Hi Haskell Cafe,
When I start a web server (http-server:Network.HTTP.Server.serverWith) on a separate thread (async:Control.Concurrent.Async.withAsync) and then try to retrieve a response from the server (HTTP:Network.Browser.*) on a threaded runtime, I see eitherBefore I sink time into reading the source of the packages in question, does anybody see what's wrong with the code below?
- connection refusals or
- deadlock.
Increasing the timeout to wait for the server to initialize doesn't solve the problem. Using a bound thread doesn't solve the problem. I'm compiling with options "-threaded -rtsopts -with-rtsopts=-N".
Thank you for taking a look.
--Patrick
module Lib
( someFunc
) where
import Control.Monad.IO.Class (liftIO)
import qualified Control.Concurrent as Concurrent
import qualified Control.Concurrent.Async as Async
import qualified Control.Exception as Exception
import qualified Data.Maybe as Maybe
import qualified Network.Browser as Browser
import qualified Network.HTTP as HTTP
import qualified Network.HTTP.Server as Server
import qualified Network.HTTP.Server.Logger as ServerL
import qualified Network.HTTP.Server.Response as ServerR
import qualified Network.URI as URI
someFunc :: IO (Either Exception.SomeException (URI.URI, HTTP.Response String))
someFunc = do
Async.withAsync (Server.serverWith config handler) $ \_ -> do
Concurrent.threadDelay . round $ 2e6
Exception.try . Browser.browse . Browser.request . Browser.defaultGETRequest $ uri
where
uri = Maybe.fromJust . URI.parseURI $ "http://localhost:8080/"
config = Server.Config ServerL.stdLogger "localhost" 8080
handler _ url req = return (ServerR.respond ServerR.OK :: Server.Response String)