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