summaryrefslogtreecommitdiff
path: root/lib/Hakyll/Web/Pandoc
diff options
context:
space:
mode:
authorJasper Van der Jeugt <m@jaspervdj.be>2017-06-19 11:57:23 +0200
committerJasper Van der Jeugt <m@jaspervdj.be>2017-06-19 11:57:23 +0200
commit67ecff7ad383640bc73d64edc2506c7cc648a134 (patch)
tree6d328e43c3ab86c29a2d775fabaa23618c16fb51 /lib/Hakyll/Web/Pandoc
parent2df3209bafa08e6b77ee4a8598fc503269513527 (diff)
downloadhakyll-67ecff7ad383640bc73d64edc2506c7cc648a134.tar.gz
Move src/ to lib/, put Init.hs in src/
Diffstat (limited to 'lib/Hakyll/Web/Pandoc')
-rw-r--r--lib/Hakyll/Web/Pandoc/Biblio.hs115
-rw-r--r--lib/Hakyll/Web/Pandoc/Binary.hs32
-rw-r--r--lib/Hakyll/Web/Pandoc/FileType.hs74
3 files changed, 221 insertions, 0 deletions
diff --git a/lib/Hakyll/Web/Pandoc/Biblio.hs b/lib/Hakyll/Web/Pandoc/Biblio.hs
new file mode 100644
index 0000000..dfe6d93
--- /dev/null
+++ b/lib/Hakyll/Web/Pandoc/Biblio.hs
@@ -0,0 +1,115 @@
+--------------------------------------------------------------------------------
+-- | Wraps pandocs bibiliography handling
+--
+-- In order to add a bibliography, you will need a bibliography file (e.g.
+-- @.bib@) and a CSL file (@.csl@). Both need to be compiled with their
+-- respective compilers ('biblioCompiler' and 'cslCompiler'). Then, you can
+-- refer to these files when you use 'readPandocBiblio'. This function also
+-- takes the reader options for completeness -- you can use
+-- 'defaultHakyllReaderOptions' if you're unsure.
+-- 'pandocBiblioCompiler' is a convenience wrapper which works like 'pandocCompiler',
+-- but also takes paths to compiled bibliography and csl files.
+{-# LANGUAGE Arrows #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+module Hakyll.Web.Pandoc.Biblio
+ ( CSL
+ , cslCompiler
+ , Biblio (..)
+ , biblioCompiler
+ , readPandocBiblio
+ , pandocBiblioCompiler
+ ) where
+
+
+--------------------------------------------------------------------------------
+import Control.Monad (liftM, replicateM)
+import Data.Binary (Binary (..))
+import Data.Default (def)
+import Data.Typeable (Typeable)
+import Hakyll.Core.Compiler
+import Hakyll.Core.Identifier
+import Hakyll.Core.Item
+import Hakyll.Core.Writable
+import Hakyll.Web.Pandoc
+import Hakyll.Web.Pandoc.Binary ()
+import qualified Text.CSL as CSL
+import Text.CSL.Pandoc (processCites)
+import Text.Pandoc (Pandoc, ReaderOptions (..))
+
+
+--------------------------------------------------------------------------------
+data CSL = CSL
+ deriving (Show, Typeable)
+
+
+--------------------------------------------------------------------------------
+instance Binary CSL where
+ put CSL = return ()
+ get = return CSL
+
+
+--------------------------------------------------------------------------------
+instance Writable CSL where
+ -- Shouldn't be written.
+ write _ _ = return ()
+
+
+--------------------------------------------------------------------------------
+cslCompiler :: Compiler (Item CSL)
+cslCompiler = makeItem CSL
+
+
+--------------------------------------------------------------------------------
+newtype Biblio = Biblio [CSL.Reference]
+ deriving (Show, Typeable)
+
+
+--------------------------------------------------------------------------------
+instance Binary Biblio where
+ -- Ugly.
+ get = do
+ len <- get
+ Biblio <$> replicateM len get
+ put (Biblio rs) = put (length rs) >> mapM_ put rs
+
+
+--------------------------------------------------------------------------------
+instance Writable Biblio where
+ -- Shouldn't be written.
+ write _ _ = return ()
+
+
+--------------------------------------------------------------------------------
+biblioCompiler :: Compiler (Item Biblio)
+biblioCompiler = do
+ filePath <- toFilePath <$> getUnderlying
+ makeItem =<< unsafeCompiler (Biblio <$> CSL.readBiblioFile filePath)
+
+
+--------------------------------------------------------------------------------
+readPandocBiblio :: ReaderOptions
+ -> Item CSL
+ -> Item Biblio
+ -> (Item String)
+ -> Compiler (Item Pandoc)
+readPandocBiblio ropt csl biblio item = do
+ -- Parse CSL file, if given
+ style <- unsafeCompiler $ CSL.readCSLFile Nothing . toFilePath . itemIdentifier $ csl
+
+ -- We need to know the citation keys, add then *before* actually parsing the
+ -- actual page. If we don't do this, pandoc won't even consider them
+ -- citations!
+ let Biblio refs = itemBody biblio
+ pandoc <- itemBody <$> readPandocWith ropt item
+ let pandoc' = processCites style refs pandoc
+
+ return $ fmap (const pandoc') item
+
+--------------------------------------------------------------------------------
+pandocBiblioCompiler :: String -> String -> Compiler (Item String)
+pandocBiblioCompiler cslFileName bibFileName = do
+ csl <- load $ fromFilePath cslFileName
+ bib <- load $ fromFilePath bibFileName
+ liftM writePandoc
+ (getResourceBody >>= readPandocBiblio def csl bib)
diff --git a/lib/Hakyll/Web/Pandoc/Binary.hs b/lib/Hakyll/Web/Pandoc/Binary.hs
new file mode 100644
index 0000000..3c5b5a3
--- /dev/null
+++ b/lib/Hakyll/Web/Pandoc/Binary.hs
@@ -0,0 +1,32 @@
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+{-# LANGUAGE DeriveGeneric #-}
+module Hakyll.Web.Pandoc.Binary where
+
+import Data.Binary (Binary (..))
+
+import qualified Text.CSL as CSL
+import qualified Text.CSL.Reference as REF
+import qualified Text.CSL.Style as STY
+import Text.Pandoc
+
+--------------------------------------------------------------------------------
+-- orphans
+
+instance Binary Alignment
+instance Binary Block
+instance Binary CSL.Reference
+instance Binary Citation
+instance Binary CitationMode
+instance Binary Format
+instance Binary Inline
+instance Binary ListNumberDelim
+instance Binary ListNumberStyle
+instance Binary MathType
+instance Binary QuoteType
+instance Binary REF.CLabel
+instance Binary REF.CNum
+instance Binary REF.Literal
+instance Binary REF.RefDate
+instance Binary REF.RefType
+instance Binary STY.Agent
+instance Binary STY.Formatted
diff --git a/lib/Hakyll/Web/Pandoc/FileType.hs b/lib/Hakyll/Web/Pandoc/FileType.hs
new file mode 100644
index 0000000..3636e41
--- /dev/null
+++ b/lib/Hakyll/Web/Pandoc/FileType.hs
@@ -0,0 +1,74 @@
+--------------------------------------------------------------------------------
+-- | A module dealing with pandoc file extensions and associated file types
+module Hakyll.Web.Pandoc.FileType
+ ( FileType (..)
+ , fileType
+ , itemFileType
+ ) where
+
+
+--------------------------------------------------------------------------------
+import System.FilePath (splitExtension)
+
+
+--------------------------------------------------------------------------------
+import Hakyll.Core.Identifier
+import Hakyll.Core.Item
+
+
+--------------------------------------------------------------------------------
+-- | Datatype to represent the different file types Hakyll can deal with by
+-- default
+data FileType
+ = Binary
+ | Css
+ | DocBook
+ | Html
+ | LaTeX
+ | LiterateHaskell FileType
+ | Markdown
+ | MediaWiki
+ | OrgMode
+ | PlainText
+ | Rst
+ | Textile
+ deriving (Eq, Ord, Show, Read)
+
+
+--------------------------------------------------------------------------------
+-- | Get the file type for a certain file. The type is determined by extension.
+fileType :: FilePath -> FileType
+fileType = uncurry fileType' . splitExtension
+ where
+ fileType' _ ".css" = Css
+ fileType' _ ".dbk" = DocBook
+ fileType' _ ".htm" = Html
+ fileType' _ ".html" = Html
+ fileType' f ".lhs" = LiterateHaskell $ case fileType f of
+ -- If no extension is given, default to Markdown + LiterateHaskell
+ Binary -> Markdown
+ -- Otherwise, LaTeX + LiterateHaskell or whatever the user specified
+ x -> x
+ fileType' _ ".markdown" = Markdown
+ fileType' _ ".mediawiki" = MediaWiki
+ fileType' _ ".md" = Markdown
+ fileType' _ ".mdn" = Markdown
+ fileType' _ ".mdown" = Markdown
+ fileType' _ ".mdwn" = Markdown
+ fileType' _ ".mkd" = Markdown
+ fileType' _ ".mkdwn" = Markdown
+ fileType' _ ".org" = OrgMode
+ fileType' _ ".page" = Markdown
+ fileType' _ ".rst" = Rst
+ fileType' _ ".tex" = LaTeX
+ fileType' _ ".text" = PlainText
+ fileType' _ ".textile" = Textile
+ fileType' _ ".txt" = PlainText
+ fileType' _ ".wiki" = MediaWiki
+ fileType' _ _ = Binary -- Treat unknown files as binary
+
+
+--------------------------------------------------------------------------------
+-- | Get the file type for the current file
+itemFileType :: Item a -> FileType
+itemFileType = fileType . toFilePath . itemIdentifier