[GHC] #14118: stg2stg passes appear to produce invalid STG

GHC ghc-devs at haskell.org
Tue Aug 15 17:16:28 UTC 2017


#14118: stg2stg passes appear to produce invalid STG
-------------------------------------+-------------------------------------
           Reporter:  bgamari        |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 While building with GHC with `-dstg-lint -g3 -O0` (after fixing #14116 and
 #14117) I encountered a rather peculiar error,
 {{{
 "inplace/bin/ghc-stage1" -hisuf hi -osuf  o -hcsuf hc -static  -O -H64m
 -Wall       -this-unit-id integer-gmp-1.0.1.0 -hide-all-packages -i
 -ilibraries/integer-gmp/src/ -ilibraries/integer-gmp/dist-install/build
  -Ilibraries/integer-gmp/dist-install/build -ilibraries/integer-gmp/dist-
 install/build/./autogen -Ilibraries/integer-gmp/dist-
 install/build/./autogen -Ilibraries/integer-gmp/include    -optP-include
 -optPlibrari
 es/integer-gmp/dist-install/build/./autogen/cabal_macros.h -package-id
 ghc-prim-0.5.1.0 -this-unit-id integer-gmp -Wall -XHaskell2010 -O -dcore-
 lint -g3 -ddump-to-file -ddump-stg -dcore-lint -dstg-lint -dcmm-lin
 t  -no-user-package-db -rtsopts  -Wno-deprecated-flags     -Wnoncanonical-
 monad-instances  -odir libraries/integer-gmp/dist-install/build -hidir
 libraries/integer-gmp/dist-install/build -stubdir libraries/intege
 r-gmp/dist-install/build   -dynamic-too -c libraries/integer-
 gmp/src//GHC/Integer/Type.hs -o libraries/integer-gmp/dist-
 install/build/GHC/Integer/Type.o -dyno libraries/integer-gmp/dist-
 install/build/GHC/Integer
 /Type.dyn_o
 ghc-stage1: panic! (the 'impossible' happened)
   (GHC version 8.3.20170815 for x86_64-unknown-linux):
           *** Stg Lint ErrMsgs: in Stg2Stg ***
   <no location info>: warning:
        [in body of lambda with binders m0_scBy :: State# s_a2Em
                                                   -> State# s_a2Em,
                                        s1_scBz :: State# s_a2Em]
       s'_scBA is out of scope
   <no location info>: warning:
        [in body of lambda with binders wild1_sdUv :: Int#]
       qr_sdUp is out of scope
 }}}

 Looking at the STG it appears that these warnings are absolutely correct,
 {{{#!hs
   svoid [InlPrag=INLINE (sat-args=1)]
     :: forall s. (State# s -> State# s) -> S s ()
   [GblId,
    Arity=2,
    Caf=NoCafRefs,
    Str=<C(S),1*C1(U)><S,U>,
    Unf=OtherCon []] =
       \r [m0_scBy s1_scBz]
           src<libraries/integer-gmp/src/GHC/Integer/Type.hs:1957:1-48>
           case m0_scBy s1_scBz of s'_scBA {
             __DEFAULT ->
                 src<libraries/integer-
 gmp/src/GHC/Integer/Type.hs:1957:37-48>
                 (#,#) [s'_scBA ()];
           };

 }}}
 This is quite strange given that `s'_scBA` is clearly in scope, being
 bound as the case binder.

 We had the following from Core Prep,
 {{{#!hs
 -- RHS size: {terms: 10, types: 17, coercions: 0, joins: 0/0}
 GHC.Integer.Type.svoid [InlPrag=INLINE (sat-args=1)]
   :: forall s.
      (GHC.Prim.State# s -> GHC.Prim.State# s) -> GHC.Integer.Type.S s ()
 [GblId,
  Arity=2,
  Caf=NoCafRefs,
  Str=<C(S),1*C1(U)><S,U>,
  Unf=OtherCon []]
 GHC.Integer.Type.svoid
   = \ (@ s_a2Em)
       (m0_scBy [Occ=Once!]
          :: GHC.Prim.State# s_a2Em -> GHC.Prim.State# s_a2Em)
       (s1_scBz [Occ=Once] :: GHC.Prim.State# s_a2Em) ->
       src<libraries/integer-gmp/src/GHC/Integer/Type.hs:1957:1-48>
       case m0_scBy s1_scBz of s'_scBA { __DEFAULT ->
       src<libraries/integer-gmp/src/GHC/Integer/Type.hs:1957:37-48>
       (# s'_scBA, GHC.Tuple.() #)
       }
 }}}


 The reason the linter fails here is due to the following logic in
 `lintStgExpr`,
 {{{#!hs
     in_scope <- MaybeT $ liftM Just $
      case alts_type of
         AlgAlt tc     -> check_bndr (tyConPrimRep tc) >> return True
         PrimAlt rep   -> check_bndr [rep]             >> return True
         MultiValAlt _ -> return False -- Binder is always dead in this
 case
         PolyAlt       -> return True

     MaybeT $ addInScopeVars [bndr | in_scope] $
              lintStgAlts alts scrut_ty
 }}}
 In the `svoid` case above we hit `MultiValAlt` path, which causes us to
 ignore the case binder. The fact that we hit `MultiValAlt` at all is a bit
 surprising given that the result is not an unboxed sum or tuple.

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


More information about the ghc-tickets mailing list