{-# LINE 1 "Std/IO/UV/Errno.hsc" #-}
{-# LANGUAGE PatternSynonyms #-}
{-|
Module      : Std.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 Std.IO.UV.Errno where

import Foreign.C.Types
import Foreign.C.String



uvStdError :: CInt -> IO String
uvStdError errno = peekCString =<< uv_strerror errno

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

uvErrName :: CInt -> IO String
uvErrName errno = peekCString =<< 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 35 "Std/IO/UV/Errno.hsc" #-}
-- | permission denied
pattern UV_EACCES          :: CInt
pattern UV_EACCES          = -13
{-# LINE 38 "Std/IO/UV/Errno.hsc" #-}
-- | address already in use
pattern UV_EADDRINUSE      :: CInt
pattern UV_EADDRINUSE      = -48
{-# LINE 41 "Std/IO/UV/Errno.hsc" #-}
-- | address not available
pattern UV_EADDRNOTAVAIL   :: CInt
pattern UV_EADDRNOTAVAIL   = -49
{-# LINE 44 "Std/IO/UV/Errno.hsc" #-}
-- | address family not supported
pattern UV_EAFNOSUPPORT    :: CInt
pattern UV_EAFNOSUPPORT    = -47
{-# LINE 47 "Std/IO/UV/Errno.hsc" #-}
-- | resource temporarily unavailable
pattern UV_EAGAIN          :: CInt
pattern UV_EAGAIN          = -35
{-# LINE 50 "Std/IO/UV/Errno.hsc" #-}
-- | address family not supported
pattern UV_EAI_ADDRFAMILY  :: CInt
pattern UV_EAI_ADDRFAMILY  = -3000
{-# LINE 53 "Std/IO/UV/Errno.hsc" #-}
-- | temporary failure
pattern UV_EAI_AGAIN       :: CInt
pattern UV_EAI_AGAIN       = -3001
{-# LINE 56 "Std/IO/UV/Errno.hsc" #-}
-- | bad ai_flags value
pattern UV_EAI_BADFLAGS    :: CInt
pattern UV_EAI_BADFLAGS    = -3002
{-# LINE 59 "Std/IO/UV/Errno.hsc" #-}
-- | invalid value for hints
pattern UV_EAI_BADHINTS    :: CInt
pattern UV_EAI_BADHINTS    = -3013
{-# LINE 62 "Std/IO/UV/Errno.hsc" #-}
-- | request canceled
pattern UV_EAI_CANCELED    :: CInt
pattern UV_EAI_CANCELED    = -3003
{-# LINE 65 "Std/IO/UV/Errno.hsc" #-}
-- | permanent failure
pattern UV_EAI_FAIL        :: CInt
pattern UV_EAI_FAIL        = -3004
{-# LINE 68 "Std/IO/UV/Errno.hsc" #-}
-- | ai_family not supported
pattern UV_EAI_FAMILY      :: CInt
pattern UV_EAI_FAMILY      = -3005
{-# LINE 71 "Std/IO/UV/Errno.hsc" #-}
-- | out of memory
pattern UV_EAI_MEMORY      :: CInt
pattern UV_EAI_MEMORY      = -3006
{-# LINE 74 "Std/IO/UV/Errno.hsc" #-}
-- | no address
pattern UV_EAI_NODATA      :: CInt
pattern UV_EAI_NODATA      = -3007
{-# LINE 77 "Std/IO/UV/Errno.hsc" #-}
-- | unknown node or service
pattern UV_EAI_NONAME      :: CInt
pattern UV_EAI_NONAME      = -3008
{-# LINE 80 "Std/IO/UV/Errno.hsc" #-}
-- | argument buffer overflow
pattern UV_EAI_OVERFLOW    :: CInt
pattern UV_EAI_OVERFLOW    = -3009
{-# LINE 83 "Std/IO/UV/Errno.hsc" #-}
-- | resolved protocol is unknown
pattern UV_EAI_PROTOCOL    :: CInt
pattern UV_EAI_PROTOCOL    = -3014
{-# LINE 86 "Std/IO/UV/Errno.hsc" #-}
-- | service not available for socket type
pattern UV_EAI_SERVICE     :: CInt
pattern UV_EAI_SERVICE     = -3010
{-# LINE 89 "Std/IO/UV/Errno.hsc" #-}
-- | socket type not supported
pattern UV_EAI_SOCKTYPE    :: CInt
pattern UV_EAI_SOCKTYPE    = -3011
{-# LINE 92 "Std/IO/UV/Errno.hsc" #-}
-- | connection already in progress
pattern UV_EALREADY        :: CInt
pattern UV_EALREADY        = -37
{-# LINE 95 "Std/IO/UV/Errno.hsc" #-}
-- | bad file descriptor
pattern UV_EBADF           :: CInt
pattern UV_EBADF           = -9
{-# LINE 98 "Std/IO/UV/Errno.hsc" #-}
-- | resource busy or locked
pattern UV_EBUSY           :: CInt
pattern UV_EBUSY           = -16
{-# LINE 101 "Std/IO/UV/Errno.hsc" #-}
-- | operation canceled
pattern UV_ECANCELED       :: CInt
pattern UV_ECANCELED       = -89
{-# LINE 104 "Std/IO/UV/Errno.hsc" #-}
-- | invalid Unicode character
pattern UV_ECHARSET        :: CInt
pattern UV_ECHARSET        = -4080
{-# LINE 107 "Std/IO/UV/Errno.hsc" #-}
-- | software caused connection abort
pattern UV_ECONNABORTED    :: CInt
pattern UV_ECONNABORTED    = -53
{-# LINE 110 "Std/IO/UV/Errno.hsc" #-}
-- | connection refused
pattern UV_ECONNREFUSED    :: CInt
pattern UV_ECONNREFUSED    = -61
{-# LINE 113 "Std/IO/UV/Errno.hsc" #-}
-- | connection reset by peer
pattern UV_ECONNRESET      :: CInt
pattern UV_ECONNRESET      = -54
{-# LINE 116 "Std/IO/UV/Errno.hsc" #-}
-- | destination address required
pattern UV_EDESTADDRREQ    :: CInt
pattern UV_EDESTADDRREQ    = -39
{-# LINE 119 "Std/IO/UV/Errno.hsc" #-}
-- | file already exists
pattern UV_EEXIST          :: CInt
pattern UV_EEXIST          = -17
{-# LINE 122 "Std/IO/UV/Errno.hsc" #-}
-- | bad address in system call argument
pattern UV_EFAULT          :: CInt
pattern UV_EFAULT          = -14
{-# LINE 125 "Std/IO/UV/Errno.hsc" #-}
-- | file too large
pattern UV_EFBIG           :: CInt
pattern UV_EFBIG           = -27
{-# LINE 128 "Std/IO/UV/Errno.hsc" #-}
-- | host is unreachable
pattern UV_EHOSTUNREACH    :: CInt
pattern UV_EHOSTUNREACH    = -65
{-# LINE 131 "Std/IO/UV/Errno.hsc" #-}
-- | interrupted system call
pattern UV_EINTR           :: CInt
pattern UV_EINTR           = -4
{-# LINE 134 "Std/IO/UV/Errno.hsc" #-}
-- | invalid argument
pattern UV_EINVAL          :: CInt
pattern UV_EINVAL          = -22
{-# LINE 137 "Std/IO/UV/Errno.hsc" #-}
-- | i/o error
pattern UV_EIO             :: CInt
pattern UV_EIO             = -5
{-# LINE 140 "Std/IO/UV/Errno.hsc" #-}
-- | socket is already connected
pattern UV_EISCONN         :: CInt
pattern UV_EISCONN         = -56
{-# LINE 143 "Std/IO/UV/Errno.hsc" #-}
-- | illegal operation on a directory
pattern UV_EISDIR          :: CInt
pattern UV_EISDIR          = -21
{-# LINE 146 "Std/IO/UV/Errno.hsc" #-}
-- | too many symbolic links encountered
pattern UV_ELOOP           :: CInt
pattern UV_ELOOP           = -62
{-# LINE 149 "Std/IO/UV/Errno.hsc" #-}
-- | too many open files
pattern UV_EMFILE          :: CInt
pattern UV_EMFILE          = -24
{-# LINE 152 "Std/IO/UV/Errno.hsc" #-}
-- | message too long
pattern UV_EMSGSIZE        :: CInt
pattern UV_EMSGSIZE        = -40
{-# LINE 155 "Std/IO/UV/Errno.hsc" #-}
-- | name too long
pattern UV_ENAMETOOLONG    :: CInt
pattern UV_ENAMETOOLONG    = -63
{-# LINE 158 "Std/IO/UV/Errno.hsc" #-}
-- | network is down
pattern UV_ENETDOWN        :: CInt
pattern UV_ENETDOWN        = -50
{-# LINE 161 "Std/IO/UV/Errno.hsc" #-}
-- | network is unreachable
pattern UV_ENETUNREACH     :: CInt
pattern UV_ENETUNREACH     = -51
{-# LINE 164 "Std/IO/UV/Errno.hsc" #-}
-- | file table overflow
pattern UV_ENFILE          :: CInt
pattern UV_ENFILE          = -23
{-# LINE 167 "Std/IO/UV/Errno.hsc" #-}
-- | no buffer space available
pattern UV_ENOBUFS         :: CInt
pattern UV_ENOBUFS         = -55
{-# LINE 170 "Std/IO/UV/Errno.hsc" #-}
-- | no such device
pattern UV_ENODEV          :: CInt
pattern UV_ENODEV          = -19
{-# LINE 173 "Std/IO/UV/Errno.hsc" #-}
-- | no such file or directory
pattern UV_ENOENT          :: CInt
pattern UV_ENOENT          = -2
{-# LINE 176 "Std/IO/UV/Errno.hsc" #-}
-- | not enough memory
pattern UV_ENOMEM          :: CInt
pattern UV_ENOMEM          = -12
{-# LINE 179 "Std/IO/UV/Errno.hsc" #-}
-- | machine is not on the network
pattern UV_ENONET          :: CInt
pattern UV_ENONET          = -4056
{-# LINE 182 "Std/IO/UV/Errno.hsc" #-}
-- | protocol not available
pattern UV_ENOPROTOOPT     :: CInt
pattern UV_ENOPROTOOPT     = -42
{-# LINE 185 "Std/IO/UV/Errno.hsc" #-}
-- | no space left on device
pattern UV_ENOSPC          :: CInt
pattern UV_ENOSPC          = -28
{-# LINE 188 "Std/IO/UV/Errno.hsc" #-}
-- | function not implemented
pattern UV_ENOSYS          :: CInt
pattern UV_ENOSYS          = -78
{-# LINE 191 "Std/IO/UV/Errno.hsc" #-}
-- | socket is not connected
pattern UV_ENOTCONN        :: CInt
pattern UV_ENOTCONN        = -57
{-# LINE 194 "Std/IO/UV/Errno.hsc" #-}
-- | not a directory
pattern UV_ENOTDIR         :: CInt
pattern UV_ENOTDIR         = -20
{-# LINE 197 "Std/IO/UV/Errno.hsc" #-}
-- | directory not empty
pattern UV_ENOTEMPTY       :: CInt
pattern UV_ENOTEMPTY       = -66
{-# LINE 200 "Std/IO/UV/Errno.hsc" #-}
-- | socket operation on non-socket
pattern UV_ENOTSOCK        :: CInt
pattern UV_ENOTSOCK        = -38
{-# LINE 203 "Std/IO/UV/Errno.hsc" #-}
-- | operation not supported on socket
pattern UV_ENOTSUP         :: CInt
pattern UV_ENOTSUP         = -45
{-# LINE 206 "Std/IO/UV/Errno.hsc" #-}
-- | operation not permitted
pattern UV_EPERM           :: CInt
pattern UV_EPERM           = -1
{-# LINE 209 "Std/IO/UV/Errno.hsc" #-}
-- | broken pipe
pattern UV_EPIPE           :: CInt
pattern UV_EPIPE           = -32
{-# LINE 212 "Std/IO/UV/Errno.hsc" #-}
-- | protocol error
pattern UV_EPROTO          :: CInt
pattern UV_EPROTO          = -100
{-# LINE 215 "Std/IO/UV/Errno.hsc" #-}
-- | protocol not supported
pattern UV_EPROTONOSUPPORT :: CInt
pattern UV_EPROTONOSUPPORT = -43
{-# LINE 218 "Std/IO/UV/Errno.hsc" #-}
-- | protocol wrong type for socket
pattern UV_EPROTOTYPE      :: CInt
pattern UV_EPROTOTYPE      = -41
{-# LINE 221 "Std/IO/UV/Errno.hsc" #-}
-- | result too large
pattern UV_ERANGE          :: CInt
pattern UV_ERANGE          = -34
{-# LINE 224 "Std/IO/UV/Errno.hsc" #-}
-- | read-only file system
pattern UV_EROFS           :: CInt
pattern UV_EROFS           = -30
{-# LINE 227 "Std/IO/UV/Errno.hsc" #-}
-- | cannot send after transport endpoint shutdown
pattern UV_ESHUTDOWN       :: CInt
pattern UV_ESHUTDOWN       = -58
{-# LINE 230 "Std/IO/UV/Errno.hsc" #-}
-- | invalid seek
pattern UV_ESPIPE          :: CInt
pattern UV_ESPIPE          = -29
{-# LINE 233 "Std/IO/UV/Errno.hsc" #-}
-- | no such process
pattern UV_ESRCH           :: CInt
pattern UV_ESRCH           = -3
{-# LINE 236 "Std/IO/UV/Errno.hsc" #-}
-- | connection timed out
pattern UV_ETIMEDOUT       :: CInt
pattern UV_ETIMEDOUT       = -60
{-# LINE 239 "Std/IO/UV/Errno.hsc" #-}
-- | text file is busy
pattern UV_ETXTBSY         :: CInt
pattern UV_ETXTBSY         = -26
{-# LINE 242 "Std/IO/UV/Errno.hsc" #-}
-- | cross-device link not permitted
pattern UV_EXDEV           :: CInt
pattern UV_EXDEV           = -18
{-# LINE 245 "Std/IO/UV/Errno.hsc" #-}
-- | unknown error
pattern UV_UNKNOWN         :: CInt
pattern UV_UNKNOWN         = -4094
{-# LINE 248 "Std/IO/UV/Errno.hsc" #-}
-- | end of file
pattern UV_EOF             :: CInt
pattern UV_EOF             = -4095
{-# LINE 251 "Std/IO/UV/Errno.hsc" #-}
-- | no such device or address
pattern UV_ENXIO           :: CInt
pattern UV_ENXIO           = -6
{-# LINE 254 "Std/IO/UV/Errno.hsc" #-}
-- | too many links
pattern UV_EMLINK          :: CInt
pattern UV_EMLINK          = -31
{-# LINE 257 "Std/IO/UV/Errno.hsc" #-}