
Using 'hugs -98', I noticed it accepts: instance Monad m => Functor m where fmap f x = x >>= return.f Has this been considered (say) as a part of the upcoming Haskell Prime? Hans Aberg

Hans Aberg wrote:
Using 'hugs -98', I noticed it accepts: instance Monad m => Functor m where fmap f x = x >>= return.f
Has this been considered (say) as a part of the upcoming Haskell Prime?
This forbids any Functors which are not monads. Unless you allow overlapping instances (which of course would not be h98 any more!). Other solutions, such as class Functor m => Monad m are frequently discussed. I see no H' ticket for it, though. Jules

On 9 Apr 2008, at 11:26, Jules Bean wrote:
Using 'hugs -98', I noticed it accepts: instance Monad m => Functor m where fmap f x = x >>= return.f Has this been considered (say) as a part of the upcoming Haskell Prime?
This forbids any Functors which are not monads. Unless you allow overlapping instances...
I see it as a Haskell limitation of not being able to indicate the function names in the class definition head: If one could write say class Monoid (a; unit, mult) where unit :: a mult :: a -> a -> a then it is possible to say instance Monoid ([]; [], (++)) where -- 'unit' already defined -- definition of (++) Similarly: class Functor (m; fmap) where fmap :: (a -> b) -> (m a -> m b) instance Monad m => Functor (m, mmap) where mmap f x = x >>= return.f - For backwards compatibility, if the function names are not indicated, one gets the declaration names as default. I don't know if it is possible to extend the syntax this way, but it would be closer to math usage. And one would avoid duplicate definitions just to indicate different operator names, like: class AdditiveMonoid a where o :: a (+) :: a -> a -> a as it could be create using class Monoid (a; o, (+))
...(which of course would not be h98 any more!).
It does not work in 'hugs +98' mode; if I avoid the Prelude names by: class Munctor m where mmap :: (a -> b) -> (m a -> m b) instance Monad m => Munctor m where mmap f x = x >>= return.f I get ERROR - Syntax error in instance head (constructor expected)
Other solutions, such as class Functor m => Monad m are frequently discussed.
The point is that Monads have a code lifting property, so the functor is already conatained in the current definition. One might want to have away to override, so even if instance Monad m => Functor (m, mmap) functor specialization can take place if one has a more efficeint definition. For example instance Functor ([], mmap) where mmap = map Hans

On Wed, 9 Apr 2008, Hans Aberg wrote:
I don't know if it is possible to extend the syntax this way, but it would be closer to math usage. And one would avoid duplicate definitions just to indicate different operator names, like: class AdditiveMonoid a where o :: a (+) :: a -> a -> a as it could be create using class Monoid (a; o, (+))
I also recognized that problem in the past, but didn't know how to solve it. In Haskell 98, methods are resolved using the types of the operands. How would the compiler find out which implementation of (+) to choose for an expression like x+y using your approach?

On 9 Apr 2008, at 15:23, Henning Thielemann wrote:
I don't know if it is possible to extend the syntax this way, but it would be closer to math usage. And one would avoid duplicate definitions just to indicate different operator names, like: class AdditiveMonoid a where o :: a (+) :: a -> a -> a as it could be create using class Monoid (a; o, (+))
I also recognized that problem in the past, but didn't know how to solve it. In Haskell 98, methods are resolved using the types of the operands. How would the compiler find out which implementation of (+) to choose for an expression like x+y using your approach?
Different names result in different operator hierarchies. So a class like class Monoid (a; unit, mult) where unit :: a mult :: a -> a -> a must have an instantiation that specifies the names of the operators. In particular, one will need a class (Monoid (a; 0; (+)), ...) => Num a ... if (+) should be used as Monoid.(+) together with Num.(+). Or give an example you think may cause problems, and I will give it a try. Hans

On Wed, 9 Apr 2008, Hans Aberg wrote:
Different names result in different operator hierarchies. So a class like class Monoid (a; unit, mult) where unit :: a mult :: a -> a -> a must have an instantiation that specifies the names of the operators. In particular, one will need a class (Monoid (a; 0; (+)), ...) => Num a ... if (+) should be used as Monoid.(+) together with Num.(+).
Or give an example you think may cause problems, and I will give it a try.
I think a classical example are number sequences which can be considered as rings in two ways: 1. elementwise multiplication 2. convolution and you have some function which invokes the ring multiplication f :: Ring a => a -> a and a concrete sequence x :: Sequence Integer what multiplication (elementwise or convolution) shall be used for computing (f x) ?

On 9 Apr 2008, at 16:26, Henning Thielemann wrote:
I think a classical example are number sequences which can be considered as rings in two ways: 1. elementwise multiplication 2. convolution
and you have some function which invokes the ring multiplication
f :: Ring a => a -> a
and a concrete sequence
x :: Sequence Integer
what multiplication (elementwise or convolution) shall be used for computing (f x) ?
For that problem to arise, one must have, when defining Sequence class Ring (a; o, e, add, mult) ... class (Ring(a; o, e, add, (*)), Ring(a; o, e, add, (**)) => Sequence a It is a good question, but can be avoided by not admitting such constructs. - I will think a bit more on it. Hans

On 9 Apr 2008, at 16:26, Henning Thielemann wrote:
1. elementwise multiplication 2. convolution
and you have some function which invokes the ring multiplication
f :: Ring a => a -> a
and a concrete sequence
x :: Sequence Integer
what multiplication (elementwise or convolution) shall be used for computing (f x) ?
In math, if there is a theorem about a ring, and one wants to apply it to an object which more than one ring structure, one needs to indicate which ring to use. So if I translate, then one might get something like class Ring (a; o, e, add, mult) ... ... class Ring(a; o, e, add, (*)) => Sequence.mult a Ring(a; o, e, add, (**) => Sequence.conv a where ... Then Sequence.mult and Sequence.conv will be treated as different types whenever there is a clash using Sequence only. - I am not sure how this fits into Haskell syntax though. This might be useful, if it can be worked out. Hans

On Wed, 9 Apr 2008, Hans Aberg wrote:
On 9 Apr 2008, at 16:26, Henning Thielemann wrote:
1. elementwise multiplication 2. convolution
and you have some function which invokes the ring multiplication
f :: Ring a => a -> a
and a concrete sequence
x :: Sequence Integer
what multiplication (elementwise or convolution) shall be used for computing (f x) ?
In math, if there is a theorem about a ring, and one wants to apply it to an object which more than one ring structure, one needs to indicate which ring to use. So if I translate, then one might get something like class Ring (a; o, e, add, mult) ... ... class Ring(a; o, e, add, (*)) => Sequence.mult a Ring(a; o, e, add, (**) => Sequence.conv a where ... Then Sequence.mult and Sequence.conv will be treated as different types whenever there is a clash using Sequence only. - I am not sure how this fits into Haskell syntax though.
Additionally I see the problem, that we put more interpretation into standard symbols by convention. Programming is not only about the most general formulation of an algorithm but also about error detection. E.g. you cannot compare complex numbers in a natural way, that is x < (y :: Complex Rational) is probably a programming error. However, some people might be happy if (<) is defined by lexicgraphic ordering. This way complex numbers can be used as keys in a Data.Map. But then accidental uses of (<) could no longer be detected. (Thus I voted for a different class for keys to be used in Data.Map, Data.Set et.al.) Also (2*5 == 7) would surprise people, if (*) is the symbol for a general group operation, and we want to use it for the additive group of integers.

On 9 Apr 2008, at 17:49, Henning Thielemann wrote:
Additionally I see the problem, that we put more interpretation into standard symbols by convention. Programming is not only about the most general formulation of an algorithm but also about error detection. E.g. you cannot compare complex numbers in a natural way, that is x < (y :: Complex Rational) is probably a programming error. However, some people might be happy if (<) is defined by lexicgraphic ordering. This way complex numbers can be used as keys in a Data.Map. But then accidental uses of (<) could no longer be detected. (Thus I voted for a different class for keys to be used in Data.Map, Data.Set et.al.)
I think there it might be convenient with a total order defined on all types, for that data-map sorting purpose you indicate. But it would then be different from the semantic order that some types have. So the former should have a different name. Also, one might have Ordering(LT, EQ, GT, Unrelated) so t can be used on all relations.
Also (2*5 == 7) would surprise people, if (*) is the symbol for a general group operation, and we want to use it for the additive group of integers.
This is in fact as it should be; the idea is to admit such things: class Group(a; unit, inverse, mult) ... class (Group(a; 0, (-), (+)), Monoid(a; 1, (*)) => Ring(a; 0, 1, (-), (+), (*)) ... -- (or better variable names). instance Ring(a; 0, 1, (-), (+), (*)) => Integer A group can be written additively or multiplicatively, (+) is often reserved for commutative operations. But there is not way to express that, unless one can write class AbelianGroup(a; unit, inverse, mult) where ... satisfying mult a b = mult b a One would need pattern matching to Haskell in order to make this useful. Hans

On 9 Apr 2008, at 17:49, Henning Thielemann wrote:
Also (2*5 == 7) would surprise people, if (*) is the symbol for a general group operation, and we want to use it for the additive group of integers.
One might resolve the "Num" binding of (+) problem by putting all operators into an implicit superclass: Roughly, let T be the set of of most general types, and for each t in T define a mangling string s(t). Then if the operator <op> :: t is defined somewhere, it is internally defined as class Operator_s(t)_<op> t where <op> :: t Then usages of it get implicit class (Operator_s(t)_<op> t, ...) => <Class> where ... and instance Operator_s(t)_<op> t where ... If I now have another class using (+), it need not be derived from Num, as both usages are derivable from an internal class Operator_(+) The mangling of the type via s(t) might be used to generate C++ style name overloading. It will then depend on how much ambiguity one wants to accept in the context. I do not see exactly how this works with Haskell current syntax; just an input. Hans

On 9 Apr 2008, at 17:49, Henning Thielemann wrote:
Additionally I see the problem, that we put more interpretation into standard symbols by convention. Programming is not only about the most general formulation of an algorithm but also about error detection. E.g. you cannot compare complex numbers in a natural way, that is x < (y :: Complex Rational) is probably a programming error. However, some people might be happy if (<) is defined by lexicgraphic ordering. This way complex numbers can be used as keys in a Data.Map. But then accidental uses of (<) could no longer be detected. (Thus I voted for a different class for keys to be used in Data.Map, Data.Set et.al.)
If one just needs to compare equal and unequal elements, then a hash- map is faster than a balanced tree map, and a total order is not needed. So those that want to use complex numbers as keys perhaps have not considered that possibility. And if one considers a total order (<) for all data types, then if that includes functions, then it may happen that two equal functions f, g satisfy f < g. So it would not have the expected semantic properties. Hans

On 9 Apr 2008, at 15:23, Henning Thielemann wrote:
I also recognized that problem in the past, but didn't know how to solve it. In Haskell 98, methods are resolved using the types of the operands. How would the compiler find out which implementation of (+) to choose for an expression like x+y using your approach?
I might describe the idea via mangling. So if one has class Magma (a; unit, mult) where unit :: a mult :: a -> a -> a then instances Monoid (a; 0; (+)) Monoid (a; 1; (*)) should logically equivalent to Monoid_0_+ (a) 0 :: a (+) :: a -> a -> a Monoid_1_* (a) 1 :: a (*) :: a -> a -> a or whatever internal mangling that ensures that the names Monoid_0_+ and Monoid_1_* are different. Would this not work? - They code should be essentially a shortcut for defining new classes. Hans

G'day all.
Quoting Jules Bean
Other solutions, such as class Functor m => Monad m are frequently discussed.
I see no H' ticket for it, though.
Then add it. :-) You'll probably want to make it depend on Ticket #101, because making class hierarchies more granular generally depends on flexible instances. Cheers, Andrew Bromage
participants (4)
-
ajb@spamcop.net
-
Hans Aberg
-
Henning Thielemann
-
Jules Bean