From bc36487224f670c23002cc4575c0dba3e5dc1be1 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Tue, 15 Mar 2022 07:24:35 -0400 Subject: De-sigil-ification: ^ --- stdlib/source/library/lux.lux | 398 ++++++++++++++++-------------------------- 1 file changed, 147 insertions(+), 251 deletions(-) (limited to 'stdlib/source/library/lux.lux') diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux index 6120a52be..aa5e5c476 100644 --- a/stdlib/source/library/lux.lux +++ b/stdlib/source/library/lux.lux @@ -1435,8 +1435,7 @@ var)))) body (list#reversed bindings))] - (meta#in (list (form$ (list (variant$ (list (tuple$ (list (symbol$ [..prelude_module "#in"]) g!in - (symbol$ [..prelude_module "#then"]) g!then)) + (meta#in (list (form$ (list (variant$ (list (tuple$ (list g!in g!then)) body')) monad))))) @@ -2458,7 +2457,7 @@ (failure "Wrong syntax for case")} tokens)) -(macro:' .public (^ tokens) +(macro:' .public (pattern tokens) (case tokens {#Item [_ {#Form {#Item pattern {#End}}}] {#Item body branches}} (do meta_monad @@ -2468,17 +2467,17 @@ (in (list& pattern' body branches)) _ - (failure "^ can only expand to 1 pattern."))) + (failure "`pattern` can only expand to 1 pattern."))) _ - (failure "Wrong syntax for ^ macro"))) + (failure "Wrong syntax for `pattern` macro"))) -(macro:' .public (^or tokens) +(macro:' .private (pattern#or tokens) (case tokens - (^ (list& [_ {#Form patterns}] body branches)) + (pattern (list& [_ {#Form patterns}] body branches)) (case patterns {#End} - (failure "^or cannot have 0 patterns") + (failure "pattern#or cannot have 0 patterns") _ (let' [pairs (|> patterns @@ -2486,7 +2485,7 @@ (list#conjoint))] (meta#in (list#composite pairs branches)))) _ - (failure "Wrong syntax for ^or"))) + (failure "Wrong syntax for pattern#or"))) (def:' .private (symbol? code) (-> Code Bit) @@ -2499,7 +2498,7 @@ (macro:' .public (let tokens) (case tokens - (^ (list [_ {#Tuple bindings}] body)) + (pattern (list [_ {#Tuple bindings}] body)) (case (..pairs bindings) {#Some bindings} (|> bindings @@ -2523,7 +2522,7 @@ (macro:' .public (function tokens) (case (: (Maybe [Text Code (List Code) Code]) (case tokens - (^ (list [_ {#Form (list& [_ {#Symbol ["" name]}] head tail)}] body)) + (pattern (list [_ {#Form (list& [_ {#Symbol ["" name]}] head tail)}] body)) {#Some name head tail body} _ @@ -2552,7 +2551,7 @@ (def:' .private (parsed parser tokens) (All (_ a) (-> (Parser a) (List Code) (Maybe a))) (case (parser tokens) - (^ {#Some [(list) it]}) + (pattern {#Some [(list) it]}) {#Some it} _ @@ -2599,7 +2598,7 @@ (All (_ a) (-> (Parser a) (Parser a))) (case tokens - (^ (list& [_ {#Tuple tuple}] tokens')) + (pattern (list& [_ {#Tuple tuple}] tokens')) (do maybe_monad [it (parsed itP tuple)] (in [tokens' it])) @@ -2610,7 +2609,7 @@ (def:' .private (bindingP tokens) (Parser [Text Code]) (case tokens - (^ (list& [_ {#Symbol ["" name]}] value &rest)) + (pattern (list& [_ {#Symbol ["" name]}] value &rest)) {#Some [&rest [name value]]} _ @@ -2619,7 +2618,7 @@ (def:' .private (endP tokens) (-> (List Code) (Maybe Any)) (case tokens - (^ (list)) + (pattern (list)) {#Some []} _ @@ -2628,7 +2627,7 @@ (def:' .private (anyP tokens) (Parser Code) (case tokens - (^ (list& code tokens')) + (pattern (list& code tokens')) {#Some [tokens' code]} _ @@ -2637,7 +2636,7 @@ (def:' .private (local_symbolP tokens) (-> (List Code) (Maybe [(List Code) Text])) (case tokens - (^ (list& [_ {#Symbol ["" local_symbol]}] tokens')) + (pattern (list& [_ {#Symbol ["" local_symbol]}] tokens')) {#Some [tokens' local_symbol]} _ @@ -2665,7 +2664,7 @@ [(def:' .private ( tokens) (-> (List Code) (Maybe [(List Code) [Text (List )]])) (case tokens - (^ (list& [_ {#Form local_declaration}] tokens')) + (pattern (list& [_ {#Form local_declaration}] tokens')) (do maybe_monad [% (local_symbolP local_declaration) .let' [[local_declaration name] %] @@ -2685,7 +2684,7 @@ (def:' .private (export_policyP tokens) (-> (List Code) [(List Code) Code]) (case tokens - (^ (list& candidate tokens')) + (pattern (list& candidate tokens')) (case candidate [_ {#Bit it}] [tokens' candidate] @@ -2719,11 +2718,11 @@ (-> (List Code) (Maybe [(List Code) [(Maybe Code) Code]])) (case tokens ... TB - (^ (list& type body tokens')) + (pattern (list& type body tokens')) {#Some [tokens' [{#Some type} body]]} ... B - (^ (list& body tokens')) + (pattern (list& body tokens')) {#Some [tokens' [{#None} body]]} _ @@ -2809,7 +2808,7 @@ (template [
] [(macro: .public ( tokens) (case (list#reversed tokens) - (^ (list& last init)) + (pattern (list& last init)) (meta#in (list (list#mix (: (-> Code Code Code) (function (_ pre post) (` ))) last @@ -2831,7 +2830,7 @@ (macro: (maybe#else tokens state) (case tokens - (^ (list else maybe)) + (pattern (list else maybe)) (let [g!temp (: Code [dummy_location {#Symbol ["" ""]}]) code (` (case (~ maybe) {.#Some (~ g!temp)} @@ -3144,7 +3143,7 @@ (: (-> Code (Meta (List Code))) (function (_ token) (case token - (^ [_ {#Form (list [_ {#Text "lux def"}] [_ {#Symbol ["" slot_name]}] value export_policy)}]) + (pattern [_ {#Form (list [_ {#Text "lux def"}] [_ {#Symbol ["" slot_name]}] value export_policy)}]) (case (plist#value slot_name tag_mappings) {#Some tag} (in (list tag value)) @@ -3233,10 +3232,10 @@ (def: (caseP tokens) (-> (List Code) (Maybe [(List Code) [Text Code]])) (case tokens - (^ (list& [_ {#Variant (list [_ {#Symbol ["" niladic]}])}] tokens')) + (pattern (list& [_ {#Variant (list [_ {#Symbol ["" niladic]}])}] tokens')) {#Some [tokens' [niladic (` .Any)]]} - (^ (list& [_ {#Variant (list& [_ {#Symbol ["" polyadic]}] caseT)}] tokens')) + (pattern (list& [_ {#Variant (list& [_ {#Symbol ["" polyadic]}] caseT)}] tokens')) {#Some [tokens' [polyadic (` (..Tuple (~+ caseT)))]]} _ @@ -3256,7 +3255,7 @@ (def: (slotP tokens) (-> (List Code) (Maybe [(List Code) [Text Code]])) (case tokens - (^ (list& [_ {#Symbol ["" slot]}] type tokens')) + (pattern (list& [_ {#Symbol ["" slot]}] type tokens')) {#Some [tokens' [slot type]]} _ @@ -3264,7 +3263,7 @@ (macro: .public (Record tokens) (case tokens - (^ (list [_ {#Tuple record}])) + (pattern (list [_ {#Tuple record}])) (case (everyP slotP record) {#Some slots} (meta#in (list (` (..Tuple (~+ (list#each product#right slots)))) @@ -3291,7 +3290,7 @@ (def: (textP tokens) (-> (List Code) (Maybe [(List Code) Text])) (case tokens - (^ (list& [_ {#Text it}] tokens')) + (pattern (list& [_ {#Text it}] tokens')) {#Some [tokens' it]} _ @@ -3303,7 +3302,7 @@ (do meta_monad [declaration (single_expansion (form$ (list& (symbol$ declarer) parameters)))] (case declaration - (^ (list type [_ {#Variant tags}])) + (pattern (list type [_ {#Variant tags}])) (case (everyP textP tags) {#Some tags} (meta#in [type {#Some {#Left tags}}]) @@ -3311,7 +3310,7 @@ {#None} (failure "Improper type-definition syntax")) - (^ (list type [_ {#Tuple slots}])) + (pattern (list type [_ {#Tuple slots}])) (case (everyP textP slots) {#Some slots} (meta#in [type {#Some {#Right slots}}]) @@ -3319,7 +3318,7 @@ {#None} (failure "Improper type-definition syntax")) - (^ (list type)) + (pattern (list type)) (meta#in [it {#None}]) _ @@ -3412,24 +3411,24 @@ (def: (referrals_parser tokens) (-> (List Code) (Meta [Referrals (List Code)])) (case tokens - (^or (^ (list& [_ {#Variant (list& [_ {#Text "+"}] defs)}] tokens')) - (^ (list& [_ {#Variant (list& [_ {#Text "only"}] defs)}] tokens'))) + (pattern#or (pattern (list& [_ {#Variant (list& [_ {#Text "+"}] defs)}] tokens')) + (pattern (list& [_ {#Variant (list& [_ {#Text "only"}] defs)}] tokens'))) (do meta_monad [defs' (..referral_references defs)] (in [{#Only defs'} tokens'])) - (^or (^ (list& [_ {#Variant (list& [_ {#Text "-"}] defs)}] tokens')) - (^ (list& [_ {#Variant (list& [_ {#Text "exclude"}] defs)}] tokens'))) + (pattern#or (pattern (list& [_ {#Variant (list& [_ {#Text "-"}] defs)}] tokens')) + (pattern (list& [_ {#Variant (list& [_ {#Text "exclude"}] defs)}] tokens'))) (do meta_monad [defs' (..referral_references defs)] (in [{#Exclude defs'} tokens'])) - (^or (^ (list& [_ {#Text "*"}] tokens')) - (^ (list& [_ {#Text "all"}] tokens'))) + (pattern#or (pattern (list& [_ {#Text "*"}] tokens')) + (pattern (list& [_ {#Text "all"}] tokens'))) (meta#in [{#All} tokens']) - (^or (^ (list& [_ {#Text "_"}] tokens')) - (^ (list& [_ {#Text "ignore"}] tokens'))) + (pattern#or (pattern (list& [_ {#Text "_"}] tokens')) + (pattern (list& [_ {#Text "ignore"}] tokens'))) (meta#in [{#Ignore} tokens']) _ @@ -3441,7 +3440,7 @@ {#End} (meta#in [{#End} {#End}]) - (^ (list& [_ {#Form (list& [_ {#Text prefix}] structs)}] parts')) + (pattern (list& [_ {#Form (list& [_ {#Text prefix}] structs)}] parts')) (do meta_monad [structs' (monad#each meta_monad (function (_ struct) @@ -3540,7 +3539,7 @@ (def: (list#after amount list) (All (_ a) (-> Nat (List a) (List a))) (case [amount list] - (^or [0 _] [_ {#End}]) + (pattern#or [0 _] [_ {#End}]) list [_ {#Item _ tail}] @@ -3590,7 +3589,7 @@ #refer_open (list)]]))) ... Nested - (^ [_ {#Tuple (list& [_ {#Symbol ["" module_name]}] extra)}]) + (pattern [_ {#Tuple (list& [_ {#Symbol ["" module_name]}] extra)}]) (do meta_monad [absolute_module_name (case (normal_parallel_path relative_root module_name) {#Some parallel_path} @@ -3614,7 +3613,7 @@ #refer_open openings]] sub_imports)))) - (^ [_ {#Tuple (list& [_ {#Text alias}] [_ {#Symbol ["" module_name]}] extra)}]) + (pattern [_ {#Tuple (list& [_ {#Text alias}] [_ {#Symbol ["" module_name]}] extra)}]) (do meta_monad [absolute_module_name (case (normal_parallel_path relative_root module_name) {#Some parallel_path} @@ -3887,14 +3886,14 @@ _ (list))) -(macro: .public (^open tokens) +(macro: .public (open tokens) (case tokens - (^ (list& [_ {#Form (list [_ {#Text alias}])}] body branches)) + (pattern (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 (list& g!temp (` (..open (~ g!temp) (~ (text$ alias)) (~ body))) branches))) - (^ (list [_ {#Symbol name}] [_ {#Text alias}] body)) + (pattern (list [_ {#Symbol name}] [_ {#Text alias}] body)) (do meta_monad [init_type (type_definition name) struct_evidence (record_slots init_type)] @@ -3911,7 +3910,7 @@ ["" (..module_alias (list t_name) alias)]]) tags) pattern (case locals - (^ (list [slot binding])) + (pattern (list [slot binding])) (symbol$ binding) _ @@ -3941,11 +3940,11 @@ (in (list full_body))))) _ - (failure "Wrong syntax for ^open"))) + (failure "Wrong syntax for open"))) (macro: .public (cond tokens) (case (list#reversed tokens) - (^ (list& else branches')) + (pattern (list& else branches')) (case (pairs branches') {#Some branches'} (meta#in (list (list#mix (: (-> [Code Code] Code Code) @@ -3978,7 +3977,7 @@ (macro: .public (the tokens) (case tokens - (^ (list [_ {#Symbol slot'}] record)) + (pattern (list [_ {#Symbol slot'}] record)) (do meta_monad [slot (normal slot') output (..type_slot slot) @@ -4001,14 +4000,14 @@ _ (failure "the can only use records."))) - (^ (list [_ {#Tuple slots}] record)) + (pattern (list [_ {#Tuple slots}] record)) (meta#in (list (list#mix (: (-> Code Code Code) (function (_ slot inner) (` (..the (~ slot) (~ inner))))) record slots))) - (^ (list selector)) + (pattern (list selector)) (do meta_monad [g!_ (..generated_symbol "_") g!record (..generated_symbol "record")] @@ -4048,7 +4047,7 @@ (macro: .public (open: tokens) (case tokens - (^ (list [_ {#Text alias}] struct)) + (pattern (list [_ {#Text alias}] struct)) (case struct [_ {#Symbol struct_name}] (do meta_monad @@ -4164,7 +4163,7 @@ (macro: (refer tokens) (case tokens - (^ (list& [_ {#Text module_name}] options)) + (pattern (list& [_ {#Text module_name}] options)) (do meta_monad [=refer (referrals module_name options)] (referral_definitions module_name =refer)) @@ -4201,11 +4200,11 @@ (macro: .public (# tokens) (case tokens - (^ (list struct [_ {#Symbol member}])) - (meta#in (list (` (let [(^open (~ (text$ (alias_stand_in 0)))) (~ struct)] + (pattern (list struct [_ {#Symbol member}])) + (meta#in (list (` (..let [(..open (~ (text$ (alias_stand_in 0)))) (~ struct)] (~ (symbol$ member)))))) - (^ (list& struct member args)) + (pattern (list& struct member args)) (meta#in (list (` ((..# (~ struct) (~ member)) (~+ args))))) _ @@ -4213,7 +4212,7 @@ (macro: .public (has tokens) (case tokens - (^ (list [_ {#Symbol slot'}] value record)) + (pattern (list [_ {#Symbol slot'}] value record)) (do meta_monad [slot (normal slot') output (..type_slot slot) @@ -4249,7 +4248,7 @@ _ (failure "has can only use records."))) - (^ (list [_ {#Tuple slots}] value record)) + (pattern (list [_ {#Tuple slots}] value record)) (case slots {#End} (failure "Wrong syntax for has") @@ -4276,14 +4275,14 @@ (in (list (` (let [(~+ accesses)] (~ update_expr))))))) - (^ (list selector value)) + (pattern (list selector value)) (do meta_monad [g!_ (..generated_symbol "_") g!record (..generated_symbol "record")] (in (list (` (function ((~ g!_) (~ g!record)) (..has (~ selector) (~ value) (~ g!record))))))) - (^ (list selector)) + (pattern (list selector)) (do meta_monad [g!_ (..generated_symbol "_") g!value (..generated_symbol "value") @@ -4296,7 +4295,7 @@ (macro: .public (revised tokens) (case tokens - (^ (list [_ {#Symbol slot'}] fun record)) + (pattern (list [_ {#Symbol slot'}] fun record)) (do meta_monad [slot (normal slot') output (..type_slot slot) @@ -4332,7 +4331,7 @@ _ (failure "revised can only use records."))) - (^ (list [_ {#Tuple slots}] fun record)) + (pattern (list [_ {#Tuple slots}] fun record)) (case slots {#End} (failure "Wrong syntax for revised") @@ -4345,14 +4344,14 @@ (~ g!temp) (the [(~+ slots)] (~ g!record))] (has [(~+ slots)] ((~ fun) (~ g!temp)) (~ g!record)))))))) - (^ (list selector fun)) + (pattern (list selector fun)) (do meta_monad [g!_ (..generated_symbol "_") g!record (..generated_symbol "record")] (in (list (` (function ((~ g!_) (~ g!record)) (..revised (~ selector) (~ fun) (~ g!record))))))) - (^ (list selector)) + (pattern (list selector)) (do meta_monad [g!_ (..generated_symbol "_") g!fun (..generated_symbol "fun") @@ -4363,12 +4362,12 @@ _ (failure "Wrong syntax for revised"))) -(macro: .public (^template tokens) +(macro: .private (pattern#template tokens) (case tokens - (^ (list& [_ {#Form (list [_ {#Tuple bindings}] - [_ {#Tuple templates}])}] - [_ {#Form data}] - branches)) + (pattern (list& [_ {#Form (list [_ {#Tuple bindings}] + [_ {#Tuple templates}])}] + [_ {#Form data}] + branches)) (case (: (Maybe (List Code)) (do maybe_monad [bindings' (monad#each maybe_monad symbol_short bindings) @@ -4387,10 +4386,10 @@ (meta#in (list#composite output branches)) {#None} - (failure "Wrong syntax for ^template")) + (failure "Wrong syntax for pattern#template")) _ - (failure "Wrong syntax for ^template"))) + (failure "Wrong syntax for pattern#template"))) (template [ ] [(def: .public @@ -4423,22 +4422,22 @@ {#Primitive name params} (` {.#Primitive (~ (text$ name)) (~ (untemplated_list (list#each type_code params)))}) - (^template [] - [{ left right} - (` { (~ (type_code left)) (~ (type_code right))})]) + (pattern#template [] + [{ left right} + (` { (~ (type_code left)) (~ (type_code right))})]) ([.#Sum] [.#Product] [.#Function] [.#Apply]) - (^template [] - [{ id} - (` { (~ (nat$ id))})]) + (pattern#template [] + [{ id} + (` { (~ (nat$ id))})]) ([.#Parameter] [.#Var] [.#Ex]) - (^template [] - [{ env type} - (let [env' (untemplated_list (list#each type_code env))] - (` { (~ env') (~ (type_code type))}))]) + (pattern#template [] + [{ env type} + (let [env' (untemplated_list (list#each type_code env))] + (` { (~ env') (~ (type_code type))}))]) ([.#UnivQ] [.#ExQ]) {#Named [module name] anonymous} @@ -4450,10 +4449,10 @@ (macro: .public (loop tokens) (let [?params (case tokens - (^ (list name [_ {#Tuple bindings}] body)) + (pattern (list name [_ {#Tuple bindings}] body)) {#Some [name bindings body]} - (^ (list [_ {#Tuple bindings}] body)) + (pattern (list [_ {#Tuple bindings}] body)) {#Some [(local_symbol$ "again") bindings body]} _ @@ -4497,7 +4496,7 @@ (def: (with_expansions' label tokens target) (-> Text (List Code) Code (List Code)) (case target - (^or [_ {#Bit _}] [_ {#Nat _}] [_ {#Int _}] [_ {#Rev _}] [_ {#Frac _}] [_ {#Text _}]) + (pattern#or [_ {#Bit _}] [_ {#Nat _}] [_ {#Int _}] [_ {#Rev _}] [_ {#Frac _}] [_ {#Text _}]) (list target) [_ {#Symbol [module name]}] @@ -4506,9 +4505,9 @@ tokens (list target)) - (^template [] - [[location { elems}] - (list [location { (list#conjoint (list#each (with_expansions' label tokens) elems))}])]) + (pattern#template [] + [[location { elems}] + (list [location { (list#conjoint (list#each (with_expansions' label tokens) elems))}])]) ([#Form] [#Variant] [#Tuple]))) @@ -4529,7 +4528,7 @@ {#Item [var_name expr] &rest} (do meta_monad [expansion (case (normal expr) - (^ (list expr)) + (pattern (list expr)) (single_expansion expr) _ @@ -4548,9 +4547,9 @@ (def: (flat_alias type) (-> Type Type) (case type - (^template [] - [{#Named ["library/lux" ] _} - type]) + (pattern#template [] + [{#Named ["library/lux" ] _} + type]) (["Bit"] ["Nat"] ["Int"] @@ -4570,9 +4569,9 @@ [type+value (definition_value name) .let [[type value] type+value]] (case (flat_alias type) - (^template [ ] - [{#Named ["library/lux" ] _} - (in ( (:as value)))]) + (pattern#template [ ] + [{#Named ["library/lux" ] _} + (in ( (:as value)))]) (["Bit" Bit bit$] ["Nat" Nat nat$] ["Int" Int int$] @@ -4593,11 +4592,11 @@ (static_simple_literal [current_module def_name])) (static_simple_literal [def_module def_name])) - (^template [] - [[meta { parts}] - (do meta_monad - [=parts (monad#each meta_monad static_literal parts)] - (in [meta { =parts}]))]) + (pattern#template [] + [[meta { parts}] + (do meta_monad + [=parts (monad#each meta_monad static_literal parts)] + (in [meta { =parts}]))]) ([#Form] [#Variant] [#Tuple]) @@ -4610,7 +4609,7 @@ (macro: .public (static tokens) (case tokens - (^ (list pattern)) + (pattern (list pattern)) (do meta_monad [pattern' (static_literal pattern)] (in (list pattern'))) @@ -4624,7 +4623,7 @@ (def: (case_level^ level) (-> Code (Meta [Code Code])) (case level - (^ [_ {#Tuple (list expr binding)}]) + (pattern [_ {#Tuple (list expr binding)}]) (meta#in [expr binding]) _ @@ -4662,9 +4661,9 @@ (: (List [Code Code]) (list#reversed levels)))] (list init_pattern inner_pattern_body))) -(macro: .public (^multi tokens) +(macro: (pattern#multi tokens) (case tokens - (^ (list& [_meta {#Form levels}] body next_branches)) + (pattern (list& [_meta {#Form levels}] body next_branches)) (do meta_monad [mlc (multi_level_case^ levels) .let [initial_bind? (case mlc @@ -4675,24 +4674,23 @@ #0)] expected ..expected_type g!temp (..generated_symbol "temp")] - (let [output (list g!temp - (` ({{.#Some (~ g!temp)} - (~ g!temp) - - {.#None} - (case (~ g!temp) - (~+ next_branches))} - ("lux type check" {.#Apply (~ (type_code expected)) Maybe} - (case (~ g!temp) - (~+ (multi_level_case$ g!temp [mlc body])) - - (~+ (if initial_bind? - (list) - (list g!temp (` {.#None})))))))))] - (in output))) + (in (list g!temp + (` ({{.#Some (~ g!temp)} + (~ g!temp) + + {.#None} + (case (~ g!temp) + (~+ next_branches))} + ("lux type check" {.#Apply (~ (type_code expected)) Maybe} + (case (~ g!temp) + (~+ (multi_level_case$ g!temp [mlc body])) + + (~+ (if initial_bind? + (list) + (list g!temp (` {.#None}))))))))))) _ - (failure "Wrong syntax for ^multi"))) + (failure "Wrong syntax for pattern#multi"))) ... TODO: Allow asking the compiler for the name of the definition ... currently being defined. That name can then be fed into @@ -4704,7 +4702,7 @@ (macro: .public (symbol tokens) (case tokens - (^ (list [_ {#Symbol [module name]}])) + (pattern (list [_ {#Symbol [module name]}])) (meta#in (list (` [(~ (text$ module)) (~ (text$ name))]))) _ @@ -4715,32 +4713,9 @@ (-> a a Bit)) ("lux is" reference sample)) -(macro: .public (^let tokens) - (case tokens - (^ (list& [_meta {#Form (list [_ {#Symbol ["" name]}] pattern)}] body branches)) - (let [g!whole (local_symbol$ name)] - (meta#in (list& g!whole - (` (case (~ g!whole) (~ pattern) (~ body))) - branches))) - - _ - (failure (..wrong_syntax_error (symbol ..^let))))) - -(macro: .public (^|> tokens) - (case tokens - (^ (list& [_meta {#Form (list [_ {#Symbol ["" name]}] [_ {#Tuple steps}])}] body branches)) - (let [g!name (local_symbol$ name)] - (meta#in (list& g!name - (` (let [(~ g!name) (|> (~ g!name) (~+ steps))] - (~ body))) - branches))) - - _ - (failure (..wrong_syntax_error (symbol ..^|>))))) - (macro: .public (:expected tokens) (case tokens - (^ (list expr)) + (pattern (list expr)) (do meta_monad [type ..expected_type] (in (list (` ("lux type as" (~ (type_code type)) (~ expr)))))) @@ -4768,12 +4743,12 @@ (macro: .public (:of tokens) (case tokens - (^ (list [_ {#Symbol var_name}])) + (pattern (list [_ {#Symbol var_name}])) (do meta_monad [var_type (type_definition var_name)] (in (list (type_code var_type)))) - (^ (list expression)) + (pattern (list expression)) (do meta_monad [g!temp (..generated_symbol "g!temp")] (in (list (` (let [(~ g!temp) (~ expression)] @@ -4806,7 +4781,7 @@ (in (list (` (macro: (~ export_policy) ((~ (local_symbol$ name)) (~ g!tokens) (~ g!compiler)) (case (~ g!tokens) - (^ (list (~+ (list#each local_symbol$ args)))) + (pattern (list (~+ (list#each local_symbol$ args)))) {.#Right [(~ g!compiler) (list (~+ (list#each (function (_ template) (` (`' (~ (with_replacements rep_env @@ -4834,8 +4809,8 @@ (macro: .public (char tokens compiler) (case tokens - (^multi (^ (list [_ {#Text input}])) - (|> input "lux text size" ("lux i64 =" 1))) + (pattern#multi (pattern (list [_ {#Text input}])) + (|> input "lux text size" ("lux i64 =" 1))) (|> input ("lux text char" 0) nat$ list [compiler] {#Right}) @@ -4860,8 +4835,8 @@ type+value (..definition_value symbol) .let [[type value] type+value]] (case (..flat_alias type) - (^or {#Primitive "#Text" {#End}} - {#Named ["library/lux" "Text"] {#Primitive "#Text" {#End}}}) + (pattern#or {#Primitive "#Text" {#End}} + {#Named ["library/lux" "Text"] {#Primitive "#Text" {#End}}}) (in (:as ..Text value)) _ @@ -4916,7 +4891,7 @@ (macro: .public (:parameter tokens) (case tokens - (^ (list [_ {#Nat idx}])) + (pattern (list [_ {#Nat idx}])) (do meta_monad [stvs ..scope_type_vars] (case (..item idx (list#reversed stvs)) @@ -4959,17 +4934,17 @@ (def: (embedded_expansions code) (-> Code (Meta [(List [Code Code]) Code])) (case code - (^ [ann {#Form (list [_ {#Symbol ["" "~~"]}] expansion)}]) + (pattern [ann {#Form (list [_ {#Symbol ["" "~~"]}] expansion)}]) (do meta_monad [g!expansion (..generated_symbol "g!expansion")] (in [(list [g!expansion expansion]) g!expansion])) - (^template [] - [[ann { parts}] - (do meta_monad - [=parts (monad#each meta_monad embedded_expansions parts)] - (in [(list#mix list#composite (list) (list#each product#left =parts)) - [ann { (list#each product#right =parts)}]]))]) + (pattern#template [] + [[ann { parts}] + (do meta_monad + [=parts (monad#each meta_monad embedded_expansions parts)] + (in [(list#mix list#composite (list) (list#each product#left =parts)) + [ann { (list#each product#right =parts)}]]))]) ([#Form] [#Variant] [#Tuple]) @@ -4979,7 +4954,7 @@ (macro: .public (`` tokens) (case tokens - (^ (list raw)) + (pattern (list raw)) (do meta_monad [=raw (..embedded_expansions raw) .let [[labels labelled] =raw]] @@ -4991,85 +4966,6 @@ _ (failure (..wrong_syntax_error (symbol ..``))))) -(def: (name$ [module name]) - (-> Symbol Code) - (` [(~ (text$ module)) (~ (text$ name))])) - -(def: (untemplated_list& last inits) - (-> Code (List Code) Code) - (case inits - {#End} - last - - {#Item [init inits']} - (` {.#Item (~ init) (~ (untemplated_list& last inits'))}))) - -(template [ ] - [(def: ( g!meta untemplated_pattern elems) - (-> Code (-> Code (Meta Code)) - (-> (List Code) (Meta Code))) - (case (list#reversed elems) - {#Item [_ {#Form {#Item [[_ {#Symbol ["" "~+"]}] {#Item [spliced {#End}]}]}}] - inits} - (do meta_monad - [=inits (monad#each meta_monad untemplated_pattern (list#reversed inits))] - (in (` [(~ g!meta) { (~ (untemplated_list& spliced =inits))}]))) - - _ - (do meta_monad - [=elems (monad#each meta_monad untemplated_pattern elems)] - (in (` [(~ g!meta) { (~ (untemplated_list =elems))}])))))] - - [.#Form untemplated_form] - [.#Variant untemplated_variant] - [.#Tuple untemplated_tuple] - ) - -(def: (untemplated_pattern pattern) - (-> Code (Meta Code)) - (do meta_monad - [g!meta (..generated_symbol "g!meta")] - (case pattern - (^template [ ] - [[_ { value}] - (in (` [(~ g!meta) { (~ ( value))}]))]) - ([.#Bit bit$] - [.#Nat nat$] - [.#Int int$] - [.#Rev rev$] - [.#Frac frac$] - [.#Text text$] - [.#Symbol name$]) - - [_ {#Form {#Item [[_ {#Symbol ["" "~"]}] {#Item [unquoted {#End}]}]}}] - (meta#in unquoted) - - [_ {#Form {#Item [[_ {#Symbol ["" "~+"]}] {#Item [spliced {#End}]}]}}] - (failure "Cannot use (~+) inside of ^code unless it is the last element in a form or a tuple.") - - (^template [ ] - [[_ { elems}] - ( g!meta untemplated_pattern elems)]) - ([#Form ..untemplated_form] - [#Variant ..untemplated_variant] - [#Tuple ..untemplated_tuple]) - ))) - -(macro: .public (^code tokens) - (case tokens - (^ (list& [_meta {#Form (list template)}] body branches)) - (do meta_monad - [pattern (untemplated_pattern template)] - (in (list& pattern body branches))) - - (^ (list template)) - (do meta_monad - [pattern (untemplated_pattern template)] - (in (list pattern))) - - _ - (failure (..wrong_syntax_error (symbol ..^code))))) - (def: .public false Bit #0) @@ -5080,7 +4976,7 @@ (macro: .public (:let tokens) (case tokens - (^ (list [_ {#Tuple bindings}] bodyT)) + (pattern (list [_ {#Tuple bindings}] bodyT)) (case (..pairs bindings) {#Some bindings} (meta#in (list (` (..with_expansions [(~+ (|> bindings @@ -5097,7 +4993,7 @@ (macro: .public (try tokens) (case tokens - (^ (list expression)) + (pattern (list expression)) (do meta_monad [g!_ (..generated_symbol "g!_")] (in (list (` ("lux try" @@ -5110,10 +5006,10 @@ (def: (methodP tokens) (-> (List Code) (Maybe [(List Code) [Text Code]])) (case tokens - (^ (list& [_ {#Form (list [_ {#Text "lux type check"}] - type - [_ {#Symbol ["" name]}])}] - tokens')) + (pattern (list& [_ {#Form (list [_ {#Text "lux type check"}] + type + [_ {#Symbol ["" name]}])}] + tokens')) {#Some [tokens' [name type]]} _ @@ -5139,16 +5035,16 @@ (macro: .public (Rec tokens) (case tokens - (^ (list [_ {#Symbol "" name}] body)) + (pattern (list [_ {#Symbol "" name}] body)) (do meta_monad [body' (expansion body) g!self (generated_symbol "g!self") g!dummy (generated_symbol "g!dummy")] (case body' - (^ (list body' labels)) + (pattern (list body' labels)) (in (list (..recursive_type g!self g!dummy name body') labels)) - (^ (list body')) + (pattern (list body')) (in (list (..recursive_type g!self g!dummy name body'))) _ -- cgit v1.2.3