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.Arithmetic

Description

 

Synopsis

Documentation

data ArithmeticF a s where Source #

A functor representing linear integer arithmetic: constants (cnst), addition (add or .+.), multiplication (mul or .*.), divisibility predicate (.\.) and ordering (.<., .>., .<=., .>=.).

Instances

IFoldable Sort ArithmeticF Source # 

Methods

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

IEq1 Sort ArithmeticF Source # 

Methods

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

IFunctor Sort ArithmeticF Source # 

Methods

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

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

ITraversable Sort ArithmeticF 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 ArithmeticF Source # 

Methods

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

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

Methods

top :: ALia BooleanSort #

BoundedMeetSemiLattice (QFALia BooleanSort) # 
BoundedMeetSemiLattice (Lia BooleanSort) # 

Methods

top :: Lia BooleanSort #

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

cnst :: ArithmeticF :<: f => Int -> IFix f IntegralSort Source #

A smart constructor for integer constants

add :: ArithmeticF :<: f => [IFix f IntegralSort] -> IFix f IntegralSort Source #

A smart constructor for a variadic addition

mul :: ArithmeticF :<: f => [IFix f IntegralSort] -> IFix f IntegralSort Source #

A smart constructor for a variadic multiplication

(.+.) :: forall f. ArithmeticF :<: f => IFix f IntegralSort -> IFix f IntegralSort -> IFix f IntegralSort infixl 8 Source #

A smart constructor for binary addition

(.*.) :: forall f. ArithmeticF :<: f => IFix f IntegralSort -> IFix f IntegralSort -> IFix f IntegralSort infixl 9 Source #

A smart constructor for a binary multiplication

(.\.) :: ArithmeticF :<: f => Int -> IFix f IntegralSort -> IFix f BooleanSort infix 7 Source #

A smart constructor for a divisibility predicate

(.<.) :: forall f. ArithmeticF :<: f => IFix f IntegralSort -> IFix f IntegralSort -> IFix f BooleanSort infix 7 Source #

A smart constructor for <

(.>.) :: forall f. ArithmeticF :<: f => IFix f IntegralSort -> IFix f IntegralSort -> IFix f BooleanSort infix 7 Source #

A smart constructor for >

(.<=.) :: forall f. ArithmeticF :<: f => IFix f IntegralSort -> IFix f IntegralSort -> IFix f BooleanSort infix 7 Source #

A smart constructor for <=

(.>=.) :: forall f. ArithmeticF :<: f => IFix f IntegralSort -> IFix f IntegralSort -> IFix f BooleanSort infix 7 Source #

A smart constructor for >=