diff options
author | Eduardo Julian | 2021-07-29 19:23:23 -0400 |
---|---|---|
committer | Eduardo Julian | 2021-07-29 19:23:23 -0400 |
commit | 54b28c1caeda08965c258411a32229be1766d47f (patch) | |
tree | ee0eecd3a009f80e716f2c3c07095bc80d3b70bb /stdlib/source/library/lux/tool/compiler | |
parent | 5d4583aebd00adced10275b32ff1a93ab418be50 (diff) |
Switched from the "from to" convention to the "minimum additional" convention.
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
11 files changed, 46 insertions, 46 deletions
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 f5e65f9bb..8588f52e0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux @@ -356,7 +356,7 @@ (|> members (list\map %analysis) (text.join_with " ") - (text.enclose ["[" "]"]))) + (text.enclosed ["[" "]"]))) (#Reference reference) (reference.format reference) @@ -370,8 +370,8 @@ (format (|> environment (list\map %analysis) (text.join_with " ") - (text.enclose ["[" "]"]))) - (text.enclose ["(" ")"])) + (text.enclosed ["[" "]"]))) + (text.enclosed ["(" ")"])) (#Apply _) (|> analysis @@ -379,14 +379,14 @@ #.Item (list\map %analysis) (text.join_with " ") - (text.enclose ["(" ")"])) + (text.enclosed ["(" ")"])) (#Extension name parameters) (|> parameters (list\map %analysis) (text.join_with " ") (format (%.text name) " ") - (text.enclose ["(" ")"])))) + (text.enclosed ["(" ")"])))) (template [<special> <general>] [(type: #export <special> 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 9a34b72aa..99e1730f1 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 @@ -73,7 +73,7 @@ (#Bit value') (|> value' %.bit - (text.enclose ["(#Bit " ")"])) + (text.enclosed ["(#Bit " ")"])) (#Variant ?max_cases cases) (|> cases @@ -81,9 +81,9 @@ (list\map (function (_ [idx coverage]) (format (%.nat idx) " " (%coverage coverage)))) (text.join_with " ") - (text.enclose ["{" "}"]) + (text.enclosed ["{" "}"]) (format (%.nat (..cases ?max_cases)) " ") - (text.enclose ["(#Variant " ")"])) + (text.enclosed ["(#Variant " ")"])) (#Seq left right) (format "(#Seq " (%coverage left) " " (%coverage right) ")") diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis.lux index a1a979555..93e1c6d1f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis.lux @@ -10,7 +10,7 @@ ["." / #_ ["#." lux]]) -(def: #export (bundle eval host-specific) +(def: #export (bundle eval host_specific) (-> Eval Bundle Bundle) - (dictionary.merge host-specific + (dictionary.merge host_specific (/lux.bundle eval))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux index 9f43c5f28..87c1e59cc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux @@ -125,7 +125,7 @@ ## ## (/.install "/" (binary (product.uncurry _.//2))) ## ## (/.install "%" (binary (product.uncurry _.rem/2))) ## ## (/.install "i64" (unary _.truncate/1)) -## (/.install "encode" (unary _.write-to-string/1)) +## (/.install "encode" (unary _.write_to_string/1)) ## ## (/.install "decode" (unary //runtime.f64//decode)) ## ))) @@ -139,7 +139,7 @@ ## (def: (text//char [index text]) ## (Binary (Expression Any)) -## (_.char-code/1 (_.char/2 [text index]))) +## (_.char_code/1 (_.char/2 [text index]))) (def: text_procs Bundle @@ -156,7 +156,7 @@ ## (def: (io//log! message) ## (Unary (Expression Any)) -## (_.progn (list (_.write-line/1 message) +## (_.progn (list (_.write_line/1 message) ## //runtime.unit))) ## (def: io_procs 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 bbb46cba2..5ceb08bc3 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 @@ -66,5 +66,5 @@ list.enumeration (list\map (|>> product.left (n.+ offset) //case.register)) _.args)]] - (in (_.progn (list (_.multiple-value-setq bindings (_.values/* argsO+)) + (in (_.progn (list (_.multiple_value_setq bindings (_.values/* argsO+)) (_.go tag)))))) 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 20a26e9cb..e1c4dd247 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 @@ -63,7 +63,7 @@ (//////phase\map _.return (/function.function statement expression archive abstraction)) )) -(exception: #export cannot-recur-as-an-expression) +(exception: #export cannot_recur_as_an_expression) (def: (expression archive synthesis) Phase @@ -101,7 +101,7 @@ (/loop.scope ..statement expression archive scope) (^ (synthesis.loop/recur updates)) - (//////phase.except ..cannot-recur-as-an-expression []) + (//////phase.except ..cannot_recur_as_an_expression []) (^ (synthesis.function/abstraction abstraction)) (/function.function ..statement expression archive abstraction) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux index 2fbaa82f3..06ae68255 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux @@ -729,7 +729,6 @@ (_.and (|> value (<top_cmp> top)))))] [within? _.<] - [up_to? _.<=] ) (def: (text_clip start end text) @@ -761,14 +760,13 @@ (..some (i64::of_float (|> idx (_.+ startF)))))) ..none)))) -(runtime: (text::clip text from to) +(runtime: (text::clip text minimum additional) (with_vars [length] ($_ _.then (_.set! length (_.length text)) - (_.if ($_ _.and - (|> to (within? length)) - (|> from (up_to? to))) - (..some (text_clip (inc from) (inc to) text)) + (_.set! to (_.+ additional minimum)) + (_.if (within? length to) + (..some (text_clip (inc minimum) (inc to) text)) ..none)))) (def: (char_at idx text) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/program.lux b/stdlib/source/library/lux/tool/compiler/language/lux/program.lux index 3f988197f..16b59870b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/program.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/program.lux @@ -28,7 +28,7 @@ Text "") -(exception: #export (cannot-find-program {modules (List Module)}) +(exception: #export (cannot_find_program {modules (List Module)}) (exception.report ["Modules" (exception.enumerate %.text modules)])) @@ -43,15 +43,15 @@ [id (archive.id module archive) [descriptor document] (archive.find module archive)] (in [[module id] (get@ #descriptor.registry descriptor)])))))] - (case (list.one (function (_ [[module module-id] registry]) + (case (list.one (function (_ [[module module_id] registry]) (do maybe.monad - [program-id (artifact.remember ..name registry)] - (in [module-id program-id]))) + [program_id (artifact.remember ..name registry)] + (in [module_id program_id]))) registries) - (#.Some program-context) - (in program-context) + (#.Some program_context) + (in program_context) #.None (|> registries (list\map (|>> product.left product.left)) - (exception.except ..cannot-find-program))))) + (exception.except ..cannot_find_program))))) 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 87be39c2a..e304e237c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux @@ -345,7 +345,9 @@ (#.Left [[where <start> <source_code>] error]))) -(def: no_exponent Offset 0) +(def: no_exponent + Offset + 0) (with_expansions [<int_output> (as_is (!number_output source_code start end int.decimal #.Int)) <frac_output> (as_is (!number_output source_code start end frac.decimal #.Frac)) 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 fdfebb72c..8559afe35 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux @@ -280,7 +280,7 @@ (list\map (function (_ [test then]) (format (<format> test) " " (%path' %then then)))) (text.join_with " ") - (text.enclose ["(? " ")"]))]) + (text.enclosed ["(? " ")"]))]) ([#I64_Fork (|>> .int %.int)] [#F64_Fork %.frac] [#Text_Fork %.text]) @@ -314,7 +314,7 @@ (#Then then) (|> (%then then) - (text.enclose ["(! " ")"])))) + (text.enclosed ["(! " ")"])))) (def: #export (%synthesis value) (Format Synthesis) @@ -336,13 +336,13 @@ (#analysis.Variant [lefts right? content]) (|> (%synthesis content) (format (%.nat lefts) " " (%.bit right?) " ") - (text.enclose ["(" ")"])) + (text.enclosed ["(" ")"])) (#analysis.Tuple members) (|> members (list\map %synthesis) (text.join_with " ") - (text.enclose ["[" "]"]))) + (text.enclosed ["[" "]"]))) (#Reference reference) (reference.format reference) @@ -355,36 +355,36 @@ (let [environment' (|> environment (list\map %synthesis) (text.join_with " ") - (text.enclose ["[" "]"]))] + (text.enclosed ["[" "]"]))] (|> (format environment' " " (%.nat arity) " " (%synthesis body)) - (text.enclose ["(#function " ")"]))) + (text.enclosed ["(#function " ")"]))) (#Apply func args) (|> args (list\map %synthesis) (text.join_with " ") (format (%synthesis func) " ") - (text.enclose ["(" ")"]))) + (text.enclosed ["(" ")"]))) (#Branch branch) (case branch (#Let input register body) (|> (format (%.nat register) " " (%synthesis input) " " (%synthesis body)) - (text.enclose ["(#let " ")"])) + (text.enclosed ["(#let " ")"])) (#If test then else) (|> (format (%synthesis test) " " (%synthesis then) " " (%synthesis else)) - (text.enclose ["(#if " ")"])) + (text.enclosed ["(#if " ")"])) (#Get members record) (|> (format (%.list (%path' %synthesis) (list\map (|>> #Member #Access) members)) " " (%synthesis record)) - (text.enclose ["(#get " ")"])) + (text.enclosed ["(#get " ")"])) (#Case input path) (|> (format (%synthesis input) " " (%path' %synthesis path)) - (text.enclose ["(#case " ")"]))) + (text.enclosed ["(#case " ")"]))) (#Loop loop) (case loop @@ -393,21 +393,21 @@ " " (|> (get@ #inits scope) (list\map %synthesis) (text.join_with " ") - (text.enclose ["[" "]"])) + (text.enclosed ["[" "]"])) " " (%synthesis (get@ #iteration scope))) - (text.enclose ["(#loop " ")"])) + (text.enclosed ["(#loop " ")"])) (#Recur args) (|> args (list\map %synthesis) (text.join_with " ") - (text.enclose ["(#recur " ")"])))) + (text.enclosed ["(#recur " ")"])))) (#Extension [name args]) (|> (list\map %synthesis args) (text.join_with " ") (format (%.text name) " ") - (text.enclose ["(" ")"])))) + (text.enclosed ["(" ")"])))) (def: #export %path (Format Path) diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux index 2239960c6..6af912b14 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux @@ -107,7 +107,7 @@ (get@ #descriptor.references) set.to_list (list.all (function (_ module) (dictionary.get module mapping))) - (list\map (|>> ..module_file _.string _.load-relative/1)) + (list\map (|>> ..module_file _.string _.load_relative/1)) (list\fold ..then bundle) (: _.Expression) _.code |