I'm writing a OpenGL program for learning purposes, using GPipe
library. The library does some black type magic, and that (with a newtype
from me thrown in for a good measure) makes me unable to properly parse error messages. The following code doesn't compile:
{-# LANGUAGE PackageImports #-}
module Main where
import Control.Monad.State
import Control.Monad.Except
import qualified "GPipe" Graphics.GPipe as GP
import qualified "GPipe-GLFW" Graphics.GPipe.Context.GLFW as GLFW
---- types ----
newtype Processor ctx os a = Processor {
runProcessor :: GP.ContextT ctx os (StateT (FullState os) IO) a
}
data Transition os = ToMainMenu (FullState os)
| Quit
type CType = GP.RGBFloat
type UnitWindow os = GP.Window os CType ()
data ArtState os = ArtState {
_asWindow :: UnitWindow os
}
data ProgState = ProgState
data FullState os = FullState {
_fsArtState :: ArtState os
, _fsProgState :: ProgState
}
---- constructors ----
mkFullState :: UnitWindow os -> FilePath -> ExceptT String IO (FullState os)
mkFullState window directory = do
art <- mkArtState window directory
prog <- mkProgState directory
return FullState {
_fsArtState = art
, _fsProgState = prog
}
mkArtState :: UnitWindow os -> FilePath -> ExceptT String IO (ArtState os)
mkArtState window _ = return ArtState {
_asWindow = window
}
mkProgState :: FilePath -> ExceptT String IO ProgState
mkProgState _ = return ProgState
---- processors ----
start :: Processor ctx os (Transition os)
start = Processor $ GP.runContextT GLFW.defaultHandleConfig $ do
win <- GP.newWindow (GP.WindowFormatColor GP.RGB8) (GLFW.defaultWindowConfig "Foobar")
possiblyState <- liftIO $ runExceptT $ mkFullState win "./"
case possiblyState of
Left err -> liftIO $ putStrLn err >> return Quit
Right state -> return $ ToMainMenu state
---- Main ----
main :: IO ()
main = do
transition <- runProcessor start
case transition of
Quit -> return ()
ToMainMenu _ -> return ()
The idea is to have Processor
s return a Transition
to be used by the main loop to select an appropriate path of execution. The compilation error is as follows:
/tmp/testing/app/Main.hs:60:25: error:
• Couldn't match type ‘os1’ with ‘os’
‘os1’ is a rigid type variable bound by
a type expected by the context:
forall os1.
GP.ContextT
GLFW.Handle
os1
(GP.ContextT ctx os (StateT (FullState os) IO))
(Transition os)
at app/Main.hs:(55,21)-(60,49)
‘os’ is a rigid type variable bound by
the type signature for:
start :: forall ctx os. Processor ctx os (Transition os)
at app/Main.hs:54:1-41
Expected type: GP.ContextT
GLFW.Handle
os1
(GP.ContextT ctx os (StateT (FullState os) IO))
(Transition os)
Actual type: GP.ContextT
GLFW.Handle
os1
(GP.ContextT ctx os (StateT (FullState os) IO))
(Transition os1)
• In the expression: return $ ToMainMenu state
In a case alternative: Right state -> return $ ToMainMenu state
In a stmt of a 'do' block:
case possiblyState of
Left err -> liftIO $ putStrLn err >> return Quit
Right state -> return $ ToMainMenu state
• Relevant bindings include
state :: FullState os1 (bound at app/Main.hs:60:16)
possiblyState :: Either String (FullState os1)
(bound at app/Main.hs:57:5)
win :: GP.Window os1 GP.RGBFloat () (bound at app/Main.hs:56:5)
start :: Processor ctx os (Transition os)
(bound at app/Main.hs:55:1)
|
60 | Right state -> return $ ToMainMenu state
| ^^^^^^^^^^^^^^^^^^^^^^^^^
My understanding of Haskell and monads doesn't allow me to fix this, I can sort of see that os1
and os
are produced by different equations and therefore GHC can't just mark them as same, but I'm at a loss as to how to repair that. If I remove os
parameter from the Transition
enum, the error disappears, but I need it to pass the state around instead of reinitializing it in every Processor.
Could someone explain what's going wrong and how to fix it?
PS. Oh, and when I clumped all the code in a single file, a new error appeared that was previously masked by compilation order.
A function that returns a ContextT
value (here wrapped in Processor
), like start
, should not call GP.runContextT
.
GP.runContextT
is used to initialize and provide the context to execute the processors, which you only want to do once at the start of the whole program. Thus, it should probably be in main
, together with newWindow
, defaultWindowConfig
and mkFullState
.
A Processor
like start
can get the current state using the StateT
transformer. But first, we must fix the Processor
type. Notice the type of runContextT
, in particular the forall
:
runContextT
:: (MonadIO m, MonadAsyncException m, ContextHandler ctx)
=> ContextHandlerParameters ctx -> (forall os. ContextT ctx os m a) -> m a
This forall
imposes that the type variable os
can not occur in m
or in a
, preventing certain resources from leaking. This is incompatible with the current definition of Processor
, since StateT (FullState os) IO
contains os
. You can probably swap the transformers.
newtype Processor ctx os a = Processor {
runProcessor :: StateT (FullState os) (GP.ContextT ctx os IO) a
}
Now start
can use get
to access the current state, and since it is not supposed to handle initialization, it doesn't have the Quit
branch anymore (you might no longer want to make start
a Processor
at this point, but hopefully this is close enough to what you'd actually like to do with other processors):
start :: Processor ctx os (Transition os)
start = Processor $ do
s <- get
return $ ToMainMenu s
And main
can look like this:
main :: IO ()
main =
-- Initialize and provide context, i.e, convert the wrapped
-- do-block of type `ContextT _ _ IO` to `IO`
GP.runContextT GLFW.defaultHandleConfig $ do
-- Create a GLFW window
-- You can probably create more than one
win <- GP.newWindow (GP.WindowFormatColor GP.RGB8) (GLFW.defaultWindowConfig "Foobar")
-- Create the initial processor state, handling initialization failures
s_ <- liftIO $ runExceptT $ mkFullState win "./"
s0 <- case s_ of
Left e -> fail e
Right s0 -> return s0
-- Run a processor
(transition, s1) <- (`runStateT` s0) $ runProcessor start
case transition of
Quit -> return ()
ToMainMenu _ -> return ()