summaryrefslogtreecommitdiff
path: root/src/Hakyll/Web
diff options
context:
space:
mode:
authorJasper Van der Jeugt <jaspervdj@gmail.com>2011-02-26 15:49:11 +0100
committerJasper Van der Jeugt <jaspervdj@gmail.com>2011-02-26 15:49:11 +0100
commit5c454fc2ced8364e000f8c9cc36387e39e001714 (patch)
tree59630d5dd2e19162cccba2381b54a2d052b49bd5 /src/Hakyll/Web
parented12fd21200bad030eeb8d2ccf2d0acdbdc73949 (diff)
downloadhakyll-5c454fc2ced8364e000f8c9cc36387e39e001714.tar.gz
Fix $body$ bug, add `traceShowCompiler`
Diffstat (limited to 'src/Hakyll/Web')
-rw-r--r--src/Hakyll/Web/Page.hs12
-rw-r--r--src/Hakyll/Web/Page/Internal.hs12
-rw-r--r--src/Hakyll/Web/Template.hs6
3 files changed, 15 insertions, 15 deletions
diff --git a/src/Hakyll/Web/Page.hs b/src/Hakyll/Web/Page.hs
index c61008c..8a16ef8 100644
--- a/src/Hakyll/Web/Page.hs
+++ b/src/Hakyll/Web/Page.hs
@@ -61,8 +61,6 @@ import Prelude hiding (id)
import Control.Category (id)
import Control.Arrow (arr, (>>^), (&&&), (>>>))
import System.FilePath (takeBaseName, takeDirectory)
-import Data.Monoid (Monoid, mempty)
-import Data.Map (Map)
import qualified Data.Map as M
import Data.List (sortBy)
import Data.Ord (comparing)
@@ -82,16 +80,6 @@ import Hakyll.Web.Util.String
fromBody :: a -> Page a
fromBody = Page M.empty
--- | Create a metadata page, without a body
---
-fromMap :: Monoid a => Map String String -> Page a
-fromMap m = Page m mempty
-
--- | Convert a page to a map. The body will be placed in the @body@ key.
---
-toMap :: Page String -> Map String String
-toMap (Page m b) = M.insert "body" b m
-
-- | Read a page (do not render it)
--
readPageCompiler :: Compiler Resource (Page String)
diff --git a/src/Hakyll/Web/Page/Internal.hs b/src/Hakyll/Web/Page/Internal.hs
index dd47197..55067ed 100644
--- a/src/Hakyll/Web/Page/Internal.hs
+++ b/src/Hakyll/Web/Page/Internal.hs
@@ -3,6 +3,8 @@
{-# LANGUAGE DeriveDataTypeable #-}
module Hakyll.Web.Page.Internal
( Page (..)
+ , fromMap
+ , toMap
) where
import Control.Applicative ((<$>), (<*>))
@@ -36,3 +38,13 @@ instance Binary a => Binary (Page a) where
instance Writable a => Writable (Page a) where
write p (Page _ b) = write p b
+
+-- | Create a metadata page, without a body
+--
+fromMap :: Monoid a => Map String String -> Page a
+fromMap m = Page m mempty
+
+-- | Convert a page to a map. The body will be placed in the @body@ key.
+--
+toMap :: Page String -> Map String String
+toMap (Page m b) = M.insert "body" b m
diff --git a/src/Hakyll/Web/Template.hs b/src/Hakyll/Web/Template.hs
index 5b38ba3..9c49278 100644
--- a/src/Hakyll/Web/Template.hs
+++ b/src/Hakyll/Web/Template.hs
@@ -53,6 +53,7 @@ module Hakyll.Web.Template
import Control.Arrow
import Data.Maybe (fromMaybe)
import System.FilePath (takeExtension)
+import qualified Data.Map as M
import Text.Hamlet (HamletSettings, defaultHamletSettings)
@@ -62,7 +63,6 @@ import Hakyll.Core.ResourceProvider
import Hakyll.Web.Template.Internal
import Hakyll.Web.Template.Read
import Hakyll.Web.Page.Internal
-import Hakyll.Web.Page.Metadata
-- | Substitutes @$identifiers@ in the given @Template@ by values from the given
-- "Page". When a key is not found, it is left as it is. You can specify
@@ -72,9 +72,9 @@ applyTemplate :: Template -> Page String -> Page String
applyTemplate template page =
fmap (const $ substitute =<< unTemplate template) page
where
+ map' = toMap page
substitute (Chunk chunk) = chunk
- substitute (Key key) =
- fromMaybe ("$" ++ key ++ "$") $ getFieldMaybe key page
+ substitute (Key key) = fromMaybe ("$" ++ key ++ "$") $ M.lookup key map'
substitute (Escaped) = "$"
-- | Apply a page as it's own template. This is often very useful to fill in