diff options
Diffstat (limited to 'stdlib/source/test/lux/data')
-rw-r--r-- | stdlib/source/test/lux/data/collection/array.lux | 16 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/collection/dictionary.lux | 54 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/collection/dictionary/ordered.lux | 56 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/collection/list.lux | 30 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/collection/sequence.lux | 6 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/collection/set/ordered.lux | 40 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/collection/stream.lux | 52 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/collection/tree/zipper.lux | 4 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/color.lux | 48 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/format/tar.lux | 12 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/format/xml.lux | 4 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/text.lux | 4 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/text/regex.lux | 8 |
13 files changed, 168 insertions, 166 deletions
diff --git a/stdlib/source/test/lux/data/collection/array.lux b/stdlib/source/test/lux/data/collection/array.lux index 2e2904b3d..b41a178d2 100644 --- a/stdlib/source/test/lux/data/collection/array.lux +++ b/stdlib/source/test/lux/data/collection/array.lux @@ -62,7 +62,7 @@ the_array (random.array size random.nat) evens (random.array size (random.only n.even? random.nat))] ($_ _.and - (let [(^open "/#[0]") /.functor + (let [(open "/#[0]") /.functor choose (: (-> Nat (Maybe Text)) (function (_ value) (if (n.even? value) @@ -156,9 +156,9 @@ (!.empty size))))) (_.cover [!.type] (case !.Array - (^ (<| {.#Named (symbol !.Array)} - {.#UnivQ (list)} - {.#Primitive nominal_type (list {.#Parameter 1})})) + (pattern (<| {.#Named (symbol !.Array)} + {.#UnivQ (list)} + {.#Primitive nominal_type (list {.#Parameter 1})})) (same? !.type nominal_type) _ @@ -324,10 +324,10 @@ (/.empty size))))) (_.cover [/.type_name] (case /.Array - (^ (<| {.#Named (symbol /.Array)} - {.#Named (symbol !.Array)} - {.#UnivQ (list)} - {.#Primitive nominal_type (list {.#Parameter 1})})) + (pattern (<| {.#Named (symbol /.Array)} + {.#Named (symbol !.Array)} + {.#UnivQ (list)} + {.#Primitive nominal_type (list {.#Parameter 1})})) (same? /.type_name nominal_type) _ diff --git a/stdlib/source/test/lux/data/collection/dictionary.lux b/stdlib/source/test/lux/data/collection/dictionary.lux index 4dec751e4..1054e5248 100644 --- a/stdlib/source/test/lux/data/collection/dictionary.lux +++ b/stdlib/source/test/lux/data/collection/dictionary.lux @@ -1,28 +1,28 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [hash {"+" Hash}] - [monad {"+" do}] - [\\specification - ["$[0]" equivalence] - ["$[0]" functor {"+" Injection}]]] - [control - ["[0]" maybe ("[1]#[0]" functor)] - ["[0]" try] - ["[0]" exception]] - [data - ["[0]" product] - [collection - ["[0]" list ("[1]#[0]" functor)] - ["[0]" set]]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [hash {"+" Hash}] + [monad {"+" do}] + [\\specification + ["$[0]" equivalence] + ["$[0]" functor {"+" Injection}]]] + [control + ["[0]" maybe ("[1]#[0]" functor)] + ["[0]" try] + ["[0]" exception]] + [data + ["[0]" product] + [collection + ["[0]" list ("[1]#[0]" functor)] + ["[0]" set]]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]]) (def: injection (Injection (/.Dictionary Nat)) @@ -109,12 +109,12 @@ (list.size (/.values dict)))) (_.cover [/.merged] - (let [merging_with_oneself (let [(^open "[0]") (/.equivalence n.equivalence)] + (let [merging_with_oneself (let [(open "[0]") (/.equivalence n.equivalence)] (= dict (/.merged dict dict))) overwritting_keys (let [dict' (|> dict /.entries (list#each (function (_ [k v]) [k (++ v)])) (/.of_list n.hash)) - (^open "[0]") (/.equivalence n.equivalence)] + (open "[0]") (/.equivalence n.equivalence)] (= dict' (/.merged dict' dict)))] (and merging_with_oneself overwritting_keys))) @@ -125,7 +125,7 @@ (/.values (/.merged_with n.+ dict dict))))) (_.cover [/.of_list] - (let [(^open "[0]") (/.equivalence n.equivalence)] + (let [(open "[0]") (/.equivalence n.equivalence)] (and (= dict dict) (|> dict /.entries (/.of_list n.hash) (= dict))))) ))) diff --git a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux index 5c8f43b56..3e628ec45 100644 --- a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux +++ b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux @@ -1,27 +1,27 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [equivalence {"+" Equivalence}] - [order {"+" Order}] - [\\specification - ["$[0]" equivalence]]] - [control - ["[0]" maybe ("[1]#[0]" monad)]] - [data - ["[0]" product] - ["[0]" bit ("[1]#[0]" equivalence)] - [collection - ["[0]" set] - ["[0]" list ("[1]#[0]" functor)]]] - [math - ["[0]" random {"+" Random} ("[1]#[0]" monad)] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [equivalence {"+" Equivalence}] + [order {"+" Order}] + [\\specification + ["$[0]" equivalence]]] + [control + ["[0]" maybe ("[1]#[0]" monad)]] + [data + ["[0]" product] + ["[0]" bit ("[1]#[0]" equivalence)] + [collection + ["[0]" set] + ["[0]" list ("[1]#[0]" functor)]]] + [math + ["[0]" random {"+" Random} ("[1]#[0]" monad)] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]]) (def: .public (dictionary order gen_key gen_value size) (All (_ k v) @@ -57,11 +57,11 @@ (n.< left right)) pairs) sorted_values (list#each product.right sorted_pairs) - (^open "list#[0]") (list.equivalence (: (Equivalence [Nat Nat]) - (function (_ [kr vr] [ks vs]) - (and (n.= kr ks) - (n.= vr vs))))) - (^open "/#[0]") (/.equivalence n.equivalence)]] + (open "list#[0]") (list.equivalence (: (Equivalence [Nat Nat]) + (function (_ [kr vr] [ks vs]) + (and (n.= kr ks) + (n.= vr vs))))) + (open "/#[0]") (/.equivalence n.equivalence)]] ($_ _.and (_.for [/.equivalence] ($equivalence.spec (/.equivalence n.equivalence) (..dictionary n.order random.nat random.nat size))) diff --git a/stdlib/source/test/lux/data/collection/list.lux b/stdlib/source/test/lux/data/collection/list.lux index e4d2bb2aa..88ce2f5b9 100644 --- a/stdlib/source/test/lux/data/collection/list.lux +++ b/stdlib/source/test/lux/data/collection/list.lux @@ -69,7 +69,7 @@ [parameter random.nat subject random.nat] (let [lifted (/.lifted io.monad) - (^open "io#[0]") io.monad + (open "io#[0]") io.monad expected (n.+ parameter subject)] (_.cover [/.with /.lifted] (|> (io.run! (do (/.with io.monad) @@ -77,7 +77,7 @@ b (in subject)] (in (n.+ a b)))) (pipe.case - (^ (list actual)) + (pattern (list actual)) (n.= expected actual) _ @@ -88,7 +88,7 @@ Test (do [! random.monad] [size ..bounded_size - .let [(^open "/#[0]") (/.equivalence n.equivalence)] + .let [(open "/#[0]") (/.equivalence n.equivalence)] sample (# ! each set.list (random.set n.hash size random.nat))] ($_ _.and (_.cover [/.size] @@ -130,8 +130,8 @@ (def: indices Test - (let [(^open "/#[0]") (/.equivalence n.equivalence) - (^open "/#[0]") /.functor] + (let [(open "/#[0]") (/.equivalence n.equivalence) + (open "/#[0]") /.functor] (do [! random.monad] [sample ..random .let [size (/.size sample)]] @@ -190,8 +190,8 @@ (def: slice Test - (let [(^open "/#[0]") (/.equivalence n.equivalence) - (^open "/#[0]") /.monoid] + (let [(open "/#[0]") (/.equivalence n.equivalence) + (open "/#[0]") /.monoid] (do [! random.monad] [sample (random.only (|>> /.size (n.> 0)) ..random) @@ -239,7 +239,7 @@ (def: member Test - (let [(^open "/#[0]") (/.equivalence n.equivalence)] + (let [(open "/#[0]") (/.equivalence n.equivalence)] (do [! random.monad] [sample ..random] (`` ($_ _.and @@ -277,9 +277,9 @@ (def: grouping Test - (let [(^open "/#[0]") (/.equivalence n.equivalence) - (^open "/#[0]") /.functor - (^open "/#[0]") /.monoid + (let [(open "/#[0]") (/.equivalence n.equivalence) + (open "/#[0]") /.functor + (open "/#[0]") /.monoid +/2 (: (-> Nat Nat Nat) (function (_ left right) @@ -372,7 +372,7 @@ (def: search Test - (let [(^open "/#[0]") /.functor + (let [(open "/#[0]") /.functor choice (: (-> Nat (Maybe Text)) (function (_ value) @@ -415,8 +415,8 @@ Test (<| (_.covering /._) (_.for [.List]) - (let [(^open "/#[0]") (/.equivalence n.equivalence) - (^open "/#[0]") /.functor] + (let [(open "/#[0]") (/.equivalence n.equivalence) + (open "/#[0]") /.functor] (do [! random.monad] [sample ..random separator random.nat] @@ -454,7 +454,7 @@ (/.mixes n.+ 0 sample))) (do random.monad [expected random.nat - .let [(^open "/#[0]") (/.equivalence n.equivalence)]] + .let [(open "/#[0]") (/.equivalence n.equivalence)]] (_.cover [/.when] (and (/#= (list expected) (/.when true (list expected))) (/#= (list) (/.when false (list expected)))))) diff --git a/stdlib/source/test/lux/data/collection/sequence.lux b/stdlib/source/test/lux/data/collection/sequence.lux index 220581bd2..125dfaac9 100644 --- a/stdlib/source/test/lux/data/collection/sequence.lux +++ b/stdlib/source/test/lux/data/collection/sequence.lux @@ -52,7 +52,7 @@ [size (# ! each (n.% 100) random.nat) sample (random.set n.hash size random.nat) .let [sample (|> sample set.list /.of_list)] - .let [(^open "/#[0]") (/.equivalence n.equivalence)]] + .let [(open "/#[0]") (/.equivalence n.equivalence)]] ($_ _.and (_.cover [/.size] (n.= size (/.size sample))) @@ -146,7 +146,7 @@ non_member (random.only (|>> (set.member? sample) not) random.nat) .let [sample (|> sample set.list /.of_list)] - .let [(^open "/#[0]") (/.equivalence n.equivalence)]] + .let [(open "/#[0]") (/.equivalence n.equivalence)]] ($_ _.and (do ! [value/0 random.nat @@ -194,7 +194,7 @@ (n.+ (/.size positives) (/.size negatives)))))) (_.cover [/.one] - (let [(^open "/#[0]") /.functor + (let [(open "/#[0]") /.functor choice (: (-> Nat (Maybe Text)) (function (_ value) (if (n.even? value) diff --git a/stdlib/source/test/lux/data/collection/set/ordered.lux b/stdlib/source/test/lux/data/collection/set/ordered.lux index 81626777f..04a3eed86 100644 --- a/stdlib/source/test/lux/data/collection/set/ordered.lux +++ b/stdlib/source/test/lux/data/collection/set/ordered.lux @@ -1,23 +1,23 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [order {"+" Order}] - [\\specification - ["$[0]" equivalence]]] - [data - ["[0]" bit ("[1]#[0]" equivalence)] - [collection - ["[0]" list]]] - [math - ["[0]" random {"+" Random} ("[1]#[0]" monad)] - [number - ["n" nat]]]]] - [\\library - ["[0]" / {"+" Set} - ["[0]" //]]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [order {"+" Order}] + [\\specification + ["$[0]" equivalence]]] + [data + ["[0]" bit ("[1]#[0]" equivalence)] + [collection + ["[0]" list]]] + [math + ["[0]" random {"+" Random} ("[1]#[0]" monad)] + [number + ["n" nat]]]]] + [\\library + ["[0]" / {"+" Set} + ["[0]" //]]]) (def: size (random.Random Nat) @@ -48,7 +48,7 @@ random.nat) .let [listL (//.list usetL)] listR (|> (random.set n.hash sizeR random.nat) (# ! each //.list)) - .let [(^open "/#[0]") /.equivalence + .let [(open "/#[0]") /.equivalence setL (/.of_list n.order listL) setR (/.of_list n.order listR) empty (/.empty n.order)]] diff --git a/stdlib/source/test/lux/data/collection/stream.lux b/stdlib/source/test/lux/data/collection/stream.lux index c959de821..d7fa8a191 100644 --- a/stdlib/source/test/lux/data/collection/stream.lux +++ b/stdlib/source/test/lux/data/collection/stream.lux @@ -1,25 +1,25 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [equivalence {"+" Equivalence}] - ["[0]" enum] - [\\specification - ["$[0]" functor] - ["$[0]" comonad]]] - [data - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [equivalence {"+" Equivalence}] + ["[0]" enum] + [\\specification + ["$[0]" functor] + ["$[0]" comonad]]] + [data + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]]) (implementation: (equivalence super) (All (_ a) (-> (Equivalence a) (Equivalence (/.Stream a)))) @@ -42,7 +42,7 @@ Test (<| (_.covering /._) (_.for [/.Stream]) - (let [(^open "list#[0]") (list.equivalence n.equivalence)]) + (let [(open "list#[0]") (list.equivalence n.equivalence)]) (do [! random.monad] [repeated random.nat index (# ! each (n.% 100) random.nat) @@ -103,8 +103,8 @@ (n.= (++ (n.* 2 offset)) (/.item offset odds))))) (_.cover [/.iterations] - (let [(^open "/#[0]") /.functor - (^open "list#[0]") (list.equivalence text.equivalence)] + (let [(open "/#[0]") /.functor + (open "list#[0]") (list.equivalence text.equivalence)] (list#= (/.first size (/#each %.nat (..iterations ++ offset))) (/.first size @@ -115,8 +115,8 @@ (list#= (list.together (list.repeated size cycle)) (/.first (n.* size (list.size cycle)) (/.cycle [cycle_start cycle_next]))))) - (_.cover [/.^stream&] - (let [(/.^stream& first second third next) (..iterations ++ offset)] + (_.cover [/.pattern] + (let [(/.pattern first second third next) (..iterations ++ offset)] (and (n.= offset first) (n.= (n.+ 1 offset) second) (n.= (n.+ 2 offset) third)))) diff --git a/stdlib/source/test/lux/data/collection/tree/zipper.lux b/stdlib/source/test/lux/data/collection/tree/zipper.lux index 111597da6..b39f5ea63 100644 --- a/stdlib/source/test/lux/data/collection/tree/zipper.lux +++ b/stdlib/source/test/lux/data/collection/tree/zipper.lux @@ -159,8 +159,8 @@ [[size sample] (//.tree random.nat) expected random.nat dummy (random.only (|>> (n.= expected) not) random.nat) - .let [(^open "tree#[0]") (tree.equivalence n.equivalence) - (^open "list#[0]") (list.equivalence n.equivalence)]] + .let [(open "tree#[0]") (tree.equivalence n.equivalence) + (open "list#[0]") (list.equivalence n.equivalence)]] ($_ _.and (_.for [/.equivalence] ($equivalence.spec (/.equivalence n.equivalence) (# ! each (|>> product.right /.zipper) (//.tree random.nat)))) diff --git a/stdlib/source/test/lux/data/color.lux b/stdlib/source/test/lux/data/color.lux index 9223e6b47..8df8e5813 100644 --- a/stdlib/source/test/lux/data/color.lux +++ b/stdlib/source/test/lux/data/color.lux @@ -1,27 +1,27 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [\\specification - ["$[0]" equivalence] - ["$[0]" hash] - ["$[0]" monoid]]] - [data - [collection - ["[0]" list]]] - [macro - ["[0]" template]] - ["[0]" math - ["[0]" random {"+" Random}] - [number - ["n" nat] - ["[0]" int] - ["f" frac] - ["r" rev]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [\\specification + ["$[0]" equivalence] + ["$[0]" hash] + ["$[0]" monoid]]] + [data + [collection + ["[0]" list]]] + [macro + ["[0]" template]] + ["[0]" math + ["[0]" random {"+" Random}] + [number + ["n" nat] + ["[0]" int] + ["f" frac] + ["r" rev]]]]] + [\\library + ["[0]" /]]) (def: .public random (Random /.Color) @@ -195,7 +195,7 @@ (..encoding expected) (_.cover [/.complement] (let [~expected (/.complement expected) - (^open "/#[0]") /.equivalence] + (open "/#[0]") /.equivalence] (and (not (/#= expected ~expected)) (/#= expected (/.complement ~expected))))) (_.cover [/.black /.white] diff --git a/stdlib/source/test/lux/data/format/tar.lux b/stdlib/source/test/lux/data/format/tar.lux index 9bb1e6ea0..f09796461 100644 --- a/stdlib/source/test/lux/data/format/tar.lux +++ b/stdlib/source/test/lux/data/format/tar.lux @@ -175,7 +175,7 @@ (format.result /.writer) (<b>.result /.parser))] (in (case (sequence.list tar) - (^ (list {<tag> actual_path})) + (pattern (list {<tag> actual_path})) (text#= (/.from_path expected_path) (/.from_path actual_path)) @@ -204,7 +204,7 @@ (format.result /.writer) (<b>.result /.parser))] (in (case (sequence.list tar) - (^ (list {<tag> [actual_path actual_moment actual_mode actual_ownership actual_content]})) + (pattern (list {<tag> [actual_path actual_moment actual_mode actual_ownership actual_content]})) (let [seconds (: (-> Instant Int) (|>> instant.relative (duration.ticks duration.second)))] (and (text#= (/.from_path expected_path) @@ -262,7 +262,7 @@ (format.result /.writer) (<b>.result /.parser))] (in (case (sequence.list tar) - (^ (list {/.#Normal [_ _ actual_mode _ _]})) + (pattern (list {/.#Normal [_ _ actual_mode _ _]})) (n.= (/.mode expected_mode) (/.mode actual_mode)) @@ -285,7 +285,7 @@ (format.result /.writer) (<b>.result /.parser))] (in (case (sequence.list tar) - (^ (list {/.#Normal [_ _ actual_mode _ _]})) + (pattern (list {/.#Normal [_ _ actual_mode _ _]})) (n.= (/.mode <expected_mode>) (/.mode actual_mode)) @@ -352,7 +352,7 @@ (format.result /.writer) (<b>.result /.parser))] (in (case (sequence.list tar) - (^ (list {/.#Normal [_ _ _ actual_ownership _]})) + (pattern (list {/.#Normal [_ _ _ actual_ownership _]})) (and (text#= (/.from_name expected) (/.from_name (the [/.#user /.#name] actual_ownership))) (text#= (/.from_name /.anonymous) @@ -376,7 +376,7 @@ (format.result /.writer) (<b>.result /.parser))] (in (case (sequence.list tar) - (^ (list {/.#Normal [_ _ _ actual_ownership _]})) + (pattern (list {/.#Normal [_ _ _ actual_ownership _]})) (and (text#= (/.from_name /.anonymous) (/.from_name (the [/.#user /.#name] actual_ownership))) (n.= (/.from_small /.no_id) diff --git a/stdlib/source/test/lux/data/format/xml.lux b/stdlib/source/test/lux/data/format/xml.lux index 439fe1f5c..c547d400c 100644 --- a/stdlib/source/test/lux/data/format/xml.lux +++ b/stdlib/source/test/lux/data/format/xml.lux @@ -18,6 +18,8 @@ [collection ["[0]" dictionary] ["[0]" list ("[1]#[0]" functor)]]] + [macro + ["^" pattern]] [math ["[0]" random {"+" Random} ("[1]#[0]" monad)] [number @@ -77,7 +79,7 @@ ($codec.spec /.equivalence /.codec ..random)) (do [! random.monad] - [(^let symbol [namespace name]) ..symbol] + [(^.let symbol [namespace name]) ..symbol] (`` ($_ _.and (~~ (template [<type> <format>] [(_.cover [<type> <format>] diff --git a/stdlib/source/test/lux/data/text.lux b/stdlib/source/test/lux/data/text.lux index ed6cc5d9d..8503e08ac 100644 --- a/stdlib/source/test/lux/data/text.lux +++ b/stdlib/source/test/lux/data/text.lux @@ -285,7 +285,7 @@ sampleR (random.unicode sizeR) middle (random.unicode 1) .let [sample (/.together (list sampleL sampleR)) - (^open "/#[0]") /.equivalence]] + (open "/#[0]") /.equivalence]] ($_ _.and (_.cover [/.split_at] (|> (/.split_at sizeL sample) @@ -326,7 +326,7 @@ parts (random.list sizeL part_gen) .let [sample1 (/.together (list.interposed sep1 parts)) sample2 (/.together (list.interposed sep2 parts)) - (^open "/#[0]") /.equivalence]] + (open "/#[0]") /.equivalence]] (_.cover [/.replaced] (/#= sample2 (/.replaced sep1 sep2 sample1)))) diff --git a/stdlib/source/test/lux/data/text/regex.lux b/stdlib/source/test/lux/data/text/regex.lux index 0ab71cbaa..58c26d067 100644 --- a/stdlib/source/test/lux/data/text/regex.lux +++ b/stdlib/source/test/lux/data/text/regex.lux @@ -62,7 +62,7 @@ (in (list (` (|> (~ input) (<text>.result (~ regex)) (pipe.case - (^ {try.#Success (~ pattern)}) + (pattern {try.#Success (~ pattern)}) true (~ g!_) @@ -305,10 +305,10 @@ [sample1 (random.unicode 3) sample2 (random.unicode 3) sample3 (random.unicode 4)] - (_.cover [/.^regex] + (_.cover [/.pattern] (case (format sample1 "-" sample2 "-" sample3) - (/.^regex "(.{3})-(.{3})-(.{4})" - [_ match1 match2 match3]) + (/.pattern "(.{3})-(.{3})-(.{4})" + [_ match1 match2 match3]) (and (text#= sample1 match1) (text#= sample2 match2) (text#= sample3 match3)) |