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