diff options
Diffstat (limited to 'Com/MusicMeetsComics/Look.hs')
-rw-r--r-- | Com/MusicMeetsComics/Look.hs | 567 |
1 files changed, 0 insertions, 567 deletions
diff --git a/Com/MusicMeetsComics/Look.hs b/Com/MusicMeetsComics/Look.hs deleted file mode 100644 index f53955c..0000000 --- a/Com/MusicMeetsComics/Look.hs +++ /dev/null @@ -1,567 +0,0 @@ -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE NoImplicitPrelude #-} -{-# LANGUAGE GeneralizedNewtypeDeriving #-} - --- | Styles --- --- Eventually move make this mostly well-typed. Use this EDSL: --- http://fvisser.nl/clay/ -module Com.MusicMeetsComics.Look where - -import Clay -import qualified Clay.Flexbox as Flexbox -import qualified Clay.Media as Media -import qualified Clay.Render as Clay -import qualified Clay.Stylesheet as Stylesheet -import Com.MusicMeetsComics.Look.Typography as Typo -import qualified Data.Map as Map -import qualified Data.Text.Lazy as L -import Miso (Attribute, (=:), style_) -import Miso.String (MisoString, toMisoString) -import Protolude hiding ((**), (&), rem) - -main :: Css -main = do - -- bulma adjustments - input ? marginRight (px 10) <> marginBottom (px 10) - -- base - ".fixed" ? position fixed - ".clickable" ? clickable - ".row" ? do - display flex - alignItems center - justifyContent spaceBetween - a <> a # hover <> a # visited ? do - color white - textDecoration none - ".loading" ? do - display flex - justifyContent center - alignItems center - height $ vh 100 - width $ vw 100 - -- animations - ".grow" ? do - transition "all" (sec 0.2) easeInOut (sec 0.2) - ":hover" & transform (scale 1.1 1.1) - ".blur-out" ? do - position absolute - animation - "blur" - (sec 1) - easeInOut - (sec 1) - (iterationCount 1) - normal - forwards - keyframes "blur" [ (0, Clay.filter $ blur (px 0)) - , (50, Clay.filter $ blur (px 0)) - , (100, Clay.filter $ blur (px 10)) - ] - html <> body ? do - background nite - mobile $ do - overflowX hidden - width (vw 100) - -- general app wrapper stuf - ".app" ? do - display flex - justifyContent spaceBetween - alignItems stretch - flexDirection column - color white - "#hero-logo" ? zIndex (-1) - "#app-head" <> "#app-body" <> "#app-foot" ? flexGrow 1 - "#app-head" <> "#app-foot" ? do - display flex - alignItems center - flexShrink 0 - justifyContent spaceBetween - padding 0 (rem 2) 0 (rem 2) - width (pct 100) - height (px navbarHeight) - background nite - position fixed - zIndex 999 - "#app-head" ? do - alignSelf flexStart - borderBottom solid (px 3) grai - wide - top (px 0) - mobile $ noBorder <> width (vw 100) - "#app-body" ? do - display flex - desktop $ width (vw 93) - alignContent center - alignItems flexStart - justifyContent flexStart - flexDirection column - flexShrink 0 - padding (px 0) 0 0 0 - marginY $ px 74 - mobile $ flexDirection column - "#discover #app-body" ? do desktop $ marginLeft appmenuWidth - "#app-head-right" ? do - display flex - justifyContent spaceBetween - textTransform Clay.uppercase - thicc - alignItems center - width (px 200) - "#app-foot" ? do - alignSelf flexEnd - bottom (px 0) - mobile $ remove - "#app-foot-social" ? do - display flex - flexDirection column - alignSelf flexStart - ".social-icon" ? padding 0 (px 20) (px 10) 0 - "#app-foot-logo" ? do - display flex - flexDirection column - alignItems flexEnd - "#app-foot-quote" ? do - textTransform Clay.uppercase - textAlign center - -- hide app-foot-quote when it gets crowded - query Clay.all [Media.maxDeviceWidth (px 800)] $ - hide - - -- login - "#login" ? do - -- TODO: next 3 lines can be DRYed up, methinks - display flex - justifyContent center - alignItems center - alignSelf center - height (vh 100) - "#login-inner" ? do - display flex - justifyContent center - alignItems center - flexDirection column - zIndex 1 - height (vh 100) - width (px 400) - mobile $ width (vw 90) - "#login" ** ".help" ** a ? do - color white - display flex - alignItems center - flexDirection column - "#login" ** form <> "#login" ** hr ? do - width (pct 100) - "#login" ** hr ? border solid (px 1) grai - "#login" ** ".button" ? do - marginTop (px 10) - display inlineBlock - border solid (px 2) white - "#login" ** ".action" ? do - display flex - justifyContent spaceBetween - alignItems baseline - - -- choose your experience - "#choose-experience" ** "#app-body" ? do - euro <> wide - flexCenter - width (pct 100) - desktop $ marginLeft appmenuWidth <> height (vh 90) - mobile $ marginX (rem 0) <> marginTop (rem 0) <> minHeight (vh 90) - h2 ? do - thicc <> wide <> smol <> lower <> coat 2 - textAlign center - mobile $ coat 0.8 - p ? do - thicc <> coat 0.8 <> textAlign center - maxWidth (px 900) - marginAll (rem 1) - mobile $ coat 0.6 - ul ? do - display flex - flexDirection row - flexWrap Flexbox.wrap - justifyContent spaceAround - li ? do - width (px 111) - position relative - display flex - flexDirection column - textAlign center - mobile $ coat 0.6 - coat 0.8 <> clickable - divv <? do - position relative - flexCenter - flexDirection column - span <? do - position absolute - width (pct 100) - smol <> thicc - - - - -- comic player - ".comic-player" ? marginAll auto - ".comic-page" <> ".comic-page-full" ? do - width auto - marginAll auto - transform (scale 1 1) - ".comic-page" ? height (vh 90) - let ccb = ".comic-controls" ** button - ccb <> ccb # hover ? do - background nite - borderColor nite - color white - ".comic-controls-pages" ? do - justifyContent center - alignItems center - display flex - ".comic-video" |> iframe ? do - position absolute - height (pct 93) - width (pct 100) - "#close-button" ? do - euro <> wide - position fixed - cursor pointer - let z = rem 1.8 - fontSize z - lineHeight z - let m = 24 :: Double - top $ px $ navbarHeight + m - left $ px $ m - zIndex 999 - - -- zoom button and slider - "#zoom-button" ? do - position relative - let sliderY = 75 - let sliderYY = 250 - euro <> wide - input ? do - transform $ Clay.rotate (deg (-90)) - margin 0 0 (px sliderYY) 0 - position absolute - height $ px sliderY - width $ px 200 - hide - label ? do - coat 0.9 - marginBottom $ px $ 2*sliderYY - position absolute - hide - ":hover" & ".ctrl" ? visibility visible - - -- discover - "#discover" ? do - alignItems flexStart - flexDirection column - ".media-info" ? do - padding (rem 2) 0 (rem 2) (rem 2) - margin (rem 2) 0 (rem 2) (rem 2) - borderTop solid (px 1) white - borderBottom solid (px 1) white - flexDirection row - display flex - alignItems center - justifyContent spaceBetween - mobile $ do - margin (rem 2) 0 (rem 2) 0 - padding 0 0 0 (rem 0) - noBorder - width (vw 100) - flexDirection column - ".media-info-meta" ? do - Flexbox.flex 2 1 (px 0) - display flex - flexDirection row - divv # lastChild <? paddingLeft (rem 1) - mobile $ do - width (vw 90) -- this line can be commented if you want to center the meta - img ? width (px 150) - order (-1) - Flexbox.flex 1 1 (auto) - ".media-info-summary" ? do - Flexbox.flex 2 1 (px 0) - paddingRight (rem 3) - mobile $ do - marginAll (rem 1) - padding 0 0 0 (rem 0) - ".media-info-actions" ? do - Flexbox.flex 1 1 (px 132) - maxWidth (px 132) - display flex - flexDirection column - justifyContent spaceAround - mobile $ do - maxWidth (vw 100) - flexDirection row - order (1) - flexBasis auto -- initial - height (px 50) - - -- appmenu - "#appmenu" ? do - euro <> wide - fontVariant smallCaps - position fixed - height (pct 100) - display flex - justifyContent center - zIndex 99 - alignContent center - alignItems center - flexDirection column - minWidth appmenuWidth - a ? do - display flex - flexDirection column - color white - background nite - borderColor nite - a |> img ? do - width (px 22) - height (px 22) - desktop $ a |> span ? remove - mobile $ do - order 2 - flexDirection row - position fixed - bottom (px 0) - width (vw 100) - height (px 74) - background nite - justifyContent center - alignItems center - a |> span ? fontSize (rem 0.5) - - button ? margin (rem 0.5) 0 (rem 0.5) 0 - - -- feature - "#featured-comic" ? do - display flex - flexDirection column - justifyContent center - Typo.euro - height (px 411) - mobile $ do - padding (px 0) 0 0 0 - margin 0 0 (px 50) 0 - after & do - display block - position relative - background $ linearGradient (straight sideTop) - [ (setA 0 nite, (pct 0)) - , (nite, (pct 100)) ] - let h = 149 - marginTop (px (-h)) - -- without +1, the gradient is offset by 1 px in chrome - height (px (h+1)) - content blank - ".hero-original" ? do - textTransform Clay.uppercase - fontSize (rem 1.2) - ".description" ? do - width (px 400) - mobile $ remove - "#featured-banner" ? do - position relative - minHeight (px 411) - minWidth (px 1214) - mobile $ marginLeft (px (-310)) - "#featured-content" ? do - position absolute - width (pct 100) - zIndex 9 - top (px 200) -- b/c Firefox & WebKit autocalc "top" differently - mobile $ do - marginTop (px 200) - alignItems center - display flex - flexDirection column - padding (rem 0.5) (rem 0.5) (rem 0.5) (rem 0.5) - width (vw 100) - - - -- buttons - "a.wrs-button" ? do -- the "watch/read/save" button - flexCenter - height (px 36) - width (px 132) - border solid (px 2) white - rounded - color white - margin 0 (px 15) (rem 1) 0 - fontSize (rem 0.8) - fontVariant smallCaps - euro <> thicc <> wide - mobile $ do - height (px 26) - width (px 100) - margin 0 (px 5) 0 (px 5) - fontSize (rem 0.6) - let alive = backgroundColor hero <> borderColor hero <> color white - ":hover" & alive - ".saved" & alive - img ? do - marginRight (px 7) - height (px 15) - mobile $ height (px 10) - - -- - ".comic-action-menu" ? display flex <> justifyContent (JustifyContentValue "left") - - -- shelving - ".shelf" ? do - display flex - flexDirection column - justifyContent flexStart - alignItems flexStart - mobile $ do - padding (rem 0.5) (rem 0.5) (rem 0.5) (rem 0.5) - width (vw 100) - ".comic" ? do - display flex - flexDirection column - justifyContent center - textAlign center - euro - maxWidth (px 110) - img ? do - marginBottom (rem 0.5) - minHeight (px 170) - minWidth (px 110) - ".shelf-head" ? do - width (pct 100) - margin (rem 1.5) 0 (rem 1.5) 0 - borderBottom solid (px 1) white - padding (rem 0.5) 0 0.5 0 - euro <> thicc - ".shelf-body" ? do - display flex - flexDirection row - justifyContent spaceBetween - width (vw 93) - alignItems baseline - li ? padding 0 (rem 0.5) 0 (rem 0.5) - overflowY visible - star ? overflowY visible - overflowX scroll - flexWrap Flexbox.nowrap - li <? do - margin 0 (rem 1) (rem 1) 0 - Flexbox.flex 0 0 auto - -navbarHeight :: Double -navbarHeight = 74 - ---------------------------------------------------------------------------------- --- utilities ---------------------------------------------------------------------------------- - -hide :: Css -hide = visibility hidden - -remove :: Css -remove = display none - -noBorder :: Css -noBorder = border none 0 transparent - -mobile :: Css -> Css -mobile = query Clay.all [Media.maxDeviceWidth (px 500)] - -desktop :: Css -> Css -desktop = query Clay.all [Media.minDeviceWidth (px 500)] - -rounded :: Css -rounded = borderRadius (px 30) (px 30) (px 30) (px 30) - -appmenuWidth :: Size LengthUnit -appmenuWidth = (px 67) - -flexCenter :: Css -flexCenter = do - display flex - justifyContent center - justifyItems center - alignContent center - alignItems center - -blank :: Content -blank = stringContent "" - -divv :: Clay.Selector -divv = Clay.div - -marginAll :: Size a -> Css -marginAll x = margin x x x x - -marginX :: Size a -> Css -marginX n = marginLeft n <> marginRight n - -marginY :: Size a -> Css -marginY n = marginTop n <> marginBottom n - -clickable :: Css -clickable = cursor pointer - --- heroic colors --------------------------------------------------------------- - -hero :: Color -hero = rgb 241 32 32 -- #f12020 - -nite :: Color -nite = rgb 10 10 10 -- #0a0a0a - -grai :: Color -grai = rgb 221 221 221 -- #dddddd - --- runtime (client) style stuff ------------------------------------------------ - --- | Put 'Clay.Css' into a Miso-compatible style property. --- --- Allows us to use any amount of CSS written with Clay inlined in HTML or --- dynamically as JavaScript object properties. The implementation is a bit --- hacky, but works. -css :: Clay.Css -> Attribute action -css = Miso.style_ . Map.fromList . f . Clay.renderWith Clay.htmlInline [] - where - f :: L.Text -> [(MisoString, MisoString)] - f t = L.splitOn ";" t - <&> L.splitOn ":" - <&> \(x:y) -> (toMisoString x, toMisoString $ L.intercalate ":" y) - -inlineCss :: Css -> MisoString -inlineCss = toMisoString . render - -type Style = Map MisoString MisoString - -red :: MisoString -red = "#f12020" - -bold :: Style -bold = "font-weight" =: "bold" - -condensed :: Style -condensed = "font-stretch" =: "condensed" - -expanded :: Style -expanded = "font-stretch" =: "expanded" - -uppercase :: Style -uppercase = "text-transform" =: "uppercase" - ---------------------------------------------------------------------------------- --- upstream this to Clay ---------------------------------------------------------------------------------- - - -newtype JustifyItemsValue = JustifyItemsValue Value - deriving (Val, Other, Inherit, Center, FlexEnd - , FlexStart, SpaceAround, SpaceBetween) - -justifyItems :: JustifyItemsValue -> Css -justifyItems = Stylesheet.key "justify-items" |