Move some catch definitions around to avoid an import loop
[ghc-base.git] / System / IO / Error.hs
1 {-# OPTIONS_GHC -XNoImplicitPrelude #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  System.IO.Error
6 -- Copyright   :  (c) The University of Glasgow 2001
7 -- License     :  BSD-style (see the file libraries/base/LICENSE)
8 -- 
9 -- Maintainer  :  libraries@haskell.org
10 -- Stability   :  provisional
11 -- Portability :  portable
12 --
13 -- Standard IO Errors.
14 --
15 -----------------------------------------------------------------------------
16
17 module System.IO.Error (
18
19     -- * I\/O errors
20     IOError,                    -- = IOException
21
22     userError,                  -- :: String  -> IOError
23
24 #ifndef __NHC__
25     mkIOError,                  -- :: IOErrorType -> String -> Maybe Handle
26                                 --    -> Maybe FilePath -> IOError
27
28     annotateIOError,            -- :: IOError -> String -> Maybe Handle
29                                 --    -> Maybe FilePath -> IOError
30 #endif
31
32     -- ** Classifying I\/O errors
33     isAlreadyExistsError,       -- :: IOError -> Bool
34     isDoesNotExistError,
35     isAlreadyInUseError,
36     isFullError, 
37     isEOFError,
38     isIllegalOperation, 
39     isPermissionError,
40     isUserError,
41
42     -- ** Attributes of I\/O errors
43 #ifndef __NHC__
44     ioeGetErrorType,            -- :: IOError -> IOErrorType
45     ioeGetLocation,             -- :: IOError -> String
46 #endif
47     ioeGetErrorString,          -- :: IOError -> String
48     ioeGetHandle,               -- :: IOError -> Maybe Handle
49     ioeGetFileName,             -- :: IOError -> Maybe FilePath
50
51 #ifndef __NHC__
52     ioeSetErrorType,            -- :: IOError -> IOErrorType -> IOError
53     ioeSetErrorString,          -- :: IOError -> String -> IOError
54     ioeSetLocation,             -- :: IOError -> String -> IOError
55     ioeSetHandle,               -- :: IOError -> Handle -> IOError
56     ioeSetFileName,             -- :: IOError -> FilePath -> IOError
57 #endif
58
59     -- * Types of I\/O error
60     IOErrorType,                -- abstract
61
62     alreadyExistsErrorType,     -- :: IOErrorType
63     doesNotExistErrorType,
64     alreadyInUseErrorType,
65     fullErrorType,
66     eofErrorType,
67     illegalOperationErrorType, 
68     permissionErrorType,
69     userErrorType,
70
71     -- ** 'IOErrorType' predicates
72     isAlreadyExistsErrorType,   -- :: IOErrorType -> Bool
73     isDoesNotExistErrorType,
74     isAlreadyInUseErrorType,
75     isFullErrorType, 
76     isEOFErrorType,
77     isIllegalOperationErrorType, 
78     isPermissionErrorType,
79     isUserErrorType, 
80
81     -- * Throwing and catching I\/O errors
82
83     ioError,                    -- :: IOError -> IO a
84
85     catch,                      -- :: IO a -> (IOError -> IO a) -> IO a
86     try,                        -- :: IO a -> IO (Either IOError a)
87
88 #ifndef __NHC__
89     modifyIOError,              -- :: (IOError -> IOError) -> IO a -> IO a
90 #endif
91   ) where
92
93 #ifndef __HUGS__
94 import qualified Control.Exception.Base as New (catch)
95 #endif
96
97 #ifndef __HUGS__
98 import Data.Either
99 #endif
100 import Data.Maybe
101
102 #ifdef __GLASGOW_HASKELL__
103 import GHC.Base
104 import GHC.IOBase
105 import Text.Show
106 #endif
107
108 #ifdef __HUGS__
109 import Hugs.Prelude(Handle, IOException(..), IOErrorType(..), IO)
110 #endif
111
112 #ifdef __NHC__
113 import IO
114   ( IOError ()
115   , try
116   , ioError
117   , userError
118   , isAlreadyExistsError        -- :: IOError -> Bool
119   , isDoesNotExistError
120   , isAlreadyInUseError
121   , isFullError
122   , isEOFError
123   , isIllegalOperation
124   , isPermissionError
125   , isUserError
126   , ioeGetErrorString           -- :: IOError -> String
127   , ioeGetHandle                -- :: IOError -> Maybe Handle
128   , ioeGetFileName              -- :: IOError -> Maybe FilePath
129   )
130 --import Data.Maybe (fromJust)
131 --import Control.Monad (MonadPlus(mplus))
132 #endif
133
134 -- | The construct 'try' @comp@ exposes IO errors which occur within a
135 -- computation, and which are not fully handled.
136 --
137 -- Non-I\/O exceptions are not caught by this variant; to catch all
138 -- exceptions, use 'Control.Exception.try' from "Control.Exception".
139
140 #ifndef __NHC__
141 try            :: IO a -> IO (Either IOError a)
142 try f          =  catch (do r <- f
143                             return (Right r))
144                         (return . Left)
145 #endif
146
147 #if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
148 -- -----------------------------------------------------------------------------
149 -- Constructing an IOError
150
151 -- | Construct an 'IOError' of the given type where the second argument
152 -- describes the error location and the third and fourth argument
153 -- contain the file handle and file path of the file involved in the
154 -- error if applicable.
155 mkIOError :: IOErrorType -> String -> Maybe Handle -> Maybe FilePath -> IOError
156 mkIOError t location maybe_hdl maybe_filename =
157                IOError{ ioe_type = t, 
158                         ioe_location = location,
159                         ioe_description = "",
160 #if defined(__GLASGOW_HASKELL__)
161                         ioe_errno = Nothing,
162 #endif
163                         ioe_handle = maybe_hdl, 
164                         ioe_filename = maybe_filename
165                         }
166 #ifdef __NHC__
167 mkIOError EOF       location maybe_hdl maybe_filename =
168     EOFError location (fromJust maybe_hdl)
169 mkIOError UserError location maybe_hdl maybe_filename =
170     UserError location ""
171 mkIOError t         location maybe_hdl maybe_filename =
172     NHC.FFI.mkIOError location maybe_filename maybe_handle (ioeTypeToInt t)
173   where
174     ioeTypeToInt AlreadyExists     = fromEnum EEXIST
175     ioeTypeToInt NoSuchThing       = fromEnum ENOENT
176     ioeTypeToInt ResourceBusy      = fromEnum EBUSY
177     ioeTypeToInt ResourceExhausted = fromEnum ENOSPC
178     ioeTypeToInt IllegalOperation  = fromEnum EPERM
179     ioeTypeToInt PermissionDenied  = fromEnum EACCES
180 #endif
181 #endif /* __GLASGOW_HASKELL__ || __HUGS__ */
182
183 #ifndef __NHC__
184 -- -----------------------------------------------------------------------------
185 -- IOErrorType
186
187 -- | An error indicating that an 'IO' operation failed because
188 -- one of its arguments already exists.
189 isAlreadyExistsError :: IOError -> Bool
190 isAlreadyExistsError = isAlreadyExistsErrorType    . ioeGetErrorType
191
192 -- | An error indicating that an 'IO' operation failed because
193 -- one of its arguments does not exist.
194 isDoesNotExistError :: IOError -> Bool
195 isDoesNotExistError  = isDoesNotExistErrorType     . ioeGetErrorType
196
197 -- | An error indicating that an 'IO' operation failed because
198 -- one of its arguments is a single-use resource, which is already
199 -- being used (for example, opening the same file twice for writing
200 -- might give this error).
201 isAlreadyInUseError :: IOError -> Bool
202 isAlreadyInUseError  = isAlreadyInUseErrorType     . ioeGetErrorType
203
204 -- | An error indicating that an 'IO' operation failed because
205 -- the device is full.
206 isFullError         :: IOError -> Bool
207 isFullError          = isFullErrorType             . ioeGetErrorType
208
209 -- | An error indicating that an 'IO' operation failed because
210 -- the end of file has been reached.
211 isEOFError          :: IOError -> Bool
212 isEOFError           = isEOFErrorType              . ioeGetErrorType
213
214 -- | An error indicating that an 'IO' operation failed because
215 -- the operation was not possible.
216 -- Any computation which returns an 'IO' result may fail with
217 -- 'isIllegalOperation'.  In some cases, an implementation will not be
218 -- able to distinguish between the possible error causes.  In this case
219 -- it should fail with 'isIllegalOperation'.
220 isIllegalOperation  :: IOError -> Bool
221 isIllegalOperation   = isIllegalOperationErrorType . ioeGetErrorType
222
223 -- | An error indicating that an 'IO' operation failed because
224 -- the user does not have sufficient operating system privilege
225 -- to perform that operation.
226 isPermissionError   :: IOError -> Bool
227 isPermissionError    = isPermissionErrorType       . ioeGetErrorType
228
229 -- | A programmer-defined error value constructed using 'userError'.
230 isUserError         :: IOError -> Bool
231 isUserError          = isUserErrorType             . ioeGetErrorType
232 #endif /* __NHC__ */
233
234 -- -----------------------------------------------------------------------------
235 -- IOErrorTypes
236
237 #ifdef __NHC__
238 data IOErrorType = AlreadyExists | NoSuchThing | ResourceBusy
239                  | ResourceExhausted | EOF | IllegalOperation
240                  | PermissionDenied | UserError
241 #endif
242
243 -- | I\/O error where the operation failed because one of its arguments
244 -- already exists.
245 alreadyExistsErrorType   :: IOErrorType
246 alreadyExistsErrorType    = AlreadyExists
247
248 -- | I\/O error where the operation failed because one of its arguments
249 -- does not exist.
250 doesNotExistErrorType    :: IOErrorType
251 doesNotExistErrorType     = NoSuchThing
252
253 -- | I\/O error where the operation failed because one of its arguments
254 -- is a single-use resource, which is already being used.
255 alreadyInUseErrorType    :: IOErrorType
256 alreadyInUseErrorType     = ResourceBusy
257
258 -- | I\/O error where the operation failed because the device is full.
259 fullErrorType            :: IOErrorType
260 fullErrorType             = ResourceExhausted
261
262 -- | I\/O error where the operation failed because the end of file has
263 -- been reached.
264 eofErrorType             :: IOErrorType
265 eofErrorType              = EOF
266
267 -- | I\/O error where the operation is not possible.
268 illegalOperationErrorType :: IOErrorType
269 illegalOperationErrorType = IllegalOperation
270
271 -- | I\/O error where the operation failed because the user does not
272 -- have sufficient operating system privilege to perform that operation.
273 permissionErrorType      :: IOErrorType
274 permissionErrorType       = PermissionDenied
275
276 -- | I\/O error that is programmer-defined.
277 userErrorType            :: IOErrorType
278 userErrorType             = UserError
279
280 -- -----------------------------------------------------------------------------
281 -- IOErrorType predicates
282
283 -- | I\/O error where the operation failed because one of its arguments
284 -- already exists.
285 isAlreadyExistsErrorType :: IOErrorType -> Bool
286 isAlreadyExistsErrorType AlreadyExists = True
287 isAlreadyExistsErrorType _ = False
288
289 -- | I\/O error where the operation failed because one of its arguments
290 -- does not exist.
291 isDoesNotExistErrorType :: IOErrorType -> Bool
292 isDoesNotExistErrorType NoSuchThing = True
293 isDoesNotExistErrorType _ = False
294
295 -- | I\/O error where the operation failed because one of its arguments
296 -- is a single-use resource, which is already being used.
297 isAlreadyInUseErrorType :: IOErrorType -> Bool
298 isAlreadyInUseErrorType ResourceBusy = True
299 isAlreadyInUseErrorType _ = False
300
301 -- | I\/O error where the operation failed because the device is full.
302 isFullErrorType :: IOErrorType -> Bool
303 isFullErrorType ResourceExhausted = True
304 isFullErrorType _ = False
305
306 -- | I\/O error where the operation failed because the end of file has
307 -- been reached.
308 isEOFErrorType :: IOErrorType -> Bool
309 isEOFErrorType EOF = True
310 isEOFErrorType _ = False
311
312 -- | I\/O error where the operation is not possible.
313 isIllegalOperationErrorType :: IOErrorType -> Bool
314 isIllegalOperationErrorType IllegalOperation = True
315 isIllegalOperationErrorType _ = False
316
317 -- | I\/O error where the operation failed because the user does not
318 -- have sufficient operating system privilege to perform that operation.
319 isPermissionErrorType :: IOErrorType -> Bool
320 isPermissionErrorType PermissionDenied = True
321 isPermissionErrorType _ = False
322
323 -- | I\/O error that is programmer-defined.
324 isUserErrorType :: IOErrorType -> Bool
325 isUserErrorType UserError = True
326 isUserErrorType _ = False
327
328 -- -----------------------------------------------------------------------------
329 -- Miscellaneous
330
331 #if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
332 ioeGetErrorType       :: IOError -> IOErrorType
333 ioeGetErrorString     :: IOError -> String
334 ioeGetLocation        :: IOError -> String
335 ioeGetHandle          :: IOError -> Maybe Handle
336 ioeGetFileName        :: IOError -> Maybe FilePath
337
338 ioeGetErrorType ioe = ioe_type ioe
339
340 ioeGetErrorString ioe
341    | isUserErrorType (ioe_type ioe) = ioe_description ioe
342    | otherwise                      = show (ioe_type ioe)
343
344 ioeGetLocation ioe = ioe_location ioe
345
346 ioeGetHandle ioe = ioe_handle ioe
347
348 ioeGetFileName ioe = ioe_filename ioe
349
350 ioeSetErrorType   :: IOError -> IOErrorType -> IOError
351 ioeSetErrorString :: IOError -> String      -> IOError
352 ioeSetLocation    :: IOError -> String      -> IOError
353 ioeSetHandle      :: IOError -> Handle      -> IOError
354 ioeSetFileName    :: IOError -> FilePath    -> IOError
355
356 ioeSetErrorType   ioe errtype  = ioe{ ioe_type = errtype }
357 ioeSetErrorString ioe str      = ioe{ ioe_description = str }
358 ioeSetLocation    ioe str      = ioe{ ioe_location = str }
359 ioeSetHandle      ioe hdl      = ioe{ ioe_handle = Just hdl }
360 ioeSetFileName    ioe filename = ioe{ ioe_filename = Just filename }
361
362 -- | Catch any 'IOError' that occurs in the computation and throw a
363 -- modified version.
364 modifyIOError :: (IOError -> IOError) -> IO a -> IO a
365 modifyIOError f io = catch io (\e -> ioError (f e))
366
367 -- -----------------------------------------------------------------------------
368 -- annotating an IOError
369
370 -- | Adds a location description and maybe a file path and file handle
371 -- to an 'IOError'.  If any of the file handle or file path is not given
372 -- the corresponding value in the 'IOError' remains unaltered.
373 annotateIOError :: IOError 
374               -> String 
375               -> Maybe Handle 
376               -> Maybe FilePath 
377               -> IOError 
378 annotateIOError ioe loc hdl path = 
379   ioe{ ioe_handle = hdl `mplus` ioe_handle ioe,
380        ioe_location = loc, ioe_filename = path `mplus` ioe_filename ioe }
381   where
382     Nothing `mplus` ys = ys
383     xs      `mplus` _  = xs
384 #endif /* __GLASGOW_HASKELL__ || __HUGS__ */
385
386 #if 0 /*__NHC__*/
387 annotateIOError (IOError msg file hdl code) msg' file' hdl' =
388     IOError (msg++'\n':msg') (file`mplus`file') (hdl`mplus`hdl') code
389 annotateIOError (EOFError msg hdl) msg' file' hdl' =
390     EOFError (msg++'\n':msg') (hdl`mplus`hdl')
391 annotateIOError (UserError loc msg) msg' file' hdl' =
392     UserError loc (msg++'\n':msg')
393 annotateIOError (PatternError loc) msg' file' hdl' =
394     PatternError (loc++'\n':msg')
395 #endif
396
397 #ifndef __HUGS__
398 -- | The 'catch' function establishes a handler that receives any 'IOError'
399 -- raised in the action protected by 'catch'.  An 'IOError' is caught by
400 -- the most recent handler established by 'catch'.  These handlers are
401 -- not selective: all 'IOError's are caught.  Exception propagation
402 -- must be explicitly provided in a handler by re-raising any unwanted
403 -- exceptions.  For example, in
404 --
405 -- > f = catch g (\e -> if IO.isEOFError e then return [] else ioError e)
406 --
407 -- the function @f@ returns @[]@ when an end-of-file exception
408 -- (cf. 'System.IO.Error.isEOFError') occurs in @g@; otherwise, the
409 -- exception is propagated to the next outer handler.
410 --
411 -- When an exception propagates outside the main program, the Haskell
412 -- system prints the associated 'IOError' value and exits the program.
413 --
414 -- Non-I\/O exceptions are not caught by this variant; to catch all
415 -- exceptions, use 'Control.Exception.catch' from "Control.Exception".
416 catch :: IO a -> (IOError -> IO a) -> IO a
417 catch = New.catch
418 #endif /* !__HUGS__ */