Lazy variant of sequence (or other way to approach problem)

Hey, In my (SDL based) haskell program, I do: events <- liftM ( takeWhile (/= NoEvent)) $ sequence $ repeat pollEvent The execution of this never returns, I am guessing that is because sequence evaluation never stops. But if sequence would be lazy (and assuming pollEvent returns NoEvent at some point) this should stop, should it not? Is there a lazy variant of sequence? Or am I missing something here completely? Thanks! Nathan

Nathan Hüsken
In my (SDL based) haskell program, I do:
events <- liftM ( takeWhile (/= NoEvent)) $ sequence $ repeat pollEvent
The execution of this never returns, I am guessing that is because sequence evaluation never stops.
But if sequence would be lazy (and assuming pollEvent returns NoEvent at some point) this should stop, should it not? Is there a lazy variant of sequence? Or am I missing something here completely?
The sequence function itself cannot be lazy, and there can't be a lazy variant of it. What you want is unsafeLazySequenceIO, which uses unsafeInterleaveIO under the hood, which is IO-specific. As always lazy I/O is probably a bad idea and you should write a coroutine-based combinator for that. The simplest way is the ad-hoc way: pollEvent_ = do ev <- pollEvent case ev of NoEvent -> pollEvent_ _ -> return ev The coroutine-based method would look something like this: import Control.Monad.Trans.Free -- from the 'free' package newtype AppF a = AppF (Event -> a) type App = FreeT AppF IO Since FreeT is effectively just Coroutine from the monad-coroutine package you can use that one instead with the 'Await Event' functor, but the 'free' package provides a lot more useful instances. Your main loop can then suspend to ask for the next event and the surrounding application can provide the event in whatever way it wishes (for example ignoring NoEvent): myLoop = do ev <- await case ev of Quit -> return () _ -> doSomethingWith ev By the way, if your application is non-continuously rendered, which is suggested by your ignoring of NoEvent, you shouldn't use pollEvent at all. Rather you should use waitEvent, which blocks instead of returning NoEvent. That way you don't waste precious CPU cycles. The pollEvent action is meant for applications that are continuously rendered, where you would e.g. perform drawing when you get NoEvent. Hope this helps. Greets, Ertugrul -- Not to be or to be and (not to be or to be and (not to be or to be and (not to be or to be and ... that is the list monad.

On 09/27/2012 01:45 AM, Ertugrul Söylemez wrote:
Nathan Hüsken
wrote: In my (SDL based) haskell program, I do:
events <- liftM ( takeWhile (/= NoEvent)) $ sequence $ repeat pollEvent
The execution of this never returns, I am guessing that is because sequence evaluation never stops.
But if sequence would be lazy (and assuming pollEvent returns NoEvent at some point) this should stop, should it not? Is there a lazy variant of sequence? Or am I missing something here completely?
The sequence function itself cannot be lazy, and there can't be a lazy variant of it.
I understand, that it is a bad Idea. But why is it impossible to have an lazy sequence? Why can it not wait with the execution of the action for the list elements to be evaluated?
By the way, if your application is non-continuously rendered, which is suggested by your ignoring of NoEvent, you shouldn't use pollEvent at all.
The Idea of the line what to return all events that happened in the current frame (which are to my understanding all events until pollEvent returns NoEvent).
Hope this helps.
Yes, thank you. I have to read into the Coroutine approach a little more before to understand it :). Best Regards, Nathan

On Thu, Sep 27, 2012 at 9:14 AM, Nathan Hüsken
On 09/27/2012 01:45 AM, Ertugrul Söylemez wrote:
Nathan Hüsken
wrote: In my (SDL based) haskell program, I do:
events <- liftM ( takeWhile (/= NoEvent)) $ sequence $ repeat pollEvent
The execution of this never returns, I am guessing that is because sequence evaluation never stops.
Yes, which is why you should include the condition in the loop, the standard library doesn't include facilities for that but the monad-loop package has this function (amongst others) :
unfoldWhileM :: Monadhttp://hackage.haskell.org/packages/archive/base/4.5.0.0/doc/html/Control-Mo...m => (a -> Boolhttp://hackage.haskell.org/packages/archive/base/4.5.0.0/doc/html/Data-Bool....) -> m a -> m [a]
which you could use as :
events <- unfoldWhileM (=/ NoEvent) pollEvent
(note that if this is the only thing you use from this library, you may just write this function for yourself, it is quite easy in the direct style like the pollEvent_ proposed by Ertugrul)
But if sequence would be lazy (and assuming pollEvent returns NoEvent at some point) this should stop, should it not? Is there a lazy variant of sequence? Or am I missing something here completely?
The sequence function itself cannot be lazy, and there can't be a lazy variant of it.
I understand, that it is a bad Idea. But why is it impossible to have an lazy sequence? Why can it not wait with the execution of the action for the list elements to be evaluated?
Normally, with the normal semantics of monads, you can't have a lazy sequence because it could mean that monad evaluation could be interspersed in pure code without it being apparent (which is particularly dangerous with IO) which is why you need to use unsafe functions to get this unnatural result. It is also generally a bad idea for the same reason as lazy IO is, to illustrate this in your particular case : you don't have _any_ guarantee that it would work correctly : if you only start consuming "events" a few seconds later, you wouldn't get the result from a few seconds ago, you would get the current events... Maybe this doesn't happen now in your application but can you be _sure_ that you'll never need to stock those lists of events to consult them later on ? -- Jedaï

Nathan Hüsken
On 09/27/2012 01:45 AM, Ertugrul Söylemez wrote:
Nathan Hüsken
wrote: In my (SDL based) haskell program, I do:
events <- liftM ( takeWhile (/= NoEvent)) $ sequence $ repeat pollEvent
The execution of this never returns, I am guessing that is because sequence evaluation never stops.
But if sequence would be lazy (and assuming pollEvent returns NoEvent at some point) this should stop, should it not? Is there a lazy variant of sequence? Or am I missing something here completely?
The sequence function itself cannot be lazy, and there can't be a lazy variant of it.
I understand, that it is a bad Idea. But why is it impossible to have an lazy sequence? Why can it not wait with the execution of the action for the list elements to be evaluated?
Because the Monad class does not have a combinator for that. Unsafe interleaving is a feature of the IO monad, not of monads in general. However I was lying a bit. Whether sequence is lazy does not depend on its implementation, but on the monad. If asking for the head of the result list only ever depends on part of the computation, then only that part has to be performed. This is especially true for the 'Reader e' and '(->) e' monads (which are the isomorphic, btw.): sequence (sin : undefined) = liftM2 (:) sin (sequence undefined) = \e -> sin e : sequence undefined e A trivial example is Identity: sequence (return 3 : undefined) = liftM2 (:) (return 3) (sequence undefined) = Identity (3 : runIdentity (sequence undefined)) IIRC monads with that property are called affine monads. The Maybe monad does not have this property: sequence (Just 3, undefined) = liftM2 (:) (Just 3) (sequence undefined) = case Just 3 of Just x -> case sequence undefined of Just xs -> Just (x:xs) Nothing -> Nothing Nothing -> Nothing This will reach the undefined in the inner case, before it gets the opportunity to deliver a result, because the ability to deliver a results depends on whether 'sequence undefined' is a Just. The Maybe monad's counterpart to unsafeInterleaveIO is: unsafeInterleaveMaybe :: Maybe a -> Maybe a unsafeInterleaveMaybe ~(Just x) = Just x With the help of this combinator you can actually write unsafeLazySequenceMaybe.
By the way, if your application is non-continuously rendered, which is suggested by your ignoring of NoEvent, you shouldn't use pollEvent at all.
The Idea of the line what to return all events that happened in the current frame (which are to my understanding all events until pollEvent returns NoEvent).
Lazy sequence is not what you want for that. It would be semantically wrong or at least weird if a second invocation of that action could ever produce a result, because the first one is supposed to have produced all events that ever happened. Greets, Ertugrul -- Not to be or to be and (not to be or to be and (not to be or to be and (not to be or to be and ... that is the list monad.
participants (3)
-
Chaddaï Fouché
-
Ertugrul Söylemez
-
Nathan Hüsken