ombra-1.0.0.0: Render engine.

LicenseBSD3
Maintainerziocroc@gmail.com
Stabilityexperimental
PortabilityGHC only
Safe HaskellNone
LanguageHaskell2010

Graphics.Rendering.Ombra.Geometry

Contents

Description

 

Synopsis

Documentation

data Geometry g Source #

A set of triangles.

Instances

Eq (Geometry is) Source # 

Methods

(==) :: Geometry is -> Geometry is -> Bool #

(/=) :: Geometry is -> Geometry is -> Bool #

Hashable (Geometry is) Source # 

Methods

hashWithSalt :: Int -> Geometry is -> Int #

hash :: Geometry is -> Int #

data Triangle a Source #

Constructors

Triangle a a a 

Instances

Functor Triangle Source # 

Methods

fmap :: (a -> b) -> Triangle a -> Triangle b #

(<$) :: a -> Triangle b -> Triangle a #

Hashable a => Hashable (Triangle a) Source # 

Methods

hashWithSalt :: Int -> Triangle a -> Int #

hash :: Triangle a -> Int #

mkGeometry :: (GLES, GeometryVertex g) => [Triangle (Vertex g)] -> Geometry g Source #

Create a Geometry using a list of triangles.

mapVertices :: forall a g g'. (GLES, GeometryVertex g, GeometryVertex g') => (Triangle (Vertex g) -> a) -> ([a] -> Vertex g -> Vertex g') -> Geometry g -> Geometry g' Source #

Transform each vertex of a geometry. You can create a value for each triangle so that the transforming function will receive a list of the values of the triangles the vertex belongs to.

decompose :: GeometryVertex g => Geometry g -> [Triangle (Vertex g)] Source #

Convert a Geometry back to a list of triangles.

Geometry builder

class Empty is ~ False => Attributes is Source #

Minimal complete definition

emptyAttrCol, cell, addTop, foldTop, rowToVertexAttributes

Instances

(BaseAttribute i1, Eq (CPUBase i1), Attributes ((:) * i2 is), Hashable (CPUBase i1)) => Attributes ((:) * i1 ((:) * i2 is)) Source # 

Methods

emptyAttrCol :: AttrCol ((* ': i1) ((* ': i2) is))

cell :: VertexAttributes ((* ': i1) ((* ': i2) is)) -> AttrTable p ((* ': i1) ((* ': i2) is)) -> AttrTable (Previous p) ((* ': i1) ((* ': i2) is))

addTop :: VertexAttributes ((* ': i1) ((* ': i2) is)) -> AttrCol ((* ': i1) ((* ': i2) is)) -> AttrCol ((* ': i1) ((* ': i2) is))

foldTop :: (forall i is0. BaseAttribute i => b -> AttrCol ((* ': i) is0) -> b) -> b -> AttrCol ((* ': i1) ((* ': i2) is)) -> b

rowToVertexAttributes :: NotTop p => AttrTable p ((* ': i1) ((* ': i2) is)) -> VertexAttributes ((* ': i1) ((* ': i2) is))

(BaseAttribute i, Eq (CPUBase i), Hashable (CPUBase i)) => Attributes ((:) * i ([] *)) Source # 

Methods

emptyAttrCol :: AttrCol ((* ': i) [*])

cell :: VertexAttributes ((* ': i) [*]) -> AttrTable p ((* ': i) [*]) -> AttrTable (Previous p) ((* ': i) [*])

addTop :: VertexAttributes ((* ': i) [*]) -> AttrCol ((* ': i) [*]) -> AttrCol ((* ': i) [*])

foldTop :: (forall a is. BaseAttribute a => b -> AttrCol ((* ': a) is) -> b) -> b -> AttrCol ((* ': i) [*]) -> b

rowToVertexAttributes :: NotTop p => AttrTable p ((* ': i) [*]) -> VertexAttributes ((* ': i) [*])

data AttrVertex is Source #

A vertex in a Geometry.

Instances

Eq (AttrVertex is) Source # 

Methods

(==) :: AttrVertex is -> AttrVertex is -> Bool #

(/=) :: AttrVertex is -> AttrVertex is -> Bool #

Hashable (AttrVertex is) Source # 

Methods

hashWithSalt :: Int -> AttrVertex is -> Int #

hash :: AttrVertex is -> Int #

data GeometryBuilderT g m a Source #

Instances

MonadTrans (GeometryBuilderT g) Source # 

Methods

lift :: Monad m => m a -> GeometryBuilderT g m a #

Monad m => Monad (GeometryBuilderT g m) Source # 

Methods

(>>=) :: GeometryBuilderT g m a -> (a -> GeometryBuilderT g m b) -> GeometryBuilderT g m b #

(>>) :: GeometryBuilderT g m a -> GeometryBuilderT g m b -> GeometryBuilderT g m b #

return :: a -> GeometryBuilderT g m a #

fail :: String -> GeometryBuilderT g m a #

Functor m => Functor (GeometryBuilderT g m) Source # 

Methods

fmap :: (a -> b) -> GeometryBuilderT g m a -> GeometryBuilderT g m b #

(<$) :: a -> GeometryBuilderT g m b -> GeometryBuilderT g m a #

Monad m => Applicative (GeometryBuilderT g m) Source # 

Methods

pure :: a -> GeometryBuilderT g m a #

(<*>) :: GeometryBuilderT g m (a -> b) -> GeometryBuilderT g m a -> GeometryBuilderT g m b #

(*>) :: GeometryBuilderT g m a -> GeometryBuilderT g m b -> GeometryBuilderT g m b #

(<*) :: GeometryBuilderT g m a -> GeometryBuilderT g m b -> GeometryBuilderT g m a #

vertex :: (Monad m, GeometryVertex g) => Vertex g -> GeometryBuilderT g m (AttrVertex (AttributeTypes g)) Source #

Create a new vertex that can be used in addTriangle.

triangle :: (Monad m, GeometryVertex g) => AttrVertex (AttributeTypes g) -> AttrVertex (AttributeTypes g) -> AttrVertex (AttributeTypes g) -> GeometryBuilderT g m () Source #

Add a triangle to the current geometry.

buildGeometry :: GeometryVertex g => GeometryBuilder g () -> Geometry g Source #

Create a Geometry using the GeometryBuilder monad. This is more efficient than mkGeometry.

class Attributes (AttributeTypes a) => GeometryVertex a where Source #

Types that can be used as Geometry vertices.

Associated Types

type AttributeTypes a :: [*] Source #

type Vertex a = v | v -> a Source #

Methods

toVertexAttributes :: Vertex a -> VertexAttributes (AttributeTypes a) Source #

toVertexAttributes :: (Generic a, Generic (Vertex a), GGeometryVertex (Rep a) (Rep (Vertex a)), VertexAttributes (AttributeTypes a) ~ VertexAttributes (GAttributeTypes (Rep a) (Rep (Vertex a)))) => Vertex a -> VertexAttributes (AttributeTypes a) Source #

fromVertexAttributes :: VertexAttributes (AttributeTypes a) -> Vertex a Source #

fromVertexAttributes :: (Generic a, Generic (Vertex a), GGeometryVertex (Rep a) (Rep (Vertex a)), VertexAttributes (AttributeTypes a) ~ VertexAttributes (GAttributeTypes (Rep a) (Rep (Vertex a)))) => VertexAttributes (AttributeTypes a) -> Vertex a Source #

Instances

GLES => GeometryVertex GIVec4 Source # 

Associated Types

type AttributeTypes GIVec4 :: [*] Source #

type Vertex GIVec4 = (v :: *) Source #

GLES => GeometryVertex GIVec3 Source # 

Associated Types

type AttributeTypes GIVec3 :: [*] Source #

type Vertex GIVec3 = (v :: *) Source #

GLES => GeometryVertex GIVec2 Source # 

Associated Types

type AttributeTypes GIVec2 :: [*] Source #

type Vertex GIVec2 = (v :: *) Source #

GLES => GeometryVertex GVec4 Source # 

Associated Types

type AttributeTypes GVec4 :: [*] Source #

type Vertex GVec4 = (v :: *) Source #

GLES => GeometryVertex GVec3 Source # 

Associated Types

type AttributeTypes GVec3 :: [*] Source #

type Vertex GVec3 = (v :: *) Source #

GLES => GeometryVertex GVec2 Source # 

Associated Types

type AttributeTypes GVec2 :: [*] Source #

type Vertex GVec2 = (v :: *) Source #

GLES => GeometryVertex GInt Source # 

Associated Types

type AttributeTypes GInt :: [*] Source #

type Vertex GInt = (v :: *) Source #

GLES => GeometryVertex GFloat Source # 

Associated Types

type AttributeTypes GFloat :: [*] Source #

type Vertex GFloat = (v :: *) Source #

GLES => GeometryVertex GBool Source # 

Associated Types

type AttributeTypes GBool :: [*] Source #

type Vertex GBool = (v :: *) Source #

(GeometryVertex a, GeometryVertex b, BreakVertex (AttributeTypes a) (AttributeTypes b), AppendVertex (AttributeTypes a) (AttributeTypes b)) => GeometryVertex (a, b) Source # 

Associated Types

type AttributeTypes (a, b) :: [*] Source #

type Vertex (a, b) = (v :: *) Source #

Methods

toVertexAttributes :: Vertex (a, b) -> VertexAttributes (AttributeTypes (a, b)) Source #

fromVertexAttributes :: VertexAttributes (AttributeTypes (a, b)) -> Vertex (a, b) Source #

(GeometryVertex a, GeometryVertex b, GeometryVertex c, BreakVertex (AttributeTypes a) (Append (AttributeTypes b) (AttributeTypes c)), BreakVertex (AttributeTypes b) (AttributeTypes c), AppendVertex (AttributeTypes a) (Append (AttributeTypes b) (AttributeTypes c)), AppendVertex (AttributeTypes b) (AttributeTypes c)) => GeometryVertex (a, b, c) Source # 

Associated Types

type AttributeTypes (a, b, c) :: [*] Source #

type Vertex (a, b, c) = (v :: *) Source #

Methods

toVertexAttributes :: Vertex (a, b, c) -> VertexAttributes (AttributeTypes (a, b, c)) Source #

fromVertexAttributes :: VertexAttributes (AttributeTypes (a, b, c)) -> Vertex (a, b, c) Source #