
#14203: GHC-inferred type signature doesn't actually typecheck -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.1 checker) | Keywords: TypeInType, Resolution: | TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Actually, it's not just limited to datatypes: the same effect can be observed in this program: {{{#!hs {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} module Bug where type family F a data Foo (z :: F a) bar :: forall a (z :: F a). Foo z -> Int bar _ = 42 }}} {{{ $ /opt/ghc/8.2.1/bin/ghci Bug.hs GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/ryanglscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:10:33: error: • Expected kind ‘F a0’, but ‘z’ has kind ‘F a’ • In the first argument of ‘Foo’, namely ‘z’ In the type signature: bar :: forall a (z :: F a). Foo z -> Int | 10 | bar :: forall a (z :: F a). Foo z -> Int | ^ }}} Here, I would expect `AllowAmbiguousTypes` to squash the error message about the ambiguous variable `a0` in `F a0`, but that doesn't happen. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14203#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler