{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module OAlg.Data.Boolean.Definition
(
Boolean(..)
, B.Bool(..), B.otherwise
, Bol
)
where
import Prelude as P hiding (not,(||),(&&),or,and)
import qualified Data.Bool as B
import OAlg.Structure.Definition
infixr 3 &&
infixr 2 ||
infixr 1 ~>, <~>
class Boolean b where
{-# MINIMAL true, false, not, ((||), (&&) | or, and) #-}
false :: b
true :: b
not :: b -> b
(||) :: b -> b -> b
b
a || b
b = forall b. Boolean b => [b] -> b
or [b
a,b
b]
or :: [b] -> b
or [] = forall b. Boolean b => b
false
or (b
a:[b]
as) = b
a forall b. Boolean b => b -> b -> b
|| forall b. Boolean b => [b] -> b
or [b]
as
(&&) :: b -> b -> b
b
a && b
b = forall b. Boolean b => [b] -> b
and [b
a,b
b]
and :: [b] -> b
and [] = forall b. Boolean b => b
true
and (b
a:[b]
as) = b
a forall b. Boolean b => b -> b -> b
&& forall b. Boolean b => [b] -> b
and [b]
as
(~>) :: b -> b -> b
b
a ~> b
b = forall b. Boolean b => b -> b
not b
a forall b. Boolean b => b -> b -> b
|| b
b
(<~>) :: b -> b -> b
b
a <~> b
b = (b
a forall b. Boolean b => b -> b -> b
~> b
b) forall b. Boolean b => b -> b -> b
&& (b
b forall b. Boolean b => b -> b -> b
~> b
a)
eqvl :: [b] -> b
eqvl [] = forall b. Boolean b => b
true
eqvl (b
a:[b]
as) = forall b. Boolean b => [b] -> b
and [b]
impls where
impls :: [b]
impls = forall a b. (a -> b) -> [a] -> [b]
map (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall b. Boolean b => b -> b -> b
(~>)) (forall a b. [a] -> [b] -> [(a, b)]
zip (b
aforall a. a -> [a] -> [a]
:[b]
as) ([b]
asforall a. [a] -> [a] -> [a]
++[b
a]))
instance Boolean Bool where
false :: Bool
false = Bool
False
true :: Bool
true = Bool
True
not :: Bool -> Bool
not = Bool -> Bool
B.not
|| :: Bool -> Bool -> Bool
(||) = Bool -> Bool -> Bool
(B.||)
&& :: Bool -> Bool -> Bool
(&&) = Bool -> Bool -> Bool
(B.&&)
<~> :: Bool -> Bool -> Bool
(<~>) = forall a. Eq a => a -> a -> Bool
(==)
data Bol
type instance Structure Bol x = Boolean x