diff options
author | Eduardo Julian | 2022-03-30 21:25:53 -0400 |
---|---|---|
committer | Eduardo Julian | 2022-03-30 21:25:53 -0400 |
commit | 8eb86ed366b2305751f2e831c7a081ffcca82c89 (patch) | |
tree | f8da5967f61d115414b3655dd9045cef370c8d5b /stdlib/source/library | |
parent | 4326d69ab717683449bf37bf8dd170c83455c0c0 (diff) |
De-sigil-ification: /
Diffstat (limited to '')
58 files changed, 327 insertions, 327 deletions
diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux index da0e84a92..bf523ec7c 100644 --- a/stdlib/source/library/lux.lux +++ b/stdlib/source/library/lux.lux @@ -3871,14 +3871,14 @@ temp)) ))) -(def: (zipped/2 xs ys) +(def: (zipped_2 xs ys) (All (_ a b) (-> (List a) (List b) (List [a b]))) (case xs {#Item x xs'} (case ys {#Item y ys'} - (list& [x y] (zipped/2 xs' ys')) + (list& [x y] (zipped_2 xs' ys')) _ (list)) @@ -3934,7 +3934,7 @@ {#None} (in enhanced_target)))) target - (zipped/2 locals members))] + (zipped_2 locals members))] (in (` ({(~ pattern) (~ enhanced_target)} (~ (symbol$ source))))))))) name tags&members body)] (in (list full_body))))) @@ -3986,7 +3986,7 @@ g!output (..generated_symbol "")] (case (interface_methods type) {#Some members} - (let [pattern (|> (zipped/2 tags (enumeration members)) + (let [pattern (|> (zipped_2 tags (enumeration members)) (list#each (is (-> [Symbol [Nat Type]] (List Code)) (function (_ [[r_module r_name] [r_idx r_type]]) (list (symbol$ [r_module r_name]) @@ -4037,7 +4037,7 @@ (is (-> [Nat Symbol Type] (Meta (List Code))) (function (_ [sub_tag_index sname stype]) (open_declaration alias tags' sub_tag_index sname source+ stype))) - (enumeration (zipped/2 tags' members')))] + (enumeration (zipped_2 tags' members')))] (meta#in (list#conjoint decls'))) _ @@ -4060,7 +4060,7 @@ [decls' (monad#each meta_monad (is (-> [Nat Symbol Type] (Meta (List Code))) (function (_ [tag_index sname stype]) (open_declaration alias tags tag_index sname source stype))) - (enumeration (zipped/2 tags members)))] + (enumeration (zipped_2 tags members)))] (meta#in (list#conjoint decls'))) _ @@ -4226,7 +4226,7 @@ (do meta_monad [g!slot (..generated_symbol "")] (meta#in [r_slot_name r_idx g!slot])))) - (zipped/2 tags (enumeration members)))] + (zipped_2 tags (enumeration members)))] (let [pattern (|> pattern' (list#each (is (-> [Symbol Nat Code] (List Code)) (function (_ [r_slot_name r_idx r_var]) @@ -4259,7 +4259,7 @@ (is (-> Code (Meta Code)) (function (_ _) (..generated_symbol "temp"))) slots) - .let [pairs (zipped/2 slots bindings) + .let [pairs (zipped_2 slots bindings) update_expr (list#mix (is (-> [Code Code] Code Code) (function (_ [s b] v) (` (..has (~ s) (~ v) (~ b))))) @@ -4309,7 +4309,7 @@ (do meta_monad [g!slot (..generated_symbol "")] (meta#in [r_slot_name r_idx g!slot])))) - (zipped/2 tags (enumeration members)))] + (zipped_2 tags (enumeration members)))] (let [pattern (|> pattern' (list#each (is (-> [Symbol Nat Code] (List Code)) (function (_ [r_slot_name r_idx r_var]) diff --git a/stdlib/source/library/lux/control/concatenative.lux b/stdlib/source/library/lux/control/concatenative.lux index 0f01c8d9f..3fb95ed21 100644 --- a/stdlib/source/library/lux/control/concatenative.lux +++ b/stdlib/source/library/lux/control/concatenative.lux @@ -141,7 +141,7 @@ [(~ g!stack) ((~ g!func) (~+ g!inputs))]))))))))) (template [<arity>] - [(`` (def: .public (~~ (template.symbol ["apply/" <arity>])) + [(`` (def: .public (~~ (template.symbol ["apply_" <arity>])) (..apply <arity>)))] [1] [2] [3] [4] @@ -283,7 +283,7 @@ (function (_ [[stack a] quote]) [(quote stack) a])) -(def: .public dip/2 +(def: .public dip_2 (All (_ ,,, a b) (=> ,,, [a b (=> ,,, ,,,)] ,,, [a b])) diff --git a/stdlib/source/library/lux/control/function/mutual.lux b/stdlib/source/library/lux/control/function/mutual.lux index 16506a4e3..69f1bdf40 100644 --- a/stdlib/source/library/lux/control/function/mutual.lux +++ b/stdlib/source/library/lux/control/function/mutual.lux @@ -72,7 +72,7 @@ hidden_names (monad.each ! (//.constant (macro.symbol "mutual_function#")) functions) .let [definitions (list#each (..mutual_definition hidden_names g!context) - (list.zipped/2 hidden_names + (list.zipped_2 hidden_names functions)) context_types (list#each (function (_ mutual) (` (-> (~ g!context) (~ (the #type mutual))))) @@ -82,7 +82,7 @@ g!pop (local.push (list#each (function (_ [g!name mutual]) [[here_name (the [#declaration declaration.#name] mutual)] (..macro g!context g!name)]) - (list.zipped/2 hidden_names + (list.zipped_2 hidden_names functions)))] (in (list (` (.let [(~ g!context) (is (Rec (~ g!context) [(~+ context_types)]) @@ -124,7 +124,7 @@ hidden_names (monad.each ! (//.constant (macro.symbol "mutual_function#")) functions) .let [definitions (list#each (..mutual_definition hidden_names g!context) - (list.zipped/2 hidden_names + (list.zipped_2 hidden_names (list#each (the #mutual) functions))) context_types (list#each (function (_ mutual) (` (-> (~ g!context) (~ (the [#mutual #type] mutual))))) @@ -134,7 +134,7 @@ g!pop (local.push (list#each (function (_ [g!name mutual]) [[here_name (the [#mutual #declaration declaration.#name] mutual)] (..macro g!context g!name)]) - (list.zipped/2 hidden_names + (list.zipped_2 hidden_names functions)))] (in (list& (` (.def: (~ g!context) [(~+ (list#each (the [#mutual #type]) functions))] diff --git a/stdlib/source/library/lux/control/parser/binary.lux b/stdlib/source/library/lux/control/parser/binary.lux index 0fc0350d2..a1c565360 100644 --- a/stdlib/source/library/lux/control/parser/binary.lux +++ b/stdlib/source/library/lux/control/parser/binary.lux @@ -69,10 +69,10 @@ (type: .public Size Nat) -(def: .public size/8 Size 1) -(def: .public size/16 Size (n.* 2 size/8)) -(def: .public size/32 Size (n.* 2 size/16)) -(def: .public size/64 Size (n.* 2 size/32)) +(def: .public size_8 Size 1) +(def: .public size_16 Size (n.* 2 size_8)) +(def: .public size_32 Size (n.* 2 size_16)) +(def: .public size_64 Size (n.* 2 size_32)) (template [<name> <size> <read>] [(def: .public <name> @@ -85,14 +85,14 @@ {try.#Failure error} {try.#Failure error})))] - [bits/8 ..size/8 /.bytes/1] - [bits/16 ..size/16 /.bytes/2] - [bits/32 ..size/32 /.bytes/4] - [bits/64 ..size/64 /.bytes/8] + [bits_8 ..size_8 /.bits_8] + [bits_16 ..size_16 /.bits_16] + [bits_32 ..size_32 /.bits_32] + [bits_64 ..size_64 /.bits_64] ) (template [<name> <type>] - [(def: .public <name> (Parser <type>) ..bits/64)] + [(def: .public <name> (Parser <type>) ..bits_64)] [nat Nat] [int Int] @@ -101,7 +101,7 @@ (def: .public frac (Parser Frac) - (//#each frac.of_bits ..bits/64)) + (//#each frac.of_bits ..bits_64)) (exception: .public (invalid_tag [range Nat byte Nat]) @@ -112,7 +112,7 @@ (template: (!variant <case>+) [(do [! //.monad] [flag (is (Parser Nat) - ..bits/8)] + ..bits_8)] (with_expansions [<case>+' (template.spliced <case>+)] (case flag (^.template [<number> <tag> <parser>] @@ -145,7 +145,7 @@ (Parser Bit) (do //.monad [value (is (Parser Nat) - ..bits/8)] + ..bits_8)] (case value 0 (in #0) 1 (in #1) @@ -167,10 +167,10 @@ [size (//#each (|>> .nat) <bits>)] (..segment size))))] - [08 binary/8 ..bits/8] - [16 binary/16 ..bits/16] - [32 binary/32 ..bits/32] - [64 binary/64 ..bits/64] + [08 binary_8 ..bits_8] + [16 binary_16 ..bits_16] + [32 binary_32 ..bits_32] + [64 binary_64 ..bits_64] ) (template [<size> <name> <binary>] @@ -180,13 +180,13 @@ [utf8 <binary>] (//.lifted (# utf8.codec decoded utf8)))))] - [08 utf8/8 ..binary/8] - [16 utf8/16 ..binary/16] - [32 utf8/32 ..binary/32] - [64 utf8/64 ..binary/64] + [08 utf8_8 ..binary_8] + [16 utf8_16 ..binary_16] + [32 utf8_32 ..binary_32] + [64 utf8_64 ..binary_64] ) -(def: .public text ..utf8/64) +(def: .public text ..utf8_64) (template [<size> <name> <bits>] [(def: .public (<name> valueP) @@ -208,10 +208,10 @@ (sequence.suffix value output))) (//#in output)))))] - [08 sequence/8 ..bits/8] - [16 sequence/16 ..bits/16] - [32 sequence/32 ..bits/32] - [64 sequence/64 ..bits/64] + [08 sequence_8 ..bits_8] + [16 sequence_16 ..bits_16] + [32 sequence_32 ..bits_32] + [64 sequence_64 ..bits_64] ) (def: .public maybe diff --git a/stdlib/source/library/lux/data/binary.lux b/stdlib/source/library/lux/data/binary.lux index c65ea01a7..6615131c5 100644 --- a/stdlib/source/library/lux/data/binary.lux +++ b/stdlib/source/library/lux/data/binary.lux @@ -37,7 +37,7 @@ (loop (again [index 0 output init]) (if (n.< size index) - (again (++ index) ($ (/.bytes/1 index it) output)) + (again (++ index) ($ (/.bits_8 index it) output)) output)))) (exception: .public (index_out_of_bounds [size Nat @@ -53,10 +53,10 @@ {try.#Success (<unsafe> index it)} (exception.except ..index_out_of_bounds [(/.size it) index])))] - [bytes/1 /.bytes/1 (|>)] - [bytes/2 /.bytes/2 (n.+ 1)] - [bytes/4 /.bytes/4 (n.+ 3)] - [bytes/8 /.bytes/8 (n.+ 7)] + [bits_8 /.bits_8 (|>)] + [bits_16 /.bits_16 (n.+ 1)] + [bits_32 /.bits_32 (n.+ 3)] + [bits_64 /.bits_64 (n.+ 7)] ) (template [<safe> <unsafe> <shift>] @@ -66,10 +66,10 @@ {try.#Success (<unsafe> index value it)} (exception.except ..index_out_of_bounds [(/.size it) index])))] - [has/1! /.has/1! (|>)] - [has/2! /.has/2! (n.+ 1)] - [has/4! /.has/4! (n.+ 3)] - [has/8! /.has/8! (n.+ 7)] + [has_8! /.has_8! (|>)] + [has_16! /.has_16! (n.+ 1)] + [has_32! /.has_32! (n.+ 3)] + [has_64! /.has_64! (n.+ 7)] ) (implementation: .public equivalence diff --git a/stdlib/source/library/lux/data/collection/list.lux b/stdlib/source/library/lux/data/collection/list.lux index 19d15e35e..48b6e45a1 100644 --- a/stdlib/source/library/lux/data/collection/list.lux +++ b/stdlib/source/library/lux/data/collection/list.lux @@ -491,8 +491,8 @@ _ {.#Left "Wrong syntax for zipped"})) -(def: .public zipped/2 (zipped 2)) -(def: .public zipped/3 (zipped 3)) +(def: .public zipped_2 (zipped 2)) +(def: .public zipped_3 (zipped 3)) (macro: .public (zipped_with tokens state) (case tokens @@ -534,8 +534,8 @@ _ {.#Left "Wrong syntax for zipped_with"})) -(def: .public zipped_with/2 (zipped_with 2)) -(def: .public zipped_with/3 (zipped_with 3)) +(def: .public zipped_with_2 (zipped_with 2)) +(def: .public zipped_with_3 (zipped_with 3)) (def: .public (last xs) (All (_ a) (-> (List a) (Maybe a))) diff --git a/stdlib/source/library/lux/data/format/binary.lux b/stdlib/source/library/lux/data/format/binary.lux index 1d99204b6..3c43cea09 100644 --- a/stdlib/source/library/lux/data/format/binary.lux +++ b/stdlib/source/library/lux/data/format/binary.lux @@ -76,10 +76,10 @@ (<write> offset value) try.trusted)])]))] - [bits/8 /.size/8 binary.has/1!] - [bits/16 /.size/16 binary.has/2!] - [bits/32 /.size/32 binary.has/4!] - [bits/64 /.size/64 binary.has/8!] + [bits_8 /.size_8 binary.has_8!] + [bits_16 /.size_16 binary.has_16!] + [bits_32 /.size_32 binary.has_32!] + [bits_64 /.size_64 binary.has_64!] ) (def: .public (or left right) @@ -92,7 +92,7 @@ [(.++ caseS) (function (_ [offset binary]) (|> binary - (binary.has/1! offset <number>) + (binary.has_8! offset <number>) try.trusted [(.++ offset)] caseT))])]) @@ -116,10 +116,10 @@ (def: .public bit (Writer Bit) - (|>> (pipe.case #0 0 #1 1) ..bits/8)) + (|>> (pipe.case #0 0 #1 1) ..bits_8)) (template [<name> <type>] - [(def: .public <name> (Writer <type>) ..bits/64)] + [(def: .public <name> (Writer <type>) ..bits_64)] [nat Nat] [int Int] @@ -128,7 +128,7 @@ (def: .public frac (Writer Frac) - (|>> frac.bits ..bits/64)) + (|>> frac.bits ..bits_64)) (def: .public (segment size) (-> Nat (Writer Binary)) @@ -158,10 +158,10 @@ [_ (<write> offset size binary)] (binary.copy! size 0 value (n.+ <size> offset) binary)))])]))))] - [binary/8 ..bits/8 /.size/8 binary.has/1!] - [binary/16 ..bits/16 /.size/16 binary.has/2!] - [binary/32 ..bits/32 /.size/32 binary.has/4!] - [binary/64 ..bits/64 /.size/64 binary.has/8!] + [binary_8 ..bits_8 /.size_8 binary.has_8!] + [binary_16 ..bits_16 /.size_16 binary.has_16!] + [binary_32 ..bits_32 /.size_32 binary.has_32!] + [binary_64 ..bits_64 /.size_64 binary.has_64!] ) (template [<name> <binary>] @@ -169,13 +169,13 @@ (Writer Text) (|>> (# utf8.codec encoded) <binary>))] - [utf8/8 ..binary/8] - [utf8/16 ..binary/16] - [utf8/32 ..binary/32] - [utf8/64 ..binary/64] + [utf8_8 ..binary_8] + [utf8_16 ..binary_16] + [utf8_32 ..binary_32] + [utf8_64 ..binary_64] ) -(def: .public text ..utf8/64) +(def: .public text ..utf8_64) (template [<name> <size> <write>] [(def: .public (<name> valueW) @@ -201,10 +201,10 @@ [_ (<write> offset capped_count binary)] (in (mutation [(n.+ <size> offset) binary])))))])))] - [sequence/8 /.size/8 binary.has/1!] - [sequence/16 /.size/16 binary.has/2!] - [sequence/32 /.size/32 binary.has/4!] - [sequence/64 /.size/64 binary.has/8!] + [sequence_8 /.size_8 binary.has_8!] + [sequence_16 /.size_16 binary.has_16!] + [sequence_32 /.size_32 binary.has_32!] + [sequence_64 /.size_64 binary.has_64!] ) (def: .public maybe @@ -240,7 +240,7 @@ [(.++ caseS) (function (_ [offset binary]) (|> binary - (binary.has/1! offset <number>) + (binary.has_8! offset <number>) try.trusted [(.++ offset)] caseT))])]) @@ -275,7 +275,7 @@ [(.++ caseS) (function (_ [offset binary]) (|> binary - (binary.has/1! offset <number>) + (binary.has_8! offset <number>) try.trusted [(.++ offset)] caseT))])]) diff --git a/stdlib/source/library/lux/data/format/css/class.lux b/stdlib/source/library/lux/data/format/css/class.lux index 6d056d1ac..61e71e094 100644 --- a/stdlib/source/library/lux/data/format/css/class.lux +++ b/stdlib/source/library/lux/data/format/css/class.lux @@ -28,6 +28,6 @@ (do meta.monad [module meta.current_module_name class meta.seed] - (in (list (` (..custom (~ (code.text (format "c" (%.nat/16 class) - "_" (%.nat/16 (text#hash module))))))))))) + (in (list (` (..custom (~ (code.text (format "c" (%.nat_16 class) + "_" (%.nat_16 (text#hash module))))))))))) ) diff --git a/stdlib/source/library/lux/data/format/css/id.lux b/stdlib/source/library/lux/data/format/css/id.lux index 1ace95687..c2f821ccb 100644 --- a/stdlib/source/library/lux/data/format/css/id.lux +++ b/stdlib/source/library/lux/data/format/css/id.lux @@ -28,6 +28,6 @@ (do meta.monad [module meta.current_module_name id meta.seed] - (in (list (` (..custom (~ (code.text (format "i" (%.nat/16 id) - "_" (%.nat/16 (text#hash module))))))))))) + (in (list (` (..custom (~ (code.text (format "i" (%.nat_16 id) + "_" (%.nat_16 (text#hash module))))))))))) ) diff --git a/stdlib/source/library/lux/data/format/tar.lux b/stdlib/source/library/lux/data/format/tar.lux index 2f0a2b38a..afea5a3dd 100644 --- a/stdlib/source/library/lux/data/format/tar.lux +++ b/stdlib/source/library/lux/data/format/tar.lux @@ -121,8 +121,8 @@ (def: small_suffix (Parser Any) (do <>.monad - [pre_end <binary>.bits/8 - end <binary>.bits/8 + [pre_end <binary>.bits_8 + end <binary>.bits_8 _ (let [expected (`` (char (~~ (static ..blank))))] (<>.assertion (exception.error ..wrong_character [expected pre_end]) (n.= expected pre_end))) @@ -147,7 +147,7 @@ (do <>.monad [digits (<binary>.segment ..big_size) digits (<>.lifted (# utf8.codec decoded digits)) - end <binary>.bits/8 + end <binary>.bits_8 _ (let [expected (`` (char (~~ (static ..blank))))] (<>.assertion (exception.error ..wrong_character [expected end]) (n.= expected end)))] @@ -237,7 +237,7 @@ (case end 0 {try.#Success (# utf8.codec encoded "")} _ (do try.monad - [last_char (binary.bytes/1 end string)] + [last_char (binary.bits_8 end string)] (`` (case (.nat last_char) (pattern (char (~~ (static ..null)))) (again (-- end)) @@ -283,7 +283,7 @@ (Parser <type>) (do <>.monad [string (<binary>.segment <size>) - end <binary>.bits/8 + end <binary>.bits_8 .let [expected (`` (char (~~ (static ..null))))] _ (<>.assertion (exception.error ..wrong_character [expected end]) (n.= expected end))] @@ -326,7 +326,7 @@ (Parser Magic) (do <>.monad [string (<binary>.segment ..magic_size) - end <binary>.bits/8 + end <binary>.bits_8 .let [expected (`` (char (~~ (static ..null))))] _ (<>.assertion (exception.error ..wrong_character [expected end]) (n.= expected end))] @@ -401,7 +401,7 @@ (def: link_flag_writer (Writer Link_Flag) (|>> representation - format.bits/8)) + format.bits_8)) (with_expansions [<options> (these [0 old_normal] [(char "0") normal] @@ -427,7 +427,7 @@ (def: link_flag_parser (Parser Link_Flag) (do <>.monad - [it <binary>.bits/8] + [it <binary>.bits_8] (case (.nat it) (^.template [<value> <link_flag>] [(pattern <value>) diff --git a/stdlib/source/library/lux/data/format/xml.lux b/stdlib/source/library/lux/data/format/xml.lux index 81fee7699..30e75d6e6 100644 --- a/stdlib/source/library/lux/data/format/xml.lux +++ b/stdlib/source/library/lux/data/format/xml.lux @@ -292,7 +292,7 @@ (# (dictionary.equivalence text.equivalence) = reference/attrs sample/attrs) (n.= (list.size reference/children) (list.size sample/children)) - (|> (list.zipped/2 reference/children sample/children) + (|> (list.zipped_2 reference/children sample/children) (list.every? (product.uncurried =)))) _ diff --git a/stdlib/source/library/lux/data/text.lux b/stdlib/source/library/lux/data/text.lux index e52ca50c0..e5b2ec3ed 100644 --- a/stdlib/source/library/lux/data/text.lux +++ b/stdlib/source/library/lux/data/text.lux @@ -177,7 +177,7 @@ {.#Item input} list.reversed)))) -(def: .public (replaced/1 pattern replacement template) +(def: .public (replaced_once pattern replacement template) (-> Text Text Text Text) (<| (maybe.else template) (do maybe.monad diff --git a/stdlib/source/library/lux/data/text/format.lux b/stdlib/source/library/lux/data/text/format.lux index 8160c9851..ee3f8ddc5 100644 --- a/stdlib/source/library/lux/data/text/format.lux +++ b/stdlib/source/library/lux/data/text/format.lux @@ -1,43 +1,43 @@ (.using - [library - [lux {"-" list nat int rev type symbol} - [abstract - [monad {"+" do}] - [functor - ["[0]" contravariant]]] - [control - ["<>" parser - ["<[0]>" code {"+" Parser}]]] - [data - ["[0]" bit] - ["[0]" text] - [format - ["[0]" xml] - ["[0]" json]] - [collection - ["[0]" list ("[1]#[0]" monad)]]] - ["[0]" time - ["[0]" instant] - ["[0]" duration] - ["[0]" date] - ["[0]" day] - ["[0]" month]] - [math - ["[0]" modular] - [number - ["[0]" nat] - ["[0]" int] - ["[0]" rev] - ["[0]" frac] - ["[0]" ratio]]] - [macro - [syntax {"+" syntax:}] - ["[0]" code] - ["[0]" template]] - [meta - ["[0]" location] - ["[0]" symbol]] - ["[0]" type]]]) + [library + [lux {"-" list nat int rev type symbol} + [abstract + [monad {"+" do}] + [functor + ["[0]" contravariant]]] + [control + ["<>" parser + ["<[0]>" code {"+" Parser}]]] + [data + ["[0]" bit] + ["[0]" text] + [format + ["[0]" xml] + ["[0]" json]] + [collection + ["[0]" list ("[1]#[0]" monad)]]] + ["[0]" time + ["[0]" instant] + ["[0]" duration] + ["[0]" date] + ["[0]" day] + ["[0]" month]] + [math + ["[0]" modular] + [number + ["[0]" nat] + ["[0]" int] + ["[0]" rev] + ["[0]" frac] + ["[0]" ratio]]] + [macro + [syntax {"+" syntax:}] + ["[0]" code] + ["[0]" template]] + [meta + ["[0]" location] + ["[0]" symbol]] + ["[0]" type]]]) (type: .public (Format a) (-> a Text)) @@ -89,25 +89,25 @@ (~~ (template.spliced <format>,<codec>))))] [Nat - [[nat/2 nat.binary] - [nat/8 nat.octal] - [nat/10 nat.decimal] - [nat/16 nat.hex]]] + [[nat_2 nat.binary] + [nat_8 nat.octal] + [nat_10 nat.decimal] + [nat_16 nat.hex]]] [Int - [[int/2 int.binary] - [int/8 int.octal] - [int/10 int.decimal] - [int/16 int.hex]]] + [[int_2 int.binary] + [int_8 int.octal] + [int_10 int.decimal] + [int_16 int.hex]]] [Rev - [[rev/2 rev.binary] - [rev/8 rev.octal] - [rev/10 rev.decimal] - [rev/16 rev.hex]]] + [[rev_2 rev.binary] + [rev_8 rev.octal] + [rev_10 rev.decimal] + [rev_16 rev.hex]]] [Frac - [[frac/2 frac.binary] - [frac/8 frac.octal] - [frac/10 frac.decimal] - [frac/16 frac.hex]]] + [[frac_2 frac.binary] + [frac_8 frac.octal] + [frac_10 frac.decimal] + [frac_16 frac.hex]]] ) (def: .public (mod modular) diff --git a/stdlib/source/library/lux/documentation.lux b/stdlib/source/library/lux/documentation.lux index 8a78ca8e6..a0aa01e82 100644 --- a/stdlib/source/library/lux/documentation.lux +++ b/stdlib/source/library/lux/documentation.lux @@ -341,7 +341,7 @@ _ (|> members - (list.zipped/2 tags) + (list.zipped_2 tags) (list#each (function (_ [t_name type]) (case type {.#Product _} @@ -365,7 +365,7 @@ _ (|> members - (list.zipped/2 tags) + (list.zipped_2 tags) (list#each (function (_ [t_name type]) (format t_name " " (type_definition' false level arity type_function_info {.#None} module type)))) (text.interposed (format \n " ")) @@ -469,9 +469,9 @@ Code (let [c/01 "...." c/04 (format c/01 c/01 c/01 c/01) - c/16 (format c/04 c/04 c/04 c/04)] + c_16 (format c/04 c/04 c/04 c/04)] (code.text (format blank_line - c/16 \n c/16 + c_16 \n c_16 blank_line)))) (type: Example diff --git a/stdlib/source/library/lux/ffi.jvm.lux b/stdlib/source/library/lux/ffi.jvm.lux index 5b5e96a9c..2428f6bb2 100644 --- a/stdlib/source/library/lux/ffi.jvm.lux +++ b/stdlib/source/library/lux/ffi.jvm.lux @@ -477,7 +477,7 @@ (<code>.tuple (<>.exactly (list.size arguments) <code>.any)))))] (in (` ("jvm member invoke constructor" (~ (code.text class_name)) (~+ (|> args - (list.zipped/2 (list#each product.right arguments)) + (list.zipped_2 (list#each product.right arguments)) (list#each ..decorate_input)))))))) (def: (static_method_parser class_name method_name arguments) @@ -489,7 +489,7 @@ (<code>.tuple (<>.exactly (list.size arguments) <code>.any)))))] (in (` ("jvm member invoke static" (~ (code.text class_name)) (~ (code.text method_name)) (~+ (|> args - (list.zipped/2 (list#each product.right arguments)) + (list.zipped_2 (list#each product.right arguments)) (list#each ..decorate_input)))))))) (template [<name> <jvm_op>] @@ -505,7 +505,7 @@ [(~+ (list#each (|>> ..signature code.text) type_vars))] (~ (code.local self_name)) (~+ (|> args - (list.zipped/2 (list#each product.right arguments)) + (list.zipped_2 (list#each product.right arguments)) (list#each ..decorate_input))))))))] [special_method_parser "jvm member invoke special"] @@ -1138,7 +1138,7 @@ ("jvm object cast" (~ (code.local self_name))) (~+ (|> args (list#each (|>> ~ "jvm object cast" `)) - (list.zipped/2 (list#each product.right arguments)) + (list.zipped_2 (list#each product.right arguments)) (list#each ..decorate_input)))))))))] (` ("override" (~ (declaration$ declaration)) @@ -1461,7 +1461,7 @@ (def: (jvm_invoke_inputs mode classes inputs) (-> Primitive_Mode (List (Type Value)) (List [Bit Code]) (List Code)) (|> inputs - (list.zipped/2 classes) + (list.zipped_2 classes) (list#each (function (_ [class [maybe? input]]) (|> (if maybe? (` (.is (.Primitive (~ (code.text (..reflection class)))) @@ -1516,7 +1516,7 @@ (~ (code.text full_name)) [(~+ (list#each ..var$ (the #import_member_tvars commons)))] (~+ (|> (jvm_invoke_inputs (the #import_member_mode commons) input_jvm_types arg_function_inputs) - (list.zipped/2 input_jvm_types) + (list.zipped_2 input_jvm_types) (list#each ..decorate_input)))))] (with_automatic_output_conversion (the #import_member_mode commons)) (with_return_maybe member true classT) @@ -1556,10 +1556,10 @@ [(~+ (list#each ..var$ (the #import_member_tvars commons)))] (~+ (|> object_ast (list#each ..un_quoted) - (list.zipped/2 (list (jvm.class full_name (list)))) + (list.zipped_2 (list (jvm.class full_name (list)))) (list#each (with_automatic_input_conversion (the #import_member_mode commons))))) (~+ (|> (jvm_invoke_inputs (the #import_member_mode commons) input_jvm_types arg_function_inputs) - (list.zipped/2 input_jvm_types) + (list.zipped_2 input_jvm_types) (list#each ..decorate_input)))))) jvm_interop (.is Code (case (jvm.void? method_return) diff --git a/stdlib/source/library/lux/ffi.old.lux b/stdlib/source/library/lux/ffi.old.lux index 0479558f9..ce9e50959 100644 --- a/stdlib/source/library/lux/ffi.old.lux +++ b/stdlib/source/library/lux/ffi.old.lux @@ -1433,7 +1433,7 @@ (if maybe? (` ((~! !!!) (~ (un_quote input)))) (un_quote input)))) - (list.zipped/2 classes) + (list.zipped_2 classes) (list#each (auto_convert_input mode)))) (def: (import_name format class member) diff --git a/stdlib/source/library/lux/macro/pattern.lux b/stdlib/source/library/lux/macro/pattern.lux index 62d829875..d255d9a26 100644 --- a/stdlib/source/library/lux/macro/pattern.lux +++ b/stdlib/source/library/lux/macro/pattern.lux @@ -49,7 +49,7 @@ [symbol$] [tuple$] [monad#mix] - [zipped/2] + [zipped_2] [multi_level_case^] [multi_level_case$] diff --git a/stdlib/source/library/lux/macro/template.lux b/stdlib/source/library/lux/macro/template.lux index f324e2efb..090a25ac4 100644 --- a/stdlib/source/library/lux/macro/template.lux +++ b/stdlib/source/library/lux/macro/template.lux @@ -40,7 +40,7 @@ [g!locals (|> locals (list#each //.symbol) (monad.all !))] - (in (list (` (.with_expansions [(~+ (|> (list.zipped/2 locals g!locals) + (in (list (` (.with_expansions [(~+ (|> (list.zipped_2 locals g!locals) (list#each (function (_ [name symbol]) (list (code.local name) symbol))) list#conjoint))] @@ -137,7 +137,7 @@ inputs_amount (list.size inputs)] (if (nat.= parameters_amount inputs_amount) (.let [environment (is Environment - (|> (list.zipped/2 _#parameters inputs) + (|> (list.zipped_2 _#parameters inputs) (dictionary.of_list text.hash)))] {.#Right [compiler (list#each (..applied environment) _#template)]}) (exception.except ..irregular_arguments [parameters_amount inputs_amount])))))) diff --git a/stdlib/source/library/lux/math/number/complex.lux b/stdlib/source/library/lux/math/number/complex.lux index 470a9bfbf..7f44439d0 100644 --- a/stdlib/source/library/lux/math/number/complex.lux +++ b/stdlib/source/library/lux/math/number/complex.lux @@ -210,7 +210,7 @@ (-> Complex Complex) (let [(open "[0]") subject] [..#real (|> subject ..abs f.log) - ..#imaginary (f.atan/2 #real #imaginary)])) + ..#imaginary (f.atan_2 #real #imaginary)])) (template [<name> <type> <op>] [(def: .public (<name> param input) @@ -225,7 +225,7 @@ (-> Frac Frac Frac) (f.* (f.signum sign) magnitude)) -(def: .public (root/2 input) +(def: .public (root_2 input) (-> Complex Complex) (let [(open "[0]") input t (|> input ..abs (f.+ (f.abs #real)) (f./ +2.0) (f.pow +0.5))] @@ -237,9 +237,9 @@ ..#imaginary (f./ (f.* +2.0 t) #imaginary)]))) -(def: (root/2-1z input) +(def: (root_2-1z input) (-> Complex Complex) - (|> (complex +1.0) (- (* input input)) ..root/2)) + (|> (complex +1.0) (- (* input input)) ..root_2)) (def: .public (reciprocal (open "[0]")) (-> Complex Complex) @@ -259,14 +259,14 @@ (def: .public (acos input) (-> Complex Complex) (|> input - (..+ (|> input ..root/2-1z (..* ..i))) + (..+ (|> input ..root_2-1z (..* ..i))) ..log (..* (..opposite ..i)))) (def: .public (asin input) (-> Complex Complex) (|> input - ..root/2-1z + ..root_2-1z (..+ (..* ..i input)) ..log (..* (..opposite ..i)))) @@ -281,7 +281,7 @@ (def: .public (argument (open "[0]")) (-> Complex Frac) - (f.atan/2 #real #imaginary)) + (f.atan_2 #real #imaginary)) (def: .public (roots nth input) (-> Nat Complex (List Complex)) diff --git a/stdlib/source/library/lux/math/number/frac.lux b/stdlib/source/library/lux/math/number/frac.lux index 77b54b4da..526d16ef4 100644 --- a/stdlib/source/library/lux/math/number/frac.lux +++ b/stdlib/source/library/lux/math/number/frac.lux @@ -54,8 +54,8 @@ [ceil "jvm invokestatic:java.lang.Math:ceil:double"] [floor "jvm invokestatic:java.lang.Math:floor:double"] - [root/2 "jvm invokestatic:java.lang.Math:sqrt:double"] - [root/3 "jvm invokestatic:java.lang.Math:cbrt:double"] + [root_2 "jvm invokestatic:java.lang.Math:sqrt:double"] + [root_3 "jvm invokestatic:java.lang.Math:cbrt:double"] ) (def: .public (pow param subject) (-> Frac Frac Frac) @@ -95,8 +95,8 @@ [ceil "ceil"] [floor "floor"] - [root/2 "sqrt"] - [root/3 "cbrt"] + [root_2 "sqrt"] + [root_3 "cbrt"] ) (def: .public (pow param subject) @@ -127,8 +127,8 @@ [ceil "Math.ceil"] [floor "Math.floor"] - [root/2 "Math.sqrt"] - [root/3 "Math.cbrt"] + [root_2 "Math.sqrt"] + [root_3 "Math.cbrt"] ) (def: .public (pow param subject) @@ -157,14 +157,14 @@ [ceil "ceil"] [floor "floor"] - [root/2 "sqrt"] + [root_2 "sqrt"] ) (def: .public (pow param subject) (-> Frac Frac Frac) (as Frac ("python object do" "pow" ("python import" "math") [subject param]))) - (def: .public (root/3 it) + (def: .public (root_3 it) (-> Frac Frac) (if ("lux f64 <" +0.0 it) (|> it @@ -196,14 +196,14 @@ [ceil "math.ceil"] [floor "math.floor"] - [root/2 "math.sqrt"] + [root_2 "math.sqrt"] ) (def: .public (pow param subject) (-> Frac Frac Frac) ("lua power" param subject)) - (def: .public (root/3 it) + (def: .public (root_3 it) (-> Frac Frac) (if ("lux f64 <" +0.0 it) (|> it @@ -232,8 +232,8 @@ [exp "Math.exp"] [log "Math.log"] - [root/2 "Math.sqrt"] - [root/3 "Math.cbrt"] + [root_2 "Math.sqrt"] + [root_3 "Math.cbrt"] ) (template [<name> <method>] @@ -272,14 +272,14 @@ [ceil "ceil"] [floor "floor"] - [root/2 "sqrt"] + [root_2 "sqrt"] ) (def: .public (pow param subject) (-> Frac Frac Frac) (as Frac ("php apply" ("php constant" "pow") subject param))) - (def: .public root/3 + (def: .public root_3 (-> Frac Frac) (..pow ("lux f64 /" +3.0 +1.0)))) @@ -304,14 +304,14 @@ [ceil "ceiling"] [floor "floor"] - [root/2 "sqrt"] + [root_2 "sqrt"] ) (def: .public (pow param subject) (-> Frac Frac Frac) (as Frac ("scheme apply" ("scheme constant" "expt") subject param))) - (def: .public root/3 + (def: .public root_3 (-> Frac Frac) (..pow ("lux f64 /" +3.0 +1.0)))) ) @@ -329,7 +329,7 @@ ... else floored))) -(def: .public (atan/2 x y) +(def: .public (atan_2 x y) (-> Frac Frac Frac) (cond ("lux f64 <" x +0.0) (..atan ("lux f64 /" x y)) diff --git a/stdlib/source/library/lux/math/number/i64.lux b/stdlib/source/library/lux/math/number/i64.lux index 927765984..299e192e2 100644 --- a/stdlib/source/library/lux/math/number/i64.lux +++ b/stdlib/source/library/lux/math/number/i64.lux @@ -165,18 +165,18 @@ (..or (..right_shifted size (..and high value)) (..left_shifted size (..and low value))))))) - swap/01 (swapper 0) - swap/02 (swapper 1) - swap/04 (swapper 2) - swap/08 (swapper 3) - swap/16 (swapper 4) - swap/32 (swapper 5)] - (|>> swap/32 - swap/16 - swap/08 - swap/04 - swap/02 - swap/01))) + swap_01 (swapper 0) + swap_02 (swapper 1) + swap_04 (swapper 2) + swap_08 (swapper 3) + swap_16 (swapper 4) + swap_32 (swapper 5)] + (|>> swap_32 + swap_16 + swap_08 + swap_04 + swap_02 + swap_01))) (type: .public (Sub size) (Interface diff --git a/stdlib/source/library/lux/target/common_lisp.lux b/stdlib/source/library/lux/target/common_lisp.lux index 15d35df29..c868a0781 100644 --- a/stdlib/source/library/lux/target/common_lisp.lux +++ b/stdlib/source/library/lux/target/common_lisp.lux @@ -114,7 +114,7 @@ ... else (.let [raw (%.frac value)] (.if (text.contains? "E" raw) - (text.replaced/1 "E" "d" raw) + (text.replaced_once "E" "d" raw) (format raw "d0")))))) (def: safe diff --git a/stdlib/source/library/lux/target/js.lux b/stdlib/source/library/lux/target/js.lux index d101afd55..d2b802d2f 100644 --- a/stdlib/source/library/lux/target/js.lux +++ b/stdlib/source/library/lux/target/js.lux @@ -139,7 +139,7 @@ (-> Text Expression Access) (abstraction (format (representation object) "." field))) - (def: .public (apply/* function inputs) + (def: .public (apply_* function inputs) (-> Expression (List Expression) Computation) (|> inputs (list#each ..code) @@ -150,7 +150,7 @@ (def: .public (do method inputs object) (-> Text (List Expression) Expression Computation) - (apply/* (..the method object) inputs)) + (apply_* (..the method object) inputs)) (def: .public object (-> (List [Text Expression]) Computation) @@ -428,19 +428,19 @@ [(`` (def: .public (<apply> function) (-> Expression (~~ (template.spliced <type>+)) Computation) (.function (_ (~~ (template.spliced <arg>+))) - (..apply/* function (list (~~ (template.spliced <arg>+))))))) + (..apply_* function (list (~~ (template.spliced <arg>+))))))) (`` (template [<definition> <function>] [(def: .public <definition> (<apply> (..var <function>)))] (~~ (template.spliced <function>+))))] - [apply/1 [_0] [Expression] + [apply_1 [_0] [Expression] [[not_a_number? "isNaN"]]] - [apply/2 [_0 _1] [Expression Expression] + [apply_2 [_0 _1] [Expression Expression] []] - [apply/3 [_0 _1 _2] [Expression Expression Expression] + [apply_3 [_0 _1 _2] [Expression Expression Expression] []] ) diff --git a/stdlib/source/library/lux/target/jvm/attribute/code.lux b/stdlib/source/library/lux/target/jvm/attribute/code.lux index f7619a587..9916f97b0 100644 --- a/stdlib/source/library/lux/target/jvm/attribute/code.lux +++ b/stdlib/source/library/lux/target/jvm/attribute/code.lux @@ -73,11 +73,11 @@ (///limit.writer (the #limit code)) ... u4 code_length; ... u1 code[code_length]; - (binaryF.binary/32 (the #code code)) + (binaryF.binary_32 (the #code code)) ... u2 exception_table_length; ... exception_table[exception_table_length]; - ((binaryF.sequence/16 /exception.writer) (the #exception_table code)) + ((binaryF.sequence_16 /exception.writer) (the #exception_table code)) ... u2 attributes_count; ... attribute_info attributes[attributes_count]; - ((binaryF.sequence/16 writer) (the #attributes code)) + ((binaryF.sequence_16 writer) (the #attributes code)) )) diff --git a/stdlib/source/library/lux/target/jvm/bytecode.lux b/stdlib/source/library/lux/target/jvm/bytecode.lux index 59dbcc697..1c5a85731 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode.lux @@ -1005,7 +1005,7 @@ (<| (try|do >default (try#each ..big_jump (..jump @from @default))) (try|do >cases (|> @cases (monad.each try.monad (|>> (..jump @from) (try#each ..big_jump))) - (try#each (|>> (list.zipped/2 (list#each product.left cases)))))) + (try#each (|>> (list.zipped_2 (list#each product.left cases)))))) (try|in [..no_exceptions (bytecode >default >cases)])) ... {.#None} diff --git a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux index d6717d8a9..379adfd35 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux @@ -79,7 +79,7 @@ (function (_ [offset binary]) [(n.+ (///unsigned.value ..opcode_size) offset) - (binary.has/1! offset opcode binary)])) + (binary.has_8! offset opcode binary)])) (def: nullary [Estimator (-> Opcode Instruction)] @@ -108,7 +108,7 @@ (function (_ [offset binary]) [(n.+ (///unsigned.value <shift>) offset) (|> binary - (binary.has/1! offset opcode) + (binary.has_8! offset opcode) (<writer> (n.+ (///unsigned.value ..opcode_size) offset) (<unwrap> input0)))])) @@ -119,10 +119,10 @@ [(n.+ (///unsigned.value <shift>) size) (|>> mutation ((<private> opcode input0)))])]))] - [..size/1 unary/1 U1 binary.has/1! ///unsigned.value] - [..size/2 unary/2 U2 binary.has/2! ///unsigned.value] - [..size/2 jump/2 Jump binary.has/2! ///signed.value] - [..size/4 jump/4 Big_Jump binary.has/4! ///signed.value] + [..size/1 unary/1 U1 binary.has_8! ///unsigned.value] + [..size/2 unary/2 U2 binary.has_16! ///unsigned.value] + [..size/2 jump/2 Jump binary.has_16! ///signed.value] + [..size/4 jump/4 Big_Jump binary.has_32! ///signed.value] ) (template [<shift> <name> <inputT> <writer>] @@ -132,7 +132,7 @@ (function (_ [offset binary]) [(n.+ (///unsigned.value <shift>) offset) (|> binary - (binary.has/1! offset opcode) + (binary.has_8! offset opcode) (<writer> (n.+ (///unsigned.value ..opcode_size) offset) (///signed.value input0)))])) @@ -143,8 +143,8 @@ [(n.+ (///unsigned.value <shift>) size) (|>> mutation ((<private> opcode input0)))])]))] - [..size/1 unary/1' S1 binary.has/1!] - [..size/2 unary/2' S2 binary.has/2!] + [..size/1 unary/1' S1 binary.has_8!] + [..size/2 unary/2' S2 binary.has_16!] ) (def: size/11 @@ -158,10 +158,10 @@ (function (_ [offset binary]) [(n.+ (///unsigned.value ..size/11) offset) (|> binary - (binary.has/1! offset opcode) - (binary.has/1! (n.+ (///unsigned.value ..opcode_size) offset) + (binary.has_8! offset opcode) + (binary.has_8! (n.+ (///unsigned.value ..opcode_size) offset) (///unsigned.value input0)) - (binary.has/1! (n.+ (///unsigned.value ..size/1) offset) + (binary.has_8! (n.+ (///unsigned.value ..size/1) offset) (///unsigned.value input1)))])) (def: binary/11 @@ -182,10 +182,10 @@ (function (_ [offset binary]) [(n.+ (///unsigned.value ..size/21) offset) (|> binary - (binary.has/1! offset opcode) - (binary.has/2! (n.+ (///unsigned.value ..opcode_size) offset) - (///unsigned.value input0)) - (binary.has/1! (n.+ (///unsigned.value ..size/2) offset) + (binary.has_8! offset opcode) + (binary.has_16! (n.+ (///unsigned.value ..opcode_size) offset) + (///unsigned.value input0)) + (binary.has_8! (n.+ (///unsigned.value ..size/2) offset) (///unsigned.value input1)))])) (def: binary/21 @@ -207,12 +207,12 @@ (function (_ [offset binary]) [(n.+ (///unsigned.value ..size/211) offset) (|> binary - (binary.has/1! offset opcode) - (binary.has/2! (n.+ (///unsigned.value ..opcode_size) offset) - (///unsigned.value input0)) - (binary.has/1! (n.+ (///unsigned.value ..size/2) offset) + (binary.has_8! offset opcode) + (binary.has_16! (n.+ (///unsigned.value ..opcode_size) offset) + (///unsigned.value input0)) + (binary.has_8! (n.+ (///unsigned.value ..size/2) offset) (///unsigned.value input1)) - (binary.has/1! (n.+ (///unsigned.value ..size/21) offset) + (binary.has_8! (n.+ (///unsigned.value ..size/21) offset) (///unsigned.value input2)))])) (def: trinary/211 @@ -606,21 +606,21 @@ (do [! try.monad] [amount_of_afterwards (|> amount_of_afterwards .int ///signed.s4) maximum (///signed.+/4 minimum amount_of_afterwards)] - (in (let [_ (binary.has/1! offset (hex "AA") binary) + (in (let [_ (binary.has_8! offset (hex "AA") binary) offset (n.+ (///unsigned.value ..opcode_size) offset) _ (case padding 3 (|> binary - (binary.has/1! offset 0) - (binary.has/2! (++ offset) 0)) - 2 (binary.has/2! offset 0 binary) - 1 (binary.has/1! offset 0 binary) + (binary.has_8! offset 0) + (binary.has_16! (++ offset) 0)) + 2 (binary.has_16! offset 0 binary) + 1 (binary.has_8! offset 0 binary) _ binary) offset (n.+ padding offset) - _ (binary.has/4! offset (///signed.value default) binary) + _ (binary.has_32! offset (///signed.value default) binary) offset (n.+ (///unsigned.value ..big_jump_size) offset) - _ (binary.has/4! offset (///signed.value minimum) binary) + _ (binary.has_32! offset (///signed.value minimum) binary) offset (n.+ (///unsigned.value ..integer_size) offset) - _ (binary.has/4! offset (///signed.value maximum) binary)] + _ (binary.has_32! offset (///signed.value maximum) binary)] (loop (again [offset (n.+ (///unsigned.value ..integer_size) offset) afterwards (is (List Big_Jump) {.#Item at_minimum afterwards})]) @@ -630,7 +630,7 @@ {.#Item head tail} (exec - (binary.has/4! offset (///signed.value head) binary) + (binary.has_32! offset (///signed.value head) binary) (again (n.+ (///unsigned.value ..big_jump_size) offset) tail))))))))]))] [(n.+ tableswitch_size @@ -666,19 +666,19 @@ lookupswitch_mutation (is Mutation (function (_ [offset binary]) [(n.+ lookupswitch_size offset) - (let [_ (binary.has/1! offset (hex "AB") binary) + (let [_ (binary.has_8! offset (hex "AB") binary) offset (n.+ (///unsigned.value ..opcode_size) offset) _ (case padding 3 (|> binary - (binary.has/1! offset 0) - (binary.has/2! (++ offset) 0)) - 2 (binary.has/2! offset 0 binary) - 1 (binary.has/1! offset 0 binary) + (binary.has_8! offset 0) + (binary.has_16! (++ offset) 0)) + 2 (binary.has_16! offset 0 binary) + 1 (binary.has_8! offset 0 binary) _ binary) offset (n.+ padding offset) - _ (binary.has/4! offset (///signed.value default) binary) + _ (binary.has_32! offset (///signed.value default) binary) offset (n.+ (///unsigned.value ..big_jump_size) offset) - _ (binary.has/4! offset amount_of_cases binary)] + _ (binary.has_32! offset amount_of_cases binary)] (loop (again [offset (n.+ (///unsigned.value ..integer_size) offset) cases cases]) (case cases @@ -687,8 +687,8 @@ {.#Item [value jump] tail} (exec - (binary.has/4! offset (///signed.value value) binary) - (binary.has/4! (n.+ (///unsigned.value ..integer_size) offset) (///signed.value jump) binary) + (binary.has_32! offset (///signed.value value) binary) + (binary.has_32! (n.+ (///unsigned.value ..integer_size) offset) (///signed.value jump) binary) (again (n.+ case_size offset) tail)))))]))] [(n.+ lookupswitch_size diff --git a/stdlib/source/library/lux/target/jvm/class.lux b/stdlib/source/library/lux/target/jvm/class.lux index 4d2cf203c..8447c56de 100644 --- a/stdlib/source/library/lux/target/jvm/class.lux +++ b/stdlib/source/library/lux/target/jvm/class.lux @@ -140,7 +140,7 @@ [//index.writer #this] [//index.writer #super])) (~~ (template [<writer> <slot>] - [((binaryF.sequence/16 <writer>) (the <slot> class))] + [((binaryF.sequence_16 <writer>) (the <slot> class))] [//index.writer #interfaces] [//field.writer #fields] diff --git a/stdlib/source/library/lux/target/jvm/constant.lux b/stdlib/source/library/lux/target/jvm/constant.lux index edd68d05b..c32ca731c 100644 --- a/stdlib/source/library/lux/target/jvm/constant.lux +++ b/stdlib/source/library/lux/target/jvm/constant.lux @@ -38,7 +38,7 @@ (def: utf8_writer (Writer UTF8) - binaryF.utf8/16) + binaryF.utf8_16) (abstract: .public Class (Index UTF8) @@ -119,10 +119,10 @@ (~~ (template.spliced <write>)) (~~ (template.spliced <writer>)))))] - [integer_writer Integer [] [binaryF.bits/32]] - [float_writer Float [java/lang/Float::floatToRawIntBits ffi.of_int .i64] [i32.i32 binaryF.bits/32]] - [long_writer Long [] [binaryF.bits/64]] - [double_writer Double [java/lang/Double::doubleToRawLongBits ffi.of_long] [binaryF.bits/64]] + [integer_writer Integer [] [binaryF.bits_32]] + [float_writer Float [java/lang/Float::floatToRawIntBits ffi.of_int .i64] [i32.i32 binaryF.bits_32]] + [long_writer Long [] [binaryF.bits_64]] + [double_writer Double [java/lang/Double::doubleToRawLongBits ffi.of_long] [binaryF.bits_64]] [string_writer String [] [//index.writer]] ) ) diff --git a/stdlib/source/library/lux/target/jvm/constant/pool.lux b/stdlib/source/library/lux/target/jvm/constant/pool.lux index d8584aaa6..12e6609e3 100644 --- a/stdlib/source/library/lux/target/jvm/constant/pool.lux +++ b/stdlib/source/library/lux/target/jvm/constant/pool.lux @@ -202,7 +202,7 @@ (function (_ [next pool]) (sequence#mix (function (_ [_index post] pre) (specification#composite pre (//.writer post))) - (format.bits/16 (!index next)) + (format.bits_16 (!index next)) pool))) (def: .public empty diff --git a/stdlib/source/library/lux/target/jvm/encoding/signed.lux b/stdlib/source/library/lux/target/jvm/encoding/signed.lux index 981d8c3f7..160141e3b 100644 --- a/stdlib/source/library/lux/target/jvm/encoding/signed.lux +++ b/stdlib/source/library/lux/target/jvm/encoding/signed.lux @@ -105,8 +105,8 @@ (Writer <type>) (|>> representation <writer>))] - [writer/1 S1 format.bits/8] - [writer/2 S2 format.bits/16] - [writer/4 S4 format.bits/32] + [writer/1 S1 format.bits_8] + [writer/2 S2 format.bits_16] + [writer/4 S4 format.bits_32] ) ) diff --git a/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux b/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux index d733b0480..0282dd0b2 100644 --- a/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux +++ b/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux @@ -114,8 +114,8 @@ (Writer <type>) (|>> representation <writer>))] - [writer/1 U1 format.bits/8] - [writer/2 U2 format.bits/16] - [writer/4 U4 format.bits/32] + [writer/1 U1 format.bits_8] + [writer/2 U2 format.bits_16] + [writer/4 U4 format.bits_32] ) ) diff --git a/stdlib/source/library/lux/target/jvm/field.lux b/stdlib/source/library/lux/target/jvm/field.lux index ab2ef722c..5db3ac6b0 100644 --- a/stdlib/source/library/lux/target/jvm/field.lux +++ b/stdlib/source/library/lux/target/jvm/field.lux @@ -57,7 +57,7 @@ [modifier.writer #modifier] [//index.writer #name] [//index.writer #descriptor] - [(binaryF.sequence/16 //attribute.writer) #attributes])) + [(binaryF.sequence_16 //attribute.writer) #attributes])) ))) (def: .public (field modifier name with_signature? type attributes) diff --git a/stdlib/source/library/lux/target/jvm/method.lux b/stdlib/source/library/lux/target/jvm/method.lux index 264e6d475..be590f849 100644 --- a/stdlib/source/library/lux/target/jvm/method.lux +++ b/stdlib/source/library/lux/target/jvm/method.lux @@ -105,5 +105,5 @@ [//modifier.writer #modifier] [//index.writer #name] [//index.writer #descriptor] - [(format.sequence/16 //attribute.writer) #attributes])) + [(format.sequence_16 //attribute.writer) #attributes])) ))) diff --git a/stdlib/source/library/lux/target/jvm/reflection.lux b/stdlib/source/library/lux/target/jvm/reflection.lux index 44c4bda89..55b6a4185 100644 --- a/stdlib/source/library/lux/target/jvm/reflection.lux +++ b/stdlib/source/library/lux/target/jvm/reflection.lux @@ -304,7 +304,7 @@ (if (text#= class_name name) (if (n.= num_class_params num_type_params) (|> params - (list.zipped/2 (list#each (|>> java/lang/reflect/TypeVariable::getName) + (list.zipped_2 (list#each (|>> java/lang/reflect/TypeVariable::getName) class_params)) (list#mix (function (_ [name paramT] mapping) (dictionary.has name paramT mapping)) diff --git a/stdlib/source/library/lux/test.lux b/stdlib/source/library/lux/test.lux index 7e38a497f..2ac3daa16 100644 --- a/stdlib/source/library/lux/test.lux +++ b/stdlib/source/library/lux/test.lux @@ -213,7 +213,7 @@ "100%" (let [raw (|> done_percent %.frac - (text.replaced/1 "+" ""))] + (text.replaced_once "+" ""))] (|> raw (text.clip 0 (if (f.< +10.0 done_percent) 4 ... X.XX 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 9c5a1c045..ccb3e06ed 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 @@ -113,7 +113,7 @@ (and (n.= (list.size flatR) (list.size flatS)) (list.every? (function (_ [coverageR coverageS]) (= coverageR coverageS)) - (list.zipped/2 flatR flatS)))) + (list.zipped_2 flatR flatS)))) _ #0))) 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 fba921765..fdb485bbd 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 @@ -339,7 +339,7 @@ (in []) (/.except ..record_size_mismatch [size_ts size_record recordT record])) .let [tuple_range (list.indices size_ts) - tag->idx (dictionary.of_list symbol.hash (list.zipped/2 slot_set tuple_range))] + tag->idx (dictionary.of_list symbol.hash (list.zipped_2 slot_set tuple_range))] idx->val (monad.mix ! (function (_ [key val] idx->val) (do ! 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 ce1654cd4..95915309c 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 @@ -1192,7 +1192,7 @@ (list.size parameters)) (list.every? (function (_ [expectedJC actualJC]) (jvm#= expectedJC (de_aliased aliasing actualJC))) - (list.zipped/2 parameters inputsJT)))]] + (list.zipped_2 parameters inputsJT)))]] (in (and correct_class? correct_method? same_static? @@ -1210,7 +1210,7 @@ (n.= (list.size inputsJT) (list.size parameters)) (list.every? (function (_ [expectedJC actualJC]) (jvm#= expectedJC (de_aliased aliasing actualJC))) - (list.zipped/2 parameters inputsJT)))))) + (list.zipped_2 parameters inputsJT)))))) (def: index_parameter (-> Nat .Type) @@ -1369,7 +1369,7 @@ (def: (aliasing expected actual) (-> (List (Type Var)) (List (Type Var)) Aliasing) - (|> (list.zipped/2 (list#each parser.name actual) + (|> (list.zipped_2 (list#each parser.name actual) (list#each parser.name expected)) (dictionary.of_list text.hash))) @@ -1488,7 +1488,7 @@ (def: (decorate_inputs typesT inputsA) (-> (List (Type Value)) (List Analysis) (List Analysis)) (|> inputsA - (list.zipped/2 (list#each (|>> ..signature /////analysis.text) typesT)) + (list.zipped_2 (list#each (|>> ..signature /////analysis.text) typesT)) (list#each (function (_ [type value]) (/////analysis.tuple (list type value)))))) @@ -2169,7 +2169,7 @@ phase.lifted)] (|> super_parameters (monad.each ! (..reflection_type mapping)) - (# ! each (|>> (list.zipped/2 parent_parameters))))) + (# ! each (|>> (list.zipped_2 parent_parameters))))) (phase.lifted (exception.except ..mismatched_super_parameters [parent_name expected_count actual_count])))) {.#None} @@ -2301,7 +2301,7 @@ _ (phase.assertion ..class_parameter_mismatch [name class expected_parameters actual_parameters] (n.= (list.size expected_parameters) (list.size actual_parameters)))] - (in (|> (list.zipped/2 expected_parameters actual_parameters) + (in (|> (list.zipped_2 expected_parameters actual_parameters) (list#mix (function (_ [expected actual] mapping) (case (parser.var? actual) {.#Some actual} 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 a018f3ab3..d2f911155 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 @@ -60,7 +60,7 @@ (function (_ [argT argC]) (<| (typeA.expecting argT) (analyse archive argC))) - (list.zipped/2 inputsT+ args))] + (list.zipped_2 inputsT+ args))] (in {////analysis.#Extension extension_name argsA})) (////analysis.except ///.incorrect_arity [extension_name num_expected num_actual])))))) 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 121fd29fa..c8c48451e 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 @@ -67,7 +67,7 @@ (def: f64//decode (Unary Expression) (|>> list - (_.apply/* (_.var "parseFloat")) + (_.apply_* (_.var "parseFloat")) _.return (_.closure (list)) //runtime.lux//try)) @@ -76,7 +76,7 @@ (Unary Expression) (|>> //runtime.i64##number (list) - (_.apply/* (_.var "String.fromCharCode")))) + (_.apply_* (_.var "String.fromCharCode")))) ... [[Text]] (def: (text//concat [leftG rightG]) @@ -167,7 +167,7 @@ (in [(list#each (|>> .int _.int) chars) branch!]))) conditionals))] - ... (in (_.apply/* (_.closure (list) + ... (in (_.apply_* (_.closure (list) ... (_.switch (_.the //runtime.i64_low_field inputG) ... conditionals! ... {.#Some (_.return else!)})) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux index 77908df35..f3305a2d5 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux @@ -124,7 +124,7 @@ (do [! ////////phase.monad] [abstractionG (phase archive abstractionS) inputsG (monad.each ! (phase archive) inputsS)] - (in (_.apply/* abstractionG inputsG))))])) + (in (_.apply_* abstractionG inputsG))))])) (def: js::function (custom @@ -142,9 +142,9 @@ ($_ _.then (_.define g!abstraction abstractionG) (_.return (case (.nat arity) - 0 (_.apply/1 g!abstraction //runtime.unit) - 1 (_.apply/* g!abstraction g!inputs) - _ (_.apply/1 g!abstraction (_.array g!inputs)))))))))])) + 0 (_.apply_1 g!abstraction //runtime.unit) + 1 (_.apply_* g!abstraction g!inputs) + _ (_.apply_1 g!abstraction (_.array g!inputs)))))))))])) (def: .public bundle Bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux index f98ce4c6f..4fc1e5427 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux @@ -92,7 +92,7 @@ (do [! meta.monad] [ids (monad.all ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars - (list.zipped/2 ids) + (list.zipped_2 ids) (list#each (function (_ [id var]) (list (code.local var) (` (_.var (~ (code.text (format "v" (%.nat id))))))))) 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 4c3e03ca3..1573a17e5 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 @@ -63,7 +63,7 @@ [valueO (expression archive valueS) bodyO (expression archive bodyS)] ... TODO: Find some way to do 'let' without paying the price of the closure. - (in (_.apply/* (_.closure (list (..register register)) + (in (_.apply_* (_.closure (list (..register register)) (_.return bodyO)) (list valueO))))) @@ -342,4 +342,4 @@ (-> Phase! (Generator [Synthesis Path])) (do ///////phase.monad [pattern_matching! (..case! statement expression archive [valueS pathP])] - (in (_.apply/* (_.closure (list) pattern_matching!) (list))))) + (in (_.apply_* (_.closure (list) pattern_matching!) (list))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux index 06f2a1884..39fdda23a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux @@ -38,7 +38,7 @@ (do [! ///////phase.monad] [functionO (expression archive functionS) argsO+ (monad.each ! (expression archive) argsS+)] - (in (_.apply/* functionO argsO+)))) + (in (_.apply_* functionO argsO+)))) (def: capture (-> Register Var) @@ -56,7 +56,7 @@ (|> (list.enumeration inits) (list#each (|>> product.left ..capture))) (_.return (_.function @self (list) body!))) - (_.apply/* @self inits)])) + (_.apply_* @self inits)])) (def: @curried (_.var "curried")) 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 c18131d4c..5321ca9f8 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 @@ -93,7 +93,7 @@ _ (do [! ///////phase.monad] [loop! (scope! statement expression archive [start initsS+ bodyS])] - (in (_.apply/* (_.closure (list) loop!) (list)))))) + (in (_.apply_* (_.closure (list) loop!) (list)))))) (def: @temp (_.var "lux_again_values")) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux index af22a192b..36db99857 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux @@ -86,7 +86,7 @@ (do [! meta.monad] [ids (monad.all ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars - (list.zipped/2 ids) + (list.zipped_2 ids) (list#each (function (_ [id var]) (list (code.local var) (` (_.var (~ (code.text (format "v" (%.nat id))))))))) @@ -118,7 +118,7 @@ inputs_typesC (list#each (function.constant (` _.Expression)) inputs)] (in (list (` (def: .public ((~ g!name) (~+ inputsC)) (-> (~+ inputs_typesC) Computation) - (_.apply/* (~ runtime_name) (list (~+ inputsC))))) + (_.apply_* (~ runtime_name) (list (~+ inputsC))))) (` (def: (~ (code.local (format "@" name))) Statement @@ -241,7 +241,7 @@ (runtime: (lux//try op) (with_vars [ex] - (_.try (_.return (..right (_.apply/1 op ..unit))) + (_.try (_.return (..right (_.apply_1 op ..unit))) [ex (_.return (..left (|> ex (_.do "toString" (list)))))]))) (runtime: (lux//program_args inputs) @@ -590,14 +590,14 @@ ($_ _.then (_.define approximate (|> (i64##number remainder) (_./ (i64##number parameter)) - (_.apply/1 (_.var "Math.floor")) - (_.apply/2 (_.var "Math.max") (_.i32 +1)))) + (_.apply_1 (_.var "Math.floor")) + (_.apply_2 (_.var "Math.max") (_.i32 +1)))) (_.define log2 (|> approximate - (_.apply/1 (_.var "Math.log")) + (_.apply_1 (_.var "Math.log")) (_./ (_.var "Math.LN2")) - (_.apply/1 (_.var "Math.ceil")))) + (_.apply_1 (_.var "Math.ceil")))) (_.define delta (_.? (_.> (_.i32 +48) log2) - (_.apply/2 (_.var "Math.pow") + (_.apply_2 (_.var "Math.pow") (_.i32 +2) (_.- (_.i32 +48) log2)) @@ -692,10 +692,10 @@ end!)) (_.if (|> print _.type_of (_.= (_.string "undefined")) _.not) ($_ _.then - (_.statement (_.apply/1 print (_.? (_.= (_.string "string") + (_.statement (_.apply_1 print (_.? (_.= (_.string "string") (_.type_of message)) message - (_.apply/1 (_.var "JSON.stringify") message)))) + (_.apply_1 (_.var "JSON.stringify") message)))) end!)) end!))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux index dfce813ed..be52af3e7 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux @@ -108,7 +108,7 @@ (do [! meta.monad] [ids (monad.all ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars - (list.zipped/2 ids) + (list.zipped_2 ids) (list#each (function (_ [id var]) (list (code.local var) (` (_.var (~ (code.text (format "v" (%.nat id))))))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux index 165bbd55d..5baba49fc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux @@ -75,7 +75,7 @@ (do [! meta.monad] [ids (monad.all ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars - (list.zipped/2 ids) + (list.zipped_2 ids) (list#each (function (_ [id var]) (list (code.local var) (` (_.var (~ (code.text (format "v" (%.nat id))))))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux index adddebae3..525b2a108 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux @@ -114,7 +114,7 @@ (do [! meta.monad] [ids (monad.all ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars - (list.zipped/2 ids) + (list.zipped_2 ids) (list#each (function (_ [id var]) (list (code.local var) (` (_.var (~ (code.text (format "v" (%.nat id))))))))) 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 02c38d130..c6ff7f292 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 @@ -81,7 +81,7 @@ (do [! meta.monad] [ids (monad.all ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars - (list.zipped/2 ids) + (list.zipped_2 ids) (list#each (function (_ [id var]) (list (code.local var) (` (_.var (~ (code.text (format "v" (%.nat id))))))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux index 086c1ff0c..ed673e53a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux @@ -73,7 +73,7 @@ (do [! meta.monad] [ids (monad.all ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars - (list.zipped/2 ids) + (list.zipped_2 ids) (list#each (function (_ [id var]) (list (code.local var) (` (_.local (~ (code.text (format "v" (%.nat id))))))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux index bc785f38d..f40915ce9 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux @@ -63,7 +63,7 @@ (do [! meta.monad] [ids (monad.all ! (list.repeated (list.size vars) meta.seed))] (in (list (` (let [(~+ (|> vars - (list.zipped/2 ids) + (list.zipped_2 ids) (list#each (function (_ [id var]) (list (code.local var) (` (_.var (~ (code.text (format "v" (%.nat id))))))))) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux index 3e9726924..26ee6ba8e 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux @@ -135,7 +135,7 @@ dependencies (is (Writer (Set unit.ID)) (binary.set dependency)) artifacts (is (Writer (Sequence [Category Bit (Set unit.ID)])) - (binary.sequence/64 ($_ binary.and category mandatory? dependencies)))] + (binary.sequence_64 ($_ binary.and category mandatory? dependencies)))] (|>> representation (the #artifacts) (sequence#each (function (_ [it dependencies]) @@ -181,7 +181,7 @@ (<>.and <binary>.nat <binary>.nat)) dependencies (is (Parser (Set unit.ID)) (<binary>.set unit.hash dependency))] - (|> (<binary>.sequence/64 ($_ <>.and category mandatory? dependencies)) + (|> (<binary>.sequence_64 ($_ <>.and category mandatory? dependencies)) (# <>.monad each (sequence#mix (function (_ [category mandatory? dependencies] registry) (product.right (case category diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux index 3abcfbf5a..548a89b36 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux @@ -149,7 +149,7 @@ (if (text.ends_with? ..lux_extension file) (do ! [source_code (# fs read file)] - (async#in (dictionary.has' (text.replaced/1 context "" file) source_code enumeration))) + (async#in (dictionary.has' (text.replaced_once context "" file) source_code enumeration))) (in enumeration))) enumeration)) (# ! conjoint))] diff --git a/stdlib/source/library/lux/type.lux b/stdlib/source/library/lux/type.lux index 402e1a2c7..8bd91191c 100644 --- a/stdlib/source/library/lux/type.lux +++ b/stdlib/source/library/lux/type.lux @@ -190,7 +190,7 @@ (n.= (list.size yparams) (list.size xparams)) (list#mix (.function (_ [x y] prev) (and prev (= x y))) #1 - (list.zipped/2 xparams yparams))) + (list.zipped_2 xparams yparams))) (^.template [<tag>] [[{<tag> xid} {<tag> yid}] @@ -217,7 +217,7 @@ (= xbody ybody) (list#mix (.function (_ [x y] prev) (and prev (= x y))) #1 - (list.zipped/2 xenv yenv))) + (list.zipped_2 xenv yenv))) _ #0 diff --git a/stdlib/source/library/lux/type/implicit.lux b/stdlib/source/library/lux/type/implicit.lux index 19d3f17cf..5fde46588 100644 --- a/stdlib/source/library/lux/type/implicit.lux +++ b/stdlib/source/library/lux/type/implicit.lux @@ -176,7 +176,7 @@ (in (list#mix (function (_ [imported_module definitions] tail) (available_definitions sig_type imported_module this_module_name definitions tail)) {.#End} - (list.zipped/2 imported_modules accessible_definitions))))) + (list.zipped_2 imported_modules accessible_definitions))))) (def: (on_argument arg func) (-> Type Type (Check Type)) @@ -363,7 +363,7 @@ {.#Right [args _]} (do [! meta.monad] [labels (|> (macro.symbol "") (list.repeated (list.size args)) (monad.all !))] - (in (list (` (let [(~+ (|> args (list.zipped/2 labels) (list#each ..pair_list) list#conjoint))] + (in (list (` (let [(~+ (|> args (list.zipped_2 labels) (list#each ..pair_list) list#conjoint))] (..## (~ (code.symbol member)) (~+ labels))))))) )) @@ -381,7 +381,7 @@ body <code>.any]) (do meta.monad [g!implicit+ (implicit_bindings (list.size implementations))] - (in (list (` (let [(~+ (|> (list.zipped/2 g!implicit+ implementations) + (in (list (` (let [(~+ (|> (list.zipped_2 g!implicit+ implementations) (list#each (function (_ [g!implicit implementation]) (list g!implicit implementation))) list#conjoint))] @@ -390,7 +390,7 @@ (syntax: .public (implicit: [implementations ..implicits]) (do meta.monad [g!implicit+ (implicit_bindings (list.size implementations))] - (in (|> (list.zipped/2 g!implicit+ implementations) + (in (|> (list.zipped_2 g!implicit+ implementations) (list#each (function (_ [g!implicit implementation]) (` (def: .private (~ g!implicit) (~ implementation))))))))) diff --git a/stdlib/source/library/lux/world/output/video/resolution.lux b/stdlib/source/library/lux/world/output/video/resolution.lux index ffd481769..6e6bf1036 100644 --- a/stdlib/source/library/lux/world/output/video/resolution.lux +++ b/stdlib/source/library/lux/world/output/video/resolution.lux @@ -1,14 +1,14 @@ (.using - [library - [lux "*" - [abstract - [equivalence {"+" Equivalence}] - [hash {"+" Hash}]] - [data - ["[0]" product]] - [math - [number - ["[0]" nat]]]]]) + [library + [lux "*" + [abstract + [equivalence {"+" Equivalence}] + [hash {"+" Hash}]] + [data + ["[0]" product]] + [math + [number + ["[0]" nat]]]]]) (type: .public Resolution (Record @@ -34,9 +34,9 @@ [wsvga 1024 600] [xga 1024 768] [xga+ 1152 864] - [wxga/16:9 1280 720] - [wxga/5:3 1280 768] - [wxga/16:10 1280 800] + [wxga_16:9 1280 720] + [wxga_5:3 1280 768] + [wxga_16:10 1280 800] [sxga 1280 1024] [wxga+ 1440 900] [hd+ 1600 900] diff --git a/stdlib/source/library/lux/world/program.lux b/stdlib/source/library/lux/world/program.lux index 10a2cc7b1..0561a7c66 100644 --- a/stdlib/source/library/lux/world/program.lux +++ b/stdlib/source/library/lux/world/program.lux @@ -300,7 +300,7 @@ {.#Some process/env} (|> (Object::entries [process/env]) (array.list {.#None}) - (list#each (|>> (array.read! 0) maybe.trusted))) + (list#each (|>> (array.item 0) maybe.trusted))) {.#None} (list)) @@ -344,8 +344,8 @@ @.js (io.io (if ffi.on_node_js? (case (do maybe.monad [process/env (ffi.global Object [process env])] - (array.read! (as Nat name) - (as (Array Text) process/env))) + (array.item (as Nat name) + (as (Array Text) process/env))) {.#Some value} {try.#Success value} |