-- | This module provides 'Context's which are used to expand expressions in
-- templates and allow for arbitrary customisation.
--
-- 'Template's define a small expression DSL which consists of strings,
-- identifiers and function application. There is no type system, every value is
-- a string and on the top level they get substituted verbatim into the page.
--
-- For example, you can build a context that contains
--
-- > … <> functionField "concat" (const . concat) <> …
--
-- which will allow you to use the @concat@ identifier as a function that takes
-- arbitrarily many stings and concatenates them to a new string:
--
-- > $partial(concat("templates/categories/", category))$
--
-- This will evaluate the @category@ field in the context, then prepend the path,
-- and include the referenced file as a template.


--------------------------------------------------------------------------------
{-# 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)


--------------------------------------------------------------------------------
-- | Mostly for internal usage
data ContextField
    = EmptyField
    | StringField String
    | forall a. ListField (Context a) [Item a]


--------------------------------------------------------------------------------
-- | The 'Context' monoid. Please note that the order in which you
-- compose the items is important. For example in
--
-- > field "A" f1 <> field "A" f2
--
-- the first context will overwrite the second. This is especially
-- important when something is being composed with
-- 'metadataField' (or 'defaultContext'). If you want your context to be
-- overwritten by the metadata fields, compose it from the right:
--
-- @
-- 'metadataField' \<\> field \"date\" fDate
-- @
--
newtype Context a = Context
    { Context a -> String -> [String] -> Item a -> Compiler ContextField
unContext :: String -> [String] -> Item a -> Compiler ContextField
    }


--------------------------------------------------------------------------------
-- | Tries to find a key in the left context,
-- or when that fails in the right context.
#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


--------------------------------------------------------------------------------
-- | Constructs a new field for a 'Context'.
-- If the key matches, the compiler is run and its result is substituted in the
-- template.
--
-- If the compiler fails, the field will be considered non-existent
-- in an @$if()$@ macro or ultimately break the template application
-- (unless the key is found in another context when using '<>').
-- Use 'empty' or 'noResult' for intentional failures of fields used in
-- @$if()$@, to distinguish them from exceptions thrown with 'fail'.
field
    :: String                      -- ^ Key
    -> (Item a -> Compiler String) -- ^ Function that constructs a value based
                                   -- on the item (e.g. accessing metadata)
    -> 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)


--------------------------------------------------------------------------------
-- | Creates a 'field' to use with the @$if()$@ template macro.
-- Attempting to substitute the field into the template will cause an error.
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")


--------------------------------------------------------------------------------
-- | Creates a 'field' that does not depend on the 'Item' but always yields
-- the same string
constField :: String     -- ^ Key
           -> String     -- ^ Value
           -> 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


--------------------------------------------------------------------------------
-- | Creates a list field to be consumed by a @$for(…)$@ expression.
-- The compiler returns multiple items which are rendered in the loop body
-- with the supplied context.
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)


--------------------------------------------------------------------------------
-- | Creates a list field like 'listField', but supplies the current page
-- to the compiler.
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


--------------------------------------------------------------------------------
-- | Creates a variadic function field.
--
-- The function will be called with the dynamically evaluated string arguments
-- from the template as well as the page that is currently rendered.
functionField :: String                                  -- ^ Key
              -> ([String] -> Item a -> Compiler String) -- ^ Function
              -> 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


--------------------------------------------------------------------------------
-- | Transform the respective string results of all fields in a context.
-- For example,
--
-- > mapContext (++"c") (constField "x" "a" <> constField "y" "b")
--
-- is equivalent to
--
-- > constField "x" "ac" <> constField "y" "bc"
--
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
"!"

--------------------------------------------------------------------------------
-- | A context that allows snippet inclusion. In processed file, use as:
--
-- > ...
-- > $snippet("path/to/snippet/")$
-- > ...
--
-- The contents of the included file will not be interpolated like @partial@
-- does it.
--
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()'"

--------------------------------------------------------------------------------
-- | A context that contains (in that order)
--
--     1. A @$body$@ field
--
--     2. Metadata fields
--
--     3. A @$url$@ 'urlField'
--
--     4. A @$path$@ 'pathField'
--
--     5. A @$title$@ 'titleField'
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-->"


--------------------------------------------------------------------------------
-- | Constructs a 'field' that contains the body of the item.
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


--------------------------------------------------------------------------------
-- | Map any field to its metadata value, if present
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


--------------------------------------------------------------------------------
-- | Absolute url to the resulting item
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


--------------------------------------------------------------------------------
-- | Filepath of the underlying file of the item
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


--------------------------------------------------------------------------------
-- | This title 'field' takes the basename of the underlying file by default
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


--------------------------------------------------------------------------------
-- | When the metadata has a field called @published@ in one of the
-- following formats then this function can render the date.
--
--   * @Mon, 06 Sep 2010 00:01:00 +0000@
--
--   * @Mon, 06 Sep 2010 00:01:00 UTC@
--
--   * @Mon, 06 Sep 2010 00:01:00@
--
--   * @2010-09-06T00:01:00+0000@
--
--   * @2010-09-06T00:01:00Z@
--
--   * @2010-09-06T00:01:00@
--
--   * @2010-09-06 00:01:00+0000@
--
--   * @2010-09-06 00:01:00@
--
--   * @September 06, 2010 00:01 AM@
--
-- Following date-only formats are supported too (@00:00:00@ for time is
-- assumed)
--
--   * @2010-09-06@
--
--   * @September 06, 2010@
--
-- Alternatively, when the metadata has a field called @path@ in a
-- @folder/yyyy-mm-dd-title.extension@ format (the convention for pages)
-- and no @published@ metadata field set, this function can render
-- the date. This pattern matches the file name or directory names
-- that begins with @yyyy-mm-dd@ . For example:
-- @folder//yyyy-mm-dd-title//dist//main.extension@ .
-- In case of multiple matches, the rightmost one is used.
--
-- As another alternative, if none of the above matches, and the file has a
-- path which contains nested directories specifying a date, then that date
-- will be used. In other words, if the path is of the form
-- @**//yyyy//mm//dd//**//main.extension@ .
-- As above, in case of multiple matches, the rightmost one is used.

dateField :: String     -- ^ Key in which the rendered date should be placed
          -> String     -- ^ Format to use on the date
          -> Context a  -- ^ Resulting context
dateField :: String -> String -> Context a
dateField = TimeLocale -> String -> String -> Context a
forall a. TimeLocale -> String -> String -> Context a
dateFieldWith TimeLocale
defaultTimeLocale


--------------------------------------------------------------------------------
-- | This is an extended version of 'dateField' that allows you to
-- specify a time locale that is used for outputting the date. For more
-- details, see 'dateField' and 'formatTime'.
dateFieldWith :: TimeLocale  -- ^ Output time locale
              -> String      -- ^ Destination key
              -> String      -- ^ Format to use on the date
              -> Context a   -- ^ Resulting context
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


--------------------------------------------------------------------------------
-- | Parser to try to extract and parse the time from the @published@
-- field or from the filename. See 'dateField' for more information.
-- Exported for user convenience.
getItemUTC :: (MonadMetadata m, MonadFail m)
           => TimeLocale        -- ^ Output time locale
           -> Identifier        -- ^ Input page
           -> m UTCTime         -- ^ Parsed 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"
        ]


--------------------------------------------------------------------------------
-- | Get the time on which the actual file was last modified. This only works if
-- there actually is an underlying file, of couse.
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


--------------------------------------------------------------------------------
-- | Creates a field with the last modification date of the underlying item.
modificationTimeField :: String     -- ^ Key
                      -> String     -- ^ Format
                      -> Context  a -- ^ Resulting context
modificationTimeField :: String -> String -> Context a
modificationTimeField = TimeLocale -> String -> String -> Context a
forall a. TimeLocale -> String -> String -> Context a
modificationTimeFieldWith TimeLocale
defaultTimeLocale


--------------------------------------------------------------------------------
-- | Creates a field with the last modification date of the underlying item
-- in a custom localisation format (see 'formatTime').
modificationTimeFieldWith :: TimeLocale  -- ^ Time output locale
                          -> String      -- ^ Key
                          -> String      -- ^ Format
                          -> Context a   -- ^ Resulting context
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


--------------------------------------------------------------------------------
-- | A context with "teaser" key which contain a teaser of the item.
-- The item is loaded from the given snapshot (which should be saved
-- in the user code before any templates are applied).
teaserField :: String           -- ^ Key to use
            -> Snapshot         -- ^ Snapshot to load
            -> Context String   -- ^ Resulting context
teaserField :: String -> String -> Context String
teaserField = String -> String -> String -> Context String
teaserFieldWithSeparator String
teaserSeparator


--------------------------------------------------------------------------------
-- | A context with "teaser" key which contain a teaser of the item, defined as
-- the snapshot content before the teaser separator. The item is loaded from the
-- given snapshot (which should be saved in the user code before any templates
-- are applied).
teaserFieldWithSeparator :: String           -- ^ Separator to use
                         -> String           -- ^ Key to use
                         -> Snapshot         -- ^ Snapshot to load
                         -> Context String   -- ^ Resulting context
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


--------------------------------------------------------------------------------
-- | Constantly reports any field as missing. Mostly for internal usage,
-- it is the last choice in every context used in a template application.
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"