djot-0.1.1.3: Parser and renderer for djot light markup syntax.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Djot.Parse

Synopsis

Documentation

data Parser s a Source #

Instances

Instances details
Alternative (Parser s) Source # 
Instance details

Defined in Djot.Parse

Methods

empty :: Parser s a #

(<|>) :: Parser s a -> Parser s a -> Parser s a #

some :: Parser s a -> Parser s [a] #

many :: Parser s a -> Parser s [a] #

Applicative (Parser s) Source # 
Instance details

Defined in Djot.Parse

Methods

pure :: a -> Parser s a #

(<*>) :: Parser s (a -> b) -> Parser s a -> Parser s b #

liftA2 :: (a -> b -> c) -> Parser s a -> Parser s b -> Parser s c #

(*>) :: Parser s a -> Parser s b -> Parser s b #

(<*) :: Parser s a -> Parser s b -> Parser s a #

Functor (Parser s) Source # 
Instance details

Defined in Djot.Parse

Methods

fmap :: (a -> b) -> Parser s a -> Parser s b #

(<$) :: a -> Parser s b -> Parser s a #

Monad (Parser s) Source # 
Instance details

Defined in Djot.Parse

Methods

(>>=) :: Parser s a -> (a -> Parser s b) -> Parser s b #

(>>) :: Parser s a -> Parser s b -> Parser s b #

return :: a -> Parser s a #

MonadPlus (Parser s) Source # 
Instance details

Defined in Djot.Parse

Methods

mzero :: Parser s a #

mplus :: Parser s a -> Parser s a -> Parser s a #

data Chunk Source #

Constructors

Chunk 

Instances

Instances details
Show Chunk Source # 
Instance details

Defined in Djot.Parse

Methods

showsPrec :: Int -> Chunk -> ShowS #

show :: Chunk -> String #

showList :: [Chunk] -> ShowS #

Eq Chunk Source # 
Instance details

Defined in Djot.Parse

Methods

(==) :: Chunk -> Chunk -> Bool #

(/=) :: Chunk -> Chunk -> Bool #

Ord Chunk Source # 
Instance details

Defined in Djot.Parse

Methods

compare :: Chunk -> Chunk -> Ordering #

(<) :: Chunk -> Chunk -> Bool #

(<=) :: Chunk -> Chunk -> Bool #

(>) :: Chunk -> Chunk -> Bool #

(>=) :: Chunk -> Chunk -> Bool #

max :: Chunk -> Chunk -> Chunk #

min :: Chunk -> Chunk -> 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.

asciiChar :: Char -> Parser s () Source #

Parse an ASCII character.

satisfyByte :: (Char -> Bool) -> Parser s Char Source #

Parse a byte satisfying a predicate.

skipSatisfyByte :: (Char -> Bool) -> Parser s () Source #

Skip byte satisfying a predicate.

satisfy :: (Char -> Bool) -> Parser s Char Source #

Parse a (possibly multibyte) Char satisfying a predicate. Assumes UTF-8 encoding.

anyChar :: Parser s Char Source #

Parse any character. Assumes UTF-8 encoding.

skipMany :: Parser s a -> Parser s () Source #

Apply parser 0 or more times, discarding result.

skipSome :: Parser s a -> Parser s () Source #

Apply parser 1 or more times, discarding result.

eof :: Parser s () Source #

Succeeds if no more input.

getState :: Parser s s Source #

Returns current user state.

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.

peek :: Parser s (Maybe Char) Source #

Returns current byte as Char.

peekBack :: Parser s (Maybe Char) Source #

Returns previous byte as Char. Doesn't cross chunk boundaries.

fails :: Parser s a -> Parser s () Source #

Succeeds if parser fails.

failed :: Parser s a Source #

Always fails.

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.

getOffset :: Parser s Int Source #

Returns byte offset in input.

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.

endline :: Parser s () Source #

Parse an end of line sequence.

restOfLine :: Parser s ByteString Source #

Return the rest of line (including the end of line).

ws :: Parser s () Source #

Skip 1 or more ASCII whitespace.

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.

isWs :: Char -> Bool Source #

Is space, tab, `r`, or `n`.