Re: [Haskell-cafe] Proposal: add Monoid1 and Semigroup1 classes

CC-ing the Café on class naming... On 2016-10-01 04:07 AM, Edward Kmett wrote:
I'm somewhat weakly against these, simply because they haven't seen broad adoption in the wild in any of the attempts to introduce them elsewhere, and they don't quite fit the naming convention of the other Foo1 classes in Data.Functor.Classes
Eq1 f says more or less that Eq a => Eq (f a).
Semigroup1 in your proposal makes a stronger claim. Semgiroup1 f is saying forall a. (f a) is a semigroup parametrically. Both of these constructions could be useful, but they ARE different constructions.
The standard fully parametric classes like Functor and Monad have no suffix at all. It makes sense to reserve the suffix "1" for non-parametric lifting classes. Can you suggest a different naming scheme for parametric classes of a higher order? I'm also guilty of abusing the suffix "1", at least provisionally, but these are different beasts yet again: -- | Equivalent of 'Functor' for rank 2 data types class Functor1 g where fmap1 :: (forall a. p a -> q a) -> g p -> g q https://github.com/blamario/grampa/blob/master/Text/Grampa/Classes.hs What would be a proper suffix here? I guess Functor2 would make sense, for a rank-2 type?
If folks had actually been using, say, the Plus and Alt classes from semigroupoids or the like more or less at all pretty much anywhere, I could maybe argue towards bringing them up towards base, but I've seen almost zero adoption of the ideas over multiple years -- and these represent yet _another_ point in the design space where we talk about semigroupal and monoidal structures where f is a Functor instead. =/
Many points in the design space, and little demonstrated will for adoption seems to steers me to think that the community isn't ready to pick one and enshrine it some place central yet.
Overall, -1.
-Edward
On Fri, Sep 30, 2016 at 7:25 PM, David Feuer
mailto:david.feuer@gmail.com> wrote: I've been playing around with the idea of writing Haskell 2010 type classes for finite sequences and non-empty sequences, somewhat similar to Michael Snoyman's Sequence class in mono-traversable. These are naturally based on Monoid1 and Semigroup1, which I think belong in base.
class Semigroup1 f where (<<>>) :: f a -> f a -> f a class Semigroup1 f => Monoid1 f where mempty1 :: f a
Then I can write
class (Monoid1 t, Traversable t) => Sequence t where singleton :: a -> t a -- and other less-critical methods
class (Semigroup1 t, Traversable1 t) => NESequence where singleton1 :: a -> t a -- etc.
I can, of course, just write my own, but I don't think I'm the only one using such.
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Let's just pause and consider what is already available on hackage today
for these situations:
In my constraints package I have a class named `Lifting`, which provides.
class Lifting p f where
lifting :: p a :- p (f a)
Lifting Eq, Lifting Monad, Lifting Semigroup, Lifting (MonadReader e), etc.
are then able to be handled all uniformly.
It is, alas, somewhat annoying to use, as you need to use `\\ lifting` with
a scoped type variable signature to get the instance in scope
The currrent Eq1 is a somewhat more powerful claim though, since you can
supply the equality for its argument without needing functoriality in f.
This is both good and bad. It means you can't just write `instance Eq1 f`
and let default methods take over, but it does mean Eq1 f works in more
situations if you put in the work or use generics to generate it
automatically.
http://hackage.haskell.org/package/constraints-0.8/docs/Data-Constraint-Lift...
For the rank-2 situation, I also have `Forall` and `ForallF` which provides
the ability to talk about the quantified form.
ForallF Eq f is defined by a fancy skolem type family trick and comes with
instF :: forall p f a. ForallF p f :- p (f a)
This covers the rank-2 situation today pretty well, even if you have to use
`\\ instF` or what have you to get the instance in scope.
I don't however, have something in a "mainstream" package for that third
form mentioned above, the 'Functor'-like form, but I do have classes in
semgroupoids for Alt, Plus, etc. covering the particular
semigroup/monoid-like cases.
Finally, going very far off the beaten and well-supported path, in `hask`,
I have code for talking about entailment in the category of constraints,
but like the above two tricks, it requires the user to explicitly bring the
instance into scope from an `Eq a |- Eq (f a)` constraint or the like, and
the more general form of `|-` lifts into not just Constraint, but k ->
Constraint, and combines with Lim functor to provide quantified entailment.
This doesn't compromise the thinness of the category of constraints. I'd
love to see compiler support for this, eliminating the need for the \\
nonsense above, but it'd be a fair bit of work!
-Edward
On Sat, Oct 1, 2016 at 2:10 PM, Mario Blažević
CC-ing the Café on class naming...
On 2016-10-01 04:07 AM, Edward Kmett wrote:
I'm somewhat weakly against these, simply because they haven't seen broad adoption in the wild in any of the attempts to introduce them elsewhere, and they don't quite fit the naming convention of the other Foo1 classes in Data.Functor.Classes
Eq1 f says more or less that Eq a => Eq (f a).
Semigroup1 in your proposal makes a stronger claim. Semgiroup1 f is saying forall a. (f a) is a semigroup parametrically. Both of these constructions could be useful, but they ARE different constructions.
The standard fully parametric classes like Functor and Monad have no suffix at all. It makes sense to reserve the suffix "1" for non-parametric lifting classes. Can you suggest a different naming scheme for parametric classes of a higher order?
I'm also guilty of abusing the suffix "1", at least provisionally, but these are different beasts yet again:
-- | Equivalent of 'Functor' for rank 2 data types class Functor1 g where fmap1 :: (forall a. p a -> q a) -> g p -> g q
https://github.com/blamario/grampa/blob/master/Text/Grampa/Classes.hs
What would be a proper suffix here? I guess Functor2 would make sense, for a rank-2 type?
If folks had actually been using, say, the Plus and Alt classes from semigroupoids or the like more or less at all pretty much anywhere, I could maybe argue towards bringing them up towards base, but I've seen almost zero adoption of the ideas over multiple years -- and these represent yet _another_ point in the design space where we talk about semigroupal and monoidal structures where f is a Functor instead. =/
Many points in the design space, and little demonstrated will for adoption seems to steers me to think that the community isn't ready to pick one and enshrine it some place central yet.
Overall, -1.
-Edward
On Fri, Sep 30, 2016 at 7:25 PM, David Feuer
mailto:david.feuer@gmail.com> wrote: I've been playing around with the idea of writing Haskell 2010 type classes for finite sequences and non-empty sequences, somewhat similar to Michael Snoyman's Sequence class in mono-traversable. These are naturally based on Monoid1 and Semigroup1, which I think belong in base.
class Semigroup1 f where (<<>>) :: f a -> f a -> f a class Semigroup1 f => Monoid1 f where mempty1 :: f a
Then I can write
class (Monoid1 t, Traversable t) => Sequence t where singleton :: a -> t a -- and other less-critical methods
class (Semigroup1 t, Traversable1 t) => NESequence where singleton1 :: a -> t a -- etc.
I can, of course, just write my own, but I don't think I'm the only one using such.
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

The difficulty and inconvenience of using Forall and the fact that it is
very far from standard Haskell make it unsuitable for some purposes. I
believe it can probably lead to some efficiency issues as well, since the
constraint has to be instantiated manually at each type; perhaps GHC can
optimize that away. It would be fantastic if the language could expand to
allow such constraints natively, but for now it seems that manually writing
multiple classes is often the best approach.
On Oct 1, 2016 5:24 PM, "Edward Kmett"
Let's just pause and consider what is already available on hackage today for these situations:
In my constraints package I have a class named `Lifting`, which provides.
class Lifting p f where lifting :: p a :- p (f a)
Lifting Eq, Lifting Monad, Lifting Semigroup, Lifting (MonadReader e), etc. are then able to be handled all uniformly.
It is, alas, somewhat annoying to use, as you need to use `\\ lifting` with a scoped type variable signature to get the instance in scope
The currrent Eq1 is a somewhat more powerful claim though, since you can supply the equality for its argument without needing functoriality in f. This is both good and bad. It means you can't just write `instance Eq1 f` and let default methods take over, but it does mean Eq1 f works in more situations if you put in the work or use generics to generate it automatically.
http://hackage.haskell.org/package/constraints-0.8/docs/ Data-Constraint-Lifting.html
For the rank-2 situation, I also have `Forall` and `ForallF` which provides the ability to talk about the quantified form.
ForallF Eq f is defined by a fancy skolem type family trick and comes with
instF :: forall p f a. ForallF p f :- p (f a)
This covers the rank-2 situation today pretty well, even if you have to use `\\ instF` or what have you to get the instance in scope.
I don't however, have something in a "mainstream" package for that third form mentioned above, the 'Functor'-like form, but I do have classes in semgroupoids for Alt, Plus, etc. covering the particular semigroup/monoid-like cases.
Finally, going very far off the beaten and well-supported path, in `hask`, I have code for talking about entailment in the category of constraints, but like the above two tricks, it requires the user to explicitly bring the instance into scope from an `Eq a |- Eq (f a)` constraint or the like, and the more general form of `|-` lifts into not just Constraint, but k -> Constraint, and combines with Lim functor to provide quantified entailment. This doesn't compromise the thinness of the category of constraints. I'd love to see compiler support for this, eliminating the need for the \\ nonsense above, but it'd be a fair bit of work!
-Edward
On Sat, Oct 1, 2016 at 2:10 PM, Mario Blažević
wrote: CC-ing the Café on class naming...
On 2016-10-01 04:07 AM, Edward Kmett wrote:
I'm somewhat weakly against these, simply because they haven't seen broad adoption in the wild in any of the attempts to introduce them elsewhere, and they don't quite fit the naming convention of the other Foo1 classes in Data.Functor.Classes
Eq1 f says more or less that Eq a => Eq (f a).
Semigroup1 in your proposal makes a stronger claim. Semgiroup1 f is saying forall a. (f a) is a semigroup parametrically. Both of these constructions could be useful, but they ARE different constructions.
The standard fully parametric classes like Functor and Monad have no suffix at all. It makes sense to reserve the suffix "1" for non-parametric lifting classes. Can you suggest a different naming scheme for parametric classes of a higher order?
I'm also guilty of abusing the suffix "1", at least provisionally, but these are different beasts yet again:
-- | Equivalent of 'Functor' for rank 2 data types class Functor1 g where fmap1 :: (forall a. p a -> q a) -> g p -> g q
https://github.com/blamario/grampa/blob/master/Text/Grampa/Classes.hs
What would be a proper suffix here? I guess Functor2 would make sense, for a rank-2 type?
If folks had actually been using, say, the Plus and Alt classes from semigroupoids or the like more or less at all pretty much anywhere, I could maybe argue towards bringing them up towards base, but I've seen almost zero adoption of the ideas over multiple years -- and these represent yet _another_ point in the design space where we talk about semigroupal and monoidal structures where f is a Functor instead. =/
Many points in the design space, and little demonstrated will for adoption seems to steers me to think that the community isn't ready to pick one and enshrine it some place central yet.
Overall, -1.
-Edward
On Fri, Sep 30, 2016 at 7:25 PM, David Feuer
mailto:david.feuer@gmail.com> wrote: I've been playing around with the idea of writing Haskell 2010 type classes for finite sequences and non-empty sequences, somewhat similar to Michael Snoyman's Sequence class in mono-traversable. These are naturally based on Monoid1 and Semigroup1, which I think belong in base.
class Semigroup1 f where (<<>>) :: f a -> f a -> f a class Semigroup1 f => Monoid1 f where mempty1 :: f a
Then I can write
class (Monoid1 t, Traversable t) => Sequence t where singleton :: a -> t a -- and other less-critical methods
class (Semigroup1 t, Traversable1 t) => NESequence where singleton1 :: a -> t a -- etc.
I can, of course, just write my own, but I don't think I'm the only one using such.
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

If folks had actually been using, say, the Plus and Alt classes from semigroupoids or the like more or less at all pretty much anywhere, I could maybe argue towards bringing them up towards base, but I've seen almost zero adoption of the ideas over multiple years -- and these represent yet _another_ point in the design space where we talk about semigroupal and monoidal structures where f is a Functor instead. =/
FWIW, very rarely do I write a package without semigroups and/or semigroupoids; sometimes for "not very important" or superficial reasons, but more typically otherwise. Even something as disparate as a CASR61.345 compliant pilot logbook uses both packages heavily, and for good reason (it says/implies so in the law!). Why others chooses to forgo the advantages is beyond me. Just a data point, cheerio!

On 01/10/16 15:10, Mario Blažević wrote:
CC-ing the Café on class naming...
On 2016-10-01 04:07 AM, Edward Kmett wrote:
I'm somewhat weakly against these, simply because they haven't seen broad adoption in the wild in any of the attempts to introduce them elsewhere, and they don't quite fit the naming convention of the other Foo1 classes in Data.Functor.Classes
Basically this. What is popular on hackage should be the first metric to consider when putting something in base (even if it fits well on a module in there), we ought to not bypass this. BTW, I think that Alt newtype in Data.Monoid helps with this use case but that is usually for Alternative instead of Functor (to me just really esoteric things are one and not the other), am I missing something else on this proposal?
participants (5)
-
David Feuer
-
Edward Kmett
-
Mario Blažević
-
Ruben Astudillo
-
Tony Morris