Boolean-0.2.4: Generalized booleans and numbers

Copyright(c) Conal Elliott 2009-2012
LicenseBSD3
Maintainerconal@conal.net
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell98

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 where Source #

Generalized boolean class

Minimal complete definition

true, false, notB, (&&*), (||*)

Methods

true, false :: b Source #

notB :: b -> b Source #

(&&*), (||*) :: b -> b -> b infixr 3 &&*infixr 2 ||* Source #

Instances

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

Methods

true :: z -> bool Source #

false :: z -> bool Source #

notB :: (z -> bool) -> z -> bool Source #

(&&*) :: (z -> bool) -> (z -> bool) -> z -> bool Source #

(||*) :: (z -> bool) -> (z -> bool) -> z -> bool Source #

type family BooleanOf a Source #

BooleanOf computed the boolean analog of a specific type.

Instances

type BooleanOf Bool Source # 
type BooleanOf Char Source # 
type BooleanOf Double Source # 
type BooleanOf Float Source # 
type BooleanOf Int Source # 
type BooleanOf Integer Source # 
type BooleanOf [a] Source # 
type BooleanOf [a] = BooleanOf a
type BooleanOf (z -> a) Source # 
type BooleanOf (z -> a) = z -> BooleanOf a
type BooleanOf (a, b) Source # 
type BooleanOf (a, b) = BooleanOf a
type BooleanOf (a, b, c) Source # 
type BooleanOf (a, b, c) = BooleanOf a
type BooleanOf (a, b, c, d) Source # 
type BooleanOf (a, b, c, d) = BooleanOf a

class Boolean (BooleanOf a) => IfB a where Source #

Types with conditionals

Minimal complete definition

ifB

Methods

ifB :: bool ~ BooleanOf a => bool -> a -> a -> a Source #

Instances

IfB Bool Source # 

Methods

ifB :: (* ~ bool) (BooleanOf Bool) => bool -> Bool -> Bool -> Bool Source #

IfB Char Source # 

Methods

ifB :: (* ~ bool) (BooleanOf Char) => bool -> Char -> Char -> Char Source #

IfB Double Source # 

Methods

ifB :: (* ~ bool) (BooleanOf Double) => bool -> Double -> Double -> Double Source #

IfB Float Source # 

Methods

ifB :: (* ~ bool) (BooleanOf Float) => bool -> Float -> Float -> Float Source #

IfB Int Source # 

Methods

ifB :: (* ~ bool) (BooleanOf Int) => bool -> Int -> Int -> Int Source #

IfB Integer Source # 

Methods

ifB :: (* ~ bool) (BooleanOf Integer) => bool -> Integer -> Integer -> Integer Source #

(Boolean (BooleanOf a), (~) * (BooleanOf a) Bool) => IfB [a] Source # 

Methods

ifB :: (* ~ bool) (BooleanOf [a]) => bool -> [a] -> [a] -> [a] Source #

IfB a => IfB (z -> a) Source # 

Methods

ifB :: (* ~ bool) (BooleanOf (z -> a)) => bool -> (z -> a) -> (z -> a) -> z -> a Source #

((~) * bool (BooleanOf p), (~) * bool (BooleanOf q), IfB p, IfB q) => IfB (p, q) Source # 

Methods

ifB :: (* ~ bool) (BooleanOf (p, q)) => bool -> (p, q) -> (p, q) -> (p, q) Source #

((~) * bool (BooleanOf p), (~) * bool (BooleanOf q), (~) * bool (BooleanOf r), IfB p, IfB q, IfB r) => IfB (p, q, r) Source # 

Methods

ifB :: (* ~ bool) (BooleanOf (p, q, r)) => bool -> (p, q, r) -> (p, q, r) -> (p, q, r) Source #

((~) * 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) Source # 

Methods

ifB :: (* ~ bool) (BooleanOf (p, q, r, s)) => bool -> (p, q, r, s) -> (p, q, r, s) -> (p, q, r, s) Source #

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) => EqB a where Source #

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

Minimal complete definition

(==*)

Methods

(==*), (/=*) :: bool ~ BooleanOf a => a -> a -> bool infix 4 ==*, /=* Source #

Instances

EqB Bool Source # 

Methods

(==*) :: (* ~ bool) (BooleanOf Bool) => Bool -> Bool -> bool Source #

(/=*) :: (* ~ bool) (BooleanOf Bool) => Bool -> Bool -> bool Source #

EqB Char Source # 

Methods

(==*) :: (* ~ bool) (BooleanOf Char) => Char -> Char -> bool Source #

(/=*) :: (* ~ bool) (BooleanOf Char) => Char -> Char -> bool Source #

EqB Double Source # 

Methods

(==*) :: (* ~ bool) (BooleanOf Double) => Double -> Double -> bool Source #

(/=*) :: (* ~ bool) (BooleanOf Double) => Double -> Double -> bool Source #

EqB Float Source # 

Methods

(==*) :: (* ~ bool) (BooleanOf Float) => Float -> Float -> bool Source #

(/=*) :: (* ~ bool) (BooleanOf Float) => Float -> Float -> bool Source #

EqB Int Source # 

Methods

(==*) :: (* ~ bool) (BooleanOf Int) => Int -> Int -> bool Source #

(/=*) :: (* ~ bool) (BooleanOf Int) => Int -> Int -> bool Source #

EqB Integer Source # 

Methods

(==*) :: (* ~ bool) (BooleanOf Integer) => Integer -> Integer -> bool Source #

(/=*) :: (* ~ bool) (BooleanOf Integer) => Integer -> Integer -> bool Source #

EqB a => EqB (z -> a) Source # 

Methods

(==*) :: (* ~ bool) (BooleanOf (z -> a)) => (z -> a) -> (z -> a) -> bool Source #

(/=*) :: (* ~ bool) (BooleanOf (z -> a)) => (z -> a) -> (z -> a) -> bool Source #

class Boolean (BooleanOf a) => OrdB a where Source #

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

Minimal complete definition

(<*)

Methods

(<*), (<=*), (>*), (>=*) :: bool ~ BooleanOf a => a -> a -> bool infix 4 <*, <=*, >*, >=* Source #

Instances

OrdB Bool Source # 

Methods

(<*) :: (* ~ bool) (BooleanOf Bool) => Bool -> Bool -> bool Source #

(<=*) :: (* ~ bool) (BooleanOf Bool) => Bool -> Bool -> bool Source #

(>*) :: (* ~ bool) (BooleanOf Bool) => Bool -> Bool -> bool Source #

(>=*) :: (* ~ bool) (BooleanOf Bool) => Bool -> Bool -> bool Source #

OrdB Char Source # 

Methods

(<*) :: (* ~ bool) (BooleanOf Char) => Char -> Char -> bool Source #

(<=*) :: (* ~ bool) (BooleanOf Char) => Char -> Char -> bool Source #

(>*) :: (* ~ bool) (BooleanOf Char) => Char -> Char -> bool Source #

(>=*) :: (* ~ bool) (BooleanOf Char) => Char -> Char -> bool Source #

OrdB Double Source # 

Methods

(<*) :: (* ~ bool) (BooleanOf Double) => Double -> Double -> bool Source #

(<=*) :: (* ~ bool) (BooleanOf Double) => Double -> Double -> bool Source #

(>*) :: (* ~ bool) (BooleanOf Double) => Double -> Double -> bool Source #

(>=*) :: (* ~ bool) (BooleanOf Double) => Double -> Double -> bool Source #

OrdB Float Source # 

Methods

(<*) :: (* ~ bool) (BooleanOf Float) => Float -> Float -> bool Source #

(<=*) :: (* ~ bool) (BooleanOf Float) => Float -> Float -> bool Source #

(>*) :: (* ~ bool) (BooleanOf Float) => Float -> Float -> bool Source #

(>=*) :: (* ~ bool) (BooleanOf Float) => Float -> Float -> bool Source #

OrdB Int Source # 

Methods

(<*) :: (* ~ bool) (BooleanOf Int) => Int -> Int -> bool Source #

(<=*) :: (* ~ bool) (BooleanOf Int) => Int -> Int -> bool Source #

(>*) :: (* ~ bool) (BooleanOf Int) => Int -> Int -> bool Source #

(>=*) :: (* ~ bool) (BooleanOf Int) => Int -> Int -> bool Source #

OrdB Integer Source # 

Methods

(<*) :: (* ~ bool) (BooleanOf Integer) => Integer -> Integer -> bool Source #

(<=*) :: (* ~ bool) (BooleanOf Integer) => Integer -> Integer -> bool Source #

(>*) :: (* ~ bool) (BooleanOf Integer) => Integer -> Integer -> bool Source #

(>=*) :: (* ~ bool) (BooleanOf Integer) => Integer -> Integer -> bool Source #

OrdB a => OrdB (z -> a) Source # 

Methods

(<*) :: (* ~ bool) (BooleanOf (z -> a)) => (z -> a) -> (z -> a) -> bool Source #

(<=*) :: (* ~ bool) (BooleanOf (z -> a)) => (z -> a) -> (z -> a) -> bool Source #

(>*) :: (* ~ bool) (BooleanOf (z -> a)) => (z -> a) -> (z -> a) -> bool Source #

(>=*) :: (* ~ bool) (BooleanOf (z -> a)) => (z -> a) -> (z -> a) -> bool Source #

minB :: (IfB a, OrdB a) => a -> a -> a Source #

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

maxB :: (IfB a, OrdB a) => a -> a -> a Source #

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

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

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

guardedB :: (IfB b, bool ~ BooleanOf b) => bool -> [(bool, b)] -> b -> b Source #

A generalized replacement for guards and chained ifs.

caseB :: (IfB b, bool ~ BooleanOf b) => a -> [(a -> bool, b)] -> b -> b Source #

A generalized version of a case like control structure.