0

Suppose we have the following:

{-# LANGUAGE FlexibleInstances #-}

module Sample where

newtype A a =
  A a
  deriving (Show)

newtype L a =
  L [a]

class ListContainer l where
  getList :: l a -> [a]

instance ListContainer L where
  getList (L l) = l

instance (Show a, ListContainer l) => Show (l a) where
  show = const "example"

With this code, ghc complains:

warning: [-Wdeferred-type-errors]
• Overlapping instances for Show (A a)
    arising from a use of ‘GHC.Show.$dmshowList’
  Matching instances:
    instance (Show a, ListContainer l) => Show (l a)
      -- Defined at /.../src/Sample.hs:18:10
    instance Show a => Show (A a)
      -- Defined at /.../src/Sample.hs:7:13
• In the expression: GHC.Show.$dmshowList @(A a)
  In an equation for ‘showList’:
      showList = GHC.Show.$dmshowList @(A a)
  When typechecking the code for ‘showList’
    in a derived instance for ‘Show (A a)’:
    To see the code I am typechecking, use -ddump-deriv
  In the instance declaration for ‘Show (A a)’
warning: [-Wdeferred-type-errors]
• Overlapping instances for Show (A a)
    arising from a use of ‘GHC.Show.$dmshow’
  Matching instances:
    instance (Show a, ListContainer l) => Show (l a)
      -- Defined at /.../src/Sample.hs:18:10
    instance Show a => Show (A a)
      -- Defined at /.../src/Sample.hs:7:13
• In the expression: GHC.Show.$dmshow @(A a)
  In an equation for ‘show’: show = GHC.Show.$dmshow @(A a)
  When typechecking the code for ‘show’
    in a derived instance for ‘Show (A a)’:
    To see the code I am typechecking, use -ddump-deriv
  In the instance declaration for ‘Show (A a)’

I can understand that it thinks type a can either derive Show, or derive ListContainer, which may result in Show.

How do we avoid that?

I understand that there exists a function showList, but its signature is a bit foreign. I do already have a function that I intend to use to display certain lists, which returns String directly.

Allan W
  • 2,791
  • 4
  • 23
  • 41

2 Answers2

4

I can understand that it thinks type a can either derive Show, or derive ListContainer, which may result in Show.

That is not what it thinks.

When Haskell chooses class instance, it doesn't look at instance constraints at all. All it considers when choosing an instance is the instance head (the thing that comes right after class name).

In your Show instance, the instance head is l a. This instance head matches A a (by assuming l = A). It also matches a lot of other things by the way - for example, it matches Maybe a (where l = Maybe), and Either b a (with l = Either b), and Identity a, and IO a - pretty much every type with a type parameter, come to think of it. It doesn't matter that neither A nor Maybe nor IO have an instance of ListContainer, because like I said above, Haskell doesn't look at constraints when choosing instances, only at instance heads.

It is only after finding a matching instance (by matching on its head) that Haskell will check if that instance's constraints are in fact satisfied. And will complain if they aren't. But it will never go back and try to pick another instance instead.

So coming back to your example: since A now has two matching Show instances - its own derived one and the Show (l a) one that you wrote, - the compiler complains that they are overlapping.

Fyodor Soikin
  • 78,590
  • 9
  • 125
  • 172
  • This seems like unfortunate and unintuitive behaviour, at least from the perspective of the user. Is there are good reason that ghc works this way? – Quelklef Jan 02 '21 at 10:22
  • If instances were chosen based on constraints, then the result would depend on which instances are in scope, which would be super fragile. For example, the meaning of your program could change if you add an import of a seemingly unrelated module that just happens to contain an instance. Or even without changing your imports, but instead upgrading dependencies. This would be hell to debug. – Fyodor Soikin Jan 02 '21 at 14:16
2

In your example you can just remove instance (Show a, ListContainer l) => Show (l a) and add deriving (Show) to L definition.

Alternatively you can remove deriving (Show) from A definition.

If you want you code behave as it is now remove deriving (Show) and implement it explicitly

 instance {-# OVERLAPPING #-}  Show a => Show (A a)
      where 
         show (A a) = "A " ++ show a
talex
  • 17,973
  • 3
  • 29
  • 66