|
@@ -2,6 +2,8 @@
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
import Data.Monoid (mappend)
|
|
|
import Hakyll
|
|
|
+import qualified Data.Set as S
|
|
|
+import Text.Pandoc
|
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
@@ -11,6 +13,14 @@ main = hakyll $ do
|
|
|
route idRoute
|
|
|
compile copyFileCompiler
|
|
|
|
|
|
+ match "images/*/*" $ do
|
|
|
+ route idRoute
|
|
|
+ compile copyFileCompiler
|
|
|
+
|
|
|
+ match "scripts/*" $ do
|
|
|
+ route idRoute
|
|
|
+ compile copyFileCompiler
|
|
|
+
|
|
|
match "css/*" $ do
|
|
|
route idRoute
|
|
|
compile compressCssCompiler
|
|
@@ -22,7 +32,7 @@ main = hakyll $ do
|
|
|
|
|
|
match "*.md" $ do
|
|
|
route $ setExtension "html"
|
|
|
- compile $ pandocCompiler
|
|
|
+ compile $ siteCompiler
|
|
|
>>= loadAndApplyTemplate "templates/default.html" defaultContext
|
|
|
>>= relativizeUrls
|
|
|
|
|
@@ -44,8 +54,9 @@ main = hakyll $ do
|
|
|
|
|
|
match "posts/*.md" $ do
|
|
|
route $ setExtension "html"
|
|
|
- compile $ pandocCompiler
|
|
|
+ compile $ siteCompiler
|
|
|
>>= loadAndApplyTemplate "templates/post.html" (postCtxWithTags tags)
|
|
|
+ >>= saveSnapshot "post_content"
|
|
|
>>= loadAndApplyTemplate "templates/default.html" (postCtxWithTags tags)
|
|
|
>>= relativizeUrls
|
|
|
|
|
@@ -63,16 +74,14 @@ main = hakyll $ do
|
|
|
>>= loadAndApplyTemplate "templates/default.html" archiveCtx
|
|
|
>>= relativizeUrls
|
|
|
|
|
|
-
|
|
|
create ["new_index.html"] $ do
|
|
|
route idRoute
|
|
|
compile $ do
|
|
|
- post <- fmap (head) . recentFirst =<< loadAll "posts/*.md"
|
|
|
- pandocCompiler
|
|
|
- >>= loadAndApplyTemplate "templates/post.html" (postCtxWithTags tags)
|
|
|
- >>= loadAndApplyTemplate "templates/default.html" (postCtxWithTags tags)
|
|
|
- >>= relativizeUrls
|
|
|
-
|
|
|
+ post <- fmap head . recentFirst =<< loadAllSnapshots "posts/*.md" "post_content"
|
|
|
+ -- loadAndApplyTemplate "templates/post.html" (postCtxWithTags tags) post
|
|
|
+ loadAndApplyTemplate "templates/default.html" (postCtxWithTags tags) post
|
|
|
+ >>= relativizeUrls
|
|
|
+ >>= changeIdentifier "new_index.html"
|
|
|
|
|
|
match "index.html" $ do
|
|
|
route idRoute
|
|
@@ -100,3 +109,25 @@ postCtx =
|
|
|
postCtxWithTags :: Tags -> Context String
|
|
|
postCtxWithTags tags = tagsField "tags" tags `mappend` postCtx
|
|
|
|
|
|
+changeIdentifier :: Identifier -> Item a -> Compiler (Item a)
|
|
|
+changeIdentifier idt item = return (itemSetIdentifier idt item)
|
|
|
+
|
|
|
+itemSetIdentifier :: Identifier -> Item a -> Item a
|
|
|
+itemSetIdentifier x (Item _ i) = Item x i
|
|
|
+
|
|
|
+
|
|
|
+siteCompiler :: Compiler (Item String)
|
|
|
+siteCompiler =
|
|
|
+ let addExtensions = [Ext_tex_math_dollars, Ext_tex_math_double_backslash,
|
|
|
+ Ext_latex_macros, Ext_footnotes, Ext_inline_notes]
|
|
|
+ wExtensions = foldr S.insert (writerExtensions defaultHakyllWriterOptions) addExtensions
|
|
|
+ rExtensions = foldr S.insert (readerExtensions defaultHakyllReaderOptions) addExtensions
|
|
|
+ siteWriterOptions = defaultHakyllWriterOptions {
|
|
|
+ writerExtensions = wExtensions,
|
|
|
+ writerHTMLMathMethod = MathJax ""
|
|
|
+ }
|
|
|
+ siteReaderOptions = defaultHakyllReaderOptions {
|
|
|
+ readerExtensions = rExtensions
|
|
|
+ }
|
|
|
+ in pandocCompilerWith siteReaderOptions siteWriterOptions
|
|
|
+
|