Copyright | Copyright (C) 2006-2018 John MacFarlane |
---|---|
License | GNU GPL, version 2 or above |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Stability | alpha |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Text.Pandoc.Shared
Contents
Description
Utility functions and definitions used by the various Pandoc modules.
Synopsis
- 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 -> Text -> Text
- crFilter :: Text -> Text
- normalizeDate :: String -> Maybe String
- orderedListMarkers :: (Int, ListNumberStyle, ListNumberDelim) -> [String]
- extractSpaces :: (Inlines -> Inlines) -> Inlines -> Inlines
- removeFormatting :: Walkable Inline a => a -> [Inline]
- deNote :: Inline -> Inline
- stringify :: Walkable Inline a => a -> String
- capitalize :: Walkable Inline a => a -> a
- compactify :: [Blocks] -> [Blocks]
- compactifyDL :: [(Inlines, [Blocks])] -> [(Inlines, [Blocks])]
- linesToPara :: [[Inline]] -> Block
- data Element
- hierarchicalize :: [Block] -> [Element]
- uniqueIdent :: [Inline] -> Set String -> String
- inlineListToIdentifier :: [Inline] -> String
- isHeaderBlock :: Block -> Bool
- headerShift :: Int -> Pandoc -> Pandoc
- stripEmptyParagraphs :: Pandoc -> Pandoc
- isTightList :: [[Block]] -> Bool
- addMetaField :: ToMetaValue a => String -> a -> Meta -> Meta
- makeMeta :: [Inline] -> [[Inline]] -> [Inline] -> Meta
- eastAsianLineBreakFilter :: Pandoc -> Pandoc
- underlineSpan :: Inlines -> Inlines
- renderTags' :: [Tag String] -> String
- inDirectory :: FilePath -> IO a -> IO a
- collapseFilePath :: FilePath -> FilePath
- uriPathToPath :: String -> FilePath
- filteredFilesFromArchive :: Archive -> (FilePath -> Bool) -> [(FilePath, ByteString)]
- schemes :: Set String
- isURI :: String -> Bool
- mapLeft :: (a -> b) -> Either a c -> Either b c
- blocksToInlines :: [Block] -> [Inline]
- blocksToInlines' :: [Block] -> Inlines
- 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.
trim :: String -> String Source #
Remove leading and 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.
Convert tabs to spaces. 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. 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) -> [String] 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 -> 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”.
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]
.
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.
Data structure for defining hierarchical Pandoc documents
Instances
Eq Element Source # | |
Data Element Source # | |
Defined in Text.Pandoc.Shared Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Element -> c Element # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Element # toConstr :: Element -> Constr # dataTypeOf :: Element -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Element) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Element) # gmapT :: (forall b. Data b => b -> b) -> Element -> Element # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Element -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Element -> r # gmapQ :: (forall d. Data d => d -> u) -> Element -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Element -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Element -> m Element # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Element -> m Element # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Element -> m Element # | |
Read Element Source # | |
Show Element Source # | |
ToLuaStack Element | |
Defined in Text.Pandoc.Lua.StackInstances | |
Walkable Block Element Source # | |
Walkable Inline Element Source # | |
hierarchicalize :: [Block] -> [Element] Source #
Convert list of Pandoc blocks into (hierarchical) list of Elements
uniqueIdent :: [Inline] -> Set String -> String Source #
Generate a unique identifier from a list of inlines. Second argument is a list of already used identifiers.
inlineListToIdentifier :: [Inline] -> String 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.
headerShift :: Int -> Pandoc -> Pandoc Source #
Shift header levels up or down.
stripEmptyParagraphs :: Pandoc -> Pandoc Source #
Remove empty paragraphs.
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.
eastAsianLineBreakFilter :: Pandoc -> Pandoc Source #
Remove soft breaks between East Asian characters.
underlineSpan :: Inlines -> Inlines Source #
Builder for underline. This probably belongs in Builder.hs in pandoc-types. Will be replaced once Underline is an element.
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.
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 :: String -> FilePath Source #
filteredFilesFromArchive :: Archive -> (FilePath -> Bool) -> [(FilePath, ByteString)] Source #
URI handling
schemes :: Set String Source #
Schemes from http://www.iana.org/assignments/uri-schemes.html plus the unofficial schemes doi, javascript, isbn, pmid.
isURI :: String -> 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 #
Safe read
Temp directory
Version
pandocVersion :: String Source #
Version number of pandoc library.