{-# LANGUAGE CPP, ScopedTypeVariables, PatternSynonyms #-}
module Graphics.GL.Ext.SUN.GlobalAlpha (
gl_SUN_global_alpha
, glGlobalAlphaFactorbSUN
, glGlobalAlphaFactordSUN
, glGlobalAlphaFactorfSUN
, glGlobalAlphaFactoriSUN
, glGlobalAlphaFactorsSUN
, glGlobalAlphaFactorubSUN
, glGlobalAlphaFactoruiSUN
, glGlobalAlphaFactorusSUN
, pattern GL_GLOBAL_ALPHA_FACTOR_SUN
, pattern GL_GLOBAL_ALPHA_SUN
) 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_SUN_global_alpha :: Bool
gl_SUN_global_alpha :: Bool
gl_SUN_global_alpha = String -> Set String -> Bool
forall a. Ord a => a -> Set a -> Bool
member String
"GL_SUN_global_alpha" Set String
extensions
{-# NOINLINE gl_SUN_global_alpha #-}
glGlobalAlphaFactorbSUN :: MonadIO m => GLbyte -> m ()
glGlobalAlphaFactorbSUN :: forall (m :: * -> *). MonadIO m => GLbyte -> m ()
glGlobalAlphaFactorbSUN = FunPtr (GLbyte -> IO ()) -> GLbyte -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLbyte -> IO ()) -> GLbyte -> m ()
ffibyteIOV FunPtr (GLbyte -> IO ())
glGlobalAlphaFactorbSUNFunPtr
glGlobalAlphaFactorbSUNFunPtr :: FunPtr (GLbyte -> IO ())
glGlobalAlphaFactorbSUNFunPtr :: FunPtr (GLbyte -> IO ())
glGlobalAlphaFactorbSUNFunPtr = IO (FunPtr (GLbyte -> IO ())) -> FunPtr (GLbyte -> IO ())
forall a. IO a -> a
unsafePerformIO (String -> IO (FunPtr (GLbyte -> IO ()))
forall a. String -> IO (FunPtr a)
getProcAddress String
"glGlobalAlphaFactorbSUN")
{-# NOINLINE glGlobalAlphaFactorbSUNFunPtr #-}
glGlobalAlphaFactordSUN :: MonadIO m => GLdouble -> m ()
glGlobalAlphaFactordSUN :: forall (m :: * -> *). MonadIO m => GLdouble -> m ()
glGlobalAlphaFactordSUN = FunPtr (GLdouble -> IO ()) -> GLdouble -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLdouble -> IO ()) -> GLdouble -> m ()
ffidoubleIOV FunPtr (GLdouble -> IO ())
glGlobalAlphaFactordSUNFunPtr
glGlobalAlphaFactordSUNFunPtr :: FunPtr (GLdouble -> IO ())
glGlobalAlphaFactordSUNFunPtr :: FunPtr (GLdouble -> IO ())
glGlobalAlphaFactordSUNFunPtr = IO (FunPtr (GLdouble -> IO ())) -> FunPtr (GLdouble -> IO ())
forall a. IO a -> a
unsafePerformIO (String -> IO (FunPtr (GLdouble -> IO ()))
forall a. String -> IO (FunPtr a)
getProcAddress String
"glGlobalAlphaFactordSUN")
{-# NOINLINE glGlobalAlphaFactordSUNFunPtr #-}
glGlobalAlphaFactorfSUN :: MonadIO m => GLfloat -> m ()
glGlobalAlphaFactorfSUN :: forall (m :: * -> *). MonadIO m => GLfloat -> m ()
glGlobalAlphaFactorfSUN = FunPtr (GLfloat -> IO ()) -> GLfloat -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLfloat -> IO ()) -> GLfloat -> m ()
ffifloatIOV FunPtr (GLfloat -> IO ())
glGlobalAlphaFactorfSUNFunPtr
glGlobalAlphaFactorfSUNFunPtr :: FunPtr (GLfloat -> IO ())
glGlobalAlphaFactorfSUNFunPtr :: FunPtr (GLfloat -> IO ())
glGlobalAlphaFactorfSUNFunPtr = IO (FunPtr (GLfloat -> IO ())) -> FunPtr (GLfloat -> IO ())
forall a. IO a -> a
unsafePerformIO (String -> IO (FunPtr (GLfloat -> IO ()))
forall a. String -> IO (FunPtr a)
getProcAddress String
"glGlobalAlphaFactorfSUN")
{-# NOINLINE glGlobalAlphaFactorfSUNFunPtr #-}
glGlobalAlphaFactoriSUN :: MonadIO m => GLint -> m ()
glGlobalAlphaFactoriSUN :: forall (m :: * -> *). MonadIO m => GLint -> m ()
glGlobalAlphaFactoriSUN = FunPtr (GLint -> IO ()) -> GLint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLint -> IO ()) -> GLint -> m ()
ffiintIOV FunPtr (GLint -> IO ())
glGlobalAlphaFactoriSUNFunPtr
glGlobalAlphaFactoriSUNFunPtr :: FunPtr (GLint -> IO ())
glGlobalAlphaFactoriSUNFunPtr :: FunPtr (GLint -> IO ())
glGlobalAlphaFactoriSUNFunPtr = IO (FunPtr (GLint -> IO ())) -> FunPtr (GLint -> IO ())
forall a. IO a -> a
unsafePerformIO (String -> IO (FunPtr (GLint -> IO ()))
forall a. String -> IO (FunPtr a)
getProcAddress String
"glGlobalAlphaFactoriSUN")
{-# NOINLINE glGlobalAlphaFactoriSUNFunPtr #-}
glGlobalAlphaFactorsSUN :: MonadIO m => GLshort -> m ()
= FunPtr (GLshort -> IO ()) -> GLshort -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLshort -> IO ()) -> GLshort -> m ()
ffishortIOV FunPtr (GLshort -> IO ())
glGlobalAlphaFactorsSUNFunPtr
glGlobalAlphaFactorsSUNFunPtr :: FunPtr (GLshort -> IO ())
= IO (FunPtr (GLshort -> IO ())) -> FunPtr (GLshort -> IO ())
forall a. IO a -> a
unsafePerformIO (String -> IO (FunPtr (GLshort -> IO ()))
forall a. String -> IO (FunPtr a)
getProcAddress String
"glGlobalAlphaFactorsSUN")
{-# NOINLINE glGlobalAlphaFactorsSUNFunPtr #-}
glGlobalAlphaFactorubSUN :: MonadIO m => GLubyte -> m ()
glGlobalAlphaFactorubSUN :: forall (m :: * -> *). MonadIO m => GLubyte -> m ()
glGlobalAlphaFactorubSUN = FunPtr (GLubyte -> IO ()) -> GLubyte -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLubyte -> IO ()) -> GLubyte -> m ()
ffiubyteIOV FunPtr (GLubyte -> IO ())
glGlobalAlphaFactorubSUNFunPtr
glGlobalAlphaFactorubSUNFunPtr :: FunPtr (GLubyte -> IO ())
glGlobalAlphaFactorubSUNFunPtr :: FunPtr (GLubyte -> IO ())
glGlobalAlphaFactorubSUNFunPtr = IO (FunPtr (GLubyte -> IO ())) -> FunPtr (GLubyte -> IO ())
forall a. IO a -> a
unsafePerformIO (String -> IO (FunPtr (GLubyte -> IO ()))
forall a. String -> IO (FunPtr a)
getProcAddress String
"glGlobalAlphaFactorubSUN")
{-# NOINLINE glGlobalAlphaFactorubSUNFunPtr #-}
glGlobalAlphaFactoruiSUN :: MonadIO m => GLuint -> m ()
glGlobalAlphaFactoruiSUN :: forall (m :: * -> *). MonadIO m => GLuint -> m ()
glGlobalAlphaFactoruiSUN = FunPtr (GLuint -> IO ()) -> GLuint -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLuint -> IO ()) -> GLuint -> m ()
ffiuintIOV FunPtr (GLuint -> IO ())
glGlobalAlphaFactoruiSUNFunPtr
glGlobalAlphaFactoruiSUNFunPtr :: FunPtr (GLuint -> IO ())
glGlobalAlphaFactoruiSUNFunPtr :: FunPtr (GLuint -> IO ())
glGlobalAlphaFactoruiSUNFunPtr = IO (FunPtr (GLuint -> IO ())) -> FunPtr (GLuint -> IO ())
forall a. IO a -> a
unsafePerformIO (String -> IO (FunPtr (GLuint -> IO ()))
forall a. String -> IO (FunPtr a)
getProcAddress String
"glGlobalAlphaFactoruiSUN")
{-# NOINLINE glGlobalAlphaFactoruiSUNFunPtr #-}
glGlobalAlphaFactorusSUN :: MonadIO m => GLushort -> m ()
glGlobalAlphaFactorusSUN :: forall (m :: * -> *). MonadIO m => GLushort -> m ()
glGlobalAlphaFactorusSUN = FunPtr (GLushort -> IO ()) -> GLushort -> m ()
forall (m :: * -> *).
MonadIO m =>
FunPtr (GLushort -> IO ()) -> GLushort -> m ()
ffiushortIOV FunPtr (GLushort -> IO ())
glGlobalAlphaFactorusSUNFunPtr
glGlobalAlphaFactorusSUNFunPtr :: FunPtr (GLushort -> IO ())
glGlobalAlphaFactorusSUNFunPtr :: FunPtr (GLushort -> IO ())
glGlobalAlphaFactorusSUNFunPtr = IO (FunPtr (GLushort -> IO ())) -> FunPtr (GLushort -> IO ())
forall a. IO a -> a
unsafePerformIO (String -> IO (FunPtr (GLushort -> IO ()))
forall a. String -> IO (FunPtr a)
getProcAddress String
"glGlobalAlphaFactorusSUN")
{-# NOINLINE glGlobalAlphaFactorusSUNFunPtr #-}
pattern GL_GLOBAL_ALPHA_FACTOR_SUN :: (Eq a, Num a) => a
pattern $mGL_GLOBAL_ALPHA_FACTOR_SUN :: forall {r} {a}.
(Eq a, Num a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
$bGL_GLOBAL_ALPHA_FACTOR_SUN :: forall a. (Eq a, Num a) => a
GL_GLOBAL_ALPHA_FACTOR_SUN = 0x81DA
pattern GL_GLOBAL_ALPHA_SUN :: (Eq a, Num a) => a
pattern $mGL_GLOBAL_ALPHA_SUN :: forall {r} {a}.
(Eq a, Num a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
$bGL_GLOBAL_ALPHA_SUN :: forall a. (Eq a, Num a) => a
GL_GLOBAL_ALPHA_SUN = 0x81D9