aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test/lux/control/parser/text.lux
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/test/lux/control/parser/text.lux316
1 files changed, 158 insertions, 158 deletions
diff --git a/stdlib/source/test/lux/control/parser/text.lux b/stdlib/source/test/lux/control/parser/text.lux
index 8436e30ca..8465393de 100644
--- a/stdlib/source/test/lux/control/parser/text.lux
+++ b/stdlib/source/test/lux/control/parser/text.lux
@@ -38,7 +38,7 @@
_
false))
-(def: (should-fail' sample parser exception)
+(def: (should_fail' sample parser exception)
(All [a e] (-> Text (/.Parser a) (Exception e) Bit))
(case (/.run parser sample)
(#try.Failure error)
@@ -47,7 +47,7 @@
_
false))
-(def: (should-fail sample parser)
+(def: (should_fail sample parser)
(All [a] (-> Text (/.Parser a) Bit))
(case (/.run parser sample)
(#try.Failure _)
@@ -56,157 +56,157 @@
_
false))
-(def: (should-pass expected parser)
+(def: (should_pass expected parser)
(-> Text (/.Parser Text) Bit)
(|> expected
(/.run parser)
(\ try.functor map (text\= expected))
(try.default false)))
-(def: (should-pass! expected parser)
+(def: (should_pass! expected parser)
(-> Text (/.Parser /.Slice) Bit)
- (..should-pass expected (/.slice parser)))
+ (..should_pass expected (/.slice parser)))
-(def: character-classes
+(def: character_classes
Test
($_ _.and
(do {! random.monad}
[offset (\ ! map (n.% 50) random.nat)
range (\ ! map (|>> (n.% 50) (n.+ 10)) random.nat)
#let [limit (n.+ offset range)]
- expected (\ ! map (|>> (n.% range) (n.+ offset) text.from-code) random.nat)
- out-of-range (case offset
- 0 (\ ! map (|>> (n.% 10) inc (n.+ limit) text.from-code) random.nat)
- _ (\ ! map (|>> (n.% offset) text.from-code) random.nat))]
+ expected (\ ! map (|>> (n.% range) (n.+ offset) text.from_code) random.nat)
+ out_of_range (case offset
+ 0 (\ ! map (|>> (n.% 10) inc (n.+ limit) text.from_code) random.nat)
+ _ (\ ! map (|>> (n.% offset) text.from_code) random.nat))]
(_.cover [/.range]
- (and (..should-pass expected (/.range offset limit))
- (..should-fail out-of-range (/.range offset limit)))))
+ (and (..should_pass expected (/.range offset limit))
+ (..should_fail out_of_range (/.range offset limit)))))
(do {! random.monad}
- [expected (random.char unicode.ascii/upper-alpha)
- invalid (random.filter (|>> (unicode/block.within? unicode/block.basic-latin/upper-alpha) not)
+ [expected (random.char unicode.ascii/upper_alpha)
+ invalid (random.filter (|>> (unicode/block.within? unicode/block.basic_latin/upper_alpha) not)
(random.char unicode.character))]
(_.cover [/.upper]
- (and (..should-pass (text.from-code expected) /.upper)
- (..should-fail (text.from-code invalid) /.upper))))
+ (and (..should_pass (text.from_code expected) /.upper)
+ (..should_fail (text.from_code invalid) /.upper))))
(do {! random.monad}
- [expected (random.char unicode.ascii/lower-alpha)
- invalid (random.filter (|>> (unicode/block.within? unicode/block.basic-latin/lower-alpha) not)
+ [expected (random.char unicode.ascii/lower_alpha)
+ invalid (random.filter (|>> (unicode/block.within? unicode/block.basic_latin/lower_alpha) not)
(random.char unicode.character))]
(_.cover [/.lower]
- (and (..should-pass (text.from-code expected) /.lower)
- (..should-fail (text.from-code invalid) /.lower))))
+ (and (..should_pass (text.from_code expected) /.lower)
+ (..should_fail (text.from_code invalid) /.lower))))
(do {! random.monad}
[expected (\ ! map (n.% 10) random.nat)
- invalid (random.char (unicode.set [unicode/block.number-forms (list)]))]
+ invalid (random.char (unicode.set [unicode/block.number_forms (list)]))]
(_.cover [/.decimal]
- (and (..should-pass (\ n.decimal encode expected) /.decimal)
- (..should-fail (text.from-code invalid) /.decimal))))
+ (and (..should_pass (\ n.decimal encode expected) /.decimal)
+ (..should_fail (text.from_code invalid) /.decimal))))
(do {! random.monad}
[expected (\ ! map (n.% 8) random.nat)
- invalid (random.char (unicode.set [unicode/block.number-forms (list)]))]
+ invalid (random.char (unicode.set [unicode/block.number_forms (list)]))]
(_.cover [/.octal]
- (and (..should-pass (\ n.octal encode expected) /.octal)
- (..should-fail (text.from-code invalid) /.octal))))
+ (and (..should_pass (\ n.octal encode expected) /.octal)
+ (..should_fail (text.from_code invalid) /.octal))))
(do {! random.monad}
[expected (\ ! map (n.% 16) random.nat)
- invalid (random.char (unicode.set [unicode/block.number-forms (list)]))]
+ invalid (random.char (unicode.set [unicode/block.number_forms (list)]))]
(_.cover [/.hexadecimal]
- (and (..should-pass (\ n.hex encode expected) /.hexadecimal)
- (..should-fail (text.from-code invalid) /.hexadecimal))))
+ (and (..should_pass (\ n.hex encode expected) /.hexadecimal)
+ (..should_fail (text.from_code invalid) /.hexadecimal))))
(do {! random.monad}
[expected (random.char unicode.ascii/alpha)
invalid (random.filter (function (_ char)
- (not (or (unicode/block.within? unicode/block.basic-latin/upper-alpha char)
- (unicode/block.within? unicode/block.basic-latin/lower-alpha char))))
+ (not (or (unicode/block.within? unicode/block.basic_latin/upper_alpha char)
+ (unicode/block.within? unicode/block.basic_latin/lower_alpha char))))
(random.char unicode.character))]
(_.cover [/.alpha]
- (and (..should-pass (text.from-code expected) /.alpha)
- (..should-fail (text.from-code invalid) /.alpha))))
+ (and (..should_pass (text.from_code expected) /.alpha)
+ (..should_fail (text.from_code invalid) /.alpha))))
(do {! random.monad}
- [expected (random.char unicode.ascii/alpha-num)
+ [expected (random.char unicode.ascii/alpha_num)
invalid (random.filter (function (_ char)
- (not (or (unicode/block.within? unicode/block.basic-latin/upper-alpha char)
- (unicode/block.within? unicode/block.basic-latin/lower-alpha char)
- (unicode/block.within? unicode/block.basic-latin/decimal char))))
+ (not (or (unicode/block.within? unicode/block.basic_latin/upper_alpha char)
+ (unicode/block.within? unicode/block.basic_latin/lower_alpha char)
+ (unicode/block.within? unicode/block.basic_latin/decimal char))))
(random.char unicode.character))]
- (_.cover [/.alpha-num]
- (and (..should-pass (text.from-code expected) /.alpha-num)
- (..should-fail (text.from-code invalid) /.alpha-num))))
+ (_.cover [/.alpha_num]
+ (and (..should_pass (text.from_code expected) /.alpha_num)
+ (..should_fail (text.from_code invalid) /.alpha_num))))
(do {! random.monad}
[expected ($_ random.either
(wrap text.tab)
- (wrap text.vertical-tab)
+ (wrap text.vertical_tab)
(wrap text.space)
- (wrap text.new-line)
- (wrap text.carriage-return)
- (wrap text.form-feed))
+ (wrap text.new_line)
+ (wrap text.carriage_return)
+ (wrap text.form_feed))
invalid (|> (random.unicode 1) (random.filter (function (_ char)
(not (or (text\= text.tab char)
- (text\= text.vertical-tab char)
+ (text\= text.vertical_tab char)
(text\= text.space char)
- (text\= text.new-line char)
- (text\= text.carriage-return char)
- (text\= text.form-feed char))))))]
+ (text\= text.new_line char)
+ (text\= text.carriage_return char)
+ (text\= text.form_feed char))))))]
(_.cover [/.space]
- (and (..should-pass expected /.space)
- (..should-fail invalid /.space))))
+ (and (..should_pass expected /.space)
+ (..should_fail invalid /.space))))
(do {! random.monad}
- [#let [num-options 3]
+ [#let [num_options 3]
options (|> (random.char unicode.character)
- (random.set n.hash num-options)
- (\ ! map (|>> set.to-list
- (list\map text.from-code)
- (text.join-with ""))))
+ (random.set n.hash num_options)
+ (\ ! map (|>> set.to_list
+ (list\map text.from_code)
+ (text.join_with ""))))
expected (\ ! map (function (_ value)
(|> options
- (text.nth (n.% num-options value))
+ (text.nth (n.% num_options value))
maybe.assume))
random.nat)
invalid (random.filter (function (_ char)
- (not (text.contains? (text.from-code char) options)))
+ (not (text.contains? (text.from_code char) options)))
(random.char unicode.character))]
- (_.cover [/.one-of /.one-of! /.character-should-be]
- (and (..should-pass (text.from-code expected) (/.one-of options))
- (..should-fail (text.from-code invalid) (/.one-of options))
- (..should-fail' (text.from-code invalid) (/.one-of options)
- /.character-should-be)
+ (_.cover [/.one_of /.one_of! /.character_should_be]
+ (and (..should_pass (text.from_code expected) (/.one_of options))
+ (..should_fail (text.from_code invalid) (/.one_of options))
+ (..should_fail' (text.from_code invalid) (/.one_of options)
+ /.character_should_be)
- (..should-pass! (text.from-code expected) (/.one-of! options))
- (..should-fail (text.from-code invalid) (/.one-of! options))
- (..should-fail' (text.from-code invalid) (/.one-of! options)
- /.character-should-be)
+ (..should_pass! (text.from_code expected) (/.one_of! options))
+ (..should_fail (text.from_code invalid) (/.one_of! options))
+ (..should_fail' (text.from_code invalid) (/.one_of! options)
+ /.character_should_be)
)))
(do {! random.monad}
- [#let [num-options 3]
+ [#let [num_options 3]
options (|> (random.char unicode.character)
- (random.set n.hash num-options)
- (\ ! map (|>> set.to-list
- (list\map text.from-code)
- (text.join-with ""))))
+ (random.set n.hash num_options)
+ (\ ! map (|>> set.to_list
+ (list\map text.from_code)
+ (text.join_with ""))))
invalid (\ ! map (function (_ value)
(|> options
- (text.nth (n.% num-options value))
+ (text.nth (n.% num_options value))
maybe.assume))
random.nat)
expected (random.filter (function (_ char)
- (not (text.contains? (text.from-code char) options)))
+ (not (text.contains? (text.from_code char) options)))
(random.char unicode.character))]
- (_.cover [/.none-of /.none-of! /.character-should-not-be]
- (and (..should-pass (text.from-code expected) (/.none-of options))
- (..should-fail (text.from-code invalid) (/.none-of options))
- (..should-fail' (text.from-code invalid) (/.none-of options)
- /.character-should-not-be)
+ (_.cover [/.none_of /.none_of! /.character_should_not_be]
+ (and (..should_pass (text.from_code expected) (/.none_of options))
+ (..should_fail (text.from_code invalid) (/.none_of options))
+ (..should_fail' (text.from_code invalid) (/.none_of options)
+ /.character_should_not_be)
- (..should-pass! (text.from-code expected) (/.none-of! options))
- (..should-fail (text.from-code invalid) (/.none-of! options))
- (..should-fail' (text.from-code invalid) (/.none-of! options)
- /.character-should-not-be)
+ (..should_pass! (text.from_code expected) (/.none_of! options))
+ (..should_fail (text.from_code invalid) (/.none_of! options))
+ (..should_fail' (text.from_code invalid) (/.none_of! options)
+ /.character_should_not_be)
)))
))
(def: runs
Test
- (let [octal! (/.one-of! "01234567")]
+ (let [octal! (/.one_of! "01234567")]
($_ _.and
(do {! random.monad}
[left (\ ! map (|>> (n.% 8) (\ n.octal encode)) random.nat)
@@ -217,10 +217,10 @@
(random.filter (n.>= 8))
(\ ! map (\ n.hex encode)))]
(_.cover [/.many /.many!]
- (and (..should-pass expected (/.many /.octal))
- (..should-fail invalid (/.many /.octal))
+ (and (..should_pass expected (/.many /.octal))
+ (..should_fail invalid (/.many /.octal))
- (..should-pass! expected (/.many! octal!)))))
+ (..should_pass! expected (/.many! octal!)))))
(do {! random.monad}
[left (\ ! map (|>> (n.% 8) (\ n.octal encode)) random.nat)
right (\ ! map (|>> (n.% 8) (\ n.octal encode)) random.nat)
@@ -230,64 +230,64 @@
(random.filter (n.>= 8))
(\ ! map (\ n.hex encode)))]
(_.cover [/.some /.some!]
- (and (..should-pass expected (/.some /.octal))
- (..should-pass "" (/.some /.octal))
- (..should-fail invalid (/.some /.octal))
+ (and (..should_pass expected (/.some /.octal))
+ (..should_pass "" (/.some /.octal))
+ (..should_fail invalid (/.some /.octal))
- (..should-pass! expected (/.some! octal!))
- (..should-pass! "" (/.some! octal!)))))
+ (..should_pass! expected (/.some! octal!))
+ (..should_pass! "" (/.some! octal!)))))
(do {! random.monad}
[#let [octal (\ ! map (|>> (n.% 8) (\ n.octal encode)) random.nat)]
first octal
second octal
third octal]
(_.cover [/.exactly /.exactly!]
- (and (..should-pass (format first second) (/.exactly 2 /.octal))
- (..should-fail (format first second third) (/.exactly 2 /.octal))
- (..should-fail (format first) (/.exactly 2 /.octal))
+ (and (..should_pass (format first second) (/.exactly 2 /.octal))
+ (..should_fail (format first second third) (/.exactly 2 /.octal))
+ (..should_fail (format first) (/.exactly 2 /.octal))
- (..should-pass! (format first second) (/.exactly! 2 octal!))
- (..should-fail (format first second third) (/.exactly! 2 octal!))
- (..should-fail (format first) (/.exactly! 2 octal!)))))
+ (..should_pass! (format first second) (/.exactly! 2 octal!))
+ (..should_fail (format first second third) (/.exactly! 2 octal!))
+ (..should_fail (format first) (/.exactly! 2 octal!)))))
(do {! random.monad}
[#let [octal (\ ! map (|>> (n.% 8) (\ n.octal encode)) random.nat)]
first octal
second octal
third octal]
- (_.cover [/.at-most /.at-most!]
- (and (..should-pass (format first second) (/.at-most 2 /.octal))
- (..should-pass (format first) (/.at-most 2 /.octal))
- (..should-fail (format first second third) (/.at-most 2 /.octal))
+ (_.cover [/.at_most /.at_most!]
+ (and (..should_pass (format first second) (/.at_most 2 /.octal))
+ (..should_pass (format first) (/.at_most 2 /.octal))
+ (..should_fail (format first second third) (/.at_most 2 /.octal))
- (..should-pass! (format first second) (/.at-most! 2 octal!))
- (..should-pass! (format first) (/.at-most! 2 octal!))
- (..should-fail (format first second third) (/.at-most! 2 octal!)))))
+ (..should_pass! (format first second) (/.at_most! 2 octal!))
+ (..should_pass! (format first) (/.at_most! 2 octal!))
+ (..should_fail (format first second third) (/.at_most! 2 octal!)))))
(do {! random.monad}
[#let [octal (\ ! map (|>> (n.% 8) (\ n.octal encode)) random.nat)]
first octal
second octal
third octal]
- (_.cover [/.at-least /.at-least!]
- (and (..should-pass (format first second) (/.at-least 2 /.octal))
- (..should-pass (format first second third) (/.at-least 2 /.octal))
- (..should-fail (format first) (/.at-least 2 /.octal))
+ (_.cover [/.at_least /.at_least!]
+ (and (..should_pass (format first second) (/.at_least 2 /.octal))
+ (..should_pass (format first second third) (/.at_least 2 /.octal))
+ (..should_fail (format first) (/.at_least 2 /.octal))
- (..should-pass! (format first second) (/.at-least! 2 octal!))
- (..should-pass! (format first second third) (/.at-least! 2 octal!))
- (..should-fail (format first) (/.at-least! 2 octal!)))))
+ (..should_pass! (format first second) (/.at_least! 2 octal!))
+ (..should_pass! (format first second third) (/.at_least! 2 octal!))
+ (..should_fail (format first) (/.at_least! 2 octal!)))))
(do {! random.monad}
[#let [octal (\ ! map (|>> (n.% 8) (\ n.octal encode)) random.nat)]
first octal
second octal
third octal]
(_.cover [/.between /.between!]
- (and (..should-pass (format first second) (/.between 2 3 /.octal))
- (..should-pass (format first second third) (/.between 2 3 /.octal))
- (..should-fail (format first) (/.between 2 3 /.octal))
+ (and (..should_pass (format first second) (/.between 2 3 /.octal))
+ (..should_pass (format first second third) (/.between 2 3 /.octal))
+ (..should_fail (format first) (/.between 2 3 /.octal))
- (..should-pass! (format first second) (/.between! 2 3 octal!))
- (..should-pass! (format first second third) (/.between! 2 3 octal!))
- (..should-fail (format first) (/.between! 2 3 octal!)))))
+ (..should_pass! (format first second) (/.between! 2 3 octal!))
+ (..should_pass! (format first second third) (/.between! 2 3 octal!))
+ (..should_fail (format first) (/.between! 2 3 octal!)))))
)))
(def: #export test
@@ -309,42 +309,42 @@
expected (random.unicode size)
dummy (|> (random.unicode size)
(random.filter (|>> (text\= expected) not)))]
- (_.cover [/.this /.cannot-match]
+ (_.cover [/.this /.cannot_match]
(and (|> (/.run (/.this expected)
expected)
(!expect (#try.Success [])))
(|> (/.run (/.this expected)
dummy)
(!expect (^multi (#try.Failure error)
- (exception.match? /.cannot-match error)))))))
- (_.cover [/.Slice /.slice /.cannot-slice]
+ (exception.match? /.cannot_match error)))))))
+ (_.cover [/.Slice /.slice /.cannot_slice]
(|> ""
(/.run (/.slice /.any!))
(!expect (^multi (#try.Failure error)
- (exception.match? /.cannot-slice error)))))
+ (exception.match? /.cannot_slice error)))))
(do {! random.monad}
[expected (random.unicode 1)]
(_.cover [/.any /.any!]
- (and (..should-pass expected /.any)
- (..should-fail "" /.any)
+ (and (..should_pass expected /.any)
+ (..should_fail "" /.any)
- (..should-pass! expected /.any!)
- (..should-fail "" /.any!))))
+ (..should_pass! expected /.any!)
+ (..should_fail "" /.any!))))
(do {! random.monad}
[expected (random.unicode 1)]
- (_.cover [/.peek /.cannot-parse]
- (and (..should-pass expected (<>.before /.any /.peek))
+ (_.cover [/.peek /.cannot_parse]
+ (and (..should_pass expected (<>.before /.any /.peek))
(|> ""
(/.run (<>.before /.any /.peek))
(!expect (^multi (#try.Failure error)
- (exception.match? /.cannot-parse error)))))))
+ (exception.match? /.cannot_parse error)))))))
(do {! random.monad}
[dummy (random.unicode 1)]
- (_.cover [/.unconsumed-input]
+ (_.cover [/.unconsumed_input]
(|> (format dummy dummy)
(/.run /.any)
(!expect (^multi (#try.Failure error)
- (exception.match? /.unconsumed-input error))))))
+ (exception.match? /.unconsumed_input error))))))
(do {! random.monad}
[sample (random.unicode 1)]
(_.cover [/.Offset /.offset]
@@ -359,12 +359,12 @@
[left (random.unicode 1)
right (random.unicode 1)
#let [input (format left right)]]
- (_.cover [/.get-input]
+ (_.cover [/.get_input]
(|> input
(/.run (do <>.monad
- [pre /.get-input
+ [pre /.get_input
_ /.any
- post /.get-input
+ post /.get_input
_ /.any]
(wrap (and (text\= input pre)
(text\= right post)))))
@@ -395,47 +395,47 @@
(!expect (^multi (#try.Success actual)
(text\= expected actual))))))
(do {! random.monad}
- [invalid (random.ascii/upper-alpha 1)
- expected (random.filter (|>> (unicode/block.within? unicode/block.basic-latin/upper-alpha)
+ [invalid (random.ascii/upper_alpha 1)
+ expected (random.filter (|>> (unicode/block.within? unicode/block.basic_latin/upper_alpha)
not)
(random.char unicode.character))
- #let [upper! (/.one-of! "ABCDEFGHIJKLMNOPQRSTUVWXYZ")]]
- (_.cover [/.not /.not! /.expected-to-fail]
- (and (..should-pass (text.from-code expected) (/.not /.upper))
+ #let [upper! (/.one_of! "ABCDEFGHIJKLMNOPQRSTUVWXYZ")]]
+ (_.cover [/.not /.not! /.expected_to_fail]
+ (and (..should_pass (text.from_code expected) (/.not /.upper))
(|> invalid
(/.run (/.not /.upper))
(!expect (^multi (#try.Failure error)
- (exception.match? /.expected-to-fail error))))
+ (exception.match? /.expected_to_fail error))))
- (..should-pass! (text.from-code expected) (/.not! upper!))
+ (..should_pass! (text.from_code expected) (/.not! upper!))
(|> invalid
(/.run (/.not! upper!))
(!expect (^multi (#try.Failure error)
- (exception.match? /.expected-to-fail error)))))))
+ (exception.match? /.expected_to_fail error)))))))
(do {! random.monad}
- [upper (random.ascii/upper-alpha 1)
- lower (random.ascii/lower-alpha 1)
+ [upper (random.ascii/upper_alpha 1)
+ lower (random.ascii/lower_alpha 1)
invalid (random.filter (function (_ char)
- (not (or (unicode/block.within? unicode/block.basic-latin/upper-alpha char)
- (unicode/block.within? unicode/block.basic-latin/lower-alpha char))))
+ (not (or (unicode/block.within? unicode/block.basic_latin/upper_alpha char)
+ (unicode/block.within? unicode/block.basic_latin/lower_alpha char))))
(random.char unicode.character))
- #let [upper! (/.one-of! "ABCDEFGHIJKLMNOPQRSTUVWXYZ")
- lower! (/.one-of! "abcdefghijklmnopqrstuvwxyz")]]
+ #let [upper! (/.one_of! "ABCDEFGHIJKLMNOPQRSTUVWXYZ")
+ lower! (/.one_of! "abcdefghijklmnopqrstuvwxyz")]]
(_.cover [/.and /.and!]
- (and (..should-pass (format upper lower) (/.and /.upper /.lower))
- (..should-fail (format (text.from-code invalid) lower) (/.and /.upper /.lower))
- (..should-fail (format upper (text.from-code invalid)) (/.and /.upper /.lower))
+ (and (..should_pass (format upper lower) (/.and /.upper /.lower))
+ (..should_fail (format (text.from_code invalid) lower) (/.and /.upper /.lower))
+ (..should_fail (format upper (text.from_code invalid)) (/.and /.upper /.lower))
- (..should-pass! (format upper lower) (/.and! upper! lower!))
- (..should-fail (format (text.from-code invalid) lower) (/.and! upper! lower!))
- (..should-fail (format upper (text.from-code invalid)) (/.and! upper! lower!)))))
+ (..should_pass! (format upper lower) (/.and! upper! lower!))
+ (..should_fail (format (text.from_code invalid) lower) (/.and! upper! lower!))
+ (..should_fail (format upper (text.from_code invalid)) (/.and! upper! lower!)))))
(do {! random.monad}
[expected (random.unicode 1)
invalid (random.unicode 1)]
- (_.cover [/.satisfies /.character-does-not-satisfy-predicate]
- (and (..should-pass expected (/.satisfies (function.constant true)))
- (..should-fail' invalid (/.satisfies (function.constant false))
- /.character-does-not-satisfy-predicate))))
- ..character-classes
+ (_.cover [/.satisfies /.character_does_not_satisfy_predicate]
+ (and (..should_pass expected (/.satisfies (function.constant true)))
+ (..should_fail' invalid (/.satisfies (function.constant false))
+ /.character_does_not_satisfy_predicate))))
+ ..character_classes
..runs
)))