Text.Pandoc.Builder (original) (raw)
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
Documentation
(<>) :: Semigroup a => a -> a -> a infixr 6 #
An associative operation.
>>> [1,2,3] <> [4,5,6]** **[1,2,3,4,5,6]
Document buildersInline list buildersBlock list buildersTable processing
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](Text-Pandoc-Definition.html#t:RowSpan "Text.Pandoc.Definition") 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](Text-Pandoc-Builder.html#v:emptyCell "Text.Pandoc.Builder")` to the [`[Cell](Text-Pandoc-Definition.html#t:Cell "Text.Pandoc.Definition")`] list and using [clipRows](Text-Pandoc-Builder.html#v:clipRows "Text.Pandoc.Builder") 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](Text-Pandoc-Definition.html#t:ColSpan "Text.Pandoc.Definition") 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](Text-Pandoc-Definition.html#t:RowSpan "Text.Pandoc.Definition")`], 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 ofreplicate 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](Text-Pandoc-Builder.html#v:clipRows "Text.Pandoc.Builder") 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](Text-Pandoc-Builder.html#v:placeRowSection "Text.Pandoc.Builder") 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.