module Data.Algebra.Boolean
( Boolean(..), fromBool, Bitwise(..)
) where
import Data.Monoid (Any(..), All(..), Dual(..), Endo(..))
import Data.Bits (Bits, complement, (.|.), (.&.))
import qualified Data.Bits as Bits
import Data.Function (on)
import Data.Typeable
import Data.Data
import Data.Ix
import Data.Foldable (Foldable)
import qualified Data.Foldable as F
import Foreign.Storable
import Text.Printf
import Prelude hiding ((&&), (||), not, and, or, any, all)
import qualified Prelude as P
infixr 1 <-->, `xor`, -->
infixr 2 ||
infixr 3 &&
class Boolean b where
true :: b
false :: b
not :: b -> b
(&&) :: b -> b -> b
(||) :: b -> b -> b
xor :: b -> b -> b
(-->) :: b -> b -> b
(<-->) :: b -> b -> b
and :: Foldable t => t b -> b
or :: Foldable t => t b -> b
nand :: Foldable t => t b -> b
nand = not . and
all :: Foldable t => (a -> b) -> t a -> b
any :: Foldable t => (a -> b) -> t a -> b
nor :: Foldable t => t b -> b
nor = not . or
true = not false
false = not true
not = (<--> false)
x && y = not (not x || not y)
x || y = not (not x && not y)
x `xor` y = (x || y) && (not (x && y))
x --> y = not x || y
x <--> y = (x && y) || not (x || y)
and = F.foldl' (&&) true
or = F.foldl' (||) false
all p = F.foldl' f true
where f a b = a && p b
any p = F.foldl' f false
where f a b = a || p b
fromBool :: Boolean b => Bool -> b
fromBool b = if b then true else false
instance Boolean Bool where
true = True
false = False
(&&) = (P.&&)
(||) = (P.||)
not = P.not
xor = (/=)
True --> True = True
True --> False = False
False --> _ = True
(<-->) = (==)
instance Boolean Any where
true = Any True
false = Any False
not (Any p) = Any (not p)
(Any p) && (Any q) = Any (p && q)
(Any p) || (Any q) = Any (p || q)
(Any p) `xor` (Any q) = Any (p `xor` q)
(Any p) --> (Any q) = Any (p --> q)
(Any p) <--> (Any q) = Any (p <--> q)
instance Boolean All where
true = All True
false = All False
not (All p) = All (not p)
(All p) && (All q) = All (p && q)
(All p) || (All q) = All (p || q)
(All p) `xor` (All q) = All (p `xor` q)
(All p) --> (All q) = All (p --> q)
(All p) <--> (All q) = All (p <--> q)
instance Boolean (Dual Bool) where
true = Dual True
false = Dual False
not (Dual p) = Dual (not p)
(Dual p) && (Dual q) = Dual (p && q)
(Dual p) || (Dual q) = Dual (p || q)
(Dual p) `xor` (Dual q) = Dual (p `xor` q)
(Dual p) --> (Dual q) = Dual (p --> q)
(Dual p) <--> (Dual q) = Dual (p <--> q)
instance Boolean (Endo Bool) where
true = Endo (const True)
false = Endo (const False)
not (Endo p) = Endo (not . p)
(Endo p) && (Endo q) = Endo (\a -> p a && q a)
(Endo p) || (Endo q) = Endo (\a -> p a || q a)
(Endo p) `xor` (Endo q) = Endo (\a -> p a `xor` q a)
(Endo p) --> (Endo q) = Endo (\a -> p a --> q a)
(Endo p) <--> (Endo q) = Endo (\a -> p a <--> q a)
instance (Boolean x, Boolean y) => Boolean (x, y) where
true = (true, true)
false = (false, false)
not (a, b) = (not a, not b)
(a, b) && (c, d) = (a && c, b && d)
(a, b) || (c, d) = (a || c, b || d)
(a, b) `xor` (c, d) = (a `xor` c, b `xor` d)
(a, b) --> (c, d) = (a --> c, b --> d)
(a, b) <--> (c, d) = (a <--> c, b <--> d)
newtype Bitwise a = Bitwise {getBits :: a}
deriving (Num, Bits, Eq, Ord, Bounded, Enum, Show, Read, Real,
Integral, Typeable, Data, Ix, Storable, PrintfArg)
instance (Num a, Bits a) => Boolean (Bitwise a) where
true = not false
false = Bitwise 0
not = Bitwise . complement . getBits
(&&) = (Bitwise .) . (.&.) `on` getBits
(||) = (Bitwise .) . (.|.) `on` getBits
xor = (Bitwise .) . (Bits.xor `on` getBits)
(<-->) = xor `on` not