module Graphics.Rendering.OpenGL.Raw.GetProcAddress (
getProcAddress,
getProcAddressWithSuffixes,
getExtension,
getProcAddressChecked,
getProcAddressWithSuffixesChecked,
getExtensionChecked
) where
import Control.Monad.IO.Class ( MonadIO(..) )
import Foreign.C.String ( withCString, CString )
import Foreign.Marshal.Error ( throwIf )
import Foreign.Ptr ( FunPtr, nullFunPtr )
#ifdef __HUGS__
#endif
getProcAddress :: MonadIO m => String -> m (FunPtr a)
getProcAddress cmd = liftIO $ withCString cmd hs_OpenGLRaw_getProcAddress
foreign import ccall unsafe "hs_OpenGLRaw_getProcAddress"
hs_OpenGLRaw_getProcAddress :: CString -> IO (FunPtr a)
getProcAddressChecked :: MonadIO m => String -> m (FunPtr a)
getProcAddressChecked cmd = liftIO $ check cmd $ getProcAddress cmd
getProcAddressWithSuffixes :: MonadIO m => String -> [String] -> m (FunPtr a)
getProcAddressWithSuffixes _ [] = return nullFunPtr
getProcAddressWithSuffixes cmd (x:xs) = do
p <- getProcAddress (cmd ++ x)
if p == nullFunPtr
then getProcAddressWithSuffixes cmd xs
else return p
getProcAddressWithSuffixesChecked :: MonadIO m
=> String -> [String] -> m (FunPtr a)
getProcAddressWithSuffixesChecked cmd suffixes =
liftIO $ check cmd $ getProcAddressWithSuffixes cmd suffixes
getExtension :: MonadIO m => String -> m (FunPtr a)
getExtension cmd = liftIO $ getProcAddressWithSuffixes cmd vendorSuffixes
getExtensionChecked :: MonadIO m => String -> m (FunPtr a)
getExtensionChecked cmd =
liftIO $ getProcAddressWithSuffixesChecked cmd vendorSuffixes
check :: String -> IO (FunPtr a) -> IO (FunPtr a)
check = throwIfNullFunPtr . ("unknown OpenGL command " ++)
throwIfNullFunPtr :: String -> IO (FunPtr a) -> IO (FunPtr a)
throwIfNullFunPtr = throwIf (== nullFunPtr) . const
vendorSuffixes :: [String]
vendorSuffixes = [
"",
"ARB", "KHR", "OES",
"EXT",
"NV", "SGIX", "AMD", "APPLE", "ATI", "SGIS", "ANGLE", "QCOM", "IMG", "SUN",
"IBM", "ARM", "MESA", "INTEL", "HP", "SGI", "OML", "INGR", "3DFX", "WIN",
"PGI", "NVX", "GREMEDY", "DMP", "VIV", "SUNX", "S3", "REND", "MESAX", "FJ",
"ANDROID" ]