
Hey Reactive, Since I have no hosting space I'm actually going to include the implementation as an attachment all in one file. It's not very long anyway, so it should be alright. A few caveats: This code is still _really_ ugly, but it does work as far as I've tested There is no game over, you need to quit manually There is no score or level adjustment yet. I need to add that when I have more time, i.e. after this week That being said, my first real reactive program was surprisingly simple once I got comfortable with the semantics. The actual reactive code isn't that complicated, but it did take a pretty big shift in thinking from writing explicit game loops. I've included a good bit of comments so it hopefully it isn't too hard to follow, but if there are any questions about why I did something a particular way (the answer may be 'I'm dumb') please e-mail me or find me on #haskell.

Excellent!
I'm still new at Haskell, and learning Reactive, but attached is some code I
would like to convert to Reactive, one day. I'm sure your Tetris example can
help me do so, thanks!
My code is most likely horrible; I did not clean it up, added no comments,
and it contains various hacks and stuff that could be done a zillion times
better and shorter by someone that actually knows Haskell well. But the
result is amusing to look at, it could be a silly screen saver.
The code is a simple semi-physical simulation of a bunch of bouncing balls.
The point of intersection is computed exactly, so the balls can move as fast
as possible. Moving the mouse to the right makes the balls move faster. It
would be interesting to see if Reactive can handle this: the sampling time
step needs to be rewound to the time of the first collision (or it could be
handled differently in a Reactive setting, I don't know)
Currently the code needs Yampa and GLFW (from Hackage), but I use Yampa only
for its vector space and forceable classes...
If anyone else wants to give this a shot: the more tutorials and demos that
use Reactive, the better :)
Cheers,
Peter Verswyvelen
2008/11/17 Creighton Hogg
Hey Reactive, Since I have no hosting space I'm actually going to include the implementation as an attachment all in one file. It's not very long anyway, so it should be alright.
A few caveats:
This code is still _really_ ugly, but it does work as far as I've tested There is no game over, you need to quit manually There is no score or level adjustment yet. I need to add that when I have more time, i.e. after this week
That being said, my first real reactive program was surprisingly simple once I got comfortable with the semantics. The actual reactive code isn't that complicated, but it did take a pretty big shift in thinking from writing explicit game loops.
I've included a good bit of comments so it hopefully it isn't too hard to follow, but if there are any questions about why I did something a particular way (the answer may be 'I'm dumb') please e-mail me or find me on #haskell.
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

I forgot to mention that if you want to run the code I've attached, you
should compile it with -O or -O2. The interpreter is too slow to handle the
brute force approach I applied...
On Tue, Nov 18, 2008 at 12:55 AM, Peter Verswyvelen
Excellent! I'm still new at Haskell, and learning Reactive, but attached is some code I would like to convert to Reactive, one day. I'm sure your Tetris example can help me do so, thanks!
My code is most likely horrible; I did not clean it up, added no comments, and it contains various hacks and stuff that could be done a zillion times better and shorter by someone that actually knows Haskell well. But the result is amusing to look at, it could be a silly screen saver.
The code is a simple semi-physical simulation of a bunch of bouncing balls. The point of intersection is computed exactly, so the balls can move as fast as possible. Moving the mouse to the right makes the balls move faster. It would be interesting to see if Reactive can handle this: the sampling time step needs to be rewound to the time of the first collision (or it could be handled differently in a Reactive setting, I don't know)
Currently the code needs Yampa and GLFW (from Hackage), but I use Yampa only for its vector space and forceable classes...
If anyone else wants to give this a shot: the more tutorials and demos that use Reactive, the better :)
Cheers, Peter Verswyvelen
2008/11/17 Creighton Hogg
Hey Reactive, Since I have no hosting space I'm actually going to include the implementation as an attachment all in one file. It's not very long anyway, so it should be alright.
A few caveats:
This code is still _really_ ugly, but it does work as far as I've tested There is no game over, you need to quit manually There is no score or level adjustment yet. I need to add that when I have more time, i.e. after this week
That being said, my first real reactive program was surprisingly simple once I got comfortable with the semantics. The actual reactive code isn't that complicated, but it did take a pretty big shift in thinking from writing explicit game loops.
I've included a good bit of comments so it hopefully it isn't too hard to follow, but if there are any questions about why I did something a particular way (the answer may be 'I'm dumb') please e-mail me or find me on #haskell.
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

Creighton,
Congratulations! As far as I know, you've made the first Reactive-based
game. And it worked on my machine without any problem.
Regards, - Conal
2008/11/17 Creighton Hogg
Hey Reactive, Since I have no hosting space I'm actually going to include the implementation as an attachment all in one file. It's not very long anyway, so it should be alright.
A few caveats:
This code is still _really_ ugly, but it does work as far as I've tested There is no game over, you need to quit manually There is no score or level adjustment yet. I need to add that when I have more time, i.e. after this week
That being said, my first real reactive program was surprisingly simple once I got comfortable with the semantics. The actual reactive code isn't that complicated, but it did take a pretty big shift in thinking from writing explicit game loops.
I've included a good bit of comments so it hopefully it isn't too hard to follow, but if there are any questions about why I did something a particular way (the answer may be 'I'm dumb') please e-mail me or find me on #haskell.
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

On 17 Nov 2008, at 21:53, Creighton Hogg wrote:
Hey Reactive, Since I have no hosting space I'm actually going to include the implementation as an attachment all in one file. It's not very long anyway, so it should be alright.
A few caveats:
This code is still _really_ ugly, but it does work as far as I've tested There is no game over, you need to quit manually There is no score or level adjustment yet. I need to add that when I have more time, i.e. after this week
That being said, my first real reactive program was surprisingly simple once I got comfortable with the semantics. The actual reactive code isn't that complicated, but it did take a pretty big shift in thinking from writing explicit game loops.
I've included a good bit of comments so it hopefully it isn't too hard to follow, but if there are any questions about why I did something a particular way (the answer may be 'I'm dumb') please e- mail me or find me on #haskell.
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. Bob

Maybe we should provide a "real" random generator in the UI / adapter...
Some CPUs provide a hardware random generator...
Maybe this http://firefly.is-a-geek.org/gmpbbs/dist/igo/igo-0.10/hwrandom.c
wraps
it already, don't known
On Tue, Nov 18, 2008 at 9:30 AM, Thomas Davie
On 17 Nov 2008, at 21:53, Creighton Hogg wrote:
Hey Reactive,
Since I have no hosting space I'm actually going to include the implementation as an attachment all in one file. It's not very long anyway, so it should be alright.
A few caveats:
This code is still _really_ ugly, but it does work as far as I've tested There is no game over, you need to quit manually There is no score or level adjustment yet. I need to add that when I have more time, i.e. after this week
That being said, my first real reactive program was surprisingly simple once I got comfortable with the semantics. The actual reactive code isn't that complicated, but it did take a pretty big shift in thinking from writing explicit game loops.
I've included a good bit of comments so it hopefully it isn't too hard to follow, but if there are any questions about why I did something a particular way (the answer may be 'I'm dumb') please e-mail me or find me on #haskell.
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.
Bob
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

On Tue, Nov 18, 2008 at 2:30 AM, Thomas Davie
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? Cheers, Creighton

On Tue, Nov 18, 2008 at 9:45 AM, Creighton Hogg
On Tue, Nov 18, 2008 at 2:30 AM, Thomas Davie
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.

Cool! Thanks to quicksilver for the insight on and elegant definition of
subs.
How about one of the following terser variations on the randomEvent def:
randomEvent std e = subs (randoms g) e
randomEvent std = subs (randoms g)
randomEvent = subs . randoms
- Conal
2008/11/18 Creighton Hogg
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.
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

Also, a less forgetful version of subs might be useful:
withSubs xs e :: [a] -> Event b -> Event (b,a)
and then
subs xs e = snd <$> withSubs xs e
or, if you like,
subs = (fmap.fmap.fmap) snd withSubs
Btw, you can read the three fmaps directly from the signature of withSubs
(two arrows plus one Event on the way to the pair).
- Conal
On Tue, Nov 18, 2008 at 10:11 AM, Conal Elliott
Cool! Thanks to quicksilver for the insight on and elegant definition of subs.
How about one of the following terser variations on the randomEvent def:
randomEvent std e = subs (randoms g) e
randomEvent std = subs (randoms g)
randomEvent = subs . randoms
- Conal
2008/11/18 Creighton Hogg
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.
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

On Tue, Nov 18, 2008 at 12:15 PM, Conal Elliott
Also, a less forgetful version of subs might be useful:
withSubs xs e :: [a] -> Event b -> Event (b,a)
and then
subs xs e = snd <$> withSubs xs e
or, if you like,
subs = (fmap.fmap.fmap) snd withSubs
Btw, you can read the three fmaps directly from the signature of withSubs (two arrows plus one Event on the way to the pair).
- Conal
That's a cute trick with the number of fmap's required. Never thought of it that way. Also, I'd like to apologize for not mentioning quicksilver from #haskell in my last e-mail. An honest slip-up, but an inappropriate one.

You can also mix in 'first' and 'second' arbitrarily and read them directly
from the type as well, when there is (possibly nested) pair structure on the
way to the value being modified. That's why I call fmap, first, and second
"semantic editor combinators". Sometime soon I'm going to blog about these
tricks.
- Conal
On Tue, Nov 18, 2008 at 10:20 AM, Creighton Hogg
On Tue, Nov 18, 2008 at 12:15 PM, Conal Elliott
wrote: Also, a less forgetful version of subs might be useful:
withSubs xs e :: [a] -> Event b -> Event (b,a)
and then
subs xs e = snd <$> withSubs xs e
or, if you like,
subs = (fmap.fmap.fmap) snd withSubs
Btw, you can read the three fmaps directly from the signature of withSubs (two arrows plus one Event on the way to the pair).
- Conal
That's a cute trick with the number of fmap's required. Never thought of it that way.
Also, I'd like to apologize for not mentioning quicksilver from #haskell in my last e-mail. An honest slip-up, but an inappropriate one.

fmap actually does the same thing as second (when applied to pairs), so
you can replace second with fmap.
If you want to go insane, you can actually make this redefinition:
import Prelude hiding ((.))
infixr 9 .
(.) :: (Functor f) => (a -> b) -> f a -> f b
(.) = fmap
and then just use (.) (either infix or bracketed) instead of fmap
throughout.
--
Robin
On Tue, 18 Nov 2008 10:23:37 -0800
"Conal Elliott"
You can also mix in 'first' and 'second' arbitrarily and read them directly from the type as well, when there is (possibly nested) pair structure on the way to the value being modified. That's why I call fmap, first, and second "semantic editor combinators". Sometime soon I'm going to blog about these tricks.
- Conal
On Tue, Nov 18, 2008 at 10:20 AM, Creighton Hogg
wrote: On Tue, Nov 18, 2008 at 12:15 PM, Conal Elliott
wrote: Also, a less forgetful version of subs might be useful:
withSubs xs e :: [a] -> Event b -> Event (b,a)
and then
subs xs e = snd <$> withSubs xs e
or, if you like,
subs = (fmap.fmap.fmap) snd withSubs
Btw, you can read the three fmaps directly from the signature of withSubs (two arrows plus one Event on the way to the pair).
- Conal
That's a cute trick with the number of fmap's required. Never thought of it that way.
Also, I'd like to apologize for not mentioning quicksilver from #haskell in my last e-mail. An honest slip-up, but an inappropriate one.

I believed second == fmap (on pairs) also until very recently. See
http://netsuperbrain.com/blog/posts/analysis-of-lazy-stream-programs/
http://lukepalmer.wordpress.com/2008/10/03/laziness-and-the-monad-laws/
Hm!
- Conal
On Tue, Nov 18, 2008 at 10:41 AM, Robin Green
fmap actually does the same thing as second (when applied to pairs), so you can replace second with fmap.
If you want to go insane, you can actually make this redefinition:
import Prelude hiding ((.))
infixr 9 . (.) :: (Functor f) => (a -> b) -> f a -> f b (.) = fmap
and then just use (.) (either infix or bracketed) instead of fmap throughout.
-- Robin
On Tue, 18 Nov 2008 10:23:37 -0800 "Conal Elliott"
wrote: You can also mix in 'first' and 'second' arbitrarily and read them directly from the type as well, when there is (possibly nested) pair structure on the way to the value being modified. That's why I call fmap, first, and second "semantic editor combinators". Sometime soon I'm going to blog about these tricks.
- Conal
On Tue, Nov 18, 2008 at 10:20 AM, Creighton Hogg
wrote: On Tue, Nov 18, 2008 at 12:15 PM, Conal Elliott
wrote: Also, a less forgetful version of subs might be useful:
withSubs xs e :: [a] -> Event b -> Event (b,a)
and then
subs xs e = snd <$> withSubs xs e
or, if you like,
subs = (fmap.fmap.fmap) snd withSubs
Btw, you can read the three fmaps directly from the signature of withSubs (two arrows plus one Event on the way to the pair).
- Conal
That's a cute trick with the number of fmap's required. Never thought of it that way.
Also, I'd like to apologize for not mentioning quicksilver from #haskell in my last e-mail. An honest slip-up, but an inappropriate one.
Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

Just to be curious, what would be the definition of withSubs? Something like
withSubs :: [a] -> Event b -> Event (b,a)
withSubs xs = (fmap.fmap) head . stateE xs tail
Haven't tested it, still actively learning reactive...
2008/11/18 Conal Elliott
Also, a less forgetful version of subs might be useful:
withSubs xs e :: [a] -> Event b -> Event (b,a)
and then
subs xs e = snd <$> withSubs xs e
or, if you like,
subs = (fmap.fmap.fmap) snd withSubs
Btw, you can read the three fmaps directly from the signature of withSubs (two arrows plus one Event on the way to the pair).
- Conal
On Tue, Nov 18, 2008 at 10:11 AM, Conal Elliott
wrote: Cool! Thanks to quicksilver for the insight on and elegant definition of subs.
How about one of the following terser variations on the randomEvent def:
randomEvent std e = subs (randoms g) e
randomEvent std = subs (randoms g)
randomEvent = subs . randoms
- Conal
2008/11/18 Creighton Hogg
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.
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

That definition looks right to me, Peter. Nice job! - Conal
On Tue, Nov 18, 2008 at 2:18 PM, Peter Verswyvelen
Just to be curious, what would be the definition of withSubs? Something like withSubs :: [a] -> Event b -> Event (b,a) withSubs xs = (fmap.fmap) head . stateE xs tail
Haven't tested it, still actively learning reactive...
2008/11/18 Conal Elliott
Also, a less forgetful version of subs might be useful:
withSubs xs e :: [a] -> Event b -> Event (b,a)
and then
subs xs e = snd <$> withSubs xs e
or, if you like,
subs = (fmap.fmap.fmap) snd withSubs
Btw, you can read the three fmaps directly from the signature of withSubs (two arrows plus one Event on the way to the pair).
- Conal
On Tue, Nov 18, 2008 at 10:11 AM, Conal Elliott
wrote: Cool! Thanks to quicksilver for the insight on and elegant definition of subs.
How about one of the following terser variations on the randomEvent def:
randomEvent std e = subs (randoms g) e
randomEvent std = subs (randoms g)
randomEvent = subs . randoms
- Conal
2008/11/18 Creighton Hogg
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.
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

On 17 Nov 2008, at 21:53, Creighton Hogg wrote:
Hey Reactive, Since I have no hosting space I'm actually going to include the implementation as an attachment all in one file. It's not very long anyway, so it should be alright.
A few caveats:
This code is still _really_ ugly, but it does work as far as I've tested There is no game over, you need to quit manually There is no score or level adjustment yet. I need to add that when I have more time, i.e. after this week
That being said, my first real reactive program was surprisingly simple once I got comfortable with the semantics. The actual reactive code isn't that complicated, but it did take a pretty big shift in thinking from writing explicit game loops.
I've included a good bit of comments so it hopefully it isn't too hard to follow, but if there are any questions about why I did something a particular way (the answer may be 'I'm dumb') please e- mail me or find me on #haskell.
A quick note -- it appears to have a memory leak, the RAM usage steps up 30MB about every 1-2 minutes. It'd be interesting to know where that's coming from. Bob

Thanks for posting this. Great stuff!
David
2008/11/17 Creighton Hogg
Hey Reactive, Since I have no hosting space I'm actually going to include the implementation as an attachment all in one file. It's not very long anyway, so it should be alright.
A few caveats:
This code is still _really_ ugly, but it does work as far as I've tested There is no game over, you need to quit manually There is no score or level adjustment yet. I need to add that when I have more time, i.e. after this week
That being said, my first real reactive program was surprisingly simple once I got comfortable with the semantics. The actual reactive code isn't that complicated, but it did take a pretty big shift in thinking from writing explicit game loops.
I've included a good bit of comments so it hopefully it isn't too hard to follow, but if there are any questions about why I did something a particular way (the answer may be 'I'm dumb') please e-mail me or find me on #haskell.
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive
-- David Sankel Sankel Software

My colleague Thomas Davie was playing with your Tetris game, and it seemed
that it contained a space leak; it was consuming more memory, slowly.
Could it be caused by the top level
testTicks :: Event () testTicks = levelToTicks 1
I'm not sure how Events are implemented in Reactive, but in a classical FRP
setting the "heads" of this top level variable would never get garbage
collected.
2008/11/17 Creighton Hogg
Hey Reactive, Since I have no hosting space I'm actually going to include the implementation as an attachment all in one file. It's not very long anyway, so it should be alright.
A few caveats:
This code is still _really_ ugly, but it does work as far as I've tested There is no game over, you need to quit manually There is no score or level adjustment yet. I need to add that when I have more time, i.e. after this week
That being said, my first real reactive program was surprisingly simple once I got comfortable with the semantics. The actual reactive code isn't that complicated, but it did take a pretty big shift in thinking from writing explicit game loops.
I've included a good bit of comments so it hopefully it isn't too hard to follow, but if there are any questions about why I did something a particular way (the answer may be 'I'm dumb') please e-mail me or find me on #haskell.
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

Creighton Hogg wrote:
This code is still _really_ ugly, but it does work as far as I've tested
No it's not. It's slightly ugly in places, that's all :) Nice work!
That being said, my first real reactive program was surprisingly simple once I got comfortable with the semantics. The actual reactive code isn't that complicated, but it did take a pretty big shift in thinking from writing explicit game loops.
I have a comment on this point, let me find the exact code: -- This is one of the functions used to convert the event stream of keys -- into an event stream of game state modifiers. It makes me -- fundamentally happy that it can be an entirely pure transformation of -- the state instead of having to live instead a game loop. movePiece :: Key -> Board -> (Piece -> Piece) This is good design, but it's totally orthogonal to the use of reactive. All my conventional imperative haskell GUI programs contain at their core pure values like this (another alternative I sometimes use would be [(Key,Board -> Piece -> Piece)], accessed via Prelude.lookup). They are driven by an imperative scaffold instead of a reactive scaffold but actually isn't particularly hard - the scaffold is thin, the hard work is all in pure values like this. The place where I believe FRP starts to really show its usefulness is in compostionality. The imperative scaffold doesn't compose as well (I don't think) as the reactive scaffold does (I hope!). The interesting challenge to test this, I think, is to add some "modality" to your game. In particular I'm thinking of a "main menu" (that's one mode, different from playing, and presumably has different keybindings in effect), and perhaps a "game over" mode which has some kind of background animation displayed along with your final score and the option to return to the main menu. It's in composing of different modes in this sense that I have begun to find imperative scaffolds clumsy. Jules

Yes, I totally agree with Jules. The interesting part is to see how well
this "scales", how easy it is to do modifications and add enhancements.
We're playing a lot with Creighton's Tetris code here at Anygma. Bob already
added a preview of the next block, I changed the level tick so that the tick
interval decreases continuously (meaning you can never win this Tetris game
;-) and I fixed the colors of the block (Creighton, letting white blocks
fall on a white background is an interesting twitch, but rather hard to play
;-), all without too many modifications. But it is interesting to see if
adding more features indeed can be done in a nice compositional way...
Peter
On Thu, Nov 20, 2008 at 8:04 AM, Jules Bean
Creighton Hogg wrote:
This code is still _really_ ugly, but it does work as far as I've tested
No it's not.
It's slightly ugly in places, that's all :)
Nice work!
That being said, my first real reactive program was surprisingly simple
once I got comfortable with the semantics. The actual reactive code isn't that complicated, but it did take a pretty big shift in thinking from writing explicit game loops.
I have a comment on this point, let me find the exact code:
-- This is one of the functions used to convert the event stream of keys -- into an event stream of game state modifiers. It makes me -- fundamentally happy that it can be an entirely pure transformation of -- the state instead of having to live instead a game loop.
movePiece :: Key -> Board -> (Piece -> Piece)
This is good design, but it's totally orthogonal to the use of reactive. All my conventional imperative haskell GUI programs contain at their core pure values like this (another alternative I sometimes use would be [(Key,Board -> Piece -> Piece)], accessed via Prelude.lookup). They are driven by an imperative scaffold instead of a reactive scaffold but actually isn't particularly hard - the scaffold is thin, the hard work is all in pure values like this.
The place where I believe FRP starts to really show its usefulness is in compostionality. The imperative scaffold doesn't compose as well (I don't think) as the reactive scaffold does (I hope!).
The interesting challenge to test this, I think, is to add some "modality" to your game. In particular I'm thinking of a "main menu" (that's one mode, different from playing, and presumably has different keybindings in effect), and perhaps a "game over" mode which has some kind of background animation displayed along with your final score and the option to return to the main menu.
It's in composing of different modes in this sense that I have begun to find imperative scaffolds clumsy.
Jules
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive
participants (7)
-
Conal Elliott
-
Creighton Hogg
-
David Sankel
-
Jules Bean
-
Peter Verswyvelen
-
Robin Green
-
Thomas Davie