#3043: An unrelated definition monomorphizes a type even without the MR
-----------------------------+----------------------------------------------
Reporter:  Deewiant          |          Owner:                         
    Type:  bug               |         Status:  new                    
Priority:  normal            |      Component:  Compiler (Type checker)
 Version:  6.10.1            |       Severity:  normal                 
Keywords:                    |       Testcase:                         
      Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple       
-----------------------------+----------------------------------------------
 The following code:
 {{{
 {-# LANGUAGE NoMonomorphismRestriction #-}
 {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances,
 FunctionalDependencies #-}

 class Id a b | b -> a where id' :: a -> b
 instance Id [Char] [Char] where id' = id

 class Fst a where fst' :: a -> String
 instance Fst ([Char],a) where fst' = fst

 data Void a = Void

 void :: (String,a) -> Void a
 void _ = Void

 fst'' (a,b) =
   let x = (id' a, b)
       y = void x :: Void Int -- remove this line and the code compiles
    in fst' x
 }}}
 Results in:
 {{{
 arst.hs:18:6:
     No instance for (Fst (b, Int))
       arising from a use of `fst'' at arst.hs:18:6-11
     Possible fix: add an instance declaration for (Fst (b, Int))
     In the expression: fst' x
     In the expression:
         let
           x = (id' a, b)
           y = void x :: Void Int
         in fst' x
     In the definition of `fst''':
         fst'' (a, b)
                 = let
                     x = ...
                     y = ...
                   in fst' x

 arst.hs:18:11:
     No instance for (Id [Char] b)
       arising from a use of `x' at arst.hs:18:11
     Possible fix: add an instance declaration for (Id [Char] b)
     In the first argument of `fst'', namely `x'
     In the expression: fst' x
     In the expression:
         let
           x = (id' a, b)
           y = void x :: Void Int
         in fst' x
 }}}

 It seems that the definition of `y` locks down the type of `x` somewhat
 even though the monomorphism restriction is disabled. If we remove the
 definition:
 {{{
 *Main> :t fst''
 fst'' :: (Id t b, Fst (b, t1)) => (t, t1) -> String
 }}}

 To be completely honest I'm not sure whether the code should be accepted
 or not, since `(Id t b, Fst (b, t1))` can't be satisfied. Only the fully
 monomorphic signature `([Char], Int) -> String`, which is obtained with
 the definition of `y` in place and the monomorphism restriction enabled,
 works.

 In any case, I think it's a bug that the results of the type check depend
 on whether `y` is defined or not: surely that shouldn't matter at all, no
 matter what the end result is.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3043>
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