{-# OPTIONS_GHC -fglasgow-exts #-} module Language.CMonad.CPrelude(module Prelude, Boolean(..), Eq(..), Ord(..), Cond(..)) where import qualified Prelude as P import Prelude hiding (Eq(..), Ord(..), (&&), (||), not, until) infix 4 ==, /=, <, <=, >=, > infixr 3 && infixr 2 || class Boolean b where false, true :: b (&&), (||) :: b -> b -> b not :: b -> b instance Boolean Bool where {-# INLINE false #-} false = False {-# INLINE true #-} true = True {-# INLINE (&&) #-} (&&) = (P.&&) {-# INLINE (||) #-} (||) = (P.||) {-# INLINE not #-} not = P.not class (Boolean b) => Eq a b {- | a -> b -} where (==), (/=) :: a -> a -> b x /= y = not (x == y) class (Eq a b) => Ord a b {- | a -> b -} where (<), (<=), (>), (>=) :: a -> a -> b instance (P.Eq a) => Eq a Bool where {-# INLINE (==) #-} (==) = (P.==) {-# INLINE (/=) #-} (/=) = (P./=) instance (P.Ord a) => Ord a Bool where {-# INLINE (<) #-} (<) = (P.<) {-# INLINE (<=) #-} (<=) = (P.<=) {-# INLINE (>) #-} (>) = (P.>) {-# INLINE (>=) #-} (>=) = (P.>=) ------------------------------------------- class (Boolean b) => Cond a b | a -> b where cond :: b -> a -> a -> a instance Cond Int Bool where {-# INLINE cond #-} cond x y z = if x then y else z instance Cond Bool Bool where {-# INLINE cond #-} cond x y z = if x then y else z