Skip to content

Commit c54da76

Browse files
Merge pull request #9858 from Leonidas-from-XIV/update-re
chore: Update re
2 parents e86d9f8 + 7d2e6a1 commit c54da76

File tree

18 files changed

+742
-289
lines changed

18 files changed

+742
-289
lines changed

src/dune_patch/dune_patch.ml

Lines changed: 1 addition & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,5 @@
11
open Stdune
2-
3-
module Re = struct
4-
include Dune_re
5-
6-
module Group = struct
7-
include Group
8-
9-
let get_opt group n = if Group.test group n then Some (get group n) else None
10-
end
11-
end
2+
module Re = Dune_re
123

134
include struct
145
open Dune_engine

vendor/re/src/automata.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -254,11 +254,11 @@ module E = struct
254254
| TSeq (l', x, _kind) ->
255255
Format.fprintf ch "@[<2>(Seq@ ";
256256
print_state_lst ch l' x;
257-
Format.fprintf ch " %a)@]" pp x
257+
Format.fprintf ch "@ %a)@]" pp x
258258
| TExp (marks, {def = Eps; _}) ->
259-
Format.fprintf ch "(Exp %d (%a) (eps))" y.id Marks.pp_marks marks
259+
Format.fprintf ch "@[<2>(Exp@ %d@ (%a)@ (eps))@]" y.id Marks.pp_marks marks
260260
| TExp (marks, x) ->
261-
Format.fprintf ch "(Exp %d (%a) %a)" x.id Marks.pp_marks marks pp x
261+
Format.fprintf ch "@[<2>(Exp@ %d@ (%a)@ %a)@]" x.id Marks.pp_marks marks pp x
262262

263263
and print_state_lst ch l y =
264264
match l with
@@ -268,7 +268,7 @@ module E = struct
268268
print_state_rec ch e y;
269269
List.iter
270270
(fun e ->
271-
Format.fprintf ch " | ";
271+
Format.fprintf ch "@ | ";
272272
print_state_rec ch e y)
273273
rem
274274

vendor/re/src/color_map.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ let flatten cm =
2424
Bytes.set c i (Char.chr !v);
2525
Bytes.set color_repr !v (Char.chr i)
2626
done;
27-
(c, Bytes.sub color_repr 0 (!v + 1), !v + 1)
27+
(Bytes.unsafe_to_string c, Bytes.sub_string color_repr 0 (!v + 1), !v + 1)
2828

2929
(* mark all the endpoints of the intervals of the char set with the 1 byte *)
3030
let split s cm =

vendor/re/src/color_map.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,6 @@ type t
99

1010
val make : unit -> t
1111

12-
val flatten : t -> bytes * bytes * int
12+
val flatten : t -> string * string * int
1313

1414
val split : Cset.t -> t -> unit

0 commit comments

Comments
 (0)