Reputation:
I'm playing around with OpenGL in general and Haskell library named GPipe in particular. I have a monad transformer stack with IO
at the bottom, then the ContextT
transformer from the library, then a StateT
because some state is required, and finally a newtype Processor
because simple type
would produce hideous error messages for such a stack. That's the general idea. However, the code below doesn't typecheck:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Control.Lens
import Control.Monad.State
import Control.Monad.Trans
import Control.Monad.Except
import qualified "GPipe" Graphics.GPipe as GP
import qualified "GPipe-GLFW" Graphics.GPipe.Context.GLFW as GLFW
---- State and Processor types ----
class ArtState os as | as -> os where
event :: GP.ContextHandler ctx => as -> Processor ctx os (as, Maybe e)
present :: GP.ContextHandler ctx => as -> Processor ctx os as
window :: Lens' as (WindowType os)
data ProgramState = ProgramState
newtype GP.ContextHandler ctx => Processor ctx os a = Processor {
runProcessor :: StateT ProgramState (GP.ContextT ctx os IO) a
}
---- MenuArt things ----
type WindowType os = GP.Window os GP.RGBFloat GP.Depth
data MenuArt os = MenuArt {
_maWindow :: WindowType os
}
makeLenses ''MenuArt
instance ArtState os (MenuArt os) where
event ms = Processor $ return (ms, Nothing)
present ms = Processor $ return ms
window = maWindow
initMenuArt :: (ArtState os a, GP.ContextHandler ctx) =>
Maybe a
-> Processor ctx os (Either String (MenuArt os))
initMenuArt Nothing = Processor $ do
win <- lift $ GP.newWindow (GP.WindowFormatColorDepth GP.RGB8 GP.Depth16)
(GLFW.defaultWindowConfig "foobar")
return $ Right $ MenuArt {
_maWindow = win
}
initMenuArt (Just from) = Processor $ do
return $ Right $ MenuArt {
_maWindow = from ^. window
}
---- events ----
data UserEvent = CloseWindow
The error message is as follows:
/tmp/testing/app/Main.hs:49:33: error:
• Couldn't match expected type ‘GP.WindowParameters ctx’
with actual type ‘GLFW.WindowConfig’
• In the second argument of ‘GP.newWindow’, namely
‘(GLFW.defaultWindowConfig "foobar")’
In the second argument of ‘($)’, namely
‘GP.newWindow
(GP.WindowFormatColorDepth GP.RGB8 GP.Depth16)
(GLFW.defaultWindowConfig "foobar")’
In a stmt of a 'do' block:
win <- lift
$ GP.newWindow
(GP.WindowFormatColorDepth GP.RGB8 GP.Depth16)
(GLFW.defaultWindowConfig "foobar")
• Relevant bindings include
initMenuArt :: Maybe a
-> Processor ctx os (Either String (MenuArt os))
(bound at app/Main.hs:47:1)
|
49 | (GLFW.defaultWindowConfig "foobar")
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
From what I could understand, the newWindow
expects a WindowParameters ctx
as its second argument, which is an associated type for the ContextHandler
class. But the compiler doesn't see that GLFW.WindowConfig
is WindowParameters
for this stack for some reason. Throwing away StateT
and Processor
from the stack (as in the tutorial I'm working through) works, this compiles:
main :: IO ()
main = do
GP.runContextT GLFW.defaultHandleConfig $ do
win <- GP.newWindow (GP.WindowFormatColor GP.RGB8) (GLFW.defaultWindowConfig "foobar")
return ()
return ()
I'm doing something wrong, but can't figure out what.
Upvotes: 3
Views: 40
Reputation: 33429
initMenuArt
is using GLFW.defaultWindowConfig
, which is a GLFW function.
GPipe
defines an interface parameterized by a ctx
type, and GPipe-GLFW
implements that interface by instantiating ctx
with GLFW.Handle
.
Thus initMenuArt
should be specialized accordingly:
initMenuArt
:: (ArtState os a)
=> Maybe a
-> Processor GLFW.Handle os (Either String (MenuArt os))
Upvotes: 3