{-# LINE 1 "Z/IO/UV/Errno.hsc" #-}
{-|
Module      : Z.IO.UVErrno
Description : Errno provided by libuv
Copyright   : (c) Winterland, 2017-2018
License     : BSD
Maintainer  : drkoster@qq.com
Stability   : experimental
Portability : non-portable

INTERNAL MODULE, provides all libuv errno.

-}

module Z.IO.UV.Errno where

import Foreign.C.Types
import Foreign.C.String
import Z.Data.Text (Text)
import Z.Data.CBytes as CB



uvStdError :: CInt -> IO Text
uvStdError errno = toText <$> (fromCString =<< uv_strerror errno)

foreign import ccall unsafe uv_strerror :: CInt -> IO CString

uvErrName :: CInt -> IO Text
uvErrName errno = toText <$> (fromCString =<< uv_err_name errno)

foreign import ccall unsafe uv_err_name :: CInt -> IO CString

-- | argument list too long
pattern UV_E2BIG           :: CInt
pattern UV_E2BIG           = -7
{-# LINE 36 "Z/IO/UV/Errno.hsc" #-}
-- | permission denied
pattern UV_EACCES          :: CInt
pattern UV_EACCES          = -13
{-# LINE 39 "Z/IO/UV/Errno.hsc" #-}
-- | address already in use
pattern UV_EADDRINUSE      :: CInt
pattern UV_EADDRINUSE      = -98
{-# LINE 42 "Z/IO/UV/Errno.hsc" #-}
-- | address not available
pattern UV_EADDRNOTAVAIL   :: CInt
pattern UV_EADDRNOTAVAIL   = -99
{-# LINE 45 "Z/IO/UV/Errno.hsc" #-}
-- | address family not supported
pattern UV_EAFNOSUPPORT    :: CInt
pattern UV_EAFNOSUPPORT    = -97
{-# LINE 48 "Z/IO/UV/Errno.hsc" #-}
-- | resource temporarily unavailable
pattern UV_EAGAIN          :: CInt
pattern UV_EAGAIN          = -11
{-# LINE 51 "Z/IO/UV/Errno.hsc" #-}
-- | address family not supported
pattern UV_EAI_ADDRFAMILY  :: CInt
pattern UV_EAI_ADDRFAMILY  = -3000
{-# LINE 54 "Z/IO/UV/Errno.hsc" #-}
-- | temporary failure
pattern UV_EAI_AGAIN       :: CInt
pattern UV_EAI_AGAIN       = -3001
{-# LINE 57 "Z/IO/UV/Errno.hsc" #-}
-- | bad ai_flags value
pattern UV_EAI_BADFLAGS    :: CInt
pattern UV_EAI_BADFLAGS    = -3002
{-# LINE 60 "Z/IO/UV/Errno.hsc" #-}
-- | invalid value for hints
pattern UV_EAI_BADHINTS    :: CInt
pattern UV_EAI_BADHINTS    = -3013
{-# LINE 63 "Z/IO/UV/Errno.hsc" #-}
-- | request canceled
pattern UV_EAI_CANCELED    :: CInt
pattern UV_EAI_CANCELED    = -3003
{-# LINE 66 "Z/IO/UV/Errno.hsc" #-}
-- | permanent failure
pattern UV_EAI_FAIL        :: CInt
pattern UV_EAI_FAIL        = -3004
{-# LINE 69 "Z/IO/UV/Errno.hsc" #-}
-- | ai_family not supported
pattern UV_EAI_FAMILY      :: CInt
pattern UV_EAI_FAMILY      = -3005
{-# LINE 72 "Z/IO/UV/Errno.hsc" #-}
-- | out of memory
pattern UV_EAI_MEMORY      :: CInt
pattern UV_EAI_MEMORY      = -3006
{-# LINE 75 "Z/IO/UV/Errno.hsc" #-}
-- | no address
pattern UV_EAI_NODATA      :: CInt
pattern UV_EAI_NODATA      = -3007
{-# LINE 78 "Z/IO/UV/Errno.hsc" #-}
-- | unknown node or service
pattern UV_EAI_NONAME      :: CInt
pattern UV_EAI_NONAME      = -3008
{-# LINE 81 "Z/IO/UV/Errno.hsc" #-}
-- | argument buffer overflow
pattern UV_EAI_OVERFLOW    :: CInt
pattern UV_EAI_OVERFLOW    = -3009
{-# LINE 84 "Z/IO/UV/Errno.hsc" #-}
-- | resolved protocol is unknown
pattern UV_EAI_PROTOCOL    :: CInt
pattern UV_EAI_PROTOCOL    = -3014
{-# LINE 87 "Z/IO/UV/Errno.hsc" #-}
-- | service not available for socket type
pattern UV_EAI_SERVICE     :: CInt
pattern UV_EAI_SERVICE     = -3010
{-# LINE 90 "Z/IO/UV/Errno.hsc" #-}
-- | socket type not supported
pattern UV_EAI_SOCKTYPE    :: CInt
pattern UV_EAI_SOCKTYPE    = -3011
{-# LINE 93 "Z/IO/UV/Errno.hsc" #-}
-- | connection already in progress
pattern UV_EALREADY        :: CInt
pattern UV_EALREADY        = -114
{-# LINE 96 "Z/IO/UV/Errno.hsc" #-}
-- | bad file descriptor
pattern UV_EBADF           :: CInt
pattern UV_EBADF           = -9
{-# LINE 99 "Z/IO/UV/Errno.hsc" #-}
-- | resource busy or locked
pattern UV_EBUSY           :: CInt
pattern UV_EBUSY           = -16
{-# LINE 102 "Z/IO/UV/Errno.hsc" #-}
-- | operation canceled
pattern UV_ECANCELED       :: CInt
pattern UV_ECANCELED       = -125
{-# LINE 105 "Z/IO/UV/Errno.hsc" #-}
-- | invalid Unicode character
pattern UV_ECHARSET        :: CInt
pattern UV_ECHARSET        = -4080
{-# LINE 108 "Z/IO/UV/Errno.hsc" #-}
-- | software caused connection abort
pattern UV_ECONNABORTED    :: CInt
pattern UV_ECONNABORTED    = -103
{-# LINE 111 "Z/IO/UV/Errno.hsc" #-}
-- | connection refused
pattern UV_ECONNREFUSED    :: CInt
pattern UV_ECONNREFUSED    = -111
{-# LINE 114 "Z/IO/UV/Errno.hsc" #-}
-- | connection reset by peer
pattern UV_ECONNRESET      :: CInt
pattern UV_ECONNRESET      = -104
{-# LINE 117 "Z/IO/UV/Errno.hsc" #-}
-- | destination address required
pattern UV_EDESTADDRREQ    :: CInt
pattern UV_EDESTADDRREQ    = -89
{-# LINE 120 "Z/IO/UV/Errno.hsc" #-}
-- | file already exists
pattern UV_EEXIST          :: CInt
pattern UV_EEXIST          = -17
{-# LINE 123 "Z/IO/UV/Errno.hsc" #-}
-- | bad address in system call argument
pattern UV_EFAULT          :: CInt
pattern UV_EFAULT          = -14
{-# LINE 126 "Z/IO/UV/Errno.hsc" #-}
-- | file too large
pattern UV_EFBIG           :: CInt
pattern UV_EFBIG           = -27
{-# LINE 129 "Z/IO/UV/Errno.hsc" #-}
-- | host is unreachable
pattern UV_EHOSTUNREACH    :: CInt
pattern UV_EHOSTUNREACH    = -113
{-# LINE 132 "Z/IO/UV/Errno.hsc" #-}
-- | interrupted system call
pattern UV_EINTR           :: CInt
pattern UV_EINTR           = -4
{-# LINE 135 "Z/IO/UV/Errno.hsc" #-}
-- | invalid argument
pattern UV_EINVAL          :: CInt
pattern UV_EINVAL          = -22
{-# LINE 138 "Z/IO/UV/Errno.hsc" #-}
-- | i/o error
pattern UV_EIO             :: CInt
pattern UV_EIO             = -5
{-# LINE 141 "Z/IO/UV/Errno.hsc" #-}
-- | socket is already connected
pattern UV_EISCONN         :: CInt
pattern UV_EISCONN         = -106
{-# LINE 144 "Z/IO/UV/Errno.hsc" #-}
-- | illegal operation on a directory
pattern UV_EISDIR          :: CInt
pattern UV_EISDIR          = -21
{-# LINE 147 "Z/IO/UV/Errno.hsc" #-}
-- | too many symbolic links encountered
pattern UV_ELOOP           :: CInt
pattern UV_ELOOP           = -40
{-# LINE 150 "Z/IO/UV/Errno.hsc" #-}
-- | too many open files
pattern UV_EMFILE          :: CInt
pattern UV_EMFILE          = -24
{-# LINE 153 "Z/IO/UV/Errno.hsc" #-}
-- | message too long
pattern UV_EMSGSIZE        :: CInt
pattern UV_EMSGSIZE        = -90
{-# LINE 156 "Z/IO/UV/Errno.hsc" #-}
-- | name too long
pattern UV_ENAMETOOLONG    :: CInt
pattern UV_ENAMETOOLONG    = -36
{-# LINE 159 "Z/IO/UV/Errno.hsc" #-}
-- | network is down
pattern UV_ENETDOWN        :: CInt
pattern UV_ENETDOWN        = -100
{-# LINE 162 "Z/IO/UV/Errno.hsc" #-}
-- | network is unreachable
pattern UV_ENETUNREACH     :: CInt
pattern UV_ENETUNREACH     = -101
{-# LINE 165 "Z/IO/UV/Errno.hsc" #-}
-- | file table overflow
pattern UV_ENFILE          :: CInt
pattern UV_ENFILE          = -23
{-# LINE 168 "Z/IO/UV/Errno.hsc" #-}
-- | no buffer space available
pattern UV_ENOBUFS         :: CInt
pattern UV_ENOBUFS         = -105
{-# LINE 171 "Z/IO/UV/Errno.hsc" #-}
-- | no such device
pattern UV_ENODEV          :: CInt
pattern UV_ENODEV          = -19
{-# LINE 174 "Z/IO/UV/Errno.hsc" #-}
-- | no such file or directory
pattern UV_ENOENT          :: CInt
pattern UV_ENOENT          = -2
{-# LINE 177 "Z/IO/UV/Errno.hsc" #-}
-- | not enough memory
pattern UV_ENOMEM          :: CInt
pattern UV_ENOMEM          = -12
{-# LINE 180 "Z/IO/UV/Errno.hsc" #-}
-- | machine is not on the network
pattern UV_ENONET          :: CInt
pattern UV_ENONET          = -64
{-# LINE 183 "Z/IO/UV/Errno.hsc" #-}
-- | protocol not available
pattern UV_ENOPROTOOPT     :: CInt
pattern UV_ENOPROTOOPT     = -92
{-# LINE 186 "Z/IO/UV/Errno.hsc" #-}
-- | no space left on device
pattern UV_ENOSPC          :: CInt
pattern UV_ENOSPC          = -28
{-# LINE 189 "Z/IO/UV/Errno.hsc" #-}
-- | function not implemented
pattern UV_ENOSYS          :: CInt
pattern UV_ENOSYS          = -38
{-# LINE 192 "Z/IO/UV/Errno.hsc" #-}
-- | socket is not connected
pattern UV_ENOTCONN        :: CInt
pattern UV_ENOTCONN        = -107
{-# LINE 195 "Z/IO/UV/Errno.hsc" #-}
-- | not a directory
pattern UV_ENOTDIR         :: CInt
pattern UV_ENOTDIR         = -20
{-# LINE 198 "Z/IO/UV/Errno.hsc" #-}
-- | directory not empty
pattern UV_ENOTEMPTY       :: CInt
pattern UV_ENOTEMPTY       = -39
{-# LINE 201 "Z/IO/UV/Errno.hsc" #-}
-- | socket operation on non-socket
pattern UV_ENOTSOCK        :: CInt
pattern UV_ENOTSOCK        = -88
{-# LINE 204 "Z/IO/UV/Errno.hsc" #-}
-- | operation not supported on socket
pattern UV_ENOTSUP         :: CInt
pattern UV_ENOTSUP         = -95
{-# LINE 207 "Z/IO/UV/Errno.hsc" #-}
-- | operation not permitted
pattern UV_EPERM           :: CInt
pattern UV_EPERM           = -1
{-# LINE 210 "Z/IO/UV/Errno.hsc" #-}
-- | broken pipe
pattern UV_EPIPE           :: CInt
pattern UV_EPIPE           = -32
{-# LINE 213 "Z/IO/UV/Errno.hsc" #-}
-- | protocol error
pattern UV_EPROTO          :: CInt
pattern UV_EPROTO          = -71
{-# LINE 216 "Z/IO/UV/Errno.hsc" #-}
-- | protocol not supported
pattern UV_EPROTONOSUPPORT :: CInt
pattern UV_EPROTONOSUPPORT = -93
{-# LINE 219 "Z/IO/UV/Errno.hsc" #-}
-- | protocol wrong type for socket
pattern UV_EPROTOTYPE      :: CInt
pattern UV_EPROTOTYPE      = -91
{-# LINE 222 "Z/IO/UV/Errno.hsc" #-}
-- | result too large
pattern UV_ERANGE          :: CInt
pattern UV_ERANGE          = -34
{-# LINE 225 "Z/IO/UV/Errno.hsc" #-}
-- | read-only file system
pattern UV_EROFS           :: CInt
pattern UV_EROFS           = -30
{-# LINE 228 "Z/IO/UV/Errno.hsc" #-}
-- | cannot send after transport endpoint shutdown
pattern UV_ESHUTDOWN       :: CInt
pattern UV_ESHUTDOWN       = -108
{-# LINE 231 "Z/IO/UV/Errno.hsc" #-}
-- | invalid seek
pattern UV_ESPIPE          :: CInt
pattern UV_ESPIPE          = -29
{-# LINE 234 "Z/IO/UV/Errno.hsc" #-}
-- | no such process
pattern UV_ESRCH           :: CInt
pattern UV_ESRCH           = -3
{-# LINE 237 "Z/IO/UV/Errno.hsc" #-}
-- | connection timed out
pattern UV_ETIMEDOUT       :: CInt
pattern UV_ETIMEDOUT       = -110
{-# LINE 240 "Z/IO/UV/Errno.hsc" #-}
-- | text file is busy
pattern UV_ETXTBSY         :: CInt
pattern UV_ETXTBSY         = -26
{-# LINE 243 "Z/IO/UV/Errno.hsc" #-}
-- | cross-device link not permitted
pattern UV_EXDEV           :: CInt
pattern UV_EXDEV           = -18
{-# LINE 246 "Z/IO/UV/Errno.hsc" #-}
-- | unknown error
pattern UV_UNKNOWN         :: CInt
pattern UV_UNKNOWN         = -4094
{-# LINE 249 "Z/IO/UV/Errno.hsc" #-}
-- | end of file
pattern UV_EOF             :: CInt
pattern UV_EOF             = -4095
{-# LINE 252 "Z/IO/UV/Errno.hsc" #-}
-- | no such device or address
pattern UV_ENXIO           :: CInt
pattern UV_ENXIO           = -6
{-# LINE 255 "Z/IO/UV/Errno.hsc" #-}
-- | too many links
pattern UV_EMLINK          :: CInt
pattern UV_EMLINK          = -31
{-# LINE 258 "Z/IO/UV/Errno.hsc" #-}