diff options
Diffstat (limited to '')
-rw-r--r-- | stdlib/test/test/lux/compiler/default/phase/analysis/procedure/common.lux | 4 | ||||
-rw-r--r-- | stdlib/test/test/lux/compiler/default/syntax.lux | 139 | ||||
-rw-r--r-- | stdlib/test/test/lux/data/text/format.lux | 2 | ||||
-rw-r--r-- | stdlib/test/test/lux/data/text/regex.lux | 105 | ||||
-rw-r--r-- | stdlib/test/test/lux/host.jvm.lux | 2 | ||||
-rw-r--r-- | stdlib/test/test/lux/macro/code.lux | 4 | ||||
-rw-r--r-- | stdlib/test/test/lux/macro/syntax.lux | 4 | ||||
-rw-r--r-- | stdlib/test/test/lux/math/logic/fuzzy.lux | 8 |
8 files changed, 83 insertions, 185 deletions
diff --git a/stdlib/test/test/lux/compiler/default/phase/analysis/procedure/common.lux b/stdlib/test/test/lux/compiler/default/phase/analysis/procedure/common.lux index fc082155a..108b350d0 100644 --- a/stdlib/test/test/lux/compiler/default/phase/analysis/procedure/common.lux +++ b/stdlib/test/test/lux/compiler/default/phase/analysis/procedure/common.lux @@ -165,9 +165,9 @@ (test "Can query the size/length of a text." (check-success+ "lux text size" (list subjectC) Nat)) (test "Can obtain the character code of a text at a given index." - (check-success+ "lux text char" (list subjectC fromC) (type (Maybe Nat)))) + (check-success+ "lux text char" (list subjectC fromC) Nat)) (test "Can clip a piece of text between 2 indices." - (check-success+ "lux text clip" (list subjectC fromC toC) (type (Maybe Text)))) + (check-success+ "lux text clip" (list subjectC fromC toC) Text)) )))) (context: "IO procedures" diff --git a/stdlib/test/test/lux/compiler/default/syntax.lux b/stdlib/test/test/lux/compiler/default/syntax.lux index 2b4a8f5b6..887765cbd 100644 --- a/stdlib/test/test/lux/compiler/default/syntax.lux +++ b/stdlib/test/test/lux/compiler/default/syntax.lux @@ -29,8 +29,8 @@ (r.Random Text) (do r.Monad<Random> [#let [digits "0123456789" - delimiters "()[]{}#.\"" - space "\t\v \n\r\f" + delimiters (format "()[]{}#." &.text-delimiter) + space (format " " text.new-line) invalid-range (format digits delimiters space) char-gen (|> r.nat (:: @ map (|>> (n/% 256) (n/max 1))) @@ -87,23 +87,23 @@ other code^] ($_ seq (test "Can parse Lux code." - (case (&.read "" (dict.new text.Hash<Text>) - [default-cursor 0 (code.to-text sample)]) + (case (&.parse "" (dict.new text.Hash<Text>) + [default-cursor 0 (code.to-text sample)]) (#e.Error error) #0 (#e.Success [_ parsed]) (:: code.Equivalence<Code> = parsed sample))) (test "Can parse Lux multiple code nodes." - (case (&.read "" (dict.new text.Hash<Text>) - [default-cursor 0 (format (code.to-text sample) " " - (code.to-text other))]) + (case (&.parse "" (dict.new text.Hash<Text>) + [default-cursor 0 (format (code.to-text sample) " " + (code.to-text other))]) (#e.Error error) #0 (#e.Success [remaining =sample]) - (case (&.read "" (dict.new text.Hash<Text>) - remaining) + (case (&.parse "" (dict.new text.Hash<Text>) + remaining) (#e.Error error) #0 @@ -112,136 +112,33 @@ (:: code.Equivalence<Code> = other =other))))) )))) -(context: "Frac special syntax." - (<| (times 100) - (do @ - [numerator (|> r.nat (:: @ map (|>> (n/% 100) .int int-to-frac))) - denominator (|> r.nat (:: @ map (|>> (n/% 100) (n/max 1) .int int-to-frac))) - signed? r.bit - #let [expected (|> numerator (f// denominator) (f/* (if signed? -1.0 +1.0)))]] - (test "Can parse frac ratio syntax." - (case (&.read "" (dict.new text.Hash<Text>) - [default-cursor 0 - (format (if signed? "-" "+") - (%i (frac-to-int numerator)) - "/" - (%i (frac-to-int denominator)))]) - (#e.Success [_ [_ (#.Frac actual)]]) - (f/= expected actual) - - _ - #0) - )))) - -(context: "Nat special syntax." - (<| (times 100) - (do @ - [expected (|> r.nat (:: @ map (n/% 1_000)))] - (test "Can parse nat char syntax." - (case (&.read "" (dict.new text.Hash<Text>) - [default-cursor 0 - (format "#" (%t (text.from-code expected)) "")]) - (#e.Success [_ [_ (#.Nat actual)]]) - (n/= expected actual) - - _ - #0) - )))) - (def: comment-text^ (r.Random Text) - (let [char-gen (|> r.nat (r.filter (function (_ value) - (not (or (text.space? value) - (n/= (char "#") value) - (n/= (char "(") value) - (n/= (char ")") value))))))] + (let [char-gen (|> r.nat (r.filter (|>> (n/= (`` (char (~~ (static text.new-line))))) not)))] (do r.Monad<Random> [size (|> r.nat (r/map (n/% 20)))] (r.text char-gen size)))) (def: comment^ (r.Random Text) - (r.either (do r.Monad<Random> - [comment comment-text^] - (wrap (format "## " comment "\n"))) - (r.rec (function (_ nested^) - (do r.Monad<Random> - [comment (r.either comment-text^ - nested^)] - (wrap (format "#( " comment " )#"))))))) + (do r.Monad<Random> + [comment comment-text^] + (wrap (format "## " comment text.new-line)))) (context: "Multi-line text & comments." (<| (seed 12137892244981970631) ## (times 100) (do @ - [#let [char-gen (|> r.nat (r.filter (function (_ value) - (not (or (text.space? value) - (n/= (char "\"") value))))))] - x char-gen - y char-gen - z char-gen - offset-size (|> r.nat (r/map (|>> (n/% 10) (n/max 1)))) - #let [offset (text.join-with "" (list.repeat offset-size " "))] - sample code^ - comment comment^ - unbalanced-comment comment-text^] + [sample code^ + comment comment^] ($_ seq - (test "Will reject invalid multi-line text." - (let [bad-match (format (text.from-code x) "\n" - (text.from-code y) "\n" - (text.from-code z))] - (case (&.read "" (dict.new text.Hash<Text>) - [default-cursor 0 - (format "\"" bad-match "\"")]) - (#e.Error error) - #1 - - (#e.Success [_ parsed]) - #0))) - (test "Will accept valid multi-line text" - (let [good-input (format (text.from-code x) "\n" - offset (text.from-code y) "\n" - offset (text.from-code z)) - good-output (format (text.from-code x) "\n" - (text.from-code y) "\n" - (text.from-code z))] - (case (&.read "" (dict.new text.Hash<Text>) - [(|> default-cursor (update@ #.column (n/+ (dec offset-size)))) - 0 - (format "\"" good-input "\"")]) - (#e.Error error) - #0 - - (#e.Success [_ parsed]) - (:: code.Equivalence<Code> = - parsed - (code.text good-output))))) (test "Can handle comments." - (case (&.read "" (dict.new text.Hash<Text>) - [default-cursor 0 - (format comment (code.to-text sample))]) + (case (&.parse "" (dict.new text.Hash<Text>) + [default-cursor 0 + (format comment (code.to-text sample))]) (#e.Error error) #0 (#e.Success [_ parsed]) (:: code.Equivalence<Code> = parsed sample))) - (test "Will reject unbalanced multi-line comments." - (and (case (&.read "" (dict.new text.Hash<Text>) - [default-cursor 0 - (format "#(" "#(" unbalanced-comment ")#" - (code.to-text sample))]) - (#e.Error error) - #1 - - (#e.Success [_ parsed]) - #0) - (case (&.read "" (dict.new text.Hash<Text>) - [default-cursor 0 - (format "#(" unbalanced-comment ")#" ")#" - (code.to-text sample))]) - (#e.Error error) - #1 - - (#e.Success [_ parsed]) - #0))) )))) diff --git a/stdlib/test/test/lux/data/text/format.lux b/stdlib/test/test/lux/data/text/format.lux index bd66712a8..48cf24306 100644 --- a/stdlib/test/test/lux/data/text/format.lux +++ b/stdlib/test/test/lux/data/text/format.lux @@ -16,6 +16,6 @@ (&/= "+123" (%i +123)) (&/= "+123.456" (%f +123.456)) (&/= ".5" (%r .5)) - (&/= "\"YOLO\"" (%t "YOLO")) + (&/= (format text.double-quote "YOLO" text.double-quote) (%t "YOLO")) (&/= "User-id: +123 -- Active: #1" (format "User-id: " (%i +123) " -- Active: " (%b #1))))) ))) diff --git a/stdlib/test/test/lux/data/text/regex.lux b/stdlib/test/test/lux/data/text/regex.lux index 96f56c3d9..3398f4685 100644 --- a/stdlib/test/test/lux/data/text/regex.lux +++ b/stdlib/test/test/lux/data/text/regex.lux @@ -5,7 +5,8 @@ pipe ["p" parser]] [data - [text ("text/." Equivalence<Text>) + [number (#+ hex)] + ["." text ("text/." Equivalence<Text>) format ["." lexer (#+ Lexer)] ["&" regex]]] @@ -52,8 +53,8 @@ (test "Can parse character literals." (and (should-pass (&.regex "a") "a") (should-fail (&.regex "a") ".") - (should-pass (&.regex "\\.") ".") - (should-fail (&.regex "\\.") "a")))) + (should-pass (&.regex "\.") ".") + (should-fail (&.regex "\.") "a")))) (context: "Regular Expressions [System character classes]" ($_ seq @@ -61,79 +62,79 @@ (should-pass (&.regex ".") "a")) (test "Can parse digits." - (and (should-pass (&.regex "\\d") "0") - (should-fail (&.regex "\\d") "m"))) + (and (should-pass (&.regex "\d") "0") + (should-fail (&.regex "\d") "m"))) (test "Can parse non digits." - (and (should-pass (&.regex "\\D") "m") - (should-fail (&.regex "\\D") "0"))) + (and (should-pass (&.regex "\D") "m") + (should-fail (&.regex "\D") "0"))) (test "Can parse white-space." - (and (should-pass (&.regex "\\s") " ") - (should-fail (&.regex "\\s") "m"))) + (and (should-pass (&.regex "\s") " ") + (should-fail (&.regex "\s") "m"))) (test "Can parse non white-space." - (and (should-pass (&.regex "\\S") "m") - (should-fail (&.regex "\\S") " "))) + (and (should-pass (&.regex "\S") "m") + (should-fail (&.regex "\S") " "))) (test "Can parse word characters." - (and (should-pass (&.regex "\\w") "_") - (should-fail (&.regex "\\w") "^"))) + (and (should-pass (&.regex "\w") "_") + (should-fail (&.regex "\w") "^"))) (test "Can parse non word characters." - (and (should-pass (&.regex "\\W") ".") - (should-fail (&.regex "\\W") "a"))) + (and (should-pass (&.regex "\W") ".") + (should-fail (&.regex "\W") "a"))) )) (context: "Regular Expressions [Special system character classes : Part 1]" ($_ seq (test "Can parse using special character classes." - (and (and (should-pass (&.regex "\\p{Lower}") "m") - (should-fail (&.regex "\\p{Lower}") "M")) + (and (and (should-pass (&.regex "\p{Lower}") "m") + (should-fail (&.regex "\p{Lower}") "M")) - (and (should-pass (&.regex "\\p{Upper}") "M") - (should-fail (&.regex "\\p{Upper}") "m")) + (and (should-pass (&.regex "\p{Upper}") "M") + (should-fail (&.regex "\p{Upper}") "m")) - (and (should-pass (&.regex "\\p{Alpha}") "M") - (should-fail (&.regex "\\p{Alpha}") "0")) + (and (should-pass (&.regex "\p{Alpha}") "M") + (should-fail (&.regex "\p{Alpha}") "0")) - (and (should-pass (&.regex "\\p{Digit}") "1") - (should-fail (&.regex "\\p{Digit}") "n")) + (and (should-pass (&.regex "\p{Digit}") "1") + (should-fail (&.regex "\p{Digit}") "n")) - (and (should-pass (&.regex "\\p{Alnum}") "1") - (should-fail (&.regex "\\p{Alnum}") ".")) + (and (should-pass (&.regex "\p{Alnum}") "1") + (should-fail (&.regex "\p{Alnum}") ".")) - (and (should-pass (&.regex "\\p{Space}") " ") - (should-fail (&.regex "\\p{Space}") ".")) + (and (should-pass (&.regex "\p{Space}") " ") + (should-fail (&.regex "\p{Space}") ".")) )) )) (context: "Regular Expressions [Special system character classes : Part 2]" ($_ seq (test "Can parse using special character classes." - (and (and (should-pass (&.regex "\\p{HexDigit}") "a") - (should-fail (&.regex "\\p{HexDigit}") ".")) + (and (and (should-pass (&.regex "\p{HexDigit}") "a") + (should-fail (&.regex "\p{HexDigit}") ".")) - (and (should-pass (&.regex "\\p{OctDigit}") "6") - (should-fail (&.regex "\\p{OctDigit}") ".")) + (and (should-pass (&.regex "\p{OctDigit}") "6") + (should-fail (&.regex "\p{OctDigit}") ".")) - (and (should-pass (&.regex "\\p{Blank}") "\t") - (should-fail (&.regex "\\p{Blank}") ".")) + (and (should-pass (&.regex "\p{Blank}") text.tab) + (should-fail (&.regex "\p{Blank}") ".")) - (and (should-pass (&.regex "\\p{ASCII}") "\t") - (should-fail (&.regex "\\p{ASCII}") "\u1234")) + (and (should-pass (&.regex "\p{ASCII}") text.tab) + (should-fail (&.regex "\p{ASCII}") (text.from-code (hex "1234")))) - (and (should-pass (&.regex "\\p{Contrl}") "\u0012") - (should-fail (&.regex "\\p{Contrl}") "a")) + (and (should-pass (&.regex "\p{Contrl}") (text.from-code (hex "12"))) + (should-fail (&.regex "\p{Contrl}") "a")) - (and (should-pass (&.regex "\\p{Punct}") "@") - (should-fail (&.regex "\\p{Punct}") "a")) + (and (should-pass (&.regex "\p{Punct}") "@") + (should-fail (&.regex "\p{Punct}") "a")) - (and (should-pass (&.regex "\\p{Graph}") "@") - (should-fail (&.regex "\\p{Graph}") " ")) + (and (should-pass (&.regex "\p{Graph}") "@") + (should-fail (&.regex "\p{Graph}") " ")) - (and (should-pass (&.regex "\\p{Print}") "\u0020") - (should-fail (&.regex "\\p{Print}") "\u1234")) + (and (should-pass (&.regex "\p{Print}") (text.from-code (hex "20"))) + (should-fail (&.regex "\p{Print}") (text.from-code (hex "1234")))) )) )) @@ -190,9 +191,9 @@ )) (context: "Regular Expressions [Reference]" - (let [number (&.regex "\\d+")] + (let [number (&.regex "\d+")] (test "Can build complex regexs by combining simpler ones." - (should-check ["809-345-6789" "809" "345" "6789"] (&.regex "(\\@<number>)-(\\@<number>)-(\\@<number>)") "809-345-6789")))) + (should-check ["809-345-6789" "809" "345" "6789"] (&.regex "(\@<number>)-(\@<number>)-(\@<number>)") "809-345-6789")))) (context: "Regular Expressions [Fuzzy Quantifiers]" ($_ seq @@ -239,14 +240,14 @@ (test "Can extract groups of sub-matches specified in a pattern." (and (should-check ["abc" "b"] (&.regex "a(.)c") "abc") (should-check ["abbbbbc" "bbbbb"] (&.regex "a(b+)c") "abbbbbc") - (should-check ["809-345-6789" "809" "345" "6789"] (&.regex "(\\d{3})-(\\d{3})-(\\d{4})") "809-345-6789") - (should-check ["809-345-6789" "809" "6789"] (&.regex "(\\d{3})-(?:\\d{3})-(\\d{4})") "809-345-6789") - (should-check ["809-809-6789" "809" "6789"] (&.regex "(\\d{3})-\\0-(\\d{4})") "809-809-6789") - (should-check ["809-809-6789" "809" "6789"] (&.regex "(?<code>\\d{3})-\\k<code>-(\\d{4})") "809-809-6789") - (should-check ["809-809-6789-6789" "809" "6789"] (&.regex "(?<code>\\d{3})-\\k<code>-(\\d{4})-\\0") "809-809-6789-6789"))) + (should-check ["809-345-6789" "809" "345" "6789"] (&.regex "(\d{3})-(\d{3})-(\d{4})") "809-345-6789") + (should-check ["809-345-6789" "809" "6789"] (&.regex "(\d{3})-(?:\d{3})-(\d{4})") "809-345-6789") + (should-check ["809-809-6789" "809" "6789"] (&.regex "(\d{3})-\0-(\d{4})") "809-809-6789") + (should-check ["809-809-6789" "809" "6789"] (&.regex "(?<code>\d{3})-\k<code>-(\d{4})") "809-809-6789") + (should-check ["809-809-6789-6789" "809" "6789"] (&.regex "(?<code>\d{3})-\k<code>-(\d{4})-\0") "809-809-6789-6789"))) (test "Can specify groups within groups." - (should-check ["809-345-6789" "809" ["345-6789" "345" "6789"]] (&.regex "(\\d{3})-((\\d{3})-(\\d{4}))") "809-345-6789")) + (should-check ["809-345-6789" "809" ["345-6789" "345" "6789"]] (&.regex "(\d{3})-((\d{3})-(\d{4}))") "809-345-6789")) )) (context: "Regular Expressions [Alternation]" @@ -262,7 +263,7 @@ (should-fail (&.regex "a(.)(.)|b(.)(.)") "cde") (should-check ["809-345-6789" (0 ["809" "345-6789" "345" "6789"])] - (&.regex "(\\d{3})-((\\d{3})-(\\d{4}))|b(.)d") + (&.regex "(\d{3})-((\d{3})-(\d{4}))|b(.)d") "809-345-6789"))) )) diff --git a/stdlib/test/test/lux/host.jvm.lux b/stdlib/test/test/lux/host.jvm.lux index 8832bb3f6..835bdd719 100644 --- a/stdlib/test/test/lux/host.jvm.lux +++ b/stdlib/test/test/lux/host.jvm.lux @@ -88,7 +88,7 @@ (&.instance? Object "") (not (&.instance? Object (&.null))))) - (test "Can run code in a \"synchronized\" block." + (test "Can run code in a 'synchronized' block." (&.synchronized "" #1)) (test "Can access Class instances." diff --git a/stdlib/test/test/lux/macro/code.lux b/stdlib/test/test/lux/macro/code.lux index 1e0d4a606..be53adfad 100644 --- a/stdlib/test/test/lux/macro/code.lux +++ b/stdlib/test/test/lux/macro/code.lux @@ -5,7 +5,7 @@ [monad (#+ do Monad)]] [data [number] - [text ("text/." Equivalence<Text>) + ["." text ("text/." Equivalence<Text>) format]] [math ["r" random]] [macro ["&" code]]] @@ -22,7 +22,7 @@ [(&.bit #0) "#0"] [(&.int +123) "+123"] [(&.frac +123.0) "+123.0"] - [(&.text "\n") "\"\\n\""] + [(&.text "1234") (format text.double-quote "1234" text.double-quote)] [(&.tag ["yolo" "lol"]) "#yolo.lol"] [(&.identifier ["yolo" "lol"]) "yolo.lol"] [(&.form (list (&.bit #1) (&.int +123))) "(#1 +123)"] diff --git a/stdlib/test/test/lux/macro/syntax.lux b/stdlib/test/test/lux/macro/syntax.lux index b1e2f445b..0bf7b8804 100644 --- a/stdlib/test/test/lux/macro/syntax.lux +++ b/stdlib/test/test/lux/macro/syntax.lux @@ -75,9 +75,9 @@ ["Can parse Bit syntax." #1 code.bit bit.Equivalence<Bit> s.bit] ["Can parse Nat syntax." 123 code.nat number.Equivalence<Nat> s.nat] ["Can parse Int syntax." +123 code.int number.Equivalence<Int> s.int] - ["Can parse Rev syntax." .123 code.rev number.Equivalence<Rev> s.rev] + ["Can parse Rev syntax." .123 code.rev number.Equivalence<Rev> s.rev] ["Can parse Frac syntax." +123.0 code.frac number.Equivalence<Frac> s.frac] - ["Can parse Text syntax." "\n" code.text text.Equivalence<Text> s.text] + ["Can parse Text syntax." text.new-line code.text text.Equivalence<Text> s.text] ["Can parse Identifier syntax." ["yolo" "lol"] code.identifier name.Equivalence<Name> s.identifier] ["Can parse Tag syntax." ["yolo" "lol"] code.tag name.Equivalence<Name> s.tag] )] diff --git a/stdlib/test/test/lux/math/logic/fuzzy.lux b/stdlib/test/test/lux/math/logic/fuzzy.lux index fe36a58c5..38f1cc75a 100644 --- a/stdlib/test/test/lux/math/logic/fuzzy.lux +++ b/stdlib/test/test/lux/math/logic/fuzzy.lux @@ -153,13 +153,13 @@ [#let [set-10 (set.from-list number.Hash<Nat> (list.n/range 0 10))] sample (|> r.nat (:: @ map (n/% 20)))] ($_ seq - (test "Values that satisfy a predicate have membership = 1. - Values that don't have membership = 0." + (test (format "Values that satisfy a predicate have membership = 1." + "Values that don't have membership = 0.") (bit/= (r/= _.true (&.membership sample (&.from-predicate n/even?))) (n/even? sample))) - (test "Values that belong to a set have membership = 1. - Values that don't have membership = 0." + (test (format "Values that belong to a set have membership = 1." + "Values that don't have membership = 0.") (bit/= (r/= _.true (&.membership sample (&.from-set set-10))) (set.member? set-10 sample))) )))) |