New upstream version 4.14.0
This commit is contained in:
		
							parent
							
								
									4bb2864cc2
								
							
						
					
					
						commit
						73c8e3d782
					
				
							
								
								
									
										192
									
								
								0001-Do-not-trigger-warning-when-calling-virtual-methods-.patch
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										192
									
								
								0001-Do-not-trigger-warning-when-calling-virtual-methods-.patch
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,192 @@ | ||||
| From 3f6a90f1ac47c480522a009d6ea56e2acfb7112f Mon Sep 17 00:00:00 2001 | ||||
| From: =?UTF-8?q?Nicol=C3=A1s=20Ojeda=20B=C3=A4r?= <n.oje.bar@gmail.com> | ||||
| Date: Wed, 27 Apr 2022 14:46:47 +0200 | ||||
| Subject: [PATCH 1/9] Do not trigger warning when calling virtual methods | ||||
|  introduced by constraining "self" (#11204) | ||||
| 
 | ||||
| (cherry picked from commit 1e7af3f6261502bb384dc9e23a74ad0990bfd854) | ||||
| ---
 | ||||
|  Changes                                 | 11 ++++++- | ||||
|  testsuite/tests/typing-objects/Tests.ml | 15 ++++++++++ | ||||
|  typing/typeclass.ml                     | 40 ++++++++++--------------- | ||||
|  3 files changed, 40 insertions(+), 26 deletions(-) | ||||
| 
 | ||||
| diff --git a/Changes b/Changes
 | ||||
| index a8ce94bdc6..931a74b8d1 100644
 | ||||
| --- a/Changes
 | ||||
| +++ b/Changes
 | ||||
| @@ -1,3 +1,13 @@
 | ||||
| +OCaml 4.14 maintenance branch
 | ||||
| +-----------------------------
 | ||||
| +
 | ||||
| +### Bug fixes:
 | ||||
| +
 | ||||
| +- #11204: Fix regression introduced in 4.14.0 that would trigger Warning 17 when
 | ||||
| +  calling virtual methods introduced by constraining the self type from within
 | ||||
| +  the class definition.
 | ||||
| +  (Nicolás Ojeda Bär, review by Leo White)
 | ||||
| +
 | ||||
|  OCaml 4.14.0 (28 March 2022) | ||||
|  ---------------------------- | ||||
|   | ||||
| @@ -62,7 +72,6 @@ OCaml 4.14.0 (28 March 2022)
 | ||||
|    definition-aware operations. | ||||
|    (Ulysse Gérard, Thomas Refis and Leo White, review by Florian Angeletti) | ||||
|   | ||||
| -
 | ||||
|  ### Language features: | ||||
|   | ||||
|  - #10462: Add attribute to produce a compiler error for polls. | ||||
| diff --git a/testsuite/tests/typing-objects/Tests.ml b/testsuite/tests/typing-objects/Tests.ml
 | ||||
| index f617bcf1b9..3dcd87c43c 100644
 | ||||
| --- a/testsuite/tests/typing-objects/Tests.ml
 | ||||
| +++ b/testsuite/tests/typing-objects/Tests.ml
 | ||||
| @@ -955,6 +955,21 @@ Warning 17 [undeclared-virtual-method]: the virtual method m is not declared.
 | ||||
|  class c : object method m : int method n : int end | ||||
|  |}];; | ||||
|   | ||||
| +class virtual c = object (self : 'c)
 | ||||
| +  constraint 'c = < f : int; .. >
 | ||||
| +end
 | ||||
| +[%%expect {|
 | ||||
| +class virtual c : object method virtual f : int end
 | ||||
| +|}];;
 | ||||
| +
 | ||||
| +class virtual c = object (self : 'c)
 | ||||
| +  constraint 'c = < f : int; .. >
 | ||||
| +  method g = self # f
 | ||||
| +end
 | ||||
| +[%%expect {|
 | ||||
| +class virtual c : object method virtual f : int method g : int end
 | ||||
| +|}];;
 | ||||
| +
 | ||||
|  class [ 'a ] c = object (_ : 'a) end;; | ||||
|  let o = object | ||||
|      method m = 1 | ||||
| diff --git a/typing/typeclass.ml b/typing/typeclass.ml
 | ||||
| index 048ee998b0..fedbc0e025 100644
 | ||||
| --- a/typing/typeclass.ml
 | ||||
| +++ b/typing/typeclass.ml
 | ||||
| @@ -552,12 +552,11 @@ type first_pass_accummulater =
 | ||||
|      concrete_vals : VarSet.t; | ||||
|      local_meths : MethSet.t; | ||||
|      local_vals : VarSet.t; | ||||
| -    vars : Ident.t Vars.t;
 | ||||
| -    meths : Ident.t Meths.t; }
 | ||||
| +    vars : Ident.t Vars.t; }
 | ||||
|   | ||||
|  let rec class_field_first_pass self_loc cl_num sign self_scope acc cf = | ||||
|    let { rev_fields; val_env; par_env; concrete_meths; concrete_vals; | ||||
| -        local_meths; local_vals; vars; meths } = acc
 | ||||
| +        local_meths; local_vals; vars } = acc
 | ||||
|    in | ||||
|    let loc = cf.pcf_loc in | ||||
|    let attributes = cf.pcf_attributes in | ||||
| @@ -612,13 +611,6 @@ let rec class_field_first_pass self_loc cl_num sign self_scope acc cf =
 | ||||
|                    (val_env, par_env, inherited_vars, vars)) | ||||
|                 parent_sign.csig_vars (val_env, par_env, [], vars) | ||||
|             in | ||||
| -           let meths =
 | ||||
| -             Meths.fold
 | ||||
| -               (fun label _ meths ->
 | ||||
| -                  if Meths.mem label meths then meths
 | ||||
| -                  else Meths.add label (Ident.create_local label) meths)
 | ||||
| -               parent_sign.csig_meths meths
 | ||||
| -           in
 | ||||
|             (* Methods available through super *) | ||||
|             let super_meths = | ||||
|               MethSet.fold | ||||
| @@ -641,7 +633,7 @@ let rec class_field_first_pass self_loc cl_num sign self_scope acc cf =
 | ||||
|             in | ||||
|             let rev_fields = field :: rev_fields in | ||||
|             { acc with rev_fields; val_env; par_env; | ||||
| -                      concrete_meths; concrete_vals; vars; meths })
 | ||||
| +                      concrete_meths; concrete_vals; vars })
 | ||||
|    | Pcf_val (label, mut, Cfk_virtual styp) -> | ||||
|        with_attrs | ||||
|          (fun () -> | ||||
| @@ -723,15 +715,11 @@ let rec class_field_first_pass self_loc cl_num sign self_scope acc cf =
 | ||||
|             let cty = transl_simple_type val_env false sty in | ||||
|             let ty = cty.ctyp_type in | ||||
|             add_method loc val_env label.txt priv Virtual ty sign; | ||||
| -           let meths =
 | ||||
| -             if Meths.mem label.txt meths then meths
 | ||||
| -             else Meths.add label.txt (Ident.create_local label.txt) meths
 | ||||
| -           in
 | ||||
|             let field = | ||||
|               Virtual_method { label; priv; cty; loc; attributes } | ||||
|             in | ||||
|             let rev_fields = field :: rev_fields in | ||||
| -           { acc with rev_fields; meths })
 | ||||
| +           { acc with rev_fields })
 | ||||
|   | ||||
|    | Pcf_method (label, priv, Cfk_concrete (override, expr)) -> | ||||
|        with_attrs | ||||
| @@ -785,10 +773,6 @@ let rec class_field_first_pass self_loc cl_num sign self_scope acc cf =
 | ||||
|                 raise(Error(loc, val_env, | ||||
|                             Field_type_mismatch ("method", label.txt, err))) | ||||
|             end; | ||||
| -           let meths =
 | ||||
| -             if Meths.mem label.txt meths then meths
 | ||||
| -             else Meths.add label.txt (Ident.create_local label.txt) meths
 | ||||
| -           in
 | ||||
|             let sdefinition = make_method self_loc cl_num expr in | ||||
|             let warning_state = Warnings.backup () in | ||||
|             let field = | ||||
| @@ -799,7 +783,7 @@ let rec class_field_first_pass self_loc cl_num sign self_scope acc cf =
 | ||||
|             let rev_fields = field :: rev_fields in | ||||
|             let concrete_meths = MethSet.add label.txt concrete_meths in | ||||
|             let local_meths = MethSet.add label.txt local_meths in | ||||
| -           { acc with rev_fields; concrete_meths; local_meths; meths })
 | ||||
| +           { acc with rev_fields; concrete_meths; local_meths })
 | ||||
|   | ||||
|    | Pcf_constraint (sty1, sty2) -> | ||||
|        with_attrs | ||||
| @@ -837,11 +821,10 @@ and class_fields_first_pass self_loc cl_num sign self_scope
 | ||||
|    let local_meths = MethSet.empty in | ||||
|    let local_vals = VarSet.empty in | ||||
|    let vars = Vars.empty in | ||||
| -  let meths = Meths.empty in
 | ||||
|    let init_acc = | ||||
|      { rev_fields; val_env; par_env; | ||||
|        concrete_meths; concrete_vals; | ||||
| -      local_meths; local_vals; vars; meths }
 | ||||
| +      local_meths; local_vals; vars }
 | ||||
|    in | ||||
|    let acc = | ||||
|      Builtin_attributes.warning_scope [] | ||||
| @@ -850,7 +833,7 @@ and class_fields_first_pass self_loc cl_num sign self_scope
 | ||||
|            (class_field_first_pass self_loc cl_num sign self_scope) | ||||
|            init_acc cfs) | ||||
|    in | ||||
| -  List.rev acc.rev_fields, acc.vars, acc.meths
 | ||||
| +  List.rev acc.rev_fields, acc.vars
 | ||||
|   | ||||
|  and class_field_second_pass cl_num sign met_env field = | ||||
|    let mkcf desc loc attrs = | ||||
| @@ -1003,7 +986,7 @@ and class_structure cl_num virt self_scope final val_env met_env loc
 | ||||
|    end; | ||||
|   | ||||
|    (* Typing of class fields *) | ||||
| -  let (fields, vars, meths) =
 | ||||
| +  let (fields, vars) =
 | ||||
|      class_fields_first_pass self_loc cl_num sign self_scope | ||||
|             val_env par_env str | ||||
|    in | ||||
| @@ -1016,6 +999,13 @@ and class_structure cl_num virt self_scope final val_env met_env loc
 | ||||
|    update_class_signature loc val_env | ||||
|      ~warn_implicit_public:false virt kind sign; | ||||
|   | ||||
| +  let meths =
 | ||||
| +    Meths.fold
 | ||||
| +      (fun label _ meths ->
 | ||||
| +         Meths.add label (Ident.create_local label) meths)
 | ||||
| +      sign.csig_meths Meths.empty
 | ||||
| +  in
 | ||||
| +
 | ||||
|    (* Close the signature if it is final *) | ||||
|    begin match final with | ||||
|    | Not_final -> () | ||||
| -- 
 | ||||
| 2.36.1 | ||||
| 
 | ||||
| @ -0,0 +1,43 @@ | ||||
| From 538cb5217642b36a8eab1ae027767c344e880b4b Mon Sep 17 00:00:00 2001 | ||||
| From: David Allsopp <david.allsopp@metastack.com> | ||||
| Date: Thu, 5 May 2022 20:01:44 +0100 | ||||
| Subject: [PATCH 2/9] Merge pull request #11236 from Nymphium/missing-since2 | ||||
| 
 | ||||
| Add missing @since annotation to Gc.eventlog_pause | ||||
| 
 | ||||
| (cherry picked from commit 77fee6035c25d8a31084dc556ee634e46bb39164) | ||||
| ---
 | ||||
|  stdlib/gc.mli | 10 ++++++++-- | ||||
|  1 file changed, 8 insertions(+), 2 deletions(-) | ||||
| 
 | ||||
| diff --git a/stdlib/gc.mli b/stdlib/gc.mli
 | ||||
| index b211197fd4..8031eeb8df 100644
 | ||||
| --- a/stdlib/gc.mli
 | ||||
| +++ b/stdlib/gc.mli
 | ||||
| @@ -442,7 +442,10 @@ external eventlog_pause : unit -> unit = "caml_eventlog_pause"
 | ||||
|     Traces are collected if the program is linked to the instrumented runtime | ||||
|     and started with the environment variable OCAML_EVENTLOG_ENABLED. | ||||
|     Events are flushed to disk after pausing, and no new events will be | ||||
| -   recorded until [eventlog_resume] is called. *)
 | ||||
| +   recorded until [eventlog_resume] is called.
 | ||||
| +
 | ||||
| +   @since 4.11
 | ||||
| +  *)
 | ||||
|   | ||||
|  external eventlog_resume : unit -> unit = "caml_eventlog_resume" | ||||
|  (** [eventlog_resume ()] will resume the collection of traces in the | ||||
| @@ -451,7 +454,10 @@ external eventlog_resume : unit -> unit = "caml_eventlog_resume"
 | ||||
|     and started with the environment variable OCAML_EVENTLOG_ENABLED. | ||||
|     This call can be used after calling [eventlog_pause], or if the program | ||||
|     was started with OCAML_EVENTLOG_ENABLED=p. (which pauses the collection of | ||||
| -   traces before the first event.) *)
 | ||||
| +   traces before the first event.)
 | ||||
| +
 | ||||
| +   @since 4.11
 | ||||
| +  *)
 | ||||
|   | ||||
|   | ||||
|  (** [Memprof] is a sampling engine for allocated memory words. Every | ||||
| -- 
 | ||||
| 2.36.1 | ||||
| 
 | ||||
							
								
								
									
										26
									
								
								0003-misc.h-fix-preprocessor-conditional-on-_MSC_VER.patch
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										26
									
								
								0003-misc.h-fix-preprocessor-conditional-on-_MSC_VER.patch
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,26 @@ | ||||
| From c06ca224780f005b625ef406a817ead3eb9a8665 Mon Sep 17 00:00:00 2001 | ||||
| From: =?UTF-8?q?Nicol=C3=A1s=20Ojeda=20B=C3=A4r?= <n.oje.bar@gmail.com> | ||||
| Date: Tue, 17 May 2022 10:21:34 +0200 | ||||
| Subject: [PATCH 3/9] misc.h: fix preprocessor conditional on _MSC_VER | ||||
| 
 | ||||
| (cherry picked from commit 253d605e10865371aed45967a94caed0642b7583) | ||||
| ---
 | ||||
|  runtime/caml/misc.h | 2 +- | ||||
|  1 file changed, 1 insertion(+), 1 deletion(-) | ||||
| 
 | ||||
| diff --git a/runtime/caml/misc.h b/runtime/caml/misc.h
 | ||||
| index 5915c30a7b..494d45e8f8 100644
 | ||||
| --- a/runtime/caml/misc.h
 | ||||
| +++ b/runtime/caml/misc.h
 | ||||
| @@ -35,7 +35,7 @@
 | ||||
|    /* Supported since at least GCC 3.1 */ | ||||
|    #define CAMLdeprecated_typedef(name, type) \ | ||||
|      typedef type name __attribute ((deprecated)) | ||||
| -#elif _MSC_VER >= 1310
 | ||||
| +#elif defined(_MSC_VER) && _MSC_VER >= 1310
 | ||||
|    /* NB deprecated("message") only supported from _MSC_VER >= 1400 */ | ||||
|    #define CAMLdeprecated_typedef(name, type) \ | ||||
|      typedef __declspec(deprecated) type name | ||||
| -- 
 | ||||
| 2.36.1 | ||||
| 
 | ||||
							
								
								
									
										28
									
								
								0004-Changes.patch
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										28
									
								
								0004-Changes.patch
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,28 @@ | ||||
| From bfb9a2157c50c1b4a9cb8dc0319fe375b5e80b1d Mon Sep 17 00:00:00 2001 | ||||
| From: =?UTF-8?q?Nicol=C3=A1s=20Ojeda=20B=C3=A4r?= <n.oje.bar@gmail.com> | ||||
| Date: Tue, 17 May 2022 14:45:26 +0200 | ||||
| Subject: [PATCH 4/9] Changes | ||||
| 
 | ||||
| (cherry picked from commit 9a157026f115364635f8fe0ae5805e15ef071de0) | ||||
| ---
 | ||||
|  Changes | 4 ++++ | ||||
|  1 file changed, 4 insertions(+) | ||||
| 
 | ||||
| diff --git a/Changes b/Changes
 | ||||
| index 931a74b8d1..fdfffd78bb 100644
 | ||||
| --- a/Changes
 | ||||
| +++ b/Changes
 | ||||
| @@ -8,6 +8,10 @@ OCaml 4.14 maintenance branch
 | ||||
|    the class definition. | ||||
|    (Nicolás Ojeda Bär, review by Leo White) | ||||
|   | ||||
| +- #11263: caml/misc.h: check whether `_MSC_VER` is defined before using it. This
 | ||||
| +  could break the build of the compiler on non-gcc non-clang Unix builds.
 | ||||
| +  (Nicolás Ojeda Bär, review by Sebastien Hinderer)
 | ||||
| +
 | ||||
|  OCaml 4.14.0 (28 March 2022) | ||||
|  ---------------------------- | ||||
|   | ||||
| -- 
 | ||||
| 2.36.1 | ||||
| 
 | ||||
							
								
								
									
										93
									
								
								0005-Guard-more-instances-of-undefined-_MSC_VER.patch
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										93
									
								
								0005-Guard-more-instances-of-undefined-_MSC_VER.patch
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,93 @@ | ||||
| From 53ce1f582e37faabfd616a0b09521497e2e7ef14 Mon Sep 17 00:00:00 2001 | ||||
| From: David Allsopp <david.allsopp@metastack.com> | ||||
| Date: Wed, 18 May 2022 12:48:33 +0100 | ||||
| Subject: [PATCH 5/9] Guard more instances of undefined _MSC_VER | ||||
| 
 | ||||
| ---
 | ||||
|  Changes               |  8 +++++--- | ||||
|  runtime/caml/memory.h |  2 +- | ||||
|  runtime/caml/misc.h   | 12 +++++++----- | ||||
|  3 files changed, 13 insertions(+), 9 deletions(-) | ||||
| 
 | ||||
| diff --git a/Changes b/Changes
 | ||||
| index fdfffd78bb..590268262d 100644
 | ||||
| --- a/Changes
 | ||||
| +++ b/Changes
 | ||||
| @@ -8,9 +8,11 @@ OCaml 4.14 maintenance branch
 | ||||
|    the class definition. | ||||
|    (Nicolás Ojeda Bär, review by Leo White) | ||||
|   | ||||
| -- #11263: caml/misc.h: check whether `_MSC_VER` is defined before using it. This
 | ||||
| -  could break the build of the compiler on non-gcc non-clang Unix builds.
 | ||||
| -  (Nicolás Ojeda Bär, review by Sebastien Hinderer)
 | ||||
| +- #11263, #11267: caml/{memory,misc}.h: check whether `_MSC_VER` is defined
 | ||||
| +  before using it to ensure that the headers can always be used in code which
 | ||||
| +  turns on -Wundef (or equivalent).
 | ||||
| +  (David Allsopp and Nicolás Ojeda Bär, review by Nicolás Ojeda Bär and
 | ||||
| +   Sebastien Hinderer)
 | ||||
|   | ||||
|  OCaml 4.14.0 (28 March 2022) | ||||
|  ---------------------------- | ||||
| diff --git a/runtime/caml/memory.h b/runtime/caml/memory.h
 | ||||
| index 1e9cdf6d9b..d9e58bc2d0 100644
 | ||||
| --- a/runtime/caml/memory.h
 | ||||
| +++ b/runtime/caml/memory.h
 | ||||
| @@ -329,7 +329,7 @@ struct caml__roots_block {
 | ||||
|    #define CAMLunused_start __attribute__ ((unused)) | ||||
|    #define CAMLunused_end | ||||
|    #define CAMLunused __attribute__ ((unused)) | ||||
| -#elif _MSC_VER >= 1500
 | ||||
| +#elif defined(_MSC_VER) && _MSC_VER >= 1500
 | ||||
|    #define CAMLunused_start  __pragma( warning (push) )           \ | ||||
|      __pragma( warning (disable:4189 ) ) | ||||
|    #define CAMLunused_end __pragma( warning (pop)) | ||||
| diff --git a/runtime/caml/misc.h b/runtime/caml/misc.h
 | ||||
| index 494d45e8f8..c605f8711e 100644
 | ||||
| --- a/runtime/caml/misc.h
 | ||||
| +++ b/runtime/caml/misc.h
 | ||||
| @@ -43,7 +43,8 @@
 | ||||
|    #define CAMLdeprecated_typedef(name, type) typedef type name | ||||
|  #endif | ||||
|   | ||||
| -#if defined(__GNUC__) && __STDC_VERSION__ >= 199901L || _MSC_VER >= 1925
 | ||||
| +#if defined(__GNUC__) && __STDC_VERSION__ >= 199901L \
 | ||||
| + || defined(_MSC_VER) && _MSC_VER >= 1925
 | ||||
|   | ||||
|  #define CAML_STRINGIFY(x) #x | ||||
|  #ifdef _MSC_VER | ||||
| @@ -90,7 +91,7 @@ CAMLdeprecated_typedef(addr, char *);
 | ||||
|    #define CAMLnoreturn_start | ||||
|    #define CAMLnoreturn_end __attribute__ ((noreturn)) | ||||
|    #define Noreturn __attribute__ ((noreturn)) | ||||
| -#elif _MSC_VER >= 1500
 | ||||
| +#elif defined(_MSC_VER) && _MSC_VER >= 1500
 | ||||
|    #define CAMLnoreturn_start __declspec(noreturn) | ||||
|    #define CAMLnoreturn_end | ||||
|    #define Noreturn | ||||
| @@ -138,11 +139,12 @@ CAMLdeprecated_typedef(addr, char *);
 | ||||
|  /* we need to be able to compute the exact offset of each member. */ | ||||
|  #if defined(__STDC_VERSION__) && __STDC_VERSION__ >= 201112L | ||||
|  #define CAMLalign(n) _Alignas(n) | ||||
| -#elif defined(__cplusplus) && (__cplusplus >= 201103L || _MSC_VER >= 1900)
 | ||||
| +#elif defined(__cplusplus) \
 | ||||
| +   && (__cplusplus >= 201103L || defined(_MSC_VER) && _MSC_VER >= 1900)
 | ||||
|  #define CAMLalign(n) alignas(n) | ||||
|  #elif defined(SUPPORTS_ALIGNED_ATTRIBUTE) | ||||
|  #define CAMLalign(n) __attribute__((aligned(n))) | ||||
| -#elif _MSC_VER >= 1500
 | ||||
| +#elif defined(_MSC_VER) && _MSC_VER >= 1500
 | ||||
|  #define CAMLalign(n) __declspec(align(n)) | ||||
|  #else | ||||
|  #error "How do I align values on this platform?" | ||||
| @@ -170,7 +172,7 @@ CAMLdeprecated_typedef(addr, char *);
 | ||||
|    #define CAMLunused_start __attribute__ ((unused)) | ||||
|    #define CAMLunused_end | ||||
|    #define CAMLunused __attribute__ ((unused)) | ||||
| -#elif _MSC_VER >= 1500
 | ||||
| +#elif defined(_MSC_VER) && _MSC_VER >= 1500
 | ||||
|    #define CAMLunused_start  __pragma( warning (push) )           \ | ||||
|      __pragma( warning (disable:4189 ) ) | ||||
|    #define CAMLunused_end __pragma( warning (pop)) | ||||
| -- 
 | ||||
| 2.36.1 | ||||
| 
 | ||||
| @ -1,14 +1,14 @@ | ||||
| From 23f2e84d360208759c7d82b7ff795770ce6cf0b2 Mon Sep 17 00:00:00 2001 | ||||
| From fc7eb8e75bee1b8bf12dcbb7787781169b260558 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/4] Don't add rpaths to libraries. | ||||
| Subject: [PATCH 6/9] Don't add rpaths to libraries. | ||||
| 
 | ||||
| ---
 | ||||
|  utils/config.mlp | 4 ++-- | ||||
|  1 file changed, 2 insertions(+), 2 deletions(-) | ||||
| 
 | ||||
| diff --git a/utils/config.mlp b/utils/config.mlp
 | ||||
| index bbb3c5694..57d509cd0 100644
 | ||||
| index 44c6ff8fa5..a12c31a2bd 100644
 | ||||
| --- a/utils/config.mlp
 | ||||
| +++ b/utils/config.mlp
 | ||||
| @@ -55,8 +55,8 @@ let native_c_compiler =
 | ||||
| @ -23,5 +23,5 @@ index bbb3c5694..57d509cd0 100644 | ||||
|  let supports_shared_libraries = %%SUPPORTS_SHARED_LIBRARIES%% | ||||
|  let mkdll, mkexe, mkmaindll = | ||||
| -- 
 | ||||
| 2.32.0 | ||||
| 2.36.1 | ||||
| 
 | ||||
| @ -1,17 +1,17 @@ | ||||
| From 9966786a7389dc6621f2bc2dce7c690c5a38b67d Mon Sep 17 00:00:00 2001 | ||||
| From b91178cc8fdf657933c26d54a0c67fd69eb67427 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/4] configure: Allow user defined C compiler flags. | ||||
| Subject: [PATCH 7/9] configure: Allow user defined C compiler flags. | ||||
| 
 | ||||
| ---
 | ||||
|  configure.ac | 4 ++++ | ||||
|  1 file changed, 4 insertions(+) | ||||
| 
 | ||||
| diff --git a/configure.ac b/configure.ac
 | ||||
| index 3698c7cbf..e2a3cbea0 100644
 | ||||
| index 2f4ebf9b30..5ccfe8fb01 100644
 | ||||
| --- a/configure.ac
 | ||||
| +++ b/configure.ac
 | ||||
| @@ -669,6 +669,10 @@ AS_CASE([$host],
 | ||||
| @@ -690,6 +690,10 @@ AS_CASE([$host],
 | ||||
|        internal_cflags="$cc_warnings"], | ||||
|      [common_cflags="-O"])]) | ||||
|   | ||||
| @ -23,5 +23,5 @@ index 3698c7cbf..e2a3cbea0 100644 | ||||
|   | ||||
|  # Enable SSE2 on x86 mingw to avoid using 80-bit registers. | ||||
| -- 
 | ||||
| 2.32.0 | ||||
| 2.36.1 | ||||
| 
 | ||||
| @ -1,7 +1,7 @@ | ||||
| From 5eff09224929f8fa1a2e19f9a15befd3a4a395ea Mon Sep 17 00:00:00 2001 | ||||
| From 41d5e2db7a4667560d6aedda11a3c6a80c8f1b83 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/4] configure: Remove incorrect assumption about | ||||
| Subject: [PATCH 8/9] configure: Remove incorrect assumption about | ||||
|  cross-compiling. | ||||
| 
 | ||||
| See https://github.com/ocaml/ocaml/issues/8647#issuecomment-487094390 | ||||
| @ -14,10 +14,10 @@ sh: line 1: x86_64-pc-linux-gnu-as: command not found | ||||
|  1 file changed, 16 insertions(+), 15 deletions(-) | ||||
| 
 | ||||
| diff --git a/configure.ac b/configure.ac
 | ||||
| index e2a3cbea0..07c005f09 100644
 | ||||
| index 5ccfe8fb01..c763310acb 100644
 | ||||
| --- a/configure.ac
 | ||||
| +++ b/configure.ac
 | ||||
| @@ -560,10 +560,11 @@ AS_IF(
 | ||||
| @@ -578,10 +578,11 @@ AS_IF(
 | ||||
|   | ||||
|  # Are we building a cross-compiler | ||||
|   | ||||
| @ -33,7 +33,7 @@ index e2a3cbea0..07c005f09 100644 | ||||
|   | ||||
|  # Checks for programs | ||||
|   | ||||
| @@ -1186,17 +1187,17 @@ AS_CASE([$arch],
 | ||||
| @@ -1212,17 +1213,17 @@ AS_CASE([$arch],
 | ||||
|   | ||||
|  # Assembler | ||||
|   | ||||
| @ -63,5 +63,5 @@ index e2a3cbea0..07c005f09 100644 | ||||
|  # Finding the assembler | ||||
|  # The OCaml build system distinguishes two different assemblers: | ||||
| -- 
 | ||||
| 2.32.0 | ||||
| 2.36.1 | ||||
| 
 | ||||
| @ -1,7 +1,7 @@ | ||||
| From acb5dbaa8f8ece825a48814024404a1a6c5ba7b2 Mon Sep 17 00:00:00 2001 | ||||
| From 05b882737e0daecb86a6ef54e192508c60efcd88 Mon Sep 17 00:00:00 2001 | ||||
| From: "Richard W.M. Jones" <rjones@redhat.com> | ||||
| Date: Wed, 26 Jan 2022 15:47:02 +0000 | ||||
| Subject: [PATCH 4/4] configure: Only use OC_* for building executables | ||||
| Subject: [PATCH 9/9] configure: Only use OC_* for building executables | ||||
| 
 | ||||
| Fedora >= 36 fills LD_FLAGS with lots of cruft, particularly stuff for | ||||
| "package notes" which contains build paths. | ||||
| @ -14,10 +14,10 @@ ocamlopt uses. | ||||
|  1 file changed, 1 insertion(+), 1 deletion(-) | ||||
| 
 | ||||
| diff --git a/configure.ac b/configure.ac
 | ||||
| index 07c005f09..19fe3fd1b 100644
 | ||||
| index c763310acb..9cce5ea47a 100644
 | ||||
| --- a/configure.ac
 | ||||
| +++ b/configure.ac
 | ||||
| @@ -43,7 +43,7 @@ libraries_man_section=3
 | ||||
| @@ -37,7 +37,7 @@ CONFIGURE_ARGS="$*"
 | ||||
|  # at the moment they are not taken into account on Windows, because | ||||
|  # flexlink, which is used to build executables on this platform, can | ||||
|  # not handle them. | ||||
| @ -27,5 +27,5 @@ index 07c005f09..19fe3fd1b 100644 | ||||
|  # Flags for building executable files with debugging symbols | ||||
|  mkexedebugflag="-g" | ||||
| -- 
 | ||||
| 2.32.0 | ||||
| 2.36.1 | ||||
| 
 | ||||
							
								
								
									
										28
									
								
								ocaml.spec
									
									
									
									
									
								
							
							
						
						
									
										28
									
								
								ocaml.spec
									
									
									
									
									
								
							| @ -33,8 +33,8 @@ | ||||
| %global rcver %{nil} | ||||
| 
 | ||||
| Name:           ocaml | ||||
| Version:        4.13.1 | ||||
| Release:        4%{?dist} | ||||
| Version:        4.14.0 | ||||
| Release:        1%{?dist} | ||||
| 
 | ||||
| Summary:        OCaml compiler and programming environment | ||||
| 
 | ||||
| @ -53,16 +53,23 @@ Source0:        https://github.com/ocaml/ocaml/archive/%{version}/%{name}-%{vers | ||||
| # | ||||
| # https://pagure.io/fedora-ocaml | ||||
| # | ||||
| # Current branch: fedora-36-4.13.1 | ||||
| # Current branch: fedora-37-4.14.0 | ||||
| # | ||||
| # 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. | ||||
| 
 | ||||
| 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-configure-Only-use-OC_-for-building-executables.patch | ||||
| # Patches added after 4.14.0 was released | ||||
| Patch0001:      0001-Do-not-trigger-warning-when-calling-virtual-methods-.patch | ||||
| Patch0002:      0002-Merge-pull-request-11236-from-Nymphium-missing-since.patch | ||||
| Patch0003:      0003-misc.h-fix-preprocessor-conditional-on-_MSC_VER.patch | ||||
| Patch0004:      0004-Changes.patch | ||||
| Patch0005:      0005-Guard-more-instances-of-undefined-_MSC_VER.patch | ||||
| # Fedora-specific patches | ||||
| Patch0006:      0006-Don-t-add-rpaths-to-libraries.patch | ||||
| Patch0007:      0007-configure-Allow-user-defined-C-compiler-flags.patch | ||||
| Patch0008:      0008-configure-Remove-incorrect-assumption-about-cross-co.patch | ||||
| Patch0009:      0009-configure-Only-use-OC_-for-building-executables.patch | ||||
| 
 | ||||
| BuildRequires:  make | ||||
| BuildRequires:  git | ||||
| @ -228,7 +235,8 @@ perl -pi -e "s|^$RPM_BUILD_ROOT||" $RPM_BUILD_ROOT%{_libdir}/ocaml/ld.conf | ||||
| 
 | ||||
| echo %{version} > $RPM_BUILD_ROOT%{_libdir}/ocaml/fedora-ocaml-release | ||||
| 
 | ||||
| find $RPM_BUILD_ROOT -name .ignore -delete | ||||
| # Remove the installed documentation.  We will install it using %%doc | ||||
| rm -rf $RPM_BUILD_ROOT%{_docdir}/ocaml | ||||
| 
 | ||||
| # Remove this file.  It's only created in certain situations and it's | ||||
| # unclear why it is created at all. | ||||
| @ -291,7 +299,6 @@ rm -f $RPM_BUILD_ROOT%{_libdir}/ocaml/eventlog_metadata | ||||
| %{_libdir}/ocaml/camlheader | ||||
| %{_libdir}/ocaml/camlheader_ur | ||||
| %{_libdir}/ocaml/expunge | ||||
| %{_libdir}/ocaml/extract_crc | ||||
| %{_libdir}/ocaml/ld.conf | ||||
| %{_libdir}/ocaml/Makefile.config | ||||
| %{_libdir}/ocaml/*.a | ||||
| @ -371,6 +378,9 @@ rm -f $RPM_BUILD_ROOT%{_libdir}/ocaml/eventlog_metadata | ||||
| 
 | ||||
| 
 | ||||
| %changelog | ||||
| * Sat Jun 18 2022 Richard W.M. Jones <rjones@redhat.com> - 4.14.0-1 | ||||
| - New upstream version 4.14.0 | ||||
| 
 | ||||
| * Thu Jun  9 2022 Jerry James <loganjerry@gmail.com> - 4.13.1-4 | ||||
| - Fix the Source0 URL | ||||
| - chrpath is no longer needed | ||||
|  | ||||
							
								
								
									
										2
									
								
								sources
									
									
									
									
									
								
							
							
						
						
									
										2
									
								
								sources
									
									
									
									
									
								
							| @ -1 +1 @@ | ||||
| SHA512 (ocaml-4.13.1.tar.gz) = da3434177438c852da53c0fda7bc2519adcda6384d97d45e44137ed0fd384ffb3da61958a7b51296edb3f88f5a5310ca71b6862f6d756aaa4012d1f54e5955f6 | ||||
| SHA512 (ocaml-4.14.0.tar.gz) = 3c5e5b9f00bb109dd99b5f7b0078cf8663d4247e548f3e601d6b2a55582e04bb20f6de85005c4cf2f78ae9aaa449f5ca6f2bab2f6ce83eeb3aeb386e3f2fcc32 | ||||
|  | ||||
		Loading…
	
		Reference in New Issue
	
	Block a user