Safe Haskell | None |
---|---|
Language | Haskell2010 |
- frameCounter :: IORef Int64
- errorQueue :: Chan String
- glLog :: String -> IO ()
- data GLError
- getError :: GL (Maybe GLError)
- showError :: String -> GL Bool
- type GLO = IORef GLObj
- data GLObj = GLObj GLuint (GL GLObj) (ForeignPtr GLuint)
- getObjId :: IORef GLObj -> IO GLuint
- newGLO :: (GLsizei -> Ptr GLuint -> GL ()) -> (GLsizei -> Ptr GLuint -> GL ()) -> (GLuint -> GL ()) -> GL GLO
- genObj :: (GLsizei -> Ptr GLuint -> GL ()) -> (GLsizei -> Ptr GLuint -> GL ()) -> (GLuint -> GL ()) -> GL GLObj
- 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)
- class GLType a where
- r :: GLenum
- rg :: GLenum
- rgb :: GLenum
- rgba :: GLenum
- r_integer :: GLenum
- rg_integer :: GLenum
- rgb_integer :: GLenum
- rgba_integer :: GLenum
- depth_component :: GLenum
- depth_stencil :: GLenum
- type GLArray a = Vector a
- data Buffer a = Buffer (IORef (Either (GLArray a) Int)) GLO
- newtype BufferUsage = BufferUsage GLenum
- newtype BufferSlot = BufferSlot GLenum
- newtype DrawMode = DrawMode GLenum
- type RenderConfig = GL ()
- 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
- class UnifMat a where
- newtype Attrib p a = Attrib (GLuint, GLsizei, GLboolean, GLuint)
- class VertexAttribute a where
- glVertexAttrib :: GLuint -> a -> GL ()
- class AttrStruct a p b | a -> p where
- glVertexBuffer :: a -> Buffer b -> GL ()
- class GLType a => AttrElement a
- newtype VertexArray p = VertexArray (GLO, GL ())
- newtype VertexPicker = VertexPicker (GLenum -> GL Bool)
- class VertexIx a where
- newtype BufferMask = BufferMask GLenum
- drawOrExit :: IORef (Maybe (GL ()))
- drawQueue :: Chan (GL ())
- data Framebuffer = Framebuffer (IORef (V2 GLsizei)) GLO
- data Renderbuffer a = Renderbuffer GLint GLenum (IORef (V2 GLsizei)) GLO
- class Attachable a b where
- defaultFramebuffer :: Framebuffer
- data Texture a = Texture GLenum (IORef Ktx) GLO
- texture_2d :: Word32
- texture_cube_map :: Word32
- texture_2d_array :: Word32
- texture_3d :: Word32
- texture_cube_map_positive_x :: Word32
Internal
Logging
GL Error
GL Object management
newGLO :: (GLsizei -> Ptr GLuint -> GL ()) -> (GLsizei -> Ptr GLuint -> GL ()) -> (GLuint -> GL ()) -> GL GLO Source
genObj :: (GLsizei -> Ptr GLuint -> GL ()) -> (GLsizei -> Ptr GLuint -> GL ()) -> (GLuint -> GL ()) -> GL GLObj Source
genObj glo glGenBuffers glDeleteBuffers
Types
newtype FixedFloat Source
newtype Word2_10x3 Source
newtype Word10f11f11f Source
newtype FloatWord24_8 Source
Buffer
newtype BufferUsage Source
newtype BufferSlot Source
DrawMode
Graphics State
type RenderConfig = GL () Source
newtype Capability Source
newtype BlendingFactor Source
Programmable Shader
type ShaderType = GLenum Source
data TransformFeedback Source
Program | |
|
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
Attrib
class VertexAttribute a where Source
GLSL vertex attribute type
glVertexAttrib :: GLuint -> a -> GL () Source
class AttrStruct a p b | a -> p where Source
A set of VertexAttribute
s packed in a Buffer
glVertexBuffer :: a -> Buffer b -> GL () Source
class GLType a => AttrElement a Source
The 3rd argument of glVertexAttribI?Pointer
Vertex Array Object
newtype VertexArray p Source
VertexArray (GLO, GL ()) |
Vertex Picker
Draw Operation
drawOrExit :: IORef (Maybe (GL ())) Source
Framebuffer
data Framebuffer Source
Framebuffer (IORef (V2 GLsizei)) GLO |
data Renderbuffer a Source
class Attachable a b where Source