Instance match surprise

Dear List, Why does the first instance match? ANY is neither Eq nor Typeable. I thought I had some basic understanding of type classes, and now this... wojtek@biuro:~/src/he$ cat minimatch.hs {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} module MiniMatch where import Data.Typeable data A130 = A130 deriving (Eq) data ANY = ANY class AtmAcct a class Against q class (AtmAcct a, Against q) => Match a q where match :: a -> q -> Bool instance AtmAcct A130 instance Against ANY instance (Eq a, Eq q, Typeable a, Typeable q, AtmAcct a, Against q) => Match a q where match _ _ = False instance (AtmAcct a) => Match a ANY where match _ _ = True m1 = match A130 ANY -- offending line wojtek@biuro:~/src/he$ ghc minimatch.hs [1 of 1] Compiling MiniMatch ( minimatch.hs, minimatch.o ) minimatch.hs:21:6: error: • Overlapping instances for Match A130 ANY arising from a use of ‘match’ Matching instances: instance (Eq a, Eq q, Typeable a, Typeable q, AtmAcct a, Against q) => Match a q -- Defined at minimatch.hs:18:10 instance AtmAcct a => Match a ANY -- Defined at minimatch.hs:19:10 • In the expression: match A130 ANY In an equation for ‘m1’: m1 = match A130 ANY -- Thanks, Wojtek Narczyński

Cześć Wojtek, in instance (Eq a, Eq q, Typeable a, Typeable q, AtmAcct a, Against q) => Match a q where ANY is q because instance Against ANY A130 is a because of instance AtmAcct A130 in instance (AtmAcct a) => Match a ANY where match _ _ = True ANY is specified A130 is a because of instance AtmAcct A130 ;)

On Mon, Feb 01, 2016 at 09:22:31PM +0100, Wojtek Narczyński wrote:
On 01.02.2016 20:19, Imants Cekusins wrote:
in instance (Eq a, Eq q, Typeable a, Typeable q, AtmAcct a, Against q) => Match a q where
ANY is q because instance Against ANY
But I require q to be Eq and Typeable, and ANY is none of those two?
Correct. The actual reason is more subtle. See my sibling post. Tom

.. could we say: main purpose of instance contexts is to allow use of 'open' (e.g. a) types when defining instance methods (i.e. we can use (==) a inside instance method if the context says Eq a) , rather than for looking up an applicable instance?

On 2 February 2016 7:22:31 AM AEDT, "Wojtek Narczyński"
On 01.02.2016 20:19, Imants Cekusins wrote:
in instance (Eq a, Eq q, Typeable a, Typeable q, AtmAcct a, Against q) => Match a q where
ANY is q because instance Against ANY
But I require q to be Eq and Typeable, and ANY is none of those two?
-- Wojtek _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
But there *could* be other instances the compiler just can't see at the moment (because it's in another module that's not imported). Someone else could then import this module and that other module and observe inconsistent instances. To avoid that problem, the type class system *never* commits to "negative" information; if an instance choice is only valid because there *isn't* a possible instance in scope then that instance choice is not valid after all. A consequence is that constraints on an instance have to be ignored when choosing an instance (they still might make the choice be an error after it is chosen, but they don't affect which instance is selected). And so an instance like: ... => Match a q is the *only* possible instance you can write, since it will match everything regardless of the ... (unless you use overlapping instances).

On 01.02.2016 21:34, Ben wrote:
But there *could* be other instances the compiler just can't see at the moment (because it's in another module that's not imported). Someone else could then import this module and that other module and observe inconsistent instances.
Okay, I get it. In another module there might be instances Eq and Typeable for ANY, and then the instances would indeed overlap. It makes sense.
To avoid that problem, the type class system *never* commits to "negative" information; if an instance choice is only valid because there *isn't* a possible instance in scope then that instance choice is not valid after all.
I will have to produce many instances by hand. Couldn't the compiler just postpone the its overlap checking until linking? Or might I forbid creation of Eq and Typeable instances of ANY? -- Wojtek

On 2 February 2016 9:33:46 AM AEDT, "Wojtek Narczyński"
On 01.02.2016 21:34, Ben wrote:
But there *could* be other instances the compiler just can't see at the moment (because it's in another module that's not imported). Someone else could then import this module and that other module and observe inconsistent instances.
Okay, I get it. In another module there might be instances Eq and Typeable for ANY, and then the instances would indeed overlap. It makes
sense.
To avoid that problem, the type class system *never* commits to "negative" information; if an instance choice is only valid because there *isn't* a possible instance in scope then that instance choice is not valid after all.
I will have to produce many instances by hand.
Couldn't the compiler just postpone the its overlap checking until linking? Or might I forbid creation of Eq and Typeable instances of ANY?
-- Wojtek _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
It potentially could, but it didn't (the design isn't without tradeoffs). What you can do is look into overlapping instances; you can make the compiler allow those two instances to overlap and pick the most specific one that applies at each use site. It still wouldn't be actually using the constraints to choose the instance, but in code that statically knows its talking about Any it can use that instance, and if it's an unknown type variable you presumably *won't* be able to prove Typeable or Eq if it could possibly be Any, so the code still wouldn't compile. I have very rarely actually used this, because it can be a little "dangerous" (you can get those inconsistent instances the ignore-the-instance-constraints rule is designed to avoid), but with a little discipline it can work fine. Read up on the GHC documentation on the OverlappingInstances extension.

On Mon, Feb 01, 2016 at 07:53:32PM +0100, Wojtek Narczyński wrote:
Why does the first instance match? ANY is neither Eq nor Typeable. I thought I had some basic understanding of type classes, and now this...
minimatch.hs:21:6: error: • Overlapping instances for Match A130 ANY arising from a use of ‘match’ Matching instances: instance (Eq a, Eq q, Typeable a, Typeable q, AtmAcct a, Against q) => Match a q -- Defined at minimatch.hs:18:10 instance AtmAcct a => Match a ANY -- Defined at minimatch.hs:19:10 • In the expression: match A130 ANY In an equation for ‘m1’: m1 = match A130 ANY
The way instance resolution works is somewhat counterintuitive, and it took me a long time to get my head around it. The upshot is that the instance context is *absolutely irrelevant* when looking for a matching instance. The type is Match A130 ANY The instances in scope are (Eq a, Eq q, Typeable a, Typeable q, AtmAcct a, Against q) => Match a q and AtmAcct a => Match a ANY But because the instance contexts are irrelevant, these are just ... => Match a q and ... => Match a ANY Both of these match 'Match A123 ANY', and thus you have overlap. If you want to know *why* the instance contexts are ignored then you'll have to ask someone who knows more about Prolog :) Tom

On 01.02.2016 21:29, Tom Ellis wrote:
If you want to know*why* the instance contexts are ignored then you'll have to ask someone who knows more about Prolog:) I think I know. There is really no way of knowing that there is no vicious little instance Eq ANY lurking deep down some obscure useless module. It is called: open world assumption.
-- Wojtek

On Mon, Feb 01, 2016 at 11:56:58PM +0100, Wojtek Narczyński wrote:
On 01.02.2016 21:29, Tom Ellis wrote:
If you want to know*why* the instance contexts are ignored then you'll have to ask someone who knows more about Prolog:) I think I know. There is really no way of knowing that there is no vicious little instance Eq ANY lurking deep down some obscure useless module. It is called: open world assumption.
Yes, Ben's explanation was a good one.
participants (4)
-
Ben
-
Imants Cekusins
-
Tom Ellis
-
Wojtek Narczyński