{-# LANGUAGE CPP, ScopedTypeVariables, PatternSynonyms #-}
module Graphics.GL.Ext.MESA.WindowPos (
gl_MESA_window_pos
, glWindowPos2dMESA
, glWindowPos2dvMESA
, glWindowPos2fMESA
, glWindowPos2fvMESA
, glWindowPos2iMESA
, glWindowPos2ivMESA
, glWindowPos2sMESA
, glWindowPos2svMESA
, glWindowPos3dMESA
, glWindowPos3dvMESA
, glWindowPos3fMESA
, glWindowPos3fvMESA
, glWindowPos3iMESA
, glWindowPos3ivMESA
, glWindowPos3sMESA
, glWindowPos3svMESA
, glWindowPos4dMESA
, glWindowPos4dvMESA
, glWindowPos4fMESA
, glWindowPos4fvMESA
, glWindowPos4iMESA
, glWindowPos4ivMESA
, glWindowPos4sMESA
, glWindowPos4svMESA
) 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_MESA_window_pos :: Bool
gl_MESA_window_pos :: Bool
gl_MESA_window_pos = [Char] -> Set [Char] -> Bool
forall a. Ord a => a -> Set a -> Bool
member "GL_MESA_window_pos" Set [Char]
extensions
{-# NOINLINE gl_MESA_window_pos #-}
glWindowPos2dMESA :: MonadIO m => GLdouble -> GLdouble -> m ()
glWindowPos2dMESA :: GLdouble -> GLdouble -> m ()
glWindowPos2dMESA = FunPtr (GLdouble -> GLdouble -> IO ())
-> GLdouble -> GLdouble -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLdouble -> GLdouble -> IO ())
-> GLdouble -> GLdouble -> m ()
ffidoubledoubleIOV FunPtr (GLdouble -> GLdouble -> IO ())
glWindowPos2dMESAFunPtr
glWindowPos2dMESAFunPtr :: FunPtr (GLdouble -> GLdouble -> IO ())
glWindowPos2dMESAFunPtr :: FunPtr (GLdouble -> GLdouble -> IO ())
glWindowPos2dMESAFunPtr = IO (FunPtr (GLdouble -> GLdouble -> IO ()))
-> FunPtr (GLdouble -> GLdouble -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLdouble -> GLdouble -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glWindowPos2dMESA")
{-# NOINLINE glWindowPos2dMESAFunPtr #-}
glWindowPos2dvMESA :: MonadIO m => Ptr GLdouble -> m ()
glWindowPos2dvMESA :: Ptr GLdouble -> m ()
glWindowPos2dvMESA = FunPtr (Ptr GLdouble -> IO ()) -> Ptr GLdouble -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLdouble -> IO ()) -> Ptr GLdouble -> m ()
ffiPtrdoubleIOV FunPtr (Ptr GLdouble -> IO ())
glWindowPos2dvMESAFunPtr
glWindowPos2dvMESAFunPtr :: FunPtr (Ptr GLdouble -> IO ())
glWindowPos2dvMESAFunPtr :: FunPtr (Ptr GLdouble -> IO ())
glWindowPos2dvMESAFunPtr = IO (FunPtr (Ptr GLdouble -> IO ()))
-> FunPtr (Ptr GLdouble -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (Ptr GLdouble -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glWindowPos2dvMESA")
{-# NOINLINE glWindowPos2dvMESAFunPtr #-}
glWindowPos2fMESA :: MonadIO m => GLfloat -> GLfloat -> m ()
glWindowPos2fMESA :: GLfloat -> GLfloat -> m ()
glWindowPos2fMESA = FunPtr (GLfloat -> GLfloat -> IO ()) -> GLfloat -> GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLfloat -> GLfloat -> IO ()) -> GLfloat -> GLfloat -> m ()
ffifloatfloatIOV FunPtr (GLfloat -> GLfloat -> IO ())
glWindowPos2fMESAFunPtr
glWindowPos2fMESAFunPtr :: FunPtr (GLfloat -> GLfloat -> IO ())
glWindowPos2fMESAFunPtr :: FunPtr (GLfloat -> GLfloat -> IO ())
glWindowPos2fMESAFunPtr = IO (FunPtr (GLfloat -> GLfloat -> IO ()))
-> FunPtr (GLfloat -> GLfloat -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLfloat -> GLfloat -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glWindowPos2fMESA")
{-# NOINLINE glWindowPos2fMESAFunPtr #-}
glWindowPos2fvMESA :: MonadIO m => Ptr GLfloat -> m ()
glWindowPos2fvMESA :: Ptr GLfloat -> m ()
glWindowPos2fvMESA = FunPtr (Ptr GLfloat -> IO ()) -> Ptr GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLfloat -> IO ()) -> Ptr GLfloat -> m ()
ffiPtrfloatIOV FunPtr (Ptr GLfloat -> IO ())
glWindowPos2fvMESAFunPtr
glWindowPos2fvMESAFunPtr :: FunPtr (Ptr GLfloat -> IO ())
glWindowPos2fvMESAFunPtr :: FunPtr (Ptr GLfloat -> IO ())
glWindowPos2fvMESAFunPtr = 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 "glWindowPos2fvMESA")
{-# NOINLINE glWindowPos2fvMESAFunPtr #-}
glWindowPos2iMESA :: MonadIO m => GLint -> GLint -> m ()
glWindowPos2iMESA :: GLint -> GLint -> m ()
glWindowPos2iMESA = FunPtr (GLint -> GLint -> IO ()) -> GLint -> GLint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLint -> GLint -> IO ()) -> GLint -> GLint -> m ()
ffiintintIOV FunPtr (GLint -> GLint -> IO ())
glWindowPos2iMESAFunPtr
glWindowPos2iMESAFunPtr :: FunPtr (GLint -> GLint -> IO ())
glWindowPos2iMESAFunPtr :: FunPtr (GLint -> GLint -> IO ())
glWindowPos2iMESAFunPtr = IO (FunPtr (GLint -> GLint -> IO ()))
-> FunPtr (GLint -> GLint -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLint -> GLint -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glWindowPos2iMESA")
{-# NOINLINE glWindowPos2iMESAFunPtr #-}
glWindowPos2ivMESA :: MonadIO m => Ptr GLint -> m ()
glWindowPos2ivMESA :: Ptr GLint -> m ()
glWindowPos2ivMESA = FunPtr (Ptr GLint -> IO ()) -> Ptr GLint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLint -> IO ()) -> Ptr GLint -> m ()
ffiPtrintIOV FunPtr (Ptr GLint -> IO ())
glWindowPos2ivMESAFunPtr
glWindowPos2ivMESAFunPtr :: FunPtr (Ptr GLint -> IO ())
glWindowPos2ivMESAFunPtr :: FunPtr (Ptr GLint -> IO ())
glWindowPos2ivMESAFunPtr = 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 "glWindowPos2ivMESA")
{-# NOINLINE glWindowPos2ivMESAFunPtr #-}
glWindowPos2sMESA :: MonadIO m => GLshort -> GLshort -> m ()
glWindowPos2sMESA :: GLshort -> GLshort -> m ()
glWindowPos2sMESA = FunPtr (GLshort -> GLshort -> IO ()) -> GLshort -> GLshort -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLshort -> GLshort -> IO ()) -> GLshort -> GLshort -> m ()
ffishortshortIOV FunPtr (GLshort -> GLshort -> IO ())
glWindowPos2sMESAFunPtr
glWindowPos2sMESAFunPtr :: FunPtr (GLshort -> GLshort -> IO ())
glWindowPos2sMESAFunPtr :: FunPtr (GLshort -> GLshort -> IO ())
glWindowPos2sMESAFunPtr = IO (FunPtr (GLshort -> GLshort -> IO ()))
-> FunPtr (GLshort -> GLshort -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLshort -> GLshort -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glWindowPos2sMESA")
{-# NOINLINE glWindowPos2sMESAFunPtr #-}
glWindowPos2svMESA :: MonadIO m => Ptr GLshort -> m ()
glWindowPos2svMESA :: Ptr GLshort -> m ()
glWindowPos2svMESA = FunPtr (Ptr GLshort -> IO ()) -> Ptr GLshort -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLshort -> IO ()) -> Ptr GLshort -> m ()
ffiPtrshortIOV FunPtr (Ptr GLshort -> IO ())
glWindowPos2svMESAFunPtr
glWindowPos2svMESAFunPtr :: FunPtr (Ptr GLshort -> IO ())
glWindowPos2svMESAFunPtr :: FunPtr (Ptr GLshort -> IO ())
glWindowPos2svMESAFunPtr = 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 "glWindowPos2svMESA")
{-# NOINLINE glWindowPos2svMESAFunPtr #-}
glWindowPos3dMESA :: MonadIO m => GLdouble -> GLdouble -> GLdouble -> m ()
glWindowPos3dMESA :: GLdouble -> GLdouble -> GLdouble -> m ()
glWindowPos3dMESA = FunPtr (GLdouble -> GLdouble -> GLdouble -> IO ())
-> GLdouble -> GLdouble -> GLdouble -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLdouble -> GLdouble -> GLdouble -> IO ())
-> GLdouble -> GLdouble -> GLdouble -> m ()
ffidoubledoubledoubleIOV FunPtr (GLdouble -> GLdouble -> GLdouble -> IO ())
glWindowPos3dMESAFunPtr
glWindowPos3dMESAFunPtr :: FunPtr (GLdouble -> GLdouble -> GLdouble -> IO ())
glWindowPos3dMESAFunPtr :: FunPtr (GLdouble -> GLdouble -> GLdouble -> IO ())
glWindowPos3dMESAFunPtr = IO (FunPtr (GLdouble -> GLdouble -> GLdouble -> IO ()))
-> FunPtr (GLdouble -> GLdouble -> GLdouble -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLdouble -> GLdouble -> GLdouble -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glWindowPos3dMESA")
{-# NOINLINE glWindowPos3dMESAFunPtr #-}
glWindowPos3dvMESA :: MonadIO m => Ptr GLdouble -> m ()
glWindowPos3dvMESA :: Ptr GLdouble -> m ()
glWindowPos3dvMESA = FunPtr (Ptr GLdouble -> IO ()) -> Ptr GLdouble -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLdouble -> IO ()) -> Ptr GLdouble -> m ()
ffiPtrdoubleIOV FunPtr (Ptr GLdouble -> IO ())
glWindowPos3dvMESAFunPtr
glWindowPos3dvMESAFunPtr :: FunPtr (Ptr GLdouble -> IO ())
glWindowPos3dvMESAFunPtr :: FunPtr (Ptr GLdouble -> IO ())
glWindowPos3dvMESAFunPtr = IO (FunPtr (Ptr GLdouble -> IO ()))
-> FunPtr (Ptr GLdouble -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (Ptr GLdouble -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glWindowPos3dvMESA")
{-# NOINLINE glWindowPos3dvMESAFunPtr #-}
glWindowPos3fMESA :: MonadIO m => GLfloat -> GLfloat -> GLfloat -> m ()
glWindowPos3fMESA :: GLfloat -> GLfloat -> GLfloat -> m ()
glWindowPos3fMESA = FunPtr (GLfloat -> GLfloat -> GLfloat -> IO ())
-> GLfloat -> GLfloat -> GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLfloat -> GLfloat -> GLfloat -> IO ())
-> GLfloat -> GLfloat -> GLfloat -> m ()
ffifloatfloatfloatIOV FunPtr (GLfloat -> GLfloat -> GLfloat -> IO ())
glWindowPos3fMESAFunPtr
glWindowPos3fMESAFunPtr :: FunPtr (GLfloat -> GLfloat -> GLfloat -> IO ())
glWindowPos3fMESAFunPtr :: FunPtr (GLfloat -> GLfloat -> GLfloat -> IO ())
glWindowPos3fMESAFunPtr = IO (FunPtr (GLfloat -> GLfloat -> GLfloat -> IO ()))
-> FunPtr (GLfloat -> GLfloat -> GLfloat -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLfloat -> GLfloat -> GLfloat -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glWindowPos3fMESA")
{-# NOINLINE glWindowPos3fMESAFunPtr #-}
glWindowPos3fvMESA :: MonadIO m => Ptr GLfloat -> m ()
glWindowPos3fvMESA :: Ptr GLfloat -> m ()
glWindowPos3fvMESA = FunPtr (Ptr GLfloat -> IO ()) -> Ptr GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLfloat -> IO ()) -> Ptr GLfloat -> m ()
ffiPtrfloatIOV FunPtr (Ptr GLfloat -> IO ())
glWindowPos3fvMESAFunPtr
glWindowPos3fvMESAFunPtr :: FunPtr (Ptr GLfloat -> IO ())
glWindowPos3fvMESAFunPtr :: FunPtr (Ptr GLfloat -> IO ())
glWindowPos3fvMESAFunPtr = 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 "glWindowPos3fvMESA")
{-# NOINLINE glWindowPos3fvMESAFunPtr #-}
glWindowPos3iMESA :: MonadIO m => GLint -> GLint -> GLint -> m ()
glWindowPos3iMESA :: GLint -> GLint -> GLint -> m ()
glWindowPos3iMESA = FunPtr (GLint -> GLint -> GLint -> IO ())
-> GLint -> GLint -> GLint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLint -> GLint -> GLint -> IO ())
-> GLint -> GLint -> GLint -> m ()
ffiintintintIOV FunPtr (GLint -> GLint -> GLint -> IO ())
glWindowPos3iMESAFunPtr
glWindowPos3iMESAFunPtr :: FunPtr (GLint -> GLint -> GLint -> IO ())
glWindowPos3iMESAFunPtr :: FunPtr (GLint -> GLint -> GLint -> IO ())
glWindowPos3iMESAFunPtr = IO (FunPtr (GLint -> GLint -> GLint -> IO ()))
-> FunPtr (GLint -> GLint -> GLint -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLint -> GLint -> GLint -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glWindowPos3iMESA")
{-# NOINLINE glWindowPos3iMESAFunPtr #-}
glWindowPos3ivMESA :: MonadIO m => Ptr GLint -> m ()
glWindowPos3ivMESA :: Ptr GLint -> m ()
glWindowPos3ivMESA = FunPtr (Ptr GLint -> IO ()) -> Ptr GLint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLint -> IO ()) -> Ptr GLint -> m ()
ffiPtrintIOV FunPtr (Ptr GLint -> IO ())
glWindowPos3ivMESAFunPtr
glWindowPos3ivMESAFunPtr :: FunPtr (Ptr GLint -> IO ())
glWindowPos3ivMESAFunPtr :: FunPtr (Ptr GLint -> IO ())
glWindowPos3ivMESAFunPtr = 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 "glWindowPos3ivMESA")
{-# NOINLINE glWindowPos3ivMESAFunPtr #-}
glWindowPos3sMESA :: MonadIO m => GLshort -> GLshort -> GLshort -> m ()
glWindowPos3sMESA :: GLshort -> GLshort -> GLshort -> m ()
glWindowPos3sMESA = FunPtr (GLshort -> GLshort -> GLshort -> IO ())
-> GLshort -> GLshort -> GLshort -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLshort -> GLshort -> GLshort -> IO ())
-> GLshort -> GLshort -> GLshort -> m ()
ffishortshortshortIOV FunPtr (GLshort -> GLshort -> GLshort -> IO ())
glWindowPos3sMESAFunPtr
glWindowPos3sMESAFunPtr :: FunPtr (GLshort -> GLshort -> GLshort -> IO ())
glWindowPos3sMESAFunPtr :: FunPtr (GLshort -> GLshort -> GLshort -> IO ())
glWindowPos3sMESAFunPtr = IO (FunPtr (GLshort -> GLshort -> GLshort -> IO ()))
-> FunPtr (GLshort -> GLshort -> GLshort -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLshort -> GLshort -> GLshort -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glWindowPos3sMESA")
{-# NOINLINE glWindowPos3sMESAFunPtr #-}
glWindowPos3svMESA :: MonadIO m => Ptr GLshort -> m ()
glWindowPos3svMESA :: Ptr GLshort -> m ()
glWindowPos3svMESA = FunPtr (Ptr GLshort -> IO ()) -> Ptr GLshort -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLshort -> IO ()) -> Ptr GLshort -> m ()
ffiPtrshortIOV FunPtr (Ptr GLshort -> IO ())
glWindowPos3svMESAFunPtr
glWindowPos3svMESAFunPtr :: FunPtr (Ptr GLshort -> IO ())
glWindowPos3svMESAFunPtr :: FunPtr (Ptr GLshort -> IO ())
glWindowPos3svMESAFunPtr = 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 "glWindowPos3svMESA")
{-# NOINLINE glWindowPos3svMESAFunPtr #-}
glWindowPos4dMESA :: MonadIO m => GLdouble -> GLdouble -> GLdouble -> GLdouble -> m ()
glWindowPos4dMESA :: GLdouble -> GLdouble -> GLdouble -> GLdouble -> m ()
glWindowPos4dMESA = FunPtr (GLdouble -> GLdouble -> GLdouble -> GLdouble -> IO ())
-> GLdouble -> GLdouble -> GLdouble -> GLdouble -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLdouble -> GLdouble -> GLdouble -> GLdouble -> IO ())
-> GLdouble -> GLdouble -> GLdouble -> GLdouble -> m ()
ffidoubledoubledoubledoubleIOV FunPtr (GLdouble -> GLdouble -> GLdouble -> GLdouble -> IO ())
glWindowPos4dMESAFunPtr
glWindowPos4dMESAFunPtr :: FunPtr (GLdouble -> GLdouble -> GLdouble -> GLdouble -> IO ())
glWindowPos4dMESAFunPtr :: FunPtr (GLdouble -> GLdouble -> GLdouble -> GLdouble -> IO ())
glWindowPos4dMESAFunPtr = IO (FunPtr (GLdouble -> GLdouble -> GLdouble -> GLdouble -> IO ()))
-> FunPtr (GLdouble -> GLdouble -> GLdouble -> GLdouble -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char]
-> IO
(FunPtr (GLdouble -> GLdouble -> GLdouble -> GLdouble -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glWindowPos4dMESA")
{-# NOINLINE glWindowPos4dMESAFunPtr #-}
glWindowPos4dvMESA :: MonadIO m => Ptr GLdouble -> m ()
glWindowPos4dvMESA :: Ptr GLdouble -> m ()
glWindowPos4dvMESA = FunPtr (Ptr GLdouble -> IO ()) -> Ptr GLdouble -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLdouble -> IO ()) -> Ptr GLdouble -> m ()
ffiPtrdoubleIOV FunPtr (Ptr GLdouble -> IO ())
glWindowPos4dvMESAFunPtr
glWindowPos4dvMESAFunPtr :: FunPtr (Ptr GLdouble -> IO ())
glWindowPos4dvMESAFunPtr :: FunPtr (Ptr GLdouble -> IO ())
glWindowPos4dvMESAFunPtr = IO (FunPtr (Ptr GLdouble -> IO ()))
-> FunPtr (Ptr GLdouble -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (Ptr GLdouble -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glWindowPos4dvMESA")
{-# NOINLINE glWindowPos4dvMESAFunPtr #-}
glWindowPos4fMESA :: MonadIO m => GLfloat -> GLfloat -> GLfloat -> GLfloat -> m ()
glWindowPos4fMESA :: GLfloat -> GLfloat -> GLfloat -> GLfloat -> m ()
glWindowPos4fMESA = FunPtr (GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
-> GLfloat -> GLfloat -> GLfloat -> GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
-> GLfloat -> GLfloat -> GLfloat -> GLfloat -> m ()
ffifloatfloatfloatfloatIOV FunPtr (GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
glWindowPos4fMESAFunPtr
glWindowPos4fMESAFunPtr :: FunPtr (GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
glWindowPos4fMESAFunPtr :: FunPtr (GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
glWindowPos4fMESAFunPtr = IO (FunPtr (GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ()))
-> FunPtr (GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char]
-> IO (FunPtr (GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glWindowPos4fMESA")
{-# NOINLINE glWindowPos4fMESAFunPtr #-}
glWindowPos4fvMESA :: MonadIO m => Ptr GLfloat -> m ()
glWindowPos4fvMESA :: Ptr GLfloat -> m ()
glWindowPos4fvMESA = FunPtr (Ptr GLfloat -> IO ()) -> Ptr GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLfloat -> IO ()) -> Ptr GLfloat -> m ()
ffiPtrfloatIOV FunPtr (Ptr GLfloat -> IO ())
glWindowPos4fvMESAFunPtr
glWindowPos4fvMESAFunPtr :: FunPtr (Ptr GLfloat -> IO ())
glWindowPos4fvMESAFunPtr :: FunPtr (Ptr GLfloat -> IO ())
glWindowPos4fvMESAFunPtr = 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 "glWindowPos4fvMESA")
{-# NOINLINE glWindowPos4fvMESAFunPtr #-}
glWindowPos4iMESA :: MonadIO m => GLint -> GLint -> GLint -> GLint -> m ()
glWindowPos4iMESA :: GLint -> GLint -> GLint -> GLint -> m ()
glWindowPos4iMESA = FunPtr (GLint -> GLint -> GLint -> GLint -> IO ())
-> GLint -> GLint -> GLint -> GLint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLint -> GLint -> GLint -> GLint -> IO ())
-> GLint -> GLint -> GLint -> GLint -> m ()
ffiintintintintIOV FunPtr (GLint -> GLint -> GLint -> GLint -> IO ())
glWindowPos4iMESAFunPtr
glWindowPos4iMESAFunPtr :: FunPtr (GLint -> GLint -> GLint -> GLint -> IO ())
glWindowPos4iMESAFunPtr :: FunPtr (GLint -> GLint -> GLint -> GLint -> IO ())
glWindowPos4iMESAFunPtr = IO (FunPtr (GLint -> GLint -> GLint -> GLint -> IO ()))
-> FunPtr (GLint -> GLint -> GLint -> GLint -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char] -> IO (FunPtr (GLint -> GLint -> GLint -> GLint -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glWindowPos4iMESA")
{-# NOINLINE glWindowPos4iMESAFunPtr #-}
glWindowPos4ivMESA :: MonadIO m => Ptr GLint -> m ()
glWindowPos4ivMESA :: Ptr GLint -> m ()
glWindowPos4ivMESA = FunPtr (Ptr GLint -> IO ()) -> Ptr GLint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLint -> IO ()) -> Ptr GLint -> m ()
ffiPtrintIOV FunPtr (Ptr GLint -> IO ())
glWindowPos4ivMESAFunPtr
glWindowPos4ivMESAFunPtr :: FunPtr (Ptr GLint -> IO ())
glWindowPos4ivMESAFunPtr :: FunPtr (Ptr GLint -> IO ())
glWindowPos4ivMESAFunPtr = 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 "glWindowPos4ivMESA")
{-# NOINLINE glWindowPos4ivMESAFunPtr #-}
glWindowPos4sMESA :: MonadIO m => GLshort -> GLshort -> GLshort -> GLshort -> m ()
glWindowPos4sMESA :: GLshort -> GLshort -> GLshort -> GLshort -> m ()
glWindowPos4sMESA = FunPtr (GLshort -> GLshort -> GLshort -> GLshort -> IO ())
-> GLshort -> GLshort -> GLshort -> GLshort -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLshort -> GLshort -> GLshort -> GLshort -> IO ())
-> GLshort -> GLshort -> GLshort -> GLshort -> m ()
ffishortshortshortshortIOV FunPtr (GLshort -> GLshort -> GLshort -> GLshort -> IO ())
glWindowPos4sMESAFunPtr
glWindowPos4sMESAFunPtr :: FunPtr (GLshort -> GLshort -> GLshort -> GLshort -> IO ())
glWindowPos4sMESAFunPtr :: FunPtr (GLshort -> GLshort -> GLshort -> GLshort -> IO ())
glWindowPos4sMESAFunPtr = IO (FunPtr (GLshort -> GLshort -> GLshort -> GLshort -> IO ()))
-> FunPtr (GLshort -> GLshort -> GLshort -> GLshort -> IO ())
forall a. IO a -> a
unsafePerformIO ([Char]
-> IO (FunPtr (GLshort -> GLshort -> GLshort -> GLshort -> IO ()))
forall a. [Char] -> IO (FunPtr a)
getProcAddress "glWindowPos4sMESA")
{-# NOINLINE glWindowPos4sMESAFunPtr #-}
glWindowPos4svMESA :: MonadIO m => Ptr GLshort -> m ()
glWindowPos4svMESA :: Ptr GLshort -> m ()
glWindowPos4svMESA = FunPtr (Ptr GLshort -> IO ()) -> Ptr GLshort -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLshort -> IO ()) -> Ptr GLshort -> m ()
ffiPtrshortIOV FunPtr (Ptr GLshort -> IO ())
glWindowPos4svMESAFunPtr
glWindowPos4svMESAFunPtr :: FunPtr (Ptr GLshort -> IO ())
glWindowPos4svMESAFunPtr :: FunPtr (Ptr GLshort -> IO ())
glWindowPos4svMESAFunPtr = 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 "glWindowPos4svMESA")
{-# NOINLINE glWindowPos4svMESAFunPtr #-}