Commit Graph

1489 Commits (49aa87c316c441aa47974e8e9191a5a7e6d03d9a)

Author SHA1 Message Date
Sébastien Hinderer 24744e8dd8 cehck-typo 2020-07-30 10:23:17 +02:00
Xavier Leroy a0a1ba4f1e
Merge pull request #9699 from EduardoRFS/trunk-ios
Add support for iOS and macOS on ARM64
2020-07-28 16:40:55 +02:00
Fourchaux 44e6cf4e0f
typos (#9806) 2020-07-28 12:22:03 +01:00
EduardoRFS 69d4ab80d0 arm64: use Arch.macosx instead of is_macosx
Also remove the duplicated declaration from proc.ml and emit.mlp

Co-authored-by: Xavier Leroy <xavier.leroy@college-de-france.fr>
2020-07-25 08:38:11 +00:00
EduardoRFS 9a98d40b86 arm64: add reference to Apple ARM64 ABI 2020-07-25 08:37:39 +00:00
EduardoRFS 8c38ac6bf6 arm64: support ios shared library
* the stub on iOS also saves x8 and x9
* use x8 for ADDITIONAL_ARG
* use only 8 regs for calling args
2020-07-25 08:37:39 +00:00
iOS Porting Team d189dcef62 arm64 emitter: support apple variant of assembler 2020-07-25 08:36:23 +00:00
Xavier Leroy e41dc9c443
Merge pull request #9752 from xavierleroy/c-calling-conventions
Revised handing of calling conventions for external C functions
2020-07-25 09:50:42 +02:00
Xavier Leroy ed8f3b427c ARM64 back-end: support the iOS/macOS ABI for calling external C functions
Unboxed arguments of type `int32` that are passed on the stack
are passed in 32-bit words instead of 64-bit words as in the AAPCS64 ABI.

To support this, we introduce a new specific operation, `Imove32`,
that compiles down to 32-bit moves or 32-bit stack loads or 32-bit
stack stores.

In the Selection pass, method `insert_move_extcall_arg`,
we generate `Imove32` instructions when required, i.e. if the
argument is an unboxed `int32` and needs to be passed on stack.

We then update `Proc.loc_external_arguments` to use 32-bit stack words
for `int32` arguments.
2020-07-24 17:39:27 +02:00
Xavier Leroy 9fcb295b98 Revised passing of arguments to external C functions
Introduce the type Cmm.exttype to precisely describe arguments to
external C functions, especially unboxed numerical arguments.

Annotate Cmm.Cextcall with the types of the arguments (Cmm.exttype list).
An empty list means "all arguments have default type XInt".

Annotate Mach.Iextcall with the type of the result (Cmm.machtype)
and the types of the arguments (Cmm.exttype list).

Change (slightly) the API for describing calling conventions in Proc:
- loc_external_arguments now takes a Cmm.exttype list,
  in order to know more precisely the types of the arguments.
- loc_arguments, loc_parameters, loc_results, loc_external_results
  now take a Cmm.machype instead of an array of pseudoregisters.
  (Only the types of the pseudoregisters mattered anyway.)

Update the implementations of module Proc accordingly, in every port.

Introduce a new overridable method in Selectgen, insert_move_extcall_arg,
to produce the code that moves an argument of an external C function
to the locations returned by Proc.loc_external_arguments.

Revise the selection of external calls accordingly
(method emit_extcall_args in Selectgen).
2020-07-24 17:39:22 +02:00
Xavier Leroy 1e71f75ec4
Selectgen#bind_let_mut: use self#regs_for to allocate target registers (#9782)
Software emulation of floating-point arithmetic, as in the ARM EABI port,
use pairs of pseudoregisters of type Int to represent values of type Float.

This is achieved by the `regs_for` method of class `selector_generic`,
which defaults to `Reg.createv` but is overriden for ARM EABI so
as to perform the transformation Float -> Int,Int on the fly.

The method `bind_let_mut` uses `Reg.createv` to associate
pseudoregisters to bound variables.  This is incorrect in a soft FP
context, as a bound variable of type Float will get a Float register
nonetheless.  `self#regs_for` must be used instead.  This is what this
commit does.
2020-07-20 11:24:37 +02:00
David Allsopp e6ab329541 Don't call the archiver/librarian for empty .cmxa 2020-04-22 14:56:02 +01:00
David Allsopp 793cd86785 Allow linking empty .cmxa files on MSVC
MSVC .lib format doesn't support having no .obj files in the library, so
ocamlopt -o foo.cmxa -a generates foo.cmxa but not foo.lib (there's no
error from the Microsoft Linker). The resulting foo.cmxa is unlinkable,
since OCaml passes foo.lib on to the linker.

This patch relaxes the requirement for foo.lib if the .cmxa contains no
units.
2019-10-03 10:44:54 +01:00
Xavier Leroy 7f5a137972 New representation of closures, native-code compilation
In code that builds closures, instead of the old arity field,
produce a closure information field encoding arity + position of environment.
2020-06-05 17:46:58 +02:00
Stephen Dolan 0d44a6cfe6 Remove Const_pointer from Lambda and Clambda (#9585)
Lambda and Clambda distinguish Const_int from Const_pointer only so
that they can pass the information to Cmm. But now that that
Const_pointer is gone from Cmm (#9578), there's no need for the
distinction in Lambda either.

This PR requires a bootstrap, because the .cmo format changes:
Lambda.structured_constant has one fewer constructor.  The bootstrap
is in the following commit.
2020-06-02 11:19:20 +02:00
Greta Yorsh 6cb283b1d8 Move float compare from cmmgen to cmm_helpers 2020-05-27 16:59:15 +01:00
Greta Yorsh 8fce17d902 Bind arguments of integer and float compare in cmmgen 2020-05-27 14:49:35 +01:00
Stephen Dolan 9e09fde735
Avoid creating ill-formed blocks in Cmm letrec (#9577)
Use "1" (integer 0) as filler value instead of "0" (null pointer).

Fixes: 7718
2020-05-25 10:11:45 +02:00
Stephen Dolan 2d92955749
Remove Const_pointer (#9578)
Since #9316 was merged, Cconst_pointer is compiled in exactly the same way as Cconst_int. This commit removes the now-redundant Cconst_pointer and Cconst_natpointer.
2020-05-19 15:31:08 +02:00
David Allsopp b6c8b35e2d
Make -flarge-toc the default for PowerPC (#9557)
Introduce -fsmall-toc in order to access the previous behaviour and
document both options in the manual and ocamlopt manpage.
2020-05-13 18:23:37 +02:00
Xavier Leroy ea6896f9f1 Update C calling conventions to the RISC-V ELF psABI
The original implementation of loc_external_arguments and
loc_external_results was following an older ABI,
where an FP argument passed in an FP register "burns" an integer register.

In the ELF psABI, integer registers and FP registers are used independently,
as in the OCaml calling convention.  Plus, if all FP registers are used
but an integer register remains, the integer register is used to pass
the next FP argument.

Fixes: #9515
2020-04-30 16:20:46 +02:00
Xavier Leroy 16794b9405 Support FP reg -> int reg moves
Using instruction fmv.x.d.

This is necessary to implement the ELF psABI calling conventions,
whereas some FP arguments may have to be passed in integer registers.
2020-04-30 16:20:46 +02:00
Stephen Dolan 0040c5d783 Print function names (derived from Lambda.scoped_location) in backtraces
Function names now appear in backtraces and are available via Printexc.
2020-04-27 12:58:53 +01:00
Stephen Dolan 2986beaa78 Replace Location.t with Lambda.scoped_location in Lambda code
This commit threads scopes through translation from Typedtree to
Lambda, extending the scopes when entering functions, modules,
classes and methods.
2020-04-27 12:58:53 +01:00
Nicolás Ojeda Bär 8f3833c4d0
Add RISC-V native-code backend (#9441)
This is a port of ocamlopt for the RISC-V processor in 64-bit mode.
2020-04-24 16:04:50 +02:00
Xavier Leroy 83598da1ab
Merge pull request #9392 from stedolan/visit-once
Visit registers at most once in Coloring.iter_preferred.
2020-04-22 09:38:08 +02:00
Stephen Dolan d5dadae8ed
Make Cconst_symbol have typ_int to fix no-naked-pointers mode (#9282) 2020-04-21 12:06:19 +01:00
Gabriel Scherer 702e34fbe5
Merge pull request #9463 from lthls/fix_int64_cmm_typ
Fix Cmm type of unboxed integers in Clet_mut
2020-04-20 11:34:15 +02:00
Nicolás Ojeda Bär ec6690fb53
x86 asm: handle unit names with special characters (#9465) 2020-04-19 11:17:00 +02:00
Vincent Laviron 8f006a366b Fix Cmm type of unboxed Int64 values in Clet_mut 2020-04-18 11:39:25 +02:00
Gabriel Scherer 9568154248
Merge pull request #9389 from Anukriti12/trunk
call_linker now returns exit_code for better user response on linking_error, fixes #7141
2020-04-17 17:05:56 +02:00
Stephen Dolan 6fbecf0f72 Reset Reg.visit_generation during Reg.reset 2020-04-16 13:19:33 +01:00
Stephen Dolan 2208a4cbe6
Fix tail-call optimisation with a mutable ref (#9443)
Fix tail-call optimisation with a mutable ref
(Clet_mutable was not recognized properly in tail position.)

Add a test for tail-call optimisation with a mutable ref
2020-04-13 18:20:56 +02:00
Anukriti12 7266b79d60 code review changes 2020-04-02 16:38:54 +05:30
Stephen Dolan d48df3cac1 Visit registers at most once in Coloring.iter_preferred 2020-03-31 12:34:02 +01:00
Anukriti12 7feaeb52a1
Merge branch 'trunk' into trunk 2020-03-31 15:50:39 +05:30
Greta Yorsh 824ce35492
Replace caml_int_compare and caml_float_compare with primitives (#2324) 2020-03-26 10:58:10 +01:00
Anukriti12 8f235efdf5 call_linker now returns exit_code for better error response on linking_error, fixes #7141 2020-03-23 06:12:05 +05:30
Stephen Dolan 4d4a056bc7
Micro-optimise allocations on amd64 to save a register (#9280)
There's no need for allocation on amd64 to clobber the %rax register. It's only used in one case (-compact out-of-line allocation of >3 words), and only used there to do a single subtraction. That subtraction can be done by the caller at no code size penalty, freeing up %rax.

Inside amd64.S functions, %r11 can be used instead of %rax as temporary.  %r11 is destroyed by PLT stub code, so on ELF platforms it costs nothing to use.
2020-03-09 19:52:36 +01:00
Stephen Dolan de9e630852 Assert that Cassign is only used on Clet_mut-bound variables 2020-02-25 15:23:38 +00:00
Stephen Dolan 1336ce0c0d Use typing information from Clambda for mutable Cmm variables 2020-02-25 15:03:14 +00:00
octachron dcebfa1617 output-complete-obj .so: link runtime c libraries
This commit align the behavior of output-complete-obj and output-obj
when building shared libraries
2020-02-17 10:10:45 +01:00
Gabriel Scherer 8938886721 -dno-locations: hide source locations (and debug events) from IR dumps
This PR was tested with also the -dsel, -dlinear output (also fixed to
not-print locations), but the output is architecture-dependent so this
part of the test was removed.
2020-01-09 15:25:16 +01:00
Greta Yorsh 6daaf62904 Do not emit references to dead labels (spacetime) (#9097) 2019-11-26 12:06:19 +00:00
Gabriel Scherer 5a1f224aae
Merge pull request #9070 from lthls/fix_cache_public_method_cmm
Fix addition kind in cache_public_method
2019-11-12 13:57:55 +01:00
Gabriel Scherer c76edb9677 [refactoring] use named fields for Consistbl.Inconsistency exception 2019-11-07 15:07:46 +01:00
Gabriel Scherer 92bfafc1ac
Merge pull request #8805 from stedolan/statmemprof-comballoc-native
Keep information about allocation sizes, for statmemprof, and use during GC.
2019-11-06 13:44:14 +01:00
Greta Yorsh 7c11fcbdd1 Stop before emit 2019-10-30 15:27:29 +00:00
Vincent Laviron 42e9ab34f4 Fix addition kind in cache_public_method
No Changes entry needed
2019-10-24 18:47:38 +02:00
Stephen Dolan 7fe360401b Per-architecture support for allocation size info in frame tables.
amd64: remove caml_call_gc{1,2,3} and simplify caml_alloc{1,2,3,N}
       by tail-calling caml_call_gc.

i386:  simplify caml_alloc{1,2,3,N} by tail-calling caml_call_gc.
       these functions do not need to preserve ebx.

arm:   simplify caml_alloc{1,2,3,N} by tail-calling caml_call_gc.
       partial revert of #8619.

arm64: simplify caml_alloc{1,2,3,N} by tail-calling caml_call_gc.
       partial revert of #8619.

power: partial revert of #8619.
       avoid restarting allocation sequence after failure.

s390:  partial revert of #8619.
       avoid restarting allocation seqeunce after failure.
2019-10-23 09:24:13 +01:00