diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Site.hs | 19 |
1 files changed, 14 insertions, 5 deletions
diff --git a/src/Site.hs b/src/Site.hs index 98a598f..c1e4854 100644 --- a/src/Site.hs +++ b/src/Site.hs | |||
@@ -9,13 +9,16 @@ import Data.Maybe (mapMaybe, fromMaybe) | |||
9 | import Data.Map (Map) | 9 | import Data.Map (Map) |
10 | import qualified Data.Map as Map | 10 | import qualified Data.Map as Map |
11 | import qualified Data.Set as Set | 11 | import qualified Data.Set as Set |
12 | import Data.List (take, reverse, nub, groupBy, concatMap) | 12 | import Data.List (take, reverse, nub, groupBy, concatMap, intersperse) |
13 | import Data.Function (on) | 13 | import Data.Function (on) |
14 | import Data.Default | 14 | import Data.Default |
15 | import Text.Pandoc | 15 | import Text.Pandoc |
16 | import Text.Pandoc.Walk (query, walkM) | 16 | import Text.Pandoc.Walk (query, walkM) |
17 | import Text.Pandoc.Error | 17 | import Text.Pandoc.Error |
18 | import Control.Applicative (Alternative(..), Applicative(..)) | 18 | import Control.Applicative (Alternative(..), Applicative(..)) |
19 | import Text.Blaze.Html (toHtml, toValue, (!)) | ||
20 | import qualified Text.Blaze.Html5 as H | ||
21 | import qualified Text.Blaze.Html5.Attributes as A | ||
19 | 22 | ||
20 | import System.FilePath (takeBaseName, (</>), (<.>)) | 23 | import System.FilePath (takeBaseName, (</>), (<.>)) |
21 | 24 | ||
@@ -45,16 +48,20 @@ main = hakyllWith config $ do | |||
45 | saveSnapshot "alignment" $ fmap snd item | 48 | saveSnapshot "alignment" $ fmap snd item |
46 | return $ fmap fst item | 49 | return $ fmap fst item |
47 | 50 | ||
51 | tags <- buildTags "posts/*" tagTranslation' >>= addTag "All Posts" "posts/*" | ||
52 | |||
48 | match "posts/*" $ do | 53 | match "posts/*" $ do |
49 | route $ setExtension ".html" | 54 | route $ setExtension ".html" |
50 | compile $ do | 55 | compile $ do |
56 | let ctx = mconcat [ defaultContext | ||
57 | , dateField "published" "%F" | ||
58 | , tagsFieldWith getTags (\tag _ -> Just . H.li $ H.a ! A.href (toValue . toUrl $ "tags" </> tagTranslation tag <.> "html") $ toHtml tag) (mconcat . intersperse "\n") "tagList" tags | ||
59 | ] | ||
51 | getResourceBody >>= saveSnapshot "content" | 60 | getResourceBody >>= saveSnapshot "content" |
52 | pandocCompilerWithTransformM defaultHakyllReaderOptions defaultHakyllWriterOptions mathTransform | 61 | pandocCompilerWithTransformM defaultHakyllReaderOptions defaultHakyllWriterOptions mathTransform |
53 | >>= loadAndApplyTemplate "templates/default.html" defaultContext | 62 | >>= loadAndApplyTemplate "templates/default.html" ctx |
54 | >>= relativizeUrls | 63 | >>= relativizeUrls |
55 | 64 | ||
56 | tags <- buildTags "posts/*" tagTranslation' >>= addTag "All Posts" "posts/*" | ||
57 | |||
58 | tagsRules tags $ \tag pattern -> do | 65 | tagsRules tags $ \tag pattern -> do |
59 | route idRoute | 66 | route idRoute |
60 | compile $ do | 67 | compile $ do |
@@ -89,7 +96,9 @@ main = hakyllWith config $ do | |||
89 | , defaultContext | 96 | , defaultContext |
90 | ] | 97 | ] |
91 | item <- getResourceBody | 98 | item <- getResourceBody |
92 | pandocCompilerWith def (def { writerEmailObfuscation = NoObfuscation }) | 99 | {-pandocCompilerWith def (def { writerEmailObfuscation = NoObfuscation }) |
100 | >>=-} | ||
101 | makeItem "" | ||
93 | >>= loadAndApplyTemplate "templates/index.html" ctx | 102 | >>= loadAndApplyTemplate "templates/index.html" ctx |
94 | >>= loadAndApplyTemplate "templates/default.html" ctx | 103 | >>= loadAndApplyTemplate "templates/default.html" ctx |
95 | >>= relativizeUrls | 104 | >>= relativizeUrls |