[GHC] #16002: Type family equation with wrong name is silently accepted (GHC 8.6+ only)

#16002: Type family equation with wrong name is silently accepted (GHC 8.6+ only) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.2 Keywords: TypeFamilies | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC accepts Unknown/Multiple | invalid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Here's a program: {{{#!hs {-# LANGUAGE TypeFamilies #-} module TypeFamilies where data A type family B (x :: *) :: * where A x = x }}} One would hope that GHC would reject that nonsensical equation for `B` that references `A`. On GHC 7.8 through 8.4, that is the case: {{{ $ /opt/ghc/8.4.4/bin/ghci Bug.hs GHCi, version 8.4.4: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling TypeFamilies ( Bug.hs, interpreted ) Bug.hs:6:3: error: • Mismatched type name in type family instance. Expected: B Actual: A • In the type family declaration for ‘B’ | 6 | A x = x | ^^^^^^^ }}} But GHC 8.6.2 and HEAD actually //accept// this program! Thankfully, GHC appears to just treat `A x = x` as though you had written `B x = x`, so it's not like this breaks type safety or anything. Still, this most definitely ought to be rejected. One interesting observation is that `B` having a CUSK appears to be important. If `B` doesn't have a CUSK, as in the following variant: {{{#!hs {-# LANGUAGE TypeFamilies #-} module TypeFamilies where data A type family B x where A x = x }}} Then GHC properly catches the mismatched use of `A`: {{{ $ /opt/ghc/8.6.2/bin/ghci Bug.hs GHCi, version 8.6.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling TypeFamilies ( Bug.hs, interpreted ) Bug.hs:6:3: error: • Mismatched type name in type family instance. Expected: B Actual: A • In the type family declaration for ‘B’ | 6 | A x = x | ^^^^^^^ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16002 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16002: Type family equation with wrong name is silently accepted (GHC 8.6+ only) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.2 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This regression was introduced in commit faec8d358985e5d0bf363bd96f23fe76c9e281f7 (`Track type variable scope more carefully.`). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16002#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16002: Type family equation with wrong name is silently accepted (GHC 8.6+ only) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.2 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Ah, it's due to this change: {{{#!diff kcLTyClDecl :: LTyClDecl GhcRn -> TcM () -- See Note [Kind checking for type and class decls] kcLTyClDecl (L loc decl) + | hsDeclHasCusk decl + = traceTc "kcTyClDecl skipped due to cusk" (ppr tc_name) + | otherwise = setSrcSpan loc $ tcAddDeclCtxt decl $ - do { traceTc "kcTyClDecl {" (ppr (tyClDeclLName decl)) + do { traceTc "kcTyClDecl {" (ppr tc_name) ; kcTyClDecl decl - ; traceTc "kcTyClDecl done }" (ppr (tyClDeclLName decl)) } + ; traceTc "kcTyClDecl done }" (ppr tc_name) } + where + tc_name = tyClDeclLName decl }}} Note that `kcTyClDecl` (which performs the validity check needed to reject `A x = x` above) is only invoked when a type family declaration lacks a CUSK! NB: This code no longer exists in GHC HEAD, as it has since been refactored into [http://git.haskell.org/ghc.git/blob/5f1d949ab9e09b8d95319633854b7959df06eb58... kcTyClGroup]: {{{#!hs kcTyClGroup decls = do { ... ; let (cusk_decls, no_cusk_decls) = partition (hsDeclHasCusk . unLoc) decls ; ... ; mapM_ kcLTyClDecl no_cusk_decls ; ... } }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16002#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16002: Type family equation with wrong name is silently accepted (GHC 8.6+ only) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.2 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): (Interestingly, this exact bit of code was also [https://ghc.haskell.org/trac/ghc/ticket/15116#comment:2 responsible] for causing #15116.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16002#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16002: Type family equation with wrong name is silently accepted (GHC 8.6+ only) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.2 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Ah yes, good catch. I think the Right Thing is to move the test out of `kcTyFamInstEqn` and put it in `RnSource.rnFamInstEqn`. That way it'll be nailed by the renamer, which has plenty of information to give a good error message. Would you consider doing that? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16002#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16002: Type family equation with wrong name is silently accepted (GHC 8.6+ only) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.2 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5420 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D5420 Comment: Moving the check to the renamer seems to work pretty well! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16002#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16002: Type family equation with wrong name is silently accepted (GHC 8.6+ only) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.2 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5420 Wiki Page: | -------------------------------------+------------------------------------- Comment (by carter): should this fix go into a 8.6.3 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16002#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16002: Type family equation with wrong name is silently accepted (GHC 8.6+ only)
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone: 8.8.1
Component: Compiler | Version: 8.6.2
Resolution: | Keywords: TypeFamilies
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC accepts | Unknown/Multiple
invalid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D5420
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#16002: Type family equation with wrong name is silently accepted (GHC 8.6+ only) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.2 Resolution: fixed | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC accepts | Test Case: invalid program | rename/should_fail/T16002 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5420 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * testcase: => rename/should_fail/T16002 * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16002#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC