aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test/lux.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/test/lux.lux')
-rw-r--r--stdlib/source/test/lux.lux235
1 files changed, 114 insertions, 121 deletions
diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux
index 751655065..2cccd5878 100644
--- a/stdlib/source/test/lux.lux
+++ b/stdlib/source/test/lux.lux
@@ -193,8 +193,8 @@
(type: (Returner a)
(/.Interface
- (: (-> Any a)
- return)))
+ (is (-> Any a)
+ return)))
(/.implementation: (global_returner value)
(All (_ a) (-> a (Returner a)))
@@ -210,10 +210,10 @@
Test
(do random.monad
[expected random.nat
- .let [local_returner (: (Returner Nat)
- (/.implementation
- (def: (return _)
- expected)))]]
+ .let [local_returner (is (Returner Nat)
+ (/.implementation
+ (def: (return _)
+ expected)))]]
(_.for [/.Interface]
($_ _.and
(_.cover [/.implementation:]
@@ -404,22 +404,22 @@
(def: for_macro
Test
- (let [macro (: /.Macro'
- (function (_ tokens lux)
- {.#Right [lux (list)]}))]
+ (let [macro (is /.Macro'
+ (function (_ tokens lux)
+ {.#Right [lux (list)]}))]
(do random.monad
[expected random.nat]
(`` (`` ($_ _.and
(_.cover [/.Macro']
(|> macro
- (: /.Macro')
+ (is /.Macro')
(same? macro)))
(_.cover [/.Macro]
(|> macro
"lux macro"
- (: /.Macro)
- (: Any)
- (same? (: Any macro))))
+ (is /.Macro)
+ (is Any)
+ (same? (is Any macro))))
(_.cover [/.macro:]
(same? expected (..identity_macro expected)))
(~~ (for @.old (~~ (as_is))
@@ -452,23 +452,23 @@
<open/0> (template.text [<module/0> "#[0]"])]
(and (~~ (template [<input> <module> <referrals>]
[(with_expansions [<input>' (macro.final <input>)]
- (let [scenario (: (-> Any Bit)
- (function (_ _)
- ... TODO: Remove this hack once Jython is no longer being used as the Python interpreter.
- (`` (for @.python (case (' [<input>'])
- (^.` [<module>
- ("lux def" (~ [_ {.#Symbol ["" _]}]) [] #0)
- (~~ (template.spliced <referrals>))])
- true
-
- _
- false)
- (case (' [<input>'])
- (^.` [<module> (~~ (template.spliced <referrals>))])
- true
-
- _
- false)))))]
+ (let [scenario (is (-> Any Bit)
+ (function (_ _)
+ ... TODO: Remove this hack once Jython is no longer being used as the Python interpreter.
+ (`` (for @.python (case (' [<input>'])
+ (^.` [<module>
+ ("lux def" (~ [_ {.#Symbol ["" _]}]) [] #0)
+ (~~ (template.spliced <referrals>))])
+ true
+
+ _
+ false)
+ (case (' [<input>'])
+ (^.` [<module> (~~ (template.spliced <referrals>))])
+ true
+
+ _
+ false)))))]
(scenario [])))]
[(.using [<module/0>'])
@@ -563,30 +563,23 @@
expected/1 existential_type]
(<| (_.for [/.Type])
($_ _.and
- (_.cover [/.:]
+ (_.cover [/.is]
(|> expected
- (/.: Any)
- (same? (/.: Any expected))))
- (_.cover [/.:as]
+ (/.is Any)
+ (same? (/.is Any expected))))
+ (_.cover [/.as]
(|> expected
- (/.: Any)
- (/.:as /.Nat)
+ (/.is Any)
+ (/.as /.Nat)
(same? expected)))
- (_.cover [/.:expected]
+ (_.cover [/.as_expected]
(|> expected
- (/.: Any)
- /.:expected
- (/.: /.Nat)
+ (/.is Any)
+ /.as_expected
+ (/.is /.Nat)
(same? expected)))
- (_.cover [/.:let]
- (let [[actual_left actual_right]
- (: (/.:let [side /.Nat]
- [side side])
- [expected_left expected_right])]
- (and (same? expected_left actual_left)
- (same? expected_right actual_right))))
- (_.cover [/.:of]
- (same? /.Nat (/.:of expected)))
+ (_.cover [/.type_of]
+ (same? /.Nat (/.type_of expected)))
(_.cover [/.Primitive]
(case (/.Primitive "foo" [expected/0 expected/1])
(pattern {.#Primitive "foo" (list actual/0 actual/1)})
@@ -626,20 +619,20 @@
false)))
(_.cover [/.type:]
(exec
- (: /.Type ..for_type/variant)
- (: /.Type ..for_type/record)
- (: /.Type ..for_type/all)
+ (is /.Type ..for_type/variant)
+ (is /.Type ..for_type/record)
+ (is /.Type ..for_type/all)
true))
(_.cover [/.Variant]
(exec
- (: for_type/variant
- {#Case/1 expected_left})
+ (is for_type/variant
+ {#Case/1 expected_left})
true))
(_.cover [/.Record]
(exec
- (: for_type/record
- [#slot/0 (n.= expected_left expected_right)
- #slot/1 (.rev expected_right)])
+ (is for_type/record
+ [#slot/0 (n.= expected_left expected_right)
+ #slot/1 (.rev expected_right)])
true))
))))
@@ -649,17 +642,17 @@
[expected random.i64]
($_ _.and
(_.cover [/.i64]
- (same? (: Any expected)
- (: Any (/.i64 expected))))
+ (same? (is Any expected)
+ (is Any (/.i64 expected))))
(_.cover [/.nat]
- (same? (: Any expected)
- (: Any (/.nat expected))))
+ (same? (is Any expected)
+ (is Any (/.nat expected))))
(_.cover [/.int]
- (same? (: Any expected)
- (: Any (/.int expected))))
+ (same? (is Any expected)
+ (is Any (/.int expected))))
(_.cover [/.rev]
- (same? (: Any expected)
- (: Any (/.rev expected))))
+ (same? (is Any expected)
+ (is Any (/.rev expected))))
(_.cover [/.++]
(n.= 1 (n.- expected
(/.++ expected))))
@@ -674,14 +667,14 @@
[expected_left random.nat
expected_right random.nat]
(_.cover [/.-> /.function]
- (and (let [actual (: (/.-> Nat Nat Nat)
- (/.function (_ actual_left actual_right)
- (n.* (++ actual_left) (-- actual_right))))]
+ (and (let [actual (is (/.-> Nat Nat Nat)
+ (/.function (_ actual_left actual_right)
+ (n.* (++ actual_left) (-- actual_right))))]
(n.= (n.* (++ expected_left) (-- expected_right))
(actual expected_left expected_right)))
- (let [actual (: (/.-> [Nat Nat] Nat)
- (/.function (_ [actual_left actual_right])
- (n.* (++ actual_left) (-- actual_right))))]
+ (let [actual (is (/.-> [Nat Nat] Nat)
+ (/.function (_ [actual_left actual_right])
+ (n.* (++ actual_left) (-- actual_right))))]
(n.= (n.* (++ expected_left) (-- expected_right))
(actual [expected_left expected_right])))))))
@@ -801,8 +794,8 @@
(/.the #big_left)
(n.= expected/b))
(|> sample
- ((: (-> (-> Nat Nat) (-> Big Big))
- (/.revised #big_left))
+ ((is (-> (-> Nat Nat) (-> Big Big))
+ (/.revised #big_left))
(n.+ shift/b))
(/.the #big_left)
(n.= expected/b)))
@@ -815,8 +808,8 @@
(/.the [#big_right #small_left])
(n.= expected/s))
(|> sample
- ((: (-> (-> Nat Nat) (-> Big Big))
- (/.revised [#big_right #small_left]))
+ ((is (-> (-> Nat Nat) (-> Big Big))
+ (/.revised [#big_right #small_left]))
(n.+ shift/s))
(/.the [#big_right #small_left])
(n.= expected/s)))))
@@ -896,52 +889,52 @@
($_ _.and
(_.cover [/.Either]
(and (exec
- (: (/.Either Nat Text)
- {.#Left left})
+ (is (/.Either Nat Text)
+ {.#Left left})
true)
(exec
- (: (/.Either Nat Text)
- {.#Right right})
+ (is (/.Either Nat Text)
+ {.#Right right})
true)))
(_.cover [/.Any]
(and (exec
- (: /.Any
- left)
+ (is /.Any
+ left)
true)
(exec
- (: /.Any
- right)
+ (is /.Any
+ right)
true)))
(_.cover [/.Nothing]
(and (exec
- (: (-> /.Any /.Nothing)
- (function (_ _)
- (undefined)))
+ (is (-> /.Any /.Nothing)
+ (function (_ _)
+ (undefined)))
true)
(exec
- (: (-> /.Any /.Int)
- (function (_ _)
- (: /.Int (undefined))))
+ (is (-> /.Any /.Int)
+ (function (_ _)
+ (is /.Int (undefined))))
true)))
(_.for [/.__adjusted_quantified_type__]
($_ _.and
(_.cover [/.All]
- (let [identity (: (/.All (_ a) (-> a a))
- (|>>))]
+ (let [identity (is (/.All (_ a) (-> a a))
+ (|>>))]
(and (exec
- (: Nat
- (identity left))
+ (is Nat
+ (identity left))
true)
(exec
- (: Text
- (identity right))
+ (is Text
+ (identity right))
true))))
(_.cover [/.Ex]
- (let [hide (: (/.Ex (_ a) (-> Nat a))
- (|>>))]
+ (let [hide (is (/.Ex (_ a) (-> Nat a))
+ (|>>))]
(exec
- (: /.Any
- (hide left))
+ (is /.Any
+ (hide left))
true)))))
(_.cover [/.same?]
(let [not_left (atom.atom left)
@@ -950,12 +943,12 @@
(/.same? not_left not_left)
(not (/.same? left not_left)))))
(_.cover [/.Rec]
- (let [list (: (/.Rec NList
- (Maybe [Nat NList]))
- {.#Some [item/0
- {.#Some [item/1
- {.#Some [item/2
- {.#None}]}]}]})]
+ (let [list (is (/.Rec NList
+ (Maybe [Nat NList]))
+ {.#Some [item/0
+ {.#Some [item/1
+ {.#Some [item/2
+ {.#None}]}]}]})]
(case list
{.#Some [actual/0 {.#Some [actual/1 {.#Some [actual/2 {.#None}]}]}]}
(and (same? item/0 actual/0)
@@ -1012,10 +1005,10 @@
(/.case [..#left expected_nat ..#right expected_int]
[..#left 0 ..#right +0] true
_ false)
- (/.case (: (Either Nat Int) {.#Left expected_nat})
+ (/.case (is (Either Nat Int) {.#Left expected_nat})
{.#Left 0} true
_ false)
- (/.case (: (Either Nat Int) {.#Right expected_int})
+ (/.case (is (Either Nat Int) {.#Right expected_int})
{.#Right +0} true
_ false)
))
@@ -1154,20 +1147,20 @@
captured/2 (the .#captured scope/2)
- local? (: (-> Ref Bit)
- (function (_ ref)
- (case ref
- {.#Local _} true
- {.#Captured _} false)))
- captured? (: (-> Ref Bit)
- (|>> local? not))
- binding? (: (-> (-> Ref Bit) Text Bit)
- (function (_ is? name)
- (|> captured/2
- (the .#mappings)
- (plist.value name)
- (maybe#each (|>> product.right is?))
- (maybe.else false))))
+ local? (is (-> Ref Bit)
+ (function (_ ref)
+ (case ref
+ {.#Local _} true
+ {.#Captured _} false)))
+ captured? (is (-> Ref Bit)
+ (|>> local? not))
+ binding? (is (-> (-> Ref Bit) Text Bit)
+ (function (_ is? name)
+ (|> captured/2
+ (the .#mappings)
+ (plist.value name)
+ (maybe#each (|>> product.right is?))
+ (maybe.else false))))
correct_closure!
(and (n.= 6 (the .#counter captured/2))