| Portability | portable | 
|---|---|
| Stability | alpha | 
| Maintainer | John MacFarlane <jgm@berkeley.edu> | 
| Safe Haskell | None | 
Text.Pandoc.Shared
Contents
Description
Utility functions and definitions used by the various Pandoc modules.
- splitBy :: (a -> Bool) -> [a] -> [[a]]
- splitByIndices :: [Int] -> [a] -> [[a]]
- splitStringByIndices :: [Int] -> [Char] -> [[Char]]
- substitute :: Eq a => [a] -> [a] -> [a] -> [a]
- backslashEscapes :: [Char] -> [(Char, String)]
- escapeStringUsing :: [(Char, String)] -> String -> String
- stripTrailingNewlines :: String -> String
- removeLeadingTrailingSpace :: String -> String
- removeLeadingSpace :: String -> String
- removeTrailingSpace :: String -> String
- stripFirstAndLast :: String -> String
- camelCaseToHyphenated :: String -> String
- toRomanNumeral :: Int -> String
- escapeURI :: String -> String
- tabFilter :: Int -> String -> String
- normalizeDate :: String -> Maybe String
- orderedListMarkers :: (Int, ListNumberStyle, ListNumberDelim) -> [String]
- normalizeSpaces :: [Inline] -> [Inline]
- normalize :: (Eq a, Data a) => a -> a
- stringify :: [Inline] -> String
- compactify :: [[Block]] -> [[Block]]
- data Element
- hierarchicalize :: [Block] -> [Element]
- uniqueIdent :: [Inline] -> [String] -> String
- isHeaderBlock :: Block -> Bool
- headerShift :: Int -> Pandoc -> Pandoc
- data HTMLMathMethod
- data CiteMethod
- data ObfuscationMethod
- data  HTMLSlideVariant - = S5Slides
- | SlidySlides
- | SlideousSlides
- | DZSlides
- | NoSlides
 
- data  WriterOptions  = WriterOptions {- writerStandalone :: Bool
- writerTemplate :: String
- writerVariables :: [(String, String)]
- writerEPUBMetadata :: String
- writerTabStop :: Int
- writerTableOfContents :: Bool
- writerSlideVariant :: HTMLSlideVariant
- writerIncremental :: Bool
- writerXeTeX :: Bool
- writerHTMLMathMethod :: HTMLMathMethod
- writerIgnoreNotes :: Bool
- writerNumberSections :: Bool
- writerSectionDivs :: Bool
- writerStrictMarkdown :: Bool
- writerReferenceLinks :: Bool
- writerWrapText :: Bool
- writerColumns :: Int
- writerLiterateHaskell :: Bool
- writerEmailObfuscation :: ObfuscationMethod
- writerIdentifierPrefix :: String
- writerSourceDirectory :: FilePath
- writerUserDataDir :: Maybe FilePath
- writerCiteMethod :: CiteMethod
- writerBiblioFiles :: [FilePath]
- writerHtml5 :: Bool
- writerBeamer :: Bool
- writerSlideLevel :: Maybe Int
- writerChapters :: Bool
- writerListings :: Bool
- writerHighlight :: Bool
- writerHighlightStyle :: Style
- writerSetextHeaders :: Bool
- writerTeXLigatures :: Bool
 
- defaultWriterOptions :: WriterOptions
- inDirectory :: FilePath -> IO a -> IO a
- findDataFile :: Maybe FilePath -> FilePath -> IO FilePath
- readDataFile :: Maybe FilePath -> FilePath -> IO String
- err :: Int -> String -> IO a
- warn :: String -> IO ()
List processing
splitByIndices :: [Int] -> [a] -> [[a]]Source
splitStringByIndices :: [Int] -> [Char] -> [[Char]]Source
Split string into chunks divided at specified indices.
substitute :: Eq a => [a] -> [a] -> [a] -> [a]Source
Replace each occurrence of one sublist in a list with another.
Text processing
Arguments
| :: [Char] | list of special characters to escape | 
| -> [(Char, String)] | 
Returns an association list of backslash escapes for the designated characters.
escapeStringUsing :: [(Char, String)] -> String -> StringSource
Escape a string of characters, using an association list of characters and strings.
stripTrailingNewlines :: String -> StringSource
Strip trailing newlines from string.
removeLeadingTrailingSpace :: String -> StringSource
Remove leading and trailing space (including newlines) from string.
removeLeadingSpace :: String -> StringSource
Remove leading space (including newlines) from string.
removeTrailingSpace :: String -> StringSource
Remove trailing space (including newlines) from string.
stripFirstAndLast :: String -> StringSource
Strip leading and trailing characters from string
camelCaseToHyphenated :: String -> StringSource
Change CamelCase word to hyphenated lowercase (e.g., camel-case).
toRomanNumeral :: Int -> StringSource
Convert number < 4000 to uppercase roman numeral.
Arguments
| :: Int | Tab stop | 
| -> String | Input | 
| -> String | 
Convert tabs to spaces and filter out DOS line endings. Tabs will be preserved if tab stop is set to 0.
Date/time
normalizeDate :: String -> Maybe StringSource
Parse a date and convert (if possible) to YYYY-MM-DD format.
Pandoc block and inline list processing
orderedListMarkers :: (Int, ListNumberStyle, ListNumberDelim) -> [String]Source
Generate infinite lazy list of markers for an ordered list, depending on list attributes.
normalizeSpaces :: [Inline] -> [Inline]Source
Normalize a list of inline elements: remove leading and trailing
 Space elements, collapse double Spaces into singles, and
 remove empty Str elements.
Change final list item from Para to Plain if the list contains
 no other Para blocks.
Data structure for defining hierarchical Pandoc documents
hierarchicalize :: [Block] -> [Element]Source
Convert list of Pandoc blocks into (hierarchical) list of Elements
uniqueIdent :: [Inline] -> [String] -> StringSource
Generate a unique identifier from a list of inlines. Second argument is a list of already used identifiers.
isHeaderBlock :: Block -> BoolSource
True if block is a Header block.
headerShift :: Int -> Pandoc -> PandocSource
Shift header levels up or down.
Writer options
data HTMLMathMethod Source
Constructors
| PlainMath | |
| LaTeXMathML (Maybe String) | |
| JsMath (Maybe String) | |
| GladTeX | |
| WebTeX String | |
| MathML (Maybe String) | |
| MathJax String | 
Instances
| Eq HTMLMathMethod | |
| Read HTMLMathMethod | |
| Show HTMLMathMethod | 
data CiteMethod Source
Instances
| Eq CiteMethod | |
| Read CiteMethod | |
| Show CiteMethod | 
data ObfuscationMethod Source
Methods for obfuscating email addresses in HTML.
Constructors
| NoObfuscation | |
| ReferenceObfuscation | |
| JavascriptObfuscation | 
Instances
| Eq ObfuscationMethod | |
| Read ObfuscationMethod | |
| Show ObfuscationMethod | 
data HTMLSlideVariant Source
Varieties of HTML slide shows.
Constructors
| S5Slides | |
| SlidySlides | |
| SlideousSlides | |
| DZSlides | |
| NoSlides | 
Instances
| Eq HTMLSlideVariant | |
| Read HTMLSlideVariant | |
| Show HTMLSlideVariant | 
data WriterOptions Source
Options for writers
Constructors
| WriterOptions | |
| Fields 
 | |
Instances
| Show WriterOptions | 
defaultWriterOptions :: WriterOptionsSource
Default writer options.
File handling
inDirectory :: FilePath -> IO a -> IO aSource
Perform an IO action in a directory, returning to starting directory.
findDataFile :: Maybe FilePath -> FilePath -> IO FilePathSource
Get file path for data file, either from specified user data directory, or, if not found there, from Cabal data directory.
readDataFile :: Maybe FilePath -> FilePath -> IO StringSource
Read file from specified user data directory or, if not found there, from Cabal data directory.