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

#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=,
Unf=OtherCon []] =
\r [m0_scBy s1_scBz]
src,
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

#14118: Strangeness regarding STG alternative types and linter -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14118#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14118: Strangeness regarding STG alternative types and linter -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): The `MultiValAlt` here arises from `CoreToStg.mkStgAltType`, which looks at the `typePrimRep` of the case binder to determine the `AltType`, {{{#!hs = case typePrimRep bndr_ty of [LiftedRep] -> case tyConAppTyCon_maybe (unwrapType bndr_ty) of Just tc | isAbstractTyCon tc -> look_for_better_tycon | isAlgTyCon tc -> AlgAlt tc | otherwise -> ASSERT2( _is_poly_alt_tycon tc, ppr tc ) PolyAlt Nothing -> PolyAlt [unlifted] -> PrimAlt unlifted not_unary -> MultiValAlt (length not_unary) }}} Here we are hitting the `not_unary` case where `length not_unary == 0` since the binder is of type `State# s`, which is void. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14118#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14118: Strangeness regarding STG alternative types and linter -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3858 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D3858 * milestone: => 8.4.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14118#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14118: Strangeness regarding STG alternative types and linter -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3858 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Judging from the logic in `lintStgExpr` mention in the ticket description, it seems like GHC is supposed to maintain the invariant that we will not use the case binder in the RHS if it is an unboxed tuple or sum (e.g. a `MultiValAlt`). However, I can't find this invariant documented anywhere, nor do we seem to respect it. For instance, consider this example from compiling `TyCoRep`, {{{ ghc-stage1: panic! (the 'impossible' happened) (GHC version 8.3.20170824 for x86_64-unknown-linux): *** Stg Lint ErrMsgs: in Stg2Stg *** <no location info>: warning: [in body of lambda with binders w_sx0k :: Coercion, w69_sx0l :: InterestingVarFun, w70_sx0m :: VarSet, ww_sx0n :: [Var], ww1_sx0o :: VarSet] ww5_sx1u :: (# [Var], VarSet #) is out of scope }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14118#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14118: Strangeness regarding STG alternative types and linter -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3858 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): For the record, always bringing `MultiVarAlt` binders into scope allows GHC to bootstrap with `-dstg-lint`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14118#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14118: Strangeness regarding STG alternative types and linter -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3858 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
it seems like GHC is supposed to maintain the invariant that we will not use the case binder in the RHS if it is an unboxed tuple or sum
Ah. That is true after the Unarise pass, but not before. (That's a change we brought in a few years back.) E.g. we can write {{{ f :: (# Int, Bool #) -> Int f x = ... g :: Bool -> (# Int, Bool #) }}} and then call it thus {{{ f (g True) }}} By the time we translate to STG that'll look like {{{ case g True of (r :: (# Int, Bool #)) -> f r }}} and I think that's what is happening here. But the Unarise pass transforms it to {{{ case g True of (# (x::Int), (y::Bool) #) -> f x y }}} by making f take two explicit arguments. Can you check that the problem is gone after Unarise? It'd be ideal for STG lint to have a flag that checked the stronger invariant after Unarise. Incidentally, this should also be true of lambda binders, whether used or not; before Unarise they can be unboxed tuples, but not after. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14118#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14118: Strangeness regarding STG alternative types and linter -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3889 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * differential: Phab:D3858 => Phab:D3889 Comment: Here is a patch fixing the linter to only check the invariant post- unarisation.
Incidentally, this should also be true of lambda binders, whether used or not; before Unarise they can be unboxed tuples, but not after.
The StgLinter considers any `StgLam` expression to be an error, so this case should already be covered. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14118#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14118: Strangeness regarding STG alternative types and linter -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3889 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
The StgLinter considers any StgLam expression to be an error, so this case should already be covered.
I meant the binders in `StgRhsClosure`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14118#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14118: Strangeness regarding STG alternative types and linter
-------------------------------------+-------------------------------------
Reporter: bgamari | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone: 8.4.1
Component: Compiler | Version: 8.2.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3889
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#14118: Strangeness regarding STG alternative types and linter -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3889 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14118#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14118: Strangeness regarding STG alternative types and linter -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: fixed | Keywords: stg-lint Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3889 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => stg-lint -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14118#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC