aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library
diff options
context:
space:
mode:
authorEduardo Julian2021-09-14 16:41:18 -0400
committerEduardo Julian2021-09-14 16:41:18 -0400
commitccfa75463cd7c702f41c3dae5cbdaeade7ba5c31 (patch)
treec47937a8f62a25ef945a876b3af76c5fca989db9 /stdlib/source/library
parentea15b844b51ff60f9785c6791507f813729f85c3 (diff)
Re-named "recur" to "again".
Diffstat (limited to 'stdlib/source/library')
-rw-r--r--stdlib/source/library/lux.lux18
-rw-r--r--stdlib/source/library/lux/abstract/enum.lux4
-rw-r--r--stdlib/source/library/lux/abstract/monad.lux14
-rw-r--r--stdlib/source/library/lux/abstract/predicate.lux4
-rw-r--r--stdlib/source/library/lux/control/concurrency/actor.lux6
-rw-r--r--stdlib/source/library/lux/control/concurrency/atom.lux2
-rw-r--r--stdlib/source/library/lux/control/concurrency/frp.lux12
-rw-r--r--stdlib/source/library/lux/control/concurrency/semaphore.lux2
-rw-r--r--stdlib/source/library/lux/control/concurrency/stm.lux8
-rw-r--r--stdlib/source/library/lux/control/concurrency/thread.lux2
-rw-r--r--stdlib/source/library/lux/control/parser/binary.lux6
-rw-r--r--stdlib/source/library/lux/control/parser/cli.lux2
-rw-r--r--stdlib/source/library/lux/control/parser/json.lux4
-rw-r--r--stdlib/source/library/lux/control/parser/type.lux4
-rw-r--r--stdlib/source/library/lux/control/parser/xml.lux4
-rw-r--r--stdlib/source/library/lux/control/pipe.lux2
-rw-r--r--stdlib/source/library/lux/data/binary.lux6
-rw-r--r--stdlib/source/library/lux/data/collection/array.lux20
-rw-r--r--stdlib/source/library/lux/data/collection/bits.lux16
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary/ordered.lux24
-rw-r--r--stdlib/source/library/lux/data/collection/list.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/queue/priority.lux10
-rw-r--r--stdlib/source/library/lux/data/collection/row.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/sequence.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/tree.lux2
-rw-r--r--stdlib/source/library/lux/data/collection/tree/finger.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/tree/zipper.lux4
-rw-r--r--stdlib/source/library/lux/data/format/binary.lux18
-rw-r--r--stdlib/source/library/lux/data/format/json.lux2
-rw-r--r--stdlib/source/library/lux/data/format/tar.lux2
-rw-r--r--stdlib/source/library/lux/data/format/xml.lux2
-rw-r--r--stdlib/source/library/lux/data/text.lux8
-rw-r--r--stdlib/source/library/lux/data/text/escape.lux12
-rw-r--r--stdlib/source/library/lux/data/text/unicode/set.lux4
-rw-r--r--stdlib/source/library/lux/debug.lux6
-rw-r--r--stdlib/source/library/lux/ffi.jvm.lux2
-rw-r--r--stdlib/source/library/lux/ffi.old.lux8
-rw-r--r--stdlib/source/library/lux/math.lux2
-rw-r--r--stdlib/source/library/lux/math/number/i64.lux2
-rw-r--r--stdlib/source/library/lux/math/number/int.lux2
-rw-r--r--stdlib/source/library/lux/math/number/nat.lux8
-rw-r--r--stdlib/source/library/lux/math/number/rev.lux26
-rw-r--r--stdlib/source/library/lux/math/random.lux8
-rw-r--r--stdlib/source/library/lux/meta.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/instruction.lux4
-rw-r--r--stdlib/source/library/lux/target/jvm/constant/pool.lux2
-rw-r--r--stdlib/source/library/lux/test.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/init.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/platform.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux2
-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/case/coverage.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux16
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux8
-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/js/common.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux28
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux20
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux28
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux16
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux18
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux26
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux16
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux32
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux16
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.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.lux64
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux74
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux26
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux24
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/io/archive.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux10
-rw-r--r--stdlib/source/library/lux/tool/interpreter.lux6
-rw-r--r--stdlib/source/library/lux/type.lux2
-rw-r--r--stdlib/source/library/lux/type/abstract.lux4
-rw-r--r--stdlib/source/library/lux/type/check.lux4
-rw-r--r--stdlib/source/library/lux/type/resource.lux2
-rw-r--r--stdlib/source/library/lux/world/file.lux18
-rw-r--r--stdlib/source/library/lux/world/file/watch.lux6
-rw-r--r--stdlib/source/library/lux/world/net/http/client.lux12
-rw-r--r--stdlib/source/library/lux/world/program.lux2
109 files changed, 463 insertions, 463 deletions
diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux
index 6dff86c3c..ad9fcc8d8 100644
--- a/stdlib/source/library/lux.lux
+++ b/stdlib/source/library/lux.lux
@@ -1927,10 +1927,10 @@
_
(let' [loop ("lux type check" (-> Nat Text Text)
- (function' recur [input output]
+ (function' again [input output]
(if ("lux i64 =" 0 input)
output
- (recur (n// 10 input)
+ (again (n// 10 input)
(text#composite (|> input (n/% 10) digit::format)
output)))))]
(loop value ""))}
@@ -1950,10 +1950,10 @@
"+"
"-")]
(("lux type check" (-> Int Text Text)
- (function' recur [input output]
+ (function' again [input output]
(if ("lux i64 =" +0 input)
(text#composite sign output)
- (recur ("lux i64 /" +10 input)
+ (again ("lux i64 /" +10 input)
(text#composite (|> input ("lux i64 %" +10) ("lux type as" Nat) digit::format)
output)))))
(|> value ("lux i64 /" +10) int#abs)
@@ -3336,10 +3336,10 @@
(def: (replaced pattern replacement template)
(-> Text Text Text Text)
((: (-> Text Text Text)
- (function (recur left right)
+ (function (again left right)
(case (..text#split_by pattern right)
{#Some [pre post]}
- (recur ($_ "lux text concat" left pre replacement) post)
+ (again ($_ "lux text concat" left pre replacement) post)
{#None}
("lux text concat" left right))))
@@ -3764,7 +3764,7 @@
{#Some tags&members}
(do meta_monad
[full_body ((: (-> Symbol [(List Symbol) (List Type)] Code (Meta Code))
- (function (recur source [tags members] target)
+ (function (again source [tags members] target)
(let [locals (list#each (function (_ [t_module t_name])
[[t_module t_name]
["" (..module_alias (list t_name) alias)]])
@@ -3782,7 +3782,7 @@
[m_implementation (record_slots m_type)]
(case m_implementation
{#Some m_tags&members}
- (recur m_local
+ (again m_local
m_tags&members
enhanced_target)
@@ -4324,7 +4324,7 @@
{#Some [name bindings body]}
(^ (list [_ {#Tuple bindings}] body))
- {#Some [(local_symbol$ "recur") bindings body]}
+ {#Some [(local_symbol$ "again") bindings body]}
_
{#None})]
diff --git a/stdlib/source/library/lux/abstract/enum.lux b/stdlib/source/library/lux/abstract/enum.lux
index 61069d2ef..e3a865018 100644
--- a/stdlib/source/library/lux/abstract/enum.lux
+++ b/stdlib/source/library/lux/abstract/enum.lux
@@ -16,10 +16,10 @@
(loop [end to
output {.#End}]
(cond (< end from)
- (recur (pred end) {.#Item end output})
+ (again (pred end) {.#Item end output})
(< from end)
- (recur (succ end) {.#Item end output})
+ (again (succ end) {.#Item end output})
... (= end from)
{.#Item end output}))))
diff --git a/stdlib/source/library/lux/abstract/monad.lux b/stdlib/source/library/lux/abstract/monad.lux
index 738654ef5..ed63ebf8c 100644
--- a/stdlib/source/library/lux/abstract/monad.lux
+++ b/stdlib/source/library/lux/abstract/monad.lux
@@ -25,7 +25,7 @@
counter
{.#Item _ xs'}
- (recur (++ counter) xs'))))
+ (again (++ counter) xs'))))
(def: (reversed xs)
(All (_ a)
@@ -118,7 +118,7 @@
(-> (Monad !) (List (! a))
(! (List a))))
(let [(^open "!#[0]") monad]
- (function (recur xs)
+ (function (again xs)
(case xs
{.#End}
(!#in {.#End})
@@ -126,7 +126,7 @@
{.#Item x xs'}
(|> x
(!#each (function (_ _x)
- (!#each (|>> {.#Item _x}) (recur xs'))))
+ (!#each (|>> {.#Item _x}) (again xs'))))
!#conjoint)))))
(def: .public (each monad f)
@@ -134,7 +134,7 @@
(-> (Monad M) (-> a (M b)) (List a)
(M (List b))))
(let [(^open "!#[0]") monad]
- (function (recur xs)
+ (function (again xs)
(case xs
{.#End}
(!#in {.#End})
@@ -142,7 +142,7 @@
{.#Item x xs'}
(|> (f x)
(!#each (function (_ _x)
- (!#each (|>> {.#Item _x}) (recur xs'))))
+ (!#each (|>> {.#Item _x}) (again xs'))))
!#conjoint)))))
(def: .public (only monad f)
@@ -150,7 +150,7 @@
(-> (Monad !) (-> a (! Bit)) (List a)
(! (List a))))
(let [(^open "!#[0]") monad]
- (function (recur xs)
+ (function (again xs)
(case xs
{.#End}
(!#in {.#End})
@@ -162,7 +162,7 @@
(if verdict
{.#Item head tail}
tail))
- (recur xs'))))
+ (again xs'))))
!#conjoint)))))
(def: .public (mix monad f init xs)
diff --git a/stdlib/source/library/lux/abstract/predicate.lux b/stdlib/source/library/lux/abstract/predicate.lux
index ae78a23dd..e70d5f25a 100644
--- a/stdlib/source/library/lux/abstract/predicate.lux
+++ b/stdlib/source/library/lux/abstract/predicate.lux
@@ -51,8 +51,8 @@
(All (_ a)
(-> (-> (Predicate a) (Predicate a))
(Predicate a)))
- (function (recur input)
- (predicate recur input)))
+ (function (again input)
+ (predicate again input)))
(implementation: .public functor
(contravariant.Functor Predicate)
diff --git a/stdlib/source/library/lux/control/concurrency/actor.lux b/stdlib/source/library/lux/control/concurrency/actor.lux
index b3f261d65..5809cb9ee 100644
--- a/stdlib/source/library/lux/control/concurrency/actor.lux
+++ b/stdlib/source/library/lux/control/concurrency/actor.lux
@@ -103,7 +103,7 @@
(in [])))
{try.#Success state'}
- (recur state' tail))))]
+ (again state' tail))))]
self)))
(def: .public (alive? actor)
@@ -148,10 +148,10 @@
(do !
[_ (atom.write! (product.right entry) (value@ #mailbox (:representation actor)))]
(in {try.#Success []}))
- (recur |mailbox|&resolve)))
+ (again |mailbox|&resolve)))
{.#Some [_ |mailbox|']}
- (recur |mailbox|'))))))
+ (again |mailbox|'))))))
(in (exception.except ..dead [])))))
(type: .public (Message s o)
diff --git a/stdlib/source/library/lux/control/concurrency/atom.lux b/stdlib/source/library/lux/control/concurrency/atom.lux
index 3a4b2ad24..cc075549e 100644
--- a/stdlib/source/library/lux/control/concurrency/atom.lux
+++ b/stdlib/source/library/lux/control/concurrency/atom.lux
@@ -87,7 +87,7 @@
swapped? (compare_and_swap! old new atom)]
(if swapped?
(in [old new])
- (recur [])))))
+ (again [])))))
(def: .public (write! value atom)
(All (_ a) (-> a (Atom a) (IO a)))
diff --git a/stdlib/source/library/lux/control/concurrency/frp.lux b/stdlib/source/library/lux/control/concurrency/frp.lux
index d91cf4dbf..2b1889535 100644
--- a/stdlib/source/library/lux/control/concurrency/frp.lux
+++ b/stdlib/source/library/lux/control/concurrency/frp.lux
@@ -50,7 +50,7 @@
... Someone else closed the sink.
(in (exception.except ..channel_is_already_closed []))
... Someone else fed the sink while I was closing it.
- (recur [])))))))
+ (again [])))))))
(def: (feed value)
(loop [_ []]
@@ -76,7 +76,7 @@
... Someone else closed the sink while I was feeding it.
(in (exception.except ..channel_is_already_closed []))
... Someone else fed the sink.
- (recur []))))))))))
+ (again []))))))))))
(def: .public (channel _)
(All (_ a) (-> Any [(Channel a) (Sink a)]))
@@ -137,11 +137,11 @@
{.#Some [a ma']}
(exec
(io.run! (# sink feed a))
- (recur ma'))
+ (again ma'))
{.#None}
(in []))))]
- (recur mma'))
+ (again mma'))
{.#None}
(in (: Any (io.run! (# sink close))))))))
@@ -161,7 +161,7 @@
{.#Some [head tail]}
(case (io.run! (subscriber head))
{.#Some _}
- (recur tail)
+ (again tail)
{.#None}
(in []))
@@ -229,7 +229,7 @@
(do io.monad
[value action
_ (# sink feed value)]
- (async.upon! recur (async.delay milli_seconds)))))
+ (async.upon! again (async.delay milli_seconds)))))
[output sink])))
(def: .public (periodic milli_seconds)
diff --git a/stdlib/source/library/lux/control/concurrency/semaphore.lux b/stdlib/source/library/lux/control/concurrency/semaphore.lux
index 7e9b039b4..121a78c2b 100644
--- a/stdlib/source/library/lux/control/concurrency/semaphore.lux
+++ b/stdlib/source/library/lux/control/concurrency/semaphore.lux
@@ -144,7 +144,7 @@
(if (n.< times step)
(do async.monad
[outcome (..signal! turnstile)]
- (recur (++ step)))
+ (again (++ step)))
(# async.monad in []))))
(template [<phase> <update> <goal> <turnstile>]
diff --git a/stdlib/source/library/lux/control/concurrency/stm.lux b/stdlib/source/library/lux/control/concurrency/stm.lux
index 12e8b21e8..771b07b4a 100644
--- a/stdlib/source/library/lux/control/concurrency/stm.lux
+++ b/stdlib/source/library/lux/control/concurrency/stm.lux
@@ -221,10 +221,10 @@
[resolved? (resolve entry)]
(if resolved?
(atom.write! (product.right entry) pending_commits)
- (recur |commits|&resolve)))
+ (again |commits|&resolve)))
{.#Some [head tail]}
- (recur tail)))))))
+ (again tail)))))))
(def: (process_commit! commit)
(All (_ a) (-> (Commit a) (IO Any)))
@@ -247,10 +247,10 @@
(if was_first?
(do !
[[async resolve] (atom.read! pending_commits)]
- (async.upon! (function (recur [head [tail _resolve]])
+ (async.upon! (function (again [head [tail _resolve]])
(do !
[_ (..process_commit! head)]
- (async.upon! recur tail)))
+ (async.upon! again tail)))
async))
(in [])))
)))
diff --git a/stdlib/source/library/lux/control/concurrency/thread.lux b/stdlib/source/library/lux/control/concurrency/thread.lux
index e074c322a..0c4626bab 100644
--- a/stdlib/source/library/lux/control/concurrency/thread.lux
+++ b/stdlib/source/library/lux/control/concurrency/thread.lux
@@ -167,7 +167,7 @@
(if swapped?
(do !
[_ (monad.each ! (|>> (value@ #action) ..execute! io.io) ready)]
- (recur []))
+ (again []))
(panic! (exception.error ..cannot_continue_running_threads []))))
))))
))
diff --git a/stdlib/source/library/lux/control/parser/binary.lux b/stdlib/source/library/lux/control/parser/binary.lux
index b76df036e..c6a56de41 100644
--- a/stdlib/source/library/lux/control/parser/binary.lux
+++ b/stdlib/source/library/lux/control/parser/binary.lux
@@ -203,7 +203,7 @@
(if (n.< amount index)
(do //.monad
[value valueP]
- (recur (.++ index)
+ (again (.++ index)
(row.suffix value output)))
(//#in output)))))]
@@ -265,8 +265,8 @@
(def: .public code
(Parser Code)
(..rec
- (function (_ recur)
- (let [sequence (..list recur)]
+ (function (_ again)
+ (let [sequence (..list again)]
(//.and ..location
(!variant [[0 [.#Bit] ..bit]
[1 [.#Nat] ..nat]
diff --git a/stdlib/source/library/lux/control/parser/cli.lux b/stdlib/source/library/lux/control/parser/cli.lux
index dbb5a2d32..1af6a30f2 100644
--- a/stdlib/source/library/lux/control/parser/cli.lux
+++ b/stdlib/source/library/lux/control/parser/cli.lux
@@ -69,7 +69,7 @@
{.#Item to_omit immediate'}
(do try.monad
- [[remaining output] (recur immediate')]
+ [[remaining output] (again immediate')]
(in [{.#Item to_omit remaining}
output])))))))
diff --git a/stdlib/source/library/lux/control/parser/json.lux b/stdlib/source/library/lux/control/parser/json.lux
index 22487ec8a..ae1e82d9c 100644
--- a/stdlib/source/library/lux/control/parser/json.lux
+++ b/stdlib/source/library/lux/control/parser/json.lux
@@ -167,7 +167,7 @@
(def: .public (field field_name parser)
(All (_ a) (-> Text (Parser a) (Parser a)))
- (function (recur inputs)
+ (function (again inputs)
(case inputs
(^ (list& {/.#String key} value inputs'))
(if (text#= key field_name)
@@ -181,7 +181,7 @@
{try.#Failure error}
{try.#Failure error})
(do try.monad
- [[inputs'' output] (recur inputs')]
+ [[inputs'' output] (again inputs')]
(in [(list& {/.#String key} value inputs'')
output])))
diff --git a/stdlib/source/library/lux/control/parser/type.lux b/stdlib/source/library/lux/control/parser/type.lux
index 85e710ec2..941767839 100644
--- a/stdlib/source/library/lux/control/parser/type.lux
+++ b/stdlib/source/library/lux/control/parser/type.lux
@@ -189,7 +189,7 @@
(if (n.< num_args current_arg)
(if (n.= 0 current_arg)
(let [varL (label (++ funcI))]
- (recur (++ current_arg)
+ (again (++ current_arg)
(|> env'
(dictionary.has funcI [headT funcL])
(dictionary.has (++ funcI) [{.#Parameter (++ funcI)} varL]))
@@ -200,7 +200,7 @@
partialC (` ((~ funcL) (~+ (|> (list.indices num_args)
(list#each (|>> (n.* 2) ++ (n.+ funcI) label))
list.reversed))))]
- (recur (++ current_arg)
+ (again (++ current_arg)
(|> env'
(dictionary.has partialI [(|recursion_dummy|) partialC])
(dictionary.has partial_varI [{.#Parameter partial_varI} partial_varL]))
diff --git a/stdlib/source/library/lux/control/parser/xml.lux b/stdlib/source/library/lux/control/parser/xml.lux
index 0fc4ab793..780a0b18f 100644
--- a/stdlib/source/library/lux/control/parser/xml.lux
+++ b/stdlib/source/library/lux/control/parser/xml.lux
@@ -128,7 +128,7 @@
(def: .public (somewhere parser)
(All (_ a) (-> (Parser a) (Parser a)))
- (function (recur [attrs input])
+ (function (again [attrs input])
(case (//.result parser [attrs input])
{try.#Success [[attrs remaining] output]}
{try.#Success [[attrs remaining] output]}
@@ -140,6 +140,6 @@
{.#Item head tail}
(do try.monad
- [[[attrs tail'] output] (recur [attrs tail])]
+ [[[attrs tail'] output] (again [attrs tail])]
(in [[attrs {.#Item head tail'}]
output]))))))
diff --git a/stdlib/source/library/lux/control/pipe.lux b/stdlib/source/library/lux/control/pipe.lux
index 2d44a11fb..7c7866e31 100644
--- a/stdlib/source/library/lux/control/pipe.lux
+++ b/stdlib/source/library/lux/control/pipe.lux
@@ -73,7 +73,7 @@
(with_symbols [g!temp]
(in (list (` (loop [(~ g!temp) (~ prev)]
(if (|> (~ g!temp) (~+ test))
- ((~' recur) (|> (~ g!temp) (~+ then)))
+ ((~' again) (|> (~ g!temp) (~+ then)))
(~ g!temp))))))))
(syntax: .public (do> [monad <code>.any
diff --git a/stdlib/source/library/lux/data/binary.lux b/stdlib/source/library/lux/data/binary.lux
index e747e40b1..b5530923d 100644
--- a/stdlib/source/library/lux/data/binary.lux
+++ b/stdlib/source/library/lux/data/binary.lux
@@ -192,7 +192,7 @@
(loop [index 0
output init]
(if (n.< size index)
- (recur (++ index) (f (!read index binary) output))
+ (again (++ index) (f (!read index binary) output))
output))))
(def: .public (read/8! index binary)
@@ -295,7 +295,7 @@
(if (n.< limit index)
(and (n.= (!read index reference)
(!read index sample))
- (recur (++ index)))
+ (again (++ index)))
true))))))))
(for [@.old (as_is)
@@ -328,7 +328,7 @@
(exec (!write (n.+ target_offset index)
(!read (n.+ source_offset index) source)
target)
- (recur (++ index)))
+ (again (++ index)))
{try.#Success target})))))))
(def: .public (slice offset length binary)
diff --git a/stdlib/source/library/lux/data/collection/array.lux b/stdlib/source/library/lux/data/collection/array.lux
index 766213cea..2fe33d2e1 100644
--- a/stdlib/source/library/lux/data/collection/array.lux
+++ b/stdlib/source/library/lux/data/collection/array.lux
@@ -227,12 +227,12 @@
(if (n.< arr_size idx)
(case (read! idx xs)
{.#None}
- (recur (++ idx))
+ (again (++ idx))
{.#Some x}
(if (p x)
{.#Some x}
- (recur (++ idx))))
+ (again (++ idx))))
{.#None}))))
(def: .public (example+ p xs)
@@ -243,12 +243,12 @@
(if (n.< arr_size idx)
(case (read! idx xs)
{.#None}
- (recur (++ idx))
+ (again (++ idx))
{.#Some x}
(if (p idx x)
{.#Some [idx x]}
- (recur (++ idx))))
+ (again (++ idx))))
{.#None}))))
(def: .public (clone xs)
@@ -284,7 +284,7 @@
output
_
- (recur (-- idx)
+ (again (-- idx)
(case (read! idx array)
{.#Some head}
{.#Item head output}
@@ -301,7 +301,7 @@
output
_
- (recur (-- idx)
+ (again (-- idx)
{.#Item (maybe.else default (read! idx array))
output}))))
@@ -375,10 +375,10 @@
(if (n.< arr_size idx)
(case (read! idx xs)
{.#None}
- (recur so_far (++ idx))
+ (again so_far (++ idx))
{.#Some value}
- (recur (f value so_far) (++ idx)))
+ (again (f value so_far) (++ idx)))
so_far)))))
(template [<name> <init> <op>]
@@ -392,10 +392,10 @@
(case (..read! idx array)
{.#Some value}
(<op> (predicate value)
- (recur (++ idx)))
+ (again (++ idx)))
{.#None}
- (recur (++ idx)))
+ (again (++ idx)))
<init>)))))]
[every? true and]
diff --git a/stdlib/source/library/lux/data/collection/bits.lux b/stdlib/source/library/lux/data/collection/bits.lux
index 3db996fdf..b2fbeced2 100644
--- a/stdlib/source/library/lux/data/collection/bits.lux
+++ b/stdlib/source/library/lux/data/collection/bits.lux
@@ -78,7 +78,7 @@
.nat)
0
... TODO: Remove 'no_op' once new-luxc is the official compiler.
- (let [no_op (recur (-- size|output) output)]
+ (let [no_op (again (-- size|output) output)]
no_op)
chunk
@@ -86,7 +86,7 @@
(: Bits (array.empty size|output))
output)
(array.write! idx|output (.i64 chunk))
- (recur (-- size|output))))
+ (again (-- size|output))))
output)))))]
[one i64.one]
@@ -104,7 +104,7 @@
(i64.and (..chunk idx reference))
("lux i64 =" empty_chunk)
.not)
- (recur (++ idx)))
+ (again (++ idx)))
#0))))
(def: .public (not input)
@@ -119,7 +119,7 @@
(let [idx (-- size|output)]
(case (|> input (..chunk idx) i64.not .nat)
0
- (recur (-- size|output) output)
+ (again (-- size|output) output)
chunk
(if (n.> 0 size|output)
@@ -127,7 +127,7 @@
(: Bits (array.empty size|output))
output)
(array.write! idx (.i64 chunk))
- (recur (-- size|output)))
+ (again (-- size|output)))
output))))))
(template [<name> <op>]
@@ -147,14 +147,14 @@
(<op> (..chunk idx param))
.nat)
0
- (recur (-- size|output) output)
+ (again (-- size|output) output)
chunk
(|> (if (same? ..empty output)
(: Bits (array.empty size|output))
output)
(array.write! idx (.i64 chunk))
- (recur (-- size|output))))
+ (again (-- size|output))))
output)))))]
[and i64.and]
@@ -173,5 +173,5 @@
(.and ("lux i64 ="
(..chunk idx reference)
(..chunk idx sample))
- (recur (++ idx)))
+ (again (++ idx)))
#1)))))
diff --git a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
index 9b4b308b7..9ef4d8686 100644
--- a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
@@ -73,10 +73,10 @@
(# dict < node_key key)
... (_#< node_key key)
- (recur (value@ #left node))
+ (again (value@ #left node))
... (_#> (value@ #key node) key)
- (recur (value@ #right node))))
+ (again (value@ #right node))))
))))
... TODO: Doing inneficient access of Order functions due to compiler bug.
@@ -96,8 +96,8 @@
... (_#= node_key key)
(if (# dict < node_key key)
... (_#< node_key key)
- (recur (value@ #left node))
- (recur (value@ #right node)))))))))
+ (again (value@ #left node))
+ (again (value@ #right node)))))))))
(template [<name> <side>]
[(def: .public (<name> dict)
@@ -113,7 +113,7 @@
{.#Some (value@ #value node)}
{.#Some side}
- (recur side)))))]
+ (again side)))))]
[min #left]
[max #right]
@@ -127,8 +127,8 @@
0
{.#Some node}
- (++ (n.+ (recur (value@ #left node))
- (recur (value@ #right node)))))))
+ (++ (n.+ (again (value@ #left node))
+ (again (value@ #right node)))))))
(def: .public empty?
(All (_ k v) (-> (Dictionary k v) Bit))
@@ -260,7 +260,7 @@
(`` (cond (~~ (template [<comp> <tag> <add>]
[(<comp> reference key)
(let [side_root (value@ <tag> root)
- outcome (recur side_root)]
+ outcome (again side_root)]
(if (same? side_root outcome)
?root
{.#Some (<add> (maybe.trusted outcome)
@@ -486,7 +486,7 @@
(value@ #right root))
#1]
(let [go_left? (_#< root_key key)]
- (case (recur (if go_left?
+ (case (again (if go_left?
(value@ #left root)
(value@ #right root)))
[{.#None} #0]
@@ -551,9 +551,9 @@
{.#Some node'}
($_ list#composite
- (recur (value@ #left node'))
+ (again (value@ #left node'))
(list <output>)
- (recur (value@ #right node'))))))]
+ (again (value@ #right node'))))))]
[entries [k v] [(value@ #key node') (value@ #value node')]]
[keys k (value@ #key node')]
@@ -574,7 +574,7 @@
[{.#Item [keyR valueR] entriesR'} {.#Item [keyS valueS] entriesS'}]
(and (/#= keyR keyS)
(,#= valueR valueS)
- (recur entriesR' entriesS'))
+ (again entriesR' entriesS'))
_
#0)))))
diff --git a/stdlib/source/library/lux/data/collection/list.lux b/stdlib/source/library/lux/data/collection/list.lux
index 6860eb4d6..6166724c7 100644
--- a/stdlib/source/library/lux/data/collection/list.lux
+++ b/stdlib/source/library/lux/data/collection/list.lux
@@ -449,7 +449,7 @@
input' (n./ 10 input)]
(case input'
0 output'
- _ (recur input' output')))))
+ _ (again input' output')))))
(macro: .public (zipped tokens state)
(case tokens
@@ -602,7 +602,7 @@
{.#End}
{.#Item x xs'}
- {.#Item [idx x] (recur (++ idx) xs')})))
+ {.#Item [idx x] (again (++ idx) xs')})))
(macro: .public (when tokens state)
(case tokens
diff --git a/stdlib/source/library/lux/data/collection/queue/priority.lux b/stdlib/source/library/lux/data/collection/queue/priority.lux
index 52cd3929a..4766683b8 100644
--- a/stdlib/source/library/lux/data/collection/queue/priority.lux
+++ b/stdlib/source/library/lux/data/collection/queue/priority.lux
@@ -64,7 +64,7 @@
1
{0 #1 [left right]}
- (n.+ (recur left) (recur right))))))
+ (n.+ (again left) (again right))))))
(def: .public (member? equivalence queue member)
(All (_ a) (-> (Equivalence a) (Queue a) a Bit))
@@ -79,8 +79,8 @@
(# equivalence = reference member)
{0 #1 [left right]}
- (or (recur left)
- (recur right))))))
+ (or (again left)
+ (again right))))))
(def: .public (next queue)
(All (_ a) (-> (Queue a) (Queue a)))
@@ -97,13 +97,13 @@
{0 #1 left right}
(if (n.= highest_priority (tree.tag left))
- (case (recur left)
+ (case (again left)
{.#None}
{.#Some right}
{.#Some =left}
{.#Some (# ..builder branch =left right)})
- (case (recur right)
+ (case (again right)
{.#None}
{.#Some left}
diff --git a/stdlib/source/library/lux/data/collection/row.lux b/stdlib/source/library/lux/data/collection/row.lux
index c1b3b6ece..ae8a99c37 100644
--- a/stdlib/source/library/lux/data/collection/row.lux
+++ b/stdlib/source/library/lux/data/collection/row.lux
@@ -262,7 +262,7 @@
(case [(n.> branching_exponent level)
(array.read! (branch_idx (i64.right_shifted level idx)) hierarchy)]
[#1 {.#Some {#Hierarchy sub}}]
- (recur (level_down level) sub)
+ (again (level_down level) sub)
[#0 {.#Some {#Base base}}]
{try.#Success base}
@@ -333,7 +333,7 @@
(if (n.> branching_exponent level)
(case [(array.read! 1 root) (array.read! 0 root)]
[{.#None} {.#Some {#Hierarchy sub_node}}]
- (recur (level_down level) sub_node)
+ (again (level_down level) sub_node)
... [{.#None} {.#Some {#Base _}}]
... (undefined)
diff --git a/stdlib/source/library/lux/data/collection/sequence.lux b/stdlib/source/library/lux/data/collection/sequence.lux
index fbd998ae2..fcfe2d0ed 100644
--- a/stdlib/source/library/lux/data/collection/sequence.lux
+++ b/stdlib/source/library/lux/data/collection/sequence.lux
@@ -40,10 +40,10 @@
tail next]
(//.pending [head (case tail
{.#End}
- (recur start next)
+ (again start next)
{.#Item head' tail'}
- (recur head' tail'))])))
+ (again head' tail'))])))
(template [<name> <return>]
[(def: .public (<name> sequence)
diff --git a/stdlib/source/library/lux/data/collection/tree.lux b/stdlib/source/library/lux/data/collection/tree.lux
index fe98bdfdf..7be4807e8 100644
--- a/stdlib/source/library/lux/data/collection/tree.lux
+++ b/stdlib/source/library/lux/data/collection/tree.lux
@@ -57,7 +57,7 @@
(syntax: .public (tree [root tree^])
(in (list (` (~ (loop [[value children] root]
(` [#value (~ value)
- #children (list (~+ (list#each recur children)))])))))))
+ #children (list (~+ (list#each again children)))])))))))
(implementation: .public (equivalence super)
(All (_ a) (-> (Equivalence a) (Equivalence (Tree a))))
diff --git a/stdlib/source/library/lux/data/collection/tree/finger.lux b/stdlib/source/library/lux/data/collection/tree/finger.lux
index a82b78f96..90e929937 100644
--- a/stdlib/source/library/lux/data/collection/tree/finger.lux
+++ b/stdlib/source/library/lux/data/collection/tree/finger.lux
@@ -96,8 +96,8 @@
{0 #1 [left right]}
(let [shifted_tag (tag//composite _tag (..tag left))]
(if (predicate shifted_tag)
- (recur _tag (value@ #root (:representation left)))
- (recur shifted_tag (value@ #root (:representation right))))))))
+ (again _tag (value@ #root (:representation left)))
+ (again shifted_tag (value@ #root (:representation right))))))))
{.#None})))
)
diff --git a/stdlib/source/library/lux/data/collection/tree/zipper.lux b/stdlib/source/library/lux/data/collection/tree/zipper.lux
index 19581bb40..daeab670d 100644
--- a/stdlib/source/library/lux/data/collection/tree/zipper.lux
+++ b/stdlib/source/library/lux/data/collection/tree/zipper.lux
@@ -185,7 +185,7 @@
{.#None}
(do maybe.monad
[@ (..up @)]
- (recur @))))))
+ (again @))))))
(def: (bottom zipper)
(All (_ a) (-> (Zipper a) (Zipper a)))
@@ -229,7 +229,7 @@
{.#Some @}
{.#Some @}
- (recur @)))))]
+ (again @)))))]
[end ..next]
[start ..previous]
diff --git a/stdlib/source/library/lux/data/format/binary.lux b/stdlib/source/library/lux/data/format/binary.lux
index 94fdea2bc..abf28f5d0 100644
--- a/stdlib/source/library/lux/data/format/binary.lux
+++ b/stdlib/source/library/lux/data/format/binary.lux
@@ -105,8 +105,8 @@
(def: .public (rec body)
(All (_ a) (-> (-> (Writer a) (Writer a)) (Writer a)))
- (function (recur value)
- (body recur value)))
+ (function (again value)
+ (body again value)))
(def: .public any
(Writer Any)
@@ -226,10 +226,10 @@
(def: .public type
(Writer Type)
(..rec
- (function (_ recur)
- (let [pair (..and recur recur)
+ (function (_ again)
+ (let [pair (..and again again)
indexed ..nat
- quantified (..and (..list recur) recur)]
+ quantified (..and (..list again) again)]
(function (_ altV)
(case altV
(^template [<number> <tag> <writer>]
@@ -242,7 +242,7 @@
try.trusted
[(.++ offset)]
caseT))])])
- ([0 .#Primitive (..and ..text (..list recur))]
+ ([0 .#Primitive (..and ..text (..list again))]
[1 .#Sum pair]
[2 .#Product pair]
[3 .#Function pair]
@@ -252,7 +252,7 @@
[7 .#UnivQ quantified]
[8 .#ExQ quantified]
[9 .#Apply pair]
- [10 .#Named (..and ..symbol recur)])
+ [10 .#Named (..and ..symbol again)])
))))))
(def: .public location
@@ -262,8 +262,8 @@
(def: .public code
(Writer Code)
(..rec
- (function (_ recur)
- (let [sequence (..list recur)]
+ (function (_ again)
+ (let [sequence (..list again)]
(..and ..location
(function (_ altV)
(case altV
diff --git a/stdlib/source/library/lux/data/format/json.lux b/stdlib/source/library/lux/data/format/json.lux
index 0a160e2ff..56400e0ca 100644
--- a/stdlib/source/library/lux/data/format/json.lux
+++ b/stdlib/source/library/lux/data/format/json.lux
@@ -386,7 +386,7 @@
(if (text#= "\" stop)
(do !
[escaped escaped_parser
- next_chars (recur [])]
+ next_chars (again [])]
(in ($_ text#composite chars escaped next_chars)))
(in chars))))
diff --git a/stdlib/source/library/lux/data/format/tar.lux b/stdlib/source/library/lux/data/format/tar.lux
index fdc3c0022..dd511524b 100644
--- a/stdlib/source/library/lux/data/format/tar.lux
+++ b/stdlib/source/library/lux/data/format/tar.lux
@@ -238,7 +238,7 @@
[last_char (binary.read/8! end string)]
(`` (case (.nat last_char)
(^ (char (~~ (static ..null))))
- (recur (-- end))
+ (again (-- end))
_
(binary.slice 0 (++ end) string))))))))
diff --git a/stdlib/source/library/lux/data/format/xml.lux b/stdlib/source/library/lux/data/format/xml.lux
index ec9516eb5..265b05516 100644
--- a/stdlib/source/library/lux/data/format/xml.lux
+++ b/stdlib/source/library/lux/data/format/xml.lux
@@ -268,7 +268,7 @@
($_ text#composite prefix "<" tag attrs "/>")
($_ text#composite prefix "<" tag attrs ">"
(|> xml_children
- (list#each (|>> (recur (text#composite prefix text.tab)) (text#composite text.new_line)))
+ (list#each (|>> (again (text#composite prefix text.tab)) (text#composite text.new_line)))
text.together)
text.new_line prefix "</" tag ">")))))
))))
diff --git a/stdlib/source/library/lux/data/text.lux b/stdlib/source/library/lux/data/text.lux
index 9a475bae4..ee72cef3e 100644
--- a/stdlib/source/library/lux/data/text.lux
+++ b/stdlib/source/library/lux/data/text.lux
@@ -75,7 +75,7 @@
output
{.#Some offset'}
- (recur (++ offset') output')))))
+ (again (++ offset') output')))))
(def: .public (starts_with? prefix x)
(-> Text Text Bit)
@@ -168,7 +168,7 @@
{.#Some [pre post]}
(|> output
{.#Item pre}
- (recur post))
+ (again post))
{.#None}
(|> output
@@ -220,7 +220,7 @@
right template]
(case (..split_by pattern right)
{.#Some [pre post]}
- (recur ($_ "lux text concat" left pre replacement) post)
+ (again ($_ "lux text concat" left pre replacement) post)
{.#None}
("lux text concat" left right)))))
@@ -273,7 +273,7 @@
(loop [index 0
hash 0]
(if (n.< length index)
- (recur (++ index)
+ (again (++ index)
(|> hash
(i64.left_shifted 5)
(n.- hash)
diff --git a/stdlib/source/library/lux/data/text/escape.lux b/stdlib/source/library/lux/data/text/escape.lux
index 33d2d0a9e..ffefa4ade 100644
--- a/stdlib/source/library/lux/data/text/escape.lux
+++ b/stdlib/source/library/lux/data/text/escape.lux
@@ -120,7 +120,7 @@
(^template [<char> <replacement>]
[(^ (static <char>))
(let [[previous' current' limit'] (ascii_escaped <replacement> offset limit previous current)]
- (recur 0 previous' current' limit'))])
+ (again 0 previous' current' limit'))])
([..\0 ..escaped_\0]
[..\a ..escaped_\a]
[..\b ..escaped_\b]
@@ -136,8 +136,8 @@
(if (or (n.< ..ascii_bottom char)
(n.> ..ascii_top char))
(let [[previous' current' limit'] (unicode_escaped char offset limit previous current)]
- (recur 0 previous' current' limit'))
- (recur (++ offset) previous current limit)))
+ (again 0 previous' current' limit'))
+ (again (++ offset) previous current limit)))
(format previous current))))
(exception: .public (dangling_escape [text Text])
@@ -208,7 +208,7 @@
(^template [<sigil> <un_escaped>]
[(^ (static <sigil>))
(let [[previous' current' limit'] (..ascii_un_escaped <un_escaped> offset previous current limit)]
- (recur 0 previous' current' limit'))])
+ (again 0 previous' current' limit'))])
([..\0_sigil //.\0]
[..\a_sigil //.\a]
[..\b_sigil //.\b]
@@ -225,7 +225,7 @@
(if (n.< limit @unicode)
(do try.monad
[[previous' current' limit'] (..unicode_un_escaped offset previous current limit)]
- (recur 0 previous' current' limit'))
+ (again 0 previous' current' limit'))
(exception.except ..invalid_unicode_escape [text offset])))
invalid_sigil
@@ -233,7 +233,7 @@
(exception.except ..dangling_escape [text])))
_
- (recur (++ offset) previous current limit))
+ (again (++ offset) previous current limit))
{try.#Success (case previous
"" current
_ (format previous current))})))
diff --git a/stdlib/source/library/lux/data/text/unicode/set.lux b/stdlib/source/library/lux/data/text/unicode/set.lux
index b7f6720b8..6adc2b4b2 100644
--- a/stdlib/source/library/lux/data/text/unicode/set.lux
+++ b/stdlib/source/library/lux/data/text/unicode/set.lux
@@ -221,8 +221,8 @@
true
{0 #1 left right}
- (or (recur left)
- (recur right)))
+ (or (again left)
+ (again right)))
false)))
(implementation: .public equivalence
diff --git a/stdlib/source/library/lux/debug.lux b/stdlib/source/library/lux/debug.lux
index ed076d3ae..ee83680a0 100644
--- a/stdlib/source/library/lux/debug.lux
+++ b/stdlib/source/library/lux/debug.lux
@@ -126,7 +126,7 @@
(let [member ("lua array read" idx tuple)]
(if ("lua object nil?" member)
{.#End}
- {.#Item member (recur (++ idx))})))))]
+ {.#Item member (again (++ idx))})))))]
(as_is))
(def: (tuple_inspection inspection)
@@ -458,7 +458,7 @@
[lefts #1 (rightR right)]
_
- (recur (++ lefts) {.#Item rightR extraR+} right)))
+ (again (++ lefts) {.#Item rightR extraR+} right)))
_
(undefined)))]
@@ -480,7 +480,7 @@
{.#Item headR tailR}
(let [[leftV rightV] (:as [Any Any] tupleV)]
- (%.format (headR leftV) " " (recur tailR rightV)))))]
+ (%.format (headR leftV) " " (again tailR rightV)))))]
(%.format "[" tuple_body "]"))))))
(def: representation_parser
diff --git a/stdlib/source/library/lux/ffi.jvm.lux b/stdlib/source/library/lux/ffi.jvm.lux
index 7e8a46ce3..415189510 100644
--- a/stdlib/source/library/lux/ffi.jvm.lux
+++ b/stdlib/source/library/lux/ffi.jvm.lux
@@ -618,7 +618,7 @@
(def: (parameter^ type_vars)
(-> (List (Type Var)) (Parser (Type Parameter)))
(<>.rec
- (function (_ recur^)
+ (function (_ _)
(let [class^ (..class^' parameter^ type_vars)]
($_ <>.either
(..variable^ type_vars)
diff --git a/stdlib/source/library/lux/ffi.old.lux b/stdlib/source/library/lux/ffi.old.lux
index e40d2302c..25a26ef69 100644
--- a/stdlib/source/library/lux/ffi.old.lux
+++ b/stdlib/source/library/lux/ffi.old.lux
@@ -554,7 +554,7 @@
(def: (generic_type^ type_vars)
(-> (List Type_Parameter) (Parser GenericType))
(<>.rec
- (function (_ recur^)
+ (function (_ again^)
($_ <>.either
(do <>.monad
[_ (<code>.this! (' ?))]
@@ -562,7 +562,7 @@
(<code>.tuple (do <>.monad
[_ (<code>.this! (' ?))
bound_kind bound_kind^
- bound recur^]
+ bound again^]
(in {#GenericWildcard {.#Some [bound_kind bound]}})))
(do <>.monad
[name <code>.local_symbol
@@ -571,7 +571,7 @@
(in {#GenericTypeVar name})
(in {#GenericClass name (list)})))
(<code>.tuple (do <>.monad
- [component recur^]
+ [component again^]
(case component
(^template [<class> <name>]
[{#GenericClass <name> {.#End}}
@@ -590,7 +590,7 @@
(<code>.form (do <>.monad
[name <code>.local_symbol
_ (no_periods_assertion name)
- params (<>.some recur^)
+ params (<>.some again^)
_ (<>.assertion (format name " cannot be a type-parameter!")
(not (list.member? text.equivalence (list#each product.left type_vars) name)))]
(in {#GenericClass name params})))
diff --git a/stdlib/source/library/lux/math.lux b/stdlib/source/library/lux/math.lux
index 22b79ed09..616e32661 100644
--- a/stdlib/source/library/lux/math.lux
+++ b/stdlib/source/library/lux/math.lux
@@ -329,7 +329,7 @@
(loop [acc 1
it it]
(if (n.> 1 it)
- (recur (n.* it acc) (-- it))
+ (again (n.* it acc) (-- it))
acc)))
(def: .public (hypotenuse catA catB)
diff --git a/stdlib/source/library/lux/math/number/i64.lux b/stdlib/source/library/lux/math/number/i64.lux
index 03f2241af..651c9f943 100644
--- a/stdlib/source/library/lux/math/number/i64.lux
+++ b/stdlib/source/library/lux/math/number/i64.lux
@@ -151,7 +151,7 @@
(loop [iterations 1
output char]
(if (n.< times iterations)
- (recur (++ iterations)
+ (again (++ iterations)
("lux text concat" char output))
output))))
pattern (repetitions (n./ (n.+ size size) ..width)
diff --git a/stdlib/source/library/lux/math/number/int.lux b/stdlib/source/library/lux/math/number/int.lux
index 3aa65a4c4..d04023bcb 100644
--- a/stdlib/source/library/lux/math/number/int.lux
+++ b/stdlib/source/library/lux/math/number/int.lux
@@ -137,7 +137,7 @@
(case b1
+0 [[x y] a1]
_ (let [q (/ b1 a1)]
- (recur x1 (- (* q x1) x)
+ (again x1 (- (* q x1) x)
y1 (- (* q y1) y)
b1 (- (* q b1) a1))))))
diff --git a/stdlib/source/library/lux/math/number/nat.lux b/stdlib/source/library/lux/math/number/nat.lux
index 515f5887a..a94118ad9 100644
--- a/stdlib/source/library/lux/math/number/nat.lux
+++ b/stdlib/source/library/lux/math/number/nat.lux
@@ -303,7 +303,7 @@
output'
input'
- (recur input' output')))))))
+ (again input' output')))))))
(def: (decoded repr)
(let [input_size ("lux text size" repr)]
@@ -313,7 +313,7 @@
(if (..< input_size idx)
(case (<to_value> ("lux text char" idx repr))
{.#Some digit_value}
- (recur (++ idx)
+ (again (++ idx)
(|> output
("lux i64 left-shift" <shift>)
("lux i64 or" digit_value)))
@@ -341,7 +341,7 @@
output'
input'
- (recur input' output')))))
+ (again input' output')))))
(def: (decoded repr)
(let [input_size ("lux text size" repr)]
@@ -355,7 +355,7 @@
<failure>
{.#Some digit_value}
- (recur (++ idx)
+ (again (++ idx)
(|> output (..* 10) (..+ digit_value))))
{try.#Success output}))
<failure>)))))
diff --git a/stdlib/source/library/lux/math/number/rev.lux b/stdlib/source/library/lux/math/number/rev.lux
index 7f594c5ac..acefd9944 100644
--- a/stdlib/source/library/lux/math/number/rev.lux
+++ b/stdlib/source/library/lux/math/number/rev.lux
@@ -241,7 +241,7 @@
output (: Text "")]
(if (//nat.= 0 zeroes_left)
output
- (recur (-- zeroes_left)
+ (again (-- zeroes_left)
("lux text concat" "0" output)))))]
(|> raw_output
("lux text concat" zero_padding)
@@ -305,7 +305,7 @@
(let [raw (|> (..digit idx output)
(//nat.* 5)
(//nat.+ carry))]
- (recur (-- idx)
+ (again (-- idx)
(//nat./ 10 raw)
(digits#put! idx (//nat.% 10 raw) output))))))
@@ -316,7 +316,7 @@
(digits#put! power 1))]
(if (//int.< +0 (.int times))
output
- (recur (-- times)
+ (again (-- times)
(digits#times_5! power output)))))
(def: (format digits)
@@ -331,8 +331,8 @@
(let [digit (..digit idx digits)]
(if (and (//nat.= 0 digit)
all_zeroes?)
- (recur (-- idx) true output)
- (recur (-- idx)
+ (again (-- idx) true output)
+ (again (-- idx)
false
("lux text concat"
(# //nat.decimal encoded digit)
@@ -349,7 +349,7 @@
carry
(..digit idx param)
(..digit idx subject))]
- (recur (-- idx)
+ (again (-- idx)
(//nat./ 10 raw)
(digits#put! idx (//nat.% 10 raw) output))))))
@@ -366,7 +366,7 @@
{.#None}
{.#Some digit}
- (recur (++ idx)
+ (again (++ idx)
(digits#put! idx digit output)))
{.#Some output})))))
@@ -377,7 +377,7 @@
(let [pd (..digit idx param)
sd (..digit idx subject)]
(if (//nat.= pd sd)
- (recur (++ idx))
+ (again (++ idx))
(//nat.< pd sd))))))
(def: (digits#-!' idx param subject)
@@ -398,7 +398,7 @@
output subject]
(if (//int.< +0 (.int idx))
output
- (recur (-- idx)
+ (again (-- idx)
(digits#-!' idx (..digit idx param) output)))))
(implementation: .public decimal
@@ -418,9 +418,9 @@
(if (//i64.one? idx input)
(let [digits' (digits#+! (power_digits (//nat.- idx last_idx))
digits)]
- (recur (-- idx)
+ (again (-- idx)
digits'))
- (recur (-- idx)
+ (again (-- idx)
digits)))))))
(def: (decoded input)
@@ -443,8 +443,8 @@
(let [power (power_digits idx)]
(if (digits#< power digits)
... Skip power
- (recur digits (++ idx) output)
- (recur (digits#-! power digits)
+ (again digits (++ idx) output)
+ (again (digits#-! power digits)
(++ idx)
(//i64.one (//nat.- idx (-- //i64.width)) output))))
{try.#Success (.rev output)}))
diff --git a/stdlib/source/library/lux/math/random.lux b/stdlib/source/library/lux/math/random.lux
index 3b0d97912..a7fffe898 100644
--- a/stdlib/source/library/lux/math/random.lux
+++ b/stdlib/source/library/lux/math/random.lux
@@ -277,7 +277,7 @@
.let [xs+ (set.has x xs)]]
(if (n.= size (set.size xs+))
(in xs+)
- (recur [])))))
+ (again [])))))
(# ..monad in (set.empty hash))))
(def: .public (dictionary hash size key_gen value_gen)
@@ -292,7 +292,7 @@
.let [kv+ (dictionary.has k v kv)]]
(if (n.= size (dictionary.size kv+))
(in kv+)
- (recur [])))))
+ (again [])))))
(# ..monad in (dictionary.empty hash))))
(def: .public instant
@@ -344,9 +344,9 @@
(def: .public (prng update return)
(All (_ a) (-> (-> a a) (-> a I64) (-> a PRNG)))
- (function (recur state)
+ (function (again state)
(function (_ _)
- [(recur (update state))
+ [(again (update state))
(return state)])))
(def: .public (pcg_32 [increase seed])
diff --git a/stdlib/source/library/lux/meta.lux b/stdlib/source/library/lux/meta.lux
index aa333b9d3..a3b214027 100644
--- a/stdlib/source/library/lux/meta.lux
+++ b/stdlib/source/library/lux/meta.lux
@@ -185,7 +185,7 @@
(plist.value name)))]
(case definition
{.#Alias [r_module r_name]}
- (recur r_module r_name)
+ (again r_module r_name)
{.#Definition [exported? def_type def_value]}
(if (macro_type? def_type)
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
index 61bb956bd..c77332e4e 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
@@ -643,7 +643,7 @@
{.#Item head tail}
(do !
[_ (binary.write/32! offset (///signed.value head) binary)]
- (recur (n.+ (///unsigned.value ..big_jump_size) offset)
+ (again (n.+ (///unsigned.value ..big_jump_size) offset)
tail))))))]))]
[(n.+ tableswitch_size
size)
@@ -703,7 +703,7 @@
(do !
[_ (binary.write/32! offset (///signed.value value) binary)
_ (binary.write/32! (n.+ (///unsigned.value ..integer_size) offset) (///signed.value jump) binary)]
- (recur (n.+ case_size offset)
+ (again (n.+ case_size offset)
tail))))))]))]
[(n.+ lookupswitch_size
size)
diff --git a/stdlib/source/library/lux/target/jvm/constant/pool.lux b/stdlib/source/library/lux/target/jvm/constant/pool.lux
index 8451bfdfa..65d5847b7 100644
--- a/stdlib/source/library/lux/target/jvm/constant/pool.lux
+++ b/stdlib/source/library/lux/target/jvm/constant/pool.lux
@@ -54,7 +54,7 @@
(template: (!add <tag> <equivalence> <value>)
[(function (_ [current pool])
(let [<value>' <value>]
- (with_expansions [<try_again> (as_is (recur (.++ idx)))]
+ (with_expansions [<try_again> (as_is (again (.++ idx)))]
(loop [idx 0]
(case (row.item idx pool)
{try.#Success entry}
diff --git a/stdlib/source/library/lux/test.lux b/stdlib/source/library/lux/test.lux
index 802320de4..745153897 100644
--- a/stdlib/source/library/lux/test.lux
+++ b/stdlib/source/library/lux/test.lux
@@ -169,7 +169,7 @@
0 (..failure (exception.error ..must_try_test_at_least_once []))
_ (do random.monad
[seed random.nat]
- (function (recur prng)
+ (function (again prng)
(let [[prng' instance] (random.result (random.pcg_32 [..pcg_32_magic_inc seed]) test)]
[prng' (do [! async.monad]
[[tally documentation] instance]
@@ -307,7 +307,7 @@
output (set.of_list symbol.hash (list))]
(case (text.split_by ..coverage_separator remaining)
{.#Some [head tail]}
- (recur tail (set.has [module head] output))
+ (again tail (set.has [module head] output))
{.#None}
(set.has [module remaining] output))))
diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux
index 8abaa949c..4fa1d7ed8 100644
--- a/stdlib/source/library/lux/tool/compiler/default/init.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/init.lux
@@ -270,7 +270,7 @@
(value@ ///directive.#imports)
(list#each product.left))
///.#process (function (_ state archive)
- (recur (<| (///phase.result' state)
+ (again (<| (///phase.result' state)
(do [! ///phase.monad]
[analysis_module (<| (: (Operation .Module))
///directive.lifted_analysis
diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux
index 64bef708c..e6b1ea9bb 100644
--- a/stdlib/source/library/lux/tool/compiler/default/platform.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux
@@ -558,7 +558,7 @@
(-> <Context> (///.Compilation <State+> .Module Any) (Set Module)
(Action [Archive <State+>]))
- (:expected recur))
+ (:expected again))
... 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.
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 4cb9d6911..d3663d830 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
@@ -284,7 +284,7 @@
inputs (list)]
(case abstraction
{#Apply input next}
- (recur next {.#Item input inputs})
+ (again next {.#Item input inputs})
_
[abstraction inputs])))
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 c0cd0f8c2..c7339a509 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
@@ -94,22 +94,22 @@
(check.peek id))]
(.case ?caseT'
{.#Some caseT'}
- (recur envs caseT')
+ (again envs caseT')
_
(/.except ..cannot_simplify_for_pattern_matching caseT)))
{.#Named name unnamedT}
- (recur envs unnamedT)
+ (again envs unnamedT)
{.#UnivQ env unquantifiedT}
- (recur {.#Item env envs} unquantifiedT)
+ (again {.#Item env envs} unquantifiedT)
{.#ExQ _}
(do ///.monad
[[var_id varT] (//type.with_env
check.var)]
- (recur envs (maybe.trusted (type.applied (list varT) caseT))))
+ (again envs (maybe.trusted (type.applied (list varT) caseT))))
{.#Apply inputT funcT}
(.case funcT
@@ -124,12 +124,12 @@
_
(check.except ..cannot_simplify_for_pattern_matching caseT))))]
- (recur envs {.#Apply inputT funcT'}))
+ (again envs {.#Apply inputT funcT'}))
_
(.case (type.applied (list inputT) funcT)
{.#Some outputT}
- (recur envs outputT)
+ (again envs outputT)
{.#None}
(/.except ..cannot_simplify_for_pattern_matching caseT)))
@@ -179,7 +179,7 @@
{.#Item [headT (code.tuple remainingP)] output}
[{.#Item headT tailT} {.#Item headP tailP}]
- (recur tailT tailP {.#Item [headT headP] output})
+ (again tailT tailP {.#Item [headT headP] output})
_
(undefined)))]
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 19a00d406..065badbe5 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
@@ -343,7 +343,7 @@
(case altMSF
{#Alt _}
(do !
- [[success altsSF+] (recur altsSF')]
+ [[success altsSF+] (again altsSF')]
(in [success {.#Item altSF altsSF+}]))
_
@@ -359,7 +359,7 @@
{.#Some coverageA'}
(do !
[[successA' possibilitiesSF'] (fuse_once coverageA' possibilitiesSF)]
- (recur successA' possibilitiesSF'))
+ (again successA' possibilitiesSF'))
{.#None}
(case (list.reversed possibilitiesSF)
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 951e367dc..498388a60 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
@@ -55,12 +55,12 @@
(/.with_stack ..cannot_analyse [expectedT function_name arg_name body]
(case expectedT
{.#Named name unnamedT}
- (recur unnamedT)
+ (again unnamedT)
{.#Apply argT funT}
(case (type.applied (list argT) funT)
{.#Some value}
- (recur value)
+ (again value)
{.#None}
(/.failure (ex.error cannot_analyse [expectedT function_name arg_name body])))
@@ -69,7 +69,7 @@
[{<tag> _}
(do !
[[_ instanceT] (//type.with_env <instancer>)]
- (recur (maybe.trusted (type.applied (list instanceT) expectedT))))])
+ (again (maybe.trusted (type.applied (list instanceT) expectedT))))])
([.#UnivQ check.existential]
[.#ExQ check.var])
@@ -79,7 +79,7 @@
(check.peek id))]
(case ?expectedT'
{.#Some expectedT'}
- (recur expectedT')
+ (again expectedT')
... Inference
_
@@ -87,7 +87,7 @@
[[input_id inputT] (//type.with_env check.var)
[output_id outputT] (//type.with_env check.var)
.let [functionT {.#Function inputT outputT}]
- functionA (recur functionT)
+ functionA (again functionT)
_ (//type.with_env
(check.check expectedT functionT))]
(in functionA))))
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 e031e8234..69192c27e 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
@@ -187,14 +187,14 @@
(def: (substitute_bound target sub)
(-> Nat Type Type Type)
- (function (recur base)
+ (function (again base)
(case base
{.#Primitive name parameters}
- {.#Primitive name (list#each recur parameters)}
+ {.#Primitive name (list#each again parameters)}
(^template [<tag>]
[{<tag> left right}
- {<tag> (recur left) (recur right)}])
+ {<tag> (again left) (again right)}])
([.#Sum] [.#Product] [.#Function] [.#Apply])
{.#Parameter index}
@@ -204,7 +204,7 @@
(^template [<tag>]
[{<tag> environment quantified}
- {<tag> (list#each recur environment) quantified}])
+ {<tag> (list#each again environment) quantified}])
([.#UnivQ] [.#ExQ])
_
@@ -254,13 +254,13 @@
(case currentT
{.#Named name unnamedT}
(do ///.monad
- [unnamedT+ (recur depth unnamedT)]
+ [unnamedT+ (again depth unnamedT)]
(in unnamedT+))
(^template [<tag>]
[{<tag> env bodyT}
(do ///.monad
- [bodyT+ (recur (++ depth) bodyT)]
+ [bodyT+ (again (++ depth) bodyT)]
(in {<tag> env bodyT+}))])
([.#UnivQ]
[.#ExQ])
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 e7a30e10f..854a977cf 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
@@ -57,7 +57,7 @@
{.#Item [_name [_source_type _source_ref]] mappings'}
(if (text#= name _name)
{.#Some [_source_type {variable.#Foreign idx}]}
- (recur (++ idx) mappings'))
+ (again (++ idx) mappings'))
{.#End}
{.#None})))
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 f8101daf3..ae20d2c6f 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
@@ -109,7 +109,7 @@
(def: .public (sum analyse lefts right? archive)
(-> Phase Nat Bit Phase)
(let [tag (/.tag lefts right?)]
- (function (recur valueC)
+ (function (again valueC)
(do [! ///.monad]
[expectedT (///extension.lifted meta.expected_type)
expectedT' (//type.with_env
@@ -130,7 +130,7 @@
{.#Named name unnamedT}
(//type.with_type unnamedT
- (recur valueC))
+ (again valueC))
{.#Var id}
(do !
@@ -139,7 +139,7 @@
(case ?expectedT'
{.#Some expectedT'}
(//type.with_type expectedT'
- (recur valueC))
+ (again valueC))
... Cannot do inference when the tag is numeric.
... This is because there is no way of knowing how many
@@ -152,7 +152,7 @@
(do !
[[instance_id instanceT] (//type.with_env <instancer>)]
(//type.with_type (maybe.trusted (type.applied (list instanceT) expectedT))
- (recur valueC)))])
+ (again valueC)))])
([.#UnivQ check.existential]
[.#ExQ check.var])
@@ -165,7 +165,7 @@
(case ?funT'
{.#Some funT'}
(//type.with_type {.#Apply inputT funT'}
- (recur valueC))
+ (again valueC))
_
(/.except ..invalid_variant_type [expectedT tag valueC])))
@@ -174,7 +174,7 @@
(case (type.applied (list inputT) funT)
{.#Some outputT}
(//type.with_type outputT
- (recur valueC))
+ (again valueC))
{.#None}
(/.except ..not_a_quantified_type funT)))
@@ -208,7 +208,7 @@
(do !
[memberA (//type.with_type memberT
(analyse archive memberC))
- memberA+ (recur membersT+' membersC+')]
+ memberA+ (again membersT+' membersC+')]
(in {.#Item memberA memberA+}))
_
@@ -314,7 +314,7 @@
(^ (list& [_ {.#Symbol slotH}] valueH tail))
(do ///.monad
[slotH (///extension.lifted (meta.normal slotH))]
- (recur tail {.#Item [slotH valueH] output}))
+ (again tail {.#Item [slotH valueH] output}))
{.#End}
(# ///.monad in {.#Some 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 918d1d504..d68fbd843 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
@@ -58,7 +58,7 @@
(def: .public (phase wrapper expander)
(-> //.Wrapper Expander Phase)
(let [analysis (//analysis.phase expander)]
- (function (recur archive code)
+ (function (again archive code)
(do [! //.monad]
[state //.get_state
.let [compiler_eval (meta_eval archive
@@ -71,7 +71,7 @@
_ (//.set_state (with@ [//extension.#state /.#analysis /.#state //extension.#state .#eval] extension_eval state))]
(case code
(^ [_ {.#Form (list& [_ {.#Text name}] inputs)}])
- (//extension.apply archive recur [name inputs])
+ (//extension.apply archive again [name inputs])
(^ [_ {.#Form (list& macro inputs)}])
(do !
@@ -95,12 +95,12 @@
(//.except ..invalid_macro_call code))))]
(case expansion
(^ (list& <lux_def_module> referrals))
- (|> (recur archive <lux_def_module>)
+ (|> (again archive <lux_def_module>)
(# ! each (revised@ /.#referrals (list#composite referrals))))
_
(|> expansion
- (monad.each ! (recur archive))
+ (monad.each ! (again archive))
(# ! each (list#mix /.merge_requirements /.no_requirements)))))
_
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 b067a6953..2b2290cb3 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
@@ -960,7 +960,7 @@
(list.only product.right)
(list#each product.left))
{.#Item [next_name nextT] _}
- (recur [next_name nextT])
+ (again [next_name nextT])
{.#End}
(in false)))))))))]
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 7f090639f..5e7ac077a 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
@@ -223,7 +223,7 @@
(////.failure (exception.error ..not_a_type [(symbol .Macro')]))
{.#Alias real_name}
- (recur real_name))))]
+ (again real_name))))]
(typeA.with_type input_type
(phase archive valueC))))]))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux
index 35b89e142..82192f954 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux
@@ -136,8 +136,8 @@
(^ (synthesis.loop/scope scope))
(//loop.scope! statement expression archive scope)
- (^ (synthesis.loop/recur updates))
- (//loop.recur! statement expression archive updates)
+ (^ (synthesis.loop/again updates))
+ (//loop.again! statement expression archive updates)
(^ (synthesis.function/abstraction abstraction))
(/////#each _.return (//function.function statement expression archive abstraction))
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 42809487f..7058b41c6 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
@@ -849,14 +849,14 @@
(def: (normalize_path normalize)
(-> (-> Synthesis Synthesis)
(-> Path Path))
- (function (recur path)
+ (function (again path)
(case path
(^ (//////synthesis.path/then bodyS))
(//////synthesis.path/then (normalize bodyS))
(^template [<tag>]
[(^ {<tag> leftP rightP})
- {<tag> (recur leftP) (recur rightP)}])
+ {<tag> (again leftP) (again rightP)}])
([//////synthesis.#Alt]
[//////synthesis.#Seq])
@@ -872,7 +872,7 @@
(def: (normalize_method_body mapping)
(-> (Dictionary Variable Variable) Synthesis Synthesis)
- (function (recur body)
+ (function (again body)
(case body
(^template [<tag>]
[(^ {<tag> value})
@@ -881,10 +881,10 @@
[//////synthesis.constant])
(^ (//////synthesis.variant [lefts right? sub]))
- (//////synthesis.variant [lefts right? (recur sub)])
+ (//////synthesis.variant [lefts right? (again sub)])
(^ (//////synthesis.tuple members))
- (//////synthesis.tuple (list#each recur members))
+ (//////synthesis.tuple (list#each again members))
(^ (//////synthesis.variable var))
(|> mapping
@@ -893,22 +893,22 @@
//////synthesis.variable)
(^ (//////synthesis.branch/case [inputS pathS]))
- (//////synthesis.branch/case [(recur inputS) (normalize_path recur pathS)])
+ (//////synthesis.branch/case [(again inputS) (normalize_path again pathS)])
(^ (//////synthesis.branch/let [inputS register outputS]))
- (//////synthesis.branch/let [(recur inputS) register (recur outputS)])
+ (//////synthesis.branch/let [(again inputS) register (again outputS)])
(^ (//////synthesis.branch/if [testS thenS elseS]))
- (//////synthesis.branch/if [(recur testS) (recur thenS) (recur elseS)])
+ (//////synthesis.branch/if [(again testS) (again thenS) (again elseS)])
(^ (//////synthesis.branch/get [path recordS]))
- (//////synthesis.branch/get [path (recur recordS)])
+ (//////synthesis.branch/get [path (again recordS)])
(^ (//////synthesis.loop/scope [offset initsS+ bodyS]))
- (//////synthesis.loop/scope [offset (list#each recur initsS+) (recur bodyS)])
+ (//////synthesis.loop/scope [offset (list#each again initsS+) (again bodyS)])
- (^ (//////synthesis.loop/recur updatesS+))
- (//////synthesis.loop/recur (list#each recur updatesS+))
+ (^ (//////synthesis.loop/again updatesS+))
+ (//////synthesis.loop/again (list#each again updatesS+))
(^ (//////synthesis.function/abstraction [environment arity bodyS]))
(//////synthesis.function/abstraction [(list#each (function (_ local)
@@ -926,10 +926,10 @@
bodyS])
(^ (//////synthesis.function/apply [functionS inputsS+]))
- (//////synthesis.function/apply [(recur functionS) (list#each recur inputsS+)])
+ (//////synthesis.function/apply [(again functionS) (list#each again inputsS+)])
{//////synthesis.#Extension [name inputsS+]}
- {//////synthesis.#Extension [name (list#each recur inputsS+)]})))
+ {//////synthesis.#Extension [name (list#each again inputsS+)]})))
(def: $Object
(type.class "java.lang.Object" (list)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
index 637ade6fb..cc11f4b4a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
@@ -98,8 +98,8 @@
[[inits scope!] (//loop.scope! statement expression archive false scope)]
(in scope!))
- (^ (synthesis.loop/recur updates))
- (//loop.recur! statement expression archive updates)
+ (^ (synthesis.loop/again updates))
+ (//loop.again! statement expression archive updates)
(^ (synthesis.function/abstraction abstraction))
(/////#each _.return (//function.function statement expression archive abstraction))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux
index 5f7cb433f..416d0ccb6 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux
@@ -79,7 +79,7 @@
([synthesis.branch/let //case.let!]
[synthesis.branch/if //case.if!]
[synthesis.loop/scope //loop.scope!]
- [synthesis.loop/recur //loop.recur!])
+ [synthesis.loop/again //loop.again!])
(^ (synthesis.function/abstraction abstraction))
(/////#each _.return (//function.function statement expression archive abstraction))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux
index 3be90b82c..3af83fe3e 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux
@@ -91,7 +91,7 @@
([synthesis.branch/let //case.let!]
[synthesis.branch/if //case.if!]
[synthesis.loop/scope //loop.scope!]
- [synthesis.loop/recur //loop.recur!])
+ [synthesis.loop/again //loop.again!])
(^ (synthesis.function/abstraction abstraction))
(/////#each _.return (//function.function statement expression archive abstraction))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp.lux
index 1f4312482..3fbab9bfc 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp.lux
@@ -49,7 +49,7 @@
[////synthesis.branch/case /case.case]
[////synthesis.loop/scope /loop.scope]
- [////synthesis.loop/recur /loop.recur]
+ [////synthesis.loop/again /loop.again]
[////synthesis.function/abstraction /function.function])
{////synthesis.#Extension extension}
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux
index 215ce0d05..48a1cc87a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux
@@ -138,7 +138,7 @@
(def: (pattern_matching' expression archive)
(Generator [Var/1 _.Tag _.Tag Path])
- (function (recur [$output @done @fail pathP])
+ (function (again [$output @done @fail pathP])
(.case pathP
(^ (/////synthesis.path/then bodyS))
(# ///////phase.monad each
@@ -155,10 +155,10 @@
{/////synthesis.#Bit_Fork when thenP elseP}
(do [! ///////phase.monad]
- [then! (recur [$output @done @fail thenP])
+ [then! (again [$output @done @fail thenP])
else! (.case elseP
{.#Some elseP}
- (recur [$output @done @fail elseP])
+ (again [$output @done @fail elseP])
{.#None}
(in (_.go @fail)))]
@@ -175,7 +175,7 @@
(do [! ///////phase.monad]
[clauses (monad.each ! (function (_ [match then])
(do !
- [then! (recur [$output @done @fail then])]
+ [then! (again [$output @done @fail then])]
(in [(<=> [(|> match <format>)
..peek])
then!])))
@@ -194,7 +194,7 @@
(^ (<simple> idx nextP))
(|> nextP
- [$output @done @fail] recur
+ [$output @done @fail] again
(# ///////phase.monad each (|>> {.#Some} (<choice> @fail true idx))))])
([/////synthesis.side/left /////synthesis.simple_left_side ..left_choice]
[/////synthesis.side/right /////synthesis.simple_right_side ..right_choice])
@@ -211,21 +211,21 @@
(^ (/////synthesis.!multi_pop nextP))
(.let [[extra_pops nextP'] (////synthesis/case.count_pops nextP)]
(do ///////phase.monad
- [next! (recur [$output @done @fail nextP'])]
+ [next! (again [$output @done @fail nextP'])]
(///////phase#in (_.progn (list (..multi_pop! (n.+ 2 extra_pops))
next!)))))
(^ (/////synthesis.path/alt preP postP))
(do [! ///////phase.monad]
[@otherwise (# ! each (|>> %.nat (format "lux_case_otherwise") _.tag) /////generation.next)
- pre! (recur [$output @done @otherwise preP])
- post! (recur [$output @done @fail postP])]
+ pre! (again [$output @done @otherwise preP])
+ post! (again [$output @done @fail postP])]
(in (..alternation @otherwise pre! post!)))
(^ (/////synthesis.path/seq preP postP))
(do ///////phase.monad
- [pre! (recur [$output @done @fail preP])
- post! (recur [$output @done @fail postP])]
+ [pre! (again [$output @done @fail preP])
+ post! (again [$output @done @fail postP])]
(in (_.progn (list pre! post!)))))))
(def: (pattern_matching $output expression archive pathP)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux
index 04b30cb45..454148842 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux
@@ -57,7 +57,7 @@
(_.setq @output bodyG)))
@output))))))
-(def: .public (recur expression archive argsS+)
+(def: .public (again expression archive argsS+)
(Generator (List Synthesis))
(do [! ///////phase.monad]
[[tag offset] /////generation.anchor
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js.lux
index 2acd26bd7..114149f64 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js.lux
@@ -67,7 +67,7 @@
(^ (synthesis.loop/scope scope))
(/loop.scope ///extension/common.statement expression archive scope)
- (^ (synthesis.loop/recur updates))
+ (^ (synthesis.loop/again updates))
(//////phase.except ..cannot_recur_as_an_expression [])
(^ (synthesis.function/abstraction abstraction))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux
index f23a1a152..700e95254 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux
@@ -158,14 +158,14 @@
..restore_cursor!
post!)))
-(def: (optimized_pattern_matching recur pathP)
+(def: (optimized_pattern_matching again pathP)
(-> (-> Path (Operation Statement))
(-> Path (Operation (Maybe Statement))))
(.case pathP
(^template [<simple> <choice>]
[(^ (<simple> idx nextP))
(|> nextP
- recur
+ again
(# ///////phase.monad each (|>> (_.then (<choice> true idx)) {.#Some})))])
([/////synthesis.simple_left_side ..left_choice]
[/////synthesis.simple_right_side ..right_choice])
@@ -178,7 +178,7 @@
(/////synthesis.member/left 0)
(/////synthesis.!bind_top register thenP)))
(do ///////phase.monad
- [then! (recur thenP)]
+ [then! (again thenP)]
(in {.#Some ($_ _.then
(_.define (..register register) (_.at (_.i32 +0) ..peek_cursor))
then!)}))
@@ -189,7 +189,7 @@
(<pm> lefts)
(/////synthesis.!bind_top register thenP)))
(do ///////phase.monad
- [then! (recur thenP)]
+ [then! (again thenP)]
(in {.#Some ($_ _.then
(_.define (..register register) (<getter> (_.i32 (.int lefts)) ..peek_cursor))
then!)}))])
@@ -198,7 +198,7 @@
(^ (/////synthesis.!bind_top register thenP))
(do ///////phase.monad
- [then! (recur thenP)]
+ [then! (again thenP)]
(in {.#Some ($_ _.then
(_.define (..register register) ..peek_and_pop_cursor)
then!)}))
@@ -206,7 +206,7 @@
(^ (/////synthesis.!multi_pop nextP))
(.let [[extra_pops nextP'] (////synthesis/case.count_pops nextP)]
(do ///////phase.monad
- [next! (recur nextP')]
+ [next! (again nextP')]
(in {.#Some ($_ _.then
(multi_pop_cursor! (n.+ 2 extra_pops))
next!)})))
@@ -217,9 +217,9 @@
(def: (pattern_matching' statement expression archive)
(-> Phase! Phase Archive
(-> Path (Operation Statement)))
- (function (recur pathP)
+ (function (again pathP)
(do ///////phase.monad
- [outcome (optimized_pattern_matching recur pathP)]
+ [outcome (optimized_pattern_matching again pathP)]
(.case outcome
{.#Some outcome}
(in outcome)
@@ -237,10 +237,10 @@
{/////synthesis.#Bit_Fork when thenP elseP}
(do [! ///////phase.monad]
- [then! (recur thenP)
+ [then! (again thenP)
else! (.case elseP
{.#Some elseP}
- (recur elseP)
+ (again elseP)
{.#None}
(in ..fail_pm!))]
@@ -256,7 +256,7 @@
(do [! ///////phase.monad]
[clauses (monad.each ! (function (_ [match then])
(do !
- [then! (recur then)]
+ [then! (again then)]
(in [(//runtime.i64//= (//primitive.i64 (.int match))
..peek_cursor)
then!])))
@@ -267,7 +267,7 @@
[{<tag> item}
(do [! ///////phase.monad]
[cases (monad.each ! (function (_ [match then])
- (# ! each (|>> [(list (<format> match))]) (recur then)))
+ (# ! each (|>> [(list (<format> match))]) (again then)))
{.#Item item})]
(in (_.switch ..peek_cursor
cases
@@ -290,8 +290,8 @@
(^template [<tag> <combinator>]
[(^ (<tag> leftP rightP))
(do ///////phase.monad
- [left! (recur leftP)
- right! (recur rightP)]
+ [left! (again leftP)
+ right! (again rightP)]
(in (<combinator> left! right!)))])
([/////synthesis.path/seq _.then]
[/////synthesis.path/alt ..alternation]))))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux
index 725f08062..8030faee5 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux
@@ -74,9 +74,9 @@
(in (_.apply/* (_.closure (list) loop!) (list))))))
(def: @temp
- (_.var "lux_recur_values"))
+ (_.var "lux_again_values"))
-(def: .public (recur! statement expression archive argsS+)
+(def: .public (again! statement expression archive argsS+)
(Generator! (List Synthesis))
(do [! ///////phase.monad]
[[offset @scope] /////generation.anchor
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm.lux
index c6fb592ea..4b40a2209 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm.lux
@@ -59,8 +59,8 @@
(^ (synthesis.loop/scope scope))
(/loop.scope generate archive scope)
- (^ (synthesis.loop/recur updates))
- (/loop.recur generate archive updates)
+ (^ (synthesis.loop/again updates))
+ (/loop.again generate archive updates)
(^ (synthesis.function/abstraction abstraction))
(/function.abstraction generate archive abstraction)
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 644287c38..30591c1d3 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
@@ -37,7 +37,7 @@
(def: no_op
(_#in []))
-(def: .public (recur translate archive updatesS)
+(def: .public (again translate archive updatesS)
(Generator (List Synthesis))
(do [! phase.monad]
[[@begin offset] generation.anchor
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux
index a6e053c61..1532e6252 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux
@@ -67,7 +67,7 @@
(^ (synthesis.loop/scope scope))
(/loop.scope ///extension/common.statement expression archive scope)
- (^ (synthesis.loop/recur updates))
+ (^ (synthesis.loop/again updates))
(//////phase.except ..cannot_recur_as_an_expression [])
(^ (synthesis.function/abstraction abstraction))
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 71ec87fe1..843393e72 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
@@ -161,7 +161,7 @@
(def: (pattern_matching' statement expression archive)
(-> Phase! Phase Archive Path (Operation Statement))
- (function (recur pathP)
+ (function (again pathP)
(.case pathP
{/////synthesis.#Then bodyS}
(statement expression archive bodyS)
@@ -174,10 +174,10 @@
{/////synthesis.#Bit_Fork when thenP elseP}
(do [! ///////phase.monad]
- [then! (recur thenP)
+ [then! (again thenP)
else! (.case elseP
{.#Some elseP}
- (recur elseP)
+ (again elseP)
{.#None}
(in ..fail!))]
@@ -194,7 +194,7 @@
(do [! ///////phase.monad]
[clauses (monad.each ! (function (_ [match then])
(do !
- [then! (recur then)]
+ [then! (again then)]
(in [(_.= (|> match <format>)
..peek)
then!])))
@@ -209,7 +209,7 @@
(///////phase#in (<choice> false idx))
(^ (<simple> idx nextP))
- (///////phase#each (_.then (<choice> true idx)) (recur nextP))])
+ (///////phase#each (_.then (<choice> true idx)) (again nextP))])
([/////synthesis.side/left /////synthesis.simple_left_side ..left_choice]
[/////synthesis.side/right /////synthesis.simple_right_side ..right_choice])
@@ -224,7 +224,7 @@
(^ (/////synthesis.!bind_top register thenP))
(do ///////phase.monad
- [then! (recur thenP)]
+ [then! (again thenP)]
(///////phase#in ($_ _.then
(_.local/1 (..register register) ..peek_and_pop)
then!)))
@@ -232,8 +232,8 @@
(^template [<tag> <combinator>]
[(^ (<tag> preP postP))
(do ///////phase.monad
- [pre! (recur preP)
- post! (recur postP)]
+ [pre! (again preP)
+ post! (again postP)]
(in (<combinator> pre! post!)))])
([/////synthesis.path/seq _.then]
[/////synthesis.path/alt ..alternation]))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux
index 8e62fd7c8..b5fddc44d 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux
@@ -111,7 +111,7 @@
_ (/////generation.save! artifact_id {.#None} directive)]
(in (|> instantiation (_.apply/* initsO+))))))
-(def: .public (recur! statement expression archive argsS+)
+(def: .public (again! statement expression archive argsS+)
(Generator! (List Synthesis))
(do [! ///////phase.monad]
[[offset @scope] /////generation.anchor
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux
index df16028a6..a70018d3e 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux
@@ -57,7 +57,7 @@
([////synthesis.branch/let /case.let!]
[////synthesis.branch/if /case.if!]
[////synthesis.loop/scope /loop.scope!]
- [////synthesis.loop/recur /loop.recur!])
+ [////synthesis.loop/again /loop.again!])
(^ (////synthesis.function/abstraction abstraction))
(//////phase#each _.return (/function.function statement expression archive abstraction))
@@ -96,7 +96,7 @@
[////synthesis.loop/scope /loop.scope]
[////synthesis.function/abstraction /function.function])
- (^ (////synthesis.loop/recur _))
+ (^ (////synthesis.loop/again _))
(//////phase.except ..cannot_recur_as_an_expression [])
{////synthesis.#Extension extension}
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 fcdccdb3b..3a6d52a57 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
@@ -161,7 +161,7 @@
(def: (pattern_matching' statement expression archive)
(Generator! Path)
- (function (recur pathP)
+ (function (again pathP)
(.case pathP
{/////synthesis.#Then bodyS}
(statement expression archive bodyS)
@@ -174,10 +174,10 @@
{/////synthesis.#Bit_Fork when thenP elseP}
(do [! ///////phase.monad]
- [then! (recur thenP)
+ [then! (again thenP)
else! (.case elseP
{.#Some elseP}
- (recur elseP)
+ (again elseP)
{.#None}
(in ..fail!))]
@@ -194,7 +194,7 @@
(do [! ///////phase.monad]
[clauses (monad.each ! (function (_ [match then])
(do !
- [then! (recur then)]
+ [then! (again then)]
(in [(_.=== (|> match <format>)
..peek)
then!])))
@@ -210,7 +210,7 @@
(^ (<simple> idx nextP))
(|> nextP
- recur
+ again
(# ///////phase.monad each (_.then (<choice> true idx))))])
([/////synthesis.side/left /////synthesis.simple_left_side ..left_choice]
[/////synthesis.side/right /////synthesis.simple_right_side ..right_choice])
@@ -226,7 +226,7 @@
(^ (/////synthesis.!bind_top register thenP))
(do ///////phase.monad
- [then! (recur thenP)]
+ [then! (again thenP)]
(///////phase#in ($_ _.then
(_.set! (..register register) ..peek_and_pop)
then!)))
@@ -234,7 +234,7 @@
... (^ (/////synthesis.!multi_pop nextP))
... (.let [[extra_pops nextP'] (////synthesis/case.count_pops nextP)]
... (do ///////phase.monad
- ... [next! (recur nextP')]
+ ... [next! (again nextP')]
... (///////phase#in ($_ _.then
... (..multi_pop! (n.+ 2 extra_pops))
... next!))))
@@ -242,8 +242,8 @@
(^template [<tag> <combinator>]
[(^ (<tag> preP postP))
(do ///////phase.monad
- [pre! (recur preP)
- post! (recur postP)]
+ [pre! (again preP)
+ post! (again postP)]
(in (<combinator> pre! post!)))])
([/////synthesis.path/seq _.then]
[/////synthesis.path/alt ..alternation]))))
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 709daa132..a3797ce16 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
@@ -105,9 +105,9 @@
(in (_.apply/* (list) instantiation)))))
(def: @temp
- (_.var "lux_recur_values"))
+ (_.var "lux_again_values"))
-(def: .public (recur! statement expression archive argsS+)
+(def: .public (again! statement expression archive argsS+)
(Generator! (List Synthesis))
(do [! ///////phase.monad]
[[offset @scope] /////generation.anchor
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux
index bb6ee4429..70219c160 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux
@@ -67,7 +67,7 @@
(^ (////synthesis.loop/scope scope))
(/loop.scope ///extension/common.statement expression archive scope)
- (^ (////synthesis.loop/recur updates))
+ (^ (////synthesis.loop/again updates))
(//////phase.except ..cannot_recur_as_an_expression [])
(^ (////synthesis.function/abstraction abstraction))
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 41f22d6e1..022d87a07 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
@@ -175,16 +175,16 @@
..restore!
post!))
-(def: (primitive_pattern_matching recur pathP)
+(def: (primitive_pattern_matching again pathP)
(-> (-> Path (Operation (Statement Any)))
(-> Path (Operation (Maybe (Statement Any)))))
(.case pathP
{/////synthesis.#Bit_Fork when thenP elseP}
(do [! ///////phase.monad]
- [then! (recur thenP)
+ [then! (again thenP)
else! (.case elseP
{.#Some elseP}
- (recur elseP)
+ (again elseP)
{.#None}
(in ..fail_pm!))]
@@ -203,7 +203,7 @@
(# ! each
(|>> [(_.= (|> match <format>)
..peek)])
- (recur then)))
+ (again then)))
{.#Item item})]
(in {.#Some (_.cond clauses
..fail_pm!)}))])
@@ -216,9 +216,9 @@
(def: (pattern_matching' in_closure? statement expression archive)
(-> Bit Phase! Phase Archive Path (Operation (Statement Any)))
- (function (recur pathP)
+ (function (again pathP)
(do [! ///////phase.monad]
- [?output (primitive_pattern_matching recur pathP)]
+ [?output (primitive_pattern_matching again pathP)]
(.case ?output
{.#Some output}
(in output)
@@ -240,7 +240,7 @@
(^ (<simple> idx nextP))
(|> nextP
- recur
+ again
(///////phase#each (_.then (<choice> true idx))))])
([/////synthesis.side/left /////synthesis.simple_left_side ..left_choice]
[/////synthesis.side/right /////synthesis.simple_right_side ..right_choice])
@@ -256,7 +256,7 @@
(^ (/////synthesis.!bind_top register thenP))
(do !
- [then! (recur thenP)]
+ [then! (again thenP)]
(///////phase#in ($_ _.then
(_.set (list (..register register)) ..peek_and_pop)
then!)))
@@ -264,21 +264,21 @@
(^ (/////synthesis.!multi_pop nextP))
(.let [[extra_pops nextP'] (case.count_pops nextP)]
(do !
- [next! (recur nextP')]
+ [next! (again nextP')]
(///////phase#in ($_ _.then
(..multi_pop! (n.+ 2 extra_pops))
next!))))
(^ (/////synthesis.path/seq preP postP))
(do !
- [pre! (recur preP)
- post! (recur postP)]
+ [pre! (again preP)
+ post! (again postP)]
(in (_.then pre! post!)))
(^ (/////synthesis.path/alt preP postP))
(do !
- [pre! (recur preP)
- post! (recur postP)
+ [pre! (again preP)
+ post! (again postP)
g!once (..symbol "once")]
(in (..alternation in_closure? g!once pre! post!)))
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 5579c4d48..85ccf3818 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
@@ -106,11 +106,11 @@
_ (/////generation.save! loop_artifact {.#None} directive)]
(in (_.apply/* instantiation initsO+)))))
-(def: .public (recur! statement expression archive argsS+)
+(def: .public (again! statement expression archive argsS+)
(Generator! (List Synthesis))
(do [! ///////phase.monad]
[offset /////generation.anchor
- @temp (//case.symbol "lux_recur_values")
+ @temp (//case.symbol "lux_again_values")
argsO+ (monad.each ! (expression archive) argsS+)
.let [re_binds (|> argsO+
list.enumeration
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r.lux
index 24933ea51..ec7cbaab9 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r.lux
@@ -51,7 +51,7 @@
[////synthesis.branch/case /case.case]
[////synthesis.loop/scope /loop.scope]
- [////synthesis.loop/recur /loop.recur]
+ [////synthesis.loop/again /loop.again]
[////synthesis.function/abstraction /function.function])
{////synthesis.#Extension extension}
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 265b1fd46..fdebb120c 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
@@ -133,7 +133,7 @@
(def: (pattern_matching' expression archive)
(Generator Path)
- (function (recur pathP)
+ (function (again pathP)
(.case pathP
{/////synthesis.#Then bodyS}
(expression archive bodyS)
@@ -146,10 +146,10 @@
{/////synthesis.#Bit_Fork when thenP elseP}
(do [! ///////phase.monad]
- [then! (recur thenP)
+ [then! (again thenP)
else! (.case elseP
{.#Some elseP}
- (recur elseP)
+ (again elseP)
{.#None}
(in ..fail!))]
@@ -166,7 +166,7 @@
(do [! ///////phase.monad]
[clauses (monad.each ! (function (_ [match then])
(do !
- [then! (recur then)]
+ [then! (again then)]
(in [(<=> (|> match <format>)
..peek)
then!])))
@@ -200,16 +200,16 @@
(^ (/////synthesis.path/seq leftP rightP))
(do ///////phase.monad
- [leftO (recur leftP)
- rightO (recur rightP)]
+ [leftO (again leftP)
+ rightO (again rightP)]
(in ($_ _.then
leftO
rightO)))
(^ (/////synthesis.path/alt leftP rightP))
(do [! ///////phase.monad]
- [leftO (recur leftP)
- rightO (recur rightP)]
+ [leftO (again leftP)
+ rightO (again rightP)]
(in (_.try ($_ _.then
..save_cursor!
leftO)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux
index 3e7bcf927..1971d79eb 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux
@@ -57,7 +57,7 @@
bodyO))
(_.apply initsO+ $scope)))))))
-(def: .public (recur expression archive argsS+)
+(def: .public (again expression archive argsS+)
(Generator (List Synthesis))
(do [! ///////phase.monad]
[$scope /////generation.anchor
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux
index f45c9c04d..a87c13d2e 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux
@@ -133,11 +133,11 @@
(&.throw Wrong_Syntax (wrong_syntax proc_name inputsS)))
)))
-(def: lux//recur
+(def: lux//again
(-> Text Proc)
(function (_ proc_name)
(function (_ translate inputsS)
- (loopT.translate_recur translate inputsS))))
+ (loopT.translate_again translate inputsS))))
(def: lux_procs
Bundle
@@ -146,7 +146,7 @@
(install "try" (unary lux//try))
(install "if" (trinary lux//if))
(install "loop" lux//loop)
- (install "recur" lux//recur)
+ (install "again" lux//again)
))
... [[Bits]]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux
index e249ece33..5efc84ab5 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux
@@ -62,7 +62,7 @@
[////synthesis.loop/scope /loop.scope]
[////synthesis.function/abstraction /function.function])
- (^ (////synthesis.loop/recur _))
+ (^ (////synthesis.loop/again _))
(//////phase.except ..cannot_recur_as_an_expression [])
{////synthesis.#Reference value}
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 d6f4d2a2b..574e49b80 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
@@ -184,16 +184,16 @@
..restore!
post!))
-(def: (primitive_pattern_matching recur pathP)
+(def: (primitive_pattern_matching again pathP)
(-> (-> Path (Operation Statement))
(-> Path (Operation (Maybe Statement))))
(.case pathP
{/////synthesis.#Bit_Fork when thenP elseP}
(do [! ///////phase.monad]
- [then! (recur thenP)
+ [then! (again thenP)
else! (.case elseP
{.#Some elseP}
- (recur elseP)
+ (again elseP)
{.#None}
(in ..fail!))]
@@ -212,7 +212,7 @@
(# ! each
(|>> [(_.= (|> match <format>)
..peek)])
- (recur then)))
+ (again then)))
{.#Item item})]
(in {.#Some (_.cond clauses
..fail!)}))])
@@ -225,9 +225,9 @@
(def: (pattern_matching' in_closure? statement expression archive)
(-> Bit (Generator! Path))
- (function (recur pathP)
+ (function (again pathP)
(do ///////phase.monad
- [?output (primitive_pattern_matching recur pathP)]
+ [?output (primitive_pattern_matching again pathP)]
(.case ?output
{.#Some output}
(in output)
@@ -245,10 +245,10 @@
{/////synthesis.#Bit_Fork when thenP elseP}
(do [! ///////phase.monad]
- [then! (recur thenP)
+ [then! (again thenP)
else! (.case elseP
{.#Some elseP}
- (recur elseP)
+ (again elseP)
{.#None}
(in ..fail!))]
@@ -267,7 +267,7 @@
(# ! each
(|>> [(_.= (|> match <format>)
..peek)])
- (recur then)))
+ (again then)))
{.#Item item})]
(in (_.cond clauses
..fail!)))])
@@ -281,7 +281,7 @@
(^ (<simple> idx nextP))
(|> nextP
- recur
+ again
(///////phase#each (_.then (<choice> true idx))))])
([/////synthesis.side/left /////synthesis.simple_left_side ..left_choice]
[/////synthesis.side/right /////synthesis.simple_right_side ..right_choice])
@@ -297,7 +297,7 @@
(^ (/////synthesis.!bind_top register thenP))
(do ///////phase.monad
- [then! (recur thenP)]
+ [then! (again thenP)]
(///////phase#in ($_ _.then
(_.set (list (..register register)) ..peek_and_pop)
then!)))
@@ -305,23 +305,23 @@
(^ (/////synthesis.!multi_pop nextP))
(.let [[extra_pops nextP'] (case.count_pops nextP)]
(do ///////phase.monad
- [next! (recur nextP')]
+ [next! (again nextP')]
(///////phase#in ($_ _.then
(..multi_pop! (n.+ 2 extra_pops))
next!))))
(^ (/////synthesis.path/seq preP postP))
(do ///////phase.monad
- [pre! (recur preP)
- post! (recur postP)]
+ [pre! (again preP)
+ post! (again postP)]
(in ($_ _.then
pre!
post!)))
(^ (/////synthesis.path/alt preP postP))
(do ///////phase.monad
- [pre! (recur preP)
- post! (recur postP)
+ [pre! (again preP)
+ post! (again postP)
g!once (..symbol "once")
g!continue? (..symbol "continue")]
(in (..alternation in_closure? g!once g!continue? pre! post!))))))))
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 9ff64de7f..479eb50e6 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
@@ -80,11 +80,11 @@
(_.lambda {.#None} (list))
(_.apply_lambda/* (list)))))))
-(def: .public (recur! statement expression archive argsS+)
+(def: .public (again! statement expression archive argsS+)
(Generator! (List Synthesis))
(do [! ///////phase.monad]
[offset /////generation.anchor
- @temp (//case.symbol "lux_recur_values")
+ @temp (//case.symbol "lux_again_values")
argsO+ (monad.each ! (expression archive) argsS+)
.let [re_binds (|> argsO+
list.enumeration
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme.lux
index 12a559202..6fb424be4 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme.lux
@@ -51,7 +51,7 @@
[////synthesis.branch/case /case.case]
[////synthesis.loop/scope /loop.scope]
- [////synthesis.loop/recur /loop.recur]
+ [////synthesis.loop/again /loop.again]
[////synthesis.function/abstraction /function.function])
{////synthesis.#Extension extension}
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux
index 176b4e5dd..8367ac43b 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux
@@ -127,7 +127,7 @@
(def: (pattern_matching' expression archive)
(Generator Path)
- (function (recur pathP)
+ (function (again pathP)
(.case pathP
{/////synthesis.#Then bodyS}
(expression archive bodyS)
@@ -140,10 +140,10 @@
{/////synthesis.#Bit_Fork when thenP elseP}
(do [! ///////phase.monad]
- [then! (recur thenP)
+ [then! (again thenP)
else! (.case elseP
{.#Some elseP}
- (recur elseP)
+ (again elseP)
{.#None}
(in ..fail!))]
@@ -160,7 +160,7 @@
(do [! ///////phase.monad]
[clauses (monad.each ! (function (_ [match then])
(do !
- [then! (recur then)]
+ [then! (again then)]
(in [(<=> (|> match <format>)
..peek)
then!])))
@@ -193,15 +193,15 @@
(^ (/////synthesis.path/seq leftP rightP))
(do ///////phase.monad
- [leftO (recur leftP)
- rightO (recur rightP)]
+ [leftO (again leftP)
+ rightO (again rightP)]
(in (_.begin (list leftO
rightO))))
(^ (/////synthesis.path/alt leftP rightP))
(do [! ///////phase.monad]
- [leftO (recur leftP)
- rightO (recur rightP)]
+ [leftO (again leftP)
+ rightO (again rightP)]
(in (try_pm (_.begin (list restore_cursor!
rightO))
(_.begin (list save_cursor!
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux
index 1fef5ee57..08e8e1eb0 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux
@@ -56,7 +56,7 @@
bodyO)])
(_.apply/* initsO+ @scope))))))
-(def: .public (recur expression archive argsS+)
+(def: .public (again expression archive argsS+)
(Generator (List Synthesis))
(do [! ///////phase.monad]
[@scope /////generation.anchor
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 2c2d1784b..b3ecf225e 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
@@ -193,7 +193,7 @@
(loop [lefts 0
patterns patterns]
(with_expansions [<failure> (as_is (list))
- <continue> (as_is (recur (++ lefts)
+ <continue> (as_is (again (++ lefts)
tail))
<member> (as_is (if (list.empty? tail)
{.#Right (-- lefts)}
@@ -421,7 +421,7 @@
(value@ #dependencies)))
(list#mix for_synthesis synthesis_storage initsS+))
- (^ (/.loop/recur replacementsS+))
+ (^ (/.loop/again replacementsS+))
(list#mix for_synthesis synthesis_storage replacementsS+)
{/.#Extension [extension argsS]}
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 7dfef8a48..721669f39 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
@@ -205,10 +205,10 @@
iterationS' (grow environment iterationS)]
(in (/.loop/scope [(++ start) initsS+' iterationS'])))
- {/.#Recur argumentsS+}
+ {/.#Again argumentsS+}
(|> argumentsS+
(monad.each phase.monad (grow environment))
- (phase#each (|>> /.loop/recur))))
+ (phase#each (|>> /.loop/again))))
{/.#Function function}
(case function
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 ff6818b83..8bbe32ad4 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
@@ -28,7 +28,7 @@
(def: (path_optimization body_optimization offset)
(-> (Transform Synthesis) Register (Transform Path))
- (function (recur path)
+ (function (again path)
(case path
{/.#Bind register}
{.#Some {/.#Bind (register_optimization offset register)}}
@@ -36,17 +36,17 @@
(^template [<tag>]
[{<tag> left right}
(do maybe.monad
- [left' (recur left)
- right' (recur right)]
+ [left' (again left)
+ right' (again right)]
(in {<tag> left' right'}))])
([/.#Alt] [/.#Seq])
{/.#Bit_Fork when then else}
(do [! maybe.monad]
- [then (recur then)
+ [then (again then)
else (case else
{.#Some else}
- (# ! each (|>> {.#Some}) (recur else))
+ (# ! each (|>> {.#Some}) (again else))
{.#None}
(in {.#None}))]
@@ -55,10 +55,10 @@
(^template [<tag>]
[{<tag> [[test then] elses]}
(do [! maybe.monad]
- [then (recur then)
+ [then (again then)
elses (monad.each ! (function (_ [else_test else_then])
(do !
- [else_then (recur else_then)]
+ [else_then (again else_then)]
(in [else_test else_then])))
elses)]
(in {<tag> [[test then] elses]}))])
@@ -86,14 +86,14 @@
(case structure
{analysis.#Variant variant}
(do maybe.monad
- [value' (|> variant (value@ analysis.#value) (recur false))]
+ [value' (|> variant (value@ analysis.#value) (again false))]
(in (|> variant
(with@ analysis.#value value')
/.variant)))
{analysis.#Tuple tuple}
(|> tuple
- (monad.each maybe.monad (recur false))
+ (monad.each maybe.monad (again false))
(maybe#each (|>> /.tuple))))
{/.#Reference reference}
@@ -116,59 +116,59 @@
(^ (/.branch/case [input path]))
(do maybe.monad
- [input' (recur false input)
- path' (path_optimization (recur return?) offset path)]
+ [input' (again false input)
+ path' (path_optimization (again return?) offset path)]
(in (|> path' [input'] /.branch/case)))
(^ (/.branch/let [input register body]))
(do maybe.monad
- [input' (recur false input)
- body' (recur return? body)]
+ [input' (again false input)
+ body' (again return? body)]
(in (/.branch/let [input' (register_optimization offset register) body'])))
(^ (/.branch/if [input then else]))
(do maybe.monad
- [input' (recur false input)
- then' (recur return? then)
- else' (recur return? else)]
+ [input' (again false input)
+ then' (again return? then)
+ else' (again return? else)]
(in (/.branch/if [input' then' else'])))
(^ (/.branch/get [path record]))
(do maybe.monad
- [record (recur false record)]
+ [record (again false record)]
(in (/.branch/get [path record])))
(^ (/.loop/scope scope))
(do [! maybe.monad]
[inits' (|> scope
(value@ /.#inits)
- (monad.each ! (recur false)))
- iteration' (recur return? (value@ /.#iteration scope))]
+ (monad.each ! (again false)))
+ iteration' (again return? (value@ /.#iteration scope))]
(in (/.loop/scope [/.#start (|> scope (value@ /.#start) (register_optimization offset))
/.#inits inits'
/.#iteration iteration'])))
- (^ (/.loop/recur args))
+ (^ (/.loop/again args))
(|> args
- (monad.each maybe.monad (recur false))
- (maybe#each (|>> /.loop/recur)))
+ (monad.each maybe.monad (again false))
+ (maybe#each (|>> /.loop/again)))
(^ (/.function/abstraction [environment arity body]))
(do [! maybe.monad]
- [environment' (monad.each ! (recur false) environment)]
+ [environment' (monad.each ! (again false) environment)]
(in (/.function/abstraction [environment' arity body])))
(^ (/.function/apply [abstraction arguments]))
(do [! maybe.monad]
- [arguments' (monad.each ! (recur false) arguments)]
+ [arguments' (monad.each ! (again false) arguments)]
(with_expansions [<application> (as_is (do !
- [abstraction' (recur false abstraction)]
+ [abstraction' (again false abstraction)]
(in (/.function/apply [abstraction' arguments']))))]
(case abstraction
(^ {/.#Reference {reference.#Variable (variable.self)}})
(if (and return?
(n.= arity (list.size arguments)))
- (in (/.loop/recur arguments'))
+ (in (/.loop/again arguments'))
(if true_loop?
{.#None}
<application>))
@@ -180,26 +180,26 @@
(^ {/.#Extension ["lux syntax char case!" (list& input else matches)]})
(if return?
(do [! maybe.monad]
- [input (recur false input)
+ [input (again false input)
matches (monad.each !
(function (_ match)
(case match
(^ {/.#Structure {analysis.#Tuple (list when then)}})
(do !
- [when (recur false when)
- then (recur return? then)]
+ [when (again false when)
+ then (again return? then)]
(in {/.#Structure {analysis.#Tuple (list when then)}}))
_
- (recur false match)))
+ (again false match)))
matches)
- else (recur return? else)]
+ else (again return? else)]
(in {/.#Extension ["lux syntax char case!" (list& input else matches)]}))
{.#None})
{/.#Extension [name args]}
(|> args
- (monad.each maybe.monad (recur false))
+ (monad.each maybe.monad (again false))
(maybe#each (|>> [name] {/.#Extension}))))))
(def: .public (optimization true_loop? offset inits functionS)
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 b423da2a7..91253b66b 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
@@ -37,16 +37,16 @@
(def: (remove_local_from_path remove_local redundant)
(-> (Remover Synthesis) (Remover Path))
- (function (recur path)
+ (function (again path)
(case path
{/.#Seq {/.#Bind register}
post}
(if (n.= redundant register)
- (recur post)
+ (again post)
{/.#Seq {/.#Bind (if (n.> redundant register)
(-- register)
register)}
- (recur post)})
+ (again post)})
(^or {/.#Seq {/.#Access {/.#Member member}}
{/.#Seq {/.#Bind register}
@@ -57,27 +57,27 @@
{/.#Bind register}}
post})
(if (n.= redundant register)
- (recur post)
+ (again post)
{/.#Seq {/.#Access {/.#Member member}}
{/.#Seq {/.#Bind (if (n.> redundant register)
(-- register)
register)}
- (recur post)}})
+ (again post)}})
(^template [<tag>]
[{<tag> left right}
- {<tag> (recur left) (recur right)}])
+ {<tag> (again left) (again right)}])
([/.#Seq]
[/.#Alt])
{/.#Bit_Fork when then else}
- {/.#Bit_Fork when (recur then) (maybe#each recur else)}
+ {/.#Bit_Fork when (again then) (maybe#each again else)}
(^template [<tag>]
[{<tag> [[test then] tail]}
- {<tag> [[test (recur then)]
+ {<tag> [[test (again then)]
(list#each (function (_ [test' then'])
- [test' (recur then')])
+ [test' (again then')])
tail)]}])
([/.#I64_Fork]
[/.#F64_Fork]
@@ -105,7 +105,7 @@
(def: (remove_local redundant)
(Remover Synthesis)
- (function (recur synthesis)
+ (function (again synthesis)
(case synthesis
{/.#Primitive _}
synthesis
@@ -113,10 +113,10 @@
{/.#Structure structure}
{/.#Structure (case structure
{analysis.#Variant [lefts right value]}
- {analysis.#Variant [lefts right (recur value)]}
+ {analysis.#Variant [lefts right (again value)]}
{analysis.#Tuple tuple}
- {analysis.#Tuple (list#each recur tuple)})}
+ {analysis.#Tuple (list#each again tuple)})}
{/.#Reference reference}
(case reference
@@ -131,41 +131,41 @@
{/.#Branch branch}
{/.#Branch (case branch
{/.#Let input register output}
- {/.#Let (recur input)
+ {/.#Let (again input)
(..prune redundant register)
- (recur output)}
+ (again output)}
{/.#If test then else}
- {/.#If (recur test) (recur then) (recur else)}
+ {/.#If (again test) (again then) (again else)}
{/.#Get path record}
- {/.#Get path (recur record)}
+ {/.#Get path (again record)}
{/.#Case input path}
- {/.#Case (recur input) (remove_local_from_path remove_local redundant path)})}
+ {/.#Case (again input) (remove_local_from_path remove_local redundant path)})}
{/.#Loop loop}
{/.#Loop (case loop
{/.#Scope [start inits iteration]}
{/.#Scope [(..prune redundant start)
- (list#each recur inits)
- (recur iteration)]}
+ (list#each again inits)
+ (again iteration)]}
- {/.#Recur resets}
- {/.#Recur (list#each recur resets)})}
+ {/.#Again resets}
+ {/.#Again (list#each again resets)})}
{/.#Function function}
{/.#Function (case function
{/.#Abstraction [environment arity body]}
- {/.#Abstraction [(list#each recur environment)
+ {/.#Abstraction [(list#each again environment)
arity
body]}
{/.#Apply abstraction inputs}
- {/.#Apply (recur abstraction) (list#each recur inputs)})})}
+ {/.#Apply (again abstraction) (list#each again inputs)})})}
{/.#Extension name inputs}
- {/.#Extension name (list#each recur inputs)})))
+ {/.#Extension name (list#each again inputs)})))
(type: Redundancy
(Dictionary Register Bit))
@@ -195,7 +195,7 @@
(def: (list_optimization optimization)
(All (_ a) (-> (Optimization a) (Optimization (List a))))
- (function (recur [redundancy values])
+ (function (again [redundancy values])
(case values
{.#End}
{try.#Success [redundancy
@@ -204,7 +204,7 @@
{.#Item head tail}
(do try.monad
[[redundancy head] (optimization [redundancy head])
- [redundancy tail] (recur [redundancy tail])]
+ [redundancy tail] (again [redundancy tail])]
(in [redundancy
{.#Item head tail}])))))
@@ -245,7 +245,7 @@
(def: (path_optimization optimization)
(-> (Optimization Synthesis) (Optimization Path))
- (function (recur [redundancy path])
+ (function (again [redundancy path])
(case path
(^or {/.#Pop}
{/.#Access _})
@@ -254,13 +254,13 @@
{/.#Bit_Fork when then else}
(do [! try.monad]
- [[redundancy then] (recur [redundancy then])
+ [[redundancy then] (again [redundancy then])
[redundancy else] (case else
{.#Some else}
(# ! each
(function (_ [redundancy else])
[redundancy {.#Some else}])
- (recur [redundancy else]))
+ (again [redundancy else]))
{.#None}
(in [redundancy {.#None}]))]
@@ -269,11 +269,11 @@
(^template [<tag> <type>]
[{<tag> [[test then] elses]}
(do [! try.monad]
- [[redundancy then] (recur [redundancy then])
+ [[redundancy then] (again [redundancy then])
[redundancy elses] (..list_optimization (: (Optimization [<type> Path])
(function (_ [redundancy [else_test else_then]])
(do !
- [[redundancy else_then] (recur [redundancy else_then])]
+ [[redundancy else_then] (again [redundancy else_then])]
(in [redundancy [else_test else_then]]))))
[redundancy elses])]
(in [redundancy {<tag> [[test then] elses]}]))])
@@ -289,8 +289,8 @@
{/.#Alt left right}
(do try.monad
- [[redundancy left] (recur [redundancy left])
- [redundancy right] (recur [redundancy right])]
+ [[redundancy left] (again [redundancy left])
+ [redundancy right] (again [redundancy right])]
(in [redundancy {/.#Alt left right}]))
{/.#Seq pre post}
@@ -298,12 +298,12 @@
[.let [baseline (|> redundancy
dictionary.keys
(set.of_list n.hash))]
- [redundancy pre] (recur [redundancy pre])
+ [redundancy pre] (again [redundancy pre])
.let [bindings (|> redundancy
dictionary.keys
(set.of_list n.hash)
(set.difference baseline))]
- [redundancy post] (recur [redundancy post])
+ [redundancy post] (again [redundancy post])
.let [redundants (|> redundancy
dictionary.entries
(list.only (function (_ [register redundant?])
@@ -408,11 +408,11 @@
(in [(list#mix dictionary.lacks redundancy extension)
{/.#Control {/.#Loop {/.#Scope [start inits iteration]}}}]))
- {/.#Recur resets}
+ {/.#Again resets}
(do try.monad
[[redundancy resets] (..list_optimization optimization' [redundancy resets])]
(in [redundancy
- {/.#Control {/.#Loop {/.#Recur resets}}}])))
+ {/.#Control {/.#Loop {/.#Again resets}}}])))
{/.#Function function}
(case function
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 5be0c68f9..874789201 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux
@@ -228,7 +228,7 @@
stack (: (List Code) {.#End})]
(case (parse source)
{.#Right [source' top]}
- (recur source' {.#Item top stack})
+ (again source' {.#Item top stack})
{.#Left [source' error]}
(if (same? <close> error)
@@ -252,7 +252,7 @@
(case (parse source)
{.#Right [sourceF field]}
(!letE [sourceFV value] (parse sourceF)
- (recur sourceFV {.#Item [field value] stack}))
+ (again sourceFV {.#Item [field value] stack}))
{.#Left [source' error]}
(if (same? ..close_variant error)
@@ -368,7 +368,7 @@
exponent (static ..no_exponent)]
(<| (!with_char+ source_code//size source_code end char/0 <frac_output>)
(!if_digit?+ char/0
- (recur (!++ end) exponent)
+ (again (!++ end) exponent)
[["e" "E"]
(if (same? (static ..no_exponent) exponent)
@@ -377,7 +377,7 @@
[[<signs>]
(<| (!with_char+ source_code//size source_code (!n/+ 2 end) char/2 <failure>)
(!if_digit?+ char/2
- (recur (!n/+ 3 end) char/0)
+ (again (!n/+ 3 end) char/0)
[]
<failure>))]
... else
@@ -392,7 +392,7 @@
(loop [end offset]
(<| (!with_char+ source_code//size source_code end char <int_output>)
(!if_digit?+ char
- (recur (!++ end))
+ (again (!++ end))
[[<frac_separator>]
(frac_parser source_code//size start where (!++ end) source_code)]
@@ -407,7 +407,7 @@
(loop [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
- (recur (!++ g!end))
+ (again (!++ g!end))
[]
(!number_output source_code start g!end <codec> <tag>)))))]
@@ -433,7 +433,7 @@
(loop [end offset]
(<| (!with_char+ source_code//size source_code end char <output>)
(!if_symbol_char?|tail char
- (recur (!++ end))
+ (again (!++ end))
<output>))))))
(template: (!half_symbol_parser @offset @char @module)
@@ -488,7 +488,7 @@
(with_expansions [<consume_1> (as_is where (!++ offset/0) source_code)
<move_1> (as_is [(!forward 1 where) (!++ offset/0) source_code])
<move_2> (as_is [(!forward 1 where) (!++/2 offset/0) source_code])
- <recur> (as_is (parse current_module aliases source_code//size))]
+ <again> (as_is (parse current_module aliases source_code//size))]
(template: (!close closer)
[{.#Left [<move_1> closer]}])
@@ -506,12 +506,12 @@
... This is to preserve the loop as much as possible and keep it tight.
(exec
[]
- (function (recur [where offset/0 source_code])
+ (function (again [where offset/0 source_code])
(<| (!with_char+ source_code//size source_code offset/0 char/0
(!end_of_file where offset/0 source_code current_module))
(with_expansions [<composites> (template [<open> <close> <parser>]
[[(~~ (static <open>))]
- (<parser> <recur> <consume_1>)
+ (<parser> <again> <consume_1>)
[(~~ (static <close>))]
(!close <close>)]
@@ -523,11 +523,11 @@
(`` ("lux syntax char case!" char/0
[[(~~ (static text.space))
(~~ (static text.carriage_return))]
- (recur (!horizontal where offset/0 source_code))
+ (again (!horizontal where offset/0 source_code))
... New line
[(~~ (static text.new_line))]
- (recur (!vertical where offset/0 source_code))
+ (again (!vertical where offset/0 source_code))
<composites>
@@ -544,7 +544,7 @@
<short_symbol_parser> (!short_symbol_parser source_code//size current_module [where offset/1 source_code] where .#Symbol)
<comment_parser> (case ("lux text index" (!++ offset/1) (static text.new_line) source_code)
{.#Some end}
- (recur (!vertical where end source_code))
+ (again (!vertical where end source_code))
_
(!end_of_file where offset/1 source_code current_module))]
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 55333ca42..188cc541f 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux
@@ -113,7 +113,7 @@
(type: .public (Loop s)
(Variant
{#Scope (Scope s)}
- {#Recur (List s)}))
+ {#Again (List s)}))
(type: .public (Function s)
(Variant
@@ -265,7 +265,7 @@
[branch/if ..#Branch ..#If]
[branch/get ..#Branch ..#Get]
- [loop/recur ..#Loop ..#Recur]
+ [loop/again ..#Loop ..#Again]
[loop/scope ..#Loop ..#Scope]
[function/abstraction ..#Function ..#Abstraction]
@@ -412,11 +412,11 @@
" " (%synthesis (value@ #iteration scope)))
(text.enclosed ["{#loop " "}"]))
- {#Recur args}
+ {#Again args}
(|> args
(list#each %synthesis)
(text.interposed " ")
- (text.enclosed ["{#recur " "}"]))))
+ (text.enclosed ["{#again " "}"]))))
{#Extension [name args]}
(|> (list#each %synthesis args)
@@ -578,8 +578,8 @@
(^template [<factor> <tag>]
[{<tag> fork}
- (let [recur_hash (path'_hash super)
- fork_hash (product.hash recur_hash recur_hash)]
+ (let [again_hash (path'_hash super)
+ fork_hash (product.hash again_hash again_hash)]
(n.* <factor> (# fork_hash hash fork)))])
([19 #Alt]
[23 #Seq])
@@ -660,7 +660,7 @@
(# (list.equivalence #=) = reference_inits sample_inits)
(#= reference_iteration sample_iteration))
- [{#Recur reference} {#Recur sample}]
+ [{#Again reference} {#Again sample}]
(# (list.equivalence #=) = reference sample)
_
@@ -680,7 +680,7 @@
(# (list.hash super) hash inits)
(# super hash iteration))
- {#Recur resets}
+ {#Again resets}
($_ n.* 3
(# (list.hash super) hash resets))
)))
@@ -782,16 +782,16 @@
(def: &equivalence ..equivalence)
(def: (hash value)
- (let [recur_hash [..equivalence hash]]
+ (let [again_hash [..equivalence hash]]
(case value
(^template [<tag> <hash>]
[{<tag> value}
(# <hash> hash value)])
([#Primitive ..primitive_hash]
- [#Structure (analysis.composite_hash recur_hash)]
+ [#Structure (analysis.composite_hash again_hash)]
[#Reference reference.hash]
- [#Control (..control_hash recur_hash)]
- [#Extension (extension.hash recur_hash)])))))
+ [#Control (..control_hash again_hash)]
+ [#Extension (extension.hash again_hash)])))))
(template: .public (!bind_top register thenP)
[($_ ..path/seq
diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux
index 953b23605..7e6c0e1f1 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux
@@ -54,7 +54,7 @@
(def: (ancestry archive)
(-> Archive Graph)
(let [memo (: (Memo Module Ancestry)
- (function (_ recur module)
+ (function (_ again module)
(do [! state.monad]
[.let [parents (case (archive.find module archive)
{try.#Success [descriptor document]}
@@ -62,7 +62,7 @@
{try.#Failure error}
..fresh)]
- ancestors (monad.each ! recur (set.list parents))]
+ ancestors (monad.each ! again (set.list parents))]
(in (list#mix set.union parents ancestors)))))
ancestry (memo.open memo)]
(list#mix (function (_ module memory)
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 5328ecf74..c2b649fd1 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
@@ -313,7 +313,7 @@
directives]
output]))))
{try.#Success [definitions' bundles' output']}
- (recur input' definitions' bundles' output')
+ (again input' definitions' bundles' output')
failure
failure)
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 0e8c265c7..24cdea54c 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
@@ -174,7 +174,7 @@
bytes_read
(exec
(java/io/OutputStream::write chunk +0 bytes_read buffer)
- (recur (|> bytes_read .nat (n.+ so_far))))))))
+ (again (|> bytes_read .nat (n.+ so_far))))))))
(def: (read_jar_entry_with_known_size expected_size input)
(-> Nat java/util/jar/JarInputStream [Nat Binary])
@@ -186,7 +186,7 @@
(n.+ so_far))]
(if (n.= expected_size so_far')
[expected_size buffer]
- (recur so_far'))))))
+ (again so_far'))))))
(def: (read_jar_entry entry input)
(-> java/util/jar/JarEntry java/util/jar/JarInputStream [Nat Binary])
@@ -226,19 +226,19 @@
(text.starts_with? "META-INF/leiningen/" entry_path)))
(case (java/util/jar/JarOutputStream::putNextEntry (java/util/jar/JarEntry::new entry_path) sink)
{try.#Failure error}
- (recur entries
+ (again entries
(set.has entry_path duplicates)
sink)
{try.#Success _}
(let [[entry_size entry_data] (read_jar_entry entry input)]
- (recur (set.has entry_path entries)
+ (again (set.has entry_path entries)
duplicates
(do_to sink
(java/util/zip/ZipOutputStream::write entry_data +0 (.int entry_size))
(java/io/Flushable::flush)
(java/util/zip/ZipOutputStream::closeEntry)))))
- (recur entries
+ (again entries
duplicates
sink))))))))
diff --git a/stdlib/source/library/lux/tool/interpreter.lux b/stdlib/source/library/lux/tool/interpreter.lux
index b08b79461..184b4444c 100644
--- a/stdlib/source/library/lux/tool/interpreter.lux
+++ b/stdlib/source/library/lux/tool/interpreter.lux
@@ -221,11 +221,11 @@
{try.#Success [context' representation]}
(do !
[_ (# Console<!> write representation)]
- (recur context' #0))
+ (again context' #0))
{try.#Failure error}
(if (ex.match? syntax.end_of_file error)
- (recur context #1)
+ (again context #1)
(exec (log! (ex.error ..error error))
- (recur (with@ #source ..fresh_source context) #0))))))
+ (again (with@ #source ..fresh_source context) #0))))))
)))
diff --git a/stdlib/source/library/lux/type.lux b/stdlib/source/library/lux/type.lux
index b389af6de..1d573186f 100644
--- a/stdlib/source/library/lux/type.lux
+++ b/stdlib/source/library/lux/type.lux
@@ -34,7 +34,7 @@
type type]
(case type
{<tag> env sub_type}
- (recur (++ num_args) sub_type)
+ (again (++ num_args) sub_type)
_
[num_args type])))]
diff --git a/stdlib/source/library/lux/type/abstract.lux b/stdlib/source/library/lux/type/abstract.lux
index 0e199c7ad..0d533d80f 100644
--- a/stdlib/source/library/lux/type/abstract.lux
+++ b/stdlib/source/library/lux/type/abstract.lux
@@ -52,7 +52,7 @@
{.#Item [head_name head] tail}
(if (text#= <reference> head_name)
<then>
- (recur tail))
+ (again tail))
{.#End}
(undefined)))])
@@ -112,7 +112,7 @@
{.#Item [head_name <then>]
tail}
{.#Item [head_name head]
- (recur tail)})
+ (again tail)})
{.#End}
(undefined)))])
diff --git a/stdlib/source/library/lux/type/check.lux b/stdlib/source/library/lux/type/check.lux
index b93188bb1..59e8459f7 100644
--- a/stdlib/source/library/lux/type/check.lux
+++ b/stdlib/source/library/lux/type/check.lux
@@ -314,7 +314,7 @@
{.#Var post}
(if (!n#= start post)
{try.#Success [context output]}
- (recur post (set.has post output)))
+ (again post (set.has post output)))
_
{try.#Success [context empty_ring]})
@@ -631,7 +631,7 @@
[{.#Item e_head e_tail} {.#Item a_head a_tail}]
(do ..monad
[assumptions' (check' assumptions e_head a_head)]
- (recur assumptions' e_tail a_tail))
+ (again assumptions' e_tail a_tail))
_
..silent_failure!))
diff --git a/stdlib/source/library/lux/type/resource.lux b/stdlib/source/library/lux/type/resource.lux
index d9ffdfea7..9105a18f1 100644
--- a/stdlib/source/library/lux/type/resource.lux
+++ b/stdlib/source/library/lux/type/resource.lux
@@ -118,7 +118,7 @@
[head <code>.nat
_ (<>.assertion (exception.error ..index_cannot_be_repeated head)
(not (set.member? seen head)))
- tail (recur (set.has head seen))]
+ tail (again (set.has head seen))]
(in (list& head tail))))))))
(def: (no_op monad)
diff --git a/stdlib/source/library/lux/world/file.lux b/stdlib/source/library/lux/world/file.lux
index 4ddb44aa6..b32861291 100644
--- a/stdlib/source/library/lux/world/file.lux
+++ b/stdlib/source/library/lux/world/file.lux
@@ -736,7 +736,7 @@
{.#Item head tail}
(do !
[verdict (<test> head)]
- (recur tail (if verdict
+ (again tail (if verdict
{.#Item head output}
output)))))
_ (RubyDir::close [] self)]
@@ -932,8 +932,8 @@
... (do !
... [verdict (<test> head)]
... (if verdict
- ... (recur tail {.#Item (<constructor> head) output})
- ... (recur tail output)))))))]
+ ... (again tail {.#Item (<constructor> head) output})
+ ... (again tail output)))))))]
... [files ..is_file ..file File]
... [directories ..is_dir directory Directory]
@@ -1024,7 +1024,7 @@
{try.#Success [head file]}
[{.#Right sub_directory} {.#Item _}]
- (recur sub_directory tail)
+ (again sub_directory tail)
_
(exception.except ..cannot_find_file [path])))
@@ -1062,7 +1062,7 @@
[{.#Right sub_directory} {.#Item _}]
(do try.monad
- [sub_directory (recur sub_directory tail)]
+ [sub_directory (again sub_directory tail)]
(in (dictionary.has head {.#Right sub_directory} directory)))
_
@@ -1100,7 +1100,7 @@
{.#Right sub_directory}
(do try.monad
- [sub_directory' (recur sub_directory tail)]
+ [sub_directory' (again sub_directory tail)]
(in (dictionary.has head {.#Right sub_directory'} directory))))))
{.#End}
@@ -1138,7 +1138,7 @@
(case [node tail]
[{.#Right sub_directory} {.#Item _}]
(do try.monad
- [sub_directory (recur sub_directory tail)]
+ [sub_directory (again sub_directory tail)]
(in (dictionary.has head {.#Right sub_directory} directory)))
_
@@ -1171,7 +1171,7 @@
{try.#Success sub_directory}
{.#Item _}
- (recur sub_directory tail)))))))
+ (again sub_directory tail)))))))
(def: .public (mock separator)
(-> Text (System Async))
@@ -1347,7 +1347,7 @@
(in {try.#Success []})
{.#Item head tail}
- (recur (format current (# fs separator) head)
+ (again (format current (# fs separator) head)
tail))
{try.#Failure error}
diff --git a/stdlib/source/library/lux/world/file/watch.lux b/stdlib/source/library/lux/world/file/watch.lux
index b3796ed38..02cdb0ff1 100644
--- a/stdlib/source/library/lux/world/file/watch.lux
+++ b/stdlib/source/library/lux/world/file/watch.lux
@@ -277,7 +277,7 @@
(loop [idx 0
output {.#End}]
(if (n.< size idx)
- (recur (++ idx)
+ (again (++ idx)
{.#Item (java/util/List::get (.int idx) list)
output})
output))))
@@ -386,9 +386,9 @@
java/nio/file/Path::toString
(:as //.Path))]
the_concern (..default_key_concern key)]
- (recur {.#Item [the_concern path]
+ (again {.#Item [the_concern path]
output}))
- (recur output)))
+ (again output)))
{.#None}
(in output)))))
diff --git a/stdlib/source/library/lux/world/net/http/client.lux b/stdlib/source/library/lux/world/net/http/client.lux
index d2dc29f2d..3403523cd 100644
--- a/stdlib/source/library/lux/world/net/http/client.lux
+++ b/stdlib/source/library/lux/world/net/http/client.lux
@@ -138,10 +138,10 @@
-1 (do !
[_ (java/lang/AutoCloseable::close input)]
(in [(.nat so_far) buffer]))
- +0 (recur so_far)
+ +0 (again so_far)
_ (if (i.= remaining bytes_read)
(in [buffer_size buffer])
- (recur (i.+ bytes_read so_far))))))
+ (again (i.+ bytes_read so_far))))))
(loop [so_far +0
output (# binary.monoid identity)]
(do [! (try.with io.monad)]
@@ -158,11 +158,11 @@
(|>> (# binary.monoid composite output)
..body_of))
(# io.monad in))))
- +0 (recur so_far output)
+ +0 (again so_far output)
_ (if (i.= remaining bytes_read)
- (recur +0
+ (again +0
(# binary.monoid composite output buffer))
- (recur (i.+ bytes_read so_far)
+ (again (i.+ bytes_read so_far)
output))))))))))
(def: (default_headers connection)
@@ -175,7 +175,7 @@
{.#Some name}
(do !
[?value (java/net/URLConnection::getHeaderField index connection)]
- (recur (++ index)
+ (again (++ index)
(dictionary.has name (maybe.else "" ?value) headers)))
{.#None}
diff --git a/stdlib/source/library/lux/world/program.lux b/stdlib/source/library/lux/world/program.lux
index e69b0524b..5c5ca77f6 100644
--- a/stdlib/source/library/lux/world/program.lux
+++ b/stdlib/source/library/lux/world/program.lux
@@ -343,7 +343,7 @@
... (if ("scheme object nil?" input)
... (in output)
... (let [entry (..head input)]
- ... (recur (..tail input)
+ ... (again (..tail input)
... (dictionary.has (..car entry) (..cdr entry) output))))))
])))