doc typo
[ghc-base.git] / GHC / Float.lhs
index d68119c..dbb556f 100644 (file)
@@ -1,5 +1,7 @@
 \begin{code}
 {-# OPTIONS_GHC -XNoImplicitPrelude #-}
+-- We believe we could deorphan this module, by moving lots of things
+-- around, but we haven't got there yet:
 {-# OPTIONS_GHC -fno-warn-orphans #-}
 {-# OPTIONS_HADDOCK hide #-}
 -----------------------------------------------------------------------------
@@ -57,6 +59,11 @@ class  (Fractional a) => Floating a  where
     sinh, cosh, tanh    :: a -> a
     asinh, acosh, atanh :: a -> a
 
+    {-# INLINE (**) #-}
+    {-# INLINE logBase #-}
+    {-# INLINE sqrt #-}
+    {-# INLINE tan #-}
+    {-# INLINE tanh #-}
     x ** y              =  exp (log x * y)
     logBase x y         =  log y / log x
     sqrt x              =  x ** 0.5
@@ -149,19 +156,6 @@ class  (RealFrac a, Floating a) => RealFloat a  where
 %*********************************************************
 
 \begin{code}
-instance Eq Float where
-    (F# x) == (F# y) = x `eqFloat#` y
-
-instance Ord Float where
-    (F# x) `compare` (F# y) | x `ltFloat#` y = LT
-                            | x `eqFloat#` y = EQ
-                            | otherwise      = GT
-
-    (F# x) <  (F# y) = x `ltFloat#`  y
-    (F# x) <= (F# y) = x `leFloat#`  y
-    (F# x) >= (F# y) = x `geFloat#`  y
-    (F# x) >  (F# y) = x `gtFloat#`  y
-
 instance  Num Float  where
     (+)         x y     =  plusFloat x y
     (-)         x y     =  minusFloat x y
@@ -205,7 +199,7 @@ instance  RealFrac Float  where
 #error FLT_RADIX must be 2
 #endif
     properFraction (F# x#)
-      = case (decodeFloat_Int# x#) of
+      = case decodeFloat_Int# x# of
         (# m#, n# #) ->
             let m = I# m#
                 n = I# n#
@@ -293,19 +287,6 @@ instance  Show Float  where
 %*********************************************************
 
 \begin{code}
-instance Eq Double where
-    (D# x) == (D# y) = x ==## y
-
-instance Ord Double where
-    (D# x) `compare` (D# y) | x <## y   = LT
-                            | x ==## y  = EQ
-                            | otherwise = GT
-
-    (D# x) <  (D# y) = x <##  y
-    (D# x) <= (D# y) = x <=## y
-    (D# x) >= (D# y) = x >=## y
-    (D# x) >  (D# y) = x >##  y
-
 instance  Num Double  where
     (+)         x y     =  plusDouble x y
     (-)         x y     =  minusDouble x y
@@ -625,7 +606,9 @@ floatToDigits base x =
         -- Haskell promises that p-1 <= logBase b f < p.
         (p - 1 + e0) * 3 `div` 10
      else
-        ceiling ((log (fromInteger (f+1)) +
+       -- f :: Integer, log :: Float -> Float, 
+        --               ceiling :: Float -> Int
+        ceiling ((log (fromInteger (f+1) :: Float) +
                  fromIntegral e * log (fromInteger b)) /
                    log (fromInteger base))
 --WAS:            fromInt e * log (fromInteger b))
@@ -903,21 +886,12 @@ powerDouble  (D# x) (D# y) = D# (x **## y)
 \end{code}
 
 \begin{code}
-foreign import ccall unsafe "__encodeFloat"
-        encodeFloat# :: Int# -> ByteArray# -> Int -> Float
-foreign import ccall unsafe "__int_encodeFloat"
-        int_encodeFloat# :: Int# -> Int -> Float
-
-
 foreign import ccall unsafe "isFloatNaN" isFloatNaN :: Float -> Int
 foreign import ccall unsafe "isFloatInfinite" isFloatInfinite :: Float -> Int
 foreign import ccall unsafe "isFloatDenormalized" isFloatDenormalized :: Float -> Int
 foreign import ccall unsafe "isFloatNegativeZero" isFloatNegativeZero :: Float -> Int
 
 
-foreign import ccall unsafe "__encodeDouble"
-        encodeDouble# :: Int# -> ByteArray# -> Int -> Double
-
 foreign import ccall unsafe "isDoubleNaN" isDoubleNaN :: Double -> Int
 foreign import ccall unsafe "isDoubleInfinite" isDoubleInfinite :: Double -> Int
 foreign import ccall unsafe "isDoubleDenormalized" isDoubleDenormalized :: Double -> Int