{-# LANGUAGE CPP, ScopedTypeVariables, PatternSynonyms #-}
module Graphics.GL.Ext.NV.FramebufferBlit (
gl_NV_framebuffer_blit
, glBlitFramebufferNV
, pattern GL_DRAW_FRAMEBUFFER_BINDING_NV
, pattern GL_DRAW_FRAMEBUFFER_NV
, pattern GL_READ_FRAMEBUFFER_BINDING_NV
, pattern GL_READ_FRAMEBUFFER_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_framebuffer_blit :: Bool
gl_NV_framebuffer_blit :: Bool
gl_NV_framebuffer_blit = [Char] -> Set [Char] -> Bool
forall a. Ord a => a -> Set a -> Bool
member "GL_NV_framebuffer_blit" Set [Char]
extensions
{-# NOINLINE gl_NV_framebuffer_blit #-}
glBlitFramebufferNV :: MonadIO m => GLint -> GLint -> GLint -> GLint -> GLint -> GLint -> GLint -> GLint -> GLbitfield -> GLenum -> m ()
glBlitFramebufferNV :: GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLbitfield
-> GLbitfield
-> m ()
glBlitFramebufferNV = FunPtr
(GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLbitfield
-> GLbitfield
-> IO ())
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLbitfield
-> GLbitfield
-> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr
(GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLbitfield
-> GLbitfield
-> IO ())
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLbitfield
-> GLbitfield
-> m ()
ffiintintintintintintintintbitfieldenumIOV FunPtr
(GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLbitfield
-> GLbitfield
-> IO ())
glBlitFramebufferNVFunPtr
glBlitFramebufferNVFunPtr :: FunPtr (GLint -> GLint -> GLint -> GLint -> GLint -> GLint -> GLint -> GLint -> GLbitfield -> GLenum -> IO ())
glBlitFramebufferNVFunPtr :: FunPtr
(GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLbitfield
-> GLbitfield
-> IO ())
glBlitFramebufferNVFunPtr = IO
(FunPtr
(GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLbitfield
-> GLbitfield
-> IO ()))
-> FunPtr
(GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLbitfield
-> GLbitfield
-> IO ())
forall a. IO a -> a
unsafePerformIO ([Char]
-> IO
(FunPtr
(GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLint
-> GLbitfield
-> GLbitfield
-> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glBlitFramebufferNV")
{-# NOINLINE glBlitFramebufferNVFunPtr #-}
pattern $bGL_DRAW_FRAMEBUFFER_BINDING_NV :: a
$mGL_DRAW_FRAMEBUFFER_BINDING_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_DRAW_FRAMEBUFFER_BINDING_NV = 0x8CA6
pattern $bGL_DRAW_FRAMEBUFFER_NV :: a
$mGL_DRAW_FRAMEBUFFER_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_DRAW_FRAMEBUFFER_NV = 0x8CA9
pattern $bGL_READ_FRAMEBUFFER_BINDING_NV :: a
$mGL_READ_FRAMEBUFFER_BINDING_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_READ_FRAMEBUFFER_BINDING_NV = 0x8CAA
pattern $bGL_READ_FRAMEBUFFER_NV :: a
$mGL_READ_FRAMEBUFFER_NV :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_READ_FRAMEBUFFER_NV = 0x8CA8