module System.IO.Uniform.Targets (TlsSettings(..), UniformIO(..), SocketIO, FileIO, TlsStream, BoundedPort, SomeIO(..), connectTo, connectToHost, bindPort, accept, openFile, getPeer, closePort) where
import Foreign
import Foreign.C.Types
import Foreign.C.String
import Foreign.C.Error
import qualified Data.IP as IP
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import qualified Data.List as L
import Control.Exception
import qualified Network.Socket as Soc
import System.IO.Error
import Data.Default.Class
data TlsSettings = TlsSettings {tlsPrivateKeyFile :: String, tlsCertificateChainFile :: String} deriving (Read, Show)
instance Default TlsSettings where
def = TlsSettings "" ""
class UniformIO a where
uRead :: a -> Int -> IO ByteString
uPut :: a -> ByteString -> IO ()
uClose :: a -> IO ()
startTls :: TlsSettings -> a -> IO TlsStream
isSecure :: a -> Bool
data SomeIO = forall a. (UniformIO a) => SomeIO a
instance UniformIO SomeIO where
uRead (SomeIO s) n = uRead s n
uPut (SomeIO s) t = uPut s t
uClose (SomeIO s) = uClose s
startTls set (SomeIO s) = startTls set s
isSecure (SomeIO s) = isSecure s
data Nethandler
newtype BoundedPort = BoundedPort {lis :: (Ptr Nethandler)}
data SockDs
newtype SocketIO = SocketIO {sock :: (Ptr SockDs)}
data FileDs
newtype FileIO = FileIO {fd :: (Ptr FileDs)}
data TlsDs
newtype TlsStream = TlsStream {tls :: (Ptr TlsDs)}
instance UniformIO SocketIO where
uRead s n = allocaArray n (
\b -> do
count <- c_recvSock (sock s) b (fromIntegral n)
if count < 0
then throwErrno "could not read"
else BS.packCStringLen (b, fromIntegral count)
)
uPut s t = BS.useAsCStringLen t (
\(str, n) -> do
count <- c_sendSock (sock s) str $ fromIntegral n
if count < 0
then throwErrno "could not write"
else return ()
)
uClose s = c_closeSock (sock s)
startTls st s = withCString (tlsCertificateChainFile st) (
\cert -> withCString (tlsPrivateKeyFile st) (
\key -> do
r <- c_startSockTls (sock s) cert key
if r == nullPtr
then throwErrno "could not start TLS"
else return . TlsStream $ r
)
)
isSecure _ = False
instance UniformIO FileIO where
uRead s n = allocaArray n (
\b -> do
count <- c_recvFile (fd s) b $ fromIntegral n
if count < 0
then throwErrno "could not read"
else BS.packCStringLen (b, fromIntegral count)
)
uPut s t = BS.useAsCStringLen t (
\(str, n) -> do
count <- c_sendFile (fd s) str $ fromIntegral n
if count < 0
then throwErrno "could not write"
else return ()
)
uClose s = c_closeFile (fd s)
startTls _ _ = return . TlsStream $ nullPtr
isSecure _ = False
instance UniformIO TlsStream where
uRead s n = allocaArray n (
\b -> do
count <- c_recvTls (tls s) b $ fromIntegral n
if count < 0
then throwErrno "could not read"
else BS.packCStringLen (b, fromIntegral count)
)
uPut s t = BS.useAsCStringLen t (
\(str, n) -> do
count <- c_sendTls (tls s) str $ fromIntegral n
if count < 0
then throwErrno "could not write"
else return ()
)
uClose s = c_closeTls (tls s)
startTls _ s = return s
isSecure _ = True
connectToHost :: String -> Int -> IO SocketIO
connectToHost host port = do
ip <- getAddr
connectTo ip port
where
getAddr :: IO IP.IP
getAddr = do
add <- Soc.getAddrInfo Nothing (Just host) Nothing
case add of
[] -> throwIO $ mkIOError doesNotExistErrorType "host not found" Nothing Nothing
(a:_) -> case Soc.addrAddress a of
Soc.SockAddrInet _ a' -> return . IP.IPv4 . IP.fromHostAddress $ a'
Soc.SockAddrInet6 _ _ a' _ -> return . IP.IPv6 . IP.fromHostAddress6 $ a'
_ -> throwIO $ mkIOError doesNotExistErrorType "host not found" Nothing Nothing
connectTo :: IP.IP -> Int -> IO SocketIO
connectTo host port = do
r <- case host of
IP.IPv4 host' -> fmap SocketIO $ c_connect4 (fromIntegral . IP.toHostAddress $ host') (fromIntegral port)
IP.IPv6 host' -> fmap SocketIO $ withArray (ipToArray host') (
\add -> c_connect6 add (fromIntegral port)
)
if sock r == nullPtr
then throwErrno "could not connect to host"
else return r
where
ipToArray :: IP.IPv6 -> [CUChar]
ipToArray ip = let
(w0, w1, w2, w3) = IP.toHostAddress6 ip
in L.concat [wtoc w0, wtoc w1, wtoc w2, wtoc w3]
wtoc :: Word32 -> [CUChar]
wtoc w = let
c0 = fromIntegral $ mod w 256
w1 = div w 256
c1 = fromIntegral $ mod w1 256
w2 = div w1 256
c2 = fromIntegral $ mod w2 256
c3 = fromIntegral $ div w2 256
in [c3, c2, c1, c0]
bindPort :: Int -> IO BoundedPort
bindPort port = do
r <- fmap BoundedPort $ c_getPort $ fromIntegral port
if lis r == nullPtr
then throwErrno "could not bind to port"
else return r
accept :: BoundedPort -> IO SocketIO
accept port = do
r <- fmap SocketIO $ c_accept (lis port)
if sock r == nullPtr
then throwErrno "could not accept connection"
else return r
openFile :: String -> IO FileIO
openFile fileName = do
r <- withCString fileName (
\f -> fmap FileIO $ c_createFile f
)
if fd r == nullPtr
then throwErrno "could not open file"
else return r
getPeer :: SocketIO -> IO (IP.IP, Int)
getPeer s = allocaArray 16 (
\p6 -> alloca (
\p4 -> alloca (
\iptype -> do
p <- c_getPeer (sock s) p4 p6 iptype
if p == 1
then throwErrno "could not get peer address"
else do
iptp <- peek iptype
if iptp == 1
then do --IPv6
add <- peekArray 16 p6
return (IP.IPv6 . IP.toIPv6b $ map fromIntegral add, fromIntegral p)
else do --IPv4
add <- peek p4
return (IP.IPv4 . IP.fromHostAddress . fromIntegral $ add, fromIntegral p)
)
)
)
closePort :: BoundedPort -> IO ()
closePort p = c_closePort (lis p)
foreign import ccall safe "getPort" c_getPort :: CInt -> IO (Ptr Nethandler)
foreign import ccall safe "createFromHandler" c_accept :: Ptr Nethandler -> IO (Ptr SockDs)
foreign import ccall safe "createFromFileName" c_createFile :: CString -> IO (Ptr FileDs)
foreign import ccall safe "createToIPv4Host" c_connect4 :: CUInt -> CInt -> IO (Ptr SockDs)
foreign import ccall safe "createToIPv6Host" c_connect6 :: Ptr CUChar -> CInt -> IO (Ptr SockDs)
foreign import ccall safe "startSockTls" c_startSockTls :: Ptr SockDs -> CString -> CString -> IO (Ptr TlsDs)
foreign import ccall safe "getPeer" c_getPeer :: Ptr SockDs -> Ptr CUInt -> Ptr CUChar -> Ptr CInt -> IO (CInt)
foreign import ccall safe "closeSockDs" c_closeSock :: Ptr SockDs -> IO ()
foreign import ccall safe "closeFileDs" c_closeFile :: Ptr FileDs -> IO ()
foreign import ccall safe "closeHandler" c_closePort :: Ptr Nethandler -> IO ()
foreign import ccall safe "closeTlsDs" c_closeTls :: Ptr TlsDs -> IO ()
foreign import ccall interruptible "fileDsSend" c_sendFile :: Ptr FileDs -> Ptr CChar -> CInt -> IO CInt
foreign import ccall interruptible "sockDsSend" c_sendSock :: Ptr SockDs -> Ptr CChar -> CInt -> IO CInt
foreign import ccall interruptible "tlsDsSend" c_sendTls :: Ptr TlsDs -> Ptr CChar -> CInt -> IO CInt
foreign import ccall interruptible "fileDsRecv" c_recvFile :: Ptr FileDs -> Ptr CChar -> CInt -> IO CInt
foreign import ccall interruptible "sockDsRecv" c_recvSock :: Ptr SockDs -> Ptr CChar -> CInt -> IO CInt
foreign import ccall interruptible "tlsDsRecv" c_recvTls :: Ptr TlsDs -> Ptr CChar -> CInt -> IO CInt