aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/tool/compiler
diff options
context:
space:
mode:
authorEduardo Julian2021-08-02 20:26:21 -0400
committerEduardo Julian2021-08-02 20:26:21 -0400
commiteff4c59794868b89d60fdc411f9b544a270b817e (patch)
treee88c4dd09acdf1e83c8683940c0496a844096dfe /stdlib/source/library/lux/tool/compiler
parentbcd70df3568d71f14763959f454c15d8164e2d15 (diff)
Fixed a bug in the new compiler which allowed the same module to be imported more than once.
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/init.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/platform.lux111
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/generation.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux26
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux14
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux18
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux30
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux16
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux38
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux18
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/program.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/io/context.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/phase.lux2
49 files changed, 226 insertions, 203 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux
index 1a8617f53..ecd883cfe 100644
--- a/stdlib/source/library/lux/tool/compiler/default/init.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/init.lux
@@ -186,7 +186,7 @@
post_payload (..get_current_payload pre_payoad)]
(in [requirements post_payload])))
-(def: (iteration archive expander reader source pre_payload)
+(def: (iteration' archive expander reader source pre_payload)
(All [directive]
(-> Archive Expander Reader Source (Payload directive)
(All [anchor expression]
@@ -198,7 +198,7 @@
[requirements post_payload] (process_directive archive expander pre_payload code)]
(in [source requirements post_payload])))
-(def: (iterate archive expander module source pre_payload aliases)
+(def: (iteration archive expander module source pre_payload aliases)
(All [directive]
(-> Archive Expander Module Source (Payload directive) Aliases
(All [anchor expression]
@@ -208,7 +208,7 @@
[reader (///directive.lift_analysis
(..reader module aliases source))]
(function (_ state)
- (case (///phase.run' state (..iteration archive expander reader source pre_payload))
+ (case (///phase.run' state (..iteration' archive expander reader source pre_payload))
(#try.Success [state source&requirements&buffer])
(#try.Success [state (#.Some source&requirements&buffer)])
@@ -243,7 +243,7 @@
(..begin dependencies hash input))
#let [module (get@ #///.module input)]]
(loop [iteration (<| (///phase.run' state)
- (..iterate archive expander module source buffer ///syntax.no_aliases))]
+ (..iteration archive expander module source buffer ///syntax.no_aliases))]
(do !
[[state ?source&requirements&temporary_payload] iteration]
(case ?source&requirements&temporary_payload
@@ -284,5 +284,5 @@
(get@ #///directive.referrals)
(monad.map ! (execute! archive)))
temporary_payload (..get_current_payload temporary_payload)]
- (..iterate archive expander module source temporary_payload (..module_aliases analysis_module))))))})]))
+ (..iteration archive expander module source temporary_payload (..module_aliases analysis_module))))))})]))
)))))}))))
diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux
index 1848c28bc..8a3f17237 100644
--- a/stdlib/source/library/lux/tool/compiler/default/platform.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux
@@ -8,7 +8,7 @@
["." monad (#+ Monad do)]]
[control
["." function]
- ["." try (#+ Try) ("#\." functor)]
+ ["." try (#+ Try) ("#\." monad)]
["." exception (#+ exception:)]
[concurrency
["." async (#+ Async Resolver) ("#\." monad)]
@@ -366,6 +366,12 @@
["Importer" (%.text importer)]
["importee" (%.text importee)]))
+ (exception: #export (cannot_import_twice {importer Module}
+ {duplicates (Set Module)})
+ (exception.report
+ ["Importer" (%.text importer)]
+ ["Duplicates" (%.list %.text (set.to_list duplicates))]))
+
(def: (verify_dependencies importer importee dependence)
(-> Module Module Dependence (Try Any))
(cond (text\= importer importee)
@@ -541,20 +547,34 @@
module)]
(loop [[archive state] [archive state]
compilation (base_compiler (:as ///.Input input))
- all_dependencies (: (List Module)
- (list))]
- (let [new_dependencies (get@ #///.dependencies compilation)
- all_dependencies (list\compose new_dependencies all_dependencies)
- continue! (:sharing [<type_vars>]
- <Platform>
- platform
-
- (-> <Context> (///.Compilation <State+> .Module Any) (List Module)
- (Action [Archive <State+>]))
- (:assume
- recur))]
- (do !
- [[archive state] (case new_dependencies
+ all_dependencies (: (Set Module)
+ (set.of_list text.hash (list)))]
+ (do !
+ [#let [new_dependencies (get@ #///.dependencies compilation)
+ continue! (:sharing [<type_vars>]
+ <Platform>
+ platform
+
+ (-> <Context> (///.Compilation <State+> .Module Any) (Set Module)
+ (Action [Archive <State+>]))
+ (:assume recur))
+ ## TODO: Come up with a less hacky way to prevent duplicate imports.
+ ## This currently assumes that all imports will be specified once in a single .module: form.
+ ## This might not be the case in the future.
+ [all_dependencies duplicates _] (: [(Set Module) (Set Module) Bit]
+ (list\fold (function (_ new [all duplicates seen_prelude?])
+ (if (set.member? all new)
+ (if (text\= .prelude_module new)
+ (if seen_prelude?
+ [all (set.add new duplicates) seen_prelude?]
+ [all duplicates true])
+ [all (set.add new duplicates) seen_prelude?])
+ [(set.add new all) duplicates seen_prelude?]))
+ (: [(Set Module) (Set Module) Bit]
+ [all_dependencies ..empty (set.empty? all_dependencies)])
+ new_dependencies))]
+ [archive state] (if (set.empty? duplicates)
+ (case new_dependencies
#.End
(in [archive state])
@@ -567,36 +587,37 @@
(list\map product.left)
(list\fold archive.merged archive))]]
(in [archive (try.assumed
- (..updated_state archive state))])))]
- (case ((get@ #///.process compilation)
- ## TODO: The "///directive.set_current_module" below shouldn't be necessary. Remove it ASAP.
- ## TODO: The context shouldn't need to be re-set either.
- (|> (///directive.set_current_module module)
- (///phase.run' state)
- try.assumed
- product.left)
- archive)
- (#try.Success [state more|done])
- (case more|done
- (#.Left more)
- (continue! [archive state] more all_dependencies)
-
- (#.Right [descriptor document output])
- (do !
- [#let [_ (debug.log! (..module_compilation_log module state))
- descriptor (set@ #descriptor.references (set.of_list text.hash all_dependencies) descriptor)]
- _ (..cache_module static platform module_id [descriptor document output])]
- (case (archive.add module [descriptor document output] archive)
- (#try.Success archive)
- (in [archive
- (..with_reset_log state)])
-
- (#try.Failure error)
- (async\in (#try.Failure error)))))
-
- (#try.Failure error)
+ (..updated_state archive state))])))
+ (async\in (exception.except ..cannot_import_twice [module duplicates])))]
+ (case ((get@ #///.process compilation)
+ ## TODO: The "///directive.set_current_module" below shouldn't be necessary. Remove it ASAP.
+ ## TODO: The context shouldn't need to be re-set either.
+ (|> (///directive.set_current_module module)
+ (///phase.run' state)
+ try.assumed
+ product.left)
+ archive)
+ (#try.Success [state more|done])
+ (case more|done
+ (#.Left more)
+ (continue! [archive state] more all_dependencies)
+
+ (#.Right [descriptor document output])
(do !
- [_ (ioW.freeze (get@ #&file_system platform) static archive)]
- (async\in (#try.Failure error))))))))))]
+ [#let [_ (debug.log! (..module_compilation_log module state))
+ descriptor (set@ #descriptor.references all_dependencies descriptor)]
+ _ (..cache_module static platform module_id [descriptor document output])]
+ (case (archive.add module [descriptor document output] archive)
+ (#try.Success archive)
+ (in [archive
+ (..with_reset_log state)])
+
+ (#try.Failure error)
+ (async\in (#try.Failure error)))))
+
+ (#try.Failure error)
+ (do !
+ [_ (ioW.freeze (get@ #&file_system platform) static archive)]
+ (async\in (#try.Failure error)))))))))]
(compiler archive.runtime_module compilation_module)))
)))
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 02100305d..7dc985749 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
@@ -471,7 +471,7 @@
(def: #export (except exception parameters)
(All [e] (-> (Exception e) e Operation))
- (..failure (exception.construct exception parameters)))
+ (..failure (exception.error exception parameters)))
(def: #export (assertion exception parameters condition)
(All [e] (-> (Exception e) e Bit (Operation Any)))
@@ -486,7 +486,7 @@
(def: #export (except' exception parameters)
(All [e] (-> (Exception e) e (phase.Operation Lux)))
- (..failure' (exception.construct exception parameters)))
+ (..failure' (exception.error exception parameters)))
(def: #export (with_stack exception message action)
(All [e o] (-> (Exception e) e (Operation o) (Operation o)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux
index ecc765794..95f38c760 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux
@@ -16,14 +16,14 @@
(exception: #export (expansion_failed {macro Name} {inputs (List Code)} {error Text})
(exception.report
["Macro" (%.name macro)]
- ["Inputs" (exception.enumerate %.code inputs)]
+ ["Inputs" (exception.listing %.code inputs)]
["Error" error]))
(exception: #export (must_have_single_expansion {macro Name} {inputs (List Code)} {outputs (List Code)})
(exception.report
["Macro" (%.name macro)]
- ["Inputs" (exception.enumerate %.code inputs)]
- ["Outputs" (exception.enumerate %.code outputs)]))
+ ["Inputs" (exception.listing %.code inputs)]
+ ["Outputs" (exception.listing %.code outputs)]))
(type: #export Expander
(-> Macro (List Code) Lux (Try (Try [Lux (List Code)]))))
@@ -38,7 +38,7 @@
(#try.Success output)
(#try.Failure error)
- ((meta.failure (exception.construct ..expansion_failed [name inputs error])) state)))))
+ ((meta.failure (exception.error ..expansion_failed [name inputs error])) state)))))
(def: #export (expand_one expander name macro inputs)
(-> Expander Name Macro (List Code) (Meta Code))
@@ -49,4 +49,4 @@
(in single)
_
- (meta.failure (exception.construct ..must_have_single_expansion [name inputs expansion])))))
+ (meta.failure (exception.error ..must_have_single_expansion [name inputs expansion])))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux
index bbe6da451..856a044fb 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux
@@ -258,7 +258,7 @@
(exception.report
["Definition" (name.short name)]
["Module" (name.module name)]
- ["Known Definitions" (exception.enumerate function.identity known_definitions)]))
+ ["Known Definitions" (exception.listing function.identity known_definitions)]))
(def: #export (remember archive name)
(All [anchor expression directive]
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 c7b843385..fe7de804f 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
@@ -255,7 +255,7 @@
size_sum (list.size flat_sum)
num_cases (maybe.else size_sum num_tags)
idx (/.tag lefts right?)]
- (.case (list.nth idx flat_sum)
+ (.case (list.item idx flat_sum)
(^multi (#.Some caseT)
(n.< num_cases idx))
(do ///.monad
@@ -288,7 +288,7 @@
(/.with_location location
(do ///.monad
[tag (///extension.lift (meta.normal tag))
- [idx group variantT] (///extension.lift (meta.resolve_tag tag))
+ [idx group variantT] (///extension.lift (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 7799be183..a0d02badc 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
@@ -1,12 +1,12 @@
(.module:
[library
- [lux #*
+ [lux (#- Variant)
[abstract
equivalence
["." monad (#+ do)]]
[control
["." try (#+ Try) ("#\." monad)]
- ["ex" exception (#+ exception:)]]
+ ["." exception (#+ exception:)]]
[data
["." bit ("#\." equivalence)]
["." maybe]
@@ -166,8 +166,9 @@
## Because of that, the presence of redundant patterns is assumed to
## be a bug, likely due to programmer carelessness.
(exception: #export (redundant_pattern {so_far Coverage} {addition Coverage})
- (ex.report ["Coverage so-far" (%coverage so_far)]
- ["Coverage addition" (%coverage addition)]))
+ (exception.report
+ ["Coverage so-far" (%coverage so_far)]
+ ["Coverage addition" (%coverage addition)]))
(def: (flat_alt coverage)
(-> Coverage (List Coverage))
@@ -210,8 +211,9 @@
(open: "coverage/." ..equivalence)
(exception: #export (variants_do_not_match {addition_cases Nat} {so_far_cases Nat})
- (ex.report ["So-far Cases" (%.nat so_far_cases)]
- ["Addition Cases" (%.nat addition_cases)]))
+ (exception.report
+ ["So-far Cases" (%.nat so_far_cases)]
+ ["Addition Cases" (%.nat addition_cases)]))
## After determining the coverage of each individual pattern, it is
## necessary to merge them all to figure out if the entire
@@ -234,10 +236,10 @@
(cond (and (known_cases? addition_cases)
(known_cases? so_far_cases)
(not (n.= addition_cases so_far_cases)))
- (ex.except ..variants_do_not_match [addition_cases so_far_cases])
+ (exception.except ..variants_do_not_match [addition_cases so_far_cases])
(\ (dictionary.equivalence ..equivalence) = casesSF casesA)
- (ex.except ..redundant_pattern [so_far addition])
+ (exception.except ..redundant_pattern [so_far addition])
## else
(do {! try.monad}
@@ -291,11 +293,11 @@
## There is nothing the addition adds to the coverage.
[#1 #1]
- (ex.except ..redundant_pattern [so_far addition]))
+ (exception.except ..redundant_pattern [so_far addition]))
## The addition cannot possibly improve the coverage.
[_ #Exhaustive]
- (ex.except ..redundant_pattern [so_far addition])
+ (exception.except ..redundant_pattern [so_far addition])
## The addition completes the coverage.
[#Exhaustive _]
@@ -304,7 +306,7 @@
## The left part will always match, so the addition is redundant.
(^multi [(#Seq left right) single]
(coverage/= left single))
- (ex.except ..redundant_pattern [so_far addition])
+ (exception.except ..redundant_pattern [so_far addition])
## The right part is not necessary, since it can always match the left.
(^multi [single (#Seq left right)]
@@ -368,6 +370,6 @@
_
(if (coverage/= so_far addition)
## The addition cannot possibly improve the coverage.
- (ex.except ..redundant_pattern [so_far addition])
+ (exception.except ..redundant_pattern [so_far addition])
## There are now 2 alternative paths.
(try\in (#Alt so_far addition)))))
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 7fb985f4b..d50f72630 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
@@ -58,7 +58,7 @@
(recur value)
#.None
- (/.failure (ex.construct cannot_analyse [expectedT function_name arg_name body])))
+ (/.failure (ex.error cannot_analyse [expectedT function_name arg_name body])))
(^template [<tag> <instancer>]
[(<tag> _)
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 05a147c3d..8daf5242f 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
@@ -37,7 +37,7 @@
(exception: #export (cannot_infer {type Type} {args (List Code)})
(exception.report
["Type" (%.type type)]
- ["Arguments" (exception.enumerate %.code args)]))
+ ["Arguments" (exception.listing %.code args)]))
(exception: #export (cannot_infer_argument {inferred Type} {argument Code})
(exception.report
@@ -264,7 +264,7 @@
(cond (or (n.= expected_size actual_size)
(and (n.> expected_size actual_size)
(n.< boundary tag)))
- (case (list.nth tag cases)
+ (case (list.item tag cases)
(#.Some caseT)
(///\in (if (n.= 0 depth)
(type.function (list caseT) currentT)
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 0af3736ac..b0d9920df 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
@@ -67,7 +67,7 @@
["Old annotations" (%.code old)]
["New annotations" (%.code new)]))
-(def: #export (new hash)
+(def: #export (empty hash)
(-> Nat Module)
{#.module_hash hash
#.module_aliases (list)
@@ -158,7 +158,7 @@
(///extension.lift
(function (_ state)
(#try.Success [(update@ #.modules
- (plist.put name (new hash))
+ (plist.put name (..empty hash))
state)
[]]))))
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 4ecca3d1a..1a787efec 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
@@ -102,7 +102,7 @@
(case expectedT
(#.Sum _)
(let [flat (type.flat_variant expectedT)]
- (case (list.nth tag flat)
+ (case (list.item tag flat)
(#.Some variant_type)
(do !
[valueA (//type.with_type variant_type
@@ -263,7 +263,7 @@
(-> Phase Name Phase)
(do {! ///.monad}
[tag (///extension.lift (meta.normal tag))
- [idx group variantT] (///extension.lift (meta.resolve_tag tag))
+ [idx group variantT] (///extension.lift (meta.tag tag))
#let [case_size (list.size group)
[lefts right?] (/.choice case_size idx)]
expectedT (///extension.lift meta.expected_type)]
@@ -308,7 +308,7 @@
(#.Item [head_k head_v] _)
(do {! ///.monad}
[head_k (///extension.lift (meta.normal head_k))
- [_ tag_set recordT] (///extension.lift (meta.resolve_tag head_k))
+ [_ tag_set recordT] (///extension.lift (meta.tag head_k))
#let [size_record (list.size record)
size_ts (list.size tag_set)]
_ (if (n.= size_ts size_record)
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 aa78e8ade..60f625250 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
@@ -73,7 +73,7 @@
(exception: #export [a] (invalid_syntax {name Name} {%format (Format a)} {inputs (List a)})
(exception.report
["Extension" (%.text name)]
- ["Inputs" (exception.enumerate %format inputs)]))
+ ["Inputs" (exception.listing %format inputs)]))
(exception: #export [s i o] (unknown {name Name} {bundle (Bundle s i o)})
(exception.report
@@ -81,7 +81,7 @@
["Available" (|> bundle
dictionary.keys
(list.sort text\<)
- (exception.enumerate %.text))]))
+ (exception.listing %.text))]))
(type: #export (Extender s i o)
(-> Any (Handler s i o)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
index 0a60511ab..8d38f4754 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
@@ -230,8 +230,8 @@
(exception.report
["Class" class]
["Method" method]
- ["Arguments" (exception.enumerate ..signature inputsJT)]
- ["Hints" (exception.enumerate %.type (list\map product.left hints))]))]
+ ["Arguments" (exception.listing ..signature inputsJT)]
+ ["Hints" (exception.listing %.type (list\map product.left hints))]))]
[no_candidates]
[too_many_candidates]
@@ -1589,7 +1589,7 @@
(template [<name>]
[(exception: #export (<name> {methods (List [Text (Type Method)])})
(exception.report
- ["Methods" (exception.enumerate
+ ["Methods" (exception.listing
(function (_ [name type])
(format (%.text name) " " (..signature type)))
methods)]))]
@@ -1889,7 +1889,7 @@
(exception: #export (unknown_super {name Text} {supers (List (Type Class))})
(exception.report
["Name" (%.text name)]
- ["Available" (exception.enumerate (|>> jvm_parser.read_class product.left) supers)]))
+ ["Available" (exception.listing (|>> jvm_parser.read_class product.left) supers)]))
(exception: #export (mismatched_super_parameters {name Text} {expected Nat} {actual Nat})
(exception.report
@@ -2052,9 +2052,9 @@
{actual (List (Type Parameter))})
(exception.report
["Expected (amount)" (%.nat (list.size expected))]
- ["Expected (parameters)" (exception.enumerate %.text expected)]
+ ["Expected (parameters)" (exception.listing %.text expected)]
["Actual (amount)" (%.nat (list.size actual))]
- ["Actual (parameters)" (exception.enumerate ..signature actual)]))
+ ["Actual (parameters)" (exception.listing ..signature actual)]))
(def: (super_aliasing class_loader class)
(-> java/lang/ClassLoader (Type Class) (Operation Aliasing))
@@ -2141,7 +2141,7 @@
super_interfaces))
selfT (///.lift (do meta.monad
[where meta.current_module_name
- id meta.count]
+ id meta.seed]
(in (inheritance_relationship_type (#.Primitive (..anonymous_class_name where id) (list))
super_classT
super_interfaceT+))))
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 906b54e23..470078b0f 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,8 +90,8 @@
(do <>.monad
[raw <code>.text]
(case (text.size raw)
- 1 (in (|> raw (text.nth 0) maybe.assume))
- _ (<>.failure (exception.construct ..char_text_must_be_size_1 [raw])))))
+ 1 (in (|> raw (text.char 0) maybe.assume))
+ _ (<>.failure (exception.error ..char_text_must_be_size_1 [raw])))))
(def: lux::syntax_char_case!
(..custom
@@ -164,9 +164,9 @@
(case args
(^ (list typeC valueC))
(do {! ////.monad}
- [count (///.lift meta.count)
+ [seed (///.lift meta.seed)
actualT (\ ! map (|>> (:as Type))
- (eval archive count Type typeC))
+ (eval archive seed Type typeC))
_ (typeA.infer actualT)]
(typeA.with_type actualT
(analyse archive valueC)))
@@ -180,9 +180,9 @@
(case args
(^ (list typeC valueC))
(do {! ////.monad}
- [count (///.lift meta.count)
+ [seed (///.lift meta.seed)
actualT (\ ! map (|>> (:as Type))
- (eval archive count Type typeC))
+ (eval archive seed Type typeC))
_ (typeA.infer actualT)
[valueT valueA] (typeA.with_inference
(analyse archive valueC))]
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 2c78f5988..8f61e7ea8 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
@@ -345,7 +345,7 @@
(in elementJT)
#.None
- (<>.failure (exception.construct ..not_an_object_array arrayJT)))
+ (<>.failure (exception.error ..not_an_object_array arrayJT)))
#.None
(undefined))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux
index a66a198c7..b728760c0 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux
@@ -43,7 +43,7 @@
(def: (array::read [indexG arrayG])
(Binary Expression)
- (_.nth (_.+ (_.int +1) indexG) arrayG))
+ (_.item (_.+ (_.int +1) indexG) arrayG))
(def: (array::write [indexG valueG arrayG])
(Trinary Expression)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux
index 39ddd3df9..f7a42c5d2 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux
@@ -39,7 +39,7 @@
(def: (array::read [indexG arrayG])
(Binary Expression)
- (_.nth indexG arrayG))
+ (_.item indexG arrayG))
(def: (array::write [indexG valueG arrayG])
(Trinary Expression)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux
index 56393387f..57e53f579 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux
@@ -42,7 +42,7 @@
(def: (array::read [indexG arrayG])
(Binary (Expression Any))
- (_.nth indexG arrayG))
+ (_.item indexG arrayG))
(def: (array::write [indexG valueG arrayG])
(Trinary (Expression Any))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux
index 9e6df81c7..cb2e4d28b 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux
@@ -43,7 +43,7 @@
(def: (array::read [indexG arrayG])
(Binary Expression)
- (_.nth indexG arrayG))
+ (_.item indexG arrayG))
(def: (array::write [indexG valueG arrayG])
(Trinary Expression)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux
index 6b390352b..b69836192 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux
@@ -90,7 +90,7 @@
(syntax: #export (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))}
body)
(do {! meta.monad}
- [ids (monad.seq ! (list.repeat (list.size vars) meta.count))]
+ [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))]
(in (list (` (let [(~+ (|> vars
(list.zipped/2 ids)
(list\map (function (_ [id var])
@@ -104,7 +104,7 @@
(<>.some <code>.local_identifier))))}
code)
(do meta.monad
- [runtime_id meta.count]
+ [runtime_id meta.seed]
(macro.with_gensyms [g!_]
(let [runtime (code.local_identifier (///reference.artifact [..module_id runtime_id]))
runtime_name (` (_.var (~ (code.text (%.code runtime)))))]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
index 5ac8a93ec..d351cd6ac 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
@@ -88,7 +88,7 @@
(syntax: #export (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))}
body)
(do {! meta.monad}
- [ids (monad.seq ! (list.repeat (list.size vars) meta.count))]
+ [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))]
(in (list (` (let [(~+ (|> vars
(list.zipped/2 ids)
(list\map (function (_ [id var])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux
index 0e1b681c4..6d1fda16c 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux
@@ -113,7 +113,7 @@
(def: peek
Expression
- (_.nth (_.length @cursor) @cursor))
+ (_.item (_.length @cursor) @cursor))
(def: save!
Statement
@@ -214,7 +214,7 @@
[/////synthesis.side/right /////synthesis.simple_right_side ..right_choice])
(^ (/////synthesis.member/left 0))
- (///////phase\in (|> ..peek (_.nth (_.int +1)) ..push!))
+ (///////phase\in (|> ..peek (_.item (_.int +1)) ..push!))
(^template [<pm> <getter>]
[(^ (<pm> lefts))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
index 9affe12f6..28c33a86a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
@@ -82,7 +82,7 @@
initialize! (list\fold (.function (_ post pre!)
($_ _.then
pre!
- (_.local/1 (..input post) (_.nth (|> post inc .int _.int) @curried))))
+ (_.local/1 (..input post) (_.item (|> post inc .int _.int) @curried))))
initialize_self!
(list.indices arity))
pack (|>> (list) _.array)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux
index 7d92f48d3..935caf949 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux
@@ -105,7 +105,7 @@
(syntax: #export (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))}
body)
(do {! meta.monad}
- [ids (monad.seq ! (list.repeat (list.size vars) meta.count))]
+ [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))]
(in (list (` (let [(~+ (|> vars
(list.zipped/2 ids)
(list\map (function (_ [id var])
@@ -122,7 +122,7 @@
(<>.some <code>.local_identifier))))}
code)
(do meta.monad
- [runtime_id meta.count]
+ [runtime_id meta.seed]
(macro.with_gensyms [g!_]
(let [runtime (code.local_identifier (///reference.artifact [..module_id runtime_id]))
runtime_name (` (_.var (~ (code.text (%.code runtime)))))]
@@ -158,16 +158,16 @@
(_.function (~ g!_) (list (~+ inputsC))
(~ code))))))))))))))))
-(def: (nth index table)
+(def: (item index table)
(-> Expression Expression Location)
- (_.nth (_.+ (_.int +1) index) table))
+ (_.item (_.+ (_.int +1) index) table))
(def: last_index
(|>> _.length (_.- (_.int +1))))
(with_expansions [<recur> (as_is ($_ _.then
(_.set (list lefts) (_.- last_index_right lefts))
- (_.set (list tuple) (..nth last_index_right tuple))))]
+ (_.set (list tuple) (..item last_index_right tuple))))]
(runtime: (tuple//left lefts tuple)
(with_vars [last_index_right]
(<| (_.while (_.bool true))
@@ -175,7 +175,7 @@
(_.local/1 last_index_right (..last_index tuple))
(_.if (_.> lefts last_index_right)
## No need for recursion
- (_.return (..nth lefts tuple))
+ (_.return (..item lefts tuple))
## Needs recursion
<recur>)))))
@@ -186,7 +186,7 @@
(_.local/1 last_index_right (..last_index tuple))
(_.local/1 right_index (_.+ (_.int +1) lefts))
(_.cond (list [(_.= last_index_right right_index)
- (_.return (..nth right_index tuple))]
+ (_.return (..item right_index tuple))]
[(_.> last_index_right right_index)
## Needs recursion.
<recur>])
@@ -246,7 +246,7 @@
($_ _.then
(_.let (list tail) ..none)
(<| (_.for_step idx (_.length raw) (_.int +1) (_.int -1))
- (_.set (list tail) (..some (_.array (list (_.nth idx raw)
+ (_.set (list tail) (..some (_.array (list (_.item idx raw)
tail)))))
(_.return tail))))
@@ -399,7 +399,7 @@
(runtime: (array//write idx value array)
($_ _.then
- (_.set (list (..nth idx array)) value)
+ (_.set (list (..item idx array)) value)
(_.return array)))
(def: runtime//array
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux
index 5eb23e1a9..549d19954 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux
@@ -50,7 +50,7 @@
(in (|> bodyG
(list (_.set (..register register) valueG))
_.array/*
- (_.nth (_.int +1))))))
+ (_.item (_.int +1))))))
(def: #export (let! statement expression archive [valueS register bodyS])
(Generator! [Synthesis Register Synthesis])
@@ -112,8 +112,8 @@
(def: peek
Expression
- (_.nth (|> @cursor _.count/1 (_.- (_.int +1)))
- @cursor))
+ (_.item (|> @cursor _.count/1 (_.- (_.int +1)))
+ @cursor))
(def: save!
Statement
@@ -216,7 +216,7 @@
[/////synthesis.side/right /////synthesis.simple_right_side ..right_choice])
(^ (/////synthesis.member/left 0))
- (///////phase\in (|> ..peek (_.nth (_.int +0)) ..push!))
+ (///////phase\in (|> ..peek (_.item (_.int +0)) ..push!))
(^template [<pm> <getter>]
[(^ (<pm> lefts))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux
index 08a124e2c..f3ad84b3d 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux
@@ -86,7 +86,7 @@
(bundle.install "index" (trinary text//index))
(bundle.install "size" (unary _.strlen/1))
(bundle.install "char" (binary (function (text//char [text idx])
- (|> text (_.nth idx) _.ord/1))))
+ (|> text (_.item idx) _.ord/1))))
(bundle.install "clip" (trinary (function (text//clip [from to text])
(_.substr/3 [text from (_.- from to)]))))
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux
index 9f02325d3..6318a9d88 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux
@@ -87,7 +87,7 @@
initialize! (list\fold (.function (_ post pre!)
($_ _.then
pre!
- (_.set! (..input post) (_.nth (|> post .int _.int) @curried))))
+ (_.set! (..input post) (_.item (|> post .int _.int) @curried))))
initialize_self!
(list.indices arity))]
#let [[definition instantiation] (..with_closure closureG+ @selfG @selfL
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux
index 630e222e5..0c3c94f1f 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux
@@ -118,5 +118,5 @@
(|> argsO+
list.enumeration
(list\map (function (_ [idx _])
- (_.nth (_.int (.int idx)) @temp))))
+ (_.item (_.int (.int idx)) @temp))))
(_.go_to @scope))))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux
index 6c08b4ed0..a18335967 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux
@@ -73,7 +73,7 @@
(syntax: #export (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))}
body)
(do {! meta.monad}
- [ids (monad.seq ! (list.repeat (list.size vars) meta.count))]
+ [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))]
(in (list (` (let [(~+ (|> vars
(list.zipped/2 ids)
(list\map (function (_ [id var])
@@ -90,7 +90,7 @@
(<>.some <code>.local_identifier))))}
code)
(do meta.monad
- [runtime_id meta.count]
+ [runtime_id meta.seed]
(macro.with_gensyms [g!_]
(let [runtime (code.local_identifier (///reference.artifact [..module_id runtime_id]))
runtime_name (` (_.constant (~ (code.text (%.code runtime)))))]
@@ -149,7 +149,7 @@
"_lux_size")
(def: tuple_size
- (_.nth (_.string ..tuple_size_field)))
+ (_.item (_.string ..tuple_size_field)))
(def: jphp?
(_.=== (_.string "5.6.99") (_.phpversion/0 [])))
@@ -162,7 +162,7 @@
(runtime: (array//write idx value array)
($_ _.then
- (_.set! (_.nth idx array) value)
+ (_.set! (_.item idx array) value)
(_.return array)))
(def: runtime//array
@@ -180,7 +180,7 @@
(with_expansions [<recur> (as_is ($_ _.then
(_.set! lefts (_.- last_index_right lefts))
- (_.set! tuple (_.nth last_index_right tuple))))]
+ (_.set! tuple (_.item last_index_right tuple))))]
(runtime: (tuple//make size values)
(_.if ..jphp?
($_ _.then
@@ -202,7 +202,7 @@
(_.set! last_index_right (..normal_last_index tuple)))
(_.if (_.> lefts last_index_right)
## No need for recursion
- (_.return (_.nth lefts tuple))
+ (_.return (_.item lefts tuple))
## Needs recursion
<recur>)))))
@@ -215,7 +215,7 @@
(_.set! output (_.array/* (list)))
(<| (_.while (|> index (_.+ offset) (_.< size)))
($_ _.then
- (_.set! (_.nth index output) (_.nth (_.+ offset index) input))
+ (_.set! (_.item index output) (_.item (_.+ offset index) input))
(_.set! index (_.+ (_.int +1) index))
))
(_.return (..tuple//make (_.- offset size) output))
@@ -230,7 +230,7 @@
(_.set! last_index_right (..normal_last_index tuple)))
(_.set! right_index (_.+ (_.int +1) lefts))
(_.cond (list [(_.=== last_index_right right_index)
- (_.return (_.nth right_index tuple))]
+ (_.return (_.item right_index tuple))]
[(_.> last_index_right right_index)
## Needs recursion.
<recur>])
@@ -274,12 +274,12 @@
(runtime: (sum//get sum wantsLast wantedTag)
(let [no_match! (_.return _.null)
- sum_tag (_.nth (_.string ..variant_tag_field) sum)
- ## sum_tag (_.nth (_.int +0) sum)
- sum_flag (_.nth (_.string ..variant_flag_field) sum)
- ## sum_flag (_.nth (_.int +1) sum)
- sum_value (_.nth (_.string ..variant_value_field) sum)
- ## sum_value (_.nth (_.int +2) sum)
+ sum_tag (_.item (_.string ..variant_tag_field) sum)
+ ## sum_tag (_.item (_.int +0) sum)
+ sum_flag (_.item (_.string ..variant_flag_field) sum)
+ ## sum_flag (_.item (_.int +1) sum)
+ sum_value (_.item (_.string ..variant_value_field) sum)
+ ## sum_value (_.item (_.int +2) sum)
is_last? (_.=== ..unit sum_flag)
test_recursion! (_.if is_last?
## Must recurse.
@@ -540,7 +540,7 @@
_.iconv/3
[(_.string "V")]
_.unpack/2
- (_.nth (_.int +1)))))
+ (_.item (_.int +1)))))
(_.throw (_.new (_.constant "Exception") (list (_.string "[Lux Error] Cannot get char from text."))))))
(def: runtime//text
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux
index cdfaf74fe..fa1a42e49 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux
@@ -117,7 +117,7 @@
(def: peek
(Expression Any)
- (_.nth (_.int -1) @cursor))
+ (_.item (_.int -1) @cursor))
(def: save!
(Statement Any)
@@ -246,7 +246,7 @@
[/////synthesis.side/right /////synthesis.simple_right_side ..right_choice])
(^ (/////synthesis.member/left 0))
- (///////phase\in (|> ..peek (_.nth (_.int +0)) ..push!))
+ (///////phase\in (|> ..peek (_.item (_.int +0)) ..push!))
(^template [<pm> <getter>]
[(^ (<pm> lefts))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux
index 58d814dcc..fd225dfe4 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux
@@ -83,7 +83,7 @@
initialize! (list\fold (.function (_ post pre!)
($_ _.then
pre!
- (_.set (list (..input post)) (_.nth (|> post .int _.int) @curried))))
+ (_.set (list (..input post)) (_.item (|> post .int _.int) @curried))))
initialize_self!
(list.indices arity))]]
(with_closure function_artifact @self environment
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux
index 830154cbd..37296dd7c 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux
@@ -115,7 +115,7 @@
#let [re_binds (|> argsO+
list.enumeration
(list\map (function (_ [idx _])
- (_.nth (_.int (.int idx)) @temp))))]]
+ (_.item (_.int (.int idx)) @temp))))]]
(in ($_ _.then
(_.set (list @temp) (_.list argsO+))
(..setup offset re_binds
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux
index 44ea19376..b653d67b7 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux
@@ -112,7 +112,7 @@
(syntax: #export (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))}
body)
(do {! meta.monad}
- [ids (monad.seq ! (list.repeat (list.size vars) meta.count))]
+ [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))]
(in (list (` (let [(~+ (|> vars
(list.zipped/2 ids)
(list\map (function (_ [id var])
@@ -209,7 +209,7 @@
(with_expansions [<recur> (as_is ($_ _.then
(_.set (list lefts) (_.- last_index_right lefts))
- (_.set (list tuple) (_.nth last_index_right tuple))))]
+ (_.set (list tuple) (_.item last_index_right tuple))))]
(runtime: (tuple::left lefts tuple)
(with_vars [last_index_right]
(_.while (_.bool true)
@@ -217,7 +217,7 @@
(_.set (list last_index_right) (..last_index tuple))
(_.if (_.> lefts last_index_right)
## No need for recursion
- (_.return (_.nth lefts tuple))
+ (_.return (_.item lefts tuple))
## Needs recursion
<recur>))
#.None)))
@@ -229,7 +229,7 @@
(_.set (list last_index_right) (..last_index tuple))
(_.set (list right_index) (_.+ (_.int +1) lefts))
(_.cond (list [(_.= last_index_right right_index)
- (_.return (_.nth right_index tuple))]
+ (_.return (_.item right_index tuple))]
[(_.> last_index_right right_index)
## Needs recursion.
<recur>])
@@ -238,9 +238,9 @@
(runtime: (sum::get sum wantsLast wantedTag)
(let [no_match! (_.return _.none)
- sum_tag (_.nth (_.int +0) sum)
- sum_flag (_.nth (_.int +1) sum)
- sum_value (_.nth (_.int +2) sum)
+ sum_tag (_.item (_.int +0) sum)
+ sum_flag (_.item (_.int +1) sum)
+ sum_value (_.item (_.int +2) sum)
is_last? (_.= ..unit sum_flag)
test_recursion! (_.if is_last?
## Must recurse.
@@ -421,7 +421,7 @@
(runtime: (array::write idx value array)
($_ _.then
- (_.set (list (_.nth idx array)) value)
+ (_.set (list (_.item idx array)) value)
(_.return array)))
(def: runtime::array
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux
index 8ef713643..dcaf7f395 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux
@@ -90,11 +90,11 @@
(def: (push! value var)
(-> Expression SVar Expression)
- (_.set_nth! (next var) value var))
+ (_.set_item! (next var) value var))
(def: (pop! var)
(-> SVar Expression)
- (_.set_nth! (top var) _.null var))
+ (_.set_item! (top var) _.null var))
(def: (push_cursor! value)
(-> Expression Expression)
@@ -107,11 +107,11 @@
(def: restore_cursor!
Expression
- (_.set! $cursor (_.nth (top $savepoint) $savepoint)))
+ (_.set! $cursor (_.item (top $savepoint) $savepoint)))
(def: peek
Expression
- (|> $cursor (_.nth (top $cursor))))
+ (|> $cursor (_.item (top $cursor))))
(def: pop_cursor!
Expression
@@ -190,7 +190,7 @@
[/////synthesis.side/right true inc])
(^ (/////synthesis.member/left 0))
- (///////phase\in (_.nth (_.int +1) ..peek))
+ (///////phase\in (_.item (_.int +1) ..peek))
(^template [<pm> <getter>]
[(^ (<pm> lefts))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux
index a6497d206..850f99475 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux
@@ -69,7 +69,7 @@
(def: (input_declaration register)
(-> Register Expression)
(_.set! (|> register inc //case.register)
- (|> $curried (_.nth (|> register inc .int _.int)))))
+ (|> $curried (_.item (|> register inc .int _.int)))))
(def: #export (function expression archive [environment arity bodyS])
(Generator (Abstraction Synthesis))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux
index 0dcaf6ac8..f71070979 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux
@@ -79,7 +79,7 @@
(syntax: #export (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))}
body)
(do {! meta.monad}
- [ids (monad.seq ! (list.repeat (list.size vars) meta.count))]
+ [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))]
(in (list (` (let [(~+ (|> vars
(list.zipped/2 ids)
(list\map (function (_ [id var])
@@ -93,7 +93,7 @@
(<>.some <code>.local_identifier))))}
code)
(do meta.monad
- [runtime_id meta.count]
+ [runtime_id meta.seed]
(macro.with_gensyms [g!_]
(let [runtime (code.local_identifier (///reference.artifact [..module_id runtime_id]))
runtime_name (` (_.var (~ (code.text (%.code runtime)))))]
@@ -180,14 +180,14 @@
(runtime: (i64::unsigned_low input)
(with_vars [low]
($_ _.then
- (_.set! low (|> input (_.nth (_.string ..i64_low_field))))
+ (_.set! low (|> input (_.item (_.string ..i64_low_field))))
(_.if (|> low (_.>= (_.int +0)))
low
(|> low (_.+ f2^32))))))
(runtime: (i64::to_float input)
(let [high (|> input
- (_.nth (_.string ..i64_high_field))
+ (_.item (_.string ..i64_high_field))
high_shift)
low (|> input
i64::unsigned_low)]
@@ -227,8 +227,8 @@
[i64::max i\top]
)
-(def: #export i64_high (_.nth (_.string ..i64_high_field)))
-(def: #export i64_low (_.nth (_.string ..i64_low_field)))
+(def: #export i64_high (_.item (_.string ..i64_high_field)))
+(def: #export i64_low (_.item (_.string ..i64_low_field)))
(runtime: (i64::not input)
(i64::new (|> input i64_high _.bit_not)
@@ -524,8 +524,8 @@
(..right value))
#.None
(#.Some (_.function (list error)
- (..left (_.nth (_.string "message")
- error))))
+ (..left (_.item (_.string "message")
+ error))))
#.None)))
(runtime: (lux::program_args program_args)
@@ -565,11 +565,11 @@
(def: (product_element product index)
(-> Expression Expression Expression)
- (|> product (_.nth (|> index (_.+ (_.int +1))))))
+ (|> product (_.item (|> index (_.+ (_.int +1))))))
(def: (product_tail product)
(-> SVar Expression)
- (|> product (_.nth (_.length product))))
+ (|> product (_.item (_.length product))))
(def: (updated_index min_length product)
(-> Expression Expression Expression)
@@ -602,9 +602,9 @@
(runtime: (sum::get sum wants_last? wanted_tag)
(let [no_match _.null
- sum_tag (|> sum (_.nth (_.string ..variant_tag_field)))
- sum_flag (|> sum (_.nth (_.string ..variant_flag_field)))
- sum_value (|> sum (_.nth (_.string ..variant_value_field)))
+ sum_tag (|> sum (_.item (_.string ..variant_tag_field)))
+ sum_flag (|> sum (_.item (_.string ..variant_flag_field)))
+ sum_value (|> sum (_.item (_.string ..variant_value_field)))
is_last? (|> sum_flag (_.= (_.string "")))
test_recursion (_.if is_last?
## Must recurse.
@@ -754,7 +754,7 @@
subject)))
(list ["fixed" (_.bool #1)])
(_.var "regexpr"))
- (_.nth (_.int +1))))
+ (_.item (_.int +1))))
(_.if (|> idx (_.= (_.int -1)))
..none
(..some (i64::of_float (|> idx (_.+ startF))))))
@@ -799,16 +799,16 @@
(with_vars [output]
($_ _.then
(_.set! output (_.list (list)))
- (_.set_nth! (|> size (_.+ (_.int +1)))
- _.null
- output)
+ (_.set_item! (|> size (_.+ (_.int +1)))
+ _.null
+ output)
output)))
(runtime: (array::get array idx)
(with_vars [temp]
(<| (check_index_out_of_bounds array idx)
($_ _.then
- (_.set! temp (|> array (_.nth (_.+ (_.int +1) idx))))
+ (_.set! temp (|> array (_.item (_.+ (_.int +1) idx))))
(_.if (|> temp (_.= _.null))
..none
(..some temp))))))
@@ -816,7 +816,7 @@
(runtime: (array::put array idx value)
(<| (check_index_out_of_bounds array idx)
($_ _.then
- (_.set_nth! (_.+ (_.int +1) idx) value array)
+ (_.set_item! (_.+ (_.int +1) idx) value array)
array)))
(def: runtime::array
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux
index d1bbfae39..18185171c 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux
@@ -119,7 +119,7 @@
(def: peek
Expression
- (_.nth (_.int -1) @cursor))
+ (_.item (_.int -1) @cursor))
(def: save!
Statement
@@ -287,7 +287,7 @@
[/////synthesis.side/right /////synthesis.simple_right_side ..right_choice])
(^ (/////synthesis.member/left 0))
- (///////phase\in (|> ..peek (_.nth (_.int +0)) ..push!))
+ (///////phase\in (|> ..peek (_.item (_.int +0)) ..push!))
(^template [<pm> <getter>]
[(^ (<pm> lefts))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux
index 8c849da68..e7e831a77 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux
@@ -80,7 +80,7 @@
initialize! (list\fold (.function (_ post pre!)
($_ _.then
pre!
- (_.set (list (..input post)) (_.nth (|> post .int _.int) @curried))))
+ (_.set (list (..input post)) (_.item (|> post .int _.int) @curried))))
initialize_self!
(list.indices arity))
[declaration instatiation] (with_closure closureO+ function_name
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux
index d021df198..5c255fcc9 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux
@@ -89,7 +89,7 @@
#let [re_binds (|> argsO+
list.enumeration
(list\map (function (_ [idx _])
- (_.nth (_.int (.int idx)) @temp))))]]
+ (_.item (_.int (.int idx)) @temp))))]]
(in ($_ _.then
(_.set (list @temp) (_.array argsO+))
(..setup offset re_binds
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux
index 1ab1ab616..989fdf220 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux
@@ -74,7 +74,7 @@
(syntax: #export (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))}
body)
(do {! meta.monad}
- [ids (monad.seq ! (list.repeat (list.size vars) meta.count))]
+ [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))]
(in (list (` (let [(~+ (|> vars
(list.zipped/2 ids)
(list\map (function (_ [id var])
@@ -91,7 +91,7 @@
(<>.some <code>.local_identifier))))}
code)
(do meta.monad
- [runtime_id meta.count]
+ [runtime_id meta.seed]
(macro.with_gensyms [g!_]
(let [runtime (code.local_identifier (///reference.artifact [..module_id runtime_id]))
runtime_name (` (_.local (~ (code.text (%.code runtime)))))]
@@ -132,7 +132,7 @@
(with_expansions [<recur> (as_is ($_ _.then
(_.set (list lefts) (_.- last_index_right lefts))
- (_.set (list tuple) (_.nth last_index_right tuple))))]
+ (_.set (list tuple) (_.item last_index_right tuple))))]
(runtime: (tuple//left lefts tuple)
(with_vars [last_index_right]
(<| (_.while (_.bool true))
@@ -140,7 +140,7 @@
(_.set (list last_index_right) (..last_index tuple))
(_.if (_.> lefts last_index_right)
## No need for recursion
- (_.return (_.nth lefts tuple))
+ (_.return (_.item lefts tuple))
## Needs recursion
<recur>)))))
@@ -151,7 +151,7 @@
(_.set (list last_index_right) (..last_index tuple))
(_.set (list right_index) (_.+ (_.int +1) lefts))
(_.cond (list [(_.= last_index_right right_index)
- (_.return (_.nth right_index tuple))]
+ (_.return (_.item right_index tuple))]
[(_.> last_index_right right_index)
## Needs recursion.
<recur>])
@@ -189,9 +189,9 @@
(runtime: (sum//get sum wantsLast wantedTag)
(let [no_match! (_.return _.nil)
- sum_tag (_.nth (_.string ..variant_tag_field) sum)
- sum_flag (_.nth (_.string ..variant_flag_field) sum)
- sum_value (_.nth (_.string ..variant_value_field) sum)
+ sum_tag (_.item (_.string ..variant_tag_field) sum)
+ sum_flag (_.item (_.string ..variant_flag_field) sum)
+ sum_value (_.item (_.string ..variant_value_field) sum)
is_last? (_.= ..unit sum_flag)
test_recursion! (_.if is_last?
## Must recurse.
@@ -369,7 +369,7 @@
(runtime: (array//write idx value array)
($_ _.then
- (_.set (list (_.nth idx array)) value)
+ (_.set (list (_.item idx array)) value)
(_.return array)))
(def: runtime//array
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux
index 2e5c8d495..72ec2ef27 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux
@@ -61,7 +61,7 @@
(syntax: #export (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))}
body)
(do {! meta.monad}
- [ids (monad.seq ! (list.repeat (list.size vars) meta.count))]
+ [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))]
(in (list (` (let [(~+ (|> vars
(list.zipped/2 ids)
(list\map (function (_ [id var])
@@ -75,7 +75,7 @@
(<>.some <code>.local_identifier))))}
code)
(do meta.monad
- [runtime_id meta.count]
+ [runtime_id meta.seed]
(macro.with_gensyms [g!_]
(let [runtime (code.local_identifier (///reference.artifact [..module_id runtime_id]))
runtime_name (` (_.var (~ (code.text (%.code runtime)))))]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux
index 4dc984bae..b19403e90 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux
@@ -30,7 +30,7 @@
(exception: #export (cannot_find_foreign_variable_in_environment {foreign Register} {environment (Environment Synthesis)})
(exception.report
["Foreign" (%.nat foreign)]
- ["Environment" (exception.enumerate /.%synthesis environment)]))
+ ["Environment" (exception.listing /.%synthesis environment)]))
(def: arity_arguments
(-> Arity (List Synthesis))
@@ -83,7 +83,7 @@
(def: (find_foreign environment register)
(-> (Environment Synthesis) Register (Operation Synthesis))
- (case (list.nth register environment)
+ (case (list.item register environment)
(#.Some aliased)
(phase\in aliased)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux
index f64693134..6e83a6a6a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux
@@ -110,7 +110,7 @@
(^ (reference.foreign register))
(if true_loop?
- (list.nth register scope_environment)
+ (list.item register scope_environment)
(#.Some expr)))
(^ (/.branch/case [input path]))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/program.lux b/stdlib/source/library/lux/tool/compiler/language/lux/program.lux
index 16b59870b..be1eead63 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/program.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/program.lux
@@ -30,7 +30,7 @@
(exception: #export (cannot_find_program {modules (List Module)})
(exception.report
- ["Modules" (exception.enumerate %.text modules)]))
+ ["Modules" (exception.listing %.text modules)]))
(def: #export (context archive)
(-> Archive (Try Context))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux
index d6c43e896..4c930475b 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux
@@ -169,11 +169,11 @@
(template: (!failure parser where offset source_code)
(#.Left [[where offset source_code]
- (exception.construct ..unrecognized_input [where (%.name (name_of parser)) source_code offset])]))
+ (exception.error ..unrecognized_input [where (%.name (name_of parser)) source_code offset])]))
(template: (!end_of_file where offset source_code current_module)
(#.Left [[where offset source_code]
- (exception.construct ..end_of_file current_module)]))
+ (exception.error ..end_of_file current_module)]))
(type: (Parser a)
(-> Source (Either [Source Text] [Source a])))
@@ -263,7 +263,7 @@
g!_
(#.Left [[where offset source_code]
- (exception.construct ..text_cannot_contain_new_lines content)])))
+ (exception.error ..text_cannot_contain_new_lines content)])))
(def: (text_parser where offset source_code)
(-> Location Offset Text (Either [Source Text] [Source Code]))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux
index a45c7ad59..cd6b245ee 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux
@@ -45,7 +45,7 @@
{known_modules (List Module)})
(exception.report
["Module" (%.text module)]
- ["Known Modules" (exception.enumerate %.text known_modules)]))
+ ["Known Modules" (exception.listing %.text known_modules)]))
(exception: #export (cannot_replace_document {module Module}
{old (Document Any)}
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux
index 7feeac2a0..76266ad19 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux
@@ -141,7 +141,7 @@
[5 #Directive <binary>.text]
[6 #Custom <binary>.text])
- _ (<>.failure (exception.construct ..invalid_category [tag])))))]
+ _ (<>.failure (exception.error ..invalid_category [tag])))))]
(|> (<binary>.row/64 category)
(\ <>.monad map (row\fold (function (_ artifact registry)
(product.right
diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux
index 8903ab503..e049ef8b5 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux
@@ -138,7 +138,7 @@
(type: #export Enumeration
(Dictionary file.Path Binary))
-(def: (enumerate_context fs directory enumeration)
+(def: (context_listing fs directory enumeration)
(-> (file.System Async) Context Enumeration (Async (Try Enumeration)))
(do {! (try.with async.monad)}
[enumeration (|> directory
@@ -153,17 +153,17 @@
(\ ! join))]
(|> directory
(\ fs sub_directories)
- (\ ! map (monad.fold ! (enumerate_context fs) enumeration))
+ (\ ! map (monad.fold ! (context_listing fs) enumeration))
(\ ! join))))
(def: Action
(type (All [a] (Async (Try a)))))
-(def: #export (enumerate fs contexts)
+(def: #export (listing fs contexts)
(-> (file.System Async) (List Context) (Action Enumeration))
(monad.fold (: (Monad Action)
(try.with async.monad))
- (..enumerate_context fs)
+ (..context_listing fs)
(: Enumeration
(dictionary.empty text.hash))
contexts))
diff --git a/stdlib/source/library/lux/tool/compiler/phase.lux b/stdlib/source/library/lux/tool/compiler/phase.lux
index ed4def938..0a0db986e 100644
--- a/stdlib/source/library/lux/tool/compiler/phase.lux
+++ b/stdlib/source/library/lux/tool/compiler/phase.lux
@@ -74,7 +74,7 @@
(def: #export (except exception parameters)
(All [e] (-> (Exception e) e Operation))
- (..failure (ex.construct exception parameters)))
+ (..failure (ex.error exception parameters)))
(def: #export (lift error)
(All [s a] (-> (Try a) (Operation s a)))