{-# LANGUAGE CPP, ScopedTypeVariables, PatternSynonyms #-}
module Graphics.GL.Ext.ARB.WindowPos (
gl_ARB_window_pos
, glWindowPos2dARB
, glWindowPos2dvARB
, glWindowPos2fARB
, glWindowPos2fvARB
, glWindowPos2iARB
, glWindowPos2ivARB
, glWindowPos2sARB
, glWindowPos2svARB
, glWindowPos3dARB
, glWindowPos3dvARB
, glWindowPos3fARB
, glWindowPos3fvARB
, glWindowPos3iARB
, glWindowPos3ivARB
, glWindowPos3sARB
, glWindowPos3svARB
) 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_ARB_window_pos :: Bool
gl_ARB_window_pos :: Bool
gl_ARB_window_pos = [Char] -> Set [Char] -> Bool
forall a. Ord a => a -> Set a -> Bool
member "GL_ARB_window_pos" Set [Char]
extensions
{-# NOINLINE gl_ARB_window_pos #-}
glWindowPos2dARB :: MonadIO m => GLdouble -> GLdouble -> m ()
glWindowPos2dARB :: GLdouble -> GLdouble -> m ()
glWindowPos2dARB = FunPtr (GLdouble -> GLdouble -> IO ())
-> GLdouble -> GLdouble -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLdouble -> GLdouble -> IO ())
-> GLdouble -> GLdouble -> m ()
ffidoubledoubleIOV FunPtr (GLdouble -> GLdouble -> IO ())
glWindowPos2dARBFunPtr
glWindowPos2dARBFunPtr :: FunPtr (GLdouble -> GLdouble -> IO ())
glWindowPos2dARBFunPtr :: FunPtr (GLdouble -> GLdouble -> IO ())
glWindowPos2dARBFunPtr = 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 "glWindowPos2dARB")
{-# NOINLINE glWindowPos2dARBFunPtr #-}
glWindowPos2dvARB :: MonadIO m => Ptr GLdouble -> m ()
glWindowPos2dvARB :: Ptr GLdouble -> m ()
glWindowPos2dvARB = FunPtr (Ptr GLdouble -> IO ()) -> Ptr GLdouble -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLdouble -> IO ()) -> Ptr GLdouble -> m ()
ffiPtrdoubleIOV FunPtr (Ptr GLdouble -> IO ())
glWindowPos2dvARBFunPtr
glWindowPos2dvARBFunPtr :: FunPtr (Ptr GLdouble -> IO ())
glWindowPos2dvARBFunPtr :: FunPtr (Ptr GLdouble -> IO ())
glWindowPos2dvARBFunPtr = 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 "glWindowPos2dvARB")
{-# NOINLINE glWindowPos2dvARBFunPtr #-}
glWindowPos2fARB :: MonadIO m => GLfloat -> GLfloat -> m ()
glWindowPos2fARB :: GLfloat -> GLfloat -> m ()
glWindowPos2fARB = FunPtr (GLfloat -> GLfloat -> IO ()) -> GLfloat -> GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLfloat -> GLfloat -> IO ()) -> GLfloat -> GLfloat -> m ()
ffifloatfloatIOV FunPtr (GLfloat -> GLfloat -> IO ())
glWindowPos2fARBFunPtr
glWindowPos2fARBFunPtr :: FunPtr (GLfloat -> GLfloat -> IO ())
glWindowPos2fARBFunPtr :: FunPtr (GLfloat -> GLfloat -> IO ())
glWindowPos2fARBFunPtr = 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 "glWindowPos2fARB")
{-# NOINLINE glWindowPos2fARBFunPtr #-}
glWindowPos2fvARB :: MonadIO m => Ptr GLfloat -> m ()
glWindowPos2fvARB :: Ptr GLfloat -> m ()
glWindowPos2fvARB = FunPtr (Ptr GLfloat -> IO ()) -> Ptr GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLfloat -> IO ()) -> Ptr GLfloat -> m ()
ffiPtrfloatIOV FunPtr (Ptr GLfloat -> IO ())
glWindowPos2fvARBFunPtr
glWindowPos2fvARBFunPtr :: FunPtr (Ptr GLfloat -> IO ())
glWindowPos2fvARBFunPtr :: FunPtr (Ptr GLfloat -> IO ())
glWindowPos2fvARBFunPtr = 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 "glWindowPos2fvARB")
{-# NOINLINE glWindowPos2fvARBFunPtr #-}
glWindowPos2iARB :: MonadIO m => GLint -> GLint -> m ()
glWindowPos2iARB :: GLint -> GLint -> m ()
glWindowPos2iARB = FunPtr (GLint -> GLint -> IO ()) -> GLint -> GLint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLint -> GLint -> IO ()) -> GLint -> GLint -> m ()
ffiintintIOV FunPtr (GLint -> GLint -> IO ())
glWindowPos2iARBFunPtr
glWindowPos2iARBFunPtr :: FunPtr (GLint -> GLint -> IO ())
glWindowPos2iARBFunPtr :: FunPtr (GLint -> GLint -> IO ())
glWindowPos2iARBFunPtr = 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 "glWindowPos2iARB")
{-# NOINLINE glWindowPos2iARBFunPtr #-}
glWindowPos2ivARB :: MonadIO m => Ptr GLint -> m ()
glWindowPos2ivARB :: Ptr GLint -> m ()
glWindowPos2ivARB = FunPtr (Ptr GLint -> IO ()) -> Ptr GLint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLint -> IO ()) -> Ptr GLint -> m ()
ffiPtrintIOV FunPtr (Ptr GLint -> IO ())
glWindowPos2ivARBFunPtr
glWindowPos2ivARBFunPtr :: FunPtr (Ptr GLint -> IO ())
glWindowPos2ivARBFunPtr :: FunPtr (Ptr GLint -> IO ())
glWindowPos2ivARBFunPtr = 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 "glWindowPos2ivARB")
{-# NOINLINE glWindowPos2ivARBFunPtr #-}
glWindowPos2sARB :: MonadIO m => GLshort -> GLshort -> m ()
glWindowPos2sARB :: GLshort -> GLshort -> m ()
glWindowPos2sARB = FunPtr (GLshort -> GLshort -> IO ()) -> GLshort -> GLshort -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLshort -> GLshort -> IO ()) -> GLshort -> GLshort -> m ()
ffishortshortIOV FunPtr (GLshort -> GLshort -> IO ())
glWindowPos2sARBFunPtr
glWindowPos2sARBFunPtr :: FunPtr (GLshort -> GLshort -> IO ())
glWindowPos2sARBFunPtr :: FunPtr (GLshort -> GLshort -> IO ())
glWindowPos2sARBFunPtr = 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 "glWindowPos2sARB")
{-# NOINLINE glWindowPos2sARBFunPtr #-}
glWindowPos2svARB :: MonadIO m => Ptr GLshort -> m ()
glWindowPos2svARB :: Ptr GLshort -> m ()
glWindowPos2svARB = FunPtr (Ptr GLshort -> IO ()) -> Ptr GLshort -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLshort -> IO ()) -> Ptr GLshort -> m ()
ffiPtrshortIOV FunPtr (Ptr GLshort -> IO ())
glWindowPos2svARBFunPtr
glWindowPos2svARBFunPtr :: FunPtr (Ptr GLshort -> IO ())
glWindowPos2svARBFunPtr :: FunPtr (Ptr GLshort -> IO ())
glWindowPos2svARBFunPtr = 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 "glWindowPos2svARB")
{-# NOINLINE glWindowPos2svARBFunPtr #-}
glWindowPos3dARB :: MonadIO m => GLdouble -> GLdouble -> GLdouble -> m ()
glWindowPos3dARB :: GLdouble -> GLdouble -> GLdouble -> m ()
glWindowPos3dARB = 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 ())
glWindowPos3dARBFunPtr
glWindowPos3dARBFunPtr :: FunPtr (GLdouble -> GLdouble -> GLdouble -> IO ())
glWindowPos3dARBFunPtr :: FunPtr (GLdouble -> GLdouble -> GLdouble -> IO ())
glWindowPos3dARBFunPtr = 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 "glWindowPos3dARB")
{-# NOINLINE glWindowPos3dARBFunPtr #-}
glWindowPos3dvARB :: MonadIO m => Ptr GLdouble -> m ()
glWindowPos3dvARB :: Ptr GLdouble -> m ()
glWindowPos3dvARB = FunPtr (Ptr GLdouble -> IO ()) -> Ptr GLdouble -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLdouble -> IO ()) -> Ptr GLdouble -> m ()
ffiPtrdoubleIOV FunPtr (Ptr GLdouble -> IO ())
glWindowPos3dvARBFunPtr
glWindowPos3dvARBFunPtr :: FunPtr (Ptr GLdouble -> IO ())
glWindowPos3dvARBFunPtr :: FunPtr (Ptr GLdouble -> IO ())
glWindowPos3dvARBFunPtr = 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 "glWindowPos3dvARB")
{-# NOINLINE glWindowPos3dvARBFunPtr #-}
glWindowPos3fARB :: MonadIO m => GLfloat -> GLfloat -> GLfloat -> m ()
glWindowPos3fARB :: GLfloat -> GLfloat -> GLfloat -> m ()
glWindowPos3fARB = 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 ())
glWindowPos3fARBFunPtr
glWindowPos3fARBFunPtr :: FunPtr (GLfloat -> GLfloat -> GLfloat -> IO ())
glWindowPos3fARBFunPtr :: FunPtr (GLfloat -> GLfloat -> GLfloat -> IO ())
glWindowPos3fARBFunPtr = 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 "glWindowPos3fARB")
{-# NOINLINE glWindowPos3fARBFunPtr #-}
glWindowPos3fvARB :: MonadIO m => Ptr GLfloat -> m ()
glWindowPos3fvARB :: Ptr GLfloat -> m ()
glWindowPos3fvARB = FunPtr (Ptr GLfloat -> IO ()) -> Ptr GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLfloat -> IO ()) -> Ptr GLfloat -> m ()
ffiPtrfloatIOV FunPtr (Ptr GLfloat -> IO ())
glWindowPos3fvARBFunPtr
glWindowPos3fvARBFunPtr :: FunPtr (Ptr GLfloat -> IO ())
glWindowPos3fvARBFunPtr :: FunPtr (Ptr GLfloat -> IO ())
glWindowPos3fvARBFunPtr = 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 "glWindowPos3fvARB")
{-# NOINLINE glWindowPos3fvARBFunPtr #-}
glWindowPos3iARB :: MonadIO m => GLint -> GLint -> GLint -> m ()
glWindowPos3iARB :: GLint -> GLint -> GLint -> m ()
glWindowPos3iARB = 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 ())
glWindowPos3iARBFunPtr
glWindowPos3iARBFunPtr :: FunPtr (GLint -> GLint -> GLint -> IO ())
glWindowPos3iARBFunPtr :: FunPtr (GLint -> GLint -> GLint -> IO ())
glWindowPos3iARBFunPtr = 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 "glWindowPos3iARB")
{-# NOINLINE glWindowPos3iARBFunPtr #-}
glWindowPos3ivARB :: MonadIO m => Ptr GLint -> m ()
glWindowPos3ivARB :: Ptr GLint -> m ()
glWindowPos3ivARB = FunPtr (Ptr GLint -> IO ()) -> Ptr GLint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLint -> IO ()) -> Ptr GLint -> m ()
ffiPtrintIOV FunPtr (Ptr GLint -> IO ())
glWindowPos3ivARBFunPtr
glWindowPos3ivARBFunPtr :: FunPtr (Ptr GLint -> IO ())
glWindowPos3ivARBFunPtr :: FunPtr (Ptr GLint -> IO ())
glWindowPos3ivARBFunPtr = 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 "glWindowPos3ivARB")
{-# NOINLINE glWindowPos3ivARBFunPtr #-}
glWindowPos3sARB :: MonadIO m => GLshort -> GLshort -> GLshort -> m ()
glWindowPos3sARB :: GLshort -> GLshort -> GLshort -> m ()
glWindowPos3sARB = 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 ())
glWindowPos3sARBFunPtr
glWindowPos3sARBFunPtr :: FunPtr (GLshort -> GLshort -> GLshort -> IO ())
glWindowPos3sARBFunPtr :: FunPtr (GLshort -> GLshort -> GLshort -> IO ())
glWindowPos3sARBFunPtr = 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 "glWindowPos3sARB")
{-# NOINLINE glWindowPos3sARBFunPtr #-}
glWindowPos3svARB :: MonadIO m => Ptr GLshort -> m ()
glWindowPos3svARB :: Ptr GLshort -> m ()
glWindowPos3svARB = FunPtr (Ptr GLshort -> IO ()) -> Ptr GLshort -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (Ptr GLshort -> IO ()) -> Ptr GLshort -> m ()
ffiPtrshortIOV FunPtr (Ptr GLshort -> IO ())
glWindowPos3svARBFunPtr
glWindowPos3svARBFunPtr :: FunPtr (Ptr GLshort -> IO ())
glWindowPos3svARBFunPtr :: FunPtr (Ptr GLshort -> IO ())
glWindowPos3svARBFunPtr = 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 "glWindowPos3svARB")
{-# NOINLINE glWindowPos3svARBFunPtr #-}