diff options
author | Eduardo Julian | 2021-08-11 02:38:59 -0400 |
---|---|---|
committer | Eduardo Julian | 2021-08-11 02:38:59 -0400 |
commit | a62ce3f9c2b605e0033f4772b0f64c4525de4d86 (patch) | |
tree | ecbabe8f110d82b2e6481cf7c0532d4bd4386570 /stdlib/source/library/lux/tool/compiler | |
parent | 464b6e8f5e6c62f58fa8c7ff61ab2ad215e98bd1 (diff) |
Relocated maybe and lazy from data to control.
Diffstat (limited to '')
67 files changed, 339 insertions, 343 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux index 6127ea59a..6af02e080 100644 --- a/stdlib/source/library/lux/tool/compiler/default/init.lux +++ b/stdlib/source/library/lux/tool/compiler/default/init.lux @@ -208,7 +208,7 @@ [reader (///directive.lift_analysis (..reader module aliases source))] (function (_ state) - (case (///phase.run' state (..iteration' archive expander reader source pre_payload)) + (case (///phase.result' state (..iteration' archive expander reader source pre_payload)) (#try.Success [state source&requirements&buffer]) (#try.Success [state (#.Some source&requirements&buffer)]) @@ -239,17 +239,17 @@ #///.process (function (_ state archive) (do {! try.monad} [.let [hash (text\hash (get@ #///.code input))] - [state [source buffer]] (<| (///phase.run' state) + [state [source buffer]] (<| (///phase.result' state) (..begin dependencies hash input)) .let [module (get@ #///.module input)]] - (loop [iteration (<| (///phase.run' state) + (loop [iteration (<| (///phase.result' state) (..iteration archive expander module source buffer ///syntax.no_aliases))] (do ! [[state ?source&requirements&temporary_payload] iteration] (case ?source&requirements&temporary_payload #.None (do ! - [[state [analysis_module [final_buffer final_registry]]] (///phase.run' state (..end module)) + [[state [analysis_module [final_buffer final_registry]]] (///phase.result' state (..end module)) .let [descriptor {#descriptor.hash hash #descriptor.name module #descriptor.file (get@ #///.file input) @@ -270,7 +270,7 @@ (get@ #///directive.imports) (list\map product.left)) #///.process (function (_ state archive) - (recur (<| (///phase.run' state) + (recur (<| (///phase.result' state) (do {! ///phase.monad} [analysis_module (<| (: (Operation .Module)) ///directive.lift_analysis diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux index 814e6dfd2..e5ed96552 100644 --- a/stdlib/source/library/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux @@ -8,6 +8,7 @@ ["." monad (#+ Monad do)]] [control ["." function] + ["." maybe] ["." try (#+ Try) ("#\." monad)] ["." exception (#+ exception:)] [concurrency @@ -17,7 +18,6 @@ ["." binary (#+ Binary)] ["." bit] ["." product] - ["." maybe] ["." text ("#\." equivalence) ["%" format (#+ format)]] [collection @@ -105,7 +105,7 @@ [_ (ioW.prepare system static module_id) _ (for {@.python (|> output row.list - (list.chunk 128) + (list.sub 128) (monad.map ! (monad.map ! write_artifact!)) (: (Action (List (List Any)))))} (|> output @@ -115,7 +115,7 @@ document (\ async.monad in (document.check $.key document))] (ioW.cache system static module_id - (_.run ..writer [descriptor document]))))) + (_.result ..writer [descriptor document]))))) ... TODO: Inline ASAP (def: initialize_buffer! @@ -192,7 +192,7 @@ (extension.with extender (:assume generators))) _ (extension.with extender (:assume directives))] (in []))) - (///phase.run' state) + (///phase.result' state) (\ try.monad map product.left))) (def: (phase_wrapper archive platform state) @@ -202,7 +202,7 @@ (|> archive phase_wrapper ///directive.lift_generation - (///phase.run' state)))) + (///phase.result' state)))) (def: (complete_extensions host_directive_bundle phase_wrapper [analysers synthesizers generators directives]) (All [<type_vars>] @@ -263,7 +263,7 @@ (in [state archive])) (do ! [[state [archive payload]] (|> (..process_runtime archive platform) - (///phase.run' state) + (///phase.result' state) async\in) _ (..cache_module static platform 0 payload) @@ -519,7 +519,7 @@ (All [<type_vars>] (-> Module <State+> <State+>)) (|> (///directive.set_current_module module) - (///phase.run' state) + (///phase.result' state) try.assumed product.left)) @@ -593,7 +593,7 @@ ... 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) + (///phase.result' state) try.assumed product.left) archive) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux index c79f514c3..eb325ddd0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux @@ -7,11 +7,11 @@ [monad (#+ do)]] [control ["." function] + ["." maybe] ["." try] ["." exception (#+ Exception)]] [data ["." product] - ["." maybe] ["." bit ("#\." equivalence)] ["." text ("#\." equivalence) ["%" format (#+ Format format)]] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux index 74cadee55..5ae124d96 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux @@ -49,9 +49,9 @@ module (extensionP.lift meta.current_module_name)] (phase.lift (do try.monad - [exprS (|> exprA (synthesisP.phase archive) (phase.run synthesis_state))] - (phase.run generation_state - (do phase.monad - [exprO (generate archive exprS) - module_id (generation.module_id module archive)] - (generation.evaluate! (..context [module_id count]) exprO))))))))) + [exprS (|> exprA (synthesisP.phase archive) (phase.result synthesis_state))] + (phase.result generation_state + (do phase.monad + [exprO (generate archive exprS) + module_id (generation.module_id module archive)] + (generation.evaluate! (..context [module_id count]) exprO))))))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux index 315424e3c..0a1841ad1 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux @@ -173,7 +173,7 @@ _ (extension.update (update@ #counter inc))] (in count))) -(def: .public (gensym prefix) +(def: .public (identifier prefix) (All [anchor expression directive] (-> Text (Operation anchor expression directive Text))) (\ phase.monad map (|>> %.nat (format prefix)) ..next)) 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 11c4ba626..454704918 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 @@ -5,11 +5,11 @@ [abstract ["." monad (#+ do)]] [control + ["." maybe] ["." try] ["." exception (#+ exception:)]] [data ["." product] - ["." maybe] [text ["%" format (#+ format)]] [collection 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 7dd813c09..5a47352b4 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 @@ -5,11 +5,11 @@ equivalence ["." monad (#+ do)]] [control + ["." maybe] ["." try (#+ Try) ("#\." monad)] ["." exception (#+ exception:)]] [data ["." bit ("#\." equivalence)] - ["." maybe] ["." text ["%" format (#+ Format format)]] [collection diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux index 265311550..8063f450d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux @@ -4,9 +4,9 @@ [abstract monad] [control + ["." maybe] ["ex" exception (#+ exception:)]] [data - ["." maybe] ["." text ["%" format (#+ format)]] [collection 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 a07afe1fa..1a8d43477 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 @@ -4,9 +4,9 @@ [abstract [monad (#+ do)]] [control + ["." maybe] ["." exception (#+ exception:)]] [data - ["." maybe] ["." text ["%" format (#+ format)]] [collection diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux index 097f47cce..351c396e0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux @@ -4,11 +4,11 @@ [abstract monad] [control + ["." maybe ("#\." monad)] ["." try] ["." exception (#+ exception:)]] [data ["." text ("#\." equivalence)] - ["." maybe ("#\." monad)] ["." product] [collection ["." list ("#\." functor fold monoid)] @@ -118,8 +118,8 @@ (|>> (update@ #.counter inc) (update@ #.mappings (plist.put name [type new_var_id])))) head)] - (case (///.run' [bundle (set@ #.scopes (#.Item new_head tail) state)] - action) + (case (///.result' [bundle (set@ #.scopes (#.Item new_head tail) state)] + action) (#try.Success [[bundle' state'] output]) (case (get@ #.scopes state') (#.Item head' tail') 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 6ff5f7ce4..f5f5d89c8 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 @@ -5,12 +5,12 @@ [abstract ["." monad (#+ do)]] [control + ["." maybe] ["ex" exception (#+ exception:)] ["." state]] [data ["." name] ["." product] - ["." maybe] [text ["%" format (#+ format)]] [collection diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux index 0620b8c01..3142451e4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux @@ -80,7 +80,7 @@ ["Extension" (%.text name)] ["Available" (|> bundle dictionary.keys - (list.sort text\<) + (list.sorted text\<) (exception.listing %.text))])) (type: .public (Extender s i o) 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 d74b18019..27ce292a0 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 @@ -7,13 +7,13 @@ ["." monad (#+ do)]] [control pipe + ["." maybe] ["." try (#+ Try) ("#\." monad)] ["." exception (#+ exception:)] ["<>" parser ["<.>" code (#+ Parser)] ["<.>" text]]] [data - ["." maybe] ["." product] ["." text ("#\." equivalence) ["%" format (#+ format)]] @@ -400,7 +400,7 @@ [objectJ (jvm_type objectT)] (|> objectJ ..signature - (<text>.run jvm_parser.array) + (<text>.result jvm_parser.array) phase.lift))) (def: (primitive_array_length_handler primitive_type) @@ -845,7 +845,7 @@ (template [<name> <category> <parser>] [(def: .public (<name> mapping typeJ) (-> Mapping (Type <category>) (Operation .Type)) - (case (|> typeJ ..signature (<text>.run (<parser> mapping))) + (case (|> typeJ ..signature (<text>.result (<parser> mapping))) (#try.Success check) (typeA.with_env check) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux index 5a76b1804..979af197a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux @@ -4,12 +4,12 @@ [abstract ["." monad (#+ do)]] [control + ["." maybe] ["." try] ["." exception (#+ exception:)] ["<>" parser ["<.>" code (#+ Parser)]]] [data - ["." maybe] ["." text ["%" format (#+ format)]] [collection @@ -40,7 +40,7 @@ (-> Text Phase Archive s (Operation Analysis))] Handler)) (function (_ extension_name analyse archive args) - (case (<code>.run syntax args) + (case (<code>.result syntax args) (#try.Success inputs) (handler extension_name analyse archive inputs) 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 5c130e466..6e3ca3a70 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 @@ -12,7 +12,6 @@ ["<.>" code (#+ Parser)]]] [data ["." product] - ["." maybe] ["." text ["%" format (#+ format)]] [collection @@ -54,7 +53,7 @@ (Operation anchor expression directive Requirements))] (Handler anchor expression directive))) (function (_ extension_name phase archive inputs) - (case (<code>.run syntax inputs) + (case (<code>.result syntax inputs) (#try.Success inputs) (handler extension_name phase archive inputs) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux index bfe808472..e8518812e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux @@ -44,7 +44,7 @@ (-> Text (Generator s))] Handler)) (function (_ extension_name phase archive input) - (case (<s>.run parser input) + (case (<s>.result parser input) (#try.Success input') (handler extension_name phase archive input') @@ -64,7 +64,7 @@ ... <s>.any)))) ... (function (_ extension_name phase archive [input else conditionals]) ... (do {! /////.monad} -... [@input (\ ! map _.var (generation.gensym "input")) +... [@input (\ ! map _.var (generation.identifier "input")) ... inputG (phase archive input) ... elseG (phase archive else) ... conditionalsG (: (Operation (List [Expression Expression])) @@ -101,7 +101,7 @@ (/.install "or" (binary _.logior/2)) (/.install "xor" (binary _.logxor/2)) (/.install "left-shift" (binary _.ash/2)) - (/.install "right-shift" (binary (product.uncurry //runtime.i64//right_shifted))) + (/.install "right-shift" (binary (product.uncurried //runtime.i64//right_shifted))) (/.install "=" (binary _.=/2)) (/.install "<" (binary _.</2)) (/.install "+" (binary _.+/2)) @@ -117,13 +117,13 @@ Bundle (<| (/.prefix "f64") (|> /.empty - ... (/.install "=" (binary (product.uncurry _.=/2))) - ... (/.install "<" (binary (product.uncurry _.</2))) - ... (/.install "+" (binary (product.uncurry _.+/2))) - ... (/.install "-" (binary (product.uncurry _.-/2))) - ... (/.install "*" (binary (product.uncurry _.*/2))) - ... (/.install "/" (binary (product.uncurry _.//2))) - ... (/.install "%" (binary (product.uncurry _.rem/2))) + ... (/.install "=" (binary (product.uncurried _.=/2))) + ... (/.install "<" (binary (product.uncurried _.</2))) + ... (/.install "+" (binary (product.uncurried _.+/2))) + ... (/.install "-" (binary (product.uncurried _.-/2))) + ... (/.install "*" (binary (product.uncurried _.*/2))) + ... (/.install "/" (binary (product.uncurried _.//2))) + ... (/.install "%" (binary (product.uncurried _.rem/2))) ... (/.install "i64" (unary _.truncate/1)) (/.install "encode" (unary _.write_to_string/1)) ... (/.install "decode" (unary //runtime.f64//decode)) @@ -146,7 +146,7 @@ (<| (/.prefix "text") (|> /.empty (/.install "=" (binary _.string=/2)) - ... (/.install "<" (binary (product.uncurry _.string<?/2))) + ... (/.install "<" (binary (product.uncurried _.string<?/2))) (/.install "concat" (binary (function (_ [left right]) (_.concatenate/3 [(_.symbol "string") left right])))) (/.install "index" (trinary ..text//index)) 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 f17ea75a3..50b60d954 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 @@ -38,7 +38,7 @@ (-> Text (Generator s))] Handler)) (function (_ extension_name phase archive input) - (case (<s>.run parser input) + (case (<s>.result parser input) (#try.Success input') (handler extension_name phase archive input') @@ -122,25 +122,25 @@ Bundle (|> /.empty (/.install "syntax char case!" lux::syntax_char_case!) - (/.install "is" (binary (product.uncurry _.=))) + (/.install "is" (binary (product.uncurried _.=))) (/.install "try" (unary //runtime.lux//try)))) (def: i64_procs Bundle (<| (/.prefix "i64") (|> /.empty - (/.install "and" (binary (product.uncurry //runtime.i64//and))) - (/.install "or" (binary (product.uncurry //runtime.i64//or))) - (/.install "xor" (binary (product.uncurry //runtime.i64//xor))) + (/.install "and" (binary (product.uncurried //runtime.i64//and))) + (/.install "or" (binary (product.uncurried //runtime.i64//or))) + (/.install "xor" (binary (product.uncurried //runtime.i64//xor))) (/.install "left-shift" (binary i64//left_shifted)) (/.install "right-shift" (binary i64//right_shifted)) - (/.install "=" (binary (product.uncurry //runtime.i64//=))) - (/.install "<" (binary (product.uncurry //runtime.i64//<))) - (/.install "+" (binary (product.uncurry //runtime.i64//+))) - (/.install "-" (binary (product.uncurry //runtime.i64//-))) - (/.install "*" (binary (product.uncurry //runtime.i64//*))) - (/.install "/" (binary (product.uncurry //runtime.i64///))) - (/.install "%" (binary (product.uncurry //runtime.i64//%))) + (/.install "=" (binary (product.uncurried //runtime.i64//=))) + (/.install "<" (binary (product.uncurried //runtime.i64//<))) + (/.install "+" (binary (product.uncurried //runtime.i64//+))) + (/.install "-" (binary (product.uncurried //runtime.i64//-))) + (/.install "*" (binary (product.uncurried //runtime.i64//*))) + (/.install "/" (binary (product.uncurried //runtime.i64///))) + (/.install "%" (binary (product.uncurried //runtime.i64//%))) (/.install "f64" (unary //runtime.i64//number)) (/.install "char" (unary i64//char)) ))) @@ -149,13 +149,13 @@ Bundle (<| (/.prefix "f64") (|> /.empty - (/.install "+" (binary (product.uncurry _.+))) - (/.install "-" (binary (product.uncurry _.-))) - (/.install "*" (binary (product.uncurry _.*))) - (/.install "/" (binary (product.uncurry _./))) - (/.install "%" (binary (product.uncurry _.%))) - (/.install "=" (binary (product.uncurry _.=))) - (/.install "<" (binary (product.uncurry _.<))) + (/.install "+" (binary (product.uncurried _.+))) + (/.install "-" (binary (product.uncurried _.-))) + (/.install "*" (binary (product.uncurried _.*))) + (/.install "/" (binary (product.uncurried _./))) + (/.install "%" (binary (product.uncurried _.%))) + (/.install "=" (binary (product.uncurried _.=))) + (/.install "<" (binary (product.uncurried _.<))) (/.install "i64" (unary //runtime.i64//of_number)) (/.install "encode" (unary (_.do "toString" (list)))) (/.install "decode" (unary f64//decode))))) @@ -164,12 +164,12 @@ Bundle (<| (/.prefix "text") (|> /.empty - (/.install "=" (binary (product.uncurry _.=))) - (/.install "<" (binary (product.uncurry _.<))) + (/.install "=" (binary (product.uncurried _.=))) + (/.install "<" (binary (product.uncurried _.<))) (/.install "concat" (binary text//concat)) (/.install "index" (trinary text//index)) (/.install "size" (unary (|>> (_.the "length") //runtime.i64//of_number))) - (/.install "char" (binary (product.uncurry //runtime.text//char))) + (/.install "char" (binary (product.uncurried //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 b2c84251e..9e681c65d 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 @@ -133,7 +133,7 @@ (do {! ////////phase.monad} [abstractionG (phase archive abstractionS) .let [variable (: (-> Text (Operation Var)) - (|>> generation.gensym + (|>> generation.identifier (\ ! map _.var)))] g!inputs (monad.map ! (function (_ _) (variable "input")) (list.repeated (.nat arity) [])) 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 4bd10e9ec..770e1cce0 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 @@ -48,7 +48,7 @@ (-> Text Phase Archive s (Operation (Bytecode Any)))] Handler)) (function (_ extension_name phase archive input) - (case (<s>.run parser input) + (case (<s>.result parser input) (#try.Success input') (handler extension_name phase archive input') 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 953a4b88a..b3b4be343 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 @@ -4,6 +4,7 @@ [abstract ["." monad (#+ do)]] [control + ["." maybe] ["." try] ["." exception (#+ exception:)] ["<>" parser @@ -11,7 +12,6 @@ ["<s>" synthesis (#+ Parser)]]] [data ["." product] - ["." maybe] ["." text ("#\." equivalence) ["%" format (#+ format)]] [number @@ -1070,7 +1070,7 @@ bodyG (returnG returnT))))))) normalized_methods) - bytecode (<| (\ ! map (format.run class.writer)) + bytecode (<| (\ ! map (format.result class.writer)) //////.lift (class.class version.v6_0 ($_ modifier\compose class.public class.final) (name.internal anonymous_class_name) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux index 1ef715e28..db25d1d70 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux @@ -41,7 +41,7 @@ (-> Text (Generator s))] Handler)) (function (_ extension_name phase archive input) - (case (<s>.run parser input) + (case (<s>.result parser input) (#try.Success input') (handler extension_name phase archive input') @@ -63,7 +63,7 @@ (do {! /////.monad} [inputG (phase archive input) elseG (phase archive else) - @input (\ ! map _.var (generation.gensym "input")) + @input (\ ! map _.var (generation.identifier "input")) conditionalsG (: (Operation (List [Expression Expression])) (monad.map ! (function (_ [chars branch]) (do ! @@ -88,25 +88,25 @@ Bundle (|> /.empty (/.install "syntax char case!" lux::syntax_char_case!) - (/.install "is" (binary (product.uncurry _.=))) + (/.install "is" (binary (product.uncurried _.=))) (/.install "try" (unary //runtime.lux//try)))) (def: i64_procs Bundle (<| (/.prefix "i64") (|> /.empty - (/.install "and" (binary (product.uncurry _.bit_and))) - (/.install "or" (binary (product.uncurry _.bit_or))) - (/.install "xor" (binary (product.uncurry _.bit_xor))) - (/.install "left-shift" (binary (product.uncurry //runtime.i64//left_shift))) - (/.install "right-shift" (binary (product.uncurry //runtime.i64//right_shift))) - (/.install "=" (binary (product.uncurry _.=))) - (/.install "+" (binary (product.uncurry _.+))) - (/.install "-" (binary (product.uncurry _.-))) - (/.install "<" (binary (product.uncurry _.<))) - (/.install "*" (binary (product.uncurry _.*))) - (/.install "/" (binary (product.uncurry //runtime.i64//division))) - (/.install "%" (binary (product.uncurry //runtime.i64//remainder))) + (/.install "and" (binary (product.uncurried _.bit_and))) + (/.install "or" (binary (product.uncurried _.bit_or))) + (/.install "xor" (binary (product.uncurried _.bit_xor))) + (/.install "left-shift" (binary (product.uncurried //runtime.i64//left_shift))) + (/.install "right-shift" (binary (product.uncurried //runtime.i64//right_shift))) + (/.install "=" (binary (product.uncurried _.=))) + (/.install "+" (binary (product.uncurried _.+))) + (/.install "-" (binary (product.uncurried _.-))) + (/.install "<" (binary (product.uncurried _.<))) + (/.install "*" (binary (product.uncurried _.*))) + (/.install "/" (binary (product.uncurried //runtime.i64//division))) + (/.install "%" (binary (product.uncurried //runtime.i64//remainder))) (/.install "f64" (unary (_./ (_.float +1.0)))) (/.install "char" (unary (_.apply/1 (_.var "utf8.char")))) ))) @@ -119,13 +119,13 @@ Bundle (<| (/.prefix "f64") (|> /.empty - (/.install "+" (binary (product.uncurry _.+))) - (/.install "-" (binary (product.uncurry _.-))) - (/.install "*" (binary (product.uncurry _.*))) - (/.install "/" (binary (product.uncurry _./))) - (/.install "%" (binary (product.uncurry (function.flip (_.apply/2 (_.var "math.fmod")))))) - (/.install "=" (binary (product.uncurry _.=))) - (/.install "<" (binary (product.uncurry _.<))) + (/.install "+" (binary (product.uncurried _.+))) + (/.install "-" (binary (product.uncurried _.-))) + (/.install "*" (binary (product.uncurried _.*))) + (/.install "/" (binary (product.uncurried _./))) + (/.install "%" (binary (product.uncurried (function.flip (_.apply/2 (_.var "math.fmod")))))) + (/.install "=" (binary (product.uncurried _.=))) + (/.install "<" (binary (product.uncurried _.<))) (/.install "i64" (unary (!unary "math.floor"))) (/.install "encode" (unary (_.apply/2 (_.var "string.format") (_.string "%.17g")))) (/.install "decode" (unary ..f64//decode))))) @@ -146,9 +146,9 @@ Bundle (<| (/.prefix "text") (|> /.empty - (/.install "=" (binary (product.uncurry _.=))) - (/.install "<" (binary (product.uncurry _.<))) - (/.install "concat" (binary (product.uncurry (function.flip _.concat)))) + (/.install "=" (binary (product.uncurried _.=))) + (/.install "<" (binary (product.uncurried _.<))) + (/.install "concat" (binary (product.uncurried (function.flip _.concat)))) (/.install "index" (trinary ..text//index)) (/.install "size" (unary //runtime.text//size)) ... TODO: Use version below once the Lua compiler becomes self-hosted. diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux index e3363fe01..f3525e411 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux @@ -171,7 +171,7 @@ (do {! ////////phase.monad} [abstractionG (phase archive abstractionS) .let [variable (: (-> Text (Operation Var)) - (|>> generation.gensym + (|>> generation.identifier (\ ! map _.var)))] g!inputs (monad.map ! (function (_ _) (variable "input")) 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 b061d4cc1..957407cc8 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 @@ -44,7 +44,7 @@ (-> Text (Generator s))] Handler)) (function (_ extension_name phase archive input) - (case (<s>.run parser input) + (case (<s>.result parser input) (#try.Success input') (handler extension_name phase archive input') @@ -67,7 +67,7 @@ [inputG (phase archive input) [[context_module context_artifact] elseG] (generation.with_new_context archive (phase archive else)) - @input (\ ! map _.var (generation.gensym "input")) + @input (\ ! map _.var (generation.identifier "input")) conditionalsG (: (Operation (List [Expression Expression])) (monad.map ! (function (_ [chars branch]) (do ! @@ -101,7 +101,7 @@ Bundle (|> /.empty (/.install "syntax char case!" lux::syntax_char_case!) - (/.install "is" (binary (product.uncurry _.===))) + (/.install "is" (binary (product.uncurried _.===))) (/.install "try" (unary //runtime.lux//try)) )) @@ -113,19 +113,19 @@ Bundle (<| (/.prefix "i64") (|> /.empty - (/.install "and" (binary (product.uncurry _.bit_and))) - (/.install "or" (binary (product.uncurry _.bit_or))) - (/.install "xor" (binary (product.uncurry _.bit_xor))) + (/.install "and" (binary (product.uncurried _.bit_and))) + (/.install "or" (binary (product.uncurried _.bit_or))) + (/.install "xor" (binary (product.uncurried _.bit_xor))) (/.install "left-shift" (binary ..left_shifted)) - (/.install "right-shift" (binary (product.uncurry //runtime.i64//right_shifted))) - (/.install "=" (binary (product.uncurry _.==))) - (/.install "<" (binary (product.uncurry _.<))) - (/.install "+" (binary (product.uncurry //runtime.i64//+))) - (/.install "-" (binary (product.uncurry //runtime.i64//-))) - (/.install "*" (binary (product.uncurry //runtime.i64//*))) + (/.install "right-shift" (binary (product.uncurried //runtime.i64//right_shifted))) + (/.install "=" (binary (product.uncurried _.==))) + (/.install "<" (binary (product.uncurried _.<))) + (/.install "+" (binary (product.uncurried //runtime.i64//+))) + (/.install "-" (binary (product.uncurried //runtime.i64//-))) + (/.install "*" (binary (product.uncurried //runtime.i64//*))) (/.install "/" (binary (function (_ [parameter subject]) (_.intdiv/2 [subject parameter])))) - (/.install "%" (binary (product.uncurry _.%))) + (/.install "%" (binary (product.uncurried _.%))) (/.install "f64" (unary (_./ (_.float +1.0)))) (/.install "char" (unary //runtime.i64//char)) ))) @@ -142,12 +142,12 @@ Bundle (<| (/.prefix "f64") (|> /.empty - (/.install "=" (binary (product.uncurry _.==))) - (/.install "<" (binary (product.uncurry _.<))) - (/.install "+" (binary (product.uncurry _.+))) - (/.install "-" (binary (product.uncurry _.-))) - (/.install "*" (binary (product.uncurry _.*))) - (/.install "/" (binary (product.uncurry _./))) + (/.install "=" (binary (product.uncurried _.==))) + (/.install "<" (binary (product.uncurried _.<))) + (/.install "+" (binary (product.uncurried _.+))) + (/.install "-" (binary (product.uncurried _.-))) + (/.install "*" (binary (product.uncurried _.*))) + (/.install "/" (binary (product.uncurried _./))) (/.install "%" (binary ..f64//%)) (/.install "i64" (unary _.intval/1)) (/.install "encode" (unary ..f64//encode)) @@ -165,12 +165,12 @@ Bundle (<| (/.prefix "text") (|> /.empty - (/.install "=" (binary (product.uncurry _.==))) - (/.install "<" (binary (product.uncurry _.<))) - (/.install "concat" (binary (product.uncurry (function.flip _.concat)))) + (/.install "=" (binary (product.uncurried _.==))) + (/.install "<" (binary (product.uncurried _.<))) + (/.install "concat" (binary (product.uncurried (function.flip _.concat)))) (/.install "index" (trinary ..text//index)) (/.install "size" (unary //runtime.text//size)) - (/.install "char" (binary (product.uncurry //runtime.text//char))) + (/.install "char" (binary (product.uncurried //runtime.text//char))) (/.install "clip" (trinary ..text//clip)) ))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux index 7d32ad88a..5b9eba41e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux @@ -41,7 +41,7 @@ (-> Text (Generator s))] Handler)) (function (_ extension_name phase archive input) - (case (<s>.run parser input) + (case (<s>.result parser input) (#try.Success input') (handler extension_name phase archive input') @@ -60,7 +60,7 @@ (do {! /////.monad} [inputG (phase archive input) elseG (phase archive else) - @input (\ ! map _.var (generation.gensym "input")) + @input (\ ! map _.var (generation.identifier "input")) conditionalsG (: (Operation (List [(Expression Any) (Expression Any)])) (monad.map ! (function (_ [chars branch]) @@ -86,7 +86,7 @@ Bundle (|> /.empty (/.install "syntax char case!" lux::syntax_char_case!) - (/.install "is" (binary (product.uncurry _.is))) + (/.install "is" (binary (product.uncurried _.is))) (/.install "try" (unary //runtime.lux::try)))) (def: (capped operation parameter subject) @@ -98,19 +98,19 @@ Bundle (<| (/.prefix "i64") (|> /.empty - (/.install "and" (binary (product.uncurry //runtime.i64::and))) - (/.install "or" (binary (product.uncurry //runtime.i64::or))) - (/.install "xor" (binary (product.uncurry //runtime.i64::xor))) - (/.install "left-shift" (binary (product.uncurry //runtime.i64::left_shift))) - (/.install "right-shift" (binary (product.uncurry //runtime.i64::right_shift))) + (/.install "and" (binary (product.uncurried //runtime.i64::and))) + (/.install "or" (binary (product.uncurried //runtime.i64::or))) + (/.install "xor" (binary (product.uncurried //runtime.i64::xor))) + (/.install "left-shift" (binary (product.uncurried //runtime.i64::left_shift))) + (/.install "right-shift" (binary (product.uncurried //runtime.i64::right_shift))) - (/.install "<" (binary (product.uncurry _.<))) - (/.install "=" (binary (product.uncurry _.=))) - (/.install "+" (binary (product.uncurry (..capped _.+)))) - (/.install "-" (binary (product.uncurry (..capped _.-)))) - (/.install "*" (binary (product.uncurry (..capped _.*)))) - (/.install "/" (binary (product.uncurry //runtime.i64::division))) - (/.install "%" (binary (product.uncurry //runtime.i64::remainder))) + (/.install "<" (binary (product.uncurried _.<))) + (/.install "=" (binary (product.uncurried _.=))) + (/.install "+" (binary (product.uncurried (..capped _.+)))) + (/.install "-" (binary (product.uncurried (..capped _.-)))) + (/.install "*" (binary (product.uncurried (..capped _.*)))) + (/.install "/" (binary (product.uncurried //runtime.i64::division))) + (/.install "%" (binary (product.uncurried //runtime.i64::remainder))) (/.install "f64" (unary _.float/1)) (/.install "char" (unary //runtime.i64::char)) ))) @@ -119,15 +119,15 @@ Bundle (<| (/.prefix "f64") (|> /.empty - (/.install "+" (binary (product.uncurry _.+))) - (/.install "-" (binary (product.uncurry _.-))) - (/.install "*" (binary (product.uncurry _.*))) - (/.install "/" (binary (product.uncurry //runtime.f64::/))) + (/.install "+" (binary (product.uncurried _.+))) + (/.install "-" (binary (product.uncurried _.-))) + (/.install "*" (binary (product.uncurried _.*))) + (/.install "/" (binary (product.uncurried //runtime.f64::/))) (/.install "%" (binary (function (_ [parameter subject]) (|> (_.__import__/1 (_.unicode "math")) (_.do "fmod" (list subject parameter)))))) - (/.install "=" (binary (product.uncurry _.=))) - (/.install "<" (binary (product.uncurry _.<))) + (/.install "=" (binary (product.uncurried _.=))) + (/.install "<" (binary (product.uncurried _.<))) (/.install "i64" (unary _.int/1)) (/.install "encode" (unary _.repr/1)) (/.install "decode" (unary //runtime.f64::decode))))) @@ -144,12 +144,12 @@ Bundle (<| (/.prefix "text") (|> /.empty - (/.install "=" (binary (product.uncurry _.=))) - (/.install "<" (binary (product.uncurry _.<))) - (/.install "concat" (binary (product.uncurry (function.flip _.+)))) + (/.install "=" (binary (product.uncurried _.=))) + (/.install "<" (binary (product.uncurried _.<))) + (/.install "concat" (binary (product.uncurried (function.flip _.+)))) (/.install "index" (trinary ..text::index)) (/.install "size" (unary _.len/1)) - (/.install "char" (binary (product.uncurry //runtime.text::char))) + (/.install "char" (binary (product.uncurried //runtime.text::char))) (/.install "clip" (trinary ..text::clip)) ))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux index 81d1373d6..8db4b2ffd 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux @@ -131,7 +131,7 @@ (do {! ////////phase.monad} [abstractionG (phase archive abstractionS) .let [variable (: (-> Text (Operation SVar)) - (|>> generation.gensym + (|>> generation.identifier (\ ! map _.var)))] g!inputs (monad.map ! (function (_ _) (variable "input")) (list.repeated (.nat arity) []))] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux index f14017891..25e244035 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux @@ -44,7 +44,7 @@ (-> Text (Generator s))] Handler)) (function (_ extension_name phase archive input) - (case (<s>.run parser input) + (case (<s>.result parser input) (#try.Success input') (handler extension_name phase archive input') @@ -64,7 +64,7 @@ ... ... <s>.any)))) ... ... (function (_ extension_name phase archive [input else conditionals]) ... ... (do {! /////.monad} -... ... [@input (\ ! map _.var (generation.gensym "input")) +... ... [@input (\ ! map _.var (generation.identifier "input")) ... ... inputG (phase archive input) ... ... elseG (phase archive else) ... ... conditionalsG (: (Operation (List [Expression Expression])) @@ -101,7 +101,7 @@ ... (/.install "or" (binary _.logior/2)) ... (/.install "xor" (binary _.logxor/2)) ... (/.install "left-shift" (binary _.ash/2)) - ... (/.install "right-shift" (binary (product.uncurry //runtime.i64//right_shift))) + ... (/.install "right-shift" (binary (product.uncurried //runtime.i64//right_shift))) ... (/.install "=" (binary _.=/2)) ... (/.install "<" (binary _.</2)) ... (/.install "+" (binary _.+/2)) @@ -117,13 +117,13 @@ ... Bundle ... (<| (/.prefix "f64") ... (|> /.empty -... ... (/.install "=" (binary (product.uncurry _.=/2))) -... ... (/.install "<" (binary (product.uncurry _.</2))) -... ... (/.install "+" (binary (product.uncurry _.+/2))) -... ... (/.install "-" (binary (product.uncurry _.-/2))) -... ... (/.install "*" (binary (product.uncurry _.*/2))) -... ... (/.install "/" (binary (product.uncurry _.//2))) -... ... (/.install "%" (binary (product.uncurry _.rem/2))) +... ... (/.install "=" (binary (product.uncurried _.=/2))) +... ... (/.install "<" (binary (product.uncurried _.</2))) +... ... (/.install "+" (binary (product.uncurried _.+/2))) +... ... (/.install "-" (binary (product.uncurried _.-/2))) +... ... (/.install "*" (binary (product.uncurried _.*/2))) +... ... (/.install "/" (binary (product.uncurried _.//2))) +... ... (/.install "%" (binary (product.uncurried _.rem/2))) ... ... (/.install "i64" (unary _.truncate/1)) ... (/.install "encode" (unary _.write_to_string/1)) ... ... (/.install "decode" (unary //runtime.f64//decode)) @@ -146,7 +146,7 @@ (<| (/.prefix "text") (|> /.empty ... (/.install "=" (binary _.string=/2)) - ... (/.install "<" (binary (product.uncurry _.string<?/2))) + ... (/.install "<" (binary (product.uncurried _.string<?/2))) (/.install "concat" (binary _.paste/2)) ... (/.install "index" (trinary ..text//index)) ... (/.install "size" (unary _.length/1)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux index cfe4e85e6..651f7a62d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux @@ -41,7 +41,7 @@ (-> Text (Generator s))] Handler)) (function (_ extension_name phase archive input) - (case (<s>.run parser input) + (case (<s>.result parser input) (#try.Success input') (handler extension_name phase archive input') @@ -60,7 +60,7 @@ (do {! /////.monad} [inputG (phase archive input) elseG (phase archive else) - @input (\ ! map _.local (generation.gensym "input")) + @input (\ ! map _.local (generation.identifier "input")) conditionalsG (: (Operation (List [Expression Expression])) (monad.map ! (function (_ [chars branch]) (do ! @@ -98,18 +98,18 @@ Bundle (<| (/.prefix "i64") (|> /.empty - (/.install "and" (binary (product.uncurry //runtime.i64//and))) - (/.install "or" (binary (product.uncurry //runtime.i64//or))) - (/.install "xor" (binary (product.uncurry //runtime.i64//xor))) - (/.install "left-shift" (binary (product.uncurry //runtime.i64//left_shift))) - (/.install "right-shift" (binary (product.uncurry //runtime.i64//right_shift))) + (/.install "and" (binary (product.uncurried //runtime.i64//and))) + (/.install "or" (binary (product.uncurried //runtime.i64//or))) + (/.install "xor" (binary (product.uncurried //runtime.i64//xor))) + (/.install "left-shift" (binary (product.uncurried //runtime.i64//left_shift))) + (/.install "right-shift" (binary (product.uncurried //runtime.i64//right_shift))) - (/.install "<" (binary (product.uncurry _.<))) - (/.install "=" (binary (product.uncurry _.=))) - (/.install "+" (binary (product.uncurry (..capped _.+)))) - (/.install "-" (binary (product.uncurry (..capped _.-)))) - (/.install "*" (binary (product.uncurry (..capped _.*)))) - (/.install "/" (binary (product.uncurry //runtime.i64//division))) + (/.install "<" (binary (product.uncurried _.<))) + (/.install "=" (binary (product.uncurried _.=))) + (/.install "+" (binary (product.uncurried (..capped _.+)))) + (/.install "-" (binary (product.uncurried (..capped _.-)))) + (/.install "*" (binary (product.uncurried (..capped _.*)))) + (/.install "/" (binary (product.uncurried //runtime.i64//division))) (/.install "%" (binary (function (_ [parameter subject]) (_.do "remainder" (list parameter) subject)))) @@ -121,14 +121,14 @@ Bundle (<| (/.prefix "f64") (|> /.empty - (/.install "+" (binary (product.uncurry _.+))) - (/.install "-" (binary (product.uncurry _.-))) - (/.install "*" (binary (product.uncurry _.*))) - (/.install "/" (binary (product.uncurry _./))) + (/.install "+" (binary (product.uncurried _.+))) + (/.install "-" (binary (product.uncurried _.-))) + (/.install "*" (binary (product.uncurried _.*))) + (/.install "/" (binary (product.uncurried _./))) (/.install "%" (binary (function (_ [parameter subject]) (_.do "remainder" (list parameter) subject)))) - (/.install "=" (binary (product.uncurry _.=))) - (/.install "<" (binary (product.uncurry _.<))) + (/.install "=" (binary (product.uncurried _.=))) + (/.install "<" (binary (product.uncurried _.<))) (/.install "i64" (unary (_.do "floor" (list)))) (/.install "encode" (unary (_.do "to_s" (list)))) (/.install "decode" (unary //runtime.f64//decode))))) @@ -149,12 +149,12 @@ Bundle (<| (/.prefix "text") (|> /.empty - (/.install "=" (binary (product.uncurry _.=))) - (/.install "<" (binary (product.uncurry _.<))) - (/.install "concat" (binary (product.uncurry (function.flip _.+)))) + (/.install "=" (binary (product.uncurried _.=))) + (/.install "<" (binary (product.uncurried _.<))) + (/.install "concat" (binary (product.uncurried (function.flip _.+)))) (/.install "index" (trinary text//index)) (/.install "size" (unary (_.the "length"))) - (/.install "char" (binary (product.uncurry //runtime.text//char))) + (/.install "char" (binary (product.uncurried //runtime.text//char))) (/.install "clip" (trinary text//clip)) ))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux index c90072ef1..2b2fca71f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux @@ -44,7 +44,7 @@ (-> Text (Generator s))] Handler)) (function (_ extension_name phase archive input) - (case (<s>.run parser input) + (case (<s>.result parser input) (#try.Success input') (handler extension_name phase archive input') @@ -64,7 +64,7 @@ <s>.any)))) (function (_ extension_name phase archive [input else conditionals]) (do {! /////.monad} - [@input (\ ! map _.var (generation.gensym "input")) + [@input (\ ! map _.var (generation.identifier "input")) inputG (phase archive input) elseG (phase archive else) conditionalsG (: (Operation (List [Expression Expression])) @@ -84,7 +84,7 @@ Bundle (|> /.empty (/.install "syntax char case!" lux::syntax_char_case!) - (/.install "is" (binary (product.uncurry _.eq?/2))) + (/.install "is" (binary (product.uncurried _.eq?/2))) (/.install "try" (unary //runtime.lux//try)) )) @@ -97,18 +97,18 @@ Bundle (<| (/.prefix "i64") (|> /.empty - (/.install "and" (binary (product.uncurry //runtime.i64//and))) - (/.install "or" (binary (product.uncurry //runtime.i64//or))) - (/.install "xor" (binary (product.uncurry //runtime.i64//xor))) - (/.install "left-shift" (binary (product.uncurry //runtime.i64//left_shift))) - (/.install "right-shift" (binary (product.uncurry //runtime.i64//right_shift))) - (/.install "=" (binary (product.uncurry _.=/2))) - (/.install "<" (binary (product.uncurry _.</2))) - (/.install "+" (binary (product.uncurry (..capped _.+/2)))) - (/.install "-" (binary (product.uncurry (..capped _.-/2)))) - (/.install "*" (binary (product.uncurry (..capped _.*/2)))) - (/.install "/" (binary (product.uncurry //runtime.i64//division))) - (/.install "%" (binary (product.uncurry _.remainder/2))) + (/.install "and" (binary (product.uncurried //runtime.i64//and))) + (/.install "or" (binary (product.uncurried //runtime.i64//or))) + (/.install "xor" (binary (product.uncurried //runtime.i64//xor))) + (/.install "left-shift" (binary (product.uncurried //runtime.i64//left_shift))) + (/.install "right-shift" (binary (product.uncurried //runtime.i64//right_shift))) + (/.install "=" (binary (product.uncurried _.=/2))) + (/.install "<" (binary (product.uncurried _.</2))) + (/.install "+" (binary (product.uncurried (..capped _.+/2)))) + (/.install "-" (binary (product.uncurried (..capped _.-/2)))) + (/.install "*" (binary (product.uncurried (..capped _.*/2)))) + (/.install "/" (binary (product.uncurried //runtime.i64//division))) + (/.install "%" (binary (product.uncurried _.remainder/2))) (/.install "f64" (unary (_.//2 (_.float +1.0)))) (/.install "char" (unary (|>> _.integer->char/1 (_.make_string/2 (_.int +1))))) ))) @@ -117,13 +117,13 @@ Bundle (<| (/.prefix "f64") (|> /.empty - (/.install "=" (binary (product.uncurry _.=/2))) - (/.install "<" (binary (product.uncurry _.</2))) - (/.install "+" (binary (product.uncurry _.+/2))) - (/.install "-" (binary (product.uncurry _.-/2))) - (/.install "*" (binary (product.uncurry _.*/2))) - (/.install "/" (binary (product.uncurry _.//2))) - (/.install "%" (binary (product.uncurry _.remainder/2))) + (/.install "=" (binary (product.uncurried _.=/2))) + (/.install "<" (binary (product.uncurried _.</2))) + (/.install "+" (binary (product.uncurried _.+/2))) + (/.install "-" (binary (product.uncurried _.-/2))) + (/.install "*" (binary (product.uncurried _.*/2))) + (/.install "/" (binary (product.uncurried _.//2))) + (/.install "%" (binary (product.uncurried _.remainder/2))) (/.install "i64" (unary _.truncate/1)) (/.install "encode" (unary _.number->string/1)) (/.install "decode" (unary //runtime.f64//decode))))) @@ -140,12 +140,12 @@ Bundle (<| (/.prefix "text") (|> /.empty - (/.install "=" (binary (product.uncurry _.string=?/2))) - (/.install "<" (binary (product.uncurry _.string<?/2))) - (/.install "concat" (binary (product.uncurry _.string_append/2))) + (/.install "=" (binary (product.uncurried _.string=?/2))) + (/.install "<" (binary (product.uncurried _.string<?/2))) + (/.install "concat" (binary (product.uncurried _.string_append/2))) (/.install "index" (trinary ..text//index)) (/.install "size" (unary _.string_length/1)) - (/.install "char" (binary (product.uncurry //runtime.text//char))) + (/.install "char" (binary (product.uncurried //runtime.text//char))) (/.install "clip" (trinary ..text//clip)) ))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux index 6cd07080a..c4b5b3764 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux @@ -26,7 +26,7 @@ (def: lux_procs Bundle (|> bundle.empty - (bundle.install "is" (binary (product.uncurry _.eq))) + (bundle.install "is" (binary (product.uncurried _.eq))) (bundle.install "try" (unary ///runtime.lux//try)))) (def: (i64//left_shifted [paramG subjectG]) @@ -46,19 +46,19 @@ Bundle (<| (bundle.prefix "i64") (|> bundle.empty - (bundle.install "and" (binary (product.uncurry _.logand))) - (bundle.install "or" (binary (product.uncurry _.logior))) - (bundle.install "xor" (binary (product.uncurry _.logxor))) + (bundle.install "and" (binary (product.uncurried _.logand))) + (bundle.install "or" (binary (product.uncurried _.logior))) + (bundle.install "xor" (binary (product.uncurried _.logxor))) (bundle.install "left-shift" (binary i64//left_shifted)) (bundle.install "logical-right-shift" (binary i64//logic_right_shifted)) (bundle.install "arithmetic-right-shift" (binary i64//arithmetic_right_shifted)) - (bundle.install "=" (binary (product.uncurry _.=))) - (bundle.install "<" (binary (product.uncurry _.<))) - (bundle.install "+" (binary (product.uncurry _.+))) - (bundle.install "-" (binary (product.uncurry _.-))) - (bundle.install "*" (binary (product.uncurry _.*))) - (bundle.install "/" (binary (product.uncurry _.floor))) - (bundle.install "%" (binary (product.uncurry _.rem))) + (bundle.install "=" (binary (product.uncurried _.=))) + (bundle.install "<" (binary (product.uncurried _.<))) + (bundle.install "+" (binary (product.uncurried _.+))) + (bundle.install "-" (binary (product.uncurried _.-))) + (bundle.install "*" (binary (product.uncurried _.*))) + (bundle.install "/" (binary (product.uncurried _.floor))) + (bundle.install "%" (binary (product.uncurried _.rem))) (bundle.install "f64" (unary (function (_ value) (_.coerce/2 [value (_.symbol "double-float")])))) (bundle.install "char" (unary (|>> _.code_char/1 _.string/1))) @@ -68,13 +68,13 @@ Bundle (<| (bundle.prefix "f64") (|> bundle.empty - (bundle.install "+" (binary (product.uncurry _.+))) - (bundle.install "-" (binary (product.uncurry _.-))) - (bundle.install "*" (binary (product.uncurry _.*))) - (bundle.install "/" (binary (product.uncurry _./))) - (bundle.install "%" (binary (product.uncurry _.mod))) - (bundle.install "=" (binary (product.uncurry _.=))) - (bundle.install "<" (binary (product.uncurry _.<))) + (bundle.install "+" (binary (product.uncurried _.+))) + (bundle.install "-" (binary (product.uncurried _.-))) + (bundle.install "*" (binary (product.uncurried _.*))) + (bundle.install "/" (binary (product.uncurried _./))) + (bundle.install "%" (binary (product.uncurried _.mod))) + (bundle.install "=" (binary (product.uncurried _.=))) + (bundle.install "<" (binary (product.uncurried _.<))) (bundle.install "i64" (unary _.floor/1)) (bundle.install "encode" (unary _.write_to_string/1)) (bundle.install "decode" (unary (let [@temp (_.var "temp")] @@ -103,7 +103,7 @@ Bundle (<| (bundle.prefix "text") (|> bundle.empty - (bundle.install "=" (binary (product.uncurry _.string=))) + (bundle.install "=" (binary (product.uncurried _.string=))) (bundle.install "<" (binary text//<)) (bundle.install "concat" (binary _.concatenate/2|string)) (bundle.install "index" (trinary text//index)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux index 9731cb94c..ce6b2bdc6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux @@ -48,7 +48,7 @@ _ (do {! ///////phase.monad} - [@closure (\ ! map _.var (/////generation.gensym "closure"))] + [@closure (\ ! map _.var (/////generation.identifier "closure"))] (in (_.labels (list [@closure [(|> (list.enumeration inits) (list\map (|>> product.left ..capture)) _.args) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux index 32b090ae1..172a4d13c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux @@ -105,7 +105,7 @@ code) (do meta.monad [runtime_id meta.seed] - (macro.with_gensyms [g!_] + (macro.with_identifiers [g!_] (let [runtime (code.local_identifier (///reference.artifact [..module_id runtime_id])) runtime_name (` (_.var (~ (code.text (%.code runtime)))))] (case declaration diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux index 5d8406d48..aeeb17528 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux @@ -10,7 +10,7 @@ [collection ["." list ("#\." functor)]]] ["." meta] - ["." macro (#+ with_gensyms) + ["." macro (#+ with_identifiers) ["." code] [syntax (#+ syntax:)]]]] ["." /// #_ @@ -31,9 +31,9 @@ (type: .public (Variadic of) (-> (List of) of)) (syntax: (arity: {arity s.nat} {name s.local_identifier} type) - (with_gensyms [g!_ g!extension g!name g!phase g!archive g!inputs g!of g!anchor g!expression g!directive] + (with_identifiers [g!_ g!extension g!name g!phase g!archive g!inputs g!of g!anchor g!expression g!directive] (do {! meta.monad} - [g!input+ (monad.seq ! (list.repeated arity (macro.gensym "input")))] + [g!input+ (monad.seq ! (list.repeated arity (macro.identifier "input")))] (in (list (` (def: .public ((~ (code.local_identifier name)) (~ g!extension)) (All [(~ g!anchor) (~ g!expression) (~ g!directive)] (-> ((~ type) (~ g!expression)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux index 6671f1e3f..12bce545f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux @@ -3,8 +3,9 @@ [lux (#- case let if) [abstract ["." monad (#+ do)]] + [control + ["." maybe]] [data - ["." maybe] ["." text] [collection ["." list ("#\." functor fold)]]] 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 815ee4a36..84e546a41 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 @@ -101,7 +101,7 @@ (<code>.form (<>.and <code>.local_identifier (<>.some <code>.local_identifier))))} code) - (macro.with_gensyms [g!_ runtime] + (macro.with_identifiers [g!_ runtime] (let [runtime_name (` (_.var (~ (code.text (%.code runtime)))))] (case declaration (#.Left name) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux index 7a8dd2860..095c973b4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux @@ -111,7 +111,7 @@ fields methods (row.row))) - .let [bytecode (format.run class.writer class)] + .let [bytecode (format.result class.writer class)] _ (generation.execute! [function_class bytecode]) _ (generation.save! function_class #.None [function_class bytecode])] (in instance))) @@ -124,7 +124,7 @@ (in ($_ _.compose abstractionG (|> inputsG - (list.chunk /arity.maximum) + (list.sub /arity.maximum) (monad.map _.monad (function (_ batchG) ($_ _.compose diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux index c3d119ec4..4db70e828 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux @@ -113,27 +113,27 @@ (_.putstatic (type.class bytecode_name (list)) ..value::field ..value::type) _.return)))) (row.row))] - (io.run (do {! (try.with io.monad)} - [bytecode (\ ! map (format.run class.writer) - (io.io bytecode)) - _ (loader.store eval_class bytecode library) - class (loader.load eval_class loader) - value (\ io.monad in (class_value eval_class class))] - (in [value - [eval_class bytecode]]))))) + (io.run! (do {! (try.with io.monad)} + [bytecode (\ ! map (format.result class.writer) + (io.io bytecode)) + _ (loader.store eval_class bytecode library) + class (loader.load eval_class loader) + value (\ io.monad in (class_value eval_class class))] + (in [value + [eval_class bytecode]]))))) (def: (execute! library loader temp_label [class_name class_bytecode]) (-> Library java/lang/ClassLoader Text Definition (Try Any)) - (io.run (do (try.with io.monad) - [existing_class? (|> (atom.read! library) - (\ io.monad map (function (_ library) - (dictionary.key? library class_name))) - (try.lift io.monad) - (: (IO (Try Bit)))) - _ (if existing_class? - (in []) - (loader.store class_name class_bytecode library))] - (loader.load class_name loader)))) + (io.run! (do (try.with io.monad) + [existing_class? (|> (atom.read! library) + (\ io.monad map (function (_ library) + (dictionary.key? library class_name))) + (try.lift io.monad) + (: (IO (Try Bit)))) + _ (if existing_class? + (in []) + (loader.store class_name class_bytecode library))] + (loader.load class_name loader)))) (def: (define! library loader [module name] valueG) (-> Library java/lang/ClassLoader Name (Bytecode Any) (Try [Text Any Definition])) 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 0a749f337..f7ba0eb93 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 @@ -139,7 +139,7 @@ ..run_io _.return)))] [..class - (<| (format.run class.writer) + (<| (format.result class.writer) try.assumed (class.class version.v6_0 ..program::modifier 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 dff909982..8fcd70360 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 @@ -515,7 +515,7 @@ ($_ modifier\compose class.public class.final)) - bytecode (<| (format.run class.writer) + bytecode (<| (format.result class.writer) try.assumed (class.class jvm/version.v6_0 modifier @@ -583,7 +583,7 @@ //function/count.field //function/count.type (row.row))) - bytecode (<| (format.run class.writer) + bytecode (<| (format.result class.writer) try.assumed (class.class jvm/version.v6_0 modifier diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux index bfb1ab115..5ba5d0f5e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux @@ -123,12 +123,12 @@ code) (do meta.monad [runtime_id meta.seed] - (macro.with_gensyms [g!_] + (macro.with_identifiers [g!_] (let [runtime (code.local_identifier (///reference.artifact [..module_id runtime_id])) runtime_name (` (_.var (~ (code.text (%.code runtime)))))] (case declaration (#.Left name) - (macro.with_gensyms [g!_] + (macro.with_identifiers [g!_] (let [g!name (code.local_identifier name)] (in (list (` (def: .public (~ g!name) Var @@ -141,7 +141,7 @@ (_.set (~ g!name) (~ code)))))))))) (#.Right [name inputs]) - (macro.with_gensyms [g!_] + (macro.with_identifiers [g!_] (let [g!name (code.local_identifier name) inputsC (list\map code.local_identifier inputs) inputs_typesC (list\map (function.constant (` _.Expression)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux index 9b99a1ca6..bfc75d6ca 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux @@ -257,10 +257,6 @@ iteration!) (_.throw (_.new (_.constant "Exception") (list (_.string ////synthesis/case.pattern_matching_error)))))))) -(def: (gensym prefix) - (-> Text (Operation Text)) - (\ ///////phase.monad map (|>> %.nat (format prefix)) /////generation.next)) - (def: .public dependencies (-> Path (List Var)) (|>> ////synthesis/case.storage diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux index a630b31c3..c236c3f75 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux @@ -27,32 +27,32 @@ (def: lux_procs Bundle (|> bundle.empty - (bundle.install "is" (binary (product.uncurry _.=))) + (bundle.install "is" (binary (product.uncurried _.=))) (bundle.install "try" (unary ///runtime.lux//try)))) (def: i64_procs Bundle (<| (bundle.prefix "i64") (|> bundle.empty - (bundle.install "and" (binary (product.uncurry _.bit_and))) - (bundle.install "or" (binary (product.uncurry _.bit_or))) - (bundle.install "xor" (binary (product.uncurry _.bit_xor))) - (bundle.install "left-shift" (binary (product.uncurry _.bit_shl))) - (bundle.install "logical-right-shift" (binary (product.uncurry ///runtime.i64//logic_right_shift))) - (bundle.install "arithmetic-right-shift" (binary (product.uncurry _.bit_shr))) - (bundle.install "=" (binary (product.uncurry _.=))) - (bundle.install "+" (binary (product.uncurry _.+))) - (bundle.install "-" (binary (product.uncurry _.-))) + (bundle.install "and" (binary (product.uncurried _.bit_and))) + (bundle.install "or" (binary (product.uncurried _.bit_or))) + (bundle.install "xor" (binary (product.uncurried _.bit_xor))) + (bundle.install "left-shift" (binary (product.uncurried _.bit_shl))) + (bundle.install "logical-right-shift" (binary (product.uncurried ///runtime.i64//logic_right_shift))) + (bundle.install "arithmetic-right-shift" (binary (product.uncurried _.bit_shr))) + (bundle.install "=" (binary (product.uncurried _.=))) + (bundle.install "+" (binary (product.uncurried _.+))) + (bundle.install "-" (binary (product.uncurried _.-))) ))) (def: int_procs Bundle (<| (bundle.prefix "int") (|> bundle.empty - (bundle.install "<" (binary (product.uncurry _.<))) - (bundle.install "*" (binary (product.uncurry _.*))) - (bundle.install "/" (binary (product.uncurry _./))) - (bundle.install "%" (binary (product.uncurry _.%))) + (bundle.install "<" (binary (product.uncurried _.<))) + (bundle.install "*" (binary (product.uncurried _.*))) + (bundle.install "/" (binary (product.uncurried _./))) + (bundle.install "%" (binary (product.uncurried _.%))) (bundle.install "frac" (unary _.floatval/1)) (bundle.install "char" (unary _.chr/1))))) @@ -60,13 +60,13 @@ Bundle (<| (bundle.prefix "frac") (|> bundle.empty - (bundle.install "+" (binary (product.uncurry _.+))) - (bundle.install "-" (binary (product.uncurry _.-))) - (bundle.install "*" (binary (product.uncurry _.*))) - (bundle.install "/" (binary (product.uncurry _./))) - (bundle.install "%" (binary (product.uncurry _.%))) - (bundle.install "=" (binary (product.uncurry _.=))) - (bundle.install "<" (binary (product.uncurry _.<))) + (bundle.install "+" (binary (product.uncurried _.+))) + (bundle.install "-" (binary (product.uncurried _.-))) + (bundle.install "*" (binary (product.uncurried _.*))) + (bundle.install "/" (binary (product.uncurried _./))) + (bundle.install "%" (binary (product.uncurried _.%))) + (bundle.install "=" (binary (product.uncurried _.=))) + (bundle.install "<" (binary (product.uncurried _.<))) (bundle.install "int" (unary _.intval/1)) (bundle.install "encode" (unary _.strval/1)) (bundle.install "decode" (unary (|>> _.floatval/1 ///runtime.some))) @@ -80,9 +80,9 @@ Bundle (<| (bundle.prefix "text") (|> bundle.empty - (bundle.install "=" (binary (product.uncurry _.=))) - (bundle.install "<" (binary (product.uncurry _.<))) - (bundle.install "concat" (binary (product.uncurry _.concat))) + (bundle.install "=" (binary (product.uncurried _.=))) + (bundle.install "<" (binary (product.uncurried _.<))) + (bundle.install "concat" (binary (product.uncurried _.concat))) (bundle.install "index" (trinary text//index)) (bundle.install "size" (unary _.strlen/1)) (bundle.install "char" (binary (function (text//char [text idx]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux index f1c4c0eb6..62238c960 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux @@ -91,12 +91,12 @@ code) (do meta.monad [runtime_id meta.seed] - (macro.with_gensyms [g!_] + (macro.with_identifiers [g!_] (let [runtime (code.local_identifier (///reference.artifact [..module_id runtime_id])) runtime_name (` (_.constant (~ (code.text (%.code runtime)))))] (case declaration (#.Left name) - (macro.with_gensyms [g!_] + (macro.with_identifiers [g!_] (let [g!name (code.local_identifier name)] (in (list (` (def: .public (~ g!name) Var @@ -109,7 +109,7 @@ (_.define (~ g!name) (~ code)))))))))) (#.Right [name inputs]) - (macro.with_gensyms [g!_] + (macro.with_identifiers [g!_] (let [g!name (code.local_identifier name) inputsC (list\map code.local_identifier inputs) inputs_typesC (list\map (function.constant (` _.Expression)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux index 137623c8a..b00d65682 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux @@ -34,7 +34,7 @@ [meta [archive (#+ Archive)]]]]]]]) -(def: .public (gensym prefix) +(def: .public (identifier prefix) (-> Text (Operation SVar)) (///////phase\map (|>> %.nat (format prefix) _.var) /////generation.next)) @@ -279,7 +279,7 @@ (do ! [pre! (recur preP) post! (recur postP) - g!once (..gensym "once")] + g!once (..identifier "once")] (in (..alternation in_closure? g!once pre! post!))) _ @@ -289,7 +289,7 @@ (-> Bit Phase! Phase Archive Path (Operation (Statement Any))) (do ///////phase.monad [pattern_matching! (pattern_matching' in_closure? statement expression archive pathP) - g!once (..gensym "once")] + g!once (..identifier "once")] (in ($_ _.then (..with_looping in_closure? g!once pattern_matching!) 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 4332539e5..6739e6ec5 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 @@ -110,7 +110,7 @@ (Generator! (List Synthesis)) (do {! ///////phase.monad} [offset /////generation.anchor - @temp (//case.gensym "lux_recur_values") + @temp (//case.identifier "lux_recur_values") argsO+ (monad.map ! (expression archive) argsS+) .let [re_binds (|> argsO+ list.enumeration diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux index 2cd100ce9..360d33002 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux @@ -127,7 +127,7 @@ code) (case declaration (#.Left name) - (macro.with_gensyms [g!_] + (macro.with_identifiers [g!_] (let [nameC (code.local_identifier name) code_nameC (code.local_identifier (format "@" name)) runtime_nameC (` (runtime_name (~ (code.text name))))] @@ -139,7 +139,7 @@ (_.set (list (~ g!_)) (~ code)))))))))) (#.Right [name inputs]) - (macro.with_gensyms [g!_] + (macro.with_identifiers [g!_] (let [nameC (code.local_identifier name) code_nameC (code.local_identifier (format "@" name)) runtime_nameC (` (runtime_name (~ (code.text name)))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux index cdbaf6e1f..859744980 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux @@ -43,7 +43,7 @@ ... true loop _ (do {! ///////phase.monad} - [$scope (\ ! map _.var (/////generation.gensym "loop_scope")) + [$scope (\ ! map _.var (/////generation.identifier "loop_scope")) initsO+ (monad.map ! (expression archive) initsS+) bodyO (/////generation.with_anchor $scope (expression archive bodyS))] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux index c257a2c0c..18de8ffef 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux @@ -10,7 +10,7 @@ [number] (coll [list "list/" Functor<List>] (dictionary ["dict" unordered #+ Dict]))) - [macro #+ with_gensyms] + [macro #+ with_identifiers] (macro [code] ["s" syntax #+ syntax:]) [host]) @@ -63,9 +63,9 @@ " Actual: " (|> actual .int %i))) (syntax: (arity: {name s.local_identifier} {arity s.nat}) - (with_gensyms [g!_ g!proc g!name g!translate g!inputs] + (with_identifiers [g!_ g!proc g!name g!translate g!inputs] (do {@ macro.monad} - [g!input+ (monad.seq @ (list.repeated arity (macro.gensym "input")))] + [g!input+ (monad.seq @ (list.repeated arity (macro.identifier "input")))] (in (list (` (def: .public ((~ (code.local_identifier name)) (~ g!proc)) (-> (-> (..Vector (~ (code.nat arity)) Expression) Expression) (-> Text ..Proc)) @@ -123,7 +123,7 @@ (-> Text Proc) (function (_ proc_name) (function (_ translate inputsS) - (case (s.run inputsS ($_ p.seq s.nat (s.tuple (p.many s.any)) s.any)) + (case (s.result inputsS ($_ p.seq s.nat (s.tuple (p.many s.any)) s.any)) (#e.Success [offset initsS+ bodyS]) (loopT.translate_loop translate offset initsS+ bodyS) 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 b416fc128..1bcb51d73 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 @@ -94,7 +94,7 @@ code) (do meta.monad [runtime_id meta.seed] - (macro.with_gensyms [g!_] + (macro.with_identifiers [g!_] (let [runtime (code.local_identifier (///reference.artifact [..module_id runtime_id])) runtime_name (` (_.var (~ (code.text (%.code runtime)))))] (case declaration diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux index 253bec114..dbdb0b1d0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux @@ -36,7 +36,7 @@ [meta [archive (#+ Archive)]]]]]]]) -(def: .public (gensym prefix) +(def: .public (identifier prefix) (-> Text (Operation LVar)) (///////phase\map (|>> %.nat (format prefix) _.local) /////generation.next)) @@ -322,8 +322,8 @@ (do ///////phase.monad [pre! (recur preP) post! (recur postP) - g!once (..gensym "once") - g!continue? (..gensym "continue")] + g!once (..identifier "once") + g!continue? (..identifier "continue")] (in (..alternation in_closure? g!once g!continue? pre! post!))) _ @@ -333,8 +333,8 @@ (-> Bit (Generator! Path)) (do ///////phase.monad [pattern_matching! (pattern_matching' in_closure? statement expression archive pathP) - g!once (..gensym "once") - g!continue? (..gensym "continue")] + g!once (..identifier "once") + g!continue? (..identifier "continue")] (in ($_ _.then (..with_looping in_closure? g!once g!continue? pattern_matching!) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux index 9e2a43500..9fe46c86d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux @@ -84,7 +84,7 @@ (Generator! (List Synthesis)) (do {! ///////phase.monad} [offset /////generation.anchor - @temp (//case.gensym "lux_recur_values") + @temp (//case.identifier "lux_recur_values") argsO+ (monad.map ! (expression archive) argsS+) .let [re_binds (|> argsO+ list.enumeration 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 9de984f61..424d8b14b 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 @@ -92,12 +92,12 @@ code) (do meta.monad [runtime_id meta.seed] - (macro.with_gensyms [g!_] + (macro.with_identifiers [g!_] (let [runtime (code.local_identifier (///reference.artifact [..module_id runtime_id])) runtime_name (` (_.local (~ (code.text (%.code runtime)))))] (case declaration (#.Left name) - (macro.with_gensyms [g!_] + (macro.with_identifiers [g!_] (let [g!name (code.local_identifier name)] (in (list (` (def: .public (~ g!name) LVar (~ runtime_name))) (` (def: (~ (code.local_identifier (format "@" name))) @@ -107,7 +107,7 @@ (_.set (list (~ g!name)) (~ code)))))))))) (#.Right [name inputs]) - (macro.with_gensyms [g!_] + (macro.with_identifiers [g!_] (let [g!name (code.local_identifier name) inputsC (list\map code.local_identifier inputs) inputs_typesC (list\map (function.constant (` _.Expression)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux index 95e2f1edb..c6d6f4da8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux @@ -15,7 +15,7 @@ [collection ["." list ("#\." functor)] ["dict" dictionary (#+ Dictionary)]]] - ["." macro (#+ with_gensyms) + ["." macro (#+ with_identifiers) ["." code] [syntax (#+ syntax:)]] [target @@ -38,9 +38,9 @@ (type: .public Variadic (-> (List Expression) Computation)) (syntax: (arity: {name s.local_identifier} {arity s.nat}) - (with_gensyms [g!_ g!extension g!name g!phase g!inputs] + (with_identifiers [g!_ g!extension g!name g!phase g!inputs] (do {! macro.monad} - [g!input+ (monad.seq ! (list.repeated arity (macro.gensym "input")))] + [g!input+ (monad.seq ! (list.repeated arity (macro.identifier "input")))] (in (list (` (def: .public ((~ (code.local_identifier name)) (~ g!extension)) (-> (-> (..Vector (~ (code.nat arity)) Expression) Computation) Handler) @@ -73,7 +73,7 @@ (def: bundle::lux Bundle (|> bundle.empty - (bundle.install "is?" (binary (product.uncurry _.eq?/2))) + (bundle.install "is?" (binary (product.uncurried _.eq?/2))) (bundle.install "try" (unary ///runtime.lux//try)))) (template [<name> <op>] @@ -189,7 +189,7 @@ (|> bundle.empty (bundle.install "=" (binary text::=)) (bundle.install "<" (binary text::<)) - (bundle.install "concat" (binary (product.uncurry _.string_append/2))) + (bundle.install "concat" (binary (product.uncurried _.string_append/2))) (bundle.install "size" (unary _.string_length/1)) (bundle.install "char" (binary text::char)) (bundle.install "clip" (trinary text::clip))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux index e61519d16..f5f293f92 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux @@ -76,7 +76,7 @@ code) (do meta.monad [runtime_id meta.seed] - (macro.with_gensyms [g!_] + (macro.with_identifiers [g!_] (let [runtime (code.local_identifier (///reference.artifact [..module_id runtime_id])) runtime_name (` (_.var (~ (code.text (%.code runtime)))))] (case declaration 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 4adb10f57..2b9202239 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 @@ -7,7 +7,6 @@ [pipe (#+ case>)] ["." try]] [data - ["." maybe] [collection ["." list ("#\." functor)] ["." dictionary (#+ Dictionary)]]]]] @@ -86,7 +85,7 @@ (/.with_currying? false (function (_ state) (|> (//extension.apply archive optimization [name args]) - (phase.run' state) + (phase.result' state) (case> (#try.Success output) (#try.Success output) @@ -94,7 +93,7 @@ (|> args (monad.map phase.monad optimization') (phase\map (|>> [name] #/.Extension)) - (phase.run' state)))))) + (phase.result' state)))))) ))) (def: .public (phase archive analysis) 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 46189fb26..875b2ca60 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 @@ -227,7 +227,7 @@ (-> Phase Archive Synthesis Match (Operation Synthesis)) (do {! ///.monad} [headSP (path archive synthesize headP headA) - tailSP+ (monad.map ! (product.uncurry (path archive synthesize)) tailPA+)] + tailSP+ (monad.map ! (product.uncurried (path archive synthesize)) tailPA+)] (in (/.branch/case [input (list\fold weave headSP tailSP+)])))) (template: (!masking <variable> <output>) 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 83822639e..7becfbe4d 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 @@ -6,9 +6,9 @@ ["." enum]] [control [pipe (#+ case>)] + ["." maybe ("#\." functor)] ["." exception (#+ exception:)]] [data - ["." maybe ("#\." functor)] ["." text ["%" format (#+ format)]] [collection 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 23227e4df..d9890dbc9 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 @@ -3,8 +3,9 @@ [lux #* [abstract ["." monad (#+ do)]] + [control + ["." maybe ("#\." monad)]] [data - ["." maybe ("#\." monad)] [collection ["." list]]] [math 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 6ba15c700..41d618cc3 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 @@ -4,11 +4,11 @@ [abstract ["." monad (#+ do)]] [control + ["." maybe ("#\." functor)] ["." try (#+ Try)] ["." exception (#+ exception:)]] [data ["." product] - ["." maybe ("#\." functor)] ["." text ["%" format]] [collection @@ -312,7 +312,7 @@ (list\map product.left))]] (in [(list\fold dictionary.remove redundancy (set.list bindings)) (|> redundants - (list.sort n.>) + (list.sorted n.>) (list\fold (..remove_local_from_path ..remove_local) (#/.Seq pre post)))])) (#/.Then then) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/program.lux b/stdlib/source/library/lux/tool/compiler/language/lux/program.lux index af17d9e15..365f9e804 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/program.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/program.lux @@ -4,11 +4,11 @@ [abstract ["." monad (#+ do)]] [control + ["." maybe] ["." try (#+ Try)] ["." exception (#+ exception:)]] [data ["." product] - ["." maybe] [text ["%" format (#+ format)]] [collection 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 6615d49a9..6db98721b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux @@ -31,11 +31,11 @@ [abstract monad] [control + ["." maybe] ["." exception (#+ exception:)] [parser [text (#+ Offset)]]] [data - ["." maybe] ["." text ["%" format (#+ format)]] [collection 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 0f02d37be..806fdc3c9 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux @@ -7,11 +7,11 @@ [hash (#+ Hash)]] [control [pipe (#+ case>)] + ["." maybe] ["." exception (#+ exception:)]] [data ["." sum] ["." product] - ["." maybe] ["." bit ("#\." equivalence)] ["." text ("#\." equivalence) ["%" format (#+ Format format)]] diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux index e42b2d2c5..348a7ced9 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux @@ -239,7 +239,7 @@ (#.Some _) (#.Some [module id]) #.None #.None))) [version next] - (binary.run ..writer)))) + (binary.result ..writer)))) (exception: .public (version_mismatch {expected Version} {actual Version}) (exception.report @@ -272,7 +272,7 @@ (def: .public (import expected binary) (-> Version Binary (Try Archive)) (do try.monad - [[actual next reservations] (<binary>.run ..reader binary) + [[actual next reservations] (<binary>.result ..reader binary) _ (exception.assertion ..version_mismatch [expected actual] (n\= expected actual)) _ (exception.assertion ..corrupt_data [] diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux index 4a9773f6c..66a903ca1 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux @@ -4,12 +4,12 @@ [abstract ["." monad (#+ do)]] [control + ["." maybe ("#\." functor)] ["." try (#+ Try)] ["." state] ["." function ["." memo (#+ Memo)]]] [data - ["." maybe ("#\." functor)] ["." text ["%" format (#+ format)]] [collection @@ -87,7 +87,7 @@ (let [ancestry (..ancestry archive)] (|> ancestry dictionary.keys - (list.sort (..dependency? ancestry)) + (list.sorted (..dependency? ancestry)) (monad.map try.monad (function (_ module) (do try.monad 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 21d657352..a87c3840b 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux @@ -412,7 +412,7 @@ (monad.map ! (function (_ [module_name module_id]) (do ! [data (..read_module_descriptor fs static module_id) - [descriptor document] (async\in (<binary>.run ..parser data))] + [descriptor document] (async\in (<binary>.result ..parser data))] (if (text\= archive.runtime_module module_name) (in [true [module_name [module_id [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 a36b2fda0..993b2264d 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux @@ -5,10 +5,10 @@ [abstract ["." monad (#+ Monad do)]] [control + ["." maybe ("#\." functor)] ["." try (#+ Try)]] [data ["." binary (#+ Binary)] - ["." maybe ("#\." functor)] ["." text ["%" format (#+ format)]] [collection @@ -162,7 +162,7 @@ (def: (read_jar_entry_with_unknown_size input) (-> java/util/jar/JarInputStream [Nat Binary]) - (let [chunk (binary.create ..mebi_byte) + (let [chunk (binary.empty ..mebi_byte) chunk_size (.int ..mebi_byte) buffer (java/io/ByteArrayOutputStream::new chunk_size)] (loop [so_far 0] @@ -178,7 +178,7 @@ (def: (read_jar_entry_with_known_size expected_size input) (-> Nat java/util/jar/JarInputStream [Nat Binary]) - (let [buffer (binary.create expected_size)] + (let [buffer (binary.empty expected_size)] (loop [so_far 0] (let [so_far' (|> input (java/io/InputStream::read buffer (.int so_far) (.int (n.- so_far expected_size))) 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 f3bfea5b0..42a1a378c 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux @@ -129,4 +129,4 @@ entries (monad.map ! (..write_module now mapping) order)] (in (|> entries row.of_list - (binary.run tar.writer)))))) + (binary.result tar.writer)))))) diff --git a/stdlib/source/library/lux/tool/compiler/phase.lux b/stdlib/source/library/lux/tool/compiler/phase.lux index 73aef8bcd..5bfdac402 100644 --- a/stdlib/source/library/lux/tool/compiler/phase.lux +++ b/stdlib/source/library/lux/tool/compiler/phase.lux @@ -34,12 +34,12 @@ (type: .public (Phase s i o) (-> Archive i (Operation s o))) -(def: .public (run' state operation) +(def: .public (result' state operation) (All [s o] (-> s (Operation s o) (Try [s o]))) (operation state)) -(def: .public (run state operation) +(def: .public (result state operation) (All [s o] (-> s (Operation s o) (Try o))) (|> state @@ -107,10 +107,10 @@ (-> Name Text (Operation s a) (Operation s a))) (do ..monad [_ (in []) - .let [pre (io.run instant.now)] + .let [pre (io.run! instant.now)] output operation .let [_ (|> instant.now - io.run + io.run! instant.relative (duration.difference (instant.relative pre)) %.duration |