Fix $body$ bug, add traceShowCompiler

This commit is contained in:
Jasper Van der Jeugt 2011-02-26 15:49:11 +01:00
parent ed12fd2120
commit 5c454fc2ce
4 changed files with 24 additions and 15 deletions

View file

@ -101,6 +101,7 @@ module Hakyll.Core.Compiler
, requireAllA , requireAllA
, cached , cached
, unsafeCompiler , unsafeCompiler
, traceShowCompiler
, mapCompiler , mapCompiler
, timedCompiler , timedCompiler
, byExtension , byExtension
@ -277,6 +278,14 @@ unsafeCompiler :: (a -> IO b) -- ^ Function to lift
-> Compiler a b -- ^ Resulting compiler -> Compiler a b -- ^ Resulting compiler
unsafeCompiler f = fromJob $ CompilerM . liftIO . f unsafeCompiler f = fromJob $ CompilerM . liftIO . f
-- | Compiler for debugging purposes
--
traceShowCompiler :: Show a => Compiler a a
traceShowCompiler = fromJob $ \x -> CompilerM $ do
logger <- compilerLogger <$> ask
report logger $ show x
return x
-- | Map over a compiler -- | Map over a compiler
-- --
mapCompiler :: Compiler a b mapCompiler :: Compiler a b

View file

@ -61,8 +61,6 @@ import Prelude hiding (id)
import Control.Category (id) import Control.Category (id)
import Control.Arrow (arr, (>>^), (&&&), (>>>)) import Control.Arrow (arr, (>>^), (&&&), (>>>))
import System.FilePath (takeBaseName, takeDirectory) import System.FilePath (takeBaseName, takeDirectory)
import Data.Monoid (Monoid, mempty)
import Data.Map (Map)
import qualified Data.Map as M import qualified Data.Map as M
import Data.List (sortBy) import Data.List (sortBy)
import Data.Ord (comparing) import Data.Ord (comparing)
@ -82,16 +80,6 @@ import Hakyll.Web.Util.String
fromBody :: a -> Page a fromBody :: a -> Page a
fromBody = Page M.empty 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) -- | Read a page (do not render it)
-- --
readPageCompiler :: Compiler Resource (Page String) readPageCompiler :: Compiler Resource (Page String)

View file

@ -3,6 +3,8 @@
{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveDataTypeable #-}
module Hakyll.Web.Page.Internal module Hakyll.Web.Page.Internal
( Page (..) ( Page (..)
, fromMap
, toMap
) where ) where
import Control.Applicative ((<$>), (<*>)) import Control.Applicative ((<$>), (<*>))
@ -36,3 +38,13 @@ instance Binary a => Binary (Page a) where
instance Writable a => Writable (Page a) where instance Writable a => Writable (Page a) where
write p (Page _ b) = write p b 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

View file

@ -53,6 +53,7 @@ module Hakyll.Web.Template
import Control.Arrow import Control.Arrow
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import System.FilePath (takeExtension) import System.FilePath (takeExtension)
import qualified Data.Map as M
import Text.Hamlet (HamletSettings, defaultHamletSettings) import Text.Hamlet (HamletSettings, defaultHamletSettings)
@ -62,7 +63,6 @@ import Hakyll.Core.ResourceProvider
import Hakyll.Web.Template.Internal import Hakyll.Web.Template.Internal
import Hakyll.Web.Template.Read import Hakyll.Web.Template.Read
import Hakyll.Web.Page.Internal import Hakyll.Web.Page.Internal
import Hakyll.Web.Page.Metadata
-- | Substitutes @$identifiers@ in the given @Template@ by values from the given -- | 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 -- "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 = applyTemplate template page =
fmap (const $ substitute =<< unTemplate template) page fmap (const $ substitute =<< unTemplate template) page
where where
map' = toMap page
substitute (Chunk chunk) = chunk substitute (Chunk chunk) = chunk
substitute (Key key) = substitute (Key key) = fromMaybe ("$" ++ key ++ "$") $ M.lookup key map'
fromMaybe ("$" ++ key ++ "$") $ getFieldMaybe key page
substitute (Escaped) = "$" substitute (Escaped) = "$"
-- | Apply a page as it's own template. This is often very useful to fill in -- | Apply a page as it's own template. This is often very useful to fill in