| Portability | portable | 
|---|---|
| Stability | alpha | 
| Maintainer | John MacFarlane <jgm@berkeley.edu> | 
| Safe Haskell | None | 
Text.Pandoc.Builder
Description
Convenience functions for building pandoc documents programmatically.
Example of use (with OverloadedStrings pragma):
 import Text.Pandoc.Builder
 myDoc :: Pandoc
 myDoc = setTitle "My title" $ doc $
   para "This is the first paragraph" <>
   para ("And " <> emph "another" <> ".") <>
   bulletList [ para "item one" <> para "continuation"
              , plain ("item two and a " <>
                  link "/url" "go to url" "link")
              ]
Isn't that nicer than writing the following?
 import Text.Pandoc.Definition
 import Data.Map (fromList)
 myDoc :: Pandoc
 myDoc = Pandoc (Meta {unMeta = fromList [("title",
           MetaInlines [Str "My",Space,Str "title"])]})
         [Para [Str "This",Space,Str "is",Space,Str "the",Space,Str "first",
          Space,Str "paragraph"],Para [Str "And",Space,Emph [Str "another"],
          Str "."]
         ,BulletList [
           [Para [Str "item",Space,Str "one"]
           ,Para [Str "continuation"]]
          ,[Plain [Str "item",Space,Str "two",Space,Str "and",Space,
                   Str "a",Space,Link [Str "link"] ("/url","go to url")]]]]
And of course, you can use Haskell to define your own builders:
 import Text.Pandoc.Builder
 import Text.JSON
 import Control.Arrow ((***))
 import Data.Monoid (mempty)
 -- | Converts a JSON document into 'Blocks'.
 json :: String -> Blocks
 json x =
   case decode x of
        Ok y    -> jsValueToBlocks y
        Error y -> error y
    where jsValueToBlocks x =
           case x of
            JSNull         -> mempty
            JSBool x       -> plain $ text $ show x
            JSRational _ x -> plain $ text $ show x
            JSString x     -> plain $ text $ fromJSString x
            JSArray xs     -> bulletList $ map jsValueToBlocks xs
            JSObject x     -> definitionList $
                               map (text *** (:[]) . jsValueToBlocks) $
                               fromJSObject x
- module Text.Pandoc.Definition
 - newtype Many a = Many {}
 - type Inlines = Many Inline
 - type Blocks = Many Block
 - (<>) :: Monoid m => m -> m -> m
 - singleton :: a -> Many a
 - toList :: Many a -> [a]
 - fromList :: [a] -> Many a
 - isNull :: Many a -> Bool
 - doc :: Blocks -> Pandoc
 - class  ToMetaValue a  where
- toMetaValue :: a -> MetaValue
 
 - class  HasMeta a  where
- setMeta :: ToMetaValue b => String -> b -> a -> a
 - deleteMeta :: String -> a -> a
 
 - setTitle :: Inlines -> Pandoc -> Pandoc
 - setAuthors :: [Inlines] -> Pandoc -> Pandoc
 - setDate :: Inlines -> Pandoc -> Pandoc
 - text :: String -> Inlines
 - str :: String -> Inlines
 - emph :: Inlines -> Inlines
 - strong :: Inlines -> Inlines
 - strikeout :: Inlines -> Inlines
 - superscript :: Inlines -> Inlines
 - subscript :: Inlines -> Inlines
 - smallcaps :: Inlines -> Inlines
 - singleQuoted :: Inlines -> Inlines
 - doubleQuoted :: Inlines -> Inlines
 - cite :: [Citation] -> Inlines -> Inlines
 - codeWith :: Attr -> String -> Inlines
 - code :: String -> Inlines
 - space :: Inlines
 - linebreak :: Inlines
 - math :: String -> Inlines
 - displayMath :: String -> Inlines
 - rawInline :: String -> String -> Inlines
 - link :: String -> String -> Inlines -> Inlines
 - image :: String -> String -> Inlines -> Inlines
 - note :: Blocks -> Inlines
 - spanWith :: Attr -> Inlines -> Inlines
 - trimInlines :: Inlines -> Inlines
 - para :: Inlines -> Blocks
 - plain :: Inlines -> Blocks
 - codeBlockWith :: Attr -> String -> Blocks
 - codeBlock :: String -> Blocks
 - rawBlock :: String -> String -> Blocks
 - blockQuote :: Blocks -> Blocks
 - bulletList :: [Blocks] -> Blocks
 - orderedListWith :: ListAttributes -> [Blocks] -> Blocks
 - orderedList :: [Blocks] -> Blocks
 - definitionList :: [(Inlines, [Blocks])] -> Blocks
 - header :: Int -> Inlines -> Blocks
 - headerWith :: Attr -> Int -> Inlines -> Blocks
 - horizontalRule :: Blocks
 - table :: Inlines -> [(Alignment, Double)] -> [Blocks] -> [[Blocks]] -> Blocks
 - simpleTable :: [Blocks] -> [[Blocks]] -> Blocks
 - divWith :: Attr -> Blocks -> Blocks
 
Documentation
module Text.Pandoc.Definition
Document builders
class ToMetaValue a whereSource
Methods
toMetaValue :: a -> MetaValueSource
Instances
| ToMetaValue Bool | |
| ToMetaValue MetaValue | |
| ToMetaValue Blocks | |
| ToMetaValue Inlines | |
| ToMetaValue a => ToMetaValue [a] | |
| ToMetaValue a => ToMetaValue (Map String a) | 
setAuthors :: [Inlines] -> Pandoc -> PandocSource
Inline list builders
superscript :: Inlines -> InlinesSource
singleQuoted :: Inlines -> InlinesSource
doubleQuoted :: Inlines -> InlinesSource
displayMath :: String -> InlinesSource
Display math
trimInlines :: Inlines -> InlinesSource
Trim leading and trailing Sp (spaces) from an Inlines.
Block list builders
codeBlockWith :: Attr -> String -> BlocksSource
A code block with attributes.
blockQuote :: Blocks -> BlocksSource
bulletList :: [Blocks] -> BlocksSource
orderedListWith :: ListAttributes -> [Blocks] -> BlocksSource
Ordered list with attributes.
orderedList :: [Blocks] -> BlocksSource
Ordered list with default attributes.
definitionList :: [(Inlines, [Blocks])] -> BlocksSource
A simple table without a caption.