{-# LANGUAGE CPP, ScopedTypeVariables, PatternSynonyms #-}
module Graphics.GL.Ext.ARB.SampleLocations (
gl_ARB_sample_locations
, glEvaluateDepthValuesARB
, glFramebufferSampleLocationsfvARB
, glNamedFramebufferSampleLocationsfvARB
, pattern GL_FRAMEBUFFER_PROGRAMMABLE_SAMPLE_LOCATIONS_ARB
, pattern GL_FRAMEBUFFER_SAMPLE_LOCATION_PIXEL_GRID_ARB
, pattern GL_PROGRAMMABLE_SAMPLE_LOCATION_ARB
, pattern GL_PROGRAMMABLE_SAMPLE_LOCATION_TABLE_SIZE_ARB
, pattern GL_SAMPLE_LOCATION_ARB
, pattern GL_SAMPLE_LOCATION_PIXEL_GRID_HEIGHT_ARB
, pattern GL_SAMPLE_LOCATION_PIXEL_GRID_WIDTH_ARB
, pattern GL_SAMPLE_LOCATION_SUBPIXEL_BITS_ARB
) 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
gl_ARB_sample_locations :: Bool
gl_ARB_sample_locations :: Bool
gl_ARB_sample_locations = [Char] -> Set [Char] -> Bool
forall a. Ord a => a -> Set a -> Bool
member "GL_ARB_sample_locations" Set [Char]
extensions
{-# NOINLINE gl_ARB_sample_locations #-}
glEvaluateDepthValuesARB :: MonadIO m => m ()
glEvaluateDepthValuesARB :: m ()
glEvaluateDepthValuesARB = FunPtr (IO ()) -> m ()
forall (m :: * -> *). MonadIO m => FunPtr (IO ()) -> m ()
ffiIOV FunPtr (IO ())
glEvaluateDepthValuesARBFunPtr
glEvaluateDepthValuesARBFunPtr :: FunPtr (IO ())
glEvaluateDepthValuesARBFunPtr :: FunPtr (IO ())
glEvaluateDepthValuesARBFunPtr = IO (FunPtr (IO ())) -> FunPtr (IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glEvaluateDepthValuesARB")
{-# NOINLINE glEvaluateDepthValuesARBFunPtr #-}
glFramebufferSampleLocationsfvARB :: MonadIO m => GLenum -> GLuint -> GLsizei -> Ptr GLfloat -> m ()
glFramebufferSampleLocationsfvARB :: GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> m ()
glFramebufferSampleLocationsfvARB = FunPtr (GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> IO ())
-> GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> IO ())
-> GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> m ()
ffienumuintsizeiPtrfloatIOV FunPtr (GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> IO ())
glFramebufferSampleLocationsfvARBFunPtr
glFramebufferSampleLocationsfvARBFunPtr :: FunPtr (GLenum -> GLuint -> GLsizei -> Ptr GLfloat -> IO ())
glFramebufferSampleLocationsfvARBFunPtr :: FunPtr (GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> IO ())
glFramebufferSampleLocationsfvARBFunPtr = IO (FunPtr (GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> IO ()))
-> FunPtr (GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char]
-> IO
(FunPtr (GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glFramebufferSampleLocationsfvARB")
{-# NOINLINE glFramebufferSampleLocationsfvARBFunPtr #-}
glNamedFramebufferSampleLocationsfvARB :: MonadIO m => GLuint -> GLuint -> GLsizei -> Ptr GLfloat -> m ()
glNamedFramebufferSampleLocationsfvARB :: GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> m ()
glNamedFramebufferSampleLocationsfvARB = FunPtr (GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> IO ())
-> GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> IO ())
-> GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> m ()
ffiuintuintsizeiPtrfloatIOV FunPtr (GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> IO ())
glNamedFramebufferSampleLocationsfvARBFunPtr
glNamedFramebufferSampleLocationsfvARBFunPtr :: FunPtr (GLuint -> GLuint -> GLsizei -> Ptr GLfloat -> IO ())
glNamedFramebufferSampleLocationsfvARBFunPtr :: FunPtr (GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> IO ())
glNamedFramebufferSampleLocationsfvARBFunPtr = IO (FunPtr (GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> IO ()))
-> FunPtr (GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char]
-> IO
(FunPtr (GLenum -> GLenum -> GLsizei -> Ptr GLfloat -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glNamedFramebufferSampleLocationsfvARB")
{-# NOINLINE glNamedFramebufferSampleLocationsfvARBFunPtr #-}
pattern $bGL_FRAMEBUFFER_PROGRAMMABLE_SAMPLE_LOCATIONS_ARB :: a
$mGL_FRAMEBUFFER_PROGRAMMABLE_SAMPLE_LOCATIONS_ARB :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_FRAMEBUFFER_PROGRAMMABLE_SAMPLE_LOCATIONS_ARB = 0x9342
pattern $bGL_FRAMEBUFFER_SAMPLE_LOCATION_PIXEL_GRID_ARB :: a
$mGL_FRAMEBUFFER_SAMPLE_LOCATION_PIXEL_GRID_ARB :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_FRAMEBUFFER_SAMPLE_LOCATION_PIXEL_GRID_ARB = 0x9343
pattern $bGL_PROGRAMMABLE_SAMPLE_LOCATION_ARB :: a
$mGL_PROGRAMMABLE_SAMPLE_LOCATION_ARB :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_PROGRAMMABLE_SAMPLE_LOCATION_ARB = 0x9341
pattern $bGL_PROGRAMMABLE_SAMPLE_LOCATION_TABLE_SIZE_ARB :: a
$mGL_PROGRAMMABLE_SAMPLE_LOCATION_TABLE_SIZE_ARB :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_PROGRAMMABLE_SAMPLE_LOCATION_TABLE_SIZE_ARB = 0x9340
pattern $bGL_SAMPLE_LOCATION_ARB :: a
$mGL_SAMPLE_LOCATION_ARB :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_SAMPLE_LOCATION_ARB = 0x8E50
pattern $bGL_SAMPLE_LOCATION_PIXEL_GRID_HEIGHT_ARB :: a
$mGL_SAMPLE_LOCATION_PIXEL_GRID_HEIGHT_ARB :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_SAMPLE_LOCATION_PIXEL_GRID_HEIGHT_ARB = 0x933F
pattern $bGL_SAMPLE_LOCATION_PIXEL_GRID_WIDTH_ARB :: a
$mGL_SAMPLE_LOCATION_PIXEL_GRID_WIDTH_ARB :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_SAMPLE_LOCATION_PIXEL_GRID_WIDTH_ARB = 0x933E
pattern $bGL_SAMPLE_LOCATION_SUBPIXEL_BITS_ARB :: a
$mGL_SAMPLE_LOCATION_SUBPIXEL_BITS_ARB :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_SAMPLE_LOCATION_SUBPIXEL_BITS_ARB = 0x933D