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