Deriving a Domain Specific Language for purely functional 3D Graphics

In this paper, we present a simple yet powerful Domain Specific Language for working with three-dimensional scene data. We start by specifying the domain types (see DDD) of a example problem, and extend the domain model with functionality for rendering and interaction.

Our first example is a little drawing tool which allows users to draw polygons on a vertical plane centered in the 3D scene. Later, we will extend the program with functionality for picking and translating objects by using a Maya-style 3D controller.

Note that this document is written as F# literate script, i.e. this document is both, the paper and the implementation ;)

Domain Driven Design

Let us start with the domain model for polygons:

1: 
2: 
3: 
open Aardvark.Base // Aardvark.Base provides vector types

type Polygon = list<V3d>

Thus, a polygon is simple a immutable list of vectors (vertices). Next, we need a way to model polygons which are not yet fully defined. A mouse click extends these, and eventually they are finalized.

1: 
2: 
3: 
4: 
5: 
type OpenPolygon = {
    finishedPoints  : list<V3d> // points already added to the polygon
    cursor         : Option<V3d> (* the last point of the polygon which can still be modified. 
            Note that the last point of the polygon might be undefined (represented as None). *)
}

The Domain Model can be completed using a list of polygons in the scene, as well as one open polygon the user is currently working on.

1: 
2: 
3: 
4: 
type DrawingModel = {
    finished : list<Polygon>
    working  : Option<OpenPolygon>
}

Creating a visual representation for our model

The simplest way of specifying a visual representation for data is by specifying a function which maps from data to graphics. Since we aim for rendering our graphics using graphics hardware (OpenGL), we don't directly compute pixels for the data, but we map our domain model to an explicit description of the scene, which we can render efficiently. Aardvark uses the typical description of this sort, a scene graph with geometric primitives at the leaves.

Let us start with the type describing 3D entities in the scene:

1: 
2: 
3: 
4: 
5: 
type Primitive = 
    | Sphere      of center : V3d * radius : float
    | Cone        of center : V3d * dir : V3d * height : float * radius : float
    | Cylinder    of center : V3d * dir : V3d * height : float * radius : float
    | Quad        of Quad3d 

This type allows us to specify individual entities in a 3D scene.

Next let us extend the API to support many entities being packed together.

1: 
2: 
3: 
4: 
5: 
type Scene1 = 
        | Transform of Trafo3d * list<Scene1>
        | Colored   of C4b     * list<Scene1>
        | Render    of Primitive 
        | Group     of list<Scene1>

This definition allows us to describe scenes.

An example:

1: 
2: 
3: 
4: 
5: 
let scene =
    Transform ( Trafo3d.Translation(10.0,10.0,10.0), [
                  Render ( Sphere(V3d.OOO, 1.0))
                  Render ( Sphere(V3d.OOO, 0.1))
               ])

Which represents the following scene:

[todo image]

Thus, a visual representation for our polygon-sketching scene can be implemented as follows:

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
17: 
18: 
19: 
20: 
21: 
22: 
23: 
24: 
25: 
26: 
27: 
28: 
29: 
30: 
31: 
32: 
33: 
34: 
35: 
36: 
37: 
38: 
39: 
40: 
// curried version of Colored in order to nicely compose
let colored1 c xs = Colored(c,xs)
let transformed1 t x = Transform(t,[x])

let view1 (m : DrawingModel) : Scene1 =

    let groundPlane =
        [ Quad (Quad3d [| V3d(-1,-1,0); V3d(1,-1,0); V3d(1,1,0); V3d(-1,1,0) |]) |> Render ] 
        |> colored1 C4b.Gray

    let viewPolygon (p : list<V3d>) : Scene1 = 
        [ for edge in Polygon3d(p |> List.toSeq).EdgeLines do
            let v = edge.P1 - edge.P0
            yield Cylinder(edge.P0,v.Normalized,v.Length,0.03) |> Render
        ] |> Group

    let openPolygon =   
        match m.working with
            | None   -> [] // no open polygon -> just return empty list)
            | Some v -> [viewPolygon v.finishedPoints]

    let cursor =
        match m.working with
            | Some v when Option.isSome v.cursor -> 
                // if we have a last point (cursor)
                [ [ Sphere(V3d.OOO,0.1) |> Render ] 
                   |> colored1 C4b.Red
                   |> transformed1 (Trafo3d.Translation(v.cursor.Value))
                ]
            | _ -> [] // no working polygon or no cursor

    let polygons = 
        m.finished |> List.map viewPolygon

    Group [
        yield  groundPlane
        yield! openPolygon
        yield! cursor
        yield! polygons
    ]

Altough the function is rather verbose F# (many let bindings can be inlined), it precisely captures the semantics of the transformation. Next, we would like to implement interaction techniques. The user usually wants to issue commands to the program and observe the resulting effects.

In order to model interactions cleanly, let us introduce a union type modeling all possible interactions.

1: 
2: 
3: 
4: 
type DrawCommand =
    | ClosePolygon
    | AddPoint   of V3d
    | MoveCursor of V3d

Remember, our model is immutable. Therefore, adding a point to our model actually means computing a new model, which is the old model containing the new point.

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
17: 
18: 
19: 
20: 
21: 
22: 
23: 
let updateDrawing (m : DrawingModel) (cmd : DrawCommand) =
    match cmd with
        | AddPoint p -> // we want to add a point to our drawing model
            match m.working with // do we have a polygon we could add to point to?
                | Some v -> // yes we have, create a new OpenPolygon with our new point added and update the model
                    { m with working = Some { v with finishedPoints = p :: v.finishedPoints }}
                | None -> { m with working = Some { finishedPoints = [ p ]; cursor = None;  }}
        | ClosePolygon -> 
            match m.working with
                | None -> m // we have no polygon to close -> identity. the updated model is the old model
                | Some p -> 
                    { m with 
                        working = None // close a polygon. there is no more open polygon ...
                        finished = p.finishedPoints :: m.finished // ... and the formerly opened polygon is now part of the finished polygons
                    }
        | MoveCursor p -> // the last point of the current working polygon follows the mouse cursor
            match m.working with // check if we have a working polygon
                | None -> 
                    // start a new open polygon with our current cursor set to mouse position
                    { m with working = Some { finishedPoints = []; cursor = Some p }}
                | Some v -> 
                    // override current cursor position
                    { m with working = Some { v with cursor = Some p }}

Again, the function precisely captures the semantics of our update commands. Who generates these update commands?

ClosePolygon, for example, could be associated with a mouse click. This means that mouse clicks must produce 3D positions. But a mouse click doesn't usually produce anything, so what can we do? This is exactly the point where our clean API seems to get messy.

One common approach here is to define a picking manager which handles mouse events and translates the events to domain specific data (such as 3D positions). However, the scope and responsibilities of such a manager are often difficult to define, and an implementation using mutable/global state becomes chaotic.

In this work, we take a different approach inspired by the Elm Architecture. The key insight is to perform operations exactly at the points where all necessary information is at hand, or can be computed easily. Since we already defined a DSL for specifying 3D scenes, the obvious choice is to resolve our commands there! This leads to a clean seperation of concerns and encapsulation of state.

Let us take the expression which effectively creates the drawable 3D plane in our scene:

1: 
2: 
3: 
let groundPlane =
    [ Quad (Quad3d [| V3d(-1,-1,0); V3d(1,-1,0); V3d(1,1,0); V3d(-1,1,0) |]) |> Render ] 
    |> colored1 C4b.Gray

We have the domain model at hand, as well as specfic information such as 3D coordinates. In order to express pick operations here, we need to enrich our Scene representation with pick operations.

Let us first define an API for specifying picks. For our example, we need to handle clicks and mouse moves. Since we want to work with 3D data, our events should be equipped with 3D coordinates:

1: 
2: 
3: 
4: 
5: 
open Aardvark.Application // Aardvark.Application provides helpers for working with user inputs

type MouseEvent = 
    | Move of V3d 
    | Down of MouseButtons * V3d

Let us now define a type which describes the reaction of a mouse event in a generic manner. This means that the produced command message is a type argument for our function type.

1: 
type PickOperation<'msg> = MouseEvent -> Option<'msg>

This abstraction here leads the way to specifying message-agnostic 3D scenes. As a consequence, our scene type now carries a type argument representing the type of message which can be produced by the scene itself.

Additionally we equip our render constructor with the capability of producing pick commands.

1: 
2: 
3: 
4: 
5: 
6: 
// scene produces messages of type 'msg
type Scene<'msg> = 
        | Transform of Trafo3d * seq<Scene<'msg>>
        | Colored   of C4b     * seq<Scene<'msg>>
        | Render    of list<PickOperation<'msg>> * Primitive // new bits in here
        | Group     of seq<Scene<'msg>>

Let us define functions which provide curried constructions of our message type. This comes in handy soon:

1: 
2: 
3: 
4: 
5: 
6: 
let transform t xs = Transform(t,xs)
let transform' t x = Transform(t,[x])
let translate x y z xs = Transform(Trafo3d.Translation(x,y,z),xs)
let colored c xs = Colored(c,xs)
let render picks primitive = Render(picks,primitive)
let group xs = Group xs

We can check our design by implementing a visual representation of our drawing plane and let us associate a pick operation to it.

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
17: 
18: 
19: 
20: 
let drawGroundPlane =
    Quad (Quad3d [| V3d(-1,-1,0); V3d(1,-1,0); V3d(1,1,0); V3d(-1,1,0) |]) 
        |> render [ 
                // Pick operations for moving the cursor.
                // if the ground plane is hit by a mouse move event, construct the MoveCursor command
                (fun evt -> 
                    match evt with
                        | Move p -> Some (MoveCursor p)
                        | _ -> None
                )
                (fun evt -> 
                    match evt with
                        | Down(MouseButtons.Left,p) -> Some (AddPoint p)
                        | _ -> None
                )
                (fun evt -> 
                    match evt with
                        | Down(MouseButtons.Right,_) -> Some ClosePolygon
                        | _ -> None)
        ]

The above code is a pure expression, i.e. no side effects are involved. The value simply stores first class functions. When provided with a world space pick point, and the description of a mouse event, they produce a command. Although rather nice, the code is still repetitive.

Some helpers will make the function look nicer.

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
// some predicates which take in a mouseEvent and check whether the mouse event is interesting
module Event =
    // "function" is the combined lambda/match syntax
    let move : MouseEvent -> bool = function Move _ -> true | _ -> false
    let down = function Down _ -> true | _ -> false       
    let down' p = function Down(p',_) when p = p' -> true | _ -> false 
    let leftDown = down' MouseButtons.Left
    let rightDown = down' MouseButtons.Right
    let position = function Move s -> s | Down(_, s) -> s

// Look back on the repetitive code. 
// One can see that all PickOperations perform some filtering/matching on the
// observed input. 

// This pattern can be catpured by a higher order function such as:
let on (p : MouseEvent -> bool) (r : V3d -> 'msg) (k : MouseEvent) = if p k then Some (r (Event.position k)) else None

Applied to our original drawGroundPlane, the code duplication disappears:

1: 
2: 
3: 
4: 
5: 
6: 
7: 
let drawGroundPlane2 =
    Quad (Quad3d [| V3d(-1,-1,0); V3d(1,-1,0); V3d(1,1,0); V3d(-1,1,0) |]) 
        |> render [ 
                on Event.move      (fun p -> MoveCursor p)            
                on Event.leftDown  (fun p -> AddPoint p)
                on Event.rightDown (fun _ -> ClosePolygon) 
           ]

Eta reduced:

1: 
2: 
3: 
4: 
5: 
6: 
7: 
let drawGroundPlane3 =
    Quad (Quad3d [| V3d(-1,-1,0); V3d(1,-1,0); V3d(1,1,0); V3d(-1,1,0) |]) 
        |> render [ 
                on Event.move      MoveCursor            
                on Event.leftDown  AddPoint 
                on Event.rightDown (fun _ -> ClosePolygon) 
           ]

Since moving cursors, adding points and closing polygons are the only operations in our example, our implementation is complete.

Our final DSL

Next we define a type which captures two functions and a domain model:

1: 
2: 
3: 
4: 
5: 
6: 
type App<'model,'msg,'view> =
    {
        initial   : 'model
        update    : 'model   -> 'msg -> 'model
        view      : 'model   -> 'view
    }

In that context, we always work with views of the type Scene<'msg>. Therefore this type alias makes sense:

1: 
type ThreeDApp<'model,'msg> = App<'model,'msg,Scene<'msg>>

We refactor the app instance for our polygon-sketching example, including the view function, a bit:

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
17: 
18: 
19: 
20: 
21: 
22: 
23: 
24: 
25: 
26: 
27: 
28: 
29: 
30: 
31: 
32: 
33: 
34: 
35: 
module Pick =
    let ignore = [] // empty list of pick operations shorthand


let viewDrawing (m : DrawingModel) =
    let viewPolygon (p : list<V3d>) =
        [ for edge in Polygon3d(p |> List.toSeq).EdgeLines do
            let v = edge.P1 - edge.P0
            yield Cylinder(edge.P0,v.Normalized,v.Length,0.03) |> render Pick.ignore 
        ] |> group

    group [
        yield [ Quad (Quad3d [| V3d(-1,-1,0); V3d(1,-1,0); V3d(1,1,0); V3d(-1,1,0) |]) 
                    |> render [ 
                            on Event.move MoveCursor
                            on Event.leftDown  AddPoint 
                            on Event.rightDown (constF ClosePolygon) // constF == fun a -> fun _ -> a
                        ] 
                ] |> colored C4b.Gray
        match m.working with
            | Some v when v.cursor.IsSome -> 
                yield 
                    [ Sphere(V3d.OOO,0.1) |> render Pick.ignore ] 
                        |> colored C4b.Red
                        |> transform' (Trafo3d.Translation(v.cursor.Value))
                yield viewPolygon (v.cursor.Value :: v.finishedPoints)
            | _ -> ()
        for p in m.finished do yield viewPolygon p
    ]

let drawingApp = { 
    initial = { finished = []; working = None }
    update  = updateDrawing
    view    = viewDrawing
}

It's no accident. Our final formulation matches the formulation of Elm applications!

In other words, we just reinvented the core part of the Elm Architecture!

An implementation for our API using the aardvark rendering engine.

Proof of Concept: Rendering values of type Scene

We want to render the scene using the Aardvark rendering engine.

To achieve this, there are several possibilities: Manually compute Render Objects for our scene. Create a Scene Graph which describes our scene in rendering terms.

In this work we chose the latter. Please note that the implementation is far from optimal, but serves as a simple base that we can optimize subsequently.

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
17: 
18: 
19: 
20: 
21: 
22: 
23: 
24: 
25: 
26: 
27: 
28: 
29: 
30: 
31: 
32: 
[<AutoOpen>]
module ConvertToSceneGraph =

    open Aardvark.SceneGraph

    type State = { trafo : Trafo3d; color : C4b }

    let toSg (scene : Scene<'msg>) : ISg = 
        let rec toSg (s : State) (scene : Scene<'msg>) =
            match scene with
                | Transform(t,children) -> children |> Seq.map ( toSg { s with trafo = s.trafo * t } ) |> Sg.group'
                | Colored(c,children) -> children |> Seq.map ( toSg { s with color = c } ) |> Sg.group'
                | Render (_, Cone(center,dir,height,radius)) -> 
                    IndexedGeometryPrimitives.solidCone center dir height radius 10 s.color 
                    |> Sg.ofIndexedGeometry |> Sg.transform s.trafo
                | Render (_, Cylinder(center,dir,height,radius)) -> 
                    IndexedGeometryPrimitives.solidCylinder center dir height radius radius 10 s.color 
                    |> Sg.ofIndexedGeometry |> Sg.transform s.trafo
                | Render (_, Sphere(center,radius)) ->
                    IndexedGeometryPrimitives.solidSubdivisionSphere (Sphere3d(center,radius)) 5 s.color 
                    |> Sg.ofIndexedGeometry |> Sg.transform s.trafo
                | Render(_, Quad(p)) ->
                    IndexedGeometry(
                            IndexedGeometryMode.TriangleList, [| 0; 1; 2; 0; 2; 3 |], 
                            SymDict.ofList [
                                DefaultSemantic.Positions, p.Points |> Seq.map V3f |> Seq.toArray :> Array; 
                                DefaultSemantic.Colors,  Array.replicate 4 s.color  :> System.Array; 
                                DefaultSemantic.Normals, Array.replicate 4 (p.Edge03.Cross(p.P2-p.P0)).Normalized :> System.Array
                            ], SymDict.empty)  |> Sg.ofIndexedGeometry |> Sg.transform s.trafo
                | Group xs -> xs |> Seq.map ( toSg s) |> Sg.group'

        toSg { trafo = Trafo3d.Identity; color = C4b.White } scene

The function toSg is a mapping from our scene representation to the Aardvark.Rendering Scene Graph.

Now we can render scenes. Next, we implement a simple picking scheme which computes command messages out of mouse clicks:

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
17: 
18: 
19: 
20: 
21: 
22: 
23: 
24: 
25: 
26: 
27: 
28: 
29: 
30: 
31: 
32: 
33: 
34: 
35: 
36: 
37: 
38: 
module Picking =
    // implement ray - object intersections for all renderable primitives:
    let hitPrimitive (p : Primitive) (trafo : Trafo3d) (ray : Ray3d) action =
        let mutable ha = RayHit3d.MaxRange
        match p with
            | Sphere(center,radius)-> 
                let transformed = trafo.Forward.TransformPos(center)
                let mutable ha = RayHit3d.MaxRange
                if ray.HitsSphere(transformed,radius,0.0,Double.PositiveInfinity, &ha) then
                    [ha.T, action]
                else []
            | Cone(center,dir,height,radius) | Cylinder(center,dir,height,radius) -> 
                let cylinder = Cylinder3d(trafo.Forward.TransformPos center,trafo.Forward.TransformPos (center+dir*height),radius)
                let mutable ha = RayHit3d.MaxRange
                if ray.Hits(cylinder,0.0,Double.MaxValue,&ha) then
                    [ha.T, action]
                else []
            | Quad q -> 
                let transformed = Quad3d(q.Points |> Seq.map trafo.Forward.TransformPos)
                if ray.HitsPlane(Plane3d.ZPlane,0.0,Double.MaxValue,&ha) then [ha.T, action]
                else []

    // given a ray and a scene -> perform a PickOperation.
    let pick (r : Ray3d) (s : Scene<'msg>)  =
        let rec go (state : State) s = 
            match s with    
                // collect pick operations for all children
                | Group xs -> xs |> Seq.toList |>  List.collect (go state)
                | Transform(t,xs) -> xs |> Seq.toList |> List.collect (go { state with trafo = state.trafo * t })
                | Colored(_,xs) -> xs |> Seq.toList |> List.collect (go state)
                | Render(action,p) -> 
                    // do the actual work
                    hitPrimitive p state.trafo r action
        match s |> go { trafo = Trafo3d.Identity; color = C4b.White } with
            | [] -> []
            | xs -> 
                // sort PickOperations by camera distance
                xs |> List.filter (not << List.isEmpty << snd) |>  List.sortBy fst 

Up to now, all presented functions are pure! For running the application, however, we need one single (!) side effecting function.

In Aardvark.Rendering Scene Graphs are compiled into an IRenderTask. This is then assigned to an IRenderControl, which displays the result.

The following code runs the evaluation of Elm-style program logic (the "Elm loop"), and attaches the 3D app to a IRenderControl.

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
17: 
18: 
19: 
20: 
21: 
22: 
23: 
24: 
25: 
26: 
27: 
28: 
29: 
30: 
31: 
open Aardvark.Base.Incremental
open Aardvark.SceneGraph

// note: this function contains side effects. we just left the functional programming world!
let createApp (ctrl : IRenderControl) (camera : IMod<Camera>) (app : App<'model,'msg, Scene<'msg>>) = 

    let mutable model = app.initial
    let view = Mod.init (app.view model)
    let sceneGraph = view |> Mod.map ConvertToSceneGraph.toSg |> Sg.dynamic

    let updateScene (m : 'model)  =
        let newView = app.view m
        transact (fun _ -> 
            view.Value <- newView
        )

    let handleMouseEvent (createEvent : V3d -> MouseEvent) =
        let ray = ctrl.Mouse.Position |> Mod.force  |> Camera.pickRay (camera |> Mod.force) 
        match Picking.pick ray view.Value with
            | [] -> ()
            | (d,f)::_ -> 
                for msg in f do
                    match msg (createEvent (ray.GetPointOnRay d)) with
                        | Some r -> model <- app.update model r
                        | _ -> ()
        updateScene model 

    ctrl.Mouse.Move.Values.Add(fun _-> handleMouseEvent MouseEvent.Move) 
    ctrl.Mouse.Down.Values.Add(fun p -> handleMouseEvent ((curry MouseEvent.Down) p))
	
    sceneGraph

This concludes our first implementation. Let us try to run our app:

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
17: 
18: 
19: 
open Aardvark.Base.Rendering
open Aardvark.Application.WinForms
let app = new OpenGlApplication()
let win = app.CreateSimpleRenderWindow()

let frustum = win.Sizes |> Mod.map (fun s -> Frustum.perspective 60.0 0.1 10.0 (float s.X / float s.Y))
let cameraView = CameraView.lookAt (V3d.III*3.0) V3d.OOO V3d.OOI
let camera = 
    frustum |> Mod.map (fun f -> Camera.create cameraView f) 

let sg = createApp win camera drawingApp

win.RenderTask <- 
    win.Runtime.CompileRender(win.FramebufferSignature,
        sg 
         |> Sg.effect [DefaultSurfaces.trafo |> toEffect; DefaultSurfaces.simpleLighting |> toEffect]
    )

win.Run()

Comparison to Related Work and Analysis of the Approach

In interactive graphics applications, the common approach is to map the domain model into some domain specific representation. Whenever a user input and the associated interactions lead to changes in the model, those changes need to be applied to the application state and the graphics representation (e.g. the scene graph). This approach puts the burden of synchronizing application state and graphics state on the application programmer, as found by Tobler 2011.

Where does the synchronization code go? There are basically two approaches:

  • Move all state including domain logic into the scene representation
  • Store deep references into the graphics representation and modify them on change

In Tobler's work, a semantic scene graph serves as model, and a rendering scene graph (view), including rendering state, is generated on the fly while traversing the semantic graph. Since the semantic scene graph serves as domain model description language, all domain modelling needs do be done directly in the semantic scene graph.

However versatile, domain logic which is not easily implemented as graph traversal poses difficulties.

In particular, cross cutting concerns (e.g. game objects need to modify other game objects far away in the graph) result in a lot of graph searching for the appropriate nodes. When optimizing away this search effort, the scene representation approach gradually converges toward the reference-keeping approach. Graphics entities, or global state, increasingly keep references on modifiable cells in order to be able to update those immediately.

The main subject of our design pattern is to not use any graphics specific state at all. The graphics representation is entirely recomputed after each domain model modification instead. This completely eliminates the need to track state in the graphics representation, but the trivial implementation is very inefficent.

Can this model be implemented efficiently?

Towards an efficient implementation

Let us summarize how our Elm-style polygon-sketching application performs updates. First, we apply the view function to the initial model, producing a value of type Scene<_>. Next, we use a subscription on potential mouse events, which, when fired, traverses the scene and collects all potential PickOperations. Each pick operation potentially yields a message, which is fed into the update function, which recomputes the model.

Feeding back this model to our view function ties the knot. We receive our final interaction loop.

Let us investigate the involved functions and their runtime behavior:

  • view is linear in the size of the model (independent of the real change).
  • in the worst case, each update message touches every single entity in the model, resulting in linear runtime. In that case, the change really is of that size, i.e. a mutable update has O(n) as well. In practise however, operations often affect a single value deeply nested in the immutable structure, resulting in logarithmic runtime and memory cost. Accordingly, for updating immutable domain models we achieve log(n) blowup compared to a mutable implementation.

Update cannot be optimized in the purely functional case.

Looking at the view function, however, we identify that the function is repeatedly invoked with an almost identical input.

Incremental Evaluation helps they said

Incremental evaluation, as used in Aardvark, can be used to incrementalize purely functional algorithms. Conforming to the provided API, all inputs need to be wrapped into ModRef<_> cells. Given a set of modifiable input cells, functions can be implemented by utilizing combinator functions, such as Mod.map or the adaptive Computation Expression. These functions become agnostic to input value changes:

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
17: 
// Adaptively compute scene for input value of type cursor
let cursorGeometry (hasCursor : IMod<Option<V3d>>) : IMod<list<Scene<DrawCommand>>> = 
    adaptive {
            let! hasCursor = hasCursor
            match hasCursor with    
                | None -> return []
                | Some c -> 
                   return [[ Sphere(V3d.OOO,0.1) |> render Pick.ignore ] 
                            |> colored C4b.Red
                            |> transform' (Trafo3d.Translation(c))]
    }

let hasCursor = Mod.init None
let adaptiveScene = cursorGeometry hasCursor
let sceneWithDisabledCursor = adaptiveScene |> Mod.force // compute scene with current input state
transact (fun _ -> hasCursor.Value <- Some V3d.OOI) // change input state to have a cursor
let sceneWithCursor = adaptiveScene |> Mod.force // compute scene with current input state

From a high level perspective, our incremental system has the following features:

  • Inputs can be defined as modifiable cells
  • Purely functional algorithms can be formulated on top of such modifiable cells
  • The outpus of the algorithm can be computed by using Mod.force
  • The inputs can be changed by using transact. Subsequent calls to Mod.force will return a value consistent with the current input values.

Thus, incremental evaluation does NOT provide us with a solution to our view function efficiency problem. We are working with purely functional input data. The entire domain model is new after a modification, meaning that our inputs alone will never be modified without everything else. This makes incremental evaluation infeasible.

As we discovered in practise, incremental evaluation can greatly speed up rendering performance. However, from an engineering point of view, programs quickly become large and interactions between various value changes complex (comparable to callback hell).

In order to utilize incremental evaluation, we need to map our purely functional model to a modifiable one. This allows us to perform updates as specific, targeted changes, which in turn can be used by the incremental evaluation system.

Mapping immutable values to mutable data sounds plausible. But where should this conversion occur?

While fablish and web frameworks use immutable data until the final rendering phase, we chose to map immutable values to mutable data prior to scene description generation. The rationale behind this is:

  • The domain model is relatively small compared to a scene description. Working with a mutable scene description is more efficient.
  • Typically, domain models are built on simple datatypes consisting of records and similar things. These might be easier to work with than general purpose scene descriptions.

Unpersisting data structures

Consider the transition of a record from immtuable to modifiable:

1: 
2: 
3: 
4: 
// Immutable data we would like to work on
type ImmutableData1 = { value : int }
// Modifiable data the rendering system would like to work on
type MutableData1 = { mvalue : IModRef<int> }

ImmutableData1 and MutableData1 are structurally equal, with all leaf fields wrapped into modifiable cells. //what? please rephrase.

How can we implement a procedure that applies immutable data changes into the mutable variant as update?

When immutable changes are detected, updates must be performed onto the according mutable fields. For records containing primitive values, the procedure boils down to traversing the data structure and applying new values to their mutable counterparts.

The problem arises with set data structures. In order to associate old entries in the mutable data with new values in the immutable set, some artificial references need to be introduced.

In this setup we propose to use integer values wrapped in a container class:

1: 
2: 
3: 
4: 
5: 
6: 
7: 
8: 
9: 
module IDs =
    open System.Threading // for Interlocked.Increment

    [<AllowNullLiteral>]
    type Id() =
        static let mutable current = 0
        let id = Interlocked.Increment(&current)
        static member New = Id()
        override x.ToString() = sprintf "Id %d" id

Let us now derive immutable and mutable models for our polygon-sketching app:

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
17: 
18: 
19: 
20: 
21: 
22: 
23: 
24: 
25: 
26: 
27: 
28: 
29: 
30: 
31: 
32: 
33: 
type OpenPolygon2 = {    
    finishedPolys  : list<V3d> 
    cursor         : Option<V3d> 
} 

type DrawingModel2 = {
    id : Id
    finished : pset<Polygon>
    working  : Option<OpenPolygon>
} 

type MDrawingModel2 = {
    original : DrawingModel2
    finished : cset<Polygon> 
    working  : ModRef<Option<OpenPolygon>>
}

let unpersist (m : DrawingModel2) : MDrawingModel2 =
    {
        original = m
        finished = CSet.ofSeq m.finished
        working = Mod.init m.working
    }

let apply (m : MDrawingModel2) (newModel : DrawingModel2) =
    transact (fun _ -> 
        let added = newModel.finished |> Seq.filter (not << m.finished.Contains)
        let removed = m.finished |> Seq.filter  (not << newModel.finished.Contains)
        for add in added do m.finished.Add add |> ignore
        for rem in removed do m.finished.Remove rem |> ignore
        //...
        ()
    )

Such a transformation seems to be rather mechanical. It can be formalized into the following procedure:

  • Equip each immutable domain type with an identifier (to be used for nested changes in sets)
  • For each domain type, create an associated mutable version. It contains one extra field which points to the immutable structure, and:
    • for each field which is a domain type, use the mutable variant of the domain type in the mutable version of the parent structure
    • for each primitive field, create a field which wraps the original value in a Mod
    • for each field of type set or list, generate a data structure which tracks immutable references and allows to efficiently merge an immutable representation of the set/list into the mutable version

This translation sheme can be implemented as compiler plugin. For the sake of completeness we present the compilation result for our drawing model (We use the DomainType attribute as a hint for the plugin to handle this type as domain type):

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
17: 
18: 
19: 
20: 
21: 
22: 
23: 
24: 
25: 
26: 
27: 
28: 
29: 
30: 
31: 
32: 
33: 
34: 
35: 
36: 
37: 
38: 
39: 
40: 
41: 
42: 
43: 
44: 
45: 
46: 
47: 
48: 
49: 
50: 
// original user written model
module SimpleDrawingApp =

    type Polygon = list<V3d>

    type OpenPolygon = {
        cursor         : Option<V3d>
        finishedPoints : list<V3d>
    }
    
    [<DomainType>]
    type Model = {
        finished : pset<Polygon>
        working  : Option<OpenPolygon>
    }

// under-the-hoood compiled variant for the domain model
module SimpleDrawingAppGenerated = 
    type Polygon = list<V3d>
    
    type OpenPolygon =  
        { cursor : Option<V3d>
          finishedPoints : list<V3d> }
    
    [<DomainType>]
    type Model = 
        { mutable _id : Id
          finished : pset<Polygon>
          working : Option<OpenPolygon> }
        
        member x.ToMod(reuseCache : ReuseCache) = 
            {   _original = x
                mfinished = ResetSet(x.finished)
                mworking = Mod.init (x.working) }
        
        interface IUnique with
            
            member x.Id 
                with get () = x._id
                and set v = x._id <- v
    
    and [<DomainType>] MModel = 
        { mutable _original : Model
          mfinished : ResetSet<Polygon>
          mworking : ModRef<Option<OpenPolygon>> }
        member x.Apply(arg0 : Model, reuseCache : ReuseCache) = 
            if not (System.Object.ReferenceEquals(arg0, x._original)) then 
                x._original <- arg0
                x.mfinished.Update(arg0.finished)
                x.mworking.Value <- arg0.working

The mutable model allows us to implement an incremental variant of the view function.

Our immutable scene representation, as-is, cannot express inner changes efficiently. As an example, consider the constructor for scene transformations: val Transform : Trafo3d * seq<Scene1> -> Scene<'msg> In order to efficiently handle trafo changes, the following signature is required: val Transform : IMod<Trafo3d> * aset<Scene1> -> Scene<'msg>> An incremental version of the scene data type can be derived by replacing all immutable values with their modifiable counterparts:

1: 
2: 
3: 
4: 
5: 
type Scene2 = 
        | Transform of IMod<Trafo3d> * aset<Scene2>
        | Colored   of IMod<C4b>     * aset<Scene1>
        | Render    of Primitive 
        | Group     of aset<Scene1>

In our implementation, we chose a different representation.

Instead of using a discriminated union, we prefer to use the extensible (regarding data types) OOP approach found in Aardvark.Rendering. We can directly integrate with the Aardvark Scene Graph this way:

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
17: 
module AdaptiveScene =
    open Aardvark.SceneGraph

    type ISg<'msg> = inherit ISg // ISg comes from Aardvark.SceneGraph


    type Group<'msg>(xs : aset<ISg<'msg>>) =
        interface ISg<'msg>
        interface IGroup with
            member x.Children = xs |> ASet.map (fun a -> a :> ISg)
        member x.Children = xs

    type Render<'msg>(xs : Primitive) =
        interface ISg<'msg>
        member x.Primitive = xs

    //...

The Aardvark Scene Graph implementation is based on Attribute Grammars. We can extend the Aardvark Scene Graph by defining additional Ag-rules for our types dynamically. We augment our type ISg<'msg> with semantic functions such as:

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
module AgExtension =
    open Aardvark.Base.Ag
    open Aardvark.SceneGraph.Semantics
    open AdaptiveScene

    [<Semantic>]
    type LeafSemantics() =
        member x.RenderObjects(l : Render<'msg>) =
            match l.Primitive with
                | Sphere(center,radius) -> 
                    Sg.sphere 5 (l?InhColor) (Mod.constant radius) |> Sg.transform (Trafo3d.Translation center)
                    |> Semantic.renderObjects
                | _ -> failwith "..."

This translates our ISg<'msg> into Aardvark ISg nodes whenever their RenderObjects semantic is requested.

The complete implementation of the scene graph nodes can be found here.

An efficient version of the drawing application

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
17: 
18: 
19: 
20: 
21: 
22: 
23: 
24: 
25: 
26: 
27: 
28: 
29: 
30: 
31: 
32: 
33: 
34: 
35: 
36: 
37: 
38: 
39: 
40: 
41: 
42: 
43: 
44: 
45: 
46: 
47: 
48: 
49: 
50: 
51: 
52: 
53: 
54: 
55: 
56: 
57: 
58: 
59: 
60: 
61: 
62: 
63: 
64: 
65: 
66: 
67: 
68: 
69: 
70: 
71: 
72: 
73: 
74: 
75: 
76: 
77: 
78: 
79: 
80: 
81: 
82: 
83: 
module FinalDrawingApp =

    open Aardvark.ImmutableSceneGraph
    open Aardvark.Elmish
    open Primitives

    open SimpleDrawingAppGenerated


    type Action =
        | ClosePolygon
        | AddPoint   of V3d
        | MoveCursor of V3d

    let update e (m : Model) (cmd : Action) =
        match cmd with
            | ClosePolygon -> 
                match m.working with
                    | None -> m
                    | Some p -> 
                        { m with 
                            working = None 
                            finished = PSet.add p.finishedPoints m.finished
                        }
            | AddPoint p ->
                match m.working with
                    | None -> { m with working = Some { finishedPoints = [ p ]; cursor = None;  }}
                    | Some v -> 
                        { m with working = Some { v with finishedPoints = p :: v.finishedPoints }}
            | MoveCursor p ->
                match m.working with
                    | None -> { m with working = Some { finishedPoints = []; cursor = Some p }}
                    | Some v -> { m with working = Some { v with cursor = Some p }}


    let viewPolygon (p : list<V3d>) =
        [ for edge in Polygon3d(p |> List.toSeq).EdgeLines do
            let v = edge.P1 - edge.P0
            yield Primitives.cylinder edge.P0 v.Normalized v.Length 0.03 |> Scene.render Pick.ignore 
        ] |> Scene.group


    let view (m : MModel) = 
        let t =
           aset {
                yield [ Quad (Quad3d [| V3d(-1,-1,0); V3d(1,-1,0); V3d(1,1,0); V3d(-1,1,0) |]) 
                            |>  Scene.render [ 
                                 on Mouse.move MoveCursor
                                 on (Mouse.down' MouseButtons.Left)  AddPoint 
                                 on (Mouse.down' MouseButtons.Right) (constF ClosePolygon)
                               ] 
                      ] |>  Scene.colored (Mod.constant C4b.Gray)
                for p in m.mfinished :> aset<_> do yield viewPolygon p
                let! working = m.mworking
                match working with
                    | Some v when v.cursor.IsSome -> 
                        yield 
                            [ Sphere3d(V3d.OOO,0.1) |> Sphere |>  Scene.render Pick.ignore ] 
                                |> Scene.colored (Mod.constant C4b.Red)
                                |> Scene.transform' (Mod.constant <| Trafo3d.Translation(v.cursor.Value))
                        yield viewPolygon (v.cursor.Value :: v.finishedPoints)
                    | _ -> ()
            }
        Scene.agroup  t

    let viewScene (sizes : IMod<V2i>) (m : MModel) =
        let cameraView = CameraView.lookAt (V3d.III * 3.0) V3d.OOO V3d.OOI |> Mod.constant
        let frustum = sizes |> Mod.map (fun (b : V2i) -> Frustum.perspective 60.0 0.1 10.0 (float b.X / float b.Y))
        view m
            |> Scene.camera (Mod.map2 Camera.create cameraView frustum)
            |> Scene.effect [toEffect DefaultSurfaces.trafo; toEffect DefaultSurfaces.vertexColor; toEffect DefaultSurfaces.simpleLighting]


    let initial = { finished = PSet.empty; working = None; _id = null }

    let app s =
        {
            initial = initial
            update = update
            view = viewScene s
            ofPickMsg = fun _ _ -> []
            subscriptions = Aardvark.Elmish.Subscriptions.none
        }

Discussion

We ended up with an API for submitting changes to a domain model and evaluating a view function on that model. For efficiency reasons, we utilized adaptive functional programming in order to write one single view function which is agnostic to changes. Since the incremental system requires changes at inputs in order to perform necessary recomputations, we, at some point, need to translate changes in immutable data to reference cell mutations. This procedure can be automated and implemented as a compiler extension.

In other words: Previous work focused on feeding changes into a scene representation efficiently. Incremental evaluation is greatly beneficial (even indispensable) to those procedures. Although this is very efficient, keeping track of incremental computations and adaptive dependencies becomes difficult as complexity increases. On the other side, working with immutable updates on domain models is easy, but an efficient implementation is not tangible.

In this work we combine the two, and indeed we get the best of both. The immutable update mechanism can be seen as automatic, convenient input changer, while the incremental evaluation backend takes care of mapping updates efficiently to the underlying graphics hardware.

Refining the Model

External events

So far we only worked with mouse inputs and their interactions with 3D objects. In general, however, we often need to emit messages without user interaction, or due to the occurance of an external event. Elm extends its application pattern with an additional function. It allows subscriptions to be registered between the current model and sources of events.

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
17: 
18: 
19: 
20: 
21: 
22: 
23: 
24: 
25: 
26: 
27: 
28: 
29: 
30: 
31: 
32: 
module Subscriptions1 =

    type Sub<'msg> = 
        | TimeSub  of TimeSpan * (TimeSpan -> 'msg) 
        | KeyPress of (Keys -> Option<'msg>)
        | Many     of list<Sub<'msg>>

    let timeSub ts f = TimeSub(ts,f)

// todo subscription example

module Animation =

    open System
    open Aardvark.ImmutableSceneGraph
    open Aardvark.Elmish
    open Primitives

    type Model = { rotation : float; _id : Id }
    type MModel = { mrotation : ModRef<float>} // mutable model impl skipped

    type Msg = TimeStep of TimeSpan

    let update e (m : Model) (msg : Msg) =
        match msg with  
            | TimeStep t -> { m with rotation = m.rotation + t.TotalMilliseconds * 0.1 }
    
    let view (m : MModel) =
         [ Sphere3d(V3d.OOO,0.1) |> Sphere |>  Scene.render Pick.ignore ]  |> Scene.transform (m.mrotation |> Mod.map  Trafo3d.RotationZ) 

    let subscriptions (m : Model) : Subscriptions1.Sub<Msg> =
        Subscriptions1.timeSub (TimeSpan.FromMilliseconds 10.0) TimeStep

After each update, we purely functionally recompute the subscription set. Then we compute the difference between the current and the old subscription set. Unnecessary subscriptions can be removed safely, while new subscriptions are added where needed.

Subscriptions --- The observer pattern's new clothes?

At first, subscriptions look like a rather imperative pattern.

Traditional subscription-based techniques have severe flaws:

  • Subscriptions need to be registered, and they need to be unregistered after expiration. Subscribe in Rx has type: 'val subscribe : ('a -> unit) -> IDisposable' which already hints at the significant effort required for tracking subscriptions in application code.
  • Classic subscriptions compose by building up subscription networks, through which input events travel. Observing results from such networks can only be accomplished by registering (mutating) actions. Whenever an input changes, the change propagates through subscription chains. Eventually, actions are triggered to write new values into application state. Since change propagation in such networks is performed eagerly, the program can be assigned with faithful semantics. But understanding such networks statically, or even debugging their runtime behavior, can be extremely tricky.

In our design pattern, the set of subscriptions is recomputed automatically after each update. This means that the problem of "cleaning up" subscriptions completely disappears. Secondly, subscriptions in our model are purely functional. They build up lists of messages representing their effects, which in turn are fed back into the update function. This greatly improves debugging, since the results of external events can be observed at a single point in code instead of various points scattered in the domain logic.

Depth ordering of Pick Events

In our original implementation, we always used the frontmost pick and ignored all further hits along the pick ray. Howewer, it is often necessary to compute all pick occurences along the pick ray. The user might want to move polygon corners around by click-dragging. When hovering over control points of a polygon, the pick must go "through" the control point geometry and hit the ground plane below. This can be accomplished by a simple extension to the pick API:

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
type Transparency = Solid | PickThrough
type PickOperation2<'msg> = (V3d -> Option<'msg>) * Transparency

let rec depthTest (xs : list<float*PickOperation2<'msg>>) =
    match xs |> List.sortBy fst with // sort picks by distance
        | [] -> [] // no picks
        | (d1,(f1,Solid))::(d2,(f2,Solid))::rest when d1 = d2 -> 
            // two solid picks, equal distance, use both
            (d1,(f1,Solid)) ::(d2,(f2,Solid)) :: depthTest rest
        | (d, (f,Solid))::_ ->      
            // solid pick, stop here
            [d, (f,Solid)]
        | (d, (f,PickThrough))::xs -> 
            // transparent object, take and pick test further
            (d, (f,PickThrough)) :: depthTest xs

Asynchronous computations

One main design guideline when designing the API for pick operations was to have necessary information available at one point in the code. Considering commands which trigger long-running or computationally intensive tasks, the best place for implementation is in the update function, where the message itself and the immutable domain model are available. However, performing long-running computations in the update function directly stalls the application. Therefore, to express such operations, we introduce the Cmd type and an additional argument to the update function.

 1: 
 2: 
 3: 
 4: 
 5: 
 6: 
 7: 
 8: 
 9: 
10: 
11: 
12: 
13: 
14: 
15: 
16: 
17: 
18: 
19: 
20: 
21: 
22: 
23: 
24: 
25: 
26: 
27: 
28: 
29: 
30: 
31: 
32: 
module EnvExample =

    open System
    open Aardvark.ImmutableSceneGraph
    open Aardvark.Elmish
    open Primitives
    open Fablish.CommonTypes // env is defined here

    type Model = { image : list<PixImage>; }

    type Msg = 
        | LoadImages of list<string>
        | ImagesLoaded of list<PixImage> // pixImage is a loaded image
        | Progress of float

    let loadImage (p : list<string>) (e : Env<Msg>) =
        async {
            let cnt = List.length p
            let images =
                p |> List.mapi (fun i p -> 
                    async { return Progress (float i / float cnt) } |> Cmd |> e.run
                    PixImage.Create(p)
                )
            return ImagesLoaded images
        }
    let update (env : Env<Msg>) (m : Model) (msg : Msg) =
        match msg with 
            | LoadImages paths -> 
                loadImage paths env |> Cmd |> env.run
                m
            | ImagesLoaded img -> { m with image = img }
            | Progress _ -> m

Further examples

Implementing a transformation controller

  1: 
  2: 
  3: 
  4: 
  5: 
  6: 
  7: 
  8: 
  9: 
 10: 
 11: 
 12: 
 13: 
 14: 
 15: 
 16: 
 17: 
 18: 
 19: 
 20: 
 21: 
 22: 
 23: 
 24: 
 25: 
 26: 
 27: 
 28: 
 29: 
 30: 
 31: 
 32: 
 33: 
 34: 
 35: 
 36: 
 37: 
 38: 
 39: 
 40: 
 41: 
 42: 
 43: 
 44: 
 45: 
 46: 
 47: 
 48: 
 49: 
 50: 
 51: 
 52: 
 53: 
 54: 
 55: 
 56: 
 57: 
 58: 
 59: 
 60: 
 61: 
 62: 
 63: 
 64: 
 65: 
 66: 
 67: 
 68: 
 69: 
 70: 
 71: 
 72: 
 73: 
 74: 
 75: 
 76: 
 77: 
 78: 
 79: 
 80: 
 81: 
 82: 
 83: 
 84: 
 85: 
 86: 
 87: 
 88: 
 89: 
 90: 
 91: 
 92: 
 93: 
 94: 
 95: 
 96: 
 97: 
 98: 
 99: 
100: 
101: 
102: 
103: 
104: 
105: 
106: 
107: 
108: 
109: 
110: 
111: 
112: 
113: 
114: 
115: 
116: 
117: 
118: 
119: 
120: 
121: 
122: 
123: 
124: 
125: 
126: 
127: 
128: 
129: 
module TranslateController =

    open Aardvark.ImmutableSceneGraph
    open Aardvark.ImmutableSceneGraph.Scene
    open Primitives
    open Aardvark.Elmish

    open Scratch.DomainTypes

    [<CompilationRepresentation(CompilationRepresentationFlags.ModuleSuffix)>]
    module Axis =
        let dir = function | X -> V3d.XAxis | Y -> V3d.YAxis | Z -> V3d.ZAxis
        let moveAxis (trafo : Trafo3d) = function
            | X -> Plane3d(trafo.Forward.TransformDir V3d.OOI, trafo.Forward.TransformPos V3d.OOO)
            | Y -> Plane3d(trafo.Forward.TransformDir V3d.OOI, trafo.Forward.TransformPos V3d.OOO)
            | Z -> Plane3d(trafo.Forward.TransformDir V3d.OIO, trafo.Forward.TransformPos V3d.OOO)

    type Action = 

        // hover overs
        | Hover           of Axis * V3d
        | NoHit       
        | MoveRay         of Ray3d

        // translations    
        | Translate       of Axis * V3d
        | EndTranslation 

        | ResetTrafo

    open TranslateController

    let hasEnded a =
        match a with
            | EndTranslation -> true
            | _ -> false

    let hover      = curry Hover
    let translate_ = curry Translate

    let initalModel = { hovered = None; activeTranslation = None; trafo = Trafo3d.Identity; _id = null }

    let initial =  { 
            scene = initalModel
            camera = Camera.create ( CameraView.lookAt (V3d.III*3.0) V3d.OOO V3d.OOI ) (Frustum.perspective 60.0 0.1 10.0 1.0)
            _id = null
        }


    let updateModel (m : TModel) (a : Action) =
        match a, m.activeTranslation with
            | NoHit, _             ->  { m with hovered = None; }
            | Hover (v,_), _       ->  { m with hovered = Some v}
            | Translate (dir,s), _ -> { m with activeTranslation = Some (Axis.moveAxis m.trafo dir, m.trafo.Backward.TransformPos s) }
            | EndTranslation, _    -> { m with activeTranslation = None;  }
            | MoveRay r, Some (t,start) -> 
                let mutable ha = RayHit3d.MaxRange
                if r.HitsPlane(t,0.0,Double.MaxValue,&ha) then
                    let v = (ha.Point - start).XOO
                    { m with trafo = Trafo3d.Translation (ha.Point - start) }
                else m
            | MoveRay r, None -> m
            | ResetTrafo, _ -> { m with trafo = Trafo3d.Identity }

    let update e (m : Scene) (a : Action) =
        let scene = updateModel m.scene a
        { m with scene = scene }

    let viewModel (m : MTModel) =
        let arrow dir = Cone(V3d.OOO,dir,0.3,0.1)

        let ifHit (a : Axis) (selection : C4b) (defaultColor : C4b) =
            adaptive {
                let! hovered = m.mhovered
                match hovered with
                    | Some v when v = a -> return selection
                    | _ -> return defaultColor
            }
            
        transform m.mtrafo [
                translate 1.0 0.0 0.0 [
                    [ arrow V3d.IOO |> render [on Mouse.move (hover X); on Mouse.down (translate_ X)] ] 
                        |> colored (ifHit X C4b.White C4b.DarkRed)
                ]
                translate 0.0 1.0 0.0 [
                    [ arrow V3d.OIO |> render [on Mouse.move (hover Y); on Mouse.down (translate_ Y)] ] 
                        |> colored (ifHit Y C4b.White C4b.DarkBlue)
                ]
                translate 0.0 0.0 1.0 [
                    [ arrow V3d.OOI |> render [on Mouse.move (hover Z); on Mouse.down (translate_ Z)] ] 
                        |> colored (ifHit Z C4b.White C4b.DarkGreen)
                ]

                [ cylinder V3d.OOO V3d.IOO 1.0 0.05 |> render [ on Mouse.move (hover X); on Mouse.down (translate_ X) ] ] |> colored (ifHit X C4b.White C4b.DarkRed)
                [ cylinder V3d.OOO V3d.OIO 1.0 0.05 |> render [ on Mouse.move (hover Y); on Mouse.down (translate_ Y) ] ] |> colored (ifHit Y C4b.White C4b.DarkBlue)
                [ cylinder V3d.OOO V3d.OOI 1.0 0.05 |> render [ on Mouse.move (hover Z); on Mouse.down (translate_ Z) ] ] |> colored (ifHit Z C4b.White C4b.DarkGreen)
                
                translate 0.0 0.0 0.0 [
                    [ Sphere3d(V3d.OOO,0.1) |> Sphere |> render Pick.ignore ] |> colored (Mod.constant C4b.Gray)
                ]

                Everything |> render [whenever Mouse.move MoveRay]
        ]

    let viewScene (sizes : IMod<V2i>) s =   
        let cameraView = CameraView.lookAt (V3d.III * 3.0) V3d.OOO V3d.OOI |> Mod.constant
        let frustum = sizes |> Mod.map (fun (b : V2i) -> Frustum.perspective 60.0 0.1 10.0 (float b.X / float b.Y))
        viewModel s.mscene 
            |> Scene.camera (Mod.map2 Camera.create cameraView frustum)
            |> effect [toEffect DefaultSurfaces.trafo; toEffect DefaultSurfaces.vertexColor; toEffect DefaultSurfaces.simpleLighting]

    let ofPickMsgModel (model : TModel) (pick : GlobalPick) =
        match pick.mouseEvent with   
            | MouseEvent.Click _ | MouseEvent.Down _  -> []
            | MouseEvent.Move when Option.isNone model.activeTranslation -> [NoHit]
            | MouseEvent.Move ->  []
            | MouseEvent.Up _   -> [EndTranslation]
            | MouseEvent.NoEvent -> []

    let ofPickMsg (model : Scene) noPick =
        ofPickMsgModel model.scene noPick

    let app (sizes : IMod<V2i>) = {
        initial = initial
        update = update
        view = viewScene sizes
        ofPickMsg = ofPickMsg
        subscriptions = Subscriptions.none
    }

Composing translation controller and polygon drawing

Related Work

Conclusions

In this work we used the ELM architecture in the context of 3D graphics. We developed a DSL for specifying 3D scenes and user interaction with graphical elements in a purely functional manner. When rendering UI elements, the resulting scene description can be efficiently rendered using HTML virtual dom diffing. This approach is not feasable for data intensive 3D applications. In this paper we show how to compute changes of immutable data structures in order to use those changes in the incremental rendering engine provided by the aardvark platform.

namespace System
namespace Aardvark
namespace Aardvark.Base
type Polygon = obj

Full name: Elmish.Polygon
type 'T list = List<'T>

Full name: Microsoft.FSharp.Collections.list<_>
type OpenPolygon =
  {finishedPoints: obj;
   cursor: obj;}

Full name: Elmish.OpenPolygon
OpenPolygon.finishedPoints: obj
OpenPolygon.cursor: obj
module Option

from Microsoft.FSharp.Core
type DrawingModel =
  {finished: Polygon list;
   working: Option<OpenPolygon>;}

Full name: Elmish.DrawingModel
DrawingModel.finished: Polygon list
DrawingModel.working: Option<OpenPolygon>
type Primitive =
  | Sphere of center: obj * radius: float
  | Cone of center: obj * dir: obj * height: float * radius: float
  | Cylinder of center: obj * dir: obj * height: float * radius: float
  | Quad of obj

Full name: Elmish.Primitive
union case Primitive.Sphere: center: obj * radius: float -> Primitive
Multiple items
val float : value:'T -> float (requires member op_Explicit)

Full name: Microsoft.FSharp.Core.Operators.float

--------------------
type float = Double

Full name: Microsoft.FSharp.Core.float

--------------------
type float<'Measure> = float

Full name: Microsoft.FSharp.Core.float<_>
union case Primitive.Cone: center: obj * dir: obj * height: float * radius: float -> Primitive
union case Primitive.Cylinder: center: obj * dir: obj * height: float * radius: float -> Primitive
union case Primitive.Quad: obj -> Primitive
type Scene1 =
  | Transform of obj * Scene1 list
  | Colored of obj * Scene1 list
  | Render of Primitive
  | Group of Scene1 list

Full name: Elmish.Scene1
union case Scene1.Transform: obj * Scene1 list -> Scene1
union case Scene1.Colored: obj * Scene1 list -> Scene1
union case Scene1.Render: Primitive -> Scene1
union case Scene1.Group: Scene1 list -> Scene1
val scene : Scene1

Full name: Elmish.scene
val colored1 : c:'a -> xs:Scene1 list -> Scene1

Full name: Elmish.colored1
val c : 'a
val xs : Scene1 list
val transformed1 : t:'a -> x:Scene1 -> Scene1

Full name: Elmish.transformed1
val t : 'a
val x : Scene1
val view1 : m:DrawingModel -> Scene1

Full name: Elmish.view1
val m : DrawingModel
val groundPlane : Scene1
val viewPolygon : ('a -> Scene1)
val p : 'a
val edge : obj
Multiple items
module List

from Microsoft.FSharp.Collections

--------------------
type List<'T> =
  | ( [] )
  | ( :: ) of Head: 'T * Tail: 'T list
  interface IEnumerable
  interface IEnumerable<'T>
  member GetSlice : startIndex:int option * endIndex:int option -> 'T list
  member Head : 'T
  member IsEmpty : bool
  member Item : index:int -> 'T with get
  member Length : int
  member Tail : 'T list
  static member Cons : head:'T * tail:'T list -> 'T list
  static member Empty : 'T list

Full name: Microsoft.FSharp.Collections.List<_>
val toSeq : list:'T list -> seq<'T>

Full name: Microsoft.FSharp.Collections.List.toSeq
val v : obj
val openPolygon : Scene1 list
union case Option.None: Option<'T>
union case Option.Some: Value: 'T -> Option<'T>
val v : OpenPolygon
val cursor : Scene1 list
val isSome : option:'T option -> bool

Full name: Microsoft.FSharp.Core.Option.isSome
val polygons : Scene1 list
val map : mapping:('T -> 'U) -> list:'T list -> 'U list

Full name: Microsoft.FSharp.Collections.List.map
type DrawCommand =
  | ClosePolygon
  | AddPoint of obj
  | MoveCursor of obj

Full name: Elmish.DrawCommand
union case DrawCommand.ClosePolygon: DrawCommand
union case DrawCommand.AddPoint: obj -> DrawCommand
union case DrawCommand.MoveCursor: obj -> DrawCommand
val updateDrawing : m:DrawingModel -> cmd:DrawCommand -> DrawingModel

Full name: Elmish.updateDrawing
val cmd : DrawCommand
val p : obj
val p : OpenPolygon
val groundPlane : Scene1

Full name: Elmish.groundPlane
namespace Aardvark.Application
type MouseEvent =
  | Move of obj
  | Down of obj * obj

Full name: Elmish.MouseEvent
union case MouseEvent.Move: obj -> MouseEvent
union case MouseEvent.Down: obj * obj -> MouseEvent
type PickOperation<'msg> = MouseEvent -> Option<'msg>

Full name: Elmish.PickOperation<_>
type Scene<'msg> =
  | Transform of obj * seq<Scene<'msg>>
  | Colored of obj * seq<Scene<'msg>>
  | Render of PickOperation<'msg> list * Primitive
  | Group of seq<Scene<'msg>>

Full name: Elmish.Scene<_>
union case Scene.Transform: obj * seq<Scene<'msg>> -> Scene<'msg>
Multiple items
val seq : sequence:seq<'T> -> seq<'T>

Full name: Microsoft.FSharp.Core.Operators.seq

--------------------
type seq<'T> = Collections.Generic.IEnumerable<'T>

Full name: Microsoft.FSharp.Collections.seq<_>
union case Scene.Colored: obj * seq<Scene<'msg>> -> Scene<'msg>
union case Scene.Render: PickOperation<'msg> list * Primitive -> Scene<'msg>
union case Scene.Group: seq<Scene<'msg>> -> Scene<'msg>
val transform : t:'a -> xs:seq<Scene<'b>> -> Scene<'b>

Full name: Elmish.transform
val xs : seq<Scene<'a>>
val transform' : t:'a -> x:Scene<'b> -> Scene<'b>

Full name: Elmish.transform'
val x : Scene<'a>
val translate : x:'a -> y:'b -> z:'c -> xs:seq<Scene<'d>> -> Scene<'d>

Full name: Elmish.translate
val x : 'a
val y : 'a
val z : 'a
val colored : c:'a -> xs:seq<Scene<'b>> -> Scene<'b>

Full name: Elmish.colored
val render : picks:PickOperation<'a> list -> primitive:Primitive -> Scene<'a>

Full name: Elmish.render
val picks : PickOperation<'a> list
val primitive : Primitive
val group : xs:seq<Scene<'a>> -> Scene<'a>

Full name: Elmish.group
val drawGroundPlane : Scene<DrawCommand>

Full name: Elmish.drawGroundPlane
val evt : MouseEvent
Multiple items
module Event

from Microsoft.FSharp.Control

--------------------
type Event<'T> =
  new : unit -> Event<'T>
  member Trigger : arg:'T -> unit
  member Publish : IEvent<'T>

Full name: Microsoft.FSharp.Control.Event<_>

--------------------
type Event<'Delegate,'Args (requires delegate and 'Delegate :> Delegate)> =
  new : unit -> Event<'Delegate,'Args>
  member Trigger : sender:obj * args:'Args -> unit
  member Publish : IEvent<'Delegate,'Args>

Full name: Microsoft.FSharp.Control.Event<_,_>

--------------------
new : unit -> Event<'T>

--------------------
new : unit -> Event<'Delegate,'Args>
val move : _arg1:MouseEvent -> bool

Full name: Elmish.Event.move
type bool = Boolean

Full name: Microsoft.FSharp.Core.bool
val down : _arg1:MouseEvent -> bool

Full name: Elmish.Event.down
val down' : p:obj -> _arg1:MouseEvent -> bool

Full name: Elmish.Event.down'
val p' : obj
val leftDown : (MouseEvent -> bool)

Full name: Elmish.Event.leftDown
val rightDown : (MouseEvent -> bool)

Full name: Elmish.Event.rightDown
val position : _arg1:MouseEvent -> obj

Full name: Elmish.Event.position
val s : obj
val on : p:(MouseEvent -> bool) -> r:(obj -> 'msg) -> k:MouseEvent -> 'msg option

Full name: Elmish.on
val p : (MouseEvent -> bool)
val r : (obj -> 'msg)
val k : MouseEvent
Multiple items
module Event

from Elmish

--------------------
module Event

from Microsoft.FSharp.Control

--------------------
type Event<'T> =
  new : unit -> Event<'T>
  member Trigger : arg:'T -> unit
  member Publish : IEvent<'T>

Full name: Microsoft.FSharp.Control.Event<_>

--------------------
type Event<'Delegate,'Args (requires delegate and 'Delegate :> Delegate)> =
  new : unit -> Event<'Delegate,'Args>
  member Trigger : sender:obj * args:'Args -> unit
  member Publish : IEvent<'Delegate,'Args>

Full name: Microsoft.FSharp.Control.Event<_,_>

--------------------
new : unit -> Event<'T>

--------------------
new : unit -> Event<'Delegate,'Args>
val drawGroundPlane2 : Scene<DrawCommand>

Full name: Elmish.drawGroundPlane2
val drawGroundPlane3 : Scene<DrawCommand>

Full name: Elmish.drawGroundPlane3
type App<'model,'msg,'view> =
  {initial: 'model;
   update: 'model -> 'msg -> 'model;
   view: 'model -> 'view;}

Full name: Elmish.App<_,_,_>
App.initial: 'model
App.update: 'model -> 'msg -> 'model
App.view: 'model -> 'view
type ThreeDApp<'model,'msg> = App<'model,'msg,Scene<'msg>>

Full name: Elmish.ThreeDApp<_,_>
val ignore : 'a list

Full name: Elmish.Pick.ignore
val viewDrawing : m:DrawingModel -> Scene<DrawCommand>

Full name: Elmish.viewDrawing
val viewPolygon : ('a -> Scene<'b>)
module Pick

from Elmish
val p : Polygon
val drawingApp : App<DrawingModel,DrawCommand,Scene<DrawCommand>>

Full name: Elmish.drawingApp
Multiple items
type AutoOpenAttribute =
  inherit Attribute
  new : unit -> AutoOpenAttribute
  new : path:string -> AutoOpenAttribute
  member Path : string

Full name: Microsoft.FSharp.Core.AutoOpenAttribute

--------------------
new : unit -> AutoOpenAttribute
new : path:string -> AutoOpenAttribute
namespace Aardvark.SceneGraph
type State =
  {trafo: obj;
   color: obj;}

Full name: Elmish.ConvertToSceneGraph.State
State.trafo: obj
State.color: obj
val toSg : scene:Scene<'msg> -> 'a

Full name: Elmish.ConvertToSceneGraph.toSg
val scene : Scene<'msg>
val toSg : (State -> Scene<'msg> -> 'a)
val s : State
val t : obj
val children : seq<Scene<'msg>>
module Seq

from Microsoft.FSharp.Collections
val map : mapping:('T -> 'U) -> source:seq<'T> -> seq<'U>

Full name: Microsoft.FSharp.Collections.Seq.map
val c : obj
val center : obj
val dir : obj
val height : float
val radius : float
val toArray : source:seq<'T> -> 'T []

Full name: Microsoft.FSharp.Collections.Seq.toArray
type Array =
  member Clone : unit -> obj
  member CopyTo : array:Array * index:int -> unit + 1 overload
  member GetEnumerator : unit -> IEnumerator
  member GetLength : dimension:int -> int
  member GetLongLength : dimension:int -> int64
  member GetLowerBound : dimension:int -> int
  member GetUpperBound : dimension:int -> int
  member GetValue : [<ParamArray>] indices:int[] -> obj + 7 overloads
  member Initialize : unit -> unit
  member IsFixedSize : bool
  ...

Full name: System.Array
val replicate : count:int -> initial:'T -> 'T []

Full name: Microsoft.FSharp.Collections.Array.replicate
val xs : seq<Scene<'msg>>
val hitPrimitive : p:Primitive -> trafo:'a -> ray:'b -> action:'c -> ('d * 'c) list

Full name: Elmish.Picking.hitPrimitive
val p : Primitive
val trafo : 'a
val ray : 'a
val action : 'a
val mutable ha : obj
val transformed : obj
type Double =
  struct
    member CompareTo : value:obj -> int + 1 overload
    member Equals : obj:obj -> bool + 1 overload
    member GetHashCode : unit -> int
    member GetTypeCode : unit -> TypeCode
    member ToString : unit -> string + 3 overloads
    static val MinValue : float
    static val MaxValue : float
    static val Epsilon : float
    static val NegativeInfinity : float
    static val PositiveInfinity : float
    ...
  end

Full name: System.Double
field float.PositiveInfinity = Infinity
val cylinder : obj
field float.MaxValue = 1.79769313486e+308
val q : obj
val pick : r:'a -> s:Scene<'msg> -> ('b * PickOperation<'msg> list) list (requires comparison)

Full name: Elmish.Picking.pick
val r : 'a
val s : Scene<'msg>
val go : (State -> Scene<'a> -> ('b * PickOperation<'a> list) list)
val state : State
val s : Scene<'a>
val toList : source:seq<'T> -> 'T list

Full name: Microsoft.FSharp.Collections.Seq.toList
val collect : mapping:('T -> 'U list) -> list:'T list -> 'U list

Full name: Microsoft.FSharp.Collections.List.collect
val action : PickOperation<'a> list
val xs : ('a * PickOperation<'msg> list) list (requires comparison)
val filter : predicate:('T -> bool) -> list:'T list -> 'T list

Full name: Microsoft.FSharp.Collections.List.filter
val not : value:bool -> bool

Full name: Microsoft.FSharp.Core.Operators.not
val isEmpty : list:'T list -> bool

Full name: Microsoft.FSharp.Collections.List.isEmpty
val snd : tuple:('T1 * 'T2) -> 'T2

Full name: Microsoft.FSharp.Core.Operators.snd
val sortBy : projection:('T -> 'Key) -> list:'T list -> 'T list (requires comparison)

Full name: Microsoft.FSharp.Collections.List.sortBy
val fst : tuple:('T1 * 'T2) -> 'T1

Full name: Microsoft.FSharp.Core.Operators.fst
namespace Aardvark.Base.Incremental
val createApp : ctrl:'a -> camera:'b -> app:App<'model,'msg,Scene<'msg>> -> 'c

Full name: Elmish.createApp
val ctrl : 'a
val camera : 'a
val app : App<'model,'msg,Scene<'msg>>
val mutable model : 'model
val view : 'a
App.view: 'model -> Scene<'msg>
val sceneGraph : 'a
module ConvertToSceneGraph

from Elmish
val updateScene : ('model -> 'a)
val m : 'model
val newView : Scene<'msg>
val handleMouseEvent : (('a -> MouseEvent) -> 'b)
val createEvent : ('a -> MouseEvent)
module Picking

from Elmish
val d : 'a (requires comparison)
val f : PickOperation<'msg> list
val msg : PickOperation<'msg>
val r : 'msg
namespace Aardvark.Base.Rendering
namespace Aardvark.Application.WinForms
val app : 'a

Full name: Elmish.app
val win : 'a

Full name: Elmish.win
val frustum : 'a

Full name: Elmish.frustum
val cameraView : 'a

Full name: Elmish.cameraView
val camera : 'a

Full name: Elmish.camera
val sg : 'a

Full name: Elmish.sg
namespace System.Runtime
val cursorGeometry : hasCursor:'a -> 'b

Full name: Elmish.cursorGeometry
val hasCursor : 'a
val hasCursor : 'a

Full name: Elmish.hasCursor
val adaptiveScene : 'a

Full name: Elmish.adaptiveScene
val sceneWithDisabledCursor : 'a

Full name: Elmish.sceneWithDisabledCursor
val sceneWithCursor : 'a

Full name: Elmish.sceneWithCursor
type ImmutableData1 =
  {value: int;}

Full name: Elmish.ImmutableData1
ImmutableData1.value: int
Multiple items
val int : value:'T -> int (requires member op_Explicit)

Full name: Microsoft.FSharp.Core.Operators.int

--------------------
type int = int32

Full name: Microsoft.FSharp.Core.int

--------------------
type int<'Measure> = int

Full name: Microsoft.FSharp.Core.int<_>
type MutableData1 =
  {mvalue: obj;}

Full name: Elmish.MutableData1
MutableData1.mvalue: obj
namespace System.Threading
Multiple items
type AllowNullLiteralAttribute =
  inherit Attribute
  new : unit -> AllowNullLiteralAttribute
  new : value:bool -> AllowNullLiteralAttribute
  member Value : bool

Full name: Microsoft.FSharp.Core.AllowNullLiteralAttribute

--------------------
new : unit -> AllowNullLiteralAttribute
new : value:bool -> AllowNullLiteralAttribute
Multiple items
type Id =
  new : unit -> Id
  override ToString : unit -> string
  static member New : Id

Full name: Elmish.IDs.Id

--------------------
new : unit -> Id
val mutable current : int
val id : int
type Interlocked =
  static member Add : location1:int * value:int -> int + 1 overload
  static member CompareExchange : location1:int * value:int * comparand:int -> int + 6 overloads
  static member Decrement : location:int -> int + 1 overload
  static member Exchange : location1:int * value:int -> int + 6 overloads
  static member Increment : location:int -> int + 1 overload
  static member Read : location:int64 -> int64

Full name: System.Threading.Interlocked
Interlocked.Increment(location: byref<int64>) : int64
Interlocked.Increment(location: byref<int>) : int
static member Id.New : Id

Full name: Elmish.IDs.Id.New
val x : Id
override Id.ToString : unit -> string

Full name: Elmish.IDs.Id.ToString
val sprintf : format:Printf.StringFormat<'T> -> 'T

Full name: Microsoft.FSharp.Core.ExtraTopLevelOperators.sprintf
type OpenPolygon2 =
  {finishedPolys: obj;
   cursor: obj;}

Full name: Elmish.OpenPolygon2
OpenPolygon2.finishedPolys: obj
OpenPolygon2.cursor: obj
type DrawingModel2 =
  {id: obj;
   finished: obj;
   working: Option<OpenPolygon>;}

Full name: Elmish.DrawingModel2
DrawingModel2.id: obj
DrawingModel2.finished: obj
DrawingModel2.working: Option<OpenPolygon>
type MDrawingModel2 =
  {original: DrawingModel2;
   finished: obj;
   working: obj;}

Full name: Elmish.MDrawingModel2
MDrawingModel2.original: DrawingModel2
MDrawingModel2.finished: obj
MDrawingModel2.working: obj
val unpersist : m:DrawingModel2 -> MDrawingModel2

Full name: Elmish.unpersist
val m : DrawingModel2
val apply : m:MDrawingModel2 -> newModel:DrawingModel2 -> 'a

Full name: Elmish.apply
val m : MDrawingModel2
val newModel : DrawingModel2
val filter : predicate:('T -> bool) -> source:seq<'T> -> seq<'T>

Full name: Microsoft.FSharp.Collections.Seq.filter
val ignore : value:'T -> unit

Full name: Microsoft.FSharp.Core.Operators.ignore
type Polygon = obj

Full name: Elmish.SimpleDrawingApp.Polygon
type OpenPolygon =
  {cursor: obj;
   finishedPoints: obj;}

Full name: Elmish.SimpleDrawingApp.OpenPolygon
type Model =
  {finished: obj;
   working: Option<OpenPolygon>;}

Full name: Elmish.SimpleDrawingApp.Model
Model.finished: obj
Model.working: Option<OpenPolygon>
type Polygon = obj

Full name: Elmish.SimpleDrawingAppGenerated.Polygon
type OpenPolygon =
  {cursor: obj;
   finishedPoints: obj;}

Full name: Elmish.SimpleDrawingAppGenerated.OpenPolygon
type Model =
  {mutable _id: obj;
   finished: obj;
   working: Option<OpenPolygon>;}
  interface obj
  member ToMod : reuseCache:'a0 -> MModel
  override Id : obj
  override Id : 'a with set

Full name: Elmish.SimpleDrawingAppGenerated.Model
Model._id: obj
val x : Model
member Model.ToMod : reuseCache:'a0 -> MModel

Full name: Elmish.SimpleDrawingAppGenerated.Model.ToMod
val reuseCache : 'a
override Model.Id : obj

Full name: Elmish.SimpleDrawingAppGenerated.Model.Id
val set : elements:seq<'T> -> Set<'T> (requires comparison)

Full name: Microsoft.FSharp.Core.ExtraTopLevelOperators.set
val v : 'a
type MModel =
  {mutable _original: Model;
   mfinished: obj;
   mworking: obj;}
  member Apply : arg0:Model * reuseCache:'a0 -> unit

Full name: Elmish.SimpleDrawingAppGenerated.MModel
MModel._original: Model
MModel.mfinished: obj
MModel.mworking: obj
val x : MModel
member MModel.Apply : arg0:Model * reuseCache:'a0 -> unit

Full name: Elmish.SimpleDrawingAppGenerated.MModel.Apply
val arg0 : Model
Multiple items
type Object =
  new : unit -> obj
  member Equals : obj:obj -> bool
  member GetHashCode : unit -> int
  member GetType : unit -> Type
  member ToString : unit -> string
  static member Equals : objA:obj * objB:obj -> bool
  static member ReferenceEquals : objA:obj * objB:obj -> bool

Full name: System.Object

--------------------
Object() : unit
Object.ReferenceEquals(objA: obj, objB: obj) : bool
type Scene2 =
  | Transform of obj * obj
  | Colored of obj * obj
  | Render of Primitive
  | Group of obj

Full name: Elmish.Scene2
union case Scene2.Transform: obj * obj -> Scene2
union case Scene2.Colored: obj * obj -> Scene2
union case Scene2.Render: Primitive -> Scene2
union case Scene2.Group: obj -> Scene2
type ISg<'msg> =
  interface
    inherit obj
  end

Full name: Elmish.AdaptiveScene.ISg<_>
Multiple items
type Group<'msg> =
  interface obj
  interface ISg<'msg>
  new : xs:'a -> Group<'msg>
  member Children : 'a
  override Children : 'a

Full name: Elmish.AdaptiveScene.Group<_>

--------------------
new : xs:'a -> Group<'msg>
val xs : 'a
val x : Group<'msg>
override Group.Children : 'a

Full name: Elmish.AdaptiveScene.Group`1.Children
member Group.Children : 'a

Full name: Elmish.AdaptiveScene.Group`1.Children
Multiple items
type Render<'msg> =
  interface ISg<'msg>
  new : xs:Primitive -> Render<'msg>
  member Primitive : Primitive

Full name: Elmish.AdaptiveScene.Render<_>

--------------------
new : xs:Primitive -> Render<'msg>
val xs : Primitive
val x : Render<'msg>
Multiple items
member Render.Primitive : Primitive

Full name: Elmish.AdaptiveScene.Render`1.Primitive

--------------------
type Primitive =
  | Sphere of center: obj * radius: float
  | Cone of center: obj * dir: obj * height: float * radius: float
  | Cylinder of center: obj * dir: obj * height: float * radius: float
  | Quad of obj

Full name: Elmish.Primitive
module Ag

from Aardvark.Base
namespace Aardvark.SceneGraph.Semantics
module AdaptiveScene

from Elmish
Multiple items
module Semantic

from Aardvark.SceneGraph.Semantics.ActiveSemantics

--------------------
module Semantic

from Aardvark.SceneGraph.Semantics.AttributeExtensions

--------------------
module Semantic

from Aardvark.SceneGraph.Semantics.BoundingBoxes

--------------------
module Semantic

from Aardvark.SceneGraph.Semantics.ModeSemantics

--------------------
module Semantic

from Aardvark.SceneGraph.Semantics.RenderObjectSemantics

--------------------
module Semantic

from Aardvark.SceneGraph.Semantics.SurfaceSemantics

--------------------
module Semantic

from Aardvark.SceneGraph.Semantics.TrafoExtensions

--------------------
module Semantic

from Aardvark.SceneGraph.Semantics.UniformSemantics

--------------------
type Semantic =
  inherit Attribute
  new : unit -> Semantic

Full name: Aardvark.Base.Ag.Semantic

--------------------
new : unit -> Semantic
Multiple items
type LeafSemantics =
  new : unit -> LeafSemantics
  member RenderObjects : l:Render<'msg> -> aset<IRenderObject>

Full name: Elmish.AgExtension.LeafSemantics

--------------------
new : unit -> LeafSemantics
val x : LeafSemantics
member LeafSemantics.RenderObjects : l:Render<'msg> -> Aardvark.Base.Incremental.aset<Aardvark.Base.IRenderObject>

Full name: Elmish.AgExtension.LeafSemantics.RenderObjects
val l : Render<'msg>
property Render.Primitive: Primitive
val renderObjects : s:Aardvark.SceneGraph.ISg -> Aardvark.Base.Incremental.aset<Aardvark.Base.IRenderObject>

Full name: Aardvark.SceneGraph.Semantics.RenderObjectSemantics.Semantic.renderObjects
val failwith : message:string -> 'T

Full name: Microsoft.FSharp.Core.Operators.failwith
namespace Aardvark.ImmutableSceneGraph
namespace Aardvark.Elmish
module Primitives

from Aardvark.ImmutableSceneGraph.PickStuff
module SimpleDrawingAppGenerated

from Elmish
Multiple items
type Action =
  | ClosePolygon
  | AddPoint of obj
  | MoveCursor of obj

Full name: Elmish.FinalDrawingApp.Action

--------------------
type Action<'T> =
  delegate of 'T -> unit

Full name: System.Action<_>

--------------------
type Action<'T1,'T2> =
  delegate of 'T1 * 'T2 -> unit

Full name: System.Action<_,_>

--------------------
type Action<'T1,'T2,'T3> =
  delegate of 'T1 * 'T2 * 'T3 -> unit

Full name: System.Action<_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 -> unit

Full name: System.Action<_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 -> unit

Full name: System.Action<_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 -> unit

Full name: System.Action<_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 -> unit

Full name: System.Action<_,_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 -> unit

Full name: System.Action<_,_,_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 -> unit

Full name: System.Action<_,_,_,_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 -> unit

Full name: System.Action<_,_,_,_,_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 -> unit

Full name: System.Action<_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 -> unit

Full name: System.Action<_,_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12,'T13> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 * 'T13 -> unit

Full name: System.Action<_,_,_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12,'T13,'T14> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 * 'T13 * 'T14 -> unit

Full name: System.Action<_,_,_,_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12,'T13,'T14,'T15> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 * 'T13 * 'T14 * 'T15 -> unit

Full name: System.Action<_,_,_,_,_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12,'T13,'T14,'T15,'T16> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 * 'T13 * 'T14 * 'T15 * 'T16 -> unit

Full name: System.Action<_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_>
union case Action.ClosePolygon: Action
union case Action.AddPoint: obj -> Action
union case Action.MoveCursor: obj -> Action
val update : e:'a -> m:Model -> cmd:Action -> Model

Full name: Elmish.FinalDrawingApp.update
val e : 'a
val m : Model
val cmd : Action
val viewPolygon : p:'a -> ISg<'b>

Full name: Elmish.FinalDrawingApp.viewPolygon
val edge : 'a
Multiple items
module List

from Aardvark.ImmutableSceneGraph.PickStuff

--------------------
module List

from Microsoft.FSharp.Collections

--------------------
type List<'T> =
  | ( [] )
  | ( :: ) of Head: 'T * Tail: 'T list
  interface IEnumerable
  interface IEnumerable<'T>
  member GetSlice : startIndex:int option * endIndex:int option -> 'T list
  member Head : 'T
  member IsEmpty : bool
  member Item : index:int -> 'T with get
  member Length : int
  member Tail : 'T list
  static member Cons : head:'T * tail:'T list -> 'T list
  static member Empty : 'T list

Full name: Microsoft.FSharp.Collections.List<_>
val v : 'a (requires member ( - ))
val cylinder : c:Aardvark.Base.V3d -> d:Aardvark.Base.V3d -> h:float -> r:float -> Primitive

Full name: Aardvark.ImmutableSceneGraph.PickStuff.Primitives.cylinder
Multiple items
module Scene

from Aardvark.ImmutableSceneGraph

--------------------
type Scene<'msg> =
  | Transform of obj * seq<Scene<'msg>>
  | Colored of obj * seq<Scene<'msg>>
  | Render of PickOperation<'msg> list * Primitive
  | Group of seq<Scene<'msg>>

Full name: Elmish.Scene<_>
val render : picks:PickOperation<'a> list -> p:Primitive -> ISg<'a>

Full name: Aardvark.ImmutableSceneGraph.Scene.render
Multiple items
module Pick

from Aardvark.ImmutableSceneGraph.PickStuff

--------------------
module Pick

from Aardvark.ImmutableSceneGraph

--------------------
module Pick

from Elmish
Multiple items
val ignore : 'a list

Full name: Aardvark.ImmutableSceneGraph.PickStuff.Pick.ignore

--------------------
val ignore : 'a list

Full name: Elmish.Pick.ignore
val group : xs:ISg<'msg> list -> ISg<'msg>

Full name: Aardvark.ImmutableSceneGraph.Scene.group
val view : m:MModel -> ISg<'a>

Full name: Elmish.FinalDrawingApp.view
val m : MModel
val t : 'a (requires 'a :> Aardvark.Base.Incremental.aset<ISg<'b>>)
union case Primitive.Quad: Aardvark.Base.Quad3d -> Primitive
val on : p:(PickOccurance -> bool) -> r:(Aardvark.Base.V3d -> 'msg) -> PickOperation<'msg>

Full name: Aardvark.ImmutableSceneGraph.PickStuff.on
Multiple items
union case Sub.Mouse: (Direction -> Aardvark.Application.MouseButtons -> Aardvark.Base.PixelPosition -> Option<'msg>) -> Sub<'msg>

--------------------
module Mouse

from Aardvark.ImmutableSceneGraph.PickStuff
val move : p:PickOccurance -> bool

Full name: Aardvark.ImmutableSceneGraph.PickStuff.Mouse.move
val down' : button:Aardvark.Application.MouseButtons -> p:PickOccurance -> bool

Full name: Aardvark.ImmutableSceneGraph.PickStuff.Mouse.down'
val colored : c:Aardvark.Base.Incremental.IMod<Aardvark.Base.C4b> -> xs:ISg<'msg> list -> ISg<'msg>

Full name: Aardvark.ImmutableSceneGraph.Scene.colored
union case Primitive.Sphere: Aardvark.Base.Sphere3d -> Primitive
val transform' : t:Aardvark.Base.Incremental.IMod<Aardvark.Base.Trafo3d> -> x:ISg<'msg> -> ISg<'msg>

Full name: Aardvark.ImmutableSceneGraph.Scene.transform'
val agroup : xs:Aardvark.Base.Incremental.aset<ISg<'msg>> -> ISg<'msg>

Full name: Aardvark.ImmutableSceneGraph.Scene.agroup
val viewScene : sizes:'a -> m:MModel -> ISg<'b>

Full name: Elmish.FinalDrawingApp.viewScene
val sizes : 'a
val cameraView : 'a
val frustum : 'a
val camera : camera:Aardvark.Base.Incremental.IMod<Aardvark.Base.Camera> -> xs:ISg<'a> -> ISg<'a>

Full name: Aardvark.ImmutableSceneGraph.Scene.camera
val effect : effects:seq<Aardvark.Base.Rendering.FShadeEffect> -> xs:ISg<'a> -> ISg<'a>

Full name: Aardvark.ImmutableSceneGraph.Scene.effect
val initial : Model

Full name: Elmish.FinalDrawingApp.initial
val app : s:'a -> App<Model,MModel,Action,ISg<'b>>

Full name: Elmish.FinalDrawingApp.app
val s : 'a
module Subscriptions

from Aardvark.Elmish
val none : 'a -> Sub<'b>

Full name: Aardvark.Elmish.Subscriptions.none
type Sub<'msg> =
  | TimeSub of TimeSpan * (TimeSpan -> 'msg)
  | KeyPress of (obj -> Option<'msg>)
  | Many of Sub<'msg> list

Full name: Elmish.Subscriptions1.Sub<_>
union case Sub.TimeSub: TimeSpan * (TimeSpan -> 'msg) -> Sub<'msg>
Multiple items
type TimeSpan =
  struct
    new : ticks:int64 -> TimeSpan + 3 overloads
    member Add : ts:TimeSpan -> TimeSpan
    member CompareTo : value:obj -> int + 1 overload
    member Days : int
    member Duration : unit -> TimeSpan
    member Equals : value:obj -> bool + 1 overload
    member GetHashCode : unit -> int
    member Hours : int
    member Milliseconds : int
    member Minutes : int
    ...
  end

Full name: System.TimeSpan

--------------------
TimeSpan()
TimeSpan(ticks: int64) : unit
TimeSpan(hours: int, minutes: int, seconds: int) : unit
TimeSpan(days: int, hours: int, minutes: int, seconds: int) : unit
TimeSpan(days: int, hours: int, minutes: int, seconds: int, milliseconds: int) : unit
union case Sub.KeyPress: (obj -> Option<'msg>) -> Sub<'msg>
union case Sub.Many: Sub<'msg> list -> Sub<'msg>
val timeSub : ts:TimeSpan -> f:(TimeSpan -> 'a) -> Sub<'a>

Full name: Elmish.Subscriptions1.timeSub
val ts : TimeSpan
val f : (TimeSpan -> 'a)
type Model =
  {rotation: float;
   _id: obj;}

Full name: Elmish.Animation.Model
Model.rotation: float
type MModel =
  {mrotation: obj;}

Full name: Elmish.Animation.MModel
MModel.mrotation: obj
type Msg = | TimeStep of TimeSpan

Full name: Elmish.Animation.Msg
union case Msg.TimeStep: TimeSpan -> Msg
val update : e:'a -> m:Model -> msg:Msg -> Model

Full name: Elmish.Animation.update
val msg : Msg
val t : TimeSpan
property TimeSpan.TotalMilliseconds: float
val view : m:MModel -> ISg<'a>

Full name: Elmish.Animation.view
val transform : t:Aardvark.Base.Incremental.IMod<Aardvark.Base.Trafo3d> -> xs:ISg<'msg> list -> ISg<'msg>

Full name: Aardvark.ImmutableSceneGraph.Scene.transform
val subscriptions : m:Model -> Subscriptions1.Sub<Msg>

Full name: Elmish.Animation.subscriptions
module Subscriptions1

from Elmish
val timeSub : ts:TimeSpan -> f:(TimeSpan -> 'a) -> Subscriptions1.Sub<'a>

Full name: Elmish.Subscriptions1.timeSub
TimeSpan.FromMilliseconds(value: float) : TimeSpan
type Transparency =
  | Solid
  | PickThrough

Full name: Elmish.Transparency
union case Transparency.Solid: Transparency
union case Transparency.PickThrough: Transparency
type PickOperation2<'msg> = (obj -> Option<'msg>) * Transparency

Full name: Elmish.PickOperation2<_>
val depthTest : xs:(float * PickOperation2<'msg>) list -> (float * (('a -> Option<'msg>) * Transparency)) list

Full name: Elmish.depthTest
val xs : (float * PickOperation2<'msg>) list
val d1 : float
val f1 : (obj -> Option<'msg>)
val d2 : float
val f2 : (obj -> Option<'msg>)
val rest : (float * PickOperation2<'msg>) list
val d : float
val f : (obj -> Option<'msg>)
namespace Fablish
module CommonTypes

from Fablish
type Model =
  {image: obj;}

Full name: Elmish.EnvExample.Model
Model.image: obj
type Msg =
  | LoadImages of string list
  | ImagesLoaded of obj
  | Progress of float

Full name: Elmish.EnvExample.Msg
union case Msg.LoadImages: string list -> Msg
Multiple items
val string : value:'T -> string

Full name: Microsoft.FSharp.Core.Operators.string

--------------------
type string = String

Full name: Microsoft.FSharp.Core.string
union case Msg.ImagesLoaded: obj -> Msg
union case Msg.Progress: float -> Msg
val loadImage : p:string list -> e:Env<Msg> -> Async<Msg>

Full name: Elmish.EnvExample.loadImage
val p : string list
val e : Env<Msg>
Multiple items
module Env

from Fablish.CommonTypes

--------------------
type Env<'msg> =
  {run: Cmd<'msg> -> unit;}

Full name: Fablish.CommonTypes.Env<_>
val async : AsyncBuilder

Full name: Microsoft.FSharp.Core.ExtraTopLevelOperators.async
val cnt : int
val length : list:'T list -> int

Full name: Microsoft.FSharp.Collections.List.length
val images : 'a list
val mapi : mapping:(int -> 'T -> 'U) -> list:'T list -> 'U list

Full name: Microsoft.FSharp.Collections.List.mapi
val i : int
val p : string
Multiple items
union case Cmd.Cmd: Async<'msg> -> Cmd<'msg>

--------------------
module Cmd

from Fablish.CommonTypes

--------------------
type Cmd<'msg> =
  | NoCmd
  | Cmd of Async<'msg>

Full name: Fablish.CommonTypes.Cmd<_>
Env.run: Cmd<Msg> -> unit
val update : env:Env<Msg> -> m:Model -> msg:Msg -> Model

Full name: Elmish.EnvExample.update
val env : Env<Msg>
val paths : string list
val img : obj
module TranslateController

from Elmish
module Scene

from Aardvark.ImmutableSceneGraph
namespace Scratch
namespace Scratch.DomainTypes
Multiple items
type CompilationRepresentationAttribute =
  inherit Attribute
  new : flags:CompilationRepresentationFlags -> CompilationRepresentationAttribute
  member Flags : CompilationRepresentationFlags

Full name: Microsoft.FSharp.Core.CompilationRepresentationAttribute

--------------------
new : flags:CompilationRepresentationFlags -> CompilationRepresentationAttribute
type CompilationRepresentationFlags =
  | None = 0
  | Static = 1
  | Instance = 2
  | ModuleSuffix = 4
  | UseNullAsTrueValue = 8
  | Event = 16

Full name: Microsoft.FSharp.Core.CompilationRepresentationFlags
CompilationRepresentationFlags.ModuleSuffix: CompilationRepresentationFlags = 4
type Axis =
  | X
  | Y
  | Z

Full name: Scratch.DomainTypes.Generated.Axis
val dir : _arg1:Axis -> 'a

Full name: Elmish.TranslateController.AxisModule.dir
union case Axis.X: Axis
union case Axis.Y: Axis
union case Axis.Z: Axis
val moveAxis : trafo:'a -> _arg1:Axis -> 'b

Full name: Elmish.TranslateController.AxisModule.moveAxis
Multiple items
type Action =
  | Hover of Axis * obj
  | NoHit
  | MoveRay of obj
  | Translate of Axis * obj
  | EndTranslation
  | ResetTrafo

Full name: Elmish.TranslateController.Action

--------------------
type Action<'T> =
  delegate of 'T -> unit

Full name: System.Action<_>

--------------------
type Action<'T1,'T2> =
  delegate of 'T1 * 'T2 -> unit

Full name: System.Action<_,_>

--------------------
type Action<'T1,'T2,'T3> =
  delegate of 'T1 * 'T2 * 'T3 -> unit

Full name: System.Action<_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 -> unit

Full name: System.Action<_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 -> unit

Full name: System.Action<_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 -> unit

Full name: System.Action<_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 -> unit

Full name: System.Action<_,_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 -> unit

Full name: System.Action<_,_,_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 -> unit

Full name: System.Action<_,_,_,_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 -> unit

Full name: System.Action<_,_,_,_,_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 -> unit

Full name: System.Action<_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 -> unit

Full name: System.Action<_,_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12,'T13> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 * 'T13 -> unit

Full name: System.Action<_,_,_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12,'T13,'T14> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 * 'T13 * 'T14 -> unit

Full name: System.Action<_,_,_,_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12,'T13,'T14,'T15> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 * 'T13 * 'T14 * 'T15 -> unit

Full name: System.Action<_,_,_,_,_,_,_,_,_,_,_,_,_,_,_>

--------------------
type Action<'T1,'T2,'T3,'T4,'T5,'T6,'T7,'T8,'T9,'T10,'T11,'T12,'T13,'T14,'T15,'T16> =
  delegate of 'T1 * 'T2 * 'T3 * 'T4 * 'T5 * 'T6 * 'T7 * 'T8 * 'T9 * 'T10 * 'T11 * 'T12 * 'T13 * 'T14 * 'T15 * 'T16 -> unit

Full name: System.Action<_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_>
union case Action.Hover: Axis * obj -> Action
Multiple items
module Axis

from Elmish.TranslateController

--------------------
type Axis =
  | X
  | Y
  | Z

Full name: Scratch.DomainTypes.Generated.Axis
union case Action.NoHit: Action
union case Action.MoveRay: obj -> Action
union case Action.Translate: Axis * obj -> Action
union case Action.EndTranslation: Action
union case Action.ResetTrafo: Action
Multiple items
module TranslateController

from Scratch.DomainTypes.Generated

--------------------
module TranslateController

from Scratch.DomainTypes
val hasEnded : a:Action -> bool

Full name: Elmish.TranslateController.hasEnded
val a : Action
val hover : (Axis -> Aardvark.Base.V3d -> 'a)

Full name: Elmish.TranslateController.hover
val translate_ : (Axis -> Aardvark.Base.V3d -> 'a)

Full name: Elmish.TranslateController.translate_
val initalModel : TModel

Full name: Elmish.TranslateController.initalModel
val initial : Scene

Full name: Elmish.TranslateController.initial
Multiple items
module Camera

from Scratch.DomainTypes.Generated

--------------------
module Camera

from Scratch.DomainTypes
val updateModel : m:TModel -> a:Action -> TModel

Full name: Elmish.TranslateController.updateModel
val m : TModel
type TModel =
  {mutable _id: Id;
   hovered: Option<Axis>;
   activeTranslation: Option<Axis * Plane3d * V3d>;
   trafo: Trafo3d;
   editTrafo: Trafo3d;}
  interface IUnique
  member ToMod : reuseCache:ReuseCache -> MTModel

Full name: Scratch.DomainTypes.Generated.TranslateController.TModel
TModel.activeTranslation: Option<Axis * Aardvark.Base.Plane3d * Aardvark.Base.V3d>
val v : Axis
val dir : Axis
TModel.trafo: Aardvark.Base.Trafo3d
field Aardvark.Base.Trafo3d.Backward
Aardvark.Base.M44d.TransformPos(p: Aardvark.Base.V3d) : Aardvark.Base.V3d
val update : e:'a -> m:Scene -> a:Action -> Scene

Full name: Elmish.TranslateController.update
val m : Scene
Multiple items
module Scene

from Aardvark.ImmutableSceneGraph

--------------------
type Scene =
  {mutable _id: Id;
   camera: Camera;
   scene: TModel;}
  interface IUnique
  member ToMod : reuseCache:ReuseCache -> MScene

Full name: Scratch.DomainTypes.Generated.TranslateController.Scene

--------------------
type Scene<'msg> =
  | Transform of obj * seq<Scene<'msg>>
  | Colored of obj * seq<Scene<'msg>>
  | Render of PickOperation<'msg> list * Primitive
  | Group of seq<Scene<'msg>>

Full name: Elmish.Scene<_>
val scene : TModel
Scene.scene: TModel
val viewModel : m:MTModel -> ISg<'a>

Full name: Elmish.TranslateController.viewModel
val m : MTModel
type MTModel =
  {mutable _original: TModel;
   mhovered: ModRef<Option<Axis>>;
   mactiveTranslation: ModRef<Option<Axis * Plane3d * V3d>>;
   mtrafo: ModRef<Trafo3d>;
   meditTrafo: ModRef<Trafo3d>;}
  member Apply : arg0:TModel * reuseCache:ReuseCache -> unit

Full name: Scratch.DomainTypes.Generated.TranslateController.MTModel
val arrow : (Aardvark.Base.V3d -> Primitive)
val dir : Aardvark.Base.V3d
union case Primitive.Cone: center: Aardvark.Base.V3d * dir: Aardvark.Base.V3d * height: float * radius: float -> Primitive
val ifHit : (Axis -> 'a -> 'b -> 'c)
val a : Axis
val selection : 'a
val defaultColor : 'a
MTModel.mhovered: Aardvark.Base.Incremental.ModRef<Option<Axis>>
MTModel.mtrafo: Aardvark.Base.Incremental.ModRef<Aardvark.Base.Trafo3d>
val translate : x:float -> y:float -> z:float -> xs:ISg<'msg> list -> ISg<'msg>

Full name: Aardvark.ImmutableSceneGraph.Scene.translate
val down : p:PickOccurance -> bool

Full name: Aardvark.ImmutableSceneGraph.PickStuff.Mouse.down
union case Primitive.Everything: Primitive
val whenever : p:(PickOccurance -> bool) -> r:(Aardvark.Base.Ray3d -> 'msg) -> PickOperation<'msg>

Full name: Aardvark.ImmutableSceneGraph.PickStuff.whenever
val viewScene : sizes:'a -> s:MScene -> ISg<'b>

Full name: Elmish.TranslateController.viewScene
val s : MScene
val map : f:('a -> 'b) -> a:ISg<'a> -> ISg<'b>

Full name: Aardvark.ImmutableSceneGraph.Scene.map
MScene.mscene: MTModel
val ofPickMsgModel : model:TModel -> pick:GlobalPick -> Action list

Full name: Elmish.TranslateController.ofPickMsgModel
val model : TModel
val pick : GlobalPick
type GlobalPick =
  {mouseEvent: MouseEvent;
   hits: bool;
   keyEvent: KeyEvent;}

Full name: Aardvark.ImmutableSceneGraph.PickStuff.GlobalPick
GlobalPick.mouseEvent: MouseEvent
type MouseEvent =
  | Down of MouseButtons
  | Move
  | Click of MouseButtons
  | Up of MouseButtons
  | NoEvent

Full name: Aardvark.ImmutableSceneGraph.PickStuff.MouseEvent
union case MouseEvent.Click: Aardvark.Application.MouseButtons -> MouseEvent
Multiple items
union case MouseEvent.Down: Aardvark.Application.MouseButtons -> MouseEvent

--------------------
union case MouseEvent.Down: obj * obj -> MouseEvent
Multiple items
union case MouseEvent.Move: MouseEvent

--------------------
union case MouseEvent.Move: obj -> MouseEvent
val isNone : option:'T option -> bool

Full name: Microsoft.FSharp.Core.Option.isNone
union case MouseEvent.Up: Aardvark.Application.MouseButtons -> MouseEvent
union case MouseEvent.NoEvent: MouseEvent
val ofPickMsg : model:Scene -> noPick:GlobalPick -> Action list

Full name: Elmish.TranslateController.ofPickMsg
val model : Scene
val noPick : GlobalPick
val app : sizes:'a -> App<Scene,MScene,Action,ISg<'b>>

Full name: Elmish.TranslateController.app