Skip to content

Commit

Permalink
Merge pull request #239 from ocaml/ps/rr/inline__first__on__tmatch_
Browse files Browse the repository at this point in the history
inline [first] on [TMatch]
  • Loading branch information
vouillon authored Apr 15, 2024
2 parents 4c55716 + 84eaa13 commit 06d35f3
Showing 1 changed file with 9 additions and 27 deletions.
36 changes: 9 additions & 27 deletions lib/automata.ml
Original file line number Diff line number Diff line change
Expand Up @@ -128,17 +128,6 @@ let rec pp ch e =
| After c ->
sexp ch "after" Category.pp c


(****)

let rec first f = function
| [] ->
None
| x :: r ->
match f x with
None -> first f r
| Some _ as res -> res

(****)

type ids = int ref
Expand Down Expand Up @@ -275,6 +264,11 @@ module E = struct
let pp ch t = print_state_lst ch [t] { id = 0; def = Eps }
end

let rec first_match = function
| [] -> None
| (E.TMatch marks) :: _ -> Some marks
| _ :: r -> first_match r

module State = struct
type t =
{ idx: idx
Expand Down Expand Up @@ -410,10 +404,7 @@ let rec delta_1 marks c ~next_cat ~prev_cat x rem =
| Rep (rep_kind, kind, y) ->
let y' = delta_1 marks c ~next_cat ~prev_cat y [] in
let (y'', marks') =
match
first
(function E.TMatch marks -> Some marks | _ -> None) y'
with
match first_match y' with
None -> (y', marks)
| Some marks' -> (remove_matches y', marks')
in
Expand Down Expand Up @@ -444,9 +435,7 @@ and delta_2 marks c ~next_cat ~prev_cat l rem =
(delta_2 marks c ~next_cat ~prev_cat r rem)

and delta_seq c ~next_cat ~prev_cat kind y z rem =
match
first (function E.TMatch marks -> Some marks | _ -> None) y
with
match first_match y with
None ->
E.tseq kind y z rem
| Some marks ->
Expand Down Expand Up @@ -545,11 +534,7 @@ let rec deriv_1 all_chars categories marks cat x rem =
List.fold_right
(fun (s, z) rem ->
let (z', marks') =
match
first
(function E.TMatch marks -> Some marks | _ -> None)
z
with
match first_match z with
None -> (z, marks)
| Some marks' -> (remove_matches z, marks')
in
Expand Down Expand Up @@ -589,10 +574,7 @@ and deriv_seq all_chars categories cat kind y z rem =
let z' = deriv_1 all_chars categories Marks.empty cat z [(all_chars, [])] in
List.fold_right
(fun (s, y) rem ->
match
first (function E.TMatch marks -> Some marks | _ -> None)
y
with
match first_match y with
None ->
Cset.prepend s (E.tseq kind y z []) rem
| Some marks ->
Expand Down

0 comments on commit 06d35f3

Please sign in to comment.