Reputation: 15199
I have a type alias for a monad transformer stack:
type KStat s a = ReaderT (KStatRoot s) (ExceptT KindError (ST s)) a
I need to abstract users away from this type, largely because the KStatRoot
structure was causing cyclic dependencies. I therefore created a separate module and defined a typeclass for it:
class (Monad (m s), MonadError KindError (m s)) =>
MStat m s where
liftToST :: ST s a -> m s a
kstatNewRef :: a -> m s (STRef s a)
kstatReadRef :: STRef s a -> m s a
kstatWriteRef :: STRef s a -> a -> m s ()
This definition compiles OK (albeit needing {-# LANGUAGE MultiParamTypeClasses,FlexibleContexts #-}
to work, but I can see why both of those are required), and I've been able to convert some use sites to the typeclass and have them type check, so everything seems OK there. But I'm struggling to work out how to define my instance for the class:
instance MStat (KStat s a) s where
liftToST = lift . lift
kstatNewRef = liftToST . newSTRef
kstatReadRef = liftToST . readSTRef
kstatWriteRef r v = liftToST $ writeSTRef r v
gives me the error:
src/KindLang/Data/KStat.hs:27:17:
The first argument of ‘MStat’ should have kind ‘* -> * -> *’,
but ‘KStat s a’ has kind ‘*’
In the instance declaration for ‘MStat (KStat s a) s’
which kind of makes sense, but then if I change KStat s a
to KStat
in the instance header I get this error:
src/KindLang/Data/KStat.hs:27:10:
Type synonym ‘KStat’ should have 2 arguments, but has been given none
In the instance declaration for ‘MStat KStat s’
which seems to basically saying the exact opposite.
I'm using these language extensions in the module I declare the instance:
{-# LANGUAGE RankNTypes, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses #-}
How do I resolve these errors?
Complete file demonstrating the errors follows:
{-# LANGUAGE RankNTypes, TypeSynonymInstances, FlexibleContexts,
FlexibleInstances, MultiParamTypeClasses #-}
import Control.Monad.Except
import Control.Monad.ST
import Control.Monad.Reader
import Data.STRef
data KStatRoot s = KStatRoot
data KindError
class (Monad (m s), MonadError KindError (m s)) =>
MStat m s where
liftToST :: ST s a -> m s a
kstatNewRef :: a -> m s (STRef s a)
kstatReadRef :: STRef s a -> m s a
kstatWriteRef :: STRef s a -> a -> m s ()
type KStat s a = ReaderT (KStatRoot s) (ExceptT KindError (ST s)) a
instance MStat (KStat s m) s where
liftToST = lift . lift
kstatNewRef = liftToST . newSTRef
kstatReadRef = liftToST . readSTRef
kstatWriteRef r v = liftToST $ writeSTRef r v
Upvotes: 1
Views: 77
Reputation: 85757
The first error is "correct" (you need to use a type of two arguments in the instance declaration), and your attempted fix makes sense.
However, a type
synonym doesn't really exist without its arguments. That is, after
type Foo a = ...
you can't use Foo
by itself. Foo
has to be applied to an argument in order to be processed by the type checker. This is the cause of your second error.
The only workaround I see is changing KStat
to a newtype
:
newtype KStat s a = KStat{ runKStat :: ReaderT (KStatRoot s) (ExceptT KindError (ST s)) a }
That will let you use KStat
without arguments. You'll just have to add explicit runKStat
/KStat
conversions everywhere.
Upvotes: 4