Skip to content

Commit

Permalink
Support the two variants on i386.
Browse files Browse the repository at this point in the history
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/raise_variants@14231 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
  • Loading branch information
alainfrisch committed Oct 15, 2013
1 parent 0efe8df commit 784b0b3
Show file tree
Hide file tree
Showing 2 changed files with 22 additions and 5 deletions.
11 changes: 8 additions & 3 deletions asmcomp/i386/emit.mlp
Original file line number Diff line number Diff line change
Expand Up @@ -830,11 +830,16 @@ let emit_instr fallthrough i =
` addl ${emit_int (trap_frame_size - 4)}, %esp\n`;
cfi_adjust_cfa_offset (-trap_frame_size);
stack_offset := !stack_offset - trap_frame_size
| Lraise ->
if !Clflags.debug then begin
| Lraise k ->
begin match !Clflags.debug, k with
| true, Lambda.Raise_regular ->
` call {emit_symbol "caml_raise_exn"}\n`;
record_frame Reg.Set.empty i.dbg
end else begin
| true, Lambda.Raise_reraise ->
` call {emit_symbol "caml_reraise_exn"}\n`;
record_frame Reg.Set.empty i.dbg
| false, _
| true, Lambda.Raise_notrace ->
` movl {emit_symbol "caml_exception_pointer"}, %esp\n`;
` popl {emit_symbol "caml_exception_pointer"}\n`;
if trap_frame_size > 8 then
Expand Down
16 changes: 14 additions & 2 deletions asmrun/i386.S
Original file line number Diff line number Diff line change
Expand Up @@ -339,6 +339,8 @@ FUNCTION(caml_raise_exn)
UNDO_ALIGN_STACK(8)
ret
LBL(110):
movl $0, G(caml_backtrace_pos)
LBL(111):
movl %eax, %esi /* Save exception bucket in esi */
movl G(caml_exception_pointer), %edi /* SP of handler */
movl 0(%esp), %eax /* PC of raise */
Expand All @@ -356,19 +358,29 @@ LBL(110):
ret
CFI_ENDPROC

FUNCTION(caml_reraise_exn)
CFI_STARTPROC
testl $1, G(caml_backtrace_active)
jne LBL(111)
movl G(caml_exception_pointer), %esp
popl G(caml_exception_pointer); CFI_ADJUST(-4)
UNDO_ALIGN_STACK(8)
ret
CFI_ENDPROC

/* Raise an exception from C */

FUNCTION(caml_raise_exception)
CFI_STARTPROC
PROFILE_C
testl $1, G(caml_backtrace_active)
jne LBL(111)
jne LBL(112)
movl 4(%esp), %eax
movl G(caml_exception_pointer), %esp
popl G(caml_exception_pointer); CFI_ADJUST(-4)
UNDO_ALIGN_STACK(8)
ret
LBL(111):
LBL(112):
movl 4(%esp), %esi /* Save exception bucket in esi */
ALIGN_STACK(12)
pushl G(caml_exception_pointer); CFI_ADJUST(4) /* 4: sp of handler */
Expand Down

0 comments on commit 784b0b3

Please sign in to comment.