diff options
author | Eduardo Julian | 2021-07-25 03:12:17 -0400 |
---|---|---|
committer | Eduardo Julian | 2021-07-25 03:12:17 -0400 |
commit | 62b3abfcc014ca1c19d62aacdd497f6a250b372c (patch) | |
tree | c23155ecef6018b78b349f0ba6cd238872b24da7 /stdlib/source/library/lux/tool/compiler | |
parent | 0f545b7e57d2564e351d907befd2ce26900c5521 (diff) |
Better syntax for "library/lux.^multi".
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
34 files changed, 253 insertions, 254 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux index 3d49eb706..7fcbb94eb 100644 --- a/stdlib/source/library/lux/tool/compiler/default/init.lux +++ b/stdlib/source/library/lux/tool/compiler/default/init.lux @@ -225,7 +225,7 @@ (def: module_aliases (-> .Module Aliases) - (|>> (get@ #.module_aliases) (dictionary.from_list text.hash))) + (|>> (get@ #.module_aliases) (dictionary.of_list text.hash))) (def: #export (compiler expander prelude write_directive) (All [anchor expression directive] @@ -252,7 +252,7 @@ #let [descriptor {#descriptor.hash hash #descriptor.name module #descriptor.file (get@ #///.file input) - #descriptor.references (set.from_list text.hash dependencies) + #descriptor.references (set.of_list text.hash dependencies) #descriptor.state #.Compiled #descriptor.registry final_registry}]] (wrap [state diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux index 3d3f4cde0..2e5fb6fed 100644 --- a/stdlib/source/library/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux @@ -1,7 +1,7 @@ (.module: [library [lux (#- Module) - [type (#+ :share)] + [type (#+ :sharing)] ["." debug] ["@" target] [abstract @@ -176,22 +176,22 @@ .Lux <State+> (Try <State+>))) - (|> (:share [<type_vars>] - <State+> - state - - (///directive.Operation <type_vars> Any) - (do ///phase.monad - [_ (///directive.lift_analysis - (///analysis.install analysis_state)) - _ (///directive.lift_analysis - (extension.with extender analysers)) - _ (///directive.lift_synthesis - (extension.with extender synthesizers)) - _ (///directive.lift_generation - (extension.with extender (:assume generators))) - _ (extension.with extender (:assume directives))] - (wrap []))) + (|> (:sharing [<type_vars>] + <State+> + state + + (///directive.Operation <type_vars> Any) + (do ///phase.monad + [_ (///directive.lift_analysis + (///analysis.install analysis_state)) + _ (///directive.lift_analysis + (extension.with extender analysers)) + _ (///directive.lift_synthesis + (extension.with extender synthesizers)) + _ (///directive.lift_generation + (extension.with extender (:assume generators))) + _ (extension.with extender (:assume directives))] + (wrap []))) (///phase.run' state) (\ try.monad map product.left))) @@ -389,74 +389,74 @@ (-> <Context> (-> <Compiler> <Importer>))) (let [current (stm.var initial) - pending (:share [<type_vars>] - <Context> - initial - - (Var (Dictionary Module <Pending>)) - (:assume (stm.var (dictionary.new text.hash)))) + pending (:sharing [<type_vars>] + <Context> + initial + + (Var (Dictionary Module <Pending>)) + (:assume (stm.var (dictionary.new text.hash)))) dependence (: (Var Dependence) (stm.var ..independence))] (function (_ compile) (function (import! importer module) (do {! promise.monad} - [[return signal] (:share [<type_vars>] - <Context> - initial - - (Promise [<Return> (Maybe [<Context> - archive.ID - <Signal>])]) - (:assume - (stm.commit - (do {! stm.monad} - [dependence (if (text\= archive.runtime_module importer) - (stm.read dependence) - (do ! - [[_ dependence] (stm.update (..depend importer module) dependence)] - (wrap dependence)))] - (case (..verify_dependencies importer module dependence) - (#try.Failure error) - (wrap [(promise.resolved (#try.Failure error)) - #.None]) - - (#try.Success _) - (do ! - [[archive state] (stm.read current)] - (if (archive.archived? archive module) - (wrap [(promise\wrap (#try.Success [archive state])) - #.None]) - (do ! - [@pending (stm.read pending)] - (case (dictionary.get module @pending) - (#.Some [return signal]) - (wrap [return - #.None]) - - #.None - (case (if (archive.reserved? archive module) - (do try.monad - [module_id (archive.id module archive)] - (wrap [module_id archive])) - (archive.reserve module archive)) - (#try.Success [module_id archive]) - (do ! - [_ (stm.write [archive state] current) - #let [[return signal] (:share [<type_vars>] - <Context> - initial - - <Pending> - (promise.promise []))] - _ (stm.update (dictionary.put module [return signal]) pending)] - (wrap [return - (#.Some [[archive state] - module_id - signal])])) + [[return signal] (:sharing [<type_vars>] + <Context> + initial + + (Promise [<Return> (Maybe [<Context> + archive.ID + <Signal>])]) + (:assume + (stm.commit + (do {! stm.monad} + [dependence (if (text\= archive.runtime_module importer) + (stm.read dependence) + (do ! + [[_ dependence] (stm.update (..depend importer module) dependence)] + (wrap dependence)))] + (case (..verify_dependencies importer module dependence) + (#try.Failure error) + (wrap [(promise.resolved (#try.Failure error)) + #.None]) + + (#try.Success _) + (do ! + [[archive state] (stm.read current)] + (if (archive.archived? archive module) + (wrap [(promise\wrap (#try.Success [archive state])) + #.None]) + (do ! + [@pending (stm.read pending)] + (case (dictionary.get module @pending) + (#.Some [return signal]) + (wrap [return + #.None]) - (#try.Failure error) - (wrap [(promise\wrap (#try.Failure error)) - #.None]))))))))))) + #.None + (case (if (archive.reserved? archive module) + (do try.monad + [module_id (archive.id module archive)] + (wrap [module_id archive])) + (archive.reserve module archive)) + (#try.Success [module_id archive]) + (do ! + [_ (stm.write [archive state] current) + #let [[return signal] (:sharing [<type_vars>] + <Context> + initial + + <Pending> + (promise.promise []))] + _ (stm.update (dictionary.put module [return signal]) pending)] + (wrap [return + (#.Some [[archive state] + module_id + signal])])) + + (#try.Failure error) + (wrap [(promise\wrap (#try.Failure error)) + #.None]))))))))))) _ (case signal #.None (wrap []) @@ -492,7 +492,7 @@ (archive.archived archive)) #let [additions (|> modules (list\map product.left) - (set.from_list text.hash))]] + (set.of_list text.hash))]] (wrap (update@ [#extension.state #///directive.analysis #///directive.state @@ -501,10 +501,10 @@ (|> analysis_state (:as .Lux) (update@ #.modules (function (_ current) - (list\compose (list.filter (|>> product.left - (set.member? additions) - not) - current) + (list\compose (list.only (|>> product.left + (set.member? additions) + not) + current) modules))) :assume)) state)))) @@ -514,20 +514,20 @@ (-> Module <State+> <State+>)) (|> (///directive.set_current_module module) (///phase.run' state) - try.assume + try.assumed product.left)) (def: #export (compile import static expander platform compilation context) (All [<type_vars>] (-> Import Static Expander <Platform> Compilation <Context> <Return>)) (let [[compilation_sources compilation_host_dependencies compilation_libraries compilation_target compilation_module] compilation - base_compiler (:share [<type_vars>] - <Context> - context - - (///.Compiler <State+> .Module Any) - (:assume - ((//init.compiler expander syntax.prelude (get@ #write platform)) $.key (list)))) + base_compiler (:sharing [<type_vars>] + <Context> + context + + (///.Compiler <State+> .Module Any) + (:assume + ((//init.compiler expander syntax.prelude (get@ #write platform)) $.key (list)))) compiler (..parallel context (function (_ importer import! module_id [archive state] module) @@ -545,14 +545,14 @@ (list))] (let [new_dependencies (get@ #///.dependencies compilation) all_dependencies (list\compose new_dependencies all_dependencies) - continue! (:share [<type_vars>] - <Platform> - platform - - (-> <Context> (///.Compilation <State+> .Module Any) (List Module) - (Action [Archive <State+>])) - (:assume - recur))] + continue! (:sharing [<type_vars>] + <Platform> + platform + + (-> <Context> (///.Compilation <State+> .Module Any) (List Module) + (Action [Archive <State+>])) + (:assume + recur))] (do ! [[archive state] (case new_dependencies #.Nil @@ -566,14 +566,14 @@ #let [archive (|> archive,document+ (list\map product.left) (list\fold archive.merge archive))]] - (wrap [archive (try.assume + (wrap [archive (try.assumed (..updated_state archive state))])))] (case ((get@ #///.process compilation) ## TODO: The "///directive.set_current_module" below shouldn't be necessary. Remove it ASAP. ## TODO: The context shouldn't need to be re-set either. (|> (///directive.set_current_module module) (///phase.run' state) - try.assume + try.assumed product.left) archive) (#try.Success [state more|done]) @@ -584,7 +584,7 @@ (#.Right [descriptor document output]) (do ! [#let [_ (debug.log! (..module_compilation_log module state)) - descriptor (set@ #descriptor.references (set.from_list text.hash all_dependencies) descriptor)] + descriptor (set@ #descriptor.references (set.of_list text.hash all_dependencies) descriptor)] _ (..cache_module static platform module_id [descriptor document output])] (case (archive.add module [descriptor document output] archive) (#try.Success archive) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux index d447b8d1d..327488817 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux @@ -129,7 +129,7 @@ (#.Product _) (|> caseT - type.flatten_tuple + type.flat_tuple (list\map (re_quantify envs)) type.tuple (\ ///.monad wrap)) @@ -193,7 +193,7 @@ [inputT' (simplify_case inputT)] (.case inputT' (#.Product _) - (let [subs (type.flatten_tuple inputT') + (let [subs (type.flat_tuple inputT') num_subs (maybe.default (list.size subs) num_tags) num_sub_patterns (list.size sub_patterns) @@ -251,7 +251,7 @@ [inputT' (simplify_case inputT)] (.case inputT' (#.Sum _) - (let [flat_sum (type.flatten_variant inputT') + (let [flat_sum (type.flat_variant inputT') size_sum (list.size flat_sum) num_cases (maybe.default size_sum num_tags) idx (/.tag lefts right?)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux index df92858ec..bc4fad3d3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux @@ -169,11 +169,11 @@ (ex.report ["Coverage so-far" (%coverage so_far)] ["Coverage addition" (%coverage addition)])) -(def: (flatten_alt coverage) +(def: (flat_alt coverage) (-> Coverage (List Coverage)) (case coverage (#Alt left right) - (list& left (flatten_alt right)) + (list& left (flat_alt right)) _ (list coverage))) @@ -197,8 +197,8 @@ (= rightR rightS)) [(#Alt _) (#Alt _)] - (let [flatR (flatten_alt reference) - flatS (flatten_alt sample)] + (let [flatR (flat_alt reference) + flatS (flat_alt sample)] (and (n.= (list.size flatR) (list.size flatS)) (list.every? (function (_ [coverageR coverageS]) (= coverageR coverageS)) @@ -346,7 +346,7 @@ (#try.Failure error) (try.fail error)) ))))] - [successA possibilitiesSF] (fuse_once addition (flatten_alt so_far))] + [successA possibilitiesSF] (fuse_once addition (flat_alt so_far))] (loop [successA successA possibilitiesSF possibilitiesSF] (case successA diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux index 9ad503709..ace669fbe 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux @@ -228,7 +228,7 @@ (#.Product _) (///\wrap (|> inferT - (type.function (type.flatten_tuple inferT)) + (type.function (type.flat_tuple inferT)) (substitute_bound target originalT))) _ @@ -258,7 +258,7 @@ [#.ExQ]) (#.Sum _) - (let [cases (type.flatten_variant currentT) + (let [cases (type.flat_variant currentT) actual_size (list.size cases) boundary (dec expected_size)] (cond (or (n.= expected_size actual_size) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux index 0f8106a7d..c49e936ec 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux @@ -101,7 +101,7 @@ (/.with_stack ..cannot_analyse_variant [expectedT' tag valueC] (case expectedT (#.Sum _) - (let [flat (type.flatten_variant expectedT)] + (let [flat (type.flat_variant expectedT)] (case (list.nth tag flat) (#.Some variant_type) (do ! @@ -170,7 +170,7 @@ (do {! ///.monad} [expectedT (///extension.lift meta.expected_type) membersA+ (: (Operation (List Analysis)) - (loop [membersT+ (type.flatten_tuple expectedT) + (loop [membersT+ (type.flat_tuple expectedT) membersC+ members] (case [membersT+ membersC+] [(#.Cons memberT #.Nil) _] @@ -315,7 +315,7 @@ (wrap []) (/.throw ..record_size_mismatch [size_ts size_record recordT record])) #let [tuple_range (list.indices size_ts) - tag->idx (dictionary.from_list name.hash (list.zip/2 tag_set tuple_range))] + tag->idx (dictionary.of_list name.hash (list.zip/2 tag_set tuple_range))] idx->val (monad.fold ! (function (_ [key val] idx->val) (do ! diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux index e5af044c3..f47ca7aea 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux @@ -343,7 +343,7 @@ [(reflection.reflection reflection.float) [box.float jvm.float]] [(reflection.reflection reflection.double) [box.double jvm.double]] [(reflection.reflection reflection.char) [box.char jvm.char]]) - (dictionary.from_list text.hash))) + (dictionary.of_list text.hash))) (def: (jvm_type luxT) (-> .Type (Operation (Type Value))) @@ -950,7 +950,7 @@ (inheritance_candidate_parents class_loader currentT to_class toT fromC) (class_candidate_parents class_loader current_name currentT to_name to_class)))] (case (|> candidate_parents - (list.filter product.right) + (list.only product.right) (list\map product.left)) (#.Cons [next_name nextT] _) (recur [next_name nextT]) @@ -1170,7 +1170,7 @@ list.reverse) num_owner_tvars (list.size owner_tvars) owner_tvarsT (|> lux_tvars (list.take num_owner_tvars) (list\map product.right)) - mapping (dictionary.from_list text.hash lux_tvars)] + mapping (dictionary.of_list text.hash lux_tvars)] [owner_tvarsT mapping])) (def: (method_signature method_style method) @@ -1280,7 +1280,7 @@ (-> (List (Type Var)) (List (Type Var)) Aliasing) (|> (list.zip/2 (list\map jvm_parser.name actual) (list\map jvm_parser.name expected)) - (dictionary.from_list text.hash))) + (dictionary.of_list text.hash))) (def: (method_candidate class_loader actual_class_tvars class_name actual_method_tvars method_name method_style inputsJT) (-> java/lang/ClassLoader (List (Type Var)) External (List (Type Var)) Text Method_Style (List (Type Value)) (Operation Method_Signature)) @@ -1290,7 +1290,7 @@ candidates (|> class java/lang/Class::getDeclaredMethods array.to_list - (list.filter (|>> java/lang/reflect/Method::getName (text\= method_name))) + (list.only (|>> java/lang/reflect/Method::getName (text\= method_name))) (monad.map ! (: (-> java/lang/reflect/Method (Operation Evaluation)) (function (_ method) (do ! @@ -1542,13 +1542,13 @@ (list (/////analysis.text argument) (value_analysis argumentJT)))) -(template [<name> <filter>] +(template [<name> <only>] [(def: <name> (-> (java/lang/Class java/lang/Object) (Try (List [Text (Type Method)]))) (|>> java/lang/Class::getDeclaredMethods array.to_list - <filter> + <only> (monad.map try.monad (function (_ method) (do {! try.monad} @@ -1568,7 +1568,7 @@ (wrap [(java/lang/reflect/Method::getName method) (jvm.method [type_variables inputs return exceptions])]))))))] - [abstract_methods (list.filter (|>> java/lang/reflect/Method::getModifiers java/lang/reflect/Modifier::isAbstract))] + [abstract_methods (list.only (|>> java/lang/reflect/Method::getModifiers java/lang/reflect/Modifier::isAbstract))] [methods (<|)] ) @@ -1913,7 +1913,7 @@ (do {! phase.monad} [parent_parameters (|> parent_parameters (monad.map maybe.monad jvm_parser.var?) - try.from_maybe + try.of_maybe phase.lift)] (|> super_parameters (monad.map ! (..reflection_type mapping)) @@ -2038,15 +2038,15 @@ (-> (List [Text (Type Method)]) (List [Text (Type Method)]) (List [Text (Type Method)])) - (list.filter (function (_ [sub_name subJT]) - (|> super_set - (list.filter (function (_ [super_name superJT]) - (and (text\= super_name sub_name) - (jvm\= superJT subJT)))) - list.size - (n.= 1) - not)) - sub_set)) + (list.only (function (_ [sub_name subJT]) + (|> super_set + (list.only (function (_ [super_name superJT]) + (and (text\= super_name sub_name) + (jvm\= superJT subJT)))) + list.size + (n.= 1) + not)) + sub_set)) (exception: #export (class_parameter_mismatch {expected (List Text)} {actual (List (Type Parameter))}) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux index 3fb0c967e..95b04daa2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux @@ -26,4 +26,4 @@ (-> Text (-> (Bundle s i o) (Bundle s i o)))) (|>> dictionary.entries (list\map (function (_ [key val]) [(format prefix " " key) val])) - (dictionary.from_list text.hash))) + (dictionary.of_list text.hash))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux index 8678c6269..d11c6cb49 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux @@ -191,7 +191,7 @@ (^template [<tag> <type> <constant>] [[_ (<tag> value)] (do pool.monad - [constant (`` (|> value (~~ (template.splice <constant>)))) + [constant (`` (|> value (~~ (template.spliced <constant>)))) attribute (attribute.constant constant)] (field.field ..constant::modifier name <type> (row.row attribute)))]) ([#.Bit type.boolean [(case> #0 +0 #1 +1) .i64 i32.i32 constant.integer pool.integer]] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux index 8fd5d2416..b67f9287b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux @@ -22,7 +22,7 @@ [math [number ["n" nat]]] - ["." type (#+ :share) + ["." type (#+ :sharing) ["." check]]]] ["." /// (#+ Extender) ["#." bundle] @@ -328,12 +328,12 @@ valueC) _ (<| <scope> (///.install extender (:as Text name)) - (:share [anchor expression directive] - (Handler anchor expression directive) - handler - - <type> - (:assume handlerV))) + (:sharing [anchor expression directive] + (Handler anchor expression directive) + handler + + <type> + (:assume handlerV))) _ (/////directive.lift_generation (/////generation.log! (format <description> " " (%.text (:as Text name)))))] (wrap /////directive.no_requirements)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux index a74c72d38..9cc6c1dbc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux @@ -156,7 +156,7 @@ (/.install "%" (binary (product.uncurry _.%))) (/.install "=" (binary (product.uncurry _.=))) (/.install "<" (binary (product.uncurry _.<))) - (/.install "i64" (unary //runtime.i64//from_number)) + (/.install "i64" (unary //runtime.i64//of_number)) (/.install "encode" (unary (_.do "toString" (list)))) (/.install "decode" (unary f64//decode))))) @@ -168,7 +168,7 @@ (/.install "<" (binary (product.uncurry _.<))) (/.install "concat" (binary text//concat)) (/.install "index" (trinary text//index)) - (/.install "size" (unary (|>> (_.the "length") //runtime.i64//from_number))) + (/.install "size" (unary (|>> (_.the "length") //runtime.i64//of_number))) (/.install "char" (binary (product.uncurry //runtime.text//char))) (/.install "clip" (trinary text//clip)) ))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux index edc4e2321..67966efe8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux @@ -36,7 +36,7 @@ (def: array::length (Unary Expression) - (|>> (_.the "length") //runtime.i64//from_number)) + (|>> (_.the "length") //runtime.i64//of_number)) (def: (array::read [indexG arrayG]) (Binary Expression) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux index da55a6c32..d71b9dbcc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux @@ -116,7 +116,7 @@ [branchG (phase archive branch) @branch ///runtime.forge-label] (wrap [(list\map (function (_ char) - [(try.assume (signed.s4 (.int char))) @branch]) + [(try.assumed (signed.s4 (.int char))) @branch]) chars) ($_ _.compose (_.set-label @branch) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux index 2d31a6b71..aa07cbe9f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux @@ -85,7 +85,7 @@ (list\map (|>> product.right synthesis.path/then //case.dependencies)) (list& (//case.dependencies (synthesis.path/then else))) list.concat - (set.from_list _.hash) + (set.of_list _.hash) set.to_list) @expression (_.constant (reference.artifact [context_module context_artifact])) directive (_.define_function @expression (list& (_.parameter @input) (list\map _.reference foreigns)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux index 65783662a..bfd952cc9 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux @@ -391,7 +391,7 @@ (runtime: i64//-one (i64//negate i64//one)) -(runtime: (i64//from_number value) +(runtime: (i64//of_number value) (_.return (<| (_.? (_.not_a_number? value) i64//zero) (_.? (_.<= (_.negate i64//2^63) value) @@ -399,7 +399,7 @@ (_.? (|> value (_.+ (_.i32 +1)) (_.>= i64//2^63)) i64//max) (_.? (|> value (_.< (_.i32 +0))) - (|> value _.negate i64//from_number i64//negate)) + (|> value _.negate i64//of_number i64//negate)) (..i64 (|> value (_./ i64//2^32) _.to_i32) (|> value (_.% i64//2^32) _.to_i32))))) @@ -590,7 +590,7 @@ (_.define remainder subject) (_.while (i64//<= remainder parameter) (with_vars [approximate approximate_result approximate_remainder log2 delta] - (let [approximate_result' (i64//from_number approximate) + (let [approximate_result' (i64//of_number approximate) approx_remainder (i64//* parameter approximate_result)] ($_ _.then (_.define approximate (|> (i64//to_number remainder) @@ -647,7 +647,7 @@ @i64//+ @i64//negate @i64//to_number - @i64//from_number + @i64//of_number @i64//- @i64//* @i64//< @@ -662,7 +662,7 @@ (_.define idx (|> text (_.do "indexOf" (list part (i64//to_number start))))) (_.return (_.? (_.= (_.i32 -1) idx) ..none - (..some (i64//from_number idx))))))) + (..some (i64//of_number idx))))))) (runtime: (text//clip offset length text) (_.return (|> text (_.do "substring" (list (_.the ..i64_low_field offset) @@ -675,7 +675,7 @@ (_.define result (|> text (_.do "charCodeAt" (list (_.the ..i64_low_field idx))))) (_.if (_.not_a_number? result) (_.throw (_.string "[Lux Error] Cannot get char from text.")) - (_.return (i64//from_number result)))))) + (_.return (i64//of_number result)))))) (def: runtime//text Statement diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial/count.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial/count.lux index 5497cc094..a3e4fc738 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial/count.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial/count.lux @@ -18,7 +18,7 @@ (def: #export initial (Bytecode Any) - (|> +0 signed.s1 try.assume _.bipush)) + (|> +0 signed.s1 try.assumed _.bipush)) (def: this _.aload_0) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux index e42804d63..da80cbfdd 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux @@ -153,5 +153,5 @@ (monad.seq _.monad))]] ($_ _.compose ///partial/count.value - (_.tableswitch (try.assume (signed.s4 +0)) @default [@labelsH @labelsT]) + (_.tableswitch (try.assumed (signed.s4 +0)) @default [@labelsH @labelsT]) cases))))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux index 3785f9a40..ef5717521 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux @@ -56,7 +56,7 @@ type.void (list)])) -(def: no-partials (|> 0 unsigned.u1 try.assume _.bipush)) +(def: no-partials (|> 0 unsigned.u1 try.assumed _.bipush)) (def: #export (super environment-size arity) (-> Nat Arity (Bytecode Any)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux index 0441f3b00..67a384781 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux @@ -133,7 +133,7 @@ _.return)))] [..class (<| (format.run class.writer) - try.assume + try.assumed (class.class version.v6_0 ..program::modifier (name.internal ..class) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux index 28d9b81cd..86a980c95 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux @@ -516,7 +516,7 @@ class.public class.final)) bytecode (<| (format.run class.writer) - try.assume + try.assumed (class.class jvm/version.v6_0 modifier (name.internal class) @@ -584,7 +584,7 @@ //function/count.type (row.row))) bytecode (<| (format.run class.writer) - try.assume + try.assumed (class.class jvm/version.v6_0 modifier (name.internal class) 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 18b65c352..6004e31a8 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 @@ -90,8 +90,8 @@ [directive instantiation] (: [Statement Expression] (case (|> (synthesis.path/then bodyS) //case.dependencies - (set.from_list _.hash) - (set.difference (set.from_list _.hash locals)) + (set.of_list _.hash) + (set.difference (set.of_list _.hash locals)) set.to_list) #.Nil [(_.function @loop locals diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux index 9dc7e9e78..8b99967a2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux @@ -82,11 +82,11 @@ list.enumeration (list\map (|>> product.left (n.+ start) //case.register _.parameter))) @loop (_.constant (///reference.artifact [loop_module loop_artifact])) - loop_variables (set.from_list _.hash (list\map product.right locals)) + loop_variables (set.of_list _.hash (list\map product.right locals)) referenced_variables (: (-> Synthesis (Set Var)) (|>> synthesis.path/then //case.dependencies - (set.from_list _.hash))) + (set.of_list _.hash))) [directive instantiation] (: [Statement Expression] (case (|> (list\map referenced_variables initsS+) (list\fold set.union (referenced_variables bodyS)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux index 4ec21d754..96c1d1ce1 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux @@ -88,8 +88,8 @@ [directive instantiation] (: [(Statement Any) (Expression Any)] (case (|> (synthesis.path/then bodyS) //case.dependencies - (set.from_list _.hash) - (set.difference (set.from_list _.hash locals)) + (set.of_list _.hash) + (set.difference (set.of_list _.hash locals)) set.to_list) #.Nil [actual_loop diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux index 4682a593d..40ef044f6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux @@ -303,7 +303,7 @@ ..i64_high (_.< (_.int +0)))))))) -(runtime: (i64::from_float input) +(runtime: (i64::of_float input) (_.cond (list [(_.apply (list input) (_.var "is.nan")) i64::zero] [(|> input (_.<= (_.negate f2^63))) @@ -311,7 +311,7 @@ [(|> input (_.+ (_.float +1.0)) (_.>= f2^63)) i64::max] [(|> input (_.< (_.float +0.0))) - (|> input _.negate i64::from_float i64::negate)]) + (|> input _.negate i64::of_float i64::negate)]) (i64::new (|> input (_./ f2^32)) (|> input (_.%% f2^32))))) @@ -483,7 +483,7 @@ (_.or (|> remainder (i64::= param)))) (let [calc_rough_estimate (_.apply (list (|> (i64::to_float remainder) (_./ (i64::to_float param)))) (_.var "floor")) - calc_approximate_result (i64::from_float approximate) + calc_approximate_result (i64::of_float approximate) calc_approximate_remainder (|> approximate_result (i64::* param)) delta (_.if (|> (_.float +48.0) (_.<= log2)) (_.float +1.0) @@ -551,7 +551,7 @@ (runtime: (io::current_time! _) (|> current_time_float (_.* (_.float +1,000.0)) - i64::from_float)) + i64::of_float)) (def: runtime::io Expression @@ -676,7 +676,7 @@ @f2^63 @i64::new - @i64::from_float + @i64::of_float @i64::and @i64::or @@ -758,7 +758,7 @@ (_.nth (_.int +1)))) (_.if (|> idx (_.= (_.int -1))) ..none - (..some (i64::from_float (|> idx (_.+ startF)))))) + (..some (i64::of_float (|> idx (_.+ startF)))))) ..none)))) (runtime: (text::clip text from to) @@ -780,7 +780,7 @@ (_.if (|> idx (within? (_.length text))) ($_ _.then (_.set! idx (inc idx)) - (..some (i64::from_float (char_at idx text)))) + (..some (i64::of_float (char_at idx text)))) ..none)) (def: runtime::text diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux index 02938eb7a..e0f9ea89e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux @@ -414,7 +414,7 @@ (update@ #bindings (set.union (|> initsS+ list.enumeration (list\map (|>> product.left (n.+ start))) - (set.from_list n.hash)))) + (set.of_list n.hash)))) (for_synthesis iterationS) (get@ #dependencies))) (list\fold for_synthesis synthesis_storage initsS+)) 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 07e7a54b9..9e292c485 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 @@ -297,18 +297,18 @@ (do try.monad [#let [baseline (|> redundancy dictionary.keys - (set.from_list n.hash))] + (set.of_list n.hash))] [redundancy pre] (recur [redundancy pre]) #let [bindings (|> redundancy dictionary.keys - (set.from_list n.hash) + (set.of_list n.hash) (set.difference baseline))] [redundancy post] (recur [redundancy post]) #let [redundants (|> redundancy dictionary.entries - (list.filter (function (_ [register redundant?]) - (and (set.member? bindings register) - redundant?))) + (list.only (function (_ [register redundant?]) + (and (set.member? bindings register) + redundant?))) (list\map product.left))]] (wrap [(list\fold dictionary.remove redundancy (set.to_list bindings)) (|> redundants diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux index de266d0ad..e5329f36a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux @@ -236,11 +236,11 @@ ## Form and tuple syntax is mostly the same, differing only in the ## delimiters involved. ## They may have an arbitrary number of arbitrary Code nodes as elements. - [parse_form ..close_form #.Form] - [parse_tuple ..close_tuple #.Tuple] + [form_parser ..close_form #.Form] + [tuple_parser ..close_tuple #.Tuple] ) -(inline: (parse_record parse where offset source_code) +(inline: (record_parser parse where offset source_code) (-> (Parser Code) Location Offset Text (Either [Source Text] [Source Code])) (loop [source (: Source [(!forward 1 where) offset source_code]) @@ -265,7 +265,7 @@ (#.Left [[where offset source_code] (exception.construct ..text_cannot_contain_new_lines content)]))) -(def: (parse_text where offset source_code) +(def: (text_parser where offset source_code) (-> Location Offset Text (Either [Source Text] [Source Code])) (case ("lux text index" offset (static ..text_delimiter) source_code) (#.Some g!end) @@ -279,7 +279,7 @@ (#.Text g!content)]])) _ - (!failure ..parse_text where offset source_code))) + (!failure ..text_parser where offset source_code))) (with_expansions [<digits> (as_is "0" "1" "2" "3" "4" "5" "6" "7" "8" "9") <non_name_chars> (template [<char>] @@ -307,7 +307,7 @@ [[<digits> <digit_separator>] @then - (~~ (template.splice @else_options))] + (~~ (template.spliced @else_options))] ## else @else))) @@ -349,14 +349,14 @@ (with_expansions [<int_output> (as_is (!number_output source_code start end int.decimal #.Int)) <frac_output> (as_is (!number_output source_code start end frac.decimal #.Frac)) - <failure> (!failure ..parse_frac where offset source_code) + <failure> (!failure ..frac_parser where offset source_code) <frac_separator> (static ..frac_separator) <signs> (template [<sign>] [(~~ (static <sign>))] [..positive_sign] [..negative_sign])] - (inline: (parse_frac source_code//size start where offset source_code) + (inline: (frac_parser source_code//size start where offset source_code) (-> Nat Nat Location Offset Text (Either [Source Text] [Source Code])) (loop [end offset @@ -381,7 +381,7 @@ <frac_output>)))) - (inline: (parse_signed source_code//size start where offset source_code) + (inline: (signed_parser source_code//size start where offset source_code) (-> Nat Nat Location Offset Text (Either [Source Text] [Source Code])) (loop [end offset] @@ -390,7 +390,7 @@ (recur (!inc end)) [[<frac_separator>] - (parse_frac source_code//size start where (!inc end) source_code)] + (frac_parser source_code//size start where (!inc end) source_code)] <int_output>)))) ) @@ -406,22 +406,22 @@ [] (!number_output source_code start g!end <codec> <tag>)))))] - [parse_nat n.decimal #.Nat] - [parse_rev rev.decimal #.Rev] + [nat_parser n.decimal #.Nat] + [rev_parser rev.decimal #.Rev] ) -(template: (!parse_signed source_code//size offset where source_code @aliases @end) +(template: (!signed_parser source_code//size offset where source_code @aliases @end) (<| (let [g!offset/1 (!inc offset)]) (!with_char+ source_code//size source_code g!offset/1 g!char/1 @end) (!if_digit? g!char/1 - (parse_signed source_code//size offset where (!inc/2 offset) source_code) - (!parse_full_name offset [where (!inc offset) source_code] where @aliases #.Identifier)))) + (signed_parser source_code//size offset where (!inc/2 offset) source_code) + (!full_name_parser offset [where (!inc offset) source_code] where @aliases #.Identifier)))) (with_expansions [<output> (#.Right [[(update@ #.column (|>> (!n/+ (!n/- start end))) where) end source_code] (!clip start end source_code)])] - (inline: (parse_name_part start where offset source_code) + (inline: (name_part_parser start where offset source_code) (-> Nat Location Offset Text (Either [Source Text] [Source Text])) (let [source_code//size ("lux text size" source_code)] @@ -431,13 +431,13 @@ (recur (!inc end)) <output>)))))) -(template: (!parse_half_name @offset @char @module) +(template: (!half_name_parser @offset @char @module) (!if_name_char?|head @char - (!letE [source' name] (..parse_name_part @offset where (!inc @offset) source_code) + (!letE [source' name] (..name_part_parser @offset where (!inc @offset) source_code) (#.Right [source' [@module name]])) - (!failure ..!parse_half_name where @offset source_code))) + (!failure ..!half_name_parser where @offset source_code))) -(`` (def: (parse_short_name source_code//size current_module [where offset/0 source_code]) +(`` (def: (short_name_parser source_code//size current_module [where offset/0 source_code]) (-> Nat Text (Parser Name)) (<| (!with_char+ source_code//size source_code offset/0 char/0 (!end_of_file where offset/0 source_code current_module)) @@ -445,34 +445,34 @@ (<| (let [offset/1 (!inc offset/0)]) (!with_char+ source_code//size source_code offset/1 char/1 (!end_of_file where offset/1 source_code current_module)) - (!parse_half_name offset/1 char/1 current_module)) - (!parse_half_name offset/0 char/0 (static ..prelude)))))) + (!half_name_parser offset/1 char/1 current_module)) + (!half_name_parser offset/0 char/0 (static ..prelude)))))) -(template: (!parse_short_name source_code//size @current_module @source @where @tag) - (!letE [source' name] (..parse_short_name source_code//size @current_module @source) +(template: (!short_name_parser source_code//size @current_module @source @where @tag) + (!letE [source' name] (..short_name_parser source_code//size @current_module @source) (#.Right [source' [@where (@tag name)]]))) (with_expansions [<simple> (as_is (#.Right [source' ["" simple]]))] - (`` (def: (parse_full_name aliases start source) + (`` (def: (full_name_parser aliases start source) (-> Aliases Offset (Parser Name)) (<| (!letE [source' simple] (let [[where offset source_code] source] - (..parse_name_part start where offset source_code))) + (..name_part_parser start where offset source_code))) (let [[where' offset' source_code'] source']) (!with_char source_code' offset' char/separator <simple>) (if (!n/= (char (~~ (static ..name_separator))) char/separator) (<| (let [offset'' (!inc offset')]) - (!letE [source'' complex] (..parse_name_part offset'' (!forward 1 where') offset'' source_code')) + (!letE [source'' complex] (..name_part_parser offset'' (!forward 1 where') offset'' source_code')) (if ("lux text =" "" complex) (let [[where offset source_code] source] - (!failure ..parse_full_name where offset source_code)) + (!failure ..full_name_parser where offset source_code)) (#.Right [source'' [(|> aliases (dictionary.get simple) (maybe.default simple)) complex]]))) <simple>))))) -(template: (!parse_full_name @offset @source @where @aliases @tag) - (!letE [source' full_name] (..parse_full_name @aliases @offset @source) +(template: (!full_name_parser @offset @source @where @aliases @tag) + (!letE [source' full_name] (..full_name_parser @aliases @offset @source) (#.Right [source' [@where (@tag full_name)]]))) ## TODO: Grammar macro for specifying syntax. @@ -511,9 +511,9 @@ [(~~ (static <close>))] (!close <close>)] - [..open_form ..close_form parse_form] - [..open_tuple ..close_tuple parse_tuple] - [..open_record ..close_record parse_record] + [..open_form ..close_form form_parser] + [..open_tuple ..close_tuple tuple_parser] + [..open_record ..close_record record_parser] )] (`` ("lux syntax char case!" char/0 [[(~~ (static text.space)) @@ -528,7 +528,7 @@ ## Text [(~~ (static ..text_delimiter))] - (parse_text where (!inc offset/0) source_code) + (text_parser where (!inc offset/0) source_code) ## Special code [(~~ (static ..sigil))] @@ -537,7 +537,7 @@ (!end_of_file where offset/1 source_code current_module)) ("lux syntax char case!" char/1 [[(~~ (static ..name_separator))] - (!parse_short_name source_code//size current_module <move_2> where #.Tag) + (!short_name_parser source_code//size current_module <move_2> where #.Tag) ## Single_line comment [(~~ (static ..sigil))] @@ -558,7 +558,7 @@ ## else (!if_name_char?|head char/1 ## Tag - (!parse_full_name offset/1 <move_2> where aliases #.Tag) + (!full_name_parser offset/1 <move_2> where aliases #.Tag) (!failure ..parse where offset/0 source_code)))) ## Coincidentally (= ..name_separator ..frac_separator) @@ -569,20 +569,20 @@ (!with_char+ source_code//size source_code offset/1 char/1 (!end_of_file where offset/1 source_code current_module)) (!if_digit? char/1 - (parse_rev source_code//size offset/0 where (!inc offset/1) source_code) - (!parse_short_name source_code//size current_module [where offset/1 source_code] where #.Identifier))) + (rev_parser source_code//size offset/0 where (!inc offset/1) source_code) + (!short_name_parser source_code//size current_module [where offset/1 source_code] where #.Identifier))) [(~~ (static ..positive_sign)) (~~ (static ..negative_sign))] - (!parse_signed source_code//size offset/0 where source_code aliases - (!end_of_file where offset/0 source_code current_module))] + (!signed_parser source_code//size offset/0 where source_code aliases + (!end_of_file where offset/0 source_code current_module))] ## else (!if_digit? char/0 ## Natural number - (parse_nat source_code//size offset/0 where (!inc offset/0) source_code) + (nat_parser source_code//size offset/0 where (!inc offset/0) source_code) ## Identifier - (!parse_full_name offset/0 [<consume_1>] where aliases #.Identifier)) + (!full_name_parser offset/0 [<consume_1>] where aliases #.Identifier)) ))) ))) )) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux index 39beec921..4442bd5f3 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux @@ -251,7 +251,7 @@ (n.= (list.size reservations) (|> reservations (list\map product.left) - (set.from_list text.hash) + (set.of_list text.hash) set.size))) (def: (correct_ids? reservations) @@ -259,7 +259,7 @@ (n.= (list.size reservations) (|> reservations (list\map product.right) - (set.from_list n.hash) + (set.of_list n.hash) set.size))) (def: (correct_reservations? reservations) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux index 39edd668e..3e2e86663 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux @@ -13,7 +13,7 @@ ["." dictionary (#+ Dictionary)]] [format ["." binary (#+ Writer)]]] - [type (#+ :share) + [type (#+ :sharing) abstract]]] [// ["." signature (#+ Signature)] @@ -35,12 +35,12 @@ (if (\ signature.equivalence = (key.signature key) document//signature) - (#try.Success (:share [e] - (Key e) - key - - e - (:assume document//content))) + (#try.Success (:sharing [e] + (Key e) + key + + e + (:assume document//content))) (exception.throw ..invalid_signature [(key.signature key) document//signature])))) diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux index b41b272f5..cb52004f4 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux @@ -183,12 +183,12 @@ (\ fs directory_files) (\ ! map (|>> (list\map (function (_ file) [(file.name fs file) file])) - (list.filter (|>> product.left (text\= ..module_descriptor_file) not)) + (list.only (|>> product.left (text\= ..module_descriptor_file) not)) (monad.map ! (function (_ [name path]) (|> path (\ fs read) (\ ! map (|>> [name]))))) - (\ ! map (dictionary.from_list text.hash)))) + (\ ! map (dictionary.of_list text.hash)))) (\ ! join)))) (type: Definitions (Dictionary Text Any)) @@ -225,7 +225,7 @@ (case input (#.Cons [[artifact_id artifact_category] input']) (case (do ! - [data (try.from_maybe (dictionary.get (format (%.nat artifact_id) extension) actual)) + [data (try.of_maybe (dictionary.get (format (%.nat artifact_id) extension) actual)) #let [context [module_id artifact_id] directive (\ host ingest context data)]] (case artifact_category @@ -329,7 +329,7 @@ (#.Definition [exported? type annotations _]) (|> definitions (dictionary.get def_name) - try.from_maybe + try.of_maybe (\ ! map (|>> [exported? type annotations] #.Definition [def_name]))))) @@ -378,7 +378,7 @@ (if valid_cache? #.None (#.Some [module_name module_id])))) - (dictionary.from_list text.hash))) + (dictionary.of_list text.hash))) (def: (full_purge caches load_order) (-> (List [Bit [Module [archive.ID [Descriptor (Document .Module)]]]]) @@ -434,7 +434,7 @@ dictionary.entries (monad.map ! (..purge! fs static))) loaded_caches (|> load_order - (list.filter (|>> product.left (dictionary.key? purge) not)) + (list.only (|>> product.left (dictionary.key? purge) not)) (monad.map ! (function (_ [module_name [module_id [descriptor document _]]]) (do ! [[descriptor,document,output bundles] (..load_definitions fs static module_id host_environment descriptor document)] diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux index 7794d3f5e..60c50db11 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux @@ -1,7 +1,6 @@ (.module: [library [lux (#- Module Definition) - [type (#+ :share)] ["." ffi (#+ import: do_to)] [abstract ["." monad (#+ Monad do)]] diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux index 514de6852..e69755445 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux @@ -1,7 +1,7 @@ (.module: [library [lux (#- Module) - [type (#+ :share)] + [type (#+ :sharing)] [abstract ["." monad (#+ Monad do)]] [control @@ -64,11 +64,11 @@ (\ encoding.utf8 decode) (\ try.monad map (|>> :assume - (:share [directive] - directive - so_far - - directive) + (:sharing [directive] + directive + so_far + + directive) (..then so_far))))) (: _.Expression (_.manual ""))))) @@ -124,9 +124,9 @@ #let [mapping (|> order (list\map (function (_ [module [module_id [descriptor document output]]]) [module module_id])) - (dictionary.from_list text.hash) + (dictionary.of_list text.hash) (: (Dictionary Module archive.ID)))] entries (monad.map ! (..write_module now mapping) order)] (wrap (|> entries - row.from_list + row.of_list (binary.run tar.writer)))))) diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux index 404b3d800..080765231 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux @@ -1,7 +1,7 @@ (.module: [library [lux #* - [type (#+ :share)] + [type (#+ :sharing)] [abstract ["." monad (#+ Monad do)]] [control @@ -46,11 +46,11 @@ (\ utf8.codec decode) (\ try.monad map (|>> :assume - (:share [directive] - directive - so_far - - directive) + (:sharing [directive] + directive + so_far + + directive) (sequence so_far))))) so_far))) diff --git a/stdlib/source/library/lux/tool/compiler/phase.lux b/stdlib/source/library/lux/tool/compiler/phase.lux index d69098f92..f7e3ddf03 100644 --- a/stdlib/source/library/lux/tool/compiler/phase.lux +++ b/stdlib/source/library/lux/tool/compiler/phase.lux @@ -70,7 +70,7 @@ (def: #export fail (-> Text Operation) - (|>> try.fail (state.lift try.monad))) + (|>> #try.Failure (state.lift try.monad))) (def: #export (throw exception parameters) (All [e] (-> (Exception e) e Operation)) |