Copyright | Copyright (C) 2006-2020 John MacFarlane |
---|---|
License | GNU GPL, version 2 or above |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Stability | alpha |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Utility functions and definitions used by the various Pandoc modules.
Synopsis
- splitBy :: (a -> Bool) -> [a] -> [[a]]
- splitTextBy :: (Char -> Bool) -> Text -> [Text]
- splitByIndices :: [Int] -> [a] -> [[a]]
- splitStringByIndices :: [Int] -> [Char] -> [[Char]]
- splitTextByIndices :: [Int] -> Text -> [Text]
- substitute :: Eq a => [a] -> [a] -> [a] -> [a]
- ordNub :: Ord a => [a] -> [a]
- findM :: forall m t a. (Monad m, Foldable t) => (a -> m Bool) -> t a -> m (Maybe a)
- class ToString a where
- class ToText a where
- tshow :: Show a => a -> Text
- backslashEscapes :: [Char] -> [(Char, Text)]
- escapeStringUsing :: [(Char, Text)] -> Text -> Text
- elemText :: Char -> Text -> Bool
- notElemText :: Char -> Text -> Bool
- stripTrailingNewlines :: Text -> Text
- trim :: Text -> Text
- triml :: Text -> Text
- trimr :: Text -> Text
- trimMath :: Text -> Text
- stripFirstAndLast :: Text -> Text
- camelCaseToHyphenated :: Text -> Text
- camelCaseStrToHyphenated :: String -> String
- toRomanNumeral :: Int -> Text
- escapeURI :: Text -> Text
- tabFilter :: Int -> Text -> Text
- crFilter :: Text -> Text
- normalizeDate :: Text -> Maybe Text
- orderedListMarkers :: (Int, ListNumberStyle, ListNumberDelim) -> [Text]
- extractSpaces :: (Inlines -> Inlines) -> Inlines -> Inlines
- removeFormatting :: Walkable Inline a => a -> [Inline]
- deNote :: Inline -> Inline
- deLink :: Inline -> Inline
- stringify :: Walkable Inline a => a -> Text
- capitalize :: Walkable Inline a => a -> a
- compactify :: [Blocks] -> [Blocks]
- compactifyDL :: [(Inlines, [Blocks])] -> [(Inlines, [Blocks])]
- linesToPara :: [[Inline]] -> Block
- makeSections :: Bool -> Maybe Int -> [Block] -> [Block]
- uniqueIdent :: Extensions -> [Inline] -> Set Text -> Text
- inlineListToIdentifier :: Extensions -> [Inline] -> Text
- isHeaderBlock :: Block -> Bool
- headerShift :: Int -> Pandoc -> Pandoc
- stripEmptyParagraphs :: Pandoc -> Pandoc
- onlySimpleTableCells :: [[[Block]]] -> Bool
- isTightList :: [[Block]] -> Bool
- taskListItemFromAscii :: Extensions -> [Block] -> [Block]
- taskListItemToAscii :: Extensions -> [Block] -> [Block]
- addMetaField :: ToMetaValue a => Text -> a -> Meta -> Meta
- makeMeta :: [Inline] -> [[Inline]] -> [Inline] -> Meta
- eastAsianLineBreakFilter :: Pandoc -> Pandoc
- underlineSpan :: Inlines -> Inlines
- htmlSpanLikeElements :: Set Text
- splitSentences :: [Inline] -> [[Inline]]
- filterIpynbOutput :: Maybe Format -> Pandoc -> Pandoc
- renderTags' :: [Tag Text] -> Text
- inDirectory :: FilePath -> IO a -> IO a
- collapseFilePath :: FilePath -> FilePath
- uriPathToPath :: Text -> FilePath
- filteredFilesFromArchive :: Archive -> (FilePath -> Bool) -> [(FilePath, ByteString)]
- schemes :: Set Text
- isURI :: Text -> Bool
- mapLeft :: (a -> b) -> Either a c -> Either b c
- blocksToInlines :: [Block] -> [Inline]
- blocksToInlines' :: [Block] -> Inlines
- blocksToInlinesWithSep :: Inlines -> [Block] -> Inlines
- defaultBlocksSeparator :: Inlines
- safeRead :: (MonadPlus m, Read a) => Text -> m a
- safeStrRead :: (MonadPlus m, Read a) => String -> m a
- defaultUserDataDirs :: IO [FilePath]
- pandocVersion :: Text
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, Text)] -> Text -> Text Source #
Escape a string of characters, using an association list of characters and strings.
stripTrailingNewlines :: Text -> Text Source #
Strip trailing newlines from string.
stripFirstAndLast :: Text -> Text Source #
Strip leading and trailing characters from string
camelCaseToHyphenated :: Text -> Text Source #
Change CamelCase word to hyphenated lowercase (e.g., camel-case).
toRomanNumeral :: Int -> Text Source #
Convert number < 4000 to uppercase roman numeral.
Convert tabs to spaces. Tabs will be preserved if tab stop is set to 0.
Date/time
normalizeDate :: Text -> Maybe Text Source #
Parse a date and convert (if possible) to "YYYY-MM-DD" format. We limit years to the range 1601-9999 (ISO 8601 accepts greater than or equal to 1583, but MS Word only accepts dates starting 1601).
Pandoc block and inline list processing
orderedListMarkers :: (Int, ListNumberStyle, ListNumberDelim) -> [Text] Source #
Generate infinite lazy list of markers for an ordered list, depending on list attributes.
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.
removeFormatting :: Walkable Inline a => a -> [Inline] Source #
Extract inlines, removing formatting.
stringify :: Walkable Inline a => a -> Text 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. Otherwise (if the list items contain Para
blocks besides possibly at the end), turn any Plain
s into Para
s (#5285).
compactifyDL :: [(Inlines, [Blocks])] -> [(Inlines, [Blocks])] Source #
Like compactify
, but acts on items of definition lists.
linesToPara :: [[Inline]] -> Block Source #
Convert a list of lines into a paragraph with hard line breaks. This is useful e.g. for rudimentary support of LineBlock elements in writers.
makeSections :: Bool -> Maybe Int -> [Block] -> [Block] Source #
Put a list of Pandoc blocks into a hierarchical structure:
a list of sections (each a Div with class "section" and first
element a Header). If the numbering
parameter is True, Header
numbers are added via the number attribute on the header.
If the baseLevel parameter is Just n, Header levels are
adjusted to be gapless starting at level n.
uniqueIdent :: Extensions -> [Inline] -> Set Text -> Text Source #
Generate a unique identifier from a list of inlines. Second argument is a list of already used identifiers.
inlineListToIdentifier :: Extensions -> [Inline] -> Text Source #
Convert Pandoc inline list to plain text identifier. HTML identifiers must start with a letter, and may contain only letters, digits, and the characters _-.
isHeaderBlock :: Block -> Bool Source #
True if block is a Header block.
stripEmptyParagraphs :: Pandoc -> Pandoc Source #
Remove empty paragraphs.
onlySimpleTableCells :: [[[Block]]] -> Bool Source #
Detect if table rows contain only cells consisting of a single
paragraph that has no LineBreak
.
isTightList :: [[Block]] -> Bool Source #
Detect if a list is tight.
taskListItemFromAscii :: Extensions -> [Block] -> [Block] Source #
Convert a list item containing tasklist syntax (e.g. [x]
)
to using U+2610 BALLOT BOX
or U+2612 BALLOT BOX WITH X
.
taskListItemToAscii :: Extensions -> [Block] -> [Block] Source #
Convert a list item containing text starting with U+2610 BALLOT BOX
or U+2612 BALLOT BOX WITH X
to tasklist syntax (e.g. [x]
).
addMetaField :: ToMetaValue a => Text -> 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.
eastAsianLineBreakFilter :: Pandoc -> Pandoc Source #
Remove soft breaks between East Asian characters.
underlineSpan :: Inlines -> Inlines Source #
Deprecated: Use Text.Pandoc.Builder.underline instead
Builder for underline (deprecated). This probably belongs in Builder.hs in pandoc-types. Will be replaced once Underline is an element.
htmlSpanLikeElements :: Set Text Source #
Set of HTML elements that are represented as Span with a class equal as the element tag itself.
splitSentences :: [Inline] -> [[Inline]] Source #
Split a list of inlines into sentences.
filterIpynbOutput :: Maybe Format -> Pandoc -> Pandoc Source #
Process ipynb output cells. If mode is Nothing, remove all output. If mode is Just format, select best output for the format. If format is not ipynb, strip out ANSI escape sequences from CodeBlocks (see #5633).
TagSoup HTML handling
File handling
inDirectory :: FilePath -> IO a -> IO a Source #
Perform an IO action in a directory, returning to starting directory.
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"
uriPathToPath :: Text -> FilePath Source #
filteredFilesFromArchive :: Archive -> (FilePath -> Bool) -> [(FilePath, ByteString)] Source #
URI handling
Schemes from http://www.iana.org/assignments/uri-schemes.html plus the unofficial schemes doi, javascript, isbn, pmid.
isURI :: Text -> Bool Source #
Check if the string is a valid URL with a IANA or frequently used but
unofficial scheme (see schemes
).
Error handling
for squashing blocks
blocksToInlines :: [Block] -> [Inline] Source #
blocksToInlines' :: [Block] -> Inlines Source #
defaultBlocksSeparator :: Inlines Source #
Inline elements used to separate blocks when squashing blocks into inlines.
Safe read
User data directory
defaultUserDataDirs :: IO [FilePath] Source #
Return appropriate user data directory for platform. We use XDG_DATA_HOME (or its default value), but fall back to the legacy user data directory ($HOME/.pandoc on *nix) if this is missing.
Version
pandocVersion :: Text Source #
Version number of pandoc library.