[GHC] #12950: unnecessarily complicated left-hand side causing RULE left-hand side too complicated to desugar

#12950: unnecessarily complicated left-hand side causing RULE left-hand side too complicated to desugar -------------------------------------+------------------------------------- Reporter: nfrisby | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | error/warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: #10555,#12074 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- GHC 7.10.2 rejects the `SPECIALIZE` pragma in the following snippet with "RULE left-hand side too complicated to desugar". {{{#!hs class C a where type TF a; m :: a -> TF a instance C Int where type TF Int = String; m = show overloaded :: C a => a -> (a,TF a) {-# INLINABLE overloaded #-} overloaded a = (a,m a) {-# SPECIALIZE overloaded :: Int -> (Int,TF Int) #-} }}} This use case is so simple/basic/prevalent that it seems inappropriate to reject it. The actual message is {{{ RULE left-hand side too complicated to desugar Optimised lhs: case cobox_awc of _ [Occ=Dead] { GHC.Types.Eq# cobox -> overloaded @ Int $dC_awb } Orig lhs: case cobox_awc of cobox_awc { GHC.Types.Eq# cobox -> overloaded @ Int $dC_awb } }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12950 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12950: unnecessarily complicated left-hand side causing RULE left-hand side too complicated to desugar -------------------------------------+------------------------------------- Reporter: nfrisby | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #10555,#12074 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nfrisby): I'm unfamiliar with the implementation of the type-checker. Even so, I flipped on `-ddump-tc-trace` to investigate where that troublesome coercion was coming from. I noticed the following subsequence of trace messages. {{{ tcSubTypeDS_NC the type signature for ‘overloaded’ a_awb[tau:1] -> (a_awb[tau:1], TF a_awb[tau:1]) Int -> (Int, TF Int) *snip* writeMetaTyVar a_awb[tau:1] := Int *snip* utype_defer cobox_awd TF a_awb[tau:1] TF Int arising from a type equality a_awb[tau:1] -> (a_awb[tau:1], TF a_awb[tau:1]) ~ Int -> (Int, TF Int) *snip* u_tys yields coercion: cobox_awd }}} This indicates that `cobox_awd` is the result of the unifier deferring the question of whether `TF a_awb ~ TF Int`, even though `a_awd` was already set to `Int`. Digging a bit deeper, I see that `TcUnify.uType` contains [https://github.com/ghc/ghc/blob/086b4836c4b279d5ae0e330719e1a679dd16392e/com... the following matches], which ultimately incur the coercion that sinks the SPECIALISE pragma since they do not check if the types' already solved tyvars admit reflexivity as a proof here. {{{#!hs -- Always defer if a type synonym family (type function) -- is involved. (Data families behave rigidly.) go ty1@(TyConApp tc1 _) ty2 | isTypeFamilyTyCon tc1 = uType_defer origin ty1 ty2 go ty1 ty2@(TyConApp tc2 _) | isTypeFamilyTyCon tc2 = uType_defer origin ty1 ty2 }}} I anticipate that a possible "fix" for this ticket would be for the `go` function to check if the solved type variables render `ty1` and `ty2` equivalent such that `TcRefl` would suffice here. Or perhaps there's somewhere more appropriate (`dsSpec`?) to perform that "optimization" for the sake of accepting SPECIALIZE pragmas like this one. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12950#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12950: unnecessarily complicated left-hand side causing RULE left-hand side too complicated to desugar -------------------------------------+------------------------------------- Reporter: nfrisby | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): #10555,#12074,#12649 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by nfrisby): * related: #10555,#12074 => #10555,#12074,#12649 Comment: The proposal in #12649 might involve an "alternate" code path in the type- checker that side-steps this issue: if a SPECIALIZE pragma could be declared more directly ("set `a` to `Int`"), then `decomposeRuleLhs` (the function that emits "RULE left-hand side too complicated to desugar") might not even be necessary. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12950#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12950: Unnecessarily complicated left-hand side for SPECIALIZE pragma causing RULE left-hand side too complicated to desugar -------------------------------------+------------------------------------- Reporter: nfrisby | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): #10555,#12074,#12649 | Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12950#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12950: Unnecessarily complicated left-hand side for SPECIALIZE pragma causing RULE left-hand side too complicated to desugar -------------------------------------+------------------------------------- Reporter: nfrisby | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: worksforme | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): #10555,#12074,#12649 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by nfrisby): * status: new => closed * resolution: => worksforme Comment: Closing this ticket -- the SPECIALIZE pragma is accepted and works as expected in in GHC 8.0.1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12950#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12950: Unnecessarily complicated left-hand side for SPECIALIZE pragma causing RULE
left-hand side too complicated to desugar
-------------------------------------+-------------------------------------
Reporter: nfrisby | Owner:
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.10.2
checker) |
Resolution: worksforme | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect | Unknown/Multiple
error/warning at compile-time | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
#10555,#12074,#12649 |
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#12950: Unnecessarily complicated left-hand side for SPECIALIZE pragma causing RULE left-hand side too complicated to desugar -------------------------------------+------------------------------------- Reporter: nfrisby | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: worksforme | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: error/warning at compile-time | deSugar/should_compile/T12950 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): #10555,#12074,#12649 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => deSugar/should_compile/T12950 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12950#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC