Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data AttrList is where
- AttrListNil :: AttrList []
- AttrListCons :: (Hashable c, AttributeCPU c g, ShaderType g) => (a -> g) -> [c] -> AttrList gs -> AttrList (g : gs)
- data Geometry is = Geometry (AttrList is) [Word16] Int
- type Geometry2D = `[Position2, UV]`
- type Geometry3D = `[Position3, UV, Normal3]`
- data GPUBufferGeometry = GPUBufferGeometry {
- attributeBuffers :: [(Buffer, GLUInt, GLUInt -> GL ())]
- elementBuffer :: Buffer
- elementCount :: Int
- geometryHash :: Int
- data GPUVAOGeometry = GPUVAOGeometry {}
- extend :: t
- remove :: t
- withGPUBufferGeometry :: GLES => GPUBufferGeometry -> (Int -> [Buffer] -> GL a) -> GL a
- mkGeometry :: GLES => AttrList is -> [Word16] -> Geometry is
- mkGeometry2D :: GLES => [Vec2] -> [Vec2] -> [Word16] -> Geometry Geometry2D
- mkGeometry3D :: GLES => [Vec3] -> [Vec2] -> [Vec3] -> [Word16] -> Geometry Geometry3D
- castGeometry :: Geometry is -> Geometry is'
- facesToArrays :: Vector Vec3 -> Vector Vec2 -> Vector Vec3 -> [[(Int, Int, Int)]] -> [(Vec3, Vec2, Vec3)]
- arraysToElements :: Foldable f => f (Vec3, Vec2, Vec3) -> ([Vec3], [Vec2], [Vec3], [Word16])
- triangulate :: [a] -> [(a, a, a)]
Documentation
A heterogeneous list of attributes.
AttrListNil :: AttrList [] | |
AttrListCons :: (Hashable c, AttributeCPU c g, ShaderType g) => (a -> g) -> [c] -> AttrList gs -> AttrList (g : gs) |
A set of attributes and indices.
type Geometry2D = `[Position2, UV]` Source
A 2D geometry.
type Geometry3D = `[Position3, UV, Normal3]` Source
A 3D geometry.
data GPUBufferGeometry Source
GPUBufferGeometry | |
|
data GPUVAOGeometry Source
withGPUBufferGeometry :: GLES => GPUBufferGeometry -> (Int -> [Buffer] -> GL a) -> GL a Source
:: GLES | |
=> [Vec2] | List of vertices. |
-> [Vec2] | List of UV coordinates. |
-> [Word16] | Triangles expressed as triples of indices to the two lists above. |
-> Geometry Geometry2D |
Create a 2D Geometry
. The first two lists should have the same length.
:: GLES | |
=> [Vec3] | List of vertices. |
-> [Vec2] | List of UV coordinates. |
-> [Vec3] | List of normals. |
-> [Word16] | Triangles expressed as triples of indices to the three lists above. |
-> Geometry Geometry3D |
Create a 3D Geometry
. The first three lists should have the same length.
castGeometry :: Geometry is -> Geometry is' Source
facesToArrays :: Vector Vec3 -> Vector Vec2 -> Vector Vec3 -> [[(Int, Int, Int)]] -> [(Vec3, Vec2, Vec3)] Source
triangulate :: [a] -> [(a, a, a)] Source