| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Graphics.OpenGLES.Internal
Contents
- errorQueue :: Chan String
- glLog :: String -> IO ()
- data GLError
- getError :: GL (Maybe GLError)
- showError :: String -> GL Bool
- type GLO = IORef (GLuint, ForeignPtr GLuint)
- newGLO :: (GLsizei -> Ptr GLuint -> GL ()) -> (GLuint -> GL ()) -> (GLsizei -> Ptr GLuint -> GL ()) -> GL GLO
- genObj :: GLO -> (GLsizei -> Ptr GLuint -> GL ()) -> (GLuint -> GL ()) -> (GLsizei -> Ptr GLuint -> GL ()) -> GL GLuint
- data Buffer a = Buffer BufferUsage GLO (IORef (StorableArray Int a))
- newtype BufferUsage = BufferUsage GLenum
- newtype BufferSlot = BufferSlot GLenum
- newBuffer :: GL GLO
- newtype DrawMode = DrawMode GLenum
- newtype Capability = Capability GLenum
- newtype CullFace = Culling GLenum
- newtype CompFunc = CompFunc GLenum
- newtype StencilOp = StencilOp GLenum
- newtype BlendOp = BlendOp GLenum
- newtype BlendingFactor = BlendingFactor GLenum
- newtype Hint = Hint GLenum
- type ShaderType = GLenum
- data Shader = Shader ShaderType GLName ByteString
- data TransformFeedback
- data Program p = Program {
- programGLO :: GLO
- programTF :: TransformFeedback
- programShaders :: [Shader]
- programVariables :: ([VarDesc], [VarDesc])
- type ProgramBinary = ByteString
- type VarDesc = (String, (GLint, GLsizei, GLenum))
- programDict :: IORef [(String, Program ())]
- lookupVarDesc :: TypeRep -> IO (Maybe ([VarDesc], [VarDesc]))
- loadProgram :: Typeable p => Program p -> (Int -> String -> Maybe ProgramBinary -> GL ()) -> GL (Progress [String] (Program p))
- postLink :: Typeable p => String -> Int -> Program p -> GLuint -> (Int -> String -> Maybe ProgramBinary -> GL ()) -> GL (Progress [String] (Program p))
- c_link_status :: GLenum
- c_info_log_length :: GLenum
- loadShader :: (Int -> String -> Maybe ProgramBinary -> GL ()) -> (Int, Shader) -> GL (Progress [String] GLuint)
- c_compile_status :: GLenum
- getActiveVariables :: GLuint -> GL ([VarDesc], [VarDesc])
- c_active_uniform_max_length :: GLenum
- c_active_attribute_max_length :: GLenum
- c_active_uniforms :: GLenum
- c_active_attributes :: GLenum
- newtype Uniform p a = Uniform (GLint, GLsizei, Ptr ())
- class UnifVal a where
- newtype Attrib p a = Attrib (GLuint, GLsizei, GLboolean, GLuint)
- class (Num a, Storable a) => GenericVertexAttribute a where
- glVertexAttrib4v :: GLuint -> Ptr (V4 a) -> GL ()
- class ShaderAttribute a where
- glVertexAttrib :: GLuint -> a -> GL ()
- class Storable b => AttrStruct b a p | a -> p where
- glVertexAttribPtr :: a -> Buffer b -> GL ()
- newtype VertexArray p = VertexArray (GLO, GL ())
- newtype HalfFloat = HalfFloat Word16
- newtype FixedFloat = FixedFloat Int32
- newtype Int10x3_2 = Int10x3_2 Int32
- newtype Word10x3_2 = Word10x3_2 Int32
- class GLType a where
- newtype VertexPicker = VertexPicker (GLenum -> GL Bool)
- class VertexIx a where
- newtype ClearBufferMask = ClearBufferMask GLenum
- drawOrExit :: IORef (Maybe (GL ()))
- drawQueue :: Chan (GL ())
Internal
Logging
GL Error
GL Object management
newGLO :: (GLsizei -> Ptr GLuint -> GL ()) -> (GLuint -> GL ()) -> (GLsizei -> Ptr GLuint -> GL ()) -> GL GLO Source
genObj :: GLO -> (GLsizei -> Ptr GLuint -> GL ()) -> (GLuint -> GL ()) -> (GLsizei -> Ptr GLuint -> GL ()) -> GL GLuint Source
genObj glo glGenBuffers glDeleteBuffers
Buffer
Constructors
| Buffer BufferUsage GLO (IORef (StorableArray Int a)) |
newtype BufferUsage Source
Constructors
| BufferUsage GLenum |
newtype BufferSlot Source
Constructors
| BufferSlot GLenum |
DrawMode
Graphics State
newtype Capability Source
Constructors
| Capability GLenum |
newtype BlendingFactor Source
Constructors
| BlendingFactor GLenum |
Programmable Shader
type ShaderType = GLenum Source
data TransformFeedback Source
Constructors
| NoFeedback | |
| FeedbackArrays [String] | |
| FeedbackPacked [String] |
Instances
Constructors
| Program | |
Fields
| |
type ProgramBinary = ByteString Source
programDict :: IORef [(String, Program ())] Source
loadProgram :: Typeable p => Program p -> (Int -> String -> Maybe ProgramBinary -> GL ()) -> GL (Progress [String] (Program p)) Source
postLink :: Typeable p => String -> Int -> Program p -> GLuint -> (Int -> String -> Maybe ProgramBinary -> GL ()) -> GL (Progress [String] (Program p)) Source
loadShader :: (Int -> String -> Maybe ProgramBinary -> GL ()) -> (Int, Shader) -> GL (Progress [String] GLuint) Source
Uniform
Instances
Attrib
Instances
| AttrStruct Float (Attrib p Float) p | |
| AttrStruct Word8 (Attrib p Float) p | |
| AttrStruct Vec4 (Attrib p Vec4) p | |
| AttrStruct Vec3 (Attrib p Vec3) p | |
| AttrStruct Vec2 (Attrib p Vec2) p | |
| AttrStruct (V2 Word8) (Attrib p Vec2) p | |
| AttrStruct (V3 Word8) (Attrib p Vec3) p | |
| AttrStruct (V4 Word8) (Attrib p Vec4) p | |
| Show (Attrib p a) |
class (Num a, Storable a) => GenericVertexAttribute a where Source
class ShaderAttribute a where Source
Methods
glVertexAttrib :: GLuint -> a -> GL () Source
Instances
class Storable b => AttrStruct b a p | a -> p where Source
Methods
glVertexAttribPtr :: a -> Buffer b -> GL () Source
Instances
| AttrStruct Float (Attrib p Float) p | |
| AttrStruct Word8 (Attrib p Float) p | |
| AttrStruct Vec4 (Attrib p Vec4) p | |
| AttrStruct Vec3 (Attrib p Vec3) p | |
| AttrStruct Vec2 (Attrib p Vec2) p | |
| AttrStruct (V2 Word8) (Attrib p Vec2) p | |
| AttrStruct (V3 Word8) (Attrib p Vec3) p | |
| AttrStruct (V4 Word8) (Attrib p Vec4) p |
Vertex Array Object
newtype VertexArray p Source
Constructors
| VertexArray (GLO, GL ()) |
newtype FixedFloat Source
Constructors
| FixedFloat Int32 |
newtype Word10x3_2 Source
Constructors
| Word10x3_2 Int32 |
Vertex Picker
newtype VertexPicker Source
Constructors
| VertexPicker (GLenum -> GL Bool) |
Draw Operation
drawOrExit :: IORef (Maybe (GL ())) Source