pandoc-types-1.9.1: Types for representing a structured document

Portabilityportable
Stabilityalpha
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Safe HaskellNone

Text.Pandoc.Builder

Contents

Description

Convenience functions for building pandoc documents programmatically.

Example of use:

 
 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

 myDoc :: Pandoc
 myDoc = Pandoc (Meta {docTitle = [Str "My",Space,Str "title"]
                      , docAuthors = []
                      , docDate = []})
  [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

Synopsis

Documentation

(<>) :: Monoid m => m -> m -> m

An infix synonym for mappend.

class Listable a b whereSource

Methods

toList :: a -> [b]Source

fromList :: [b] -> aSource

foldMap :: (b -> a) -> a -> aSource

singleton :: b -> aSource

foldlM :: Monad m => (a -> b -> m a) -> a -> a -> m aSource

isNull :: a -> BoolSource

Document builders

Inline list builders

text :: String -> InlinesSource

Convert a String to Inlines, treating interword spaces as Spaces. If you want a Str with literal spaces, use str.

codeWith :: Attr -> String -> InlinesSource

Inline code with attributes.

code :: String -> InlinesSource

Plain inline code.

math :: String -> InlinesSource

Inline math

displayMath :: String -> InlinesSource

Display math

linkSource

Arguments

:: String

URL

-> String

Title

-> Inlines

Label

-> Inlines 

imageSource

Arguments

:: String

URL

-> String

Title

-> Inlines

Alt text

-> Inlines 

trimInlines :: Inlines -> InlinesSource

Trim leading and trailing Sp (spaces) from an Inlines.

Block list builders

codeBlockWith :: Attr -> String -> BlocksSource

A code block with attributes.

codeBlock :: String -> BlocksSource

A plain code block.

orderedListWith :: ListAttributes -> [Blocks] -> BlocksSource

Ordered list with attributes.

orderedList :: [Blocks] -> BlocksSource

Ordered list with default attributes.

headerSource

Arguments

:: Int

Level

-> Inlines 
-> Blocks 

tableSource

Arguments

:: Inlines

Caption

-> [(Alignment, Double)]

Column alignments and fractional widths

-> [Blocks]

Headers

-> [[Blocks]]

Rows

-> Blocks 

simpleTableSource

Arguments

:: [Blocks]

Headers

-> [[Blocks]]

Rows

-> Blocks 

A simple table without a caption.