ombra-1.1.0.0: Render engine.

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

Graphics.Rendering.Ombra.Geometry

Contents

Description

 

Synopsis

Documentation

data Geometry e g Source #

A set of triangles.

Instances

Eq (Geometry e is) Source # 

Methods

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

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

Hashable (Geometry e is) Source # 

Methods

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

hash :: Geometry e is -> Int #

data Point a Source #

Constructors

Point a 

Instances

Functor Point Source # 

Methods

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

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

Foldable Point Source # 

Methods

fold :: Monoid m => Point m -> m #

foldMap :: Monoid m => (a -> m) -> Point a -> m #

foldr :: (a -> b -> b) -> b -> Point a -> b #

foldr' :: (a -> b -> b) -> b -> Point a -> b #

foldl :: (b -> a -> b) -> b -> Point a -> b #

foldl' :: (b -> a -> b) -> b -> Point a -> b #

foldr1 :: (a -> a -> a) -> Point a -> a #

foldl1 :: (a -> a -> a) -> Point a -> a #

toList :: Point a -> [a] #

null :: Point a -> Bool #

length :: Point a -> Int #

elem :: Eq a => a -> Point a -> Bool #

maximum :: Ord a => Point a -> a #

minimum :: Ord a => Point a -> a #

sum :: Num a => Point a -> a #

product :: Num a => Point a -> a #

ElementType Point Source # 

Methods

elementType :: GLES => proxy Point -> GLEnum

elementFromList :: [a] -> Point a

Hashable a => Hashable (Point a) Source # 

Methods

hashWithSalt :: Int -> Point a -> Int #

hash :: Point a -> Int #

data Line a Source #

Constructors

Line a a 

Instances

Functor Line Source # 

Methods

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

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

Foldable Line Source # 

Methods

fold :: Monoid m => Line m -> m #

foldMap :: Monoid m => (a -> m) -> Line a -> m #

foldr :: (a -> b -> b) -> b -> Line a -> b #

foldr' :: (a -> b -> b) -> b -> Line a -> b #

foldl :: (b -> a -> b) -> b -> Line a -> b #

foldl' :: (b -> a -> b) -> b -> Line a -> b #

foldr1 :: (a -> a -> a) -> Line a -> a #

foldl1 :: (a -> a -> a) -> Line a -> a #

toList :: Line a -> [a] #

null :: Line a -> Bool #

length :: Line a -> Int #

elem :: Eq a => a -> Line a -> Bool #

maximum :: Ord a => Line a -> a #

minimum :: Ord a => Line a -> a #

sum :: Num a => Line a -> a #

product :: Num a => Line a -> a #

ElementType Line Source # 

Methods

elementType :: GLES => proxy Line -> GLEnum

elementFromList :: [a] -> Line a

Hashable a => Hashable (Line a) Source # 

Methods

hashWithSalt :: Int -> Line a -> Int #

hash :: Line a -> 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 #

Foldable Triangle Source # 

Methods

fold :: Monoid m => Triangle m -> m #

foldMap :: Monoid m => (a -> m) -> Triangle a -> m #

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

foldr' :: (a -> b -> b) -> b -> Triangle a -> b #

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

foldl' :: (b -> a -> b) -> b -> Triangle a -> b #

foldr1 :: (a -> a -> a) -> Triangle a -> a #

foldl1 :: (a -> a -> a) -> Triangle a -> a #

toList :: Triangle a -> [a] #

null :: Triangle a -> Bool #

length :: Triangle a -> Int #

elem :: Eq a => a -> Triangle a -> Bool #

maximum :: Ord a => Triangle a -> a #

minimum :: Ord a => Triangle a -> a #

sum :: Num a => Triangle a -> a #

product :: Num a => Triangle a -> a #

ElementType Triangle Source # 

Methods

elementType :: GLES => proxy Triangle -> GLEnum

elementFromList :: [a] -> Triangle a

Hashable a => Hashable (Triangle a) Source # 

Methods

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

hash :: Triangle a -> Int #

mkGeometry Source #

Arguments

:: (GLES, GeometryVertex g, ElementType e, Hashable (e (AttrVertex (AttributeTypes g)))) 
=> [e (Vertex g)]

List of elements.

-> Geometry e g 

Create a Geometry using a list of points, lines or triangles.

mapVertices Source #

Arguments

:: (GLES, GeometryVertex g, GeometryVertex g', ElementType e) 
=> (e (Vertex g) -> a)

Value to associate to each element.

-> ([a] -> Vertex g -> Vertex g')

The first argument is the list of values associated with the elements the vertex belongs to.

-> Geometry e g 
-> Geometry e g' 

Transform each vertex of a geometry.

foldGeometry :: forall g e vacc eacc. (GLES, GeometryVertex g, ElementType e) => (e (Vertex g) -> eacc -> eacc) -> (eacc -> Vertex g -> vacc -> vacc) -> eacc -> vacc -> Geometry e g -> (eacc, vacc) Source #

Fold elements and then vertices.

decompose :: (GeometryVertex g, Functor e) => Geometry e g -> [e (Vertex g)] Source #

Convert a Geometry back to a list of elements.

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 e g m a Source #

Instances

MonadTrans (GeometryBuilderT e g) Source # 

Methods

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

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

Methods

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

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

return :: a -> GeometryBuilderT e g m a #

fail :: String -> GeometryBuilderT e g m a #

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

Methods

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

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

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

Methods

pure :: a -> GeometryBuilderT e g m a #

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

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

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

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

Create a new vertex that can be used in triangle, line and point.

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

Add a point to the current geometry.

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

Add a line to the current geometry.

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

Add a triangle to the current geometry.

buildGeometry :: GeometryVertex g => GeometryBuilder e g () -> Geometry e 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 #

class (Functor e, Foldable e) => ElementType e Source #

Minimal complete definition

elementType, elementFromList