{- | Type classes (and instances) for things that are like Booleans. The names of methods in 'Boolean' clash with the standard Prelude, so you probably want to inport the Prelude hiding these three names (since the class methods do the same thing, but with more general type signatures). An interesting consequence of the 'Boolean' instance for monads is that 'P.Maybe' 'P.Bool' is a 'Boolean'. You can use this to implement 3-value logic (\"true\", \"false\" and \"other\"), with 'P.Nothing' implementing \"other\". Any logical operations yield 'P.Nothing' unless all arguments are 'P.Just' something. (This is usually the behaviour you want.) -} {-# LANGUAGE FlexibleInstances #-} module Data.Boolean where import qualified Prelude as P {- | Typeclass for things that have true and false values. Instances: * Normal 'P.Bool' values (obviously). * Any function that yields a 'BoolValue' as its result. (For example, 'true' is just a constant function that always returns a truth value, regardless of its input.) * Any monadic action that yields a 'BoolValue' as its result. (This is just 'P.return' applied to the appropriate 'BoolValue'.) -} class BoolValue b where true :: b false :: b instance BoolValue P.Bool where true = P.True false = P.False instance (BoolValue b) => BoolValue (x -> b) where true = \ _ -> true false = \ _ -> false instance (P.Monad m, BoolValue b) => BoolValue (m b) where true = P.return true false = P.return false -- | Convert a 'P.Bool' value to the appropriate 'BoolValue'. lift_bool :: (BoolValue b) => P.Bool -> b lift_bool b = if b then true else false {- | Typeclass for things that support Boolean operators. Instances: * Normal 'P.Bool' values (obviously). * Any function that returns a 'Boolean'. (The result is a new function that runs the old function(s) and applies the appropriate operator to the result(s).) * Any monadic action that returns a 'Boolean'. (Again, the result is a new action that runs the existing action(s) and applies the appropriate operator to the result(s).) -} class Boolean b where -- | Logical-AND of two values. (&&) :: b -> b -> b -- | Logical-OR of two values. (Inclusive-OR.) (||) :: b -> b -> b -- | Logical-NOT of two values. (Logical inverse.) not :: b -> b {- | Exclusive-OR (XOR). There is a default implementation, but you can override it for efficiency if desired. -} xor :: b -> b -> b x `xor` y = (x || y) && (not (x && y)) instance Boolean P.Bool where (&&) = (P.&&) (||) = (P.||) not = P.not instance (Boolean b) => Boolean (x -> b) where f && g = \ x -> f x && g x f || g = \ x -> f x || g x not f = \ x -> not (f x) f `xor` g = \ x -> (f x) `xor` (g x) instance (P.Monad m, Boolean b) => Boolean (m b) where f && g = f P.>>= \ x -> g P.>>= \ y -> P.return (x && y) f || g = f P.>>= \ x -> g P.>>= \ y -> P.return (x || y) not f = f P.>>= \ x -> P.return (not x) f `xor` g = f P.>>= \ x -> g P.>>= \ y -> P.return (x `xor` y)