{-# LANGUAGE CPP, ScopedTypeVariables, PatternSynonyms #-}
module Graphics.GL.Ext.OES.ViewportArray (
gl_OES_viewport_array
, glDepthRangeArrayfvOES
, glDepthRangeIndexedfOES
, glDisableiOES
, glEnableiOES
, glGetFloati_vOES
, glIsEnablediOES
, glScissorArrayvOES
, glScissorIndexedOES
, glScissorIndexedvOES
, glViewportArrayvOES
, glViewportIndexedfOES
, glViewportIndexedfvOES
, pattern GL_DEPTH_RANGE
, pattern GL_MAX_VIEWPORTS_OES
, pattern GL_SCISSOR_BOX
, pattern GL_SCISSOR_TEST
, pattern GL_VIEWPORT
, pattern GL_VIEWPORT_BOUNDS_RANGE_OES
, pattern GL_VIEWPORT_INDEX_PROVOKING_VERTEX_OES
, pattern GL_VIEWPORT_SUBPIXEL_BITS_OES
) 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.Internal.Shared
import Graphics.GL.Types
import System.IO.Unsafe
gl_OES_viewport_array :: Bool
gl_OES_viewport_array :: Bool
gl_OES_viewport_array = [Char] -> Set [Char] -> Bool
forall a. Ord a => a -> Set a -> Bool
member "GL_OES_viewport_array" Set [Char]
extensions
{-# NOINLINE gl_OES_viewport_array #-}
glDepthRangeArrayfvOES :: MonadIO m => GLuint -> GLsizei -> Ptr GLfloat -> m ()
glDepthRangeArrayfvOES :: GLuint -> GLsizei -> Ptr GLfloat -> m ()
glDepthRangeArrayfvOES = FunPtr (GLuint -> GLsizei -> Ptr GLfloat -> IO ())
-> GLuint -> GLsizei -> Ptr GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLuint -> GLsizei -> Ptr GLfloat -> IO ())
-> GLuint -> GLsizei -> Ptr GLfloat -> m ()
ffiuintsizeiPtrfloatIOV FunPtr (GLuint -> GLsizei -> Ptr GLfloat -> IO ())
glDepthRangeArrayfvOESFunPtr
glDepthRangeArrayfvOESFunPtr :: FunPtr (GLuint -> GLsizei -> Ptr GLfloat -> IO ())
glDepthRangeArrayfvOESFunPtr :: FunPtr (GLuint -> GLsizei -> Ptr GLfloat -> IO ())
glDepthRangeArrayfvOESFunPtr = IO (FunPtr (GLuint -> GLsizei -> Ptr GLfloat -> IO ()))
-> FunPtr (GLuint -> GLsizei -> Ptr GLfloat -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLuint -> GLsizei -> Ptr GLfloat -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDepthRangeArrayfvOES")
{-# NOINLINE glDepthRangeArrayfvOESFunPtr #-}
glDepthRangeIndexedfOES :: MonadIO m => GLuint -> GLfloat -> GLfloat -> m ()
glDepthRangeIndexedfOES :: GLuint -> GLfloat -> GLfloat -> m ()
glDepthRangeIndexedfOES = FunPtr (GLuint -> GLfloat -> GLfloat -> IO ())
-> GLuint -> GLfloat -> GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLuint -> GLfloat -> GLfloat -> IO ())
-> GLuint -> GLfloat -> GLfloat -> m ()
ffiuintfloatfloatIOV FunPtr (GLuint -> GLfloat -> GLfloat -> IO ())
glDepthRangeIndexedfOESFunPtr
glDepthRangeIndexedfOESFunPtr :: FunPtr (GLuint -> GLfloat -> GLfloat -> IO ())
glDepthRangeIndexedfOESFunPtr :: FunPtr (GLuint -> GLfloat -> GLfloat -> IO ())
glDepthRangeIndexedfOESFunPtr = IO (FunPtr (GLuint -> GLfloat -> GLfloat -> IO ()))
-> FunPtr (GLuint -> GLfloat -> GLfloat -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLuint -> GLfloat -> GLfloat -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDepthRangeIndexedfOES")
{-# NOINLINE glDepthRangeIndexedfOESFunPtr #-}
glGetFloati_vOES :: MonadIO m => GLenum -> GLuint -> Ptr GLfloat -> m ()
glGetFloati_vOES :: GLuint -> GLuint -> Ptr GLfloat -> m ()
glGetFloati_vOES = FunPtr (GLuint -> GLuint -> Ptr GLfloat -> IO ())
-> GLuint -> GLuint -> Ptr GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLuint -> GLuint -> Ptr GLfloat -> IO ())
-> GLuint -> GLuint -> Ptr GLfloat -> m ()
ffienumuintPtrfloatIOV FunPtr (GLuint -> GLuint -> Ptr GLfloat -> IO ())
glGetFloati_vOESFunPtr
glGetFloati_vOESFunPtr :: FunPtr (GLenum -> GLuint -> Ptr GLfloat -> IO ())
glGetFloati_vOESFunPtr :: FunPtr (GLuint -> GLuint -> Ptr GLfloat -> IO ())
glGetFloati_vOESFunPtr = IO (FunPtr (GLuint -> GLuint -> Ptr GLfloat -> IO ()))
-> FunPtr (GLuint -> GLuint -> Ptr GLfloat -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLuint -> GLuint -> Ptr GLfloat -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glGetFloati_vOES")
{-# NOINLINE glGetFloati_vOESFunPtr #-}
glScissorArrayvOES :: MonadIO m => GLuint -> GLsizei -> Ptr GLint -> m ()
glScissorArrayvOES :: GLuint -> GLsizei -> Ptr GLsizei -> m ()
glScissorArrayvOES = FunPtr (GLuint -> GLsizei -> Ptr GLsizei -> IO ())
-> GLuint -> GLsizei -> Ptr GLsizei -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLuint -> GLsizei -> Ptr GLsizei -> IO ())
-> GLuint -> GLsizei -> Ptr GLsizei -> m ()
ffiuintsizeiPtrintIOV FunPtr (GLuint -> GLsizei -> Ptr GLsizei -> IO ())
glScissorArrayvOESFunPtr
glScissorArrayvOESFunPtr :: FunPtr (GLuint -> GLsizei -> Ptr GLint -> IO ())
glScissorArrayvOESFunPtr :: FunPtr (GLuint -> GLsizei -> Ptr GLsizei -> IO ())
glScissorArrayvOESFunPtr = IO (FunPtr (GLuint -> GLsizei -> Ptr GLsizei -> IO ()))
-> FunPtr (GLuint -> GLsizei -> Ptr GLsizei -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLuint -> GLsizei -> Ptr GLsizei -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glScissorArrayvOES")
{-# NOINLINE glScissorArrayvOESFunPtr #-}
glScissorIndexedOES :: MonadIO m => GLuint -> GLint -> GLint -> GLsizei -> GLsizei -> m ()
glScissorIndexedOES :: GLuint -> GLsizei -> GLsizei -> GLsizei -> GLsizei -> m ()
glScissorIndexedOES = FunPtr
(GLuint -> GLsizei -> GLsizei -> GLsizei -> GLsizei -> IO ())
-> GLuint -> GLsizei -> GLsizei -> GLsizei -> GLsizei -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr
(GLuint -> GLsizei -> GLsizei -> GLsizei -> GLsizei -> IO ())
-> GLuint -> GLsizei -> GLsizei -> GLsizei -> GLsizei -> m ()
ffiuintintintsizeisizeiIOV FunPtr
(GLuint -> GLsizei -> GLsizei -> GLsizei -> GLsizei -> IO ())
glScissorIndexedOESFunPtr
glScissorIndexedOESFunPtr :: FunPtr (GLuint -> GLint -> GLint -> GLsizei -> GLsizei -> IO ())
glScissorIndexedOESFunPtr :: FunPtr
(GLuint -> GLsizei -> GLsizei -> GLsizei -> GLsizei -> IO ())
glScissorIndexedOESFunPtr = IO
(FunPtr
(GLuint -> GLsizei -> GLsizei -> GLsizei -> GLsizei -> IO ()))
-> FunPtr
(GLuint -> GLsizei -> GLsizei -> GLsizei -> GLsizei -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char]
-> IO
(FunPtr
(GLuint -> GLsizei -> GLsizei -> GLsizei -> GLsizei -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glScissorIndexedOES")
{-# NOINLINE glScissorIndexedOESFunPtr #-}
glScissorIndexedvOES :: MonadIO m => GLuint -> Ptr GLint -> m ()
glScissorIndexedvOES :: GLuint -> Ptr GLsizei -> m ()
glScissorIndexedvOES = FunPtr (GLuint -> Ptr GLsizei -> IO ())
-> GLuint -> Ptr GLsizei -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLuint -> Ptr GLsizei -> IO ())
-> GLuint -> Ptr GLsizei -> m ()
ffiuintPtrintIOV FunPtr (GLuint -> Ptr GLsizei -> IO ())
glScissorIndexedvOESFunPtr
glScissorIndexedvOESFunPtr :: FunPtr (GLuint -> Ptr GLint -> IO ())
glScissorIndexedvOESFunPtr :: FunPtr (GLuint -> Ptr GLsizei -> IO ())
glScissorIndexedvOESFunPtr = IO (FunPtr (GLuint -> Ptr GLsizei -> IO ()))
-> FunPtr (GLuint -> Ptr GLsizei -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLuint -> Ptr GLsizei -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glScissorIndexedvOES")
{-# NOINLINE glScissorIndexedvOESFunPtr #-}
glViewportArrayvOES :: MonadIO m => GLuint -> GLsizei -> Ptr GLfloat -> m ()
glViewportArrayvOES :: GLuint -> GLsizei -> Ptr GLfloat -> m ()
glViewportArrayvOES = FunPtr (GLuint -> GLsizei -> Ptr GLfloat -> IO ())
-> GLuint -> GLsizei -> Ptr GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLuint -> GLsizei -> Ptr GLfloat -> IO ())
-> GLuint -> GLsizei -> Ptr GLfloat -> m ()
ffiuintsizeiPtrfloatIOV FunPtr (GLuint -> GLsizei -> Ptr GLfloat -> IO ())
glViewportArrayvOESFunPtr
glViewportArrayvOESFunPtr :: FunPtr (GLuint -> GLsizei -> Ptr GLfloat -> IO ())
glViewportArrayvOESFunPtr :: FunPtr (GLuint -> GLsizei -> Ptr GLfloat -> IO ())
glViewportArrayvOESFunPtr = IO (FunPtr (GLuint -> GLsizei -> Ptr GLfloat -> IO ()))
-> FunPtr (GLuint -> GLsizei -> Ptr GLfloat -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLuint -> GLsizei -> Ptr GLfloat -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glViewportArrayvOES")
{-# NOINLINE glViewportArrayvOESFunPtr #-}
glViewportIndexedfOES :: MonadIO m => GLuint -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> m ()
glViewportIndexedfOES :: GLuint -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> m ()
glViewportIndexedfOES = FunPtr
(GLuint -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
-> GLuint -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr
(GLuint -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
-> GLuint -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> m ()
ffiuintfloatfloatfloatfloatIOV FunPtr
(GLuint -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
glViewportIndexedfOESFunPtr
glViewportIndexedfOESFunPtr :: FunPtr (GLuint -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
glViewportIndexedfOESFunPtr :: FunPtr
(GLuint -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
glViewportIndexedfOESFunPtr = IO
(FunPtr
(GLuint -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ()))
-> FunPtr
(GLuint -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char]
-> IO
(FunPtr
(GLuint -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glViewportIndexedfOES")
{-# NOINLINE glViewportIndexedfOESFunPtr #-}
glViewportIndexedfvOES :: MonadIO m => GLuint -> Ptr GLfloat -> m ()
glViewportIndexedfvOES :: GLuint -> Ptr GLfloat -> m ()
glViewportIndexedfvOES = FunPtr (GLuint -> Ptr GLfloat -> IO ())
-> GLuint -> Ptr GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLuint -> Ptr GLfloat -> IO ())
-> GLuint -> Ptr GLfloat -> m ()
ffiuintPtrfloatIOV FunPtr (GLuint -> Ptr GLfloat -> IO ())
glViewportIndexedfvOESFunPtr
glViewportIndexedfvOESFunPtr :: FunPtr (GLuint -> Ptr GLfloat -> IO ())
glViewportIndexedfvOESFunPtr :: FunPtr (GLuint -> Ptr GLfloat -> IO ())
glViewportIndexedfvOESFunPtr = IO (FunPtr (GLuint -> Ptr GLfloat -> IO ()))
-> FunPtr (GLuint -> Ptr GLfloat -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLuint -> Ptr GLfloat -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glViewportIndexedfvOES")
{-# NOINLINE glViewportIndexedfvOESFunPtr #-}
pattern $bGL_MAX_VIEWPORTS_OES :: a
$mGL_MAX_VIEWPORTS_OES :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_MAX_VIEWPORTS_OES = 0x825B
pattern $bGL_VIEWPORT_BOUNDS_RANGE_OES :: a
$mGL_VIEWPORT_BOUNDS_RANGE_OES :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_VIEWPORT_BOUNDS_RANGE_OES = 0x825D
pattern $bGL_VIEWPORT_INDEX_PROVOKING_VERTEX_OES :: a
$mGL_VIEWPORT_INDEX_PROVOKING_VERTEX_OES :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_VIEWPORT_INDEX_PROVOKING_VERTEX_OES = 0x825F
pattern $bGL_VIEWPORT_SUBPIXEL_BITS_OES :: a
$mGL_VIEWPORT_SUBPIXEL_BITS_OES :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_VIEWPORT_SUBPIXEL_BITS_OES = 0x825C