{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE OverloadedStrings #-} module Server where import Network.Socket import Data.ByteString.Lazy.Char8 as L ( fromChunks , putStrLn ) import Data.ByteString.Char8 ( hGetNonBlocking ) import System.IO ( IOMode(..) , hSetBuffering , BufferMode(..) , hWaitForInput , hClose , hIsEOF ) import Control.Monad import Control.Concurrent (forkIO) import Control.Exception (handle,SomeException(..)) import Data.HList import Data.HList.TypeEqGeneric1() import Data.HList.TypeCastGeneric1() import System.IO.Error import ByteStringOperators newtype ConnId = ConnId Int deriving Eq newtype ConnectionFinalizer = ConnectionFinalizer (IO ()) getPacket h = do { hWaitForInput h (-1) ; fmap (fromChunks . (:[])) $ hGetNonBlocking h 1024 } newtype ServerHandle = ServerHandle Socket quitListening :: ServerHandle -> IO () quitListening (ServerHandle socket) = sClose socket doServer addrfamily port g startCon = do doServer' addrfamily port g startCon doServer' family port g startCon = runServer2 port (runConn2 g) where runConn2 g st (sock,_) = do h <- socketToHandle sock ReadWriteMode hSetBuffering h NoBuffering st'' <- startCon sock (h .*. st) let doException (SomeException e) = Prelude.putStrLn ("\n\nexception: " ++ show e ++ "\n\n") handle doException $ fix $ \loop -> do let continue () = hIsEOF h >>= flip when loop . not packet <- getPacket h g st'' packet continue let ConnectionFinalizer cleanup = hOccursFst st'' cleanup hClose h {- runServer2 :: Num num => PortNumber -> (num -> (Socket, SockAddr) -> IO b -> IO b) -> IO b -} runServer2 st@(HCons port _) go = do sock <- socket family Stream 0 setSocketOption sock ReuseAddr 1 case family of AF_INET -> bindSocket sock (SockAddrInet port iNADDR_ANY) AF_INET6 -> bindSocket sock (SockAddrInet6 port 0 iN6ADDR_ANY 0) listen sock 2 forkIO $ do mainLoop sock (ConnId 0) go -- L.putStrLn $ "quit accept loop" return (ServerHandle sock) where mainLoop sock idnum@(ConnId n) go = do let doException ioerror = do let typ = ioeGetErrorType ioerror if -- typ == InvalidArgument -- but the symbol is not exported :/ bshow typ=="invalid argument" then do L.putStrLn $ "quit accept-loop." else do L.putStrLn ("accept-loop exception: " <++> bshow ioerror <++> "\n") return Nothing mcon <- handle doException $ fix $ \loop -> do con <- accept sock return $ Just con case mcon of Just con -> do forkIO $ go (idnum .*. st) con mainLoop sock (ConnId (n+1)) go Nothing -> return ()