Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

12 changed files:

Changes:

  • compiler/GHC/Builtin/Uniques.hs
    ... ... @@ -97,37 +97,37 @@ Note [Unique layout for unboxed sums]
    97 97
     
    
    98 98
     Sum arities start from 2. The encoding is a bit funny: we break up the
    
    99 99
     integral part into bitfields for the arity, an alternative index (which is
    
    100
    -taken to be 0xfc in the case of the TyCon), and, in the case of a datacon, a
    
    101
    -tag (used to identify the sum's TypeRep binding).
    
    100
    +taken to be 0x1ffc in the case of the TyCon), and, in the case of a datacon,
    
    101
    +a tag (used to identify the sum's TypeRep binding).
    
    102 102
     
    
    103 103
     This layout is chosen to remain compatible with the usual unique allocation
    
    104 104
     for wired-in data constructors described in GHC.Types.Unique
    
    105 105
     
    
    106 106
     TyCon for sum of arity k:
    
    107
    -  00000000 kkkkkkkk 11111100
    
    107
    +  kkkkkkkk kkk11111 11111100
    
    108 108
     
    
    109 109
     TypeRep of TyCon for sum of arity k:
    
    110
    -  00000000 kkkkkkkk 11111101
    
    110
    +  kkkkkkkk kkk11111 11111101
    
    111 111
     
    
    112 112
     DataCon for sum of arity k and alternative n (zero-based):
    
    113
    -  00000000 kkkkkkkk nnnnnn00
    
    113
    +  kkkkkkkk kkknnnnn nnnnnn00
    
    114 114
     
    
    115 115
     TypeRep for sum DataCon of arity k and alternative n (zero-based):
    
    116
    -  00000000 kkkkkkkk nnnnnn10
    
    116
    +  kkkkkkkk kkknnnnn nnnnnn10
    
    117 117
     -}
    
    118 118
     
    
    119 119
     mkSumTyConUnique :: Arity -> Unique
    
    120 120
     mkSumTyConUnique arity =
    
    121
    -    assertPpr (arity <= 0x3f) (ppr arity) $
    
    122
    -              -- 0x3f since we only have 6 bits to encode the
    
    121
    +    assertPpr (arity <= 0x7ff) (ppr arity) $
    
    122
    +              -- 0x7ff since we only have 11 bits to encode the
    
    123 123
                   -- alternative
    
    124
    -    mkUniqueInt 'z' (arity `shiftL` 8 .|. 0xfc)
    
    124
    +    mkUniqueInt 'z' (arity `shiftL` 13 .|. 0x1ffc)
    
    125 125
     
    
    126 126
     -- | Inverse of 'mkSumTyConUnique'
    
    127 127
     isSumTyConUnique :: Unique -> Maybe Arity
    
    128 128
     isSumTyConUnique u =
    
    129
    -  case (tag, n .&. 0xfc) of
    
    130
    -    ('z', 0xfc) -> Just (word64ToInt n `shiftR` 8)
    
    129
    +  case (tag, n .&. 0x1ffc) of
    
    130
    +    ('z', 0x1ffc) -> Just (word64ToInt n `shiftR` 13)
    
    131 131
         _ -> Nothing
    
    132 132
       where
    
    133 133
         (tag, n) = unpkUnique u
    
    ... ... @@ -137,11 +137,11 @@ mkSumDataConUnique alt arity
    137 137
       | alt >= arity
    
    138 138
       = panic ("mkSumDataConUnique: " ++ show alt ++ " >= " ++ show arity)
    
    139 139
       | otherwise
    
    140
    -  = mkUniqueInt 'z' (arity `shiftL` 8 + alt `shiftL` 2) {- skip the tycon -}
    
    140
    +  = mkUniqueInt 'z' (arity `shiftL` 13 + alt `shiftL` 2) {- skip the tycon -}
    
    141 141
     
    
    142 142
     getUnboxedSumName :: Int -> Name
    
    143 143
     getUnboxedSumName n
    
    144
    -  | n .&. 0xfc == 0xfc
    
    144
    +  | n .&. 0x1ffc == 0x1ffc
    
    145 145
       = case tag of
    
    146 146
           0x0 -> tyConName $ sumTyCon arity
    
    147 147
           0x1 -> getRep $ sumTyCon arity
    
    ... ... @@ -155,8 +155,8 @@ getUnboxedSumName n
    155 155
       | otherwise
    
    156 156
       = pprPanic "getUnboxedSumName" (ppr n)
    
    157 157
       where
    
    158
    -    arity = n `shiftR` 8
    
    159
    -    alt = (n .&. 0xfc) `shiftR` 2
    
    158
    +    arity = n `shiftR` 13
    
    159
    +    alt = (n .&. 0x1ffc) `shiftR` 2
    
    160 160
         tag = 0x3 .&. n
    
    161 161
         getRep tycon =
    
    162 162
             fromMaybe (pprPanic "getUnboxedSumName(getRep)" (ppr tycon))
    

  • compiler/GHC/Cmm/Utils.hs
    ... ... @@ -115,6 +115,9 @@ slotCmmType platform = \case
    115 115
        PtrUnliftedSlot -> gcWord platform
    
    116 116
        PtrLiftedSlot   -> gcWord platform
    
    117 117
        WordSlot        -> bWord platform
    
    118
    +   Word8Slot       -> b8
    
    119
    +   Word16Slot      -> b16
    
    120
    +   Word32Slot      -> b32
    
    118 121
        Word64Slot      -> b64
    
    119 122
        FloatSlot       -> f32
    
    120 123
        DoubleSlot      -> f64
    

  • compiler/GHC/Stg/Unarise.hs
    ... ... @@ -404,7 +404,6 @@ import GHC.Stg.Syntax
    404 404
     import GHC.Stg.Utils
    
    405 405
     import GHC.Stg.Make
    
    406 406
     import GHC.Core.Type
    
    407
    -import GHC.Builtin.Types.Prim (intPrimTy)
    
    408 407
     import GHC.Builtin.Types
    
    409 408
     import GHC.Types.Unique.Supply
    
    410 409
     import GHC.Types.Unique
    
    ... ... @@ -681,15 +680,15 @@ elimCase rho args bndr (MultiValAlt _) [GenStgAlt{ alt_con = _
    681 680
     
    
    682 681
     elimCase rho args@(tag_arg : real_args) bndr (MultiValAlt _) alts
    
    683 682
       | isUnboxedSumBndr bndr
    
    684
    -  = do tag_bndr <- mkId (mkFastString "tag") tagTy
    
    683
    +  = do tag_bndr <- mkId (mkFastString "tag") (tagTyArg tag_arg)
    
    685 684
               -- this won't be used but we need a binder anyway
    
    686 685
            let rho1 = extendRho rho bndr (MultiVal args)
    
    687 686
                scrut' = case tag_arg of
    
    688 687
                           StgVarArg v     -> StgApp v []
    
    689 688
                           StgLitArg l     -> StgLit l
    
    690
    -
    
    691
    -       alts' <- unariseSumAlts rho1 real_args alts
    
    692
    -       return (StgCase scrut' tag_bndr tagAltTy alts')
    
    689
    +           alt_ty = (tagAltTyArg tag_arg)
    
    690
    +       alts' <- unariseSumAlts rho1 alt_ty real_args alts
    
    691
    +       return (StgCase scrut' tag_bndr alt_ty alts')
    
    693 692
     
    
    694 693
     elimCase _ args bndr alt_ty alts
    
    695 694
       = pprPanic "elimCase - unhandled case"
    
    ... ... @@ -732,8 +731,9 @@ unariseAlts rho (MultiValAlt _) bndr [GenStgAlt{ alt_con = DEFAULT
    732 731
     unariseAlts rho (MultiValAlt _) bndr alts
    
    733 732
       | isUnboxedSumBndr bndr
    
    734 733
       = do (rho_sum_bndrs, scrt_bndrs@(tag_bndr : real_bndrs)) <- unariseConArgBinder rho bndr
    
    735
    -       alts' <- unariseSumAlts rho_sum_bndrs (map StgVarArg real_bndrs) alts
    
    736
    -       let inner_case = StgCase (StgApp tag_bndr []) tag_bndr tagAltTy alts'
    
    734
    +       let alt_ty = tagAltTy tag_bndr
    
    735
    +       alts' <- unariseSumAlts rho_sum_bndrs alt_ty (map StgVarArg real_bndrs) alts
    
    736
    +       let inner_case = StgCase (StgApp tag_bndr []) tag_bndr alt_ty alts'
    
    737 737
            return [GenStgAlt{ alt_con   = DataAlt (tupleDataCon Unboxed (length scrt_bndrs))
    
    738 738
                             , alt_bndrs = scrt_bndrs
    
    739 739
                             , alt_rhs   = inner_case
    
    ... ... @@ -753,21 +753,23 @@ unariseAlt rho alt@GenStgAlt{alt_con=_,alt_bndrs=xs,alt_rhs=e}
    753 753
     -- | Make alternatives that match on the tag of a sum
    
    754 754
     -- (i.e. generate LitAlts for the tag)
    
    755 755
     unariseSumAlts :: UnariseEnv
    
    756
    +               -> AltType
    
    756 757
                    -> [StgArg] -- sum components _excluding_ the tag bit.
    
    757 758
                    -> [StgAlt] -- original alternative with sum LHS
    
    758 759
                    -> UniqSM [StgAlt]
    
    759
    -unariseSumAlts env args alts
    
    760
    -  = do alts' <- mapM (unariseSumAlt env args) alts
    
    760
    +unariseSumAlts env tag_slot args alts
    
    761
    +  = do alts' <- mapM (unariseSumAlt env tag_slot args) alts
    
    761 762
            return (mkDefaultLitAlt alts')
    
    762 763
     
    
    763 764
     unariseSumAlt :: UnariseEnv
    
    765
    +              -> AltType
    
    764 766
                   -> [StgArg] -- sum components _excluding_ the tag bit.
    
    765 767
                   -> StgAlt   -- original alternative with sum LHS
    
    766 768
                   -> UniqSM StgAlt
    
    767
    -unariseSumAlt rho _ GenStgAlt{alt_con=DEFAULT,alt_bndrs=_,alt_rhs=e}
    
    769
    +unariseSumAlt rho _ _ GenStgAlt{alt_con=DEFAULT,alt_bndrs=_,alt_rhs=e}
    
    768 770
       = GenStgAlt DEFAULT mempty <$> unariseExpr rho e
    
    769 771
     
    
    770
    -unariseSumAlt rho args alt@GenStgAlt{ alt_con   = DataAlt sumCon
    
    772
    +unariseSumAlt rho tag_slot args alt@GenStgAlt{ alt_con   = DataAlt sumCon
    
    771 773
                                     , alt_bndrs = bs
    
    772 774
                                     , alt_rhs   = e
    
    773 775
                                     }
    
    ... ... @@ -776,10 +778,18 @@ unariseSumAlt rho args alt@GenStgAlt{ alt_con = DataAlt sumCon
    776 778
                   [b] -> mapSumIdBinders b args e rho
    
    777 779
                   -- Sums must have one binder
    
    778 780
                   _ -> pprPanic "unariseSumAlt2" (ppr args $$ pprPanicAlt alt)
    
    779
    -       let lit_case   = LitAlt (LitNumber LitNumInt (fromIntegral (dataConTag sumCon)))
    
    781
    +       let num_ty =
    
    782
    +            case tag_slot of
    
    783
    +              PrimAlt Word8Rep  -> LitNumWord8
    
    784
    +              PrimAlt Word16Rep -> LitNumWord16
    
    785
    +              PrimAlt Word32Rep -> LitNumWord32
    
    786
    +              PrimAlt WordRep   -> LitNumWord
    
    787
    +              _ -> pprPanic "unariseSumAlt: unexpected tag slot type" (ppr tag_slot)
    
    788
    +
    
    789
    +           lit_case   = LitAlt (LitNumber num_ty (fromIntegral (dataConTag sumCon)))
    
    780 790
            GenStgAlt lit_case mempty <$> unariseExpr rho' e'
    
    781 791
     
    
    782
    -unariseSumAlt _ scrt alt
    
    792
    +unariseSumAlt _ _ scrt alt
    
    783 793
       = pprPanic "unariseSumAlt3" (ppr scrt $$ pprPanicAlt alt)
    
    784 794
     
    
    785 795
     --------------------------------------------------------------------------------
    
    ... ... @@ -865,12 +875,6 @@ mapSumIdBinders alt_bndr args rhs rho0
    865 875
     
    
    866 876
           typed_id_args = map StgVarArg typed_ids
    
    867 877
     
    
    868
    -      -- pprTrace "mapSumIdBinders"
    
    869
    -      --           (text "fld_reps" <+> ppr fld_reps $$
    
    870
    -      --           text "id_args" <+> ppr id_arg_exprs $$
    
    871
    -      --           text "rhs" <+> ppr rhs $$
    
    872
    -      --           text "rhs_with_casts" <+> ppr rhs_with_casts
    
    873
    -      --           ) $
    
    874 878
         if isMultiValBndr alt_bndr
    
    875 879
           then return (extendRho rho0 alt_bndr (MultiVal typed_id_args), rhs_with_casts rhs)
    
    876 880
           else assert (typed_id_args `lengthIs` 1) $
    
    ... ... @@ -921,13 +925,19 @@ mkUbxSum
    921 925
          )
    
    922 926
     mkUbxSum dc ty_args args0 us
    
    923 927
       = let
    
    924
    -      _ :| sum_slots = ubxSumRepType ty_args
    
    928
    +      tag_slot :| sum_slots = ubxSumRepType ty_args
    
    925 929
           -- drop tag slot
    
    926 930
           field_slots = (mapMaybe (repSlotTy . stgArgRep) args0)
    
    927 931
           tag = dataConTag dc
    
    928 932
           layout'  = layoutUbxSum sum_slots field_slots
    
    929 933
     
    
    930
    -      tag_arg  = StgLitArg (LitNumber LitNumInt (fromIntegral tag))
    
    934
    +      tag_arg =
    
    935
    +        case tag_slot of
    
    936
    +          Word8Slot  -> StgLitArg (LitNumber LitNumWord8 (fromIntegral tag))
    
    937
    +          Word16Slot -> StgLitArg (LitNumber LitNumWord16 (fromIntegral tag))
    
    938
    +          Word32Slot -> StgLitArg (LitNumber LitNumWord32 (fromIntegral tag))
    
    939
    +          WordSlot   -> StgLitArg (LitNumber LitNumWord (fromIntegral tag))
    
    940
    +          _          -> pprPanic "mkUbxSum: unexpected tag slot type" (ppr tag_slot)
    
    931 941
           arg_idxs = IM.fromList (zipEqual layout' args0)
    
    932 942
     
    
    933 943
           ((_idx,_idx_map,_us,wrapper),slot_args)
    
    ... ... @@ -990,6 +1000,9 @@ ubxSumRubbishArg :: SlotTy -> StgArg
    990 1000
     ubxSumRubbishArg PtrLiftedSlot   = StgVarArg aBSENT_SUM_FIELD_ERROR_ID
    
    991 1001
     ubxSumRubbishArg PtrUnliftedSlot = StgVarArg aBSENT_SUM_FIELD_ERROR_ID
    
    992 1002
     ubxSumRubbishArg WordSlot        = StgLitArg (LitNumber LitNumWord 0)
    
    1003
    +ubxSumRubbishArg Word8Slot       = StgLitArg (LitNumber LitNumWord8 0)
    
    1004
    +ubxSumRubbishArg Word16Slot      = StgLitArg (LitNumber LitNumWord16 0)
    
    1005
    +ubxSumRubbishArg Word32Slot      = StgLitArg (LitNumber LitNumWord32 0)
    
    993 1006
     ubxSumRubbishArg Word64Slot      = StgLitArg (LitNumber LitNumWord64 0)
    
    994 1007
     ubxSumRubbishArg FloatSlot       = StgLitArg (LitFloat 0)
    
    995 1008
     ubxSumRubbishArg DoubleSlot      = StgLitArg (LitDouble 0)
    
    ... ... @@ -1166,11 +1179,18 @@ isUnboxedTupleBndr = isUnboxedTupleType . idType
    1166 1179
     mkTuple :: [StgArg] -> StgExpr
    
    1167 1180
     mkTuple args = StgConApp (tupleDataCon Unboxed (length args)) NoNumber args []
    
    1168 1181
     
    
    1169
    -tagAltTy :: AltType
    
    1170
    -tagAltTy = PrimAlt IntRep
    
    1182
    +tagAltTyArg :: StgArg -> AltType
    
    1183
    +tagAltTyArg a
    
    1184
    +  | [pr] <- typePrimRep (stgArgType a) = PrimAlt pr
    
    1185
    +  | otherwise = pprPanic "tagAltTyArg" (ppr a)
    
    1186
    +
    
    1187
    +tagAltTy :: Id -> AltType
    
    1188
    +tagAltTy i
    
    1189
    +  | [pr] <- typePrimRep (idType i) = PrimAlt pr
    
    1190
    +  | otherwise = pprPanic "tagAltTy" (ppr $ idType i)
    
    1171 1191
     
    
    1172
    -tagTy :: Type
    
    1173
    -tagTy = intPrimTy
    
    1192
    +tagTyArg :: StgArg -> Type
    
    1193
    +tagTyArg x = stgArgType x
    
    1174 1194
     
    
    1175 1195
     voidArg :: StgArg
    
    1176 1196
     voidArg = StgVarArg voidPrimId
    

  • compiler/GHC/StgToCmm/DataCon.hs
    ... ... @@ -107,10 +107,10 @@ cgTopRhsCon cfg id con mn args
    107 107
                 fix_padding (x@(Padding n off) : rest)
    
    108 108
                   | n == 0                 = fix_padding rest
    
    109 109
                   | n `elem` [1,2,4,8]     = x : fix_padding rest
    
    110
    -              | n > 8                  = add_pad 8
    
    111
    -              | n > 4                  = add_pad 4
    
    112
    -              | n > 2                  = add_pad 2
    
    113
    -              | otherwise              = add_pad 1
    
    110
    +              | testBit n 0            = add_pad 1
    
    111
    +              | testBit n 1            = add_pad 2
    
    112
    +              | testBit n 2            = add_pad 4
    
    113
    +              | otherwise              = add_pad 8
    
    114 114
                   where add_pad m = Padding m off : fix_padding (Padding (n-m) (off+m) : rest)
    
    115 115
                 fix_padding (x : rest)     = x : fix_padding rest
    
    116 116
                 fix_padding []             = []
    

  • compiler/GHC/Types/RepType.hs
    ... ... @@ -197,12 +197,12 @@ type SortedSlotTys = [SlotTy]
    197 197
     -- of the list we have the slot for the tag.
    
    198 198
     ubxSumRepType :: [[PrimRep]] -> NonEmpty SlotTy
    
    199 199
     ubxSumRepType constrs0
    
    200
    -  -- These first two cases never classify an actual unboxed sum, which always
    
    200
    +  -- This first case never classifies an actual unboxed sum, which always
    
    201 201
       -- has at least two disjuncts. But it could happen if a user writes, e.g.,
    
    202 202
       -- forall (a :: TYPE (SumRep [IntRep])). ...
    
    203 203
       -- which could never be instantiated. We still don't want to panic.
    
    204 204
       | constrs0 `lengthLessThan` 2
    
    205
    -  = WordSlot :| []
    
    205
    +  = Word8Slot :| []
    
    206 206
     
    
    207 207
       | otherwise
    
    208 208
       = let
    
    ... ... @@ -230,8 +230,17 @@ ubxSumRepType constrs0
    230 230
           rep :: [PrimRep] -> SortedSlotTys
    
    231 231
           rep ty = sort (map primRepSlot ty)
    
    232 232
     
    
    233
    -      sumRep = WordSlot :| combine_alts (map rep constrs0)
    
    234
    -               -- WordSlot: for the tag of the sum
    
    233
    +      -- constructors start at 1, pick an appropriate slot size for the tag
    
    234
    +      tag_slot | length constrs0 < 256        = Word8Slot
    
    235
    +               | length constrs0 < 65536      = Word16Slot
    
    236
    +               -- we use 2147483647 instead of 4294967296 to avoid
    
    237
    +               -- overflow when building a 32 bit GHC. Please fix the
    
    238
    +               -- overflow if you encounter a type with more than 2147483646
    
    239
    +               -- constructors and need the tag to be 32 bits.
    
    240
    +               | length constrs0 < 2147483647 = Word32Slot
    
    241
    +               | otherwise                    = WordSlot
    
    242
    +
    
    243
    +      sumRep = tag_slot :| combine_alts (map rep constrs0)
    
    235 244
         in
    
    236 245
           sumRep
    
    237 246
     
    
    ... ... @@ -275,22 +284,32 @@ layoutUbxSum sum_slots0 arg_slots0 =
    275 284
     --   - Float slots: Shared between floating point types.
    
    276 285
     --
    
    277 286
     --   - Void slots: Shared between void types. Not used in sums.
    
    278
    ---
    
    279
    --- TODO(michalt): We should probably introduce `SlotTy`s for 8-/16-/32-bit
    
    280
    --- values, so that we can pack things more tightly.
    
    281
    -data SlotTy = PtrLiftedSlot | PtrUnliftedSlot | WordSlot | Word64Slot | FloatSlot | DoubleSlot | VecSlot Int PrimElemRep
    
    287
    +
    
    288
    +data SlotTy = PtrLiftedSlot
    
    289
    +            | PtrUnliftedSlot
    
    290
    +            | Word8Slot
    
    291
    +            | Word16Slot
    
    292
    +            | Word32Slot
    
    293
    +            | WordSlot
    
    294
    +            | Word64Slot
    
    295
    +            | FloatSlot
    
    296
    +            | DoubleSlot
    
    297
    +            | VecSlot Int PrimElemRep
    
    282 298
       deriving (Eq, Ord)
    
    283 299
         -- Constructor order is important! If slot A could fit into slot B
    
    284 300
         -- then slot A must occur first.  E.g.  FloatSlot before DoubleSlot
    
    285 301
         --
    
    286
    -    -- We are assuming that WordSlot is smaller than or equal to Word64Slot
    
    287
    -    -- (would not be true on a 128-bit machine)
    
    302
    +    -- We are assuming that Word32Slot <= WordSlot <= Word64Slot
    
    303
    +    -- (would not be true on a 16-bit or 128-bit machine)
    
    288 304
     
    
    289 305
     instance Outputable SlotTy where
    
    290 306
       ppr PtrLiftedSlot   = text "PtrLiftedSlot"
    
    291 307
       ppr PtrUnliftedSlot = text "PtrUnliftedSlot"
    
    292 308
       ppr Word64Slot      = text "Word64Slot"
    
    293 309
       ppr WordSlot        = text "WordSlot"
    
    310
    +  ppr Word32Slot      = text "Word32Slot"
    
    311
    +  ppr Word16Slot      = text "Word16Slot"
    
    312
    +  ppr Word8Slot       = text "Word8Slot"
    
    294 313
       ppr DoubleSlot      = text "DoubleSlot"
    
    295 314
       ppr FloatSlot       = text "FloatSlot"
    
    296 315
       ppr (VecSlot n e)   = text "VecSlot" <+> ppr n <+> ppr e
    
    ... ... @@ -307,14 +326,14 @@ primRepSlot (BoxedRep mlev) = case mlev of
    307 326
       Just Lifted   -> PtrLiftedSlot
    
    308 327
       Just Unlifted -> PtrUnliftedSlot
    
    309 328
     primRepSlot IntRep      = WordSlot
    
    310
    -primRepSlot Int8Rep     = WordSlot
    
    311
    -primRepSlot Int16Rep    = WordSlot
    
    312
    -primRepSlot Int32Rep    = WordSlot
    
    329
    +primRepSlot Int8Rep     = Word8Slot
    
    330
    +primRepSlot Int16Rep    = Word16Slot
    
    331
    +primRepSlot Int32Rep    = Word32Slot
    
    313 332
     primRepSlot Int64Rep    = Word64Slot
    
    314 333
     primRepSlot WordRep     = WordSlot
    
    315
    -primRepSlot Word8Rep    = WordSlot
    
    316
    -primRepSlot Word16Rep   = WordSlot
    
    317
    -primRepSlot Word32Rep   = WordSlot
    
    334
    +primRepSlot Word8Rep    = Word8Slot
    
    335
    +primRepSlot Word16Rep   = Word16Slot
    
    336
    +primRepSlot Word32Rep   = Word32Slot
    
    318 337
     primRepSlot Word64Rep   = Word64Slot
    
    319 338
     primRepSlot AddrRep     = WordSlot
    
    320 339
     primRepSlot FloatRep    = FloatSlot
    
    ... ... @@ -325,6 +344,9 @@ slotPrimRep :: SlotTy -> PrimRep
    325 344
     slotPrimRep PtrLiftedSlot   = BoxedRep (Just Lifted)
    
    326 345
     slotPrimRep PtrUnliftedSlot = BoxedRep (Just Unlifted)
    
    327 346
     slotPrimRep Word64Slot      = Word64Rep
    
    347
    +slotPrimRep Word32Slot      = Word32Rep
    
    348
    +slotPrimRep Word16Slot      = Word16Rep
    
    349
    +slotPrimRep Word8Slot       = Word8Rep
    
    328 350
     slotPrimRep WordSlot        = WordRep
    
    329 351
     slotPrimRep DoubleSlot      = DoubleRep
    
    330 352
     slotPrimRep FloatSlot       = FloatRep
    
    ... ... @@ -349,11 +371,12 @@ fitsIn ty1 ty2
    349 371
       -- See Note [Casting slot arguments]
    
    350 372
       where
    
    351 373
         isWordSlot Word64Slot = True
    
    374
    +    isWordSlot Word32Slot = True
    
    375
    +    isWordSlot Word16Slot = True
    
    376
    +    isWordSlot Word8Slot  = True
    
    352 377
         isWordSlot WordSlot   = True
    
    353 378
         isWordSlot _          = False
    
    354 379
     
    
    355
    -
    
    356
    -
    
    357 380
     {- **********************************************************************
    
    358 381
     *                                                                       *
    
    359 382
                        PrimRep
    

  • testsuite/tests/codeGen/should_compile/T25166.stdouttestsuite/tests/codeGen/should_compile/T25166.stdout-ws-32
    ... ... @@ -2,5 +2,7 @@
    2 2
          Test.foo_closure:
    
    3 3
              const Test.D_con_info;
    
    4 4
              const GHC.Internal.Types.True_closure+2;
    
    5
    -         const 2;
    
    5
    +         const 2 :: W8;
    
    6
    +         const 0 :: W8;
    
    7
    +         const 0 :: W16;
    
    6 8
              const 3;

  • testsuite/tests/codeGen/should_compile/T25166.stdout-ws-64
    1
    +[section ""data" . Test.foo_closure" {
    
    2
    +     Test.foo_closure:
    
    3
    +         const Test.D_con_info;
    
    4
    +         const GHC.Internal.Types.True_closure+2;
    
    5
    +         const 2 :: W8;
    
    6
    +         const 0 :: W8;
    
    7
    +         const 0 :: W16;
    
    8
    +         const 0 :: W32;
    
    9
    +         const 3;

  • testsuite/tests/unboxedsums/UbxSumUnpackedSize.hs
    1
    +module Main where
    
    2
    +
    
    3
    +import GHC.Exts.Heap.Closures
    
    4
    +import Control.Exception (evaluate)
    
    5
    +import Data.Word (Word32)
    
    6
    +import Data.Int (Int8, Int16)
    
    7
    +
    
    8
    +-- this should get a Word8 tag
    
    9
    +data E1
    
    10
    +  = E1_1 | E1_2 | E1_3 | E1_4 | E1_5 | E1_6 | E1_7 | E1_8
    
    11
    +  | E1_9 | E1_10 | E1_11 | E1_12 | E1_13 | E1_14 | E1_15 | E1_16
    
    12
    +  | E1_17 | E1_18 | E1_19 | E1_20 | E1_21 | E1_22 | E1_23 | E1_24
    
    13
    +  | E1_25 | E1_26 | E1_27 | E1_28 | E1_29 | E1_30 | E1_31 | E1_32
    
    14
    +  | E1_33 | E1_34 | E1_35 | E1_36 | E1_37 | E1_38 | E1_39 | E1_40
    
    15
    +  | E1_41 | E1_42 | E1_43 | E1_44 | E1_45 | E1_46 | E1_47 | E1_48
    
    16
    +  | E1_49 | E1_50 | E1_51 | E1_52 | E1_53 | E1_54 | E1_55 | E1_56
    
    17
    +  | E1_57 | E1_58 | E1_59 | E1_60 | E1_61 | E1_62 | E1_63 | E1_64
    
    18
    +  | E1_65 | E1_66 | E1_67 | E1_68 | E1_69 | E1_70 | E1_71 | E1_72
    
    19
    +  | E1_73 | E1_74 | E1_75 | E1_76 | E1_77 | E1_78 | E1_79 | E1_80
    
    20
    +  | E1_81 | E1_82 | E1_83 | E1_84 | E1_85 | E1_86 | E1_87 | E1_88
    
    21
    +  | E1_89 | E1_90 | E1_91 | E1_92 | E1_93 | E1_94 | E1_95 | E1_96
    
    22
    +  | E1_97 | E1_98 | E1_99 | E1_100 | E1_101 | E1_102 | E1_103 | E1_104
    
    23
    +  | E1_105 | E1_106 | E1_107 | E1_108 | E1_109 | E1_110 | E1_111 | E1_112
    
    24
    +  | E1_113 | E1_114 | E1_115 | E1_116 | E1_117 | E1_118 | E1_119 | E1_120
    
    25
    +  | E1_121 | E1_122 | E1_123 | E1_124 | E1_125 | E1_126 | E1_127 | E1_128
    
    26
    +  | E1_129 | E1_130 | E1_131 | E1_132 | E1_133 | E1_134 | E1_135 | E1_136
    
    27
    +  | E1_137 | E1_138 | E1_139 | E1_140 | E1_141 | E1_142 | E1_143 | E1_144
    
    28
    +  | E1_145 | E1_146 | E1_147 | E1_148 | E1_149 | E1_150 | E1_151 | E1_152
    
    29
    +  | E1_153 | E1_154 | E1_155 | E1_156 | E1_157 | E1_158 | E1_159 | E1_160
    
    30
    +  | E1_161 | E1_162 | E1_163 | E1_164 | E1_165 | E1_166 | E1_167 | E1_168
    
    31
    +  | E1_169 | E1_170 | E1_171 | E1_172 | E1_173 | E1_174 | E1_175 | E1_176
    
    32
    +  | E1_177 | E1_178 | E1_179 | E1_180 | E1_181 | E1_182 | E1_183 | E1_184
    
    33
    +  | E1_185 | E1_186 | E1_187 | E1_188 | E1_189 | E1_190 | E1_191 | E1_192
    
    34
    +  | E1_193 | E1_194 | E1_195 | E1_196 | E1_197 | E1_198 | E1_199 | E1_200
    
    35
    +  | E1_201 | E1_202 | E1_203 | E1_204 | E1_205 | E1_206 | E1_207 | E1_208
    
    36
    +  | E1_209 | E1_210 | E1_211 | E1_212 | E1_213 | E1_214 | E1_215 | E1_216
    
    37
    +  | E1_217 | E1_218 | E1_219 | E1_220 | E1_221 | E1_222 | E1_223 | E1_224
    
    38
    +  | E1_225 | E1_226 | E1_227 | E1_228 | E1_229 | E1_230 | E1_231 | E1_232
    
    39
    +  | E1_233 | E1_234 | E1_235 | E1_236 | E1_237 | E1_238 | E1_239 | E1_240
    
    40
    +  | E1_241 | E1_242 | E1_243 | E1_244 | E1_245 | E1_246 | E1_247 | E1_248
    
    41
    +  | E1_249 | E1_250 | E1_251 | E1_252 | E1_253 | E1_254
    
    42
    +  deriving (Enum, Bounded, Show)
    
    43
    +
    
    44
    +-- this should get a Word8 tag
    
    45
    +data E2
    
    46
    +  = E2_1 | E2_2 | E2_3 | E2_4 | E2_5 | E2_6 | E2_7 | E2_8
    
    47
    +  | E2_9 | E2_10 | E2_11 | E2_12 | E2_13 | E2_14 | E2_15 | E2_16
    
    48
    +  | E2_17 | E2_18 | E2_19 | E2_20 | E2_21 | E2_22 | E2_23 | E2_24
    
    49
    +  | E2_25 | E2_26 | E2_27 | E2_28 | E2_29 | E2_30 | E2_31 | E2_32
    
    50
    +  | E2_33 | E2_34 | E2_35 | E2_36 | E2_37 | E2_38 | E2_39 | E2_40
    
    51
    +  | E2_41 | E2_42 | E2_43 | E2_44 | E2_45 | E2_46 | E2_47 | E2_48
    
    52
    +  | E2_49 | E2_50 | E2_51 | E2_52 | E2_53 | E2_54 | E2_55 | E2_56
    
    53
    +  | E2_57 | E2_58 | E2_59 | E2_60 | E2_61 | E2_62 | E2_63 | E2_64
    
    54
    +  | E2_65 | E2_66 | E2_67 | E2_68 | E2_69 | E2_70 | E2_71 | E2_72
    
    55
    +  | E2_73 | E2_74 | E2_75 | E2_76 | E2_77 | E2_78 | E2_79 | E2_80
    
    56
    +  | E2_81 | E2_82 | E2_83 | E2_84 | E2_85 | E2_86 | E2_87 | E2_88
    
    57
    +  | E2_89 | E2_90 | E2_91 | E2_92 | E2_93 | E2_94 | E2_95 | E2_96
    
    58
    +  | E2_97 | E2_98 | E2_99 | E2_100 | E2_101 | E2_102 | E2_103 | E2_104
    
    59
    +  | E2_105 | E2_106 | E2_107 | E2_108 | E2_109 | E2_110 | E2_111 | E2_112
    
    60
    +  | E2_113 | E2_114 | E2_115 | E2_116 | E2_117 | E2_118 | E2_119 | E2_120
    
    61
    +  | E2_121 | E2_122 | E2_123 | E2_124 | E2_125 | E2_126 | E2_127 | E2_128
    
    62
    +  | E2_129 | E2_130 | E2_131 | E2_132 | E2_133 | E2_134 | E2_135 | E2_136
    
    63
    +  | E2_137 | E2_138 | E2_139 | E2_140 | E2_141 | E2_142 | E2_143 | E2_144
    
    64
    +  | E2_145 | E2_146 | E2_147 | E2_148 | E2_149 | E2_150 | E2_151 | E2_152
    
    65
    +  | E2_153 | E2_154 | E2_155 | E2_156 | E2_157 | E2_158 | E2_159 | E2_160
    
    66
    +  | E2_161 | E2_162 | E2_163 | E2_164 | E2_165 | E2_166 | E2_167 | E2_168
    
    67
    +  | E2_169 | E2_170 | E2_171 | E2_172 | E2_173 | E2_174 | E2_175 | E2_176
    
    68
    +  | E2_177 | E2_178 | E2_179 | E2_180 | E2_181 | E2_182 | E2_183 | E2_184
    
    69
    +  | E2_185 | E2_186 | E2_187 | E2_188 | E2_189 | E2_190 | E2_191 | E2_192
    
    70
    +  | E2_193 | E2_194 | E2_195 | E2_196 | E2_197 | E2_198 | E2_199 | E2_200
    
    71
    +  | E2_201 | E2_202 | E2_203 | E2_204 | E2_205 | E2_206 | E2_207 | E2_208
    
    72
    +  | E2_209 | E2_210 | E2_211 | E2_212 | E2_213 | E2_214 | E2_215 | E2_216
    
    73
    +  | E2_217 | E2_218 | E2_219 | E2_220 | E2_221 | E2_222 | E2_223 | E2_224
    
    74
    +  | E2_225 | E2_226 | E2_227 | E2_228 | E2_229 | E2_230 | E2_231 | E2_232
    
    75
    +  | E2_233 | E2_234 | E2_235 | E2_236 | E2_237 | E2_238 | E2_239 | E2_240
    
    76
    +  | E2_241 | E2_242 | E2_243 | E2_244 | E2_245 | E2_246 | E2_247 | E2_248
    
    77
    +  | E2_249 | E2_250 | E2_251 | E2_252 | E2_253 | E2_254 | E2_255
    
    78
    +  deriving (Enum, Bounded, Show)
    
    79
    +
    
    80
    +-- this needs a Word16 tag
    
    81
    +data E3
    
    82
    +  = E3_1 | E3_2 | E3_3 | E3_4 | E3_5 | E3_6 | E3_7 | E3_8
    
    83
    +  | E3_9 | E3_10 | E3_11 | E3_12 | E3_13 | E3_14 | E3_15 | E3_16
    
    84
    +  | E3_17 | E3_18 | E3_19 | E3_20 | E3_21 | E3_22 | E3_23 | E3_24
    
    85
    +  | E3_25 | E3_26 | E3_27 | E3_28 | E3_29 | E3_30 | E3_31 | E3_32
    
    86
    +  | E3_33 | E3_34 | E3_35 | E3_36 | E3_37 | E3_38 | E3_39 | E3_40
    
    87
    +  | E3_41 | E3_42 | E3_43 | E3_44 | E3_45 | E3_46 | E3_47 | E3_48
    
    88
    +  | E3_49 | E3_50 | E3_51 | E3_52 | E3_53 | E3_54 | E3_55 | E3_56
    
    89
    +  | E3_57 | E3_58 | E3_59 | E3_60 | E3_61 | E3_62 | E3_63 | E3_64
    
    90
    +  | E3_65 | E3_66 | E3_67 | E3_68 | E3_69 | E3_70 | E3_71 | E3_72
    
    91
    +  | E3_73 | E3_74 | E3_75 | E3_76 | E3_77 | E3_78 | E3_79 | E3_80
    
    92
    +  | E3_81 | E3_82 | E3_83 | E3_84 | E3_85 | E3_86 | E3_87 | E3_88
    
    93
    +  | E3_89 | E3_90 | E3_91 | E3_92 | E3_93 | E3_94 | E3_95 | E3_96
    
    94
    +  | E3_97 | E3_98 | E3_99 | E3_100 | E3_101 | E3_102 | E3_103 | E3_104
    
    95
    +  | E3_105 | E3_106 | E3_107 | E3_108 | E3_109 | E3_110 | E3_111 | E3_112
    
    96
    +  | E3_113 | E3_114 | E3_115 | E3_116 | E3_117 | E3_118 | E3_119 | E3_120
    
    97
    +  | E3_121 | E3_122 | E3_123 | E3_124 | E3_125 | E3_126 | E3_127 | E3_128
    
    98
    +  | E3_129 | E3_130 | E3_131 | E3_132 | E3_133 | E3_134 | E3_135 | E3_136
    
    99
    +  | E3_137 | E3_138 | E3_139 | E3_140 | E3_141 | E3_142 | E3_143 | E3_144
    
    100
    +  | E3_145 | E3_146 | E3_147 | E3_148 | E3_149 | E3_150 | E3_151 | E3_152
    
    101
    +  | E3_153 | E3_154 | E3_155 | E3_156 | E3_157 | E3_158 | E3_159 | E3_160
    
    102
    +  | E3_161 | E3_162 | E3_163 | E3_164 | E3_165 | E3_166 | E3_167 | E3_168
    
    103
    +  | E3_169 | E3_170 | E3_171 | E3_172 | E3_173 | E3_174 | E3_175 | E3_176
    
    104
    +  | E3_177 | E3_178 | E3_179 | E3_180 | E3_181 | E3_182 | E3_183 | E3_184
    
    105
    +  | E3_185 | E3_186 | E3_187 | E3_188 | E3_189 | E3_190 | E3_191 | E3_192
    
    106
    +  | E3_193 | E3_194 | E3_195 | E3_196 | E3_197 | E3_198 | E3_199 | E3_200
    
    107
    +  | E3_201 | E3_202 | E3_203 | E3_204 | E3_205 | E3_206 | E3_207 | E3_208
    
    108
    +  | E3_209 | E3_210 | E3_211 | E3_212 | E3_213 | E3_214 | E3_215 | E3_216
    
    109
    +  | E3_217 | E3_218 | E3_219 | E3_220 | E3_221 | E3_222 | E3_223 | E3_224
    
    110
    +  | E3_225 | E3_226 | E3_227 | E3_228 | E3_229 | E3_230 | E3_231 | E3_232
    
    111
    +  | E3_233 | E3_234 | E3_235 | E3_236 | E3_237 | E3_238 | E3_239 | E3_240
    
    112
    +  | E3_241 | E3_242 | E3_243 | E3_244 | E3_245 | E3_246 | E3_247 | E3_248
    
    113
    +  | E3_249 | E3_250 | E3_251 | E3_252 | E3_253 | E3_254 | E3_255 | E3_256
    
    114
    +  deriving (Enum, Bounded, Show)
    
    115
    +
    
    116
    +data U_Bool = U_Bool {-# UNPACK #-} !Bool
    
    117
    +                     {-# UNPACK #-} !Bool
    
    118
    +                     {-# UNPACK #-} !Bool
    
    119
    +                     {-# UNPACK #-} !Bool
    
    120
    +                     {-# UNPACK #-} !Bool
    
    121
    +                     {-# UNPACK #-} !Bool
    
    122
    +                     {-# UNPACK #-} !Bool
    
    123
    +                     {-# UNPACK #-} !Bool
    
    124
    +    deriving (Show)
    
    125
    +
    
    126
    +data U_E1 = U_E1 {-# UNPACK #-} !E1
    
    127
    +                 {-# UNPACK #-} !Int8
    
    128
    +                 {-# UNPACK #-} !Int8
    
    129
    +                 {-# UNPACK #-} !Int8
    
    130
    +                 {-# UNPACK #-} !Int8
    
    131
    +                 {-# UNPACK #-} !Int8
    
    132
    +                 {-# UNPACK #-} !Int8
    
    133
    +                 {-# UNPACK #-} !Int8
    
    134
    +    deriving (Show)
    
    135
    +
    
    136
    +data U_E2 = U_E2 {-# UNPACK #-} !E2
    
    137
    +                 {-# UNPACK #-} !Int8
    
    138
    +                 {-# UNPACK #-} !Int8
    
    139
    +                 {-# UNPACK #-} !Int8
    
    140
    +                 {-# UNPACK #-} !Int8
    
    141
    +                 {-# UNPACK #-} !Int8
    
    142
    +                 {-# UNPACK #-} !Int8
    
    143
    +                 {-# UNPACK #-} !Int8
    
    144
    +    deriving (Show)
    
    145
    +
    
    146
    +{-
    
    147
    +  disabled to reduce memory consumption of test
    
    148
    +
    
    149
    +data U_E3 = U_E3 {-# UNPACK #-} !E3
    
    150
    +                 {-# UNPACK #-} !Int8
    
    151
    +                 {-# UNPACK #-} !Int8
    
    152
    +                 {-# UNPACK #-} !Int8
    
    153
    +                 {-# UNPACK #-} !Int8
    
    154
    +                 {-# UNPACK #-} !Int8
    
    155
    +                 {-# UNPACK #-} !Int8
    
    156
    +                 {-# UNPACK #-} !Int8
    
    157
    +    deriving (Show)
    
    158
    +
    
    159
    +data U_Mixed = U_Mixed {-# UNPACK #-} !E1
    
    160
    +                       {-# UNPACK #-} !Int8
    
    161
    +                       {-# UNPACK #-} !E2
    
    162
    +                       {-# UNPACK #-} !Int16
    
    163
    +                       {-# UNPACK #-} !Int16
    
    164
    +                       {-# UNPACK #-} !Int16
    
    165
    +                       {-# UNPACK #-} !Bool
    
    166
    +                       {-# UNPACK #-} !Bool
    
    167
    +    deriving (Show)
    
    168
    +-}
    
    169
    +
    
    170
    +data U_Maybe = U_Maybe {-# UNPACK #-} !(Maybe Bool)
    
    171
    +                       {-# UNPACK #-} !(Maybe Bool)
    
    172
    +                       {-# UNPACK #-} !(Maybe Bool)
    
    173
    +                       {-# UNPACK #-} !(Maybe Bool)
    
    174
    +                       {-# UNPACK #-} !(Maybe Bool)
    
    175
    +                       {-# UNPACK #-} !(Maybe Bool)
    
    176
    +                       {-# UNPACK #-} !(Maybe Bool)
    
    177
    +                       {-# UNPACK #-} !(Maybe Bool)
    
    178
    +    deriving (Show)
    
    179
    +
    
    180
    +
    
    181
    +data MaybeW32 = NothingW32
    
    182
    +              | JustW32 {-# UNPACK #-} !Word32
    
    183
    +    deriving (Show)
    
    184
    +
    
    185
    +data U_MaybeW32 = U_MaybeW32 {-# UNPACK #-} !MaybeW32
    
    186
    +                             {-# UNPACK #-} !MaybeW32
    
    187
    +                             {-# UNPACK #-} !MaybeW32
    
    188
    +                             {-# UNPACK #-} !MaybeW32
    
    189
    +                             {-# UNPACK #-} !MaybeW32
    
    190
    +                             {-# UNPACK #-} !MaybeW32
    
    191
    +                             {-# UNPACK #-} !MaybeW32
    
    192
    +                             {-# UNPACK #-} !MaybeW32
    
    193
    +    deriving (Show)
    
    194
    +
    
    195
    +u_ba :: U_Bool
    
    196
    +u_ba = U_Bool minBound maxBound minBound maxBound
    
    197
    +              minBound maxBound minBound maxBound
    
    198
    +
    
    199
    +u_e1a :: U_E1
    
    200
    +u_e1a = U_E1 minBound maxBound minBound maxBound
    
    201
    +             minBound maxBound minBound maxBound
    
    202
    +
    
    203
    +u_e1b :: U_E1
    
    204
    +u_e1b = U_E1 maxBound minBound maxBound minBound
    
    205
    +             maxBound minBound maxBound minBound
    
    206
    +
    
    207
    +u_e1c :: U_E1
    
    208
    +u_e1c = U_E1 E1_1 126 127 0 1 2 3 4
    
    209
    +
    
    210
    +u_e1d :: U_E1
    
    211
    +u_e1d = U_E1 E1_254 126 127 0 1 2 3 4
    
    212
    +
    
    213
    +u_e2a :: U_E2
    
    214
    +u_e2a = U_E2 minBound maxBound minBound maxBound
    
    215
    +             minBound maxBound minBound maxBound
    
    216
    +{-
    
    217
    +u_e3a :: U_E3
    
    218
    +u_e3a = U_E3 minBound maxBound minBound maxBound
    
    219
    +             minBound maxBound minBound maxBound
    
    220
    +
    
    221
    +u_mixed :: U_Mixed
    
    222
    +u_mixed = U_Mixed maxBound minBound maxBound minBound
    
    223
    +                  maxBound minBound maxBound minBound
    
    224
    +-}
    
    225
    +
    
    226
    +u_maybe :: U_Maybe
    
    227
    +u_maybe = U_Maybe Nothing (Just False) Nothing (Just True)
    
    228
    +                  Nothing (Just False) Nothing (Just True)
    
    229
    +
    
    230
    +u_maybeW32 :: U_MaybeW32
    
    231
    +u_maybeW32 = U_MaybeW32 NothingW32 (JustW32 minBound)
    
    232
    +                        NothingW32 (JustW32 maxBound)
    
    233
    +                        NothingW32 (JustW32 minBound)
    
    234
    +                        NothingW32 (JustW32 maxBound)
    
    235
    +
    
    236
    +test :: Show a => String -> a -> IO ()
    
    237
    +test name value = do
    
    238
    +    putStrLn $ "\n### " ++ name
    
    239
    +    value' <- evaluate value
    
    240
    +    print value'
    
    241
    +    putStrLn ("size: " ++ show (closureSize $ asBox value'))
    
    242
    +
    
    243
    +main :: IO ()
    
    244
    +main = do
    
    245
    +    test "u_ba"       u_ba
    
    246
    +    test "u_e1a"      u_e1a
    
    247
    +    test "u_e1b"      u_e1b
    
    248
    +    test "u_e1c"      u_e1c
    
    249
    +    test "u_e1d"      u_e1d
    
    250
    +    test "u_e2a"      u_e2a
    
    251
    +    -- test "u_e3a"      u_e3a
    
    252
    +    -- test "u_mixed"    u_mixed
    
    253
    +    test "u_maybe"    u_maybe
    
    254
    +    test "u_maybeW32" u_maybeW32

  • testsuite/tests/unboxedsums/UbxSumUnpackedSize.stdout
    1
    +
    
    2
    +### u_ba
    
    3
    +U_Bool False True False True False True False True
    
    4
    +size: 2
    
    5
    +
    
    6
    +### u_e1a
    
    7
    +U_E1 E1_1 127 (-128) 127 (-128) 127 (-128) 127
    
    8
    +size: 2
    
    9
    +
    
    10
    +### u_e1b
    
    11
    +U_E1 E1_254 (-128) 127 (-128) 127 (-128) 127 (-128)
    
    12
    +size: 2
    
    13
    +
    
    14
    +### u_e1c
    
    15
    +U_E1 E1_1 126 127 0 1 2 3 4
    
    16
    +size: 2
    
    17
    +
    
    18
    +### u_e1d
    
    19
    +U_E1 E1_254 126 127 0 1 2 3 4
    
    20
    +size: 2
    
    21
    +
    
    22
    +### u_e2a
    
    23
    +U_E2 E2_1 127 (-128) 127 (-128) 127 (-128) 127
    
    24
    +size: 2
    
    25
    +
    
    26
    +### u_maybe
    
    27
    +U_Maybe Nothing (Just False) Nothing (Just True) Nothing (Just False) Nothing (Just True)
    
    28
    +size: 10
    
    29
    +
    
    30
    +### u_maybeW32
    
    31
    +U_MaybeW32 NothingW32 (JustW32 0) NothingW32 (JustW32 4294967295) NothingW32 (JustW32 0) NothingW32 (JustW32 4294967295)
    
    32
    +size: 9

  • testsuite/tests/unboxedsums/UbxSumUnpackedSize.stdout-ws-32
    1
    +
    
    2
    +### u_ba
    
    3
    +U_Bool False True False True False True False True
    
    4
    +size: 3
    
    5
    +
    
    6
    +### u_e1a
    
    7
    +U_E1 E1_1 127 (-128) 127 (-128) 127 (-128) 127
    
    8
    +size: 3
    
    9
    +
    
    10
    +### u_e1b
    
    11
    +U_E1 E1_254 (-128) 127 (-128) 127 (-128) 127 (-128)
    
    12
    +size: 3
    
    13
    +
    
    14
    +### u_e1c
    
    15
    +U_E1 E1_1 126 127 0 1 2 3 4
    
    16
    +size: 3
    
    17
    +
    
    18
    +### u_e1d
    
    19
    +U_E1 E1_254 126 127 0 1 2 3 4
    
    20
    +size: 3
    
    21
    +
    
    22
    +### u_e2a
    
    23
    +U_E2 E2_1 127 (-128) 127 (-128) 127 (-128) 127
    
    24
    +size: 3
    
    25
    +
    
    26
    +### u_maybe
    
    27
    +U_Maybe Nothing (Just False) Nothing (Just True) Nothing (Just False) Nothing (Just True)
    
    28
    +size: 11
    
    29
    +
    
    30
    +### u_maybeW32
    
    31
    +U_MaybeW32 NothingW32 (JustW32 0) NothingW32 (JustW32 4294967295) NothingW32 (JustW32 0) NothingW32 (JustW32 4294967295)
    
    32
    +size: 17

  • testsuite/tests/unboxedsums/all.T
    ... ... @@ -62,3 +62,5 @@ test('ManyUbxSums',
    62 62
          ['ManyUbxSums',
    
    63 63
             [('ManyUbxSums_Addr.hs','')]
    
    64 64
             , '-v0 -dstg-lint -dcmm-lint'])
    
    65
    +
    
    66
    +test('UbxSumUnpackedSize', [js_broken(22374)], compile_and_run, ['-O'])

  • testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs
    ... ... @@ -63,33 +63,33 @@ layout_tests = sequence_
    63 63
           assert_layout "layout1"
    
    64 64
             [ ubxtup [ intTy, intPrimTy ]
    
    65 65
             , ubxtup [ intPrimTy, intTy ] ]
    
    66
    -        [ WordSlot, PtrLiftedSlot, WordSlot ]
    
    66
    +        [ Word8Slot, PtrLiftedSlot, WordSlot ]
    
    67 67
     
    
    68 68
         layout2 =
    
    69 69
           assert_layout "layout2"
    
    70 70
             [ ubxtup [ intTy ]
    
    71 71
             , intTy ]
    
    72
    -        [ WordSlot, PtrLiftedSlot ]
    
    72
    +        [ Word8Slot, PtrLiftedSlot ]
    
    73 73
     
    
    74 74
         layout3 =
    
    75 75
           assert_layout "layout3"
    
    76 76
             [ ubxtup [ intTy, intPrimTy, intTy, intPrimTy ]
    
    77 77
             , ubxtup [ intPrimTy, intTy, intPrimTy, intTy ] ]
    
    78
    -        [ WordSlot, PtrLiftedSlot, PtrLiftedSlot, WordSlot, WordSlot ]
    
    78
    +        [ Word8Slot, PtrLiftedSlot, PtrLiftedSlot, WordSlot, WordSlot ]
    
    79 79
     
    
    80 80
         layout4 =
    
    81 81
           assert_layout "layout4"
    
    82 82
             [ ubxtup [ floatPrimTy, floatPrimTy ]
    
    83 83
             , ubxtup [ intPrimTy, intPrimTy ] ]
    
    84
    -        [ WordSlot, WordSlot, WordSlot, FloatSlot, FloatSlot ]
    
    84
    +        [ Word8Slot, WordSlot, WordSlot, FloatSlot, FloatSlot ]
    
    85 85
     
    
    86 86
         layout5 =
    
    87 87
           assert_layout "layout5"
    
    88 88
             [ ubxtup [ intPrimTy, intPrimTy ]
    
    89 89
             , ubxtup [ floatPrimTy, floatPrimTy ] ]
    
    90
    -        [ WordSlot, WordSlot, WordSlot, FloatSlot, FloatSlot ]
    
    90
    +        [ Word8Slot, WordSlot, WordSlot, FloatSlot, FloatSlot ]
    
    91 91
     
    
    92 92
         enum_layout =
    
    93 93
           assert_layout "enum"
    
    94 94
             (replicate 10 (ubxtup []))
    
    95
    -        [ WordSlot ]
    95
    +        [ Word8Slot ]