7250ef4810c888d257ad7ab8d7dded1eaa587dcb
[ghc-base.git] / System / IO / Error.hs
1 {-# OPTIONS -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 #endif
46     ioeGetErrorString,          -- :: IOError -> String
47     ioeGetHandle,               -- :: IOError -> Maybe Handle
48     ioeGetFileName,             -- :: IOError -> Maybe FilePath
49
50 #ifndef __NHC__
51     ioeSetErrorType,            -- :: IOError -> IOErrorType -> IOError
52     ioeSetErrorString,          -- :: IOError -> String -> IOError
53     ioeSetHandle,               -- :: IOError -> Handle -> IOError
54     ioeSetFileName,             -- :: IOError -> FilePath -> IOError
55 #endif
56
57     -- * Types of I\/O error
58     IOErrorType,                -- abstract
59
60     alreadyExistsErrorType,     -- :: IOErrorType
61     doesNotExistErrorType,
62     alreadyInUseErrorType,
63     fullErrorType,
64     eofErrorType,
65     illegalOperationErrorType, 
66     permissionErrorType,
67     userErrorType,
68
69     -- ** 'IOErrorType' predicates
70     isAlreadyExistsErrorType,   -- :: IOErrorType -> Bool
71     isDoesNotExistErrorType,
72     isAlreadyInUseErrorType,
73     isFullErrorType, 
74     isEOFErrorType,
75     isIllegalOperationErrorType, 
76     isPermissionErrorType,
77     isUserErrorType, 
78
79     -- * Throwing and catching I\/O errors
80
81     ioError,                    -- :: IOError -> IO a
82
83     catch,                      -- :: IO a -> (IOError -> IO a) -> IO a
84     try,                        -- :: IO a -> IO (Either IOError a)
85
86 #ifndef __NHC__
87     modifyIOError,              -- :: (IOError -> IOError) -> IO a -> IO a
88 #endif
89   ) where
90
91 import Data.Either
92 import Data.Maybe
93
94 #ifdef __GLASGOW_HASKELL__
95 import GHC.Base
96 import GHC.IOBase
97 import GHC.Exception
98 import Text.Show
99 #endif
100
101 #ifdef __HUGS__
102 import Hugs.Prelude(Handle, IOException(..), IOErrorType(..))
103 #endif
104
105 #ifdef __NHC__
106 import IO
107   ( IOError ()
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 Data.Maybe (fromJust)
124 --import Control.Monad (MonadPlus(mplus))
125 #endif
126
127 -- | The construct 'try' @comp@ exposes IO errors which occur within a
128 -- computation, and which are not fully handled.
129 --
130 -- Non-I\/O exceptions are not caught by this variant; to catch all
131 -- exceptions, use 'Control.Exception.try' from "Control.Exception".
132
133 #ifndef __NHC__
134 try            :: IO a -> IO (Either IOError a)
135 try f          =  catch (do r <- f
136                             return (Right r))
137                         (return . Left)
138 #endif
139
140 #if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
141 -- -----------------------------------------------------------------------------
142 -- Constructing an IOError
143
144 -- | Construct an 'IOError' of the given type where the second argument
145 -- describes the error location and the third and fourth argument
146 -- contain the file handle and file path of the file involved in the
147 -- error if applicable.
148 mkIOError :: IOErrorType -> String -> Maybe Handle -> Maybe FilePath -> IOError
149 mkIOError t location maybe_hdl maybe_filename =
150                IOError{ ioe_type = t, 
151                         ioe_location = location,
152                         ioe_description = "",
153                         ioe_handle = maybe_hdl, 
154                         ioe_filename = maybe_filename
155                         }
156 #ifdef __NHC__
157 mkIOError EOF       location maybe_hdl maybe_filename =
158     EOFError location (fromJust maybe_hdl)
159 mkIOError UserError location maybe_hdl maybe_filename =
160     UserError location ""
161 mkIOError t         location maybe_hdl maybe_filename =
162     NHC.FFI.mkIOError location maybe_filename maybe_handle (ioeTypeToInt t)
163   where
164     ioeTypeToInt AlreadyExists     = fromEnum EEXIST
165     ioeTypeToInt NoSuchThing       = fromEnum ENOENT
166     ioeTypeToInt ResourceBusy      = fromEnum EBUSY
167     ioeTypeToInt ResourceExhausted = fromEnum ENOSPC
168     ioeTypeToInt IllegalOperation  = fromEnum EPERM
169     ioeTypeToInt PermissionDenied  = fromEnum EACCES
170 #endif
171 #endif /* __GLASGOW_HASKELL__ || __HUGS__ */
172
173 #ifndef __NHC__
174 -- -----------------------------------------------------------------------------
175 -- IOErrorType
176
177 -- | An error indicating that an 'IO' operation failed because
178 -- one of its arguments already exists.
179 isAlreadyExistsError :: IOError -> Bool
180 isAlreadyExistsError = isAlreadyExistsErrorType    . ioeGetErrorType
181
182 -- | An error indicating that an 'IO' operation failed because
183 -- one of its arguments does not exist.
184 isDoesNotExistError :: IOError -> Bool
185 isDoesNotExistError  = isDoesNotExistErrorType     . ioeGetErrorType
186
187 -- | An error indicating that an 'IO' operation failed because
188 -- one of its arguments is a single-use resource, which is already
189 -- being used (for example, opening the same file twice for writing
190 -- might give this error).
191 isAlreadyInUseError :: IOError -> Bool
192 isAlreadyInUseError  = isAlreadyInUseErrorType     . ioeGetErrorType
193
194 -- | An error indicating that an 'IO' operation failed because
195 -- the device is full.
196 isFullError         :: IOError -> Bool
197 isFullError          = isFullErrorType             . ioeGetErrorType
198
199 -- | An error indicating that an 'IO' operation failed because
200 -- the end of file has been reached.
201 isEOFError          :: IOError -> Bool
202 isEOFError           = isEOFErrorType              . ioeGetErrorType
203
204 -- | An error indicating that an 'IO' operation failed because
205 -- the operation was not possible.
206 -- Any computation which returns an 'IO' result may fail with
207 -- 'isIllegalOperation'.  In some cases, an implementation will not be
208 -- able to distinguish between the possible error causes.  In this case
209 -- it should fail with 'isIllegalOperation'.
210 isIllegalOperation  :: IOError -> Bool
211 isIllegalOperation   = isIllegalOperationErrorType . ioeGetErrorType
212
213 -- | An error indicating that an 'IO' operation failed because
214 -- the user does not have sufficient operating system privilege
215 -- to perform that operation.
216 isPermissionError   :: IOError -> Bool
217 isPermissionError    = isPermissionErrorType       . ioeGetErrorType
218
219 -- | A programmer-defined error value constructed using 'userError'.
220 isUserError         :: IOError -> Bool
221 isUserError          = isUserErrorType             . ioeGetErrorType
222 #endif /* __NHC__ */
223
224 -- -----------------------------------------------------------------------------
225 -- IOErrorTypes
226
227 #ifdef __NHC__
228 data IOErrorType = AlreadyExists | NoSuchThing | ResourceBusy
229                  | ResourceExhausted | EOF | IllegalOperation
230                  | PermissionDenied | UserError
231 #endif
232
233 -- | I\/O error where the operation failed because one of its arguments
234 -- already exists.
235 alreadyExistsErrorType   :: IOErrorType
236 alreadyExistsErrorType    = AlreadyExists
237
238 -- | I\/O error where the operation failed because one of its arguments
239 -- does not exist.
240 doesNotExistErrorType    :: IOErrorType
241 doesNotExistErrorType     = NoSuchThing
242
243 -- | I\/O error where the operation failed because one of its arguments
244 -- is a single-use resource, which is already being used.
245 alreadyInUseErrorType    :: IOErrorType
246 alreadyInUseErrorType     = ResourceBusy
247
248 -- | I\/O error where the operation failed because the device is full.
249 fullErrorType            :: IOErrorType
250 fullErrorType             = ResourceExhausted
251
252 -- | I\/O error where the operation failed because the end of file has
253 -- been reached.
254 eofErrorType             :: IOErrorType
255 eofErrorType              = EOF
256
257 -- | I\/O error where the operation is not possible.
258 illegalOperationErrorType :: IOErrorType
259 illegalOperationErrorType = IllegalOperation
260
261 -- | I\/O error where the operation failed because the user does not
262 -- have sufficient operating system privilege to perform that operation.
263 permissionErrorType      :: IOErrorType
264 permissionErrorType       = PermissionDenied
265
266 -- | I\/O error that is programmer-defined.
267 userErrorType            :: IOErrorType
268 userErrorType             = UserError
269
270 -- -----------------------------------------------------------------------------
271 -- IOErrorType predicates
272
273 -- | I\/O error where the operation failed because one of its arguments
274 -- already exists.
275 isAlreadyExistsErrorType :: IOErrorType -> Bool
276 isAlreadyExistsErrorType AlreadyExists = True
277 isAlreadyExistsErrorType _ = False
278
279 -- | I\/O error where the operation failed because one of its arguments
280 -- does not exist.
281 isDoesNotExistErrorType :: IOErrorType -> Bool
282 isDoesNotExistErrorType NoSuchThing = True
283 isDoesNotExistErrorType _ = False
284
285 -- | I\/O error where the operation failed because one of its arguments
286 -- is a single-use resource, which is already being used.
287 isAlreadyInUseErrorType :: IOErrorType -> Bool
288 isAlreadyInUseErrorType ResourceBusy = True
289 isAlreadyInUseErrorType _ = False
290
291 -- | I\/O error where the operation failed because the device is full.
292 isFullErrorType :: IOErrorType -> Bool
293 isFullErrorType ResourceExhausted = True
294 isFullErrorType _ = False
295
296 -- | I\/O error where the operation failed because the end of file has
297 -- been reached.
298 isEOFErrorType :: IOErrorType -> Bool
299 isEOFErrorType EOF = True
300 isEOFErrorType _ = False
301
302 -- | I\/O error where the operation is not possible.
303 isIllegalOperationErrorType :: IOErrorType -> Bool
304 isIllegalOperationErrorType IllegalOperation = True
305 isIllegalOperationErrorType _ = False
306
307 -- | I\/O error where the operation failed because the user does not
308 -- have sufficient operating system privilege to perform that operation.
309 isPermissionErrorType :: IOErrorType -> Bool
310 isPermissionErrorType PermissionDenied = True
311 isPermissionErrorType _ = False
312
313 -- | I\/O error that is programmer-defined.
314 isUserErrorType :: IOErrorType -> Bool
315 isUserErrorType UserError = True
316 isUserErrorType _ = False
317
318 -- -----------------------------------------------------------------------------
319 -- Miscellaneous
320
321 #if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
322 ioeGetErrorType       :: IOError -> IOErrorType
323 ioeGetErrorString     :: IOError -> String
324 ioeGetHandle          :: IOError -> Maybe Handle
325 ioeGetFileName        :: IOError -> Maybe FilePath
326
327 ioeGetErrorType ioe = ioe_type ioe
328
329 ioeGetErrorString ioe
330    | isUserErrorType (ioe_type ioe) = ioe_description ioe
331    | otherwise                      = show (ioe_type ioe)
332
333 ioeGetHandle ioe = ioe_handle ioe
334
335 ioeGetFileName ioe = ioe_filename ioe
336
337 ioeSetErrorType         :: IOError -> IOErrorType -> IOError
338 ioeSetErrorString       :: IOError -> String      -> IOError
339 ioeSetHandle            :: IOError -> Handle      -> IOError
340 ioeSetFileName          :: IOError -> FilePath    -> IOError
341
342 ioeSetErrorType   ioe errtype  = ioe{ ioe_type = errtype }
343 ioeSetErrorString ioe str      = ioe{ ioe_description = str }
344 ioeSetHandle      ioe hdl      = ioe{ ioe_handle = Just hdl }
345 ioeSetFileName    ioe filename = ioe{ ioe_filename = Just filename }
346
347 -- | Catch any 'IOError' that occurs in the computation and throw a
348 -- modified version.
349 modifyIOError :: (IOError -> IOError) -> IO a -> IO a
350 modifyIOError f io = catch io (\e -> ioError (f e))
351
352 -- -----------------------------------------------------------------------------
353 -- annotating an IOError
354
355 -- | Adds a location description and maybe a file path and file handle
356 -- to an 'IOError'.  If any of the file handle or file path is not given
357 -- the corresponding value in the 'IOError' remains unaltered.
358 annotateIOError :: IOError 
359               -> String 
360               -> Maybe Handle 
361               -> Maybe FilePath 
362               -> IOError 
363 annotateIOError (IOError ohdl errTy _ str opath) loc hdl path = 
364   IOError (hdl `mplus` ohdl) errTy loc str (path `mplus` opath)
365   where
366     Nothing `mplus` ys = ys
367     xs      `mplus` _  = xs
368 #endif /* __GLASGOW_HASKELL__ || __HUGS__ */
369
370 #if 0 /*__NHC__*/
371 annotateIOError (IOError msg file hdl code) msg' file' hdl' =
372     IOError (msg++'\n':msg') (file`mplus`file') (hdl`mplus`hdl') code
373 annotateIOError (EOFError msg hdl) msg' file' hdl' =
374     EOFError (msg++'\n':msg') (hdl`mplus`hdl')
375 annotateIOError (UserError loc msg) msg' file' hdl' =
376     UserError loc (msg++'\n':msg')
377 annotateIOError (PatternError loc) msg' file' hdl' =
378     PatternError (loc++'\n':msg')
379 #endif