Copyright | Copyright (C) 2013-2019 John MacFarlane |
---|---|
License | GNU GPL, version 2 or above |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Stability | alpha |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Shared utility functions for pandoc writers.
Synopsis
- metaToJSON :: (Functor m, Monad m, ToJSON a) => WriterOptions -> ([Block] -> m a) -> ([Inline] -> m a) -> Meta -> m Value
- metaToJSON' :: (Functor m, Monad m, ToJSON a) => ([Block] -> m a) -> ([Inline] -> m a) -> Meta -> m Value
- addVariablesToJSON :: WriterOptions -> Value -> Value
- getField :: FromJSON a => String -> Value -> Maybe a
- setField :: ToJSON a => String -> a -> Value -> Value
- resetField :: ToJSON a => String -> a -> Value -> Value
- defField :: ToJSON a => String -> a -> Value -> Value
- tagWithAttrs :: String -> Attr -> Doc
- isDisplayMath :: Inline -> Bool
- fixDisplayMath :: Block -> Block
- unsmartify :: WriterOptions -> String -> String
- gridTable :: Monad m => WriterOptions -> (WriterOptions -> [Block] -> m Doc) -> Bool -> [Alignment] -> [Double] -> [[Block]] -> [[[Block]]] -> m Doc
- lookupMetaBool :: String -> Meta -> Bool
- lookupMetaBlocks :: String -> Meta -> [Block]
- lookupMetaInlines :: String -> Meta -> [Inline]
- lookupMetaString :: String -> Meta -> String
- stripLeadingTrailingSpace :: [Inline] -> [Inline]
- toSubscript :: Char -> Maybe Char
- toSuperscript :: Char -> Maybe Char
- toTableOfContents :: WriterOptions -> [Block] -> Block
Documentation
metaToJSON :: (Functor m, Monad m, ToJSON a) => WriterOptions -> ([Block] -> m a) -> ([Inline] -> m a) -> Meta -> m Value Source #
Create JSON value for template 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.
metaToJSON' :: (Functor m, Monad m, ToJSON a) => ([Block] -> m a) -> ([Inline] -> m a) -> Meta -> m Value Source #
Like metaToJSON
, but does not include variables and is
not sensitive to writerTemplate
.
addVariablesToJSON :: WriterOptions -> Value -> Value Source #
Add variables to JSON object, replacing any existing values.
Also include meta-json
, a field containing a string representation
of the original JSON object itself, prior to addition of variables.
getField :: FromJSON a => String -> Value -> Maybe a Source #
Retrieve a field value from a JSON object.
setField :: ToJSON a => String -> a -> Value -> Value Source #
Set a field of a JSON object. 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 :: ToJSON a => String -> a -> Value -> Value Source #
Reset a field of a JSON object. 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 :: ToJSON a => String -> a -> Value -> Value Source #
Set a field of a JSON object 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.
isDisplayMath :: Inline -> Bool Source #
fixDisplayMath :: Block -> Block Source #
unsmartify :: WriterOptions -> String -> String Source #
lookupMetaBool :: String -> Meta -> Bool Source #
Retrieve the metadata value for a given key
and convert to Bool.
lookupMetaBlocks :: String -> Meta -> [Block] Source #
Retrieve the metadata value for a given key
and extract blocks.
lookupMetaInlines :: String -> Meta -> [Inline] Source #
Retrieve the metadata value for a given key
and extract inlines.
lookupMetaString :: String -> Meta -> String Source #
Retrieve the metadata value for a given key
and convert to String.
stripLeadingTrailingSpace :: [Inline] -> [Inline] Source #
toTableOfContents :: WriterOptions -> [Block] -> Block Source #
Construct table of contents (as a bullet list) from document body.