83dfd7e5a1b847953cf5ffbecca0c2d5b3620fb2
[haskell-directory.git] / System / IO / Error.hs
1 {-# OPTIONS_GHC -fno-implicit-prelude #-}
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 import Data.Either
94 import Data.Maybe
95
96 #ifdef __GLASGOW_HASKELL__
97 import GHC.Base
98 import GHC.IOBase
99 import GHC.Exception
100 import Text.Show
101 #endif
102
103 #ifdef __HUGS__
104 import Hugs.Prelude(Handle, IOException(..), IOErrorType(..))
105 #endif
106
107 #ifdef __NHC__
108 import IO
109   ( IOError ()
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 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                         ioe_handle = maybe_hdl, 
156                         ioe_filename = maybe_filename
157                         }
158 #ifdef __NHC__
159 mkIOError EOF       location maybe_hdl maybe_filename =
160     EOFError location (fromJust maybe_hdl)
161 mkIOError UserError location maybe_hdl maybe_filename =
162     UserError location ""
163 mkIOError t         location maybe_hdl maybe_filename =
164     NHC.FFI.mkIOError location maybe_filename maybe_handle (ioeTypeToInt t)
165   where
166     ioeTypeToInt AlreadyExists     = fromEnum EEXIST
167     ioeTypeToInt NoSuchThing       = fromEnum ENOENT
168     ioeTypeToInt ResourceBusy      = fromEnum EBUSY
169     ioeTypeToInt ResourceExhausted = fromEnum ENOSPC
170     ioeTypeToInt IllegalOperation  = fromEnum EPERM
171     ioeTypeToInt PermissionDenied  = fromEnum EACCES
172 #endif
173 #endif /* __GLASGOW_HASKELL__ || __HUGS__ */
174
175 #ifndef __NHC__
176 -- -----------------------------------------------------------------------------
177 -- IOErrorType
178
179 -- | An error indicating that an 'IO' operation failed because
180 -- one of its arguments already exists.
181 isAlreadyExistsError :: IOError -> Bool
182 isAlreadyExistsError = isAlreadyExistsErrorType    . ioeGetErrorType
183
184 -- | An error indicating that an 'IO' operation failed because
185 -- one of its arguments does not exist.
186 isDoesNotExistError :: IOError -> Bool
187 isDoesNotExistError  = isDoesNotExistErrorType     . ioeGetErrorType
188
189 -- | An error indicating that an 'IO' operation failed because
190 -- one of its arguments is a single-use resource, which is already
191 -- being used (for example, opening the same file twice for writing
192 -- might give this error).
193 isAlreadyInUseError :: IOError -> Bool
194 isAlreadyInUseError  = isAlreadyInUseErrorType     . ioeGetErrorType
195
196 -- | An error indicating that an 'IO' operation failed because
197 -- the device is full.
198 isFullError         :: IOError -> Bool
199 isFullError          = isFullErrorType             . ioeGetErrorType
200
201 -- | An error indicating that an 'IO' operation failed because
202 -- the end of file has been reached.
203 isEOFError          :: IOError -> Bool
204 isEOFError           = isEOFErrorType              . ioeGetErrorType
205
206 -- | An error indicating that an 'IO' operation failed because
207 -- the operation was not possible.
208 -- Any computation which returns an 'IO' result may fail with
209 -- 'isIllegalOperation'.  In some cases, an implementation will not be
210 -- able to distinguish between the possible error causes.  In this case
211 -- it should fail with 'isIllegalOperation'.
212 isIllegalOperation  :: IOError -> Bool
213 isIllegalOperation   = isIllegalOperationErrorType . ioeGetErrorType
214
215 -- | An error indicating that an 'IO' operation failed because
216 -- the user does not have sufficient operating system privilege
217 -- to perform that operation.
218 isPermissionError   :: IOError -> Bool
219 isPermissionError    = isPermissionErrorType       . ioeGetErrorType
220
221 -- | A programmer-defined error value constructed using 'userError'.
222 isUserError         :: IOError -> Bool
223 isUserError          = isUserErrorType             . ioeGetErrorType
224 #endif /* __NHC__ */
225
226 -- -----------------------------------------------------------------------------
227 -- IOErrorTypes
228
229 #ifdef __NHC__
230 data IOErrorType = AlreadyExists | NoSuchThing | ResourceBusy
231                  | ResourceExhausted | EOF | IllegalOperation
232                  | PermissionDenied | UserError
233 #endif
234
235 -- | I\/O error where the operation failed because one of its arguments
236 -- already exists.
237 alreadyExistsErrorType   :: IOErrorType
238 alreadyExistsErrorType    = AlreadyExists
239
240 -- | I\/O error where the operation failed because one of its arguments
241 -- does not exist.
242 doesNotExistErrorType    :: IOErrorType
243 doesNotExistErrorType     = NoSuchThing
244
245 -- | I\/O error where the operation failed because one of its arguments
246 -- is a single-use resource, which is already being used.
247 alreadyInUseErrorType    :: IOErrorType
248 alreadyInUseErrorType     = ResourceBusy
249
250 -- | I\/O error where the operation failed because the device is full.
251 fullErrorType            :: IOErrorType
252 fullErrorType             = ResourceExhausted
253
254 -- | I\/O error where the operation failed because the end of file has
255 -- been reached.
256 eofErrorType             :: IOErrorType
257 eofErrorType              = EOF
258
259 -- | I\/O error where the operation is not possible.
260 illegalOperationErrorType :: IOErrorType
261 illegalOperationErrorType = IllegalOperation
262
263 -- | I\/O error where the operation failed because the user does not
264 -- have sufficient operating system privilege to perform that operation.
265 permissionErrorType      :: IOErrorType
266 permissionErrorType       = PermissionDenied
267
268 -- | I\/O error that is programmer-defined.
269 userErrorType            :: IOErrorType
270 userErrorType             = UserError
271
272 -- -----------------------------------------------------------------------------
273 -- IOErrorType predicates
274
275 -- | I\/O error where the operation failed because one of its arguments
276 -- already exists.
277 isAlreadyExistsErrorType :: IOErrorType -> Bool
278 isAlreadyExistsErrorType AlreadyExists = True
279 isAlreadyExistsErrorType _ = False
280
281 -- | I\/O error where the operation failed because one of its arguments
282 -- does not exist.
283 isDoesNotExistErrorType :: IOErrorType -> Bool
284 isDoesNotExistErrorType NoSuchThing = True
285 isDoesNotExistErrorType _ = False
286
287 -- | I\/O error where the operation failed because one of its arguments
288 -- is a single-use resource, which is already being used.
289 isAlreadyInUseErrorType :: IOErrorType -> Bool
290 isAlreadyInUseErrorType ResourceBusy = True
291 isAlreadyInUseErrorType _ = False
292
293 -- | I\/O error where the operation failed because the device is full.
294 isFullErrorType :: IOErrorType -> Bool
295 isFullErrorType ResourceExhausted = True
296 isFullErrorType _ = False
297
298 -- | I\/O error where the operation failed because the end of file has
299 -- been reached.
300 isEOFErrorType :: IOErrorType -> Bool
301 isEOFErrorType EOF = True
302 isEOFErrorType _ = False
303
304 -- | I\/O error where the operation is not possible.
305 isIllegalOperationErrorType :: IOErrorType -> Bool
306 isIllegalOperationErrorType IllegalOperation = True
307 isIllegalOperationErrorType _ = False
308
309 -- | I\/O error where the operation failed because the user does not
310 -- have sufficient operating system privilege to perform that operation.
311 isPermissionErrorType :: IOErrorType -> Bool
312 isPermissionErrorType PermissionDenied = True
313 isPermissionErrorType _ = False
314
315 -- | I\/O error that is programmer-defined.
316 isUserErrorType :: IOErrorType -> Bool
317 isUserErrorType UserError = True
318 isUserErrorType _ = False
319
320 -- -----------------------------------------------------------------------------
321 -- Miscellaneous
322
323 #if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
324 ioeGetErrorType       :: IOError -> IOErrorType
325 ioeGetErrorString     :: IOError -> String
326 ioeGetLocation        :: IOError -> String
327 ioeGetHandle          :: IOError -> Maybe Handle
328 ioeGetFileName        :: IOError -> Maybe FilePath
329
330 ioeGetErrorType ioe = ioe_type ioe
331
332 ioeGetErrorString ioe
333    | isUserErrorType (ioe_type ioe) = ioe_description ioe
334    | otherwise                      = show (ioe_type ioe)
335
336 ioeGetLocation ioe = ioe_location ioe
337
338 ioeGetHandle ioe = ioe_handle ioe
339
340 ioeGetFileName ioe = ioe_filename ioe
341
342 ioeSetErrorType   :: IOError -> IOErrorType -> IOError
343 ioeSetErrorString :: IOError -> String      -> IOError
344 ioeSetLocation    :: IOError -> String      -> IOError
345 ioeSetHandle      :: IOError -> Handle      -> IOError
346 ioeSetFileName    :: IOError -> FilePath    -> IOError
347
348 ioeSetErrorType   ioe errtype  = ioe{ ioe_type = errtype }
349 ioeSetErrorString ioe str      = ioe{ ioe_description = str }
350 ioeSetLocation    ioe str      = ioe{ ioe_location = str }
351 ioeSetHandle      ioe hdl      = ioe{ ioe_handle = Just hdl }
352 ioeSetFileName    ioe filename = ioe{ ioe_filename = Just filename }
353
354 -- | Catch any 'IOError' that occurs in the computation and throw a
355 -- modified version.
356 modifyIOError :: (IOError -> IOError) -> IO a -> IO a
357 modifyIOError f io = catch io (\e -> ioError (f e))
358
359 -- -----------------------------------------------------------------------------
360 -- annotating an IOError
361
362 -- | Adds a location description and maybe a file path and file handle
363 -- to an 'IOError'.  If any of the file handle or file path is not given
364 -- the corresponding value in the 'IOError' remains unaltered.
365 annotateIOError :: IOError 
366               -> String 
367               -> Maybe Handle 
368               -> Maybe FilePath 
369               -> IOError 
370 annotateIOError (IOError ohdl errTy _ str opath) loc hdl path = 
371   IOError (hdl `mplus` ohdl) errTy loc str (path `mplus` opath)
372   where
373     Nothing `mplus` ys = ys
374     xs      `mplus` _  = xs
375 #endif /* __GLASGOW_HASKELL__ || __HUGS__ */
376
377 #if 0 /*__NHC__*/
378 annotateIOError (IOError msg file hdl code) msg' file' hdl' =
379     IOError (msg++'\n':msg') (file`mplus`file') (hdl`mplus`hdl') code
380 annotateIOError (EOFError msg hdl) msg' file' hdl' =
381     EOFError (msg++'\n':msg') (hdl`mplus`hdl')
382 annotateIOError (UserError loc msg) msg' file' hdl' =
383     UserError loc (msg++'\n':msg')
384 annotateIOError (PatternError loc) msg' file' hdl' =
385     PatternError (loc++'\n':msg')
386 #endif