{-# LANGUAGE TypeFamilies, RankNTypes, GeneralizedNewtypeDeriving, FlexibleContexts, FlexibleInstances, GADTs, DeriveDataTypeable #-}
module Graphics.GPipe.Internal.Context
(
ContextHandler(..),
ContextT(),
GPipeException(..),
runContextT,
newWindow,
deleteWindow,
swapWindowBuffers,
getFrameBufferSize,
withContextWindow,
WindowState(..),
RenderState(..),
liftNonWinContextIO,
liftNonWinContextAsyncIO,
addContextFinalizer,
Window(..),
addVAOBufferFinalizer,
addFBOTextureFinalizer,
getVAO, setVAO,
getFBO, setFBO,
ContextData,
VAOKey(..), FBOKey(..), FBOKeys(..),
Render(..), render,
registerRenderWriteTexture,
getLastRenderWin,
asSync
)
where
import Graphics.GPipe.Internal.Format
import Control.Monad.Exception (MonadException, Exception, MonadAsyncException,bracket)
import Control.Monad.Trans.Reader
import qualified Control.Monad.Fail as MF
import Control.Monad.IO.Class
import Control.Monad.Trans.Class
import Control.Applicative (Applicative, (<$>))
import Data.Typeable
import qualified Data.IntSet as Set
import qualified Data.IntMap.Strict as IMap
import Data.IntMap ((!))
import qualified Data.Map.Strict as Map
import Graphics.GL.Core33
import Graphics.GL.Types
import Control.Concurrent.MVar
import Data.IORef
import Control.Monad
import Data.List (delete)
import Foreign.C.Types
import Data.Maybe
import Linear.V2 (V2(V2))
import Control.Monad.Trans.Except
import Control.Exception (throwIO)
import Control.Arrow
import Control.Monad.Trans.State.Strict
class ContextHandler ctx where
data ContextHandlerParameters ctx
type ContextWindow ctx
type WindowParameters ctx
contextHandlerCreate :: ContextHandlerParameters ctx -> IO ctx
contextHandlerDelete :: ctx -> IO ()
createContext :: ctx -> Maybe (WindowBits, WindowParameters ctx) -> IO (ContextWindow ctx)
contextDoAsync :: ctx -> Maybe (ContextWindow ctx) -> IO () -> IO ()
contextSwap :: ctx -> ContextWindow ctx -> IO ()
contextFrameBufferSize :: ctx -> ContextWindow ctx -> IO (Int, Int)
contextDelete :: ctx -> ContextWindow ctx -> IO ()
newtype ContextT ctx os m a =
ContextT (ReaderT (ContextEnv ctx) (StateT (ContextState ctx) m) a)
deriving (Functor, Applicative, Monad, MonadIO, MonadException, MonadAsyncException)
data ContextEnv ctx = ContextEnv {
context :: ctx,
sharedContextData :: SharedContextDatas
}
data ContextState ctx = ContextState {
nextName :: Name,
perWindowState :: PerWindowState ctx,
lastUsedWin :: Name
}
newtype Render os a = Render { unRender :: ExceptT String (ReaderT RenderEnv (StateT RenderState IO)) a } deriving (Monad, Applicative, Functor)
data RenderEnv = RenderEnv {
renderSharedContextData :: SharedContextDatas,
nonWindowDoAsync :: ContextDoAsync
}
data RenderState = RenderState {
perWindowRenderState :: PerWindowRenderState,
renderWriteTextures :: Set.IntSet,
renderLastUsedWin :: Name
}
type Name = Int
type ContextDoAsync = IO () -> IO ()
type PerWindowState ctx = IMap.IntMap (WindowState, ContextWindow ctx)
type PerWindowRenderState = IMap.IntMap (WindowState, ContextDoAsync)
data WindowState = WindowState {
windowContextData :: !ContextData
}
render :: (ContextHandler ctx, MonadIO m, MonadException m) => Render os () -> ContextT ctx os m ()
render (Render m) = do
void getLastContextWin
ContextT $ do
ContextEnv ctx cds <- ask
cs <- lift get
let wmap' = IMap.map (\(ws,w) -> (ws, contextDoAsync ctx (Just w))) $ perWindowState cs
(eError, rs) <- liftIO $ runStateT (runReaderT (runExceptT m) (RenderEnv cds (contextDoAsync ctx Nothing))) (RenderState wmap' Set.empty (lastUsedWin cs))
lift $ put $ cs { lastUsedWin = renderLastUsedWin rs}
case eError of
Left s -> liftIO $ throwIO $ GPipeException s
_ -> return ()
registerRenderWriteTexture :: Int -> Render os ()
registerRenderWriteTexture n = Render $ lift $ lift $ modify $ \ rs -> rs { renderWriteTextures = Set.insert n $ renderWriteTextures rs }
instance MonadTrans (ContextT ctx os) where
lift = ContextT . lift . lift
instance MonadIO m => MF.MonadFail (ContextT ctx os m) where
fail = liftIO . MF.fail
runContextT :: (MonadIO m, MonadAsyncException m, ContextHandler ctx) => ContextHandlerParameters ctx -> (forall os. ContextT ctx os m a) -> m a
runContextT chp (ContextT m) = do
cds <- liftIO newContextDatas
bracket
(liftIO $ contextHandlerCreate chp)
(\ctx -> liftIO $ do
cds' <- readMVar cds
mapM_ snd cds'
contextHandlerDelete ctx
)
(\ctx -> evalStateT (runReaderT m (ContextEnv ctx cds)) (ContextState 1 IMap.empty (-1)))
data Window os c ds = Window { getWinName :: Name }
instance Eq (Window os c ds) where
(Window a) == (Window b) = a == b
createHiddenWin :: (ContextHandler ctx, MonadIO m) => ContextT ctx os m (ContextWindow ctx)
createHiddenWin = ContextT $ do
ContextEnv ctx cds <- ask
ContextState wid _ _ <- lift get
w <- liftIO $ createContext ctx Nothing
cd <- liftIO $ addContextData (contextDelete ctx w) cds
let ws = WindowState cd
lift $ put $ ContextState wid (IMap.singleton 0 (ws,w)) 0
liftIO $ contextDoAsync ctx (Just w) initGlState
return w
newWindow :: (ContextHandler ctx, MonadIO m) => WindowFormat c ds -> WindowParameters ctx -> ContextT ctx os m (Window os c ds)
newWindow wf wp = ContextT $ do
ContextEnv ctx cds <- ask
ContextState wid wmap _ <- lift get
w <- liftIO $ createContext ctx (Just (windowBits wf, wp))
cd <- liftIO $ addContextData (contextDelete ctx w) cds
let wid' = wid+1
let ws = WindowState cd
lift $ put $ ContextState wid' (IMap.insert wid (ws,w) wmap) wid
liftIO $ contextDoAsync ctx (Just w) initGlState
return $ Window wid
deleteWindow :: (ContextHandler ctx, MonadIO m) => Window os c ds -> ContextT ctx os m ()
deleteWindow (Window wid) = ContextT $ do
ContextState nid wmap n <- lift get
case IMap.lookup wid wmap of
Nothing -> return ()
Just (ws, w) -> do
ContextEnv ctx cds <- ask
let wmap' = IMap.delete wid wmap
n' <- if (IMap.null wmap')
then do
void $ let ContextT m = createHiddenWin in m
return 0
else if n /= wid then return n
else return (fst (head (IMap.toList wmap')))
liftIO $ do removeContextData cds (windowContextData ws)
contextDelete ctx w
lift $ put $ ContextState nid wmap' n'
initGlState :: IO ()
initGlState = do
glEnable GL_FRAMEBUFFER_SRGB
glEnable GL_SCISSOR_TEST
glPixelStorei GL_PACK_ALIGNMENT 1
glPixelStorei GL_UNPACK_ALIGNMENT 1
asSync :: (IO () -> IO ()) -> IO x -> IO x
asSync f m = do mutVar <- newEmptyMVar
f (m >>= putMVar mutVar)
takeMVar mutVar
getLastContextWin :: (ContextHandler ctx, MonadIO m) => ContextT ctx os m (ContextWindow ctx)
getLastContextWin = ContextT $ do
cs <- lift get
let wid = lastUsedWin cs
if wid >= 0
then return (snd $ perWindowState cs ! wid)
else let ContextT m = createHiddenWin in m
liftNonWinContextIO :: (ContextHandler ctx, MonadIO m) => IO a -> ContextT ctx os m a
liftNonWinContextIO m = do
ContextEnv ctx _ <- ContextT ask
w <- getLastContextWin
ContextT $ liftIO $ asSync (contextDoAsync ctx (Just w)) m
liftNonWinContextAsyncIO :: (ContextHandler ctx, MonadIO m) => IO () -> ContextT ctx os m ()
liftNonWinContextAsyncIO m = do
ContextEnv ctx _ <- ContextT ask
w <- getLastContextWin
ContextT $ liftIO $ contextDoAsync ctx (Just w) m
addContextFinalizer :: (ContextHandler ctx, MonadIO m) => IORef a -> IO () -> ContextT ctx os m ()
addContextFinalizer k m = ContextT $ do
ContextEnv ctx _ <- ask
liftIO $ void $ mkWeakIORef k $ contextDoAsync ctx Nothing m
getLastRenderWin = Render $ do
rs <- lift $ lift get
let cwid = renderLastUsedWin rs
let (ws, doAsync) = perWindowRenderState rs ! cwid
cd = windowContextData ws
return (cwid, cd, doAsync)
swapWindowBuffers :: (ContextHandler ctx, MonadIO m) => Window os c ds -> ContextT ctx os m ()
swapWindowBuffers (Window wid) = ContextT $ do
wmap <- lift $ gets perWindowState
case IMap.lookup wid wmap of
Nothing -> return ()
Just (_, w) -> do
ctx <- asks context
liftIO $ contextSwap ctx w
getFrameBufferSize :: (ContextHandler ctx, MonadIO m) => Window os c ds -> ContextT ctx os m (V2 Int)
getFrameBufferSize (Window wid) = ContextT $ do
wmap <- lift $ gets perWindowState
case IMap.lookup wid wmap of
Nothing -> return $ V2 0 0
Just (_, w) -> do
ctx <- asks context
(x,y) <- liftIO $ contextFrameBufferSize ctx w
return $ V2 x y
withContextWindow :: MonadIO m => Window os c ds -> (Maybe (ContextWindow ctx) -> IO a) -> ContextT ctx os m a
withContextWindow (Window wid) m = ContextT $ do
wmap <- lift $ gets perWindowState
liftIO $ m (snd <$> IMap.lookup wid wmap)
data GPipeException = GPipeException String
deriving (Show, Typeable)
instance Exception GPipeException
type SharedContextDatas = MVar [(ContextData, IO ())]
type ContextData = MVar (VAOCache, FBOCache)
data VAOKey = VAOKey { vaoBname :: !GLuint, vaoCombBufferOffset :: !Int, vaoComponents :: !GLint, vaoNorm :: !Bool, vaoDiv :: !Int } deriving (Eq, Ord)
data FBOKey = FBOKey { fboTname :: !GLuint, fboTlayerOrNegIfRendBuff :: !Int, fboTlevel :: !Int } deriving (Eq, Ord)
data FBOKeys = FBOKeys { fboColors :: [FBOKey], fboDepth :: Maybe FBOKey, fboStencil :: Maybe FBOKey } deriving (Eq, Ord)
type VAOCache = Map.Map [VAOKey] (IORef GLuint)
type FBOCache = Map.Map FBOKeys (IORef GLuint)
getFBOKeys :: FBOKeys -> [FBOKey]
getFBOKeys (FBOKeys xs d s) = xs ++ maybeToList d ++ maybeToList s
newContextDatas :: IO SharedContextDatas
newContextDatas = newMVar []
addContextData :: IO () -> SharedContextDatas -> IO ContextData
addContextData io r = do cd <- newMVar (Map.empty, Map.empty)
modifyMVar_ r $ return . ((cd,io):)
return cd
removeContextData :: SharedContextDatas -> ContextData -> IO ()
removeContextData r cd = modifyMVar_ r $ return . remove cd
where remove x ((k,v):xs) | x == k = xs
remove x (kv:xs) = kv : remove x xs
remove _ [] = []
addCacheFinalizer :: MonadIO m => (GLuint -> (VAOCache, FBOCache) -> (VAOCache, FBOCache)) -> IORef GLuint -> ContextT ctx os m ()
addCacheFinalizer f r = ContextT $ do cds <- asks sharedContextData
liftIO $ do n <- readIORef r
void $ mkWeakIORef r $ do cs' <- readMVar cds
mapM_ (\(cd,_) -> modifyMVar_ cd (return . f n)) cs'
addVAOBufferFinalizer :: MonadIO m => IORef GLuint -> ContextT ctx os m ()
addVAOBufferFinalizer = addCacheFinalizer deleteVAOBuf
where deleteVAOBuf n (vao, fbo) = (Map.filterWithKey (\k _ -> all ((/=n) . vaoBname) k) vao, fbo)
addFBOTextureFinalizer :: MonadIO m => Bool -> IORef GLuint -> ContextT ctx os m ()
addFBOTextureFinalizer isRB = addCacheFinalizer deleteVBOBuf
where deleteVBOBuf n (vao, fbo) = (vao, Map.filterWithKey
(\ k _ ->
all
(\ fk ->
fboTname fk /= n || isRB /= (fboTlayerOrNegIfRendBuff fk < 0))
$ getFBOKeys k)
fbo)
getVAO :: ContextData -> [VAOKey] -> IO (Maybe (IORef GLuint))
getVAO cd k = do (vaos, _) <- readMVar cd
return (Map.lookup k vaos)
setVAO :: ContextData -> [VAOKey] -> IORef GLuint -> IO ()
setVAO cd k v = modifyMVar_ cd $ \ (vaos, fbos) -> return (Map.insert k v vaos, fbos)
getFBO :: ContextData -> FBOKeys -> IO (Maybe (IORef GLuint))
getFBO cd k = do (_, fbos) <- readMVar cd
return (Map.lookup k fbos)
setFBO :: ContextData -> FBOKeys -> IORef GLuint -> IO ()
setFBO cd k v = modifyMVar_ cd $ \(vaos, fbos) -> return (vaos, Map.insert k v fbos)