parsley-0.1.1.0: A fast parser combinator library backed by Typed Template Haskell
Safe HaskellNone
LanguageHaskell2010

Parsley.Internal.Core.InputTypes

Synopsis

Documentation

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
PositionOps Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

same :: forall (rep :: TYPE (RepKind Stream)). rep ~ Rep Stream => Proxy Stream -> Code rep -> Code rep -> Code Bool Source #

shiftRight :: forall (rep :: TYPE (RepKind Stream)). rep ~ Rep Stream => Proxy Stream -> Code rep -> Code Int# -> Code rep Source #

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 #

LogHandler Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Ops

Methods

logHandler :: forall s a (xs :: [Type]) (n :: Nat) ks. (?ops :: InputOps (Rep Stream)) => String -> Ctx s Stream a -> Γ s Stream xs ('Succ n) ks a -> Code (Rep Stream) -> Code (Handler s Stream a) Source #

RecBuilder Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Ops

Methods

buildIter :: ReturnOps Stream => Ctx s Stream a -> MVar Void -> Machine s Stream '[] One Void a -> (Code (Rep Stream) -> Code (Handler s Stream a)) -> Code (Rep Stream) -> Code (ST s (Maybe a)) Source #

buildRec :: forall (rs :: [Type]) s a r. Regs rs -> Ctx s Stream a -> Machine s Stream '[] One r a -> Code (Func rs s Stream a r) Source #

JoinBuilder Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Ops

Methods

setupJoinPoint :: forall x s (xs :: [Type]) (n :: Nat) r a. ΦVar x -> Machine s Stream (x ': xs) n r a -> Machine s Stream xs n r a -> MachineMonad s Stream xs n r a Source #

ReturnOps Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Ops

ContOps Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Ops

Methods

suspend :: forall s x (xs :: [Type]) (n :: Nat) r a. (Γ s Stream (x ': xs) n r a -> Code (ST s (Maybe a))) -> Γ s Stream xs n r a -> Code (Cont s Stream a x) Source #

HandlerOps Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Ops

Methods

buildHandler :: forall s (xs :: [Type]) (n :: Nat) r a. Γ s Stream xs n r a -> (Γ s Stream (Stream ': xs) n r a -> Code (ST s (Maybe a))) -> Code (Rep Stream) -> Code (Handler s Stream a) Source #

fatal :: Code (Handler s Stream a) Source #

Input Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

newtype CharList Source #

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 

Instances

Instances details
PositionOps CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

same :: forall (rep :: TYPE (RepKind CharList)). rep ~ Rep CharList => Proxy CharList -> Code rep -> Code rep -> Code Bool Source #

shiftRight :: forall (rep :: TYPE (RepKind CharList)). rep ~ Rep CharList => Proxy CharList -> Code rep -> Code Int# -> Code rep Source #

InputPrep CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

prepare :: forall (rep :: TYPE (RepKind CharList)). rep ~ Rep CharList => Code CharList -> Code (InputDependant rep) Source #

LogHandler CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Ops

Methods

logHandler :: forall s a (xs :: [Type]) (n :: Nat) ks. (?ops :: InputOps (Rep CharList)) => String -> Ctx s CharList a -> Γ s CharList xs ('Succ n) ks a -> Code (Rep CharList) -> Code (Handler s CharList a) Source #

RecBuilder CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Ops

Methods

buildIter :: ReturnOps CharList => Ctx s CharList a -> MVar Void -> Machine s CharList '[] One Void a -> (Code (Rep CharList) -> Code (Handler s CharList a)) -> Code (Rep CharList) -> Code (ST s (Maybe a)) Source #

buildRec :: forall (rs :: [Type]) s a r. Regs rs -> Ctx s CharList a -> Machine s CharList '[] One r a -> Code (Func rs s CharList a r) Source #

JoinBuilder CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Ops

Methods

setupJoinPoint :: forall x s (xs :: [Type]) (n :: Nat) r a. ΦVar x -> Machine s CharList (x ': xs) n r a -> Machine s CharList xs n r a -> MachineMonad s CharList xs n r a Source #

ReturnOps CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Ops

ContOps CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Ops

Methods

suspend :: forall s x (xs :: [Type]) (n :: Nat) r a. (Γ s CharList (x ': xs) n r a -> Code (ST s (Maybe a))) -> Γ s CharList xs n r a -> Code (Cont s CharList a x) Source #

HandlerOps CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Ops

Methods

buildHandler :: forall s (xs :: [Type]) (n :: Nat) r a. Γ s CharList xs n r a -> (Γ s CharList (CharList ': xs) n r a -> Code (ST s (Maybe a))) -> Code (Rep CharList) -> Code (Handler s CharList a) Source #

fatal :: Code (Handler s CharList a) Source #

Input CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

newtype Text16 Source #

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 

Instances

Instances details
PositionOps Text16 Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

same :: forall (rep :: TYPE (RepKind Text16)). rep ~ Rep Text16 => Proxy Text16 -> Code rep -> Code rep -> Code Bool Source #

shiftRight :: forall (rep :: TYPE (RepKind Text16)). rep ~ Rep Text16 => Proxy Text16 -> Code rep -> Code Int# -> Code rep Source #

InputPrep Text16 Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.InputOps

Methods

prepare :: forall (rep :: TYPE (RepKind Text16)). rep ~ Rep Text16 => Code Text16 -> Code (InputDependant rep) Source #

LogHandler Text16 Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Ops

Methods

logHandler :: forall s a (xs :: [Type]) (n :: Nat) ks. (?ops :: InputOps (Rep Text16)) => String -> Ctx s Text16 a -> Γ s Text16 xs ('Succ n) ks a -> Code (Rep Text16) -> Code (Handler s Text16 a) Source #

RecBuilder Text16 Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Ops

Methods

buildIter :: ReturnOps Text16 => Ctx s Text16 a -> MVar Void -> Machine s Text16 '[] One Void a -> (Code (Rep Text16) -> Code (Handler s Text16 a)) -> Code (Rep Text16) -> Code (ST s (Maybe a)) Source #

buildRec :: forall (rs :: [Type]) s a r. Regs rs -> Ctx s Text16 a -> Machine s Text16 '[] One r a -> Code (Func rs s Text16 a r) Source #

JoinBuilder Text16 Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Ops

Methods

setupJoinPoint :: forall x s (xs :: [Type]) (n :: Nat) r a. ΦVar x -> Machine s Text16 (x ': xs) n r a -> Machine s Text16 xs n r a -> MachineMonad s Text16 xs n r a Source #

ReturnOps Text16 Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Ops

ContOps Text16 Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Ops

Methods

suspend :: forall s x (xs :: [Type]) (n :: Nat) r a. (Γ s Text16 (x ': xs) n r a -> Code (ST s (Maybe a))) -> Γ s Text16 xs n r a -> Code (Cont s Text16 a x) Source #

HandlerOps Text16 Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Ops

Methods

buildHandler :: forall s (xs :: [Type]) (n :: Nat) r a. Γ s Text16 xs n r a -> (Γ s Text16 (Text16 ': xs) n r a -> Code (ST s (Maybe a))) -> Code (Rep Text16) -> Code (Handler s Text16 a) Source #

fatal :: Code (Handler s Text16 a) Source #

Input Text16 Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

nomore :: Stream Source #

The "end" of a stream, an infinite stream of '\0' (null) characters

Since: 0.1.0.0