Interaction of multiple overlapping instances

297 views Asked by At

The module Type.hs defines the homonym newtype and exports only its type constructor, but not the value constructor, to avoid exposing the detail; it also provides a constructor function makeType to balance the lack of value ctor. Why do I need to wrap a String in a new type? Because I want it to be more than a String; in my specific case, Type is actually called Line, and what corresponds to makeType enforces that it contains only one \n, as the last character. A newtype seemed the most obvious choice to me. If this is not the case, forgive me: I'm learning.

module Type (Type, makeType) where

newtype Type = Type String

makeType :: String -> Type
makeType = Type

In order to show a value of type Type the way I like (for instance, given my actual usecase of Line, I might want to represent \n with a nice unicode character, or with the sequence <NL>, or whatever), I created another module TypeShow.hs, which I later (in the attempt of doing what I'm describing) I edited by adding some pragmas. Why another module? Because I guess the way something works inside and the way I show it to screen are two separete aspects. Am I wrong?

{-# LANGUAGE FlexibleInstances #-}
module TypeShow () where

import Type

instance Show Type where
  show = const "Type"

-- the following instance came later, see below why
instance {-# OVERLAPS #-} Show (Maybe Type) where
  show (Just t) = show t
  show _ = ""

Beside this pair of modules (which describe the core of Type, and how it should be shown), I created other similar pairs Type1/Type1Show, Type2/Type2Show, which all wrap a String to represent and show other String-like entities.

For other reasons, I also needed another type which wraps an optional value, which can be of type Type, Type1, or any other type, so I wrote this module

module Wrapper (Wrapper, makeWrapper, getInside) where

newtype Wrapper a = Wrapper { getInside :: Maybe a }

makeWrapper :: a -> Wrapper a
makeWrapper = Wrapper . Just

(In reality Wrapper actually wraps more than one Type value, but I'll avoid putting more details then necessary; if the following is stupid exactly because I'm wrapping only one Type value in Wrapper, then please consider it's wrapping more than one, in reality.) Again, here I tried to hide the details of Wrapper while providing makeWrapper to make one, and getInside to have a "controlled" access to its inside.

I also wanted to show this on screen, so I created a corresponding WrapperShow.hs module, so that Wrapper's show method relies on the content's show method.

module WrapperShow () where

import Wrapper

instance Show a => Show (Wrapper a) where
  show = show . getInside

At this point, however, when the type a is a Maybe Type, I wanted to show the content of the Wrapper printing an empty string instead of Nothing, or the content of the Just; therefore I wrote the instance Show (Maybe Type) that I commented above.

Given this, Type "hello" and Just $ Type "hello" are both correcly shown as Type, but Wrapper $ Just $ Type "hello" is displayed as Just Type, just like it's using Maybe's original instance of Show, irrespective of the fact that for this specific type inside the Maybe (the Type) I've customized the Show instance.

1

There are 1 answers

5
danidiaz On

In the Show instance declaration for Wrapper, we don't really know what a is. But apparently we must already choose what Show instance to use for the Maybe a. With the information available, the only instance that matches is the default one Show a => Show (Maybe a), which doesn't require a concrete a.

The GHC User Guide, in the section about overlapping instances, mentions the concept of "postponing" the choice of an instance:

That postpones the question of which instance to pick to the call site for f by which time more is known about the type b. You can write this type signature yourself if you use the FlexibleContexts extension.

and

Exactly the same situation can arise in instance declarations themselves [...] The solution is to postpone the choice by adding the constraint to the context of the instance declaration

We could try such a trick. Instead of requiring Show a, require the whole Show (Maybe a). Now the Show instance is taken as "given" and we don't make a local decision. I think this has the effect of delaying the selection of the Show (Maybe a) instance to call sites like print $ Wrapper $ Just $ Type 3, where we have more information about the concrete type of a.

Testing this hypothesis:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
newtype Type = Type Int

instance Show Type where
  show = const "Type"

instance {-# OVERLAPS #-} Show (Maybe Type) where
  show (Just t) = show t
  show _ = ""

newtype Wrapper a = Wrapper (Maybe a)

instance Show (Maybe a) => Show (Wrapper a) where
  show (Wrapper edit) = show edit

main :: IO ()
main = print $ Wrapper $ Just $ Type 3
-- output: Type

That said, I find this behavior confusing and would steer clear of it in production code.


As @dfeuer notes in a comment and linked code, the overlapping instance is problematic. For example, if we add this innocent function to the code of this answer:

foo :: Show a => Maybe a -> String
foo = show

The module ceases to compile:

    * Overlapping instances for Show (Maybe a)
        arising from a use of `show'
      Matching instances:
        instance Show a => Show (Maybe a) -- Defined in `GHC.Show'
        instance [overlap ok] Show (Maybe Type) -- Defined at Main.hs:14:27
      (The choice depends on the instantiation of `a'

But now I'm confused. Why doesn't the exact same type error happen with the instance definition Show (Wrapper a) in the original question?


The reason foo fails to compile seems to be the last bullet point in the description of the instance search procedure:

Now find all instances, or in-scope given constraints, that unify with the target constraint, but do not match it. [here, Show (Maybe Type)] Such non-candidate instances might match when the target constraint is further instantiated. If all of them are incoherent top-level instances, the search succeeds, returning the prime candidate. Otherwise the search fails. [...]

The final bullet (about unifiying instances) makes GHC conservative about committing to an overlapping instance. For example:

f :: [b] -> [b]

Suppose that from the RHS of f we get the constraint C b [b]. But GHC does not commit to instance (C), because in a particular call of f, b might be instantiated to Int, in which case instance (D) would be more specific still. So GHC rejects the program.

Perhaps—unlike normal functions—instance definitions are exempt from this particular rule, but I don't see that mentioned in the docs.