[project @ 1996-01-18 16:33:17 by partain]
[ghc-hetmet.git] / ghc / lib / prelude / PreludeMonadicIO.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1994
3 %
4 \section[PrelMonIO]{Monadic I/O Primitives}
5
6 This module defines the basic monadic framework for Haskell 1.3 I/O. 
7
8 \begin{code}
9
10 module PreludeMonadicIO (
11     (>>), 
12     (>>=), 
13     accumulate,
14     either, 
15     fail, 
16     failWith, 
17     handle, 
18     return, 
19     sequence,
20     try,
21
22     IO(..), 
23     Either(..)
24
25     ) where
26
27 import Cls
28 import Core
29 import IChar
30 import IInt
31 import IList
32 import List             ( (++) )
33 import Prel             ( (.), not )
34 import PS               ( _PackedString, _unpackPS )
35 import Text
36 import TyArray
37 import TyComplex
38
39 import PreludeGlaST
40 import PreludeIOError
41
42 infixr 1 >>, >>=
43
44 \end{code}
45
46 \subsection[IOMonad]{The IO Monad}
47
48 I/O operations may need to indicate errors, and implementations may
49 need to handle these errors.  The $IO$ monad extends existing practice
50 by making this functionality primitive.  The exact errors which may
51 occur are defined in $PreludeIOError13$.
52
53 \begin{code}
54
55 type IO a = PrimIO (Either IOError13 a)
56
57 data Either a b =  Left a | Right b deriving (Text, Eq, Ord)
58
59 \end{code}
60
61 An expression of type $IO a$, for some type {\em a}, denotes a
62 computation whose answer is either a result of type {\em a} or an
63 <em>error</em> of type $IOError13$.  The computation succeeds with
64 result {\em succ} if its answer is $Right succ$, and fails with
65 result {\em fail} if its answer is $Left fail$.  Note that the
66 type system delimits the possibility of failure: only expressions of
67 some type $IO a$ can <em>fail</em> in the sense defined here.
68
69 \begin{code}
70
71 {-# INLINE return #-}
72 {-# INLINE failWith #-}
73
74 return   :: a       -> IO a
75 failWith :: IOError13 -> IO a
76
77 return = returnPrimIO . Right
78 failWith = returnPrimIO . Left
79
80 \end{code}
81
82 There are two primitives to create trivial computations, one for
83 each of the two possibilities, success or failure.
84
85 $return result$ is a computation that succeeds with result 
86 {\em result}.
87
88 $failWith fail$ is a computation that fails with the error 
89 {\em fail}.
90
91 \begin{code}
92
93 {-# INLINE (>>=) #-}
94
95 (>>=) :: IO a -> (a -> IO b) -> IO b 
96 m >>= k = m `thenPrimIO` \ r -> k' r
97   where
98     k' (Right x)  = k x
99     k' (Left err) = returnPrimIO (Left err)
100
101 \end{code}
102
103 The $>>=$ operation is used to sequence two computations, where the
104 second computation is parameterised on the result of the first.
105
106 \begin{code}
107
108 {-# INLINE (>>) #-}
109
110 (>>) :: IO a -> IO b -> IO b
111 m >> k = m >>= \ _ -> k
112
113 \end{code}
114
115 The restricted form of $>>=$, $>>$, is used when the result of the
116 first computation is uninteresting.
117
118 \subsection[Error-Handling]{Error Handling}
119
120 \begin{code}
121
122 handle :: IO a -> (IOError13 -> IO a) -> IO a
123 handle m k = m `thenPrimIO` \ r -> k' r
124   where
125     k' (Left err) = k err
126     k' result = returnPrimIO result
127
128 \end{code}
129
130 The construct $handle comp handler$ can be used to handle a
131 simple error during a computation {\em comp}.  Its usefulness is
132 limited in that the replacement value must be of the same type as the
133 result of {\em comp}.
134
135 \begin{code}
136
137 try :: IO a -> IO (Either IOError13 a) 
138 try p = handle (p >>= (return . Right)) (return . Left)
139
140 \end{code}
141
142 The construct $try comp$ exposes errors which occur within a
143 computation, and which are not fully handled.  It always succeeds.
144
145 \subsection[UserErrors]{User-Defined Errors}
146
147 \begin{code}
148
149 fail :: String -> IO a 
150 fail = failWith . UserError
151
152 \end{code}
153
154 As a convention for user-generated errors, to return an error message
155 $msg :: String$, return the error value $UserError msg$
156 via the computation $fail msg$.
157
158 This construct should be used instead of Haskell's $error :: String -> a$ 
159 operation wherever convenient.
160
161 \subsection[HOFs]{Higher-Order Utility Functions}
162
163 \begin{code}
164
165 either :: (a -> c) -> (b -> c) -> (Either a b) -> c
166 either kl kr x = case x of {Left a -> kl a; Right b -> kr b}
167
168 \end{code}
169
170 The construct $either a b$ can be used to generate functions on types
171 of the form $Either a b$.
172
173 \begin{code}
174
175 accumulate :: [IO a] -> IO [a] 
176
177 accumulate [] = return []
178 accumulate (f:fs) 
179   = f             >>= \ x ->
180     accumulate fs >>= \ xs ->
181     return (x:xs)
182
183 {- partain: this may be right, but I'm going w/ a more-certainly-right version
184 accumulate = foldr mcons (return [])
185   where
186     mcons :: IO a -> IO [a] -> IO [a]
187     mcons p q = p >>= \x -> q >>= \y -> return (x : y)
188 -}
189
190 \end{code}
191
192 The $accumulate$ computation is used to process a list of computations
193 of the same type, and to return a list of their results when executed
194 in sequence.
195
196 \begin{code}
197
198 sequence :: [IO a] -> IO () 
199 sequence = foldr (>>) (return ())
200
201 \end{code}
202
203 The $sequence$ computation is used for the simpler case when the
204 computations are executed entirely for their external effect, and the
205 results are therefore uninteresting.
206