Thanks Jasper. I thought it had to be something like that.
I'm still not sure exactly where to put it. I tried putting it in my
newsCompiler but no joy.
How exactly does
>>> setFieldPageList (newest 5)
"templates/news_item.html" "news"
(newsDirs `mappend` inGroup Nothing)
work? Does it grab already rendered pages or does it recompile them?
If it recompiles them, with which compiler?
Here's the whole code. It's mostly Benedict Eastaugh's (thanks!) code
from
extralogical.net as it was almost exactly what I needed.
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-unused-do-bind #-}
module Main where
import Control.Arrow ((>>>), arr)
import Control.Monad (forM_)
import Data.List (intercalate)
import Data.Monoid (mappend, mempty)
import Data.Time.Clock (UTCTime)
import Data.Time.Format (parseTime, formatTime)
import System.FilePath
import System.Locale (defaultTimeLocale)
import Text.Pandoc.Shared
( HTMLMathMethod(..)
, ObfuscationMethod(..)
, WriterOptions(..)
, defaultWriterOptions
)
import Hakyll hiding (applyTemplateCompiler)
main :: IO ()
main = hakyll $ do
-- Copy images to /images/
match "images/**" $ do
route idRoute
compile copyFileCompiler
-- Copy files to /files/
match "files/**" $ do
route idRoute
compile copyFileCompiler
-- Copy JavaScript to /scripts/
match "scripts/*" $ do
route idRoute
compile copyFileCompiler
-- Compress CSS
match "css/*" $ do
route idRoute
compile compressCssCompiler
-- Read templates
match "templates/*" $ compile templateCompiler
let newsDirs = regex "^(news|drafts)\\/.+\\.[a-z]+$"
-- News
match newsDirs $ do
route $ routeNews
compile $ newsCompiler
>>> arr pageTitle
>>> arr formatDate
>>> arr publicationDates
-- Post title and body. No accordion.
>>> applyTemplateCompiler "templates/news_single.html"
>>> applyTemplateCompiler "templates/default.html"
>>> relativizeUrlsCompiler
-- Home page
match "index.html" $ route idRoute
create "index.html" $ constA mempty
>>> arr (setField "pageTitle" "Home")
>>> requireA "intro.md" (setFieldA "intro" $ arr pageBody)
-- Intro with 5 newest news items below, readable by clicking
on post h2
>>> setFieldPageList (newest 5)
"templates/news_item.html" "news"
(newsDirs `mappend` inGroup Nothing)
>>> applyTemplateCompiler "templates/home.html"
>>> applyTemplateCompiler "templates/default.html"
>>> relativizeUrlsCompiler
-- Intro
match "intro.md" $ compile pageCompiler
-- News listing
match "news.html" $ route routePage
create "news.html" $ constA mempty
>>> arr (setField "title" "News")
>>> arr pageTitle
-- list of news items viewable using accordion
>>> setFieldPageList recentFirst
"templates/news_item.html" "news"
(newsDirs `mappend` inGroup Nothing)
>>> applyTemplateCompiler "templates/news.html"
>>> applyTemplateCompiler "templates/default.html"
>>> relativizeUrlsCompiler
-- About pages
forM_ [ "about/test1.md"
, "about/test2.md"
, "about/test3.md"
] $ \page -> do
match page $ do
route $ routePage
compile $ pageCompiler'
-- Industry pages
forM_ [ "industry/test1.md"
, "industry/test2.md"
, "industry/test3.md"
] $ \page -> do
match page $ do
route $ routePage
compile $ pageCompiler'
-- Technology pages
forM_ [ "tech/test1.md"
, "tech/test2.md"
, "tech/test3.md"
] $ \page -> do
match page $ do
route $ routePage
compile $ pageCompiler'
-- Mtn. pages
forM_ [ "mtn/test1.md"
, "mtn/test2.md"
, "mtn/test3.md"
] $ \page -> do
match page $ do
route $ routePage
compile $ pageCompiler'
-- Atom feed
match "news.atom" $ route idRoute
create "news.atom" $
requireAll_ (newsDirs `mappend` inGroup Nothing)
>>> renderAtom feedConfiguration
-- 404 page
match "404.html" $ do
route idRoute
compile $ readPageCompiler
>>> addDefaultFields
>>> arr applySelf
>>> arr pageTitle
>>> applyTemplateCompiler "templates/page.html"
>>> applyTemplateCompiler "templates/default.html"
>>> relativizeUrlsCompiler
-- Finish
return ()
-- | Read a page, add default fields, substitute fields and render
with Pandoc.
--
newsCompiler :: Compiler Resource (Page String)
newsCompiler = pageCompilerWith defaultHakyllParserState
newsWriterOptions
pageCompiler' :: Compiler Resource (Page String)
pageCompiler' = newsCompiler
>>> arr pageTitle
>>> arr publicationDates
>>> applyTemplateCompiler "templates/page.html"
>>> applyTemplateCompiler "templates/default.html"
>>> relativizeUrlsCompiler
-- | Pandoc writer options for news.
--
newsWriterOptions :: WriterOptions
newsWriterOptions = defaultWriterOptions
{ writerHtml5 = True
, writerTableOfContents = True
, writerEmailObfuscation = NoObfuscation
, writerHTMLMathMethod = MathML Nothing
, writerLiterateHaskell = True
}
applyTemplateCompiler :: Identifier Template -- ^
Template
-> Compiler (Page String) (Page String) -- ^
Compiler
applyTemplateCompiler = applyTemplateCompilerWith missingHandler
-- | Set defaults for a few keys. Print the string again if not
handled.
missingHandler :: String -> String
missingHandler k = case k of
"pageClass" -> "default"
_ -> "$" ++ k ++ "$"
-- | Take a page like @\"/about/notebooks.md\"@ and route it to
-- @\"/about/notebooks\"@, i.e. turn a filename into a drectory.
--
routePage :: Routes
routePage = customRoute fileToDirectory
-- | Drop the date and set the file extension to ".html" when routing
news.
--
routeNews :: Routes
routeNews = routeNewsExt ".html"
-- | Drop the date and set the file extension to ".raw" when routing
the raw
-- versions of news.
--
routeNewsRaw :: Routes
routeNewsRaw = routeNewsExt ".txt"
-- | Article routing with a specific file extension.
--
routeNewsExt :: String -> Routes
routeNewsExt ext = customRoute
$ flip replaceExtension ext
. flip replaceDirectory "news"
. dropDate
-- | Turn an @Identifier@ into a @FilePath@, dropping the date prefix
(e.g.
-- @\"2011-04-07-\"@) along the way.
dropDate :: Identifier a -> FilePath
dropDate ident = let file = toFilePath ident
in replaceFileName file (drop 11 $ takeFileName
file)
-- | Turn a filename reference into a directory with an index file.
--
fileToDirectory :: Identifier a -> FilePath
fileToDirectory = flip combine "index.html" . dropExtension .
toFilePath
-- | Date formatting.
--
formatDate :: Page a -> Page a
formatDate = renderDateField "published" "%B %e, %Y" "Date unknown"
-- | Publication and last modified date rendering.
--
publicationDates :: Page a -> Page a
publicationDates page = setField "publicationDates" datesString page
where
datesString = intercalate ". "
$ filter ((> 0) . length) [published, updated]
published = formatTime' "%B %e, %Y" $ getPublicationDate page
updated = formatTime' "Last updated %B %e, %Y" $
getUpdatedDate page
formatTime' :: String -> Maybe UTCTime -> String
formatTime' _ Nothing = ""
formatTime' format (Just t) = formatTime defaultTimeLocale format t
getPublicationDate :: Page a -> Maybe UTCTime
getPublicationDate page = parseTime defaultTimeLocale "%Y-%m-%d"
dateString
where
dateString = intercalate "-" $ take 3
$ splitAll "-" $ takeFileName (getField "path" page)
getUpdatedDate :: Page a -> Maybe UTCTime
getUpdatedDate page =
parseTime defaultTimeLocale "%Y-%m-%d" (getField "updated" page)
-- | Prefix page titles with "TEST".
--
pageTitle :: Page a -> Page a
pageTitle = renderField "title" "pageTitle" ("TEST -- " ++)
markdownH1 :: String -> Page a -> Page a
markdownH1 field page = setField field md page
where
title = getField "title" page
line = replicate (length title) '='
md = init $ unlines [title, line]
htmlUrl :: String -> Page a -> Page a
htmlUrl field page = setField field url page
where
url = replaceExtension (getField "url" page) ".html"
-- | Take the most recent n news.
--
newest :: Int -> [Page a] -> [Page a]
newest n = take n . recentFirst
-- | test feed metadata.
--
feedConfiguration :: FeedConfiguration
feedConfiguration = FeedConfiguration
{ feedTitle = "TEST"
, feedDescription = "This is a test"
, feedAuthorName = "tset"
, feedRoot = "
http://test.com"