Hi,

you do realise that "-fallow-incoherent-instances" is enabling a hell.
What mostly happens is that the most general instance is chosen.
Which explains the error here: Say the confusing instance is chosen
(because it is generic) and hence the type checker tries to establish the
Confuse constraint, which it can't because the addGeneralFallOut function
does not promise it.

I am just finishing up a draft on such class issues
having to do with Scrap your boilerplate,
which I would be keen to share somewhere later this week.

General conclusion:
I still have to see a good reason to use "-fallow-incoherent-instances".
It's mostly good to shot yourself in the head.

Ralf

Christian Maeder wrote:

The attached module does not compile and yields the following error:

InCoherentInst.hs:17:
Could not deduce (Confuse a) from the context (Typeable a)
arising from use of `breakFn' at InCoherentInst.hs:17
Probable fix:
Add (Confuse a) to the type signature(s) for `addGeneralFallOut'
In the first argument of `GeneralBreakFn', namely `breakFn'
In the definition of `addGeneralFallOut':
addGeneralFallOut = let
breakFn a = throwDyn (GeneralFallOutExcep a)
in GeneralBreakFn breakFn



The same source compiles ok without -fallow-incoherent-instances (or with -fno-allow-incoherent-instances).


If, furthermore, the "confusing instance" is commented out, the source even compiles without extensions.

I don't know if this is a bug, possibly related to the import of Typeable stuff. I don't need a fix. I only want to point out that globally switching on the option -fallow-incoherent-instances is likely to break existing code, currently (ghc 6.2.2).

Cheers Christian

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

{-# OPTIONS -fglasgow-exts -fallow-overlapping-instances 
-fallow-undecidable-instances -fallow-incoherent-instances #-}
module InCoherentInst where

import Control.Exception(throwDyn)

import Data.Typeable(Typeable)

class Confuse a where
   confuse :: a -> String

instance Confuse a => Typeable a

data GeneralBreakFn a = GeneralBreakFn (forall b . a -> b)

addGeneralFallOut :: Typeable a => GeneralBreakFn a
addGeneralFallOut =
     let breakFn a = throwDyn (GeneralFallOutExcep a)
     in GeneralBreakFn breakFn

data GeneralFallOutExcep a = GeneralFallOutExcep a deriving (Typeable)


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

_______________________________________________
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




_______________________________________________
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to