| Copyright | Copyright (C) 2006-2015 John MacFarlane | 
|---|---|
| License | GNU GPL, version 2 or above | 
| Maintainer | John MacFarlane <jgm@berkeley.edu> | 
| Stability | alpha | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell98 | 
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]
- ordNub :: Ord 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]
- extractSpaces :: (Inlines -> Inlines) -> Inlines -> Inlines
- normalize :: Pandoc -> Pandoc
- normalizeInlines :: [Inline] -> [Inline]
- normalizeBlocks :: [Block] -> [Block]
- removeFormatting :: Walkable Inline a => a -> [Inline]
- stringify :: Walkable Inline a => a -> String
- capitalize :: Walkable Inline a => a -> a
- 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
- getDefaultReferenceDocx :: Maybe FilePath -> IO Archive
- getDefaultReferenceODT :: Maybe FilePath -> IO Archive
- readDataFile :: Maybe FilePath -> FilePath -> IO ByteString
- readDataFileUTF8 :: Maybe FilePath -> FilePath -> IO String
- fetchItem :: Maybe String -> String -> IO (Either SomeException (ByteString, Maybe MimeType))
- fetchItem' :: MediaBag -> Maybe String -> String -> IO (Either SomeException (ByteString, Maybe MimeType))
- openURL :: String -> IO (Either SomeException (ByteString, Maybe MimeType))
- collapseFilePath :: FilePath -> FilePath
- err :: Int -> String -> IO a
- warn :: String -> IO ()
- mapLeft :: (a -> b) -> Either a c -> Either b c
- hush :: Either a b -> Maybe b
- safeRead :: (MonadPlus m, Read a) => String -> m a
- withTempDir :: String -> (FilePath -> IO a) -> IO a
- pandocVersion :: String
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
Returns an association list of backslash escapes for the designated characters.
escapeStringUsing :: [(Char, String)] -> String -> String Source
Escape a string of characters, using an association list of characters and strings.
stripTrailingNewlines :: String -> String Source
Strip trailing newlines from string.
stripFirstAndLast :: String -> String Source
Strip leading and trailing characters from string
camelCaseToHyphenated :: String -> String Source
Change CamelCase word to hyphenated lowercase (e.g., camel-case).
toRomanNumeral :: Int -> String Source
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 Source
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.
extractSpaces :: (Inlines -> Inlines) -> Inlines -> Inlines Source
Extract the leading and trailing spaces from inside an inline element and place them outside the element. SoftBreaks count as Spaces for these purposes.
normalizeInlines :: [Inline] -> [Inline] Source
normalizeBlocks :: [Block] -> [Block] Source
removeFormatting :: Walkable Inline a => a -> [Inline] Source
Extract inlines, removing formatting.
stringify :: Walkable Inline a => a -> String Source
Convert pandoc structure to a string with formatting removed. Footnotes are skipped (since we don't want their contents in link labels).
capitalize :: Walkable Inline a => a -> a Source
Bring all regular text in a pandoc structure to uppercase.
This function correctly handles cases where a lowercase character doesn't match to a single uppercase character – e.g. “Straße” would be converted to “STRASSE”, not “STRAßE”.
Change final list item from Para to Plain if the list contains
 no other Para 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])] Source
Like compactify', but acts on items of definition lists.
Data structure for defining hierarchical Pandoc documents
hierarchicalize :: [Block] -> [Element] Source
Convert list of Pandoc blocks into (hierarchical) list of Elements
uniqueIdent :: [Inline] -> [String] -> String Source
Generate a unique identifier from a list of inlines. Second argument is a list of already used identifiers.
isHeaderBlock :: Block -> Bool Source
True if block is a Header block.
headerShift :: Int -> Pandoc -> Pandoc Source
Shift header levels up or down.
isTightList :: [[Block]] -> Bool Source
Detect if a list is tight.
addMetaField :: ToMetaValue a => String -> a -> Meta -> Meta Source
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 Source
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 Source
Render HTML tags.
File handling
inDirectory :: FilePath -> IO a -> IO a Source
Perform an IO action in a directory, returning to starting directory.
readDataFile :: Maybe FilePath -> FilePath -> IO ByteString Source
Read file from specified user data directory or, if not found there, from Cabal data directory.
readDataFileUTF8 :: Maybe FilePath -> FilePath -> IO String Source
Same as readDataFile but returns a String instead of a ByteString.
fetchItem :: Maybe String -> String -> IO (Either SomeException (ByteString, Maybe MimeType)) Source
Fetch an image or other item from the local filesystem or the net. Returns raw content and maybe mime type.
fetchItem' :: MediaBag -> Maybe String -> String -> IO (Either SomeException (ByteString, Maybe MimeType)) Source
openURL :: String -> IO (Either SomeException (ByteString, Maybe MimeType)) Source
Read from a URL and return raw data and maybe mime type.
collapseFilePath :: FilePath -> FilePath Source
Remove intermediate "." and ".." directories from a path.
collapseFilePath "./foo" == "foo" collapseFilePath "/bar/../baz" == "/baz" collapseFilePath "/../baz" == "/../baz" collapseFilePath "parent/foo/baz/../bar" == "parent/foo/bar" collapseFilePath "parent/foo/baz/../../bar" == "parent/bar" collapseFilePath "parent/foo/.." == "parent" collapseFilePath "/parent/foo/../../bar" == "/bar"
Error handling
Safe read
Temp directory
Version
pandocVersion :: String Source
Version number of pandoc library.