Network.hs 5.6 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188
  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 (SocketIO s) n = do
  39. allocaArray n (
  40. \b -> do
  41. count <- c_recv s b (fromIntegral n)
  42. if count < 0
  43. then throwErrno "could not read"
  44. else BS.packCStringLen (b, fromIntegral count)
  45. )
  46. uRead (TlsSocketIO s) n = do
  47. allocaArray n (
  48. \b -> do
  49. count <- c_recvTls s b $ fromIntegral n
  50. if count < 0
  51. then throwErrno "could not read"
  52. else BS.packCStringLen (b, fromIntegral count)
  53. )
  54. uPut (SocketIO s) t = do
  55. BS.useAsCStringLen t (
  56. \(str, n) -> do
  57. count <- c_send s str $ fromIntegral n
  58. if count < 0
  59. then throwErrno "could not write"
  60. else return ()
  61. )
  62. uPut (TlsSocketIO s) t = do
  63. BS.useAsCStringLen t (
  64. \(str, n) -> do
  65. count <- c_sendTls s str $ fromIntegral n
  66. if count < 0
  67. then throwErrno "could not write"
  68. else return ()
  69. )
  70. uClose (SocketIO s) = do
  71. f <- Fd <$> c_prepareToClose s
  72. closeFd f
  73. uClose (TlsSocketIO s) = do
  74. d <- c_closeTls s
  75. f <- Fd <$> c_prepareToClose d
  76. closeFd f
  77. startTls st (SocketIO s) = withCString (tlsCertificateChainFile st) (
  78. \cert -> withCString (tlsPrivateKeyFile st) (
  79. \key -> withCString (tlsDHParametersFile st) (
  80. \para -> do
  81. r <- c_startSockTls s cert key para
  82. if r == nullPtr
  83. then throwErrno "could not start TLS"
  84. else return . TlsSocketIO $ r
  85. )
  86. )
  87. )
  88. startTls _ s@(TlsSocketIO _) = return s
  89. isSecure (SocketIO _) = False
  90. isSecure (TlsSocketIO _) = True
  91. -- | connectToHost hostName port
  92. --
  93. -- Connects to the given host and port.
  94. connectToHost :: String -> Int -> IO SocketIO
  95. connectToHost host port = do
  96. ip <- getAddr
  97. connectTo ip port
  98. where
  99. getAddr :: IO IP.IP
  100. getAddr = do
  101. add <- Soc.getAddrInfo Nothing (Just host) Nothing
  102. case add of
  103. [] -> throwIO $ mkIOError doesNotExistErrorType "host not found" Nothing Nothing
  104. (a:_) -> case Soc.addrAddress a of
  105. Soc.SockAddrInet _ a' -> return . IP.IPv4 . IP.fromHostAddress $ a'
  106. Soc.SockAddrInet6 _ _ a' _ -> return . IP.IPv6 . IP.fromHostAddress6 $ a'
  107. _ -> throwIO $ mkIOError doesNotExistErrorType "host not found" Nothing Nothing
  108. -- | ConnecctTo ipAddress port
  109. --
  110. -- Connects to the given port of the host at the given IP address.
  111. connectTo :: IP.IP -> Int -> IO SocketIO
  112. connectTo host port = do
  113. r <- case host of
  114. IP.IPv4 host' -> fmap SocketIO $ c_connect4 (fromIntegral . IP.toHostAddress $ host') (fromIntegral port)
  115. IP.IPv6 host' -> fmap SocketIO $ withArray (ipToArray host') (
  116. \add -> c_connect6 add (fromIntegral port)
  117. )
  118. if sock r == nullPtr
  119. then throwErrno "could not connect to host"
  120. else return r
  121. where
  122. ipToArray :: IP.IPv6 -> [CUChar]
  123. ipToArray ip = let
  124. (w0, w1, w2, w3) = IP.toHostAddress6 ip
  125. in L.concat [wtoc w0, wtoc w1, wtoc w2, wtoc w3]
  126. wtoc :: Word32 -> [CUChar]
  127. wtoc w = let
  128. c0 = fromIntegral $ mod w 256
  129. w1 = div w 256
  130. c1 = fromIntegral $ mod w1 256
  131. w2 = div w1 256
  132. c2 = fromIntegral $ mod w2 256
  133. c3 = fromIntegral $ div w2 256
  134. in [c3, c2, c1, c0]
  135. -- | bindPort port
  136. -- Binds to the given IP port, becoming ready to accept connections on it.
  137. -- Binding to port numbers under 1024 will fail unless performed by the superuser,
  138. -- once bounded, a process can reduce its privileges and still accept clients on that port.
  139. bindPort :: Int -> IO BoundedPort
  140. bindPort port = do
  141. r <- fmap BoundedPort $ c_getPort $ fromIntegral port
  142. if lis r == nullPtr
  143. then throwErrno "could not bind to port"
  144. else return r
  145. -- | accept port
  146. --
  147. -- Accept clients on a port previously bound with bindPort.
  148. accept :: BoundedPort -> IO SocketIO
  149. accept port = do
  150. r <- fmap SocketIO $ c_accept (lis port)
  151. if sock r == nullPtr
  152. then throwErrno "could not accept connection"
  153. else return r
  154. -- | Gets the address of the peer socket of a internet connection.
  155. getPeer :: SocketIO -> IO (IP.IP, Int)
  156. getPeer s = allocaArray 16 (
  157. \p6 -> alloca (
  158. \p4 -> alloca (
  159. \iptype -> do
  160. p <- c_getPeer (sock s) p4 p6 iptype
  161. if p == -1
  162. then throwErrno "could not get peer address"
  163. else do
  164. iptp <- peek iptype
  165. if iptp == 1
  166. then do --IPv6
  167. add <- peekArray 16 p6
  168. return (IP.IPv6 . IP.toIPv6b $ map fromIntegral add, fromIntegral p)
  169. else do --IPv4
  170. add <- peek p4
  171. return (IP.IPv4 . IP.fromHostAddress . fromIntegral $ add, fromIntegral p)
  172. )
  173. )
  174. )