-- | Equality operations module Feldspar.Core.Functions.Eq where import qualified Prelude import Data.Complex import Data.Int import Data.Word import Feldspar.Prelude import Feldspar.Range import Feldspar.Core.Types import Feldspar.Core.Representation import Feldspar.Core.Constructs infix 4 == infix 4 /= -- | Redefinition of the standard 'Prelude.Eq' class for Feldspar class Type a => Eq a where (==) :: Data a -> Data a -> Data Bool (==) = defaultEq (/=) :: Data a -> Data a -> Data Bool (/=) = defaultNeq defaultEq :: Eq a => Data a -> Data a -> Data Bool defaultEq a b | a Prelude.== b = true | otherwise = function2 "(==)" fullProp (Prelude.==) a b defaultNeq :: Eq a => Data a -> Data a -> Data Bool defaultNeq a b | a Prelude.== b = false | otherwise = function2 "(/=)" fullProp (Prelude./=) a b optEq :: (Eq a, BoundedInt b, Size a ~ Range b) => Data a -> Data a -> Data Bool optEq a b | sa `disjoint` sb = false | otherwise = defaultEq a b where sa = dataSize a sb = dataSize b optNeq :: (Eq a, BoundedInt b, Size a ~ Range b) => Data a -> Data a -> Data Bool optNeq a b | sa `disjoint` sb = true | otherwise = defaultNeq a b where sa = dataSize a sb = dataSize b instance Eq () instance Eq Bool instance Eq Float instance Eq Word8 where (==) = optEq (/=) = optNeq instance Eq Int8 where (==) = optEq (/=) = optNeq instance Eq Word16 where (==) = optEq (/=) = optNeq instance Eq Int16 where (==) = optEq (/=) = optNeq instance Eq Word32 where (==) = optEq (/=) = optNeq instance Eq Int32 where (==) = optEq (/=) = optNeq instance Eq DefaultWord where (==) = optEq (/=) = optNeq instance Eq DefaultInt where (==) = optEq (/=) = optNeq instance (Eq a, RealFloat a) => Eq (Complex a) instance Eq a => Eq [a] instance (Eq a, Eq b) => Eq (a,b) instance (Eq a, Eq b, Eq c) => Eq (a,b,c) instance (Eq a, Eq b, Eq c, Eq d) => Eq (a,b,c,d)