| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Raylib.Util.RLGL
Contents
- High level
- Matrix operations
 - Vertex level operations
 - OpenGL style functions (common to 1.1, 3.3+, ES2)
 - rlgl functionality
- rlgl initialization functions
 - Render batch management
 - Vertex buffers management
 - Textures management
 - Framebuffer management (fbo)
 - Shaders management
 - Compute shader management
 - Shader buffer storage object management (ssbo)
 - Buffer management
 - Matrix state management
 - Quick and dirty cube/quad buffers load->draw->unload
 
 
 - Native
 
Description
Bindings to rlgl
Synopsis
- rlMatrixMode :: RLMatrixMode -> IO ()
 - rlPushMatrix :: IO ()
 - rlPopMatrix :: IO ()
 - rlLoadIdentity :: IO ()
 - rlTranslatef :: Float -> Float -> Float -> IO ()
 - rlRotatef :: Float -> Float -> Float -> Float -> IO ()
 - rlScalef :: Float -> Float -> Float -> IO ()
 - rlMultMatrixf :: [Float] -> IO ()
 - rlFrustum :: Double -> Double -> Double -> Double -> Double -> Double -> IO ()
 - rlOrtho :: Double -> Double -> Double -> Double -> Double -> Double -> IO ()
 - rlViewport :: Int -> Int -> Int -> Int -> IO ()
 - rlBegin :: RLDrawMode -> IO ()
 - rlEnd :: IO ()
 - rlVertex2i :: Int -> Int -> IO ()
 - rlVertex2f :: Float -> Float -> IO ()
 - rlVertex3f :: Float -> Float -> Float -> IO ()
 - rlTexCoord2f :: Float -> Float -> IO ()
 - rlNormal3f :: Float -> Float -> Float -> IO ()
 - rlColor4ub :: Word8 -> Word8 -> Word8 -> Word8 -> IO ()
 - rlColor3f :: Float -> Float -> Float -> IO ()
 - rlColor4f :: Float -> Float -> Float -> Float -> IO ()
 - rlEnableVertexArray :: Integer -> IO Bool
 - rlDisableVertexArray :: IO ()
 - rlEnableVertexBuffer :: Integer -> IO ()
 - rlDisableVertexBuffer :: IO ()
 - rlEnableVertexBufferElement :: Integer -> IO ()
 - rlDisableVertexBufferElement :: IO ()
 - rlEnableVertexAttribute :: Integer -> IO ()
 - rlDisableVertexAttribute :: Integer -> IO ()
 - rlActiveTextureSlot :: Int -> IO ()
 - rlEnableTexture :: Integer -> IO ()
 - rlDisableTexture :: IO ()
 - rlEnableTextureCubemap :: Integer -> IO ()
 - rlDisableTextureCubemap :: IO ()
 - rlTextureParameters :: Integer -> RLTextureParam -> Int -> IO ()
 - rlCubemapParameters :: Integer -> RLTextureParam -> Int -> IO ()
 - rlEnableShader :: Integer -> IO ()
 - rlDisableShader :: IO ()
 - rlEnableFramebuffer :: Integer -> IO ()
 - rlDisableFramebuffer :: IO ()
 - rlGetActiveFramebuffer :: IO Integer
 - rlActiveDrawBuffers :: Int -> IO ()
 - rlBlitFramebuffer :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> [RLBitField] -> IO ()
 - rlBindFramebuffer :: Integer -> Integer -> IO ()
 - rlEnableColorBlend :: IO ()
 - rlDisableColorBlend :: IO ()
 - rlEnableDepthTest :: IO ()
 - rlDisableDepthTest :: IO ()
 - rlEnableDepthMask :: IO ()
 - rlDisableDepthMask :: IO ()
 - rlEnableBackfaceCulling :: IO ()
 - rlDisableBackfaceCulling :: IO ()
 - rlColorMask :: Bool -> Bool -> Bool -> Bool -> IO ()
 - rlSetCullFace :: RLCullMode -> IO ()
 - rlEnableScissorTest :: IO ()
 - rlDisableScissorTest :: IO ()
 - rlScissor :: Int -> Int -> Int -> Int -> IO ()
 - rlEnableWireMode :: IO ()
 - rlEnablePointMode :: IO ()
 - rlDisableWireMode :: IO ()
 - rlSetLineWidth :: Float -> IO ()
 - rlGetLineWidth :: IO Float
 - rlEnableSmoothLines :: IO ()
 - rlDisableSmoothLines :: IO ()
 - rlEnableStereoRender :: IO ()
 - rlDisableStereoRender :: IO ()
 - rlIsStereoRenderEnabled :: IO Bool
 - rlClearColor :: Word8 -> Word8 -> Word8 -> Word8 -> IO ()
 - rlClearScreenBuffers :: IO ()
 - rlCheckErrors :: IO ()
 - rlSetBlendMode :: RLBlendMode -> IO ()
 - rlSetBlendFactors :: Int -> Int -> Int -> IO ()
 - rlSetBlendFactorsSeparate :: Int -> Int -> Int -> Int -> Int -> Int -> IO ()
 - rlglInit :: Int -> Int -> IO ()
 - rlglClose :: IO ()
 - rlLoadExtensions :: Ptr () -> IO ()
 - rlGetVersion :: IO Int
 - rlSetFramebufferWidth :: Int -> IO ()
 - rlGetFramebufferWidth :: IO Int
 - rlSetFramebufferHeight :: Int -> IO ()
 - rlGetFramebufferHeight :: IO Int
 - rlGetTextureIdDefault :: IO Integer
 - rlGetShaderIdDefault :: IO Integer
 - rlGetShaderLocsDefault :: IO [Int]
 - rlLoadRenderBatch :: Int -> Int -> IO RLRenderBatch
 - rlUnloadRenderBatch :: RLRenderBatch -> IO ()
 - rlDrawRenderBatch :: RLRenderBatch -> IO RLRenderBatch
 - rlSetRenderBatchActive :: Maybe RLRenderBatch -> IO ()
 - rlDrawRenderBatchActive :: IO ()
 - rlCheckRenderBatchLimit :: Int -> IO Bool
 - rlSetTexture :: Integer -> IO ()
 - rlLoadVertexArray :: IO Integer
 - rlLoadVertexBuffer :: (Freeable a, Storable a) => [a] -> Int -> Bool -> IO Integer
 - rlLoadVertexBufferElement :: (Freeable a, Storable a) => [a] -> Int -> Bool -> IO Integer
 - rlUpdateVertexBuffer :: (Freeable a, Storable a) => Integer -> [a] -> Int -> Int -> IO ()
 - rlUpdateVertexBufferElements :: (Freeable a, Storable a) => Integer -> [a] -> Int -> Int -> IO ()
 - rlUnloadVertexArray :: Integer -> IO ()
 - rlUnloadVertexBuffer :: Integer -> IO ()
 - rlSetVertexAttribute :: Integer -> Int -> Int -> Bool -> Int -> Ptr () -> IO ()
 - rlSetVertexAttributeDivisor :: Integer -> Int -> IO ()
 - rlSetVertexAttributeDefault :: Int -> Ptr () -> Int -> Int -> IO ()
 - rlDrawVertexArray :: Int -> Int -> IO ()
 - rlDrawVertexArrayElements :: Int -> [Int] -> IO ()
 - rlDrawVertexArrayInstanced :: Int -> Int -> Int -> IO ()
 - rlDrawVertexArrayElementsInstanced :: Int -> [Int] -> Int -> IO ()
 - rlLoadTexture :: [Int] -> Int -> Int -> RLPixelFormat -> Int -> IO Integer
 - rlLoadTextureDepth :: Int -> Int -> Bool -> IO Integer
 - rlLoadTextureCubemap :: [Int] -> RLPixelFormat -> IO Integer
 - rlUpdateTexture :: (Freeable a, Storable a) => Integer -> Int -> Int -> Int -> Int -> RLPixelFormat -> [a] -> IO ()
 - rlGetGlTextureFormats :: RLPixelFormat -> IO (Integer, Integer, Integer)
 - rlGetPixelFormatName :: RLPixelFormat -> String
 - rlUnloadTexture :: Integer -> IO ()
 - rlGenTextureMipmaps :: Integer -> Int -> Int -> RLPixelFormat -> IO Int
 - rlReadTexturePixels :: Integer -> Int -> Int -> RLPixelFormat -> IO [Word8]
 - rlReadScreenPixels :: Int -> Int -> IO [Word8]
 - rlLoadFramebuffer :: IO Integer
 - rlFramebufferAttach :: Integer -> Integer -> RLFramebufferAttachType -> RLFramebufferAttachTextureType -> Int -> IO ()
 - rlFramebufferComplete :: Integer -> IO Bool
 - rlUnloadFramebuffer :: Integer -> IO ()
 - rlLoadShaderCode :: String -> String -> IO Integer
 - rlCompileShader :: String -> RLShaderType -> IO Integer
 - rlLoadShaderProgram :: Integer -> Integer -> IO Integer
 - rlUnloadShaderProgram :: Integer -> IO ()
 - rlGetLocationUniform :: Integer -> String -> IO Int
 - rlGetLocationAttrib :: Integer -> String -> IO Int
 - rlSetUniform :: Int -> ShaderUniformDataV -> IO ()
 - rlSetUniformMatrix :: Int -> Matrix -> IO ()
 - rlSetUniformSampler :: Int -> Integer -> IO ()
 - rlSetShader :: Integer -> [Int] -> IO ()
 - rlLoadComputeShaderProgram :: Integer -> IO Integer
 - rlComputeShaderDispatch :: Integer -> Integer -> Integer -> IO ()
 - rlLoadShaderBuffer :: (Freeable a, Storable a) => Integer -> [a] -> RLBufferHint -> IO Integer
 - rlUnloadShaderBuffer :: Integer -> IO ()
 - rlUpdateShaderBuffer :: (Freeable a, Storable a) => Integer -> a -> Integer -> IO ()
 - rlBindShaderBuffer :: Integer -> Integer -> IO ()
 - rlCopyShaderBuffer :: Integer -> Integer -> Integer -> Integer -> Integer -> IO ()
 - rlGetShaderBufferSize :: Integer -> IO Integer
 - rlBindImageTexture :: Integer -> Integer -> RLPixelFormat -> Bool -> IO ()
 - rlGetMatrixModelview :: IO Matrix
 - rlGetMatrixProjection :: IO Matrix
 - rlGetMatrixTransform :: IO Matrix
 - rlGetMatrixProjectionStereo :: Int -> IO Matrix
 - rlGetMatrixViewOffsetStereo :: Int -> IO Matrix
 - rlSetMatrixProjection :: Matrix -> IO ()
 - rlSetMatrixModelview :: Matrix -> IO ()
 - rlSetMatrixProjectionStereo :: Matrix -> Matrix -> IO ()
 - rlSetMatrixViewOffsetStereo :: Matrix -> Matrix -> IO ()
 - rlLoadDrawCube :: IO ()
 - rlLoadDrawQuad :: IO ()
 - c'rlMatrixMode :: CInt -> IO ()
 - c'rlTranslatef :: CFloat -> CFloat -> CFloat -> IO ()
 - c'rlRotatef :: CFloat -> CFloat -> CFloat -> CFloat -> IO ()
 - c'rlScalef :: CFloat -> CFloat -> CFloat -> IO ()
 - c'rlMultMatrixf :: Ptr CFloat -> IO ()
 - c'rlFrustum :: CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
 - c'rlOrtho :: CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
 - c'rlViewport :: CInt -> CInt -> CInt -> CInt -> IO ()
 - c'rlBegin :: CInt -> IO ()
 - c'rlVertex2i :: CInt -> CInt -> IO ()
 - c'rlVertex2f :: CFloat -> CFloat -> IO ()
 - c'rlVertex3f :: CFloat -> CFloat -> CFloat -> IO ()
 - c'rlTexCoord2f :: CFloat -> CFloat -> IO ()
 - c'rlNormal3f :: CFloat -> CFloat -> CFloat -> IO ()
 - c'rlColor4ub :: CUChar -> CUChar -> CUChar -> CUChar -> IO ()
 - c'rlColor3f :: CFloat -> CFloat -> CFloat -> IO ()
 - c'rlColor4f :: CFloat -> CFloat -> CFloat -> CFloat -> IO ()
 - c'rlEnableVertexArray :: CUInt -> IO CBool
 - c'rlEnableVertexBuffer :: CUInt -> IO ()
 - c'rlEnableVertexBufferElement :: CUInt -> IO ()
 - c'rlEnableVertexAttribute :: CUInt -> IO ()
 - c'rlDisableVertexAttribute :: CUInt -> IO ()
 - c'rlActiveTextureSlot :: CInt -> IO ()
 - c'rlEnableTexture :: CUInt -> IO ()
 - c'rlEnableTextureCubemap :: CUInt -> IO ()
 - c'rlTextureParameters :: CUInt -> CInt -> CInt -> IO ()
 - c'rlCubemapParameters :: CUInt -> CInt -> CInt -> IO ()
 - c'rlEnableShader :: CUInt -> IO ()
 - c'rlEnableFramebuffer :: CUInt -> IO ()
 - c'rlActiveDrawBuffers :: CInt -> IO ()
 - c'rlBlitFramebuffer :: CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO ()
 - c'rlBindFramebuffer :: CUInt -> CUInt -> IO ()
 - c'rlColorMask :: CBool -> CBool -> CBool -> CBool -> IO ()
 - c'rlSetCullFace :: CInt -> IO ()
 - c'rlScissor :: CInt -> CInt -> CInt -> CInt -> IO ()
 - c'rlSetLineWidth :: CFloat -> IO ()
 - c'rlGetLineWidth :: IO CFloat
 - c'rlIsStereoRenderEnabled :: IO CBool
 - c'rlClearColor :: CUChar -> CUChar -> CUChar -> CUChar -> IO ()
 - c'rlSetBlendMode :: CInt -> IO ()
 - c'rlSetBlendFactors :: CInt -> CInt -> CInt -> IO ()
 - c'rlSetBlendFactorsSeparate :: CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO ()
 - c'rlglInit :: CInt -> CInt -> IO ()
 - c'rlLoadExtensions :: Ptr () -> IO ()
 - c'rlGetVersion :: IO CInt
 - c'rlSetFramebufferWidth :: CInt -> IO ()
 - c'rlGetFramebufferWidth :: IO CInt
 - c'rlSetFramebufferHeight :: CInt -> IO ()
 - c'rlGetFramebufferHeight :: IO CInt
 - c'rlGetTextureIdDefault :: IO CUInt
 - c'rlGetShaderIdDefault :: IO CUInt
 - c'rlGetShaderLocsDefault :: IO (Ptr CInt)
 - c'rlLoadRenderBatch :: CInt -> CInt -> IO (Ptr RLRenderBatch)
 - c'rlUnloadRenderBatch :: Ptr RLRenderBatch -> IO ()
 - c'rlDrawRenderBatch :: Ptr RLRenderBatch -> IO ()
 - c'rlSetRenderBatchActive :: Ptr RLRenderBatch -> IO ()
 - c'rlCheckRenderBatchLimit :: CInt -> IO CBool
 - c'rlSetTexture :: CUInt -> IO ()
 - c'rlLoadVertexArray :: IO CUInt
 - c'rlLoadVertexBuffer :: Ptr () -> CInt -> CBool -> IO CUInt
 - c'rlLoadVertexBufferElement :: Ptr () -> CInt -> CBool -> IO CUInt
 - c'rlUpdateVertexBuffer :: CUInt -> Ptr () -> CInt -> CInt -> IO ()
 - c'rlUpdateVertexBufferElements :: CUInt -> Ptr () -> CInt -> CInt -> IO ()
 - c'rlUnloadVertexArray :: CUInt -> IO ()
 - c'rlUnloadVertexBuffer :: CUInt -> IO ()
 - c'rlSetVertexAttribute :: CUInt -> CInt -> CInt -> CBool -> CInt -> Ptr () -> IO ()
 - c'rlSetVertexAttributeDivisor :: CUInt -> CInt -> IO ()
 - c'rlSetVertexAttributeDefault :: CInt -> Ptr () -> CInt -> CInt -> IO ()
 - c'rlDrawVertexArray :: CInt -> CInt -> IO ()
 - c'rlDrawVertexArrayElements :: CInt -> CInt -> Ptr () -> IO ()
 - c'rlDrawVertexArrayInstanced :: CInt -> CInt -> CInt -> IO ()
 - c'rlDrawVertexArrayElementsInstanced :: CInt -> CInt -> Ptr () -> CInt -> IO ()
 - c'rlLoadTexture :: Ptr () -> CInt -> CInt -> CInt -> CInt -> IO CUInt
 - c'rlLoadTextureDepth :: CInt -> CInt -> CBool -> IO CUInt
 - c'rlLoadTextureCubemap :: Ptr () -> CInt -> CInt -> IO CUInt
 - c'rlUpdateTexture :: CUInt -> CInt -> CInt -> CInt -> CInt -> CInt -> Ptr () -> IO ()
 - c'rlGetGlTextureFormats :: CInt -> Ptr CUInt -> Ptr CUInt -> Ptr CUInt -> IO ()
 - c'rlGetPixelFormatName :: CUInt -> IO CString
 - c'rlUnloadTexture :: CUInt -> IO ()
 - c'rlGenTextureMipmaps :: CUInt -> CInt -> CInt -> CInt -> Ptr CInt -> IO ()
 - c'rlReadTexturePixels :: CUInt -> CInt -> CInt -> CInt -> IO (Ptr ())
 - c'rlReadScreenPixels :: CInt -> CInt -> IO (Ptr CUChar)
 - c'rlLoadFramebuffer :: IO CUInt
 - c'rlFramebufferAttach :: CUInt -> CUInt -> CInt -> CInt -> CInt -> IO ()
 - c'rlFramebufferComplete :: CUInt -> IO CBool
 - c'rlUnloadFramebuffer :: CUInt -> IO ()
 - c'rlLoadShaderCode :: CString -> CString -> IO CUInt
 - c'rlCompileShader :: CString -> CInt -> IO CUInt
 - c'rlLoadShaderProgram :: CUInt -> CUInt -> IO CUInt
 - c'rlUnloadShaderProgram :: CUInt -> IO ()
 - c'rlGetLocationUniform :: CUInt -> CString -> IO CInt
 - c'rlGetLocationAttrib :: CUInt -> CString -> IO CInt
 - c'rlSetUniform :: CInt -> Ptr () -> CInt -> CInt -> IO ()
 - c'rlSetUniformMatrix :: CInt -> Ptr Matrix -> IO ()
 - c'rlSetUniformSampler :: CInt -> CUInt -> IO ()
 - c'rlSetShader :: CUInt -> Ptr CInt -> IO ()
 - c'rlLoadComputeShaderProgram :: CUInt -> IO CUInt
 - c'rlComputeShaderDispatch :: CUInt -> CUInt -> CUInt -> IO ()
 - c'rlLoadShaderBuffer :: CUInt -> Ptr () -> CInt -> IO CUInt
 - c'rlUnloadShaderBuffer :: CUInt -> IO ()
 - c'rlUpdateShaderBuffer :: CUInt -> Ptr () -> CUInt -> CUInt -> IO ()
 - c'rlBindShaderBuffer :: CUInt -> CUInt -> IO ()
 - c'rlReadShaderBuffer :: CUInt -> Ptr () -> CUInt -> CUInt -> IO ()
 - c'rlCopyShaderBuffer :: CUInt -> CUInt -> CUInt -> CUInt -> CUInt -> IO ()
 - c'rlGetShaderBufferSize :: CUInt -> IO CUInt
 - c'rlBindImageTexture :: CUInt -> CUInt -> CInt -> CBool -> IO ()
 - c'rlGetMatrixModelview :: IO (Ptr Matrix)
 - c'rlGetMatrixProjection :: IO (Ptr Matrix)
 - c'rlGetMatrixTransform :: IO (Ptr Matrix)
 - c'rlGetMatrixProjectionStereo :: CInt -> IO (Ptr Matrix)
 - c'rlGetMatrixViewOffsetStereo :: CInt -> IO (Ptr Matrix)
 - c'rlSetMatrixProjection :: Ptr Matrix -> IO ()
 - c'rlSetMatrixModelview :: Ptr Matrix -> IO ()
 - c'rlSetMatrixProjectionStereo :: Ptr Matrix -> Ptr Matrix -> IO ()
 - c'rlSetMatrixViewOffsetStereo :: Ptr Matrix -> Ptr Matrix -> IO ()
 - c'rlGetPixelDataSize :: CInt -> CInt -> CInt -> IO CInt
 - c'rlPushMatrix :: IO ()
 - c'rlPopMatrix :: IO ()
 - c'rlLoadIdentity :: IO ()
 - c'rlEnd :: IO ()
 - c'rlDisableVertexArray :: IO ()
 - c'rlDisableVertexBuffer :: IO ()
 - c'rlDisableVertexBufferElement :: IO ()
 - c'rlDisableTexture :: IO ()
 - c'rlDisableTextureCubemap :: IO ()
 - c'rlDisableShader :: IO ()
 - c'rlDisableFramebuffer :: IO ()
 - c'rlGetActiveFramebuffer :: IO CUInt
 - c'rlEnableColorBlend :: IO ()
 - c'rlDisableColorBlend :: IO ()
 - c'rlEnableDepthTest :: IO ()
 - c'rlDisableDepthTest :: IO ()
 - c'rlEnableDepthMask :: IO ()
 - c'rlDisableDepthMask :: IO ()
 - c'rlEnableBackfaceCulling :: IO ()
 - c'rlDisableBackfaceCulling :: IO ()
 - c'rlEnableScissorTest :: IO ()
 - c'rlDisableScissorTest :: IO ()
 - c'rlEnableWireMode :: IO ()
 - c'rlEnablePointMode :: IO ()
 - c'rlDisableWireMode :: IO ()
 - c'rlEnableSmoothLines :: IO ()
 - c'rlDisableSmoothLines :: IO ()
 - c'rlEnableStereoRender :: IO ()
 - c'rlDisableStereoRender :: IO ()
 - c'rlClearScreenBuffers :: IO ()
 - c'rlCheckErrors :: IO ()
 - c'rlglClose :: IO ()
 - c'rlDrawRenderBatchActive :: IO ()
 - c'rlLoadDrawCube :: IO ()
 - c'rlLoadDrawQuad :: IO ()
 
High level
Matrix operations
rlMatrixMode :: RLMatrixMode -> IO () Source #
Choose the current matrix to be transformed
rlPushMatrix :: IO () Source #
Push the current matrix to stack
rlPopMatrix :: IO () Source #
Pop latest inserted matrix from stack
rlLoadIdentity :: IO () Source #
Reset current matrix to identity matrix
rlTranslatef :: Float -> Float -> Float -> IO () Source #
Multiply the current matrix by a translation matrix
rlRotatef :: Float -> Float -> Float -> Float -> IO () Source #
Multiply the current matrix by a rotation matrix
rlScalef :: Float -> Float -> Float -> IO () Source #
Multiply the current matrix by a scaling matrix
rlMultMatrixf :: [Float] -> IO () Source #
Multiply the current matrix by another matrix
rlFrustum :: Double -> Double -> Double -> Double -> Double -> Double -> IO () Source #
Multiply the current matrix by a perspective matrix generated by parameters
rlOrtho :: Double -> Double -> Double -> Double -> Double -> Double -> IO () Source #
Multiply the current matrix by an orthographic matrix generated by parameters
Vertex level operations
rlBegin :: RLDrawMode -> IO () Source #
Initialize drawing mode (how to organize vertex)
OpenGL style functions (common to 1.1, 3.3+, ES2)
NOTE: These functions are used to completely abstract raylib code from OpenGL layer, some of them are direct wrappers over OpenGL calls, some others are custom
Vertex buffers state
rlDisableVertexArray :: IO () Source #
Disable vertex array (VAO, if supported)
rlEnableVertexBuffer :: Integer -> IO () Source #
Enable vertex buffer (VBO)
rlDisableVertexBuffer :: IO () Source #
Disable vertex buffer (VBO)
rlEnableVertexBufferElement :: Integer -> IO () Source #
Enable vertex buffer element (VBO element)
rlDisableVertexBufferElement :: IO () Source #
Disable vertex buffer element (VBO element)
rlEnableVertexAttribute :: Integer -> IO () Source #
Enable vertex attribute index
rlDisableVertexAttribute :: Integer -> IO () Source #
Disable vertex attribute index
Textures state
rlActiveTextureSlot :: Int -> IO () Source #
Select and active a texture slot
rlEnableTexture :: Integer -> IO () Source #
Enable texture
rlDisableTexture :: IO () Source #
Disable texture
rlEnableTextureCubemap :: Integer -> IO () Source #
Enable texture cubemap
rlDisableTextureCubemap :: IO () Source #
Disable texture cubemap
rlTextureParameters :: Integer -> RLTextureParam -> Int -> IO () Source #
Set texture parameters (filter, wrap)
rlCubemapParameters :: Integer -> RLTextureParam -> Int -> IO () Source #
Set cubemap parameters (filter, wrap)
Shader state
rlEnableShader :: Integer -> IO () Source #
Enable shader program
rlDisableShader :: IO () Source #
Disable shader program
Framebuffer state
rlEnableFramebuffer :: Integer -> IO () Source #
Enable render texture (fbo)
rlDisableFramebuffer :: IO () Source #
Disable render texture (fbo), return to default framebuffer
rlGetActiveFramebuffer :: IO Integer Source #
Get the currently active render texture (fbo), 0 for default framebuffer
rlActiveDrawBuffers :: Int -> IO () Source #
Activate multiple draw color buffers
rlBlitFramebuffer :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> [RLBitField] -> IO () Source #
Blit active framebuffer to main framebuffer
General render state
rlEnableColorBlend :: IO () Source #
Enable color blending
rlDisableColorBlend :: IO () Source #
Disable color blending
rlEnableDepthTest :: IO () Source #
Enable depth test
rlDisableDepthTest :: IO () Source #
Disable depth test
rlEnableDepthMask :: IO () Source #
Enable depth write
rlDisableDepthMask :: IO () Source #
Disable depth write
rlEnableBackfaceCulling :: IO () Source #
Enable backface culling
rlDisableBackfaceCulling :: IO () Source #
Disable backface culling
rlSetCullFace :: RLCullMode -> IO () Source #
Set face culling mode
rlEnableScissorTest :: IO () Source #
Enable scissor test
rlDisableScissorTest :: IO () Source #
Disable scissor test
rlEnableWireMode :: IO () Source #
Enable wire mode
rlEnablePointMode :: IO () Source #
Enable point mode
rlDisableWireMode :: IO () Source #
Disable wire and point mode
rlSetLineWidth :: Float -> IO () Source #
Set the line drawing width
rlGetLineWidth :: IO Float Source #
Get the line drawing width
rlEnableSmoothLines :: IO () Source #
Enable line aliasing
rlDisableSmoothLines :: IO () Source #
Disable line aliasing
rlEnableStereoRender :: IO () Source #
Enable stereo rendering
rlDisableStereoRender :: IO () Source #
Disable stereo rendering
rlIsStereoRenderEnabled :: IO Bool Source #
Check if stereo render is enabled
rlClearScreenBuffers :: IO () Source #
Clear used screen buffers (color and depth)
rlCheckErrors :: IO () Source #
Check and log OpenGL error codes
rlSetBlendMode :: RLBlendMode -> IO () Source #
Set blending mode
rlSetBlendFactors :: Int -> Int -> Int -> IO () Source #
Set blending mode factor and equation (using OpenGL factors)
rlSetBlendFactorsSeparate :: Int -> Int -> Int -> Int -> Int -> Int -> IO () Source #
Set blending mode factors and equations separately (using OpenGL factors)
rlgl functionality
rlgl initialization functions
rlLoadExtensions :: Ptr () -> IO () Source #
Load OpenGL extensions (loader function required)
rlGetVersion :: IO Int Source #
Get current OpenGL version
rlSetFramebufferWidth :: Int -> IO () Source #
Set current framebuffer width
rlGetFramebufferWidth :: IO Int Source #
Get default framebuffer width
rlSetFramebufferHeight :: Int -> IO () Source #
Set current framebuffer height
rlGetFramebufferHeight :: IO Int Source #
Get default framebuffer height
rlGetTextureIdDefault :: IO Integer Source #
Get default texture id
rlGetShaderIdDefault :: IO Integer Source #
Get default shader id
rlGetShaderLocsDefault :: IO [Int] Source #
Get default shader locations
Render batch management
NOTE: rlgl provides a default render batch to behave like OpenGL 1.1 immediate mode but this render batch API is exposed in case custom batches are required
rlLoadRenderBatch :: Int -> Int -> IO RLRenderBatch Source #
Load a render batch system
rlUnloadRenderBatch :: RLRenderBatch -> IO () Source #
Unload render batch system
rlDrawRenderBatch :: RLRenderBatch -> IO RLRenderBatch Source #
Draw render batch data (Update->Draw->Reset)
rlSetRenderBatchActive :: Maybe RLRenderBatch -> IO () Source #
Set the active render batch for rlgl (NULL for default internal)
rlDrawRenderBatchActive :: IO () Source #
Update and draw internal render batch
rlCheckRenderBatchLimit :: Int -> IO Bool Source #
Check internal buffer overflow for a given number of vertex
rlSetTexture :: Integer -> IO () Source #
Set current texture for render batch and check buffers limits
Vertex buffers management
rlLoadVertexArray :: IO Integer Source #
Load vertex array (vao) if supported
rlLoadVertexBuffer :: (Freeable a, Storable a) => [a] -> Int -> Bool -> IO Integer Source #
Load a vertex buffer attribute
rlLoadVertexBufferElement :: (Freeable a, Storable a) => [a] -> Int -> Bool -> IO Integer Source #
Load a new attributes element buffer (typically the buffer data will be a list of Ints)
rlUpdateVertexBuffer :: (Freeable a, Storable a) => Integer -> [a] -> Int -> Int -> IO () Source #
Update GPU buffer with new data. WARNING: Fails on empty list
rlUpdateVertexBufferElements :: (Freeable a, Storable a) => Integer -> [a] -> Int -> Int -> IO () Source #
Update vertex buffer elements with new data (typically the buffer data will be a list of Ints).
 WARNING: Fails on empty list
rlUnloadVertexArray :: Integer -> IO () Source #
Unload vertex array object (VAO)
rlUnloadVertexBuffer :: Integer -> IO () Source #
Unload vertex buffer (VBO)
rlSetVertexAttribute :: Integer -> Int -> Int -> Bool -> Int -> Ptr () -> IO () Source #
Set vertex attribute (the type must be a valid GLenum value)
rlSetVertexAttributeDefault :: Int -> Ptr () -> Int -> Int -> IO () Source #
Set vertex attribute default value
rlDrawVertexArrayElementsInstanced :: Int -> [Int] -> Int -> IO () Source #
Draw vertex array elements instanced
Textures management
rlLoadTexture :: [Int] -> Int -> Int -> RLPixelFormat -> Int -> IO Integer Source #
Load texture in GPU
rlLoadTextureDepth :: Int -> Int -> Bool -> IO Integer Source #
Load depth texture/renderbuffer (to be attached to fbo)
rlLoadTextureCubemap :: [Int] -> RLPixelFormat -> IO Integer Source #
Load texture cubemap
rlUpdateTexture :: (Freeable a, Storable a) => Integer -> Int -> Int -> Int -> Int -> RLPixelFormat -> [a] -> IO () Source #
Update GPU texture with new data
rlGetGlTextureFormats Source #
Arguments
| :: RLPixelFormat | |
| -> IO (Integer, Integer, Integer) | Return type as tuple: (glInternalFormat, glFormat, glType)  | 
Get OpenGL internal formats
rlGetPixelFormatName :: RLPixelFormat -> String Source #
Get name string for pixel format
rlUnloadTexture :: Integer -> IO () Source #
Unload texture from GPU memory
Generate mipmap data for selected texture
rlReadTexturePixels :: Integer -> Int -> Int -> RLPixelFormat -> IO [Word8] Source #
Read texture pixel data
Framebuffer management (fbo)
rlLoadFramebuffer :: IO Integer Source #
Load an empty framebuffer
rlFramebufferAttach :: Integer -> Integer -> RLFramebufferAttachType -> RLFramebufferAttachTextureType -> Int -> IO () Source #
Attach texture/renderbuffer to a framebuffer
rlUnloadFramebuffer :: Integer -> IO () Source #
Delete framebuffer from GPU
Shaders management
rlCompileShader :: String -> RLShaderType -> IO Integer Source #
Compile custom shader and return shader id
rlUnloadShaderProgram :: Integer -> IO () Source #
Unload shader program
rlSetUniform :: Int -> ShaderUniformDataV -> IO () Source #
Set shader value uniform
Compute shader management
rlComputeShaderDispatch :: Integer -> Integer -> Integer -> IO () Source #
Dispatch compute shader (equivalent to *draw* for graphics pipeline)
Shader buffer storage object management (ssbo)
rlLoadShaderBuffer :: (Freeable a, Storable a) => Integer -> [a] -> RLBufferHint -> IO Integer Source #
Load shader storage buffer object (SSBO). WARNING: Fails if list is empty
rlUnloadShaderBuffer :: Integer -> IO () Source #
Unload shader storage buffer object (SSBO)
rlUpdateShaderBuffer :: (Freeable a, Storable a) => Integer -> a -> Integer -> IO () Source #
Update SSBO buffer data
rlCopyShaderBuffer :: Integer -> Integer -> Integer -> Integer -> Integer -> IO () Source #
Copy SSBO data between buffers
Buffer management
rlBindImageTexture :: Integer -> Integer -> RLPixelFormat -> Bool -> IO () Source #
Bind image texture
Matrix state management
rlGetMatrixModelview :: IO Matrix Source #
Get internal modelview matrix
rlGetMatrixProjection :: IO Matrix Source #
Get internal projection matrix
rlGetMatrixTransform :: IO Matrix Source #
Get internal accumulated transform matrix
rlGetMatrixProjectionStereo :: Int -> IO Matrix Source #
Get internal projection matrix for stereo render (selected eye)
rlGetMatrixViewOffsetStereo :: Int -> IO Matrix Source #
Get internal view offset matrix for stereo render (selected eye)
rlSetMatrixProjection :: Matrix -> IO () Source #
Set a custom projection matrix (replaces internal projection matrix)
rlSetMatrixModelview :: Matrix -> IO () Source #
Set a custom modelview matrix (replaces internal modelview matrix)
rlSetMatrixProjectionStereo :: Matrix -> Matrix -> IO () Source #
Set eyes projection matrices for stereo rendering
rlSetMatrixViewOffsetStereo :: Matrix -> Matrix -> IO () Source #
Set eyes view offsets matrices for stereo rendering
Quick and dirty cube/quad buffers load->draw->unload
rlLoadDrawCube :: IO () Source #
Load and draw a cube
rlLoadDrawQuad :: IO () Source #
Load and draw a quad
Native
c'rlMatrixMode :: CInt -> IO () Source #
c'rlEnableVertexBuffer :: CUInt -> IO () Source #
c'rlEnableVertexBufferElement :: CUInt -> IO () Source #
c'rlEnableVertexAttribute :: CUInt -> IO () Source #
c'rlDisableVertexAttribute :: CUInt -> IO () Source #
c'rlActiveTextureSlot :: CInt -> IO () Source #
c'rlEnableTexture :: CUInt -> IO () Source #
c'rlEnableTextureCubemap :: CUInt -> IO () Source #
c'rlEnableShader :: CUInt -> IO () Source #
c'rlEnableFramebuffer :: CUInt -> IO () Source #
c'rlActiveDrawBuffers :: CInt -> IO () Source #
c'rlBlitFramebuffer :: CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO () Source #
c'rlSetCullFace :: CInt -> IO () Source #
c'rlSetLineWidth :: CFloat -> IO () Source #
c'rlSetBlendMode :: CInt -> IO () Source #
c'rlLoadExtensions :: Ptr () -> IO () Source #
c'rlGetVersion :: IO CInt Source #
c'rlSetFramebufferWidth :: CInt -> IO () Source #
c'rlSetFramebufferHeight :: CInt -> IO () Source #
c'rlLoadRenderBatch :: CInt -> CInt -> IO (Ptr RLRenderBatch) Source #
c'rlUnloadRenderBatch :: Ptr RLRenderBatch -> IO () Source #
c'rlDrawRenderBatch :: Ptr RLRenderBatch -> IO () Source #
c'rlSetRenderBatchActive :: Ptr RLRenderBatch -> IO () Source #
c'rlSetTexture :: CUInt -> IO () Source #
c'rlUnloadVertexArray :: CUInt -> IO () Source #
c'rlUnloadVertexBuffer :: CUInt -> IO () Source #
c'rlUnloadTexture :: CUInt -> IO () Source #
c'rlUnloadFramebuffer :: CUInt -> IO () Source #
c'rlUnloadShaderProgram :: CUInt -> IO () Source #
c'rlUnloadShaderBuffer :: CUInt -> IO () Source #
c'rlPushMatrix :: IO () Source #
c'rlPopMatrix :: IO () Source #
c'rlLoadIdentity :: IO () Source #
c'rlDisableVertexArray :: IO () Source #
c'rlDisableVertexBuffer :: IO () Source #
c'rlDisableTexture :: IO () Source #
c'rlDisableTextureCubemap :: IO () Source #
c'rlDisableShader :: IO () Source #
c'rlDisableFramebuffer :: IO () Source #
c'rlEnableColorBlend :: IO () Source #
c'rlDisableColorBlend :: IO () Source #
c'rlEnableDepthTest :: IO () Source #
c'rlDisableDepthTest :: IO () Source #
c'rlEnableDepthMask :: IO () Source #
c'rlDisableDepthMask :: IO () Source #
c'rlEnableBackfaceCulling :: IO () Source #
c'rlDisableBackfaceCulling :: IO () Source #
c'rlEnableScissorTest :: IO () Source #
c'rlDisableScissorTest :: IO () Source #
c'rlEnableWireMode :: IO () Source #
c'rlEnablePointMode :: IO () Source #
c'rlDisableWireMode :: IO () Source #
c'rlEnableSmoothLines :: IO () Source #
c'rlDisableSmoothLines :: IO () Source #
c'rlEnableStereoRender :: IO () Source #
c'rlDisableStereoRender :: IO () Source #
c'rlClearScreenBuffers :: IO () Source #
c'rlCheckErrors :: IO () Source #
c'rlglClose :: IO () Source #
c'rlDrawRenderBatchActive :: IO () Source #
c'rlLoadDrawCube :: IO () Source #
c'rlLoadDrawQuad :: IO () Source #