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

CopyrightCopyright (C) 2010-2019 John MacFarlane
LicenseBSD3
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Stabilityalpha
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.Pandoc.Builder

Contents

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 nullAttr [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

newtype Many a Source #

Constructors

Many 

Fields

Instances
Functor Many Source # 
Instance details

Defined in Text.Pandoc.Builder

Methods

fmap :: (a -> b) -> Many a -> Many b #

(<$) :: a -> Many b -> Many a #

IsString Inlines Source # 
Instance details

Defined in Text.Pandoc.Builder

Methods

fromString :: String -> Inlines #

Foldable Many Source # 
Instance details

Defined in Text.Pandoc.Builder

Methods

fold :: Monoid m => Many m -> m #

foldMap :: Monoid m => (a -> m) -> Many a -> m #

foldr :: (a -> b -> b) -> b -> Many a -> b #

foldr' :: (a -> b -> b) -> b -> Many a -> b #

foldl :: (b -> a -> b) -> b -> Many a -> b #

foldl' :: (b -> a -> b) -> b -> Many a -> b #

foldr1 :: (a -> a -> a) -> Many a -> a #

foldl1 :: (a -> a -> a) -> Many a -> a #

toList :: Many a -> [a] #

null :: Many a -> Bool #

length :: Many a -> Int #

elem :: Eq a => a -> Many a -> Bool #

maximum :: Ord a => Many a -> a #

minimum :: Ord a => Many a -> a #

sum :: Num a => Many a -> a #

product :: Num a => Many a -> a #

Traversable Many Source # 
Instance details

Defined in Text.Pandoc.Builder

Methods

traverse :: Applicative f => (a -> f b) -> Many a -> f (Many b) #

sequenceA :: Applicative f => Many (f a) -> f (Many a) #

mapM :: Monad m => (a -> m b) -> Many a -> m (Many b) #

sequence :: Monad m => Many (m a) -> m (Many a) #

Semigroup Inlines Source # 
Instance details

Defined in Text.Pandoc.Builder

Monoid Inlines Source # 
Instance details

Defined in Text.Pandoc.Builder

Arbitrary Blocks Source # 
Instance details

Defined in Text.Pandoc.Arbitrary

Arbitrary Inlines Source # 
Instance details

Defined in Text.Pandoc.Arbitrary

ToMetaValue Blocks Source # 
Instance details

Defined in Text.Pandoc.Builder

ToMetaValue Inlines Source # 
Instance details

Defined in Text.Pandoc.Builder

Eq a => Eq (Many a) Source # 
Instance details

Defined in Text.Pandoc.Builder

Methods

(==) :: Many a -> Many a -> Bool #

(/=) :: Many a -> Many a -> Bool #

Data a => Data (Many a) Source # 
Instance details

Defined in Text.Pandoc.Builder

Methods

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

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

toConstr :: Many a -> Constr #

dataTypeOf :: Many a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Many a) Source # 
Instance details

Defined in Text.Pandoc.Builder

Methods

compare :: Many a -> Many a -> Ordering #

(<) :: Many a -> Many a -> Bool #

(<=) :: Many a -> Many a -> Bool #

(>) :: Many a -> Many a -> Bool #

(>=) :: Many a -> Many a -> Bool #

max :: Many a -> Many a -> Many a #

min :: Many a -> Many a -> Many a #

Read a => Read (Many a) Source # 
Instance details

Defined in Text.Pandoc.Builder

Show a => Show (Many a) Source # 
Instance details

Defined in Text.Pandoc.Builder

Methods

showsPrec :: Int -> Many a -> ShowS #

show :: Many a -> String #

showList :: [Many a] -> ShowS #

Generic (Many a) Source # 
Instance details

Defined in Text.Pandoc.Builder

Associated Types

type Rep (Many a) :: Type -> Type #

Methods

from :: Many a -> Rep (Many a) x #

to :: Rep (Many a) x -> Many a #

Semigroup (Many Block) Source # 
Instance details

Defined in Text.Pandoc.Builder

Monoid (Many Block) Source # 
Instance details

Defined in Text.Pandoc.Builder

type Rep (Many a) Source # 
Instance details

Defined in Text.Pandoc.Builder

type Rep (Many a) = D1 (MetaData "Many" "Text.Pandoc.Builder" "pandoc-types-1.21-Acc5QWPGRW06YHKed5pawD" True) (C1 (MetaCons "Many" PrefixI True) (S1 (MetaSel (Just "unMany") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Seq a))))

(<>) :: Semigroup a => a -> a -> a infixr 6 #

An associative operation.

toList :: Many a -> [a] Source #

fromList :: [a] -> Many a Source #

Document builders

class ToMetaValue a where Source #

Methods

toMetaValue :: a -> MetaValue Source #

Instances
ToMetaValue Bool Source # 
Instance details

Defined in Text.Pandoc.Builder

ToMetaValue String Source # 
Instance details

Defined in Text.Pandoc.Builder

ToMetaValue Text Source # 
Instance details

Defined in Text.Pandoc.Builder

ToMetaValue MetaValue Source # 
Instance details

Defined in Text.Pandoc.Builder

ToMetaValue Blocks Source # 
Instance details

Defined in Text.Pandoc.Builder

ToMetaValue Inlines Source # 
Instance details

Defined in Text.Pandoc.Builder

ToMetaValue a => ToMetaValue [a] Source # 
Instance details

Defined in Text.Pandoc.Builder

Methods

toMetaValue :: [a] -> MetaValue Source #

ToMetaValue a => ToMetaValue (Map String a) Source # 
Instance details

Defined in Text.Pandoc.Builder

ToMetaValue a => ToMetaValue (Map Text a) Source # 
Instance details

Defined in Text.Pandoc.Builder

class HasMeta a where Source #

Methods

setMeta :: ToMetaValue b => Text -> b -> a -> a Source #

deleteMeta :: Text -> a -> a Source #

Instances
HasMeta Meta Source # 
Instance details

Defined in Text.Pandoc.Builder

Methods

setMeta :: ToMetaValue b => Text -> b -> Meta -> Meta Source #

deleteMeta :: Text -> Meta -> Meta Source #

HasMeta Pandoc Source # 
Instance details

Defined in Text.Pandoc.Builder

Inline list builders

text :: Text -> Inlines Source #

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

codeWith :: Attr -> Text -> Inlines Source #

Inline code with attributes.

code :: Text -> Inlines Source #

Plain inline code.

math :: Text -> Inlines Source #

Inline math

displayMath :: Text -> Inlines Source #

Display math

link Source #

Arguments

:: Text

URL

-> Text

Title

-> Inlines

Label

-> Inlines 

linkWith Source #

Arguments

:: Attr

Attributes

-> Text

URL

-> Text

Title

-> Inlines

Label

-> Inlines 

image Source #

Arguments

:: Text

URL

-> Text

Title

-> Inlines

Alt text

-> Inlines 

imageWith Source #

Arguments

:: Attr

Attributes

-> Text

URL

-> Text

Title

-> Inlines

Alt text

-> Inlines 

trimInlines :: Inlines -> Inlines Source #

Trim leading and trailing spaces and softbreaks from an Inlines.

Block list builders

codeBlockWith :: Attr -> Text -> Blocks Source #

A code block with attributes.

codeBlock :: Text -> Blocks Source #

A plain code block.

orderedListWith :: ListAttributes -> [Blocks] -> Blocks Source #

Ordered list with attributes.

orderedList :: [Blocks] -> Blocks Source #

Ordered list with default attributes.

header Source #

Arguments

:: Int

Level

-> Inlines 
-> Blocks 

simpleCell :: Blocks -> Cell Source #

A 1×1 cell with default alignment.

emptyCell :: Cell Source #

A 1×1 empty cell.

table :: Caption -> [ColSpec] -> TableHead -> [TableBody] -> TableFoot -> Blocks Source #

Table builder. Performs normalization with normalizeTableHead, normalizeTableBody, and normalizeTableFoot. The number of table columns is given by the length of [ColSpec].

simpleTable Source #

Arguments

:: [Blocks]

Headers

-> [[Blocks]]

Rows

-> Blocks 

A simple table without a caption.

Table processing

normalizeTableHead :: Int -> TableHead -> TableHead Source #

Normalize the TableHead with clipRows and placeRowSection so that when placed on a grid with the given width and a height equal to the number of rows in the initial TableHead, there will be no empty spaces or overlapping cells, and the cells will not protrude beyond the grid.

normalizeTableBody :: Int -> TableBody -> TableBody Source #

Normalize the intermediate head and body section of a TableBody, as in normalizeTableHead, but additionally ensure that row head cells do not go beyond the row head.

placeRowSection Source #

Arguments

:: [RowSpan]

The overhang of the previous grid row

-> [Cell]

The cells to lay on the grid row

-> ([RowSpan], [Cell], [Cell])

The overhang of the current grid row, the normalized cells that fit on the current row, and the remaining unmodified cells

Normalize the given list of cells so that they fit on a single grid row. The RowSpan values of the cells are assumed to be valid (clamped to lie between 1 and the remaining grid height). The cells in the list are also assumed to be able to fill the entire grid row. These conditions can be met by appending repeat emptyCell to the [Cell] list and using clipRows on the entire table section beforehand.

Normalization follows the principle that cells are placed on a grid row in order, each at the first available grid position from the left, having their ColSpan reduced if they would overlap with a previous cell, stopping once the row is filled. Only the dimensions of cells are changed, and only of those cells that fit on the row.

Possible overlap is detected using the given [RowSpan], which is the "overhang" of the previous grid row, a list of the heights of cells that descend through the previous row, reckoned only from the previous row. Its length should be the width (number of columns) of the current grid row.

For example, the numbers in the following headerless grid table represent the overhang at each grid position for that table:

    1   1   1   1
  +---+---+---+---+
  | 1 | 2   2 | 3 |
  +---+       +   +
  | 1 | 1   1 | 2 |
  +---+---+---+   +
  | 1   1 | 1 | 1 |
  +---+---+---+---+

In any table, the row before the first has an overhang of replicate tableWidth 1, since there are no cells to descend into the table from there. The overhang of the first row in the example is [1, 2, 2, 3].

So if after clipRows the unnormalized second row of that example table were

r = [("a", 1, 2),("b", 2, 3)] -- the cells displayed as (label, RowSpan, ColSpan) only

a correct invocation of placeRowSection to normalize it would be

>>> placeRowSection [1, 2, 2, 3] $ r ++ repeat emptyCell
([1, 1, 1, 2], [("a", 1, 1)], [("b", 2, 3)] ++ repeat emptyCell) -- wouldn't stop printing, of course

and if the third row were only [("c", 1, 2)], then the expression would be

>>> placeRowSection [1, 1, 1, 2] $ [("c", 1, 2)] ++ repeat emptyCell
([1, 1, 1, 1], [("c", 1, 2), emptyCell], repeat emptyCell)

clipRows :: [Row] -> [Row] Source #

Ensure that the height of each cell in a table section lies between 1 and the distance from its row to the end of the section. So if there were four rows in the input list, the cells in the second row would have their height clamped between 1 and 3.