type error

Ed Komp komp@ittc.ku.edu
Mon, 02 Jun 2003 09:42:31 -0500


I have encountered an unexpected type error of the form:

 >>     Could not unambiguously deduce <type> from the context <context>

I was able to generate a quite simple test case to demonstrate
the problem, that I include at the end of this message.

I am using Version 5.04.2 of the Glasgow Compiler, with options:

-fglasgow-exts -fallow-overlapping-instances -fallow-undecidable-instances

Here is the output generated when I attempt to load the file, test.hs,
(test.hs appears at the end of this message):

 >> fleck [61] % ghci --version
 >> The Glorious Glasgow Haskell Compilation System, version 5.04.2
 >> fleck [62] % ghci -fglasgow-exts -fallow-overlapping-instances 
-fallow-undecidable-instances test.hs
 >>    ___         ___ _
 >>   / _ \ /\  /\/ __(_)
 >>  / /_\// /_/ / /  | |      GHC Interactive, version 5.04.2, for Haskell 98.
 >> / /_\\/ __  / /___| |      http://www.haskell.org/ghc/
 >> \____/\/ /_/\____/|_|      Type :? for help.
 >>
 >> Loading package base ... linking ... done.
 >> Loading package haskell98 ... linking ... done.
 >> Compiling Test             ( test.hs, interpreted )
 >>
 >> test.hs:26:
 >>     Could not unambiguously deduce (SubType x Value)
 >> 	from the context (SubType x BaseType)
 >>     The choice of (overlapping) instance declaration
 >> 	depends on the instantiation of `x'
 >>     Probable fix:
 >> 	Add (SubType x Value)
 >> 	to the existential context of a data constructor
 >> 	Or add an instance declaration for (SubType x Value)
 >>     arising from use of `inj' at test.hs:26
 >>     In the definition of `test': inj x
 >> Failed, modules loaded: none.
 >> Prelude>

I do not understand why the compiler cannot deduce
(SubType x Value) from (SubType x BaseType)

since:

type Value = (Either Double BaseType)

and
instance (SubType a b) => SubType a (Either x b) where

The message actually says it cannot "unambiguously" make the
deduction.

Can someone explain to me why this is, and more importantly
how I can resolve the issue?

The suggestion,
 >> 	Add (SubType x Value)
 >> 	to the existential context of a data constructor

will work in this simple example (I tested this);
but in the code where I originally encountered the problem
this is not a viable alternative since it would generate
circular dependencies.

Thanks in advance for your help !

Ed Komp
komp@ittc.ku.edu

-- -----------------------------------------------------------
-- test.hs
-- -----------------------------------------------------------
module Test where

import Control.Monad.Error

class SubType a b where
  inj :: a -> b
  prj :: b -> Maybe a

instance SubType a (Either a x) where
  inj       = Left
  prj       = either Just (const Nothing)

instance (SubType a b) => SubType a (Either x b) where
    inj       = Right . inj
    prj       = either (const Nothing) prj

-- -----------------------------------------------------------

type BaseType = Either Integer ( Either Bool () )

type Value = (Either Double BaseType)

data Foo =  forall x. (SubType x BaseType)  => MkFoo x

test :: Foo -> Value
test (MkFoo x) = inj x