Targets.hs 11 KB

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