From e00ba096c8837abe85d366e0c1293c09dbe84d81 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Wed, 18 Aug 2021 03:29:15 -0400 Subject: Some bug fixes. --- stdlib/source/library/lux.lux | 90 +++++++++++++++++++++---------------------- 1 file changed, 45 insertions(+), 45 deletions(-) (limited to 'stdlib/source/library/lux.lux') diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux index f9be2bf36..6554978c9 100644 --- a/stdlib/source/library/lux.lux +++ b/stdlib/source/library/lux.lux @@ -2109,8 +2109,8 @@ "... By specifying a pattern (with holes), and the input data to fill those holes, repeats the pattern as many times as necessary." __paragraph "(template [ ]" ..\n " " "[(def: .public (-> Int Int) (+ ))]" __paragraph - " " "[inc +1]" ..\n - " " "[dec -1]"))]) + " " "[++ +1]" ..\n + " " "[-- -1]"))]) ({(#Item [[_ (#Tuple bindings)] (#Item [[_ (#Tuple templates)] data])]) ({[(#Some bindings') (#Some data')] (let' [apply ("lux type check" (-> Replacement_Environment ($' List Code)) @@ -4460,16 +4460,16 @@ (All [a] (-> (List a) (List [Nat a]))) (enumeration' 0 xs)) -(macro: .public (get@ tokens) +(macro: .public (value@ tokens) {#.doc (text$ ($_ "lux text concat" "... Accesses the value of a record at a given tag." ..\n - "(get@ #field my_record)" + "(value@ #field my_record)" __paragraph "... Can also work with multiple levels of nesting:" ..\n - "(get@ [#foo #bar #baz] my_record)" + "(value@ [#foo #bar #baz] my_record)" __paragraph "... And, if only the slot/path is given, generates an accessor function:" ..\n - "(let [getter (get@ [#foo #bar #baz])]" ..\n + "(let [getter (value@ [#foo #bar #baz])]" ..\n " (getter my_record))"))} (case tokens (^ (list [_ (#Tag slot')] record)) @@ -4491,12 +4491,12 @@ (in_meta (list (` ({(~ pattern) (~ g!output)} (~ record)))))) _ - (failure "get@ can only use records."))) + (failure "value@ can only use records."))) (^ (list [_ (#Tuple slots)] record)) (in_meta (list (list\fold (: (-> Code Code Code) (function (_ slot inner) - (` (..get@ (~ slot) (~ inner))))) + (` (..value@ (~ slot) (~ inner))))) record slots))) @@ -4504,10 +4504,10 @@ (do meta_monad [g!_ (..identifier "_") g!record (..identifier "record")] - (in (list (` (function ((~ g!_) (~ g!record)) (..get@ (~ selector) (~ g!record))))))) + (in (list (` (function ((~ g!_) (~ g!record)) (..value@ (~ selector) (~ g!record))))))) _ - (failure "Wrong syntax for get@"))) + (failure "Wrong syntax for value@"))) (def: (open_declaration alias tags my_tag_index [module short] source type) (-> Text (List Name) Nat Name Code Type (Meta (List Code))) @@ -4774,17 +4774,17 @@ _ (failure "Wrong syntax for \"))) -(macro: .public (set@ tokens) +(macro: .public (with@ tokens) {#.doc (text$ ($_ "lux text concat" "... Sets the value of a record at a given tag." ..\n - "(set@ #name ''Lux'' lang)" + "(with@ #name ''Lux'' lang)" __paragraph "... Can also work with multiple levels of nesting:" ..\n - "(set@ [#foo #bar #baz] value my_record)" + "(with@ [#foo #bar #baz] value my_record)" __paragraph "... And, if only the slot/path and (optionally) the value are given, generates a mutator function:" ..\n - "(let [setter (set@ [#foo #bar #baz] value)] (setter my_record))" ..\n - "(let [setter (set@ [#foo #bar #baz])] (setter value my_record))"))} + "(let [setter (with@ [#foo #bar #baz] value)] (setter my_record))" ..\n + "(let [setter (with@ [#foo #bar #baz])] (setter value my_record))"))} (case tokens (^ (list [_ (#Tag slot')] value record)) (do meta_monad @@ -4816,12 +4816,12 @@ (in_meta (list (` ({(~ pattern) (~ output)} (~ record))))))) _ - (failure "set@ can only use records."))) + (failure "with@ can only use records."))) (^ (list [_ (#Tuple slots)] value record)) (case slots #End - (failure "Wrong syntax for set@") + (failure "Wrong syntax for with@") _ (do meta_monad @@ -4832,12 +4832,12 @@ .let [pairs (zipped/2 slots bindings) update_expr (list\fold (: (-> [Code Code] Code Code) (function (_ [s b] v) - (` (..set@ (~ s) (~ v) (~ b))))) + (` (..with@ (~ s) (~ v) (~ b))))) value (list\reverse pairs)) [_ accesses'] (list\fold (: (-> [Code Code] [Code (List (List Code))] [Code (List (List Code))]) (function (_ [new_slot new_binding] [old_record accesses']) - [(` (get@ (~ new_slot) (~ new_binding))) + [(` (value@ (~ new_slot) (~ new_binding))) (#Item (list new_binding old_record) accesses')])) [record (: (List (List Code)) #End)] pairs) @@ -4850,7 +4850,7 @@ [g!_ (..identifier "_") g!record (..identifier "record")] (in (list (` (function ((~ g!_) (~ g!record)) - (..set@ (~ selector) (~ value) (~ g!record))))))) + (..with@ (~ selector) (~ value) (~ g!record))))))) (^ (list selector)) (do meta_monad @@ -4858,22 +4858,22 @@ g!value (..identifier "value") g!record (..identifier "record")] (in (list (` (function ((~ g!_) (~ g!value) (~ g!record)) - (..set@ (~ selector) (~ g!value) (~ g!record))))))) + (..with@ (~ selector) (~ g!value) (~ g!record))))))) _ - (failure "Wrong syntax for set@"))) + (failure "Wrong syntax for with@"))) -(macro: .public (update@ tokens) +(macro: .public (revised@ tokens) {#.doc (text$ ($_ "lux text concat" "... Modifies the value of a record at a given tag, based on some function." ..\n - "(update@ #age inc person)" + "(revised@ #age ++ person)" __paragraph "... Can also work with multiple levels of nesting:" ..\n - "(update@ [#foo #bar #baz] func my_record)" + "(revised@ [#foo #bar #baz] func my_record)" __paragraph "... And, if only the slot/path and (optionally) the value are given, generates a mutator function:" ..\n - "(let [updater (update@ [#foo #bar #baz] func)] (updater my_record))" ..\n - "(let [updater (update@ [#foo #bar #baz])] (updater func my_record))"))} + "(let [updater (revised@ [#foo #bar #baz] func)] (updater my_record))" ..\n + "(let [updater (revised@ [#foo #bar #baz])] (updater func my_record))"))} (case tokens (^ (list [_ (#Tag slot')] fun record)) (do meta_monad @@ -4905,27 +4905,27 @@ (in_meta (list (` ({(~ pattern) (~ output)} (~ record))))))) _ - (failure "update@ can only use records."))) + (failure "revised@ can only use records."))) (^ (list [_ (#Tuple slots)] fun record)) (case slots #End - (failure "Wrong syntax for update@") + (failure "Wrong syntax for revised@") _ (do meta_monad [g!record (..identifier "record") g!temp (..identifier "temp")] (in (list (` (let [(~ g!record) (~ record) - (~ g!temp) (get@ [(~+ slots)] (~ g!record))] - (set@ [(~+ slots)] ((~ fun) (~ g!temp)) (~ g!record)))))))) + (~ g!temp) (value@ [(~+ slots)] (~ g!record))] + (with@ [(~+ slots)] ((~ fun) (~ g!temp)) (~ g!record)))))))) (^ (list selector fun)) (do meta_monad [g!_ (..identifier "_") g!record (..identifier "record")] (in (list (` (function ((~ g!_) (~ g!record)) - (..update@ (~ selector) (~ fun) (~ g!record))))))) + (..revised@ (~ selector) (~ fun) (~ g!record))))))) (^ (list selector)) (do meta_monad @@ -4933,10 +4933,10 @@ g!fun (..identifier "fun") g!record (..identifier "record")] (in (list (` (function ((~ g!_) (~ g!fun) (~ g!record)) - (..update@ (~ selector) (~ g!fun) (~ g!record))))))) + (..revised@ (~ selector) (~ g!fun) (~ g!record))))))) _ - (failure "Wrong syntax for update@"))) + (failure "Wrong syntax for revised@"))) (macro: .public (^template tokens) {#.doc (text$ ($_ "lux text concat" @@ -5047,8 +5047,8 @@ (All [s] (-> (I64 s) (I64 s))) (|>> ( 1)))] - [inc "lux i64 +" "Increment function."] - [dec "lux i64 -" "Decrement function."] + [++ "lux i64 +" "Increment function."] + [-- "lux i64 -" "Decrement function."] ) (def: tag\encode @@ -5107,9 +5107,9 @@ (let [[group_location' parts_text] (list\fold (function (_ part [last_location text_accum]) (let [[part_location part_text] (example_documentation last_location baseline part)] [part_location (text\compose text_accum part_text)])) - [(update@ #column inc group_location) ""] + [(revised@ #column ++ group_location) ""] ( parts))] - [(update@ #column inc group_location') + [(revised@ #column ++ group_location') ($_ text\compose (location_padding baseline prev_location group_location) parts_text @@ -5134,7 +5134,7 @@ (#Documentation_Example example) (let [baseline (baseline_column example) [location _] example - [_ text] (..example_documentation (set@ #.column baseline location) baseline example)] + [_ text] (..example_documentation (with@ #.column baseline location) baseline example)] (text\compose text __paragraph)))) (macro: .public (example tokens) @@ -5147,7 +5147,7 @@ " (loop [count +0" ..\n " x init]" ..\n " (if (< +10 count)" ..\n - " (recur (inc count) (f x))" ..\n + " (recur (++ count) (f x))" ..\n " x)))"))} (in_meta (list (` [(~ location_code) (#.Text (~ (|> tokens @@ -5206,7 +5206,7 @@ (loop [count +0 x init] (if (< +10 count) - (recur (inc count) (f x)) + (recur (++ count) (f x)) x)) "Loops can also be given custom names." @@ -5214,7 +5214,7 @@ [count +0 x init] (if (< +10 count) - (my_loop (inc count) (f x)) + (my_loop (++ count) (f x)) x)))} (let [?params (case tokens (^ (list name [_ (#Tuple bindings)] body)) @@ -5665,7 +5665,7 @@ (macro: .public (^|> tokens) {#.doc (example "Pipes the value being pattern-matched against prior to binding it to a variable." (case input - (^|> value [inc (% 10) (max 1)]) + (^|> value [++ (% 10) (max 1)]) (foo value)))} (case tokens (^ (list& [_meta (#Form (list [_ (#Identifier ["" name])] [_ (#Tuple steps)]))] body branches)) @@ -5696,7 +5696,7 @@ {#.doc "The location of the current expression being analyzed."} (Meta Location) (function (_ compiler) - (#Right [compiler (get@ #location compiler)]))) + (#Right [compiler (value@ #location compiler)]))) (macro: .public (undefined tokens) {#.doc (example "Meant to be used as a stand-in for functions with undefined implementations." @@ -5845,7 +5845,7 @@ (def: target (Meta Text) (function (_ compiler) - (#Right [compiler (get@ [#info #target] compiler)]))) + (#Right [compiler (value@ [#info #target] compiler)]))) (def: (platform_name choice) (-> Code (Meta Text)) -- cgit v1.2.3