readme-lhs-0.2.2: See readme.md

Safe HaskellNone
LanguageHaskell2010

Readme.Lhs

Synopsis

Documentation

para :: Text -> Block Source #

doctest >>> :set -XOverloadedStrings

turn text into a Pandoc Paragraph Block >>> para "hello" Para [Str "hello"]

plain :: Text -> Block Source #

turn text into a Pandoc Plain Block >>> plain "hello" Plain [Str "hello"]

table :: Text -> [Text] -> [Alignment] -> [Int] -> [[Text]] -> Block Source #

table caption headers alignments widths rows >>> table "an example table" ["first column", "second column"] [AlignLeft, AlignRight] [0,0] [["first row", "1"], ["second row", "1000"]] Table [Str "an example table"] [AlignLeft,AlignRight] [0.0,0.0] [[Para [Str "first column"]],[Para [Str "second column"]]] [[[Para [Str "first row"]],[Para [Str "1"]]],[[Para [Str "second row"]],[Para [Str "1000"]]]]

code :: Text -> [Text] -> Text -> Block Source #

code identifier classes text >>> code "name" ["sourceCode", "literate", "haskell"] "x = 1n" CodeBlock ("name",["sourceCode","literate","haskell"],[]) "x = 1n"

data Flavour Source #

use LHS when you want to just add output to a *.lhs | use GitHubMarkdown for rendering code and results on github

Constructors

GitHubMarkdown 
LHS 

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

read a file into the pandoc AST

data Output Source #

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

Constructors

Native [Block] 
Replace Text 
Fence Text 

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

add an output key-value pair to state

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.

data Block #

Block element.

Constructors

Plain [Inline]

Plain text, not a paragraph

Para [Inline]

Paragraph

LineBlock [[Inline]]

Multiple non-breaking lines

CodeBlock Attr String

Code block (literal) with attributes

RawBlock Format String

Raw block

BlockQuote [Block]

Block quote (list of blocks)

OrderedList ListAttributes [[Block]]

Ordered list (attributes and a list of items, each a list of blocks)

BulletList [[Block]]

Bullet list (list of items, each a list of blocks)

DefinitionList [([Inline], [[Block]])]

Definition list Each list item is a pair consisting of a term (a list of inlines) and one or more definitions (each a list of blocks)

Header Int Attr [Inline]

Header - level (integer) and text (inlines)

HorizontalRule

Horizontal rule

Table [Inline] [Alignment] [Double] [TableCell] [[TableCell]]

Table, with caption, column alignments (required), relative column widths (0 = default), column headers (each a list of blocks), and rows (each a list of lists of blocks)

Div Attr [Block]

Generic block container with attributes

Null

Nothing

Instances
Eq Block 
Instance details

Defined in Text.Pandoc.Definition

Methods

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

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

Data Block 
Instance details

Defined in Text.Pandoc.Definition

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Block -> c Block #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Block #

toConstr :: Block -> Constr #

dataTypeOf :: Block -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Block) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Block) #

gmapT :: (forall b. Data b => b -> b) -> Block -> Block #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r #

gmapQ :: (forall d. Data d => d -> u) -> Block -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Block -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Block -> m Block #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Block -> m Block #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Block -> m Block #

Ord Block 
Instance details

Defined in Text.Pandoc.Definition

Methods

compare :: Block -> Block -> Ordering #

(<) :: Block -> Block -> Bool #

(<=) :: Block -> Block -> Bool #

(>) :: Block -> Block -> Bool #

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

max :: Block -> Block -> Block #

min :: Block -> Block -> Block #

Read Block 
Instance details

Defined in Text.Pandoc.Definition

Show Block 
Instance details

Defined in Text.Pandoc.Definition

Methods

showsPrec :: Int -> Block -> ShowS #

show :: Block -> String #

showList :: [Block] -> ShowS #

Generic Block 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep Block :: Type -> Type #

Methods

from :: Block -> Rep Block x #

to :: Rep Block x -> Block #

ToJSON Block 
Instance details

Defined in Text.Pandoc.Definition

FromJSON Block 
Instance details

Defined in Text.Pandoc.Definition

NFData Block 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: Block -> () #

type Rep Block 
Instance details

Defined in Text.Pandoc.Definition

type Rep Block = D1 (MetaData "Block" "Text.Pandoc.Definition" "pandoc-types-1.17.6.1-CjWsfVClWhahZsSAbTYgT" False) (((C1 (MetaCons "Plain" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])) :+: (C1 (MetaCons "Para" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])) :+: C1 (MetaCons "LineBlock" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [[Inline]])))) :+: ((C1 (MetaCons "CodeBlock" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attr) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "RawBlock" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Format) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) :+: (C1 (MetaCons "BlockQuote" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Block])) :+: C1 (MetaCons "OrderedList" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ListAttributes) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [[Block]]))))) :+: ((C1 (MetaCons "BulletList" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [[Block]])) :+: (C1 (MetaCons "DefinitionList" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [([Inline], [[Block]])])) :+: C1 (MetaCons "Header" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attr) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline]))))) :+: ((C1 (MetaCons "HorizontalRule" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Table" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Alignment])) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Double]) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TableCell]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [[TableCell]]))))) :+: (C1 (MetaCons "Div" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attr) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Block])) :+: C1 (MetaCons "Null" PrefixI False) (U1 :: Type -> Type)))))

data Alignment #

Alignment of a table column.

Instances
Eq Alignment 
Instance details

Defined in Text.Pandoc.Definition

Data Alignment 
Instance details

Defined in Text.Pandoc.Definition

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Alignment -> c Alignment #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Alignment #

toConstr :: Alignment -> Constr #

dataTypeOf :: Alignment -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Alignment) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Alignment) #

gmapT :: (forall b. Data b => b -> b) -> Alignment -> Alignment #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alignment -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alignment -> r #

gmapQ :: (forall d. Data d => d -> u) -> Alignment -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Alignment -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Alignment -> m Alignment #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Alignment -> m Alignment #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Alignment -> m Alignment #

Ord Alignment 
Instance details

Defined in Text.Pandoc.Definition

Read Alignment 
Instance details

Defined in Text.Pandoc.Definition

Show Alignment 
Instance details

Defined in Text.Pandoc.Definition

Generic Alignment 
Instance details

Defined in Text.Pandoc.Definition

Associated Types

type Rep Alignment :: Type -> Type #

ToJSON Alignment 
Instance details

Defined in Text.Pandoc.Definition

FromJSON Alignment 
Instance details

Defined in Text.Pandoc.Definition

NFData Alignment 
Instance details

Defined in Text.Pandoc.Definition

Methods

rnf :: Alignment -> () #

type Rep Alignment 
Instance details

Defined in Text.Pandoc.Definition

type Rep Alignment = D1 (MetaData "Alignment" "Text.Pandoc.Definition" "pandoc-types-1.17.6.1-CjWsfVClWhahZsSAbTYgT" False) ((C1 (MetaCons "AlignLeft" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AlignRight" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "AlignCenter" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AlignDefault" PrefixI False) (U1 :: Type -> Type)))