From 41495e32d3f5f88b5f189f48dd4fdbfa883c6ac0 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Mon, 14 Mar 2022 18:27:37 -0400 Subject: De-sigil-ification: > --- .../specification/compositor/generation/case.lux | 98 ++++---- .../specification/compositor/generation/common.lux | 258 +++++++++++---------- .../compositor/generation/function.lux | 1 - .../compositor/generation/primitive.lux | 49 ++-- .../compositor/generation/reference.lux | 56 ++--- .../compositor/generation/structure.lux | 106 ++++----- 6 files changed, 297 insertions(+), 271 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 7d6c81a7b..46fd92eb2 100644 --- a/stdlib/source/specification/compositor/generation/case.lux +++ b/stdlib/source/specification/compositor/generation/case.lux @@ -1,32 +1,32 @@ (.using - [lux {"-" case} - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - [pipe {"+" case>}] - ["[0]" try {"+" Try}]] - [data - ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}]] - [number - ["n" nat] - ["f" frac]] - [collection - ["[0]" list ("[1]#[0]" mix)]]] - [math - ["r" random {"+" Random}]] - [tool - [compiler - ["[0]" reference] - ["[0]" analysis] - ["[0]" synthesis {"+" Path Synthesis}] - ["[0]" phase - ["[1]/[0]" synthesis - ["[0]" case]] - ["[0]" extension/synthesis]]]]] - [/// - [common {"+" Runner}]]) + [lux {"-" case} + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" pipe] + ["[0]" try {"+" Try}]] + [data + ["[0]" text ("[1]#[0]" equivalence) + ["%" format {"+" format}]] + [number + ["n" nat] + ["f" frac]] + [collection + ["[0]" list ("[1]#[0]" mix)]]] + [math + ["r" random {"+" Random}]] + [tool + [compiler + ["[0]" reference] + ["[0]" analysis] + ["[0]" synthesis {"+" Path Synthesis}] + ["[0]" phase + ["[1]/[0]" synthesis + ["[0]" case]] + ["[0]" extension/synthesis]]]]] + [/// + [common {"+" Runner}]]) (def: limit Nat 10) @@ -40,11 +40,12 @@ (def: .public (verify expected) (-> Frac (Try Any) Bit) - (|>> (case> {try.#Success actual} - (f.= expected (:as Frac actual)) + (|>> (pipe.case + {try.#Success actual} + (f.= expected (:as Frac actual)) - {try.#Failure _} - false))) + {try.#Failure _} + false))) (def: case (Random [Synthesis Path]) @@ -249,29 +250,32 @@ (_.test "CODE" (|> special_input (run "special_input") - (case> {try.#Success output} - true - - {try.#Failure _} - false))) + (pipe.case + {try.#Success output} + true + + {try.#Failure _} + false))) (_.test "PATTERN_MATCHING 0" (|> (synthesis.branch/case [special_input special_path]) (run "special_path") - (case> {try.#Success output} - true - - {try.#Failure _} - false))) + (pipe.case + {try.#Success output} + true + + {try.#Failure _} + false))) (_.test "PATTERN_MATCHING 1" (|> (synthesis.branch/case [special_input special_pattern_path]) (run "special_pattern_path") - (case> {try.#Success output} - true - - {try.#Failure _} - false))) + (pipe.case + {try.#Success output} + true + + {try.#Failure _} + false))) )) (def: .public (spec run) diff --git a/stdlib/source/specification/compositor/generation/common.lux b/stdlib/source/specification/compositor/generation/common.lux index 88f13e2ae..19041bbb7 100644 --- a/stdlib/source/specification/compositor/generation/common.lux +++ b/stdlib/source/specification/compositor/generation/common.lux @@ -1,32 +1,32 @@ (.using - [lux {"-" i64} - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - [pipe {"+" case>}] - ["[0]" try {"+" Try}]] - [data - ["[0]" bit ("[1]#[0]" equivalence)] - [number - ["[0]" i64] - ["n" nat] - ["i" int] - ["f" frac]] - ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}]] - [collection - ["[0]" list]]] - [math - ["r" random {"+" Random}]] - [tool - [compiler - ["[0]" reference] - ["[0]" synthesis]]]] - ["[0]" // "_" - ["[1][0]" case] - [// - [common {"+" Runner}]]]) + [lux {"-" i64} + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" pipe] + ["[0]" try {"+" Try}]] + [data + ["[0]" bit ("[1]#[0]" equivalence)] + [number + ["[0]" i64] + ["n" nat] + ["i" int] + ["f" frac]] + ["[0]" text ("[1]#[0]" equivalence) + ["%" format {"+" format}]] + [collection + ["[0]" list]]] + [math + ["r" random {"+" Random}]] + [tool + [compiler + ["[0]" reference] + ["[0]" synthesis]]]] + ["[0]" // "_" + ["[1][0]" case] + [// + [common {"+" Runner}]]]) (def: safe (-> Text Text) @@ -42,11 +42,12 @@ (|> {synthesis.#Extension (list (synthesis.i64 param) (synthesis.i64 subject))} (run (..safe )) - (case> {try.#Success valueT} - (n.= ( param subject) (:as Nat valueT)) + (pipe.case + {try.#Success valueT} + (n.= ( param subject) (:as Nat valueT)) - {try.#Failure _} - false) + {try.#Failure _} + false) (let [param ])))] ["lux i64 and" i64.and param] @@ -62,13 +63,14 @@ (list (synthesis.i64 subject) (synthesis.i64 param))} (run (..safe "lux i64 arithmetic-right-shift")) - (case> {try.#Success valueT} - ("lux i64 =" - (i64.arithmetic_right_shifted param subject) - (:as I64 valueT)) - - {try.#Failure _} - false) + (pipe.case + {try.#Success valueT} + ("lux i64 =" + (i64.arithmetic_right_shifted param subject) + (:as I64 valueT)) + + {try.#Failure _} + false) (let [param (n.% 64 param)]))) )))) @@ -82,11 +84,12 @@ [(_.test (|> {synthesis.#Extension (list (synthesis.i64 subject))} (run (..safe )) - (case> {try.#Success valueT} - ( ( subject) (:as valueT)) + (pipe.case + {try.#Success valueT} + ( ( subject) (:as valueT)) - {try.#Failure _} - false) + {try.#Failure _} + false) (let [subject ])))] ["lux i64 f64" Frac i.frac f.= subject] @@ -100,11 +103,12 @@ (|> {synthesis.#Extension (list (synthesis.i64 param) (synthesis.i64 subject))} (run (..safe )) - (case> {try.#Success valueT} - ( ( param subject) (:as valueT)) + (pipe.case + {try.#Success valueT} + ( ( param subject) (:as valueT)) - {try.#Failure _} - false)))] + {try.#Failure _} + false)))] ["lux i64 +" i.+ Int i.=] ["lux i64 -" i.- Int i.=] @@ -144,12 +148,13 @@ (|> {synthesis.#Extension (list (synthesis.f64 param) (synthesis.f64 subject))} (run (..safe )) - (case> {try.#Success valueV} - (bit#= ( param subject) - (:as Bit valueV)) + (pipe.case + {try.#Success valueV} + (bit#= ( param subject) + (:as Bit valueV)) - _ - false)))] + _ + false)))] ["lux f64 =" f.=] ["lux f64 <" f.<] @@ -193,65 +198,72 @@ (_.test "Can compare texts for equality." (and (|> {synthesis.#Extension "lux text =" (list sample_lowerS sample_lowerS)} (run (..safe "lux text =")) - (case> {try.#Success valueV} - (:as Bit valueV) + (pipe.case + {try.#Success valueV} + (:as Bit valueV) - _ - false)) + _ + false)) (|> {synthesis.#Extension "lux text =" (list sample_upperS sample_lowerS)} (run (..safe "lux text =")) - (case> {try.#Success valueV} - (not (:as Bit valueV)) + (pipe.case + {try.#Success valueV} + (not (:as Bit valueV)) - _ - false)))) + _ + false)))) (_.test "Can compare texts for order." (|> {synthesis.#Extension "lux text <" (list sample_lowerS sample_upperS)} (run (..safe "lux text <")) - (case> {try.#Success valueV} - (:as Bit valueV) + (pipe.case + {try.#Success valueV} + (:as Bit valueV) - {try.#Failure _} - false))) + {try.#Failure _} + false))) (_.test "Can get length of text." (|> {synthesis.#Extension "lux text size" (list sample_lowerS)} (run (..safe "lux text size")) - (case> {try.#Success valueV} - (n.= sample_size (:as Nat valueV)) + (pipe.case + {try.#Success valueV} + (n.= sample_size (:as Nat valueV)) - _ - false))) + _ + false))) (_.test "Can concatenate text." (|> {synthesis.#Extension "lux text size" (list concatenatedS)} (run (..safe "lux text size")) - (case> {try.#Success valueV} - (n.= (n.* 2 sample_size) (:as Nat valueV)) + (pipe.case + {try.#Success valueV} + (n.= (n.* 2 sample_size) (:as Nat valueV)) - _ - false))) + _ + false))) (_.test "Can find index of sub-text." (and (|> {synthesis.#Extension "lux text index" (list concatenatedS sample_lowerS (synthesis.i64 +0))} (run (..safe "lux text index")) - (case> (^multi {try.#Success valueV} - [(:as (Maybe Nat) valueV) - {.#Some valueV}]) - (n.= 0 valueV) + (pipe.case + (^multi {try.#Success valueV} + [(:as (Maybe Nat) valueV) + {.#Some valueV}]) + (n.= 0 valueV) - _ - false)) + _ + false)) (|> {synthesis.#Extension "lux text index" (list concatenatedS sample_upperS (synthesis.i64 +0))} (run (..safe "lux text index")) - (case> (^multi {try.#Success valueV} - [(:as (Maybe Nat) valueV) - {.#Some valueV}]) - (n.= sample_size valueV) + (pipe.case + (^multi {try.#Success valueV} + [(:as (Maybe Nat) valueV) + {.#Some valueV}]) + (n.= sample_size valueV) - _ - false)))) + _ + false)))) (let [test_clip (: (-> (I64 Any) (I64 Any) Text Bit) (function (_ offset length expected) (|> {synthesis.#Extension "lux text clip" @@ -259,13 +271,14 @@ (synthesis.i64 offset) (synthesis.i64 length))} (run (..safe "lux text clip")) - (case> (^multi {try.#Success valueV} - [(:as (Maybe Text) valueV) - {.#Some valueV}]) - (text#= expected valueV) - - _ - false))))] + (pipe.case + (^multi {try.#Success valueV} + [(:as (Maybe Text) valueV) + {.#Some valueV}]) + (text#= expected valueV) + + _ + false))))] (_.test "Can clip text to extract sub-text." (and (test_clip 0 sample_size sample_lower) (test_clip sample_size sample_size sample_upper)))) @@ -274,14 +287,15 @@ (list sample_lowerS (synthesis.i64 char_idx))} (run (..safe "lux text char")) - (case> (^multi {try.#Success valueV} - [(:as (Maybe Int) valueV) - {.#Some valueV}]) - (text.contains? ("lux i64 char" valueV) - sample_lower) - - _ - false))) + (pipe.case + (^multi {try.#Success valueV} + [(:as (Maybe Int) valueV) + {.#Some valueV}]) + (text.contains? ("lux i64 char" valueV) + sample_lower) + + _ + false))) ))) (def: (io run) @@ -293,11 +307,12 @@ (|> {synthesis.#Extension "lux io log" (list (synthesis.text (format "LOG: " message)))} (run (..safe "lux io log")) - (case> {try.#Success valueV} - true + (pipe.case + {try.#Success valueV} + true - {try.#Failure _} - false))) + {try.#Failure _} + false))) (_.test "Can throw runtime errors." (and (|> {synthesis.#Extension "lux try" (list (synthesis.function/abstraction @@ -306,36 +321,39 @@ synthesis.#body {synthesis.#Extension "lux io error" (list (synthesis.text message))}]))} (run (..safe "lux try")) - (case> (^multi {try.#Success valueV} - [(:as (Try Text) valueV) - {try.#Failure error}]) - (text.contains? message error) + (pipe.case + (^multi {try.#Success valueV} + [(:as (Try Text) valueV) + {try.#Failure error}]) + (text.contains? message error) - _ - false)) + _ + false)) (|> {synthesis.#Extension "lux try" (list (synthesis.function/abstraction [synthesis.#environment (list) synthesis.#arity 1 synthesis.#body (synthesis.text message)]))} (run (..safe "lux try")) - (case> (^multi {try.#Success valueV} - [(:as (Try Text) valueV) - {try.#Success valueV}]) - (text#= message valueV) + (pipe.case + (^multi {try.#Success valueV} + [(:as (Try Text) valueV) + {try.#Success valueV}]) + (text#= message valueV) - _ - false)))) + _ + 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)})) (run (..safe "lux io current-time")) - (case> {try.#Success valueV} - (let [[pre post] (:as [Nat Nat] valueV)] - (n.>= pre post)) + (pipe.case + {try.#Success valueV} + (let [[pre post] (:as [Nat Nat] valueV)] + (n.>= pre post)) - {try.#Failure _} - false))) + {try.#Failure _} + false))) ))) (def: .public (spec runner) diff --git a/stdlib/source/specification/compositor/generation/function.lux b/stdlib/source/specification/compositor/generation/function.lux index c03971eef..e6bdf79c0 100644 --- a/stdlib/source/specification/compositor/generation/function.lux +++ b/stdlib/source/specification/compositor/generation/function.lux @@ -5,7 +5,6 @@ [monad {"+" do}] ["[0]" enum]] [control - [pipe {"+" case>}] ["[0]" maybe]] [data [number diff --git a/stdlib/source/specification/compositor/generation/primitive.lux b/stdlib/source/specification/compositor/generation/primitive.lux index c7d486553..a193aa16f 100644 --- a/stdlib/source/specification/compositor/generation/primitive.lux +++ b/stdlib/source/specification/compositor/generation/primitive.lux @@ -1,24 +1,24 @@ (.using - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - [pipe {"+" case>}] - ["[0]" try]] - [data - ["[0]" bit ("[1]#[0]" equivalence)] - [number - ["f" frac]] - ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}]]] - [math - ["r" random]] - [tool - [compiler - ["[0]" synthesis]]]] - [/// - [common {"+" Runner}]]) + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" pipe] + ["[0]" try]] + [data + ["[0]" bit ("[1]#[0]" equivalence)] + [number + ["f" frac]] + ["[0]" text ("[1]#[0]" equivalence) + ["%" format {"+" format}]]] + [math + ["r" random]] + [tool + [compiler + ["[0]" synthesis]]]] + [/// + [common {"+" Runner}]]) (def: (f/=' reference subject) (-> Frac Frac Bit) @@ -34,11 +34,12 @@ [expected ] (_.test (%.symbol (symbol )) (|> (run ( expected)) - (case> {try.#Success actual} - ( expected (:expected actual)) + (pipe.case + {try.#Success actual} + ( expected (:expected actual)) - {try.#Failure _} - false))))] + {try.#Failure _} + false))))] ["bit" synthesis.bit r.bit bit#=] ["i64" synthesis.i64 r.i64 "lux i64 ="] diff --git a/stdlib/source/specification/compositor/generation/reference.lux b/stdlib/source/specification/compositor/generation/reference.lux index b3f270445..87c7b605b 100644 --- a/stdlib/source/specification/compositor/generation/reference.lux +++ b/stdlib/source/specification/compositor/generation/reference.lux @@ -1,23 +1,23 @@ (.using - [lux {"-" symbol} - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - [pipe {"+" case>}] - ["[0]" try]] - [data - [number - ["n" nat] - ["f" frac]]] - [tool - [compiler - ["[0]" reference] - ["[0]" synthesis]]] - [math - ["r" random {"+" Random}]]] - [/// - [common {"+" Runner Definer}]]) + [lux {"-" symbol} + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" pipe] + ["[0]" try]] + [data + [number + ["n" nat] + ["f" frac]]] + [tool + [compiler + ["[0]" reference] + ["[0]" synthesis]]] + [math + ["r" random {"+" Random}]]] + [/// + [common {"+" Runner Definer}]]) (def: symbol (Random Symbol) @@ -31,11 +31,12 @@ expected r.safe_frac] (_.test "Definitions." (|> (define name (synthesis.f64 expected)) - (case> {try.#Success actual} - (f.= expected (:as Frac actual)) + (pipe.case + {try.#Success actual} + (f.= expected (:as Frac actual)) - {try.#Failure _} - false))))) + {try.#Failure _} + false))))) (def: (variable run) (-> Runner Test) @@ -47,11 +48,12 @@ register (synthesis.variable/local register)]) (run "variable") - (case> {try.#Success actual} - (f.= expected (:as Frac actual)) + (pipe.case + {try.#Success actual} + (f.= expected (:as Frac actual)) - {try.#Failure _} - false))))) + {try.#Failure _} + false))))) (def: .public (spec runner definer) (-> Runner Definer Test) diff --git a/stdlib/source/specification/compositor/generation/structure.lux b/stdlib/source/specification/compositor/generation/structure.lux index bf852085d..5fe2a809f 100644 --- a/stdlib/source/specification/compositor/generation/structure.lux +++ b/stdlib/source/specification/compositor/generation/structure.lux @@ -1,30 +1,30 @@ (.using - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - [pipe {"+" case>}] - ["[0]" maybe] - ["[0]" try]] - [data - [number - ["n" nat] - ["i" int]] - ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}]] - [collection - ["[0]" array {"+" Array}] - ["[0]" list ("[1]#[0]" functor)]]] - [math - ["r" random]] - ["[0]" ffi {"+" import:}] - [tool - [compiler - ["[0]" analysis] - ["[0]" synthesis]]]] - [/// - [common {"+" Runner}]]) + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" pipe] + ["[0]" maybe] + ["[0]" try]] + [data + [number + ["n" nat] + ["i" int]] + ["[0]" text ("[1]#[0]" equivalence) + ["%" format {"+" format}]] + [collection + ["[0]" array {"+" Array}] + ["[0]" list ("[1]#[0]" functor)]]] + [math + ["r" random]] + ["[0]" ffi {"+" import:}] + [tool + [compiler + ["[0]" analysis] + ["[0]" synthesis]]]] + [/// + [common {"+" Runner}]]) (import: java/lang/Integer) @@ -42,26 +42,27 @@ analysis.#right? last?_in analysis.#value (synthesis.i64 value_in)]) (run "variant") - (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))) - last?_out (array.read! 1 valueT) - 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'} - (and last?_in (text#= "" (:as Text last?_out'))) + (pipe.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))) + last?_out (array.read! 1 valueT) + 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'} + (and last?_in (text#= "" (:as Text last?_out'))) - {.#None} - (not last?_in)) - same_value? (|> value_out (:as Int) (i.= value_in))] - (and same_tag? - same_flag? - same_value?)))) + {.#None} + (not last?_in)) + same_value? (|> value_out (:as Int) (i.= value_in))] + (and same_tag? + same_flag? + same_value?)))) - {try.#Failure _} - false))))) + {try.#Failure _} + false))))) (def: (tuple run) (-> Runner Test) @@ -71,15 +72,16 @@ (_.test (%.symbol (symbol synthesis.tuple)) (|> (synthesis.tuple (list#each (|>> synthesis.i64) tuple_in)) (run "tuple") - (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))))) + (pipe.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 _} - false))))) + {try.#Failure _} + false))))) (def: .public (spec runner) (-> Runner Test) -- cgit v1.2.3