Skip to content

Commit

Permalink
Fix instances where the depreciated Core.Caml is used.
Browse files Browse the repository at this point in the history
Core.Caml is depreciated in favor of Core.Stdlib. In the cases here I just made
it use the Core equivalent functions instead of the ones from the Ocaml stdlib.

This fixes a bunch of compiler warns with new core and does not break users who
may still have the older version.
  • Loading branch information
georgyo committed Jan 15, 2024
1 parent 05ee37a commit 5ac138c
Show file tree
Hide file tree
Showing 5 changed files with 12 additions and 12 deletions.
10 changes: 5 additions & 5 deletions exercises/practice/word-count/.meta/example.ml
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ type position =
| Start
| End

let quote_at s ~pos =
let quote_at s ~pos =
let p = match pos with
| Start -> 0
| End -> String.length s - 1
Expand All @@ -20,12 +20,12 @@ let quote_at s ~pos =

let word_count s =
let s = String.map s ~f:normalize in
let split =
let split =
List.filter (String.split s ~on:' ') ~f:(Fn.non String.is_empty)
|> List.map ~f:(fun w ->
|> List.map ~f:(fun w ->
let len = String.length w in
if len >= 2 && quote_at w ~pos:Start && quote_at w ~pos:End
then Caml.String.sub w 1 (len - 2)
if len >= 2 && quote_at w ~pos:Start && quote_at w ~pos:End
then String.sub w ~pos:1 ~len:(len - 2)
else w)
in
List.fold ~init:(Map.empty (module String)) ~f:add_to_map split
2 changes: 1 addition & 1 deletion test-generator/bin_test_gen/test_gen.ml
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ let command =
let cwd =
flag_optional_with_default_doc "w" string Sexp.of_string
~aliases:["--cwd"]
~default:(Caml.Sys.getcwd ()) ~doc:"directory to assume as cwd"
~default:(Core_unix.getcwd ()) ~doc:"directory to assume as cwd"
and templates_folder =
flag_optional_with_default_doc "t" string Sexp.of_string
~aliases:["--templates"]
Expand Down
2 changes: 1 addition & 1 deletion test-generator/lib_generator/exercise.ml
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ let of_candidate ~(tpl: string) ~(out: string) (c: Exercise_candidate.t): t =
let to_string (e: t): string =
let print_description = function
| None -> "None"
| Some d -> Caml.Printf.sprintf "%s" d
| Some d -> Printf.sprintf "%s" d
in
Printf.sprintf "ExerciseCandidate { name = \"%s\"; directory = \"%s\"; description = \"%s\"; canonical_data = %s; templates = %s }"
e.name
Expand Down
4 changes: 2 additions & 2 deletions test-generator/lib_generator/files.ml
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ let mkdir_if_not_present dir =

let backup ~(base_folder: string) ~(slug: string) ~(contents: string): bool =
mkdir_if_not_present base_folder;
let path = Caml.Filename.concat base_folder slug in
let path = Filename.concat base_folder slug in
let matches_contents =
Option.try_with (fun () -> In_channel.read_all path)
|> Option.map ~f:(String.equal contents)
Expand Down Expand Up @@ -88,7 +88,7 @@ let read_file (p: string): (string, exn) Result.t =
try
let c = Stdio.In_channel.create p in
while true do
Buffer.add_string b (Caml.input_line c);
Buffer.add_string b (In_channel.input_line_exn c);
Buffer.add_char b '\n';
done;
failwith "unreachable"
Expand Down
6 changes: 3 additions & 3 deletions test-generator/lib_generator/glob.ml
Original file line number Diff line number Diff line change
Expand Up @@ -4,11 +4,11 @@ let split c s =
let len = String.length s in
let rec loop acc last_pos pos =
if pos = -1 then
Caml.String.sub s 0 last_pos :: acc
String.sub s ~pos:0 ~len:last_pos :: acc
else
if Char.equal (String.get s pos) c then
let pos1 = pos + 1 in
let sub_str = Caml.String.sub s pos1 (last_pos - pos1) in
let sub_str = String.sub s ~pos:pos1 ~len:(last_pos - pos1) in
loop (sub_str :: acc) pos (pos - 1)
else loop acc last_pos (pos - 1)
in
Expand All @@ -21,7 +21,7 @@ let find_substrings ?(start_point=0) substr x =
if len_x - i < len_s
then acc
else
if String.equal (Caml.String.sub x i len_s) substr
if String.equal (String.sub x ~pos:i ~len:len_s) substr
then aux (i::acc) (i + 1)
else aux acc (i + 1)
in
Expand Down

0 comments on commit 5ac138c

Please sign in to comment.