readme-lhs-0.8.1: Literate programming support.
Safe HaskellNone
LanguageHaskell2010

Readme.Lhs

Description

Help for inserting programming output into an lhs or md-style file.

Synopsis

Usage

>>> :set -XOverloadedStrings
>>> import Readme.Lhs
>>> import Text.Pandoc.Builder as B
>>> let table1 = Table ("",["table","table-bordered","table-hover","m-3"],[("style","width: 70%;")]) (Caption Nothing [Plain [Str "an",Space,Str "example",Space,Str "table"]]) [(AlignLeft,ColWidthDefault),(AlignRight,ColWidthDefault)] (TableHead ("",[],[]) [Row ("",[],[]) [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "first",Space,Str "column"]],Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "second",Space,Str "column"]]]]) [TableBody ("",[],[]) (RowHeadColumns 0) [] [Row ("",[],[]) [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "first",Space,Str "row"]],Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "1"]]],Row ("",[],[]) [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "second",Space,Str "row"]],Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "1000"]]]]] (TableFoot ("",[],[]) [])

pandoc

data Flavour Source #

use LHS when you want to just add output to a *.lhs

use GitHubMarkdown for rendering code and results on github

The main differences between LHS and GitHubMarkdown is that GitHubMarkdown parses bird tracks as a BlockQuote.

>>> readPandoc "test/test.md" GitHubMarkdown
Right (Pandoc (Meta {unMeta = fromList []}) [Para [Str "haskell",Space,Str "LHS",Space,Str "style"],CodeBlock ("",["sourceCode","literate","haskell"],[]) "",Para [Str "bird-tracks"],BlockQuote [Para [Str "import",Space,Str "Readme.Lhs"]],Para [Str "code",Space,Str "block"],CodeBlock ("",[],[]) "indented\nunfenced code",Para [Str "github-style",Space,Str "fenced",Space,Str "code",Space,Str "blocks"],CodeBlock ("",["haskell"],[]) "",Para [Code ("",[],[]) "output test1"],Para [Str "php-style",Space,Str "fenced",Space,Str "code",Space,Str "blocks"],CodeBlock ("",["output","test1"],[]) "",Para [Str "raw",Space,Str "html"],RawBlock (Format "html") "<div>",Para [RawInline (Format "html") "<br>",RawInline (Format "html") "<p>",Str "I",Space,Str "am",Space,Str "raw",Space,Str "Html",RawInline (Format "html") "</p>",RawInline (Format "html") "</div>"]])
>>> readPandoc "test/test.md" LHS
Right (Pandoc (Meta {unMeta = fromList []}) [Plain [Str "haskell",Space,Str "LHS",Space,Str "style",SoftBreak,Str "```{.sourceCode",Space,Str ".literate",Space,Str ".haskell}",SoftBreak,Str "```",SoftBreak,Str "bird-tracks",SoftBreak,Str ">",Space,Str "import",Space,Str "Readme.Lhs",SoftBreak,Str "code",Space,Str "block",SoftBreak,Str "indented",SoftBreak,Str "unfenced",Space,Str "code",SoftBreak,Str "github-style",Space,Str "fenced",Space,Str "code",Space,Str "blocks",SoftBreak,Str "```",Space,Str "haskell",SoftBreak,Str "```",SoftBreak,Str "```",Space,Str "output",Space,Str "test1",SoftBreak,Str "```",SoftBreak,Str "php-style",Space,Str "fenced",Space,Str "code",Space,Str "blocks",SoftBreak,Str "```",Space,Str "{.output",Space,Str ".test1}",SoftBreak,Str "```",SoftBreak,Str "raw",Space,Str "html"],Div ("",[],[]) [Plain [LineBreak],Para [Str "I",Space,Str "am",Space,Str "raw",Space,Str "Html"]]])

Note how raw html inside markdown files is broken.

>>> (Right (Pandoc _ t1)) <- readPandoc "test/table1.html" Html
>>> t1 == [table1]
True

Constructors

GitHubMarkdown 
LHS 
Html 

Instances

Instances details
Eq Flavour Source # 
Instance details

Defined in Readme.Lhs

Methods

(==) :: Flavour -> Flavour -> Bool #

(/=) :: Flavour -> Flavour -> Bool #

Ord Flavour Source # 
Instance details

Defined in Readme.Lhs

Show Flavour Source # 
Instance details

Defined in Readme.Lhs

readPandoc :: FilePath -> Flavour -> IO (Either PandocError Pandoc) Source #

read a file into the pandoc AST

renderPandoc :: Flavour -> Pandoc -> Either PandocError Text Source #

render a pandoc AST

>>> renderPandoc GitHubMarkdown (Pandoc mempty [table1])
Right "| first column | second column |\n|:-------------|--------------:|\n| first row    |             1 |\n| second row   |          1000 |\n\nan example table\n"
>>> renderPandoc Html (Pandoc mempty [table1])
Right "<table class=\"table table-bordered table-hover m-3\" style=\"width: 70%;\">\n<caption>an example table</caption>\n<thead>\n<tr class=\"header\">\n<th style=\"text-align: left;\">first column</th>\n<th style=\"text-align: right;\">second column</th>\n</tr>\n</thead>\n<tbody>\n<tr class=\"odd\">\n<td style=\"text-align: left;\">first row</td>\n<td style=\"text-align: right;\">1</td>\n</tr>\n<tr class=\"even\">\n<td style=\"text-align: left;\">second row</td>\n<td style=\"text-align: right;\">1000</td>\n</tr>\n</tbody>\n</table>"

Note how pandoc strips things like links, style and scripts.

output

data Output Source #

output can be native pandoc, text that replaces or inserts into the output code block, or Html.

type OutputMap = Map Text Output Source #

a Map of output keyed off of defined section names in the receiving file

output :: Monad m => Text -> Output -> StateT OutputMap m () Source #

add an output key-value pair to state

insertOutput :: OutputMap -> Block -> [Block] Source #

Insert a block into the OutputMap

runOutput :: (FilePath, Flavour) -> (FilePath, Flavour) -> StateT OutputMap IO () -> IO (Either PandocError ()) Source #

insert outputs into a new file

tweakHaskellCodeBlock :: Block -> Block Source #

literate haskell code blocks comes out of markdown+lhs to native pandoc with the following classes:

"sourceCode","literate","haskell"

and then conversion to github flavour gives:

``` sourceCode ```

which doesn't lead to nice code highlighting on github (and elsewhere). This function tweaks the list so that ["haskell"] is the class, and it all works.

common patterns

defaultTable :: Attr -> Inlines -> [ColSpec] -> [Inlines] -> [[Inlines]] -> Blocks Source #

create a simple table from Inlines

>>> defaultTable bootTableAttr (B.fromList [Str "an",Space,Str "example",Space,Str "table"]) [(AlignLeft, ColWidthDefault), (AlignRight, ColWidthDefault)] (B.fromList <$> [[Str "first",Space,Str "column"], [Str "second",Space,Str "column"]]) (fmap B.fromList <$> [[[Str "first",Space,Str "row"], [Str "1"]], [[Str "second",Space,Str "row"], [Str "1000"]]]) == singleton table1
True

defaultTextTable :: Attr -> Text -> [ColSpec] -> [Text] -> [[Text]] -> Blocks Source #

create a simple table from Text

defaultTextTable bootTableAttr "an example table" [(AlignLeft, ColWidthDefault), (AlignRight, ColWidthDefault)] ["first column", "second column"] [["first row", "1"], ["second row", "1000"]]

bootTableAttr :: Attr Source #

bootstrap classes

thead :: [Inlines] -> TableHead Source #

aligned simple table header

tbody :: [[Inlines]] -> TableBody Source #

aligned simple table body

cell1 :: Alignment -> Inlines -> Cell Source #

aligned simple cell

badge :: Text -> Text -> Text -> Inlines Source #

create a badge link

>>> B.toList $ badge "Build Status" "https://travis-ci.org/tonyday567/readme-lhs.svg" "https://travis-ci.org/tonyday567/readme-lhs"
[Link ("",[],[]) [Image ("",[],[]) [Str "Build Status"] ("https://travis-ci.org/tonyday567/readme-lhs.svg","")] ("https://travis-ci.org/tonyday567/readme-lhs","")]

hask :: Maybe Text -> Text -> Inlines Source #

haskell code block

exports