{-# LANGUAGE DeriveAnyClass #-}

{-# OPTIONS -Wall #-}

-- | Bindings for types used in @rlgl@
module Raylib.Types.Util.RLGL
  ( -- * Enumerations
    RLGLVersion (..),
    RLTraceLogLevel (..),
    RLPixelFormat (..),
    RLTextureFilter (..),
    RLBlendMode (..),
    RLShaderLocationIndex (..),
    RLShaderUniformDataType (..),
    RLShaderAttributeDataType (..),
    RLFramebufferAttachType (..),
    RLFramebufferAttachTextureType (..),
    RLCullMode (..),
    RLMatrixMode (..),
    RLDrawMode (..),
    RLTextureParam (..),
    RLShaderType (..),
    RLBufferHint (..),
    RLBitField (..),

    -- * Structures
    RLVertexBuffer (..),
    RLDrawCall (..),
    RLRenderBatch (..),

    -- * Pointer utilities
    p'rlVertexBuffer'elementCount,
    p'rlVertexBuffer'vertices,
    p'rlVertexBuffer'texcoords,
    p'rlVertexBuffer'colors,
    p'rlVertexBuffer'indices,
    p'rlVertexBuffer'vaoId,
    p'rlVertexBuffer'vboId,
    p'rlDrawCall'mode,
    p'rlDrawCall'vertexCount,
    p'rlDrawCall'vertexAlignment,
    p'rlDrawCall'textureId,
    p'rlRenderBatch'bufferCount,
    p'rlRenderBatch'currentBuffer,
    p'rlRenderBatch'vertexBuffers,
    p'rlRenderBatch'draws,
    p'rlRenderBatch'drawCounter,
    p'rlRenderBatch'currentDepth,
  )
where

import Foreign
  ( Ptr,
    Storable (alignment, peek, poke, sizeOf),
    castPtr,
    newArray,
    peekArray,
    plusPtr,
  )
import Foreign.C
  ( CFloat,
    CInt (..),
    CUInt,
  )
import Raylib.Internal.Foreign (Freeable (rlFreeDependents), c'free, peekStaticArray, pokeStaticArray, rlFree)
import Raylib.Types.Core (Color, Vector2, Vector3)

---------------------------------------
-- rlgl enums -------------------------
---------------------------------------

-- | OpenGL version
data RLGLVersion
  = -- | OpenGL 1.1
    RLOpenGL11
  | -- | OpenGL 2.1 (GLSL 120)
    RLOpenGL21
  | -- | OpenGL 3.3 (GLSL 330)
    RLOpenGL33
  | -- | OpenGL 4.3 (using GLSL 330)
    RLOpenGL43
  | -- | OpenGL ES 2.0 (GLSL 100)
    RLOpenGLES20
  deriving (RLGLVersion -> RLGLVersion -> Bool
(RLGLVersion -> RLGLVersion -> Bool)
-> (RLGLVersion -> RLGLVersion -> Bool) -> Eq RLGLVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLGLVersion -> RLGLVersion -> Bool
== :: RLGLVersion -> RLGLVersion -> Bool
$c/= :: RLGLVersion -> RLGLVersion -> Bool
/= :: RLGLVersion -> RLGLVersion -> Bool
Eq, Int -> RLGLVersion -> ShowS
[RLGLVersion] -> ShowS
RLGLVersion -> String
(Int -> RLGLVersion -> ShowS)
-> (RLGLVersion -> String)
-> ([RLGLVersion] -> ShowS)
-> Show RLGLVersion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLGLVersion -> ShowS
showsPrec :: Int -> RLGLVersion -> ShowS
$cshow :: RLGLVersion -> String
show :: RLGLVersion -> String
$cshowList :: [RLGLVersion] -> ShowS
showList :: [RLGLVersion] -> ShowS
Show)

instance Enum RLGLVersion where
  fromEnum :: RLGLVersion -> Int
fromEnum RLGLVersion
n = case RLGLVersion
n of
    RLGLVersion
RLOpenGL11 -> Int
0
    RLGLVersion
RLOpenGL21 -> Int
1
    RLGLVersion
RLOpenGL33 -> Int
2
    RLGLVersion
RLOpenGL43 -> Int
3
    RLGLVersion
RLOpenGLES20 -> Int
4
  toEnum :: Int -> RLGLVersion
toEnum Int
n = case Int
n of
    Int
0 -> RLGLVersion
RLOpenGL11
    Int
1 -> RLGLVersion
RLOpenGL21
    Int
2 -> RLGLVersion
RLOpenGL33
    Int
3 -> RLGLVersion
RLOpenGL43
    Int
4 -> RLGLVersion
RLOpenGLES20
    Int
_ -> String -> RLGLVersion
forall a. HasCallStack => String -> a
error (String -> RLGLVersion) -> String -> RLGLVersion
forall a b. (a -> b) -> a -> b
$ String
"(RLGLVersion.toEnum) Invalid value: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n

instance Storable RLGLVersion where
  sizeOf :: RLGLVersion -> Int
sizeOf RLGLVersion
_ = Int
4
  alignment :: RLGLVersion -> Int
alignment RLGLVersion
_ = Int
4
  peek :: Ptr RLGLVersion -> IO RLGLVersion
peek Ptr RLGLVersion
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLGLVersion -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLGLVersion
ptr)
    RLGLVersion -> IO RLGLVersion
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLGLVersion -> IO RLGLVersion) -> RLGLVersion -> IO RLGLVersion
forall a b. (a -> b) -> a -> b
$ Int -> RLGLVersion
forall a. Enum a => Int -> a
toEnum (Int -> RLGLVersion) -> Int -> RLGLVersion
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr RLGLVersion -> RLGLVersion -> IO ()
poke Ptr RLGLVersion
ptr RLGLVersion
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLGLVersion -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLGLVersion
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (RLGLVersion -> Int
forall a. Enum a => a -> Int
fromEnum RLGLVersion
v) :: CInt)

-- | Trace log level.
-- NOTE: Organized by priority level
data RLTraceLogLevel
  = -- | Display all logs
    RLLogAll
  | -- | Trace logging, intended for internal use only
    RLLogTrace
  | -- | Debug logging, used for internal debugging, it should be disabled on release builds
    RLLogDebug
  | -- | Info logging, used for program execution info
    RLLogInfo
  | -- | Warning logging, used on recoverable failures
    RLLogWarning
  | -- | Error logging, used on unrecoverable failures
    RLLogError
  | -- | Fatal logging, used to abort program: exit(EXIT_FAILURE)
    RLLogFatal
  | -- | Disable logging
    RLLogNone
  deriving (RLTraceLogLevel -> RLTraceLogLevel -> Bool
(RLTraceLogLevel -> RLTraceLogLevel -> Bool)
-> (RLTraceLogLevel -> RLTraceLogLevel -> Bool)
-> Eq RLTraceLogLevel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLTraceLogLevel -> RLTraceLogLevel -> Bool
== :: RLTraceLogLevel -> RLTraceLogLevel -> Bool
$c/= :: RLTraceLogLevel -> RLTraceLogLevel -> Bool
/= :: RLTraceLogLevel -> RLTraceLogLevel -> Bool
Eq, Int -> RLTraceLogLevel -> ShowS
[RLTraceLogLevel] -> ShowS
RLTraceLogLevel -> String
(Int -> RLTraceLogLevel -> ShowS)
-> (RLTraceLogLevel -> String)
-> ([RLTraceLogLevel] -> ShowS)
-> Show RLTraceLogLevel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLTraceLogLevel -> ShowS
showsPrec :: Int -> RLTraceLogLevel -> ShowS
$cshow :: RLTraceLogLevel -> String
show :: RLTraceLogLevel -> String
$cshowList :: [RLTraceLogLevel] -> ShowS
showList :: [RLTraceLogLevel] -> ShowS
Show, Int -> RLTraceLogLevel
RLTraceLogLevel -> Int
RLTraceLogLevel -> [RLTraceLogLevel]
RLTraceLogLevel -> RLTraceLogLevel
RLTraceLogLevel -> RLTraceLogLevel -> [RLTraceLogLevel]
RLTraceLogLevel
-> RLTraceLogLevel -> RLTraceLogLevel -> [RLTraceLogLevel]
(RLTraceLogLevel -> RLTraceLogLevel)
-> (RLTraceLogLevel -> RLTraceLogLevel)
-> (Int -> RLTraceLogLevel)
-> (RLTraceLogLevel -> Int)
-> (RLTraceLogLevel -> [RLTraceLogLevel])
-> (RLTraceLogLevel -> RLTraceLogLevel -> [RLTraceLogLevel])
-> (RLTraceLogLevel -> RLTraceLogLevel -> [RLTraceLogLevel])
-> (RLTraceLogLevel
    -> RLTraceLogLevel -> RLTraceLogLevel -> [RLTraceLogLevel])
-> Enum RLTraceLogLevel
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RLTraceLogLevel -> RLTraceLogLevel
succ :: RLTraceLogLevel -> RLTraceLogLevel
$cpred :: RLTraceLogLevel -> RLTraceLogLevel
pred :: RLTraceLogLevel -> RLTraceLogLevel
$ctoEnum :: Int -> RLTraceLogLevel
toEnum :: Int -> RLTraceLogLevel
$cfromEnum :: RLTraceLogLevel -> Int
fromEnum :: RLTraceLogLevel -> Int
$cenumFrom :: RLTraceLogLevel -> [RLTraceLogLevel]
enumFrom :: RLTraceLogLevel -> [RLTraceLogLevel]
$cenumFromThen :: RLTraceLogLevel -> RLTraceLogLevel -> [RLTraceLogLevel]
enumFromThen :: RLTraceLogLevel -> RLTraceLogLevel -> [RLTraceLogLevel]
$cenumFromTo :: RLTraceLogLevel -> RLTraceLogLevel -> [RLTraceLogLevel]
enumFromTo :: RLTraceLogLevel -> RLTraceLogLevel -> [RLTraceLogLevel]
$cenumFromThenTo :: RLTraceLogLevel
-> RLTraceLogLevel -> RLTraceLogLevel -> [RLTraceLogLevel]
enumFromThenTo :: RLTraceLogLevel
-> RLTraceLogLevel -> RLTraceLogLevel -> [RLTraceLogLevel]
Enum)

instance Storable RLTraceLogLevel where
  sizeOf :: RLTraceLogLevel -> Int
sizeOf RLTraceLogLevel
_ = Int
4
  alignment :: RLTraceLogLevel -> Int
alignment RLTraceLogLevel
_ = Int
4
  peek :: Ptr RLTraceLogLevel -> IO RLTraceLogLevel
peek Ptr RLTraceLogLevel
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLTraceLogLevel -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLTraceLogLevel
ptr)
    RLTraceLogLevel -> IO RLTraceLogLevel
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLTraceLogLevel -> IO RLTraceLogLevel)
-> RLTraceLogLevel -> IO RLTraceLogLevel
forall a b. (a -> b) -> a -> b
$ Int -> RLTraceLogLevel
forall a. Enum a => Int -> a
toEnum (Int -> RLTraceLogLevel) -> Int -> RLTraceLogLevel
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr RLTraceLogLevel -> RLTraceLogLevel -> IO ()
poke Ptr RLTraceLogLevel
ptr RLTraceLogLevel
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLTraceLogLevel -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLTraceLogLevel
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (RLTraceLogLevel -> Int
forall a. Enum a => a -> Int
fromEnum RLTraceLogLevel
v) :: CInt)

-- | Texture pixel formats.
-- NOTE: Support depends on OpenGL version
data RLPixelFormat
  = -- | 8 bit per pixel (no alpha)
    RLPixelFormatUncompressedGrayscale
  | -- | 8*2 bpp (2 channels)
    RLPixelFormatUncompressedGrayAlpha
  | -- | 16 bpp
    RLPixelFormatUncompressedR5G6B5
  | -- | 24 bpp
    RLPixelFormatUncompressedR8G8B8
  | -- | 16 bpp (1 bit alpha)
    RLPixelFormatUncompressedR5G5B5A1
  | -- | 16 bpp (4 bit alpha)
    RLPixelFormatUncompressedR4G4B4A4
  | -- | 32 bpp
    RLPixelFormatUncompressedR8G8B8A8
  | -- | 32 bpp (1 channel - float)
    RLPixelFormatUncompressedR32
  | -- | 32*3 bpp (3 channels - float)
    RLPixelFormatUncompressedR32G32B32
  | -- | 32*4 bpp (4 channels - float)
    RLPixelFormatUncompressedR32G32B32A32
  | -- | 16 bpp (1 channel - half float)
    RLPixelFormatUncompressedR16
  | -- | 16*3 bpp (3 channels - half float)
    RLPixelFormatUncompressedR16G16B16
  | -- | 16*4 bpp (4 channels - half float)
    RLPixelFormatUncompressedR16G16B16A16
  | -- | 4 bpp (no alpha)
    RLPixelFormatCompressedDxt1Rgb
  | -- | 4 bpp (1 bit alpha)
    RLPixelFormatCompressedDxt1Rgba
  | -- | 8 bpp
    RLPixelFormatCompressedDxt3Rgba
  | -- | 8 bpp
    RLPixelFormatCompressedDxt5Rgba
  | -- | 4 bpp
    RLPixelFormatCompressedEtc1Rgb
  | -- | 4 bpp
    RLPixelFormatCompressedEtc2Rgb
  | -- | 8 bpp
    RLPixelFormatCompressedEtc2EacRgba
  | -- | 4 bpp
    RLPixelFormatCompressedPvrtRgb
  | -- | 4 bpp
    RLPixelFormatCompressedPvrtRgba
  | -- | 8 bpp
    RLPixelFormatCompressedAstc4x4Rgba
  | -- | 2 bpp
    RLPixelFormatCompressedAstc8x8Rgba
  deriving (RLPixelFormat -> RLPixelFormat -> Bool
(RLPixelFormat -> RLPixelFormat -> Bool)
-> (RLPixelFormat -> RLPixelFormat -> Bool) -> Eq RLPixelFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLPixelFormat -> RLPixelFormat -> Bool
== :: RLPixelFormat -> RLPixelFormat -> Bool
$c/= :: RLPixelFormat -> RLPixelFormat -> Bool
/= :: RLPixelFormat -> RLPixelFormat -> Bool
Eq, Int -> RLPixelFormat -> ShowS
[RLPixelFormat] -> ShowS
RLPixelFormat -> String
(Int -> RLPixelFormat -> ShowS)
-> (RLPixelFormat -> String)
-> ([RLPixelFormat] -> ShowS)
-> Show RLPixelFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLPixelFormat -> ShowS
showsPrec :: Int -> RLPixelFormat -> ShowS
$cshow :: RLPixelFormat -> String
show :: RLPixelFormat -> String
$cshowList :: [RLPixelFormat] -> ShowS
showList :: [RLPixelFormat] -> ShowS
Show)

instance Enum RLPixelFormat where
  fromEnum :: RLPixelFormat -> Int
fromEnum RLPixelFormat
n = case RLPixelFormat
n of
    RLPixelFormat
RLPixelFormatUncompressedGrayscale -> Int
1
    RLPixelFormat
RLPixelFormatUncompressedGrayAlpha -> Int
2
    RLPixelFormat
RLPixelFormatUncompressedR5G6B5 -> Int
3
    RLPixelFormat
RLPixelFormatUncompressedR8G8B8 -> Int
4
    RLPixelFormat
RLPixelFormatUncompressedR5G5B5A1 -> Int
5
    RLPixelFormat
RLPixelFormatUncompressedR4G4B4A4 -> Int
6
    RLPixelFormat
RLPixelFormatUncompressedR8G8B8A8 -> Int
7
    RLPixelFormat
RLPixelFormatUncompressedR32 -> Int
8
    RLPixelFormat
RLPixelFormatUncompressedR32G32B32 -> Int
9
    RLPixelFormat
RLPixelFormatUncompressedR32G32B32A32 -> Int
10
    RLPixelFormat
RLPixelFormatUncompressedR16 -> Int
11
    RLPixelFormat
RLPixelFormatUncompressedR16G16B16 -> Int
12
    RLPixelFormat
RLPixelFormatUncompressedR16G16B16A16 -> Int
13
    RLPixelFormat
RLPixelFormatCompressedDxt1Rgb -> Int
14
    RLPixelFormat
RLPixelFormatCompressedDxt1Rgba -> Int
15
    RLPixelFormat
RLPixelFormatCompressedDxt3Rgba -> Int
16
    RLPixelFormat
RLPixelFormatCompressedDxt5Rgba -> Int
17
    RLPixelFormat
RLPixelFormatCompressedEtc1Rgb -> Int
18
    RLPixelFormat
RLPixelFormatCompressedEtc2Rgb -> Int
19
    RLPixelFormat
RLPixelFormatCompressedEtc2EacRgba -> Int
20
    RLPixelFormat
RLPixelFormatCompressedPvrtRgb -> Int
21
    RLPixelFormat
RLPixelFormatCompressedPvrtRgba -> Int
22
    RLPixelFormat
RLPixelFormatCompressedAstc4x4Rgba -> Int
23
    RLPixelFormat
RLPixelFormatCompressedAstc8x8Rgba -> Int
24

  toEnum :: Int -> RLPixelFormat
toEnum Int
n = case Int
n of
    Int
1 -> RLPixelFormat
RLPixelFormatUncompressedGrayscale
    Int
2 -> RLPixelFormat
RLPixelFormatUncompressedGrayAlpha
    Int
3 -> RLPixelFormat
RLPixelFormatUncompressedR5G6B5
    Int
4 -> RLPixelFormat
RLPixelFormatUncompressedR8G8B8
    Int
5 -> RLPixelFormat
RLPixelFormatUncompressedR5G5B5A1
    Int
6 -> RLPixelFormat
RLPixelFormatUncompressedR4G4B4A4
    Int
7 -> RLPixelFormat
RLPixelFormatUncompressedR8G8B8A8
    Int
8 -> RLPixelFormat
RLPixelFormatUncompressedR32
    Int
9 -> RLPixelFormat
RLPixelFormatUncompressedR32G32B32
    Int
10 -> RLPixelFormat
RLPixelFormatUncompressedR32G32B32A32
    Int
11 -> RLPixelFormat
RLPixelFormatUncompressedR16
    Int
12 -> RLPixelFormat
RLPixelFormatUncompressedR16G16B16
    Int
13 -> RLPixelFormat
RLPixelFormatUncompressedR16G16B16A16
    Int
14 -> RLPixelFormat
RLPixelFormatCompressedDxt1Rgb
    Int
15 -> RLPixelFormat
RLPixelFormatCompressedDxt1Rgba
    Int
16 -> RLPixelFormat
RLPixelFormatCompressedDxt3Rgba
    Int
17 -> RLPixelFormat
RLPixelFormatCompressedDxt5Rgba
    Int
18 -> RLPixelFormat
RLPixelFormatCompressedEtc1Rgb
    Int
19 -> RLPixelFormat
RLPixelFormatCompressedEtc2Rgb
    Int
20 -> RLPixelFormat
RLPixelFormatCompressedEtc2EacRgba
    Int
21 -> RLPixelFormat
RLPixelFormatCompressedPvrtRgb
    Int
22 -> RLPixelFormat
RLPixelFormatCompressedPvrtRgba
    Int
23 -> RLPixelFormat
RLPixelFormatCompressedAstc4x4Rgba
    Int
24 -> RLPixelFormat
RLPixelFormatCompressedAstc8x8Rgba
    Int
_ -> String -> RLPixelFormat
forall a. HasCallStack => String -> a
error (String -> RLPixelFormat) -> String -> RLPixelFormat
forall a b. (a -> b) -> a -> b
$ String
"(RLPixelFormat.toEnum) Invalid value: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n

instance Storable RLPixelFormat where
  sizeOf :: RLPixelFormat -> Int
sizeOf RLPixelFormat
_ = Int
4
  alignment :: RLPixelFormat -> Int
alignment RLPixelFormat
_ = Int
4
  peek :: Ptr RLPixelFormat -> IO RLPixelFormat
peek Ptr RLPixelFormat
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLPixelFormat -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLPixelFormat
ptr)
    RLPixelFormat -> IO RLPixelFormat
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLPixelFormat -> IO RLPixelFormat)
-> RLPixelFormat -> IO RLPixelFormat
forall a b. (a -> b) -> a -> b
$ Int -> RLPixelFormat
forall a. Enum a => Int -> a
toEnum (Int -> RLPixelFormat) -> Int -> RLPixelFormat
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr RLPixelFormat -> RLPixelFormat -> IO ()
poke Ptr RLPixelFormat
ptr RLPixelFormat
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLPixelFormat -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLPixelFormat
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (RLPixelFormat -> Int
forall a. Enum a => a -> Int
fromEnum RLPixelFormat
v) :: CInt)

-- | Texture parameters: filter mode.
-- NOTE 1: Filtering considers mipmaps if available in the texture.
-- NOTE 2: Filter is accordingly set for minification and magnification.
data RLTextureFilter
  = -- | No filter, just pixel approximation
    RLTextureFilterPoint
  | -- | Linear filtering
    RLTextureFilterBilinear
  | -- | Trilinear filtering (linear with mipmaps)
    RLTextureFilterTrilinear
  | -- | Anisotropic filtering 4x
    RLTextureFilterAnisotropic4x
  | -- | Anisotropic filtering 8x
    RLTextureFilterAnisotropic8x
  | -- | Anisotropic filtering 16x
    RLTextureFilterAnisotropic16x
  deriving (RLTextureFilter -> RLTextureFilter -> Bool
(RLTextureFilter -> RLTextureFilter -> Bool)
-> (RLTextureFilter -> RLTextureFilter -> Bool)
-> Eq RLTextureFilter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLTextureFilter -> RLTextureFilter -> Bool
== :: RLTextureFilter -> RLTextureFilter -> Bool
$c/= :: RLTextureFilter -> RLTextureFilter -> Bool
/= :: RLTextureFilter -> RLTextureFilter -> Bool
Eq, Int -> RLTextureFilter -> ShowS
[RLTextureFilter] -> ShowS
RLTextureFilter -> String
(Int -> RLTextureFilter -> ShowS)
-> (RLTextureFilter -> String)
-> ([RLTextureFilter] -> ShowS)
-> Show RLTextureFilter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLTextureFilter -> ShowS
showsPrec :: Int -> RLTextureFilter -> ShowS
$cshow :: RLTextureFilter -> String
show :: RLTextureFilter -> String
$cshowList :: [RLTextureFilter] -> ShowS
showList :: [RLTextureFilter] -> ShowS
Show, Int -> RLTextureFilter
RLTextureFilter -> Int
RLTextureFilter -> [RLTextureFilter]
RLTextureFilter -> RLTextureFilter
RLTextureFilter -> RLTextureFilter -> [RLTextureFilter]
RLTextureFilter
-> RLTextureFilter -> RLTextureFilter -> [RLTextureFilter]
(RLTextureFilter -> RLTextureFilter)
-> (RLTextureFilter -> RLTextureFilter)
-> (Int -> RLTextureFilter)
-> (RLTextureFilter -> Int)
-> (RLTextureFilter -> [RLTextureFilter])
-> (RLTextureFilter -> RLTextureFilter -> [RLTextureFilter])
-> (RLTextureFilter -> RLTextureFilter -> [RLTextureFilter])
-> (RLTextureFilter
    -> RLTextureFilter -> RLTextureFilter -> [RLTextureFilter])
-> Enum RLTextureFilter
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RLTextureFilter -> RLTextureFilter
succ :: RLTextureFilter -> RLTextureFilter
$cpred :: RLTextureFilter -> RLTextureFilter
pred :: RLTextureFilter -> RLTextureFilter
$ctoEnum :: Int -> RLTextureFilter
toEnum :: Int -> RLTextureFilter
$cfromEnum :: RLTextureFilter -> Int
fromEnum :: RLTextureFilter -> Int
$cenumFrom :: RLTextureFilter -> [RLTextureFilter]
enumFrom :: RLTextureFilter -> [RLTextureFilter]
$cenumFromThen :: RLTextureFilter -> RLTextureFilter -> [RLTextureFilter]
enumFromThen :: RLTextureFilter -> RLTextureFilter -> [RLTextureFilter]
$cenumFromTo :: RLTextureFilter -> RLTextureFilter -> [RLTextureFilter]
enumFromTo :: RLTextureFilter -> RLTextureFilter -> [RLTextureFilter]
$cenumFromThenTo :: RLTextureFilter
-> RLTextureFilter -> RLTextureFilter -> [RLTextureFilter]
enumFromThenTo :: RLTextureFilter
-> RLTextureFilter -> RLTextureFilter -> [RLTextureFilter]
Enum)

instance Storable RLTextureFilter where
  sizeOf :: RLTextureFilter -> Int
sizeOf RLTextureFilter
_ = Int
4
  alignment :: RLTextureFilter -> Int
alignment RLTextureFilter
_ = Int
4
  peek :: Ptr RLTextureFilter -> IO RLTextureFilter
peek Ptr RLTextureFilter
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLTextureFilter -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLTextureFilter
ptr)
    RLTextureFilter -> IO RLTextureFilter
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLTextureFilter -> IO RLTextureFilter)
-> RLTextureFilter -> IO RLTextureFilter
forall a b. (a -> b) -> a -> b
$ Int -> RLTextureFilter
forall a. Enum a => Int -> a
toEnum (Int -> RLTextureFilter) -> Int -> RLTextureFilter
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr RLTextureFilter -> RLTextureFilter -> IO ()
poke Ptr RLTextureFilter
ptr RLTextureFilter
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLTextureFilter -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLTextureFilter
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (RLTextureFilter -> Int
forall a. Enum a => a -> Int
fromEnum RLTextureFilter
v) :: CInt)

-- | Color blending modes (pre-defined)
data RLBlendMode
  = -- | Blend textures considering alpha (default)
    RlBlendAlpha
  | -- | Blend textures adding colors
    RlBlendAdditive
  | -- | Blend textures multiplying colors
    RlBlendMultiplied
  | -- | Blend textures adding colors (alternative)
    RlBlendAddColors
  | -- | Blend textures subtracting colors (alternative)
    RlBlendSubtractColors
  | -- | Blend premultiplied textures considering alpha
    RlBlendAlphaPremultiply
  | -- | Blend textures using custom src/dst factors (use rlSetBlendFactors())
    RlBlendCustom
  | -- | Blend textures using custom src/dst factors (use rlSetBlendFactorsSeparate())
    RlBlendCustomSeparate
  deriving (RLBlendMode -> RLBlendMode -> Bool
(RLBlendMode -> RLBlendMode -> Bool)
-> (RLBlendMode -> RLBlendMode -> Bool) -> Eq RLBlendMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLBlendMode -> RLBlendMode -> Bool
== :: RLBlendMode -> RLBlendMode -> Bool
$c/= :: RLBlendMode -> RLBlendMode -> Bool
/= :: RLBlendMode -> RLBlendMode -> Bool
Eq, Int -> RLBlendMode -> ShowS
[RLBlendMode] -> ShowS
RLBlendMode -> String
(Int -> RLBlendMode -> ShowS)
-> (RLBlendMode -> String)
-> ([RLBlendMode] -> ShowS)
-> Show RLBlendMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLBlendMode -> ShowS
showsPrec :: Int -> RLBlendMode -> ShowS
$cshow :: RLBlendMode -> String
show :: RLBlendMode -> String
$cshowList :: [RLBlendMode] -> ShowS
showList :: [RLBlendMode] -> ShowS
Show, Int -> RLBlendMode
RLBlendMode -> Int
RLBlendMode -> [RLBlendMode]
RLBlendMode -> RLBlendMode
RLBlendMode -> RLBlendMode -> [RLBlendMode]
RLBlendMode -> RLBlendMode -> RLBlendMode -> [RLBlendMode]
(RLBlendMode -> RLBlendMode)
-> (RLBlendMode -> RLBlendMode)
-> (Int -> RLBlendMode)
-> (RLBlendMode -> Int)
-> (RLBlendMode -> [RLBlendMode])
-> (RLBlendMode -> RLBlendMode -> [RLBlendMode])
-> (RLBlendMode -> RLBlendMode -> [RLBlendMode])
-> (RLBlendMode -> RLBlendMode -> RLBlendMode -> [RLBlendMode])
-> Enum RLBlendMode
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RLBlendMode -> RLBlendMode
succ :: RLBlendMode -> RLBlendMode
$cpred :: RLBlendMode -> RLBlendMode
pred :: RLBlendMode -> RLBlendMode
$ctoEnum :: Int -> RLBlendMode
toEnum :: Int -> RLBlendMode
$cfromEnum :: RLBlendMode -> Int
fromEnum :: RLBlendMode -> Int
$cenumFrom :: RLBlendMode -> [RLBlendMode]
enumFrom :: RLBlendMode -> [RLBlendMode]
$cenumFromThen :: RLBlendMode -> RLBlendMode -> [RLBlendMode]
enumFromThen :: RLBlendMode -> RLBlendMode -> [RLBlendMode]
$cenumFromTo :: RLBlendMode -> RLBlendMode -> [RLBlendMode]
enumFromTo :: RLBlendMode -> RLBlendMode -> [RLBlendMode]
$cenumFromThenTo :: RLBlendMode -> RLBlendMode -> RLBlendMode -> [RLBlendMode]
enumFromThenTo :: RLBlendMode -> RLBlendMode -> RLBlendMode -> [RLBlendMode]
Enum)

instance Storable RLBlendMode where
  sizeOf :: RLBlendMode -> Int
sizeOf RLBlendMode
_ = Int
4
  alignment :: RLBlendMode -> Int
alignment RLBlendMode
_ = Int
4
  peek :: Ptr RLBlendMode -> IO RLBlendMode
peek Ptr RLBlendMode
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLBlendMode -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLBlendMode
ptr)
    RLBlendMode -> IO RLBlendMode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLBlendMode -> IO RLBlendMode) -> RLBlendMode -> IO RLBlendMode
forall a b. (a -> b) -> a -> b
$ Int -> RLBlendMode
forall a. Enum a => Int -> a
toEnum (Int -> RLBlendMode) -> Int -> RLBlendMode
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr RLBlendMode -> RLBlendMode -> IO ()
poke Ptr RLBlendMode
ptr RLBlendMode
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLBlendMode -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLBlendMode
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (RLBlendMode -> Int
forall a. Enum a => a -> Int
fromEnum RLBlendMode
v) :: CInt)

-- | Shader location point type
data RLShaderLocationIndex
  = -- | Shader location: vertex attribute: position
    RLShaderLocVertexPosition
  | -- | Shader location: vertex attribute: texcoord01
    RLShaderLocVertexTexcoord01
  | -- | Shader location: vertex attribute: texcoord02
    RLShaderLocVertexTexcoord02
  | -- | Shader location: vertex attribute: normal
    RLShaderLocVertexNormal
  | -- | Shader location: vertex attribute: tangent
    RLShaderLocVertexTangent
  | -- | Shader location: vertex attribute: color
    RLShaderLocVertexColor
  | -- | Shader location: matrix uniform: model-view-projection
    RLShaderLocMatrixMVP
  | -- | Shader location: matrix uniform: view (camera transform)
    RLShaderLocMatrixView
  | -- | Shader location: matrix uniform: projection
    RLShaderLocMatrixProjection
  | -- | Shader location: matrix uniform: model (transform)
    RLShaderLocMatrixModel
  | -- | Shader location: matrix uniform: normal
    RLShaderLocMatrixNormal
  | -- | Shader location: vector uniform: view
    RLShaderLocVectorView
  | -- | Shader location: vector uniform: diffuse color
    RLShaderLocColorDiffuse
  | -- | Shader location: vector uniform: specular color
    RLShaderLocColorSpecular
  | -- | Shader location: vector uniform: ambient color
    RLShaderLocColorAmbient
  | -- | Shader location: sampler2d texture: albedo (same as: RL_SHADER_LOC_MAP_DIFFUSE)
    RLShaderLocMapAlbedo
  | -- | Shader location: sampler2d texture: metalness (same as: RL_SHADER_LOC_MAP_SPECULAR)
    RLShaderLocMapMetalness
  | -- | Shader location: sampler2d texture: normal
    RLShaderLocMapNormal
  | -- | Shader location: sampler2d texture: roughness
    RLShaderLocMapRoughness
  | -- | Shader location: sampler2d texture: occlusion
    RLShaderLocMapOcclusion
  | -- | Shader location: sampler2d texture: emission
    RLShaderLocMapEmission
  | -- | Shader location: sampler2d texture: height
    RLShaderLocMapHeight
  | -- | Shader location: samplerCube texture: cubemap
    RLShaderLocMapCubemap
  | -- | Shader location: samplerCube texture: irradiance
    RLShaderLocMapIrradiance
  | -- | Shader location: samplerCube texture: prefilter
    RLShaderLocMapPrefilter
  | -- | Shader location: sampler2d texture: brdf
    RLShaderLocMapBRDF
  deriving (RLShaderLocationIndex -> RLShaderLocationIndex -> Bool
(RLShaderLocationIndex -> RLShaderLocationIndex -> Bool)
-> (RLShaderLocationIndex -> RLShaderLocationIndex -> Bool)
-> Eq RLShaderLocationIndex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLShaderLocationIndex -> RLShaderLocationIndex -> Bool
== :: RLShaderLocationIndex -> RLShaderLocationIndex -> Bool
$c/= :: RLShaderLocationIndex -> RLShaderLocationIndex -> Bool
/= :: RLShaderLocationIndex -> RLShaderLocationIndex -> Bool
Eq, Int -> RLShaderLocationIndex -> ShowS
[RLShaderLocationIndex] -> ShowS
RLShaderLocationIndex -> String
(Int -> RLShaderLocationIndex -> ShowS)
-> (RLShaderLocationIndex -> String)
-> ([RLShaderLocationIndex] -> ShowS)
-> Show RLShaderLocationIndex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLShaderLocationIndex -> ShowS
showsPrec :: Int -> RLShaderLocationIndex -> ShowS
$cshow :: RLShaderLocationIndex -> String
show :: RLShaderLocationIndex -> String
$cshowList :: [RLShaderLocationIndex] -> ShowS
showList :: [RLShaderLocationIndex] -> ShowS
Show, Int -> RLShaderLocationIndex
RLShaderLocationIndex -> Int
RLShaderLocationIndex -> [RLShaderLocationIndex]
RLShaderLocationIndex -> RLShaderLocationIndex
RLShaderLocationIndex
-> RLShaderLocationIndex -> [RLShaderLocationIndex]
RLShaderLocationIndex
-> RLShaderLocationIndex
-> RLShaderLocationIndex
-> [RLShaderLocationIndex]
(RLShaderLocationIndex -> RLShaderLocationIndex)
-> (RLShaderLocationIndex -> RLShaderLocationIndex)
-> (Int -> RLShaderLocationIndex)
-> (RLShaderLocationIndex -> Int)
-> (RLShaderLocationIndex -> [RLShaderLocationIndex])
-> (RLShaderLocationIndex
    -> RLShaderLocationIndex -> [RLShaderLocationIndex])
-> (RLShaderLocationIndex
    -> RLShaderLocationIndex -> [RLShaderLocationIndex])
-> (RLShaderLocationIndex
    -> RLShaderLocationIndex
    -> RLShaderLocationIndex
    -> [RLShaderLocationIndex])
-> Enum RLShaderLocationIndex
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RLShaderLocationIndex -> RLShaderLocationIndex
succ :: RLShaderLocationIndex -> RLShaderLocationIndex
$cpred :: RLShaderLocationIndex -> RLShaderLocationIndex
pred :: RLShaderLocationIndex -> RLShaderLocationIndex
$ctoEnum :: Int -> RLShaderLocationIndex
toEnum :: Int -> RLShaderLocationIndex
$cfromEnum :: RLShaderLocationIndex -> Int
fromEnum :: RLShaderLocationIndex -> Int
$cenumFrom :: RLShaderLocationIndex -> [RLShaderLocationIndex]
enumFrom :: RLShaderLocationIndex -> [RLShaderLocationIndex]
$cenumFromThen :: RLShaderLocationIndex
-> RLShaderLocationIndex -> [RLShaderLocationIndex]
enumFromThen :: RLShaderLocationIndex
-> RLShaderLocationIndex -> [RLShaderLocationIndex]
$cenumFromTo :: RLShaderLocationIndex
-> RLShaderLocationIndex -> [RLShaderLocationIndex]
enumFromTo :: RLShaderLocationIndex
-> RLShaderLocationIndex -> [RLShaderLocationIndex]
$cenumFromThenTo :: RLShaderLocationIndex
-> RLShaderLocationIndex
-> RLShaderLocationIndex
-> [RLShaderLocationIndex]
enumFromThenTo :: RLShaderLocationIndex
-> RLShaderLocationIndex
-> RLShaderLocationIndex
-> [RLShaderLocationIndex]
Enum)

instance Storable RLShaderLocationIndex where
  sizeOf :: RLShaderLocationIndex -> Int
sizeOf RLShaderLocationIndex
_ = Int
4
  alignment :: RLShaderLocationIndex -> Int
alignment RLShaderLocationIndex
_ = Int
4
  peek :: Ptr RLShaderLocationIndex -> IO RLShaderLocationIndex
peek Ptr RLShaderLocationIndex
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLShaderLocationIndex -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLShaderLocationIndex
ptr)
    RLShaderLocationIndex -> IO RLShaderLocationIndex
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLShaderLocationIndex -> IO RLShaderLocationIndex)
-> RLShaderLocationIndex -> IO RLShaderLocationIndex
forall a b. (a -> b) -> a -> b
$ Int -> RLShaderLocationIndex
forall a. Enum a => Int -> a
toEnum (Int -> RLShaderLocationIndex) -> Int -> RLShaderLocationIndex
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr RLShaderLocationIndex -> RLShaderLocationIndex -> IO ()
poke Ptr RLShaderLocationIndex
ptr RLShaderLocationIndex
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLShaderLocationIndex -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLShaderLocationIndex
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (RLShaderLocationIndex -> Int
forall a. Enum a => a -> Int
fromEnum RLShaderLocationIndex
v) :: CInt)

-- | Shader uniform data type
data RLShaderUniformDataType
  = -- | Shader uniform type: float
    RLShaderUniformFloat
  | -- | Shader uniform type: vec2 (2 float)
    RLShaderUniformVec2
  | -- | Shader uniform type: vec3 (3 float)
    RLShaderUniformVec3
  | -- | Shader uniform type: vec4 (4 float)
    RLShaderUniformVec4
  | -- | Shader uniform type: int
    RLShaderUniformInt
  | -- | Shader uniform type: ivec2 (2 int)
    RLShaderUniformIVec2
  | -- | Shader uniform type: ivec3 (3 int)
    RLShaderUniformIVec3
  | -- | Shader uniform type: ivec4 (4 int)
    RLShaderUniformIVec4
  | -- | Shader uniform type: sampler2d
    RLShaderUniformSampler2D
  deriving (RLShaderUniformDataType -> RLShaderUniformDataType -> Bool
(RLShaderUniformDataType -> RLShaderUniformDataType -> Bool)
-> (RLShaderUniformDataType -> RLShaderUniformDataType -> Bool)
-> Eq RLShaderUniformDataType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLShaderUniformDataType -> RLShaderUniformDataType -> Bool
== :: RLShaderUniformDataType -> RLShaderUniformDataType -> Bool
$c/= :: RLShaderUniformDataType -> RLShaderUniformDataType -> Bool
/= :: RLShaderUniformDataType -> RLShaderUniformDataType -> Bool
Eq, Int -> RLShaderUniformDataType -> ShowS
[RLShaderUniformDataType] -> ShowS
RLShaderUniformDataType -> String
(Int -> RLShaderUniformDataType -> ShowS)
-> (RLShaderUniformDataType -> String)
-> ([RLShaderUniformDataType] -> ShowS)
-> Show RLShaderUniformDataType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLShaderUniformDataType -> ShowS
showsPrec :: Int -> RLShaderUniformDataType -> ShowS
$cshow :: RLShaderUniformDataType -> String
show :: RLShaderUniformDataType -> String
$cshowList :: [RLShaderUniformDataType] -> ShowS
showList :: [RLShaderUniformDataType] -> ShowS
Show, Int -> RLShaderUniformDataType
RLShaderUniformDataType -> Int
RLShaderUniformDataType -> [RLShaderUniformDataType]
RLShaderUniformDataType -> RLShaderUniformDataType
RLShaderUniformDataType
-> RLShaderUniformDataType -> [RLShaderUniformDataType]
RLShaderUniformDataType
-> RLShaderUniformDataType
-> RLShaderUniformDataType
-> [RLShaderUniformDataType]
(RLShaderUniformDataType -> RLShaderUniformDataType)
-> (RLShaderUniformDataType -> RLShaderUniformDataType)
-> (Int -> RLShaderUniformDataType)
-> (RLShaderUniformDataType -> Int)
-> (RLShaderUniformDataType -> [RLShaderUniformDataType])
-> (RLShaderUniformDataType
    -> RLShaderUniformDataType -> [RLShaderUniformDataType])
-> (RLShaderUniformDataType
    -> RLShaderUniformDataType -> [RLShaderUniformDataType])
-> (RLShaderUniformDataType
    -> RLShaderUniformDataType
    -> RLShaderUniformDataType
    -> [RLShaderUniformDataType])
-> Enum RLShaderUniformDataType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RLShaderUniformDataType -> RLShaderUniformDataType
succ :: RLShaderUniformDataType -> RLShaderUniformDataType
$cpred :: RLShaderUniformDataType -> RLShaderUniformDataType
pred :: RLShaderUniformDataType -> RLShaderUniformDataType
$ctoEnum :: Int -> RLShaderUniformDataType
toEnum :: Int -> RLShaderUniformDataType
$cfromEnum :: RLShaderUniformDataType -> Int
fromEnum :: RLShaderUniformDataType -> Int
$cenumFrom :: RLShaderUniformDataType -> [RLShaderUniformDataType]
enumFrom :: RLShaderUniformDataType -> [RLShaderUniformDataType]
$cenumFromThen :: RLShaderUniformDataType
-> RLShaderUniformDataType -> [RLShaderUniformDataType]
enumFromThen :: RLShaderUniformDataType
-> RLShaderUniformDataType -> [RLShaderUniformDataType]
$cenumFromTo :: RLShaderUniformDataType
-> RLShaderUniformDataType -> [RLShaderUniformDataType]
enumFromTo :: RLShaderUniformDataType
-> RLShaderUniformDataType -> [RLShaderUniformDataType]
$cenumFromThenTo :: RLShaderUniformDataType
-> RLShaderUniformDataType
-> RLShaderUniformDataType
-> [RLShaderUniformDataType]
enumFromThenTo :: RLShaderUniformDataType
-> RLShaderUniformDataType
-> RLShaderUniformDataType
-> [RLShaderUniformDataType]
Enum)

instance Storable RLShaderUniformDataType where
  sizeOf :: RLShaderUniformDataType -> Int
sizeOf RLShaderUniformDataType
_ = Int
4
  alignment :: RLShaderUniformDataType -> Int
alignment RLShaderUniformDataType
_ = Int
4
  peek :: Ptr RLShaderUniformDataType -> IO RLShaderUniformDataType
peek Ptr RLShaderUniformDataType
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLShaderUniformDataType -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLShaderUniformDataType
ptr)
    RLShaderUniformDataType -> IO RLShaderUniformDataType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLShaderUniformDataType -> IO RLShaderUniformDataType)
-> RLShaderUniformDataType -> IO RLShaderUniformDataType
forall a b. (a -> b) -> a -> b
$ Int -> RLShaderUniformDataType
forall a. Enum a => Int -> a
toEnum (Int -> RLShaderUniformDataType) -> Int -> RLShaderUniformDataType
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr RLShaderUniformDataType -> RLShaderUniformDataType -> IO ()
poke Ptr RLShaderUniformDataType
ptr RLShaderUniformDataType
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLShaderUniformDataType -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLShaderUniformDataType
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (RLShaderUniformDataType -> Int
forall a. Enum a => a -> Int
fromEnum RLShaderUniformDataType
v) :: CInt)

-- | Shader attribute data types
data RLShaderAttributeDataType
  = -- | Shader attribute type: float
    RLShaderAttribFloat
  | -- | Shader attribute type: vec2 (2 float)
    RLShaderAttribVec2
  | -- | Shader attribute type: vec3 (3 float)
    RLShaderAttribVec3
  | -- | Shader attribute type: vec4 (4 float)
    RLShaderAttribVec4
  deriving (RLShaderAttributeDataType -> RLShaderAttributeDataType -> Bool
(RLShaderAttributeDataType -> RLShaderAttributeDataType -> Bool)
-> (RLShaderAttributeDataType -> RLShaderAttributeDataType -> Bool)
-> Eq RLShaderAttributeDataType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLShaderAttributeDataType -> RLShaderAttributeDataType -> Bool
== :: RLShaderAttributeDataType -> RLShaderAttributeDataType -> Bool
$c/= :: RLShaderAttributeDataType -> RLShaderAttributeDataType -> Bool
/= :: RLShaderAttributeDataType -> RLShaderAttributeDataType -> Bool
Eq, Int -> RLShaderAttributeDataType -> ShowS
[RLShaderAttributeDataType] -> ShowS
RLShaderAttributeDataType -> String
(Int -> RLShaderAttributeDataType -> ShowS)
-> (RLShaderAttributeDataType -> String)
-> ([RLShaderAttributeDataType] -> ShowS)
-> Show RLShaderAttributeDataType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLShaderAttributeDataType -> ShowS
showsPrec :: Int -> RLShaderAttributeDataType -> ShowS
$cshow :: RLShaderAttributeDataType -> String
show :: RLShaderAttributeDataType -> String
$cshowList :: [RLShaderAttributeDataType] -> ShowS
showList :: [RLShaderAttributeDataType] -> ShowS
Show, Int -> RLShaderAttributeDataType
RLShaderAttributeDataType -> Int
RLShaderAttributeDataType -> [RLShaderAttributeDataType]
RLShaderAttributeDataType -> RLShaderAttributeDataType
RLShaderAttributeDataType
-> RLShaderAttributeDataType -> [RLShaderAttributeDataType]
RLShaderAttributeDataType
-> RLShaderAttributeDataType
-> RLShaderAttributeDataType
-> [RLShaderAttributeDataType]
(RLShaderAttributeDataType -> RLShaderAttributeDataType)
-> (RLShaderAttributeDataType -> RLShaderAttributeDataType)
-> (Int -> RLShaderAttributeDataType)
-> (RLShaderAttributeDataType -> Int)
-> (RLShaderAttributeDataType -> [RLShaderAttributeDataType])
-> (RLShaderAttributeDataType
    -> RLShaderAttributeDataType -> [RLShaderAttributeDataType])
-> (RLShaderAttributeDataType
    -> RLShaderAttributeDataType -> [RLShaderAttributeDataType])
-> (RLShaderAttributeDataType
    -> RLShaderAttributeDataType
    -> RLShaderAttributeDataType
    -> [RLShaderAttributeDataType])
-> Enum RLShaderAttributeDataType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RLShaderAttributeDataType -> RLShaderAttributeDataType
succ :: RLShaderAttributeDataType -> RLShaderAttributeDataType
$cpred :: RLShaderAttributeDataType -> RLShaderAttributeDataType
pred :: RLShaderAttributeDataType -> RLShaderAttributeDataType
$ctoEnum :: Int -> RLShaderAttributeDataType
toEnum :: Int -> RLShaderAttributeDataType
$cfromEnum :: RLShaderAttributeDataType -> Int
fromEnum :: RLShaderAttributeDataType -> Int
$cenumFrom :: RLShaderAttributeDataType -> [RLShaderAttributeDataType]
enumFrom :: RLShaderAttributeDataType -> [RLShaderAttributeDataType]
$cenumFromThen :: RLShaderAttributeDataType
-> RLShaderAttributeDataType -> [RLShaderAttributeDataType]
enumFromThen :: RLShaderAttributeDataType
-> RLShaderAttributeDataType -> [RLShaderAttributeDataType]
$cenumFromTo :: RLShaderAttributeDataType
-> RLShaderAttributeDataType -> [RLShaderAttributeDataType]
enumFromTo :: RLShaderAttributeDataType
-> RLShaderAttributeDataType -> [RLShaderAttributeDataType]
$cenumFromThenTo :: RLShaderAttributeDataType
-> RLShaderAttributeDataType
-> RLShaderAttributeDataType
-> [RLShaderAttributeDataType]
enumFromThenTo :: RLShaderAttributeDataType
-> RLShaderAttributeDataType
-> RLShaderAttributeDataType
-> [RLShaderAttributeDataType]
Enum)

instance Storable RLShaderAttributeDataType where
  sizeOf :: RLShaderAttributeDataType -> Int
sizeOf RLShaderAttributeDataType
_ = Int
4
  alignment :: RLShaderAttributeDataType -> Int
alignment RLShaderAttributeDataType
_ = Int
4
  peek :: Ptr RLShaderAttributeDataType -> IO RLShaderAttributeDataType
peek Ptr RLShaderAttributeDataType
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLShaderAttributeDataType -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLShaderAttributeDataType
ptr)
    RLShaderAttributeDataType -> IO RLShaderAttributeDataType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLShaderAttributeDataType -> IO RLShaderAttributeDataType)
-> RLShaderAttributeDataType -> IO RLShaderAttributeDataType
forall a b. (a -> b) -> a -> b
$ Int -> RLShaderAttributeDataType
forall a. Enum a => Int -> a
toEnum (Int -> RLShaderAttributeDataType)
-> Int -> RLShaderAttributeDataType
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr RLShaderAttributeDataType -> RLShaderAttributeDataType -> IO ()
poke Ptr RLShaderAttributeDataType
ptr RLShaderAttributeDataType
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLShaderAttributeDataType -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLShaderAttributeDataType
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (RLShaderAttributeDataType -> Int
forall a. Enum a => a -> Int
fromEnum RLShaderAttributeDataType
v) :: CInt)

-- | Framebuffer attachment type.
-- NOTE: By default up to 8 color channels are defined, but it can be more
data RLFramebufferAttachType
  = -- | Framebuffer attachment type: color 0
    RLAttachmentColorChannel0
  | -- | Framebuffer attachment type: color 1
    RLAttachmentColorChannel1
  | -- | Framebuffer attachment type: color 2
    RLAttachmentColorChannel2
  | -- | Framebuffer attachment type: color 3
    RLAttachmentColorChannel3
  | -- | Framebuffer attachment type: color 4
    RLAttachmentColorChannel4
  | -- | Framebuffer attachment type: color 5
    RLAttachmentColorChannel5
  | -- | Framebuffer attachment type: color 6
    RLAttachmentColorChannel6
  | -- | Framebuffer attachment type: color 7
    RLAttachmentColorChannel7
  | -- | Framebuffer attachment type: depth
    RLAttachmentDepth
  | -- | Framebuffer attachment type: stencil
    RLAttachmentStencil
  deriving (RLFramebufferAttachType -> RLFramebufferAttachType -> Bool
(RLFramebufferAttachType -> RLFramebufferAttachType -> Bool)
-> (RLFramebufferAttachType -> RLFramebufferAttachType -> Bool)
-> Eq RLFramebufferAttachType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLFramebufferAttachType -> RLFramebufferAttachType -> Bool
== :: RLFramebufferAttachType -> RLFramebufferAttachType -> Bool
$c/= :: RLFramebufferAttachType -> RLFramebufferAttachType -> Bool
/= :: RLFramebufferAttachType -> RLFramebufferAttachType -> Bool
Eq, Int -> RLFramebufferAttachType -> ShowS
[RLFramebufferAttachType] -> ShowS
RLFramebufferAttachType -> String
(Int -> RLFramebufferAttachType -> ShowS)
-> (RLFramebufferAttachType -> String)
-> ([RLFramebufferAttachType] -> ShowS)
-> Show RLFramebufferAttachType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLFramebufferAttachType -> ShowS
showsPrec :: Int -> RLFramebufferAttachType -> ShowS
$cshow :: RLFramebufferAttachType -> String
show :: RLFramebufferAttachType -> String
$cshowList :: [RLFramebufferAttachType] -> ShowS
showList :: [RLFramebufferAttachType] -> ShowS
Show)

instance Enum RLFramebufferAttachType where
  fromEnum :: RLFramebufferAttachType -> Int
fromEnum RLFramebufferAttachType
n = case RLFramebufferAttachType
n of
    RLFramebufferAttachType
RLAttachmentColorChannel0 -> Int
0
    RLFramebufferAttachType
RLAttachmentColorChannel1 -> Int
1
    RLFramebufferAttachType
RLAttachmentColorChannel2 -> Int
2
    RLFramebufferAttachType
RLAttachmentColorChannel3 -> Int
3
    RLFramebufferAttachType
RLAttachmentColorChannel4 -> Int
4
    RLFramebufferAttachType
RLAttachmentColorChannel5 -> Int
5
    RLFramebufferAttachType
RLAttachmentColorChannel6 -> Int
6
    RLFramebufferAttachType
RLAttachmentColorChannel7 -> Int
7
    RLFramebufferAttachType
RLAttachmentDepth -> Int
100
    RLFramebufferAttachType
RLAttachmentStencil -> Int
200

  toEnum :: Int -> RLFramebufferAttachType
toEnum Int
n = case Int
n of
    Int
0 -> RLFramebufferAttachType
RLAttachmentColorChannel0
    Int
1 -> RLFramebufferAttachType
RLAttachmentColorChannel1
    Int
2 -> RLFramebufferAttachType
RLAttachmentColorChannel2
    Int
3 -> RLFramebufferAttachType
RLAttachmentColorChannel3
    Int
4 -> RLFramebufferAttachType
RLAttachmentColorChannel4
    Int
5 -> RLFramebufferAttachType
RLAttachmentColorChannel5
    Int
6 -> RLFramebufferAttachType
RLAttachmentColorChannel6
    Int
7 -> RLFramebufferAttachType
RLAttachmentColorChannel7
    Int
100 -> RLFramebufferAttachType
RLAttachmentDepth
    Int
200 -> RLFramebufferAttachType
RLAttachmentStencil
    Int
_ -> String -> RLFramebufferAttachType
forall a. HasCallStack => String -> a
error (String -> RLFramebufferAttachType)
-> String -> RLFramebufferAttachType
forall a b. (a -> b) -> a -> b
$ String
"(RLFramebufferAttachType.toEnum) Invalid value: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n

instance Storable RLFramebufferAttachType where
  sizeOf :: RLFramebufferAttachType -> Int
sizeOf RLFramebufferAttachType
_ = Int
4
  alignment :: RLFramebufferAttachType -> Int
alignment RLFramebufferAttachType
_ = Int
4
  peek :: Ptr RLFramebufferAttachType -> IO RLFramebufferAttachType
peek Ptr RLFramebufferAttachType
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLFramebufferAttachType -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLFramebufferAttachType
ptr)
    RLFramebufferAttachType -> IO RLFramebufferAttachType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLFramebufferAttachType -> IO RLFramebufferAttachType)
-> RLFramebufferAttachType -> IO RLFramebufferAttachType
forall a b. (a -> b) -> a -> b
$ Int -> RLFramebufferAttachType
forall a. Enum a => Int -> a
toEnum (Int -> RLFramebufferAttachType) -> Int -> RLFramebufferAttachType
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr RLFramebufferAttachType -> RLFramebufferAttachType -> IO ()
poke Ptr RLFramebufferAttachType
ptr RLFramebufferAttachType
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLFramebufferAttachType -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLFramebufferAttachType
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (RLFramebufferAttachType -> Int
forall a. Enum a => a -> Int
fromEnum RLFramebufferAttachType
v) :: CInt)

-- | Framebuffer texture attachment type
data RLFramebufferAttachTextureType
  = -- | Framebuffer texture attachment type: cubemap, +X side
    RLAttachmentCubemapPositiveX
  | -- | Framebuffer texture attachment type: cubemap, -X side
    RLAttachmentCubemapNegativeX
  | -- | Framebuffer texture attachment type: cubemap, +Y side
    RLAttachmentCubemapPositiveY
  | -- | Framebuffer texture attachment type: cubemap, -Y side
    RLAttachmentCubemapNegativeY
  | -- | Framebuffer texture attachment type: cubemap, +Z side
    RLAttachmentCubemapPositiveZ
  | -- | Framebuffer texture attachment type: cubemap, -Z side
    RLAttachmentCubemapNegativeZ
  | -- | Framebuffer texture attachment type: texture2d
    RLAttachmentTexture2D
  | -- | Framebuffer texture attachment type: renderbuffer
    RLAttachmentRenderBuffer
  deriving (RLFramebufferAttachTextureType
-> RLFramebufferAttachTextureType -> Bool
(RLFramebufferAttachTextureType
 -> RLFramebufferAttachTextureType -> Bool)
-> (RLFramebufferAttachTextureType
    -> RLFramebufferAttachTextureType -> Bool)
-> Eq RLFramebufferAttachTextureType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLFramebufferAttachTextureType
-> RLFramebufferAttachTextureType -> Bool
== :: RLFramebufferAttachTextureType
-> RLFramebufferAttachTextureType -> Bool
$c/= :: RLFramebufferAttachTextureType
-> RLFramebufferAttachTextureType -> Bool
/= :: RLFramebufferAttachTextureType
-> RLFramebufferAttachTextureType -> Bool
Eq, Int -> RLFramebufferAttachTextureType -> ShowS
[RLFramebufferAttachTextureType] -> ShowS
RLFramebufferAttachTextureType -> String
(Int -> RLFramebufferAttachTextureType -> ShowS)
-> (RLFramebufferAttachTextureType -> String)
-> ([RLFramebufferAttachTextureType] -> ShowS)
-> Show RLFramebufferAttachTextureType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLFramebufferAttachTextureType -> ShowS
showsPrec :: Int -> RLFramebufferAttachTextureType -> ShowS
$cshow :: RLFramebufferAttachTextureType -> String
show :: RLFramebufferAttachTextureType -> String
$cshowList :: [RLFramebufferAttachTextureType] -> ShowS
showList :: [RLFramebufferAttachTextureType] -> ShowS
Show)

instance Enum RLFramebufferAttachTextureType where
  fromEnum :: RLFramebufferAttachTextureType -> Int
fromEnum RLFramebufferAttachTextureType
n = case RLFramebufferAttachTextureType
n of
    RLFramebufferAttachTextureType
RLAttachmentCubemapPositiveX -> Int
0
    RLFramebufferAttachTextureType
RLAttachmentCubemapNegativeX -> Int
1
    RLFramebufferAttachTextureType
RLAttachmentCubemapPositiveY -> Int
2
    RLFramebufferAttachTextureType
RLAttachmentCubemapNegativeY -> Int
3
    RLFramebufferAttachTextureType
RLAttachmentCubemapPositiveZ -> Int
4
    RLFramebufferAttachTextureType
RLAttachmentCubemapNegativeZ -> Int
5
    RLFramebufferAttachTextureType
RLAttachmentTexture2D -> Int
100
    RLFramebufferAttachTextureType
RLAttachmentRenderBuffer -> Int
200

  toEnum :: Int -> RLFramebufferAttachTextureType
toEnum Int
n = case Int
n of
    Int
0 -> RLFramebufferAttachTextureType
RLAttachmentCubemapPositiveX
    Int
1 -> RLFramebufferAttachTextureType
RLAttachmentCubemapNegativeX
    Int
2 -> RLFramebufferAttachTextureType
RLAttachmentCubemapPositiveY
    Int
3 -> RLFramebufferAttachTextureType
RLAttachmentCubemapNegativeY
    Int
4 -> RLFramebufferAttachTextureType
RLAttachmentCubemapPositiveZ
    Int
5 -> RLFramebufferAttachTextureType
RLAttachmentCubemapNegativeZ
    Int
100 -> RLFramebufferAttachTextureType
RLAttachmentTexture2D
    Int
200 -> RLFramebufferAttachTextureType
RLAttachmentRenderBuffer
    Int
_ -> String -> RLFramebufferAttachTextureType
forall a. HasCallStack => String -> a
error (String -> RLFramebufferAttachTextureType)
-> String -> RLFramebufferAttachTextureType
forall a b. (a -> b) -> a -> b
$ String
"(RLFramebufferAttachTextureType.toEnum) Invalid value: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n

instance Storable RLFramebufferAttachTextureType where
  sizeOf :: RLFramebufferAttachTextureType -> Int
sizeOf RLFramebufferAttachTextureType
_ = Int
4
  alignment :: RLFramebufferAttachTextureType -> Int
alignment RLFramebufferAttachTextureType
_ = Int
4
  peek :: Ptr RLFramebufferAttachTextureType
-> IO RLFramebufferAttachTextureType
peek Ptr RLFramebufferAttachTextureType
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLFramebufferAttachTextureType -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLFramebufferAttachTextureType
ptr)
    RLFramebufferAttachTextureType -> IO RLFramebufferAttachTextureType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLFramebufferAttachTextureType
 -> IO RLFramebufferAttachTextureType)
-> RLFramebufferAttachTextureType
-> IO RLFramebufferAttachTextureType
forall a b. (a -> b) -> a -> b
$ Int -> RLFramebufferAttachTextureType
forall a. Enum a => Int -> a
toEnum (Int -> RLFramebufferAttachTextureType)
-> Int -> RLFramebufferAttachTextureType
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr RLFramebufferAttachTextureType
-> RLFramebufferAttachTextureType -> IO ()
poke Ptr RLFramebufferAttachTextureType
ptr RLFramebufferAttachTextureType
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLFramebufferAttachTextureType -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLFramebufferAttachTextureType
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (RLFramebufferAttachTextureType -> Int
forall a. Enum a => a -> Int
fromEnum RLFramebufferAttachTextureType
v) :: CInt)

-- | Face culling mode
data RLCullMode
  = RLCullFaceFront
  | RLCullFaceBack
  deriving (RLCullMode -> RLCullMode -> Bool
(RLCullMode -> RLCullMode -> Bool)
-> (RLCullMode -> RLCullMode -> Bool) -> Eq RLCullMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLCullMode -> RLCullMode -> Bool
== :: RLCullMode -> RLCullMode -> Bool
$c/= :: RLCullMode -> RLCullMode -> Bool
/= :: RLCullMode -> RLCullMode -> Bool
Eq, Int -> RLCullMode -> ShowS
[RLCullMode] -> ShowS
RLCullMode -> String
(Int -> RLCullMode -> ShowS)
-> (RLCullMode -> String)
-> ([RLCullMode] -> ShowS)
-> Show RLCullMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLCullMode -> ShowS
showsPrec :: Int -> RLCullMode -> ShowS
$cshow :: RLCullMode -> String
show :: RLCullMode -> String
$cshowList :: [RLCullMode] -> ShowS
showList :: [RLCullMode] -> ShowS
Show, Int -> RLCullMode
RLCullMode -> Int
RLCullMode -> [RLCullMode]
RLCullMode -> RLCullMode
RLCullMode -> RLCullMode -> [RLCullMode]
RLCullMode -> RLCullMode -> RLCullMode -> [RLCullMode]
(RLCullMode -> RLCullMode)
-> (RLCullMode -> RLCullMode)
-> (Int -> RLCullMode)
-> (RLCullMode -> Int)
-> (RLCullMode -> [RLCullMode])
-> (RLCullMode -> RLCullMode -> [RLCullMode])
-> (RLCullMode -> RLCullMode -> [RLCullMode])
-> (RLCullMode -> RLCullMode -> RLCullMode -> [RLCullMode])
-> Enum RLCullMode
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RLCullMode -> RLCullMode
succ :: RLCullMode -> RLCullMode
$cpred :: RLCullMode -> RLCullMode
pred :: RLCullMode -> RLCullMode
$ctoEnum :: Int -> RLCullMode
toEnum :: Int -> RLCullMode
$cfromEnum :: RLCullMode -> Int
fromEnum :: RLCullMode -> Int
$cenumFrom :: RLCullMode -> [RLCullMode]
enumFrom :: RLCullMode -> [RLCullMode]
$cenumFromThen :: RLCullMode -> RLCullMode -> [RLCullMode]
enumFromThen :: RLCullMode -> RLCullMode -> [RLCullMode]
$cenumFromTo :: RLCullMode -> RLCullMode -> [RLCullMode]
enumFromTo :: RLCullMode -> RLCullMode -> [RLCullMode]
$cenumFromThenTo :: RLCullMode -> RLCullMode -> RLCullMode -> [RLCullMode]
enumFromThenTo :: RLCullMode -> RLCullMode -> RLCullMode -> [RLCullMode]
Enum)

instance Storable RLCullMode where
  sizeOf :: RLCullMode -> Int
sizeOf RLCullMode
_ = Int
4
  alignment :: RLCullMode -> Int
alignment RLCullMode
_ = Int
4
  peek :: Ptr RLCullMode -> IO RLCullMode
peek Ptr RLCullMode
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLCullMode -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLCullMode
ptr)
    RLCullMode -> IO RLCullMode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLCullMode -> IO RLCullMode) -> RLCullMode -> IO RLCullMode
forall a b. (a -> b) -> a -> b
$ Int -> RLCullMode
forall a. Enum a => Int -> a
toEnum (Int -> RLCullMode) -> Int -> RLCullMode
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr RLCullMode -> RLCullMode -> IO ()
poke Ptr RLCullMode
ptr RLCullMode
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLCullMode -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLCullMode
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (RLCullMode -> Int
forall a. Enum a => a -> Int
fromEnum RLCullMode
v) :: CInt)

-- | Matrix modes (equivalent to OpenGL)
data RLMatrixMode
  = -- | GL_MODELVIEW
    RLModelView
  | -- | GL_PROJECTION
    RLProjection
  | -- | GL_TEXTURE
    RLTexture
  deriving (RLMatrixMode -> RLMatrixMode -> Bool
(RLMatrixMode -> RLMatrixMode -> Bool)
-> (RLMatrixMode -> RLMatrixMode -> Bool) -> Eq RLMatrixMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLMatrixMode -> RLMatrixMode -> Bool
== :: RLMatrixMode -> RLMatrixMode -> Bool
$c/= :: RLMatrixMode -> RLMatrixMode -> Bool
/= :: RLMatrixMode -> RLMatrixMode -> Bool
Eq, Int -> RLMatrixMode -> ShowS
[RLMatrixMode] -> ShowS
RLMatrixMode -> String
(Int -> RLMatrixMode -> ShowS)
-> (RLMatrixMode -> String)
-> ([RLMatrixMode] -> ShowS)
-> Show RLMatrixMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLMatrixMode -> ShowS
showsPrec :: Int -> RLMatrixMode -> ShowS
$cshow :: RLMatrixMode -> String
show :: RLMatrixMode -> String
$cshowList :: [RLMatrixMode] -> ShowS
showList :: [RLMatrixMode] -> ShowS
Show)

instance Enum RLMatrixMode where
  fromEnum :: RLMatrixMode -> Int
fromEnum RLMatrixMode
n = case RLMatrixMode
n of
    RLMatrixMode
RLModelView -> Int
0x1700
    RLMatrixMode
RLProjection -> Int
0x1701
    RLMatrixMode
RLTexture -> Int
0x1702

  toEnum :: Int -> RLMatrixMode
toEnum Int
n = case Int
n of
    Int
0x1700 -> RLMatrixMode
RLModelView
    Int
0x1701 -> RLMatrixMode
RLProjection
    Int
0x1702 -> RLMatrixMode
RLTexture
    Int
_ -> String -> RLMatrixMode
forall a. HasCallStack => String -> a
error (String -> RLMatrixMode) -> String -> RLMatrixMode
forall a b. (a -> b) -> a -> b
$ String
"(RLMatrixMode.toEnum) Invalid value: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n

instance Storable RLMatrixMode where
  sizeOf :: RLMatrixMode -> Int
sizeOf RLMatrixMode
_ = Int
4
  alignment :: RLMatrixMode -> Int
alignment RLMatrixMode
_ = Int
4
  peek :: Ptr RLMatrixMode -> IO RLMatrixMode
peek Ptr RLMatrixMode
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLMatrixMode -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLMatrixMode
ptr)
    RLMatrixMode -> IO RLMatrixMode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLMatrixMode -> IO RLMatrixMode)
-> RLMatrixMode -> IO RLMatrixMode
forall a b. (a -> b) -> a -> b
$ Int -> RLMatrixMode
forall a. Enum a => Int -> a
toEnum (Int -> RLMatrixMode) -> Int -> RLMatrixMode
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr RLMatrixMode -> RLMatrixMode -> IO ()
poke Ptr RLMatrixMode
ptr RLMatrixMode
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLMatrixMode -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLMatrixMode
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (RLMatrixMode -> Int
forall a. Enum a => a -> Int
fromEnum RLMatrixMode
v) :: CInt)

-- | Primitive assembly draw modes
data RLDrawMode
  = -- | GL_LINES
    RLLines
  | -- | GL_TRIANGLES
    RLTriangles
  | -- | GL_QUADS
    RLQuads
  deriving (RLDrawMode -> RLDrawMode -> Bool
(RLDrawMode -> RLDrawMode -> Bool)
-> (RLDrawMode -> RLDrawMode -> Bool) -> Eq RLDrawMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLDrawMode -> RLDrawMode -> Bool
== :: RLDrawMode -> RLDrawMode -> Bool
$c/= :: RLDrawMode -> RLDrawMode -> Bool
/= :: RLDrawMode -> RLDrawMode -> Bool
Eq, Int -> RLDrawMode -> ShowS
[RLDrawMode] -> ShowS
RLDrawMode -> String
(Int -> RLDrawMode -> ShowS)
-> (RLDrawMode -> String)
-> ([RLDrawMode] -> ShowS)
-> Show RLDrawMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLDrawMode -> ShowS
showsPrec :: Int -> RLDrawMode -> ShowS
$cshow :: RLDrawMode -> String
show :: RLDrawMode -> String
$cshowList :: [RLDrawMode] -> ShowS
showList :: [RLDrawMode] -> ShowS
Show)

instance Enum RLDrawMode where
  fromEnum :: RLDrawMode -> Int
fromEnum RLDrawMode
n = case RLDrawMode
n of
    RLDrawMode
RLLines -> Int
0x0001
    RLDrawMode
RLTriangles -> Int
0x0004
    RLDrawMode
RLQuads -> Int
0x0007

  toEnum :: Int -> RLDrawMode
toEnum Int
n = case Int
n of
    Int
0x0001 -> RLDrawMode
RLLines
    Int
0x0004 -> RLDrawMode
RLTriangles
    Int
0x0007 -> RLDrawMode
RLQuads
    Int
_ -> String -> RLDrawMode
forall a. HasCallStack => String -> a
error (String -> RLDrawMode) -> String -> RLDrawMode
forall a b. (a -> b) -> a -> b
$ String
"(RLDrawMode.toEnum) Invalid value: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n

instance Storable RLDrawMode where
  sizeOf :: RLDrawMode -> Int
sizeOf RLDrawMode
_ = Int
4
  alignment :: RLDrawMode -> Int
alignment RLDrawMode
_ = Int
4
  peek :: Ptr RLDrawMode -> IO RLDrawMode
peek Ptr RLDrawMode
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLDrawMode -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLDrawMode
ptr)
    RLDrawMode -> IO RLDrawMode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLDrawMode -> IO RLDrawMode) -> RLDrawMode -> IO RLDrawMode
forall a b. (a -> b) -> a -> b
$ Int -> RLDrawMode
forall a. Enum a => Int -> a
toEnum (Int -> RLDrawMode) -> Int -> RLDrawMode
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr RLDrawMode -> RLDrawMode -> IO ()
poke Ptr RLDrawMode
ptr RLDrawMode
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLDrawMode -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLDrawMode
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (RLDrawMode -> Int
forall a. Enum a => a -> Int
fromEnum RLDrawMode
v) :: CInt)

-- | Texture parameters (equivalent to OpenGL defines)
data RLTextureParam
  = -- | GL_TEXTURE_WRAP_S
    RLTextureParamWrapS
  | -- | GL_TEXTURE_WRAP_T
    RLTextureParamWrapT
  | -- | GL_TEXTURE_MAG_FILTER
    RLTextureParamMagFilter
  | -- | GL_TEXTURE_MIN_FILTER
    RLTextureParamMinFilter
  | -- | GL_NEAREST
    RLTextureParamFilterNearest
  | -- | GL_LINEAR
    RLTextureParamFilterLinear
  | -- | GL_NEAREST_MIPMAP_NEAREST
    RLTextureParamFilterMipNearest
  | -- | GL_NEAREST_MIPMAP_LINEAR
    RLTextureParamFilterNearestMipLinear
  | -- | GL_LINEAR_MIPMAP_NEAREST
    RLTextureParamFilterLinearMipNearest
  | -- | GL_LINEAR_MIPMAP_LINEAR
    RLTextureParamFilterMipLinear
  | -- | Anisotropic filter (custom identifier)
    RLTextureParamFilterAnisotropic
  | -- | Texture mipmap bias, percentage ratio (custom identifier)
    RLTextureParamMipmapBiasRatio
  deriving (RLTextureParam -> RLTextureParam -> Bool
(RLTextureParam -> RLTextureParam -> Bool)
-> (RLTextureParam -> RLTextureParam -> Bool) -> Eq RLTextureParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLTextureParam -> RLTextureParam -> Bool
== :: RLTextureParam -> RLTextureParam -> Bool
$c/= :: RLTextureParam -> RLTextureParam -> Bool
/= :: RLTextureParam -> RLTextureParam -> Bool
Eq, Int -> RLTextureParam -> ShowS
[RLTextureParam] -> ShowS
RLTextureParam -> String
(Int -> RLTextureParam -> ShowS)
-> (RLTextureParam -> String)
-> ([RLTextureParam] -> ShowS)
-> Show RLTextureParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLTextureParam -> ShowS
showsPrec :: Int -> RLTextureParam -> ShowS
$cshow :: RLTextureParam -> String
show :: RLTextureParam -> String
$cshowList :: [RLTextureParam] -> ShowS
showList :: [RLTextureParam] -> ShowS
Show)

instance Enum RLTextureParam where
  fromEnum :: RLTextureParam -> Int
fromEnum RLTextureParam
n = case RLTextureParam
n of
    RLTextureParam
RLTextureParamWrapS -> Int
0x2802
    RLTextureParam
RLTextureParamWrapT -> Int
0x2803
    RLTextureParam
RLTextureParamMagFilter -> Int
0x2800
    RLTextureParam
RLTextureParamMinFilter -> Int
0x2801
    RLTextureParam
RLTextureParamFilterNearest -> Int
0x2600
    RLTextureParam
RLTextureParamFilterLinear -> Int
0x2601
    RLTextureParam
RLTextureParamFilterMipNearest -> Int
0x2700
    RLTextureParam
RLTextureParamFilterNearestMipLinear -> Int
0x2702
    RLTextureParam
RLTextureParamFilterLinearMipNearest -> Int
0x2701
    RLTextureParam
RLTextureParamFilterMipLinear -> Int
0x2703
    RLTextureParam
RLTextureParamFilterAnisotropic -> Int
0x3000
    RLTextureParam
RLTextureParamMipmapBiasRatio -> Int
0x4000

  toEnum :: Int -> RLTextureParam
toEnum Int
n = case Int
n of
    Int
0x2802 -> RLTextureParam
RLTextureParamWrapS
    Int
0x2803 -> RLTextureParam
RLTextureParamWrapT
    Int
0x2800 -> RLTextureParam
RLTextureParamMagFilter
    Int
0x2801 -> RLTextureParam
RLTextureParamMinFilter
    Int
0x2600 -> RLTextureParam
RLTextureParamFilterNearest
    Int
0x2601 -> RLTextureParam
RLTextureParamFilterLinear
    Int
0x2700 -> RLTextureParam
RLTextureParamFilterMipNearest
    Int
0x2702 -> RLTextureParam
RLTextureParamFilterNearestMipLinear
    Int
0x2701 -> RLTextureParam
RLTextureParamFilterLinearMipNearest
    Int
0x2703 -> RLTextureParam
RLTextureParamFilterMipLinear
    Int
0x3000 -> RLTextureParam
RLTextureParamFilterAnisotropic
    Int
0x4000 -> RLTextureParam
RLTextureParamMipmapBiasRatio
    Int
_ -> String -> RLTextureParam
forall a. HasCallStack => String -> a
error (String -> RLTextureParam) -> String -> RLTextureParam
forall a b. (a -> b) -> a -> b
$ String
"(RLTextureParam.toEnum) Invalid value: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n

instance Storable RLTextureParam where
  sizeOf :: RLTextureParam -> Int
sizeOf RLTextureParam
_ = Int
4
  alignment :: RLTextureParam -> Int
alignment RLTextureParam
_ = Int
4
  peek :: Ptr RLTextureParam -> IO RLTextureParam
peek Ptr RLTextureParam
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLTextureParam -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLTextureParam
ptr)
    RLTextureParam -> IO RLTextureParam
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLTextureParam -> IO RLTextureParam)
-> RLTextureParam -> IO RLTextureParam
forall a b. (a -> b) -> a -> b
$ Int -> RLTextureParam
forall a. Enum a => Int -> a
toEnum (Int -> RLTextureParam) -> Int -> RLTextureParam
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr RLTextureParam -> RLTextureParam -> IO ()
poke Ptr RLTextureParam
ptr RLTextureParam
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLTextureParam -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLTextureParam
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (RLTextureParam -> Int
forall a. Enum a => a -> Int
fromEnum RLTextureParam
v) :: CInt)

-- | OpenGL shader type
data RLShaderType
  = -- | GL_FRAGMENT_SHADER
    RLFragmentShader
  | -- | GL_VERTEX_SHADER
    RLVertexShader
  | -- | GL_COMPUTE_SHADER
    RLComputeShader
  deriving (RLShaderType -> RLShaderType -> Bool
(RLShaderType -> RLShaderType -> Bool)
-> (RLShaderType -> RLShaderType -> Bool) -> Eq RLShaderType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLShaderType -> RLShaderType -> Bool
== :: RLShaderType -> RLShaderType -> Bool
$c/= :: RLShaderType -> RLShaderType -> Bool
/= :: RLShaderType -> RLShaderType -> Bool
Eq, Int -> RLShaderType -> ShowS
[RLShaderType] -> ShowS
RLShaderType -> String
(Int -> RLShaderType -> ShowS)
-> (RLShaderType -> String)
-> ([RLShaderType] -> ShowS)
-> Show RLShaderType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLShaderType -> ShowS
showsPrec :: Int -> RLShaderType -> ShowS
$cshow :: RLShaderType -> String
show :: RLShaderType -> String
$cshowList :: [RLShaderType] -> ShowS
showList :: [RLShaderType] -> ShowS
Show)

instance Enum RLShaderType where
  fromEnum :: RLShaderType -> Int
fromEnum RLShaderType
n = case RLShaderType
n of
    RLShaderType
RLFragmentShader -> Int
0x8B30
    RLShaderType
RLVertexShader -> Int
0x8B31
    RLShaderType
RLComputeShader -> Int
0x91B9

  toEnum :: Int -> RLShaderType
toEnum Int
n = case Int
n of
    Int
0x8B30 -> RLShaderType
RLFragmentShader
    Int
0x8B31 -> RLShaderType
RLVertexShader
    Int
0x91B9 -> RLShaderType
RLComputeShader
    Int
_ -> String -> RLShaderType
forall a. HasCallStack => String -> a
error (String -> RLShaderType) -> String -> RLShaderType
forall a b. (a -> b) -> a -> b
$ String
"(RLShaderType.toEnum) Invalid value: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n

instance Storable RLShaderType where
  sizeOf :: RLShaderType -> Int
sizeOf RLShaderType
_ = Int
4
  alignment :: RLShaderType -> Int
alignment RLShaderType
_ = Int
4
  peek :: Ptr RLShaderType -> IO RLShaderType
peek Ptr RLShaderType
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLShaderType -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLShaderType
ptr)
    RLShaderType -> IO RLShaderType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLShaderType -> IO RLShaderType)
-> RLShaderType -> IO RLShaderType
forall a b. (a -> b) -> a -> b
$ Int -> RLShaderType
forall a. Enum a => Int -> a
toEnum (Int -> RLShaderType) -> Int -> RLShaderType
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr RLShaderType -> RLShaderType -> IO ()
poke Ptr RLShaderType
ptr RLShaderType
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLShaderType -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLShaderType
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (RLShaderType -> Int
forall a. Enum a => a -> Int
fromEnum RLShaderType
v) :: CInt)

-- | GL buffer usage hint
data RLBufferHint
  = -- | GL_STREAM_DRAW
    RLBufferHintStreamDraw
  | -- | GL_STREAM_READ
    RLBufferHintStreamRead
  | -- | GL_STREAM_COPY
    RLBufferHintStreamCopy
  | -- | GL_STATIC_DRAW
    RLBufferHintStaticDraw
  | -- | GL_STATIC_READ
    RLBufferHintStaticRead
  | -- | GL_STATIC_COPY
    RLBufferHintStaticCopy
  | -- | GL_DYNAMIC_DRAW
    RLBufferHintDynamicDraw
  | -- | GL_DYNAMIC_READ
    RLBufferHintDynamicRead
  | -- | GL_DYNAMIC_COPY
    RLBufferHintDynamicCopy
  deriving (RLBufferHint -> RLBufferHint -> Bool
(RLBufferHint -> RLBufferHint -> Bool)
-> (RLBufferHint -> RLBufferHint -> Bool) -> Eq RLBufferHint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLBufferHint -> RLBufferHint -> Bool
== :: RLBufferHint -> RLBufferHint -> Bool
$c/= :: RLBufferHint -> RLBufferHint -> Bool
/= :: RLBufferHint -> RLBufferHint -> Bool
Eq, Int -> RLBufferHint -> ShowS
[RLBufferHint] -> ShowS
RLBufferHint -> String
(Int -> RLBufferHint -> ShowS)
-> (RLBufferHint -> String)
-> ([RLBufferHint] -> ShowS)
-> Show RLBufferHint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLBufferHint -> ShowS
showsPrec :: Int -> RLBufferHint -> ShowS
$cshow :: RLBufferHint -> String
show :: RLBufferHint -> String
$cshowList :: [RLBufferHint] -> ShowS
showList :: [RLBufferHint] -> ShowS
Show)

instance Enum RLBufferHint where
  fromEnum :: RLBufferHint -> Int
fromEnum RLBufferHint
n = case RLBufferHint
n of
    RLBufferHint
RLBufferHintStreamDraw -> Int
0x88E0
    RLBufferHint
RLBufferHintStreamRead -> Int
0x88E1
    RLBufferHint
RLBufferHintStreamCopy -> Int
0x88E2
    RLBufferHint
RLBufferHintStaticDraw -> Int
0x88E4
    RLBufferHint
RLBufferHintStaticRead -> Int
0x88E5
    RLBufferHint
RLBufferHintStaticCopy -> Int
0x88E6
    RLBufferHint
RLBufferHintDynamicDraw -> Int
0x88E8
    RLBufferHint
RLBufferHintDynamicRead -> Int
0x88E9
    RLBufferHint
RLBufferHintDynamicCopy -> Int
0x88EA

  toEnum :: Int -> RLBufferHint
toEnum Int
n = case Int
n of
    Int
0x88E0 -> RLBufferHint
RLBufferHintStreamDraw
    Int
0x88E1 -> RLBufferHint
RLBufferHintStreamRead
    Int
0x88E2 -> RLBufferHint
RLBufferHintStreamCopy
    Int
0x88E4 -> RLBufferHint
RLBufferHintStaticDraw
    Int
0x88E5 -> RLBufferHint
RLBufferHintStaticRead
    Int
0x88E6 -> RLBufferHint
RLBufferHintStaticCopy
    Int
0x88E8 -> RLBufferHint
RLBufferHintDynamicDraw
    Int
0x88E9 -> RLBufferHint
RLBufferHintDynamicRead
    Int
0x88EA -> RLBufferHint
RLBufferHintDynamicCopy
    Int
_ -> String -> RLBufferHint
forall a. HasCallStack => String -> a
error (String -> RLBufferHint) -> String -> RLBufferHint
forall a b. (a -> b) -> a -> b
$ String
"(RLBufferHint.toEnum) Invalid value: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n

instance Storable RLBufferHint where
  sizeOf :: RLBufferHint -> Int
sizeOf RLBufferHint
_ = Int
4
  alignment :: RLBufferHint -> Int
alignment RLBufferHint
_ = Int
4
  peek :: Ptr RLBufferHint -> IO RLBufferHint
peek Ptr RLBufferHint
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLBufferHint -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLBufferHint
ptr)
    RLBufferHint -> IO RLBufferHint
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLBufferHint -> IO RLBufferHint)
-> RLBufferHint -> IO RLBufferHint
forall a b. (a -> b) -> a -> b
$ Int -> RLBufferHint
forall a. Enum a => Int -> a
toEnum (Int -> RLBufferHint) -> Int -> RLBufferHint
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr RLBufferHint -> RLBufferHint -> IO ()
poke Ptr RLBufferHint
ptr RLBufferHint
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLBufferHint -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLBufferHint
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (RLBufferHint -> Int
forall a. Enum a => a -> Int
fromEnum RLBufferHint
v) :: CInt)

-- | GL buffer mask
data RLBitField
  = -- | GL_COLOR_BUFFER_BIT
    RLGLColorBuffer
  | -- | GL_DEPTH_BUFFER_BIT
    RLGLDepthBuffer
  | -- | GL_STENCIL_BUFFER_BIT
    RLGLStencilBuffer
  deriving (RLBitField -> RLBitField -> Bool
(RLBitField -> RLBitField -> Bool)
-> (RLBitField -> RLBitField -> Bool) -> Eq RLBitField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLBitField -> RLBitField -> Bool
== :: RLBitField -> RLBitField -> Bool
$c/= :: RLBitField -> RLBitField -> Bool
/= :: RLBitField -> RLBitField -> Bool
Eq, Int -> RLBitField -> ShowS
[RLBitField] -> ShowS
RLBitField -> String
(Int -> RLBitField -> ShowS)
-> (RLBitField -> String)
-> ([RLBitField] -> ShowS)
-> Show RLBitField
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLBitField -> ShowS
showsPrec :: Int -> RLBitField -> ShowS
$cshow :: RLBitField -> String
show :: RLBitField -> String
$cshowList :: [RLBitField] -> ShowS
showList :: [RLBitField] -> ShowS
Show)

instance Enum RLBitField where
  fromEnum :: RLBitField -> Int
fromEnum RLBitField
n = case RLBitField
n of
    RLBitField
RLGLColorBuffer -> Int
0x00004000
    RLBitField
RLGLDepthBuffer -> Int
0x00000100
    RLBitField
RLGLStencilBuffer -> Int
0x00000400

  toEnum :: Int -> RLBitField
toEnum Int
n = case Int
n of
    Int
0x00004000 -> RLBitField
RLGLColorBuffer
    Int
0x00000100 -> RLBitField
RLGLDepthBuffer
    Int
0x00000400 -> RLBitField
RLGLStencilBuffer
    Int
_ -> String -> RLBitField
forall a. HasCallStack => String -> a
error (String -> RLBitField) -> String -> RLBitField
forall a b. (a -> b) -> a -> b
$ String
"(RLGLBitField.toEnum) Invalid value: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n

instance Storable RLBitField where
  sizeOf :: RLBitField -> Int
sizeOf RLBitField
_ = Int
4
  alignment :: RLBitField -> Int
alignment RLBitField
_ = Int
4
  peek :: Ptr RLBitField -> IO RLBitField
peek Ptr RLBitField
ptr = do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLBitField -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLBitField
ptr)
    RLBitField -> IO RLBitField
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLBitField -> IO RLBitField) -> RLBitField -> IO RLBitField
forall a b. (a -> b) -> a -> b
$ Int -> RLBitField
forall a. Enum a => Int -> a
toEnum (Int -> RLBitField) -> Int -> RLBitField
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt
val :: CInt)
  poke :: Ptr RLBitField -> RLBitField -> IO ()
poke Ptr RLBitField
ptr RLBitField
v = Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLBitField -> Ptr CInt
forall a b. Ptr a -> Ptr b
castPtr Ptr RLBitField
ptr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (RLBitField -> Int
forall a. Enum a => a -> Int
fromEnum RLBitField
v) :: CInt)

---------------------------------------
-- rlgl structures --------------------
---------------------------------------

-- | Dynamic vertex buffers (position + texcoords + colors + indices arrays)
data RLVertexBuffer = RLVertexBuffer
  { -- | Number of elements in the buffer (QUADS)
    RLVertexBuffer -> Int
rlVertexBuffer'elementCount :: Int,
    -- | Vertex position (shader-location = 0)
    RLVertexBuffer -> [Vector3]
rlVertexBuffer'vertices :: [Vector3],
    -- | Vertex texture coordinates (UV - 2 components per vertex) (shader-location = 1)
    RLVertexBuffer -> [Vector2]
rlVertexBuffer'texcoords :: [Vector2],
    -- | Vertex colors (RGBA - 4 components per vertex) (shader-location = 3)
    RLVertexBuffer -> [Color]
rlVertexBuffer'colors :: [Color],
    -- | Vertex indices (in case vertex data comes indexed) (6 indices per quad)
    RLVertexBuffer -> [Integer]
rlVertexBuffer'indices :: [Integer],
    -- | OpenGL Vertex Array Object id
    RLVertexBuffer -> Integer
rlVertexBuffer'vaoId :: Integer,
    -- | OpenGL Vertex Buffer Objects id (4 types of vertex data)
    RLVertexBuffer -> [Integer]
rlVertexBuffer'vboId :: [Integer]
  }
  deriving (RLVertexBuffer -> RLVertexBuffer -> Bool
(RLVertexBuffer -> RLVertexBuffer -> Bool)
-> (RLVertexBuffer -> RLVertexBuffer -> Bool) -> Eq RLVertexBuffer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLVertexBuffer -> RLVertexBuffer -> Bool
== :: RLVertexBuffer -> RLVertexBuffer -> Bool
$c/= :: RLVertexBuffer -> RLVertexBuffer -> Bool
/= :: RLVertexBuffer -> RLVertexBuffer -> Bool
Eq, Int -> RLVertexBuffer -> ShowS
[RLVertexBuffer] -> ShowS
RLVertexBuffer -> String
(Int -> RLVertexBuffer -> ShowS)
-> (RLVertexBuffer -> String)
-> ([RLVertexBuffer] -> ShowS)
-> Show RLVertexBuffer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLVertexBuffer -> ShowS
showsPrec :: Int -> RLVertexBuffer -> ShowS
$cshow :: RLVertexBuffer -> String
show :: RLVertexBuffer -> String
$cshowList :: [RLVertexBuffer] -> ShowS
showList :: [RLVertexBuffer] -> ShowS
Show)

instance Storable RLVertexBuffer where
  sizeOf :: RLVertexBuffer -> Int
sizeOf RLVertexBuffer
_ = Int
64
  alignment :: RLVertexBuffer -> Int
alignment RLVertexBuffer
_ = Int
8
  peek :: Ptr RLVertexBuffer -> IO RLVertexBuffer
peek Ptr RLVertexBuffer
_p = do
    Int
elementCount <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLVertexBuffer -> Ptr CInt
p'rlVertexBuffer'elementCount Ptr RLVertexBuffer
_p)
    [Vector3]
vertices <- Int -> Ptr Vector3 -> IO [Vector3]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
elementCount (Ptr Vector3 -> IO [Vector3]) -> IO (Ptr Vector3) -> IO [Vector3]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr Vector3) -> IO (Ptr Vector3)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLVertexBuffer -> Ptr (Ptr Vector3)
p'rlVertexBuffer'vertices Ptr RLVertexBuffer
_p)
    [Vector2]
texcoords <- Int -> Ptr Vector2 -> IO [Vector2]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
elementCount (Ptr Vector2 -> IO [Vector2]) -> IO (Ptr Vector2) -> IO [Vector2]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr Vector2) -> IO (Ptr Vector2)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLVertexBuffer -> Ptr (Ptr Vector2)
p'rlVertexBuffer'texcoords Ptr RLVertexBuffer
_p)
    [Color]
colors <- Int -> Ptr Color -> IO [Color]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
elementCount (Ptr Color -> IO [Color]) -> IO (Ptr Color) -> IO [Color]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr Color) -> IO (Ptr Color)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLVertexBuffer -> Ptr (Ptr Color)
p'rlVertexBuffer'colors Ptr RLVertexBuffer
_p)
    [Integer]
indices <- (CUInt -> Integer) -> [CUInt] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
map CUInt -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([CUInt] -> [Integer]) -> IO [CUInt] -> IO [Integer]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Int -> Ptr CUInt -> IO [CUInt]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
elementCount (Ptr CUInt -> IO [CUInt]) -> IO (Ptr CUInt) -> IO [CUInt]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr CUInt) -> IO (Ptr CUInt)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLVertexBuffer -> Ptr (Ptr CUInt)
p'rlVertexBuffer'indices Ptr RLVertexBuffer
_p))
    Integer
vaoId <- CUInt -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUInt -> Integer) -> IO CUInt -> IO Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLVertexBuffer -> Ptr CUInt
p'rlVertexBuffer'vaoId Ptr RLVertexBuffer
_p)
    [Integer]
vboId <- (CUInt -> Integer) -> [CUInt] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
map CUInt -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([CUInt] -> [Integer]) -> IO [CUInt] -> IO [Integer]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Ptr CUInt -> IO [CUInt]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekStaticArray Int
4 (Ptr RLVertexBuffer -> Ptr CUInt
p'rlVertexBuffer'vboId Ptr RLVertexBuffer
_p)
    RLVertexBuffer -> IO RLVertexBuffer
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLVertexBuffer -> IO RLVertexBuffer)
-> RLVertexBuffer -> IO RLVertexBuffer
forall a b. (a -> b) -> a -> b
$ Int
-> [Vector3]
-> [Vector2]
-> [Color]
-> [Integer]
-> Integer
-> [Integer]
-> RLVertexBuffer
RLVertexBuffer Int
elementCount [Vector3]
vertices [Vector2]
texcoords [Color]
colors [Integer]
indices Integer
vaoId [Integer]
vboId
  poke :: Ptr RLVertexBuffer -> RLVertexBuffer -> IO ()
poke Ptr RLVertexBuffer
_p (RLVertexBuffer Int
elementCount [Vector3]
vertices [Vector2]
texcoords [Color]
colors [Integer]
indices Integer
vaoId [Integer]
vboId) = do
    Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLVertexBuffer -> Ptr CInt
p'rlVertexBuffer'elementCount Ptr RLVertexBuffer
_p) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
elementCount)
    Ptr (Ptr Vector3) -> Ptr Vector3 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLVertexBuffer -> Ptr (Ptr Vector3)
p'rlVertexBuffer'vertices Ptr RLVertexBuffer
_p) (Ptr Vector3 -> IO ()) -> IO (Ptr Vector3) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [Vector3] -> IO (Ptr Vector3)
forall a. Storable a => [a] -> IO (Ptr a)
newArray [Vector3]
vertices
    Ptr (Ptr Vector2) -> Ptr Vector2 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLVertexBuffer -> Ptr (Ptr Vector2)
p'rlVertexBuffer'texcoords Ptr RLVertexBuffer
_p) (Ptr Vector2 -> IO ()) -> IO (Ptr Vector2) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [Vector2] -> IO (Ptr Vector2)
forall a. Storable a => [a] -> IO (Ptr a)
newArray [Vector2]
texcoords
    Ptr (Ptr Color) -> Ptr Color -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLVertexBuffer -> Ptr (Ptr Color)
p'rlVertexBuffer'colors Ptr RLVertexBuffer
_p) (Ptr Color -> IO ()) -> IO (Ptr Color) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [Color] -> IO (Ptr Color)
forall a. Storable a => [a] -> IO (Ptr a)
newArray [Color]
colors
    Ptr (Ptr CUInt) -> Ptr CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLVertexBuffer -> Ptr (Ptr CUInt)
p'rlVertexBuffer'indices Ptr RLVertexBuffer
_p) (Ptr CUInt -> IO ()) -> IO (Ptr CUInt) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [CUInt] -> IO (Ptr CUInt)
forall a. Storable a => [a] -> IO (Ptr a)
newArray ((Integer -> CUInt) -> [Integer] -> [CUInt]
forall a b. (a -> b) -> [a] -> [b]
map Integer -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral [Integer]
indices)
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLVertexBuffer -> Ptr CUInt
p'rlVertexBuffer'vaoId Ptr RLVertexBuffer
_p) (Integer -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
vaoId)
    Ptr CUInt -> [CUInt] -> IO ()
forall a. Storable a => Ptr a -> [a] -> IO ()
pokeStaticArray (Ptr RLVertexBuffer -> Ptr CUInt
p'rlVertexBuffer'vboId Ptr RLVertexBuffer
_p) ((Integer -> CUInt) -> [Integer] -> [CUInt]
forall a b. (a -> b) -> [a] -> [b]
map Integer -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral [Integer]
vboId)
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

p'rlVertexBuffer'elementCount :: Ptr RLVertexBuffer -> Ptr CInt
p'rlVertexBuffer'elementCount :: Ptr RLVertexBuffer -> Ptr CInt
p'rlVertexBuffer'elementCount = (Ptr RLVertexBuffer -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0)

-- array (rlVertexBuffer'elementCount)
p'rlVertexBuffer'vertices :: Ptr RLVertexBuffer -> Ptr (Ptr Vector3)
p'rlVertexBuffer'vertices :: Ptr RLVertexBuffer -> Ptr (Ptr Vector3)
p'rlVertexBuffer'vertices = (Ptr RLVertexBuffer -> Int -> Ptr (Ptr Vector3)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8)

-- array (rlVertexBuffer'elementCount)
p'rlVertexBuffer'texcoords :: Ptr RLVertexBuffer -> Ptr (Ptr Vector2)
p'rlVertexBuffer'texcoords :: Ptr RLVertexBuffer -> Ptr (Ptr Vector2)
p'rlVertexBuffer'texcoords = (Ptr RLVertexBuffer -> Int -> Ptr (Ptr Vector2)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16)

-- array (rlVertexBuffer'elementCount)
p'rlVertexBuffer'colors :: Ptr RLVertexBuffer -> Ptr (Ptr Color)
p'rlVertexBuffer'colors :: Ptr RLVertexBuffer -> Ptr (Ptr Color)
p'rlVertexBuffer'colors = (Ptr RLVertexBuffer -> Int -> Ptr (Ptr Color)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24)

-- array (rlVertexBuffer'elementCount)
p'rlVertexBuffer'indices :: Ptr RLVertexBuffer -> Ptr (Ptr CUInt)
p'rlVertexBuffer'indices :: Ptr RLVertexBuffer -> Ptr (Ptr CUInt)
p'rlVertexBuffer'indices = (Ptr RLVertexBuffer -> Int -> Ptr (Ptr CUInt)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32)

p'rlVertexBuffer'vaoId :: Ptr RLVertexBuffer -> Ptr CUInt
p'rlVertexBuffer'vaoId :: Ptr RLVertexBuffer -> Ptr CUInt
p'rlVertexBuffer'vaoId = (Ptr RLVertexBuffer -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40)

-- static array (4)
p'rlVertexBuffer'vboId :: Ptr RLVertexBuffer -> Ptr CUInt
p'rlVertexBuffer'vboId :: Ptr RLVertexBuffer -> Ptr CUInt
p'rlVertexBuffer'vboId = (Ptr RLVertexBuffer -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44)

instance Freeable RLVertexBuffer where
  rlFreeDependents :: RLVertexBuffer -> Ptr RLVertexBuffer -> IO ()
rlFreeDependents RLVertexBuffer
_ Ptr RLVertexBuffer
ptr = do
    Ptr () -> IO ()
c'free (Ptr () -> IO ())
-> (Ptr Vector3 -> Ptr ()) -> Ptr Vector3 -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Vector3 -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (Ptr Vector3 -> IO ()) -> IO (Ptr Vector3) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr Vector3) -> IO (Ptr Vector3)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLVertexBuffer -> Ptr (Ptr Vector3)
p'rlVertexBuffer'vertices Ptr RLVertexBuffer
ptr)
    Ptr () -> IO ()
c'free (Ptr () -> IO ())
-> (Ptr Vector2 -> Ptr ()) -> Ptr Vector2 -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Vector2 -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (Ptr Vector2 -> IO ()) -> IO (Ptr Vector2) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr Vector2) -> IO (Ptr Vector2)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLVertexBuffer -> Ptr (Ptr Vector2)
p'rlVertexBuffer'texcoords Ptr RLVertexBuffer
ptr)
    Ptr () -> IO ()
c'free (Ptr () -> IO ()) -> (Ptr Color -> Ptr ()) -> Ptr Color -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Color -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (Ptr Color -> IO ()) -> IO (Ptr Color) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr Color) -> IO (Ptr Color)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLVertexBuffer -> Ptr (Ptr Color)
p'rlVertexBuffer'colors Ptr RLVertexBuffer
ptr)
    Ptr () -> IO ()
c'free (Ptr () -> IO ()) -> (Ptr CUInt -> Ptr ()) -> Ptr CUInt -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr CUInt -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (Ptr CUInt -> IO ()) -> IO (Ptr CUInt) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr CUInt) -> IO (Ptr CUInt)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLVertexBuffer -> Ptr (Ptr CUInt)
p'rlVertexBuffer'indices Ptr RLVertexBuffer
ptr)

-- | Draw call type.
--
-- NOTE: Only texture changes register a new draw, other state-change-related elements are not
-- used at this moment (vaoId, shaderId, matrices), raylib just forces a batch draw call if any
-- of those state changes happen (this is done in the core module).
data RLDrawCall = RLDrawCall
  { -- | Drawing mode: LINES, TRIANGLES, QUADS
    RLDrawCall -> RLDrawMode
rlDrawCall'mode :: RLDrawMode,
    -- | Number of vertices of the draw
    RLDrawCall -> Int
rlDrawCall'vertexCount :: Int,
    -- | Number of vertices required for index alignment (LINES, TRIANGLES)
    RLDrawCall -> Int
rlDrawCall'vertexAlignment :: Int,
    -- | Texture id to be used on the draw -> Used to create new draw call if changed
    RLDrawCall -> Integer
rlDrawCall'textureId :: Integer
  }
  deriving (RLDrawCall -> RLDrawCall -> Bool
(RLDrawCall -> RLDrawCall -> Bool)
-> (RLDrawCall -> RLDrawCall -> Bool) -> Eq RLDrawCall
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLDrawCall -> RLDrawCall -> Bool
== :: RLDrawCall -> RLDrawCall -> Bool
$c/= :: RLDrawCall -> RLDrawCall -> Bool
/= :: RLDrawCall -> RLDrawCall -> Bool
Eq, Int -> RLDrawCall -> ShowS
[RLDrawCall] -> ShowS
RLDrawCall -> String
(Int -> RLDrawCall -> ShowS)
-> (RLDrawCall -> String)
-> ([RLDrawCall] -> ShowS)
-> Show RLDrawCall
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLDrawCall -> ShowS
showsPrec :: Int -> RLDrawCall -> ShowS
$cshow :: RLDrawCall -> String
show :: RLDrawCall -> String
$cshowList :: [RLDrawCall] -> ShowS
showList :: [RLDrawCall] -> ShowS
Show, RLDrawCall -> Ptr RLDrawCall -> IO ()
(RLDrawCall -> Ptr RLDrawCall -> IO ())
-> (RLDrawCall -> Ptr RLDrawCall -> IO ()) -> Freeable RLDrawCall
forall a.
(a -> Ptr a -> IO ()) -> (a -> Ptr a -> IO ()) -> Freeable a
$crlFreeDependents :: RLDrawCall -> Ptr RLDrawCall -> IO ()
rlFreeDependents :: RLDrawCall -> Ptr RLDrawCall -> IO ()
$crlFree :: RLDrawCall -> Ptr RLDrawCall -> IO ()
rlFree :: RLDrawCall -> Ptr RLDrawCall -> IO ()
Freeable)

instance Storable RLDrawCall where
  sizeOf :: RLDrawCall -> Int
sizeOf RLDrawCall
_ = Int
16
  alignment :: RLDrawCall -> Int
alignment RLDrawCall
_ = Int
8
  peek :: Ptr RLDrawCall -> IO RLDrawCall
peek Ptr RLDrawCall
_p = do
    RLDrawMode
mode <- Ptr RLDrawMode -> IO RLDrawMode
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLDrawCall -> Ptr RLDrawMode
p'rlDrawCall'mode Ptr RLDrawCall
_p)
    Int
vertexCount <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLDrawCall -> Ptr CInt
p'rlDrawCall'vertexCount Ptr RLDrawCall
_p)
    Int
vertexAlignment <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLDrawCall -> Ptr CInt
p'rlDrawCall'vertexAlignment Ptr RLDrawCall
_p)
    Integer
textureId <- CUInt -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUInt -> Integer) -> IO CUInt -> IO Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLDrawCall -> Ptr CUInt
p'rlDrawCall'textureId Ptr RLDrawCall
_p)
    RLDrawCall -> IO RLDrawCall
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLDrawCall -> IO RLDrawCall) -> RLDrawCall -> IO RLDrawCall
forall a b. (a -> b) -> a -> b
$ RLDrawMode -> Int -> Int -> Integer -> RLDrawCall
RLDrawCall RLDrawMode
mode Int
vertexCount Int
vertexAlignment Integer
textureId
  poke :: Ptr RLDrawCall -> RLDrawCall -> IO ()
poke Ptr RLDrawCall
_p (RLDrawCall RLDrawMode
mode Int
vertexCount Int
vertexAlignment Integer
textureId) = do
    Ptr RLDrawMode -> RLDrawMode -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLDrawCall -> Ptr RLDrawMode
p'rlDrawCall'mode Ptr RLDrawCall
_p) RLDrawMode
mode
    Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLDrawCall -> Ptr CInt
p'rlDrawCall'vertexCount Ptr RLDrawCall
_p) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
vertexCount)
    Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLDrawCall -> Ptr CInt
p'rlDrawCall'vertexAlignment Ptr RLDrawCall
_p) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
vertexAlignment)
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLDrawCall -> Ptr CUInt
p'rlDrawCall'textureId Ptr RLDrawCall
_p) (Integer -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
textureId)
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

p'rlDrawCall'mode :: Ptr RLDrawCall -> Ptr RLDrawMode
p'rlDrawCall'mode :: Ptr RLDrawCall -> Ptr RLDrawMode
p'rlDrawCall'mode = (Ptr RLDrawCall -> Int -> Ptr RLDrawMode
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0)

p'rlDrawCall'vertexCount :: Ptr RLDrawCall -> Ptr CInt
p'rlDrawCall'vertexCount :: Ptr RLDrawCall -> Ptr CInt
p'rlDrawCall'vertexCount = (Ptr RLDrawCall -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4)

p'rlDrawCall'vertexAlignment :: Ptr RLDrawCall -> Ptr CInt
p'rlDrawCall'vertexAlignment :: Ptr RLDrawCall -> Ptr CInt
p'rlDrawCall'vertexAlignment = (Ptr RLDrawCall -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8)

p'rlDrawCall'textureId :: Ptr RLDrawCall -> Ptr CUInt
p'rlDrawCall'textureId :: Ptr RLDrawCall -> Ptr CUInt
p'rlDrawCall'textureId = (Ptr RLDrawCall -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12)

-- rlRenderBatch type
data RLRenderBatch = RLRenderBatch
  { -- | Number of vertex buffers (multi-buffering support)
    RLRenderBatch -> Int
rlRenderBatch'bufferCount :: Int,
    -- | Current buffer tracking in case of multi-buffering
    RLRenderBatch -> Int
rlRenderBatch'currentBuffer :: Int,
    -- | Dynamic buffer(s) for vertex data
    RLRenderBatch -> [RLVertexBuffer]
rlRenderBatch'vertexBuffers :: [RLVertexBuffer],
    -- | Draw calls array, depends on textureId
    RLRenderBatch -> [RLDrawCall]
rlRenderBatch'draws :: [RLDrawCall],
    -- | Draw calls counter
    RLRenderBatch -> Int
rlRenderBatch'drawCounter :: Int,
    -- | Current depth value for next draw
    RLRenderBatch -> Float
rlRenderBatch'currentDepth :: Float
  }
  deriving (RLRenderBatch -> RLRenderBatch -> Bool
(RLRenderBatch -> RLRenderBatch -> Bool)
-> (RLRenderBatch -> RLRenderBatch -> Bool) -> Eq RLRenderBatch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RLRenderBatch -> RLRenderBatch -> Bool
== :: RLRenderBatch -> RLRenderBatch -> Bool
$c/= :: RLRenderBatch -> RLRenderBatch -> Bool
/= :: RLRenderBatch -> RLRenderBatch -> Bool
Eq, Int -> RLRenderBatch -> ShowS
[RLRenderBatch] -> ShowS
RLRenderBatch -> String
(Int -> RLRenderBatch -> ShowS)
-> (RLRenderBatch -> String)
-> ([RLRenderBatch] -> ShowS)
-> Show RLRenderBatch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RLRenderBatch -> ShowS
showsPrec :: Int -> RLRenderBatch -> ShowS
$cshow :: RLRenderBatch -> String
show :: RLRenderBatch -> String
$cshowList :: [RLRenderBatch] -> ShowS
showList :: [RLRenderBatch] -> ShowS
Show)

instance Storable RLRenderBatch where
  sizeOf :: RLRenderBatch -> Int
sizeOf RLRenderBatch
_ = Int
32
  alignment :: RLRenderBatch -> Int
alignment RLRenderBatch
_ = Int
8
  peek :: Ptr RLRenderBatch -> IO RLRenderBatch
peek Ptr RLRenderBatch
_p = do
    Int
bufferCount <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLRenderBatch -> Ptr CInt
p'rlRenderBatch'bufferCount Ptr RLRenderBatch
_p)
    Int
currentBuffer <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLRenderBatch -> Ptr CInt
p'rlRenderBatch'currentBuffer Ptr RLRenderBatch
_p)
    [RLVertexBuffer]
vertexBuffers <- Int -> Ptr RLVertexBuffer -> IO [RLVertexBuffer]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
bufferCount (Ptr RLVertexBuffer -> IO [RLVertexBuffer])
-> IO (Ptr RLVertexBuffer) -> IO [RLVertexBuffer]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr RLVertexBuffer) -> IO (Ptr RLVertexBuffer)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLRenderBatch -> Ptr (Ptr RLVertexBuffer)
p'rlRenderBatch'vertexBuffers Ptr RLRenderBatch
_p)
    [RLDrawCall]
draws <- Int -> Ptr RLDrawCall -> IO [RLDrawCall]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
256 (Ptr RLDrawCall -> IO [RLDrawCall])
-> IO (Ptr RLDrawCall) -> IO [RLDrawCall]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr RLDrawCall) -> IO (Ptr RLDrawCall)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLRenderBatch -> Ptr (Ptr RLDrawCall)
p'rlRenderBatch'draws Ptr RLRenderBatch
_p)
    Int
drawCounter <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLRenderBatch -> Ptr CInt
p'rlRenderBatch'drawCounter Ptr RLRenderBatch
_p)
    Float
currentDepth <- CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac (CFloat -> Float) -> IO CFloat -> IO Float
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLRenderBatch -> Ptr CFloat
p'rlRenderBatch'currentDepth Ptr RLRenderBatch
_p)
    RLRenderBatch -> IO RLRenderBatch
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (RLRenderBatch -> IO RLRenderBatch)
-> RLRenderBatch -> IO RLRenderBatch
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> [RLVertexBuffer]
-> [RLDrawCall]
-> Int
-> Float
-> RLRenderBatch
RLRenderBatch Int
bufferCount Int
currentBuffer [RLVertexBuffer]
vertexBuffers [RLDrawCall]
draws Int
drawCounter Float
currentDepth
  poke :: Ptr RLRenderBatch -> RLRenderBatch -> IO ()
poke Ptr RLRenderBatch
_p (RLRenderBatch Int
bufferCount Int
currentBuffer [RLVertexBuffer]
vertexBuffers [RLDrawCall]
draws Int
drawCounter Float
currentDepth) = do
    Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLRenderBatch -> Ptr CInt
p'rlRenderBatch'bufferCount Ptr RLRenderBatch
_p) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
bufferCount)
    Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLRenderBatch -> Ptr CInt
p'rlRenderBatch'currentBuffer Ptr RLRenderBatch
_p) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
currentBuffer)
    Ptr (Ptr RLVertexBuffer) -> Ptr RLVertexBuffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLRenderBatch -> Ptr (Ptr RLVertexBuffer)
p'rlRenderBatch'vertexBuffers Ptr RLRenderBatch
_p) (Ptr RLVertexBuffer -> IO ()) -> IO (Ptr RLVertexBuffer) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [RLVertexBuffer] -> IO (Ptr RLVertexBuffer)
forall a. Storable a => [a] -> IO (Ptr a)
newArray [RLVertexBuffer]
vertexBuffers
    Ptr (Ptr RLDrawCall) -> Ptr RLDrawCall -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLRenderBatch -> Ptr (Ptr RLDrawCall)
p'rlRenderBatch'draws Ptr RLRenderBatch
_p) (Ptr RLDrawCall -> IO ()) -> IO (Ptr RLDrawCall) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [RLDrawCall] -> IO (Ptr RLDrawCall)
forall a. Storable a => [a] -> IO (Ptr a)
newArray [RLDrawCall]
draws
    Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLRenderBatch -> Ptr CInt
p'rlRenderBatch'drawCounter Ptr RLRenderBatch
_p) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
drawCounter)
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RLRenderBatch -> Ptr CFloat
p'rlRenderBatch'currentDepth Ptr RLRenderBatch
_p) (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
currentDepth)
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

p'rlRenderBatch'bufferCount :: Ptr RLRenderBatch -> Ptr CInt
p'rlRenderBatch'bufferCount :: Ptr RLRenderBatch -> Ptr CInt
p'rlRenderBatch'bufferCount = (Ptr RLRenderBatch -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0)

p'rlRenderBatch'currentBuffer :: Ptr RLRenderBatch -> Ptr CInt
p'rlRenderBatch'currentBuffer :: Ptr RLRenderBatch -> Ptr CInt
p'rlRenderBatch'currentBuffer = (Ptr RLRenderBatch -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4)

-- array (rlRenderBatch'bufferCount)
p'rlRenderBatch'vertexBuffers :: Ptr RLRenderBatch -> Ptr (Ptr RLVertexBuffer)
p'rlRenderBatch'vertexBuffers :: Ptr RLRenderBatch -> Ptr (Ptr RLVertexBuffer)
p'rlRenderBatch'vertexBuffers = (Ptr RLRenderBatch -> Int -> Ptr (Ptr RLVertexBuffer)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8)

-- array (256)
p'rlRenderBatch'draws :: Ptr RLRenderBatch -> Ptr (Ptr RLDrawCall)
p'rlRenderBatch'draws :: Ptr RLRenderBatch -> Ptr (Ptr RLDrawCall)
p'rlRenderBatch'draws = (Ptr RLRenderBatch -> Int -> Ptr (Ptr RLDrawCall)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16)

p'rlRenderBatch'drawCounter :: Ptr RLRenderBatch -> Ptr CInt
p'rlRenderBatch'drawCounter :: Ptr RLRenderBatch -> Ptr CInt
p'rlRenderBatch'drawCounter = (Ptr RLRenderBatch -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24)

p'rlRenderBatch'currentDepth :: Ptr RLRenderBatch -> Ptr CFloat
p'rlRenderBatch'currentDepth :: Ptr RLRenderBatch -> Ptr CFloat
p'rlRenderBatch'currentDepth = (Ptr RLRenderBatch -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28)

instance Freeable RLRenderBatch where
  rlFreeDependents :: RLRenderBatch -> Ptr RLRenderBatch -> IO ()
rlFreeDependents RLRenderBatch
val Ptr RLRenderBatch
ptr = do
    [RLVertexBuffer] -> Ptr [RLVertexBuffer] -> IO ()
forall a. Freeable a => a -> Ptr a -> IO ()
rlFree (RLRenderBatch -> [RLVertexBuffer]
rlRenderBatch'vertexBuffers RLRenderBatch
val) (Ptr [RLVertexBuffer] -> IO ())
-> (Ptr RLVertexBuffer -> Ptr [RLVertexBuffer])
-> Ptr RLVertexBuffer
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr RLVertexBuffer -> Ptr [RLVertexBuffer]
forall a b. Ptr a -> Ptr b
castPtr (Ptr RLVertexBuffer -> IO ()) -> IO (Ptr RLVertexBuffer) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr RLVertexBuffer) -> IO (Ptr RLVertexBuffer)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLRenderBatch -> Ptr (Ptr RLVertexBuffer)
p'rlRenderBatch'vertexBuffers Ptr RLRenderBatch
ptr)
    Ptr () -> IO ()
c'free (Ptr () -> IO ())
-> (Ptr RLDrawCall -> Ptr ()) -> Ptr RLDrawCall -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr RLDrawCall -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (Ptr RLDrawCall -> IO ()) -> IO (Ptr RLDrawCall) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr RLDrawCall) -> IO (Ptr RLDrawCall)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RLRenderBatch -> Ptr (Ptr RLDrawCall)
p'rlRenderBatch'draws Ptr RLRenderBatch
ptr)