aboutsummaryrefslogtreecommitdiff
path: root/stdlib/test
diff options
context:
space:
mode:
authorEduardo Julian2018-07-21 02:57:44 -0400
committerEduardo Julian2018-07-21 02:57:44 -0400
commit35b77d1ae1e0e4d59f8341089b12c0043abaddd8 (patch)
tree65d68583f1d694a8c80d2742c77aab68092bb947 /stdlib/test
parent660c7fe6af927c6e668a86e44fd2f0a9b1fb8b8b (diff)
Re-named "Ident" to "Name".
Diffstat (limited to 'stdlib/test')
-rw-r--r--stdlib/test/test/lux/compiler/default/phase/analysis/reference.lux4
-rw-r--r--stdlib/test/test/lux/compiler/default/syntax.lux12
-rw-r--r--stdlib/test/test/lux/data/format/xml.lux6
-rw-r--r--stdlib/test/test/lux/data/ident.lux73
-rw-r--r--stdlib/test/test/lux/data/name.lux73
-rw-r--r--stdlib/test/test/lux/macro/syntax.lux6
-rw-r--r--stdlib/test/test/lux/type.lux39
-rw-r--r--stdlib/test/test/lux/type/check.lux47
-rw-r--r--stdlib/test/tests.lux2
9 files changed, 119 insertions, 143 deletions
diff --git a/stdlib/test/test/lux/compiler/default/phase/analysis/reference.lux b/stdlib/test/test/lux/compiler/default/phase/analysis/reference.lux
index 6a103d155..de813de4e 100644
--- a/stdlib/test/test/lux/compiler/default/phase/analysis/reference.lux
+++ b/stdlib/test/test/lux/compiler/default/phase/analysis/reference.lux
@@ -5,7 +5,7 @@
pipe]
[data
["e" error]
- [ident ("ident/." Equivalence<Ident>)]
+ [name ("name/." Equivalence<Name>)]
[text ("text/." Equivalence<Text>)]]
[math
["r" random]]
@@ -96,7 +96,7 @@
(phase.run [analysisE.bundle (init.compiler [])])
(case> (^ (#e.Success [_ inferredT (#analysis.Reference (reference.constant constant-name))]))
(and (type/= expectedT inferredT)
- (ident/= def-name constant-name))
+ (name/= def-name constant-name))
_
#0))))
diff --git a/stdlib/test/test/lux/compiler/default/syntax.lux b/stdlib/test/test/lux/compiler/default/syntax.lux
index 42ae7f379..a0d5ce367 100644
--- a/stdlib/test/test/lux/compiler/default/syntax.lux
+++ b/stdlib/test/test/lux/compiler/default/syntax.lux
@@ -26,7 +26,7 @@
#.line +0
#.column +0})
-(def: ident-part^
+(def: name-part^
(r.Random Text)
(do r.Monad<Random>
[#let [digits "0123456789"
@@ -41,9 +41,9 @@
size (|> r.nat (:: @ map (|>> (n/% +20) (n/max +1))))]
(r.text char-gen size)))
-(def: ident^
- (r.Random Ident)
- (r.seq ident-part^ ident-part^))
+(def: name^
+ (r.Random Name)
+ (r.seq name-part^ name-part^))
(def: code^
(r.Random Code)
@@ -59,8 +59,8 @@
(do r.Monad<Random>
[size (|> r.nat (r/map (n/% +20)))]
(|> (r.unicode size) (r/map code.text)))
- (|> ident^ (r/map code.symbol))
- (|> ident^ (r/map code.tag))))
+ (|> name^ (r/map code.symbol))
+ (|> name^ (r/map code.tag))))
simple^ (: (r.Random Code)
($_ r.either
numeric^
diff --git a/stdlib/test/test/lux/data/format/xml.lux b/stdlib/test/test/lux/data/format/xml.lux
index d09dc1b45..37eec4169 100644
--- a/stdlib/test/test/lux/data/format/xml.lux
+++ b/stdlib/test/test/lux/data/format/xml.lux
@@ -5,7 +5,7 @@
["p" parser]
pipe]
[data
- ["." ident]
+ ["." name]
["E" error]
["." maybe]
["." text ("text/." Equivalence<Text>)
@@ -43,7 +43,7 @@
(r.text xml-char^ size)))
(def: xml-identifier^
- (r.Random Ident)
+ (r.Random Name)
(r.seq (xml-text^ +0 +10)
(xml-text^ +1 +10)))
@@ -55,7 +55,7 @@
[size (size^ +0 +2)]
($_ r.seq
xml-identifier^
- (r.dictionary ident.Hash<Ident> size xml-identifier^ (xml-text^ +0 +10))
+ (r.dictionary name.Hash<Name> size xml-identifier^ (xml-text^ +0 +10))
(r.list size gen-xml)))))))
(context: "XML."
diff --git a/stdlib/test/test/lux/data/ident.lux b/stdlib/test/test/lux/data/ident.lux
deleted file mode 100644
index ed9339f01..000000000
--- a/stdlib/test/test/lux/data/ident.lux
+++ /dev/null
@@ -1,73 +0,0 @@
-(.module:
- [lux #*
- [control
- [monad (#+ do Monad)]
- pipe]
- [data
- ["&" ident]
- ["." text ("text/." Equivalence<Text>)
- format]]
- [math
- ["r" random]]]
- lux/test)
-
-(def: (gen-part size)
- (-> Nat (r.Random Text))
- (|> (r.unicode size) (r.filter (|>> (text.contains? ".") not))))
-
-(context: "Idents"
- (<| (times +100)
- (do @
- [## First Ident
- sizeM1 (|> r.nat (:: @ map (n/% +100)))
- sizeN1 (|> r.nat (:: @ map (|>> (n/% +100) (n/max +1))))
- module1 (gen-part sizeM1)
- name1 (gen-part sizeN1)
- #let [ident1 [module1 name1]]
- ## Second Ident
- sizeM2 (|> r.nat (:: @ map (n/% +100)))
- sizeN2 (|> r.nat (:: @ map (|>> (n/% +100) (n/max +1))))
- module2 (gen-part sizeM2)
- name2 (gen-part sizeN2)
- #let [ident2 [module2 name2]]
- #let [(^open "&/.") &.Equivalence<Ident>
- (^open "&/.") &.Codec<Text,Ident>]]
- ($_ seq
- (test "Can get the module & name parts of an ident."
- (and (is? module1 (&.module ident1))
- (is? name1 (&.name ident1))))
-
- (test "Can compare idents for equivalence."
- (and (&/= ident1 ident1)
- (if (&/= ident1 ident2)
- (and (text/= module1 module2)
- (text/= name1 name2))
- (or (not (text/= module1 module2))
- (not (text/= name1 name2))))))
-
- (test "Can encode idents as text."
- (|> ident1
- &/encode &/decode
- (case> (#.Right dec-ident) (&/= ident1 dec-ident)
- _ #0)))
-
- (test "Encoding an ident without a module component results in text equal to the name of the ident."
- (if (text.empty? module1)
- (text/= name1 (&/encode ident1))
- #1))
- ))))
-
-(context: "Ident-related macros."
- (let [(^open "&/.") &.Equivalence<Ident>]
- ($_ seq
- (test "Can obtain Ident from symbol."
- (and (&/= ["lux" "yolo"] (ident-for .yolo))
- (&/= ["test/lux/data/ident" "yolo"] (ident-for ..yolo))
- (&/= ["" "yolo"] (ident-for yolo))
- (&/= ["lux/test" "yolo"] (ident-for lux/test.yolo))))
-
- (test "Can obtain Ident from tag."
- (and (&/= ["lux" "yolo"] (ident-for #.yolo))
- (&/= ["test/lux/data/ident" "yolo"] (ident-for #..yolo))
- (&/= ["" "yolo"] (ident-for #yolo))
- (&/= ["lux/test" "yolo"] (ident-for #lux/test.yolo)))))))
diff --git a/stdlib/test/test/lux/data/name.lux b/stdlib/test/test/lux/data/name.lux
new file mode 100644
index 000000000..699b76bb2
--- /dev/null
+++ b/stdlib/test/test/lux/data/name.lux
@@ -0,0 +1,73 @@
+(.module:
+ [lux #*
+ [control
+ [monad (#+ do Monad)]
+ pipe]
+ [data
+ ["&" name]
+ ["." text ("text/." Equivalence<Text>)
+ format]]
+ [math
+ ["r" random]]]
+ lux/test)
+
+(def: (gen-part size)
+ (-> Nat (r.Random Text))
+ (|> (r.unicode size) (r.filter (|>> (text.contains? ".") not))))
+
+(context: "Names"
+ (<| (times +100)
+ (do @
+ [## First Name
+ sizeM1 (|> r.nat (:: @ map (n/% +100)))
+ sizeN1 (|> r.nat (:: @ map (|>> (n/% +100) (n/max +1))))
+ module1 (gen-part sizeM1)
+ short1 (gen-part sizeN1)
+ #let [name1 [module1 short1]]
+ ## Second Name
+ sizeM2 (|> r.nat (:: @ map (n/% +100)))
+ sizeN2 (|> r.nat (:: @ map (|>> (n/% +100) (n/max +1))))
+ module2 (gen-part sizeM2)
+ short2 (gen-part sizeN2)
+ #let [name2 [module2 short2]]
+ #let [(^open "&/.") &.Equivalence<Name>
+ (^open "&/.") &.Codec<Text,Name>]]
+ ($_ seq
+ (test "Can get the module & short parts of an name."
+ (and (is? module1 (&.module name1))
+ (is? short1 (&.short name1))))
+
+ (test "Can compare names for equivalence."
+ (and (&/= name1 name1)
+ (if (&/= name1 name2)
+ (and (text/= module1 module2)
+ (text/= short1 short2))
+ (or (not (text/= module1 module2))
+ (not (text/= short1 short2))))))
+
+ (test "Can encode names as text."
+ (|> name1
+ &/encode &/decode
+ (case> (#.Right dec-name) (&/= name1 dec-name)
+ _ #0)))
+
+ (test "Encoding an name without a module component results in text equal to the short of the name."
+ (if (text.empty? module1)
+ (text/= short1 (&/encode name1))
+ #1))
+ ))))
+
+(context: "Name-related macros."
+ (let [(^open "&/.") &.Equivalence<Name>]
+ ($_ seq
+ (test "Can obtain Name from symbol."
+ (and (&/= ["lux" "yolo"] (name-for .yolo))
+ (&/= ["test/lux/data/name" "yolo"] (name-for ..yolo))
+ (&/= ["" "yolo"] (name-for yolo))
+ (&/= ["lux/test" "yolo"] (name-for lux/test.yolo))))
+
+ (test "Can obtain Name from tag."
+ (and (&/= ["lux" "yolo"] (name-for #.yolo))
+ (&/= ["test/lux/data/name" "yolo"] (name-for #..yolo))
+ (&/= ["" "yolo"] (name-for #yolo))
+ (&/= ["lux/test" "yolo"] (name-for #lux/test.yolo)))))))
diff --git a/stdlib/test/test/lux/macro/syntax.lux b/stdlib/test/test/lux/macro/syntax.lux
index a9913f754..d378153bc 100644
--- a/stdlib/test/test/lux/macro/syntax.lux
+++ b/stdlib/test/test/lux/macro/syntax.lux
@@ -6,7 +6,7 @@
["p" parser]]
[data
["." bit]
- ["." ident]
+ ["." name]
["e" error]
["." number]
["." text
@@ -78,8 +78,8 @@
["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 Symbol syntax." ["yolo" "lol"] code.symbol ident.Equivalence<Ident> s.symbol]
- ["Can parse Tag syntax." ["yolo" "lol"] code.tag ident.Equivalence<Ident> s.tag]
+ ["Can parse Symbol syntax." ["yolo" "lol"] code.symbol name.Equivalence<Name> s.symbol]
+ ["Can parse Tag syntax." ["yolo" "lol"] code.tag name.Equivalence<Name> s.tag]
)]
($_ seq
<simple-tests>
diff --git a/stdlib/test/test/lux/type.lux b/stdlib/test/test/lux/type.lux
index 9592170ff..611f7bd60 100644
--- a/stdlib/test/test/lux/type.lux
+++ b/stdlib/test/test/lux/type.lux
@@ -15,33 +15,36 @@
lux/test)
## [Utils]
-(def: gen-name
+(def: #export gen-short
(r.Random Text)
(do r.Monad<Random>
[size (|> r.nat (:: @ map (n/% +10)))]
(r.unicode size)))
-(def: gen-ident
- (r.Random Ident)
- (r.seq gen-name gen-name))
+(def: #export gen-name
+ (r.Random Name)
+ (r.seq gen-short gen-short))
-(def: gen-type
+(def: #export gen-type
(r.Random Type)
(let [(^open "R/.") r.Monad<Random>]
(r.rec (function (_ gen-type)
- ($_ r.alt
- (r.seq gen-name (R/wrap (list)))
- (r.seq gen-type gen-type)
- (r.seq gen-type gen-type)
- (r.seq gen-type gen-type)
- r.nat
- r.nat
- r.nat
- (r.seq (R/wrap (list)) gen-type)
- (r.seq (R/wrap (list)) gen-type)
- (r.seq gen-type gen-type)
- (r.seq gen-ident gen-type)
- )))))
+ (let [pairG (r.seq gen-type gen-type)
+ idG r.nat
+ quantifiedG (r.seq (R/wrap (list)) gen-type)]
+ ($_ r.alt
+ (r.seq gen-short (R/wrap (list)))
+ pairG
+ pairG
+ pairG
+ idG
+ idG
+ idG
+ quantifiedG
+ quantifiedG
+ pairG
+ (r.seq gen-name gen-type)
+ ))))))
## [Tests]
(context: "Types"
diff --git a/stdlib/test/test/lux/type/check.lux b/stdlib/test/test/lux/type/check.lux
index c817ec61e..b1d0365e1 100644
--- a/stdlib/test/test/lux/type/check.lux
+++ b/stdlib/test/test/lux/type/check.lux
@@ -15,37 +15,10 @@
["r" random]]
["." type ("type/." Equivalence<Type>)
["@" check]]]
- lux/test)
+ lux/test
+ ["." //])
## [Utils]
-(def: gen-name
- (r.Random Text)
- (do r.Monad<Random>
- [size (|> r.nat (:: @ map (n/% +10)))]
- (r.unicode size)))
-
-(def: gen-ident
- (r.Random Ident)
- (r.seq gen-name gen-name))
-
-(def: gen-type
- (r.Random Type)
- (let [(^open "r/.") r.Monad<Random>]
- (r.rec (function (_ gen-type)
- ($_ r.alt
- (r.seq gen-name (r/wrap (list)))
- (r.seq gen-type gen-type)
- (r.seq gen-type gen-type)
- (r.seq gen-type gen-type)
- r.nat
- r.nat
- r.nat
- (r.seq (r/wrap (list)) gen-type)
- (r.seq (r/wrap (list)) gen-type)
- (r.seq gen-type gen-type)
- (r.seq gen-ident gen-type)
- )))))
-
(def: (valid-type? type)
(-> Type Bit)
(case type
@@ -79,7 +52,7 @@
(context: "Any and Nothing."
(<| (times +100)
(do @
- [sample (|> gen-type (r.filter valid-type?))]
+ [sample (|> //.gen-type (r.filter valid-type?))]
($_ seq
(test "Any is the super-type of everything."
(@.checks? Any sample))
@@ -127,8 +100,8 @@
(context: "Type application."
(<| (times +100)
(do @
- [meta gen-type
- data gen-type]
+ [meta //.gen-type
+ data //.gen-type]
(test "Can type-check type application."
(and (@.checks? (|> Ann (#.Apply meta) (#.Apply data))
(type.tuple (list meta data)))
@@ -138,10 +111,10 @@
(context: "Primitive types."
(<| (times +100)
(do @
- [nameL gen-name
- nameR (|> gen-name (r.filter (|>> (text/= nameL) not)))
- paramL gen-type
- paramR (|> gen-type (r.filter (|>> (@.checks? paramL) not)))]
+ [nameL //.gen-short
+ nameR (|> //.gen-short (r.filter (|>> (text/= nameL) not)))
+ paramL //.gen-type
+ paramR (|> //.gen-type (r.filter (|>> (@.checks? paramL) not)))]
($_ seq
(test "Primitive types match when they have the same name and the same parameters."
(@.checks? (#.Primitive nameL (list paramL))
@@ -207,7 +180,7 @@
(<| (times +100)
(do @
[num-connections (|> r.nat (:: @ map (n/% +100)))
- boundT (|> gen-type (r.filter (|>> (case> (#.Var _) #0 _ #1))))
+ boundT (|> //.gen-type (r.filter (|>> (case> (#.Var _) #0 _ #1))))
pick-pcg (r.seq r.nat r.nat)]
($_ seq
(test "Can create rings of variables."
diff --git a/stdlib/test/tests.lux b/stdlib/test/tests.lux
index e855220dd..db2687876 100644
--- a/stdlib/test/tests.lux
+++ b/stdlib/test/tests.lux
@@ -96,7 +96,7 @@
["_." bit]
["_." color]
["_." error]
- ["_." ident]
+ ["_." name]
["_." identity]
["_." lazy]
["_." maybe]