aboutsummaryrefslogtreecommitdiff
path: root/stdlib/test
diff options
context:
space:
mode:
authorEduardo Julian2018-07-21 22:58:54 -0400
committerEduardo Julian2018-07-21 22:58:54 -0400
commit2746f1a2d7606e3295e12e9c2e6833663658ffa8 (patch)
treeab578e1caf50a57d65c514b173be57311459786c /stdlib/test
parent7061c56c7b038a633389c35eccb4a2cfef5098d0 (diff)
Re-named "Symbol" to "Identifier".
Diffstat (limited to 'stdlib/test')
-rw-r--r--stdlib/test/test/lux/compiler/default/phase/analysis/function.lux4
-rw-r--r--stdlib/test/test/lux/compiler/default/phase/analysis/procedure/common.lux6
-rw-r--r--stdlib/test/test/lux/compiler/default/phase/analysis/reference.lux6
-rw-r--r--stdlib/test/test/lux/compiler/default/syntax.lux2
-rw-r--r--stdlib/test/test/lux/data/name.lux2
-rw-r--r--stdlib/test/test/lux/macro/code.lux4
-rw-r--r--stdlib/test/test/lux/macro/syntax.lux26
7 files changed, 25 insertions, 25 deletions
diff --git a/stdlib/test/test/lux/compiler/default/phase/analysis/function.lux b/stdlib/test/test/lux/compiler/default/phase/analysis/function.lux
index b5140f782..66c5f1a23 100644
--- a/stdlib/test/test/lux/compiler/default/phase/analysis/function.lux
+++ b/stdlib/test/test/lux/compiler/default/phase/analysis/function.lux
@@ -53,7 +53,7 @@
arg-name (|> (r.unicode +5) (r.filter (|>> (text/= func-name) not)))
[outputT outputC] _primitive.primitive
[inputT _] _primitive.primitive
- #let [g!arg (code.local-symbol arg-name)]]
+ #let [g!arg (code.local-identifier arg-name)]]
($_ seq
(test "Can analyse function."
(and (|> (typeA.with-type (All [a] (-> a outputT))
@@ -71,7 +71,7 @@
_structure.check-succeeds)))
(test "The function's name is bound to the function's type."
(|> (typeA.with-type (Rec self (-> inputT self))
- (/.function ..analyse func-name arg-name (code.local-symbol func-name)))
+ (/.function ..analyse func-name arg-name (code.local-identifier func-name)))
_structure.check-succeeds))
))))
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 70679e22a..5c7296eff 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
@@ -178,7 +178,7 @@
idxC (|> r.nat (:: @ map code.nat))
var-name (r.unicode +5)
#let [arrayT (type (Array elemT))
- g!array (code.local-symbol var-name)
+ g!array (code.local-identifier var-name)
array-operation (function (_ output-type code)
(|> (scope.with-scope ""
(scope.with-local [var-name arrayT]
@@ -253,7 +253,7 @@
(|> (scope.with-scope ""
(scope.with-local [var-name atomT]
(typeA.with-type elemT
- (_primitive.analyse (` ("lux atom read" (~ (code.symbol ["" var-name]))))))))
+ (_primitive.analyse (` ("lux atom read" (~ (code.identifier ["" var-name]))))))))
(phase.run [analysisE.bundle (init.compiler [])])
(case> (#e.Success _)
#1
@@ -265,7 +265,7 @@
(scope.with-local [var-name atomT]
(typeA.with-type Bit
(_primitive.analyse (` ("lux atom compare-and-swap"
- (~ (code.symbol ["" var-name]))
+ (~ (code.identifier ["" var-name]))
(~ elemC)
(~ elemC)))))))
(phase.run [analysisE.bundle (init.compiler [])])
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 de813de4e..5c5ac9ee5 100644
--- a/stdlib/test/test/lux/compiler/default/phase/analysis/reference.lux
+++ b/stdlib/test/test/lux/compiler/default/phase/analysis/reference.lux
@@ -60,7 +60,7 @@
(module.import def-module)
(wrap []))]
(typeA.with-inference
- (..analyse (code.symbol [def-module var-name]))))))
+ (..analyse (code.identifier [def-module var-name]))))))
(phase.run [analysisE.bundle (init.compiler [])])
check!))
@@ -78,7 +78,7 @@
(|> (scope.with-scope scope-name
(scope.with-local [var-name expectedT]
(typeA.with-inference
- (..analyse (code.local-symbol var-name)))))
+ (..analyse (code.local-identifier var-name)))))
(phase.run [analysisE.bundle (init.compiler [])])
(case> (^ (#e.Success [inferredT (#analysis.Reference (reference.local var))]))
(and (type/= expectedT inferredT)
@@ -91,7 +91,7 @@
(|> (do phase.Monad<Operation>
[_ (module.define var-name [expectedT (' {}) []])]
(typeA.with-inference
- (..analyse (code.symbol def-name))))
+ (..analyse (code.identifier def-name))))
(module.with-module +0 def-module)
(phase.run [analysisE.bundle (init.compiler [])])
(case> (^ (#e.Success [_ inferredT (#analysis.Reference (reference.constant constant-name))]))
diff --git a/stdlib/test/test/lux/compiler/default/syntax.lux b/stdlib/test/test/lux/compiler/default/syntax.lux
index a0d5ce367..8717f03fa 100644
--- a/stdlib/test/test/lux/compiler/default/syntax.lux
+++ b/stdlib/test/test/lux/compiler/default/syntax.lux
@@ -59,7 +59,7 @@
(do r.Monad<Random>
[size (|> r.nat (r/map (n/% +20)))]
(|> (r.unicode size) (r/map code.text)))
- (|> name^ (r/map code.symbol))
+ (|> name^ (r/map code.identifier))
(|> name^ (r/map code.tag))))
simple^ (: (r.Random Code)
($_ r.either
diff --git a/stdlib/test/test/lux/data/name.lux b/stdlib/test/test/lux/data/name.lux
index 699b76bb2..296e9c1bf 100644
--- a/stdlib/test/test/lux/data/name.lux
+++ b/stdlib/test/test/lux/data/name.lux
@@ -60,7 +60,7 @@
(context: "Name-related macros."
(let [(^open "&/.") &.Equivalence<Name>]
($_ seq
- (test "Can obtain Name from symbol."
+ (test "Can obtain Name from identifier."
(and (&/= ["lux" "yolo"] (name-for .yolo))
(&/= ["test/lux/data/name" "yolo"] (name-for ..yolo))
(&/= ["" "yolo"] (name-for yolo))
diff --git a/stdlib/test/test/lux/macro/code.lux b/stdlib/test/test/lux/macro/code.lux
index 735c28f64..d4739c894 100644
--- a/stdlib/test/test/lux/macro/code.lux
+++ b/stdlib/test/test/lux/macro/code.lux
@@ -24,11 +24,11 @@
[(&.frac 123.0) "123.0"]
[(&.text "\n") "\"\\n\""]
[(&.tag ["yolo" "lol"]) "#yolo.lol"]
- [(&.symbol ["yolo" "lol"]) "yolo.lol"]
+ [(&.identifier ["yolo" "lol"]) "yolo.lol"]
[(&.form (list (&.bit #1) (&.int 123))) "(#1 123)"]
[(&.tuple (list (&.bit #1) (&.int 123))) "[#1 123]"]
[(&.record (list [(&.bit #1) (&.int 123)])) "{#1 123}"]
[(&.local-tag "lol") "#lol"]
- [(&.local-symbol "lol") "lol"]
+ [(&.local-identifier "lol") "lol"]
)]
($_ seq <tests>)))
diff --git a/stdlib/test/test/lux/macro/syntax.lux b/stdlib/test/test/lux/macro/syntax.lux
index d378153bc..dfeacb0c6 100644
--- a/stdlib/test/test/lux/macro/syntax.lux
+++ b/stdlib/test/test/lux/macro/syntax.lux
@@ -72,24 +72,24 @@
(found? (s.this? (<ctor> <value>)) (list (<ctor> <value>)))
(enforced? (s.this (<ctor> <value>)) (list (<ctor> <value>)))))]
- ["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 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 name.Equivalence<Name> s.symbol]
- ["Can parse Tag syntax." ["yolo" "lol"] code.tag name.Equivalence<Name> s.tag]
+ ["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 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 Identifier syntax." ["yolo" "lol"] code.identifier name.Equivalence<Name> s.identifier]
+ ["Can parse Tag syntax." ["yolo" "lol"] code.tag name.Equivalence<Name> s.tag]
)]
($_ seq
<simple-tests>
- (test "Can parse symbols belonging to the current namespace."
+ (test "Can parse identifiers belonging to the current namespace."
(and (match "yolo"
- (p.run (list (code.local-symbol "yolo"))
- s.local-symbol))
- (fails? (p.run (list (code.symbol ["yolo" "lol"]))
- s.local-symbol))))
+ (p.run (list (code.local-identifier "yolo"))
+ s.local-identifier))
+ (fails? (p.run (list (code.identifier ["yolo" "lol"]))
+ s.local-identifier))))
(test "Can parse tags belonging to the current namespace."
(and (match "yolo"