From 9afaa3a3236366d57cb1c3d771b25779ee76269b Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Fri, 31 Dec 2021 00:58:08 -0400 Subject: Fixes for the pure-Lux JVM compiler machinery. --- stdlib/source/test/lux.lux | 63 +-- stdlib/source/test/lux/data/collection/list.lux | 70 +-- .../source/test/lux/data/collection/sequence.lux | 82 ++- stdlib/source/test/lux/target/python.lux | 323 +++++++++++ stdlib/source/test/lux/target/ruby.lux | 594 +++++++++++++++++++++ stdlib/source/test/lux/tool.lux | 2 + .../test/lux/tool/compiler/reference/variable.lux | 41 ++ 7 files changed, 1084 insertions(+), 91 deletions(-) create mode 100644 stdlib/source/test/lux/target/python.lux create mode 100644 stdlib/source/test/lux/target/ruby.lux create mode 100644 stdlib/source/test/lux/tool/compiler/reference/variable.lux (limited to 'stdlib/source/test') diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux index 86ed33be3..255d15c71 100644 --- a/stdlib/source/test/lux.lux +++ b/stdlib/source/test/lux.lux @@ -64,8 +64,11 @@ ["[1][0]" target "_" (~~ (.for ["{old}" (~~ (.as_is ["[1]/[0]" jvm])) "JVM" (~~ (.as_is ["[1]/[0]" jvm])) - "JavaScript" (~~ (.as_is ["[1]/[0]" js]))] - (~~ (.as_is))))]]))) + "JavaScript" (~~ (.as_is ["[1]/[0]" js])) + "Ruby" (~~ (.as_is ["[1]/[0]" ruby])) + "Python" (~~ (.as_is ["[1]/[0]" python]))] + (~~ (.as_is))))] + ]))) ... TODO: Get rid of this ASAP (template: (!bundle body) @@ -76,34 +79,34 @@ (def: sub_tests Test - (with_expansions [... TODO: Update & expand tests for this - (for [@.jvm (~~ (as_is /target/jvm.test)) - @.old (~~ (as_is /target/jvm.test)) - @.js (~~ (as_is /target/js.test))] - (~~ (as_is))) - (for [@.old (~~ (as_is))] - (~~ (as_is /extension.test)))] - (`` (_.in_parallel (list /abstract.test - /control.test - /data.test - /debug.test - /documentation.test - /locale.test - /macro.test - /math.test - /meta.test - /program.test - /static.test - /target.test - /test.test - /time.test - /tool.test - /type.test - /world.test - /ffi.test - - - ))))) + (`` (`` (_.in_parallel (list /abstract.test + /control.test + /data.test + /debug.test + /documentation.test + /locale.test + /macro.test + /math.test + /meta.test + /program.test + /static.test + /target.test + /test.test + /time.test + /tool.test + /type.test + /world.test + /ffi.test + ... TODO: Update & expand tests for this + (~~ (for [@.jvm (~~ (as_is /target/jvm.test)) + @.old (~~ (as_is /target/jvm.test)) + @.js (~~ (as_is /target/js.test)) + @.ruby (~~ (as_is /target/ruby.test)) + @.python (~~ (as_is /target/python.test))] + (~~ (as_is)))) + (~~ (for [@.old (~~ (as_is))] + (~~ (as_is /extension.test)))) + ))))) (def: for_bit Test diff --git a/stdlib/source/test/lux/data/collection/list.lux b/stdlib/source/test/lux/data/collection/list.lux index c305ce6a0..06218dbb8 100644 --- a/stdlib/source/test/lux/data/collection/list.lux +++ b/stdlib/source/test/lux/data/collection/list.lux @@ -1,36 +1,36 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - ["[0]" enum] - [\\specification - ["$[0]" equivalence] - ["$[0]" hash] - ["$[0]" monoid] - ["$[0]" mix] - ["$[0]" functor] - ["$[0]" apply] - ["$[0]" monad]]] - [control - pipe - ["[0]" io] - ["[0]" maybe] - ["[0]" function]] - [data - ["[0]" bit] - ["[0]" product] - ["[0]" text ("[1]#[0]" equivalence)] - [collection - ["[0]" set]]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat] - ["[0]" int]]]]] - [\\library - ["[0]" / ("[1]#[0]" monad)]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + ["[0]" enum] + [\\specification + ["$[0]" equivalence] + ["$[0]" hash] + ["$[0]" monoid] + ["$[0]" mix] + ["$[0]" functor] + ["$[0]" apply] + ["$[0]" monad]]] + [control + pipe + ["[0]" io] + ["[0]" maybe] + ["[0]" function]] + [data + ["[0]" bit] + ["[0]" product] + ["[0]" text ("[1]#[0]" equivalence)] + [collection + ["[0]" set]]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat] + ["[0]" int]]]]] + [\\library + ["[0]" / ("[1]#[0]" monad)]]) (def: bounded_size (Random Nat) @@ -362,7 +362,7 @@ Test (let [(^open "/#[0]") /.functor - choose (: (-> Nat (Maybe Text)) + choice (: (-> Nat (Maybe Text)) (function (_ value) (if (n.even? value) {.#Some (# n.decimal encoded value)} @@ -375,7 +375,7 @@ (/.only n.even?) (/#each (# n.decimal encoded)) /.head) - (/.one choose sample)] + (/.one choice sample)] [{.#Some expected} {.#Some actual}] (text#= expected actual) @@ -389,7 +389,7 @@ (|> sample (/.only n.even?) (/#each (# n.decimal encoded))) - (/.all choose sample))) + (/.all choice sample))) (_.cover [/.example] (case (/.example n.even? sample) {.#Some found} diff --git a/stdlib/source/test/lux/data/collection/sequence.lux b/stdlib/source/test/lux/data/collection/sequence.lux index 87b67009b..220581bd2 100644 --- a/stdlib/source/test/lux/data/collection/sequence.lux +++ b/stdlib/source/test/lux/data/collection/sequence.lux @@ -1,30 +1,31 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [\\specification - ["$[0]" equivalence] - ["$[0]" monoid] - ["$[0]" mix] - ["$[0]" functor {"+" Injection}] - ["$[0]" apply] - ["$[0]" monad]]] - [control - ["[0]" try {"+" Try}] - ["[0]" exception]] - [data - ["[0]" bit ("[1]#[0]" equivalence)] - [collection - ["[0]" list ("[1]#[0]" mix)] - ["[0]" set]]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" / ("[1]#[0]" monad)]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [\\specification + ["$[0]" equivalence] + ["$[0]" monoid] + ["$[0]" mix] + ["$[0]" functor {"+" Injection}] + ["$[0]" apply] + ["$[0]" monad]]] + [control + ["[0]" try {"+" Try}] + ["[0]" exception]] + [data + ["[0]" bit ("[1]#[0]" equivalence)] + ["[0]" text ("[1]#[0]" equivalence)] + [collection + ["[0]" list ("[1]#[0]" mix)] + ["[0]" set]]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" / ("[1]#[0]" monad)]]) (def: signatures Test @@ -183,5 +184,34 @@ (/#= sample))] (and expected_size! symmetry!)))) + (_.cover [/.only] + (let [positives (/.only n.even? sample) + negatives (/.only (bit.complement n.even?) sample)] + (and (/.every? n.even? positives) + (not (/.any? n.even? negatives)) + + (n.= (/.size sample) + (n.+ (/.size positives) + (/.size negatives)))))) + (_.cover [/.one] + (let [(^open "/#[0]") /.functor + choice (: (-> Nat (Maybe Text)) + (function (_ value) + (if (n.even? value) + {.#Some (# n.decimal encoded value)} + {.#None})))] + (case [(|> sample + (/.only n.even?) + (/#each (# n.decimal encoded)) + (/.item 0)) + (/.one choice sample)] + [{try.#Success expected} {.#Some actual}] + (text#= expected actual) + + [{try.#Failure _} {.#None}] + true + + _ + false))) )) )))) diff --git a/stdlib/source/test/lux/target/python.lux b/stdlib/source/test/lux/target/python.lux new file mode 100644 index 000000000..49d74c1b3 --- /dev/null +++ b/stdlib/source/test/lux/target/python.lux @@ -0,0 +1,323 @@ +(.using + [library + [lux "*" + ["_" test {"+" Test}] + ["[0]" ffi] + [abstract + [monad {"+" do}] + ["[0]" predicate]] + [control + ["[0]" maybe ("[1]#[0]" functor)] + ["[0]" try {"+" Try} ("[1]#[0]" functor)]] + [data + ["[0]" bit ("[1]#[0]" equivalence)] + ["[0]" text {"+" \n} ("[1]#[0]" equivalence) + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + ["[0]" math + ["[0]" random {"+" Random} ("[1]#[0]" monad)] + [number + ["n" nat] + ["i" int] + ["f" frac] + ["[0]" i64]]]]] + [\\library + ["[0]" /]]) + +(ffi.import: (eval [Text] "try" "?" Any)) + +(def: (expression ??? it) + (-> (-> Any Bit) (/.Expression Any) Bit) + ... (case (|> it /.code ..eval) + ... {try.#Success it} + ... (|> it + ... (maybe#each ???) + ... (maybe.else false)) + + ... {try.#Failure error} + ... (exec + ... ("lux io log" "try.#Failure") + ... ("lux io log" error) + ... ("lux io log" (|> it /.code)) + ... false)) + (|> it + /.code + ..eval + (try#each (|>> (maybe#each ???) + (maybe.else false))) + (try.else false)) + ) + +(def: test|literal + Test + (do [! random.monad] + [bool random.bit + float random.frac + int random.int + string (random.ascii/upper 5)] + ($_ _.and + (_.cover [/.none] + (|> /.none + /.code + ..eval + (try#each (function (_ it) + (case it + {.#None} true + {.#Some _} true))) + (try.else false))) + (_.cover [/.bool] + (expression (|>> (:as Bit) (bit#= bool)) + (/.bool bool))) + (_.cover [/.int] + (expression (|>> (:as Int) (i.= int)) + (/.int int))) + ... (_.cover [/.long] + ... (expression (|>> (:as Int) (i.= int)) + ... (/.long int))) + (_.cover [/.float] + (expression (|>> (:as Frac) (f.= float)) + (/.float float))) + (_.cover [/.string] + (expression (|>> (:as Text) (text#= string)) + (/.string string))) + (_.cover [/.unicode] + (expression (|>> (:as Text) (text#= string)) + (/.unicode string))) + ))) + +(def: test|bool + Test + (do [! random.monad] + [left random.bit + right random.bit] + (`` ($_ _.and + (~~ (template [ ] + [(_.cover [] + (let [expected ( left right)] + (expression (|>> (:as Bit) (bit#= expected)) + ( (/.bool left) (/.bool right)))))] + + [/.or .or] + [/.and .and] + )) + (_.cover [/.not] + (expression (|>> (:as Bit) (bit#= (not left))) + (/.not (/.bool left)))) + )))) + +(def: test|float + Test + (do [! random.monad] + [parameter (random.only (|>> (f.= +0.0) not) + random.safe_frac) + subject random.safe_frac] + (`` ($_ _.and + (~~ (template [
]
+                  [(_.cover []
+                            (let [expected ( (
 parameter) (
 subject))]
+                              (expression (|>> (:as Frac) (f.= expected))
+                                          ( (/.float (
 parameter)) (/.float (
 subject))))))]
+
+                  [/.+ f.+ |>]
+                  [/.- f.- |>]
+                  [/.* f.* |>]
+                  [/./ f./ |>]
+                  [/.% f.mod |>]
+                  [/.** math.pow f.abs]
+                  ))
+            (~~ (template [ ]
+                  [(_.cover []
+                            (let [expected ( parameter subject)]
+                              (expression (|>> (:as Bit) (bit#= expected))
+                                          ( (/.float parameter) (/.float subject)))))]
+
+                  [/.<  f.<]
+                  [/.<= f.<=]
+                  [/.>  f.>]
+                  [/.>= f.>=]
+                  [/.=  f.=]
+                  ))
+            ))))
+
+(def: int/16
+  (-> Int Int)
+  (i64.and (-- (i64.left_shifted 15 1))))
+
+(def: test|int
+  Test
+  (do [! random.monad]
+    [left random.int
+     right random.int
+
+     i16 (# ! each ..int/16 random.int)
+     shift (# ! each (n.% 16) random.nat)]
+    (`` ($_ _.and
+            (~~ (template [ ]
+                  [(_.cover []
+                            (let [expected ( left right)]
+                              (expression (|>> (:as Frac) f.int (i.= expected))
+                                          ( (/.int left) (/.int right)))))]
+
+                  [/.bit_or i64.or]
+                  [/.bit_xor i64.xor]
+                  [/.bit_and i64.and]
+                  ))
+            (_.cover [/.opposite]
+                     (expression (|>> (:as Int) (i.= (i.* -1 left)))
+                                 (/.opposite (/.int left))))
+            (_.cover [/.bit_shl]
+                     (let [expected (i64.left_shifted shift i16)]
+                       (expression (|>> (:as Frac) f.int (i.= expected))
+                                   (/.bit_shl (/.int (.int shift))
+                                              (/.int i16)))))
+            (_.cover [/.bit_shr]
+                     (let [expected (i.right_shifted shift i16)]
+                       (expression (|>> (:as Frac) f.int (i.= expected))
+                                   (/.bit_shr (/.int (.int shift))
+                                              (/.int i16)))))
+            ))))
+
+(def: test|array
+  Test
+  (do [! random.monad]
+    [size (# ! each (|>> (n.% 10) ++) random.nat)
+     index (# ! each (n.% size) random.nat)
+     items (random.list size random.safe_frac)
+     .let [expected (|> items
+                        (list.item index)
+                        (maybe.else f.not_a_number))]
+     from (# ! each (n.% size) random.nat)
+     plus (# ! each (n.% (n.- from size)) random.nat)
+     .let [slice_from|size (n.- from size)
+           to (/.int (.int (n.+ plus from)))
+           from (/.int (.int from))]]
+    ($_ _.and
+        (_.cover [/.list /.item]
+                 (expression (|>> (:as Frac) (f.= expected))
+                             (/.item (/.int (.int index))
+                                     (/.list (list#each /.float items)))))
+        (_.cover [/.tuple /.item]
+                 (expression (|>> (:as Frac) (f.= expected))
+                             (/.item (/.int (.int index))
+                                     (/.tuple (list#each /.float items)))))
+        (_.cover [/.slice /.len/1]
+                 (expression (|>> (:as Int) (i.= (.int plus)))
+                             (|> (/.list (list#each /.float items))
+                                 (/.slice from to)
+                                 /.len/1)))
+        (_.cover [/.slice_from]
+                 (expression (|>> (:as Int) (i.= (.int slice_from|size)))
+                             (|> (/.list (list#each /.float items))
+                                 (/.slice_from from)
+                                 /.len/1)))
+        )))
+
+(def: test|dict
+  Test
+  (do [! random.monad]
+    [expected random.safe_frac
+     field (random.ascii/upper 5)
+     dummy (random.only (|>> (text#= field) not)
+                        (random.ascii/upper 5))
+     .let [field (/.string field)
+           dummy (/.string dummy)]]
+    ($_ _.and
+        (_.cover [/.dict]
+                 (expression (|>> (:as Frac) (f.= expected))
+                             (/.item field (/.dict (list [field (/.float expected)])))))
+        )))
+
+(def: test|computation
+  Test
+  (do [! random.monad]
+    [test random.bit
+     then random.safe_frac
+     else random.safe_frac
+
+     bool random.bit
+     float random.frac
+     string (random.ascii/upper 5)
+
+     comment (random.ascii/upper 10)]
+    ($_ _.and
+        ..test|bool
+        ..test|float
+        ..test|int
+        ..test|array
+        ..test|dict
+        (_.cover [/.?]
+                 (let [expected (if test then else)]
+                   (expression (|>> (:as Frac) (f.= expected))
+                               (/.? (/.bool test)
+                                    (/.float then)
+                                    (/.float else)))))
+        (_.cover [/.comment]
+                 (expression (|>> (:as Frac) (f.= then))
+                             (/.comment comment
+                               (/.float then))))
+        )))
+
+(def: test|function
+  Test
+  (do [! random.monad]
+    [float/0 random.safe_frac
+     float/1 random.safe_frac
+     float/2 random.safe_frac
+     $arg/0 (# ! each /.var (random.ascii/lower 10))
+     $arg/1 (# ! each /.var (random.ascii/lower 11))
+     $arg/2 (# ! each /.var (random.ascii/lower 12))]
+    ($_ _.and
+        (_.cover [/.lambda]
+                 (expression (|>> (:as Frac) (f.= float/0))
+                             (/.apply/* (/.lambda (list)
+                                                  (/.float float/0))
+                                        (list))))
+        (_.cover [/.apply/1]
+                 (expression (|>> (:as Frac) (f.= float/0))
+                             (/.apply/1 (/.lambda (list $arg/0)
+                                                  $arg/0)
+                                        (/.float float/0))))
+        (_.cover [/.apply/2]
+                 (expression (|>> (:as Frac) (f.= ($_ f.+ float/0 float/1)))
+                             (/.apply/2 (/.lambda (list $arg/0 $arg/1)
+                                                  ($_ /.+ $arg/0 $arg/1))
+                                        (/.float float/0)
+                                        (/.float float/1))))
+        (_.cover [/.apply/3]
+                 (expression (|>> (:as Frac) (f.= ($_ f.+ float/0 float/1 float/2)))
+                             (/.apply/3 (/.lambda (list $arg/0 $arg/1 $arg/2)
+                                                  ($_ /.+ $arg/0 $arg/1 $arg/2))
+                                        (/.float float/0)
+                                        (/.float float/1)
+                                        (/.float float/2))))
+        (_.cover [/.apply/*]
+                 (expression (|>> (:as Frac) (f.= ($_ f.+ float/0 float/1 float/2)))
+                             (/.apply/* (/.lambda (list $arg/0 $arg/1 $arg/2)
+                                                  ($_ /.+ $arg/0 $arg/1 $arg/2))
+                                        (list (/.float float/0) (/.float float/1) (/.float float/2)))))
+        )))
+
+(def: test|expression
+  Test
+  (do [! random.monad]
+    [dummy random.safe_frac
+     expected random.safe_frac]
+    (`` ($_ _.and
+            (_.for [/.Literal]
+                   ..test|literal)
+            (_.for [/.Computation]
+                   ..test|computation)
+            ..test|function
+            ))))
+
+(def: .public test
+  Test
+  (do [! random.monad]
+    []
+    (<| (_.covering /._)
+        (_.for [/.Code /.code])
+        ($_ _.and
+            (_.for [/.Expression]
+                   ..test|expression)
+            ))))
diff --git a/stdlib/source/test/lux/target/ruby.lux b/stdlib/source/test/lux/target/ruby.lux
new file mode 100644
index 000000000..80d4a161f
--- /dev/null
+++ b/stdlib/source/test/lux/target/ruby.lux
@@ -0,0 +1,594 @@
+(.using
+ [library
+  [lux "*"
+   ["_" test {"+" Test}]
+   ["[0]" ffi]
+   [abstract
+    [monad {"+" do}]
+    ["[0]" predicate]]
+   [control
+    ["[0]" maybe ("[1]#[0]" functor)]
+    ["[0]" try {"+" Try} ("[1]#[0]" functor)]]
+   [data
+    ["[0]" bit ("[1]#[0]" equivalence)]
+    ["[0]" text ("[1]#[0]" equivalence)]
+    [collection
+     ["[0]" list ("[1]#[0]" functor)]]]
+   ["[0]" math
+    ["[0]" random {"+" Random} ("[1]#[0]" monad)]
+    [number
+     ["n" nat]
+     ["i" int]
+     ["f" frac]
+     ["[0]" i64]]]]]
+ [\\library
+  ["[0]" /]])
+
+(ffi.import: (eval [Text] "try" "?" Any))
+
+(def: (expression ??? it)
+  (-> (-> Any Bit) /.Expression Bit)
+  (|> it
+      /.code
+      ..eval
+      (try#each (|>> (maybe#each ???)
+                     (maybe.else false)))
+      (try.else false)))
+
+(def: test|literal
+  Test
+  (do [! random.monad]
+    [bool random.bit
+     float random.frac
+     int random.int
+     string (random.ascii/upper 5)]
+    ($_ _.and
+        (_.cover [/.nil]
+                 (|> /.nil
+                     /.code
+                     ..eval
+                     (try#each (function (_ it)
+                                 (case it
+                                   {.#None} true
+                                   {.#Some _} true)))
+                     (try.else false)))
+        (_.cover [/.bool]
+                 (expression (|>> (:as Bit) (bit#= bool))
+                             (/.bool bool)))
+        (_.cover [/.int]
+                 (expression (|>> (:as Int) (i.= int))
+                             (/.int int)))
+        (_.cover [/.float]
+                 (expression (|>> (:as Frac) (f.= float))
+                             (/.float float)))
+        (_.cover [/.string]
+                 (expression (|>> (:as Text) (text#= string))
+                             (/.string string)))
+        (_.cover [/.symbol]
+                 (expression (|>> (:as Text) (text#= string))
+                             (/.do "id2name" (list) {.#None} (/.symbol string))))
+        )))
+
+(def: test|bool
+  Test
+  (do [! random.monad]
+    [left random.bit
+     right random.bit]
+    (`` ($_ _.and
+            (~~ (template [ ]
+                  [(_.cover []
+                            (let [expected ( left right)]
+                              (expression (|>> (:as Bit) (bit#= expected))
+                                          ( (/.bool left) (/.bool right)))))]
+
+                  [/.or .or]
+                  [/.and .and]
+                  ))
+            (_.cover [/.not]
+                     (expression (|>> (:as Bit) (bit#= (not left)))
+                                 (/.not (/.bool left))))
+            ))))
+
+(def: test|float
+  Test
+  (do [! random.monad]
+    [parameter (random.only (|>> (f.= +0.0) not)
+                            random.safe_frac)
+     subject random.safe_frac]
+    (`` ($_ _.and
+            (~~ (template [  
]
+                  [(_.cover []
+                            (let [expected ( (
 parameter) (
 subject))]
+                              (expression (|>> (:as Frac) (f.= expected))
+                                          ( (/.float (
 parameter)) (/.float (
 subject))))))]
+
+                  [/.+ f.+ |>]
+                  [/.- f.- |>]
+                  [/.* f.* |>]
+                  [/./ f./ |>]
+                  [/.% f.mod |>]
+                  [/.pow math.pow f.abs]
+                  ))
+            (~~ (template [ ]
+                  [(_.cover []
+                            (let [expected ( parameter subject)]
+                              (expression (|>> (:as Bit) (bit#= expected))
+                                          ( (/.float parameter) (/.float subject)))))]
+
+                  [/.<  f.<]
+                  [/.<= f.<=]
+                  [/.>  f.>]
+                  [/.>= f.>=]
+                  [/.=  f.=]
+                  ))
+            ))))
+
+(def: int/16
+  (-> Int Int)
+  (i64.and (-- (i64.left_shifted 15 1))))
+
+(def: test|int
+  Test
+  (do [! random.monad]
+    [left random.int
+     right random.int
+
+     i16 (# ! each ..int/16 random.int)
+     shift (# ! each (n.% 16) random.nat)]
+    (`` ($_ _.and
+            (~~ (template [ ]
+                  [(_.cover []
+                            (let [expected ( left right)]
+                              (expression (|>> (:as Frac) f.int (i.= expected))
+                                          ( (/.int left) (/.int right)))))]
+
+                  [/.bit_or i64.or]
+                  [/.bit_xor i64.xor]
+                  [/.bit_and i64.and]
+                  ))
+            (_.cover [/.bit_not]
+                     (expression (|>> (:as Int) (i.= (i64.not left)))
+                                 (/.bit_not (/.int left))))
+            (_.cover [/.opposite]
+                     (expression (|>> (:as Int) (i.= (i.* -1 left)))
+                                 (/.opposite (/.int left))))
+            (_.cover [/.bit_shl]
+                     (let [expected (i64.left_shifted shift i16)]
+                       (expression (|>> (:as Frac) f.int (i.= expected))
+                                   (/.bit_shl (/.int (.int shift))
+                                              (/.int i16)))))
+            (_.cover [/.bit_shr]
+                     (let [expected (i.right_shifted shift i16)]
+                       (expression (|>> (:as Frac) f.int (i.= expected))
+                                   (/.bit_shr (/.int (.int shift))
+                                              (/.int i16)))))
+            ))))
+
+(def: test|array
+  Test
+  (do [! random.monad]
+    [size (# ! each (|>> (n.% 10) ++) random.nat)
+     index (# ! each (n.% size) random.nat)
+     items (random.list size random.safe_frac)
+     .let [expected (|> items
+                        (list.item index)
+                        (maybe.else f.not_a_number))]
+     from (# ! each (n.% size) random.nat)
+     plus (# ! each (n.% (n.- from size)) random.nat)
+     .let [to (/.int (.int (n.+ plus from)))
+           from (/.int (.int from))]]
+    ($_ _.and
+        (_.cover [/.array /.item]
+                 (and (expression (|>> (:as Frac) (f.= expected))
+                                  (/.item (/.int (.int index))
+                                          (/.array (list#each /.float items))))
+                      (expression (|>> (:as Bit))
+                                  (|> (/.array (list#each /.float items))
+                                      (/.item (/.int (.int size)))
+                                      (/.= /.nil)))))
+        (_.cover [/.array_range]
+                 (expression (|>> (:as Int) (i.= (.int (++ plus))))
+                             (|> (/.array (list#each /.float items))
+                                 (/.array_range from to)
+                                 (/.the "length"))))
+        )))
+
+(def: test|hash
+  Test
+  (do [! random.monad]
+    [expected random.safe_frac
+     field (random.ascii/upper 5)
+     dummy (random.only (|>> (text#= field) not)
+                        (random.ascii/upper 5))
+     .let [field (/.string field)
+           dummy (/.string dummy)]]
+    ($_ _.and
+        (_.cover [/.hash]
+                 (and (expression (|>> (:as Frac) (f.= expected))
+                                  (/.item field (/.hash (list [field (/.float expected)]))))
+                      (expression (|>> (:as Bit))
+                                  (|> (/.hash (list [field (/.float expected)]))
+                                      (/.item dummy)
+                                      (/.= /.nil)))))
+        )))
+
+... (def: test|object
+...   Test
+...   (do [! random.monad]
+...     [expected random.safe_frac
+...      field (random.ascii/upper 5)
+...      dummy (random.only (|>> (text#= field) not)
+...                         (random.ascii/upper 5))
+
+...      size (# ! each (|>> (n.% 10) ++) random.nat)
+...      index (# ! each (n.% size) random.nat)
+...      items (random.list size random.safe_frac)]
+...     ($_ _.and
+...         (_.cover [/.object /.the]
+...                  (expression (|>> (:as Frac) (f.= expected))
+...                              (/.the field (/.object (list [field (/.float expected)])))))
+...         (let [expected (|> items
+...                            (list.item index)
+...                            (maybe.else f.not_a_number))]
+...           (_.cover [/.do]
+...                    (expression (|>> (:as Frac) f.int (i.= (.int index)))
+...                                (|> (/.array (list#each /.float items))
+...                                    (/.do "lastIndexOf" (list (/.float expected)))))))
+...         (_.cover [/.undefined]
+...                  (expression (|>> (:as Bit))
+...                              (|> (/.object (list [field (/.float expected)]))
+...                                  (/.the dummy)
+...                                  (/.= /.undefined))))
+...         )))
+
+(def: test|computation
+  Test
+  (do [! random.monad]
+    [test random.bit
+     then random.safe_frac
+     else random.safe_frac
+
+     bool random.bit
+     float random.frac
+     string (random.ascii/upper 5)
+
+     comment (random.ascii/upper 10)]
+    ($_ _.and
+        ..test|bool
+        ..test|float
+        ..test|int
+        ..test|array
+        ..test|hash
+        ... ..test|object
+        (_.cover [/.?]
+                 (let [expected (if test then else)]
+                   (expression (|>> (:as Frac) (f.= expected))
+                               (/.? (/.bool test)
+                                    (/.float then)
+                                    (/.float else)))))
+        (_.cover [/.comment]
+                 (expression (|>> (:as Frac) (f.= then))
+                             (/.comment comment
+                               (/.float then))))
+        )))
+
+(def: test|expression
+  Test
+  (do [! random.monad]
+    [dummy random.safe_frac
+     expected random.safe_frac]
+    (`` ($_ _.and
+            (_.for [/.Literal]
+                   ..test|literal)
+            (_.for [/.Computation]
+                   ..test|computation)
+            ))))
+
+(def: test/location
+  Test
+  (do [! random.monad]
+    [float/0 random.safe_frac
+     $foreign (# ! each /.local (random.ascii/lower 10))
+     field (# ! each /.string (random.ascii/upper 10))]
+    ($_ _.and
+        (<| (_.for [/.Var])
+            ($_ _.and
+                (_.cover [/.LVar /.local /.set]
+                         (expression (|>> (:as Frac) (f.= (f.+ float/0 float/0)))
+                                     (|> ($_ /.then
+                                             (/.set (list $foreign) (/.+ $foreign $foreign))
+                                             (/.return $foreign))
+                                         (/.lambda {.#None} (list $foreign))
+                                         (/.apply_lambda/* (list (/.float float/0))))))
+                ))
+        (_.cover [/.Access]
+                 (and (expression (|>> (:as Frac) (f.= (f.+ float/0 float/0)))
+                                  (let [@ (/.item (/.int +0) $foreign)]
+                                    (|> ($_ /.then
+                                            (/.set (list $foreign) (/.array (list $foreign)))
+                                            (/.set (list @) (/.+ @ @))
+                                            (/.return @))
+                                        (/.lambda {.#None} (list $foreign))
+                                        (/.apply_lambda/* (list (/.float float/0))))))
+                      (expression (|>> (:as Frac) (f.= (f.+ float/0 float/0)))
+                                  (let [@ (/.item field $foreign)]
+                                    (|> ($_ /.then
+                                            (/.set (list $foreign) (/.hash (list [field $foreign])))
+                                            (/.set (list @) (/.+ @ @))
+                                            (/.return @))
+                                        (/.lambda {.#None} (list $foreign))
+                                        (/.apply_lambda/* (list (/.float float/0))))))
+                      ))
+        )))
+
+(def: test|label
+  Test
+  (do [! random.monad]
+    [input (# ! each ..int/16 random.int)
+
+     full_inner_iterations (# ! each (|>> (n.% 20) ++) random.nat)
+     expected_inner_iterations (# ! each (n.% full_inner_iterations) random.nat)
+
+     full_outer_iterations (# ! each (|>> (n.% 10) ++) random.nat)
+     expected_outer_iterations (# ! each (n.% full_outer_iterations) random.nat)
+
+     .let [$input (/.local "input")
+           $output (/.local "output")
+           $inner_index (/.local "inner_index")
+           $outer_index (/.local "outer_index")]]
+    ($_ _.and
+        (_.cover [/.break]
+                 (let [expected (i.* (.int expected_inner_iterations) input)]
+                   (expression (|>> (:as Frac) f.int (i.= expected))
+                               (|> ($_ /.then
+                                       (/.set (list $inner_index) (/.int +0))
+                                       (/.set (list $output) (/.int +0))
+                                       (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index)
+                                                ($_ /.then
+                                                    (/.when (/.= (/.int (.int expected_inner_iterations)) $inner_index)
+                                                            /.break)
+                                                    (/.set (list $output) (/.+ $input $output))
+                                                    (/.set (list $inner_index) (/.+ (/.int +1) $inner_index))
+                                                    ))
+                                       (/.return $output))
+                                   (/.lambda {.#None} (list $input))
+                                   (/.apply_lambda/* (list (/.int input)))))))
+        (_.cover [/.next]
+                 (let [expected (i.* (.int (n.- expected_inner_iterations full_inner_iterations)) input)]
+                   (expression (|>> (:as Frac) f.int (i.= expected))
+                               (|> ($_ /.then
+                                       (/.set (list $inner_index) (/.int +0))
+                                       (/.set (list $output) (/.int +0))
+                                       (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index)
+                                                ($_ /.then
+                                                    (/.set (list $inner_index) (/.+ (/.int +1) $inner_index))
+                                                    (/.when (/.<= (/.int (.int expected_inner_iterations)) $inner_index)
+                                                            /.next)
+                                                    (/.set (list $output) (/.+ $input $output))
+                                                    ))
+                                       (/.return $output))
+                                   (/.lambda {.#None} (list $input))
+                                   (/.apply_lambda/* (list (/.int input)))))))
+        )))
+
+(def: test|loop
+  Test
+  (do [! random.monad]
+    [input random.int
+     iterations (# ! each (n.% 10) random.nat)
+     .let [$input (/.local "input")
+           $output (/.local "output")
+           $index (/.local "index")
+           expected (i.* (.int iterations) input)]]
+    ($_ _.and
+        (_.cover [/.while]
+                 (expression (|>> (:as Int) (i.= expected))
+                             (|> ($_ /.then
+                                     (/.set (list $index) (/.int +0))
+                                     (/.set (list $output) (/.int +0))
+                                     (/.while (/.< (/.int (.int iterations)) $index)
+                                              ($_ /.then
+                                                  (/.set (list $output) (/.+ $input $output))
+                                                  (/.set (list $index) (/.+ (/.int +1) $index))
+                                                  ))
+                                     (/.return $output))
+                                 (/.lambda {.#None} (list $input))
+                                 (/.apply_lambda/* (list (/.int input))))))
+        (_.cover [/.for_in]
+                 (expression (|>> (:as Int) (i.= expected))
+                             (|> ($_ /.then
+                                     (/.set (list $output) (/.int +0))
+                                     (/.for_in $index (/.array (list.repeated iterations (/.int input)))
+                                               (/.set (list $output) (/.+ $index $output)))
+                                     (/.return $output))
+                                 (/.lambda {.#None} (list $input))
+                                 (/.apply_lambda/* (list (/.int input))))))
+        ..test|label
+        )))
+
+(def: test|exception
+  Test
+  (do [! random.monad]
+    [expected random.safe_frac
+     dummy (random.only (|>> (f.= expected) not)
+                        random.safe_frac)
+     $ex (# ! each /.local (random.ascii/lower 10))]
+    ($_ _.and
+        (_.cover [/.begin]
+                 (expression (|>> (:as Frac) (f.= expected))
+                             (|> (/.begin (/.return (/.float expected))
+                                          (list [(list) $ex (/.return (/.float dummy))]))
+                                 (/.lambda {.#None} (list))
+                                 (/.apply_lambda/* (list)))))
+        (_.cover [/.Rescue /.throw/1]
+                 (expression (|>> (:as Frac) (f.= expected))
+                             (|> (/.begin ($_ /.then
+                                              (/.throw/1 (/.string ""))
+                                              (/.return (/.float dummy)))
+                                          (list [(list) $ex (/.return (/.float expected))]))
+                                 (/.lambda {.#None} (list))
+                                 (/.apply_lambda/* (list)))))
+        )))
+
+(def: test|function
+  Test
+  (do [! random.monad]
+    [iterations (# ! each (n.% 10) random.nat)
+     $self (# ! each /.local (random.ascii/lower 1))
+     field (random.ascii/lower 3)
+     $class (# ! each /.local (random.ascii/upper 4))
+
+     float/0 random.safe_frac
+     float/1 random.safe_frac
+     float/2 random.safe_frac
+     $arg/0 (# ! each /.local (random.ascii/lower 10))
+     $arg/1 (# ! each /.local (random.ascii/lower 11))
+     $arg/2 (# ! each /.local (random.ascii/lower 12))]
+    ($_ _.and
+        (_.cover [/.lambda /.return]
+                 (and (expression (|>> (:as Frac) (f.= float/0))
+                                  (|> (/.return (/.float float/0))
+                                      (/.lambda {.#None} (list))
+                                      (/.apply_lambda/* (list))))
+                      (expression (|>> (:as Frac) f.nat (n.= iterations))
+                                  (|> (/.lambda {.#Some $self} (list $arg/0)
+                                                (/.return (/.? (/.< (/.int (.int iterations)) $arg/0)
+                                                               (/.apply_lambda/* (list (/.+ (/.int +1) $arg/0)) $self)
+                                                               $arg/0)))
+                                      (/.apply_lambda/* (list (/.int +0)))))))
+        (_.cover [/.apply_lambda/*]
+                 (expression (|>> (:as Frac) (f.= ($_ f.+ float/0 float/1 float/2)))
+                             (|> (/.return ($_ /.+ $arg/0 $arg/1 $arg/2))
+                                 (/.lambda {.#None} (list $arg/0 $arg/1 $arg/2))
+                                 (/.apply_lambda/* (list (/.float float/0) (/.float float/1) (/.float float/2))))))
+        (_.cover [/.function]
+                 (expression (|>> (:as Frac) f.nat (n.= iterations))
+                             (|> ($_ /.then
+                                     (/.function $self (list $arg/0)
+                                       (/.return (/.? (/.< (/.int (.int iterations)) $arg/0)
+                                                      (/.apply/1 $self (/.+ (/.int +1) $arg/0))
+                                                      $arg/0)))
+                                     (/.return (/.apply/1 $self (/.int +0))))
+                                 (/.lambda {.#None} (list))
+                                 (/.apply_lambda/* (list)))))
+        (_.cover [/.apply/1]
+                 (expression (|>> (:as Frac) (f.= float/0))
+                             (|> ($_ /.then
+                                     (/.function $self (list $arg/0)
+                                       (/.return $arg/0))
+                                     (/.return (/.apply/1 $self (/.float float/0))))
+                                 (/.lambda {.#None} (list))
+                                 (/.apply_lambda/* (list)))))
+        (_.cover [/.apply/2]
+                 (expression (|>> (:as Frac) (f.= ($_ f.+ float/0 float/1)))
+                             (|> ($_ /.then
+                                     (/.function $self (list $arg/0 $arg/1)
+                                       (/.return ($_ /.+ $arg/0 $arg/1)))
+                                     (/.return (/.apply/2 $self (/.float float/0) (/.float float/1))))
+                                 (/.lambda {.#None} (list))
+                                 (/.apply_lambda/* (list)))))
+        (_.cover [/.apply/3]
+                 (expression (|>> (:as Frac) (f.= ($_ f.+ float/0 float/1 float/2)))
+                             (|> ($_ /.then
+                                     (/.function $self (list $arg/0 $arg/1 $arg/2)
+                                       (/.return ($_ /.+ $arg/0 $arg/1 $arg/2)))
+                                     (/.return (/.apply/3 $self (/.float float/0) (/.float float/1) (/.float float/2))))
+                                 (/.lambda {.#None} (list))
+                                 (/.apply_lambda/* (list)))))
+        (_.cover [/.apply/*]
+                 (expression (|>> (:as Frac) (f.= ($_ f.+ float/0 float/1 float/2)))
+                             (|> ($_ /.then
+                                     (/.function $self (list $arg/0 $arg/1 $arg/2)
+                                       (/.return ($_ /.+ $arg/0 $arg/1 $arg/2)))
+                                     (/.return (/.apply/* (list (/.float float/0) (/.float float/1) (/.float float/2)) {.#None} $self)))
+                                 (/.lambda {.#None} (list))
+                                 (/.apply_lambda/* (list)))))
+        ... (_.cover [/.new]
+        ...          (let [$this (/.local "this")]
+        ...            (expression (|>> (:as Frac) (f.= float/0))
+        ...                        (/.apply/1 (/.closure (list $arg/0)
+        ...                                              ($_ /.then
+        ...                                                  (/.function $class (list)
+        ...                                                               (/.set (/.the field $this) $arg/0))
+        ...                                                  (/.return (/.the field (/.new $class (list))))))
+        ...                                   (/.float float/0)))))
+        )))
+
+(def: test|branching
+  Test
+  (do [! random.monad]
+    [float/0 random.safe_frac
+     float/1 random.safe_frac
+     float/2 random.safe_frac
+     arg/0 (random.ascii/lower 10)
+     arg/1 (random.only (|>> (text#= arg/0) not)
+                        (random.ascii/lower 10))
+     arg/2 (random.only (predicate.and (|>> (text#= arg/0) not)
+                                       (|>> (text#= arg/1) not))
+                        (random.ascii/lower 10))
+     .let [$arg/0 (/.local arg/0)
+           $arg/1 (/.local arg/1)
+           $arg/2 (/.local arg/2)]
+     ??? random.bit]
+    ($_ _.and
+        (_.cover [/.if]
+                 (expression (|>> (:as Frac) (f.= (if ??? float/0 float/1)))
+                             (|> (/.if (/.bool ???)
+                                   (/.return (/.float float/0))
+                                   (/.return (/.float float/1)))
+                                 (/.lambda {.#None} (list))
+                                 (/.apply_lambda/* (list)))))
+        (_.cover [/.when]
+                 (expression (|>> (:as Frac) (f.= (if ??? float/0 float/1)))
+                             (|> ($_ /.then
+                                     (/.when (/.bool ???)
+                                             (/.return (/.float float/0)))
+                                     (/.return (/.float float/1)))
+                                 (/.lambda {.#None} (list))
+                                 (/.apply_lambda/* (list)))))
+        )))
+
+(def: test|statement
+  Test
+  (do [! random.monad]
+    [float/0 random.safe_frac
+     float/1 random.safe_frac
+     float/2 random.safe_frac
+     $arg/0 (# ! each /.local (random.ascii/lower 10))
+     $arg/1 (# ! each /.local (random.ascii/lower 11))
+     $arg/2 (# ! each /.local (random.ascii/lower 12))]
+    ($_ _.and
+        (_.cover [/.statement]
+                 (expression (|>> (:as Frac) (f.= float/0))
+                             (|> ($_ /.then
+                                     (/.statement (/.+ $arg/0 $arg/0))
+                                     (/.return $arg/0))
+                                 (/.lambda {.#None} (list $arg/0))
+                                 (/.apply_lambda/* (list (/.float float/0))))))
+        (_.cover [/.then]
+                 (expression (|>> (:as Frac) (f.= float/0))
+                             (|> ($_ /.then
+                                     (/.return $arg/0)
+                                     (/.return $arg/1))
+                                 (/.lambda {.#None} (list $arg/0 $arg/1))
+                                 (/.apply_lambda/* (list (/.float float/0) (/.float float/1))))))
+        ..test|exception
+        ..test|function
+        ..test|branching
+        ..test|loop
+        (_.for [/.Location]
+               ..test/location)
+        )))
+
+(def: .public test
+  Test
+  (do [! random.monad]
+    []
+    (<| (_.covering /._)
+        (_.for [/.Code /.code])
+        ($_ _.and
+            (_.for [/.Expression]
+                   ..test|expression)
+            (_.for [/.Statement]
+                   ..test|statement)
+            ))))
diff --git a/stdlib/source/test/lux/tool.lux b/stdlib/source/test/lux/tool.lux
index 5a7509b99..37e45bcee 100644
--- a/stdlib/source/test/lux/tool.lux
+++ b/stdlib/source/test/lux/tool.lux
@@ -5,6 +5,7 @@
   ["[0]" / "_"
    [compiler
     ["[1][0]" arity]
+    ["[1][0]" reference/variable]
     ... [language
     ...  [lux
     ...   ["[1][0]" syntax]
@@ -17,6 +18,7 @@
   Test
   ($_ _.and
       /arity.test
+      /reference/variable.test
       ... /syntax.test
       ... /analysis.test
       ... /synthesis.test
diff --git a/stdlib/source/test/lux/tool/compiler/reference/variable.lux b/stdlib/source/test/lux/tool/compiler/reference/variable.lux
new file mode 100644
index 000000000..980a280f0
--- /dev/null
+++ b/stdlib/source/test/lux/tool/compiler/reference/variable.lux
@@ -0,0 +1,41 @@
+(.using
+ [library
+  [lux "*"
+   ["_" test {"+" Test}]
+   [abstract
+    [monad {"+" do}]
+    [\\specification
+     ["$[0]" equivalence]
+     ["$[0]" hash]]]
+   [data
+    ["[0]" text ("[1]#[0]" equivalence)]]
+   [math
+    ["[0]" random {"+" Random}]]]]
+ [\\library
+  ["[0]" /]])
+
+(def: .public random
+  (Random /.Variable)
+  ($_ random.or
+      random.nat
+      random.nat
+      ))
+
+(def: .public test
+  Test
+  (<| (_.covering /._)
+      (_.for [/.Variable])
+      (do [! random.monad]
+        [register random.nat]
+        ($_ _.and
+            (_.for [/.equivalence]
+                   ($equivalence.spec /.equivalence ..random))
+            (_.for [/.hash]
+                   ($hash.spec /.hash ..random))
+            (_.cover [/.self /.self?]
+                     (/.self? (/.self)))
+            (_.for [/.Register]
+                   (_.cover [/.format]
+                            (not (text#= (/.format {/.#Local register})
+                                         (/.format {/.#Foreign register})))))
+            ))))
-- 
cgit v1.2.3