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