summaryrefslogtreecommitdiff
path: root/src/Doc.lhs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Doc.lhs')
-rw-r--r--src/Doc.lhs78
1 files changed, 34 insertions, 44 deletions
diff --git a/src/Doc.lhs b/src/Doc.lhs
index 2f787d8..a0d5121 100644
--- a/src/Doc.lhs
+++ b/src/Doc.lhs
@@ -6,62 +6,32 @@ Building documentation
> {-# LANGUAGE OverloadedStrings #-}
> import Text.Pandoc
> import Text.Pandoc.Error (handleError)
-> import Text.Highlighting.Kate.Styles (tango)
-> import Data.List (stripPrefix)
-> import System.FilePath (replaceFileName)
-> import qualified Data.Set as S
+> import Text.Pandoc.Extensions (extensionsFromList)
+> import Text.Pandoc.Highlighting (tango)
+> import qualified Data.Text.IO as TIO
+> import System.Directory (setCurrentDirectory)
-The HTML documentation is generated directly from the source code of
-Codec.Pesto by running ``cabal run pesto-doc``. That module serves as starting
-point and it includes the other modules in a sensible order. Pandoc_ renders
-the restructuredText_ to HTML. We use a slightly modified template.
+The documentation can be generated running ``cabal run pesto-doc``. It is
+exclusively based on the restructuredText inside this packages’ literal Haskell
+source code.
-.. _pandoc: http://www.pandoc.org/
.. _restructuredText: http://docutils.sourceforge.net/rst.html
-> main = do
-> tpl <- readFile "template.html"
-> doc <- readWithInclude "src/Codec/Pesto.lhs"
-> writeFile "_build/index.html" $ rstToHtml tpl doc
-
-Since pandoc currently does not support restructured text’s include directive
-directly, emulate it by recursively replacing all lines starting with ``..
-include::`` with the referenced file’s contents.
-
-> readWithInclude f = do
-> c <- readFile f
-> let l = lines c
-> linc <- mapM (\line -> case stripPrefix ".. include:: " line of
-> Just incfile -> readWithInclude $ replaceFileName f incfile
-> Nothing -> return line) l
-> return $ unlines linc
-
-The resulting string is parsed as literate Haskell with restructuredText markup.
-
> readDoc = readRST def {
-> readerExtensions = S.fromList [
+> readerExtensions = extensionsFromList [
> Ext_literate_haskell
> , Ext_implicit_header_references
> ]
> , readerStandalone = True }
-Module definitions and imports should not be visible in the final
-documentation. They are marked up with the class ``nodoc`` and removed from the
-doctree before transforming it into HTML.
+.. _Pandoc: http://www.pandoc.org/
-> dropNoDoc = topDown f
-> where
-> f (Div (_, classes, _) _) | "nodoc" `elem` classes = Null
-> f x = x
+Pandoc_ outputs a single HTML5 page with syntax highlighting and MathJax for
+formulas.
-> rstToHtml tpl = writeDoc tpl . dropNoDoc . handleError . readDoc
-
-> writeDoc tpl = writeHtmlString def {
-> writerStandalone = True
-> , writerTemplate = tpl
-> , writerHtml5 = True
-> , writerHighlight = True
-> , writerHighlightStyle = tango
+> writeDoc tpl = writeHtml5String def {
+> writerTemplate = Just tpl
+> , writerHighlightStyle = Just tango
> , writerNumberSections = True
> , writerSectionDivs = True
> , writerTabStop = 4
@@ -69,3 +39,23 @@ doctree before transforming it into HTML.
> , writerVariables = [("css", "pesto.css"), ("lang", "en")]
> }
+A slightly customized template is used.
+
+> main = do
+> tpl <- readFile "template.html"
+
+The module Codec.Pesto serves as starting point and it includes every other
+module in a sensible order. For the relative includes to work, we need to
+change our current working directory.
+
+> setCurrentDirectory "src/Codec"
+> doc <- TIO.readFile "Pesto.lhs"
+> result <- runIO $ readDoc doc >>= writeDoc tpl
+> setCurrentDirectory "../../"
+> html <- handleError result
+
+Output is written to the directory ``_build``, which contains the corresponding
+stylesheet.
+
+> TIO.writeFile "_build/index.html" html
+