expressions-0.5: Expressions and Formulae a la carte

Copyright(C) 2017-18 Jakub Daniel
LicenseBSD-style (see the file LICENSE)
MaintainerJakub Daniel <jakub.daniel@protonmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.Expression.Utils.Indexed.Sum

Description

 
Synopsis

Documentation

data (f :+: g) a i infixr 8 Source #

Sum of two indexed functors

Constructors

InL (f a i) 
InR (g a i) 
Instances
(IShow f, IShow g) => IShow (f :+: g :: (k1 -> Type) -> k2 -> Type) Source # 
Instance details

Defined in Data.Expression.Utils.Indexed.Sum

Methods

ishow :: (f :+: g) (Const String) i -> Const String i Source #

(IFunctor f, IFunctor g, IFunctor h, f :<<: g) => (f :: (k -> Type) -> k -> Type) :<<: (h :+: g :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Expression.Utils.Indexed.Sum

Methods

emb :: f a i -> (h :+: g) a i

res :: (h :+: g) a i -> Maybe (f a i)

(IFunctor f, IFunctor g) => (f :: (k -> Type) -> k -> Type) :<<: (g :+: f :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Expression.Utils.Indexed.Sum

Methods

emb :: f a i -> (g :+: f) a i

res :: (g :+: f) a i -> Maybe (f a i)

(IFunctor f, IFunctor g, IFunctor h, f :<: g) => (f :: (k -> Type) -> k -> Type) :<: (h :+: g :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Expression.Utils.Indexed.Sum

Methods

inj :: f a i -> (h :+: g) a i Source #

prj :: (h :+: g) a i -> Maybe (f a i) Source #

(IFunctor f, IFunctor g) => (f :: (k -> Type) -> k -> Type) :<: (f :+: g :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Expression.Utils.Indexed.Sum

Methods

inj :: f a i -> (f :+: g) a i Source #

prj :: (f :+: g) a i -> Maybe (f a i) Source #

(IEq1 f, IEq1 g) => IEq1 (f :+: g :: (i -> Type) -> i -> Type) Source # 
Instance details

Defined in Data.Expression.Utils.Indexed.Sum

Methods

ieq1 :: IEq a => (f :+: g) a j -> (f :+: g) a j -> Bool Source #

(IFoldable f, IFoldable g) => IFoldable (f :+: g :: (i -> Type) -> i -> Type) Source # 
Instance details

Defined in Data.Expression.Utils.Indexed.Sum

Methods

ifold :: Monoid m => (f :+: g) (Const m) i' -> Const m i' Source #

(IFunctor f, IFunctor g) => IFunctor (f :+: g :: (i -> Type) -> i -> Type) Source # 
Instance details

Defined in Data.Expression.Utils.Indexed.Sum

Methods

imap :: (forall (i' :: i0). a i' -> b i') -> forall (i' :: i0). (f :+: g) a i' -> (f :+: g) b i' Source #

index :: (f :+: g) a i' -> Sing i' Source #

(ITraversable f, ITraversable g) => ITraversable (f :+: g :: (i -> Type) -> i -> Type) Source # 
Instance details

Defined in Data.Expression.Utils.Indexed.Sum

Methods

itraverse :: Applicative f0 => (forall (i' :: i0). a i' -> f0 (b i')) -> forall (i' :: i0). (f :+: g) a i' -> f0 ((f :+: g) b i') Source #

(MaybeQuantified f, MaybeQuantified g) => MaybeQuantified (f :+: g :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Expression

Heyting (ALia BooleanSort) Source # 
Instance details

Defined in Data.Expression

Heyting (QFALia BooleanSort) Source # 
Instance details

Defined in Data.Expression

Heyting (Lia BooleanSort) Source # 
Instance details

Defined in Data.Expression

Heyting (QFLia BooleanSort) Source # 
Instance details

Defined in Data.Expression

Heyting (QFLogic BooleanSort) Source # 
Instance details

Defined in Data.Expression

Lattice (ALia BooleanSort) Source # 
Instance details

Defined in Data.Expression

Lattice (QFALia BooleanSort) Source # 
Instance details

Defined in Data.Expression

Lattice (Lia BooleanSort) Source # 
Instance details

Defined in Data.Expression

Lattice (QFLia BooleanSort) Source # 
Instance details

Defined in Data.Expression

Lattice (QFLogic BooleanSort) Source # 
Instance details

Defined in Data.Expression

BoundedJoinSemiLattice (ALia BooleanSort) Source # 
Instance details

Defined in Data.Expression

BoundedJoinSemiLattice (QFALia BooleanSort) Source # 
Instance details

Defined in Data.Expression

BoundedJoinSemiLattice (Lia BooleanSort) Source # 
Instance details

Defined in Data.Expression

BoundedJoinSemiLattice (QFLia BooleanSort) Source # 
Instance details

Defined in Data.Expression

BoundedJoinSemiLattice (QFLogic BooleanSort) Source # 
Instance details

Defined in Data.Expression

BoundedMeetSemiLattice (ALia BooleanSort) Source # 
Instance details

Defined in Data.Expression

Methods

top :: ALia BooleanSort #

BoundedMeetSemiLattice (QFALia BooleanSort) Source # 
Instance details

Defined in Data.Expression

BoundedMeetSemiLattice (Lia BooleanSort) Source # 
Instance details

Defined in Data.Expression

Methods

top :: Lia BooleanSort #

BoundedMeetSemiLattice (QFLia BooleanSort) Source # 
Instance details

Defined in Data.Expression

BoundedMeetSemiLattice (QFLogic BooleanSort) Source # 
Instance details

Defined in Data.Expression

(Parseable f h, Parseable g h) => Parseable (f :+: g :: k1 -> k2 -> Type) h Source # 
Instance details

Defined in Data.Expression.Parser

class (IFunctor f, IFunctor g) => f :<: g where Source #

Inclusion relation for indexed sum functors

Methods

inj :: f a i -> g a i Source #

prj :: g a i -> Maybe (f a i) Source #

Instances
IFunctor f => (f :: (i -> Type) -> i -> Type) :<: (f :: (i -> Type) -> i -> Type) Source # 
Instance details

Defined in Data.Expression.Utils.Indexed.Sum

Methods

inj :: f a i0 -> f a i0 Source #

prj :: f a i0 -> Maybe (f a i0) Source #

(IFunctor f, IFunctor g, IFunctor h, f :<: g) => (f :: (k -> Type) -> k -> Type) :<: (h :+: g :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Expression.Utils.Indexed.Sum

Methods

inj :: f a i -> (h :+: g) a i Source #

prj :: (h :+: g) a i -> Maybe (f a i) Source #

(IFunctor f, IFunctor g) => (f :: (k -> Type) -> k -> Type) :<: (f :+: g :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Expression.Utils.Indexed.Sum

Methods

inj :: f a i -> (f :+: g) a i Source #

prj :: (f :+: g) a i -> Maybe (f a i) Source #

class (IFunctor f, IFunctor g) => f :<<: g Source #

Minimal complete definition

emb, res

Instances
(IFunctor f, IFunctor g, IFunctor h, f :<<: g) => (f :: (k -> Type) -> k -> Type) :<<: (h :+: g :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Expression.Utils.Indexed.Sum

Methods

emb :: f a i -> (h :+: g) a i

res :: (h :+: g) a i -> Maybe (f a i)

(IFunctor f, IFunctor g) => (f :: (k -> Type) -> k -> Type) :<<: (g :+: f :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Expression.Utils.Indexed.Sum

Methods

emb :: f a i -> (g :+: f) a i

res :: (g :+: f) a i -> Maybe (f a i)

inject :: g :<: f => forall i. g (IFix f) i -> IFix f i Source #

Inject a component into a sum.

match :: g :<: f => forall i. IFix f i -> Maybe (g (IFix f) i) Source #

Try to unpack a sum into a component.

embed :: (IFunctor f, f :<<: g) => IFix f i -> IFix g i Source #

Embed a subset in a superset.

restrict :: (ITraversable g, f :<<: g) => IFix g i -> Maybe (IFix f i) Source #

Try to restrict a superset to a subset.