Open tomjaguarpaw opened 4 years ago
Thanks for the great feedback. If you're happy to wait them I'm happy to discuss and polish until we feel we have the right design.
I agree that purePP
should be pureP
. It was only after realising that the analogue of lose
ought to be loseVP
under that scheme that I realised the scheme was flawed :)
If we're going for maximal consistency then I personally prefer naming everything after the standard Haskell typeclasses that exhibit the same properties. Curiously it seems that both DivisibleProfunctor
and AlternativeProfunctor
would be p a b -> p a' b' -> p (a, a') (Either b b')
. I don't know how p a b -> p a' b' -> p (Either a a') (b, b')
fits into this correspondence. Maybe the correspondence we found is a mirage! In any case, I don't think I've ever had the need for either of those two.
I think Divisible
falls out from ApplicativateProfunctor
. For contravariant functors, it's this:
class Contravariant f => Divisible f where
divide :: (a -> (b, c)) -> f b -> f c -> f a
conquer :: f a
If we profunctorise it, we expect that behaviour on the first parameter, so we want something like:
divideP :: (a -> (b, c)) -> p b x -> p c x -> p a x
We can get tuples in the first position of p b x
and p c x
with lmap fst
and lmap snd
. ApplicativeProfunctor
already gives us what we need to write p2
, so the only question remains is: what to do with the two x
s? We need (x, x) -> x
, which is uncurry (<>)
!
So I think you can recover a profunctor-flavoured Divisible
from ApplicativeProfunctor
via:
divideP :: (Semigroup x, ApplyProfunctor p) => (a -> (b, c)) -> p b x -> p c x -> p a x
divideP f p q = dimap f (uncurry (<>)) $ p2 p q
conquerP :: (Monoid x, ApplicativeProfunctor p) => p a x
conquerP = pureP mempty
Symmetrically, can we construct a profunctor-flavoured Alternative
from DecidableProfunctor
?
-- Using "semigroupoids"-inspired classes because I think the 'Applicative' superclass might be a red herring?
class Functor f => Alt f where
-- (<!>) :: f a -> f a -> f a
alt :: f a -> f b -> f (Either a b)
alt left right = (Left <$> left) <!> (Right <$> right)
class Alt f => Plus f where
zero :: f a
Profunctorise:
altP :: p x a -> p x b -> p x (Either a b)
We can then use decideP id
to get a p (Either x x) (Either a b)
, and this is where I get stuck: we can't sneak in Semigroup
/Monoid
to get out of trouble. Maybe we can profunctorise (<!>)
and use p2
again, and use Monoid
?
-- (<!>) :: f a -> f a -> f a
altP :: (ApplicativeProfunctor p, Semigroup x) => p a x -> p a x -> p a x
altP o q = dimap d (uncurry (<>)) $ p2 p q
where d x = (x, x)
zeroP = conquerP -- !?
This seems surprising and strange. I don't know if I'm thinking too narrowly and this is only one possible monoid over profunctors of a certain subclass, or we're butting up against Mysterious Incomposability when Either
s get involved, or something else.
It does make me lean towards favouring the SumProfunctor
and ProductProfunctor
, because the ApplicativeProfunctor
/DecidableProfunctor
naming doesn't show all the possibilities. Maybe then {Sum
,Product
}`Profunctor can still have the applicative/decidable/?divisible names in the class so they can be replaced with more efficient versions?
Had an interesting talk with @gwils about this, and why it all looks so weird and asymmetrical. Basically, to recover one of (Applicative, Alternative, Divisible, Decidable) we take either the sum or product of p a b
and p c d
, do "the operation" of the typeclass (respectively: (<*>)
, (<|>)
, divide
, choose
) on the appropriate type variable (the covariant or contravariant one), and then do "something" with the other type variable.
Let's look at recovering the Divisible
operations again:
divideP :: (Semigroup x, ApplyProfunctor p) => (a -> (b, c)) -> p b x -> p c x -> p a x
divideP f p q = dimap f (uncurry (<>)) $ p2 p q
conquerP :: (Monoid x, ApplicativeProfunctor p) => p a x
conquerP = pureP mempty
Why doesn't a Monoid
-ish typeclass appear in the others? Why can't we do this for Alternative
? For Applicative
, we're working on the covariant variable with the Applicative
operations pure
and (<*>)
, so we need to map an "uncombining" operation on the contravariant variable. But what would a comonoid typeclass look like?
class Comonoid w where
comappend :: w -> (w, w)
comempty :: w -> ()
Both of which are trivial for any w
. So we can recover pureP :: ProductProfunctor p => b -> p a b
and applyP :: ProductProfunctor p => p a (b -> c) -> p a b -> p a c
without an extra constraint. Similarly, if you consider the monoidal category (Hask, Either, Void) instead of (Hask, (,), ()), you get a different Semigroup
/Monoid
hierarchy:
class MonoidE a where
mappendE :: Either a a -> a
memptyE :: Void -> a
Like comonoids using (,), the MonoidE
class is trivial. mappendE = either id id
and memptyE = absurd
everywhere. So that's why there's no typeclass hanging around when we're implementing the Decidable
operations atop SumProfunctor
.
And this is why we struggled to implement Alternative
. We'd need a class ComonoidE
which would look something like this:
class ComonoidE where
comappendE :: a -> Either a a
comemptyE :: a -> Void
comemptyE
is impossible, and even if you delete comemptyE
and try for some CosemigroupE
class, I'm still at a loss for what sensible instances for a -> Either a a
there are that satisfy an associative coappend.
Just like ()
is trivially a Monoid
, Void
is trivially a ComonoidE
. But that's probably the only instance indeed.
Revisiting this again after some haskell-cafe discussion: I think the naming principles that are currently making me the happiest are:
SumProfunctor
, VoidProfunctor
, ProductProfunctor
, UnitProfunctor
. Reason: there's no good reason for any of the Applicative/Divisible/Decidable names to canonically identify the classP
to distinguish them.(***!)
-style primitive operations (for theoretical clarity) and also operations named after the ones in Applicative
/Divisible
/Decidable
etc (makes use cases obvious, and allows them to be overridden for performance).
(****)
around, and accept that it's a bit of a wart - (<*>)
has pretty much replaced ap
, and I can't see apP
taking off.class Profunctor p => ProductProfunctor p where
-- Provide default in terms of (****)
(***!) :: p a c -> p b d -> p (a,b) (c,d)
-- Derived operations
(****) :: p x (a -> b) -> p x a -> p x b
-- In some cases (e.g., lifting an 'Applicative' via 'Joker'), the 'Semigroup' constraint is not required.
-- But I think it's almost always necessary and so easy to get that it's probably okay to require it.
divideP :: Semigroup x => (a -> (b,c)) -> p b x -> p c x -> p a x
-- Alternate name: liftA2P?
liftP2 :: (a -> b -> c) => p x a -> p x b -> p x c
class ProductProfunctor p => UnitProfunctor p where
unitP :: P () ()
-- Derived operations
pureP :: a -> p x a
conquerP :: Monoid x => p a x
class Profunctor p => SumProfunctor p where
(+++!) :: p a c -> p b d -> p (Either a b) (Either c d)
-- Derived operations
decideP :: (a -> Either b c) -> p b x -> p c x -> p a x
class SumProfunctor p => VoidProfunctor p where
voidP :: p Void Void
-- Derived operations
-- Returning @p a x@ instead of @p a Void@ keeps symmetry with 'pureP'.
-- This seems fine, as the @f@ argument essentially says "@a@ is impossible".
concludeP :: (a -> Void) -> p a x
concludeP f = dimap f absurd voidP
Thanks, I like this rationale.
I'm uneasy about UnitProfunctor
(and VoidProfunctor
) though. A context of UnitProfunctor p => ...
looks weird when it's the product that's actually doing most of the work (generally). Similarly, Semigroup a => Unit a
(as opposed to Monoid a
) would be pretty weird. On the other hand I don't have any better ideas.
Minor preference: liftA2P
instead of liftA2
I would also be happy with:
class Profunctor p => SemiproductProfunctor p -- Formerly ProductProfunctor
class SemiproductProfunctor p => ProductProfunctor p -- Formerly UnitProfunctor
(and similar for sums)
Minor preference:
liftA2P
instead ofliftA2
I assume you mean liftP2
? I liked liftP2
because I felt it fit with existing convention (liftF2
, liftU2
/liftI2
, liftM2
). However all of those are for unary type constructors. For binary type constructors, the convention looks a bit different: biliftA2
, bilift2
. Would you prefer lift2P
, liftA2P
, liftP2
, or something else?
I would also be happy with ...
OK, great. This is beginning to take shape. Semi...
seems reasonable by analogy with Semigroup
.
I assume you mean
liftP2
?
Ah yes indeed. In any case it is a very minor objection and I'm sure it can be resolved easily..
I think I'm missing something, but what's the motivation (maybe somewhere in this comment thread) for why there's no common superclass of ProductProfunctor
/SumProfunctor
before Profunctor
in the revised hierarchy?
Speaking as someone jumping into profunctors without the benefit of documentation or tutorials outside of what I can glean from papers, blogs and sporadic reddit threads --- please correct me if I'm wrong --- MonoidalProfunctor
might be what a reader of de Oliveira et al 2022 would expect, but given what I understand of the revised typeclass hierarchy discussed here it sounds like SemigroupalProfunctor
(SemigroupoidProfunctor
?) would fit better than MonoidalProfunctor
.
I also don't really understand exactly why all of this (the ProductProfunctor
/SumProfunctor
typeclasses +/- the revision) are missing from profunctors
other than the vague sense that supporting profunctor optics might be the principle ("myopic"?) focus for design tradeoffs in the profunctors
package, at least for the time being.
In theory, you could build out this hierarchy:
flowchart TD
A(SemigroupalProfunctor) --> B
A --> C
A --> D
B(SemiproductProfunctor) --> E(ProductProfunctor)
C(MonoidalProfunctor) --> E
C --> F
D(SemisumProfunctor) --> F(SumProfunctor)
However, it gets awkward to use: SemigroupalProfunctor
and MonoidalProfunctor
require you to identify which tensor you're using when you define an instance:
import qualified Control.Category.Monoidal as C -- from package `categories`
class C.Associative (->) m => SemigroupalProfunctor m p | p -> m where
(!!!!) :: p a c -> p b d -> p (m a c) (m b d)
class (C.Monoidal (->) m, SemigroupalProfunctor m p) => MonoidalProfunctor m p | p -> m where
unit :: p (C.Id (->) m) (C.Id (->) m)
-- These merge their two arguments using (!!!!), then pull the unit off using
-- typeclass methods from `Monoidal`
lunit :: p (C.Id (->) m) (C.Id (->) m) -> p a b -> p a b
runit :: p a b -> p (C.Id (->) m) (C.Id (->) m) -> p a b
Even so, you can't put more than one MonoidalProfunctor
instance on a given profunctor, even when it would admit multiple, so you lock yourself to one side of the hierarchy unless you use newtype
and then your ergonomics of having a profunctor that can do both sums and products are gone.
Ironically, the reason I got into hacking on this package is that I want to do bidirectional printing/parsing. That is, you staple an encoder to a decoder like data EncDec a = EncDec (Encoder a) (Decoder a)
and build up a build up a bidirectional codec at every step, and then pick out the one you actually want at the use site. If you keep a parser and a printer next to each other, you don't get Applicative
or Divisible
; instead you get "monoidal endofunctor with (,)
as the tensor" (and similarly for Alternative
and Decidable
). Instead, people suggested I look into profunctors data EncDec a b = EncDec (Encoder a) (Decoder b)
and where you generally stay on the diagonal p a a
but can step off where really necessary. Then the sum/product profunctor machinery is a lot more ergonomic (particularly when you use something like generics-eot
).
So overall I'm not sure what benefit a common monoidal profunctor superclass gives you here.
Hope that illuminates somewhat; let me know if it doesn't.
In theory, you could build out this hierarchy:
However, it gets awkward to use:
SemigroupalProfunctor
andMonoidalProfunctor
require you to identify which tensor you're using when you define an instance:...
Even so, you can't put more than one
MonoidalProfunctor
instance on a given profunctor, even when it would admit multiple, so you lock yourself to one side of the hierarchy unless you usenewtype
and then your ergonomics of having a profunctor that can do both sums and products are gone.
I think I understand -- the same reasoning behind why e.g. defining a Semiring
class (or figuring out how to use it) is a bit obnoxious.
So overall I'm not sure what benefit a common monoidal profunctor superclass gives you here.
In the short run, perhaps not much, but what about generally Arrow
-like eDSL use cases where you want way more granularity than an Arrow
gives you -- e.g. you can't or don't want to write a definition for arr
, and hence profunctors
/product-profunctors
looks like the next most obvious choice?
For example, in Elliot 2018 the Cocartesian
instance is associated with (,)
rather than Either
. Even there however, I'd guess that for similar reasons to what you outlined (+/- simplicity of exposition in a paper), we can see class Monoidal k ⇒ Cartesian k
but not class Monoidal k ⇒ Cocartesian k
.
I'm not quite sure how Semiring
plays into it. class Semiring
defines both operations in a single class, so you can usually get away with one instance for each type. The problem we have here is that the sums and products we care about are at the type level, and it is not necessarily the case that a given type will be both a SumProfunctor
and a ProductProfunctor
. So you need to be able to say "this is a monoidal profunctor with (,)
as tensor" as well as "this is a monoidal profunctor with Either
as tensor", necessitating multi-param typeclass. Then you have to decide whether to add a fundep to that second parameter:
instance MonoidalProfunctor p (,)
and instance MonoidalProfunctor p Either
for the same p
(and if you define instance MonoidalProfunctor p (,)
you can't define instance SumProfunctor p
and vice versa);acts
— classes for monoid actions have never really caught on because of this).Arrows
I'm not sure what problems you foresee. SemiproductProfunctor
gives you (***)
and (&&&)
; you need Category
to get (>>>)
and maybe you need Strong
to get first
and second
. ArrowChoice
seems to be a combination of Choice
profunctors and SemisumProfunctor
. I have a suspicion that ArrowZero
corresponds to SumProfunctor
, but that there's no class corresponding to ProductProfunctor
because of the way arr
is put in.
Eliott 2018
I think it's more likely that (,)
is by far the most useful tensor when considering Hask as a monoidal category. There are some packages that are explicit about which tensor they use (e.g., monoidal-functors
), but the extra flexibility is not worth the notational overhead.
Also: What Elliot calls class Monoidal
is what we call class SemisumProfunctor
in #64 except with a Category
superclass. Not sure how that fits in.
with Tom Ellis