Time - Yale University

Download Report

Transcript Time - Yale University

Little Languages
for Big Applications
Paul Hudak
Department of Computer Science
Yale University
Indiana University
March 30, 2001
Copyright
©
2001, Paul Hudak, All rights reserved.
Acknowledgements
• At Yale:
John Peterson, Walid Taha, Henrik
Nilsson, Antony Courtney, Zhanyong Wan
• Conal Elliott, Micro$oft Research
• Greg Hager, Johns Hopkins University
• Alastair Reid, University of Utah
Is “Higher Level” Better?
• A programming language can be viewed as
an interface to an abstract machine.
• When is one general-purpose language
higher-level than another?
• Assembly language is just the right
abstraction for a CPU.
• 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:
–
–
–
–
specifications (starting point!)
optimizations and transformations
software tools
type systems, aspects, constraints, etc.
Advantages of 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:
– can often be written by non-programmers
Helps bridge gap between
developer and user
Total SW Cost
The Bottom Line
Conventional
Methodology
C2
Start-up
Costs
C1
DSL-based
Methodolog
y
Software Life-Cycle
DSL’s Allow Faster Prototyping
Using the “Spiral Model” of Software Development
design
build
specify
test
Without DSL
specify
design
build
test
With DSL
Why Study DSL’s?
• Ok, so perhaps DSL’s are useful.
• But why should programming language
researchers be interested in DSL’s?
– To have an impact on the real world.
– The chances of a general purpose language
succeeding are slim, no matter how good it is.
– DSL design and implementation is a source of new
and interesting problems.
– It is also fun!
• In the remainder of the talk I will
concentrate on the latter two points.
A Case Study: FRP
•
•
•
•
Fran is a DSL for graphics and animation.
Frob is a DSL for robotics.
FranTk is a DSL for graphical user interfaces.
FRP (functional reactive programming) is the
essence of Fran, Frob, and FranTk:
– Fran = FRP + graphics engine + library
– Frob = FRP + robot controller + library
– FranTk = FRP + Tk substrate + library
• FRP has two key abstractions:
– Continuous time-varying behaviors.
– Discrete streams of events.
Domain-Specific Languages
FVision
FranTk
Frob
Fran
Graphics, Robotics, GUIs, Vision
FRP
Functional Programming
Applications
Specialized languages
Continuous behaviors
and discrete reactivity
Functions, types, etc.
(Haskell)
FRP by example
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 = moveXY x 0 becky
where
x = -1 + integral 1
Integrate Twice: Acceleration
accelBecky = moveXY x 0 becky
where
x = -1 + integral v
v = 0 + integral 1
Mouse Position is a Behavior
beckyChaseMouse = move offset becky
where offset = integral vel
vel
= mousePosition - offset
Events
• Discrete event streams include user input as
well as domain-specific sensors,
asynchronous messages, interrupts, etc.
• They also include tests for dynamic
conditions (“predicate events”) on behaviors
(temperature too high, level too low, etc.)
• Operations on event streams include:
– Mapping, filtering, reduction, etc.
– Reactive behavior modification (next slide).
Reactivity
“Where the Continuous Meets the Discrete”
• FRP’s key reactive form:
x `until` e ==> y
can be read:
“Behave as x until event e, then behave as y.”
• Declarative semantics.
• Rich event algebra.
• Examples...
Reactive Control of Discrete Values
tricycle =
withColor (cycle3 green yellow red)
(stretch (wiggleRange 0.5 1) circle)
where
cycle3 c1 c2 c3 =
c1 `untilB` lbp ==> cycle3 c2 c3 c1
Reactive Control of Continuous Values
growFlower = stretch size flower
where size = 1 + integral bSign
bSign =
0 `until`
(lbp ==> -1 `until` lbr ==> bSign) .|.
(rbp ==> 1 `until` rbr ==> bSign)
Fran Also Supports 3D
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 Haskell
(or other language)
• Haskell features that facilitate task:
–
–
–
–
type classes
higher-order functions
lazy evaluation
syntactic extensions
• Goal: Embed semantics in functions rather
than interpret as a data structure.
DSL’s Embedded in Haskell
At Yale:
• Graphics/Animation (Fran, w/Microsoft)
• Robotics (Frob)
• Computer Vision (Fvision)
• Computer Music (Haskore)
• Sound Synthesis (Hsound)
• Dance/choreography (Haskanotation)
Elsewhere:
• HaskellScript for the WWW (Utrecht)
• Scripting COM objects (Utrecht, Microsoft)
• Hardware Description (OGI, Chalmers)
• Parsing/pretty printing (Utrecht, Chalmers)
• GUI’s (FranTK, etc.)
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 behaviors and events?
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 central to our stream-based
implementation, thus emulating “demand-driven”
computation.
The Semantics of Fran
• Denotational semantics [Elliott,Hudak,ICFP98]
– at [[b]] t : instantaneous value of behavior b at time t.
– occ [[e]] t : presence of event e at time t.
– Domain (cpo) of time T, with partial elements >t that
denote “a time that is at least t”.
• Stream-based operational semantics [Hudak2000 and
Wan,Hudak,PLDI2000]
– Streams represent behaviors and events.
– Compositional semantics via stream transformers.
– Leads naturally to concrete implementation.
Theorem:
In the limit, as sample time goes to zero,
the stream-based semantics is faithful to
the denotational semantics [PLDI2000].
From Semantics to Implementation
ICFP semantics:
User semantics:
at :: Beh a -> Time -> a
occ :: Event a -> ((Time,a), Event a)
at :: Beh a -> (User, Time) -> a
occ :: (User, Event a)->((Time,a),User)
time :: Beh Time
time `at` t = t
time :: Beh Time
time `at` (u,t) = t
switch :: Beh b -> Event (Beh b) -> Beh b
(b `switch` e) `at` t =
let ((t0,b0),e0) = occ e
in if t<=t0 then b `at` t
else (b0 `switch` e0) `at` t
switch :: Beh b -> Event(Beh b) ->Beh b
(b `switch` e) `at` (u,t) =
let ((t0,b0),u0) = occ (u,e)
in if t<=t0 then b `at` (u,t)
else (b0 `switch` e) `at` (u0,t)
which suggests the implementation:
which suggests the implementation:
type Beh a = Time -> a
type Event a = [(Time, a)]
type Beh a = (User, Time) -> a
type Event a = User -> ((Time,a), User)
type User
= [(Time, UA)]
b `at` t = b t
occ e = (head e, tail e)
b `at` (u,t) = b (u,t)
occ (u,e) = e u
Time-Ordered Search
• Motivation by analogy:
Consider ordered list L :: [T] and function:
inList :: [T] -> T -> Bool
• Now suppose we want to find many elements in L:
manyInList :: [T] -> [T] -> [Bool]
manyInList xs ys = map (inList xs) ys
This is quadratic: O(|xs|*|ys|)
• Better to order ys first, then do the search:
manyInList xs (y:ys) =
let (b,xs’) = inListRem xs y
in b : manyInList xs’ ys
This is linear: O(|xs|)
Type-Directed Derivation
Behaviors:
Events:
specification:
Beh a = (User, Time) -> a
uncurry:
Beh a = User -> Time -> a
time-ordered search:
Beh a = User -> [Time] -> [a]
unfold User:
Beh a = [(UA,Time)] -> [Time] -> [a]
unzip User and uncurry:
Beh a = [UA] -> [Time] -> [Time]->[a]
synchronize:
Beh a = [UA] -> [Time] -> [a]
specification:
Ev a = User -> ((Time,a), User)
encode non-occurences:
Ev a = User -> (Maybe (Time,a), User)
decouple aging:
Ev a = User -> Maybe (Time,a)
time-ordered search:
Ev a = User -> [Maybe (Time,a)]
unfold User:
Ev a = [(UA,Time)] -> [Maybe (Time,a)]
unzip User and uncurry:
Ev a = [UA] -> [Time] -> [Maybe (Time,a)]
synchronize:
Ev a = [UA] -> [Time] -> [Maybe a]
Note now: Ev a = Beh (Maybe a)
Advantages of Stream Design
• “User” implicitly “aged;” no User argument
to event generators.
• No dynamic adjustments in time;
everything is fully synchronized.
• Behaviors can be memoized using a
singleton cache.
• Potential for heavy optimization.
• Event a = Behavior (Maybe a)
One disadvantage: cannot easily time-transform User.
Faithful Implementations
• The stream implementation of FRP is an
approximation to continuous behaviors.
• But the denotational semantics is exact.
• So in what sense is the implementation
faithful to the formal semantics?
• Is there any hope for semantics-directed
compilation or transformation/optimization?
Egregious Behaviors
• Consider this behavior:
> zeno :: Event ()
> zeno = when (lift1 f time) where
>
f t = if t>2 || t<1 then t<0.5
>
else f (2*t-2)
• This captures Zeno’s Paradox:
on or off??
light on
light off
1
2
time
and is a natural expression of non-determinism!
More Egregious Behavior
• Consider this simple behavior:
> sharp :: Event ()
> sharp = when (time ==* 1)
• This seems innocent enough, but the predicate is
true only instantaneously at time = 1. However, a
stream-based implementation may miss this event.
• In fact we can show that:
A stream-based implementation may miss this
event even at the limit of event sampling.
“Good” Behaviors
• Zeno’s paradox represents a problem with the
semantics, and instantaneous events represent a
problem with a stream-based implementation.
• Solution: define good behaviors as those that
converge to a stable value as the sampling rate
increases. Similarly, good events are those whose
frequency within a finite period becomes stable as
the sampling rate increases.
• Key result: we can show that, with suitable
constraints, in the limit, as the sample time
decreases to zero, a steam-based implementation is
faithful to the denotational semantics.
l
ll
Lambda in Motion:
Controlling Robots with Haskell
Robots with Vision
Motivation
• Mobile robot control is hard!
• Prototyping is essential: repeated experimentation
required.
• Must deal with uncertainty: imprecise sensors, unknown
environment, moving obstacles, mechanical problems.
• Need to compose solved sub-problems.
• Reliability needed – programs must recover from errors
and deploy 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.
Autonomous Coordinated Motion
• Natural behavior amongst living animals:
– flocking, herding, schooling, swarming
• Specific tasks of interest to us:
– congregation, navigation, “escortation”,
formation motion, obstacle avoidance,
dispersion, etc.
• Key technologies of interest:
– computational vision and control
– FRP
Example of Coordinated Motion
• Problem:
– Specify local control strategy for two differential-drive
robots in interleaving trajectories, where each robot only
knows the relative position of the other.
• Can be achieved by two-step simplification:
– Non-holonomic constraint on differential-drive robot is
eliminated by considering a moving frame of reference.
– Relative to that frame, each robot exhibits identical
behavior: simply circle the other robot.
• Frob permits abstract formulation of solution.
– Two independent critically-damped PI controllers.
– Local motion assumes holonomic vehicle; i.e. differential
drive robot can be treated as omni-directional robot.
Local Behavior
vFrame
desired rotation
vLat
vRot
moving
frame of
reference
Code Snippet
interleaveC dist omega0 vFrame =
let …
distError = distOther - dist
vLat = vector2Polar
(kpDist * distError +
kiDist * integralB distError)
angOther
vRot = vector2Polar
(omega0*distOther/2)
(angOther - pi/2)
in velocityV (vFrame + vLat + vRot)
Our old 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
Real-Time FRP (RT-FRP)
• Abstract, restricted subset of FRP.
• Behaviors and events captured uniformly as signals:
s ::= input | time | ext e | delay v s
| let signal x = s1 in s2
| s1 switch on x = ev in s2
• Expressive enough to encode most of FRP. For
example, integration by the forward Euler method:
integral s =
let signal t = time
in let signal v = s
in let signal st = delay (0,(0,0)) (ext (i,(v,t))
where (i0,(v0,t0)) = st
i = i0 + v0(t - t0))
in ext (fst st)
Operational Semantics of RT-FRP
• Two judgements:
Γ, Δ |– s : t
E,K |– s i,t s’, v
• Key: constrain higher-order behaviors and recursion.
– well-formed and tail-recursive
• Results:
– Type safety / preservation.
– Each step takes constant time (thus no time leaks).
– Term size cannot grow (thus no space leaks).
• So far only theoretical result. We need to:
– Compile FRP (when possible) into RT-FRP core.
– Compile RT-FRP into lower-level code (C, etc).
– Consider application to embedded systems.
Ongoing Work
• Vision-based Control (FVision).
• Language enhancements (“running” behaviors, time
transformations, parallel tasks, etc).
• Multiple robots and RoboCup soccer.
• Teaching robotics using Frob.
• Better implementation / optimization.
• Better tools (debugging, profiling, etc).
• “Visual FRP”.
• Graphical user interfaces.
• Formal semantics / verification.
• Real-time control and embedded systems.
For Further Reading...
• The Haskell School of Expression --
Learning Functional Programming
through Multimedia
• Cambridge University Press
• Teaches functional programming using Haskell,
including three DSL’s: a Fran-like language (FAL), a
Haskore-like language (MDL), and an imperative
robot language (IRL).
• Available now from your favorite bookstore…
Glove
by Tom Makucevich
with help from Paul Hudak
Composed using Haskore, a Haskell DSL,
and rendered using csound.
How to Hide a Flock of Turkeys
Conclusions
There are two ways of constructing a software design. One way is to
make it so simple that there are obviously no deficiencies. And the other
way is to make it so complicated that there are no obvious deficiencies.
---C.A.R. Hoare
• Domain Specific Languages are a Good Thing.
• Embedded DSL’s (ala Haskell) can be used to implement
highly effective programming environments.
• “Functional Reactive Programming” is a good abstraction
for many real-time reactive domains.
• The programming languages community has some
good ideas; let’s start using them!
• DSL technology is fertile ground for programming
language research.
A Formal Semantics for FRP
• What should an operational or denotational
semantics for FRP look like?
• How is Time represented?
• Are all continuous behaviors well-behaved?
• In what sense is an implementation (which
must approximate continuous behaviors)
faithful to a formal semantics?
Some Key Design Issues
• Recursion vs. combinators
until, switch :: Beh a -> Event (Beh a) -> Beh a
b `switch` e = b `until` e ==> \b1 -> b1 `switch` e
• A rich algebra of events
lbp
:: Event ( );
key :: Event Char
(==>)
:: Event a -> (a->b) -> Event b
accum
:: a -> Event (a -> a) -> Event a
snapshot :: Event a -> Behavior b -> Event (a,b)
when
:: Behavior Bool -> Event ( )
(.|.)
:: Event a -> Event a -> Event a
• “Aging” the “user”
let getString = constB "Init" `switch`
accum "" (key ==> \ch -> (++ [ch])) ==> constB
in constB "Start" `switch` lbp -=> getString
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
Domain Specific Transformations
• Many domains exhibit nice algebraic properties,
with which one can reason about, transform, and
optimize programs.
• Query optimization in databases is the
prototypical example.
• An implementation can often be proven correct
with respect to these properties.
• But we cannot expect a general purpose compiler
to perform these optimizations for us.
• We need source level meta-programming tools.
Example: Simple Graphics
-- Atomic objects:
circle
square
importGIF "p.gif"
-- Composite objects:
scale
v p
color
c p
trans
v p
p1 `over` p2
p1 `above` p2
p1 `beside` p2
-- a unit circle
-- a unit square
-- an imported bit-map
-------
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.
Visual Languages
• In some domains, the most common
notation is pictorial.
• For example: signal processing, digital
hardware design, control systems, and
sound synthesis.
• Should Fran / FRP be a visual programming
language, and if so, what should it look like?
• We need tools to provide both views of a
program.
Visual FRP