Skip Navigation

I enjoyed the simplicity of this recent Computerphile video on web servers: https://www.youtube.com/watch?v=7GBlCinu9yg

I enjoyed the simplicity of this recent Computerphile video on web servers: https://www.youtube.com/watch?v=7GBlCinu9yg

I attempted to recreate it in #haskell, but we don't really have a library on the same level of abstraction. wai is too abstract and network is not abstract enough.

2
2 comments
  • Actually, if you combine network with network-run then it is the right level of abstraction:

    {- cabal:
    build-depends: base, network, network-run, monad-loops
    -}
    
    import Network.Run.TCP
    import Network.Socket
    import System.IO
    import Control.Monad.Loops
    
    main = runTCPServer (Just "127.0.0.1") "9999" talk where
      talk s = do
        h <- socketToHandle s ReadWriteMode
        l <- hGetLine h
        case words l of
          ["GET", resource, "HTTP/1.1"] -> do
            whileM_ (("\r" /=) <$> hGetLine h) (pure ())
            let path = concat
                  [ "htdocs/"
                  , dropWhile (== '/') resource
                  , if last resource == '/' then "index.html" else ""
                  ]
            hPutStr h "HTTP/1.1 200 OK\r\n\r\n"
            hPutStr h =<< readFile path
            hClose h
          _ -> error "todo"
    
    
    • We can make it a lot more performant, shorter, and also safer by using lazy byte strings:

      {- cabal:
      build-depends: base, network, network-run, bytestring
      -}
      
      {-# LANGUAGE OverloadedStrings #-}
      
      import Network.Run.TCP (runTCPServer)
      import qualified Network.Socket.ByteString.Lazy as Net
      import qualified Data.ByteString.Lazy.Char8 as Str
      
      main = runTCPServer (Just "127.0.0.1") "9999" $ \s -> do
        request <- Net.getContents s
        case Str.words (Str.takeWhile (/= '\r') request) of
          ["GET", resource, "HTTP/1.1"] -> do
            let path = Str.concat
                  [ "htdocs/"
                  , Str.dropWhile (== '/') resource
                  , if Str.last resource == '/' then "index.html" else ""
                  ]
            page <- Str.readFile (Str.unpack path)
            Net.sendAll s ("HTTP/1.1 200 OK\r\n\r\n" <> page)
          _ -> error "todo"