StgCase - are LiveVars and SRT fields going to be used?

Ömer Sinan Ağacan omeragacan at gmail.com
Sat Feb 6 02:50:30 UTC 2016


Simon, I broke the debug build with that commit. I actually validated locally
before committing, but apparently the default validate settings doesn't define
DEBUG, so the new assertion implementation was not tested. (Why validate
doesn't define DEBUG by default???)

The fastest way to reproduce the bug is to use these validate settings:

    DYNAMIC_GHC_PROGRAMS = NO
    GhcLibWays = v
    GhcStage1HcOpts += -DDEBUG

I did some debugging. Here's an example definition that causes the assertion
failure:

      unpackCString#
      unpackCString# [InlPrag=NOINLINE] :: Addr# -> [Char]
      [GblId,
       Arity=1,
       Caf=NoCafRefs,
       Str=DmdType <S,U>,
       Unf=OtherCon []] =
          \r [addr_seX]
              let {
                unpack_seY [Occ=LoopBreaker] :: Int# -> [Char]
                [LclId, Arity=1, Str=DmdType <S,U>, Unf=OtherCon []] =
                    sat-only \r [nh_seZ]
                        case indexCharOffAddr# [addr_seX nh_seZ] of ch_sf0 {
                          __DEFAULT ->
                              let {
                                sat_sf3 [Occ=Once] :: [Char]
                                [LclId, Str=DmdType] =
                                    \u []
                                        case +# [nh_seZ 1#] of sat_sf2 {
                                          __DEFAULT -> unpack_seY sat_sf2;
                                        }; } in
                              let {
                                sat_sf1 [Occ=Once] :: Char
                                [LclId, Str=DmdType] =
                                    NO_CCS C#! [ch_sf0];
                              } in  : [sat_sf1 sat_sf3];
                          '\NUL'# -> [] [];
                        };
              } in  unpack_seY 0#;

Here the IdInfo says this doesn't have CAF refs, but `sat_sf3` is updatable, so
in our assertion we say that this has a CAF. In the implementation I basically
followed your description:

"
- If the binding is an updatable thunk, it has CAF refs.

- Otherwise it has CAF reffs iff any of its free Ids (including imported ones)
  has mayHaveCafRefs in its IdInfo. Actually you can probably ignore the "free"
  part and just check if any Id has mayHaveCafRefs set.
"

The first case is why we say "yes" to stgBindHasCafRefs. But I don't quite
understand why we say every updatable thunk has CAFs. I think this is only the
case with top-level updatable thunks, right? If no, then maybe the problem is
not with the assertion but rather with the CorePrep step that sets IdInfos? Any
ideas?

Thanks..

2016-02-01 20:19 GMT-05:00 Ömer Sinan Ağacan <omeragacan at gmail.com>:
> https://phabricator.haskell.org/D1880
>
> 2016-02-01 18:04 GMT-05:00 Simon Peyton Jones <simonpj at microsoft.com>:
>> Those fields are dead, now that the Cmm pass deals with it.  We left it in while making the transition, but they can go now.  Go ahead!
>>
>> (Lots of code should disappear along with them!)
>>
>> Simon
>>
>> | -----Original Message-----
>> | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Ömer Sinan
>> | Agacan
>> | Sent: 01 February 2016 22:06
>> | To: ghc-devs <ghc-devs at haskell.org>
>> | Subject: StgCase - are LiveVars and SRT fields going to be used?
>> |
>> | Hi all,
>> |
>> | This is how case expression in STG currently defined:
>> |
>> |
>> |   | StgCase
>> |         (GenStgExpr bndr occ)
>> |         (GenStgLiveVars occ)
>> |         (GenStgLiveVars occ)
>> |         bndr
>> |         SRT
>> |         AltType
>> |         [GenStgAlt bndr occ]
>> |
>> |
>> | The GenStgLiveVars and SRT fields are never used anywhere in the compiler
>> | (except the printer). So the question is, I'm assuming those were used at
>> | some
>> | point, but are they going to be used in the future? Or can I just delete
>> | those?
>> |
>> | As a proof of concept, I just compiled GHC using this:
>> |
>> |
>> |   | StgCase
>> |         (GenStgExpr bndr occ)
>> |         bndr
>> |         AltType
>> |         [GenStgAlt bndr occ]
>> |
>> |
>> | Normally this is not a big deal, but I'm doing lots of STG-to-STG
>> | transformations nowadays, and I have to keep those field updated which is
>> | annoying as those are never going to be used (I can't even know if I'm doing
>> | it
>> | right), or leave those `undefined` which is not a good practice.
>> | _______________________________________________
>> | ghc-devs mailing list
>> | ghc-devs at haskell.org
>> | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.haskell.
>> | org%2fcgi-bin%2fmailman%2flistinfo%2fghc-
>> | devs&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c12ca56c8fc514f477f7f08
>> | d32b53f4bc%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=LPiupNbUJ9OGL9cmbP%2f
>> | PAs2JSdxqlxk%2bGbXuYTHFbzg%3d


More information about the ghc-devs mailing list