Converting unboxed sum types in StgCmm

Simon Peyton Jones simonpj at microsoft.com
Tue Sep 22 12:43:43 UTC 2015


Johan

Sorry I’ve been buried.  Let’s fix a time for a Skype call if you’d like to chat about this stuff.

Quick response to the below. I think that afterwards we want it to look like this:

post-unarise

f = \r [ ds1::Int#  ds2::Ptr ]
      case ds1 of
          0#  ->  <rhs with ds2 in place of x_svo>
         1#  -> <rhs>

ds2 is the thing that contains either an Int or a char; ds1 is the tag that distinguishes htem.

Simon

From: Johan Tibell [mailto:johan.tibell at gmail.com]
Sent: 14 September 2015 17:03
To: Ryan Newton; Simon Peyton Jones
Cc: Simon Marlow; ghc-devs at haskell.org
Subject: Re: Converting unboxed sum types in StgCmm

I've given this a yet some more thought. Given this simple core program:

f [InlPrag=NOINLINE] :: (#|#) Int Char -> Int
[GblId, Arity=1, Str=DmdType]
f =
  \ (ds_dmE :: (#|#) Int Char) ->
    case ds_dmE of _ [Occ=Dead] {
      (#_|#) x_amy -> x_amy;
      (#|_#) ipv_smK -> patError @ Int "UnboxedSum.hs:5:1-15|function f"#
    }

We will get this stg pre-unarise:

unarise
  [f [InlPrag=NOINLINE] :: (#|#) Int Char -> Int
   [GblId, Arity=1, Str=DmdType, Unf=OtherCon []] =
       \r srt:SRT:[0e :-> patError] [ds_svm]
           case ds_svm of _ [Occ=Dead] {
             (#_|#) x_svo [Occ=Once] -> x_svo;
             (#|_#) _ [Occ=Dead] -> patError "UnboxedSum.hs:5:1-15|function f"#;
           };]

What do we want it to look like afterwards? I currently, have this, modeled after unboxed tuples:

post-unarise:
  [f [InlPrag=NOINLINE] :: (#|#) Int Char -> Int
   [GblId, Arity=1, Str=DmdType, Unf=OtherCon []] =
       \r srt:SRT:[0e :-> patError] [ds_gvu ds_gvv]
           case (#_|#) [ds_gvu ds_gvv] of _ [Occ=Dead] {  -- <-- WHAT SHOULD GO HERE?
             (#_|#) x_svo [Occ=Once] -> x_svo;
             (#|_#) _ [Occ=Dead] -> patError "UnboxedSum.hs:5:1-15|function f"#;
           };]

Here I have performed the same rewriting of the scrutinee in the case statement as for unboxed tuples, but note that this doesn't quite work, as we don't know which data constructor to apply in "..." in case ... of. In the case of tuples it's easy; there is only one.

It seems to me that we just want to rewrite the case altogether into something that looks at the tag field of the data constructor. Also, in stg we use the same DataCon as in core, but after stg the unboxed sum case really only has one constructor (one with the union of all the fields), which makes it awkward to reuse the original DataCon.



On Mon, Sep 14, 2015 at 7:27 AM, Ryan Newton <rrnewton at gmail.com<mailto:rrnewton at gmail.com>> wrote:

  *
data RepType = UbxTupleRep [UnaryType]
    | UbxSumRep [UnaryType]
    | UnaryRep UnaryType
Not, fully following, but ... this reptype business is orthogonal to whether you add a normal type to the STG level that models anonymous, untagged unions, right?

That is, when using Any for pointer types, they could use indicative phantom types, like "Any (Union Bool Char)", even if there's not full support for doing anything useful with (Union Bool Char) by itself.  Maybe the casting machinery could greenlight a cast from Any (Union Bool Char) to Bool at least?

There's already the unboxed union itself, (|# #|) , but that's different than a pointer to a union of types...



-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20150922/a2a3785c/attachment-0001.html>


More information about the ghc-devs mailing list