aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test/lux/tool/compiler
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/test/lux/tool/compiler/default/syntax.lux2
-rw-r--r--stdlib/source/test/lux/tool/compiler/phase/analysis/function.lux8
-rw-r--r--stdlib/source/test/lux/tool/compiler/phase/analysis/primitive.lux21
-rw-r--r--stdlib/source/test/lux/tool/compiler/phase/analysis/reference.lux14
-rw-r--r--stdlib/source/test/lux/tool/compiler/phase/analysis/structure.lux20
-rw-r--r--stdlib/source/test/lux/tool/compiler/phase/extension/analysis/lux.lux6
-rw-r--r--stdlib/source/test/lux/tool/compiler/phase/synthesis/case.lux13
-rw-r--r--stdlib/source/test/lux/tool/compiler/phase/synthesis/function.lux14
-rw-r--r--stdlib/source/test/lux/tool/compiler/phase/synthesis/primitive.lux7
-rw-r--r--stdlib/source/test/lux/tool/compiler/phase/synthesis/structure.lux8
10 files changed, 55 insertions, 58 deletions
diff --git a/stdlib/source/test/lux/tool/compiler/default/syntax.lux b/stdlib/source/test/lux/tool/compiler/default/syntax.lux
index a9744dfb6..1b9e5c7a4 100644
--- a/stdlib/source/test/lux/tool/compiler/default/syntax.lux
+++ b/stdlib/source/test/lux/tool/compiler/default/syntax.lux
@@ -7,10 +7,10 @@
["r" math/random (#+ Random) ("#@." monad)]
["_" test (#+ Test)]
[control
+ ["." try]
[parser
["l" text]]]
[data
- ["." error]
["." text]
[collection
["." list]
diff --git a/stdlib/source/test/lux/tool/compiler/phase/analysis/function.lux b/stdlib/source/test/lux/tool/compiler/phase/analysis/function.lux
index 08346c47b..7d5046571 100644
--- a/stdlib/source/test/lux/tool/compiler/phase/analysis/function.lux
+++ b/stdlib/source/test/lux/tool/compiler/phase/analysis/function.lux
@@ -7,9 +7,9 @@
["r" math/random (#+ Random) ("#@." monad)]
["_" test (#+ Test)]
[control
- pipe]
+ pipe
+ ["." try]]
[data
- ["." error]
["." maybe]
["." product]
["." text ("#@." equivalence)]
@@ -36,11 +36,11 @@
(|> analysis
(//type.with-type expectedT)
(///.run _primitive.state)
- (case> (#error.Success applyA)
+ (case> (#try.Success applyA)
(let [[funcA argsA] (////analysis.application applyA)]
(n/= num-args (list.size argsA)))
- (#error.Failure error)
+ (#try.Failure _)
false)))
(def: abstraction
diff --git a/stdlib/source/test/lux/tool/compiler/phase/analysis/primitive.lux b/stdlib/source/test/lux/tool/compiler/phase/analysis/primitive.lux
index 1a7aec26f..57c3152d9 100644
--- a/stdlib/source/test/lux/tool/compiler/phase/analysis/primitive.lux
+++ b/stdlib/source/test/lux/tool/compiler/phase/analysis/primitive.lux
@@ -9,9 +9,8 @@
["_" test (#+ Test)]
[control
pipe
+ ["." try (#+ Try)]
["." exception (#+ exception:)]]
- [data
- ["." error (#+ Error)]]
["." type ("#@." equivalence)]
[macro
["." code]]]
@@ -32,12 +31,12 @@
(def: #export (expander macro inputs state)
Expander
- (#error.Failure "NOPE"))
+ (#try.Failure "NOPE"))
(def: #export (eval count type expression)
Eval
(function (_ state)
- (#error.Failure "NO!")))
+ (#try.Failure "NO!")))
(def: #export phase
////analysis.Phase
@@ -69,24 +68,24 @@
["Inferred" (%.type inferred)]))
(def: (infer expected-type analysis)
- (-> Type (Operation Analysis) (Error Analysis))
+ (-> Type (Operation Analysis) (Try Analysis))
(|> analysis
//type.with-inference
(///.run ..state)
- (case> (#error.Success [inferred-type output])
+ (case> (#try.Success [inferred-type output])
(if (is? expected-type inferred-type)
- (#error.Success output)
+ (#try.Success output)
(exception.throw wrong-inference [expected-type inferred-type]))
- (#error.Failure error)
- (#error.Failure error))))
+ (#try.Failure error)
+ (#try.Failure error))))
(def: #export test
(<| (_.context (name.module (name-of /._)))
(`` ($_ _.and
(_.test (%.name (name-of #////analysis.Unit))
(|> (infer Any (..phase (' [])))
- (case> (^ (#error.Success (#////analysis.Primitive (#////analysis.Unit output))))
+ (case> (^ (#try.Success (#////analysis.Primitive (#////analysis.Unit output))))
(is? [] output)
_
@@ -96,7 +95,7 @@
[sample <random>]
(_.test (%.name (name-of <tag>))
(|> (infer <type> (..phase (<constructor> sample)))
- (case> (#error.Success (#////analysis.Primitive (<tag> output)))
+ (case> (#try.Success (#////analysis.Primitive (<tag> output)))
(is? sample output)
_
diff --git a/stdlib/source/test/lux/tool/compiler/phase/analysis/reference.lux b/stdlib/source/test/lux/tool/compiler/phase/analysis/reference.lux
index 427e0dc2c..777fe152f 100644
--- a/stdlib/source/test/lux/tool/compiler/phase/analysis/reference.lux
+++ b/stdlib/source/test/lux/tool/compiler/phase/analysis/reference.lux
@@ -6,9 +6,9 @@
["r" math/random (#+ Random) ("#@." monad)]
["_" test (#+ Test)]
[control
- pipe]
+ pipe
+ ["." try (#+ Try)]]
[data
- ["." error (#+ Error)]
["." text ("#@." equivalence)]]
["." type ("#@." equivalence)]
[macro
@@ -26,15 +26,15 @@
["#." reference]
["#." analysis (#+ Analysis Variant Tag Operation)]]]]]})
-(type: Check (-> (Error Any) Bit))
+(type: Check (-> (Try Any) Bit))
(template [<name> <on-success> <on-failure>]
[(def: <name>
Check
- (|>> (case> (#error.Success _)
+ (|>> (case> (#try.Success _)
<on-success>
- (#error.Failure error)
+ (#try.Failure _)
<on-failure>)))]
[success? true false]
@@ -72,7 +72,7 @@
(//type.with-inference
(_primitive.phase (code.local-identifier var-name)))))
(///.run _primitive.state)
- (case> (^ (#error.Success [inferredT (#////analysis.Reference (////reference.local var))]))
+ (case> (^ (#try.Success [inferredT (#////analysis.Reference (////reference.local var))]))
(and (type@= expectedT inferredT)
(n/= 0 var))
@@ -86,7 +86,7 @@
(_primitive.phase (code.identifier def-name))))
(//module.with-module 0 def-module)
(///.run _primitive.state)
- (case> (^ (#error.Success [_ inferredT (#////analysis.Reference (////reference.constant constant-name))]))
+ (case> (^ (#try.Success [_ inferredT (#////analysis.Reference (////reference.constant constant-name))]))
(and (type@= expectedT inferredT)
(name@= def-name constant-name))
diff --git a/stdlib/source/test/lux/tool/compiler/phase/analysis/structure.lux b/stdlib/source/test/lux/tool/compiler/phase/analysis/structure.lux
index 156965a55..08344f23e 100644
--- a/stdlib/source/test/lux/tool/compiler/phase/analysis/structure.lux
+++ b/stdlib/source/test/lux/tool/compiler/phase/analysis/structure.lux
@@ -7,10 +7,10 @@
["r" math/random (#+ Random) ("#@." monad)]
["_" test (#+ Test)]
[control
- pipe]
+ pipe
+ ["." try]]
[data
["." bit ("#@." equivalence)]
- ["." error]
["." product]
["." maybe]
["." text]
@@ -36,7 +36,7 @@
[(def: #export <name>
(All [a] (-> (Operation a) Bit))
(|>> (///.run _primitive.state)
- (case> (#error.Success _)
+ (case> (#try.Success _)
<on-success>
_
@@ -64,7 +64,7 @@
(|> analysis
(//type.with-type type)
(///.run _primitive.state)
- (case> (^ (#error.Success (////analysis.variant variant)))
+ (case> (^ (#try.Success (////analysis.variant variant)))
(check-sum' tag size variant)
_
@@ -82,7 +82,7 @@
(with-tags module tags variantT)
(//type.with-type expectedT)
(///.run _primitive.state)
- (case> (^ (#error.Success [_ (////analysis.variant variant)]))
+ (case> (^ (#try.Success [_ (////analysis.variant variant)]))
(check-sum' tag (list.size tags) variant)
_
@@ -104,7 +104,7 @@
(with-tags module tags recordT)
(//type.with-type expectedT)
(///.run _primitive.state)
- (case> (#error.Success [_ productA])
+ (case> (#try.Success [_ productA])
(correct-size? size productA)
_
@@ -138,7 +138,7 @@
(//type.with-type varT
(/.sum _primitive.phase choice valueC)))
(///.run _primitive.state)
- (case> (^ (#error.Success (////analysis.variant variant)))
+ (case> (^ (#try.Success (////analysis.variant variant)))
(check-sum' choice size variant)
_
@@ -180,7 +180,7 @@
(|> (//type.with-type tupleT
(/.product _primitive.phase (list@map product.right primitives)))
(///.run _primitive.state)
- (case> (#error.Success tupleA)
+ (case> (#try.Success tupleA)
(correct-size? size tupleA)
_
@@ -189,7 +189,7 @@
(|> (//type.with-inference
(/.product _primitive.phase (list@map product.right primitives)))
(///.run _primitive.state)
- (case> (#error.Success [_type tupleA])
+ (case> (#try.Success [_type tupleA])
(and (check.checks? tupleT _type)
(correct-size? size tupleA))
@@ -207,7 +207,7 @@
(//type.with-type varT
(/.product _primitive.phase (list@map product.right primitives))))
(///.run _primitive.state)
- (case> (#error.Success tupleA)
+ (case> (#try.Success tupleA)
(correct-size? size tupleA)
_
diff --git a/stdlib/source/test/lux/tool/compiler/phase/extension/analysis/lux.lux b/stdlib/source/test/lux/tool/compiler/phase/extension/analysis/lux.lux
index 1b89d30d4..c659d9db0 100644
--- a/stdlib/source/test/lux/tool/compiler/phase/extension/analysis/lux.lux
+++ b/stdlib/source/test/lux/tool/compiler/phase/extension/analysis/lux.lux
@@ -9,10 +9,10 @@
[control
pipe
[io (#+ IO)]
+ ["." try]
[concurrency
["." atom]]]
[data
- ["." error]
["." product]]
["." type ("#@." equivalence)]
[macro
@@ -34,10 +34,10 @@
(////type.with-type output-type
(_primitive.phase (` ((~ (code.text procedure)) (~+ params))))))
(////.run _primitive.state)
- (case> (#error.Success _)
+ (case> (#try.Success _)
<success>
- (#error.Failure error)
+ (#try.Failure _)
<failure>)))]
[check-success+ true false]
diff --git a/stdlib/source/test/lux/tool/compiler/phase/synthesis/case.lux b/stdlib/source/test/lux/tool/compiler/phase/synthesis/case.lux
index b5a03fd9f..d2d310fa1 100644
--- a/stdlib/source/test/lux/tool/compiler/phase/synthesis/case.lux
+++ b/stdlib/source/test/lux/tool/compiler/phase/synthesis/case.lux
@@ -6,9 +6,8 @@
["r" math/random (#+ Random) ("#@." monad)]
["_" test (#+ Test)]
[control
- pipe]
- [data
- ["." error ("#@." functor)]]]
+ pipe
+ ["." try ("#@." functor)]]]
["." // #_
["#." primitive]]
{1
@@ -36,8 +35,8 @@
(|> maskA
//.phase
(///.run [///bundle.empty ////synthesis.init])
- (error@map (//primitive.corresponds? maskedA))
- (error.default false)))))
+ (try@map (//primitive.corresponds? maskedA))
+ (try.default false)))))
(def: let-expr
Test
@@ -54,7 +53,7 @@
(|> letA
//.phase
(///.run [///bundle.empty ////synthesis.init])
- (case> (^ (#error.Success (////synthesis.branch/let [inputS registerS outputS])))
+ (case> (^ (#try.Success (////synthesis.branch/let [inputS registerS outputS])))
(and (n/= registerA registerS)
(//primitive.corresponds? inputA inputS)
(//primitive.corresponds? outputA outputS))
@@ -82,7 +81,7 @@
(|> ifA
//.phase
(///.run [///bundle.empty ////synthesis.init])
- (case> (^ (#error.Success (////synthesis.branch/if [inputS thenS elseS])))
+ (case> (^ (#try.Success (////synthesis.branch/if [inputS thenS elseS])))
(and (//primitive.corresponds? inputA inputS)
(//primitive.corresponds? thenA thenS)
(//primitive.corresponds? elseA elseS))
diff --git a/stdlib/source/test/lux/tool/compiler/phase/synthesis/function.lux b/stdlib/source/test/lux/tool/compiler/phase/synthesis/function.lux
index 3ca60e77b..368b692e9 100644
--- a/stdlib/source/test/lux/tool/compiler/phase/synthesis/function.lux
+++ b/stdlib/source/test/lux/tool/compiler/phase/synthesis/function.lux
@@ -6,11 +6,11 @@
["r" math/random (#+ Random) ("#@." monad)]
["_" test (#+ Test)]
[control
- pipe]
+ pipe
+ ["." try]]
[data
["." product]
["." maybe]
- ["." error]
[number
["." nat]]
[collection
@@ -118,7 +118,7 @@
(|> function//constant
//.phase
(///.run [///bundle.empty ////synthesis.init])
- (case> (^ (#error.Success (////synthesis.function/abstraction [environment arity output])))
+ (case> (^ (#try.Success (////synthesis.function/abstraction [environment arity output])))
(and (n/= arity//constant arity)
(//primitive.corresponds? prediction//constant output))
@@ -128,7 +128,7 @@
(|> function//environment
//.phase
(///.run [///bundle.empty ////synthesis.init])
- (case> (^ (#error.Success (////synthesis.function/abstraction [environment arity (#////synthesis.Reference (////reference.variable output))])))
+ (case> (^ (#try.Success (////synthesis.function/abstraction [environment arity (#////synthesis.Reference (////reference.variable output))])))
(and (n/= arity//environment arity)
(variable@= prediction//environment output))
@@ -138,7 +138,7 @@
(|> function//local
//.phase
(///.run [///bundle.empty ////synthesis.init])
- (case> (^ (#error.Success (////synthesis.function/abstraction [environment arity (#////synthesis.Reference (////reference.variable output))])))
+ (case> (^ (#try.Success (////synthesis.function/abstraction [environment arity (#////synthesis.Reference (////reference.variable output))])))
(and (n/= arity//local arity)
(variable@= prediction//local output))
@@ -157,7 +157,7 @@
(|> (////analysis.apply [funcA argsA])
//.phase
(///.run [///bundle.empty ////synthesis.init])
- (case> (^ (#error.Success (////synthesis.function/apply [funcS argsS])))
+ (case> (^ (#try.Success (////synthesis.function/apply [funcS argsS])))
(and (//primitive.corresponds? funcA funcS)
(list.every? (product.uncurry //primitive.corresponds?)
(list.zip2 argsA argsS)))
@@ -168,7 +168,7 @@
(|> (////analysis.apply [funcA (list)])
//.phase
(///.run [///bundle.empty ////synthesis.init])
- (case> (#error.Success funcS)
+ (case> (#try.Success funcS)
(//primitive.corresponds? funcA funcS)
_
diff --git a/stdlib/source/test/lux/tool/compiler/phase/synthesis/primitive.lux b/stdlib/source/test/lux/tool/compiler/phase/synthesis/primitive.lux
index f54ace3d5..d9d24ea21 100644
--- a/stdlib/source/test/lux/tool/compiler/phase/synthesis/primitive.lux
+++ b/stdlib/source/test/lux/tool/compiler/phase/synthesis/primitive.lux
@@ -7,9 +7,8 @@
["r" math/random (#+ Random) ("#@." monad)]
["_" test (#+ Test)]
[control
- pipe]
- [data
- ["." error]]]
+ pipe
+ ["." try]]]
{1
["." / #_
["/#" //
@@ -66,7 +65,7 @@
(|> (#////analysis.Primitive (<analysis> expected))
//.phase
(///.run [///bundle.empty ////synthesis.init])
- (case> (#error.Success (#////synthesis.Primitive (<synthesis> actual)))
+ (case> (#try.Success (#////synthesis.Primitive (<synthesis> actual)))
(is? expected actual)
_
diff --git a/stdlib/source/test/lux/tool/compiler/phase/synthesis/structure.lux b/stdlib/source/test/lux/tool/compiler/phase/synthesis/structure.lux
index 0ea42a2a9..76405c771 100644
--- a/stdlib/source/test/lux/tool/compiler/phase/synthesis/structure.lux
+++ b/stdlib/source/test/lux/tool/compiler/phase/synthesis/structure.lux
@@ -7,11 +7,11 @@
["r" math/random (#+ Random) ("#@." monad)]
["_" test (#+ Test)]
[control
- pipe]
+ pipe
+ ["." try]]
[data
["." bit ("#@." equivalence)]
["." product]
- ["." error]
[collection
["." list]]]]
["." // #_
@@ -40,7 +40,7 @@
(|> (////analysis.variant [lefts right? memberA])
//.phase
(///.run [///bundle.empty ////synthesis.init])
- (case> (^ (#error.Success (////synthesis.variant [leftsS right?S valueS])))
+ (case> (^ (#try.Success (////synthesis.variant [leftsS right?S valueS])))
(let [tagS (if right?S (inc leftsS) leftsS)]
(and (n/= tagA tagS)
(|> tagS (n/= (dec size)) (bit@= right?S))
@@ -58,7 +58,7 @@
(|> (////analysis.tuple membersA)
//.phase
(///.run [///bundle.empty ////synthesis.init])
- (case> (^ (#error.Success (////synthesis.tuple membersS)))
+ (case> (^ (#try.Success (////synthesis.tuple membersS)))
(and (n/= size (list.size membersS))
(list.every? (product.uncurry //primitive.corresponds?)
(list.zip2 membersA membersS)))