Copyright | Bryan O'Sullivan 2007-2015 |
---|---|
License | BSD3 |
Maintainer | bos@serpentine.com |
Stability | experimental |
Portability | unknown |
Safe Haskell | None |
Language | GHC2024 |
Data.Attoparsec.Internal
Description
Simple, efficient parser combinators, loosely based on the Parsec library.
Synopsis
- compareResults :: (Eq i, Eq r) => IResult i r -> IResult i r -> Maybe Bool
- class (DirectedPlus d, Chunk c, Show (DirState d c)) => DirChunk (d :: Dir) c
- prompt :: forall t (d :: Dir) r. (Show t, DirChunk d t) => DirState d t -> DirPos d -> More -> (DirState d t -> DirPos d -> More -> IResult t r) -> (DirState d t -> DirPos d -> More -> IResult t r) -> IResult t r
- demandInput :: forall t (d :: Dir). (Show t, DirChunk d t) => DirParser d t ()
- demandInput_ :: forall (d :: Dir) t. DirChunk d t => DirParser d t t
- wantInput :: forall t (d :: Dir). (Show t, DirChunk d t) => DirParser d t Bool
- endOfInput :: forall t (d :: Dir). (Show t, DirChunk d t) => DirParser d t ()
- atEnd :: forall t (d :: Dir). (Show t, DirChunk d t) => DirParser d t Bool
- satisfyElem :: forall t (d :: Dir). (Show t, DirChunk d t) => (DirChunkElem d t -> Bool) -> DirParser d t (DirChunkElem d t)
- concatReverse :: DirChunk d c => [Tagged d c] -> Tagged d c
Documentation
class (DirectedPlus d, Chunk c, Show (DirState d c)) => DirChunk (d :: Dir) c Source #
Minimal complete definition
notAtBufferEnd, bufferElemAt, shiftPositionOnBufferExtend, pappendChunk, concatReverse
Instances
prompt :: forall t (d :: Dir) r. (Show t, DirChunk d t) => DirState d t -> DirPos d -> More -> (DirState d t -> DirPos d -> More -> IResult t r) -> (DirState d t -> DirPos d -> More -> IResult t r) -> IResult t r Source #
Ask for input. If we receive any, pass the augmented input to a success continuation, otherwise to a failure continuation.
demandInput :: forall t (d :: Dir). (Show t, DirChunk d t) => DirParser d t () Source #
Immediately demand more input via a Partial
continuation
result.
demandInput_ :: forall (d :: Dir) t. DirChunk d t => DirParser d t t Source #
Immediately demand more input via a Partial
continuation
result. Return the new input.
endOfInput :: forall t (d :: Dir). (Show t, DirChunk d t) => DirParser d t () Source #
Match only if all input has been consumed.
atEnd :: forall t (d :: Dir). (Show t, DirChunk d t) => DirParser d t Bool Source #
Return an indication of whether the end of input has been reached.
satisfyElem :: forall t (d :: Dir). (Show t, DirChunk d t) => (DirChunkElem d t -> Bool) -> DirParser d t (DirChunkElem d t) Source #
The parser satisfyElem p
succeeds for any chunk element for which the
predicate p
returns True
. Returns the element that is
actually parsed.