diff options
author | Eduardo Julian | 2022-03-15 07:24:35 -0400 |
---|---|---|
committer | Eduardo Julian | 2022-03-15 07:24:35 -0400 |
commit | bc36487224f670c23002cc4575c0dba3e5dc1be1 (patch) | |
tree | 01601f7e5d992ace77a16cfa90240ffc4511a7af /stdlib/source | |
parent | 4ef1ac1dfe0edd1a11bb7f1fd13c8b6cb8f1bab4 (diff) |
De-sigil-ification: ^
Diffstat (limited to '')
257 files changed, 4152 insertions, 3763 deletions
diff --git a/stdlib/source/documentation/lux.lux b/stdlib/source/documentation/lux.lux index efa13a913..bbefd85a6 100644 --- a/stdlib/source/documentation/lux.lux +++ b/stdlib/source/documentation/lux.lux @@ -358,12 +358,12 @@ _ {#None})]) -(documentation: /.^ +(documentation: /.pattern (format "Macro-expanding patterns." \n "It's a special macro meant to be used with 'case'.") [(case (: (List Int) (list +1 +2 +3)) - (^ (list x y z)) + (pattern (list x y z)) {#Some ($_ * x y z)} _ @@ -433,8 +433,8 @@ [(macro: .public (symbol tokens) (case tokens (^template [<tag>] - [(^ (list [_ {<tag> [module name]}])) - (in (list (` [(~ (text$ module)) (~ (text$ name))])))]) + [(pattern (list [_ {<tag> [module name]}])) + (in (list (` [(~ (text$ module)) (~ (text$ name))])))]) ([#Symbol]) _ @@ -529,12 +529,12 @@ (format "Character used to separate the parts of module names." \n "Value: " (%.text /.module_separator))) -(documentation: /.^open +(documentation: /.open (format "Same as the 'open' macro, but meant to be used as a pattern-matching macro for generating local bindings." \n "Takes an 'alias' text for the generated local bindings.") [(def: .public (range enum from to) (All (_ a) (-> (Enum a) a a (List a))) - (let [(^open "[0]") enum] + (let [(open "[0]") enum] (loop [end to output {.#End}] (cond (< end from) @@ -642,23 +642,23 @@ {.#Primitive name (list#each (reduced env) params)} (^template [<tag>] - [{<tag> left right} - {<tag> (reduced env left) (reduced env right)}]) + [{<tag> left right} + {<tag> (reduced env left) (reduced env right)}]) ([.#Sum] [.#Product]) (^template [<tag>] - [{<tag> left right} - {<tag> (reduced env left) (reduced env right)}]) + [{<tag> left right} + {<tag> (reduced env left) (reduced env right)}]) ([.#Function] [.#Apply]) (^template [<tag>] - [{<tag> old_env def} - (case old_env - {.#End} - {<tag> env def} + [{<tag> old_env def} + (case old_env + {.#End} + {<tag> env def} - _ - type)]) + _ + type)]) ([.#UnivQ] [.#ExQ]) {.#Parameter idx} @@ -727,13 +727,13 @@ [(def: my_nat 123) (def: my_text "456") (and (case [my_nat my_text] - (^ (static [..my_nat ..my_text])) + (pattern (static [..my_nat ..my_text])) true _ false) (case [my_nat my_text] - (^ [(static ..my_nat) (static ..my_text)]) + (pattern [(static ..my_nat) (static ..my_text)]) true _ @@ -959,7 +959,7 @@ ..Rec ..exec ..case - ..^ + ..pattern ..^or ..let ..function @@ -979,7 +979,7 @@ ..int ..rev ..module_separator - ..^open + ..open ..cond ..the ..open: diff --git a/stdlib/source/documentation/lux/control/security/policy.lux b/stdlib/source/documentation/lux/control/security/policy.lux index bf9e6cb61..9bb54bef8 100644 --- a/stdlib/source/documentation/lux/control/security/policy.lux +++ b/stdlib/source/documentation/lux/control/security/policy.lux @@ -1,14 +1,14 @@ (.using - [library - [lux "*" - ["$" documentation {"+" documentation:}] - [data - [text {"+" \n} - ["%" format {"+" format}]]] - [macro - ["[0]" template]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["$" documentation {"+" documentation:}] + [data + [text {"+" \n} + ["%" format {"+" format}]]] + [macro + ["[0]" template]]]] + [\\library + ["[0]" /]]) (documentation: (/.Policy brand value %) "A security policy encoded as the means to 'upgrade' or 'downgrade' in a secure context.") @@ -48,7 +48,7 @@ (Ex (_ %) (-> Any (Policy %))) (with_policy (: (Context Privacy Policy) - (function (_ (^open "%::.")) + (function (_ (open "%::.")) (implementation (def: (password value) (%::can_upgrade value)) diff --git a/stdlib/source/documentation/lux/data/collection/stream.lux b/stdlib/source/documentation/lux/data/collection/stream.lux index 6961530c6..4d3e89a52 100644 --- a/stdlib/source/documentation/lux/data/collection/stream.lux +++ b/stdlib/source/documentation/lux/data/collection/stream.lux @@ -1,19 +1,19 @@ (.using - [library - [lux {"-" list} - ["$" documentation {"+" documentation:}] - [control - ["<>" parser - ["<[0]>" code]]] - [data - ["[0]" text {"+" \n} - ["%" format {"+" format}]]] - [macro - [syntax {"+" syntax:}] - ["[0]" code] - ["[0]" template]]]] - [\\library - ["[0]" /]]) + [library + [lux {"-" list} + ["$" documentation {"+" documentation:}] + [control + ["<>" parser + ["<[0]>" code]]] + [data + ["[0]" text {"+" \n} + ["%" format {"+" format}]]] + [macro + [syntax {"+" syntax:}] + ["[0]" code] + ["[0]" template]]]] + [\\library + ["[0]" /]]) (documentation: (/.Stream it) "An infinite sequence of values.") @@ -44,10 +44,10 @@ \n "The right side contains all entries for which the predicate is #0.") [(partition left? xs)]) -(documentation: /.^stream& +(documentation: /.pattern (format "Allows destructuring of streams in pattern-matching expressions." \n "Caveat emptor: Only use it for destructuring, and not for testing values within the streams.") - [(let [(^stream& x y z _tail) (some_stream_func +1 +2 +3)] + [(let [(pattern x y z _tail) (some_stream_func +1 +2 +3)] (func x y z))]) (.def: .public documentation @@ -62,7 +62,7 @@ ..only ..partition - ..^stream& + ..pattern ($.default /.head) ($.default /.tail) ($.default /.functor) diff --git a/stdlib/source/documentation/lux/data/text/regex.lux b/stdlib/source/documentation/lux/data/text/regex.lux index 2b8bedfbc..631195a86 100644 --- a/stdlib/source/documentation/lux/data/text/regex.lux +++ b/stdlib/source/documentation/lux/data/text/regex.lux @@ -1,14 +1,14 @@ (.using - [library - [lux "*" - ["$" documentation {"+" documentation:}] - [data - [text {"+" \n} - ["%" format {"+" format}]]] - [macro - ["[0]" template]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["$" documentation {"+" documentation:}] + [data + [text {"+" \n} + ["%" format {"+" format}]]] + [macro + ["[0]" template]]]] + [\\library + ["[0]" /]]) (documentation: /.regex "Create lexers using regular-expression syntax." @@ -56,14 +56,14 @@ (regex "a|b") (regex "a(.)(.)|b(.)(.)")]) -(documentation: /.^regex +(documentation: /.pattern "Allows you to test text against regular expressions." [(case some_text - (^regex "(\d{3})-(\d{3})-(\d{4})" - [_ country_code area_code place_code]) + (pattern "(\d{3})-(\d{3})-(\d{4})" + [_ country_code area_code place_code]) do_some_thing_when_number - (^regex "\w+") + (pattern "\w+") do_some_thing_when_word _ @@ -74,6 +74,6 @@ ($.module /._ "" [..regex - ..^regex + ..pattern ($.default /.incorrect_quantification)] [])) 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 (<parser> tokens) (-> (List Code) (Maybe [(List Code) [Text (List <parameter_type>)]])) (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 [<name> <form> <message>] [(macro: .public (<name> tokens) (case (list#reversed tokens) - (^ (list& last init)) + (pattern (list& last init)) (meta#in (list (list#mix (: (-> Code Code Code) (function (_ pre post) (` <form>))) 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 [<name> <extension>] [(def: .public <name> @@ -4423,22 +4422,22 @@ {#Primitive name params} (` {.#Primitive (~ (text$ name)) (~ (untemplated_list (list#each type_code params)))}) - (^template [<tag>] - [{<tag> left right} - (` {<tag> (~ (type_code left)) (~ (type_code right))})]) + (pattern#template [<tag>] + [{<tag> left right} + (` {<tag> (~ (type_code left)) (~ (type_code right))})]) ([.#Sum] [.#Product] [.#Function] [.#Apply]) - (^template [<tag>] - [{<tag> id} - (` {<tag> (~ (nat$ id))})]) + (pattern#template [<tag>] + [{<tag> id} + (` {<tag> (~ (nat$ id))})]) ([.#Parameter] [.#Var] [.#Ex]) - (^template [<tag>] - [{<tag> env type} - (let [env' (untemplated_list (list#each type_code env))] - (` {<tag> (~ env') (~ (type_code type))}))]) + (pattern#template [<tag>] + [{<tag> env type} + (let [env' (untemplated_list (list#each type_code env))] + (` {<tag> (~ 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 [<tag>] - [[location {<tag> elems}] - (list [location {<tag> (list#conjoint (list#each (with_expansions' label tokens) elems))}])]) + (pattern#template [<tag>] + [[location {<tag> elems}] + (list [location {<tag> (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 [<name>] - [{#Named ["library/lux" <name>] _} - type]) + (pattern#template [<name>] + [{#Named ["library/lux" <name>] _} + type]) (["Bit"] ["Nat"] ["Int"] @@ -4570,9 +4569,9 @@ [type+value (definition_value name) .let [[type value] type+value]] (case (flat_alias type) - (^template [<name> <type> <wrapper>] - [{#Named ["library/lux" <name>] _} - (in (<wrapper> (:as <type> value)))]) + (pattern#template [<name> <type> <wrapper>] + [{#Named ["library/lux" <name>] _} + (in (<wrapper> (:as <type> 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 [<tag>] - [[meta {<tag> parts}] - (do meta_monad - [=parts (monad#each meta_monad static_literal parts)] - (in [meta {<tag> =parts}]))]) + (pattern#template [<tag>] + [[meta {<tag> parts}] + (do meta_monad + [=parts (monad#each meta_monad static_literal parts)] + (in [meta {<tag> =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 [<tag>] - [[ann {<tag> parts}] - (do meta_monad - [=parts (monad#each meta_monad embedded_expansions parts)] - (in [(list#mix list#composite (list) (list#each product#left =parts)) - [ann {<tag> (list#each product#right =parts)}]]))]) + (pattern#template [<tag>] + [[ann {<tag> parts}] + (do meta_monad + [=parts (monad#each meta_monad embedded_expansions parts)] + (in [(list#mix list#composite (list) (list#each product#left =parts)) + [ann {<tag> (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 [<tag> <name>] - [(def: (<name> 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) {<tag> (~ (untemplated_list& spliced =inits))}]))) - - _ - (do meta_monad - [=elems (monad#each meta_monad untemplated_pattern elems)] - (in (` [(~ g!meta) {<tag> (~ (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 [<tag> <gen>] - [[_ {<tag> value}] - (in (` [(~ g!meta) {<tag> (~ (<gen> 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 [<tag> <untemplated>] - [[_ {<tag> elems}] - (<untemplated> 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'))) _ diff --git a/stdlib/source/library/lux/abstract/comonad.lux b/stdlib/source/library/lux/abstract/comonad.lux index 8405c7152..b5c1598d2 100644 --- a/stdlib/source/library/lux/abstract/comonad.lux +++ b/stdlib/source/library/lux/abstract/comonad.lux @@ -1,16 +1,16 @@ (.using - [library - [lux "*" - [data - [collection - ["[0]" list ("[1]#[0]" mix)]]] - [math - [number - ["n" nat]]] - [meta - ["[0]" location]]]] - [// - [functor {"+" Functor}]]) + [library + [lux "*" + [data + [collection + ["[0]" list ("[1]#[0]" mix)]]] + [math + [number + ["n" nat]]] + [meta + ["[0]" location]]]] + [// + [functor {"+" Functor}]]) (type: .public (CoMonad w) (Interface @@ -26,10 +26,10 @@ (macro: .public (be tokens state) (case (: (Maybe [(Maybe Text) Code (List Code) Code]) (case tokens - (^ (list [_ {.#Tuple (list [_ {.#Symbol ["" name]}] comonad)}] [_ {.#Tuple bindings}] body)) + (pattern (list [_ {.#Tuple (list [_ {.#Symbol ["" name]}] comonad)}] [_ {.#Tuple bindings}] body)) {.#Some [{.#Some name} comonad bindings body]} - (^ (list comonad [_ {.#Tuple bindings}] body)) + (pattern (list comonad [_ {.#Tuple bindings}] body)) {.#Some [{.#None} comonad bindings body]} _ diff --git a/stdlib/source/library/lux/abstract/enum.lux b/stdlib/source/library/lux/abstract/enum.lux index f136fc92d..c172df2ab 100644 --- a/stdlib/source/library/lux/abstract/enum.lux +++ b/stdlib/source/library/lux/abstract/enum.lux @@ -12,7 +12,7 @@ (def: .public (range enum from to) (All (_ a) (-> (Enum a) a a (List a))) - (let [(^open "/#[0]") enum] + (let [(open "/#[0]") enum] (loop [end to output (`` (: (List (~~ (:of from))) {.#End}))] diff --git a/stdlib/source/library/lux/abstract/functor.lux b/stdlib/source/library/lux/abstract/functor.lux index fb3dab4c8..636e4c592 100644 --- a/stdlib/source/library/lux/abstract/functor.lux +++ b/stdlib/source/library/lux/abstract/functor.lux @@ -1,6 +1,6 @@ (.using - [library - [lux {"-" Or And}]]) + [library + [lux {"-" Or And}]]) (type: .public (Functor f) (Interface @@ -12,7 +12,7 @@ (type: .public (Or f g) (All (_ a) (.Or (f a) (g a)))) -(def: .public (sum (^open "f#[0]") (^open "g#[0]")) +(def: .public (sum (open "f#[0]") (open "g#[0]")) (All (_ F G) (-> (Functor F) (Functor G) (Functor (..Or F G)))) (implementation (def: (each f fa|ga) @@ -26,7 +26,7 @@ (type: .public (And f g) (All (_ a) (.And (f a) (g a)))) -(def: .public (product (^open "f#[0]") (^open "g#[0]")) +(def: .public (product (open "f#[0]") (open "g#[0]")) (All (_ F G) (-> (Functor F) (Functor G) (Functor (..And F G)))) (implementation (def: (each f [fa ga]) @@ -36,7 +36,7 @@ (type: .public (Then f g) (All (_ a) (f (g a)))) -(def: .public (composite (^open "f#[0]") (^open "g#[0]")) +(def: .public (composite (open "f#[0]") (open "g#[0]")) (All (_ F G) (-> (Functor F) (Functor G) (Functor (..Then F G)))) (implementation (def: (each f fga) diff --git a/stdlib/source/library/lux/abstract/interval.lux b/stdlib/source/library/lux/abstract/interval.lux index d16e140de..68865241c 100644 --- a/stdlib/source/library/lux/abstract/interval.lux +++ b/stdlib/source/library/lux/abstract/interval.lux @@ -35,7 +35,7 @@ (template [<name> <comp>] [(def: .public (<name> interval) (All (_ a) (-> (Interval a) Bit)) - (let [(^open ",#[0]") interval] + (let [(open ",#[0]") interval] (<comp> ,#bottom ,#top)))] [inner? (order.> ,#&order)] @@ -45,7 +45,7 @@ (def: .public (within? interval elem) (All (_ a) (-> (Interval a) a Bit)) - (let [(^open ",#[0]") interval] + (let [(open ",#[0]") interval] (cond (inner? interval) (and (order.>= ,#&order ,#bottom elem) (order.<= ,#&order ,#top elem)) @@ -61,7 +61,7 @@ (template [<name> <limit>] [(def: .public (<name> elem interval) (All (_ a) (-> a (Interval a) Bit)) - (let [(^open "[0]") interval] + (let [(open "[0]") interval] (= <limit> elem)))] [starts_with? bottom] @@ -96,7 +96,7 @@ (def: .public (precedes? reference sample) (All (_ a) (-> (Interval a) (Interval a) Bit)) - (let [(^open "[0]") reference + (let [(open "[0]") reference limit (# reference bottom)] (and (< limit (# sample bottom)) (< limit (# sample top))))) @@ -108,7 +108,7 @@ (template [<name> <comp>] [(def: .public (<name> reference sample) (All (_ a) (-> a (Interval a) Bit)) - (let [(^open ",#[0]") sample] + (let [(open ",#[0]") sample] (and (<comp> reference ,#bottom) (<comp> reference ,#top))))] @@ -118,7 +118,7 @@ (def: .public (meets? reference sample) (All (_ a) (-> (Interval a) (Interval a) Bit)) - (let [(^open ",#[0]") reference + (let [(open ",#[0]") reference limit (# reference bottom)] (and (,#= limit (# sample top)) (order.<= ,#&order limit (# sample bottom))))) @@ -131,7 +131,7 @@ (template [<name> <eq_side> <ineq> <ineq_side>] [(def: .public (<name> reference sample) (All (_ a) (-> (Interval a) (Interval a) Bit)) - (let [(^open ",#[0]") reference] + (let [(open ",#[0]") reference] (and (,#= (# reference <eq_side>) (# sample <eq_side>)) (<ineq> ,#&order @@ -146,7 +146,7 @@ (All (_ a) (Equivalence (Interval a))) (def: (= reference sample) - (let [(^open ",#[0]") reference] + (let [(open ",#[0]") reference] (and (,#= ,#bottom (# sample bottom)) (,#= ,#top (# sample top)))))) @@ -155,7 +155,7 @@ (cond (or (singleton? sample) (and (inner? reference) (inner? sample)) (and (outer? reference) (outer? sample))) - (let [(^open ",#[0]") reference] + (let [(open ",#[0]") reference] (and (order.>= ,#&order (# reference bottom) (# sample bottom)) (order.<= ,#&order (# reference top) (# sample top)))) @@ -164,7 +164,7 @@ #0 ... (and (outer? reference) (inner? sample)) - (let [(^open ",#[0]") reference] + (let [(open ",#[0]") reference] (or (and (order.>= ,#&order (# reference bottom) (# sample bottom)) (order.> ,#&order (# reference bottom) (# sample top))) (and (,#< (# reference top) (# sample bottom)) @@ -173,7 +173,7 @@ (def: .public (overlaps? reference sample) (All (_ a) (-> (Interval a) (Interval a) Bit)) - (let [(^open ",#[0]") reference] + (let [(open ",#[0]") reference] (and (not (# ..equivalence = reference sample)) (cond (singleton? sample) #0 diff --git a/stdlib/source/library/lux/abstract/mix.lux b/stdlib/source/library/lux/abstract/mix.lux index c3c0412ee..0a3c2088a 100644 --- a/stdlib/source/library/lux/abstract/mix.lux +++ b/stdlib/source/library/lux/abstract/mix.lux @@ -1,8 +1,8 @@ (.using - [library - [lux "*"]] - [// - [monoid {"+" Monoid}]]) + [library + [lux "*"]] + [// + [monoid {"+" Monoid}]]) (type: .public (Mix F) (Interface @@ -13,5 +13,5 @@ (def: .public (with_monoid monoid mix value) (All (_ F a) (-> (Monoid a) (Mix F) (F a) a)) - (let [(^open "/#[0]") monoid] + (let [(open "/#[0]") monoid] (mix /#composite /#identity value))) diff --git a/stdlib/source/library/lux/abstract/monad.lux b/stdlib/source/library/lux/abstract/monad.lux index ae57f2912..0802c0198 100644 --- a/stdlib/source/library/lux/abstract/monad.lux +++ b/stdlib/source/library/lux/abstract/monad.lux @@ -1,10 +1,10 @@ (.using - [library - [lux "*" - [meta - ["[0]" location]]]] - [// - [functor {"+" Functor}]]) + [library + [lux "*" + [meta + ["[0]" location]]]] + [// + [functor {"+" Functor}]]) (def: (list#mix f init xs) (All (_ a b) @@ -57,10 +57,10 @@ (macro: .public (do tokens state) (case (: (Maybe [(Maybe Text) Code (List Code) Code]) (case tokens - (^ (list [_ {.#Tuple (list [_ {.#Symbol ["" name]}] monad)}] [_ {.#Tuple bindings}] body)) + (pattern (list [_ {.#Tuple (list [_ {.#Symbol ["" name]}] monad)}] [_ {.#Tuple bindings}] body)) {.#Some [{.#Some name} monad bindings body]} - (^ (list monad [_ {.#Tuple bindings}] body)) + (pattern (list monad [_ {.#Tuple bindings}] body)) {.#Some [{.#None} monad bindings body]} _ @@ -117,7 +117,7 @@ (All (_ ! a) (-> (Monad !) (List (! a)) (! (List a)))) - (let [(^open "!#[0]") monad] + (let [(open "!#[0]") monad] (function (again xs) (case xs {.#End} @@ -133,7 +133,7 @@ (All (_ M a b) (-> (Monad M) (-> a (M b)) (List a) (M (List b)))) - (let [(^open "!#[0]") monad] + (let [(open "!#[0]") monad] (function (again xs) (case xs {.#End} @@ -149,7 +149,7 @@ (All (_ ! a b) (-> (Monad !) (-> a (! Bit)) (List a) (! (List a)))) - (let [(^open "!#[0]") monad] + (let [(open "!#[0]") monad] (function (again xs) (case xs {.#End} diff --git a/stdlib/source/library/lux/control/concurrency/async.lux b/stdlib/source/library/lux/control/concurrency/async.lux index 489513399..32bc8cca1 100644 --- a/stdlib/source/library/lux/control/concurrency/async.lux +++ b/stdlib/source/library/lux/control/concurrency/async.lux @@ -11,6 +11,8 @@ ["[0]" io {"+" IO io}]] [data ["[0]" product]] + [macro + ["^" pattern]] [type {"+" :sharing} abstract]]] [// @@ -29,7 +31,7 @@ (function (resolve value) (let [async (:representation async)] (do [! io.monad] - [(^let old [_value _observers]) (atom.read! async)] + [(^.let old [_value _observers]) (atom.read! async)] (case _value {.#Some _} (in #0) @@ -64,7 +66,7 @@ (All (_ a) (-> (-> a (IO Any)) (Async a) (IO Any))) (do [! io.monad] [.let [async (:representation async)] - (^let old [_value _observers]) (atom.read! async)] + (^.let old [_value _observers]) (atom.read! async)] (case _value {.#Some value} (f value) diff --git a/stdlib/source/library/lux/control/concurrency/stm.lux b/stdlib/source/library/lux/control/concurrency/stm.lux index 22ebc470e..2be44daba 100644 --- a/stdlib/source/library/lux/control/concurrency/stm.lux +++ b/stdlib/source/library/lux/control/concurrency/stm.lux @@ -13,6 +13,8 @@ ["[0]" product] [collection ["[0]" list]]] + [macro + ["^" pattern]] [type abstract]]] [// @@ -46,7 +48,7 @@ (All (_ a) (-> a (Var a) (IO Any))) (do [! io.monad] [.let [var' (:representation var)] - (^let old [old_value observers]) (atom.read! var') + (^.let old [old_value observers]) (atom.read! var') succeeded? (atom.compare_and_swap! old [new_value observers] var')] (if succeeded? (do ! diff --git a/stdlib/source/library/lux/control/function/memo.lux b/stdlib/source/library/lux/control/function/memo.lux index 5d25cae50..381a1ba28 100644 --- a/stdlib/source/library/lux/control/function/memo.lux +++ b/stdlib/source/library/lux/control/function/memo.lux @@ -1,19 +1,19 @@ ... Inspired by; ... "The Different Aspects of Monads and Mixins" by Bruno C. d. S. Oliveira (.using - [library - [lux "*" - [abstract - [hash {"+" Hash}] - [monad {"+" do}]] - [control - ["[0]" state {"+" State}]] - [data - ["[0]" product] - [collection - ["[0]" dictionary {"+" Dictionary}]]]]] - ["[0]" // "_" - ["[1]" mixin {"+" Mixin Recursive}]]) + [library + [lux {"-" open} + [abstract + [hash {"+" Hash}] + [monad {"+" do}]] + [control + ["[0]" state {"+" State}]] + [data + ["[0]" product] + [collection + ["[0]" dictionary {"+" Dictionary}]]]]] + ["[0]" // "_" + ["[1]" mixin {"+" Mixin Recursive}]]) (def: .public memoization (All (_ i o) diff --git a/stdlib/source/library/lux/control/function/mutual.lux b/stdlib/source/library/lux/control/function/mutual.lux index 102457383..ba9da195e 100644 --- a/stdlib/source/library/lux/control/function/mutual.lux +++ b/stdlib/source/library/lux/control/function/mutual.lux @@ -111,8 +111,8 @@ (in (list)) {.#Item definition {.#End}} - (.let [(^open "_[0]") definition - (^open "_[0]") _#mutual] + (.let [(open "_[0]") definition + (open "_[0]") _#mutual] (in (list (` (.def: (~ _#export_policy) (~ (declaration.format _#declaration)) (~ _#type) (~ _#body)))))) diff --git a/stdlib/source/library/lux/control/lazy.lux b/stdlib/source/library/lux/control/lazy.lux index 8d3c877d8..01b3432cd 100644 --- a/stdlib/source/library/lux/control/lazy.lux +++ b/stdlib/source/library/lux/control/lazy.lux @@ -47,7 +47,7 @@ (with_symbols [g!_] (in (list (` ((~! ..lazy') (function ((~ g!_) (~ g!_)) (~ expression)))))))) -(implementation: .public (equivalence (^open "_#[0]")) +(implementation: .public (equivalence (open "_#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (Lazy a)))) (def: (= left right) diff --git a/stdlib/source/library/lux/control/maybe.lux b/stdlib/source/library/lux/control/maybe.lux index 386548905..cd963db10 100644 --- a/stdlib/source/library/lux/control/maybe.lux +++ b/stdlib/source/library/lux/control/maybe.lux @@ -127,7 +127,7 @@ (macro: .public (else tokens state) (case tokens - (^ (.list else maybe)) + (pattern (.list else maybe)) (let [g!temp (: Code [location.dummy {.#Symbol ["" ""]}])] {.#Right [state (.list (` (.case (~ maybe) {.#Some (~ g!temp)} @@ -156,7 +156,7 @@ (macro: .public (when tokens state) (case tokens - (^ (.list test then)) + (pattern (.list test then)) {.#Right [state (.list (` (.if (~ test) (~ then) {.#None})))]} diff --git a/stdlib/source/library/lux/control/parser/analysis.lux b/stdlib/source/library/lux/control/parser/analysis.lux index 31bc63a43..0d1fb35c5 100644 --- a/stdlib/source/library/lux/control/parser/analysis.lux +++ b/stdlib/source/library/lux/control/parser/analysis.lux @@ -1,37 +1,37 @@ (.using - [library - [lux {"-" nat int rev local} - [abstract - [monad {"+" do}]] - [control - ["[0]" try {"+" Try}] - ["[0]" exception {"+" exception:}]] - [data - ["[0]" bit] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [macro - ["[0]" template]] - [math - [number - ["[0]" i64] - ["[0]" nat] - ["[0]" int] - ["[0]" rev] - ["[0]" frac]]] - [meta - ["[0]" symbol]] - [tool - [compiler - [arity {"+" Arity}] - [reference {"+" } - [variable {"+" }]] - [language - [lux - ["/" analysis {"+" Environment Analysis}]]]]]]] - ["[0]" //]) + [library + [lux {"-" nat int rev local} + [abstract + [monad {"+" do}]] + [control + ["[0]" try {"+" Try}] + ["[0]" exception {"+" exception:}]] + [data + ["[0]" bit] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [macro + ["[0]" template]] + [math + [number + ["[0]" i64] + ["[0]" nat] + ["[0]" int] + ["[0]" rev] + ["[0]" frac]]] + [meta + ["[0]" symbol]] + [tool + [compiler + [arity {"+" Arity}] + [reference {"+" } + [variable {"+" }]] + [language + [lux + ["/" analysis {"+" Environment Analysis}]]]]]]] + ["[0]" //]) (def: (remaining_inputs asts) (-> (List Analysis) Text) @@ -93,7 +93,7 @@ (Parser <type>) (function (_ input) (case input - (^ (list& (<tag> x) input')) + (pattern (list& (<tag> x) input')) {try.#Success [input' x]} _ @@ -103,7 +103,7 @@ (-> <type> (Parser Any)) (function (_ input) (case input - (^ (list& (<tag> actual) input')) + (pattern (list& (<tag> actual) input')) (if (# <eq> = expected actual) {try.#Success [input' []]} (exception.except ..cannot_parse input)) @@ -126,7 +126,7 @@ (All (_ a) (-> (Parser a) (Parser a))) (function (_ input) (case input - (^ (list& (/.tuple head) tail)) + (pattern (list& (/.tuple head) tail)) (do try.monad [output (..result parser head)] {try.#Success [tail output]}) diff --git a/stdlib/source/library/lux/control/parser/binary.lux b/stdlib/source/library/lux/control/parser/binary.lux index a3430e4d7..a9ed31dbd 100644 --- a/stdlib/source/library/lux/control/parser/binary.lux +++ b/stdlib/source/library/lux/control/parser/binary.lux @@ -19,6 +19,7 @@ ["[0]" sequence {"+" Sequence}] ["[0]" set {"+" Set}]]] [macro + ["^" pattern] ["[0]" template]] [math [number @@ -52,17 +53,17 @@ (def: .public end? (Parser Bit) - (function (_ (^let input [offset data])) + (function (_ (^.let input [offset data])) {try.#Success [input (n.= offset (/.size data))]})) (def: .public offset (Parser Offset) - (function (_ (^let input [offset data])) + (function (_ (^.let input [offset data])) {try.#Success [input offset]})) (def: .public remaining (Parser Nat) - (function (_ (^let input [offset data])) + (function (_ (^.let input [offset data])) {try.#Success [input (n.- offset (/.size data))]})) (type: .public Size @@ -114,7 +115,7 @@ ..bits/8)] (with_expansions [<case>+' (template.spliced <case>+)] (case flag - (^template [<number> <tag> <parser>] + (^.template [<number> <tag> <parser>] [<number> (`` (# ! each (|>> {(~~ (template.spliced <tag>))}) <parser>))]) (<case>+') diff --git a/stdlib/source/library/lux/control/parser/json.lux b/stdlib/source/library/lux/control/parser/json.lux index 87c0ce5db..f17c4c763 100644 --- a/stdlib/source/library/lux/control/parser/json.lux +++ b/stdlib/source/library/lux/control/parser/json.lux @@ -1,26 +1,26 @@ (.using - [library - [lux {"-" symbol} - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" try {"+" Try}] - ["[0]" exception {"+" exception:}]] - [data - ["[0]" bit] - ["[0]" text ("[1]#[0]" equivalence monoid)] - [collection - ["[0]" list ("[1]#[0]" functor)] - ["[0]" sequence] - ["[0]" dictionary {"+" Dictionary}]] - [format - ["/" json {"+" JSON}]]] - [macro - ["[0]" code]] - [math - [number - ["[0]" frac]]]]] - ["[0]" // ("[1]#[0]" functor)]) + [library + [lux {"-" symbol} + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" try {"+" Try}] + ["[0]" exception {"+" exception:}]] + [data + ["[0]" bit] + ["[0]" text ("[1]#[0]" equivalence monoid)] + [collection + ["[0]" list ("[1]#[0]" functor)] + ["[0]" sequence] + ["[0]" dictionary {"+" Dictionary}]] + [format + ["/" json {"+" JSON}]]] + [macro + ["[0]" code]] + [math + [number + ["[0]" frac]]]]] + ["[0]" // ("[1]#[0]" functor)]) (type: .public (Parser a) (//.Parser (List JSON) a)) @@ -169,7 +169,7 @@ (All (_ a) (-> Text (Parser a) (Parser a))) (function (again inputs) (case inputs - (^ (list& {/.#String key} value inputs')) + (pattern (list& {/.#String key} value inputs')) (if (text#= key field_name) (case (//.result parser (list value)) {try.#Success [{.#End} output]} diff --git a/stdlib/source/library/lux/control/parser/synthesis.lux b/stdlib/source/library/lux/control/parser/synthesis.lux index d0cebbb12..66976a680 100644 --- a/stdlib/source/library/lux/control/parser/synthesis.lux +++ b/stdlib/source/library/lux/control/parser/synthesis.lux @@ -92,7 +92,7 @@ (Parser <type>) (.function (_ input) (case input - (^ (list& (<tag> x) input')) + (pattern (list& (<tag> x) input')) {try.#Success [input' x]} _ @@ -102,7 +102,7 @@ (-> <type> (Parser Any)) (.function (_ input) (case input - (^ (list& (<tag> actual) input')) + (pattern (list& (<tag> actual) input')) (if (# <eq> = expected actual) {try.#Success [input' []]} (exception.except ..cannot_parse input)) @@ -123,7 +123,7 @@ (All (_ a) (-> (Parser a) (Parser a))) (.function (_ input) (case input - (^ (list& (/.tuple head) tail)) + (pattern (list& (/.tuple head) tail)) (do try.monad [output (..result parser head)] {try.#Success [tail output]}) @@ -135,7 +135,7 @@ (All (_ a) (-> Arity (Parser a) (Parser [(Environment Synthesis) a]))) (.function (_ input) (case input - (^ (list& (/.function/abstraction [environment actual body]) tail)) + (pattern (list& (/.function/abstraction [environment actual body]) tail)) (if (n.= expected actual) (do try.monad [output (..result parser (list body))] @@ -149,7 +149,7 @@ (All (_ a b) (-> (Parser a) (Parser b) (Parser [Register a b]))) (.function (_ input) (case input - (^ (list& (/.loop/scope [start inits iteration]) tail)) + (pattern (list& (/.loop/scope [start inits iteration]) tail)) (do try.monad [inits (..result init_parsers inits) iteration (..result iteration_parser (list iteration))] diff --git a/stdlib/source/library/lux/control/parser/text.lux b/stdlib/source/library/lux/control/parser/text.lux index 8fe67d90f..4767ef744 100644 --- a/stdlib/source/library/lux/control/parser/text.lux +++ b/stdlib/source/library/lux/control/parser/text.lux @@ -13,6 +13,7 @@ [collection ["[0]" list ("[1]#[0]" mix)]]] [macro + ["^" pattern] ["[0]" code] ["[0]" template]] [math @@ -68,7 +69,7 @@ (def: .public offset (Parser Offset) - (function (_ (^let input [offset tape])) + (function (_ (^.let input [offset tape])) {try.#Success [input offset]})) (def: (with_slices parser) @@ -139,14 +140,14 @@ (def: .public end! (Parser Any) - (function (_ (^let input [offset tape])) + (function (_ (^.let input [offset tape])) (if (n.= offset (/.size tape)) {try.#Success [input []]} (exception.except ..unconsumed_input input)))) (def: .public next (Parser Text) - (function (_ (^let input [offset tape])) + (function (_ (^.let input [offset tape])) (case (/.char offset tape) {.#Some output} {try.#Success [input (/.of_char output)]} @@ -156,7 +157,7 @@ (def: .public remaining (Parser Text) - (function (_ (^let input [offset tape])) + (function (_ (^.let input [offset tape])) {try.#Success [input (..left_over offset tape)]})) (def: .public (range bottom top) @@ -350,7 +351,7 @@ (-> (Parser Slice) (Parser Text)) (do //.monad [[basis distance] parser] - (function (_ (^let input [offset tape])) + (function (_ (^.let input [offset tape])) (case (/.clip basis distance tape) {.#Some output} {try.#Success [input output]} diff --git a/stdlib/source/library/lux/control/parser/type.lux b/stdlib/source/library/lux/control/parser/type.lux index 3f4da5ee2..726454fe0 100644 --- a/stdlib/source/library/lux/control/parser/type.lux +++ b/stdlib/source/library/lux/control/parser/type.lux @@ -14,6 +14,7 @@ ["[0]" list ("[1]#[0]" functor)] ["[0]" dictionary {"+" Dictionary}]]] [macro + ["^" pattern] ["[0]" code]] [math [number @@ -310,7 +311,7 @@ (do [! //.monad] [headT any] (case (type.anonymous headT) - (^ {.#Apply (|recursion_dummy|) {.#UnivQ _ headT'}}) + (pattern {.#Apply (|recursion_dummy|) {.#UnivQ _ headT'}}) (do ! [[recT _ output] (|> poly (with_extension (|recursion_dummy|)) @@ -327,9 +328,9 @@ [env ..env headT any] (case (type.anonymous headT) - (^multi (^ {.#Apply (|recursion_dummy|) {.#Parameter funcT_idx}}) - (n.= 0 (..argument env funcT_idx)) - [(dictionary.value 0 env) {.#Some [self_type self_call]}]) + (^.multi (pattern {.#Apply (|recursion_dummy|) {.#Parameter funcT_idx}}) + (n.= 0 (..argument env funcT_idx)) + [(dictionary.value 0 env) {.#Some [self_type self_call]}]) (in self_call) _ diff --git a/stdlib/source/library/lux/control/pipe.lux b/stdlib/source/library/lux/control/pipe.lux index 5251267d6..b65802ce6 100644 --- a/stdlib/source/library/lux/control/pipe.lux +++ b/stdlib/source/library/lux/control/pipe.lux @@ -19,12 +19,12 @@ ["n" nat] ["i" int]]]]]) -(def: body^ +(def: body (Parser (List Code)) (<code>.tuple (<>.some <code>.any))) (syntax: .public (new [start <code>.any - body body^ + body ..body prev <code>.any]) (in (list (` (|> (~ start) (~+ body)))))) @@ -41,9 +41,9 @@ (syntax: .public (cond [_ _reversed_ prev <code>.any - else body^ + else ..body _ _reversed_ - branches (<>.some (<>.and body^ body^))]) + branches (<>.some (<>.and ..body ..body))]) (with_symbols [g!temp] (in (list (` (.let [(~ g!temp) (~ prev)] (.cond (~+ (monad.do list.monad @@ -52,23 +52,23 @@ (` (|> (~ g!temp) (~+ then)))))) (|> (~ g!temp) (~+ else))))))))) -(syntax: .public (if [test body^ - then body^ - else body^ +(syntax: .public (if [test ..body + then ..body + else ..body prev <code>.any]) (in (list (` (..cond [(~+ test)] [(~+ then)] [(~+ else)] (~ prev)))))) -(syntax: .public (when [test body^ - then body^ +(syntax: .public (when [test ..body + then ..body prev <code>.any]) (in (list (` (..cond [(~+ test)] [(~+ then)] [] (~ prev)))))) -(syntax: .public (loop [test body^ - then body^ +(syntax: .public (loop [test ..body + then ..body prev <code>.any]) (with_symbols [g!temp] (in (list (` (.loop [(~ g!temp) (~ prev)] @@ -77,11 +77,11 @@ (~ g!temp)))))))) (syntax: .public (do [monad <code>.any - steps (<>.some body^) + steps (<>.some ..body) prev <code>.any]) (with_symbols [g!temp] (.case (list.reversed steps) - (^ (list& last_step prev_steps)) + (pattern (list& last_step prev_steps)) (.let [step_bindings (monad.do list.monad [step (list.reversed prev_steps)] (list g!temp (` (|> (~ g!temp) (~+ step)))))] @@ -93,14 +93,14 @@ _ (in (list prev))))) -(syntax: .public (exec [body body^ +(syntax: .public (exec [body ..body prev <code>.any]) (with_symbols [g!temp] (in (list (` (.let [(~ g!temp) (~ prev)] (.exec (|> (~ g!temp) (~+ body)) (~ g!temp)))))))) -(syntax: .public (tuple [paths (<>.many body^) +(syntax: .public (tuple [paths (<>.many ..body) prev <code>.any]) (with_symbols [g!temp] (in (list (` (.let [(~ g!temp) (~ prev)] diff --git a/stdlib/source/library/lux/control/try.lux b/stdlib/source/library/lux/control/try.lux index d1722f394..6f50ef702 100644 --- a/stdlib/source/library/lux/control/try.lux +++ b/stdlib/source/library/lux/control/try.lux @@ -91,7 +91,7 @@ (All (_ ! a) (-> (Monad !) (-> (! a) (! (Try a))))) (# monad each (# ..monad in))) -(implementation: .public (equivalence (^open "_#[0]")) +(implementation: .public (equivalence (open "_#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (Try a)))) (def: (= reference sample) @@ -140,7 +140,7 @@ (macro: .public (else tokens compiler) (case tokens - (^ (list else try)) + (pattern (list else try)) {#Success [compiler (list (` (case (~ try) {..#Success (~' g!temp)} (~' g!temp) diff --git a/stdlib/source/library/lux/data/collection/dictionary.lux b/stdlib/source/library/lux/data/collection/dictionary.lux index 6ff9c51fe..8383fc8e1 100644 --- a/stdlib/source/library/lux/data/collection/dictionary.lux +++ b/stdlib/source/library/lux/data/collection/dictionary.lux @@ -15,6 +15,8 @@ ["[0]" list ("[1]#[0]" mix functor monoid)] ["[0]" array "_" ["[1]" \\unsafe {"+" Array}]]]] + [macro + ["^" pattern]] [math ["[0]" number ["n" nat] @@ -263,7 +265,7 @@ (Hash k) Level Bit_Map (Base k v) (Array (Node k v)))) - (product.right (list#mix (function (_ hierarchy_idx (^let default [base_idx h_array])) + (product.right (list#mix (function (_ hierarchy_idx (^.let default [base_idx h_array])) (if (with_bit_position? (to_bit_position hierarchy_idx) bitmap) [(++ base_idx) @@ -687,7 +689,7 @@ (empty key_hash) keys))) -(implementation: .public (equivalence (^open ",#[0]")) +(implementation: .public (equivalence (open ",#[0]")) (All (_ k v) (-> (Equivalence v) (Equivalence (Dictionary k v)))) (def: (= reference subject) diff --git a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux index 13f9c1568..d7e8d99d1 100644 --- a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux +++ b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux @@ -11,6 +11,8 @@ ["p" product] [collection ["[0]" list ("[1]#[0]" monoid mix)]]] + [macro + ["^" pattern]] [math [number ["n" nat]]]]]) @@ -58,7 +60,7 @@ ... TODO: Must improve it as soon as bug is fixed. (def: .public (value key dict) (All (_ k v) (-> k (Dictionary k v) (Maybe v))) - (let [... (^open "_#[0]") (the #&order dict) + (let [... (open "_#[0]") (the #&order dict) ] (loop [node (the #root dict)] (case node @@ -83,7 +85,7 @@ ... TODO: Must improve it as soon as bug is fixed. (def: .public (key? dict key) (All (_ k v) (-> (Dictionary k v) k Bit)) - (let [... (^open "_#[0]") (the #&order dict) + (let [... (open "_#[0]") (the #&order dict) ] (loop [node (the #root dict)] (case node @@ -167,8 +169,8 @@ (case (the #color addition) {#Red} (case (the #left addition) - (^multi {.#Some left} - [(the #color left) {#Red}]) + (^.multi {.#Some left} + [(the #color left) {#Red}]) (red (the #key addition) (the #value addition) {.#Some (blackened left)} @@ -179,8 +181,8 @@ _ (case (the #right addition) - (^multi {.#Some right} - [(the #color right) {#Red}]) + (^.multi {.#Some right} + [(the #color right) {#Red}]) (red (the #key right) (the #value right) {.#Some (black (the #key addition) @@ -216,8 +218,8 @@ (case (the #color addition) {#Red} (case (the #right addition) - (^multi {.#Some right} - [(the #color right) {#Red}]) + (^.multi {.#Some right} + [(the #color right) {#Red}]) (red (the #key addition) (the #value addition) {.#Some (black (the #key center) @@ -228,8 +230,8 @@ _ (case (the #left addition) - (^multi {.#Some left} - [(the #color left) {#Red}]) + (^.multi {.#Some left} + [(the #color left) {#Red}]) (red (the #key left) (the #value left) {.#Some (black (the #key center) @@ -249,7 +251,7 @@ (def: .public (has key value dict) (All (_ k v) (-> k v (Dictionary k v) (Dictionary k v))) - (let [(^open "_#[0]") (the #&order dict) + (let [(open "_#[0]") (the #&order dict) root' (loop [?root (the #root dict)] (case ?root {.#None} @@ -279,19 +281,19 @@ (def: (left_balanced key value ?left ?right) (All (_ k v) (-> k v (Maybe (Node k v)) (Maybe (Node k v)) (Node k v))) (case ?left - (^multi {.#Some left} - [(the #color left) {#Red}] - [(the #left left) {.#Some left>>left}] - [(the #color left>>left) {#Red}]) + (^.multi {.#Some left} + [(the #color left) {#Red}] + [(the #left left) {.#Some left>>left}] + [(the #color left>>left) {#Red}]) (red (the #key left) (the #value left) {.#Some (blackened left>>left)} {.#Some (black key value (the #right left) ?right)}) - (^multi {.#Some left} - [(the #color left) {#Red}] - [(the #right left) {.#Some left>>right}] - [(the #color left>>right) {#Red}]) + (^.multi {.#Some left} + [(the #color left) {#Red}] + [(the #right left) {.#Some left>>right}] + [(the #color left>>right) {#Red}]) (red (the #key left>>right) (the #value left>>right) {.#Some (black (the #key left) @@ -308,19 +310,19 @@ (def: (right_balanced key value ?left ?right) (All (_ k v) (-> k v (Maybe (Node k v)) (Maybe (Node k v)) (Node k v))) (case ?right - (^multi {.#Some right} - [(the #color right) {#Red}] - [(the #right right) {.#Some right>>right}] - [(the #color right>>right) {#Red}]) + (^.multi {.#Some right} + [(the #color right) {#Red}] + [(the #right right) {.#Some right>>right}] + [(the #color right>>right) {#Red}]) (red (the #key right) (the #value right) {.#Some (black key value ?left (the #left right))} {.#Some (blackened right>>right)}) - (^multi {.#Some right} - [(the #color right) {#Red}] - [(the #left right) {.#Some right>>left}] - [(the #color right>>left) {#Red}]) + (^.multi {.#Some right} + [(the #color right) {#Red}] + [(the #left right) {.#Some right>>left}] + [(the #color right>>left) {#Red}]) (red (the #key right>>left) (the #value right>>left) {.#Some (black key value ?left (the #left right>>left))} @@ -335,20 +337,20 @@ (def: (without_left key value ?left ?right) (All (_ k v) (-> k v (Maybe (Node k v)) (Maybe (Node k v)) (Node k v))) (case ?left - (^multi {.#Some left} - [(the #color left) {#Red}]) + (^.multi {.#Some left} + [(the #color left) {#Red}]) (red key value {.#Some (blackened left)} ?right) _ (case ?right - (^multi {.#Some right} - [(the #color right) {#Black}]) + (^.multi {.#Some right} + [(the #color right) {#Black}]) (right_balanced key value ?left {.#Some (reddened right)}) - (^multi {.#Some right} - [(the #color right) {#Red}] - [(the #left right) {.#Some right>>left}] - [(the #color right>>left) {#Black}]) + (^.multi {.#Some right} + [(the #color right) {#Red}] + [(the #left right) {.#Some right>>left}] + [(the #color right>>left) {#Black}]) (red (the #key right>>left) (the #value right>>left) {.#Some (black key value ?left (the #left right>>left))} @@ -364,20 +366,20 @@ (def: (without_right key value ?left ?right) (All (_ k v) (-> k v (Maybe (Node k v)) (Maybe (Node k v)) (Node k v))) (case ?right - (^multi {.#Some right} - [(the #color right) {#Red}]) + (^.multi {.#Some right} + [(the #color right) {#Red}]) (red key value ?left {.#Some (blackened right)}) _ (case ?left - (^multi {.#Some left} - [(the #color left) {#Black}]) + (^.multi {.#Some left} + [(the #color left) {#Black}]) (left_balanced key value {.#Some (reddened left)} ?right) - (^multi {.#Some left} - [(the #color left) {#Red}] - [(the #right left) {.#Some left>>right}] - [(the #color left>>right) {#Black}]) + (^.multi {.#Some left} + [(the #color left) {#Red}] + [(the #right left) {.#Some left>>right}] + [(the #color left>>right) {#Black}]) (red (the #key left>>right) (the #value left>>right) {.#Some (left_balanced (the #key left) @@ -472,7 +474,7 @@ (def: .public (lacks key dict) (All (_ k v) (-> k (Dictionary k v) (Dictionary k v))) - (let [(^open "_#[0]") (the #&order dict) + (let [(open "_#[0]") (the #&order dict) [?root found?] (loop [?root (the #root dict)] (case ?root {.#Some root} @@ -492,8 +494,8 @@ [side_outcome _] (if go_left? (case (the #left root) - (^multi {.#Some left} - [(the #color left) {#Black}]) + (^.multi {.#Some left} + [(the #color left) {#Black}]) [{.#Some (without_left root_key root_val side_outcome (the #right root))} #0] @@ -501,8 +503,8 @@ [{.#Some (red root_key root_val side_outcome (the #right root))} #0]) (case (the #right root) - (^multi {.#Some right} - [(the #color right) {#Black}]) + (^.multi {.#Some right} + [(the #color right) {#Black}]) [{.#Some (without_right root_key root_val (the #left root) side_outcome)} #0] @@ -560,11 +562,11 @@ [values v (the #value node')] ) -(implementation: .public (equivalence (^open ",#[0]")) +(implementation: .public (equivalence (open ",#[0]")) (All (_ k v) (-> (Equivalence v) (Equivalence (Dictionary k v)))) (def: (= reference sample) - (let [(^open "/#[0]") (the #&order reference)] + (let [(open "/#[0]") (the #&order reference)] (loop [entriesR (entries reference) entriesS (entries sample)] (case [entriesR entriesS] diff --git a/stdlib/source/library/lux/data/collection/dictionary/plist.lux b/stdlib/source/library/lux/data/collection/dictionary/plist.lux index 5417fca5d..03227f727 100644 --- a/stdlib/source/library/lux/data/collection/dictionary/plist.lux +++ b/stdlib/source/library/lux/data/collection/dictionary/plist.lux @@ -96,7 +96,7 @@ {.#Item [k' v'] (lacks key properties')}))) -(implementation: .public (equivalence (^open "/#[0]")) +(implementation: .public (equivalence (open "/#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (PList a)))) (def: (= reference subject) diff --git a/stdlib/source/library/lux/data/collection/list.lux b/stdlib/source/library/lux/data/collection/list.lux index 4992f3ae0..4b0071ddd 100644 --- a/stdlib/source/library/lux/data/collection/list.lux +++ b/stdlib/source/library/lux/data/collection/list.lux @@ -78,7 +78,7 @@ (def: .public (pairs xs) (All (_ a) (-> (List a) (Maybe (List [a a])))) (case xs - (^ (list& x1 x2 xs')) + (pattern (list& x1 x2 xs')) (case (pairs xs') {.#Some tail} {.#Some (list& [x1 x2] tail)} @@ -86,7 +86,7 @@ {.#None} {.#None}) - (^ (list)) + (pattern (list)) {.#Some (list)} _ @@ -456,9 +456,9 @@ (macro: .public (zipped tokens state) (case tokens - (^ (list [_ {.#Nat num_lists}])) + (pattern (list [_ {.#Nat num_lists}])) (if (n.> 0 num_lists) - (let [(^open "[0]") ..functor + (let [(open "[0]") ..functor indices (..indices num_lists) type_vars (: (List Code) (each (|>> nat#encoded symbol$) indices)) zipped_type (` (.All ((~ (symbol$ "0_")) (~+ type_vars)) @@ -496,9 +496,9 @@ (macro: .public (zipped_with tokens state) (case tokens - (^ (list [_ {.#Nat num_lists}])) + (pattern (list [_ {.#Nat num_lists}])) (if (n.> 0 num_lists) - (let [(^open "[0]") ..functor + (let [(open "[0]") ..functor indices (..indices num_lists) g!return_type (symbol$ "0return_type0") g!func (symbol$ "0func0") @@ -608,7 +608,7 @@ (macro: .public (when tokens state) (case tokens - (^ (.list test then)) + (pattern (.list test then)) {.#Right [state (.list (` (.if (~ test) (~ then) (.list))))]} diff --git a/stdlib/source/library/lux/data/collection/queue.lux b/stdlib/source/library/lux/data/collection/queue.lux index 81eb6092c..c9106c1c4 100644 --- a/stdlib/source/library/lux/data/collection/queue.lux +++ b/stdlib/source/library/lux/data/collection/queue.lux @@ -28,7 +28,7 @@ (def: .public (list queue) (All (_ a) (-> (Queue a) (List a))) - (let [(^open "_[0]") queue] + (let [(open "_[0]") queue] (list#composite _#front (list.reversed _#rear)))) (def: .public front @@ -37,7 +37,7 @@ (def: .public (size queue) (All (_ a) (-> (Queue a) Nat)) - (let [(^open "_[0]") queue] + (let [(open "_[0]") queue] (n.+ (list.size _#front) (list.size _#rear)))) @@ -47,7 +47,7 @@ (def: .public (member? equivalence queue member) (All (_ a) (-> (Equivalence a) (Queue a) a Bit)) - (let [(^open "_[0]") queue] + (let [(open "_[0]") queue] (or (list.member? equivalence _#front member) (list.member? equivalence _#rear member)))) @@ -55,17 +55,17 @@ (All (_ a) (-> (Queue a) (Queue a))) (case (the #front queue) ... Empty... - (^ (.list)) + (pattern (.list)) queue ... Front has dried up... - (^ (.list _)) + (pattern (.list _)) (|> queue (has #front (list.reversed (the #rear queue))) (has #rear (.list))) ... Consume front! - (^ (.list& _ front')) + (pattern (.list& _ front')) (|> queue (has #front front')))) diff --git a/stdlib/source/library/lux/data/collection/sequence.lux b/stdlib/source/library/lux/data/collection/sequence.lux index 4c935a3d4..8e9340a6f 100644 --- a/stdlib/source/library/lux/data/collection/sequence.lux +++ b/stdlib/source/library/lux/data/collection/sequence.lux @@ -27,6 +27,7 @@ ["[1]" \\unsafe {"+" Array}]]]] [macro [syntax {"+" syntax:}] + ["^" pattern] ["[0]" code]] [math [number @@ -140,8 +141,8 @@ (|> (array.clone hierarchy) (array.has! sub_idx {#Hierarchy (hierarchy#has (level_down level) idx val sub_node)})) - (^multi {#Base base} - (n.= 0 (level_down level))) + (^.multi {#Base base} + (n.= 0 (level_down level))) (|> (array.clone hierarchy) (array.has! sub_idx (|> (array.clone base) (array.has! (branch_idx idx) val) @@ -385,7 +386,7 @@ (def: (= v1 v2) (and (n.= (the #size v1) (the #size v2)) - (let [(^open "node#[0]") (node_equivalence //#=)] + (let [(open "node#[0]") (node_equivalence //#=)] (and (node#= {#Base (the #tail v1)} {#Base (the #tail v2)}) (node#= {#Hierarchy (the #root v1)} @@ -410,7 +411,7 @@ (Mix Sequence) (def: (mix $ init xs) - (let [(^open "[0]") node_mix] + (let [(open "[0]") node_mix] (mix $ (mix $ init @@ -453,9 +454,9 @@ (def: &functor ..functor) (def: (on fa ff) - (let [(^open "[0]") ..functor - (^open "[0]") ..mix - (^open "[0]") ..monoid + (let [(open "[0]") ..functor + (open "[0]") ..mix + (open "[0]") ..monoid results (each (function (_ f) (each f fa)) ff)] (mix composite identity results)))) @@ -469,8 +470,8 @@ (|>> sequence)) (def: conjoint - (let [(^open "[0]") ..mix - (^open "[0]") ..monoid] + (let [(open "[0]") ..mix + (open "[0]") ..monoid] (mix (function (_ post pre) (composite pre post)) identity)))) (def: .public reversed @@ -493,7 +494,7 @@ {#Hierarchy hierarchy} (<array> (help predicate) hierarchy))))] (function (<name> predicate sequence) - (let [(^open "_[0]") sequence] + (let [(open "_[0]") sequence] (<op> (help predicate {#Hierarchy _#root}) (help predicate {#Base _#tail}))))))] diff --git a/stdlib/source/library/lux/data/collection/set.lux b/stdlib/source/library/lux/data/collection/set.lux index ee9d8f345..b0f03ef92 100644 --- a/stdlib/source/library/lux/data/collection/set.lux +++ b/stdlib/source/library/lux/data/collection/set.lux @@ -9,6 +9,8 @@ [data [collection ["[0]" list ("[1]#[0]" mix)]]] + [macro + ["^" pattern]] [math [number ["n" nat]]]]] @@ -62,7 +64,7 @@ (implementation: .public equivalence (All (_ a) (Equivalence (Set a))) - (def: (= (^let reference [hash _]) sample) + (def: (= (^.let reference [hash _]) sample) (and (n.= (..size reference) (..size sample)) (list.every? (..member? reference) diff --git a/stdlib/source/library/lux/data/collection/set/multi.lux b/stdlib/source/library/lux/data/collection/set/multi.lux index 57c40d2fa..ea7fd7df0 100644 --- a/stdlib/source/library/lux/data/collection/set/multi.lux +++ b/stdlib/source/library/lux/data/collection/set/multi.lux @@ -8,6 +8,8 @@ [control ["[0]" function] ["[0]" maybe]] + [macro + ["^" pattern]] [math [number ["n" nat]]] @@ -104,7 +106,7 @@ (def: .public (support set) (All (_ a) (-> (Set a) (//.Set a))) - (let [(^let set [hash _]) (:representation set)] + (let [(^.let set [hash _]) (:representation set)] (|> set dictionary.keys (//.of_list hash)))) diff --git a/stdlib/source/library/lux/data/collection/stream.lux b/stdlib/source/library/lux/data/collection/stream.lux index 0624cebac..2c059103a 100644 --- a/stdlib/source/library/lux/data/collection/stream.lux +++ b/stdlib/source/library/lux/data/collection/stream.lux @@ -1,23 +1,23 @@ (.using - [library - [lux "*" - [abstract - [functor {"+" Functor}] - [comonad {"+" CoMonad}]] - [control - ["//" continuation {"+" Cont}] - ["<>" parser - ["<[0]>" code {"+" Parser}]]] - [macro {"+" with_symbols} - [syntax {"+" syntax:}] - ["[0]" code]] - [data - ["[0]" bit] - [collection - ["[0]" list ("[1]#[0]" monad)]]] - [math - [number - ["n" nat]]]]]) + [library + [lux {"-" pattern} + [abstract + [functor {"+" Functor}] + [comonad {"+" CoMonad}]] + [control + ["//" continuation {"+" Cont}] + ["<>" parser + ["<[0]>" code {"+" Parser}]]] + [data + ["[0]" bit] + [collection + ["[0]" list ("[1]#[0]" monad)]]] + [macro {"+" with_symbols} + [syntax {"+" syntax:}] + ["[0]" code]] + [math + [number + ["n" nat]]]]]) (type: .public (Stream a) (Cont [a (Stream a)])) @@ -127,9 +127,9 @@ (let [[head tail] (//.result wa)] (//.pending [wa (disjoint tail)])))) -(syntax: .public (^stream& [patterns (<code>.form (<>.many <code>.any)) - body <code>.any - branches (<>.some <code>.any)]) +(syntax: .public (pattern [patterns (<code>.form (<>.many <code>.any)) + body <code>.any + branches (<>.some <code>.any)]) (with_symbols [g!stream] (let [body+ (` (let [(~+ (|> patterns (list#each (function (_ pattern) diff --git a/stdlib/source/library/lux/data/collection/tree/finger.lux b/stdlib/source/library/lux/data/collection/tree/finger.lux index a7bf860b4..30486daff 100644 --- a/stdlib/source/library/lux/data/collection/tree/finger.lux +++ b/stdlib/source/library/lux/data/collection/tree/finger.lux @@ -86,7 +86,7 @@ (All (_ @ t v) (-> (Predicate t) (Tree @ t v) (Maybe v))) (let [[monoid tag root] (:representation tree)] (if (predicate tag) - (let [(^open "tag//[0]") monoid] + (let [(open "tag//[0]") monoid] (loop [_tag tag//identity _node root] (case _node diff --git a/stdlib/source/library/lux/data/collection/tree/zipper.lux b/stdlib/source/library/lux/data/collection/tree/zipper.lux index da4a69951..e4fd53818 100644 --- a/stdlib/source/library/lux/data/collection/tree/zipper.lux +++ b/stdlib/source/library/lux/data/collection/tree/zipper.lux @@ -102,7 +102,7 @@ (All (_ a) (-> (Zipper a) (Maybe (Zipper a)))) (do maybe.monad [family (the #family zipper)] - (in (let [(^open "_[0]") family] + (in (let [(open "_[0]") family] (for @.old (revised #node (: (-> (Tree (:parameter 0)) (Tree (:parameter 0))) @@ -292,8 +292,8 @@ (implementation: .public functor (Functor Zipper) - (def: (each f (^open "_[0]")) - [#family (maybe#each (function (_ (^open "_[0]")) + (def: (each f (open "_[0]")) + [#family (maybe#each (function (_ (open "_[0]")) [#parent (each f _#parent) #lefts (list#each (//#each f) _#lefts) #rights (list#each (//#each f) _#rights)]) @@ -309,14 +309,14 @@ (def: out (the [#node //.#value])) - (def: (disjoint (^open "_[0]")) + (def: (disjoint (open "_[0]")) (let [tree_splitter (: (All (_ a) (-> (Tree a) (Tree (Zipper a)))) (function (tree_splitter tree) [//.#value (..zipper tree) //.#children (|> tree (the //.#children) (list#each tree_splitter))]))] - [#family (maybe#each (function (_ (^open "_[0]")) + [#family (maybe#each (function (_ (open "_[0]")) [..#parent (disjoint _#parent) ..#lefts (list#each tree_splitter _#lefts) ..#rights (list#each tree_splitter _#rights)]) diff --git a/stdlib/source/library/lux/data/format/binary.lux b/stdlib/source/library/lux/data/format/binary.lux index 4d0eb7b57..cc85465f6 100644 --- a/stdlib/source/library/lux/data/format/binary.lux +++ b/stdlib/source/library/lux/data/format/binary.lux @@ -22,6 +22,8 @@ ["[0]" list] ["[0]" sequence {"+" Sequence} ("[1]#[0]" functor)] ["[0]" set {"+" Set}]]] + [macro + ["^" pattern]] [math [number ["[0]" i64] @@ -84,7 +86,7 @@ (All (_ l r) (-> (Writer l) (Writer r) (Writer (Or l r)))) (function (_ altV) (case altV - (^template [<number> <tag> <writer>] + (^.template [<number> <tag> <writer>] [{<tag> caseV} (let [[caseS caseT] (<writer> caseV)] [(.++ caseS) @@ -185,7 +187,7 @@ value (if (n.= original_count capped_count) value (|> value sequence.list (list.first capped_count) sequence.of_list)) - (^open "specification#[0]") ..monoid + (open "specification#[0]") ..monoid [size mutation] (|> value (sequence#each valueW) (# sequence.mix mix @@ -232,7 +234,7 @@ quantified (..and (..list again) again)] (function (_ altV) (case altV - (^template [<number> <tag> <writer>] + (^.template [<number> <tag> <writer>] [{<tag> caseV} (let [[caseS caseT] (<writer> caseV)] [(.++ caseS) @@ -267,7 +269,7 @@ (..and ..location (function (_ altV) (case altV - (^template [<number> <tag> <writer>] + (^.template [<number> <tag> <writer>] [{<tag> caseV} (let [[caseS caseT] (<writer> caseV)] [(.++ caseS) diff --git a/stdlib/source/library/lux/data/format/css/selector.lux b/stdlib/source/library/lux/data/format/css/selector.lux index d19cbd9bb..47a394603 100644 --- a/stdlib/source/library/lux/data/format/css/selector.lux +++ b/stdlib/source/library/lux/data/format/css/selector.lux @@ -188,7 +188,7 @@ (def: .public (formula input) (-> Formula Index) - (let [(^open "_[0]") input] + (let [(open "_[0]") input] (:abstraction (format (if (i.< +0 _#variable) (%.int _#variable) (%.nat (.nat _#variable))) diff --git a/stdlib/source/library/lux/data/format/css/value.lux b/stdlib/source/library/lux/data/format/css/value.lux index 4dd831528..b48718568 100644 --- a/stdlib/source/library/lux/data/format/css/value.lux +++ b/stdlib/source/library/lux/data/format/css/value.lux @@ -830,7 +830,7 @@ (def: .public (rgba pigment) (-> color.Pigment (Value Color)) - (let [(^open "_[0]") pigment + (let [(open "_[0]") pigment [red green blue] (color.rgb _#color)] (..apply "rgba" (list (%.nat red) (%.nat green) diff --git a/stdlib/source/library/lux/data/format/json.lux b/stdlib/source/library/lux/data/format/json.lux index aee3310cd..d5eafa15d 100644 --- a/stdlib/source/library/lux/data/format/json.lux +++ b/stdlib/source/library/lux/data/format/json.lux @@ -24,6 +24,7 @@ ["[0]" dictionary {"+" Dictionary}]]] [macro [syntax {"+" syntax:}] + ["^" pattern] ["[0]" code]] [math [number @@ -100,7 +101,7 @@ {#Null' _} (` {..#Null}) - (^template [<ctor> <input_tag> <output_tag>] + (^.template [<ctor> <input_tag> <output_tag>] [{<input_tag> value} (` {<output_tag> (~ (<ctor> value))})]) ([code.bit ..#Boolean' ..#Boolean] @@ -184,7 +185,7 @@ [{#Null} {#Null}] #1 - (^template [<tag> <struct>] + (^.template [<tag> <struct>] [[{<tag> x'} {<tag> y'}] (# <struct> = x' y')]) ([#Boolean bit.equivalence] @@ -290,7 +291,7 @@ (def: .public (format json) (-> JSON Text) (case json - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> value} (<format> value)]) ([#Null ..null_format] diff --git a/stdlib/source/library/lux/data/format/tar.lux b/stdlib/source/library/lux/data/format/tar.lux index 3b7e5d329..0d79977b1 100644 --- a/stdlib/source/library/lux/data/format/tar.lux +++ b/stdlib/source/library/lux/data/format/tar.lux @@ -21,6 +21,8 @@ [collection ["[0]" list ("[1]#[0]" mix)] ["[0]" sequence {"+" Sequence} ("[1]#[0]" mix)]]] + [macro + ["^" pattern]] [math ["[0]" number ["n" nat] @@ -237,7 +239,7 @@ _ (do try.monad [last_char (binary.read/8! end string)] (`` (case (.nat last_char) - (^ (char (~~ (static ..null)))) + (pattern (char (~~ (static ..null)))) (again (-- end)) _ @@ -427,8 +429,8 @@ (do <>.monad [it <binary>.bits/8] (case (.nat it) - (^template [<value> <link_flag>] - [(^ <value>) + (^.template [<value> <link_flag>] + [(pattern <value>) (in <link_flag>)]) (<options>) diff --git a/stdlib/source/library/lux/data/format/xml.lux b/stdlib/source/library/lux/data/format/xml.lux index 087604d0a..825daeac3 100644 --- a/stdlib/source/library/lux/data/format/xml.lux +++ b/stdlib/source/library/lux/data/format/xml.lux @@ -1,26 +1,26 @@ (.using - [library - [lux {"-" symbol} - [abstract - [monad {"+" do}] - [equivalence {"+" Equivalence}] - [codec {"+" Codec}]] - [control - [try {"+" Try}] - ["<>" parser ("[1]#[0]" monad) - ["<[0]>" text {"+" Parser}]]] - [data - ["[0]" product] - ["[0]" text {"+" \n} ("[1]#[0]" equivalence monoid)] - [collection - ["[0]" list ("[1]#[0]" functor)] - ["[0]" dictionary {"+" Dictionary}]]] - [math - [number - ["n" nat] - ["[0]" int]]] - [meta - ["[0]" symbol ("[1]#[0]" equivalence codec)]]]]) + [library + [lux {"-" symbol} + [abstract + [monad {"+" do}] + [equivalence {"+" Equivalence}] + [codec {"+" Codec}]] + [control + [try {"+" Try}] + ["<>" parser ("[1]#[0]" monad) + ["<[0]>" text {"+" Parser}]]] + [data + ["[0]" product] + ["[0]" text {"+" \n} ("[1]#[0]" equivalence monoid)] + [collection + ["[0]" list ("[1]#[0]" functor)] + ["[0]" dictionary {"+" Dictionary}]]] + [math + [number + ["n" nat] + ["[0]" int]]] + [meta + ["[0]" symbol ("[1]#[0]" equivalence codec)]]]]) (type: .public Tag Symbol) @@ -249,7 +249,7 @@ {#Text value} (sanitize_value value) - (^ {#Node xml_tag xml_attrs (list {#Text value})}) + (pattern {#Node xml_tag xml_attrs (list {#Text value})}) (let [tag (..tag xml_tag) attrs (if (dictionary.empty? xml_attrs) "" diff --git a/stdlib/source/library/lux/data/text.lux b/stdlib/source/library/lux/data/text.lux index 043736329..29d2d0ca8 100644 --- a/stdlib/source/library/lux/data/text.lux +++ b/stdlib/source/library/lux/data/text.lux @@ -14,6 +14,8 @@ [data [collection ["[0]" list ("[1]#[0]" mix)]]] + [macro + ["^" pattern]] [math [number ["n" nat] @@ -184,7 +186,7 @@ (for @.js (as_is (macro: (defined? tokens lux) (case tokens - (^ (list it)) + (pattern (list it)) {.#Right [lux (list (` (.case ("js type-of" ("js constant" (~ it))) "undefined" .false @@ -196,7 +198,7 @@ {.#Left ""})) (macro: (if_nashorn tokens lux) (case tokens - (^ (list then else)) + (pattern (list then else)) {.#Right [lux (list (if (and (..defined? "java") (..defined? "java.lang") (..defined? "java.lang.Object")) @@ -311,7 +313,7 @@ (def: .public together (-> (List Text) Text) - (let [(^open "[0]") ..monoid] + (let [(^.open "[0]") ..monoid] (|>> list.reversed (list#mix composite identity)))) @@ -334,7 +336,7 @@ (def: .public (space? char) (-> Char Bit) (with_expansions [<options> (template [<char>] - [(^ (.char (~~ (static <char>))))] + [(pattern (.char (~~ (static <char>))))] [..tab] [..vertical_tab] @@ -344,7 +346,7 @@ [..form_feed] )] (`` (case char - (^or <options>) + (^.or <options>) true _ diff --git a/stdlib/source/library/lux/data/text/escape.lux b/stdlib/source/library/lux/data/text/escape.lux index c30343aac..ec2adf129 100644 --- a/stdlib/source/library/lux/data/text/escape.lux +++ b/stdlib/source/library/lux/data/text/escape.lux @@ -15,6 +15,7 @@ ["n" nat]]] [macro [syntax {"+" syntax:}] + ["^" pattern] ["[0]" code]]]] ["[0]" // {"+" Char} ["%" format {"+" format}]]) @@ -72,8 +73,8 @@ (or (n.< ..ascii_bottom char) (n.> ..ascii_top char) (case char - (^template [<char>] - [(^ (static <char>)) + (^.template [<char>] + [(pattern (static <char>)) true]) ([..\0] [..\a] [..\b] [..\t] [..\n] [..\v] [..\f] [..\r] @@ -117,8 +118,8 @@ limit ("lux text size" text)] (if (n.< limit offset) (case ("lux text char" offset current) - (^template [<char> <replacement>] - [(^ (static <char>)) + (^.template [<char> <replacement>] + [(pattern (static <char>)) (let [[previous' current' limit'] (ascii_escaped <replacement> offset limit previous current)] (again 0 previous' current' limit'))]) ([..\0 ..escaped_\0] @@ -201,12 +202,12 @@ limit ("lux text size" text)] (if (n.< limit offset) (case ("lux text char" offset current) - (^ (static ..sigil_char)) + (pattern (static ..sigil_char)) (let [@sigil (++ offset)] (if (n.< limit @sigil) (case ("lux text char" @sigil current) - (^template [<sigil> <un_escaped>] - [(^ (static <sigil>)) + (^.template [<sigil> <un_escaped>] + [(pattern (static <sigil>)) (let [[previous' current' limit'] (..ascii_un_escaped <un_escaped> offset previous current limit)] (again 0 previous' current' limit'))]) ([..\0_sigil //.\0] @@ -220,7 +221,7 @@ [..\''_sigil //.\''] [..\\_sigil ..sigil]) - (^ (static ..\u_sigil)) + (pattern (static ..\u_sigil)) (let [@unicode (n.+ code_size @sigil)] (if (n.< limit @unicode) (do try.monad diff --git a/stdlib/source/library/lux/data/text/regex.lux b/stdlib/source/library/lux/data/text/regex.lux index f6bc9f626..02a9d8de5 100644 --- a/stdlib/source/library/lux/data/text/regex.lux +++ b/stdlib/source/library/lux/data/text/regex.lux @@ -1,28 +1,29 @@ (.using - [library - [lux "*" - ["[0]" meta] - [abstract - monad] - [control - ["[0]" maybe] - ["[0]" try] - ["[0]" exception {"+" exception:}] - ["<>" parser ("[1]#[0]" monad) - ["<[0]>" text {"+" Parser}] - ["<[0]>" code]]] - [data - ["[0]" product] - [collection - ["[0]" list ("[1]#[0]" mix monad)]]] - [macro {"+" with_symbols} - [syntax {"+" syntax:}] - ["[0]" code]] - [math - [number {"+" hex} - ["n" nat ("[1]#[0]" decimal)]]]]] - ["[0]" // - ["%" format {"+" format}]]) + [library + [lux {"-" pattern} + ["[0]" meta] + [abstract + monad] + [control + ["[0]" maybe] + ["[0]" try] + ["[0]" exception {"+" exception:}] + ["<>" parser ("[1]#[0]" monad) + ["<[0]>" text {"+" Parser}] + ["<[0]>" code]]] + [data + ["[0]" product] + [collection + ["[0]" list ("[1]#[0]" mix monad)]]] + [macro {"+" with_symbols} + [syntax {"+" syntax:}] + ["^" pattern] + ["[0]" code]] + [math + [number {"+" hex} + ["n" nat ("[1]#[0]" decimal)]]]]] + ["[0]" // + ["%" format {"+" format}]]) (def: regex_char^ (Parser Text) @@ -290,8 +291,8 @@ [Nat (List Code) (List (List Code))]) (function (_ part [idx names steps]) (case part - (^or {.#Left complex} - {.#Right [{#Non_Capturing} complex]}) + (^.or {.#Left complex} + {.#Right [{#Non_Capturing} complex]}) [idx names (list& (list g!temp complex @@ -425,12 +426,12 @@ {try.#Success regex} (in (list regex))))) -(syntax: .public (^regex [[pattern bindings] (<code>.form (<>.and <code>.text (<>.maybe <code>.any))) - body <code>.any - branches (<>.many <code>.any)]) +(syntax: .public (pattern [[pattern bindings] (<code>.form (<>.and <code>.text (<>.maybe <code>.any))) + body <code>.any + branches (<>.many <code>.any)]) (with_symbols [g!temp] - (in (list& (` (^multi (~ g!temp) - [((~! <text>.result) (..regex (~ (code.text pattern))) (~ g!temp)) - {try.#Success (~ (maybe.else g!temp bindings))}])) + (in (list& (` (^.multi (~ g!temp) + [((~! <text>.result) (..regex (~ (code.text pattern))) (~ g!temp)) + {try.#Success (~ (maybe.else g!temp bindings))}])) body branches)))) diff --git a/stdlib/source/library/lux/debug.lux b/stdlib/source/library/lux/debug.lux index 3fbb14abf..c4bf1f96a 100644 --- a/stdlib/source/library/lux/debug.lux +++ b/stdlib/source/library/lux/debug.lux @@ -26,6 +26,7 @@ ["[0]" list ("[1]#[0]" functor)] ["[0]" dictionary]]] [macro + ["^" pattern] ["[0]" template] ["[0]" syntax {"+" syntax:}] ["[0]" code]] @@ -161,11 +162,11 @@ {.#Some value} (let [value (:as (array.Array java/lang/Object) value)] (case (array.read! 0 value) - (^multi {.#Some tag} - [(ffi.check java/lang/Integer tag) - {.#Some tag}] - [[(array.read! 1 value) (array.read! 2 value)] - [last? {.#Some choice}]]) + (^.multi {.#Some tag} + [(ffi.check java/lang/Integer tag) + {.#Some tag}] + [[(array.read! 1 value) (array.read! 2 value)] + [last? {.#Some choice}]]) (let [last? (case last? {.#Some _} #1 {.#None} #0)] @@ -183,7 +184,7 @@ @.js (case (ffi.type_of value) - (^template [<type_of> <then>] + (^.template [<type_of> <then>] [<type_of> (`` (|> value (~~ (template.spliced <then>))))]) (["boolean" [(:as .Bit) %.bit]] @@ -218,8 +219,8 @@ @.python (case (..str (..type value)) - (^template [<type_of> <class_of> <then>] - [(^or <type_of> <class_of>) + (^.template [<type_of> <class_of> <then>] + [(^.or <type_of> <class_of>) (`` (|> value (~~ (template.spliced <then>))))]) (["<type 'bool'>" "<class 'bool'>" [(:as .Bit) %.bit]] ["<type 'int'>" "<class 'int'>" [(:as .Int) %.int]] @@ -227,10 +228,10 @@ ["<type 'str'>" "<class 'str'>" [(:as .Text) %.text]] ["<type 'unicode'>" "<class 'unicode'>" [(:as .Text) %.text]]) - (^or "<type 'list'>" "<class 'list'>") + (^.or "<type 'list'>" "<class 'list'>") (tuple_inspection inspection value) - (^or "<type 'tuple'>" "<class 'tuple'>") + (^.or "<type 'tuple'>" "<class 'tuple'>") (let [variant (:as (array.Array Any) value)] (case (array.size variant) 3 (let [variant_tag ("python array read" 0 variant) @@ -250,7 +251,7 @@ @.lua (case (..type value) - (^template [<type_of> <then>] + (^.template [<type_of> <then>] [<type_of> (`` (|> value (~~ (template.spliced <then>))))]) (["boolean" [(:as .Bit) %.bit]] @@ -323,7 +324,7 @@ @.php (case (..gettype value) - (^template [<type_of> <then>] + (^.template [<type_of> <then>] [<type_of> (`` (|> value (~~ (template.spliced <then>))))]) (["boolean" [(:as .Bit) %.bit]] diff --git a/stdlib/source/library/lux/documentation.lux b/stdlib/source/library/lux/documentation.lux index 676746bd5..1576770d5 100644 --- a/stdlib/source/library/lux/documentation.lux +++ b/stdlib/source/library/lux/documentation.lux @@ -23,6 +23,7 @@ ["md" markdown {"+" Markdown Block}]]] ["[0]" macro [syntax {"+" syntax:}] + ["^" pattern] ["[0]" code] ["[0]" template]] [math @@ -50,7 +51,7 @@ (def: (reference_column code) (-> Code Nat) (case code - (^template [<tag>] + (^.template [<tag>] [[[_ _ column] {<tag> _}] column]) ([.#Bit] @@ -61,7 +62,7 @@ [.#Text] [.#Symbol]) - (^template [<tag>] + (^.template [<tag>] [[[_ _ column] {<tag> members}] (|> members (list#each reference_column) @@ -100,7 +101,7 @@ (format (padding reference_column old_location new_location) documentation)]) - (^template [<tag> <format>] + (^.template [<tag> <format>] [[new_location {<tag> value}] (let [documentation (`` (|> value (~~ (template.spliced <format>))))] [(revised .#column (n.+ (text.size documentation)) new_location) @@ -113,7 +114,7 @@ [.#Frac [%.frac]] [.#Text [%.text]]) - (^template [|<| |>| <tag>] + (^.template [|<| |>| <tag>] [[group_location {<tag> members}] (let [[group_location' members_documentation] (list#mix (function (_ part [last_location text_accum]) (let [[member_location member_documentation] (code_documentation expected_module last_location reference_column part)] @@ -250,13 +251,13 @@ {.#Parameter idx} (parameter_name [type_function_name (list)] level idx) - (^template [<tag> <pre> <post>] + (^.template [<tag> <pre> <post>] [{<tag> id} (format <pre> (%.nat id) <post>)]) ([.#Var "⌈" "⌋"] [.#Ex "⟨" "⟩"]) - (^template [<tag> <name> <flat>] + (^.template [<tag> <name> <flat>] [{<tag> _} (let [[level' body] (<flat> type) args (level_parameters level level') @@ -269,10 +270,10 @@ ([.#UnivQ "All" type.flat_univ_q] [.#ExQ "Ex" type.flat_ex_q]) - (^ {.#Apply (|recursion_dummy|) {.#Parameter 0}}) + (pattern {.#Apply (|recursion_dummy|) {.#Parameter 0}}) type_function_name - (^ {.#Apply (|recursion_dummy|) {.#UnivQ _ body}}) + (pattern {.#Apply (|recursion_dummy|) {.#UnivQ _ body}}) (format "(Rec " type_function_name \n (nested " " (%type' level type_function_name nestable? module body)) ")") @@ -314,7 +315,7 @@ (def: (type_definition' nestable? level arity type_function_info tags module type) (-> Bit Nat Nat [Text (List Text)] (List Text) Text Type Text) (case tags - (^ (list single_tag)) + (pattern (list single_tag)) (format "(Record" \n " [#" single_tag " " (type_definition' false level arity type_function_info {.#None} module type) "])") @@ -381,13 +382,13 @@ {.#Parameter idx} (parameter_name type_function_info level idx) - (^template [<tag> <pre>] + (^.template [<tag> <pre>] [{<tag> id} (format <pre> (%.nat id))]) ([.#Var "-"] [.#Ex "+"]) - (^template [<tag> <name> <flat>] + (^.template [<tag> <name> <flat>] [{<tag> _} (let [[level' body] (<flat> type) args (level_parameters (n.- arity level) level') @@ -404,10 +405,10 @@ [.#ExQ "Ex" type.flat_ex_q]) ... Recursive call - (^ {.#Apply (|recursion_dummy|) {.#Parameter 0}}) + (pattern {.#Apply (|recursion_dummy|) {.#Parameter 0}}) (product.left type_function_info) - (^ {.#Apply (|recursion_dummy|) {.#UnivQ _ body}}) + (pattern {.#Apply (|recursion_dummy|) {.#UnivQ _ body}}) (|> (type_definition' nestable? level arity type_function_info tags module body) (text.all_split_by \n) (list#each (text.prefix " ")) @@ -652,7 +653,7 @@ (def: (module_documentation module) (-> Module (Markdown Block)) - (let [(^open "_[0]") module] + (let [(open "_[0]") module] ($_ md.then ... Name (md.heading/1 (the #module module)) diff --git a/stdlib/source/library/lux/ffi.jvm.lux b/stdlib/source/library/lux/ffi.jvm.lux index 3a53efeb9..6ef0e751b 100644 --- a/stdlib/source/library/lux/ffi.jvm.lux +++ b/stdlib/source/library/lux/ffi.jvm.lux @@ -21,6 +21,7 @@ ["[0]" dictionary {"+" Dictionary}]]] [macro {"+" with_symbols} [syntax {"+" syntax:}] + ["^" pattern] ["[0]" code] ["[0]" template]] [target @@ -434,7 +435,7 @@ (def: (replaced f input) (-> (-> Code Code) Code Code) (case (f input) - (^template [<tag>] + (^.template [<tag>] [[meta {<tag> parts}] [meta {<tag> (list#each (replaced f) parts)}]]) ([.#Form] @@ -534,7 +535,7 @@ (def: privacy_modifier^ (Parser Privacy) - (let [(^open "[0]") <>.monad] + (let [(open "[0]") <>.monad] ($_ <>.or (<code>.this! (' "public")) (<code>.this! (' "private")) @@ -543,7 +544,7 @@ (def: inheritance_modifier^ (Parser Inheritance) - (let [(^open "[0]") <>.monad] + (let [(open "[0]") <>.monad] ($_ <>.or (<code>.this! (' "final")) (<code>.this! (' "abstract")) @@ -1041,7 +1042,7 @@ (def: (method_decl$ [[name pm anns] method_decl]) (-> [Member_Declaration MethodDecl] Code) - (let [(^open "[0]") method_decl] + (let [(open "[0]") method_decl] (` ((~ (code.text name)) [(~+ (list#each annotation$ anns))] [(~+ (list#each var$ #method_tvars))] @@ -1335,8 +1336,8 @@ (def: (member_def_arg_bindings vars member) (-> (List (Type Var)) Import_Member_Declaration (Meta [(List [Bit Code]) (List (Type Value)) (List Code)])) (case member - (^or {#ConstructorDecl [commons _]} {#MethodDecl [commons _]}) - (let [(^open "[0]") commons] + (^.or {#ConstructorDecl [commons _]} {#MethodDecl [commons _]}) + (let [(open "[0]") commons] (do [! meta.monad] [arg_inputs (monad.each ! (: (-> [Bit (Type Value)] (Meta [Bit Code])) @@ -1360,7 +1361,7 @@ (def: (with_return_maybe member never_null? unboxed return_term) (-> Import_Member_Declaration Bit (Type Value) Code Code) (case member - (^or {#ConstructorDecl [commons _]} {#MethodDecl [commons _]}) + (^.or {#ConstructorDecl [commons _]} {#MethodDecl [commons _]}) (cond (or never_null? (dictionary.key? ..boxes unboxed)) return_term @@ -1383,7 +1384,7 @@ [(def: (<name> member return_term) (-> Import_Member_Declaration Code Code) (case member - (^or {#ConstructorDecl [commons _]} {#MethodDecl [commons _]}) + (^.or {#ConstructorDecl [commons _]} {#MethodDecl [commons _]}) (if (the <tag> commons) <term_trans> return_term) @@ -1528,8 +1529,8 @@ (with_symbols [g!obj] (do meta.monad [.let [def_name (code.symbol ["" (..import_name import_format method_prefix (the #import_member_alias commons))]) - (^open "[0]") commons - (^open "[0]") method + (open "[0]") commons + (open "[0]") method [jvm_op object_ast] (: [Text (List Code)] (case #import_member_kind {#StaticIMK} @@ -1581,7 +1582,7 @@ {#FieldAccessDecl fad} (do meta.monad - [.let [(^open "_[0]") fad + [.let [(open "_[0]") fad getter_name (code.symbol ["" (..import_name import_format method_prefix _#import_field_name)]) setter_name (code.symbol ["" (..import_name import_format method_prefix (format _#import_field_name "!"))])] getter_interop (with_symbols [g!obj] @@ -1924,7 +1925,7 @@ object <code>.any]) (case [(parser.array? type) (parser.class? type)] - (^or [{.#Some _} _] [_ {.#Some _}]) + (^.or [{.#Some _} _] [_ {.#Some _}]) (in (list (` (.: (~ (..value_type {#ManualPrM} type)) ("jvm object cast" (~ object)))))) diff --git a/stdlib/source/library/lux/ffi.old.lux b/stdlib/source/library/lux/ffi.old.lux index caff78c66..2cd19ade0 100644 --- a/stdlib/source/library/lux/ffi.old.lux +++ b/stdlib/source/library/lux/ffi.old.lux @@ -22,6 +22,7 @@ ["[0]" list ("[1]#[0]" monad mix monoid)]]] ["[0]" macro {"+" with_symbols} [syntax {"+" syntax:}] + ["^" pattern] ["[0]" code] ["[0]" template]] ["[0]" meta]]]) @@ -280,7 +281,7 @@ (def: (manual_primitive_type class) (-> Text (Maybe Code)) (case class - (^template [<prim> <type>] + (^.template [<prim> <type>] [<prim> {.#Some (' <type>)}]) (["boolean" (Primitive "java.lang.Boolean")] @@ -299,7 +300,7 @@ (def: (auto_primitive_type class) (-> Text (Maybe Code)) (case class - (^template [<prim> <type>] + (^.template [<prim> <type>] [<prim> {.#Some (' <type>)}]) (["boolean" .Bit] @@ -324,14 +325,14 @@ (-> Primitive_Mode (List Type_Parameter) Bit GenericType Code) Code) (case [name+params mode in_array?] - (^multi [[prim {.#End}] {#ManualPrM} #0] - [(manual_primitive_type prim) - {.#Some output}]) + (^.multi [[prim {.#End}] {#ManualPrM} #0] + [(manual_primitive_type prim) + {.#Some output}]) output - (^multi [[prim {.#End}] {#AutoPrM} #0] - [(auto_primitive_type prim) - {.#Some output}]) + (^.multi [[prim {.#End}] {#AutoPrM} #0] + [(auto_primitive_type prim) + {.#Some output}]) output [[name params] _ _] @@ -361,8 +362,8 @@ (let [=param (class_type' mode type_params #1 param)] (` ((~! array.Array) (~ =param)))) - (^or {#GenericWildcard {.#None}} - {#GenericWildcard {.#Some [{#LowerBound} _]}}) + (^.or {#GenericWildcard {.#None}} + {#GenericWildcard {.#Some [{#LowerBound} _]}}) (` .Any) {#GenericWildcard {.#Some [{#UpperBound} upper_bound]}} @@ -377,7 +378,7 @@ (-> Type_Parameter Code) (code.symbol ["" name])) -(def: (class_decl_type$ (^open "[0]")) +(def: (class_decl_type$ (open "[0]")) (-> Class_Declaration Code) (let [=params (list#each (: (-> Type_Parameter Code) (function (_ [pname pbounds]) @@ -407,8 +408,8 @@ {.#Some [pname pbounds]} (simple_class$ env (maybe.trusted (list.head pbounds)))) - (^or {#GenericWildcard {.#None}} - {#GenericWildcard {.#Some [{#LowerBound} _]}}) + (^.or {#GenericWildcard {.#None}} + {#GenericWildcard {.#Some [{#LowerBound} _]}}) type_var_class {#GenericWildcard {.#Some [{#UpperBound} upper_bound]}} @@ -422,7 +423,7 @@ {#GenericArray param} (format "[" (simple_class$ env param)) - (^template [<prim> <class>] + (^.template [<prim> <class>] [{#GenericClass <prim> {.#End}} <class>]) (["boolean" "[Z"] @@ -463,7 +464,7 @@ (def: (pre_walk_replace f input) (-> (-> Code Code) Code Code) (case (f input) - (^template [<tag>] + (^.template [<tag>] [[meta {<tag> parts}] [meta {<tag> (list#each (pre_walk_replace f) parts)}]]) ([.#Form] @@ -539,8 +540,8 @@ {#StaticMethod strict? type_vars args return_type return_expr exs} (static_method_parser params class_name method_name args) - (^or {#VirtualMethod final? strict? type_vars self_name args return_type return_expr exs} - {#OverridenMethod strict? owner_class type_vars self_name args return_type return_expr exs}) + (^.or {#VirtualMethod final? strict? type_vars self_name args return_type return_expr exs} + {#OverridenMethod strict? owner_class type_vars self_name args return_type return_expr exs}) (special_method_parser params class_name method_name args) {#AbstractMethod type_vars args return_type exs} @@ -552,7 +553,7 @@ ... Parsers (def: privacy_modifier^ (Parser Privacy) - (let [(^open "[0]") <>.monad] + (let [(open "[0]") <>.monad] ($_ <>.or (<code>.this! (' "public")) (<code>.this! (' "private")) @@ -561,7 +562,7 @@ (def: inheritance_modifier^ (Parser Inheritance) - (let [(^open "[0]") <>.monad] + (let [(open "[0]") <>.monad] ($_ <>.or (<code>.this! (' "final")) (<code>.this! (' "abstract")) @@ -599,7 +600,7 @@ (<code>.tuple (do <>.monad [component again^] (case component - (^template [<class> <name>] + (^.template [<class> <name>] [{#GenericClass <name> {.#End}} (in {#GenericClass <class> (list)})]) (["[Z" "boolean"] @@ -1032,11 +1033,11 @@ (-> Type_Parameter JVM_Code) (format "(" name " " (spaced (list#each generic_type$ bounds)) ")")) -(def: (class_decl$ (^open "[0]")) +(def: (class_decl$ (open "[0]")) (-> Class_Declaration JVM_Code) (format "(" (safe #class_name) " " (spaced (list#each type_param$ #class_params)) ")")) -(def: (super_class_decl$ (^open "[0]")) +(def: (super_class_decl$ (open "[0]")) (-> Super_Class_Decl JVM_Code) (format "(" (safe #super_class_name) " " (spaced (list#each generic_type$ #super_class_params)) @@ -1044,7 +1045,7 @@ (def: (method_decl$ [[name pm anns] method_decl]) (-> [Member_Declaration MethodDecl] JVM_Code) - (let [(^open "[0]") method_decl] + (let [(open "[0]") method_decl] (with_parens (spaced (list name (with_brackets (spaced (list#each annotation$ anns))) @@ -1339,8 +1340,8 @@ (def: (member_def_arg_bindings type_params class member) (-> (List Type_Parameter) Class_Declaration Import_Member_Declaration (Meta [(List [Bit Code]) (List Text) (List Code)])) (case member - (^or {#ConstructorDecl [commons _]} {#MethodDecl [commons _]}) - (let [(^open "[0]") commons] + (^.or {#ConstructorDecl [commons _]} {#MethodDecl [commons _]}) + (let [(open "[0]") commons] (do [! meta.monad] [arg_inputs (monad.each ! (: (-> [Bit GenericType] (Meta [Bit Code])) @@ -1366,7 +1367,7 @@ (def: (decorate_return_maybe class member return_term) (-> Class_Declaration Import_Member_Declaration Code Code) (case member - (^or {#ConstructorDecl [commons _]} {#MethodDecl [commons _]}) + (^.or {#ConstructorDecl [commons _]} {#MethodDecl [commons _]}) (if (the #import_member_maybe? commons) (` (??? (~ return_term))) (let [g!temp (` ((~' ~') (~ (code.symbol ["" " Ω "]))))] @@ -1385,7 +1386,7 @@ [(def: (<name> member return_term) (-> Import_Member_Declaration Code Code) (case member - (^or {#ConstructorDecl [commons _]} {#MethodDecl [commons _]}) + (^.or {#ConstructorDecl [commons _]} {#MethodDecl [commons _]}) (if (the <tag> commons) <term_trans> return_term) @@ -1492,8 +1493,8 @@ (with_symbols [g!obj] (do meta.monad [.let [def_name (code.symbol ["" (..import_name import_format method_prefix (the #import_member_alias commons))]) - (^open "[0]") commons - (^open "[0]") method + (open "[0]") commons + (open "[0]") method [jvm_op object_ast] (: [Text (List Code)] (case #import_member_kind {#StaticIMK} @@ -1524,7 +1525,7 @@ {#FieldAccessDecl fad} (do meta.monad - [.let [(^open "[0]") fad + [.let [(open "[0]") fad base_gtype (class_type #import_field_mode type_params #import_field_type) classC (class_decl_type$ class) typeC (if #import_field_maybe? @@ -1623,8 +1624,8 @@ (syntax: .public (array [type (..generic_type^ (list)) size <code>.any]) (case type - (^template [<type> <array_op>] - [(^ {#GenericClass <type> (list)}) + (^.template [<type> <array_op>] + [(pattern {#GenericClass <type> (list)}) (in (list (` (<array_op> (~ size)))))]) (["boolean" "jvm znewarray"] ["byte" "jvm bnewarray"] @@ -1671,7 +1672,7 @@ [array_type (meta.type array_name) array_jvm_type (type_class_name array_type)] (case array_jvm_type - (^template [<type> <array_op>] + (^.template [<type> <array_op>] [<type> (in (list (` (<array_op> (~ array) (~ idx)))))]) (["[Z" "jvm zaload"] @@ -1700,7 +1701,7 @@ [array_type (meta.type array_name) array_jvm_type (type_class_name array_type)] (case array_jvm_type - (^template [<type> <array_op>] + (^.template [<type> <array_op>] [<type> (in (list (` (<array_op> (~ array) (~ idx) (~ value)))))]) (["[Z" "jvm zastore"] diff --git a/stdlib/source/library/lux/macro.lux b/stdlib/source/library/lux/macro.lux index 55bcbbfd8..60df4a57f 100644 --- a/stdlib/source/library/lux/macro.lux +++ b/stdlib/source/library/lux/macro.lux @@ -117,7 +117,7 @@ (macro: .public (with_symbols tokens) (case tokens - (^ (list [_ {.#Tuple symbols}] body)) + (pattern (list [_ {.#Tuple symbols}] body)) (do [! //.monad] [symbol_names (monad.each ! ..local_symbol symbols) .let [symbol_defs (list#conjoint (list#each (: (-> Text (List Code)) @@ -135,7 +135,7 @@ (do //.monad [token+ (..expansion token)] (case token+ - (^ (list token')) + (pattern (list token')) (in token') _ @@ -148,11 +148,11 @@ macro_name [module short]] (case (: (Maybe [Bit Code]) (case tokens - (^ (list [_ {.#Text "omit"}] - token)) + (pattern (list [_ {.#Text "omit"}] + token)) {.#Some [#1 token]} - (^ (list token)) + (pattern (list token)) {.#Some [#0 token]} _ @@ -179,7 +179,7 @@ (macro: .public (times tokens) (case tokens - (^ (list& [_ {.#Nat times}] terms)) + (pattern (list& [_ {.#Nat times}] terms)) (loop [times times before terms] (case times diff --git a/stdlib/source/library/lux/macro/code.lux b/stdlib/source/library/lux/macro/code.lux index 5a77eb1f0..0ced45d10 100644 --- a/stdlib/source/library/lux/macro/code.lux +++ b/stdlib/source/library/lux/macro/code.lux @@ -1,23 +1,25 @@ (.using - [library - [lux {"-" nat int rev symbol} - [abstract - [equivalence {"+" Equivalence}]] - [data - ["[0]" product] - ["[0]" bit] - ["[0]" text ("[1]#[0]" monoid equivalence)] - [collection - ["[0]" list ("[1]#[0]" functor mix)]]] - [math - [number - ["[0]" nat] - ["[0]" int] - ["[0]" rev] - ["[0]" frac]]] - [meta - ["[0]" location] - ["[0]" symbol]]]]) + [library + [lux {"-" nat int rev symbol} + [abstract + [equivalence {"+" Equivalence}]] + [data + ["[0]" product] + ["[0]" bit] + ["[0]" text ("[1]#[0]" monoid equivalence)] + [collection + ["[0]" list ("[1]#[0]" functor mix)]]] + [macro + ["^" pattern]] + [math + [number + ["[0]" nat] + ["[0]" int] + ["[0]" rev] + ["[0]" frac]]] + [meta + ["[0]" location] + ["[0]" symbol]]]]) ... (type: (Code' w) ... {.#Bit Bit} @@ -63,7 +65,7 @@ (def: (= x y) (case [x y] - (^template [<tag> <eq>] + (^.template [<tag> <eq>] [[[_ {<tag> x'}] [_ {<tag> y'}]] (# <eq> = x' y')]) ([.#Bit bit.equivalence] @@ -74,7 +76,7 @@ [.#Text text.equivalence] [.#Symbol symbol.equivalence]) - (^template [<tag>] + (^.template [<tag>] [[[_ {<tag> xs'}] [_ {<tag> ys'}]] (# (list.equivalence =) = xs' ys')]) ([.#Form] @@ -87,7 +89,7 @@ (def: .public (format ast) (-> Code Text) (case ast - (^template [<tag> <struct>] + (^.template [<tag> <struct>] [[_ {<tag> value}] (# <struct> encoded value)]) ([.#Bit bit.codec] @@ -100,7 +102,7 @@ [_ {.#Text value}] (text.format value) - (^template [<tag> <open> <close>] + (^.template [<tag> <open> <close>] [[_ {<tag> members}] ($_ text#composite <open> @@ -122,7 +124,7 @@ (if (# ..equivalence = original ast) substitute (case ast - (^template [<tag>] + (^.template [<tag>] [[location {<tag> parts}] [location {<tag> (list#each (replaced original substitute) parts)}]]) ([.#Form] diff --git a/stdlib/source/library/lux/macro/pattern.lux b/stdlib/source/library/lux/macro/pattern.lux new file mode 100644 index 000000000..b789e1f19 --- /dev/null +++ b/stdlib/source/library/lux/macro/pattern.lux @@ -0,0 +1,246 @@ +(.using + [library + [lux {"-" or template let |> `}]]) + +(macro: (locally tokens lux) + (.let [[prelude _] (symbol ._)] + (case tokens + (pattern (list [@ {.#Symbol ["" name]}])) + {.#Right [lux (list (.` ("lux in-module" (~ [@ {.#Text prelude}]) + (~ [@ {.#Symbol [prelude name]}]))))]} + + _ + {.#Left ""}))) + +(.template [<name>] + [(def: <name> (..locally <name>))] + + [list#size] + [list#composite] + [list#each] + [list#conjoint] + [every?] + + [maybe_monad] + + [function#composite] + + [failure] + [meta#in] + + [do] + [monad#each] + + [Replacement_Environment] + [realized_template] + [replacement_environment] + + [symbol_short] + [tuple_list] + + [meta_monad] + [text$] + [generated_symbol] + [type_definition] + [record_slots] + [text#composite] + [type#encoded] + [module_alias] + [symbol$] + [tuple$] + [monad#mix] + [zipped/2] + + [multi_level_case^] + [multi_level_case$] + [type_code] + [expected_type] + + [wrong_syntax_error] + [local_symbol$] + + [list#reversed] + [untemplated_list] + [bit$] + [nat$] + [int$] + [rev$] + [frac$] + ) + +(macro: .public (or tokens) + (case tokens + (pattern (list& [_ {.#Form patterns}] body branches)) + (case patterns + {.#End} + (failure (..wrong_syntax_error (symbol ..or))) + + _ + (.let [pairs (.|> patterns + (list#each (function (_ pattern) (list pattern body))) + list#conjoint)] + (meta#in (list#composite pairs branches)))) + _ + (failure (..wrong_syntax_error (symbol ..or))))) + +(macro: .public (template tokens) + (case tokens + (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) + data' (monad#each maybe_monad tuple_list data)] + (.let [num_bindings (list#size bindings')] + (if (every? (|>> ("lux i64 =" num_bindings)) + (list#each list#size data')) + (.let [apply (: (-> Replacement_Environment (List Code)) + (function (_ env) (list#each (realized_template env) templates)))] + (.|> data' + (list#each (function#composite apply (replacement_environment bindings'))) + list#conjoint + in)) + {.#None})))) + {.#Some output} + (meta#in (list#composite output branches)) + + {.#None} + (failure (..wrong_syntax_error (symbol ..template)))) + + _ + (failure (..wrong_syntax_error (symbol ..template))))) + +(macro: .public (multi tokens) + (case tokens + (pattern (list& [_meta {.#Form levels}] body next_branches)) + (do meta_monad + [mlc (multi_level_case^ levels) + .let [initial_bind? (case mlc + [[_ {.#Symbol _}] _] + #1 + + _ + #0)] + expected ..expected_type + g!temp (..generated_symbol "temp")] + (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_error (symbol ..multi))))) + +(macro: .public (let tokens) + (case tokens + (pattern (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 + (pattern (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 ..|>))))) + +(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 [<tag> <name>] + [(def: (<name> 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) {<tag> (~ (untemplated_list& spliced =inits))}]))) + + _ + (do meta_monad + [=elems (monad#each meta_monad untemplated_pattern elems)] + (in (.` [(~ g!meta) {<tag> (~ (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 [<tag> <gen>] + [[_ {<tag> value}] + (in (.` [(~ g!meta) {<tag> (~ (<gen> value))}]))]) + ([.#Bit bit$] + [.#Nat nat$] + [.#Int int$] + [.#Rev rev$] + [.#Frac frac$] + [.#Text text$] + [.#Symbol name$]) + + [_ {.#Form {.#Item [[_ {.#Symbol ["" "~"]}] {.#Item [unquoted {.#End}]}]}}] + (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 [<tag> <untemplated>] + [[_ {<tag> elems}] + (<untemplated> g!meta untemplated_pattern elems)]) + ([.#Form ..untemplated_form] + [.#Variant ..untemplated_variant] + [.#Tuple ..untemplated_tuple]) + ))) + +(macro: .public (` tokens) + (case tokens + (pattern (list& [_meta {.#Form (list template)}] body branches)) + (do meta_monad + [pattern (untemplated_pattern template)] + (in (list& pattern body branches))) + + (pattern (list template)) + (do meta_monad + [pattern (untemplated_pattern template)] + (in (list pattern))) + + _ + (failure (..wrong_syntax_error (symbol ..`))))) diff --git a/stdlib/source/library/lux/macro/syntax/check.lux b/stdlib/source/library/lux/macro/syntax/check.lux index 554fdd1aa..00f01aa3f 100644 --- a/stdlib/source/library/lux/macro/syntax/check.lux +++ b/stdlib/source/library/lux/macro/syntax/check.lux @@ -1,18 +1,18 @@ (.using - [library - [lux "*" - ["[0]" meta] - [abstract - [equivalence {"+" Equivalence}] - [monad {"+" do}]] - [control - ["[0]" exception {"+" exception:}] - ["<>" parser - ["<[0]>" code {"+" Parser}]]] - [data - ["[0]" product]] - [macro - ["[0]" code]]]]) + [library + [lux "*" + ["[0]" meta] + [abstract + [equivalence {"+" Equivalence}] + [monad {"+" do}]] + [control + ["[0]" exception {"+" exception:}] + ["<>" parser + ["<[0]>" code {"+" Parser}]]] + [data + ["[0]" product]] + [macro + ["[0]" code]]]]) (def: extension "lux check") @@ -29,7 +29,7 @@ code.equivalence )) -(def: .public (format (^open "_[0]")) +(def: .public (format (open "_[0]")) (-> Check Code) (` ((~ (code.text ..extension)) (~ _#type) diff --git a/stdlib/source/library/lux/macro/syntax/definition.lux b/stdlib/source/library/lux/macro/syntax/definition.lux index 6d84be918..f889c3dfa 100644 --- a/stdlib/source/library/lux/macro/syntax/definition.lux +++ b/stdlib/source/library/lux/macro/syntax/definition.lux @@ -50,7 +50,7 @@ .#line (~ (code.nat (the .#line location.dummy))) .#column (~ (code.nat (the .#column location.dummy)))])) -(def: .public (format (^open "_[0]")) +(def: .public (format (open "_[0]")) (-> Definition Code) (` ((~ (code.text ..extension)) (~ (code.local_symbol _#name)) diff --git a/stdlib/source/library/lux/macro/syntax/export.lux b/stdlib/source/library/lux/macro/syntax/export.lux index 7a87e30fd..5a75b096c 100644 --- a/stdlib/source/library/lux/macro/syntax/export.lux +++ b/stdlib/source/library/lux/macro/syntax/export.lux @@ -1,11 +1,13 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]] - [control - ["<>" parser - ["<[0]>" code {"+" Parser}]]]]]) + [library + [lux "*" + [abstract + [monad {"+" do}]] + [control + ["<>" parser + ["<[0]>" code {"+" Parser}]]] + [macro + ["^" pattern]]]]) (def: .public default_policy Code @@ -19,8 +21,8 @@ [_ {.#Symbol ["" _]}] (in default_policy) - (^or [_ {.#Bit _}] - [_ {.#Symbol _}]) + (^.or [_ {.#Bit _}] + [_ {.#Symbol _}]) (do ! [_ <code>.any] (in candidate)) diff --git a/stdlib/source/library/lux/macro/template.lux b/stdlib/source/library/lux/macro/template.lux index 9e5db759a..df2064f4a 100644 --- a/stdlib/source/library/lux/macro/template.lux +++ b/stdlib/source/library/lux/macro/template.lux @@ -15,6 +15,8 @@ [collection ["[0]" list ("[1]#[0]" monad)] ["[0]" dictionary {"+" Dictionary}]]] + [macro + ["^" pattern]] [math [number ["[0]" nat ("[1]#[0]" decimal)] @@ -105,7 +107,7 @@ {.#None} template) - (^template [<tag>] + (^.template [<tag>] [[meta {<tag> elems}] [meta {<tag> (list#each (applied env) elems)}]]) ([.#Form] @@ -127,7 +129,7 @@ ["Expected" (# nat.decimal encoded expected)] ["Actual" (# nat.decimal encoded actual)])) -(def: (macro (^open "_[0]")) +(def: (macro (open "_[0]")) (-> Local Macro) ("lux macro" (function (_ inputs compiler) diff --git a/stdlib/source/library/lux/math/number.lux b/stdlib/source/library/lux/math/number.lux index d52fc62e0..d28d6a90c 100644 --- a/stdlib/source/library/lux/math/number.lux +++ b/stdlib/source/library/lux/math/number.lux @@ -1,17 +1,19 @@ (.using - [library - [lux "*" - [abstract - [codec {"+" Codec}]] - [control - ["[0]" try {"+" Try}]] - [data - ["[0]" text]]]] - ["[0]" / "_" - ["[1][0]" nat] - ["[1][0]" int] - ["[1][0]" rev] - ["[1][0]" frac]]) + [library + [lux "*" + [abstract + [codec {"+" Codec}]] + [control + ["[0]" try {"+" Try}]] + [data + ["[0]" text]] + [macro + ["^" pattern]]]] + ["[0]" / "_" + ["[1][0]" nat] + ["[1][0]" int] + ["[1][0]" rev] + ["[1][0]" frac]]) (def: separator ",") @@ -40,19 +42,19 @@ {try.#Success value} {try.#Success [state (list [meta {.#Nat value}])]} - (^multi {try.#Failure _} - [(# <int> decoded repr) - {try.#Success value}]) + (^.multi {try.#Failure _} + [(# <int> decoded repr) + {try.#Success value}]) {try.#Success [state (list [meta {.#Int value}])]} - (^multi {try.#Failure _} - [(# <rev> decoded repr) - {try.#Success value}]) + (^.multi {try.#Failure _} + [(# <rev> decoded repr) + {try.#Success value}]) {try.#Success [state (list [meta {.#Rev value}])]} - (^multi {try.#Failure _} - [(# <frac> decoded repr) - {try.#Success value}]) + (^.multi {try.#Failure _} + [(# <frac> decoded repr) + {try.#Success value}]) {try.#Success [state (list [meta {.#Frac value}])]} _ diff --git a/stdlib/source/library/lux/math/number/complex.lux b/stdlib/source/library/lux/math/number/complex.lux index b1c14d1bb..52947b51b 100644 --- a/stdlib/source/library/lux/math/number/complex.lux +++ b/stdlib/source/library/lux/math/number/complex.lux @@ -111,7 +111,7 @@ (def: .public (/ param input) (-> Complex Complex Complex) - (let [(^open "[0]") param] + (let [(open "[0]") param] (if (f.< (f.abs #imaginary) (f.abs #real)) (let [quot (f./ #imaginary #real) @@ -125,7 +125,7 @@ (def: .public (/' param subject) (-> Frac Complex Complex) - (let [(^open "[0]") subject] + (let [(open "[0]") subject] [..#real (f./ param #real) ..#imaginary (f./ param #imaginary)])) @@ -140,7 +140,7 @@ (def: .public (cos subject) (-> Complex Complex) - (let [(^open "[0]") subject] + (let [(open "[0]") subject] [..#real (f.* (math.cosh #imaginary) (math.cos #real)) ..#imaginary (f.opposite (f.* (math.sinh #imaginary) @@ -148,7 +148,7 @@ (def: .public (cosh subject) (-> Complex Complex) - (let [(^open "[0]") subject] + (let [(open "[0]") subject] [..#real (f.* (math.cos #imaginary) (math.cosh #real)) ..#imaginary (f.* (math.sin #imaginary) @@ -156,7 +156,7 @@ (def: .public (sin subject) (-> Complex Complex) - (let [(^open "[0]") subject] + (let [(open "[0]") subject] [..#real (f.* (math.cosh #imaginary) (math.sin #real)) ..#imaginary (f.* (math.sinh #imaginary) @@ -164,7 +164,7 @@ (def: .public (sinh subject) (-> Complex Complex) - (let [(^open "[0]") subject] + (let [(open "[0]") subject] [..#real (f.* (math.cos #imaginary) (math.sinh #real)) ..#imaginary (f.* (math.sin #imaginary) @@ -172,7 +172,7 @@ (def: .public (tan subject) (-> Complex Complex) - (let [(^open "[0]") subject + (let [(open "[0]") subject r2 (f.* +2.0 #real) i2 (f.* +2.0 #imaginary) d (f.+ (math.cos r2) (math.cosh i2))] @@ -181,7 +181,7 @@ (def: .public (tanh subject) (-> Complex Complex) - (let [(^open "[0]") subject + (let [(open "[0]") subject r2 (f.* +2.0 #real) i2 (f.* +2.0 #imaginary) d (f.+ (math.cosh r2) (math.cos i2))] @@ -190,7 +190,7 @@ (def: .public (abs subject) (-> Complex Frac) - (let [(^open "[0]") subject] + (let [(open "[0]") subject] (if (f.< (f.abs #imaginary) (f.abs #real)) (if (f.= +0.0 #imaginary) @@ -206,14 +206,14 @@ (def: .public (exp subject) (-> Complex Complex) - (let [(^open "[0]") subject + (let [(open "[0]") subject r_exp (math.exp #real)] [..#real (f.* r_exp (math.cos #imaginary)) ..#imaginary (f.* r_exp (math.sin #imaginary))])) (def: .public (log subject) (-> Complex Complex) - (let [(^open "[0]") subject] + (let [(open "[0]") subject] [..#real (|> subject ..abs math.log) ..#imaginary (math.atan/2 #real #imaginary)])) @@ -232,7 +232,7 @@ (def: .public (root/2 input) (-> Complex Complex) - (let [(^open "[0]") input + (let [(open "[0]") input t (|> input ..abs (f.+ (f.abs #real)) (f./ +2.0) (math.pow +0.5))] (if (f.< +0.0 #real) [..#real (f./ (f.* +2.0 t) @@ -246,7 +246,7 @@ (-> Complex Complex) (|> (complex +1.0) (- (* input input)) ..root/2)) -(def: .public (reciprocal (^open "[0]")) +(def: .public (reciprocal (open "[0]")) (-> Complex Complex) (if (f.< (f.abs #imaginary) (f.abs #real)) @@ -284,7 +284,7 @@ ..log (..* (../ (..complex +2.0) ..i)))) -(def: .public (argument (^open "[0]")) +(def: .public (argument (open "[0]")) (-> Complex Frac) (math.atan/2 #real #imaginary)) diff --git a/stdlib/source/library/lux/math/number/frac.lux b/stdlib/source/library/lux/math/number/frac.lux index ac528ad6d..d3cd5f138 100644 --- a/stdlib/source/library/lux/math/number/frac.lux +++ b/stdlib/source/library/lux/math/number/frac.lux @@ -14,7 +14,9 @@ ["[0]" maybe] ["[0]" try {"+" Try}]] [data - ["[0]" text]]]] + ["[0]" text]] + [macro + ["^" pattern]]]] ["[0]" // "_" ["[1][0]" i64] ["[1][0]" nat] @@ -308,13 +310,13 @@ (case [(: Nat (..exponent it)) (: Nat (..mantissa it)) (: Nat (..sign it))] - (^ [(static ..special_exponent_bits) 0 0]) + (pattern [(static ..special_exponent_bits) 0 0]) ..positive_infinity - (^ [(static ..special_exponent_bits) 0 1]) + (pattern [(static ..special_exponent_bits) 0 1]) ..negative_infinity - (^ [(static ..special_exponent_bits) _ _]) + (pattern [(static ..special_exponent_bits) _ _]) ..not_a_number ... Positive zero @@ -348,7 +350,7 @@ ("lux text index" 0 "E+" representation) ("lux text index" 0 "e-" representation) ("lux text index" 0 "E-" representation)] - (^template [<factor> <patterns>] + (^.template [<factor> <patterns>] [<patterns> (do try.monad [.let [after_offset (//nat.+ 2 split_index) @@ -358,10 +360,10 @@ (# codec decoded))] (in [("lux text clip" 0 split_index representation) (//int.* <factor> (.int exponent))]))]) - ([+1 (^or [{.#Some split_index} {.#None} {.#None} {.#None}] - [{.#None} {.#Some split_index} {.#None} {.#None}])] - [-1 (^or [{.#None} {.#None} {.#Some split_index} {.#None}] - [{.#None} {.#None} {.#None} {.#Some split_index}])]) + ([+1 (^.or [{.#Some split_index} {.#None} {.#None} {.#None}] + [{.#None} {.#Some split_index} {.#None} {.#None}])] + [-1 (^.or [{.#None} {.#None} {.#Some split_index} {.#None}] + [{.#None} {.#None} {.#None} {.#Some split_index}])]) _ {try.#Success [representation +0]})) diff --git a/stdlib/source/library/lux/math/number/int.lux b/stdlib/source/library/lux/math/number/int.lux index 67c640f22..8214514a7 100644 --- a/stdlib/source/library/lux/math/number/int.lux +++ b/stdlib/source/library/lux/math/number/int.lux @@ -14,7 +14,9 @@ ["[0]" maybe] ["[0]" try {"+" Try}]] [data - [text {"+" Char}]]]] + [text {"+" Char}]] + [macro + ["^" pattern]]]] ["[0]" // "_" ["[1][0]" nat] ["[1][0]" i64]]) @@ -145,7 +147,7 @@ (def: .public (lcm a b) (-> Int Int Int) (case [a b] - (^or [_ +0] [+0 _]) + (^.or [_ +0] [+0 _]) +0 _ @@ -216,13 +218,13 @@ (let [input_size ("lux text size" repr)] (if (//nat.> 1 input_size) (case ("lux text clip" 0 1 repr) - (^ (static ..+sign)) + (pattern (static ..+sign)) (|> repr ("lux text clip" 1 (-- input_size)) (# <codec> decoded) (# try.functor each (|>> .int))) - (^ (static ..-sign)) + (pattern (static ..-sign)) (|> repr ("lux text clip" 1 (-- input_size)) (# <codec> decoded) diff --git a/stdlib/source/library/lux/math/number/nat.lux b/stdlib/source/library/lux/math/number/nat.lux index 9d3f69e00..c52647e32 100644 --- a/stdlib/source/library/lux/math/number/nat.lux +++ b/stdlib/source/library/lux/math/number/nat.lux @@ -1,18 +1,20 @@ (.using - [library - [lux "*" - [abstract - [hash {"+" Hash}] - [enum {"+" Enum}] - [interval {"+" Interval}] - [monoid {"+" Monoid}] - [equivalence {"+" Equivalence}] - [codec {"+" Codec}] - ["[0]" order {"+" Order}]] - [control - ["[0]" function] - ["[0]" maybe] - ["[0]" try {"+" Try}]]]]) + [library + [lux "*" + [abstract + [hash {"+" Hash}] + [enum {"+" Enum}] + [interval {"+" Interval}] + [monoid {"+" Monoid}] + [equivalence {"+" Equivalence}] + [codec {"+" Codec}] + ["[0]" order {"+" Order}]] + [control + ["[0]" function] + ["[0]" maybe] + ["[0]" try {"+" Try}]] + [macro + ["^" pattern]]]]) (template [<extension> <output> <name>] [(def: .public (<name> parameter subject) @@ -125,7 +127,7 @@ (def: .public (lcm a b) (-> Nat Nat Nat) (case [a b] - (^or [_ 0] [0 _]) + (^.or [_ 0] [0 _]) 0 _ @@ -191,8 +193,8 @@ (def: (binary_value digit) (-> Nat (Maybe Nat)) (case digit - (^ (char "0")) {.#Some 0} - (^ (char "1")) {.#Some 1} + (pattern (char "0")) {.#Some 0} + (pattern (char "1")) {.#Some 1} _ {.#None})) (def: (octal_character value) @@ -211,14 +213,14 @@ (def: (octal_value digit) (-> Nat (Maybe Nat)) (case digit - (^ (char "0")) {.#Some 0} - (^ (char "1")) {.#Some 1} - (^ (char "2")) {.#Some 2} - (^ (char "3")) {.#Some 3} - (^ (char "4")) {.#Some 4} - (^ (char "5")) {.#Some 5} - (^ (char "6")) {.#Some 6} - (^ (char "7")) {.#Some 7} + (pattern (char "0")) {.#Some 0} + (pattern (char "1")) {.#Some 1} + (pattern (char "2")) {.#Some 2} + (pattern (char "3")) {.#Some 3} + (pattern (char "4")) {.#Some 4} + (pattern (char "5")) {.#Some 5} + (pattern (char "6")) {.#Some 6} + (pattern (char "7")) {.#Some 7} _ {.#None})) (def: (decimal_character value) @@ -239,16 +241,16 @@ (def: (decimal_value digit) (-> Nat (Maybe Nat)) (case digit - (^ (char "0")) {.#Some 0} - (^ (char "1")) {.#Some 1} - (^ (char "2")) {.#Some 2} - (^ (char "3")) {.#Some 3} - (^ (char "4")) {.#Some 4} - (^ (char "5")) {.#Some 5} - (^ (char "6")) {.#Some 6} - (^ (char "7")) {.#Some 7} - (^ (char "8")) {.#Some 8} - (^ (char "9")) {.#Some 9} + (pattern (char "0")) {.#Some 0} + (pattern (char "1")) {.#Some 1} + (pattern (char "2")) {.#Some 2} + (pattern (char "3")) {.#Some 3} + (pattern (char "4")) {.#Some 4} + (pattern (char "5")) {.#Some 5} + (pattern (char "6")) {.#Some 6} + (pattern (char "7")) {.#Some 7} + (pattern (char "8")) {.#Some 8} + (pattern (char "9")) {.#Some 9} _ {.#None})) (def: (hexadecimal_character value) @@ -275,13 +277,13 @@ (def: (hexadecimal_value digit) (-> Nat (Maybe Nat)) (case digit - (^template [<character> <number>] - [(^ (char <character>)) {.#Some <number>}]) + (^.template [<character> <number>] + [(pattern (char <character>)) {.#Some <number>}]) (["0" 0] ["1" 1] ["2" 2] ["3" 3] ["4" 4] ["5" 5] ["6" 6] ["7" 7] ["8" 8] ["9" 9]) - (^template [<lower> <upper> <number>] - [(^or (^ (char <lower>)) (^ (char <upper>))) {.#Some <number>}]) + (^.template [<lower> <upper> <number>] + [(^.or (pattern (char <lower>)) (pattern (char <upper>))) {.#Some <number>}]) (["a" "A" 10] ["b" "B" 11] ["c" "C" 12] ["d" "D" 13] ["e" "E" 14] ["f" "F" 15]) _ {.#None})) diff --git a/stdlib/source/library/lux/math/number/ratio.lux b/stdlib/source/library/lux/math/number/ratio.lux index 93bdca39e..d8e6bd016 100644 --- a/stdlib/source/library/lux/math/number/ratio.lux +++ b/stdlib/source/library/lux/math/number/ratio.lux @@ -33,7 +33,7 @@ 1 {.#Some (the #numerator value)} _ {.#None})) -(def: (normal (^open "_[0]")) +(def: (normal (open "_[0]")) (-> Ratio Ratio) (let [common (n.gcd _#numerator _#denominator)] [..#numerator (n./ common _#numerator) @@ -121,7 +121,7 @@ (..- (revised #numerator (n.* quot) parameter) subject))) -(def: .public (reciprocal (^open "_[0]")) +(def: .public (reciprocal (open "_[0]")) (-> Ratio Ratio) [..#numerator _#denominator ..#denominator _#numerator]) @@ -131,7 +131,7 @@ (implementation: .public codec (Codec Text Ratio) - (def: (encoded (^open "_[0]")) + (def: (encoded (open "_[0]")) ($_ text#composite (n#encoded _#numerator) ..separator (n#encoded _#denominator))) diff --git a/stdlib/source/library/lux/math/number/rev.lux b/stdlib/source/library/lux/math/number/rev.lux index 86a962e88..8b5e28996 100644 --- a/stdlib/source/library/lux/math/number/rev.lux +++ b/stdlib/source/library/lux/math/number/rev.lux @@ -251,7 +251,7 @@ (let [repr_size ("lux text size" repr)] (if (//nat.> 1 repr_size) (case ("lux text char" 0 repr) - (^ (char ".")) + (pattern (char ".")) (case (# <codec> decoded (..decimals repr)) {try.#Success output} {try.#Success (.rev output)} diff --git a/stdlib/source/library/lux/math/random.lux b/stdlib/source/library/lux/math/random.lux index 7ae9974a8..2d21ae951 100644 --- a/stdlib/source/library/lux/math/random.lux +++ b/stdlib/source/library/lux/math/random.lux @@ -1,41 +1,41 @@ (.using - [library - [lux {"-" or and list i64 nat int rev char} - [abstract - [hash {"+" Hash}] - [functor {"+" Functor}] - [apply {"+" Apply}] - ["[0]" monad {"+" Monad do}]] - [data - ["[0]" text {"+" Char} ("[1]#[0]" monoid) - ["[0]" unicode "_" - ["[1]" set]]] - [collection - ["[0]" list ("[1]#[0]" mix)] - ["[0]" array {"+" Array}] - ["[0]" dictionary {"+" Dictionary}] - ["[0]" queue {"+" Queue}] - ["[0]" set {"+" Set}] - ["[0]" stack {"+" Stack}] - ["[0]" sequence {"+" Sequence}] - [tree - ["[0]" finger {"+" Tree}]]]] - [math - [number {"+" hex} - ["n" nat] - ["i" int] - ["f" frac] - ["r" ratio] - ["c" complex] - ["[0]" i64]]] - ["[0]" time {"+" Time} - ["[0]" instant {"+" Instant}] - ["[0]" date {"+" Date}] - ["[0]" duration {"+" Duration}] - ["[0]" month {"+" Month}] - ["[0]" day {"+" Day}]] - [type - [refinement {"+" Refiner Refined}]]]]) + [library + [lux {"-" or and list i64 nat int rev char} + [abstract + [hash {"+" Hash}] + [functor {"+" Functor}] + [apply {"+" Apply}] + ["[0]" monad {"+" Monad do}]] + [data + ["[0]" text {"+" Char} ("[1]#[0]" monoid) + ["[0]" unicode "_" + ["[1]" set]]] + [collection + ["[0]" list ("[1]#[0]" mix)] + ["[0]" array {"+" Array}] + ["[0]" dictionary {"+" Dictionary}] + ["[0]" queue {"+" Queue}] + ["[0]" set {"+" Set}] + ["[0]" stack {"+" Stack}] + ["[0]" sequence {"+" Sequence}] + [tree + ["[0]" finger {"+" Tree}]]]] + [math + [number {"+" hex} + ["n" nat] + ["i" int] + ["f" frac] + ["r" ratio] + ["c" complex] + ["[0]" i64]]] + ["[0]" time {"+" Time} + ["[0]" instant {"+" Instant}] + ["[0]" date {"+" Date}] + ["[0]" duration {"+" Duration}] + ["[0]" month {"+" Month}] + ["[0]" day {"+" Day}]] + [type + [refinement {"+" Refiner Refined}]]]]) (type: .public PRNG (Rec PRNG @@ -311,7 +311,7 @@ (def: .public month (Random Month) - (let [(^open "_#[0]") ..monad] + (let [(open "_#[0]") ..monad] (..either (..either (..either (_#in {month.#January}) (..either (_#in {month.#February}) (_#in {month.#March}))) @@ -327,7 +327,7 @@ (def: .public day (Random Day) - (let [(^open "_#[0]") ..monad] + (let [(open "_#[0]") ..monad] (..either (..either (_#in {day.#Sunday}) (..either (_#in {day.#Monday}) (_#in {day.#Tuesday}))) diff --git a/stdlib/source/library/lux/meta.lux b/stdlib/source/library/lux/meta.lux index 5f6dad623..6b78550a3 100644 --- a/stdlib/source/library/lux/meta.lux +++ b/stdlib/source/library/lux/meta.lux @@ -16,6 +16,7 @@ [dictionary ["[0]" plist]]]] [macro + ["^" pattern] ["[0]" code]] [math [number @@ -136,7 +137,7 @@ (def: .public current_module (Meta Module) - (let [(^open "#[0]") ..monad] + (let [(open "#[0]") ..monad] (|> ..current_module_name (#each ..module) #conjoint))) @@ -243,7 +244,7 @@ (case (|> lux (the [.#type_context .#var_bindings]) (type_variable var)) - (^or {.#None} {.#Some {.#Var _}}) + (^.or {.#None} {.#Some {.#Var _}}) {try.#Success [lux type]} {.#Some type'} @@ -300,9 +301,9 @@ (function (_ lux) (case (: (Maybe Global) (do maybe.monad - [(^open "[0]") (|> lux - (the .#modules) - (plist.value normal_module))] + [(open "[0]") (|> lux + (the .#modules) + (plist.value normal_module))] (plist.value normal_short #definitions))) {.#Some definition} {try.#Success [lux definition]} @@ -325,8 +326,8 @@ (the .#definitions) (list.all (function (_ [def_name global]) (case global - (^or {.#Definition [exported? _]} - {.#Type [exported? _]}) + (^.or {.#Definition [exported? _]} + {.#Type [exported? _]}) (if (and exported? (text#= normal_short def_name)) {.#Some (symbol#encoded [module_name def_name])} @@ -508,8 +509,8 @@ (case (plist.value name (the .#definitions module)) {.#Some {.#Type [exported? type labels]}} (case labels - (^or {.#Left labels} - {.#Right labels}) + (^.or {.#Left labels} + {.#Right labels}) (in {.#Some (list#each (|>> [module_name]) {.#Item labels})})) @@ -534,13 +535,13 @@ (def: .public (imported_modules module_name) (-> Text (Meta (List Text))) (do ..monad - [(^open "_[0]") (..module module_name)] + [(open "_[0]") (..module module_name)] (in _#imports))) (def: .public (imported_by? import module) (-> Text Text (Meta Bit)) (do ..monad - [(^open "_[0]") (..module module)] + [(open "_[0]") (..module module)] (in (list.any? (text#= import) _#imports)))) (def: .public (imported? import) diff --git a/stdlib/source/library/lux/meta/symbol.lux b/stdlib/source/library/lux/meta/symbol.lux index b1848864d..d07f8e092 100644 --- a/stdlib/source/library/lux/meta/symbol.lux +++ b/stdlib/source/library/lux/meta/symbol.lux @@ -1,14 +1,14 @@ (.using - [library - [lux "*" - [abstract - [equivalence {"+" Equivalence}] - [hash {"+" Hash}] - [order {"+" Order}] - [codec {"+" Codec}]] - [data - ["[0]" text ("[1]#[0]" equivalence monoid)] - ["[0]" product]]]]) + [library + [lux "*" + [abstract + [equivalence {"+" Equivalence}] + [hash {"+" Hash}] + [order {"+" Order}] + [codec {"+" Codec}]] + [data + ["[0]" text ("[1]#[0]" equivalence monoid)] + ["[0]" product]]]]) ... (type: Symbol ... [Text Text]) @@ -52,10 +52,10 @@ (def: (decoded input) (case (text.all_split_by ..separator input) - (^ (list short)) + (pattern (list short)) {.#Right ["" short]} - (^ (list module short)) + (pattern (list module short)) {.#Right [module short]} _ diff --git a/stdlib/source/library/lux/meta/version.lux b/stdlib/source/library/lux/meta/version.lux index 4a8800ff4..b2a9f8784 100644 --- a/stdlib/source/library/lux/meta/version.lux +++ b/stdlib/source/library/lux/meta/version.lux @@ -21,7 +21,7 @@ (def: .public latest Version - 00,06,06) + 00,07,00) (syntax: .public (current []) (do meta.monad diff --git a/stdlib/source/library/lux/target/jvm/attribute.lux b/stdlib/source/library/lux/target/jvm/attribute.lux index ffef45083..50d73af68 100644 --- a/stdlib/source/library/lux/target/jvm/attribute.lux +++ b/stdlib/source/library/lux/target/jvm/attribute.lux @@ -12,6 +12,8 @@ ["[0]" product] [format ["[0]F" binary {"+" Writer}]]] + [macro + ["^" pattern]] [math [number ["n" nat]]]]] @@ -86,7 +88,7 @@ (def: (length attribute) (-> Attribute Nat) (case attribute - (^template [<tag>] + (^.template [<tag>] [{<tag> [name length info]} (|> length //unsigned.value (n.+ ..common_attribute_length))]) ([#Constant] diff --git a/stdlib/source/library/lux/target/jvm/bytecode.lux b/stdlib/source/library/lux/target/jvm/bytecode.lux index c104eb74a..690d5f62b 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode.lux @@ -21,6 +21,7 @@ ["[0]" dictionary {"+" Dictionary}] ["[0]" sequence {"+" Sequence}]]] [macro + ["^" pattern] ["[0]" template]] [math [number @@ -571,7 +572,7 @@ [(def: .public (<name> value) (-> <type> (Bytecode Any)) (case (|> value <to_lux>) - (^template [<special> <instruction>] + (^.template [<special> <instruction>] [<special> (..bytecode $0 $1 @_ <instruction> [])]) <specializations> @@ -621,7 +622,7 @@ (..float_bits value)) (..arbitrary_float value) (case (|> value ffi.float_to_double (:as Frac)) - (^template [<special> <instruction>] + (^.template [<special> <instruction>] [<special> (..bytecode $0 $1 @_ <instruction> [])]) ([+0.0 _.fconst_0] [+1.0 _.fconst_1] @@ -633,7 +634,7 @@ [(def: .public (<name> value) (-> <type> (Bytecode Any)) (case (|> value <to_lux>) - (^template [<special> <instruction>] + (^.template [<special> <instruction>] [<special> (..bytecode $0 $2 @_ <instruction> [])]) <specializations> @@ -667,7 +668,7 @@ (..double_bits value)) (..arbitrary_double value) (case (:as Frac value) - (^template [<special> <instruction>] + (^.template [<special> <instruction>] [<special> (..bytecode $0 $2 @_ <instruction> [])]) ([+0.0 _.dconst_0] [+1.0 _.dconst_1]) diff --git a/stdlib/source/library/lux/target/jvm/constant.lux b/stdlib/source/library/lux/target/jvm/constant.lux index 101e723fd..71aab1ed3 100644 --- a/stdlib/source/library/lux/target/jvm/constant.lux +++ b/stdlib/source/library/lux/target/jvm/constant.lux @@ -13,6 +13,7 @@ [format ["[0]F" binary {"+" Writer} ("[1]#[0]" monoid)]]] [macro + ["^" pattern] ["[0]" template]] [math [number @@ -170,7 +171,7 @@ (def: .public (size constant) (-> Constant Nat) (case constant - (^or {#Long _} {#Double _}) + (^.or {#Long _} {#Double _}) 2 _ @@ -183,7 +184,7 @@ (implementation (def: (= reference sample) (case [reference sample] - (^template [<tag> <equivalence>] + (^.template [<tag> <equivalence>] [[{<tag> reference} {<tag> sample}] (# <equivalence> = reference sample)]) ([#UTF8 text.equivalence] @@ -241,7 +242,7 @@ )] (function (_ value) (case value - (^template [<case> <tag> <writer>] + (^.template [<case> <tag> <writer>] [{<case> value} (binaryF#composite (/tag.writer <tag>) (<writer> value))]) diff --git a/stdlib/source/library/lux/target/jvm/reflection.lux b/stdlib/source/library/lux/target/jvm/reflection.lux index 98896184c..fd3900ee6 100644 --- a/stdlib/source/library/lux/target/jvm/reflection.lux +++ b/stdlib/source/library/lux/target/jvm/reflection.lux @@ -17,6 +17,8 @@ ["[0]" list ("[1]#[0]" mix functor)] ["[0]" array] ["[0]" dictionary]]] + [macro + ["^" pattern]] [math [number ["n" nat]]]]] @@ -183,7 +185,7 @@ ... allow for multiple ones. (case [(array.read! 0 (java/lang/reflect/WildcardType::getLowerBounds reflection)) (array.read! 0 (java/lang/reflect/WildcardType::getUpperBounds reflection))] - (^template [<pattern> <kind>] + (^.template [<pattern> <kind>] [<pattern> (case (ffi.check java/lang/reflect/GenericArrayType bound) {.#Some it} @@ -288,7 +290,7 @@ (def: .public (correspond class type) (-> (java/lang/Class java/lang/Object) Type (Try Mapping)) (case type - (^ {.#Primitive (static array.type_name) (list :member:)}) + (pattern {.#Primitive (static array.type_name) (list :member:)}) (if (java/lang/Class::isArray class) (correspond (java/lang/Class::getComponentType class) :member:) diff --git a/stdlib/source/library/lux/target/lua.lux b/stdlib/source/library/lux/target/lua.lux index 97f9abab1..069e5d2a7 100644 --- a/stdlib/source/library/lux/target/lua.lux +++ b/stdlib/source/library/lux/target/lua.lux @@ -1,6 +1,6 @@ (.using [library - [lux {"-" Location Code Label int if function or and not let ^ local comment the} + [lux {"-" Location Code Label int if function or and not let local comment the} ["@" target] [abstract [equivalence {"+" Equivalence}] diff --git a/stdlib/source/library/lux/time.lux b/stdlib/source/library/lux/time.lux index 2b7c172f5..f6e77fb8f 100644 --- a/stdlib/source/library/lux/time.lux +++ b/stdlib/source/library/lux/time.lux @@ -200,7 +200,7 @@ (def: (format time) (-> Time Text) - (let [(^open "_[0]") (..clock time)] + (let [(open "_[0]") (..clock time)] ($_ text#composite (..padded _#hour) ..separator (..padded _#minute) diff --git a/stdlib/source/library/lux/time/day.lux b/stdlib/source/library/lux/time/day.lux index b4eb13ede..2a717427e 100644 --- a/stdlib/source/library/lux/time/day.lux +++ b/stdlib/source/library/lux/time/day.lux @@ -1,22 +1,23 @@ (.using - [library - [lux {"-" nat} - [abstract - [equivalence {"+" Equivalence}] - [hash {"+" Hash}] - [order {"+" Order}] - [enum {"+" Enum}] - [codec {"+" Codec}]] - [control - ["[0]" try {"+" Try}] - ["[0]" exception {"+" exception:}]] - [data - ["[0]" text ("[1]#[0]" monoid)]] - [macro - ["[0]" template]] - [math - [number - ["n" nat]]]]]) + [library + [lux {"-" nat} + [abstract + [equivalence {"+" Equivalence}] + [hash {"+" Hash}] + [order {"+" Order}] + [enum {"+" Enum}] + [codec {"+" Codec}]] + [control + ["[0]" try {"+" Try}] + ["[0]" exception {"+" exception:}]] + [data + ["[0]" text ("[1]#[0]" monoid)]] + [macro + ["^" pattern] + ["[0]" template]] + [math + [number + ["n" nat]]]]]) (type: .public Day (Variant @@ -33,7 +34,7 @@ (def: (= reference sample) (case [reference sample] - (^template [<tag>] + (^.template [<tag>] [[{<tag>} {<tag>}] #1]) ([#Sunday] @@ -100,7 +101,7 @@ (def: (encoded value) (case value - (^template [<tag>] + (^.template [<tag>] [{<tag>} (text.replaced "#" "" (template.text [<tag>]))]) ([..#Monday] @@ -112,8 +113,8 @@ [..#Sunday]))) (def: (decoded value) (case (text#composite "#" value) - (^template [<tag>] - [(^ (template.text [<tag>])) + (^.template [<tag>] + [(pattern (template.text [<tag>])) {try.#Success {<tag>}}]) ([..#Monday] [..#Tuesday] @@ -144,7 +145,7 @@ (def: .public (number day) (-> Day Nat) (case day - (^template [<number> <day>] + (^.template [<number> <day>] [{<day>} <number>]) (<pairs>))) @@ -160,7 +161,7 @@ (def: .public (by_number number) (-> Nat (Try Day)) (case number - (^template [<number> <day>] + (^.template [<number> <day>] [<number> {try.#Success {<day>}}]) (<pairs>) @@ -175,7 +176,7 @@ (def: &equivalence ..equivalence) (def: (hash day) (case day - (^template [<prime> <day>] + (^.template [<prime> <day>] [{<day>} <prime>]) ([02 #Sunday] diff --git a/stdlib/source/library/lux/time/month.lux b/stdlib/source/library/lux/time/month.lux index 985e8f1cb..1916819c2 100644 --- a/stdlib/source/library/lux/time/month.lux +++ b/stdlib/source/library/lux/time/month.lux @@ -1,22 +1,23 @@ (.using - [library - [lux "*" - [abstract - [equivalence {"+" Equivalence}] - [hash {"+" Hash}] - [order {"+" Order}] - [enum {"+" Enum}] - [codec {"+" Codec}]] - [control - ["[0]" try {"+" Try}] - ["[0]" exception {"+" exception:}]] - [data - ["[0]" text ("[1]#[0]" monoid)]] - [macro - ["[0]" template]] - [math - [number - ["n" nat]]]]]) + [library + [lux "*" + [abstract + [equivalence {"+" Equivalence}] + [hash {"+" Hash}] + [order {"+" Order}] + [enum {"+" Enum}] + [codec {"+" Codec}]] + [control + ["[0]" try {"+" Try}] + ["[0]" exception {"+" exception:}]] + [data + ["[0]" text ("[1]#[0]" monoid)]] + [macro + ["^" pattern] + ["[0]" template]] + [math + [number + ["n" nat]]]]]) (type: .public Month (Variant @@ -38,7 +39,7 @@ (def: (= reference sample) (case [reference sample] - (^template [<tag>] + (^.template [<tag>] [[{<tag>} {<tag>}] true]) ([#January] @@ -72,7 +73,7 @@ (def: .public (number month) (-> Month Nat) (case month - (^template [<number> <month>] + (^.template [<number> <month>] [{<month>} <number>]) (<pairs>))) @@ -88,7 +89,7 @@ (def: .public (by_number number) (-> Nat (Try Month)) (case number - (^template [<number> <month>] + (^.template [<number> <month>] [<number> {try.#Success {<month>}}]) (<pairs>) @@ -103,7 +104,7 @@ (def: &equivalence ..equivalence) (def: (hash month) (case month - (^template [<prime> <month>] + (^.template [<prime> <month>] [{<month>} <prime>]) ([02 #January] @@ -166,7 +167,7 @@ (def: .public (days month) (-> Month Nat) (case month - (^template [<days> <month>] + (^.template [<days> <month>] [{<month>} <days>]) ([31 #January] @@ -215,7 +216,7 @@ (def: (encoded value) (case value - (^template [<tag>] + (^.template [<tag>] [{<tag>} (text.replaced "#" "" (template.text [<tag>]))]) ([..#January] @@ -232,8 +233,8 @@ [..#December]))) (def: (decoded value) (case (text#composite "#" value) - (^template [<tag>] - [(^ (template.text [<tag>])) + (^.template [<tag>] + [(pattern (template.text [<tag>])) {try.#Success {<tag>}}]) ([..#January] [..#February] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/complex.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/complex.lux index b3a2f635f..4ee608dd2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/complex.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/complex.lux @@ -49,7 +49,7 @@ [(..lefts right? pick) right?])) -(implementation: .public (equivalence (^open "/#[0]")) +(implementation: .public (equivalence (open "/#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (Complex a)))) (def: (= reference sample) 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 71bc09f77..34840bbea 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 @@ -17,6 +17,7 @@ ["[0]" dictionary {"+" Dictionary}] ["[0]" set {"+" Set} ("[1]#[0]" equivalence)]]] [macro + ["^" pattern] ["[0]" template]] [math [number @@ -89,7 +90,7 @@ [{#Bit sideR} {#Bit sideS}] (bit#= sideR sideS) - (^template [<tag>] + (^.template [<tag>] [[{<tag> partialR} {<tag> partialS}] (set#= partialR partialS)]) ([#Nat] @@ -125,7 +126,7 @@ {#Bit it} (%.bit it) - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> it} (|> it set.list @@ -164,13 +165,13 @@ (def: .public (coverage pattern) (-> Pattern (Try Coverage)) (case pattern - (^or {//pattern.#Simple {//simple.#Unit}} - {//pattern.#Bind _}) + (^.or {//pattern.#Simple {//simple.#Unit}} + {//pattern.#Bind _}) {try.#Success {#Exhaustive}} ... Simple patterns (other than unit/[]) always have partial coverage because there ... are too many possibilities as far as values go. - (^template [<from> <to> <hash>] + (^.template [<from> <to> <hash>] [{//pattern.#Simple {<from> it}} {try.#Success {<to> (set.of_list <hash> (list it))}}]) ([//simple.#Nat #Nat n.hash] @@ -189,7 +190,7 @@ ... their sub-patterns. {//pattern.#Complex {//complex.#Tuple membersP+}} (case (list.reversed membersP+) - (^or (^ (list)) (^ (list _))) + (^.or (pattern (list)) (pattern (list _))) (exception.except ..invalid_tuple [(list.size membersP+)]) {.#Item lastP prevsP+} @@ -273,7 +274,7 @@ {try.#Success {#Exhaustive}} <redundancy>) - (^template [<tag>] + (^.template [<tag>] [[{<tag> partialA} {<tag> partialSF}] (if (set.empty? (set.intersection partialA partialSF)) {try.#Success {<tag> (set.union partialA partialSF)}} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux index 4b18f2874..92435a3ae 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux @@ -15,6 +15,7 @@ [collection ["[0]" list ("[1]#[0]" functor monoid)]]] [macro + ["^" pattern] ["[0]" template]] [math [number @@ -59,7 +60,7 @@ {.#Primitive name co_variant} {.#Primitive name (list#each (quantified @var @parameter) co_variant)} - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} {<tag> (quantified @var @parameter left) (quantified @var @parameter right)}]) @@ -73,16 +74,16 @@ {.#Parameter @parameter} :it:) - (^template [<tag>] + (^.template [<tag>] [{<tag> env body} {<tag> (list#each (quantified @var @parameter) env) (quantified @var (n.+ 2 @parameter) body)}]) ([.#UnivQ] [.#ExQ]) - (^or {.#Parameter _} - {.#Ex _} - {.#Named _}) + (^.or {.#Parameter _} + {.#Ex _} + {.#Named _}) :it:)) ... Type-inference works by applying some (potentially quantified) type @@ -159,7 +160,7 @@ [[just_before vars :inference: terms] (general' (list) archive analyse inferT args)] (in [:inference: terms]) ... (case vars - ... (^ (list)) + ... (pattern (list)) ... (in [:inference: terms]) ... _ @@ -191,19 +192,19 @@ (-> Nat Type Type Type) (function (again it) (case it - (^or {.#Parameter index} - {.#Apply {.#Primitive "" {.#End}} - {.#Parameter index}}) + (^.or {.#Parameter index} + {.#Apply {.#Primitive "" {.#End}} + {.#Parameter index}}) (if (n.= @self index) recursion it) - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} {<tag> (again left) (again right)}]) ([.#Sum] [.#Product] [.#Function] [.#Apply]) - (^template [<tag>] + (^.template [<tag>] [{<tag> environment quantified} {<tag> (list#each again environment) (with_recursion (n.+ 2 @self) recursion quantified)}]) @@ -230,7 +231,7 @@ {.#Named name it} (again depth it) - (^template [<tag>] + (^.template [<tag>] [{<tag> env it} (phase#each (|>> {<tag> env}) (again (++ depth) it))]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux index 98fb50427..d86eab516 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux @@ -49,7 +49,7 @@ (do meta.monad [expansion (..expansion expander name macro inputs)] (case expansion - (^ (list single)) + (pattern (list single)) (in single) _ diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/simple.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/simple.lux index 192e6552f..b7518ded0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/simple.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/simple.lux @@ -7,6 +7,8 @@ ["[0]" bit ("[1]#[0]" equivalence)] ["[0]" text ("[1]#[0]" equivalence) ["%" format {"+" Format}]]] + [macro + ["^" pattern]] [math [number ["n" nat] @@ -32,7 +34,7 @@ [{#Unit} {#Unit}] true - (^template [<tag> <=>] + (^.template [<tag> <=>] [[{<tag> reference} {<tag> sample}] (<=> reference sample)]) ([#Bit bit#=] @@ -51,7 +53,7 @@ {#Unit} "[]" - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> value} (<format> value)]) ([#Bit %.bit] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux index f8002874f..724d85a24 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux @@ -12,6 +12,8 @@ ["%" format {"+" format}]] [collection ["[0]" list]]] + [macro + ["^" pattern]] [math [number ["n" nat]]] @@ -26,7 +28,7 @@ (def: .public (check action) (All (_ a) (-> (Check a) (Operation a))) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (case (action (the .#type_context state)) {try.#Success [context' output]} {try.#Success [[bundle (has .#type_context context' state)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux index e439110f9..cb2710a6b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux @@ -17,6 +17,7 @@ ["[0]" list ("[1]#[0]" functor mix)] ["[0]" set {"+" Set}]]] [macro + ["^" pattern] ["[0]" template]] [math [number @@ -135,7 +136,7 @@ (def: .public <get> (All (_ anchor expression directive) (Operation anchor expression directive <get_type>)) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (case (the <tag> state) {.#Some output} {try.#Success [stateE output]} @@ -168,7 +169,7 @@ (def: .public get_registry (All (_ anchor expression directive) (Operation anchor expression directive Registry)) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) {try.#Success [stateE (the #registry state)]})) (def: .public (set_registry value) @@ -204,7 +205,7 @@ (def: .public (evaluate! label code) (All (_ anchor expression directive) (-> unit.ID [(Maybe unit.ID) expression] (Operation anchor expression directive Any))) - (function (_ (^let state+ [bundle state])) + (function (_ (^.let state+ [bundle state])) (case (# (the #host state) evaluate label code) {try.#Success output} {try.#Success [state+ output]} @@ -215,7 +216,7 @@ (def: .public (execute! code) (All (_ anchor expression directive) (-> directive (Operation anchor expression directive Any))) - (function (_ (^let state+ [bundle state])) + (function (_ (^.let state+ [bundle state])) (case (# (the #host state) execute code) {try.#Success output} {try.#Success [state+ output]} @@ -226,7 +227,7 @@ (def: .public (define! context custom code) (All (_ anchor expression directive) (-> unit.ID (Maybe Text) [(Maybe unit.ID) expression] (Operation anchor expression directive [Text Any directive]))) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (case (# (the #host state) define context custom code) {try.#Success output} {try.#Success [stateE output]} @@ -253,7 +254,7 @@ [(`` (def: .public (<name> it (~~ (template.spliced <inputs>)) dependencies) (All (_ anchor expression directive) (-> <type> (~~ (template.spliced <input_types>)) (Set unit.ID) (Operation anchor expression directive artifact.ID))) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (let [[id registry'] (<artifact> it <mandatory?> dependencies (the #registry state))] {try.#Success [[bundle (has #registry registry' state)] id]}))))] @@ -276,7 +277,7 @@ (def: .public (remember archive name) (All (_ anchor expression directive) (-> Archive Symbol (Operation anchor expression directive unit.ID))) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (let [[_module _name] name] (do try.monad [@module (archive.id _module archive) @@ -295,7 +296,7 @@ (def: .public (definition archive name) (All (_ anchor expression directive) (-> Archive Symbol (Operation anchor expression directive [unit.ID (Maybe category.Definition)]))) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (let [[_module _name] name] (do try.monad [@module (archive.id _module archive) @@ -316,7 +317,7 @@ (def: .public (module_id module archive) (All (_ anchor expression directive) (-> descriptor.Module Archive (Operation anchor expression directive module.ID))) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (do try.monad [@module (archive.id module archive)] (in [stateE @module])))) @@ -324,7 +325,7 @@ (def: .public (context archive) (All (_ anchor expression directive) (-> Archive (Operation anchor expression directive unit.ID))) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (case (the #context state) {.#None} (exception.except ..no_context []) @@ -360,7 +361,7 @@ (All (_ anchor expression directive a) (-> Archive (Set unit.ID) (Operation anchor expression directive a) (Operation anchor expression directive [unit.ID a]))) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (let [[@artifact registry'] (registry.resource false dependencies (the #registry state)) @artifact (n.+ @artifact (the #registry_shift state))] (do try.monad diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux index 085e071a7..8d66cfd79 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux @@ -11,6 +11,7 @@ [collection ["[0]" list]]] [macro + ["^" pattern] ["[0]" code]] [math [number @@ -42,7 +43,7 @@ (template: (variant_analysis analysis archive tag values) ... (-> Phase Archive Symbol (List Code) (Operation Analysis)) [(case values - (^ (list value)) + (pattern (list value)) (/complex.variant analysis tag archive value) _ @@ -51,7 +52,7 @@ (template: (sum_analysis analysis archive lefts right? values) ... (-> Phase Archive Nat Bit (List Code) (Operation Analysis)) [(case values - (^ (list value)) + (pattern (list value)) (/complex.sum analysis lefts right? archive value) _ @@ -72,7 +73,7 @@ [[functionT functionA] (/type.inferring (analysis archive functionC))] (case functionA - (^ (/.constant def_name)) + (pattern (/.constant def_name)) (do ! [?macro (//extension.lifted (meta.macro def_name))] (case ?macro @@ -95,7 +96,7 @@ ... of having useful error messages. (/.with_location location) (case code - (^template [<tag> <analyser>] + (^.template [<tag> <analyser>] [[_ {<tag> value}] (<analyser> value)]) ([.#Symbol /reference.reference] @@ -106,25 +107,25 @@ [.#Int /simple.int] [.#Rev /simple.rev]) - (^code [(~+ elems)]) + (^.` [(~+ elems)]) (/complex.record analysis archive elems) - (^code {(~ [_ {.#Symbol tag}]) (~+ values)}) + (^.` {(~ [_ {.#Symbol tag}]) (~+ values)}) (..variant_analysis analysis archive tag values) - (^code ({(~+ branches)} (~ input))) + (^.` ({(~+ branches)} (~ input))) (..case_analysis analysis archive input branches code) - (^code ([(~ [_ {.#Symbol ["" function_name]}]) (~ [_ {.#Symbol ["" arg_name]}])] (~ body))) + (^.` ([(~ [_ {.#Symbol ["" function_name]}]) (~ [_ {.#Symbol ["" arg_name]}])] (~ body))) (/function.function analysis function_name arg_name archive body) - (^code ((~ [_ {.#Text extension_name}]) (~+ extension_args))) + (^.` ((~ [_ {.#Text extension_name}]) (~+ extension_args))) (//extension.apply archive analysis [extension_name extension_args]) - (^code ((~ functionC) (~+ argsC+))) + (^.` ((~ functionC) (~+ argsC+))) (..apply_analysis expander analysis archive functionC argsC+) - (^code {(~ [_ {.#Nat lefts}]) (~ [_ {.#Bit right?}]) (~+ values)}) + (^.` {(~ [_ {.#Nat lefts}]) (~ [_ {.#Bit right?}]) (~+ values)}) (..sum_analysis analysis archive lefts right? values) _ diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux index fa5dd353a..8643a435a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux @@ -18,6 +18,7 @@ [number ["n" nat]]] [macro + ["^" pattern] ["[0]" code]] ["[0]" type ["[0]" check {"+" Check}]]]] @@ -232,7 +233,7 @@ idx /scope.next] (in [{/pattern.#Bind idx} outputA]))) - (^template [<type> <input> <output>] + (^.template [<type> <input> <output>] [[location <input>] (simple_pattern_analysis <type> :input: location {/pattern.#Simple <output>} next)]) ([Bit {.#Bit pattern_value} {/simple.#Bit pattern_value}] @@ -243,7 +244,7 @@ [Text {.#Text pattern_value} {/simple.#Text pattern_value}] [Any {.#Tuple {.#End}} {/simple.#Unit}]) - (^ [location {.#Tuple (list singleton)}]) + (pattern [location {.#Tuple (list singleton)}]) (pattern_analysis {.#None} :input: singleton next) [location {.#Tuple sub_patterns}] @@ -271,7 +272,7 @@ _ (in []))] (.case members - (^ (list singleton)) + (pattern (list singleton)) (pattern_analysis {.#None} :input: singleton next) _ @@ -280,7 +281,7 @@ {.#None} (..tuple_pattern_analysis pattern_analysis :input: sub_patterns next)))) - (^ [location {.#Variant (list& [_ {.#Nat lefts}] [_ {.#Bit right?}] values)}]) + (pattern [location {.#Variant (list& [_ {.#Nat lefts}] [_ {.#Bit right?}] values)}]) (/.with_location location (do ///.monad [[@ex_var+ :input:'] (/type.check (..tuple :input:))] @@ -291,8 +292,8 @@ num_cases (maybe.else size_sum num_tags) idx (/complex.tag right? lefts)] (.case (list.item idx flat_sum) - (^multi {.#Some caseT} - (n.< num_cases idx)) + (^.multi {.#Some caseT} + (n.< num_cases idx)) (do ///.monad [[testP nextA] (if (and (n.> num_cases size_sum) (n.= (-- num_cases) idx)) @@ -321,7 +322,7 @@ _ (/.except ..mismatch [:input:' pattern])))) - (^ [location {.#Variant (list& [_ {.#Symbol tag}] values)}]) + (pattern [location {.#Variant (list& [_ {.#Symbol tag}] values)}]) (/.with_location location (do ///.monad [tag (///extension.lifted (meta.normal tag)) 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 669f4f59a..8c9407a1b 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 @@ -296,14 +296,14 @@ output (: (List [Symbol Code]) {.#End})] (case input - (^ (list& [_ {.#Symbol ["" slotH]}] valueH tail)) + (pattern (list& [_ {.#Symbol ["" slotH]}] valueH tail)) (if pattern_matching? (///#in {.#None}) (do ///.monad [slotH (///extension.lifted (meta.normal ["" slotH]))] (again tail {.#Item [slotH valueH] output}))) - (^ (list& [_ {.#Symbol slotH}] valueH tail)) + (pattern (list& [_ {.#Symbol slotH}] valueH tail)) (do ///.monad [slotH (///extension.lifted (meta.normal slotH))] (again tail {.#Item [slotH valueH] output})) @@ -388,13 +388,13 @@ (def: .public (record analyse archive members) (-> Phase Archive (List Code) (Operation Analysis)) (case members - (^ (list)) + (pattern (list)) //simple.unit - (^ (list singletonC)) + (pattern (list singletonC)) (analyse archive singletonC) - (^ (list [_ {.#Symbol pseudo_slot}] singletonC)) + (pattern (list [_ {.#Symbol pseudo_slot}] singletonC)) (do [! ///.monad] [head_k (///extension.lifted (meta.normal pseudo_slot)) slot (///extension.lifted (meta.try (meta.slot head_k)))] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux index f38a33f0d..f0f08dfcf 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux @@ -1,14 +1,16 @@ (.using [library [lux "*" + ["[0]" meta] [abstract monad] [control ["[0]" exception {"+" exception:}]] - ["[0]" meta] [data ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}]]]]] + ["%" format {"+" format}]]] + [macro + ["^" pattern]]]] ["[0]" // "_" ["/[1]" // "_" ["[1][0]" extension] @@ -48,7 +50,7 @@ {.#Definition [exported? actualT _]} (do ! [_ (/type.inference actualT) - (^let def_name [::module ::name]) (///extension.lifted (meta.normal def_name)) + (^.let def_name [::module ::name]) (///extension.lifted (meta.normal def_name)) current (///extension.lifted meta.current_module_name)] (if (text#= current ::module) <return> @@ -63,7 +65,7 @@ {.#Type [exported? value labels]} (do ! [_ (/type.inference .Type) - (^let def_name [::module ::name]) (///extension.lifted (meta.normal def_name)) + (^.let def_name [::module ::name]) (///extension.lifted (meta.normal def_name)) current (///extension.lifted meta.current_module_name)] (if (text#= current ::module) <return> diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux index f5be4859f..b3e3fd242 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux @@ -90,17 +90,17 @@ extension_eval (:as Eval (wrapper (:expected compiler_eval)))] _ (//.with (has [//extension.#state /.#analysis /.#state //extension.#state .#eval] extension_eval state))] (case code - (^ [_ {.#Form (list& [_ {.#Text name}] inputs)}]) + (pattern [_ {.#Form (list& [_ {.#Text name}] inputs)}]) (//extension.apply archive again [name inputs]) - (^ [_ {.#Form (list& macro inputs)}]) + (pattern [_ {.#Form (list& macro inputs)}]) (do ! [expansion (/.lifted_analysis (do ! [macroA (<| (///analysis/type.expecting Macro) (analysis archive macro))] (case macroA - (^ (///analysis.constant macro_name)) + (pattern (///analysis.constant macro_name)) (do ! [?macro (//extension.lifted (meta.macro macro_name)) macro (case ?macro @@ -114,7 +114,7 @@ _ (//.except ..invalid_macro_call code))))] (case expansion - (^ (list& <lux_def_module> referrals)) + (pattern (list& <lux_def_module> referrals)) (|> (again archive <lux_def_module>) (# ! each (revised /.#referrals (list#composite referrals)))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux index b4e91c905..c90c949af 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux @@ -15,7 +15,9 @@ ["%" format {"+" Format format}]] [collection ["[0]" list] - ["[0]" dictionary {"+" Dictionary}]]]]] + ["[0]" dictionary {"+" Dictionary}]]] + [macro + ["^" pattern]]]] [///// ["//" phase] [meta @@ -117,7 +119,7 @@ (def: .public (apply archive phase [name parameters]) (All (_ s i o) (-> Archive (Phase s i o) (Extension i) (Operation s i o o))) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (case (dictionary.value name bundle) {.#Some handler} (((handler name phase) archive parameters) 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 5b833c0b7..8d2e90900 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 @@ -27,6 +27,7 @@ ["[0]" format "_" ["[1]" binary]]] [macro + ["^" pattern] ["[0]" template]] [math [number @@ -400,7 +401,7 @@ {.#None} (/////analysis.except ..non_jvm_type luxT)) - (^ {.#Primitive (static array.type_name) (list elemT)}) + (pattern {.#Primitive (static array.type_name) (list elemT)}) (phase#each jvm.array (jvm_type elemT)) {.#Primitive class parametersT} @@ -448,7 +449,7 @@ (-> (Type Primitive) Handler) (function (_ extension_name analyse archive args) (case args - (^ (list arrayC)) + (pattern (list arrayC)) (do phase.monad [_ (typeA.inference ..int) arrayA (<| (typeA.expecting {.#Primitive (|> (jvm.array primitive_type) @@ -464,7 +465,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (^ (list arrayC)) + (pattern (list arrayC)) (<| typeA.with_var (function (_ [@var :var:])) (do phase.monad @@ -483,7 +484,7 @@ (-> (Type Primitive) Handler) (function (_ extension_name analyse archive args) (case args - (^ (list lengthC)) + (pattern (list lengthC)) (do phase.monad [lengthA (<| (typeA.expecting ..int) (analyse archive lengthC)) @@ -498,7 +499,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (^ (list lengthC)) + (pattern (list lengthC)) (do phase.monad [lengthA (<| (typeA.expecting ..int) (analyse archive lengthC)) @@ -519,8 +520,8 @@ (def: (check_parameter objectT) (-> .Type (Operation (Type Parameter))) (case objectT - (^ {.#Primitive (static array.type_name) - (list elementT)}) + (pattern {.#Primitive (static array.type_name) + (list elementT)}) (/////analysis.except ..non_parameter objectT) {.#Primitive name parameters} @@ -554,11 +555,11 @@ {.#None} (in (jvm.class ..object_class (list))))) - (^or {.#Ex id} - {.#Parameter id}) + (^.or {.#Ex id} + {.#Parameter id}) (phase#in (jvm.class ..object_class (list))) - (^template [<tag>] + (^.template [<tag>] [{<tag> env unquantified} (check_parameter unquantified)]) ([.#UnivQ] @@ -613,8 +614,8 @@ ... else (phase#in (jvm.class name (list))))) - (^ {.#Primitive (static array.type_name) - (list elementT)}) + (pattern {.#Primitive (static array.type_name) + (list elementT)}) (|> elementT check_jvm (phase#each jvm.array)) @@ -627,7 +628,7 @@ {.#Named name anonymous} (check_jvm anonymous) - (^template [<tag>] + (^.template [<tag>] [{<tag> env unquantified} (check_jvm unquantified)]) ([.#UnivQ] @@ -681,7 +682,7 @@ (-> .Type (Type Primitive) Handler) (function (_ extension_name analyse archive args) (case args - (^ (list idxC arrayC)) + (pattern (list idxC arrayC)) (do phase.monad [_ (typeA.inference lux_type) idxA (<| (typeA.expecting ..int) @@ -698,7 +699,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (^ (list idxC arrayC)) + (pattern (list idxC arrayC)) (<| typeA.with_var (function (_ [@var :var:])) (do phase.monad @@ -722,7 +723,7 @@ (list)}] (function (_ extension_name analyse archive args) (case args - (^ (list idxC valueC arrayC)) + (pattern (list idxC valueC arrayC)) (do phase.monad [_ (typeA.inference array_type) idxA (<| (typeA.expecting ..int) @@ -742,7 +743,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (^ (list idxC valueC arrayC)) + (pattern (list idxC valueC arrayC)) (<| typeA.with_var (function (_ [@var :var:])) (do phase.monad @@ -817,7 +818,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (^ (list)) + (pattern (list)) (do phase.monad [expectedT (///.lifted meta.expected_type) [_ :object:] (check_object expectedT) @@ -831,7 +832,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (^ (list objectC)) + (pattern (list objectC)) (do phase.monad [_ (typeA.inference .Bit) [objectT objectA] (typeA.inferring @@ -846,7 +847,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (^ (list monitorC exprC)) + (pattern (list monitorC exprC)) (do phase.monad [[monitorT monitorA] (typeA.inferring (analyse archive monitorC)) @@ -861,7 +862,7 @@ (-> java/lang/ClassLoader Handler) (function (_ extension_name analyse archive args) (case args - (^ (list exceptionC)) + (pattern (list exceptionC)) (do phase.monad [_ (typeA.inference Nothing) [exceptionT exceptionA] (typeA.inferring @@ -881,7 +882,7 @@ (-> java/lang/ClassLoader Handler) (function (_ extension_name analyse archive args) (case args - (^ (list classC)) + (pattern (list classC)) (case classC [_ {.#Text class}] (do phase.monad @@ -938,7 +939,7 @@ (def: (inheritance_candidate_parents class_loader fromT target_class toT fromC) (-> java/lang/ClassLoader .Type (java/lang/Class java/lang/Object) .Type Code (Operation (List [[Text .Type] Bit]))) (case fromT - (^ {.#Primitive _ (list& self_classT super_classT super_interfacesT+)}) + (pattern {.#Primitive _ (list& self_classT super_classT super_interfacesT+)}) (monad.each phase.monad (function (_ superT) (do [! phase.monad] @@ -955,7 +956,7 @@ (-> java/lang/ClassLoader Handler) (function (_ extension_name analyse archive args) (case args - (^ (list fromC)) + (pattern (list fromC)) (do [! phase.monad] [toT (///.lifted meta.expected_type) target_name (# ! each ..reflection (check_jvm toT)) @@ -2185,7 +2186,7 @@ (<| /////analysis.tuple (list (/////analysis.unit)) (case arity - (^or 0 1) + (^.or 0 1) bodyA 2 @@ -2399,7 +2400,7 @@ ... TODO: Handle annotations. {#Constant [name annotations type value]} (case value - (^template [<tag> <type> <constant>] + (^.template [<tag> <type> <constant>] [[_ {<tag> value}] (do pool.monad [constant (`` (|> value (~~ (template.spliced <constant>)))) 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 21cf02c95..59193e0c8 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 @@ -15,6 +15,8 @@ [collection ["[0]" list ("[1]#[0]" functor)] ["[0]" dictionary {"+" Dictionary}]]] + [macro + ["^" pattern]] [math [number ["n" nat]]] @@ -135,7 +137,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (^ (list opC)) + (pattern (list opC)) (<| typeA.with_var (function (_ [@var :var:])) (do [! ////.monad] @@ -152,7 +154,7 @@ Handler (function (_ extension_name analyse archive argsC+) (case argsC+ - (^ (list [_ {.#Text module_name}] exprC)) + (pattern (list [_ {.#Text module_name}] exprC)) (////analysis.with_current_module module_name (analyse archive exprC)) @@ -163,7 +165,7 @@ (-> Eval Handler) (function (_ extension_name analyse archive args) (case args - (^ (list typeC valueC)) + (pattern (list typeC valueC)) (do [! ////.monad] [actualT (# ! each (|>> (:as Type)) (eval archive Type typeC)) @@ -178,7 +180,7 @@ (-> Eval Handler) (function (_ extension_name analyse archive args) (case args - (^ (list typeC valueC)) + (pattern (list typeC valueC)) (do [! ////.monad] [actualT (# ! each (|>> (:as Type)) (eval archive Type typeC)) @@ -215,12 +217,12 @@ (do ! [input_type (///.lifted (meta.definition (symbol .Macro')))] (case input_type - (^or {.#Definition [exported? def_type def_value]} - {.#Type [exported? def_value labels]}) + (^.or {.#Definition [exported? def_type def_value]} + {.#Type [exported? def_value labels]}) (in (:as Type def_value)) - (^or {.#Tag _} - {.#Slot _}) + (^.or {.#Tag _} + {.#Slot _}) (////.failure (exception.error ..not_a_type [(symbol .Macro')])) {.#Alias real_name} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux index 0dc4e8ed4..a35443c11 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux @@ -25,6 +25,7 @@ ["[0]" format "_" ["[1]" binary]]] [macro + ["^" pattern] ["[0]" template]] [math [number @@ -230,7 +231,7 @@ ... TODO: Handle annotations. {#Constant [name annotations type value]} (case value - (^template [<tag> <type> <constant>] + (^.template [<tag> <type> <constant>] [[_ {<tag> value}] (do pool.monad [constant (`` (|> value (~~ (template.spliced <constant>)))) @@ -916,7 +917,7 @@ _ (..save_class! name bytecode all_dependencies)] (in directive.no_requirements)))])) -(def: (method_declaration (^open "/[0]")) +(def: (method_declaration (open "/[0]")) (-> (jvm.Method_Declaration Code) (Resource Method)) (let [type (type.method [/#type_variables /#arguments /#return /#exceptions])] (method.method ($_ modifier#composite diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux index 3680787de..831211fb9 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux @@ -23,6 +23,7 @@ ["[0]" list ("[1]#[0]" functor mix)] ["[0]" set {"+" Set}]]] [macro + ["^" pattern] ["[0]" code]] [math [number @@ -126,7 +127,7 @@ [interim_artifacts codeG] (/////generation.with_interim_artifacts archive (generate archive codeS)) .let [@abstraction (case codeS - (^ (/////synthesis.function/abstraction [env arity body])) + (pattern (/////synthesis.function/abstraction [env arity body])) (|> interim_artifacts list.last (maybe#each (|>> [arity]))) @@ -245,7 +246,7 @@ (-> Expander /////analysis.Bundle Handler) (function (_ extension_name phase archive inputsC+) (case inputsC+ - (^ (list [_ {.#Symbol ["" short_name]}] valueC exported?C)) + (pattern (list [_ {.#Symbol ["" short_name]}] valueC exported?C)) (do phase.monad [current_module (/////directive.lifted_analysis (///.lifted meta.current_module_name)) @@ -354,12 +355,12 @@ {.#Alias de_aliased} (phase.except ..cannot_alias_an_alias [[current_module alias] original de_aliased]) - (^or {.#Definition _} - {.#Type _}) + (^.or {.#Definition _} + {.#Type _}) (moduleA.define alias {.#Alias original}) - (^or {.#Tag _} - {.#Slot _}) + (^.or {.#Tag _} + {.#Slot _}) (phase.except ..cannot_alias_a_label [[current_module alias] original])))) (def: def::alias @@ -396,7 +397,7 @@ {.#Primitive name parameters} {.#Primitive name (list#each again parameters)} - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} {<tag> (again left) (again right)}]) ([.#Sum] @@ -404,12 +405,12 @@ [.#Function] [.#Apply]) - (^or {.#Parameter _} - {.#Var _} - {.#Ex _}) + (^.or {.#Parameter _} + {.#Var _} + {.#Ex _}) type - (^template [<tag>] + (^.template [<tag>] [{<tag> closure body} {<tag> closure (again body)}]) ([.#UnivQ] @@ -425,7 +426,7 @@ (Handler anchor expression directive))) (function (handler extension_name phase archive inputsC+) (case inputsC+ - (^ (list nameC valueC)) + (pattern (list nameC valueC)) (do phase.monad [target_platform (/////directive.lifted_analysis (///.lifted meta.target)) @@ -433,11 +434,11 @@ [_ handlerV] (<definer> archive (:as Text name) (let [raw_type (type <def_type>)] (case target_platform - (^or (^ (static @.jvm)) - (^ (static @.js))) + (^.or (pattern (static @.jvm)) + (pattern (static @.js))) raw_type - (^ (static @.python)) + (pattern (static @.python)) (swapped binary.Binary Binary|Python raw_type) _ @@ -519,7 +520,7 @@ (-> (Program expression directive) (Handler anchor expression directive))) (function (handler extension_name phase archive inputsC+) (case inputsC+ - (^ (list programC)) + (pattern (list programC)) (do phase.monad [state (///.lifted phase.state) .let [analyse (the [/////directive.#analysis /////directive.#phase] state) 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 f162595e7..8f4bec35c 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 @@ -12,6 +12,8 @@ [collection ["[0]" list ("[1]#[0]" functor)] ["[0]" dictionary]]] + [macro + ["^" pattern]] [math [number ["f" frac]]] @@ -105,8 +107,8 @@ [body (expression archive synthesis)] (in (:as Statement body))) - (^template [<tag>] - [(^ (<tag> value)) + (^.template [<tag>] + [(pattern (<tag> value)) (/////#each _.return (expression archive synthesis))]) ([synthesis.bit] [synthesis.i64] @@ -117,31 +119,31 @@ [synthesis.branch/get] [synthesis.function/apply]) - (^template [<tag>] - [(^ {<tag> value}) + (^.template [<tag>] + [(pattern {<tag> value}) (/////#each _.return (expression archive synthesis))]) ([synthesis.#Reference] [synthesis.#Extension]) - (^ (synthesis.branch/case case)) + (pattern (synthesis.branch/case case)) (//case.case! statement expression archive case) - (^ (synthesis.branch/exec it)) + (pattern (synthesis.branch/exec it)) (//case.exec! statement expression archive it) - (^ (synthesis.branch/let let)) + (pattern (synthesis.branch/let let)) (//case.let! statement expression archive let) - (^ (synthesis.branch/if if)) + (pattern (synthesis.branch/if if)) (//case.if! statement expression archive if) - (^ (synthesis.loop/scope scope)) + (pattern (synthesis.loop/scope scope)) (//loop.scope! statement expression archive scope) - (^ (synthesis.loop/again updates)) + (pattern (synthesis.loop/again updates)) (//loop.again! statement expression archive updates) - (^ (synthesis.function/abstraction abstraction)) + (pattern (synthesis.function/abstraction abstraction)) (/////#each _.return (//function.function statement expression archive abstraction)) )) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux index 4fbc7e603..a89e094ea 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux @@ -21,6 +21,7 @@ ["[0]" format "_" ["[1]" binary]]] [macro + ["^" pattern] ["[0]" template]] [math [number @@ -823,11 +824,11 @@ (-> Nat Synthesis Synthesis) (with_expansions [<oops> (panic! (%.format (%.nat arity) " " (//////synthesis.%synthesis body)))] (case [arity body] - (^or [0 _] - [1 _]) + (^.or [0 _] + [1 _]) body - (^ [2 {//////synthesis.#Control {//////synthesis.#Branch {//////synthesis.#Let _ 2 (//////synthesis.tuple (list _ hidden))}}}]) + (pattern [2 {//////synthesis.#Control {//////synthesis.#Branch {//////synthesis.#Let _ 2 (//////synthesis.tuple (list _ hidden))}}}]) hidden [_ {//////synthesis.#Control {//////synthesis.#Branch {//////synthesis.#Case _ path}}}] @@ -836,7 +837,7 @@ {//////synthesis.#Seq _ next} (again next) - (^ {//////synthesis.#Then (//////synthesis.tuple (list _ hidden))}) + (pattern {//////synthesis.#Then (//////synthesis.tuple (list _ hidden))}) hidden _ @@ -874,16 +875,16 @@ (-> Path Path)) (function (again path) (case path - (^ (//////synthesis.path/then bodyS)) + (pattern (//////synthesis.path/then bodyS)) (//////synthesis.path/then (normalize bodyS)) - (^template [<tag>] - [(^ {<tag> leftP rightP}) + (^.template [<tag>] + [(pattern {<tag> leftP rightP}) {<tag> (again leftP) (again rightP)}]) ([//////synthesis.#Alt] [//////synthesis.#Seq]) - (^template [<tag>] + (^.template [<tag>] [{<tag> _} path]) ([//////synthesis.#Pop] @@ -893,7 +894,7 @@ {//////synthesis.#Bit_Fork when then else} {//////synthesis.#Bit_Fork when (again then) (maybe#each again else)} - (^template [<tag>] + (^.template [<tag>] [{<tag> [[exampleH nextH] tail]} {<tag> [[exampleH (again nextH)] (list#each (function (_ [example next]) @@ -910,49 +911,49 @@ (-> Mapping Synthesis Synthesis) (function (again body) (case body - (^template [<tag>] - [(^ <tag>) + (^.template [<tag>] + [(pattern <tag>) body]) ([{//////synthesis.#Simple _}] [(//////synthesis.constant _)]) - (^ (//////synthesis.variant [lefts right? sub])) + (pattern (//////synthesis.variant [lefts right? sub])) (//////synthesis.variant [lefts right? (again sub)]) - (^ (//////synthesis.tuple members)) + (pattern (//////synthesis.tuple members)) (//////synthesis.tuple (list#each again members)) - (^ (//////synthesis.variable var)) + (pattern (//////synthesis.variable var)) (|> mapping (dictionary.value body) (maybe.else var) //////synthesis.variable) - (^ (//////synthesis.branch/case [inputS pathS])) + (pattern (//////synthesis.branch/case [inputS pathS])) (//////synthesis.branch/case [(again inputS) (normalize_path again pathS)]) - (^ (//////synthesis.branch/exec [this that])) + (pattern (//////synthesis.branch/exec [this that])) (//////synthesis.branch/exec [(again this) (again that)]) - (^ (//////synthesis.branch/let [inputS register outputS])) + (pattern (//////synthesis.branch/let [inputS register outputS])) (//////synthesis.branch/let [(again inputS) register (again outputS)]) - (^ (//////synthesis.branch/if [testS thenS elseS])) + (pattern (//////synthesis.branch/if [testS thenS elseS])) (//////synthesis.branch/if [(again testS) (again thenS) (again elseS)]) - (^ (//////synthesis.branch/get [path recordS])) + (pattern (//////synthesis.branch/get [path recordS])) (//////synthesis.branch/get [path (again recordS)]) - (^ (//////synthesis.loop/scope [offset initsS+ bodyS])) + (pattern (//////synthesis.loop/scope [offset initsS+ bodyS])) (//////synthesis.loop/scope [offset (list#each again initsS+) (again bodyS)]) - (^ (//////synthesis.loop/again updatesS+)) + (pattern (//////synthesis.loop/again updatesS+)) (//////synthesis.loop/again (list#each again updatesS+)) - (^ (//////synthesis.function/abstraction [environment arity bodyS])) + (pattern (//////synthesis.function/abstraction [environment arity bodyS])) (//////synthesis.function/abstraction [(list#each (function (_ captured) (case captured - (^ (//////synthesis.variable var)) + (pattern (//////synthesis.variable var)) (|> mapping (dictionary.value captured) (maybe.else var) @@ -964,7 +965,7 @@ arity bodyS]) - (^ (//////synthesis.function/apply [functionS inputsS+])) + (pattern (//////synthesis.function/apply [functionS inputsS+])) (//////synthesis.function/apply [(again functionS) (list#each again inputsS+)]) {//////synthesis.#Extension [name inputsS+]} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux index 40b036496..e8be23f6c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux @@ -1,45 +1,47 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" function] - ["[0]" try] - ["<>" parser - ["<s>" synthesis {"+" Parser}]]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" dictionary] - ["[0]" list ("[1]#[0]" functor mix)]]] - [math - [number - ["f" frac]]] - ["@" target - ["_" lua {"+" Expression Statement}]]]] - ["[0]" //// "_" - ["/" bundle] - ["/[1]" // "_" - ["[0]" extension] - [generation - [extension {"+" Nullary Unary Binary Trinary - nullary unary binary trinary}] - ["//" lua "_" - ["[1][0]" runtime {"+" Operation Phase Phase! Handler Bundle Generator}] - ["[1][0]" primitive] - ["[1][0]" structure] - ["[1][0]" reference] - ["[1][0]" case] - ["[1][0]" loop] - ["[1][0]" function]]] - [// - ["[0]" synthesis {"+" %synthesis}] - ["[0]" generation] - [/// - ["[1]" phase ("[1]#[0]" monad)]]]]]) + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" function] + ["[0]" try] + ["<>" parser + ["<s>" synthesis {"+" Parser}]]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" dictionary] + ["[0]" list ("[1]#[0]" functor mix)]]] + [macro + ["^" pattern]] + [math + [number + ["f" frac]]] + ["@" target + ["_" lua {"+" Expression Statement}]]]] + ["[0]" //// "_" + ["/" bundle] + ["/[1]" // "_" + ["[0]" extension] + [generation + [extension {"+" Nullary Unary Binary Trinary + nullary unary binary trinary}] + ["//" lua "_" + ["[1][0]" runtime {"+" Operation Phase Phase! Handler Bundle Generator}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" case] + ["[1][0]" loop] + ["[1][0]" function]]] + [// + ["[0]" synthesis {"+" %synthesis}] + ["[0]" generation] + [/// + ["[1]" phase ("[1]#[0]" monad)]]]]]) (def: .public (custom [parser handler]) (All (_ s) @@ -66,8 +68,8 @@ [body (expression archive synthesis)] (in (:as Statement body))) - (^template [<tag>] - [(^ (<tag> value)) + (^.template [<tag>] + [(pattern (<tag> value)) (/////#each _.return (expression archive synthesis))]) ([synthesis.bit] [synthesis.i64] @@ -78,33 +80,33 @@ [synthesis.branch/get] [synthesis.function/apply]) - (^template [<tag>] - [(^ {<tag> value}) + (^.template [<tag>] + [(pattern {<tag> value}) (/////#each _.return (expression archive synthesis))]) ([synthesis.#Reference] [synthesis.#Extension]) - (^ (synthesis.branch/case case)) + (pattern (synthesis.branch/case case)) (//case.case! statement expression archive case) - (^ (synthesis.branch/exec it)) + (pattern (synthesis.branch/exec it)) (//case.exec! statement expression archive it) - (^ (synthesis.branch/let let)) + (pattern (synthesis.branch/let let)) (//case.let! statement expression archive let) - (^ (synthesis.branch/if if)) + (pattern (synthesis.branch/if if)) (//case.if! statement expression archive if) - (^ (synthesis.loop/scope scope)) + (pattern (synthesis.loop/scope scope)) (do /////.monad [[inits scope!] (//loop.scope! statement expression archive false scope)] (in scope!)) - (^ (synthesis.loop/again updates)) + (pattern (synthesis.loop/again updates)) (//loop.again! statement expression archive updates) - (^ (synthesis.function/abstraction abstraction)) + (pattern (synthesis.function/abstraction abstraction)) (/////#each _.return (//function.function statement expression archive abstraction)) )) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux index c4be93d94..481eefce0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux @@ -1,47 +1,49 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" function] - ["[0]" try] - ["<>" parser - ["<[0]>" synthesis {"+" Parser}]]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" dictionary] - ["[0]" list ("[1]#[0]" functor mix)]]] - [math - [number - ["f" frac]]] - [target - ["_" python {"+" Expression Statement}]]]] - ["[0]" //// "_" - ["/" bundle] - ["/[1]" // "_" - ["[0]" extension] - [generation - ["[0]" reference] - [extension {"+" Nullary Unary Binary Trinary - nullary unary binary trinary}] - ["//" python "_" - ["[1][0]" runtime {"+" Operation Phase Phase! Handler Bundle Generator}] - ["[1][0]" primitive] - ["[1][0]" structure] - ["[1][0]" reference] - ["[1][0]" function] - ["[1][0]" case] - ["[1][0]" loop]]] - [// - [analysis {"+" }] - ["[0]" synthesis {"+" %synthesis}] - ["[0]" generation] - [/// - ["[1]" phase ("[1]#[0]" monad)]]]]]) + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" function] + ["[0]" try] + ["<>" parser + ["<[0]>" synthesis {"+" Parser}]]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" dictionary] + ["[0]" list ("[1]#[0]" functor mix)]]] + [macro + ["^" pattern]] + [math + [number + ["f" frac]]] + [target + ["_" python {"+" Expression Statement}]]]] + ["[0]" //// "_" + ["/" bundle] + ["/[1]" // "_" + ["[0]" extension] + [generation + ["[0]" reference] + [extension {"+" Nullary Unary Binary Trinary + nullary unary binary trinary}] + ["//" python "_" + ["[1][0]" runtime {"+" Operation Phase Phase! Handler Bundle Generator}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" function] + ["[1][0]" case] + ["[1][0]" loop]]] + [// + [analysis {"+" }] + ["[0]" synthesis {"+" %synthesis}] + ["[0]" generation] + [/// + ["[1]" phase ("[1]#[0]" monad)]]]]]) (def: .public (statement expression archive synthesis) Phase! @@ -52,8 +54,8 @@ [body (expression archive synthesis)] (in (:as (Statement Any) body))) - (^template [<tag>] - [(^ (<tag> value)) + (^.template [<tag>] + [(pattern (<tag> value)) (/////#each _.return (expression archive synthesis))]) ([synthesis.bit] [synthesis.i64] @@ -64,17 +66,17 @@ [synthesis.branch/get] [synthesis.function/apply]) - (^template [<tag>] - [(^ {<tag> value}) + (^.template [<tag>] + [(pattern {<tag> value}) (/////#each _.return (expression archive synthesis))]) ([synthesis.#Reference] [synthesis.#Extension]) - (^ (synthesis.branch/case case)) + (pattern (synthesis.branch/case case)) (//case.case! false statement expression archive case) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> statement expression archive value)]) ([synthesis.branch/exec //case.exec!] [synthesis.branch/let //case.let!] @@ -82,7 +84,7 @@ [synthesis.loop/scope //loop.scope!] [synthesis.loop/again //loop.again!]) - (^ (synthesis.function/abstraction abstraction)) + (pattern (synthesis.function/abstraction abstraction)) (/////#each _.return (//function.function statement expression archive abstraction)) )) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux index 2328c2f2a..7f71e4292 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux @@ -1,45 +1,47 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" function] - ["[0]" try] - ["<>" parser - ["<s>" synthesis {"+" Parser}]]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" dictionary] - ["[0]" list ("[1]#[0]" functor mix)]]] - [math - [number - ["f" frac]]] - [target - ["_" ruby {"+" Expression Statement}]]]] - ["[0]" //// "_" - ["/" bundle] - ["/[1]" // "_" - ["[0]" extension] - [generation - [extension {"+" Nullary Unary Binary Trinary - nullary unary binary trinary}] - ["//" ruby "_" - ["[1][0]" runtime {"+" Operation Phase Phase! Handler Bundle Generator}] - ["[1][0]" primitive] - ["[1][0]" structure] - ["[1][0]" reference] - ["[1][0]" function] - ["[1][0]" case] - ["[1][0]" loop]]] - [// - ["[0]" synthesis {"+" %synthesis}] - ["[0]" generation] - [/// - ["[1]" phase ("[1]#[0]" monad)]]]]]) + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" function] + ["[0]" try] + ["<>" parser + ["<s>" synthesis {"+" Parser}]]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" dictionary] + ["[0]" list ("[1]#[0]" functor mix)]]] + [macro + ["^" pattern]] + [math + [number + ["f" frac]]] + [target + ["_" ruby {"+" Expression Statement}]]]] + ["[0]" //// "_" + ["/" bundle] + ["/[1]" // "_" + ["[0]" extension] + [generation + [extension {"+" Nullary Unary Binary Trinary + nullary unary binary trinary}] + ["//" ruby "_" + ["[1][0]" runtime {"+" Operation Phase Phase! Handler Bundle Generator}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" function] + ["[1][0]" case] + ["[1][0]" loop]]] + [// + ["[0]" synthesis {"+" %synthesis}] + ["[0]" generation] + [/// + ["[1]" phase ("[1]#[0]" monad)]]]]]) (def: .public (custom [parser handler]) (All (_ s) @@ -64,8 +66,8 @@ (in (:as Statement body))) - (^template [<tag>] - [(^ (<tag> value)) + (^.template [<tag>] + [(pattern (<tag> value)) (/////#each _.return (expression archive synthesis))]) ([synthesis.bit] [synthesis.i64] @@ -76,17 +78,17 @@ [synthesis.branch/get] [synthesis.function/apply]) - (^template [<tag>] - [(^ {<tag> value}) + (^.template [<tag>] + [(pattern {<tag> value}) (/////#each _.return (expression archive synthesis))]) ([synthesis.#Reference] [synthesis.#Extension]) - (^ (synthesis.branch/case case)) + (pattern (synthesis.branch/case case)) (//case.case! false statement expression archive case) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> statement expression archive value)]) ([synthesis.branch/exec //case.exec!] [synthesis.branch/let //case.let!] @@ -94,7 +96,7 @@ [synthesis.loop/scope //loop.scope!] [synthesis.loop/again //loop.again!]) - (^ (synthesis.function/abstraction abstraction)) + (pattern (synthesis.function/abstraction abstraction)) (/////#each _.return (//function.function statement expression archive abstraction)) )) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp.lux index 1bd5a5f88..d92c3084f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp.lux @@ -1,33 +1,35 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]]]] - ["[0]" / "_" - [runtime {"+" Phase}] - ["[1][0]" primitive] - ["[1][0]" structure] + [library + [lux "*" + [abstract + [monad {"+" do}]] + [macro + ["^" pattern]]]] + ["[0]" / "_" + [runtime {"+" Phase}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" case] + ["[1][0]" loop] + ["[1][0]" function] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" case] - ["[1][0]" loop] - ["[1][0]" function] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" extension] ["/[1]" // "_" - ["[1][0]" extension] - ["/[1]" // "_" - [analysis {"+" }] - ["[1][0]" synthesis] - ["//[1]" /// "_" - ["[1][0]" phase ("[1]#[0]" monad)] - [reference {"+"} - [variable {"+"}]]]]]]]) + [analysis {"+" }] + ["[1][0]" synthesis] + ["//[1]" /// "_" + ["[1][0]" phase ("[1]#[0]" monad)] + [reference {"+"} + [variable {"+"}]]]]]]]) (def: .public (generate archive synthesis) Phase (case synthesis - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] @@ -37,8 +39,8 @@ {////synthesis.#Reference value} (//reference.reference /reference.system archive value) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> generate archive value)]) ([////synthesis.variant /structure.variant] [////synthesis.tuple /structure.tuple] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux index 09ab89d42..60b9cd96e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux @@ -11,6 +11,8 @@ [collection ["[0]" list ("[1]#[0]" functor mix monoid)] ["[0]" set]]] + [macro + ["^" pattern]] [math [number ["n" nat]]] @@ -65,7 +67,7 @@ [valueG (expression archive valueS)] (in (list#mix (function (_ side source) (.let [method (.case side - (^template [<side> <accessor>] + (^.template [<side> <accessor>] [(<side> lefts) (<accessor> (_.int (.int lefts)))]) ([.#Left //runtime.tuple//left] @@ -140,7 +142,7 @@ (Generator [Var/1 _.Tag _.Tag Path]) (function (again [$output @done @fail pathP]) (.case pathP - (^ (/////synthesis.path/then bodyS)) + (pattern (/////synthesis.path/then bodyS)) (# ///////phase.monad each (function (_ outputV) (_.progn (list (_.setq $output outputV) @@ -170,7 +172,7 @@ else! then!)))) - (^template [<tag> <format> <=>] + (^.template [<tag> <format> <=>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -188,41 +190,41 @@ [/////synthesis.#F64_Fork //primitive.f64 _.=/2] [/////synthesis.#Text_Fork //primitive.text _.string=/2]) - (^template [<complex> <simple> <choice>] - [(^ (<complex> idx)) + (^.template [<complex> <simple> <choice>] + [(pattern (<complex> idx)) (///////phase#in (<choice> @fail false idx {.#None})) - (^ (<simple> idx nextP)) + (pattern (<simple> idx nextP)) (|> nextP [$output @done @fail] again (# ///////phase.monad each (|>> {.#Some} (<choice> @fail true idx))))]) ([/////synthesis.side/left /////synthesis.simple_left_side ..left_choice] [/////synthesis.side/right /////synthesis.simple_right_side ..right_choice]) - (^ (/////synthesis.member/left 0)) + (pattern (/////synthesis.member/left 0)) (///////phase#in (..push! (_.elt/2 [..peek (_.int +0)]))) - (^template [<pm> <getter>] - [(^ (<pm> lefts)) + (^.template [<pm> <getter>] + [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (^ (/////synthesis.!multi_pop nextP)) + (pattern (/////synthesis.!multi_pop nextP)) (.let [[extra_pops nextP'] (////synthesis/case.count_pops nextP)] (do ///////phase.monad [next! (again [$output @done @fail nextP'])] (///////phase#in (_.progn (list (..multi_pop! (n.+ 2 extra_pops)) next!))))) - (^ (/////synthesis.path/alt preP postP)) + (pattern (/////synthesis.path/alt preP postP)) (do [! ///////phase.monad] [@otherwise (# ! each (|>> %.nat (format "lux_case_otherwise") _.tag) /////generation.next) pre! (again [$output @done @otherwise preP]) post! (again [$output @done @fail postP])] (in (..alternation @otherwise pre! post!))) - (^ (/////synthesis.path/seq preP postP)) + (pattern (/////synthesis.path/seq preP postP)) (do ///////phase.monad [pre! (again [$output @done @fail preP]) post! (again [$output @done @fail postP])] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux index 532b407a7..7a28610fb 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux @@ -1,25 +1,25 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - [parser - ["<[0]>" code]]] - [data - [collection - ["[0]" list ("[1]#[0]" functor)]]] - ["[0]" meta] - ["[0]" macro {"+" with_symbols} - ["[0]" code] - [syntax {"+" syntax:}]]]] - ["[0]" /// "_" - ["[1][0]" extension] - [// - [synthesis {"+" Synthesis}] - ["[0]" generation] - [/// - ["[1]" phase]]]]) + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + [parser + ["<[0]>" code]]] + [data + [collection + ["[0]" list ("[1]#[0]" functor)]]] + ["[0]" meta] + ["[0]" macro {"+" with_symbols} + ["[0]" code] + [syntax {"+" syntax:}]]]] + ["[0]" /// "_" + ["[1][0]" extension] + [// + [synthesis {"+" Synthesis}] + ["[0]" generation] + [/// + ["[1]" phase]]]]) (syntax: (Vector [size <code>.nat elemT <code>.any]) @@ -43,7 +43,7 @@ (generation.Handler (~ g!anchor) (~ g!expression) (~ g!directive)))) (function ((~ g!_) (~ g!name) (~ g!phase) (~ g!archive) (~ g!inputs)) (case (~ g!inputs) - (^ (list (~+ g!input+))) + (pattern (list (~+ g!input+))) (do ///.monad [(~+ (|> g!input+ (list#each (function (_ g!input) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js.lux index af1b3b605..637513242 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js.lux @@ -1,82 +1,84 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]] - [control - ["[0]" exception {"+" exception:}]] - [target - ["_" js]]]] - ["[0]" / "_" - [runtime {"+" Phase Phase!}] - ["[1][0]" primitive] - ["[1][0]" structure] + [library + [lux "*" + [abstract + [monad {"+" do}]] + [control + ["[0]" exception {"+" exception:}]] + [macro + ["^" pattern]] + [target + ["_" js]]]] + ["[0]" / "_" + [runtime {"+" Phase Phase!}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" case] + ["[1][0]" loop] + ["[1][0]" function] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" case] - ["[1][0]" loop] - ["[1][0]" function] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" extension + [generation + [js + ["[1]/[0]" common]]]] ["/[1]" // "_" - ["[1][0]" extension - [generation - [js - ["[1]/[0]" common]]]] - ["/[1]" // "_" - [analysis {"+" }] - ["[0]" synthesis] - ["//[1]" /// "_" - ["[1][0]" phase ("[1]#[0]" monad)] - [reference {"+"} - [variable {"+"}]]]]]]]) + [analysis {"+" }] + ["[0]" synthesis] + ["//[1]" /// "_" + ["[1][0]" phase ("[1]#[0]" monad)] + [reference {"+"} + [variable {"+"}]]]]]]]) (exception: .public cannot_recur_as_an_expression) (def: (expression archive synthesis) Phase (case synthesis - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([synthesis.bit /primitive.bit] [synthesis.i64 /primitive.i64] [synthesis.f64 /primitive.f64] [synthesis.text /primitive.text]) - (^ (synthesis.variant variantS)) + (pattern (synthesis.variant variantS)) (/structure.variant expression archive variantS) - (^ (synthesis.tuple members)) + (pattern (synthesis.tuple members)) (/structure.tuple expression archive members) {synthesis.#Reference value} (//reference.reference /reference.system archive value) - (^ (synthesis.branch/case case)) + (pattern (synthesis.branch/case case)) (/case.case ///extension/common.statement expression archive case) - (^ (synthesis.branch/exec it)) + (pattern (synthesis.branch/exec it)) (/case.exec expression archive it) - (^ (synthesis.branch/let let)) + (pattern (synthesis.branch/let let)) (/case.let expression archive let) - (^ (synthesis.branch/if if)) + (pattern (synthesis.branch/if if)) (/case.if expression archive if) - (^ (synthesis.branch/get get)) + (pattern (synthesis.branch/get get)) (/case.get expression archive get) - (^ (synthesis.loop/scope scope)) + (pattern (synthesis.loop/scope scope)) (/loop.scope ///extension/common.statement expression archive scope) - (^ (synthesis.loop/again updates)) + (pattern (synthesis.loop/again updates)) (//////phase.except ..cannot_recur_as_an_expression []) - (^ (synthesis.function/abstraction abstraction)) + (pattern (synthesis.function/abstraction abstraction)) (/function.function ///extension/common.statement expression archive abstraction) - (^ (synthesis.function/apply application)) + (pattern (synthesis.function/apply application)) (/function.apply expression archive application) {synthesis.#Extension extension} 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 e9b316c72..cca5cda23 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 @@ -9,6 +9,8 @@ ["[0]" text] [collection ["[0]" list ("[1]#[0]" functor mix)]]] + [macro + ["^" pattern]] [math [number ["n" nat]]] @@ -179,21 +181,21 @@ (-> (-> Path (Operation Statement)) (-> Path (Operation (Maybe Statement)))) (.case pathP - (^template [<simple> <choice>] - [(^ (<simple> idx nextP)) + (^.template [<simple> <choice>] + [(pattern (<simple> idx nextP)) (|> nextP again (# ///////phase.monad each (|>> (_.then (<choice> true idx)) {.#Some})))]) ([/////synthesis.simple_left_side ..left_choice] [/////synthesis.simple_right_side ..right_choice]) - (^ (/////synthesis.member/left 0)) + (pattern (/////synthesis.member/left 0)) (///////phase#in {.#Some (push_cursor! (_.at (_.i32 +0) ..peek_cursor))}) ... Extra optimization - (^ (/////synthesis.path/seq - (/////synthesis.member/left 0) - (/////synthesis.!bind_top register thenP))) + (pattern (/////synthesis.path/seq + (/////synthesis.member/left 0) + (/////synthesis.!bind_top register thenP))) (do ///////phase.monad [then! (again thenP)] (in {.#Some ($_ _.then @@ -201,10 +203,10 @@ then!)})) ... Extra optimization - (^template [<pm> <getter>] - [(^ (/////synthesis.path/seq - (<pm> lefts) - (/////synthesis.!bind_top register thenP))) + (^.template [<pm> <getter>] + [(pattern (/////synthesis.path/seq + (<pm> lefts) + (/////synthesis.!bind_top register thenP))) (do ///////phase.monad [then! (again thenP)] (in {.#Some ($_ _.then @@ -213,14 +215,14 @@ ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (^ (/////synthesis.!bind_top register thenP)) + (pattern (/////synthesis.!bind_top register thenP)) (do ///////phase.monad [then! (again thenP)] (in {.#Some ($_ _.then (_.define (..register register) ..peek_and_pop_cursor) then!)})) - (^ (/////synthesis.!multi_pop nextP)) + (pattern (/////synthesis.!multi_pop nextP)) (.let [[extra_pops nextP'] (////synthesis/case.count_pops nextP)] (do ///////phase.monad [next! (again nextP')] @@ -283,7 +285,7 @@ ..fail_pm! clauses))) - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> item} (do [! ///////phase.monad] [cases (monad.each ! (function (_ [match then]) @@ -295,20 +297,20 @@ ([/////synthesis.#F64_Fork //primitive.f64] [/////synthesis.#Text_Fork //primitive.text]) - (^template [<complex> <choice>] - [(^ (<complex> idx)) + (^.template [<complex> <choice>] + [(pattern (<complex> idx)) (///////phase#in (<choice> false idx))]) ([/////synthesis.side/left ..left_choice] [/////synthesis.side/right ..right_choice]) - (^template [<pm> <getter>] - [(^ (<pm> lefts)) + (^.template [<pm> <getter>] + [(pattern (<pm> lefts)) (///////phase#in (push_cursor! (<getter> (_.i32 (.int lefts)) ..peek_cursor)))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (^template [<tag> <combinator>] - [(^ (<tag> leftP rightP)) + (^.template [<tag> <combinator>] + [(pattern (<tag> leftP rightP)) (do ///////phase.monad [left! (again leftP) right! (again rightP)] 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 e97ee4c43..c18131d4c 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 @@ -36,10 +36,10 @@ (def: (setup $iteration initial? offset bindings body) (-> Var Bit Register (List Expression) Statement Statement) (case bindings - (^ (list)) + (pattern (list)) body - (^ (list binding)) + (pattern (list binding)) (let [$binding (//case.register offset)] ($_ _.then (if initial? diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm.lux index 7cabfc178..67ae82f54 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm.lux @@ -2,7 +2,9 @@ [library [lux "*" [abstract - [monad {"+" do}]]]] + [monad {"+" do}]] + [macro + ["^" pattern]]]] ["[0]" / "_" [runtime {"+" Phase}] ["[1][0]" primitive] @@ -22,18 +24,18 @@ (def: .public (generate archive synthesis) Phase (case synthesis - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (///#in (<generator> value))]) ([synthesis.bit /primitive.bit] [synthesis.i64 /primitive.i64] [synthesis.f64 /primitive.f64] [synthesis.text /primitive.text]) - (^ (synthesis.variant variantS)) + (pattern (synthesis.variant variantS)) (/structure.variant generate archive variantS) - (^ (synthesis.tuple members)) + (pattern (synthesis.tuple members)) (/structure.tuple generate archive members) {synthesis.#Reference reference} @@ -44,31 +46,31 @@ {reference.#Constant constant} (/reference.constant archive constant)) - (^ (synthesis.branch/case [valueS pathS])) + (pattern (synthesis.branch/case [valueS pathS])) (/case.case generate archive [valueS pathS]) - (^ (synthesis.branch/exec [this that])) + (pattern (synthesis.branch/exec [this that])) (/case.exec generate archive [this that]) - (^ (synthesis.branch/let [inputS register bodyS])) + (pattern (synthesis.branch/let [inputS register bodyS])) (/case.let generate archive [inputS register bodyS]) - (^ (synthesis.branch/if [conditionS thenS elseS])) + (pattern (synthesis.branch/if [conditionS thenS elseS])) (/case.if generate archive [conditionS thenS elseS]) - (^ (synthesis.branch/get [path recordS])) + (pattern (synthesis.branch/get [path recordS])) (/case.get generate archive [path recordS]) - (^ (synthesis.loop/scope scope)) + (pattern (synthesis.loop/scope scope)) (/loop.scope generate archive scope) - (^ (synthesis.loop/again updates)) + (pattern (synthesis.loop/again updates)) (/loop.again generate archive updates) - (^ (synthesis.function/abstraction abstraction)) + (pattern (synthesis.function/abstraction abstraction)) (/function.abstraction generate archive abstraction) - (^ (synthesis.function/apply application)) + (pattern (synthesis.function/apply application)) (/function.apply generate archive application) {synthesis.#Extension extension} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux index 6504a5f55..4e237921c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux @@ -10,6 +10,8 @@ ["[0]" list ("[1]#[0]" mix)]] ["[0]" text ("[1]#[0]" equivalence) ["%" format {"+" format}]]] + [macro + ["^" pattern]] [math [number ["n" nat] @@ -165,7 +167,7 @@ {synthesis.#Bind register} (..path|bind register) - (^template [<tag> <path>] + (^.template [<tag> <path>] [{<tag> it} (<path> again @else it)]) ([synthesis.#Bit_Fork ..path|bit_fork] @@ -181,7 +183,7 @@ body! (_.when_continuous (_.goto @end))))) - (^ (synthesis.side lefts right?)) + (pattern (synthesis.side lefts right?)) (operation#in (do _.monad [@success _.new_label] @@ -198,17 +200,17 @@ (_.set_label @success) //runtime.push))) - (^template [<pattern> <projection>] - [(^ (<pattern> lefts)) + (^.template [<pattern> <projection>] + [(pattern (<pattern> lefts)) (operation#in ($_ _.composite ..peek (<projection> lefts) //runtime.push)) ... Extra optimization - (^ (synthesis.path/seq - (<pattern> lefts) - (synthesis.!bind_top register thenP))) + (pattern (synthesis.path/seq + (<pattern> lefts) + (synthesis.!bind_top register thenP))) (do phase.monad [then! (path' stack_depth @else @end phase archive thenP)] (in ($_ _.composite diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux index 6a9b7bf4b..1a0569fbc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux @@ -171,7 +171,7 @@ (def: .public (apply generate archive [abstractionS inputsS]) (Generator Apply) (case abstractionS - (^ (synthesis.constant $abstraction)) + (pattern (synthesis.constant $abstraction)) (do [! phase.monad] [[@definition |abstraction|] (generation.definition archive $abstraction) .let [actual_arity (list.size inputsS)]] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux index dc3e63e85..9e7d92565 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux @@ -5,7 +5,6 @@ [abstract [monad {"+" do}]] [control - pipe ["[0]" maybe] ["[0]" try {"+" Try}] ["[0]" exception {"+" exception:}] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux index 23914096a..0d510baa6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux @@ -29,7 +29,7 @@ (def: (invariant? register changeS) (-> Register Synthesis Bit) (case changeS - (^ (synthesis.variable/local var)) + (pattern (synthesis.variable/local var)) (n.= register var) _ diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux index c1b79618b..10f11edd9 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux @@ -6,6 +6,8 @@ [monad {"+" do}]] [control ["[0]" try]] + [macro + ["^" pattern]] [math [number ["i" int]]] @@ -32,7 +34,7 @@ (def: .public (i64 value) (-> (I64 Any) (Bytecode Any)) (case (.int value) - (^template [<int> <instruction>] + (^.template [<int> <instruction>] [<int> (do _.monad [_ <instruction>] @@ -40,7 +42,7 @@ ([+0 _.lconst_0] [+1 _.lconst_1]) - (^template [<int> <instruction>] + (^.template [<int> <instruction>] [<int> (do _.monad [_ <instruction> @@ -89,14 +91,14 @@ (def: .public (f64 value) (-> Frac (Bytecode Any)) (case value - (^template [<int> <instruction>] + (^.template [<int> <instruction>] [<int> (do _.monad [_ <instruction>] ..wrap_f64)]) ([+1.0 _.dconst_1]) - (^template [<int> <instruction>] + (^.template [<int> <instruction>] [<int> (do _.monad [_ <instruction> @@ -104,7 +106,7 @@ ..wrap_f64)]) ([+2.0 _.fconst_2]) - (^template [<int> <instruction>] + (^.template [<int> <instruction>] [<int> (do _.monad [_ <instruction> diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux index 3319eb024..6493ea02a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux @@ -1,82 +1,84 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]] - [control - ["[0]" exception {"+" exception:}]] - [target - ["_" lua]]]] - ["[0]" / "_" - [runtime {"+" Phase}] - ["[1][0]" primitive] - ["[1][0]" structure] + [library + [lux "*" + [abstract + [monad {"+" do}]] + [control + ["[0]" exception {"+" exception:}]] + [macro + ["^" pattern]] + [target + ["_" lua]]]] + ["[0]" / "_" + [runtime {"+" Phase}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" case] + ["[1][0]" loop] + ["[1][0]" function] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" case] - ["[1][0]" loop] - ["[1][0]" function] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" extension + [generation + [lua + ["[1]/[0]" common]]]] ["/[1]" // "_" - ["[1][0]" extension - [generation - [lua - ["[1]/[0]" common]]]] - ["/[1]" // "_" - [analysis {"+" }] - ["[0]" synthesis] - ["//[1]" /// "_" - ["[1][0]" phase ("[1]#[0]" monad)] - [reference {"+" } - [variable {"+" }]]]]]]]) + [analysis {"+" }] + ["[0]" synthesis] + ["//[1]" /// "_" + ["[1][0]" phase ("[1]#[0]" monad)] + [reference {"+" } + [variable {"+" }]]]]]]]) (exception: .public cannot_recur_as_an_expression) (def: (expression archive synthesis) Phase (case synthesis - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([synthesis.bit /primitive.bit] [synthesis.i64 /primitive.i64] [synthesis.f64 /primitive.f64] [synthesis.text /primitive.text]) - (^ (synthesis.variant variantS)) + (pattern (synthesis.variant variantS)) (/structure.variant expression archive variantS) - (^ (synthesis.tuple members)) + (pattern (synthesis.tuple members)) (/structure.tuple expression archive members) {synthesis.#Reference value} (//reference.reference /reference.system archive value) - (^ (synthesis.branch/case case)) + (pattern (synthesis.branch/case case)) (/case.case ///extension/common.statement expression archive case) - (^ (synthesis.branch/exec it)) + (pattern (synthesis.branch/exec it)) (/case.exec expression archive it) - (^ (synthesis.branch/let let)) + (pattern (synthesis.branch/let let)) (/case.let expression archive let) - (^ (synthesis.branch/if if)) + (pattern (synthesis.branch/if if)) (/case.if expression archive if) - (^ (synthesis.branch/get get)) + (pattern (synthesis.branch/get get)) (/case.get expression archive get) - (^ (synthesis.loop/scope scope)) + (pattern (synthesis.loop/scope scope)) (/loop.scope ///extension/common.statement expression archive scope) - (^ (synthesis.loop/again updates)) + (pattern (synthesis.loop/again updates)) (//////phase.except ..cannot_recur_as_an_expression []) - (^ (synthesis.function/abstraction abstraction)) + (pattern (synthesis.function/abstraction abstraction)) (/function.function ///extension/common.statement expression archive abstraction) - (^ (synthesis.function/apply application)) + (pattern (synthesis.function/apply application)) (/function.apply expression archive application) {synthesis.#Extension extension} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux index 7e879516a..6d79e0750 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux @@ -9,6 +9,8 @@ [collection ["[0]" list ("[1]#[0]" functor mix)] ["[0]" set]]] + [macro + ["^" pattern]] [target ["_" lua {"+" Expression Var Statement}]]]] ["[0]" // "_" @@ -207,7 +209,7 @@ else! then!)))) - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -225,33 +227,33 @@ [/////synthesis.#F64_Fork _.float] [/////synthesis.#Text_Fork _.string]) - (^template [<complex> <simple> <choice>] - [(^ (<complex> idx)) + (^.template [<complex> <simple> <choice>] + [(pattern (<complex> idx)) (///////phase#in (<choice> false idx)) - (^ (<simple> idx nextP)) + (pattern (<simple> idx nextP)) (///////phase#each (_.then (<choice> true idx)) (again nextP))]) ([/////synthesis.side/left /////synthesis.simple_left_side ..left_choice] [/////synthesis.side/right /////synthesis.simple_right_side ..right_choice]) - (^ (/////synthesis.member/left 0)) + (pattern (/////synthesis.member/left 0)) (///////phase#in (|> ..peek (_.item (_.int +1)) ..push!)) - (^template [<pm> <getter>] - [(^ (<pm> lefts)) + (^.template [<pm> <getter>] + [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (^ (/////synthesis.!bind_top register thenP)) + (pattern (/////synthesis.!bind_top register thenP)) (do ///////phase.monad [then! (again thenP)] (///////phase#in ($_ _.then (_.local/1 (..register register) ..peek_and_pop) then!))) - (^template [<tag> <combinator>] - [(^ (<tag> preP postP)) + (^.template [<tag> <combinator>] + [(pattern (<tag> preP postP)) (do ///////phase.monad [pre! (again preP) post! (again postP)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux index 205510ed1..460350507 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux @@ -1,37 +1,39 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]] - [control - ["[0]" exception {"+" exception:}]] - [target - ["_" php]]]] - ["[0]" / "_" - [runtime {"+" Phase Phase!}] - ["[1][0]" primitive] - ["[1][0]" structure] + [library + [lux "*" + [abstract + [monad {"+" do}]] + [control + ["[0]" exception {"+" exception:}]] + [macro + ["^" pattern]] + [target + ["_" php]]]] + ["[0]" / "_" + [runtime {"+" Phase Phase!}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" case] + ["[1][0]" loop] + ["[1][0]" function] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" case] - ["[1][0]" loop] - ["[1][0]" function] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" extension] ["/[1]" // "_" - ["[1][0]" extension] - ["/[1]" // "_" - [analysis {"+" }] - ["[1][0]" synthesis] - ["//[1]" /// "_" - ["[1][0]" phase ("[1]#[0]" monad)] - [reference {"+"} - [variable {"+"}]]]]]]]) + [analysis {"+" }] + ["[1][0]" synthesis] + ["//[1]" /// "_" + ["[1][0]" phase ("[1]#[0]" monad)] + [reference {"+"} + [variable {"+"}]]]]]]]) (def: (statement expression archive synthesis) Phase! (case synthesis - (^template [<tag>] - [(^ (<tag> value)) + (^.template [<tag>] + [(pattern (<tag> value)) (//////phase#each _.return (expression archive synthesis))]) ([////synthesis.bit] [////synthesis.i64] @@ -42,24 +44,24 @@ [////synthesis.branch/get] [////synthesis.function/apply]) - (^template [<tag>] - [(^ {<tag> value}) + (^.template [<tag>] + [(pattern {<tag> value}) (//////phase#each _.return (expression archive synthesis))]) ([////synthesis.#Reference] [////synthesis.#Extension]) - (^ (////synthesis.branch/case case)) + (pattern (////synthesis.branch/case case)) (/case.case! statement expression archive case) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> statement expression archive value)]) ([////synthesis.branch/let /case.let!] [////synthesis.branch/if /case.if!] [////synthesis.loop/scope /loop.scope!] [////synthesis.loop/again /loop.again!]) - (^ (////synthesis.function/abstraction abstraction)) + (pattern (////synthesis.function/abstraction abstraction)) (//////phase#each _.return (/function.function statement expression archive abstraction)) )) @@ -68,8 +70,8 @@ (def: .public (expression archive synthesis) Phase (case synthesis - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] @@ -79,8 +81,8 @@ {////synthesis.#Reference value} (//reference.reference /reference.system archive value) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> expression archive value)]) ([////synthesis.variant /structure.variant] [////synthesis.tuple /structure.tuple] @@ -89,14 +91,14 @@ [////synthesis.branch/get /case.get] [////synthesis.function/apply /function.apply]) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> statement expression archive value)]) ([////synthesis.branch/case /case.case] [////synthesis.loop/scope /loop.scope] [////synthesis.function/abstraction /function.function]) - (^ (////synthesis.loop/again _)) + (pattern (////synthesis.loop/again _)) (//////phase.except ..cannot_recur_as_an_expression []) {////synthesis.#Extension extension} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux index 54685bfff..595c313cf 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux @@ -10,6 +10,8 @@ [collection ["[0]" list ("[1]#[0]" functor mix)] ["[0]" set]]] + [macro + ["^" pattern]] [math [number ["i" int]]] @@ -85,7 +87,7 @@ [valueG (expression archive valueS)] (in (list#mix (function (_ side source) (.let [method (.case side - (^template [<side> <accessor>] + (^.template [<side> <accessor>] [(<side> lefts) (<accessor> (_.int (.int lefts)))]) ([.#Left //runtime.tuple//left] @@ -189,7 +191,7 @@ else! then!)))) - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -204,34 +206,34 @@ [/////synthesis.#F64_Fork //primitive.f64] [/////synthesis.#Text_Fork //primitive.text]) - (^template [<complex> <simple> <choice>] - [(^ (<complex> idx)) + (^.template [<complex> <simple> <choice>] + [(pattern (<complex> idx)) (///////phase#in (<choice> false idx)) - (^ (<simple> idx nextP)) + (pattern (<simple> idx nextP)) (|> nextP again (# ///////phase.monad each (_.then (<choice> true idx))))]) ([/////synthesis.side/left /////synthesis.simple_left_side ..left_choice] [/////synthesis.side/right /////synthesis.simple_right_side ..right_choice]) - (^ (/////synthesis.member/left 0)) + (pattern (/////synthesis.member/left 0)) (///////phase#in (|> ..peek (_.item (_.int +0)) ..push!)) - (^template [<pm> <getter>] - [(^ (<pm> lefts)) + (^.template [<pm> <getter>] + [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (^ (/////synthesis.!bind_top register thenP)) + (pattern (/////synthesis.!bind_top register thenP)) (do ///////phase.monad [then! (again thenP)] (///////phase#in ($_ _.then (_.set! (..register register) ..peek_and_pop) then!))) - ... (^ (/////synthesis.!multi_pop nextP)) + ... (pattern (/////synthesis.!multi_pop nextP)) ... (.let [[extra_pops nextP'] (////synthesis/case.count_pops nextP)] ... (do ///////phase.monad ... [next! (again nextP')] @@ -239,8 +241,8 @@ ... (..multi_pop! (n.+ 2 extra_pops)) ... next!)))) - (^template [<tag> <combinator>] - [(^ (<tag> preP postP)) + (^.template [<tag> <combinator>] + [(pattern (<tag> preP postP)) (do ///////phase.monad [pre! (again preP) post! (again postP)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux index 10a220018..7e620b07a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux @@ -5,6 +5,8 @@ [monad {"+" do}]] [control ["[0]" exception {"+" exception:}]] + [macro + ["^" pattern]] [target ["_" python]]]] ["[0]" / "_" @@ -35,16 +37,16 @@ (def: .public (expression archive synthesis) Phase (case synthesis - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] [////synthesis.f64 /primitive.f64] [////synthesis.text /primitive.text]) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> expression archive value)]) ([////synthesis.variant /structure.variant] [////synthesis.tuple /structure.tuple] @@ -56,14 +58,14 @@ [////synthesis.function/apply /function.apply]) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> ///extension/common.statement expression archive value)]) ([////synthesis.branch/case /case.case] [////synthesis.loop/scope /loop.scope] [////synthesis.function/abstraction /function.function]) - (^ (////synthesis.loop/again updates)) + (pattern (////synthesis.loop/again updates)) (//////phase.except ..cannot_recur_as_an_expression []) {////synthesis.#Reference value} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux index bfb3ebdc8..3e4699361 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux @@ -9,6 +9,8 @@ [collection ["[0]" list ("[1]#[0]" functor mix)] ["[0]" set]]] + [macro + ["^" pattern]] [math [number ["n" nat] @@ -216,7 +218,7 @@ else! then!))})) - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -256,34 +258,34 @@ {/////synthesis.#Bind register} (///////phase#in (_.set (list (..register register)) ..peek)) - (^template [<complex> <simple> <choice>] - [(^ (<complex> idx)) + (^.template [<complex> <simple> <choice>] + [(pattern (<complex> idx)) (///////phase#in (<choice> false idx)) - (^ (<simple> idx nextP)) + (pattern (<simple> idx nextP)) (|> nextP again (///////phase#each (_.then (<choice> true idx))))]) ([/////synthesis.side/left /////synthesis.simple_left_side ..left_choice] [/////synthesis.side/right /////synthesis.simple_right_side ..right_choice]) - (^ (/////synthesis.member/left 0)) + (pattern (/////synthesis.member/left 0)) (///////phase#in (|> ..peek (_.item (_.int +0)) ..push!)) - (^template [<pm> <getter>] - [(^ (<pm> lefts)) + (^.template [<pm> <getter>] + [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple::left] [/////synthesis.member/right //runtime.tuple::right]) - (^ (/////synthesis.!bind_top register thenP)) + (pattern (/////synthesis.!bind_top register thenP)) (do ! [then! (again thenP)] (///////phase#in ($_ _.then (_.set (list (..register register)) ..peek_and_pop) then!))) - (^ (/////synthesis.!multi_pop nextP)) + (pattern (/////synthesis.!multi_pop nextP)) (.let [[extra_pops nextP'] (case.count_pops nextP)] (do ! [next! (again nextP')] @@ -291,13 +293,13 @@ (..multi_pop! (n.+ 2 extra_pops)) next!)))) - (^ (/////synthesis.path/seq preP postP)) + (pattern (/////synthesis.path/seq preP postP)) (do ! [pre! (again preP) post! (again postP)] (in (_.then pre! post!))) - (^ (/////synthesis.path/alt preP postP)) + (pattern (/////synthesis.path/alt preP postP)) (do ! [pre! (again preP) post! (again postP) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r.lux index 6e2e8ccb2..ff391b986 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r.lux @@ -1,35 +1,37 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]] - [target - ["_" r]]]] - ["[0]" / "_" - [runtime {"+" Phase}] - ["[1][0]" primitive] - ["[1][0]" structure] + [library + [lux "*" + [abstract + [monad {"+" do}]] + [macro + ["^" pattern]] + [target + ["_" r]]]] + ["[0]" / "_" + [runtime {"+" Phase}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" case] + ["[1][0]" loop] + ["[1][0]" function] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" case] - ["[1][0]" loop] - ["[1][0]" function] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" extension] ["/[1]" // "_" - ["[1][0]" extension] - ["/[1]" // "_" - [analysis {"+" }] - ["[1][0]" synthesis] - ["//[1]" /// "_" - ["[1][0]" phase ("[1]#[0]" monad)] - [reference {"+"} - [variable {"+"}]]]]]]]) + [analysis {"+" }] + ["[1][0]" synthesis] + ["//[1]" /// "_" + ["[1][0]" phase ("[1]#[0]" monad)] + [reference {"+"} + [variable {"+"}]]]]]]]) (def: .public (generate archive synthesis) Phase (case synthesis - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] @@ -39,8 +41,8 @@ {////synthesis.#Reference value} (//reference.reference /reference.system archive value) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> generate archive value)]) ([////synthesis.variant /structure.variant] [////synthesis.tuple /structure.tuple] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux index a7b82af5a..2b849271b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux @@ -1,40 +1,41 @@ (.using - [library - [lux {"-" case let if} - [abstract - ["[0]" monad {"+" do}]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor mix)] - ["[0]" set]]] - [macro - ["[0]" template]] - [math - [number - ["i" int]]] - [target - ["_" r {"+" Expression SVar}]]]] - ["[0]" // "_" - ["[1][0]" runtime {"+" Operation Phase Generator}] + [library + [lux {"-" case let if} + [abstract + ["[0]" monad {"+" do}]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor mix)] + ["[0]" set]]] + [macro + ["^" pattern] + ["[0]" template]] + [math + [number + ["i" int]]] + [target + ["_" r {"+" Expression SVar}]]]] + ["[0]" // "_" + ["[1][0]" runtime {"+" Operation Phase Generator}] + ["[1][0]" reference] + ["[1][0]" primitive] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" primitive] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" synthesis "_" + ["[1]/[0]" case]] ["/[1]" // "_" - ["[1][0]" synthesis "_" - ["[1]/[0]" case]] - ["/[1]" // "_" - ["[1][0]" synthesis {"+" Member Synthesis Path}] - ["[1][0]" generation] - ["//[1]" /// "_" - [reference - ["[1][0]" variable {"+" Register}]] - ["[1][0]" phase ("[1]#[0]" monad)] - [meta - [archive {"+" Archive}]]]]]]]) + ["[1][0]" synthesis {"+" Member Synthesis Path}] + ["[1][0]" generation] + ["//[1]" /// "_" + [reference + ["[1][0]" variable {"+" Register}]] + ["[1][0]" phase ("[1]#[0]" monad)] + [meta + [archive {"+" Archive}]]]]]]]) (def: .public register (-> Register SVar) @@ -68,7 +69,7 @@ [valueO (expression archive valueS)] (in (list#mix (function (_ side source) (.let [method (.case side - (^template [<side> <accessor>] + (^.template [<side> <accessor>] [(<side> lefts) (<accessor> (_.int (.int lefts)))]) ([.#Left //runtime.tuple::left] @@ -161,7 +162,7 @@ else! then!)))) - (^template [<tag> <format> <=>] + (^.template [<tag> <format> <=>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -179,8 +180,8 @@ [/////synthesis.#F64_Fork //primitive.f64 _.=] [/////synthesis.#Text_Fork //primitive.text _.=]) - (^template [<pm> <flag> <prep>] - [(^ (<pm> idx)) + (^.template [<pm> <flag> <prep>] + [(pattern (<pm> idx)) (///////phase#in ($_ _.then (_.set! $temp (|> idx <prep> .int _.int (//runtime.sum::get ..peek (//runtime.flag <flag>)))) (_.if (_.= _.null $temp) @@ -189,16 +190,16 @@ ([/////synthesis.side/left false (<|)] [/////synthesis.side/right true ++]) - (^ (/////synthesis.member/left 0)) + (pattern (/////synthesis.member/left 0)) (///////phase#in (_.item (_.int +1) ..peek)) - (^template [<pm> <getter>] - [(^ (<pm> lefts)) + (^.template [<pm> <getter>] + [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push_cursor!))]) ([/////synthesis.member/left //runtime.tuple::left] [/////synthesis.member/right //runtime.tuple::right]) - (^ (/////synthesis.path/seq leftP rightP)) + (pattern (/////synthesis.path/seq leftP rightP)) (do ///////phase.monad [leftO (again leftP) rightO (again rightP)] @@ -206,7 +207,7 @@ leftO rightO))) - (^ (/////synthesis.path/alt leftP rightP)) + (pattern (/////synthesis.path/alt leftP rightP)) (do [! ///////phase.monad] [leftO (again leftP) rightO (again rightP)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux index 65f464d29..e0800d768 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux @@ -1,28 +1,28 @@ (.using - lux - (lux (control [library - [monad {"+" do}]] - ["ex" exception {"+" exception:}] - ["p" parser]) - (data ["e" error] - [text] - text/format - [number] - (coll [list "list/" Functor<List>] - (dictionary ["dict" unordered {"+" Dict}]))) - [macro {"+" with_symbols}] - (macro [code] - ["s" syntax {"+" syntax:}]) - [host]) - (luxc ["&" lang] - (lang ["la" analysis] - ["ls" synthesis] - (host [r {"+" Expression}]))) - [///] - (/// ["[0]T" runtime] - ["[0]T" case] - ["[0]T" function] - ["[0]T" loop])) + lux + (lux (control [library + [monad {"+" do}]] + ["ex" exception {"+" exception:}] + ["p" parser]) + (data ["e" error] + [text] + text/format + [number] + (coll [list "list/" Functor<List>] + (dictionary ["dict" unordered {"+" Dict}]))) + [macro {"+" with_symbols}] + (macro [code] + ["s" syntax {"+" syntax:}]) + [host]) + (luxc ["&" lang] + (lang ["la" analysis] + ["ls" synthesis] + (host [r {"+" Expression}]))) + [///] + (/// ["[0]T" runtime] + ["[0]T" case] + ["[0]T" function] + ["[0]T" loop])) ... [Types] (type: .public Translator @@ -74,7 +74,7 @@ (function ((~ g!_) (~ g!name)) (function ((~ g!_) (~ g!translate) (~ g!inputs)) (case (~ g!inputs) - (^ (list (~+ g!input+))) + (pattern (list (~+ g!input+))) (do macro.Monad<Meta> [(~+ (|> g!input+ (list/each (function (_ g!input) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux index 04094f9a9..f459b2d31 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux @@ -1,19 +1,19 @@ (.using - lux - (lux (control [library - [monad {"+" do}]]) - (data [text] - text/format - (coll [list "list/" Functor<List>] - (dictionary ["dict" unordered {"+" Dict}]))) - [macro "macro/" Monad<Meta>]) - (luxc ["&" lang] - (lang ["la" analysis] - ["ls" synthesis] - (host [ruby {"+" Ruby Expression Statement}]))) - [///] - (/// ["[0]T" runtime]) - (// ["@" common])) + lux + (lux (control [library + [monad {"+" do}]]) + (data [text] + text/format + (coll [list "list/" Functor<List>] + (dictionary ["dict" unordered {"+" Dict}]))) + [macro "macro/" Monad<Meta>]) + (luxc ["&" lang] + (lang ["la" analysis] + ["ls" synthesis] + (host [ruby {"+" Ruby Expression Statement}]))) + [///] + (/// ["[0]T" runtime]) + (// ["@" common])) ... (template [<name> <lua>] ... [(def: (<name> _) @.Nullary <lua>)] @@ -25,7 +25,7 @@ ... (def: (lua//global proc translate inputs) ... (-> Text @.Proc) ... (case inputs -... (^ (list [_ {.#Text name}])) +... (pattern (list [_ {.#Text name}])) ... (do macro.Monad<Meta> ... [] ... (in name)) @@ -36,7 +36,7 @@ ... (def: (lua//call proc translate inputs) ... (-> Text @.Proc) ... (case inputs -... (^ (list& functionS argsS+)) +... (pattern (list& functionS argsS+)) ... (do [@ macro.Monad<Meta>] ... [functionO (translate functionS) ... argsO+ (monad.each @ translate argsS+)] @@ -56,7 +56,7 @@ ... (def: (table//call proc translate inputs) ... (-> Text @.Proc) ... (case inputs -... (^ (list& tableS [_ {.#Text field}] argsS+)) +... (pattern (list& tableS [_ {.#Text field}] argsS+)) ... (do [@ macro.Monad<Meta>] ... [tableO (translate tableS) ... argsO+ (monad.each @ translate argsS+)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux index ca563e3e1..8e8da02ef 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux @@ -1,50 +1,52 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]] - [control - ["[0]" exception {"+" exception:}]] - [target - ["_" ruby]]]] - ["[0]" / "_" - [runtime {"+" Phase Phase!}] - ["[1][0]" primitive] - ["[1][0]" structure] + [library + [lux "*" + [abstract + [monad {"+" do}]] + [control + ["[0]" exception {"+" exception:}]] + [macro + ["^" pattern]] + [target + ["_" ruby]]]] + ["[0]" / "_" + [runtime {"+" Phase Phase!}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" function] + ["[1][0]" case] + ["[1][0]" loop] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" function] - ["[1][0]" case] - ["[1][0]" loop] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" extension + [generation + [ruby + ["[1]/[0]" common]]]] ["/[1]" // "_" - ["[1][0]" extension - [generation - [ruby - ["[1]/[0]" common]]]] - ["/[1]" // "_" - [analysis {"+" }] - ["[1][0]" synthesis] - ["//[1]" /// "_" - ["[1][0]" phase ("[1]#[0]" monad)] - [reference {"+" } - [variable {"+" }]]]]]]]) + [analysis {"+" }] + ["[1][0]" synthesis] + ["//[1]" /// "_" + ["[1][0]" phase ("[1]#[0]" monad)] + [reference {"+" } + [variable {"+" }]]]]]]]) (exception: .public cannot_recur_as_an_expression) (def: (expression archive synthesis) Phase (case synthesis - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] [////synthesis.f64 /primitive.f64] [////synthesis.text /primitive.text]) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> expression archive value)]) ([////synthesis.variant /structure.variant] [////synthesis.tuple /structure.tuple] @@ -56,14 +58,14 @@ [////synthesis.function/apply /function.apply]) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> ///extension/common.statement expression archive value)]) ([////synthesis.branch/case /case.case] [////synthesis.loop/scope /loop.scope] [////synthesis.function/abstraction /function.function]) - (^ (////synthesis.loop/again _)) + (pattern (////synthesis.loop/again _)) (//////phase.except ..cannot_recur_as_an_expression []) {////synthesis.#Reference value} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux index d4abe4b2b..1d513b57b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux @@ -11,6 +11,8 @@ [collection ["[0]" list ("[1]#[0]" functor mix)] ["[0]" set]]] + [macro + ["^" pattern]] [math [number ["n" nat] @@ -225,7 +227,7 @@ else! then!))})) - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -282,7 +284,7 @@ else! then!)))) - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -299,34 +301,34 @@ [/////synthesis.#F64_Fork (<| //primitive.f64)] [/////synthesis.#Text_Fork (<| //primitive.text)]) - (^template [<complex> <simple> <choice>] - [(^ (<complex> idx)) + (^.template [<complex> <simple> <choice>] + [(pattern (<complex> idx)) (///////phase#in (<choice> false idx)) - (^ (<simple> idx nextP)) + (pattern (<simple> idx nextP)) (|> nextP again (///////phase#each (_.then (<choice> true idx))))]) ([/////synthesis.side/left /////synthesis.simple_left_side ..left_choice] [/////synthesis.side/right /////synthesis.simple_right_side ..right_choice]) - (^ (/////synthesis.member/left 0)) + (pattern (/////synthesis.member/left 0)) (///////phase#in (|> ..peek (_.item (_.int +0)) ..push!)) - (^template [<pm> <getter>] - [(^ (<pm> lefts)) + (^.template [<pm> <getter>] + [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (^ (/////synthesis.!bind_top register thenP)) + (pattern (/////synthesis.!bind_top register thenP)) (do ///////phase.monad [then! (again thenP)] (///////phase#in ($_ _.then (_.set (list (..register register)) ..peek_and_pop) then!))) - (^ (/////synthesis.!multi_pop nextP)) + (pattern (/////synthesis.!multi_pop nextP)) (.let [[extra_pops nextP'] (case.count_pops nextP)] (do ///////phase.monad [next! (again nextP')] @@ -334,7 +336,7 @@ (..multi_pop! (n.+ 2 extra_pops)) next!)))) - (^ (/////synthesis.path/seq preP postP)) + (pattern (/////synthesis.path/seq preP postP)) (do ///////phase.monad [pre! (again preP) post! (again postP)] @@ -342,7 +344,7 @@ pre! post!))) - (^ (/////synthesis.path/alt preP postP)) + (pattern (/////synthesis.path/alt preP postP)) (do ///////phase.monad [pre! (again preP) post! (again postP) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme.lux index 9052782ec..690ab94b9 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme.lux @@ -1,35 +1,37 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]] - [target - ["_" scheme]]]] - ["[0]" / "_" - [runtime {"+" Phase}] - ["[1][0]" primitive] - ["[1][0]" structure] + [library + [lux "*" + [abstract + [monad {"+" do}]] + [macro + ["^" pattern]] + [target + ["_" scheme]]]] + ["[0]" / "_" + [runtime {"+" Phase}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" case] + ["[1][0]" loop] + ["[1][0]" function] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" case] - ["[1][0]" loop] - ["[1][0]" function] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" extension] ["/[1]" // "_" - ["[1][0]" extension] - ["/[1]" // "_" - [analysis {"+" }] - ["[1][0]" synthesis] - ["//[1]" /// "_" - ["[1][0]" phase ("[1]#[0]" monad)] - [reference {"+"} - [variable {"+"}]]]]]]]) + [analysis {"+" }] + ["[1][0]" synthesis] + ["//[1]" /// "_" + ["[1][0]" phase ("[1]#[0]" monad)] + [reference {"+"} + [variable {"+"}]]]]]]]) (def: .public (generate archive synthesis) Phase (case synthesis - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] @@ -39,8 +41,8 @@ {////synthesis.#Reference value} (//reference.reference /reference.system archive value) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> generate archive value)]) ([////synthesis.variant /structure.variant] [////synthesis.tuple /structure.tuple] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux index 3db6fab36..aeed6ea59 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux @@ -1,40 +1,41 @@ (.using - [library - [lux {"-" case let if} - [abstract - ["[0]" monad {"+" do}]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor mix)] - ["[0]" set]]] - [macro - ["[0]" template]] - [math - [number - ["i" int]]] - [target - ["_" scheme {"+" Expression Computation Var}]]]] - ["[0]" // "_" - ["[1][0]" runtime {"+" Operation Phase Generator}] + [library + [lux {"-" case let if} + [abstract + ["[0]" monad {"+" do}]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor mix)] + ["[0]" set]]] + [macro + ["^" pattern] + ["[0]" template]] + [math + [number + ["i" int]]] + [target + ["_" scheme {"+" Expression Computation Var}]]]] + ["[0]" // "_" + ["[1][0]" runtime {"+" Operation Phase Generator}] + ["[1][0]" reference] + ["[1][0]" primitive] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" primitive] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" synthesis "_" + ["[1]/[0]" case]] ["/[1]" // "_" - ["[1][0]" synthesis "_" - ["[1]/[0]" case]] - ["/[1]" // "_" - ["[1][0]" synthesis {"+" Member Synthesis Path}] - ["[1][0]" generation] - ["//[1]" /// "_" - [reference - ["[1][0]" variable {"+" Register}]] - ["[1][0]" phase ("[1]#[0]" monad)] - [meta - [archive {"+" Archive}]]]]]]]) + ["[1][0]" synthesis {"+" Member Synthesis Path}] + ["[1][0]" generation] + ["//[1]" /// "_" + [reference + ["[1][0]" variable {"+" Register}]] + ["[1][0]" phase ("[1]#[0]" monad)] + [meta + [archive {"+" Archive}]]]]]]]) (def: .public register (-> Register Var) @@ -66,7 +67,7 @@ [valueO (expression archive valueS)] (in (list#mix (function (_ side source) (.let [method (.case side - (^template [<side> <accessor>] + (^.template [<side> <accessor>] [(<side> lefts) (<accessor> (_.int (.int lefts)))]) ([.#Left //runtime.tuple//left] @@ -155,7 +156,7 @@ else! then!)))) - (^template [<tag> <format> <=>] + (^.template [<tag> <format> <=>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -173,8 +174,8 @@ [/////synthesis.#F64_Fork //primitive.f64 _.=/2] [/////synthesis.#Text_Fork //primitive.text _.string=?/2]) - (^template [<pm> <flag> <prep>] - [(^ (<pm> idx)) + (^.template [<pm> <flag> <prep>] + [(pattern (<pm> idx)) (///////phase#in (_.let (list [@temp (|> idx <prep> .int _.int (//runtime.sum//get ..peek (_.bool <flag>)))]) (_.if (_.null?/1 @temp) ..fail! @@ -182,23 +183,23 @@ ([/////synthesis.side/left false (<|)] [/////synthesis.side/right true ++]) - (^ (/////synthesis.member/left 0)) + (pattern (/////synthesis.member/left 0)) (///////phase#in (..push_cursor! (_.vector_ref/2 ..peek (_.int +0)))) - (^template [<pm> <getter>] - [(^ (<pm> lefts)) + (^.template [<pm> <getter>] + [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push_cursor!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (^ (/////synthesis.path/seq leftP rightP)) + (pattern (/////synthesis.path/seq leftP rightP)) (do ///////phase.monad [leftO (again leftP) rightO (again rightP)] (in (_.begin (list leftO rightO)))) - (^ (/////synthesis.path/alt leftP rightP)) + (pattern (/////synthesis.path/alt leftP rightP)) (do [! ///////phase.monad] [leftO (again leftP) rightO (again rightP)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux index 77eb47de5..b588619b7 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux @@ -1,32 +1,32 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - ["ex" exception {"+" exception:}] - [parser - ["<[0]>" code]]] - [data - ["[0]" product] - ["[0]" text] - [number {"+" hex} - ["f" frac]] - [collection - ["[0]" list ("[1]#[0]" functor)] - ["dict" dictionary {"+" Dictionary}]]] - ["[0]" macro {"+" with_symbols} - ["[0]" code] - [syntax {"+" syntax:}]] - [target - ["_" scheme {"+" Expression Computation}]]]] - ["[0]" /// "_" - ["[1][0]" runtime {"+" Operation Phase Handler Bundle}] - ["[1]//" /// - ["[1][0]" extension - ["[0]" bundle]] - ["[1]/" // "_" - ["[1][0]" synthesis {"+" Synthesis}]]]]) + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + ["ex" exception {"+" exception:}] + [parser + ["<[0]>" code]]] + [data + ["[0]" product] + ["[0]" text] + [number {"+" hex} + ["f" frac]] + [collection + ["[0]" list ("[1]#[0]" functor)] + ["dict" dictionary {"+" Dictionary}]]] + ["[0]" macro {"+" with_symbols} + ["[0]" code] + [syntax {"+" syntax:}]] + [target + ["_" scheme {"+" Expression Computation}]]]] + ["[0]" /// "_" + ["[1][0]" runtime {"+" Operation Phase Handler Bundle}] + ["[1]//" /// + ["[1][0]" extension + ["[0]" bundle]] + ["[1]/" // "_" + ["[1][0]" synthesis {"+" Synthesis}]]]]) (syntax: (Vector [size <code>.nat elemT <code>.any]) @@ -48,7 +48,7 @@ Handler) (function ((~ g!_) (~ g!name) (~ g!phase) (~ g!inputs)) (case (~ g!inputs) - (^ (list (~+ g!input+))) + (pattern (list (~+ g!input+))) (do /////.monad [(~+ (|> g!input+ (list#each (function (_ g!input) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux index 274c4d0ad..38fc993d0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux @@ -9,7 +9,9 @@ [data [collection ["[0]" list ("[1]#[0]" functor)] - ["[0]" dictionary {"+" Dictionary}]]]]] + ["[0]" dictionary {"+" Dictionary}]]] + [macro + ["^" pattern]]]] ["[0]" / "_" ["[1][0]" function] ["[1][0]" case] @@ -33,14 +35,14 @@ {///simple.#Unit} {/simple.#Text /.unit} - (^template [<analysis> <synthesis>] + (^.template [<analysis> <synthesis>] [{<analysis> value} {<synthesis> value}]) ([///simple.#Bit /simple.#Bit] [///simple.#Frac /simple.#F64] [///simple.#Text /simple.#Text]) - (^template [<analysis> <synthesis>] + (^.template [<analysis> <synthesis>] [{<analysis> value} {<synthesis> (.i64 value)}]) ([///simple.#Nat /simple.#I64] @@ -74,7 +76,7 @@ (/.with_currying? false (/case.synthesize optimization branchesAB+ archive inputA)) - (^ (///analysis.no_op value)) + (pattern (///analysis.no_op value)) (optimization' value) {///analysis.#Apply _} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux index a9fa9c013..d21a2a13e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux @@ -13,6 +13,8 @@ [collection ["[0]" list ("[1]#[0]" functor mix monoid)] ["[0]" set {"+" Set}]]] + [macro + ["^" pattern]] [math [number ["n" nat] @@ -52,7 +54,7 @@ {/.#Bit_Fork when then {.#None}}) thenC) - (^template [<from> <to> <conversion>] + (^.template [<from> <to> <conversion>] [{<from> test} (///#each (function (_ then) {<to> [(<conversion> test) then] (list)}) @@ -150,8 +152,8 @@ [{.#None} {.#None}] {.#None} - (^or [{.#Some woven_then} {.#None}] - [{.#None} {.#Some woven_then}]) + (^.or [{.#Some woven_then} {.#None}] + [{.#None} {.#Some woven_then}]) {.#Some woven_then} [{.#Some new_else} {.#Some old_else}] @@ -170,14 +172,14 @@ {.#Some old_else} (weave new_then old_else))}}) - (^template [<tag> <equivalence>] + (^.template [<tag> <equivalence>] [[{<tag> new_fork} {<tag> old_fork}] {<tag> (..weave_fork weave <equivalence> new_fork old_fork)}]) ([/.#I64_Fork i64.equivalence] [/.#F64_Fork frac.equivalence] [/.#Text_Fork text.equivalence]) - (^template [<access> <side> <lefts> <right?>] + (^.template [<access> <side> <lefts> <right?>] [[{/.#Access {<access> [<lefts> newL <right?> <side>]}} {/.#Access {<access> [<lefts> oldL <right?> <side>]}}] (if (n.= newL oldL) @@ -285,7 +287,7 @@ path (case input - (^ (/.branch/get [sub_path sub_input])) + (pattern (/.branch/get [sub_path sub_input])) (///#in (/.branch/get [(list#composite path sub_path) sub_input])) _ @@ -296,15 +298,15 @@ (do [! ///.monad] [inputS (synthesize^ archive inputA)] (case [headB tailB+] - (^ (!masking @variable @output)) + (pattern (!masking @variable @output)) (..synthesize_masking synthesize^ archive inputS @variable @output) - (^ [[(///pattern.unit) body] - {.#End}]) + (pattern [[(///pattern.unit) body] + {.#End}]) (case inputA - (^or {///analysis.#Simple _} - {///analysis.#Structure _} - {///analysis.#Reference _}) + (^.or {///analysis.#Simple _} + {///analysis.#Structure _} + {///analysis.#Reference _}) (synthesize^ archive body) _ @@ -314,18 +316,18 @@ {.#End}] (..synthesize_let synthesize^ archive inputS @variable body) - (^or (^ [[(///pattern.bit #1) then] - (list [(///pattern.bit #0) else])]) - (^ [[(///pattern.bit #1) then] - (list [(///pattern.unit) else])]) - - (^ [[(///pattern.bit #0) else] - (list [(///pattern.bit #1) then])]) - (^ [[(///pattern.bit #0) else] - (list [(///pattern.unit) then])])) + (^.or (pattern [[(///pattern.bit #1) then] + (list [(///pattern.bit #0) else])]) + (pattern [[(///pattern.bit #1) then] + (list [(///pattern.unit) else])]) + + (pattern [[(///pattern.bit #0) else] + (list [(///pattern.bit #1) then])]) + (pattern [[(///pattern.bit #0) else] + (list [(///pattern.unit) then])])) (..synthesize_if synthesize^ archive inputS then else) - (^ (!get patterns @member)) + (pattern (!get patterns @member)) (..synthesize_get synthesize^ archive inputS patterns @member) match @@ -334,7 +336,7 @@ (def: .public (count_pops path) (-> Path [Nat Path]) (case path - (^ (/.path/seq {/.#Pop} path')) + (pattern (/.path/seq {/.#Pop} path')) (let [[pops post_pops] (count_pops path')] [(++ pops) post_pops]) @@ -366,11 +368,11 @@ [path path path_storage ..empty] (case path - (^or {/.#Pop} - {/.#Access Access}) + (^.or {/.#Pop} + {/.#Access Access}) path_storage - (^ (/.path/bind register)) + (pattern (/.path/bind register)) (revised #bindings (set.has register) path_storage) @@ -383,30 +385,30 @@ (for_path otherwise path_storage)) (for_path default)) - (^or {/.#I64_Fork forks} - {/.#F64_Fork forks} - {/.#Text_Fork forks}) + (^.or {/.#I64_Fork forks} + {/.#F64_Fork forks} + {/.#Text_Fork forks}) (|> {.#Item forks} (list#each product.right) (list#mix for_path path_storage)) - (^or (^ (/.path/seq left right)) - (^ (/.path/alt left right))) + (^.or (pattern (/.path/seq left right)) + (pattern (/.path/alt left right))) (list#mix for_path path_storage (list left right)) - (^ (/.path/then bodyS)) + (pattern (/.path/then bodyS)) (loop for_synthesis [bodyS bodyS synthesis_storage path_storage] (case bodyS - (^or {/.#Simple _} - (^ (/.constant _))) + (^.or {/.#Simple _} + (pattern (/.constant _))) synthesis_storage - (^ (/.variant [lefts right? valueS])) + (pattern (/.variant [lefts right? valueS])) (for_synthesis valueS synthesis_storage) - (^ (/.tuple members)) + (pattern (/.tuple members)) (list#mix for_synthesis synthesis_storage members) {/.#Reference {///reference.#Variable {///reference/variable.#Local register}}} @@ -417,21 +419,21 @@ {/.#Reference {///reference.#Variable var}} (revised #dependencies (set.has var) synthesis_storage) - (^ (/.function/apply [functionS argsS])) + (pattern (/.function/apply [functionS argsS])) (list#mix for_synthesis synthesis_storage {.#Item functionS argsS}) - (^ (/.function/abstraction [environment arity bodyS])) + (pattern (/.function/abstraction [environment arity bodyS])) (list#mix for_synthesis synthesis_storage environment) - (^ (/.branch/case [inputS pathS])) + (pattern (/.branch/case [inputS pathS])) (revised #dependencies (set.union (the #dependencies (for_path pathS synthesis_storage))) (for_synthesis inputS synthesis_storage)) - (^ (/.branch/exec [before after])) + (pattern (/.branch/exec [before after])) (list#mix for_synthesis synthesis_storage (list before after)) - (^ (/.branch/let [inputS register exprS])) + (pattern (/.branch/let [inputS register exprS])) (revised #dependencies (set.union (|> synthesis_storage (revised #bindings (set.has register)) @@ -439,13 +441,13 @@ (the #dependencies))) (for_synthesis inputS synthesis_storage)) - (^ (/.branch/if [testS thenS elseS])) + (pattern (/.branch/if [testS thenS elseS])) (list#mix for_synthesis synthesis_storage (list testS thenS elseS)) - (^ (/.branch/get [access whole])) + (pattern (/.branch/get [access whole])) (for_synthesis whole synthesis_storage) - (^ (/.loop/scope [start initsS+ iterationS])) + (pattern (/.loop/scope [start initsS+ iterationS])) (revised #dependencies (set.union (|> synthesis_storage (revised #bindings (set.union (|> initsS+ @@ -456,7 +458,7 @@ (the #dependencies))) (list#mix for_synthesis synthesis_storage initsS+)) - (^ (/.loop/again replacementsS+)) + (pattern (/.loop/again replacementsS+)) (list#mix for_synthesis synthesis_storage replacementsS+) {/.#Extension [extension argsS]} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux index e9ec84dca..164261eb6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux @@ -13,6 +13,8 @@ ["%" format {"+" format}]] [collection ["[0]" list ("[1]#[0]" functor monoid)]]] + [macro + ["^" pattern]] [math [number ["n" nat]]]]] @@ -56,7 +58,7 @@ argsS (monad.each ! (phase archive) argsA)] (with_expansions [<apply> (as_is (/.function/apply [funcS argsS]))] (case funcS - (^ (/.function/abstraction functionS)) + (pattern (/.function/abstraction functionS)) (if (n.= (the /.#arity functionS) (list.size argsS)) (do ! @@ -66,7 +68,7 @@ (maybe#each (: (-> [Nat (List Synthesis) Synthesis] Synthesis) (function (_ [start inits iteration]) (case iteration - (^ (/.loop/scope [start' inits' output])) + (pattern (/.loop/scope [start' inits' output])) (if (and (n.= start start') (list.empty? inits')) (/.loop/scope [start inits output]) @@ -77,7 +79,7 @@ (maybe.else <apply>)))) (in <apply>)) - (^ (/.function/apply [funcS' argsS'])) + (pattern (/.function/apply [funcS' argsS'])) (in (/.function/apply [funcS' (list#composite argsS' argsS)])) _ @@ -98,7 +100,7 @@ {/.#Bind register} (phase#in {/.#Bind (++ register)}) - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} (do phase.monad [left' (grow_path grow left) @@ -117,7 +119,7 @@ (in {.#None}))] (in {/.#Bit_Fork when then else})) - (^template [<tag>] + (^.template [<tag>] [{<tag> [[test then] elses]} (do [! phase.monad] [then (grow_path grow then) @@ -154,7 +156,7 @@ (monad.each phase.monad (grow environment)) (phase#each (|>> /.tuple)))) - (^ (..self_reference)) + (pattern (..self_reference)) (phase#in (/.function/apply [expression (list (/.variable/local 1))])) {/.#Reference reference} @@ -236,7 +238,7 @@ [funcS (grow environment funcS) argsS+ (monad.each ! (grow environment) argsS+)] (in (/.function/apply (case funcS - (^ (/.function/apply [(..self_reference) pre_argsS+])) + (pattern (/.function/apply [(..self_reference) pre_argsS+])) [(..self_reference) (list#composite pre_argsS+ argsS+)] @@ -261,7 +263,7 @@ (phase archive bodyA))) abstraction (: (Operation Abstraction) (case bodyS - (^ (/.function/abstraction [env' down_arity' bodyS'])) + (pattern (/.function/abstraction [env' down_arity' bodyS'])) (|> bodyS' (grow env') (# ! each (function (_ body) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux index f3d6b8b68..2121e37b9 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux @@ -8,6 +8,8 @@ [data [collection ["[0]" list]]] + [macro + ["^" pattern]] [math [number ["n" nat]]]]] @@ -34,7 +36,7 @@ {/.#Bind register} {.#Some {/.#Bind (register_optimization offset register)}} - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} (do maybe.monad [left' (again left) @@ -53,7 +55,7 @@ (in {.#None}))] (in {/.#Bit_Fork when then else})) - (^template [<tag>] + (^.template [<tag>] [{<tag> [[test then] elses]} (do [! maybe.monad] [then (again then) @@ -99,53 +101,53 @@ {/.#Reference reference} (case reference - (^ {reference.#Variable (variable.self)}) + (pattern {reference.#Variable (variable.self)}) (if true_loop? {.#None} {.#Some expr}) - (^ (reference.constant constant)) + (pattern (reference.constant constant)) {.#Some expr} - (^ (reference.local register)) + (pattern (reference.local register)) {.#Some {/.#Reference (reference.local (register_optimization offset register))}} - (^ (reference.foreign register)) + (pattern (reference.foreign register)) (if true_loop? (list.item register scope_environment) {.#Some expr})) - (^ (/.branch/case [input path])) + (pattern (/.branch/case [input path])) (do maybe.monad [input' (again false input) path' (path_optimization (again return?) offset path)] (in (|> path' [input'] /.branch/case))) - (^ (/.branch/exec [this that])) + (pattern (/.branch/exec [this that])) (do maybe.monad [this (again false this) that (again return? that)] (in (/.branch/exec [this that]))) - (^ (/.branch/let [input register body])) + (pattern (/.branch/let [input register body])) (do maybe.monad [input' (again false input) body' (again return? body)] (in (/.branch/let [input' (register_optimization offset register) body']))) - (^ (/.branch/if [input then else])) + (pattern (/.branch/if [input then else])) (do maybe.monad [input' (again false input) then' (again return? then) else' (again return? else)] (in (/.branch/if [input' then' else']))) - (^ (/.branch/get [path record])) + (pattern (/.branch/get [path record])) (do maybe.monad [record (again false record)] (in (/.branch/get [path record]))) - (^ (/.loop/scope scope)) + (pattern (/.loop/scope scope)) (do [! maybe.monad] [inits' (|> scope (the /.#inits) @@ -155,24 +157,24 @@ /.#inits inits' /.#iteration iteration']))) - (^ (/.loop/again args)) + (pattern (/.loop/again args)) (|> args (monad.each maybe.monad (again false)) (maybe#each (|>> /.loop/again))) - (^ (/.function/abstraction [environment arity body])) + (pattern (/.function/abstraction [environment arity body])) (do [! maybe.monad] [environment' (monad.each ! (again false) environment)] (in (/.function/abstraction [environment' arity body]))) - (^ (/.function/apply [abstraction arguments])) + (pattern (/.function/apply [abstraction arguments])) (do [! maybe.monad] [arguments' (monad.each ! (again false) arguments)] (with_expansions [<application> (as_is (do ! [abstraction' (again false abstraction)] (in (/.function/apply [abstraction' arguments']))))] (case abstraction - (^ {/.#Reference {reference.#Variable (variable.self)}}) + (pattern {/.#Reference {reference.#Variable (variable.self)}}) (if (and return? (n.= arity (list.size arguments))) (in (/.loop/again arguments')) @@ -184,14 +186,14 @@ <application>))) ... TODO: Stop relying on this custom code. - (^ {/.#Extension ["lux syntax char case!" (list& input else matches)]}) + (pattern {/.#Extension ["lux syntax char case!" (list& input else matches)]}) (if return? (do [! maybe.monad] [input (again false input) matches (monad.each ! (function (_ match) (case match - (^ {/.#Structure {analysis/complex.#Tuple (list when then)}}) + (pattern {/.#Structure {analysis/complex.#Tuple (list when then)}}) (do ! [when (again false when) then (again return? then)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux index 74abfe432..3d795ff2f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux @@ -15,6 +15,8 @@ ["[0]" dictionary {"+" Dictionary}] ["[0]" list ("[1]#[0]" functor mix)] ["[0]" set]]] + [macro + ["^" pattern]] [math [number ["n" nat]]]]] @@ -50,14 +52,14 @@ register)} (again post)}) - (^or {/.#Seq {/.#Access {/access.#Member member}} - {/.#Seq {/.#Bind register} - post}} - ... This alternative form should never occur in practice. - ... Yet, it is "technically" possible to construct it. - {/.#Seq {/.#Seq {/.#Access {/access.#Member member}} - {/.#Bind register}} - post}) + (^.or {/.#Seq {/.#Access {/access.#Member member}} + {/.#Seq {/.#Bind register} + post}} + ... This alternative form should never occur in practice. + ... Yet, it is "technically" possible to construct it. + {/.#Seq {/.#Seq {/.#Access {/access.#Member member}} + {/.#Bind register}} + post}) (if (n.= redundant register) (again post) {/.#Seq {/.#Access {/access.#Member member}} @@ -66,7 +68,7 @@ register)} (again post)}}) - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} {<tag> (again left) (again right)}]) ([/.#Seq] @@ -75,7 +77,7 @@ {/.#Bit_Fork when then else} {/.#Bit_Fork when (again then) (maybe#each again else)} - (^template [<tag>] + (^.template [<tag>] [{<tag> [[test then] tail]} {<tag> [[test (again then)] (list#each (function (_ [test' then']) @@ -85,8 +87,8 @@ [/.#F64_Fork] [/.#Text_Fork]) - (^or {/.#Pop} - {/.#Access _}) + (^.or {/.#Pop} + {/.#Access _}) path {/.#Bind register} @@ -253,8 +255,8 @@ (-> (Optimization Synthesis) (Optimization Path)) (function (again [redundancy path]) (case path - (^or {/.#Pop} - {/.#Access _}) + (^.or {/.#Pop} + {/.#Access _}) {try.#Success [redundancy path]} @@ -272,7 +274,7 @@ (in [redundancy {.#None}]))] (in [redundancy {/.#Bit_Fork when then else}])) - (^template [<tag> <type>] + (^.template [<tag> <type>] [{<tag> [[test then] elses]} (do [! try.monad] [[redundancy then] (again [redundancy then]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux index b4e9e5b28..3fd47f828 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux @@ -17,6 +17,8 @@ [collection ["[0]" list ("[1]#[0]" functor)] ["[0]" dictionary {"+" Dictionary}]]] + [macro + ["^" pattern]] [math [number ["[0]" i64] @@ -287,7 +289,7 @@ "") ")") - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> item} (|> {.#Item item} (list#each (function (_ [test then]) @@ -420,7 +422,7 @@ (= reference_then sample_then) (# (maybe.equivalence =) = reference_else sample_else)) - (^template [<tag> <equivalence>] + (^.template [<tag> <equivalence>] [[{<tag> reference_item} {<tag> sample_item}] (# (list.equivalence (product.equivalence <equivalence> =)) = @@ -430,7 +432,7 @@ [#F64_Fork f.equivalence] [#Text_Fork text.equivalence]) - (^template [<tag> <equivalence>] + (^.template [<tag> <equivalence>] [[{<tag> reference'} {<tag> sample'}] (# <equivalence> = reference' sample')]) ([#Access /access.equivalence] @@ -439,7 +441,7 @@ [{#Bind reference'} {#Bind sample'}] (n.= reference' sample') - (^template [<tag>] + (^.template [<tag>] [[{<tag> leftR rightR} {<tag> leftS rightS}] (and (= leftR leftS) (= rightR rightS))]) @@ -472,7 +474,7 @@ (hash then) (# (maybe.hash (path'_hash super)) hash else)) - (^template [<factor> <tag> <hash>] + (^.template [<factor> <tag> <hash>] [{<tag> item} (let [case_hash (product.hash <hash> (path'_hash super)) @@ -482,7 +484,7 @@ [13 #F64_Fork f.hash] [17 #Text_Fork text.hash]) - (^template [<factor> <tag>] + (^.template [<factor> <tag>] [{<tag> fork} (let [again_hash (path'_hash super) fork_hash (product.hash again_hash again_hash)] @@ -494,7 +496,7 @@ (n.* 29 (# super hash body)) ))) -(implementation: (branch_equivalence (^open "#[0]")) +(implementation: (branch_equivalence (open "#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (Branch a)))) (def: (= reference sample) @@ -560,7 +562,7 @@ (# (..path'_hash super) hash path)) ))) -(implementation: (loop_equivalence (^open "/#[0]")) +(implementation: (loop_equivalence (open "/#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (Loop a)))) (def: (= reference sample) @@ -596,7 +598,7 @@ (# (list.hash super) hash resets)) ))) -(implementation: (function_equivalence (^open "#[0]")) +(implementation: (function_equivalence (open "#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (Function a)))) (def: (= reference sample) @@ -635,12 +637,12 @@ (# (list.hash super) hash arguments)) ))) -(implementation: (control_equivalence (^open "#[0]")) +(implementation: (control_equivalence (open "#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (Control a)))) (def: (= reference sample) (case [reference sample] - (^template [<tag> <equivalence>] + (^.template [<tag> <equivalence>] [[{<tag> reference} {<tag> sample}] (# (<equivalence> #=) = reference sample)]) ([#Branch ..branch_equivalence] @@ -658,7 +660,7 @@ (def: (hash value) (case value - (^template [<factor> <tag> <hash>] + (^.template [<factor> <tag> <hash>] [{<tag> value} (n.* <factor> (# (<hash> super) hash value))]) ([2 #Branch ..branch_hash] @@ -671,7 +673,7 @@ (def: (= reference sample) (case [reference sample] - (^template [<tag> <equivalence>] + (^.template [<tag> <equivalence>] [[{<tag> reference'} {<tag> sample'}] (# <equivalence> = reference' sample')]) ([#Simple /simple.equivalence] @@ -695,7 +697,7 @@ (def: (hash value) (let [again_hash [..equivalence hash]] (case value - (^template [<tag> <hash>] + (^.template [<tag> <hash>] [{<tag> value} (# <hash> hash value)]) ([#Simple /simple.hash] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/simple.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/simple.lux index 7d98c463a..05b5201f8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/simple.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/simple.lux @@ -10,6 +10,8 @@ ["[0]" bit ("[1]#[0]" equivalence)] ["[0]" text ("[1]#[0]" equivalence) ["%" format]]] + [macro + ["^" pattern]] [math [number ["[0]" i64 ("[1]#[0]" equivalence)] @@ -27,7 +29,7 @@ (def: .public (format it) (%.Format Simple) (case it - (^template [<pattern> <format>] + (^.template [<pattern> <format>] [{<pattern> value} (<format> value)]) ([#Bit %.bit] @@ -42,7 +44,7 @@ (def: (= reference sample) (case [reference sample] - (^template [<tag> <eq> <format>] + (^.template [<tag> <eq> <format>] [[{<tag> reference'} {<tag> sample'}] (<eq> reference' sample')]) ([#Bit bit#= %.bit] @@ -62,7 +64,7 @@ (def: hash (|>> (pipe.case - (^template [<factor> <tag> <hash>] + (^.template [<factor> <tag> <hash>] [{<tag> value'} (n.* <factor> (# <hash> hash value'))]) ([2 #Bit bit.hash] diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux index a63bde0a1..58bb26a18 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux @@ -88,7 +88,7 @@ (def: .public (id module archive) (-> descriptor.Module Archive (Try module.ID)) - (let [(^open "/[0]") (:representation archive)] + (let [(open "/[0]") (:representation archive)] (case (dictionary.value module /#resolver) {.#Some [id _]} {try.#Success id} @@ -99,7 +99,7 @@ (def: .public (reserve module archive) (-> descriptor.Module Archive (Try [module.ID Archive])) - (let [(^open "/[0]") (:representation archive)] + (let [(open "/[0]") (:representation archive)] (case (dictionary.value module /#resolver) {.#Some _} (exception.except ..module_has_already_been_reserved [module]) @@ -114,7 +114,7 @@ (def: .public (has module entry archive) (-> descriptor.Module (Entry Any) Archive (Try Archive)) - (let [(^open "/[0]") (:representation archive)] + (let [(open "/[0]") (:representation archive)] (case (dictionary.value module /#resolver) {.#Some [id {.#None}]} {try.#Success (|> archive @@ -142,7 +142,7 @@ (def: .public (find module archive) (-> descriptor.Module Archive (Try (Entry Any))) - (let [(^open "/[0]") (:representation archive)] + (let [(open "/[0]") (:representation archive)] (case (dictionary.value module /#resolver) {.#Some [id {.#Some entry}]} {try.#Success entry} @@ -174,7 +174,7 @@ (def: .public (reserved? archive module) (-> Archive descriptor.Module Bit) - (let [(^open "/[0]") (:representation archive)] + (let [(open "/[0]") (:representation archive)] (case (dictionary.value module /#resolver) {.#Some [id _]} true @@ -236,7 +236,7 @@ (def: .public (export version archive) (-> Version Archive Binary) - (let [(^open "/[0]") (:representation archive)] + (let [(open "/[0]") (:representation archive)] (|> /#resolver dictionary.entries (list.all (function (_ [module [id descriptor+document]]) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact/category.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact/category.lux index 61698487d..3f1bf2256 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact/category.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact/category.lux @@ -8,6 +8,8 @@ [data ["[0]" product] ["[0]" text ("[1]#[0]" equivalence)]] + [macro + ["^" pattern]] [math [number ["[0]" nat]]]]] @@ -49,7 +51,7 @@ [{#Definition left} {#Definition right}] (# definition_equivalence = left right) - (^template [<tag>] + (^.template [<tag>] [[{<tag> left} {<tag> right}] (text#= left right)]) ([#Analyser] diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/module/descriptor.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/module/descriptor.lux index cc8fbbf2b..e798429e1 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/module/descriptor.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/module/descriptor.lux @@ -13,6 +13,8 @@ ["[0]" set {"+" Set}]] ["[0]" format "_" ["[1]" binary {"+" Writer}]]] + [macro + ["^" pattern]] [math [number ["[0]" nat]]] @@ -39,7 +41,7 @@ (def: (= left right) (case [left right] - (^template [<tag>] + (^.template [<tag>] [[{<tag>} {<tag>}] true]) ([.#Active] 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 a1a201a79..8c11b0fca 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux @@ -20,6 +20,8 @@ ["[0]" dictionary {"+" Dictionary}]] [format ["[0]" binary {"+" Writer}]]] + [macro + ["^" pattern]] [type abstract]]] ["[0]" // "_" @@ -117,7 +119,7 @@ category (: (Writer Category) (function (_ value) (case value - (^template [<nat> <tag> <writer>] + (^.template [<nat> <tag> <writer>] [{<tag> value} ((binary.and binary.nat <writer>) [<nat> value])]) ([0 //category.#Anonymous binary.any] @@ -162,7 +164,7 @@ (do [! <>.monad] [tag <binary>.nat] (case tag - (^template [<nat> <tag> <parser>] + (^.template [<nat> <tag> <parser>] [<nat> (# ! each (|>> {<tag>}) <parser>)]) ([0 //category.#Anonymous <binary>.any] @@ -186,7 +188,7 @@ {//category.#Anonymous} (..resource mandatory? dependencies registry) - (^template [<tag> <create>] + (^.template [<tag> <create>] [{<tag> name} (<create> name mandatory? dependencies registry)]) ([//category.#Definition ..definition] diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux index f1c4a4806..90085fc31 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux @@ -12,6 +12,8 @@ ["[0]" set {"+" Set}] ["[0]" dictionary {"+" Dictionary}] ["[0]" sequence]]] + [macro + ["^" pattern]] [math [number ["[0]" nat]]] @@ -38,12 +40,12 @@ (-> Path (List Constant))) (function (again path) (case path - (^or {synthesis.#Pop} - {synthesis.#Access _} - {synthesis.#Bind _}) + (^.or {synthesis.#Pop} + {synthesis.#Access _} + {synthesis.#Bind _}) (list) - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} ($_ list#composite (again left) @@ -61,7 +63,7 @@ {.#None} (again then)) - (^template [<tag>] + (^.template [<tag>] [{<tag> fork} (|> {.#Item fork} (list#each (|>> product.right again)) diff --git a/stdlib/source/library/lux/tool/compiler/meta/cli.lux b/stdlib/source/library/lux/tool/compiler/meta/cli.lux index ba6bb8706..bbc2735e7 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cli.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cli.lux @@ -15,6 +15,8 @@ ["%" format]] [collection ["[0]" list ("[1]#[0]" functor)]]] + [macro + ["^" pattern]] [math [number {"+" hex}]] [meta @@ -107,7 +109,7 @@ (def: .public target (-> Service Target) (|>> (pipe.case - (^or {#Compilation [host_dependencies libraries compilers sources target module]} - {#Interpretation [host_dependencies libraries compilers sources target module]} - {#Export [sources target]}) + (^.or {#Compilation [host_dependencies libraries compilers sources target module]} + {#Interpretation [host_dependencies libraries compilers sources target module]} + {#Export [sources target]}) target))) diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux index f4125ab61..95d9a5e1a 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux @@ -20,6 +20,8 @@ ["[0]" list ("[1]#[0]" mix)] ["[0]" dictionary {"+" Dictionary}] ["[0]" sequence {"+" Sequence}]]] + [macro + ["^" pattern]] [meta ["[0]" configuration {"+" Configuration}] ["[0]" version]] @@ -219,7 +221,7 @@ content (document.content $.key document) definitions (monad.each ! (function (_ [def_name def_global]) (case def_global - (^template [<tag>] + (^.template [<tag>] [{<tag> payload} (in [def_name {<tag> payload}])]) ([.#Alias] diff --git a/stdlib/source/library/lux/tool/compiler/reference.lux b/stdlib/source/library/lux/tool/compiler/reference.lux index 7dff736ed..3e962f14f 100644 --- a/stdlib/source/library/lux/tool/compiler/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/reference.lux @@ -9,6 +9,8 @@ [data [text ["%" format {"+" Format}]]] + [macro + ["^" pattern]] [math [number ["n" nat]]] @@ -30,7 +32,7 @@ (def: (= reference sample) (case [reference sample] - (^template [<tag> <equivalence>] + (^.template [<tag> <equivalence>] [[{<tag> reference} {<tag> sample}] (# <equivalence> = reference sample)]) ([#Variable /variable.equivalence] @@ -47,7 +49,7 @@ (def: (hash value) (case value - (^template [<factor> <tag> <hash>] + (^.template [<factor> <tag> <hash>] [{<tag> value} (|> value (# <hash> hash) diff --git a/stdlib/source/library/lux/tool/compiler/reference/variable.lux b/stdlib/source/library/lux/tool/compiler/reference/variable.lux index 0614c5b30..a9d4f432e 100644 --- a/stdlib/source/library/lux/tool/compiler/reference/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/reference/variable.lux @@ -9,6 +9,8 @@ [data [text ["%" format {"+" Format}]]] + [macro + ["^" pattern]] [math [number ["n" nat] @@ -27,7 +29,7 @@ (def: (= reference sample) (case [reference sample] - (^template [<tag>] + (^.template [<tag>] [[{<tag> reference'} {<tag> sample'}] (n.= reference' sample')]) ([#Local] [#Foreign]) @@ -43,7 +45,7 @@ (def: hash (|>> (pipe.case - (^template [<factor> <tag>] + (^.template [<factor> <tag>] [{<tag> register} (|> register (# n.hash hash) @@ -57,7 +59,7 @@ (def: .public self? (-> Variable Bit) (|>> (pipe.case - (^ (..self)) + (pattern (..self)) true _ diff --git a/stdlib/source/library/lux/type.lux b/stdlib/source/library/lux/type.lux index e0b7a4f0e..55fa0b166 100644 --- a/stdlib/source/library/lux/type.lux +++ b/stdlib/source/library/lux/type.lux @@ -19,6 +19,7 @@ ["[0]" list ("[1]#[0]" functor monoid mix)]]] ["[0]" macro [syntax {"+" syntax:}] + ["^" pattern] ["[0]" code]] [math [number @@ -89,7 +90,7 @@ (list#mix (function.flipped text#composite) "")) ")") - (^template [<tag> <open> <close> <flat>] + (^.template [<tag> <open> <close> <flat>] [{<tag> _} ($_ text#composite <open> (|> (<flat> type) @@ -124,7 +125,7 @@ (let [[type_func type_args] (flat_application type)] ($_ text#composite "(" (format type_func) " " (|> type_args (list#each format) list.reversed (list.interposed " ") (list#mix text#composite "")) ")")) - (^template [<tag> <desc>] + (^.template [<tag> <desc>] [{<tag> env body} ($_ text#composite "(" <desc> " {" (|> env (list#each format) (text.interposed " ")) "} " (format body) ")")]) ([.#UnivQ "All"] @@ -141,13 +142,13 @@ {.#Primitive name params} {.#Primitive name (list#each (reduced env) params)} - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} {<tag> (reduced env left) (reduced env right)}]) ([.#Sum] [.#Product] [.#Function] [.#Apply]) - (^template [<tag>] + (^.template [<tag>] [{<tag> old_env def} (case old_env {.#End} @@ -191,13 +192,13 @@ #1 (list.zipped/2 xparams yparams))) - (^template [<tag>] + (^.template [<tag>] [[{<tag> xid} {<tag> yid}] (n.= yid xid)]) ([.#Var] [.#Ex] [.#Parameter]) - (^or [{.#Function xleft xright} {.#Function yleft yright}] - [{.#Apply xleft xright} {.#Apply yleft yright}]) + (^.or [{.#Function xleft xright} {.#Function yleft yright}] + [{.#Apply xleft xright} {.#Apply yleft yright}]) (and (= xleft yleft) (= xright yright)) @@ -205,13 +206,13 @@ (and (symbol#= xname yname) (= xtype ytype)) - (^template [<tag>] + (^.template [<tag>] [[{<tag> xL xR} {<tag> yL yR}] (and (= xL yL) (= xR yR))]) ([.#Sum] [.#Product]) - (^or [{.#UnivQ xenv xbody} {.#UnivQ yenv ybody}] - [{.#ExQ xenv xbody} {.#ExQ yenv ybody}]) + (^.or [{.#UnivQ xenv xbody} {.#UnivQ yenv ybody}] + [{.#ExQ xenv xbody} {.#ExQ yenv ybody}]) (and (n.= (list.size yenv) (list.size xenv)) (= xbody ybody) (list#mix (.function (_ [x y] prev) (and prev (= x y))) @@ -230,7 +231,7 @@ {.#Item param params'} (case func - (^template [<tag>] + (^.template [<tag>] [{<tag> env body} (|> body (reduced (list& func param env)) @@ -253,12 +254,12 @@ (` {.#Primitive (~ (code.text name)) (.list (~+ (list#each code params)))}) - (^template [<tag>] + (^.template [<tag>] [{<tag> idx} (` {<tag> (~ (code.nat idx))})]) ([.#Var] [.#Ex] [.#Parameter]) - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} (` {<tag> (~ (code left)) (~ (code right))})]) @@ -267,7 +268,7 @@ {.#Named name sub_type} (code.symbol name) - (^template [<tag>] + (^.template [<tag>] [{<tag> env body} (` {<tag> (.list (~+ (list#each code env))) (~ (code body))})]) @@ -349,7 +350,7 @@ (# maybe.monad each quantified?) (maybe.else #0)) - (^or {.#UnivQ _} {.#ExQ _}) + (^.or {.#UnivQ _} {.#ExQ _}) #1 _ @@ -367,8 +368,8 @@ (def: .public (flat_array type) (-> Type [Nat Type]) (case type - (^multi (^ {.#Primitive name (list element_type)}) - (text#= array.type_name name)) + (^.multi (pattern {.#Primitive name (list element_type)}) + (text#= array.type_name name)) (let [[depth element_type] (flat_array element_type)] [(++ depth) element_type]) @@ -477,7 +478,7 @@ {.#Primitive name co_variant} {.#Primitive name (list#each again co_variant)} - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} {<tag> (again left) (again right)}]) ([.#Sum] @@ -485,14 +486,14 @@ [.#Function] [.#Apply]) - (^template [<tag>] + (^.template [<tag>] [{<tag> env body} {<tag> (list#each again env) (again body)}]) ([.#UnivQ] [.#ExQ]) - (^or {.#Parameter _} - {.#Var _} - {.#Ex _} - {.#Named _}) + (^.or {.#Parameter _} + {.#Var _} + {.#Ex _} + {.#Named _}) it)))) diff --git a/stdlib/source/library/lux/type/abstract.lux b/stdlib/source/library/lux/type/abstract.lux index 77ca88bee..7f5f73fee 100644 --- a/stdlib/source/library/lux/type/abstract.lux +++ b/stdlib/source/library/lux/type/abstract.lux @@ -13,6 +13,7 @@ [collection ["[0]" list ("[1]#[0]" functor monoid)]]] [macro + ["^" pattern] ["[0]" code] [syntax {"+" syntax:} ["|[0]|" export]]] @@ -64,10 +65,10 @@ {.#Definition [exported? frame_type frame_value]} (:as (Stack Frame) frame_value) - (^or {.#Type _} - {.#Alias _} - {.#Tag _} - {.#Slot _}) + (^.or {.#Type _} + {.#Alias _} + {.#Tag _} + {.#Slot _}) (undefined)))) (def: (peek_frames reference definition_reference source) @@ -126,10 +127,10 @@ frames_type (..push frame (:as (Stack Frame) frames_value))]} - (^or {.#Type _} - {.#Alias _} - {.#Tag _} - {.#Slot _}) + (^.or {.#Type _} + {.#Alias _} + {.#Tag _} + {.#Slot _}) (undefined)))) (def: (push_frame [module_reference definition_reference] frame source) @@ -160,10 +161,10 @@ {.#None} current_frames))]} - (^or {.#Type _} - {.#Alias _} - {.#Tag _} - {.#Slot _}) + (^.or {.#Type _} + {.#Alias _} + {.#Tag _} + {.#Slot _}) (undefined)))) (def: (pop_frame [module_reference definition_reference] source) diff --git a/stdlib/source/library/lux/type/check.lux b/stdlib/source/library/lux/type/check.lux index 757eac347..02dd48227 100644 --- a/stdlib/source/library/lux/type/check.lux +++ b/stdlib/source/library/lux/type/check.lux @@ -16,6 +16,8 @@ [collection ["[0]" list ("[1]#[0]" mix)] ["[0]" set {"+" Set}]]] + [macro + ["^" pattern]] [math [number ["n" nat ("[1]#[0]" decimal)]]]]] @@ -197,8 +199,8 @@ (-> Var (Check <outputT>)) (function (_ context) (case (|> context (the .#var_bindings) (var::get id)) - (^or {.#Some {.#Some {.#Var _}}} - {.#Some {.#None}}) + (^.or {.#Some {.#Some {.#Var _}}} + {.#Some {.#None}}) {try.#Success [context <fail>]} {.#Some {.#Some bound}} @@ -383,20 +385,20 @@ (do [! ..monad] [ring (..ring' @)] (case ring - (^ (list)) + (pattern (list)) (in []) - (^ (list @me)) + (pattern (list @me)) (erase! @me) - (^ (list @other @me)) + (pattern (list @other @me)) (do ! [_ (re_bind' {.#None} @other)] (erase! @me)) - (^ (list& @prev _)) + (pattern (list& @prev _)) (case (list.reversed ring) - (^ (list& @me @next _)) + (pattern (list& @me @next _)) (do ! [_ (re_bind {.#Var @next} @prev) _ (re_bind {.#Var @prev} @next)] @@ -525,7 +527,7 @@ (set.list ringA))] (in assumptions)))) - (^template [<pattern> <id> <type>] + (^.template [<pattern> <id> <type>] [<pattern> (do ! [ring (..ring <id>) @@ -572,7 +574,7 @@ [actual_function'' (..on actual_input' actual_function')] (check' assumptions {.#Apply expected} {.#Apply [actual_input actual_function'']})) - (^or [{.#Ex _} _] [_ {.#Ex _}]) + (^.or [{.#Ex _} _] [_ {.#Ex _}]) (do ..monad [assumptions (check' assumptions expected_function actual_function)] (check' assumptions expected_input actual_input)) @@ -659,7 +661,7 @@ (function (_ bound) (check' assumptions expected bound))) - (^template [<fE> <fA>] + (^.template [<fE> <fA>] [[{.#Apply aE <fE>} {.#Apply aA <fA>}] (check_apply check' assumptions [aE <fE>] [aA <fA>])]) ([F1 {.#Ex ex}] @@ -681,7 +683,7 @@ (check' assumptions expected actual')) ... TODO: Refactor-away as cold-code - (^template [<tag> <instancer>] + (^.template [<tag> <instancer>] [[{<tag> _} _] (do ..monad [[_ paramT] <instancer> @@ -691,7 +693,7 @@ [.#ExQ ..var]) ... TODO: Refactor-away as cold-code - (^template [<tag> <instancer>] + (^.template [<tag> <instancer>] [[_ {<tag> _}] (do ..monad [[_ paramT] <instancer> @@ -718,7 +720,7 @@ ..silent_failure!)) ..silent_failure!) - (^template [<composite>] + (^.template [<composite>] [[{<composite> eL eR} {<composite> aL aR}] (do ..monad [assumptions (check' assumptions eL aL)] @@ -777,10 +779,10 @@ (monad.each ..monad (clean aliases)) (check#each (|>> {.#Primitive name}))) - (^or {.#Parameter _} {.#Ex _} {.#Named _}) + (^.or {.#Parameter _} {.#Ex _} {.#Named _}) (check#in inputT) - (^template [<tag>] + (^.template [<tag>] [{<tag> leftT rightT} (do ..monad [leftT' (clean aliases leftT)] @@ -790,7 +792,7 @@ {.#Var @it} (case aliases - (^ (list)) + (pattern (list)) (do ..monad [?actualT (..peek @it)] (case ?actualT @@ -815,7 +817,7 @@ failure (in inputT)))) - (^template [<tag>] + (^.template [<tag>] [{<tag> envT+ unquantifiedT} (do [! ..monad] [envT+' (monad.each ! (clean aliases) envT+) diff --git a/stdlib/source/library/lux/type/poly.lux b/stdlib/source/library/lux/type/poly.lux index f2cecab1e..7f31f5187 100644 --- a/stdlib/source/library/lux/type/poly.lux +++ b/stdlib/source/library/lux/type/poly.lux @@ -17,8 +17,9 @@ ["[0]" list ("[1]#[0]" functor)] ["[0]" dictionary]]] [macro {"+" with_symbols} - ["[0]" code] - [syntax {"+" syntax:}]] + [syntax {"+" syntax:}] + ["^" pattern] + ["[0]" code]] [math [number ["n" nat]]]]]) @@ -55,7 +56,7 @@ (` {.#Primitive (~ (code.text name)) (.list (~+ (list#each (code env) params)))}) - (^template [<tag>] + (^.template [<tag>] [{<tag> idx} (` {<tag> (~ (code.nat idx))})]) ([.#Var] [.#Ex]) @@ -72,13 +73,13 @@ 0 (|> env (dictionary.value 0) maybe.trusted product.left (code env)) idx (undefined)) - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} (` {<tag> (~ (code env left)) (~ (code env right))})]) ([.#Function] [.#Apply]) - (^template [<macro> <tag> <flattener>] + (^.template [<macro> <tag> <flattener>] [{<tag> left right} (` (<macro> (~+ (list#each (code env) (<flattener> type)))))]) ([.Union .#Sum type.flat_variant] @@ -87,7 +88,7 @@ {.#Named name sub_type} (code.symbol name) - (^template [<tag>] + (^.template [<tag>] [{<tag> scope body} (` {<tag> (.list (~+ (list#each (code env) scope))) (~ (code env body))})]) diff --git a/stdlib/source/library/lux/type/refinement.lux b/stdlib/source/library/lux/type/refinement.lux index df4fc8d3c..304d7a07b 100644 --- a/stdlib/source/library/lux/type/refinement.lux +++ b/stdlib/source/library/lux/type/refinement.lux @@ -43,7 +43,7 @@ (-> (-> t t) (-> (Refined t %) (Maybe (Refined t %))))) (function (_ refined) - (let [(^open "_[0]") (:representation refined) + (let [(open "_[0]") (:representation refined) value' (transform _#value)] (if (_#predicate value') {.#Some (:abstraction [..#value value' diff --git a/stdlib/source/library/lux/type/unit.lux b/stdlib/source/library/lux/type/unit.lux index f2a361ebc..6da16af7e 100644 --- a/stdlib/source/library/lux/type/unit.lux +++ b/stdlib/source/library/lux/type/unit.lux @@ -1,30 +1,30 @@ (.using - [library - [lux "*" - ["[0]" meta] - [abstract - [monad {"+" Monad do}] - [equivalence {"+" Equivalence}] - [order {"+" Order}] - [enum {"+" Enum}]] - [control - ["<>" parser ("[1]#[0]" monad) - ["<[0]>" code {"+" Parser}]]] - [data - ["[0]" text - ["%" format {"+" format}]]] - [macro - ["[0]" code] - ["[0]" template] - [syntax {"+" syntax:} - ["|[0]|" export]]] - [math - [number - ["n" nat] - ["i" int] - ["[0]" ratio {"+" Ratio}]]] - [type - abstract]]]) + [library + [lux "*" + ["[0]" meta] + [abstract + [monad {"+" Monad do}] + [equivalence {"+" Equivalence}] + [order {"+" Order}] + [enum {"+" Enum}]] + [control + ["<>" parser ("[1]#[0]" monad) + ["<[0]>" code {"+" Parser}]]] + [data + ["[0]" text + ["%" format {"+" format}]]] + [macro + ["[0]" code] + ["[0]" template] + [syntax {"+" syntax:} + ["|[0]|" export]]] + [math + [number + ["n" nat] + ["i" int] + ["[0]" ratio {"+" Ratio}]]] + [type + abstract]]]) (abstract: .public (Qty unit) Int @@ -121,7 +121,7 @@ <code>.local_symbol ..scaleP))]) (do meta.monad - [.let [(^open "_[0]") ratio] + [.let [(open "_[0]") ratio] @ meta.current_module_name .let [g!scale (code.local_symbol type_name)]] (in (list (` (type: (~ export_policy) ((~ g!scale) (~' u)) diff --git a/stdlib/source/library/lux/world/net/http/request.lux b/stdlib/source/library/lux/world/net/http/request.lux index a7a29eaca..bea2b0ffc 100644 --- a/stdlib/source/library/lux/world/net/http/request.lux +++ b/stdlib/source/library/lux/world/net/http/request.lux @@ -22,6 +22,8 @@ [collection ["[0]" list ("[1]#[0]" functor mix)] ["[0]" dictionary]]] + [macro + ["^" pattern]] [world ["[0]" binary {"+" Binary}]]]] ["[0]" // {"+" Body Response Server} @@ -54,7 +56,7 @@ (def: .public (json reader server) (All (_ a) (-> (<json>.Reader a) (-> a Server) Server)) - (function (_ (^let request [identification protocol resource message])) + (function (_ (^.let request [identification protocol resource message])) (do async.monad [?raw (read_text_body (the //.#body message))] (case (do try.monad @@ -69,7 +71,7 @@ (def: .public (text server) (-> (-> Text Server) Server) - (function (_ (^let request [identification protocol resource message])) + (function (_ (^.let request [identification protocol resource message])) (do async.monad [?raw (read_text_body (the //.#body message))] (case ?raw @@ -99,7 +101,7 @@ (def: .public (form property server) (All (_ a) (-> (Property a) (-> a Server) Server)) - (function (_ (^let request [identification protocol resource message])) + (function (_ (^.let request [identification protocol resource message])) (do async.monad [?body (read_text_body (the //.#body message))] (case (do try.monad @@ -114,7 +116,7 @@ (def: .public (cookies property server) (All (_ a) (-> (Property a) (-> a Server) Server)) - (function (_ (^let request [identification protocol resource message])) + (function (_ (^.let request [identification protocol resource message])) (case (do try.monad [cookies (|> (the //.#headers message) (dictionary.value "Cookie") diff --git a/stdlib/source/library/lux/world/net/http/route.lux b/stdlib/source/library/lux/world/net/http/route.lux index e882c126c..c94dd8235 100644 --- a/stdlib/source/library/lux/world/net/http/route.lux +++ b/stdlib/source/library/lux/world/net/http/route.lux @@ -9,7 +9,9 @@ [data ["[0]" text] [number - ["n" nat]]]]] + ["n" nat]]] + [macro + ["^" pattern]]]] ["[0]" // {"+" URI Server} ["[1][0]" status] ["[1][0]" response]]) @@ -17,7 +19,7 @@ (template [<scheme> <name>] [(def: .public (<name> server) (-> Server Server) - (function (_ (^let request [identification protocol resource message])) + (function (_ (^.let request [identification protocol resource message])) (case (the //.#scheme protocol) {<scheme>} (server request) @@ -32,7 +34,7 @@ (template [<method> <name>] [(def: .public (<name> server) (-> Server Server) - (function (_ (^let request [identification protocol resource message])) + (function (_ (^.let request [identification protocol resource message])) (case (the //.#method resource) {<method>} (server request) diff --git a/stdlib/source/library/lux/world/shell.lux b/stdlib/source/library/lux/world/shell.lux index d77f1aa2f..c9092ae35 100644 --- a/stdlib/source/library/lux/world/shell.lux +++ b/stdlib/source/library/lux/world/shell.lux @@ -140,7 +140,7 @@ (Ex (_ ?) (-> (Sanitizer Command) (Sanitizer Argument) (Policy ?))) (?.with_policy (: (Context Safety Policy) - (function (_ (^open "?[0]")) + (function (_ (open "?[0]")) (implementation (def: command (|>> safe_command ?#can_upgrade)) (def: argument (|>> safe_argument ?#can_upgrade)) diff --git a/stdlib/source/program/aedifex.lux b/stdlib/source/program/aedifex.lux index a92340ce3..191a46ec5 100644 --- a/stdlib/source/program/aedifex.lux +++ b/stdlib/source/program/aedifex.lux @@ -83,7 +83,7 @@ profile) [exit_code output] ((command console program (file.async file.default) (shell.async shell.default) resolution) profile) _ (case exit_code - (^ (static shell.normal)) + (pattern (static shell.normal)) (in []) _ diff --git a/stdlib/source/program/aedifex/artifact/snapshot/stamp.lux b/stdlib/source/program/aedifex/artifact/snapshot/stamp.lux index d84234cb5..f17f27680 100644 --- a/stdlib/source/program/aedifex/artifact/snapshot/stamp.lux +++ b/stdlib/source/program/aedifex/artifact/snapshot/stamp.lux @@ -1,20 +1,20 @@ (.using - [library - [lux "*" - [abstract - [equivalence {"+" Equivalence}] - [monad {"+" do}]] - [control - ["<>" parser - ["<[0]>" xml {"+" Parser}] - ["<[0]>" text]]] - [data - ["[0]" product] - [format - ["[0]" xml {"+" XML}]]]]] - ["[0]" // "_" - ["[1][0]" time {"+" Time}] - ["[1][0]" build {"+" Build}]]) + [library + [lux "*" + [abstract + [equivalence {"+" Equivalence}] + [monad {"+" do}]] + [control + ["<>" parser + ["<[0]>" xml {"+" Parser}] + ["<[0]>" text]]] + [data + ["[0]" product] + [format + ["[0]" xml {"+" XML}]]]]] + ["[0]" // "_" + ["[1][0]" time {"+" Time}] + ["[1][0]" build {"+" Build}]]) (type: .public Stamp (Record @@ -39,7 +39,7 @@ list {xml.#Node ..<timestamp> xml.attributes})) -(def: .public (format (^open "_[0]")) +(def: .public (format (open "_[0]")) (-> Stamp (List XML)) (list (..time_format _#time) (//build.format _#build))) diff --git a/stdlib/source/program/aedifex/artifact/snapshot/version.lux b/stdlib/source/program/aedifex/artifact/snapshot/version.lux index d23e166c8..66923459c 100644 --- a/stdlib/source/program/aedifex/artifact/snapshot/version.lux +++ b/stdlib/source/program/aedifex/artifact/snapshot/version.lux @@ -1,21 +1,21 @@ (.using - [library - [lux {"-" Type} - [abstract - [equivalence {"+" Equivalence}] - [monad {"+" do}]] - [control - ["<>" parser - ["<[0]>" xml {"+" Parser}] - ["<[0]>" text]]] - [data - ["[0]" product] - ["[0]" text] - [format - ["[0]" xml {"+" XML}]]]]] - ["[0]" /// "_" - ["[1][0]" type {"+" Type}] - ["[1][0]" time {"+" Time}]]) + [library + [lux {"-" Type} + [abstract + [equivalence {"+" Equivalence}] + [monad {"+" do}]] + [control + ["<>" parser + ["<[0]>" xml {"+" Parser}] + ["<[0]>" text]]] + [data + ["[0]" product] + ["[0]" text] + [format + ["[0]" xml {"+" XML}]]]]] + ["[0]" /// "_" + ["[1][0]" type {"+" Type}] + ["[1][0]" time {"+" Time}]]) (type: .public Version (Record @@ -45,7 +45,7 @@ (-> xml.Tag Text XML) (|> value {xml.#Text} list {xml.#Node tag xml.attributes})) -(def: .public (format (^open "_[0]")) +(def: .public (format (open "_[0]")) (-> Version XML) (<| {xml.#Node ..<snapshot_version> xml.attributes} (list (..text_format ..<extension> _#extension) diff --git a/stdlib/source/program/aedifex/artifact/snapshot/version/value.lux b/stdlib/source/program/aedifex/artifact/snapshot/version/value.lux index f01c01522..65d30acdf 100644 --- a/stdlib/source/program/aedifex/artifact/snapshot/version/value.lux +++ b/stdlib/source/program/aedifex/artifact/snapshot/version/value.lux @@ -1,15 +1,15 @@ (.using - [library - [lux "*" - [abstract - [equivalence {"+" Equivalence}]] - [data - ["[0]" product] - ["[0]" text - ["%" format]]]]] - ["[0]" /// {"+" Snapshot} - ["[1][0]" time] - ["[1][0]" stamp]]) + [library + [lux "*" + [abstract + [equivalence {"+" Equivalence}]] + [data + ["[0]" product] + ["[0]" text + ["%" format]]]]] + ["[0]" /// {"+" Snapshot} + ["[1][0]" time] + ["[1][0]" stamp]]) (type: .public Value (Record @@ -29,14 +29,14 @@ (def: .public snapshot "SNAPSHOT") -(def: .public (format (^open "/[0]")) +(def: .public (format (open "/[0]")) (%.Format Value) (case /#snapshot {///.#Local} /#version {///.#Remote stamp} - (let [(^open "/[0]") stamp] + (let [(open "/[0]") stamp] (%.format (text.replaced ..snapshot (///time.format /#time) /#version) diff --git a/stdlib/source/program/aedifex/artifact/time/time.lux b/stdlib/source/program/aedifex/artifact/time/time.lux index ed66ebff2..15ce0e183 100644 --- a/stdlib/source/program/aedifex/artifact/time/time.lux +++ b/stdlib/source/program/aedifex/artifact/time/time.lux @@ -1,27 +1,27 @@ (.using - [library - [lux "*" - ["[0]" time] - [abstract - [monad {"+" do}]] - [control - ["<>" parser - ["<[0]>" text {"+" Parser}]]] - [data - [text - ["%" format]]] - [math - [number - ["n" nat]]]]] - ["[0]" // "_" - ["[1]" date]]) + [library + [lux "*" + ["[0]" time] + [abstract + [monad {"+" do}]] + [control + ["<>" parser + ["<[0]>" text {"+" Parser}]]] + [data + [text + ["%" format]]] + [math + [number + ["n" nat]]]]] + ["[0]" // "_" + ["[1]" date]]) (type: .public Time time.Time) (def: .public (format value) (%.Format Time) - (let [(^open "_[0]") (time.clock value)] + (let [(open "_[0]") (time.clock value)] (%.format (//.pad _#hour) (//.pad _#minute) (//.pad _#second)))) diff --git a/stdlib/source/program/aedifex/artifact/versioning.lux b/stdlib/source/program/aedifex/artifact/versioning.lux index 381087a49..377e33a67 100644 --- a/stdlib/source/program/aedifex/artifact/versioning.lux +++ b/stdlib/source/program/aedifex/artifact/versioning.lux @@ -1,33 +1,33 @@ (.using - [library - [lux "*" - [abstract - [equivalence {"+" Equivalence}] - [monad {"+" do}]] - [control - ["[0]" exception {"+" exception:}] - ["<>" parser - ["<[0]>" xml {"+" Parser}] - ["<[0]>" text]]] - [data - ["[0]" product] - ["[0]" text - ["%" format]] - [format - ["[0]" xml {"+" XML}]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [math - [number - ["n" nat]]] - ["[0]" time {"+" Time} - ["[0]" date {"+" Date}] - ["[0]" year] - ["[0]" month]]]] - ["[0]" // "_" - ["[1][0]" time] - ["[1][0]" snapshot {"+" Snapshot} - ["[1]/[0]" version {"+" Version}]]]) + [library + [lux "*" + [abstract + [equivalence {"+" Equivalence}] + [monad {"+" do}]] + [control + ["[0]" exception {"+" exception:}] + ["<>" parser + ["<[0]>" xml {"+" Parser}] + ["<[0]>" text]]] + [data + ["[0]" product] + ["[0]" text + ["%" format]] + [format + ["[0]" xml {"+" XML}]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [math + [number + ["n" nat]]] + ["[0]" time {"+" Time} + ["[0]" date {"+" Date}] + ["[0]" year] + ["[0]" month]]]] + ["[0]" // "_" + ["[1][0]" time] + ["[1][0]" snapshot {"+" Snapshot} + ["[1]/[0]" version {"+" Version}]]]) (type: .public Versioning (Record @@ -61,7 +61,7 @@ (-> //time.Time XML) (|>> //time.format {xml.#Text} list {xml.#Node ..<last_updated> xml.attributes})) -(def: .public (format (^open "_[0]")) +(def: .public (format (open "_[0]")) (-> Versioning XML) (<| {xml.#Node ..<versioning> xml.attributes} (list (//snapshot.format _#snapshot) diff --git a/stdlib/source/program/aedifex/command/build.lux b/stdlib/source/program/aedifex/command/build.lux index ecbcb703f..a8a5ffbc1 100644 --- a/stdlib/source/program/aedifex/command/build.lux +++ b/stdlib/source/program/aedifex/command/build.lux @@ -19,6 +19,8 @@ ["[0]" list ("[1]#[0]" functor mix)] ["[0]" dictionary {"+" Dictionary}] ["[0]" set]]] + [macro + ["^" pattern]] [math [number {"+" hex} ["n" nat] @@ -102,8 +104,8 @@ (case (..dependency_finder lux_group lux_name resolution) {.#Some dependency} (case lux_name - (^template [<tag> <name>] - [(^ (static <name>)) + (^.template [<tag> <name>] + [(pattern (static <name>)) {try.#Success [(..remove_dependency dependency resolution) {<tag> dependency}]}]) ([#JVM ..jvm_lux_name] @@ -293,7 +295,7 @@ (with_jvm_class_path {.#Item (..path fs home dependency) host_dependencies})) "program.jar"] - (^template [<tag> <runtime> <program>] + (^.template [<tag> <runtime> <program>] [{<tag> dependency} [(|> dependency (..path fs home) diff --git a/stdlib/source/program/aedifex/command/test.lux b/stdlib/source/program/aedifex/command/test.lux index 649201465..3df3e0724 100644 --- a/stdlib/source/program/aedifex/command/test.lux +++ b/stdlib/source/program/aedifex/command/test.lux @@ -6,6 +6,8 @@ [control [concurrency ["[0]" async {"+" Async} ("[1]#[0]" monad)]]] + [macro + ["^" pattern]] [math [number ["i" int]]] @@ -47,7 +49,7 @@ (///runtime.for (the ///.#java profile)) (//build.with_jvm_class_path host_dependencies)) - (^template [<tag> <runtime>] + (^.template [<tag> <runtime>] [{<tag> artifact} (///runtime.for (the <runtime> profile) program)]) diff --git a/stdlib/source/program/aedifex/hash.lux b/stdlib/source/program/aedifex/hash.lux index 23421b264..6af53e362 100644 --- a/stdlib/source/program/aedifex/hash.lux +++ b/stdlib/source/program/aedifex/hash.lux @@ -14,6 +14,8 @@ ["[0]" text ["%" format {"+" Format format}] ["[0]" encoding]]] + [macro + ["^" pattern]] [math [number ["n" nat] @@ -135,7 +137,7 @@ {.#None} (case (..hash_size input) 0 (constructor output) - (^template [<size> <write>] + (^.template [<size> <write>] [<size> (do try.monad [head (# n.hex decoded input) diff --git a/stdlib/source/program/aedifex/metadata/artifact.lux b/stdlib/source/program/aedifex/metadata/artifact.lux index 7a2957ae0..b5aef41de 100644 --- a/stdlib/source/program/aedifex/metadata/artifact.lux +++ b/stdlib/source/program/aedifex/metadata/artifact.lux @@ -59,7 +59,7 @@ (def: (time_format value) (%.Format Time) - (let [(^open "[0]") (time.clock value)] + (let [(open "[0]") (time.clock value)] (%.format (..pad #hour) (..pad #minute) (..pad #second)))) @@ -189,7 +189,7 @@ {try.#Failure error} (in {try.#Success - (let [(^open "[0]") artifact] + (let [(open "[0]") artifact] [..#group #group ..#name #name ..#versions (list) diff --git a/stdlib/source/program/aedifex/metadata/snapshot.lux b/stdlib/source/program/aedifex/metadata/snapshot.lux index 83ba59279..cc41be0b5 100644 --- a/stdlib/source/program/aedifex/metadata/snapshot.lux +++ b/stdlib/source/program/aedifex/metadata/snapshot.lux @@ -69,9 +69,9 @@ [version_format Version ..<version> (|>)] ) -(def: .public (format (^open "/[0]")) +(def: .public (format (open "/[0]")) (-> Metadata XML) - (let [(^open "//[0]") /#artifact] + (let [(open "//[0]") /#artifact] {xml.#Node ..<metadata> xml.attributes (list (..group_format //#group) @@ -100,7 +100,7 @@ (: (-> (List ///artifact/snapshot/version.Version) (List ///artifact/snapshot/version.Version)) (|>> (pipe.case - (^ (list)) + (pattern (list)) (list <default_version>) versions diff --git a/stdlib/source/program/aedifex/profile.lux b/stdlib/source/program/aedifex/profile.lux index 048aabf27..56e79674b 100644 --- a/stdlib/source/program/aedifex/profile.lux +++ b/stdlib/source/program/aedifex/profile.lux @@ -16,6 +16,7 @@ ["[0]" dictionary {"+" Dictionary} ["[0]" plist {"+" PList} ("[1]#[0]" monoid)]]]] [macro + ["^" pattern] ["[0]" template]] [meta ["[0]" symbol]] @@ -53,7 +54,7 @@ (def: (= reference subject) (case [reference subject] - (^template [<tag>] + (^.template [<tag>] [[{<tag>} {<tag>}] true]) ([#Repo] diff --git a/stdlib/source/program/aedifex/repository/remote.lux b/stdlib/source/program/aedifex/repository/remote.lux index 6252d75f2..85fe69b3c 100644 --- a/stdlib/source/program/aedifex/repository/remote.lux +++ b/stdlib/source/program/aedifex/repository/remote.lux @@ -67,7 +67,7 @@ {.#None} http))] (case status - (^ (static http/status.ok)) + (pattern (static http/status.ok)) (# ! each product.right ((the @http.#body message) {.#None})) _ @@ -90,7 +90,7 @@ http)) _ ((the @http.#body message) {.#Some 0})] (case status - (^ (static http/status.created)) + (pattern (static http/status.created)) (in []) _ diff --git a/stdlib/source/specification/compositor/common.lux b/stdlib/source/specification/compositor/common.lux index f97ca894e..58546822c 100644 --- a/stdlib/source/specification/compositor/common.lux +++ b/stdlib/source/specification/compositor/common.lux @@ -31,7 +31,7 @@ (generation.State+ anchor expression directive) what))) -(def: (runner (^open "[0]") state) +(def: (runner (open "[0]") state) (Instancer Runner) (function (_ evaluation_name expressionS) (do try.monad @@ -42,7 +42,7 @@ (phase expressionS)))] (# host evaluate! evaluation_name expressionG)))) -(def: (definer (^open "[0]") state) +(def: (definer (open "[0]") state) (Instancer Definer) (function (_ lux_name expressionS) (do try.monad diff --git a/stdlib/source/specification/compositor/generation/common.lux b/stdlib/source/specification/compositor/generation/common.lux index 19041bbb7..cf94de3a9 100644 --- a/stdlib/source/specification/compositor/generation/common.lux +++ b/stdlib/source/specification/compositor/generation/common.lux @@ -17,6 +17,8 @@ ["%" format {"+" format}]] [collection ["[0]" list]]] + [macro + ["^" pattern]] [math ["r" random {"+" Random}]] [tool @@ -245,9 +247,9 @@ (synthesis.i64 +0))} (run (..safe "lux text index")) (pipe.case - (^multi {try.#Success valueV} - [(:as (Maybe Nat) valueV) - {.#Some valueV}]) + (^.multi {try.#Success valueV} + [(:as (Maybe Nat) valueV) + {.#Some valueV}]) (n.= 0 valueV) _ @@ -257,9 +259,9 @@ (synthesis.i64 +0))} (run (..safe "lux text index")) (pipe.case - (^multi {try.#Success valueV} - [(:as (Maybe Nat) valueV) - {.#Some valueV}]) + (^.multi {try.#Success valueV} + [(:as (Maybe Nat) valueV) + {.#Some valueV}]) (n.= sample_size valueV) _ @@ -272,9 +274,9 @@ (synthesis.i64 length))} (run (..safe "lux text clip")) (pipe.case - (^multi {try.#Success valueV} - [(:as (Maybe Text) valueV) - {.#Some valueV}]) + (^.multi {try.#Success valueV} + [(:as (Maybe Text) valueV) + {.#Some valueV}]) (text#= expected valueV) _ @@ -288,9 +290,9 @@ (synthesis.i64 char_idx))} (run (..safe "lux text char")) (pipe.case - (^multi {try.#Success valueV} - [(:as (Maybe Int) valueV) - {.#Some valueV}]) + (^.multi {try.#Success valueV} + [(:as (Maybe Int) valueV) + {.#Some valueV}]) (text.contains? ("lux i64 char" valueV) sample_lower) @@ -322,9 +324,9 @@ (list (synthesis.text message))}]))} (run (..safe "lux try")) (pipe.case - (^multi {try.#Success valueV} - [(:as (Try Text) valueV) - {try.#Failure error}]) + (^.multi {try.#Success valueV} + [(:as (Try Text) valueV) + {try.#Failure error}]) (text.contains? message error) _ @@ -336,9 +338,9 @@ synthesis.#body (synthesis.text message)]))} (run (..safe "lux try")) (pipe.case - (^multi {try.#Success valueV} - [(:as (Try Text) valueV) - {try.#Success valueV}]) + (^.multi {try.#Success valueV} + [(:as (Try Text) valueV) + {try.#Success valueV}]) (text#= message valueV) _ diff --git a/stdlib/source/specification/lux/abstract/apply.lux b/stdlib/source/specification/lux/abstract/apply.lux index 3d01a1217..fe61d1a33 100644 --- a/stdlib/source/specification/lux/abstract/apply.lux +++ b/stdlib/source/specification/lux/abstract/apply.lux @@ -15,7 +15,7 @@ [// [functor {"+" Injection Comparison}]]) -(def: (identity injection comparison (^open "/#[0]")) +(def: (identity injection comparison (open "/#[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test)) (do [! random.monad] [sample (# ! each injection random.nat)] @@ -24,7 +24,7 @@ (/#on sample (injection function.identity)) sample)))) -(def: (homomorphism injection comparison (^open "/#[0]")) +(def: (homomorphism injection comparison (open "/#[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test)) (do [! random.monad] [sample random.nat @@ -34,7 +34,7 @@ (/#on (injection sample) (injection increase)) (injection (increase sample)))))) -(def: (interchange injection comparison (^open "/#[0]")) +(def: (interchange injection comparison (open "/#[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test)) (do [! random.monad] [sample random.nat @@ -45,7 +45,7 @@ (/#on (injection increase) (injection (: (-> (-> Nat Nat) Nat) (function (_ f) (f sample))))))))) -(def: (composition injection comparison (^open "/#[0]")) +(def: (composition injection comparison (open "/#[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test)) (:let [:$/1: (-> Nat Nat)] (do [! random.monad] diff --git a/stdlib/source/specification/lux/abstract/codec.lux b/stdlib/source/specification/lux/abstract/codec.lux index c220c8de6..9a39f4b1c 100644 --- a/stdlib/source/specification/lux/abstract/codec.lux +++ b/stdlib/source/specification/lux/abstract/codec.lux @@ -1,19 +1,19 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - ["[0]" try]] - [math - ["[0]" random {"+" Random}]]]] - [\\library - ["[0]" / - [// - [equivalence {"+" Equivalence}]]]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" try]] + [math + ["[0]" random {"+" Random}]]]] + [\\library + ["[0]" / + [// + [equivalence {"+" Equivalence}]]]]) -(def: .public (spec (^open "@//[0]") (^open "@//[0]") generator) +(def: .public (spec (open "@//[0]") (open "@//[0]") generator) (All (_ m a) (-> (Equivalence a) (/.Codec m a) (Random a) Test)) (do random.monad [expected generator] diff --git a/stdlib/source/specification/lux/abstract/comonad.lux b/stdlib/source/specification/lux/abstract/comonad.lux index 97ccee43e..6147cff90 100644 --- a/stdlib/source/specification/lux/abstract/comonad.lux +++ b/stdlib/source/specification/lux/abstract/comonad.lux @@ -1,19 +1,19 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" / {"+" CoMonad}]] - [// - [functor {"+" Injection Comparison}]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" / {"+" CoMonad}]] + [// + [functor {"+" Injection Comparison}]]) -(def: (left_identity injection (^open "_//[0]")) +(def: (left_identity injection (open "_//[0]")) (All (_ f) (-> (Injection f) (CoMonad f) Test)) (do [! random.monad] [sample random.nat @@ -25,7 +25,7 @@ (n.= (morphism start) (|> start _//disjoint (_//each morphism) _//out))))) -(def: (right_identity injection comparison (^open "_//[0]")) +(def: (right_identity injection comparison (open "_//[0]")) (All (_ f) (-> (Injection f) (Comparison f) (CoMonad f) Test)) (do random.monad [sample random.nat @@ -35,7 +35,7 @@ (== start (|> start _//disjoint (_//each _//out)))))) -(def: (associativity injection comparison (^open "_//[0]")) +(def: (associativity injection comparison (open "_//[0]")) (All (_ f) (-> (Injection f) (Comparison f) (CoMonad f) Test)) (do [! random.monad] [sample random.nat diff --git a/stdlib/source/specification/lux/abstract/enum.lux b/stdlib/source/specification/lux/abstract/enum.lux index 48e67fcf5..c2feb2a3f 100644 --- a/stdlib/source/specification/lux/abstract/enum.lux +++ b/stdlib/source/specification/lux/abstract/enum.lux @@ -1,15 +1,15 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [math - ["[0]" random {"+" Random}]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [math + ["[0]" random {"+" Random}]]]] + [\\library + ["[0]" /]]) -(def: .public (spec (^open "_#[0]") gen_sample) +(def: .public (spec (open "_#[0]") gen_sample) (All (_ a) (-> (/.Enum a) (Random a) Test)) (do random.monad [sample gen_sample] diff --git a/stdlib/source/specification/lux/abstract/equivalence.lux b/stdlib/source/specification/lux/abstract/equivalence.lux index 42d9e3750..386fafc8d 100644 --- a/stdlib/source/specification/lux/abstract/equivalence.lux +++ b/stdlib/source/specification/lux/abstract/equivalence.lux @@ -11,7 +11,7 @@ [\\library ["[0]" / {"+" Equivalence}]]) -(def: .public (spec (^open "/#[0]") random) +(def: .public (spec (open "/#[0]") random) (All (_ a) (-> (Equivalence a) (Random a) Test)) (do random.monad [left random diff --git a/stdlib/source/specification/lux/abstract/functor.lux b/stdlib/source/specification/lux/abstract/functor.lux index 2d5e6b11d..b82a0c83d 100644 --- a/stdlib/source/specification/lux/abstract/functor.lux +++ b/stdlib/source/specification/lux/abstract/functor.lux @@ -1,18 +1,18 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [equivalence {"+" Equivalence}] - [monad {"+" do}]] - [control - ["[0]" function]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" / {"+" Functor}]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [equivalence {"+" Equivalence}] + [monad {"+" do}]] + [control + ["[0]" function]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" / {"+" Functor}]]) (type: .public (Injection f) (All (_ a) (-> a (f a)))) @@ -22,7 +22,7 @@ (-> (Equivalence a) (Equivalence (f a))))) -(def: (identity injection comparison (^open "@//[0]")) +(def: (identity injection comparison (open "@//[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Functor f) Test)) (do [! random.monad] [sample (# ! each injection random.nat)] @@ -31,7 +31,7 @@ (@//each function.identity sample) sample)))) -(def: (homomorphism injection comparison (^open "@//[0]")) +(def: (homomorphism injection comparison (open "@//[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Functor f) Test)) (do [! random.monad] [sample random.nat @@ -41,7 +41,7 @@ (@//each increase (injection sample)) (injection (increase sample)))))) -(def: (composition injection comparison (^open "@//[0]")) +(def: (composition injection comparison (open "@//[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Functor f) Test)) (do [! random.monad] [sample (# ! each injection random.nat) diff --git a/stdlib/source/specification/lux/abstract/functor/contravariant.lux b/stdlib/source/specification/lux/abstract/functor/contravariant.lux index 45401b15d..8f379472e 100644 --- a/stdlib/source/specification/lux/abstract/functor/contravariant.lux +++ b/stdlib/source/specification/lux/abstract/functor/contravariant.lux @@ -1,20 +1,20 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [equivalence {"+" Equivalence}] - [monad {"+" do}]] - [control - ["[0]" function]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" / {"+" Functor}]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [equivalence {"+" Equivalence}] + [monad {"+" do}]] + [control + ["[0]" function]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" / {"+" Functor}]]) -(def: (identity equivalence value (^open "@//[0]")) +(def: (identity equivalence value (open "@//[0]")) (All (_ f a) (-> (Equivalence (f a)) (f a) (Functor f) Test)) (_.test "Law of identity." (equivalence diff --git a/stdlib/source/specification/lux/abstract/hash.lux b/stdlib/source/specification/lux/abstract/hash.lux index 4ba0e5f53..935dc6a2d 100644 --- a/stdlib/source/specification/lux/abstract/hash.lux +++ b/stdlib/source/specification/lux/abstract/hash.lux @@ -1,17 +1,17 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]]) -(def: .public (spec (^open "_#[0]") random) +(def: .public (spec (open "_#[0]") random) (All (_ a) (-> (/.Hash a) (Random a) Test)) (do random.monad [parameter random diff --git a/stdlib/source/specification/lux/abstract/interval.lux b/stdlib/source/specification/lux/abstract/interval.lux index 6994353f1..c767e42fd 100644 --- a/stdlib/source/specification/lux/abstract/interval.lux +++ b/stdlib/source/specification/lux/abstract/interval.lux @@ -1,16 +1,16 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - ["[0]" order]] - [math - ["[0]" random {"+" Random}]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + ["[0]" order]] + [math + ["[0]" random {"+" Random}]]]] + [\\library + ["[0]" /]]) -(def: .public (spec (^open "@//[0]") gen_sample) +(def: .public (spec (open "@//[0]") gen_sample) (All (_ a) (-> (/.Interval a) (Random a) Test)) (<| (_.for [/.Interval]) (do random.monad diff --git a/stdlib/source/specification/lux/abstract/mix.lux b/stdlib/source/specification/lux/abstract/mix.lux index c6413c601..8ea932916 100644 --- a/stdlib/source/specification/lux/abstract/mix.lux +++ b/stdlib/source/specification/lux/abstract/mix.lux @@ -1,19 +1,19 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [// - [functor {"+" Injection Comparison}]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [// + [functor {"+" Injection Comparison}]] + [\\library + ["[0]" /]]) -(def: .public (spec injection comparison (^open "@//[0]")) +(def: .public (spec injection comparison (open "@//[0]")) (All (_ f) (-> (Injection f) (Comparison f) (/.Mix f) Test)) (do random.monad [subject random.nat diff --git a/stdlib/source/specification/lux/abstract/monad.lux b/stdlib/source/specification/lux/abstract/monad.lux index 132e9eeb2..fe14440fd 100644 --- a/stdlib/source/specification/lux/abstract/monad.lux +++ b/stdlib/source/specification/lux/abstract/monad.lux @@ -1,17 +1,17 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" / {"+" do}]] - [// - [functor {"+" Injection Comparison}]]) + [library + [lux "*" + ["_" test {"+" Test}] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" / {"+" do}]] + [// + [functor {"+" Injection Comparison}]]) -(def: (left_identity injection comparison (^open "_//[0]")) +(def: (left_identity injection comparison (open "_//[0]")) (All (_ f) (-> (Injection f) (Comparison f) (/.Monad f) Test)) (do [! random.monad] [sample random.nat @@ -23,7 +23,7 @@ (|> (injection sample) (_//each morphism) _//conjoint) (morphism sample))))) -(def: (right_identity injection comparison (^open "_//[0]")) +(def: (right_identity injection comparison (open "_//[0]")) (All (_ f) (-> (Injection f) (Comparison f) (/.Monad f) Test)) (do random.monad [sample random.nat] @@ -32,7 +32,7 @@ (|> (injection sample) (_//each _//in) _//conjoint) (injection sample))))) -(def: (associativity injection comparison (^open "_//[0]")) +(def: (associativity injection comparison (open "_//[0]")) (All (_ f) (-> (Injection f) (Comparison f) (/.Monad f) Test)) (do [! random.monad] [sample random.nat diff --git a/stdlib/source/specification/lux/abstract/monoid.lux b/stdlib/source/specification/lux/abstract/monoid.lux index c3857dbbb..6d5ab67fc 100644 --- a/stdlib/source/specification/lux/abstract/monoid.lux +++ b/stdlib/source/specification/lux/abstract/monoid.lux @@ -1,17 +1,17 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [math - ["[0]" random {"+" Random}]]]] - [\\library - ["[0]" / - [// - [equivalence {"+" Equivalence}]]]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [math + ["[0]" random {"+" Random}]]]] + [\\library + ["[0]" / + [// + [equivalence {"+" Equivalence}]]]]) -(def: .public (spec (^open "_#[0]") (^open "_#[0]") gen_sample) +(def: .public (spec (open "_#[0]") (open "_#[0]") gen_sample) (All (_ a) (-> (Equivalence a) (/.Monoid a) (Random a) Test)) (do random.monad [sample gen_sample diff --git a/stdlib/source/specification/lux/abstract/order.lux b/stdlib/source/specification/lux/abstract/order.lux index fd5560710..1c77ffc3b 100644 --- a/stdlib/source/specification/lux/abstract/order.lux +++ b/stdlib/source/specification/lux/abstract/order.lux @@ -1,15 +1,15 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [math - ["[0]" random {"+" Random}]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [math + ["[0]" random {"+" Random}]]]] + [\\library + ["[0]" /]]) -(def: .public (spec (^open "@//[0]") generator) +(def: .public (spec (open "@//[0]") generator) (All (_ a) (-> (/.Order a) (Random a) Test)) (<| (_.for [/.Order]) ($_ _.and diff --git a/stdlib/source/specification/lux/world/file.lux b/stdlib/source/specification/lux/world/file.lux index 0e4a240d2..c3164d544 100644 --- a/stdlib/source/specification/lux/world/file.lux +++ b/stdlib/source/specification/lux/world/file.lux @@ -1,34 +1,34 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - ["[0]" predicate]] - [control - [io {"+" IO}] - ["[0]" maybe ("[1]#[0]" functor)] - ["[0]" try ("[1]#[0]" functor)] - ["[0]" exception] - [concurrency - ["[0]" async {"+" Async}]]] - [data - ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}] - [encoding - ["[0]" utf8 ("[1]#[0]" codec)]]] - ["[0]" binary {"+" Binary} ("[1]#[0]" equivalence monoid) - ["$[1]" \\test]] - [collection - ["[0]" list]]] - [math - ["[0]" random] - [number - ["n" nat]]] - [time - ["[0]" instant {"+" Instant} ("[1]#[0]" equivalence)]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + ["[0]" predicate]] + [control + [io {"+" IO}] + ["[0]" maybe ("[1]#[0]" functor)] + ["[0]" try ("[1]#[0]" functor)] + ["[0]" exception] + [concurrency + ["[0]" async {"+" Async}]]] + [data + ["[0]" text ("[1]#[0]" equivalence) + ["%" format {"+" format}] + [encoding + ["[0]" utf8 ("[1]#[0]" codec)]]] + ["[0]" binary {"+" Binary} ("[1]#[0]" equivalence monoid) + ["$[1]" \\test]] + [collection + ["[0]" list]]] + [math + ["[0]" random] + [number + ["n" nat]]] + [time + ["[0]" instant {"+" Instant} ("[1]#[0]" equivalence)]]]] + [\\library + ["[0]" /]]) (def: (for_path fs) (-> (IO (/.System Async)) Test) @@ -125,7 +125,7 @@ [made_sub? (# fs make_directory sub_dir) directory_files (# fs directory_files parent) sub_directories (# fs sub_directories parent) - .let [(^open "list#[0]") (list.equivalence text.equivalence)]] + .let [(open "list#[0]") (list.equivalence text.equivalence)]] (in (<| (try.else false) (do try.monad [_ made_sub?] diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux index bd30cf30e..751655065 100644 --- a/stdlib/source/test/lux.lux +++ b/stdlib/source/test/lux.lux @@ -26,6 +26,7 @@ ["[0]" plist]]]] ["[0]" macro [syntax {"+" syntax:}] + ["^" pattern] ["[0]" code ("[1]#[0]" equivalence)] ["[0]" template]] ["[0]" math @@ -172,7 +173,7 @@ ($_ _.and (_.cover [/.list] (case (/.list e/0 e/1) - (^ (/.list a/0 a/1)) + (pattern (/.list a/0 a/1)) (and (n.= e/0 a/0) (n.= e/1 a/1)) @@ -180,7 +181,7 @@ false)) (_.cover [/.list&] (case (/.list& e/0 e/1 (/.list e/2 e/3)) - (^ (/.list& a/0 a/1 (/.list a/2 a/3))) + (pattern (/.list& a/0 a/1 (/.list a/2 a/3))) (and (n.= e/0 a/0) (n.= e/1 a/1) (n.= e/2 a/2) @@ -221,8 +222,8 @@ (n.= expected (# local_returner return []))) (_.cover [/.open:] (n.= static_return (global#return []))) - (_.cover [/.^open] - (let [(/.^open "local#[0]") local_returner] + (_.cover [/.open] + (let [(/.open "local#[0]") local_returner] (n.= expected (local#return [])))) (_.cover [/.#] (n.= expected (/.# local_returner return []))) @@ -455,15 +456,15 @@ (function (_ _) ... TODO: Remove this hack once Jython is no longer being used as the Python interpreter. (`` (for @.python (case (' [<input>']) - (^code [<module> - ("lux def" (~ [_ {.#Symbol ["" _]}]) [] #0) - (~~ (template.spliced <referrals>))]) + (^.` [<module> + ("lux def" (~ [_ {.#Symbol ["" _]}]) [] #0) + (~~ (template.spliced <referrals>))]) true _ false) (case (' [<input>']) - (^code [<module> (~~ (template.spliced <referrals>))]) + (^.` [<module> (~~ (template.spliced <referrals>))]) true _ @@ -588,7 +589,7 @@ (same? /.Nat (/.:of expected))) (_.cover [/.Primitive] (case (/.Primitive "foo" [expected/0 expected/1]) - (^ {.#Primitive "foo" (list actual/0 actual/1)}) + (pattern {.#Primitive "foo" (list actual/0 actual/1)}) (and (same? expected/0 actual/0) (same? expected/1 actual/1)) @@ -704,16 +705,6 @@ (_.cover [/.template:] (n.= (n.+ left right) (!n/+ left right)))) - (do [! random.monad] - [sample (# ! each (n.% 5) random.nat)] - (_.cover [/.^template] - (case sample - (/.^template [<case>] - [<case> true]) - ([0] [1] [2] [3] [4]) - - _ - false))) ))) (def: option/0 "0") @@ -728,8 +719,8 @@ ($_ _.and (_.cover [/.static] (case sample - (^ (/.static option/0)) true - (^ (/.static option/1)) true + (pattern (/.static option/0)) true + (pattern (/.static option/1)) true _ false)) (_.cover [/.char] (|> (`` (/.char (~~ (/.static static_char)))) @@ -1028,55 +1019,9 @@ {.#Right +0} true _ false) )) - (_.cover [/.^or] - (and (/.case expected_rev - (/.^or .5 .25) true - _ false) - (/.case expected_frac - (/.^or +0.5 +1.25) true - _ false) - (/.case expected_text - (/.^or "+0.5" "+1.25") true - _ false))) - (_.cover [/.^] + (_.cover [/.pattern] (/.case [..#left expected_nat ..#right expected_int] - (/.^ (!pair 0 +0)) true - _ false)) - (_.cover [/.^let] - (let [expected_pair (: (Pair Nat Int) - [..#left expected_nat ..#right expected_int])] - (/.case expected_pair - (/.^let actual_pair (/.^ (!pair actual_left actual_right))) - (and (/.same? expected_pair actual_pair) - (/.same? expected_nat actual_left) - (/.same? expected_int actual_right))))) - (_.cover [/.^multi] - (let [expected_pair (: (Pair Nat Int) - [..#left expected_nat ..#right expected_int])] - (and (/.case expected_pair - (/.^multi (/.^ (!pair 0 actual_right)) - [actual_right - +0]) - true - - _ - false) - (/.case expected_pair - (/.^multi (/.^ (!pair 0 actual_right)) - (i.= +0 actual_right)) - true - - _ - false)))) - (_.cover [/.^|>] - (case expected_frac - (/.^|> actual_frac [(f.* +2.0) (f.* +2.0)]) - (f.= (f.* +4.0 expected_frac) - actual_frac))) - (_.cover [/.^code] - (case (code.text expected_text) - (/.^code "+0.5") true - (/.^code "+1.25") true + (/.pattern (!pair 0 +0)) true _ false)) (_.cover [/.let] (and (/.let [actual_nat expected_nat] @@ -1193,7 +1138,7 @@ let/3 <code>.local_symbol]) (in (list (code.bit (case (the .#scopes *lux*) - (^ (list& scope/2 _)) + (pattern (list& scope/2 _)) (let [locals/2 (the .#locals scope/2) expected_locals/2 (set.of_list text.hash (list fn/2 var/2 let/2 let/3)) diff --git a/stdlib/source/test/lux/abstract/apply.lux b/stdlib/source/test/lux/abstract/apply.lux index 1ff97f5b6..ad0bb0250 100644 --- a/stdlib/source/test/lux/abstract/apply.lux +++ b/stdlib/source/test/lux/abstract/apply.lux @@ -1,20 +1,20 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]] - [control - ["[0]" maybe]] - [data - [collection - ["[0]" list]]] - [math - ["[0]" random] - [number - ["n" nat]]] - ["_" test {"+" Test}]]] - [\\library - ["[0]" / {"+" Apply}]]) + [library + [lux "*" + [abstract + [monad {"+" do}]] + [control + ["[0]" maybe]] + [data + [collection + ["[0]" list]]] + [math + ["[0]" random] + [number + ["n" nat]]] + ["_" test {"+" Test}]]] + [\\library + ["[0]" / {"+" Apply}]]) (def: .public test Test @@ -28,7 +28,7 @@ (case (# (/.composite maybe.monad maybe.apply list.apply) on {.#Some (list right)} {.#Some (list (n.+ left))}) - (^ {.#Some (list actual)}) + (pattern {.#Some (list actual)}) (n.= expected actual) _ diff --git a/stdlib/source/test/lux/abstract/functor.lux b/stdlib/source/test/lux/abstract/functor.lux index b4b333f13..541c88971 100644 --- a/stdlib/source/test/lux/abstract/functor.lux +++ b/stdlib/source/test/lux/abstract/functor.lux @@ -1,20 +1,20 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - ["[0]" maybe]] - [data - [collection - ["[0]" list]]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" / {"+" Functor}]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" maybe]] + [data + [collection + ["[0]" list]]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" / {"+" Functor}]]) (def: .public test Test @@ -36,7 +36,7 @@ (case (# (/.sum maybe.functor list.functor) each (n.+ shift) {.#Right (list right)}) - (^ {.#Right (list actual)}) + (pattern {.#Right (list actual)}) (n.= (n.+ shift right) actual) _ @@ -45,7 +45,7 @@ (case (# (/.product maybe.functor list.functor) each (n.+ shift) [{.#Some left} (list right)]) - (^ [{.#Some actualL} (list actualR)]) + (pattern [{.#Some actualL} (list actualR)]) (and (n.= (n.+ shift left) actualL) (n.= (n.+ shift right) actualR)) @@ -55,7 +55,7 @@ (case (# (/.composite maybe.functor list.functor) each (n.+ shift) {.#Some (list left)}) - (^ {.#Some (list actual)}) + (pattern {.#Some (list actual)}) (n.= (n.+ shift left) actual) _ diff --git a/stdlib/source/test/lux/abstract/hash.lux b/stdlib/source/test/lux/abstract/hash.lux index 198babcda..635476226 100644 --- a/stdlib/source/test/lux/abstract/hash.lux +++ b/stdlib/source/test/lux/abstract/hash.lux @@ -1,22 +1,22 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [\\specification - [functor - ["$[0]" contravariant]]]] - [data - ["[0]" bit ("[1]#[0]" equivalence)]] - [math - ["[0]" random] - [number - ["[0]" nat]]]]] - [\\library - ["[0]" / {"+" Hash} - [// - [equivalence {"+" Equivalence}]]]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [\\specification + [functor + ["$[0]" contravariant]]]] + [data + ["[0]" bit ("[1]#[0]" equivalence)]] + [math + ["[0]" random] + [number + ["[0]" nat]]]]] + [\\library + ["[0]" / {"+" Hash} + [// + [equivalence {"+" Equivalence}]]]]) (def: .public test Test @@ -25,7 +25,7 @@ rightN random.nat .let [hash (: (Equivalence (/.Hash Nat)) (implementation - (def: (= (^open "left#[0]") (^open "right#[0]")) + (def: (= (open "left#[0]") (open "right#[0]")) (and (bit#= (left#= (left#hash leftN) (left#hash leftN)) (right#= (right#hash leftN) (right#hash leftN))) (bit#= (left#= (left#hash rightN) (left#hash rightN)) diff --git a/stdlib/source/test/lux/abstract/interval.lux b/stdlib/source/test/lux/abstract/interval.lux index a9dfc2572..f2b0d2713 100644 --- a/stdlib/source/test/lux/abstract/interval.lux +++ b/stdlib/source/test/lux/abstract/interval.lux @@ -142,7 +142,7 @@ (# ! each (|>> set.list (list.sorted n.<) (pipe.case - (^ (list b t1 t2)) + (pattern (list b t1 t2)) [b t1 t2] _ @@ -165,7 +165,7 @@ (# ! each (|>> set.list (list.sorted n.<) (pipe.case - (^ (list b t1 t2)) + (pattern (list b t1 t2)) [b t1 t2] _ @@ -193,7 +193,7 @@ (# ! each (|>> set.list (list.sorted n.<) (pipe.case - (^ (list x0 x1 x2 x3)) + (pattern (list x0 x1 x2 x3)) [x0 x1 x2 x3] _ @@ -227,7 +227,7 @@ (# ! each (|>> set.list (list.sorted n.<) (pipe.case - (^ (list x0 x1 x2 x3)) + (pattern (list x0 x1 x2 x3)) [x0 x1 x2 x3] _ diff --git a/stdlib/source/test/lux/control/concurrency/actor.lux b/stdlib/source/test/lux/control/concurrency/actor.lux index cec359f0e..5f96bbe35 100644 --- a/stdlib/source/test/lux/control/concurrency/actor.lux +++ b/stdlib/source/test/lux/control/concurrency/actor.lux @@ -1,29 +1,29 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - ["[0]" try {"+" Try}] - ["[0]" exception {"+" exception:}] - ["[0]" io {"+" IO io}]] - [data - [text - ["%" format {"+" format}]] - [collection - ["[0]" list] - ["[0]" sequence {"+" Sequence}]]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" / {"+" actor: message:} - [// - ["[0]" atom {"+" Atom}] - ["[0]" async {"+" Async Resolver} ("[1]#[0]" monad)] - ["[0]" frp]]]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" try {"+" Try}] + ["[0]" exception {"+" exception:}] + ["[0]" io {"+" IO io}]] + [data + [text + ["%" format {"+" format}]] + [collection + ["[0]" list] + ["[0]" sequence {"+" Sequence}]]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" / {"+" actor: message:} + [// + ["[0]" atom {"+" Atom}] + ["[0]" async {"+" Async Resolver} ("[1]#[0]" monad)] + ["[0]" frp]]]]) (exception: got_wrecked) @@ -145,7 +145,7 @@ (in {try.#Success [actor sent? alive? obituary]})))] (_.cover' [/.Obituary /.obituary'] (case result - (^ {try.#Success [actor sent? alive? {.#Some [error state (list single_pending_message)]}]}) + (pattern {try.#Success [actor sent? alive? {.#Some [error state (list single_pending_message)]}]}) (and (..mailed? sent?) (not alive?) (exception.match? ..got_wrecked error) @@ -187,7 +187,7 @@ (..mailed? sent/--?) (..mailed? poisoned?) (case obituary - (^ {.#Some [error final_state (list poison_pill)]}) + (pattern {.#Some [error final_state (list poison_pill)]}) (and (exception.match? /.poisoned error) (n.= (++ (++ initial_state)) final_state)) diff --git a/stdlib/source/test/lux/control/concurrency/frp.lux b/stdlib/source/test/lux/control/concurrency/frp.lux index 7b564d904..c7b5922f3 100644 --- a/stdlib/source/test/lux/control/concurrency/frp.lux +++ b/stdlib/source/test/lux/control/concurrency/frp.lux @@ -65,7 +65,7 @@ (def: .public test Test (<| (_.covering /._) - (let [(^open "list#[0]") (list.equivalence n.equivalence)] + (let [(open "list#[0]") (list.equivalence n.equivalence)] (do [! random.monad] [inputs (random.list 5 random.nat) sample random.nat diff --git a/stdlib/source/test/lux/control/continuation.lux b/stdlib/source/test/lux/control/continuation.lux index ca5cc1c2a..6514b1332 100644 --- a/stdlib/source/test/lux/control/continuation.lux +++ b/stdlib/source/test/lux/control/continuation.lux @@ -1,22 +1,22 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [\\specification - ["$[0]" functor {"+" Injection Comparison}] - ["$[0]" apply] - ["$[0]" monad]]] - [data - [collection - ["[0]" list]]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [\\specification + ["$[0]" functor {"+" Injection Comparison}] + ["$[0]" apply] + ["$[0]" monad]]] + [data + [collection + ["[0]" list]]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]]) (def: injection (All (_ o) (Injection (All (_ i) (/.Cont i o)))) @@ -32,8 +32,8 @@ (<| (_.covering /._) (do random.monad [sample random.nat - .let [(^open "_#[0]") /.apply - (^open "_#[0]") /.monad] + .let [(open "_#[0]") /.apply + (open "_#[0]") /.monad] elems (random.list 3 random.nat)]) (_.for [/.Cont]) ($_ _.and @@ -66,8 +66,8 @@ (restart [(n.+ 10 output) (++ idx)]) (in output)))))) (_.cover [/.shift /.reset] - (let [(^open "_#[0]") /.monad - (^open "list#[0]") (list.equivalence n.equivalence) + (let [(open "_#[0]") /.monad + (open "list#[0]") (list.equivalence n.equivalence) visit (: (-> (List Nat) (/.Cont (List Nat) (List Nat))) (function (visit xs) diff --git a/stdlib/source/test/lux/control/function/memo.lux b/stdlib/source/test/lux/control/function/memo.lux index b85135c9c..b36688fbb 100644 --- a/stdlib/source/test/lux/control/function/memo.lux +++ b/stdlib/source/test/lux/control/function/memo.lux @@ -1,29 +1,31 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - ["[0]" io {"+" IO}] - ["[0]" state {"+" State} ("[1]#[0]" monad)]] - [data - ["[0]" product] - [collection - ["[0]" dictionary {"+" Dictionary}] - ["[0]" list ("[1]#[0]" functor mix)]]] - [math - ["[0]" random] - [number - ["n" nat] - ["[0]" i64]]] - [time - ["[0]" instant] - ["[0]" duration {"+" Duration}]]]] - [\\library - ["[0]" / - ["/[1]" // "_" - ["[1]" mixin]]]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" io {"+" IO}] + ["[0]" state {"+" State} ("[1]#[0]" monad)]] + [data + ["[0]" product] + [collection + ["[0]" dictionary {"+" Dictionary}] + ["[0]" list ("[1]#[0]" functor mix)]]] + [macro + ["^" pattern]] + [math + ["[0]" random] + [number + ["n" nat] + ["[0]" i64]]] + [time + ["[0]" instant] + ["[0]" duration {"+" Duration}]]]] + [\\library + ["[0]" / + ["/[1]" // "_" + ["[1]" mixin]]]]) (def: (fibonacci again input) (/.Memo Nat Nat) @@ -106,7 +108,7 @@ (: (//.Mixin Nat (State (Dictionary Nat Nat) Nat)) (function (factorial delegate again input) (case input - (^or 0 1) (# state.monad in 1) + (^.or 0 1) (# state.monad in 1) _ (do state.monad [output' (again (-- input))] (in (n.* input output'))))))) diff --git a/stdlib/source/test/lux/control/function/mixin.lux b/stdlib/source/test/lux/control/function/mixin.lux index 948d6885b..7ec7c8c09 100644 --- a/stdlib/source/test/lux/control/function/mixin.lux +++ b/stdlib/source/test/lux/control/function/mixin.lux @@ -1,25 +1,27 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [equivalence {"+" Equivalence}] - [predicate {"+" Predicate}] - [monad {"+" do}] - [\\specification - ["$[0]" monoid]]] - [control - ["[0]" state {"+" State}]] - [data - ["[0]" product] - [collection - ["[0]" list ("[1]#[0]" functor mix)]]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [equivalence {"+" Equivalence}] + [predicate {"+" Predicate}] + [monad {"+" do}] + [\\specification + ["$[0]" monoid]]] + [control + ["[0]" state {"+" State}]] + [data + ["[0]" product] + [collection + ["[0]" list ("[1]#[0]" functor mix)]]] + [macro + ["^" pattern]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]]) (def: .public test Test @@ -51,7 +53,7 @@ (let [factorial (/.fixed (function (_ delegate again input) (case input - (^or 0 1) 1 + (^.or 0 1) 1 _ (n.* input (again (-- input))))))] (n.= expected (factorial input)))) @@ -59,7 +61,7 @@ (let [bottom (: (/.Mixin Nat Nat) (function (_ delegate again input) (case input - (^or 0 1) 1 + (^.or 0 1) 1 _ (delegate input)))) multiplication (: (/.Mixin Nat Nat) (function (_ delegate again input) @@ -71,7 +73,7 @@ (let [loop (: (/.Mixin Nat Nat) (function (_ delegate again input) (case input - (^or 0 1) 1 + (^.or 0 1) 1 _ (n.* input (delegate (-- input)))))) left (/.fixed (/.mixed /.nothing loop)) right (/.fixed (/.mixed loop /.nothing))] @@ -86,7 +88,7 @@ bottom? (: (Predicate Nat) (function (_ input) (case input - (^or 0 1) true + (^.or 0 1) true _ false))) multiplication (: (/.Mixin Nat Nat) (function (_ delegate again input) @@ -128,7 +130,7 @@ (/.of_recursive (function (_ again input) (case input - (^or 0 1) 1 + (^.or 0 1) 1 _ (n.* input (again (-- input)))))))] (n.= expected (factorial input))))) diff --git a/stdlib/source/test/lux/control/lazy.lux b/stdlib/source/test/lux/control/lazy.lux index cc78de46f..8955a580d 100644 --- a/stdlib/source/test/lux/control/lazy.lux +++ b/stdlib/source/test/lux/control/lazy.lux @@ -1,22 +1,22 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [\\specification - ["$[0]" functor {"+" Injection Comparison}] - ["$[0]" apply] - ["$[0]" monad] - ["$[0]" equivalence]]] - [data - ["[0]" product]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat]]]]] - [\\library - ["[0]" / {"+" Lazy}]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [\\specification + ["$[0]" functor {"+" Injection Comparison}] + ["$[0]" apply] + ["$[0]" monad] + ["$[0]" equivalence]]] + [data + ["[0]" product]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat]]]]] + [\\library + ["[0]" / {"+" Lazy}]]) (def: injection (Injection Lazy) @@ -54,7 +54,7 @@ (_.cover [/.lazy] (let [lazy (/.lazy <eager>) - (^open "_#=") (product.equivalence n.equivalence n.equivalence)] + (open "_#=") (product.equivalence n.equivalence n.equivalence)] (_#= expected (/.value lazy)))) diff --git a/stdlib/source/test/lux/control/maybe.lux b/stdlib/source/test/lux/control/maybe.lux index 6fefaecfe..9563e44ce 100644 --- a/stdlib/source/test/lux/control/maybe.lux +++ b/stdlib/source/test/lux/control/maybe.lux @@ -83,7 +83,7 @@ (/.list {.#Some value})))) (do random.monad [expected random.nat - .let [(^open "/#[0]") (/.equivalence n.equivalence)]] + .let [(open "/#[0]") (/.equivalence n.equivalence)]] (_.cover [/.when] (and (/#= {.#Some expected} (/.when true {.#Some expected})) (/#= {.#None} (/.when false {.#Some expected}))))) diff --git a/stdlib/source/test/lux/control/parser.lux b/stdlib/source/test/lux/control/parser.lux index 5a76942ed..02da11358 100644 --- a/stdlib/source/test/lux/control/parser.lux +++ b/stdlib/source/test/lux/control/parser.lux @@ -1,44 +1,44 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [equivalence {"+" Equivalence}] - [\\specification - ["$[0]" functor {"+" Injection Comparison}] - ["$[0]" apply] - ["$[0]" monad]]] - [control - ["[0]" try {"+" Try}] - [parser - ["<[0]>" code]]] - [data - ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [math - ["[0]" random] - [number - ["n" nat]]] - [macro - [syntax {"+" syntax:}] - ["[0]" code]]]] - [\\library - ["[0]" / {"+" Parser}]] - ["[0]" / "_" - ["[1][0]" analysis] - ["[1][0]" binary] - ["[1][0]" cli] - ["[1][0]" code] - ["[1][0]" environment] - ["[1][0]" json] - ["[1][0]" synthesis] - ["[1][0]" text] - ["[1][0]" tree] - ["[1][0]" type] - ["[1][0]" xml]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [equivalence {"+" Equivalence}] + [\\specification + ["$[0]" functor {"+" Injection Comparison}] + ["$[0]" apply] + ["$[0]" monad]]] + [control + ["[0]" try {"+" Try}] + [parser + ["<[0]>" code]]] + [data + ["[0]" text ("[1]#[0]" equivalence) + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [math + ["[0]" random] + [number + ["n" nat]]] + [macro + [syntax {"+" syntax:}] + ["[0]" code]]]] + [\\library + ["[0]" / {"+" Parser}]] + ["[0]" / "_" + ["[1][0]" analysis] + ["[1][0]" binary] + ["[1][0]" cli] + ["[1][0]" code] + ["[1][0]" environment] + ["[1][0]" json] + ["[1][0]" synthesis] + ["[1][0]" text] + ["[1][0]" tree] + ["[1][0]" type] + ["[1][0]" xml]]) (def: (should_fail expected input) (All (_ a) (-> Text (Try a) Bit)) @@ -80,7 +80,7 @@ then <code>.any input <code>.any]) (in (list (` (case (~ input) - (^ {try.#Success [(~' _) (~ pattern)]}) + (pattern {try.#Success [(~' _) (~ pattern)]}) (~ then) (~' _) diff --git a/stdlib/source/test/lux/control/parser/binary.lux b/stdlib/source/test/lux/control/parser/binary.lux index 11cca9980..00ff979d9 100644 --- a/stdlib/source/test/lux/control/parser/binary.lux +++ b/stdlib/source/test/lux/control/parser/binary.lux @@ -28,6 +28,7 @@ ["[0]" sequence] ["[0]" set]]] [macro + ["^" pattern] ["[0]" code]] [math ["[0]" random {"+" Random}] @@ -114,7 +115,7 @@ (def: random_type (Random Type) - (let [(^open "[0]") random.monad] + (let [(open "[0]") random.monad] ($_ random.either (in .Nat) (in .List) @@ -132,9 +133,9 @@ (_.cover [<size> <parser> <format>] (|> (format.result <format> expected) (/.result <parser>) - (!expect (^multi {try.#Success actual} - (n.= (.nat expected) - (.nat actual)))))))] + (!expect (^.multi {try.#Success actual} + (n.= (.nat expected) + (.nat actual)))))))] [/.size/8 /.bits/8 format.bits/8] [/.size/16 /.bits/16 format.bits/16] @@ -151,8 +152,8 @@ (_.cover [<parser> <format>] (|> (format.result <format> expected) (/.result <parser>) - (!expect (^multi {try.#Success actual} - (# binary.equivalence = expected actual))))))] + (!expect (^.multi {try.#Success actual} + (# binary.equivalence = expected actual))))))] [/.binary/8 format.binary/8] [/.binary/16 format.binary/16] @@ -169,8 +170,8 @@ (_.cover [<parser> <format>] (|> (format.result <format> expected) (/.result <parser>) - (!expect (^multi {try.#Success actual} - (# text.equivalence = expected actual))))))] + (!expect (^.multi {try.#Success actual} + (# text.equivalence = expected actual))))))] [/.utf8/8 format.utf8/8] [/.utf8/16 format.utf8/16] @@ -189,8 +190,8 @@ (|> expected (format.result (<format> format.nat)) (/.result (<parser> /.nat)) - (!expect (^multi {try.#Success actual} - (# (sequence.equivalence n.equivalence) = expected actual))))))] + (!expect (^.multi {try.#Success actual} + (# (sequence.equivalence n.equivalence) = expected actual))))))] [/.sequence/8 format.sequence/8] [/.sequence/16 format.sequence/16] @@ -208,8 +209,8 @@ (|> expected (format.result <format>) (/.result <parser>) - (!expect (^multi {try.#Success actual} - (# <equivalence> = expected actual))))))] + (!expect (^.multi {try.#Success actual} + (# <equivalence> = expected actual))))))] [/.bit format.bit random.bit bit.equivalence] [/.nat format.nat random.nat n.equivalence] @@ -221,10 +222,10 @@ (|> expected (format.result format.frac) (/.result /.frac) - (!expect (^multi {try.#Success actual} - (or (# frac.equivalence = expected actual) - (and (frac.not_a_number? expected) - (frac.not_a_number? actual)))))))) + (!expect (^.multi {try.#Success actual} + (or (# frac.equivalence = expected actual) + (and (frac.not_a_number? expected) + (frac.not_a_number? actual)))))))) (do [! random.monad] [expected (# ! each (|>> (i64.and (i64.mask /.size/8)) (n.max 2)) @@ -233,8 +234,8 @@ (|> expected (format.result format.bits/8) (/.result /.bit) - (!expect (^multi {try.#Failure error} - (exception.match? /.not_a_bit error)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.not_a_bit error)))))) ))) (def: complex @@ -247,8 +248,8 @@ (|> expected (format.result <format>) (/.result <parser>) - (!expect (^multi {try.#Success actual} - (# <equivalence> = expected actual))))))] + (!expect (^.multi {try.#Success actual} + (# <equivalence> = expected actual))))))] [/.location format.location random_location location_equivalence] [/.code format.code random_code code.equivalence] @@ -261,8 +262,8 @@ (|> expected (format.result <format>) (/.result <parser>) - (!expect (^multi {try.#Success actual} - (# <equivalence> = expected actual))))))] + (!expect (^.multi {try.#Success actual} + (# <equivalence> = expected actual))))))] [/.maybe (/.maybe /.nat) format.maybe (format.maybe format.nat) (random.maybe random.nat) (maybe.equivalence n.equivalence)] [/.list (/.list /.nat) format.list (format.list format.nat) (random.list ..segment_size random.nat) (list.equivalence n.equivalence)] @@ -274,8 +275,8 @@ (|> expected (format.result (format.list format.nat)) (/.result (/.set n.hash /.nat)) - (!expect (^multi {try.#Failure error} - (exception.match? /.set_elements_are_not_unique error)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.set_elements_are_not_unique error)))))) (do [! random.monad] [expected (random.or random.bit random.nat)] (_.cover [/.or format.or] @@ -283,10 +284,10 @@ (format.result (format.or format.bit format.nat)) (/.result (: (/.Parser (Either Bit Nat)) (/.or /.bit /.nat))) - (!expect (^multi {try.#Success actual} - (# (sum.equivalence bit.equivalence n.equivalence) = - expected - actual)))))) + (!expect (^.multi {try.#Success actual} + (# (sum.equivalence bit.equivalence n.equivalence) = + expected + actual)))))) (do [! random.monad] [tag (# ! each (|>> (i64.and (i64.mask /.size/8)) (n.max 2)) @@ -297,8 +298,8 @@ (format.result (format.and format.bits/8 format.bit)) (/.result (: (/.Parser (Either Bit Nat)) (/.or /.bit /.nat))) - (!expect (^multi {try.#Failure error} - (exception.match? /.invalid_tag error)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.invalid_tag error)))))) (do [! random.monad] [expected (random.list ..segment_size random.nat)] (_.cover [/.rec format.rec format.and format.any] @@ -311,10 +312,10 @@ (/.or /.any (<>.and /.nat again)))))) - (!expect (^multi {try.#Success actual} - (# (list.equivalence n.equivalence) = - expected - actual)))))) + (!expect (^.multi {try.#Success actual} + (# (list.equivalence n.equivalence) = + expected + actual)))))) ))) (def: .public test @@ -332,16 +333,16 @@ (_.cover [/.binary_was_not_fully_read] (|> data (/.result /.any) - (!expect (^multi {try.#Failure error} - (exception.match? /.binary_was_not_fully_read error)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.binary_was_not_fully_read error)))))) (do [! random.monad] [expected (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))] (_.cover [/.segment format.segment format.result] (|> expected (format.result (format.segment ..segment_size)) (/.result (/.segment ..segment_size)) - (!expect (^multi {try.#Success actual} - (# binary.equivalence = expected actual)))))) + (!expect (^.multi {try.#Success actual} + (# binary.equivalence = expected actual)))))) (do [! random.monad] [data (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))] (_.cover [/.end?] diff --git a/stdlib/source/test/lux/control/parser/cli.lux b/stdlib/source/test/lux/control/parser/cli.lux index 55b57bf62..812b23586 100644 --- a/stdlib/source/test/lux/control/parser/cli.lux +++ b/stdlib/source/test/lux/control/parser/cli.lux @@ -1,22 +1,24 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - ["[0]" try] - ["<>" parser]] - [data - ["[0]" text ("[1]#[0]" equivalence)] - [collection - ["[0]" list]]] - [math - ["[0]" random] - [number - ["n" nat ("[1]#[0]" decimal)]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" try] + ["<>" parser]] + [data + ["[0]" text ("[1]#[0]" equivalence)] + [collection + ["[0]" list]]] + [macro + ["^" pattern]] + [math + ["[0]" random] + [number + ["n" nat ("[1]#[0]" decimal)]]]]] + [\\library + ["[0]" /]]) (template: (!expect <pattern> <value>) [(case <value> @@ -42,13 +44,13 @@ ($_ _.and (_.cover [/.result /.any] (|> (/.result /.any (list expected)) - (!expect (^multi {try.#Success actual} - (text#= expected actual))))) + (!expect (^.multi {try.#Success actual} + (text#= expected actual))))) (_.cover [/.parse] (|> (/.result (/.parse n#decoded) (list expected)) - (!expect (^multi {try.#Success actual} - (text#= expected - (n#encoded actual)))))) + (!expect (^.multi {try.#Success actual} + (text#= expected + (n#encoded actual)))))) (_.cover [/.this] (and (|> (/.result (/.this expected) (list expected)) (!expect {try.#Success _})) @@ -66,17 +68,17 @@ (!expect {try.#Failure _})))) (_.cover [/.named] (|> (/.result (/.named dummy /.any) (list dummy expected)) - (!expect (^multi {try.#Success actual} - (text#= expected actual))))) + (!expect (^.multi {try.#Success actual} + (text#= expected actual))))) (_.cover [/.parameter] (and (|> (/.result (/.parameter [short long] /.any) (list short expected)) - (!expect (^multi {try.#Success actual} - (text#= expected actual)))) + (!expect (^.multi {try.#Success actual} + (text#= expected actual)))) (|> (/.result (/.parameter [short long] /.any) (list long expected)) - (!expect (^multi {try.#Success actual} - (text#= expected actual)))) + (!expect (^.multi {try.#Success actual} + (text#= expected actual)))) (|> (/.result (/.parameter [short long] /.any) (list dummy expected)) (!expect {try.#Failure _})))) diff --git a/stdlib/source/test/lux/control/parser/code.lux b/stdlib/source/test/lux/control/parser/code.lux index d851a79d1..62030c6bd 100644 --- a/stdlib/source/test/lux/control/parser/code.lux +++ b/stdlib/source/test/lux/control/parser/code.lux @@ -14,6 +14,7 @@ [collection ["[0]" list]]] [macro + ["^" pattern] ["[0]" code]] [math ["[0]" random {"+" Random} ("[1]#[0]" functor)] @@ -73,8 +74,8 @@ ($_ _.and (_.cover [<query>] (|> (/.result <query> (list (<code> expected))) - (!expect (^multi {try.#Success actual} - (# <equivalence> = expected actual))))) + (!expect (^.multi {try.#Success actual} + (# <equivalence> = expected actual))))) (_.cover [<check>] (and (|> (/.result (<check> expected) (list (<code> expected))) (!expect {try.#Success []})) @@ -101,9 +102,9 @@ (|> (/.result (<query> (<>.and /.nat /.int)) (list (<code> (list (code.nat expected_left) (code.int expected_right))))) - (!expect (^multi {try.#Success [actual_left actual_right]} - (and (# nat.equivalence = expected_left actual_left) - (# int.equivalence = expected_right actual_right)))))))] + (!expect (^.multi {try.#Success [actual_left actual_right]} + (and (# nat.equivalence = expected_left actual_left) + (# int.equivalence = expected_right actual_right)))))))] [/.form code.form] [/.variant code.variant] @@ -116,9 +117,9 @@ (|> (/.result (<>.and (/.local (list (code.nat expected_local)) /.nat) /.int) (list (code.int expected_global))) - (!expect (^multi {try.#Success [actual_local actual_global]} - (and (# nat.equivalence = expected_local actual_local) - (# int.equivalence = expected_global actual_global))))))) + (!expect (^.multi {try.#Success [actual_local actual_global]} + (and (# nat.equivalence = expected_local actual_local) + (# int.equivalence = expected_global actual_global))))))) (do [! random.monad] [dummy (# ! each code.bit random.bit)] (_.cover [/.end?] @@ -129,8 +130,8 @@ (in (and (not pre) post))) (list dummy)) - (!expect (^multi {try.#Success verdict} - verdict))))) + (!expect (^.multi {try.#Success verdict} + verdict))))) (do [! random.monad] [dummy (# ! each code.bit random.bit)] (_.cover [/.end!] @@ -152,8 +153,8 @@ [expected (# ! each code.bit random.bit)] (_.cover [/.not] (and (|> (/.result (/.not /.nat) (list expected)) - (!expect (^multi {try.#Success actual} - (same? expected actual)))) + (!expect (^.multi {try.#Success actual} + (same? expected actual)))) (|> (/.result (/.not /.bit) (list expected)) (!expect {try.#Failure _}))))) )))) diff --git a/stdlib/source/test/lux/control/parser/json.lux b/stdlib/source/test/lux/control/parser/json.lux index 0ac380274..ea42e6178 100644 --- a/stdlib/source/test/lux/control/parser/json.lux +++ b/stdlib/source/test/lux/control/parser/json.lux @@ -20,6 +20,8 @@ ["[0]" sequence {"+" sequence} ("[1]#[0]" functor)]] [format ["[0]" json]]] + [macro + ["^" pattern]] [math ["[0]" random {"+" Random}] [number @@ -49,8 +51,8 @@ [expected (# ! each (|>> {json.#String}) (random.unicode 1))] (_.cover [/.result /.any] (|> (/.result /.any expected) - (!expect (^multi {try.#Success actual} - (# json.equivalence = expected actual)))))) + (!expect (^.multi {try.#Success actual} + (# json.equivalence = expected actual)))))) (_.cover [/.null] (|> (/.result /.null {json.#Null}) (!expect {try.#Success _}))) @@ -61,8 +63,8 @@ ($_ _.and (_.cover [<query>] (|> (/.result <query> {<json> expected}) - (!expect (^multi {try.#Success actual} - (# <equivalence> = expected actual))))) + (!expect (^.multi {try.#Success actual} + (# <equivalence> = expected actual))))) (_.cover [<test>] (and (|> (/.result (<test> expected) {<json> expected}) (!expect {try.#Success #1})) @@ -83,24 +85,24 @@ dummy random.bit] (_.cover [/.unexpected_value] (|> (/.result /.string {json.#Boolean dummy}) - (!expect (^multi {try.#Failure error} - (exception.match? /.unexpected_value error)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.unexpected_value error)))))) (do [! random.monad] [expected (random.unicode 1) dummy (|> (random.unicode 1) (random.only (|>> (# text.equivalence = expected) not)))] (_.cover [/.value_mismatch] (|> (/.result (/.string! expected) {json.#String dummy}) - (!expect (^multi {try.#Failure error} - (exception.match? /.value_mismatch error)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.value_mismatch error)))))) (do [! random.monad] [expected (random.unicode 1)] (_.cover [/.nullable] (and (|> (/.result (/.nullable /.string) {json.#Null}) - (!expect (^multi {try.#Success actual} - (# (maybe.equivalence text.equivalence) = {.#None} actual)))) + (!expect (^.multi {try.#Success actual} + (# (maybe.equivalence text.equivalence) = {.#None} actual)))) (|> (/.result (/.nullable /.string) {json.#String expected}) - (!expect (^multi {try.#Success actual} - (# (maybe.equivalence text.equivalence) = {.#Some expected} actual))))))) + (!expect (^.multi {try.#Success actual} + (# (maybe.equivalence text.equivalence) = {.#Some expected} actual))))))) (do [! random.monad] [size (# ! each (n.% 10) random.nat) expected (|> (random.unicode 1) @@ -109,18 +111,18 @@ (_.cover [/.array] (|> (/.result (/.array (<>.some /.string)) {json.#Array (sequence#each (|>> {json.#String}) expected)}) - (!expect (^multi {try.#Success actual} - (# (sequence.equivalence text.equivalence) = expected (sequence.of_list actual))))))) + (!expect (^.multi {try.#Success actual} + (# (sequence.equivalence text.equivalence) = expected (sequence.of_list actual))))))) (do [! random.monad] [expected (# ! each (|>> {json.#String}) (random.unicode 1))] (_.cover [/.unconsumed_input] (|> (/.result (/.array /.any) {json.#Array (sequence expected expected)}) - (!expect (^multi {try.#Failure error} - (exception.match? /.unconsumed_input error)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.unconsumed_input error)))))) (_.cover [/.empty_input] (|> (/.result (/.array /.any) {json.#Array (sequence)}) - (!expect (^multi {try.#Failure error} - (exception.match? /.empty_input error))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.empty_input error))))) (do [! random.monad] [expected_boolean random.bit expected_number ..safe_frac @@ -128,7 +130,7 @@ [boolean_field number_field string_field] (|> (random.set text.hash 3 (random.unicode 3)) (# ! each (|>> set.list (pipe.case - (^ (list boolean_field number_field string_field)) + (pattern (list boolean_field number_field string_field)) [boolean_field number_field string_field] _ @@ -143,10 +145,10 @@ (list [boolean_field {json.#Boolean expected_boolean}] [number_field {json.#Number expected_number}] [string_field {json.#String expected_string}]))}) - (!expect (^multi {try.#Success [actual_boolean actual_number actual_string]} - (and (# bit.equivalence = expected_boolean actual_boolean) - (# frac.equivalence = expected_number actual_number) - (# text.equivalence = expected_string actual_string))))))) + (!expect (^.multi {try.#Success [actual_boolean actual_number actual_string]} + (and (# bit.equivalence = expected_boolean actual_boolean) + (# frac.equivalence = expected_number actual_number) + (# text.equivalence = expected_string actual_string))))))) (do [! random.monad] [size (# ! each (n.% 10) random.nat) keys (random.list size (random.unicode 1)) @@ -159,6 +161,6 @@ (list#each (|>> {json.#String})) (list.zipped/2 keys) (dictionary.of_list text.hash))}) - (!expect (^multi {try.#Success actual} - (# (dictionary.equivalence text.equivalence) = expected actual)))))) + (!expect (^.multi {try.#Success actual} + (# (dictionary.equivalence text.equivalence) = expected actual)))))) )))) diff --git a/stdlib/source/test/lux/control/parser/synthesis.lux b/stdlib/source/test/lux/control/parser/synthesis.lux index 62a78cd0e..97d6934ed 100644 --- a/stdlib/source/test/lux/control/parser/synthesis.lux +++ b/stdlib/source/test/lux/control/parser/synthesis.lux @@ -13,6 +13,8 @@ ["[0]" text] [collection ["[0]" list ("[1]#[0]" functor)]]] + [macro + ["^" pattern]] [math ["[0]" random {"+" Random}] [number @@ -68,14 +70,14 @@ ($_ _.and (_.cover [<query>] (|> (/.result <query> (list (<synthesis> expected))) - (!expect (^multi {try.#Success actual} - (# <equivalence> = expected actual))))) + (!expect (^.multi {try.#Success actual} + (# <equivalence> = expected actual))))) (_.cover [<check>] (and (|> (/.result (<check> expected) (list (<synthesis> expected))) (!expect {try.#Success _})) (|> (/.result (<check> expected) (list (<synthesis> dummy))) - (!expect (^multi {try.#Failure error} - (exception.match? /.cannot_parse error)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.cannot_parse error)))))) ))] [/.bit /.bit! random.bit synthesis.bit bit.equivalence] @@ -102,15 +104,15 @@ (synthesis.i64 expected_i64) (synthesis.f64 expected_f64) (synthesis.text expected_text))))) - (!expect (^multi {try.#Success [actual_bit actual_i64 actual_f64 actual_text]} - (and (# bit.equivalence = expected_bit actual_bit) - (# i64.equivalence = expected_i64 actual_i64) - (# frac.equivalence = expected_f64 actual_f64) - (# text.equivalence = expected_text actual_text))))) + (!expect (^.multi {try.#Success [actual_bit actual_i64 actual_f64 actual_text]} + (and (# bit.equivalence = expected_bit actual_bit) + (# i64.equivalence = expected_i64 actual_i64) + (# frac.equivalence = expected_f64 actual_f64) + (# text.equivalence = expected_text actual_text))))) (|> (/.result (/.tuple ($_ <>.and /.bit /.i64 /.f64 /.text)) (list (synthesis.text expected_text))) - (!expect (^multi {try.#Failure error} - (exception.match? /.cannot_parse error))))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.cannot_parse error))))))) (do [! random.monad] [arity random.nat expected_environment ..random_environment @@ -118,15 +120,15 @@ (_.cover [/.function] (and (|> (/.result (/.function arity /.text) (list (synthesis.function/abstraction [expected_environment arity (synthesis.text expected_body)]))) - (!expect (^multi {try.#Success [actual_environment actual_body]} - (and (# (list.equivalence synthesis.equivalence) = - expected_environment - actual_environment) - (# text.equivalence = expected_body actual_body))))) + (!expect (^.multi {try.#Success [actual_environment actual_body]} + (and (# (list.equivalence synthesis.equivalence) = + expected_environment + actual_environment) + (# text.equivalence = expected_body actual_body))))) (|> (/.result (/.function arity /.text) (list (synthesis.text expected_body))) - (!expect (^multi {try.#Failure error} - (exception.match? /.cannot_parse error))))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.cannot_parse error))))))) (do [! random.monad] [arity random.nat expected_environment ..random_environment @@ -134,8 +136,8 @@ (_.cover [/.wrong_arity] (|> (/.result (/.function (++ arity) /.text) (list (synthesis.function/abstraction [expected_environment arity (synthesis.text expected_body)]))) - (!expect (^multi {try.#Failure error} - (exception.match? /.wrong_arity error)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.wrong_arity error)))))) (do [! random.monad] [arity (# ! each (|>> (n.% 10) ++) random.nat) expected_offset random.nat @@ -146,16 +148,16 @@ (list (synthesis.loop/scope [expected_offset (list#each (|>> synthesis.bit) expected_inits) (synthesis.text expected_body)]))) - (!expect (^multi {try.#Success [actual_offset actual_inits actual_body]} - (and (# n.equivalence = expected_offset actual_offset) - (# (list.equivalence bit.equivalence) = - expected_inits - actual_inits) - (# text.equivalence = expected_body actual_body))))) + (!expect (^.multi {try.#Success [actual_offset actual_inits actual_body]} + (and (# n.equivalence = expected_offset actual_offset) + (# (list.equivalence bit.equivalence) = + expected_inits + actual_inits) + (# text.equivalence = expected_body actual_body))))) (|> (/.result (/.loop (<>.many /.bit) /.text) (list (synthesis.text expected_body))) - (!expect (^multi {try.#Failure error} - (exception.match? /.cannot_parse error))))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.cannot_parse error))))))) )) (def: .public test @@ -167,26 +169,26 @@ [expected (# ! each (|>> synthesis.i64) random.i64)] (_.cover [/.result /.any] (|> (/.result /.any (list expected)) - (!expect (^multi {try.#Success actual} - (# synthesis.equivalence = expected actual)))))) + (!expect (^.multi {try.#Success actual} + (# synthesis.equivalence = expected actual)))))) (_.cover [/.empty_input] (|> (/.result /.any (list)) - (!expect (^multi {try.#Failure error} - (exception.match? /.empty_input error))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.empty_input error))))) (do [! random.monad] [expected (# ! each (|>> synthesis.i64) random.i64)] (_.cover [/.unconsumed_input] (|> (/.result /.any (list expected expected)) - (!expect (^multi {try.#Failure error} - (exception.match? /.unconsumed_input error)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.unconsumed_input error)))))) (do [! random.monad] [dummy (# ! each (|>> synthesis.i64) random.i64)] (_.cover [/.end! /.expected_empty_input] (and (|> (/.result /.end! (list)) (!expect {try.#Success _})) (|> (/.result /.end! (list dummy)) - (!expect (^multi {try.#Failure error} - (exception.match? /.expected_empty_input error))))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.expected_empty_input error))))))) (do [! random.monad] [dummy (# ! each (|>> synthesis.i64) random.i64)] (_.cover [/.end?] diff --git a/stdlib/source/test/lux/control/parser/text.lux b/stdlib/source/test/lux/control/parser/text.lux index 92367175a..0c49e8043 100644 --- a/stdlib/source/test/lux/control/parser/text.lux +++ b/stdlib/source/test/lux/control/parser/text.lux @@ -1,35 +1,36 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - ["[0]" maybe] - ["[0]" try {"+" Try}] - ["[0]" exception {"+" Exception}] - ["[0]" function]] - [data - ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}] - ["[0]" unicode "_" - ["[1]" set] - ["[1]/[0]" block]]] - [collection - ["[0]" set] - ["[0]" list ("[1]#[0]" functor)] - [tree - ["[0]" finger]]]] - [math - ["[0]" random] - [number {"+" hex} - ["n" nat]]] - [macro - ["[0]" code]]]] - [\\library - ["[0]" / - ["<>" // - ["<c>" code]]]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" maybe] + ["[0]" try {"+" Try}] + ["[0]" exception {"+" Exception}] + ["[0]" function]] + [data + ["[0]" text ("[1]#[0]" equivalence) + ["%" format {"+" format}] + ["[0]" unicode "_" + ["[1]" set] + ["[1]/[0]" block]]] + [collection + ["[0]" set] + ["[0]" list ("[1]#[0]" functor)] + [tree + ["[0]" finger]]]] + [math + ["[0]" random] + [number {"+" hex} + ["n" nat]]] + [macro + ["^" pattern] + ["[0]" code]]]] + [\\library + ["[0]" / + ["<>" // + ["<c>" code]]]]) (template: (!expect <pattern> <value>) [(case <value> @@ -316,13 +317,13 @@ (!expect {try.#Success []})) (|> (/.result (/.this expected) dummy) - (!expect (^multi {try.#Failure error} - (exception.match? /.cannot_match error))))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.cannot_match error))))))) (_.cover [/.Slice /.slice /.cannot_slice] (|> "" (/.result (/.slice /.any!)) - (!expect (^multi {try.#Failure error} - (exception.match? /.cannot_slice error))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.cannot_slice error))))) (do [! random.monad] [expected (random.unicode 1)] (_.cover [/.any /.any!] @@ -337,15 +338,15 @@ (and (..should_pass expected (<>.before /.any /.next)) (|> "" (/.result (<>.before /.any /.next)) - (!expect (^multi {try.#Failure error} - (exception.match? /.cannot_parse error))))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.cannot_parse error))))))) (do [! random.monad] [dummy (random.unicode 1)] (_.cover [/.unconsumed_input] (|> (format dummy dummy) (/.result /.any) - (!expect (^multi {try.#Failure error} - (exception.match? /.unconsumed_input error)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.unconsumed_input error)))))) (do [! random.monad] [sample (random.unicode 1)] (_.cover [/.Offset /.offset] @@ -393,8 +394,8 @@ (_.cover [/.then] (|> (list (code.text expected)) (<c>.result (/.then /.octal <c>.text)) - (!expect (^multi {try.#Success actual} - (text#= expected actual)))))) + (!expect (^.multi {try.#Success actual} + (text#= expected actual)))))) (do [! random.monad] [invalid (random.ascii/upper 1) expected (random.only (|>> (unicode/block.within? unicode/block.basic_latin/upper) @@ -405,14 +406,14 @@ (and (..should_pass (text.of_char expected) (/.not /.upper)) (|> invalid (/.result (/.not /.upper)) - (!expect (^multi {try.#Failure error} - (exception.match? /.expected_to_fail error)))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.expected_to_fail error)))) (..should_pass! (text.of_char expected) (/.not! upper!)) (|> invalid (/.result (/.not! upper!)) - (!expect (^multi {try.#Failure error} - (exception.match? /.expected_to_fail error))))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.expected_to_fail error))))))) (do [! random.monad] [upper (random.ascii/upper 1) lower (random.ascii/lower 1) diff --git a/stdlib/source/test/lux/control/parser/tree.lux b/stdlib/source/test/lux/control/parser/tree.lux index 18718e129..3f8bebaaf 100644 --- a/stdlib/source/test/lux/control/parser/tree.lux +++ b/stdlib/source/test/lux/control/parser/tree.lux @@ -1,23 +1,25 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - ["[0]" try] - ["[0]" exception]] - [data - [collection - ["[0]" tree - ["[0]" zipper]]]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" / - ["/[1]" //]]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" try] + ["[0]" exception]] + [data + [collection + ["[0]" tree + ["[0]" zipper]]]] + [macro + ["^" pattern]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" / + ["/[1]" //]]]) (template: (!expect <pattern> <value>) [(case <value> @@ -34,8 +36,8 @@ (_.cover <coverage> (|> (/.result <parser> <sample>) - (!expect (^multi {try.#Success actual} - (n.= expected actual))))))]) + (!expect (^.multi {try.#Success actual} + (n.= expected actual))))))]) (template: (!cover/2 <coverage> <parser> <sample0> <sample1>) [(do [! random.monad] @@ -43,11 +45,11 @@ expected (|> random.nat (random.only (|>> (n.= dummy) not)))] (_.cover <coverage> (and (|> (/.result <parser> <sample0>) - (!expect (^multi {try.#Success actual} - (n.= expected actual)))) + (!expect (^.multi {try.#Success actual} + (n.= expected actual)))) (|> (/.result <parser> <sample1>) - (!expect (^multi {try.#Success actual} - (n.= expected actual)))))))]) + (!expect (^.multi {try.#Success actual} + (n.= expected actual)))))))]) (def: .public test Test @@ -62,8 +64,8 @@ (_.cover [/.result'] (|> (/.result' /.value (zipper.zipper (tree.leaf expected))) - (!expect (^multi {try.#Success actual} - (n.= expected actual)))))) + (!expect (^.multi {try.#Success actual} + (n.= expected actual)))))) (!cover [/.down] (do //.monad [_ /.down] @@ -163,8 +165,8 @@ (`` (and (~~ (template [<parser>] [(|> (/.result <parser> (tree.leaf dummy)) - (!expect (^multi {try.#Failure error} - (exception.match? /.cannot_move_further error))))] + (!expect (^.multi {try.#Failure error} + (exception.match? /.cannot_move_further error))))] [/.down] [/.up] [/.right] [/.left] diff --git a/stdlib/source/test/lux/control/parser/type.lux b/stdlib/source/test/lux/control/parser/type.lux index 5258921b2..0a3bf5945 100644 --- a/stdlib/source/test/lux/control/parser/type.lux +++ b/stdlib/source/test/lux/control/parser/type.lux @@ -13,6 +13,8 @@ ["%" format {"+" format}]] [collection ["[0]" list]]] + [macro + ["^" pattern]] [math ["[0]" random {"+" Random}] [number @@ -49,8 +51,8 @@ (and (|> (/.result (/.exactly expected) expected) (!expect {try.#Success []})) (|> (/.result (/.exactly expected) dummy) - (!expect (^multi {try.#Failure error} - (exception.match? /.types_do_not_match error)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.types_do_not_match error)))))) (_.cover [/.sub] (and (|> (/.result (/.sub expected) expected) (!expect {try.#Success []})) @@ -59,8 +61,8 @@ (|> (/.result (/.sub expected) Nothing) (!expect {try.#Success []})) (|> (/.result (/.sub expected) dummy) - (!expect (^multi {try.#Failure error} - (exception.match? /.types_do_not_match error)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.types_do_not_match error)))))) (_.cover [/.super] (and (|> (/.result (/.super expected) expected) (!expect {try.#Success []})) @@ -69,8 +71,8 @@ (|> (/.result (/.super Nothing) expected) (!expect {try.#Success []})) (|> (/.result (/.super expected) dummy) - (!expect (^multi {try.#Failure error} - (exception.match? /.types_do_not_match error)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.types_do_not_match error)))))) ))) (def: test|aggregate @@ -84,14 +86,14 @@ [(_.cover [<parser> <exception>] (and (|> (/.result (<parser> ($_ //.and /.any /.any /.any)) (<good_constructor> (list expected_left expected_middle expected_right))) - (!expect (^multi {try.#Success [actual_left actual_middle actual_right]} - (and (type#= expected_left actual_left) - (type#= expected_middle actual_middle) - (type#= expected_right actual_right))))) + (!expect (^.multi {try.#Success [actual_left actual_middle actual_right]} + (and (type#= expected_left actual_left) + (type#= expected_middle actual_middle) + (type#= expected_right actual_right))))) (|> (/.result (<parser> ($_ //.and /.any /.any /.any)) (<bad_constructor> (list expected_left expected_middle expected_right))) - (!expect (^multi {try.#Failure error} - (exception.match? <exception> error))))))] + (!expect (^.multi {try.#Failure error} + (exception.match? <exception> error))))))] [/.variant /.not_variant type.variant type.tuple] [/.tuple /.not_tuple type.tuple type.variant] @@ -100,25 +102,25 @@ (_.cover [/.function /.not_function] (and (|> (/.result (/.function ($_ //.and /.any /.any) /.any) (type.function (list expected_left expected_middle) expected_right)) - (!expect (^multi {try.#Success [[actual_left actual_middle] actual_right]} - (and (type#= expected_left actual_left) - (type#= expected_middle actual_middle) - (type#= expected_right actual_right))))) + (!expect (^.multi {try.#Success [[actual_left actual_middle] actual_right]} + (and (type#= expected_left actual_left) + (type#= expected_middle actual_middle) + (type#= expected_right actual_right))))) (|> (/.result (/.function ($_ //.and /.any /.any) /.any) (type.variant (list expected_left expected_middle expected_right))) - (!expect (^multi {try.#Failure error} - (exception.match? /.not_function error)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.not_function error)))))) (_.cover [/.applied /.not_application] (and (|> (/.result (/.applied ($_ //.and /.any /.any /.any)) (type.application (list expected_middle expected_right) expected_left)) - (!expect (^multi {try.#Success [actual_left actual_middle actual_right]} - (and (type#= expected_left actual_left) - (type#= expected_middle actual_middle) - (type#= expected_right actual_right))))) + (!expect (^.multi {try.#Success [actual_left actual_middle actual_right]} + (and (type#= expected_left actual_left) + (type#= expected_middle actual_middle) + (type#= expected_right actual_right))))) (|> (/.result (/.applied ($_ //.and /.any /.any /.any)) (type.variant (list expected_left expected_middle expected_right))) - (!expect (^multi {try.#Failure error} - (exception.match? /.not_application error)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.not_application error)))))) )))) (def: test|parameter @@ -131,19 +133,19 @@ ($_ _.and (_.cover [/.not_parameter] (|> (/.result /.parameter not_parameter) - (!expect (^multi {try.#Failure error} - (exception.match? /.not_parameter error))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.not_parameter error))))) (_.cover [/.unknown_parameter] (|> (/.result /.parameter {.#Parameter parameter}) - (!expect (^multi {try.#Failure error} - (exception.match? /.unknown_parameter error))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.unknown_parameter error))))) (_.cover [/.with_extension] (|> (/.result (<| (/.with_extension quantification) (/.with_extension argument) /.any) not_parameter) - (!expect (^multi {try.#Success [quantification##binding argument##binding actual]} - (same? not_parameter actual))))) + (!expect (^.multi {try.#Success [quantification##binding argument##binding actual]} + (same? not_parameter actual))))) (_.cover [/.parameter] (|> (/.result (<| (/.with_extension quantification) (/.with_extension argument) @@ -162,8 +164,8 @@ _ /.any] (in (/.argument env @)))) not_parameter) - (!expect (^multi {try.#Success [_ _ _ _ actual]} - (n.= expected actual))))))] + (!expect (^.multi {try.#Success [_ _ _ _ actual]} + (n.= expected actual))))))] (and (argument? 0 2) (argument? 1 3) (argument? 2 0)))) @@ -172,8 +174,8 @@ (/.with_extension argument) (/.parameter! 1)) {.#Parameter 0}) - (!expect (^multi {try.#Failure error} - (exception.match? /.wrong_parameter error))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.wrong_parameter error))))) (_.cover [/.parameter!] (|> (/.result (<| (/.with_extension quantification) (/.with_extension argument) @@ -191,18 +193,18 @@ (_.cover [/.not_polymorphic] (and (|> (/.result (/.polymorphic /.any) not_polymorphic) - (!expect (^multi {try.#Failure error} - (exception.match? /.not_polymorphic error)))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.not_polymorphic error)))) (|> (/.result (/.polymorphic /.any) (type.univ_q 0 not_polymorphic)) - (!expect (^multi {try.#Failure error} - (exception.match? /.not_polymorphic error)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.not_polymorphic error)))))) (_.cover [/.polymorphic] (|> (/.result (/.polymorphic /.any) (type.univ_q expected_inputs not_polymorphic)) - (!expect (^multi {try.#Success [g!poly actual_inputs bodyT]} - (and (n.= expected_inputs (list.size actual_inputs)) - (same? not_polymorphic bodyT)))))) + (!expect (^.multi {try.#Success [g!poly actual_inputs bodyT]} + (and (n.= expected_inputs (list.size actual_inputs)) + (same? not_polymorphic bodyT)))))) ))) (def: test|recursive @@ -213,13 +215,13 @@ (_.cover [/.recursive] (|> (.type (Rec @ expected)) (/.result (/.recursive /.any)) - (!expect (^multi {try.#Success [@self actual]} - (type#= expected actual))))) + (!expect (^.multi {try.#Success [@self actual]} + (type#= expected actual))))) (_.cover [/.recursive_self] (|> (.type (Rec @ @)) (/.result (/.recursive /.recursive_self)) - (!expect (^multi {try.#Success [@expected @actual]} - (same? @expected @actual))))) + (!expect (^.multi {try.#Success [@expected @actual]} + (same? @expected @actual))))) (_.cover [/.recursive_call] (|> (.type (All (self input) (self input))) (/.result (/.polymorphic /.recursive_call)) @@ -227,12 +229,12 @@ (_.cover [/.not_recursive] (and (|> expected (/.result (/.recursive /.any)) - (!expect (^multi {try.#Failure error} - (exception.match? /.not_recursive error)))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.not_recursive error)))) (|> expected (/.result /.recursive_self) - (!expect (^multi {try.#Failure error} - (exception.match? /.not_recursive error)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.not_recursive error)))))) ))) (def: .public test @@ -244,8 +246,8 @@ [expected ..primitive] (_.cover [/.result /.any] (|> (/.result /.any expected) - (!expect (^multi {try.#Success actual} - (type#= expected actual)))))) + (!expect (^.multi {try.#Success actual} + (type#= expected actual)))))) (do [! random.monad] [expected ..primitive] (_.cover [/.next /.unconsumed_input] @@ -254,11 +256,11 @@ _ /.any] (in actual)) expected) - (!expect (^multi {try.#Success actual} - (type#= expected actual)))) + (!expect (^.multi {try.#Success actual} + (type#= expected actual)))) (|> (/.result /.next expected) - (!expect (^multi {try.#Failure error} - (exception.match? /.unconsumed_input error))))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.unconsumed_input error))))))) (do [! random.monad] [expected ..primitive] (_.cover [/.empty_input] @@ -267,8 +269,8 @@ [_ /.any] <parser>) expected) - (!expect (^multi {try.#Failure error} - (exception.match? /.empty_input error))))] + (!expect (^.multi {try.#Failure error} + (exception.match? /.empty_input error))))] [/.any] [/.next] @@ -281,8 +283,8 @@ _ /.any] (in env)) expected) - (!expect (^multi {try.#Success environment} - (same? /.fresh environment)))))) + (!expect (^.multi {try.#Success environment} + (same? /.fresh environment)))))) (do [! random.monad] [expected ..primitive dummy (random.only (|>> (type#= expected) not) @@ -293,15 +295,15 @@ (/.local (list expected) /.any)) dummy) - (!expect (^multi {try.#Success actual} - (type#= expected actual)))))) + (!expect (^.multi {try.#Success actual} + (type#= expected actual)))))) (do [! random.monad] [expected random.nat] (_.cover [/.existential /.not_existential] (|> (/.result /.existential {.#Ex expected}) - (!expect (^multi {try.#Success actual} - (n.= expected actual)))))) + (!expect (^.multi {try.#Success actual} + (n.= expected actual)))))) (do [! random.monad] [expected_name (random.and (random.ascii/alpha_num 1) (random.ascii/alpha_num 1)) @@ -309,9 +311,9 @@ (_.cover [/.named /.not_named] (|> (/.result /.named {.#Named expected_name expected_type}) - (!expect (^multi {try.#Success [actual_name actual_type]} - (and (symbol#= expected_name actual_name) - (type#= expected_type actual_type))))))) + (!expect (^.multi {try.#Success [actual_name actual_type]} + (and (symbol#= expected_name actual_name) + (type#= expected_type actual_type))))))) ..test|aggregate ..test|matches ..test|parameter diff --git a/stdlib/source/test/lux/control/parser/xml.lux b/stdlib/source/test/lux/control/parser/xml.lux index f3b966816..40582948d 100644 --- a/stdlib/source/test/lux/control/parser/xml.lux +++ b/stdlib/source/test/lux/control/parser/xml.lux @@ -1,31 +1,32 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - ["[0]" type ("[1]#[0]" equivalence)] - [abstract - [monad {"+" do}]] - [control - ["[0]" try ("[1]#[0]" functor)] - ["[0]" exception]] - [data - ["[0]" text ("[1]#[0]" equivalence)] - [format - ["[0]" xml ("[1]#[0]" equivalence)]] - [collection - ["[0]" dictionary] - ["[0]" list]]] - [macro - ["[0]" template]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat]]] - [meta - ["[0]" symbol ("[1]#[0]" equivalence)]]]] - [\\library - ["[0]" / - ["/[1]" // ("[1]#[0]" monad)]]]) + [library + [lux "*" + ["_" test {"+" Test}] + ["[0]" type ("[1]#[0]" equivalence)] + [abstract + [monad {"+" do}]] + [control + ["[0]" try ("[1]#[0]" functor)] + ["[0]" exception]] + [data + ["[0]" text ("[1]#[0]" equivalence)] + [format + ["[0]" xml ("[1]#[0]" equivalence)]] + [collection + ["[0]" dictionary] + ["[0]" list]]] + [macro + ["^" pattern] + ["[0]" template]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat]]] + [meta + ["[0]" symbol ("[1]#[0]" equivalence)]]]] + [\\library + ["[0]" / + ["/[1]" // ("[1]#[0]" monad)]]]) (template: (!expect <pattern> <value>) [(case <value> @@ -42,8 +43,8 @@ (_.cover [<exception>] (`` (and (~~ (template [<parser> <input>] [(|> (/.result <parser> (list <input>)) - (!expect (^multi {try.#Failure error} - (exception.match? <exception> error))))] + (!expect (^.multi {try.#Failure error} + (exception.match? <exception> error))))] <<cases>>)))))))]) @@ -64,8 +65,8 @@ [expected (random.ascii/alpha 1)] (_.cover [/.result /.text] (|> (/.result /.text (list {xml.#Text expected})) - (!expect (^multi {try.#Success actual} - (text#= expected actual)))))) + (!expect (^.multi {try.#Success actual} + (text#= expected actual)))))) (!failure /.unconsumed_inputs [[(//#in expected) {xml.#Text expected}]]) @@ -173,7 +174,7 @@ (|> (/.result parser (list (node parent (list.repeated repetitions (node wrong (list)))))) - (!expect (^multi {try.#Failure error} - (exception.match? /.nowhere error))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.nowhere error))))) )) ))) diff --git a/stdlib/source/test/lux/control/reader.lux b/stdlib/source/test/lux/control/reader.lux index e32e06bd6..7b2c8e43f 100644 --- a/stdlib/source/test/lux/control/reader.lux +++ b/stdlib/source/test/lux/control/reader.lux @@ -1,21 +1,21 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [\\specification - ["$[0]" functor {"+" Injection Comparison}] - ["$[0]" apply] - ["$[0]" monad]]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" / {"+" Reader} - [// - ["[0]" io {"+" IO}]]]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [\\specification + ["$[0]" functor {"+" Injection Comparison}] + ["$[0]" apply] + ["$[0]" monad]]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" / {"+" Reader} + [// + ["[0]" io {"+" IO}]]]]) (def: (injection value) (Injection (All (_ a r) (Reader r a))) @@ -48,7 +48,7 @@ (_.cover [/.local] (n.= (n.* factor sample) (/.result sample (/.local (n.* factor) /.read)))) - (let [(^open "io#[0]") io.monad] + (let [(open "io#[0]") io.monad] (_.cover [/.with /.lifted] (|> (: (/.Reader Any (IO Nat)) (do (/.with io.monad) diff --git a/stdlib/source/test/lux/control/remember.lux b/stdlib/source/test/lux/control/remember.lux index 2aedc2438..d7313ee0e 100644 --- a/stdlib/source/test/lux/control/remember.lux +++ b/stdlib/source/test/lux/control/remember.lux @@ -1,32 +1,32 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - ["[0]" meta] - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" io] - ["[0]" try {"+" Try}] - ["[0]" exception] - [parser - ["<[0]>" code]]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]]] - [math - [number {"+" hex}] - ["[0]" random {"+" Random} ("[1]#[0]" monad)]] - [time - ["[0]" date {"+" Date}] - ["[0]" instant] - ["[0]" duration]] - ["[0]" macro - ["[0]" code] - ["[0]" syntax {"+" syntax:}]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + ["[0]" meta] + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" io] + ["[0]" try {"+" Try}] + ["[0]" exception] + [parser + ["<[0]>" code]]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]]] + [math + [number {"+" hex}] + ["[0]" random {"+" Random} ("[1]#[0]" monad)]] + [time + ["[0]" date {"+" Date}] + ["[0]" instant] + ["[0]" duration]] + ["[0]" macro + ["[0]" code] + ["[0]" syntax {"+" syntax:}]]]] + [\\library + ["[0]" /]]) (def: deadline (Random Date) random.date) (def: message (Random Text) (random#each %.bit random.bit)) @@ -92,13 +92,13 @@ _ false) (case should_succeed0 - (^ {try.#Success (list)}) + (pattern {try.#Success (list)}) true _ false) (case should_succeed1 - (^ {try.#Success (list actual)}) + (pattern {try.#Success (list actual)}) (same? expected actual) _ diff --git a/stdlib/source/test/lux/control/security/policy.lux b/stdlib/source/test/lux/control/security/policy.lux index 34b24c1f4..6ced1e85c 100644 --- a/stdlib/source/test/lux/control/security/policy.lux +++ b/stdlib/source/test/lux/control/security/policy.lux @@ -11,6 +11,8 @@ ["$[0]" monad]]] [data ["[0]" text ("[1]#[0]" equivalence)]] + [macro + ["^" pattern]] [math ["[0]" random] [number @@ -48,7 +50,7 @@ (Ex (_ %) (-> Any (Policy %))) (/.with_policy (: (Context Privacy Policy) - (function (_ (^let privilege (^open "%[0]"))) + (function (_ (^.let privilege (open "%[0]"))) (implementation (def: &hash (implementation diff --git a/stdlib/source/test/lux/control/state.lux b/stdlib/source/test/lux/control/state.lux index 39e10983a..9cc2cac76 100644 --- a/stdlib/source/test/lux/control/state.lux +++ b/stdlib/source/test/lux/control/state.lux @@ -106,7 +106,7 @@ [state random.nat left random.nat right random.nat] - (let [(^open "io#[0]") io.monad] + (let [(open "io#[0]") io.monad] (_.cover [/.+State /.with /.lifted /.result'] (|> (: (/.+State io.IO Nat Nat) (do (/.with io.monad) diff --git a/stdlib/source/test/lux/control/try.lux b/stdlib/source/test/lux/control/try.lux index b3efe3dd2..a606da407 100644 --- a/stdlib/source/test/lux/control/try.lux +++ b/stdlib/source/test/lux/control/try.lux @@ -44,7 +44,7 @@ [expected random.nat alternative (|> random.nat (random.only (|>> (n.= expected) not))) error (random.unicode 1) - .let [(^open "io#[0]") io.monad]]) + .let [(open "io#[0]") io.monad]]) ($_ _.and (_.for [/.equivalence] ($equivalence.spec (/.equivalence n.equivalence) (..attempt random.nat))) diff --git a/stdlib/source/test/lux/control/writer.lux b/stdlib/source/test/lux/control/writer.lux index 63c59adb0..2e8989f1f 100644 --- a/stdlib/source/test/lux/control/writer.lux +++ b/stdlib/source/test/lux/control/writer.lux @@ -1,26 +1,26 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [equivalence {"+" Equivalence}] - [monoid {"+" Monoid}] - [monad {"+" do}] - [\\specification - ["$[0]" functor {"+" Injection Comparison}] - ["$[0]" apply] - ["$[0]" monad]]] - [control - ["[0]" io]] - [data - ["[0]" product] - ["[0]" text ("[1]#[0]" equivalence)]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" / {"+" Writer}]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [equivalence {"+" Equivalence}] + [monoid {"+" Monoid}] + [monad {"+" do}] + [\\specification + ["$[0]" functor {"+" Injection Comparison}] + ["$[0]" apply] + ["$[0]" monad]]] + [control + ["[0]" io]] + [data + ["[0]" product] + ["[0]" text ("[1]#[0]" equivalence)]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" / {"+" Writer}]]) (def: (injection monoid value) (All (_ w) (-> (Monoid w) (Injection (Writer w)))) @@ -52,7 +52,7 @@ (product.left (/.write log)))) (_.cover [/.with /.lifted] (let [lifted (/.lifted text.monoid io.monad) - (^open "io#[0]") io.monad] + (open "io#[0]") io.monad] (|> (do (/.with text.monoid io.monad) [a (lifted (io#in left)) b (in right)] diff --git a/stdlib/source/test/lux/data/collection/array.lux b/stdlib/source/test/lux/data/collection/array.lux index 2e2904b3d..b41a178d2 100644 --- a/stdlib/source/test/lux/data/collection/array.lux +++ b/stdlib/source/test/lux/data/collection/array.lux @@ -62,7 +62,7 @@ the_array (random.array size random.nat) evens (random.array size (random.only n.even? random.nat))] ($_ _.and - (let [(^open "/#[0]") /.functor + (let [(open "/#[0]") /.functor choose (: (-> Nat (Maybe Text)) (function (_ value) (if (n.even? value) @@ -156,9 +156,9 @@ (!.empty size))))) (_.cover [!.type] (case !.Array - (^ (<| {.#Named (symbol !.Array)} - {.#UnivQ (list)} - {.#Primitive nominal_type (list {.#Parameter 1})})) + (pattern (<| {.#Named (symbol !.Array)} + {.#UnivQ (list)} + {.#Primitive nominal_type (list {.#Parameter 1})})) (same? !.type nominal_type) _ @@ -324,10 +324,10 @@ (/.empty size))))) (_.cover [/.type_name] (case /.Array - (^ (<| {.#Named (symbol /.Array)} - {.#Named (symbol !.Array)} - {.#UnivQ (list)} - {.#Primitive nominal_type (list {.#Parameter 1})})) + (pattern (<| {.#Named (symbol /.Array)} + {.#Named (symbol !.Array)} + {.#UnivQ (list)} + {.#Primitive nominal_type (list {.#Parameter 1})})) (same? /.type_name nominal_type) _ diff --git a/stdlib/source/test/lux/data/collection/dictionary.lux b/stdlib/source/test/lux/data/collection/dictionary.lux index 4dec751e4..1054e5248 100644 --- a/stdlib/source/test/lux/data/collection/dictionary.lux +++ b/stdlib/source/test/lux/data/collection/dictionary.lux @@ -1,28 +1,28 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [hash {"+" Hash}] - [monad {"+" do}] - [\\specification - ["$[0]" equivalence] - ["$[0]" functor {"+" Injection}]]] - [control - ["[0]" maybe ("[1]#[0]" functor)] - ["[0]" try] - ["[0]" exception]] - [data - ["[0]" product] - [collection - ["[0]" list ("[1]#[0]" functor)] - ["[0]" set]]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [hash {"+" Hash}] + [monad {"+" do}] + [\\specification + ["$[0]" equivalence] + ["$[0]" functor {"+" Injection}]]] + [control + ["[0]" maybe ("[1]#[0]" functor)] + ["[0]" try] + ["[0]" exception]] + [data + ["[0]" product] + [collection + ["[0]" list ("[1]#[0]" functor)] + ["[0]" set]]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]]) (def: injection (Injection (/.Dictionary Nat)) @@ -109,12 +109,12 @@ (list.size (/.values dict)))) (_.cover [/.merged] - (let [merging_with_oneself (let [(^open "[0]") (/.equivalence n.equivalence)] + (let [merging_with_oneself (let [(open "[0]") (/.equivalence n.equivalence)] (= dict (/.merged dict dict))) overwritting_keys (let [dict' (|> dict /.entries (list#each (function (_ [k v]) [k (++ v)])) (/.of_list n.hash)) - (^open "[0]") (/.equivalence n.equivalence)] + (open "[0]") (/.equivalence n.equivalence)] (= dict' (/.merged dict' dict)))] (and merging_with_oneself overwritting_keys))) @@ -125,7 +125,7 @@ (/.values (/.merged_with n.+ dict dict))))) (_.cover [/.of_list] - (let [(^open "[0]") (/.equivalence n.equivalence)] + (let [(open "[0]") (/.equivalence n.equivalence)] (and (= dict dict) (|> dict /.entries (/.of_list n.hash) (= dict))))) ))) diff --git a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux index 5c8f43b56..3e628ec45 100644 --- a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux +++ b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux @@ -1,27 +1,27 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [equivalence {"+" Equivalence}] - [order {"+" Order}] - [\\specification - ["$[0]" equivalence]]] - [control - ["[0]" maybe ("[1]#[0]" monad)]] - [data - ["[0]" product] - ["[0]" bit ("[1]#[0]" equivalence)] - [collection - ["[0]" set] - ["[0]" list ("[1]#[0]" functor)]]] - [math - ["[0]" random {"+" Random} ("[1]#[0]" monad)] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [equivalence {"+" Equivalence}] + [order {"+" Order}] + [\\specification + ["$[0]" equivalence]]] + [control + ["[0]" maybe ("[1]#[0]" monad)]] + [data + ["[0]" product] + ["[0]" bit ("[1]#[0]" equivalence)] + [collection + ["[0]" set] + ["[0]" list ("[1]#[0]" functor)]]] + [math + ["[0]" random {"+" Random} ("[1]#[0]" monad)] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]]) (def: .public (dictionary order gen_key gen_value size) (All (_ k v) @@ -57,11 +57,11 @@ (n.< left right)) pairs) sorted_values (list#each product.right sorted_pairs) - (^open "list#[0]") (list.equivalence (: (Equivalence [Nat Nat]) - (function (_ [kr vr] [ks vs]) - (and (n.= kr ks) - (n.= vr vs))))) - (^open "/#[0]") (/.equivalence n.equivalence)]] + (open "list#[0]") (list.equivalence (: (Equivalence [Nat Nat]) + (function (_ [kr vr] [ks vs]) + (and (n.= kr ks) + (n.= vr vs))))) + (open "/#[0]") (/.equivalence n.equivalence)]] ($_ _.and (_.for [/.equivalence] ($equivalence.spec (/.equivalence n.equivalence) (..dictionary n.order random.nat random.nat size))) diff --git a/stdlib/source/test/lux/data/collection/list.lux b/stdlib/source/test/lux/data/collection/list.lux index e4d2bb2aa..88ce2f5b9 100644 --- a/stdlib/source/test/lux/data/collection/list.lux +++ b/stdlib/source/test/lux/data/collection/list.lux @@ -69,7 +69,7 @@ [parameter random.nat subject random.nat] (let [lifted (/.lifted io.monad) - (^open "io#[0]") io.monad + (open "io#[0]") io.monad expected (n.+ parameter subject)] (_.cover [/.with /.lifted] (|> (io.run! (do (/.with io.monad) @@ -77,7 +77,7 @@ b (in subject)] (in (n.+ a b)))) (pipe.case - (^ (list actual)) + (pattern (list actual)) (n.= expected actual) _ @@ -88,7 +88,7 @@ Test (do [! random.monad] [size ..bounded_size - .let [(^open "/#[0]") (/.equivalence n.equivalence)] + .let [(open "/#[0]") (/.equivalence n.equivalence)] sample (# ! each set.list (random.set n.hash size random.nat))] ($_ _.and (_.cover [/.size] @@ -130,8 +130,8 @@ (def: indices Test - (let [(^open "/#[0]") (/.equivalence n.equivalence) - (^open "/#[0]") /.functor] + (let [(open "/#[0]") (/.equivalence n.equivalence) + (open "/#[0]") /.functor] (do [! random.monad] [sample ..random .let [size (/.size sample)]] @@ -190,8 +190,8 @@ (def: slice Test - (let [(^open "/#[0]") (/.equivalence n.equivalence) - (^open "/#[0]") /.monoid] + (let [(open "/#[0]") (/.equivalence n.equivalence) + (open "/#[0]") /.monoid] (do [! random.monad] [sample (random.only (|>> /.size (n.> 0)) ..random) @@ -239,7 +239,7 @@ (def: member Test - (let [(^open "/#[0]") (/.equivalence n.equivalence)] + (let [(open "/#[0]") (/.equivalence n.equivalence)] (do [! random.monad] [sample ..random] (`` ($_ _.and @@ -277,9 +277,9 @@ (def: grouping Test - (let [(^open "/#[0]") (/.equivalence n.equivalence) - (^open "/#[0]") /.functor - (^open "/#[0]") /.monoid + (let [(open "/#[0]") (/.equivalence n.equivalence) + (open "/#[0]") /.functor + (open "/#[0]") /.monoid +/2 (: (-> Nat Nat Nat) (function (_ left right) @@ -372,7 +372,7 @@ (def: search Test - (let [(^open "/#[0]") /.functor + (let [(open "/#[0]") /.functor choice (: (-> Nat (Maybe Text)) (function (_ value) @@ -415,8 +415,8 @@ Test (<| (_.covering /._) (_.for [.List]) - (let [(^open "/#[0]") (/.equivalence n.equivalence) - (^open "/#[0]") /.functor] + (let [(open "/#[0]") (/.equivalence n.equivalence) + (open "/#[0]") /.functor] (do [! random.monad] [sample ..random separator random.nat] @@ -454,7 +454,7 @@ (/.mixes n.+ 0 sample))) (do random.monad [expected random.nat - .let [(^open "/#[0]") (/.equivalence n.equivalence)]] + .let [(open "/#[0]") (/.equivalence n.equivalence)]] (_.cover [/.when] (and (/#= (list expected) (/.when true (list expected))) (/#= (list) (/.when false (list expected)))))) diff --git a/stdlib/source/test/lux/data/collection/sequence.lux b/stdlib/source/test/lux/data/collection/sequence.lux index 220581bd2..125dfaac9 100644 --- a/stdlib/source/test/lux/data/collection/sequence.lux +++ b/stdlib/source/test/lux/data/collection/sequence.lux @@ -52,7 +52,7 @@ [size (# ! each (n.% 100) random.nat) sample (random.set n.hash size random.nat) .let [sample (|> sample set.list /.of_list)] - .let [(^open "/#[0]") (/.equivalence n.equivalence)]] + .let [(open "/#[0]") (/.equivalence n.equivalence)]] ($_ _.and (_.cover [/.size] (n.= size (/.size sample))) @@ -146,7 +146,7 @@ non_member (random.only (|>> (set.member? sample) not) random.nat) .let [sample (|> sample set.list /.of_list)] - .let [(^open "/#[0]") (/.equivalence n.equivalence)]] + .let [(open "/#[0]") (/.equivalence n.equivalence)]] ($_ _.and (do ! [value/0 random.nat @@ -194,7 +194,7 @@ (n.+ (/.size positives) (/.size negatives)))))) (_.cover [/.one] - (let [(^open "/#[0]") /.functor + (let [(open "/#[0]") /.functor choice (: (-> Nat (Maybe Text)) (function (_ value) (if (n.even? value) diff --git a/stdlib/source/test/lux/data/collection/set/ordered.lux b/stdlib/source/test/lux/data/collection/set/ordered.lux index 81626777f..04a3eed86 100644 --- a/stdlib/source/test/lux/data/collection/set/ordered.lux +++ b/stdlib/source/test/lux/data/collection/set/ordered.lux @@ -1,23 +1,23 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [order {"+" Order}] - [\\specification - ["$[0]" equivalence]]] - [data - ["[0]" bit ("[1]#[0]" equivalence)] - [collection - ["[0]" list]]] - [math - ["[0]" random {"+" Random} ("[1]#[0]" monad)] - [number - ["n" nat]]]]] - [\\library - ["[0]" / {"+" Set} - ["[0]" //]]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [order {"+" Order}] + [\\specification + ["$[0]" equivalence]]] + [data + ["[0]" bit ("[1]#[0]" equivalence)] + [collection + ["[0]" list]]] + [math + ["[0]" random {"+" Random} ("[1]#[0]" monad)] + [number + ["n" nat]]]]] + [\\library + ["[0]" / {"+" Set} + ["[0]" //]]]) (def: size (random.Random Nat) @@ -48,7 +48,7 @@ random.nat) .let [listL (//.list usetL)] listR (|> (random.set n.hash sizeR random.nat) (# ! each //.list)) - .let [(^open "/#[0]") /.equivalence + .let [(open "/#[0]") /.equivalence setL (/.of_list n.order listL) setR (/.of_list n.order listR) empty (/.empty n.order)]] diff --git a/stdlib/source/test/lux/data/collection/stream.lux b/stdlib/source/test/lux/data/collection/stream.lux index c959de821..d7fa8a191 100644 --- a/stdlib/source/test/lux/data/collection/stream.lux +++ b/stdlib/source/test/lux/data/collection/stream.lux @@ -1,25 +1,25 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [equivalence {"+" Equivalence}] - ["[0]" enum] - [\\specification - ["$[0]" functor] - ["$[0]" comonad]]] - [data - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [equivalence {"+" Equivalence}] + ["[0]" enum] + [\\specification + ["$[0]" functor] + ["$[0]" comonad]]] + [data + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]]) (implementation: (equivalence super) (All (_ a) (-> (Equivalence a) (Equivalence (/.Stream a)))) @@ -42,7 +42,7 @@ Test (<| (_.covering /._) (_.for [/.Stream]) - (let [(^open "list#[0]") (list.equivalence n.equivalence)]) + (let [(open "list#[0]") (list.equivalence n.equivalence)]) (do [! random.monad] [repeated random.nat index (# ! each (n.% 100) random.nat) @@ -103,8 +103,8 @@ (n.= (++ (n.* 2 offset)) (/.item offset odds))))) (_.cover [/.iterations] - (let [(^open "/#[0]") /.functor - (^open "list#[0]") (list.equivalence text.equivalence)] + (let [(open "/#[0]") /.functor + (open "list#[0]") (list.equivalence text.equivalence)] (list#= (/.first size (/#each %.nat (..iterations ++ offset))) (/.first size @@ -115,8 +115,8 @@ (list#= (list.together (list.repeated size cycle)) (/.first (n.* size (list.size cycle)) (/.cycle [cycle_start cycle_next]))))) - (_.cover [/.^stream&] - (let [(/.^stream& first second third next) (..iterations ++ offset)] + (_.cover [/.pattern] + (let [(/.pattern first second third next) (..iterations ++ offset)] (and (n.= offset first) (n.= (n.+ 1 offset) second) (n.= (n.+ 2 offset) third)))) diff --git a/stdlib/source/test/lux/data/collection/tree/zipper.lux b/stdlib/source/test/lux/data/collection/tree/zipper.lux index 111597da6..b39f5ea63 100644 --- a/stdlib/source/test/lux/data/collection/tree/zipper.lux +++ b/stdlib/source/test/lux/data/collection/tree/zipper.lux @@ -159,8 +159,8 @@ [[size sample] (//.tree random.nat) expected random.nat dummy (random.only (|>> (n.= expected) not) random.nat) - .let [(^open "tree#[0]") (tree.equivalence n.equivalence) - (^open "list#[0]") (list.equivalence n.equivalence)]] + .let [(open "tree#[0]") (tree.equivalence n.equivalence) + (open "list#[0]") (list.equivalence n.equivalence)]] ($_ _.and (_.for [/.equivalence] ($equivalence.spec (/.equivalence n.equivalence) (# ! each (|>> product.right /.zipper) (//.tree random.nat)))) diff --git a/stdlib/source/test/lux/data/color.lux b/stdlib/source/test/lux/data/color.lux index 9223e6b47..8df8e5813 100644 --- a/stdlib/source/test/lux/data/color.lux +++ b/stdlib/source/test/lux/data/color.lux @@ -1,27 +1,27 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [\\specification - ["$[0]" equivalence] - ["$[0]" hash] - ["$[0]" monoid]]] - [data - [collection - ["[0]" list]]] - [macro - ["[0]" template]] - ["[0]" math - ["[0]" random {"+" Random}] - [number - ["n" nat] - ["[0]" int] - ["f" frac] - ["r" rev]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [\\specification + ["$[0]" equivalence] + ["$[0]" hash] + ["$[0]" monoid]]] + [data + [collection + ["[0]" list]]] + [macro + ["[0]" template]] + ["[0]" math + ["[0]" random {"+" Random}] + [number + ["n" nat] + ["[0]" int] + ["f" frac] + ["r" rev]]]]] + [\\library + ["[0]" /]]) (def: .public random (Random /.Color) @@ -195,7 +195,7 @@ (..encoding expected) (_.cover [/.complement] (let [~expected (/.complement expected) - (^open "/#[0]") /.equivalence] + (open "/#[0]") /.equivalence] (and (not (/#= expected ~expected)) (/#= expected (/.complement ~expected))))) (_.cover [/.black /.white] diff --git a/stdlib/source/test/lux/data/format/tar.lux b/stdlib/source/test/lux/data/format/tar.lux index 9bb1e6ea0..f09796461 100644 --- a/stdlib/source/test/lux/data/format/tar.lux +++ b/stdlib/source/test/lux/data/format/tar.lux @@ -175,7 +175,7 @@ (format.result /.writer) (<b>.result /.parser))] (in (case (sequence.list tar) - (^ (list {<tag> actual_path})) + (pattern (list {<tag> actual_path})) (text#= (/.from_path expected_path) (/.from_path actual_path)) @@ -204,7 +204,7 @@ (format.result /.writer) (<b>.result /.parser))] (in (case (sequence.list tar) - (^ (list {<tag> [actual_path actual_moment actual_mode actual_ownership actual_content]})) + (pattern (list {<tag> [actual_path actual_moment actual_mode actual_ownership actual_content]})) (let [seconds (: (-> Instant Int) (|>> instant.relative (duration.ticks duration.second)))] (and (text#= (/.from_path expected_path) @@ -262,7 +262,7 @@ (format.result /.writer) (<b>.result /.parser))] (in (case (sequence.list tar) - (^ (list {/.#Normal [_ _ actual_mode _ _]})) + (pattern (list {/.#Normal [_ _ actual_mode _ _]})) (n.= (/.mode expected_mode) (/.mode actual_mode)) @@ -285,7 +285,7 @@ (format.result /.writer) (<b>.result /.parser))] (in (case (sequence.list tar) - (^ (list {/.#Normal [_ _ actual_mode _ _]})) + (pattern (list {/.#Normal [_ _ actual_mode _ _]})) (n.= (/.mode <expected_mode>) (/.mode actual_mode)) @@ -352,7 +352,7 @@ (format.result /.writer) (<b>.result /.parser))] (in (case (sequence.list tar) - (^ (list {/.#Normal [_ _ _ actual_ownership _]})) + (pattern (list {/.#Normal [_ _ _ actual_ownership _]})) (and (text#= (/.from_name expected) (/.from_name (the [/.#user /.#name] actual_ownership))) (text#= (/.from_name /.anonymous) @@ -376,7 +376,7 @@ (format.result /.writer) (<b>.result /.parser))] (in (case (sequence.list tar) - (^ (list {/.#Normal [_ _ _ actual_ownership _]})) + (pattern (list {/.#Normal [_ _ _ actual_ownership _]})) (and (text#= (/.from_name /.anonymous) (/.from_name (the [/.#user /.#name] actual_ownership))) (n.= (/.from_small /.no_id) diff --git a/stdlib/source/test/lux/data/format/xml.lux b/stdlib/source/test/lux/data/format/xml.lux index 439fe1f5c..c547d400c 100644 --- a/stdlib/source/test/lux/data/format/xml.lux +++ b/stdlib/source/test/lux/data/format/xml.lux @@ -18,6 +18,8 @@ [collection ["[0]" dictionary] ["[0]" list ("[1]#[0]" functor)]]] + [macro + ["^" pattern]] [math ["[0]" random {"+" Random} ("[1]#[0]" monad)] [number @@ -77,7 +79,7 @@ ($codec.spec /.equivalence /.codec ..random)) (do [! random.monad] - [(^let symbol [namespace name]) ..symbol] + [(^.let symbol [namespace name]) ..symbol] (`` ($_ _.and (~~ (template [<type> <format>] [(_.cover [<type> <format>] diff --git a/stdlib/source/test/lux/data/text.lux b/stdlib/source/test/lux/data/text.lux index ed6cc5d9d..8503e08ac 100644 --- a/stdlib/source/test/lux/data/text.lux +++ b/stdlib/source/test/lux/data/text.lux @@ -285,7 +285,7 @@ sampleR (random.unicode sizeR) middle (random.unicode 1) .let [sample (/.together (list sampleL sampleR)) - (^open "/#[0]") /.equivalence]] + (open "/#[0]") /.equivalence]] ($_ _.and (_.cover [/.split_at] (|> (/.split_at sizeL sample) @@ -326,7 +326,7 @@ parts (random.list sizeL part_gen) .let [sample1 (/.together (list.interposed sep1 parts)) sample2 (/.together (list.interposed sep2 parts)) - (^open "/#[0]") /.equivalence]] + (open "/#[0]") /.equivalence]] (_.cover [/.replaced] (/#= sample2 (/.replaced sep1 sep2 sample1)))) diff --git a/stdlib/source/test/lux/data/text/regex.lux b/stdlib/source/test/lux/data/text/regex.lux index 0ab71cbaa..58c26d067 100644 --- a/stdlib/source/test/lux/data/text/regex.lux +++ b/stdlib/source/test/lux/data/text/regex.lux @@ -62,7 +62,7 @@ (in (list (` (|> (~ input) (<text>.result (~ regex)) (pipe.case - (^ {try.#Success (~ pattern)}) + (pattern {try.#Success (~ pattern)}) true (~ g!_) @@ -305,10 +305,10 @@ [sample1 (random.unicode 3) sample2 (random.unicode 3) sample3 (random.unicode 4)] - (_.cover [/.^regex] + (_.cover [/.pattern] (case (format sample1 "-" sample2 "-" sample3) - (/.^regex "(.{3})-(.{3})-(.{4})" - [_ match1 match2 match3]) + (/.pattern "(.{3})-(.{3})-(.{4})" + [_ match1 match2 match3]) (and (text#= sample1 match1) (text#= sample2 match2) (text#= sample3 match3)) diff --git a/stdlib/source/test/lux/documentation.lux b/stdlib/source/test/lux/documentation.lux index 692b28b43..9e6566d91 100644 --- a/stdlib/source/test/lux/documentation.lux +++ b/stdlib/source/test/lux/documentation.lux @@ -53,7 +53,7 @@ ($_ _.and (_.cover [/.default] (case (`` (/.default (~~ (template.symbol [.._] [g!default])))) - (^ (list definition)) + (pattern (list definition)) (and (|> definition (the /.#definition) (text#= (template.text [g!default]))) @@ -67,7 +67,7 @@ false)) (_.cover [/.documentation:] (case ..documentation: - (^ (list documentation:)) + (pattern (list documentation:)) (and (|> documentation: (the /.#definition) (text#= (template.text [/.documentation:]))) @@ -97,7 +97,7 @@ (text.contains? (template.text ['super_description']) (/.documentation super)) (case ..documentation: - (^ (list documentation:)) + (pattern (list documentation:)) (text.contains? (md.markdown (the /.#documentation documentation:)) (/.documentation super)) diff --git a/stdlib/source/test/lux/macro.lux b/stdlib/source/test/lux/macro.lux index f2e29ec1a..5cb684336 100644 --- a/stdlib/source/test/lux/macro.lux +++ b/stdlib/source/test/lux/macro.lux @@ -15,6 +15,8 @@ ["%" format {"+" format}]] [collection ["[0]" list]]] + [macro + ["^" pattern]] [math ["[0]" random {"+" Random} ("[1]#[0]" functor)] [number @@ -31,7 +33,8 @@ ["[1][0]" code] ["[1][0]" local] ["[1][0]" syntax] - ["[1][0]" template]]) + ["[1][0]" template] + ["[1][0]" pattern]]) (template: (!expect <pattern> <value>) [(case <value> @@ -169,7 +172,7 @@ <actual> (/.times <cycles> (..iterated <max> <expected>))] (let [expected_remaining (n.- <cycles> <max>)] (case (` <actual>) - (^code (..iterated (~ [_ {.#Nat actual_remaining}]) (~ [_ {.#Nat actual}]))) + (^.` (..iterated (~ [_ {.#Nat actual_remaining}]) (~ [_ {.#Nat actual}]))) (and (n.= expected_remaining actual_remaining) (n.= <expected> actual)) @@ -188,23 +191,23 @@ (|> (/.symbol symbol_prefix) (# meta.monad each %.code) (meta.result lux) - (!expect (^multi {try.#Success actual_symbol} - (and (text.contains? symbol_prefix actual_symbol) - (text.contains? (%.nat seed) actual_symbol)))))) + (!expect (^.multi {try.#Success actual_symbol} + (and (text.contains? symbol_prefix actual_symbol) + (text.contains? (%.nat seed) actual_symbol)))))) (_.cover [/.wrong_syntax_error] (|> (/.single_expansion (` (/.log_single_expansion!))) (meta.result lux) - (!expect (^multi {try.#Failure error} - (text.contains? (/.wrong_syntax_error (symbol /.log_single_expansion!)) - error))))) + (!expect (^.multi {try.#Failure error} + (text.contains? (/.wrong_syntax_error (symbol /.log_single_expansion!)) + error))))) (_.cover [/.with_symbols] (with_expansions [<expected> (fresh_symbol)] (|> (/.with_symbols [<expected>] (# meta.monad in <expected>)) (meta.result lux) - (!expect (^multi {try.#Success [_ {.#Symbol ["" actual]}]} - (text.contains? (template.text [<expected>]) - actual)))))) + (!expect (^.multi {try.#Success [_ {.#Symbol ["" actual]}]} + (text.contains? (template.text [<expected>]) + actual)))))) )) ..test|expansion @@ -213,4 +216,5 @@ /local.test /syntax.test /template.test + /pattern.test ))) diff --git a/stdlib/source/test/lux/macro/pattern.lux b/stdlib/source/test/lux/macro/pattern.lux new file mode 100644 index 000000000..d5b7b9dcb --- /dev/null +++ b/stdlib/source/test/lux/macro/pattern.lux @@ -0,0 +1,98 @@ +(.using + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [data + ["[0]" bit ("[1]#[0]" equivalence)]] + [macro + ["[0]" code]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat] + ["i" int] + ["f" frac]]]]] + [\\library + ["[0]" /]]) + +(type: (Pair l r) + (Record + [#left l + #right r])) + +(template: (!pair <left> <right>) + [[..#left <left> + ..#right <right>]]) + +(def: .public test + Test + (<| (_.covering /._) + (do [! random.monad] + [expected_nat (# ! each (n.% 1) random.nat) + expected_int (# ! each (i.% +1) random.int) + expected_rev (random.either (in .5) + (in .25)) + expected_frac (random.either (in +0.5) + (in +1.25)) + expected_text (random.either (in "+0.5") + (in "+1.25"))] + ($_ _.and + (do [! random.monad] + [sample (# ! each (n.% 5) random.nat)] + (_.cover [/.template] + (case sample + (/.template [<case>] + [<case> true]) + ([0] [1] [2] [3] [4]) + + _ + false))) + (_.cover [/.or] + (and (/.case expected_rev + (/.or .5 .25) true + _ false) + (/.case expected_frac + (/.or +0.5 +1.25) true + _ false) + (/.case expected_text + (/.or "+0.5" "+1.25") true + _ false))) + (_.cover [/.let] + (let [expected_pair (: (Pair Nat Int) + [..#left expected_nat ..#right expected_int])] + (/.case expected_pair + (/.let actual_pair (/.pattern (!pair actual_left actual_right))) + (and (/.same? expected_pair actual_pair) + (/.same? expected_nat actual_left) + (/.same? expected_int actual_right))))) + (_.cover [/.multi] + (let [expected_pair (: (Pair Nat Int) + [..#left expected_nat ..#right expected_int])] + (and (/.case expected_pair + (/.multi (/.pattern (!pair 0 actual_right)) + [actual_right + +0]) + true + + _ + false) + (/.case expected_pair + (/.multi (/.pattern (!pair 0 actual_right)) + (i.= +0 actual_right)) + true + + _ + false)))) + (_.cover [/.|>] + (case expected_frac + (/.|> actual_frac [(f.* +2.0) (f.* +2.0)]) + (f.= (f.* +4.0 expected_frac) + actual_frac))) + (_.cover [/.`] + (case (code.text expected_text) + (/.` "+0.5") true + (/.` "+1.25") true + _ false)) + )))) diff --git a/stdlib/source/test/lux/math/logic/fuzzy.lux b/stdlib/source/test/lux/math/logic/fuzzy.lux index aa53e0e20..3c7b34b10 100644 --- a/stdlib/source/test/lux/math/logic/fuzzy.lux +++ b/stdlib/source/test/lux/math/logic/fuzzy.lux @@ -1,27 +1,27 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [equivalence {"+" Equivalence}] - [monad {"+" do}] - [\\specification - [functor - ["$[0]" contravariant]]]] - [data - ["[0]" bit ("[1]#[0]" equivalence)] - [collection - ["[0]" list] - ["[0]" set]]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat] - ["r" rev]]]]] - [\\library - ["[0]" / {"+" Fuzzy} - ["/[1]" // "_" - ["[1]" continuous]]]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [equivalence {"+" Equivalence}] + [monad {"+" do}] + [\\specification + [functor + ["$[0]" contravariant]]]] + [data + ["[0]" bit ("[1]#[0]" equivalence)] + [collection + ["[0]" list] + ["[0]" set]]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat] + ["r" rev]]]]] + [\\library + ["[0]" / {"+" Fuzzy} + ["/[1]" // "_" + ["[1]" continuous]]]]) (def: trivial Test @@ -92,7 +92,7 @@ (# ! each (|>> set.list (list.sorted r.<))) (random.one (function (_ thresholds) (case thresholds - (^ (list threshold_0 threshold_1 threshold_2 threshold_3)) + (pattern (list threshold_0 threshold_1 threshold_2 threshold_3)) {.#Some [threshold_0 threshold_1 threshold_2 threshold_3]} _ @@ -176,7 +176,7 @@ (# ! each (|>> set.list (list.sorted r.<))) (random.one (function (_ thresholds) (case thresholds - (^ (list threshold_0 threshold_1 threshold_2 threshold_3)) + (pattern (list threshold_0 threshold_1 threshold_2 threshold_3)) {.#Some [threshold_0 threshold_1 threshold_2 threshold_3]} _ diff --git a/stdlib/source/test/lux/math/number/int.lux b/stdlib/source/test/lux/math/number/int.lux index 2c47ee6d1..4a6b893f4 100644 --- a/stdlib/source/test/lux/math/number/int.lux +++ b/stdlib/source/test/lux/math/number/int.lux @@ -77,7 +77,7 @@ Test (<| (_.covering /._) (_.for [.Int]) - (let [(^open "/#[0]") /.interval]) + (let [(open "/#[0]") /.interval]) ($_ _.and (do random.monad [sample random.int diff --git a/stdlib/source/test/lux/math/number/ratio.lux b/stdlib/source/test/lux/math/number/ratio.lux index 276ccf956..d9c1c1ba8 100644 --- a/stdlib/source/test/lux/math/number/ratio.lux +++ b/stdlib/source/test/lux/math/number/ratio.lux @@ -1,24 +1,24 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [\\specification - ["$[0]" equivalence] - ["$[0]" order] - ["$[0]" monoid] - ["$[0]" codec]]] - [control - ["[0]" maybe ("[1]#[0]" functor)]] - [data - ["[0]" bit ("[1]#[0]" equivalence)]] - [math - ["[0]" random {"+" Random}]]]] - [\\library - ["[0]" / - [// - ["n" nat ("[1]#[0]" equivalence)]]]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [\\specification + ["$[0]" equivalence] + ["$[0]" order] + ["$[0]" monoid] + ["$[0]" codec]]] + [control + ["[0]" maybe ("[1]#[0]" functor)]] + [data + ["[0]" bit ("[1]#[0]" equivalence)]] + [math + ["[0]" random {"+" Random}]]]] + [\\library + ["[0]" / + [// + ["n" nat ("[1]#[0]" equivalence)]]]]) (def: part (Random Nat) @@ -54,7 +54,7 @@ ($codec.spec /.equivalence /.codec ..random)) (do random.monad - [.let [(^open "#[0]") /.equivalence] + [.let [(open "#[0]") /.equivalence] denom/0 ..part denom/1 ..part] (_.cover [/.ratio] diff --git a/stdlib/source/test/lux/meta.lux b/stdlib/source/test/lux/meta.lux index 3aa4fc763..8a4f63425 100644 --- a/stdlib/source/test/lux/meta.lux +++ b/stdlib/source/test/lux/meta.lux @@ -21,13 +21,15 @@ [collection ["[0]" list ("[1]#[0]" functor monoid)] ["[0]" set]]] - [meta - ["[0]" location] - ["[0]" symbol ("[1]#[0]" equivalence)]] + [macro + ["^" pattern]] [math ["[0]" random {"+" Random}] [number - ["n" nat]]]]] + ["n" nat]]] + [meta + ["[0]" location] + ["[0]" symbol ("[1]#[0]" equivalence)]]]] [\\library ["[0]" /]] ["[0]" / "_" @@ -77,29 +79,29 @@ (_.cover [/.result] (|> (# /.monad in expected) (/.result expected_lux) - (!expect (^multi {try.#Success actual} - (n.= expected actual))))) + (!expect (^.multi {try.#Success actual} + (n.= expected actual))))) (_.cover [/.result'] (|> (# /.monad in expected) (/.result' expected_lux) - (!expect (^multi {try.#Success [actual_lux actual]} - (and (same? expected_lux actual_lux) - (n.= expected actual)))))) + (!expect (^.multi {try.#Success [actual_lux actual]} + (and (same? expected_lux actual_lux) + (n.= expected actual)))))) (_.cover [/.compiler_state] (|> /.compiler_state (/.result expected_lux) - (!expect (^multi {try.#Success actual_lux} - (same? expected_lux actual_lux))))) + (!expect (^.multi {try.#Success actual_lux} + (same? expected_lux actual_lux))))) (_.cover [/.version] (|> /.version (/.result expected_lux) - (!expect (^multi {try.#Success it} - (same? version it))))) + (!expect (^.multi {try.#Success it} + (same? version it))))) (_.cover [/.configuration] (|> /.configuration (/.result expected_lux) - (!expect (^multi {try.#Success it} - (same? configuration it))))) + (!expect (^.multi {try.#Success it} + (same? configuration it))))) ))) (def: error_handling @@ -137,9 +139,9 @@ (|> (/.failure expected_error) (: (Meta Any)) (/.result expected_lux) - (!expect (^multi {try.#Failure actual_error} - (text#= (location.with location.dummy expected_error) - actual_error))))) + (!expect (^.multi {try.#Failure actual_error} + (text#= (location.with location.dummy expected_error) + actual_error))))) (_.cover [/.assertion] (and (|> (/.assertion expected_error true) (: (Meta Any)) @@ -147,45 +149,45 @@ (!expect {try.#Success []})) (|> (/.assertion expected_error false) (/.result expected_lux) - (!expect (^multi {try.#Failure actual_error} - (text#= expected_error actual_error)))))) + (!expect (^.multi {try.#Failure actual_error} + (text#= expected_error actual_error)))))) (_.cover [/.either] (and (|> (/.either (# /.monad in expected) (: (Meta Nat) (/.failure expected_error))) (/.result expected_lux) - (!expect (^multi {try.#Success actual} - (n.= expected actual)))) + (!expect (^.multi {try.#Success actual} + (n.= expected actual)))) (|> (/.either (: (Meta Nat) (/.failure expected_error)) (# /.monad in expected)) (/.result expected_lux) - (!expect (^multi {try.#Success actual} - (n.= expected actual)))) + (!expect (^.multi {try.#Success actual} + (n.= expected actual)))) (|> (/.either (: (Meta Nat) (/.failure expected_error)) (: (Meta Nat) (/.failure expected_error))) (/.result expected_lux) - (!expect (^multi {try.#Failure actual_error} - (text#= (location.with location.dummy expected_error) - actual_error)))) + (!expect (^.multi {try.#Failure actual_error} + (text#= (location.with location.dummy expected_error) + actual_error)))) (|> (/.either (# /.monad in expected) (# /.monad in dummy)) (/.result expected_lux) - (!expect (^multi {try.#Success actual} - (n.= expected actual)))) + (!expect (^.multi {try.#Success actual} + (n.= expected actual)))) )) (_.cover [/.try] (and (|> (/.try (/.failure expected_error)) (/.result expected_lux) - (!expect (^multi {try.#Success {try.#Failure actual_error}} - (text#= (location.with location.dummy expected_error) - actual_error)))) + (!expect (^.multi {try.#Success {try.#Failure actual_error}} + (text#= (location.with location.dummy expected_error) + actual_error)))) (|> (/.try (# /.monad in expected)) (/.result expected_lux) - (!expect (^multi {try.#Success {try.#Success actual}} - (same? expected actual)))))) + (!expect (^.multi {try.#Success {try.#Success actual}} + (same? expected actual)))))) ))) (def: module_related @@ -243,18 +245,18 @@ (_.cover [/.current_module_name] (|> /.current_module_name (/.result expected_lux) - (!expect (^multi {try.#Success actual_current_module} - (text#= expected_current_module actual_current_module))))) + (!expect (^.multi {try.#Success actual_current_module} + (text#= expected_current_module actual_current_module))))) (_.cover [/.current_module] (|> /.current_module (/.result expected_lux) - (!expect (^multi {try.#Success actual_module} - (same? expected_module actual_module))))) + (!expect (^.multi {try.#Success actual_module} + (same? expected_module actual_module))))) (_.cover [/.module] (|> (/.module expected_current_module) (/.result expected_lux) - (!expect (^multi {try.#Success actual_module} - (same? expected_module actual_module))))) + (!expect (^.multi {try.#Success actual_module} + (same? expected_module actual_module))))) (_.cover [/.module_exists?] (and (|> (/.module_exists? expected_current_module) (/.result expected_lux) @@ -265,8 +267,8 @@ (_.cover [/.modules] (|> /.modules (/.result expected_lux) - (!expect (^multi {try.#Success actual_modules} - (same? expected_modules actual_modules))))) + (!expect (^.multi {try.#Success actual_modules} + (same? expected_modules actual_modules))))) (_.cover [/.imported_modules] (and (|> (/.imported_modules expected_current_module) (/.result expected_lux) @@ -289,14 +291,14 @@ (_.cover [/.normal] (and (|> (/.normal ["" expected_short]) (/.result expected_lux) - (!expect (^multi {try.#Success [actual_module actual_short]} - (and (text#= expected_current_module actual_module) - (same? expected_short actual_short))))) + (!expect (^.multi {try.#Success [actual_module actual_short]} + (and (text#= expected_current_module actual_module) + (same? expected_short actual_short))))) (|> (/.normal [dummy_module expected_short]) (/.result expected_lux) - (!expect (^multi {try.#Success [actual_module actual_short]} - (and (text#= dummy_module actual_module) - (same? expected_short actual_short))))))) + (!expect (^.multi {try.#Success [actual_module actual_short]} + (and (text#= dummy_module actual_module) + (same? expected_short actual_short))))))) )))) (def: random_location @@ -350,19 +352,19 @@ post /.seed] (in [pre post])) (/.result expected_lux) - (!expect (^multi {try.#Success [actual_pre actual_post]} - (and (n.= expected_seed actual_pre) - (n.= (++ expected_seed) actual_post)))))) + (!expect (^.multi {try.#Success [actual_pre actual_post]} + (and (n.= expected_seed actual_pre) + (n.= (++ expected_seed) actual_post)))))) (_.cover [/.location] (|> /.location (/.result expected_lux) - (!expect (^multi {try.#Success actual_location} - (same? expected_location actual_location))))) + (!expect (^.multi {try.#Success actual_location} + (same? expected_location actual_location))))) (_.cover [/.expected_type] (|> /.expected_type (/.result expected_lux) - (!expect (^multi {try.#Success actual_type} - (same? expected_type actual_type))))) + (!expect (^.multi {try.#Success actual_type} + (same? expected_type actual_type))))) (_.cover [.Type_Context /.type_context] (|> /.type_context (/.result expected_lux) @@ -438,14 +440,14 @@ current_globals! (|> (/.globals expected_current_module) (/.result expected_lux) - (!expect (^multi {try.#Success actual_globals} - (same? current_globals actual_globals)))) + (!expect (^.multi {try.#Success actual_globals} + (same? current_globals actual_globals)))) macro_globals! (|> (/.globals expected_macro_module) (/.result expected_lux) - (!expect (^multi {try.#Success actual_globals} - (same? macro_globals actual_globals))))] + (!expect (^.multi {try.#Success actual_globals} + (same? macro_globals actual_globals))))] (and current_globals! macro_globals!))) (_.cover [.Definition /.definitions] @@ -453,35 +455,35 @@ (expected_lux true {.#Some .Macro})] (and (|> (/.definitions expected_current_module) (/.result expected_lux) - (!expect (^multi {try.#Success actual_definitions} - (n.= 0 (list.size actual_definitions))))) + (!expect (^.multi {try.#Success actual_definitions} + (n.= 0 (list.size actual_definitions))))) (|> (/.definitions expected_macro_module) (/.result expected_lux) - (!expect (^multi {try.#Success actual_definitions} - (n.= 1 (list.size actual_definitions))))) + (!expect (^.multi {try.#Success actual_definitions} + (n.= 1 (list.size actual_definitions))))) ))) (_.cover [/.exports] (and (let [[current_globals macro_globals expected_lux] (expected_lux true {.#Some .Macro})] (and (|> (/.exports expected_current_module) (/.result expected_lux) - (!expect (^multi {try.#Success actual_definitions} - (n.= 0 (list.size actual_definitions))))) + (!expect (^.multi {try.#Success actual_definitions} + (n.= 0 (list.size actual_definitions))))) (|> (/.exports expected_macro_module) (/.result expected_lux) - (!expect (^multi {try.#Success actual_definitions} - (n.= 1 (list.size actual_definitions))))) + (!expect (^.multi {try.#Success actual_definitions} + (n.= 1 (list.size actual_definitions))))) )) (let [[current_globals macro_globals expected_lux] (expected_lux false {.#Some .Macro})] (and (|> (/.exports expected_current_module) (/.result expected_lux) - (!expect (^multi {try.#Success actual_definitions} - (n.= 0 (list.size actual_definitions))))) + (!expect (^.multi {try.#Success actual_definitions} + (n.= 0 (list.size actual_definitions))))) (|> (/.exports expected_macro_module) (/.result expected_lux) - (!expect (^multi {try.#Success actual_definitions} - (n.= 0 (list.size actual_definitions))))) + (!expect (^.multi {try.#Success actual_definitions} + (n.= 0 (list.size actual_definitions))))) )))) ))) @@ -564,8 +566,8 @@ (expected_lux true {.#Some .Macro})] (|> (/.macro [expected_macro_module expected_short]) (/.result expected_lux) - (!expect (^multi {try.#Success {.#Some actual_value}} - (same? expected_value actual_value))))) + (!expect (^.multi {try.#Success {.#Some actual_value}} + (same? expected_value actual_value))))) not_macro! (let [[current_globals macro_globals expected_lux] @@ -586,8 +588,8 @@ (expected_lux true {.#Some .Macro})] (|> (/.macro [expected_current_module expected_short]) (/.result expected_lux) - (!expect (^multi {try.#Success {.#Some actual_value}} - (same? expected_value actual_value)))))] + (!expect (^.multi {try.#Success {.#Some actual_value}} + (same? expected_value actual_value)))))] (and same_module! not_macro! not_found! @@ -610,17 +612,17 @@ definition! (|> (/.definition [expected_macro_module expected_short]) (/.result expected_lux) - (!expect (^multi {try.#Success {.#Definition [actual_exported? actual_type actual_value]}} - (and (bit#= expected_exported? actual_exported?) - (same? expected_type actual_type) - (same? (:as Any expected_value) actual_value))))) + (!expect (^.multi {try.#Success {.#Definition [actual_exported? actual_type actual_value]}} + (and (bit#= expected_exported? actual_exported?) + (same? expected_type actual_type) + (same? (:as Any expected_value) actual_value))))) alias! (|> (/.definition [expected_current_module expected_short]) (/.result expected_lux) - (!expect (^multi {try.#Success {.#Alias [actual_module actual_short]}} - (and (same? expected_macro_module actual_module) - (same? expected_short actual_short)))))] + (!expect (^.multi {try.#Success {.#Alias [actual_module actual_short]}} + (and (same? expected_macro_module actual_module) + (same? expected_short actual_short)))))] (and definition! alias!))) (_.cover [/.definition_type] @@ -630,14 +632,14 @@ definition! (|> (/.definition_type [expected_macro_module expected_short]) (/.result expected_lux) - (!expect (^multi {try.#Success actual_type} - (same? expected_type actual_type)))) + (!expect (^.multi {try.#Success actual_type} + (same? expected_type actual_type)))) alias! (|> (/.definition_type [expected_current_module expected_short]) (/.result expected_lux) - (!expect (^multi {try.#Success actual_type} - (same? expected_type actual_type))))] + (!expect (^.multi {try.#Success actual_type} + (same? expected_type actual_type))))] (and definition! alias!))) (_.cover [/.type_definition] @@ -647,14 +649,14 @@ definition! (|> (/.type_definition [expected_macro_module expected_short]) (/.result expected_lux) - (!expect (^multi {try.#Success actual_value} - (same? (:as .Type expected_value) actual_value)))) + (!expect (^.multi {try.#Success actual_value} + (same? (:as .Type expected_value) actual_value)))) alias! (|> (/.type_definition [expected_current_module expected_short]) (/.result expected_lux) - (!expect (^multi {try.#Success actual_value} - (same? (:as .Type expected_value) actual_value))))] + (!expect (^.multi {try.#Success actual_value} + (same? (:as .Type expected_value) actual_value))))] (and definition! alias!))) ))) @@ -755,22 +757,22 @@ (|> [label_module label] /.tag (/.result expected_lux) - (!expect (^multi {try.#Success [actual_index actual_tags actual_type]} - (let [correct_index! - (n.= expected_index - actual_index) - - correct_tags! - (# (list.equivalence symbol.equivalence) = - (list#each (|>> [label_module]) {.#Item tags_0}) - actual_tags) - - correct_type! - (type#= type_0 - actual_type)] - (and correct_index! + (!expect (^.multi {try.#Success [actual_index actual_tags actual_type]} + (let [correct_index! + (n.= expected_index + actual_index) + correct_tags! - correct_type!)))) + (# (list.equivalence symbol.equivalence) = + (list#each (|>> [label_module]) {.#Item tags_0}) + actual_tags) + + correct_type! + (type#= type_0 + actual_type)] + (and correct_index! + correct_tags! + correct_type!)))) ))))) (_.cover [/.slot] (|> {.#Item tags_1} @@ -779,22 +781,22 @@ (|> [label_module label] /.slot (/.result expected_lux) - (!expect (^multi {try.#Success [actual_index actual_tags actual_type]} - (let [correct_index! - (n.= expected_index - actual_index) - - correct_tags! - (# (list.equivalence symbol.equivalence) = - (list#each (|>> [label_module]) {.#Item tags_1}) - actual_tags) - - correct_type! - (type#= type_1 - actual_type)] - (and correct_index! + (!expect (^.multi {try.#Success [actual_index actual_tags actual_type]} + (let [correct_index! + (n.= expected_index + actual_index) + correct_tags! - correct_type!)))) + (# (list.equivalence symbol.equivalence) = + (list#each (|>> [label_module]) {.#Item tags_1}) + actual_tags) + + correct_type! + (type#= type_1 + actual_type)] + (and correct_index! + correct_tags! + correct_type!)))) ))))) ))) @@ -807,7 +809,7 @@ (# ! each set.list) (random.one (function (_ values) (case values - (^ (list name_0 name_1 name_2 name_3 name_4)) + (pattern (list name_0 name_1 name_2 name_3 name_4)) {.#Some [name_0 name_1 name_2 name_3 name_4]} _ @@ -991,16 +993,16 @@ (: (Try Nat)) /.lifted (/.result expected_lux) - (!expect (^multi {try.#Failure actual} - (text#= (location.with expected_location expected_error) - actual)))) + (!expect (^.multi {try.#Failure actual} + (text#= (location.with expected_location expected_error) + actual)))) (|> expected_value {try.#Success} (: (Try Nat)) /.lifted (/.result expected_lux) - (!expect (^multi {try.#Success actual} - (same? expected_value actual))))))) + (!expect (^.multi {try.#Success actual} + (same? expected_value actual))))))) ..compiler_related ..error_handling diff --git a/stdlib/source/test/lux/meta/symbol.lux b/stdlib/source/test/lux/meta/symbol.lux index 261015a31..e12f209d1 100644 --- a/stdlib/source/test/lux/meta/symbol.lux +++ b/stdlib/source/test/lux/meta/symbol.lux @@ -11,6 +11,8 @@ ["$[0]" codec]]] [data ["[0]" text]] + [macro + ["^" pattern]] [math ["[0]" random {"+" Random}] [number @@ -30,11 +32,11 @@ [... First Symbol sizeM1 (|> random.nat (# ! each (n.% 100))) sizeS1 (|> random.nat (# ! each (|>> (n.% 100) (n.max 1)))) - (^let symbol1 [module1 short1]) (..random sizeM1 sizeS1) + (^.let symbol1 [module1 short1]) (..random sizeM1 sizeS1) ... Second Symbol sizeM2 (|> random.nat (# ! each (n.% 100))) sizeS2 (|> random.nat (# ! each (|>> (n.% 100) (n.max 1)))) - (^let symbol2 [module2 short2]) (..random sizeM2 sizeS2)] + (^.let symbol2 [module2 short2]) (..random sizeM2 sizeS2)] (_.for [.Symbol] ($_ _.and (_.for [/.equivalence] @@ -61,7 +63,7 @@ (and (same? module1 (/.module symbol1)) (same? short1 (/.short symbol1)))) (_.for [.symbol] - (let [(^open "/#[0]") /.equivalence] + (let [(open "/#[0]") /.equivalence] ($_ _.and (_.test "Can obtain Symbol from a symbol." (and (/#= [.prelude_module "yolo"] (.symbol .yolo)) diff --git a/stdlib/source/test/lux/program.lux b/stdlib/source/test/lux/program.lux index e78630278..f2aafead6 100644 --- a/stdlib/source/test/lux/program.lux +++ b/stdlib/source/test/lux/program.lux @@ -32,7 +32,7 @@ (do random.monad [inputs (random.list 5 (random.ascii/upper 5))] (_.cover [/.program:] - (let [(^open "list#[0]") (list.equivalence text.equivalence)] + (let [(open "list#[0]") (list.equivalence text.equivalence)] (and (with_expansions [<program> (/.program: all_arguments (io.io all_arguments))] (let [outcome ((: (-> (List Text) (io.IO Any)) diff --git a/stdlib/source/test/lux/time/duration.lux b/stdlib/source/test/lux/time/duration.lux index a4544e4cc..af1550e29 100644 --- a/stdlib/source/test/lux/time/duration.lux +++ b/stdlib/source/test/lux/time/duration.lux @@ -1,24 +1,24 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [\\specification - ["$[0]" equivalence] - ["$[0]" order] - ["$[0]" enum] - ["$[0]" monoid] - ["$[0]" codec]]] - [data - ["[0]" bit ("[1]#[0]" equivalence)]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat] - ["i" int]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [\\specification + ["$[0]" equivalence] + ["$[0]" order] + ["$[0]" enum] + ["$[0]" monoid] + ["$[0]" codec]]] + [data + ["[0]" bit ("[1]#[0]" equivalence)]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat] + ["i" int]]]]] + [\\library + ["[0]" /]]) (def: .public test Test @@ -41,7 +41,7 @@ (_.cover [/.of_millis /.millis] (|> duration /.millis /.of_millis (# /.equivalence = duration)))) (do random.monad - [.let [(^open "#[0]") /.equivalence] + [.let [(open "#[0]") /.equivalence] expected random.duration parameter random.duration] ($_ _.and @@ -59,12 +59,12 @@ (/.neutral? (/.inverse expected))))) )) (do random.monad - [.let [(^open "#[0]") /.equivalence] + [.let [(open "#[0]") /.equivalence] factor random.nat] (_.cover [/.up /.down] (|> /.milli_second (/.up factor) (/.down factor) (#= /.milli_second)))) (do [! random.monad] - [.let [(^open "#[0]") /.order + [.let [(open "#[0]") /.order positive (|> random.duration (random.only (|>> (#= /.empty) not)) (# ! each (function (_ duration) diff --git a/stdlib/source/test/lux/time/instant.lux b/stdlib/source/test/lux/time/instant.lux index c61d4e163..12f2ca7c3 100644 --- a/stdlib/source/test/lux/time/instant.lux +++ b/stdlib/source/test/lux/time/instant.lux @@ -1,28 +1,28 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [\\specification - ["$[0]" equivalence] - ["$[0]" order] - ["$[0]" enum] - ["$[0]" codec]]] - [control - ["[0]" function] - ["[0]" try] - ["[0]" io]] - [data - [collection - ["[0]" list ("[1]#[0]" mix)]]] - [math - ["[0]" random]] - [time - ["[0]" duration {"+" Duration}] - ["[0]" day {"+" Day} ("[1]#[0]" enum)]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [\\specification + ["$[0]" equivalence] + ["$[0]" order] + ["$[0]" enum] + ["$[0]" codec]]] + [control + ["[0]" function] + ["[0]" try] + ["[0]" io]] + [data + [collection + ["[0]" list ("[1]#[0]" mix)]]] + [math + ["[0]" random]] + [time + ["[0]" duration {"+" Duration}] + ["[0]" day {"+" Day} ("[1]#[0]" enum)]]]] + [\\library + ["[0]" /]]) (def: .public test Test @@ -39,7 +39,7 @@ ($codec.spec /.equivalence /.codec random.instant)) (do random.monad - [.let [(^open "#[0]") /.equivalence] + [.let [(open "#[0]") /.equivalence] expected random.instant] ($_ _.and (_.cover [/.millis /.of_millis] @@ -52,8 +52,8 @@ (/.time expected)))) )) (do random.monad - [.let [(^open "#[0]") /.equivalence - (^open "duration#[0]") duration.equivalence] + [.let [(open "#[0]") /.equivalence + (open "duration#[0]") duration.equivalence] from random.instant to random.instant] ($_ _.and diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis.lux index eb623b548..02c25c3e6 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis.lux @@ -111,7 +111,7 @@ (`` ($_ _.and (_.cover [/.unit] (case (/.unit) - (^ (/.unit)) + (pattern (/.unit)) true _ @@ -119,7 +119,7 @@ (~~ (template [<tag> <expected>] [(_.cover [<tag>] (case (<tag> <expected>) - (^ (<tag> actual)) + (pattern (<tag> actual)) (same? <expected> actual) _ @@ -146,7 +146,7 @@ expected_right expected_left)] (case (/.variant [expected_lefts expected_right? expected]) - (^ (/.variant [actual_lefts actual_right? actual])) + (pattern (/.variant [actual_lefts actual_right? actual])) (and (same? expected_lefts actual_lefts) (same? expected_right? actual_right?) (same? expected actual)) @@ -155,7 +155,7 @@ false))) (_.cover [/.tuple] (case (/.tuple (list expected_left expected_right)) - (^ (/.tuple (list actual_left actual_right))) + (pattern (/.tuple (list actual_left actual_right))) (and (same? expected_left actual_left) (same? expected_right actual_right)) @@ -173,7 +173,7 @@ (~~ (template [<tag> <expected>] [(_.cover [<tag>] (case (<tag> <expected>) - (^ (<tag> actual)) + (pattern (<tag> actual)) (same? <expected> actual) _ @@ -206,7 +206,7 @@ (case (|> [expected_abstraction (list expected_parameter/0 expected_parameter/1)] /.reified /.reification) - (^ [actual_abstraction (list actual_parameter/0 actual_parameter/1)]) + (pattern [actual_abstraction (list actual_parameter/0 actual_parameter/1)]) (and (same? expected_abstraction actual_abstraction) (same? expected_parameter/0 actual_parameter/0) (same? expected_parameter/1 actual_parameter/1)) @@ -215,7 +215,7 @@ false)) (_.cover [/.no_op] (case (/.no_op expected_parameter/0) - (^ (/.no_op actual)) + (pattern (/.no_op actual)) (same? expected_parameter/0 actual) _ @@ -230,7 +230,7 @@ ($_ _.and (_.cover [/.case] (case (/.case [expected_input expected_match]) - (^ (/.case [actual_input actual_match])) + (pattern (/.case [actual_input actual_match])) (and (same? expected_input actual_input) (same? expected_match actual_match)) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/coverage.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/coverage.lux index e7e26bd54..dfd65e1ba 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/coverage.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/coverage.lux @@ -20,6 +20,8 @@ ["[0]" set] ["[0]" dictionary] ["[0]" list ("[1]#[0]" functor mix)]]] + [macro + ["^" pattern]] [math ["[0]" random {"+" Random} ("[1]#[0]" monad)] [number @@ -144,7 +146,7 @@ (def: test|value Test - (<| (let [(^open "/#[0]") /.equivalence]) + (<| (let [(open "/#[0]") /.equivalence]) (do [! random.monad] [left ..random right ..random] @@ -162,7 +164,7 @@ (def: test|coverage Test - (<| (let [(^open "/#[0]") /.equivalence]) + (<| (let [(open "/#[0]") /.equivalence]) (do [! random.monad] [[expected pattern] ..random_pattern] ($_ _.and @@ -198,7 +200,7 @@ (def: test|variant Test - (<| (let [(^open "/#[0]") /.equivalence]) + (<| (let [(open "/#[0]") /.equivalence]) (do [! random.monad] [[expected/0 pattern/0] ..random_partial_pattern [expected/1 pattern/1] (random.only (|>> product.left (/#= expected/0) not) @@ -223,7 +225,7 @@ (Random [/.Coverage Pattern]) (random.only (function (_ [coverage pattern]) (case coverage - (^or {/.#Alt _} {/.#Seq _}) + (^.or {/.#Alt _} {/.#Seq _}) false _ @@ -232,7 +234,7 @@ (def: test|composite Test - (<| (let [(^open "/#[0]") /.equivalence]) + (<| (let [(open "/#[0]") /.equivalence]) (do [! random.monad] [[expected/0 pattern/0] ..random_value_pattern [expected/1 pattern/1] (random.only (|>> product.left (/#= expected/0) not) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/module.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/module.lux index 52ab6e6ff..f87e34b08 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/module.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/module.lux @@ -122,7 +122,7 @@ (/phase.result state) (try#each (|>> (the .#module_aliases) (pipe.case - (^ (list [actual_alias actual_import])) + (pattern (list [actual_alias actual_import])) (and (same? expected_alias actual_alias) (same? expected_import actual_import)) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/pattern.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/pattern.lux index e5eb0c0f5..cd72d2b50 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/pattern.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/pattern.lux @@ -52,11 +52,11 @@ ($equivalence.spec /.equivalence ..random)) (_.cover [/.format] - (bit#= (# /.equivalence = left right) - (text#= (/.format left) (/.format right)))) + (bit#= (# /.equivalence = left right) + (text#= (/.format left) (/.format right)))) (_.cover [/.unit] (case (/.unit) - (^ (/.unit)) + (pattern (/.unit)) true _ @@ -64,7 +64,7 @@ (~~ (template [<tag> <value>] [(_.cover [<tag>] (case (<tag> <value>) - (^ (<tag> actual)) + (pattern (<tag> actual)) (same? <value> actual) _ @@ -80,7 +80,7 @@ )) (_.cover [/.variant] (case (/.variant [expected_lefts expected_right? (/.text expected_text)]) - (^ (/.variant [actual_lefts actual_right? (/.text actual_text)])) + (pattern (/.variant [actual_lefts actual_right? (/.text actual_text)])) (and (same? expected_lefts actual_lefts) (same? expected_right? actual_right?) (same? expected_text actual_text)) @@ -94,12 +94,12 @@ (/.rev expected_rev) (/.frac expected_frac) (/.text expected_text))) - (^ (/.tuple (list (/.bit actual_bit) - (/.nat actual_nat) - (/.int actual_int) - (/.rev actual_rev) - (/.frac actual_frac) - (/.text actual_text)))) + (pattern (/.tuple (list (/.bit actual_bit) + (/.nat actual_nat) + (/.int actual_int) + (/.rev actual_rev) + (/.frac actual_frac) + (/.text actual_text)))) (and (same? expected_bit actual_bit) (same? expected_nat actual_nat) (same? expected_int actual_int) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/scope.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/scope.lux index faf28f47e..bd2309561 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/scope.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/scope.lux @@ -158,7 +158,7 @@ (n.= 1 (list.size (the [.#captured .#mappings] scope/1)))))) (try.else false))) (_.cover [/.environment] - (let [(^open "list#[0]") (list.equivalence //variable.equivalence)] + (let [(open "list#[0]") (list.equivalence //variable.equivalence)] (and (|> (<| /.with (/.with_local [name/0 type/0]) (/.with_local [name/1 type/1]) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis.lux index 6c1e342ec..88577b388 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis.lux @@ -64,7 +64,7 @@ //type.inferring)] (in (and (type#= .Any :it:) (case it - (^ (//.unit)) + (pattern (//.unit)) true _ @@ -87,7 +87,7 @@ //type.inferring)] (in (and (type#= <type> :it:) (case it - (^ (<analysis> it)) + (pattern (<analysis> it)) (same? <expected> it) _ @@ -128,7 +128,7 @@ (/.phase ..expander archive.empty) (//type.expecting :variant:))] (in (case it - (^ (//.variant [0 #0 (//.unit)])) + (pattern (//.variant [0 #0 (//.unit)])) true _ @@ -144,7 +144,7 @@ (/.phase ..expander archive.empty) (//type.expecting :variant:))] (in (case it - (^ (//.variant [<lefts> <right> (<analysis> actual)])) + (pattern (//.variant [<lefts> <right> (<analysis> actual)])) (same? <expected> actual) _ @@ -170,7 +170,7 @@ (/.phase ..expander archive.empty) (//type.expecting :either:))] (in (case it - (^ (//.variant [0 #0 (//.unit)])) + (pattern (//.variant [0 #0 (//.unit)])) true _ @@ -196,13 +196,13 @@ (/.phase ..expander archive.empty) (//type.expecting :either:))] (in (case it - (^ (//.variant [0 #1 (//.tuple (list (//.unit) - (//.bit bit/?) - (//.nat nat/?) - (//.int int/?) - (//.rev rev/?) - (//.frac frac/?) - (//.text text/?)))])) + (pattern (//.variant [0 #1 (//.tuple (list (//.unit) + (//.bit bit/?) + (//.nat nat/?) + (//.int int/?) + (//.rev rev/?) + (//.frac frac/?) + (//.text text/?)))])) (and (same? bit/0 bit/?) (same? nat/0 nat/?) (same? int/0 int/?) @@ -242,7 +242,7 @@ (in (and (type#= :variant: :it:) (case it - (^ (//.variant [0 #0 (//.unit)])) + (pattern (//.variant [0 #0 (//.unit)])) true _ @@ -261,7 +261,7 @@ (in (and (type#= :variant: :it:) (case it - (^ (//.variant [<lefts> <right> (<analysis> actual)])) + (pattern (//.variant [<lefts> <right> (<analysis> actual)])) (same? <expected> actual) _ @@ -292,7 +292,7 @@ (in (and (type#= :either: :it:) (case it - (^ (//.variant [0 #0 (//.unit)])) + (pattern (//.variant [0 #0 (//.unit)])) true _ @@ -322,13 +322,13 @@ (in (and (type#= :either: :it:) (case it - (^ (//.variant [0 #1 (//.tuple (list (//.unit) - (//.bit bit/?) - (//.nat nat/?) - (//.int int/?) - (//.rev rev/?) - (//.frac frac/?) - (//.text text/?)))])) + (pattern (//.variant [0 #1 (//.tuple (list (//.unit) + (//.bit bit/?) + (//.nat nat/?) + (//.int int/?) + (//.rev rev/?) + (//.frac frac/?) + (//.text text/?)))])) (and (same? bit/0 bit/?) (same? nat/0 nat/?) (same? int/0 int/?) @@ -364,13 +364,13 @@ (in (and (type#= (type [.Any .Bit .Nat .Int .Rev .Frac .Text]) :it:) (case it - (^ (//.tuple (list (//.unit) - (//.bit bit/?) - (//.nat nat/?) - (//.int int/?) - (//.rev rev/?) - (//.frac frac/?) - (//.text text/?)))) + (pattern (//.tuple (list (//.unit) + (//.bit bit/?) + (//.nat nat/?) + (//.int int/?) + (//.rev rev/?) + (//.frac frac/?) + (//.text text/?)))) (and (same? bit/0 bit/?) (same? nat/0 nat/?) (same? int/0 int/?) @@ -407,13 +407,13 @@ (in (and (type#= :record: :it:) (case it - (^ (//.tuple (list (//.unit) - (//.bit bit/?) - (//.nat nat/?) - (//.int int/?) - (//.rev rev/?) - (//.frac frac/?) - (//.text text/?)))) + (pattern (//.tuple (list (//.unit) + (//.bit bit/?) + (//.nat nat/?) + (//.int int/?) + (//.rev rev/?) + (//.frac frac/?) + (//.text text/?)))) (and (same? bit/0 bit/?) (same? nat/0 nat/?) (same? int/0 int/?) @@ -442,7 +442,7 @@ (in (and (type#= (All (_ a) (-> a .Nat)) :it:) (case it - (^ {//.#Function (list) (//.nat nat/?)}) + (pattern {//.#Function (list) (//.nat nat/?)}) (same? nat/0 nat/?) _ @@ -463,7 +463,7 @@ (in (and (type#= (All (_ a) (-> a (All (_ b) (-> b .Nat)))) :it:) (case it - (^ {//.#Function (list) {//.#Function (list) (//.nat nat/?)}}) + (pattern {//.#Function (list) {//.#Function (list) (//.nat nat/?)}}) (same? nat/0 nat/?) _ @@ -484,7 +484,7 @@ (in (and (type#= (All (_ a) (-> a (All (_ b) (-> b b)))) :it:) (case it - (^ {//.#Function (list) {//.#Function (list) (//.local 1)}}) + (pattern {//.#Function (list) {//.#Function (list) (//.local 1)}}) true _ @@ -503,7 +503,7 @@ (/.phase ..expander archive.empty) //type.inferring)] (in (and (case it - (^ {//.#Function (list) {//.#Function (list (//.local 1)) (//.foreign 0)}}) + (pattern {//.#Function (list) {//.#Function (list (//.local 1)) (//.foreign 0)}}) true _ @@ -529,7 +529,7 @@ ... (/.phase ..expander archive.empty) ... //type.inferring)] ... (in (case it - ... (^ {//.#Function (list) {//.#Function (list) (//.local 0)}}) + ... (pattern {//.#Function (list) {//.#Function (list) (//.local 0)}}) ... true ... _ @@ -547,7 +547,7 @@ ... (/.phase ..expander archive.empty) ... //type.inferring)] ... (in (case it - ... (^ {//.#Function (list) {//.#Function (list (//.local 0)) (//.foreign 0)}}) + ... (pattern {//.#Function (list) {//.#Function (list (//.local 0)) (//.foreign 0)}}) ... true ... _ @@ -572,8 +572,8 @@ //type.inferring)] (in (and (type#= .Bit :it:) (case it - (^ {//.#Apply (//.nat nat/?) - {//.#Function (list) (//.bit bit/?)}}) + (pattern {//.#Apply (//.nat nat/?) + {//.#Function (list) (//.bit bit/?)}}) (and (same? bit/0 bit/?) (same? nat/0 nat/?)) @@ -593,8 +593,8 @@ //type.inferring)] (in (and (type#= .Nat :it:) (case it - (^ {//.#Apply (//.nat nat/?) - {//.#Function (list) (//.local 1)}}) + (pattern {//.#Apply (//.nat nat/?) + {//.#Function (list) (//.local 1)}}) (same? nat/0 nat/?) _ @@ -615,9 +615,9 @@ //type.inferring)] (in (and (check.subsumes? (All (_ a) (-> a Bit)) :it:) (case it - (^ {//.#Apply (//.nat nat/?) - {//.#Function (list) - {//.#Function (list) (//.bit bit/?)}}}) + (pattern {//.#Apply (//.nat nat/?) + {//.#Function (list) + {//.#Function (list) (//.bit bit/?)}}}) (and (same? bit/0 bit/?) (same? nat/0 nat/?)) @@ -642,7 +642,7 @@ //type.inferring)] (in (and (type#= .Text :it:) (case it - (^ {//.#Extension "lux text concat" (list (//.text left) (//.text right))}) + (pattern {//.#Extension "lux text concat" (list (//.text left) (//.text right))}) (and (same? text/0 left) (same? text/0 right)) @@ -675,10 +675,10 @@ //type.inferring)] (in (and (type#= .Frac :it:) (case it - (^ {//.#Case (<analysis> input/?) - [[//.#when (//pattern.bind 0) - //.#then (//.frac frac/?)] - (list)]}) + (pattern {//.#Case (<analysis> input/?) + [[//.#when (//pattern.bind 0) + //.#then (//.frac frac/?)] + (list)]}) (and (same? <input> input/?) (same? frac/0 frac/?)) @@ -700,11 +700,11 @@ //type.inferring)] (in (and (type#= .Frac :it:) (case it - (^ {//.#Case (<analysis> input/?) - [[//.#when (<pattern> pattern/?) - //.#then (//.frac frac/?)] - (list [//.#when (//pattern.bind 0) - //.#then (//.frac frac/?)])]}) + (pattern {//.#Case (<analysis> input/?) + [[//.#when (<pattern> pattern/?) + //.#then (//.frac frac/?)] + (list [//.#when (//pattern.bind 0) + //.#then (//.frac frac/?)])]}) (and (same? <input> input/?) (same? <input> pattern/?) (same? frac/0 frac/?)) @@ -737,11 +737,11 @@ //type.inferring)] (in (and (type#= .Frac :it:) (case it - (^ {//.#Case (//.bit bit/?) - [[//.#when (//pattern.bit #0) - //.#then (//.frac false/?)] - (list [//.#when (//pattern.bit #1) - //.#then (//.frac true/?)])]}) + (pattern {//.#Case (//.bit bit/?) + [[//.#when (//pattern.bit #0) + //.#then (//.frac false/?)] + (list [//.#when (//pattern.bit #1) + //.#then (//.frac true/?)])]}) (and (same? bit/0 bit/?) (same? frac/0 false/?) (same? frac/0 true/?)) @@ -768,11 +768,11 @@ //type.inferring)] (in (and (type#= .Frac :it:) (case it - (^ {//.#Case (//.variant [<lefts> <right?> (<analysis> analysis/?)]) - [[//.#when (//pattern.variant [<lefts> <right?> (<pattern> pattern/?)]) - //.#then (//.frac match/?)] - (list [//.#when (//pattern.bind 0) - //.#then (//.frac mismatch/?)])]}) + (pattern {//.#Case (//.variant [<lefts> <right?> (<analysis> analysis/?)]) + [[//.#when (//pattern.variant [<lefts> <right?> (<pattern> pattern/?)]) + //.#then (//.frac match/?)] + (list [//.#when (//pattern.bind 0) + //.#then (//.frac mismatch/?)])]}) (and (same? <expected> analysis/?) (same? <expected> pattern/?) (same? frac/0 match/?) @@ -807,11 +807,11 @@ //type.inferring)] (in (and (type#= .Frac :it:) (case it - (^ {//.#Case (//.tuple (list (//.bit bit/?) (//.nat nat/?))) - [[//.#when (//pattern.tuple (list (//pattern.bit #0) (//pattern.bind 0))) - //.#then (//.frac false/?)] - (list [//.#when (//pattern.tuple (list (//pattern.bit #1) (//pattern.bind 0))) - //.#then (//.frac true/?)])]}) + (pattern {//.#Case (//.tuple (list (//.bit bit/?) (//.nat nat/?))) + [[//.#when (//pattern.tuple (list (//pattern.bit #0) (//pattern.bind 0))) + //.#then (//.frac false/?)] + (list [//.#when (//pattern.tuple (list (//pattern.bit #1) (//pattern.bind 0))) + //.#then (//.frac true/?)])]}) (and (same? bit/0 bit/?) (same? nat/0 nat/?) (same? frac/0 false/?) @@ -850,23 +850,23 @@ //type.inferring)] (in (and (type#= .Frac :it:) (case it - (^ {//.#Case (//.tuple (list (//.unit) - (//.bit bit/?) - (//.nat nat/?) - (//.int int/?) - (//.rev rev/?) - (//.frac frac/?) - (//.text text/?))) - [[//.#when (//pattern.tuple (list (//pattern.unit) - (//pattern.bit bit/?') - (//pattern.nat nat/?') - (//pattern.int int/?') - (//pattern.rev rev/?') - (//pattern.frac frac/?') - (//pattern.text text/?'))) - //.#then (//.frac match/?)] - (list [//.#when (//pattern.bind 0) - //.#then (//.frac mismatch/?)])]}) + (pattern {//.#Case (//.tuple (list (//.unit) + (//.bit bit/?) + (//.nat nat/?) + (//.int int/?) + (//.rev rev/?) + (//.frac frac/?) + (//.text text/?))) + [[//.#when (//pattern.tuple (list (//pattern.unit) + (//pattern.bit bit/?') + (//pattern.nat nat/?') + (//pattern.int int/?') + (//pattern.rev rev/?') + (//pattern.frac frac/?') + (//pattern.text text/?'))) + //.#then (//.frac match/?)] + (list [//.#when (//pattern.bind 0) + //.#then (//.frac mismatch/?)])]}) (and (same? bit/0 bit/?) (same? bit/0 bit/?') (same? nat/0 nat/?) (same? nat/0 nat/?') (same? int/0 int/?) (same? int/0 int/?') diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/complex.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/complex.lux index f27af5d36..f6d69fc56 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/complex.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/complex.lux @@ -18,6 +18,7 @@ ["[0]" list ("[1]#[0]" monad monoid)] ["[0]" set]]] [macro + ["^" pattern] ["[0]" code]] [math ["[0]" random {"+" Random} ("[1]#[0]" monad)] @@ -104,18 +105,18 @@ (def: (analysed? expected actual) (-> Code Analysis Bit) (case [expected actual] - (^ [[_ {.#Tuple (list)}] (//analysis.unit)]) + (pattern [[_ {.#Tuple (list)}] (//analysis.unit)]) true - (^ [[_ {.#Tuple expected}] (//analysis.tuple actual)]) + (pattern [[_ {.#Tuple expected}] (//analysis.tuple actual)]) (and (n.= (list.size expected) (list.size actual)) (list.every? (function (_ [expected actual]) (analysed? expected actual)) (list.zipped/2 expected actual))) - (^template [<expected> <actual>] - [(^ [[_ {<expected> expected}] (<actual> actual)]) + (^.template [<expected> <actual>] + [(pattern [[_ {<expected> expected}] (<actual> actual)]) (same? expected actual)]) ([.#Bit //analysis.bit] [.#Nat //analysis.nat] @@ -149,7 +150,7 @@ [analysis (|> (/.sum ..analysis lefts right? archive.empty code) (//type.expecting type))] (in (case analysis - (^ (//analysis.variant [lefts' right?' analysis])) + (pattern (//analysis.variant [lefts' right?' analysis])) (and (n.= lefts lefts') (bit#= right? right?') (..analysed? code analysis)) @@ -168,7 +169,7 @@ analysis (|> (/.sum ..analysis lefts right? archive.empty tagC) (//type.expecting varT))] (in (case analysis - (^ (//analysis.variant [lefts' right?' it])) + (pattern (//analysis.variant [lefts' right?' it])) (and (n.= lefts lefts') (bit#= right? right?') (..analysed? tagC it)) @@ -241,7 +242,7 @@ analysis (|> (/.variant ..analysis tag archive.empty tagC) (//type.expecting variantT))] (in (case analysis - (^ (//analysis.variant [lefts' right?' analysis])) + (pattern (//analysis.variant [lefts' right?' analysis])) (and (n.= lefts lefts') (bit#= right? right?') (..analysed? tagC analysis)) @@ -259,7 +260,7 @@ [actualT analysis] (|> (/.variant ..analysis tag archive.empty tagC) //type.inferring)] (in (case analysis - (^ (//analysis.variant [lefts' right?' analysis])) + (pattern (//analysis.variant [lefts' right?' analysis])) (and (n.= lefts lefts') (bit#= right? right?') (..analysed? tagC analysis) @@ -306,7 +307,7 @@ (/.product ..analysis archive.empty) (//type.expecting type))] (in (case analysis - (^ (//analysis.tuple actual)) + (pattern (//analysis.tuple actual)) (and (n.= (list.size expected) (list.size actual)) (list.every? (function (_ [expected actual]) @@ -331,7 +332,7 @@ (/.product ..analysis archive.empty) (//type.expecting varT))] (in (case analysis - (^ (//analysis.tuple actual)) + (pattern (//analysis.tuple actual)) (and (n.= (list.size expected) (list.size actual)) (list.every? (function (_ [expected actual]) @@ -349,7 +350,7 @@ (/.product ..analysis archive.empty) //type.inferring)] (in (case analysis - (^ (//analysis.tuple actual)) + (pattern (//analysis.tuple actual)) (and (n.= (list.size expected) (list.size actual)) (list.every? (function (_ [expected actual]) @@ -372,7 +373,7 @@ (list term/0 term/1 term/2 term/2 term/2)))) :inferred: (//type.check (check.clean (list @var) :inferred:))] (in (case analysis - (^ (//analysis.tuple (list analysis/0 analysis/1 (//analysis.tuple (list analysis/2 analysis/3 analysis/4))))) + (pattern (//analysis.tuple (list analysis/0 analysis/1 (//analysis.tuple (list analysis/2 analysis/3 analysis/4))))) (and (type#= (Tuple type/0 type/1 type/2 type/2 type/2) :inferred:) (..analysed? term/0 analysis/0) @@ -392,7 +393,7 @@ (/.product ..analysis archive.empty) (//type.expecting (Tuple type/0 type/1 type/2 type/2 type/2)))] (in (case analysis - (^ (//analysis.tuple (list analysis/0 analysis/1 (//analysis.tuple (list analysis/2 analysis/3 analysis/4))))) + (pattern (//analysis.tuple (list analysis/0 analysis/1 (//analysis.tuple (list analysis/2 analysis/3 analysis/4))))) (and (..analysed? term/0 analysis/0) (..analysed? term/1 analysis/1) (..analysed? term/2 analysis/2) @@ -481,7 +482,7 @@ (//phase.result state) (pipe.case {try.#Success {.#Some actual}} - (let [(^open "list#[0]") (list.equivalence (product.equivalence symbol.equivalence code.equivalence))] + (let [(open "list#[0]") (list.equivalence (product.equivalence symbol.equivalence code.equivalence))] (list#= expected (list.reversed actual))) _ @@ -522,7 +523,7 @@ (|> (/.order false (list)) (//phase.result state) (pipe.case - (^ {try.#Success {.#Some [0 (list) actual_type]}}) + (pattern {try.#Success {.#Some [0 (list) actual_type]}}) (same? .Any actual_type) _ diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/reference.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/reference.lux index 45fef5649..d8c5ce4f8 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/reference.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/reference.lux @@ -54,7 +54,7 @@ (//phase.result state) (try#each (|>> product.right (pipe.case - (^ [actual_type (//analysis.local 0)]) + (pattern [actual_type (//analysis.local 0)]) (type#= expected_type actual_type) _ @@ -73,7 +73,7 @@ (try#each (|>> product.right product.right (pipe.case - (^ [actual_type (//analysis.foreign 0)]) + (pattern [actual_type (//analysis.foreign 0)]) (type#= expected_type actual_type) _ @@ -89,7 +89,7 @@ (//phase.result state) (try#each (|>> product.right (pipe.case - (^ [actual_type (//analysis.constant [actual_module actual_name])]) + (pattern [actual_type (//analysis.constant [actual_module actual_name])]) (and (type#= expected_type actual_type) (same? expected_module actual_module) (same? expected_name actual_name)) @@ -109,7 +109,7 @@ (//phase.result state) (try#each (|>> product.right (pipe.case - (^ [actual_type (//analysis.constant [actual_module actual_name])]) + (pattern [actual_type (//analysis.constant [actual_module actual_name])]) (and (type#= expected_type actual_type) (same? import actual_module) (same? expected_name actual_name)) @@ -130,7 +130,7 @@ (//phase.result state) (try#each (|>> product.right (pipe.case - (^ [actual_type (//analysis.constant [actual_module actual_name])]) + (pattern [actual_type (//analysis.constant [actual_module actual_name])]) (and (type#= expected_type actual_type) (same? import actual_module) (same? expected_name actual_name)) @@ -151,7 +151,7 @@ (//phase.result state) (try#each (|>> product.right (pipe.case - (^ [actual_type (//analysis.constant [actual_module actual_name])]) + (pattern [actual_type (//analysis.constant [actual_module actual_name])]) (and (type#= .Type actual_type) (same? expected_module actual_module) (same? expected_name actual_name)) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/simple.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/simple.lux index 454cebdc6..ea5d4ebb4 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/simple.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/simple.lux @@ -35,7 +35,7 @@ (/phase.result [/extension.#bundle /extension.empty /extension.#state state]) (pipe.case - (^ {try.#Success analysis}) + (pattern {try.#Success analysis}) (? analysis) _ @@ -47,7 +47,7 @@ (/phase.result [/extension.#bundle /extension.empty /extension.#state state]) (pipe.case - (^ {try.#Failure error}) + (pattern {try.#Failure error}) true _ @@ -59,7 +59,7 @@ (/phase.result [/extension.#bundle /extension.empty /extension.#state state]) (pipe.case - (^ {try.#Success [inferred analysis]}) + (pattern {try.#Success [inferred analysis]}) (and (type#= type inferred) (? analysis)) @@ -70,7 +70,7 @@ [(: (-> <type> Analysis Bit) (function (_ expected) (|>> (pipe.case - (^ (<tag> actual)) + (pattern (<tag> actual)) (same? expected actual) _ @@ -87,7 +87,7 @@ (`` ($_ _.and (_.cover [/.unit] (..analysis state module .Any /.unit - (|>> (pipe.case (^ (/analysis.unit)) true _ false)))) + (|>> (pipe.case (pattern (/analysis.unit)) true _ false)))) (~~ (template [<analysis> <type> <random> <tag>] [(do ! [sample <random>] diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/case.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/case.lux index c5d7ccd02..ea325ec72 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/case.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/case.lux @@ -72,7 +72,7 @@ (//.phase archive.empty) (phase.result [///bundle.empty synthesis.init]) (pipe.case - (^ {try.#Success (synthesis.branch/let [inputS registerS outputS])}) + (pattern {try.#Success (synthesis.branch/let [inputS registerS outputS])}) (and (n.= registerA registerS) (//primitive.corresponds? inputA inputS) (//primitive.corresponds? outputA outputS)) @@ -101,7 +101,7 @@ (//.phase archive.empty) (phase.result [///bundle.empty synthesis.init]) (pipe.case - (^ {try.#Success (synthesis.branch/if [inputS thenS elseS])}) + (pattern {try.#Success (synthesis.branch/if [inputS thenS elseS])}) (and (//primitive.corresponds? inputA inputS) (//primitive.corresponds? thenA thenS) (//primitive.corresponds? elseA elseS)) @@ -161,7 +161,7 @@ (//.phase archive.empty) (phase.result [///bundle.empty synthesis.init]) (pipe.case - (^ {try.#Success (synthesis.branch/get [pathS recordS])}) + (pattern {try.#Success (synthesis.branch/get [pathS recordS])}) (and (# (list.equivalence (sum.equivalence n.= n.=)) = pathA pathS) (//primitive.corresponds? recordA recordS)) @@ -189,7 +189,7 @@ (random.set hash 5) (# random.monad each (|>> set.list (pipe.case - (^ (list s0 s1 s2 s3 s4)) + (pattern (list s0 s1 s2 s3 s4)) [s0 s1 s2 s3 s4] _ @@ -338,7 +338,7 @@ (|> (/.synthesize_case //.phase archive.empty expected_input match) (phase.result [///bundle.empty synthesis.init]) (pipe.case - (^ {try.#Success (synthesis.branch/case [actual_input actual_path])}) + (pattern {try.#Success (synthesis.branch/case [actual_input actual_path])}) (and (# synthesis.equivalence = expected_input actual_input) (# synthesis.path_equivalence = expected_path actual_path)) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/function.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/function.lux index 79b5c2e8a..ba3f7dc86 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/function.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/function.lux @@ -1,40 +1,42 @@ (.using - [lux "*" - ["_" test {"+" Test}] - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" try]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [number - ["n" nat]] - [collection - ["[0]" list ("[1]#[0]" functor mix monoid)] - ["[0]" dictionary {"+" Dictionary}] - ["[0]" set]]] - [math - ["[0]" random {"+" Random}]]] - ["[0]" // "_" - ["[1][0]" primitive]] - [\\ - ["[0]" / - ["/[1]" // - ["/[1]" // "_" - [extension - ["[1][0]" bundle]] - ["/[1]" // - ["[0]" analysis {"+" Analysis}] - ["[0]" synthesis {"+" Synthesis}] - [/// - [arity {"+" Arity}] - ["[0]" reference - ["[0]" variable {"+" Variable}]] - ["[0]" phase] - [meta - ["[0]" archive]]]]]]]]) + [lux "*" + ["_" test {"+" Test}] + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" try]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [number + ["n" nat]] + [collection + ["[0]" list ("[1]#[0]" functor mix monoid)] + ["[0]" dictionary {"+" Dictionary}] + ["[0]" set]]] + [macro + ["^" pattern]] + [math + ["[0]" random {"+" Random}]]] + ["[0]" // "_" + ["[1][0]" primitive]] + [\\ + ["[0]" / + ["/[1]" // + ["/[1]" // "_" + [extension + ["[1][0]" bundle]] + ["/[1]" // + ["[0]" analysis {"+" Analysis}] + ["[0]" synthesis {"+" Synthesis}] + [/// + [arity {"+" Arity}] + ["[0]" reference + ["[0]" variable {"+" Variable}]] + ["[0]" phase] + [meta + ["[0]" archive]]]]]]]]) (def: (n_function loop? arity body) (-> Bit Arity Synthesis Synthesis) @@ -432,8 +434,8 @@ (|> input (//.phase archive.empty) (phase.result [///bundle.empty synthesis.init]) - (!expect (^multi {try.#Success actual} - (# synthesis.equivalence = expected actual))))))) + (!expect (^.multi {try.#Success actual} + (# synthesis.equivalence = expected actual))))))) (def: application Test @@ -445,15 +447,15 @@ (and (|> (analysis.apply [funcA argsA]) (//.phase archive.empty) (phase.result [///bundle.empty synthesis.init]) - (!expect (^multi (^ {try.#Success (synthesis.function/apply [funcS argsS])}) - (and (//primitive.corresponds? funcA funcS) - (list.every? (product.uncurried //primitive.corresponds?) - (list.zipped/2 argsA argsS)))))) + (!expect (^.multi (pattern {try.#Success (synthesis.function/apply [funcS argsS])}) + (and (//primitive.corresponds? funcA funcS) + (list.every? (product.uncurried //primitive.corresponds?) + (list.zipped/2 argsA argsS)))))) (|> (analysis.apply [funcA (list)]) (//.phase archive.empty) (phase.result [///bundle.empty synthesis.init]) - (!expect (^multi {try.#Success funcS} - (//primitive.corresponds? funcA funcS)))))))) + (!expect (^.multi {try.#Success funcS} + (//primitive.corresponds? funcA funcS)))))))) (def: .public test Test diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/loop.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/loop.lux index 4a89589e2..1f220e13a 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/loop.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/loop.lux @@ -1,27 +1,27 @@ (.using - [lux {"-" structure loop function} - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - ["[0]" try] - ["[0]" exception]] - [data - [number - ["n" nat]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [math - ["[0]" random {"+" Random} ("[1]#[0]" monad)]]] - [\\ - ["[0]" / - [//// - ["[0]" analysis {"+" Environment}] - ["/[1]" synthesis {"+" Member Path Synthesis}] - [/// - [arity {"+" Arity}] - ["[0]" reference {"+" Constant} - ["[0]" variable {"+" Register Variable}]]]]]]) + [lux {"-" structure loop function} + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" try] + ["[0]" exception]] + [data + [number + ["n" nat]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [math + ["[0]" random {"+" Random} ("[1]#[0]" monad)]]] + [\\ + ["[0]" / + [//// + ["[0]" analysis {"+" Environment}] + ["/[1]" synthesis {"+" Member Path Synthesis}] + [/// + [arity {"+" Arity}] + ["[0]" reference {"+" Constant} + ["[0]" variable {"+" Register Variable}]]]]]]) (type: (Scenario a) (-> Register Arity Register (Random [Register [a a]]))) @@ -279,8 +279,8 @@ (list#each (|>> {variable.#Local}))) //.#arity arity //.#body iteration]) - (^ {.#Some (//.loop/scope [actual_offset actual_inits - actual])}) + (pattern {.#Some (//.loop/scope [actual_offset actual_inits + actual])}) (and (n.= expected_offset actual_offset) (# (list.equivalence //.equivalence) = diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/primitive.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/primitive.lux index 159207280..80499a5e2 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/primitive.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/primitive.lux @@ -60,8 +60,8 @@ [////analysis.#Text (|>) ////synthesis.#Text (|>)] )) - (^ [(////analysis.tuple expected) - (////synthesis.tuple actual)]) + (pattern [(////analysis.tuple expected) + (////synthesis.tuple actual)]) (and (n.= (list.size expected) (list.size actual)) (list.every? (function (_ [expected actual]) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/structure.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/structure.lux index 2f66190b4..6adfb95b2 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/structure.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/structure.lux @@ -49,7 +49,7 @@ (//.phase archive.empty) (phase.result [///bundle.empty ////synthesis.init]) (pipe.case - (^ {try.#Success (////synthesis.variant [leftsS right?S valueS])}) + (pattern {try.#Success (////synthesis.variant [leftsS right?S valueS])}) (let [tagS (if right?S (++ leftsS) leftsS)] (and (n.= tagA tagS) (|> tagS (n.= (-- size)) (bit#= right?S)) @@ -68,7 +68,7 @@ (//.phase archive.empty) (phase.result [///bundle.empty ////synthesis.init]) (pipe.case - (^ {try.#Success (////synthesis.tuple membersS)}) + (pattern {try.#Success (////synthesis.tuple membersS)}) (and (n.= size (list.size membersS)) (list.every? (product.uncurried //primitive.corresponds?) (list.zipped/2 membersA membersS))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/variable.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/variable.lux index 42a9d531a..f6085d963 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/variable.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/variable.lux @@ -15,7 +15,9 @@ ["n" nat]] [collection ["[0]" list ("[1]#[0]" functor mix)] - ["[0]" dictionary {"+" Dictionary}]]]] + ["[0]" dictionary {"+" Dictionary}]]] + [macro + ["^" pattern]]] [\\ ["[0]" / [//// @@ -329,6 +331,6 @@ [[expected input] (..scenario ..default)] (_.cover [/.optimization] (|> (/.optimization input) - (!expect (^multi {try.#Success actual} - (# synthesis.equivalence = expected actual)))))) + (!expect (^.multi {try.#Success actual} + (# synthesis.equivalence = expected actual)))))) ))) diff --git a/stdlib/source/test/lux/tool/compiler/meta/archive.lux b/stdlib/source/test/lux/tool/compiler/meta/archive.lux index f89666969..e8b0dbb26 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/archive.lux @@ -137,7 +137,7 @@ /.#registry /registry.empty]] archive (/.has module/0 entry archive) .let [post (/.archived archive) - (^open "list#[0]") (list.equivalence text.equivalence)]] + (open "list#[0]") (list.equivalence text.equivalence)]] (in (and (list#= (list) pre) (list#= (list module/0) post)))) (try.else false))) @@ -153,7 +153,7 @@ archive (/.has module/0 entry archive)] (in (and (list.empty? pre) (case (/.entries archive) - (^ (list [module/0' @module/0' entry'])) + (pattern (list [module/0' @module/0' entry'])) (and (same? module/0 module/0') (same? @module/0 @module/0') (same? entry entry')) diff --git a/stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux b/stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux index b26e16b6a..e347edf4a 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux @@ -70,7 +70,7 @@ (_.cover [/.resource] (let [[@it registry] (/.resource mandatory? expected_dependencies /.empty)] (case (sequence.list (/.artifacts registry)) - (^ (list [artifact actual_dependencies])) + (pattern (list [artifact actual_dependencies])) (and (same? @it (the artifact.#id artifact)) (same? mandatory? (the artifact.#mandatory? artifact)) (tagged? category.#Anonymous (the artifact.#category artifact)) @@ -84,13 +84,13 @@ <wrong_expected> <wrong_expected>'] (and (let [[@it registry] (<new> <expected> mandatory? expected_dependencies /.empty)] (and (case (<query> registry) - (^ (list actual_name)) + (pattern (list actual_name)) (same? <expected> actual_name) _ false) (case (sequence.list (/.artifacts registry)) - (^ (list [artifact actual_dependencies])) + (pattern (list [artifact actual_dependencies])) (and (same? @it (the artifact.#id artifact)) (same? mandatory? (the artifact.#mandatory? artifact)) (case (the artifact.#category artifact) @@ -105,7 +105,7 @@ false))) (let [[@it registry] (<wrong_new> <wrong_expected> mandatory? expected_dependencies /.empty)] (case (<query> registry) - (^ (list)) + (pattern (list)) true _ diff --git a/stdlib/source/test/lux/tool/compiler/meta/cli.lux b/stdlib/source/test/lux/tool/compiler/meta/cli.lux index 725d1f495..ab9504ee5 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/cli.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/cli.lux @@ -33,7 +33,7 @@ Test (<| (_.covering /._) (_.for [/.Service /.service]) - (let [(^open "list#[0]") (list.equivalence text.equivalence)]) + (let [(open "list#[0]") (list.equivalence text.equivalence)]) (do [! random.monad] [amount (# ! each (|>> (n.% 5) ++) random.nat) sources (random.list amount (random.ascii/lower 1)) diff --git a/stdlib/source/test/lux/tool/compiler/meta/export.lux b/stdlib/source/test/lux/tool/compiler/meta/export.lux index 762449a9e..82efdf546 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/export.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/export.lux @@ -80,8 +80,8 @@ (try#each (|>> product.left sequence.list (pipe.case - (^ (list {tar.#Normal [actual_path/0 when/0 mode/0 ownership/0 actual_content/0]} - {tar.#Normal [actual_path/1 when/1 mode/1 ownership/1 actual_content/1]})) + (pattern (list {tar.#Normal [actual_path/0 when/0 mode/0 ownership/0 actual_content/0]} + {tar.#Normal [actual_path/1 when/1 mode/1 ownership/1 actual_content/1]})) (with_expansions [<test> (and (and (text#= file/0' (tar.from_path actual_path/0)) (same? /.mode mode/0) (same? /.ownership ownership/0) @@ -103,8 +103,8 @@ (try#each (|>> product.right sequence.list (pipe.case - (^ (list {tar.#Normal [actual_path/0 _ _ _ actual_content/0]} - {tar.#Normal [actual_path/1 _ _ _ actual_content/1]})) + (pattern (list {tar.#Normal [actual_path/0 _ _ _ actual_content/0]} + {tar.#Normal [actual_path/1 _ _ _ actual_content/1]})) (with_expansions [<test> (and (and (text#= file/0' (tar.from_path actual_path/0)) (binary#= content/0 (tar.data actual_content/0))) (and (text#= file/1' (tar.from_path actual_path/1)) diff --git a/stdlib/source/test/lux/tool/compiler/reference.lux b/stdlib/source/test/lux/tool/compiler/reference.lux index fd76a5146..e938f99b9 100644 --- a/stdlib/source/test/lux/tool/compiler/reference.lux +++ b/stdlib/source/test/lux/tool/compiler/reference.lux @@ -52,7 +52,7 @@ (~~ (template [<tag>] [(_.cover [<tag>] (case (<tag> expected_register) - (^ (<tag> actual_register)) + (pattern (<tag> actual_register)) (n.= expected_register actual_register) _ @@ -65,20 +65,20 @@ (_.cover [/.variable /.self] (and (# /.equivalence = (/.self) (/.variable (variable.self))) (case (/.self) - (^ (/.self)) + (pattern (/.self)) true _ false) (case (/.variable (variable.self)) - (^ (/.self)) + (pattern (/.self)) true _ false))) (_.cover [/.constant] (case (/.constant expected_constant) - (^ (/.constant actual_constant)) + (pattern (/.constant actual_constant)) (symbol#= expected_constant actual_constant) _ diff --git a/stdlib/source/test/lux/tool/compiler/reference/variable.lux b/stdlib/source/test/lux/tool/compiler/reference/variable.lux index 15d0997e4..0c0c88936 100644 --- a/stdlib/source/test/lux/tool/compiler/reference/variable.lux +++ b/stdlib/source/test/lux/tool/compiler/reference/variable.lux @@ -34,7 +34,7 @@ ($hash.spec /.hash ..random)) (_.cover [/.self] (case (/.self) - (^ (/.self)) true + (pattern (/.self)) true _ false)) (_.cover [/.self?] (/.self? (/.self))) diff --git a/stdlib/source/test/lux/type.lux b/stdlib/source/test/lux/type.lux index a9799f045..c173fdc85 100644 --- a/stdlib/source/test/lux/type.lux +++ b/stdlib/source/test/lux/type.lux @@ -16,6 +16,7 @@ ["[0]" list] ["[0]" array]]] [macro + ["^" pattern] ["[0]" code ("[1]#[0]" equivalence)]] [math ["[0]" random {"+" Random} ("[1]#[0]" monad)] @@ -97,15 +98,15 @@ members (|> (..random 0) (random.only (function (_ type) (case type - (^or {.#Sum _} {.#Product _}) + (^.or {.#Sum _} {.#Product _}) #0 _ #1))) (list.repeated size) (monad.all !)) - .let [(^open "/#[0]") /.equivalence - (^open "list#[0]") (list.equivalence /.equivalence)]] + .let [(open "/#[0]") /.equivalence + (open "list#[0]") (list.equivalence /.equivalence)]] (`` ($_ _.and (~~ (template [<ctor> <dtor> <unit>] [(_.cover [<ctor> <dtor>] @@ -132,13 +133,13 @@ extra (|> (..random 0) (random.only (function (_ type) (case type - (^or {.#Function _} {.#Apply _}) + (^.or {.#Function _} {.#Apply _}) #0 _ #1)))) - .let [(^open "/#[0]") /.equivalence - (^open "list#[0]") (list.equivalence /.equivalence)]] + .let [(open "/#[0]") /.equivalence + (open "list#[0]") (list.equivalence /.equivalence)]] ($_ _.and (_.cover [/.function /.flat_function] (let [[inputs output] (|> (/.function members extra) /.flat_function)] @@ -153,12 +154,12 @@ body_type (|> (..random 0) (random.only (function (_ type) (case type - (^or {.#UnivQ _} {.#ExQ _}) + (^.or {.#UnivQ _} {.#ExQ _}) #0 _ #1)))) - .let [(^open "/#[0]") /.equivalence]] + .let [(open "/#[0]") /.equivalence]] (`` ($_ _.and (~~ (template [<ctor> <dtor>] [(_.cover [<ctor> <dtor>] @@ -179,12 +180,12 @@ element_type (|> (..random 0) (random.only (function (_ type) (case type - (^ {.#Primitive name (list element_type)}) + (pattern {.#Primitive name (list element_type)}) (not (text#= array.type_name name)) _ #1)))) - .let [(^open "/#[0]") /.equivalence]] + .let [(open "/#[0]") /.equivalence]] ($_ _.and (_.cover [/.array /.flat_array] (let [[flat_depth flat_element] (|> element_type (/.array depth) /.flat_array)] @@ -229,7 +230,7 @@ (I64 a) (.i64 expected))))) (do random.monad - [.let [(^open "/#[0]") /.equivalence] + [.let [(open "/#[0]") /.equivalence] left (..random 0) right (..random 0)] ($_ _.and diff --git a/stdlib/source/test/lux/type/check.lux b/stdlib/source/test/lux/type/check.lux index 04ab804ec..05ced5386 100644 --- a/stdlib/source/test/lux/type/check.lux +++ b/stdlib/source/test/lux/type/check.lux @@ -22,6 +22,8 @@ [collection ["[0]" list ("[1]#[0]" functor monoid)] ["[0]" set]]] + [macro + ["^" pattern]] [math ["[0]" random {"+" Random} ("[1]#[0]" monad)] [number @@ -77,7 +79,7 @@ {.#Ex id} #1 - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} (and (valid_type? left) (valid_type? right))]) diff --git a/stdlib/source/test/lux/type/implicit.lux b/stdlib/source/test/lux/type/implicit.lux index b061ea059..38e683a02 100644 --- a/stdlib/source/test/lux/type/implicit.lux +++ b/stdlib/source/test/lux/type/implicit.lux @@ -1,23 +1,23 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [equivalence {"+" }] - [functor {"+" }] - [monoid {"+" }] - [monad {"+" do}] - ["[0]" enum]] - [data - ["[0]" bit ("[1]#[0]" equivalence)] - [collection - ["[0]" list]]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [equivalence {"+" }] + [functor {"+" }] + [monoid {"+" }] + [monad {"+" do}] + ["[0]" enum]] + [data + ["[0]" bit ("[1]#[0]" equivalence)] + [collection + ["[0]" list]]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]]) (/.implicit: [n.multiplication]) @@ -36,7 +36,7 @@ ($_ _.and (_.cover [/.##] (let [first_order! - (let [(^open "list#[0]") (list.equivalence n.equivalence)] + (let [(open "list#[0]") (list.equivalence n.equivalence)] (and (bit#= (# n.equivalence = left right) (/.## = left right)) (list#= (# list.functor each ++ (enum.range n.enum start end)) diff --git a/stdlib/source/test/lux/type/unit.lux b/stdlib/source/test/lux/type/unit.lux index c997eadef..714ea853b 100644 --- a/stdlib/source/test/lux/type/unit.lux +++ b/stdlib/source/test/lux/type/unit.lux @@ -1,26 +1,26 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - ["[0]" debug] - ["[0]" meta] - [abstract - [monad {"+" do}] - [equivalence {"+" Equivalence}] - [\\specification - ["$[0]" equivalence] - ["$[0]" order] - ["$[0]" enum]]] - [macro - [syntax {"+" syntax:}] - ["[0]" code]] - [math - ["[0]" random {"+" Random}] - [number - ["i" int] - ["[0]" ratio ("[1]#[0]" equivalence)]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + ["[0]" debug] + ["[0]" meta] + [abstract + [monad {"+" do}] + [equivalence {"+" Equivalence}] + [\\specification + ["$[0]" equivalence] + ["$[0]" order] + ["$[0]" enum]]] + [macro + [syntax {"+" syntax:}] + ["[0]" code]] + [math + ["[0]" random {"+" Random}] + [number + ["i" int] + ["[0]" ratio ("[1]#[0]" equivalence)]]]]] + [\\library + ["[0]" /]]) (template [<name> <type> <unit>] [(def: (<name> range) @@ -101,8 +101,8 @@ (# ! each (i.% +1,000)) (# ! each (i.* +1,000,000,000)) (# ! each (# /.meter in))) - .let [(^open "meter#[0]") (: (Equivalence (/.Qty /.Meter)) - /.equivalence)] + .let [(open "meter#[0]") (: (Equivalence (/.Qty /.Meter)) + /.equivalence)] unscaled (|> random.int (# ! each (i.% +1,000)) (# ! each (i.* (.int how::to))) @@ -156,8 +156,8 @@ Test (do random.monad [.let [zero (# /.meter in +0) - (^open "meter#[0]") (: (Equivalence (/.Qty /.Meter)) - /.equivalence)] + (open "meter#[0]") (: (Equivalence (/.Qty /.Meter)) + /.equivalence)] left (random.only (|>> (meter#= zero) not) (..meter 1,000)) right (..meter 1,000) extra (..second 1,000)] diff --git a/stdlib/source/test/lux/world/file.lux b/stdlib/source/test/lux/world/file.lux index 5c05b5437..f494b7705 100644 --- a/stdlib/source/test/lux/world/file.lux +++ b/stdlib/source/test/lux/world/file.lux @@ -17,6 +17,8 @@ [collection ["[0]" dictionary {"+" Dictionary}] ["[0]" list]]] + [macro + ["^" pattern]] [math ["[0]" random]] [time @@ -70,8 +72,8 @@ [now instant.now disk' (atom.read! disk)] (case (dictionary.value @ disk') - (^or {.#None} - {.#Some {.#Left _}}) + (^.or {.#None} + {.#Some {.#Left _}}) (do ! [_ (atom.compare_and_swap! disk' (dictionary.has @ {.#Left [now it]} disk') disk)] (case (/.parent fs @) diff --git a/stdlib/source/test/lux/world/file/watch.lux b/stdlib/source/test/lux/world/file/watch.lux index cd7c95c46..cbdb160d9 100644 --- a/stdlib/source/test/lux/world/file/watch.lux +++ b/stdlib/source/test/lux/world/file/watch.lux @@ -104,7 +104,7 @@ poll/pre (# watcher poll []) poll/post (# watcher poll [])] (in (and (case poll/pre - (^ (list [concern actual_path])) + (pattern (list [concern actual_path])) (and (text#= expected_path actual_path) (and (/.creation? concern) (not (/.modification? concern)) @@ -122,7 +122,7 @@ poll/2 (# watcher poll []) poll/2' (# watcher poll [])] (in (and (case poll/2 - (^ (list [concern actual_path])) + (pattern (list [concern actual_path])) (and (text#= expected_path actual_path) (and (not (/.creation? concern)) (/.modification? concern) @@ -139,7 +139,7 @@ poll/3 (# watcher poll []) poll/3' (# watcher poll [])] (in (and (case poll/3 - (^ (list [concern actual_path])) + (pattern (list [concern actual_path])) (and (not (/.creation? concern)) (not (/.modification? concern)) (/.deletion? concern)) |