@@ -158,11 +158,15 @@ static Uint do_session_breakpoint(Process *c_p, ErtsCodeInfo *info, Eterm *reg,
158158 (pi0)->accumulator += (pi1)->accumulator; \
159159 } while(0)
160160
161- static void bp_hash_init (bp_trace_hash_t * hash , Uint n );
162- static void bp_hash_rehash (bp_trace_hash_t * hash , Uint n );
163- static ERTS_INLINE bp_data_trace_item_t * bp_hash_get (bp_trace_hash_t * hash , bp_data_trace_item_t * sitem );
164- static ERTS_INLINE bp_data_trace_item_t * bp_hash_put (bp_trace_hash_t * hash , bp_data_trace_item_t * sitem );
165- static void bp_hash_delete (bp_trace_hash_t * hash );
161+ static bp_trace_hash_t * bp_hash_alloc (Uint n );
162+ static bp_trace_hash_t * bp_hash_rehash (bp_trace_hash_t * hash , Uint n );
163+ static ERTS_INLINE bp_data_trace_bucket_t * bp_hash_get (bp_trace_hash_t * hash ,
164+ const bp_data_trace_bucket_t * sitem );
165+ static ERTS_INLINE void bp_hash_put (bp_trace_hash_t * * ,
166+ const bp_data_trace_bucket_t * sitem );
167+ static void bp_hash_accum (bp_trace_hash_t * * hash_p ,
168+ const bp_data_trace_bucket_t * sitem );
169+ static void bp_hash_dealloc (bp_trace_hash_t * hash );
166170
167171/* *************************************************************************
168172** External interfaces
@@ -1225,10 +1229,9 @@ erts_trace_call_acc(Process* c_p,
12251229 const ErtsCodeInfo * info , BpDataAccumulator accum ,
12261230 int psd_ix , BpDataCallTrace * bdt )
12271231{
1228- bp_data_trace_item_t sitem , * item = NULL ;
1229- bp_trace_hash_t * h = NULL ;
1232+ bp_data_trace_bucket_t sitem ;
12301233 BpDataCallTrace * pbdt = NULL ;
1231- Uint32 six = acquire_bp_sched_ix (c_p );
1234+ const Uint32 six = acquire_bp_sched_ix (c_p );
12321235 const ErtsCodeInfo * prev_info ;
12331236
12341237 ASSERT (c_p );
@@ -1256,17 +1259,7 @@ erts_trace_call_acc(Process* c_p,
12561259
12571260 /* if null then the breakpoint was removed */
12581261 if (pbdt ) {
1259- h = & (pbdt -> hash [six ]);
1260-
1261- ASSERT (h );
1262- ASSERT (h -> item );
1263-
1264- item = bp_hash_get (h , & sitem );
1265- if (!item ) {
1266- item = bp_hash_put (h , & sitem );
1267- } else {
1268- BP_ACCUMULATE (item , & sitem );
1269- }
1262+ bp_hash_accum (& (pbdt -> threads [six ]), & sitem );
12701263 }
12711264 }
12721265 /*else caller is not call_time traced */
@@ -1277,18 +1270,7 @@ erts_trace_call_acc(Process* c_p,
12771270 sitem .accumulator = 0 ;
12781271
12791272 /* this breakpoint */
1280- ASSERT (bdt );
1281- h = & (bdt -> hash [six ]);
1282-
1283- ASSERT (h );
1284- ASSERT (h -> item );
1285-
1286- item = bp_hash_get (h , & sitem );
1287- if (!item ) {
1288- item = bp_hash_put (h , & sitem );
1289- } else {
1290- BP_ACCUMULATE (item , & sitem );
1291- }
1273+ bp_hash_accum (& (bdt -> threads [six ]), & sitem );
12921274
12931275 prev_info = pbt -> ci ;
12941276 pbt -> ci = info ;
@@ -1303,27 +1285,15 @@ static void
13031285call_trace_add (Process * p , BpDataCallTrace * pbdt , Uint32 six ,
13041286 BpDataAccumulator accum , BpDataAccumulator prev_accum )
13051287{
1306- bp_data_trace_item_t sitem , * item = NULL ;
1307- bp_trace_hash_t * h = NULL ;
1288+ bp_data_trace_bucket_t sitem ;
13081289
13091290 sitem .accumulator = accum - prev_accum ;
13101291 sitem .pid = p -> common .id ;
13111292 sitem .count = 0 ;
13121293
13131294 /* beware, the trace_pattern might have been removed */
13141295 if (pbdt ) {
1315-
1316- h = & (pbdt -> hash [six ]);
1317-
1318- ASSERT (h );
1319- ASSERT (h -> item );
1320-
1321- item = bp_hash_get (h , & sitem );
1322- if (!item ) {
1323- item = bp_hash_put (h , & sitem );
1324- } else {
1325- BP_ACCUMULATE (item , & sitem );
1326- }
1296+ bp_hash_accum (& (pbdt -> threads [six ]), & sitem );
13271297 }
13281298}
13291299
@@ -1446,8 +1416,8 @@ int erts_is_call_break(Process *p, ErtsTraceSession *session, int is_time,
14461416 const ErtsCodeInfo * ci , Eterm * retval )
14471417{
14481418 Uint i , ix ;
1449- bp_trace_hash_t hash ;
1450- bp_data_trace_item_t * item = NULL ;
1419+ bp_trace_hash_t * tot_hash ;
1420+ bp_data_trace_bucket_t * item = NULL ;
14511421 BpDataCallTrace * bdt = is_time ? get_time_break (session , ci )
14521422 : get_memory_break (session , ci );
14531423
@@ -1456,36 +1426,30 @@ int erts_is_call_break(Process *p, ErtsTraceSession *session, int is_time,
14561426
14571427 ASSERT (retval );
14581428 /* collect all hashes to one hash */
1459- bp_hash_init (& hash , 64 );
1460- /* foreach threadspecific hash */
1461- for (i = 0 ; i < bdt -> n ; i ++ ) {
1462- bp_data_trace_item_t * sitem ;
1429+ tot_hash = bp_hash_alloc (64 );
14631430
1431+ /* foreach threadspecific hash */
1432+ for (i = 0 ; i < bdt -> nthreads ; i ++ ) {
14641433 /* foreach hash bucket not NIL*/
1465- for (ix = 0 ; ix < bdt -> hash [i ]. n ; ix ++ ) {
1466- item = & (bdt -> hash [i ]. item [ix ]);
1434+ for (ix = 0 ; ix < bdt -> threads [i ]-> n ; ix ++ ) {
1435+ item = & (bdt -> threads [i ]-> buckets [ix ]);
14671436 if (item -> pid != NIL ) {
1468- sitem = bp_hash_get (& hash , item );
1469- if (sitem ) {
1470- BP_ACCUMULATE (sitem , item );
1471- } else {
1472- bp_hash_put (& hash , item );
1473- }
1437+ bp_hash_accum (& tot_hash , item );
14741438 }
14751439 }
14761440 }
14771441 /* *retval should be NIL or term from previous bif in export entry */
14781442
1479- if (hash . used > 0 ) {
1443+ if (tot_hash -> used > 0 ) {
14801444 Uint size ;
14811445 Eterm * hp , * hp_end , t ;
14821446
1483- size = hash . used * (is_time ? (2 + 5 ) : (2 + 4 + ERTS_MAX_SINT64_HEAP_SIZE ));
1447+ size = tot_hash -> used * (is_time ? (2 + 5 ) : (2 + 4 + ERTS_MAX_SINT64_HEAP_SIZE ));
14841448 hp = HAlloc (p , size );
14851449 hp_end = hp + size ;
14861450
1487- for (ix = 0 ; ix < hash . n ; ix ++ ) {
1488- item = & (hash . item [ix ]);
1451+ for (ix = 0 ; ix < tot_hash -> n ; ix ++ ) {
1452+ item = & (tot_hash -> buckets [ix ]);
14891453 if (item -> pid != NIL ) {
14901454 if (is_time ) {
14911455 BpDataAccumulator sec , usec ;
@@ -1511,7 +1475,7 @@ int erts_is_call_break(Process *p, ErtsTraceSession *session, int is_time,
15111475 ASSERT (hp <= hp_end );
15121476 HRelease (p , hp_end , hp );
15131477 }
1514- bp_hash_delete ( & hash );
1478+ bp_hash_dealloc ( tot_hash );
15151479 return 1 ;
15161480}
15171481
@@ -1668,109 +1632,100 @@ erts_find_local_func(const ErtsCodeMFA *mfa) {
16681632 return NULL ;
16691633}
16701634
1671- static void bp_hash_init (bp_trace_hash_t * hash , Uint n ) {
1672- Uint size = sizeof (bp_data_trace_item_t )* n ;
1673- Uint i ;
1635+ static bp_trace_hash_t * bp_hash_alloc (Uint n )
1636+ {
1637+ Uint size = sizeof (bp_trace_hash_t ) + sizeof (bp_data_trace_bucket_t [n ]);
1638+ bp_trace_hash_t * hash = (bp_trace_hash_t * ) Alloc (size );
16741639
1640+ sys_memzero (hash , size );
16751641 hash -> n = n ;
16761642 hash -> used = 0 ;
16771643
1678- hash -> item = (bp_data_trace_item_t * )Alloc (size );
1679- sys_memzero (hash -> item , size );
1680-
1681- for (i = 0 ; i < n ; ++ i ) {
1682- hash -> item [i ].pid = NIL ;
1644+ for (Uint i = 0 ; i < n ; ++ i ) {
1645+ hash -> buckets [i ].pid = NIL ;
16831646 }
1647+ return hash ;
16841648}
16851649
1686- static void bp_hash_rehash (bp_trace_hash_t * hash , Uint n ) {
1687- bp_data_trace_item_t * item = NULL ;
1688- Uint size = sizeof (bp_data_trace_item_t )* n ;
1689- Uint ix ;
1690- Uint hval ;
1650+ static bp_trace_hash_t * bp_hash_rehash (bp_trace_hash_t * hash , Uint n )
1651+ {
1652+ bp_trace_hash_t * ERTS_RESTRICT dst ;
16911653
16921654 ASSERT (n > 0 );
1693-
1694- item = (bp_data_trace_item_t * )Alloc (size );
1695- sys_memzero (item , size );
1696-
1697- for ( ix = 0 ; ix < n ; ++ ix ) {
1698- item [ix ].pid = NIL ;
1699- }
1700-
1655+ dst = bp_hash_alloc (n );
17011656
17021657 /* rehash, old hash -> new hash */
17031658
1704- for ( ix = 0 ; ix < hash -> n ; ix ++ ) {
1705- if (hash -> item [ix ].pid != NIL ) {
1659+ for (Uint ix = 0 ; ix < hash -> n ; ix ++ ) {
1660+ if (hash -> buckets [ix ].pid != NIL ) {
1661+ Uint hval = ((hash -> buckets [ix ].pid ) >> 4 ) % n ; /* new n */
17061662
1707- hval = ((hash -> item [ix ].pid ) >> 4 ) % n ; /* new n */
1708-
1709- while (item [hval ].pid != NIL ) {
1663+ while (dst -> buckets [hval ].pid != NIL ) {
17101664 hval = (hval + 1 ) % n ;
17111665 }
1712- item [hval ].pid = hash -> item [ix ].pid ;
1713- item [hval ].count = hash -> item [ix ].count ;
1714- item [hval ].accumulator = hash -> item [ix ].accumulator ;
1666+ dst -> buckets [hval ] = hash -> buckets [ix ];
17151667 }
17161668 }
1717-
1718- Free (hash -> item );
1719- hash -> n = n ;
1720- hash -> item = item ;
1669+ dst -> used = hash -> used ;
1670+ Free (hash );
1671+ return dst ;
17211672}
1722- static ERTS_INLINE bp_data_trace_item_t * bp_hash_get (bp_trace_hash_t * hash , bp_data_trace_item_t * sitem ) {
1673+ static ERTS_INLINE
1674+ bp_data_trace_bucket_t * bp_hash_get (bp_trace_hash_t * hash ,
1675+ const bp_data_trace_bucket_t * sitem ) {
17231676 Eterm pid = sitem -> pid ;
17241677 Uint hval = (pid >> 4 ) % hash -> n ;
1725- bp_data_trace_item_t * item = NULL ;
1726-
1727- item = hash -> item ;
17281678
1729- while (item [hval ].pid != pid ) {
1730- if (item [hval ].pid == NIL ) return NULL ;
1679+ while (hash -> buckets [hval ].pid != pid ) {
1680+ if (hash -> buckets [hval ].pid == NIL ) return NULL ;
17311681 hval = (hval + 1 ) % hash -> n ;
17321682 }
17331683
1734- return & (item [hval ]);
1684+ return & (hash -> buckets [hval ]);
17351685}
17361686
1737- static ERTS_INLINE bp_data_trace_item_t * bp_hash_put (bp_trace_hash_t * hash , bp_data_trace_item_t * sitem ) {
1687+ static ERTS_INLINE void bp_hash_put (bp_trace_hash_t * * hash_p ,
1688+ const bp_data_trace_bucket_t * sitem )
1689+ {
1690+ bp_trace_hash_t * hash = * hash_p ;
17381691 Uint hval ;
17391692 float r = 0.0 ;
1740- bp_data_trace_item_t * item ;
17411693
17421694 /* make sure that the hash is not saturated */
17431695 /* if saturated, rehash it */
17441696
17451697 r = hash -> used / (float ) hash -> n ;
17461698
17471699 if (r > 0.7f ) {
1748- bp_hash_rehash (hash , hash -> n * 2 );
1700+ hash = bp_hash_rehash (hash , hash -> n * 2 );
1701+ * hash_p = hash ;
17491702 }
17501703 /* Do hval after rehash */
17511704 hval = (sitem -> pid >> 4 ) % hash -> n ;
17521705
1753- /* find free slot */
1754- item = hash -> item ;
1755-
1756- while (item [hval ].pid != NIL ) {
1706+ while (hash -> buckets [hval ].pid != NIL ) {
17571707 hval = (hval + 1 ) % hash -> n ;
17581708 }
1759- item = & (hash -> item [hval ]);
17601709
1761- item -> pid = sitem -> pid ;
1762- item -> accumulator = sitem -> accumulator ;
1763- item -> count = sitem -> count ;
1710+ hash -> buckets [hval ] = * sitem ;
17641711 hash -> used ++ ;
1712+ }
1713+
1714+ static void bp_hash_accum (bp_trace_hash_t * * hash_p ,
1715+ const bp_data_trace_bucket_t * sitem )
1716+ {
1717+ bp_data_trace_bucket_t * item ;
17651718
1766- return item ;
1719+ item = bp_hash_get (* hash_p , sitem );
1720+ if (!item ) {
1721+ bp_hash_put (hash_p , sitem );
1722+ } else {
1723+ BP_ACCUMULATE (item , sitem );
1724+ }
17671725}
17681726
1769- static void bp_hash_delete (bp_trace_hash_t * hash ) {
1770- hash -> n = 0 ;
1771- hash -> used = 0 ;
1772- Free (hash -> item );
1773- hash -> item = NULL ;
1727+ static void bp_hash_dealloc (bp_trace_hash_t * hash ) {
1728+ Free (hash );
17741729}
17751730
17761731static void bp_hash_reset (BpDataCallTrace * * bdt_p ) {
@@ -1780,8 +1735,7 @@ static void bp_hash_reset(BpDataCallTrace** bdt_p) {
17801735
17811736void erts_schedule_time_break (Process * p , Uint schedule ) {
17821737 process_breakpoint_trace_t * pbt = NULL ;
1783- bp_data_trace_item_t sitem , * item = NULL ;
1784- bp_trace_hash_t * h = NULL ;
1738+ bp_data_trace_bucket_t sitem ;
17851739 BpDataCallTrace * pbdt = NULL ;
17861740 Uint32 six = acquire_bp_sched_ix (p );
17871741
@@ -1804,17 +1758,7 @@ void erts_schedule_time_break(Process *p, Uint schedule) {
18041758 sitem .pid = p -> common .id ;
18051759 sitem .count = 0 ;
18061760
1807- h = & (pbdt -> hash [six ]);
1808-
1809- ASSERT (h );
1810- ASSERT (h -> item );
1811-
1812- item = bp_hash_get (h , & sitem );
1813- if (!item ) {
1814- item = bp_hash_put (h , & sitem );
1815- } else {
1816- BP_ACCUMULATE (item , & sitem );
1817- }
1761+ bp_hash_accum (& (pbdt -> threads [six ]), & sitem );
18181762 }
18191763 }
18201764 }
@@ -2159,12 +2103,12 @@ bp_count_unref(BpCount* bcp)
21592103static BpDataCallTrace * bp_calltrace_alloc (void )
21602104{
21612105 const Uint n = erts_no_schedulers + 1 ;
2162- BpDataCallTrace * bdt = Alloc (offsetof (BpDataCallTrace , hash ) +
2163- sizeof (bp_trace_hash_t ) * n );
2164- bdt -> n = n ;
2106+ BpDataCallTrace * bdt = Alloc (sizeof (BpDataCallTrace ) +
2107+ sizeof (bp_trace_hash_t [ n ]) );
2108+ bdt -> nthreads = n ;
21652109 erts_refc_init (& bdt -> refc , 1 );
21662110 for (Uint i = 0 ; i < n ; i ++ ) {
2167- bp_hash_init ( & ( bdt -> hash [i ]), 32 );
2111+ bdt -> threads [i ] = bp_hash_alloc ( 32 );
21682112 }
21692113 return bdt ;
21702114}
@@ -2173,10 +2117,8 @@ static void
21732117bp_calltrace_unref (BpDataCallTrace * bdt )
21742118{
21752119 if (erts_refc_dectest (& bdt -> refc , 0 ) <= 0 ) {
2176- Uint i = 0 ;
2177-
2178- for (i = 0 ; i < bdt -> n ; ++ i ) {
2179- bp_hash_delete (& (bdt -> hash [i ]));
2120+ for (Uint i = 0 ; i < bdt -> nthreads ; ++ i ) {
2121+ bp_hash_dealloc (bdt -> threads [i ]);
21802122 }
21812123 Free (bdt );
21822124 }
0 commit comments