From dda05bca0956af5e5b3875c4cc36e61aa04772e4 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Sun, 12 Sep 2021 00:07:08 -0400 Subject: Made the "#" character great again! --- .../specification/compositor/generation/case.lux | 34 +++--- .../specification/compositor/generation/common.lux | 122 ++++++++++----------- .../compositor/generation/function.lux | 36 +++--- .../compositor/generation/primitive.lux | 4 +- .../compositor/generation/reference.lux | 8 +- .../compositor/generation/structure.lux | 18 +-- 6 files changed, 111 insertions(+), 111 deletions(-) (limited to 'stdlib/source/specification/compositor/generation') diff --git a/stdlib/source/specification/compositor/generation/case.lux b/stdlib/source/specification/compositor/generation/case.lux index eb27aea29..52689480e 100644 --- a/stdlib/source/specification/compositor/generation/case.lux +++ b/stdlib/source/specification/compositor/generation/case.lux @@ -40,10 +40,10 @@ (def: .public (verify expected) (-> Frac (Try Any) Bit) - (|>> (case> {#try.Success actual} + (|>> (case> {try.#Success actual} (f.= expected (:as Frac actual)) - {#try.Failure _} + {try.#Failure _} false))) (def: case @@ -85,9 +85,9 @@ [subS subP] case .let [right? (tail? size idx) caseS (synthesis.variant - [#analysis.lefts idx - #analysis.right? right? - #analysis.value subS]) + [analysis.#lefts idx + analysis.#right? right? + analysis.#value subS]) caseP ($_ synthesis.path/seq (if right? (synthesis.side/right idx) @@ -187,11 +187,11 @@ (def: special_path Path - (let [_end_ (synthesis.path/side {#.Left 0}) - _item_ (synthesis.path/side {#.Right 0}) - _head_ (synthesis.path/member {#.Left 0}) - _tail_ (synthesis.path/member {#.Right 0}) - _tuple_ (synthesis.path/side {#.Left 9})] + (let [_end_ (synthesis.path/side {.#Left 0}) + _item_ (synthesis.path/side {.#Right 0}) + _head_ (synthesis.path/member {.#Left 0}) + _tail_ (synthesis.path/member {.#Right 0}) + _tuple_ (synthesis.path/side {.#Left 9})] ($_ synthesis.path/alt ($_ synthesis.path/seq _item_ @@ -219,7 +219,7 @@ analysis.pattern/variant [0 #1] analysis.pattern/tuple (list (analysis.pattern/bind 3) (analysis.pattern/bind 4))) - ... {#Item body #End} + ... {#Item body {#End}} tail (<| analysis.pattern/variant [0 #1] analysis.pattern/tuple (list (analysis.pattern/bind 5)) analysis.pattern/variant [0 #0] @@ -253,28 +253,28 @@ (_.test "CODE" (|> special_input (run "special_input") - (case> {#try.Success output} + (case> {try.#Success output} true - {#try.Failure _} + {try.#Failure _} false))) (_.test "PATTERN_MATCHING 0" (|> (synthesis.branch/case [special_input special_path]) (run "special_path") - (case> {#try.Success output} + (case> {try.#Success output} true - {#try.Failure _} + {try.#Failure _} false))) (_.test "PATTERN_MATCHING 1" (|> (synthesis.branch/case [special_input special_pattern_path]) (run "special_pattern_path") - (case> {#try.Success output} + (case> {try.#Success output} true - {#try.Failure _} + {try.#Failure _} false))) )) diff --git a/stdlib/source/specification/compositor/generation/common.lux b/stdlib/source/specification/compositor/generation/common.lux index 7aad9a7a7..eeaa68a94 100644 --- a/stdlib/source/specification/compositor/generation/common.lux +++ b/stdlib/source/specification/compositor/generation/common.lux @@ -39,13 +39,13 @@ subject r.i64] (with_expansions [ (template [ ] [(_.test - (|> {#synthesis.Extension (list (synthesis.i64 param) + (|> {synthesis.#Extension (list (synthesis.i64 param) (synthesis.i64 subject))} (run (..safe )) - (case> {#try.Success valueT} + (case> {try.#Success valueT} (n.= ( param subject) (:as Nat valueT)) - {#try.Failure _} + {try.#Failure _} false) (let [param ])))] @@ -58,16 +58,16 @@ ($_ _.and (_.test "lux i64 arithmetic-right-shift" - (|> {#synthesis.Extension "lux i64 arithmetic-right-shift" + (|> {synthesis.#Extension "lux i64 arithmetic-right-shift" (list (synthesis.i64 subject) (synthesis.i64 param))} (run (..safe "lux i64 arithmetic-right-shift")) - (case> {#try.Success valueT} + (case> {try.#Success valueT} ("lux i64 =" (i64.arithmetic_right_shifted param subject) (:as I64 valueT)) - {#try.Failure _} + {try.#Failure _} false) (let [param (n.% 64 param)]))) )))) @@ -80,12 +80,12 @@ (`` ($_ _.and (~~ (template [ ] [(_.test - (|> {#synthesis.Extension (list (synthesis.i64 subject))} + (|> {synthesis.#Extension (list (synthesis.i64 subject))} (run (..safe )) - (case> {#try.Success valueT} + (case> {try.#Success valueT} ( ( subject) (:as valueT)) - {#try.Failure _} + {try.#Failure _} false) (let [subject ])))] @@ -97,13 +97,13 @@ )) (~~ (template [ ] [(_.test - (|> {#synthesis.Extension (list (synthesis.i64 param) + (|> {synthesis.#Extension (list (synthesis.i64 param) (synthesis.i64 subject))} (run (..safe )) - (case> {#try.Success valueT} + (case> {try.#Success valueT} ( ( param subject) (:as valueT)) - {#try.Failure _} + {try.#Failure _} false)))] ["lux i64 +" i.+ Int i.=] @@ -128,7 +128,7 @@ (`` ($_ _.and (~~ (template [ ] [(_.test - (|> {#synthesis.Extension (list (synthesis.f64 param) + (|> {synthesis.#Extension (list (synthesis.f64 param) (synthesis.f64 subject))} (run (..safe )) (//case.verify ( param subject))))] @@ -141,10 +141,10 @@ )) (~~ (template [ ] [(_.test - (|> {#synthesis.Extension (list (synthesis.f64 param) + (|> {synthesis.#Extension (list (synthesis.f64 param) (synthesis.f64 subject))} (run (..safe )) - (case> {#try.Success valueV} + (case> {try.#Success valueV} (bit\= ( param subject) (:as Bit valueV)) @@ -156,7 +156,7 @@ )) (~~ (template [ ] [(_.test - (|> {#synthesis.Extension (list)} + (|> {synthesis.#Extension (list)} (run (..safe )) (//case.verify )))] @@ -167,8 +167,8 @@ (_.test "'lux f64 i64 && 'lux i64 f64'" (|> (run (..safe "lux f64 i64") (|> subject synthesis.f64 - (list) {#synthesis.Extension "lux f64 i64"} - (list) {#synthesis.Extension "lux i64 f64"})) + (list) {synthesis.#Extension "lux f64 i64"} + (list) {synthesis.#Extension "lux i64 f64"})) (//case.verify subject))) )))) @@ -184,84 +184,84 @@ .let [sample_lowerS (synthesis.text sample_lower) sample_upperS (synthesis.text sample_upper) sample_alphaS (synthesis.text sample_alpha) - concatenatedS {#synthesis.Extension "lux text concat" (list sample_lowerS sample_upperS)} + concatenatedS {synthesis.#Extension "lux text concat" (list sample_lowerS sample_upperS)} pre_rep_once (format sample_lower sample_upper) post_rep_once (format sample_lower sample_alpha) pre_rep_all (|> sample_lower (list.repeated sample_size) (text.interposed sample_upper)) post_rep_all (|> sample_lower (list.repeated sample_size) (text.interposed sample_alpha))]] ($_ _.and (_.test "Can compare texts for equality." - (and (|> {#synthesis.Extension "lux text =" (list sample_lowerS sample_lowerS)} + (and (|> {synthesis.#Extension "lux text =" (list sample_lowerS sample_lowerS)} (run (..safe "lux text =")) - (case> {#try.Success valueV} + (case> {try.#Success valueV} (:as Bit valueV) _ false)) - (|> {#synthesis.Extension "lux text =" (list sample_upperS sample_lowerS)} + (|> {synthesis.#Extension "lux text =" (list sample_upperS sample_lowerS)} (run (..safe "lux text =")) - (case> {#try.Success valueV} + (case> {try.#Success valueV} (not (:as Bit valueV)) _ false)))) (_.test "Can compare texts for order." - (|> {#synthesis.Extension "lux text <" (list sample_lowerS sample_upperS)} + (|> {synthesis.#Extension "lux text <" (list sample_lowerS sample_upperS)} (run (..safe "lux text <")) - (case> {#try.Success valueV} + (case> {try.#Success valueV} (:as Bit valueV) - {#try.Failure _} + {try.#Failure _} false))) (_.test "Can get length of text." - (|> {#synthesis.Extension "lux text size" (list sample_lowerS)} + (|> {synthesis.#Extension "lux text size" (list sample_lowerS)} (run (..safe "lux text size")) - (case> {#try.Success valueV} + (case> {try.#Success valueV} (n.= sample_size (:as Nat valueV)) _ false))) (_.test "Can concatenate text." - (|> {#synthesis.Extension "lux text size" (list concatenatedS)} + (|> {synthesis.#Extension "lux text size" (list concatenatedS)} (run (..safe "lux text size")) - (case> {#try.Success valueV} + (case> {try.#Success valueV} (n.= (n.* 2 sample_size) (:as Nat valueV)) _ false))) (_.test "Can find index of sub-text." - (and (|> {#synthesis.Extension "lux text index" + (and (|> {synthesis.#Extension "lux text index" (list concatenatedS sample_lowerS (synthesis.i64 +0))} (run (..safe "lux text index")) - (case> (^multi {#try.Success valueV} + (case> (^multi {try.#Success valueV} [(:as (Maybe Nat) valueV) - {#.Some valueV}]) + {.#Some valueV}]) (n.= 0 valueV) _ false)) - (|> {#synthesis.Extension "lux text index" + (|> {synthesis.#Extension "lux text index" (list concatenatedS sample_upperS (synthesis.i64 +0))} (run (..safe "lux text index")) - (case> (^multi {#try.Success valueV} + (case> (^multi {try.#Success valueV} [(:as (Maybe Nat) valueV) - {#.Some valueV}]) + {.#Some valueV}]) (n.= sample_size valueV) _ false)))) (let [test_clip (: (-> (I64 Any) (I64 Any) Text Bit) (function (_ offset length expected) - (|> {#synthesis.Extension "lux text clip" + (|> {synthesis.#Extension "lux text clip" (list concatenatedS (synthesis.i64 offset) (synthesis.i64 length))} (run (..safe "lux text clip")) - (case> (^multi {#try.Success valueV} + (case> (^multi {try.#Success valueV} [(:as (Maybe Text) valueV) - {#.Some valueV}]) + {.#Some valueV}]) (text\= expected valueV) _ @@ -270,13 +270,13 @@ (and (test_clip 0 sample_size sample_lower) (test_clip sample_size sample_size sample_upper)))) (_.test "Can extract individual characters from text." - (|> {#synthesis.Extension "lux text char" + (|> {synthesis.#Extension "lux text char" (list sample_lowerS (synthesis.i64 char_idx))} (run (..safe "lux text char")) - (case> (^multi {#try.Success valueV} + (case> (^multi {try.#Success valueV} [(:as (Maybe Int) valueV) - {#.Some valueV}]) + {.#Some valueV}]) (text.contains? ("lux i64 char" valueV) sample_lower) @@ -290,51 +290,51 @@ [message (r.ascii/alpha 5)] ($_ _.and (_.test "Can log messages." - (|> {#synthesis.Extension "lux io log" + (|> {synthesis.#Extension "lux io log" (list (synthesis.text (format "LOG: " message)))} (run (..safe "lux io log")) - (case> {#try.Success valueV} + (case> {try.#Success valueV} true - {#try.Failure _} + {try.#Failure _} false))) (_.test "Can throw runtime errors." - (and (|> {#synthesis.Extension "lux try" + (and (|> {synthesis.#Extension "lux try" (list (synthesis.function/abstraction - [#synthesis.environment (list) - #synthesis.arity 1 - #synthesis.body {#synthesis.Extension "lux io error" + [synthesis.#environment (list) + synthesis.#arity 1 + synthesis.#body {synthesis.#Extension "lux io error" (list (synthesis.text message))}]))} (run (..safe "lux try")) - (case> (^multi {#try.Success valueV} + (case> (^multi {try.#Success valueV} [(:as (Try Text) valueV) - {#try.Failure error}]) + {try.#Failure error}]) (text.contains? message error) _ false)) - (|> {#synthesis.Extension "lux try" + (|> {synthesis.#Extension "lux try" (list (synthesis.function/abstraction - [#synthesis.environment (list) - #synthesis.arity 1 - #synthesis.body (synthesis.text message)]))} + [synthesis.#environment (list) + synthesis.#arity 1 + synthesis.#body (synthesis.text message)]))} (run (..safe "lux try")) - (case> (^multi {#try.Success valueV} + (case> (^multi {try.#Success valueV} [(:as (Try Text) valueV) - {#try.Success valueV}]) + {try.#Success valueV}]) (text\= message valueV) _ false)))) (_.test "Can obtain current time in milli-seconds." - (|> (synthesis.tuple (list {#synthesis.Extension "lux io current-time" (list)} - {#synthesis.Extension "lux io current-time" (list)})) + (|> (synthesis.tuple (list {synthesis.#Extension "lux io current-time" (list)} + {synthesis.#Extension "lux io current-time" (list)})) (run (..safe "lux io current-time")) - (case> {#try.Success valueV} + (case> {try.#Success valueV} (let [[pre post] (:as [Nat Nat] valueV)] (n.>= pre post)) - {#try.Failure _} + {try.#Failure _} false))) ))) diff --git a/stdlib/source/specification/compositor/generation/function.lux b/stdlib/source/specification/compositor/generation/function.lux index 1708264a2..9a2f68a8a 100644 --- a/stdlib/source/specification/compositor/generation/function.lux +++ b/stdlib/source/specification/compositor/generation/function.lux @@ -43,9 +43,9 @@ local (..local arity)] (in [arity local (synthesis.function/abstraction - [#synthesis.environment (list) - #synthesis.arity arity - #synthesis.body (synthesis.variable/local local)])]))) + [synthesis.#environment (list) + synthesis.#arity arity + synthesis.#body (synthesis.variable/local local)])]))) (def: .public (spec run) (-> Runner Test) @@ -57,39 +57,39 @@ inputsS (list\each (|>> synthesis.f64) inputs)]] ($_ _.and (_.test "Can read arguments." - (|> (synthesis.function/apply [#synthesis.function functionS - #synthesis.arguments inputsS]) + (|> (synthesis.function/apply [synthesis.#function functionS + synthesis.#arguments inputsS]) (run "with_local") (//case.verify expectation))) (_.test "Can partially apply functions." (or (n.= 1 arity) (let [preS (list.first partial_arity inputsS) postS (list.after partial_arity inputsS) - partialS (synthesis.function/apply [#synthesis.function functionS - #synthesis.arguments preS])] - (|> (synthesis.function/apply [#synthesis.function partialS - #synthesis.arguments postS]) + partialS (synthesis.function/apply [synthesis.#function functionS + synthesis.#arguments preS])] + (|> (synthesis.function/apply [synthesis.#function partialS + synthesis.#arguments postS]) (run "partial_application") (//case.verify expectation))))) (_.test "Can read environment." (or (n.= 1 arity) (let [environment (|> partial_arity (enum.range n.enum 1) - (list\each (|>> #reference.Local))) + (list\each (|>> {reference.#Local}))) variableS (if (n.<= partial_arity local) (synthesis.variable/foreign (-- local)) (synthesis.variable/local (|> local (n.- partial_arity)))) inner_arity (n.- partial_arity arity) innerS (synthesis.function/abstraction - [#synthesis.environment environment - #synthesis.arity inner_arity - #synthesis.body variableS]) + [synthesis.#environment environment + synthesis.#arity inner_arity + synthesis.#body variableS]) outerS (synthesis.function/abstraction - [#synthesis.environment (list) - #synthesis.arity partial_arity - #synthesis.body innerS])] - (|> (synthesis.function/apply [#synthesis.function outerS - #synthesis.arguments inputsS]) + [synthesis.#environment (list) + synthesis.#arity partial_arity + synthesis.#body innerS])] + (|> (synthesis.function/apply [synthesis.#function outerS + synthesis.#arguments inputsS]) (run "with_foreign") (//case.verify expectation))))) ))) diff --git a/stdlib/source/specification/compositor/generation/primitive.lux b/stdlib/source/specification/compositor/generation/primitive.lux index 670b30d30..f4bf220a4 100644 --- a/stdlib/source/specification/compositor/generation/primitive.lux +++ b/stdlib/source/specification/compositor/generation/primitive.lux @@ -34,10 +34,10 @@ [expected ] (_.test (%.name (name_of )) (|> (run ( expected)) - (case> {#try.Success actual} + (case> {try.#Success actual} ( expected (:expected actual)) - {#try.Failure _} + {try.#Failure _} false))))] ["bit" synthesis.bit r.bit bit\=] diff --git a/stdlib/source/specification/compositor/generation/reference.lux b/stdlib/source/specification/compositor/generation/reference.lux index d98e660e0..a8391f63a 100644 --- a/stdlib/source/specification/compositor/generation/reference.lux +++ b/stdlib/source/specification/compositor/generation/reference.lux @@ -31,10 +31,10 @@ expected r.safe_frac] (_.test "Definitions." (|> (define name (synthesis.f64 expected)) - (case> {#try.Success actual} + (case> {try.#Success actual} (f.= expected (:as Frac actual)) - {#try.Failure _} + {try.#Failure _} false))))) (def: (variable run) @@ -47,10 +47,10 @@ register (synthesis.variable/local register)]) (run "variable") - (case> {#try.Success actual} + (case> {try.#Success actual} (f.= expected (:as Frac actual)) - {#try.Failure _} + {try.#Failure _} false))))) (def: .public (spec runner definer) diff --git a/stdlib/source/specification/compositor/generation/structure.lux b/stdlib/source/specification/compositor/generation/structure.lux index c98013875..1b98fc558 100644 --- a/stdlib/source/specification/compositor/generation/structure.lux +++ b/stdlib/source/specification/compositor/generation/structure.lux @@ -36,13 +36,13 @@ .let [last?_in (|> num_tags -- (n.= tag_in))] value_in r.i64] (_.test (%.name (name_of synthesis.variant)) - (|> (synthesis.variant [#analysis.lefts (if last?_in + (|> (synthesis.variant [analysis.#lefts (if last?_in (-- tag_in) tag_in) - #analysis.right? last?_in - #analysis.value (synthesis.i64 value_in)]) + analysis.#right? last?_in + analysis.#value (synthesis.i64 value_in)]) (run "variant") - (case> {#try.Success valueT} + (case> {try.#Success valueT} (let [valueT (:as (Array Any) valueT)] (and (n.= 3 (array.size valueT)) (let [tag_out (:as java/lang/Integer (maybe.trusted (array.read! 0 valueT))) @@ -50,17 +50,17 @@ value_out (:as Any (maybe.trusted (array.read! 2 valueT))) same_tag? (|> tag_out ffi.int_to_long (:as Nat) (n.= tag_in)) same_flag? (case last?_out - {#.Some last?_out'} + {.#Some last?_out'} (and last?_in (text\= "" (:as Text last?_out'))) - #.None + {.#None} (not last?_in)) same_value? (|> value_out (:as Int) (i.= value_in))] (and same_tag? same_flag? same_value?)))) - {#try.Failure _} + {try.#Failure _} false))))) (def: (tuple run) @@ -71,14 +71,14 @@ (_.test (%.name (name_of synthesis.tuple)) (|> (synthesis.tuple (list\each (|>> synthesis.i64) tuple_in)) (run "tuple") - (case> {#try.Success tuple_out} + (case> {try.#Success tuple_out} (let [tuple_out (:as (Array Any) tuple_out)] (and (n.= size (array.size tuple_out)) (list.every? (function (_ [left right]) (i.= left (:as Int right))) (list.zipped/2 tuple_in (array.list tuple_out))))) - {#try.Failure _} + {try.#Failure _} false))))) (def: .public (spec runner) -- cgit v1.2.3