| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Graphics.OpenGLES.Types
Contents
- type Vec2 = V2 Float
- type Vec3 = V3 Float
- type Vec4 = V4 Float
- type IVec2 = V2 Int32
- type IVec3 = V3 Int32
- type IVec4 = V4 Int32
- type UVec2 = V2 Word32
- type UVec3 = V3 Word32
- type UVec4 = V4 Word32
- type Mat2 = M22 Float
- type Mat3 = M33 Float
- type Mat4 = M44 Float
- type Mat2x3 = M23 Float
- type Mat2x4 = M24 Float
- type Mat3x2 = M32 Float
- type Mat3x4 = M34 Float
- type Mat4x2 = M42 Float
- type Mat4x3 = M43 Float
- newtype HalfFloat = HalfFloat Word16
- newtype FixedFloat = FixedFloat Int32
- newtype Int2_10x3 = Int210x3 Int32
- newtype Word2_10x3 = Word2_10x3 Int32
- newtype Word4444 = Word4444 Word16
- newtype Word5551 = Word5551 Word16
- newtype Word565 = Word565 Word16
- newtype Word10f11f11f = Word10f11f11f Word32
- newtype Word5999 = Word5999 Word32
- newtype Word24_8 = Word24_8 Word32
- newtype FloatWord24_8 = FloatWord24_8 (Float, Word32)
- type family SizeOf f :: Nat
- type family Aligned x :: Nat
- type family Stride list :: Nat
- castGL :: (CmpNat (Aligned (SizeOf x)) (Aligned (SizeOf y)) ~ EQ) => p x -> p y
- data Uniform p a
- class UnifVal a
- data Attrib p a
- class VertexAttribute a
- class GLType a => AttrElement a
- type family Vectorize a :: *
- type family VDim v :: Nat
- class VertexAttributeArray attr src
- class AttrStruct a p b | a -> p
- class Storable a => GLStorable a where
- pokeArrayGL :: Ptr a -> [a] -> GL ()
Shading Language Base Types
Vertex Attribute Array Source Datatypes
Instances
newtype FixedFloat Source
Constructors
| FixedFloat Int32 |
newtype Word2_10x3 Source
Constructors
| Word2_10x3 Int32 |
Texture Pixel Formats
newtype Word10f11f11f Source
Constructors
| Word10f11f11f Word32 |
newtype FloatWord24_8 Source
Constructors
| FloatWord24_8 (Float, Word32) |
Type-Level Utilities
type family SizeOf f :: Nat Source
Equations
| SizeOf Float = 4 | |
| SizeOf HalfFloat = 2 | |
| SizeOf FixedFloat = 4 | |
| SizeOf Word8 = 1 | |
| SizeOf Word16 = 2 | |
| SizeOf Word32 = 4 | |
| SizeOf Int8 = 1 | |
| SizeOf Int16 = 2 | |
| SizeOf Int32 = 4 | |
| SizeOf Int2_10x3 = 4 | |
| SizeOf Word2_10x3 = 4 | |
| SizeOf Word4444 = 2 | |
| SizeOf Word5551 = 2 | |
| SizeOf Word10f11f11f = 4 | |
| SizeOf Word5999 = 4 | |
| SizeOf Word24_8 = 4 | |
| SizeOf FloatWord24_8 = 8 | |
| SizeOf (V2 a) = 2 * SizeOf a | |
| SizeOf (V3 a) = 3 * SizeOf a | |
| SizeOf (V4 a) = 4 * SizeOf a | |
| SizeOf Double = 8 |
Uniform Variable
Minimal complete definition
Instances
| UnifVal Double | |
| 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 DVec4 | |
| UnifVal DVec3 | |
| UnifVal DVec2 | |
| UnifVal [Double] | |
| 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] | |
| UnifVal [DVec4] | |
| UnifVal [DVec3] | |
| UnifVal [DVec2] | |
| (Distributive g, Functor f, UnifMat (f (g a)), Storable (g (f a))) => UnifVal (f (g a)) | Matrix Not tested!!! |
Vertex Attribute
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)) |
class VertexAttribute a Source
GLSL vertex attribute type
Minimal complete definition
Instances
| VertexAttribute Double | |
| VertexAttribute Float | |
| VertexAttribute Int32 | |
| VertexAttribute Word32 | |
| VertexAttribute UVec4 | |
| VertexAttribute UVec3 | |
| VertexAttribute UVec2 | |
| VertexAttribute IVec4 | |
| VertexAttribute IVec3 | |
| VertexAttribute IVec2 | |
| VertexAttribute Vec4 | |
| VertexAttribute Vec3 | |
| VertexAttribute Vec2 | |
| VertexAttribute DVec4 | |
| VertexAttribute DVec3 | |
| VertexAttribute DVec2 | |
| (Functor f, Floating a, Distributive g, VertexAttribute (f a), FoldableWithIndex (E V4) g) => VertexAttribute (f (g a)) | Matrices Not tested!!! |
| VertexAttribute a => VertexAttribute (V1 a) |
class GLType a => AttrElement a Source
The 3rd argument of glVertexAttribI?Pointer
type family Vectorize a :: * Source
Temporarily gives a vector representation for type comparison
Equations
| Vectorize Int2_10x3 = V4 Int2_10x3 | |
| Vectorize Word2_10x3 = V4 Word2_10x3 | |
| Vectorize (f Int2_10x3) = f (V4 Int2_10x3) | |
| Vectorize (f Word2_10x3) = f (V4 Word2_10x3) | |
| Vectorize (f a) = f a | |
| Vectorize a = V1 a |
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
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)) |