module Hakyll.Web.Pandoc
(
readPandoc
, readPandocWith
, writePandoc
, writePandocWith
, renderPandoc
, renderPandocWith
, pandocCompiler
, pandocCompilerWith
, pandocCompilerWithTransform
, pandocCompilerWithTransformM
, defaultHakyllReaderOptions
, defaultHakyllWriterOptions
) where
import qualified Data.Text as T
import Text.Pandoc
import Text.Pandoc.Highlighting (pygments)
import Hakyll.Core.Compiler
import Hakyll.Core.Item
import Hakyll.Web.Pandoc.FileType
readPandoc
:: Item String
-> Compiler (Item Pandoc)
readPandoc = readPandocWith defaultHakyllReaderOptions
readPandocWith
:: ReaderOptions
-> Item String
-> Compiler (Item Pandoc)
readPandocWith ropt item =
case runPure $ traverse (reader ropt (itemFileType item)) (fmap T.pack item) of
Left err -> fail $
"Hakyll.Web.Pandoc.readPandocWith: parse failed: " ++ show err
Right item' -> return item'
where
reader ro t = case t of
DocBook -> readDocBook ro
Html -> readHtml ro
LaTeX -> readLaTeX ro
LiterateHaskell t' -> reader (addExt ro Ext_literate_haskell) t'
Markdown -> readMarkdown ro
MediaWiki -> readMediaWiki ro
OrgMode -> readOrg ro
Rst -> readRST ro
Textile -> readTextile ro
_ -> error $
"Hakyll.Web.readPandocWith: I don't know how to read a file of " ++
"the type " ++ show t ++ " for: " ++ show (itemIdentifier item)
addExt ro e = ro {readerExtensions = enableExtension e $ readerExtensions ro}
writePandoc :: Item Pandoc
-> Item String
writePandoc = writePandocWith defaultHakyllWriterOptions
writePandocWith :: WriterOptions
-> Item Pandoc
-> Item String
writePandocWith wopt (Item itemi doc) =
case runPure $ writeHtml5String wopt doc of
Left err -> error $ "Hakyll.Web.Pandoc.writePandocWith: " ++ show err
Right item' -> Item itemi $ T.unpack item'
renderPandoc :: Item String -> Compiler (Item String)
renderPandoc =
renderPandocWith defaultHakyllReaderOptions defaultHakyllWriterOptions
renderPandocWith
:: ReaderOptions -> WriterOptions -> Item String -> Compiler (Item String)
renderPandocWith ropt wopt item =
writePandocWith wopt <$> readPandocWith ropt item
pandocCompiler :: Compiler (Item String)
pandocCompiler =
pandocCompilerWith defaultHakyllReaderOptions defaultHakyllWriterOptions
pandocCompilerWith :: ReaderOptions -> WriterOptions -> Compiler (Item String)
pandocCompilerWith ropt wopt =
cached "Hakyll.Web.Pandoc.pandocCompilerWith" $
pandocCompilerWithTransform ropt wopt id
pandocCompilerWithTransform :: ReaderOptions -> WriterOptions
-> (Pandoc -> Pandoc)
-> Compiler (Item String)
pandocCompilerWithTransform ropt wopt f =
pandocCompilerWithTransformM ropt wopt (return . f)
pandocCompilerWithTransformM :: ReaderOptions -> WriterOptions
-> (Pandoc -> Compiler Pandoc)
-> Compiler (Item String)
pandocCompilerWithTransformM ropt wopt f =
writePandocWith wopt <$>
(traverse f =<< readPandocWith ropt =<< getResourceBody)
defaultHakyllReaderOptions :: ReaderOptions
defaultHakyllReaderOptions = def
{
readerExtensions = enableExtension Ext_smart pandocExtensions
}
defaultHakyllWriterOptions :: WriterOptions
defaultHakyllWriterOptions = def
{
writerExtensions = enableExtension Ext_smart pandocExtensions
,
writerHighlightStyle = Just pygments
}