| Copyright | Copyright (C) 2013-2023 John MacFarlane | 
|---|---|
| License | GNU GPL, version 2 or above | 
| Maintainer | John MacFarlane <jgm@berkeley.edu> | 
| Stability | alpha | 
| Portability | portable | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Text.Pandoc.Writers.Shared
Description
Shared utility functions for pandoc writers.
Synopsis
- metaToContext :: (Monad m, TemplateTarget a) => WriterOptions -> ([Block] -> m (Doc a)) -> ([Inline] -> m (Doc a)) -> Meta -> m (Context a)
- metaToContext' :: (Monad m, TemplateTarget a) => ([Block] -> m (Doc a)) -> ([Inline] -> m (Doc a)) -> Meta -> m (Context a)
- addVariablesToContext :: TemplateTarget a => WriterOptions -> Context a -> Context a
- getField :: FromContext a b => Text -> Context a -> Maybe b
- setField :: ToContext a b => Text -> b -> Context a -> Context a
- resetField :: ToContext a b => Text -> b -> Context a -> Context a
- defField :: ToContext a b => Text -> b -> Context a -> Context a
- getLang :: WriterOptions -> Meta -> Maybe Text
- tagWithAttrs :: HasChars a => a -> Attr -> Doc a
- htmlAddStyle :: (Text, Text) -> [(Text, Text)] -> [(Text, Text)]
- htmlAlignmentToString :: Alignment -> Maybe Text
- htmlAttrs :: HasChars a => Attr -> Doc a
- isDisplayMath :: Inline -> Bool
- fixDisplayMath :: Block -> Block
- unsmartify :: WriterOptions -> Text -> Text
- gridTable :: (Monad m, HasChars a) => WriterOptions -> (WriterOptions -> [Block] -> m (Doc a)) -> Bool -> [Alignment] -> [Double] -> [[Block]] -> [[[Block]]] -> m (Doc a)
- lookupMetaBool :: Text -> Meta -> Bool
- lookupMetaBlocks :: Text -> Meta -> [Block]
- lookupMetaInlines :: Text -> Meta -> [Inline]
- lookupMetaString :: Text -> Meta -> Text
- stripLeadingTrailingSpace :: [Inline] -> [Inline]
- toSubscript :: Char -> Maybe Char
- toSuperscript :: Char -> Maybe Char
- toTableOfContents :: WriterOptions -> [Block] -> Block
- endsWithPlain :: [Block] -> Bool
- toLegacyTable :: Caption -> [ColSpec] -> TableHead -> [TableBody] -> TableFoot -> ([Inline], [Alignment], [Double], [[Block]], [[[Block]]])
- splitSentences :: Doc Text -> Doc Text
- ensureValidXmlIdentifiers :: Pandoc -> Pandoc
- setupTranslations :: PandocMonad m => Meta -> m ()
Documentation
metaToContext :: (Monad m, TemplateTarget a) => WriterOptions -> ([Block] -> m (Doc a)) -> ([Inline] -> m (Doc a)) -> Meta -> m (Context a) Source #
Create template Context from a Meta and an association list
 of variables, specified at the command line or in the writer.
 Variables overwrite metadata fields with the same names.
 If multiple variables are set with the same name, a list is
 assigned.  Does nothing if writerTemplate is Nothing.
Arguments
| :: (Monad m, TemplateTarget a) | |
| => ([Block] -> m (Doc a)) | block writer | 
| -> ([Inline] -> m (Doc a)) | inline writer | 
| -> Meta | |
| -> m (Context a) | 
Like 'metaToContext, but does not include variables and is
 not sensitive to writerTemplate.
addVariablesToContext :: TemplateTarget a => WriterOptions -> Context a -> Context a Source #
Add variables to a template Context, using monoidal append. Also add `meta-json`. Note that metadata values are used in template contexts only when like-named variables aren't set.
getField :: FromContext a b => Text -> Context a -> Maybe b Source #
Retrieve a field value from a template context.
setField :: ToContext a b => Text -> b -> Context a -> Context a Source #
Set a field of a template context. If the field already has a value, convert it into a list with the new value appended to the old value(s). This is a utility function to be used in preparing template contexts.
resetField :: ToContext a b => Text -> b -> Context a -> Context a Source #
Reset a field of a template context. If the field already has a value, the new value replaces it. This is a utility function to be used in preparing template contexts.
defField :: ToContext a b => Text -> b -> Context a -> Context a Source #
Set a field of a template context if it currently has no value. If it has a value, do nothing. This is a utility function to be used in preparing template contexts.
getLang :: WriterOptions -> Meta -> Maybe Text Source #
Get the contents of the lang metadata field or variable.
tagWithAttrs :: HasChars a => a -> Attr -> Doc a Source #
Produce an HTML tag with the given pandoc attributes.
htmlAddStyle :: (Text, Text) -> [(Text, Text)] -> [(Text, Text)] Source #
Adds a key-value pair to the style attribute.
htmlAlignmentToString :: Alignment -> Maybe Text Source #
Get the html representation of an alignment key
htmlAttrs :: HasChars a => Attr -> Doc a Source #
Produce HTML for the given pandoc attributes, to be used in HTML tags
isDisplayMath :: Inline -> Bool Source #
Returns True iff the argument is an inline Math element of type
 DisplayMath.
fixDisplayMath :: Block -> Block Source #
Put display math in its own block (for ODT/DOCX).
unsmartify :: WriterOptions -> Text -> Text Source #
Converts a Unicode character into the ASCII sequence used to represent the character in "smart" Markdown.
Arguments
| :: (Monad m, HasChars a) | |
| => WriterOptions | |
| -> (WriterOptions -> [Block] -> m (Doc a)) | format Doc writer | 
| -> Bool | headless | 
| -> [Alignment] | column alignments | 
| -> [Double] | column widths | 
| -> [[Block]] | table header row | 
| -> [[[Block]]] | table body rows | 
| -> m (Doc a) | 
Writes a grid table.
lookupMetaBool :: Text -> Meta -> Bool Source #
Retrieve the metadata value for a given key
 and convert to Bool.
lookupMetaBlocks :: Text -> Meta -> [Block] Source #
Retrieve the metadata value for a given key
 and extract blocks.
lookupMetaInlines :: Text -> Meta -> [Inline] Source #
Retrieve the metadata value for a given key
 and extract inlines.
lookupMetaString :: Text -> Meta -> Text Source #
Retrieve the metadata value for a given key
 and convert to String.
stripLeadingTrailingSpace :: [Inline] -> [Inline] Source #
Remove leading and trailing Space and SoftBreak elements.
toSubscript :: Char -> Maybe Char Source #
Tries to convert a character into a unicode subscript version of the character.
toSuperscript :: Char -> Maybe Char Source #
Tries to convert a character into a unicode superscript version of the character.
toTableOfContents :: WriterOptions -> [Block] -> Block Source #
Construct table of contents (as a bullet list) from document body.
endsWithPlain :: [Block] -> Bool Source #
Returns True iff the list of blocks has a Plain
toLegacyTable :: Caption -> [ColSpec] -> TableHead -> [TableBody] -> TableFoot -> ([Inline], [Alignment], [Double], [[Block]], [[[Block]]]) Source #
Convert the relevant components of a new-style table (with block
 caption, row headers, row and column spans, and so on) to those of
 an old-style table (inline caption, table head with one row, no
 foot, and so on). Cells with a RowSpan and ColSpan of (h, w)
 will be cut up into h * w cells of dimension (1, 1), with the
 content placed in the upper-left corner.
splitSentences :: Doc Text -> Doc Text Source #
ensureValidXmlIdentifiers :: Pandoc -> Pandoc Source #
Ensure that all identifiers start with a letter, and modify internal links accordingly. (Yes, XML allows an underscore, but HTML 4 doesn't, so we are more conservative.)
setupTranslations :: PandocMonad m => Meta -> m () Source #
Set translations based on the lang in metadata.