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

Safe HaskellNone
LanguageHaskell2010

Graphics.OpenGLES.Types

Contents

Synopsis

Shading Language Base Types

Vertex Attribute Array Source Datatypes

Texture Pixel Formats

Type-Level Utilities

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

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 a)), Applicative g, Floating a, FoldableWithIndex (E V4) g, KnownNat (VDim f), KnownNat (SizeOf (f a)), KnownNat (SizeOf (f (g a))), AttrElement a) => AttrStruct (Attrib p (f (g a))) 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 a)), Applicative g, Floating a, FoldableWithIndex (E V4) g, KnownNat (VDim f), KnownNat (SizeOf (f a)), KnownNat (SizeOf (f (g a))), AttrElement a) => AttrStruct (Attrib p (f (g a))) 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))