| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Graphics.GPipe.Internal.PrimitiveArray
Synopsis
- data VertexArray t a = VertexArray {
- vertexArrayLength :: Int
- vertexArraySkip :: Int
- bArrBFunc :: BInput -> a
- data Instances
- newVertexArray :: Buffer os a -> Render os (VertexArray t a)
- zipVertices :: (a -> b -> c) -> VertexArray t a -> VertexArray t' b -> VertexArray (Combine t t') c
- type family Combine t t' where ...
- takeVertices :: Int -> VertexArray t a -> VertexArray t a
- dropVertices :: Int -> VertexArray () a -> VertexArray t a
- replicateEach :: Int -> VertexArray t a -> VertexArray Instances a
- type family IndexFormat a where ...
- data IndexArray = IndexArray {}
- newIndexArray :: forall os f b a. (BufferFormat b, Integral a, IndexFormat b ~ a) => Buffer os b -> Maybe a -> Render os IndexArray
- takeIndices :: Int -> IndexArray -> IndexArray
- dropIndices :: Int -> IndexArray -> IndexArray
- data Points = PointList
- data Lines
- data LinesWithAdjacency
- data Triangles
- data TrianglesWithAdjacency
- class PrimitiveTopology p where
- data Geometry p a
- toGLtopology :: p -> GLuint
- toPrimitiveSize :: p -> Int
- toGeometryShaderOutputTopology :: p -> GLuint
- toLayoutIn :: p -> String
- toLayoutOut :: p -> String
- type InstanceCount = Int
- type BaseVertex = Int
- data PrimitiveArrayInt p a
- newtype PrimitiveArray p a = PrimitiveArray {
- getPrimitiveArray :: [PrimitiveArrayInt p a]
- toPrimitiveArray :: PrimitiveTopology p => p -> VertexArray () a -> PrimitiveArray p a
- toPrimitiveArrayIndexed :: PrimitiveTopology p => p -> IndexArray -> VertexArray () a -> PrimitiveArray p a
- toPrimitiveArrayInstanced :: PrimitiveTopology p => p -> (a -> b -> c) -> VertexArray () a -> VertexArray t b -> PrimitiveArray p c
- toPrimitiveArrayIndexedInstanced :: PrimitiveTopology p => p -> IndexArray -> (a -> b -> c) -> VertexArray () a -> VertexArray t b -> PrimitiveArray p c
Documentation
data VertexArray t a Source #
A vertex array is the basic building block for a primitive array. It is created from the contents of a Buffer, but unlike a Buffer,
it may be truncated, zipped with other vertex arrays, and even morphed into arrays of a different type with the provided Functor instance.
A VertexArray t a has elements of type a, and t indicates whether the vertex array may be used as instances or not.
Constructors
| VertexArray | |
Fields
| |
Instances
| Functor (VertexArray t) Source # | |
Defined in Graphics.GPipe.Internal.PrimitiveArray Methods fmap :: (a -> b) -> VertexArray t a -> VertexArray t b # (<$) :: a -> VertexArray t b -> VertexArray t a # | |
A phantom type to indicate that a VertexArray may only be used for instances (in toPrimitiveArrayInstanced and toPrimitiveArrayIndexedInstanced).
newVertexArray :: Buffer os a -> Render os (VertexArray t a) Source #
Create a VertexArray from a Buffer. The vertex array will have the same number of elements as the buffer, use takeVertices and dropVertices to make it smaller.
zipVertices :: (a -> b -> c) -> VertexArray t a -> VertexArray t' b -> VertexArray (Combine t t') c Source #
Zip two VertexArrays using the function given as first argument. If either of the argument VertexArrays are restriced to Instances only, then so will the resulting
array be, as depicted by the Combine type family.
takeVertices :: Int -> VertexArray t a -> VertexArray t a Source #
takeVertices n a creates a shorter vertex array by taking the n first elements of the array a.
dropVertices :: Int -> VertexArray () a -> VertexArray t a Source #
dropVertices n a creates a shorter vertex array by dropping the n first elements of the array a. The argument array a must not be
constrained to only Instances.
replicateEach :: Int -> VertexArray t a -> VertexArray Instances a Source #
replicateEach n a will create a longer vertex array, only to be used for instances, by replicating each element of the array a n times. E.g.
replicateEach 3 {ABCD...} will yield {AAABBBCCCDDD...}. This is particulary useful before zipping the array with another that has a different replication rate.
type family IndexFormat a where ... Source #
Equations
| IndexFormat (B Word32) = Word32 | |
| IndexFormat (BPacked Word16) = Word16 | |
| IndexFormat (BPacked Word8) = Word8 |
data IndexArray Source #
An index array is like a vertex array, but contains only integer indices. These indices must come from a tightly packed Buffer, hence the lack of
a Functor instance and no conversion from VertexArrays.
Constructors
| IndexArray | |
newIndexArray :: forall os f b a. (BufferFormat b, Integral a, IndexFormat b ~ a) => Buffer os b -> Maybe a -> Render os IndexArray Source #
Create an IndexArray from a Buffer of unsigned integers (as constrained by the closed IndexFormat type family instances). The index array will have the same number of elements as the buffer, use takeIndices and dropIndices to make it smaller.
The Maybe a argument is used to optionally denote a primitive restart index.
takeIndices :: Int -> IndexArray -> IndexArray Source #
takeIndices n a creates a shorter index array by taking the n first indices of the array a.
dropIndices :: Int -> IndexArray -> IndexArray Source #
dropIndices n a creates a shorter index array by dropping the n first indices of the array a.
Constructors
| PointList |
Instances
| PrimitiveTopology Points Source # | |
Defined in Graphics.GPipe.Internal.PrimitiveArray Methods toGLtopology :: Points -> GLuint Source # toPrimitiveSize :: Points -> Int Source # toGeometryShaderOutputTopology :: Points -> GLuint Source # toLayoutIn :: Points -> String Source # toLayoutOut :: Points -> String Source # | |
| AnotherVertexInput a => GeometryInput Points a Source # | |
Defined in Graphics.GPipe.Internal.GeometryStream Methods toGeometry :: ToGeometry a (Geometry Points a) Source # | |
| data Geometry Points a Source # | |
Defined in Graphics.GPipe.Internal.PrimitiveArray | |
Instances
| PrimitiveTopology Lines Source # | |
Defined in Graphics.GPipe.Internal.PrimitiveArray Methods toGLtopology :: Lines -> GLuint Source # toPrimitiveSize :: Lines -> Int Source # toGeometryShaderOutputTopology :: Lines -> GLuint Source # toLayoutIn :: Lines -> String Source # toLayoutOut :: Lines -> String Source # | |
| AnotherVertexInput a => GeometryInput Lines a Source # | |
Defined in Graphics.GPipe.Internal.GeometryStream Methods toGeometry :: ToGeometry a (Geometry Lines a) Source # | |
| data Geometry Lines a Source # | |
Defined in Graphics.GPipe.Internal.PrimitiveArray | |
data LinesWithAdjacency Source #
Constructors
| LineListAdjacency | |
| LineStripAdjacency |
Instances
| PrimitiveTopology LinesWithAdjacency Source # | |
Defined in Graphics.GPipe.Internal.PrimitiveArray Associated Types data Geometry LinesWithAdjacency a Source # | |
| AnotherVertexInput a => GeometryInput LinesWithAdjacency a Source # | |
Defined in Graphics.GPipe.Internal.GeometryStream Methods toGeometry :: ToGeometry a (Geometry LinesWithAdjacency a) Source # | |
| data Geometry LinesWithAdjacency a Source # | |
Defined in Graphics.GPipe.Internal.PrimitiveArray | |
Constructors
| TriangleList | |
| TriangleStrip |
Instances
| PrimitiveTopology Triangles Source # | |
Defined in Graphics.GPipe.Internal.PrimitiveArray Methods toGLtopology :: Triangles -> GLuint Source # toPrimitiveSize :: Triangles -> Int Source # toGeometryShaderOutputTopology :: Triangles -> GLuint Source # toLayoutIn :: Triangles -> String Source # toLayoutOut :: Triangles -> String Source # | |
| FragmentCreator a => FragmentInputFromGeometry Triangles a Source # | |
Defined in Graphics.GPipe.Internal.GeometryStream Methods toFragmentFromGeometry :: ToFragmentFromGeometry (GGenerativeGeometry Triangles (b, a)) (FragmentFormat a) Source # | |
| AnotherVertexInput a => GeometryInput Triangles a Source # | |
Defined in Graphics.GPipe.Internal.GeometryStream Methods toGeometry :: ToGeometry a (Geometry Triangles a) Source # | |
| data Geometry Triangles a Source # | |
Defined in Graphics.GPipe.Internal.PrimitiveArray | |
data TrianglesWithAdjacency Source #
Constructors
| TriangleListAdjacency | |
| TriangleStripAdjacency |
Instances
| PrimitiveTopology TrianglesWithAdjacency Source # | |
Defined in Graphics.GPipe.Internal.PrimitiveArray Associated Types data Geometry TrianglesWithAdjacency a Source # | |
| AnotherVertexInput a => GeometryInput TrianglesWithAdjacency a Source # | |
Defined in Graphics.GPipe.Internal.GeometryStream Methods toGeometry :: ToGeometry a (Geometry TrianglesWithAdjacency a) Source # | |
| data Geometry TrianglesWithAdjacency a Source # | |
Defined in Graphics.GPipe.Internal.PrimitiveArray | |
class PrimitiveTopology p where Source #
Methods
toGLtopology :: p -> GLuint Source #
toPrimitiveSize :: p -> Int Source #
toGeometryShaderOutputTopology :: p -> GLuint Source #
toLayoutIn :: p -> String Source #
toLayoutOut :: p -> String Source #
Instances
type InstanceCount = Int Source #
type BaseVertex = Int Source #
data PrimitiveArrayInt p a Source #
newtype PrimitiveArray p a Source #
An array of primitives
Constructors
| PrimitiveArray | |
Fields
| |
Instances
| Functor (PrimitiveArray p) Source # | |
Defined in Graphics.GPipe.Internal.PrimitiveArray Methods fmap :: (a -> b) -> PrimitiveArray p a -> PrimitiveArray p b # (<$) :: a -> PrimitiveArray p b -> PrimitiveArray p a # | |
| Semigroup (PrimitiveArray p a) Source # | |
Defined in Graphics.GPipe.Internal.PrimitiveArray Methods (<>) :: PrimitiveArray p a -> PrimitiveArray p a -> PrimitiveArray p a # sconcat :: NonEmpty (PrimitiveArray p a) -> PrimitiveArray p a # stimes :: Integral b => b -> PrimitiveArray p a -> PrimitiveArray p a # | |
| Monoid (PrimitiveArray p a) Source # | |
Defined in Graphics.GPipe.Internal.PrimitiveArray Methods mempty :: PrimitiveArray p a # mappend :: PrimitiveArray p a -> PrimitiveArray p a -> PrimitiveArray p a # mconcat :: [PrimitiveArray p a] -> PrimitiveArray p a # | |
toPrimitiveArray :: PrimitiveTopology p => p -> VertexArray () a -> PrimitiveArray p a Source #
toPrimitiveArrayIndexed :: PrimitiveTopology p => p -> IndexArray -> VertexArray () a -> PrimitiveArray p a Source #
toPrimitiveArrayInstanced :: PrimitiveTopology p => p -> (a -> b -> c) -> VertexArray () a -> VertexArray t b -> PrimitiveArray p c Source #
toPrimitiveArrayIndexedInstanced :: PrimitiveTopology p => p -> IndexArray -> (a -> b -> c) -> VertexArray () a -> VertexArray t b -> PrimitiveArray p c Source #