[project @ 2001-11-14 11:35:23 by simonmar]
[ghc-hetmet.git] / ghc / lib / std / Prelude.lhs
index 8dcb1fe..79feaf8 100644 (file)
@@ -1,3 +1,11 @@
+% ------------------------------------------------------------------------------
+% $Id: Prelude.lhs,v 1.27 2001/11/14 11:15:53 simonmar 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
@@ -20,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(..),
@@ -43,11 +53,9 @@ module Prelude (
     Ord(..), 
     Enum(..),
     Bounded(..), 
-    Num((+), (-), (*), negate, abs, signum, fromInteger),
-       -- The fromInt method is exposed only by GlaExts
+    Num(..),
     Real(..),
-    Integral(quot, rem, div, mod, quotRem, divMod, toInteger),
-       -- The toInt method is exposed only by GlaExts
+    Integral(..),
     Fractional(..),
     Floating(..),
     RealFrac(..),
@@ -69,11 +77,14 @@ module Prelude (
 
   ) where
 
+import Monad
+
 import PrelBase
 import PrelList
 #ifndef USE_REPORT_PRELUDE
      hiding ( takeUInt_append )
 #endif
+import PrelIO
 import PrelIOBase
 import PrelException
 import PrelRead
@@ -84,10 +95,8 @@ import PrelFloat
 import PrelTup
 import PrelMaybe
 import PrelShow
-import PrelConc
-import PrelErr   ( error )
+import PrelErr   ( error, undefined )
 
-infixr 1 =<<
 infixr 0 $!
 \end{code}
 
@@ -101,13 +110,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}
 
 
@@ -142,130 +144,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}
-{-# SPECIALIZE fromIntegral ::
-    Int                -> Rational,
-    Integer    -> Rational,
-    Int        -> Int,
-    Int        -> Integer,
-    Int                -> Float,
-    Int                -> Double,
-    Integer    -> Int,
-    Integer    -> Integer,
-    Integer    -> Float,
-    Integer    -> 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 #-}
-realToFrac     :: (Real a, Fractional b) => a -> b
-realToFrac     =  fromRational . toRational
-\end{code}
-
-
-%*********************************************************
-%*                                                      *
-\subsection{Standard IO}
-%*                                                      *
-%*********************************************************
-
-The Prelude has from Day 1 provided a collection of common
-IO functions. We define these here, but let the Prelude
-export them.
-
-\begin{code}
-putChar         :: Char -> IO ()
-putChar c       =  hPutChar stdout c
-
-putStr          :: String -> IO ()
-putStr s        =  hPutStr stdout s
-
-putStrLn        :: String -> IO ()
-putStrLn s      =  do putStr s
-                      putChar '\n'
-
-print           :: Show a => a -> IO ()
-print x         =  putStrLn (show x)
-
-getChar         :: IO Char
-getChar         =  hGetChar stdin
-
-getLine         :: IO String
-getLine         =  hGetLine stdin
-            
-getContents     :: IO String
-getContents     =  hGetContents stdin
-
-interact        ::  (String -> String) -> IO ()
-interact f      =   do s <- getContents
-                       putStr (f s)
-
-readFile        :: FilePath -> IO String
-readFile name  =  openFile name ReadMode >>= hGetContents
-
-writeFile       :: FilePath -> String -> IO ()
-writeFile name str = do
-    hdl <- openFile name WriteMode
-    hPutStr hdl str
-    hClose hdl
-
-appendFile      :: FilePath -> String -> IO ()
-appendFile name str = do
-    hdl <- openFile name AppendMode
-    hPutStr hdl str
-    hClose hdl
-
-readLn          :: Read a => IO a
-readLn          =  do l <- getLine
-                      r <- readIO l
-                      return r
-
-
-\end{code}