summaryrefslogtreecommitdiff
path: root/src/Site.hs
blob: 241f59648495e28f41f456c21f3f63d0e51f0d1c (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
{-# LANGUAGE OverloadedStrings, RankNTypes, StandaloneDeriving, FlexibleInstances #-}

import Hakyll

import Data.Monoid (Monoid(..), mconcat, (<>))
import Control.Monad (liftM)
import Data.Char (toLower, isSpace, isAlphaNum)
import Data.Maybe (mapMaybe, fromMaybe)
import Data.Map (Map)
import qualified Data.Map as Map
import Data.List (take, reverse)
import Data.Default
import Text.Pandoc.Options (WriterOptions(..), ObfuscationMethod(..))
import Control.Applicative (Alternative(..), Applicative(..))

import System.FilePath (takeBaseName, (</>), (<.>))

main :: IO ()
main = hakyllWith config $ do
  match "templates/*" $ compile templateCompiler

  match "css/*" $ do
    route idRoute
    compile copyFileCompiler

  match "posts/*" $ do
    route $ setExtension ".html"
    compile $ do
      getResourceBody >>= saveSnapshot "content"
      pandocCompiler
        >>= loadAndApplyTemplate "templates/default.html" defaultContext
        >>= relativizeUrls

  tags <- buildTags "posts/*" tagTranslation' >>= addTag "All Posts" "posts/*"

  tagsRules tags $ \tag pattern -> do
    route idRoute
    compile $ do
      let ctx = mconcat [ constField "title" tag
                        , listField "posts" defaultContext $ chronological =<< loadAll pattern
                        , constField "rss" $ "/rss" </> tagTranslation tag <.> "rss"
                        , defaultContext
                        ]
      makeItem ""
        >>= loadAndApplyTemplate "templates/post-list.html" ctx
        >>= loadAndApplyTemplate "templates/default.html" ctx
        >>= relativizeUrls

  let
    tags' = tags { tagsMakeId = fromFilePath . (\b -> "rss" </> b <.> "rss") . takeBaseName . toFilePath . tagsMakeId tags}

  tagsRules tags' $ \tag pattern -> do
    route idRoute
    compile $ do
      let
        feedCtx = mconcat [ bodyField "description"
                          , defaultContext
                          ]
      renderRss (feedConfig tag) feedCtx =<< loadAllSnapshots pattern "content"

  match "index.md" $ do
    route $ setExtension ".html"
    compile $ do
      let ctx = mconcat [ listField "tags" defaultContext $ mapM (\(k, _) -> renderTag k tags) $ tagsMap tags
                        , constField "title" "Index"
                        , constField "rss" "/rss/all-posts.rss"
                        , defaultContext
                        ]
      item <- getResourceBody
      pandocCompilerWith def (def { writerEmailObfuscation = NoObfuscation })
        >>= loadAndApplyTemplate "templates/index.html" ctx
        >>= loadAndApplyTemplate "templates/default.html" ctx
        >>= relativizeUrls

deriving instance Eq (Item String)

feedConfig :: String -> FeedConfiguration
feedConfig tagName = FeedConfiguration { feedTitle = "dirty-haskell.org: " ++ tagName
                                       , feedDescription = "dirty-haskell.org — A Blog."
                                       , feedAuthorName = "G. Kleen"
                                       , feedAuthorEmail = "blog@dirty-haskell.org"
                                       , feedRoot = "https://dirty-haskell.org"
                                       }

renderTag :: String -- ^ Tag name
          -> Tags
          -> Compiler (Item String)
renderTag tag tags = do
  ellipsisItem <- makeItem ""
  let
    ids = fromMaybe [] $ lookup tag $ tagsMap tags
    postCtx = mconcat [ listField "posts" (ellipsisContext ellipsisItem) $ liftM (withEllipsis ellipsisItem) $ chronological =<< mapM load ids
                      , constField "title" tag
                      , constField "rss" ("rss" </> tagTranslation tag <.> "rss")
                      , constField "url" ("tags" </> tagTranslation tag <.> "html")
                      , defaultContext
                      ]
  makeItem ""
    >>= loadAndApplyTemplate "templates/post-list.html" postCtx
    >>= loadAndApplyTemplate "templates/tag.html" postCtx
  where
    ellipsisContext item = mconcat [ boolField "ellipsis" (== item)
                                   , defaultContext
                                   ]
    boolField name f = field name (\i -> if f i
                                         then pure (error $ unwords ["no string value for bool field:",name])
                                         else empty)
    withEllipsis ellipsisItem xs
      | length xs > max = ellipsisItem : takeEnd (max - 1) xs
      | otherwise = xs
    takeEnd i = reverse . take i . reverse
    max = 4

tagTranslation' :: String -> Identifier
tagTranslation' = fromCapture "tags/*.html" . tagTranslation

tagTranslation :: String -> String
tagTranslation = mapMaybe charTrans
  where
    charTrans c
      | isSpace c = Just '-'
      | isAlphaNum c = Just $ toLower c
      | otherwise = Nothing

addTag :: MonadMetadata m => String -> Pattern -> Tags -> m Tags
addTag name pattern tags = do
  ids <- getMatches pattern
  return $ tags { tagsMap = tagsMap tags ++ [(name, ids)] }

config :: Configuration
config = defaultConfiguration { providerDirectory = "provider"
                              , deployCommand = "rsync -av --progress -c --delete-delay -m  _site/ gkleen@surtr.yggdrasil.li:/var/www/dirty-haskell.org/"
                              }