[Haskell-cafe] Undecideable instances for one instance?

Christophe Poucet christophe.poucet at gmail.com
Wed Jun 7 04:27:22 EDT 2006


Dear,

Recently I was wrapping something in a typeclass (you may argue the 
reason for the typeclass, I will admit that's no longer needed, yet the 
compile error still begs questioning). Basically if you have only one 
global instance of a typeclass (so there is no overlapping), GHC will 
still complain about overlapping. Is there any reason this is so or is 
this a remnant of more complicated overlapping situations?

The sample code is:

{-# OPTIONS_GHC -fglasgow-exts #-}
module Main where

data Located a = L a

class Locatable a where
value :: Located a -> a
wrap :: a -> Located a

instance Locatable a where
value (L a) = a
wrap a = L a

main :: IO ()
main = do
print . value . wrap $ 1

-- Illegal instance declaration for `Locatable a'
-- (There must be at least one non-type-variable in the instance head
-- Use -fallow-undecidable-instances to permit this)
-- In the instance declaration for `Locatable a'

Christophe(vincenz)

-- 
Christophe Poucet
Ph.D. Student
Phone:+32 16 28 87 20
E-mail: Christophe (dot) Poucet (at) imec (dot) be
Website: http://notvincenz.com/  
IMEC vzw – Register of Legal Entities Leuven VAT BE 0425.260.668 – Kapeldreef 75, B-3001 Leuven, Belgium – www.imec.be
*****DISCLAIMER*****
This e-mail and/or its attachments may contain confidential information. It is intended solely for the intended addressee(s).
Any use of the information contained herein by other persons is prohibited. IMEC vzw does not accept any liability for the contents of this e-mail and/or its attachments.
**********



More information about the Haskell-Cafe mailing list