Portability | portable |
---|---|
Stability | alpha |
Maintainer | John MacFarlane <[email protected]> |
Text.Pandoc.Builder
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
- module Text.Pandoc.Definition
- newtype Inlines = Inlines {}
- newtype Blocks = Blocks {}
- (<>) :: Monoid a => a -> a -> a
- class Listable a b where
- doc :: Blocks -> Pandoc
- 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 :: Format -> String -> Inlines
- link :: String -> String -> Inlines -> Inlines
- image :: String -> String -> Inlines -> Inlines
- note :: Blocks -> Inlines
- trimInlines :: Inlines -> Inlines
- para :: Inlines -> Blocks
- plain :: Inlines -> Blocks
- codeBlockWith :: Attr -> String -> Blocks
- codeBlock :: String -> Blocks
- rawBlock :: Format -> String -> Blocks
- blockQuote :: Blocks -> Blocks
- bulletList :: [Blocks] -> Blocks
- orderedListWith :: ListAttributes -> [Blocks] -> Blocks
- orderedList :: [Blocks] -> Blocks
- definitionList :: [(Inlines, [Blocks])] -> Blocks
- header :: Int -> Inlines -> Blocks
- horizontalRule :: Blocks
- table :: Inlines -> [(Alignment, Double)] -> [Blocks] -> [[Blocks]] -> Blocks
- simpleTable :: [Blocks] -> [[Blocks]] -> Blocks
Documentation
module Text.Pandoc.Definition
Document builders
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.