Portability | portable |
---|---|
Stability | alpha |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Safe Haskell | None |
A utility library with parsers used in pandoc readers.
- (>>~) :: Monad m => m a -> m b -> m a
- anyLine :: GenParser Char st [Char]
- many1Till :: GenParser tok st a -> GenParser tok st end -> GenParser tok st [a]
- notFollowedBy' :: Show b => GenParser a st b -> GenParser a st ()
- oneOfStrings :: [String] -> GenParser Char st String
- spaceChar :: CharParser st Char
- nonspaceChar :: CharParser st Char
- skipSpaces :: GenParser Char st ()
- blankline :: GenParser Char st Char
- blanklines :: GenParser Char st [Char]
- enclosed :: GenParser Char st t -> GenParser Char st end -> GenParser Char st a -> GenParser Char st [a]
- stringAnyCase :: [Char] -> CharParser st String
- parseFromString :: GenParser tok st a -> [tok] -> GenParser tok st a
- lineClump :: GenParser Char st String
- charsInBalanced :: Char -> Char -> GenParser Char st Char -> GenParser Char st String
- romanNumeral :: Bool -> GenParser Char st Int
- emailAddress :: GenParser Char st (String, String)
- uri :: GenParser Char st (String, String)
- withHorizDisplacement :: GenParser Char st a -> GenParser Char st (a, Int)
- withRaw :: GenParser Char st a -> GenParser Char st (a, [Char])
- nullBlock :: GenParser Char st Block
- failIfStrict :: GenParser a ParserState ()
- failUnlessLHS :: GenParser tok ParserState ()
- escaped :: GenParser Char st Char -> GenParser Char st Char
- characterReference :: GenParser Char st Char
- updateLastStrPos :: GenParser Char ParserState ()
- anyOrderedListMarker :: GenParser Char ParserState ListAttributes
- orderedListMarker :: ListNumberStyle -> ListNumberDelim -> GenParser Char ParserState Int
- charRef :: GenParser Char st Inline
- tableWith :: GenParser Char ParserState ([[Block]], [Alignment], [Int]) -> ([Int] -> GenParser Char ParserState [[Block]]) -> GenParser Char ParserState sep -> GenParser Char ParserState end -> GenParser Char ParserState [Inline] -> GenParser Char ParserState Block
- gridTableWith :: GenParser Char ParserState Block -> GenParser Char ParserState [Inline] -> Bool -> GenParser Char ParserState Block
- readWith :: GenParser t ParserState a -> ParserState -> [t] -> a
- testStringWith :: Show a => GenParser Char ParserState a -> String -> IO ()
- data ParserState = ParserState {
- stateParseRaw :: Bool
- stateParserContext :: ParserContext
- stateQuoteContext :: QuoteContext
- stateMaxNestingLevel :: Int
- stateLastStrPos :: Maybe SourcePos
- stateKeys :: KeyTable
- stateCitations :: [String]
- stateNotes :: NoteTable
- stateTabStop :: Int
- stateStandalone :: Bool
- stateTitle :: [Inline]
- stateAuthors :: [[Inline]]
- stateDate :: [Inline]
- stateStrict :: Bool
- stateSmart :: Bool
- stateOldDashes :: Bool
- stateLiterateHaskell :: Bool
- stateColumns :: Int
- stateHeaderTable :: [HeaderType]
- stateIndentedCodeClasses :: [String]
- stateNextExample :: Int
- stateExamples :: Map String Int
- stateHasChapters :: Bool
- stateApplyMacros :: Bool
- stateMacros :: [Macro]
- stateRstDefaultRole :: String
- defaultParserState :: ParserState
- data HeaderType
- = SingleHeader Char
- | DoubleHeader Char
- data ParserContext
- data QuoteContext
- type NoteTable = [(String, String)]
- type KeyTable = Map Key Target
- data Key
- toKey :: [Inline] -> Key
- fromKey :: Key -> [Inline]
- lookupKeySrc :: KeyTable -> Key -> Maybe Target
- smartPunctuation :: GenParser Char ParserState Inline -> GenParser Char ParserState Inline
- macro :: GenParser Char ParserState Block
- applyMacros' :: String -> GenParser Char ParserState String
Documentation
(>>~) :: Monad m => m a -> m b -> m aSource
Like >>, but returns the operation on the left. (Suggested by Tillmann Rendel on Haskell-cafe list.)
many1Till :: GenParser tok st a -> GenParser tok st end -> GenParser tok st [a]Source
Like manyTill
, but reads at least one item.
notFollowedBy' :: Show b => GenParser a st b -> GenParser a st ()Source
A more general form of notFollowedBy
. This one allows any
type of parser to be specified, and succeeds only if that parser fails.
It does not consume any input.
oneOfStrings :: [String] -> GenParser Char st StringSource
Parses one of a list of strings (tried in order).
spaceChar :: CharParser st CharSource
Parses a space or tab.
nonspaceChar :: CharParser st CharSource
Parses a nonspace, nonnewline character.
skipSpaces :: GenParser Char st ()Source
Skips zero or more spaces or tabs.
blanklines :: GenParser Char st [Char]Source
Parses one or more blank lines and returns a string of newlines.
:: GenParser Char st t | start parser |
-> GenParser Char st end | end parser |
-> GenParser Char st a | content parser (to be used repeatedly) |
-> GenParser Char st [a] |
Parses material enclosed between start and end parsers.
stringAnyCase :: [Char] -> CharParser st StringSource
Parse string, case insensitive.
parseFromString :: GenParser tok st a -> [tok] -> GenParser tok st aSource
Parse contents of str
using parser
and return result.
charsInBalanced :: Char -> Char -> GenParser Char st Char -> GenParser Char st StringSource
Parse a string of characters between an open character
and a close character, including text between balanced
pairs of open and close, which must be different. For example,
charsInBalanced '(' ')' anyChar
will parse (hello (there))
and return hello (there).
:: Bool | Uppercase if true |
-> GenParser Char st Int |
Parses a roman numeral (uppercase or lowercase), returns number.
emailAddress :: GenParser Char st (String, String)Source
Parses an email address; returns original and corresponding escaped mailto: URI.
uri :: GenParser Char st (String, String)Source
Parses a URI. Returns pair of original and URI-escaped version.
Applies a parser, returns tuple of its results and its horizontal displacement (the difference between the source column at the end and the source column at the beginning). Vertical displacement (source row) is ignored.
withRaw :: GenParser Char st a -> GenParser Char st (a, [Char])Source
Applies a parser and returns the raw string that was parsed, along with the value produced by the parser.
nullBlock :: GenParser Char st BlockSource
Parses a character and returns Null
(so that the parser can move on
if it gets stuck).
failIfStrict :: GenParser a ParserState ()Source
Fail if reader is in strict markdown syntax mode.
failUnlessLHS :: GenParser tok ParserState ()Source
Fail unless we're in literate haskell mode.
Parses backslash, then applies character parser.
characterReference :: GenParser Char st CharSource
Parse character entity.
updateLastStrPos :: GenParser Char ParserState ()Source
anyOrderedListMarker :: GenParser Char ParserState ListAttributesSource
Parses an ordered list marker and returns list attributes.
orderedListMarker :: ListNumberStyle -> ListNumberDelim -> GenParser Char ParserState IntSource
Parses an ordered list marker with a given style and delimiter, returns number.
tableWith :: GenParser Char ParserState ([[Block]], [Alignment], [Int]) -> ([Int] -> GenParser Char ParserState [[Block]]) -> GenParser Char ParserState sep -> GenParser Char ParserState end -> GenParser Char ParserState [Inline] -> GenParser Char ParserState BlockSource
Parse a table using headerParser
, rowParser
,
lineParser
, and footerParser
.
:: GenParser Char ParserState Block | Block parser |
-> GenParser Char ParserState [Inline] | Caption parser |
-> Bool | Headerless table |
-> GenParser Char ParserState Block |
:: GenParser t ParserState a | parser |
-> ParserState | initial state |
-> [t] | input |
-> a |
Parse a string with a given parser and state.
testStringWith :: Show a => GenParser Char ParserState a -> String -> IO ()Source
Parse a string with parser
(for testing).
data ParserState Source
Parsing options.
ParserState | |
|
Show ParserState |
data HeaderType Source
SingleHeader Char | Single line of characters underneath |
DoubleHeader Char | Lines of characters above and below |
Eq HeaderType | |
Show HeaderType |
data ParserContext Source
ListItemState | Used when running parser on list item contents |
NullState | Default state |
Eq ParserContext | |
Show ParserContext |
data QuoteContext Source
InSingleQuote | Used when parsing inside single quotes |
InDoubleQuote | Used when parsing inside double quotes |
NoQuote | Used when not parsing inside quotes |
Eq QuoteContext | |
Show QuoteContext |
Look up key in key table and return target object.
smartPunctuation :: GenParser Char ParserState Inline -> GenParser Char ParserState InlineSource
macro :: GenParser Char ParserState BlockSource
Parse a newcommand or renewcommand macro definition.
applyMacros' :: String -> GenParser Char ParserState StringSource
Apply current macros to string.