graphted-0.3.0.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

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 Then f (i :: p) (j :: p) :: p Source #

The then operation (*>) on the graph index.

Default instance: Then f i j = Apply f (Replace f i) j

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.

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.

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 :: (Apply f (Replace f i) j ~ Then f i j, ApplyInv f (Replace f i) j, ThenInv f (Replace 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 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 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 #