[project @ 2001-03-23 16:36:20 by simonmar]
[ghc-hetmet.git] / ghc / lib / std / Prelude.lhs
1 % ------------------------------------------------------------------------------
2 % $Id: Prelude.lhs,v 1.25 2001/02/28 00:01:03 qrczak Exp $
3 %
4 % (c) The University of Glasgow, 1992-2000
5 %
6
7 \section[Prelude]{Module @Prelude@}
8
9 We add the option -fno-implicit-prelude here to tell the reader that
10 special names such as () and -> shouldn't be resolved to Prelude.()
11 and Prelude.-> (as they are normally). -- SDM 8/10/97
12
13 \begin{code}
14 {-# OPTIONS -fno-implicit-prelude #-}
15
16 module Prelude (
17
18         -- Everything corresponding to the Report's PreludeList
19     module PrelList, 
20     lines, words, unlines, unwords,
21     sum, product,
22
23         -- Everything corresponding to the Report's PreludeText
24     ReadS, ShowS,
25     Read(readsPrec, readList),
26     Show(showsPrec, showList, show),
27     reads, shows, read, lex, 
28     showChar, showString, readParen, showParen,
29     
30         -- Everything corresponding to the Report's PreludeIO
31     FilePath, IOError,
32     ioError, userError, catch,
33     putChar, putStr, putStrLn, print,
34     getChar, getLine, getContents, interact,
35     readFile, writeFile, appendFile, readIO, readLn,
36
37     Bool(..),
38     Maybe(..),
39     Either(..),
40     Ordering(..), 
41     Char, String, Int, Integer, Float, Double, IO,
42     Rational,
43     []((:), []),
44     
45     module PrelTup,
46         -- Includes tuple types + fst, snd, curry, uncurry
47     ()(..),             -- The unit type
48     (->),               -- functions
49     
50     Eq(..),
51     Ord(..), 
52     Enum(..),
53     Bounded(..), 
54     Num(..),
55     Real(..),
56     Integral(..),
57     Fractional(..),
58     Floating(..),
59     RealFrac(..),
60     RealFloat(..),
61
62         -- Monad stuff, from PrelBase, and defined here
63     Monad(..),
64     Functor(..), 
65     mapM, mapM_, sequence, sequence_, (=<<),
66
67     maybe, either,
68     (&&), (||), not, otherwise,
69     subtract, even, odd, gcd, lcm, (^), (^^), 
70     fromIntegral, realToFrac,
71     --exported by PrelTup: fst, snd, curry, uncurry,
72     id, const, (.), flip, ($), until,
73     asTypeOf, error, undefined,
74     seq, ($!)
75
76   ) where
77
78 import PrelBase
79 import PrelList
80 #ifndef USE_REPORT_PRELUDE
81      hiding ( takeUInt_append )
82 #endif
83 import PrelIO
84 import PrelIOBase
85 import PrelException
86 import PrelRead
87 import PrelEnum
88 import PrelNum
89 import PrelReal
90 import PrelFloat
91 import PrelTup
92 import PrelMaybe
93 import PrelShow
94 import PrelConc
95 import PrelErr   ( error )
96
97 infixr 1 =<<
98 infixr 0 $!
99 \end{code}
100
101
102 %*********************************************************
103 %*                                                      *
104 \subsection{Miscellaneous functions}
105 %*                                                      *
106 %*********************************************************
107
108 \begin{code}
109 ($!)    :: (a -> b) -> a -> b
110 f $! x  = x `seq` f x
111
112 -- It is expected that compilers will recognize this and insert error
113 -- messages which are more appropriate to the context in which undefined 
114 -- appears. 
115
116 undefined               :: a
117 undefined               =  error "Prelude.undefined"
118 \end{code}
119
120
121 %*********************************************************
122 %*                                                      *
123 \subsection{List sum and product}
124 %*                                                      *
125 %*********************************************************
126
127 List sum and product are defined here because PrelList is too far
128 down the compilation chain to "see" the Num class.
129
130 \begin{code}
131 -- sum and product compute the sum or product of a finite list of numbers.
132 {-# SPECIALISE sum     :: [Int] -> Int #-}
133 {-# SPECIALISE sum     :: [Integer] -> Integer #-}
134 {-# SPECIALISE product :: [Int] -> Int #-}
135 {-# SPECIALISE product :: [Integer] -> Integer #-}
136 sum, product            :: (Num a) => [a] -> a
137 #ifdef USE_REPORT_PRELUDE
138 sum                     =  foldl (+) 0  
139 product                 =  foldl (*) 1
140 #else
141 sum     l       = sum' l 0
142   where
143     sum' []     a = a
144     sum' (x:xs) a = sum' xs (a+x)
145 product l       = prod l 1
146   where
147     prod []     a = a
148     prod (x:xs) a = prod xs (a*x)
149 #endif
150 \end{code}
151
152
153 %*********************************************************
154 %*                                                      *
155 \subsection{Prelude monad functions}
156 %*                                                      *
157 %*********************************************************
158
159 \begin{code}
160 {-# SPECIALISE (=<<) :: (a -> [b]) -> [a] -> [b] #-}
161 (=<<)           :: Monad m => (a -> m b) -> m a -> m b
162 f =<< x         = x >>= f
163
164 sequence       :: Monad m => [m a] -> m [a] 
165 {-# INLINE sequence #-}
166 sequence ms = foldr k (return []) ms
167             where
168               k m m' = do { x <- m; xs <- m'; return (x:xs) }
169
170 sequence_        :: Monad m => [m a] -> m () 
171 {-# INLINE sequence_ #-}
172 sequence_ ms     =  foldr (>>) (return ()) ms
173
174 mapM            :: Monad m => (a -> m b) -> [a] -> m [b]
175 {-# INLINE mapM #-}
176 mapM f as       =  sequence (map f as)
177
178 mapM_           :: Monad m => (a -> m b) -> [a] -> m ()
179 {-# INLINE mapM_ #-}
180 mapM_ f as      =  sequence_ (map f as)
181 \end{code}