-- This file was automatically generated.
{-# LANGUAGE CPP, ScopedTypeVariables, PatternSynonyms #-}
module Graphics.GL.Ext.NV.CommandList (
  -- * Extension Support
    gl_NV_command_list

  -- * GL_NV_command_list
  , glCallCommandListNV
  , glCommandListSegmentsNV
  , glCompileCommandListNV
  , glCreateCommandListsNV
  , glCreateStatesNV
  , glDeleteCommandListsNV
  , glDeleteStatesNV
  , glDrawCommandsAddressNV
  , glDrawCommandsNV
  , glDrawCommandsStatesAddressNV
  , glDrawCommandsStatesNV
  , glGetCommandHeaderNV
  , glGetStageIndexNV
  , glIsCommandListNV
  , glIsStateNV
  , glListDrawCommandsStatesClientNV
  , glStateCaptureNV
  , pattern GL_ALPHA_REF_COMMAND_NV
  , pattern GL_ATTRIBUTE_ADDRESS_COMMAND_NV
  , pattern GL_BLEND_COLOR_COMMAND_NV
  , pattern GL_DRAW_ARRAYS_COMMAND_NV
  , pattern GL_DRAW_ARRAYS_INSTANCED_COMMAND_NV
  , pattern GL_DRAW_ARRAYS_STRIP_COMMAND_NV
  , pattern GL_DRAW_ELEMENTS_COMMAND_NV
  , pattern GL_DRAW_ELEMENTS_INSTANCED_COMMAND_NV
  , pattern GL_DRAW_ELEMENTS_STRIP_COMMAND_NV
  , pattern GL_ELEMENT_ADDRESS_COMMAND_NV
  , pattern GL_FRONT_FACE_COMMAND_NV
  , pattern GL_LINE_WIDTH_COMMAND_NV
  , pattern GL_NOP_COMMAND_NV
  , pattern GL_POLYGON_OFFSET_COMMAND_NV
  , pattern GL_SCISSOR_COMMAND_NV
  , pattern GL_STENCIL_REF_COMMAND_NV
  , pattern GL_TERMINATE_SEQUENCE_COMMAND_NV
  , pattern GL_UNIFORM_ADDRESS_COMMAND_NV
  , pattern GL_VIEWPORT_COMMAND_NV
) where

import Control.Monad.IO.Class
import Data.Set
import Foreign.Ptr
import Graphics.GL.Internal.FFI
import Graphics.GL.Internal.Proc
import Graphics.GL.Types
import System.IO.Unsafe

-- | Checks that the <https://cvs.khronos.org/svn/repos/ogl/trunk/doc/registry/public/specs/NV/command_list.txt GL_NV_command_list> extension is available.

gl_NV_command_list :: Bool
gl_NV_command_list :: Bool
gl_NV_command_list = [Char] -> Set [Char] -> Bool
forall a. Ord a => a -> Set a -> Bool
member "GL_NV_command_list" Set [Char]
extensions
{-# NOINLINE gl_NV_command_list #-}

-- | Usage: @'glCallCommandListNV' list@


glCallCommandListNV :: MonadIO m => GLuint -> m ()
glCallCommandListNV :: GLuint -> m ()
glCallCommandListNV = FunPtr (GLuint -> IO ()) -> GLuint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLuint -> IO ()) -> GLuint -> m ()
ffiuintIOV FunPtr (GLuint -> IO ())
glCallCommandListNVFunPtr

glCallCommandListNVFunPtr :: FunPtr (GLuint -> IO ())
glCallCommandListNVFunPtr :: FunPtr (GLuint -> IO ())
glCallCommandListNVFunPtr = IO (FunPtr (GLuint -> IO ())) -> FunPtr (GLuint -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLuint -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glCallCommandListNV")

{-# NOINLINE glCallCommandListNVFunPtr #-}

-- | Usage: @'glCommandListSegmentsNV' list segments@


glCommandListSegmentsNV :: MonadIO m => GLuint -> GLuint -> m ()
glCommandListSegmentsNV :: GLuint -> GLuint -> m ()
glCommandListSegmentsNV = FunPtr (GLuint -> GLuint -> IO ()) -> GLuint -> GLuint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLuint -> GLuint -> IO ()) -> GLuint -> GLuint -> m ()
ffiuintuintIOV FunPtr (GLuint -> GLuint -> IO ())
glCommandListSegmentsNVFunPtr

glCommandListSegmentsNVFunPtr :: FunPtr (GLuint -> GLuint -> IO ())
glCommandListSegmentsNVFunPtr :: FunPtr (GLuint -> GLuint -> IO ())
glCommandListSegmentsNVFunPtr = IO (FunPtr (GLuint -> GLuint -> IO ()))
-> FunPtr (GLuint -> GLuint -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLuint -> GLuint -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glCommandListSegmentsNV")

{-# NOINLINE glCommandListSegmentsNVFunPtr #-}

-- | Usage: @'glCompileCommandListNV' list@


glCompileCommandListNV :: MonadIO m => GLuint -> m ()
glCompileCommandListNV :: GLuint -> m ()
glCompileCommandListNV = FunPtr (GLuint -> IO ()) -> GLuint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLuint -> IO ()) -> GLuint -> m ()
ffiuintIOV FunPtr (GLuint -> IO ())
glCompileCommandListNVFunPtr

glCompileCommandListNVFunPtr :: FunPtr (GLuint -> IO ())
glCompileCommandListNVFunPtr :: FunPtr (GLuint -> IO ())
glCompileCommandListNVFunPtr = IO (FunPtr (GLuint -> IO ())) -> FunPtr (GLuint -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLuint -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glCompileCommandListNV")

{-# NOINLINE glCompileCommandListNVFunPtr #-}

-- | Usage: @'glCreateCommandListsNV' n lists@


glCreateCommandListsNV :: MonadIO m => GLsizei -> Ptr GLuint -> m ()
glCreateCommandListsNV :: GLsizei -> Ptr GLuint -> m ()
glCreateCommandListsNV = FunPtr (GLsizei -> Ptr GLuint -> IO ())
-> GLsizei -> Ptr GLuint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLsizei -> Ptr GLuint -> IO ())
-> GLsizei -> Ptr GLuint -> m ()
ffisizeiPtruintIOV FunPtr (GLsizei -> Ptr GLuint -> IO ())
glCreateCommandListsNVFunPtr

glCreateCommandListsNVFunPtr :: FunPtr (GLsizei -> Ptr GLuint -> IO ())
glCreateCommandListsNVFunPtr :: FunPtr (GLsizei -> Ptr GLuint -> IO ())
glCreateCommandListsNVFunPtr = IO (FunPtr (GLsizei -> Ptr GLuint -> IO ()))
-> FunPtr (GLsizei -> Ptr GLuint -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLsizei -> Ptr GLuint -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glCreateCommandListsNV")

{-# NOINLINE glCreateCommandListsNVFunPtr #-}

-- | Usage: @'glCreateStatesNV' n states@


glCreateStatesNV :: MonadIO m => GLsizei -> Ptr GLuint -> m ()
glCreateStatesNV :: GLsizei -> Ptr GLuint -> m ()
glCreateStatesNV = FunPtr (GLsizei -> Ptr GLuint -> IO ())
-> GLsizei -> Ptr GLuint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLsizei -> Ptr GLuint -> IO ())
-> GLsizei -> Ptr GLuint -> m ()
ffisizeiPtruintIOV FunPtr (GLsizei -> Ptr GLuint -> IO ())
glCreateStatesNVFunPtr

glCreateStatesNVFunPtr :: FunPtr (GLsizei -> Ptr GLuint -> IO ())
glCreateStatesNVFunPtr :: FunPtr (GLsizei -> Ptr GLuint -> IO ())
glCreateStatesNVFunPtr = IO (FunPtr (GLsizei -> Ptr GLuint -> IO ()))
-> FunPtr (GLsizei -> Ptr GLuint -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLsizei -> Ptr GLuint -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glCreateStatesNV")

{-# NOINLINE glCreateStatesNVFunPtr #-}

-- | Usage: @'glDeleteCommandListsNV' n lists@


glDeleteCommandListsNV :: MonadIO m => GLsizei -> Ptr GLuint -> m ()
glDeleteCommandListsNV :: GLsizei -> Ptr GLuint -> m ()
glDeleteCommandListsNV = FunPtr (GLsizei -> Ptr GLuint -> IO ())
-> GLsizei -> Ptr GLuint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLsizei -> Ptr GLuint -> IO ())
-> GLsizei -> Ptr GLuint -> m ()
ffisizeiPtruintIOV FunPtr (GLsizei -> Ptr GLuint -> IO ())
glDeleteCommandListsNVFunPtr

glDeleteCommandListsNVFunPtr :: FunPtr (GLsizei -> Ptr GLuint -> IO ())
glDeleteCommandListsNVFunPtr :: FunPtr (GLsizei -> Ptr GLuint -> IO ())
glDeleteCommandListsNVFunPtr = IO (FunPtr (GLsizei -> Ptr GLuint -> IO ()))
-> FunPtr (GLsizei -> Ptr GLuint -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLsizei -> Ptr GLuint -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDeleteCommandListsNV")

{-# NOINLINE glDeleteCommandListsNVFunPtr #-}

-- | Usage: @'glDeleteStatesNV' n states@


glDeleteStatesNV :: MonadIO m => GLsizei -> Ptr GLuint -> m ()
glDeleteStatesNV :: GLsizei -> Ptr GLuint -> m ()
glDeleteStatesNV = FunPtr (GLsizei -> Ptr GLuint -> IO ())
-> GLsizei -> Ptr GLuint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLsizei -> Ptr GLuint -> IO ())
-> GLsizei -> Ptr GLuint -> m ()
ffisizeiPtruintIOV FunPtr (GLsizei -> Ptr GLuint -> IO ())
glDeleteStatesNVFunPtr

glDeleteStatesNVFunPtr :: FunPtr (GLsizei -> Ptr GLuint -> IO ())
glDeleteStatesNVFunPtr :: FunPtr (GLsizei -> Ptr GLuint -> IO ())
glDeleteStatesNVFunPtr = IO (FunPtr (GLsizei -> Ptr GLuint -> IO ()))
-> FunPtr (GLsizei -> Ptr GLuint -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLsizei -> Ptr GLuint -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDeleteStatesNV")

{-# NOINLINE glDeleteStatesNVFunPtr #-}

-- | Usage: @'glDrawCommandsAddressNV' primitiveMode indirects sizes count@


glDrawCommandsAddressNV :: MonadIO m => GLenum -> Ptr GLuint64 -> Ptr GLsizei -> GLuint -> m ()
glDrawCommandsAddressNV :: GLuint -> Ptr GLuint64 -> Ptr GLsizei -> GLuint -> m ()
glDrawCommandsAddressNV = FunPtr (GLuint -> Ptr GLuint64 -> Ptr GLsizei -> GLuint -> IO ())
-> GLuint -> Ptr GLuint64 -> Ptr GLsizei -> GLuint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLuint -> Ptr GLuint64 -> Ptr GLsizei -> GLuint -> IO ())
-> GLuint -> Ptr GLuint64 -> Ptr GLsizei -> GLuint -> m ()
ffienumPtruint64PtrsizeiuintIOV FunPtr (GLuint -> Ptr GLuint64 -> Ptr GLsizei -> GLuint -> IO ())
glDrawCommandsAddressNVFunPtr

glDrawCommandsAddressNVFunPtr :: FunPtr (GLenum -> Ptr GLuint64 -> Ptr GLsizei -> GLuint -> IO ())
glDrawCommandsAddressNVFunPtr :: FunPtr (GLuint -> Ptr GLuint64 -> Ptr GLsizei -> GLuint -> IO ())
glDrawCommandsAddressNVFunPtr = IO
  (FunPtr (GLuint -> Ptr GLuint64 -> Ptr GLsizei -> GLuint -> IO ()))
-> FunPtr
     (GLuint -> Ptr GLuint64 -> Ptr GLsizei -> GLuint -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char]
-> IO
     (FunPtr (GLuint -> Ptr GLuint64 -> Ptr GLsizei -> GLuint -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDrawCommandsAddressNV")

{-# NOINLINE glDrawCommandsAddressNVFunPtr #-}

-- | Usage: @'glDrawCommandsNV' primitiveMode buffer indirects sizes count@


glDrawCommandsNV :: MonadIO m => GLenum -> GLuint -> Ptr GLintptr -> Ptr GLsizei -> GLuint -> m ()
glDrawCommandsNV :: GLuint -> GLuint -> Ptr GLintptr -> Ptr GLsizei -> GLuint -> m ()
glDrawCommandsNV = FunPtr
  (GLuint
   -> GLuint -> Ptr GLintptr -> Ptr GLsizei -> GLuint -> IO ())
-> GLuint
-> GLuint
-> Ptr GLintptr
-> Ptr GLsizei
-> GLuint
-> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr
  (GLuint
   -> GLuint -> Ptr GLintptr -> Ptr GLsizei -> GLuint -> IO ())
-> GLuint
-> GLuint
-> Ptr GLintptr
-> Ptr GLsizei
-> GLuint
-> m ()
ffienumuintPtrintptrPtrsizeiuintIOV FunPtr
  (GLuint
   -> GLuint -> Ptr GLintptr -> Ptr GLsizei -> GLuint -> IO ())
glDrawCommandsNVFunPtr

glDrawCommandsNVFunPtr :: FunPtr (GLenum -> GLuint -> Ptr GLintptr -> Ptr GLsizei -> GLuint -> IO ())
glDrawCommandsNVFunPtr :: FunPtr
  (GLuint
   -> GLuint -> Ptr GLintptr -> Ptr GLsizei -> GLuint -> IO ())
glDrawCommandsNVFunPtr = IO
  (FunPtr
     (GLuint
      -> GLuint -> Ptr GLintptr -> Ptr GLsizei -> GLuint -> IO ()))
-> FunPtr
     (GLuint
      -> GLuint -> Ptr GLintptr -> Ptr GLsizei -> GLuint -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char]
-> IO
     (FunPtr
        (GLuint
         -> GLuint -> Ptr GLintptr -> Ptr GLsizei -> GLuint -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDrawCommandsNV")

{-# NOINLINE glDrawCommandsNVFunPtr #-}

-- | Usage: @'glDrawCommandsStatesAddressNV' indirects sizes states fbos count@


glDrawCommandsStatesAddressNV :: MonadIO m => Ptr GLuint64 -> Ptr GLsizei -> Ptr GLuint -> Ptr GLuint -> GLuint -> m ()
glDrawCommandsStatesAddressNV :: Ptr GLuint64
-> Ptr GLsizei -> Ptr GLuint -> Ptr GLuint -> GLuint -> m ()
glDrawCommandsStatesAddressNV = FunPtr
  (Ptr GLuint64
   -> Ptr GLsizei -> Ptr GLuint -> Ptr GLuint -> GLuint -> IO ())
-> Ptr GLuint64
-> Ptr GLsizei
-> Ptr GLuint
-> Ptr GLuint
-> GLuint
-> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr
  (Ptr GLuint64
   -> Ptr GLsizei -> Ptr GLuint -> Ptr GLuint -> GLuint -> IO ())
-> Ptr GLuint64
-> Ptr GLsizei
-> Ptr GLuint
-> Ptr GLuint
-> GLuint
-> m ()
ffiPtruint64PtrsizeiPtruintPtruintuintIOV FunPtr
  (Ptr GLuint64
   -> Ptr GLsizei -> Ptr GLuint -> Ptr GLuint -> GLuint -> IO ())
glDrawCommandsStatesAddressNVFunPtr

glDrawCommandsStatesAddressNVFunPtr :: FunPtr (Ptr GLuint64 -> Ptr GLsizei -> Ptr GLuint -> Ptr GLuint -> GLuint -> IO ())
glDrawCommandsStatesAddressNVFunPtr :: FunPtr
  (Ptr GLuint64
   -> Ptr GLsizei -> Ptr GLuint -> Ptr GLuint -> GLuint -> IO ())
glDrawCommandsStatesAddressNVFunPtr = IO
  (FunPtr
     (Ptr GLuint64
      -> Ptr GLsizei -> Ptr GLuint -> Ptr GLuint -> GLuint -> IO ()))
-> FunPtr
     (Ptr GLuint64
      -> Ptr GLsizei -> Ptr GLuint -> Ptr GLuint -> GLuint -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char]
-> IO
     (FunPtr
        (Ptr GLuint64
         -> Ptr GLsizei -> Ptr GLuint -> Ptr GLuint -> GLuint -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDrawCommandsStatesAddressNV")

{-# NOINLINE glDrawCommandsStatesAddressNVFunPtr #-}

-- | Usage: @'glDrawCommandsStatesNV' buffer indirects sizes states fbos count@


glDrawCommandsStatesNV :: MonadIO m => GLuint -> Ptr GLintptr -> Ptr GLsizei -> Ptr GLuint -> Ptr GLuint -> GLuint -> m ()
glDrawCommandsStatesNV :: GLuint
-> Ptr GLintptr
-> Ptr GLsizei
-> Ptr GLuint
-> Ptr GLuint
-> GLuint
-> m ()
glDrawCommandsStatesNV = FunPtr
  (GLuint
   -> Ptr GLintptr
   -> Ptr GLsizei
   -> Ptr GLuint
   -> Ptr GLuint
   -> GLuint
   -> IO ())
-> GLuint
-> Ptr GLintptr
-> Ptr GLsizei
-> Ptr GLuint
-> Ptr GLuint
-> GLuint
-> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr
  (GLuint
   -> Ptr GLintptr
   -> Ptr GLsizei
   -> Ptr GLuint
   -> Ptr GLuint
   -> GLuint
   -> IO ())
-> GLuint
-> Ptr GLintptr
-> Ptr GLsizei
-> Ptr GLuint
-> Ptr GLuint
-> GLuint
-> m ()
ffiuintPtrintptrPtrsizeiPtruintPtruintuintIOV FunPtr
  (GLuint
   -> Ptr GLintptr
   -> Ptr GLsizei
   -> Ptr GLuint
   -> Ptr GLuint
   -> GLuint
   -> IO ())
glDrawCommandsStatesNVFunPtr

glDrawCommandsStatesNVFunPtr :: FunPtr (GLuint -> Ptr GLintptr -> Ptr GLsizei -> Ptr GLuint -> Ptr GLuint -> GLuint -> IO ())
glDrawCommandsStatesNVFunPtr :: FunPtr
  (GLuint
   -> Ptr GLintptr
   -> Ptr GLsizei
   -> Ptr GLuint
   -> Ptr GLuint
   -> GLuint
   -> IO ())
glDrawCommandsStatesNVFunPtr = IO
  (FunPtr
     (GLuint
      -> Ptr GLintptr
      -> Ptr GLsizei
      -> Ptr GLuint
      -> Ptr GLuint
      -> GLuint
      -> IO ()))
-> FunPtr
     (GLuint
      -> Ptr GLintptr
      -> Ptr GLsizei
      -> Ptr GLuint
      -> Ptr GLuint
      -> GLuint
      -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char]
-> IO
     (FunPtr
        (GLuint
         -> Ptr GLintptr
         -> Ptr GLsizei
         -> Ptr GLuint
         -> Ptr GLuint
         -> GLuint
         -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDrawCommandsStatesNV")

{-# NOINLINE glDrawCommandsStatesNVFunPtr #-}

-- | Usage: @'glGetCommandHeaderNV' tokenID size@


glGetCommandHeaderNV :: MonadIO m => GLenum -> GLuint -> m GLuint
glGetCommandHeaderNV :: GLuint -> GLuint -> m GLuint
glGetCommandHeaderNV = FunPtr (GLuint -> GLuint -> IO GLuint)
-> GLuint -> GLuint -> m GLuint
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLuint -> GLuint -> IO GLuint)
-> GLuint -> GLuint -> m GLuint
ffienumuintIOuint FunPtr (GLuint -> GLuint -> IO GLuint)
glGetCommandHeaderNVFunPtr

glGetCommandHeaderNVFunPtr :: FunPtr (GLenum -> GLuint -> IO GLuint)
glGetCommandHeaderNVFunPtr :: FunPtr (GLuint -> GLuint -> IO GLuint)
glGetCommandHeaderNVFunPtr = IO (FunPtr (GLuint -> GLuint -> IO GLuint))
-> FunPtr (GLuint -> GLuint -> IO GLuint)
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLuint -> GLuint -> IO GLuint))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glGetCommandHeaderNV")

{-# NOINLINE glGetCommandHeaderNVFunPtr #-}

-- | Usage: @'glGetStageIndexNV' shadertype@


glGetStageIndexNV :: MonadIO m => GLenum -> m GLushort
glGetStageIndexNV :: GLuint -> m GLushort
glGetStageIndexNV = FunPtr (GLuint -> IO GLushort) -> GLuint -> m GLushort
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLuint -> IO GLushort) -> GLuint -> m GLushort
ffienumIOushort FunPtr (GLuint -> IO GLushort)
glGetStageIndexNVFunPtr

glGetStageIndexNVFunPtr :: FunPtr (GLenum -> IO GLushort)
glGetStageIndexNVFunPtr :: FunPtr (GLuint -> IO GLushort)
glGetStageIndexNVFunPtr = IO (FunPtr (GLuint -> IO GLushort))
-> FunPtr (GLuint -> IO GLushort)
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLuint -> IO GLushort))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glGetStageIndexNV")

{-# NOINLINE glGetStageIndexNVFunPtr #-}

-- | Usage: @'glIsCommandListNV' list@


glIsCommandListNV :: MonadIO m => GLuint -> m GLboolean
glIsCommandListNV :: GLuint -> m GLboolean
glIsCommandListNV = FunPtr (GLuint -> IO GLboolean) -> GLuint -> m GLboolean
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLuint -> IO GLboolean) -> GLuint -> m GLboolean
ffiuintIOboolean FunPtr (GLuint -> IO GLboolean)
glIsCommandListNVFunPtr

glIsCommandListNVFunPtr :: FunPtr (GLuint -> IO GLboolean)
glIsCommandListNVFunPtr :: FunPtr (GLuint -> IO GLboolean)
glIsCommandListNVFunPtr = IO (FunPtr (GLuint -> IO GLboolean))
-> FunPtr (GLuint -> IO GLboolean)
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLuint -> IO GLboolean))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glIsCommandListNV")

{-# NOINLINE glIsCommandListNVFunPtr #-}

-- | Usage: @'glIsStateNV' state@


glIsStateNV :: MonadIO m => GLuint -> m GLboolean
glIsStateNV :: GLuint -> m GLboolean
glIsStateNV = FunPtr (GLuint -> IO GLboolean) -> GLuint -> m GLboolean
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLuint -> IO GLboolean) -> GLuint -> m GLboolean
ffiuintIOboolean FunPtr (GLuint -> IO GLboolean)
glIsStateNVFunPtr

glIsStateNVFunPtr :: FunPtr (GLuint -> IO GLboolean)
glIsStateNVFunPtr :: FunPtr (GLuint -> IO GLboolean)
glIsStateNVFunPtr = IO (FunPtr (GLuint -> IO GLboolean))
-> FunPtr (GLuint -> IO GLboolean)
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLuint -> IO GLboolean))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glIsStateNV")

{-# NOINLINE glIsStateNVFunPtr #-}

-- | Usage: @'glListDrawCommandsStatesClientNV' list segment indirects sizes states fbos count@


glListDrawCommandsStatesClientNV :: MonadIO m => GLuint -> GLuint -> Ptr (Ptr ()) -> Ptr GLsizei -> Ptr GLuint -> Ptr GLuint -> GLuint -> m ()
glListDrawCommandsStatesClientNV :: GLuint
-> GLuint
-> Ptr (Ptr ())
-> Ptr GLsizei
-> Ptr GLuint
-> Ptr GLuint
-> GLuint
-> m ()
glListDrawCommandsStatesClientNV = FunPtr
  (GLuint
   -> GLuint
   -> Ptr (Ptr ())
   -> Ptr GLsizei
   -> Ptr GLuint
   -> Ptr GLuint
   -> GLuint
   -> IO ())
-> GLuint
-> GLuint
-> Ptr (Ptr ())
-> Ptr GLsizei
-> Ptr GLuint
-> Ptr GLuint
-> GLuint
-> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr
  (GLuint
   -> GLuint
   -> Ptr (Ptr ())
   -> Ptr GLsizei
   -> Ptr GLuint
   -> Ptr GLuint
   -> GLuint
   -> IO ())
-> GLuint
-> GLuint
-> Ptr (Ptr ())
-> Ptr GLsizei
-> Ptr GLuint
-> Ptr GLuint
-> GLuint
-> m ()
ffiuintuintPtrPtrVPtrsizeiPtruintPtruintuintIOV FunPtr
  (GLuint
   -> GLuint
   -> Ptr (Ptr ())
   -> Ptr GLsizei
   -> Ptr GLuint
   -> Ptr GLuint
   -> GLuint
   -> IO ())
glListDrawCommandsStatesClientNVFunPtr

glListDrawCommandsStatesClientNVFunPtr :: FunPtr (GLuint -> GLuint -> Ptr (Ptr ()) -> Ptr GLsizei -> Ptr GLuint -> Ptr GLuint -> GLuint -> IO ())
glListDrawCommandsStatesClientNVFunPtr :: FunPtr
  (GLuint
   -> GLuint
   -> Ptr (Ptr ())
   -> Ptr GLsizei
   -> Ptr GLuint
   -> Ptr GLuint
   -> GLuint
   -> IO ())
glListDrawCommandsStatesClientNVFunPtr = IO
  (FunPtr
     (GLuint
      -> GLuint
      -> Ptr (Ptr ())
      -> Ptr GLsizei
      -> Ptr GLuint
      -> Ptr GLuint
      -> GLuint
      -> IO ()))
-> FunPtr
     (GLuint
      -> GLuint
      -> Ptr (Ptr ())
      -> Ptr GLsizei
      -> Ptr GLuint
      -> Ptr GLuint
      -> GLuint
      -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char]
-> IO
     (FunPtr
        (GLuint
         -> GLuint
         -> Ptr (Ptr ())
         -> Ptr GLsizei
         -> Ptr GLuint
         -> Ptr GLuint
         -> GLuint
         -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glListDrawCommandsStatesClientNV")

{-# NOINLINE glListDrawCommandsStatesClientNVFunPtr #-}

-- | Usage: @'glStateCaptureNV' state mode@


glStateCaptureNV :: MonadIO m => GLuint -> GLenum -> m ()
glStateCaptureNV :: GLuint -> GLuint -> m ()
glStateCaptureNV = FunPtr (GLuint -> GLuint -> IO ()) -> GLuint -> GLuint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLuint -> GLuint -> IO ()) -> GLuint -> GLuint -> m ()
ffiuintenumIOV FunPtr (GLuint -> GLuint -> IO ())
glStateCaptureNVFunPtr

glStateCaptureNVFunPtr :: FunPtr (GLuint -> GLenum -> IO ())
glStateCaptureNVFunPtr :: FunPtr (GLuint -> GLuint -> IO ())
glStateCaptureNVFunPtr = IO (FunPtr (GLuint -> GLuint -> IO ()))
-> FunPtr (GLuint -> GLuint -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLuint -> GLuint -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glStateCaptureNV")

{-# NOINLINE glStateCaptureNVFunPtr #-}

pattern $bGL_ALPHA_REF_COMMAND_NV :: a
$mGL_ALPHA_REF_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_ALPHA_REF_COMMAND_NV = 0x000F

pattern $bGL_ATTRIBUTE_ADDRESS_COMMAND_NV :: a
$mGL_ATTRIBUTE_ADDRESS_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_ATTRIBUTE_ADDRESS_COMMAND_NV = 0x0009

pattern $bGL_BLEND_COLOR_COMMAND_NV :: a
$mGL_BLEND_COLOR_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_BLEND_COLOR_COMMAND_NV = 0x000B

pattern $bGL_DRAW_ARRAYS_COMMAND_NV :: a
$mGL_DRAW_ARRAYS_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_DRAW_ARRAYS_COMMAND_NV = 0x0003

pattern $bGL_DRAW_ARRAYS_INSTANCED_COMMAND_NV :: a
$mGL_DRAW_ARRAYS_INSTANCED_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_DRAW_ARRAYS_INSTANCED_COMMAND_NV = 0x0007

pattern $bGL_DRAW_ARRAYS_STRIP_COMMAND_NV :: a
$mGL_DRAW_ARRAYS_STRIP_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_DRAW_ARRAYS_STRIP_COMMAND_NV = 0x0005

pattern $bGL_DRAW_ELEMENTS_COMMAND_NV :: a
$mGL_DRAW_ELEMENTS_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_DRAW_ELEMENTS_COMMAND_NV = 0x0002

pattern $bGL_DRAW_ELEMENTS_INSTANCED_COMMAND_NV :: a
$mGL_DRAW_ELEMENTS_INSTANCED_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_DRAW_ELEMENTS_INSTANCED_COMMAND_NV = 0x0006

pattern $bGL_DRAW_ELEMENTS_STRIP_COMMAND_NV :: a
$mGL_DRAW_ELEMENTS_STRIP_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_DRAW_ELEMENTS_STRIP_COMMAND_NV = 0x0004

pattern $bGL_ELEMENT_ADDRESS_COMMAND_NV :: a
$mGL_ELEMENT_ADDRESS_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_ELEMENT_ADDRESS_COMMAND_NV = 0x0008

pattern $bGL_FRONT_FACE_COMMAND_NV :: a
$mGL_FRONT_FACE_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_FRONT_FACE_COMMAND_NV = 0x0012

pattern $bGL_LINE_WIDTH_COMMAND_NV :: a
$mGL_LINE_WIDTH_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_LINE_WIDTH_COMMAND_NV = 0x000D

pattern $bGL_NOP_COMMAND_NV :: a
$mGL_NOP_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_NOP_COMMAND_NV = 0x0001

pattern $bGL_POLYGON_OFFSET_COMMAND_NV :: a
$mGL_POLYGON_OFFSET_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_POLYGON_OFFSET_COMMAND_NV = 0x000E

pattern $bGL_SCISSOR_COMMAND_NV :: a
$mGL_SCISSOR_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_SCISSOR_COMMAND_NV = 0x0011

pattern $bGL_STENCIL_REF_COMMAND_NV :: a
$mGL_STENCIL_REF_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_STENCIL_REF_COMMAND_NV = 0x000C

pattern $bGL_TERMINATE_SEQUENCE_COMMAND_NV :: a
$mGL_TERMINATE_SEQUENCE_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_TERMINATE_SEQUENCE_COMMAND_NV = 0x0000

pattern $bGL_UNIFORM_ADDRESS_COMMAND_NV :: a
$mGL_UNIFORM_ADDRESS_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_UNIFORM_ADDRESS_COMMAND_NV = 0x000A

pattern $bGL_VIEWPORT_COMMAND_NV :: a
$mGL_VIEWPORT_COMMAND_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_VIEWPORT_COMMAND_NV = 0x0010