{-# LANGUAGE CPP, ScopedTypeVariables, PatternSynonyms #-}
module Graphics.GL.Ext.EXT.DepthBoundsTest (
gl_EXT_depth_bounds_test
, glDepthBoundsEXT
, pattern GL_DEPTH_BOUNDS_EXT
, pattern GL_DEPTH_BOUNDS_TEST_EXT
) 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_EXT_depth_bounds_test :: Bool
gl_EXT_depth_bounds_test :: Bool
gl_EXT_depth_bounds_test = [Char] -> Set [Char] -> Bool
forall a. Ord a => a -> Set a -> Bool
member "GL_EXT_depth_bounds_test" Set [Char]
extensions
{-# NOINLINE gl_EXT_depth_bounds_test #-}
glDepthBoundsEXT :: MonadIO m => GLclampd -> GLclampd -> m ()
glDepthBoundsEXT :: GLclampd -> GLclampd -> m ()
glDepthBoundsEXT = FunPtr (GLclampd -> GLclampd -> IO ())
-> GLclampd -> GLclampd -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLclampd -> GLclampd -> IO ())
-> GLclampd -> GLclampd -> m ()
fficlampdclampdIOV FunPtr (GLclampd -> GLclampd -> IO ())
glDepthBoundsEXTFunPtr
glDepthBoundsEXTFunPtr :: FunPtr (GLclampd -> GLclampd -> IO ())
glDepthBoundsEXTFunPtr :: FunPtr (GLclampd -> GLclampd -> IO ())
glDepthBoundsEXTFunPtr = IO (FunPtr (GLclampd -> GLclampd -> IO ()))
-> FunPtr (GLclampd -> GLclampd -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLclampd -> GLclampd -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDepthBoundsEXT")
{-# NOINLINE glDepthBoundsEXTFunPtr #-}
pattern $bGL_DEPTH_BOUNDS_EXT :: a
$mGL_DEPTH_BOUNDS_EXT :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_DEPTH_BOUNDS_EXT = 0x8891
pattern $bGL_DEPTH_BOUNDS_TEST_EXT :: a
$mGL_DEPTH_BOUNDS_TEST_EXT :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_DEPTH_BOUNDS_TEST_EXT = 0x8890