module Graphics.GPipe.Context.GLFW
( newContext,
GLFWWindow(),
getCursorPos, getMouseButton, getKey, windowShouldClose,
MouseButtonState(..), MouseButton(..), KeyState(..), Key(..),
) where
import qualified Control.Concurrent as C
import qualified Graphics.GPipe.Context.GLFW.Format as Format
import qualified Graphics.GPipe.Context.GLFW.Resource as Resource
import qualified Graphics.GPipe.Context.GLFW.Util as Util
import qualified Graphics.UI.GLFW as GLFW (getCursorPos, getMouseButton, getKey, windowShouldClose, makeContextCurrent, destroyWindow, pollEvents)
import Control.Monad.IO.Class (MonadIO)
import Graphics.GPipe.Context (ContextFactory, ContextHandle(..),ContextT,withContextWindow)
import Graphics.UI.GLFW (MouseButtonState(..), MouseButton(..), KeyState(..), Key(..))
import Data.IORef
import Control.Monad (when)
data Message where
ReqShutDown :: C.MVar () -> Message
ReqExecuteSync :: forall a. IO a -> C.MVar a -> Message
ReqExecuteAsync :: IO () -> Message
newtype GLFWWindow = GLFWWindow { unGLFWWindow :: Resource.Window }
newContext :: ContextFactory c ds GLFWWindow
newContext fmt = do
chReply <- C.newEmptyMVar
_ <- C.forkOS $ begin chReply
msgC <- C.takeMVar chReply
h <- createContext msgC Nothing fmt
contextDoAsync h True (return ())
return h
createContext :: C.Chan Message -> Maybe Resource.Window -> ContextFactory c ds GLFWWindow
createContext msgC share fmt = do
w <- makeContext share
GLFW.makeContextCurrent Nothing
alive <- newIORef True
return ContextHandle
{ newSharedContext = mainthreadDoWhileContextUncurrent msgC w . createContext msgC (Just w)
, contextDoSync = contextDoSyncImpl w msgC
, contextDoAsync = contextDoAsyncImpl alive w msgC
, contextSwap = contextDoSyncImpl w msgC False $ Util.swapBuffers w
, contextFrameBufferSize = Util.getFramebufferSize w
, contextDelete = case share of
Nothing -> do contextDeleteImpl msgC
GLFW.destroyWindow w
Just parentW -> mainthreadDoWhileContextUncurrent msgC parentW (writeIORef alive False >> GLFW.destroyWindow w)
, contextWindow = GLFWWindow w
}
where
hints = Format.toHints fmt
makeContext :: Maybe Resource.Window -> IO Resource.Window
makeContext Nothing = Resource.newContext Nothing hints Nothing
makeContext (Just s) = Resource.newSharedContext s hints Nothing
begin :: C.MVar (C.Chan Message) -> IO ()
begin chReply = do
msgC <- C.newChan
C.putMVar chReply msgC
loop msgC
loop :: C.Chan Message -> IO ()
loop msgC = do
msg <- C.readChan msgC
case msg of
ReqShutDown reply -> GLFW.makeContextCurrent Nothing >> C.putMVar reply ()
ReqExecuteSync action reply -> action >>= C.putMVar reply >> loop msgC
ReqExecuteAsync action -> action >> loop msgC
contextDoSyncImpl :: Resource.Window -> C.Chan Message -> Bool -> IO a -> IO a
contextDoSyncImpl w msgC inwin action = do
reply <- C.newEmptyMVar
C.writeChan msgC $ ReqExecuteSync (do when inwin (GLFW.makeContextCurrent (Just w))
action)
reply
GLFW.pollEvents
C.takeMVar reply
contextDoAsyncImpl :: IORef Bool -> Resource.Window -> C.Chan Message -> Bool -> IO () -> IO ()
contextDoAsyncImpl alive w msgC inwin action =
C.writeChan msgC $ ReqExecuteAsync $ if inwin
then do
alive' <- readIORef alive
when alive' $ do
GLFW.makeContextCurrent (Just w)
action
else
action
mainthreadDoWhileContextUncurrent :: C.Chan Message -> Resource.Window -> IO a -> IO a
mainthreadDoWhileContextUncurrent msgC w mainAction = do
syncMainWait <- C.newEmptyMVar
syncRendWait <- C.newEmptyMVar
let m = do GLFW.makeContextCurrent Nothing
C.putMVar syncMainWait ()
C.takeMVar syncRendWait
GLFW.makeContextCurrent (Just w)
C.writeChan msgC $ ReqExecuteAsync m
C.takeMVar syncMainWait
ret <- mainAction
C.putMVar syncRendWait ()
return ret
contextDeleteImpl :: C.Chan Message -> IO ()
contextDeleteImpl msgC = do
syncMainWait <- C.newEmptyMVar
C.writeChan msgC $ ReqShutDown syncMainWait
C.takeMVar syncMainWait
getCursorPos :: MonadIO m => ContextT GLFWWindow os f m (Double, Double)
getCursorPos = withContextWindow (GLFW.getCursorPos . unGLFWWindow)
getMouseButton :: MonadIO m => MouseButton -> ContextT GLFWWindow os f m MouseButtonState
getMouseButton mb = withContextWindow (\(GLFWWindow w) -> GLFW.getMouseButton w mb)
getKey :: MonadIO m => Key -> ContextT GLFWWindow os f m KeyState
getKey k = withContextWindow (\(GLFWWindow w) -> GLFW.getKey w k)
windowShouldClose :: MonadIO m => ContextT GLFWWindow os f m Bool
windowShouldClose = withContextWindow (GLFW.windowShouldClose . unGLFWWindow)