[GHC] #13410: GHC HEAD regression: Template variable unbound in rewrite rule

GHC ghc-devs at haskell.org
Sat Mar 11 04:21:30 UTC 2017


#13410: GHC HEAD regression: Template variable unbound in rewrite rule
-------------------------------------+-------------------------------------
        Reporter:  RyanGlScott       |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  highest           |            Milestone:  8.2.1
       Component:  Compiler          |              Version:  8.1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Compile-time      |  Unknown/Multiple
  crash or panic                     |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Description changed by RyanGlScott:

Old description:

> `hybrid-vectors-0.2.1` currently fails to build with GHC HEAD. I've
> attached a minimized repro file with no dependencies (it's 410 lines
> long, since I had to copy-paste a lot of code from `vector` in order to
> reproduce this). The attached file builds on GHC 7.10.3 and 8.0.2, but
> fails on GHC HEAD with this panic:
>
> {{{
> $ ~/Software/ghc2/inplace/bin/ghc-stage2 -O2 -fforce-recomp Bug.hs
> [1 of 1] Compiling Data.Vector.Hybrid.Internal ( Bug.hs, Bug.o )
>
> Bug.hs:389:10: warning: [-Wmissing-methods]
>     • No explicit implementation for
>         ‘gmbasicOverlaps’, ‘gmbasicInitialize’, and ‘gmbasicUnsafeRead’
>     • In the instance declaration for ‘GMVector (MVector u v) (a, b)’
>     |
> 389 | instance (GMVector u a, GMVector v b) => GMVector (MVector u v) (a,
> b) where
>     |
> ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
>
> Bug.hs:407:10: warning: [-Wmissing-methods]
>     • No explicit implementation for
>         ‘gbasicUnsafeFreeze’, ‘gbasicUnsafeThaw’, ‘gbasicLength’,
>         ‘gbasicUnsafeSlice’, and ‘gbasicUnsafeIndexM’
>     • In the instance declaration for ‘GVector (Vector u v) (a, b)’
>     |
> 407 | instance (GVector u a, GVector v b) => GVector (Vector u v) (a, b)
> where
>     |          ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
> ghc-stage2: panic! (the 'impossible' happened)
>   (GHC version 8.3.20170310 for x86_64-unknown-linux):
>         Template variable unbound in rewrite rule
>   Variable: sc_s8FV
>   Rule "SC:$j0"
>   Rule bndrs: [sc_s8FV, sc_s8FW, sc_s8FX, sg_s8FY, sc_s8FU]
>   LHS args: [sc_s8FU,
>              (MV
>                 @ (GMutable u_a4oM)
>                 @ (GMutable v_a4oO)
>                 @ (PrimState (ST RealWorld))
>                 @ (a_a4oN, b_a4oP)
>                 @ a_a4oN
>                 @ b_a4oP
>                 @~ (<(a_a4oN, b_a4oP)>_N
>                     :: ((a_a4oN, b_a4oP) :: *) ~# ((a_a4oN, b_a4oP) ::
> *))
>                 sc_s8FW
>                 sc_s8FX)
>              `cast` (sg_s8FY
>                      :: (MVector
>                            (GMutable u_a4oM)
>                            (GMutable v_a4oO)
>                            (PrimState (ST RealWorld))
>                            (a_a4oN, b_a4oP) :: *)
>                         ~R#
>                         (GMutable
>                            (Vector u_a4oM v_a4oO) (PrimState (ST
> RealWorld)) c_a4oQ :: *))]
>   Actual args: [sc_s8FS,
>                 wild_X3x
>                 `cast` (Sub
>                           (Sym (D:R:GMutableVector[0] <u_a4oM>_N
> <v_a4oO>_N)) <PrimState
> (ST
> RealWorld)>_N (Sym
> cobox_a4Gz)
>                         :: (MVector
>                               (GMutable u_a4oM)
>                               (GMutable v_a4oO)
>                               (PrimState (ST RealWorld))
>                               (a_a4oN, b_a4oP) :: *)
>                            ~R#
>                            (GMutable
>                               (Vector u_a4oM v_a4oO) (PrimState (ST
> RealWorld)) c_a4oQ :: *))]
>   Call stack:
>       CallStack (from HasCallStack):
>         prettyCurrentCallStack, called at
> compiler/utils/Outputable.hs:1191:58 in ghc:Outputable
>         callStackDoc, called at compiler/utils/Outputable.hs:1195:37 in
> ghc:Outputable
>         pprPanic, called at compiler/specialise/Rules.hs:579:19 in
> ghc:Rules
> }}}
>
> Some important things to note:
>
> * `-O2` is required to trigger this bug; using `-O1` or below works fine.
> * The problematic code is the `Read (Vector u v c)` instance at the very
> bottom. In particular, commenting out the last line `readPrec =
> greadPrec` makes the panic go away.
> * Moreover, there's a particular `INLINE` pragma in the `GMVector
> (MVector u v) (a, b)` instance that is critical to triggering the panic
> (it's on line 394; I've added a comment `Removing this INLINE pragma
> makes it compile` above it).

New description:

 `hybrid-vectors-0.2.1` currently fails to build with GHC HEAD. I've
 attached a minimized repro file with no dependencies (it's 410 lines long,
 since I had to copy-paste a lot of code from `vector` in order to
 reproduce this). The attached file builds on GHC 7.10.3 and 8.0.2, but
 fails on GHC HEAD with this panic:

 {{{
 $ ~/Software/ghc2/inplace/bin/ghc-stage2 -O2 -fforce-recomp Bug.hs
 [1 of 1] Compiling Data.Vector.Hybrid.Internal ( Bug.hs, Bug.o )

 Bug.hs:389:10: warning: [-Wmissing-methods]
     • No explicit implementation for
         ‘gmbasicOverlaps’, ‘gmbasicInitialize’, and ‘gmbasicUnsafeRead’
     • In the instance declaration for ‘GMVector (MVector u v) (a, b)’
     |
 389 | instance (GMVector u a, GMVector v b) => GMVector (MVector u v) (a,
 b) where
     |
 ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

 Bug.hs:407:10: warning: [-Wmissing-methods]
     • No explicit implementation for
         ‘gbasicUnsafeFreeze’, ‘gbasicUnsafeThaw’, ‘gbasicLength’,
         ‘gbasicUnsafeSlice’, and ‘gbasicUnsafeIndexM’
     • In the instance declaration for ‘GVector (Vector u v) (a, b)’
     |
 407 | instance (GVector u a, GVector v b) => GVector (Vector u v) (a, b)
 where
     |          ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
 ghc-stage2: panic! (the 'impossible' happened)
   (GHC version 8.3.20170310 for x86_64-unknown-linux):
         Template variable unbound in rewrite rule
   Variable: sc_s8FV
   Rule "SC:$j0"
   Rule bndrs: [sc_s8FV, sc_s8FW, sc_s8FX, sg_s8FY, sc_s8FU]
   LHS args: [sc_s8FU,
              (MV
                 @ (GMutable u_a4oM)
                 @ (GMutable v_a4oO)
                 @ (PrimState (ST RealWorld))
                 @ (a_a4oN, b_a4oP)
                 @ a_a4oN
                 @ b_a4oP
                 @~ (<(a_a4oN, b_a4oP)>_N
                     :: ((a_a4oN, b_a4oP) :: *) ~# ((a_a4oN, b_a4oP) :: *))
                 sc_s8FW
                 sc_s8FX)
              `cast` (sg_s8FY
                      :: (MVector
                            (GMutable u_a4oM)
                            (GMutable v_a4oO)
                            (PrimState (ST RealWorld))
                            (a_a4oN, b_a4oP) :: *)
                         ~R#
                         (GMutable
                            (Vector u_a4oM v_a4oO) (PrimState (ST
 RealWorld)) c_a4oQ :: *))]
   Actual args: [sc_s8FS,
                 wild_X3x
                 `cast` (Sub
                           (Sym (D:R:GMutableVector[0] <u_a4oM>_N
 <v_a4oO>_N)) <PrimState
 (ST
 RealWorld)>_N (Sym
 cobox_a4Gz)
                         :: (MVector
                               (GMutable u_a4oM)
                               (GMutable v_a4oO)
                               (PrimState (ST RealWorld))
                               (a_a4oN, b_a4oP) :: *)
                            ~R#
                            (GMutable
                               (Vector u_a4oM v_a4oO) (PrimState (ST
 RealWorld)) c_a4oQ :: *))]
   Call stack:
       CallStack (from HasCallStack):
         prettyCurrentCallStack, called at
 compiler/utils/Outputable.hs:1191:58 in ghc:Outputable
         callStackDoc, called at compiler/utils/Outputable.hs:1195:37 in
 ghc:Outputable
         pprPanic, called at compiler/specialise/Rules.hs:579:19 in
 ghc:Rules
 }}}

 Some important things to note:

 * `-O2` is required to trigger this bug; using `-O1` or below works fine.
 * The problematic code is the `Read (Vector u v c)` instance at the very
 bottom. In particular, commenting out the last line `readPrec = greadPrec`
 makes the panic go away.
 * Moreover, there's a particular `INLINE` pragma in the `GMVector (MVector
 u v) (a, b)` instance that is critical to triggering the panic (it's on
 line 395; I've added a comment `Removing this INLINE pragma makes it
 compile` above it).

--

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13410#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list