[reactive] First draft of reactive-tetris

Creighton Hogg wchogg at gmail.com
Tue Nov 18 11:16:54 EST 2008


On Tue, Nov 18, 2008 at 9:45 AM, Creighton Hogg <wchogg at gmail.com> wrote:

> On Tue, Nov 18, 2008 at 2:30 AM, Thomas Davie <tom.davie at gmail.com> wrote:
>  <snip me>
>
>> Wow, that's rather nice, unfortunately I can't run it at the moment,
>> because I've run into the GLUT problems so many people have.  I'm wondering
>> though about your definition of randomBehavior.
>>
>> randomBehavior :: (Random a) => Double -> Behavior a
>> randomBehavior s = fmap (fst . random . mkStdGen . round . (+s)) time
>>
>> I don't know the theory behind pseudo random number generators well enough
>> to be sure, but I have a feeling that while this may be good enough for a
>> game, it's probably not good enough for anything the relies on the numbers
>> it generates being totally unpredictable.  The reason I say that is that as
>> far as I understand it, the guarentee we're given with a pseudo random
>> number generator is that given an output number, the next output number is
>> impossible to predict.  I don't think we're given any guarantee that given a
>> monotonically increasing seed, the output of the generator will look
>> particularly different, or be unpredictable.
>>
>> Unfortunately, I don't think that I can come up with a better way to
>> define the behavior though.  It would be possible to define an Event at a
>> certain interval that splits the random seed at each occurrence, but I can't
>> do better than that.
>
>
> You're absolutely right about randomBehavior and, unfortunately, I was a
> bit at a loss for what to do to thread through a random number generator.
>
> I think the basic conclusion I've come to is that it might actually be
> 'wrong' to want a Behavior of random values if they are to be properly
> generated from a pseudo-random generator, as the semantics would require you
> to somehow be using the RandomGen an infinite number of times to get the
> right see at any instance.  Behaviors are supposed to be continuous
> afterall.
>
> What I think we really want is a way of saying "at every occurrence of an
> event, we want an 'a'" such that the distribution of a's is pseudorandom.
> To me, this would mean trying to make Event, already a Monad, an instance of
> MonadRandom from Cale Gibbard's library of the same name.  This doesn't seem
> like it should be hard, but I'm not clear on it yet.
>
> I guess it would drop out pretty readily if one had a way to substitute the
> values of an infinite list sequentially into an Event stream, since then one
> could take in a RandomGen and use the randoms :: g -> [a] function to create
> the list & then pair it with the Event.  I don't know if there's a way to do
> that without breaking the Event abstraction, but conceptually it makes sense
> to me:  it's just establishing an isomorphism between infinite lists.
>
> Any other thoughts anyone?


Being a dirty schlub & replying to myself, it turns out there is a way to
substitute an infinite list into an Event as we've talked about this on
#haskell this morning.

subs xs e :: [a] -> Event b -> Event a
subs xs e = head <$> accumE xs (tail <$ e)

so then we can very easily do

randomEvent :: (RandomGen g,Random b) => g -> Event a -> Event b
randomEvent std e = let vals = randoms g in subs vals e

Cool!
Now I just need to change my Tetris to do that instead of messing with a
Behavior.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/reactive/attachments/20081118/340a2328/attachment-0001.htm


More information about the Reactive mailing list