expressions-0.1.1: Expressions and Formulas 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.Array

Description

 

Synopsis

Documentation

data ArrayF a s where Source #

A functor representing array-theoretic terms (select and store also known as "read" and "write")

Constructors

Select :: Sing i -> Sing e -> a (ArraySort i e) -> a i -> ArrayF a e 
Store :: Sing i -> Sing e -> a (ArraySort i e) -> a i -> a e -> ArrayF a (ArraySort i e) 

Instances

IFoldable Sort ArrayF Source # 

Methods

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

IEq1 Sort ArrayF Source # 

Methods

ieq1 :: IEq ArrayF a => f a j -> f a j -> Bool Source #

IFunctor Sort ArrayF Source # 

Methods

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

index :: f a i' -> Sing ArrayF i' Source #

ITraversable Sort ArrayF Source # 

Methods

itraverse :: Applicative f => (forall i'. a i' -> f (b i')) -> forall i'. t a i' -> f (t b i') Source #

IShow Sort Sort ArrayF Source # 

Methods

ishow :: f (Const k String) i -> Const ArrayF String i Source #

JoinSemiLattice (ALia BooleanSort) # 
JoinSemiLattice (QFALia BooleanSort) # 
MeetSemiLattice (ALia BooleanSort) # 
MeetSemiLattice (QFALia BooleanSort) # 
Lattice (ALia BooleanSort) # 
Lattice (QFALia BooleanSort) # 
BoundedJoinSemiLattice (ALia BooleanSort) # 
BoundedJoinSemiLattice (QFALia BooleanSort) # 
BoundedMeetSemiLattice (ALia BooleanSort) # 

Methods

top :: ALia BooleanSort #

BoundedMeetSemiLattice (QFALia BooleanSort) # 
BoundedLattice (ALia BooleanSort) # 
BoundedLattice (QFALia BooleanSort) # 
ComplementedLattice (ALia BooleanSort) Source # 
ComplementedLattice (QFALia BooleanSort) Source # 
(:<:) Sort ArrayF f => Parseable ((Sort -> *) -> Sort -> *) ArrayF f Source # 

select :: (ArrayF :<: f, SingI i, SingI e) => IFix f (ArraySort i e) -> IFix f i -> IFix f e Source #

A smart constructor for select

store :: (ArrayF :<: f, SingI i, SingI e) => IFix f (ArraySort i e) -> IFix f i -> IFix f e -> IFix f (ArraySort i e) Source #

A smart constructor for store