parsley-core-2.3.0.0: A fast parser combinator library backed by Typed Template Haskell
LicenseBSD-3-Clause
MaintainerJamie Willis
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010
Extensions
  • Cpp
  • MonoLocalBinds
  • TemplateHaskell
  • TemplateHaskellQuotes
  • ScopedTypeVariables
  • UnboxedTuples
  • BangPatterns
  • TypeFamilies
  • GADTs
  • GADTSyntax
  • PolyKinds
  • DataKinds
  • TypeSynonymInstances
  • FlexibleContexts
  • FlexibleInstances
  • MagicHash
  • KindSignatures
  • RankNTypes
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • StandaloneKindSignatures

Parsley.Internal.Backend.Machine.InputRep

Description

This module contains the translation from user input type to the underlying parsley representation of it, as well as some miscellaneous functions for working with specific types of input (these do not appear in the rest of the machinery, but in Parsley.Internal.Backend.Machine.InputOps and potentially the generated code).

Since: 1.0.0.0

Synopsis

Representation Type-Families

type family DynRep input where ... Source #

This type family relates a user input type with the underlying parsley representation, which is significantly more efficient to work with. Most parts of the machine work with Rep.

Since: 1.0.0.0

type family RepKind input where ... Source #

The representation type of an input Rep, does not have to be a lifted type. To match a representation of an input with the correct kind, this type family must be used.

Since: 1.0.0.0

Int# Operations

intSame :: Code Int# -> Code Int# -> Code Bool Source #

Verifies that two Int#s are equal.

Since: 1.0.0.0

intLess :: Code Int# -> Code Int# -> Code a -> Code a -> Code a Source #

Is the first argument is less than the second?

Since: 2.3.0.0

min# :: Int# -> Int# -> Int# Source #

Finds the minimum of two Int# values.

Since: 1.0.0.0

max# :: Int# -> Int# -> Int# Source #

Finds the maximum of two Int# values.

Since: 1.0.0.0

Offwith Operations

type OffWith ts = (# Int#, ts #) Source #

This allows types like String and Stream to be manipulated more efficiently by packaging them along with an offset which can be used for quicker comparisons.

Since: 1.0.0.0

offWithShiftRight Source #

Arguments

:: Code (Int -> ts -> ts)

A drop function for underlying input.

-> PartialStaOffset 
-> Code ts

The OffWith to shift.

-> Int

How much to shift by.

-> (PartialStaOffset, Code ts) 

Shifts an OffWith to the right, taking care to also drop tokens from the companion input.

Since: 1.0.0.0

LazyByteString Operations

type UnpackedLazyByteString = (# Int#, Addr#, ForeignPtrContents, Int#, Int#, ByteString #) Source #

This type unpacks lazy ByteStrings for efficiency.

Since: 1.0.0.0

emptyUnpackedLazyByteString :: Code Int# -> Code UnpackedLazyByteString Source #

Initialises an UnpackedLazyByteString with a specified offset. This offset varies as each lazy chunk is consumed.

Since: 1.0.0.0

byteStringShiftLeft :: Code UnpackedLazyByteString -> Int# -> Code UnpackedLazyByteString Source #

Rewinds input consumption on a lazy ByteString if input is still available (within the same chunk).

Since: 2.3.0.0

Stream Operations

dropStream :: Int -> Stream -> Stream Source #

Drops tokens off of a Stream.

Since: 1.0.0.0

Text Operations

data StaText Source #

Constructors

StaText 

Fields

offsetText :: PartialStaText -> Code Int Source #

Extracts the offset from Text.

Since: 1.0.0.0

textShiftRight :: Code Text -> Int# -> Code Text Source #

Drops tokens off of Text.

Since: 2.3.0.0

textShiftLeft :: Code Text -> Int# -> Code Text Source #

Rewinds input consumption on Text where the input is still available (i.e. in the same chunk).

Since: 2.3.0.0

Crucial Exposed Functions

These functions must be exposed, since they can appear in the generated code.

Re-exports

data Stream Source #

An input type that represents an infinite stream of input characters.

Since: 0.1.0.0

Constructors

!Char :> Stream 

Instances

Instances details
Input Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

HandlerOps Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

Methods

bindHandler# :: StaHandler# s Stream a -> (DynHandler s Stream a -> Code b) -> Code b Source #

JoinBuilder Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

Methods

setupJoinPoint# :: StaCont# s Stream a x -> (DynCont s Stream a x -> Code b) -> Code b Source #

MarshalOps Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

RecBuilder Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

InputPrep Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

_prepare :: starep ~ StaRep Stream => Code Stream -> (InputOps starep -> starep -> Code r) -> Code r

LogOps (PartialStaOffWith Stream) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

newtype CharList Source #

Deprecated: CharList is no longer necessary, use String directly instead

By wrapping a regular String with this newtype, Parsley will not preprocess it into an array of characters, instead using regular pattern matching for the implementation.

Since: 0.1.0.0

Constructors

CharList String

Deprecated: CharList is no longer necessary, use String directly instead

Instances

Instances details
Input CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

HandlerOps CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

JoinBuilder CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

Methods

setupJoinPoint# :: StaCont# s CharList a x -> (DynCont s CharList a x -> Code b) -> Code b Source #

MarshalOps CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

RecBuilder CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.BindingOps

InputPrep CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

_prepare :: starep ~ StaRep CharList => Code CharList -> (InputOps starep -> starep -> Code r) -> Code r

newtype Text16 Source #

Deprecated: Text16 is not legal with the UTF-8 encoding of Text, use Text instead

By wrapping a regular Text input with this newtype, Parsley will assume that all of the characters fit into exactly one 16-bit chunk. This allows the consumption of characters in the datatype to be consumed much faster, but does not support multi-word characters.

Since: 0.1.0.0

Constructors

Text16 Text

Deprecated: Text16 is not legal with the UTF-8 encoding of Text, use Text instead