The following little module:

        module Bug where

        newtype Foo = Foo [Foo]
        newtype Bar = Bar Foo

        unBar :: Bar -> Foo
        unBar (Bar x) = x

fails core-lint in both 6.2 and the HEAD:

*** Core Lint Errors: in result of Desugar ***
Bug.hs:7:
    [RHS of x :: Bug.Foo]
    The type of this binder doesn't match the type of its RHS: x
    Binder's type: Bug.Foo
    Rhs type: Bug.Bar
*** Offending Program ***
Rec {
unBar :: Bug.Bar -> Bug.Foo
unBar = \ ds_dch :: Bug.Bar ->
          let {
            x :: Bug.Foo
            x = ds_dch
          } in  x
Bug.unBar :: Bug.Bar -> Bug.Foo
Bug.unBar = unBar
end Rec }

*** End of Offense ***
_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to