Network.hs 4.9 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166
  1. -- {-# LANGUAGE OverloadedStrings #-}
  2. -- {-# LANGUAGE ExistentialQuantification #-}
  3. -- {-# LANGUAGE ForeignFunctionInterface #-}
  4. -- {-# LANGUAGE InterruptibleFFI #-}
  5. -- {-# LANGUAGE EmptyDataDecls #-}
  6. module System.IO.Uniform.Network (
  7. SocketIO,
  8. BoundedPort,
  9. connectTo,
  10. connectToHost,
  11. bindPort,
  12. accept,
  13. closePort,
  14. getPeer
  15. ) where
  16. import System.IO.Uniform
  17. import System.IO.Uniform.External
  18. import Foreign
  19. import Foreign.C.Types
  20. import Foreign.C.String
  21. import Foreign.C.Error
  22. import qualified Data.IP as IP
  23. --import Data.ByteString (ByteString)
  24. import qualified Data.ByteString as BS
  25. --import qualified Data.ByteString.Lazy as LBS
  26. --import qualified Data.ByteString.Builder as BSBuild
  27. import qualified Data.List as L
  28. import Control.Exception
  29. import Control.Applicative ((<$>))
  30. --import Data.Monoid (mappend)
  31. import qualified Network.Socket as Soc
  32. import System.IO.Error
  33. --import Control.Concurrent.MVar
  34. --import Data.Default.Class
  35. import System.Posix.Types (Fd(..))
  36. -- | UniformIO IP connections.
  37. instance UniformIO SocketIO where
  38. uRead s n = do
  39. allocaArray n (
  40. \b -> do
  41. count <- c_recv (sock s) b (fromIntegral n)
  42. if count < 0
  43. then throwErrno "could not read"
  44. else BS.packCStringLen (b, fromIntegral count)
  45. )
  46. uPut s t = do
  47. BS.useAsCStringLen t (
  48. \(str, n) -> do
  49. count <- c_send (sock s) str $ fromIntegral n
  50. if count < 0
  51. then throwErrno "could not write"
  52. else return ()
  53. )
  54. uClose s = do
  55. f <- Fd <$> c_prepareToClose (sock s)
  56. closeFd f
  57. startTls st s = withCString (tlsCertificateChainFile st) (
  58. \cert -> withCString (tlsPrivateKeyFile st) (
  59. \key -> withCString (tlsDHParametersFile st) (
  60. \para -> do
  61. r <- c_startSockTls (sock s) cert key para
  62. if r == nullPtr
  63. then throwErrno "could not start TLS"
  64. else return . TlsIO $ r
  65. )
  66. )
  67. )
  68. isSecure _ = False
  69. -- | connectToHost hostName port
  70. --
  71. -- Connects to the given host and port.
  72. connectToHost :: String -> Int -> IO SocketIO
  73. connectToHost host port = do
  74. ip <- getAddr
  75. connectTo ip port
  76. where
  77. getAddr :: IO IP.IP
  78. getAddr = do
  79. add <- Soc.getAddrInfo Nothing (Just host) Nothing
  80. case add of
  81. [] -> throwIO $ mkIOError doesNotExistErrorType "host not found" Nothing Nothing
  82. (a:_) -> case Soc.addrAddress a of
  83. Soc.SockAddrInet _ a' -> return . IP.IPv4 . IP.fromHostAddress $ a'
  84. Soc.SockAddrInet6 _ _ a' _ -> return . IP.IPv6 . IP.fromHostAddress6 $ a'
  85. _ -> throwIO $ mkIOError doesNotExistErrorType "host not found" Nothing Nothing
  86. -- | ConnecctTo ipAddress port
  87. --
  88. -- Connects to the given port of the host at the given IP address.
  89. connectTo :: IP.IP -> Int -> IO SocketIO
  90. connectTo host port = do
  91. r <- case host of
  92. IP.IPv4 host' -> fmap SocketIO $ c_connect4 (fromIntegral . IP.toHostAddress $ host') (fromIntegral port)
  93. IP.IPv6 host' -> fmap SocketIO $ withArray (ipToArray host') (
  94. \add -> c_connect6 add (fromIntegral port)
  95. )
  96. if sock r == nullPtr
  97. then throwErrno "could not connect to host"
  98. else return r
  99. where
  100. ipToArray :: IP.IPv6 -> [CUChar]
  101. ipToArray ip = let
  102. (w0, w1, w2, w3) = IP.toHostAddress6 ip
  103. in L.concat [wtoc w0, wtoc w1, wtoc w2, wtoc w3]
  104. wtoc :: Word32 -> [CUChar]
  105. wtoc w = let
  106. c0 = fromIntegral $ mod w 256
  107. w1 = div w 256
  108. c1 = fromIntegral $ mod w1 256
  109. w2 = div w1 256
  110. c2 = fromIntegral $ mod w2 256
  111. c3 = fromIntegral $ div w2 256
  112. in [c3, c2, c1, c0]
  113. -- | bindPort port
  114. -- Binds to the given IP port, becoming ready to accept connections on it.
  115. -- Binding to port numbers under 1024 will fail unless performed by the superuser,
  116. -- once bounded, a process can reduce its privileges and still accept clients on that port.
  117. bindPort :: Int -> IO BoundedPort
  118. bindPort port = do
  119. r <- fmap BoundedPort $ c_getPort $ fromIntegral port
  120. if lis r == nullPtr
  121. then throwErrno "could not bind to port"
  122. else return r
  123. -- | accept port
  124. --
  125. -- Accept clients on a port previously bound with bindPort.
  126. accept :: BoundedPort -> IO SocketIO
  127. accept port = do
  128. r <- fmap SocketIO $ c_accept (lis port)
  129. if sock r == nullPtr
  130. then throwErrno "could not accept connection"
  131. else return r
  132. -- | Gets the address of the peer socket of a internet connection.
  133. getPeer :: SocketIO -> IO (IP.IP, Int)
  134. getPeer s = allocaArray 16 (
  135. \p6 -> alloca (
  136. \p4 -> alloca (
  137. \iptype -> do
  138. p <- c_getPeer (sock s) p4 p6 iptype
  139. if p == -1
  140. then throwErrno "could not get peer address"
  141. else do
  142. iptp <- peek iptype
  143. if iptp == 1
  144. then do --IPv6
  145. add <- peekArray 16 p6
  146. return (IP.IPv6 . IP.toIPv6b $ map fromIntegral add, fromIntegral p)
  147. else do --IPv4
  148. add <- peek p4
  149. return (IP.IPv4 . IP.fromHostAddress . fromIntegral $ add, fromIntegral p)
  150. )
  151. )
  152. )