{-# LANGUAGE OverloadedStrings #-} module Main where import Prelude hiding (id) import Control.Arrow import Control.Category (id) import Control.Monad import Data.Function (on) import Data.List hiding (group) import Data.Maybe import Data.Monoid (mempty, mconcat) import System.FilePath (takeFileName) import System.Locale (defaultTimeLocale, TimeLocale) import Data.Time.Calendar import Data.Time.Clock (UTCTime (..)) import Data.Time.Format (parseTime, formatTime) import Text.Printf import Hakyll hiding (chronological, recentFirst) main :: IO () main = hakyll $ do -- Compress CSS match "css/*" $ do route idRoute compile compressCssCompiler -- Images match "images/**" $ do route idRoute compile copyFileCompiler -- Render posts group "posts" $ do match (inPostGroup "posts/*") $ do route $ setExtension ".html" compile $ pageCompiler >>> addDate >>> addTagCloud >>> addArchiveLinks >>> renderTagsField "prettytags" (fromCapture "tags/*") >>> applyTemplateCompiler "templates/post.html" >>> addTopnav >>> applyTemplateCompiler "templates/default.html" >>> relativizeUrlsCompiler -- Index match "index*" $ route $ setExtension ".html" metaCompile $ requireAllA allPosts $ arr (recentFirst . snd) >>> (constA ("Home", "index*") &&& id) >>> paginatePosts match "posts/*" $ compile $ pageCompiler >>> (id &&& arr (getField "path")) >>> setFieldA "url" (arr (Identifier postGroup) >>> getRouteFor >>> arr (fromMaybe "" . fmap toUrl)) -- Tags create "tags" $ requireAll_ allPosts >>> arr readTags match "tags/*" $ route $ setExtension ".html" metaCompile $ require_ "tags" >>> arr tagsMap >>> arr (map $ second recentFirst) >>> mapCompiler (((arr (\tag -> "Posts tagged ‘" ++ tag ++ "’") &&& arr (parseGlob . (++ "*") . identifierPath . tagIdentifier)) *** id) >>> paginatePosts ) >>> arr concat -- Archive create "archive" $ requireAll_ allPosts >>> arr (Tags . groupTuples . reverse . sortBy (compare `on` fst) . catMaybes . map (\page -> getDate page >>= (\date -> return (date, page)))) match "archive/**" $ route $ setExtension ".html" metaCompile $ require_ "archive" >>> arr tagsMap >>> arr (map $ second recentFirst) >>> mapCompiler (((arr (\month -> "Archive for " ++ prettyMonth month) &&& arr (parseGlob . (++ "*") . identifierPath . archiveIdentifier)) *** id) >>> paginatePosts ) >>> arr concat -- Render RSS feed match "rss.xml" $ route idRoute create "rss.xml" $ requireAll_ allPosts >>> mapCompiler (arr $ copyBodyToField "description") >>> renderRss feedConfiguration -- Read templates match "templates/*" $ compile templateCompiler where postGroup = Just "posts" inPostGroup :: Pattern a -> Pattern a inPostGroup p = patternIntersection [inGroup postGroup, p] notInPostGroup :: Pattern a -> Pattern a notInPostGroup p = patternIntersection [complement $ inGroup postGroup, p] allPosts :: Pattern (Page String) allPosts = notInPostGroup "posts/*" addTopnav :: Compiler (Page a) (Page a) addTopnav = arr (id &&& const ()) >>> setFieldA "topnav" topnav topnav :: Compiler () String topnav = constA topLinks >>> mapCompiler topnavLink >>> arr (concat . catMaybes) where topnavLink = second (id &&& (getRouteFor >>> arr (fmap toUrl)) >>> arr pullSnd) >>> arr pullSnd >>> (getIdentifier &&& id) >>> arr pullSnd >>> arr (fmap (\(cur, (text, (link, url))) -> "
  • " ++ escapeHtml text ++ "
  • ")) cl cur link = if cur == link then " class=\"s\"" else "" maybeGetRouteFor :: Compiler (Maybe (Identifier (Page String))) (Maybe FilePath) maybeGetRouteFor = arr maybeToEither >>> (constA Nothing ||| getRouteFor) where maybeToEither Nothing = Left () maybeToEither (Just a) = Right a addPagenav :: Compiler (Page a, (Maybe (Identifier (Page String)), Maybe (Identifier (Page String)))) (Page a) addPagenav = setFieldA "pagenav" $ (maybeGetRouteFor *** maybeGetRouteFor) >>> arr pagenav pagenav (prev, next) = pagenavPrev prev ++ pagenavNext next pagenavPrev Nothing = " " pagenavPrev (Just url) = "« Newer Entries" pagenavNext Nothing = " " pagenavNext (Just url) = "Older Entries »" pageTitle 0 = "" pageTitle i = " – Page " ++ show (i+1) paginatePosts :: Compiler ((String, Pattern (Page String)), [Page String]) [(Identifier (Page String), Compiler () (Page String))] paginatePosts = paginate 5 (arr (\(title, prev, next, i, pages) -> (((mempty, (prev, next)), (title, i)), pages)) >>> first (first (first (addTagCloud >>> addArchiveLinks) >>> addPagenav) >>> arr (\(page, (title, i)) -> setField "title" (title ++ pageTitle i) page) ) >>> addPosts >>> applyTemplateCompiler "templates/index.html" >>> addTopnav >>> applyTemplateCompiler "templates/default.html" >>> relativizeUrlsCompiler ) topLinks :: [(String, Identifier (Page String))] topLinks = [("Home", "index") ] pullSnd :: Functor m => (a, m b) -> m (a, b) pullSnd (a, b) = fmap (const a &&& id) b patternIntersection :: [Pattern a] -> Pattern a patternIntersection patterns = predicate $ flip all patterns . flip matches getUTCMaybe :: Page a -- ^ Input page -> Maybe UTCTime -- ^ Parsed UTCTime getUTCMaybe page = msum [ fromPublished "%a, %d %b %Y %H:%M:%S UT" , fromPublished "%Y-%m-%dT%H:%M:%SZ" , fromPublished "%B %e, %Y %l:%M %p" , fromPublished "%B %e, %Y" , getFieldMaybe "path" page >>= parseTime' "%Y-%m-%d" . intercalate "-" . take 3 . splitAll "-" . takeFileName ] where fromPublished f = getFieldMaybe "published" page >>= parseTime' f parseTime' f str = parseTime defaultTimeLocale f str getDate :: Page a -> Maybe String getDate = liftM ((\(y, m, _) -> printf "%04d/%02d" y m) . toGregorian . utctDay) . getUTCMaybe chronological :: [Page a] -> [Page a] chronological = sortBy (compare `on` getUTCMaybe) recentFirst :: [Page a] -> [Page a] recentFirst = reverse . chronological groupTuples :: Eq a => [(a, b)] -> [(a, [b])] groupTuples = map (fst . head &&& map snd) . groupBy ((==) `on` fst) paginate :: Int -> Compiler (a, Maybe (Identifier (Page String)), Maybe (Identifier (Page String)), Int, [Page String]) (Page String) -> Compiler ((a, Pattern (Page String)), [Page String]) [(Identifier (Page String), Compiler () (Page String))] paginate perPage c = arr $ \((a, pattern), posts) -> renderPages a pattern 0 (n posts) posts where renderPages _ _ _ _ [] = [] renderPages a pattern i n posts = (name i, constA (a, prev i, next i n, i, cur) >>> c):(renderPages a pattern (i+1) n rest) where (cur, rest) = splitAt perPage posts prev 0 = Nothing prev i = Just . name $ i-1 next i n = if i == (n-1) then Nothing else Just . name $ i+1 name 0 = fromCapture pattern "" name i = fromCapture pattern $ show i n posts = (length posts + perPage - 1) `div` perPage addPosts :: Compiler (Page String, [Page String]) (Page String) addPosts = setFieldA "posts" $ mapCompiler (addDate >>> addTagCloud >>> renderTagsField "prettytags" (fromCapture "tags/*") >>> applyTemplateCompiler "templates/post.html") >>> arr mconcat >>> arr pageBody addDate = arr $ renderDateField "date" "%e%b/%y" "" addTagCloud = requireA "tags" (setFieldA "tagcloud" renderTagCloud') where renderTagCloud' :: Compiler (Tags String) String renderTagCloud' = renderTagCloud tagIdentifier 100 300 addArchiveLinks = requireA "archive" (setFieldA "archive" renderArchive) where renderArchive :: Compiler (Tags String) String renderArchive = arr tagsMap >>> arr (map (\(s, p) -> "
  • " ++ prettyMonth s ++ " (" ++ show (length p) ++ ")
  • ")) >>> arr mconcat prettyMonth :: String -> String prettyMonth s = month ++ " " ++ year where year = take 4 s month = case (drop 5 s) of "01" -> "January" "02" -> "February" "03" -> "March" "04" -> "April" "05" -> "May" "06" -> "June" "07" -> "July" "08" -> "August" "09" -> "September" "10" -> "October" "11" -> "November" "12" -> "December" _ -> "Unknown" tagIdentifier :: String -> Identifier (Page String) tagIdentifier = fromCapture "tags/*" archiveIdentifier :: String -> Identifier (Page String) archiveIdentifier = fromCapture "archive/*" feedConfiguration :: FeedConfiguration feedConfiguration = FeedConfiguration { feedTitle = "Universe Factory" , feedDescription = "Because one universe is not enough" , feedAuthorName = "NeoRaider" , feedRoot = "http://blog.universe-factory.net" }