module Graphics.OpenGLES.Sync where
import Control.Applicative
import Control.Monad
import Data.IORef
import Foreign
import Graphics.OpenGLES.Base
import Graphics.OpenGLES.Internal
data Sync = Sync Word64 (IORef GLsync)
getSync :: Maybe Word64 -> IO Sync
getSync timeout_ns = Sync timeout <$> newIORef nullPtr
where
timeout = maybe timeoutIgnored id timeout_ns
timeoutIgnored = 0xFFFFFFFFFFFFFFFF
glFence :: Sync -> (Bool -> GL a) -> GL a
glFence sync io = do
isExpired <- waitFence False sync
result <- io isExpired
createFence sync
return result
glFenceInGpu :: Sync -> GL a -> GL a
glFenceInGpu sync io = do
waitFenceAtGpu sync
result <- io
createFence sync
return result
waitFence :: Bool -> Sync -> GL Bool
waitFence flushCmdQ (Sync timeout ref) = do
sync <- readIORef ref
if sync /= nullPtr then do
result <- glClientWaitSync sync flushBit timeout
glDeleteSync sync
writeIORef ref nullPtr
return $ case result of
0x911A -> False
0x911C -> False
0x911B -> True
0x911D -> error "glFence: WaitFailed"
_ -> error "glFence: InvalidValue"
else return False
where
flushBit = if flushCmdQ then 1 else 0
createFence :: Sync -> GL ()
createFence (Sync _ ref) = do
sync <- glFenceSync 0x9117 0
writeIORef ref sync
waitFenceAtGpu :: Sync -> GL ()
waitFenceAtGpu (Sync _ ref) = do
sync <- readIORef ref
when (sync /= nullPtr) $ do
result <- glWaitSync sync 0 0xFFFFFFFFFFFFFFFF
glDeleteSync sync
writeIORef ref nullPtr
glFlushCommandQ :: GL ()
glFlushCommandQ = glFlush
glWaitComplete :: GL ()
glWaitComplete = glFinish