Skip to content

Commit 47d6fd3

Browse files
committed
Make all steps ofterm_to_binary work in chunks and yield
Rewrite and extend of Happi's initial work Extra_root to process structure to enable GC of state - Changed the process structure to point to a separate struct, the struct also contains a destructor function to allow for proper cleanup. Rewrote encode_size_struct and enc_term to have internal versions with reduction counters which will result in interrupt for later restart when the counter reaches zero - removed the EWA_STACK from Happis version and directly save the ESTACK's and WSTACK's in the above mentioned struct (or array thereof) that are pointed out from the process structure. The destructor will take care of the deallocation in case of process death. Added ESTACK and WSTACK macros to save and restore stack and to change allocator, which makes the previously mentioned stack-save work. Rewrote enc_term to not store pointers on the stack, and use one WSTACK for commands etc and another ESTACK for Eterms - Slightly different than Happis version to make halfword code simpler. Rewrote encode_size_struct2 so that it does not store pointers on the stack, also switched to ESTACK instead of WSTACK, this also handles halfword correctly. Added interfaces for chunkwise compression, that are used from term_to_binary/2 when the compressed option is given.
1 parent 6d366f0 commit 47d6fd3

12 files changed

+824
-458
lines changed

erts/emulator/beam/atom.names

+1-2
Original file line numberDiff line numberDiff line change
@@ -197,7 +197,6 @@ atom elib_malloc
197197
atom emulator
198198
atom enable_trace
199199
atom enabled
200-
atom enc_term_cont
201200
atom endian
202201
atom env
203202
atom eof
@@ -531,7 +530,7 @@ atom system_version
531530
atom system_architecture
532531
atom SYSTEM='SYSTEM'
533532
atom table
534-
atom term_to_binary_of_size
533+
atom term_to_binary_trap
535534
atom this
536535
atom thread_pool_size
537536
atom threads

erts/emulator/beam/dist.c

+2-2
Original file line numberDiff line numberDiff line change
@@ -1740,10 +1740,10 @@ dsig_send(ErtsDSigData *dsdp, Eterm ctl, Eterm msg, int force_busy)
17401740
/* Encode internal version of dist header */
17411741
obuf->extp = erts_encode_ext_dist_header_setup(obuf->ext_endp, acmp);
17421742
/* Encode control message */
1743-
erts_encode_dist_ext(c_p, ctl, &obuf->ext_endp, flags, acmp);
1743+
erts_encode_dist_ext(ctl, &obuf->ext_endp, flags, acmp);
17441744
if (is_value(msg)) {
17451745
/* Encode message */
1746-
erts_encode_dist_ext(c_p, msg, &obuf->ext_endp, flags, acmp);
1746+
erts_encode_dist_ext(msg, &obuf->ext_endp, flags, acmp);
17471747
}
17481748

17491749
ASSERT(obuf->extp < obuf->ext_endp);

erts/emulator/beam/erl_alloc.types

+1
Original file line numberDiff line numberDiff line change
@@ -150,6 +150,7 @@ type LINK_LH STANDARD PROCESSES link_lh
150150
type SUSPEND_MON STANDARD PROCESSES suspend_monitor
151151
type PEND_SUSPEND SHORT_LIVED PROCESSES pending_suspend
152152
type PROC_LIST SHORT_LIVED PROCESSES proc_list
153+
type EXTRA_ROOT SHORT_LIVED PROCESSES extra_root
153154
type FUN_ENTRY LONG_LIVED CODE fun_entry
154155
type ATOM_TXT LONG_LIVED ATOM atom_text
155156
type BEAM_REGISTER EHEAP PROCESSES beam_register

erts/emulator/beam/erl_gc.c

+11-6
Original file line numberDiff line numberDiff line change
@@ -1964,15 +1964,20 @@ setup_rootset(Process *p, Eterm *objv, int nobj, Rootset *rootset)
19641964
++n;
19651965
}
19661966

1967-
// Check if a suspended bif has live working data.
1968-
// How do we know n is small enough to fit in roots[32?]?
1967+
/*
1968+
* A trapping BIF can add to rootset by setting the extra_root
1969+
* in the process_structure.
1970+
*/
19691971
if (p->extra_root != NULL) {
1970-
printf("GC with extra_root 0x%xl\n", p->extra_root);
1971-
roots[n].v = p->extra_root;
1972-
roots[n].sz = p->extra_root_sz;
1973-
++n;
1972+
#ifdef HARDDEBUG
1973+
erts_fprintf(stderr,"GC with extra root 0x%xl\n", p->extra_root->objv);
1974+
#endif
1975+
roots[n].v = p->extra_root->objv;
1976+
roots[n].sz = p->extra_root->sz;
1977+
++n;
19741978
}
19751979

1980+
19761981
ASSERT((is_nil(p->seq_trace_token) ||
19771982
is_tuple(follow_moved(p->seq_trace_token)) ||
19781983
is_atom(p->seq_trace_token)));

erts/emulator/beam/erl_process.c

+6-3
Original file line numberDiff line numberDiff line change
@@ -7512,10 +7512,7 @@ erl_create_process(Process* parent, /* Parent of process (default group leader).
75127512
p->htop = p->heap;
75137513
p->heap_sz = sz;
75147514
p->catches = 0;
7515-
75167515
p->extra_root = NULL;
7517-
p->extra_root_sz = 0;
7518-
p->extra_root_allocator = 0;
75197516

75207517
p->bin_vheap_sz = p->min_vheap_size;
75217518
p->bin_old_vheap_sz = p->min_vheap_size;
@@ -8948,6 +8945,12 @@ erts_continue_exit_process(Process *p)
89488945
if (pbt)
89498946
erts_free(ERTS_ALC_T_BPD, (void *) pbt);
89508947

8948+
if (p->extra_root != NULL) {
8949+
(p->extra_root->cleanup)(p->extra_root); /* Should deallocate
8950+
whole structure */
8951+
p->extra_root = NULL;
8952+
}
8953+
89518954
delete_process(p);
89528955

89538956
#ifdef ERTS_SMP

erts/emulator/beam/erl_process.h

+10-4
Original file line numberDiff line numberDiff line change
@@ -699,6 +699,14 @@ struct ErtsPendingSuspend_ {
699699

700700
#endif
701701

702+
703+
typedef struct ErlExtraRootSet_ ErlExtraRootSet;
704+
struct ErlExtraRootSet_ {
705+
Eterm *objv;
706+
Uint sz;
707+
void (*cleanup)(ErlExtraRootSet *);
708+
};
709+
702710
/* Defines to ease the change of memory architecture */
703711
# define HEAP_START(p) (p)->heap
704712
# define HEAP_TOP(p) (p)->htop
@@ -792,10 +800,7 @@ struct process {
792800

793801
ErlMessageQueue msg; /* Message queue */
794802

795-
Eterm *extra_root; /* Extra root set, used e.g. by yielding bifs. */
796-
Uint extra_root_sz; /* Size of extra root set. */
797-
ErtsAlcType_t extra_root_allocator; /* Type of memory allocator used,
798-
used for freeing extra_root if process dies. */
803+
ErlExtraRootSet *extra_root; /* Used by trapping BIF's */
799804

800805
union {
801806
ErtsBifTimer *bif_timers; /* Bif timers aiming at this process */
@@ -1980,6 +1985,7 @@ erts_sched_poke(ErtsSchedulerSleepInfo *ssi)
19801985
}
19811986
}
19821987

1988+
19831989
#endif /* #if ERTS_GLB_INLINE_INCL_FUNC_DEF */
19841990

19851991
#endif /* #ifdef ERTS_SMP */

erts/emulator/beam/erl_zlib.c

+42
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,48 @@ void erl_zlib_zfree_callback (voidpf opaque, voidpf ptr)
4444
erts_free(ERTS_ALC_T_ZLIB, ptr);
4545
}
4646

47+
/*
48+
* Initialize a z_stream with a source, to later *chunk* data into a destination
49+
* Returns Z_OK or Error.
50+
*/
51+
int ZEXPORT erl_zlib_deflate_start(z_stream *streamp, const Bytef* source,
52+
uLong sourceLen, int level)
53+
{
54+
streamp->next_in = (Bytef*)source;
55+
streamp->avail_in = (uInt)sourceLen;
56+
streamp->total_out = streamp->avail_out = 0;
57+
streamp->next_out = NULL;
58+
erl_zlib_alloc_init(streamp);
59+
return deflateInit(streamp, level);
60+
}
61+
/*
62+
* Deflate a chunk, The destination length is the limit.
63+
* Returns Z_OK if more to process, Z_STREAM_END if we are done.
64+
*/
65+
int ZEXPORT erl_zlib_deflate_chunk(z_stream *streamp, Bytef* dest, uLongf* destLen)
66+
{
67+
int err;
68+
uLongf last_tot = streamp->total_out;
69+
70+
streamp->next_out = dest;
71+
streamp->avail_out = (uInt)*destLen;
72+
73+
if ((uLong)streamp->avail_out != *destLen) return Z_BUF_ERROR;
74+
75+
err = deflate(streamp, Z_FINISH);
76+
*destLen = streamp->total_out - last_tot;
77+
return err;
78+
}
79+
80+
81+
/*
82+
* When we are done, free up the deflate structure
83+
* Retyurns Z_OK or Error
84+
*/
85+
int ZEXPORT erl_zlib_deflate_finish(z_stream *streamp)
86+
{
87+
return deflateEnd(streamp);
88+
}
4789

4890
int ZEXPORT erl_zlib_compress2 (Bytef* dest, uLongf* destLen,
4991
const Bytef* source, uLong sourceLen,

erts/emulator/beam/erl_zlib.h

+8
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,14 @@
3131
(s)->zfree = erl_zlib_zfree_callback; \
3232
} while (0)
3333

34+
/*
35+
* Chunked interface, used by term_to_binary among others.
36+
*/
37+
int ZEXPORT erl_zlib_deflate_start(z_stream *streamp, const Bytef* source,
38+
uLong sourceLen, int level);
39+
int ZEXPORT erl_zlib_deflate_chunk(z_stream *streamp, Bytef* dest, uLongf* destLen);
40+
int ZEXPORT erl_zlib_deflate_finish(z_stream *streamp);
41+
3442
/* Use instead of compress
3543
*/
3644
#define erl_zlib_compress(dest,destLen,source,sourceLen) \

0 commit comments

Comments
 (0)