[GHC] #15358: no way to talk about unpacking sum types / unpacking tuples

GHC ghc-devs at haskell.org
Tue Jul 10 19:59:56 UTC 2018


#15358: no way to talk about unpacking sum types / unpacking tuples
-------------------------------------+-------------------------------------
        Reporter:  chessai           |                Owner:  (none)
            Type:  feature request   |               Status:  new
        Priority:  normal            |            Milestone:  8.6.1
       Component:  Compiler          |              Version:  8.4.3
      Resolution:                    |             Keywords:  unboxedsums,
                                     |  unboxedtuples
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 osa1):

 If I understand correctly you want two things:

 1. Unpacking polymorphic fields
 2. Deeply unpacking strict fields

 (1) gets requested from time to time and it's not something that can be
 implemented easily, it deserves a detailed design and a proposal.

 (2) already works today. E.g.

 {{{
 {-# LANGUAGE BangPatterns #-}

 module Lib where

 data StrictIntPair = StrictIntPair {-# UNPACK #-} !Int {-# UNPACK #-} !Int

 data StrictTuple = StrictTuple
   {-# UNPACK #-} !Int
   {-# UNPACK #-} !StrictIntPair
 }}}

 If you look at worker functions for `StrictIntPair` and `StrictTuple`
 constructors:

 {{{
 Lib.$WStrictIntPair [InlPrag=INLINE[2]]
   :: GHC.Types.Int -> GHC.Types.Int -> Lib.StrictIntPair
 [GblId[DataConWrapper],
  Arity=2,
  Caf=NoCafRefs,
  Str=<S,U><S,U>m,
  Unf=OtherCon []] =
     [] \r [dt_s1aj dt_s1ak]
         case dt_s1aj of {
           GHC.Types.I# dt_s1am [Occ=Once] ->
               case dt_s1ak of {
                 GHC.Types.I# dt_s1ao [Occ=Once] ->
                     Lib.StrictIntPair [dt_s1am dt_s1ao];
               };
         };

 Lib.$WStrictTuple [InlPrag=INLINE[2]]
   :: GHC.Types.Int -> Lib.StrictIntPair -> Lib.StrictTuple
 [GblId[DataConWrapper],
  Arity=2,
  Caf=NoCafRefs,
  Str=<S,U><S,U>m,
  Unf=OtherCon []] =
     [] \r [dt_s1ac dt_s1ad]
         case dt_s1ac of {
           GHC.Types.I# dt_s1af [Occ=Once] ->
               case dt_s1ad of {
                 Lib.StrictIntPair dt_s1ah [Occ=Once] dt_s1ai [Occ=Once] ->
                     Lib.StrictTuple [dt_s1af dt_s1ah dt_s1ai];
               };
         };
 }}}

 Notice that `StrictIntPair` unpacks `Int`s, and `StrictTuple` uses those
 unpacked `Int`s.

 In your example you have two problems:

 - In the first example the data type is polymorphic on the field so you
 can't unpack the `SJust` field even if it's strict.
 - In `StrictTuple` you can't unpack `Int`s because the tuple is not strict
 in its fields. If you define a strict tuple as I did in my example you'll
 see that you get three unboxed `Int`s as fields in `StrictTuple`.

 Finally, when trying these out make sure you're using explicit `{-# UNPACK
 #-}` pragmas (otherwise it's hard to know if your field will be unpacked)
 and use `-O` (or `-O2`) as otherwise `UNPACK` pragmas don't work and you
 don't get automatic unpacking of small fields (e.g. `Int`s).

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


More information about the ghc-tickets mailing list