summaryrefslogtreecommitdiff
path: root/web/site.hs
diff options
context:
space:
mode:
authorJasper Van der Jeugt <m@jaspervdj.be>2012-12-14 10:42:30 +0100
committerJasper Van der Jeugt <m@jaspervdj.be>2012-12-14 10:42:30 +0100
commita2620eec367711480ee2e34ada39b76dc52dbb17 (patch)
tree5bab9f4c497bcbcd06e09c40936cceeb7901521b /web/site.hs
parentcfac1bbca6e5950d8abdc8329e84de4794e08677 (diff)
downloadhakyll-a2620eec367711480ee2e34ada39b76dc52dbb17.tar.gz
Work on installation tutorial
Diffstat (limited to 'web/site.hs')
-rw-r--r--web/site.hs71
1 files changed, 71 insertions, 0 deletions
diff --git a/web/site.hs b/web/site.hs
new file mode 100644
index 0000000..f106ca7
--- /dev/null
+++ b/web/site.hs
@@ -0,0 +1,71 @@
+--------------------------------------------------------------------------------
+{-# LANGUAGE OverloadedStrings #-}
+import Control.Monad (forM_)
+import Data.Monoid (mappend)
+import Hakyll
+import Text.Pandoc
+
+
+--------------------------------------------------------------------------------
+main :: IO ()
+main = hakyllWith config $ do
+ match "css/*" $ do
+ route idRoute
+ compile compressCssCompiler
+
+ -- Static directories
+ forM_ ["images/*", "examples/*", "reference/**"] $ \f -> match f $ do
+ route idRoute
+ compile copyFileCompiler
+
+ -- Pages
+ match "*.markdown" $ do
+ route $ setExtension "html"
+ compile $ pageCompiler
+ >>= loadAndApplyTemplate "templates/default.html" defaultContext
+ >>= relativizeUrls
+
+ -- Tutorials
+ match "tutorials/*" $ do
+ route $ setExtension "html"
+ compile $ pageCompilerWith defaultHakyllParserState withToc
+ >>= loadAndApplyTemplate "templates/tutorial.html" defaultContext
+ >>= loadAndApplyTemplate "templates/default.html" defaultContext
+ >>= relativizeUrls
+
+ -- Tutorial list
+ match "tutorials.html" $ do
+ route idRoute
+ compile $ do
+ tutorials <- loadAll "tutorials/*"
+ itemTpl <- loadBody "templates/tutorial-item.html"
+ list <- applyTemplateList itemTpl defaultContext $
+ chronological tutorials
+
+ let tutorialsCtx =
+ constField "title" "Tutorials" `mappend`
+ constField "tutorials" list `mappend`
+ defaultContext
+
+ makeItem ""
+ >>= loadAndApplyTemplate "templates/tutorials.html" tutorialsCtx
+ >>= loadAndApplyTemplate "templates/default.html" tutorialsCtx
+ >>= relativizeUrls
+
+ -- Templates
+ match "templates/*" $ compile templateCompiler
+ where
+ withToc = defaultHakyllWriterOptions
+ { writerTableOfContents = True
+ , writerTemplate = "$toc$\n$body$"
+ , writerStandalone = True
+ }
+
+
+--------------------------------------------------------------------------------
+config :: Configuration
+config = defaultConfiguration
+ { verbosity = Debug
+ , deployCommand = "rsync --checksum -ave 'ssh -p 2222' \
+ \_site/* jaspervdj@jaspervdj.be:jaspervdj.be/hakyll"
+ }