{-# LANGUAGE CPP, ScopedTypeVariables, PatternSynonyms #-}
module Graphics.GL.Ext.OES.DrawTexture (
gl_OES_draw_texture
, glDrawTexfOES
, glDrawTexfvOES
, glDrawTexiOES
, glDrawTexivOES
, glDrawTexsOES
, glDrawTexsvOES
, glDrawTexxOES
, glDrawTexxvOES
, pattern GL_TEXTURE_CROP_RECT_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.Types
import System.IO.Unsafe
gl_OES_draw_texture :: Bool
gl_OES_draw_texture :: Bool
gl_OES_draw_texture = [Char] -> Set [Char] -> Bool
forall a. Ord a => a -> Set a -> Bool
member "GL_OES_draw_texture" Set [Char]
extensions
{-# NOINLINE gl_OES_draw_texture #-}
glDrawTexfOES :: MonadIO m => GLfloat -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> m ()
glDrawTexfOES :: GLfloat -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> m ()
glDrawTexfOES = FunPtr
(GLfloat -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
-> GLfloat -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr
(GLfloat -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
-> GLfloat -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> m ()
ffifloatfloatfloatfloatfloatIOV FunPtr
(GLfloat -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
glDrawTexfOESFunPtr
glDrawTexfOESFunPtr :: FunPtr (GLfloat -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
glDrawTexfOESFunPtr :: FunPtr
(GLfloat -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
glDrawTexfOESFunPtr = IO
(FunPtr
(GLfloat -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ()))
-> FunPtr
(GLfloat -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char]
-> IO
(FunPtr
(GLfloat -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDrawTexfOES")
{-# NOINLINE glDrawTexfOESFunPtr #-}
glDrawTexfvOES :: MonadIO m => Ptr GLfloat -> m ()
glDrawTexfvOES :: Ptr GLfloat -> m ()
glDrawTexfvOES = FunPtr (Ptr GLfloat -> IO ()) -> Ptr GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLfloat -> IO ()) -> Ptr GLfloat -> m ()
ffiPtrfloatIOV FunPtr (Ptr GLfloat -> IO ())
glDrawTexfvOESFunPtr
glDrawTexfvOESFunPtr :: FunPtr (Ptr GLfloat -> IO ())
glDrawTexfvOESFunPtr :: FunPtr (Ptr GLfloat -> IO ())
glDrawTexfvOESFunPtr = IO (FunPtr (Ptr GLfloat -> IO ())) -> FunPtr (Ptr GLfloat -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (Ptr GLfloat -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDrawTexfvOES")
{-# NOINLINE glDrawTexfvOESFunPtr #-}
glDrawTexiOES :: MonadIO m => GLint -> GLint -> GLint -> GLint -> GLint -> m ()
glDrawTexiOES :: GLint -> GLint -> GLint -> GLint -> GLint -> m ()
glDrawTexiOES = FunPtr (GLint -> GLint -> GLint -> GLint -> GLint -> IO ())
-> GLint -> GLint -> GLint -> GLint -> GLint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLint -> GLint -> GLint -> GLint -> GLint -> IO ())
-> GLint -> GLint -> GLint -> GLint -> GLint -> m ()
ffiintintintintintIOV FunPtr (GLint -> GLint -> GLint -> GLint -> GLint -> IO ())
glDrawTexiOESFunPtr
glDrawTexiOESFunPtr :: FunPtr (GLint -> GLint -> GLint -> GLint -> GLint -> IO ())
glDrawTexiOESFunPtr :: FunPtr (GLint -> GLint -> GLint -> GLint -> GLint -> IO ())
glDrawTexiOESFunPtr = IO (FunPtr (GLint -> GLint -> GLint -> GLint -> GLint -> IO ()))
-> FunPtr (GLint -> GLint -> GLint -> GLint -> GLint -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char]
-> IO (FunPtr (GLint -> GLint -> GLint -> GLint -> GLint -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDrawTexiOES")
{-# NOINLINE glDrawTexiOESFunPtr #-}
glDrawTexivOES :: MonadIO m => Ptr GLint -> m ()
glDrawTexivOES :: Ptr GLint -> m ()
glDrawTexivOES = FunPtr (Ptr GLint -> IO ()) -> Ptr GLint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLint -> IO ()) -> Ptr GLint -> m ()
ffiPtrintIOV FunPtr (Ptr GLint -> IO ())
glDrawTexivOESFunPtr
glDrawTexivOESFunPtr :: FunPtr (Ptr GLint -> IO ())
glDrawTexivOESFunPtr :: FunPtr (Ptr GLint -> IO ())
glDrawTexivOESFunPtr = IO (FunPtr (Ptr GLint -> IO ())) -> FunPtr (Ptr GLint -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (Ptr GLint -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDrawTexivOES")
{-# NOINLINE glDrawTexivOESFunPtr #-}
glDrawTexsOES :: MonadIO m => GLshort -> GLshort -> GLshort -> GLshort -> GLshort -> m ()
glDrawTexsOES :: GLshort -> GLshort -> GLshort -> GLshort -> GLshort -> m ()
glDrawTexsOES = FunPtr
(GLshort -> GLshort -> GLshort -> GLshort -> GLshort -> IO ())
-> GLshort -> GLshort -> GLshort -> GLshort -> GLshort -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr
(GLshort -> GLshort -> GLshort -> GLshort -> GLshort -> IO ())
-> GLshort -> GLshort -> GLshort -> GLshort -> GLshort -> m ()
ffishortshortshortshortshortIOV FunPtr
(GLshort -> GLshort -> GLshort -> GLshort -> GLshort -> IO ())
glDrawTexsOESFunPtr
glDrawTexsOESFunPtr :: FunPtr (GLshort -> GLshort -> GLshort -> GLshort -> GLshort -> IO ())
glDrawTexsOESFunPtr :: FunPtr
(GLshort -> GLshort -> GLshort -> GLshort -> GLshort -> IO ())
glDrawTexsOESFunPtr = IO
(FunPtr
(GLshort -> GLshort -> GLshort -> GLshort -> GLshort -> IO ()))
-> FunPtr
(GLshort -> GLshort -> GLshort -> GLshort -> GLshort -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char]
-> IO
(FunPtr
(GLshort -> GLshort -> GLshort -> GLshort -> GLshort -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDrawTexsOES")
{-# NOINLINE glDrawTexsOESFunPtr #-}
glDrawTexsvOES :: MonadIO m => Ptr GLshort -> m ()
glDrawTexsvOES :: Ptr GLshort -> m ()
glDrawTexsvOES = FunPtr (Ptr GLshort -> IO ()) -> Ptr GLshort -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLshort -> IO ()) -> Ptr GLshort -> m ()
ffiPtrshortIOV FunPtr (Ptr GLshort -> IO ())
glDrawTexsvOESFunPtr
glDrawTexsvOESFunPtr :: FunPtr (Ptr GLshort -> IO ())
glDrawTexsvOESFunPtr :: FunPtr (Ptr GLshort -> IO ())
glDrawTexsvOESFunPtr = IO (FunPtr (Ptr GLshort -> IO ())) -> FunPtr (Ptr GLshort -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (Ptr GLshort -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDrawTexsvOES")
{-# NOINLINE glDrawTexsvOESFunPtr #-}
glDrawTexxOES :: MonadIO m => GLfixed -> GLfixed -> GLfixed -> GLfixed -> GLfixed -> m ()
glDrawTexxOES :: GLfixed -> GLfixed -> GLfixed -> GLfixed -> GLfixed -> m ()
glDrawTexxOES = FunPtr
(GLfixed -> GLfixed -> GLfixed -> GLfixed -> GLfixed -> IO ())
-> GLfixed -> GLfixed -> GLfixed -> GLfixed -> GLfixed -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr
(GLfixed -> GLfixed -> GLfixed -> GLfixed -> GLfixed -> IO ())
-> GLfixed -> GLfixed -> GLfixed -> GLfixed -> GLfixed -> m ()
ffifixedfixedfixedfixedfixedIOV FunPtr
(GLfixed -> GLfixed -> GLfixed -> GLfixed -> GLfixed -> IO ())
glDrawTexxOESFunPtr
glDrawTexxOESFunPtr :: FunPtr (GLfixed -> GLfixed -> GLfixed -> GLfixed -> GLfixed -> IO ())
glDrawTexxOESFunPtr :: FunPtr
(GLfixed -> GLfixed -> GLfixed -> GLfixed -> GLfixed -> IO ())
glDrawTexxOESFunPtr = IO
(FunPtr
(GLfixed -> GLfixed -> GLfixed -> GLfixed -> GLfixed -> IO ()))
-> FunPtr
(GLfixed -> GLfixed -> GLfixed -> GLfixed -> GLfixed -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char]
-> IO
(FunPtr
(GLfixed -> GLfixed -> GLfixed -> GLfixed -> GLfixed -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDrawTexxOES")
{-# NOINLINE glDrawTexxOESFunPtr #-}
glDrawTexxvOES :: MonadIO m => Ptr GLfixed -> m ()
glDrawTexxvOES :: Ptr GLfixed -> m ()
glDrawTexxvOES = FunPtr (Ptr GLfixed -> IO ()) -> Ptr GLfixed -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLfixed -> IO ()) -> Ptr GLfixed -> m ()
ffiPtrfixedIOV FunPtr (Ptr GLfixed -> IO ())
glDrawTexxvOESFunPtr
glDrawTexxvOESFunPtr :: FunPtr (Ptr GLfixed -> IO ())
glDrawTexxvOESFunPtr :: FunPtr (Ptr GLfixed -> IO ())
glDrawTexxvOESFunPtr = IO (FunPtr (Ptr GLfixed -> IO ())) -> FunPtr (Ptr GLfixed -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (Ptr GLfixed -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glDrawTexxvOES")
{-# NOINLINE glDrawTexxvOESFunPtr #-}
pattern $bGL_TEXTURE_CROP_RECT_OES :: a
$mGL_TEXTURE_CROP_RECT_OES :: forall r a. (Eq a, Num a) => a -> (Void# -> r) -> (Void# -> r) -> r
GL_TEXTURE_CROP_RECT_OES = 0x8B9D