[project @ 2000-04-10 12:12:27 by simonpj]
[ghc-hetmet.git] / ghc / lib / std / Prelude.lhs
1 We add the option -fno-implicit-prelude here to tell the reader that
2 special names such as () and -> shouldn't be resolved to Prelude.()
3 and Prelude.-> (as they are normally). -- SDM 8/10/97
4
5 \begin{code}
6 {-# OPTIONS -fno-implicit-prelude #-}
7
8 module Prelude (
9
10         -- Everything corresponding to the Report's PreludeList
11     module PrelList, 
12     lines, words, unlines, unwords,
13     sum, product,
14
15         -- Everything corresponding to the Report's PreludeText
16     ReadS, ShowS,
17     Read(readsPrec, readList),
18     Show(showsPrec, showList, show),
19     reads, shows, read, lex, 
20     showChar, showString, readParen, showParen,
21     
22         -- Everything corresponding to the Report's PreludeIO
23     FilePath, IOError,
24     ioError, userError, catch,
25     putChar, putStr, putStrLn, print,
26     getChar, getLine, getContents, interact,
27     readFile, writeFile, appendFile, readIO, readLn,
28
29     Bool(..),
30     Maybe(..),
31     Either(..),
32     Ordering(..), 
33     Char, String, Int, Integer, Float, Double, IO,
34     Rational,
35     []((:), []),
36     
37     module PrelTup,
38         -- Includes tuple types + fst, snd, curry, uncurry
39     ()(..),             -- The unit type
40     (->),               -- functions
41     
42     Eq(..),
43     Ord(..), 
44     Enum(..),
45     Bounded(..), 
46     Num((+), (-), (*), negate, abs, signum, fromInteger),
47         -- The fromInt method is exposed only by GlaExts
48     Real(..),
49     Integral(quot, rem, div, mod, quotRem, divMod, toInteger),
50         -- The toInt method is exposed only by GlaExts
51     Fractional(..),
52     Floating(..),
53     RealFrac(..),
54     RealFloat(..),
55
56         -- Monad stuff, from PrelBase, and defined here
57     Monad(..),
58     Functor(..), 
59     mapM, mapM_, sequence, sequence_, (=<<),
60
61     maybe, either,
62     (&&), (||), not, otherwise,
63     subtract, even, odd, gcd, lcm, (^), (^^), 
64     fromIntegral, realToFrac,
65     --exported by PrelTup: fst, snd, curry, uncurry,
66     id, const, (.), flip, ($), until,
67     asTypeOf, error, undefined,
68     seq, ($!)
69
70   ) where
71
72 import PrelBase
73 import PrelList
74 #ifndef USE_REPORT_PRELUDE
75      hiding ( takeUInt_append )
76 #endif
77 import PrelIOBase
78 import PrelException
79 import PrelRead
80 import PrelEnum
81 import PrelNum
82 import PrelReal
83 import PrelFloat
84 import PrelTup
85 import PrelMaybe
86 import PrelShow
87 import PrelConc
88 import PrelErr   ( error )
89
90 infixr 1 =<<
91 infixr 0 $!
92 \end{code}
93
94
95 %*********************************************************
96 %*                                                      *
97 \subsection{Miscellaneous functions}
98 %*                                                      *
99 %*********************************************************
100
101 \begin{code}
102 ($!)    :: (a -> b) -> a -> b
103 f $! x  = x `seq` f x
104
105 -- It is expected that compilers will recognize this and insert error
106 -- messages which are more appropriate to the context in which undefined 
107 -- appears. 
108
109 undefined               :: a
110 undefined               =  error "Prelude.undefined"
111 \end{code}
112
113
114 %*********************************************************
115 %*                                                      *
116 \subsection{List sum and product}
117 %*                                                      *
118 %*********************************************************
119
120 List sum and product are defined here because PrelList is too far
121 down the compilation chain to "see" the Num class.
122
123 \begin{code}
124 -- sum and product compute the sum or product of a finite list of numbers.
125 {-# SPECIALISE sum     :: [Int] -> Int #-}
126 {-# SPECIALISE sum     :: [Integer] -> Integer #-}
127 {-# SPECIALISE product :: [Int] -> Int #-}
128 {-# SPECIALISE product :: [Integer] -> Integer #-}
129 sum, product            :: (Num a) => [a] -> a
130 #ifdef USE_REPORT_PRELUDE
131 sum                     =  foldl (+) 0  
132 product                 =  foldl (*) 1
133 #else
134 sum     l       = sum' l 0
135   where
136     sum' []     a = a
137     sum' (x:xs) a = sum' xs (a+x)
138 product l       = prod l 1
139   where
140     prod []     a = a
141     prod (x:xs) a = prod xs (a*x)
142 #endif
143 \end{code}
144
145
146 %*********************************************************
147 %*                                                      *
148 \subsection{Prelude monad functions}
149 %*                                                      *
150 %*********************************************************
151
152 \begin{code}
153 {-# SPECIALISE (=<<) :: (a -> [b]) -> [a] -> [b] #-}
154 (=<<)           :: Monad m => (a -> m b) -> m a -> m b
155 f =<< x         = x >>= f
156
157 sequence       :: Monad m => [m a] -> m [a] 
158 {-# INLINE sequence #-}
159 sequence ms = foldr k (return []) ms
160             where
161               k m m' = do { x <- m; xs <- m'; return (x:xs) }
162
163 sequence_        :: Monad m => [m a] -> m () 
164 {-# INLINE sequence_ #-}
165 sequence_ ms     =  foldr (>>) (return ()) ms
166
167 mapM            :: Monad m => (a -> m b) -> [a] -> m [b]
168 {-# INLINE mapM #-}
169 mapM f as       =  sequence (map f as)
170
171 mapM_           :: Monad m => (a -> m b) -> [a] -> m ()
172 {-# INLINE mapM_ #-}
173 mapM_ f as      =  sequence_ (map f as)
174 \end{code}
175
176
177 %*********************************************************
178 %*                                                      *
179 \subsection{Coercions}
180 %*                                                      *
181 %*********************************************************
182
183 \begin{code}
184 {-# SPECIALIZE fromIntegral ::
185     Int         -> Rational,
186     Integer     -> Rational,
187     Int         -> Int,
188     Int         -> Integer,
189     Int         -> Float,
190     Int         -> Double,
191     Integer     -> Int,
192     Integer     -> Integer,
193     Integer     -> Float,
194     Integer     -> Double #-}
195 fromIntegral    :: (Integral a, Num b) => a -> b
196 fromIntegral    =  fromInteger . toInteger
197
198 {-# SPECIALIZE realToFrac ::
199     Double      -> Rational, 
200     Rational    -> Double,
201     Float       -> Rational,
202     Rational    -> Float,
203     Rational    -> Rational,
204     Double      -> Double,
205     Double      -> Float,
206     Float       -> Float,
207     Float       -> Double #-}
208 realToFrac      :: (Real a, Fractional b) => a -> b
209 realToFrac      =  fromRational . toRational
210 \end{code}
211
212
213 %*********************************************************
214 %*                                                       *
215 \subsection{Standard IO}
216 %*                                                       *
217 %*********************************************************
218
219 The Prelude has from Day 1 provided a collection of common
220 IO functions. We define these here, but let the Prelude
221 export them.
222
223 \begin{code}
224 putChar         :: Char -> IO ()
225 putChar c       =  hPutChar stdout c
226
227 putStr          :: String -> IO ()
228 putStr s        =  hPutStr stdout s
229
230 putStrLn        :: String -> IO ()
231 putStrLn s      =  do putStr s
232                       putChar '\n'
233
234 print           :: Show a => a -> IO ()
235 print x         =  putStrLn (show x)
236
237 getChar         :: IO Char
238 getChar         =  hGetChar stdin
239
240 getLine         :: IO String
241 getLine         =  hGetLine stdin
242             
243 getContents     :: IO String
244 getContents     =  hGetContents stdin
245
246 interact        ::  (String -> String) -> IO ()
247 interact f      =   do s <- getContents
248                        putStr (f s)
249
250 readFile        :: FilePath -> IO String
251 readFile name   =  openFile name ReadMode >>= hGetContents
252
253 writeFile       :: FilePath -> String -> IO ()
254 writeFile name str = do
255     hdl <- openFile name WriteMode
256     hPutStr hdl str
257     hClose hdl
258
259 appendFile      :: FilePath -> String -> IO ()
260 appendFile name str = do
261     hdl <- openFile name AppendMode
262     hPutStr hdl str
263     hClose hdl
264
265 readLn          :: Read a => IO a
266 readLn          =  do l <- getLine
267                       r <- readIO l
268                       return r
269
270
271 \end{code}