-- This file was automatically generated.
{-# LANGUAGE ScopedTypeVariables, PatternSynonyms #-}
module Graphics.GL.Raw.Extension.ARB.TextureCompression (
  -- * Extension Support
    gl_ARB_texture_compression

  -- * GL_ARB_texture_compression
  , glCompressedTexImage1DARB
  , glCompressedTexImage2DARB
  , glCompressedTexImage3DARB
  , glCompressedTexSubImage1DARB
  , glCompressedTexSubImage2DARB
  , glCompressedTexSubImage3DARB
  , glGetCompressedTexImageARB
  , pattern GL_COMPRESSED_ALPHA_ARB
  , pattern GL_COMPRESSED_INTENSITY_ARB
  , pattern GL_COMPRESSED_LUMINANCE_ALPHA_ARB
  , pattern GL_COMPRESSED_LUMINANCE_ARB
  , pattern GL_COMPRESSED_RGBA_ARB
  , pattern GL_COMPRESSED_RGB_ARB
  , pattern GL_COMPRESSED_TEXTURE_FORMATS_ARB
  , pattern GL_NUM_COMPRESSED_TEXTURE_FORMATS_ARB
  , pattern GL_TEXTURE_COMPRESSED_ARB
  , pattern GL_TEXTURE_COMPRESSED_IMAGE_SIZE_ARB
  , pattern GL_TEXTURE_COMPRESSION_HINT_ARB
) 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/ARB/texture_compression.txt GL_ARB_texture_compression> extension is available.

gl_ARB_texture_compression :: Bool
gl_ARB_texture_compression = member "GL_ARB_texture_compression" extensions
{-# NOINLINE gl_ARB_texture_compression #-}

-- | Usage: @'glCompressedTexImage1DARB' target level internalformat width border imageSize data@
--
-- 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 @data@ is a @CompressedTextureARB@.
--
-- The length of @data@ should be @imageSize@.
--
-- This command is an alias for 'Graphics.GL.Raw.Internal.Shared.glCompressedTexImage1D'.


glCompressedTexImage1DARB :: MonadIO m => GLenum -> GLint -> GLenum -> GLsizei -> GLint -> GLsizei -> Ptr () -> m ()
glCompressedTexImage1DARB = ffienumintenumsizeiintsizeiPtrVIOV glCompressedTexImage1DARBFunPtr

glCompressedTexImage1DARBFunPtr :: FunPtr (GLenum -> GLint -> GLenum -> GLsizei -> GLint -> GLsizei -> Ptr () -> IO ())
glCompressedTexImage1DARBFunPtr = unsafePerformIO (getProcAddress "glCompressedTexImage1DARB")

{-# NOINLINE glCompressedTexImage1DARBFunPtr #-}

-- | Usage: @'glCompressedTexImage2DARB' target level internalformat width height border imageSize data@
--
-- 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 @data@ is a @CompressedTextureARB@.
--
-- The length of @data@ should be @imageSize@.
--
-- This command is an alias for 'Graphics.GL.Raw.Internal.Shared.glCompressedTexImage2D'.


glCompressedTexImage2DARB :: MonadIO m => GLenum -> GLint -> GLenum -> GLsizei -> GLsizei -> GLint -> GLsizei -> Ptr () -> m ()
glCompressedTexImage2DARB = ffienumintenumsizeisizeiintsizeiPtrVIOV glCompressedTexImage2DARBFunPtr

glCompressedTexImage2DARBFunPtr :: FunPtr (GLenum -> GLint -> GLenum -> GLsizei -> GLsizei -> GLint -> GLsizei -> Ptr () -> IO ())
glCompressedTexImage2DARBFunPtr = unsafePerformIO (getProcAddress "glCompressedTexImage2DARB")

{-# NOINLINE glCompressedTexImage2DARBFunPtr #-}

-- | Usage: @'glCompressedTexImage3DARB' target level internalformat width height depth border imageSize data@
--
-- 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 @data@ is a @CompressedTextureARB@.
--
-- The length of @data@ should be @imageSize@.
--
-- This command is an alias for 'Graphics.GL.Raw.Internal.Shared.glCompressedTexImage3D'.


glCompressedTexImage3DARB :: MonadIO m => GLenum -> GLint -> GLenum -> GLsizei -> GLsizei -> GLsizei -> GLint -> GLsizei -> Ptr () -> m ()
glCompressedTexImage3DARB = ffienumintenumsizeisizeisizeiintsizeiPtrVIOV glCompressedTexImage3DARBFunPtr

glCompressedTexImage3DARBFunPtr :: FunPtr (GLenum -> GLint -> GLenum -> GLsizei -> GLsizei -> GLsizei -> GLint -> GLsizei -> Ptr () -> IO ())
glCompressedTexImage3DARBFunPtr = unsafePerformIO (getProcAddress "glCompressedTexImage3DARB")

{-# NOINLINE glCompressedTexImage3DARBFunPtr #-}

-- | Usage: @'glCompressedTexSubImage1DARB' target level xoffset width format imageSize data@
--
-- 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 @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 @data@ is a @CompressedTextureARB@.
--
-- The length of @data@ should be @imageSize@.
--
-- This command is an alias for 'Graphics.GL.Raw.Internal.Shared.glCompressedTexSubImage1D'.


glCompressedTexSubImage1DARB :: MonadIO m => GLenum -> GLint -> GLint -> GLsizei -> GLenum -> GLsizei -> Ptr () -> m ()
glCompressedTexSubImage1DARB = ffienumintintsizeienumsizeiPtrVIOV glCompressedTexSubImage1DARBFunPtr

glCompressedTexSubImage1DARBFunPtr :: FunPtr (GLenum -> GLint -> GLint -> GLsizei -> GLenum -> GLsizei -> Ptr () -> IO ())
glCompressedTexSubImage1DARBFunPtr = unsafePerformIO (getProcAddress "glCompressedTexSubImage1DARB")

{-# NOINLINE glCompressedTexSubImage1DARBFunPtr #-}

-- | Usage: @'glCompressedTexSubImage2DARB' target level xoffset yoffset width height format imageSize data@
--
-- 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 @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 @data@ is a @CompressedTextureARB@.
--
-- The length of @data@ should be @imageSize@.
--
-- This command is an alias for 'Graphics.GL.Raw.Internal.Shared.glCompressedTexSubImage2D'.


glCompressedTexSubImage2DARB :: MonadIO m => GLenum -> GLint -> GLint -> GLint -> GLsizei -> GLsizei -> GLenum -> GLsizei -> Ptr () -> m ()
glCompressedTexSubImage2DARB = ffienumintintintsizeisizeienumsizeiPtrVIOV glCompressedTexSubImage2DARBFunPtr

glCompressedTexSubImage2DARBFunPtr :: FunPtr (GLenum -> GLint -> GLint -> GLint -> GLsizei -> GLsizei -> GLenum -> GLsizei -> Ptr () -> IO ())
glCompressedTexSubImage2DARBFunPtr = unsafePerformIO (getProcAddress "glCompressedTexSubImage2DARB")

{-# NOINLINE glCompressedTexSubImage2DARBFunPtr #-}

-- | Usage: @'glCompressedTexSubImage3DARB' target level xoffset yoffset zoffset width height depth format imageSize data@
--
-- 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 @data@ is a @CompressedTextureARB@.
--
-- The length of @data@ should be @imageSize@.
--
-- This command is an alias for 'Graphics.GL.Raw.Internal.Shared.glCompressedTexSubImage3D'.


glCompressedTexSubImage3DARB :: MonadIO m => GLenum -> GLint -> GLint -> GLint -> GLint -> GLsizei -> GLsizei -> GLsizei -> GLenum -> GLsizei -> Ptr () -> m ()
glCompressedTexSubImage3DARB = ffienumintintintintsizeisizeisizeienumsizeiPtrVIOV glCompressedTexSubImage3DARBFunPtr

glCompressedTexSubImage3DARBFunPtr :: FunPtr (GLenum -> GLint -> GLint -> GLint -> GLint -> GLsizei -> GLsizei -> GLsizei -> GLenum -> GLsizei -> Ptr () -> IO ())
glCompressedTexSubImage3DARBFunPtr = unsafePerformIO (getProcAddress "glCompressedTexSubImage3DARB")

{-# NOINLINE glCompressedTexSubImage3DARBFunPtr #-}

-- | Usage: @'glGetCompressedTexImageARB' target level img@
--
-- 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 @img@ is a @CompressedTextureARB@.
--
-- The length of @img@ should be @COMPSIZE(target,level)@.
--
-- This command is an alias for 'Graphics.GL.Raw.Internal.Shared.glGetCompressedTexImage'.


glGetCompressedTexImageARB :: MonadIO m => GLenum -> GLint -> Ptr () -> m ()
glGetCompressedTexImageARB = ffienumintPtrVIOV glGetCompressedTexImageARBFunPtr

glGetCompressedTexImageARBFunPtr :: FunPtr (GLenum -> GLint -> Ptr () -> IO ())
glGetCompressedTexImageARBFunPtr = unsafePerformIO (getProcAddress "glGetCompressedTexImageARB")

{-# NOINLINE glGetCompressedTexImageARBFunPtr #-}

pattern GL_COMPRESSED_ALPHA_ARB = 0x84E9

pattern GL_COMPRESSED_INTENSITY_ARB = 0x84EC

pattern GL_COMPRESSED_LUMINANCE_ALPHA_ARB = 0x84EB

pattern GL_COMPRESSED_LUMINANCE_ARB = 0x84EA

pattern GL_COMPRESSED_RGBA_ARB = 0x84EE

pattern GL_COMPRESSED_RGB_ARB = 0x84ED

pattern GL_COMPRESSED_TEXTURE_FORMATS_ARB = 0x86A3

pattern GL_NUM_COMPRESSED_TEXTURE_FORMATS_ARB = 0x86A2

pattern GL_TEXTURE_COMPRESSED_ARB = 0x86A1

pattern GL_TEXTURE_COMPRESSED_IMAGE_SIZE_ARB = 0x86A0

pattern GL_TEXTURE_COMPRESSION_HINT_ARB = 0x84EF