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