-- This file was automatically generated.
{-# LANGUAGE ScopedTypeVariables, PatternSynonyms #-}
module Graphics.GL.Raw.Extension.EXT.Texture3D (
  -- * Extension Support
    gl_EXT_texture3D

  -- * GL_EXT_texture3D
  , glTexImage3DEXT
  , glTexSubImage3DEXT
  , pattern GL_MAX_3D_TEXTURE_SIZE_EXT
  , pattern GL_PACK_IMAGE_HEIGHT_EXT
  , pattern GL_PACK_SKIP_IMAGES_EXT
  , pattern GL_PROXY_TEXTURE_3D_EXT
  , pattern GL_TEXTURE_3D_EXT
  , pattern GL_TEXTURE_DEPTH_EXT
  , pattern GL_TEXTURE_WRAP_R_EXT
  , pattern GL_UNPACK_IMAGE_HEIGHT_EXT
  , pattern GL_UNPACK_SKIP_IMAGES_EXT
) where

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

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

gl_EXT_texture3D :: Bool
gl_EXT_texture3D = member "GL_EXT_texture3D" extensions
{-# NOINLINE gl_EXT_texture3D #-}

-- | Usage: @'glTexImage3DEXT' target level internalformat width height depth border format type pixels@
--
-- The parameter @target@ is a @TextureTarget@, one of: 'Graphics.GL.Raw.Extension.SGIS.DetailTexture.GL_DETAIL_TEXTURE_2D_SGIS', 'Graphics.GL.Raw.Internal.Shared.GL_PROXY_TEXTURE_1D', 'Graphics.GL.Raw.Extension.EXT.Texture.GL_PROXY_TEXTURE_1D_EXT', 'Graphics.GL.Raw.Internal.Shared.GL_PROXY_TEXTURE_2D', 'Graphics.GL.Raw.Extension.EXT.Texture.GL_PROXY_TEXTURE_2D_EXT', 'Graphics.GL.Raw.Internal.Shared.GL_PROXY_TEXTURE_3D', 'Graphics.GL.Raw.Extension.EXT.Texture3D.GL_PROXY_TEXTURE_3D_EXT', 'Graphics.GL.Raw.Extension.SGIS.Texture4D.GL_PROXY_TEXTURE_4D_SGIS', 'Graphics.GL.Raw.Internal.Shared.GL_TEXTURE_1D', 'Graphics.GL.Raw.Internal.Shared.GL_TEXTURE_2D', 'Graphics.GL.Raw.Internal.Shared.GL_TEXTURE_3D', 'Graphics.GL.Raw.Extension.EXT.Texture3D.GL_TEXTURE_3D_EXT', 'Graphics.GL.Raw.Extension.OES.Texture3D.GL_TEXTURE_3D_OES', 'Graphics.GL.Raw.Extension.SGIS.Texture4D.GL_TEXTURE_4D_SGIS', 'Graphics.GL.Raw.Internal.Shared.GL_TEXTURE_BASE_LEVEL', 'Graphics.GL.Raw.Extension.SGIS.TextureLod.GL_TEXTURE_BASE_LEVEL_SGIS', 'Graphics.GL.Raw.Internal.Shared.GL_TEXTURE_MAX_LEVEL', 'Graphics.GL.Raw.Extension.SGIS.TextureLod.GL_TEXTURE_MAX_LEVEL_SGIS', 'Graphics.GL.Raw.Internal.Shared.GL_TEXTURE_MAX_LOD', 'Graphics.GL.Raw.Extension.SGIS.TextureLod.GL_TEXTURE_MAX_LOD_SGIS', 'Graphics.GL.Raw.Internal.Shared.GL_TEXTURE_MIN_LOD', 'Graphics.GL.Raw.Extension.SGIS.TextureLod.GL_TEXTURE_MIN_LOD_SGIS'.
--
-- The parameter @level@ is a @CheckedInt32@.
--
-- The parameter @internalformat@ is a @PixelInternalFormat@.
--
-- The parameter @border@ is a @CheckedInt32@.
--
-- The parameter @format@ is a @PixelFormat@, one of: 'Graphics.GL.Raw.Extension.EXT.Abgr.GL_ABGR_EXT', 'Graphics.GL.Raw.Internal.Shared.GL_ALPHA', 'Graphics.GL.Raw.Internal.Shared.GL_BLUE', 'Graphics.GL.Raw.Extension.EXT.Cmyka.GL_CMYKA_EXT', 'Graphics.GL.Raw.Extension.EXT.Cmyka.GL_CMYK_EXT', 'Graphics.GL.Raw.Internal.Shared.GL_COLOR_INDEX', 'Graphics.GL.Raw.Internal.Shared.GL_DEPTH_COMPONENT', 'Graphics.GL.Raw.Internal.Shared.GL_GREEN', 'Graphics.GL.Raw.Internal.Shared.GL_LUMINANCE', 'Graphics.GL.Raw.Internal.Shared.GL_LUMINANCE_ALPHA', 'Graphics.GL.Raw.Internal.Shared.GL_RED', 'Graphics.GL.Raw.Extension.EXT.TextureRg.GL_RED_EXT', 'Graphics.GL.Raw.Internal.Shared.GL_RGB', 'Graphics.GL.Raw.Internal.Shared.GL_RGBA', 'Graphics.GL.Raw.Internal.Shared.GL_STENCIL_INDEX', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_INT', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_SHORT', 'Graphics.GL.Raw.Extension.SGIX.Ycrcb.GL_YCRCB_422_SGIX', 'Graphics.GL.Raw.Extension.SGIX.Ycrcb.GL_YCRCB_444_SGIX'.
--
-- The parameter @type@ is a @PixelType@, one of: 'Graphics.GL.Raw.Internal.Shared.GL_BITMAP', 'Graphics.GL.Raw.Internal.Shared.GL_BYTE', 'Graphics.GL.Raw.Internal.Shared.GL_FLOAT', 'Graphics.GL.Raw.Internal.Shared.GL_INT', 'Graphics.GL.Raw.Internal.Shared.GL_SHORT', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_BYTE', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_BYTE_3_3_2', 'Graphics.GL.Raw.Extension.EXT.PackedPixels.GL_UNSIGNED_BYTE_3_3_2_EXT', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_INT', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_INT_10_10_10_2', 'Graphics.GL.Raw.Extension.EXT.PackedPixels.GL_UNSIGNED_INT_10_10_10_2_EXT', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_INT_8_8_8_8', 'Graphics.GL.Raw.Extension.EXT.PackedPixels.GL_UNSIGNED_INT_8_8_8_8_EXT', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_SHORT', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_SHORT_4_4_4_4', 'Graphics.GL.Raw.Extension.EXT.PackedPixels.GL_UNSIGNED_SHORT_4_4_4_4_EXT', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_SHORT_5_5_5_1', 'Graphics.GL.Raw.Extension.EXT.PackedPixels.GL_UNSIGNED_SHORT_5_5_5_1_EXT'.
--
-- The length of @pixels@ should be @COMPSIZE(format,type,width,height,depth)@.
--
-- This command is an alias for 'Graphics.GL.Raw.Internal.Shared.glTexImage3D'.


glTexImage3DEXT :: MonadIO m => GLenum -> GLint -> GLenum -> GLsizei -> GLsizei -> GLsizei -> GLint -> GLenum -> GLenum -> Ptr () -> m ()
glTexImage3DEXT = ffienumintenumsizeisizeisizeiintenumenumPtrVIOV glTexImage3DEXTFunPtr

glTexImage3DEXTFunPtr :: FunPtr (GLenum -> GLint -> GLenum -> GLsizei -> GLsizei -> GLsizei -> GLint -> GLenum -> GLenum -> Ptr () -> IO ())
glTexImage3DEXTFunPtr = unsafePerformIO (getProcAddress "glTexImage3DEXT")

{-# NOINLINE glTexImage3DEXTFunPtr #-}

-- | Usage: @'glTexSubImage3DEXT' target level xoffset yoffset zoffset width height depth format type pixels@
--
-- The parameter @target@ is a @TextureTarget@, one of: 'Graphics.GL.Raw.Extension.SGIS.DetailTexture.GL_DETAIL_TEXTURE_2D_SGIS', 'Graphics.GL.Raw.Internal.Shared.GL_PROXY_TEXTURE_1D', 'Graphics.GL.Raw.Extension.EXT.Texture.GL_PROXY_TEXTURE_1D_EXT', 'Graphics.GL.Raw.Internal.Shared.GL_PROXY_TEXTURE_2D', 'Graphics.GL.Raw.Extension.EXT.Texture.GL_PROXY_TEXTURE_2D_EXT', 'Graphics.GL.Raw.Internal.Shared.GL_PROXY_TEXTURE_3D', 'Graphics.GL.Raw.Extension.EXT.Texture3D.GL_PROXY_TEXTURE_3D_EXT', 'Graphics.GL.Raw.Extension.SGIS.Texture4D.GL_PROXY_TEXTURE_4D_SGIS', 'Graphics.GL.Raw.Internal.Shared.GL_TEXTURE_1D', 'Graphics.GL.Raw.Internal.Shared.GL_TEXTURE_2D', 'Graphics.GL.Raw.Internal.Shared.GL_TEXTURE_3D', 'Graphics.GL.Raw.Extension.EXT.Texture3D.GL_TEXTURE_3D_EXT', 'Graphics.GL.Raw.Extension.OES.Texture3D.GL_TEXTURE_3D_OES', 'Graphics.GL.Raw.Extension.SGIS.Texture4D.GL_TEXTURE_4D_SGIS', 'Graphics.GL.Raw.Internal.Shared.GL_TEXTURE_BASE_LEVEL', 'Graphics.GL.Raw.Extension.SGIS.TextureLod.GL_TEXTURE_BASE_LEVEL_SGIS', 'Graphics.GL.Raw.Internal.Shared.GL_TEXTURE_MAX_LEVEL', 'Graphics.GL.Raw.Extension.SGIS.TextureLod.GL_TEXTURE_MAX_LEVEL_SGIS', 'Graphics.GL.Raw.Internal.Shared.GL_TEXTURE_MAX_LOD', 'Graphics.GL.Raw.Extension.SGIS.TextureLod.GL_TEXTURE_MAX_LOD_SGIS', 'Graphics.GL.Raw.Internal.Shared.GL_TEXTURE_MIN_LOD', 'Graphics.GL.Raw.Extension.SGIS.TextureLod.GL_TEXTURE_MIN_LOD_SGIS'.
--
-- The parameter @level@ is a @CheckedInt32@.
--
-- The parameter @xoffset@ is a @CheckedInt32@.
--
-- The parameter @yoffset@ is a @CheckedInt32@.
--
-- The parameter @zoffset@ is a @CheckedInt32@.
--
-- The parameter @format@ is a @PixelFormat@, one of: 'Graphics.GL.Raw.Extension.EXT.Abgr.GL_ABGR_EXT', 'Graphics.GL.Raw.Internal.Shared.GL_ALPHA', 'Graphics.GL.Raw.Internal.Shared.GL_BLUE', 'Graphics.GL.Raw.Extension.EXT.Cmyka.GL_CMYKA_EXT', 'Graphics.GL.Raw.Extension.EXT.Cmyka.GL_CMYK_EXT', 'Graphics.GL.Raw.Internal.Shared.GL_COLOR_INDEX', 'Graphics.GL.Raw.Internal.Shared.GL_DEPTH_COMPONENT', 'Graphics.GL.Raw.Internal.Shared.GL_GREEN', 'Graphics.GL.Raw.Internal.Shared.GL_LUMINANCE', 'Graphics.GL.Raw.Internal.Shared.GL_LUMINANCE_ALPHA', 'Graphics.GL.Raw.Internal.Shared.GL_RED', 'Graphics.GL.Raw.Extension.EXT.TextureRg.GL_RED_EXT', 'Graphics.GL.Raw.Internal.Shared.GL_RGB', 'Graphics.GL.Raw.Internal.Shared.GL_RGBA', 'Graphics.GL.Raw.Internal.Shared.GL_STENCIL_INDEX', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_INT', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_SHORT', 'Graphics.GL.Raw.Extension.SGIX.Ycrcb.GL_YCRCB_422_SGIX', 'Graphics.GL.Raw.Extension.SGIX.Ycrcb.GL_YCRCB_444_SGIX'.
--
-- The parameter @type@ is a @PixelType@, one of: 'Graphics.GL.Raw.Internal.Shared.GL_BITMAP', 'Graphics.GL.Raw.Internal.Shared.GL_BYTE', 'Graphics.GL.Raw.Internal.Shared.GL_FLOAT', 'Graphics.GL.Raw.Internal.Shared.GL_INT', 'Graphics.GL.Raw.Internal.Shared.GL_SHORT', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_BYTE', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_BYTE_3_3_2', 'Graphics.GL.Raw.Extension.EXT.PackedPixels.GL_UNSIGNED_BYTE_3_3_2_EXT', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_INT', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_INT_10_10_10_2', 'Graphics.GL.Raw.Extension.EXT.PackedPixels.GL_UNSIGNED_INT_10_10_10_2_EXT', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_INT_8_8_8_8', 'Graphics.GL.Raw.Extension.EXT.PackedPixels.GL_UNSIGNED_INT_8_8_8_8_EXT', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_SHORT', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_SHORT_4_4_4_4', 'Graphics.GL.Raw.Extension.EXT.PackedPixels.GL_UNSIGNED_SHORT_4_4_4_4_EXT', 'Graphics.GL.Raw.Internal.Shared.GL_UNSIGNED_SHORT_5_5_5_1', 'Graphics.GL.Raw.Extension.EXT.PackedPixels.GL_UNSIGNED_SHORT_5_5_5_1_EXT'.
--
-- The length of @pixels@ should be @COMPSIZE(format,type,width,height,depth)@.
--
-- This command is an alias for 'Graphics.GL.Raw.Internal.Shared.glTexSubImage3D'.


glTexSubImage3DEXT :: MonadIO m => GLenum -> GLint -> GLint -> GLint -> GLint -> GLsizei -> GLsizei -> GLsizei -> GLenum -> GLenum -> Ptr () -> m ()
glTexSubImage3DEXT = ffienumintintintintsizeisizeisizeienumenumPtrVIOV glTexSubImage3DEXTFunPtr

glTexSubImage3DEXTFunPtr :: FunPtr (GLenum -> GLint -> GLint -> GLint -> GLint -> GLsizei -> GLsizei -> GLsizei -> GLenum -> GLenum -> Ptr () -> IO ())
glTexSubImage3DEXTFunPtr = unsafePerformIO (getProcAddress "glTexSubImage3DEXT")

{-# NOINLINE glTexSubImage3DEXTFunPtr #-}

pattern GL_MAX_3D_TEXTURE_SIZE_EXT = 0x8073

pattern GL_PACK_IMAGE_HEIGHT_EXT = 0x806C

pattern GL_PACK_SKIP_IMAGES_EXT = 0x806B

pattern GL_PROXY_TEXTURE_3D_EXT = 0x8070

pattern GL_TEXTURE_3D_EXT = 0x806F

pattern GL_TEXTURE_DEPTH_EXT = 0x8071

pattern GL_TEXTURE_WRAP_R_EXT = 0x8072

pattern GL_UNPACK_IMAGE_HEIGHT_EXT = 0x806E

pattern GL_UNPACK_SKIP_IMAGES_EXT = 0x806D