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

Commits:

5 changed files:

Changes:

  • compiler/GHC/Runtime/Heap/Inspect.hs
    ... ... @@ -74,12 +74,12 @@ import GHC.Utils.Outputable as Ppr
    74 74
     import GHC.Utils.Panic
    
    75 75
     import GHC.Char
    
    76 76
     import GHC.Exts.Heap
    
    77
    -import GHC.Runtime.Heap.Layout ( roundUpTo )
    
    77
    +import GHC.Runtime.Heap.Layout (ByteOff)
    
    78 78
     import GHC.IO (throwIO)
    
    79 79
     
    
    80 80
     import Control.Monad
    
    81 81
     import Data.Maybe
    
    82
    -import Data.List ((\\))
    
    82
    +import Data.List ((\\), mapAccumL)
    
    83 83
     import Data.List.NonEmpty (NonEmpty (..))
    
    84 84
     import qualified Data.List.NonEmpty as NE
    
    85 85
     import GHC.Exts
    
    ... ... @@ -89,6 +89,10 @@ import Foreign hiding (shiftL, shiftR)
    89 89
     import System.IO.Unsafe
    
    90 90
     import GHC.InfoProv
    
    91 91
     
    
    92
    +import GHC.StgToCmm.Closure ( NonVoid(NonVoid))
    
    93
    +import GHC.StgToCmm.Layout (mkVirtHeapOffsets, ClosureHeader(..))
    
    94
    +import Data.Array (Array, (!), array)
    
    95
    +
    
    92 96
     ---------------------------------------------
    
    93 97
     -- * A representation of semi evaluated Terms
    
    94 98
     ---------------------------------------------
    
    ... ... @@ -922,63 +926,80 @@ extractSubTerms :: (Type -> ForeignHValue -> TcM Term)
    922 926
                     -> [Word]          -- ^ data arguments
    
    923 927
                     -> [Type]
    
    924 928
                     -> TcM [Term]
    
    925
    -extractSubTerms recurse ptr_args data_args = liftM thdOf3 . go 0 0
    
    929
    +extractSubTerms recurse ptr_args data_args tys = do
    
    930
    +  dflags <- getDynFlags
    
    931
    +  let profile = targetProfile dflags
    
    932
    +      (n_primreps, r) = mapAccumL collectReps 0 tys
    
    933
    +      (rep_tys, make_term) = unzip r
    
    934
    +      (_tot_words, ptr_words, nv_rep_offsets) =
    
    935
    +          mkVirtHeapOffsets profile NoHeader (map NonVoid $ concat rep_tys)
    
    936
    +      rep_offsets = map (\(NonVoid x, off) -> (x, off)) nv_rep_offsets
    
    937
    +      -- index maps the Int index of each PrimRep to its ByteOff
    
    938
    +      index :: Array Int ByteOff
    
    939
    +      index = array (0, n_primreps-1) rep_offsets
    
    940
    +  mapM (\m -> m index ptr_words) make_term
    
    926 941
       where
    
    927
    -    go ptr_i arr_i [] = return (ptr_i, arr_i, [])
    
    928
    -    go ptr_i arr_i (ty:tys)
    
    942
    +
    
    943
    +    {- Collect all PrimReps from the Type, indexing each with an Int.
    
    944
    +       Also returns a function to construct the Term once the heap offset of
    
    945
    +       each indexed PrimRep is known.
    
    946
    +    -}
    
    947
    +    collectReps :: Int                  -- first index to use
    
    948
    +                -> Type
    
    949
    +                -> ( Int                -- next available index
    
    950
    +                   , ( [(PrimRep, Int)] -- indexed PrimReps
    
    951
    +                     , Array Int ByteOff -> Int -> TcM Term
    
    952
    +                     ))
    
    953
    +    collectReps n ty
    
    929 954
           | Just (tc, elem_tys) <- tcSplitTyConApp_maybe ty
    
    930 955
           , isUnboxedTupleTyCon tc
    
    931
    -                -- See Note [Unboxed tuple RuntimeRep vars] in GHC.Core.TyCon
    
    932
    -      = do (ptr_i, arr_i, terms0) <-
    
    933
    -               go ptr_i arr_i (dropRuntimeRepArgs elem_tys)
    
    934
    -           (ptr_i, arr_i, terms1) <- go ptr_i arr_i tys
    
    935
    -           return (ptr_i, arr_i, unboxedTupleTerm ty terms0 : terms1)
    
    936
    -      | otherwise
    
    937
    -      = case typePrimRep ty of
    
    938
    -          [rep_ty] -> do
    
    939
    -            (ptr_i, arr_i, term0)  <- go_rep ptr_i arr_i ty rep_ty
    
    940
    -            (ptr_i, arr_i, terms1) <- go ptr_i arr_i tys
    
    941
    -            return (ptr_i, arr_i, term0 : terms1)
    
    942
    -          rep_tys -> do
    
    943
    -           (ptr_i, arr_i, terms0) <- go_unary_types ptr_i arr_i rep_tys
    
    944
    -           (ptr_i, arr_i, terms1) <- go ptr_i arr_i tys
    
    945
    -           return (ptr_i, arr_i, unboxedTupleTerm ty terms0 : terms1)
    
    946
    -
    
    947
    -    go_unary_types ptr_i arr_i [] = return (ptr_i, arr_i, [])
    
    948
    -    go_unary_types ptr_i arr_i (rep_ty:rep_tys) = do
    
    949
    -      tv <- newVar liftedTypeKind
    
    950
    -      (ptr_i, arr_i, term0)  <- go_rep ptr_i arr_i tv rep_ty
    
    951
    -      (ptr_i, arr_i, terms1) <- go_unary_types ptr_i arr_i rep_tys
    
    952
    -      return (ptr_i, arr_i, term0 : terms1)
    
    953
    -
    
    954
    -    go_rep ptr_i arr_i ty rep
    
    956
    +      -- See Note [Unboxed tuple RuntimeRep vars] in GHC.Core.TyCon
    
    957
    +      = let (n', sub) = mapAccumL collectReps n (dropRuntimeRepArgs elem_tys)
    
    958
    +            (reps, mk_terms) = unzip sub
    
    959
    +        in (n', (concat reps,
    
    960
    +                   \idx ptr_words -> unboxedTupleTerm ty <$>
    
    961
    +                        mapM (\mk -> mk idx ptr_words) mk_terms))
    
    962
    +      | otherwise =
    
    963
    +          case typePrimRep ty of
    
    964
    +              [rep] -> (n + 1
    
    965
    +                       ,([(rep, n)]
    
    966
    +                        ,\idx ptr_words -> mkTerm ptr_words ty rep (idx ! n)))
    
    967
    +              reps  -> let n_reps = length reps
    
    968
    +                           indexed_reps = zip reps [n..]
    
    969
    +                           mk idx ptr_words =
    
    970
    +                               unboxedTupleTerm ty <$>
    
    971
    +                                 mapM (\(rep, i) -> mkTerm ptr_words ty rep (idx ! i))
    
    972
    +                                      indexed_reps
    
    973
    +                       in (n + n_reps, (indexed_reps, mk))
    
    974
    +
    
    975
    +
    
    976
    +
    
    977
    +    mkTerm :: Int -> Type -> PrimRep -> ByteOff -> TcM Term
    
    978
    +    mkTerm ptr_words ty rep byte_offset
    
    955 979
           | isGcPtrRep rep = do
    
    956
    -          t <- recurse ty $ ptr_args !! ptr_i
    
    957
    -          return (ptr_i + 1, arr_i, t)
    
    980
    +          platform <- getPlatform
    
    981
    +          let word_size = platformWordSizeInBytes platform
    
    982
    +              (word_offset, r) = byte_offset `quotRem` word_size
    
    983
    +          massert (word_offset < length ptr_args)
    
    984
    +          massert (r == 0)
    
    985
    +          r <- recurse ty (ptr_args !! (byte_offset `quot` word_size))
    
    986
    +          pure r
    
    958 987
           | otherwise = do
    
    959
    -          -- This is a bit involved since we allow packing multiple fields
    
    960
    -          -- within a single word. See also
    
    961
    -          -- GHC.StgToCmm.Layout.mkVirtHeapOffsetsWithPadding
    
    962 988
               platform <- getPlatform
    
    963 989
               let word_size = platformWordSizeInBytes platform
    
    964
    -              endian = platformByteOrder platform
    
    965
    -              size_b = primRepSizeB platform rep
    
    966
    -              -- Align the start offset (eg, 2-byte value should be 2-byte
    
    967
    -              -- aligned). But not more than to a word. The offset calculation
    
    968
    -              -- should be the same with the offset calculation in
    
    969
    -              -- GHC.StgToCmm.Layout.mkVirtHeapOffsetsWithPadding.
    
    970
    -              !aligned_idx = roundUpTo arr_i (min word_size size_b)
    
    971
    -              !new_arr_i = aligned_idx + size_b
    
    972
    -              ws | size_b < word_size =
    
    973
    -                     [index size_b aligned_idx word_size endian]
    
    974
    -                 | otherwise =
    
    975
    -                     let (q, r) = size_b `quotRem` word_size
    
    976
    -                     in assert (r == 0 )
    
    977
    -                        [ data_args !! i
    
    978
    -                        | o <- [0.. q - 1]
    
    979
    -                        , let i = (aligned_idx `quot` word_size) + o
    
    980
    -                        ]
    
    981
    -          return (ptr_i, new_arr_i, Prim ty ws)
    
    990
    +              endian    = platformByteOrder platform
    
    991
    +              size_b    = primRepSizeB platform rep
    
    992
    +              ws        | size_b < word_size
    
    993
    +                        = [index size_b (byte_offset - word_size * ptr_words) word_size endian]
    
    994
    +                        | otherwise
    
    995
    +                        =
    
    996
    +                            let (q, r) = size_b `quotRem` word_size
    
    997
    +                            in assert (r == 0 )
    
    998
    +                                [ data_args !! i
    
    999
    +                                | o <- [0.. q - 1]
    
    1000
    +                                , let i = (byte_offset `quot` word_size) - ptr_words + o
    
    1001
    +                                ]
    
    1002
    +          return (Prim ty ws)
    
    982 1003
     
    
    983 1004
         unboxedTupleTerm ty terms
    
    984 1005
           = Term ty (Right (tupleDataCon Unboxed (length terms)))
    

  • compiler/GHC/StgToCmm/Layout.hs
    ... ... @@ -56,7 +56,8 @@ import GHC.Platform.Profile
    56 56
     import GHC.Unit
    
    57 57
     
    
    58 58
     import GHC.Utils.Misc
    
    59
    -import Data.List (mapAccumL, partition)
    
    59
    +import Data.List (mapAccumL, partition, sortBy)
    
    60
    +import Data.Ord (comparing)
    
    60 61
     import GHC.Utils.Outputable
    
    61 62
     import GHC.Utils.Panic
    
    62 63
     import GHC.Utils.Constants (debugIsOn)
    
    ... ... @@ -459,10 +460,19 @@ mkVirtHeapOffsetsWithPadding profile header things =
    459 460
           ThunkHeader -> thunkHdrSize profile
    
    460 461
         hdr_bytes = wordsToBytes platform hdr_words
    
    461 462
     
    
    462
    -    (ptrs, non_ptrs) = partition (isGcPtrRep . fst . fromNonVoid) things
    
    463
    +    (ptrs, unsorted_non_ptrs) = partition (isGcPtrRep . fst . fromNonVoid) things
    
    464
    +
    
    465
    +    -- Sort the non-pointer fields by their size, starting with the largest
    
    466
    +    -- size, so that we can pack them more efficiently.
    
    467
    +
    
    468
    +    cmp_sizes (NonVoid (rep1, _)) (NonVoid (rep2, _)) =
    
    469
    +        comparing (primRepSizeB platform) rep2 rep1
    
    470
    +
    
    471
    +    non_ptrs = sortBy cmp_sizes unsorted_non_ptrs
    
    463 472
     
    
    464 473
         (bytes_of_ptrs, ptrs_w_offsets) =
    
    465 474
            mapAccumL computeOffset 0 ptrs
    
    475
    +
    
    466 476
         (tot_bytes, non_ptrs_w_offsets) =
    
    467 477
            mapAccumL computeOffset bytes_of_ptrs non_ptrs
    
    468 478
     
    

  • testsuite/tests/codeGen/should_run/T13825-unit.hs
    ... ... @@ -25,8 +25,8 @@ tests :: Ghc ()
    25 25
     tests = do
    
    26 26
           (_, _, off) <- runTest [("a", FloatRep), ("b", DoubleRep)]
    
    27 27
           assert_32_64 (map fmt off)
    
    28
    -          ["F(a,4)", "F(b,8)"]
    
    29
    -          ["F(a,8)", "P(4,12)", "F(b,16)"]
    
    28
    +          ["F(b,4)", "F(a,12)"]
    
    29
    +          ["F(b,8)", "F(a,16)", "P(4,20)"]
    
    30 30
     
    
    31 31
           (_, _, off) <- runTest [("a", FloatRep), ("b", FloatRep)]
    
    32 32
           assert_32_64 (map fmt off)
    
    ... ... @@ -40,8 +40,8 @@ tests = do
    40 40
     
    
    41 41
           (_, _, off) <- runTest [("a", FloatRep), ("b", FloatRep), ("c", Int64Rep)]
    
    42 42
           assert_32_64 (map fmt off)
    
    43
    -          ["F(a,4)", "F(b,8)", "F(c,12)"]
    
    44
    -          ["F(a,8)", "F(b,12)", "F(c,16)"]
    
    43
    +          ["F(c,4)", "F(a,12)", "F(b,16)"]
    
    44
    +          ["F(c,8)", "F(a,16)", "F(b,20)"]
    
    45 45
     
    
    46 46
           (_, _, off) <- runTest [("a", Int64Rep), ("b", FloatRep), ("c", FloatRep)]
    
    47 47
           assert_32_64 (map fmt off)
    
    ... ... @@ -50,8 +50,8 @@ tests = do
    50 50
     
    
    51 51
           (_, _, off) <- runTest [("a", Int64Rep), ("b", FloatRep), ("c", Int64Rep)]
    
    52 52
           assert_32_64 (map fmt off)
    
    53
    -          ["F(a,4)", "F(b,12)", "F(c,16)"]
    
    54
    -          ["F(a,8)", "F(b,16)", "P(4,20)", "F(c,24)"]
    
    53
    +          ["F(a,4)", "F(c,12)", "F(b,20)"]
    
    54
    +          ["F(a,8)", "F(c,16)", "F(b,24)", "P(4,28)"]
    
    55 55
     
    
    56 56
     
    
    57 57
     assert_32_64 :: (Eq a, Show a) => a -> a -> a -> Ghc ()
    

  • testsuite/tests/unboxedsums/UbxSumUnpackedSize.stdout
    ... ... @@ -29,4 +29,4 @@ size: 10
    29 29
     
    
    30 30
     ### u_maybeW32
    
    31 31
     U_MaybeW32 NothingW32 (JustW32 0) NothingW32 (JustW32 4294967295) NothingW32 (JustW32 0) NothingW32 (JustW32 4294967295)
    
    32
    -size: 9
    32
    +size: 6

  • testsuite/tests/unboxedsums/UbxSumUnpackedSize.stdout-ws-32
    ... ... @@ -29,4 +29,4 @@ size: 11
    29 29
     
    
    30 30
     ### u_maybeW32
    
    31 31
     U_MaybeW32 NothingW32 (JustW32 0) NothingW32 (JustW32 4294967295) NothingW32 (JustW32 0) NothingW32 (JustW32 4294967295)
    
    32
    -size: 17
    32
    +size: 11