
Hello, Alexey.
As far as I know this is not directly possible, at least in 7.8. However
you could workaround it with a newtypes. (I've changed a bit definition of T,
because otherwise there is no way to write MonadTrans instance (it seems)):
import Data.Bifunctor
import Control.Monad.Trans
data T b m a = T (m (Either b a))
instance MonadTrans (T b) where
lift g = T (return . Right =<< g)
newtype TF m b a = TF { unTF :: T b m a}
instance Functor m => Bifunctor (TF m) where
bimap f g (TF (T z)) = TF (T (fmap (bimap f g) z))
In order to easily use bimap and friends you can introduce some helpers
functions like:
withTF :: (TF m b a -> TF m b c) -> T b m a -> T b m c
withTF f = unTF . f . TF
or look at more heavyweight solutions.
--
Best regards,
Vershilov Alexander
On 1 May 2015 at 22:32, Alexey Uimanov
This question probably asked already.
I have a type
data T m b a = T (m (b, a))
and it should be instance of `Bifunctor` and `MonadTrans` same time. But there is a problem:
instance Bifunctor (T m)
is ok, but
instance MonadTrans (T ...
is not, because first argument is `m` but we need `b`. Type can be rewritten like
data T b m a = T (m (b, a))
and instance of MonadTrans is ok:
instance MonadTrans (T b)
but how to define Bifunctor?
instance Bifunctor (T ...
I did not found how to workaround this. Is there any type magic for such cases?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
-- Alexander