Why do I have to specify (Monad m) here again?

Why do I have to specify (Monad m) here again? class (Monad m) => GetMV m a where ... instance GetMV m c where ... No instance for (Monad m) arising from the superclasses of an instance declaration possible fix: add (Monad m) to the instance declaration superclass context Marc

On 2/18/07, Marc Weber
Why do I have to specify (Monad m) here again?
class (Monad m) => GetMV m a where ...
instance GetMV m c where ...
No instance for (Monad m) arising from the superclasses of an instance declaration possible fix: add (Monad m) to the instance declaration superclass context
The class just says that any instance *requires* an instance in Monad. Nothing more. So when you try to instantiate something in the class you have to ensure that it has an instance in Monad. A type variable "m" has no instance in the class "Monad" unless you constrain it to do so in the instance declaration (by doing "Monad m =>"). -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

Hello Marc, Sunday, February 18, 2007, 5:21:36 PM, you wrote:
Why do I have to specify (Monad m) here again?
class (Monad m) =>> GetMV m a where
instance GetMV m c where
because you can find another way to ensure that m is monad. for example, instance (MonadIO m) => GetMV m c where if i not yet proposed you to read http://haskell.org/haskellwiki/OOP_vs_type_classes then now it is time to do it :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Sun, Feb 18, 2007 at 05:06:33PM +0300, Bulat Ziganshin wrote:
Hello Marc,
Sunday, February 18, 2007, 5:21:36 PM, you wrote:
Why do I have to specify (Monad m) here again?
class (Monad m) =>> GetMV m a where
instance GetMV m c where
because you can find another way to ensure that m is monad. for example,
instance (MonadIO m) => GetMV m c where
if i not yet proposed you to read http://haskell.org/haskellwiki/OOP_vs_type_classes then now it is time to do it :)
I think I've read it once. But I'll do it again more thoroughly .. I'll try to explain why I don't get it yet class (Monad m) => GetMV m a where (1) tells that the first param called 'm' is an instance of class m, right? Then it doesn't matter wether I use instance GetMV m c where or instance GetMV <any name> c where If the class sepecification (1) forces m to be a monad, <any name> has to be one, too(?) When using your example (Monad IO): class (Monad m) => MonadIO m where liftIO :: IO a -> m a it it basically the same, isn't it? This declaration forces m to be monad.. which would't hurt if GHC would infer m beeing a monad automatically? Marc

Hello Marc, Sunday, February 18, 2007, 7:32:54 PM, you wrote:
When using your example (Monad IO): class (Monad m) => MonadIO m where liftIO :: IO a -> m a it it basically the same, isn't it? This declaration forces m to be monad.. which would't hurt if GHC would infer m beeing a monad automatically?
it is more explicit. for example, this simplifies understanding of error messages generated by compiler. and, if you change 'class' declaration, this will not silently change meaning of 'instance' declaration -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

which would't hurt if GHC would infer m beeing a monad automatically?
it is more explicit. for example, this simplifies understanding of error messages generated by compiler. and, if you change 'class' declaration, this will not silently change meaning of 'instance' declaration
Hello Bulat, do you mean that the fact that one must keep class and instance declaration in agreement manually is an advantage and not just a limitation of the Haskell type system? Why then not just require that all constraints be declared explicitly. The following code compiles: is it a bad thing that it does? class (Eq a) => Eql a where (=:=) :: a -> a -> Bool x =:= y = x == y eql :: Eql a => a -> a -> Bool eql x y = x == y David

On 18/02/07, David Tolpin
The following code compiles: is it a bad thing that it does?
class (Eq a) => Eql a where (=:=) :: a -> a -> Bool x =:= y = x == y
eql :: Eql a => a -> a -> Bool eql x y = x == y
The reason this typechecks: 1) The compiler infers that x and y must have a type which instantiates Eq. 2) Therefore, it infers the type eql :: Eq a => a -> a -> Bool 3) This doesn't match up with the type you specified for eql, though, so we need to check that your specified type is a specialisation of the inferred type (see below for a more thorough explanation). 4) It is; if we know that x has a type which instantiates Eql, then we can prove that this type also instantiates Eq, by the constraint on the class head of Eql. 5) The program is accepted. Step 3 may need more explanation. We can use type signatures to specify a polymorphic type down to a less polymorphic one. For example, if you wrote: id x = x Then the compiler infers id :: a -> a. However, if you only wanted id to work on Ints, then you could write: id :: Int -> Int id x = x This program would still be accepted, because Int -> Int is less polymorphic than a -> a, i.e., you can get from a -> a to Int -> Int by chosing the substitution a = Int. You could also decide that you only wanted id to work on instances of Show: id :: Show s => s -> s id x = x This'd work, again, because you can get from a -> a to Show s => s -> s by chosing the substitution a = Show s => s (note that (Show s => s) -> (Show s => s) is the same as Show s => s -> s). Show s => s -> s is still a polymorphic type, but it's less polymorphic than a -> a (the latter is defined over all types, the former only over types that are instances of Show). HTH. -- -David House, dmhouse@gmail.com

On 18/02/07, David Tolpin
how is this different from inferring that if a type variable is an instance of class it is subject to constraints imposed on the class?
I think you, and probably Marc Weber as well, are confusing what a constraint on a class head means. Suppose you have: class Monad m => Foo m That constraint means that every instance of class Foo must also be an instance of class Monad. So, as I explained in my email to Marc, we must use: instance Monad m => Foo m And not: instance Foo m Because, in general, m isn't an instance of Monad. In your example, we already have two types with instances of Eql, which means, by the constraint on the class head of Eql, these types are also instances of Eq, which makes the program valid. If you like, think about it this way: in order for your function body to be valid, the compiler has to prove that the types of the arguments to eql are instances of Eq (because you're using == on them). It knows they're instances of Eql by the type signature you provided, and from that it can prove that they're also instance of Eq by the constraint on class head of Eql. I think these are two completely different things to compare and say 'how are they different', but if you wanted a pithy sentence to try and explain the differences between them, perhaps it's that in Marc's example we're declaring an instance of a type where the class required that the instance type must also instantiate some other class (Monad). With your example, we're declaring a function, not an instance, that requires an instance of Eql and needs one of Eq, but can find the latter because of the class constraint. HTH more this time :) -- -David House, dmhouse@gmail.com

David: Thanks again for your explanation
Because, in general, m isn't an instance of Monad.
Talking about my example: class (Monad m) => GetMV m a where ... instance GetMV m c where (2) (2) There are only 2 cases: ghc supposes m does instantiates Monad => success ghc doesn't suppose this => failure becuase the class head of GetMV does require it. fix: adding (Monad m) => (3) That's why it would be save to assume that the programmer doesn't want a failure but success. Thus ghc could infer (3) automatically but doesn't Do I still miss a point? Marc

Hello Marc,
That's why it would be save to assume that the programmer doesn't want a failure but success.
generally speaking, languages like Haskell introduces strong typing exactly to avoid "false successes" -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi Marc, Marc Weber wrote:
class (Monad m) => GetMV m a where ... instance GetMV m c where (2)
...it would be save to assume that the programmer doesn't want a failure but success. Thus ghc could infer (3) automatically but doesn't
The Monad m on the class declaration does not mean that the programmer _wants_ m to be a monad. It means that the programmer _promises_ to make m a monad - even more, the programmer wants the compiler to force anyone using this class to first make m a monad, and otherwise enforce type safety by failing to compile. This is very good, because then any future use of an instance of GetMV can be safely assumed to have also a Monad instance, no matter what its type. One place you can use that nice assumption is in the method declarations within the original class declaration itself. Another is in function definitions, as you say. But when writing an instance declaration, it is time to pay up. You made a promise. Now you have to show the compiler where to get that Monad instance. There are two ways of doing that. One way is if the type itself already has a separate Monad instance. The other way is if the type is not fully specified - it is a variable - then you can "pass the buck" and say that whoever uses this instance must first make sure that the value of the type variable is a type that already has a Monad instance. Regards, Yitz

I wrote:
The other way is if the type is not fully specified - it is a variable - then you can "pass the buck" and say that whoever uses this instance must first make sure that the value of the type variable is a type that already has a Monad instance.
In this case, you are creating an obligation on users of this instance - they are required to provide the Monad instance themselves. So it makes sense that you need to write the constraint "Monad m =>" on the instance declaration, to make sure this obligation is clear to the users of the instance. Regards, Yitz

On 18/02/07, Marc Weber
Do I still miss a point?
I think Yitzchak's explanation of this was pretty good, so I recommend you check that out. You should also make sure you read Sebastian's argument, whose line of thought is similar to the one I'm going to try to develop. Suppose we write the print function: print x = putStrLn (show x) Now, we want it to be able to act on as many types as possible, so we write the type: print :: a -> IO () print x = putStrLn (show x) But that's not quite right; we apply x to the 'show' function, so x must be of a type that instantiates Show. However, our ever-hopeful compiler writers decided that if we wrote something like: print :: a -> IO () But the compiler inferred the type: print :: Show a => a -> IO () Then it'd fill in the extra constraint and let everything work. This is essentially your argument (although it applies to instances instead of functions; I'll make the link at the end). I say this is a bad idea, basically because the actual type of print is different to the type we wrote down. Imagine that print is in a library and a user's browsing the source of this library. They see the print function and try to use it on something that doesn't satisfy the Show constraint. The compiler bombs out with 'Cannot find Show instance' and the user is confused. The type mentioned in the source file didn't mention any Show instance, why should I need to provide one? Admittedly, in this simple example, the user would probably see the show function being used and realise what's going on, but this wouldn't happen in more complex cases. So the problem is, essentially, that the type written in the source file is incorrect, but the compiler accepts it anyway. This is just confusing. Secondly, Explicit writing of types in Haskell is completely optional -- if you want, the compiler will infer everything for you, so why do we bother at all? Well, imagine we wrote: print :: Show a => a -> IO () print x = show x If we hadn't written that type signature, then the compiler would infer a type and accept the program. However, as we _did_ provide a type signature, it acts a little like a spec or QuickCheck property and reveals a typo straight away: we missed out the putStrLn. Similarly, if we write the type: print :: a -> IO () Then the attitude taken by the language designers dictates that that's what you mean. If you then try to use show, you presumably made a mistake writing the type. The compiler could correct this mistake, but would we want it to? Perhaps this small error is indicative of a larger conceptual error we made; perhaps our spec says that print should indeed have the type we wrote, and the mistake was in using show. So we've determined that if we provide explicit types for functions, these should match up with the type the compiler infers. Instances are just the same. If we write a specific type, like 'm', then we mean 'm' and not 'Monad m => m'. We could give similar examples for instances as we did for functions above. Suppose we had: class Monad m => Foo m where ... instance Foo m where ... Then someone, just seeing the instance (which may be a completely different file to the class), may assume that there's an instance for every type, and get a similarly confusing situation to the print example. Or perhaps we _do_ indeed want an instance of Foo for every type, and the constraint on the class head of Foo was the mistake, then the compiler would accept our program, unhelpfully. Having the compiler second-guess our mistakes is unhelpful and confusing. HTH. -David House, dmhouse@gmail.com

Hi David. I see that its useful to add complete type signatures without letting the compiler add stuff magically. This is why I've tried to write the final question down under a new topic wether it would be useful to be able to write down partial type signatures where browsing coders know that they are not complete... (Scroll down to see my answer) When introducing a new concept ( partially typed functions ) we don't have to discuss wether type signatures are useful. I will indicate this incomplete type signature by adding [...] at the end.
type we wrote down. Imagine that print is in a library and a user's browsing the source of this library. They see the print function and try to use it on something that doesn't satisfy the Show constraint. The compiler bombs out with 'Cannot find Show instance' and the user is confused. Every haskell newbe will be confused by any error message ;) But the haskell programmer will only be confused the first time *lol* Then he knows how to handle it.
print :: Show a => a -> IO () print x = show x
If we hadn't written that type signature, then the compiler would infer a type and accept the program. Aeh. Was this really the issue talking about wether its useful to write down type signatures or writing down incomplete signatures users not knowing them beeing incomplete? Talking about: print x :: a -> IO () [...] print x = show x the compiler would not have compiled this in any case.
However, as we _did_ provide a
type signature, it acts a little like a spec or QuickCheck property and reveals a typo straight away: we missed out the putStrLn. Similarly, if we write the type:
print :: a -> IO ()
Then the attitude taken by the language designers dictates that that's what you mean. If you then try to use show, you presumably made a mistake writing the type. The compiler could correct this mistake, but would we want it to? Perhaps this small error is indicative of a larger conceptual error we made; perhaps our spec says that print should indeed have the type we wrote, and the mistake was in using show.
So we've determined that if we provide explicit types for functions, these should match up with the type the compiler infers. Instances are just the same. They are not. Why? As I have look at the class declaration as well when looking at instances .. Expressed differently: function implementation <-> function type signature corresponds to class method implementation <-> class type signature (1) (Monad m => ...) or class method implementation <-> instance type signature (2) (Monad m => has to be repeated here) ?
When looking at types (when browsing instances (2)) I'm always looking at the class type declaration (1) as well. So in my given example class (Monad m) => ... I would have seen it anyway. I could only think of one example where omitting the (Monad m) => part might be useful: You have a class providing a function match regex subject = ... and two implementations returning (before, match, after) or (match) Then you might want to write show3 :: (a,a,a) show3 = show te use show3 to select the right implementation. But in this case it is more convinient to write show3 a@(_,_,_) = show a So I'm totally convinced that we don't need new language features.. Marc

I think you, and probably Marc Weber as well, are confusing what a constraint on a class head means. Suppose you have:
class Monad m => Foo m
That constraint means that every instance of class Foo must also be an instance of class Monad. So, as I explained in my email to Marc, we must use:
instance Monad m => Foo m
And not:
instance Foo m
Because, in general, m isn't an instance of Monad.
Hi David, Why the compiler cannot infer class constraint on m from class definition in instance definition while it can in function type definition? If every instance of class Foo must be an insance of class Monad, then an instance of class Foo that is not an instance of class Monad cannot be declared could it? Why the compiler cannot infer this constraint in instance declarations while it can in other contexts? How does the limitation follow from the type system? What is missing in the type system reasoning that prevents the Haskell compiler from using the proof? There is no other choice for the time system than to allow only such instances of class Foo which are also instances of class Monad. Why then I have to say it explicitly again in case of instances, while other parts of the language allow inference? David

On 2/18/07, David Tolpin
I think you, and probably Marc Weber as well, are confusing what a constraint on a class head means. Suppose you have:
class Monad m => Foo m
That constraint means that every instance of class Foo must also be an instance of class Monad. So, as I explained in my email to Marc, we must use:
instance Monad m => Foo m
And not:
instance Foo m
Because, in general, m isn't an instance of Monad.
Hi David,
Why the compiler cannot infer class constraint on m from class definition in instance definition while it can in function type definition?
But it can't! If you give a type to a function, it will assume zero class constraints unless you specify them (just like it will when you give a type to an instance declaration). If you do something like: foo :: [a] -> a foo = head . sort It will *not* compile. "sort" requires "Ord", but that does *not* mean that you can write a type declaration with just a type variable and have it automatically infer that you need an "Ord" constraint and add it for you (in fact, that's a good thing, it will tell you that you forgot an Ord constraint, which may be symptomatic of some other problem). If you write down a type explicitly, Haskell will not change it for you into something else just to make the program compile. It *could* infer that the type for "foo" above needs to have an Ord constraint and just add it, but if it did then the whole point of type checking would be disappear. You *want* an error when types don't match! With functions you can leave out the type and Haskell will infer a type (which will have the correct constraints), but we don't have the option of leaving out the types when declaring instances. Haskell doesn't have any "instance inference" (and I'm not sure what that would even mean), you have to give the type of your instance explicitly, and when doing so you are not allowed to skip parts of the type because they are required elsewhere. Again, just like with functions, Haskell will not change your supplied type into something else if there is a mismatch, it will give you an error instead (which is what you want). -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

On Sun, Feb 18, 2007 at 06:59:32PM +0300, Bulat Ziganshin wrote:
Hello Marc,
Sunday, February 18, 2007, 7:32:54 PM, you wrote:
When using your example (Monad IO): class (Monad m) => MonadIO m where liftIO :: IO a -> m a it it basically the same, isn't it? This declaration forces m to be monad.. which would't hurt if GHC would infer m beeing a monad automatically?
it is more explicit. for example, this simplifies understanding of error messages generated by compiler. and, if you change 'class' declaration, this will not silently change meaning of 'instance' declaration
Is there a difference at all wehter specifying (Monad m) in the class declaration or not? I have to add it to the instance declaration anyway.. And if you don't want to change the meaning of instance declaration you would be able to add this constraint to indicate this. I don't see why it simplifies error messages. Marc

On 18/02/07, Marc Weber
Is there a difference at all wehter specifying (Monad m) in the class declaration or not? I have to add it to the instance declaration anyway..
If you have, say: class Monad m => Foo m where ... Then it's illegal to say: instance Foo Data.Set.Set where ... Because Data.Set.Set doesn't instantiate Monad. Including the constraint in the class header forces every instance to satisfy that constraint in order for it to be a valid instance. In effect, Monad is a superclass of Foo. Similarly, you can't say: instance Foo m where ... Because, in general, m doesn't instatiate Monad. You have to use (Monad m => m) instead: instance Foo (Monad m => m) where ... Which is more normally written: instance Monad m => Foo m where ... Incidentally, you're here saying that: i) Every type T that instantiates Foo must also instantiate Monad (due to the constraint on the class head). ii) Every type T that instantiates Monad also instantiates Foo (due to the instance Monad m => Foo m). So Foo and Monad both have exactly the same member types. -- -David House, dmhouse@gmail.com

Hello Marc, Sunday, February 18, 2007, 8:05:24 PM, you wrote:
Is there a difference at all wehter specifying (Monad m) in the class declaration or not? I have to add it to the instance declaration anyway.. And if you don't want to change the meaning of instance declaration you would be able to add this constraint to indicate this.
I don't see why it simplifies error messages.
i mean that it makes error message more obvious - you don't need to remember that this context is implied due to class declaration -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

i mean that it makes error message more obvious - you don't need to remember that this context is implied due to class declaration
The error might look like Missing instance (Ord m) araising from use of ... imposed by automatically infered class constraint from context line xy ? ;) Something like this is done anyway if you omit the type declaration.. (And I have to admit that there were times I had trouble understanding them .. *g* ) Marc

Marc Weber said:
I'll try to explain why I don't get it yet
class (Monad m) => GetMV m a where (1)
tells that the first param called 'm' is an instance of class m, right? Then it doesn't matter wether I use instance GetMV m c where or instance GetMV <any name> c where
If the class sepecification (1) forces m to be a monad, <any name> has to be one, too(?)
Let's look at this from another angle: What are you achieving with your class/instance definitions that you couldn't achieve with a simple function? I'm not sure what methods you have, so I'll use the following for the purpose of discussion. I'm reverting to a single-parameter type class, since the multi-parameter type class might be clouding the issue:
class Monad m => MonadFoo m where foo :: m Int
instance Monad m => MonadFoo m where foo = return 42
How is the above different from just writing the following?
foo' = return 42
Well, they do have slightly different types:
foo :: MonadFoo m => m Int foo' :: Monad m => m Int
But practically speaking, the MonadFoo class is no different to the Monad class. For a start, every member of the Monad class is also a member of the MonadFoo class, according to the sole instance declaration. Further, you can't define any other instance of MonadFoo, because it would conflict with the above instance. You're stuck with a single instance, which means you don't gain anything over the standalone function. My point is that the case you're trying to save a few keystrokes on is not really that useful. Indeed, the point of classes and instances is to allow different types to inhabit the same class with different implementations, and to allow other types to not inhabit the class at all. Contexts on instance declarations allow you to write an instance which covers a range of types, but usually the range of types is a proper subset of the class. It would be rare (if ever) that you would write an instance declaration covering the entire class, as I've done above. (Actually, you might do this if you start using overlapping and undecidable instances, but that's over my head). I suggest you look through the base libraries to see how contexts on instance declarations are used in practice.
When using your example (Monad IO): class (Monad m) => MonadIO m where liftIO :: IO a -> m a it it basically the same, isn't it? This declaration forces m to be monad.. which would't hurt if GHC would infer m beeing a monad automatically?
And here's a concrete example. The class definition requires that m be a Monad before it can be a MonadIO, but here's the important bit: not every Monad will be a MonadIO. So you would not want an instance declaration that makes that assumption.
participants (7)
-
Bulat Ziganshin
-
David House
-
David Tolpin
-
Marc Weber
-
Matthew Brecknell
-
Sebastian Sylvan
-
Yitzchak Gale