Reactive/Tutorial/A FPS display

From HaskellWiki
< Reactive
Revision as of 08:16, 9 January 2009 by Ksf (talk | contribs) (An introductory reactive-fieldtrip tutorial)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search

Being the game programmer I am, It's vitally important for me to know the FPS my code is running at, even if there is no code yet. Some knowledge of Haskell, particularly not being scared of overly-general type signatures and browsing haddock docs, is assumed. Experience with point-free style will come in handy, too.

Let's dive in, bottom to top:

fpsE :: UI -> Event TimeT
fpsE = fmap ((1/) . uncurry (-)) . withPrevE . withTimeE_ . framePass

fpsE is a function that maps from UI, defined in FRP.Reactive.GLUT.Adapter and representing the outside world as known to GLUT, to a stream of Events, each event occurrence carrying the current frames per seconds. TimeT is Double, for all you care, with a whole number increment representing a second passing in the real world.

Note that while Event a is a stream of events, the stream nature does not necessarily show up in your code: If you're only interested in one event at a time, nothing is forcing you to care about more than that.

Reading the above backwards, we get the following:

  • framePass :: UI -> Event () is fed with our UI and returns an Event (), each occurrence representing the passing of a frame.
  • The result is then being fed into withTimeE_ :: Ord t => EventG (Improving t) d -> EventG (Improving t) t, replacing the () in our stream with a TimeT representing the time of occurrence of our frame passes.
  • withPrevE :: Event a -> Event (a, a) pairs up an event's value with the value of the preceding event. This means that the resulting stream's first event occurs at the same time as the original stream's second event, which makes sense: However hard we try, we won't be able to calculate the time difference between the first frame and the ones not preceding it.
  • Finally, we compute the reciprocal of the time delta ((1/) . uncurry (-)) of (TimeT, TimeT)... not Event (TimeT, TimeT). That's what the fmap is for.

fmap is a function you'll meet quite often working with Reactive, it is a generalised map: Given a function (a -> b) and a structure S a, it will return a S b, changing the value but preserving the structure... provided S has a sane Functor instance.

Now, what are we going to do if we need an UI -> Event String, but have an UI -> Event TimeT? Procrastinating, of course. We're going to need a formatting function, anyway, so let's worry about that, first:

showFPS :: TimeT -> String
showFPS d = showFFloat (Just 2) d "fps"

fmap maps a function over a structure, so fmaping an fmap maps a function over two structures... or, if you prefer, pierces two structures: ((fmap.fmap) showFPS fpsE) is a honest-to-Hindley-Milner function of the type UI -> Event String.

Bewildered? Read the wikibook entry on Applicative Functor and Peter Verswyvelen's tutorial on (fmap.fmap.fmap.fmap.fmap.fmap). For now, just accept that ((->) a) is a type like every other.

Knowing that, we can use the function stepper :: a -> Event a -> Behaviour a to convert our Event String to a Behaviour String... the difference between Events and Behaviours being that an Event describes things that happen at particular times, like us being able to compute the current fps because a frame passed, and a Behaviour describes what a thing is, over time. stepper produces a thing that changes every time an event occurs: a discretely changing function. Behaviours may be non-discrete, too, but we're not going to worry about that, now (even if it is their main excuse for existing in the first place).

timeString :: UI -> Behaviour String
timeString = stepper "" . ((fmap.fmap) showFPS fpsE)

The fist value passed to stepper is the value the Behaviour should have before the first event occurs, in our case it's quite sensible to leave the fps display empty during the first frame.

Anim3, a type defined in FRP.Reactive.Fieldtrip.Adapter, is equivalent to UI -> Behaviour Geometry3: Given a reactive representation of the real world, we are assumed to return a continuous representation of the virtual world we want to display, so that the plumbing in the background can sample it any time it wants to display a frame.

timeText :: Anim3 -- UI -> Behaviour Geometry3
timeText = (fmap.fmap) (flatG . utext) timeString

utext takes a String and returns a Geometry2, that is, a vanilla OpenGL line font... not the actual geometry, though, just a description of it. Tesselation, rendering, in general everything that requires calls into GL, is done after reactive told fieldtrip what to render. flatG lifts two-dimensional geometry into three-dimensional space.

We're done! That is, the only thing left is opening a window, initialising GL, mangling the camera so that you can actually see stuff, and so on:

main = anim3 timeText

We could have used anim2 and left out the flatG, but I didn't fell like doing that.

Some time later, we're going to figure out how to display our fps at a decent place and scale, possibly figure out how to use TrueType fonts and, generally, figure out how to do everything one can do with reactive and fieldtrip.