From 381ec5920d9ebeb335963778dec182268819e718 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Wed, 30 Mar 2022 14:05:57 -0400 Subject: Now demanding mandatory loop names, instead of using default "again" name. --- stdlib/source/library/lux.lux | 16 +++---- stdlib/source/library/lux/abstract/enum.lux | 6 +-- stdlib/source/library/lux/abstract/monad.lux | 4 +- .../library/lux/control/concurrency/actor.lux | 6 +-- .../library/lux/control/concurrency/atom.lux | 2 +- .../source/library/lux/control/concurrency/frp.lux | 12 ++--- .../library/lux/control/concurrency/semaphore.lux | 2 +- .../source/library/lux/control/concurrency/stm.lux | 2 +- .../library/lux/control/concurrency/thread.lux | 2 +- stdlib/source/library/lux/control/maybe.lux | 4 +- .../source/library/lux/control/parser/binary.lux | 14 +++--- stdlib/source/library/lux/control/parser/cli.lux | 2 +- stdlib/source/library/lux/control/parser/type.lux | 6 +-- stdlib/source/library/lux/control/pipe.lux | 14 +++--- stdlib/source/library/lux/data/binary.lux | 4 +- stdlib/source/library/lux/data/collection/bits.lux | 18 ++++---- .../lux/data/collection/dictionary/ordered.lux | 18 ++++---- stdlib/source/library/lux/data/collection/list.lux | 8 ++-- .../library/lux/data/collection/queue/priority.lux | 6 +-- .../library/lux/data/collection/sequence.lux | 10 ++-- .../source/library/lux/data/collection/stream.lux | 4 +- stdlib/source/library/lux/data/collection/tree.lux | 6 +-- .../library/lux/data/collection/tree/finger.lux | 4 +- .../library/lux/data/collection/tree/zipper.lux | 4 +- stdlib/source/library/lux/data/format/json.lux | 2 +- stdlib/source/library/lux/data/format/tar.lux | 2 +- stdlib/source/library/lux/data/format/xml.lux | 4 +- stdlib/source/library/lux/data/text.lux | 18 ++++---- stdlib/source/library/lux/data/text/escape.lux | 16 +++---- .../source/library/lux/data/text/unicode/set.lux | 2 +- stdlib/source/library/lux/debug.lux | 12 ++--- stdlib/source/library/lux/macro.lux | 4 +- stdlib/source/library/lux/math/number/frac.lux | 4 +- stdlib/source/library/lux/math/number/i64.lux | 4 +- stdlib/source/library/lux/math/number/int.lux | 6 +-- stdlib/source/library/lux/math/number/nat.lux | 16 +++---- stdlib/source/library/lux/math/number/rev.lux | 48 +++++++++---------- stdlib/source/library/lux/math/random.lux | 4 +- stdlib/source/library/lux/meta.lux | 4 +- .../lux/target/jvm/bytecode/instruction.lux | 10 ++-- .../library/lux/target/jvm/constant/pool.lux | 2 +- stdlib/source/library/lux/test.lux | 4 +- .../library/lux/tool/compiler/default/init.lux | 4 +- .../library/lux/tool/compiler/default/platform.lux | 22 ++++----- .../lux/tool/compiler/language/lux/analysis.lux | 6 +-- .../compiler/language/lux/analysis/coverage.lux | 6 +-- .../compiler/language/lux/analysis/inference.lux | 4 +- .../tool/compiler/language/lux/analysis/scope.lux | 4 +- .../compiler/language/lux/phase/analysis/case.lux | 14 +++--- .../language/lux/phase/analysis/complex.lux | 10 ++-- .../language/lux/phase/analysis/function.lux | 2 +- .../tool/compiler/language/lux/phase/directive.lux | 6 +-- .../language/lux/phase/extension/analysis/jvm.lux | 2 +- .../language/lux/phase/extension/analysis/lux.lux | 2 +- .../lux/phase/extension/generation/jvm/host.lux | 2 +- .../compiler/language/lux/phase/synthesis/case.lux | 14 +++--- .../compiler/language/lux/phase/synthesis/loop.lux | 4 +- .../lux/tool/compiler/language/lux/syntax.lux | 14 +++--- .../compiler/meta/cache/dependency/artifact.lux | 4 +- .../library/lux/tool/compiler/meta/io/archive.lux | 10 ++-- .../lux/tool/compiler/meta/packager/jvm.lux | 10 ++-- stdlib/source/library/lux/tool/interpreter.lux | 8 ++-- stdlib/source/library/lux/type.lux | 4 +- stdlib/source/library/lux/type/abstract.lux | 4 +- stdlib/source/library/lux/type/check.lux | 10 ++-- stdlib/source/library/lux/type/resource.lux | 2 +- stdlib/source/library/lux/world/file.lux | 54 +++++++++++----------- stdlib/source/library/lux/world/file/watch.lux | 8 ++-- .../source/library/lux/world/net/http/client.lux | 10 ++-- stdlib/source/library/lux/world/program.lux | 4 +- 70 files changed, 287 insertions(+), 293 deletions(-) (limited to 'stdlib/source/library') diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux index 67f2dc4d3..da0e84a92 100644 --- a/stdlib/source/library/lux.lux +++ b/stdlib/source/library/lux.lux @@ -4449,11 +4449,8 @@ (macro: .public (loop tokens) (let [?params (case tokens - (pattern (list name [_ {#Tuple bindings}] body)) + (pattern (list [_ {#Form (list name [_ {#Tuple bindings}])}] body)) {#Some [name bindings body]} - - (pattern (list [_ {#Tuple bindings}] body)) - {#Some [(local$ "again") bindings body]} _ {#None})] @@ -4482,9 +4479,8 @@ (is (-> Code (Meta Code)) (function (_ _) (..generated_symbol ""))) inits)] - (meta#in (list (` (let [(~+ (..interleaved aliases inits))] - (.loop (~ name) - [(~+ (..interleaved vars aliases))] + (meta#in (list (` (..let [(~+ (..interleaved aliases inits))] + (..loop ((~ name) [(~+ (..interleaved vars aliases))]) (~ body))))))))) {#None} @@ -4515,9 +4511,9 @@ (macro: .public (with_expansions tokens) (case (parsed (andP (tupleP (someP bindingP)) (someP anyP)) tokens) {#Some [bindings bodies]} - (loop [bindings bindings - map (is (PList (List Code)) - (list))] + (loop (again [bindings bindings + map (is (PList (List Code)) + (list))]) (let [normal (is (-> Code (List Code)) (function (_ it) (list#mix (function (_ [binding expansion] it) diff --git a/stdlib/source/library/lux/abstract/enum.lux b/stdlib/source/library/lux/abstract/enum.lux index fd9e19e37..5ea97da4d 100644 --- a/stdlib/source/library/lux/abstract/enum.lux +++ b/stdlib/source/library/lux/abstract/enum.lux @@ -13,9 +13,9 @@ (def: .public (range enum from to) (All (_ a) (-> (Enum a) a a (List a))) (let [(open "/#[0]") enum] - (loop [end to - output (`` (is (List (~~ (type_of from))) - {.#End}))] + (loop (again [end to + output (`` (is (List (~~ (type_of from))) + {.#End}))]) (cond (/#< end from) (again (/#pred end) {.#Item end output}) diff --git a/stdlib/source/library/lux/abstract/monad.lux b/stdlib/source/library/lux/abstract/monad.lux index 6a07fe8a2..e5268e354 100644 --- a/stdlib/source/library/lux/abstract/monad.lux +++ b/stdlib/source/library/lux/abstract/monad.lux @@ -18,8 +18,8 @@ (def: (list#size xs) (All (_ a) (-> (List a) Nat)) - (loop [counter 0 - xs xs] + (loop (again [counter 0 + xs xs]) (case xs {.#End} counter diff --git a/stdlib/source/library/lux/control/concurrency/actor.lux b/stdlib/source/library/lux/control/concurrency/actor.lux index 16a789547..06eb74e44 100644 --- a/stdlib/source/library/lux/control/concurrency/actor.lux +++ b/stdlib/source/library/lux/control/concurrency/actor.lux @@ -88,8 +88,8 @@ (Actor s) (abstraction [#obituary (async.async []) #mailbox (atom (async.async []))])) - process (loop [state (on_init init) - [|mailbox| _] (io.run! (atom.read! (the #mailbox (representation self))))] + process (loop (again [state (on_init init) + [|mailbox| _] (io.run! (atom.read! (the #mailbox (representation self))))]) (do [! async.monad] [[head tail] |mailbox| ?state' (on_mail head state self)] @@ -138,7 +138,7 @@ (let [entry [mail (async.async [])]] (do ! [|mailbox|&resolve (atom.read! (the #mailbox (representation actor)))] - (loop [[|mailbox| resolve] |mailbox|&resolve] + (loop (again [[|mailbox| resolve] |mailbox|&resolve]) (do ! [|mailbox| (async.value |mailbox|)] (case |mailbox| diff --git a/stdlib/source/library/lux/control/concurrency/atom.lux b/stdlib/source/library/lux/control/concurrency/atom.lux index 8fd8e86bf..bb8c732a4 100644 --- a/stdlib/source/library/lux/control/concurrency/atom.lux +++ b/stdlib/source/library/lux/control/concurrency/atom.lux @@ -81,7 +81,7 @@ (def: .public (update! f atom) (All (_ a) (-> (-> a a) (Atom a) (IO [a a]))) - (loop [_ []] + (loop (again [_ []]) (do io.monad [old (read! atom) .let [new (f old)] diff --git a/stdlib/source/library/lux/control/concurrency/frp.lux b/stdlib/source/library/lux/control/concurrency/frp.lux index 361a2439b..cb0613fae 100644 --- a/stdlib/source/library/lux/control/concurrency/frp.lux +++ b/stdlib/source/library/lux/control/concurrency/frp.lux @@ -36,7 +36,7 @@ (let [sink (atom.atom resolve)] (implementation (def: close - (loop [_ []] + (loop (again [_ []]) (do [! io.monad] [current (atom.read! sink) stopped? (current {.#None})] @@ -53,7 +53,7 @@ (again []))))))) (def: (feed value) - (loop [_ []] + (loop (again [_ []]) (do [! io.monad] [current (atom.read! sink) .let [[next resolve_next] (sharing [a] @@ -124,13 +124,13 @@ (let [[output sink] (channel [])] (exec (is (Async Any) - (loop [mma mma] + (loop (again [mma mma]) (do [! async.monad] [?mma mma] (case ?mma {.#Some [ma mma']} (do ! - [_ (loop [ma ma] + [_ (loop (again [ma ma]) (do ! [?ma ma] (case ?ma @@ -154,7 +154,7 @@ (All (_ a) (-> (Subscriber a) (Channel a) (IO Any))) (io (exec (is (Async Any) - (loop [channel channel] + (loop (again [channel channel]) (do async.monad [item channel] (case item @@ -228,7 +228,7 @@ (-> Nat (IO a) [(Channel a) (Sink a)])) (let [[output sink] (channel [])] (exec - (io.run! (loop [_ []] + (io.run! (loop (again [_ []]) (do io.monad [value action _ (# sink feed value)] diff --git a/stdlib/source/library/lux/control/concurrency/semaphore.lux b/stdlib/source/library/lux/control/concurrency/semaphore.lux index 1e177aa5e..4b5f886a4 100644 --- a/stdlib/source/library/lux/control/concurrency/semaphore.lux +++ b/stdlib/source/library/lux/control/concurrency/semaphore.lux @@ -140,7 +140,7 @@ (def: (un_block! times turnstile) (-> Nat Semaphore (Async Any)) - (loop [step 0] + (loop (again [step 0]) (if (n.< times step) (do async.monad [outcome (..signal! turnstile)] diff --git a/stdlib/source/library/lux/control/concurrency/stm.lux b/stdlib/source/library/lux/control/concurrency/stm.lux index 9935069d9..be8203dde 100644 --- a/stdlib/source/library/lux/control/concurrency/stm.lux +++ b/stdlib/source/library/lux/control/concurrency/stm.lux @@ -214,7 +214,7 @@ (let [entry [commit (async.async [])]] (do [! io.monad] [|commits|&resolve (atom.read! pending_commits)] - (loop [[|commits| resolve] |commits|&resolve] + (loop (again [[|commits| resolve] |commits|&resolve]) (do ! [|commits| (async.value |commits|)] (case |commits| diff --git a/stdlib/source/library/lux/control/concurrency/thread.lux b/stdlib/source/library/lux/control/concurrency/thread.lux index a885b63a9..3ba009a7c 100644 --- a/stdlib/source/library/lux/control/concurrency/thread.lux +++ b/stdlib/source/library/lux/control/concurrency/thread.lux @@ -171,7 +171,7 @@ (in []) (do ! [_ (atom.write! true ..started?)] - (loop [_ []] + (loop (again [_ []]) (do ! [threads (atom.read! ..runner)] (case threads diff --git a/stdlib/source/library/lux/control/maybe.lux b/stdlib/source/library/lux/control/maybe.lux index 4f678aecb..d9c15e307 100644 --- a/stdlib/source/library/lux/control/maybe.lux +++ b/stdlib/source/library/lux/control/maybe.lux @@ -138,7 +138,7 @@ (~ else))))]}) _ - {.#Left "Wrong syntax for else"})) + {.#Left "Wrong syntax for 'else'"})) (def: .public trusted (All (_ a) (-> (Maybe a) a)) @@ -162,4 +162,4 @@ {.#None})))]} _ - {.#Left "Wrong syntax for when"})) + {.#Left "Wrong syntax for 'when'"})) diff --git a/stdlib/source/library/lux/control/parser/binary.lux b/stdlib/source/library/lux/control/parser/binary.lux index b8c37c1bb..015961926 100644 --- a/stdlib/source/library/lux/control/parser/binary.lux +++ b/stdlib/source/library/lux/control/parser/binary.lux @@ -194,13 +194,13 @@ (do //.monad [amount (is (Parser Nat) )] - (loop [index 0 - output (sharing [v] - (Parser v) - valueP - - (Sequence v) - sequence.empty)] + (loop (again [index 0 + output (sharing [v] + (Parser v) + valueP + + (Sequence v) + sequence.empty)]) (if (n.< amount index) (do //.monad [value valueP] diff --git a/stdlib/source/library/lux/control/parser/cli.lux b/stdlib/source/library/lux/control/parser/cli.lux index 11010725a..8424b4d37 100644 --- a/stdlib/source/library/lux/control/parser/cli.lux +++ b/stdlib/source/library/lux/control/parser/cli.lux @@ -57,7 +57,7 @@ (def: .public (somewhere cli) (All (_ a) (-> (Parser a) (Parser a))) (function (_ inputs) - (loop [immediate inputs] + (loop (again [immediate inputs]) (case (//.result cli immediate) {try.#Success [remaining output]} {try.#Success [remaining output]} diff --git a/stdlib/source/library/lux/control/parser/type.lux b/stdlib/source/library/lux/control/parser/type.lux index d13f44b21..714810217 100644 --- a/stdlib/source/library/lux/control/parser/type.lux +++ b/stdlib/source/library/lux/control/parser/type.lux @@ -184,9 +184,9 @@ [num_args non_poly] (local (list headT) ..polymorphic') env ..env .let [funcL (label funcI) - [all_varsL env'] (loop [current_arg 0 - env' env - all_varsL (is (List Code) (list))] + [all_varsL env'] (loop (again [current_arg 0 + env' env + all_varsL (is (List Code) (list))]) (if (n.< num_args current_arg) (if (n.= 0 current_arg) (let [varL (label (++ funcI))] diff --git a/stdlib/source/library/lux/control/pipe.lux b/stdlib/source/library/lux/control/pipe.lux index b65802ce6..3b136f771 100644 --- a/stdlib/source/library/lux/control/pipe.lux +++ b/stdlib/source/library/lux/control/pipe.lux @@ -1,6 +1,6 @@ (.using [library - [lux {"-" let cond if loop exec case} + [lux {"-" let cond if exec case} [abstract ["[0]" monad]] [control @@ -67,13 +67,13 @@ [] (~ prev)))))) -(syntax: .public (loop [test ..body - then ..body - prev .any]) - (with_symbols [g!temp] - (in (list (` (.loop [(~ g!temp) (~ prev)] +(syntax: .public (while [test ..body + then ..body + prev .any]) + (with_symbols [g!temp g!again] + (in (list (` (.loop ((~ g!again) [(~ g!temp) (~ prev)]) (.if (|> (~ g!temp) (~+ test)) - ((~' again) (|> (~ g!temp) (~+ then))) + ((~ g!again) (|> (~ g!temp) (~+ then))) (~ g!temp)))))))) (syntax: .public (do [monad .any diff --git a/stdlib/source/library/lux/data/binary.lux b/stdlib/source/library/lux/data/binary.lux index 4baadaf05..6cea2f879 100644 --- a/stdlib/source/library/lux/data/binary.lux +++ b/stdlib/source/library/lux/data/binary.lux @@ -34,8 +34,8 @@ (def: .public (aggregate $ init it) (All (_ a) (-> (-> I64 a a) a Binary a)) (let [size (/.size it)] - (loop [index 0 - output init] + (loop (again [index 0 + output init]) (if (n.< size index) (again (++ index) ($ (/.bytes/1 index it) output)) output)))) diff --git a/stdlib/source/library/lux/data/collection/bits.lux b/stdlib/source/library/lux/data/collection/bits.lux index 797bb5981..c6f692f52 100644 --- a/stdlib/source/library/lux/data/collection/bits.lux +++ b/stdlib/source/library/lux/data/collection/bits.lux @@ -64,9 +64,9 @@ [(def: .public ( index input) (-> Nat Bits Bits) (let [[chunk_index bit_index] (n./% chunk_size index)] - (loop [size|output (n.max (++ chunk_index) - (array.size input)) - output ..empty] + (loop (again [size|output (n.max (++ chunk_index) + (array.size input)) + output ..empty]) (let [idx|output (-- size|output)] (if (n.> 0 size|output) (case (|> (..chunk idx|output input) @@ -98,7 +98,7 @@ (-> Bits Bits Bit) (let [chunks (n.min (array.size reference) (array.size sample))] - (loop [idx 0] + (loop (again [idx 0]) (if (n.< chunks idx) (.or (|> (..chunk idx sample) (i64.and (..chunk idx reference)) @@ -114,8 +114,8 @@ ..empty size|output - (loop [size|output size|output - output ..empty] + (loop (again [size|output size|output + output ..empty]) (let [idx (-- size|output)] (case (|> input (..chunk idx) i64.not .nat) 0 @@ -139,8 +139,8 @@ ..empty size|output - (loop [size|output size|output - output ..empty] + (loop (again [size|output size|output + output ..empty]) (let [idx (-- size|output)] (if (n.> 0 size|output) (case (|> (..chunk idx subject) @@ -168,7 +168,7 @@ (def: (= reference sample) (let [size (n.max (array.size reference) (array.size sample))] - (loop [idx 0] + (loop (again [idx 0]) (if (n.< size idx) (.and ("lux i64 =" (..chunk idx reference) diff --git a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux index 217c07d1e..b9226a891 100644 --- a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux +++ b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux @@ -62,7 +62,7 @@ (All (_ k v) (-> k (Dictionary k v) (Maybe v))) (let [... (open "_#[0]") (the #&order dict) ] - (loop [node (the #root dict)] + (loop (again [node (the #root dict)]) (case node {.#None} {.#None} @@ -87,7 +87,7 @@ (All (_ k v) (-> (Dictionary k v) k Bit)) (let [... (open "_#[0]") (the #&order dict) ] - (loop [node (the #root dict)] + (loop (again [node (the #root dict)]) (case node {.#None} #0 @@ -109,7 +109,7 @@ {.#None} {.#Some node} - (loop [node node] + (loop (again [node node]) (case (the node) {.#None} {.#Some (the #value node)} @@ -123,7 +123,7 @@ (def: .public (size dict) (All (_ k v) (-> (Dictionary k v) Nat)) - (loop [node (the #root dict)] + (loop (again [node (the #root dict)]) (case node {.#None} 0 @@ -252,7 +252,7 @@ (def: .public (has key value dict) (All (_ k v) (-> k v (Dictionary k v) (Dictionary k v))) (let [(open "_#[0]") (the #&order dict) - root' (loop [?root (the #root dict)] + root' (loop (again [?root (the #root dict)]) (case ?root {.#None} {.#Some (red key value {.#None} {.#None})} @@ -475,7 +475,7 @@ (def: .public (lacks key dict) (All (_ k v) (-> k (Dictionary k v) (Dictionary k v))) (let [(open "_#[0]") (the #&order dict) - [?root found?] (loop [?root (the #root dict)] + [?root found?] (loop (again [?root (the #root dict)]) (case ?root {.#Some root} (let [root_key (the #key root) @@ -546,7 +546,7 @@ (template [ ] [(def: .public ( dict) (All (_ k v) (-> (Dictionary k v) (List ))) - (loop [node (the #root dict)] + (loop (again [node (the #root dict)]) (case node {.#None} (list) @@ -567,8 +567,8 @@ (def: (= reference sample) (let [(open "/#[0]") (the #&order reference)] - (loop [entriesR (entries reference) - entriesS (entries sample)] + (loop (again [entriesR (entries reference) + entriesS (entries sample)]) (case [entriesR entriesS] [{.#End} {.#End}] #1 diff --git a/stdlib/source/library/lux/data/collection/list.lux b/stdlib/source/library/lux/data/collection/list.lux index 450bfea3a..19d15e35e 100644 --- a/stdlib/source/library/lux/data/collection/list.lux +++ b/stdlib/source/library/lux/data/collection/list.lux @@ -434,8 +434,8 @@ (def: (nat#encoded value) (-> Nat Text) - (loop [input value - output ""] + (loop (again [input value + output ""]) (let [digit (case (n.% 10 input) 0 "0" 1 "1" @@ -597,8 +597,8 @@ (def: .public (enumeration xs) (All (_ a) (-> (List a) (List [Nat a]))) - (loop [idx 0 - xs xs] + (loop (again [idx 0 + xs xs]) (case xs {.#End} {.#End} diff --git a/stdlib/source/library/lux/data/collection/queue/priority.lux b/stdlib/source/library/lux/data/collection/queue/priority.lux index 102472124..904858147 100644 --- a/stdlib/source/library/lux/data/collection/queue/priority.lux +++ b/stdlib/source/library/lux/data/collection/queue/priority.lux @@ -58,7 +58,7 @@ 0 {.#Some tree} - (loop [node tree] + (loop (again [node tree]) (case (tree.root node) {0 #0 _} 1 @@ -73,7 +73,7 @@ false {.#Some tree} - (loop [node tree] + (loop (again [node tree]) (case (tree.root node) {0 #0 reference} (# equivalence = reference member) @@ -88,7 +88,7 @@ (do maybe.monad [tree (representation queue) .let [highest_priority (tree.tag tree)]] - (loop [node tree] + (loop (again [node tree]) (case (tree.root node) {0 #0 reference} (if (n.= highest_priority (tree.tag node)) diff --git a/stdlib/source/library/lux/data/collection/sequence.lux b/stdlib/source/library/lux/data/collection/sequence.lux index 285a65109..f786a9276 100644 --- a/stdlib/source/library/lux/data/collection/sequence.lux +++ b/stdlib/source/library/lux/data/collection/sequence.lux @@ -257,8 +257,8 @@ (All (_ a) (-> Index (Sequence a) (Try (Base a)))) (if (within_bounds? sequence idx) (if (n.< (tail_off (the #size sequence)) idx) - (loop [level (the #level sequence) - hierarchy (the #root sequence)] + (loop (again [level (the #level sequence) + hierarchy (the #root sequence)]) (let [index (branch_idx (i64.right_shifted level idx))] (if (array.lacks? index hierarchy) (exception.except ..base_was_not_found []) @@ -324,9 +324,9 @@ (do maybe.monad [new_tail (base_for (n.- 2 sequence_size) sequence) .let [[level' root'] (let [init_level (the #level sequence)] - (loop [level init_level - root (maybe.else (empty_hierarchy []) - (without_tail sequence_size init_level (the #root sequence)))] + (loop (again [level init_level + root (maybe.else (empty_hierarchy []) + (without_tail sequence_size init_level (the #root sequence)))]) (with_expansions [ [level root]] (if (n.> branching_exponent level) (if (array.lacks? 1 root) diff --git a/stdlib/source/library/lux/data/collection/stream.lux b/stdlib/source/library/lux/data/collection/stream.lux index 2c059103a..672fa8f72 100644 --- a/stdlib/source/library/lux/data/collection/stream.lux +++ b/stdlib/source/library/lux/data/collection/stream.lux @@ -36,8 +36,8 @@ (def: .public (cycle [start next]) (All (_ a) (-> [a (List a)] (Stream a))) - (loop [head start - tail next] + (loop (again [head start + tail next]) (//.pending [head (case tail {.#End} (again start next) diff --git a/stdlib/source/library/lux/data/collection/tree.lux b/stdlib/source/library/lux/data/collection/tree.lux index b0940209e..58694df25 100644 --- a/stdlib/source/library/lux/data/collection/tree.lux +++ b/stdlib/source/library/lux/data/collection/tree.lux @@ -55,9 +55,9 @@ (<>.and .any))) (syntax: .public (tree [root tree^]) - (in (list (` (~ (loop [[value children] root] - (` [#value (~ value) - #children (list (~+ (list#each again children)))]))))))) + (in (list (loop (again [[value children] root]) + (` [#value (~ value) + #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 26caf5317..3c8e5e1db 100644 --- a/stdlib/source/library/lux/data/collection/tree/finger.lux +++ b/stdlib/source/library/lux/data/collection/tree/finger.lux @@ -87,8 +87,8 @@ (let [[monoid tag root] (representation tree)] (if (predicate tag) (let [(open "tag//[0]") monoid] - (loop [_tag tag//identity - _node root] + (loop (again [_tag tag//identity + _node root]) (case _node {0 #0 value} {.#Some value} diff --git a/stdlib/source/library/lux/data/collection/tree/zipper.lux b/stdlib/source/library/lux/data/collection/tree/zipper.lux index 9986e63a8..4f9889f9c 100644 --- a/stdlib/source/library/lux/data/collection/tree/zipper.lux +++ b/stdlib/source/library/lux/data/collection/tree/zipper.lux @@ -177,7 +177,7 @@ {.#Some forward} {.#None} - (loop [@ zipper] + (loop (again [@ zipper]) (case (..right @) {.#Some forward} {.#Some forward} @@ -223,7 +223,7 @@ {.#None} {.#Some @} - (loop [@ @] + (loop (again [@ @]) (case ( @) {.#None} {.#Some @} diff --git a/stdlib/source/library/lux/data/format/json.lux b/stdlib/source/library/lux/data/format/json.lux index 0a08da9b6..2f21d8dc5 100644 --- a/stdlib/source/library/lux/data/format/json.lux +++ b/stdlib/source/library/lux/data/format/json.lux @@ -383,7 +383,7 @@ (def: string_parser (Parser String) (<| (.enclosed [text.double_quote text.double_quote]) - (loop [_ []]) + (loop (again [_ []])) (do [! <>.monad] [chars (.some (.none_of (text#composite "\" text.double_quote))) stop .next]) diff --git a/stdlib/source/library/lux/data/format/tar.lux b/stdlib/source/library/lux/data/format/tar.lux index 2387b162f..264acaf46 100644 --- a/stdlib/source/library/lux/data/format/tar.lux +++ b/stdlib/source/library/lux/data/format/tar.lux @@ -233,7 +233,7 @@ (-> Binary (Try Binary)) (case (binary.size string) 0 {try.#Success string} - size (loop [end (-- size)] + size (loop (again [end (-- size)]) (case end 0 {try.#Success (# utf8.codec encoded "")} _ (do try.monad diff --git a/stdlib/source/library/lux/data/format/xml.lux b/stdlib/source/library/lux/data/format/xml.lux index b7e3fd2e3..81fee7699 100644 --- a/stdlib/source/library/lux/data/format/xml.lux +++ b/stdlib/source/library/lux/data/format/xml.lux @@ -246,8 +246,8 @@ (function (_ input) ($_ text#composite ..xml_header text.new_line - (loop [prefix "" - input input] + (loop (again [prefix "" + input input]) (case input {#Text value} (sanitize_value value) diff --git a/stdlib/source/library/lux/data/text.lux b/stdlib/source/library/lux/data/text.lux index 5ac09a8e5..e52ca50c0 100644 --- a/stdlib/source/library/lux/data/text.lux +++ b/stdlib/source/library/lux/data/text.lux @@ -68,9 +68,9 @@ (def: .public (last_index part text) (-> Text Text (Maybe Nat)) - (loop [offset 0 - output (is (Maybe Nat) - {.#None})] + (loop (again [offset 0 + output (is (Maybe Nat) + {.#None})]) (let [output' ("lux text index" offset part text)] (case output' {.#None} @@ -164,8 +164,8 @@ (def: .public (all_split_by token sample) (-> Text Text (List Text)) - (loop [input sample - output (is (List Text) (list))] + (loop (again [input sample + output (is (List Text) (list))]) (case (..split_by token input) {.#Some [pre post]} (|> output @@ -212,8 +212,8 @@ (def: .public (replaced pattern replacement template) (-> Text Text Text Text) (with_expansions [... Inefficient default - (loop [left "" - right template] + (loop (again [left "" + right template]) (case (..split_by pattern right) {.#Some [pre post]} (again ($_ "lux text concat" left pre replacement) post) @@ -301,8 +301,8 @@ (as Nat)) ... Platform-independent default. (let [length ("lux text size" input)] - (loop [index 0 - hash 0] + (loop (again [index 0 + hash 0]) (if (n.< length index) (again (++ index) (|> hash diff --git a/stdlib/source/library/lux/data/text/escape.lux b/stdlib/source/library/lux/data/text/escape.lux index 3209c406d..a3b549273 100644 --- a/stdlib/source/library/lux/data/text/escape.lux +++ b/stdlib/source/library/lux/data/text/escape.lux @@ -112,10 +112,10 @@ (def: .public (escaped text) (-> Text Text) - (loop [offset 0 - previous "" - current text - limit ("lux text size" text)] + (loop (again [offset 0 + previous "" + current text + limit ("lux text size" text)]) (if (n.< limit offset) (case ("lux text char" offset current) (^.template [ ] @@ -196,10 +196,10 @@ (def: .public (un_escaped text) (-> Text (Try Text)) - (loop [offset 0 - previous "" - current text - limit ("lux text size" text)] + (loop (again [offset 0 + previous "" + current text + limit ("lux text size" text)]) (if (n.< limit offset) (case ("lux text char" offset current) (pattern (static ..sigil_char)) diff --git a/stdlib/source/library/lux/data/text/unicode/set.lux b/stdlib/source/library/lux/data/text/unicode/set.lux index 89359273b..df7afedc8 100644 --- a/stdlib/source/library/lux/data/text/unicode/set.lux +++ b/stdlib/source/library/lux/data/text/unicode/set.lux @@ -214,7 +214,7 @@ (def: .public (member? set character) (-> Set Char Bit) - (loop [tree (representation set)] + (loop (again [tree (representation set)]) (if (//block.within? (tree.tag tree) character) (case (tree.root tree) {0 #0 _} diff --git a/stdlib/source/library/lux/debug.lux b/stdlib/source/library/lux/debug.lux index 6e8b498e6..ddc343061 100644 --- a/stdlib/source/library/lux/debug.lux +++ b/stdlib/source/library/lux/debug.lux @@ -125,7 +125,7 @@ (for @.lua (def: (tuple_array tuple) (-> (array.Array Any) (array.Array Any)) (array.of_list - (loop [idx 0] + (loop (again [idx 0]) (let [member ("lua array read" idx tuple)] (if ("lua object nil?" member) {.#End} @@ -447,9 +447,9 @@ (do <>.monad [membersR+ (.variant (<>.many representation))] (in (function (_ variantV) - (let [[lefts right? sub_repr] (loop [lefts 0 - representations membersR+ - variantV variantV] + (let [[lefts right? sub_repr] (loop (again [lefts 0 + representations membersR+ + variantV variantV]) (case representations {.#Item leftR {.#Item rightR extraR+}} (case (as (Or Any Any) variantV) @@ -473,8 +473,8 @@ (do <>.monad [membersR+ (.tuple (<>.many representation))] (in (function (_ tupleV) - (let [tuple_body (loop [representations membersR+ - tupleV tupleV] + (let [tuple_body (loop (again [representations membersR+ + tupleV tupleV]) (case representations {.#End} "" diff --git a/stdlib/source/library/lux/macro.lux b/stdlib/source/library/lux/macro.lux index d0df9fc7b..733837047 100644 --- a/stdlib/source/library/lux/macro.lux +++ b/stdlib/source/library/lux/macro.lux @@ -180,8 +180,8 @@ (macro: .public (times tokens) (case tokens (pattern (list& [_ {.#Nat times}] terms)) - (loop [times times - before terms] + (loop (again [times times + before terms]) (case times 0 (# //.monad in before) diff --git a/stdlib/source/library/lux/math/number/frac.lux b/stdlib/source/library/lux/math/number/frac.lux index aff22f26d..77b54b4da 100644 --- a/stdlib/source/library/lux/math/number/frac.lux +++ b/stdlib/source/library/lux/math/number/frac.lux @@ -358,8 +358,8 @@ (def: .public (factorial it) (-> Nat Nat) - (loop [acc 1 - it it] + (loop (again [acc 1 + it it]) (if (//nat.> 1 it) (again (//nat.* it acc) (-- it)) acc))) diff --git a/stdlib/source/library/lux/math/number/i64.lux b/stdlib/source/library/lux/math/number/i64.lux index 3dcd42f8b..927765984 100644 --- a/stdlib/source/library/lux/math/number/i64.lux +++ b/stdlib/source/library/lux/math/number/i64.lux @@ -148,8 +148,8 @@ (let [size (..left_shifted power 1) repetitions (is (-> Nat Text Text) (function (_ times char) - (loop [iterations 1 - output char] + (loop (again [iterations 1 + output char]) (if (n.< times iterations) (again (++ iterations) ("lux text concat" char output)) diff --git a/stdlib/source/library/lux/math/number/int.lux b/stdlib/source/library/lux/math/number/int.lux index 7d8d19fe6..3b02cfa6e 100644 --- a/stdlib/source/library/lux/math/number/int.lux +++ b/stdlib/source/library/lux/math/number/int.lux @@ -134,9 +134,9 @@ ... https://en.wikipedia.org/wiki/Extended_Euclidean_algorithm (def: .public (extended_gcd a b) (-> Int Int [[Int Int] Int]) - (loop [x +1 x1 +0 - y +0 y1 +1 - a1 a b1 b] + (loop (again [x +1 x1 +0 + y +0 y1 +1 + a1 a b1 b]) (case b1 +0 [[x y] a1] _ (let [q (/ b1 a1)] diff --git a/stdlib/source/library/lux/math/number/nat.lux b/stdlib/source/library/lux/math/number/nat.lux index 31537c887..da1670111 100644 --- a/stdlib/source/library/lux/math/number/nat.lux +++ b/stdlib/source/library/lux/math/number/nat.lux @@ -292,8 +292,8 @@ (def: encoded (let [mask (|> 1 ("lux i64 left-shift" ) --)] (function (_ value) - (loop [input value - output ""] + (loop (again [input value + output ""]) (let [output' ("lux text concat" ( ("lux i64 and" mask input)) output)] @@ -307,8 +307,8 @@ (def: (decoded repr) (let [input_size ("lux text size" repr)] (if (..> 0 input_size) - (loop [idx 0 - output 0] + (loop (again [idx 0 + output 0]) (if (..< input_size idx) (case ( ("lux text char" idx repr)) {.#Some digit_value} @@ -331,8 +331,8 @@ (Codec Text Nat) (def: (encoded value) - (loop [input value - output ""] + (loop (again [input value + output ""]) (let [digit (decimal_character (..% 10 input)) output' ("lux text concat" digit output)] (case (../ 10 input) @@ -346,8 +346,8 @@ (let [input_size ("lux text size" repr)] (with_expansions [ {try.#Failure ("lux text concat" "Invalid decimal syntax for Nat: " repr)}] (if (..> 0 input_size) - (loop [idx 0 - output 0] + (loop (again [idx 0 + output 0]) (if (..< input_size idx) (case (decimal_value ("lux text char" idx repr)) {.#None} diff --git a/stdlib/source/library/lux/math/number/rev.lux b/stdlib/source/library/lux/math/number/rev.lux index 31aa1799b..6fed06ede 100644 --- a/stdlib/source/library/lux/math/number/rev.lux +++ b/stdlib/source/library/lux/math/number/rev.lux @@ -235,8 +235,8 @@ _ 1)) raw_size ("lux text size" raw_output) zero_padding (is Text - (loop [zeroes_left (is Nat (//nat.- raw_size max_num_chars)) - output (is Text "")] + (loop (again [zeroes_left (is Nat (//nat.- raw_size max_num_chars)) + output (is Text "")]) (if (//nat.= 0 zeroes_left) output (again (-- zeroes_left) @@ -295,9 +295,9 @@ (def: (digits#times_5! idx output) (-> Nat Digits Digits) - (loop [idx idx - carry 0 - output output] + (loop (again [idx idx + carry 0 + output output]) (if (//int.< +0 (.int idx)) output (let [raw (|> (..digit idx output) @@ -309,9 +309,9 @@ (def: (power_digits power) (-> Nat Digits) - (loop [times power - output (|> (..digits []) - (digits#put! power 1))] + (loop (again [times power + output (|> (..digits []) + (digits#put! power 1))]) (if (//int.< +0 (.int times)) output (again (-- times) @@ -319,9 +319,9 @@ (def: (format digits) (-> Digits Text) - (loop [idx (-- //i64.width) - all_zeroes? true - output ""] + (loop (again [idx (-- //i64.width) + all_zeroes? true + output ""]) (if (//int.< +0 (.int idx)) (if all_zeroes? "0" @@ -338,9 +338,9 @@ (def: (digits#+! param subject) (-> Digits Digits Digits) - (loop [idx (-- //i64.width) - carry 0 - output (..digits [])] + (loop (again [idx (-- //i64.width) + carry 0 + output (..digits [])]) (if (//int.< +0 (.int idx)) output (let [raw ($_ //nat.+ @@ -356,8 +356,8 @@ (let [length ("lux text size" input)] (if (//nat.> //i64.width length) {.#None} - (loop [idx 0 - output (..digits [])] + (loop (again [idx 0 + output (..digits [])]) (if (//nat.< length idx) (case ("lux text index" 0 ("lux text clip" idx 1 input) "0123456789") {.#None} @@ -370,7 +370,7 @@ (def: (digits#< param subject) (-> Digits Digits Bit) - (loop [idx 0] + (loop (again [idx 0]) (and (//nat.< //i64.width idx) (let [pd (..digit idx param) sd (..digit idx subject)] @@ -392,8 +392,8 @@ (def: (digits#-! param subject) (-> Digits Digits Digits) - (loop [idx (-- //i64.width) - output subject] + (loop (again [idx (-- //i64.width) + output subject]) (if (//int.< +0 (.int idx)) output (again (-- idx) @@ -409,8 +409,8 @@ input (let [last_idx (-- //i64.width)] - (loop [idx last_idx - digits (..digits [])] + (loop (again [idx last_idx + digits (..digits [])]) (if (//int.< +0 (.int idx)) ("lux text concat" "." (..format digits)) (if (//i64.one? idx input) @@ -434,9 +434,9 @@ (if (and dotted? within_limits?) (case (|> input ..decimals ..text_digits) {.#Some digits} - (loop [digits digits - idx 0 - output 0] + (loop (again [digits digits + idx 0 + output 0]) (if (//nat.< //i64.width idx) (let [power (power_digits idx)] (if (digits#< power digits) diff --git a/stdlib/source/library/lux/math/random.lux b/stdlib/source/library/lux/math/random.lux index c172e5c98..9b6153dfb 100644 --- a/stdlib/source/library/lux/math/random.lux +++ b/stdlib/source/library/lux/math/random.lux @@ -269,7 +269,7 @@ (if (n.> 0 size) (do [! ..monad] [xs (set hash (-- size) value_gen)] - (loop [_ []] + (loop (again [_ []]) (do ! [x value_gen .let [xs+ (set.has x xs)]] @@ -283,7 +283,7 @@ (if (n.> 0 size) (do [! ..monad] [kv (dictionary hash (-- size) key_gen value_gen)] - (loop [_ []] + (loop (again [_ []]) (do ! [k key_gen v value_gen diff --git a/stdlib/source/library/lux/meta.lux b/stdlib/source/library/lux/meta.lux index e349785f3..0ec0b9aaa 100644 --- a/stdlib/source/library/lux/meta.lux +++ b/stdlib/source/library/lux/meta.lux @@ -175,8 +175,8 @@ {try.#Success [_ this_module]} (let [modules (the .#modules lux)] - (loop [module module - name name] + (loop (again [module module + name name]) (do maybe.monad [$module (plist.value module modules) definition (is (Maybe Global) diff --git a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux index 237901cf1..bbfdefdd4 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux @@ -621,9 +621,9 @@ _ (binary.with/4! offset (///signed.value minimum) binary) offset (n.+ (///unsigned.value ..integer_size) offset) _ (binary.with/4! offset (///signed.value maximum) binary)] - (loop [offset (n.+ (///unsigned.value ..integer_size) offset) - afterwards (is (List Big_Jump) - {.#Item at_minimum afterwards})] + (loop (again [offset (n.+ (///unsigned.value ..integer_size) offset) + afterwards (is (List Big_Jump) + {.#Item at_minimum afterwards})]) (case afterwards {.#End} binary @@ -679,8 +679,8 @@ _ (binary.with/4! offset (///signed.value default) binary) offset (n.+ (///unsigned.value ..big_jump_size) offset) _ (binary.with/4! offset amount_of_cases binary)] - (loop [offset (n.+ (///unsigned.value ..integer_size) offset) - cases cases] + (loop (again [offset (n.+ (///unsigned.value ..integer_size) offset) + cases cases]) (case cases {.#End} binary diff --git a/stdlib/source/library/lux/target/jvm/constant/pool.lux b/stdlib/source/library/lux/target/jvm/constant/pool.lux index 11df35740..d8584aaa6 100644 --- a/stdlib/source/library/lux/target/jvm/constant/pool.lux +++ b/stdlib/source/library/lux/target/jvm/constant/pool.lux @@ -92,7 +92,7 @@ [(let [[current pool] ' ] (with_expansions [ (these (again (.++ idx)))] - (loop [idx 0] + (loop (again [idx 0]) (case (sequence.item idx pool) {try.#Success entry} (case entry diff --git a/stdlib/source/library/lux/test.lux b/stdlib/source/library/lux/test.lux index 09b549d09..7e38a497f 100644 --- a/stdlib/source/library/lux/test.lux +++ b/stdlib/source/library/lux/test.lux @@ -323,8 +323,8 @@ (def: (coverage module encoding) (-> Text Text (Set Symbol)) - (loop [remaining encoding - output (set.of_list symbol.hash (list))] + (loop (again [remaining encoding + output (set.of_list symbol.hash (list))]) (case (text.split_by ..coverage_separator remaining) {.#Some [head tail]} (again tail (set.has [module head] output)) diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux index 9f615c86e..f6c30c1cd 100644 --- a/stdlib/source/library/lux/tool/compiler/default/init.lux +++ b/stdlib/source/library/lux/tool/compiler/default/init.lux @@ -245,8 +245,8 @@ [state [source buffer]] (<| (///phase.result' state) (..begin dependencies hash input)) .let [module (the ///.#module input)]] - (loop [iteration (<| (///phase.result' state) - (..iteration wrapper archive expander module source buffer ///syntax.no_aliases))] + (loop (again [iteration (<| (///phase.result' state) + (..iteration wrapper archive expander module source buffer ///syntax.no_aliases))]) (do ! [[state ?source&requirements&temporary_payload] iteration] (case ?source&requirements&temporary_payload diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux index 4f62b38da..bf809bbb5 100644 --- a/stdlib/source/library/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux @@ -711,10 +711,10 @@ (Key document) (Writer document) (///.Compilation state document object) (-> (List ///.Custom) descriptor.Module Lux_Importer module.ID (..Context state) descriptor.Module (..Return state)))) (function (_ customs importer import! @module [archive state] module) - (loop [[archive state] [archive state] - compilation custom_compilation - all_dependencies (is (Set descriptor.Module) - (set.of_list text.hash (list)))] + (loop (again [[archive state] [archive state] + compilation custom_compilation + all_dependencies (is (Set descriptor.Module) + (set.of_list text.hash (list)))]) (do [! (try.with async.monad)] [.let [new_dependencies (the ///.#dependencies compilation) [all_dependencies duplicates] (with_new_dependencies new_dependencies all_dependencies)] @@ -751,10 +751,10 @@ (///.Compilation .Module Any) Lux_Compiler)) (function (_ customs importer import! @module [archive state] module) - (loop [[archive state] [archive (..set_current_module module state)] - compilation compilation - all_dependencies (is (Set descriptor.Module) - (set.of_list text.hash (list)))] + (loop (again [[archive state] [archive (..set_current_module module state)] + compilation compilation + all_dependencies (is (Set descriptor.Module) + (set.of_list text.hash (list)))]) (do [! (try.with async.monad)] [.let [new_dependencies (the ///.#dependencies compilation) [all_dependencies duplicates] (with_new_dependencies new_dependencies all_dependencies)] @@ -820,9 +820,9 @@ compilation_sources (the context.#host_module_extension context) module)] - (loop [customs (for @.old (as (List (///.Custom Fake_State Fake_Document Fake_Object)) - all_customs) - all_customs)] + (loop (again [customs (for @.old (as (List (///.Custom Fake_State Fake_Document Fake_Object)) + all_customs) + all_customs)]) (case customs {.#End} ((..lux_compiler import context platform compilation_sources compiler (compiler input)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux index 24c60d5fa..da220b18f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux @@ -159,9 +159,9 @@ (def: .public (reification analysis) (-> Analysis (Reification Analysis)) - (loop [abstraction analysis - inputs (is (List Analysis) - (list))] + (loop (again [abstraction analysis + inputs (is (List Analysis) + (list))]) (.case abstraction {#Apply input next} (again next {.#Item input inputs}) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux index f7170c8ce..9c5a1c045 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux @@ -371,7 +371,7 @@ (Try [(Maybe Coverage) (List Coverage)])) (function (_ coverageA possibilitiesSF) - (loop [altsSF possibilitiesSF] + (loop (again [altsSF possibilitiesSF]) (case altsSF {.#End} (in [{.#None} (list coverageA)]) @@ -387,8 +387,8 @@ _ (in [{.#Some altMSF} altsSF'])))))))]] - (loop [addition addition - possibilitiesSF (alternatives so_far)] + (loop (again [addition addition + possibilitiesSF (alternatives so_far)]) (do ! [[addition' possibilitiesSF'] (fuse_once addition possibilitiesSF)] (case addition' diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux index 8c6052ed5..4c706598f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux @@ -225,8 +225,8 @@ (template [ ] [(`` (def: .public ( (~~ (template.spliced )) complex) (-> (~~ (template.spliced )) Type (Operation Type)) - (loop [depth 0 - it complex] + (loop (again [depth 0 + it complex]) (case it {.#Named name it} (again depth it) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux index 6902cd718..578cad62c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux @@ -51,8 +51,8 @@ (def: (captured name scope) (-> Text Scope (Maybe [Type Variable])) - (loop [idx 0 - mappings (the [.#captured .#mappings] scope)] + (loop (again [idx 0 + mappings (the [.#captured .#mappings] scope)]) (case mappings {.#Item [_name [_source_type _source_ref]] mappings'} (if (text#= name _name) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux index a35c61eb3..6caf2ffab 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux @@ -89,9 +89,9 @@ ... type-check the input with respect to the patterns. (def: .public (tuple :it:) (-> Type (Check [(List check.Var) Type])) - (loop [envs (is (List (List Type)) - (list)) - :it: :it:] + (loop (again [envs (is (List (List Type)) + (list)) + :it: :it:]) (.case :it: {.#Var id} (do check.monad @@ -165,10 +165,10 @@ [[@ex_var+ :input:'] (/type.check (..tuple :input:))] (.case :input:' {.#Product _} - (let [matches (loop [types (type.flat_tuple :input:') - patterns sub_patterns - output (is (List [Type Code]) - {.#End})] + (let [matches (loop (again [types (type.flat_tuple :input:') + patterns sub_patterns + output (is (List [Type Code]) + {.#End})]) (.case [types patterns] [{.#End} {.#End}] output diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux index 2a8279ae8..fba921765 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux @@ -193,8 +193,8 @@ (<| (let [! ///.monad]) (# ! each (|>> /.tuple)) (is (Operation (List Analysis))) - (loop [membersT+ (type.flat_tuple expectedT) - membersC+ members] + (loop (again [membersT+ (type.flat_tuple expectedT) + membersC+ members]) (case [membersT+ membersC+] [{.#Item memberT {.#End}} {.#Item memberC {.#End}}] (<| (# ! each (|>> list)) @@ -292,9 +292,9 @@ ... canonical form (with their corresponding module identified). (def: .public (normal pattern_matching? record) (-> Bit (List Code) (Operation (Maybe (List [Symbol Code])))) - (loop [input record - output (is (List [Symbol Code]) - {.#End})] + (loop (again [input record + output (is (List [Symbol Code]) + {.#End})]) (case input (pattern (list& [_ {.#Symbol ["" slotH]}] valueH tail)) (if pattern_matching? diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux index ce99c9005..5bdfe1718 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux @@ -57,7 +57,7 @@ (-> Phase Text Text Phase) (do [! ///.monad] [expectedT (///extension.lifted meta.expected_type)] - (loop [expectedT expectedT] + (loop (again [expectedT expectedT]) (/.with_exception ..cannot_analyse [expectedT function_name arg_name body] (case expectedT {.#Function :input: :output:} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux index ea6adec7a..0c301f277 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux @@ -59,9 +59,9 @@ (-> (Phase anchor expression directive) Archive (List Code) (Operation anchor expression directive /.Requirements))) (function (_ state) - (loop [state state - input expansion - output /.no_requirements] + (loop (again [state state + input expansion + output /.no_requirements]) (case input {.#End} {try.#Success [state output]} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux index 49d9df8ca..ce1654cd4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux @@ -993,7 +993,7 @@ [source_class (phase.lifted (reflection!.load class_loader source_name))] (phase.assertion ..cannot_cast [fromT toT fromC] (java/lang/Class::isAssignableFrom source_class target_class)))] - (loop [[current_name currentT] [source_name fromT]] + (loop (again [[current_name currentT] [source_name fromT]]) (if (text#= target_name current_name) (in true) (do ! diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux index 31bc84be0..a018f3ab3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux @@ -213,7 +213,7 @@ (function (_ extension_name phase archive valueC) (do [! ////.monad] [_ (typeA.inference .Macro) - input_type (loop [input_name (symbol .Macro')] + input_type (loop (again [input_name (symbol .Macro')]) (do ! [input_type (///.lifted (meta.definition (symbol .Macro')))] (case input_type diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux index 91d72f959..1ccc58417 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux @@ -832,7 +832,7 @@ hidden [_ {//////synthesis.#Control {//////synthesis.#Branch {//////synthesis.#Case _ path}}}] - (loop [path (is Path path)] + (loop (again [path (is Path path)]) (case path {//////synthesis.#Seq _ next} (again next) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux index 9515ea518..3412ae778 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux @@ -201,8 +201,8 @@ (def: (get patterns @selection) (-> (///complex.Tuple Pattern) Register (List Member)) - (loop [lefts 0 - patterns patterns] + (loop (again [lefts 0 + patterns patterns]) (with_expansions [ (these (list)) (these (again (++ lefts) tail)) @@ -364,9 +364,8 @@ ... Apply this trick to JS, Python et al. (def: .public (storage path) (-> Path Storage) - (loop for_path - [path path - path_storage ..empty] + (loop (for_path [path path + path_storage ..empty]) (case path (^.or {/.#Pop} {/.#Access Access}) @@ -397,9 +396,8 @@ (list#mix for_path path_storage (list left right)) (pattern (/.path/then bodyS)) - (loop for_synthesis - [bodyS bodyS - synthesis_storage path_storage] + (loop (for_synthesis [bodyS bodyS + synthesis_storage path_storage]) (case bodyS (^.or {/.#Simple _} (pattern (/.constant _))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux index e8917d6a8..a8991f643 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux @@ -79,8 +79,8 @@ (def: (body_optimization true_loop? offset scope_environment arity expr) (-> Bit Register (Environment Synthesis) Arity (Transform Synthesis)) - (loop [return? true - expr expr] + (loop (again [return? true + expr expr]) (case expr {/.#Simple _} {.#Some expr} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux index 18ad84ac7..3f5b73842 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux @@ -228,8 +228,8 @@ [(inline: ( parse where offset source_code) (-> (Parser Code) Location Offset Text (Either [Source Text] [Source Code])) - (loop [source (is Source [(!forward 1 where) offset source_code]) - stack (is (List Code) {.#End})] + (loop (again [source (is Source [(!forward 1 where) offset source_code]) + stack (is (List Code) {.#End})]) (case (parse source) {.#Right [source' top]} (again source' {.#Item top stack}) @@ -352,8 +352,8 @@ (inline: (frac_parser source_code//size start where offset source_code) (-> Nat Nat Location Offset Text (Either [Source Text] [Source Code])) - (loop [end offset - exponent (static ..no_exponent)] + (loop (again [end offset + exponent (static ..no_exponent)]) (<| (!with_char+ source_code//size source_code end char/0 ) (!if_digit?+ char/0 (again (!++ end) exponent) @@ -377,7 +377,7 @@ (inline: (signed_parser source_code//size start where offset source_code) (-> Nat Nat Location Offset Text (Either [Source Text] [Source Code])) - (loop [end offset] + (loop (again [end offset]) (<| (!with_char+ source_code//size source_code end char ) (!if_digit?+ char (again (!++ end)) @@ -392,7 +392,7 @@ [(inline: ( source_code//size start where offset source_code) (-> Nat Nat Location Offset Text (Either [Source Text] [Source Code])) - (loop [g!end offset] + (loop (again [g!end offset]) (<| (!with_char+ source_code//size source_code g!end g!char (!number_output source_code start g!end )) (!if_digit?+ g!char (again (!++ g!end)) @@ -418,7 +418,7 @@ (-> Nat Location Offset Text (Either [Source Text] [Source Text])) (let [source_code//size ("lux text size" source_code)] - (loop [end offset] + (loop (again [end offset]) (<| (!with_char+ source_code//size source_code end char ) (!if_symbol_char?|tail char (again (!++ end)) diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux index 90085fc31..1ab3be9eb 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux @@ -212,8 +212,8 @@ (def: .public (necessary_dependencies archive) (-> Archive (Set unit.ID)) (let [[mandatory immediate] (immediate_dependencies archive)] - (loop [pending mandatory - minimum unit.none] + (loop (again [pending mandatory + minimum unit.none]) (case pending {.#Item head tail} (if (set.member? minimum head) diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux index 3bc8ed418..26298275f 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux @@ -114,11 +114,11 @@ (Try [(Document .Module) Bundles Output]))) (do [! try.monad] [[definitions bundles] (is (Try [Definitions Bundles Output]) - (loop [input (sequence.list expected) - definitions (is Definitions - (dictionary.empty text.hash)) - bundles ..empty_bundles - output (is Output sequence.empty)] + (loop (again [input (sequence.list expected) + definitions (is Definitions + (dictionary.empty text.hash)) + bundles ..empty_bundles + output (is Output sequence.empty)]) (let [[analysers synthesizers generators directives] bundles] (case input {.#Item [[[@artifact artifact_category mandatory_artifact?] artifact_dependencies] input']} diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux index 1e27186b1..2de06bf46 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux @@ -179,7 +179,7 @@ (let [chunk (binary.empty ..mebi_byte) chunk_size (.int ..mebi_byte) buffer (java/io/ByteArrayOutputStream::new (ffi.as_int chunk_size))] - (loop [so_far 0] + (loop (again [so_far 0]) (case (ffi.of_int (java/io/InputStream::read chunk (ffi.as_int +0) (ffi.as_int chunk_size) input)) -1 [so_far @@ -193,7 +193,7 @@ (def: (read_jar_entry_with_known_size expected_size input) (-> Nat java/util/jar/JarInputStream [Nat Binary]) (let [buffer (binary.empty expected_size)] - (loop [so_far 0] + (loop (again [so_far 0]) (let [so_far' (|> input (java/io/InputStream::read buffer (ffi.as_int (.int so_far)) (ffi.as_int (.int (n.- so_far expected_size)))) ffi.of_int @@ -219,9 +219,9 @@ (let [input (|> jar java/io/ByteArrayInputStream::new java/util/jar/JarInputStream::new)] - (loop [entries entries - duplicates duplicates - sink sink] + (loop (again [entries entries + duplicates duplicates + sink sink]) (case (java/util/jar/JarInputStream::getNextJarEntry input) {try.#Failure error} {try.#Failure error} diff --git a/stdlib/source/library/lux/tool/interpreter.lux b/stdlib/source/library/lux/tool/interpreter.lux index 580dc9d4e..60f200d18 100644 --- a/stdlib/source/library/lux/tool/interpreter.lux +++ b/stdlib/source/library/lux/tool/interpreter.lux @@ -205,10 +205,10 @@ (! Any))) (do [! Monad] [state (initialize Monad Console platform configuration)] - (loop [context [#configuration configuration - #state state - #source ..fresh_source] - multi_line? #0] + (loop (again [context [#configuration configuration + #state state + #source ..fresh_source] + multi_line? #0]) (do ! [_ (if multi_line? (# Console write " ") diff --git a/stdlib/source/library/lux/type.lux b/stdlib/source/library/lux/type.lux index c3c537701..402e1a2c7 100644 --- a/stdlib/source/library/lux/type.lux +++ b/stdlib/source/library/lux/type.lux @@ -31,8 +31,8 @@ (template [ ] [(def: .public ( type) (-> Type [Nat Type]) - (loop [num_args 0 - type type] + (loop (again [num_args 0 + type type]) (case type { env sub_type} (again (++ num_args) sub_type) diff --git a/stdlib/source/library/lux/type/abstract.lux b/stdlib/source/library/lux/type/abstract.lux index e5eecf50b..7b8290f11 100644 --- a/stdlib/source/library/lux/type/abstract.lux +++ b/stdlib/source/library/lux/type/abstract.lux @@ -48,7 +48,7 @@ {.#End}) (template: (!peek ) - [(loop [entries ] + [(loop (again [entries ]) (case entries {.#Item [head_name head] tail} (if (text#= head_name) @@ -106,7 +106,7 @@ (..peek! {.#Some name})) (template: (!push ) - [(loop [entries ] + [(loop (again [entries ]) (case entries {.#Item [head_name head] tail} (if (text#= head_name) diff --git a/stdlib/source/library/lux/type/check.lux b/stdlib/source/library/lux/type/check.lux index 541134b70..31d604f22 100644 --- a/stdlib/source/library/lux/type/check.lux +++ b/stdlib/source/library/lux/type/check.lux @@ -304,8 +304,8 @@ (def: .public (ring' start) (-> Var (Check (List Var))) (function (_ context) - (loop [current start - output (list start)] + (loop (again [current start + output (list start)]) (case (|> context (the .#var_bindings) (var::get current)) {.#Some {.#Some type}} (case type @@ -704,9 +704,9 @@ [{.#Primitive e_name e_params} {.#Primitive a_name a_params}] (if (!text#= e_name a_name) - (loop [assumptions assumptions - e_params e_params - a_params a_params] + (loop (again [assumptions assumptions + e_params e_params + a_params a_params]) (case [e_params a_params] [{.#End} {.#End}] (check#in assumptions) diff --git a/stdlib/source/library/lux/type/resource.lux b/stdlib/source/library/lux/type/resource.lux index 5ed5a5f7e..d31a7e1dd 100644 --- a/stdlib/source/library/lux/type/resource.lux +++ b/stdlib/source/library/lux/type/resource.lux @@ -109,7 +109,7 @@ (def: indices (Parser (List Nat)) - (.tuple (loop [seen (set.empty n.hash)] + (.tuple (loop (again [seen (set.empty n.hash)]) (do [! <>.monad] [done? .end?] (if done? diff --git a/stdlib/source/library/lux/world/file.lux b/stdlib/source/library/lux/world/file.lux index 2c8db5ea3..c0c76d6de 100644 --- a/stdlib/source/library/lux/world/file.lux +++ b/stdlib/source/library/lux/world/file.lux @@ -696,11 +696,11 @@ (do [! (try.with io.monad)] [self (Dir::open path) children (Dir::children self) - output (loop [input (|> children - (array.list {.#None}) - (list#each (|>> (format path ..ruby_separator)))) - output (is (List ..Path) - (list))] + output (loop (again [input (|> children + (array.list {.#None}) + (list#each (|>> (format path ..ruby_separator)))) + output (is (List ..Path) + (list))]) (case input {.#End} (in output) @@ -813,7 +813,7 @@ ... [(exception: .public ( [file Path]) ... (exception.report ... "Path" file))] - ... + ... [cannot_write_to_file] ... ) @@ -889,13 +889,13 @@ ... [(def: ( _) ... (do [! (try.with io.monad)] ... [children (..scandir [path])] - ... (loop [input (|> children - ... (array.list {.#None}) - ... (list.only (function (_ child) - ... (not (or (text#= "." child) - ... (text#= ".." child)))))) - ... output (is (List ( IO)) - ... (list))] + ... (loop (again [input (|> children + ... (array.list {.#None}) + ... (list.only (function (_ child) + ... (not (or (text#= "." child) + ... (text#= ".." child)))))) + ... output (is (List ( IO)) + ... (list))]) ... (case input ... {.#End} ... (in output) @@ -982,8 +982,8 @@ (def: (retrieve_mock_file! separator path mock) (-> Text Path Mock (Try [Text Mock_File])) - (loop [directory mock - trail (text.all_split_by separator path)] + (loop (again [directory mock + trail (text.all_split_by separator path)]) (case trail {.#Item head tail} (case (dictionary.value head directory) @@ -1006,8 +1006,8 @@ (def: (update_mock_file! / path now content mock) (-> Text Path Instant Binary Mock (Try Mock)) - (loop [directory mock - trail (text.all_split_by / path)] + (loop (again [directory mock + trail (text.all_split_by / path)]) (case trail {.#Item head tail} (case (dictionary.value head directory) @@ -1045,8 +1045,8 @@ (def: (delete_mock_node! / path mock) (-> Text Path Mock (Try Mock)) - (loop [directory mock - trail (text.all_split_by / path)] + (loop (again [directory mock + trail (text.all_split_by / path)]) (case trail {.#Item head tail} (case (dictionary.value head directory) @@ -1093,8 +1093,8 @@ (def: (make_mock_directory! / path mock) (-> Text Path Mock (Try Mock)) - (loop [directory mock - trail (text.all_split_by / path)] + (loop (again [directory mock + trail (text.all_split_by / path)]) (case trail {.#Item head tail} (case (dictionary.value head directory) @@ -1121,8 +1121,8 @@ (def: (retrieve_mock_directory! / path mock) (-> Text Path Mock (Try Mock)) - (loop [directory mock - trail (text.all_split_by / path)] + (loop (again [directory mock + trail (text.all_split_by / path)]) (case trail {.#End} {try.#Success directory} @@ -1306,10 +1306,10 @@ {.#Item head tail} (case head "" (# monad in (exception.except ..cannot_make_directory [path])) - _ (loop [current (if rooted? - (format (# fs separator) head) - head) - next tail] + _ (loop (again [current (if rooted? + (format (# fs separator) head) + head) + next tail]) (do monad [? (..check_or_make_directory monad fs current)] (case ? diff --git a/stdlib/source/library/lux/world/file/watch.lux b/stdlib/source/library/lux/world/file/watch.lux index 4266f170c..eca972ca5 100644 --- a/stdlib/source/library/lux/world/file/watch.lux +++ b/stdlib/source/library/lux/world/file/watch.lux @@ -276,8 +276,8 @@ (def: (default_list list) (All (_ a) (-> (java/util/List a) (List a))) (let [size (.nat (ffi.of_int (java/util/List::size list)))] - (loop [idx 0 - output {.#End}] + (loop (again [idx 0 + output {.#End}]) (if (n.< size idx) (again (++ idx) {.#Item (java/util/List::get (ffi.as_int (.int idx)) list) @@ -374,8 +374,8 @@ (def: (default_poll watcher) (-> java/nio/file/WatchService (IO (Try (List [Concern //.Path])))) - (loop [output (is (List [Concern //.Path]) - (list))] + (loop (again [output (is (List [Concern //.Path]) + (list))]) (do (try.with io.monad) [?key (java/nio/file/WatchService::poll watcher)] (case ?key diff --git a/stdlib/source/library/lux/world/net/http/client.lux b/stdlib/source/library/lux/world/net/http/client.lux index c992f10ac..35c6e9cac 100644 --- a/stdlib/source/library/lux/world/net/http/client.lux +++ b/stdlib/source/library/lux/world/net/http/client.lux @@ -134,7 +134,7 @@ [partial? buffer_size] (let [buffer (binary.empty buffer_size)] (if partial? - (loop [so_far +0] + (loop (again [so_far +0]) (do [! (try.with io.monad)] [.let [remaining (i.- so_far (.int buffer_size))] bytes_read (# ! each (|>> ffi.of_int) @@ -147,8 +147,8 @@ _ (if (i.= remaining bytes_read) (in [buffer_size buffer]) (again (i.+ bytes_read so_far)))))) - (loop [so_far +0 - output (# binary.monoid identity)] + (loop (again [so_far +0 + output (# binary.monoid identity)]) (do [! (try.with io.monad)] [.let [remaining (i.- so_far (.int buffer_size))] bytes_read (# ! each (|>> ffi.of_int) @@ -173,8 +173,8 @@ (def: (default_headers connection) (-> java/net/HttpURLConnection (IO (Try //.Headers))) - (loop [index +0 - headers //.empty] + (loop (again [index +0 + headers //.empty]) (do [! (try.with io.monad)] [?name (java/net/URLConnection::getHeaderFieldKey (ffi.as_int index) connection)] (case ?name diff --git a/stdlib/source/library/lux/world/program.lux b/stdlib/source/library/lux/world/program.lux index 4b0703936..10a2cc7b1 100644 --- a/stdlib/source/library/lux/world/program.lux +++ b/stdlib/source/library/lux/world/program.lux @@ -319,8 +319,8 @@ ... (dictionary.of_list text.hash)))) ... @.scheme (do io.monad ... [input (..get-environment-variables [])] - ... (loop [input input - ... output environment.empty] + ... (loop (again [input input + ... output environment.empty]) ... (if ("scheme object nil?" input) ... (in output) ... (let [entry (..head input)] -- cgit v1.2.3