[Haskell-cafe] Space leak with recursion
Martijn Rijkeboer
haskell at bunix.org
Fri Apr 24 10:16:55 UTC 2015
>> Maybe I don't understand, but inside the pollServer function a call to
>> poll is done and on line 47 and 56 of that same function, pollServer is
>> called again (recursive).
>
> It's fine to call `pollServer` recursively, but it's not fine to
> call it recursively from a handler, i.e. something that occurs in the
> second argument to `poll`.
Clear, my bad. I've just implemented a version with StateT (code below)
and it doesn't leak space as you already expected. Thank you very much
for your help.
Kind regards,
Martijn Rijkeboer
--- code ---
module Observable
( run
) where
import Control.Monad (forever, void)
import Control.Monad.State (StateT, get, liftIO, put, runStateT)
import Data.Int (Int64)
import System.ZMQ4
data State = State
{ nextSeqNum :: !Int64
, listenSocket :: !(Socket Pull)
}
run :: IO ()
run = do
withContext $ \ctx ->
withSocket ctx Pull $ \observer -> do
setLinger (restrict (0::Int)) observer
bind observer "tcp://*:7010"
let state = State
{ nextSeqNum = 0
, listenSocket = observer
}
void $ runStateT pollSockets state
return ()
pollSockets :: StateT State IO ()
pollSockets = do
state <- get
forever $
void $ poll (-1) [Sock (listenSocket state) [In] (Just
observerHandleEvts)]
observerHandleEvts :: [Event] -> StateT State IO ()
observerHandleEvts _ = do
state <- get
liftIO $ void $ receiveMulti $ listenSocket state
liftIO $ printSeqNum state
put $ incrSeqNum state
printSeqNum :: State -> IO ()
printSeqNum state = putStrLn $ show $ nextSeqNum state
incrSeqNum :: State -> State
incrSeqNum state = state{nextSeqNum = currSeqNum + 1}
where currSeqNum = nextSeqNum state
More information about the Haskell-Cafe
mailing list