{-# LANGUAGE CPP, ScopedTypeVariables, PatternSynonyms #-}
module Graphics.GL.Ext.NV.DepthBufferFloat (
gl_NV_depth_buffer_float
, glClearDepthdNV
, glDepthBoundsdNV
, glDepthRangedNV
, pattern GL_DEPTH32F_STENCIL8_NV
, pattern GL_DEPTH_BUFFER_FLOAT_MODE_NV
, pattern GL_DEPTH_COMPONENT32F_NV
, pattern GL_FLOAT_32_UNSIGNED_INT_24_8_REV_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
gl_NV_depth_buffer_float :: Bool
gl_NV_depth_buffer_float :: Bool
gl_NV_depth_buffer_float = [Char] -> Set [Char] -> Bool
forall a. Ord a => a -> Set a -> Bool
member "GL_NV_depth_buffer_float" Set [Char]
extensions
{-# NOINLINE gl_NV_depth_buffer_float #-}
glClearDepthdNV :: MonadIO m => GLdouble -> m ()
glClearDepthdNV :: GLdouble -> m ()
glClearDepthdNV = FunPtr (GLdouble -> IO ()) -> GLdouble -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLdouble -> IO ()) -> GLdouble -> m ()
ffidoubleIOV FunPtr (GLdouble -> IO ())
glClearDepthdNVFunPtr
glClearDepthdNVFunPtr :: FunPtr (GLdouble -> IO ())
glClearDepthdNVFunPtr :: FunPtr (GLdouble -> IO ())
glClearDepthdNVFunPtr = IO (FunPtr (GLdouble -> IO ())) -> FunPtr (GLdouble -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLdouble -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glClearDepthdNV")
{-# NOINLINE glClearDepthdNVFunPtr #-}
glDepthBoundsdNV :: MonadIO m => GLdouble -> GLdouble -> m ()
glDepthBoundsdNV :: GLdouble -> GLdouble -> m ()
glDepthBoundsdNV = FunPtr (GLdouble -> GLdouble -> IO ())
-> GLdouble -> GLdouble -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLdouble -> GLdouble -> IO ())
-> GLdouble -> GLdouble -> m ()
ffidoubledoubleIOV FunPtr (GLdouble -> GLdouble -> IO ())
glDepthBoundsdNVFunPtr
glDepthBoundsdNVFunPtr :: FunPtr (GLdouble -> GLdouble -> IO ())
glDepthBoundsdNVFunPtr :: FunPtr (GLdouble -> GLdouble -> IO ())
glDepthBoundsdNVFunPtr = IO (FunPtr (GLdouble -> GLdouble -> IO ()))
-> FunPtr (GLdouble -> GLdouble -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLdouble -> GLdouble -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDepthBoundsdNV")
{-# NOINLINE glDepthBoundsdNVFunPtr #-}
glDepthRangedNV :: MonadIO m => GLdouble -> GLdouble -> m ()
glDepthRangedNV :: GLdouble -> GLdouble -> m ()
glDepthRangedNV = FunPtr (GLdouble -> GLdouble -> IO ())
-> GLdouble -> GLdouble -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLdouble -> GLdouble -> IO ())
-> GLdouble -> GLdouble -> m ()
ffidoubledoubleIOV FunPtr (GLdouble -> GLdouble -> IO ())
glDepthRangedNVFunPtr
glDepthRangedNVFunPtr :: FunPtr (GLdouble -> GLdouble -> IO ())
glDepthRangedNVFunPtr :: FunPtr (GLdouble -> GLdouble -> IO ())
glDepthRangedNVFunPtr = IO (FunPtr (GLdouble -> GLdouble -> IO ()))
-> FunPtr (GLdouble -> GLdouble -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLdouble -> GLdouble -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDepthRangedNV")
{-# NOINLINE glDepthRangedNVFunPtr #-}
pattern $bGL_DEPTH32F_STENCIL8_NV :: a
$mGL_DEPTH32F_STENCIL8_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_DEPTH32F_STENCIL8_NV = 0x8DAC
pattern $bGL_DEPTH_BUFFER_FLOAT_MODE_NV :: a
$mGL_DEPTH_BUFFER_FLOAT_MODE_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_DEPTH_BUFFER_FLOAT_MODE_NV = 0x8DAF
pattern $bGL_DEPTH_COMPONENT32F_NV :: a
$mGL_DEPTH_COMPONENT32F_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_DEPTH_COMPONENT32F_NV = 0x8DAB
pattern $bGL_FLOAT_32_UNSIGNED_INT_24_8_REV_NV :: a
$mGL_FLOAT_32_UNSIGNED_INT_24_8_REV_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_FLOAT_32_UNSIGNED_INT_24_8_REV_NV = 0x8DAD