{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
module Graphics.GPipe.Context.GLFW.Handler where
import Control.Monad (forM_, forM)
import Text.Printf (printf)
import Data.List (partition, delete)
import Data.Maybe (fromMaybe)
import Control.Monad (when, unless, void)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Exception (Exception, throwIO)
import Control.Concurrent.Async (withAsync)
import Control.Concurrent.STM (atomically)
import Control.Concurrent.STM.TVar
( TVar, newTVarIO, readTVarIO, writeTVar, modifyTVar
)
import Control.Concurrent
( MVar, newMVar, modifyMVar_, withMVar
, ThreadId, myThreadId
)
import qualified Graphics.GPipe as GPipe (ContextHandler(..), Window(), ContextT(), WindowBits, withContextWindow)
import qualified Graphics.UI.GLFW as GLFW (Window, Error)
import qualified Graphics.GPipe.Context.GLFW.Calls as Call
import qualified Graphics.GPipe.Context.GLFW.Format as Format
import qualified Graphics.GPipe.Context.GLFW.RPC as RPC
import qualified Graphics.GPipe.Context.GLFW.Resource as Resource
import Graphics.GPipe.Context.GLFW.Resource (defaultWindowConfig)
bug :: String -> IO ()
bug s = Call.debug s >> throwIO s
data Context = Context
{ contextRaw :: GLFW.Window
}
type MMContext = MVar (Maybe Context)
data Handle = Handle
{ handleTid :: ThreadId
, handleComm :: RPC.Handle
, handleRaw :: GLFW.Window
, handleCtxs :: TVar [MMContext]
, handleEventPolicy :: Maybe EventPolicy
}
newtype GLFWWindow = WWindow (MMContext, Handle)
withContext :: String -> MMContext -> (Context -> IO a) -> IO (Maybe a)
withContext callerTag mmContext action = withMVar mmContext go
where
go Nothing = Call.debug (printf "%s: GPipe-GLFW context already closed" callerTag) >> return Nothing
go (Just context) = pure <$> action context
unwrappingGPipeWindow :: MonadIO m
=> (String -> action -> Handle -> MMContext -> IO (Maybe a))
-> String -> GPipe.Window os c ds -> action -> GPipe.ContextT Handle os m (Maybe a)
unwrappingGPipeWindow specialize callerTag wid action = GPipe.withContextWindow wid go
where
go Nothing = Call.debug (printf "%s: GPipe had no such window" callerTag) >> return Nothing
go (Just (WWindow (mmContext, handle))) = specialize callerTag action handle mmContext
withHandleFromGPipe :: MonadIO m => String -> GPipe.Window os c ds -> (Handle -> IO a) -> GPipe.ContextT Handle os m (Maybe a)
withHandleFromGPipe = unwrappingGPipeWindow $ \_callerTag action handle _mmContext ->
Just <$> action handle
withContextFromGPipe :: MonadIO m => String -> GPipe.Window os c ds -> (Context -> IO a) -> GPipe.ContextT Handle os m (Maybe a)
withContextFromGPipe = unwrappingGPipeWindow $ \callerTag action _handle mmContext ->
withContext callerTag mmContext action
withBothFromGPipe :: MonadIO m => String -> GPipe.Window os c ds -> (Handle -> Context -> IO a) -> GPipe.ContextT Handle os m (Maybe a)
withBothFromGPipe = unwrappingGPipeWindow $ \callerTag action handle mmContext ->
withContext callerTag mmContext (action handle)
effectMain :: Handle -> Call.EffectMain
effectMain handle = RPC.sendEffect (handleComm handle)
onMain :: Handle -> Call.OnMain a
onMain handle = RPC.fetchResult (handleComm handle)
defaultHandleConfig :: GPipe.ContextHandlerParameters Handle
defaultHandleConfig = HandleConfig errorHandler $ pure Poll
where
errorHandler err desc = printf "%s: %s\n" (show err) desc
instance GPipe.ContextHandler Handle where
data ContextHandlerParameters Handle = HandleConfig
{
configErrorCallback :: GLFW.Error -> String -> IO ()
, configEventPolicy :: Maybe EventPolicy
}
type ContextWindow Handle = GLFWWindow
type WindowParameters Handle = Resource.WindowConfig
createContext handle settings = do
window <- createWindow (Just $ handleRaw handle) settings
mmContext <- newMVar . pure $ Context window
atomically $ modifyTVar (handleCtxs handle) (mmContext :)
return $ WWindow (mmContext, handle)
contextDoAsync handle Nothing action = RPC.sendEffect (handleComm handle) $ do
ccHuh <- Call.getCurrentContext
maybe (Call.makeContextCurrent "contextDoAsync required some context" . pure . handleRaw $ handle)
(const $ return ())
ccHuh
action
contextDoAsync _ (Just (WWindow (mmContext, _))) action =
void $ withContext "contextDoAsync" mmContext $ \context -> do
Call.makeContextCurrent "contextDoAsync required a specific context" . pure . contextRaw $ context
action
contextSwap _ (WWindow (mmContext, handle)) = do
void $ withContext "contextSwap" mmContext $ Call.swapBuffers . contextRaw
mapM_ (mainstepInternal handle) $ handleEventPolicy handle
contextFrameBufferSize _ (WWindow (mmContext, handle)) = do
result <- withContext "contextFrameBufferSize" mmContext $ \context -> do
Call.getFramebufferSize (onMain handle) $ contextRaw context
maybe failure return result
where
failure = do
Call.debug $ printf "contextFrameBufferSize could not access context"
return (0, 0)
contextDelete _ (WWindow (mmContext, handle)) = do
modifyMVar_ mmContext $ \mContext -> do
Call.debug $ printf "contextDelete of %s" (show $ contextRaw <$> mContext)
forM_ mContext $ \context -> RPC.sendEffect (handleComm handle) $ do
Call.makeContextCurrent "contextDelete" . pure . contextRaw $ context
Call.destroyWindow id (contextRaw context)
return Nothing
atomically $ modifyTVar (handleCtxs handle) (delete mmContext)
contextHandlerCreate config = do
Call.debug "contextHandlerCreate"
tid <- myThreadId
comm <- RPC.newBound
ctxs <- newTVarIO []
Call.setErrorCallback id $ pure errorHandler
ok <- Call.init id
unless ok $ throwIO InitException
ancestor <- createWindow Nothing Nothing
return $ Handle tid comm ancestor ctxs eventPolicy
where
HandleConfig errorHandler eventPolicy = config
contextHandlerDelete handle = do
Call.debug "contextHandlerDelete"
ctxs <- readTVarIO $ handleCtxs handle
forM_ ctxs $ \mmContext -> GPipe.contextDelete handle (WWindow (mmContext, handle))
atomically $ writeTVar (handleCtxs handle) []
Call.terminate id
Call.setErrorCallback id Nothing
createWindow :: Maybe GLFW.Window -> Maybe (GPipe.WindowBits, Resource.WindowConfig) -> IO GLFW.Window
createWindow parentHuh settings = do
unless (null disallowedHints) $
throwIO $ Format.UnsafeWindowHintsException disallowedHints
windowHuh <- Call.createWindow id width height title monitor hints parentHuh
Call.debug $ printf "made context %s -> parent %s" (show windowHuh) (show parentHuh)
window <- maybe exc return windowHuh
forM_ intervalHuh $ \interval -> do
Call.makeContextCurrent "apply vsync setting" $ pure window
Call.swapInterval interval
return window
where
config = fromMaybe (defaultWindowConfig "") (snd <$> settings)
Resource.WindowConfig {Resource.configWidth=width, Resource.configHeight=height} = config
Resource.WindowConfig _ _ title monitor _ intervalHuh = config
(userHints, disallowedHints) = partition Format.allowedHint $ Resource.configHints config
hints = userHints ++ Format.bitsToHints (fst <$> settings) ++ Format.unconditionalHints
exc = throwIO . CreateSharedWindowException . show $ config {Resource.configHints = hints}
data EventPolicy
= Poll
| Wait
deriving
( Show
)
mainstep :: MonadIO m
=> GPipe.Window os c ds
-> EventPolicy
-> GPipe.ContextT Handle os m (Maybe ())
mainstep win eventPolicy = withHandleFromGPipe "mainstep" win $ liftIO . flip mainstepInternal eventPolicy
mainstepInternal :: Handle -> EventPolicy -> IO ()
mainstepInternal handle eventPolicy = do
tid <- myThreadId
when (tid /= handleTid handle) $
bug "mainstep must be called from main thread"
case eventPolicy of
Poll -> Call.pollEvents id
Wait -> withAsync
(RPC.awaitActions (handleComm handle) >> Call.postEmptyEvent)
(const $ Call.waitEvents id)
RPC.processActions $ handleComm handle
mainloop :: MonadIO m
=> GPipe.Window os c ds
-> EventPolicy
-> GPipe.ContextT Handle os m (Maybe ())
mainloop win eventPolicy = withHandleFromGPipe "mainloop" win $ liftIO . flip mainloopInternal eventPolicy
mainloopInternal :: Handle -> EventPolicy -> IO ()
mainloopInternal handle eventPolicy = do
mainstepInternal handle eventPolicy
ctxs <- readTVarIO $ handleCtxs handle
allShouldClose <- and <$> forM ctxs oneShouldClose
unless allShouldClose $
mainloopInternal handle eventPolicy
where
oneShouldClose mmContext = do
shouldCloseHuh <- withContext "oneShouldClose" mmContext $ Call.windowShouldClose . contextRaw
return $ fromMaybe True shouldCloseHuh
data InitException = InitException
deriving (Exception, Show)
data CreateWindowException
= CreateWindowException String
| CreateSharedWindowException String
deriving (Exception, Show)
instance Exception String