Targets.hs 9.4 KB

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