[web-devel] Hoogle Advice

Neil Mitchell ndmitchell at gmail.com
Mon Jan 24 21:11:37 CET 2011


Hi,

I tried switch Hoogle to Wai and Warp today. The results were good,
and once a few little things are cleared up I'm fairly certain that
the the next Hoogle release will be based on them. As I wrote the
code, I made some notes:

1) Why not add statusOK as an alias for status200? As someone who
doesn't spend all day dealing with HTTP response codes, statusOK is
far better documenting - similarly for all the other status values. I
added statusOK as a local definition in Hoogle.

2) Changing from HTTP to Wai, it was a shame that I had to define all
the header keys myself - could they be included - it would have better
performance, and give static guarantees. I added locally:

hdrContentType = mkCIByteString "Content-Type"
hdrCacheControl = mkCIByteString "Cache-Control"

3) The documentation for ResponseFile doesn't say what happens if the
file is not found. I am sure it must throw an exception, but for a
very brief second I wondered if it might change my status code to 404
on my behalf. Could the documentation be clarified.

4) I defined a Wai handler that threw an error, and Warp did nothing.
Should it? Or should I just be careful and include my own exception
handling? I'm not really sure what the right thing to do is - silently
eating the error isn't great, but bring down my server would be even
less appreciated.

5) Hoogle is currently written as lazy IO + String. Converting this
format to a response was easy with liftIO, LBS.pack and responseLBS.
Converting back was rather tricky. I eventually came up with:

responseFlatten :: Response -> IO (Status, ResponseHeaders, LBS.ByteString)
responseFlatten r = responseEnumerator r $ \status headers ->
    let f res E.EOF = return (status, headers, Blaze.toLazyByteString res)
        f res (E.Chunks xs) = E.continue (f $ mconcat $ res:xs)
    in E.continue (f mempty)

It's not too long, but it has a relatively high level of complexity.
Is there something simpler I could have done?

6) I want responseFlatten for two purposes, the first of which is to
output a CGI representation of the Response, which is easy with the
above function. However, outputting a response in CGI format is
trivial, and is probably the easiest way to debug/view the contents of
a Response. Would it be worth adding showResponse :: Response -> IO
LBS.ByteString to the Wai library, which produced the result
representing how it would be sent in CGI format, and was also useful
for debugging?

7) The second reason for using responseFlatten is that I want to write
a function Response -> IO Response which modifies a response to
rewrite "href='file://" to "href='/file/". I currently do this with
responseFlatten, converting to a String, and then stepping through it
Char by Char with isPrefixOf. Given the performance focus of this
email list, I can imagine several of you are now crying. What would
have been the Iterator/Builder approved way to do it?

8) The last point is the only point that is a blocker for Hoogle, and
regards the Warp server, Windows and ghci. In ghci on Windows, running
the network function accept doesn't terminate if you hit Ctrl+C. If
you run Warp in the main thread ghci will never respond to you again.
If you run Warp on a second thread then hitting Ctrl+C twice returns
to the prompt, but the thread serving the web page is still running
(and still serving web pages), and if you run the server again the old
server continues to serve the pages instead. I develop Hoogle on
Windows through ghci in server mode, so without a workaround it's
fairly fatal.

When writing Hoogle, I found that even though accept doesn't terminate
on exceptions, if you do sClose on the socket it raises an exception
in accept and does terminate. I experimented in a local copy of Warp
and found the following worked very well:

import Control.Concurrent
import Control.Monad

run :: Port -> Application -> IO ()
run port app = withSocketsDo $ do
    var <- newMVar Nothing
    let clean = modifyMVar_ var $ \s -> maybe (return ()) sClose s >>
return Nothing
    forkIO $ bracket
        (listenOn $ PortNumber $ fromIntegral port)
        (const clean)
        (\s -> do modifyMVar_ var (\_ -> return $ Just s);
serveConnections port app s)
    forever (threadDelay maxBound) `finally` clean

If you hit Ctrl+C in ghci on Windows you get the message
"Network.Socket.accept: failed (No error)" - but it terminates
perfectly. That error could even be dropped silently if you reach the
`finally` clause. Can this code be included in Warp?

Thanks, Neil



More information about the web-devel mailing list