Rename pageCompiler to pandocCompiler

This commit is contained in:
Jasper Van der Jeugt 2012-12-15 18:02:47 +01:00
parent 3f42c9cd6f
commit e633df17dd
9 changed files with 40 additions and 102 deletions

View file

@ -18,14 +18,14 @@ main = hakyll $ do
match (fromList ["about.rst", "contact.markdown"]) $ do
route $ setExtension "html"
compile $ pageCompiler
compile $ pandocCompiler
>>= loadAndApplyTemplate "templates/default.html" defaultContext
>>= relativizeUrls
match "posts/*" $ do
route $ setExtension "html"
compile $ do
post <- pageCompiler
post <- pandocCompiler
saveSnapshot "content" post
return post
>>= loadAndApplyTemplate "templates/post.html" postCtx

View file

@ -126,7 +126,6 @@ Library
Hakyll.Main
Hakyll.Web.CompressCss
Hakyll.Web.Feed
Hakyll.Web.Page
Hakyll.Web.Pandoc
Hakyll.Web.Pandoc.Biblio
Hakyll.Web.Pandoc.FileType

View file

@ -20,7 +20,6 @@ module Hakyll
, module Hakyll.Main
, module Hakyll.Web.CompressCss
, module Hakyll.Web.Feed
, module Hakyll.Web.Page
, module Hakyll.Web.Pandoc
, module Hakyll.Web.Pandoc.Biblio
, module Hakyll.Web.Pandoc.FileType
@ -52,7 +51,6 @@ import Hakyll.Core.Writable.CopyFile
import Hakyll.Main
import Hakyll.Web.CompressCss
import Hakyll.Web.Feed
import Hakyll.Web.Page
import Hakyll.Web.Pandoc
import Hakyll.Web.Pandoc.Biblio
import Hakyll.Web.Pandoc.FileType

View file

@ -1,92 +0,0 @@
--------------------------------------------------------------------------------
-- | A page is a key-value mapping, representing a page on your site
--
-- A page is an important concept in Hakyll. It is a key-value mapping, and has
-- one field with an arbitrary type. A 'Page' thus consists of
--
-- * metadata (of the type @Map String String@);
--
-- * the actual value (of the type @a@).
--
-- Usually, the value will be a 'String' as well, and the value will be the body
-- of the page.
--
-- However, this is certainly no restriction. For example, @Page ByteString@
-- could be used to represent a binary item (e.g. an image) and some metadata.
--
-- Pages can be constructed using Haskell, but they are usually parsed from a
-- file. The file format for pages is pretty straightforward.
--
-- > This is a simple page
-- > consisting of two lines.
--
-- This is a valid page with two lines. If we load this in Hakyll, there would
-- be no metadata, and the body would be the given text. Let's look at a page
-- with some metadata:
--
-- > ---
-- > title: Alice's Adventures in Wonderland
-- > author: Lewis Caroll
-- > year: 1865
-- > ---
-- >
-- > Chapter I
-- > =========
-- >
-- > Down the Rabbit-Hole
-- > --------------------
-- >
-- > Alice was beginning to get very tired of sitting by her sister on the bank,
-- > and of having nothing to do: once or twice she had peeped into the book her
-- > sister was reading, but it had no pictures or conversations in it, "and
-- > what is the use of a book," thought Alice "without pictures or
-- > conversation?"
-- >
-- > ...
--
-- As you can see, we construct a metadata header in Hakyll using @---@. Then,
-- we simply list all @key: value@ pairs, and end with @---@ again. This page
-- contains three metadata fields and a body. The body is given in markdown
-- format, which can be easily rendered to HTML by Hakyll, using pandoc.
module Hakyll.Web.Page
( pageCompiler
, pageCompilerWith
, pageCompilerWithPandoc
) where
--------------------------------------------------------------------------------
import Control.Applicative ((<$>))
import Text.Pandoc (Pandoc, ParserState, WriterOptions)
--------------------------------------------------------------------------------
import Hakyll.Core.Compiler
import Hakyll.Core.Item
import Hakyll.Web.Pandoc
--------------------------------------------------------------------------------
-- | Read a page render using pandoc
pageCompiler :: Compiler (Item String)
pageCompiler =
pageCompilerWith defaultHakyllParserState defaultHakyllWriterOptions
--------------------------------------------------------------------------------
-- | A version of 'pageCompiler' which allows you to specify your own pandoc
-- options
pageCompilerWith :: ParserState -> WriterOptions -> Compiler (Item String)
pageCompilerWith state options = pageCompilerWithPandoc state options id
--------------------------------------------------------------------------------
-- | An extension of 'pageCompilerWith' which allows you to specify a custom
-- pandoc transformation for the content
pageCompilerWithPandoc :: ParserState -> WriterOptions
-> (Pandoc -> Pandoc)
-> Compiler (Item String)
pageCompilerWithPandoc state options f = cached cacheName $
writePandocWith options . fmap f . readPandocWith state <$> getResourceBody
where
cacheName = "Hakyll.Web.Page.pageCompilerWithPandoc"

View file

@ -1,5 +1,5 @@
--------------------------------------------------------------------------------
-- | Module exporting convenientpandoc bindings
-- | Module exporting convenient pandoc bindings
module Hakyll.Web.Pandoc
( -- * The basic building blocks
readPandoc
@ -9,6 +9,11 @@ module Hakyll.Web.Pandoc
, renderPandoc
, renderPandocWith
-- * Derived compilers
, pandocCompiler
, pandocCompilerWith
, pandocCompilerWithTransform
-- * Default options
, defaultHakyllParserState
, defaultHakyllWriterOptions
@ -16,10 +21,12 @@ module Hakyll.Web.Pandoc
--------------------------------------------------------------------------------
import Control.Applicative ((<$>))
import Text.Pandoc
--------------------------------------------------------------------------------
import Hakyll.Core.Compiler
import Hakyll.Core.Item
import Hakyll.Web.Pandoc.FileType
@ -78,6 +85,32 @@ renderPandocWith :: ParserState -> WriterOptions -> Item String -> Item String
renderPandocWith state options = writePandocWith options . readPandocWith state
--------------------------------------------------------------------------------
-- | Read a page render using pandoc
pandocCompiler :: Compiler (Item String)
pandocCompiler =
pandocCompilerWith defaultHakyllParserState defaultHakyllWriterOptions
--------------------------------------------------------------------------------
-- | A version of 'pandocCompiler' which allows you to specify your own pandoc
-- options
pandocCompilerWith :: ParserState -> WriterOptions -> Compiler (Item String)
pandocCompilerWith state options = pandocCompilerWithTransform state options id
--------------------------------------------------------------------------------
-- | An extension of 'pandocCompilerWith' which allows you to specify a custom
-- pandoc transformation for the content
pandocCompilerWithTransform :: ParserState -> WriterOptions
-> (Pandoc -> Pandoc)
-> Compiler (Item String)
pandocCompilerWithTransform state options f = cached cacheName $
writePandocWith options . fmap f . readPandocWith state <$> getResourceBody
where
cacheName = "Hakyll.Web.Page.pageCompilerWithPandoc"
--------------------------------------------------------------------------------
-- | The default reader options for pandoc parsing in hakyll
defaultHakyllParserState :: ParserState

View file

@ -20,7 +20,7 @@ import Hakyll.Core.Routes
import Hakyll.Core.Rules
import Hakyll.Core.Rules.Internal
import Hakyll.Core.Writable.CopyFile
import Hakyll.Web.Page
import Hakyll.Web.Pandoc
import TestSuite.Util
@ -61,7 +61,7 @@ rules = do
-- Compile some posts
match "*.md" $ do
route $ setExtension "html"
compile pageCompiler
compile pandocCompiler
-- Compile them, raw
match "*.md" $ version "raw" $ do

View file

@ -15,7 +15,7 @@ import Test.HUnit (Assertion, (@=?))
--------------------------------------------------------------------------------
import Hakyll.Core.Item
import Hakyll.Core.Provider
import Hakyll.Web.Page
import Hakyll.Web.Pandoc
import Hakyll.Web.Template
import Hakyll.Web.Template.Context
import TestSuite.Util
@ -36,7 +36,7 @@ case01 = withTestStore $ \store -> do
out <- resourceString provider "template.html.out"
tpl <- testCompilerDone store provider "template.html" $ templateCompiler
item <- testCompilerDone store provider "example.md" $
pageCompiler >>= applyTemplate (itemBody tpl) testContext
pandocCompiler >>= applyTemplate (itemBody tpl) testContext
out @=? itemBody item