+ All Categories
Home > Documents > Chapter 15 A Module of Reactive Animations. Motivation The design of animations in Chapter 13 is...

Chapter 15 A Module of Reactive Animations. Motivation The design of animations in Chapter 13 is...

Date post: 21-Dec-2015
Category:
View: 216 times
Download: 2 times
Share this document with a friend
22
Chapter 15 A Module of Reactive Animations
Transcript

Chapter 15

A Module of Reactive Animations

Motivation

The design of animations in Chapter 13 is elegant, and in fact has the feel of a small domain-specific language (DSL), embedded in Haskell.

However, the language lacks reactivity:the ability to interact with the user or other external stimuli.

In this chapter we add reactivity, and call the resulting DSL functional animation language, or FAL.

In addition, an implementation of FAL is described, using streams.

FAL by Example

As before, we use the polymorphic data type “Behavior” to capture time-varying values.

For example:color1 :: Behavior Colorcolor1 = red `untilB` (lbp ->> blue)

ball1 :: Behavior Pictureball1 = paint color1 circ

circ :: Behavior Regioncirc = translate (cos time, sin time) (ell 0.2 0.2)

The function “untilB” reflects reactive behavior, and “lbp” corresponds to a left button press.

More Reactivity

Recursive reactivity:color1r = red `untilB` lbp ->>

blue `untilB` lbp ->>color1r

Choice reactivity:color2 = red `untilB`

((lbp ->> blue) .|. (key ->> yellow))

Recursive, choice reactivity:color2r = red `untilB` colorEvent where

colorEvent = (lbp ->> blue `untilB` colorEvent) .|.

(key ->> yellow `untilB` colorEvent)

Pushing recursion into combinator:color2h = red `switch` ((lbp ->> blue) .|. (key ->>

yellow))

Events With Data

Convert button-press events into color events:color1h = red `switch`

(lbp `withElem_` cycle [blue, red]) Dispatch on key press:

color3 = white `switch` (key =>> \c -> case c of 'R' -> red

'B' -> blue'Y' -> yellow _ -> white )

Carrying state forward:color4 = white `switch`

((key `snapshot` color4) =>> \(c, old) ->

case c of 'R' -> red'B' -> blue'Y' -> yellow _ -> lift0 old)

Dynamic Events

Not all events are external. For example: while (time >* 42)

generates no events until time exceeds 42, and then generates events “infinitely often”.

when (time >* 42)generates exactly one event when the time exceeds 42.

color5 = red `untilB` (when (time >* 5) ->> blue)

Integration

The position of a mass under the influence of an accelerating force f:

s, v :: Behavior Floats = s0 + integral vv = v0 + integral f

Combining with reactivity, a bouncing ball:ball2 = paint red (translate (x,y) (ell 0.2 0.2))

where g = -4x = -3 + integral 0.5y = 1.5 + integral vv = integral g `switch` (hit `snapshot_` v

=>> \v'-> lift0 (-v') + integral g)

hit = when (y <* -1.5)

Note similarity tomathematical equations.

Implementing FAL

Previously a behavior was conceptually a function:

Behavior a ≡ Time -> a But somehow we must now introduce events.

One obvious approach would be:Behavior a ≡ [(UserAction, Time)] -> Time -> a

But this would be very inefficient (why?). Better to do this:

Behavior a ≡ [(UserAction, Time)] -> [Time] -> [a]

Or, even more efficient, and now as Haskell code:newtype Behavior a = Behavior ( ([Maybe UserAction], [Time]) -> [a] )

(see text for definition of UserAction)

Time and Constants

Recall:newtype Behavior a =

Behavior ( ([Maybe UserAction], [Time]) -> [a] )

With this representation, let’s define time:time :: Behavior Timetime = Behavior (\(_,ts) -> ts)

Constant behaviors are achieved via lifting:constB :: a -> Behavior aconstB x = Behavior (\_ -> repeat x)

For example:red, blue :: Behavior Colorred = constB Redblue = constB Blue

Curried Liftings

From this “lifted” version of application:($*) :: Beh (a->b) -> Beh a -> Beh bBeh ff $* Beh fb =

Beh (\uts -> zipWith ($) (ff uts) (fb uts)) and the constant lifting operator:

lift0 :: a -> Beh alift0 = constB

all other lifting operators can be defined:lift1 :: (a -> b) -> (Beh a -> Beh b)lift1 f b1 = lift0 f $* b1

lift2 :: (a -> b -> c) -> (Beh a -> Beh b -> Beh c)lift2 f b1 b2 = lift1 f b1 $* b2

lift3 :: (a -> b -> c -> d) -> (Beh a -> Beh b -> Beh c -> Beh d)

lift3 f b1 b2 b3 = lift2 f b1 b2 $* b3

(For conciseness, “Beh” is used

instead of “Behavior”.)

Sample Liftings

pairB :: Behavior a -> Behavior b -> Behavior (a,b)pairB = lift2 (,)fstB :: Behavior (a,b) -> Behavior afstB = lift1 fstpaint :: Behavior Color -> Behavior Region -> Behavior Picturepaint = lift2 Regionred, blue, yellow, green, white, black :: Behavior Colorred = lift0 Redblue = lift0 Blue. . .shape :: Behavior Shape -> Behavior Regionshape = lift1 Shapeell, rec :: Behavior Float -> Behavior Float -> Behavior Regionell x y = shape (lift2 Ellipse x y) rec x y = shape (lift2 Rectangle x y)

See text for more liftings.

Events and Reactivity

Abstractly, we can think of events as:type Event a = Behavior (Maybe a)

But for type safety, this is better:newtype Event a =

Event ( ([Maybe UserAction], [Time]) -> [Maybe a] ) Core of FAL’s reactivity:

untilB :: Behavior a -> Event (Behavior a) -> Behavior a

switch :: Behavior a -> Event (Behavior a) -> Behavior a

(->>) :: Event a -> b -> Event b(=>>) :: Event a -> (a->b) -> Event b

plus primitive events such as:lbp :: Event ( )

Primitive Events

“lbp” must look for a “left button press” in the stream of UserActions:

lbp :: Event ( )lbp = Event (\(uas,_) -> map getlbp uas) where getlbp (Just (Button _ True True)) = Just ( )

getlbp _ = Nothing

Similarly for “key”:key :: Event Charkey = Event (\(uas,_) -> map getkey uas) where getkey (Just (Key ch True)) = Just ch

getkey _ = Nothing

Implementing UntilB

untilB switches into a new behavior carried by the event.

untilB :: Behavior a -> Event (Behavior a) -> Behavior aBehavior fb `untilB` Event fe =

memoB $ Behavior (\uts@(us,ts) -> loop us ts (fe uts) (fb uts))where loop (_:us) (_:ts) ~(e:es) (b:bs) =

b : case e ofNothing -> loop us ts es bsJust (Behavior fb') -> fb' (us,ts)

memoB :: Behavior a -> Behavior amemoB (Behavior fb) = Behavior (memo1 fb)

Stare at this code until you understand it completely!The definition of “switch” is very similar (see text).

Event Map

Recall: color1 :: Behavior Colorcolor1 = red `untilB` (lbp ->> blue)

What does “->>” do? Consider types:

red, blue :: Behavior ColoruntilB :: Behavior Color -> Event (Behavior

Color) -> Behavior Color

lbp :: Event ( )(->>) :: Event ( ) -> Behavior Color

-> Event (Behavior Color) So (->>) somehow “tags” an event with a

Behavior. Polymorphically speaking:(->>) :: Event a -> b -> Event b

It is actually a special case of the more general:(=>>) :: Event a -> (a->b) -> Event b

Implementing Event Map

(=>>) is defined as:

Event fe =>> f = Event (\uts -> map aux (fe uts))where aux (Just a) = Just (f a)

aux Nothing = Nothing

Which can be defined more succinctly using fmap from the Functor class (discussed in Chapter 18!):

Event fe =>> f = Event (map (fmap f) . fe)

(->>) is then defined in terms of (=>>):e ->> v = e =>> \_ -> v

ImplementingPredicate Events

“while” is defined as:

while :: Behavior Bool -> Event ()while (Behavior fb) =

Event (\uts -> map aux (fb uts))where aux True = Just ()

aux False = Nothing

“when” is defined similarly (see text).

Implementing Integration

“integral” is defined by:integral :: Behavior Float -> Behavior Floatintegral (Behavior fb) =

Behavior (\uts@(us,t:ts) -> 0 : loop t 0 ts (fb uts))where loop t0 acc (t1:ts) (a:as) =

let acc' = acc + (t1-t0)*ain acc' : loop t1 acc' ts as

This corresponds to the standard definition of integration as a limit in calculus (see text).

“Steppers”

“Steppers” are convenient variations of switch:step :: a -> Event a -> Behavior aa `step` e = constB a `switch` e =>> constB

stepAccum :: a -> Event (a->a) -> Behavior aa `stepAccum` e = b where b = a `step` (e `snapshot` b =>> uncurry ($))

For example, a counter:

counter = 0 `stepAccum` lbp ->> (+1)

an example involving `step` is on the next slide.

Mouse Movement

It’s convenient to treat mouse position as a pair of Behaviors:

mouse :: (Behavior Float, Behavior Float)mouse = (fstB m, sndB m)

where m = (0,0) `step` mm

where “mm” is defined as:mm :: Event Coordinatemm = Event (\(uas,_) -> map getmm uas)

where getmm (Just (MouseMove pt)) =Just (gPtToPt pt)

getmm _ = Nothing

Final Example: Paddleball!

A paddleball game consists of three parts:paddleball vel = walls `over` paddle `over` pball vel

Where ”walls” and ”paddle” are defined by:walls = let upper = paint blue

(translate ( 0,1.7) (rec 4.4 0.05)) left = paint blue

(translate (-2.2,0) (rec 0.05 3.4)) right = paint blue

(translate ( 2.2,0) (rec 0.05 3.4)) in upper `over` left `over` right

paddle = paint red (translate (fst mouse, -1.7) (rec 0.5 0.05))

The core of the game is in “pball”.

Putting it All Together

pball vel =let xvel = vel `stepAccum` xbounce ->> negate

xpos = integral xvelxbounce = when (xpos >* 2 ||* xpos <* -2)yvel = vel `stepAccum` ybounce ->> negateypos = integral yvelybounce = when (ypos >* 1.5

||* ypos `between` (-2.0,-1.5) &&* fst mouse `between` (xpos-

0.25,xpos+0.25))in paint yellow (translate (xpos, ypos) (ell 0.2 0.2))

x `between` (a,b) = x >* a &&* x <* b


Recommended