Move to OCaml 4.11.0+dev2-2020-04-22.

- Backport upstream RISC-V backend from 4.12 + fixes.
- Enable tests on riscv64.
- Disable ocaml-instr-* tools on riscv64.
This commit is contained in:
Richard W.M. Jones 2020-05-04 10:16:53 +01:00
parent 7eb82f0e55
commit a2dcfff43b
12 changed files with 2138 additions and 386 deletions

View File

@ -1,4 +1,4 @@
From 14d63e7a96ab39598f7c42b8513c914253afb173 Mon Sep 17 00:00:00 2001
From 1b1a2ad3294327e5bbbc753f306d1199b0a2a583 Mon Sep 17 00:00:00 2001
From: "Richard W.M. Jones" <rjones@redhat.com>
Date: Tue, 24 Jun 2014 10:00:15 +0100
Subject: [PATCH 1/7] Don't add rpaths to libraries.
@ -8,7 +8,7 @@ Subject: [PATCH 1/7] Don't add rpaths to libraries.
1 file changed, 2 insertions(+), 2 deletions(-)
diff --git a/tools/Makefile b/tools/Makefile
index 8bd51bfd8..b34cbbf32 100644
index 96a4244cc..076411a91 100644
--- a/tools/Makefile
+++ b/tools/Makefile
@@ -153,8 +153,8 @@ $(call byte_and_opt,ocamlmklib,ocamlmklibconfig.cmo config.cmo \

View File

@ -1,4 +1,4 @@
From 65456b148ad6532a6b0086ba5812b67c0371e768 Mon Sep 17 00:00:00 2001
From 8ea0bc7713a89cd6340e35b4dae048be63c50aec Mon Sep 17 00:00:00 2001
From: "Richard W.M. Jones" <rjones@redhat.com>
Date: Tue, 29 May 2012 20:44:18 +0100
Subject: [PATCH 2/7] configure: Allow user defined C compiler flags.
@ -8,10 +8,10 @@ Subject: [PATCH 2/7] configure: Allow user defined C compiler flags.
1 file changed, 4 insertions(+)
diff --git a/configure.ac b/configure.ac
index e84dc0431..1687918a2 100644
index fbd49c1ee..a35da2040 100644
--- a/configure.ac
+++ b/configure.ac
@@ -608,6 +608,10 @@ AS_CASE([$host],
@@ -609,6 +609,10 @@ AS_CASE([$host],
internal_cflags="$gcc_warnings"],
[common_cflags="-O"])])

View File

@ -1,4 +1,4 @@
From 0b1b91841a3a227321f8e155ed932893e285b429 Mon Sep 17 00:00:00 2001
From 39df379f1aa139a073d7b436bb9bd33ef2f70caf Mon Sep 17 00:00:00 2001
From: "Richard W.M. Jones" <rjones@redhat.com>
Date: Fri, 26 Apr 2019 16:16:29 +0100
Subject: [PATCH 3/7] configure: Remove incorrect assumption about
@ -10,10 +10,10 @@ See https://github.com/ocaml/ocaml/issues/8647#issuecomment-487094390
1 file changed, 6 insertions(+), 5 deletions(-)
diff --git a/configure.ac b/configure.ac
index 1687918a2..01edbff17 100644
index a35da2040..4c9358897 100644
--- a/configure.ac
+++ b/configure.ac
@@ -510,10 +510,11 @@ AS_IF(
@@ -511,10 +511,11 @@ AS_IF(
# Are we building a cross-compiler
@ -29,7 +29,7 @@ index 1687918a2..01edbff17 100644
# Checks for programs
@@ -996,7 +997,7 @@ AS_IF([test $arch != "none" && $arch64 ],
@@ -1018,7 +1019,7 @@ AS_CASE([$arch],
# Assembler

View File

@ -1,4 +1,4 @@
From 0b805df7403257a71b9852deb2f468aac16133b0 Mon Sep 17 00:00:00 2001
From e829051c3b35920db3c5e0dd913026f556448675 Mon Sep 17 00:00:00 2001
From: "Richard W.M. Jones" <rjones@redhat.com>
Date: Sat, 18 Jan 2020 11:31:27 +0000
Subject: [PATCH 4/7] Remove configure from .gitattributes.
@ -9,7 +9,7 @@ It's not a binary file.
1 file changed, 4 deletions(-)
diff --git a/.gitattributes b/.gitattributes
index db37bfbe5..b6e540188 100644
index 200eb49c6..d871764de 100644
--- a/.gitattributes
+++ b/.gitattributes
@@ -29,10 +29,6 @@

File diff suppressed because it is too large Load Diff

View File

@ -1,174 +0,0 @@
From 2e40ed7452896a5ad043ca1297112d2a5bf6189b Mon Sep 17 00:00:00 2001
From: David Allsopp <david.allsopp@metastack.com>
Date: Mon, 20 Apr 2020 16:13:26 +0100
Subject: [PATCH 5/7] Merge pull request #9457 from dra27/fix-mod_use
Fix #mod_use in toplevel
(cherry picked from commit f4dc3003d579e45f6ddeb6ffceb4c283a9e15bc7)
---
Changes | 2 +-
testsuite/tests/tool-toplevel/mod.ml | 1 +
testsuite/tests/tool-toplevel/mod_use.ml | 9 +++++++++
toplevel/opttoploop.ml | 19 +++++++++++--------
toplevel/toploop.ml | 19 +++++++++++--------
5 files changed, 33 insertions(+), 17 deletions(-)
create mode 100644 testsuite/tests/tool-toplevel/mod.ml
create mode 100644 testsuite/tests/tool-toplevel/mod_use.ml
diff --git a/Changes b/Changes
index f16158f12..a65573604 100644
--- a/Changes
+++ b/Changes
@@ -164,7 +164,7 @@ Working version
points to the grammar.
(Andreas Abel, review by Xavier Leroy)
-- #9283: add a new toplevel directive `#use_output "<command>"` to
+- #9283, #9455, #9457: add a new toplevel directive `#use_output "<command>"` to
run a command and evaluate its output.
(Jérémie Dimino, review by David Allsopp)
diff --git a/testsuite/tests/tool-toplevel/mod.ml b/testsuite/tests/tool-toplevel/mod.ml
new file mode 100644
index 000000000..cd298427b
--- /dev/null
+++ b/testsuite/tests/tool-toplevel/mod.ml
@@ -0,0 +1 @@
+let answer = 42
diff --git a/testsuite/tests/tool-toplevel/mod_use.ml b/testsuite/tests/tool-toplevel/mod_use.ml
new file mode 100644
index 000000000..e068ffc3a
--- /dev/null
+++ b/testsuite/tests/tool-toplevel/mod_use.ml
@@ -0,0 +1,9 @@
+(* TEST
+ files = "mod.ml"
+ * expect
+*)
+
+#mod_use "mod.ml"
+[%%expect {|
+module Mod : sig val answer : int end
+|}];;
diff --git a/toplevel/opttoploop.ml b/toplevel/opttoploop.ml
index cd4210bbe..ad9a2569e 100644
--- a/toplevel/opttoploop.ml
+++ b/toplevel/opttoploop.ml
@@ -449,7 +449,7 @@ let preprocess_phrase ppf phr =
if !Clflags.dump_source then Pprintast.top_phrase ppf phr;
phr
-let use_channel ppf wrap_mod ic name filename =
+let use_channel ppf ~wrap_in_module ic name filename =
let lb = Lexing.from_channel ic in
Location.init lb filename;
(* Skip initial #! line if any *)
@@ -461,7 +461,7 @@ let use_channel ppf wrap_mod ic name filename =
(fun ph ->
let ph = preprocess_phrase ppf ph in
if not (execute_phrase !use_print_results ppf ph) then raise Exit)
- (if wrap_mod then
+ (if wrap_in_module then
parse_mod_use_file name lb
else
!parse_use_file lb);
@@ -485,27 +485,30 @@ let use_output ppf command =
| 0 ->
let ic = open_in_bin fn in
Misc.try_finally ~always:(fun () -> close_in ic)
- (fun () -> use_channel ppf false ic "" "(command-output)")
+ (fun () ->
+ use_channel ppf ~wrap_in_module:false ic "" "(command-output)")
| n ->
fprintf ppf "Command exited with code %d.@." n;
false)
-let use_file ppf wrap_mode name =
+let use_file ppf ~wrap_in_module name =
match name with
| "" ->
- use_channel ppf wrap_mode stdin name "(stdin)"
+ use_channel ppf ~wrap_in_module stdin name "(stdin)"
| _ ->
match Load_path.find name with
| filename ->
let ic = open_in_bin filename in
Misc.try_finally ~always:(fun () -> close_in ic)
- (fun () -> use_channel ppf false ic name filename)
+ (fun () -> use_channel ppf ~wrap_in_module ic name filename)
| exception Not_found ->
fprintf ppf "Cannot find file %s.@." name;
false
-let mod_use_file ppf name = use_file ppf true name
-let use_file ppf name = use_file ppf false name
+let mod_use_file ppf name =
+ use_file ppf ~wrap_in_module:true name
+let use_file ppf name =
+ use_file ppf ~wrap_in_module:false name
let use_silently ppf name =
protect_refs [ R (use_print_results, false) ] (fun () -> use_file ppf name)
diff --git a/toplevel/toploop.ml b/toplevel/toploop.ml
index 02f629f9d..09e550796 100644
--- a/toplevel/toploop.ml
+++ b/toplevel/toploop.ml
@@ -394,7 +394,7 @@ let preprocess_phrase ppf phr =
if !Clflags.dump_source then Pprintast.top_phrase ppf phr;
phr
-let use_channel ppf wrap_mod ic name filename =
+let use_channel ppf ~wrap_in_module ic name filename =
let lb = Lexing.from_channel ic in
Warnings.reset_fatal ();
Location.init lb filename;
@@ -408,7 +408,7 @@ let use_channel ppf wrap_mod ic name filename =
(fun ph ->
let ph = preprocess_phrase ppf ph in
if not (execute_phrase !use_print_results ppf ph) then raise Exit)
- (if wrap_mod then
+ (if wrap_in_module then
parse_mod_use_file name lb
else
!parse_use_file lb);
@@ -431,27 +431,30 @@ let use_output ppf command =
| 0 ->
let ic = open_in_bin fn in
Misc.try_finally ~always:(fun () -> close_in ic)
- (fun () -> use_channel ppf false ic "" "(command-output)")
+ (fun () ->
+ use_channel ppf ~wrap_in_module:false ic "" "(command-output)")
| n ->
fprintf ppf "Command exited with code %d.@." n;
false)
-let use_file ppf wrap_mode name =
+let use_file ppf ~wrap_in_module name =
match name with
| "" ->
- use_channel ppf wrap_mode stdin name "(stdin)"
+ use_channel ppf ~wrap_in_module stdin name "(stdin)"
| _ ->
match Load_path.find name with
| filename ->
let ic = open_in_bin filename in
Misc.try_finally ~always:(fun () -> close_in ic)
- (fun () -> use_channel ppf false ic name filename)
+ (fun () -> use_channel ppf ~wrap_in_module ic name filename)
| exception Not_found ->
fprintf ppf "Cannot find file %s.@." name;
false
-let mod_use_file ppf name = use_file ppf true name
-let use_file ppf name = use_file ppf false name
+let mod_use_file ppf name =
+ use_file ppf ~wrap_in_module:true name
+let use_file ppf name =
+ use_file ppf ~wrap_in_module:false name
let use_silently ppf name =
protect_refs [ R (use_print_results, false) ] (fun () -> use_file ppf name)
--
2.24.1

View File

@ -1,134 +0,0 @@
From 13bec130864d682032f3b3086764487c26076093 Mon Sep 17 00:00:00 2001
From: Gabriel Scherer <gabriel.scherer@gmail.com>
Date: Mon, 20 Apr 2020 11:34:15 +0200
Subject: [PATCH 6/7] Merge pull request #9463 from lthls/fix_int64_cmm_typ
Fix Cmm type of unboxed integers in Clet_mut
(cherry picked from commit 702e34fbe56f6f03db086efe42148395c5e395ff)
---
Changes | 6 ++-
asmcomp/cmmgen.ml | 15 ++++----
testsuite/tests/lib-int64/issue9460.ml | 37 +++++++++++++++++++
testsuite/tests/lib-int64/issue9460.reference | 1 +
4 files changed, 49 insertions(+), 10 deletions(-)
create mode 100644 testsuite/tests/lib-int64/issue9460.ml
create mode 100644 testsuite/tests/lib-int64/issue9460.reference
diff --git a/Changes b/Changes
index a65573604..5f92e00c1 100644
--- a/Changes
+++ b/Changes
@@ -66,8 +66,10 @@ Working version
- #9280: Micro-optimise allocations on amd64 to save a register.
(Stephen Dolan, review by Xavier Leroy)
-- #9316: Use typing information from Clambda for mutable Cmm variables.
- (Stephen Dolan, review by Vincent Laviron, Guillaume Bury and Xavier Leroy)
+- #9316, #9443, #9463: Use typing information from Clambda
+ for mutable Cmm variables.
+ (Stephen Dolan, review by Vincent Laviron, Guillaume Bury, Xavier Leroy,
+ and Gabriel Scherer; temporary bug report by Richard Jones)
- #9426: build the Mingw ports with higher levels of GCC optimization
(Xavier Leroy, review by Sébastien Hinderer)
diff --git a/asmcomp/cmmgen.ml b/asmcomp/cmmgen.ml
index 6e1c924dc..ec9697177 100644
--- a/asmcomp/cmmgen.ml
+++ b/asmcomp/cmmgen.ml
@@ -247,6 +247,11 @@ let box_int dbg bi arg =
(* Boxed numbers *)
+let typ_of_boxed_number = function
+ | Boxed_float _ -> Cmm.typ_float
+ | Boxed_integer (Pint64, _) when size_int = 4 -> [|Int;Int|]
+ | Boxed_integer _ -> Cmm.typ_int
+
let equal_unboxed_integer ui1 ui2 =
match ui1, ui2 with
| Pnativeint, Pnativeint -> true
@@ -687,11 +692,6 @@ and transl_catch env nfail ids body handler dbg =
in
let env_body = add_notify_catch nfail report env in
let body = transl env_body body in
- let typ_of_bn = function
- | Boxed_float _ -> Cmm.typ_float
- | Boxed_integer (Pint64, _) when size_int = 4 -> [|Int;Int|]
- | Boxed_integer _ -> Cmm.typ_int
- in
let new_env, rewrite, ids =
List.fold_right
(fun (id, _kind, u) (env, rewrite, ids) ->
@@ -704,7 +704,7 @@ and transl_catch env nfail ids body handler dbg =
let unboxed_id = V.create_local (VP.name id) in
add_unboxed_id (VP.var id) unboxed_id bn env,
(unbox_number Debuginfo.none bn) :: rewrite,
- (VP.create unboxed_id, typ_of_bn bn) :: ids
+ (VP.create unboxed_id, typ_of_boxed_number bn) :: ids
)
ids (env, [], [])
in
@@ -1165,8 +1165,7 @@ and transl_let env str kind id exp body =
transl (add_unboxed_id (VP.var id) unboxed_id boxed_number env) body in
begin match str, boxed_number with
| Immutable, _ -> Clet (v, cexp, body)
- | Mutable, Boxed_float _ -> Clet_mut (v, typ_float, cexp, body)
- | Mutable, Boxed_integer _ -> Clet_mut (v, typ_int, cexp, body)
+ | Mutable, bn -> Clet_mut (v, typ_of_boxed_number bn, cexp, body)
end
and make_catch ncatch body handler dbg = match body with
diff --git a/testsuite/tests/lib-int64/issue9460.ml b/testsuite/tests/lib-int64/issue9460.ml
new file mode 100644
index 000000000..aacbe6189
--- /dev/null
+++ b/testsuite/tests/lib-int64/issue9460.ml
@@ -0,0 +1,37 @@
+(* TEST
+*)
+
+(* See https://github.com/ocaml/ocaml/issues/9460
+ This test comes from Richard Jones
+ at
+ https://github.com/libguestfs/libnbd/blob/0475bfe04a527051c0a37af59a733c4c8554e427/ocaml/tests/test_400_pread.ml#L21-L36
+*)
+let test_result =
+ let b = Bytes.create 16 in
+ for i = 0 to 16/8-1 do
+ let i64 = ref (Int64.of_int (i*8)) in
+ for j = 0 to 7 do
+ let c = Int64.shift_right_logical !i64 56 in
+ let c = Int64.to_int c in
+ let c = Char.chr c in
+ Bytes.unsafe_set b (i*8+j) c;
+ i64 := Int64.shift_left !i64 8
+ done
+ done;
+ (Bytes.to_string b) ;;
+
+let expected =
+ "\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\008"
+
+let () =
+ assert (test_result = expected)
+
+(* Reproduction case by Jeremy Yallop in
+ https://github.com/ocaml/ocaml/pull/9463#issuecomment-615831765
+*)
+let () =
+ let x = ref Int64.max_int in
+ assert (!x = Int64.max_int)
+
+let () =
+ print_endline "OK"
diff --git a/testsuite/tests/lib-int64/issue9460.reference b/testsuite/tests/lib-int64/issue9460.reference
new file mode 100644
index 000000000..d86bac9de
--- /dev/null
+++ b/testsuite/tests/lib-int64/issue9460.reference
@@ -0,0 +1 @@
+OK
--
2.24.1

View File

@ -0,0 +1,34 @@
From d26a313ae92bb515b04865b6a71a63701dd1fe41 Mon Sep 17 00:00:00 2001
From: Xavier Leroy <xavier.leroy@college-de-france.fr>
Date: Thu, 30 Apr 2020 16:18:06 +0200
Subject: [PATCH 6/7] 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.
(cherry picked from commit 16794b940555315c723411077a2902fc85a33c45)
---
asmcomp/riscv/emit.mlp | 4 +++-
1 file changed, 3 insertions(+), 1 deletion(-)
diff --git a/asmcomp/riscv/emit.mlp b/asmcomp/riscv/emit.mlp
index dc652de42..dbfdc2d40 100644
--- a/asmcomp/riscv/emit.mlp
+++ b/asmcomp/riscv/emit.mlp
@@ -283,8 +283,10 @@ let emit_instr i =
match (src, dst) with
| {loc = Reg _; typ = (Val | Int | Addr)}, {loc = Reg _} ->
` mv {emit_reg dst}, {emit_reg src}\n`
- | {loc = Reg _; typ = Float}, {loc = Reg _} ->
+ | {loc = Reg _; typ = Float}, {loc = Reg _; typ = Float} ->
` fmv.d {emit_reg dst}, {emit_reg src}\n`
+ | {loc = Reg _; typ = Float}, {loc = Reg _; typ = (Val | Int | Addr)} ->
+ ` fmv.x.d {emit_reg dst}, {emit_reg src}\n`
| {loc = Reg _; typ = (Val | Int | Addr)}, {loc = Stack s} ->
let ofs = slot_offset s (register_class dst) in
emit_store src ofs
--
2.24.1

View File

@ -0,0 +1,59 @@
From 5bc92d0cdb5cb26b8d8d517f30914c2b18e85f2b Mon Sep 17 00:00:00 2001
From: Xavier Leroy <xavier.leroy@college-de-france.fr>
Date: Thu, 30 Apr 2020 16:19:16 +0200
Subject: [PATCH 7/7] 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
(cherry picked from commit ea6896f9f184305cc455d3af18cd1cb75cdcd93d)
---
asmcomp/riscv/proc.ml | 11 +++++++----
1 file changed, 7 insertions(+), 4 deletions(-)
diff --git a/asmcomp/riscv/proc.ml b/asmcomp/riscv/proc.ml
index 70909cd83..4c7b58612 100644
--- a/asmcomp/riscv/proc.ml
+++ b/asmcomp/riscv/proc.ml
@@ -187,6 +187,8 @@ let loc_results res =
first integer args in a0 .. a7
first float args in fa0 .. fa7
remaining args on stack.
+ A FP argument can be passed in an integer register if all FP registers
+ are exhausted but integer registers remain.
Return values in a0 .. a1 or fa0 .. fa1. *)
let external_calling_conventions
@@ -202,8 +204,7 @@ let external_calling_conventions
| Val | Int | Addr as ty ->
if !int <= last_int then begin
loc.(i) <- [| phys_reg !int |];
- incr int;
- incr float;
+ incr int
end else begin
loc.(i) <- [| stack_slot (make_stack !ofs) ty |];
ofs := !ofs + size_int
@@ -211,8 +212,10 @@ let external_calling_conventions
| Float ->
if !float <= last_float then begin
loc.(i) <- [| phys_reg !float |];
- incr float;
- incr int;
+ incr float
+ end else if !int <= last_int then begin
+ loc.(i) <- [| phys_reg !int |];
+ incr int
end else begin
loc.(i) <- [| stack_slot (make_stack !ofs) Float |];
ofs := !ofs + size_float
--
2.24.1

View File

@ -1,55 +0,0 @@
From 946b5c2563dbf7d8969781e6b05d9fc531cd65a2 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Nicol=C3=A1s=20Ojeda=20B=C3=A4r?= <n.oje.bar@gmail.com>
Date: Sun, 19 Apr 2020 11:17:00 +0200
Subject: [PATCH 7/7] x86 asm: handle unit names with special characters
(#9465)
(cherry picked from commit ec6690fb53b6caced797e1a7a083a787ff8bd97c)
---
asmcomp/amd64/emit.mlp | 2 +-
testsuite/tests/asmcomp/0-!@#%.compilers.reference | 2 ++
testsuite/tests/asmcomp/0-!@#%.ml | 10 ++++++++++
3 files changed, 13 insertions(+), 1 deletion(-)
create mode 100644 testsuite/tests/asmcomp/0-!@#%.compilers.reference
create mode 100644 testsuite/tests/asmcomp/0-!@#%.ml
diff --git a/asmcomp/amd64/emit.mlp b/asmcomp/amd64/emit.mlp
index 2e9e3a86d..d9c5eb6e6 100644
--- a/asmcomp/amd64/emit.mlp
+++ b/asmcomp/amd64/emit.mlp
@@ -1146,7 +1146,7 @@ let end_assembly() =
};
if system = S_linux then begin
- let frametable = Compilenv.make_symbol (Some "frametable") in
+ let frametable = emit_symbol (Compilenv.make_symbol (Some "frametable")) in
D.size frametable (ConstSub (ConstThis, ConstLabel frametable))
end;
diff --git a/testsuite/tests/asmcomp/0-!@#%.compilers.reference b/testsuite/tests/asmcomp/0-!@#%.compilers.reference
new file mode 100644
index 000000000..7df9a5456
--- /dev/null
+++ b/testsuite/tests/asmcomp/0-!@#%.compilers.reference
@@ -0,0 +1,2 @@
+File "0-!@#%.ml", line 1:
+Warning 24: bad source file name: "0-!@#%" is not a valid module name.
diff --git a/testsuite/tests/asmcomp/0-!@#%.ml b/testsuite/tests/asmcomp/0-!@#%.ml
new file mode 100644
index 000000000..9f24bc382
--- /dev/null
+++ b/testsuite/tests/asmcomp/0-!@#%.ml
@@ -0,0 +1,10 @@
+(* TEST *)
+
+(* We could not include the following characters the file name:
+
+ - '$' : this character is interpreted specially by [ocamltest] (as it uses
+ [Buffer.add_substitute] on the filenames).
+
+ - '^' : this character causes problems under Windows if not properly
+ quoted. In particular, flexlink needed to be adapted.
+*)
--
2.24.1

View File

@ -17,7 +17,7 @@
# These are all the architectures that the tests run on. The tests
# take a long time to run, so don't run them on slow machines.
%global test_arches aarch64 %{power64} x86_64
%global test_arches aarch64 %{power64} riscv64 x86_64
# These are the architectures for which the tests must pass otherwise
# the build will fail.
#global test_arches_required aarch64 ppc64le x86_64
@ -31,7 +31,7 @@
Name: ocaml
Version: 4.11.0
Release: 0.3.pre%{?dist}
Release: 0.4.dev2%{?dist}
Summary: OCaml compiler and programming environment
@ -40,9 +40,8 @@ License: QPL and (LGPLv2+ with exceptions)
URL: http://www.ocaml.org
#Source0: http://caml.inria.fr/pub/distrib/ocaml-4.10/ocaml-%{version}%{rcver}.tar.xz
# This is a pre-release of OCaml 4.11.0 with addition of the RISC-V
# patches. See:
# https://pagure.io/fedora-ocaml/commits/fedora-33-4.11.0-pre
# This is a pre-release of OCaml 4.11.0. See:
# https://pagure.io/fedora-ocaml/commits/fedora-33-4.11.0-dev2
Source0: ocaml-4.11.0.tar.gz
# IMPORTANT NOTE:
@ -54,22 +53,21 @@ Source0: ocaml-4.11.0.tar.gz
#
# https://pagure.io/fedora-ocaml
#
# Current branch: fedora-33-4.11.0-pre
# Current branch: fedora-33-4.11.0-dev2
#
# ALTERNATIVELY add a patch to the end of the list (leaving the
# existing patches unchanged) adding a comment to note that it should
# be incorporated into the git repo at a later time.
# Fedora-specific downstream patches.
Patch0001: 0001-Don-t-add-rpaths-to-libraries.patch
Patch0002: 0002-configure-Allow-user-defined-C-compiler-flags.patch
Patch0003: 0003-configure-Remove-incorrect-assumption-about-cross-co.patch
Patch0004: 0004-Remove-configure-from-.gitattributes.patch
# All of these fixes are upstream in 4.11.
Patch0005: 0005-Merge-pull-request-9457-from-dra27-fix-mod_use.patch
Patch0006: 0006-Merge-pull-request-9463-from-lthls-fix_int64_cmm_typ.patch
Patch0007: 0007-x86-asm-handle-unit-names-with-special-characters-94.patch
# Add RISC-V backend. This is upstream in 4.12 (not 4.11).
Patch0005: 0005-Add-RISC-V-native-code-backend-9441.patch
Patch0006: 0006-Support-FP-reg-int-reg-moves.patch
Patch0007: 0007-Update-C-calling-conventions-to-the-RISC-V-ELF-psABI.patch
BuildRequires: git
BuildRequires: gcc
@ -242,6 +240,10 @@ find $RPM_BUILD_ROOT -name .ignore -delete
# See also: http://www.ocamlpro.com/blog/2012/08/20/ocamlpro-and-4.00.0.html
find $RPM_BUILD_ROOT \( -name '*.cmt' -o -name '*.cmti' \) -a -delete
# Remove this file. It's only created in certain situations and it's
# unclear why it is created at all.
rm -f $RPM_BUILD_ROOT%{_libdir}/ocaml/eventlog_metadata
%files
%doc LICENSE
@ -249,8 +251,10 @@ find $RPM_BUILD_ROOT \( -name '*.cmt' -o -name '*.cmti' \) -a -delete
%{_bindir}/ocamlcmt
%{_bindir}/ocamldebug
%ifnarch riscv64
%{_bindir}/ocaml-instr-graph
%{_bindir}/ocaml-instr-report
%endif
%{_bindir}/ocamlyacc
# symlink to either .byte or .opt version
@ -373,6 +377,12 @@ find $RPM_BUILD_ROOT \( -name '*.cmt' -o -name '*.cmti' \) -a -delete
%changelog
* Mon May 04 2020 Richard W.M. Jones <rjones@redhat.com> - 4.11.0-0.4.dev2.fc33
- Move to OCaml 4.11.0+dev2-2020-04-22.
- Backport upstream RISC-V backend from 4.12 + fixes.
- Enable tests on riscv64.
- Disable ocaml-instr-* tools on riscv64.
* Tue Apr 21 2020 Richard W.M. Jones <rjones@redhat.com> - 4.11.0-0.3.pre.fc33
- Add fixes for various issues found in the previous build.

View File

@ -1 +1 @@
SHA512 (ocaml-4.11.0.tar.gz) = 3d41e50b73981af1f6d5e51cf1878a2fd54b52a4da434298a48159d48ea66166689c2fb30a8fe6a9e8dd6f4a483009af24e550fb03fa6dc736b6bf37c4534645
SHA512 (ocaml-4.11.0.tar.gz) = b07208b8679ef285f30b2da4070a3cf894cb881b79330e1ee50839fff634e58be1b7c378690658d146d2565ddbfa40aaa12ecec9558d7eab501b1863f50bfc88