forked from ocaml/ocaml
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathfiber.h
281 lines (249 loc) · 11.8 KB
/
fiber.h
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
/**************************************************************************/
/* */
/* OCaml */
/* */
/* KC Sivaramakrishnan, Indian Institute of Technology, Madras */
/* Tom Kelly, OCaml Labs Consultancy */
/* Stephen Dolan, University of Cambridge */
/* */
/* Copyright 2021 Indian Institute of Technology, Madras */
/* Copyright 2021 OCaml Labs Consultancy */
/* Copyright 2019 University of Cambridge */
/* */
/* All rights reserved. This file is distributed under the terms of */
/* the GNU Lesser General Public License version 2.1, with the */
/* special exception on linking described in the file LICENSE. */
/* */
/**************************************************************************/
#ifndef CAML_FIBER_H
#define CAML_FIBER_H
#ifdef CAML_INTERNALS
#include "misc.h"
#include "mlvalues.h"
#include "roots.h"
struct stack_info;
/* stack_handler describes the state for using fibers as part of effects */
struct stack_handler {
value handle_value;
value handle_exn;
value handle_effect;
struct stack_info* parent; /* parent OCaml stack if any */
};
/* stack_info describes the OCaml stack. It is used for:
* - storing information about the OCaml stack allowing it to be switched
* - accessing the stack_handler for the stack to handle effects
* - handling a freelist of OCaml stacks in a stack_cache
*/
struct stack_info {
#ifdef NATIVE_CODE
void* sp; /* stack pointer of the OCaml stack when suspended */
void* exception_ptr; /* exception pointer of OCaml stack when suspended */
#else
value* sp;
value* exception_ptr;
#endif
struct stack_handler* handler; /* effect handling state for the fiber */
/* [cache_bucket] is an index into the [Caml_state->stack_cache] array if
* this size is pooled. If unpooled, it is [-1].
*
* Stacks may be unpooled if either the stack size is not 2**N multiple of
* [caml_fiber_wsz] or the stack is bigger than pooled sizes. */
int cache_bucket;
size_t size; /* only used when USE_MMAP_MAP_STACK is defined */
uintnat magic;
int64_t id;
};
CAML_STATIC_ASSERT(sizeof(struct stack_info) ==
Stack_ctx_words * sizeof(value));
#define Stack_base(stk) ((value*)(stk + 1))
#define Stack_threshold_ptr(stk) \
(Stack_base(stk) + Stack_threshold / sizeof(value))
#define Stack_high(stk) (value*)stk->handler
#define Stack_handle_value(stk) (stk)->handler->handle_value
#define Stack_handle_exception(stk) (stk)->handler->handle_exn
#define Stack_handle_effect(stk) (stk)->handler->handle_effect
#define Stack_parent(stk) (stk)->handler->parent
/* Stack layout for native code. Stack grows downwards.
*
* +------------------------+
* | struct stack_handler |
* +------------------------+ <--- Stack_high
* | caml_runstack / |
* | caml_start_program |
* +------------------------+
* | |
* . OCaml frames . <--- sp
* | |
* +------------------------+ <--- Stack_threshold
* | |
* . Red Zone .
* | |
* +------------------------+ <--- Stack_base
* | struct stack_info |
* +------------------------+ <--- Caml_state->current_stack
*/
/* This structure is used for storing the OCaml return pointer when
* transitioning from an OCaml stack to a C stack at a C call. When an OCaml
* stack is reallocated, this linked list is walked to update the OCaml stack
* pointers. It is also used for DWARF backtraces. */
struct c_stack_link {
/* The reference to the OCaml stack */
struct stack_info* stack;
/* OCaml return address */
void* sp;
struct c_stack_link* prev;
};
/* `gc_regs` and `gc_regs_buckets`.
When entering certain runtime functions, the OCaml runtime saves
all registers into a `gc_regs` "bucket", a value array allocated on
the C heap. This is notably used by the garbage collector to know
which registers contain local roots.
`Caml_state->gc_regs` points to the bucket currently in use, or
NULL if no runtime function saving all registers is currently being
called.
`Caml_state->gc_regs_buckets` is a domain-local cache of buckets
that are not currently in use. It has a linked list structure
(the first element of each bucket is a pointer to the next
available bucket or 0). It is guaranteed to be non-empty, to
contain at least one free bucket, whenever we are running OCaml
code on the domain. This invariant is maintained by calling
[caml_maybe_expand_stack] before calling OCaml code from C code,
which allocates a new bucket if the list is empty.
When OCaml code needs to save all registers, it pops the next
bucket from `gc_regs_bucket`. It is pushed back on return.
When C code passes control to an OCaml callback, the current
`Caml_state->gc_regs` value is saved to the top of the OCaml stack
(see the `caml_start_program` logic, which is also used by
`caml_callback` functions). In general we can thus have several
buckets storing registers, one for each nested call to runtime
functions saving all registers, with the currently-active one in
`Caml_state` and the rest at the beginning of each OCaml stack
fragment created from C.
*/
/* Overview of the stack switching primitives for effects
*
* For an understanding of effect handlers in OCaml please see:
* Retrofitting Effect Handlers onto OCaml, KC Sivaramakrishnan, et al.
* PLDI 2021
*
* Native code
* -----------
*
* In native compilation the stack switching primitives Prunstack,
* Pperform, Preperform and Presume make use of corresponding functions
* implemented in the assembly files for an architecture (such as
* runtime/amd64.S).
*
* A continuation object represents a suspended OCaml stack. It contains
* the stack pointer tagged as an integer to avoid being followed by the GC.
* In the code the tagged pointer can be referred to as a 'fiber':
* fiber := Val_ptr(stack)
*
* caml_runstack new_stack function argument
* caml_runstack launches a function (with an argument) in a new OCaml
* stack. It switches execution from the parent OCaml stack to the fresh
* stack and installs an exception handler. On return the new OCaml stack
* is freed, the stack is restored to the parent OCaml stack and the
* handle_value/handle_exn function is executed on the parent OCaml stack.
*
* caml_perform effect continuation
* caml_perform captures the current OCaml stack in the continuation object
* provided and raises the effect by switching to the parent OCaml stack and
* then executing the handle_effect function. Should there be no parent OCaml
* stack then the Effect.Unhandled exception is raised.
*
* caml_reperform effect continuation last_fiber
* caml_reperform is used to walk up the parent OCaml stacks to execute the
* next effect handler installed in the chain. This function is implemented
* by setting up the required registers then jumping into caml_perform which
* does the switch to the parent and execution of the handle_effect function.
*
* caml_resume new_fiber function argument
* caml_resume resumes execution on new_fiber by making the current stack
* the parent of the new_fiber and then switching to the stack for new_fiber.
* The function with argument is then executed on the new stack. Care is taken
* to check if the new_fiber argument has already been resumed and so is null.
*
*
* Bytecode
* --------
*
* In bytecode compilation the primitives are mapped to effect instructions and
* some changes are made to the bytecode interpreter on every function return
* and exception raise. In particular:
*
* Presume | Prunstack -> RESUME (& RESUMETERM if a tail call)
* RESUME checks that the stack is valid (a NULL stack indicates a
* continuation that has already been resumed). The stacks are then switched
* with the old stack becoming the parent of the new stack. Care is taken
* to setup the exception handler for the new stack. Execution continues
* on the new OCaml stack with the passed function and argument.
*
* Pperform -> PERFORM
* PERFORM captures the current stack in a continuation object it allocates.
* The parent stack is then switched to and the handle_effect function for
* the parent stack is executed. If no parent stack exists then the
* Effect.Unhandled exception is raised.
*
* Preperform -> REPERFORMTERM
* REPERFORMTERM is used to walk up the parent OCaml stacks to execute the
* next effect handler installed in the chain. The instruction takes care to
* switch back to the continuation stack to raise the Effect.Unhandled
* exception in in the case no parent is left. Otherwise the instruction
* switches to the parent stack and executes the handle_effect function for
* that parent stack.
*
* Special return handling:
* There is special handling on every function return (see do_return of
* interp.c). This handling allows the completion of a child stack to be
* detected. On completion of a child stack, the child stack is freed and
* control returns to the parent stack to execute the handle_value function.
*
* Special exception handling:
* When an exception is raised (see raise_notrace of interp.c), the trap
* offset is checked. If there are no more exceptions in this stack and a
* parent stack exists, then the child stack is freed and the
* handle_exception function is executed on the parent stack.
*/
/* The table of global identifiers */
extern value caml_global_data;
#define Trap_pc(tp) (((code_t *)(tp))[0])
#define Trap_link(tp) ((tp)[1])
struct stack_info** caml_alloc_stack_cache (void);
CAMLextern struct stack_info* caml_alloc_main_stack (uintnat init_wsize);
void caml_scan_stack(
scanning_action f, scanning_action_flags fflags, void* fdata,
struct stack_info* stack, value* v_gc_regs);
struct stack_info* caml_alloc_stack_noexc(mlsize_t wosize, value hval,
value hexn, value heff, int64_t id);
/* try to grow the stack until at least required_size words are available.
returns nonzero on success */
CAMLextern int caml_try_realloc_stack (asize_t required_wsize);
CAMLextern uintnat caml_get_init_stack_wsize(void);
void caml_change_max_stack_size (uintnat new_max_wsize);
void caml_maybe_expand_stack(void);
CAMLextern void caml_free_stack(struct stack_info* stk);
/* gc_regs_buckets is allocated on-demand by [maybe_expand_stack]. */
CAMLextern void caml_free_gc_regs_buckets(value *gc_regs_buckets);
#ifdef NATIVE_CODE
void caml_get_stack_sp_pc (struct stack_info* stack,
char** sp /* out */, uintnat* pc /* out */);
void
caml_rewrite_exception_stack(struct stack_info *old_stack,
value** exn_ptr, struct stack_info *new_stack);
#endif
value caml_continuation_use (value cont);
/* Replace the stack of a continuation that was previously removed
with caml_continuation_use. The GC must not be allowed to run
between continuation_use and continuation_replace.
Used for cloning continuations and continuation backtraces. */
void caml_continuation_replace(value cont, struct stack_info* stack);
CAMLnoreturn_start
CAMLextern void caml_raise_continuation_already_resumed (void)
CAMLnoreturn_end;
CAMLnoreturn_start
CAMLextern void caml_raise_unhandled_effect (value effect)
CAMLnoreturn_end;
value caml_make_unhandled_effect_exn (value effect);
#endif /* CAML_INTERNALS */
#endif /* CAML_FIBER_H */