Main.hs
» see on github
module Main where
import Clay hiding (i, s, id)
import Control.Monad
import Data.Monoid
import Prelude hiding (div, span)
import System.Environment
import qualified Clay.Media as Media
import qualified Data.Text.Lazy.IO as Text
import Codeblock
import Common
import Header
main :: IO ()
main =
do args <- getArgs
case args of
"compact" : _
-> Text.putStr (renderWith compact theStylesheet)
_ -> putCss theStylesheet
---------------------------------------------------------------------------
theStylesheet :: Css
theStylesheet =
do
body ?
do sym margin 0
sym padding 0
".index" & "#container" ?
paddingTop 360
theSections
header ? theHeader
footer ? theFooter
---------------------------------------------------------------------------
theSections :: Css
theSections =
do section ?
do boxSizing borderBox
[paddingTop, paddingBottom] `forM_` ($ 60)
borderTop solid (px 1) transparent
div <?
do
centered
sym2 padding 0 (px 10)
".one-col" ? oneColumn
".two-col" ? oneOrTwoColumns
codeblocks
textblocks
(section <> footer) # nthChild "odd" ?
backgroundColor trdColor
oneColumn :: Css
oneColumn =
do width (px 550)
boxSizing borderBox
oneOrTwoColumns :: Css
oneOrTwoColumns =
do query Clay.all [Media.minWidth 800] twoColumns
query Clay.all [Media.maxWidth 800] oneColumn
twoColumns :: Css
twoColumns =
do
div <?
do width (pct 50)
boxSizing borderBox
column "1" floatLeft paddingRight
column "2" floatRight paddingLeft
br ? clear both
where column i side pad =
div # nthChild i <?
do float side
pad (px 30)
---------------------------------------------------------------------------
textblocks :: Css
textblocks = ".text" ?
do textFont
anchors
h3 ?
do textTransform uppercase
color (sndColor -. 80)
fontWeight bold
ul ? paddingLeft (px 20)
code ? color "#ff4422"
".goto" ? paddingLeft (px 25)
---------------------------------------------------------------------------
theFooter :: Css
theFooter = div <?
do centered
width (px 550)
textFont
fontSize (px 12)
textTransform uppercase
textAlign (alignSide sideCenter)
color (setA 150 black)
sym2 padding (px 10) 0
Common.hs
» see on github
module Common where
import Clay
fstColor, sndColor, trdColor :: Color
fstColor = rgb 255 160 50
sndColor = rgb 56 135 190
trdColor = "#f8f8f8"
---------------------------------------------------------------------------
textFont, headerFont, codeFont, anchors :: Css
textFont =
do fontSize (px 20)
lineHeight (px 30)
fontFamily ["Europa", "Helvetica"] [sansSerif]
textRendering optimizeLegibility
color "#222"
headerFont =
do textFont
lineHeight inherit
codeFont =
do fontSize (px 16)
fontFamily ["Monaco", "Courier New"] [monospace]
lineHeight (ex 2.6)
textRendering optimizeLegibility
anchors =
a ? do textDecoration none
transitions [ ("background-color" , sec 0.5, ease, sec 0)
, ("color" , sec 0.2, ease, sec 0)
]
backgroundColor (setA 0 yellow)
hover & backgroundColor (setA 60 yellow)
color sndColor
hover & color black
---------------------------------------------------------------------------
centered :: Css
centered =
do width (px 800)
boxSizing borderBox
sym2 margin 0 auto
Codeblock.hs
» see on github
module Codeblock where
import Prelude hiding (div)
import Clay
import Common (codeFont, sndColor)
codeblocks :: Css
codeblocks =
do isCode ?
do
boxSizing borderBox
sym borderRadius (px 2)
overflowX auto
sym padding 20
marginTop (px 60)
marginBottom (px 60)
boxShadow 0 0 (px 60)
(setA 30 black)
pre ?
do sym margin 0
codeFont
".haskell" & haskell
".shell" & haskell
".css" & css
isCode |+ isCode ? marginTop (px (-40))
isCode :: Selector
isCode = div # ".code"
---------------------------------------------------------------------------
haskell :: Css
haskell =
do background (sndColor -. 150)
pre ?
do color (setA 160 white)
".Comment" ? color (setA 170 lime)
".ConId" ? color (sndColor +. 100)
".Function" ? color white
".Keyword" ? color (sndColor +. 20)
".Number" ? color (setG 100 orange)
".String" ? color (setG 40 red)
".Symbol" ? color orange
---------------------------------------------------------------------------
css :: Css
css =
do backgroundColor none
pre ?
do fontSize (px 14)
color "#456"
".Number" ? color red
".Property" ? color black
".Selector" ? color (sndColor -. 60)
".String" ? color red
".Symbol" ? color (orange -. 60)
Header.hs
» see on github
module Header where
import Clay hiding (i, s, id)
import Control.Monad
import Data.Monoid
import Prelude hiding (div, span)
import Common
---------------------------------------------------------------------------
theHeader :: Css
theHeader =
do
position fixed
top (px 0)
left (px 0)
right (px 0)
height (px 240)
background (vGradient (fstColor -. 80) (fstColor +. 20))
headerFont
before & interlaced
nav ? theMenu
"#logo" <? theLogo
interlaced :: Css
interlaced =
do mapM_ ($ px 0)
[ top
, bottom
, left
, right
]
position absolute
content (stringContent "")
pointerEvents none
backgroundSize (pct 100 `by` px 5)
backgroundImage ( repeatingLinearGradient (straight sideTop)
[ ( setA 0 white, 0)
, ( setA 20 white, 50)
, ( setA 0 white, 100)
]
)
---------------------------------------------------------------------------
theMenu :: Css
theMenu =
do let h = 60
boxSizing borderBox
position absolute
left 0
right 0
bottom (px (-h))
height (px h)
background (setA 249 white)
boxShadow 0 0 (px 60) (setA 20 black)
lineHeight (px h)
fontSize (px 19)
textTransform uppercase
div <?
do centered
width (px 530)
textAlign (alignSide sideCenter)
a ? do paddingRight (px 5)
transition "color" (sec 0.4) ease (sec 0)
textDecoration none
color sndColor
lastOfType & paddingRight (px 0)
hover & color black
---------------------------------------------------------------------------
theLogo :: Css
theLogo =
do centered
width (px 550)
paddingTop (px 40)
height (pct 100)
overflow hidden
backgroundImage $
radialGradient sideCenter (ellipse closestSide)
[ ( setA 150 yellow , 0 )
, ( setA 25 yellow , 50 )
, ( setA 0 yellow , 75 )
]
a ?
do textDecoration none
color inherit
h1 <> h2 ?
do textTransform uppercase
textAlign (alignSide sideCenter)
sym margin 0
h1 ?
do fontSize (px 90)
color (setA 200 white)
textShadow 0 0 (px 20) (setA 200 (fstColor -. 80))
fontWeight normal
letterSpacing (em 0.40)
span # ".a" ? letterSpacing (em 0.36)
span # ".y" ? letterSpacing (em 0.00)
h2 ?
do fontSize (px 35)
color (setA 120 black)
letterSpacing (em 0.3)
a # hover ? color (setA 220 black)