aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux.lux')
-rw-r--r--stdlib/source/library/lux.lux164
1 files changed, 82 insertions, 82 deletions
diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux
index bf523ec7c..5c6c625a8 100644
--- a/stdlib/source/library/lux.lux
+++ b/stdlib/source/library/lux.lux
@@ -1165,12 +1165,12 @@
(meta#in {#Item (list#mix |#Item| |#End| (list#reversed xs))
{#End}}))
-(macro:' .public (list& xs)
+(macro:' .public (partial_list xs)
({{#Item last init}
(meta#in (list (list#mix |#Item| last init)))
_
- (failure "Wrong syntax for list&")}
+ (failure "Wrong syntax for partial_list")}
(list#reversed xs)))
(macro:' .public (Union tokens)
@@ -1512,8 +1512,8 @@
(-> Text a ($' PList a) ($' PList a)))
({{#Item [k' v'] plist'}
(if (text#= k k')
- (list& [k v] plist')
- (list& [k' v'] (plist#with k v plist')))
+ (partial_list [k v] plist')
+ (partial_list [k' v'] (plist#with k v plist')))
{#End}
(list [k v])}
@@ -2065,7 +2065,7 @@
xs
{#Item [x xs']}
- (list& x sep (list#interposed sep xs'))}
+ (partial_list x sep (list#interposed sep xs'))}
xs))
(def:''' .private (single_expansion token)
@@ -2423,18 +2423,18 @@
[??? (macro? name)]
(if ???
(do meta_monad
- [init_expansion (single_expansion (form$ (list& (symbol$ name) (form$ args) body branches')))]
+ [init_expansion (single_expansion (form$ (partial_list (symbol$ name) (form$ args) body branches')))]
(expander init_expansion))
(do meta_monad
[sub_expansion (expander branches')]
- (in (list& (form$ (list& (symbol$ name) args))
- body
- sub_expansion)))))
+ (in (partial_list (form$ (partial_list (symbol$ name) args))
+ body
+ sub_expansion)))))
{#Item pattern {#Item body branches'}}
(do meta_monad
[sub_expansion (expander branches')]
- (in (list& pattern body sub_expansion)))
+ (in (partial_list pattern body sub_expansion)))
{#End}
(do meta_monad [] (in (list)))
@@ -2464,7 +2464,7 @@
[pattern+ (full_expansion #1 pattern)]
(case pattern+
{#Item pattern' {#End}}
- (in (list& pattern' body branches))
+ (in (partial_list pattern' body branches))
_
(failure "`pattern` can only expand to 1 pattern.")))
@@ -2474,7 +2474,7 @@
(macro:' .private (pattern#or tokens)
(case tokens
- (pattern (list& [_ {#Form patterns}] body branches))
+ (pattern (partial_list [_ {#Form patterns}] body branches))
(case patterns
{#End}
(failure "pattern#or cannot have 0 patterns")
@@ -2522,7 +2522,7 @@
(macro:' .public (function tokens)
(case (is (Maybe [Text Code (List Code) Code])
(case tokens
- (pattern (list [_ {#Form (list& [_ {#Symbol ["" name]}] head tail)}] body))
+ (pattern (list [_ {#Form (partial_list [_ {#Symbol ["" name]}] head tail)}] body))
{#Some name head tail body}
_
@@ -2578,7 +2578,7 @@
(do maybe_monad
[it (someP itP tokens)
.let [[tokens tail] it]]
- (in [tokens (list& head tail)]))
+ (in [tokens (partial_list head tail)]))
{#None}
{#Some [tokens (list)]}))
@@ -2598,7 +2598,7 @@
(All (_ a)
(-> (Parser a) (Parser a)))
(case tokens
- (pattern (list& [_ {#Tuple tuple}] tokens'))
+ (pattern (partial_list [_ {#Tuple tuple}] tokens'))
(do maybe_monad
[it (parsed itP tuple)]
(in [tokens' it]))
@@ -2609,7 +2609,7 @@
(def:' .private (bindingP tokens)
(Parser [Text Code])
(case tokens
- (pattern (list& [_ {#Symbol ["" name]}] value &rest))
+ (pattern (partial_list [_ {#Symbol ["" name]}] value &rest))
{#Some [&rest [name value]]}
_
@@ -2627,7 +2627,7 @@
(def:' .private (anyP tokens)
(Parser Code)
(case tokens
- (pattern (list& code tokens'))
+ (pattern (partial_list code tokens'))
{#Some [tokens' code]}
_
@@ -2636,7 +2636,7 @@
(def:' .private (localP tokens)
(-> (List Code) (Maybe [(List Code) Text]))
(case tokens
- (pattern (list& [_ {#Symbol ["" local]}] tokens'))
+ (pattern (partial_list [_ {#Symbol ["" local]}] tokens'))
{#Some [tokens' local]}
_
@@ -2664,7 +2664,7 @@
[(def:' .private (<parser> tokens)
(-> (List Code) (Maybe [(List Code) [Text (List <parameter_type>)]]))
(case tokens
- (pattern (list& [_ {#Form local_declaration}] tokens'))
+ (pattern (partial_list [_ {#Form local_declaration}] tokens'))
(do maybe_monad
[% (localP local_declaration)
.let' [[local_declaration name] %]
@@ -2684,7 +2684,7 @@
(def:' .private (export_policyP tokens)
(-> (List Code) [(List Code) Code])
(case tokens
- (pattern (list& candidate tokens'))
+ (pattern (partial_list candidate tokens'))
(case candidate
[_ {#Bit it}]
[tokens' candidate]
@@ -2718,11 +2718,11 @@
(-> (List Code) (Maybe [(List Code) [(Maybe Code) Code]]))
(case tokens
... TB
- (pattern (list& type body tokens'))
+ (pattern (partial_list type body tokens'))
{#Some [tokens' [{#Some type} body]]}
... B
- (pattern (list& body tokens'))
+ (pattern (partial_list body tokens'))
{#Some [tokens' [{#None} body]]}
_
@@ -2808,7 +2808,7 @@
(template [<name> <form> <message>]
[(macro: .public (<name> tokens)
(case (list#reversed tokens)
- (pattern (list& last init))
+ (pattern (partial_list last init))
(meta#in (list (list#mix (is (-> Code Code Code)
(function (_ pre post) (` <form>)))
last
@@ -2850,13 +2850,13 @@
(list input)
{#Some idx}
- (list& ("lux text clip" 0 idx input)
- (text#all_split_by splitter
- (let [after_offset ("lux i64 +" 1 idx)
- after_length ("lux i64 -"
- after_offset
- ("lux text size" input))]
- ("lux text clip" after_offset after_length input))))))
+ (partial_list ("lux text clip" 0 idx input)
+ (text#all_split_by splitter
+ (let [after_offset ("lux i64 +" 1 idx)
+ after_length ("lux i64 -"
+ after_offset
+ ("lux text size" input))]
+ ("lux text clip" after_offset after_length input))))))
(def: (item idx xs)
(All (_ a)
@@ -2921,10 +2921,10 @@
(-> Type Type (Maybe Type))
(case type_fn
{#UnivQ env body}
- {#Some (reduced (list& type_fn param env) body)}
+ {#Some (reduced (partial_list type_fn param env) body)}
{#ExQ env body}
- {#Some (reduced (list& type_fn param env) body)}
+ {#Some (reduced (partial_list type_fn param env) body)}
{#Apply A F}
(do maybe_monad
@@ -2942,7 +2942,7 @@
(-> Type (List Type))
(case type
{<tag> left right}
- (list& left (<name> right))
+ (partial_list left (<name> right))
_
(list type)))]
@@ -3224,7 +3224,7 @@
{#End}
(in (list)))]
- (in (list& head tail)))
+ (in (partial_list head tail)))
{#End}
{#Some (list)}))
@@ -3232,10 +3232,10 @@
(def: (caseP tokens)
(-> (List Code) (Maybe [(List Code) [Text Code]]))
(case tokens
- (pattern (list& [_ {#Variant (list [_ {#Symbol ["" niladic]}])}] tokens'))
+ (pattern (partial_list [_ {#Variant (list [_ {#Symbol ["" niladic]}])}] tokens'))
{#Some [tokens' [niladic (` .Any)]]}
- (pattern (list& [_ {#Variant (list& [_ {#Symbol ["" polyadic]}] caseT)}] tokens'))
+ (pattern (partial_list [_ {#Variant (partial_list [_ {#Symbol ["" polyadic]}] caseT)}] tokens'))
{#Some [tokens' [polyadic (` (..Tuple (~+ caseT)))]]}
_
@@ -3255,7 +3255,7 @@
(def: (slotP tokens)
(-> (List Code) (Maybe [(List Code) [Text Code]]))
(case tokens
- (pattern (list& [_ {#Symbol ["" slot]}] type tokens'))
+ (pattern (partial_list [_ {#Symbol ["" slot]}] type tokens'))
{#Some [tokens' [slot type]]}
_
@@ -3290,7 +3290,7 @@
(def: (textP tokens)
(-> (List Code) (Maybe [(List Code) Text]))
(case tokens
- (pattern (list& [_ {#Text it}] tokens'))
+ (pattern (partial_list [_ {#Text it}] tokens'))
{#Some [tokens' it]}
_
@@ -3300,7 +3300,7 @@
(-> Code (Meta (Tuple Code (Maybe (Either (List Text) (List Text))))))
({[_ {#Form {#Item [_ {#Symbol declarer}] parameters}}]
(do meta_monad
- [declaration (single_expansion (form$ (list& (symbol$ declarer) parameters)))]
+ [declaration (single_expansion (form$ (partial_list (symbol$ declarer) parameters)))]
(case declaration
(pattern (list type [_ {#Variant tags}]))
(case (everyP textP tags)
@@ -3411,24 +3411,24 @@
(def: (referrals_parser tokens)
(-> (List Code) (Meta [Referrals (List Code)]))
(case tokens
- (pattern#or (pattern (list& [_ {#Variant (list& [_ {#Text "+"}] defs)}] tokens'))
- (pattern (list& [_ {#Variant (list& [_ {#Text "only"}] defs)}] tokens')))
+ (pattern#or (pattern (partial_list [_ {#Variant (partial_list [_ {#Text "+"}] defs)}] tokens'))
+ (pattern (partial_list [_ {#Variant (partial_list [_ {#Text "only"}] defs)}] tokens')))
(do meta_monad
[defs' (..referral_references defs)]
(in [{#Only defs'} tokens']))
- (pattern#or (pattern (list& [_ {#Variant (list& [_ {#Text "-"}] defs)}] tokens'))
- (pattern (list& [_ {#Variant (list& [_ {#Text "exclude"}] defs)}] tokens')))
+ (pattern#or (pattern (partial_list [_ {#Variant (partial_list [_ {#Text "-"}] defs)}] tokens'))
+ (pattern (partial_list [_ {#Variant (partial_list [_ {#Text "exclude"}] defs)}] tokens')))
(do meta_monad
[defs' (..referral_references defs)]
(in [{#Exclude defs'} tokens']))
- (pattern#or (pattern (list& [_ {#Text "*"}] tokens'))
- (pattern (list& [_ {#Text "all"}] tokens')))
+ (pattern#or (pattern (partial_list [_ {#Text "*"}] tokens'))
+ (pattern (partial_list [_ {#Text "all"}] tokens')))
(meta#in [{#All} tokens'])
- (pattern#or (pattern (list& [_ {#Text "_"}] tokens'))
- (pattern (list& [_ {#Text "ignore"}] tokens')))
+ (pattern#or (pattern (partial_list [_ {#Text "_"}] tokens'))
+ (pattern (partial_list [_ {#Text "ignore"}] tokens')))
(meta#in [{#Ignore} tokens'])
_
@@ -3440,7 +3440,7 @@
{#End}
(meta#in [{#End} {#End}])
- (pattern (list& [_ {#Form (list& [_ {#Text prefix}] structs)}] parts'))
+ (pattern (partial_list [_ {#Form (partial_list [_ {#Text prefix}] structs)}] parts'))
(do meta_monad
[structs' (monad#each meta_monad
(function (_ struct)
@@ -3589,7 +3589,7 @@
#refer_open (list)]])))
... Nested
- (pattern [_ {#Tuple (list& [_ {#Symbol ["" module_name]}] extra)}])
+ (pattern [_ {#Tuple (partial_list [_ {#Symbol ["" module_name]}] extra)}])
(do meta_monad
[absolute_module_name (case (normal_parallel_path relative_root module_name)
{#Some parallel_path}
@@ -3607,13 +3607,13 @@
sub_imports
_
- (list& [#import_name absolute_module_name
- #import_alias {#None}
- #import_refer [#refer_defs referral
- #refer_open openings]]
- sub_imports))))
+ (partial_list [#import_name absolute_module_name
+ #import_alias {#None}
+ #import_refer [#refer_defs referral
+ #refer_open openings]]
+ sub_imports))))
- (pattern [_ {#Tuple (list& [_ {#Text alias}] [_ {#Symbol ["" module_name]}] extra)}])
+ (pattern [_ {#Tuple (partial_list [_ {#Text alias}] [_ {#Symbol ["" module_name]}] extra)}])
(do meta_monad
[absolute_module_name (case (normal_parallel_path relative_root module_name)
{#Some parallel_path}
@@ -3632,11 +3632,11 @@
sub_imports
_
- (list& [#import_name absolute_module_name
- #import_alias {#Some module_alias}
- #import_refer [#refer_defs referral
- #refer_open openings]]
- sub_imports))))
+ (partial_list [#import_name absolute_module_name
+ #import_alias {#Some module_alias}
+ #import_refer [#refer_defs referral
+ #refer_open openings]]
+ sub_imports))))
... Unrecognized syntax.
_
@@ -3878,7 +3878,7 @@
{#Item x xs'}
(case ys
{#Item y ys'}
- (list& [x y] (zipped_2 xs' ys'))
+ (partial_list [x y] (zipped_2 xs' ys'))
_
(list))
@@ -3888,10 +3888,10 @@
(macro: .public (open tokens)
(case tokens
- (pattern (list& [_ {#Form (list [_ {#Text alias}])}] body branches))
+ (pattern (partial_list [_ {#Form (list [_ {#Text alias}])}] body branches))
(do meta_monad
[g!temp (..generated_symbol "temp")]
- (in (list& g!temp (` (..open (~ g!temp) (~ (text$ alias)) (~ body))) branches)))
+ (in (partial_list g!temp (` (..open (~ g!temp) (~ (text$ alias)) (~ body))) branches)))
(pattern (list [_ {#Symbol name}] [_ {#Text alias}] body))
(do meta_monad
@@ -3944,7 +3944,7 @@
(macro: .public (cond tokens)
(case (list#reversed tokens)
- (pattern (list& else branches'))
+ (pattern (partial_list else branches'))
(case (pairs branches')
{#Some branches'}
(meta#in (list (list#mix (is (-> [Code Code] Code Code)
@@ -4163,7 +4163,7 @@
(macro: (refer tokens)
(case tokens
- (pattern (list& [_ {#Text module_name}] options))
+ (pattern (partial_list [_ {#Text module_name}] options))
(do meta_monad
[=refer (referrals module_name options)]
(referral_definitions module_name =refer))
@@ -4180,10 +4180,10 @@
(list (' "*"))
{#Only defs}
- (list (variant$ (list& (' "+") (list#each local$ defs))))
+ (list (variant$ (partial_list (' "+") (list#each local$ defs))))
{#Exclude defs}
- (list (variant$ (list& (' "-") (list#each local$ defs))))
+ (list (variant$ (partial_list (' "-") (list#each local$ defs))))
{#Ignore}
(list)
@@ -4191,8 +4191,8 @@
{#Nothing}
(list)))
openings (list#each (function (_ [alias structs])
- (form$ (list& (text$ (..module_alias (list (alias_stand_in 0) module_alias) alias))
- (list#each local$ structs))))
+ (form$ (partial_list (text$ (..module_alias (list (alias_stand_in 0) module_alias) alias))
+ (list#each local$ structs))))
r_opens)]
(` ((~! ..refer) (~ (text$ module_name))
(~+ localizations)
@@ -4204,7 +4204,7 @@
(meta#in (list (` (..let [(..open (~ (text$ (alias_stand_in 0)))) (~ struct)]
(~ (symbol$ member))))))
- (pattern (list& struct member args))
+ (pattern (partial_list struct member args))
(meta#in (list (` ((..# (~ struct) (~ member)) (~+ args)))))
_
@@ -4364,10 +4364,10 @@
(macro: .private (pattern#template tokens)
(case tokens
- (pattern (list& [_ {#Form (list [_ {#Tuple bindings}]
- [_ {#Tuple templates}])}]
- [_ {#Form data}]
- branches))
+ (pattern (partial_list [_ {#Form (list [_ {#Tuple bindings}]
+ [_ {#Tuple templates}])}]
+ [_ {#Form data}]
+ branches))
(case (is (Maybe (List Code))
(do maybe_monad
[bindings' (monad#each maybe_monad symbol_short bindings)
@@ -4414,7 +4414,7 @@
{#End}
{#Item y ys'}
- (list& x y (interleaved xs' ys')))))
+ (partial_list x y (interleaved xs' ys')))))
(def: (type_code type)
(-> Type Code)
@@ -4659,7 +4659,7 @@
(macro: (pattern#multi tokens)
(case tokens
- (pattern (list& [_meta {#Form levels}] body next_branches))
+ (pattern (partial_list [_meta {#Form levels}] body next_branches))
(do meta_monad
[mlc (multi_level_case^ levels)
.let [initial_bind? (case mlc
@@ -4923,8 +4923,8 @@
... {library/lux/tool/compiler/language/lux/generation.no_buffer_for_saving_code}
... Artifact ID: 0
... Which only ever happens for the Python compiler.
- (list& (` ("lux def" (~ g!_) [] #0))
- =refers)
+ (partial_list (` ("lux def" (~ g!_) [] #0))
+ =refers)
=refers)})))
(def: (embedded_expansions code)
@@ -4985,10 +4985,10 @@
(def: (methodP tokens)
(-> (List Code) (Maybe [(List Code) [Text Code]]))
(case tokens
- (pattern (list& [_ {#Form (list [_ {#Text "lux type check"}]
- type
- [_ {#Symbol ["" name]}])}]
- tokens'))
+ (pattern (partial_list [_ {#Form (list [_ {#Text "lux type check"}]
+ type
+ [_ {#Symbol ["" name]}])}]
+ tokens'))
{#Some [tokens' [name type]]}
_