Quick tip: did you try using withSocketsDo[1]? [1] http://hackage.haskell.org/packages/archive/network/2.4.1.2/doc/html/Network.html#g:2
On Thu, Mar 28, 2013 at 5:00 PM, Lars Kuhtz <hask...@kuhtz.eu> wrote: > Hi, > > I'd like to know what is wrong with the following program on windows8 (GHC > 7.4.2, 32bit): > > {-# LANGUAGE OverloadedStrings #-} > {-# LANGUAGE ScopedTypeVariables #-} > > module Main where > > import Control.Concurrent.Async > import qualified Control.Exception as E > import Network.HTTP.Conduit > import Network.HTTP.Types > import Network.Wai > import Network.Wai.Handler.Warp > > query port = E.catch > (simpleHttp ("http://haskell.org:" ++ show port) >>= print . take 10 . > show) > (\(e :: HttpException) -> print $ "caught: " ++ show e) > > listen = run 8080 $ \_ -> > return $ responseLBS ok200 [] "abc" > > main = do > withAsync (query 12345) $ \a -> do > withAsync listen $ \b -> do > wait a > wait b > > I compile the program with "ghc --make -threaded Main.hs" and run it as > "./Main +RTS -N". > > On POSIX systems this works as expected. Even if the failing "query" runs in > a forever loop the "listen" thread responds promptly to requests. On windows > the "listen" thread seems blocked by the failing "query" thread. Sometimes > the query returns (relatively) prompt. But sometimes (about a third of all > runs) it takes very long (about 20 sec). Also, sometimes it returns with > "Connection timed out (WSAETIMEDOUT)", sometimes with "getAddrInfo: does not > exist (error 11003)", and sometimes just with "FailedConnectionException". > > The fact that the "listen" thread is blocked seems to contradict the > following quote form the documentation of Control.Concurrent: > > -- Quote from Control.Concurrent -- > Using forkOS instead of forkIO makes no difference at all to the scheduling > behaviour of the Haskell runtime system. It is a common misconception that > you need to use forkOS instead of forkIO to avoid blocking all the Haskell > threads when making a foreign call; this isn't the case. To allow foreign > calls to be made without blocking all the Haskell threads (with GHC), it is > only necessary to use the -threaded option when linking your program, and to > make sure the foreign import is not marked unsafe. > -- End Quote -- > > By the way: using withAsyncBound instead of withAsync seems to improve (but > not completely solve) the issue. > > Thanks, > Lars > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Felipe. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe