| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Parameterized.Control.Applicative
- type family PUnary (m :: k -> Type -> Type) (t :: k) = (r :: Type -> Type) | r -> m t
- class PPointed m id where
- class (Functor (PUnary m t), Functor (PUnary m u), Functor (PUnary m v)) => PApplicative m t u v | t u -> v where
- (&<*>) :: PApplicative m t u v => PUnary m t (a -> b) -> PUnary m u a -> PUnary m v b
- (&*>) :: PApplicative m t u v => PUnary m t a -> PUnary m u b -> PUnary m v b
- (&<*) :: PApplicative m t u v => PUnary m t a -> PUnary m u b -> PUnary m v a
- pliftA :: Functor (PUnary m t) => (a -> b) -> PUnary m t a -> PUnary m t b
- pliftA2 :: PApplicative m t u v => (a -> b -> c) -> PUnary m t a -> PUnary m u b -> PUnary m v c
- pliftA3 :: (PApplicative m t u v, PApplicative m v w x) => (a -> b -> c -> d) -> PUnary m t a -> PUnary m u b -> PUnary m w c -> PUnary m x d
- class PEmpty m id | m -> id where
- class PAlternative m t u v | t u -> v where
- (&<|>) :: PAlternative m t u v => PUnary m t a -> PUnary m u a -> PUnary m v a
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
NB. For ChangingState,
the id s "parameter" cannot be purely determined from m,
so unlike pappend there is not functional dependency to help type inference.
Hint: use ppure @_ @_ id@ to specify the id type to avoid ambiguity.
Minimal complete definition
Instances
| Applicative m => PPointed * (ManyReader m) (Many ([] Type)) Source # | |
| Applicative m => PPointed * (DistinctWhichReader m) (Which ([] Type)) Source # | |
| Applicative m => PPointed * (OverlappingWhichReader m) (Which ([] Type)) Source # | |
| Monad m => PPointed * (ManyState m) (Many ([] Type)) Source # | |
| Applicative m => PPointed * (ChangingState m) (s, s) Source # | |
class (Functor (PUnary m t), Functor (PUnary m u), Functor (PUnary 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
Methods
papply :: PUnary m t (a -> b) -> PUnary m u a -> PUnary m v b infixl 4 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 # | |
| (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 # | |
| Monad m => PApplicative * (ChangingState m) (s, t) (t, u) (s, u) Source # | |
(&<*>) :: PApplicative m t u v => PUnary m t (a -> b) -> PUnary m u a -> PUnary m v b infixl 4 Source #
Sequential application.
(&*>) :: PApplicative m t u v => PUnary m t a -> PUnary m u b -> PUnary m v b infixl 4 Source #
Sequence actions, discarding the value of the first argument.
(&<*) :: PApplicative m t u v => PUnary m t a -> PUnary m u b -> PUnary m v a infixl 4 Source #
Sequence actions, discarding the value of the second argument.
pliftA :: Functor (PUnary m t) => (a -> b) -> PUnary m t a -> PUnary m t b Source #
Lift a function to actions.
pliftA2 :: PApplicative m t u v => (a -> b -> c) -> PUnary m t a -> PUnary m u b -> PUnary 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) -> PUnary m t a -> PUnary m u b -> PUnary m w c -> PUnary 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
Instances
| Alternative m => PEmpty * (ManyReader m) (Many ([] Type)) Source # | |
| Alternative m => PEmpty * (DistinctWhichReader m) (Which ([] Type)) Source # | |
| Alternative m => PEmpty * (OverlappingWhichReader m) (Which ([] Type)) Source # | |
| Alternative m => PEmpty * (ManyState m) (Many ([] Type)) 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
Methods
pappend :: PUnary m t a -> PUnary m u a -> PUnary m v a infixl 3 Source #
An associative binary operation
Instances
| (Alternative m, Select a c, Select b c, (~) [Type] c (AppendUnique Type a b)) => PAlternative * (ManyReader m) (Many a) (Many b) (Many c) 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 # | |
| (Alternative m, Reinterpret b c, Reinterpret a c, (~) [Type] c (AppendUnique Type a b)) => PAlternative * (OverlappingWhichReader m) (Which a) (Which b) (Which c) 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 # | |