diff options
author | Eduardo Julian | 2022-02-27 04:53:04 -0400 |
---|---|---|
committer | Eduardo Julian | 2022-02-27 04:53:04 -0400 |
commit | 4167849041d7635a0fc2e81fc2bebae3fa0bb3d9 (patch) | |
tree | 5bbe3fc5efb146e709820d2b00a2bcbbf8b4827a /stdlib/source/library | |
parent | 08518ba37d9094c5cc8683fc404c349e534b8dc9 (diff) |
Fixed directive extensions for Lux/Lua.
Diffstat (limited to '')
17 files changed, 270 insertions, 223 deletions
diff --git a/stdlib/source/library/lux/ffi.jvm.lux b/stdlib/source/library/lux/ffi.jvm.lux index ff3550fde..b43a1b122 100644 --- a/stdlib/source/library/lux/ffi.jvm.lux +++ b/stdlib/source/library/lux/ffi.jvm.lux @@ -1956,5 +1956,6 @@ [as_byte .Int ..long_to_byte ..Long ..byte_to_long ..Byte of_byte] [as_short .Int ..long_to_short ..Long ..short_to_long ..Short of_short] [as_int .Int ..long_to_int ..Long ..int_to_long ..Integer of_int] + [as_char .Int ..long_to_char ..Long ..char_to_long ..Character of_char] [as_float .Frac ..double_to_float ..Double ..float_to_double ..Float of_float] ) diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux index 752d3fe65..c63f5cb2c 100644 --- a/stdlib/source/library/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux @@ -577,16 +577,17 @@ ///directive.#analysis ///directive.#state extension.#state] - (function (_ analysis_state) - (|> analysis_state - (:as .Lux) - (revised@ .#modules (function (_ current) - (list#composite (list.only (|>> product.left - (set.member? additions) - not) - current) - modules))) - :expected))))] + (: (All (_ a) (-> a a)) + (function (_ analysis_state) + (|> analysis_state + (:as .Lux) + (revised@ .#modules (function (_ current) + (list#composite (list.only (|>> product.left + (set.member? additions) + not) + current) + modules))) + :expected)))))] state (monad.mix ! with_all_extensions state extended_states)] (in (with_modules state)))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux index 7e286955e..f6e024d3b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux @@ -43,68 +43,73 @@ (custom [<code>.any (function (_ extension phase archive lengthC) - (do phase.monad - [lengthA (analysis/type.expecting Nat - (phase archive lengthC)) - [var_id varT] (analysis/type.check check.var) - _ (analysis/type.inference (type (Array varT)))] - (in {analysis.#Extension extension (list lengthA)})))])) + (<| analysis/type.with_var + (function (_ [@var :var:])) + (do phase.monad + [lengthA (analysis/type.expecting Nat + (phase archive lengthC)) + _ (analysis/type.inference (type (Array :var:)))] + (in {analysis.#Extension extension (list lengthA)}))))])) (def: array::length Handler (custom [<code>.any (function (_ extension phase archive arrayC) - (do phase.monad - [[var_id varT] (analysis/type.check check.var) - arrayA (analysis/type.expecting (type (Array varT)) - (phase archive arrayC)) - _ (analysis/type.inference Nat)] - (in {analysis.#Extension extension (list arrayA)})))])) + (<| analysis/type.with_var + (function (_ [@var :var:])) + (do phase.monad + [arrayA (analysis/type.expecting (type (Array :var:)) + (phase archive arrayC)) + _ (analysis/type.inference Nat)] + (in {analysis.#Extension extension (list arrayA)}))))])) (def: array::read Handler (custom [(<>.and <code>.any <code>.any) (function (_ extension phase archive [indexC arrayC]) - (do phase.monad - [indexA (analysis/type.expecting Nat - (phase archive indexC)) - [var_id varT] (analysis/type.check check.var) - arrayA (analysis/type.expecting (type (Array varT)) - (phase archive arrayC)) - _ (analysis/type.inference varT)] - (in {analysis.#Extension extension (list indexA arrayA)})))])) + (<| analysis/type.with_var + (function (_ [@var :var:])) + (do phase.monad + [indexA (analysis/type.expecting Nat + (phase archive indexC)) + arrayA (analysis/type.expecting (type (Array :var:)) + (phase archive arrayC)) + _ (analysis/type.inference :var:)] + (in {analysis.#Extension extension (list indexA arrayA)}))))])) (def: array::write Handler (custom [($_ <>.and <code>.any <code>.any <code>.any) (function (_ extension phase archive [indexC valueC arrayC]) - (do phase.monad - [indexA (analysis/type.expecting Nat - (phase archive indexC)) - [var_id varT] (analysis/type.check check.var) - valueA (analysis/type.expecting varT - (phase archive valueC)) - arrayA (analysis/type.expecting (type (Array varT)) - (phase archive arrayC)) - _ (analysis/type.inference (type (Array varT)))] - (in {analysis.#Extension extension (list indexA valueA arrayA)})))])) + (<| analysis/type.with_var + (function (_ [@var :var:])) + (do phase.monad + [indexA (analysis/type.expecting Nat + (phase archive indexC)) + valueA (analysis/type.expecting :var: + (phase archive valueC)) + arrayA (analysis/type.expecting (type (Array :var:)) + (phase archive arrayC)) + _ (analysis/type.inference (type (Array :var:)))] + (in {analysis.#Extension extension (list indexA valueA arrayA)}))))])) (def: array::delete Handler (custom [($_ <>.and <code>.any <code>.any) (function (_ extension phase archive [indexC arrayC]) - (do phase.monad - [indexA (analysis/type.expecting Nat - (phase archive indexC)) - [var_id varT] (analysis/type.check check.var) - arrayA (analysis/type.expecting (type (Array varT)) - (phase archive arrayC)) - _ (analysis/type.inference (type (Array varT)))] - (in {analysis.#Extension extension (list indexA arrayA)})))])) + (<| analysis/type.with_var + (function (_ [@var :var:])) + (do phase.monad + [indexA (analysis/type.expecting Nat + (phase archive indexC)) + arrayA (analysis/type.expecting (type (Array :var:)) + (phase archive arrayC)) + _ (analysis/type.inference (type (Array :var:)))] + (in {analysis.#Extension extension (list indexA arrayA)}))))])) (def: bundle::array Bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/ruby.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/ruby.lux index 4f6a34452..eae384992 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/ruby.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/ruby.lux @@ -31,68 +31,73 @@ (custom [<c>.any (function (_ extension phase archive lengthC) - (do phase.monad - [lengthA (<| (analysis/type.expecting Nat) - (phase archive lengthC)) - [var_id varT] (analysis/type.check check.var) - _ (analysis/type.inference (type (Array varT)))] - (in {analysis.#Extension extension (list lengthA)})))])) + (<| analysis/type.with_var + (function (_ [@var :var:])) + (do phase.monad + [lengthA (<| (analysis/type.expecting Nat) + (phase archive lengthC)) + _ (analysis/type.inference (type (Array :var:)))] + (in {analysis.#Extension extension (list lengthA)}))))])) (def: array::length Handler (custom [<c>.any (function (_ extension phase archive arrayC) - (do phase.monad - [[var_id varT] (analysis/type.check check.var) - arrayA (<| (analysis/type.expecting (type (Array varT))) - (phase archive arrayC)) - _ (analysis/type.inference Nat)] - (in {analysis.#Extension extension (list arrayA)})))])) + (<| analysis/type.with_var + (function (_ [@var :var:])) + (do phase.monad + [arrayA (<| (analysis/type.expecting (type (Array :var:))) + (phase archive arrayC)) + _ (analysis/type.inference Nat)] + (in {analysis.#Extension extension (list arrayA)}))))])) (def: array::read Handler (custom [(<>.and <c>.any <c>.any) (function (_ extension phase archive [indexC arrayC]) - (do phase.monad - [indexA (<| (analysis/type.expecting Nat) - (phase archive indexC)) - [var_id varT] (analysis/type.check check.var) - arrayA (<| (analysis/type.expecting (type (Array varT))) - (phase archive arrayC)) - _ (analysis/type.inference varT)] - (in {analysis.#Extension extension (list indexA arrayA)})))])) + (<| analysis/type.with_var + (function (_ [@var :var:])) + (do phase.monad + [indexA (<| (analysis/type.expecting Nat) + (phase archive indexC)) + arrayA (<| (analysis/type.expecting (type (Array :var:))) + (phase archive arrayC)) + _ (analysis/type.inference :var:)] + (in {analysis.#Extension extension (list indexA arrayA)}))))])) (def: array::write Handler (custom [($_ <>.and <c>.any <c>.any <c>.any) (function (_ extension phase archive [indexC valueC arrayC]) - (do phase.monad - [indexA (<| (analysis/type.expecting Nat) - (phase archive indexC)) - [var_id varT] (analysis/type.check check.var) - valueA (<| (analysis/type.expecting varT) - (phase archive valueC)) - arrayA (<| (analysis/type.expecting (type (Array varT))) - (phase archive arrayC)) - _ (analysis/type.inference (type (Array varT)))] - (in {analysis.#Extension extension (list indexA valueA arrayA)})))])) + (<| analysis/type.with_var + (function (_ [@var :var:])) + (do phase.monad + [indexA (<| (analysis/type.expecting Nat) + (phase archive indexC)) + valueA (<| (analysis/type.expecting :var:) + (phase archive valueC)) + arrayA (<| (analysis/type.expecting (type (Array :var:))) + (phase archive arrayC)) + _ (analysis/type.inference (type (Array :var:)))] + (in {analysis.#Extension extension (list indexA valueA arrayA)}))))])) (def: array::delete Handler (custom [($_ <>.and <c>.any <c>.any) (function (_ extension phase archive [indexC arrayC]) - (do phase.monad - [indexA (<| (analysis/type.expecting Nat) - (phase archive indexC)) - [var_id varT] (analysis/type.check check.var) - arrayA (<| (analysis/type.expecting (type (Array varT))) - (phase archive arrayC)) - _ (analysis/type.inference (type (Array varT)))] - (in {analysis.#Extension extension (list indexA arrayA)})))])) + (<| analysis/type.with_var + (function (_ [@var :var:])) + (do phase.monad + [indexA (<| (analysis/type.expecting Nat) + (phase archive indexC)) + arrayA (<| (analysis/type.expecting (type (Array :var:))) + (phase archive arrayC)) + _ (analysis/type.inference (type (Array :var:)))] + (in {analysis.#Extension extension (list indexA arrayA)}))))])) (def: bundle::array Bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux index 944cac7a8..cbcfac6ec 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux @@ -947,7 +947,7 @@ (^template [<tag>] [(^ <tag>) body]) - ([{//////synthesis.#Primitive _}] + ([{//////synthesis.#Simple _}] [(//////synthesis.constant _)]) (^ (//////synthesis.variant [lefts right? sub])) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux index e2ed832c1..ef4118721 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux @@ -30,7 +30,8 @@ [archive ["[0]" unit]] ["[0]" cache "_" - ["[1]" artifact]]] + [dependency + ["[1]" artifact]]]] [reference [variable {"+" Register Variable}]]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux index 59d88e612..9409ab00f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux @@ -28,7 +28,8 @@ [meta [archive {"+" Archive}] ["[0]" cache "_" - ["[1]" artifact]]] + [dependency + ["[1]" artifact]]]] [reference [variable {"+" Register}]]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux index 1e427dbfc..6d4193788 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux @@ -29,7 +29,8 @@ [variable {"+" Register Variable}]] [meta ["[0]" cache "_" - ["[1]/[0]" artifact]]]]]]]) + [dependency + ["[1]/[0]" artifact]]]]]]]]) (def: .public (apply expression archive [functionS argsS+]) (Generator (Reification Synthesis)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux index 5249d2c55..f6a61ca8c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux @@ -28,7 +28,6 @@ ["[0]" /// "_" ["[1][0]" reference] ["//[1]" /// "_" - ["$" version] ["[1][0]" synthesis {"+" Synthesis}] ["[1][0]" generation] ["//[1]" /// diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux index 428e3438c..d711e963a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux @@ -17,7 +17,8 @@ ["/[1]" // "_" ["[1][0]" extension] ["/[1]" // "_" - ["/" synthesis {"+" Synthesis Phase}] + ["/" synthesis {"+" Synthesis Phase} + ["[1][0]" simple]] ["[1][0]" analysis {"+" Analysis} ["[2][0]" simple] ["[2][0]" complex]] @@ -26,32 +27,32 @@ [reference {"+"} [variable {"+"}]]]]]]) -(def: (primitive analysis) - (-> ///simple.Simple /.Primitive) +(def: (simple analysis) + (-> ///simple.Simple /simple.Simple) (case analysis {///simple.#Unit} - {/.#Text /.unit} + {/simple.#Text /.unit} (^template [<analysis> <synthesis>] [{<analysis> value} {<synthesis> value}]) - ([///simple.#Bit /.#Bit] - [///simple.#Frac /.#F64] - [///simple.#Text /.#Text]) + ([///simple.#Bit /simple.#Bit] + [///simple.#Frac /simple.#F64] + [///simple.#Text /simple.#Text]) (^template [<analysis> <synthesis>] [{<analysis> value} {<synthesis> (.i64 value)}]) - ([///simple.#Nat /.#I64] - [///simple.#Int /.#I64] - [///simple.#Rev /.#I64]))) + ([///simple.#Nat /simple.#I64] + [///simple.#Int /simple.#I64] + [///simple.#Rev /simple.#I64]))) (def: (optimization archive) Phase (function (optimization' analysis) (case analysis {///analysis.#Simple analysis'} - (phase#in {/.#Primitive (..primitive analysis')}) + (phase#in {/.#Simple (..simple analysis')}) {///analysis.#Reference reference} (phase#in {/.#Reference reference}) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux index 4d6ec6354..8e37a6714 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux @@ -248,7 +248,7 @@ (monad.each phase.monad (grow environment)) (phase#each (|>> {/.#Extension name}))) - {/.#Primitive _} + {/.#Simple _} (phase#in expression))) (def: .public (abstraction phase environment archive bodyA) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux index 080bc436c..75ddb63b0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux @@ -1,24 +1,24 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" maybe ("[1]#[0]" monad)]] - [data - [collection - ["[0]" list]]] - [math - [number - ["n" nat]]]]] - [//// - ["[0]" analysis {"+" Environment} - ["[1]/[0]" complex]] - ["/" synthesis {"+" Path Abstraction Synthesis}] - [/// - [arity {"+" Arity}] - ["[0]" reference - ["[0]" variable {"+" Register Variable}]]]]) + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" maybe ("[1]#[0]" monad)]] + [data + [collection + ["[0]" list]]] + [math + [number + ["n" nat]]]]] + [//// + ["[0]" analysis {"+" Environment} + ["[1]/[0]" complex]] + ["/" synthesis {"+" Path Abstraction Synthesis}] + [/// + [arity {"+" Arity}] + ["[0]" reference + ["[0]" variable {"+" Register Variable}]]]]) (type: .public (Transform a) (-> a (Maybe a))) @@ -80,7 +80,7 @@ (loop [return? true expr expr] (case expr - {/.#Primitive _} + {/.#Simple _} {.#Some expr} {/.#Structure structure} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux index 2d9e8ce5c..beccd504c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux @@ -1,31 +1,31 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" maybe ("[1]#[0]" functor)] - ["[0]" try {"+" Try}] - ["[0]" exception {"+" exception:}]] - [data - ["[0]" product] - ["[0]" text - ["%" format]] - [collection - ["[0]" dictionary {"+" Dictionary}] - ["[0]" list ("[1]#[0]" functor mix)] - ["[0]" set]]] - [math - [number - ["n" nat]]]]] - [//// - ["/" synthesis {"+" Path Synthesis}] - ["[0]" analysis - ["[1]/[0]" complex]] - [/// - [arity {"+" Arity}] - ["[0]" reference - ["[0]" variable {"+" Register Variable}]]]]) + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" maybe ("[1]#[0]" functor)] + ["[0]" try {"+" Try}] + ["[0]" exception {"+" exception:}]] + [data + ["[0]" product] + ["[0]" text + ["%" format]] + [collection + ["[0]" dictionary {"+" Dictionary}] + ["[0]" list ("[1]#[0]" functor mix)] + ["[0]" set]]] + [math + [number + ["n" nat]]]]] + [//// + ["/" synthesis {"+" Path Synthesis}] + ["[0]" analysis + ["[1]/[0]" complex]] + [/// + [arity {"+" Arity}] + ["[0]" reference + ["[0]" variable {"+" Register Variable}]]]]) (def: (prune redundant register) (-> Register Register Register) @@ -108,7 +108,7 @@ (Remover Synthesis) (function (again synthesis) (case synthesis - {/.#Primitive _} + {/.#Simple _} synthesis {/.#Structure structure} @@ -331,7 +331,7 @@ (with_expansions [<no_op> (as_is {try.#Success [redundancy synthesis]})] (case synthesis - {/.#Primitive _} + {/.#Simple _} <no_op> {/.#Structure structure} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux index 4f87318aa..99d99dbc6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux @@ -1,6 +1,6 @@ (.using [library - [lux {"-" Primitive Scope i64} + [lux {"-" Scope i64} [abstract [monad {"+" do}] [equivalence {"+" Equivalence}] @@ -24,16 +24,18 @@ ["n" nat] ["i" int] ["f" frac]]]]] - [// - ["[0]" analysis {"+" Environment Analysis} - ["[1]/[0]" complex {"+" Complex}]] - [phase - ["[0]" extension {"+" Extension}]] - [/// - [arity {"+" Arity}] - ["[0]" phase] - ["[0]" reference {"+" Reference} - ["[0]" variable {"+" Register Variable}]]]]) + ["[0]" / "_" + ["[1][0]" simple {"+" Simple}] + [// + ["[0]" analysis {"+" Environment Analysis} + ["[1]/[0]" complex {"+" Complex}]] + [phase + ["[0]" extension {"+" Extension}]] + [/// + [arity {"+" Arity}] + ["[0]" phase] + ["[0]" reference {"+" Reference} + ["[0]" variable {"+" Register Variable}]]]]]) (type: .public Resolver (Dictionary Variable Variable)) @@ -53,13 +55,6 @@ [#locals 0 #currying? false]) -(type: .public Primitive - (Variant - {#Bit Bit} - {#I64 (I64 Any)} - {#F64 Frac} - {#Text Text})) - (type: .public Side (Either Nat Nat)) @@ -131,7 +126,7 @@ (type: .public Synthesis (Rec Synthesis (Variant - {#Primitive Primitive} + {#Simple Simple} {#Structure (Complex Synthesis)} {#Reference Reference} {#Control (Control Synthesis)} @@ -225,12 +220,12 @@ (template [<name> <tag>] [(template: .public (<name> content) - [{..#Primitive {<tag> content}}])] + [{..#Simple {<tag> content}}])] - [bit ..#Bit] - [i64 ..#I64] - [f64 ..#F64] - [text ..#Text] + [bit /simple.#Bit] + [i64 /simple.#I64] + [f64 /simple.#F64] + [text /simple.#Text] ) (template [<name> <tag>] @@ -337,17 +332,8 @@ (def: .public (%synthesis value) (Format Synthesis) (case value - {#Primitive primitive} - (case primitive - (^template [<pattern> <format>] - [{<pattern> value} - (<format> value)]) - ([#Bit %.bit] - [#F64 %.frac] - [#Text %.text]) - - {#I64 value} - (%.int (.int value))) + {#Simple it} + (/simple.format it) {#Structure structure} (case structure @@ -435,38 +421,6 @@ (Format Path) (%path' %synthesis)) -(implementation: .public primitive_equivalence - (Equivalence Primitive) - - (def: (= reference sample) - (case [reference sample] - (^template [<tag> <eq> <format>] - [[{<tag> reference'} {<tag> sample'}] - (<eq> reference' sample')]) - ([#Bit bit#= %.bit] - [#F64 f.= %.frac] - [#Text text#= %.text]) - - [{#I64 reference'} {#I64 sample'}] - (i.= (.int reference') (.int sample')) - - _ - false))) - -(implementation: primitive_hash - (Hash Primitive) - - (def: &equivalence ..primitive_equivalence) - - (def: hash - (|>> (case> (^template [<tag> <hash>] - [{<tag> value'} - (# <hash> hash value')]) - ([#Bit bit.hash] - [#F64 f.hash] - [#Text text.hash] - [#I64 i64.hash]))))) - (def: side_equivalence (Equivalence Side) (sum.equivalence n.equivalence n.equivalence)) @@ -775,7 +729,7 @@ (^template [<tag> <equivalence>] [[{<tag> reference'} {<tag> sample'}] (# <equivalence> = reference' sample')]) - ([#Primitive ..primitive_equivalence] + ([#Simple /simple.equivalence] [#Structure (analysis/complex.equivalence =)] [#Reference reference.equivalence] [#Control (control_equivalence =)] @@ -799,7 +753,7 @@ (^template [<tag> <hash>] [{<tag> value} (# <hash> hash value)]) - ([#Primitive ..primitive_hash] + ([#Simple /simple.hash] [#Structure (analysis/complex.hash again_hash)] [#Reference reference.hash] [#Control (..control_hash again_hash)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/simple.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/simple.lux new file mode 100644 index 000000000..0b1825953 --- /dev/null +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/simple.lux @@ -0,0 +1,70 @@ +(.using + [library + [lux "*" + [abstract + [equivalence {"+" Equivalence}] + [hash {"+" Hash}]] + [control + [pipe {"+" case>}]] + [data + ["[0]" bit ("[1]#[0]" equivalence)] + ["[0]" text ("[1]#[0]" equivalence) + ["%" format]]] + [math + [number + ["[0]" i64] + ["n" nat] + ["i" int] + ["f" frac]]]]]) + +(type: .public Simple + (Variant + {#Bit Bit} + {#I64 (I64 Any)} + {#F64 Frac} + {#Text Text})) + +(def: .public (format it) + (%.Format Simple) + (case it + (^template [<pattern> <format>] + [{<pattern> value} + (<format> value)]) + ([#Bit %.bit] + [#F64 %.frac] + [#Text %.text]) + + {#I64 value} + (%.int (.int value)))) + +(implementation: .public equivalence + (Equivalence Simple) + + (def: (= reference sample) + (case [reference sample] + (^template [<tag> <eq> <format>] + [[{<tag> reference'} {<tag> sample'}] + (<eq> reference' sample')]) + ([#Bit bit#= %.bit] + [#F64 f.= %.frac] + [#Text text#= %.text]) + + [{#I64 reference'} {#I64 sample'}] + (i.= (.int reference') (.int sample')) + + _ + false))) + +(implementation: .public hash + (Hash Simple) + + (def: &equivalence ..equivalence) + + (def: hash + (|>> (case> (^template [<factor> <tag> <hash>] + [{<tag> value'} + (n.* <factor> (# <hash> hash value'))]) + ([1 #Bit bit.hash] + [2 #F64 f.hash] + [3 #Text text.hash] + [5 #I64 i64.hash]))))) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux index fb7cc745b..ed2e00876 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux @@ -6,6 +6,8 @@ [hash {"+" Hash}]] [data ["[0]" product] + [text + ["%" format]] [collection ["[0]" set {"+" Set}]]] [math @@ -33,3 +35,9 @@ (def: .public none (Set ID) (set.empty ..hash)) + +(def: .public (format it) + (%.Format ID) + (%.format (%.nat (value@ #module it)) + "." + (%.nat (value@ #artifact it)))) diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux index 327cae965..9bce830d6 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux @@ -76,7 +76,7 @@ (def: (references value) (-> Synthesis (List Constant)) (case value - {synthesis.#Primitive value} + {synthesis.#Simple value} (list) {synthesis.#Structure value} |