June 17, 1998
Fran (Function Reactive Animation) is a collection of data types and functions for composing interactive multimedia animations. It is implemented in Haskell and runs under the Hugs and GHC Haskell systems.
The Fran project has been carried out jointly by Microsoft Research and other Haskell researchers. Currently Fran runs under the Microsoft Windows '95/NT systems. This is research in progress; it is very likely that Fran will continue to change in the near future. We have tested all of the examples distributed with Fran but there are sure to be bugs in the current system. Please report any problems to fran-bugs@haskell.org. This document is associated with version 1.1 of Fran, which is available at the Fran home page: http://conal.net/Fran. Version 1.09 is distributed with January 1998 Hugs 1.4 distribution (http://haskell.systemsz.cs.yale.edu/hugs).
This manual contains a short introduction to Fran and an overview of the pre-defined types and functions available in Fran. A more detailed Fran tutorial is available from the Fran home page.
All of the examples used in this manual are found in the ../demos/UsersMan.hs. If you are unfamiliar with Fran, the best way to use this manual is to open (double click) UsersMan.hs in the ../demos directory. An individual example can be executed using the run function: run n executes the nth example. The animation window may initially be hidden when you run an animation -- just click it on the task bar to make it visible. Terminate the animation by closing the animation window. Exit Hugs using :q when you are done. If you encounter a program error while an animation is running you may need to exit and restart Hugs. Running main displays all of the examples in sequence. Use the arrow keys to step through the examples.
Fran is based on two concepts: behaviors and events. A behavior is a value that varies over time; an event is a sequence of occurrences, each of which has a specific time and value. The interplay between behaviors and events is the essence of Fran. While this manual mainly discusses animations, the same model serves for other reactive systems. Indeed, this implementation cleanly separates the core behavior -- event interaction and the graphics library layered on top of it.
In Fran, a value of type Behavior T is a time-varying value of type T. Behaviors are similar to functions over time: operationally, the type Behavior T is the same as Time -> T in that it maps time values onto values of type T. For example, this behavior oscillates between -1 and 1:
wiggle :: Behavior Double wiggle = sin (pi * time)
This definition of wiggle uses a pre-defined behavior: time. The type of time is Behavior Double (or TimeB, as defined by a synonym) and its value is the current time in seconds. Thus the wiggle behavior cycles from -1 to 1 with a period of 2 seconds. Here the sin and (*) functions are applied to behaviors instead of ordinary numeric values. This is possible since Fran defines an instance of the Behavior type for many built-in classes; in this case the Num and Floating classes are overloaded in the type Behavior. Much more will be said of this later.
Since behaviors exist over time, a behavior is observed by playing it in some manner. That is, the user watches and listens to an object as it changes and reacts to input. Fran includes functions for constructing animations that are played in a graphics window. Full details of this library are presented later; here we will introduce just enough of it so that we can explore events and behaviors. Here is a small subset of the graphics library:
-- Basic data types data Color -- data type of colors type RealVal = Double type Time = Double data Point2 = -- a 2D point data Vector2 = -- a 2D vector data ImageB -- Reactive images -- synonyms that abbreviate common behavioral types type RealB = Behavior RealVal type ColorB = Behavior Color type Point2B = Behavior Point2 type Vector2B = Behavior Point2 type TimeB = Behavior Time -- Graphics operations -- A behavioral point constructor point2XY :: RealB -> RealB -> Point2B -- Construct a 2D point vector2XY :: RealB -> RealB -> Vector2B -- Construct a 2D vector origin2 :: RealB -- The origin (maps to window center) circle :: ImageB -- A circle at (0,0) with unit radius withColor :: ColorB -> ImageB -> ImageB -- Paint with a solid color move :: Vector2B -> ImageB -> ImageB -- Move an image red, blue,green :: ColorB -- Some built-in colors over :: ImageB -> ImageB -> ImageB -- Place one image over another stretch :: RealB -> ImageB -> ImageB -- Enlarge (or reduce) the -- size of an image -- Display routine. Initial screen scaled to (-1,-1) , (1,1) displayU :: (User -> ImageB) -> IO () -- display a user-dependent animation
To avoid clutter in type signatures involving Behavior many types have pre-defined synonyms for their behavioral counterparts. The type declarations above show some of these synonyms. Some behavioral types, such as ImageB, are implemented directly instead of using the Behavior type constructor.
The disp function takes a reactive animation and plays it in a graphics window. Fran uses the type User to represent external events generated by the user. Images which don't react user input can usually ignore the User value that disp passes to the animation.
Here are a few of the built-in behaviors in Fran:
time :: TimeB constantB :: a -> Behavior a -- create a constant behavior mouseMotion :: User -> Vector2B -- tracks the position of the mouse
Here is a very simple program to display a pulsing circle:
module Examples where import Fran -- Basic Fran functionality circ :: ImageB circ = stretch wiggle (withColor red circle) example1 u = circ
Execute this example using either disp example1 or run 1, for short.
Here is a slightly more complex behavior:
ball1, ball2, movingBall1, movingBall2 :: User -> ImageB ball1 u = stretch 0.3 (withColor red circle) ball2 u = stretch 0.4 (withColor blue circle) movingBall1 u = move (vector2XY 0 wiggle) (ball1 u) movingBall2 u = move (vector2XY wiggle 0) (ball2 u) example2 u = movingBall1 u `over` movingBall2 u
Some behaviors are generated by user interaction. For example, the mouse motion is represented by the following behavior:
mouseMotion :: User -> Vector2B
As mouse motion is part of the user input, the User value passed into the animation by the disp function must then be passed on to mouseMotion. This program displays a ball that follows the mouse:
example3 u = move (mouseMotion u) ball1
Behaviors are continuous, defined over a continuous range of time values. Events, in contrast, are instantaneous: an event occurs at a discrete set of times. Each event occurrence has a corresponding value; the type Event T denotes an event that generates a value of type T when it happens. Events that do not generate interesting values have type Event (). Events in Fran are concrete values rather than ephemeral happenings and may be treated as any other data object.
Specific kinds of events, such as `resize window' or `keyboard press' are extracted from the User type. For example, these events are associated with the mouse buttons:
lbp,rbp :: User -> Event () -- Mouse button presses
One can think of Event a as [(Time,a)]: a time-sorted list of occurrences containing the time and event value for each occurrence.
Here are some other basic events:
neverE :: Event a constE :: Time -> a -> Event a timeIs :: Time -> Event () timeIs t = constE t () alarmE :: Time -> Time -> Event ()
The neverE event never happens. The constE and timeIs events occur eactly once. The alarmE event goes off at regular intervals: the arguments are the start time and the time between events.
Events are used to build reactive behaviors which change course in response to events. Reactive behaviors are defined using the untilB function:
untilB :: GBehavior bv => bv -> Event bv -> bv
The class GBehavior defines reactive data types. Some reactive types, such as RealB or ColorB are formed by applying the Behavior type constructor to an existing type. Other types, such as ImageB, User, and all event types are conceptually behaviors in that they exist over time and support untilB, but are not literally behaviors. The untilB function changes the course of a behavior when an event occurs; the first event occurrence generates the new behavior to be followed after the occurrence time.
Before we can use untilB in an example, we need to transform an event such as lbp of type Event () into an event which generates a behavior. These functions transform an event:
(-=>) :: Event a -> b -> Event b (==>) :: Event a -> (a -> b) -> Event b
Note the similarity between (==>) and the map function. Using (==>), we can now write a simple reactive behavior:
example4 u = withColor col circle where col = red `untilB` lbp u -=> blue
The circle changes from red to blue on the first left button press. The implicit parentheses are around the -=> expressions, since `untilB` has a lower fixity than -=> .
Fran contains a rich library of functions involving events and behaviors.
The choice operator merges two events into a single one:
(.|.) :: Event a -> Event a -> Event a anyE :: [Event a] -> Event a anyE = foldr (.|.) neverE
For example, given the definition
click u = lbp u .|. rbp u
and a user u, the event click u contains all of left and right button presses from u.
In the following example, the circle may turn either red or blue, depending on which mouse button is pressed first:
example5 u = withColor col circle where col = red `untilB` lbp u -=> blue .|. rbp u -=> green
Note that ".|." has lower precedence than "-=>", but higher than untilB.
The -=> and ==> operators are special cases of a more general event handler, handleE. Using handleE, the event time, event value, and residual event are all revealed.
handleE :: Event a -> (Time -> a -> Event a -> b) -> Event b (==>) :: Event a -> (a -> b) -> Event b e ==> f = e `handleE` (\_ x _ -> f x) (-=>) :: Event a -> b -> Event b e -=> v = e ==> const v withRestE :: Event a -> Event (a, Event a) withRestE e = e `handleE` (\_ v e' -> (v,e')) withTimeE :: Event a -> Event (a, Time) withTimeE e = e `handleE` (\t v _ -> (v,t)) withRestE_ :: Event a -> Event (Event a) withRestE_ e = e `handleE` \ te x e' -> e' withTimeE :: Event a -> Event (a, Time) withTimeE e = e `handleE` \ te x e' -> (x,te) nextE :: Event a -> Event (Event a) nextE = withRestE_
These functions associate the events in an event stream with values in a list:
withElemE :: Event a -> [b] -> Event (a,b) withElemE_ :: Event a -> [b] -> Event b e `withElemE_` l = (e `withElemE` l) ==> snd
Finally, these utilities convert events into behaviors:
-- Assemble a behavior piecewise from an initial one and an event switcher :: GBehavior bv => bv -> Event bv -> bv -- Accumulate using f, but age the accumulator accumB :: GBehavior bv => (bv -> b -> bv) -> bv -> Event b -> bv -- Map a function over a switching behavior mapSwitcher :: GBehavior b => (a -> b) -> a -> Event a -> b mapSwitcher f x0 e = switcher (f x0) (e ==> f) -- A switcher for piecewise-constant behaviors stepper :: a -> Event a -> Behavior a stepper x0 e = mapSwitcher constantB x0 e -- A similar operation but for piecewise-constant behaviors: stepAccum :: a -> Event (a -> a) -> Behavior a stepAccum x0 change = stepper x0 (accumE x0 change)
Using these functions, one write state machines succinctly. Here is a variation of example5 that changes color whenever the left or right button is pressed (not just the first time):
example6 u = withColor c circle where c = switcher red (lbp u -=> blue .|. rbp u -=> red)
Another useful technique is to represent a "state" as a piecewise-constant behavior with stepAccum. The following variation of example4 toggles between red and blue whenever the right mouse button is pressed:
example7 u = withColor (fstB state) circle where state = stepAccum (S.red,S.blue) (lbp u -=> \ (a,b) -> (b,a))
This example uses withElemE_ to map the left button presses onto a series of numbers then uses stepper to convert the event into a behavior.
example8 u = move (vector2XY l l) ball where l = stepper 0 (lbpCounter u) ball = stretch 0.3 (withColor red circle) lbpCounter :: User -> Event RealVal lbpCounter u = withElemE_ (lbp u) [0.1, 0.2 ..]
These functions filter a selected set of occurrences out of an event:
filterE :: Event a -> (a -> Maybe b) -> Event b suchThat :: Event a -> (a -> Bool) -> Event a suchThat ev pred = filterE ev (\a -> if pred a then Just a else Nothing)
These events and behaviors are derived from user input.
-- mouse button press and release events lbp, rbp, lbr, rbr :: User -> Event () -- keyboard stuff. VKey is defined in the Win32 module keyPressAny :: User -> Event VKey keyPress :: VKey -> User -> Event () keyReleaseAny :: User -> Event VKey keyRelease :: VKey -> User -> Event () -- These use Char instead of VKey charPress :: User -> Event Char charPressAny :: Char -> User -> Event () -- Returns size of resized window resize :: User -> Event Vector2 viewSize :: User -> Vector2B -- Mouse motion mouseMove :: User -> Event Point2 mouse :: User -> Point2B mouseMotion :: User -> Vector2B -- Stylus (tablet) stylusPresent :: User -> Bool stylusMove :: User -> Event Point2 stylusPressureChange :: User -> Event Double stylusButton :: User -> Event Bool stylusDown, stylusUp :: User -> Event () stylus :: User -> Point2B stylusMotion :: User -> Vector2B stylusPressure :: User -> RealB -- Allows synchronization with display events updateDone :: User -> Event Time updatePeriod :: User -> TimeB -- Time since start of User. userTime :: User -> TimeB userTimeIs :: Time -> User -> Event ()
The integral function integrates numeric behaviors over time. Both reals and vectors can be integrated. The type of integral is:
integral :: (VectorSpace v) => Behavior v -> User -> Behavior v atRate :: (VectorSpace v) => Behavior v -> User -> Behavior v
Function atRate is another name for integral. The types in VectorSpace include Real, Vector2, and Vector3.
The User argument supplies the integration start time and a sampling clock which determines the step size used by the underlying numerical method.
This example uses integration to express the motion of a falling ball:
example9 u = withColor red (moveXY 0 pos (stretch 0.1 circle)) where pos = p0 + integral vel u vel = v0 + integral acc u acc = -0.3 p0 = -1 v0 = 1
Integrals may be mutually recursive.
A snapshot samples the value of a behavior at an event occurrence. The snapshot functions are:
snapshot :: Event a -> Behavior b -> Event (a, b) snapshot_ :: Event a -> Behavior b -> Event b snapshot_ e b = (e `snapshot` b) ==> snd whenSnap :: Event a -> Behavior b -> (a -> b -> Bool) -> Event a whenSnap e b pred = (e `snapshot` b `suchThat` uncurry pred) ==> fst whenE :: Event a -> Behavior Bool -> Event a e `whenE` b = whenSnap e b (curry snd)
This program captures the mouse position when the left button is pressed and moves the ball to that position:
mouseEvs :: User -> Event Point2B mouseEvs u = lbp u `snapshot_` mouseMotion u example10 u = withColor red $ move (stepper S.zeroVector (mouseEvs u)) $ stretch 0.1 circle
The predicate function creates an event which monitors a boolean behavior:
predicate :: Behavior Bool -> User -> Event (User)
The User argument is used as a sampling clock. Care must be taken since sampling may miss occurrences of the boolean behavior. (Some previous versions of Fran were able to detect even equality events, and we hope that future ones will.)
The following example is of a bouncing ball. Again, it defines the position as the integral of velocity, and uses the integral of acceleration in defining the velocity. This time, however, we also sum up instanteous velocity changes, or "impulses", due to collision. The trick is to snapshot the velocity at each collision, and multiply the snapshot by nearly negative two to reverse the instantaneous velocity with a small energy loss.
example11 u = withColor red (moveXY 0 pos (stretch 0.1 circle)) where pos = p0 + integral vel u vel = v0 + integral acc u + sumE impulse impulse = collide `snapshot_` vel ==> (* (-1.9)) collide = predicate (pos <=* (-1) &&* vel <* 0) u acc = -1 p0 = -1 v0 = 2 sumE :: Num a => Event a -> Behavior a sumE ev = stepper 0 (scanlE (+) 0 ev)
The <=* operator is a behavioral version of <=, as explained in the next section. The predicate checks that the position is less or equal to the floor height rather than simply checking for equality since sampling may miss the instant at which the position is exactly at the floor. The test for negative velocity (downward motion) is so that a ball is not considered to be colliding when it is trying to come back up out of the floor.
A time transform alters the time frame within a behavior.
timeTransform :: GBehavior bv => bv -> Behavior Time -> bv later, earlier :: GBehavior bv => TimeB -> bv -> bv later dt b = b `timeTransform` (time - dt) earlier dt = later (-dt) faster, slower :: GBehavior bv => TimeB -> bv -> bv faster x b = b `timeTransform` (time * x) slower x = faster (1/x)
The expression timeTransform b1 tb yields a new behavior which is evaluated in a transformed time-frame according to behavior tb. For example:
example12 u = move (mouseMotion u) (stretch 0.2 (withColor red circle)) `over` move (timeTransform (mouseMotion u) (time - 2)) (stretch 0.3 (withColor blue circle))
These are some miscellaneous utilities:
-- explicit aging of generalized behavior: afterE :: GBehavior bv => Event a -> bv -> Event (a, bv) afterE_ :: GBehavior bv => Event a -> bv -> Event bv -- Ties switcher to an event stream repeatE :: GBehavior bv => Event bv -> Event bv repeatE e = withRestE e ==> uncurry switcher -- An event based version of scanl: scanlE :: (a -> b -> a) -> a -> Event b -> Event a -- Accumulate via a function-valued event accumE :: a -> Event (a -> a) -> Event a accumE x0 change = scanlE (flip ($)) x0 change countE :: Event a -> Behavior Int countE e = stepper 0 (scanlE (\ c _ -> c + 1) 0 e) -- Adds the previous value to the current event value: withPrevE :: Event a -> a -> Event (a,a) withPrevE_ :: Event a -> a -> Event a timeSince :: Time -> Behavior DTime timeSince t0 = time - constantB t0 -- modify an ongoing behavior using event stream values accumB :: GBehavior bv => (bv -> b -> bv) -> bv -> Event b -> bv nextUser :: (User -> Event a) -> (User -> Event (a,User)) nextUser f u = f u `afterE` u nextUser_ :: (User -> Event a) -> (User -> Event User) nextUser_ f u = nextUser f u ==> snd leftButton, rightButton :: User -> BoolB leftButton u = toggle (lbp u) (lbr u) rightButton u = toggle (rbp u) (rbr u) -- Debugging support data TraceEFlag = TraceOccsE | TraceAllE deriving (Show, Eq) traceE :: Show a => String -> TraceEFlag -> Event a -> Event a
We say a type or function which has been raised from the domain of ordinary Haskell values to behaviors is "lifted". For example, a function such as
(&&) :: Bool -> Bool -> Bool
can be promoted to a corresponding function over behaviors:
(&&*) :: BoolB -> BoolB -> BoolB
The type BoolB is a synonym for Behavior Bool; most commonly used types have a behavioral synonym defined in Fran. The name &&* arises from a simple naming convention in Fran: lifted operators are appended with a * and lifted vars are appended with B.
The renaming required by && can sometimes be avoided using type classes. For example, an instance declaration such as the following
instance Num a => Num (Behavior a)
allows all of the methods in Num to be applied directly to behaviors without renaming. Constant types in the class definition cannot be lifted by such a declaration. In the Num instance above, the type of fromInteger is
fromInteger :: Num a => Integer -> (Behavior a)
The argument to fromInteger is not lifted - only the result. This allows integer constants to be treated as constant behaviors. While fromInteger works in the expected way, other class methods cannot be used. In the declaration
instance Ord a => Ord (Behavior a)
is not useful since it defines operations such as
(>) :: Behavior a -> Behavior a -> Bool
Unfortunately, Fran needs a > function which returns Behavior Bool instead of just Bool. The Eq and Ord classes are not lifted using instance declarations. Rather, each method is individually renamed and lifted. These are the lifting functions: they transform a non-behavioral function into its behavioral counterpart:
constantB :: a -> Behavior a ($*) :: Behavior (a -> b) -> Behavior a -> Behavior b lift0 :: a -> Behavior a lift0 = constantB lift1 :: (a -> b) -> Behavior a -> Behavior b lift1 f b1 = lift0 f $* b1 lift2 :: (a -> b -> c) -> Behavior a -> Behavior b -> Behavior c lift2 f b1 b2 = lift1 f b1 $* b2 lift3 :: (a -> b -> c -> d) -> Behavior a -> Behavior b -> Behavior c -> Behavior d lift3 f b1 b2 b3 = lift2 f b1 b2 $* b3 ... lift7 ...
Using these functions, the definition of (>*) is
(>*) = lift2 (>)
Many Prelude functions have been lifted in Fran via overloading:
(+) :: Num a => Behavior a -> Behavior a -> Behavior a (*) :: Num a => Behavior a -> Behavior a -> Behavior a negate :: Num a => Behavior a -> Behavior a abs :: Num a => Behavior a -> Behavior a fromInteger :: Num a => Integer -> Behavior a fromInt :: Num a => Int -> Behavior a quot :: Integral a => Behavior a -> Behavior a -> Behavior a rem :: Integral a => Behavior a -> Behavior a -> Behavior a div :: Integral a => Behavior a -> Behavior a -> Behavior a mod :: Integral a => Behavior a -> Behavior a -> Behavior a quotRem :: Integral a => Behavior a -> Behavior a -> (Behavior a, Behavior a) divMod :: Integral a => Behavior a -> Behavior a -> (Behavior a, Behavior a) fromDouble :: Fractional a => Double -> Behavior a fromRational :: Fractional a => Rational -> Behavior a (/) :: Fractional a => Behavior a -> Behavior a -> Behavior a sin :: Floating a => Behavior a -> Behavior a cos :: Floating a => Behavior a -> Behavior a tan :: Floating a => Behavior a -> Behavior a asin :: Floating a => Behavior a -> Behavior a acos :: Floating a => Behavior a -> Behavior a atan :: Floating a => Behavior a -> Behavior a sinh :: Floating a => Behavior a -> Behavior a cosh :: Floating a => Behavior a -> Behavior a tanh :: Floating a => Behavior a -> Behavior a asinh :: Floating a => Behavior a -> Behavior a acosh :: Floating a => Behavior a -> Behavior a atanh :: Floating a => Behavior a -> Behavior a pi :: Floating a => Behavior a exp :: Floating a => Behavior a -> Behavior a log :: Floating a => Behavior a -> Behavior a sqrt :: Floating a => Behavior a -> Behavior a (**) :: Floating a => Behavior a -> Behavior a -> Behavior a logBase :: Floating a => Behavior a -> Behavior a -> Behavior a
These operations correspond to functions which cannot be overloaded for behaviors. The convention is to use the B suffix for vars and a * suffix for ops.
fromIntegerB :: Num a => IntegerB -> Behavior a toRationalB :: Real a => Behavior a -> Behavior Rational toIntegerB :: Integral a => Behavior a -> IntegerB evenB, oddB :: Integral a => Behavior a -> BoolB toIntB :: Integral a => Behavior a -> IntB properFractionB :: (RealFrac a, Integral b) => Behavior a -> Behavior (b,a) truncateB :: (RealFrac a, Integral b) => Behavior a -> Behavior b roundB :: (RealFrac a, Integral b) => Behavior a -> Behavior b ceilingB :: (RealFrac a, Integral b) => Behavior a -> Behavior b floorB :: (RealFrac a, Integral b) => Behavior a -> Behavior b (^*) :: (Num a, Integral b) => Behavior a -> Behavior b -> Behavior a (^^*) :: (Fractional a, Integral b) => Behavior a -> Behavior b -> Behavior a (==*) :: Eq a => Behavior a -> Behavior a -> BoolB (/=*) :: Eq a => Behavior a -> Behavior a -> BoolB (<*) :: Ord a => Behavior a -> Behavior a -> BoolB (<=*) :: Ord a => Behavior a -> Behavior a -> BoolB (>=*) :: Ord a => Behavior a -> Behavior a -> BoolB (>*) :: Ord a => Behavior a -> Behavior a -> BoolB cond :: BoolB -> Behavior a -> Behavior a -> Behavior a notB :: BoolB -> BoolB (&&*) :: BoolB -> BoolB -> BoolB (||*) :: BoolB -> BoolB -> BoolB pairB :: Behavior a -> Behavior b -> Behavior (a,b) fstB :: Behavior (a,b) -> Behavior a sndB :: Behavior (a,b) -> Behavior b pairBSplit :: Behavior (a,b) -> (Behavior a, Behavior b) showB :: (Show a) => Behavior a -> Behavior String
A few list-based functions are lifted, although most of the functions in PreludeList are not lifted.
nilB :: Behavior [a] consB :: Behavior a -> Behavior [b] -> Behavior [b] headB :: Behavior [a] -> Behavior a tailB :: Behavior [a] -> Behavior [a] nullB :: Behavior [a] -> BoolB (!!*) :: Behavior [a] -> IntB -> Behavior a -- Turn a list of behaviors into a behavior over list bListToListB :: [Behavior a] -> Behavior [a] bListToListB = foldr consB nilB -- Lift a function over lists into a function over behavior lists liftL :: ([a] -> b) -> ([Behavior a] -> Behavior b) liftL f bs = lift1 f (bListToListB bs)
The numeric types and functions are available both a static values and as behaviors. Since the same name is generally used for both the static and behavioral version of a function, only the behavioral names are exported by the Fran module. If the non-behavioral functions are needed, the convention is to add
import qualified StaticTypes as S
to the program and qualify static names with S., as in S.origin2.
All scalar types are essentially the same in Fran. Synonyms allow type signatures to contain extra descriptive information such as Fraction for values between 0 and 1 but no explicit type conversions are required between the various scalar types.
type RealVal = Double type Length = RealVal -- non-negative type Radians = RealVal -- 0 .. 2pi (when generated) type Fraction = RealVal -- 0 to 1 (inclusive) type Scalar = Double type Time = Double type DTime = Time -- Time deltas, i.e., durations data Point2 -- 2D point data Vector2 -- 2D vector data Transform2 -- 2D transformation data Point3 -- 3D point data Vector3 -- 3D vector data Transform3 -- 3D transformation type RealB = Behavior RealVal type FractionB = Behavior Fraction type RadiansB = Behavior Radians type LengthB = Behavior Length type TimeB = Behavior Time type IntB = Behavior Int type Point2B = Behavior Point2 type Vector2B = Behavior Vector2 type Transform2B = Behavior Transform2 type Point3B = Behavior Point3 type Vector3B = Behavior Vector3 type Transform3B = Behavior Transform3
origin2 :: Point2B point2XY :: RealB -> RealB -> Point2B point2Polar :: LengthB -> RadiansB -> Point2B point2XYCoords :: Point2B -> (RealB, RealB) point2PolarCoords :: Point2B -> (RealB, RealB) distance2 :: Point2B -> Point2B -> LengthB distance2Squared :: Point2B -> Point2B -> LengthB linearInterpolate2 :: Point2B -> Point2B -> RealB -> Point2B (.+^) :: Point2B -> Vector2B -> Point2B (.-^) :: Point2B -> Vector2B -> Point2B (.-.) :: Point2B -> Point2B -> Vector2B origin3 :: Point3B point3XYZ :: RealB -> RealB -> RealB -> Point3B point3XYZCoords :: Point3B -> (RealB, RealB, RealB) distance3 :: Point3B -> Point3B -> LengthB distance3Squared :: Point3B -> Point3B -> LengthB linearInterpolate3 :: Point3B -> Point3B -> RealB -> Point3B (.+^#) :: Point3B -> Vector3B -> Point3B (.-^#) :: Point3B -> Vector3B -> Point3B (.-.#) :: Point3B -> Point3B -> Vector3B xVector2, yVector2 :: Vector2B -- unit vectors vector2XY :: RealB -> RealB -> Vector2B vector2Polar :: RealB -> RealB -> Vector2B vector2XYCoords :: Vector2B -> (RealB, RealB) vector2PolarCoords :: Vector2B -> (RealB, RealB) instance Num Vector2 -- fromInteger, * not allowed xVector3 :: Vector3B -- unit vector yVector3 :: Vector3B -- unit vector zVector3 :: Vector3B -- unit vector vector3XYZ :: RealB -> RealB -> RealB -> Vector3B vector3XYZCoords :: Vector3B -> (RealB, RealB, RealB) vector3Spherical :: RealB -> RealB -> RealB -> Vector3B vector3PolarCoords :: Vector3B -> (RealB, RealB, RealB) instance Num Vector3 -- fromInteger, * not allowed/pre>
Note that vectors and points have distinct types. You cannot use + to add a point to a vector. Vectors are a member of the Num class while points are not; thus + works with vectors but not points. Although it is in class Num, the * operator cannot be used for vectors.
Read the `.' in the operators above as `point' and `^' as `vector'. Thus .+^ means `point plus vector'.
zeroVector :: VectorSpace v => Behavior v (*^) :: VectorSpace v => ScalarB -> Behavior v -> Behavior v (^/) :: VectorSpace v => Behavior v -> ScalarB -> Behavior v (^+^),(^-^) :: VectorSpace v => Behavior v -> Behavior v -> Behavior v dot :: VectorSpace v => Behavior v -> Behavior v -> ScalarB magnitude :: VectorSpace v => Behavior v -> ScalarB magnitudeSquared :: VectorSpace v => Behavior v -> ScalarB normalize :: VectorSpace v => Behavior v -> Behavior v instance VectorSpace Double instance VectorSpace Float instance VectorSpace Vector2 instance VectorSpace Vector3
The types Transformation2B and Transformation3B represent geometric transformation on images, points, or vectors. The basic transformations are translation, rotation, and scaling. Complex transformations are created by composing basic transformations. The class Transformable2 contains 2D transformable objects.
class Tranformable2B a where (*%) :: Transform2B -> a -> a -- Applies a transform
These are the operations on 2D transforms:
identity2 :: Transform2B translate2 :: Vector2B -> Transform2B rotate2 :: RealB -> Transform2B compose2 :: Transform2B -> Transform2B -> Transform2B inverse2 :: Transform2B -> Transform2B uscale2 :: RealB -> Transform2B -- only uniform scaling instance Transformable2B Point2B instance Transformable2B Vector2B instance Transformable2B RectB
The treatment of 3D is similar.
identity3 :: Transform3B translate3 :: Vector3B -> Transform3B rotate3 :: Vector3B -> RealB -> Transform3B scale3 :: Vector3B -> Transform3B compose3 :: Transform3B -> Transform3B -> Transform3B uscale3 :: RealB -> Transform3B class Tranformable3B a where (**%) :: Transform3B -> a -> a
A transformation that doubles the size of an object and then rotates it 90 degrees would be
rotate2 (pi/2) `compose2` uscale2 2.
Note that the first transform applied is the one on the right, as with Haskell's function composition operator (.).
Fran is capable of rendering 2-D images, 3-D images, and sounds.
Fonts are defined as follows:
data Font = Font Family Bool Bool -- family isBold isItalic data Family = System | TimesRoman | Courier | Arial | Symbol system, timesRoman, courier, arial, symbol :: Font bold :: Font -> Font italic :: Font -> Font data TextT = TextT Font String type TextB = Behavior TextT simpleText :: StringB -> TextB boldT :: TextB -> TextB italicT :: TextB -> TextB textFont :: Font -> TextB -> TextB
The simpleText function creates a text object using a default font. The other operators transform text objects by changing their font.
These functions define Fran colors:
colorRGB :: RealB -> RealB -> RealB -> ColorB colorHSL :: RealB -> RealB -> RealB -> ColorB colorRGBCoords :: ColorB -> (RealB, RealB, RealB) colorHSLCoords :: ColorB -> (RealB, RealB, RealB) interpolateColorRGB :: ColorB -> ColorB -> RealB -> ColorB interpolateColorHSL :: ColorB -> ColorB -> RealB -> ColorB grey :: FractionB -> ColorB stronger :: FractionB -> ColorB -> ColorB duller :: FractionB -> ColorB -> ColorB darker :: FractionB -> ColorB -> ColorB brighter :: FractionB -> ColorB -> ColorB shade :: FractionB -> ColorB -> ColorB white, black, red, green, blue :: ColorB lightBlue, royalBlue, yellow, brown :: ColorB asColorRef :: ColorB -> Win32.COLORREF -- It's easy to find color defs with 256-scaled rgb params, e.g., in -- etc/rgb.txt in the GNU Emacs distribution. colorRGB256 :: IntB -> IntB -> IntB -> ColorB
The type ImageB represents reactive 2-D animations.
emptyImage :: ImageB solidImage :: ImageB flipImage :: HFlipBook -> RealB -> ImageB soundImage :: SoundB -> ImageB over :: ImageB -> ImageB -> ImageB overs :: [ImageB] -> ImageB withColor :: ColorB -> ImageB -> ImageB crop :: RectB -> ImageB -> ImageB line :: Point2B -> Point2B -> ImageB circle :: ImageB polygon :: [Point2B] -> ImageB polyline :: [Point2B] -> ImageB polyBezier :: [Point2B] -> ImageB polygonB :: Behavior [Point2] -> ImageB polylineB :: Behavior [Point2] -> ImageB polyBezierB :: Behavior [Point2] -> ImageB bezier :: Point2B -> Point2B -> Point2B -> Point2B -> ImageB textImage :: TextB -> ImageB importBitmap :: String -> ImageB importBitmapWithSize :: String -> (ImageB, RealVal, RealVal) instance Transformable2 ImageB instance GBehavior ImageB
Most of these operations are self-explanatory. The line, polyline, and bezier functions form lines and curves of a fixed system-determined width. Polygon filling uses a odd-even rule to determine whether a region is inside the polygon. All but the bitmaps are painted with a solid color, as selected by withColor. Most of these objects are centered at the origin. Text is centered just below the origin.
Bitmaps are centered at the origin and are displayed actual size unless scaled. Bitmaps must be stored in .bmp files.
The RectB type used in cropping represents axis-aligned rectangles. They may be constructed from any pair of opposite corners or from a center and size, by intersection, or by expansion about the center:.
rectFromCorners :: Point2B -> Point2B -> RectB rectFromCenterSize :: Point2B -> Vector2B -> RectB intersectRect :: RectB -> RectB -> RectB expandRect :: RealB -> RectB -> RectB
Similarly, they may be inspected to extract any corner or the center or size:
rectLL, rectUR, rectLR, rectUL :: RectB -> Point2B rectCenter :: RectB -> Point2B rectSize :: RectB -> Vector2B
They may also be tested for containment:
rectContains :: RectB -> Point2B -> BoolB
These rectangles are also 2D transformables, but a run-time check is made to ensure that no rotation is applied. Try the cropping examples in ../demos/Test.hs.
Fast bitmap-based animation sequences are imported with flipImage, which takes a "flip book" and a page number behavior.
-- Make a flip book given: surface, width and height, X,Y start pos on surface, -- number of columns, and rows of pages flipBook :: HDDSurface -> Pixels -> Pixels -> Pixels -> Pixels -> Int -> Int -> HFlipBook
A "surface" is made by the following function, which takes the name of a .bmp file:
bitmapDDSurface :: String -> HDDSurface
Note that static imported bitmaps are a degenerate case of flip-book animation:
importBitmap :: String -> ImageB importBitmapWithSize :: String -> (ImageB, RealVal, RealVal)
For convenience if you have a bitmap file with just one bitmap, you can use the following:
importFlipBook :: String -> Int -> Int -> HFlipBook
Here's a tip: start with an animated GIF, and use GIF Movie Gear to view it. Do Tools/Unoptimize, and then File/Export As/GIF Filmstrip, with horizontal orientation, and a factor of the number of frames as the "number of frames per strip". Then use another program (e.g., MS Photo Editor) to convert the resulting non-animated GIF into a BMP. Then use importFlipBook to bring it into Fran. Someday maybe Fran will import animated GIFs directly. (Volunteers?)
It is sometimes convenient to put more than one flipbook into a bitmap file, so Fran provides a convenience function for parsing a DDSurface into a bunch of flip books. The DDSurface is assumed to be a vertical concatenation of flip books, each of which is rectangular arrays of images. These arrays are all presumed to fill up the whole DDSurface width. The given list of pairs specifies the number of columns and rows of each flip book, starting from the given vertical pixel number (with the top pixel being zero). If some or all of your surface does not fit this format, you can still use the flipBook construction function directly.
parseFlipBooks :: [(Int, Int)] -> Pixels -> HDDSurface -> [HFlipBook]
For example, one could parse up the BMP file in Media\donuts.bmp (which came from the Microsoft DirectX SDK) as follows:
[ donutBook, pyramidBook, sphereBook, cubeBook, shipBook, shipShieldBook ] = parseFlipBooks [(5,6), (10,4), (20,2), (20,2), (10,4), (10,4)] 0 donutsSurface where donutsSurface = bitmapDDSurface "..\\..\\Media\\donuts.bmp"
(We are assuming here that the current directory is something like Fran\demos\Roids.)
These are some simple utilities for 2-D images. The Transformable2B context denotes images as well as 2-D points and vectors.
-- Star figure. Arguments: skip and vertices. star :: IntB -> IntB -> ImageB regularPolygon :: IntB -> ImageB regularPolygon vs = star 1 vs circle, square :: ImageB move :: Transformable2B a => Vector2B -> a -> a move dp thing = translate2 dp *% thing moveXY :: Transformable2B a => RealB -> RealB -> a -> a moveXY dx dy thing = move (vector2XY dx dy) thing moveTo :: Transformable2B bv => Point2B -> bv -> bv moveTo p = move (p .-. origin2) stretch :: RealB -> ImageB -> ImageB stretch sc = (uscale2 sc *%) -- 1.0 = 180 degrees turnLeft, turnRight :: Transformable2B a => FractionB -> a -> a turnLeft frac im = rotate2 (frac * pi) *% im turnRight frac = turnLeft (-frac) stringBIm :: StringB -> ImageB stringIm : String -> ImageB stringBIm str = textImage (simpleText str) stringIm = stringBIm . constantB showBIm :: Show a => Behavior a -> ImageB showIm :: Show a => a -> ImageB showBIm = stringBIm . showB showIm = showBIm . constantB -- Given an image and a canonical size, stretch the image uniformly so -- that the size maps exactly onto the window view size. viewStretch :: Vector2B -> User -> ImageB -> ImageB
emptyG :: GeometryB unionG :: GeometryB -> GeometryB -> GeometryB withColorG :: ColorB -> GeometryB -> GeometryB ambientLightG :: GeometryB pointLightG :: GeometryB spotLightG :: GeometryB directionalLightG :: GeometryB parallelPointLightG :: GeometryB -- Import geometry from a file importX :: String -> GeometryB instance GBehavior GeometryB where instance Transformable3B GeometryB where
Some 3D convenience functions:
move3 :: Vector3B -> GeometryB -> GeometryB move3 dp = (translate3 dp **%) moveXYZ :: RealB -> RealB -> RealB -> GeometryB -> GeometryB moveXYZ dx dy dz = move3 (vector3XYZ dx dy dz) moveTo3 :: Point3B -> GeometryB -> GeometryB moveTo3 p = move3 (p .-.# origin3) stretch3 :: RealB -> GeometryB -> GeometryB stretch3 sc = (uscale3 sc **%) turn3 :: Transformable3B a => Vector3B -> RealB -> a -> a turn3 axis angle = (rotate3 axis angle **%)
-- import from .wav file, possibly repeating importWave :: String -> Bool -> SoundB silence :: SoundB mix :: SoundB -> SoundB -> SoundB volume :: RealB -> SoundB -> SoundB -- multiply intensity pitch :: RealB -> SoundB -> SoundB -- multiply pitch pan :: RealB -> SoundB -> SoundB -- Pan, in dB. May change instance GBehavior SoundB
Almost all of Fran is concerned with modeling reactive animations of various types. There are also a few functions concerned with the display of animations. The first is a generalized display function. Its argument is a function from a user that produces an ImageB and a function from the created window to an effect-valued event. Upon each event occurence, the corresponding action is performed. Also, instead of starting up the event loop, this function returns the window, so that the program can do things like setting the window title.
displayEx :: (User -> (ImageB, Win32.HWND -> Event (IO ()))) -> IO Win32.HWND
Given a list of Fran windows, one can run them concurrently (though in practice, the responsiveness of each suffers considerably):
eventLoops :: [Win32.HWND] -> IO ()
These functions suffice, but there are several more convenient versions:
eventLoop :: Win32.HWND -> IO () displayUs :: [User -> ImageB] -> IO () displayU :: (User -> ImageB) -> IO () displayU imF = displayUs [imF] userDelay :: GBehavior bv => bv -> User -> bv userDelay bv u = later (constantB (userStartTime u)) bv displays :: [ImageB] -> IO () displays = displayUs . map userDelay display :: ImageB -> IO () display imB = displays [imB] displayGs :: [GeometryB] -> IO () displayGs = displayGUs . map const displayG :: GeometryB -> IO () displayG g = displayGs [g] displayGUs :: [User -> GeometryB] -> IO () displayGUs = displayUs . map imF where imF gf = \ u -> renderGeometry (gf u) defaultCamera displayGU :: (User -> GeometryB) -> IO () displayGU gf = displayGUs [gf]
There are also two functions for changing the initial size of Fran windows. One persistent and the other temporary:
setInitialViewSize :: RealVal -> RealVal -> IO () withInitialViewSize :: RealVal -> RealVal -> IO a -> IO a
When giving a demo or recording an animation for later presentation, it is helpful to show the observer what the user is doing. Fran includes a few convenient functions for this purpose.
-- Echo button and keyboard input events at the bottom of the window inputMonitor :: User -> ImageB -- displayU plus input monitor of given color displayUMonC :: ColorB -> (User -> ImageB) -> IO () displayUMon :: (User -> ImageB) -> IO () displayUMon = displayUMonC blue -- displayEx plus input monitor of given color displayExMon :: ColorB -> (User -> (ImageB, Event (IO ()))) -> Win32.HWND -> IO ()
Here are all fixities defined in Fran. Lifted versions of standard Haskell functions take on the same fixities as the unlifted versions. Infix event modifiers like ==>, suchThat, etc., all have equal, left-associative fixities so that they cascade pleasantly.
infixr 0 $* -- lifted $ infixr 1 `untilB` infixl 2 .|. infixr 2 ||* -- lifted || infixl 3 ==>, -=> infixl 3 `handleE`, `filterE` infixl 3 `withElemE`, `withElemE_` infixl 3 `withPrevE`, `withPrevE_` infixl 3 `suchThat`, `suchThat_` infixl 3 `afterE`, `afterE_` infixr 3 &&* -- lifted && infix 4 ==*, <*, <=* , >=*, >* -- Lifted comparisons infix 4 .+^, .-^, .-. -- point / vector addition/subtraction infix 4 .+^#, .-^#, .-.# -- 3D points infixl 6 `unionG` infixl 6 `over` infixl 6 ^+^, ^-^ -- vector add and subtract infixr 7 `dot`, *^, ^/ -- scalar * vector, vector / scalar infixr 7 *%, `compose2` -- 2D transforms infixr 7 **%, `compose3` -- 3D transforms infixr 8 ^*, ^^* -- lifted ^, ^^