[GHC] #9867: PatternSynonyms + ScopedTypeVariables triggers an internal error

#9867: PatternSynonyms + ScopedTypeVariables triggers an internal error -------------------------------------+------------------------------------- Reporter: antalsz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: Blocked By: | None/Unknown Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- When trying to give a type signature with a free type variable to a pattern in a pattern synonym, GHC dies with an internal error. Given the file {{{#!hs {-# LANGUAGE PatternSynonyms, ScopedTypeVariables #-} pattern Nil = [] :: [a] }}} the resulting error is {{{ Example.hs:2:22: GHC internal error: ‘a’ is not in scope during type checking, but it passed the renamer … tcl_env of environment: [] In an expression type signature: [a] In the expression: [] :: [a] In an equation for ‘$WNil’: $WNil = [] :: [a] Compilation failed. }}} The fix is to add `RankNTypes` and an explicit `forall`: {{{#!hs {-# LANGUAGE PatternSynonyms, ScopedTypeVariables, RankNTypes #-} pattern Nil = [] :: forall a. [a] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9867 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9867: PatternSynonyms + ScopedTypeVariables triggers an internal error -------------------------------------+------------------------------------- Reporter: antalsz | Owner: cactus Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: | Blocked By: None/Unknown | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => cactus Comment: Gergo, would you like to look at this? I think we should write down the rules for scoped type variables in pattern synonym definitions! Thanks Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9867#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9867: PatternSynonyms + ScopedTypeVariables triggers an internal error -------------------------------------+------------------------------------- Reporter: antalsz | Owner: cactus Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: | Blocked By: None/Unknown | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by cactus): Hrm. So what's happening here is that when we see {{{ pattern Nil = [] :: [a] }}} we rename and typecheck `[] :: [a]` as a pattern (like in a function definition); this by itself requires `ScopedTypeVariables` (in `rnHsBndrSig` I believe), as you can see by trying the following: {{{ {-# LANGUAGE PatternSynonyms #-} pattern Nil = [] :: [a] }}} {{{ T9867a.hs:2:21: Illegal type signature: ‘[a]’ Perhaps you intended to use ScopedTypeVariables In a pattern type-signature }}} If you do turn on `ScopedTypeVariables`, renaming succeeds and puts an unbound type variable in the type signature: {{{ pattern main@main:Main.Nil{d rvh} = ghc-prim-0.3.1.0:GHC.Types.[]{(w) d 6m} :: [a{tv awt}] }}} Then `tcInferPatSynDecl` typechecks this right-hand side, via some indirections: {{{ T9867.hs:2:15: env2 [(a{tv awt}, Type variable ‘a{tv awt}’ = a{tv aww}[sig:2])] T9867.hs:2:9: Skolemising a{tv aww}[sig:2] := a{tv awx}[sk] T9867.hs:2:9: writeMetaTyVar a{tv aww}[sig:2] := a{tv awx}[sk] }}} but by the time we get to `tc_patsyn_finish`, both `a{tv aww}` and `a{tv awx}` show up, as two separate types: the pattern type is `[a{tv awx}]`, but the pattern definition is `[] :: [a{tv aww}]`, so we end up generating the following code for the matcher: {{{ main@main:Main.$mNil{v rws}[gid] :: forall (r{tv awy}[sk] :: ghc-prim-0.3.1.0:GHC.Prim.OpenKind{(w) tc 34g}) a{tv awx}[sk]. [a{tv awx}[sk]] -> (ghc-prim-0.3.1.0:GHC.Prim.Void#{(w) tc 32L} -> r{tv awy}[sk]) -> (ghc-prim-0.3.1.0:GHC.Prim.Void#{(w) tc 32L} -> r{tv awy}[sk]) -> r{tv awy}[sk] [GblId, Str=DmdType] main@main:Main.$mNil{v rws} = /\(@ (r{tv awy}[sk] :: ghc-prim-0.3.1.0:GHC.Prim.OpenKind{(w) tc 34g})). /\(@ a{tv awx}[sk]). \ ((scrut_awA{v}[lid] :: [a{tv awx}[sk]])) ((cont_awB{v}[lid] :: Void#{(w) tc 32L} -> r{tv awy}[sk])) ((fail_awC{v}[lid] :: Void#{(w) tc 32L} -> r{tv awy}[sk])) -> case scrut_awA{v} of { ghc-prim-0.3.1.0:GHC.Types.[]{(w) d 6m}{EvBinds{}} :: [a{tv aww}[sig:2]] -> cont_awB{v} ghc-prim-0.3.1.0:GHC.Prim.void#{(w) v 0l} _ -> fail_awC{v} ghc-prim-0.3.1.0:GHC.Prim.void#{(w) v 0l} } }}} (note how we still have `[a{tv aww}]` in the type annotation of the case branch). This is where the error message is coming from. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9867#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9867: PatternSynonyms + ScopedTypeVariables triggers an internal error -------------------------------------+------------------------------------- Reporter: antalsz | Owner: cactus Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: | Blocked By: None/Unknown | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by cactus): I think we need to zonk the typechecked pattern before passing it to `tc_patsyn_finish`, so that the signature in it can be replaced with `[a{tv awx}]`. `TcHsSyn` doesn't currently export `zonkPat` but hopefully it will be enough to pass it an empty `ZonkEnv`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9867#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9867: PatternSynonyms + ScopedTypeVariables triggers an internal error -------------------------------------+------------------------------------- Reporter: antalsz | Owner: cactus Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 (Type checker) | Keywords: pattern synonyms Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: Compile- | Related Tickets: time crash | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by cactus): * keywords: => pattern synonyms * failure: None/Unknown => Compile-time crash * component: Compiler => Compiler (Type checker) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9867#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9867: PatternSynonyms + ScopedTypeVariables triggers an internal error -------------------------------------+------------------------------------- Reporter: antalsz | Owner: cactus Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 (Type checker) | Keywords: pattern synonyms Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: Compile- | Related Tickets: time crash | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by cactus): Some brainstorming: The patsyn builders are typechecked from this code: {{{ (binds', (extra_binds', thing)) <- tcBindGroups top_lvl sig_fn prag_fn binds $ do { thing <- thing_inside -- See Note [Pattern synonym builders don't yield dependencies] ; patsyn_builders <- mapM tcPatSynBuilderBind patsyns ; let extra_binds = [ (NonRecursive, builder) | builder <- patsyn_builders ] ; return (extra_binds, thing) } }}} At the time we call `tcPatSynBuilderBind`, all the typechecked pattern synonyms are available in the global environment, so we could look up whatever we could possibly need from the output of the typechecker. Currently, it is only easy to grab stuff from the `PatSyn` (which deliberately doesn't contain any details of the actual definition of the pattern synonym, only its type), but we should be able to look up the `PatSynBind Id Id` for a given `PatSynBind Name Name`; and then we should be in business. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9867#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9867: PatternSynonyms + ScopedTypeVariables triggers an internal error -------------------------------------+------------------------------------- Reporter: antalsz | Owner: cactus Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 (Type checker) | Keywords: PatternSynonyms Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: Compile- | Related Tickets: time crash | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by cactus): * keywords: pattern synonyms => PatternSynonyms -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9867#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9867: PatternSynonyms + ScopedTypeVariables triggers an internal error
-------------------------------------+-------------------------------------
Reporter: antalsz | Owner: cactus
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.8.3
checker) | Keywords:
Resolution: | PatternSynonyms
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#9867: PatternSynonyms + ScopedTypeVariables triggers an internal error
-------------------------------------+-------------------------------------
Reporter: antalsz | Owner: cactus
Type: bug | Status: merge
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.8.3
checker) | Keywords:
Resolution: | PatternSynonyms
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash | Test Case:
Blocked By: | patsyn/should_compile/T9867
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Changes (by simonpj):
* status: new => merge
* testcase: => patsyn/should_compile/T9867
Comment:
Fixed by
{{{
commit 3ea40e38a7ae03c05cb79485fb04a3f00c632793
Author: Simon Peyton Jones

#9867: PatternSynonyms + ScopedTypeVariables triggers an internal error -------------------------------------+------------------------------------- Reporter: antalsz | Owner: cactus Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.8.3 checker) | Keywords: Resolution: fixed | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | patsyn/should_compile/T9867 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thoughtpolice): * status: merge => closed * resolution: => fixed * milestone: => 7.12.1 Comment: I don't think this can be easily merged to `ghc-7.10` because I think it's dependent on 32973bf3c2f6fe00e01b44a63ac1904080466938, which I'm not keen on merging. So I'm going to drop this one to 7.12 instead. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9867#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC