| Copyright | (c) Aaron Friel |
|---|---|
| License | BSD-3 |
| Maintainer | Aaron Friel <mayreply@aaronfriel.com> |
| Stability | unstable |
| Portability | portable |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Control.Applicative.Graph
Description
- type family DefaultThen (useReplace :: Bool) (f :: p -> * -> *) (i :: p) (j :: p) where ...
- type family DefaultThenCxt (useReplace :: Bool) (f :: p -> * -> *) (i :: p) (j :: p) where ...
- class GApplicativeThen useReplace f where
- class (GFunctor f, GPointed f) => GApplicative f where
- type Apply f (i :: p) (j :: p) :: p
- type ApplyInv f (i :: p) (j :: p) :: Constraint
- type LiftA2 f (i :: p) (j :: p) :: p
- type LiftA2Inv f (i :: p) (j :: p) :: Constraint
- type ThenUseReplace f :: Bool
- type Then f (i :: p) (j :: p) :: p
- type ThenInv f (i :: p) (j :: p) :: Constraint
- type But f (i :: p) (j :: p) :: p
- type ButInv f (i :: p) (j :: p) :: Constraint
Documentation
type family DefaultThen (useReplace :: Bool) (f :: p -> * -> *) (i :: p) (j :: p) where ... Source #
Equations
| DefaultThen True f i j = Apply f (Replace f i) j | |
| DefaultThen False f i j = LiftA2 f i j |
type family DefaultThenCxt (useReplace :: Bool) (f :: p -> * -> *) (i :: p) (j :: p) where ... Source #
class GApplicativeThen useReplace f where Source #
Minimal complete definition
Methods
gdefaultThenProxy :: DefaultThenCxt useReplace f i j => proxy useReplace -> f i a -> f j b -> f (Then f i j) b Source #
gdefaultThen :: DefaultThenCxt useReplace f i j => f i a -> f j b -> f (Then f i j) b Source #
Instances
| GApplicative p f => GApplicativeThen p False f Source # | |
| GApplicative p f => GApplicativeThen p True f Source # | |
class (GFunctor f, GPointed f) => GApplicative f where Source #
Graph indexed applicative functor.
Minimal complete definition
Associated Types
type Apply f (i :: p) (j :: p) :: p Source #
type ApplyInv f (i :: p) (j :: p) :: Constraint Source #
type LiftA2 f (i :: p) (j :: p) :: p Source #
The liftA2 operation on the graph index.
Default instance: Lift f i j = Apply f (Apply f (Pure f) i) j
type LiftA2Inv f (i :: p) (j :: p) :: Constraint Source #
type ThenUseReplace f :: Bool Source #
Whether to use gliftA2, or gap and greplace in the definition
of gthen.
If an efficient Replace exists, we should probably use that to reduce
allocations. But liftA2 might also be appropriate.
type Then f (i :: p) (j :: p) :: p Source #
The then operation (*>) on the graph index.
Default instance depends on :ThenUseReplace f
type ThenInv f (i :: p) (j :: p) :: Constraint Source #
type But f (i :: p) (j :: p) :: p Source #
type ButInv f (i :: p) (j :: p) :: Constraint Source #
Methods
gap :: ApplyInv f i j => f i (a -> b) -> f j a -> f (Apply f i j) b Source #
Sequential application (<*>).
gliftA2 :: LiftA2Inv f i j => (a -> b -> c) -> f i a -> f j b -> f (LiftA2 f i j) c Source #
gliftA2 :: (Apply f (Fmap f i) j ~ LiftA2 f i j, ApplyInv f (Fmap f i) j) => (a -> b -> c) -> f i a -> f j b -> f (LiftA2 f i j) c Source #
gthen :: ThenInv f i j => f i a -> f j b -> f (Then f i j) b Source #
Sequence actions, discarding the value of the first argument (*>).
Default implementation requires the default instance of Then.
gthen :: (GApplicativeThen (ThenUseReplace f) f, DefaultThenCxt (ThenUseReplace f) f i j) => f i a -> f j b -> f (Then f i j) b Source #
Sequence actions, discarding the value of the first argument (*>).
Default implementation requires the default instance of Then.
gbut :: ButInv f i j => f i a -> f j b -> f (But f i j) a Source #
Sequence actions, discarding values of the second argument (<*).
Default implementation requires the default instance of But.
gbut :: (LiftA2 f i j ~ But f i j, LiftA2Inv f i j) => f i a -> f j b -> f (But f i j) a Source #
Instances
| Applicative f => GApplicative * (GWrapped f) Source # | |
| IxApplicative * f => GApplicative (*, *) (WrappedIx f) Source # | |