graphted-0.2.5.1: Graph indexed monads.

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

Data.GWrappedIx

Description

 

Synopsis

Documentation

newtype WrappedIx m p a Source #

Wrap a two-parameter-indexed type constructor:

Constructors

WrappedIx 

Fields

Instances

IxFunctor * * f => GFunctor (*, *) (WrappedIx f) Source # 

Associated Types

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

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

Methods

gmap :: (a -> b) -> f i a -> f (Fmap (WrappedIx f) f i) b Source #

gconst :: a -> f i b -> f (Fconst (WrappedIx f) f i) a Source #

Graphted (*, *) (WrappedIx m) Source # 

Associated Types

type Unit (WrappedIx m) (f :: WrappedIx m -> * -> *) :: p Source #

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

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

IxPointed * f => GPointed (*, *) (WrappedIx f) Source # 

Associated Types

type Pure (WrappedIx f) (f :: WrappedIx f -> * -> *) :: p Source #

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

Methods

gpure :: a -> f (Pure (WrappedIx f) f) a Source #

gpure' :: PureCxt (WrappedIx f) f t => a -> f t 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 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 #

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 #

IxMonad * m => GMonad (*, *) (WrappedIx m) Source # 

Associated Types

type Bind (WrappedIx m) (m :: WrappedIx m -> * -> *) (i :: WrappedIx m) (j :: WrappedIx m) :: p Source #

type BindInv (WrappedIx m) (m :: WrappedIx m -> * -> *) (i :: WrappedIx m) (j :: WrappedIx m) :: Constraint Source #

type Join (WrappedIx m) (m :: WrappedIx m -> * -> *) (i :: WrappedIx m) (j :: WrappedIx m) :: p Source #

type JoinInv (WrappedIx m) (m :: WrappedIx m -> * -> *) (i :: WrappedIx m) (j :: WrappedIx m) :: Constraint Source #

Methods

gbind :: BindInv (WrappedIx m) m i j => m i a -> (a -> m j b) -> m (Bind (WrappedIx m) m i j) b Source #

gjoin :: JoinInv (WrappedIx m) m i j => m i (m j b) -> m (Join (WrappedIx m) m i j) b Source #

IxMonadZero * m => GMonadZero (*, *) (WrappedIx m) Source # 

Associated Types

type Zero (WrappedIx m) (m :: WrappedIx m -> * -> *) :: p Source #

Methods

gzero :: m (Zero (WrappedIx m) m) a Source #

IxMonadZero * m => GMonadFail (*, *) (WrappedIx m) Source # 

Associated Types

type Fail (WrappedIx m) (m :: WrappedIx m -> * -> *) :: p Source #

Methods

gfail :: String -> m (Fail (WrappedIx m) m) a Source #

IxMonadPlus * m => GMonadPlus (*, *) (WrappedIx m) Source # 

Associated Types

type Plus (WrappedIx m) (m :: WrappedIx m -> * -> *) (i :: WrappedIx m) (j :: WrappedIx m) :: p Source #

type PlusInv (WrappedIx m) (m :: WrappedIx m -> * -> *) (i :: WrappedIx m) (j :: WrappedIx m) :: Constraint Source #

Methods

gplus :: PlusInv (WrappedIx m) m i j => m i a -> m j a -> m (Plus (WrappedIx m) m i j) a Source #

type Unit (*, *) (WrappedIx m) Source # 
type Unit (*, *) (WrappedIx m) = (,) * * (Any *) (Any *)
type Pure (*, *) (WrappedIx f) Source # 
type Pure (*, *) (WrappedIx f) = Unit (*, *) (WrappedIx f)
type Zero (*, *) (WrappedIx m) Source # 
type Zero (*, *) (WrappedIx m) = Unit (*, *) (WrappedIx m)
type Fail (*, *) (WrappedIx m) Source # 
type Fail (*, *) (WrappedIx m) = Unit (*, *) (WrappedIx m)
type Fmap (*, *) (WrappedIx f) i Source # 
type Fmap (*, *) (WrappedIx f) i = i
type Fconst (*, *) (WrappedIx f) i Source # 
type Fconst (*, *) (WrappedIx f) i = Fmap (*, *) (WrappedIx f) i
type PureCxt (*, *) (WrappedIx f) i Source # 
type PureCxt (*, *) (WrappedIx f) i = (~) * (FstIx * i) (SndIx * i)
type Inv (*, *) (WrappedIx m) i j Source # 
type Inv (*, *) (WrappedIx m) i j = (~) * (SndIx * i) (FstIx * j)
type Combine (*, *) (WrappedIx m) i j Source # 
type Combine (*, *) (WrappedIx m) i j = (,) * * (FstIx * i) (SndIx * j)
type Apply (*, *) (WrappedIx f) i j Source # 
type Apply (*, *) (WrappedIx f) i j = Combine (*, *) (WrappedIx f) i j
type ApplyInv (*, *) (WrappedIx f) i j Source # 
type ApplyInv (*, *) (WrappedIx f) i j = Inv (*, *) (WrappedIx f) i j
type Then (*, *) (WrappedIx f) i j Source # 
type Then (*, *) (WrappedIx f) i j = Apply (*, *) (WrappedIx f) (Fconst (*, *) (WrappedIx f) i) j
type ThenInv (*, *) (WrappedIx f) i j Source # 
type ThenInv (*, *) (WrappedIx f) i j = ApplyInv (*, *) (WrappedIx f) i j
type But (*, *) (WrappedIx m) l r Source # 
type But (*, *) (WrappedIx m) l r = (,) * * (FstIx * l) (SndIx * r)
type ButInv (*, *) (WrappedIx f) i j Source # 
type ButInv (*, *) (WrappedIx f) i j = ApplyInv (*, *) (WrappedIx f) i j
type Bind (*, *) (WrappedIx m) i j Source # 
type Bind (*, *) (WrappedIx m) i j = Combine (*, *) (WrappedIx m) i j
type BindInv (*, *) (WrappedIx m) i j Source # 
type BindInv (*, *) (WrappedIx m) i j = Inv (*, *) (WrappedIx m) i j
type Join (*, *) (WrappedIx m) i j Source # 
type Join (*, *) (WrappedIx m) i j = Bind (*, *) (WrappedIx m) i j
type JoinInv (*, *) (WrappedIx m) i j Source # 
type JoinInv (*, *) (WrappedIx m) i j = BindInv (*, *) (WrappedIx m) i j
type Plus (*, *) (WrappedIx m) i j Source # 
type Plus (*, *) (WrappedIx m) i j = Combine (*, *) (WrappedIx m) i j
type PlusInv (*, *) (WrappedIx m) l r Source # 
type PlusInv (*, *) (WrappedIx m) l r = ((~) * (FstIx * l) (FstIx * r), (~) * (SndIx * l) (SndIx * r))

type family FstIx p :: * where ... Source #

Equations

FstIx '(i, j) = i 

type family SndIx p :: * where ... Source #

Equations

SndIx '(i, j) = j 

liftIx :: m i j a -> WrappedIx m '(i, j) a Source #

Lift an object to WrappedIx.