| Copyright | Bryan O'Sullivan 2007-2015 | 
|---|---|
| License | BSD3 | 
| Maintainer | bos@serpentine.com | 
| Stability | experimental | 
| Portability | unknown | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Data.Attoparsec.Internal.Types
Description
Simple, efficient parser combinators, loosely based on the Parsec library.
Synopsis
- newtype Parser i a = Parser {}
- type family State i
- type Failure i t r = t -> Pos -> More -> [String] -> String -> IResult i r
- type Success i t a r = t -> Pos -> More -> a -> IResult i r
- newtype Pos = Pos {}
- data IResult i r
- data More
- (<>) :: Semigroup a => a -> a -> a
- class Monoid c => Chunk c where- type ChunkElem c
- nullChunk :: c -> Bool
- pappendChunk :: State c -> c -> State c
- atBufferEnd :: c -> State c -> Pos
- bufferElemAt :: c -> Pos -> State c -> Maybe (ChunkElem c, Int)
- chunkElemToChar :: c -> ChunkElem c -> Char
 
Documentation
The core parser type.  This is parameterised over the type i
 of string being processed.
This type is an instance of the following classes:
- Monad, where- failthrows an exception (i.e. fails) with an error message.
- Functorand- Applicative, which follow the usual definitions.
- MonadPlus, where- mzerofails (with no error message) and- mplusexecutes the right-hand parser if the left-hand one fails. When the parser on the right executes, the input is reset to the same state as the parser on the left started with. (In other words, attoparsec is a backtracking parser that supports arbitrary lookahead.)
- Alternative, which follows- MonadPlus.
Constructors
| Parser | |
Instances
| Monad (Parser i) Source # | |
| Functor (Parser i) Source # | |
| MonadFail (Parser i) Source # | |
| Defined in Data.Attoparsec.Internal.Types | |
| a ~ Text => IsString (Parser a) Source # | |
| Defined in Data.Attoparsec.Text.Internal Methods fromString :: String -> Parser a # | |
| a ~ ByteString => IsString (Parser a) Source # | |
| Defined in Data.Attoparsec.ByteString.Char8 Methods fromString :: String -> Parser a # | |
| Applicative (Parser i) Source # | |
| Alternative (Parser i) Source # | |
| MonadPlus (Parser i) Source # | |
| Semigroup (Parser i a) Source # | |
| Monoid (Parser i a) Source # | |
Instances
| type State ByteString Source # | |
| Defined in Data.Attoparsec.Internal.Types | |
| type State Text Source # | |
| Defined in Data.Attoparsec.Internal.Types | |
The result of a parse.  This is parameterised over the type i
 of string that was processed.
This type is an instance of Functor, where fmap transforms the
 value in a Done result.
Constructors
| Fail i [String] String | The parse failed.  The  | 
| Partial (i -> IResult i r) | Supply this continuation with more input so that the parser can resume. To indicate that no more input is available, pass an empty string to the continuation. Note: if you get a  | 
| Done i r | The parse succeeded.  The  | 
Have we read all available input?
Constructors
| Complete | |
| Incomplete | 
(<>) :: Semigroup a => a -> a -> a infixr 6 #
An associative operation.
>>>[1,2,3] <> [4,5,6][1,2,3,4,5,6]
class Monoid c => Chunk c where Source #
A common interface for input chunks.
Methods
nullChunk :: c -> Bool Source #
Test if the chunk is empty.
pappendChunk :: State c -> c -> State c Source #
Append chunk to a buffer.
atBufferEnd :: c -> State c -> Pos Source #
Position at the end of a buffer. The first argument is ignored.
bufferElemAt :: c -> Pos -> State c -> Maybe (ChunkElem c, Int) Source #
Return the buffer element at the given position along with its length.
chunkElemToChar :: c -> ChunkElem c -> Char Source #
Map an element to the corresponding character. The first argument is ignored.
Instances
| Chunk ByteString Source # | |
| Defined in Data.Attoparsec.Internal.Types Associated Types type ChunkElem ByteString Source # Methods nullChunk :: ByteString -> Bool Source # pappendChunk :: State ByteString -> ByteString -> State ByteString Source # atBufferEnd :: ByteString -> State ByteString -> Pos Source # bufferElemAt :: ByteString -> Pos -> State ByteString -> Maybe (ChunkElem ByteString, Int) Source # chunkElemToChar :: ByteString -> ChunkElem ByteString -> Char Source # | |
| Chunk Text Source # | |
| Defined in Data.Attoparsec.Internal.Types | |