3
votes

Background

I have written the following code in Haskell (GHC 8.6.3):

{-# LANGUAGE 
  NoImplicitPrelude,
  MultiParamTypeClasses,
  FlexibleInstances, FlexibleContexts,
  TypeFamilies, UndecidableInstances,
  AllowAmbiguousTypes
#-}

import Prelude(Char, Show, show, undefined, id)

data Nil
nil :: Nil
nil = undefined

instance Show Nil where
  show _ = "nil"

data Cons x xs = Cons x xs 
  deriving Show

class FPack f r where
  fpack :: f -> r

instance {-# OVERLAPPABLE #-} f ~ (Nil -> r) => FPack f r where
  fpack f = f nil

instance (FPack (x -> b) r, f ~ (Cons a x -> b)) => FPack f (a -> r) where
  fpack f a = fpack (\x -> f (Cons a x))

The idea behind this code is to produce a function of variable arity that takes its arguments and packs them into a heterogeneous list.

For example, the following

fpack id "a" "b" :: Cons [Char] (Cons [Char] Nil)

produces the list Cons "a" (Cons "b" nil).

Problem

In general, I want to call fpack by passing id as its f parameter (like above) so I wish to define the following function as a shorthand:

pack = fpack id

If I load the above program into GHCi and execute the above line, pack is defined as desired and its type (as given by :t) is FPack (a -> a) r => r. So I defined the function like so in my program:

pack :: FPack (a -> a) r => r
pack = fpack id

But this gives the following error when loading said program into GHCi:

bugs\so-pack.hs:31:8: error:
    * Overlapping instances for FPack (a0 -> a0) r
        arising from a use of `fpack'
      Matching givens (or their superclasses):
        FPack (a -> a) r
          bound by the type signature for:
                     pack :: forall a r. FPack (a -> a) r => r
          at bugs\so-pack.hs:30:1-29
      Matching instances:
        instance [overlappable] (f ~ (Nil -> r)) => FPack f r
          -- Defined at bugs\so-pack.hs:24:31
        instance (FPack (x -> b) r, f ~ (Cons a x -> b)) =>
                 FPack f (a -> r)
          -- Defined at bugs\so-pack.hs:27:10
      (The choice depends on the instantiation of `a0, r')
    * In the expression: fpack id
      In an equation for `pack': pack = fpack id
   |
31 | pack = fpack id
   |     

This leads me to my questions. Why does this function work when defined in GHCi, but not when defined in the program proper? Is there a way I can make this work in the program proper? If so, how?

My Thoughts

From what I understand about GHC and Haskell, this error comes from the fact that pack could resolve to either one of the two overlapping instances, and that bothers GHC. However, I thought that the AllowAmbiguousTypes option should solve that problem by deferring instance selection to the final call site. Unfortunately, that apparently that isn't sufficient. I am curious as to why, but I am even more curious as to why GHCi accepts this definition in its REPL loop but it does not accept it when it is inside a program.

A Tangent

I have another question regarding this program that is not directly related to main thrust of this question, but I thought it might be wise to ask it here rather than create another question about the same program.

As seen in the example above i.e.

fpack id "a" "b" :: Cons [Char] (Cons [Char] Nil)

I have to provide an explicit type signature to fpack in order for it to work as desired. If I don't provide one (i.e. just call fpack id "a" "b"), GHCi produces the following error:

<interactive>:120:1: error:
    * Couldn't match type `Cons [Char] (Cons [Char] Nil)' with `()'
        arising from a use of `it'
    * In the first argument of `System.IO.print', namely `it'
      In a stmt of an interactive GHCi command: System.IO.print it

Is there any way I could alter the definition of fpack to get GHC to infer the proper type signature?

1

1 Answers

3
votes

You need to instantiate fpack manually.

pack :: forall a r . FPack (a -> a) r => r
pack = fpack @(a->a) @r id

This requires ScopedTypeVariables, TypeApplications, AllowAmbiguousTypes.

Alternatively, provide a type for id.

pack :: forall a r . FPack (a -> a) r => r
pack = fpack (id :: a -> a)

The issue it that GHC can't see if it should use the fpack provided by that FPack (a->a) r constraint. That might be puzzling at first, but note that fpack (id :: T -> T) could also correctly generate r if there is some instance FPack (T -> T) r available. Since id could be both a -> a and T -> T (for any T), GHC can not safely choose.

One can see this phenomenon in the type error, since GHC mentions a0. That type variable stands for some type which might be a, but might also be something else. One then can try to guess why the code isn't forcing a0 = a, pretending there are other instances around that could be used instead.