{-# LANGUAGE NoImplicitPrelude #-} module Algebra.Real ( C(abs, signum), ) where import qualified Algebra.Ring as Ring import qualified Algebra.Additive as Additive import qualified Algebra.ZeroTestable as ZeroTestable import Algebra.Ring (one, ) -- fromInteger import Algebra.Additive (zero, negate,) import Data.Int (Int, Int8, Int16, Int32, Int64, ) import Data.Word (Word, Word8, Word16, Word32, Word64, ) import PreludeBase import qualified Prelude as P import Prelude(Int,Integer,Float,Double) {- | This is the type class of an ordered ring, satisfying the laws > a * b === b * a > a + (max b c) === max (a+b) (a+c) > negate (max b c) === min (negate b) (negate c) > a * (max b c) === max (a*b) (a*c) where a >= 0 Note that abs is in a rather different place than it is in the Haskell 98 Prelude. In particular, > abs :: Complex -> Complex is not defined. To me, this seems to have the wrong type anyway; Complex.magnitude has the correct type. -} class (Ring.C a, ZeroTestable.C a, Ord a) => C a where abs :: a -> a signum :: a -> a -- Minimal definition: nothing abs x = max x (negate x) signum x = case compare x zero of GT -> one EQ -> zero LT -> negate one instance C Integer where {-# INLINE abs #-} {-# INLINE signum #-} abs = P.abs signum = P.signum instance C Float where {-# INLINE abs #-} {-# INLINE signum #-} abs = P.abs signum = P.signum instance C Double where {-# INLINE abs #-} {-# INLINE signum #-} abs = P.abs signum = P.signum instance C Int where {-# INLINE abs #-} {-# INLINE signum #-} abs = P.abs signum = P.signum instance C Int8 where {-# INLINE abs #-} {-# INLINE signum #-} abs = P.abs signum = P.signum instance C Int16 where {-# INLINE abs #-} {-# INLINE signum #-} abs = P.abs signum = P.signum instance C Int32 where {-# INLINE abs #-} {-# INLINE signum #-} abs = P.abs signum = P.signum instance C Int64 where {-# INLINE abs #-} {-# INLINE signum #-} abs = P.abs signum = P.signum instance C Word where {-# INLINE abs #-} {-# INLINE signum #-} abs = P.abs signum = P.signum instance C Word8 where {-# INLINE abs #-} {-# INLINE signum #-} abs = P.abs signum = P.signum instance C Word16 where {-# INLINE abs #-} {-# INLINE signum #-} abs = P.abs signum = P.signum instance C Word32 where {-# INLINE abs #-} {-# INLINE signum #-} abs = P.abs signum = P.signum instance C Word64 where {-# INLINE abs #-} {-# INLINE signum #-} abs = P.abs signum = P.signum