Copyright | (c) Conal Elliott 2009-2012 |
---|---|
License | BSD3 |
Maintainer | conal@conal.net |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell98 |
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.
- class Boolean b where
- type family BooleanOf a
- class Boolean (BooleanOf a) => IfB a where
- boolean :: (IfB a, bool ~ BooleanOf a) => a -> a -> bool -> a
- cond :: (Applicative f, IfB a, bool ~ BooleanOf a) => f bool -> f a -> f a -> f a
- crop :: (Applicative f, Monoid (f a), IfB a, bool ~ BooleanOf a) => f bool -> f a -> f a
- class Boolean (BooleanOf a) => EqB a where
- class Boolean (BooleanOf a) => OrdB a where
- minB :: (IfB a, OrdB a) => a -> a -> a
- maxB :: (IfB a, OrdB a) => a -> a -> a
- sort2B :: (IfB a, OrdB a) => (a, a) -> (a, a)
- guardedB :: (IfB b, bool ~ BooleanOf b) => bool -> [(bool, b)] -> b -> b
- caseB :: (IfB b, bool ~ BooleanOf b) => a -> [(a -> bool, b)] -> b -> b
Documentation
Generalized boolean class
type family BooleanOf a Source
BooleanOf
computed the boolean analog of a specific type.
type BooleanOf Bool = Bool | |
type BooleanOf Char = Bool | |
type BooleanOf Double = Bool | |
type BooleanOf Float = Bool | |
type BooleanOf Int = Bool | |
type BooleanOf Integer = Bool | |
type BooleanOf [a] = BooleanOf a | |
type BooleanOf (z -> a) = z -> BooleanOf a | |
type BooleanOf (a, b) = BooleanOf a | |
type BooleanOf (a, b, c) = BooleanOf a | |
type BooleanOf (a, b, c, d) = BooleanOf a |
class Boolean (BooleanOf a) => IfB a where Source
Types with conditionals
IfB Bool | |
IfB Char | |
IfB Double | |
IfB Float | |
IfB Int | |
IfB Integer | |
(Boolean (BooleanOf a), (~) * (BooleanOf a) Bool) => IfB [a] | |
IfB a => IfB (z -> a) | |
((~) * bool (BooleanOf p), (~) * bool (BooleanOf q), IfB p, IfB q) => IfB (p, q) | |
((~) * bool (BooleanOf p), (~) * bool (BooleanOf q), (~) * bool (BooleanOf r), IfB p, IfB q, IfB r) => IfB (p, q, r) | |
((~) * 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 -> a Source
Expression-lifted conditional with condition last
cond :: (Applicative f, IfB a, bool ~ BooleanOf a) => f bool -> f a -> f a -> f a Source
Point-wise conditional
crop :: (Applicative f, Monoid (f a), IfB a, bool ~ BooleanOf a) => f bool -> f a -> f a Source
Generalized cropping, filling in mempty
where the test yields false.
class Boolean (BooleanOf a) => OrdB a where Source
Types with inequality. Minimum definition: '(<*)'.