diff options
Diffstat (limited to '')
-rw-r--r-- | stdlib/source/test/lux/ffi.jvm.lux | 79 | ||||
-rw-r--r-- | stdlib/source/test/lux/macro/code.lux | 63 | ||||
-rw-r--r-- | stdlib/source/test/lux/target/ruby.lux | 21 | ||||
-rw-r--r-- | stdlib/source/test/lux/test.lux | 47 | ||||
-rw-r--r-- | stdlib/source/test/lux/tool/compiler/language/lux/analysis.lux | 2 | ||||
-rw-r--r-- | stdlib/source/test/lux/tool/compiler/language/lux/analysis/inference.lux | 406 | ||||
-rw-r--r-- | stdlib/source/test/lux/tool/compiler/language/lux/analysis/type.lux | 26 | ||||
-rw-r--r-- | stdlib/source/test/lux/world.lux | 34 | ||||
-rw-r--r-- | stdlib/source/test/lux/world/file/watch.lux | 108 |
9 files changed, 598 insertions, 188 deletions
diff --git a/stdlib/source/test/lux/ffi.jvm.lux b/stdlib/source/test/lux/ffi.jvm.lux index ea54c56d7..f77fbc54f 100644 --- a/stdlib/source/test/lux/ffi.jvm.lux +++ b/stdlib/source/test/lux/ffi.jvm.lux @@ -1,35 +1,35 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - ["[0]" type ("[1]#[0]" equivalence)] - ["[0]" meta] - [abstract - [monad {"+" do}]] - [control - [pipe {"+" case>}] - ["[0]" try] - ["[0]" exception] - [parser - ["<[0]>" code]]] - [data - ["[0]" bit ("[1]#[0]" equivalence)] - ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}]] - [collection - ["[0]" array {"+" Array}]]] - ["[0]" macro - [syntax {"+" syntax:}] - ["[0]" code] - ["[0]" template]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat] - ["i" int ("[1]#[0]" equivalence)] - ["f" frac ("[1]#[0]" equivalence)]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + ["[0]" type ("[1]#[0]" equivalence)] + ["[0]" meta] + [abstract + [monad {"+" do}]] + [control + [pipe {"+" case>}] + ["[0]" try] + ["[0]" exception] + [parser + ["<[0]>" code]]] + [data + ["[0]" bit ("[1]#[0]" equivalence)] + ["[0]" text ("[1]#[0]" equivalence) + ["%" format {"+" format}]] + [collection + ["[0]" array {"+" Array}]]] + ["[0]" macro + [syntax {"+" syntax:}] + ["[0]" code] + ["[0]" template]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat] + ["i" int ("[1]#[0]" equivalence)] + ["f" frac ("[1]#[0]" equivalence)]]]]] + [\\library + ["[0]" /]]) (/.import: java/lang/Boolean) (/.import: java/lang/Long) @@ -252,11 +252,11 @@ (actual3 [] a)]) (/.interface: test/TestInterface4 - ([] actual4 [long long long] long)) + ([] actual4 [long long] long)) (/.import: test/TestInterface4 ["[1]::[0]" - (actual4 [long long long] long)]) + (actual4 [long long] long)]) (def: for_interface Test @@ -327,20 +327,20 @@ [] (test/TestInterface4 [] (actual4 self [actual_left long - actual_right long - _ long]) + actual_right long]) long (:as java/lang/Long (i.+ (:as Int actual_left) (:as Int actual_right)))))] (i.= expected - (test/TestInterface4::actual4 left right right object/4)))]] + (test/TestInterface4::actual4 left right object/4)))]] (_.cover [/.interface: /.object] (and example/0! example/1! example/2! example/3! - example/4!)))) + example/4! + )))) (/.class: "final" test/TestClass0 [test/TestInterface0] ... Fields @@ -464,8 +464,7 @@ ... Methods (test/TestInterface4 [] (actual4 self [actual_left long - actual_right long - _ long]) + actual_right long]) long (:as java/lang/Long (i.+ (:as Int actual_left) @@ -550,7 +549,7 @@ (let [expected (i.+ left right) object/8 (test/TestClass8::new)] (i.= expected - (test/TestInterface4::actual4 left right right object/8)))] + (test/TestInterface4::actual4 left right object/8)))] .let [random_long (: (Random java/lang/Long) (# ! each (|>> (:as java/lang/Long)) diff --git a/stdlib/source/test/lux/macro/code.lux b/stdlib/source/test/lux/macro/code.lux index 4c6eb7e38..ffa65358b 100644 --- a/stdlib/source/test/lux/macro/code.lux +++ b/stdlib/source/test/lux/macro/code.lux @@ -1,31 +1,31 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [\\specification - ["$[0]" equivalence]]] - [control - ["[0]" try {"+" Try}]] - [data - ["[0]" product] - ["[0]" text] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [math - ["[0]" random {"+" Random} ("[1]#[0]" monad)] - [number - ["n" nat]]] - [meta - ["[0]" location]] - [tool - [compiler - [language - [lux - ["[0]" syntax]]]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [\\specification + ["$[0]" equivalence]]] + [control + ["[0]" try {"+" Try}]] + [data + ["[0]" product] + ["[0]" text] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [math + ["[0]" random {"+" Random} ("[1]#[0]" monad)] + [number + ["n" nat]]] + [meta + ["[0]" location]] + [tool + [compiler + [language + [lux + ["[0]" syntax]]]]]]] + [\\library + ["[0]" /]]) (def: random_text (Random Text) @@ -78,10 +78,11 @@ (function (_ replacement_simulation) (let [for_sequence (: (-> (-> (List Code) Code) (Random [Code Code])) (function (_ to_code) - (do [! random.monad] - [parts (..random_sequence replacement_simulation)] - (in [(to_code (list#each product.left parts)) - (to_code (list#each product.right parts))]))))] + (random.only (|>> product.left (# /.equivalence = original) not) + (do [! random.monad] + [parts (..random_sequence replacement_simulation)] + (in [(to_code (list#each product.left parts)) + (to_code (list#each product.right parts))])))))] ($_ random.either (random#in [original substitute]) (do [! random.monad] diff --git a/stdlib/source/test/lux/target/ruby.lux b/stdlib/source/test/lux/target/ruby.lux index 281ffe594..ee6b63d1c 100644 --- a/stdlib/source/test/lux/target/ruby.lux +++ b/stdlib/source/test/lux/target/ruby.lux @@ -432,7 +432,8 @@ Test (do [! random.monad] [float/0 random.safe_frac - $global (# ! each /.global (random.ascii/lower 10))] + $global (# ! each /.global (random.ascii/lower 10)) + pattern (# ! each /.string (random.ascii/lower 11))] ($_ _.and (_.cover [/.global] (expression (|>> (:as Text) (text#= "global-variable")) @@ -461,6 +462,24 @@ (_.cover [/.command_line_arguments] (expression (|>> (:as Int) (i.= +0)) (/.the "length" /.command_line_arguments))) + (_.cover [/.last_string_matched] + (expression (|>> (:as Bit)) + (|> ($_ /.then + (/.statement + (|> (/.manual "Regexp") + (/.new (list pattern) {.#None}) + (/.do "match" (list pattern) {.#None}))) + (/.return (/.= pattern /.last_string_matched))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.cover [/.last_regexp_match] + (expression (|>> (:as Bit)) + (|> (/.return (|> (/.manual "Regexp") + (/.new (list pattern) {.#None}) + (/.do "match" (list pattern) {.#None}) + (/.= /.last_regexp_match))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) ))) (def: test|local_var diff --git a/stdlib/source/test/lux/test.lux b/stdlib/source/test/lux/test.lux index b2334c7bc..feec778bb 100644 --- a/stdlib/source/test/lux/test.lux +++ b/stdlib/source/test/lux/test.lux @@ -1,25 +1,26 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]] - [control - ["[0]" io] - ["[0]" exception] - [concurrency - ["[0]" async] - ["[0]" atom {"+" Atom}]]] - [data - ["[0]" text ("[1]#[0]" equivalence)] - [collection - ["[0]" list] - ["[0]" set]]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + [abstract + [monad {"+" do}]] + [control + ["[0]" io] + ["[0]" exception] + [concurrency + ["[0]" async] + ["[0]" atom {"+" Atom}]]] + [data + ["[0]" text ("[1]#[0]" equivalence) + ["%" format]] + [collection + ["[0]" list] + ["[0]" set]]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]]) (def: (verify expected_message/0 expected_message/1 successes failures [tally message]) (-> Text Text Nat Nat [/.Tally Text] Bit) @@ -237,8 +238,8 @@ [[success_tally success_message] success_assertion [failure_tally failure_message] failure_assertion] (/.cover' [/.test] - (and (text.ends_with? expected_message/0 success_message) - (text.ends_with? expected_message/0 failure_message) + (and (text.ends_with? (%.text expected_message/0) success_message) + (text.ends_with? (%.text expected_message/0) failure_message) (and (n.= 1 (value@ /.#successes success_tally)) (n.= 0 (value@ /.#failures success_tally))) (and (n.= 0 (value@ /.#successes failure_tally)) 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 8f6a7b381..ccca4213f 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis.lux @@ -30,6 +30,7 @@ ["[1][0]" macro] ["[1][0]" type] ["[1][0]" module] + ["[1][0]" inference] [//// ["[1][0]" reference ["[2][0]" variable]] @@ -442,4 +443,5 @@ /macro.test /type.test /module.test + /inference.test )))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/inference.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/inference.lux new file mode 100644 index 000000000..672a8f25a --- /dev/null +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/inference.lux @@ -0,0 +1,406 @@ +(.using + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" maybe ("[1]#[0]" functor)] + ["[0]" try {"+" Try} ("[1]#[0]" functor)] + ["[0]" exception {"+" Exception}]] + [data + ["[0]" product] + ["[0]" bit ("[1]#[0]" equivalence)] + ["[0]" text] + [collection + ["[0]" list ("[1]#[0]" monad)]]] + [macro + ["[0]" code]] + [math + ["[0]" random {"+" Random} ("[1]#[0]" monad)] + [number + ["n" nat]]] + [meta + ["[0]" symbol "_" + ["$[1]" \\test]]] + ["[0]" type ("[1]#[0]" equivalence) + ["[0]" check {"+" Check}]]]] + [\\library + ["[0]" / + ["/[1]" // + [evaluation {"+" Eval}] + ["[1][0]" macro] + ["[1][0]" type] + ["[1][0]" module] + ["[1][0]" complex] + [// + [phase + ["[2][0]" analysis] + ["[2][0]" extension + ["[1]/[0]"analysis "_" + ["[1]" lux]]]] + [/// + ["[2][0]" phase ("[1]#[0]" monad)] + [meta + ["[0]" archive]]]]]]]) + +(def: (eval archive type term) + Eval + (/phase#in [])) + +(def: (expander macro inputs state) + //macro.Expander + {try.#Success ((.macro macro) inputs state)}) + +(def: random_state + (Random Lux) + (do random.monad + [version random.nat + host (random.ascii/lower 1)] + (in (//.state (//.info version host))))) + +(def: primitive + (Random Type) + (do random.monad + [name (random.ascii/lower 1)] + (in {.#Primitive name (list)}))) + +(def: analysis + //.Phase + (/analysis.phase ..expander)) + +(def: (fails? exception try) + (All (_ e a) (-> (Exception e) (Try a) Bit)) + (case try + {try.#Success _} + false + + {try.#Failure error} + (text.contains? (value@ exception.#label exception) error))) + +(def: simple_parameter + (Random [Type Code]) + (`` ($_ random.either + (~~ (template [<type> <random> <code>] + [(random#each (|>> <code> [<type>]) <random>)] + + [.Bit random.bit code.bit] + [.Nat random.nat code.nat] + [.Int random.int code.int] + [.Rev random.rev code.rev] + [.Frac random.frac code.frac] + [.Text (random.ascii/lower 1) code.text] + )) + ))) + +(def: test|general + Test + (do [! random.monad] + [lux ..random_state + .let [state [/extension.#bundle (/extension/analysis.bundle ..eval) + /extension.#state lux]] + expected ..primitive + name ($symbol.random 1 1) + [type/0 term/0] ..simple_parameter + arity (# ! each (n.% 10) random.nat) + nats (random.list arity random.nat)] + ($_ _.and + (_.cover [/.general] + (and (|> (/.general archive.empty ..analysis expected (list)) + (//type.expecting expected) + (/phase.result state) + (try#each (|>> product.left (type#= expected))) + (try.else false)) + (|> (/.general archive.empty ..analysis + (type.function (list.repeated arity .Nat) expected) + (list#each code.nat nats)) + (//type.expecting expected) + (/phase.result state) + (try#each (function (_ [actual analysis/*]) + (and (type#= expected actual) + (# (list.equivalence //.equivalence) = + (list#each (|>> //.nat) nats) + analysis/*)))) + (try.else false)) + (|> (/.general archive.empty ..analysis + (type (-> type/0 expected)) + (list term/0)) + (//type.expecting expected) + (/phase.result state) + (try#each (|>> product.left (type#= expected))) + (try.else false)) + (|> (/.general archive.empty ..analysis + (type {.#Named name (-> type/0 expected)}) + (list term/0)) + (//type.expecting expected) + (/phase.result state) + (try#each (|>> product.left (type#= expected))) + (try.else false)) + (|> (/.general archive.empty ..analysis + (type (All (_ a) (-> a a))) + (list term/0)) + (//type.expecting type/0) + (/phase#each (|>> product.left check.clean //type.check)) + /phase#conjoint + (/phase.result state) + (try#each (type#= type/0)) + (try.else false)) + (|> (/.general archive.empty ..analysis + (type ((All (_ a) (-> a a)) type/0)) + (list term/0)) + (//type.expecting type/0) + (/phase.result state) + (try#each (|>> product.left (type#= type/0))) + (try.else false)) + (|> (do /phase.monad + [[@var varT] (//type.check check.var) + _ (//type.check (check.check varT (type (-> type/0 expected))))] + (/.general archive.empty ..analysis varT (list term/0))) + (//type.expecting expected) + (/phase#each (|>> product.left check.clean //type.check)) + /phase#conjoint + (/phase.result state) + (try#each (type#= expected)) + (try.else false)) + )) + (_.cover [/.cannot_infer] + (and (|> (/.general archive.empty ..analysis expected (list term/0)) + (//type.expecting expected) + (/phase.result state) + (..fails? /.cannot_infer)) + (|> (do /phase.monad + [[@var varT] (//type.check check.var)] + (/.general archive.empty ..analysis varT (list term/0))) + (//type.expecting expected) + (/phase.result state) + (..fails? /.cannot_infer)))) + (_.cover [/.cannot_infer_argument] + (|> (/.general archive.empty ..analysis + (type (-> expected expected)) + (list term/0)) + (//type.expecting expected) + (/phase.result state) + (..fails? /.cannot_infer_argument))) + (_.cover [/.existential?] + (|> (/.general archive.empty ..analysis + (type (Ex (_ a) (-> a a))) + (list (` ("lux io error" "")))) + //type.inferring + (//module.with_module 0 (product.left name)) + (/phase#each (|>> product.right product.left check.clean //type.check)) + /phase#conjoint + (/phase.result state) + (try#each /.existential?) + (try.else false))) + ))) + +(def: test|variant + Test + (do [! random.monad] + [lux ..random_state + .let [state [/extension.#bundle (/extension/analysis.bundle ..eval) + /extension.#state lux]] + name ($symbol.random 1 1) + arity (# ! each (|>> (n.% 5) (n.+ 2)) random.nat) + [type/0 term/0] ..simple_parameter + [type/1 term/1] (random.only (|>> product.left (same? type/0) not) + ..simple_parameter) + types/*,terms,* (random.list arity ..simple_parameter) + tag (# ! each (n.% arity) random.nat) + .let [[lefts right?] (//complex.choice arity tag)] + arbitrary_right? random.bit] + ($_ _.and + (_.cover [/.variant] + (let [variantT (type.variant (list#each product.left types/*,terms,*)) + [tagT tagC] (|> types/*,terms,* + (list.item tag) + (maybe.else [Any (' [])])) + variant?' (: (-> Type (Maybe Type) Nat Bit Code Bit) + (function (_ variant inferred lefts right? term) + (|> (do /phase.monad + [inferT (/.variant lefts right? variant) + [_ [it _]] (|> (/.general archive.empty ..analysis inferT (list term)) + //type.inferring)] + (case inferred + {.#Some inferred} + (//type.check + (do check.monad + [_ (check.check inferred it) + _ (check.check it inferred)] + (in true))) + + {.#None} + (in true))) + (//module.with_module 0 (product.left name)) + (/phase#each product.right) + (/phase.result state) + (try.else false)))) + variant? (: (-> Type Nat Bit Code Bit) + (function (_ type lefts right? term) + (variant?' type {.#Some type} lefts right? term))) + + can_match_case! + (variant? variantT lefts right? tagC) + + names_do_not_matter! + (variant? {.#Named name variantT} lefts right? tagC) + + cases_independent_of_parameters_conform_to_anything! + (variant? (type (Maybe type/0)) 0 #0 (' [])) + + cases_dependent_on_parameters_are_tettered_to_those_parameters! + (and (variant? (type (Maybe type/0)) 0 #1 term/0) + (not (variant? (type (Maybe type/0)) 0 #1 term/1))) + + only_bottom_conforms_to_tags_outside_of_range! + (`` (and (~~ (template [<verdict> <term>] + [(bit#= <verdict> (variant? variantT arity arbitrary_right? <term>))] + + [#0 term/0] + [#1 (` ("lux io error" ""))])))) + + can_handle_universal_quantification! + (and (variant?' (type (All (_ a) (Maybe a))) + {.#Some Maybe} + 0 #0 (' [])) + (variant?' (type (All (_ a) (Maybe a))) + {.#Some (type (Maybe type/0))} + 0 #1 term/0) + (not (variant?' (type (All (_ a) (Maybe a))) + {.#Some Maybe} + 0 #1 term/0))) + + existential_types_do_not_affect_independent_cases! + (variant?' (type (Ex (_ a) (Maybe a))) + {.#None} + 0 #0 (' [])) + + existential_types_affect_dependent_cases! + (`` (and (~~ (template [<verdict> <term>] + [(bit#= <verdict> (variant?' (type (Ex (_ a) (Maybe a))) {.#None} 0 #1 <term>))] + + [#0 term/0] + [#1 (` ("lux io error" ""))]))))] + (and can_match_case! + names_do_not_matter! + + cases_independent_of_parameters_conform_to_anything! + cases_dependent_on_parameters_are_tettered_to_those_parameters! + + only_bottom_conforms_to_tags_outside_of_range! + + can_handle_universal_quantification! + + existential_types_do_not_affect_independent_cases! + existential_types_affect_dependent_cases! + ))) + (_.cover [/.not_a_variant] + (let [[tagT tagC] (|> types/*,terms,* + (list.item tag) + (maybe.else [Any (' [])]))] + (|> (/.variant lefts right? tagT) + (/phase.result state) + (..fails? /.not_a_variant)))) + ))) + +(def: test|record + Test + (do [! random.monad] + [lux ..random_state + .let [state [/extension.#bundle (/extension/analysis.bundle ..eval) + /extension.#state lux]] + name ($symbol.random 1 1) + arity (# ! each (|>> (n.% 5) (n.+ 2)) random.nat) + [type/0 term/0] ..simple_parameter + [type/1 term/1] (random.only (|>> product.left (same? type/0) not) + ..simple_parameter) + types/*,terms,* (random.list arity ..simple_parameter) + .let [record? (: (-> Type (Maybe Type) Nat (List Code) Bit) + (function (_ record expected arity terms) + (|> (do /phase.monad + [inference (/.record arity record) + [_ [it _]] (|> (/.general archive.empty ..analysis inference terms) + //type.inferring)] + (case expected + {.#Some expected} + (//type.check + (do check.monad + [_ (check.check expected it) + _ (check.check it expected)] + (in true))) + + {.#None} + (in true))) + (//module.with_module 0 (product.left name)) + (/phase#each product.right) + (/phase.result state) + (try.else false)))) + record (type.tuple (list#each product.left types/*,terms,*)) + terms (list#each product.right types/*,terms,*)]] + ($_ _.and + (_.cover [/.record] + (let [can_infer_record! + (record? record {.#None} arity terms) + + names_do_not_matter! + (record? {.#Named name record} {.#None} arity terms) + + can_handle_universal_quantification! + (and (record? (All (_ a) (Tuple type/0 a)) + {.#Some (Tuple type/0 type/1)} + 2 (list term/0 term/1)) + (record? (All (_ a) (Tuple a type/0)) + {.#Some (Tuple type/1 type/0)} + 2 (list term/1 term/0))) + + can_handle_existential_quantification! + (and (not (record? (Ex (_ a) (Tuple type/0 a)) + {.#Some (Tuple type/0 type/1)} + 2 (list term/0 term/1))) + (record? (Ex (_ a) (Tuple type/0 a)) + {.#None} + 2 (list term/0 (` ("lux io error" "")))) + (not (record? (Ex (_ a) (Tuple a type/0)) + {.#Some (Tuple type/1 type/0)} + 2 (list term/1 term/0))) + (record? (Ex (_ a) (Tuple a type/0)) + {.#None} + 2 (list (` ("lux io error" "")) term/0)))] + (and can_infer_record! + names_do_not_matter! + can_handle_universal_quantification! + can_handle_existential_quantification! + ))) + (_.cover [/.not_a_record] + (|> (/.record arity type/0) + (/phase.result state) + (..fails? /.not_a_record))) + ))) + +(def: .public test + Test + (<| (_.covering /._) + (do [! random.monad] + [lux ..random_state + .let [state [/extension.#bundle (/extension/analysis.bundle ..eval) + /extension.#state lux]] + [type/0 term/0] ..simple_parameter + [type/1 term/1] (random.only (|>> product.left (same? type/0) not) + ..simple_parameter) + lefts (# ! each (n.% 10) random.nat) + right? random.bit] + ($_ _.and + ..test|general + ..test|variant + ..test|record + (_.cover [/.invalid_type_application] + (and (|> (/.general archive.empty ..analysis (type (type/0 type/1)) (list term/0)) + (/phase.result state) + (..fails? /.invalid_type_application)) + (|> (/.variant lefts right? (type (type/0 type/1))) + (/phase.result state) + (..fails? /.invalid_type_application)) + (|> (/.record lefts (type (type/0 type/1))) + (/phase.result state) + (..fails? /.invalid_type_application)))) + )))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/type.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/type.lux index 66876be3c..781a7f38f 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/type.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/type.lux @@ -2,35 +2,17 @@ [library [lux "*" ["_" test {"+" Test}] - ["[0]" meta] [abstract - [monad {"+" do}] - [\\specification - ["$[0]" equivalence]]] + [monad {"+" do}]] [control [pipe {"+" case>}] - ["[0]" maybe ("[1]#[0]" functor)] - ["[0]" try ("[1]#[0]" functor)] - ["[0]" exception]] + ["[0]" try ("[1]#[0]" functor)]] [data - ["[0]" product] - ["[0]" bit ("[1]#[0]" equivalence)] - ["[0]" text ("[1]#[0]" equivalence)] - [collection - ["[0]" list ("[1]#[0]" monad)]]] - [macro - ["[0]" code ("[1]#[0]" equivalence)]] + ["[0]" product]] [math - ["[0]" random {"+" Random} ("[1]#[0]" monad)] - [number - ["n" nat]]] + ["[0]" random {"+" Random}]] ["[0]" type ("[1]#[0]" equivalence) ["[0]" check]]]] - ["$" /////// "_" - [macro - ["[1][0]" code]] - [meta - ["[1][0]" symbol]]] [\\library ["[0]" / ["/[1]" // diff --git a/stdlib/source/test/lux/world.lux b/stdlib/source/test/lux/world.lux index f705e6269..e57811f1a 100644 --- a/stdlib/source/test/lux/world.lux +++ b/stdlib/source/test/lux/world.lux @@ -1,21 +1,21 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}]]] - ["[0]" / "_" - ["[1][0]" file] - ["[1][0]" shell] - ["[1][0]" console] - ["[1][0]" program] - ["[1][0]" input "_" - ["[1]/[0]" keyboard]] - ["[1][0]" output "_" - ["[1]/[0]" video "_" - ["[1]/[0]" resolution]]] - ["[1][0]" net "_" - ["[1]/[0]" http "_" - ["[1]/[0]" client] - ["[1]/[0]" status]]]]) + [library + [lux "*" + ["_" test {"+" Test}]]] + ["[0]" / "_" + ["[1][0]" file] + ["[1][0]" shell] + ["[1][0]" console] + ["[1][0]" program] + ["[1][0]" input "_" + ["[1]/[0]" keyboard]] + ["[1][0]" output "_" + ["[1]/[0]" video "_" + ["[1]/[0]" resolution]]] + ["[1][0]" net "_" + ["[1]/[0]" http "_" + ["[1]/[0]" client] + ["[1]/[0]" status]]]]) (def: .public test Test diff --git a/stdlib/source/test/lux/world/file/watch.lux b/stdlib/source/test/lux/world/file/watch.lux index 0a9a742fb..cd7c95c46 100644 --- a/stdlib/source/test/lux/world/file/watch.lux +++ b/stdlib/source/test/lux/world/file/watch.lux @@ -1,29 +1,29 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [predicate {"+" Predicate}] - [monad {"+" do}]] - [control - ["[0]" try {"+" Try}] - ["[0]" exception] - [concurrency - ["[0]" async {"+" Async}]]] - [data - ["[0]" binary {"+" Binary} ("[1]#[0]" equivalence)] - ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}]] - [collection - ["[0]" list]]] - [math - ["[0]" random {"+" Random} ("[1]#[0]" monad)]]]] - [\\library - ["[0]" / - ["/[1]" //]]] - [//// + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [predicate {"+" Predicate}] + [monad {"+" do}]] + [control + ["[0]" try {"+" Try}] + ["[0]" exception] + [concurrency + ["[0]" async {"+" Async}]]] [data - ["$[0]" binary]]]) + ["[0]" binary {"+" Binary} ("[1]#[0]" equivalence)] + ["[0]" text ("[1]#[0]" equivalence) + ["%" format {"+" format}]] + [collection + ["[0]" list]]] + [math + ["[0]" random {"+" Random} ("[1]#[0]" monad)]]]] + [\\library + ["[0]" / + ["/[1]" //]]] + [//// + [data + ["$[0]" binary]]]) (def: concern (Random [/.Concern (Predicate /.Concern)]) @@ -35,35 +35,34 @@ (def: concern##test Test - (<| (_.for [/.Concern]) - ($_ _.and - (_.cover [/.creation /.creation?] - (and (/.creation? /.creation) - (not (/.creation? /.modification)) - (not (/.creation? /.deletion)))) - (_.cover [/.modification /.modification?] - (and (not (/.modification? /.creation)) - (/.modification? /.modification) - (not (/.modification? /.deletion)))) - (_.cover [/.deletion /.deletion?] - (and (not (/.deletion? /.creation)) - (not (/.deletion? /.modification)) - (/.deletion? /.deletion))) - (do random.monad - [left ..concern - right (random.only (|>> (same? left) not) - ..concern) - .let [[left left?] left - [right right?] right]] - (_.cover [/.also] - (let [composition (/.also left right)] - (and (left? composition) - (right? composition))))) - (_.cover [/.all] - (and (/.creation? /.all) - (/.modification? /.all) - (/.deletion? /.all))) - ))) + ($_ _.and + (_.cover [/.creation /.creation?] + (and (/.creation? /.creation) + (not (/.creation? /.modification)) + (not (/.creation? /.deletion)))) + (_.cover [/.modification /.modification?] + (and (not (/.modification? /.creation)) + (/.modification? /.modification) + (not (/.modification? /.deletion)))) + (_.cover [/.deletion /.deletion?] + (and (not (/.deletion? /.creation)) + (not (/.deletion? /.modification)) + (/.deletion? /.deletion))) + (do random.monad + [left ..concern + right (random.only (|>> (same? left) not) + ..concern) + .let [[left left?] left + [right right?] right]] + (_.cover [/.also] + (let [composition (/.also left right)] + (and (left? composition) + (right? composition))))) + (_.cover [/.all] + (and (/.creation? /.all) + (/.modification? /.all) + (/.deletion? /.all))) + )) (def: exception Test @@ -154,7 +153,8 @@ (<| (_.covering /._) (_.for [/.Watcher]) ($_ _.and - ..concern##test + (_.for [/.Concern] + ..concern##test) ..exception (do [! random.monad] |