mtl: Why there is "Monoid w" constraint in the definition of class MonadWriter?

The class is defined as
class (Monoid w, Monad m) => MonadWriter w m | m -> w where ...
What is the reason for the Monoid constrait? It seems superfluous to me. I recompiled the whole package without it, with no problems. Of course, the Monoid constraint is necessary for most _instances_, like in
instance (Monoid w, Monad m) => MonadWriter w (Lazy.WriterT w m) where ...
but this is a different thing - it depends on how the particular instance is implemented. I encountered the problem when I needed to define an instance where the monoidal structure is fixed (Last) and I didn't want to expose it to the user. I wanted to spare the user of of having to write Last/getLast everywhere. (I have an instance of MonadWriter independent of WriterT, its 'tell' saves values to a MVar. Functions 'listen' and 'pass' create a new temporary MVar. I can post the detail, if anybody is interested.) Would anything break by removing the constraint? I think the type class would get a bit more general this way. Thanks for help, Petr Pudlak

The monoid instance is necessary to ensure adherence to the monad laws. Cheers, Edward Excerpts from Petr P's message of Sat Dec 08 10:59:25 -0800 2012:
The class is defined as
class (Monoid w, Monad m) => MonadWriter w m | m -> w where ...
What is the reason for the Monoid constrait? It seems superfluous to me. I recompiled the whole package without it, with no problems.
Of course, the Monoid constraint is necessary for most _instances_, like in
instance (Monoid w, Monad m) => MonadWriter w (Lazy.WriterT w m) where ...
but this is a different thing - it depends on how the particular instance is implemented.
I encountered the problem when I needed to define an instance where the monoidal structure is fixed (Last) and I didn't want to expose it to the user. I wanted to spare the user of of having to write Last/getLast everywhere. (I have an instance of MonadWriter independent of WriterT, its 'tell' saves values to a MVar. Functions 'listen' and 'pass' create a new temporary MVar. I can post the detail, if anybody is interested.)
Would anything break by removing the constraint? I think the type class would get a bit more general this way.
Thanks for help, Petr Pudlak

* Edward Z. Yang
The monoid instance is necessary to ensure adherence to the monad laws.
This doesn't make any sense to me. Are you sure you're talking about the MonadWriter class and not about the Writer monad? Roman

Excerpts from Roman Cheplyaka's message of Sat Dec 08 14:00:52 -0800 2012:
* Edward Z. Yang
[2012-12-08 11:19:01-0800] The monoid instance is necessary to ensure adherence to the monad laws.
This doesn't make any sense to me. Are you sure you're talking about the MonadWriter class and not about the Writer monad?
Well, I assume the rules for Writer generalize for MonadWriter, no? Here's an example. Haskell monads have the associativity law: (f >=> g) >=> h === f >=> (g >=> h)
From this, we can see that
(m1 >> m2) >> m3 === m1 >> (m2 >> m3) Now, consider tell. We'd expect it to obey a law like this: tell w1 >> tell w2 === tell (w1 <> w2) Combine this with the monad associativity law: (tell w1 >> tell w2) >> tell w3 === tell w1 >> (tell w2 >> tell w3) And it's easy to see that '<>' must be associative in order for this law to be upheld. Additionally, the existence of identities in monads means that there must be a corresponding identity for the monoid. So anything that is "writer-like" and also satisfies the monad laws... is going to be a monoid. Now, it's possible what GP is actually asking about is more a question of encapsulation. Well, one answer is, "Well, just give the user specialized functions which do the appropriate wrapping/unwrapping"; another answer is, "if you let the user run a writer action and extract the resulting written value, then he can always reverse engineer the monoid instance out of it". Edward

* Edward Z. Yang
Excerpts from Roman Cheplyaka's message of Sat Dec 08 14:00:52 -0800 2012:
* Edward Z. Yang
[2012-12-08 11:19:01-0800] The monoid instance is necessary to ensure adherence to the monad laws.
This doesn't make any sense to me. Are you sure you're talking about the MonadWriter class and not about the Writer monad?
Well, I assume the rules for Writer generalize for MonadWriter, no?
Here's an example. Haskell monads have the associativity law:
(f >=> g) >=> h === f >=> (g >=> h)
From this, we can see that
(m1 >> m2) >> m3 === m1 >> (m2 >> m3)
Now, consider tell. We'd expect it to obey a law like this:
tell w1 >> tell w2 === tell (w1 <> w2)
First of all, I don't see why two tells should be equivalent to one tell. Imagine a MonadWriter that additionally records the number of times 'tell' has been called. (You might argue that your last equation should be a MonadWriter class law, but that's a different story — we're talking about the Monad laws here.) Second, even *if* the above holds (two tells are equivalent to one tell), then there is *some* function f such that tell w1 >> tell w2 == tell (f w1 w2) It isn't necessary that f coincides with mappend, or even that the type w is declared as a Monoid at all. The only thing we can tell from the Monad laws is that that function f should be associative. Roman

The only thing we can tell from the Monad laws is that that function f should be associative.
That f is associative is a very small step away from f forming a monoid.
What about listen :: m a -> m (w, a)? What laws should it hold that are
compatible with those of the monad and those of tell? Reasoning about
listen is enough to force the existence of a monoid identity.
-- Kim-Ee
On Sun, Dec 9, 2012 at 5:41 AM, Roman Cheplyaka
Excerpts from Roman Cheplyaka's message of Sat Dec 08 14:00:52 -0800 2012:
* Edward Z. Yang
[2012-12-08 11:19:01-0800] The monoid instance is necessary to ensure adherence to the monad laws.
This doesn't make any sense to me. Are you sure you're talking about
* Edward Z. Yang
[2012-12-08 14:18:38-0800] the MonadWriter class and not about the Writer monad?
Well, I assume the rules for Writer generalize for MonadWriter, no?
Here's an example. Haskell monads have the associativity law:
(f >=> g) >=> h === f >=> (g >=> h)
From this, we can see that
(m1 >> m2) >> m3 === m1 >> (m2 >> m3)
Now, consider tell. We'd expect it to obey a law like this:
tell w1 >> tell w2 === tell (w1 <> w2)
First of all, I don't see why two tells should be equivalent to one tell. Imagine a MonadWriter that additionally records the number of times 'tell' has been called. (You might argue that your last equation should be a MonadWriter class law, but that's a different story — we're talking about the Monad laws here.)
Second, even *if* the above holds (two tells are equivalent to one tell), then there is *some* function f such that
tell w1 >> tell w2 == tell (f w1 w2)
It isn't necessary that f coincides with mappend, or even that the type w is declared as a Monoid at all. The only thing we can tell from the Monad laws is that that function f should be associative.
Roman
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

First of all, I don't see why two tells should be equivalent to one tell. Imagine a MonadWriter that additionally records the number of times 'tell' has been called. (You might argue that your last equation should be a MonadWriter class law, but that's a different story — we're talking about the Monad laws here.)
Yes, I think I would argue that my equation should be a MonadWriter class law, and if you don't grant me that, I don't have a leg to stand on.
Second, even *if* the above holds (two tells are equivalent to one tell), then there is *some* function f such that
tell w1 >> tell w2 == tell (f w1 w2)
It isn't necessary that f coincides with mappend, or even that the type w is declared as a Monoid at all. The only thing we can tell from the Monad laws is that that function f should be associative.
Well, the function is associative: that's half of the way there to a monoid; all you need is the identity! But we have those too: whatever the value of the execWriter (return ()) is... Cheers, Edward

* Edward Z. Yang
Second, even *if* the above holds (two tells are equivalent to one tell), then there is *some* function f such that
tell w1 >> tell w2 == tell (f w1 w2)
It isn't necessary that f coincides with mappend, or even that the type w is declared as a Monoid at all. The only thing we can tell from the Monad laws is that that function f should be associative.
Well, the function is associative: that's half of the way there to a monoid; all you need is the identity! But we have those too: whatever the value of the execWriter (return ()) is...
Let me repeat: It isn't necessary that f coincides with mappend, or even that the type w is declared as a Monoid at all. Let me illustrate this with an example. data MyWriter a = MyWriter Integer a instance Monad MyWriter where return = MyWriter 0 MyWriter n x >>= k = let MyWriter n' y = k x in MyWriter (n+n') y instance MonadWriter Integer MyWriter where tell n = MyWriter n () listen (MyWriter n x) = return (x,n) pass (MyWriter n (a,f)) = MyWriter (f n) a Yes, integers do form a monoid when equipped with 0 and (+). However, we know well why they are not an instance of Monoid — namely, there's more than one way they form a monoid. Even if something is in theory a monoid, there may be technical reasons not to declare it a Monoid. Likewise, imposing a (technical) superclass constraint on MonadWriter has nothing to do with whether the Monad will be well-behaved. This is true in both directions: even if the type is an instance of Monoid, nothing forces the Monad instance to use the Monoid instance. I.e. I can declare a MonadWriter on the Sum newtype whose bind, instead of adding, subtracts the numbers. Roman

Hi all,
I'd say that a type class declares functions and specifies laws (in the
docs)
what its implementations must adhere to. It's not the job of a type class to
fulfill the laws, it's the job of its implementations. So the reason for
'Monoid w' in 'MonadWriter' cannot be that then 'MonadWriter' wouldn't be a
monad. Such constraints should be required only by implementations.
It is true that any Writer has an implicit underlying monoid, and we can
even "extract" the operations from it as follows. The empty element can be
extracted as
empty = liftM snd (listen (return ())) :: m w
Having this 'empty', we can give 'const empty' to 'pass' to discard output
of
an action, so we can construct:
-- | @contained m@ executes the action @m@ in a contained environment
and
-- returns its value and its output. The current output is not modified.
contained :: m a -> m (a, w)
contained k = do
-- we can retrieve mempty even if we don't have the monoid
constraint:
~(_, empty) <- listen (return ())
-- listen what @k@ does, get its result and ignore its output
change:
pass (listen k >>= \x -> return (x, const empty))
This generalizes 'listen' and 'pass' (both can be easily defined from it)
and I find this function much easier to understand. In a way, it is also a
generalization of WriterT's runWriterT, because for WriterT we have
'contained = lift . runWriterT'.
[I implemented 'contained' in a fork of the mtl library, if anybody is
interested: https://github.com/ppetr/mtl ]
With that, we can do
-- Doesn't produce any output, only returns the combination
-- of the arguments.
append x y = liftM snd $ contained (tell x >> tell y) :: w -> w -> m w
I didn't check the monoid laws, but it seems obvious that they follow from
the
monad laws and (a bit vague) specification of 'listen' and 'pass'.
Personally, I'd find it better if `MonadWriter` would be split into two
levels:
One with just 'tell' and 'writer' and the next level extending it with
'listen'/'pass'/'contained'. The first level would allow things like
logging to
a file, without any monoidal structure. But this would break a lot of stuff
(until we agree on and develop something like
http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances).
Best regards,
Petr
2012/12/9 Roman Cheplyaka
* Edward Z. Yang
[2012-12-08 15:45:54-0800] Second, even *if* the above holds (two tells are equivalent to one tell), then there is *some* function f such that
tell w1 >> tell w2 == tell (f w1 w2)
It isn't necessary that f coincides with mappend, or even that the type w is declared as a Monoid at all. The only thing we can tell from the Monad laws is that that function f should be associative.
Well, the function is associative: that's half of the way there to a monoid; all you need is the identity! But we have those too: whatever the value of the execWriter (return ()) is...
Let me repeat:
It isn't necessary that f coincides with mappend, or even that the type w is declared as a Monoid at all.
Let me illustrate this with an example.
data MyWriter a = MyWriter Integer a
instance Monad MyWriter where return = MyWriter 0 MyWriter n x >>= k = let MyWriter n' y = k x in MyWriter (n+n') y
instance MonadWriter Integer MyWriter where tell n = MyWriter n () listen (MyWriter n x) = return (x,n) pass (MyWriter n (a,f)) = MyWriter (f n) a
Yes, integers do form a monoid when equipped with 0 and (+). However, we know well why they are not an instance of Monoid — namely, there's more than one way they form a monoid.
Even if something is in theory a monoid, there may be technical reasons not to declare it a Monoid. Likewise, imposing a (technical) superclass constraint on MonadWriter has nothing to do with whether the Monad will be well-behaved.
This is true in both directions: even if the type is an instance of Monoid, nothing forces the Monad instance to use the Monoid instance. I.e. I can declare a MonadWriter on the Sum newtype whose bind, instead of adding, subtracts the numbers.
Roman

An additional thought: I'd say 'contained' is sort of inverse to 'writer':
writer <=< contained = id
contained . writer = return
Petr Pudlak
2012/12/9 Petr P
Hi all,
I'd say that a type class declares functions and specifies laws (in the docs) what its implementations must adhere to. It's not the job of a type class to fulfill the laws, it's the job of its implementations. So the reason for 'Monoid w' in 'MonadWriter' cannot be that then 'MonadWriter' wouldn't be a monad. Such constraints should be required only by implementations.
It is true that any Writer has an implicit underlying monoid, and we can even "extract" the operations from it as follows. The empty element can be extracted as
empty = liftM snd (listen (return ())) :: m w
Having this 'empty', we can give 'const empty' to 'pass' to discard output of an action, so we can construct:
-- | @contained m@ executes the action @m@ in a contained environment and -- returns its value and its output. The current output is not modified. contained :: m a -> m (a, w) contained k = do -- we can retrieve mempty even if we don't have the monoid constraint: ~(_, empty) <- listen (return ()) -- listen what @k@ does, get its result and ignore its output change: pass (listen k >>= \x -> return (x, const empty))
This generalizes 'listen' and 'pass' (both can be easily defined from it) and I find this function much easier to understand. In a way, it is also a generalization of WriterT's runWriterT, because for WriterT we have 'contained = lift . runWriterT'.
[I implemented 'contained' in a fork of the mtl library, if anybody is interested: https://github.com/ppetr/mtl ]
With that, we can do
-- Doesn't produce any output, only returns the combination -- of the arguments. append x y = liftM snd $ contained (tell x >> tell y) :: w -> w -> m w
I didn't check the monoid laws, but it seems obvious that they follow from the monad laws and (a bit vague) specification of 'listen' and 'pass'.
Personally, I'd find it better if `MonadWriter` would be split into two levels: One with just 'tell' and 'writer' and the next level extending it with 'listen'/'pass'/'contained'. The first level would allow things like logging to a file, without any monoidal structure. But this would break a lot of stuff (until we agree on and develop something like http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances).
Best regards, Petr
2012/12/9 Roman Cheplyaka
* Edward Z. Yang
[2012-12-08 15:45:54-0800] Second, even *if* the above holds (two tells are equivalent to one tell), then there is *some* function f such that
tell w1 >> tell w2 == tell (f w1 w2)
It isn't necessary that f coincides with mappend, or even that the type w is declared as a Monoid at all. The only thing we can tell from the Monad laws is that that function f should be associative.
Well, the function is associative: that's half of the way there to a monoid; all you need is the identity! But we have those too: whatever the value of the execWriter (return ()) is...
Let me repeat:
It isn't necessary that f coincides with mappend, or even that the type w is declared as a Monoid at all.
Let me illustrate this with an example.
data MyWriter a = MyWriter Integer a
instance Monad MyWriter where return = MyWriter 0 MyWriter n x >>= k = let MyWriter n' y = k x in MyWriter (n+n') y
instance MonadWriter Integer MyWriter where tell n = MyWriter n () listen (MyWriter n x) = return (x,n) pass (MyWriter n (a,f)) = MyWriter (f n) a
Yes, integers do form a monoid when equipped with 0 and (+). However, we know well why they are not an instance of Monoid — namely, there's more than one way they form a monoid.
Even if something is in theory a monoid, there may be technical reasons not to declare it a Monoid. Likewise, imposing a (technical) superclass constraint on MonadWriter has nothing to do with whether the Monad will be well-behaved.
This is true in both directions: even if the type is an instance of Monoid, nothing forces the Monad instance to use the Monoid instance. I.e. I can declare a MonadWriter on the Sum newtype whose bind, instead of adding, subtracts the numbers.
Roman

I guess you have a point here: 1. The definition of the MonadWriter operations does not need the Monoid operations. Hence, the class constraint Monoid w should be removed. 2. The formulation of the MonadWriter laws (which are sadly missing from the documentation) would need the Monoid operations, though, e.g. tell v >> tell w = tell (v <> w) This is a weak indication that a constraint Monoid w should be present. However, currently Haskell does not provide a formal specification of laws (except maybe as RULES!?), so having the constraint here is a bit too eager. The story would be different in Agda... Indeed, if one wants Roman's MyWriter to be an instance of MonadWriter, one needs to declare an annoying fake monoid instance for Integer. {-# LANGUAGE MultiParamTypeClasses, DeriveFunctor, GeneralizedNewtypeDeriving #-} import Control.Arrow import Control.Applicative import Control.Monad.Writer import Data.Monoid newtype MyWriter a = MyWriter { myWriter :: Writer (Sum Integer) a } deriving (Functor, Monad) instance Monoid Integer where instance MonadWriter Integer MyWriter where tell w = MyWriter $ tell $ Sum w listen m = MyWriter $ (id *** getSum) <$> listen (myWriter m) pass m = MyWriter $ pass $ (id *** \ f -> Sum . f . getSum) <$> myWriter m Petr, you might wanna make a propsal to remove the Monoid w constraint to libraries@haskell.org, summarizing the current state of discussion so far. Cheers, Andreas On 09.12.2012 11:04, Petr P wrote:
Hi all,
I'd say that a type class declares functions and specifies laws (in the docs) what its implementations must adhere to. It's not the job of a type class to fulfill the laws, it's the job of its implementations. So the reason for 'Monoid w' in 'MonadWriter' cannot be that then 'MonadWriter' wouldn't be a monad. Such constraints should be required only by implementations.
It is true that any Writer has an implicit underlying monoid, and we can even "extract" the operations from it as follows. The empty element can be extracted as
empty = liftM snd (listen (return ())) :: m w
Having this 'empty', we can give 'const empty' to 'pass' to discard output of an action, so we can construct:
-- | @contained m@ executes the action @m@ in a contained environment and -- returns its value and its output. The current output is not modified. contained :: m a -> m (a, w) contained k = do -- we can retrieve mempty even if we don't have the monoid constraint: ~(_, empty) <- listen (return ())
This seems a contrived way of getting 'empty'. In this case, I prefer the monoid instance.
-- listen what @k@ does, get its result and ignore its output change: pass (listen k >>= \x -> return (x, const empty))
This generalizes 'listen' and 'pass' (both can be easily defined from it) and I find this function much easier to understand. In a way, it is also a generalization of WriterT's runWriterT, because for WriterT we have 'contained = lift . runWriterT'.
[I implemented 'contained' in a fork of the mtl library, if anybody is interested: https://github.com/ppetr/mtl ]
With that, we can do
-- Doesn't produce any output, only returns the combination -- of the arguments. append x y = liftM snd $ contained (tell x >> tell y) :: w -> w -> m w
I didn't check the monoid laws, but it seems obvious that they follow from the monad laws and (a bit vague) specification of 'listen' and 'pass'.
Personally, I'd find it better if `MonadWriter` would be split into two levels: One with just 'tell' and 'writer' and the next level extending it with 'listen'/'pass'/'contained'. The first level would allow things like logging to a file, without any monoidal structure. But this would break a lot of stuff (until we agree on and develop something like http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances).
Best regards, Petr
2012/12/9 Roman Cheplyaka
mailto:roma@ro-che.info> * Edward Z. Yang
mailto:ezyang@MIT.EDU> [2012-12-08 15:45:54-0800] > > Second, even *if* the above holds (two tells are equivalent to one > > tell), then there is *some* function f such that > > > > tell w1 >> tell w2 == tell (f w1 w2) > > > > It isn't necessary that f coincides with mappend, or even that the type > > w is declared as a Monoid at all. The only thing we can tell from the > > Monad laws is that that function f should be associative. > > Well, the function is associative: that's half of the way there to > a monoid; all you need is the identity! But we have those too: > whatever the value of the execWriter (return ()) is... Let me repeat:
It isn't necessary that f coincides with mappend, or even that the type w is declared as a Monoid at all.
Let me illustrate this with an example.
data MyWriter a = MyWriter Integer a
instance Monad MyWriter where return = MyWriter 0 MyWriter n x >>= k = let MyWriter n' y = k x in MyWriter (n+n') y
instance MonadWriter Integer MyWriter where tell n = MyWriter n () listen (MyWriter n x) = return (x,n) pass (MyWriter n (a,f)) = MyWriter (f n) a
Yes, integers do form a monoid when equipped with 0 and (+). However, we know well why they are not an instance of Monoid — namely, there's more than one way they form a monoid.
Even if something is in theory a monoid, there may be technical reasons not to declare it a Monoid. Likewise, imposing a (technical) superclass constraint on MonadWriter has nothing to do with whether the Monad will be well-behaved.
This is true in both directions: even if the type is an instance of Monoid, nothing forces the Monad instance to use the Monoid instance. I.e. I can declare a MonadWriter on the Sum newtype whose bind, instead of adding, subtracts the numbers.
Roman
-- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

Am 08.12.2012 um 23:18 schrieb Edward Z. Yang:
Excerpts from Roman Cheplyaka's message of Sat Dec 08 14:00:52 -0800 2012:
* Edward Z. Yang
[2012-12-08 11:19:01-0800] The monoid instance is necessary to ensure adherence to the monad laws.
This doesn't make any sense to me. Are you sure you're talking about the MonadWriter class and not about the Writer monad?
(...)
Now, it's possible what GP is actually asking about is more a question of encapsulation. Well, one answer is, "Well, just give the user specialized functions which do the appropriate wrapping/unwrapping"; another answer is, "if you let the user run a writer action and extract the resulting written value, then he can always reverse engineer the monoid instance out of it".
For deriving a monoid instance of w from monad (Writer w), you will need function execWriter:: Writer w a -> w, but in case of a general instance of (MonadWriter w m) you would have to use function listen :: m a -> m (a, w) that will only provide you a value of type (m w), but not of type w. Therefore, I'm not yet convinced that every instance of (MonadWriter w m) gives rise to a monoid instance of w. Regards, Holger

Excerpts from Holger Siegel's message of Sat Dec 08 15:27:38 -0800 2012:
For deriving a monoid instance of w from monad (Writer w), you will need function execWriter:: Writer w a -> w, but in case of a general instance of (MonadWriter w m) you would have to use function listen :: m a -> m (a, w) that will only provide you a value of type (m w), but not of type w. Therefore, I'm not yet convinced that every instance of (MonadWriter w m) gives rise to a monoid instance of w.
Definitely not. I need a way of running the monad, some way or another, otherwise, it's like having the IO monad without a 'main' function :) But you don't need very much to get there... Edward

Am 09.12.2012 um 00:27 schrieb Holger Siegel:
For deriving a monoid instance of w from monad (Writer w), you will need function execWriter:: Writer w a -> w, but in case of a general instance of (MonadWriter w m) you would have to use function listen :: m a -> m (a, w) that will only provide you a value of type (m w), but not of type w.
sorry, I meant function execWriterT :: Monad m => WriterT w m a -> m w.
Therefore, I'm not yet convinced that every instance of (MonadWriter w m) gives rise to a monoid instance of w.

Hi Petr,
On Sun, Dec 9, 2012 at 7:59 AM, Petr P
The class is defined as
class (Monoid w, Monad m) => MonadWriter w m | m -> w where ...
What is the reason for the Monoid constrait? It seems superfluous to me. I recompiled the whole package without it, with no problems.
How I see it, the MTL classes are there to lift operations automatically through layers of transformers. They're just a hack to avoid having to call `lift` all the time, and aren't really designed to be used on monads other than the original WriterT. With this interpretation, the constraint makes sense -- it is simply reflecting the constraints already on the concrete monad. Chris
Of course, the Monoid constraint is necessary for most _instances_, like in
instance (Monoid w, Monad m) => MonadWriter w (Lazy.WriterT w m) where ...
but this is a different thing - it depends on how the particular instance is implemented.
I encountered the problem when I needed to define an instance where the monoidal structure is fixed (Last) and I didn't want to expose it to the user. I wanted to spare the user of of having to write Last/getLast everywhere. (I have an instance of MonadWriter independent of WriterT, its 'tell' saves values to a MVar. Functions 'listen' and 'pass' create a new temporary MVar. I can post the detail, if anybody is interested.)
Would anything break by removing the constraint? I think the type class would get a bit more general this way.
Thanks for help, Petr Pudlak
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (7)
-
Andreas Abel
-
Chris Wong
-
Edward Z. Yang
-
Holger Siegel
-
Kim-Ee Yeoh
-
Petr P
-
Roman Cheplyaka