From ae2d5697d93a45dcbff768c32c4dc8fb291096cd Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Sat, 7 Jan 2023 18:55:20 -0400 Subject: Now wrapping C++ values inside a universal box. --- .../specification/compositor/generation/case.lux | 290 ----------------- .../specification/compositor/generation/common.lux | 350 --------------------- .../compositor/generation/function.lux | 96 ------ .../compositor/generation/primitive.lux | 51 --- .../compositor/generation/reference.lux | 64 ---- .../compositor/generation/structure.lux | 93 ------ 6 files changed, 944 deletions(-) delete mode 100644 stdlib/source/specification/compositor/generation/case.lux delete mode 100644 stdlib/source/specification/compositor/generation/common.lux delete mode 100644 stdlib/source/specification/compositor/generation/function.lux delete mode 100644 stdlib/source/specification/compositor/generation/primitive.lux delete mode 100644 stdlib/source/specification/compositor/generation/reference.lux delete mode 100644 stdlib/source/specification/compositor/generation/structure.lux (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 deleted file mode 100644 index 5b36db339..000000000 --- a/stdlib/source/specification/compositor/generation/case.lux +++ /dev/null @@ -1,290 +0,0 @@ -(.require - [library - [lux (.except when) - [abstract - [monad (.only do)]] - [control - ["[0]" pipe] - ["[0]" try (.only Try)]] - [data - ["[0]" text (.use "[1]#[0]" equivalence) - ["%" \\format (.only format)]] - [number - ["n" nat] - ["f" frac]] - [collection - ["[0]" list (.use "[1]#[0]" mix)]]] - [math - ["r" random (.only Random)]] - [meta - [compiler - ["[0]" reference] - ["[0]" analysis] - ["[0]" synthesis (.only Path Synthesis)] - ["[0]" phase - ["[1]/[0]" synthesis - ["[0]" when]] - ["[0]" extension/synthesis]]]] - [test - ["_" property (.only Test)]]]] - [/// - [common (.only Runner)]]) - -(def limit Nat 10) - -(def size - (Random Nat) - (|> r.nat (of r.monad each (|>> (n.% ..limit) (n.max 2))))) - -(def (tail? size idx) - (-> Nat Nat Bit) - (n.= (-- size) idx)) - -(def .public (verify expected) - (-> Frac (Try Any) Bit) - (|>> (pipe.when - {try.#Success actual} - (f.= expected (as Frac actual)) - - {try.#Failure _} - false))) - -(def when - (Random [Synthesis Path]) - (<| r.rec (function (_ when)) - (`` (all r.either - (do r.monad - [value r.i64] - (in [(synthesis.i64 value) - synthesis.path/pop])) - (,, (with_template [ ] - [(do r.monad - [value ] - (in [( value) - ( value)]))] - - [r.bit synthesis.bit synthesis.path/bit] - [r.i64 synthesis.i64 synthesis.path/i64] - [r.frac synthesis.f64 synthesis.path/f64] - [(r.unicode 5) synthesis.text synthesis.path/text])) - (do [! r.monad] - [size ..size - idx (|> r.nat (of ! each (n.% size))) - [subS subP] when - .let [unitS (synthesis.text synthesis.unit) - whenS (synthesis.tuple - (list.together (list (list.repeated idx unitS) - (list subS) - (list.repeated (|> size -- (n.- idx)) unitS)))) - whenP (all synthesis.path/seq - (if (tail? size idx) - (synthesis.member/right idx) - (synthesis.member/left idx)) - subP)]] - (in [whenS whenP])) - (do [! r.monad] - [size ..size - idx (|> r.nat (of ! each (n.% size))) - [subS subP] when - .let [right? (tail? size idx) - whenS (synthesis.variant - [analysis.#lefts idx - analysis.#right? right? - analysis.#value subS]) - whenP (all synthesis.path/seq - (if right? - (synthesis.side/right idx) - (synthesis.side/left idx)) - subP)]] - (in [whenS whenP])) - )))) - -(def (let_spec run) - (-> Runner Test) - (do r.monad - [value r.safe_frac] - (_.test (%.symbol (symbol synthesis.branch/let)) - (|> (synthesis.branch/let [(synthesis.f64 value) - 0 - (synthesis.variable/local 0)]) - (run "let_spec") - (verify value))))) - -(def (if_spec run) - (-> Runner Test) - (do r.monad - [on_true r.safe_frac - on_false (|> r.safe_frac (r.only (|>> (f.= on_true) not))) - verdict r.bit] - (_.test (%.symbol (symbol synthesis.branch/if)) - (|> (synthesis.branch/if [(synthesis.bit verdict) - (synthesis.f64 on_true) - (synthesis.f64 on_false)]) - (run "if_spec") - (verify (if verdict on_true on_false)))))) - -(def (when_spec run) - (-> Runner Test) - (do r.monad - [[inputS pathS] ..when - on_success r.safe_frac - on_failure (|> r.safe_frac (r.only (|>> (f.= on_success) not)))] - (_.test (%.symbol (symbol synthesis.branch/when)) - (|> (synthesis.branch/when - [inputS - (all synthesis.path/alt - (all synthesis.path/seq - pathS - (synthesis.path/then (synthesis.f64 on_success))) - (synthesis.path/then (synthesis.f64 on_failure)))]) - (run "when_spec") - (verify on_success))))) - -(def special_input - Synthesis - (let [_cursor_ (is Synthesis - (synthesis.tuple (list (synthesis.text .prelude) - (synthesis.i64 +901) - (synthesis.i64 +13)))) - _code_ (is (-> Synthesis Synthesis) - (function (_ content) - (synthesis.tuple (list _cursor_ content)))) - _end_ (is Synthesis - (synthesis.variant [0 #0 (synthesis.text "")])) - _item_ (is (-> Synthesis Synthesis Synthesis) - (function (_ head tail) - (synthesis.variant [0 #1 (synthesis.tuple (list head tail))]))) - _list_ (is (-> (List Synthesis) Synthesis) - (list#mix _item_ _end_))] - (let [__tuple__ (is (-> (List Synthesis) Synthesis) - (|>> list.reversed _list_ [9 #0] synthesis.variant _code_)) - __form__ (is (-> (List Synthesis) Synthesis) - (|>> list.reversed _list_ [7 #0] synthesis.variant _code_)) - __text__ (is (-> Text Synthesis) - (function (_ value) - (_code_ (synthesis.variant [5 #0 (synthesis.text value)])))) - __symbol__ (is (-> Symbol Synthesis) - (function (_ [module short]) - (_code_ (synthesis.variant [6 #0 (synthesis.tuple (list (synthesis.text module) - (synthesis.text short)))])))) - __list__ (is (-> (List Synthesis) Synthesis) - (list#mix (function (_ head tail) - (__form__ (list (__tag__ ["" "Item"]) head tail))) - (__tag__ ["" "End"]))) - __apply__ (is (-> Synthesis Synthesis Synthesis) - (function (_ func arg) - (__form__ (list func arg))))] - (|> _end_ - (_item_ (__apply__ (__symbol__ ["" "form$"]) - (__list__ (list (__apply__ (__symbol__ ["" "tag$"]) - (__tuple__ (list (__text__ .prelude) - (__text__ "Item")))) - (__symbol__ ["" "export?-meta"]) - (__symbol__ ["" "tail"]))))) - (_item_ (__tuple__ (list (__symbol__ ["" "tail"])))) - )))) - -(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})] - (all synthesis.path/alt - (all synthesis.path/seq - _item_ - _head_ - _head_ (synthesis.path/bind 2) synthesis.path/pop - _tail_ _tuple_ _item_ - _head_ (synthesis.path/bind 3) synthesis.path/pop - _tail_ (synthesis.path/bind 4) synthesis.path/pop - synthesis.path/pop synthesis.path/pop synthesis.path/pop synthesis.path/pop - _tail_ _item_ - _head_ (synthesis.path/bind 5) synthesis.path/pop - _tail_ _end_ - ... THEN - (synthesis.path/then (synthesis.bit #1))) - (all synthesis.path/seq - (synthesis.path/bind 2) - ... THEN - (synthesis.path/then (synthesis.bit #0)))))) - -(def special_pattern - analysis.Pattern - (let [... [_ {#Tuple {#Item arg args'}}] - head (<| analysis.pattern/tuple (list (analysis.pattern/bind 2)) - analysis.pattern/variant [9 #0] - analysis.pattern/variant [0 #1] - analysis.pattern/tuple (list (analysis.pattern/bind 3) - (analysis.pattern/bind 4))) - ... {#Item body {#End}} - tail (<| analysis.pattern/variant [0 #1] - analysis.pattern/tuple (list (analysis.pattern/bind 5)) - analysis.pattern/variant [0 #0] - (analysis.pattern/unit))] - ... {#Item } - (<| analysis.pattern/variant [0 #1] - (analysis.pattern/tuple (list head tail))))) - -(def special_pattern_path - Path - (all synthesis.path/alt - (<| try.trusted - (phase.result [extension/synthesis.bundle - synthesis.init]) - (when.path phase/synthesis.phase - special_pattern) - (analysis.bit #1)) - (all synthesis.path/seq - (synthesis.path/bind 2) - ... THEN - (synthesis.path/then (synthesis.bit #0))))) - -... TODO: Get rid of this ASAP -(def (special_spec run) - (-> Runner Test) - (all _.and - (_.test "===" - (and (text#= (synthesis.%path special_path) - (synthesis.%path special_pattern_path)) - (of synthesis.path_equivalence = special_path special_pattern_path))) - (_.test "CODE" - (|> special_input - (run "special_input") - (pipe.when - {try.#Success output} - true - - {try.#Failure _} - false))) - (_.test "PATTERN_MATCHING 0" - (|> (synthesis.branch/when [special_input - special_path]) - (run "special_path") - (pipe.when - {try.#Success output} - true - - {try.#Failure _} - false))) - (_.test "PATTERN_MATCHING 1" - (|> (synthesis.branch/when [special_input - special_pattern_path]) - (run "special_pattern_path") - (pipe.when - {try.#Success output} - true - - {try.#Failure _} - false))) - )) - -(def .public (spec run) - (-> Runner Test) - (all _.and - (..special_spec run) - (..let_spec run) - (..if_spec run) - (..when_spec run) - )) diff --git a/stdlib/source/specification/compositor/generation/common.lux b/stdlib/source/specification/compositor/generation/common.lux deleted file mode 100644 index acb782c1f..000000000 --- a/stdlib/source/specification/compositor/generation/common.lux +++ /dev/null @@ -1,350 +0,0 @@ -(.require - [library - [lux (.except i64) - [abstract - [monad (.only do)]] - [control - ["[0]" pipe] - ["[0]" try (.only Try)]] - [data - ["[0]" bit (.use "[1]#[0]" equivalence)] - [number - ["[0]" i64] - ["n" nat] - ["i" int] - ["f" frac]] - ["[0]" text (.use "[1]#[0]" equivalence) - ["%" \\format (.only format)]] - [collection - ["[0]" list]]] - [math - ["r" random (.only Random)]] - [meta - [macro - ["^" pattern]] - [compiler - ["[0]" reference] - ["[0]" synthesis]]] - [test - ["_" property (.only Test)]]]] - ["[0]" // - ["[1][0]" when] - [// - [common (.only Runner)]]]) - -(def safe - (-> Text Text) - (text.replaced " " "_")) - -(def (bit run) - (-> Runner Test) - (do r.monad - [param r.i64 - subject r.i64] - (with_expansions [ (with_template [ ] - [(_.test - (|> {synthesis.#Extension (symbol ) (list (synthesis.i64 param) - (synthesis.i64 subject))} - (run (..safe )) - (pipe.when - {try.#Success valueT} - (n.= ( param subject) (as Nat valueT)) - - {try.#Failure _} - false) - (let [param ])))] - - [.i64_and# i64.and param] - [.i64_or# i64.or param] - [.i64_xor# i64.xor param] - [.i64_left# i64.left_shifted (n.% 64 param)] - ["lux i64 logical-right-shift" i64.logic_right_shifted (n.% 64 param)] - )] - (all _.and - - (_.test "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")) - (pipe.when - {try.#Success valueT} - (.i64_=# (i64.arithmetic_right_shifted param subject) - (as I64 valueT)) - - {try.#Failure _} - false) - (let [param (n.% 64 param)]))) - )))) - -(def (i64 run) - (-> Runner Test) - (do r.monad - [param (|> r.i64 (r.only (|>> (.i64_=# 0) not))) - subject r.i64] - (`` (all _.and - (,, (with_template [ ] - [(_.test - (|> {synthesis.#Extension (symbol ) (list (synthesis.i64 subject))} - (run (..safe )) - (pipe.when - {try.#Success valueT} - ( ( subject) (as valueT)) - - {try.#Failure _} - false) - (let [subject ])))] - - [.int_f64# Frac i.frac f.= subject] - [.int_char# Text (|>> (as Nat) text.from_code) text#= (|> subject - (as Nat) - (n.% (i64.left_shifted 8 1)) - (as Int))] - )) - (,, (with_template [ ] - [(_.test - (|> {synthesis.#Extension (symbol ) (list (synthesis.i64 param) - (synthesis.i64 subject))} - (run (..safe )) - (pipe.when - {try.#Success valueT} - ( ( param subject) (as valueT)) - - {try.#Failure _} - false)))] - - [.i64_+# i.+ Int i.=] - [.i64_-# i.- Int i.=] - [.i64_=# i.= Bit bit#=] - - [.int_<# i.< Bit bit#=] - [.int_*# i.* Int i.=] - [.int_/# i./ Int i.=] - [.int_%# i.% Int i.=] - )) - )))) - -(def simple_frac - (Random Frac) - (|> r.nat (of r.monad each (|>> (n.% 1000) .int i.frac)))) - -(def (f64 run) - (-> Runner Test) - (do r.monad - [param (|> ..simple_frac (r.only (|>> (f.= +0.0) not))) - subject ..simple_frac] - (`` (all _.and - (,, (with_template [ ] - [(_.test - (|> {synthesis.#Extension (symbol ) (list (synthesis.f64 param) - (synthesis.f64 subject))} - (run (..safe )) - (//when.verify ( param subject))))] - - [.f64_+# f.+ f.=] - [.f64_-# f.- f.=] - [.f64_*# f.* f.=] - [.f64_/# f./ f.=] - [.f64_%# f.% f.=] - )) - (,, (with_template [ ] - [(_.test - (|> {synthesis.#Extension (symbol ) (list (synthesis.f64 param) - (synthesis.f64 subject))} - (run (..safe )) - (pipe.when - {try.#Success valueV} - (bit#= ( param subject) - (as Bit valueV)) - - _ - false)))] - - [.f64_=# f.=] - [.f64_<# f.<] - )) - (_.test ".f64_int# && .int_f64#" - (|> (run (..safe .f64_int#) - (|> subject synthesis.f64 - (list) {synthesis.#Extension (symbol .f64_int#)} - (list) {synthesis.#Extension (symbol .int_f64#)})) - (//when.verify subject))) - )))) - -(def (text run) - (-> Runner Test) - (do [! r.monad] - [sample_size (|> r.nat (of ! each (|>> (n.% 10) (n.max 1)))) - sample_lower (r.lower_case_alpha sample_size) - sample_upper (r.upper_case_alpha sample_size) - sample_alpha (|> (r.alphabetic sample_size) - (r.only (|>> (text#= sample_upper) not))) - char_idx (|> r.nat (of ! each (n.% sample_size))) - .let [sample_lowerS (synthesis.text sample_lower) - sample_upperS (synthesis.text sample_upper) - sample_alphaS (synthesis.text sample_alpha) - concatenatedS {synthesis.#Extension (symbol .text_composite#) (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))]] - (all _.and - (_.test "Can compare texts for equality." - (and (|> {synthesis.#Extension (symbol .text_=#) (list sample_lowerS sample_lowerS)} - (run (..safe .text_=#)) - (pipe.when - {try.#Success valueV} - (as Bit valueV) - - _ - false)) - (|> {synthesis.#Extension (symbol .text_=#) (list sample_upperS sample_lowerS)} - (run (..safe .text_=#)) - (pipe.when - {try.#Success valueV} - (not (as Bit valueV)) - - _ - false)))) - (_.test "Can compare texts for order." - (|> {synthesis.#Extension (symbol .text_<#) (list sample_lowerS sample_upperS)} - (run (..safe .text_<#)) - (pipe.when - {try.#Success valueV} - (as Bit valueV) - - {try.#Failure _} - false))) - (_.test "Can get length of text." - (|> {synthesis.#Extension (symbol .text_size#) (list sample_lowerS)} - (run (..safe .text_size#)) - (pipe.when - {try.#Success valueV} - (n.= sample_size (as Nat valueV)) - - _ - false))) - (_.test "Can concatenate text." - (|> {synthesis.#Extension (symbol .text_size#) (list concatenatedS)} - (run (..safe .text_size#)) - (pipe.when - {try.#Success valueV} - (n.= (n.* 2 sample_size) (as Nat valueV)) - - _ - false))) - (_.test "Can find index of sub-text." - (and (|> {synthesis.#Extension (symbol .text_index#) - (list concatenatedS sample_lowerS - (synthesis.i64 +0))} - (run (..safe .text_index#)) - (pipe.when - (^.multi {try.#Success valueV} - [(as (Maybe Nat) valueV) - {.#Some valueV}]) - (n.= 0 valueV) - - _ - false)) - (|> {synthesis.#Extension (symbol .text_index#) - (list concatenatedS sample_upperS - (synthesis.i64 +0))} - (run (..safe .text_index#)) - (pipe.when - (^.multi {try.#Success valueV} - [(as (Maybe Nat) valueV) - {.#Some valueV}]) - (n.= sample_size valueV) - - _ - false)))) - (let [test_clip (is (-> (I64 Any) (I64 Any) Text Bit) - (function (_ offset length expected) - (|> {synthesis.#Extension (symbol .text_clip#) - (list concatenatedS - (synthesis.i64 offset) - (synthesis.i64 length))} - (run (..safe .text_clip#)) - (pipe.when - (^.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)))) - (_.test "Can extract individual characters from text." - (|> {synthesis.#Extension (symbol .text_char#) - (list sample_lowerS - (synthesis.i64 char_idx))} - (run (..safe .text_char#)) - (pipe.when - (^.multi {try.#Success valueV} - [(as (Maybe Int) valueV) - {.#Some valueV}]) - (text.contains? (.int_char# valueV) - sample_lower) - - _ - false))) - ))) - -(def (io run) - (-> Runner Test) - (do r.monad - [message (r.alphabetic 5)] - (all _.and - (_.test "Can log messages." - (|> {synthesis.#Extension .log!# - (list (synthesis.text (format "LOG: " message)))} - (run (..safe .log!#)) - (pipe.when - {try.#Success valueV} - true - - {try.#Failure _} - false))) - (_.test "Can throw runtime errors." - (and (|> {synthesis.#Extension .try# - (list (synthesis.function/abstraction - [synthesis.#environment (list) - synthesis.#arity 1 - synthesis.#body {synthesis.#Extension (symbol .error#) - (list (synthesis.text message))}]))} - (run (..safe .try#)) - (pipe.when - (^.multi {try.#Success valueV} - [(as (Try Text) valueV) - {try.#Failure error}]) - (text.contains? message error) - - _ - false)) - (|> {synthesis.#Extension .try# - (list (synthesis.function/abstraction - [synthesis.#environment (list) - synthesis.#arity 1 - synthesis.#body (synthesis.text message)]))} - (run (..safe .try#)) - (pipe.when - (^.multi {try.#Success valueV} - [(as (Try Text) valueV) - {try.#Success valueV}]) - (text#= message valueV) - - _ - false)))) - ))) - -(def .public (spec runner) - (-> Runner Test) - (all _.and - (..bit runner) - (..i64 runner) - (..f64 runner) - (..text runner) - (..io runner) - )) diff --git a/stdlib/source/specification/compositor/generation/function.lux b/stdlib/source/specification/compositor/generation/function.lux deleted file mode 100644 index 63b025065..000000000 --- a/stdlib/source/specification/compositor/generation/function.lux +++ /dev/null @@ -1,96 +0,0 @@ -(.require - [library - [lux (.except function) - [abstract - [monad (.only do)] - ["[0]" enum]] - [control - ["[0]" maybe]] - [data - [number - ["n" nat]] - [collection - ["[0]" list (.use "[1]#[0]" functor)]]] - [math - ["r" random (.only Random) (.use "[1]#[0]" monad)]] - [meta - [compiler - [analysis (.only Arity)] - ["[0]" reference (.only Register)] - ["[0]" synthesis (.only Synthesis)]]]] - [test - ["_" property (.only Test)]]] - ["[0]" // - ["[1][0]" case] - [// - [common (.only Runner)]]]) - -(def max_arity - Arity - 10) - -(def arity - (Random Arity) - (|> r.nat (r#each (|>> (n.% max_arity) (n.max 1))))) - -(def (local arity) - (-> Arity (Random Register)) - (|> r.nat (r#each (|>> (n.% arity) ++)))) - -(def function - (Random [Arity Register Synthesis]) - (do r.monad - [arity ..arity - local (..local arity)] - (in [arity local - (synthesis.function/abstraction - [synthesis.#environment (list) - synthesis.#arity arity - synthesis.#body (synthesis.variable/local local)])]))) - -(def .public (spec run) - (-> Runner Test) - (do [! r.monad] - [[arity local functionS] ..function - partial_arity (|> r.nat (of ! each (|>> (n.% arity) (n.max 1)))) - inputs (r.list arity r.safe_frac) - .let [expectation (maybe.trusted (list.item (-- local) inputs)) - inputsS (list#each (|>> synthesis.f64) inputs)]] - (all _.and - (_.test "Can read arguments." - (|> (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]) - (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}))) - 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]) - outerS (synthesis.function/abstraction - [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 deleted file mode 100644 index 167f219e8..000000000 --- a/stdlib/source/specification/compositor/generation/primitive.lux +++ /dev/null @@ -1,51 +0,0 @@ -(.require - [library - [lux (.except) - [abstract - [monad (.only do)]] - [control - ["[0]" pipe] - ["[0]" try]] - [data - ["[0]" bit (.use "[1]#[0]" equivalence)] - [number - ["f" frac]] - ["[0]" text (.use "[1]#[0]" equivalence) - ["%" \\format (.only format)]]] - [math - ["r" random]] - [meta - [compiler - ["[0]" synthesis]]] - [test - ["_" property (.only Test)]]]] - [/// - [common (.only Runner)]]) - -(def (f/=' reference subject) - (-> Frac Frac Bit) - (or (f.= reference subject) - (and (f.not_a_number? reference) - (f.not_a_number? subject)))) - -(def .public (spec run) - (-> Runner Test) - (`` (all _.and - (,, (with_template [ ] - [(do r.monad - [expected ] - (_.test (%.symbol (symbol )) - (|> (run ( expected)) - (pipe.when - {try.#Success actual} - ( expected (as_expected actual)) - - {try.#Failure _} - false))))] - - ["bit" synthesis.bit r.bit bit#=] - ["i64" synthesis.i64 r.i64 .i64_=#] - ["f64" synthesis.f64 r.frac f.='] - ["text" synthesis.text (r.ascii 5) text#=] - )) - ))) diff --git a/stdlib/source/specification/compositor/generation/reference.lux b/stdlib/source/specification/compositor/generation/reference.lux deleted file mode 100644 index 74c556d80..000000000 --- a/stdlib/source/specification/compositor/generation/reference.lux +++ /dev/null @@ -1,64 +0,0 @@ -(.require - [library - [lux (.except symbol) - [abstract - [monad (.only do)]] - [control - ["[0]" pipe] - ["[0]" try]] - [data - [number - ["n" nat] - ["f" frac]]] - [meta - [compiler - ["[0]" reference] - ["[0]" synthesis]]] - [math - ["r" random (.only Random)]] - [test - ["_" property (.only Test)]]]] - [/// - [common (.only Runner Definer)]]) - -(def symbol - (Random Symbol) - (let [symbol_part (r.upper_case_alpha 5)] - [(r.and symbol_part symbol_part)])) - -(def (definition define) - (-> Definer Test) - (do r.monad - [name ..symbol - expected r.safe_frac] - (_.test "Definitions." - (|> (define name (synthesis.f64 expected)) - (pipe.when - {try.#Success actual} - (f.= expected (as Frac actual)) - - {try.#Failure _} - false))))) - -(def (variable run) - (-> Runner Test) - (do [! r.monad] - [register (|> r.nat (of ! each (n.% 100))) - expected r.safe_frac] - (_.test "Local variables." - (|> (synthesis.branch/let [(synthesis.f64 expected) - register - (synthesis.variable/local register)]) - (run "variable") - (pipe.when - {try.#Success actual} - (f.= expected (as Frac actual)) - - {try.#Failure _} - false))))) - -(def .public (spec runner definer) - (-> Runner Definer Test) - (all _.and - (..definition definer) - (..variable runner))) diff --git a/stdlib/source/specification/compositor/generation/structure.lux b/stdlib/source/specification/compositor/generation/structure.lux deleted file mode 100644 index b28648520..000000000 --- a/stdlib/source/specification/compositor/generation/structure.lux +++ /dev/null @@ -1,93 +0,0 @@ -(.require - [library - [lux (.except) - ["[0]" ffi (.only import)] - [abstract - [monad (.only do)]] - [control - ["[0]" pipe] - ["[0]" maybe] - ["[0]" try]] - [data - [number - ["n" nat] - ["i" int]] - ["[0]" text (.use "[1]#[0]" equivalence) - ["%" \\format (.only format)]] - [collection - ["[0]" array (.only Array)] - ["[0]" list (.use "[1]#[0]" functor)]]] - [math - ["r" random]] - [meta - [compiler - ["[0]" analysis] - ["[0]" synthesis]]] - [test - ["_" property (.only Test)]]]] - [/// - [common (.only Runner)]]) - -(import java/lang/Integer) - -(def (variant run) - (-> Runner Test) - (do [! r.monad] - [num_tags (|> r.nat (of ! each (|>> (n.% 10) (n.max 2)))) - tag_in (|> r.nat (of ! each (n.% num_tags))) - .let [last?_in (|> num_tags -- (n.= tag_in))] - value_in r.i64] - (_.test (%.symbol (symbol synthesis.variant)) - (|> (synthesis.variant [analysis.#lefts (if last?_in - (-- tag_in) - tag_in) - analysis.#right? last?_in - analysis.#value (synthesis.i64 value_in)]) - (run "variant") - (pipe.when - {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? (when 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?)))) - - {try.#Failure _} - false))))) - -(def (tuple run) - (-> Runner Test) - (do [! r.monad] - [size (|> r.nat (of ! each (|>> (n.% 10) (n.max 2)))) - tuple_in (r.list size r.i64)] - (_.test (%.symbol (symbol synthesis.tuple)) - (|> (synthesis.tuple (list#each (|>> synthesis.i64) tuple_in)) - (run "tuple") - (pipe.when - {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))))) - -(def .public (spec runner) - (-> Runner Test) - (all _.and - (..variant runner) - (..tuple runner) - )) -- cgit v1.2.3