Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data AttrList is where
- AttrListNil :: AttrList []
- AttrListCons :: (Hashable c, AttributeCPU c g) => g -> [c] -> AttrList gs -> AttrList (g : gs)
- data Geometry is = Geometry (AttrList is) [Word16] Int
- type Geometry2 = `[Position2, UV]`
- type Geometry3 = `[Position3, UV, Normal3]`
- data GPUGeometry = GPUGeometry {
- attributeBuffers :: [(String, Buffer, GLUInt -> GL ())]
- elementBuffer :: Buffer
- elementCount :: Int
- mkGeometry :: GLES => AttrList is -> [Word16] -> Geometry is
- mkGeometry2 :: GLES => [V2] -> [V2] -> [Word16] -> Geometry Geometry2
- mkGeometry3 :: GLES => [V3] -> [V2] -> [V3] -> [Word16] -> Geometry Geometry3
- castGeometry :: Geometry is -> Geometry is'
- facesToArrays :: Vector V3 -> Vector V2 -> Vector V3 -> [[(Int, Int, Int)]] -> [(V3, V2, V3)]
- arraysToElements :: Foldable f => f (V3, V2, V3) -> ([V3], [V2], [V3], [Word16])
- triangulate :: [a] -> [(a, a, a)]
Documentation
AttrListNil :: AttrList [] | |
AttrListCons :: (Hashable c, AttributeCPU c g) => g -> [c] -> AttrList gs -> AttrList (g : gs) |
A set of attributes and indices.
data GPUGeometry Source
GPUGeometry | |
|
:: GLES | |
=> [V2] | List of vertices. |
-> [V2] | List of UV coordinates. |
-> [Word16] | Triangles expressed as triples of indices to the two lists above. |
-> Geometry Geometry2 |
Create a 2D Geometry
. The first two lists should have the same length.
:: GLES | |
=> [V3] | List of vertices. |
-> [V2] | List of UV coordinates. |
-> [V3] | List of normals. |
-> [Word16] | Triangles expressed as triples of indices to the three lists above. |
-> Geometry Geometry3 |
Create a 3D Geometry
. The first three lists should have the same length.
castGeometry :: Geometry is -> Geometry is' Source
facesToArrays :: Vector V3 -> Vector V2 -> Vector V3 -> [[(Int, Int, Int)]] -> [(V3, V2, V3)] Source
triangulate :: [a] -> [(a, a, a)] Source