[project @ 2001-02-22 16:10:12 by rrt]
[ghc-hetmet.git] / ghc / lib / std / Prelude.lhs
index 01e82b3..1e86072 100644 (file)
@@ -1,3 +1,11 @@
+% ------------------------------------------------------------------------------
+% $Id: Prelude.lhs,v 1.23 2001/02/22 13:17:59 simonpj Exp $
+%
+% (c) The University of Glasgow, 1992-2000
+%
+
+\section[Prelude]{Module @Prelude@}
+
 We add the option -fno-implicit-prelude here to tell the reader that
 special names such as () and -> shouldn't be resolved to Prelude.()
 and Prelude.-> (as they are normally). -- SDM 8/10/97
@@ -44,7 +52,6 @@ module Prelude (
     Enum(..),
     Bounded(..), 
     Num((+), (-), (*), negate, abs, signum, fromInteger),
-       -- The fromInt method is exposed only by GlaExts
     Real(..),
     Integral(quot, rem, div, mod, quotRem, divMod, toInteger),
        -- The toInt method is exposed only by GlaExts
@@ -53,7 +60,7 @@ module Prelude (
     RealFrac(..),
     RealFloat(..),
 
-       -- From Monad
+       -- Monad stuff, from PrelBase, and defined here
     Monad(..),
     Functor(..), 
     mapM, mapM_, sequence, sequence_, (=<<),
@@ -74,6 +81,9 @@ import PrelList
 #ifndef USE_REPORT_PRELUDE
      hiding ( takeUInt_append )
 #endif
+import PrelIO
+import PrelIOBase
+import PrelException
 import PrelRead
 import PrelEnum
 import PrelNum
@@ -83,13 +93,20 @@ import PrelTup
 import PrelMaybe
 import PrelShow
 import PrelConc
-import Monad
-import Maybe
 import PrelErr   ( error )
-import IO
 
+infixr 1 =<<
 infixr 0 $!
+\end{code}
 
+
+%*********************************************************
+%*                                                     *
+\subsection{Miscellaneous functions}
+%*                                                     *
+%*********************************************************
+
+\begin{code}
 ($!)    :: (a -> b) -> a -> b
 f $! x  = x `seq` f x
 
@@ -136,35 +153,83 @@ product   l       = prod l 1
 
 %*********************************************************
 %*                                                     *
+\subsection{Prelude monad functions}
+%*                                                     *
+%*********************************************************
+
+\begin{code}
+{-# SPECIALISE (=<<) :: (a -> [b]) -> [a] -> [b] #-}
+(=<<)           :: Monad m => (a -> m b) -> m a -> m b
+f =<< x                = x >>= f
+
+sequence       :: Monad m => [m a] -> m [a] 
+{-# INLINE sequence #-}
+sequence ms = foldr k (return []) ms
+           where
+             k m m' = do { x <- m; xs <- m'; return (x:xs) }
+
+sequence_        :: Monad m => [m a] -> m () 
+{-# INLINE sequence_ #-}
+sequence_ ms     =  foldr (>>) (return ()) ms
+
+mapM            :: Monad m => (a -> m b) -> [a] -> m [b]
+{-# INLINE mapM #-}
+mapM f as       =  sequence (map f as)
+
+mapM_           :: Monad m => (a -> m b) -> [a] -> m ()
+{-# INLINE mapM_ #-}
+mapM_ f as      =  sequence_ (map f as)
+\end{code}
+
+
+%*********************************************************
+%*                                                     *
 \subsection{Coercions}
 %*                                                     *
 %*********************************************************
 
 \begin{code}
-{-# SPECIALIZE fromIntegral ::
-    Int                -> Rational,
-    Integer    -> Rational,
-    Int        -> Int,
-    Int        -> Integer,
-    Int                -> Float,
-    Int                -> Double,
-    Integer    -> Int,
-    Integer    -> Integer,
-    Integer    -> Float,
-    Integer    -> Double #-}
+{-# RULES
+"fromIntegral/Int->Int"                     fromIntegral   = id :: Int     -> Int
+"fromIntegral/Integer->Integer"             fromIntegral   = id :: Integer -> Integer
+"fromIntegral/Int->Integer"                 fromIntegral   = int2Integer
+"fromIntegral/Integer->Int"                 fromIntegral   = integer2Int
+"fromIntegral/Int->Rational"     forall n . fromIntegral n = int2Integer n :% 1
+"fromIntegral/Integer->Rational" forall n . fromIntegral n = n :% (1 :: Integer)
+"fromIntegral/Int->Float"                   fromIntegral   = int2Float
+"fromIntegral/Int->Double"                  fromIntegral   = int2Double
+"fromIntegral/Integer->Float"    forall n . fromIntegral n = encodeFloat n 0 :: Float
+"fromIntegral/Integer->Double"   forall n . fromIntegral n = encodeFloat n 0 :: Double
+ #-}
 fromIntegral   :: (Integral a, Num b) => a -> b
 fromIntegral   =  fromInteger . toInteger
 
-{-# SPECIALIZE realToFrac ::
-    Double     -> Rational, 
-    Rational   -> Double,
-    Float      -> Rational,
-    Rational   -> Float,
-    Rational   -> Rational,
-    Double     -> Double,
-    Double     -> Float,
-    Float      -> Float,
-    Float      -> Double #-}
+{-# RULES
+"realToFrac/Float->Double"      realToFrac = floatToDouble
+"realToFrac/Double->Float"      realToFrac = doubleToFloat
+"realToFrac/Float->Float"       realToFrac = id      :: Float    -> Float
+"realToFrac/Double->Double"     realToFrac = id      :: Double   -> Double
+"realToFrac/Rational->Rational" realToFrac = id      :: Rational -> Rational
+"realToFrac/Float->Rational"    realToFrac = rf2rat  :: Float    -> Rational
+"realToFrac/Double->Rational"   realToFrac = rf2rat  :: Double   -> Rational
+"realToFrac/Rational->Float"    realToFrac = fromRat :: Rational -> Float
+"realToFrac/Rational->Double"   realToFrac = fromRat :: Rational -> Double
+ #-}
 realToFrac     :: (Real a, Fractional b) => a -> b
 realToFrac     =  fromRational . toRational
+
+doubleToFloat :: Double -> Float
+doubleToFloat (D# d) = F# (double2Float# d)
+
+floatToDouble :: Float -> Double
+floatToDouble (F# f) = D# (float2Double# f)
+
+{-# SPECIALIZE rf2rat ::
+    Float  -> Rational,
+    Double -> Rational
+ #-}
+rf2rat :: RealFloat a => a -> Rational
+rf2rat x = if n >= 0 then (m * (b ^ n)) :% 1 else m :% (b ^ (-n))
+   where (m,n) = decodeFloat x
+         b     = floatRadix  x
 \end{code}