Skip to content

Commit

Permalink
flambda-backend: Use C++ name mangling convention (ocaml#483)
Browse files Browse the repository at this point in the history
Co-authored-by: basimkhajwal <basimkhajwal@gmail.com>
Co-authored-by: Mark Shinwell <mshinwell@pm.me>
  • Loading branch information
3 people committed Feb 8, 2022
1 parent 81881bb commit 1010539
Show file tree
Hide file tree
Showing 3 changed files with 51 additions and 1 deletion.
2 changes: 1 addition & 1 deletion testsuite/tests/asmcomp/func_sections.run
Original file line number Diff line number Diff line change
Expand Up @@ -7,4 +7,4 @@ ${program}

# now check the assembly file produced during compilation
asm=${test_build_directory}/func_sections.s
grep ".section .text.caml.camlFunc_sections__" "$asm" | wc -l | tr -d ' ' | sed '/^$/d'
grep -E ".section .text.caml.(camlFunc_sections__|_ZN13Func_sections)" "$asm" | wc -l | tr -d ' ' | sed '/^$/d'
41 changes: 41 additions & 0 deletions utils/misc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -97,6 +97,8 @@ let rec split_last = function

module Stdlib = struct
module List = struct
include List

type 'a t = 'a list

let rec compare cmp l1 l2 =
Expand Down Expand Up @@ -227,6 +229,45 @@ module Stdlib = struct

let print ppf t =
Format.pp_print_string ppf t

let begins_with ?(from = 0) str ~prefix =
let rec helper idx =
if idx < 0 then true
else
String.get str (from + idx) = String.get prefix idx && helper (idx-1)
in
let n = String.length str in
let m = String.length prefix in
if n >= from + m then helper (m-1) else false

let split_on_string str ~split_on =
let n = String.length str in
let m = String.length split_on in
let rec helper acc last_idx idx =
if idx = n then
let cur = String.sub str last_idx (idx - last_idx) in
List.rev (cur :: acc)
else if begins_with ~from:idx str ~prefix:split_on then
let cur = String.sub str last_idx (idx - last_idx) in
helper (cur :: acc) (idx + m) (idx + m)
else
helper acc last_idx (idx + 1)
in
helper [] 0 0

let split_on_chars str ~split_on:chars =
let rec helper chars_left s acc =
match chars_left with
| [] -> s :: acc
| c :: cs ->
List.fold_right (helper cs) (String.split_on_char c s) acc
in
helper chars str []

let split_last_exn str ~split_on =
let n = String.length str in
let ridx = String.rindex str split_on in
String.sub str 0 ridx, String.sub str (ridx + 1) (n - ridx - 1)
end

external compare : 'a -> 'a -> int = "%compare"
Expand Down
9 changes: 9 additions & 0 deletions utils/misc.mli
Original file line number Diff line number Diff line change
Expand Up @@ -173,6 +173,15 @@ module Stdlib : sig
val print : Format.formatter -> t -> unit

val for_all : (char -> bool) -> t -> bool

val begins_with : ?from:int -> string -> prefix:string -> bool

val split_on_string : string -> split_on:string -> string list

val split_on_chars : string -> split_on:char list -> string list

(** Splits on the last occurrence of the given character. *)
val split_last_exn : string -> split_on:char -> string * string
end

external compare : 'a -> 'a -> int = "%compare"
Expand Down

0 comments on commit 1010539

Please sign in to comment.