#4875: ghc misdiagnoses a compile time error concerning parameterized types
---------------------------------+------------------------------------------
    Reporter:  Stef Joosten      |        Owner:        
        Type:  bug               |       Status:  new   
    Priority:  normal            |    Milestone:        
   Component:  Compiler          |      Version:  6.12.3
    Keywords:                    |     Testcase:        
   Blockedby:                    |   Difficulty:        
          Os:  Windows           |     Blocking:        
Architecture:  Unknown/Multiple  |      Failure:  Other 
---------------------------------+------------------------------------------
Description changed by igloo:

Old description:

> Please find the script HaskellBug.hs at the bottom of this message.
> Here is how to reproduce the behaviour in two steps.
>
> Step 1: verify that Module HaskellBug produces the following error
> message:
>
> [1 of 1] Compiling HaskellBug       ( \HaskellBug.hs, interpreted )
>
> \HaskellBug.hs:12:22:
>     `rel' is not applied to enough type arguments
>     Expected kind `??', but `rel' has kind `* -> *'
>     In the type `rel -> concept'
>     In the class declaration for `Association'
>
> Step 2: remove the definition of class Morphic r c and verify that the
> script is now error free.
>
> You have now reproduced the symptoms.
>
> Assessment:
> In this situation, ghc has diagnosed an error in the definition of
> class Association. This error was resolved by removing another
> definition, without altering the definition of class Association.
> This proves that the definition of class Association was correct in the
> first place. Therefore, ghc has made a mistake. It has diagnosed
> the error in the wrong location. I whould have expected an error
> message like
> \HaskellBug.hs:23:22:
>     `r' is applied to too many type arguments
>     Expected <something sensible here>
>     In the type `r -> c'
>     In the class declaration for `Morphic'
>
> Epilog:
> I have taken the trouble to isolate the problem in a small script,
> because this error has caused serious havoc in a large Haskell
> project. Students, who were still learning about parameterized
> types, have systematically been 'fixing' the wrong code, because
> ghc has never pointed in the direction of the real error. In the
> end, they were unable to resolve their mistake.
> Besides haarvesting a frustrating experience with parameterized
> types, wasting two entire days before giving up, they have turned a
> large script upside down and introduced many more mistakes. That is
> why I think it is important to get this fixed.
>
> Here is the script:
>
> {{{
> {-# OPTIONS  -XMultiParamTypeClasses  -XFunctionalDependencies
> -XFlexibleInstances #-}
> module HaskellBug where
>
>   data Relation c -- The basic Relation
>      = Rel { relnm :: String -- The name of the relation
>            , relsrc :: c -- Source concept
>            , reltrg :: c -- ^Target concept
>            }
>        deriving Eq
>
>   class (Eq concept)=> Association rel concept | rel -> concept where
>     source, target :: rel -> concept      -- e.g. Declaration Concept ->
> Concept
>     sign  :: rel -> (concept,concept)
>     sign x = (source x,target x)
>     homogeneous :: rel -> Bool
>     homogeneous s = source s == target s
>
>   instance (Eq c)=>Association (Relation c) c where
>     source = relsrc
>     target = reltrg
>
>   class (Eq c, Association r c) => Morphic r c where
>     multiplicities :: r c -> [c]
>     multiplicities _ = []
> }}}

New description:

 Please find the script HaskellBug.hs at the bottom of this message.
 Here is how to reproduce the behaviour in two steps.

 Step 1: verify that Module HaskellBug produces the following error
 message:
 {{{
 [1 of 1] Compiling HaskellBug       ( HaskellBug.hs, interpreted )

 HaskellBug.hs:12:22:
     `rel' is not applied to enough type arguments
     Expected kind `??', but `rel' has kind `* -> *'
     In the type `rel -> concept'
     In the class declaration for `Association'
 }}}
 Step 2: remove the definition of class Morphic r c and verify that the
 script is now error free.

 You have now reproduced the symptoms.

 Assessment:
 In this situation, ghc has diagnosed an error in the definition of
 class Association. This error was resolved by removing another
 definition, without altering the definition of class Association.
 This proves that the definition of class Association was correct in the
 first place. Therefore, ghc has made a mistake. It has diagnosed
 the error in the wrong location. I whould have expected an error
 message like
 {{{
 HaskellBug.hs:23:22:
     `r' is applied to too many type arguments
     Expected <something sensible here>
     In the type `r -> c'
     In the class declaration for `Morphic'
 }}}
 Epilog:
 I have taken the trouble to isolate the problem in a small script,
 because this error has caused serious havoc in a large Haskell
 project. Students, who were still learning about parameterized
 types, have systematically been 'fixing' the wrong code, because
 ghc has never pointed in the direction of the real error. In the
 end, they were unable to resolve their mistake.
 Besides haarvesting a frustrating experience with parameterized
 types, wasting two entire days before giving up, they have turned a
 large script upside down and introduced many more mistakes. That is
 why I think it is important to get this fixed.

 Here is the script:

 {{{
 {-# OPTIONS  -XMultiParamTypeClasses  -XFunctionalDependencies
 -XFlexibleInstances #-}
 module HaskellBug where

   data Relation c -- The basic Relation
      = Rel { relnm :: String -- The name of the relation
            , relsrc :: c -- Source concept
            , reltrg :: c -- ^Target concept
            }
        deriving Eq

   class (Eq concept)=> Association rel concept | rel -> concept where
     source, target :: rel -> concept      -- e.g. Declaration Concept ->
 Concept
     sign  :: rel -> (concept,concept)
     sign x = (source x,target x)
     homogeneous :: rel -> Bool
     homogeneous s = source s == target s

   instance (Eq c)=>Association (Relation c) c where
     source = relsrc
     target = reltrg

   class (Eq c, Association r c) => Morphic r c where
     multiplicities :: r c -> [c]
     multiplicities _ = []
 }}}

--

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4875#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to