License | BSD3 |
---|---|
Maintainer | ziocroc@gmail.com |
Stability | experimental |
Portability | GHC only |
Safe Haskell | None |
Language | Haskell2010 |
Graphics.Rendering.Ombra.Geometry
Contents
Description
- data Geometry g
- data Triangle a = Triangle a a a
- mkGeometry :: (GLES, GeometryVertex g) => [Triangle (Vertex g)] -> Geometry g
- mapVertices :: forall a g g'. (GLES, GeometryVertex g, GeometryVertex g') => (Triangle (Vertex g) -> a) -> ([a] -> Vertex g -> Vertex g') -> Geometry g -> Geometry g'
- decompose :: GeometryVertex g => Geometry g -> [Triangle (Vertex g)]
- class Empty is ~ False => Attributes is
- data AttrVertex is
- type GeometryBuilder g = GeometryBuilderT g Identity
- data GeometryBuilderT g m a
- vertex :: (Monad m, GeometryVertex g) => Vertex g -> GeometryBuilderT g m (AttrVertex (AttributeTypes g))
- triangle :: (Monad m, GeometryVertex g) => AttrVertex (AttributeTypes g) -> AttrVertex (AttributeTypes g) -> AttrVertex (AttributeTypes g) -> GeometryBuilderT g m ()
- buildGeometry :: GeometryVertex g => GeometryBuilder g () -> Geometry g
- buildGeometryT :: (Monad m, GeometryVertex g) => GeometryBuilderT g m () -> m (Geometry g)
- class Attributes (AttributeTypes a) => GeometryVertex a where
- type AttributeTypes a :: [*]
- type Vertex a = v | v -> a
Documentation
A set of triangles.
Constructors
Triangle a a a |
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
data AttrVertex is Source #
A vertex in a Geometry
.
Instances
Eq (AttrVertex is) Source # | |
Hashable (AttrVertex is) Source # | |
type GeometryBuilder g = GeometryBuilderT g Identity Source #
data GeometryBuilderT g m a Source #
Instances
MonadTrans (GeometryBuilderT g) Source # | |
Monad m => Monad (GeometryBuilderT g m) Source # | |
Functor m => Functor (GeometryBuilderT g m) Source # | |
Monad m => Applicative (GeometryBuilderT g m) Source # | |
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
.
buildGeometryT :: (Monad m, GeometryVertex g) => GeometryBuilderT g m () -> m (Geometry g) Source #
class Attributes (AttributeTypes a) => GeometryVertex a where Source #
Types that can be used as Geometry
vertices.
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 # | |
GLES => GeometryVertex GIVec3 Source # | |
GLES => GeometryVertex GIVec2 Source # | |
GLES => GeometryVertex GVec4 Source # | |
GLES => GeometryVertex GVec3 Source # | |
GLES => GeometryVertex GVec2 Source # | |
GLES => GeometryVertex GInt Source # | |
GLES => GeometryVertex GFloat Source # | |
GLES => GeometryVertex GBool Source # | |
(GeometryVertex a, GeometryVertex b, BreakVertex (AttributeTypes a) (AttributeTypes b), AppendVertex (AttributeTypes a) (AttributeTypes b)) => GeometryVertex (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 # | |