parsley-core-1.4.0.0: A fast parser combinator library backed by Typed Template Haskell
LicenseBSD-3-Clause
MaintainerJamie Willis
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010
Extensions
  • 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 Rep 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 Bool Source #

Is the first argument is less than the second?

Since: 1.0.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

offWith :: Code ts -> Code (OffWith ts) Source #

Initialises an OffWith type, with a starting offset of 0.

Since: 1.0.0.0

offWithSame :: Code (OffWith ts) -> Code (OffWith ts) -> Code Bool Source #

Compares the bundled offsets of two OffWiths are equal: does not need to inspect the corresponding input.

Since: 1.0.0.0

offWithShiftRight Source #

Arguments

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

A drop function for underlying input.

-> Code (OffWith ts)

The OffWith to shift.

-> Code Int#

How much to shift by.

-> Code (OffWith 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

Stream Operations

data Stream Source #

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

Since: 0.1.0.0

Instances

Instances details
InputPrep Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

prepare :: forall (rep :: TYPE (RepKind Stream)). rep ~ Rep Stream => Code Stream -> Code (InputDependant rep) 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

Methods

bindIterHandler# :: (Code (Rep Stream) -> StaHandler# s Stream a) -> (Code (Rep Stream -> Handler# s Stream a) -> Code b) -> Code b Source #

bindIter# :: Code (Rep Stream) -> (DynHandler s Stream a -> Code (Rep Stream) -> Code (ST s (Maybe a))) -> Code (ST s (Maybe a)) Source #

bindRec# :: (DynSubroutine s Stream a x -> DynCont s Stream a x -> Code (Rep Stream) -> DynHandler s Stream a -> Code (ST s (Maybe a))) -> DynSubroutine s Stream a x 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 #

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 #

Input Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

PositionOps (# Int#, Stream #) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

same :: Code (# Int#, Stream #) -> Code (# Int#, Stream #) -> Code Bool Source #

shiftRight :: Code (# Int#, Stream #) -> Code Int# -> Code (# Int#, Stream #) Source #

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

Drops tokens off of a Stream.

Since: 1.0.0.0

Text Operations

offsetText :: Code Text -> Code Int Source #

Extracts the offset from Text.

Since: 1.0.0.0

Crucial Exposed Functions

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

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

Drops tokens off of Text.

Since: 1.0.0.0

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

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

Since: 1.0.0.0

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

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

Since: 1.0.0.0