pandoc-1.15.1.1: Conversion between markup formats

CopyrightCopyright (C) 2006-2015 John MacFarlane
LicenseGNU GPL, version 2 or above
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Stabilityalpha
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Text.Pandoc.Shared

Contents

Description

Utility functions and definitions used by the various Pandoc modules.

Synopsis

List processing

splitBy :: (a -> Bool) -> [a] -> [[a]] Source

Split list by groups of one or more sep.

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.

ordNub :: Ord a => [a] -> [a] Source

Text processing

backslashEscapes Source

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 -> String Source

Escape a string of characters, using an association list of characters and strings.

stripTrailingNewlines :: String -> String Source

Strip trailing newlines from string.

trim :: String -> String Source

Remove leading and trailing space (including newlines) from string.

triml :: String -> String Source

Remove leading space (including newlines) from string.

trimr :: String -> String Source

Remove trailing space (including 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.

escapeURI :: String -> String Source

Escape whitespace and some punctuation characters in URI.

tabFilter Source

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 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.

normalize :: Pandoc -> Pandoc Source

Normalize Pandoc document, consolidating doubled Spaces, combining adjacent Strs and Emphs, remove Nulls and empty elements, etc.

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”.

compactify Source

Arguments

:: [[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.

compactify' Source

Arguments

:: [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])] Source

Like compactify', but acts on items of definition lists.

data Element Source

Data structure for defining hierarchical Pandoc documents

Constructors

Blk Block 
Sec Int [Int] Attr [Inline] [Element] 

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

Like fetchItem, but also looks for items in a MediaBag.

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

err :: Int -> String -> IO a Source

warn :: String -> IO () Source

mapLeft :: (a -> b) -> Either a c -> Either b c Source

hush :: Either a b -> Maybe b Source

Safe read

safeRead :: (MonadPlus m, Read a) => String -> m a Source

Temp directory

Version

pandocVersion :: String Source

Version number of pandoc library.