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.

Slides:



Advertisements
Similar presentations
Code examples Mechanics: random balls Biology/evolution: flocking Game of tag.
Advertisements

Structured Design The Structured Design Approach (also called Layered Approach) focuses on the conceptual and physical level. As discussed earlier: Conceptual.
Introduction to Programming
Haskell Chapter 7. Topics  Defining data types  Exporting types  Type parameters  Derived instances  Type synonyms  Either  Type classes  Not.
RAPTOR Syntax and Semantics By Lt Col Schorsch
NEW SLIDE PROCEDURE A single combined PowerPoint™ file should be submitted for the entire session. Must be coordinated with your Program Chair Slides should.
Chapter 8 A Module of Regions. The Region Data Type  A region represents an area on the two-dimensional Cartesian plane.  It is represented by a tree-like.
Kathleen Fisher cs242 Reading: “A history of Haskell: Being lazy with class”,A history of Haskell: Being lazy with class Section 6.4 and Section 7 “Monads.
Basics of Inheritance CS 5010 Program Design Paradigms "Bootcamp" Lesson 12.1 © Mitchell Wand, This work is licensed under a Creative Commons.
1 Programming Languages (CS 550) Lecture Summary Functional Programming and Operational Semantics for Scheme Jeremy R. Johnson.
Functional Reactive Programming Lecture 6, Designing and Using Combinators John Hughes.
Chapter 11 Arrays. Introduction Array: An ordered collection of values with two distinguishing characters: – Ordered and fixed length – Homogeneous. Every.
Functional Programming Universitatea Politehnica Bucuresti Adina Magda Florea
Chapter 19 An Imperative Robot Language. Motivation  In the previous chapter, monads were introduced.  In particular, state monads were described as.
© Copyright by Deitel & Associates, Inc. and Pearson Education Inc. All Rights Reserved. 1 Tutorial 21 - “Cat and Mouse” Painter Application.
Cse536 Functional Programming 1 6/10/2015 Lecture #8, Oct. 20, 2004 Todays Topics –Sets and characteristic functions –Regions –Is a point in a Region –Currying.
Chapter 3 Simple Graphics. Side Effects and Haskell  All the programs we have seen so far have no “side-effects.” That is, programs are executed only.
Chapter 17 Rendering Reactive Animations. Motivation  In the previous chapter we learned just enough about advanced IO and concurrency to develop a “renderer”
Comp 205: Comparative Programming Languages User-Defined Types Enumerated types Parameterised types Recursive types Lecture notes, exercises, etc., can.
Advanced Programming Handout 12 Higher-Order Types (SOE Chapter 18)
While there is a generally accepted precise definition for the term "first order differential equation'', this is not the case for the term "Bifurcation''.
Chapter 13 A Module of Simple Animations. Motivation  In the abstract, an animation is a continuous, time-varying image.  But in practice, it is a sequence.
Advanced Programming Handout 10 A Module of Simple Animations (SOE Chapter 13)
Cse536 Functional Programming 1 6/30/2015 Lecture #16, Nov. 29, 2004 Todays Topics – Files, Channels, and Handles –IO exception handling –First Class Channels.
Introduction to LabVIEW Seth Price Department of Chemical Engineering New Mexico Tech Rev. 10/5/14.
Advanced Programming Handout 5 Recursive Data Types (SOE Chapter 7)
Cse536 Functional Programming 1 7/16/2015 Lecture #15, Nov. 15, 2004 Todays Topics – Simple Animations - Review –Reactive animations –Vocabulary – Examples.
MIT AITI 2003 Lecture 7 Class and Object - Part I.
© Maths Support Service 2007 Binary and Hexadecimal Numbers Next Slide AE98FD AE98FD.
1 Relational Algebra and Calculus Chapter 4. 2 Relational Query Languages  Query languages: Allow manipulation and retrieval of data from a database.
Domain-Specific Languages: Challenges and Opportunities Zhanyong Wan Yale University.
Making a Boat Racing Game in Alice By Jenna Hayes Under the direction of Professor Susan Rodger Duke University, July 2010.
Locally Edited Animations We will need 3 files to help get us started at
Programing Concept Ken Youssefi/Ping HsuIntroduction to Engineering – E10 1 ENGR 10 Introduction to Engineering (Part A)
We will be creating a spaceship that simulates real movements in space. The spaceship will fire a laser beam that can destroy targets. The spaceship will.
Operators, Functions and Modules1 Pattern Matching & Recursion.
Haskell. 2 GHC and HUGS Haskell 98 is the current version of Haskell GHC (Glasgow Haskell Compiler, version 7.4.1) is the version of Haskell I am using.
10/5: Primitives, the for loop Primitive data types –why we mention them Return to counter-controlled repetition.
Application of Data Programming Blocks. Objectives  Understand the use of data programming blocks and their applications  Understand the basic logic.
Programming for Artists ART 315 Dr. J. R. Parker Art/Digital Media Lab Lec 10 Fall 2010.
© Copyright by Deitel & Associates, Inc. and Pearson Education Inc. All Rights Reserved. 1 Tutorial 21 - “Cat and Mouse” Painter Application.
CIS 3.5 Lecture 2.2 More programming with "Processing"
CS324e - Elements of Graphics and Visualization Timing Framework.
Com Functional Programming Lazy Evaluation Marian Gheorghe Lecture 13 Module homepage Mole & ©University of Sheffieldcom2010.
COMPSCI 102 Discrete Mathematics for Computer Science.
10/4: the for loop & the switch structure Primitive data types –why we mention them Return to counter-controlled repetition.
1/33 Basic Scheme February 8, 2007 Compound expressions Rules of evaluation Creating procedures by capturing common patterns.
1 FP Foundations, Scheme In Text: Chapter Chapter 14: FP Foundations, Scheme Mathematical Functions Def: A mathematical function is a mapping of.
1 CSC 221: Computer Programming I Fall 2009 Introduction to programming in Scratch  animation sprites  motion, control & sensing  costume changes 
7/19: Primitives, the for loop Primitive data types –why we mention them Return to counter-controlled repetition.
Haskell. GHC and HUGS Haskell 98 is the current version of Haskell GHC (Glasgow Haskell Compiler, version 7.4.1) is the version of Haskell I am using.
GAME:IT Paddle Ball Objectives: Review skills from Introduction Create a background Add simple object control (up and down) Add how to create a simple.
6-Jul-16 Haskell II Functions and patterns. Data Types Int + - * / ^ even odd Float + - * / ^ sin cos pi truncate Char ord chr isSpace isUpper … Bool.
Polymorphic Functions
Haskell Chapter 7.
String is a synonym for the type [Char].
Theory of Computation Lecture 4: Programs and Computable Functions II
Unit 11 – PowerPoint Interaction
PROGRAMMING IN HASKELL
Compiling Real-Time Functional Reactive Programming (RT-FRP)
What Color is it?.
Reactive Animations Todays Topics
Theory of Computation Lecture 4: Programs and Computable Functions II
CSC1401 Manipulating Pictures 2
Simple Animations Today’s Topics Reading Assignment Simple animations
CSC 221: Introduction to Programming Fall 2018
PROGRAMMING IN HASKELL
Presentation 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 Color color1 = red `untilB` (lbp ->> blue) ball1 :: Behavior Picture ball1 = paint color1 circ circ :: Behavior Region circ = translate (cos time, sin time) (ell )  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 Float s = s0 + integral v v = v0 + integral f  Combining with reactivity, a bouncing ball: ball2 = paint red (translate (x,y) (ell )) whereg = -4 x = -3 + integral 0.5 y = integral v v = integral g `switch` (hit `snapshot_` v =>> \v'-> lift0 (-v') + integral g) hit = when (y <* -1.5) Note similarity to mathematical 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 Time time = Behavior (\(_,ts) -> ts)  Constant behaviors are achieved via lifting: constB :: a -> Behavior a constB x = Behavior (\_ -> repeat x)  For example: red, blue :: Behavior Color red = constB Red blue = constB Blue

Curried Liftings  From this “lifted” version of application: ($*) :: Beh (a->b) -> Beh a -> Beh b Beh ff $* Beh fb = Beh (\uts -> zipWith ($) (ff uts) (fb uts))  and the constant lifting operator: lift0 :: a -> Beh a lift0 = 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 a fstB = lift1 fst paint :: Behavior Color -> Behavior Region -> Behavior Picture paint = lift2 Region red, blue, yellow, green, white, black :: Behavior Color red = lift0 Red blue = lift0 Blue... shape :: Behavior Shape -> Behavior Region shape = lift1 Shape ell, rec :: Behavior Float -> Behavior Float -> Behavior Region ell 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 Char key = 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 a Behavior fb `untilB` Event fe = memoB $ Behavior -> loop us ts (fe uts) (fb uts)) where loop (_:us) (_:ts) ~(e:es) (b:bs) = b : case e of Nothing -> loop us ts es bs Just (Behavior fb') -> fb' (us,ts) memoB :: Behavior a -> Behavior a memoB (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 Color color1 = red `untilB` (lbp ->> blue) What does “->>” do?  Consider types: red, blue :: Behavior Color untilB :: 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)) whereaux (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

Implementing Predicate 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 Float integral (Behavior fb) = Behavior -> 0 : loop t 0 ts (fb uts)) where loop t0 acc (t1:ts) (a:as) = let acc' = acc + (t1-t0)*a in 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 a a `step` e = constB a `switch` e =>> constB stepAccum :: a -> Event (a->a) -> Behavior a a `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 Coordinate mm = 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 )) left = paint blue (translate (-2.2,0) (rec )) right = paint blue (translate ( 2.2,0) (rec )) in upper `over` left `over` right paddle = paint red (translate (fst mouse, -1.7) (rec ))  The core of the game is in “pball”.

Putting it All Together pball vel = letxvel = vel `stepAccum` xbounce ->> negate xpos = integral xvel xbounce = when (xpos >* 2 ||* xpos > negate ypos = integral yvel ybounce = 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 )) x `between` (a,b) = x >* a &&* x <* b