Open aavogt opened 7 years ago
Turns out SelectT has parameters in the wrong order. Still, djinn can write a dimap for type T m r a = ((a -> m r) -> m a)
with m as Either t
, (,) t
, (->) t
and probably others.
I'm a bit confused here—are you proposing something concrete here that profunctors
should add?
T
U
or V
below could be added. I don't like those names. A 4th option is to change SelectT
in the transformers package to allow instance Functor f => Profunctor (SelectT f)
, which would break instance MonadTrans (SelectT r)
{-# LANGUAGE FlexibleInstances #-}
import Control.Monad.Trans.Select
import Data.Profunctor
import Data.Coerce
newtype T m r a = T (SelectT r m a)
newtype U m r a = U (Costar ((->) a) (m r) (m a))
newtype V m r a = V ( (a -> m r) -> m a )
ut :: T m r a -> U m r a
ut = coerce
tv :: T m r a -> V m r a
tv = coerce
instance Functor f => Profunctor (T f) where
dimap a b (T (SelectT c)) = T $ SelectT $ \d -> b <$> c (fmap a . d . b)
{- law abiding:
dimap id id (T (SelectT c)) =>
T $ SelectT $ \d -> id <$> c (fmap id . d . id)
T $ SelectT $ \d -> c (id . d . id) -- fmap id
T $ SelectT $ \d -> c d -- id and (.)
T $ SelectT $ c
(T (SelectT c))
=> dimap id id = id
-}
Indeed, I think changing the order of type variables in SelectT
is a non-starter.
I don't have a strong opinion on adding a newtype wrapper around SelectT
, but it doesn't strike me as a terribly general solution. After all, there are several other types that could be Bifunctor
s/Profunctor
s were it not for the order of variables (WriterT
/ContT
come to mind), so if we wanted to support them, we'd need a hand-rolled newtype for each of them as well.
I suppose a general solution would be to figure out a way to make this typecheck:
newtype Swizzle p m a b = Swizzle { runSwizzle :: p a m b }
instance (???) => Profunctor (Swizzle p m) where ...
But I don't know what to put in place of the (???)
.
SelectT
is in http://hackage.haskell.org/package/transformers-0.5.4.0/docs/Control-Monad-Trans-Select.html but is missing fromtransformers<=0.5.2.0
. It is (not?) a Profunctor because:I haven't looked into
ctx :: (* -> *) -> Constraint
ininstance ctx m => Profunctor (SelectT m)
, ctx /= Identity.