summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Hakyll.hs2
-rw-r--r--src/Hakyll/Core/Provider/Internal.hs4
-rw-r--r--src/Hakyll/Core/Routes.hs18
-rw-r--r--src/Hakyll/Web/Feed.hs1
-rw-r--r--src/Hakyll/Web/Template.hs85
-rw-r--r--src/Hakyll/Web/Template/Context.hs35
-rw-r--r--src/Hakyll/Web/Template/Internal.hs99
-rw-r--r--src/Hakyll/Web/Template/Read.hs93
8 files changed, 226 insertions, 111 deletions
diff --git a/src/Hakyll.hs b/src/Hakyll.hs
index f7113cd..edc79a0 100644
--- a/src/Hakyll.hs
+++ b/src/Hakyll.hs
@@ -28,7 +28,6 @@ module Hakyll
, module Hakyll.Web.Template
, module Hakyll.Web.Template.Context
, module Hakyll.Web.Template.List
- , module Hakyll.Web.Template.Read
) where
@@ -59,4 +58,3 @@ import Hakyll.Web.Tags
import Hakyll.Web.Template
import Hakyll.Web.Template.Context
import Hakyll.Web.Template.List
-import Hakyll.Web.Template.Read
diff --git a/src/Hakyll/Core/Provider/Internal.hs b/src/Hakyll/Core/Provider/Internal.hs
index d566f3a..fdf1342 100644
--- a/src/Hakyll/Core/Provider/Internal.hs
+++ b/src/Hakyll/Core/Provider/Internal.hs
@@ -174,7 +174,9 @@ resourceModified :: Provider -> Identifier -> Bool
resourceModified p r = case (ri, oldRi) of
(Nothing, _) -> False
(Just _, Nothing) -> True
- (Just n, Just o) -> resourceInfoModified n > resourceInfoModified o
+ (Just n, Just o) ->
+ resourceInfoModified n > resourceInfoModified o ||
+ resourceInfoMetadata n /= resourceInfoMetadata o
where
normal = setVersion Nothing r
ri = M.lookup normal (providerFiles p)
diff --git a/src/Hakyll/Core/Routes.hs b/src/Hakyll/Core/Routes.hs
index 34a613d..470d727 100644
--- a/src/Hakyll/Core/Routes.hs
+++ b/src/Hakyll/Core/Routes.hs
@@ -61,9 +61,16 @@ type UsedMetadata = Bool
--------------------------------------------------------------------------------
+data RoutesRead = RoutesRead
+ { routesProvider :: Provider
+ , routesUnderlying :: Identifier
+ }
+
+
+--------------------------------------------------------------------------------
-- | Type used for a route
newtype Routes = Routes
- { unRoutes :: Provider -> Identifier -> IO (Maybe FilePath, UsedMetadata)
+ { unRoutes :: RoutesRead -> Identifier -> IO (Maybe FilePath, UsedMetadata)
}
@@ -81,7 +88,8 @@ instance Monoid Routes where
-- | Apply a route to an identifier
runRoutes :: Routes -> Provider -> Identifier
-> IO (Maybe FilePath, UsedMetadata)
-runRoutes = unRoutes
+runRoutes routes provider identifier =
+ unRoutes routes (RoutesRead provider identifier) identifier
--------------------------------------------------------------------------------
@@ -156,9 +164,9 @@ gsubRoute pattern replacement = customRoute $
--------------------------------------------------------------------------------
-- | Get access to the metadata in order to determine the route
metadataRoute :: (Metadata -> Routes) -> Routes
-metadataRoute f = Routes $ \p i -> do
- metadata <- resourceMetadata p i
- unRoutes (f metadata) p i
+metadataRoute f = Routes $ \r i -> do
+ metadata <- resourceMetadata (routesProvider r) (routesUnderlying r)
+ unRoutes (f metadata) r i
--------------------------------------------------------------------------------
diff --git a/src/Hakyll/Web/Feed.hs b/src/Hakyll/Web/Feed.hs
index d394243..8c68a75 100644
--- a/src/Hakyll/Web/Feed.hs
+++ b/src/Hakyll/Web/Feed.hs
@@ -35,7 +35,6 @@ import Hakyll.Core.Item
import Hakyll.Web.Template
import Hakyll.Web.Template.Context
import Hakyll.Web.Template.List
-import Hakyll.Web.Template.Read
--------------------------------------------------------------------------------
diff --git a/src/Hakyll/Web/Template.hs b/src/Hakyll/Web/Template.hs
index 76911e0..086e9b2 100644
--- a/src/Hakyll/Web/Template.hs
+++ b/src/Hakyll/Web/Template.hs
@@ -33,12 +33,96 @@
--
-- 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.
+--
+-- Apart from interpolating @$key$@s from the 'Context' you can also
+-- use the following macros:
+--
+-- * @$if(key)$@
+--
+-- > $if(key)$
+-- > <b> Defined </b>
+-- > $else$
+-- > <b> Non-defined </b>
+-- > $endif$
+--
+-- This example will print @Defined@ if @key@ is defined in the
+-- context and @Non-defined@ otherwise. The @$else$@ clause is
+-- optional.
+--
+-- * @$for(key)$@
+--
+-- The @for@ macro is used for enumerating 'Context' elements that are
+-- lists, i.e. constructed using the 'listField' function. Assume that
+-- in a context we have an element @listField \"key\" c itms@. Then
+-- the snippet
+--
+-- > $for(key)$
+-- > $x$
+-- > $sep$,
+-- > $endfor$
+--
+-- would, for each item @i@ in 'itms', lookup @$x$@ in the context @c@
+-- with item @i@, interpolate it, and join the resulting list with
+-- @,@.
+--
+-- Another concrete example one may consider is the following. Given the
+-- context
+--
+-- > listField "things" (field "thing" (return . itemBody))
+-- > (sequence [makeItem "fruits", makeItem "vegetables"])
+--
+-- and a template
+--
+-- > I like
+-- > $for(things)$
+-- > fresh $thing$$sep$, and
+-- > $endfor$
+--
+-- the resulting page would look like
+--
+-- > <p>
+-- > I like
+-- >
+-- > fresh fruits, and
+-- >
+-- > fresh vegetables
+-- > </p>
+--
+-- The @$sep$@ part can be omitted. Usually, you can get by using the
+-- 'applyListTemplate' and 'applyJoinListTemplate' functions.
+--
+-- * @$partial(path)$@
+--
+-- Loads a template located in a separate file and interpolates it
+-- under the current context.
+--
+-- Assuming that the file @test.html@ contains
+--
+-- > <b>$key$</b>
+--
+-- The result of rendering
+--
+-- > <p>
+-- > $partial("test.html")$
+-- > </p>
+--
+-- is the same as the result of rendering
+--
+-- > <p>
+-- > <b>$key$</b>
+-- > </p>
+--
+-- That is, calling @$partial$@ is equivalent to just copying and pasting
+-- template code.
+--
+
module Hakyll.Web.Template
( Template
, templateCompiler
, applyTemplate
, loadAndApplyTemplate
, applyAsTemplate
+ , readTemplate
) where
@@ -56,7 +140,6 @@ import Hakyll.Core.Identifier
import Hakyll.Core.Item
import Hakyll.Web.Template.Context
import Hakyll.Web.Template.Internal
-import Hakyll.Web.Template.Read
--------------------------------------------------------------------------------
diff --git a/src/Hakyll/Web/Template/Context.hs b/src/Hakyll/Web/Template/Context.hs
index cd52eb0..a741272 100644
--- a/src/Hakyll/Web/Template/Context.hs
+++ b/src/Hakyll/Web/Template/Context.hs
@@ -56,6 +56,20 @@ data ContextField
--------------------------------------------------------------------------------
+-- | 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
{ unContext :: String -> Item a -> Compiler ContextField
}
@@ -73,11 +87,16 @@ field' key value = Context $ \k i -> if k == key then value i else empty
--------------------------------------------------------------------------------
-field :: String -> (Item a -> Compiler String) -> Context a
+-- | Constructs a new field in the 'Context.'
+field :: String -- ^ Key
+ -> (Item a -> Compiler String) -- ^ Function that constructs a
+ -- value based on the item
+ -> Context a
field key value = field' key (fmap StringField . value)
--------------------------------------------------------------------------------
+-- | Creates a 'field' that does not depend on the 'Item'
constField :: String -> String -> Context a
constField key = field key . const . return
@@ -108,6 +127,17 @@ mapContext f (Context c) = Context $ \k i -> do
--------------------------------------------------------------------------------
+-- | 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 =
bodyField "body" `mappend`
@@ -124,6 +154,7 @@ teaserSeparator = "<!--more-->"
--------------------------------------------------------------------------------
+-- | Constructs a 'field' that contains the body of the item.
bodyField :: String -> Context String
bodyField key = field key $ return . itemBody
@@ -150,7 +181,7 @@ pathField key = field key $ return . toFilePath . itemIdentifier
--------------------------------------------------------------------------------
--- | This title field takes the basename of the underlying file by default
+-- | This title 'field' takes the basename of the underlying file by default
titleField :: String -> Context a
titleField = mapContext takeBaseName . pathField
diff --git a/src/Hakyll/Web/Template/Internal.hs b/src/Hakyll/Web/Template/Internal.hs
index 138010e..4450a19 100644
--- a/src/Hakyll/Web/Template/Internal.hs
+++ b/src/Hakyll/Web/Template/Internal.hs
@@ -5,16 +5,22 @@
module Hakyll.Web.Template.Internal
( Template (..)
, TemplateElement (..)
+ , readTemplate
) where
--------------------------------------------------------------------------------
-import Control.Applicative (pure, (<$>), (<*>))
-import Data.Binary (Binary, get, getWord8, put, putWord8)
-import Data.Typeable (Typeable)
+import Control.Applicative (pure, (<$), (<$>), (<*>), (<|>))
+import Control.Monad (void)
+import Data.Binary (Binary, get, getWord8, put, putWord8)
+import Data.Typeable (Typeable)
+import GHC.Exts (IsString (..))
+import qualified Text.Parsec as P
+import qualified Text.Parsec.String as P
--------------------------------------------------------------------------------
+import Hakyll.Core.Util.Parser
import Hakyll.Core.Writable
@@ -46,10 +52,10 @@ data TemplateElement
--------------------------------------------------------------------------------
instance Binary TemplateElement where
put (Chunk string) = putWord8 0 >> put string
- put (Key key) = putWord8 1 >> put key
+ put (Key k) = putWord8 1 >> put k
put (Escaped) = putWord8 2
- put (If key t f) = putWord8 3 >> put key >> put t >> put f
- put (For key b s) = putWord8 4 >> put key >> put b >> put s
+ put (If k t f ) = putWord8 3 >> put k >> put t >> put f
+ put (For k b s) = putWord8 4 >> put k >> put b >> put s
put (Partial p) = putWord8 5 >> put p
get = getWord8 >>= \tag -> case tag of
@@ -61,3 +67,84 @@ instance Binary TemplateElement where
5 -> Partial <$> get
_ -> error $
"Hakyll.Web.Template.Internal: Error reading cached template"
+
+
+--------------------------------------------------------------------------------
+instance IsString Template where
+ fromString = readTemplate
+
+
+--------------------------------------------------------------------------------
+readTemplate :: String -> Template
+readTemplate input = case P.parse template "" input of
+ Left err -> error $ "Cannot parse template: " ++ show err
+ Right t -> t
+
+
+--------------------------------------------------------------------------------
+template :: P.Parser Template
+template = Template <$>
+ (P.many1 $ chunk <|> escaped <|> conditional <|> for <|> partial <|> key)
+
+
+--------------------------------------------------------------------------------
+chunk :: P.Parser TemplateElement
+chunk = Chunk <$> (P.many1 $ P.noneOf "$")
+
+
+--------------------------------------------------------------------------------
+escaped :: P.Parser TemplateElement
+escaped = Escaped <$ (P.try $ P.string "$$")
+
+
+--------------------------------------------------------------------------------
+conditional :: P.Parser TemplateElement
+conditional = P.try $ do
+ void $ P.string "$if("
+ i <- metadataKey
+ void $ P.string ")$"
+ thenBranch <- template
+ elseBranch <- P.optionMaybe $ P.try (P.string "$else$") >> template
+ void $ P.string "$endif$"
+ return $ If i thenBranch elseBranch
+
+
+--------------------------------------------------------------------------------
+for :: P.Parser TemplateElement
+for = P.try $ do
+ void $ P.string "$for("
+ i <- metadataKey
+ void $ P.string ")$"
+ body <- template
+ sep <- P.optionMaybe $ P.try (P.string "$sep$") >> template
+ void $ P.string "$endfor$"
+ return $ For i body sep
+
+
+--------------------------------------------------------------------------------
+partial :: P.Parser TemplateElement
+partial = P.try $ do
+ void $ P.string "$partial("
+ i <- stringLiteral
+ void $ P.string ")$"
+ return $ Partial i
+
+
+--------------------------------------------------------------------------------
+key :: P.Parser TemplateElement
+key = P.try $ do
+ void $ P.char '$'
+ k <- metadataKey
+ void $ P.char '$'
+ return $ Key k
+
+
+--------------------------------------------------------------------------------
+stringLiteral :: P.Parser String
+stringLiteral = do
+ void $ P.char '\"'
+ str <- P.many $ do
+ x <- P.noneOf "\""
+ if x == '\\' then P.anyChar else return x
+ void $ P.char '\"'
+ return str
diff --git a/src/Hakyll/Web/Template/Read.hs b/src/Hakyll/Web/Template/Read.hs
deleted file mode 100644
index 2421b2d..0000000
--- a/src/Hakyll/Web/Template/Read.hs
+++ /dev/null
@@ -1,93 +0,0 @@
---------------------------------------------------------------------------------
--- | Read templates in Hakyll's native format
-module Hakyll.Web.Template.Read
- ( readTemplate
- ) where
-
-
---------------------------------------------------------------------------------
-import Control.Applicative ((<$), (<$>))
-import Control.Monad (void)
-import Text.Parsec
-import Text.Parsec.String
-
-
---------------------------------------------------------------------------------
-import Hakyll.Core.Util.Parser
-import Hakyll.Web.Template.Internal
-
-
---------------------------------------------------------------------------------
-readTemplate :: String -> Template
-readTemplate input = case parse template "" input of
- Left err -> error $ "Cannot parse template: " ++ show err
- Right t -> t
-
-
---------------------------------------------------------------------------------
-template :: Parser Template
-template = Template <$>
- (many1 $ chunk <|> escaped <|> conditional <|> for <|> partial <|> key)
-
-
---------------------------------------------------------------------------------
-chunk :: Parser TemplateElement
-chunk = Chunk <$> (many1 $ noneOf "$")
-
-
---------------------------------------------------------------------------------
-escaped :: Parser TemplateElement
-escaped = Escaped <$ (try $ string "$$")
-
-
---------------------------------------------------------------------------------
-conditional :: Parser TemplateElement
-conditional = try $ do
- void $ string "$if("
- i <- metadataKey
- void $ string ")$"
- thenBranch <- template
- elseBranch <- optionMaybe $ try (string "$else$") >> template
- void $ string "$endif$"
- return $ If i thenBranch elseBranch
-
-
---------------------------------------------------------------------------------
-for :: Parser TemplateElement
-for = try $ do
- void $ string "$for("
- i <- metadataKey
- void $ string ")$"
- body <- template
- sep <- optionMaybe $ try (string "$sep$") >> template
- void $ string "$endfor$"
- return $ For i body sep
-
-
---------------------------------------------------------------------------------
-partial :: Parser TemplateElement
-partial = try $ do
- void $ string "$partial("
- i <- stringLiteral
- void $ string ")$"
- return $ Partial i
-
-
---------------------------------------------------------------------------------
-key :: Parser TemplateElement
-key = try $ do
- void $ char '$'
- k <- metadataKey
- void $ char '$'
- return $ Key k
-
-
---------------------------------------------------------------------------------
-stringLiteral :: Parser String
-stringLiteral = do
- void $ char '\"'
- str <- many $ do
- x <- noneOf "\""
- if x == '\\' then anyChar else return x
- void $ char '\"'
- return str