split most of Control.Exception into new Control.Exception.Base
[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 Data.Either
95 #endif
96 import Data.Maybe
97
98 #ifdef __GLASGOW_HASKELL__
99 import {-# SOURCE #-} Prelude (catch)
100
101 import GHC.Base
102 import GHC.IOBase
103 import Text.Show
104 #endif
105
106 #ifdef __HUGS__
107 import Hugs.Prelude(Handle, IOException(..), IOErrorType(..), IO)
108 #endif
109
110 #ifdef __NHC__
111 import IO
112   ( IOError ()
113   , try
114   , ioError
115   , userError
116   , isAlreadyExistsError        -- :: IOError -> Bool
117   , isDoesNotExistError
118   , isAlreadyInUseError
119   , isFullError
120   , isEOFError
121   , isIllegalOperation
122   , isPermissionError
123   , isUserError
124   , ioeGetErrorString           -- :: IOError -> String
125   , ioeGetHandle                -- :: IOError -> Maybe Handle
126   , ioeGetFileName              -- :: IOError -> Maybe FilePath
127   )
128 --import Data.Maybe (fromJust)
129 --import Control.Monad (MonadPlus(mplus))
130 #endif
131
132 -- | The construct 'try' @comp@ exposes IO errors which occur within a
133 -- computation, and which are not fully handled.
134 --
135 -- Non-I\/O exceptions are not caught by this variant; to catch all
136 -- exceptions, use 'Control.Exception.try' from "Control.Exception".
137
138 #ifndef __NHC__
139 try            :: IO a -> IO (Either IOError a)
140 try f          =  catch (do r <- f
141                             return (Right r))
142                         (return . Left)
143 #endif
144
145 #if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
146 -- -----------------------------------------------------------------------------
147 -- Constructing an IOError
148
149 -- | Construct an 'IOError' of the given type where the second argument
150 -- describes the error location and the third and fourth argument
151 -- contain the file handle and file path of the file involved in the
152 -- error if applicable.
153 mkIOError :: IOErrorType -> String -> Maybe Handle -> Maybe FilePath -> IOError
154 mkIOError t location maybe_hdl maybe_filename =
155                IOError{ ioe_type = t, 
156                         ioe_location = location,
157                         ioe_description = "",
158                         ioe_handle = maybe_hdl, 
159                         ioe_filename = maybe_filename
160                         }
161 #ifdef __NHC__
162 mkIOError EOF       location maybe_hdl maybe_filename =
163     EOFError location (fromJust maybe_hdl)
164 mkIOError UserError location maybe_hdl maybe_filename =
165     UserError location ""
166 mkIOError t         location maybe_hdl maybe_filename =
167     NHC.FFI.mkIOError location maybe_filename maybe_handle (ioeTypeToInt t)
168   where
169     ioeTypeToInt AlreadyExists     = fromEnum EEXIST
170     ioeTypeToInt NoSuchThing       = fromEnum ENOENT
171     ioeTypeToInt ResourceBusy      = fromEnum EBUSY
172     ioeTypeToInt ResourceExhausted = fromEnum ENOSPC
173     ioeTypeToInt IllegalOperation  = fromEnum EPERM
174     ioeTypeToInt PermissionDenied  = fromEnum EACCES
175 #endif
176 #endif /* __GLASGOW_HASKELL__ || __HUGS__ */
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 -- | Catch any 'IOError' that occurs in the computation and throw a
358 -- modified version.
359 modifyIOError :: (IOError -> IOError) -> IO a -> IO a
360 modifyIOError f io = catch io (\e -> ioError (f e))
361
362 -- -----------------------------------------------------------------------------
363 -- annotating an IOError
364
365 -- | Adds a location description and maybe a file path and file handle
366 -- to an 'IOError'.  If any of the file handle or file path is not given
367 -- the corresponding value in the 'IOError' remains unaltered.
368 annotateIOError :: IOError 
369               -> String 
370               -> Maybe Handle 
371               -> Maybe FilePath 
372               -> IOError 
373 annotateIOError (IOError ohdl errTy _ str opath) loc hdl path = 
374   IOError (hdl `mplus` ohdl) errTy loc str (path `mplus` opath)
375   where
376     Nothing `mplus` ys = ys
377     xs      `mplus` _  = xs
378 #endif /* __GLASGOW_HASKELL__ || __HUGS__ */
379
380 #if 0 /*__NHC__*/
381 annotateIOError (IOError msg file hdl code) msg' file' hdl' =
382     IOError (msg++'\n':msg') (file`mplus`file') (hdl`mplus`hdl') code
383 annotateIOError (EOFError msg hdl) msg' file' hdl' =
384     EOFError (msg++'\n':msg') (hdl`mplus`hdl')
385 annotateIOError (UserError loc msg) msg' file' hdl' =
386     UserError loc (msg++'\n':msg')
387 annotateIOError (PatternError loc) msg' file' hdl' =
388     PatternError (loc++'\n':msg')
389 #endif