School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for...

21
School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization & Virtual Reality Group School of Computing University of Leeds, UK Colin Runciman & Malcolm Wallace Department of Computer Science University of York, UK

Transcript of School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for...

Page 1: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

School of ComputingFaculty of Engineering

Meshing with Grids:Toward Functional Abstractions for Grid-based Visualization

Rita Borgo & David Duke

Visualization & Virtual Reality Group

School of Computing

University of Leeds, UK

Colin Runciman & Malcolm Wallace

Department of Computer Science

University of York, UK

Page 2: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

Overview

Why functional programming (still) matters

Project: a lazy polytypic grid Marching cubes Streaming Making it generic Performance Looking back, looking forwards

Page 3: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

Why Functional Programming Still Matters

“Academic” arguments J. Hughes, Why Functional Programming Matters

Problem decomposition program composition Absence of side-effects Higher-order functions Laziness

Practical arguments:

Natural progression: OO service-orientation “Tower of Babel” Novel solutions come from working against the OO

grain!

Page 4: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

Introduction to FP and Haskell

Functional building blocks

square :: Int -> Intsquare x = x*x

map :: (a -> b) -> [a] -> [b]map _ [] = []map f (a:as) = (f a):(map f as)

(.) :: (b -> c) -> (a -> b) -> (a -> c)(f . g) x = f(g(x))

sqList ls = map square lssqsqList ls = map sqList (map sqList ls) = (map sqList . map sqList) ls = map (sqList . sqList) ls

fibs = [0,1] ++ [ a+b | (a,b) <- zip fibs (tail fibs) ]

Further information: see www.haskell.org

Note: loop fusion law encoded as a rule in GHC compiler

Page 5: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

Why FP matters (to grid-enabled vis)

pipeline architecture widespread in visualization supports distribution and streaming

However Streaming is ad-hoc and coarse grained Algorithms depend on mesh type Data traversed multiple times

readerozone levels isosurface normals

normalsisosurfacereadertemperature displaygeo-reference

?

Note: analogy of pipelinecomposition and functioncomposition: f . g

Page 6: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

A Lazy Polytypic Grid

Grid enabling: distribution of the run-time system

and on-demand streaming of arbitrary data.

Through fusion laws, multiple traversals on a

single resource are folded into one pass.

2

readerozone levels isosurface normals

normalsisosurface

reader

temperature

geo-reference display

Algorithms: written once, based on generic pattern

of data types, then instantiated for any type.1

3 Specialization: adapt

programs to utilize resources

available – data or

computational.

Page 7: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

Isosurfaces

Widely-used technique for both 2D and 3D scalar data Two general approaches:

Contour tracking: follow a feature through the dataset Marching: traverse dataset, processing each cell as

encountered in-core versus out-of-core variations 2D examples: skull cross-section; isoline for t=5

Page 8: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

Marching Squares

Input: a dataset, and a threshold value to be contoured Output: line segments representing contour's path within dataset Algorithm:

For each cell, compare field value at point with threshold Sixteen possible cases: index into case-table to find edges Interpolate along edges to find intersection points Note ambiguity in cases 5 and 10!

Page 9: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

Marching Cubes ... and beyond

3D surface generalizes 2D case:

Isolines become surfaces composed of triangles

16-case lookup table becomes 256-case table

(15 cases if we use symmetry)

Tetrahedral cells also common

Other cell types possible

common pattern of processing

need appropriate case-table

Page 10: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

Implementation 1: Functional Arrays

Basic typestype XYZ = (Int,Int,Int)

type Num a => Dataset a = Array XYZ a

type Cell a = (a,a,a,a,a,a,a,a)

Top-level traversalisoA :: (Ord a, Intgeral a) => a -> Dataset a -> [Triangle]isoA th sampleArr

= concat . zipWith1 (mcubeA th lookup) addrs

where

addrs = [ (i,j,k) | k <- [1..ksz-1], j <- [1..jsz-1], i <- [1..isz-1]]

lookup arr (x,y,z) = (arr!(x,y,z), arr!(x+1,y,z), .., arr!(x+1,y+1,z+1))

“Worker” functionmcubeA :: (Ord a, Intgeral a) => a -> (XYZ -> Cell a) -> XYZ -> [Triangle]

mcubeA th lookup xyz

= group3 . map (interp th cell xyz) . mctable! . toByte . map8 (>th) $ cell

where

cell = lookup xyz

Page 11: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

Problems

Entire dataset must be resident in memory Vertex shared by n cells threshold comparison repeated n times > 1 triangle in a cell => edge interpolation repeated within cell Edge shared by m cells interpolation repeated m times

Page 12: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

Thinking differently - streaming

mkStream :: XYZ -> [a] -> [Cell a]

mkStream (isz,jsz,ksz) origin =

zip8 origin (drop 1 origin)

(drop (line+1) origin) (drop line origin)

(drop plane origin) (drop (plane+1) origin)

(drop (planeline+1) origin) (drop planeline origin)

where

line = isz

plane = isz * jsz

planeline = plane + line

line

plane

8-t

uple

...

...

...

...

Page 13: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

Discontinuities

Two solutions:

Rewrite mkStream, considering dataset boundaries; or

Strip phantom cells from output of mkStream

disContinuities :: XYZ -> [b] -> [b]

disContinuities (isz,jsz,ksz) = step (0,0,0)

where

step (i,j,k) (x:xs)

| i==(isz-1) = step (0,j+1,k) xs

| j==(jsz-1) = step (0,0,k+1) (drop (isz-1) xs)

| k==(ksz-1) = []

| otherwise = x : step (i+1,j,k) xs

cellStream = disContinuities size . stream

Page 14: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

Implementations 2 & 3: Streams

Version 2: replace array lookup with stream access

isoS th samples

= concat . zipWith2 (mcubeS th) addrs cells

where cells = stream size samples

mcubeS :: a -> XYZ -> Cell a -> [Triangle]

mcubeS th xyz cell

= group3 . map (interp th cell xyz) . mctable! . toByte . map8 (>th) $ cell

Version 3: share vertex comparison by creating a stream of case-indices

isoT th samples

= concat . zipWith3 (mcubeS th) addrs cells indices

where indices = map toByte . stream . map (>th)

mcubeT :: a -> XYZ -> Cell a -> Byte -> [Triangle]

mcubeT th xyz cell index

= group3 . map (interp th cell xyz) . mctable! $ index

Further improvements explored in IEEE Visualization paper

Page 15: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

From generic cells ...

Functions already polymorphic .. generic over one or more type variables constraints may limit instantiation isoA :: (Ord a, Intgeral a, Fractional b) => a -> Dataset a -> [Triangle b]

... and abstracting from Cell type is (nearly) straightforward

mcubeRec :: (Num a, Floating b) => a -> XYZ -> CellR a -> [Triangle b]

mcubeRec th xyz cell

= group3 . map (interp th cell xyz ) . mcTable! . toByte8 . map8 (>th) $ cell

mcubeTet :: (Num a, Floating b) => a -> CellT a -> CellT b -> [Triangle b]mcubeTet th g cell verts = group3 . map (interp th cell verts) . mtTable! . toByte4 . map4 (>th) $ cell

Can capture general pattern within a type-class class Cell T where patch :: (Num a, Floating b) => a -> T a -> T b -> [Triangle b]

Page 16: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

... to generic meshes

Dealing with different mesh-type organizations is harder ... Regular meshes: implicit geometry and topology Irregular meshes: implicit geometry Unstructured meshes: geometry and topology explicit

Polytypic functions are independent of data organization Haskell data constructions isomorphic to sum-of-products type Foundation on categorical model of data type structure

Examples

data List a = Nil | Cons a (List a)-->List = 1 + (a x List)

data Tree a = Leaf a | Node (Tree a) a (Tree a)-->Tree = a + (Tree x a x Tree)

Page 17: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

Polytypism in practice

From Generic Haskell: Practice & Theory, Hinze & Jeuring, 2001 define generic function by induction over type structure generic version can then be instantiated for any SoP type

mapG {|t::kind|} :: Map {|kind|} t t

mapG {|Char|} c = c

mapG {|Int|} i = i

mapG {|Unit|} Unit = Unit

mapG {|:+:|} mapa mapb (InL a) = InL (mapa a)

mapG {|:+:|} mapa mapb (InR b) = InR (mapb b)

mapG {|:*:|} mapa mapb a :*: b = mapa a :*: mapb b

data Tree a = Leaf a | Node (Tree a) a (Tree a)

mapList = mapG {| List |} -- standard Haskell “map”

mapTree = mapG {| Tree |} -- apply function to each node in the tree

Research question: can we actually apply this idea to mesh traversal?

surface t = concat . mapG {| Mesh |} (\c -> patch t c)

Page 18: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

Sample Results

Page 19: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

Performance

Performance difference decreases with surface size

D.J. Duke, M. Wallace, R. Borgo, and C. Runciman,

Fine-grained visualization pipelines and lazy functional languages,

to appear in Proc. IEEE Vis’06

Page 20: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

Conclusions and Future Work

What we've achieved: re-constructed fundamental visualization algorithms Implemented fine-grained streaming demonstrated that FP can be (surprisingly) efficient

What we're doing now: generalizing from specific types of mesh exploring capabilities of generic programming

Where we are going next: grid-enabled Haskell pipelines some prior work: GRID-GUM, Michaelson, Trinder, Al Zain build into York Haskell Compiler (bytecode) RTS want simple, lightweight grid tools!

Page 21: School of Computing Faculty of Engineering Meshing with Grids: Toward Functional Abstractions for Grid-based Visualization Rita Borgo & David Duke Visualization.

Finally ...

Thanks to

EPSRC “Fundamental Computing for e-Science” Programme

Further information: hackage.haskell.org/trac/PolyFunViz/

Any Questions?