-- This file was automatically generated.
{-# LANGUAGE ScopedTypeVariables, PatternSynonyms #-}
module Graphics.GL.Raw.Extension.NV.SampleLocations (
  -- * Extension Support
    gl_NV_sample_locations

  -- * GL_NV_sample_locations
  , glFramebufferSampleLocationsfvNV
  , glNamedFramebufferSampleLocationsfvNV
  , glResolveDepthValuesNV
  , pattern GL_FRAMEBUFFER_PROGRAMMABLE_SAMPLE_LOCATIONS_NV
  , pattern GL_FRAMEBUFFER_SAMPLE_LOCATION_PIXEL_GRID_NV
  , pattern GL_PROGRAMMABLE_SAMPLE_LOCATION_NV
  , pattern GL_PROGRAMMABLE_SAMPLE_LOCATION_TABLE_SIZE_NV
  , pattern GL_SAMPLE_LOCATION_NV
  , pattern GL_SAMPLE_LOCATION_PIXEL_GRID_HEIGHT_NV
  , pattern GL_SAMPLE_LOCATION_PIXEL_GRID_WIDTH_NV
  , pattern GL_SAMPLE_LOCATION_SUBPIXEL_BITS_NV
) 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

gl_NV_sample_locations :: Bool
gl_NV_sample_locations = member "GL_NV_sample_locations" extensions

glFramebufferSampleLocationsfvNV :: MonadIO m => GLenum -> GLuint -> GLsizei -> Ptr GLfloat -> m ()
glFramebufferSampleLocationsfvNV = ffienumuintsizeiPtrfloatIOV glFramebufferSampleLocationsfvNVFunPtr

glFramebufferSampleLocationsfvNVFunPtr :: FunPtr (GLenum -> GLuint -> GLsizei -> Ptr GLfloat -> IO ())
glFramebufferSampleLocationsfvNVFunPtr = unsafePerformIO (getProcAddress "glFramebufferSampleLocationsfvNV")

{-# NOINLINE glFramebufferSampleLocationsfvNVFunPtr #-}

glNamedFramebufferSampleLocationsfvNV :: MonadIO m => GLuint -> GLuint -> GLsizei -> Ptr GLfloat -> m ()
glNamedFramebufferSampleLocationsfvNV = ffiuintuintsizeiPtrfloatIOV glNamedFramebufferSampleLocationsfvNVFunPtr

glNamedFramebufferSampleLocationsfvNVFunPtr :: FunPtr (GLuint -> GLuint -> GLsizei -> Ptr GLfloat -> IO ())
glNamedFramebufferSampleLocationsfvNVFunPtr = unsafePerformIO (getProcAddress "glNamedFramebufferSampleLocationsfvNV")

{-# NOINLINE glNamedFramebufferSampleLocationsfvNVFunPtr #-}

glResolveDepthValuesNV :: MonadIO m => m ()
glResolveDepthValuesNV = ffiIOV glResolveDepthValuesNVFunPtr

glResolveDepthValuesNVFunPtr :: FunPtr (IO ())
glResolveDepthValuesNVFunPtr = unsafePerformIO (getProcAddress "glResolveDepthValuesNV")

{-# NOINLINE glResolveDepthValuesNVFunPtr #-}

pattern GL_FRAMEBUFFER_PROGRAMMABLE_SAMPLE_LOCATIONS_NV = 0x9342 :: GLenum

pattern GL_FRAMEBUFFER_SAMPLE_LOCATION_PIXEL_GRID_NV = 0x9343 :: GLenum

pattern GL_PROGRAMMABLE_SAMPLE_LOCATION_NV = 0x9341 :: GLenum

pattern GL_PROGRAMMABLE_SAMPLE_LOCATION_TABLE_SIZE_NV = 0x9340 :: GLenum

pattern GL_SAMPLE_LOCATION_NV = 0x8E50 :: GLenum

pattern GL_SAMPLE_LOCATION_PIXEL_GRID_HEIGHT_NV = 0x933F :: GLenum

pattern GL_SAMPLE_LOCATION_PIXEL_GRID_WIDTH_NV = 0x933E :: GLenum

pattern GL_SAMPLE_LOCATION_SUBPIXEL_BITS_NV = 0x933D :: GLenum