Skip to content

Commit

Permalink
test: more automata tests
Browse files Browse the repository at this point in the history
  • Loading branch information
rgrinberg committed Oct 27, 2024
1 parent 1e8f3fb commit 7263ac8
Showing 1 changed file with 53 additions and 7 deletions.
60 changes: 53 additions & 7 deletions lib_test/expect/test_automata.ml
Original file line number Diff line number Diff line change
Expand Up @@ -78,8 +78,8 @@ let%expect_test "string" =
;;

let%expect_test "alternation" =
let ids = Ids.create () in
let re =
let ids = Ids.create () in
let n = 4 in
let s =
let c = 'a' in
Expand Down Expand Up @@ -119,8 +119,8 @@ let%expect_test "alternation" =

let%expect_test "alternation shared prefix" =
let n = 4 in
let ids = Ids.create () in
let re =
let ids = Ids.create () in
let prefix =
let s =
let c = 'a' in
Expand Down Expand Up @@ -151,22 +151,68 @@ let%expect_test "alternation shared prefix" =
;;

let%expect_test "kleene star" =
let ids = Ids.create () in
let re = rep ids `Greedy `First (cst ids (Cset.csingle 'z')) in
let re =
let ids = Ids.create () in
rep ids `Greedy `First (cst ids (Cset.csingle 'z'))
in
let wa = Working_area.create () in
loop ~max:5 wa (State.create cat re) 'z';
loop ~max:4 wa (State.create cat re) 'z';
[%expect
{|
((TExp (first (Rep 122))))
((TExp (first (Rep 122))) (TMarks ()))
((TExp (first (Rep 122))) (TMarks ()))
((TExp (first (Rep 122))) (TMarks ()))
((TExp (first (Rep 122))) (TMarks ()))
|}];
|}];
loop ~max:3 wa (State.create cat re) 'a';
[%expect {|
((TExp (first (Rep 122))))
((TMarks ()))
> matched
|}]
;;

let%expect_test "derivative recomputation" =
let sem = `Longest in
let re =
let ids = Ids.create () in
let lhs = rep ids `Non_greedy sem (cst ids Cset.cany) in
let rhs =
seq
ids
sem
(Automata.mark ids Automata.Mark.start)
(Automata.alt ids [ cst ids (Cset.csingle 'z'); cst ids (Cset.csingle 'b') ])
in
seq ids sem lhs rhs
in
let wa = Working_area.create () in
loop ~max:7 wa (State.create cat re) 'z';
[%expect
{|
((TExp (long (Seq (Rep ((0 255))) (Seq (Mark 0) (Alt 122 98))))))
((long (TSeq ((TExp (Rep ((0 255))))) (Seq (Mark 0) (Alt 122 98))))
(TExp ((marks ((0 0)))) Eps))
((long (TSeq ((TExp (Rep ((0 255))))) (Seq (Mark 0) (Alt 122 98))))
(TExp ((marks ((0 1)))) Eps) (TMarks ((marks ((0 0))))))
((long (TSeq ((TExp (Rep ((0 255))))) (Seq (Mark 0) (Alt 122 98))))
(TExp ((marks ((0 0)))) Eps) (TMarks ((marks ((0 1))))))
((long (TSeq ((TExp (Rep ((0 255))))) (Seq (Mark 0) (Alt 122 98))))
(TExp ((marks ((0 1)))) Eps) (TMarks ((marks ((0 0))))))
((long (TSeq ((TExp (Rep ((0 255))))) (Seq (Mark 0) (Alt 122 98))))
(TExp ((marks ((0 0)))) Eps) (TMarks ((marks ((0 1))))))
((long (TSeq ((TExp (Rep ((0 255))))) (Seq (Mark 0) (Alt 122 98))))
(TExp ((marks ((0 1)))) Eps) (TMarks ((marks ((0 0))))))
|}];
loop ~max:7 wa (State.create cat re) 'a';
[%expect
{|
((TExp (long (Seq (Rep ((0 255))) (Seq (Mark 0) (Alt 122 98))))))
((long (TSeq ((TExp (Rep ((0 255))))) (Seq (Mark 0) (Alt 122 98)))))
((long (TSeq ((TExp (Rep ((0 255))))) (Seq (Mark 0) (Alt 122 98)))))
((long (TSeq ((TExp (Rep ((0 255))))) (Seq (Mark 0) (Alt 122 98)))))
((long (TSeq ((TExp (Rep ((0 255))))) (Seq (Mark 0) (Alt 122 98)))))
((long (TSeq ((TExp (Rep ((0 255))))) (Seq (Mark 0) (Alt 122 98)))))
((long (TSeq ((TExp (Rep ((0 255))))) (Seq (Mark 0) (Alt 122 98)))))
|}]
;;

0 comments on commit 7263ac8

Please sign in to comment.