Boolean-0.1.0: Generalized booleans

Stabilityexperimental
Maintainerconal@conal.net
Safe HaskellSafe-Inferred

Data.Boolean

Description

Some classes for generalized boolean operations.

In this design, for if-then-else, equality and inequality tests, the boolean type depends on the value type.

I also tried using a unary type constructor class. The class doesn't work for regular booleans, so generality is lost. Also, we'd probably have to wire class constraints in like: (==*) :: Eq a => f Bool -> f a -> f a -> f a, which disallows situations needing additional constraints, e.g., Show.

Starting with 0.1.0, this package uses type families. Up to version 0.0.2, it used MPTCs with functional dependencies. My thanks to Andy Gill for suggesting & helping with the change.

Synopsis

Documentation

class Boolean b whereSource

Generalized boolean class

Methods

true, false :: bSource

notB :: b -> bSource

(&&*), (||*) :: b -> b -> bSource

Instances

Boolean Bool 
Boolean bool => Boolean (z -> bool) 

type family BooleanOf a Source

BooleanOf computed the boolean analog of a specific type.

class Boolean (BooleanOf a) => IfB a whereSource

Types with conditionals

Methods

ifB :: bool ~ BooleanOf a => bool -> a -> a -> aSource

Instances

IfB Bool 
IfB Char 
IfB Double 
IfB Float 
IfB Int 
IfB Integer 
(Boolean (BooleanOf [a]), Boolean (BooleanOf a), ~ * (BooleanOf a) Bool) => IfB [a] 
(Boolean (BooleanOf (z -> a)), IfB a) => IfB (z -> a) 
(Boolean (BooleanOf (p, q)), ~ * bool (BooleanOf p), ~ * bool (BooleanOf q), IfB p, IfB q) => IfB (p, q) 
(Boolean (BooleanOf (p, q, r)), ~ * bool (BooleanOf p), ~ * bool (BooleanOf q), ~ * bool (BooleanOf r), IfB p, IfB q, IfB r) => IfB (p, q, r) 
(Boolean (BooleanOf (p, q, r, s)), ~ * bool (BooleanOf p), ~ * bool (BooleanOf q), ~ * bool (BooleanOf r), ~ * bool (BooleanOf s), IfB p, IfB q, IfB r, IfB s) => IfB (p, q, r, s) 

boolean :: (IfB a, bool ~ BooleanOf a) => a -> a -> bool -> aSource

Expression-lifted conditional with condition last

cond :: (Applicative f, IfB a, bool ~ BooleanOf a) => f bool -> f a -> f a -> f aSource

Point-wise conditional

crop :: (Applicative f, Monoid (f a), IfB a, bool ~ BooleanOf a) => f bool -> f a -> f aSource

Generalized cropping, filling in mempty where the test yields false.

class Boolean (BooleanOf a) => EqB a whereSource

Types with equality. Minimum definition: '(==*)'.

Methods

(==*), (/=*) :: bool ~ BooleanOf a => a -> a -> boolSource

Instances

EqB Bool 
EqB Char 
EqB Double 
EqB Float 
EqB Int 
EqB Integer 
(Boolean (BooleanOf (z -> a)), EqB a) => EqB (z -> a) 

class Boolean (BooleanOf a) => OrdB a whereSource

Types with inequality. Minimum definition: '(<*)'.

Methods

(<*), (>=*), (>*), (<=*) :: bool ~ BooleanOf a => a -> a -> boolSource

Instances

minB :: (IfB a, OrdB a) => a -> a -> aSource

Variant of min using ifB and '(<=*)'

maxB :: (IfB a, OrdB a) => a -> a -> aSource

Variant of max using ifB and '(>=*)'

sort2B :: (IfB a, OrdB a) => (a, a) -> (a, a)Source

Variant of min using ifB and '(<=*)'