Time -> a - Computer Science

Download Report

Transcript Time -> a - Computer Science

Functional Reactive
Programming
-- or -“How to Have Fun With Functions”
(mostly by example)
Paul Hudak
Dept. of Computer Science
Yale University
Copyright 1999, Paul Hudak
All rights reserved.
The Importance of Language
• A (general-purpose) programming
language is a (formal) interface to an
(abstract) machine. E.g.:
–
–
–
–
–
assembly language for a CPU
Java for the JVM
Haskell for the STG (graph reducer)
Prolog for the WAM
C for a yet-to-be-specified CVM
Is “Higher” Abstraction Good?
• Assembly language is just the right
abstraction for a CPU.
• When is one general-purpose language
“higher-level” than another?
• Why do some languages better match
some applications than others?
We Need Domain Specificity
• A domain-specific language (or DSL) is a
language that precisely captures a domain
semantics; no more, and no less.
• We also need domain specific:
–
–
–
–
formalizations (starting point!)
optimizations and transformations
software tools
aspects and constraints
Advantages of the DSL Approach
• Programs in the target domain are:
– more concise
– quicker to write
Contribute to higher
programmer productivity
– easier to maintain
Dominant cost in
large SW systems
– easier to reason about
Verification, transformation, optimization
These are the same arguments in favor of any highlevel language! But in addition, I should add:
– can be written by non-programmers
Helps bridge gap between
developer and user
The Bottom Line
FRP = Functional Reactive Programming
• Fran is a DSL for functional reactive animation.
• Frob is a DSL for functional robotics.
• FRP is the essence of Fran and Frob:
– Fran = FRP + graphics engine + library
– Frob = FRP + robot controller + library
• FRP has two key abstractions:
– Continuous, time-varying behaviors.
– Discrete, reactive events.
by example
(aka “Functional Reactive Animation”)
A First Example
leftRightCharlotte =
moveXY wiggle 0 charlotte
wiggle
= sin (pi * time)
charlotte = importBitmap
"../Media/charlotte.bmp"
Wiggle vs. Waggle
upDownPat = moveXY 0 waggle pat
waggle = cos (pi * time)
pat = importBitmap "../Media/pat.bmp"
The Power of Composition
charlottePatDoubleDance =
hvDance aSmall aSmall
where aSmall =
stretch 0.5 charlottePatDance
charlottePatDance = hvDance charlotte pat
hvDance im1 im2 =moveXY wiggle 0 im1 `over`
moveXY 0 waggle im2
Stretching with a Wiggle
(and a waggle)
dance2 = hvDance (stretch wiggle charlotte)
(stretch waggle pat)
Integration Over Time
velBecky u = moveXY x 0 becky
where
x = -1 + atRate 1 u
Integrating Twice Yields
Acceleration
accelBecky u = moveXY x 0 becky
where
x = -1 + atRate v u
v = 0 + atRate 1 u
The Mouse Position is a
Behavior Too
beckyChaseMouse u = move offset becky
where offset = atRate vel u
vel
= mouseMotion u - offset
Composition in Time
orbitAndLater = orbit `over` later 1 orbit
where
orbit = moveXY wiggle waggle jake
Time is Orthogonal to Space
followMouseAndDelay u =
follow `over` later 1 follow
where
follow = move (mouseMotion u) jake
Reactivity
tricycle u = buttonMonitor u `over`
withColor (cycle3 green yellow red u)
(stretch (wiggleRange 0.5 1) circle)
where
cycle3 c1 c2 c3 u =
c1 `untilB` lbp u ==> cycle3 c2 c3 c1
Reactivity is Orthogonal
growFlower u = buttonMonitor u `over`
stretch size flower
where size = 1 + atRate (bSign u)
Fran Also Supports 3D
redSpinningPot =
turn3 zVector3 time
(withColorG red teapot)
teapot =
stretch3 2 (importX "../Media/tpot2.x")
3D Light Sources
sphereLowRes = importX "../Media/sphere0.x"
movingLight =
move3 motion
(stretch3 0.1
(withColorG white
(sphereLowRes `unionG` pointLightG)))
where
motion = vector3Spherical 1.5 (pi*time)
(2*pi*time)
potAndLight =
withColorG green teapot `unionG` movingLight
A Final Example
spiralTurn = turn3 zVector3 (pi*time)
(unionGs (map ball [1 .. n]))
where
n = 40
ball i = withColorG color
(move3 motion
(stretch3 0.1 sphereLowRes ))
where
motion = vector3Spherical 1.5 (10*phi) phi
phi
= pi * fromInt i / fromInt n
color = colorHSL (2*phi) 0.5 0.5
Implementing DSL’s
•
•
•
•
Language design is difficult!
Idea: Embed DSL in existing language.
Our choice: Haskell (purely functional language)
Haskell features greatly facilitate task:
–
–
–
–
type classes
higher-order functions
lazy evaluation
syntactic extensions
• Like building an interpreter for an algebraic
data type.
A Typical Fran Expression
1
`until`
Behavior
Infix operator
time>2
Predicate event
-=>
time+1
Behavior
Infix operator
This is equivalent to:
until 1 ((-=>)((>) time 2)((+) time 1))
But, what are events and behaviors?
Fran’s Behaviors
Haskell’s type classes conveniently describe behaviors:
newtype Behavior a = Beh (Time -> a)
instance Num (Behavior a) where
Beh f + Beh g = Beh (\t -> f t + g t)
fromInteger x = Beh (\t -> x)
Also define:
time = Beh (\t->t)
And thus:
1
time+1




Beh (\t->1)
Beh (\t->t) + Beh (\t->1)
Beh (\t-> (\t->t)t + (\t->1)t)
Beh (\t-> t+1)
Lazy Evaluation
Essential for things like:
color = red `until` lbp ==> blue `until` lbp ==> color
which would not terminate under a call-by-value
interpretation.
Lazy evaluation is also used to implement various
stream-like objects that represent “demand-driven”
computation.
l
ll
Lambda in Motion:
Controlling Robots with Haskell
The Domain: Robots with Vision
Motivation
• Mobile robot control is hard!
• Prototyping is essential: repeated experimentation
required.
• Deal with unpredictability: imprecise sensors, uncertain
environment, mechanical problems.
• Need to combine solved sub-problems.
• Reliability needed - programs must recover from
errors; explore alternative strategies to meet goals.
Our Solution: Frob
• Recall that:
Frob = FRP + robot controller + robot/vision library
• Programming robots is a lot like programming an
animation!
• … except that:
–
–
–
–
The robot doesn’t always do what you want it to do
Error / anomalous conditions are more common
Real-time issues are more dominant
Robots are a lot slower than graphics hardware
Our Robots:
Nomadic Technologies SuperScout
Vision
16 Sonars
Bumpers
Wheel
Controls
Computing:
PC running Linux
Hugs
Radio Modem
A Control System for Wall Following
Time is Implicit!
Notation is nearly identical.
Details of clocking are hidden.
Side Sonar
s
Objectives:
Maintain a specified
distance
wall
follow f sfrom
d = (v,w)
w
where
v = turn
limit too
vmaxmuch
(f-d)
Don’t
w = limit
toward
wall(vcurr * sin amax)
(s-d)
- derivative s
Stop (slowly) when approaching
an obstacle ahead.
n
Front Sonar
f
n = limit(nmax, f - d)
w = limit(sin qmax * ncurr, s - d) - ds/dt
limit(mx,v) = max(-mx,min(v,mx))
Adding Reactivity
Wall follower terminates two ways:
-- Blocked in front
-- No wall on side
Data WallEnd =
Blocked | NoWall
type Wheels = (SpeedB, AngleB)
wfollow :: SonarB -> SonarB -> FloatB ->
(WallEnd -> Wheels) -> Wheels
wfollow f s d c =
follower f s d `untilB`
(
predicate (f <= d) -=> Blocked
.|. predicate (s >= 2*d) -=> NoWall) ==> c
Capture
this pattern in a Monad!
The
behavior
The
Theterminating
continuationevent
of the overall behavior
A Task Monad
A task couples a behavior with a termination event.
In it’s simplest form, we combine a behavior and an event into a task:
mkTask :: (Behavior a, Event b) -> Task a b
Continuous value defined by task
Value returned at end of task
(b1,e1) >> (b2,e2) =
(b1 `untilB` e1 -=> b2, e2)
Hide reactivity inside monadic sequencing
Using Tasks
Blocked
Wall
Follow
Left
Turn
Right
Free
Wall
left
No
Wall
Turn
Left
wallTask f s d = mkTask
(wallFollow f s d,
predicate (f <= d) -=> Blocked
.|. predicate (s >= 2*d) -=> NoWall)
roomFollow f s d =
do status <- wallTask f s d
case status of
NoWall -> turnLeft
Blocked -> turnRight
roomFollow f s d
What’s under the hood?
Event based interface to the outside world
Smoothing / sampling to allow continuous representations
Clocking controls for smoothing / sampling.
Dispatch output
events
Accept input
events
FRP Gateway
Sampling
and
Smoothing
Clocking Policy
User Program
“Mostly” continuous
world
Ongoing Work
• Vision-based Control (via FVision, another
Haskell DSL)
• Planning / Scheduling / Multiple robots
• Teach Haskell & robotics to students
• Denotational and operational semantics
• Better tools (debugging, profiling, etc.)
• Computer Music (Haskore)
• Dance (Labanotation)
• Hybrid / control systems
Glove
by Tom Makucevich
with Technical Assistance from Paul Hudak
Composed using Haskore, a Haskell DSL
rendered using csound.
Haskore
Motivation:
Traditional music notation has many limitations:
• Unable to express a composer’s intentions.
• Biased toward music that is humanly performable.
• Unable to express notions of algorithmic composition.
Haskore (“Haskell” + “Score”) is a library of Haskell
functions and datatypes for composing music.
Basic Haskore Structure
type Pitch = (PitchClass, Octave)
data PitchClass = Cf | C | Cs | Df | D | Ds | Ef | E | Es | Ff | F | Fs
| Gf | G | Gs | Af | A | As | Bf | B | Bs
type Octave = Int
data Music =
Note Pitch Dur
| Rest Dur
| Music :+: Music
| Music :=: Music
| Tempo Int Int Music
| Trans Int Music
| Instr IName Music
type Dur
= Float
type IName = String
type PName = String
-- a note \ atomic
-- a rest /
objects
-- sequential composition
-- parallel composition
-- scale the tempo
-- transposition
-- instrument label
-- in whole notes
Some Haskore Examples
t1 = test (Instr "piano"
(Phrase [Art (Staccato 0.1)] cms :+:
cms
Phrase [Art (Legato 1.1)] cms
))
:+:
t2 = test (Instr "vibes"
(Phrase [Dyn (Diminuendo 0.75)] cms :+:
Phrase [Dyn (Crescendo 4.0), Dyn (Loudness 25)] cms))
t3 = test (Instr "flute"
(Phrase [Dyn (Accelerando 0.3)] cms :+:
Phrase [Dyn (Ritardando 0.6)] cms
))
cms = <C major scale >
More Examples
A function to recursively apply transformations f (to elements in a
sequence) and g (to accumulated phrases):
rep :: (Music -> Music) -> (Music -> Music) -> Int -> Music -> Music
rep f g 0 m = Rest 0
rep f g n m = m :=: g (rep f g (n-1) (f m))
An example using "rep" three times, recursively, to create a "cascade"
of sounds.
run
cascade
= rep (Trans 5) (delay tn) 8 (c 4 tn)
= rep (Trans 4) (delay en) 8 run
cascades = rep id (delay sn) 2 cascade
waterfall
= cascades :+: revM cascades
Self-Similar (Fractal) Music
data Cluster = Cl Note [Cluster] -- a Rose tree
type Note = (AbsPitch,Dur)
sim pat = map mkCluster pat
where mkCluster note =
Cl note (map (mkCluster . addmult notes) pat)
addmult pds iss = zipWith addmult' pds iss
where addmult' (p,d) (i,s) = (p+i,d*s)
simFringe n pat = fringe n (Cl [(0,0)] (sim pat))
fringe 0 (Cl note cls) = [note]
fringe n (Cl note cls) = concat (map (fringe (n-1)) cls)
Self-Similar, Cont’d
result = rep (delay (dur s)) (Trans 4) 2 s
s = sims 3
sims n = let s = sim n
m1 = Instr "flute" s
m2 = Instr "bass" (Trans (-36) (revM s))
in m1 :=: m2
sim n = (Trans 60
(Tempo 2 1 (simToHask (simFringe n pat))))
pat = [ [(3,0.5)], [(4,0.25)], [(0,0.25)], [(6,1.0)] ]
Performance & Interpretation
A performance is a temporal sequence of musical events.
type Performance = [Event]
data Event = Event Time IName AbsPitch DurT Volume
type Time
type DurT
type Volume
= Float
= Float
= Float
Now we need a way to perform (I.e. interpret) music.
perform :: Context -> Music -> Performance
type Context = (Time,IName,DurT,Key,Volume)
time instrument tempo key volume
Music
perform
Performance
Literal Interpretation
A literal interpretation is the most straightforward.
perform c@(t,pl,i,dt,k,v) m =
case m of
Note p d
-> playNote pl c p d
Rest d
-> []
m1 :+: m2
-> perform c m1 ++
perform (setTime c (t+(dur m1)*dt)) m2
m1 :=: m2
-> merge (perform c m1) (perform c m2)
Tempo a b m -> perform (setTempo c (dt * float b / float a)) m
Trans p m -> perform (setTrans c (k+p)) m
Instr nm m -> perform (setInstr
c nm ) m
Player nm m -> perform (setPlayer c (pmap nm)) m
Phrase pas m -> interpPhrase pl c pas m
Equivalence of Musical Objects
Two musical objects are (observationally) equivalent if they
result in the same literal performance under all contexts.
Definition:
m1 = m2 iff for all contexts con,
perform con m1 = perform con m2
An Algebra of Music Emerges
Using simple equational reasoning, many useful axioms
are easily proven:
• Tempo-scaling is multiplicative.
• Transposition is additive.
• Parallel composition is commutative.
• Tempo-scaling and transposition are distributive
over both sequential and parallel composition.
• Sequential and parallel composition are associative.
• Rest 0 is a unit for Tempo and Trans, and a zero for
sequential and parallel composition.
Simple Graphics
-- Atomic objects:
circle
square
importGIF "p.gif"
-- a unit circle
-- a unit square
-- an imported bit-map
-- Composite objects:
scale
v p
-color
c p
-trans
v p
-p1 `over` p2
-p1 `above` p2
-p1 `beside` p2
--
scale picture p by vector v
color picture p with color c
translate picture p by vector v
overlay p1 on p2
place p1 above p2
place p1 beside p2
-- Axioms
over, above, and beside are associative
scale, color, and trans distribute over over, above, & beside
scale is multiplicative, trans is additive
etc.
Thus an algebra of graphics emerges.
Simple Animations
type Behavior a = Time -> a
type Animation = Behavior Picture
Now we “lift” the simple graphics operations to work on
behaviors as well. For example:
(b1 `overB` b2) t = b1 t `over` b2 t
(b1 `aboveB` b2) t = b1 t `above` b2 t
(b1 `besideB` b2) t = b1 t `beside` b2 t
(scaleB v b) t
(colorB c b) t
(transB v b) t
= scale (v t) (b t)
= color (c t) (b t)
= trans (v t) (b t)
And a new function to express the current time:
time t = t
All previous graphics axioms hold for animations.
Conclusions
• Media Specific Languages (MSL’s) are a Good Thing.
• Embedded DSL technology (ala Haskell) can be used
to implement MSL’s.
• Denotational / Algebraic Semantics are useful tools for
designing, reasoning about, and analyzing MSL’s.
• “Functional Reactive Programming” is a good abstraction
for several media applications.
• The Programming Languages community has some
good ideas; let’s start using them!
Dance!
Labanotation is a method
for notating dance (I.e.
choreography).
We are capturing labanotation
as an algebraic datatype, and
then rendering the dance as a
3D animation.
Media Applications
Currently Under
Development
• Graphics, Sound, and Animation
-- with Conal Elliott (Micro$oft Research)
• Computer Music
• Scripting Com Objects
-- Erik Meijer, Daan Leijen, Simon Peyton Jones
• HaskellScript (for embedding in HTML)
-- Erik Meijer
• Robotics
-- with Greg Hager (Yale)
• Dance/choreography
-- Created by Daan Leijen and Erik Meijer, Utrecht University
Scripting
Microsoft
Agents
demo robo dizzy jerry ie
= seqAnim
[ robo introduces,
dizzy helps,
jerry showsUp <|> dizzy isIdle1 <|> robo moves,
(robo teasesPaul <*> jerry teasesPaulToo) <|> dizzy isIdle2,
dizzy isNotPleased,
...
jerry showsCode,
jerry toEndPos,
ioWhen isAtEndPos jerry
(do ie # visible << True
ie # navigate "file:c:/agents/hugs/demo.html"),
robo isLost,
jerry writes `while`
(robo searches `while`
(dizzy goesHome)
),
robo wavesGoodbye,
robo goesSurfing,
robo completes,
dizzy completes,
jerry completes
]
introduces = [moveTo (100,100) 0,
show,
play stopListening,
speak "Excuse me Paul.",
play greet,
speak "It's me, Robbie Haskell!",
play greet,
speak "You look like you need some help."
]
Scripting
Microsoft Agents
helps
= [moveTo (500,100) 0,
show,
play greet,
speak "Hi folks, I am Dizzy, the DSL wizard.",
play think,
speak "I know someone who can help.”
]
showsUp
= [moveTo (300,300) 0,
show,
speak "Greetings! I am Jerry, the Use Nix genie!",
speak "Speak your wish and I will fulfill it.",
play suggest
]
Multimedia Programming is Difficult
For example, animation implementation chores include:
• Stepping forward discretely in time, even though
animation is conceptually continuous.
• Capturing and handling sequences of motion input
“events,” even though such input is conceptually
continuous.
• Time slicing and sequencing each time-varying
animation component, even though these components
exist conceptually in parallel.
Solution: Choose Modeling over Presentation
Why Modeling over Presentation
• Authoring. End users of content creation systems think in
terms of models, and typically have neither the expertise
nor interest in programming presentation details.
• Optimizability. Model-based systems contain a presentation
sub-system able to render any model. Because higher-level
information is available to the presentation sub-system than
with presentation programs, there are many more
opportunities for optimization.
• Regulation. The presentation sub-system can more easily
determine level-of-detail management and sampling rates,
based on scene complexity, machine speed and load, etc.
• Mobility and safety. The platform independence of the
modeling approach can facilitate the construction of mobile
web applications.