attoparsec-isotropic
CopyrightBryan O'Sullivan 2007-2015
LicenseBSD3
Maintainerbos@serpentine.com
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageGHC2024

Data.Attoparsec.Internal.Types

Description

Simple, efficient parser combinators, loosely based on the Parsec library.

Synopsis

Documentation

newtype DirParser (d :: Dir) i a Source #

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 fail throws an exception (i.e. fails) with an error message.
  • Functor and Applicative, which follow the usual definitions.
  • MonadPlus, where mzero fails (with no error message) and mplus executes 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 

Fields

Instances

Instances details
a ~ Text => IsString (Parser a) Source # 
Instance details

Defined in Data.Attoparsec.Text.Internal

Methods

fromString :: String -> Parser a #

Alternative (DirParser 'Backward ByteString) Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Alternative (DirParser 'Forward i) Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Applicative (DirParser d i) Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

pure :: a -> DirParser d i a #

(<*>) :: DirParser d i (a -> b) -> DirParser d i a -> DirParser d i b #

liftA2 :: (a -> b -> c) -> DirParser d i a -> DirParser d i b -> DirParser d i c #

(*>) :: DirParser d i a -> DirParser d i b -> DirParser d i b #

(<*) :: DirParser d i a -> DirParser d i b -> DirParser d i a #

Functor (DirParser d i) Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

fmap :: (a -> b) -> DirParser d i a -> DirParser d i b #

(<$) :: a -> DirParser d i b -> DirParser d i a #

Monad (DirParser d i) Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

(>>=) :: DirParser d i a -> (a -> DirParser d i b) -> DirParser d i b #

(>>) :: DirParser d i a -> DirParser d i b -> DirParser d i b #

return :: a -> DirParser d i a #

MonadPlus (DirParser 'Backward ByteString) Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

MonadPlus (DirParser 'Forward i) Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

MonadFail (DirParser d i) Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

fail :: String -> DirParser d i a #

(Directed d, a ~ ByteString) => IsString (DirParser d a) Source # 
Instance details

Defined in Data.Attoparsec.ByteString.Char8

Methods

fromString :: String -> DirParser d a #

Monoid (DirParser 'Forward i a) Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Semigroup (DirParser 'Forward i a) Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

type family DirState (d :: Dir) i Source #

Instances

Instances details
type DirState 'Backward ByteString Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

type DirState 'Forward ByteString Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

type DirState 'Forward ByteString = Buffer
type DirState 'Forward Text Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

type DirState 'Forward Text = Buffer

type Failure i t r = DirFailure 'Forward i t r Source #

type Success i t a r = DirSuccess 'Forward i t a r Source #

type DirFailure (d :: Dir) i t r = t -> DirPos d -> More -> [String] -> String -> IResult i r Source #

type DirSuccess (d :: Dir) i t a r = t -> DirPos d -> More -> a -> IResult i r Source #

data IResult i r Source #

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 i parameter is the input that had not yet been consumed when the failure occurred. The [String] is a list of contexts in which the error occurred. The String is the message describing the error, if any.

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 Partial result, do not call its continuation more than once.

Done i r

The parse succeeded. The i parameter is the input that had not yet been consumed (if any) when the parse succeeded.

Instances

Instances details
Functor (IResult i) Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

fmap :: (a -> b) -> IResult i a -> IResult i b #

(<$) :: a -> IResult i b -> IResult i a #

(NFData i, NFData r) => NFData (IResult i r) Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

rnf :: IResult i r -> () #

(Show i, Show r) => Show (IResult i r) Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

showsPrec :: Int -> IResult i r -> ShowS #

show :: IResult i r -> String #

showList :: [IResult i r] -> ShowS #

data More Source #

Have we read all available input?

Constructors

Complete 
Incomplete 

Instances

Instances details
Monoid More Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

mempty :: More #

mappend :: More -> More -> More #

mconcat :: [More] -> More #

Semigroup More Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

(<>) :: More -> More -> More #

sconcat :: NonEmpty More -> More #

stimes :: Integral b => b -> More -> More #

Show More Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

showsPrec :: Int -> More -> ShowS #

show :: More -> String #

showList :: [More] -> ShowS #

Eq More Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

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

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

(<>) :: Semigroup a => a -> a -> a infixr 6 #

An associative operation.

Examples

Expand
>>> [1,2,3] <> [4,5,6]
[1,2,3,4,5,6]
>>> Just [1, 2, 3] <> Just [4, 5, 6]
Just [1,2,3,4,5,6]
>>> putStr "Hello, " <> putStrLn "World!"
Hello, World!

class Monoid c => Chunk c where Source #

A common interface for input chunks.

Associated Types

type ChunkElem c Source #

Methods

nullChunk :: c -> Bool Source #

Test if the chunk is empty.

chunkElemToChar :: c -> ChunkElem c -> Char Source #

Map an element to the corresponding character. The first argument is ignored.

Instances

Instances details
Chunk ByteString Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type ChunkElem ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

Chunk Text Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type ChunkElem Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

class (DirectedPlus d, Chunk c, Show (DirState d c)) => DirChunk (d :: Dir) c where Source #

Associated Types

type DirChunkElem (d :: Dir) c Source #

Methods

notAtBufferEnd :: c -> DirPos d -> DirState d c -> Bool Source #

Position at the end of a buffer. The first argument is ignored.

bufferElemAt :: c -> DirPos d -> DirState d c -> Maybe (DirChunkElem d c, Int) Source #

Return the buffer element at the given position along with its length.

shiftPositionOnBufferExtend :: DirPos d -> c -> DirPos d Source #

pappendChunk :: DirState d c -> Tagged d c -> DirState d c Source #

Append chunk to a buffer.

concatReverse :: [Tagged d c] -> Tagged d c Source #

Instances

Instances details
DirChunk 'Backward ByteString Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type DirChunkElem 'Backward ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

DirChunk 'Forward ByteString Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type DirChunkElem 'Forward ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

DirChunk 'Forward Text Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type DirChunkElem 'Forward Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

data Dir #

Constructors

Forward 
Backward 

Instances

Instances details
Show Dir # 
Instance details

Defined in Data.Attoparsec.ByteString.Buffer

Methods

showsPrec :: Int -> Dir -> ShowS #

show :: Dir -> String #

showList :: [Dir] -> ShowS #

Eq Dir # 
Instance details

Defined in Data.Attoparsec.ByteString.Buffer

Methods

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

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

newtype DirPos (d :: Dir) Source #

Constructors

Pos 

Fields

Instances

Instances details
Num (DirPos d) Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

(+) :: DirPos d -> DirPos d -> DirPos d #

(-) :: DirPos d -> DirPos d -> DirPos d #

(*) :: DirPos d -> DirPos d -> DirPos d #

negate :: DirPos d -> DirPos d #

abs :: DirPos d -> DirPos d #

signum :: DirPos d -> DirPos d #

fromInteger :: Integer -> DirPos d #

Show (DirPos d) Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

showsPrec :: Int -> DirPos d -> ShowS #

show :: DirPos d -> String #

showList :: [DirPos d] -> ShowS #

Eq (DirPos d) Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

(==) :: DirPos d -> DirPos d -> Bool #

(/=) :: DirPos d -> DirPos d -> Bool #

Ord (DirPos d) Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

compare :: DirPos d -> DirPos d -> Ordering #

(<) :: DirPos d -> DirPos d -> Bool #

(<=) :: DirPos d -> DirPos d -> Bool #

(>) :: DirPos d -> DirPos d -> Bool #

(>=) :: DirPos d -> DirPos d -> Bool #

max :: DirPos d -> DirPos d -> DirPos d #

min :: DirPos d -> DirPos d -> DirPos d #

class DirectedPlus (d :: Dir) where Source #

Methods

there :: DirPos d -> DirPos d Source #

Instances

Instances details
DirectedPlus 'Backward Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types

DirectedPlus 'Forward Source # 
Instance details

Defined in Data.Attoparsec.Internal.Types