From 8ca6fcf3f147cae24f385423e84ae1ab0821293f Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Mon, 16 Jan 2023 14:31:15 -0400 Subject: Added compilation of references for C++. --- stdlib/source/test/lux/abstract/monad/indexed.lux | 6 +- .../source/test/lux/control/function/predicate.lux | 10 +- .../test/lux/meta/compiler/language/lux/phase.lux | 4 +- .../lux/phase/translation/jvm/function.lux | 102 ++++++++++++++------- .../lux/phase/translation/jvm/reference.lux | 87 ++++++++++++++++++ 5 files changed, 170 insertions(+), 39 deletions(-) create mode 100644 stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/reference.lux (limited to 'stdlib/source/test') diff --git a/stdlib/source/test/lux/abstract/monad/indexed.lux b/stdlib/source/test/lux/abstract/monad/indexed.lux index 152dc50d6..e0e89297d 100644 --- a/stdlib/source/test/lux/abstract/monad/indexed.lux +++ b/stdlib/source/test/lux/abstract/monad/indexed.lux @@ -16,7 +16,8 @@ ["[0]" /]]) (type (Effect input output value) - (-> input [output value])) + (-> input + [output value])) (def monad (/.Monad Effect) @@ -39,7 +40,8 @@ right random.nat .let [expected (n.+ left right)]]) (all _.and - (_.coverage [/.do] + (_.coverage [/.do + /.in /.then] (let [it (is (Effect [] [] Nat) (/.do ..monad [left' (in left) diff --git a/stdlib/source/test/lux/control/function/predicate.lux b/stdlib/source/test/lux/control/function/predicate.lux index 4640ba8fa..3e3ff9653 100644 --- a/stdlib/source/test/lux/control/function/predicate.lux +++ b/stdlib/source/test/lux/control/function/predicate.lux @@ -69,10 +69,12 @@ (bit#= (/.none sample) ((/.and /.none /.all) sample))) (_.coverage [/.complement] - (and (not (bit#= (/.none sample) - ((/.complement /.none) sample))) - (not (bit#= (/.all sample) - ((/.complement /.all) sample))))) + (and (bit#= (not (/.none sample)) + ((/.complement /.none) sample)) + (bit#= (not (/.all sample)) + ((/.complement /.all) sample)))) + (_.coverage [/.not] + (alias? /.complement /.not)) (_.coverage [/.difference] (let [/2? (multiple? 2) /3? (multiple? 3)] diff --git a/stdlib/source/test/lux/meta/compiler/language/lux/phase.lux b/stdlib/source/test/lux/meta/compiler/language/lux/phase.lux index 1ccb40e7f..35e683c48 100644 --- a/stdlib/source/test/lux/meta/compiler/language/lux/phase.lux +++ b/stdlib/source/test/lux/meta/compiler/language/lux/phase.lux @@ -37,7 +37,8 @@ ["[1]/[0]" value] ["[1]/[0]" runtime] ["[1]/[0]" complex] - ["[1]/[0]" function]]]]) + ["[1]/[0]" function] + ["[1]/[0]" reference]]]]) (def (injection value) (All (_ of) @@ -228,4 +229,5 @@ /translation/jvm/runtime.test /translation/jvm/complex.test /translation/jvm/function.test + /translation/jvm/reference.test ))) 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 c8d1d3e75..a2bdb6ce2 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 @@ -8,7 +8,8 @@ [monad (.only do)]] [control ["[0]" io] - ["[0]" try]] + ["[0]" try (.use "[1]#[0]" functor)] + ["[0]" function]] [data ["[0]" bit (.use "[1]#[0]" equivalence)] [collection @@ -21,9 +22,6 @@ [meta ["[0]" location] [compiler - [language - [lux - ["[0]" synthesis]]] [meta ["[0]" archive]]]] [test @@ -37,6 +35,7 @@ ["[0]" extension] [// ["[0]" phase] + ["[0]" synthesis] ["[0]" translation]]]]]] [// ["[0]T" complex]]) @@ -55,9 +54,10 @@ (undefined))) phase (//.translate extender complexT.lux) @ [module 0 0] - $unit [0 0]] + $unit [(-- 0) (-- 0)]] - arity (of ! each (|>> (n.% 16) ++) random.nat)]) + arity (of ! each (|>> (n.% 16) (n.+ 2)) random.nat) + inner_arity (of ! each (|>> (n.% arity) (n.+ 1)) random.nat)]) (all _.and (_.coverage [/.abstraction] (|> (do try.monad @@ -69,34 +69,72 @@ (<| (phase.result state) (do phase.monad [_ (translation.set_buffer translation.empty_buffer) - _ runtime.translation it (/.abstraction phase archive [(list) 1 (synthesis.i64 @ expected_i64)])] - (in (when (of host evaluate $unit [{.#None} it]) - {try.#Success it} - (i64#= expected_i64 ((as (-> [] I64) it) [])) - - {try.#Failure error} - false))))) + (in (|> it + [{.#None}] + (of host evaluate $unit) + (try#each (|>> (as (-> [] I64)) + (function.on []) + (i64#= expected_i64))) + (try.else false)))))) (try.else false))) (_.coverage [/.apply] - (|> (do try.monad - [[_ archive] (archive.reserve "" archive.empty) - [_ archive] (archive.reserve module archive) - .let [[_ host] (io.run! host.host) - state (is runtime.State - (translation.state host module))]] - (<| (phase.result state) - (do phase.monad - [_ (translation.set_buffer translation.empty_buffer) - it (/.apply phase archive - [(synthesis.function/abstraction @ [(list) arity (synthesis.i64 @ expected_i64)]) - (list.repeated arity (synthesis.bit @ expected_bit))])] - (in (when (of host evaluate $unit [{.#None} it]) - {try.#Success actual_i64} - (i64#= expected_i64 (as I64 actual_i64)) - - {try.#Failure error} - false))))) - (try.else false))) + (let [exact_arity! + (|> (do try.monad + [[_ archive] (archive.reserve "" archive.empty) + [_ archive] (archive.reserve module archive) + .let [[_ host] (io.run! host.host) + state (is runtime.State + (translation.state host module))]] + (<| (phase.result state) + (do phase.monad + [_ (translation.set_buffer translation.empty_buffer) + it (/.apply phase archive + [(synthesis.function/abstraction @ [(list) arity (synthesis.i64 @ expected_i64)]) + (list.repeated arity (synthesis.bit @ expected_bit))])] + (in (|> it + [{.#None}] + (of host evaluate $unit) + (try#each (|>> (as I64) + (i64#= expected_i64))) + (try.else false)))))) + (try.else false)) + + multiple_applications! + (|> (do try.monad + [[_ archive] (archive.reserve "" archive.empty) + [_ archive] (archive.reserve module archive) + .let [[_ host] (io.run! host.host) + state (is runtime.State + (translation.state host module))]] + (<| (phase.result state) + (do phase.monad + [_ (translation.set_buffer translation.empty_buffer) + .let [outer_arity (n.- inner_arity arity) + + inner_abstraction (is synthesis.Term + (<| (synthesis.function/abstraction @) + [(list) inner_arity + (synthesis.i64 @ expected_i64)])) + outer_abstraction (is synthesis.Term + (<| (synthesis.function/abstraction @) + [(list) outer_arity + inner_abstraction])) + 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))])] + (in (|> it + [{.#None}] + (of host evaluate $unit) + (try#each (|>> (as I64) + (i64#= expected_i64))) + (try.else false)))))) + (try.else false))] + (and exact_arity! + multiple_applications!))) ))) 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 new file mode 100644 index 000000000..a8d780b3e --- /dev/null +++ b/stdlib/source/test/lux/meta/compiler/language/lux/phase/translation/jvm/reference.lux @@ -0,0 +1,87 @@ +... This Source Code Form is subject to the terms of the Mozilla Public License, v. 2.0. +... If a copy of the MPL was not distributed with this file, You can obtain one at https://mozilla.org/MPL/2.0/. + +(.require + [library + [lux (.except) + [abstract + [monad (.only do)]] + [control + ["[0]" io] + ["[0]" try (.use "[1]#[0]" functor)]] + [data + [collection + ["[0]" list (.use "[1]#[0]" monoid)]]] + [math + ["[0]" random (.only Random)] + [number + ["[0]" i64 (.use "[1]#[0]" equivalence)] + ["n" nat]]] + [meta + ["[0]" location] + [compiler + [meta + ["[0]" archive]]]] + [test + ["_" property (.only Test)]]]] + [\\library + ["[0]" / (.only) + ["[0]" // (.only) + ["[0]" host] + ["[0]" runtime] + ["[0]" function] + [/// + ["[0]" extension] + [// + ["[0]" phase] + ["[0]" synthesis] + ["[0]" translation]]]]]] + [// + ["[0]T" complex]]) + +(def .public test + Test + (<| (_.covering /._) + (do [! random.monad] + [module (random.lower_cased 1) + + expected random.i64 + dummy (random.only (|>> (i64#= expected) not) random.i64) + + .let [extender (is extension.Extender + (function (_ _) + (undefined))) + next (//.translate extender complexT.lux) + @ [module 0 0] + $unit [(-- 0) (-- 0)]] + + before (of ! each (n.% 8) random.nat) + after (of ! each (n.% 8) random.nat) + .let [arity (++ (n.+ before after)) + local (++ before)]]) + (all _.and + (_.coverage [/.variable] + (|> (do try.monad + [[_ archive] (archive.reserve "" archive.empty) + [_ archive] (archive.reserve module archive) + .let [[_ host] (io.run! host.host) + state (is runtime.State + (translation.state host module))]] + (<| (phase.result state) + (do phase.monad + [_ (translation.set_buffer translation.empty_buffer) + it (next archive (<| (synthesis.function/apply @) + [(<| (synthesis.function/abstraction @) + [(list) arity (synthesis.variable/local @ local)]) + (all list#composite + (list.repeated before (synthesis.i64 @ dummy)) + (list (synthesis.i64 @ expected)) + (list.repeated after (synthesis.i64 @ dummy)))]))] + (in (|> it + [{.#None}] + (of host evaluate $unit) + (try#each (|>> (as I64) + (i64#= expected))) + (try.else false)))))) + (try.else false))) + ))) -- cgit v1.2.3