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

Parsley.Internal.Common.Indexed

Documentation

newtype Const4 a i j k l Source #

Constructors

Const4 

Fields

data Unit4 i j k l Source #

Constructors

Unit4 

newtype Const1 a k Source #

Constructors

Const1 

Fields

data Unit1 k Source #

Constructors

Unit 

class Chain r k where Source #

Methods

(|>) :: (a -> Maybe r) -> (a -> k) -> a -> k Source #

Instances

Instances details
Chain a a Source # 
Instance details

Defined in Parsley.Internal.Common.Indexed

Methods

(|>) :: (a0 -> Maybe a) -> (a0 -> a) -> a0 -> a Source #

Chain a (Maybe a) Source # 
Instance details

Defined in Parsley.Internal.Common.Indexed

Methods

(|>) :: (a0 -> Maybe a) -> (a0 -> Maybe a) -> a0 -> Maybe a Source #

data (f :*: g) i Source #

Constructors

(f i) :*: (g i) 

data Cofree f a i Source #

Constructors

(a i) :< (f (Cofree f a) i) 

Instances

Instances details
IFunctor f => IFunctor (Cofree f) Source # 
Instance details

Defined in Parsley.Internal.Common.Indexed

Methods

imap :: (forall j. a j -> b j) -> Cofree f a i -> Cofree f b i Source #

data (f :+: g) k a where Source #

Constructors

L :: f k a -> (f :+: g) k a 
R :: g k a -> (f :+: g) k a 

Instances

Instances details
(IFunctor f, IFunctor g) => IFunctor (f :+: g) Source # 
Instance details

Defined in Parsley.Internal.Common.Indexed

Methods

imap :: (forall j. a j -> b j) -> (f :+: g) a i -> (f :+: g) b i Source #

newtype Fix4 f i j k l Source #

Constructors

In4 (f (Fix4 f) i j k l) 

Instances

Instances details
Show (Fix4 (Instr o) xs n r a) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Instructions

Methods

showsPrec :: Int -> Fix4 (Instr o) xs n r a -> ShowS #

show :: Fix4 (Instr o) xs n r a -> String #

showList :: [Fix4 (Instr o) xs n r a] -> ShowS #

newtype Fix f a Source #

Constructors

In (f (Fix f) a) 

Instances

Instances details
Show (Fix Combinator a) Source # 
Instance details

Defined in Parsley.Internal.Core.CombinatorAST

class IFunctor4 (f :: ([Type] -> Nat -> Type -> Type -> Type) -> [Type] -> Nat -> Type -> Type -> Type) where Source #

Methods

imap4 :: (forall i' j' k'. a i' j' k' x -> b i' j' k' x) -> f a i j k x -> f b i j k x Source #

Instances

Instances details
IFunctor4 (Instr o) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Instructions

Methods

imap4 :: forall a x b (i :: [Type]) (j :: Nat) k. (forall (i' :: [Type]) (j' :: Nat) k'. a i' j' k' x -> b i' j' k' x) -> Instr o a i j k x -> Instr o b i j k x Source #

class IFunctor (f :: (Type -> Type) -> Type -> Type) where Source #

Methods

imap :: (forall j. a j -> b j) -> f a i -> f b i Source #

Instances

Instances details
IFunctor ScopeRegister Source # 
Instance details

Defined in Parsley.Internal.Core.CombinatorAST

Methods

imap :: (forall j. a j -> b j) -> ScopeRegister a i -> ScopeRegister b i Source #

IFunctor Combinator Source # 
Instance details

Defined in Parsley.Internal.Core.CombinatorAST

Methods

imap :: (forall j. a j -> b j) -> Combinator a i -> Combinator b i Source #

IFunctor f => IFunctor (Cofree f) Source # 
Instance details

Defined in Parsley.Internal.Common.Indexed

Methods

imap :: (forall j. a j -> b j) -> Cofree f a i -> Cofree f b i Source #

(IFunctor f, IFunctor g) => IFunctor (f :+: g) Source # 
Instance details

Defined in Parsley.Internal.Common.Indexed

Methods

imap :: (forall j. a j -> b j) -> (f :+: g) a i -> (f :+: g) b i Source #

data Nat Source #

Constructors

Zero 
Succ Nat 

Instances

Instances details
Show (Fix4 (Instr o) xs n r a) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine.Instructions

Methods

showsPrec :: Int -> Fix4 (Instr o) xs n r a -> ShowS #

show :: Fix4 (Instr o) xs n r a -> String #

showList :: [Fix4 (Instr o) xs n r a] -> ShowS #

inop :: Fix f a -> f (Fix f) a Source #

inop4 :: Fix4 f i j k l -> f (Fix4 f) i j k l Source #

cata :: forall f a i. IFunctor f => (forall j. f a j -> a j) -> Fix f i -> a i Source #

cata' :: forall f a i. IFunctor f => (forall j. Fix f j -> f a j -> a j) -> Fix f i -> a i Source #

cata4 :: forall f a i j k x. IFunctor4 f => (forall i' j' k'. f a i' j' k' x -> a i' j' k' x) -> Fix4 f i j k x -> a i j k x Source #

(\/) :: (f a i -> b) -> (g a i -> b) -> (f :+: g) a i -> b Source #

extract :: Cofree f a i -> a i Source #

histo :: IFunctor f => (forall j. f (Cofree f a) j -> a j) -> Fix f i -> a i Source #

(/\) :: (a -> f i) -> (a -> g i) -> a -> (f :*: g) i Source #

ifst :: (f :*: g) i -> f i Source #

isnd :: (f :*: g) i -> g i Source #

mutu :: IFunctor f => (forall j. f (a :*: b) j -> a j) -> (forall j. f (a :*: b) j -> b j) -> Fix f i -> (a :*: b) i Source #

zygo :: IFunctor f => (forall j. f (a :*: b) j -> a j) -> (forall j. f b j -> b j) -> Fix f i -> a i Source #

zipper :: IFunctor f => (forall j. f a j -> a j) -> (forall j. f b j -> b j) -> Fix f i -> (a :*: b) i Source #