aboutsummaryrefslogtreecommitdiff
path: root/stdlib/test
diff options
context:
space:
mode:
authorEduardo Julian2018-07-21 02:10:54 -0400
committerEduardo Julian2018-07-21 02:10:54 -0400
commit660c7fe6af927c6e668a86e44fd2f0a9b1fb8b8b (patch)
tree3110462b0bca61fd2f9082b1c352bd5346b11662 /stdlib/test
parent76e97634aaab09c89a895a6f6e863d10479821d1 (diff)
- Re-named "Compiler" to "Phase".
- Re-structured the compiler infrastructure.
Diffstat (limited to 'stdlib/test')
-rw-r--r--stdlib/test/test/lux/compiler/default/phase/analysis/case.lux (renamed from stdlib/test/test/lux/language/compiler/analysis/case.lux)15
-rw-r--r--stdlib/test/test/lux/compiler/default/phase/analysis/function.lux (renamed from stdlib/test/test/lux/language/compiler/analysis/function.lux)23
-rw-r--r--stdlib/test/test/lux/compiler/default/phase/analysis/primitive.lux (renamed from stdlib/test/test/lux/language/compiler/analysis/primitive.lux)19
-rw-r--r--stdlib/test/test/lux/compiler/default/phase/analysis/procedure/common.lux (renamed from stdlib/test/test/lux/language/compiler/analysis/procedure/common.lux)23
-rw-r--r--stdlib/test/test/lux/compiler/default/phase/analysis/reference.lux (renamed from stdlib/test/test/lux/language/compiler/analysis/reference.lux)33
-rw-r--r--stdlib/test/test/lux/compiler/default/phase/analysis/structure.lux (renamed from stdlib/test/test/lux/language/compiler/analysis/structure.lux)47
-rw-r--r--stdlib/test/test/lux/compiler/default/phase/synthesis/case.lux (renamed from stdlib/test/test/lux/language/compiler/synthesis/case.lux)23
-rw-r--r--stdlib/test/test/lux/compiler/default/phase/synthesis/function.lux (renamed from stdlib/test/test/lux/language/compiler/synthesis/function.lux)27
-rw-r--r--stdlib/test/test/lux/compiler/default/phase/synthesis/primitive.lux (renamed from stdlib/test/test/lux/language/compiler/synthesis/primitive.lux)17
-rw-r--r--stdlib/test/test/lux/compiler/default/phase/synthesis/structure.lux (renamed from stdlib/test/test/lux/language/compiler/synthesis/structure.lux)19
-rw-r--r--stdlib/test/test/lux/compiler/default/syntax.lux (renamed from stdlib/test/test/lux/language/syntax.lux)5
-rw-r--r--stdlib/test/tests.lux80
12 files changed, 171 insertions, 160 deletions
diff --git a/stdlib/test/test/lux/language/compiler/analysis/case.lux b/stdlib/test/test/lux/compiler/default/phase/analysis/case.lux
index 5956cc48e..fd516d048 100644
--- a/stdlib/test/test/lux/language/compiler/analysis/case.lux
+++ b/stdlib/test/test/lux/compiler/default/phase/analysis/case.lux
@@ -16,12 +16,13 @@
["." check]]
[macro
["." code]]
- [language
- ["." compiler
- ["." analysis
- ["." module]
- [".A" type]
- ["/" case]]]]
+ [compiler
+ [default
+ ["." phase
+ ["." analysis
+ ["." module]
+ [".A" type]
+ ["/" case]]]]]
test]
[//
["_." primitive]
@@ -170,7 +171,7 @@
analyse-pm (|>> (/.case _primitive.analyse inputC)
(typeA.with-type outputT)
analysis.with-scope
- (do compiler.Monad<Operation>
+ (do phase.Monad<Operation>
[_ (module.declare-tags variant-tags #0
(#.Named [module-name variant-name]
(type.variant primitivesT)))
diff --git a/stdlib/test/test/lux/language/compiler/analysis/function.lux b/stdlib/test/test/lux/compiler/default/phase/analysis/function.lux
index 22ff04213..b5140f782 100644
--- a/stdlib/test/test/lux/language/compiler/analysis/function.lux
+++ b/stdlib/test/test/lux/compiler/default/phase/analysis/function.lux
@@ -16,28 +16,29 @@
["." type]
["." macro
["." code]]
- ["." language
- ["." reference]
- ["." compiler
+ [compiler
+ ["." default
+ ["." reference]
["." init]
- ["." analysis (#+ Analysis Operation)
- [".A" type]
- ["." expression]
- ["/" function]]
- [extension
- [".E" analysis]]]]
+ ["." phase
+ ["." analysis (#+ Analysis Operation)
+ [".A" type]
+ ["." expression]
+ ["/" function]]
+ [extension
+ [".E" analysis]]]]]
test]
[//
["_." primitive]
["_." structure]])
-(def: analyse (expression.analyser (:coerce language.Eval [])))
+(def: analyse (expression.analyser (:coerce default.Eval [])))
(def: (check-apply expectedT num-args analysis)
(-> Type Nat (Operation Analysis) Bit)
(|> analysis
(typeA.with-type expectedT)
- (compiler.run [analysisE.bundle (init.compiler [])])
+ (phase.run [analysisE.bundle (init.compiler [])])
(case> (#e.Success applyA)
(let [[funcA argsA] (analysis.application applyA)]
(n/= num-args (list.size argsA)))
diff --git a/stdlib/test/test/lux/language/compiler/analysis/primitive.lux b/stdlib/test/test/lux/compiler/default/phase/analysis/primitive.lux
index adad90f18..ce34ff887 100644
--- a/stdlib/test/test/lux/language/compiler/analysis/primitive.lux
+++ b/stdlib/test/test/lux/compiler/default/phase/analysis/primitive.lux
@@ -13,17 +13,18 @@
[".L" type ("type/." Equivalence<Type>)]
[macro
["." code]]
- ["." language
- ["." compiler
+ [compiler
+ ["." default
["." init]
- ["." analysis (#+ Analysis Operation)
- [".A" type]
- ["." expression]]
- [extension
- [".E" analysis]]]]
+ ["." phase
+ ["." analysis (#+ Analysis Operation)
+ [".A" type]
+ ["." expression]]
+ [extension
+ [".E" analysis]]]]]
test])
-(def: #export analyse (expression.analyser (:coerce language.Eval [])))
+(def: #export analyse (expression.analyser (:coerce default.Eval [])))
(def: unit
(r.Random Code)
@@ -52,7 +53,7 @@
(-> Type (Operation Analysis) (e.Error Analysis))
(|> analysis
typeA.with-inference
- (compiler.run [analysisE.bundle (init.compiler [])])
+ (phase.run [analysisE.bundle (init.compiler [])])
(case> (#e.Success [inferred-type output])
(if (is? expected-type inferred-type)
(#e.Success output)
diff --git a/stdlib/test/test/lux/language/compiler/analysis/procedure/common.lux b/stdlib/test/test/lux/compiler/default/phase/analysis/procedure/common.lux
index 2a5cc2ee3..70679e22a 100644
--- a/stdlib/test/test/lux/language/compiler/analysis/procedure/common.lux
+++ b/stdlib/test/test/lux/compiler/default/phase/analysis/procedure/common.lux
@@ -16,14 +16,15 @@
[type ("type/." Equivalence<Type>)]
[macro
["." code]]
- [language
- ["." compiler
+ [compiler
+ [default
["." init]
- [analysis
- ["." scope]
- [".A" type]]
- [extension
- [".E" analysis]]]]
+ ["." phase
+ [analysis
+ ["." scope]
+ [".A" type]]
+ [extension
+ [".E" analysis]]]]]
test]
[///
["_." primitive]])
@@ -34,7 +35,7 @@
(|> (scope.with-scope ""
(typeA.with-type output-type
(_primitive.analyse (` ((~ (code.text procedure)) (~+ params))))))
- (compiler.run [analysisE.bundle (init.compiler [])])
+ (phase.run [analysisE.bundle (init.compiler [])])
(case> (#e.Success _)
<success>
@@ -183,7 +184,7 @@
(scope.with-local [var-name arrayT]
(typeA.with-type output-type
(_primitive.analyse code))))
- (compiler.run [analysisE.bundle (init.compiler [])])
+ (phase.run [analysisE.bundle (init.compiler [])])
(case> (#e.Success _)
#1
@@ -253,7 +254,7 @@
(scope.with-local [var-name atomT]
(typeA.with-type elemT
(_primitive.analyse (` ("lux atom read" (~ (code.symbol ["" var-name]))))))))
- (compiler.run [analysisE.bundle (init.compiler [])])
+ (phase.run [analysisE.bundle (init.compiler [])])
(case> (#e.Success _)
#1
@@ -267,7 +268,7 @@
(~ (code.symbol ["" var-name]))
(~ elemC)
(~ elemC)))))))
- (compiler.run [analysisE.bundle (init.compiler [])])
+ (phase.run [analysisE.bundle (init.compiler [])])
(case> (#e.Success _)
#1
diff --git a/stdlib/test/test/lux/language/compiler/analysis/reference.lux b/stdlib/test/test/lux/compiler/default/phase/analysis/reference.lux
index 66c990ef4..6a103d155 100644
--- a/stdlib/test/test/lux/language/compiler/analysis/reference.lux
+++ b/stdlib/test/test/lux/compiler/default/phase/analysis/reference.lux
@@ -12,22 +12,23 @@
[type ("type/." Equivalence<Type>)]
[macro
["." code]]
- ["." language
- ["." reference]
- ["." compiler
+ [compiler
+ ["." default
+ ["." reference]
["." init]
- ["." analysis
- ["." scope]
- ["." module]
- [".A" type]
- ["." expression]]
- [extension
- [".E" analysis]]]]
+ ["." phase
+ ["." analysis
+ ["." scope]
+ ["." module]
+ [".A" type]
+ ["." expression]]
+ [extension
+ [".E" analysis]]]]]
test]
[//
["_." primitive]])
-(def: analyse (expression.analyser (:coerce language.Eval [])))
+(def: analyse (expression.analyser (:coerce default.Eval [])))
(type: Check (-> (e.Error Any) Bit))
@@ -46,7 +47,7 @@
(def: (reach-test var-name [export? def-module] [import? dependent-module] check!)
(-> Text [Bit Text] [Bit Text] Check Bit)
- (|> (do compiler.Monad<Operation>
+ (|> (do phase.Monad<Operation>
[_ (module.with-module +0 def-module
(module.define var-name [Any
(if export?
@@ -60,7 +61,7 @@
(wrap []))]
(typeA.with-inference
(..analyse (code.symbol [def-module var-name]))))))
- (compiler.run [analysisE.bundle (init.compiler [])])
+ (phase.run [analysisE.bundle (init.compiler [])])
check!))
(context: "References"
@@ -78,7 +79,7 @@
(scope.with-local [var-name expectedT]
(typeA.with-inference
(..analyse (code.local-symbol var-name)))))
- (compiler.run [analysisE.bundle (init.compiler [])])
+ (phase.run [analysisE.bundle (init.compiler [])])
(case> (^ (#e.Success [inferredT (#analysis.Reference (reference.local var))]))
(and (type/= expectedT inferredT)
(n/= +0 var))
@@ -87,12 +88,12 @@
#0)))
(test "Can analyse definition (in the same module)."
(let [def-name [def-module var-name]]
- (|> (do compiler.Monad<Operation>
+ (|> (do phase.Monad<Operation>
[_ (module.define var-name [expectedT (' {}) []])]
(typeA.with-inference
(..analyse (code.symbol def-name))))
(module.with-module +0 def-module)
- (compiler.run [analysisE.bundle (init.compiler [])])
+ (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))
diff --git a/stdlib/test/test/lux/language/compiler/analysis/structure.lux b/stdlib/test/test/lux/compiler/default/phase/analysis/structure.lux
index 6dca4fb12..eb517be72 100644
--- a/stdlib/test/test/lux/language/compiler/analysis/structure.lux
+++ b/stdlib/test/test/lux/compiler/default/phase/analysis/structure.lux
@@ -18,26 +18,27 @@
["." check]]
[macro
["." code]]
- ["." language
- ["." compiler
+ [compiler
+ ["." default
["." init]
- ["." analysis (#+ Analysis Variant Tag Operation)
- ["." module]
- [".A" type]
- ["/" structure]
- ["." expression]]
- [extension
- [".E" analysis]]]]
+ ["." phase
+ ["." analysis (#+ Analysis Variant Tag Operation)
+ ["." module]
+ [".A" type]
+ ["/" structure]
+ ["." expression]]
+ [extension
+ [".E" analysis]]]]]
test]
[//
["_." primitive]])
-(def: analyse (expression.analyser (:coerce language.Eval [])))
+(def: analyse (expression.analyser (:coerce default.Eval [])))
(do-template [<name> <on-success> <on-error>]
[(def: #export <name>
(All [a] (-> (Operation a) Bit))
- (|>> (compiler.run [analysisE.bundle (init.compiler [])])
+ (|>> (phase.run [analysisE.bundle (init.compiler [])])
(case> (#e.Success _)
<on-success>
@@ -61,7 +62,7 @@
(-> Type Nat Tag (Operation Analysis) Bit)
(|> analysis
(typeA.with-type type)
- (compiler.run [analysisE.bundle (init.compiler [])])
+ (phase.run [analysisE.bundle (init.compiler [])])
(case> (^multi (#e.Success sumA)
[(analysis.variant sumA)
(#.Some variant)])
@@ -72,7 +73,7 @@
(def: (tagged module tags type)
(All [a] (-> Text (List module.Tag) Type (Operation a) (Operation [Module a])))
- (|>> (do compiler.Monad<Operation>
+ (|>> (do phase.Monad<Operation>
[_ (module.declare-tags tags #0 type)])
(module.with-module +0 module)))
@@ -81,7 +82,7 @@
(|> analysis
(tagged module tags type)
(typeA.with-type type)
- (compiler.run [analysisE.bundle (init.compiler [])])
+ (phase.run [analysisE.bundle (init.compiler [])])
(case> (^multi (#e.Success [_ sumA])
[(analysis.variant sumA)
(#.Some variant)])
@@ -98,7 +99,7 @@
(-> Text (List module.Tag) Type Nat (Operation [Type Analysis]) Bit)
(|> analysis
(tagged module tags type)
- (compiler.run [analysisE.bundle (init.compiler [])])
+ (phase.run [analysisE.bundle (init.compiler [])])
(case> (#e.Success [_ productT productA])
(and (type/= type productT)
(right-size? size productA))
@@ -127,13 +128,13 @@
(check-sum variantT size choice
(/.sum ..analyse choice valueC)))
(test "Can analyse sum through bound type-vars."
- (|> (do compiler.Monad<Operation>
+ (|> (do phase.Monad<Operation>
[[_ varT] (typeA.with-env check.var)
_ (typeA.with-env
(check.check varT variantT))]
(typeA.with-type varT
(/.sum ..analyse choice valueC)))
- (compiler.run [analysisE.bundle (init.compiler [])])
+ (phase.run [analysisE.bundle (init.compiler [])])
(case> (^multi (#e.Success sumA)
[(analysis.variant sumA)
(#.Some variant)])
@@ -142,7 +143,7 @@
_
#0)))
(test "Cannot analyse sum through unbound type-vars."
- (|> (do compiler.Monad<Operation>
+ (|> (do phase.Monad<Operation>
[[_ varT] (typeA.with-env check.var)]
(typeA.with-type varT
(/.sum ..analyse choice valueC)))
@@ -177,7 +178,7 @@
(test "Can analyse product."
(|> (typeA.with-type tupleT
(/.product ..analyse (list/map product.right primitives)))
- (compiler.run [analysisE.bundle (init.compiler [])])
+ (phase.run [analysisE.bundle (init.compiler [])])
(case> (#e.Success tupleA)
(right-size? size tupleA)
@@ -186,7 +187,7 @@
(test "Can infer product."
(|> (typeA.with-inference
(/.product ..analyse (list/map product.right primitives)))
- (compiler.run [analysisE.bundle (init.compiler [])])
+ (phase.run [analysisE.bundle (init.compiler [])])
(case> (#e.Success [_type tupleA])
(and (type/= tupleT _type)
(right-size? size tupleA))
@@ -198,13 +199,13 @@
(..analyse (` [(~ singletonC)])))
check-succeeds))
(test "Can analyse product through bound type-vars."
- (|> (do compiler.Monad<Operation>
+ (|> (do phase.Monad<Operation>
[[_ varT] (typeA.with-env check.var)
_ (typeA.with-env
(check.check varT (type.tuple (list/map product.left primitives))))]
(typeA.with-type varT
(/.product ..analyse (list/map product.right primitives))))
- (compiler.run [analysisE.bundle (init.compiler [])])
+ (phase.run [analysisE.bundle (init.compiler [])])
(case> (#e.Success tupleA)
(right-size? size tupleA)
@@ -290,7 +291,7 @@
(/.record ..analyse recordC))
(check-record-inference module-name tags named-polyT size)))
(test "Can specialize generic records."
- (|> (do compiler.Monad<Operation>
+ (|> (do phase.Monad<Operation>
[recordA (typeA.with-type tupleT
(/.record ..analyse recordC))]
(wrap [tupleT recordA]))
diff --git a/stdlib/test/test/lux/language/compiler/synthesis/case.lux b/stdlib/test/test/lux/compiler/default/phase/synthesis/case.lux
index 70e13af4b..ad0d5c60a 100644
--- a/stdlib/test/test/lux/language/compiler/synthesis/case.lux
+++ b/stdlib/test/test/lux/compiler/default/phase/synthesis/case.lux
@@ -5,14 +5,15 @@
pipe]
[data
["." error ("error/." Functor<Error>)]]
- [language
- ["." reference]
- ["." compiler
- ["." analysis (#+ Branch Analysis)]
- ["//" synthesis (#+ Synthesis)
- ["." expression]]
- [extension
- ["." bundle]]]]
+ [compiler
+ [default
+ ["." reference]
+ ["." phase
+ ["." analysis (#+ Branch Analysis)]
+ ["//" synthesis (#+ Synthesis)
+ ["." expression]]
+ [extension
+ ["." bundle]]]]]
[math
["r" random]]
test]
@@ -31,7 +32,7 @@
(test "Dummy variables created to mask expressions get eliminated during synthesis."
(|> maskA
expression.synthesize
- (compiler.run [bundle.empty //.init])
+ (phase.run [bundle.empty //.init])
(error/map (//primitive.corresponds? maskedA))
(error.default #0))))))
@@ -49,7 +50,7 @@
(test "Can detect and reify simple 'let' expressions."
(|> letA
expression.synthesize
- (compiler.run [bundle.empty //.init])
+ (phase.run [bundle.empty //.init])
(case> (^ (#error.Success (//.branch/let [inputS registerS outputS])))
(and (n/= registerA registerS)
(//primitive.corresponds? inputA inputS)
@@ -77,7 +78,7 @@
(test "Can detect and reify simple 'if' expressions."
(|> ifA
expression.synthesize
- (compiler.run [bundle.empty //.init])
+ (phase.run [bundle.empty //.init])
(case> (^ (#error.Success (//.branch/if [inputS thenS elseS])))
(and (//primitive.corresponds? inputA inputS)
(//primitive.corresponds? thenA thenS)
diff --git a/stdlib/test/test/lux/language/compiler/synthesis/function.lux b/stdlib/test/test/lux/compiler/default/phase/synthesis/function.lux
index 62d8c97a0..2249acca1 100644
--- a/stdlib/test/test/lux/language/compiler/synthesis/function.lux
+++ b/stdlib/test/test/lux/compiler/default/phase/synthesis/function.lux
@@ -14,14 +14,15 @@
["." list ("list/." Functor<List> Fold<List>)]
["dict" dictionary (#+ Dictionary)]
["." set]]]
- [language
- ["." reference (#+ Variable) ("variable/." Equivalence<Variable>)]
- ["." compiler
- ["." analysis (#+ Arity Analysis)]
- ["//" synthesis (#+ Synthesis)
- ["." expression]]
- [extension
- ["." bundle]]]]
+ [compiler
+ [default
+ ["." reference (#+ Variable) ("variable/." Equivalence<Variable>)]
+ ["." phase
+ ["." analysis (#+ Arity Analysis)]
+ ["//" synthesis (#+ Synthesis)
+ ["." expression]]
+ [extension
+ ["." bundle]]]]]
[math
["r" random]]
test]
@@ -115,7 +116,7 @@
(test "Nested functions will get folded together."
(|> function//constant
expression.synthesize
- (compiler.run [bundle.empty //.init])
+ (phase.run [bundle.empty //.init])
(case> (^ (#error.Success (//.function/abstraction [environment arity output])))
(and (n/= arity//constant arity)
(//primitive.corresponds? prediction//constant output))
@@ -125,7 +126,7 @@
(test "Folded functions provide direct access to environment variables."
(|> function//environment
expression.synthesize
- (compiler.run [bundle.empty //.init])
+ (phase.run [bundle.empty //.init])
(case> (^ (#error.Success (//.function/abstraction [environment arity (#//.Reference (reference.variable output))])))
(and (n/= arity//environment arity)
(variable/= prediction//environment output))
@@ -135,7 +136,7 @@
(test "Folded functions properly offset local variables."
(|> function//local
expression.synthesize
- (compiler.run [bundle.empty //.init])
+ (phase.run [bundle.empty //.init])
(case> (^ (#error.Success (//.function/abstraction [environment arity (#//.Reference (reference.variable output))])))
(and (n/= arity//local arity)
(variable/= prediction//local output))
@@ -154,7 +155,7 @@
(test "Can synthesize function application."
(|> (analysis.apply [funcA argsA])
expression.synthesize
- (compiler.run [bundle.empty //.init])
+ (phase.run [bundle.empty //.init])
(case> (^ (#error.Success (//.function/apply [funcS argsS])))
(and (//primitive.corresponds? funcA funcS)
(list.every? (product.uncurry //primitive.corresponds?)
@@ -165,7 +166,7 @@
(test "Function application on no arguments just synthesizes to the function itself."
(|> (analysis.apply [funcA (list)])
expression.synthesize
- (compiler.run [bundle.empty //.init])
+ (phase.run [bundle.empty //.init])
(case> (#error.Success funcS)
(//primitive.corresponds? funcA funcS)
diff --git a/stdlib/test/test/lux/language/compiler/synthesis/primitive.lux b/stdlib/test/test/lux/compiler/default/phase/synthesis/primitive.lux
index c4cc940f1..4312f2bae 100644
--- a/stdlib/test/test/lux/language/compiler/synthesis/primitive.lux
+++ b/stdlib/test/test/lux/compiler/default/phase/synthesis/primitive.lux
@@ -7,13 +7,14 @@
["." error]
[text
format]]
- [language
- ["." compiler
- ["." analysis (#+ Analysis)]
- ["//" synthesis (#+ Synthesis)
- ["." expression]]
- [extension
- ["." bundle]]]]
+ [compiler
+ [default
+ ["." phase
+ ["." analysis (#+ Analysis)]
+ ["//" synthesis (#+ Synthesis)
+ ["." expression]]
+ [extension
+ ["." bundle]]]]]
[math
["r" random]]
test])
@@ -80,7 +81,7 @@
[(test (format "Can synthesize " <desc> ".")
(|> (#analysis.Primitive (<analysis> <sample>))
expression.synthesize
- (compiler.run [bundle.empty //.init])
+ (phase.run [bundle.empty //.init])
(case> (#error.Success (#//.Primitive (<synthesis> value)))
(is? <sample> value)
diff --git a/stdlib/test/test/lux/language/compiler/synthesis/structure.lux b/stdlib/test/test/lux/compiler/default/phase/synthesis/structure.lux
index dcec26fb9..924a4126d 100644
--- a/stdlib/test/test/lux/language/compiler/synthesis/structure.lux
+++ b/stdlib/test/test/lux/compiler/default/phase/synthesis/structure.lux
@@ -9,13 +9,14 @@
["." error]
[collection
["." list]]]
- [language
- ["." compiler
- ["." analysis]
- ["//" synthesis (#+ Synthesis)
- ["." expression]]
- [extension
- ["." bundle]]]]
+ [compiler
+ [default
+ ["." phase
+ ["." analysis]
+ ["//" synthesis (#+ Synthesis)
+ ["." expression]]
+ [extension
+ ["." bundle]]]]]
[math
["r" random]]
test]
@@ -31,7 +32,7 @@
(test "Can synthesize variants."
(|> (analysis.sum-analysis size tagA memberA)
expression.synthesize
- (compiler.run [bundle.empty //.init])
+ (phase.run [bundle.empty //.init])
(case> (#error.Success (#//.Structure (#//.Variant [leftsS right?S valueS])))
(let [tagS (if right?S (inc leftsS) leftsS)]
(and (n/= tagA tagS)
@@ -51,7 +52,7 @@
(test "Can synthesize tuple."
(|> (analysis.product-analysis membersA)
expression.synthesize
- (compiler.run [bundle.empty //.init])
+ (phase.run [bundle.empty //.init])
(case> (#error.Success (#//.Structure (#//.Tuple membersS)))
(and (n/= size (list.size membersS))
(list.every? (product.uncurry //primitive.corresponds?)
diff --git a/stdlib/test/test/lux/language/syntax.lux b/stdlib/test/test/lux/compiler/default/syntax.lux
index 469e07c10..42ae7f379 100644
--- a/stdlib/test/test/lux/language/syntax.lux
+++ b/stdlib/test/test/lux/compiler/default/syntax.lux
@@ -15,8 +15,9 @@
["r" random ("r/." Monad<Random>)]]
[macro
["." code]]
- [language
- ["&" syntax]]
+ [compiler
+ [default
+ ["&" syntax]]]
test])
(def: default-cursor
diff --git a/stdlib/test/tests.lux b/stdlib/test/tests.lux
index bdd8ef0ab..e855220dd 100644
--- a/stdlib/test/tests.lux
+++ b/stdlib/test/tests.lux
@@ -39,32 +39,31 @@
[world
["._" environment]
["._" console]]
- [language
+ [compiler
[host
[".H" scheme]]
- [compiler
- ["._" translation
- [scheme
- ["._scheme" primitive]
- ["._scheme" structure]
- ["._scheme" reference]
- ["._scheme" function]
- ["._scheme" loop]
- ["._scheme" case]
- ["._scheme" extension]
- ["._scheme" extension/common]
- ["._scheme" expression]]]
- [default
- [repl
- ["._" type]]]
- [meta
- ["._meta" io
- ["._meta_io" context]
- ["._meta_io" archive]]
- ["._meta" archive]
- ["._meta" cache]]
- [default
- ["._default" cache]]]]]
+ [default
+ [phase
+ ["._" translation
+ [scheme
+ ["._scheme" primitive]
+ ["._scheme" structure]
+ ["._scheme" reference]
+ ["._scheme" function]
+ ["._scheme" loop]
+ ["._scheme" case]
+ ["._scheme" extension]
+ ["._scheme" extension/common]
+ ["._scheme" expression]]]]
+ ["._default" cache]
+ [repl
+ ["._" type]]]
+ [meta
+ ["._meta" io
+ ["._meta_io" context]
+ ["._meta_io" archive]]
+ ["._meta" archive]
+ ["._meta" cache]]]]
[test
["_." lux]
[lux
@@ -150,22 +149,23 @@
[object
["_." interface]
["_." protocol]]]
- [language
- ["_language/." syntax]
- [compiler
- [analysis
- ["_.A" primitive]
- ["_.A" structure]
- ["_.A" reference]
- ["_.A" case]
- ["_.A" function]
- [procedure
- ["_.A" common]]]
- [synthesis
- ["_.S" primitive]
- ["_.S" structure]
- ["_.S" case]
- ["_.S" function]]]]
+ [compiler
+ [default
+ ["_default/." syntax]
+ [phase
+ [analysis
+ ["_.A" primitive]
+ ["_.A" structure]
+ ["_.A" reference]
+ ["_.A" case]
+ ["_.A" function]
+ [procedure
+ ["_.A" common]]]
+ [synthesis
+ ["_.S" primitive]
+ ["_.S" structure]
+ ["_.S" case]
+ ["_.S" function]]]]]
[world
["_." binary]
## ["_." file] ## TODO: Specially troublesome...