{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -Wno-deprecations #-}
module Effectful.Network
( Network
, runNetwork
, accept
, bind
, close
, close'
, connect
, fdSocket
, getAddrInfo
, getCloseOnExec
, getNameInfo
, getNonBlock
, getPeerCredential
, getPeerName
, getSockOpt
, getSocketName
, getSocketOption
, getSocketType
, gracefulClose
, ifIndexToName
, ifNameToIndex
, listen
, mkSocket
, openSocket
, recvBuf
, recvBufFrom
, recvBufMsg
, recvFd
, sendBuf
, sendBufMsg
, sendBufTo
, sendFd
, setCloseOnExecIfNeeded
, setNonBlockIfNeeded
, setSockOpt
, setSocketOption
, shutdown
, socket
, socketPair
, socketPort
, socketPortSafe
, socketToFd
, socketToHandle
, touchSocket
, unsafeFdSocket
, whenSupported
, withFdSocket
, withSocketsDo
, recvFrom
, recv
, sendAllTo
, sendTo
, sendAll
, send
, module Data.Word
, module Foreign.C.Types
, module Foreign.Ptr
, module Foreign.Storable
, module GHC.IO.Handle.Types
, module Network.Socket
, module System.IO
) where
import Effectful
( Dispatch (Static)
, DispatchOf
, Eff
, Effect
, IOE
, type (:>)
)
import Effectful.Dispatch.Static
( SideEffects (WithSideEffects)
, StaticRep
, evalStaticRep
, unsafeEff_
, unsafeLiftMapIO
, unsafeSeqUnliftIO
)
import Data.ByteString (StrictByteString)
import Data.Word (Word8)
import Foreign.C.Types (CInt, CUInt)
import Foreign.Ptr (Ptr)
import Foreign.Storable (Storable)
import GHC.IO.Handle.Types (Handle)
import Network.Socket
( AddrInfo (..)
, Cmsg (..)
, Family (..)
, HostName
, MsgFlag (..)
, NameInfoFlag (..)
, PortNumber
, ProtocolNumber
, ServiceName
, ShutdownCmd (..)
, SockAddr (..)
, Socket
, SocketOption (..)
, SocketType (..)
)
import Network.Socket qualified as S
import Network.Socket.ByteString qualified as S
import System.IO (IOMode)
data Network :: Effect
type instance DispatchOf Network = 'Static 'WithSideEffects
newtype instance StaticRep Network = Unit ()
runNetwork :: (IOE :> es) => Eff (Network : es) a -> Eff es a
runNetwork :: forall (es :: [Effect]) a.
(IOE :> es) =>
Eff (Network : es) a -> Eff es a
runNetwork = StaticRep Network -> Eff (Network : es) a -> Eff es a
forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect])
a.
(HasCallStack, DispatchOf e ~ 'Static sideEffects,
MaybeIOE sideEffects es) =>
StaticRep e -> Eff (e : es) a -> Eff es a
evalStaticRep (() -> StaticRep Network
Unit ())
getAddrInfo
:: (Network :> es)
=> Maybe AddrInfo
-> Maybe HostName
-> Maybe ServiceName
-> Eff es [AddrInfo]
getAddrInfo :: forall (es :: [Effect]).
(Network :> es) =>
Maybe AddrInfo
-> Maybe HostName -> Maybe HostName -> Eff es [AddrInfo]
getAddrInfo Maybe AddrInfo
addrInfo Maybe HostName
hostName Maybe HostName
serviceName = IO [AddrInfo] -> Eff es [AddrInfo]
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO [AddrInfo] -> Eff es [AddrInfo])
-> IO [AddrInfo] -> Eff es [AddrInfo]
forall a b. (a -> b) -> a -> b
$ Maybe AddrInfo -> Maybe HostName -> Maybe HostName -> IO [AddrInfo]
forall (t :: * -> *).
GetAddrInfo t =>
Maybe AddrInfo
-> Maybe HostName -> Maybe HostName -> IO (t AddrInfo)
S.getAddrInfo Maybe AddrInfo
addrInfo Maybe HostName
hostName Maybe HostName
serviceName
{-# INLINE getAddrInfo #-}
withSocketsDo :: (Network :> es) => Eff es a -> Eff es a
withSocketsDo :: forall (es :: [Effect]) a. (Network :> es) => Eff es a -> Eff es a
withSocketsDo = (IO a -> IO a) -> Eff es a -> Eff es a
forall a b (es :: [Effect]).
HasCallStack =>
(IO a -> IO b) -> Eff es a -> Eff es b
unsafeLiftMapIO IO a -> IO a
forall a. IO a -> IO a
S.withSocketsDo
{-# INLINE withSocketsDo #-}
connect :: (Network :> es) => Socket -> SockAddr -> Eff es ()
connect :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> SockAddr -> Eff es ()
connect Socket
sock SockAddr
sockAddr = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> IO () -> Eff es ()
forall a b. (a -> b) -> a -> b
$ Socket -> SockAddr -> IO ()
S.connect Socket
sock SockAddr
sockAddr
{-# INLINE connect #-}
bind :: (Network :> es) => Socket -> SockAddr -> Eff es ()
bind :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> SockAddr -> Eff es ()
bind Socket
sock SockAddr
sockAddr = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> IO () -> Eff es ()
forall a b. (a -> b) -> a -> b
$ Socket -> SockAddr -> IO ()
S.bind Socket
sock SockAddr
sockAddr
{-# INLINE bind #-}
listen :: (Network :> es) => Socket -> Int -> Eff es ()
listen :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> Int -> Eff es ()
listen Socket
sock Int
n = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> IO () -> Eff es ()
forall a b. (a -> b) -> a -> b
$ Socket -> Int -> IO ()
S.listen Socket
sock Int
n
{-# INLINE listen #-}
accept :: (Network :> es) => Socket -> Eff es (Socket, SockAddr)
accept :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> Eff es (Socket, SockAddr)
accept Socket
sock = IO (Socket, SockAddr) -> Eff es (Socket, SockAddr)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (Socket, SockAddr) -> Eff es (Socket, SockAddr))
-> IO (Socket, SockAddr) -> Eff es (Socket, SockAddr)
forall a b. (a -> b) -> a -> b
$ Socket -> IO (Socket, SockAddr)
S.accept Socket
sock
{-# INLINE accept #-}
close :: (Network :> es) => Socket -> Eff es ()
close :: forall (es :: [Effect]). (Network :> es) => Socket -> Eff es ()
close = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (Socket -> IO ()) -> Socket -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> IO ()
S.close
{-# INLINE close #-}
close' :: (Network :> es) => Socket -> Eff es ()
close' :: forall (es :: [Effect]). (Network :> es) => Socket -> Eff es ()
close' = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (Socket -> IO ()) -> Socket -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> IO ()
S.close
{-# INLINE close' #-}
gracefulClose :: (Network :> es) => Socket -> Int -> Eff es ()
gracefulClose :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> Int -> Eff es ()
gracefulClose Socket
sock = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (Int -> IO ()) -> Int -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> Int -> IO ()
S.gracefulClose Socket
sock
{-# INLINE gracefulClose #-}
shutdown
:: (Network :> es) => Socket -> ShutdownCmd -> Eff es ()
shutdown :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> ShutdownCmd -> Eff es ()
shutdown Socket
sock = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (ShutdownCmd -> IO ()) -> ShutdownCmd -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> ShutdownCmd -> IO ()
S.shutdown Socket
sock
{-# INLINE shutdown #-}
whenSupported
:: (Network :> es) => SocketOption -> Eff es a -> Eff es ()
whenSupported :: forall (es :: [Effect]) a.
(Network :> es) =>
SocketOption -> Eff es a -> Eff es ()
whenSupported = (IO a -> IO ()) -> Eff es a -> Eff es ()
forall a b (es :: [Effect]).
HasCallStack =>
(IO a -> IO b) -> Eff es a -> Eff es b
unsafeLiftMapIO ((IO a -> IO ()) -> Eff es a -> Eff es ())
-> (SocketOption -> IO a -> IO ())
-> SocketOption
-> Eff es a
-> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SocketOption -> IO a -> IO ()
forall a. SocketOption -> IO a -> IO ()
S.whenSupported
{-# INLINE whenSupported #-}
getSocketOption
:: (Network :> es) => Socket -> SocketOption -> Eff es Int
getSocketOption :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> SocketOption -> Eff es Int
getSocketOption Socket
sock = IO Int -> Eff es Int
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Int -> Eff es Int)
-> (SocketOption -> IO Int) -> SocketOption -> Eff es Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> SocketOption -> IO Int
S.getSocketOption Socket
sock
{-# INLINE getSocketOption #-}
setSocketOption
:: (Network :> es) => Socket -> SocketOption -> Int -> Eff es ()
setSocketOption :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> SocketOption -> Int -> Eff es ()
setSocketOption Socket
sock SocketOption
sockOpt = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (Int -> IO ()) -> Int -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> SocketOption -> Int -> IO ()
S.setSocketOption Socket
sock SocketOption
sockOpt
{-# INLINE setSocketOption #-}
getSockOpt
:: (Network :> es)
=> forall a
. (Storable a)
=> Socket
-> SocketOption
-> Eff es a
getSockOpt :: forall (es :: [Effect]) a.
(Network :> es, Storable a) =>
Socket -> SocketOption -> Eff es a
getSockOpt Socket
sock = IO a -> Eff es a
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO a -> Eff es a)
-> (SocketOption -> IO a) -> SocketOption -> Eff es a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> SocketOption -> IO a
forall a. Storable a => Socket -> SocketOption -> IO a
S.getSockOpt Socket
sock
{-# INLINE getSockOpt #-}
setSockOpt
:: (Network :> es) => (Storable a) => Socket -> SocketOption -> a -> Eff es ()
setSockOpt :: forall (es :: [Effect]) a.
(Network :> es, Storable a) =>
Socket -> SocketOption -> a -> Eff es ()
setSockOpt Socket
sock SocketOption
sockOpt = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (a -> IO ()) -> a -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> SocketOption -> a -> IO ()
forall a. Storable a => Socket -> SocketOption -> a -> IO ()
S.setSockOpt Socket
sock SocketOption
sockOpt
{-# INLINE setSockOpt #-}
socket
:: (Network :> es) => Family -> SocketType -> ProtocolNumber -> Eff es Socket
socket :: forall (es :: [Effect]).
(Network :> es) =>
Family -> SocketType -> ProtocolNumber -> Eff es Socket
socket Family
fam SocketType
sockType = IO Socket -> Eff es Socket
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Socket -> Eff es Socket)
-> (ProtocolNumber -> IO Socket) -> ProtocolNumber -> Eff es Socket
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Family -> SocketType -> ProtocolNumber -> IO Socket
S.socket Family
fam SocketType
sockType
{-# INLINE socket #-}
openSocket :: (Network :> es) => AddrInfo -> Eff es Socket
openSocket :: forall (es :: [Effect]).
(Network :> es) =>
AddrInfo -> Eff es Socket
openSocket = IO Socket -> Eff es Socket
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Socket -> Eff es Socket)
-> (AddrInfo -> IO Socket) -> AddrInfo -> Eff es Socket
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AddrInfo -> IO Socket
S.openSocket
{-# INLINE openSocket #-}
withFdSocket
:: (Network :> es) => Socket -> (CInt -> Eff es r) -> Eff es r
withFdSocket :: forall (es :: [Effect]) r.
(Network :> es) =>
Socket -> (ProtocolNumber -> Eff es r) -> Eff es r
withFdSocket Socket
sock ProtocolNumber -> Eff es r
cb = ((forall r. Eff es r -> IO r) -> IO r) -> Eff es r
forall (es :: [Effect]) a.
HasCallStack =>
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
unsafeSeqUnliftIO (((forall r. Eff es r -> IO r) -> IO r) -> Eff es r)
-> ((forall r. Eff es r -> IO r) -> IO r) -> Eff es r
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
Socket -> (ProtocolNumber -> IO r) -> IO r
forall r. Socket -> (ProtocolNumber -> IO r) -> IO r
S.withFdSocket Socket
sock (Eff es r -> IO r
forall r. Eff es r -> IO r
unlift (Eff es r -> IO r)
-> (ProtocolNumber -> Eff es r) -> ProtocolNumber -> IO r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProtocolNumber -> Eff es r
cb)
{-# INLINE withFdSocket #-}
unsafeFdSocket :: (Network :> es) => Socket -> Eff es CInt
unsafeFdSocket :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> Eff es ProtocolNumber
unsafeFdSocket = IO ProtocolNumber -> Eff es ProtocolNumber
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO ProtocolNumber -> Eff es ProtocolNumber)
-> (Socket -> IO ProtocolNumber) -> Socket -> Eff es ProtocolNumber
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> IO ProtocolNumber
S.unsafeFdSocket
{-# INLINE unsafeFdSocket #-}
touchSocket :: (Network :> es) => Socket -> Eff es ()
touchSocket :: forall (es :: [Effect]). (Network :> es) => Socket -> Eff es ()
touchSocket = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (Socket -> IO ()) -> Socket -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> IO ()
S.touchSocket
{-# INLINE touchSocket #-}
socketToFd :: (Network :> es) => Socket -> Eff es CInt
socketToFd :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> Eff es ProtocolNumber
socketToFd = IO ProtocolNumber -> Eff es ProtocolNumber
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO ProtocolNumber -> Eff es ProtocolNumber)
-> (Socket -> IO ProtocolNumber) -> Socket -> Eff es ProtocolNumber
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> IO ProtocolNumber
S.socketToFd
{-# INLINE socketToFd #-}
fdSocket :: (Network :> es) => Socket -> Eff es CInt
fdSocket :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> Eff es ProtocolNumber
fdSocket = IO ProtocolNumber -> Eff es ProtocolNumber
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO ProtocolNumber -> Eff es ProtocolNumber)
-> (Socket -> IO ProtocolNumber) -> Socket -> Eff es ProtocolNumber
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> IO ProtocolNumber
S.fdSocket
{-# INLINE fdSocket #-}
{-# DEPRECATED fdSocket "Use withFdSocket or unsafeFdSocket instead" #-}
mkSocket :: (Network :> es) => CInt -> Eff es Socket
mkSocket :: forall (es :: [Effect]).
(Network :> es) =>
ProtocolNumber -> Eff es Socket
mkSocket = IO Socket -> Eff es Socket
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Socket -> Eff es Socket)
-> (ProtocolNumber -> IO Socket) -> ProtocolNumber -> Eff es Socket
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProtocolNumber -> IO Socket
S.mkSocket
{-# INLINE mkSocket #-}
socketToHandle
:: (Network :> es) => Socket -> IOMode -> Eff es Handle
socketToHandle :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> IOMode -> Eff es Handle
socketToHandle Socket
sock = IO Handle -> Eff es Handle
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Handle -> Eff es Handle)
-> (IOMode -> IO Handle) -> IOMode -> Eff es Handle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> IOMode -> IO Handle
S.socketToHandle Socket
sock
{-# INLINE socketToHandle #-}
getSocketType :: (Network :> es) => Socket -> Eff es SocketType
getSocketType :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> Eff es SocketType
getSocketType = IO SocketType -> Eff es SocketType
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO SocketType -> Eff es SocketType)
-> (Socket -> IO SocketType) -> Socket -> Eff es SocketType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> IO SocketType
S.getSocketType
{-# INLINE getSocketType #-}
getPeerName :: (Network :> es) => Socket -> Eff es SockAddr
getPeerName :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> Eff es SockAddr
getPeerName = IO SockAddr -> Eff es SockAddr
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO SockAddr -> Eff es SockAddr)
-> (Socket -> IO SockAddr) -> Socket -> Eff es SockAddr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> IO SockAddr
S.getPeerName
{-# INLINE getPeerName #-}
getSocketName :: (Network :> es) => Socket -> Eff es SockAddr
getSocketName :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> Eff es SockAddr
getSocketName = IO SockAddr -> Eff es SockAddr
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO SockAddr -> Eff es SockAddr)
-> (Socket -> IO SockAddr) -> Socket -> Eff es SockAddr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> IO SockAddr
S.getSocketName
{-# INLINE getSocketName #-}
ifNameToIndex :: (Network :> es) => String -> Eff es (Maybe Int)
ifNameToIndex :: forall (es :: [Effect]).
(Network :> es) =>
HostName -> Eff es (Maybe Int)
ifNameToIndex = IO (Maybe Int) -> Eff es (Maybe Int)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (Maybe Int) -> Eff es (Maybe Int))
-> (HostName -> IO (Maybe Int)) -> HostName -> Eff es (Maybe Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HostName -> IO (Maybe Int)
S.ifNameToIndex
{-# INLINE ifNameToIndex #-}
ifIndexToName :: (Network :> es) => Int -> Eff es (Maybe String)
ifIndexToName :: forall (es :: [Effect]).
(Network :> es) =>
Int -> Eff es (Maybe HostName)
ifIndexToName = IO (Maybe HostName) -> Eff es (Maybe HostName)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (Maybe HostName) -> Eff es (Maybe HostName))
-> (Int -> IO (Maybe HostName)) -> Int -> Eff es (Maybe HostName)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> IO (Maybe HostName)
S.ifIndexToName
{-# INLINE ifIndexToName #-}
socketPortSafe
:: (Network :> es) => Socket -> Eff es (Maybe PortNumber)
socketPortSafe :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> Eff es (Maybe PortNumber)
socketPortSafe = IO (Maybe PortNumber) -> Eff es (Maybe PortNumber)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (Maybe PortNumber) -> Eff es (Maybe PortNumber))
-> (Socket -> IO (Maybe PortNumber))
-> Socket
-> Eff es (Maybe PortNumber)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> IO (Maybe PortNumber)
S.socketPortSafe
{-# INLINE socketPortSafe #-}
socketPort :: (Network :> es) => Socket -> Eff es PortNumber
socketPort :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> Eff es PortNumber
socketPort = IO PortNumber -> Eff es PortNumber
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO PortNumber -> Eff es PortNumber)
-> (Socket -> IO PortNumber) -> Socket -> Eff es PortNumber
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> IO PortNumber
S.socketPort
{-# INLINE socketPort #-}
socketPair
:: (Network :> es)
=> Family
-> SocketType
-> ProtocolNumber
-> Eff es (Socket, Socket)
socketPair :: forall (es :: [Effect]).
(Network :> es) =>
Family -> SocketType -> ProtocolNumber -> Eff es (Socket, Socket)
socketPair Family
fam SocketType
sock = IO (Socket, Socket) -> Eff es (Socket, Socket)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (Socket, Socket) -> Eff es (Socket, Socket))
-> (ProtocolNumber -> IO (Socket, Socket))
-> ProtocolNumber
-> Eff es (Socket, Socket)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Family -> SocketType -> ProtocolNumber -> IO (Socket, Socket)
S.socketPair Family
fam SocketType
sock
{-# INLINE socketPair #-}
sendFd :: (Network :> es) => Socket -> CInt -> Eff es ()
sendFd :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> ProtocolNumber -> Eff es ()
sendFd Socket
sock = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (ProtocolNumber -> IO ()) -> ProtocolNumber -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> ProtocolNumber -> IO ()
S.sendFd Socket
sock
{-# INLINE sendFd #-}
recvFd :: (Network :> es) => Socket -> Eff es CInt
recvFd :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> Eff es ProtocolNumber
recvFd = IO ProtocolNumber -> Eff es ProtocolNumber
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO ProtocolNumber -> Eff es ProtocolNumber)
-> (Socket -> IO ProtocolNumber) -> Socket -> Eff es ProtocolNumber
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> IO ProtocolNumber
S.recvFd
{-# INLINE recvFd #-}
getPeerCredential
:: (Network :> es) => Socket -> Eff es (Maybe CUInt, Maybe CUInt, Maybe CUInt)
getPeerCredential :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> Eff es (Maybe CUInt, Maybe CUInt, Maybe CUInt)
getPeerCredential = IO (Maybe CUInt, Maybe CUInt, Maybe CUInt)
-> Eff es (Maybe CUInt, Maybe CUInt, Maybe CUInt)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (Maybe CUInt, Maybe CUInt, Maybe CUInt)
-> Eff es (Maybe CUInt, Maybe CUInt, Maybe CUInt))
-> (Socket -> IO (Maybe CUInt, Maybe CUInt, Maybe CUInt))
-> Socket
-> Eff es (Maybe CUInt, Maybe CUInt, Maybe CUInt)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> IO (Maybe CUInt, Maybe CUInt, Maybe CUInt)
S.getPeerCredential
{-# INLINE getPeerCredential #-}
getNameInfo
:: (Network :> es)
=> [NameInfoFlag]
-> Bool
-> Bool
-> SockAddr
-> Eff es (Maybe HostName, Maybe ServiceName)
getNameInfo :: forall (es :: [Effect]).
(Network :> es) =>
[NameInfoFlag]
-> Bool
-> Bool
-> SockAddr
-> Eff es (Maybe HostName, Maybe HostName)
getNameInfo [NameInfoFlag]
flag Bool
b1 Bool
b2 = IO (Maybe HostName, Maybe HostName)
-> Eff es (Maybe HostName, Maybe HostName)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (Maybe HostName, Maybe HostName)
-> Eff es (Maybe HostName, Maybe HostName))
-> (SockAddr -> IO (Maybe HostName, Maybe HostName))
-> SockAddr
-> Eff es (Maybe HostName, Maybe HostName)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [NameInfoFlag]
-> Bool -> Bool -> SockAddr -> IO (Maybe HostName, Maybe HostName)
S.getNameInfo [NameInfoFlag]
flag Bool
b1 Bool
b2
{-# INLINE getNameInfo #-}
setCloseOnExecIfNeeded :: (Network :> es) => CInt -> Eff es ()
setCloseOnExecIfNeeded :: forall (es :: [Effect]).
(Network :> es) =>
ProtocolNumber -> Eff es ()
setCloseOnExecIfNeeded = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (ProtocolNumber -> IO ()) -> ProtocolNumber -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProtocolNumber -> IO ()
S.setCloseOnExecIfNeeded
{-# INLINE setCloseOnExecIfNeeded #-}
getCloseOnExec :: (Network :> es) => CInt -> Eff es Bool
getCloseOnExec :: forall (es :: [Effect]).
(Network :> es) =>
ProtocolNumber -> Eff es Bool
getCloseOnExec = IO Bool -> Eff es Bool
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Bool -> Eff es Bool)
-> (ProtocolNumber -> IO Bool) -> ProtocolNumber -> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProtocolNumber -> IO Bool
S.getCloseOnExec
{-# INLINE getCloseOnExec #-}
setNonBlockIfNeeded :: (Network :> es) => CInt -> Eff es ()
setNonBlockIfNeeded :: forall (es :: [Effect]).
(Network :> es) =>
ProtocolNumber -> Eff es ()
setNonBlockIfNeeded = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (ProtocolNumber -> IO ()) -> ProtocolNumber -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProtocolNumber -> IO ()
S.setNonBlockIfNeeded
{-# INLINE setNonBlockIfNeeded #-}
getNonBlock :: (Network :> es) => CInt -> Eff es Bool
getNonBlock :: forall (es :: [Effect]).
(Network :> es) =>
ProtocolNumber -> Eff es Bool
getNonBlock = IO Bool -> Eff es Bool
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Bool -> Eff es Bool)
-> (ProtocolNumber -> IO Bool) -> ProtocolNumber -> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProtocolNumber -> IO Bool
S.getNonBlock
{-# INLINE getNonBlock #-}
sendBuf
:: (Network :> es) => Socket -> Ptr Word8 -> Int -> Eff es Int
sendBuf :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> Ptr Word8 -> Int -> Eff es Int
sendBuf Socket
sock Ptr Word8
ptr = IO Int -> Eff es Int
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Int -> Eff es Int) -> (Int -> IO Int) -> Int -> Eff es Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> Ptr Word8 -> Int -> IO Int
S.sendBuf Socket
sock Ptr Word8
ptr
{-# INLINE sendBuf #-}
recvBuf
:: (Network :> es) => Socket -> Ptr Word8 -> Int -> Eff es Int
recvBuf :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> Ptr Word8 -> Int -> Eff es Int
recvBuf Socket
sock Ptr Word8
ptr = IO Int -> Eff es Int
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Int -> Eff es Int) -> (Int -> IO Int) -> Int -> Eff es Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> Ptr Word8 -> Int -> IO Int
S.recvBuf Socket
sock Ptr Word8
ptr
{-# INLINE recvBuf #-}
sendBufTo
:: (Network :> es) => Socket -> Ptr a -> Int -> SockAddr -> Eff es Int
sendBufTo :: forall (es :: [Effect]) a.
(Network :> es) =>
Socket -> Ptr a -> Int -> SockAddr -> Eff es Int
sendBufTo Socket
sock Ptr a
ptr Int
n = IO Int -> Eff es Int
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Int -> Eff es Int)
-> (SockAddr -> IO Int) -> SockAddr -> Eff es Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> Ptr a -> Int -> SockAddr -> IO Int
forall a. Socket -> Ptr a -> Int -> SockAddr -> IO Int
S.sendBufTo Socket
sock Ptr a
ptr Int
n
{-# INLINE sendBufTo #-}
recvBufFrom
:: (Network :> es) => Socket -> Ptr a -> Int -> Eff es (Int, SockAddr)
recvBufFrom :: forall (es :: [Effect]) a.
(Network :> es) =>
Socket -> Ptr a -> Int -> Eff es (Int, SockAddr)
recvBufFrom Socket
sock Ptr a
ptr = IO (Int, SockAddr) -> Eff es (Int, SockAddr)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (Int, SockAddr) -> Eff es (Int, SockAddr))
-> (Int -> IO (Int, SockAddr)) -> Int -> Eff es (Int, SockAddr)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> Ptr a -> Int -> IO (Int, SockAddr)
forall a. Socket -> Ptr a -> Int -> IO (Int, SockAddr)
S.recvBufFrom Socket
sock Ptr a
ptr
{-# INLINE recvBufFrom #-}
sendBufMsg
:: (Network :> es)
=> Socket
-> SockAddr
-> [(Ptr Word8, Int)]
-> [Cmsg]
-> MsgFlag
-> Eff es Int
sendBufMsg :: forall (es :: [Effect]).
(Network :> es) =>
Socket
-> SockAddr
-> [(Ptr Word8, Int)]
-> [Cmsg]
-> MsgFlag
-> Eff es Int
sendBufMsg Socket
sock SockAddr
sockAddr [(Ptr Word8, Int)]
ptrs [Cmsg]
cmsgs = IO Int -> Eff es Int
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Int -> Eff es Int)
-> (MsgFlag -> IO Int) -> MsgFlag -> Eff es Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket
-> SockAddr -> [(Ptr Word8, Int)] -> [Cmsg] -> MsgFlag -> IO Int
S.sendBufMsg Socket
sock SockAddr
sockAddr [(Ptr Word8, Int)]
ptrs [Cmsg]
cmsgs
{-# INLINE sendBufMsg #-}
recvBufMsg
:: (Network :> es)
=> Socket
-> [(Ptr Word8, Int)]
-> Int
-> MsgFlag
-> Eff es (SockAddr, Int, [Cmsg], MsgFlag)
recvBufMsg :: forall (es :: [Effect]).
(Network :> es) =>
Socket
-> [(Ptr Word8, Int)]
-> Int
-> MsgFlag
-> Eff es (SockAddr, Int, [Cmsg], MsgFlag)
recvBufMsg Socket
sock [(Ptr Word8, Int)]
ptrs Int
n = IO (SockAddr, Int, [Cmsg], MsgFlag)
-> Eff es (SockAddr, Int, [Cmsg], MsgFlag)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (SockAddr, Int, [Cmsg], MsgFlag)
-> Eff es (SockAddr, Int, [Cmsg], MsgFlag))
-> (MsgFlag -> IO (SockAddr, Int, [Cmsg], MsgFlag))
-> MsgFlag
-> Eff es (SockAddr, Int, [Cmsg], MsgFlag)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket
-> [(Ptr Word8, Int)]
-> Int
-> MsgFlag
-> IO (SockAddr, Int, [Cmsg], MsgFlag)
S.recvBufMsg Socket
sock [(Ptr Word8, Int)]
ptrs Int
n
{-# INLINE recvBufMsg #-}
send :: (Network :> es) => Socket -> StrictByteString -> Eff es Int
send :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> StrictByteString -> Eff es Int
send Socket
sock = IO Int -> Eff es Int
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Int -> Eff es Int)
-> (StrictByteString -> IO Int) -> StrictByteString -> Eff es Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> StrictByteString -> IO Int
S.send Socket
sock
{-# INLINE send #-}
sendAll :: (Network :> es) => Socket -> StrictByteString -> Eff es ()
sendAll :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> StrictByteString -> Eff es ()
sendAll Socket
sock = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (StrictByteString -> IO ()) -> StrictByteString -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> StrictByteString -> IO ()
S.sendAll Socket
sock
{-# INLINE sendAll #-}
sendTo
:: (Network :> es) => Socket -> StrictByteString -> SockAddr -> Eff es Int
sendTo :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> StrictByteString -> SockAddr -> Eff es Int
sendTo Socket
sock StrictByteString
bs = IO Int -> Eff es Int
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Int -> Eff es Int)
-> (SockAddr -> IO Int) -> SockAddr -> Eff es Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> StrictByteString -> SockAddr -> IO Int
S.sendTo Socket
sock StrictByteString
bs
{-# INLINE sendTo #-}
sendAllTo
:: (Network :> es) => Socket -> StrictByteString -> SockAddr -> Eff es ()
sendAllTo :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> StrictByteString -> SockAddr -> Eff es ()
sendAllTo Socket
sock StrictByteString
bs = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (SockAddr -> IO ()) -> SockAddr -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> StrictByteString -> SockAddr -> IO ()
S.sendAllTo Socket
sock StrictByteString
bs
{-# INLINE sendAllTo #-}
recv :: (Network :> es) => Socket -> Int -> Eff es StrictByteString
recv :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> Int -> Eff es StrictByteString
recv Socket
sock = IO StrictByteString -> Eff es StrictByteString
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO StrictByteString -> Eff es StrictByteString)
-> (Int -> IO StrictByteString) -> Int -> Eff es StrictByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> Int -> IO StrictByteString
S.recv Socket
sock
{-# INLINE recv #-}
recvFrom
:: (Network :> es) => Socket -> Int -> Eff es (StrictByteString, SockAddr)
recvFrom :: forall (es :: [Effect]).
(Network :> es) =>
Socket -> Int -> Eff es (StrictByteString, SockAddr)
recvFrom Socket
sock = IO (StrictByteString, SockAddr)
-> Eff es (StrictByteString, SockAddr)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (StrictByteString, SockAddr)
-> Eff es (StrictByteString, SockAddr))
-> (Int -> IO (StrictByteString, SockAddr))
-> Int
-> Eff es (StrictByteString, SockAddr)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Socket -> Int -> IO (StrictByteString, SockAddr)
S.recvFrom Socket
sock
{-# INLINE recvFrom #-}