GPipe-Core-0.2.3.2: Typesafe functional GPU graphics programming
Safe HaskellNone
LanguageHaskell2010

Graphics.GPipe.Internal.PrimitiveStream

Synopsis

Documentation

type USize = Int Source #

newtype PrimitiveStream t a Source #

A PrimitiveStream t a is a stream of primitives of type t where the vertices are values of type a. You can operate a stream's vertex values using the Functor instance (this will result in a shader running on the GPU). You may also append PrimitiveStreams using the Monoid instance, but if possible append the origin PrimitiveArrays instead, as this will create more optimized draw calls.

class VertexInput a where Source #

This class constraints which buffer types can be turned into vertex values, and what type those values have.

Associated Types

type VertexFormat a Source #

The type the buffer value will be turned into once it becomes a vertex value.

Methods

toVertex :: ToVertex a (VertexFormat a) Source #

An arrow action that turns a value from it's buffer representation to it's vertex representation. Use toVertex from the GPipe provided instances to operate in this arrow. Also note that this arrow needs to be able to return a value lazily, so ensure you use

proc ~pattern -> do ....

Instances

Instances details
VertexInput Float Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat Float Source #

VertexInput Int32 Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat Int32 Source #

VertexInput Word32 Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat Word32 Source #

VertexInput () Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat () Source #

VertexInput a => VertexInput (Plucker a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Plucker a) Source #

VertexInput a => VertexInput (Quaternion a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Quaternion a) Source #

VertexInput a => VertexInput (V0 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (V0 a) Source #

Methods

toVertex :: ToVertex (V0 a) (VertexFormat (V0 a)) Source #

VertexInput a => VertexInput (V4 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (V4 a) Source #

Methods

toVertex :: ToVertex (V4 a) (VertexFormat (V4 a)) Source #

VertexInput a => VertexInput (V3 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (V3 a) Source #

Methods

toVertex :: ToVertex (V3 a) (VertexFormat (V3 a)) Source #

VertexInput a => VertexInput (V2 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (V2 a) Source #

Methods

toVertex :: ToVertex (V2 a) (VertexFormat (V2 a)) Source #

VertexInput a => VertexInput (V1 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (V1 a) Source #

Methods

toVertex :: ToVertex (V1 a) (VertexFormat (V1 a)) Source #

VertexInput (Normalized (B4 Int8)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Normalized (B4 Int8)) Source #

VertexInput (Normalized (B4 Int16)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Normalized (B4 Int16)) Source #

VertexInput (Normalized (B4 Int32)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Normalized (B4 Int32)) Source #

VertexInput (Normalized (B4 Word8)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Normalized (B4 Word8)) Source #

VertexInput (Normalized (B4 Word16)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Normalized (B4 Word16)) Source #

VertexInput (Normalized (B4 Word32)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Normalized (B4 Word32)) Source #

VertexInput (Normalized (B3 Int8)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Normalized (B3 Int8)) Source #

VertexInput (Normalized (B3 Int16)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Normalized (B3 Int16)) Source #

VertexInput (Normalized (B3 Int32)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Normalized (B3 Int32)) Source #

VertexInput (Normalized (B3 Word8)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Normalized (B3 Word8)) Source #

VertexInput (Normalized (B3 Word16)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Normalized (B3 Word16)) Source #

VertexInput (Normalized (B3 Word32)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Normalized (B3 Word32)) Source #

VertexInput (Normalized (B2 Int16)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Normalized (B2 Int16)) Source #

VertexInput (Normalized (B2 Int32)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Normalized (B2 Int32)) Source #

VertexInput (Normalized (B2 Word16)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Normalized (B2 Word16)) Source #

VertexInput (Normalized (B2 Word32)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Normalized (B2 Word32)) Source #

VertexInput (Normalized (B Int32)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Normalized (B Int32)) Source #

VertexInput (Normalized (B Word32)) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Normalized (B Word32)) Source #

VertexInput (B4 Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B4 Float) Source #

VertexInput (B4 Int8) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B4 Int8) Source #

VertexInput (B4 Int16) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B4 Int16) Source #

VertexInput (B4 Int32) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B4 Int32) Source #

VertexInput (B4 Word8) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B4 Word8) Source #

VertexInput (B4 Word16) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B4 Word16) Source #

VertexInput (B4 Word32) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B4 Word32) Source #

VertexInput (B3 Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B3 Float) Source #

VertexInput (B3 Int8) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B3 Int8) Source #

VertexInput (B3 Int16) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B3 Int16) Source #

VertexInput (B3 Int32) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B3 Int32) Source #

VertexInput (B3 Word8) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B3 Word8) Source #

VertexInput (B3 Word16) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B3 Word16) Source #

VertexInput (B3 Word32) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B3 Word32) Source #

VertexInput (B2 Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B2 Float) Source #

VertexInput (B2 Int16) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B2 Int16) Source #

VertexInput (B2 Int32) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B2 Int32) Source #

VertexInput (B2 Word16) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B2 Word16) Source #

VertexInput (B2 Word32) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B2 Word32) Source #

VertexInput (B Float) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B Float) Source #

VertexInput (B Int32) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B Int32) Source #

VertexInput (B Word32) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (B Word32) Source #

(VertexInput a, VertexInput b) => VertexInput (a, b) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (a, b) Source #

Methods

toVertex :: ToVertex (a, b) (VertexFormat (a, b)) Source #

(VertexInput (f a), VertexInput a, HostFormat (f a) ~ f (HostFormat a), VertexFormat (f a) ~ f (VertexFormat a)) => VertexInput (Point f a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (Point f a) Source #

Methods

toVertex :: ToVertex (Point f a) (VertexFormat (Point f a)) Source #

(VertexInput a, VertexInput b, VertexInput c) => VertexInput (a, b, c) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (a, b, c) Source #

Methods

toVertex :: ToVertex (a, b, c) (VertexFormat (a, b, c)) Source #

(VertexInput a, VertexInput b, VertexInput c, VertexInput d) => VertexInput (a, b, c, d) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (a, b, c, d) Source #

Methods

toVertex :: ToVertex (a, b, c, d) (VertexFormat (a, b, c, d)) Source #

(VertexInput a, VertexInput b, VertexInput c, VertexInput d, VertexInput e) => VertexInput (a, b, c, d, e) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (a, b, c, d, e) Source #

Methods

toVertex :: ToVertex (a, b, c, d, e) (VertexFormat (a, b, c, d, e)) Source #

(VertexInput a, VertexInput b, VertexInput c, VertexInput d, VertexInput e, VertexInput f) => VertexInput (a, b, c, d, e, f) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (a, b, c, d, e, f) Source #

Methods

toVertex :: ToVertex (a, b, c, d, e, f) (VertexFormat (a, b, c, d, e, f)) Source #

(VertexInput a, VertexInput b, VertexInput c, VertexInput d, VertexInput e, VertexInput f, VertexInput g) => VertexInput (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Associated Types

type VertexFormat (a, b, c, d, e, f, g) Source #

Methods

toVertex :: ToVertex (a, b, c, d, e, f, g) (VertexFormat (a, b, c, d, e, f, g)) Source #

data ToVertex a b Source #

The arrow type for toVertex.

Constructors

ToVertex !(Kleisli (StateT (Ptr ()) IO) a b) !(Kleisli (StateT (Int, UniOffset, OffsetToSType) (Reader (Int -> ExprM Text))) a b) !(Kleisli (State [Binding -> (IO VAOKey, IO ())]) a b) 

Instances

Instances details
Arrow ToVertex Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Methods

arr :: (b -> c) -> ToVertex b c #

first :: ToVertex b c -> ToVertex (b, d) (c, d) #

second :: ToVertex b c -> ToVertex (d, b) (d, c) #

(***) :: ToVertex b c -> ToVertex b' c' -> ToVertex (b, b') (c, c') #

(&&&) :: ToVertex b c -> ToVertex b c' -> ToVertex b (c, c') #

Category ToVertex Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveStream

Methods

id :: forall (a :: k). ToVertex a a #

(.) :: forall (b :: k) (c :: k) (a :: k). ToVertex b c -> ToVertex a b -> ToVertex a c #

toPrimitiveStream :: forall os f s a p. (PrimitiveTopology p, VertexInput a) => (s -> PrimitiveArray p a) -> Shader os s (PrimitiveStream p (VertexFormat a)) Source #

Create a primitive stream from a primitive array provided from the shader environment. TODO No way to constraint b a bit more?

toPrimitiveStream' :: forall os f s a b p. (PrimitiveTopology p, VertexInput a) => Maybe (s -> Buffer os b) -> (s -> PrimitiveArray p a) -> Shader os s (PrimitiveStream p (VertexFormat a)) Source #

withInputIndices :: (a -> InputIndices -> b) -> PrimitiveStream p a -> PrimitiveStream p b Source #

Like fmap, but where the vertex and instance IDs are provided as arguments as well.

withPointSize :: (a -> PointSize -> (b, PointSize)) -> PrimitiveStream Points a -> PrimitiveStream Points b Source #

Like fmap, but where each point's size is provided as arguments as well, and a new point size is set for each point in addition to the new vertex value.

When a PrimitiveStream of Points is created, all points will have the default size of 1.

append :: Monad m => a -> StateT [a] m () Source #

makeVertexF :: forall (m :: Type -> Type) p1 b1 p2 b2 c. Monad m => p1 -> (SType -> ExprM Text -> b1) -> SType -> p2 -> StateT (Int, b2, c) m b1 Source #

makeBindVertexFx :: forall (m :: Type -> Type) a1 a2 b. (Monad m, Integral a1) => Bool -> GLint -> GLenum -> B a2 -> StateT [a1 -> (IO VAOKey, IO ())] m b Source #

makeVertexI :: forall (m :: Type -> Type) p1 b1 p2 b2 c. Monad m => p1 -> (SType -> ExprM Text -> b1) -> SType -> p2 -> StateT (Int, b2, c) m b1 Source #

makeBindVertexI :: forall (m :: Type -> Type) a1 a2 b. (Monad m, Integral a1) => GLint -> GLenum -> B a2 -> StateT [a1 -> (IO VAOKey, IO ())] m b Source #

noWriter :: Kleisli (StateT (Ptr ()) IO) b1 b2 Source #

toUniformVertex :: forall a b. Storable a => SType -> ToVertex a (S V b) Source #