Targets.hs 9.4 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269
  1. {-# LANGUAGE OverloadedStrings #-}
  2. {-# LANGUAGE ExistentialQuantification #-}
  3. {-# LANGUAGE ForeignFunctionInterface #-}
  4. {-# LANGUAGE InterruptibleFFI #-}
  5. module System.IO.Uniform.Targets (TlsSettings(..), UniformIO(..), SocketIO, FileIO, TlsStream, BoundedPort, SomeIO(..), connectTo, connectToHost, bindPort, accept, openFile, getPeer, closePort) where
  6. import Foreign
  7. import Foreign.C.Types
  8. import Foreign.C.String
  9. import Foreign.C.Error
  10. import qualified Data.IP as IP
  11. import Data.ByteString (ByteString)
  12. import qualified Data.ByteString as BS
  13. import qualified Data.List as L
  14. import Control.Exception
  15. import qualified Network.Socket as Soc
  16. import System.IO.Error
  17. import Data.Default.Class
  18. -- | Settings for starttls functions.
  19. data TlsSettings = TlsSettings {tlsPrivateKeyFile :: String, tlsCertificateChainFile :: String} deriving (Read, Show)
  20. instance Default TlsSettings where
  21. def = TlsSettings "" ""
  22. -- |
  23. -- Typeclass for uniform IO targets.
  24. class UniformIO a where
  25. -- | uRead fd n
  26. --
  27. -- Reads a block of at most n bytes of data from the IO target.
  28. -- Reading will block if there's no data available, but will return immediately
  29. -- if any amount of data is availble.
  30. uRead :: a -> Int -> IO ByteString
  31. -- | uPut fd text
  32. --
  33. -- Writes all the bytes of text into the IO target. Takes care of retrying if needed.
  34. uPut :: a -> ByteString -> IO ()
  35. -- | fClose fd
  36. --
  37. -- Closes the IO target, releasing any allocated resource. Resources may leak if not called
  38. -- for every oppened fd.
  39. uClose :: a -> IO ()
  40. -- | startTLS fd
  41. --
  42. -- Starts a TLS connection over the IO target.
  43. startTls :: TlsSettings -> a -> IO TlsStream
  44. -- | isSecure fd
  45. --
  46. -- Indicates whether the data written or read from fd is secure at transport.
  47. isSecure :: a -> Bool
  48. -- | A type that wraps any type in the UniformIO class.
  49. data SomeIO = forall a. (UniformIO a) => SomeIO a
  50. instance UniformIO SomeIO where
  51. uRead (SomeIO s) n = uRead s n
  52. uPut (SomeIO s) t = uPut s t
  53. uClose (SomeIO s) = uClose s
  54. startTls set (SomeIO s) = startTls set s
  55. isSecure (SomeIO s) = isSecure s
  56. data Nethandler
  57. -- | A bounded IP port from where to accept SocketIO connections.
  58. newtype BoundedPort = BoundedPort {lis :: (Ptr Nethandler)}
  59. data SockDs
  60. newtype SocketIO = SocketIO {sock :: (Ptr SockDs)}
  61. data FileDs
  62. newtype FileIO = FileIO {fd :: (Ptr FileDs)}
  63. data TlsDs
  64. newtype TlsStream = TlsStream {tls :: (Ptr TlsDs)}
  65. -- | UniformIO IP connections.
  66. instance UniformIO SocketIO where
  67. uRead s n = allocaArray n (
  68. \b -> do
  69. count <- c_recvSock (sock s) b (fromIntegral n)
  70. if count < 0
  71. then throwErrno "could not read"
  72. else BS.packCStringLen (b, fromIntegral count)
  73. )
  74. uPut s t = BS.useAsCStringLen t (
  75. \(str, n) -> do
  76. count <- c_sendSock (sock s) str $ fromIntegral n
  77. if count < 0
  78. then throwErrno "could not write"
  79. else return ()
  80. )
  81. uClose s = c_closeSock (sock s)
  82. startTls st s = withCString (tlsCertificateChainFile st) (
  83. \cert -> withCString (tlsPrivateKeyFile st) (
  84. \key -> do
  85. r <- c_startSockTls (sock s) cert key
  86. if r == nullPtr
  87. then throwErrno "could not start TLS"
  88. else return . TlsStream $ r
  89. )
  90. )
  91. isSecure _ = False
  92. -- | UniformIO type for file IO.
  93. instance UniformIO FileIO where
  94. uRead s n = allocaArray n (
  95. \b -> do
  96. count <- c_recvFile (fd s) b $ fromIntegral n
  97. if count < 0
  98. then throwErrno "could not read"
  99. else BS.packCStringLen (b, fromIntegral count)
  100. )
  101. uPut s t = BS.useAsCStringLen t (
  102. \(str, n) -> do
  103. count <- c_sendFile (fd s) str $ fromIntegral n
  104. if count < 0
  105. then throwErrno "could not write"
  106. else return ()
  107. )
  108. uClose s = c_closeFile (fd s)
  109. -- Not implemented yet.
  110. startTls _ _ = return . TlsStream $ nullPtr
  111. isSecure _ = False
  112. -- | UniformIO wrapper that applies TLS to communication on IO target.
  113. -- This type is constructed by calling startTls on other targets.
  114. instance UniformIO TlsStream where
  115. uRead s n = allocaArray n (
  116. \b -> do
  117. count <- c_recvTls (tls s) b $ fromIntegral n
  118. if count < 0
  119. then throwErrno "could not read"
  120. else BS.packCStringLen (b, fromIntegral count)
  121. )
  122. uPut s t = BS.useAsCStringLen t (
  123. \(str, n) -> do
  124. count <- c_sendTls (tls s) str $ fromIntegral n
  125. if count < 0
  126. then throwErrno "could not write"
  127. else return ()
  128. )
  129. uClose s = c_closeTls (tls s)
  130. startTls _ s = return s
  131. isSecure _ = True
  132. -- | connectToHost hostName port
  133. --
  134. -- Connects to the given host and port.
  135. connectToHost :: String -> Int -> IO SocketIO
  136. connectToHost host port = do
  137. ip <- getAddr
  138. connectTo ip port
  139. where
  140. getAddr :: IO IP.IP
  141. getAddr = do
  142. add <- Soc.getAddrInfo Nothing (Just host) Nothing
  143. case add of
  144. [] -> throwIO $ mkIOError doesNotExistErrorType "host not found" Nothing Nothing
  145. (a:_) -> case Soc.addrAddress a of
  146. Soc.SockAddrInet _ a' -> return . IP.IPv4 . IP.fromHostAddress $ a'
  147. Soc.SockAddrInet6 _ _ a' _ -> return . IP.IPv6 . IP.fromHostAddress6 $ a'
  148. _ -> throwIO $ mkIOError doesNotExistErrorType "host not found" Nothing Nothing
  149. -- | ConnecctTo ipAddress port
  150. --
  151. -- Connects to the given port of the host at the given IP address.
  152. connectTo :: IP.IP -> Int -> IO SocketIO
  153. connectTo host port = do
  154. r <- case host of
  155. IP.IPv4 host' -> fmap SocketIO $ c_connect4 (fromIntegral . IP.toHostAddress $ host') (fromIntegral port)
  156. IP.IPv6 host' -> fmap SocketIO $ withArray (ipToArray host') (
  157. \add -> c_connect6 add (fromIntegral port)
  158. )
  159. if sock r == nullPtr
  160. then throwErrno "could not connect to host"
  161. else return r
  162. where
  163. ipToArray :: IP.IPv6 -> [CUChar]
  164. ipToArray ip = let
  165. (w0, w1, w2, w3) = IP.toHostAddress6 ip
  166. in L.concat [wtoc w0, wtoc w1, wtoc w2, wtoc w3]
  167. wtoc :: Word32 -> [CUChar]
  168. wtoc w = let
  169. c0 = fromIntegral $ mod w 256
  170. w1 = div w 256
  171. c1 = fromIntegral $ mod w1 256
  172. w2 = div w1 256
  173. c2 = fromIntegral $ mod w2 256
  174. c3 = fromIntegral $ div w2 256
  175. in [c3, c2, c1, c0]
  176. -- | bindPort port
  177. -- Binds to the given IP port, becoming ready to accept connections on it.
  178. -- Binding to port numbers under 1024 will fail unless performed by the superuser,
  179. -- once bounded, a process can reduce its privileges and still accept clients on that port.
  180. bindPort :: Int -> IO BoundedPort
  181. bindPort port = do
  182. r <- fmap BoundedPort $ c_getPort $ fromIntegral port
  183. if lis r == nullPtr
  184. then throwErrno "could not bind to port"
  185. else return r
  186. -- | accept port
  187. --
  188. -- Accept clients on a port previously bound with bindPort.
  189. accept :: BoundedPort -> IO SocketIO
  190. accept port = do
  191. r <- fmap SocketIO $ c_accept (lis port)
  192. if sock r == nullPtr
  193. then throwErrno "could not accept connection"
  194. else return r
  195. -- | Open a file for bidirectional IO.
  196. openFile :: String -> IO FileIO
  197. openFile fileName = do
  198. r <- withCString fileName (
  199. \f -> fmap FileIO $ c_createFile f
  200. )
  201. if fd r == nullPtr
  202. then throwErrno "could not open file"
  203. else return r
  204. -- | Gets the address of the peer socket of a internet connection.
  205. getPeer :: SocketIO -> IO (IP.IP, Int)
  206. getPeer s = allocaArray 16 (
  207. \p6 -> alloca (
  208. \p4 -> alloca (
  209. \iptype -> do
  210. p <- c_getPeer (sock s) p4 p6 iptype
  211. if p == -1
  212. then throwErrno "could not get peer address"
  213. else do
  214. iptp <- peek iptype
  215. if iptp == 1
  216. then do --IPv6
  217. add <- peekArray 16 p6
  218. return (IP.IPv6 . IP.toIPv6b $ map fromIntegral add, fromIntegral p)
  219. else do --IPv4
  220. add <- peek p4
  221. return (IP.IPv4 . IP.fromHostAddress . fromIntegral $ add, fromIntegral p)
  222. )
  223. )
  224. )
  225. -- | Closes a BoundedPort, and releases any resource used by it.
  226. closePort :: BoundedPort -> IO ()
  227. closePort p = c_closePort (lis p)
  228. foreign import ccall safe "getPort" c_getPort :: CInt -> IO (Ptr Nethandler)
  229. foreign import ccall safe "createFromHandler" c_accept :: Ptr Nethandler -> IO (Ptr SockDs)
  230. foreign import ccall safe "createFromFileName" c_createFile :: CString -> IO (Ptr FileDs)
  231. foreign import ccall safe "createToIPv4Host" c_connect4 :: CUInt -> CInt -> IO (Ptr SockDs)
  232. foreign import ccall safe "createToIPv6Host" c_connect6 :: Ptr CUChar -> CInt -> IO (Ptr SockDs)
  233. foreign import ccall safe "startSockTls" c_startSockTls :: Ptr SockDs -> CString -> CString -> IO (Ptr TlsDs)
  234. foreign import ccall safe "getPeer" c_getPeer :: Ptr SockDs -> Ptr CUInt -> Ptr CUChar -> Ptr CInt -> IO (CInt)
  235. foreign import ccall safe "closeSockDs" c_closeSock :: Ptr SockDs -> IO ()
  236. foreign import ccall safe "closeFileDs" c_closeFile :: Ptr FileDs -> IO ()
  237. foreign import ccall safe "closeHandler" c_closePort :: Ptr Nethandler -> IO ()
  238. foreign import ccall safe "closeTlsDs" c_closeTls :: Ptr TlsDs -> IO ()
  239. foreign import ccall interruptible "fileDsSend" c_sendFile :: Ptr FileDs -> Ptr CChar -> CInt -> IO CInt
  240. foreign import ccall interruptible "sockDsSend" c_sendSock :: Ptr SockDs -> Ptr CChar -> CInt -> IO CInt
  241. foreign import ccall interruptible "tlsDsSend" c_sendTls :: Ptr TlsDs -> Ptr CChar -> CInt -> IO CInt
  242. foreign import ccall interruptible "fileDsRecv" c_recvFile :: Ptr FileDs -> Ptr CChar -> CInt -> IO CInt
  243. foreign import ccall interruptible "sockDsRecv" c_recvSock :: Ptr SockDs -> Ptr CChar -> CInt -> IO CInt
  244. foreign import ccall interruptible "tlsDsRecv" c_recvTls :: Ptr TlsDs -> Ptr CChar -> CInt -> IO CInt