Reputation: 474
I want to write something similar to the following:
newtype FooT c d m a = FooT { unFooT :: (c (d m)) a }
instance (MonadTrans c, MonadTrans d) => MonadTrans (FooT c d) where
lift = FooT . lift . lift
However, this snippet will not compile:
Could not deduce (Monad (d m)) arising from a use of ‘lift’
I understand why this won't compile; we don't know that the application of an arbitrary transformer d m
is itself a monad. However, I'm not sure of the best way to proceed.
Is there a clean way to make something like this work? Presumably it would go through if I could add a constraint along the lines of Monad (d m)
to the left-hand-side of the instance declaration, but I don't know how to do so since m
is not bound.
Upvotes: 2
Views: 169
Reputation: 7014
Since transformers 0.6 the MonadTrans
type class has had a requirement that it preserves Monad
.
This means the definition of MonadTrans
is:
type Lifting cls trans = forall m. cls m => cls (trans m)
class Lifting Monad trans => MonadTrans trans where
lift :: Monad m => m ~> trans m
The composition of transformers (ComposeT
), which you call FooT
doesn't need to specify the lifting, so the code you supplied in your question should work for versions 0.6+.
ComposeT
already exists in deriving-trans
newtype Ok m a = Ok (Int -> Bool -> m a)
deriving
( Functor, Applicative, Alternative, Contravariant
, Monad, MonadPlus, MonadCont, MonadIO, MonadFix,
, MonadFail, MonadZip
)
via ReaderT Int (ReaderT Bool m)
deriving MonadTrans
via ComposeT (ReaderT Int) (ReaderT Bool)
Upvotes: 2
Reputation: 29158
With the QuantifiedConstraints
GHC extension, this is
{-# LANGUAGE QuantifiedConstraints #-}
instance (MonadTrans c, MonadTrans d, forall m. Monad m => Monad (d m)) =>
MonadTrans (FooT c d) where
lift = FooT . lift . lift
m
in the constraint is not the same m
as in lift
. The quantified constraint simply means what it says ("for any m :: Type -> Type
, if Monad m
require Monad (d m)
"), and in lift
that universal statement is being instantiated with the particular m
being passed as argument to lift
. Thus lift
's m
does not escape its scope.
Upvotes: 4