{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE InterruptibleFFI #-}
{-# LANGUAGE EmptyDataDecls #-}

module System.IO.Uniform.External where

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

import System.Posix.Types (Fd(..))

data Nethandler
-- | A bounded IP port from where to accept SocketIO connections.
newtype BoundedPort = BoundedPort {lis :: (Ptr Nethandler)}
data Ds
newtype SocketIO = SocketIO {sock :: (Ptr Ds)}
newtype FileIO = FileIO {fd :: (Ptr Ds)}
data TlsDs
newtype TlsIO = TlsIO {tls :: (Ptr TlsDs)}
data StdIO

closeFd :: Fd -> IO ()
closeFd (Fd f) = c_closeFd f
            
-- | Closes a BoundedPort, and releases any resource used by it.
closePort :: BoundedPort -> IO ()
closePort p = c_closePort (lis p)


foreign import ccall interruptible "getPort" c_getPort :: CInt -> IO (Ptr Nethandler)
foreign import ccall interruptible "createFromHandler" c_accept :: Ptr Nethandler -> IO (Ptr Ds)
foreign import ccall safe "createFromFileName" c_createFile :: CString -> IO (Ptr Ds)
foreign import ccall interruptible "createToIPv4Host" c_connect4 :: CUInt -> CInt -> IO (Ptr Ds)
foreign import ccall interruptible "createToIPv6Host" c_connect6 :: Ptr CUChar -> CInt -> IO (Ptr Ds)

foreign import ccall interruptible "startSockTls" c_startSockTls :: Ptr Ds -> CString -> CString -> CString -> IO (Ptr TlsDs)
foreign import ccall safe "getPeer" c_getPeer :: Ptr Ds -> Ptr CUInt -> Ptr CUChar -> Ptr CInt -> IO (CInt)

--foreign import ccall safe "getFd" c_getFd :: Ptr Ds -> IO CInt
--foreign import ccall safe "getTlsFd" c_getTlsFd :: Ptr TlsDs -> IO CInt
foreign import ccall safe "closeFd" c_closeFd :: CInt -> IO ()

foreign import ccall safe "prepareToClose" c_prepareToClose :: Ptr Ds -> IO CInt
foreign import ccall safe "closeHandler" c_closePort :: Ptr Nethandler -> IO ()
foreign import ccall safe "closeTls" c_closeTls :: Ptr TlsDs -> IO (Ptr Ds)

foreign import ccall interruptible "sendDs" c_send :: Ptr Ds -> Ptr CChar -> CInt -> IO CInt
foreign import ccall interruptible "stdDsSend" c_sendStd :: Ptr CChar -> CInt -> IO CInt
foreign import ccall interruptible "tlsDsSend" c_sendTls :: Ptr TlsDs -> Ptr CChar -> CInt -> IO CInt

foreign import ccall interruptible "recvDs" c_recv :: Ptr Ds -> Ptr CChar -> CInt -> IO CInt
foreign import ccall interruptible "stdDsRecv" c_recvStd :: Ptr CChar -> CInt -> IO CInt
foreign import ccall interruptible "tlsDsRecv" c_recvTls :: Ptr TlsDs -> Ptr CChar -> CInt -> IO CInt