-- | This module provides means for reading and applying 'Template's. -- -- Templates are tools to convert data (pages) into a string. They are -- perfectly suited for laying out your site. -- -- Let's look at an example template: -- -- > -- > -- > My crazy homepage - $title$ -- > -- > -- > -- >
-- > $body$ -- >
-- > -- > -- > -- -- We can use this template to render a 'Page' which has a body and a @$title$@ -- metadata field. -- -- As you can see, the format is very simple -- @$key$@ is used to render the -- @$key$@ field from the page, everything else is literally copied. If you want -- to literally insert @\"$key$\"@ into your page (for example, when you're -- writing a Hakyll tutorial) you can use -- -- >

-- > A literal $$key$$. -- >

-- -- Because of it's simplicity, these templates can be used for more than HTML: -- you could make, for example, CSS or JS templates as well. -- -- In addition to the native format, Hakyll also supports hamlet templates. For -- more information on hamlet templates, please refer to: -- . Internally, hamlet templates are -- converted to hakyll templates -- which means that you can only use variable -- insertion (and not all hamlet's features). -- -- This is an example of a valid hamlet template. You should place them in -- files with a @.hamlet@ extension: -- -- > !!! -- > -- > -- > -- > MyAweSomeCompany - #{title} -- > <body> -- > <h1> MyAweSomeCompany - #{title} -- > <div id="navigation"> -- > <a href="/index.html"> Home -- > <a href="/about.html"> About -- > <a href="/code.html"> Code -- > #{body} {-# LANGUAGE Arrows #-} {-# LANGUAGE ScopedTypeVariables #-} module Hakyll.Web.Template ( Template , applyTemplate , templateCompiler , templateCompilerWith , applyTemplateCompiler ) where -------------------------------------------------------------------------------- import Control.Arrow import Control.Category (id) import qualified Data.Map as M import Data.Maybe (fromMaybe) import Data.Tuple (swap) import Prelude hiding (id) import System.FilePath (takeExtension) import Text.Hamlet (HamletSettings, defaultHamletSettings) -------------------------------------------------------------------------------- import Hakyll.Core.Compiler import Hakyll.Core.Identifier import Hakyll.Core.Util.Arrow import Hakyll.Web.Page.Internal import Hakyll.Web.Template.Context import Hakyll.Web.Template.Internal import Hakyll.Web.Template.Read -------------------------------------------------------------------------------- applyTemplate :: forall a b. (ArrowChoice a, ArrowMap a) => a (String, b) String -> a (Template, b) String applyTemplate context = arr (\(tpl, x) -> [(e, x) | e <- unTemplate tpl]) >>> mapA applyElement >>^ concat where applyElement :: a (TemplateElement, b) String applyElement = unElement >>> (id ||| context) unElement :: a (TemplateElement, b) (Either String (String, b)) unElement = arr $ \(e, x) -> case e of Chunk c -> Left c Escaped -> Left "$" Key k -> Right (k, x) -------------------------------------------------------------------------------- -- | Read a template. If the extension of the file we're compiling is -- @.hml@ or @.hamlet@, it will be considered as a Hamlet template, and parsed -- as such. templateCompiler :: Compiler () Template templateCompiler = templateCompilerWith defaultHamletSettings -------------------------------------------------------------------------------- -- | Version of 'templateCompiler' that enables custom settings. templateCompilerWith :: HamletSettings -> Compiler () Template templateCompilerWith settings = cached "Hakyll.Web.Template.templateCompilerWith" $ getIdentifier &&& getResourceString >>^ uncurry read' where read' identifier string = if takeExtension (toFilePath identifier) `elem` [".hml", ".hamlet"] -- Hamlet template then readHamletTemplateWith settings string -- Hakyll template else readTemplate string -------------------------------------------------------------------------------- applyTemplateCompiler :: Identifier Template -- ^ Template -> Context Page -- ^ Context -> Compiler Page Page -- ^ Compiler applyTemplateCompiler identifier context = requireA identifier $ arr swap >>> applyTemplate context' where context' = proc (k, x) -> do id' <- getIdentifier -< () context -< (k, (id', x))