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 = member "GL_OES_draw_texture" extensions
glDrawTexfOES :: MonadIO m => GLfloat -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> m ()
glDrawTexfOES = ffifloatfloatfloatfloatfloatIOV glDrawTexfOESFunPtr
glDrawTexfOESFunPtr :: FunPtr (GLfloat -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
glDrawTexfOESFunPtr = unsafePerformIO (getProcAddress "glDrawTexfOES")
glDrawTexfvOES :: MonadIO m => Ptr GLfloat -> m ()
glDrawTexfvOES = ffiPtrfloatIOV glDrawTexfvOESFunPtr
glDrawTexfvOESFunPtr :: FunPtr (Ptr GLfloat -> IO ())
glDrawTexfvOESFunPtr = unsafePerformIO (getProcAddress "glDrawTexfvOES")
glDrawTexiOES :: MonadIO m => GLint -> GLint -> GLint -> GLint -> GLint -> m ()
glDrawTexiOES = ffiintintintintintIOV glDrawTexiOESFunPtr
glDrawTexiOESFunPtr :: FunPtr (GLint -> GLint -> GLint -> GLint -> GLint -> IO ())
glDrawTexiOESFunPtr = unsafePerformIO (getProcAddress "glDrawTexiOES")
glDrawTexivOES :: MonadIO m => Ptr GLint -> m ()
glDrawTexivOES = ffiPtrintIOV glDrawTexivOESFunPtr
glDrawTexivOESFunPtr :: FunPtr (Ptr GLint -> IO ())
glDrawTexivOESFunPtr = unsafePerformIO (getProcAddress "glDrawTexivOES")
glDrawTexsOES :: MonadIO m => GLshort -> GLshort -> GLshort -> GLshort -> GLshort -> m ()
glDrawTexsOES = ffishortshortshortshortshortIOV glDrawTexsOESFunPtr
glDrawTexsOESFunPtr :: FunPtr (GLshort -> GLshort -> GLshort -> GLshort -> GLshort -> IO ())
glDrawTexsOESFunPtr = unsafePerformIO (getProcAddress "glDrawTexsOES")
glDrawTexsvOES :: MonadIO m => Ptr GLshort -> m ()
glDrawTexsvOES = ffiPtrshortIOV glDrawTexsvOESFunPtr
glDrawTexsvOESFunPtr :: FunPtr (Ptr GLshort -> IO ())
glDrawTexsvOESFunPtr = unsafePerformIO (getProcAddress "glDrawTexsvOES")
glDrawTexxOES :: MonadIO m => GLfixed -> GLfixed -> GLfixed -> GLfixed -> GLfixed -> m ()
glDrawTexxOES = ffifixedfixedfixedfixedfixedIOV glDrawTexxOESFunPtr
glDrawTexxOESFunPtr :: FunPtr (GLfixed -> GLfixed -> GLfixed -> GLfixed -> GLfixed -> IO ())
glDrawTexxOESFunPtr = unsafePerformIO (getProcAddress "glDrawTexxOES")
glDrawTexxvOES :: MonadIO m => Ptr GLfixed -> m ()
glDrawTexxvOES = ffiPtrfixedIOV glDrawTexxvOESFunPtr
glDrawTexxvOESFunPtr :: FunPtr (Ptr GLfixed -> IO ())
glDrawTexxvOESFunPtr = unsafePerformIO (getProcAddress "glDrawTexxvOES")
pattern GL_TEXTURE_CROP_RECT_OES = 0x8B9D