{-# 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 Control.Monad.Fail (MonadFail)
import Data.List (intercalate, tails)
#if MIN_VERSION_base(4,9,0)
import Data.Semigroup (Semigroup (..))
#endif
import Data.Time.Clock (UTCTime (..))
import Data.Time.Format (formatTime, parseTimeM)
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 Prelude hiding (id)
import System.FilePath (dropExtension, splitDirectories,
takeBaseName)
data ContextField
= EmptyField
| StringField String
| forall a. ListField (Context a) [Item a]
newtype Context a = Context
{ Context a -> String -> [String] -> Item a -> Compiler ContextField
unContext :: String -> [String] -> Item a -> Compiler ContextField
}
#if MIN_VERSION_base(4,9,0)
instance Semigroup (Context a) where
<> :: Context a -> Context a -> Context a
(<>) (Context String -> [String] -> Item a -> Compiler ContextField
f) (Context String -> [String] -> Item a -> Compiler ContextField
g) = (String -> [String] -> Item a -> Compiler ContextField)
-> Context a
forall a.
(String -> [String] -> Item a -> Compiler ContextField)
-> Context a
Context ((String -> [String] -> Item a -> Compiler ContextField)
-> Context a)
-> (String -> [String] -> Item a -> Compiler ContextField)
-> Context a
forall a b. (a -> b) -> a -> b
$ \String
k [String]
a Item a
i -> String -> [String] -> Item a -> Compiler ContextField
f String
k [String]
a Item a
i Compiler ContextField
-> Compiler ContextField -> Compiler ContextField
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> String -> [String] -> Item a -> Compiler ContextField
g String
k [String]
a Item a
i
instance Monoid (Context a) where
mempty :: Context a
mempty = Context a
forall a. Context a
missingField
mappend :: Context a -> Context a -> Context a
mappend = Context a -> Context a -> Context a
forall a. Semigroup a => a -> a -> a
(<>)
#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' :: String -> (Item a -> Compiler ContextField) -> Context a
field' String
key Item a -> Compiler ContextField
value = (String -> [String] -> Item a -> Compiler ContextField)
-> Context a
forall a.
(String -> [String] -> Item a -> Compiler ContextField)
-> Context a
Context ((String -> [String] -> Item a -> Compiler ContextField)
-> Context a)
-> (String -> [String] -> Item a -> Compiler ContextField)
-> Context a
forall a b. (a -> b) -> a -> b
$ \String
k [String]
_ Item a
i ->
if String
k String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
key
then Item a -> Compiler ContextField
value Item a
i
else String -> Compiler ContextField
forall a. String -> Compiler a
noResult (String -> Compiler ContextField)
-> String -> Compiler ContextField
forall a b. (a -> b) -> a -> b
$ String
"Tried field " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
key
field
:: String
-> (Item a -> Compiler String)
-> Context a
field :: String -> (Item a -> Compiler String) -> Context a
field String
key Item a -> Compiler String
value = String -> (Item a -> Compiler ContextField) -> Context a
forall a. String -> (Item a -> Compiler ContextField) -> Context a
field' String
key ((String -> ContextField)
-> Compiler String -> Compiler ContextField
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> ContextField
StringField (Compiler String -> Compiler ContextField)
-> (Item a -> Compiler String) -> Item a -> Compiler ContextField
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Item a -> Compiler String
value)
boolField
:: String
-> (Item a -> Bool)
-> Context a
boolField :: String -> (Item a -> Bool) -> Context a
boolField String
name Item a -> Bool
f = String -> (Item a -> Compiler ContextField) -> Context a
forall a. String -> (Item a -> Compiler ContextField) -> Context a
field' String
name (\Item a
i -> if Item a -> Bool
f Item a
i
then ContextField -> Compiler ContextField
forall (m :: * -> *) a. Monad m => a -> m a
return ContextField
EmptyField
else String -> Compiler ContextField
forall a. String -> Compiler a
noResult (String -> Compiler ContextField)
-> String -> Compiler ContextField
forall a b. (a -> b) -> a -> b
$ String
"Field " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
name String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is false")
constField :: String
-> String
-> Context a
constField :: String -> String -> Context a
constField String
key = String -> (Item a -> Compiler String) -> Context a
forall a. String -> (Item a -> Compiler String) -> Context a
field String
key ((Item a -> Compiler String) -> Context a)
-> (String -> Item a -> Compiler String) -> String -> Context a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compiler String -> Item a -> Compiler String
forall a b. a -> b -> a
const (Compiler String -> Item a -> Compiler String)
-> (String -> Compiler String)
-> String
-> Item a
-> Compiler String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Compiler String
forall (m :: * -> *) a. Monad m => a -> m a
return
listField :: String -> Context a -> Compiler [Item a] -> Context b
listField :: String -> Context a -> Compiler [Item a] -> Context b
listField String
key Context a
c Compiler [Item a]
xs = String -> Context a -> (Item b -> Compiler [Item a]) -> Context b
forall a b.
String -> Context a -> (Item b -> Compiler [Item a]) -> Context b
listFieldWith String
key Context a
c (Compiler [Item a] -> Item b -> Compiler [Item a]
forall a b. a -> b -> a
const Compiler [Item a]
xs)
listFieldWith
:: String -> Context a -> (Item b -> Compiler [Item a]) -> Context b
listFieldWith :: String -> Context a -> (Item b -> Compiler [Item a]) -> Context b
listFieldWith String
key Context a
c Item b -> Compiler [Item a]
f = String -> (Item b -> Compiler ContextField) -> Context b
forall a. String -> (Item a -> Compiler ContextField) -> Context a
field' String
key ((Item b -> Compiler ContextField) -> Context b)
-> (Item b -> Compiler ContextField) -> Context b
forall a b. (a -> b) -> a -> b
$ ([Item a] -> ContextField)
-> Compiler [Item a] -> Compiler ContextField
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Context a -> [Item a] -> ContextField
forall a. Context a -> [Item a] -> ContextField
ListField Context a
c) (Compiler [Item a] -> Compiler ContextField)
-> (Item b -> Compiler [Item a]) -> Item b -> Compiler ContextField
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Item b -> Compiler [Item a]
f
functionField :: String
-> ([String] -> Item a -> Compiler String)
-> Context a
functionField :: String -> ([String] -> Item a -> Compiler String) -> Context a
functionField String
name [String] -> Item a -> Compiler String
value = (String -> [String] -> Item a -> Compiler ContextField)
-> Context a
forall a.
(String -> [String] -> Item a -> Compiler ContextField)
-> Context a
Context ((String -> [String] -> Item a -> Compiler ContextField)
-> Context a)
-> (String -> [String] -> Item a -> Compiler ContextField)
-> Context a
forall a b. (a -> b) -> a -> b
$ \String
k [String]
args Item a
i ->
if String
k String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
name
then String -> ContextField
StringField (String -> ContextField)
-> Compiler String -> Compiler ContextField
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [String] -> Item a -> Compiler String
value [String]
args Item a
i
else String -> Compiler ContextField
forall a. String -> Compiler a
noResult (String -> Compiler ContextField)
-> String -> Compiler ContextField
forall a b. (a -> b) -> a -> b
$ String
"Tried function field " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
name
mapContext :: (String -> String) -> Context a -> Context a
mapContext :: (String -> String) -> Context a -> Context a
mapContext String -> String
f (Context String -> [String] -> Item a -> Compiler ContextField
c) = (String -> [String] -> Item a -> Compiler ContextField)
-> Context a
forall a.
(String -> [String] -> Item a -> Compiler ContextField)
-> Context a
Context ((String -> [String] -> Item a -> Compiler ContextField)
-> Context a)
-> (String -> [String] -> Item a -> Compiler ContextField)
-> Context a
forall a b. (a -> b) -> a -> b
$ \String
k [String]
a Item a
i -> do
ContextField
fld <- String -> [String] -> Item a -> Compiler ContextField
c String
k [String]
a Item a
i
case ContextField
fld of
ContextField
EmptyField -> String -> Compiler ContextField
forall (m :: * -> *) a. MonadFail m => String -> m a
wrongType String
"boolField"
StringField String
str -> ContextField -> Compiler ContextField
forall (m :: * -> *) a. Monad m => a -> m a
return (ContextField -> Compiler ContextField)
-> ContextField -> Compiler ContextField
forall a b. (a -> b) -> a -> b
$ String -> ContextField
StringField (String -> String
f String
str)
ContextField
_ -> String -> Compiler ContextField
forall (m :: * -> *) a. MonadFail m => String -> m a
wrongType String
"ListField"
where
wrongType :: String -> m a
wrongType String
typ = String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m a) -> String -> m a
forall a b. (a -> b) -> a -> b
$ String
"Hakyll.Web.Template.Context.mapContext: " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"can't map over a " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
typ String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"!"
snippetField :: Context String
snippetField :: Context String
snippetField = String
-> ([String] -> Item String -> Compiler String) -> Context String
forall a.
String -> ([String] -> Item a -> Compiler String) -> Context a
functionField String
"snippet" [String] -> Item String -> Compiler String
forall a p. (Binary a, Typeable a) => [String] -> p -> Compiler a
f
where
f :: [String] -> p -> Compiler a
f [String
contentsPath] p
_ = Identifier -> Compiler a
forall a. (Binary a, Typeable a) => Identifier -> Compiler a
loadBody (String -> Identifier
fromFilePath String
contentsPath)
f [] p
_ = String -> Compiler a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"No argument to function 'snippet()'"
f [String]
_ p
_ = String -> Compiler a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Too many arguments to function 'snippet()'"
defaultContext :: Context String
defaultContext :: Context String
defaultContext =
String -> Context String
bodyField String
"body" Context String -> Context String -> Context String
forall a. Monoid a => a -> a -> a
`mappend`
Context String
forall a. Context a
metadataField Context String -> Context String -> Context String
forall a. Monoid a => a -> a -> a
`mappend`
String -> Context String
forall a. String -> Context a
urlField String
"url" Context String -> Context String -> Context String
forall a. Monoid a => a -> a -> a
`mappend`
String -> Context String
forall a. String -> Context a
pathField String
"path" Context String -> Context String -> Context String
forall a. Monoid a => a -> a -> a
`mappend`
String -> Context String
forall a. String -> Context a
titleField String
"title"
teaserSeparator :: String
teaserSeparator :: String
teaserSeparator = String
"<!--more-->"
bodyField :: String -> Context String
bodyField :: String -> Context String
bodyField String
key = String -> (Item String -> Compiler String) -> Context String
forall a. String -> (Item a -> Compiler String) -> Context a
field String
key ((Item String -> Compiler String) -> Context String)
-> (Item String -> Compiler String) -> Context String
forall a b. (a -> b) -> a -> b
$ String -> Compiler String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Compiler String)
-> (Item String -> String) -> Item String -> Compiler String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Item String -> String
forall a. Item a -> a
itemBody
metadataField :: Context a
metadataField :: Context a
metadataField = (String -> [String] -> Item a -> Compiler ContextField)
-> Context a
forall a.
(String -> [String] -> Item a -> Compiler ContextField)
-> Context a
Context ((String -> [String] -> Item a -> Compiler ContextField)
-> Context a)
-> (String -> [String] -> Item a -> Compiler ContextField)
-> Context a
forall a b. (a -> b) -> a -> b
$ \String
k [String]
_ Item a
i -> do
let id :: Identifier
id = Item a -> Identifier
forall a. Item a -> Identifier
itemIdentifier Item a
i
empty' :: Compiler a
empty' = String -> Compiler a
forall a. String -> Compiler a
noResult (String -> Compiler a) -> String -> Compiler a
forall a b. (a -> b) -> a -> b
$ String
"No '" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
k String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' field in metadata " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"of item " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Identifier -> String
forall a. Show a => a -> String
show Identifier
id
Maybe String
value <- Identifier -> String -> Compiler (Maybe String)
forall (m :: * -> *).
MonadMetadata m =>
Identifier -> String -> m (Maybe String)
getMetadataField Identifier
id String
k
Compiler ContextField
-> (String -> Compiler ContextField)
-> Maybe String
-> Compiler ContextField
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Compiler ContextField
forall a. Compiler a
empty' (ContextField -> Compiler ContextField
forall (m :: * -> *) a. Monad m => a -> m a
return (ContextField -> Compiler ContextField)
-> (String -> ContextField) -> String -> Compiler ContextField
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ContextField
StringField) Maybe String
value
urlField :: String -> Context a
urlField :: String -> Context a
urlField String
key = String -> (Item a -> Compiler String) -> Context a
forall a. String -> (Item a -> Compiler String) -> Context a
field String
key ((Item a -> Compiler String) -> Context a)
-> (Item a -> Compiler String) -> Context a
forall a b. (a -> b) -> a -> b
$ \Item a
i -> do
let id :: Identifier
id = Item a -> Identifier
forall a. Item a -> Identifier
itemIdentifier Item a
i
empty' :: [a]
empty' = String -> [a]
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> [a]) -> String -> [a]
forall a b. (a -> b) -> a -> b
$ String
"No route url found for item " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Identifier -> String
forall a. Show a => a -> String
show Identifier
id
(Maybe String -> String)
-> Compiler (Maybe String) -> Compiler String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String -> (String -> String) -> Maybe String -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
forall a. [a]
empty' String -> String
toUrl) (Compiler (Maybe String) -> Compiler String)
-> Compiler (Maybe String) -> Compiler String
forall a b. (a -> b) -> a -> b
$ Identifier -> Compiler (Maybe String)
getRoute Identifier
id
pathField :: String -> Context a
pathField :: String -> Context a
pathField String
key = String -> (Item a -> Compiler String) -> Context a
forall a. String -> (Item a -> Compiler String) -> Context a
field String
key ((Item a -> Compiler String) -> Context a)
-> (Item a -> Compiler String) -> Context a
forall a b. (a -> b) -> a -> b
$ String -> Compiler String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Compiler String)
-> (Item a -> String) -> Item a -> Compiler String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identifier -> String
toFilePath (Identifier -> String)
-> (Item a -> Identifier) -> Item a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Item a -> Identifier
forall a. Item a -> Identifier
itemIdentifier
titleField :: String -> Context a
titleField :: String -> Context a
titleField = (String -> String) -> Context a -> Context a
forall a. (String -> String) -> Context a -> Context a
mapContext String -> String
takeBaseName (Context a -> Context a)
-> (String -> Context a) -> String -> Context a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Context a
forall a. String -> Context a
pathField
dateField :: String
-> String
-> Context a
dateField :: String -> String -> Context a
dateField = TimeLocale -> String -> String -> Context a
forall a. TimeLocale -> String -> String -> Context a
dateFieldWith TimeLocale
defaultTimeLocale
dateFieldWith :: TimeLocale
-> String
-> String
-> Context a
dateFieldWith :: TimeLocale -> String -> String -> Context a
dateFieldWith TimeLocale
locale String
key String
format = String -> (Item a -> Compiler String) -> Context a
forall a. String -> (Item a -> Compiler String) -> Context a
field String
key ((Item a -> Compiler String) -> Context a)
-> (Item a -> Compiler String) -> Context a
forall a b. (a -> b) -> a -> b
$ \Item a
i -> do
UTCTime
time <- TimeLocale -> Identifier -> Compiler UTCTime
forall (m :: * -> *).
(MonadMetadata m, MonadFail m) =>
TimeLocale -> Identifier -> m UTCTime
getItemUTC TimeLocale
locale (Identifier -> Compiler UTCTime) -> Identifier -> Compiler UTCTime
forall a b. (a -> b) -> a -> b
$ Item a -> Identifier
forall a. Item a -> Identifier
itemIdentifier Item a
i
String -> Compiler String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Compiler String) -> String -> Compiler String
forall a b. (a -> b) -> a -> b
$ TimeLocale -> String -> UTCTime -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
locale String
format UTCTime
time
getItemUTC :: (MonadMetadata m, MonadFail m)
=> TimeLocale
-> Identifier
-> m UTCTime
getItemUTC :: TimeLocale -> Identifier -> m UTCTime
getItemUTC TimeLocale
locale Identifier
id' = do
Metadata
metadata <- Identifier -> m Metadata
forall (m :: * -> *). MonadMetadata m => Identifier -> m Metadata
getMetadata Identifier
id'
let tryField :: String -> String -> Maybe UTCTime
tryField String
k String
fmt = String -> Metadata -> Maybe String
lookupString String
k Metadata
metadata Maybe String -> (String -> Maybe UTCTime) -> Maybe UTCTime
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> String -> Maybe UTCTime
parseTime' String
fmt
paths :: [String]
paths = String -> [String]
splitDirectories (String -> [String]) -> String -> [String]
forall a b. (a -> b) -> a -> b
$ (String -> String
dropExtension (String -> String)
-> (Identifier -> String) -> Identifier -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identifier -> String
toFilePath) Identifier
id'
m UTCTime -> (UTCTime -> m UTCTime) -> Maybe UTCTime -> m UTCTime
forall b a. b -> (a -> b) -> Maybe a -> b
maybe m UTCTime
forall a. m a
empty' UTCTime -> m UTCTime
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe UTCTime -> m UTCTime) -> Maybe UTCTime -> m UTCTime
forall a b. (a -> b) -> a -> b
$ [Maybe UTCTime] -> Maybe UTCTime
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum ([Maybe UTCTime] -> Maybe UTCTime)
-> [Maybe UTCTime] -> Maybe UTCTime
forall a b. (a -> b) -> a -> b
$
[String -> String -> Maybe UTCTime
tryField String
"published" String
fmt | String
fmt <- [String]
formats] [Maybe UTCTime] -> [Maybe UTCTime] -> [Maybe UTCTime]
forall a. [a] -> [a] -> [a]
++
[String -> String -> Maybe UTCTime
tryField String
"date" String
fmt | String
fmt <- [String]
formats] [Maybe UTCTime] -> [Maybe UTCTime] -> [Maybe UTCTime]
forall a. [a] -> [a] -> [a]
++
[String -> String -> Maybe UTCTime
parseTime' String
"%Y-%m-%d" (String -> Maybe UTCTime) -> String -> Maybe UTCTime
forall a b. (a -> b) -> a -> b
$ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"-" ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
3 ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String -> String -> [String]
splitAll String
"-" String
fnCand | String
fnCand <- [String] -> [String]
forall a. [a] -> [a]
reverse [String]
paths] [Maybe UTCTime] -> [Maybe UTCTime] -> [Maybe UTCTime]
forall a. [a] -> [a] -> [a]
++
[String -> String -> Maybe UTCTime
parseTime' String
"%Y-%m-%d" (String -> Maybe UTCTime) -> String -> Maybe UTCTime
forall a b. (a -> b) -> a -> b
$ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"-" ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
fnCand | [String]
fnCand <- ([String] -> [String]) -> [[String]] -> [[String]]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
3) ([[String]] -> [[String]]) -> [[String]] -> [[String]]
forall a b. (a -> b) -> a -> b
$ [[String]] -> [[String]]
forall a. [a] -> [a]
reverse ([[String]] -> [[String]])
-> ([String] -> [[String]]) -> [String] -> [[String]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [[String]]
forall a. [a] -> [[a]]
tails ([String] -> [[String]]) -> [String] -> [[String]]
forall a b. (a -> b) -> a -> b
$ [String]
paths]
where
empty' :: m a
empty' = String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m a) -> String -> m a
forall a b. (a -> b) -> a -> b
$ String
"Hakyll.Web.Template.Context.getItemUTC: " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"could not parse time for " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Identifier -> String
forall a. Show a => a -> String
show Identifier
id'
parseTime' :: String -> String -> Maybe UTCTime
parseTime' = Bool -> TimeLocale -> String -> String -> Maybe UTCTime
forall (m :: * -> *) t.
(MonadFail m, ParseTime t) =>
Bool -> TimeLocale -> String -> String -> m t
parseTimeM Bool
True TimeLocale
locale
formats :: [String]
formats =
[ String
"%a, %d %b %Y %H:%M:%S %Z"
, String
"%a, %d %b %Y %H:%M:%S"
, String
"%Y-%m-%dT%H:%M:%S%Z"
, String
"%Y-%m-%dT%H:%M:%S"
, String
"%Y-%m-%d %H:%M:%S%Z"
, String
"%Y-%m-%d %H:%M:%S"
, String
"%Y-%m-%d"
, String
"%B %e, %Y %l:%M %p"
, String
"%B %e, %Y"
, String
"%b %d, %Y"
]
getItemModificationTime
:: Identifier
-> Compiler UTCTime
getItemModificationTime :: Identifier -> Compiler UTCTime
getItemModificationTime Identifier
identifier = do
Provider
provider <- CompilerRead -> Provider
compilerProvider (CompilerRead -> Provider)
-> Compiler CompilerRead -> Compiler Provider
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Compiler CompilerRead
compilerAsk
UTCTime -> Compiler UTCTime
forall (m :: * -> *) a. Monad m => a -> m a
return (UTCTime -> Compiler UTCTime) -> UTCTime -> Compiler UTCTime
forall a b. (a -> b) -> a -> b
$ Provider -> Identifier -> UTCTime
resourceModificationTime Provider
provider Identifier
identifier
modificationTimeField :: String
-> String
-> Context a
modificationTimeField :: String -> String -> Context a
modificationTimeField = TimeLocale -> String -> String -> Context a
forall a. TimeLocale -> String -> String -> Context a
modificationTimeFieldWith TimeLocale
defaultTimeLocale
modificationTimeFieldWith :: TimeLocale
-> String
-> String
-> Context a
modificationTimeFieldWith :: TimeLocale -> String -> String -> Context a
modificationTimeFieldWith TimeLocale
locale String
key String
fmt = String -> (Item a -> Compiler String) -> Context a
forall a. String -> (Item a -> Compiler String) -> Context a
field String
key ((Item a -> Compiler String) -> Context a)
-> (Item a -> Compiler String) -> Context a
forall a b. (a -> b) -> a -> b
$ \Item a
i -> do
UTCTime
mtime <- Identifier -> Compiler UTCTime
getItemModificationTime (Identifier -> Compiler UTCTime) -> Identifier -> Compiler UTCTime
forall a b. (a -> b) -> a -> b
$ Item a -> Identifier
forall a. Item a -> Identifier
itemIdentifier Item a
i
String -> Compiler String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Compiler String) -> String -> Compiler String
forall a b. (a -> b) -> a -> b
$ TimeLocale -> String -> UTCTime -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
locale String
fmt UTCTime
mtime
teaserField :: String
-> Snapshot
-> Context String
teaserField :: String -> String -> Context String
teaserField = String -> String -> String -> Context String
teaserFieldWithSeparator String
teaserSeparator
teaserFieldWithSeparator :: String
-> String
-> Snapshot
-> Context String
teaserFieldWithSeparator :: String -> String -> String -> Context String
teaserFieldWithSeparator String
separator String
key String
snapshot = String -> (Item String -> Compiler String) -> Context String
forall a. String -> (Item a -> Compiler String) -> Context a
field String
key ((Item String -> Compiler String) -> Context String)
-> (Item String -> Compiler String) -> Context String
forall a b. (a -> b) -> a -> b
$ \Item String
item -> do
String
body <- Item String -> String
forall a. Item a -> a
itemBody (Item String -> String)
-> Compiler (Item String) -> Compiler String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Identifier -> String -> Compiler (Item String)
forall a.
(Binary a, Typeable a) =>
Identifier -> String -> Compiler (Item a)
loadSnapshot (Item String -> Identifier
forall a. Item a -> Identifier
itemIdentifier Item String
item) String
snapshot
case String -> String -> Maybe String
needlePrefix String
separator String
body of
Maybe String
Nothing -> String -> Compiler String
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Compiler String) -> String -> Compiler String
forall a b. (a -> b) -> a -> b
$
String
"Hakyll.Web.Template.Context: no teaser defined for " String -> String -> String
forall a. [a] -> [a] -> [a]
++
Identifier -> String
forall a. Show a => a -> String
show (Item String -> Identifier
forall a. Item a -> Identifier
itemIdentifier Item String
item)
Just String
t -> String -> Compiler String
forall (m :: * -> *) a. Monad m => a -> m a
return String
t
missingField :: Context a
missingField :: Context a
missingField = (String -> [String] -> Item a -> Compiler ContextField)
-> Context a
forall a.
(String -> [String] -> Item a -> Compiler ContextField)
-> Context a
Context ((String -> [String] -> Item a -> Compiler ContextField)
-> Context a)
-> (String -> [String] -> Item a -> Compiler ContextField)
-> Context a
forall a b. (a -> b) -> a -> b
$ \String
k [String]
_ Item a
_ -> String -> Compiler ContextField
forall a. String -> Compiler a
noResult (String -> Compiler ContextField)
-> String -> Compiler ContextField
forall a b. (a -> b) -> a -> b
$
String
"Missing field '" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
k String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' in context"