{-# LANGUAGE CPP #-}
{-# LANGUAGE ExistentialQuantification #-}
module Hakyll.Web.Template.Context
( ContextField (..)
, Context (..)
, field
, boolField
, constField
, listField
, listFieldWith
, functionField
, mapContext
, defaultContext
, bodyField
, metadataField
, urlField
, pathField
, titleField
, snippetField
, dateField
, dateFieldWith
, getItemUTC
, getItemModificationTime
, modificationTimeField
, modificationTimeFieldWith
, teaserField
, teaserFieldWithSeparator
, missingField
) where
import Control.Applicative (Alternative (..))
import Control.Monad (msum)
import Data.List (intercalate)
#if MIN_VERSION_base(4,9,0)
import Data.Semigroup (Semigroup (..))
#endif
import Data.Time.Clock (UTCTime (..))
import Data.Time.Format (formatTime)
import qualified Data.Time.Format as TF
import Data.Time.Locale.Compat (TimeLocale, defaultTimeLocale)
import Hakyll.Core.Compiler
import Hakyll.Core.Compiler.Internal
import Hakyll.Core.Identifier
import Hakyll.Core.Item
import Hakyll.Core.Metadata
import Hakyll.Core.Provider
import Hakyll.Core.Util.String (needlePrefix, splitAll)
import Hakyll.Web.Html
import System.FilePath (splitDirectories, takeBaseName, dropExtension)
data ContextField
= StringField String
| forall a. ListField (Context a) [Item a]
newtype Context a = Context
{ unContext :: String -> [String] -> Item a -> Compiler ContextField
}
#if MIN_VERSION_base(4,9,0)
instance Semigroup (Context a) where
(<>) (Context f) (Context g) = Context $ \k a i -> f k a i <|> g k a i
instance Monoid (Context a) where
mempty = missingField
mappend = (<>)
#else
instance Monoid (Context a) where
mempty = missingField
mappend (Context f) (Context g) = Context $ \k a i -> f k a i <|> g k a i
#endif
field' :: String -> (Item a -> Compiler ContextField) -> Context a
field' key value = Context $ \k _ i -> if k == key then value i else empty
field
:: String
-> (Item a -> Compiler String)
-> Context a
field key value = field' key (fmap StringField . value)
boolField
:: String
-> (Item a -> Bool)
-> Context a
boolField name f = field name (\i -> if f i
then pure (error $ unwords ["no string value for bool field:",name])
else empty)
constField :: String -> String -> Context a
constField key = field key . const . return
listField :: String -> Context a -> Compiler [Item a] -> Context b
listField key c xs = listFieldWith key c (const xs)
listFieldWith
:: String -> Context a -> (Item b -> Compiler [Item a]) -> Context b
listFieldWith key c f = field' key $ fmap (ListField c) . f
functionField :: String -> ([String] -> Item a -> Compiler String) -> Context a
functionField name value = Context $ \k args i ->
if k == name
then StringField <$> value args i
else empty
mapContext :: (String -> String) -> Context a -> Context a
mapContext f (Context c) = Context $ \k a i -> do
fld <- c k a i
case fld of
StringField str -> return $ StringField (f str)
ListField _ _ -> fail $
"Hakyll.Web.Template.Context.mapContext: " ++
"can't map over a ListField!"
snippetField :: Context String
snippetField = functionField "snippet" f
where
f [contentsPath] _ = loadBody (fromFilePath contentsPath)
f _ i = error $
"Too many arguments to function 'snippet()' in item " ++
show (itemIdentifier i)
defaultContext :: Context String
defaultContext =
bodyField "body" `mappend`
metadataField `mappend`
urlField "url" `mappend`
pathField "path" `mappend`
titleField "title" `mappend`
missingField
teaserSeparator :: String
teaserSeparator = "<!--more-->"
bodyField :: String -> Context String
bodyField key = field key $ return . itemBody
metadataField :: Context a
metadataField = Context $ \k _ i -> do
value <- getMetadataField (itemIdentifier i) k
maybe empty (return . StringField) value
urlField :: String -> Context a
urlField key = field key $
fmap (maybe empty toUrl) . getRoute . itemIdentifier
pathField :: String -> Context a
pathField key = field key $ return . toFilePath . itemIdentifier
titleField :: String -> Context a
titleField = mapContext takeBaseName . pathField
dateField :: String
-> String
-> Context a
dateField = dateFieldWith defaultTimeLocale
dateFieldWith :: TimeLocale
-> String
-> String
-> Context a
dateFieldWith locale key format = field key $ \i -> do
time <- getItemUTC locale $ itemIdentifier i
return $ formatTime locale format time
getItemUTC :: MonadMetadata m
=> TimeLocale
-> Identifier
-> m UTCTime
getItemUTC locale id' = do
metadata <- getMetadata id'
let tryField k fmt = lookupString k metadata >>= parseTime' fmt
paths = splitDirectories $ (dropExtension . toFilePath) id'
maybe empty' return $ msum $
[tryField "published" fmt | fmt <- formats] ++
[tryField "date" fmt | fmt <- formats] ++
[parseTime' "%Y-%m-%d" $ intercalate "-" $ take 3 $ splitAll "-" fnCand | fnCand <- reverse paths]
where
empty' = fail $ "Hakyll.Web.Template.Context.getItemUTC: " ++
"could not parse time for " ++ show id'
parseTime' = parseTimeM True locale
formats =
[ "%a, %d %b %Y %H:%M:%S %Z"
, "%Y-%m-%dT%H:%M:%S%Z"
, "%Y-%m-%d %H:%M:%S%Z"
, "%Y-%m-%d"
, "%B %e, %Y %l:%M %p"
, "%B %e, %Y"
, "%b %d, %Y"
]
getItemModificationTime
:: Identifier
-> Compiler UTCTime
getItemModificationTime identifier = do
provider <- compilerProvider <$> compilerAsk
return $ resourceModificationTime provider identifier
modificationTimeField :: String
-> String
-> Context a
modificationTimeField = modificationTimeFieldWith defaultTimeLocale
modificationTimeFieldWith :: TimeLocale
-> String
-> String
-> Context a
modificationTimeFieldWith locale key fmt = field key $ \i -> do
mtime <- getItemModificationTime $ itemIdentifier i
return $ formatTime locale fmt mtime
teaserField :: String
-> Snapshot
-> Context String
teaserField = teaserFieldWithSeparator teaserSeparator
teaserFieldWithSeparator :: String
-> String
-> Snapshot
-> Context String
teaserFieldWithSeparator separator key snapshot = field key $ \item -> do
body <- itemBody <$> loadSnapshot (itemIdentifier item) snapshot
case needlePrefix separator body of
Nothing -> fail $
"Hakyll.Web.Template.Context: no teaser defined for " ++
show (itemIdentifier item)
Just t -> return t
missingField :: Context a
missingField = Context $ \k _ i -> fail $
"Missing field $" ++ k ++ "$ in context for item " ++
show (itemIdentifier i)
parseTimeM :: Bool -> TimeLocale -> String -> String -> Maybe UTCTime
#if MIN_VERSION_time(1,5,0)
parseTimeM = TF.parseTimeM
#else
parseTimeM _ = TF.parseTime
#endif