graphted-0.3.1.0: Graph indexed monads.

Copyright(c) Aaron Friel
LicenseBSD-3
MaintainerAaron Friel <mayreply@aaronfriel.com>
Stabilityunstable
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Control.Applicative.Graph

Description

 

Synopsis

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 #

Equations

DefaultThenCxt True f i j = (Apply f (Replace f i) j ~ Then f i j, ApplyInv f (Replace f i) j) 
DefaultThenCxt False f i j = (LiftA2 f i j ~ Then f i j, LiftA2Inv f i j) 

class GApplicativeThen useReplace f where Source #

Minimal complete definition

gdefaultThenProxy, gdefaultThen

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 # 

Methods

gdefaultThenProxy :: DefaultThenCxt False f f i j => proxy f -> f i a -> f j b -> f (Then False f i j) b Source #

gdefaultThen :: DefaultThenCxt False f f i j => f i a -> f j b -> f (Then False f i j) b Source #

GApplicative p f => GApplicativeThen p True f Source # 

Methods

gdefaultThenProxy :: DefaultThenCxt True f f i j => proxy f -> f i a -> f j b -> f (Then True f i j) b Source #

gdefaultThen :: DefaultThenCxt True f f i j => f i a -> f j b -> f (Then True f i j) b Source #

class (GFunctor f, GPointed f) => GApplicative f where Source #

Graph indexed applicative functor.

Minimal complete definition

gap

Associated Types

type Apply f (i :: p) (j :: p) :: p Source #

The apply operation (<*>) on the graph index.

Default instance: Apply f i j = Combine f i j

type ApplyInv f (i :: p) (j :: p) :: Constraint Source #

An invariant on the indexes of Apply.

Default instance: ApplyInv m i j = Inv m i j

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 #

An invariant on the indexes of But.

Default instance: ButInv m i j = ApplyInv m i j

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 #

An invariant on the indexes of Then.

Default instance: ThenInv m i j = ApplyInv m i j

type But f (i :: p) (j :: p) :: p Source #

The but operation (<*) on the graph index.

Default instance: But f i j = LiftA2 f i j

type ButInv f (i :: p) (j :: p) :: Constraint Source #

An invariant on the indexes of But.

Default instance: ButInv m i j = ApplyInv m i j

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 #

Lift a binary function to actions.

Default implementation is defined in terms of Apply and Fmap.

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 #

Lift a binary function to actions.

Default implementation is defined in terms of Apply and Fmap.

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 #

Sequence actions, discarding values of the second argument (<*).

Default implementation requires the default instance of But.

Instances

Applicative f => GApplicative * (GWrapped f) Source # 

Associated Types

type Apply (GWrapped f) (f :: GWrapped f -> * -> *) (i :: GWrapped f) (j :: GWrapped f) :: p Source #

type ApplyInv (GWrapped f) (f :: GWrapped f -> * -> *) (i :: GWrapped f) (j :: GWrapped f) :: Constraint Source #

type LiftA2 (GWrapped f) (f :: GWrapped f -> * -> *) (i :: GWrapped f) (j :: GWrapped f) :: p Source #

type LiftA2Inv (GWrapped f) (f :: GWrapped f -> * -> *) (i :: GWrapped f) (j :: GWrapped f) :: Constraint Source #

type ThenUseReplace (GWrapped f) (f :: GWrapped f -> * -> *) :: Bool Source #

type Then (GWrapped f) (f :: GWrapped f -> * -> *) (i :: GWrapped f) (j :: GWrapped f) :: p Source #

type ThenInv (GWrapped f) (f :: GWrapped f -> * -> *) (i :: GWrapped f) (j :: GWrapped f) :: Constraint Source #

type But (GWrapped f) (f :: GWrapped f -> * -> *) (i :: GWrapped f) (j :: GWrapped f) :: p Source #

type ButInv (GWrapped f) (f :: GWrapped f -> * -> *) (i :: GWrapped f) (j :: GWrapped f) :: Constraint Source #

Methods

gap :: ApplyInv (GWrapped f) f i j => f i (a -> b) -> f j a -> f (Apply (GWrapped f) f i j) b Source #

gliftA2 :: LiftA2Inv (GWrapped f) f i j => (a -> b -> c) -> f i a -> f j b -> f (LiftA2 (GWrapped f) f i j) c Source #

gthen :: ThenInv (GWrapped f) f i j => f i a -> f j b -> f (Then (GWrapped f) f i j) b Source #

gbut :: ButInv (GWrapped f) f i j => f i a -> f j b -> f (But (GWrapped f) f i j) a Source #

IxApplicative * f => GApplicative (*, *) (WrappedIx f) Source # 

Associated Types

type Apply (WrappedIx f) (f :: WrappedIx f -> * -> *) (i :: WrappedIx f) (j :: WrappedIx f) :: p Source #

type ApplyInv (WrappedIx f) (f :: WrappedIx f -> * -> *) (i :: WrappedIx f) (j :: WrappedIx f) :: Constraint Source #

type LiftA2 (WrappedIx f) (f :: WrappedIx f -> * -> *) (i :: WrappedIx f) (j :: WrappedIx f) :: p Source #

type LiftA2Inv (WrappedIx f) (f :: WrappedIx f -> * -> *) (i :: WrappedIx f) (j :: WrappedIx f) :: Constraint Source #

type ThenUseReplace (WrappedIx f) (f :: WrappedIx f -> * -> *) :: Bool Source #

type Then (WrappedIx f) (f :: WrappedIx f -> * -> *) (i :: WrappedIx f) (j :: WrappedIx f) :: p Source #

type ThenInv (WrappedIx f) (f :: WrappedIx f -> * -> *) (i :: WrappedIx f) (j :: WrappedIx f) :: Constraint Source #

type But (WrappedIx f) (f :: WrappedIx f -> * -> *) (i :: WrappedIx f) (j :: WrappedIx f) :: p Source #

type ButInv (WrappedIx f) (f :: WrappedIx f -> * -> *) (i :: WrappedIx f) (j :: WrappedIx f) :: Constraint Source #

Methods

gap :: ApplyInv (WrappedIx f) f i j => f i (a -> b) -> f j a -> f (Apply (WrappedIx f) f i j) b Source #

gliftA2 :: LiftA2Inv (WrappedIx f) f i j => (a -> b -> c) -> f i a -> f j b -> f (LiftA2 (WrappedIx f) f i j) c Source #

gthen :: ThenInv (WrappedIx f) f i j => f i a -> f j b -> f (Then (WrappedIx f) f i j) b Source #

gbut :: ButInv (WrappedIx f) f i j => f i a -> f j b -> f (But (WrappedIx f) f i j) a Source #