[project @ 2001-08-04 06:11:24 by ken]
[ghc-hetmet.git] / ghc / lib / std / Prelude.lhs
index 0866192..ebe7b82 100644 (file)
@@ -1,5 +1,5 @@
 % ------------------------------------------------------------------------------
-% $Id: Prelude.lhs,v 1.24 2001/02/22 16:48:24 qrczak Exp $
+% $Id: Prelude.lhs,v 1.26 2001/05/18 16:54:05 simonmar Exp $
 %
 % (c) The University of Glasgow, 1992-2000
 %
@@ -28,10 +28,12 @@ module Prelude (
     showChar, showString, readParen, showParen,
     
         -- Everything corresponding to the Report's PreludeIO
-    FilePath, IOError,
     ioError, userError, catch,
-    putChar, putStr, putStrLn, print,
-    getChar, getLine, getContents, interact,
+    FilePath, IOError,
+    putChar,
+    putStr, putStrLn, print,
+    getChar,
+    getLine, getContents, interact,
     readFile, writeFile, appendFile, readIO, readLn,
 
     Bool(..),
@@ -75,6 +77,8 @@ module Prelude (
 
   ) where
 
+import Monad
+
 import PrelBase
 import PrelList
 #ifndef USE_REPORT_PRELUDE
@@ -92,9 +96,8 @@ import PrelTup
 import PrelMaybe
 import PrelShow
 import PrelConc
-import PrelErr   ( error )
+import PrelErr   ( error, undefined )
 
-infixr 1 =<<
 infixr 0 $!
 \end{code}
 
@@ -108,13 +111,6 @@ infixr 0 $!
 \begin{code}
 ($!)    :: (a -> b) -> a -> b
 f $! x  = x `seq` f x
-
--- It is expected that compilers will recognize this and insert error
--- messages which are more appropriate to the context in which undefined 
--- appears. 
-
-undefined               :: a
-undefined               =  error "Prelude.undefined"
 \end{code}
 
 
@@ -149,86 +145,3 @@ product    l       = prod l 1
 #endif
 \end{code}
 
-
-%*********************************************************
-%*                                                     *
-\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}
-{-# 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
-
-{-# 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}