scenegraph-0.2.0.1: Scene Graph
Safe HaskellNone
LanguageHaskell2010

Graphics.SceneGraph.Basic

Synopsis

Documentation

data OSGState g Source #

Holds state of graph as it is built.

Constructors

OSGState 

Fields

Instances

Instances details
Eq (OSGState g) Source # 
Instance details

Defined in Graphics.SceneGraph.Basic

Methods

(==) :: OSGState g -> OSGState g -> Bool #

(/=) :: OSGState g -> OSGState g -> Bool #

Show (OSGState g) Source # 
Instance details

Defined in Graphics.SceneGraph.Basic

Methods

showsPrec :: Int -> OSGState g -> ShowS #

show :: OSGState g -> String #

showList :: [OSGState g] -> ShowS #

Default (OSGState g) Source # 
Instance details

Defined in Graphics.SceneGraph.Basic

Methods

def :: OSGState g #

type OSGT m g = StateT (OSGState g) m Source #

The OSG monad within which construction of scene graphs occur. was 'type OSGT m = ErrorT Throwable (ST.StateT OSGState m)'

type OSGSceneT m g = OSGT m g (SceneNode g) Source #

type OSG g = OSGT Identity g Source #

runOSG :: Monad m => OSGState g -> OSGSceneT m g -> m (SceneNode g, OSGState g, Node) Source #

Create and run a OSG monad to return a scene graph and root node.

osg :: Monad m => OSGSceneT m g -> m (Scene g) Source #

Wrapper for running the OSG monad to return a scene graph and root node.

addNodeBasic :: Monad m => SceneNode g -> OSGSceneT m g Source #

Basic add node

addBasicNode :: Monad m => SceneData g -> OSGSceneT m g Source #

Add node with scene data

addBasicNamedNode :: Monad m => String -> SceneData g -> OSGSceneT m g Source #

Add node with scene data

addNullNode :: Monad m => OSGSceneT m g Source #

Add empty node

addNode :: Monad m => SceneNode g -> [(SceneEdge, Node)] -> OSGSceneT m g Source #

Add a node to a scene graph with supplied children

addNode' :: OSGState g -> SceneNode g -> [(SceneEdge, Node)] -> (SceneNode g, OSGState g) Source #

Non-monadic form of addNode

replaceNode :: Monad m => SceneNode g -> OSGSceneT m g Source #

Replace a Scene Node

replaceNode' :: Monad md => SceneGraph g -> SceneNode g -> md (SceneGraph g) Source #

Inner monad version of replace node

replaceNode'' :: SceneGraph g -> SceneNode g -> SceneGraph g Source #

Actually does the job of replacing node in a scene graph

runOSGL :: Monad m => OSGState g -> OSGSceneT m g -> OSGT m g (SceneNode g, OSGState g, Node) Source #

Run the monad but keep it in the family.

runOSGL' :: Monad m => OSGSceneT m g -> OSGT m g (SceneNode g, Node) Source #

Run the monad but keep it in the family.

doOnNode :: Monad m => OSGSceneT m g -> (SceneNode g -> SceneNode g) -> OSGSceneT m g Source #

Perform a function on a scene node

light :: Monad m => OSGSceneT m g Source #

Create a light

camera :: Monad m => OSGSceneT m g Source #

Create a camera

mesh :: Monad m => Text -> g -> OSGSceneT m g Source #

Create a camera

fi :: (Integral a, Integral b) => a -> b Source #

scaleS :: Monad m => Float -> OSGSceneT m g -> OSGSceneT m g Source #

Scale a node by equal amounts in all directions

scale :: Monad m => V3 Float -> OSGSceneT m g -> OSGSceneT m g Source #

Scale a node

translate :: Monad m => V3 Float -> OSGSceneT m g -> OSGSceneT m g Source #

Translate a node

rotate :: Monad m => (Float, V3 Float) -> OSGSceneT m g -> OSGSceneT m g Source #

Rotate a node by an angle around a vector.

rotateX :: Monad m => Float -> OSGSceneT m g -> OSGSceneT m g Source #

Rotate a node around X axis

rotateY :: Monad m => Float -> OSGSceneT m g -> OSGSceneT m g Source #

Rotate a node around Y axis

rotateZ :: Monad m => Float -> OSGSceneT m g -> OSGSceneT m g Source #

Rotate a node around Z axis

colourSG :: Monad m => OSGSceneT m g -> (Phong -> Phong) -> (OSGSceneT m g -> OSGSceneT m g) -> OSGSceneT m g Source #

Apply colour to the node

transformSG :: Monad m => (M44 Float -> M44 Float) -> (OSGSceneT m g -> OSGSceneT m g) -> OSGSceneT m g -> OSGSceneT m g Source #

Transform the node of a scene graph within the Monad with the supplied matrix transform

transformSG' :: SceneGraph g -> Node -> (M44 Float -> M44 Float) -> SceneGraph g Source #

Transform the node of a scene graph with the supplied matrix transform

color :: Monad m => Color -> OSGSceneT m g -> OSGSceneT m g Source #

Add color to a node

label :: Monad m => OSGSceneT m g -> String -> OSGSceneT m g Source #

Label a node

texture :: Monad m => OSGSceneT m g -> String -> OSGSceneT m g Source #

Add texture

text :: Monad m => Text -> OSGSceneT m g Source #

(<+>) :: Monad m => OSGSceneT m g -> OSGSceneT m g -> OSGSceneT m g infixr 5 Source #

Join two graphs together

(<->) :: Monad m => OSGSceneT m g -> V3 Float -> OSGSceneT m g infixl 9 Source #

Translate a node

(</>) :: Monad m => OSGSceneT m g -> V3 Float -> OSGSceneT m g infixl 9 Source #

Scale a node

doNothing :: Monad m => p -> m () Source #

handler :: Monad m => OSGSceneT m g -> ClickHandler g -> OSGSceneT m g Source #

Add an handler node

dragHandler :: DragHandler g Source #

Create a DragHandler

switchHandler :: ClickHandler g Source #

Create a ClickHandler

switch :: Monad m => OSGSceneT m g -> OSGSceneT m g -> OSGSceneT m g Source #

Create a switch node

switch' :: Monad m => Int -> OSGSceneT m g -> OSGSceneT m g -> OSGSceneT m g Source #

group :: Monad m => [SceneNode g] -> OSGSceneT m g Source #

Make a group node from list of nodes

findHandler :: SceneGraph g -> Int -> Maybe (SceneNode g) Source #

Work up the tree from indicated no to find the first handler scene node.

findHandlerDown :: SceneGraph g -> Int -> Int Source #

Work down the tree from indicated no to find the first handler scene node.

handleClickEvent :: Scene g -> Int -> KeyState -> IO (Scene g, Maybe (Scene g), Maybe (SceneGraph g -> SceneGraph g)) Source #

Handle some event

getTransformTo :: Scene g -> Node -> M44 Float Source #

Return the matrix got by traversing down the Node