Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Parser s a
- data Chunk = Chunk {
- chunkLine :: Int
- chunkColumn :: Int
- chunkBytes :: ByteString
- parse :: Parser s a -> s -> [Chunk] -> Maybe a
- asciiChar :: Char -> Parser s ()
- satisfyByte :: (Char -> Bool) -> Parser s Char
- skipSatisfyByte :: (Char -> Bool) -> Parser s ()
- satisfy :: (Char -> Bool) -> Parser s Char
- anyChar :: Parser s Char
- skipMany :: Parser s a -> Parser s ()
- skipSome :: Parser s a -> Parser s ()
- eof :: Parser s ()
- getState :: Parser s s
- updateState :: (s -> s) -> Parser s ()
- lookahead :: Parser s a -> Parser s a
- peek :: Parser s (Maybe Char)
- peekBack :: Parser s (Maybe Char)
- fails :: Parser s a -> Parser s ()
- failed :: Parser s a
- withByteString :: Parser s a -> Parser s (a, ByteString)
- byteStringOf :: Parser s a -> Parser s ByteString
- notFollowedBy :: Parser s a -> Parser s b -> Parser s a
- optional_ :: Parser s a -> Parser s ()
- byteString :: ByteString -> Parser s ()
- getOffset :: Parser s Int
- sourceLine :: Parser s Int
- sourceColumn :: Parser st Int
- branch :: Parser s b -> Parser s a -> Parser s a -> Parser s a
- endline :: Parser s ()
- restOfLine :: Parser s ByteString
- ws :: Parser s ()
- followedByWhitespace :: Parser s ()
- followedByBlankLine :: Parser s ()
- spaceOrTab :: Parser s ()
- isWs :: Char -> Bool
- strToUtf8 :: String -> ByteString
- utf8ToStr :: ByteString -> String
Documentation
Chunk | |
|
parse :: Parser s a -> s -> [Chunk] -> Maybe a Source #
Apply a parser to a bytestring with a given user state.
Returns Nothing
on failure, Just result
on success.
satisfy :: (Char -> Bool) -> Parser s Char Source #
Parse a (possibly multibyte) Char satisfying a predicate. Assumes UTF-8 encoding.
updateState :: (s -> s) -> Parser s () Source #
Updates user state.
lookahead :: Parser s a -> Parser s a Source #
Apply a parser, returning its result but not changing state or advancing.
peekBack :: Parser s (Maybe Char) Source #
Returns previous byte as Char. Doesn't cross chunk boundaries.
withByteString :: Parser s a -> Parser s (a, ByteString) Source #
Returns result of parse together with the bytestring consumed.
byteStringOf :: Parser s a -> Parser s ByteString Source #
Returns bytestring consumed by parse.
notFollowedBy :: Parser s a -> Parser s b -> Parser s a Source #
Succeeds if first parser succeeds and second fails, returning first parser's value.
optional_ :: Parser s a -> Parser s () Source #
Apply parser but still succeed if it doesn't succeed.
byteString :: ByteString -> Parser s () Source #
Parse a bytestring.
sourceLine :: Parser s Int Source #
Returns the line number.
sourceColumn :: Parser st Int Source #
Returns the source column number. (Tab stop is computed at 4.)
branch :: Parser s b -> Parser s a -> Parser s a -> Parser s a Source #
Try the first parser: if it succeeds, apply the second, returning its result, otherwise the third.
restOfLine :: Parser s ByteString Source #
Return the rest of line (including the end of line).
followedByWhitespace :: Parser s () Source #
Next character is ASCII whitespace.
followedByBlankLine :: Parser s () Source #
Followed by 0 or more spaces/tabs and endline or eof.
spaceOrTab :: Parser s () Source #
Skip one space or tab.
strToUtf8 :: String -> ByteString Source #
utf8ToStr :: ByteString -> String Source #