{-# LINE 1 "Network/Socket.hsc" #-}
{-# LANGUAGE CPP, ScopedTypeVariables, RecordWildCards #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -fno-warn-warnings-deprecations #-}
#include "HsNetDef.h"
module Network.Socket
(
withSocketsDo
, getAddrInfo
, HostName
, ServiceName
, AddrInfo(..)
, defaultHints
, AddrInfoFlag(..)
, addrInfoFlagImplemented
, connect
, bind
, listen
, accept
, close
, close'
, shutdown
, ShutdownCmd(..)
, SocketOption(..)
, isSupportedSocketOption
, getSocketOption
, setSocketOption
, Socket(..)
, socket
, fdSocket
, mkSocket
, socketToHandle
, SocketType(..)
, isSupportedSocketType
, Family(..)
, isSupportedFamily
, ProtocolNumber
, defaultProtocol
, SockAddr(..)
, isSupportedSockAddr
, getPeerName
, getSocketName
, HostAddress
, hostAddressToTuple
, tupleToHostAddress
{-# LINE 156 "Network/Socket.hsc" #-}
, HostAddress6
, hostAddress6ToTuple
, tupleToHostAddress6
, FlowInfo
, ScopeID
{-# LINE 165 "Network/Socket.hsc" #-}
, ifNameToIndex
, ifIndexToName
{-# LINE 168 "Network/Socket.hsc" #-}
{-# LINE 169 "Network/Socket.hsc" #-}
, PortNumber
, defaultPort
, socketPortSafe
, socketPort
, isUnixDomainSocketAvailable
, socketPair
, sendFd
, recvFd
, getPeerCredential
{-# LINE 181 "Network/Socket.hsc" #-}
, NameInfoFlag(..)
, getNameInfo
{-# LINE 185 "Network/Socket.hsc" #-}
, setCloseOnExecIfNeeded
, getCloseOnExec
, setNonBlockIfNeeded
, getNonBlock
, sendBuf
, recvBuf
, sendBufTo
, recvBufFrom
, maxListenQueue
, send
, sendTo
, recv
, recvFrom
, recvLen
, htonl
, ntohl
, inet_addr
, inet_ntoa
, bindSocket
, sClose
, SocketStatus(..)
, isConnected
, isBound
, isListening
, isReadable
, isWritable
, sIsConnected
, sIsBound
, sIsListening
, sIsReadable
, sIsWritable
, aNY_PORT
, iNADDR_ANY
{-# LINE 228 "Network/Socket.hsc" #-}
, iN6ADDR_ANY
{-# LINE 230 "Network/Socket.hsc" #-}
, sOMAXCONN
, sOL_SOCKET
{-# LINE 233 "Network/Socket.hsc" #-}
, sCM_RIGHTS
{-# LINE 235 "Network/Socket.hsc" #-}
, packFamily
, unpackFamily
, packSocketType
{-# LINE 241 "Network/Socket.hsc" #-}
, getPeerCred
{-# LINE 246 "Network/Socket.hsc" #-}
{-# LINE 247 "Network/Socket.hsc" #-}
) where
import Data.Bits
import Data.Functor
import Data.List (foldl')
import Data.Maybe (isJust)
import Data.Word (Word8, Word32)
import Foreign.Ptr (Ptr, castPtr, nullPtr)
import Foreign.Storable (Storable(..))
import Foreign.C.Error
import Foreign.C.String (CString, withCString, withCStringLen, peekCString, peekCStringLen)
import Foreign.C.Types (CUInt(..), CChar)
import Foreign.C.Types (CInt(..), CSize(..))
import Foreign.Marshal.Alloc ( alloca, allocaBytes )
import Foreign.Marshal.Array ( peekArray )
import Foreign.Marshal.Utils ( maybeWith, with )
import System.IO
import Control.Monad (liftM, when, void)
import qualified Control.Exception as E
import Control.Concurrent.MVar
import Data.Typeable
import System.IO.Error
import GHC.Conc (threadWaitWrite)
{-# LINE 274 "Network/Socket.hsc" #-}
import GHC.Conc (threadWaitRead)
{-# LINE 276 "Network/Socket.hsc" #-}
#if MIN_VERSION_base(4,3,1)
import GHC.Conc (closeFdWith)
#endif
{-# LINE 284 "Network/Socket.hsc" #-}
{-# LINE 287 "Network/Socket.hsc" #-}
import qualified GHC.IO.Device
import GHC.IO.Handle.FD
import GHC.IO.Exception
import GHC.IO
import qualified System.Posix.Internals
import Network.Socket.Internal
import Network.Socket.Types
import Prelude
type HostName = String
type ServiceName = String
#if defined(mingw32_HOST_OS)
#define SAFE_ON_WIN safe
#else
#define SAFE_ON_WIN unsafe
#endif
{-# LINE 332 "Network/Socket.hsc" #-}
mkSocket :: CInt
-> Family
-> SocketType
-> ProtocolNumber
-> SocketStatus
-> IO Socket
mkSocket fd fam sType pNum stat = do
mStat <- newMVar stat
withSocketsDo $ return ()
return $ MkSocket fd fam sType pNum mStat
defaultProtocol :: ProtocolNumber
defaultProtocol = 0
instance Show SockAddr where
{-# LINE 357 "Network/Socket.hsc" #-}
showsPrec _ (SockAddrUnix str) = showString str
{-# LINE 359 "Network/Socket.hsc" #-}
showsPrec _ (SockAddrInet port ha)
= showString (unsafePerformIO (inet_ntoa ha))
. showString ":"
. shows port
{-# LINE 364 "Network/Socket.hsc" #-}
showsPrec _ addr@(SockAddrInet6 port _ _ _)
= showChar '['
. showString (unsafePerformIO $
fst `liftM` getNameInfo [NI_NUMERICHOST] True False addr >>=
maybe (fail "showsPrec: impossible internal error") return)
. showString "]:"
. shows port
{-# LINE 372 "Network/Socket.hsc" #-}
{-# LINE 373 "Network/Socket.hsc" #-}
showsPrec _ (SockAddrCan ifidx) = shows ifidx
{-# LINE 375 "Network/Socket.hsc" #-}
{-# LINE 379 "Network/Socket.hsc" #-}
socket :: Family
-> SocketType
-> ProtocolNumber
-> IO Socket
socket family stype protocol = do
c_stype <- packSocketTypeOrThrow "socket" stype
fd <- throwSocketErrorIfMinus1Retry "Network.Socket.socket" $
c_socket (packFamily family) c_stype protocol
setNonBlockIfNeeded fd
sock <- mkSocket fd family stype protocol NotConnected
{-# LINE 415 "Network/Socket.hsc" #-}
{-# LINE 423 "Network/Socket.hsc" #-}
when (family == AF_INET6 && (stype == Stream || stype == Datagram)) $
setSocketOption sock IPv6Only 0 `onException` close sock
{-# LINE 426 "Network/Socket.hsc" #-}
{-# LINE 427 "Network/Socket.hsc" #-}
return sock
socketPair :: Family
-> SocketType
-> ProtocolNumber
-> IO (Socket, Socket)
{-# LINE 438 "Network/Socket.hsc" #-}
socketPair family stype protocol = do
allocaBytes (2 * sizeOf (1 :: CInt)) $ \ fdArr -> do
c_stype <- packSocketTypeOrThrow "socketPair" stype
_rc <- throwSocketErrorIfMinus1Retry "Network.Socket.socketpair" $
c_socketpair (packFamily family) c_stype protocol fdArr
[fd1,fd2] <- peekArray 2 fdArr
s1 <- mkNonBlockingSocket fd1
s2 <- mkNonBlockingSocket fd2
return (s1,s2)
where
mkNonBlockingSocket fd = do
setNonBlockIfNeeded fd
mkSocket fd family stype protocol Connected
foreign import ccall unsafe "socketpair"
c_socketpair :: CInt -> CInt -> CInt -> Ptr CInt -> IO CInt
{-# LINE 457 "Network/Socket.hsc" #-}
{-# LINE 462 "Network/Socket.hsc" #-}
fGetFd :: CInt
fGetFd = 1
{-# LINE 464 "Network/Socket.hsc" #-}
fGetFl :: CInt
fGetFl = 3
{-# LINE 466 "Network/Socket.hsc" #-}
fdCloexec :: CInt
fdCloexec = 1
{-# LINE 468 "Network/Socket.hsc" #-}
oNonBlock :: CInt
oNonBlock = 2048
{-# LINE 470 "Network/Socket.hsc" #-}
{-# LINE 471 "Network/Socket.hsc" #-}
sockNonBlock :: CInt
sockNonBlock = 2048
{-# LINE 473 "Network/Socket.hsc" #-}
sockCloexec :: CInt
sockCloexec = 524288
{-# LINE 475 "Network/Socket.hsc" #-}
{-# LINE 476 "Network/Socket.hsc" #-}
{-# LINE 477 "Network/Socket.hsc" #-}
setNonBlockIfNeeded :: CInt -> IO ()
setNonBlockIfNeeded fd =
System.Posix.Internals.setNonBlockingFD fd True
setCloseOnExecIfNeeded :: CInt -> IO ()
{-# LINE 492 "Network/Socket.hsc" #-}
setCloseOnExecIfNeeded fd = System.Posix.Internals.setCloseOnExec fd
{-# LINE 494 "Network/Socket.hsc" #-}
{-# LINE 496 "Network/Socket.hsc" #-}
foreign import ccall unsafe "fcntl"
c_fcntl_read :: CInt -> CInt -> CInt -> IO CInt
{-# LINE 499 "Network/Socket.hsc" #-}
getCloseOnExec :: CInt -> IO Bool
{-# LINE 508 "Network/Socket.hsc" #-}
getCloseOnExec fd = do
flags <- c_fcntl_read fd fGetFd 0
let ret = flags .&. fdCloexec
return (ret /= 0)
{-# LINE 513 "Network/Socket.hsc" #-}
getNonBlock :: CInt -> IO Bool
{-# LINE 522 "Network/Socket.hsc" #-}
getNonBlock fd = do
flags <- c_fcntl_read fd fGetFl 0
let ret = flags .&. oNonBlock
return (ret /= 0)
{-# LINE 527 "Network/Socket.hsc" #-}
bind :: Socket
-> SockAddr
-> IO ()
bind (MkSocket s _family _stype _protocol socketStatus) addr = do
modifyMVar_ socketStatus $ \ status -> do
if status /= NotConnected
then
ioError $ userError $
"Network.Socket.bind: can't bind to socket with status " ++ show status
else do
withSockAddr addr $ \p_addr sz -> do
_status <- throwSocketErrorIfMinus1Retry "Network.Socket.bind" $
c_bind s p_addr (fromIntegral sz)
return Bound
connect :: Socket
-> SockAddr
-> IO ()
connect sock@(MkSocket s _family _stype _protocol socketStatus) addr = withSocketsDo $ do
modifyMVar_ socketStatus $ \currentStatus -> do
if currentStatus /= NotConnected && currentStatus /= Bound
then
ioError $ userError $
errLoc ++ ": can't connect to socket with status " ++ show currentStatus
else do
withSockAddr addr $ \p_addr sz -> do
let connectLoop = do
r <- c_connect s p_addr (fromIntegral sz)
if r == -1
then do
{-# LINE 572 "Network/Socket.hsc" #-}
err <- getErrno
case () of
_ | err == eINTR -> connectLoop
_ | err == eINPROGRESS -> connectBlocked
_otherwise -> throwSocketError errLoc
{-# LINE 581 "Network/Socket.hsc" #-}
else return ()
connectBlocked = do
threadWaitWrite (fromIntegral s)
err <- getSocketOption sock SoError
if (err == 0)
then return ()
else throwSocketErrorCode errLoc (fromIntegral err)
connectLoop
return Connected
where
errLoc = "Network.Socket.connect: " ++ show sock
listen :: Socket
-> Int
-> IO ()
listen (MkSocket s _family _stype _protocol socketStatus) backlog = do
modifyMVar_ socketStatus $ \ status -> do
if status /= Bound
then
ioError $ userError $
"Network.Socket.listen: can't listen on socket with status " ++ show status
else do
throwSocketErrorIfMinus1Retry_ "Network.Socket.listen" $
c_listen s (fromIntegral backlog)
return Listening
accept :: Socket
-> IO (Socket,
SockAddr)
accept sock@(MkSocket s family stype protocol status) = do
currentStatus <- readMVar status
if not $ isAcceptable family stype currentStatus
then
ioError $ userError $
"Network.Socket.accept: can't accept socket (" ++
show (family, stype, protocol) ++ ") with status " ++
show currentStatus
else do
let sz = sizeOfSockAddrByFamily family
allocaBytes sz $ \ sockaddr -> do
zeroMemory sockaddr $ fromIntegral sz
{-# LINE 660 "Network/Socket.hsc" #-}
with (fromIntegral sz) $ \ ptr_len -> do
{-# LINE 662 "Network/Socket.hsc" #-}
new_sock <- throwSocketErrorIfMinus1RetryMayBlock "Network.Socket.accept"
(threadWaitRead (fromIntegral s))
(c_accept4 s sockaddr ptr_len (sockNonBlock .|. sockCloexec))
{-# LINE 671 "Network/Socket.hsc" #-}
{-# LINE 672 "Network/Socket.hsc" #-}
addr <- peekSockAddr sockaddr
sock' <- mkSocket new_sock family stype protocol Connected
return (sock', addr)
{-# LINE 686 "Network/Socket.hsc" #-}
{-# DEPRECATED sendTo "Use sendTo defined in \"Network.Socket.ByteString\"" #-}
sendTo :: Socket
-> String
-> SockAddr
-> IO Int
sendTo sock xs addr = do
withCStringLen xs $ \(str, len) -> do
sendBufTo sock str len addr
sendBufTo :: Socket
-> Ptr a -> Int
-> SockAddr
-> IO Int
sendBufTo sock@(MkSocket s _family _stype _protocol _status) ptr nbytes addr = do
withSockAddr addr $ \p_addr sz -> do
liftM fromIntegral $
throwSocketErrorWaitWrite sock "Network.Socket.sendBufTo" $
c_sendto s ptr (fromIntegral $ nbytes) 0
p_addr (fromIntegral sz)
{-# DEPRECATED recvFrom "Use recvFrom defined in \"Network.Socket.ByteString\"" #-}
recvFrom :: Socket -> Int -> IO (String, Int, SockAddr)
recvFrom sock nbytes =
allocaBytes nbytes $ \ptr -> do
(len, sockaddr) <- recvBufFrom sock ptr nbytes
str <- peekCStringLen (ptr, len)
return (str, len, sockaddr)
recvBufFrom :: Socket -> Ptr a -> Int -> IO (Int, SockAddr)
recvBufFrom sock@(MkSocket s family _stype _protocol _status) ptr nbytes
| nbytes <= 0 = ioError (mkInvalidRecvArgError "Network.Socket.recvBufFrom")
| otherwise =
withNewSockAddr family $ \ptr_addr sz -> do
alloca $ \ptr_len -> do
poke ptr_len (fromIntegral sz)
len <- throwSocketErrorWaitRead sock "Network.Socket.recvBufFrom" $
c_recvfrom s ptr (fromIntegral nbytes) 0
ptr_addr ptr_len
let len' = fromIntegral len
if len' == 0
then ioError (mkEOFError "Network.Socket.recvFrom")
else do
flg <- isConnected sock
sockaddr <-
if flg then
getPeerName sock
else
peekSockAddr ptr_addr
return (len', sockaddr)
{-# DEPRECATED send "Use send defined in \"Network.Socket.ByteString\"" #-}
send :: Socket
-> String
-> IO Int
send sock xs = withCStringLen xs $ \(str, len) ->
sendBuf sock (castPtr str) len
sendBuf :: Socket
-> Ptr Word8
-> Int
-> IO Int
sendBuf sock@(MkSocket s _family _stype _protocol _status) str len = do
liftM fromIntegral $
{-# LINE 819 "Network/Socket.hsc" #-}
throwSocketErrorWaitWrite sock "Network.Socket.sendBuf" $
c_send s str (fromIntegral len) 0
{-# LINE 822 "Network/Socket.hsc" #-}
{-# DEPRECATED recv "Use recv defined in \"Network.Socket.ByteString\"" #-}
recv :: Socket -> Int -> IO String
recv sock l = fst <$> recvLen sock l
{-# DEPRECATED recvLen "Use recv defined in \"Network.Socket.ByteString\" with \"Data.Bytestring.length\"" #-}
recvLen :: Socket -> Int -> IO (String, Int)
recvLen sock nbytes =
allocaBytes nbytes $ \ptr -> do
len <- recvBuf sock ptr nbytes
s <- peekCStringLen (castPtr ptr,len)
return (s, len)
recvBuf :: Socket -> Ptr Word8 -> Int -> IO Int
recvBuf sock@(MkSocket s _family _stype _protocol _status) ptr nbytes
| nbytes <= 0 = ioError (mkInvalidRecvArgError "Network.Socket.recvBuf")
| otherwise = do
len <-
{-# LINE 873 "Network/Socket.hsc" #-}
throwSocketErrorWaitRead sock "Network.Socket.recvBuf" $
c_recv s (castPtr ptr) (fromIntegral nbytes) 0
{-# LINE 876 "Network/Socket.hsc" #-}
let len' = fromIntegral len
if len' == 0
then ioError (mkEOFError "Network.Socket.recvBuf")
else return len'
socketPort :: Socket
-> IO PortNumber
socketPort sock@(MkSocket _ AF_INET _ _ _) = do
(SockAddrInet port _) <- getSocketName sock
return port
{-# LINE 897 "Network/Socket.hsc" #-}
socketPort sock@(MkSocket _ AF_INET6 _ _ _) = do
(SockAddrInet6 port _ _ _) <- getSocketName sock
return port
{-# LINE 901 "Network/Socket.hsc" #-}
socketPort (MkSocket _ family _ _ _) =
ioError $ userError $
"Network.Socket.socketPort: address family '" ++ show family ++
"' not supported."
socketPortSafe :: Socket
-> IO (Maybe PortNumber)
socketPortSafe s = do
sa <- getSocketName s
return $ case sa of
SockAddrInet port _ -> Just port
{-# LINE 917 "Network/Socket.hsc" #-}
SockAddrInet6 port _ _ _ -> Just port
{-# LINE 919 "Network/Socket.hsc" #-}
_ -> Nothing
getPeerName :: Socket -> IO SockAddr
getPeerName (MkSocket s family _ _ _) = do
withNewSockAddr family $ \ptr sz -> do
with (fromIntegral sz) $ \int_star -> do
throwSocketErrorIfMinus1Retry_ "Network.Socket.getPeerName" $
c_getpeername s ptr int_star
_sz <- peek int_star
peekSockAddr ptr
getSocketName :: Socket -> IO SockAddr
getSocketName (MkSocket s family _ _ _) = do
withNewSockAddr family $ \ptr sz -> do
with (fromIntegral sz) $ \int_star -> do
throwSocketErrorIfMinus1Retry_ "Network.Socket.getSocketName" $
c_getsockname s ptr int_star
peekSockAddr ptr
data SocketOption
= Debug
| ReuseAddr
| Type
| SoError
| DontRoute
| Broadcast
| SendBuffer
| RecvBuffer
| KeepAlive
| OOBInline
| TimeToLive
| MaxSegment
| NoDelay
| Cork
| Linger
| ReusePort
| RecvLowWater
| SendLowWater
| RecvTimeOut
| SendTimeOut
| UseLoopBack
| UserTimeout
| IPv6Only
| CustomSockOpt (CInt, CInt)
deriving (Show, Typeable)
isSupportedSocketOption :: SocketOption -> Bool
isSupportedSocketOption = isJust . packSocketOption
packSocketOption :: SocketOption -> Maybe (CInt, CInt)
packSocketOption so =
case Just so of
{-# LINE 1002 "Network/Socket.hsc" #-}
{-# LINE 1003 "Network/Socket.hsc" #-}
Just Debug -> Just ((1), (1))
{-# LINE 1004 "Network/Socket.hsc" #-}
{-# LINE 1005 "Network/Socket.hsc" #-}
{-# LINE 1006 "Network/Socket.hsc" #-}
Just ReuseAddr -> Just ((1), (2))
{-# LINE 1007 "Network/Socket.hsc" #-}
{-# LINE 1008 "Network/Socket.hsc" #-}
{-# LINE 1009 "Network/Socket.hsc" #-}
Just Type -> Just ((1), (3))
{-# LINE 1010 "Network/Socket.hsc" #-}
{-# LINE 1011 "Network/Socket.hsc" #-}
{-# LINE 1012 "Network/Socket.hsc" #-}
Just SoError -> Just ((1), (4))
{-# LINE 1013 "Network/Socket.hsc" #-}
{-# LINE 1014 "Network/Socket.hsc" #-}
{-# LINE 1015 "Network/Socket.hsc" #-}
Just DontRoute -> Just ((1), (5))
{-# LINE 1016 "Network/Socket.hsc" #-}
{-# LINE 1017 "Network/Socket.hsc" #-}
{-# LINE 1018 "Network/Socket.hsc" #-}
Just Broadcast -> Just ((1), (6))
{-# LINE 1019 "Network/Socket.hsc" #-}
{-# LINE 1020 "Network/Socket.hsc" #-}
{-# LINE 1021 "Network/Socket.hsc" #-}
Just SendBuffer -> Just ((1), (7))
{-# LINE 1022 "Network/Socket.hsc" #-}
{-# LINE 1023 "Network/Socket.hsc" #-}
{-# LINE 1024 "Network/Socket.hsc" #-}
Just RecvBuffer -> Just ((1), (8))
{-# LINE 1025 "Network/Socket.hsc" #-}
{-# LINE 1026 "Network/Socket.hsc" #-}
{-# LINE 1027 "Network/Socket.hsc" #-}
Just KeepAlive -> Just ((1), (9))
{-# LINE 1028 "Network/Socket.hsc" #-}
{-# LINE 1029 "Network/Socket.hsc" #-}
{-# LINE 1030 "Network/Socket.hsc" #-}
Just OOBInline -> Just ((1), (10))
{-# LINE 1031 "Network/Socket.hsc" #-}
{-# LINE 1032 "Network/Socket.hsc" #-}
{-# LINE 1033 "Network/Socket.hsc" #-}
Just Linger -> Just ((1), (13))
{-# LINE 1034 "Network/Socket.hsc" #-}
{-# LINE 1035 "Network/Socket.hsc" #-}
{-# LINE 1036 "Network/Socket.hsc" #-}
Just ReusePort -> Just ((1), (15))
{-# LINE 1037 "Network/Socket.hsc" #-}
{-# LINE 1038 "Network/Socket.hsc" #-}
{-# LINE 1039 "Network/Socket.hsc" #-}
Just RecvLowWater -> Just ((1), (18))
{-# LINE 1040 "Network/Socket.hsc" #-}
{-# LINE 1041 "Network/Socket.hsc" #-}
{-# LINE 1042 "Network/Socket.hsc" #-}
Just SendLowWater -> Just ((1), (19))
{-# LINE 1043 "Network/Socket.hsc" #-}
{-# LINE 1044 "Network/Socket.hsc" #-}
{-# LINE 1045 "Network/Socket.hsc" #-}
Just RecvTimeOut -> Just ((1), (20))
{-# LINE 1046 "Network/Socket.hsc" #-}
{-# LINE 1047 "Network/Socket.hsc" #-}
{-# LINE 1048 "Network/Socket.hsc" #-}
Just SendTimeOut -> Just ((1), (21))
{-# LINE 1049 "Network/Socket.hsc" #-}
{-# LINE 1050 "Network/Socket.hsc" #-}
{-# LINE 1053 "Network/Socket.hsc" #-}
{-# LINE 1054 "Network/Socket.hsc" #-}
{-# LINE 1055 "Network/Socket.hsc" #-}
{-# LINE 1056 "Network/Socket.hsc" #-}
Just TimeToLive -> Just ((0), (2))
{-# LINE 1057 "Network/Socket.hsc" #-}
{-# LINE 1058 "Network/Socket.hsc" #-}
{-# LINE 1059 "Network/Socket.hsc" #-}
{-# LINE 1060 "Network/Socket.hsc" #-}
{-# LINE 1061 "Network/Socket.hsc" #-}
Just MaxSegment -> Just ((6), (2))
{-# LINE 1062 "Network/Socket.hsc" #-}
{-# LINE 1063 "Network/Socket.hsc" #-}
{-# LINE 1064 "Network/Socket.hsc" #-}
Just NoDelay -> Just ((6), (1))
{-# LINE 1065 "Network/Socket.hsc" #-}
{-# LINE 1066 "Network/Socket.hsc" #-}
{-# LINE 1067 "Network/Socket.hsc" #-}
Just UserTimeout -> Just ((6), (18))
{-# LINE 1068 "Network/Socket.hsc" #-}
{-# LINE 1069 "Network/Socket.hsc" #-}
{-# LINE 1070 "Network/Socket.hsc" #-}
Just Cork -> Just ((6), (3))
{-# LINE 1071 "Network/Socket.hsc" #-}
{-# LINE 1072 "Network/Socket.hsc" #-}
{-# LINE 1073 "Network/Socket.hsc" #-}
{-# LINE 1074 "Network/Socket.hsc" #-}
{-# LINE 1075 "Network/Socket.hsc" #-}
Just IPv6Only -> Just ((41), (26))
{-# LINE 1076 "Network/Socket.hsc" #-}
{-# LINE 1077 "Network/Socket.hsc" #-}
{-# LINE 1078 "Network/Socket.hsc" #-}
Just (CustomSockOpt opt) -> Just opt
_ -> Nothing
packSocketOption' :: String -> SocketOption -> IO (CInt, CInt)
packSocketOption' caller so = maybe err return (packSocketOption so)
where
err = ioError . userError . concat $ ["Network.Socket.", caller,
": socket option ", show so, " unsupported on this system"]
setSocketOption :: Socket
-> SocketOption
-> Int
-> IO ()
setSocketOption (MkSocket s _ _ _ _) so v = do
(level, opt) <- packSocketOption' "setSocketOption" so
with (fromIntegral v) $ \ptr_v -> do
throwSocketErrorIfMinus1_ "Network.Socket.setSocketOption" $
c_setsockopt s level opt ptr_v
(fromIntegral (sizeOf (undefined :: CInt)))
return ()
getSocketOption :: Socket
-> SocketOption
-> IO Int
getSocketOption (MkSocket s _ _ _ _) so = do
(level, opt) <- packSocketOption' "getSocketOption" so
alloca $ \ptr_v ->
with (fromIntegral (sizeOf (undefined :: CInt))) $ \ptr_sz -> do
throwSocketErrorIfMinus1Retry_ "Network.Socket.getSocketOption" $
c_getsockopt s level opt ptr_v ptr_sz
fromIntegral `liftM` peek ptr_v
getPeerCredential :: Socket -> IO (Maybe CUInt, Maybe CUInt, Maybe CUInt)
{-# LINE 1133 "Network/Socket.hsc" #-}
getPeerCredential sock = do
(pid, uid, gid) <- getPeerCred sock
if uid == maxBound then
return (Nothing, Nothing, Nothing)
else
return (Just pid, Just uid, Just gid)
{-# LINE 1146 "Network/Socket.hsc" #-}
{-# LINE 1148 "Network/Socket.hsc" #-}
{-# DEPRECATED getPeerCred "Use getPeerCredential instead" #-}
getPeerCred :: Socket -> IO (CUInt, CUInt, CUInt)
getPeerCred sock = do
{-# LINE 1157 "Network/Socket.hsc" #-}
let fd = fdSocket sock
let sz = (12)
{-# LINE 1159 "Network/Socket.hsc" #-}
allocaBytes sz $ \ ptr_cr ->
with (fromIntegral sz) $ \ ptr_sz -> do
_ <- ($) throwSocketErrorIfMinus1Retry "Network.Socket.getPeerCred" $
c_getsockopt fd (1) (17) ptr_cr ptr_sz
{-# LINE 1163 "Network/Socket.hsc" #-}
pid <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) ptr_cr
{-# LINE 1164 "Network/Socket.hsc" #-}
uid <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) ptr_cr
{-# LINE 1165 "Network/Socket.hsc" #-}
gid <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) ptr_cr
{-# LINE 1166 "Network/Socket.hsc" #-}
return (pid, uid, gid)
{-# LINE 1171 "Network/Socket.hsc" #-}
{-# LINE 1187 "Network/Socket.hsc" #-}
{-# LINE 1188 "Network/Socket.hsc" #-}
isUnixDomainSocketAvailable :: Bool
{-# LINE 1194 "Network/Socket.hsc" #-}
isUnixDomainSocketAvailable = True
{-# LINE 1198 "Network/Socket.hsc" #-}
#if !(MIN_VERSION_base(4,3,1))
closeFdWith closer fd = closer fd
#endif
sendFd :: Socket -> CInt -> IO ()
{-# LINE 1207 "Network/Socket.hsc" #-}
sendFd sock outfd = do
_ <- throwSocketErrorWaitWrite sock "Network.Socket.sendFd" $ c_sendFd (fdSocket sock) outfd
return ()
foreign import ccall SAFE_ON_WIN "sendFd" c_sendFd :: CInt -> CInt -> IO CInt
{-# LINE 1214 "Network/Socket.hsc" #-}
recvFd :: Socket -> IO CInt
{-# LINE 1220 "Network/Socket.hsc" #-}
recvFd sock = do
theFd <- throwSocketErrorWaitRead sock "Network.Socket.recvFd" $
c_recvFd (fdSocket sock)
return theFd
foreign import ccall SAFE_ON_WIN "recvFd" c_recvFd :: CInt -> IO CInt
{-# LINE 1228 "Network/Socket.hsc" #-}
{-# DEPRECATED aNY_PORT "Use defaultPort instead" #-}
aNY_PORT :: PortNumber
aNY_PORT = 0
defaultPort :: PortNumber
defaultPort = 0
{-# DEPRECATED iNADDR_ANY "Use getAddrInfo instead" #-}
iNADDR_ANY :: HostAddress
iNADDR_ANY = htonl (0)
{-# LINE 1244 "Network/Socket.hsc" #-}
foreign import CALLCONV unsafe "htonl" htonl :: Word32 -> Word32
foreign import CALLCONV unsafe "ntohl" ntohl :: Word32 -> Word32
{-# DEPRECATED htonl "Use getAddrInfo instead" #-}
{-# DEPRECATED ntohl "Use getAddrInfo instead" #-}
{-# LINE 1254 "Network/Socket.hsc" #-}
{-# DEPRECATED iN6ADDR_ANY "Use getAddrInfo instead" #-}
iN6ADDR_ANY :: HostAddress6
iN6ADDR_ANY = (0, 0, 0, 0)
{-# LINE 1260 "Network/Socket.hsc" #-}
{-# DEPRECATED sOMAXCONN "Use maxListenQueue instead" #-}
sOMAXCONN :: Int
sOMAXCONN = 128
{-# LINE 1264 "Network/Socket.hsc" #-}
{-# DEPRECATED sOL_SOCKET "This is not necessary anymore" #-}
sOL_SOCKET :: Int
sOL_SOCKET = 1
{-# LINE 1268 "Network/Socket.hsc" #-}
{-# LINE 1270 "Network/Socket.hsc" #-}
{-# DEPRECATED sCM_RIGHTS "This is not necessary anymore" #-}
sCM_RIGHTS :: Int
sCM_RIGHTS = 1
{-# LINE 1273 "Network/Socket.hsc" #-}
{-# LINE 1274 "Network/Socket.hsc" #-}
maxListenQueue :: Int
maxListenQueue = sOMAXCONN
data ShutdownCmd
= ShutdownReceive
| ShutdownSend
| ShutdownBoth
deriving Typeable
sdownCmdToInt :: ShutdownCmd -> CInt
sdownCmdToInt ShutdownReceive = 0
sdownCmdToInt ShutdownSend = 1
sdownCmdToInt ShutdownBoth = 2
shutdown :: Socket -> ShutdownCmd -> IO ()
shutdown (MkSocket s _ _ _ _) stype = do
throwSocketErrorIfMinus1Retry_ "Network.Socket.shutdown" $
c_shutdown s (sdownCmdToInt stype)
return ()
close :: Socket -> IO ()
close (MkSocket s _ _ _ socketStatus) = modifyMVar_ socketStatus $ \ status ->
case status of
ConvertedToHandle -> return ConvertedToHandle
Closed -> return Closed
_ -> do
closeFdWith (void . c_close . fromIntegral) (fromIntegral s)
return Closed
close' :: Socket -> IO ()
close' (MkSocket s _ _ _ socketStatus) = modifyMVar_ socketStatus $ \ status ->
case status of
ConvertedToHandle -> ioError (userError ("close: converted to a Handle, use hClose instead"))
Closed -> return Closed
_ -> do
closeFdWith (closeFd . fromIntegral) (fromIntegral s)
return Closed
isConnected :: Socket -> IO Bool
isConnected (MkSocket _ _ _ _ status) = do
value <- readMVar status
return (value == Connected)
{-# DEPRECATED isConnected "SocketStatus will be removed" #-}
isBound :: Socket -> IO Bool
isBound (MkSocket _ _ _ _ status) = do
value <- readMVar status
return (value == Bound)
{-# DEPRECATED isBound "SocketStatus will be removed" #-}
isListening :: Socket -> IO Bool
isListening (MkSocket _ _ _ _ status) = do
value <- readMVar status
return (value == Listening)
{-# DEPRECATED isListening "SocketStatus will be removed" #-}
isReadable :: Socket -> IO Bool
isReadable (MkSocket _ _ _ _ status) = do
value <- readMVar status
return (value == Listening || value == Connected)
{-# DEPRECATED isReadable "SocketStatus will be removed" #-}
isWritable :: Socket -> IO Bool
isWritable = isReadable
{-# DEPRECATED isWritable "SocketStatus will be removed" #-}
isAcceptable :: Family -> SocketType -> SocketStatus -> Bool
{-# LINE 1381 "Network/Socket.hsc" #-}
isAcceptable AF_UNIX sockTyp status
| sockTyp == Stream || sockTyp == SeqPacket =
status == Connected || status == Bound || status == Listening
isAcceptable AF_UNIX _ _ = False
{-# LINE 1386 "Network/Socket.hsc" #-}
isAcceptable _ _ status = status == Connected || status == Listening
{-# DEPRECATED isAcceptable "SocketStatus will be removed" #-}
{-# DEPRECATED inet_addr "Use \"getAddrInfo\" instead" #-}
inet_addr :: String -> IO HostAddress
inet_addr ipstr = withSocketsDo $ do
withCString ipstr $ \str -> do
had <- c_inet_addr str
if had == maxBound
then ioError $ userError $
"Network.Socket.inet_addr: Malformed address: " ++ ipstr
else return had
{-# DEPRECATED inet_ntoa "Use \"getNameInfo\" instead" #-}
inet_ntoa :: HostAddress -> IO String
inet_ntoa haddr = withSocketsDo $ do
pstr <- c_inet_ntoa haddr
peekCString pstr
socketToHandle :: Socket -> IOMode -> IO Handle
socketToHandle s@(MkSocket fd _ _ _ socketStatus) mode = do
modifyMVar socketStatus $ \ status ->
if status == ConvertedToHandle
then ioError (userError ("socketToHandle: already a Handle"))
else do
h <- fdToHandle' (fromIntegral fd) (Just GHC.IO.Device.Stream) True (show s) mode True
hSetBuffering h NoBuffering
return (ConvertedToHandle, h)
packBits :: (Eq a, Num b, Bits b) => [(a, b)] -> [a] -> b
packBits mapping xs = foldl' pack 0 mapping
where pack acc (k, v) | k `elem` xs = acc .|. v
| otherwise = acc
unpackBits :: (Num b, Bits b) => [(a, b)] -> b -> [a]
unpackBits [] _ = []
unpackBits ((k,v):xs) r
| r .&. v /= 0 = k : unpackBits xs (r .&. complement v)
| otherwise = unpackBits xs r
{-# LINE 1454 "Network/Socket.hsc" #-}
data AddrInfoFlag =
AI_ADDRCONFIG
| AI_ALL
| AI_CANONNAME
| AI_NUMERICHOST
| AI_NUMERICSERV
| AI_PASSIVE
| AI_V4MAPPED
deriving (Eq, Read, Show, Typeable)
aiFlagMapping :: [(AddrInfoFlag, CInt)]
aiFlagMapping =
[
{-# LINE 1495 "Network/Socket.hsc" #-}
(AI_ADDRCONFIG, 32),
{-# LINE 1496 "Network/Socket.hsc" #-}
{-# LINE 1499 "Network/Socket.hsc" #-}
{-# LINE 1500 "Network/Socket.hsc" #-}
(AI_ALL, 16),
{-# LINE 1501 "Network/Socket.hsc" #-}
{-# LINE 1504 "Network/Socket.hsc" #-}
(AI_CANONNAME, 2),
{-# LINE 1505 "Network/Socket.hsc" #-}
(AI_NUMERICHOST, 4),
{-# LINE 1506 "Network/Socket.hsc" #-}
{-# LINE 1507 "Network/Socket.hsc" #-}
(AI_NUMERICSERV, 1024),
{-# LINE 1508 "Network/Socket.hsc" #-}
{-# LINE 1511 "Network/Socket.hsc" #-}
(AI_PASSIVE, 1),
{-# LINE 1512 "Network/Socket.hsc" #-}
{-# LINE 1513 "Network/Socket.hsc" #-}
(AI_V4MAPPED, 8)
{-# LINE 1514 "Network/Socket.hsc" #-}
{-# LINE 1517 "Network/Socket.hsc" #-}
]
addrInfoFlagImplemented :: AddrInfoFlag -> Bool
addrInfoFlagImplemented f = packBits aiFlagMapping [f] /= 0
data AddrInfo =
AddrInfo {
addrFlags :: [AddrInfoFlag],
addrFamily :: Family,
addrSocketType :: SocketType,
addrProtocol :: ProtocolNumber,
addrAddress :: SockAddr,
addrCanonName :: Maybe String
}
deriving (Eq, Show, Typeable)
instance Storable AddrInfo where
sizeOf _ = 48
{-# LINE 1537 "Network/Socket.hsc" #-}
alignment _ = alignment (undefined :: CInt)
peek p = do
ai_flags <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) p
{-# LINE 1541 "Network/Socket.hsc" #-}
ai_family <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) p
{-# LINE 1542 "Network/Socket.hsc" #-}
ai_socktype <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) p
{-# LINE 1543 "Network/Socket.hsc" #-}
ai_protocol <- ((\hsc_ptr -> peekByteOff hsc_ptr 12)) p
{-# LINE 1544 "Network/Socket.hsc" #-}
ai_addr <- ((\hsc_ptr -> peekByteOff hsc_ptr 24)) p >>= peekSockAddr
{-# LINE 1545 "Network/Socket.hsc" #-}
ai_canonname_ptr <- ((\hsc_ptr -> peekByteOff hsc_ptr 32)) p
{-# LINE 1546 "Network/Socket.hsc" #-}
ai_canonname <- if ai_canonname_ptr == nullPtr
then return Nothing
else liftM Just $ peekCString ai_canonname_ptr
socktype <- unpackSocketType' "AddrInfo.peek" ai_socktype
return (AddrInfo
{
addrFlags = unpackBits aiFlagMapping ai_flags,
addrFamily = unpackFamily ai_family,
addrSocketType = socktype,
addrProtocol = ai_protocol,
addrAddress = ai_addr,
addrCanonName = ai_canonname
})
poke p (AddrInfo flags family socketType protocol _ _) = do
c_stype <- packSocketTypeOrThrow "AddrInfo.poke" socketType
((\hsc_ptr -> pokeByteOff hsc_ptr 0)) p (packBits aiFlagMapping flags)
{-# LINE 1566 "Network/Socket.hsc" #-}
((\hsc_ptr -> pokeByteOff hsc_ptr 4)) p (packFamily family)
{-# LINE 1567 "Network/Socket.hsc" #-}
((\hsc_ptr -> pokeByteOff hsc_ptr 8)) p c_stype
{-# LINE 1568 "Network/Socket.hsc" #-}
((\hsc_ptr -> pokeByteOff hsc_ptr 12)) p protocol
{-# LINE 1569 "Network/Socket.hsc" #-}
((\hsc_ptr -> pokeByteOff hsc_ptr 16)) p (0::CSize)
{-# LINE 1573 "Network/Socket.hsc" #-}
((\hsc_ptr -> pokeByteOff hsc_ptr 24)) p nullPtr
{-# LINE 1574 "Network/Socket.hsc" #-}
((\hsc_ptr -> pokeByteOff hsc_ptr 32)) p nullPtr
{-# LINE 1575 "Network/Socket.hsc" #-}
((\hsc_ptr -> pokeByteOff hsc_ptr 40)) p nullPtr
{-# LINE 1576 "Network/Socket.hsc" #-}
data NameInfoFlag =
NI_DGRAM
| NI_NAMEREQD
| NI_NOFQDN
| NI_NUMERICHOST
| NI_NUMERICSERV
deriving (Eq, Read, Show, Typeable)
niFlagMapping :: [(NameInfoFlag, CInt)]
niFlagMapping = [(NI_DGRAM, 16),
{-# LINE 1604 "Network/Socket.hsc" #-}
(NI_NAMEREQD, 8),
{-# LINE 1605 "Network/Socket.hsc" #-}
(NI_NOFQDN, 4),
{-# LINE 1606 "Network/Socket.hsc" #-}
(NI_NUMERICHOST, 1),
{-# LINE 1607 "Network/Socket.hsc" #-}
(NI_NUMERICSERV, 2)]
{-# LINE 1608 "Network/Socket.hsc" #-}
defaultHints :: AddrInfo
defaultHints = AddrInfo {
addrFlags = [],
addrFamily = AF_UNSPEC,
addrSocketType = NoSocketType,
addrProtocol = defaultProtocol,
addrAddress = undefined,
addrCanonName = undefined
}
showDefaultHints :: AddrInfo -> String
showDefaultHints AddrInfo{..} = concat
[ "AddrInfo {"
, "addrFlags = "
, show addrFlags
, ", addrFamily = "
, show addrFamily
, ", addrSocketType = "
, show addrSocketType
, ", addrProtocol = "
, show addrProtocol
, ", addrAddress = "
, "<assumed to be undefined>"
, ", addrCanonName = "
, "<assumed to be undefined>"
, "}"
]
getAddrInfo :: Maybe AddrInfo
-> Maybe HostName
-> Maybe ServiceName
-> IO [AddrInfo]
getAddrInfo hints node service = withSocketsDo $
maybeWith withCString node $ \c_node ->
maybeWith withCString service $ \c_service ->
maybeWith with filteredHints $ \c_hints ->
alloca $ \ptr_ptr_addrs -> do
ret <- c_getaddrinfo c_node c_service c_hints ptr_ptr_addrs
case ret of
0 -> do ptr_addrs <- peek ptr_ptr_addrs
ais <- followAddrInfo ptr_addrs
c_freeaddrinfo ptr_addrs
return ais
_ -> do err <- gai_strerror ret
let message = concat
[ "Network.Socket.getAddrInfo (called with preferred socket type/protocol: "
, maybe (show hints) showDefaultHints hints
, ", host name: "
, show node
, ", service name: "
, show service
, ")"
]
ioError (ioeSetErrorString
(mkIOError NoSuchThing message Nothing
Nothing) err)
where
{-# LINE 1729 "Network/Socket.hsc" #-}
filteredHints = hints
{-# LINE 1731 "Network/Socket.hsc" #-}
followAddrInfo :: Ptr AddrInfo -> IO [AddrInfo]
followAddrInfo ptr_ai | ptr_ai == nullPtr = return []
| otherwise = do
a <- peek ptr_ai
as <- ((\hsc_ptr -> peekByteOff hsc_ptr 40)) ptr_ai >>= followAddrInfo
{-# LINE 1738 "Network/Socket.hsc" #-}
return (a:as)
foreign import ccall safe "hsnet_getaddrinfo"
c_getaddrinfo :: CString -> CString -> Ptr AddrInfo -> Ptr (Ptr AddrInfo)
-> IO CInt
foreign import ccall safe "hsnet_freeaddrinfo"
c_freeaddrinfo :: Ptr AddrInfo -> IO ()
gai_strerror :: CInt -> IO String
{-# LINE 1750 "Network/Socket.hsc" #-}
gai_strerror n = c_gai_strerror n >>= peekCString
foreign import ccall safe "gai_strerror"
c_gai_strerror :: CInt -> IO CString
{-# LINE 1757 "Network/Socket.hsc" #-}
withCStringIf :: Bool -> Int -> (CSize -> CString -> IO a) -> IO a
withCStringIf False _ f = f 0 nullPtr
withCStringIf True n f = allocaBytes n (f (fromIntegral n))
getNameInfo :: [NameInfoFlag]
-> Bool
-> Bool
-> SockAddr
-> IO (Maybe HostName, Maybe ServiceName)
getNameInfo flags doHost doService addr = withSocketsDo $
withCStringIf doHost (1025) $ \c_hostlen c_host ->
{-# LINE 1784 "Network/Socket.hsc" #-}
withCStringIf doService (32) $ \c_servlen c_serv -> do
{-# LINE 1785 "Network/Socket.hsc" #-}
withSockAddr addr $ \ptr_addr sz -> do
ret <- c_getnameinfo ptr_addr (fromIntegral sz) c_host c_hostlen
c_serv c_servlen (packBits niFlagMapping flags)
case ret of
0 -> do
let peekIf doIf c_val = if doIf
then liftM Just $ peekCString c_val
else return Nothing
host <- peekIf doHost c_host
serv <- peekIf doService c_serv
return (host, serv)
_ -> do err <- gai_strerror ret
let message = concat
[ "Network.Socket.getNameInfo (called with flags: "
, show flags
, ", hostname lookup: "
, show doHost
, ", service name lookup: "
, show doService
, ", socket address: "
, show addr
, ")"
]
ioError (ioeSetErrorString
(mkIOError NoSuchThing message Nothing
Nothing) err)
foreign import ccall safe "hsnet_getnameinfo"
c_getnameinfo :: Ptr SockAddr -> CInt -> CString -> CSize -> CString
-> CSize -> CInt -> IO CInt
{-# LINE 1816 "Network/Socket.hsc" #-}
mkInvalidRecvArgError :: String -> IOError
mkInvalidRecvArgError loc = ioeSetErrorString (mkIOError
InvalidArgument
loc Nothing Nothing) "non-positive length"
mkEOFError :: String -> IOError
mkEOFError loc = ioeSetErrorString (mkIOError EOF loc Nothing Nothing) "end of file"
foreign import ccall unsafe "hsnet_inet_ntoa"
c_inet_ntoa :: HostAddress -> IO (Ptr CChar)
foreign import CALLCONV unsafe "inet_addr"
c_inet_addr :: Ptr CChar -> IO HostAddress
foreign import CALLCONV unsafe "shutdown"
c_shutdown :: CInt -> CInt -> IO CInt
closeFd :: CInt -> IO ()
closeFd fd = throwSocketErrorIfMinus1_ "Network.Socket.close" $ c_close fd
{-# LINE 1841 "Network/Socket.hsc" #-}
foreign import ccall unsafe "close"
c_close :: CInt -> IO CInt
{-# LINE 1847 "Network/Socket.hsc" #-}
foreign import CALLCONV unsafe "socket"
c_socket :: CInt -> CInt -> CInt -> IO CInt
foreign import CALLCONV unsafe "bind"
c_bind :: CInt -> Ptr SockAddr -> CInt -> IO CInt
foreign import CALLCONV SAFE_ON_WIN "connect"
c_connect :: CInt -> Ptr SockAddr -> CInt -> IO CInt
{-# LINE 1855 "Network/Socket.hsc" #-}
foreign import CALLCONV unsafe "accept4"
c_accept4 :: CInt -> Ptr SockAddr -> Ptr CInt -> CInt -> IO CInt
{-# LINE 1861 "Network/Socket.hsc" #-}
foreign import CALLCONV unsafe "listen"
c_listen :: CInt -> CInt -> IO CInt
{-# LINE 1870 "Network/Socket.hsc" #-}
foreign import CALLCONV unsafe "send"
c_send :: CInt -> Ptr a -> CSize -> CInt -> IO CInt
foreign import CALLCONV SAFE_ON_WIN "sendto"
c_sendto :: CInt -> Ptr a -> CSize -> CInt -> Ptr SockAddr -> CInt -> IO CInt
foreign import CALLCONV unsafe "recv"
c_recv :: CInt -> Ptr CChar -> CSize -> CInt -> IO CInt
foreign import CALLCONV SAFE_ON_WIN "recvfrom"
c_recvfrom :: CInt -> Ptr a -> CSize -> CInt -> Ptr SockAddr -> Ptr CInt -> IO CInt
foreign import CALLCONV unsafe "getpeername"
c_getpeername :: CInt -> Ptr SockAddr -> Ptr CInt -> IO CInt
foreign import CALLCONV unsafe "getsockname"
c_getsockname :: CInt -> Ptr SockAddr -> Ptr CInt -> IO CInt
foreign import CALLCONV unsafe "getsockopt"
c_getsockopt :: CInt -> CInt -> CInt -> Ptr CInt -> Ptr CInt -> IO CInt
foreign import CALLCONV unsafe "setsockopt"
c_setsockopt :: CInt -> CInt -> CInt -> Ptr CInt -> CInt -> IO CInt
{-# LINE 1893 "Network/Socket.hsc" #-}
{-# DEPRECATED bindSocket "use 'bind'" #-}
bindSocket :: Socket
-> SockAddr
-> IO ()
bindSocket = bind
{-# DEPRECATED sClose "use 'close'" #-}
sClose :: Socket -> IO ()
sClose = close
{-# DEPRECATED sIsConnected "SocketStatus will be removed" #-}
sIsConnected :: Socket -> IO Bool
sIsConnected = isConnected
{-# DEPRECATED sIsBound "SocketStatus will be removed" #-}
sIsBound :: Socket -> IO Bool
sIsBound = isBound
{-# DEPRECATED sIsListening "SocketStatus will be removed" #-}
sIsListening :: Socket -> IO Bool
sIsListening = isListening
{-# DEPRECATED sIsReadable "SocketStatus will be removed" #-}
sIsReadable :: Socket -> IO Bool
sIsReadable = isReadable
{-# DEPRECATED sIsWritable "SocketStatus will be removed" #-}
sIsWritable :: Socket -> IO Bool
sIsWritable = isWritable
{-# LINE 1941 "Network/Socket.hsc" #-}
ifNameToIndex :: String -> IO (Maybe Int)
ifNameToIndex ifname = do
index <- withCString ifname c_if_nametoindex
return $ if index == 0 then Nothing else Just $ fromIntegral index
ifIndexToName :: Int -> IO (Maybe String)
ifIndexToName ifn = allocaBytes 16 $ \ptr -> do
r <- c_if_indextoname (fromIntegral ifn) ptr
if r == nullPtr then
return Nothing
else
Just <$> peekCString ptr
foreign import CALLCONV safe "if_nametoindex"
c_if_nametoindex :: CString -> IO CUInt
foreign import CALLCONV safe "if_indextoname"
c_if_indextoname :: CUInt -> CString -> IO CString
{-# LINE 1967 "Network/Socket.hsc" #-}