[web-devel] Handling disconnection in wai or warp

Michael Snoyman michael at snoyman.com
Thu Sep 1 14:34:46 CEST 2011


I think this does what you're looking for. Note how we have to handle
the exception (via finally) that's thrown by the closing connection:

{-# LANGUAGE OverloadedStrings #-}
import Network.Wai (Application, Response (ResponseEnumerator))
import Network.Wai.Handler.Warp (run)
import Network.HTTP.Types (status200)
import Data.Enumerator (run_, ($$), enumList)
import Blaze.ByteString.Builder.Char.Utf8 (fromShow)
import Control.Exception (finally)

main :: IO ()
main = run 3000 app

app :: Application
app _ = return $ ResponseEnumerator $ \f ->
    run_ (enum $$ f status200 [("content-type", "text/plain")])
        `finally` cleanup
  where
    enum = enumList 8 $ map fromShow [1 :: Int ..]
    cleanup = putStrLn "Connection closed"

On Thu, Sep 1, 2011 at 6:38 AM, Hiromi ISHII <konn.jinro at gmail.com> wrote:
> Thanks Michael and Gregory.
>
> On 2011/08/29, at 19:07, Michael Snoyman wrote:
>
>> I'm not entirely certain what's going on here, but my guess is that
>> for either WAI or Snap you'd want to use the enumerator interface
>> instead of lazy ByteStrings.
>
> I understand that I have to use ResponseEnumerator to build a response to achieve my goal, right?
> If so, how to handle disconnections in ResponseEnumerator?
>
>>  Also, for WAI, you should *not* set the
>> transfer-encoding, that is something the backend handles for you
>> automatically.
> Thanks. I fiexed it.
>
> On 2011/08/29, at 22:10, Gregory Collins wrote:
>
>> Correct, with either WAI or Snap you will need to write an enumerator
>> to do this.
>
> You mean I have to use addToOutput function instead of writeLBS?
> I rewrote my code using addOutput  as below:
>
> = Snap  Code =
> stream :: Application ()
> stream = do
>  req <- withRequest $ return . (rqRemoteAddr &&& rqRemotePort)
>  addToOutput $ myEnumerator
>  logError "this would never be happened..."
>
> myEnumerator (Continue k) = k (Chunks $ map fromLazyByteString  $ map (LBS.pack . show) [1..])
> myEnumerator s@(Error err) = liftIO (print err) >> returnI s
> myEnumerator step@(Yield _ _) = liftIO (putStrLn "yielded.") >> returnI step
> = end =
>
> Running snap server using this code, I accessed the page from browser and disconnect, but nothing is written in the log.
> What's my mistakes?
>
>
> In addition, I tried to use 'settingsOnException' to handle the Exception in WAI.
> It could handle disconnection, but I couldn't know which conneciton is closed.
> Is there any method to know which connection is closed?
>
>
> -- Hiromi ISHII
> konn.jinro at gmail.com
>
>
>
>



More information about the web-devel mailing list