Remove datatype contexts from base
[ghc-base.git] / Data / Complex.hs
index 7d29e77..3692501 100644 (file)
@@ -1,3 +1,8 @@
+{-# LANGUAGE CPP, DeriveDataTypeable #-}
+#ifdef __GLASGOW_HASKELL__
+{-# LANGUAGE StandaloneDeriving #-}
+#endif
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Data.Complex
@@ -45,7 +50,7 @@ import Prelude
 
 import Data.Typeable
 #ifdef __GLASGOW_HASKELL__
-import Data.Generics.Basics( Data )
+import Data.Data (Data)
 #endif
 
 #ifdef __HUGS__
@@ -62,7 +67,7 @@ infix  6  :+
 -- For a complex number @z@, @'abs' z@ is a number with the magnitude of @z@,
 -- but oriented in the positive real direction, whereas @'signum' z@
 -- has the phase of @z@, but unit magnitude.
-data (RealFloat a) => Complex a
+data Complex a
   = !a :+ !a    -- ^ forms a complex number from its real and imaginary
                 -- rectangular components.
 # if __GLASGOW_HASKELL__
@@ -110,9 +115,10 @@ polar z          =  (magnitude z, phase z)
 {-# SPECIALISE magnitude :: Complex Double -> Double #-}
 magnitude :: (RealFloat a) => Complex a -> a
 magnitude (x:+y) =  scaleFloat k
-                     (sqrt ((scaleFloat mk x)^(2::Int) + (scaleFloat mk y)^(2::Int)))
+                     (sqrt (sqr (scaleFloat mk x) + sqr (scaleFloat mk y)))
                     where k  = max (exponent x) (exponent y)
                           mk = - k
+                          sqr z = z * z
 
 -- | The phase of a complex number, in the range @(-'pi', 'pi']@.
 -- If the magnitude is zero, then so is the phase.
@@ -197,4 +203,4 @@ instance  (RealFloat a) => Floating (Complex a) where
 
     asinh z        =  log (z + sqrt (1+z*z))
     acosh z        =  log (z + (z+1) * sqrt ((z-1)/(z+1)))
-    atanh z        =  log ((1+z) / sqrt (1-z*z))
+    atanh z        =  0.5 * log ((1.0+z) / (1.0-z))