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