diff options
author | Eduardo Julian | 2023-01-18 01:38:48 -0400 |
---|---|---|
committer | Eduardo Julian | 2023-01-18 01:38:48 -0400 |
commit | 670438b982bbe0b662b0a65958dc4f8b289d3906 (patch) | |
tree | 390ddabf9c802c1f38d4fd985b7e29677cb0ac66 /stdlib/source/test | |
parent | dfe09eb7a90dbf164bc0c78085b2d340e0928190 (diff) |
More efficient "let" and "exec" expressions.
Diffstat (limited to '')
12 files changed, 76 insertions, 65 deletions
diff --git a/stdlib/source/test/lux/math/number/i64.lux b/stdlib/source/test/lux/math/number/i64.lux index 32c5a1717..d03f3c6b3 100644 --- a/stdlib/source/test/lux/math/number/i64.lux +++ b/stdlib/source/test/lux/math/number/i64.lux @@ -171,7 +171,10 @@ (_.for [.I64]) (do [! random.monad] [pattern random.nat - idx (of ! each (n.% /.width) random.nat)] + idx (of ! each (n.% /.width) random.nat) + + left random.nat + right random.nat] (all _.and (_.coverage [/.width /.bits_per_byte /.bytes_per_i64] (and (n.= /.bytes_per_i64 @@ -201,7 +204,10 @@ (/.not pattern))) (/#= /.false (/.xor pattern - pattern)))) + pattern)) + (/#= (/.xor left right) + (/.and (/.or left right) + (/.not (/.and left right)))))) (_.coverage [/.ones] (let [zero&one! (if (/.one? idx pattern) diff --git a/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/complex.lux b/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/complex.lux index bf08c727a..66e5421b0 100644 --- a/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/complex.lux +++ b/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/complex.lux @@ -77,8 +77,7 @@ .let [extender (is extension.Extender (function (_ _) (undefined))) - phase (//.translate extender ..lux) - $unit [0 0]]]) + phase (//.translate extender ..lux)]]) (all _.and (_.coverage [/.variant] (`` (and (,, (with_template [<lefts> <right?> <synthesis> <expected> <=>] @@ -91,7 +90,7 @@ [_ (translation.set_buffer translation.empty_buffer) it (/.variant phase archive.empty [<lefts> <right?> (<synthesis> location.dummy <expected>)])] - (in (when (of host evaluate $unit [{.#None} it]) + (in (when (of host evaluate [{.#None} it]) {try.#Success actual} (when (as Variant/3 actual) {<lefts> <right?> actual} @@ -120,7 +119,7 @@ (list (synthesis.bit location.dummy expected_bit) (synthesis.i64 location.dummy expected_i64) (synthesis.text location.dummy expected_text)))] - (in (when (of host evaluate $unit [{.#None} it]) + (in (when (of host evaluate [{.#None} it]) {try.#Success actual} (let [[actual_bit actual_i64 actual_text] (as Tuple/3 actual)] (and (bit#= expected_bit actual_bit) diff --git a/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/function.lux b/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/function.lux index 81cfb675e..906c23a71 100644 --- a/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/function.lux +++ b/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/function.lux @@ -28,6 +28,9 @@ ["_" property (.only Test)]]]] [\\library ["[0]" / (.only) + [field + [constant + ["[0]" arity]]] ["[0]" // (.only) ["[0]" host] ["[0]" runtime] @@ -58,11 +61,10 @@ .let [extender (is extension.Extender (function (_ _) (undefined))) - phase (//.translate extender complexT.lux) - @ [module 0 0] - $unit [(-- 0) (-- 0)]] + next (//.translate extender complexT.lux) + @ [module 0 0]] - arity (of ! each (|>> (n.% 16) (n.+ 2)) random.nat) + arity (of ! each (|>> (n.% (-- arity.maximum)) (n.+ 2)) random.nat) inner_arity (of ! each (|>> (n.% arity) (n.+ 1)) random.nat)]) (all _.and (_.coverage [/.abstraction] @@ -75,11 +77,11 @@ (<| (phase.result state) (do phase.monad [_ (translation.set_buffer translation.empty_buffer) - it (/.abstraction phase archive + it (/.abstraction next archive [(list) 1 (synthesis.i64 @ expected_i64)])] (in (|> it [{.#None}] - (of host evaluate $unit) + (of host evaluate) (try#each (|>> (as (-> [] I64)) (function.on []) (i64#= expected_i64))) @@ -96,12 +98,12 @@ (<| (phase.result state) (do phase.monad [_ (translation.set_buffer translation.empty_buffer) - it (/.apply phase archive + it (/.apply next archive [(synthesis.function/abstraction @ [(list) arity (synthesis.i64 @ expected_i64)]) (list.repeated arity (synthesis.bit @ expected_bit))])] (in (|> it [{.#None}] - (of host evaluate $unit) + (of host evaluate) (try#each (|>> (as I64) (i64#= expected_i64))) (try.else false)))))) @@ -130,13 +132,15 @@ outer_application (is synthesis.Term (<| (synthesis.function/apply @) [outer_abstraction - (list.repeated outer_arity (synthesis.bit @ expected_bit))]))] - it (/.apply phase archive - [outer_application - (list.repeated inner_arity (synthesis.bit @ expected_bit))])] + (list.repeated outer_arity (synthesis.bit @ expected_bit))])) + inner_application (is synthesis.Term + (<| (synthesis.function/apply @) + [outer_application + (list.repeated inner_arity (synthesis.bit @ expected_bit))]))] + it (next archive inner_application)] (in (|> it [{.#None}] - (of host evaluate $unit) + (of host evaluate) (try#each (|>> (as I64) (i64#= expected_i64))) (try.else false)))))) diff --git a/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/function/field/variable/count.lux b/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/function/field/variable/count.lux index 974851bfd..a370740d7 100644 --- a/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/function/field/variable/count.lux +++ b/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/function/field/variable/count.lux @@ -63,8 +63,7 @@ (function (_ _) (undefined))) next (jvm.translate extender complexT.lux) - @ [module 0 0] - $unit [(-- 0) (-- 0)]] + @ [module 0 0]] arity (of ! each (|>> (n.% arity.maximum) (n.max arity.minimum)) random.nat) partial_application (of ! each (n.% arity) random.nat)]) @@ -82,7 +81,7 @@ !.i2l (value.boxed type.long)) [{.#None}] - (of host evaluate $unit) + (of host evaluate) (try#each (|>> (as Nat) (n#= 0))) (try.else false)))) (_.coverage [/.value] @@ -104,7 +103,7 @@ !.i2l (value.boxed type.long)) [{.#None}] - (of host evaluate $unit) + (of host evaluate) (try#each (|>> (as Nat) (n#= 0))) (try.else false)))))) (try.else false)) @@ -130,7 +129,7 @@ !.i2l (value.boxed type.long)) [{.#None}] - (of host evaluate $unit) + (of host evaluate) (try#each (|>> (as Nat) (n#= partial_application))) (try.else false)))))) (try.else false))] diff --git a/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/host.lux b/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/host.lux index e175d3202..8272618f6 100644 --- a/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/host.lux +++ b/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/host.lux @@ -28,13 +28,12 @@ Test (<| (_.covering /._) (do [! random.monad] - [.let [$unit [0 0]] - expected (random.upper_cased 1)]) + [expected (random.upper_cased 1)]) (all _.and (_.coverage [/.host] (io.run! (do io.monad [[class_loader host] /.host] - (in (when (of host evaluate $unit [{.#None} (bytecode.string expected)]) + (in (when (of host evaluate [{.#None} (bytecode.string expected)]) {try.#Success actual} (text#= expected (as Text actual)) @@ -43,7 +42,7 @@ (_.coverage [/.invalid_value] (io.run! (do io.monad [[class_loader host] /.host] - (in (when (of host evaluate $unit [{.#None} bytecode.aconst_null]) + (in (when (of host evaluate [{.#None} bytecode.aconst_null]) {try.#Success _} false @@ -52,13 +51,13 @@ (_.coverage [/.cannot_load] (io.run! (do io.monad [[class_loader host] /.host] - (in (when (of host evaluate $unit [{.#None} (all bytecode.composite - bytecode.lconst_0 - bytecode.lconst_0 - bytecode.ldiv - bytecode.pop2 - (bytecode.string expected) - )]) + (in (when (of host evaluate [{.#None} (all bytecode.composite + bytecode.lconst_0 + bytecode.lconst_0 + bytecode.ldiv + bytecode.pop2 + (bytecode.string expected) + )]) {try.#Success _} false diff --git a/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/primitive.lux b/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/primitive.lux index 60088f11f..565903706 100644 --- a/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/primitive.lux +++ b/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/primitive.lux @@ -31,15 +31,13 @@ [expected_bit random.bit expected_i64 random.i64 expected_f64 random.frac - expected_text (random.lower_cased 1) - - .let [$unit [0 0]]]) + expected_text (random.lower_cased 1)]) (`` (all _.and (,, (with_template [<constructor> <expected> <type> <=>] [(_.coverage [<constructor>] (io.run! (do io.monad [[class_loader host] host.host] - (in (when (of host evaluate $unit [{.#None} (<constructor> <expected>)]) + (in (when (of host evaluate [{.#None} (<constructor> <expected>)]) {try.#Success actual} (<=> <expected> (as <type> actual)) diff --git a/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/reference.lux b/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/reference.lux index a8d780b3e..1c039fe6b 100644 --- a/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/reference.lux +++ b/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/reference.lux @@ -52,8 +52,7 @@ (function (_ _) (undefined))) next (//.translate extender complexT.lux) - @ [module 0 0] - $unit [(-- 0) (-- 0)]] + @ [module 0 0]] before (of ! each (n.% 8) random.nat) after (of ! each (n.% 8) random.nat) @@ -79,7 +78,7 @@ (list.repeated after (synthesis.i64 @ dummy)))]))] (in (|> it [{.#None}] - (of host evaluate $unit) + (of host evaluate) (try#each (|>> (as I64) (i64#= expected))) (try.else false)))))) diff --git a/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/value.lux b/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/value.lux index 1190b7eac..b01c2e334 100644 --- a/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/value.lux +++ b/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/value.lux @@ -38,9 +38,7 @@ [expected_bit random.bit expected_i64 random.i64 expected_f64 random.frac - expected_text (random.lower_cased 1) - - .let [$unit [0 0]]]) + expected_text (random.lower_cased 1)]) (`` (all _.and (_.coverage [/.field] (not (text.empty? /.field))) @@ -48,12 +46,12 @@ (and (,, (with_template [<constructor> <expected> <lux_type> <=> <jvm_type>] [(io.run! (do io.monad [[class_loader host] host.host] - (in (when (of host evaluate $unit [{.#None} - (all //.composite - (<constructor> <expected>) - (/.primitive <jvm_type>) - (/.boxed <jvm_type>) - )]) + (in (when (of host evaluate [{.#None} + (all //.composite + (<constructor> <expected>) + (/.primitive <jvm_type>) + (/.boxed <jvm_type>) + )]) {try.#Success actual} (<=> <expected> (as <lux_type> actual)) diff --git a/stdlib/source/test/lux/meta/compiler/language/lux/translation.lux b/stdlib/source/test/lux/meta/compiler/language/lux/translation.lux index 3a29d167a..babc74324 100644 --- a/stdlib/source/test/lux/meta/compiler/language/lux/translation.lux +++ b/stdlib/source/test/lux/meta/compiler/language/lux/translation.lux @@ -31,7 +31,7 @@ (def dummy_host (/.Host Any Any) (implementation - (def (evaluate _ _) + (def (evaluate _) {try.#Failure ""}) (def (execute _) {try.#Failure ""}) diff --git a/stdlib/source/test/lux/meta/compiler/meta/context.lux b/stdlib/source/test/lux/meta/compiler/meta/context.lux index f310fc9d0..7229c3804 100644 --- a/stdlib/source/test/lux/meta/compiler/meta/context.lux +++ b/stdlib/source/test/lux/meta/compiler/meta/context.lux @@ -34,16 +34,20 @@ (def .public test Test (<| (_.covering /._) - (_.for [/.Context /.Extension]) + (_.for [/.Extension + + /.Context + /.#host /.#host_module_extension /.#target /.#artifact_extension]) (do [! random.monad] [target (random.lower_cased 1)] (all _.and - (_.coverage [/.js /.jvm /.lua /.python /.ruby] + (_.coverage [/.js /.jvm /.lua /.python /.ruby /.c++] (let [contexts (list (/.js target) (/.jvm target) (/.lua target) (/.python target) - (/.ruby target)) + (/.ruby target) + (/.c++ target)) maximum (list.size contexts)] (`` (and (,, (with_template [<amount> <slot>] [(|> contexts diff --git a/stdlib/source/test/lux/meta/compiler/target/jvm.lux b/stdlib/source/test/lux/meta/compiler/target/jvm.lux index 3abe5e315..7d1033a6a 100644 --- a/stdlib/source/test/lux/meta/compiler/target/jvm.lux +++ b/stdlib/source/test/lux/meta/compiler/target/jvm.lux @@ -1753,7 +1753,7 @@ (def .public test Test - (<| (_.context (%.symbol (symbol .._))) + (<| (_.covering .._) (all _.and (<| (_.context "instruction") ..instruction) diff --git a/stdlib/source/test/lux/world/time/series/average.lux b/stdlib/source/test/lux/world/time/series/average.lux index d4c6df8e7..fc5843ca6 100644 --- a/stdlib/source/test/lux/world/time/series/average.lux +++ b/stdlib/source/test/lux/world/time/series/average.lux @@ -57,7 +57,7 @@ Test (<| (_.covering /._) (do [! random.monad] - [expected_events (of ! each (|>> (n.% 10) ++) random.nat) + [expected_events (of ! each (|>> (n.% 9) (n.+ 2)) random.nat) input (series expected_events) additional (of ! each (n.% expected_events) random.nat)]) (all _.and @@ -102,13 +102,18 @@ weighted (/.moving /.weighted additional input) - .let [(open "//#[0]") (//.equivalence f.equivalence)]] - (in (and (and (well_windowed? input additional exponential) - (well_windowed? input additional simple) - (well_windowed? input additional weighted)) - (and (not (//#= exponential simple)) - (not (//#= exponential weighted)) - (not (//#= simple weighted))) - ))))) + .let [(open "//#[0]") (//.equivalence f.equivalence) + + all_are_well_windowed! + (and (well_windowed? input additional exponential) + (well_windowed? input additional simple) + (well_windowed? input additional weighted)) + + all_are_different! + (and (not (//#= exponential simple)) + (not (//#= exponential weighted)) + (not (//#= simple weighted)))]] + (in (and all_are_well_windowed! + all_are_different!))))) )) ))) |