Initial pinealservo.com hakyll site
commit
46d8678476
|
@ -0,0 +1,5 @@
|
||||||
|
_cache
|
||||||
|
*~
|
||||||
|
site.hi
|
||||||
|
site.o
|
||||||
|
site
|
|
@ -0,0 +1,5 @@
|
||||||
|
---
|
||||||
|
title: About this site
|
||||||
|
---
|
||||||
|
|
||||||
|
There's not much to say yet.
|
|
@ -0,0 +1,7 @@
|
||||||
|
---
|
||||||
|
title: Contact
|
||||||
|
---
|
||||||
|
|
||||||
|
You can reach me most easily via email, <levipearson@gmail.com>.
|
||||||
|
|
||||||
|
I occasionally follow Facebook and Google+ as well.
|
|
@ -0,0 +1,341 @@
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
import Clay hiding (div)
|
||||||
|
import Clay.Stylesheet
|
||||||
|
import Data.Monoid ((<>))
|
||||||
|
import Data.Text (pack)
|
||||||
|
import Prelude hiding ((**))
|
||||||
|
|
||||||
|
import qualified Data.List as L
|
||||||
|
|
||||||
|
data CalcSize = Px Integer
|
||||||
|
| Pt Double
|
||||||
|
| Em Double
|
||||||
|
| Rem Double
|
||||||
|
| Ex Double
|
||||||
|
| Zero
|
||||||
|
deriving (Eq, Ord)
|
||||||
|
|
||||||
|
instance Num CalcSize where
|
||||||
|
fromInteger i | j == 0 = Zero
|
||||||
|
| j < 0 = Zero
|
||||||
|
| otherwise = Px j
|
||||||
|
where j = fromIntegral i
|
||||||
|
|
||||||
|
Zero + b = b
|
||||||
|
a + Zero = a
|
||||||
|
Px a + Px b = Px $ a + b
|
||||||
|
Pt a + Pt b = Pt $ a + b
|
||||||
|
Em a + Em b = Em $ a + b
|
||||||
|
Rem a + Rem b = Rem $ a + b
|
||||||
|
Ex a + Ex b = Ex $ a + b
|
||||||
|
_ + _ = error "Can't add sizes of different kinds"
|
||||||
|
|
||||||
|
Zero * b = b
|
||||||
|
a * Zero = a
|
||||||
|
Px a * Px b = Px $ a * b
|
||||||
|
Pt a * Pt b = Pt $ a * b
|
||||||
|
Em a * Em b = Em $ a * b
|
||||||
|
Rem a * Rem b = Rem $ a * b
|
||||||
|
Ex a * Ex b = Ex $ a * b
|
||||||
|
_ * _ = error "Can't multiply sizes of different kinds"
|
||||||
|
|
||||||
|
abs Zero = Zero
|
||||||
|
abs (Px i) = Px $ abs i
|
||||||
|
abs (Pt d) = Pt $ abs d
|
||||||
|
abs (Em d) = Em $ abs d
|
||||||
|
abs (Rem d) = Rem $ abs d
|
||||||
|
abs (Ex d) = Ex $ abs d
|
||||||
|
|
||||||
|
signum Zero = Zero
|
||||||
|
signum (Px i) = Px $ signum i
|
||||||
|
signum (Pt d) = Pt $ signum d
|
||||||
|
signum (Em d) = Em $ signum d
|
||||||
|
signum (Rem d) = Rem $ signum d
|
||||||
|
signum (Ex d) = Ex $ signum d
|
||||||
|
|
||||||
|
times :: Integer -> CalcSize -> CalcSize
|
||||||
|
i `times` Zero = Zero
|
||||||
|
i `times` Px b = Px $ i * b
|
||||||
|
i `times` Pt b = Pt $ (fromIntegral i) * b
|
||||||
|
i `times` Em b = Em $ (fromIntegral i) * b
|
||||||
|
i `times` Rem b = Rem $ (fromIntegral i) * b
|
||||||
|
i `times` Ex b = Ex $ (fromIntegral i) * b
|
||||||
|
|
||||||
|
toSize :: CalcSize -> Size Abs
|
||||||
|
toSize s = case s of
|
||||||
|
Zero -> nil
|
||||||
|
Px i -> px i
|
||||||
|
Pt d -> pt d
|
||||||
|
Em d -> em d
|
||||||
|
Rem d -> em d -- todo: Add rem to Clay.Size
|
||||||
|
Ex d -> ex d
|
||||||
|
|
||||||
|
perct :: CalcSize -> CalcSize -> Double
|
||||||
|
perct Zero b = 0
|
||||||
|
perct a Zero = error "Division by zero"
|
||||||
|
perct (Px a) (Px b) = (fromIntegral a) / (fromIntegral b) * 100
|
||||||
|
perct (Pt a) (Pt b) = a / b * 100
|
||||||
|
perct (Em a) (Em b) = a / b * 100
|
||||||
|
perct (Rem a) (Rem b) = a / b * 100
|
||||||
|
perct (Ex a) (Ex b) = a / b * 100
|
||||||
|
perct _ _ = error "Can't take percentage of different kinds"
|
||||||
|
|
||||||
|
percentage :: CalcSize -> CalcSize -> Size Rel
|
||||||
|
percentage a b = pct $ perct a b
|
||||||
|
|
||||||
|
data LayoutSettings =
|
||||||
|
Layout { totalColumns :: Integer
|
||||||
|
, columnWidth :: CalcSize
|
||||||
|
, gutterWidth :: CalcSize
|
||||||
|
, gridPadding :: CalcSize
|
||||||
|
}
|
||||||
|
|
||||||
|
data ColSpec = Full
|
||||||
|
| Next Integer Integer
|
||||||
|
| Final Integer Integer
|
||||||
|
|
||||||
|
columnsWidth cols =
|
||||||
|
let gutter = gutterWidth def
|
||||||
|
colWidth = columnWidth def
|
||||||
|
baseWidth = cols `times` colWidth
|
||||||
|
in
|
||||||
|
if cols >= 1
|
||||||
|
then baseWidth + ((cols - 1) `times` gutter)
|
||||||
|
else baseWidth
|
||||||
|
|
||||||
|
relativeWidth width ctx =
|
||||||
|
percentage width (columnsWidth ctx)
|
||||||
|
|
||||||
|
widthWithGridPadding cols =
|
||||||
|
let width = columnsWidth cols
|
||||||
|
basePad = gridPadding def
|
||||||
|
in width + (2 `times` basePad)
|
||||||
|
|
||||||
|
container =
|
||||||
|
let pad = gridPadding def
|
||||||
|
width = widthWithGridPadding $ totalColumns def
|
||||||
|
in do
|
||||||
|
maxWidth $ toSize width
|
||||||
|
paddingLeft $ toSize pad
|
||||||
|
paddingRight $ toSize pad
|
||||||
|
marginLeft auto
|
||||||
|
marginRight auto
|
||||||
|
|
||||||
|
colSpan spec = case spec of
|
||||||
|
Full -> do
|
||||||
|
clear both
|
||||||
|
Next n m ->
|
||||||
|
let gutter = gutterWidth def
|
||||||
|
colsWidth = columnsWidth n
|
||||||
|
rw = relativeWidth colsWidth m
|
||||||
|
rm = percentage gutter (columnsWidth m)
|
||||||
|
in do
|
||||||
|
width rw
|
||||||
|
float floatLeft
|
||||||
|
marginRight rm
|
||||||
|
Final n m ->
|
||||||
|
let colsWidth = columnsWidth n
|
||||||
|
rw = relativeWidth colsWidth m
|
||||||
|
in do
|
||||||
|
width rw
|
||||||
|
float floatRight
|
||||||
|
marginRight nil
|
||||||
|
|
||||||
|
push spec = case spec of
|
||||||
|
Next n m ->
|
||||||
|
let gutter = gutterWidth def
|
||||||
|
colsWidth = columnsWidth n
|
||||||
|
rw = relativeWidth colsWidth m
|
||||||
|
in do
|
||||||
|
marginLeft rw
|
||||||
|
_ -> error "Bad push spec"
|
||||||
|
|
||||||
|
pull spec = case spec of
|
||||||
|
Next n m ->
|
||||||
|
let gutter = gutterWidth def
|
||||||
|
colsWidth = columnsWidth n
|
||||||
|
rw = relativeWidth colsWidth m
|
||||||
|
in do
|
||||||
|
marginLeft (0 - rw)
|
||||||
|
_ -> error "Bad pull spec"
|
||||||
|
|
||||||
|
|
||||||
|
data GridShow = Pad | Col | Gut
|
||||||
|
showGrid =
|
||||||
|
let begin = "-moz-linear-gradient(left center, "
|
||||||
|
gutColor = " transparent "
|
||||||
|
padColor = " transparent "
|
||||||
|
colColor = " rgba(255, 254, 251, 0.5) "
|
||||||
|
totalWidth = widthWithGridPadding $ totalColumns def
|
||||||
|
padWidth = perct (gridPadding def) totalWidth
|
||||||
|
colWidth = perct (columnWidth def) totalWidth
|
||||||
|
gutWidth = perct (gutterWidth def) totalWidth
|
||||||
|
colCount = fromIntegral (totalColumns def)
|
||||||
|
cols = Pad : L.intersperse Gut (replicate colCount Col)
|
||||||
|
go xs out s = case xs of
|
||||||
|
[] -> begin ++ out ++ padColor ++ (show s) ++ "%, " ++ padColor ++ "100%)"
|
||||||
|
Pad:xs ->
|
||||||
|
let n = padWidth + s
|
||||||
|
v = padColor ++ (show s) ++ "%, " ++ padColor ++ (show n) ++ "% ,"
|
||||||
|
in go xs (out ++ v) n
|
||||||
|
Col:xs ->
|
||||||
|
let n = colWidth + s
|
||||||
|
v = colColor ++ (show s) ++ "%, " ++ colColor ++ (show n) ++ "% ,"
|
||||||
|
in go xs (out ++ v) n
|
||||||
|
Gut:xs ->
|
||||||
|
let n = gutWidth + s
|
||||||
|
v = gutColor ++ (show s) ++ "%, " ++ gutColor ++ (show n) ++ "% ,"
|
||||||
|
in go xs (out ++ v) n
|
||||||
|
in pack $ go cols "" 0
|
||||||
|
|
||||||
|
showBaseline n = do
|
||||||
|
backgroundSize $ (px 40) `by` (px n)
|
||||||
|
backgroundImage $ repeatingLinearGradient (angular $ deg 0) [("#111", px 0)
|
||||||
|
,("#111", px 1)
|
||||||
|
,(transparent, px 1)
|
||||||
|
,(transparent, px n)]
|
||||||
|
height (pct 100)
|
||||||
|
width (pct 100)
|
||||||
|
opacity 0.75
|
||||||
|
position absolute
|
||||||
|
top nil
|
||||||
|
left nil
|
||||||
|
zIndex (-4)
|
||||||
|
|
||||||
|
|
||||||
|
defaultFontPx = 16
|
||||||
|
|
||||||
|
pxRatio x y = (fromIntegral x) / (fromIntegral y)
|
||||||
|
emFromRatio elemPx fontPx = em $ pxRatio elemPx fontPx
|
||||||
|
|
||||||
|
selectors :: [Selector] -> Selector
|
||||||
|
selectors = foldl1 (<>)
|
||||||
|
|
||||||
|
setFontSize x = do
|
||||||
|
let line = 1 + x `div` baselinePx
|
||||||
|
fontSize $ emFromRatio x defaultFontPx
|
||||||
|
lineHeight $ emFromRatio (line * baselinePx) x
|
||||||
|
|
||||||
|
{- Insert this into main for layout-debugging grids
|
||||||
|
|
||||||
|
body ? (showBaseline baselinePx)
|
||||||
|
"#container" ? do
|
||||||
|
container
|
||||||
|
backgroundColor "#EEE8D5"
|
||||||
|
"background-image" -: showGrid
|
||||||
|
|
||||||
|
-}
|
||||||
|
|
||||||
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
|
def =
|
||||||
|
Layout { totalColumns = 12
|
||||||
|
, columnWidth = Em 3
|
||||||
|
, gutterWidth = Em 1
|
||||||
|
, gridPadding = Em 1
|
||||||
|
}
|
||||||
|
|
||||||
|
primary = "#033E6B"
|
||||||
|
accent1 = "#FFB400"
|
||||||
|
accent2 = "#A63F00"
|
||||||
|
|
||||||
|
bodyCopyColor = "#444"
|
||||||
|
|
||||||
|
baselinePx = 24
|
||||||
|
baseFontPx = 16
|
||||||
|
headingColor = primary
|
||||||
|
|
||||||
|
main = putCss $ do
|
||||||
|
typography
|
||||||
|
|
||||||
|
"#container" ? do
|
||||||
|
container
|
||||||
|
|
||||||
|
"#header" ? do
|
||||||
|
push $ Next 1 12
|
||||||
|
colSpan $ Next 11 12
|
||||||
|
|
||||||
|
"#navigation" ? (colSpan $ Final 2 12)
|
||||||
|
|
||||||
|
"#content" ? do
|
||||||
|
push $ Next 1 12
|
||||||
|
colSpan $ Next 9 12
|
||||||
|
|
||||||
|
"#footer" ? do
|
||||||
|
push $ Next 1 12
|
||||||
|
colSpan $ Next 11 12
|
||||||
|
|
||||||
|
typography = do
|
||||||
|
-- Reset the padding/margin on all elements so we can set up a vertical
|
||||||
|
-- rhythm on a baseline grid
|
||||||
|
star ? do
|
||||||
|
sym margin nil
|
||||||
|
sym padding nil
|
||||||
|
|
||||||
|
body ? do
|
||||||
|
fontFamily ["PT Sans", "Verdana"] [sansSerif]
|
||||||
|
textRendering optimizeLegibility
|
||||||
|
color bodyCopyColor
|
||||||
|
a ? color primary
|
||||||
|
lineHeight $ emFromRatio baselinePx defaultFontPx
|
||||||
|
|
||||||
|
"#logo" ? do
|
||||||
|
paddingTop $ px (1*baselinePx)
|
||||||
|
a ? do
|
||||||
|
setFontSize 75
|
||||||
|
fontFamily ["Orbitron"] [sansSerif]
|
||||||
|
fontWeight (other "700")
|
||||||
|
textDecoration none
|
||||||
|
color headingColor
|
||||||
|
|
||||||
|
ul |> li ? do
|
||||||
|
paddingLeft $ em (-0.7)
|
||||||
|
textIndent $ indent (em (-0.7))
|
||||||
|
":before" & do
|
||||||
|
content $ stringContent "- "
|
||||||
|
color accent2
|
||||||
|
a ? do
|
||||||
|
textDecoration none
|
||||||
|
|
||||||
|
"#navigation" ** li ? do
|
||||||
|
setFontSize 24
|
||||||
|
fontFamily ["Oswald"] [sansSerif]
|
||||||
|
fontWeight (other "400")
|
||||||
|
|
||||||
|
".info" ? do
|
||||||
|
color accent2
|
||||||
|
|
||||||
|
"#footer" ** p ? do
|
||||||
|
color accent2
|
||||||
|
|
||||||
|
selectors [ p, ".info", "#logo" ] ? do
|
||||||
|
setFontSize baseFontPx
|
||||||
|
|
||||||
|
selectors [ p, ".info", "#logo" ] ? do
|
||||||
|
marginBottom $ px baselinePx
|
||||||
|
|
||||||
|
selectors [ h1, h2, h3] ? do
|
||||||
|
fontFamily ["Oswald"] [sansSerif]
|
||||||
|
fontWeight (other "400")
|
||||||
|
color headingColor
|
||||||
|
|
||||||
|
h1 ? do
|
||||||
|
setFontSize 42
|
||||||
|
let btw = 3
|
||||||
|
ptw = 6
|
||||||
|
paddingTop $ px ptw
|
||||||
|
borderTop solid (px btw) accent1
|
||||||
|
marginBottom $ px (baselinePx - btw - ptw)
|
||||||
|
|
||||||
|
h2 ? do
|
||||||
|
setFontSize 32
|
||||||
|
marginBottom $ px baselinePx
|
||||||
|
|
||||||
|
h3 ? do
|
||||||
|
setFontSize 24
|
||||||
|
|
||||||
|
ul <> ol ? do
|
||||||
|
marginLeft $ emFromRatio baselinePx baseFontPx
|
||||||
|
marginBottom $ px baselinePx
|
||||||
|
"list-style-type" -: "none"
|
||||||
|
|
|
@ -0,0 +1,130 @@
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
import Clay
|
||||||
|
import Clay.Size
|
||||||
|
import Data.Monoid
|
||||||
|
import Data.Text (Text)
|
||||||
|
import Prelude hiding ((**))
|
||||||
|
|
||||||
|
selectors :: [Selector] -> Selector
|
||||||
|
selectors = foldl1 (<>)
|
||||||
|
|
||||||
|
pseudoNot :: Text -> Refinement
|
||||||
|
pseudoNot n = func "not" [n]
|
||||||
|
|
||||||
|
main = putCss $ do
|
||||||
|
html5display
|
||||||
|
baseStyle
|
||||||
|
linksStyle
|
||||||
|
typographyStyle
|
||||||
|
embeddedContentStyle
|
||||||
|
formStyle
|
||||||
|
tableStyle
|
||||||
|
|
||||||
|
html5display = do
|
||||||
|
selectors [ article, aside, details, figcaption, figure, footer
|
||||||
|
, header, hgroup, nav, section, summary, "main"
|
||||||
|
] ? display block
|
||||||
|
|
||||||
|
selectors [ audio, canvas, video ] ? display inlineBlock
|
||||||
|
|
||||||
|
audio # pseudoNot "[controls]" ? do
|
||||||
|
display none
|
||||||
|
height $ px 0
|
||||||
|
|
||||||
|
star # "hidden" <> "template" ? display none
|
||||||
|
|
||||||
|
baseStyle = do
|
||||||
|
html ? do
|
||||||
|
fontFamily [] [sansSerif]
|
||||||
|
"-ms-text-size-adjust" -: "100%"
|
||||||
|
"-webkit-text-size-adjust" -: "100%"
|
||||||
|
body ? margin (px 0) (px 0) (px 0) (px 0)
|
||||||
|
|
||||||
|
linksStyle = do
|
||||||
|
a ? background transparent
|
||||||
|
a # focus ? do
|
||||||
|
outlineStyle dotted
|
||||||
|
"outline-width" -: "thin"
|
||||||
|
a # active <> a # hover ?
|
||||||
|
outlineWidth (px 0)
|
||||||
|
|
||||||
|
typographyStyle = do
|
||||||
|
h1 ? do
|
||||||
|
fontSize (em 2)
|
||||||
|
margin (em 0.67) (em 0) (em 0) (em 0.67)
|
||||||
|
abbr # title ? do
|
||||||
|
borderBottomWidth (px 1)
|
||||||
|
borderBottomStyle dotted
|
||||||
|
b <> strong ? fontWeight bold
|
||||||
|
dfn ? fontStyle italic
|
||||||
|
hr ? do
|
||||||
|
boxSizing contentBox
|
||||||
|
height (px 0)
|
||||||
|
mark ? do
|
||||||
|
backgroundColor (rgb 0xf 0xf 0x0)
|
||||||
|
color (rgb 0 0 0)
|
||||||
|
selectors [code, kbd, pre, samp] ? do
|
||||||
|
fontFamily [] [monospace, serif]
|
||||||
|
fontSize (em 1)
|
||||||
|
pre ? whiteSpace preWrap
|
||||||
|
"q" -: "quotes \"\\201C\" \"\\201D\" \"\\2018\" \"\\2019\""
|
||||||
|
small ? fontSize (pct 80)
|
||||||
|
sub <> sup ? do
|
||||||
|
fontSize (pct 75)
|
||||||
|
lineHeight (px 0)
|
||||||
|
position relative
|
||||||
|
"vertical-align" -: "baseline"
|
||||||
|
sub ? top (em (-0.5))
|
||||||
|
sup ? bottom (em (-0.25))
|
||||||
|
|
||||||
|
embeddedContentStyle = do
|
||||||
|
img ? borderWidth (px 0)
|
||||||
|
"svg" # pseudoNot ":root" ? overflow hidden
|
||||||
|
figure ? margin (px 0) (px 0) (px 0) (px 0)
|
||||||
|
|
||||||
|
formStyle = do
|
||||||
|
fieldset ? do
|
||||||
|
borderWidth (px 1)
|
||||||
|
borderStyle solid
|
||||||
|
borderColor (rgb 0xc0 0xc0 0xc0)
|
||||||
|
margin (px 0) (px 2) (px 2) (px 0)
|
||||||
|
padding (em 0.35) (em 0.625) (em 0.75) (em 0)
|
||||||
|
legend ? do
|
||||||
|
borderWidth (px 0)
|
||||||
|
padding (px 0) (px 0) (px 0) (px 0)
|
||||||
|
selectors [button, input, select, textarea] ? do
|
||||||
|
"font-family" -: "inherit"
|
||||||
|
fontSize (pct 100)
|
||||||
|
margin (px 0) (px 0) (px 0) (px 0)
|
||||||
|
button <> input ? lineHeight normal
|
||||||
|
button <> select ? textTransform none
|
||||||
|
selectors [ button, html ** input # ("type" @= "button")
|
||||||
|
, input # ("type" @= "reset")
|
||||||
|
, input # ("type" @= "submit")
|
||||||
|
] ? do
|
||||||
|
"-webkit-appearance" -: "button"
|
||||||
|
"cursor" -: "pointer"
|
||||||
|
button # "@disabled" <> html ** input # "@disabled" ? do
|
||||||
|
"cursor" -: "default"
|
||||||
|
input # ("type" @= "checkbox") <> input # ("type" @= "radio") ? do
|
||||||
|
boxSizing borderBox
|
||||||
|
padding (px 0) (px 0) (px 0) (px 0)
|
||||||
|
input # ("type" @= "search") ? do
|
||||||
|
"-webkit-appearance" -: "textfield"
|
||||||
|
"-moz-box-sizing" -: "content-box"
|
||||||
|
"-webkit-box-sizing" -: "content-box"
|
||||||
|
"box-sizing" -: "content-box"
|
||||||
|
input # ("type" @= "search") # "::-webkit-search-cancel-button"
|
||||||
|
<> input # ("type" @= "search") # "::-webkit-search-decoration" ? do
|
||||||
|
"-webkit-appearance" -: "none"
|
||||||
|
button # "::-moz-focus-inner" <> input # "::-moz-focus-inner" ? do
|
||||||
|
borderWidth (px 0)
|
||||||
|
padding (px 0) (px 0) (px 0) (px 0)
|
||||||
|
textarea ? do
|
||||||
|
overflow auto
|
||||||
|
"vertical-align" -: "top"
|
||||||
|
|
||||||
|
tableStyle = table ? do
|
||||||
|
"border-collapse" -: "collapse"
|
||||||
|
"border-spacing" -: "0px"
|
||||||
|
|
|
@ -0,0 +1,4 @@
|
||||||
|
$for(posts)$
|
||||||
|
<h1>$title$</h1>
|
||||||
|
$body$
|
||||||
|
$endfor$
|
|
@ -0,0 +1,32 @@
|
||||||
|
---
|
||||||
|
title: Hello, world
|
||||||
|
---
|
||||||
|
|
||||||
|
It's about time I had a blog/journal/mental dumping ground again, and
|
||||||
|
getting this set up was a nice little exercise in system
|
||||||
|
administration and a little bit of Haskell coding.
|
||||||
|
|
||||||
|
I mention system administration because this is running on a system
|
||||||
|
with a version of Debian Linux installed that has been continuously
|
||||||
|
upgraded since around 2001. It was both slightly broken and very
|
||||||
|
crufty, but I was able to get plenty of space cleared and get
|
||||||
|
everything up-to-date with few issues.
|
||||||
|
|
||||||
|
And I mention Haskell because I'm using two Haskell programs as part
|
||||||
|
of the infrastructure of this site. One is the site engine itself,
|
||||||
|
[Hakyll][1]. It's a customizable build tool that translates from
|
||||||
|
various markup formats to HTML, then assembles all the site's pieces
|
||||||
|
together.
|
||||||
|
|
||||||
|
The second Haskell program I'm using the the [Clay][2] CSS generator,
|
||||||
|
which lets me build the CSS rules in a Haskell program in a CSS-like
|
||||||
|
DSL. A short program generates both a flexible semantic grid layout
|
||||||
|
and a baseline grid for managing the vertical rhythm of the text. I am
|
||||||
|
not a master page designer by any means, but I'm happy with the
|
||||||
|
result.
|
||||||
|
|
||||||
|
I will share more details about these tools, along with other things
|
||||||
|
I've been working on, in entries to follow.
|
||||||
|
|
||||||
|
[1]: http://jaspervdj.be/hakyll/ "Hakyll's Home Page"
|
||||||
|
[2]: http://fvisser.nl/clay/ "Clay's Home Page"
|
|
@ -0,0 +1,87 @@
|
||||||
|
--------------------------------------------------------------------------------
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
import Data.Monoid (mappend)
|
||||||
|
import Data.Default
|
||||||
|
import Hakyll
|
||||||
|
|
||||||
|
-- Configuration
|
||||||
|
|
||||||
|
frontPagePosts = 5
|
||||||
|
|
||||||
|
hakyllConfig :: Configuration
|
||||||
|
hakyllConfig = def { deployCommand = "cd _site; cp -R * /var/www/pinealservo.com" }
|
||||||
|
|
||||||
|
--------------------------------------------------------------------------------
|
||||||
|
main :: IO ()
|
||||||
|
main = hakyllWith hakyllConfig $ do
|
||||||
|
match "images/*" $ do
|
||||||
|
route idRoute
|
||||||
|
compile copyFileCompiler
|
||||||
|
|
||||||
|
match "css/*.css" $ do
|
||||||
|
route idRoute
|
||||||
|
compile compressCssCompiler
|
||||||
|
|
||||||
|
match "css/*.hs" $ do
|
||||||
|
route $ setExtension "css"
|
||||||
|
compile $ getResourceString >>= withItemBody (unixFilter "runhaskell" [])
|
||||||
|
>>= return . fmap compressCss
|
||||||
|
match "*.markdown" $ do
|
||||||
|
route $ setExtension "html"
|
||||||
|
compile $ pandocCompiler
|
||||||
|
>>= loadAndApplyTemplate "templates/default.html" defaultContext
|
||||||
|
>>= relativizeUrls
|
||||||
|
|
||||||
|
match "posts/*" $ do
|
||||||
|
route $ setExtension "html"
|
||||||
|
compile $ pandocCompiler
|
||||||
|
>>= loadAndApplyTemplate "templates/post.html" postCtx
|
||||||
|
>>= saveSnapshot "content"
|
||||||
|
>>= loadAndApplyTemplate "templates/default.html" postCtx
|
||||||
|
>>= relativizeUrls
|
||||||
|
|
||||||
|
create ["archive.html"] $ do
|
||||||
|
route idRoute
|
||||||
|
compile $ do
|
||||||
|
posts <- recentFirst =<< loadAll "posts/*"
|
||||||
|
let archiveCtx =
|
||||||
|
listField "posts" postCtx (return posts) `mappend`
|
||||||
|
constField "title" "Archives" `mappend`
|
||||||
|
defaultContext
|
||||||
|
|
||||||
|
makeItem ""
|
||||||
|
>>= loadAndApplyTemplate "templates/archive.html" archiveCtx
|
||||||
|
>>= loadAndApplyTemplate "templates/default.html" archiveCtx
|
||||||
|
>>= relativizeUrls
|
||||||
|
|
||||||
|
|
||||||
|
match "index.html" $ do
|
||||||
|
route idRoute
|
||||||
|
compile $ do
|
||||||
|
allPosts <- fmap (take frontPagePosts) . recentFirst
|
||||||
|
=<< loadAllSnapshots "posts/*" "content"
|
||||||
|
let indexCtx =
|
||||||
|
listField "posts" postCtx (return allPosts) `mappend`
|
||||||
|
defaultNoTitleContext
|
||||||
|
|
||||||
|
getResourceBody
|
||||||
|
>>= applyAsTemplate indexCtx
|
||||||
|
>>= loadAndApplyTemplate "templates/default.html" indexCtx
|
||||||
|
>>= relativizeUrls
|
||||||
|
|
||||||
|
match "templates/*" $ compile templateCompiler
|
||||||
|
|
||||||
|
|
||||||
|
--------------------------------------------------------------------------------
|
||||||
|
defaultNoTitleContext :: Context String
|
||||||
|
defaultNoTitleContext =
|
||||||
|
bodyField "body" `mappend`
|
||||||
|
metadataField `mappend`
|
||||||
|
urlField "url" `mappend`
|
||||||
|
pathField "path" `mappend`
|
||||||
|
missingField
|
||||||
|
|
||||||
|
postCtx :: Context String
|
||||||
|
postCtx =
|
||||||
|
dateField "date" "%B %e, %Y" `mappend`
|
||||||
|
defaultContext
|
|
@ -0,0 +1,2 @@
|
||||||
|
<p>Here you can find all my previous posts:</p>
|
||||||
|
$partial("templates/post-list.html")$
|
|
@ -0,0 +1,43 @@
|
||||||
|
<!DOCTYPE html>
|
||||||
|
<html lang="en">
|
||||||
|
<head>
|
||||||
|
<link href='http://fonts.googleapis.com/css?family=Orbitron:700|PT+Sans|Oswald:400,300' rel='stylesheet' type='text/css'>
|
||||||
|
<meta charset="utf-8" />
|
||||||
|
<title>PinealServo$if(title)$ - $title$$endif$</title>
|
||||||
|
<link rel="stylesheet" href="/css/layout.css" />
|
||||||
|
<!--[if IE]>
|
||||||
|
<script src="http://html5shiv.googlecode.com/svn/trunk/html5.js"></script>
|
||||||
|
<![endif]-->
|
||||||
|
</head>
|
||||||
|
<body>
|
||||||
|
<div id="container">
|
||||||
|
|
||||||
|
<div id="header">
|
||||||
|
<div id="logo">
|
||||||
|
<a href="/">PinealServo</a>
|
||||||
|
</div>
|
||||||
|
</div>
|
||||||
|
|
||||||
|
<div id="navigation">
|
||||||
|
<ul>
|
||||||
|
<li><a href="/">Home</a></li>
|
||||||
|
<li><a href="/about.html">About</a></li>
|
||||||
|
<li><a href="/contact.html">Contact</a></li>
|
||||||
|
<li><a href="/archive.html">Archive</a></li>
|
||||||
|
</ul>
|
||||||
|
</div>
|
||||||
|
|
||||||
|
<div id="content">
|
||||||
|
$if(title)$<h1>$title$</h1>$endif$
|
||||||
|
|
||||||
|
$body$
|
||||||
|
</div>
|
||||||
|
|
||||||
|
<div id="footer">
|
||||||
|
<p><em>Site proudly generated by
|
||||||
|
<a href="http://jaspervdj.be/hakyll">Hakyll</a></em></p>
|
||||||
|
</div>
|
||||||
|
|
||||||
|
</div>
|
||||||
|
</body>
|
||||||
|
</html>
|
|
@ -0,0 +1,7 @@
|
||||||
|
<ul>
|
||||||
|
$for(posts)$
|
||||||
|
<li>
|
||||||
|
<a href="$url$">$title$</a> - $date$
|
||||||
|
</li>
|
||||||
|
$endfor$
|
||||||
|
</ul>
|
|
@ -0,0 +1,8 @@
|
||||||
|
<div class="info">
|
||||||
|
<em>Posted on $date$
|
||||||
|
$if(author)$
|
||||||
|
by $author$
|
||||||
|
$endif$</em>
|
||||||
|
</div>
|
||||||
|
|
||||||
|
$body$
|
Loading…
Reference in New Issue