aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test/lux.lux
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/test/lux.lux118
1 files changed, 59 insertions, 59 deletions
diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux
index a0e00fdd4..6eab1c60b 100644
--- a/stdlib/source/test/lux.lux
+++ b/stdlib/source/test/lux.lux
@@ -280,20 +280,20 @@
(do random.monad
[start random.nat
factor random.nat
- .let [expected (n.* factor (inc start))]]
+ .let [expected (n.* factor (++ start))]]
($_ _.and
(_.cover [/.|>]
(n.= expected
- (/.|> start inc (n.* factor))))
+ (/.|> start ++ (n.* factor))))
(_.cover [/.|>>]
(n.= expected
- ((/.|>> inc (n.* factor)) start)))
+ ((/.|>> ++ (n.* factor)) start)))
(_.cover [/.<|]
(n.= expected
- (/.<| (n.* factor) inc start)))
+ (/.<| (n.* factor) ++ start)))
(_.cover [/.<<|]
(n.= expected
- ((/.<<| (n.* factor) inc) start)))
+ ((/.<<| (n.* factor) ++) start)))
)))
(def: example_identifier "YOLO")
@@ -421,7 +421,7 @@
))
(_.cover [/.Ann]
(|> example
- (get@ #/.meta)
+ (value@ #/.meta)
(location\= location.dummy)))
)))
@@ -432,7 +432,7 @@
"This is an arbitrary text whose only purpose is to be found, somewhere, in the source-code.")
(/.macro: (found_crosshair? tokens lux)
- (let [[_ _ source_code] (get@ #.source lux)]
+ (let [[_ _ source_code] (value@ #.source lux)]
(#.Right [lux (list (code.bit (text.contains? ..crosshair source_code)))])))
(def: for_macro
@@ -572,11 +572,11 @@
(_.cover [/.rev]
(same? (: Any expected)
(: Any (/.rev expected))))
- (_.cover [/.inc]
+ (_.cover [/.++]
(n.= 1 (n.- expected
- (/.inc expected))))
- (_.cover [/.dec]
- (n.= 1 (n.- (/.dec expected)
+ (/.++ expected))))
+ (_.cover [/.--]
+ (n.= 1 (n.- (/.-- expected)
expected)))
)))
@@ -588,13 +588,13 @@
(_.cover [/.-> /.function]
(and (let [actual (: (/.-> Nat Nat Nat)
(/.function (_ actual_left actual_right)
- (n.* (inc actual_left) (dec actual_right))))]
- (n.= (n.* (inc expected_left) (dec expected_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.* (inc actual_left) (dec actual_right))))]
- (n.= (n.* (inc expected_left) (dec expected_right))
+ (n.* (++ actual_left) (-- actual_right))))]
+ (n.= (n.* (++ expected_left) (-- expected_right))
(actual [expected_left expected_right])))))))
(/.template: (!n/+ <left> <right>)
@@ -673,72 +673,72 @@
#big_right {#small_left start/s
#small_right text}}]]
($_ _.and
- (_.cover [/.get@]
+ (_.cover [/.value@]
(and (and (|> sample
- (/.get@ #big_left)
+ (/.value@ #big_left)
(same? start/b))
(|> sample
- ((/.get@ #big_left))
+ ((/.value@ #big_left))
(same? start/b)))
(and (|> sample
- (/.get@ [#big_right #small_left])
+ (/.value@ [#big_right #small_left])
(same? start/s))
(|> sample
- ((/.get@ [#big_right #small_left]))
+ ((/.value@ [#big_right #small_left]))
(same? start/s)))))
- (_.cover [/.set@]
+ (_.cover [/.with@]
(and (and (|> sample
- (/.set@ #big_left shift/b)
- (/.get@ #big_left)
+ (/.with@ #big_left shift/b)
+ (/.value@ #big_left)
(same? shift/b))
(|> sample
- ((/.set@ #big_left shift/b))
- (/.get@ #big_left)
+ ((/.with@ #big_left shift/b))
+ (/.value@ #big_left)
(same? shift/b))
(|> sample
- ((/.set@ #big_left) shift/b)
- (/.get@ #big_left)
+ ((/.with@ #big_left) shift/b)
+ (/.value@ #big_left)
(same? shift/b)))
(and (|> sample
- (/.set@ [#big_right #small_left] shift/s)
- (/.get@ [#big_right #small_left])
+ (/.with@ [#big_right #small_left] shift/s)
+ (/.value@ [#big_right #small_left])
(same? shift/s))
(|> sample
- ((/.set@ [#big_right #small_left] shift/s))
- (/.get@ [#big_right #small_left])
+ ((/.with@ [#big_right #small_left] shift/s))
+ (/.value@ [#big_right #small_left])
(same? shift/s))
(|> sample
- ((/.set@ [#big_right #small_left]) shift/s)
- (/.get@ [#big_right #small_left])
+ ((/.with@ [#big_right #small_left]) shift/s)
+ (/.value@ [#big_right #small_left])
(same? shift/s)))))
- (_.cover [/.update@]
+ (_.cover [/.revised@]
(and (and (|> sample
- (/.update@ #big_left (n.+ shift/b))
- (/.get@ #big_left)
+ (/.revised@ #big_left (n.+ shift/b))
+ (/.value@ #big_left)
(n.= expected/b))
(|> sample
- ((/.update@ #big_left (n.+ shift/b)))
- (/.get@ #big_left)
+ ((/.revised@ #big_left (n.+ shift/b)))
+ (/.value@ #big_left)
(n.= expected/b))
(|> sample
((: (-> (-> Nat Nat) (-> Big Big))
- (/.update@ #big_left))
+ (/.revised@ #big_left))
(n.+ shift/b))
- (/.get@ #big_left)
+ (/.value@ #big_left)
(n.= expected/b)))
(and (|> sample
- (/.update@ [#big_right #small_left] (n.+ shift/s))
- (/.get@ [#big_right #small_left])
+ (/.revised@ [#big_right #small_left] (n.+ shift/s))
+ (/.value@ [#big_right #small_left])
(n.= expected/s))
(|> sample
- ((/.update@ [#big_right #small_left] (n.+ shift/s)))
- (/.get@ [#big_right #small_left])
+ ((/.revised@ [#big_right #small_left] (n.+ shift/s)))
+ (/.value@ [#big_right #small_left])
(n.= expected/s))
(|> sample
((: (-> (-> Nat Nat) (-> Big Big))
- (/.update@ [#big_right #small_left]))
+ (/.revised@ [#big_right #small_left]))
(n.+ shift/s))
- (/.get@ [#big_right #small_left])
+ (/.value@ [#big_right #small_left])
(n.= expected/s)))))
)))
@@ -862,7 +862,7 @@
(hide left))
true)))
(_.cover [/.same?]
- (let [not_left (|> left inc dec)]
+ (let [not_left (|> left ++ --)]
(and (/.same? left left)
(and (n.= not_left left)
(not (/.same? not_left left))))))
@@ -1009,7 +1009,7 @@
(/.loop [counter 0
value 0]
(if (n.< iterations counter)
- (recur (inc counter) (n.+ factor value))
+ (recur (++ counter) (n.+ factor value))
value)))))
(do random.monad
[pre random.nat
@@ -1051,13 +1051,13 @@
(syntax: (for_meta|Info [])
(function (_ lux)
- (let [info (get@ #.info lux)
+ (let [info (value@ #.info lux)
conforming_target!
- (set.member? ..possible_targets (get@ #.target info))
+ (set.member? ..possible_targets (value@ #.target info))
compiling!
- (case (get@ #.mode info)
+ (case (value@ #.mode info)
#.Build true
_ false)]
(#.Right [lux (list (code.bit (and conforming_target!
@@ -1066,7 +1066,7 @@
(syntax: (for_meta|Module_State [])
(do meta.monad
[prelude_module (meta.module .prelude_module)]
- (in (list (code.bit (case (get@ #.module_state prelude_module)
+ (in (list (code.bit (case (value@ #.module_state prelude_module)
#.Active false
_ true))))))
@@ -1103,22 +1103,22 @@
let/2 <code>.local_identifier
let/3 <code>.local_identifier])
- (in (list (code.bit (case (get@ #.scopes *lux*)
+ (in (list (code.bit (case (value@ #.scopes *lux*)
(^ (list& scope/2 _))
- (let [locals/2 (get@ #.locals scope/2)
+ (let [locals/2 (value@ #.locals scope/2)
expected_locals/2 (set.of_list text.hash (list fn/2 var/2 let/2
let/3))
actual_locals/2 (|> locals/2
- (get@ #.mappings)
+ (value@ #.mappings)
(list\map product.left)
(set.of_list text.hash))
correct_locals!
- (and (n.= 4 (get@ #.counter locals/2))
+ (and (n.= 4 (value@ #.counter locals/2))
(set\= expected_locals/2
actual_locals/2))
- captured/2 (get@ #.captured scope/2)
+ captured/2 (value@ #.captured scope/2)
local? (: (-> Ref Bit)
(function (_ ref)
@@ -1130,13 +1130,13 @@
binding? (: (-> (-> Ref Bit) Text Bit)
(function (_ is? name)
(|> captured/2
- (get@ #.mappings)
+ (value@ #.mappings)
(plist.value name)
(maybe\map (|>> product.right is?))
(maybe.else false))))
correct_closure!
- (and (n.= 6 (get@ #.counter captured/2))
+ (and (n.= 6 (value@ #.counter captured/2))
(binding? local? fn/1)
(binding? local? var/1)
(binding? local? let/1)