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