Skip to content

Commit

Permalink
refactor: split E.texp into two simpler constructors (#503)
Browse files Browse the repository at this point in the history
  • Loading branch information
rgrinberg authored Sep 28, 2024
1 parent 891ad90 commit 2660ca2
Showing 1 changed file with 7 additions and 5 deletions.
12 changes: 7 additions & 5 deletions lib/automata.ml
Original file line number Diff line number Diff line change
Expand Up @@ -339,18 +339,21 @@ module E : sig
val equal_list : t list -> t list -> bool
val compare : t -> t -> int
val hash_list : t list -> int -> int
val texp : Marks.t -> Expr.t -> t
val is_tmatch : t -> bool
val tseq' : Sem.t -> t list -> Expr.t -> t list
val tseq : Sem.t -> t list -> Expr.t -> t list -> t list
val prepend_marks : Marks.t -> ('a * t list) list -> ('a * t list) list
val initial : Expr.t -> t
val eps : Marks.t -> t
end = struct
type t =
| TSeq of Sem.t * t list * Expr.t
| TExp of Marks.t * Expr.t
| TMatch of Marks.t

let tmatch marks = TMatch marks
let initial expr = TExp (Marks.empty, expr)
let eps marks = TExp (marks, eps_expr)

let rec equal_list l1 l2 = List.equal ~eq:equal l1 l2

Expand Down Expand Up @@ -382,7 +385,6 @@ end = struct
;;

let compare = Poly.compare
let texp marks x = TExp (marks, x)

let tseq' kind x y =
match x with
Expand Down Expand Up @@ -514,7 +516,7 @@ module State = struct
}
;;

let create cat e = mk Idx.initial cat [ E.texp Marks.empty e ]
let create cat e = mk Idx.initial cat [ E.initial e ]

let equal { idx; category; desc; status = _; hash } t =
Int.equal hash t.hash
Expand Down Expand Up @@ -627,7 +629,7 @@ type ctx =
let rec delta_expr ({ c; _ } as ctx) marks (x : Expr.t) rem =
(*Format.eprintf "%d@." x.id;*)
match x.def with
| Cst s -> if Cset.mem c s then E.texp marks Expr.eps_expr :: rem else rem
| Cst s -> if Cset.mem c s then E.eps marks :: rem else rem
| Alt l -> delta_alt ctx marks l rem
| Seq (kind, y, z) ->
let y = delta_expr ctx marks y [] in
Expand Down Expand Up @@ -722,7 +724,7 @@ let rec restrict s = function

let rec deriv_expr all_chars categories marks cat (x : Expr.t) rem =
match x.def with
| Cst s -> Cset.prepend s [ E.texp marks Expr.eps_expr ] rem
| Cst s -> Cset.prepend s [ E.eps marks ] rem
| Alt l -> deriv_alt all_chars categories marks cat l rem
| Seq (kind, y, z) ->
let y = deriv_expr all_chars categories marks cat y [ all_chars, [] ] in
Expand Down

0 comments on commit 2660ca2

Please sign in to comment.