Copyright | Copyright (C) 2006-2014 John MacFarlane |
---|---|
License | GNU GPL, version 2 or above |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Stability | alpha |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
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
- trim :: String -> String
- triml :: String -> String
- trimr :: 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 :: Walkable Inline a => a -> String
- compactify :: [[Block]] -> [[Block]]
- compactify' :: [Blocks] -> [Blocks]
- compactify'DL :: [(Inlines, [Blocks])] -> [(Inlines, [Blocks])]
- data Element
- hierarchicalize :: [Block] -> [Element]
- uniqueIdent :: [Inline] -> [String] -> String
- isHeaderBlock :: Block -> Bool
- headerShift :: Int -> Pandoc -> Pandoc
- isTightList :: [[Block]] -> Bool
- addMetaField :: ToMetaValue a => String -> a -> Meta -> Meta
- makeMeta :: [Inline] -> [[Inline]] -> [Inline] -> Meta
- renderTags' :: [Tag String] -> String
- inDirectory :: FilePath -> IO a -> IO a
- readDataFile :: Maybe FilePath -> FilePath -> IO ByteString
- readDataFileUTF8 :: Maybe FilePath -> FilePath -> IO String
- fetchItem :: Maybe String -> String -> IO (Either SomeException (ByteString, Maybe String))
- openURL :: String -> IO (Either SomeException (ByteString, Maybe String))
- err :: Int -> String -> IO a
- warn :: String -> IO ()
- safeRead :: (Monad m, Read a) => String -> m a
List processing
splitByIndices :: [Int] -> [a] -> [[a]]
splitStringByIndices :: [Int] -> [Char] -> [[Char]]
Split string into chunks divided at specified indices.
substitute :: Eq a => [a] -> [a] -> [a] -> [a]
Replace each occurrence of one sublist in a list with another.
Text processing
Returns an association list of backslash escapes for the designated characters.
escapeStringUsing :: [(Char, String)] -> String -> String
Escape a string of characters, using an association list of characters and strings.
stripTrailingNewlines :: String -> String
Strip trailing newlines from string.
stripFirstAndLast :: String -> String
Strip leading and trailing characters from string
camelCaseToHyphenated :: String -> String
Change CamelCase word to hyphenated lowercase (e.g., camel-case).
toRomanNumeral :: Int -> String
Convert number < 4000 to uppercase roman numeral.
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 String
Parse a date and convert (if possible) to YYYY-MM-DD format.
Pandoc block and inline list processing
orderedListMarkers :: (Int, ListNumberStyle, ListNumberDelim) -> [String]
Generate infinite lazy list of markers for an ordered list, depending on list attributes.
normalizeSpaces :: [Inline] -> [Inline]
Normalize a list of inline elements: remove leading and trailing
Space
elements, collapse double Space
s into singles, and
remove empty Str elements.
normalize :: (Eq a, Data a) => a -> a
Normalize Pandoc
document, consolidating doubled Space
s,
combining adjacent Str
s and Emph
s, remove Null
s and
empty elements, etc.
stringify :: Walkable Inline a => a -> String
Convert pandoc structure to a string with formatting removed. Footnotes are skipped (since we don't want their contents in link labels).
:: [[Block]] | List of list items (each a list of blocks) |
-> [[Block]] |
Change final list item from Para
to Plain
if the list contains
no other Para
blocks.
:: [Blocks] | List of list items (each a list of blocks) |
-> [Blocks] |
Change final list item from Para
to Plain
if the list contains
no other Para
blocks. Like compactify, but operates on Blocks
rather
than [Block]
.
compactify'DL :: [(Inlines, [Blocks])] -> [(Inlines, [Blocks])]
Like compactify'
, but akts on items of definition lists.
data Element
Data structure for defining hierarchical Pandoc documents
hierarchicalize :: [Block] -> [Element]
Convert list of Pandoc blocks into (hierarchical) list of Elements
uniqueIdent :: [Inline] -> [String] -> String
Generate a unique identifier from a list of inlines. Second argument is a list of already used identifiers.
isHeaderBlock :: Block -> Bool
True if block is a Header block.
headerShift :: Int -> Pandoc -> Pandoc
Shift header levels up or down.
isTightList :: [[Block]] -> Bool
Detect if a list is tight.
addMetaField :: ToMetaValue a => String -> a -> Meta -> Meta
Set a field of a Meta
object. If the field already has a value,
convert it into a list with the new value appended to the old value(s).
makeMeta :: [Inline] -> [[Inline]] -> [Inline] -> Meta
Create Meta
from old-style title, authors, date. This is
provided to ease the transition from the old API.
TagSoup HTML handling
renderTags' :: [Tag String] -> String
Render HTML tags.
File handling
inDirectory :: FilePath -> IO a -> IO a
Perform an IO action in a directory, returning to starting directory.
readDataFile :: Maybe FilePath -> FilePath -> IO ByteString
Read file from specified user data directory or, if not found there, from Cabal data directory.
readDataFileUTF8 :: Maybe FilePath -> FilePath -> IO String
Same as readDataFile
but returns a String instead of a ByteString.
fetchItem :: Maybe String -> String -> IO (Either SomeException (ByteString, Maybe String))
Fetch an image or other item from the local filesystem or the net. Returns raw content and maybe mime type.
openURL :: String -> IO (Either SomeException (ByteString, Maybe String))
Read from a URL and return raw data and maybe mime type.