c5a3787059e3bf19284f45a016d024fe49fa27cc
[ghc-hetmet.git] / ghc / lib / ghc / CError.lhs
1 `%
2 % (c) The GRASP/AQUA Project, Glasgow University, 1995
3 %
4 % Last Modified: Wed Jul 19 13:12:10 1995
5 % Darren J Moffat <moffatd@dcs.gla.ac.uk>
6 %
7 % Generated from: @(#)errno.h 2.14 90/01/23 SMI; from UCB 4.1 82/12/28
8 \section[CError]{Interface to C Error Codes}
9
10 \begin{code}
11 module CError (
12     CErrorCode(..),
13
14     errorCodeToStr,     -- :: CErrorCode -> String
15     getCErrorCode,      -- :: PrimIO CErrorCode
16     setCErrorCode       -- :: CErrorCode -> PrimIO ()
17
18 ) where
19
20 import PreludeGlaST
21 \end{code}
22
23 import PreludeGlaMisc
24 import LibSystem
25 \begin{code}     
26 data CErrorCode =
27           NOERROR       -- Added as dummy value since deriving Ix starts at 0
28         | EPERM         -- Not owner
29         | ENOENT        -- No such file or directory
30         | ESRCH         -- No such process
31         | EINTR         -- Interrupted system call
32         | EIO           -- I/O error
33         | ENXIO         -- No such device or address
34         | E2BIG         -- Arg list too long
35         | ENOEXEC       -- Exec format error
36         | EBADF         -- Bad file number
37         | ECHILD        -- No children
38         | EAGAIN        -- No more processes
39         | ENOMEM        -- Not enough core
40         | EACCES        -- Permission denied
41         | EFAULT        -- Bad address
42         | ENOTBLK       -- Block device required
43         | EBUSY         -- Mount device busy
44         | EEXIST        -- File exists
45         | EXDEV         -- Cross-device link
46         | ENODEV        -- No such device
47         | ENOTDIR       -- Not a directory*/
48         | EISDIR        -- Is a directory
49         | EINVAL        -- Invalid argument
50         | ENFILE        -- File table overflow
51         | EMFILE        -- Too many open files
52         | ENOTTY        -- Not a typewriter
53         | ETXTBSY       -- Text file busy
54         | EFBIG         -- File too large
55         | ENOSPC        -- No space left on device
56         | ESPIPE        -- Illegal seek
57         | EROFS         -- Read-only file system
58         | EMLINK        -- Too many links
59         | EPIPE         -- Broken pipe
60
61 -- math software
62         | EDOM          -- Argument too large
63         | ERANGE        -- Result too large
64
65 -- non-blocking and interrupt i/o
66         | EWOULDBLOCK   -- Operation would block
67         | EINPROGRESS   -- Operation now in progress
68         | EALREADY      -- Operation already in progress
69 -- ipc/network software
70
71 -- argument errors
72         | ENOTSOCK      -- Socket operation on non-socket
73         | EDESTADDRREQ  -- Destination address required
74         | EMSGSIZE      -- Message too long
75         | EPROTOTYPE    -- Protocol wrong type for socket
76         | ENOPROTOOPT   -- Protocol not available
77         | EPROTONOSUPPOR -- Protocol not supported
78         | ESOCKTNOSUPPORT -- Socket type not supported
79         | EOPNOTSUPP    -- Operation not supported on socket
80         | EPFNOSUPPORT  -- Protocol family not supported
81         | EAFNOSUPPORT  -- Address family not supported by protocol family
82         | EADDRINUSE    -- Address already in use
83         | EADDRNOTAVAIL -- Can't assign requested address
84 -- operational errors
85         | ENETDOWN      -- Network is down
86         | ENETUNREACH   -- Network is unreachable
87         | ENETRESET     -- Network dropped connection on reset
88         | ECONNABORTED  -- Software caused connection abort
89         | ECONNRESET    -- Connection reset by peer
90         | ENOBUFS       -- No buffer space available
91         | EISCONN       -- Socket is already connected
92         | ENOTCONN      -- Socket is not connected
93         | ESHUTDOWN     -- Can't send after socket shutdown
94         | ETOOMANYREFS  -- Too many references: can't splice
95         | ETIMEDOUT     -- Connection timed out
96         | ECONNREFUSED  -- Connection refused
97
98         | ELOOP         -- Too many levels of symbolic links
99         | ENAMETOOLONG  -- File name too long
100
101 -- should be rearranged
102         | EHOSTDOWN     -- Host is down
103         | EHOSTUNREACH  -- No route to host
104         | ENOTEMPTY     -- Directory not empty
105
106 -- quotas & mush
107         | EPROCLIM      -- Too many processes
108         | EUSERS        -- Too many users
109         | EDQUOT        -- Disc quota exceeded
110
111 -- Network File System
112         | ESTALE        -- Stale NFS file handle
113         | EREMOTE       -- Too many levels of remote in path
114
115 -- streams
116         | ENOSTR        -- Device is not a stream
117         | ETIME         -- Timer expired
118         | ENOSR         -- Out of streams resources
119         | ENOMSG        -- No message of desired type
120         | EBADMSG       -- Trying to read unreadable message
121
122 -- SystemV IPC
123         | EIDRM         -- Identifier removed
124
125 -- SystemV Record Locking
126         | EDEADLK       -- Deadlock condition.
127         | ENOLCK        -- No record locks available.
128
129 -- RFS
130         | ENONET        -- Machine is not on the network
131         | ERREMOTE      -- Object is remote
132         | ENOLINK       -- the link has been severed
133         | EADV          -- advertise error
134         | ESRMNT        -- srmount error
135         | ECOMM         -- Communication error on send
136         | EPROTO        -- Protocol error
137         | EMULTIHOP     -- multihop attempted
138         | EDOTDOT       -- Cross mount point (not an error)
139         | EREMCHG       -- Remote address changed
140 -- POSIX
141         | ENOSYS        -- function not implemented
142
143         deriving (Eq,Ord,Ix,Text)
144
145
146 errorCodeToStr :: CErrorCode -> String
147 errorCodeToStr NOERROR  = ""
148 errorCodeToStr EPERM    = "Not owner"
149 errorCodeToStr ENOENT   = "No such file or directory"
150 errorCodeToStr ESRCH    = "No such process"
151 errorCodeToStr EINTR    = "Interrupted system call"
152 errorCodeToStr EIO      = "I/O error"
153 errorCodeToStr ENXIO    = "No such device or address"
154 errorCodeToStr E2BIG    = "Arg list too long"
155 errorCodeToStr ENOEXEC  = "Exec format error"
156 errorCodeToStr EBADF    = "Bad file number"
157 errorCodeToStr ECHILD   = "No children"
158 errorCodeToStr EAGAIN   = "No more processes"
159 errorCodeToStr ENOMEM   = "Not enough core"
160 errorCodeToStr EACCES   = "Permission denied"
161 errorCodeToStr EFAULT   = "Bad address"
162 errorCodeToStr ENOTBLK  = "Block device required"
163 errorCodeToStr EBUSY    = "Mount device busy"
164 errorCodeToStr EEXIST   = "File exists"
165 errorCodeToStr EXDEV    = "Cross-device link"
166 errorCodeToStr ENODEV   = "No such device"
167 errorCodeToStr ENOTDIR  = "Not a directory"
168 errorCodeToStr EISDIR   = "Is a directory"
169 errorCodeToStr EINVAL   = "Invalid argument"
170 errorCodeToStr ENFILE   = "File table overflow"
171 errorCodeToStr EMFILE   = "Too many open files"
172 errorCodeToStr ENOTTY   = "Not a typewriter"
173 errorCodeToStr ETXTBSY  = "Text file busy"
174 errorCodeToStr EFBIG    = "File too large"
175 errorCodeToStr ENOSPC   = "No space left on device"
176 errorCodeToStr ESPIPE   = "Illegal seek"
177 errorCodeToStr EROFS    = "Read-only file system"
178 errorCodeToStr EMLINK   = "Too many links"
179 errorCodeToStr EPIPE    = "Broken pipe"
180
181 -- math software
182 errorCodeToStr EDOM     = "Argument too large"
183 errorCodeToStr ERANGE   = "Result too large"
184
185 -- non-blocking and interrupt i/o"
186 errorCodeToStr EWOULDBLOCK      = "Operation would block"
187 errorCodeToStr EINPROGRESS      = "Operation now in progress"
188 errorCodeToStr EALREADY         = "Operation already in progress"
189 -- ipc/network software
190
191 -- argument errors
192 errorCodeToStr ENOTSOCK         = "Socket operation on non-socket"
193 errorCodeToStr EDESTADDRREQ     = "Destination address required"
194 errorCodeToStr EMSGSIZE         = "Message too long"
195 errorCodeToStr EPROTOTYPE       = "Protocol wrong type for socket"
196 errorCodeToStr ENOPROTOOPT      = "Protocol not available"
197 errorCodeToStr EPROTONOSUPPOR   = "Protocol not supported"
198 errorCodeToStr ESOCKTNOSUPPORT  = "Socket type not supported"
199 errorCodeToStr EOPNOTSUPP       = "Operation not supported on socket"
200 errorCodeToStr EPFNOSUPPORT     = "Protocol family not supported"
201 errorCodeToStr EAFNOSUPPORT     = "Address family not supported by protocol family"
202 errorCodeToStr EADDRINUSE       = "Address already in use"
203 errorCodeToStr EADDRNOTAVAIL    = "Can't assign requested address"
204
205 -- operational errors
206 errorCodeToStr ENETDOWN         = "Network is down"
207 errorCodeToStr ENETUNREACH      = "Network is unreachable"
208 errorCodeToStr ENETRESET        = "Network dropped connection on reset"
209 errorCodeToStr ECONNABORTED     = "Software caused connection abort"
210 errorCodeToStr ECONNRESET       = "Connection reset by peer"
211 errorCodeToStr ENOBUFS          = "No buffer space available"
212 errorCodeToStr EISCONN          = "Socket is already connected"
213 errorCodeToStr ENOTCONN         = "Socket is not connected"
214 errorCodeToStr ESHUTDOWN        = "Can't send after socket shutdown"
215 errorCodeToStr ETOOMANYREFS     = "Too many references: can't splice"
216 errorCodeToStr ETIMEDOUT        = "Connection timed out"
217 errorCodeToStr ECONNREFUSED     = "Connection refused"
218
219 errorCodeToStr ELOOP            = "Too many levels of symbolic links"
220 errorCodeToStr ENAMETOOLONG     = "File name too long"
221
222 -- should be rearranged
223 errorCodeToStr EHOSTDOWN        = "Host is down"
224 errorCodeToStr EHOSTUNREACH     = "No route to host"
225 errorCodeToStr ENOTEMPTY        = "Directory not empty"
226
227 -- quotas & mush
228 errorCodeToStr EPROCLIM = "Too many processes"
229 errorCodeToStr EUSERS   = "Too many users"
230 errorCodeToStr EDQUOT   = "Disc quota exceeded"
231
232 -- Network File System
233 errorCodeToStr ESTALE   = "Stale NFS file handle"
234 errorCodeToStr EREMOTE  = "Too many levels of remote in path"
235
236 -- streams
237 errorCodeToStr ENOSTR   = "Device is not a stream"
238 errorCodeToStr ETIME    = "Timer expired"
239 errorCodeToStr ENOSR    = "Out of streams resources"
240 errorCodeToStr ENOMSG   = "No message of desired type"
241 errorCodeToStr EBADMSG  = "Trying to read unreadable message"
242
243 -- SystemV IPC
244 errorCodeToStr EIDRM    = "Identifier removed"
245
246 -- SystemV Record Locking
247 errorCodeToStr EDEADLK  = "Deadlock condition."
248 errorCodeToStr ENOLCK   = "No record locks available."
249
250 -- RFS
251 errorCodeToStr ENONET   = "Machine is not on the network"
252 errorCodeToStr ERREMOTE = "Object is remote"
253 errorCodeToStr ENOLINK  = "the link has been severed"
254 errorCodeToStr EADV     = "advertise error"
255 errorCodeToStr ESRMNT   = "srmount error"
256 errorCodeToStr ECOMM    = "Communication error on send"
257 errorCodeToStr EPROTO   = "Protocol error"
258 errorCodeToStr EMULTIHOP = "multihop attempted"
259 errorCodeToStr EDOTDOT  = "Cross mount point (not an error)"
260 errorCodeToStr EREMCHG  = "Remote address changed"
261
262 -- POSIX
263 errorCodeToStr ENOSYS   = "function not implemented"
264
265 unpackCErrorCode   :: Int -> CErrorCode
266 unpackCErrorCode   e = (range (NOERROR, ENOSYS))!!e
267
268 packCErrorCode :: CErrorCode -> Int
269 packCErrorCode e = index (NOERROR, ENOSYS) e
270
271
272 getCErrorCode :: PrimIO CErrorCode
273 getCErrorCode =
274     _casm_ ``%r = errno;''                          `thenPrimIO` \ errno ->    
275     returnPrimIO (unpackCErrorCode errno)
276
277
278 setCErrorCode :: CErrorCode -> PrimIO ()
279 setCErrorCode ecode =
280     _casm_ ``errno = %0;'' (packCErrorCode ecode)   `thenPrimIO` \ () ->
281     returnPrimIO ()
282
283
284 \end{code}
285