aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/tool/compiler
diff options
context:
space:
mode:
authorEduardo Julian2021-08-16 01:12:01 -0400
committerEduardo Julian2021-08-16 01:12:01 -0400
commit3289b9dcf9d5d1c1e5c380e3185065c8fd32535f (patch)
treefc2f67581dd7b1d72c20217a95e031187a375bc5 /stdlib/source/library/lux/tool/compiler
parent6fd22846f21b8b70b7867e989109d14a366c0a3e (diff)
Made extension-definition macros specify their bindings the same way as syntax:.
Diffstat (limited to '')
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/init.lux32
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/platform.lux28
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux16
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/directive.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux26
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux31
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/type.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux84
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux16
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux76
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux46
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux72
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux36
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux18
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial/count.lux7
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux20
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux16
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux78
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux14
-rw-r--r--stdlib/source/library/lux/tool/compiler/phase.lux6
43 files changed, 377 insertions, 369 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux
index 6af02e080..e8b91db8c 100644
--- a/stdlib/source/library/lux/tool/compiler/default/init.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/init.lux
@@ -127,7 +127,7 @@
(do ///phase.monad
[.let [module (get@ #///.module input)]
_ (///directive.set_current_module module)]
- (///directive.lift_analysis
+ (///directive.lifted_analysis
(do {! ///phase.monad}
[_ (module.create hash module)
_ (monad.map ! module.import dependencies)
@@ -141,15 +141,15 @@
(All [anchor expression directive]
(///directive.Operation anchor expression directive [.Module (Payload directive)])))
(do ///phase.monad
- [_ (///directive.lift_analysis
+ [_ (///directive.lifted_analysis
(module.set_compiled module))
analysis_module (<| (: (Operation .Module))
- ///directive.lift_analysis
- extension.lift
+ ///directive.lifted_analysis
+ extension.lifted
meta.current_module)
- final_buffer (///directive.lift_generation
+ final_buffer (///directive.lifted_generation
///generation.buffer)
- final_registry (///directive.lift_generation
+ final_registry (///directive.lifted_generation
///generation.get_registry)]
(in [analysis_module [final_buffer
final_registry]])))
@@ -162,9 +162,9 @@
(///directive.Operation anchor expression directive
(Payload directive)))))
(do ///phase.monad
- [buffer (///directive.lift_generation
+ [buffer (///directive.lifted_generation
///generation.buffer)
- registry (///directive.lift_generation
+ registry (///directive.lifted_generation
///generation.get_registry)]
(in [buffer registry])))
@@ -177,9 +177,9 @@
[Requirements (Payload directive)]))))
(do ///phase.monad
[.let [[pre_buffer pre_registry] pre_payoad]
- _ (///directive.lift_generation
+ _ (///directive.lifted_generation
(///generation.set_buffer pre_buffer))
- _ (///directive.lift_generation
+ _ (///directive.lifted_generation
(///generation.set_registry pre_registry))
requirements (let [execute! (directiveP.phase expander)]
(execute! archive code))
@@ -193,7 +193,7 @@
(///directive.Operation anchor expression directive
[Source Requirements (Payload directive)]))))
(do ///phase.monad
- [[source code] (///directive.lift_analysis
+ [[source code] (///directive.lifted_analysis
(..read source reader))
[requirements post_payload] (process_directive archive expander pre_payload code)]
(in [source requirements post_payload])))
@@ -205,7 +205,7 @@
(///directive.Operation anchor expression directive
(Maybe [Source Requirements (Payload directive)])))))
(do ///phase.monad
- [reader (///directive.lift_analysis
+ [reader (///directive.lifted_analysis
(..reader module aliases source))]
(function (_ state)
(case (///phase.result' state (..iteration' archive expander reader source pre_payload))
@@ -273,12 +273,12 @@
(recur (<| (///phase.result' state)
(do {! ///phase.monad}
[analysis_module (<| (: (Operation .Module))
- ///directive.lift_analysis
- extension.lift
+ ///directive.lifted_analysis
+ extension.lifted
meta.current_module)
- _ (///directive.lift_generation
+ _ (///directive.lifted_generation
(///generation.set_buffer temporary_buffer))
- _ (///directive.lift_generation
+ _ (///directive.lifted_generation
(///generation.set_registry temporary_registry))
_ (|> requirements
(get@ #///directive.referrals)
diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux
index f19ec248c..53cb07e22 100644
--- a/stdlib/source/library/lux/tool/compiler/default/platform.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux
@@ -150,14 +150,14 @@
(///directive.Operation <type_vars>
[Archive [Descriptor (Document .Module) Output]])))
(do ///phase.monad
- [[registry payload] (///directive.lift_generation
+ [[registry payload] (///directive.lifted_generation
(..compile_runtime! platform))
.let [[descriptor document] [(..runtime_descriptor registry) ..runtime_document]]
- archive (///phase.lift (if (archive.reserved? archive archive.runtime_module)
- (archive.has archive.runtime_module [descriptor document payload] archive)
- (do try.monad
- [[_ archive] (archive.reserve archive.runtime_module archive)]
- (archive.has archive.runtime_module [descriptor document payload] archive))))]
+ archive (///phase.lifted (if (archive.reserved? archive archive.runtime_module)
+ (archive.has archive.runtime_module [descriptor document payload] archive)
+ (do try.monad
+ [[_ archive] (archive.reserve archive.runtime_module archive)]
+ (archive.has archive.runtime_module [descriptor document payload] archive))))]
(in [archive [descriptor document payload]])))
(def: (initialize_state extender
@@ -182,13 +182,13 @@
(///directive.Operation <type_vars> Any)
(do ///phase.monad
- [_ (///directive.lift_analysis
+ [_ (///directive.lifted_analysis
(///analysis.install analysis_state))
- _ (///directive.lift_analysis
+ _ (///directive.lifted_analysis
(extension.with extender analysers))
- _ (///directive.lift_synthesis
+ _ (///directive.lifted_synthesis
(extension.with extender synthesizers))
- _ (///directive.lift_generation
+ _ (///directive.lifted_generation
(extension.with extender (:expected generators)))
_ (extension.with extender (:expected directives))]
(in [])))
@@ -201,7 +201,7 @@
(let [phase_wrapper (get@ #phase_wrapper platform)]
(|> archive
phase_wrapper
- ///directive.lift_generation
+ ///directive.lifted_generation
(///phase.result' state))))
(def: (complete_extensions host_directive_bundle phase_wrapper [analysers synthesizers generators directives])
@@ -520,7 +520,7 @@
(-> Module <State+> <State+>))
(|> (///directive.set_current_module module)
(///phase.result' state)
- try.assumed
+ try.trusted
product.left))
(def: .public (compile import static expander platform compilation context)
@@ -586,7 +586,7 @@
.let [archive (|> archive,document+
(list\map product.left)
(list\fold archive.merged archive))]]
- (in [archive (try.assumed
+ (in [archive (try.trusted
(..updated_state archive state))])))
(async\in (exception.except ..cannot_import_twice [module duplicates])))]
(case ((get@ #///.process compilation)
@@ -594,7 +594,7 @@
... TODO: The context shouldn't need to be re-set either.
(|> (///directive.set_current_module module)
(///phase.result' state)
- try.assumed
+ try.trusted
product.left)
archive)
(#try.Success [state more|done])
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 eb325ddd0..571185dee 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
@@ -355,7 +355,7 @@
(#Tuple members)
(|> members
(list\map %analysis)
- (text.join_with " ")
+ (text.interposed " ")
(text.enclosed ["[" "]"])))
(#Reference reference)
@@ -369,7 +369,7 @@
(format " ")
(format (|> environment
(list\map %analysis)
- (text.join_with " ")
+ (text.interposed " ")
(text.enclosed ["[" "]"])))
(text.enclosed ["(" ")"]))
@@ -378,13 +378,13 @@
..application
#.Item
(list\map %analysis)
- (text.join_with " ")
+ (text.interposed " ")
(text.enclosed ["(" ")"]))
(#Extension name parameters)
(|> parameters
(list\map %analysis)
- (text.join_with " ")
+ (text.interposed " ")
(format (%.text name) " ")
(text.enclosed ["(" ")"]))))
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 5ae124d96..1859802d6 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
@@ -46,12 +46,12 @@
(do phase.monad
[exprA (type.with_type type
(analyze archive exprC))
- module (extensionP.lift
+ module (extensionP.lifted
meta.current_module_name)]
- (phase.lift (do try.monad
- [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)))))))))
+ (phase.lifted (do try.monad
+ [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/directive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux
index 5383d2ae4..478697fd4 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux
@@ -80,18 +80,18 @@
(Operation anchor expression directive output)))
(|>> (phase.sub [(get@ [<component> #..state])
(set@ [<component> #..state])])
- extension.lift))]
+ extension.lifted))]
- [lift_analysis #..analysis analysis.Operation]
- [lift_synthesis #..synthesis synthesis.Operation]
- [lift_generation #..generation (generation.Operation anchor expression directive)]
+ [lifted_analysis #..analysis analysis.Operation]
+ [lifted_synthesis #..synthesis synthesis.Operation]
+ [lifted_generation #..generation (generation.Operation anchor expression directive)]
)
(def: .public (set_current_module module)
(All [anchor expression directive]
(-> Module (Operation anchor expression directive Any)))
(do phase.monad
- [_ (..lift_analysis
+ [_ (..lifted_analysis
(analysis.set_current_module module))]
- (..lift_generation
+ (..lifted_generation
(generation.enter_module module))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux
index b9b230b42..c8cfe9c0e 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux
@@ -116,11 +116,11 @@
(case functionA
(#/.Reference (#reference.Constant def_name))
(do !
- [?macro (//extension.lift (meta.macro def_name))]
+ [?macro (//extension.lifted (meta.macro def_name))]
(case ?macro
(#.Some macro)
(do !
- [expansion (//extension.lift (/macro.expand_one expander def_name macro argsC+))]
+ [expansion (//extension.lifted (/macro.expand_one expander def_name macro argsC+))]
(compile archive expansion))
_
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 2188bb54a..9463eeb8f 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
@@ -102,7 +102,7 @@
(do ///.monad
[[var_id varT] (//type.with_env
check.var)]
- (recur envs (maybe.assume (type.applied (list varT) caseT))))
+ (recur envs (maybe.trusted (type.applied (list varT) caseT))))
(#.Apply inputT funcT)
(.case funcT
@@ -277,7 +277,7 @@
[[ex_id exT] (//type.with_env
check.existential)]
(analyse_pattern num_tags
- (maybe.assume (type.applied (list exT) inputT'))
+ (maybe.trusted (type.applied (list exT) inputT'))
pattern
next))
@@ -287,8 +287,8 @@
(^ [location (#.Form (list& [_ (#.Tag tag)] values))])
(/.with_location location
(do ///.monad
- [tag (///extension.lift (meta.normal tag))
- [idx group variantT] (///extension.lift (meta.tag tag))
+ [tag (///extension.lifted (meta.normal tag))
+ [idx group variantT] (///extension.lifted (meta.tag tag))
_ (//type.with_env
(check.check inputT variantT))
.let [[lefts right?] (/.choice (list.size group) idx)]]
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 996272df7..25c85514e 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
@@ -80,7 +80,7 @@
dictionary.entries
(list\map (function (_ [idx coverage])
(format (%.nat idx) " " (%coverage coverage))))
- (text.join_with " ")
+ (text.interposed " ")
(text.enclosed ["{" "}"])
(format (%.nat (..cases ?max_cases)) " ")
(text.enclosed ["(#Variant " ")"]))
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 8063f450d..69e75f374 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
@@ -40,12 +40,12 @@
list.enumeration
(list\map (.function (_ [idx argC])
(format (%.nat idx) " " (%.code argC))))
- (text.join_with text.new_line))]))
+ (text.interposed text.new_line))]))
(def: .public (function analyse function_name arg_name archive body)
(-> Phase Text Text Phase)
(do {! ///.monad}
- [functionT (///extension.lift meta.expected_type)]
+ [functionT (///extension.lifted meta.expected_type)]
(loop [expectedT functionT]
(/.with_stack ..cannot_analyse [expectedT function_name arg_name body]
(case expectedT
@@ -64,7 +64,7 @@
[(<tag> _)
(do !
[[_ instanceT] (//type.with_env <instancer>)]
- (recur (maybe.assume (type.applied (list instanceT) expectedT))))])
+ (recur (maybe.trusted (type.applied (list instanceT) expectedT))))])
([#.UnivQ check.existential]
[#.ExQ check.var])
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 af25a5856..6282980be 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
@@ -96,7 +96,7 @@
(def: new_named_type
(Operation Type)
(do ///.monad
- [location (///extension.lift meta.location)
+ [location (///extension.lifted meta.location)
[ex_id _] (//type.with_env check.existential)]
(in (named_type location ex_id))))
@@ -123,13 +123,13 @@
(#.UnivQ _)
(do ///.monad
[[var_id varT] (//type.with_env check.var)]
- (general archive analyse (maybe.assume (type.applied (list varT) inferT)) args))
+ (general archive analyse (maybe.trusted (type.applied (list varT) inferT)) args))
(#.ExQ _)
(do {! ///.monad}
[[var_id varT] (//type.with_env check.var)
output (general archive analyse
- (maybe.assume (type.applied (list varT) inferT))
+ (maybe.trusted (type.applied (list varT) inferT))
args)
bound? (//type.with_env
(check.bound? var_id))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux
index db51c3d77..d5e2fd691 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux
@@ -36,7 +36,7 @@
(template [<name>]
[(exception: .public (<name> {tags (List Text)} {owner Type})
(exception.report
- ["Tags" (text.join_with " " tags)]
+ ["Tags" (text.interposed " " tags)]
["Type" (%.type owner)]))]
[cannot_declare_tags_for_unnamed_type]
@@ -80,7 +80,7 @@
(def: .public (set_annotations annotations)
(-> Code (Operation Any))
- (///extension.lift
+ (///extension.lifted
(do ///.monad
[self_name meta.current_module_name
self meta.current_module]
@@ -97,7 +97,7 @@
(def: .public (import module)
(-> Text (Operation Any))
- (///extension.lift
+ (///extension.lifted
(do ///.monad
[self_name meta.current_module_name]
(function (_ state)
@@ -112,7 +112,7 @@
(def: .public (alias alias module)
(-> Text Text (Operation Any))
- (///extension.lift
+ (///extension.lifted
(do ///.monad
[self_name meta.current_module_name]
(function (_ state)
@@ -124,7 +124,7 @@
(def: .public (exists? module)
(-> Text (Operation Bit))
- (///extension.lift
+ (///extension.lifted
(function (_ state)
(|> state
(get@ #.modules)
@@ -134,7 +134,7 @@
(def: .public (define name definition)
(-> Text Global (Operation Any))
- (///extension.lift
+ (///extension.lifted
(do ///.monad
[self_name meta.current_module_name
self meta.current_module]
@@ -155,7 +155,7 @@
(def: .public (create hash name)
(-> Nat Text (Operation Any))
- (///extension.lift
+ (///extension.lifted
(function (_ state)
(#try.Success [(update@ #.modules
(plist.has name (..empty hash))
@@ -168,13 +168,13 @@
[_ (create hash name)
output (/.with_current_module name
action)
- module (///extension.lift (meta.module name))]
+ module (///extension.lifted (meta.module name))]
(in [module output])))
(template [<setter> <asker> <tag>]
[(def: .public (<setter> module_name)
(-> Text (Operation Any))
- (///extension.lift
+ (///extension.lifted
(function (_ state)
(case (|> state (get@ #.modules) (plist.value module_name))
(#.Some module)
@@ -194,7 +194,7 @@
(def: .public (<asker> module_name)
(-> Text (Operation Bit))
- (///extension.lift
+ (///extension.lifted
(function (_ state)
(case (|> state (get@ #.modules) (plist.value module_name))
(#.Some module)
@@ -214,7 +214,7 @@
(template [<name> <tag> <type>]
[(def: (<name> module_name)
(-> Text (Operation <type>))
- (///extension.lift
+ (///extension.lifted
(function (_ state)
(case (|> state (get@ #.modules) (plist.value module_name))
(#.Some module)
@@ -246,7 +246,7 @@
(def: .public (declare_tags tags exported? type)
(-> (List Tag) Bit Type (Operation Any))
(do ///.monad
- [self_name (///extension.lift meta.current_module_name)
+ [self_name (///extension.lifted meta.current_module_name)
[type_module type_name] (case type
(#.Named type_name _)
(in type_name)
@@ -256,7 +256,7 @@
_ (ensure_undeclared_tags self_name tags)
_ (///.assertion cannot_declare_tags_for_foreign_type [tags type]
(text\= self_name type_module))]
- (///extension.lift
+ (///extension.lifted
(function (_ state)
(case (|> state (get@ #.modules) (plist.value self_name))
(#.Some module)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux
index 92e43368e..92a7a8f9c 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux
@@ -33,7 +33,7 @@
(-> Name (Operation Analysis))
(with_expansions [<return> (in (|> def_name ///reference.constant #/.Reference))]
(do {! ///.monad}
- [constant (///extension.lift (meta.definition def_name))]
+ [constant (///extension.lifted (meta.definition def_name))]
(case constant
(#.Left real_def_name)
(definition real_def_name)
@@ -41,13 +41,13 @@
(#.Right [exported? actualT def_anns _])
(do !
[_ (//type.infer actualT)
- (^@ def_name [::module ::name]) (///extension.lift (meta.normal def_name))
- current (///extension.lift meta.current_module_name)]
+ (^@ def_name [::module ::name]) (///extension.lifted (meta.normal def_name))
+ current (///extension.lifted meta.current_module_name)]
(if (text\= current ::module)
<return>
(if exported?
(do !
- [imported! (///extension.lift (meta.imported_by? ::module current))]
+ [imported! (///extension.lifted (meta.imported_by? ::module current))]
(if imported!
<return>
(/.except foreign_module_has_not_been_imported [current ::module])))
@@ -78,7 +78,7 @@
#.None
(do !
- [this_module (///extension.lift meta.current_module_name)]
+ [this_module (///extension.lifted meta.current_module_name)]
(definition [this_module simple_name]))))
_
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 98c36ec05..052173d1f 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
@@ -78,7 +78,7 @@
(def: .public (find name)
(-> Text (Operation (Maybe [Type Variable])))
- (///extension.lift
+ (///extension.lifted
(function (_ state)
(let [[inner outer] (|> state
(get@ #.scopes)
@@ -183,7 +183,7 @@
(def: .public next_local
(Operation Register)
- (///extension.lift
+ (///extension.lifted
(function (_ state)
(case (get@ #.scopes state)
(#.Item top _)
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 8f254c5d6..56924a102 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
@@ -95,7 +95,7 @@
(let [tag (/.tag lefts right?)]
(function (recur valueC)
(do {! ///.monad}
- [expectedT (///extension.lift meta.expected_type)
+ [expectedT (///extension.lifted meta.expected_type)
expectedT' (//type.with_env
(check.clean expectedT))]
(/.with_stack ..cannot_analyse_variant [expectedT' tag valueC]
@@ -135,7 +135,7 @@
[(<tag> _)
(do !
[[instance_id instanceT] (//type.with_env <instancer>)]
- (//type.with_type (maybe.assume (type.applied (list instanceT) expectedT))
+ (//type.with_type (maybe.trusted (type.applied (list instanceT) expectedT))
(recur valueC)))])
([#.UnivQ check.existential]
[#.ExQ check.var])
@@ -168,7 +168,7 @@
(def: (typed_product archive analyse members)
(-> Archive Phase (List Code) (Operation Analysis))
(do {! ///.monad}
- [expectedT (///extension.lift meta.expected_type)
+ [expectedT (///extension.lifted meta.expected_type)
membersA+ (: (Operation (List Analysis))
(loop [membersT+ (type.flat_tuple expectedT)
membersC+ members]
@@ -195,7 +195,7 @@
(def: .public (product archive analyse membersC)
(-> Archive Phase (List Code) (Operation Analysis))
(do {! ///.monad}
- [expectedT (///extension.lift meta.expected_type)]
+ [expectedT (///extension.lifted meta.expected_type)]
(/.with_stack ..cannot_analyse_tuple [expectedT membersC]
(case expectedT
(#.Product _)
@@ -228,7 +228,7 @@
[(<tag> _)
(do !
[[instance_id instanceT] (//type.with_env <instancer>)]
- (//type.with_type (maybe.assume (type.applied (list instanceT) expectedT))
+ (//type.with_type (maybe.trusted (type.applied (list instanceT) expectedT))
(product archive analyse membersC)))])
([#.UnivQ check.existential]
[#.ExQ check.var])
@@ -262,17 +262,17 @@
(def: .public (tagged_sum analyse tag archive valueC)
(-> Phase Name Phase)
(do {! ///.monad}
- [tag (///extension.lift (meta.normal tag))
- [idx group variantT] (///extension.lift (meta.tag tag))
+ [tag (///extension.lifted (meta.normal tag))
+ [idx group variantT] (///extension.lifted (meta.tag tag))
.let [case_size (list.size group)
[lefts right?] (/.choice case_size idx)]
- expectedT (///extension.lift meta.expected_type)]
+ expectedT (///extension.lifted meta.expected_type)]
(case expectedT
(#.Var _)
(do !
[inferenceT (//inference.variant idx case_size variantT)
[inferredT valueA+] (//inference.general archive analyse inferenceT (list valueC))]
- (in (/.variant [lefts right? (|> valueA+ list.head maybe.assume)])))
+ (in (/.variant [lefts right? (|> valueA+ list.head maybe.trusted)])))
_
(..sum analyse lefts right? archive valueC))))
@@ -288,7 +288,7 @@
(case key
[_ (#.Tag key)]
(do ///.monad
- [key (///extension.lift (meta.normal key))]
+ [key (///extension.lifted (meta.normal key))]
(in [key val]))
_
@@ -307,8 +307,8 @@
(#.Item [head_k head_v] _)
(do {! ///.monad}
- [head_k (///extension.lift (meta.normal head_k))
- [_ tag_set recordT] (///extension.lift (meta.tag head_k))
+ [head_k (///extension.lifted (meta.normal head_k))
+ [_ tag_set recordT] (///extension.lifted (meta.tag head_k))
.let [size_record (list.size record)
size_ts (list.size tag_set)]
_ (if (n.= size_ts size_record)
@@ -319,7 +319,7 @@
idx->val (monad.fold !
(function (_ [key val] idx->val)
(do !
- [key (///extension.lift (meta.normal key))]
+ [key (///extension.lifted (meta.normal key))]
(case (dictionary.value key tag->idx)
(#.Some idx)
(if (dictionary.key? idx->val idx)
@@ -331,7 +331,8 @@
(: (Dictionary Nat Code)
(dictionary.empty n.hash))
record)
- .let [ordered_tuple (list\map (function (_ idx) (maybe.assume (dictionary.value idx idx->val)))
+ .let [ordered_tuple (list\map (function (_ idx)
+ (maybe.trusted (dictionary.value idx idx->val)))
tuple_range)]]
(in [ordered_tuple recordT]))
))
@@ -349,7 +350,7 @@
(do {! ///.monad}
[members (normal members)
[membersC recordT] (order members)
- expectedT (///extension.lift meta.expected_type)]
+ expectedT (///extension.lifted meta.expected_type)]
(case expectedT
(#.Var _)
(do !
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/type.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/type.lux
index 374663c95..ed980b1e6 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/type.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/type.lux
@@ -40,7 +40,7 @@
(def: .public (infer actualT)
(-> Type (Operation Any))
(do ///.monad
- [expectedT (///extension.lift meta.expected_type)]
+ [expectedT (///extension.lifted meta.expected_type)]
(with_env
(check.check expectedT actualT))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux
index 8bb5d475f..81fc21caa 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux
@@ -47,21 +47,21 @@
(^ [_ (#.Form (list& macro inputs))])
(do {! //.monad}
- [expansion (/.lift_analysis
+ [expansion (/.lifted_analysis
(do !
[macroA (//analysis/type.with_type Macro
(analyze archive macro))]
(case macroA
(^ (///analysis.constant macro_name))
(do !
- [?macro (//extension.lift (meta.macro macro_name))
+ [?macro (//extension.lifted (meta.macro macro_name))
macro (case ?macro
(#.Some macro)
(in macro)
#.None
(//.except ..macro_was_not_found macro_name))]
- (//extension.lift (///analysis/macro.expand expander macro_name macro inputs)))
+ (//extension.lifted (///analysis/macro.expand expander macro_name macro inputs)))
_
(//.except ..invalid_macro_call code))))]
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 354f40fd2..206ae9f64 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
@@ -164,7 +164,7 @@
(function (_ [bundle state])
(#try.Success [[bundle (transform state)] []])))
-(def: .public (lift action)
+(def: .public (lifted action)
(All [s i o v]
(-> (//.Operation s v)
(//.Operation [(Bundle s i o) s] v)))
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 6fc53dd20..aa1730655 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
@@ -137,7 +137,7 @@
(def: (ensure_fresh_class! class_loader name)
(-> java/lang/ClassLoader External (Operation Any))
(do phase.monad
- [class (phase.lift (reflection!.load class_loader name))]
+ [class (phase.lifted (reflection!.load class_loader name))]
(phase.assertion ..deprecated_class [name]
(|> class
java/lang/Class::getDeclaredAnnotations
@@ -401,7 +401,7 @@
(|> objectJ
..signature
(<text>.result jvm_parser.array)
- phase.lift)))
+ phase.lifted)))
(def: (primitive_array_length_handler primitive_type)
(-> (Type Primitive) Handler)
@@ -460,7 +460,7 @@
(do phase.monad
[lengthA (typeA.with_type ..int
(analyse archive lengthC))
- expectedT (///.lift meta.expected_type)
+ expectedT (///.lifted meta.expected_type)
expectedJT (jvm_array_type expectedT)
elementJT (case (jvm_parser.array? expectedJT)
(#.Some elementJT)
@@ -556,7 +556,7 @@
[jvm.char]))
(text.starts_with? descriptor.array_prefix name)
- (let [[_ unprefixed] (maybe.assume (text.split_by descriptor.array_prefix name))]
+ (let [[_ unprefixed] (maybe.trusted (text.split_by descriptor.array_prefix name))]
(\ phase.monad map jvm.array
(check_jvm (#.Primitive unprefixed (list)))))
@@ -750,7 +750,7 @@
(case args
(^ (list))
(do phase.monad
- [expectedT (///.lift meta.expected_type)
+ [expectedT (///.lifted meta.expected_type)
_ (check_object expectedT)]
(in (#/////analysis.Extension extension_name (list))))
@@ -797,7 +797,7 @@
[exceptionT exceptionA] (typeA.with_inference
(analyse archive exceptionC))
exception_class (check_object exceptionT)
- ? (phase.lift (reflection!.sub? class_loader "java.lang.Throwable" exception_class))
+ ? (phase.lifted (reflection!.sub? class_loader "java.lang.Throwable" exception_class))
_ (: (Operation Any)
(if ?
(in [])
@@ -817,7 +817,7 @@
(do phase.monad
[_ (..ensure_fresh_class! class_loader class)
_ (typeA.infer (#.Primitive "java.lang.Class" (list (#.Primitive class (list)))))
- _ (phase.lift (reflection!.load class_loader class))]
+ _ (phase.lifted (reflection!.load class_loader class))]
(in (#/////analysis.Extension extension_name (list (/////analysis.text class)))))
_
@@ -837,7 +837,7 @@
[objectT objectA] (typeA.with_inference
(analyse archive objectC))
object_class (check_object objectT)
- ? (phase.lift (reflection!.sub? class_loader object_class sub_class))]
+ ? (phase.lifted (reflection!.sub? class_loader object_class sub_class))]
(if ?
(in (#/////analysis.Extension extension_name (list (/////analysis.text sub_class) objectA)))
(/////analysis.except cannot_possibly_be_an_instance (format sub_class " !<= " object_class)))))]))
@@ -862,14 +862,14 @@
(def: (class_candidate_parents class_loader source_name fromT target_name target_class)
(-> java/lang/ClassLoader External .Type External (java/lang/Class java/lang/Object) (Operation (List [[Text .Type] Bit])))
(do {! phase.monad}
- [source_class (phase.lift (reflection!.load class_loader source_name))
- mapping (phase.lift (reflection!.correspond source_class fromT))]
+ [source_class (phase.lifted (reflection!.load class_loader source_name))
+ mapping (phase.lifted (reflection!.correspond source_class fromT))]
(monad.map !
(function (_ superJT)
(do !
- [superJT (phase.lift (reflection!.type superJT))
+ [superJT (phase.lifted (reflection!.type superJT))
.let [super_name (|> superJT ..reflection)]
- super_class (phase.lift (reflection!.load class_loader super_name))
+ super_class (phase.lifted (reflection!.load class_loader super_name))
superT (reflection_type mapping superJT)]
(in [[super_name superT] (java/lang/Class::isAssignableFrom super_class target_class)])))
(case (java/lang/Class::getGenericSuperclass source_class)
@@ -890,7 +890,7 @@
(function (_ superT)
(do {! phase.monad}
[super_name (\ ! map ..reflection (check_jvm superT))
- super_class (phase.lift (reflection!.load class_loader super_name))]
+ super_class (phase.lifted (reflection!.load class_loader super_name))]
(in [[super_name superT]
(java/lang/Class::isAssignableFrom super_class target_class)])))
(list& super_classT super_interfacesT+))
@@ -904,7 +904,7 @@
(case args
(^ (list fromC))
(do {! phase.monad}
- [toT (///.lift meta.expected_type)
+ [toT (///.lifted meta.expected_type)
target_name (\ ! map ..reflection (check_jvm toT))
[fromT fromA] (typeA.with_inference
(analyse archive fromC))
@@ -934,11 +934,11 @@
(not (dictionary.key? ..boxes source_name)))
_ (phase.assertion ..primitives_are_not_objects [target_name]
(not (dictionary.key? ..boxes target_name)))
- target_class (phase.lift (reflection!.load class_loader target_name))
+ target_class (phase.lifted (reflection!.load class_loader target_name))
_ (if (text\= ..inheritance_relationship_type_name source_name)
(in [])
(do !
- [source_class (phase.lift (reflection!.load class_loader source_name))]
+ [source_class (phase.lifted (reflection!.load class_loader source_name))]
(phase.assertion ..cannot_cast [fromT toT fromC]
(java/lang/Class::isAssignableFrom source_class target_class))))]
(loop [[current_name currentT] [source_name fromT]]
@@ -986,7 +986,7 @@
(function (_ extension_name analyse archive [class field])
(do phase.monad
[_ (..ensure_fresh_class! class_loader class)
- [final? deprecated? fieldJT] (phase.lift
+ [final? deprecated? fieldJT] (phase.lifted
(do try.monad
[class (reflection!.load class_loader class)]
(reflection!.static_field field class)))
@@ -1007,7 +1007,7 @@
(do phase.monad
[_ (..ensure_fresh_class! class_loader class)
_ (typeA.infer Any)
- [final? deprecated? fieldJT] (phase.lift
+ [final? deprecated? fieldJT] (phase.lifted
(do try.monad
[class (reflection!.load class_loader class)]
(reflection!.static_field field class)))
@@ -1032,7 +1032,7 @@
[_ (..ensure_fresh_class! class_loader class)
[objectT objectA] (typeA.with_inference
(analyse archive objectC))
- [deprecated? mapping fieldJT] (phase.lift
+ [deprecated? mapping fieldJT] (phase.lifted
(do try.monad
[class (reflection!.load class_loader class)
[final? deprecated? fieldJT] (reflection!.virtual_field field class)
@@ -1058,7 +1058,7 @@
[objectT objectA] (typeA.with_inference
(analyse archive objectC))
_ (typeA.infer objectT)
- [final? deprecated? mapping fieldJT] (phase.lift
+ [final? deprecated? mapping fieldJT] (phase.lifted
(do try.monad
[class (reflection!.load class_loader class)
[final? deprecated? fieldJT] (reflection!.virtual_field field class)
@@ -1091,7 +1091,7 @@
[parameters (|> (java/lang/reflect/Method::getGenericParameterTypes method)
array.list
(monad.map try.monad reflection!.type)
- phase.lift)
+ phase.lifted)
.let [modifiers (java/lang/reflect/Method::getModifiers method)
correct_class? (java/lang/Object::equals class (java/lang/reflect/Method::getDeclaringClass method))
correct_method? (text\= method_name (java/lang/reflect/Method::getName method))
@@ -1137,7 +1137,7 @@
[parameters (|> (java/lang/reflect/Constructor::getGenericParameterTypes constructor)
array.list
(monad.map try.monad reflection!.type)
- phase.lift)]
+ phase.lifted)]
(in (and (java/lang/Object::equals class (java/lang/reflect/Constructor::getDeclaringClass constructor))
(n.= (list.size inputsJT) (list.size parameters))
(list\fold (function (_ [expectedJC actualJC] prev)
@@ -1191,18 +1191,18 @@
(do {! phase.monad}
[inputsT (|> (java/lang/reflect/Method::getGenericParameterTypes method)
array.list
- (monad.map ! (|>> reflection!.type phase.lift))
+ (monad.map ! (|>> reflection!.type phase.lifted))
(phase\map (monad.map ! (..reflection_type mapping)))
phase\join)
outputT (|> method
java/lang/reflect/Method::getGenericReturnType
reflection!.return
- phase.lift
+ phase.lifted
(phase\map (..reflection_return mapping))
phase\join)
exceptionsT (|> (java/lang/reflect/Method::getGenericExceptionTypes method)
array.list
- (monad.map ! (|>> reflection!.type phase.lift))
+ (monad.map ! (|>> reflection!.type phase.lifted))
(phase\map (monad.map ! (..reflection_type mapping)))
phase\join)
.let [methodT (<| (type.univ_q (dictionary.size mapping))
@@ -1231,12 +1231,12 @@
(do {! phase.monad}
[inputsT (|> (java/lang/reflect/Constructor::getGenericParameterTypes constructor)
array.list
- (monad.map ! (|>> reflection!.type phase.lift))
+ (monad.map ! (|>> reflection!.type phase.lifted))
(phase\map (monad.map ! (reflection_type mapping)))
phase\join)
exceptionsT (|> (java/lang/reflect/Constructor::getGenericExceptionTypes constructor)
array.list
- (monad.map ! (|>> reflection!.type phase.lift))
+ (monad.map ! (|>> reflection!.type phase.lifted))
(phase\map (monad.map ! (reflection_type mapping)))
phase\join)
.let [objectT (#.Primitive (java/lang/Class::getName owner) owner_tvarsT)
@@ -1285,7 +1285,7 @@
(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))
(do {! phase.monad}
- [class (phase.lift (reflection!.load class_loader class_name))
+ [class (phase.lifted (reflection!.load class_loader class_name))
.let [expected_class_tvars (class_type_variables class)]
candidates (|> class
java/lang/Class::getDeclaredMethods
@@ -1318,7 +1318,7 @@
(def: (constructor_candidate class_loader actual_class_tvars class_name actual_method_tvars inputsJT)
(-> java/lang/ClassLoader (List (Type Var)) External (List (Type Var)) (List (Type Value)) (Operation Method_Signature))
(do {! phase.monad}
- [class (phase.lift (reflection!.load class_loader class_name))
+ [class (phase.lifted (reflection!.load class_loader class_name))
.let [expected_class_tvars (class_type_variables class)]
candidates (|> class
java/lang/Class::getConstructors
@@ -1436,7 +1436,7 @@
(do phase.monad
[_ (..ensure_fresh_class! class_loader class_name)
.let [argsT (list\map product.left argsTC)]
- class (phase.lift (reflection!.load class_loader class_name))
+ class (phase.lifted (reflection!.load class_loader class_name))
_ (phase.assertion non_interface class_name
(java/lang/reflect/Modifier::isInterface (java/lang/Class::getModifiers class)))
[methodT deprecated? exceptionsT] (..method_candidate class_loader class_tvars class_name method_tvars method #Interface argsT)
@@ -1914,14 +1914,14 @@
[parent_parameters (|> parent_parameters
(monad.map maybe.monad jvm_parser.var?)
try.of_maybe
- phase.lift)]
+ phase.lifted)]
(|> super_parameters
(monad.map ! (..reflection_type mapping))
(\ ! map (|>> (list.zipped/2 parent_parameters)))))
- (phase.lift (exception.except ..mismatched_super_parameters [parent_name expected_count actual_count]))))
+ (phase.lifted (exception.except ..mismatched_super_parameters [parent_name expected_count actual_count]))))
#.None
- (phase.lift (exception.except ..unknown_super [parent_name supers])))))
+ (phase.lifted (exception.except ..unknown_super [parent_name supers])))))
(def: .public (with_fresh_type_vars vars mapping)
(-> (List (Type Var)) Mapping (Operation Mapping))
@@ -2060,7 +2060,7 @@
(-> java/lang/ClassLoader (Type Class) (Operation Aliasing))
(do phase.monad
[.let [[name actual_parameters] (jvm_parser.read_class class)]
- class (phase.lift (reflection!.load class_loader name))
+ class (phase.lifted (reflection!.load class_loader name))
.let [expected_parameters (|> (java/lang/Class::getTypeParameters class)
array.list
(list\map (|>> java/lang/reflect/TypeVariable::getName)))]
@@ -2086,8 +2086,8 @@
(def: .public (require_complete_method_concretion class_loader supers methods)
(-> java/lang/ClassLoader (List (Type Class)) (List (Overriden_Method Code)) (Operation Any))
(do {! phase.monad}
- [required_abstract_methods (phase.lift (all_abstract_methods class_loader supers))
- available_methods (phase.lift (all_methods class_loader supers))
+ [required_abstract_methods (phase.lifted (all_abstract_methods class_loader supers))
+ available_methods (phase.lifted (all_methods class_loader supers))
overriden_methods (monad.map ! (function (_ [parent_type method_name
strict_fp? annotations type_vars
self_name arguments return exceptions
@@ -2139,12 +2139,12 @@
(monad.map check.monad
(|>> ..signature (luxT.check (luxT.class mapping)))
super_interfaces))
- selfT (///.lift (do meta.monad
- [where meta.current_module_name
- id meta.seed]
- (in (inheritance_relationship_type (#.Primitive (..anonymous_class_name where id) (list))
- super_classT
- super_interfaceT+))))
+ selfT (///.lifted (do meta.monad
+ [where meta.current_module_name
+ id meta.seed]
+ (in (inheritance_relationship_type (#.Primitive (..anonymous_class_name where id) (list))
+ super_classT
+ super_interfaceT+))))
_ (typeA.infer selfT)
constructor_argsA+ (monad.map ! (function (_ [type term])
(do !
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 979af197a..d26820e9a 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
@@ -90,7 +90,7 @@
(do <>.monad
[raw <code>.text]
(case (text.size raw)
- 1 (in (|> raw (text.char 0) maybe.assume))
+ 1 (in (|> raw (text.char 0) maybe.trusted))
_ (<>.failure (exception.error ..char_text_must_be_size_1 [raw])))))
(def: lux::syntax_char_case!
@@ -104,7 +104,7 @@
(do {! ////.monad}
[input (typeA.with_type text.Char
(phase archive input))
- expectedT (///.lift meta.expected_type)
+ expectedT (///.lifted meta.expected_type)
conditionals (monad.map ! (function (_ [cases branch])
(do !
[branch (typeA.with_type expectedT
@@ -164,7 +164,7 @@
(case args
(^ (list typeC valueC))
(do {! ////.monad}
- [seed (///.lift meta.seed)
+ [seed (///.lifted meta.seed)
actualT (\ ! map (|>> (:as Type))
(eval archive seed Type typeC))
_ (typeA.infer actualT)]
@@ -180,7 +180,7 @@
(case args
(^ (list typeC valueC))
(do {! ////.monad}
- [seed (///.lift meta.seed)
+ [seed (///.lifted meta.seed)
actualT (\ ! map (|>> (:as Type))
(eval archive seed Type typeC))
_ (typeA.infer actualT)
@@ -210,7 +210,7 @@
[_ (typeA.infer .Macro)
input_type (loop [input_name (name_of .Macro')]
(do !
- [input_type (///.lift (meta.definition (name_of .Macro')))]
+ [input_type (///.lifted (meta.definition (name_of .Macro')))]
(case input_type
(#.Definition [exported? def_type def_data def_value])
(in (:as Type def_value))
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 04e197099..61f4e3763 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
@@ -223,7 +223,7 @@
(function (_ methodC)
(do phase.monad
[methodA (: (Operation analysis.Analysis)
- (directive.lift_analysis
+ (directive.lifted_analysis
(case methodC
(#Constructor method)
(jvm.analyse_constructor_method analyse selfT mapping method)
@@ -236,7 +236,7 @@
(#Overriden_Method method)
(jvm.analyse_overriden_method analyse selfT mapping method))))]
- (directive.lift_synthesis
+ (directive.lifted_synthesis
(synthesize methodA)))))
(def: jvm::class
@@ -260,17 +260,17 @@
fields
methods])
(do {! phase.monad}
- [parameters (directive.lift_analysis
+ [parameters (directive.lifted_analysis
(typeA.with_env
(jvm.parameter_types parameters)))
.let [mapping (list\fold (function (_ [parameterJ parameterT] mapping)
(dictionary.has (parser.name parameterJ) parameterT mapping))
luxT.fresh
parameters)]
- super_classT (directive.lift_analysis
+ super_classT (directive.lifted_analysis
(typeA.with_env
(luxT.check (luxT.class mapping) (..signature super_class))))
- super_interfaceT+ (directive.lift_analysis
+ super_interfaceT+ (directive.lifted_analysis
(typeA.with_env
(monad.map check.monad
(|>> ..signature (luxT.check (luxT.class mapping)))
@@ -278,13 +278,13 @@
.let [selfT (jvm.inheritance_relationship_type (#.Primitive name (list\map product.right parameters))
super_classT
super_interfaceT+)]
- state (extension.lift phase.get_state)
+ state (extension.lifted phase.get_state)
.let [analyse (get@ [#directive.analysis #directive.phase] state)
synthesize (get@ [#directive.synthesis #directive.phase] state)
generate (get@ [#directive.generation #directive.phase] state)]
methods (monad.map ! (..method_definition [mapping selfT] [analyse synthesize generate])
methods)
- ... _ (directive.lift_generation
+ ... _ (directive.lifted_generation
... (generation.save! true ["" name]
... [name
... (class.class version.v6_0
@@ -294,7 +294,7 @@
... (list\map ..field_definition fields)
... (list) ... TODO: Add methods
... (row.row))]))
- _ (directive.lift_generation
+ _ (directive.lifted_generation
(generation.log! (format "Class " name)))]
(in directive.no_requirements)))]))
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 04df2b765..604292cdd 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
@@ -73,7 +73,7 @@
Type
Synthesis
(Operation anchor expression directive [Type expression Any])))
- (/////directive.lift_generation
+ (/////directive.lifted_generation
(do phase.monad
[module /////generation.module
id /////generation.next
@@ -86,16 +86,16 @@
(All [anchor expression directive]
(-> Archive Type Code (Operation anchor expression directive [Type expression Any])))
(do phase.monad
- [state (///.lift phase.get_state)
+ [state (///.lifted phase.get_state)
.let [analyse (get@ [#/////directive.analysis #/////directive.phase] state)
synthesize (get@ [#/////directive.synthesis #/////directive.phase] state)
generate (get@ [#/////directive.generation #/////directive.phase] state)]
- [_ codeA] (/////directive.lift_analysis
+ [_ codeA] (/////directive.lifted_analysis
(/////analysis.with_scope
(typeA.with_fresh_env
(typeA.with_type type
(analyse archive codeC)))))
- codeS (/////directive.lift_synthesis
+ codeS (/////directive.lifted_synthesis
(synthesize archive codeA))]
(evaluate!' archive generate type codeS)))
@@ -108,11 +108,11 @@
Type
Synthesis
(Operation anchor expression directive [Type expression Any])))
- (/////directive.lift_generation
+ (/////directive.lifted_generation
(do phase.monad
[codeG (generate archive codeS)
id (/////generation.learn name)
- module_id (phase.lift (archive.id module archive))
+ module_id (phase.lifted (archive.id module archive))
[target_name value directive] (/////generation.define! [module_id id] #.None codeG)
_ (/////generation.save! id #.None directive)]
(in [code//type codeG value]))))
@@ -122,11 +122,11 @@
(-> Archive Name (Maybe Type) Code
(Operation anchor expression directive [Type expression Any])))
(do {! phase.monad}
- [state (///.lift phase.get_state)
+ [state (///.lifted phase.get_state)
.let [analyse (get@ [#/////directive.analysis #/////directive.phase] state)
synthesize (get@ [#/////directive.synthesis #/////directive.phase] state)
generate (get@ [#/////directive.generation #/////directive.phase] state)]
- [_ code//type codeA] (/////directive.lift_analysis
+ [_ code//type codeA] (/////directive.lifted_analysis
(/////analysis.with_scope
(typeA.with_fresh_env
(case expected
@@ -143,7 +143,7 @@
[codeA (typeA.with_type expected
(analyse archive codeC))]
(in [expected codeA]))))))
- codeS (/////directive.lift_synthesis
+ codeS (/////directive.lifted_synthesis
(synthesize archive codeA))]
(definition' archive generate name code//type codeS)))
@@ -158,12 +158,12 @@
Synthesis
(Operation anchor expression directive [expression Any])))
(do phase.monad
- [current_module (/////directive.lift_analysis
- (///.lift meta.current_module_name))]
- (/////directive.lift_generation
+ [current_module (/////directive.lifted_analysis
+ (///.lifted meta.current_module_name))]
+ (/////directive.lifted_generation
(do phase.monad
[codeG (generate archive codeS)
- module_id (phase.lift (archive.id current_module archive))
+ module_id (phase.lifted (archive.id current_module archive))
id (<learn> extension)
[target_name value directive] (/////generation.define! [module_id id] #.None codeG)
_ (/////generation.save! id #.None directive)]
@@ -174,16 +174,16 @@
(-> Archive Text Type Code
(Operation anchor expression directive [expression Any])))
(do phase.monad
- [state (///.lift phase.get_state)
+ [state (///.lifted phase.get_state)
.let [analyse (get@ [#/////directive.analysis #/////directive.phase] state)
synthesize (get@ [#/////directive.synthesis #/////directive.phase] state)
generate (get@ [#/////directive.generation #/////directive.phase] state)]
- [_ codeA] (/////directive.lift_analysis
+ [_ codeA] (/////directive.lifted_analysis
(/////analysis.with_scope
(typeA.with_fresh_env
(typeA.with_type codeT
(analyse archive codeC)))))
- codeS (/////directive.lift_synthesis
+ codeS (/////directive.lifted_synthesis
(synthesize archive codeA))]
(<partial> archive generate extension codeT codeS)))]
@@ -212,7 +212,7 @@
(def: (announce_definition! short type)
(All [anchor expression directive]
(-> Text Type (Operation anchor expression directive Any)))
- (/////directive.lift_generation
+ (/////directive.lifted_generation
(/////generation.log! (format short " : " (%.type type)))))
(def: (lux::def expander host_analysis)
@@ -221,13 +221,13 @@
(case inputsC+
(^ (list [_ (#.Identifier ["" short_name])] valueC annotationsC exported?C))
(do phase.monad
- [current_module (/////directive.lift_analysis
- (///.lift meta.current_module_name))
+ [current_module (/////directive.lifted_analysis
+ (///.lifted meta.current_module_name))
.let [full_name [current_module short_name]]
[type valueT value] (..definition archive full_name #.None valueC)
[_ _ exported?] (evaluate! archive Bit exported?C)
[_ _ annotations] (evaluate! archive Code annotationsC)
- _ (/////directive.lift_analysis
+ _ (/////directive.lifted_analysis
(module.define short_name (#.Right [(:as Bit exported?) type (:as Code annotations) value])))
_ (..refresh expander host_analysis)
_ (..announce_definition! short_name type)]
@@ -242,15 +242,15 @@
[($_ <>.and <code>.local_identifier <code>.any <code>.any (<code>.tuple (<>.some <code>.text)) <code>.any)
(function (_ extension_name phase archive [short_name valueC annotationsC tags exported?C])
(do phase.monad
- [current_module (/////directive.lift_analysis
- (///.lift meta.current_module_name))
+ [current_module (/////directive.lifted_analysis
+ (///.lifted meta.current_module_name))
.let [full_name [current_module short_name]]
[_ _ exported?] (evaluate! archive Bit exported?C)
[_ _ annotations] (evaluate! archive Code annotationsC)
.let [exported? (:as Bit exported?)
annotations (:as Code annotations)]
[type valueT value] (..definition archive full_name (#.Some .Type) valueC)
- _ (/////directive.lift_analysis
+ _ (/////directive.lifted_analysis
(do phase.monad
[_ (module.define short_name (#.Right [exported? type annotations value]))]
(module.declare_tags tags exported? (:as Type value))))
@@ -272,7 +272,7 @@
(do {! phase.monad}
[[_ _ annotationsV] (evaluate! archive Code annotationsC)
.let [annotationsV (:as Code annotationsV)]
- _ (/////directive.lift_analysis
+ _ (/////directive.lifted_analysis
(do !
[_ (monad.map ! (function (_ [module alias])
(do !
@@ -294,8 +294,8 @@
(def: (define_alias alias original)
(-> Text Name (/////analysis.Operation Any))
(do phase.monad
- [current_module (///.lift meta.current_module_name)
- constant (///.lift (meta.definition original))]
+ [current_module (///.lifted meta.current_module_name)
+ constant (///.lifted (meta.definition original))]
(case constant
(#.Left de_aliased)
(phase.except ..cannot_alias_an_alias [[current_module alias] original de_aliased])
@@ -309,7 +309,7 @@
[($_ <>.and <code>.local_identifier <code>.identifier)
(function (_ extension_name phase archive [alias def_name])
(do phase.monad
- [_ (///.lift
+ [_ (///.lifted
(phase.sub [(get@ [#/////directive.analysis #/////directive.state])
(set@ [#/////directive.analysis #/////directive.state])]
(define_alias alias def_name)))]
@@ -336,7 +336,7 @@
<type>
(:expected handlerV)))
- _ (/////directive.lift_generation
+ _ (/////directive.lifted_generation
(/////generation.log! (format <description> " " (%.text (:as Text name)))))]
(in /////directive.no_requirements))
@@ -346,17 +346,17 @@
["Analysis"
def::analysis
/////analysis.Handler /////analysis.Handler
- /////directive.lift_analysis
+ /////directive.lifted_analysis
..analyser]
["Synthesis"
def::synthesis
/////synthesis.Handler /////synthesis.Handler
- /////directive.lift_synthesis
+ /////directive.lifted_synthesis
..synthesizer]
["Generation"
def::generation
(/////generation.Handler anchorT expressionT directiveT) (/////generation.Handler anchor expression directive)
- /////directive.lift_generation
+ /////directive.lifted_generation
..generator]
["Directive"
def::directive
@@ -376,12 +376,12 @@
Code
(Operation anchor expression directive Synthesis)))
(do phase.monad
- [[_ programA] (/////directive.lift_analysis
+ [[_ programA] (/////directive.lifted_analysis
(/////analysis.with_scope
(typeA.with_fresh_env
(typeA.with_type (type (-> (List Text) (IO Any)))
(analyse archive programC)))))]
- (/////directive.lift_synthesis
+ (/////directive.lifted_synthesis
(synthesize archive programA))))
(def: (define_program archive module_id generate program programS)
@@ -404,15 +404,15 @@
(case inputsC+
(^ (list programC))
(do phase.monad
- [state (///.lift phase.get_state)
+ [state (///.lifted phase.get_state)
.let [analyse (get@ [#/////directive.analysis #/////directive.phase] state)
synthesize (get@ [#/////directive.synthesis #/////directive.phase] state)
generate (get@ [#/////directive.generation #/////directive.phase] state)]
programS (prepare_program archive analyse synthesize programC)
- current_module (/////directive.lift_analysis
- (///.lift meta.current_module_name))
- module_id (phase.lift (archive.id current_module archive))
- _ (/////directive.lift_generation
+ current_module (/////directive.lifted_analysis
+ (///.lifted meta.current_module_name))
+ module_id (phase.lifted (archive.id current_module archive))
+ _ (/////directive.lifted_generation
(define_program archive module_id generate program programS))]
(in /////directive.no_requirements))
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 770e1cce0..a8caf13bf 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
@@ -67,13 +67,13 @@
(def: lux_int
(Bytecode Any)
- ($_ _.compose
+ ($_ _.composite
_.i2l
(///value.wrap type.long)))
(def: jvm_int
(Bytecode Any)
- ($_ _.compose
+ ($_ _.composite
(///value.unwrap type.long)
_.l2i))
@@ -87,7 +87,7 @@
(do _.monad
[@then _.new_label
@end _.new_label]
- ($_ _.compose
+ ($_ _.composite
(bytecode @then)
(_.getstatic $Boolean "FALSE" $Boolean)
(_.goto @end)
@@ -116,9 +116,9 @@
[branchG (phase archive branch)
@branch ///runtime.forge_label]
(in [(list\map (function (_ char)
- [(try.assumed (signed.s4 (.int char))) @branch])
+ [(try.trusted (signed.s4 (.int char))) @branch])
chars)
- ($_ _.compose
+ ($_ _.composite
(_.set_label @branch)
branchG
(_.goto @end))])))
@@ -131,7 +131,7 @@
(monad.seq _.monad))]]
(in (do _.monad
[@else _.new_label]
- ($_ _.compose
+ ($_ _.composite
inputG (///value.unwrap type.long) _.l2i
(_.lookupswitch @else table)
conditionalsG
@@ -142,14 +142,14 @@
(def: (lux::is [referenceG sampleG])
(Binary (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
referenceG
sampleG
(..predicate _.if_acmpeq)))
(def: (lux::try riskyG)
(Unary (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
riskyG
(_.checkcast ///function.class)
///runtime.try))
@@ -164,7 +164,7 @@
(template [<name> <op>]
[(def: (<name> [maskG inputG])
(Binary (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
inputG (///value.unwrap type.long)
maskG (///value.unwrap type.long)
<op> (///value.wrap type.long)))]
@@ -177,7 +177,7 @@
(template [<name> <op>]
[(def: (<name> [shiftG inputG])
(Binary (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
inputG (///value.unwrap type.long)
shiftG ..jvm_int
<op> (///value.wrap type.long)))]
@@ -189,7 +189,7 @@
(template [<name> <type> <op>]
[(def: (<name> [paramG subjectG])
(Binary (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
subjectG (///value.unwrap <type>)
paramG (///value.unwrap <type>)
<op> (///value.wrap <type>)))]
@@ -211,7 +211,7 @@
[(template [<name> <reference>]
[(def: (<name> [paramG subjectG])
(Binary (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
subjectG (///value.unwrap <type>)
paramG (///value.unwrap <type>)
<cmp>
@@ -232,27 +232,27 @@
(template [<name> <prepare> <transform>]
[(def: (<name> inputG)
(Unary (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
inputG
<prepare>
<transform>))]
[i64::f64
(///value.unwrap type.long)
- ($_ _.compose
+ ($_ _.composite
_.l2d
(///value.wrap type.double))]
[i64::char
(///value.unwrap type.long)
- ($_ _.compose
+ ($_ _.composite
_.l2i
_.i2c
(..::toString ..$Character type.char))]
[f64::i64
(///value.unwrap type.double)
- ($_ _.compose
+ ($_ _.composite
_.d2l
(///value.wrap type.long))]
@@ -301,7 +301,7 @@
(def: (text::size inputG)
(Unary (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
inputG
..ensure_string
(_.invokevirtual ..$String "length" (type.method [(list) type.int (list)]))
@@ -312,7 +312,7 @@
(template [<name> <pre_subject> <pre_param> <op> <post>]
[(def: (<name> [paramG subjectG])
(Binary (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
subjectG <pre_subject>
paramG <pre_param>
<op> <post>))]
@@ -330,14 +330,14 @@
(def: (text::concat [leftG rightG])
(Binary (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
leftG ..ensure_string
rightG ..ensure_string
(_.invokevirtual ..$String "concat" (type.method [(list ..$String) ..$String (list)]))))
(def: (text::clip [startG endG subjectG])
(Trinary (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
subjectG ..ensure_string
startG ..jvm_int
endG ..jvm_int
@@ -349,7 +349,7 @@
(do _.monad
[@not_found _.new_label
@end _.new_label]
- ($_ _.compose
+ ($_ _.composite
textG ..ensure_string
partG ..ensure_string
startG ..jvm_int
@@ -380,7 +380,7 @@
(def: string_method (type.method [(list ..$String) type.void (list)]))
(def: (io::log messageG)
(Unary (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
(_.getstatic ..$System "out" ..$PrintStream)
messageG
..ensure_string
@@ -389,7 +389,7 @@
(def: (io::error messageG)
(Unary (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
(_.new ..$Error)
_.dup
messageG
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 a79807c28..a749fb6cd 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
@@ -72,7 +72,7 @@
(template [<name> <0> <1>]
[(def: <name>
(Bytecode Any)
- ($_ _.compose
+ ($_ _.composite
<0>
<1>))]
@@ -86,7 +86,7 @@
(Unary (Bytecode Any))
(if (same? _.nop <conversion>)
inputG
- ($_ _.compose
+ ($_ _.composite
inputG
<conversion>)))]
@@ -149,7 +149,7 @@
(template [<name> <op>]
[(def: (<name> [xG yG])
(Binary (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
xG
yG
<op>))]
@@ -201,7 +201,7 @@
(do _.monad
[@then _.new_label
@end _.new_label]
- ($_ _.compose
+ ($_ _.composite
xG
yG
(<op> @then)
@@ -224,7 +224,7 @@
(do _.monad
[@then _.new_label
@end _.new_label]
- ($_ _.compose
+ ($_ _.composite
xG
yG
<op>
@@ -357,7 +357,7 @@
(function (_ extension_name generate archive arrayS)
(do //////.monad
[arrayG (generate archive arrayS)]
- (in ($_ _.compose
+ (in ($_ _.composite
arrayG
(_.checkcast (type.array jvm_primitive))
_.arraylength))))]))
@@ -369,7 +369,7 @@
(function (_ extension_name generate archive [elementJT arrayS])
(do //////.monad
[arrayG (generate archive arrayS)]
- (in ($_ _.compose
+ (in ($_ _.composite
arrayG
(_.checkcast (type.array elementJT))
_.arraylength))))]))
@@ -381,7 +381,7 @@
(function (_ extension_name generate archive [lengthS])
(do //////.monad
[lengthG (generate archive lengthS)]
- (in ($_ _.compose
+ (in ($_ _.composite
lengthG
(_.newarray jvm_primitive)))))]))
@@ -392,7 +392,7 @@
(function (_ extension_name generate archive [objectJT lengthS])
(do //////.monad
[lengthG (generate archive lengthS)]
- (in ($_ _.compose
+ (in ($_ _.composite
lengthG
(_.anewarray objectJT)))))]))
@@ -404,7 +404,7 @@
(do //////.monad
[arrayG (generate archive arrayS)
idxG (generate archive idxS)]
- (in ($_ _.compose
+ (in ($_ _.composite
arrayG
(_.checkcast (type.array jvm_primitive))
idxG
@@ -418,7 +418,7 @@
(do //////.monad
[arrayG (generate archive arrayS)
idxG (generate archive idxS)]
- (in ($_ _.compose
+ (in ($_ _.composite
arrayG
(_.checkcast (type.array elementJT))
idxG
@@ -433,7 +433,7 @@
[arrayG (generate archive arrayS)
idxG (generate archive idxS)
valueG (generate archive valueS)]
- (in ($_ _.compose
+ (in ($_ _.composite
arrayG
(_.checkcast (type.array jvm_primitive))
_.dup
@@ -450,7 +450,7 @@
[arrayG (generate archive arrayS)
idxG (generate archive idxS)
valueG (generate archive valueS)]
- (in ($_ _.compose
+ (in ($_ _.composite
arrayG
(_.checkcast (type.array elementJT))
_.dup
@@ -517,7 +517,7 @@
(do _.monad
[@then _.new_label
@end _.new_label]
- ($_ _.compose
+ ($_ _.composite
objectG
(_.ifnull @then)
..falseG
@@ -528,7 +528,7 @@
(def: (object::synchronized [monitorG exprG])
(Binary (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
monitorG
_.dup
_.monitorenter
@@ -538,7 +538,7 @@
(def: (object::throw exceptionG)
(Unary (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
exceptionG
_.athrow))
@@ -552,7 +552,7 @@
(function (_ extension_name generate archive [class])
(do //////.monad
[]
- (in ($_ _.compose
+ (in ($_ _.composite
(_.string class)
(_.invokestatic ..$Class "forName" (type.method [(list ..$String) ..$Class (list)]))))))]))
@@ -563,7 +563,7 @@
(function (_ extension_name generate archive [class objectS])
(do //////.monad
[objectG (generate archive objectS)]
- (in ($_ _.compose
+ (in ($_ _.composite
objectG
(_.instanceof (type.class class (list)))
(_.invokestatic ..$Boolean "valueOf" (type.method [(list type.boolean) ..$Boolean (list)]))))))]))
@@ -586,7 +586,7 @@
(text\= <object>
to))
(let [$<object> (type.class <object> (list))]
- ($_ _.compose
+ ($_ _.composite
valueG
(_.invokestatic $<object> "valueOf" (type.method [(list <type>) $<object> (list)]))))
@@ -595,7 +595,7 @@
(text\= (..reflection <type>)
to))
(let [$<object> (type.class <object> (list))]
- ($_ _.compose
+ ($_ _.composite
valueG
(_.checkcast $<object>)
(_.invokevirtual $<object> <unwrap> (type.method [(list) <type> (list)]))))]
@@ -662,13 +662,13 @@
.let [$class (type.class class (list))]]
(case (dictionary.value unboxed ..primitives)
(#.Some primitive)
- (in ($_ _.compose
+ (in ($_ _.composite
valueG
(_.putstatic $class field primitive)
..unitG))
#.None
- (in ($_ _.compose
+ (in ($_ _.composite
valueG
(_.checkcast $class)
(_.putstatic $class field $class)
@@ -688,7 +688,7 @@
#.None
(_.getfield $class field (type.class unboxed (list))))]]
- (in ($_ _.compose
+ (in ($_ _.composite
objectG
(_.checkcast $class)
getG))))]))
@@ -708,10 +708,10 @@
#.None
(let [$unboxed (type.class unboxed (list))]
- ($_ _.compose
+ ($_ _.composite
(_.checkcast $unboxed)
(_.putfield $class field $unboxed))))]]
- (in ($_ _.compose
+ (in ($_ _.composite
objectG
(_.checkcast $class)
_.dup
@@ -733,7 +733,7 @@
(in [valueT valueG])
(#.Left valueT)
- (in [valueT ($_ _.compose
+ (in [valueT ($_ _.composite
valueG
(_.checkcast valueT))]))))
@@ -753,7 +753,7 @@
(function (_ extension_name generate archive [class method outputT inputsTS])
(do {! //////.monad}
[inputsTG (monad.map ! (generate_input generate archive) inputsTS)]
- (in ($_ _.compose
+ (in ($_ _.composite
(monad.map _.monad product.right inputsTG)
(_.invokestatic class method (type.method [(list\map product.left inputsTG) outputT (list)]))
(prepare_output outputT)))))]))
@@ -767,7 +767,7 @@
(do {! //////.monad}
[objectG (generate archive objectS)
inputsTG (monad.map ! (generate_input generate archive) inputsTS)]
- (in ($_ _.compose
+ (in ($_ _.composite
objectG
(_.checkcast class)
(monad.map _.monad product.right inputsTG)
@@ -786,7 +786,7 @@
(function (_ extension_name generate archive [class inputsTS])
(do {! //////.monad}
[inputsTG (monad.map ! (generate_input generate archive) inputsTS)]
- (in ($_ _.compose
+ (in ($_ _.composite
(_.new class)
_.dup
(monad.map _.monad product.right inputsTG)
@@ -946,13 +946,13 @@
list.size
list.indices
(monad.map _.monad (.function (_ register)
- ($_ _.compose
+ ($_ _.composite
(_.aload 0)
(_.aload (inc register))
(_.putfield class (///reference.foreign_name register) $Object)))))]
(method.method method.public "<init>" (anonymous_init_method env)
(list)
- (#.Some ($_ _.compose
+ (#.Some ($_ _.composite
(_.aload 0)
(monad.map _.monad product.right inputsTG)
(_.invokespecial super_class "<init>" (type.method [(list\map product.left inputsTG) type.void (list)]))
@@ -963,7 +963,7 @@
(-> Phase Archive (Type category.Class) (Environment Synthesis) (Operation (Bytecode Any)))
(do {! //////.monad}
[captureG+ (monad.map ! (generate archive) env)]
- (in ($_ _.compose
+ (in ($_ _.composite
(_.new class)
_.dup
(monad.seq _.monad captureG+)
@@ -978,7 +978,7 @@
(#.Left returnT)
(case (type.primitive? returnT)
(#.Left returnT)
- ($_ _.compose
+ ($_ _.composite
(_.checkcast returnT)
_.areturn)
@@ -1040,7 +1040,7 @@
[(#//////variable.Foreign foreign_id)
(|> global_mapping
(dictionary.value capture)
- maybe.assume)]))
+ maybe.trusted)]))
(dictionary.from_list //////variable.hash))]
[ownerT name
strict_fp? annotations vars
@@ -1066,12 +1066,12 @@
returnT
exceptionsT])
(list)
- (#.Some ($_ _.compose
+ (#.Some ($_ _.composite
bodyG
(returnG returnT)))))))
normalized_methods)
bytecode (<| (\ ! map (format.result class.writer))
- //////.lift
+ //////.lifted
(class.class version.v6_0 ($_ modifier\compose class.public class.final)
(name.internal anonymous_class_name)
(name.internal (..reflection super_class))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux
index d7a20b360..aebb30404 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux
@@ -42,7 +42,7 @@
1 _.pop
2 _.pop2
_ ... (n.> 2)
- ($_ _.compose
+ ($_ _.composite
_.pop2
(pop_alt (n.- 2 stack_depth)))))
@@ -60,19 +60,19 @@
(def: peek
(Bytecode Any)
- ($_ _.compose
+ ($_ _.composite
_.dup
(//runtime.get //runtime.stack_head)))
(def: pop
(Bytecode Any)
- ($_ _.compose
+ ($_ _.composite
(//runtime.get //runtime.stack_tail)
(_.checkcast //type.stack)))
(def: (left_projection lefts)
(-> Nat (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
(_.checkcast //type.tuple)
(..int lefts)
(.case lefts
@@ -84,7 +84,7 @@
(def: (right_projection lefts)
(-> Nat (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
(_.checkcast //type.tuple)
(..int lefts)
//runtime.right_projection))
@@ -96,14 +96,14 @@
(operation\in ..pop)
(#synthesis.Bind register)
- (operation\in ($_ _.compose
+ (operation\in ($_ _.composite
..peek
(_.astore register)))
(#synthesis.Then bodyS)
(do phase.monad
[bodyG (phase archive bodyS)]
- (in ($_ _.compose
+ (in ($_ _.composite
(..pop_alt stack_depth)
bodyG
(_.goto @end))))
@@ -114,7 +114,7 @@
(do _.monad
[@success _.new_label
@fail _.new_label]
- ($_ _.compose
+ ($_ _.composite
..peek
(_.checkcast //type.variant)
(//structure.tag lefts <right?>)
@@ -133,7 +133,7 @@
(^template [<pattern> <projection>]
[(^ (<pattern> lefts))
- (operation\in ($_ _.compose
+ (operation\in ($_ _.composite
..peek
(<projection> lefts)
//runtime.push))])
@@ -146,7 +146,7 @@
(synthesis.!bind_top register thenP)))
(do phase.monad
[thenG (path' stack_depth @else @end phase archive thenP)]
- (in ($_ _.compose
+ (in ($_ _.composite
..peek
(_.checkcast //type.tuple)
_.iconst_0
@@ -161,7 +161,7 @@
(synthesis.!bind_top register thenP)))
(do phase.monad
[then! (path' stack_depth @else @end phase archive thenP)]
- (in ($_ _.compose
+ (in ($_ _.composite
..peek
(_.checkcast //type.tuple)
(..int lefts)
@@ -176,7 +176,7 @@
[@alt_else //runtime.forge_label
left! (path' (inc stack_depth) @alt_else @end phase archive leftP)
right! (path' stack_depth @else @end phase archive rightP)]
- (in ($_ _.compose
+ (in ($_ _.composite
_.dup
left!
(_.set_label @alt_else)
@@ -187,7 +187,7 @@
(do phase.monad
[left! (path' stack_depth @else @end phase archive leftP)
right! (path' stack_depth @else @end phase archive rightP)]
- (in ($_ _.compose
+ (in ($_ _.composite
left!
right!)))
@@ -200,7 +200,7 @@
(do phase.monad
[@else //runtime.forge_label
pathG (..path' 1 @else @end phase archive path)]
- (in ($_ _.compose
+ (in ($_ _.composite
pathG
(_.set_label @else)
_.pop
@@ -217,7 +217,7 @@
(in (do _.monad
[@else _.new_label
@end _.new_label]
- ($_ _.compose
+ ($_ _.composite
conditionG
(//value.unwrap type.boolean)
(_.ifeq @else)
@@ -232,7 +232,7 @@
(do phase.monad
[inputG (phase archive inputS)
bodyG (phase archive bodyS)]
- (in ($_ _.compose
+ (in ($_ _.composite
inputG
(_.astore register)
bodyG))))
@@ -248,7 +248,7 @@
(#.Right lefts)
(..right_projection lefts))]
- (_.compose so_far next)))
+ (_.composite so_far next)))
recordG
(list.reversed path)))))
@@ -258,7 +258,7 @@
[@end //runtime.forge_label
valueG (phase archive valueS)
pathG (..path @end phase archive path)]
- (in ($_ _.compose
+ (in ($_ _.composite
_.aconst_null
valueG
//runtime.push
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 095c973b4..f3938db06 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
@@ -104,13 +104,13 @@
(generate archive bodyS)))
.let [function_class (//runtime.class_name function_context)]
[fields methods instance] (..with generate archive @begin function_class environment arity bodyG)
- class (phase.lift (class.class version.v6_0
- ..modifier
- (name.internal function_class)
- (..internal /abstract.class) (list)
- fields
- methods
- (row.row)))
+ class (phase.lifted (class.class version.v6_0
+ ..modifier
+ (name.internal function_class)
+ (..internal /abstract.class) (list)
+ fields
+ methods
+ (row.row)))
.let [bytecode (format.result class.writer class)]
_ (generation.execute! [function_class bytecode])
_ (generation.save! function_class #.None [function_class bytecode])]
@@ -121,13 +121,13 @@
(do {! phase.monad}
[abstractionG (generate archive abstractionS)
inputsG (monad.map ! (generate archive) inputsS)]
- (in ($_ _.compose
+ (in ($_ _.composite
abstractionG
(|> inputsG
(list.sub /arity.maximum)
(monad.map _.monad
(function (_ batchG)
- ($_ _.compose
+ ($_ _.composite
(_.checkcast /abstract.class)
(monad.seq _.monad batchG)
(_.invokevirtual /abstract.class //runtime.apply::name (//runtime.apply::type (list.size batchG)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux
index 328921a19..ba69187b8 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux
@@ -25,14 +25,14 @@
(def: .public (get class name)
(-> (Type Class) Text (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
////reference.this
(_.getfield class name ..type)
))
(def: .public (put naming class register value)
(-> (-> Register Text) (Type Class) Register (Bytecode Any) (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
////reference.this
value
(_.putfield class (naming register) ..type)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux
index 0b4208bec..57d285e8a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux
@@ -32,7 +32,7 @@
(def: .public (initial amount)
(-> Nat (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
(|> _.aconst_null
(list.repeated amount)
(monad.seq _.monad))
@@ -53,7 +53,7 @@
(def: .public (new arity)
(-> Arity (Bytecode Any))
(if (arity.multiary? arity)
- ($_ _.compose
+ ($_ _.composite
/count.initial
(initial (n.- ///arity.minimum arity)))
(_\in [])))
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 4bc179078..30f27def6 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,14 +18,17 @@
(def: .public initial
(Bytecode Any)
- (|> +0 signed.s1 try.assumed _.bipush))
+ (|> +0
+ signed.s1
+ try.trusted
+ _.bipush))
(def: this
_.aload_0)
(def: .public value
(Bytecode Any)
- ($_ _.compose
+ ($_ _.composite
..this
(_.getfield /////abstract.class ..field ..type)
))
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 f90f1999b..da3292be8 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
@@ -49,13 +49,13 @@
(def: (increment by)
(-> Nat (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
(<| _.int .i64 by)
_.iadd))
(def: (inputs offset amount)
(-> Register Nat (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
(|> amount
list.indices
(monad.map _.monad (|>> (n.+ offset) _.aload)))
@@ -65,7 +65,7 @@
(def: (apply offset amount)
(-> Register Nat (Bytecode Any))
(let [arity (n.min amount ///arity.maximum)]
- ($_ _.compose
+ ($_ _.composite
(_.checkcast ///abstract.class)
(..inputs offset arity)
(_.invokevirtual ///abstract.class ////runtime.apply::name (////runtime.apply::type arity))
@@ -86,7 +86,7 @@
(////runtime.apply::type apply_arity)
(list)
(#.Some (case num_partials
- 0 ($_ _.compose
+ 0 ($_ _.composite
////reference.this
(..inputs ..this_offset apply_arity)
(_.invokevirtual class //implementation.name (//implementation.type function_arity))
@@ -107,10 +107,10 @@
already_partial? (n.> 0 stage)
exact_match? (i.= over_extent (.int stage))
has_more_than_necessary? (i.> over_extent (.int stage))]
- ($_ _.compose
+ ($_ _.composite
(_.set_label @case)
(cond exact_match?
- ($_ _.compose
+ ($_ _.composite
////reference.this
(if already_partial?
(_.invokevirtual class //reset.name (//reset.type class))
@@ -123,7 +123,7 @@
has_more_than_necessary?
(let [arity_inputs (|> function_arity (n.- stage))
additional_inputs (|> apply_arity (n.- arity_inputs))]
- ($_ _.compose
+ ($_ _.composite
////reference.this
(_.invokevirtual class //reset.name (//reset.type class))
current_partials
@@ -139,7 +139,7 @@
missing_partials (|> _.aconst_null
(list.repeated (|> num_partials (n.- apply_arity) (n.- stage)))
(monad.seq _.monad))]
- ($_ _.compose
+ ($_ _.composite
(_.new class)
_.dup
current_environment
@@ -151,7 +151,7 @@
(_.invokevirtual class //init.name (//init.type environment function_arity))
_.areturn)))))))
(monad.seq _.monad))]]
- ($_ _.compose
+ ($_ _.composite
///partial/count.value
- (_.tableswitch (try.assumed (signed.s4 +0)) @default [@labelsH @labelsT])
+ (_.tableswitch (try.trusted (signed.s4 +0)) @default [@labelsH @labelsT])
cases)))))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux
index a43a4c0bc..a6bd0ef6b 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux
@@ -31,7 +31,7 @@
(method.method //.modifier name
(..type arity)
(list)
- (#.Some ($_ _.compose
+ (#.Some ($_ _.composite
(_.set_label @begin)
body
_.areturn
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 ac11c1cf3..cd92f4aca 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,12 +56,16 @@
type.void
(list)]))
-(def: no_partials (|> 0 unsigned.u1 try.assumed _.bipush))
+(def: no_partials
+ (|> 0
+ unsigned.u1
+ try.trusted
+ _.bipush))
(def: .public (super environment_size arity)
(-> Nat Arity (Bytecode Any))
(let [arity_register (inc environment_size)]
- ($_ _.compose
+ ($_ _.composite
(if (arity.unary? arity)
..no_partials
(_.iload arity_register))
@@ -90,7 +94,7 @@
(method.method //.modifier ..name
(..type environment arity)
(list)
- (#.Some ($_ _.compose
+ (#.Some ($_ _.composite
////reference.this
(..super environment_size arity)
(store_all environment_size (///foreign.put class) offset_foreign)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux
index 45ea0b010..d153b35e9 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux
@@ -44,7 +44,7 @@
(def: .public (instance' foreign_setup class environment arity)
(-> (List (Bytecode Any)) (Type Class) (Environment Synthesis) Arity (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
(_.new class)
_.dup
(monad.seq _.monad foreign_setup)
@@ -69,7 +69,7 @@
(method.method //.modifier //init.name
(//init.type environment arity)
(list)
- (#.Some ($_ _.compose
+ (#.Some ($_ _.composite
////reference.this
(//init.super environment_size arity)
(monad.map _.monad (function (_ register)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux
index 615cc0388..d787bf16e 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux
@@ -43,7 +43,7 @@
(method.method //.modifier ..name
(..type class)
(list)
- (#.Some ($_ _.compose
+ (#.Some ($_ _.composite
(if (arity.multiary? arity)
(//new.instance' (..current_environment class environment) class environment arity)
////reference.this)
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 4db70e828..4915e010a 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
@@ -108,7 +108,7 @@
(list (method.method ..init::modifier "<clinit>" ..init::type
(list)
(#.Some
- ($_ _.compose
+ ($_ _.composite
valueG
(_.putstatic (type.class bytecode_name (list)) ..value::field ..value::type)
_.return))))
@@ -128,7 +128,7 @@
[existing_class? (|> (atom.read! library)
(\ io.monad map (function (_ library)
(dictionary.key? library class_name)))
- (try.lift io.monad)
+ (try.lifted io.monad)
(: (IO (Try Bit))))
_ (if existing_class?
(in [])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux
index 3e009b116..6757bc987 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux
@@ -53,7 +53,7 @@
[fetchG (translate archive updateS)
.let [storeG (_.astore register)]]
(in [fetchG storeG]))))))]
- (in ($_ _.compose
+ (in ($_ _.composite
... It may look weird that first I fetch all the values separately,
... and then I store them all.
... It must be done that way in order to avoid a potential bug.
@@ -80,11 +80,11 @@
(translate archive iterationS))
.let [initializationG (|> (list.enumeration initsI+)
(list\map (function (_ [index initG])
- ($_ _.compose
+ ($_ _.composite
initG
(_.astore (n.+ offset index)))))
(monad.seq _.monad))]]
- (in ($_ _.compose
+ (in ($_ _.composite
initializationG
(_.set_label @begin)
iterationG))))
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 f7ba0eb93..419c4eac9 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
@@ -58,19 +58,19 @@
(def: amount_of_inputs
(Bytecode Any)
- ($_ _.compose
+ ($_ _.composite
_.aload_0
_.arraylength))
(def: decrease
(Bytecode Any)
- ($_ _.compose
+ ($_ _.composite
_.iconst_1
_.isub))
(def: head
(Bytecode Any)
- ($_ _.compose
+ ($_ _.composite
_.dup
_.aload_0
_.swap
@@ -81,7 +81,7 @@
(def: pair
(Bytecode Any)
- ($_ _.compose
+ ($_ _.composite
_.iconst_2
(_.anewarray ^Object)
_.dup_x1
@@ -102,7 +102,7 @@
(do _.monad
[@loop _.new_label
@end _.new_label]
- ($_ _.compose
+ ($_ _.composite
..nil
..amount_of_inputs
(_.set_label @loop)
@@ -122,7 +122,7 @@
(def: run_io
(Bytecode Any)
- ($_ _.compose
+ ($_ _.composite
(_.checkcast //function/abstract.class)
_.aconst_null
//runtime.apply))
@@ -132,7 +132,7 @@
(let [super_class (|> ..^Object type.reflection reflection.reflection name.internal)
main (method.method ..main::modifier "main" ..main::type
(list)
- (#.Some ($_ _.compose
+ (#.Some ($_ _.composite
program
..input_list
..feed_inputs
@@ -140,7 +140,7 @@
_.return)))]
[..class
(<| (format.result class.writer)
- try.assumed
+ try.trusted
(class.class version.v6_0
..program::modifier
(name.internal ..class)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux
index d983068b9..3dafea811 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux
@@ -44,7 +44,7 @@
(do {! ////.monad}
[bytecode_name (\ ! map //runtime.class_name
(generation.context archive))]
- (in ($_ _.compose
+ (in ($_ _.composite
..this
(_.getfield (type.class bytecode_name (list))
(..foreign_name variable)
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 8fcd70360..f11c871c1 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
@@ -113,13 +113,13 @@
(def: .public (get index)
(-> (Bytecode Any) (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
index
_.aaload))
(def: (set! index value)
(-> (Bytecode Any) (Bytecode Any) (Bytecode Any))
- ($_ _.compose
+ ($_ _.composite
... A
_.dup ... AA
index ... AAI
@@ -138,10 +138,10 @@
(def: variant_value _.iconst_2)
(def: variant::method
- (let [new_variant ($_ _.compose
+ (let [new_variant ($_ _.composite
_.iconst_3
(_.anewarray //type.value))
- $tag ($_ _.compose
+ $tag ($_ _.composite
_.iload_0
(//value.wrap type.int))
$last? _.aload_1
@@ -149,7 +149,7 @@
(method.method ..modifier ..variant::name
..variant::type
(list)
- (#.Some ($_ _.compose
+ (#.Some ($_ _.composite
new_variant ... A[3]
(..set! ..variant_tag $tag) ... A[3]
(..set! ..variant_last? $last?) ... A[3]
@@ -161,7 +161,7 @@
(def: .public left_injection
(Bytecode Any)
- ($_ _.compose
+ ($_ _.composite
_.iconst_0
..left_flag
_.dup2_x1
@@ -170,7 +170,7 @@
(def: .public right_injection
(Bytecode Any)
- ($_ _.compose
+ ($_ _.composite
_.iconst_1
..right_flag
_.dup2_x1
@@ -181,7 +181,7 @@
(def: .public none_injection
(Bytecode Any)
- ($_ _.compose
+ ($_ _.composite
_.iconst_0
..left_flag
..unit
@@ -192,7 +192,7 @@
(do _.monad
[@try _.new_label
@handler _.new_label]
- ($_ _.compose
+ ($_ _.composite
(_.try @try @handler @handler //type.error)
(_.set_label @try)
$unsafe
@@ -213,7 +213,7 @@
(list)
(#.Some
(..risky
- ($_ _.compose
+ ($_ _.composite
_.aload_0
(_.invokestatic //type.frac "parseDouble" (type.method [(list) (list //type.text) type.double (list)]))
(//value.wrap type.double)
@@ -226,7 +226,7 @@
out (_.getstatic ^System "out" ^PrintStream)
print_type (type.method [(list) (list //type.value) type.void (list)])
print! (function (_ method) (_.invokevirtual ^PrintStream method print_type))]
- ($_ _.compose
+ ($_ _.composite
out (_.string "LUX LOG: ") (print! "print")
out _.swap (print! "println"))))
@@ -234,7 +234,7 @@
(def: (illegal_state_exception message)
(-> Text (Bytecode Any))
(let [^IllegalStateException (type.class "java.lang.IllegalStateException" (list))]
- ($_ _.compose
+ ($_ _.composite
(_.new ^IllegalStateException)
_.dup
(_.string message)
@@ -249,7 +249,7 @@
..failure::type
(list)
(#.Some
- ($_ _.compose
+ ($_ _.composite
(..illegal_state_exception message)
_.athrow))))
@@ -271,12 +271,12 @@
..push::type
(list)
(#.Some
- (let [new_stack_frame! ($_ _.compose
+ (let [new_stack_frame! ($_ _.composite
_.iconst_2
(_.anewarray //type.value))
$head _.aload_1
$tail _.aload_0]
- ($_ _.compose
+ ($_ _.composite
new_stack_frame!
(..set! ..stack_head $head)
(..set! ..stack_tail $tail)
@@ -296,7 +296,7 @@
@tags_match! _.new_label
@maybe_nested _.new_label
@mismatch! _.new_label
- .let [::tag ($_ _.compose
+ .let [::tag ($_ _.composite
(..get ..variant_tag)
(//value.unwrap type.int))
::last? (..get ..variant_last?)
@@ -309,29 +309,29 @@
not_found _.aconst_null
update_$tag _.isub
- update_$variant ($_ _.compose
+ update_$variant ($_ _.composite
$variant ::value
(_.checkcast //type.variant)
_.astore_0)
recur (: (-> Label (Bytecode Any))
(function (_ @loop_start)
- ($_ _.compose
+ ($_ _.composite
... tag, sumT
update_$variant ... tag, sumT
update_$tag ... sub_tag
(_.goto @loop_start))))
- super_nested_tag ($_ _.compose
+ super_nested_tag ($_ _.composite
... tag, sumT
_.swap ... sumT, tag
_.isub)
- super_nested ($_ _.compose
+ super_nested ($_ _.composite
... tag, sumT
super_nested_tag ... super_tag
$variant ::last? ... super_tag, super_last
$variant ::value ... super_tag, super_last, super_value
..variant)]]
- ($_ _.compose
+ ($_ _.composite
$tag
(_.set_label @loop)
$variant ::tag
@@ -369,23 +369,23 @@
(def: projection::method2
[(Resource Method) (Resource Method)]
(let [$tuple _.aload_0
- $tuple::size ($_ _.compose
+ $tuple::size ($_ _.composite
$tuple _.arraylength)
$lefts _.iload_1
- $last_right ($_ _.compose
+ $last_right ($_ _.composite
$tuple::size _.iconst_1 _.isub)
- update_$lefts ($_ _.compose
+ update_$lefts ($_ _.composite
$lefts $last_right _.isub
_.istore_1)
- update_$tuple ($_ _.compose
+ update_$tuple ($_ _.composite
$tuple $last_right _.aaload (_.checkcast //type.tuple)
_.astore_0)
recur (: (-> Label (Bytecode Any))
(function (_ @loop)
- ($_ _.compose
+ ($_ _.composite
update_$lefts
update_$tuple
(_.goto @loop))))
@@ -397,9 +397,9 @@
(do _.monad
[@loop _.new_label
@recursive _.new_label
- .let [::left ($_ _.compose
+ .let [::left ($_ _.composite
$lefts _.aaload)]]
- ($_ _.compose
+ ($_ _.composite
(_.set_label @loop)
$lefts $last_right (_.if_icmpge @recursive)
$tuple ::left
@@ -416,19 +416,19 @@
[@loop _.new_label
@not_tail _.new_label
@slice _.new_label
- .let [$right ($_ _.compose
+ .let [$right ($_ _.composite
$lefts
_.iconst_1
_.iadd)
- $::nested ($_ _.compose
+ $::nested ($_ _.composite
$tuple _.swap _.aaload)
- super_nested ($_ _.compose
+ super_nested ($_ _.composite
$tuple
$right
$tuple::size
(_.invokestatic (type.class "java.util.Arrays" (list)) "copyOfRange"
(type.method [(list) (list //type.tuple //type.index //type.index) //type.tuple (list)])))]]
- ($_ _.compose
+ ($_ _.composite
(_.set_label @loop)
$last_right $right
_.dup2 (_.if_icmpne @not_tail)
@@ -472,13 +472,13 @@
unit _.aconst_null
^StringWriter (type.class "java.io.StringWriter" (list))
- string_writer ($_ _.compose
+ string_writer ($_ _.composite
(_.new ^StringWriter)
_.dup
(_.invokespecial ^StringWriter "<init>" (type.method [(list) (list) type.void (list)])))
^PrintWriter (type.class "java.io.PrintWriter" (list))
- print_writer ($_ _.compose
+ print_writer ($_ _.composite
... WTW
(_.new ^PrintWriter) ... WTWP
_.dup_x1 ... WTPWP
@@ -487,7 +487,7 @@
(_.invokespecial ^PrintWriter "<init>" (type.method [(list) (list (type.class "java.io.Writer" (list)) type.boolean) type.void (list)]))
... WTP
)]]
- ($_ _.compose
+ ($_ _.composite
(_.try @try @handler @handler //type.error)
(_.set_label @try)
$unsafe unit ..apply
@@ -516,7 +516,7 @@
class.public
class.final))
bytecode (<| (format.result class.writer)
- try.assumed
+ try.trusted
(class.class jvm/version.v6_0
modifier
(name.internal class)
@@ -551,7 +551,7 @@
(let [previous_inputs (|> arity
list.indices
(monad.map _.monad _.aload))]
- ($_ _.compose
+ ($_ _.composite
previous_inputs
(_.invokevirtual //function.class ..apply::name (..apply::type (dec arity)))
(_.checkcast //function.class)
@@ -566,7 +566,7 @@
(list)
(#.Some
(let [$partials _.iload_1]
- ($_ _.compose
+ ($_ _.composite
..this
(_.invokespecial ^Object "<init>" (type.method [(list) (list) type.void (list)]))
..this
@@ -584,7 +584,7 @@
//function/count.type
(row.row)))
bytecode (<| (format.result class.writer)
- try.assumed
+ try.trusted
(class.class jvm/version.v6_0
modifier
(name.internal class)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux
index fa7627b97..2eff33115 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux
@@ -44,6 +44,6 @@
(def: .public (unwrap type)
(-> (Type Primitive) (Bytecode Any))
(let [wrapper (type.class (primitive_wrapper type) (list))]
- ($_ _.compose
+ ($_ _.composite
(_.checkcast wrapper)
(_.invokevirtual wrapper (primitive_unwrap type) (type.method [(list) (list) type (list)])))))
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 2b9202239..c234f9902 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
@@ -100,4 +100,4 @@
Phase
(do phase.monad
[synthesis (..optimization archive analysis)]
- (phase.lift (/variable.optimization synthesis))))
+ (phase.lifted (/variable.optimization synthesis))))
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 78dc5dce1..feadf7fa5 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
@@ -241,7 +241,7 @@
dictionary.entries
(list\map (function (_ [register redundant?])
(%.format (%.nat register) ": " (%.bit redundant?))))
- (text.join_with ", ")))
+ (text.interposed ", ")))
(def: (path_optimization optimization)
(-> (Optimization Synthesis) (Optimization Path))
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 806fdc3c9..58dc336dd 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux
@@ -279,7 +279,7 @@
(|> (#.Item item)
(list\map (function (_ [test then])
(format (<format> test) " " (%path' %then then))))
- (text.join_with " ")
+ (text.interposed " ")
(text.enclosed ["(? " ")"]))])
([#I64_Fork (|>> .int %.int)]
[#F64_Fork %.frac]
@@ -341,7 +341,7 @@
(#analysis.Tuple members)
(|> members
(list\map %synthesis)
- (text.join_with " ")
+ (text.interposed " ")
(text.enclosed ["[" "]"])))
(#Reference reference)
@@ -354,7 +354,7 @@
(#Abstraction [environment arity body])
(let [environment' (|> environment
(list\map %synthesis)
- (text.join_with " ")
+ (text.interposed " ")
(text.enclosed ["[" "]"]))]
(|> (format environment' " " (%.nat arity) " " (%synthesis body))
(text.enclosed ["(#function " ")"])))
@@ -362,7 +362,7 @@
(#Apply func args)
(|> args
(list\map %synthesis)
- (text.join_with " ")
+ (text.interposed " ")
(format (%synthesis func) " ")
(text.enclosed ["(" ")"])))
@@ -392,7 +392,7 @@
(|> (format (%.nat (get@ #start scope))
" " (|> (get@ #inits scope)
(list\map %synthesis)
- (text.join_with " ")
+ (text.interposed " ")
(text.enclosed ["[" "]"]))
" " (%synthesis (get@ #iteration scope)))
(text.enclosed ["(#loop " ")"]))
@@ -400,12 +400,12 @@
(#Recur args)
(|> args
(list\map %synthesis)
- (text.join_with " ")
+ (text.interposed " ")
(text.enclosed ["(#recur " ")"]))))
(#Extension [name args])
(|> (list\map %synthesis args)
- (text.join_with " ")
+ (text.interposed " ")
(format (%.text name) " ")
(text.enclosed ["(" ")"]))))
diff --git a/stdlib/source/library/lux/tool/compiler/phase.lux b/stdlib/source/library/lux/tool/compiler/phase.lux
index d1cecbe50..92680654d 100644
--- a/stdlib/source/library/lux/tool/compiler/phase.lux
+++ b/stdlib/source/library/lux/tool/compiler/phase.lux
@@ -70,13 +70,13 @@
(def: .public failure
(-> Text Operation)
- (|>> #try.Failure (state.lift try.monad)))
+ (|>> #try.Failure (state.lifted try.monad)))
(def: .public (except exception parameters)
(All [e] (-> (Exception e) e Operation))
(..failure (ex.error exception parameters)))
-(def: .public (lift error)
+(def: .public (lifted error)
(All [s a] (-> (Try a) (Operation s a)))
(function (_ state)
(try\map (|>> [state]) error)))
@@ -93,7 +93,7 @@
(function (_ archive input state)
(#try.Success [state input])))
-(def: .public (compose pre post)
+(def: .public (composite pre post)
(All [s0 s1 i t o]
(-> (Phase s0 i t)
(Phase s1 t o)