{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Hakyll.Web.Template.Internal
( Template (..)
, template
, templateBodyCompiler
, templateCompiler
, applyTemplate
, loadAndApplyTemplate
, applyAsTemplate
, readTemplate
, compileTemplateItem
, unsafeReadTemplateFile
, module Hakyll.Web.Template.Internal.Element
, module Hakyll.Web.Template.Internal.Trim
) where
import Control.Monad.Except (catchError)
import Data.Binary (Binary)
import Data.List (intercalate)
import qualified Data.List.NonEmpty as NonEmpty
import Data.Typeable (Typeable)
import GHC.Exts (IsString (..))
import GHC.Generics (Generic)
import Hakyll.Core.Compiler
import Hakyll.Core.Compiler.Internal
import Hakyll.Core.Identifier
import Hakyll.Core.Item
import Hakyll.Core.Writable
import Hakyll.Web.Template.Context
import Hakyll.Web.Template.Internal.Element
import Hakyll.Web.Template.Internal.Trim
data Template = Template
{ Template -> [TemplateElement]
tplElements :: [TemplateElement]
, Template -> FilePath
tplOrigin :: FilePath
} deriving (Int -> Template -> ShowS
[Template] -> ShowS
Template -> FilePath
(Int -> Template -> ShowS)
-> (Template -> FilePath) -> ([Template] -> ShowS) -> Show Template
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Template] -> ShowS
$cshowList :: [Template] -> ShowS
show :: Template -> FilePath
$cshow :: Template -> FilePath
showsPrec :: Int -> Template -> ShowS
$cshowsPrec :: Int -> Template -> ShowS
Show, Template -> Template -> Bool
(Template -> Template -> Bool)
-> (Template -> Template -> Bool) -> Eq Template
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Template -> Template -> Bool
$c/= :: Template -> Template -> Bool
== :: Template -> Template -> Bool
$c== :: Template -> Template -> Bool
Eq, (forall x. Template -> Rep Template x)
-> (forall x. Rep Template x -> Template) -> Generic Template
forall x. Rep Template x -> Template
forall x. Template -> Rep Template x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Template x -> Template
$cfrom :: forall x. Template -> Rep Template x
Generic, Get Template
[Template] -> Put
Template -> Put
(Template -> Put)
-> Get Template -> ([Template] -> Put) -> Binary Template
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [Template] -> Put
$cputList :: [Template] -> Put
get :: Get Template
$cget :: Get Template
put :: Template -> Put
$cput :: Template -> Put
Binary, Typeable)
instance Writable Template where
write :: FilePath -> Item Template -> IO ()
write FilePath
_ Item Template
_ = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
instance IsString Template where
fromString :: FilePath -> Template
fromString = FilePath -> Template
readTemplate
template :: FilePath -> [TemplateElement] -> Template
template :: FilePath -> [TemplateElement] -> Template
template FilePath
p = ([TemplateElement] -> FilePath -> Template)
-> FilePath -> [TemplateElement] -> Template
forall a b c. (a -> b -> c) -> b -> a -> c
flip [TemplateElement] -> FilePath -> Template
Template FilePath
p ([TemplateElement] -> Template)
-> ([TemplateElement] -> [TemplateElement])
-> [TemplateElement]
-> Template
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [TemplateElement] -> [TemplateElement]
trim
readTemplate :: String -> Template
readTemplate :: FilePath -> Template
readTemplate = (FilePath -> Template)
-> ([TemplateElement] -> Template)
-> Either FilePath [TemplateElement]
-> Template
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either FilePath -> Template
forall a. HasCallStack => FilePath -> a
error (FilePath -> [TemplateElement] -> Template
template FilePath
origin) (Either FilePath [TemplateElement] -> Template)
-> (FilePath -> Either FilePath [TemplateElement])
-> FilePath
-> Template
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath -> Either FilePath [TemplateElement]
parseTemplateElemsFile FilePath
origin
where
origin :: FilePath
origin = FilePath
"{literal}"
{-# DEPRECATED readTemplate "Use templateCompiler instead" #-}
compileTemplateItem :: Item String -> Compiler Template
compileTemplateItem :: Item FilePath -> Compiler Template
compileTemplateItem Item FilePath
item = let file :: Identifier
file = Item FilePath -> Identifier
forall a. Item a -> Identifier
itemIdentifier Item FilePath
item
in Identifier -> FilePath -> Compiler Template
compileTemplateFile Identifier
file (Item FilePath -> FilePath
forall a. Item a -> a
itemBody Item FilePath
item)
compileTemplateFile :: Identifier -> String -> Compiler Template
compileTemplateFile :: Identifier -> FilePath -> Compiler Template
compileTemplateFile Identifier
file = (FilePath -> Compiler Template)
-> ([TemplateElement] -> Compiler Template)
-> Either FilePath [TemplateElement]
-> Compiler Template
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either FilePath -> Compiler Template
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (Template -> Compiler Template
forall (m :: * -> *) a. Monad m => a -> m a
return (Template -> Compiler Template)
-> ([TemplateElement] -> Template)
-> [TemplateElement]
-> Compiler Template
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> [TemplateElement] -> Template
template FilePath
origin)
(Either FilePath [TemplateElement] -> Compiler Template)
-> (FilePath -> Either FilePath [TemplateElement])
-> FilePath
-> Compiler Template
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath -> Either FilePath [TemplateElement]
parseTemplateElemsFile FilePath
origin
where
origin :: FilePath
origin = Identifier -> FilePath
forall a. Show a => a -> FilePath
show Identifier
file
templateBodyCompiler :: Compiler (Item Template)
templateBodyCompiler :: Compiler (Item Template)
templateBodyCompiler = FilePath -> Compiler (Item Template) -> Compiler (Item Template)
forall a.
(Binary a, Typeable a) =>
FilePath -> Compiler a -> Compiler a
cached FilePath
"Hakyll.Web.Template.templateBodyCompiler" (Compiler (Item Template) -> Compiler (Item Template))
-> Compiler (Item Template) -> Compiler (Item Template)
forall a b. (a -> b) -> a -> b
$ do
Item FilePath
item <- Compiler (Item FilePath)
getResourceBody
Identifier
file <- Compiler Identifier
getUnderlying
(FilePath -> Compiler Template)
-> Item FilePath -> Compiler (Item Template)
forall a b. (a -> Compiler b) -> Item a -> Compiler (Item b)
withItemBody (Identifier -> FilePath -> Compiler Template
compileTemplateFile Identifier
file) Item FilePath
item
templateCompiler :: Compiler (Item Template)
templateCompiler :: Compiler (Item Template)
templateCompiler = FilePath -> Compiler (Item Template) -> Compiler (Item Template)
forall a.
(Binary a, Typeable a) =>
FilePath -> Compiler a -> Compiler a
cached FilePath
"Hakyll.Web.Template.templateCompiler" (Compiler (Item Template) -> Compiler (Item Template))
-> Compiler (Item Template) -> Compiler (Item Template)
forall a b. (a -> b) -> a -> b
$ do
Item FilePath
item <- Compiler (Item FilePath)
getResourceString
Identifier
file <- Compiler Identifier
getUnderlying
(FilePath -> Compiler Template)
-> Item FilePath -> Compiler (Item Template)
forall a b. (a -> Compiler b) -> Item a -> Compiler (Item b)
withItemBody (Identifier -> FilePath -> Compiler Template
compileTemplateFile Identifier
file) Item FilePath
item
applyTemplate :: Template
-> Context a
-> Item a
-> Compiler (Item String)
applyTemplate :: Template -> Context a -> Item a -> Compiler (Item FilePath)
applyTemplate Template
tpl Context a
context Item a
item = do
FilePath
body <- [TemplateElement] -> Context a -> Item a -> Compiler FilePath
forall a.
[TemplateElement] -> Context a -> Item a -> Compiler FilePath
applyTemplate' (Template -> [TemplateElement]
tplElements Template
tpl) Context a
context Item a
item Compiler FilePath
-> ([FilePath] -> Compiler FilePath) -> Compiler FilePath
forall e (m :: * -> *) a.
MonadError e m =>
m a -> (e -> m a) -> m a
`catchError` [FilePath] -> Compiler FilePath
forall (m :: * -> *) a. MonadFail m => [FilePath] -> m a
handler
Item FilePath -> Compiler (Item FilePath)
forall (m :: * -> *) a. Monad m => a -> m a
return (Item FilePath -> Compiler (Item FilePath))
-> Item FilePath -> Compiler (Item FilePath)
forall a b. (a -> b) -> a -> b
$ FilePath -> Item a -> Item FilePath
forall a b. a -> Item b -> Item a
itemSetBody FilePath
body Item a
item
where
tplName :: FilePath
tplName = Template -> FilePath
tplOrigin Template
tpl
itemName :: FilePath
itemName = Identifier -> FilePath
forall a. Show a => a -> FilePath
show (Identifier -> FilePath) -> Identifier -> FilePath
forall a b. (a -> b) -> a -> b
$ Item a -> Identifier
forall a. Item a -> Identifier
itemIdentifier Item a
item
handler :: [FilePath] -> m a
handler [FilePath]
es = FilePath -> m a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> m a) -> FilePath -> m a
forall a b. (a -> b) -> a -> b
$ FilePath
"Hakyll.Web.Template.applyTemplate: Failed to " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++
(if FilePath
tplName FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
itemName
then FilePath
"interpolate template in item " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
itemName
else FilePath
"apply template " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
tplName FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
" to item " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
itemName) FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++
FilePath
":\n" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath -> [FilePath] -> FilePath
forall a. [a] -> [[a]] -> [a]
intercalate FilePath
",\n" [FilePath]
es
applyTemplate'
:: forall a.
[TemplateElement]
-> Context a
-> Item a
-> Compiler String
applyTemplate' :: [TemplateElement] -> Context a -> Item a -> Compiler FilePath
applyTemplate' [TemplateElement]
tes Context a
context Item a
x = [TemplateElement] -> Compiler FilePath
go [TemplateElement]
tes
where
context' :: String -> [String] -> Item a -> Compiler ContextField
context' :: FilePath -> [FilePath] -> Item a -> Compiler ContextField
context' = Context a
-> FilePath -> [FilePath] -> Item a -> Compiler ContextField
forall a.
Context a
-> FilePath -> [FilePath] -> Item a -> Compiler ContextField
unContext (Context a
context Context a -> Context a -> Context a
forall a. Monoid a => a -> a -> a
`mappend` Context a
forall a. Context a
missingField)
go :: [TemplateElement] -> Compiler FilePath
go = ([FilePath] -> FilePath)
-> Compiler [FilePath] -> Compiler FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [FilePath] -> FilePath
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (Compiler [FilePath] -> Compiler FilePath)
-> ([TemplateElement] -> Compiler [FilePath])
-> [TemplateElement]
-> Compiler FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TemplateElement -> Compiler FilePath)
-> [TemplateElement] -> Compiler [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM TemplateElement -> Compiler FilePath
applyElem
applyElem :: TemplateElement -> Compiler String
applyElem :: TemplateElement -> Compiler FilePath
applyElem TemplateElement
TrimL = Compiler FilePath
forall a. Compiler a
trimError
applyElem TemplateElement
TrimR = Compiler FilePath
forall a. Compiler a
trimError
applyElem (Chunk FilePath
c) = FilePath -> Compiler FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
c
applyElem (Expr TemplateExpr
e) = FilePath -> Compiler FilePath -> Compiler FilePath
forall a. FilePath -> Compiler a -> Compiler a
withErrorMessage FilePath
evalMsg (FilePath -> TemplateExpr -> Compiler FilePath
applyStringExpr FilePath
typeMsg TemplateExpr
e)
where
evalMsg :: FilePath
evalMsg = FilePath
"In expr '$" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ TemplateExpr -> FilePath
forall a. Show a => a -> FilePath
show TemplateExpr
e FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"$'"
typeMsg :: FilePath
typeMsg = FilePath
"expr '$" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ TemplateExpr -> FilePath
forall a. Show a => a -> FilePath
show TemplateExpr
e FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"$'"
applyElem TemplateElement
Escaped = FilePath -> Compiler FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
"$"
applyElem (If TemplateExpr
e [TemplateElement]
t Maybe [TemplateElement]
mf) = Compiler ContextField
-> Compiler (Either (CompilerErrors FilePath) ContextField)
forall a.
Compiler a -> Compiler (Either (CompilerErrors FilePath) a)
compilerTry (TemplateExpr -> Compiler ContextField
applyExpr TemplateExpr
e) Compiler (Either (CompilerErrors FilePath) ContextField)
-> (Either (CompilerErrors FilePath) ContextField
-> Compiler FilePath)
-> Compiler FilePath
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Either (CompilerErrors FilePath) ContextField -> Compiler FilePath
forall b. Either (CompilerErrors FilePath) b -> Compiler FilePath
handle
where
f :: Compiler FilePath
f = Compiler FilePath
-> ([TemplateElement] -> Compiler FilePath)
-> Maybe [TemplateElement]
-> Compiler FilePath
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (FilePath -> Compiler FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
"") [TemplateElement] -> Compiler FilePath
go Maybe [TemplateElement]
mf
handle :: Either (CompilerErrors FilePath) b -> Compiler FilePath
handle (Right b
_) = [TemplateElement] -> Compiler FilePath
go [TemplateElement]
t
handle (Left (CompilationNoResult [FilePath]
_)) = Compiler FilePath
f
handle (Left (CompilationFailure NonEmpty FilePath
es)) = [FilePath] -> Compiler ()
debug (NonEmpty FilePath -> [FilePath]
forall a. NonEmpty a -> [a]
NonEmpty.toList NonEmpty FilePath
es) Compiler () -> Compiler FilePath -> Compiler FilePath
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Compiler FilePath
f
debug :: [FilePath] -> Compiler ()
debug = FilePath -> [FilePath] -> Compiler ()
compilerDebugEntries (FilePath
"Hakyll.Web.Template.applyTemplate: " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++
FilePath
"[ERROR] in 'if' condition on expr '" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ TemplateExpr -> FilePath
forall a. Show a => a -> FilePath
show TemplateExpr
e FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"':")
applyElem (For TemplateExpr
e [TemplateElement]
b Maybe [TemplateElement]
s) = FilePath -> Compiler ContextField -> Compiler ContextField
forall a. FilePath -> Compiler a -> Compiler a
withErrorMessage FilePath
headMsg (TemplateExpr -> Compiler ContextField
applyExpr TemplateExpr
e) Compiler ContextField
-> (ContextField -> Compiler FilePath) -> Compiler FilePath
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ContextField
cf -> case ContextField
cf of
ContextField
EmptyField -> FilePath -> FilePath -> FilePath -> Compiler FilePath
forall (m :: * -> *) a.
MonadFail m =>
FilePath -> FilePath -> FilePath -> m a
expected FilePath
"list" FilePath
"boolean" FilePath
typeMsg
StringField FilePath
_ -> FilePath -> FilePath -> FilePath -> Compiler FilePath
forall (m :: * -> *) a.
MonadFail m =>
FilePath -> FilePath -> FilePath -> m a
expected FilePath
"list" FilePath
"string" FilePath
typeMsg
ListField Context a
c [Item a]
xs -> FilePath -> Compiler FilePath -> Compiler FilePath
forall a. FilePath -> Compiler a -> Compiler a
withErrorMessage FilePath
bodyMsg (Compiler FilePath -> Compiler FilePath)
-> Compiler FilePath -> Compiler FilePath
forall a b. (a -> b) -> a -> b
$ do
FilePath
sep <- Compiler FilePath
-> ([TemplateElement] -> Compiler FilePath)
-> Maybe [TemplateElement]
-> Compiler FilePath
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (FilePath -> Compiler FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
"") [TemplateElement] -> Compiler FilePath
go Maybe [TemplateElement]
s
[FilePath]
bs <- (Item a -> Compiler FilePath) -> [Item a] -> Compiler [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ([TemplateElement] -> Context a -> Item a -> Compiler FilePath
forall a.
[TemplateElement] -> Context a -> Item a -> Compiler FilePath
applyTemplate' [TemplateElement]
b Context a
c) [Item a]
xs
FilePath -> Compiler FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> Compiler FilePath) -> FilePath -> Compiler FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> [FilePath] -> FilePath
forall a. [a] -> [[a]] -> [a]
intercalate FilePath
sep [FilePath]
bs
where
headMsg :: FilePath
headMsg = FilePath
"In expr '$for(" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ TemplateExpr -> FilePath
forall a. Show a => a -> FilePath
show TemplateExpr
e FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
")$'"
typeMsg :: FilePath
typeMsg = FilePath
"loop expr '" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ TemplateExpr -> FilePath
forall a. Show a => a -> FilePath
show TemplateExpr
e FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"'"
bodyMsg :: FilePath
bodyMsg = FilePath
"In loop context of '$for(" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ TemplateExpr -> FilePath
forall a. Show a => a -> FilePath
show TemplateExpr
e FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
")$'"
applyElem (Partial TemplateExpr
e) = FilePath -> Compiler FilePath -> Compiler FilePath
forall a. FilePath -> Compiler a -> Compiler a
withErrorMessage FilePath
headMsg (Compiler FilePath -> Compiler FilePath)
-> Compiler FilePath -> Compiler FilePath
forall a b. (a -> b) -> a -> b
$
FilePath -> TemplateExpr -> Compiler FilePath
applyStringExpr FilePath
typeMsg TemplateExpr
e Compiler FilePath
-> (FilePath -> Compiler FilePath) -> Compiler FilePath
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \FilePath
p ->
FilePath -> Compiler FilePath -> Compiler FilePath
forall a. FilePath -> Compiler a -> Compiler a
withErrorMessage FilePath
inclMsg (Compiler FilePath -> Compiler FilePath)
-> Compiler FilePath -> Compiler FilePath
forall a b. (a -> b) -> a -> b
$ do
Template
tpl' <- Identifier -> Compiler Template
forall a. (Binary a, Typeable a) => Identifier -> Compiler a
loadBody (FilePath -> Identifier
fromFilePath FilePath
p)
Item FilePath -> FilePath
forall a. Item a -> a
itemBody (Item FilePath -> FilePath)
-> Compiler (Item FilePath) -> Compiler FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Template -> Context a -> Item a -> Compiler (Item FilePath)
forall a.
Template -> Context a -> Item a -> Compiler (Item FilePath)
applyTemplate Template
tpl' Context a
context Item a
x
where
headMsg :: FilePath
headMsg = FilePath
"In expr '$partial(" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ TemplateExpr -> FilePath
forall a. Show a => a -> FilePath
show TemplateExpr
e FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
")$'"
typeMsg :: FilePath
typeMsg = FilePath
"partial expr '" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ TemplateExpr -> FilePath
forall a. Show a => a -> FilePath
show TemplateExpr
e FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"'"
inclMsg :: FilePath
inclMsg = FilePath
"In inclusion of '$partial(" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ TemplateExpr -> FilePath
forall a. Show a => a -> FilePath
show TemplateExpr
e FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
")$'"
applyExpr :: TemplateExpr -> Compiler ContextField
applyExpr :: TemplateExpr -> Compiler ContextField
applyExpr (Ident (TemplateKey FilePath
k)) = FilePath -> [FilePath] -> Item a -> Compiler ContextField
context' FilePath
k [] Item a
x
applyExpr (Call (TemplateKey FilePath
k) [TemplateExpr]
args) = do
[FilePath]
args' <- (TemplateExpr -> Compiler FilePath)
-> [TemplateExpr] -> Compiler [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (\TemplateExpr
e -> FilePath -> TemplateExpr -> Compiler FilePath
applyStringExpr (TemplateExpr -> FilePath
forall a. Show a => a -> FilePath
typeMsg TemplateExpr
e) TemplateExpr
e) [TemplateExpr]
args
FilePath -> [FilePath] -> Item a -> Compiler ContextField
context' FilePath
k [FilePath]
args' Item a
x
where
typeMsg :: a -> FilePath
typeMsg a
e = FilePath
"argument '" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> FilePath
forall a. Show a => a -> FilePath
show a
e FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"'"
applyExpr (StringLiteral FilePath
s) = ContextField -> Compiler ContextField
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> ContextField
StringField FilePath
s)
applyStringExpr :: String -> TemplateExpr -> Compiler String
applyStringExpr :: FilePath -> TemplateExpr -> Compiler FilePath
applyStringExpr FilePath
msg TemplateExpr
expr =
TemplateExpr -> Compiler ContextField
applyExpr TemplateExpr
expr Compiler ContextField
-> (ContextField -> Compiler FilePath) -> Compiler FilePath
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ContextField -> Compiler FilePath
forall (m :: * -> *). MonadFail m => ContextField -> m FilePath
getString
where
getString :: ContextField -> m FilePath
getString ContextField
EmptyField = FilePath -> FilePath -> FilePath -> m FilePath
forall (m :: * -> *) a.
MonadFail m =>
FilePath -> FilePath -> FilePath -> m a
expected FilePath
"string" FilePath
"boolean" FilePath
msg
getString (StringField FilePath
s) = FilePath -> m FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
s
getString (ListField Context a
_ [Item a]
_) = FilePath -> FilePath -> FilePath -> m FilePath
forall (m :: * -> *) a.
MonadFail m =>
FilePath -> FilePath -> FilePath -> m a
expected FilePath
"string" FilePath
"list" FilePath
msg
expected :: FilePath -> FilePath -> FilePath -> m a
expected FilePath
typ FilePath
act FilePath
expr = FilePath -> m a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> m a) -> FilePath -> m a
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
unwords [FilePath
"Hakyll.Web.Template.applyTemplate:",
FilePath
"expected", FilePath
typ, FilePath
"but got", FilePath
act, FilePath
"for", FilePath
expr]
trimError :: Compiler a
trimError = FilePath -> Compiler a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Compiler a) -> FilePath -> Compiler a
forall a b. (a -> b) -> a -> b
$
FilePath
"Hakyll.Web.Template.applyTemplate: template not fully trimmed."
loadAndApplyTemplate :: Identifier
-> Context a
-> Item a
-> Compiler (Item String)
loadAndApplyTemplate :: Identifier -> Context a -> Item a -> Compiler (Item FilePath)
loadAndApplyTemplate Identifier
identifier Context a
context Item a
item = do
Template
tpl <- Identifier -> Compiler Template
forall a. (Binary a, Typeable a) => Identifier -> Compiler a
loadBody Identifier
identifier
Template -> Context a -> Item a -> Compiler (Item FilePath)
forall a.
Template -> Context a -> Item a -> Compiler (Item FilePath)
applyTemplate Template
tpl Context a
context Item a
item
applyAsTemplate :: Context String
-> Item String
-> Compiler (Item String)
applyAsTemplate :: Context FilePath -> Item FilePath -> Compiler (Item FilePath)
applyAsTemplate Context FilePath
context Item FilePath
item = do
Template
tpl <- Item FilePath -> Compiler Template
compileTemplateItem Item FilePath
item
Template
-> Context FilePath -> Item FilePath -> Compiler (Item FilePath)
forall a.
Template -> Context a -> Item a -> Compiler (Item FilePath)
applyTemplate Template
tpl Context FilePath
context Item FilePath
item
unsafeReadTemplateFile :: FilePath -> Compiler Template
unsafeReadTemplateFile :: FilePath -> Compiler Template
unsafeReadTemplateFile FilePath
file = do
FilePath
tpl <- IO FilePath -> Compiler FilePath
forall a. IO a -> Compiler a
unsafeCompiler (IO FilePath -> Compiler FilePath)
-> IO FilePath -> Compiler FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
readFile FilePath
file
Identifier -> FilePath -> Compiler Template
compileTemplateFile (FilePath -> Identifier
fromFilePath FilePath
file) FilePath
tpl
{-# DEPRECATED unsafeReadTemplateFile "Use templateCompiler" #-}