diff options
-rw-r--r-- | Presence/ServerC.hs | 132 | ||||
-rw-r--r-- | Presence/SocketLike.hs | 38 |
2 files changed, 170 insertions, 0 deletions
diff --git a/Presence/ServerC.hs b/Presence/ServerC.hs new file mode 100644 index 00000000..2e22825d --- /dev/null +++ b/Presence/ServerC.hs | |||
@@ -0,0 +1,132 @@ | |||
1 | {-# LANGUAGE TypeFamilies #-} | ||
2 | {-# LANGUAGE TypeOperators #-} | ||
3 | {-# LANGUAGE OverloadedStrings #-} | ||
4 | {-# LANGUAGE RankNTypes #-} | ||
5 | module ServerC | ||
6 | ( doServer | ||
7 | , ConnId(..) | ||
8 | ) where | ||
9 | |||
10 | import Network.Socket as Socket | ||
11 | import Data.ByteString.Lazy.Char8 as L | ||
12 | ( putStrLn ) | ||
13 | import Data.ByteString.Char8 | ||
14 | ( hGetNonBlocking | ||
15 | ) | ||
16 | import qualified Data.ByteString.Char8 as S | ||
17 | ( hPutStr | ||
18 | ) | ||
19 | import System.IO | ||
20 | ( IOMode(..) | ||
21 | , hSetBuffering | ||
22 | , BufferMode(..) | ||
23 | , hWaitForInput | ||
24 | , hClose | ||
25 | , hIsEOF | ||
26 | ) | ||
27 | import Control.Monad | ||
28 | import Control.Concurrent (forkIO,threadDelay) | ||
29 | import Control.Exception (handle,SomeException(..)) | ||
30 | import Data.HList | ||
31 | import Data.HList.TypeEqGeneric1() | ||
32 | import Data.HList.TypeCastGeneric1() | ||
33 | import System.IO.Error | ||
34 | |||
35 | import Data.Conduit | ||
36 | import Control.Monad.Trans.Class (lift) | ||
37 | import Control.Monad.IO.Class (MonadIO (liftIO)) | ||
38 | import qualified Data.ByteString as S (ByteString) | ||
39 | import System.IO (Handle) | ||
40 | |||
41 | import ByteStringOperators | ||
42 | import SocketLike | ||
43 | |||
44 | |||
45 | |||
46 | newtype ConnId = ConnId Int | ||
47 | deriving Eq | ||
48 | |||
49 | |||
50 | data AcceptResult = | ||
51 | GotConnection (Socket,SockAddr) | ||
52 | | Retry | ||
53 | | QuitOnException | ||
54 | |||
55 | doServer :: | ||
56 | MonadIO m => | ||
57 | HCons Socket.Family (HCons PortNumber l) | ||
58 | -> (HCons RestrictedSocket (HCons ConnId l) | ||
59 | -> Producer m S.ByteString | ||
60 | -> Consumer S.ByteString m () | ||
61 | -> IO ()) | ||
62 | -> IO Socket | ||
63 | doServer (HCons family port) g = runServer port (runConn g) | ||
64 | where | ||
65 | runServer (HCons port st) go = do | ||
66 | sock <- socket family Stream 0 | ||
67 | setSocketOption sock ReuseAddr 1 | ||
68 | case family of | ||
69 | AF_INET -> bindSocket sock (SockAddrInet port iNADDR_ANY) | ||
70 | AF_INET6 -> bindSocket sock (SockAddrInet6 port 0 iN6ADDR_ANY 0) | ||
71 | listen sock 2 | ||
72 | forkIO $ do | ||
73 | mainLoop sock (ConnId 0) go | ||
74 | -- L.putStrLn $ "quit accept loop" | ||
75 | return sock | ||
76 | where | ||
77 | mainLoop sock idnum@(ConnId n) go = do | ||
78 | let doException ioerror = do | ||
79 | let typ = ioeGetErrorType ioerror | ||
80 | case bshow typ of | ||
81 | |||
82 | -- ResourceExhausted | ||
83 | "resource exhausted" -> return Retry | ||
84 | |||
85 | -- InvalidArgument | ||
86 | "invalid argument" -> L.putStrLn "quit accept-loop." >> return QuitOnException | ||
87 | |||
88 | _ -> do | ||
89 | L.putStrLn ("accept-loop exception: " <++> bshow ioerror <++> "\n") | ||
90 | return QuitOnException | ||
91 | |||
92 | mcon <- handle doException $ fix $ \loop -> do | ||
93 | con <- accept sock | ||
94 | return $ GotConnection con | ||
95 | case mcon of | ||
96 | GotConnection con -> do | ||
97 | forkIO $ go (idnum `HCons` st) con | ||
98 | mainLoop sock (ConnId (n+1)) go | ||
99 | Retry -> threadDelay 500000 >> mainLoop sock idnum go | ||
100 | QuitOnException -> return () | ||
101 | |||
102 | packets :: MonadIO m => Handle -> Producer m S.ByteString | ||
103 | packets h = do | ||
104 | packet <- lift $ liftIO $ getPacket h | ||
105 | yield packet | ||
106 | isEof <- lift $ liftIO $ hIsEOF h | ||
107 | when (not isEof) (packets h) | ||
108 | where | ||
109 | getPacket h = do { hWaitForInput h (-1) ; hGetNonBlocking h 1024 } | ||
110 | |||
111 | outgoing :: MonadIO m => Handle -> Consumer S.ByteString m () | ||
112 | outgoing h = do | ||
113 | mpacket <- await | ||
114 | maybe (return ()) | ||
115 | (\r -> (lift . liftIO . S.hPutStr h $ r) >> outgoing h) | ||
116 | mpacket | ||
117 | |||
118 | |||
119 | runConn :: | ||
120 | MonadIO m => | ||
121 | ( HCons RestrictedSocket st | ||
122 | -> Producer m S.ByteString | ||
123 | -> Consumer S.ByteString m () | ||
124 | -> IO () ) | ||
125 | -> st -> (Socket, t) -> IO () | ||
126 | |||
127 | runConn g st (sock,_) = do | ||
128 | h <- socketToHandle sock ReadWriteMode | ||
129 | hSetBuffering h NoBuffering | ||
130 | let doException (SomeException e) = Prelude.putStrLn ("\n\nexception: " ++ show e ++ "\n\n") | ||
131 | handle doException (g (restrictSocket sock `HCons` st) (packets h) (outgoing h)) | ||
132 | hClose h | ||
diff --git a/Presence/SocketLike.hs b/Presence/SocketLike.hs new file mode 100644 index 00000000..12fa07a3 --- /dev/null +++ b/Presence/SocketLike.hs | |||
@@ -0,0 +1,38 @@ | |||
1 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
2 | module SocketLike | ||
3 | ( SocketLike | ||
4 | , getSocketName | ||
5 | , getPeerName | ||
6 | , getPeerCred | ||
7 | , socketPort | ||
8 | , RestrictedSocket | ||
9 | , restrictSocket | ||
10 | , PortNumber | ||
11 | , SockAddr | ||
12 | , CUInt | ||
13 | ) where | ||
14 | |||
15 | import Network.Socket | ||
16 | ( PortNumber | ||
17 | , SockAddr | ||
18 | ) | ||
19 | import Foreign.C.Types ( CUInt ) | ||
20 | |||
21 | import qualified Network.Socket as NS | ||
22 | |||
23 | class SocketLike sock where | ||
24 | getSocketName :: sock -> IO SockAddr | ||
25 | getPeerName :: sock -> IO SockAddr | ||
26 | getPeerCred :: sock -> IO (CUInt, CUInt, CUInt) | ||
27 | socketPort :: sock -> IO PortNumber | ||
28 | |||
29 | instance SocketLike NS.Socket where | ||
30 | getSocketName = NS.getSocketName | ||
31 | getPeerName = NS.getPeerName | ||
32 | getPeerCred = NS.getPeerCred | ||
33 | socketPort = NS.socketPort | ||
34 | |||
35 | newtype RestrictedSocket = Restricted NS.Socket deriving SocketLike | ||
36 | |||
37 | restrictSocket :: NS.Socket -> RestrictedSocket | ||
38 | restrictSocket socket = Restricted socket | ||