expressions-0.1.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.IfThenElse

Description

 

Synopsis

Documentation

data IfThenElseF a (s :: Sort) where Source #

A functor representing a conditional value (if-then-else)

Constructors

IfThenElse :: Sing s -> a BooleanSort -> a s -> a s -> IfThenElseF a s 

Instances

IEq1 Sort IfThenElseF Source # 

Methods

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

IFoldable Sort IfThenElseF Source # 

Methods

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

IFunctor Sort IfThenElseF Source # 

Methods

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

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

ITraversable Sort IfThenElseF Source # 

Methods

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

IShow Sort Sort IfThenElseF Source # 

Methods

ishow :: f (Const IfThenElseF String) i -> Const k 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 IfThenElseF f => Parseable ((Sort -> *) -> Sort -> *) IfThenElseF f Source # 

ite :: forall f s. (IfThenElseF :<: f, SingI s) => IFix f BooleanSort -> IFix f s -> IFix f s -> IFix f s Source #

A smart constructor for an if-then-else expression