{-# LANGUAGE OverloadedStrings #-} module Lykah.Style where import qualified Clay as C import Clay hiding(table) import qualified Clay.Media as M import Clay.Stylesheet import Control.Monad import Data.Function hiding ((&)) import qualified Data.Text as T import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.IO as TL import Prelude hiding (div,span) render' :: Css -> TL.Text render' = renderWith compact [] pa :: Integer -> Clay.Stylesheet.StyleM () pa = (position absolute >>).zIndex myCss :: T.Text myCss = TL.toStrict $ render myCss' smallScreen :: Css -> Css smallScreen = queryOnly M.screen [M.maxWidth $ px threshold] threshold :: Num a => a threshold = 480 -- bw = True bw = False myCss' :: Clay.Stylesheet.StyleM () myCss' = do body ? do margin nil nil nil nil fAbel -- color white fontSize $ px 16 fontWeight $ weight 300 ".clearfix" & "::after" & do clear both display block content $ stringContent "" let clf w mw = do img ? do width $ px w maxWidth $ pct 98 queryOnly M.screen [M.maxWidth $ px mw] $ float none ".imgP" & do ".halfBorder" & img ? do borderRight solid (px 1) "#ccc" borderBottom solid (px 1) "#ccc" ".border" & img ? do border solid (px 1) "#ccc" ".clearfix" & do marginBottom $ px 16 marginBottom $ px 0 img ? do float floatLeft marginRight $ px 20 marginBottom $ px 10 ".normal" & clf 300 495 ".small" & clf 220 415 ".tiny" & clf 163 265 ".right" & do textAlign $ alignSide sideRight marginRight $ px 5 display block ".keyValue" & do td ? do firstChild & do width $ px 104 verticalAlign vAlignTop a ? do paddingRight $ px 7 "#v" & do position fixed left nil >> right nil >> top nil overflow hidden height $ pct 100 video ? do pa 0 span ? do pa 1 bottom $ px 10 right $ px 10 "#content" & do zIndex 1 -- left $ px 100 marginTop $ px 100 smallScreen $ do marginTop $ px 0 marginBottom $ px 30 -- display table marginLeft auto marginRight auto maxWidth $ px 670 ".anchor" & do position relative a ? do position absolute top $ em $ -2 visibility hidden ".menu" & do fontSize $ px 20 fJul marginBottom $ px 4 let fe x = div ? ".fixedExtra" & x fe $ do paddingBottom $ px 11 paddingLeft $ px 9 display none ".title" & do cursor pointer ".fixed" ? do fe $ display block (".collapsed" &) $ fe $ display none div ? ".collapsedExtra" & do float floatLeft whiteSpace nowrap ".title" & do paddingLeft $ px 5 display none float none overflow hidden textOverflow overflowEllipsis cursor pointer ".hamburger" & do -- visibility hidden display none span ? do -- top $ px $ -2 -- left $ px $ -15 padding'' 1 4 16 4 verticalAlign $ vAlignTop fontSize $ px 12 hover & cursor pointer ".menuItem1" ? do clear clearLeft ".collapsed" ? do fontSize $ px 16 ".menuItem1" ? do clear none span ?".preload" & do position fixed left $ px $ -100 visibility hidden ".hidden" > left (px l) >> width (px w) >> height (px h)