Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data GeometryStream a
- class AnotherFragmentInput a => FragmentCreator a where
- createFragment :: State Int a
- class AnotherVertexInput a where
- toAnotherVertex :: ToAnotherVertex a a
- class FragmentInput a => AnotherFragmentInput a where
- toFragment2 :: ToAnotherFragment a (FragmentFormat a)
- class FragmentInput a => GeometryExplosive a where
- exploseGeometry :: a -> Int -> ExprM Int
- declareGeometry :: a -> State Int (GlobDeclM ())
- enumerateVaryings :: a -> State Int [Text]
- class (AnotherVertexInput a, PrimitiveTopology p) => GeometryInput p a where
- toGeometry :: ToGeometry a (Geometry p a)
- geometrize :: forall p a s os f. GeometryInput p a => PrimitiveStream p a -> Shader os s (GeometryStream (Geometry p a))
- generateAndRasterize :: forall p b a s os f. (FragmentInputFromGeometry p a, PrimitiveTopology p) => (s -> (Side, PolygonMode, ViewPort, DepthRange)) -> Int -> GeometryStream (GGenerativeGeometry p (b, a)) -> Shader os s (FragmentStream (FragmentFormat a))
- generativePoints :: FragmentInput a => GGenerativeGeometry Points a
- generativeLineStrip :: FragmentInput a => GGenerativeGeometry Lines a
- generativeTriangleStrip :: FragmentInput a => GGenerativeGeometry Triangles a
- emitVertex :: GeometryExplosive a => a -> GGenerativeGeometry p a -> GGenerativeGeometry p a
- emitVertexPosition :: GeometryExplosive a => (VPos, a) -> GGenerativeGeometry p (VPos, a) -> GGenerativeGeometry p (VPos, a)
- emitVertexLayer :: GeometryExplosive a => (VInt, a) -> GGenerativeGeometry p (VInt, a) -> GGenerativeGeometry p (VInt, a)
- emitVertexPositionAndLayer :: GeometryExplosive a => ((VPos, VInt), a) -> GGenerativeGeometry p ((VPos, VInt), a) -> GGenerativeGeometry p ((VPos, VInt), a)
- endPrimitive :: GGenerativeGeometry p a -> GGenerativeGeometry p a
The data type
data GeometryStream a Source #
Instances
Functor GeometryStream Source # | |
Defined in Graphics.GPipe.Internal.GeometryStream fmap :: (a -> b) -> GeometryStream a -> GeometryStream b # (<$) :: a -> GeometryStream b -> GeometryStream a # | |
Semigroup (GeometryStream a) Source # | |
Defined in Graphics.GPipe.Internal.GeometryStream (<>) :: GeometryStream a -> GeometryStream a -> GeometryStream a # sconcat :: NonEmpty (GeometryStream a) -> GeometryStream a # stimes :: Integral b => b -> GeometryStream a -> GeometryStream a # | |
Monoid (GeometryStream a) Source # | |
Defined in Graphics.GPipe.Internal.GeometryStream mempty :: GeometryStream a # mappend :: GeometryStream a -> GeometryStream a -> GeometryStream a # mconcat :: [GeometryStream a] -> GeometryStream a # |
Needed to use custom data types with the geometry shader.
class AnotherFragmentInput a => FragmentCreator a where Source #
createFragment :: State Int a Source #
Instances
class AnotherVertexInput a where Source #
toAnotherVertex :: ToAnotherVertex a a Source #
Instances
class FragmentInput a => AnotherFragmentInput a where Source #
toFragment2 :: ToAnotherFragment a (FragmentFormat a) Source #
Instances
class FragmentInput a => GeometryExplosive a where Source #
exploseGeometry :: a -> Int -> ExprM Int Source #
Instances
Needed for generic functions.
class (AnotherVertexInput a, PrimitiveTopology p) => GeometryInput p a where Source #
toGeometry :: ToGeometry a (Geometry p a) Source #
Instances
AnotherVertexInput a => GeometryInput TrianglesWithAdjacency a Source # | |
Defined in Graphics.GPipe.Internal.GeometryStream | |
AnotherVertexInput a => GeometryInput Triangles a Source # | |
Defined in Graphics.GPipe.Internal.GeometryStream toGeometry :: ToGeometry a (Geometry Triangles a) Source # | |
AnotherVertexInput a => GeometryInput LinesWithAdjacency a Source # | |
Defined in Graphics.GPipe.Internal.GeometryStream toGeometry :: ToGeometry a (Geometry LinesWithAdjacency a) Source # | |
AnotherVertexInput a => GeometryInput Lines a Source # | |
Defined in Graphics.GPipe.Internal.GeometryStream toGeometry :: ToGeometry a (Geometry Lines a) Source # | |
AnotherVertexInput a => GeometryInput Points a Source # | |
Defined in Graphics.GPipe.Internal.GeometryStream toGeometry :: ToGeometry a (Geometry Points a) Source # |
Creating GeometryStream
geometrize :: forall p a s os f. GeometryInput p a => PrimitiveStream p a -> Shader os s (GeometryStream (Geometry p a)) Source #
generateAndRasterize :: forall p b a s os f. (FragmentInputFromGeometry p a, PrimitiveTopology p) => (s -> (Side, PolygonMode, ViewPort, DepthRange)) -> Int -> GeometryStream (GGenerativeGeometry p (b, a)) -> Shader os s (FragmentStream (FragmentFormat a)) Source #
Various GeometryStream operations
emitVertex :: GeometryExplosive a => a -> GGenerativeGeometry p a -> GGenerativeGeometry p a Source #
emitVertexPosition :: GeometryExplosive a => (VPos, a) -> GGenerativeGeometry p (VPos, a) -> GGenerativeGeometry p (VPos, a) Source #
emitVertexLayer :: GeometryExplosive a => (VInt, a) -> GGenerativeGeometry p (VInt, a) -> GGenerativeGeometry p (VInt, a) Source #
emitVertexPositionAndLayer :: GeometryExplosive a => ((VPos, VInt), a) -> GGenerativeGeometry p ((VPos, VInt), a) -> GGenerativeGeometry p ((VPos, VInt), a) Source #
endPrimitive :: GGenerativeGeometry p a -> GGenerativeGeometry p a Source #