1 {-# LANGUAGE Trustworthy #-}
2 {-# LANGUAGE CPP, NoImplicitPrelude #-}
4 -----------------------------------------------------------------------------
6 -- Module : Foreign.C.Error
7 -- Copyright : (c) The FFI task force 2001
8 -- License : BSD-style (see the file libraries/base/LICENSE)
10 -- Maintainer : ffi@haskell.org
11 -- Stability : provisional
12 -- Portability : portable
14 -- C-specific Marshalling support: Handling of C \"errno\" error codes.
16 -----------------------------------------------------------------------------
18 module Foreign
.C
.Error
(
20 -- * Haskell representations of @errno@ values
24 -- ** Common @errno@ symbols
25 -- | Different operating systems and\/or C libraries often support
26 -- different values of @errno@. This module defines the common values,
27 -- but due to the open definition of 'Errno' users may add definitions
28 -- which are not predefined.
29 eOK
, e2BIG
, eACCES
, eADDRINUSE
, eADDRNOTAVAIL
, eADV
, eAFNOSUPPORT
, eAGAIN
,
30 eALREADY
, eBADF
, eBADMSG
, eBADRPC
, eBUSY
, eCHILD
, eCOMM
, eCONNABORTED
,
31 eCONNREFUSED
, eCONNRESET
, eDEADLK
, eDESTADDRREQ
, eDIRTY
, eDOM
, eDQUOT
,
32 eEXIST
, eFAULT
, eFBIG
, eFTYPE
, eHOSTDOWN
, eHOSTUNREACH
, eIDRM
, eILSEQ
,
33 eINPROGRESS
, eINTR
, eINVAL
, eIO
, eISCONN
, eISDIR
, eLOOP
, eMFILE
, eMLINK
,
34 eMSGSIZE
, eMULTIHOP
, eNAMETOOLONG
, eNETDOWN
, eNETRESET
, eNETUNREACH
,
35 eNFILE
, eNOBUFS
, eNODATA
, eNODEV
, eNOENT
, eNOEXEC
, eNOLCK
, eNOLINK
,
36 eNOMEM
, eNOMSG
, eNONET
, eNOPROTOOPT
, eNOSPC
, eNOSR
, eNOSTR
, eNOSYS
,
37 eNOTBLK
, eNOTCONN
, eNOTDIR
, eNOTEMPTY
, eNOTSOCK
, eNOTSUP
, eNOTTY
, eNXIO
,
38 eOPNOTSUPP
, ePERM
, ePFNOSUPPORT
, ePIPE
, ePROCLIM
, ePROCUNAVAIL
,
39 ePROGMISMATCH
, ePROGUNAVAIL
, ePROTO
, ePROTONOSUPPORT
, ePROTOTYPE
,
40 eRANGE
, eREMCHG
, eREMOTE
, eROFS
, eRPCMISMATCH
, eRREMOTE
, eSHUTDOWN
,
41 eSOCKTNOSUPPORT
, eSPIPE
, eSRCH
, eSRMNT
, eSTALE
, eTIME
, eTIMEDOUT
,
42 eTOOMANYREFS
, eTXTBSY
, eUSERS
, eWOULDBLOCK
, eXDEV
,
44 -- ** 'Errno' functions
47 -- access to the current thread's "errno" value
52 -- conversion of an "errno" value into IO error
56 -- throw current "errno" value
60 -- ** Guards for IO operations that may fail
68 throwErrnoIfMinus1Retry
,
69 throwErrnoIfMinus1Retry_
,
71 throwErrnoIfNullRetry
,
73 throwErrnoIfRetryMayBlock
,
74 throwErrnoIfRetryMayBlock_
,
75 throwErrnoIfMinus1RetryMayBlock
,
76 throwErrnoIfMinus1RetryMayBlock_
,
77 throwErrnoIfNullRetryMayBlock
,
83 throwErrnoPathIfMinus1
,
84 throwErrnoPathIfMinus1_
,
88 -- this is were we get the CONST_XXX definitions from that configure
91 #include
"HsBaseConfig.h"
94 import Foreign
.C
.Types
95 import Foreign
.C
.String
96 import Data
.Functor
( void
)
100 import GHC
.IO.Exception
101 import GHC
.IO.Handle.Types
108 -- | Haskell representation for @errno@ values.
109 -- The implementation is deliberately exposed, to allow users to add
110 -- their own definitions of 'Errno' values.
112 newtype Errno
= Errno CInt
115 instance Eq Errno
where
116 errno1
@(Errno no1
) == errno2
@(Errno no2
)
117 | isValidErrno errno1
&& isValidErrno errno2
= no1
== no2
120 -- common "errno" symbols
122 eOK
, e2BIG
, eACCES
, eADDRINUSE
, eADDRNOTAVAIL
, eADV
, eAFNOSUPPORT
, eAGAIN
,
123 eALREADY
, eBADF
, eBADMSG
, eBADRPC
, eBUSY
, eCHILD
, eCOMM
, eCONNABORTED
,
124 eCONNREFUSED
, eCONNRESET
, eDEADLK
, eDESTADDRREQ
, eDIRTY
, eDOM
, eDQUOT
,
125 eEXIST
, eFAULT
, eFBIG
, eFTYPE
, eHOSTDOWN
, eHOSTUNREACH
, eIDRM
, eILSEQ
,
126 eINPROGRESS
, eINTR
, eINVAL
, eIO
, eISCONN
, eISDIR
, eLOOP
, eMFILE
, eMLINK
,
127 eMSGSIZE
, eMULTIHOP
, eNAMETOOLONG
, eNETDOWN
, eNETRESET
, eNETUNREACH
,
128 eNFILE
, eNOBUFS
, eNODATA
, eNODEV
, eNOENT
, eNOEXEC
, eNOLCK
, eNOLINK
,
129 eNOMEM
, eNOMSG
, eNONET
, eNOPROTOOPT
, eNOSPC
, eNOSR
, eNOSTR
, eNOSYS
,
130 eNOTBLK
, eNOTCONN
, eNOTDIR
, eNOTEMPTY
, eNOTSOCK
, eNOTSUP
, eNOTTY
, eNXIO
,
131 eOPNOTSUPP
, ePERM
, ePFNOSUPPORT
, ePIPE
, ePROCLIM
, ePROCUNAVAIL
,
132 ePROGMISMATCH
, ePROGUNAVAIL
, ePROTO
, ePROTONOSUPPORT
, ePROTOTYPE
,
133 eRANGE
, eREMCHG
, eREMOTE
, eROFS
, eRPCMISMATCH
, eRREMOTE
, eSHUTDOWN
,
134 eSOCKTNOSUPPORT
, eSPIPE
, eSRCH
, eSRMNT
, eSTALE
, eTIME
, eTIMEDOUT
,
135 eTOOMANYREFS
, eTXTBSY
, eUSERS
, eWOULDBLOCK
, eXDEV
:: Errno
137 -- the cCONST_XXX identifiers are cpp symbols whose value is computed by
141 e2BIG
= Errno
(CONST_E2BIG
)
142 eACCES
= Errno
(CONST_EACCES
)
143 eADDRINUSE
= Errno
(CONST_EADDRINUSE
)
144 eADDRNOTAVAIL
= Errno
(CONST_EADDRNOTAVAIL
)
145 eADV
= Errno
(CONST_EADV
)
146 eAFNOSUPPORT
= Errno
(CONST_EAFNOSUPPORT
)
147 eAGAIN
= Errno
(CONST_EAGAIN
)
148 eALREADY
= Errno
(CONST_EALREADY
)
149 eBADF
= Errno
(CONST_EBADF
)
150 eBADMSG
= Errno
(CONST_EBADMSG
)
151 eBADRPC
= Errno
(CONST_EBADRPC
)
152 eBUSY
= Errno
(CONST_EBUSY
)
153 eCHILD
= Errno
(CONST_ECHILD
)
154 eCOMM
= Errno
(CONST_ECOMM
)
155 eCONNABORTED
= Errno
(CONST_ECONNABORTED
)
156 eCONNREFUSED
= Errno
(CONST_ECONNREFUSED
)
157 eCONNRESET
= Errno
(CONST_ECONNRESET
)
158 eDEADLK
= Errno
(CONST_EDEADLK
)
159 eDESTADDRREQ
= Errno
(CONST_EDESTADDRREQ
)
160 eDIRTY
= Errno
(CONST_EDIRTY
)
161 eDOM
= Errno
(CONST_EDOM
)
162 eDQUOT
= Errno
(CONST_EDQUOT
)
163 eEXIST
= Errno
(CONST_EEXIST
)
164 eFAULT
= Errno
(CONST_EFAULT
)
165 eFBIG
= Errno
(CONST_EFBIG
)
166 eFTYPE
= Errno
(CONST_EFTYPE
)
167 eHOSTDOWN
= Errno
(CONST_EHOSTDOWN
)
168 eHOSTUNREACH
= Errno
(CONST_EHOSTUNREACH
)
169 eIDRM
= Errno
(CONST_EIDRM
)
170 eILSEQ
= Errno
(CONST_EILSEQ
)
171 eINPROGRESS
= Errno
(CONST_EINPROGRESS
)
172 eINTR
= Errno
(CONST_EINTR
)
173 eINVAL
= Errno
(CONST_EINVAL
)
174 eIO
= Errno
(CONST_EIO
)
175 eISCONN
= Errno
(CONST_EISCONN
)
176 eISDIR
= Errno
(CONST_EISDIR
)
177 eLOOP
= Errno
(CONST_ELOOP
)
178 eMFILE
= Errno
(CONST_EMFILE
)
179 eMLINK
= Errno
(CONST_EMLINK
)
180 eMSGSIZE
= Errno
(CONST_EMSGSIZE
)
181 eMULTIHOP
= Errno
(CONST_EMULTIHOP
)
182 eNAMETOOLONG
= Errno
(CONST_ENAMETOOLONG
)
183 eNETDOWN
= Errno
(CONST_ENETDOWN
)
184 eNETRESET
= Errno
(CONST_ENETRESET
)
185 eNETUNREACH
= Errno
(CONST_ENETUNREACH
)
186 eNFILE
= Errno
(CONST_ENFILE
)
187 eNOBUFS
= Errno
(CONST_ENOBUFS
)
188 eNODATA
= Errno
(CONST_ENODATA
)
189 eNODEV
= Errno
(CONST_ENODEV
)
190 eNOENT
= Errno
(CONST_ENOENT
)
191 eNOEXEC
= Errno
(CONST_ENOEXEC
)
192 eNOLCK
= Errno
(CONST_ENOLCK
)
193 eNOLINK
= Errno
(CONST_ENOLINK
)
194 eNOMEM
= Errno
(CONST_ENOMEM
)
195 eNOMSG
= Errno
(CONST_ENOMSG
)
196 eNONET
= Errno
(CONST_ENONET
)
197 eNOPROTOOPT
= Errno
(CONST_ENOPROTOOPT
)
198 eNOSPC
= Errno
(CONST_ENOSPC
)
199 eNOSR
= Errno
(CONST_ENOSR
)
200 eNOSTR
= Errno
(CONST_ENOSTR
)
201 eNOSYS
= Errno
(CONST_ENOSYS
)
202 eNOTBLK
= Errno
(CONST_ENOTBLK
)
203 eNOTCONN
= Errno
(CONST_ENOTCONN
)
204 eNOTDIR
= Errno
(CONST_ENOTDIR
)
205 eNOTEMPTY
= Errno
(CONST_ENOTEMPTY
)
206 eNOTSOCK
= Errno
(CONST_ENOTSOCK
)
207 eNOTSUP
= Errno
(CONST_ENOTSUP
)
209 eNOTTY
= Errno
(CONST_ENOTTY
)
210 eNXIO
= Errno
(CONST_ENXIO
)
211 eOPNOTSUPP
= Errno
(CONST_EOPNOTSUPP
)
212 ePERM
= Errno
(CONST_EPERM
)
213 ePFNOSUPPORT
= Errno
(CONST_EPFNOSUPPORT
)
214 ePIPE
= Errno
(CONST_EPIPE
)
215 ePROCLIM
= Errno
(CONST_EPROCLIM
)
216 ePROCUNAVAIL
= Errno
(CONST_EPROCUNAVAIL
)
217 ePROGMISMATCH
= Errno
(CONST_EPROGMISMATCH
)
218 ePROGUNAVAIL
= Errno
(CONST_EPROGUNAVAIL
)
219 ePROTO
= Errno
(CONST_EPROTO
)
220 ePROTONOSUPPORT
= Errno
(CONST_EPROTONOSUPPORT
)
221 ePROTOTYPE
= Errno
(CONST_EPROTOTYPE
)
222 eRANGE
= Errno
(CONST_ERANGE
)
223 eREMCHG
= Errno
(CONST_EREMCHG
)
224 eREMOTE
= Errno
(CONST_EREMOTE
)
225 eROFS
= Errno
(CONST_EROFS
)
226 eRPCMISMATCH
= Errno
(CONST_ERPCMISMATCH
)
227 eRREMOTE
= Errno
(CONST_ERREMOTE
)
228 eSHUTDOWN
= Errno
(CONST_ESHUTDOWN
)
229 eSOCKTNOSUPPORT
= Errno
(CONST_ESOCKTNOSUPPORT
)
230 eSPIPE
= Errno
(CONST_ESPIPE
)
231 eSRCH
= Errno
(CONST_ESRCH
)
232 eSRMNT
= Errno
(CONST_ESRMNT
)
233 eSTALE
= Errno
(CONST_ESTALE
)
234 eTIME
= Errno
(CONST_ETIME
)
235 eTIMEDOUT
= Errno
(CONST_ETIMEDOUT
)
236 eTOOMANYREFS
= Errno
(CONST_ETOOMANYREFS
)
237 eTXTBSY
= Errno
(CONST_ETXTBSY
)
238 eUSERS
= Errno
(CONST_EUSERS
)
239 eWOULDBLOCK
= Errno
(CONST_EWOULDBLOCK
)
240 eXDEV
= Errno
(CONST_EXDEV
)
242 -- | Yield 'True' if the given 'Errno' value is valid on the system.
243 -- This implies that the 'Eq' instance of 'Errno' is also system dependent
244 -- as it is only defined for valid values of 'Errno'.
246 isValidErrno
:: Errno
-> Bool
248 -- the configure script sets all invalid "errno"s to -1
250 isValidErrno
(Errno errno
) = errno
/= -1
253 -- access to the current thread's "errno" value
254 -- --------------------------------------------
256 -- | Get the current value of @errno@ in the current thread.
258 -- On GHC, the runtime will ensure that any Haskell thread will only see "its own"
259 -- @errno@, by saving and restoring the value when Haskell threads are scheduled
260 -- across OS threads.
263 -- We must call a C function to get the value of errno in general. On
264 -- threaded systems, errno is hidden behind a C macro so that each OS
265 -- thread gets its own copy (`saved_errno`, which `rts/Schedule.c` restores
266 -- back into the thread-local `errno` when a Haskell thread is rescheduled).
267 getErrno
= do e
<- get_errno
; return (Errno e
)
268 foreign import ccall unsafe
"HsBase.h __hscore_get_errno" get_errno
:: IO CInt
270 -- | Reset the current thread\'s @errno@ value to 'eOK'.
274 -- Again, setting errno has to be done via a C function.
275 resetErrno
= set_errno
0
276 foreign import ccall unsafe
"HsBase.h __hscore_set_errno" set_errno
:: CInt
-> IO ()
278 -- throw current "errno" value
279 -- ---------------------------
281 -- | Throw an 'IOError' corresponding to the current value of 'getErrno'.
283 throwErrno
:: String -- ^ textual description of the error location
288 ioError (errnoToIOError loc errno Nothing Nothing
)
291 -- guards for IO operations that may fail
292 -- --------------------------------------
294 -- | Throw an 'IOError' corresponding to the current value of 'getErrno'
295 -- if the result value of the 'IO' action meets the given predicate.
297 throwErrnoIf
:: (a
-> Bool) -- ^ predicate to apply to the result value
298 -- of the 'IO' operation
299 -> String -- ^ textual description of the location
300 -> IO a
-- ^ the 'IO' operation to be executed
302 throwErrnoIf
pred loc f
=
305 if pred res
then throwErrno loc
else return res
307 -- | as 'throwErrnoIf', but discards the result of the 'IO' action after
310 throwErrnoIf_
:: (a
-> Bool) -> String -> IO a
-> IO ()
311 throwErrnoIf_
pred loc f
= void
$ throwErrnoIf
pred loc f
313 -- | as 'throwErrnoIf', but retry the 'IO' action when it yields the
314 -- error code 'eINTR' - this amounts to the standard retry loop for
315 -- interrupted POSIX system calls.
317 throwErrnoIfRetry
:: (a
-> Bool) -> String -> IO a
-> IO a
318 throwErrnoIfRetry
pred loc f
=
325 then throwErrnoIfRetry
pred loc f
329 -- | as 'throwErrnoIfRetry', but additionally if the operation
330 -- yields the error code 'eAGAIN' or 'eWOULDBLOCK', an alternative
331 -- action is executed before retrying.
333 throwErrnoIfRetryMayBlock
334 :: (a
-> Bool) -- ^ predicate to apply to the result value
335 -- of the 'IO' operation
336 -> String -- ^ textual description of the location
337 -> IO a
-- ^ the 'IO' operation to be executed
338 -> IO b
-- ^ action to execute before retrying if
339 -- an immediate retry would block
341 throwErrnoIfRetryMayBlock
pred loc f on_block
=
348 then throwErrnoIfRetryMayBlock
pred loc f on_block
349 else if err
== eWOULDBLOCK || err
== eAGAIN
350 then do _
<- on_block
351 throwErrnoIfRetryMayBlock
pred loc f on_block
355 -- | as 'throwErrnoIfRetry', but discards the result.
357 throwErrnoIfRetry_
:: (a
-> Bool) -> String -> IO a
-> IO ()
358 throwErrnoIfRetry_
pred loc f
= void
$ throwErrnoIfRetry
pred loc f
360 -- | as 'throwErrnoIfRetryMayBlock', but discards the result.
362 throwErrnoIfRetryMayBlock_
:: (a
-> Bool) -> String -> IO a
-> IO b
-> IO ()
363 throwErrnoIfRetryMayBlock_
pred loc f on_block
364 = void
$ throwErrnoIfRetryMayBlock
pred loc f on_block
366 -- | Throw an 'IOError' corresponding to the current value of 'getErrno'
367 -- if the 'IO' action returns a result of @-1@.
369 throwErrnoIfMinus1
:: (Eq a
, Num a
) => String -> IO a
-> IO a
370 throwErrnoIfMinus1
= throwErrnoIf
(== -1)
372 -- | as 'throwErrnoIfMinus1', but discards the result.
374 throwErrnoIfMinus1_
:: (Eq a
, Num a
) => String -> IO a
-> IO ()
375 throwErrnoIfMinus1_
= throwErrnoIf_
(== -1)
377 -- | Throw an 'IOError' corresponding to the current value of 'getErrno'
378 -- if the 'IO' action returns a result of @-1@, but retries in case of
379 -- an interrupted operation.
381 throwErrnoIfMinus1Retry
:: (Eq a
, Num a
) => String -> IO a
-> IO a
382 throwErrnoIfMinus1Retry
= throwErrnoIfRetry
(== -1)
384 -- | as 'throwErrnoIfMinus1', but discards the result.
386 throwErrnoIfMinus1Retry_
:: (Eq a
, Num a
) => String -> IO a
-> IO ()
387 throwErrnoIfMinus1Retry_
= throwErrnoIfRetry_
(== -1)
389 -- | as 'throwErrnoIfMinus1Retry', but checks for operations that would block.
391 throwErrnoIfMinus1RetryMayBlock
:: (Eq a
, Num a
)
392 => String -> IO a
-> IO b
-> IO a
393 throwErrnoIfMinus1RetryMayBlock
= throwErrnoIfRetryMayBlock
(== -1)
395 -- | as 'throwErrnoIfMinus1RetryMayBlock', but discards the result.
397 throwErrnoIfMinus1RetryMayBlock_
:: (Eq a
, Num a
)
398 => String -> IO a
-> IO b
-> IO ()
399 throwErrnoIfMinus1RetryMayBlock_
= throwErrnoIfRetryMayBlock_
(== -1)
401 -- | Throw an 'IOError' corresponding to the current value of 'getErrno'
402 -- if the 'IO' action returns 'nullPtr'.
404 throwErrnoIfNull
:: String -> IO (Ptr a
) -> IO (Ptr a
)
405 throwErrnoIfNull
= throwErrnoIf
(== nullPtr
)
407 -- | Throw an 'IOError' corresponding to the current value of 'getErrno'
408 -- if the 'IO' action returns 'nullPtr',
409 -- but retry in case of an interrupted operation.
411 throwErrnoIfNullRetry
:: String -> IO (Ptr a
) -> IO (Ptr a
)
412 throwErrnoIfNullRetry
= throwErrnoIfRetry
(== nullPtr
)
414 -- | as 'throwErrnoIfNullRetry', but checks for operations that would block.
416 throwErrnoIfNullRetryMayBlock
:: String -> IO (Ptr a
) -> IO b
-> IO (Ptr a
)
417 throwErrnoIfNullRetryMayBlock
= throwErrnoIfRetryMayBlock
(== nullPtr
)
419 -- | as 'throwErrno', but exceptions include the given path when appropriate.
421 throwErrnoPath
:: String -> FilePath -> IO a
422 throwErrnoPath loc path
=
425 ioError (errnoToIOError loc errno Nothing
(Just path
))
427 -- | as 'throwErrnoIf', but exceptions include the given path when
430 throwErrnoPathIf
:: (a
-> Bool) -> String -> FilePath -> IO a
-> IO a
431 throwErrnoPathIf
pred loc path f
=
434 if pred res
then throwErrnoPath loc path
else return res
436 -- | as 'throwErrnoIf_', but exceptions include the given path when
439 throwErrnoPathIf_
:: (a
-> Bool) -> String -> FilePath -> IO a
-> IO ()
440 throwErrnoPathIf_
pred loc path f
= void
$ throwErrnoPathIf
pred loc path f
442 -- | as 'throwErrnoIfNull', but exceptions include the given path when
445 throwErrnoPathIfNull
:: String -> FilePath -> IO (Ptr a
) -> IO (Ptr a
)
446 throwErrnoPathIfNull
= throwErrnoPathIf
(== nullPtr
)
448 -- | as 'throwErrnoIfMinus1', but exceptions include the given path when
451 throwErrnoPathIfMinus1
:: (Eq a
, Num a
) => String -> FilePath -> IO a
-> IO a
452 throwErrnoPathIfMinus1
= throwErrnoPathIf
(== -1)
454 -- | as 'throwErrnoIfMinus1_', but exceptions include the given path when
457 throwErrnoPathIfMinus1_
:: (Eq a
, Num a
) => String -> FilePath -> IO a
-> IO ()
458 throwErrnoPathIfMinus1_
= throwErrnoPathIf_
(== -1)
460 -- conversion of an "errno" value into IO error
461 -- --------------------------------------------
463 -- | Construct an 'IOError' based on the given 'Errno' value.
464 -- The optional information can be used to improve the accuracy of
467 errnoToIOError
:: String -- ^ the location where the error occurred
468 -> Errno
-- ^ the error number
469 -> Maybe Handle -- ^ optional handle associated with the error
470 -> Maybe String -- ^ optional filename associated with the error
472 errnoToIOError loc errno maybeHdl maybeName
= unsafePerformIO
$ do
473 str
<- strerror errno
>>= peekCString
474 return (IOError maybeHdl errType loc str
(Just errno
') maybeName
)
478 | errno
== eOK
= OtherError
479 | errno
== e2BIG
= ResourceExhausted
480 | errno
== eACCES
= PermissionDenied
481 | errno
== eADDRINUSE
= ResourceBusy
482 | errno
== eADDRNOTAVAIL
= UnsupportedOperation
483 | errno
== eADV
= OtherError
484 | errno
== eAFNOSUPPORT
= UnsupportedOperation
485 | errno
== eAGAIN
= ResourceExhausted
486 | errno
== eALREADY
= AlreadyExists
487 | errno
== eBADF
= InvalidArgument
488 | errno
== eBADMSG
= InappropriateType
489 | errno
== eBADRPC
= OtherError
490 | errno
== eBUSY
= ResourceBusy
491 | errno
== eCHILD
= NoSuchThing
492 | errno
== eCOMM
= ResourceVanished
493 | errno
== eCONNABORTED
= OtherError
494 | errno
== eCONNREFUSED
= NoSuchThing
495 | errno
== eCONNRESET
= ResourceVanished
496 | errno
== eDEADLK
= ResourceBusy
497 | errno
== eDESTADDRREQ
= InvalidArgument
498 | errno
== eDIRTY
= UnsatisfiedConstraints
499 | errno
== eDOM
= InvalidArgument
500 | errno
== eDQUOT
= PermissionDenied
501 | errno
== eEXIST
= AlreadyExists
502 | errno
== eFAULT
= OtherError
503 | errno
== eFBIG
= PermissionDenied
504 | errno
== eFTYPE
= InappropriateType
505 | errno
== eHOSTDOWN
= NoSuchThing
506 | errno
== eHOSTUNREACH
= NoSuchThing
507 | errno
== eIDRM
= ResourceVanished
508 | errno
== eILSEQ
= InvalidArgument
509 | errno
== eINPROGRESS
= AlreadyExists
510 | errno
== eINTR
= Interrupted
511 | errno
== eINVAL
= InvalidArgument
512 | errno
== eIO
= HardwareFault
513 | errno
== eISCONN
= AlreadyExists
514 | errno
== eISDIR
= InappropriateType
515 | errno
== eLOOP
= InvalidArgument
516 | errno
== eMFILE
= ResourceExhausted
517 | errno
== eMLINK
= ResourceExhausted
518 | errno
== eMSGSIZE
= ResourceExhausted
519 | errno
== eMULTIHOP
= UnsupportedOperation
520 | errno
== eNAMETOOLONG
= InvalidArgument
521 | errno
== eNETDOWN
= ResourceVanished
522 | errno
== eNETRESET
= ResourceVanished
523 | errno
== eNETUNREACH
= NoSuchThing
524 | errno
== eNFILE
= ResourceExhausted
525 | errno
== eNOBUFS
= ResourceExhausted
526 | errno
== eNODATA
= NoSuchThing
527 | errno
== eNODEV
= UnsupportedOperation
528 | errno
== eNOENT
= NoSuchThing
529 | errno
== eNOEXEC
= InvalidArgument
530 | errno
== eNOLCK
= ResourceExhausted
531 | errno
== eNOLINK
= ResourceVanished
532 | errno
== eNOMEM
= ResourceExhausted
533 | errno
== eNOMSG
= NoSuchThing
534 | errno
== eNONET
= NoSuchThing
535 | errno
== eNOPROTOOPT
= UnsupportedOperation
536 | errno
== eNOSPC
= ResourceExhausted
537 | errno
== eNOSR
= ResourceExhausted
538 | errno
== eNOSTR
= InvalidArgument
539 | errno
== eNOSYS
= UnsupportedOperation
540 | errno
== eNOTBLK
= InvalidArgument
541 | errno
== eNOTCONN
= InvalidArgument
542 | errno
== eNOTDIR
= InappropriateType
543 | errno
== eNOTEMPTY
= UnsatisfiedConstraints
544 | errno
== eNOTSOCK
= InvalidArgument
545 | errno
== eNOTTY
= IllegalOperation
546 | errno
== eNXIO
= NoSuchThing
547 | errno
== eOPNOTSUPP
= UnsupportedOperation
548 | errno
== ePERM
= PermissionDenied
549 | errno
== ePFNOSUPPORT
= UnsupportedOperation
550 | errno
== ePIPE
= ResourceVanished
551 | errno
== ePROCLIM
= PermissionDenied
552 | errno
== ePROCUNAVAIL
= UnsupportedOperation
553 | errno
== ePROGMISMATCH
= ProtocolError
554 | errno
== ePROGUNAVAIL
= UnsupportedOperation
555 | errno
== ePROTO
= ProtocolError
556 | errno
== ePROTONOSUPPORT
= ProtocolError
557 | errno
== ePROTOTYPE
= ProtocolError
558 | errno
== eRANGE
= UnsupportedOperation
559 | errno
== eREMCHG
= ResourceVanished
560 | errno
== eREMOTE
= IllegalOperation
561 | errno
== eROFS
= PermissionDenied
562 | errno
== eRPCMISMATCH
= ProtocolError
563 | errno
== eRREMOTE
= IllegalOperation
564 | errno
== eSHUTDOWN
= IllegalOperation
565 | errno
== eSOCKTNOSUPPORT
= UnsupportedOperation
566 | errno
== eSPIPE
= UnsupportedOperation
567 | errno
== eSRCH
= NoSuchThing
568 | errno
== eSRMNT
= UnsatisfiedConstraints
569 | errno
== eSTALE
= ResourceVanished
570 | errno
== eTIME
= TimeExpired
571 | errno
== eTIMEDOUT
= TimeExpired
572 | errno
== eTOOMANYREFS
= ResourceExhausted
573 | errno
== eTXTBSY
= ResourceBusy
574 | errno
== eUSERS
= ResourceExhausted
575 | errno
== eWOULDBLOCK
= OtherError
576 | errno
== eXDEV
= UnsupportedOperation
577 |
otherwise = OtherError
579 foreign import ccall unsafe
"string.h" strerror
:: Errno
-> IO (Ptr CChar
)