[GHC] #8907: Un-zonked kind variable passes through type checker

#8907: Un-zonked kind variable passes through type checker -------------------------------------------+------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.8.1-rc2 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: Blocked By: | None/Unknown Related Tickets: | Test Case: | Blocking: -------------------------------------------+------------------------------- I have this module: {{{ {-# LANGUAGE PolyKinds #-} module Bug where data Poly a }}} Now, I say this: {{{
ghc Bug.hs -fforce-recomp -dppr-debug -fprint-explicit-foralls -ddump-tc }}}
The following is produced: {{{ [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) TYPE SIGNATURES TYPE CONSTRUCTORS main:Bug.Poly{tc rn2} :: k{tv ao6} [sk] -> ghc-prim:GHC.Prim.*{(w) tc 34d} data Poly{tc} (k::ghc-prim:GHC.Prim.BOX{(w) tc 347}) (a::k) No C type associated Roles: [nominal, phantom] RecFlag NonRecursive, Not promotable = FamilyInstance: none COERCION AXIOMS Dependent modules: [] Dependent packages: [base, ghc-prim, integer-gmp] ==================== Typechecker ==================== }}} My concern is the `[sk]` that appears after the kind variable `k_ao6`. It would appear that a ''skolem'' type variable passes out of the type- checker and is used as the binder for polymorphic kind of `Poly`. Should this get zonked somewhere? My guess is that there is no way to get this apparent misbehavior to trigger some real failure, given that the variable will be substituted away before much else happens. Yet, when I saw a skolem appear in a similar position after modifying the type-checker, I was sure I had done something wrong somewhere. So, is this intended or accidental behavior? If accidental, should we be scared? If we needn't be scared, I'm happy to close this as wontfix, but a Note would probably be helpful somewhere. Apologies if that Note is already written and I missed it! The same behavior is present in 7.8.1 RC 2 and in HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8907 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8907: Un-zonked kind variable passes through type checker -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: 7.8.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * priority: normal => low Comment: Richard, can this ticket be closed? Output with ghc-7.10.3 is: {{{ [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) TYPE SIGNATURES TYPE CONSTRUCTORS type role Poly{tc} phantom data Poly{tc} (a :: k) COERCION AXIOMS Dependent modules: [] Dependent packages: [base-4.8.2.0, ghc-prim-0.4.0.0, integer-gmp-1.0.0.0] Bug.hs:1:1: ==================== Typechecker ==================== }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8907#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8907: Un-zonked kind variable passes through type checker -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: low | Milestone: Component: Compiler (Type | Version: 7.8.1-rc2 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * resolution: => fixed Comment: Yes, this would appear to be fixed. Thanks for noticing! Not worth a regression test, as I don't think the old behavior actually caused any problems. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8907#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC