parameterized-0.2.0.0: Extensible records and polymorphic variants.

Safe HaskellSafe
LanguageHaskell2010

Parameterized.Control.Applicative

Synopsis

Documentation

class PPointed m id where Source #

Parameterized version of pure in Applicative An instance of this should create a parameterized unary type where the parameter is an identity in respect to papply

Minimal complete definition

ppure

Methods

ppure :: a -> m id a Source #

lift a value.

Instances

Applicative m => PPointed * (ManyReader m) (Many ([] Type)) Source # 

Methods

ppure :: a -> Many [Type] id a Source #

Applicative m => PPointed * (DistinctWhichReader m) (Which ([] Type)) Source # 

Methods

ppure :: a -> Which [Type] id a Source #

Applicative m => PPointed * (OverlappingWhichReader m) (Which ([] Type)) Source # 

Methods

ppure :: a -> Which [Type] id a Source #

Monad m => PPointed * (ManyState m) (Many ([] Type)) Source # 

Methods

ppure :: a -> Many [Type] id a Source #

Applicative m => PPointed * (ChangingState m) (s, s) Source # 

Methods

ppure :: a -> (s, s) id a Source #

class (Functor (m t), Functor (m u), Functor (m v)) => PApplicative m t u v | t u -> v where Source #

Parameterized version of ap in Applicative NB. PPointed cannot be made a superclass because type variable id is not in scope.

Minimal complete definition

papply

Methods

papply :: m t (a -> b) -> m u a -> m v b Source #

Sequential application.

Instances

(Functor (ManyReader m (Many c)), Applicative m, Select a c, Select b c, (~) [Type] c (AppendUnique Type a b)) => PApplicative * (ManyReader m) (Many a) (Many b) (Many c) Source # 

Methods

papply :: Many a (Many b) (a -> b) -> Many a (Many c) a -> Many a v b Source #

(Monad m, Select a c, Select b c, Amend a c, Amend b c, (~) [Type] c (AppendUnique Type a b)) => PApplicative * (ManyState m) (Many a) (Many b) (Many c) Source # 

Methods

papply :: Many a (Many b) (a -> b) -> Many a (Many c) a -> Many a v b Source #

Monad m => PApplicative * (ChangingState m) (s, t) (t, u) (s, u) Source # 

Methods

papply :: (s, t) (t, u) (a -> b) -> (s, t) (s, u) a -> (s, t) v b Source #

(&<*>) :: PApplicative m t u v => m t (a -> b) -> m u a -> m v b infixl 4 Source #

Sequential application.

(&*>) :: PApplicative m t u v => m t a -> m u b -> m v b infixl 4 Source #

Sequence actions, discarding the value of the first argument.

(&<*) :: PApplicative m t u v => m t a -> m u b -> m v a infixl 4 Source #

Sequence actions, discarding the value of the second argument.

pliftA :: Functor (m t) => (a -> b) -> m t a -> m t b Source #

Lift a function to actions.

pliftA2 :: PApplicative m t u v => (a -> b -> c) -> m t a -> m u b -> m v c Source #

Lift a binary function to actions.

pliftA3 :: (PApplicative m t u v, PApplicative m v w x) => (a -> b -> c -> d) -> m t a -> m u b -> m w c -> m x d Source #

Lift a ternary function to actions.

class PEmpty m id | m -> id where Source #

Parameterized version of empty in Alternative. An instance of this should create a parameterized unary type where the parameter is an identity in respect to pappend

Minimal complete definition

pempty

Methods

pempty :: m id a Source #

The identity of &<|>

Instances

Alternative m => PEmpty * (ManyReader m) (Many ([] Type)) Source # 

Methods

pempty :: Many [Type] id a Source #

Alternative m => PEmpty * (DistinctWhichReader m) (Which ([] Type)) Source # 

Methods

pempty :: Which [Type] id a Source #

Alternative m => PEmpty * (OverlappingWhichReader m) (Which ([] Type)) Source # 

Methods

pempty :: Which [Type] id a Source #

Alternative m => PEmpty * (ManyState m) (Many ([] Type)) Source # 

Methods

pempty :: Many [Type] id a Source #

class PAlternative m t u v | t u -> v where Source #

Parameterized version of Alternative NB. PEmpty cannot be made a superclass because type variable id will be ambiguous. NB. PAlternative doensn't require PApplicative as a superclass, because Some things can be made instances of PAlternative but not PApplicative.

Minimal complete definition

pappend

Methods

pappend :: m t a -> m u a -> m v a Source #

An associative binary operation

Instances

(Functor (ManyReader m (Many c)), Alternative m, Select a c, Select b c, (~) [Type] c (AppendUnique Type a b)) => PAlternative * (ManyReader m) (Many a) (Many b) (Many c) Source # 

Methods

pappend :: Many a (Many b) a -> Many a (Many c) a -> Many a v a Source #

(Reinterpret b c, (~) [Type] (Complement Type c b) a, (~) [Type] (Complement Type c a) b, (~) [Type] c (Append Type a b)) => PAlternative * (DistinctWhichReader m) (Which a) (Which b) (Which c) Source # 

Methods

pappend :: Which a (Which b) a -> Which a (Which c) a -> Which a v a Source #

(Alternative m, Reinterpret b c, Reinterpret a c, (~) [Type] c (AppendUnique Type a b)) => PAlternative * (OverlappingWhichReader m) (Which a) (Which b) (Which c) Source # 

Methods

pappend :: Which a (Which b) a -> Which a (Which c) a -> Which a v a Source #

(Monad m, Alternative m, Select a c, Select b c, Amend a c, Amend b c, (~) [Type] c (AppendUnique Type a b)) => PAlternative * (ManyState m) (Many a) (Many b) (Many c) Source # 

Methods

pappend :: Many a (Many b) a -> Many a (Many c) a -> Many a v a Source #

(&<|>) :: PAlternative m t u v => m t a -> m u a -> m v a infixl 3 Source #