aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/tool/compiler
diff options
context:
space:
mode:
authorEduardo Julian2022-03-30 14:05:57 -0400
committerEduardo Julian2022-03-30 14:05:57 -0400
commit381ec5920d9ebeb335963778dec182268819e718 (patch)
tree5c9288c5fbb16c21a0f00f96710b0aa7db4585f4 /stdlib/source/library/lux/tool/compiler
parent1a962ee4b03f51f46a5979bfefc954f35ee3a1b7 (diff)
Now demanding mandatory loop names, instead of using default "again" name.
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/init.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/platform.lux22
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux14
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux10
-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/directive.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux2
-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/synthesis/case.lux14
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux14
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/io/archive.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux10
19 files changed, 69 insertions, 71 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux
index 9f615c86e..f6c30c1cd 100644
--- a/stdlib/source/library/lux/tool/compiler/default/init.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/init.lux
@@ -245,8 +245,8 @@
[state [source buffer]] (<| (///phase.result' state)
(..begin dependencies hash input))
.let [module (the ///.#module input)]]
- (loop [iteration (<| (///phase.result' state)
- (..iteration wrapper archive expander module source buffer ///syntax.no_aliases))]
+ (loop (again [iteration (<| (///phase.result' state)
+ (..iteration wrapper archive expander module source buffer ///syntax.no_aliases))])
(do !
[[state ?source&requirements&temporary_payload] iteration]
(case ?source&requirements&temporary_payload
diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux
index 4f62b38da..bf809bbb5 100644
--- a/stdlib/source/library/lux/tool/compiler/default/platform.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux
@@ -711,10 +711,10 @@
(Key document) (Writer document) (///.Compilation state document object)
(-> (List ///.Custom) descriptor.Module Lux_Importer module.ID (..Context state) descriptor.Module (..Return state))))
(function (_ customs importer import! @module [archive state] module)
- (loop [[archive state] [archive state]
- compilation custom_compilation
- all_dependencies (is (Set descriptor.Module)
- (set.of_list text.hash (list)))]
+ (loop (again [[archive state] [archive state]
+ compilation custom_compilation
+ all_dependencies (is (Set descriptor.Module)
+ (set.of_list text.hash (list)))])
(do [! (try.with async.monad)]
[.let [new_dependencies (the ///.#dependencies compilation)
[all_dependencies duplicates] (with_new_dependencies new_dependencies all_dependencies)]
@@ -751,10 +751,10 @@
(///.Compilation <State+> .Module Any)
Lux_Compiler))
(function (_ customs importer import! @module [archive state] module)
- (loop [[archive state] [archive (..set_current_module module state)]
- compilation compilation
- all_dependencies (is (Set descriptor.Module)
- (set.of_list text.hash (list)))]
+ (loop (again [[archive state] [archive (..set_current_module module state)]
+ compilation compilation
+ all_dependencies (is (Set descriptor.Module)
+ (set.of_list text.hash (list)))])
(do [! (try.with async.monad)]
[.let [new_dependencies (the ///.#dependencies compilation)
[all_dependencies duplicates] (with_new_dependencies new_dependencies all_dependencies)]
@@ -820,9 +820,9 @@
compilation_sources
(the context.#host_module_extension context)
module)]
- (loop [customs (for @.old (as (List (///.Custom Fake_State Fake_Document Fake_Object))
- all_customs)
- all_customs)]
+ (loop (again [customs (for @.old (as (List (///.Custom Fake_State Fake_Document Fake_Object))
+ all_customs)
+ all_customs)])
(case customs
{.#End}
((..lux_compiler import context platform compilation_sources compiler (compiler input))
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 24c60d5fa..da220b18f 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
@@ -159,9 +159,9 @@
(def: .public (reification analysis)
(-> Analysis (Reification Analysis))
- (loop [abstraction analysis
- inputs (is (List Analysis)
- (list))]
+ (loop (again [abstraction analysis
+ inputs (is (List Analysis)
+ (list))])
(.case abstraction
{#Apply input next}
(again next {.#Item input inputs})
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux
index f7170c8ce..9c5a1c045 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux
@@ -371,7 +371,7 @@
(Try [(Maybe Coverage)
(List Coverage)]))
(function (_ coverageA possibilitiesSF)
- (loop [altsSF possibilitiesSF]
+ (loop (again [altsSF possibilitiesSF])
(case altsSF
{.#End}
(in [{.#None} (list coverageA)])
@@ -387,8 +387,8 @@
_
(in [{.#Some altMSF} altsSF'])))))))]]
- (loop [addition addition
- possibilitiesSF (alternatives so_far)]
+ (loop (again [addition addition
+ possibilitiesSF (alternatives so_far)])
(do !
[[addition' possibilitiesSF'] (fuse_once addition possibilitiesSF)]
(case addition'
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux
index 8c6052ed5..4c706598f 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux
@@ -225,8 +225,8 @@
(template [<name> <types> <inputs> <exception> <when> <then>]
[(`` (def: .public (<name> (~~ (template.spliced <inputs>)) complex)
(-> (~~ (template.spliced <types>)) Type (Operation Type))
- (loop [depth 0
- it complex]
+ (loop (again [depth 0
+ it complex])
(case it
{.#Named name it}
(again depth it)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux
index 6902cd718..578cad62c 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux
@@ -51,8 +51,8 @@
(def: (captured name scope)
(-> Text Scope (Maybe [Type Variable]))
- (loop [idx 0
- mappings (the [.#captured .#mappings] scope)]
+ (loop (again [idx 0
+ mappings (the [.#captured .#mappings] scope)])
(case mappings
{.#Item [_name [_source_type _source_ref]] mappings'}
(if (text#= name _name)
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 a35c61eb3..6caf2ffab 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
@@ -89,9 +89,9 @@
... type-check the input with respect to the patterns.
(def: .public (tuple :it:)
(-> Type (Check [(List check.Var) Type]))
- (loop [envs (is (List (List Type))
- (list))
- :it: :it:]
+ (loop (again [envs (is (List (List Type))
+ (list))
+ :it: :it:])
(.case :it:
{.#Var id}
(do check.monad
@@ -165,10 +165,10 @@
[[@ex_var+ :input:'] (/type.check (..tuple :input:))]
(.case :input:'
{.#Product _}
- (let [matches (loop [types (type.flat_tuple :input:')
- patterns sub_patterns
- output (is (List [Type Code])
- {.#End})]
+ (let [matches (loop (again [types (type.flat_tuple :input:')
+ patterns sub_patterns
+ output (is (List [Type Code])
+ {.#End})])
(.case [types patterns]
[{.#End} {.#End}]
output
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux
index 2a8279ae8..fba921765 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux
@@ -193,8 +193,8 @@
(<| (let [! ///.monad])
(# ! each (|>> /.tuple))
(is (Operation (List Analysis)))
- (loop [membersT+ (type.flat_tuple expectedT)
- membersC+ members]
+ (loop (again [membersT+ (type.flat_tuple expectedT)
+ membersC+ members])
(case [membersT+ membersC+]
[{.#Item memberT {.#End}} {.#Item memberC {.#End}}]
(<| (# ! each (|>> list))
@@ -292,9 +292,9 @@
... canonical form (with their corresponding module identified).
(def: .public (normal pattern_matching? record)
(-> Bit (List Code) (Operation (Maybe (List [Symbol Code]))))
- (loop [input record
- output (is (List [Symbol Code])
- {.#End})]
+ (loop (again [input record
+ output (is (List [Symbol Code])
+ {.#End})])
(case input
(pattern (list& [_ {.#Symbol ["" slotH]}] valueH tail))
(if pattern_matching?
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 ce99c9005..5bdfe1718 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
@@ -57,7 +57,7 @@
(-> Phase Text Text Phase)
(do [! ///.monad]
[expectedT (///extension.lifted meta.expected_type)]
- (loop [expectedT expectedT]
+ (loop (again [expectedT expectedT])
(/.with_exception ..cannot_analyse [expectedT function_name arg_name body]
(case expectedT
{.#Function :input: :output:}
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 ea6adec7a..0c301f277 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
@@ -59,9 +59,9 @@
(-> (Phase anchor expression directive) Archive (List Code)
(Operation anchor expression directive /.Requirements)))
(function (_ state)
- (loop [state state
- input expansion
- output /.no_requirements]
+ (loop (again [state state
+ input expansion
+ output /.no_requirements])
(case input
{.#End}
{try.#Success [state output]}
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 49d9df8ca..ce1654cd4 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
@@ -993,7 +993,7 @@
[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]]
+ (loop (again [[current_name currentT] [source_name fromT]])
(if (text#= target_name current_name)
(in true)
(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 31bc84be0..a018f3ab3 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
@@ -213,7 +213,7 @@
(function (_ extension_name phase archive valueC)
(do [! ////.monad]
[_ (typeA.inference .Macro)
- input_type (loop [input_name (symbol .Macro')]
+ input_type (loop (again [input_name (symbol .Macro')])
(do !
[input_type (///.lifted (meta.definition (symbol .Macro')))]
(case input_type
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 91d72f959..1ccc58417 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
@@ -832,7 +832,7 @@
hidden
[_ {//////synthesis.#Control {//////synthesis.#Branch {//////synthesis.#Case _ path}}}]
- (loop [path (is Path path)]
+ (loop (again [path (is Path path)])
(case path
{//////synthesis.#Seq _ next}
(again next)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux
index 9515ea518..3412ae778 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux
@@ -201,8 +201,8 @@
(def: (get patterns @selection)
(-> (///complex.Tuple Pattern) Register (List Member))
- (loop [lefts 0
- patterns patterns]
+ (loop (again [lefts 0
+ patterns patterns])
(with_expansions [<failure> (these (list))
<continue> (these (again (++ lefts)
tail))
@@ -364,9 +364,8 @@
... Apply this trick to JS, Python et al.
(def: .public (storage path)
(-> Path Storage)
- (loop for_path
- [path path
- path_storage ..empty]
+ (loop (for_path [path path
+ path_storage ..empty])
(case path
(^.or {/.#Pop}
{/.#Access Access})
@@ -397,9 +396,8 @@
(list#mix for_path path_storage (list left right))
(pattern (/.path/then bodyS))
- (loop for_synthesis
- [bodyS bodyS
- synthesis_storage path_storage]
+ (loop (for_synthesis [bodyS bodyS
+ synthesis_storage path_storage])
(case bodyS
(^.or {/.#Simple _}
(pattern (/.constant _)))
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 e8917d6a8..a8991f643 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
@@ -79,8 +79,8 @@
(def: (body_optimization true_loop? offset scope_environment arity expr)
(-> Bit Register (Environment Synthesis) Arity (Transform Synthesis))
- (loop [return? true
- expr expr]
+ (loop (again [return? true
+ expr expr])
(case expr
{/.#Simple _}
{.#Some expr}
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 18ad84ac7..3f5b73842 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux
@@ -228,8 +228,8 @@
[(inline: (<name> parse where offset source_code)
(-> (Parser Code) Location Offset Text
(Either [Source Text] [Source Code]))
- (loop [source (is Source [(!forward 1 where) offset source_code])
- stack (is (List Code) {.#End})]
+ (loop (again [source (is Source [(!forward 1 where) offset source_code])
+ stack (is (List Code) {.#End})])
(case (parse source)
{.#Right [source' top]}
(again source' {.#Item top stack})
@@ -352,8 +352,8 @@
(inline: (frac_parser source_code//size start where offset source_code)
(-> Nat Nat Location Offset Text
(Either [Source Text] [Source Code]))
- (loop [end offset
- exponent (static ..no_exponent)]
+ (loop (again [end offset
+ exponent (static ..no_exponent)])
(<| (!with_char+ source_code//size source_code end char/0 <frac_output>)
(!if_digit?+ char/0
(again (!++ end) exponent)
@@ -377,7 +377,7 @@
(inline: (signed_parser source_code//size start where offset source_code)
(-> Nat Nat Location Offset Text
(Either [Source Text] [Source Code]))
- (loop [end offset]
+ (loop (again [end offset])
(<| (!with_char+ source_code//size source_code end char <int_output>)
(!if_digit?+ char
(again (!++ end))
@@ -392,7 +392,7 @@
[(inline: (<parser> source_code//size start where offset source_code)
(-> Nat Nat Location Offset Text
(Either [Source Text] [Source Code]))
- (loop [g!end offset]
+ (loop (again [g!end offset])
(<| (!with_char+ source_code//size source_code g!end g!char (!number_output source_code start g!end <codec> <tag>))
(!if_digit?+ g!char
(again (!++ g!end))
@@ -418,7 +418,7 @@
(-> Nat Location Offset Text
(Either [Source Text] [Source Text]))
(let [source_code//size ("lux text size" source_code)]
- (loop [end offset]
+ (loop (again [end offset])
(<| (!with_char+ source_code//size source_code end char <output>)
(!if_symbol_char?|tail char
(again (!++ end))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux
index 90085fc31..1ab3be9eb 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux
@@ -212,8 +212,8 @@
(def: .public (necessary_dependencies archive)
(-> Archive (Set unit.ID))
(let [[mandatory immediate] (immediate_dependencies archive)]
- (loop [pending mandatory
- minimum unit.none]
+ (loop (again [pending mandatory
+ minimum unit.none])
(case pending
{.#Item head tail}
(if (set.member? minimum head)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
index 3bc8ed418..26298275f 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
@@ -114,11 +114,11 @@
(Try [(Document .Module) Bundles Output])))
(do [! try.monad]
[[definitions bundles] (is (Try [Definitions Bundles Output])
- (loop [input (sequence.list expected)
- definitions (is Definitions
- (dictionary.empty text.hash))
- bundles ..empty_bundles
- output (is Output sequence.empty)]
+ (loop (again [input (sequence.list expected)
+ definitions (is Definitions
+ (dictionary.empty text.hash))
+ bundles ..empty_bundles
+ output (is Output sequence.empty)])
(let [[analysers synthesizers generators directives] bundles]
(case input
{.#Item [[[@artifact artifact_category mandatory_artifact?] artifact_dependencies] input']}
diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
index 1e27186b1..2de06bf46 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
@@ -179,7 +179,7 @@
(let [chunk (binary.empty ..mebi_byte)
chunk_size (.int ..mebi_byte)
buffer (java/io/ByteArrayOutputStream::new (ffi.as_int chunk_size))]
- (loop [so_far 0]
+ (loop (again [so_far 0])
(case (ffi.of_int (java/io/InputStream::read chunk (ffi.as_int +0) (ffi.as_int chunk_size) input))
-1
[so_far
@@ -193,7 +193,7 @@
(def: (read_jar_entry_with_known_size expected_size input)
(-> Nat java/util/jar/JarInputStream [Nat Binary])
(let [buffer (binary.empty expected_size)]
- (loop [so_far 0]
+ (loop (again [so_far 0])
(let [so_far' (|> input
(java/io/InputStream::read buffer (ffi.as_int (.int so_far)) (ffi.as_int (.int (n.- so_far expected_size))))
ffi.of_int
@@ -219,9 +219,9 @@
(let [input (|> jar
java/io/ByteArrayInputStream::new
java/util/jar/JarInputStream::new)]
- (loop [entries entries
- duplicates duplicates
- sink sink]
+ (loop (again [entries entries
+ duplicates duplicates
+ sink sink])
(case (java/util/jar/JarInputStream::getNextJarEntry input)
{try.#Failure error}
{try.#Failure error}