LambdaCube 3D

Purely Functional Rendering Engine

Monthly Archives: November 2012

Using Bullet physics with an FRP approach (part 2)

In the previous post, we introduced a simple attribute system to give the raw Bullet API a friendlier look. As it turns out, this system is easy to extend along the temporal dimension, since an attribute of a physical object is a time-varying value – implemented as a mutable variable under the hood. The common theme in various FRP approaches is about reifying the whole lifetime of such values in some form, which naturally leads to the idea of using the attributes as the bridge between the reactive library and the physics engine.

Time-varying attributes with Elerea

To make a seamless integration of Elerea and Bullet possible, we needed to define a few additional primitive signal constructors. Originally, the only way to feed data from IO sources into an Elerea network was through the external primitive, which constructed a signal and a corresponding IO function to update its output (the first argument is the initial value):

external :: a -> IO (Signal a, a -> IO ())

The obvious problem with external is the fact that it works outside the signal network, so it cannot be defined in a convenient way in terms of any entity that lives inside the reactive world. The simplest solution is to directly embed IO computations. One-off computations can be directly executed in SignalGen through the execute primitive, which is equivalent to liftIO. IO signals can be constructed with the effectful* family of functions, which are analogous to the applicative lifting combinators, but apply an IO function to the input signals instead of a pure one:

effectful :: IO a -> SignalGen (Signal a)
effectful1 :: (t -> IO a) -> Signal t -> SignalGen (Signal a)
effectful2 :: (t1 -> t2 -> IO a) -> Signal t1 -> Signal t2 -> SignalGen (Signal a)
...

The results must be in the SignalGen context in order to ensure that the constructed signals cause the IO computations to be evaluated exactly once per sampling step. The reason is simple: to meet this condition, the signal needs to be memoised, which requires an additional state variable, and state variables can only be introduced in SignalGen.

First, we extend the list of attribute operations with a fifth member, which defines the attribute to be updated by a signal. Since we might not want to take full control of the attribute, just intervene once in a while, the signal is required to be partial through Maybe. When the signal yields Nothing, the attribute is managed by Bullet during that superstep.

data AttrOp o = forall a . Attr o a := a
              | forall a . Attr o a :~ (a -> a)
              | forall a . Attr o a :!= IO a
              | forall a . Attr o a :!~ (a -> IO a)
              | forall a . Attr o a :< Signal (Maybe a)

Now we have all the building blocks necessary to define a signal-based variant of set from the last post:

set' :: o -> [AttrOp o] -> SignalGen (Signal ())
set' obj as = go as (return ())
  where
    go [] sig     = return sig
    go (a:as) sig = case a of
        Attr getter setter := x  ->
            execute (setter obj x >> return ()) >> go as sig
        Attr getter setter :~ f  ->
            execute (getter obj >>= setter obj . f >> return ()) >> go as sig
        Attr getter setter :!= x ->
            execute (x >>= setter obj >> return ()) >> go as sig
        Attr getter setter :!~ f ->
            execute (getter obj >>= f >>= setter obj >> return ()) >> go as sig
        Attr getter setter :< s  -> do     
            dummy <- flip effectful1 s $ \mx -> case mx of
                Nothing -> return ()
                Just x  -> setter obj x >> return ()
            go as (liftA2 const sig dummy)

The first four cases are unchanged, they just need to be wrapped with execute. The signal case is also straightforward: we use effectful1 to sample the signal and update the attribute with its current value. What might not be clear first is all the additional plumbing. Unfortunately, this is all necessary due to the fact that if a signal is not referenced anywhere in the system, it gets garbage collected.

In this case, effectful1 doesn’t produce any meaningful output. All we need is its side effects. However, we still need to store the dummy signal (a stream of unit values), otherwise the setter will only be updated until the next garbage collection round. We can think of the dummy signal as a thread that’s kept alive only as long as we have a handle to it. To ensure that the reference is not lost, we carefully wrap it in another dummy signal that keeps all the signal setters alive. It is up to the caller of set’ to store the final signal.

It is useful to define the equivalent of make as well:

make' :: IO o -> [AttrOp o] -> SignalGen (Signal o)
make' act flags = do
    obj <- execute act
    dummy <- set' obj flags
    return (liftA2 const (return obj) dummy)

To reduce the chance of user error, we return a signal that represents the object we just constructed. The signal always yields a reference to the object, and keeps all the signal attributes alive. To ensure correct behaviour, we should always sample this signal when querying the object, instead of saving the reference and passing it around. This is necessary for another reason as well: thanks to Elerea’s dependency handling, it makes sure that the signal attributes are updated before the object is queried.

A simple use case

The example scene contains two independent details: a falling brick whose collisions with a designated object cause reactions, and a ragdoll that can be dragged with the mouse. In the rest of this post we’ll concentrate on the brick.

The LambdaCube ‘FRP physics’ example

All the objects are created in the top level of the signal network, in the SignalGen monad. In this setup, the object used for collision detection is actually a ghost sphere, not a solid body. We’ll refer to it as the query space. Whenever the brick intersects this sphere, its position and orientation is reset, but its velocity is retained. First we create the sphere, which is just an ordinary IO operation, so we can execute it:

    querySpace <- execute $ do
        ghostObject <- make btPairCachingGhostObject
                       [ collisionFlags :~ (.|. e_btCollisionObject_CollisionFlags_CF_NO_CONTACT_RESPONSE)
                       , collisionShape := sphereShape ghostRadius
                       , worldTransform := Transform idmtx 0
                       ]
        btCollisionWorld_addCollisionObject dynamicsWorld ghostObject 1 (-1)
        return ghostObject

Afterwards, we create a signal that tells us in every frame which objects are colliding with the query space:

    collisions <- effectful $ collisionInfo querySpace

The collisionInfo function returns a list of tuples, where each member contains references to both bodies involved, plus some spatial information that we ignore in this scenario. This is not a library function; its full definition is part of the example. The exact details are not relevant to the topic of this post, as they are just a direct application of the Bullet API, so we’re not going to discuss it here.

Given the collision signal, we can now define the brick:

    let initBrickTrans = Transform idmtx (Vec3 2 20 (-3))
    brick <- do
        rec brick <- make' (snd <$> localCreateRigidBodyM dynamicsWorld 1 initBrickTrans (boxShape brickSize))
                     [worldTransform :< boolToMaybe initBrickTrans . bodyInCollision brickBody <$> collisions]
            brickBody <- snapshot brick
        return brick

We use make’ to invoke the constructor of the brick and define the temporal behaviour of its worldTransform attribute in a single step. Again, the details of the construction are not particularly interesting: all we need is a mass, an initial transformation (position and orientation), and a collision shape for starters.

The real magic happens in the attribute override. Given the signal that tells us who collides with the query space, we can derive the signal that describes how the world transform of the brick needs to be updated over time. This is achieved by mapping a pure function over the signal, which yields Nothing if brickBody is not involved in any of the collisions, and Just initBrickTrans if it is.

One interesting bit to note is the recursion needed for the above definition, which is made possible thanks to SignalGen being a MonadFix instance. In order to define the world transform update signal, we need a reference to the object that we’re just creating. The reference comes from taking a snapshot of the brick signal. Since the update signal doesn’t need to be sampled for the sake of constructing the object, we don’t end up in an infinite loop.

The role of dummy signals

While the general idea of using signals to define time-varying attributes works in practice, it leads to the need for ‘dummy’ signals that have to be kept around explicitly. The big problem with this solution is that it’s a potential source of programmer error. We believe that it is just one manifestation of the more general issue that Elerea provides no way to define the death of signals in a deterministic way. Currently we rely on the garbage collector to clean up all the update activity that’s not needed any more, and it’s up to the programmer to define the signals in a way that they stop their activity at the right time.

While FRP research solved the problem of start times in several ways, it’s not nearly as clear how to describe the endpoint of a signal’s life. Most likely all we need is a few additional primitives that capture the essence of end times the same way the SignalGen monad captures the essence of start times. Recently there have been some interesting developments in this area; we’re hoping that e.g. the work of Wolfgang Jeltsch or Heinrich Apfelmus will help us come up with a practical solution.

Advertisement

Using Bullet physics with an FRP approach (part 1)

Earlier this year we were experimenting with creating an FRP-style API on top of the Bullet physics engine. As a result, we developed a simple example scene using Elerea, which is now available in the project repository. This post is the first in a series to discuss the example in detail. We start the tour by introducing the libraries used.

The raw Bullet API

Bullet is a C++ library, which makes it tricky to drive from Haskell. Csaba solved the problem by generating a plain C wrapper around it, and created a Haskell binding for this wrapper. This provides us a nice steady base to build on. Programming against this interface feels very much like using Gtk2Hs. As an example, let’s see a slightly simplified variant of a function from the example used in mouse picking. In this function, we cast a ray into the world and return the closest dynamic rigid body it hit:

rayTarget :: Vec2 -> CameraInfo -> Vec2 -> Vec3

pickBody :: BtCollisionWorldClass bc => bc -> Vec2 -> CameraInfo -> Vec2 -> IO (Maybe (BtRigidBody, Vec3, Float))
pickBody dynamicsWorld windowSize cameraInfo mousePosition = do
    let rayFrom = cameraPosition cameraInfo
        rayTo = rayTarget windowSize cameraInfo mousePosition
    rayResult <- btCollisionWorld_ClosestRayResultCallback rayFrom rayTo
    btCollisionWorld_rayTest dynamicsWorld rayFrom rayTo rayResult
    hasHit <- btCollisionWorld_RayResultCallback_hasHit rayResult

    case hasHit of
        False -> return Nothing
        True -> do
            collisionObj <- btCollisionWorld_RayResultCallback_m_collisionObject_get rayResult
            isNotPickable <- btCollisionObject_isStaticOrKinematicObject collisionObj
            internalType <- btCollisionObject_getInternalType collisionObj
            case isNotPickable || internalType /= e_btCollisionObject_CollisionObjectTypes_CO_RIGID_BODY of
                True -> return Nothing
                False -> do
                    btCollisionObject_setActivationState collisionObj 4 -- DISABLE_DEACTIVATION
                    hitPosition <- btCollisionWorld_ClosestRayResultCallback_m_hitPointWorld_get rayResult
                    body <- btRigidBody_upcast collisionObj -- this would be null if the internal type is not CO_RIGID_BODY
                    return $ Just (body, hitPosition, len (hitPosition &- rayFrom))

We can think of the camera info as the transformation matrix that maps the world on the screen. The rayTarget function returns the endpoint of the ray corresponding to the mouse position on the far plane of the view frustum given all the relevant information. First we create a data structure (the ‘ray result callback’) to hold the result of the raycast, then perform the actual ray test. The value of hasHit is true if the segment between rayFrom and rayTo intersects any object in the physics world.

The C++ snippet corresponding to the first five lines of the do block might look something like this:

  btVector3 rayFrom = cameraPosition(cameraInfo);
  btVector3 rayTo = rayTarget(windowSize, cameraInfo, mousePosition);
  btCollisionWorld::ClosestRayResultCallback rayCallback(rayFrom, rayTo);
  dynamicsWorld->rayTest(rayFrom, rayTo, rayCallback);
  bool hasHit = rayCallback.hasHit();

If hasHit is true, we can get a reference to the object from rayResult, and check if it is of the right type. If everything matches, we return the body, the world position of the point where the ray hit it first, and the distance to that point from the camera. One of the nice things about this binding is that it uses the vector types from the vect library out of the box instead of exposing Bullet specific vectors, so all the spatial calculations are really easy to write without having to jump through extra hoops first.

Elerea basics

Elerea is an FRP library that’s primarily aimed at game programming. Its basic abstraction is the discrete generic stream – referred to as Signal –, and it can be used to describe fully dynamic data-flow networks. In essence, it provides a nice compositional way to define the state transformation during the simulation step. It also allows IO computations to be interspersed in this description, thereby providing lightweight (threadless) framework for cooperative multitasking.

There are two kinds of structures in Elerea. A value of type Signal a can be thought of as a time-varying value of type a. All the future values of the signal are fully determined by its definition, i.e. signals are context independent just as we expect from ordinary values in a pure functional language. The other structure is the SignalGen monad, which is a context where stateful signals are constructed. Mutually dependent signals can be defined thanks to the fact that SignalGen is an instance of MonadFix.

The basic idea behind SignalGen can be understood in terms of start times. Every context corresponds to a (discrete) moment on the global timeline, and every stateful signal constructed in that context is considered to start at that moment. However, signals themselves are defined in terms of the global time, which allows us to combine signals that originate from different contexts (e.g. create a numeric signal that’s the point-wise sum of two unrelated numeric signals). The API ensures that no signal can physically exist before its start time; theoretically, signals are undefined until that point.

When executing the resulting data-flow network, Elerea guarantees consistency by double buffering. The superstep that advances the network consists of two phases: read and commit. In the read phase every node queries its dependencies, and no-one changes their output. In the commit phase every node performs its state transition independently, based on the input from the read phase, so the inconsistent state is never observed anywhere in the system.

Attribute system

While the C-style API allows us to access all the functionalities, it’s not very comfortable to use. The biggest issue is its verbosity: all the names are fully qualified out of necessity, and each property of an object has to be set separately. Therefore, we took some inspiration from the glib attribute system used by Gtk2Hs, and implemented something similar in the example. An attribute is the pair of a getter and the corresponding setter for a given property:

data Attr o a = forall x . Attr !(o -> IO a) !(o -> a -> IO x)

We allow arbitrary return types for setters to make it easier to define attributes, since many Bullet setters return something other than unit. However, we discard these values for the time being, so it’s really just to avoid having to type ‘() <$’ so many times.

Attributes are brought to life through attribute operations, which specify how to calculate the value of the property. There are four possibilities: set a given value, transform the current value with a pure function, set a given value coming from an IO computation, and transform the current one with an IO computation. These are denoted as follows:

infixr 0 :=, :~, :!=, :!~

data AttrOp o = forall a . Attr o a := a
              | forall a . Attr o a :~ (a -> a)
              | forall a . Attr o a :!= IO a
              | forall a . Attr o a :!~ (a -> IO a)

We need existentials to hide the type of the property and only expose the type of the object, so we can easily create collections of attributes. Now we can define the functions that connect them to the actual objects:

set :: o -> [AttrOp o] -> IO o
set obj attrs = (>> return obj) $ forM_ attrs $ \op -> case op of
    Attr _      setter := x  -> setter obj x >> return ()
    Attr getter setter :~ f  -> getter obj >>= setter obj . f >> return ()
    Attr _      setter :!= x -> x >>= setter obj >> return ()
    Attr getter setter :!~ f -> getter obj >>= f >>= setter obj >> return ()

get :: o -> Attr o a -> IO a
get obj (Attr getter _) = getter obj 

make :: IO o -> [AttrOp o] -> IO o
make act flags = do
    obj <- act
    set obj flags
    return obj

This is a fully generic system nothing to do with Bullet at this point. The set function takes an object and updates all the attributes listed in its second argument. The get function is just a thin helper to retrieve the value of a property given the corresponding attribute. Finally, make is another thin helper that allows us to construct an object and set its attributes in a single step.

A simple example is the world transform property of collision objects. It can be read and written by the following two functions:

btCollisionObject_getWorldTransform
  :: BtCollisionObjectClass bc => bc -> IO Transform
btCollisionObject_setWorldTransform
  :: BtCollisionObjectClass bc => bc -> Transform -> IO Transform

Turning it into an attribute is as simple as constructing a pair out of the above functions:

worldTransform :: BtCollisionObjectClass o => Attr o Transform
worldTransform = Attr btCollisionObject_getWorldTransform
                      btCollisionObject_setWorldTransform

Given this definition, we can write set body [worldTransform := …] to update the transform, and get body worldTransform to retrieve it. In the next post we’ll see how to extend the above system to define attributes tied to Elerea signals, which allows us to define all their future values at the time of their creation, and how to use this capability to define a rigid body whose position is reset every time it collides with another given object.