Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module exports a 1:1 monadic version of pandoc-types' Builder
.
Synopsis
- module Text.Pandoc.Definition
- type Builder el = BuilderM el ()
- type URL = Text
- type Title = Text
- type Raw = Text
- doc :: Builder Block -> Pandoc
- setTitle :: Builder Inline -> Pandoc -> Pandoc
- setAuthors :: [Builder Inline] -> Pandoc -> Pandoc
- setDate :: Builder Inline -> Pandoc -> Pandoc
- setMeta :: (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
- text :: Text -> Builder Inline
- str :: Text -> Builder Inline
- emph :: Builder Inline -> Builder Inline
- underline :: Builder Inline -> Builder Inline
- strong :: Builder Inline -> Builder Inline
- strikeout :: Builder Inline -> Builder Inline
- superscript :: Builder Inline -> Builder Inline
- subscript :: Builder Inline -> Builder Inline
- smallcaps :: Builder Inline -> Builder Inline
- singleQuoted :: Builder Inline -> Builder Inline
- doubleQuoted :: Builder Inline -> Builder Inline
- cite :: [Citation] -> Builder Inline -> Builder Inline
- code :: Text -> Builder Inline
- codeWith :: Attr -> Text -> Builder Inline
- space :: Builder Inline
- softbreak :: Builder Inline
- linebreak :: Builder Inline
- math :: Text -> Builder Inline
- displayMath :: Text -> Builder Inline
- rawInline :: Format -> Raw -> Builder Inline
- link :: URL -> Title -> Builder Inline -> Builder Inline
- linkWith :: Attr -> URL -> Title -> Builder Inline -> Builder Inline
- image :: URL -> Title -> Builder Inline -> Builder Inline
- imageWith :: Attr -> Text -> Text -> Builder Inline -> Builder Inline
- note :: Builder Block -> Builder Inline
- spanWith :: Attr -> Builder Inline -> Builder Inline
- trimInlines :: Builder Inline -> Builder Inline
- para :: Builder Inline -> Builder Block
- plain :: Builder Inline -> Builder Block
- lineBlock :: [Builder Inline] -> Builder Block
- codeBlockWith :: Attr -> Text -> Builder Block
- codeBlock :: Text -> Builder Block
- rawBlock :: Format -> Raw -> Builder Block
- blockQuote :: Builder Block -> Builder Block
- bulletList :: [Builder Block] -> Builder Block
- orderedListWith :: ListAttributes -> [Builder Block] -> Builder Block
- orderedList :: [Builder Block] -> Builder Block
- definitionList :: [(Builder Inline, [Builder Block])] -> Builder Block
- header :: Int -> Builder Inline -> Builder Block
- headerWith :: Attr -> Int -> Builder Inline -> Builder Block
- horizontalRule :: Builder Block
- cell :: Alignment -> RowSpan -> ColSpan -> Builder Block -> Cell
- simpleCell :: Builder Block -> Cell
- emptyCell :: Cell
- cellWith :: Attr -> Alignment -> RowSpan -> ColSpan -> Builder Block -> Cell
- table :: Caption -> [ColSpec] -> TableHead -> [TableBody] -> TableFoot -> Builder Block
- simpleTable :: [Builder Block] -> [[Builder Block]] -> Builder Block
- tableWith :: Attr -> Caption -> [ColSpec] -> TableHead -> [TableBody] -> TableFoot -> Builder Block
- figure :: Caption -> Builder Block -> Builder Block
- figureWith :: Attr -> Caption -> Builder Block -> Builder Block
- caption :: Maybe ShortCaption -> Builder Block -> Caption
- simpleCaption :: Builder Block -> Caption
- emptyCaption :: Caption
- simpleFigureWith :: Attr -> Builder Inline -> URL -> Title -> Builder Block
- simpleFigure :: Builder Inline -> Text -> Text -> Builder Block
- divWith :: Attr -> Builder Block -> Builder Block
- normalizeTableHead :: Int -> TableHead -> TableHead
- normalizeTableBody :: Int -> TableBody -> TableBody
- normalizeTableFoot :: Int -> TableFoot -> TableFoot
- placeRowSection :: [RowSpan] -> [Cell] -> ([RowSpan], [Cell], [Cell])
- clipRows :: [Row] -> [Row]
Documentation
module Text.Pandoc.Definition
Top-level
doc :: Builder Block -> Pandoc Source #
Build a pandoc document from a Builder
of top-level elements.
setAuthors :: [Builder Inline] -> Pandoc -> Pandoc Source #
Set the document's authors in the metadata.
setMeta :: (HasMeta a, ToMetaValue b) => Text -> b -> a -> a Source #
Set a value in the document's metadata.
Inline builders
smallcaps :: Builder Inline -> Builder Inline Source #
Build a smallcaps inline. See the example in the font-family MDN page.
cite :: [Citation] -> Builder Inline -> Builder Inline Source #
Build a citation. See Citations in note style and Specifying a citation style.
displayMath :: Text -> Builder Inline Source #
Build some display-mode TeX math. Display mode is for math that is set apart from the main text.
rawInline :: Format -> Raw -> Builder Inline Source #
Embed some of the output directly. This is useful to gain access to features of the underlying output which aren't supported by pandoc directly.
link :: URL -> Title -> Builder Inline -> Builder Inline Source #
Build a link from a URL, a title, and some inline pandoc.
linkWith :: Attr -> URL -> Title -> Builder Inline -> Builder Inline Source #
Build a link from some attributes, a URL, a title, and some inline pandoc.
image :: URL -> Title -> Builder Inline -> Builder Inline Source #
Build an image from a URL, a title, and some inline pandoc.
imageWith :: Attr -> Text -> Text -> Builder Inline -> Builder Inline Source #
Build an image from some attributes, a URL, a title, and some inline pandoc.
note :: Builder Block -> Builder Inline Source #
Build a footnote or endnote from some pandoc blocks.
spanWith :: Attr -> Builder Inline -> Builder Inline Source #
Build a generic inline container from attributes and more inline pandoc.
trimInlines :: Builder Inline -> Builder Inline Source #
Trim leading and trailing spaces and softbreaks from some inline pandoc.
Block builders
rawBlock :: Format -> Raw -> Builder Block Source #
Embed some of the output directly. This is useful to gain access to features of the underlying output which aren't supported by pandoc directly.
orderedListWith :: ListAttributes -> [Builder Block] -> Builder Block Source #
Build an ordered list with attributes.
definitionList :: [(Builder Inline, [Builder Block])] -> Builder Block Source #
Build an definition list given a list of tuples, where the first element of each tuple is a term, and the second element is the definition.
header :: Int -> Builder Inline -> Builder Block Source #
Build a header, given a level and some inline pandoc.
You may consider using h1
and friends,
for a more concise API.
headerWith :: Attr -> Int -> Builder Inline -> Builder Block Source #
Build a header from some attributes, a level and some inline pandoc.
horizontalRule :: Builder Block Source #
Build a horizontal rule.
cell :: Alignment -> RowSpan -> ColSpan -> Builder Block -> Cell Source #
Build a cell of a table, full API excluding attributes.
simpleCell :: Builder Block -> Cell Source #
Build a 1x1 cell with default alignment, given some pandoc.
cellWith :: Attr -> Alignment -> RowSpan -> ColSpan -> Builder Block -> Cell Source #
Build a cell of a table, full API including attributes.
table :: Caption -> [ColSpec] -> TableHead -> [TableBody] -> TableFoot -> Builder Block Source #
Build a table, full API excluding attributes.
simpleTable :: [Builder Block] -> [[Builder Block]] -> Builder Block Source #
Build a table, given a list of header cells, and a list of rows.
tableWith :: Attr -> Caption -> [ColSpec] -> TableHead -> [TableBody] -> TableFoot -> Builder Block Source #
Build a table, full API including attributes.
figure :: Caption -> Builder Block -> Builder Block Source #
Build a captioned figure. This is available in pandoc-types >= 1.23, which corresponds to pandoc >= 3.0.
figureWith :: Attr -> Caption -> Builder Block -> Builder Block Source #
Build a captioned figure, with attributes. This is available in pandoc-types >= 1.23, which corresponds to pandoc >= 3.0.
caption :: Maybe ShortCaption -> Builder Block -> Caption Source #
Make a caption, with an optional short version.
emptyCaption :: Caption Source #
Make an empty caption
simpleFigureWith :: Attr -> Builder Inline -> URL -> Title -> Builder Block Source #
Build a captioned figure containing an image, with attributes. This is available in pandoc-types >= 1.22.1, which corresponds to pandoc >= 2.15.
simpleFigure :: Builder Inline -> Text -> Text -> Builder Block Source #
Build a captioned figure, containing an image. This is available in pandoc-types >= 1.22.1, which corresponds to pandoc >= 2.15.
divWith :: Attr -> Builder Block -> Builder Block Source #
Build a generic block container with attributes.
Table processing
normalizeTableHead :: Int -> TableHead -> TableHead #
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 #
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 inside the
intermediate body.
normalizeTableFoot :: Int -> TableFoot -> TableFoot #
Normalize the TableFoot
, as in normalizeTableHead
.
:: [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
to the emptyCell
[
list and using Cell
]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 [
, 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.RowSpan
]
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)
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.