opengles-0.6.0: OpenGL ES 2.0 and 3.0 with EGL 1.4

Safe HaskellNone
LanguageHaskell2010

Graphics.OpenGLES.Types

Contents

Synopsis

Shading Language Base Types

type M23 a = V2 (V3 a) Source

type M24 a = V2 (V4 a) Source

type M32 a = V3 (V2 a) Source

type M34 a = V3 (V4 a) Source

type M42 a = V4 (V2 a) Source

type Vec2 = V2 Float Source

type Vec3 = V3 Float Source

type Vec4 = V4 Float Source

type IVec2 = V2 Int32 Source

type IVec3 = V3 Int32 Source

type IVec4 = V4 Int32 Source

type UVec2 = V2 Word32 Source

type UVec3 = V3 Word32 Source

type UVec4 = V4 Word32 Source

type Mat2 = M22 Float Source

type Mat3 = M33 Float Source

type Mat4 = M44 Float Source

type Mat4x3 = M43 Float Source

Vertex Attribute Array Source Datatypes

Texture Pixel Formats

Type-Level Utilities

type family SizeOf f :: Nat Source

type family Aligned x :: Nat Source

Equations

Aligned 0 = 0 
Aligned 1 = 4 
Aligned 2 = 4 
Aligned 3 = 4 
Aligned x = 4 + Aligned (x - 4) 

type family Stride list :: Nat Source

Equations

Stride [] = 0 
Stride (x : xs) = Aligned (SizeOf x) + Stride xs 

castGL :: (CmpNat (Aligned (SizeOf x)) (Aligned (SizeOf y)) ~ EQ) => p x -> p y Source

Uniform Variable

data Uniform p a Source

class UnifVal a Source

Minimal complete definition

glUniform

Instances

UnifVal Float 
UnifVal Int32 
UnifVal Word32 
UnifVal UVec4 
UnifVal UVec3 
UnifVal UVec2 
UnifVal IVec4 
UnifVal IVec3 
UnifVal IVec2 
UnifVal Vec4 
UnifVal Vec3 
UnifVal Vec2 
UnifVal [Float] 
UnifVal [Int32] 
UnifVal [Word32] 
(Distributive g, Functor f, UnifMat (f (g a)), Storable (g (f a))) => UnifVal [f (g a)]

Array of matrix Not tested!!!

UnifVal [UVec4] 
UnifVal [UVec3] 
UnifVal [UVec2] 
UnifVal [IVec4] 
UnifVal [IVec3] 
UnifVal [IVec2] 
UnifVal [Vec4] 
UnifVal [Vec3] 
UnifVal [Vec2] 
(Distributive g, Functor f, UnifMat (f (g a)), Storable (g (f a))) => UnifVal (f (g a))

Matrix Not tested!!!

Vertex Attribute

data Attrib p a Source

Instances

Show (Attrib p a) 
(VertexAttribute a, (~) * (Vectorize a) (v a'), (~) * (Vectorize b) (v b'), KnownNat (VDim v), AttrElement b', VertexAttributeArray a' b') => AttrStruct (Attrib p a) p b 
(VertexAttribute (f (g Float)), Applicative g, FoldableWithIndex (E V4) g, KnownNat (VDim f), KnownNat (SizeOf (f a)), KnownNat (SizeOf (f (g a))), AttrElement a) => AttrStruct (Attrib p (f (g Float))) p (f (g a)) 

type family Vectorize a :: * Source

Temporarily gives a vector representation for type comparison

type family VDim v :: Nat Source

Equations

VDim V1 = 1 
VDim V2 = 2 
VDim V3 = 3 
VDim V4 = 4 

class VertexAttributeArray attr src Source

Minimal complete definition

glVertexAttribPtr

Instances

VertexAttributeArray Float a 
(Integral a, Integral b) => VertexAttributeArray a b

a = IntWord32, b = IntWord 81632

class AttrStruct a p b | a -> p Source

A set of VertexAttributes packed in a Buffer

Minimal complete definition

glVertexBuffer

Instances

(VertexAttribute a, (~) * (Vectorize a) (v a'), (~) * (Vectorize b) (v b'), KnownNat (VDim v), AttrElement b', VertexAttributeArray a' b') => AttrStruct (Attrib p a) p b 
(VertexAttribute (f (g Float)), Applicative g, FoldableWithIndex (E V4) g, KnownNat (VDim f), KnownNat (SizeOf (f a)), KnownNat (SizeOf (f (g a))), AttrElement a) => AttrStruct (Attrib p (f (g Float))) p (f (g a)) 

class Storable a => GLStorable a where Source

Transpose matrices

Methods

pokeArrayGL :: Ptr a -> [a] -> GL () Source

Instances

Storable a => GLStorable a 
(Storable (f (g a)), Storable (g (f a)), VertexAttribute (f (g Float)), Functor f, Distributive g) => GLStorable (f (g a))