diff options
Diffstat (limited to 'stdlib/source/test')
113 files changed, 3195 insertions, 3192 deletions
diff --git a/stdlib/source/test/aedifex/cache.lux b/stdlib/source/test/aedifex/cache.lux index 9888e2f58..09e022c89 100644 --- a/stdlib/source/test/aedifex/cache.lux +++ b/stdlib/source/test/aedifex/cache.lux @@ -104,8 +104,8 @@ [[dependency expected_package] ..package home (random.ascii/alpha 5) working_directory (random.ascii/alpha 5) - .let [fs (: (file.System Async) - (file.mock (# file.default separator))) + .let [fs (is (file.System Async) + (file.mock (# file.default separator))) program (program.async (program.mock environment.empty home working_directory))]] (in (do async.monad [wrote! (/.write_one program fs dependency expected_package) @@ -125,8 +125,8 @@ [expected ..resolution home (random.ascii/alpha 5) working_directory (random.ascii/alpha 5) - .let [fs (: (file.System Async) - (file.mock (# file.default separator))) + .let [fs (is (file.System Async) + (file.mock (# file.default separator))) program (program.async (program.mock environment.empty home working_directory))]] (in (do async.monad [wrote! (/.write_all program fs expected) diff --git a/stdlib/source/test/aedifex/command/auto.lux b/stdlib/source/test/aedifex/command/auto.lux index bfdbb789e..001bfcab3 100644 --- a/stdlib/source/test/aedifex/command/auto.lux +++ b/stdlib/source/test/aedifex/command/auto.lux @@ -48,8 +48,8 @@ (-> Nat Text (file.System Async) file.Path [(Atom Nat) (-> (Console Async) (Program Async) (file.System Async) (Shell Async) Resolution (Command [Exit Any]))]) - (let [@runs (: (Atom Nat) - (atom.atom 0))] + (let [@runs (is (Atom Nat) + (atom.atom 0))] [@runs (function (_ console program fs shell resolution profile) (do [! async.monad] @@ -74,12 +74,12 @@ program (random.ascii/alpha 5) target (random.ascii/alpha 5) source (random.ascii/alpha 5) - .let [empty_profile (: Profile - (# ///.monoid identity)) - with_target (: (-> Profile Profile) - (has ///.#target target)) - with_program (: (-> Profile Profile) - (has ///.#program {.#Some program})) + .let [empty_profile (is Profile + (# ///.monoid identity)) + with_target (is (-> Profile Profile) + (has ///.#target target)) + with_program (is (-> Profile Profile) + (has ///.#program {.#Some program})) profile (|> empty_profile with_program diff --git a/stdlib/source/test/aedifex/command/build.lux b/stdlib/source/test/aedifex/command/build.lux index f8d2d46ec..987d35506 100644 --- a/stdlib/source/test/aedifex/command/build.lux +++ b/stdlib/source/test/aedifex/command/build.lux @@ -42,68 +42,68 @@ (shell.mock (function (_ [actual_environment actual_working_directory actual_command actual_arguments]) {try.#Success - (: (shell.Mock []) - (implementation - (def: (on_read state) - (exception.except shell.no_more_output [])) - (def: (on_fail state) - (exception.except shell.no_more_output [])) - (def: (on_write input state) - {try.#Failure "on_write"}) - (def: (on_destroy state) - {try.#Failure "on_destroy"}) - (def: (on_await state) - {try.#Success [state shell.normal]})))}))) + (is (shell.Mock []) + (implementation + (def: (on_read state) + (exception.except shell.no_more_output [])) + (def: (on_fail state) + (exception.except shell.no_more_output [])) + (def: (on_write input state) + {try.#Failure "on_write"}) + (def: (on_destroy state) + {try.#Failure "on_destroy"}) + (def: (on_await state) + {try.#Success [state shell.normal]})))}))) (def: .public bad_shell (-> Any (Shell IO)) (shell.mock (function (_ [actual_environment actual_working_directory actual_command actual_arguments]) {try.#Success - (: (shell.Mock []) - (implementation - (def: (on_read state) - (exception.except shell.no_more_output [])) - (def: (on_fail state) - (exception.except shell.no_more_output [])) - (def: (on_write input state) - {try.#Failure "on_write"}) - (def: (on_destroy state) - {try.#Failure "on_destroy"}) - (def: (on_await state) - {try.#Success [state shell.error]})))}))) + (is (shell.Mock []) + (implementation + (def: (on_read state) + (exception.except shell.no_more_output [])) + (def: (on_fail state) + (exception.except shell.no_more_output [])) + (def: (on_write input state) + {try.#Failure "on_write"}) + (def: (on_destroy state) + {try.#Failure "on_destroy"}) + (def: (on_await state) + {try.#Success [state shell.error]})))}))) (def: .public (reader_shell error?) (-> Bit (-> (List Text) (Shell IO))) (shell.mock (function (_ [actual_environment actual_working_directory actual_command actual_arguments]) {try.#Success - (: (shell.Mock (List Text)) - (implementation - (def: (on_read state) - (if error? - (exception.except shell.no_more_output []) - (case state - {.#Item head tail} - {try.#Success [tail head]} - - {.#End} - (exception.except shell.no_more_output [])))) - (def: (on_error state) - (if error? - (case state - {.#Item head tail} - {try.#Success [tail head]} - - {.#End} - (exception.except shell.no_more_output [])) - (exception.except shell.no_more_output []))) - (def: (on_write input state) - {try.#Failure "on_write"}) - (def: (on_destroy state) - {try.#Failure "on_destroy"}) - (def: (on_await state) - {try.#Success [state shell.error]})))}))) + (is (shell.Mock (List Text)) + (implementation + (def: (on_read state) + (if error? + (exception.except shell.no_more_output []) + (case state + {.#Item head tail} + {try.#Success [tail head]} + + {.#End} + (exception.except shell.no_more_output [])))) + (def: (on_error state) + (if error? + (case state + {.#Item head tail} + {try.#Success [tail head]} + + {.#End} + (exception.except shell.no_more_output [])) + (exception.except shell.no_more_output []))) + (def: (on_write input state) + {try.#Failure "on_write"}) + (def: (on_destroy state) + {try.#Failure "on_destroy"}) + (def: (on_await state) + {try.#Success [state shell.error]})))}))) (def: compiler (Random Dependency) @@ -148,12 +148,12 @@ target (random.ascii/alpha 5) home (random.ascii/alpha 5) working_directory (random.ascii/alpha 5) - .let [empty_profile (: Profile - (# ///.monoid identity)) - with_target (: (-> Profile Profile) - (has ///.#target target)) - with_program (: (-> Profile Profile) - (has ///.#program {.#Some program})) + .let [empty_profile (is Profile + (# ///.monoid identity)) + with_target (is (-> Profile Profile) + (has ///.#target target)) + with_program (is (-> Profile Profile) + (has ///.#program {.#Some program})) profile (|> empty_profile with_program diff --git a/stdlib/source/test/aedifex/command/clean.lux b/stdlib/source/test/aedifex/command/clean.lux index 6a2210f1b..21372ef80 100644 --- a/stdlib/source/test/aedifex/command/clean.lux +++ b/stdlib/source/test/aedifex/command/clean.lux @@ -56,8 +56,8 @@ (def: (create_directory! fs path files) (-> (file.System Async) Path (List [Path Binary]) (Async (Try Any))) (do [! (try.with async.monad)] - [_ (: (Async (Try Any)) - (file.make_directories async.monad fs path)) + [_ (is (Async (Try Any)) + (file.make_directories async.monad fs path)) _ (monad.each ! (..create_file! fs) files)] (in []))) @@ -73,10 +73,10 @@ (-> (file.System Async) Path (List [Path Binary]) (Async (Try Bit))) (do [! (try.with async.monad)] [directory_exists? (..directory_exists? fs directory_path) - files_exist? (: (Action (List Bit)) - (|> files - (list#each product.left) - (monad.each ///action.monad (..file_exists? fs))))] + files_exist? (is (Action (List Bit)) + (|> files + (list#each product.left) + (monad.each ///action.monad (..file_exists? fs))))] (in (and directory_exists? (list.every? (|>>) files_exist?))))) diff --git a/stdlib/source/test/aedifex/command/install.lux b/stdlib/source/test/aedifex/command/install.lux index fd4780195..414d104d8 100644 --- a/stdlib/source/test/aedifex/command/install.lux +++ b/stdlib/source/test/aedifex/command/install.lux @@ -47,10 +47,10 @@ set.list (monad.each ! (function (_ head) (do ! - [_ (: (Async (Try Any)) - (file.make_directories async.monad fs head))] - (: (Async (Try Any)) - (file.make_file async.monad fs (binary.empty 0) (format head / head ".lux"))))))))) + [_ (is (Async (Try Any)) + (file.make_directories async.monad fs head))] + (is (Async (Try Any)) + (file.make_file async.monad fs (binary.empty 0) (format head / head ".lux"))))))))) (def: (execute! program fs sample) (-> (Program Async) (file.System Async) ///.Profile (Async (Try Text))) diff --git a/stdlib/source/test/aedifex/command/test.lux b/stdlib/source/test/aedifex/command/test.lux index e992f87bc..4f6cfcdc4 100644 --- a/stdlib/source/test/aedifex/command/test.lux +++ b/stdlib/source/test/aedifex/command/test.lux @@ -47,12 +47,12 @@ target (random.ascii/alpha 5) home (random.ascii/alpha 5) working_directory (random.ascii/alpha 5) - .let [empty_profile (: Profile - (# ///.monoid identity)) - with_target (: (-> Profile Profile) - (has ///.#target target)) - with_test (: (-> Profile Profile) - (has ///.#test {.#Some test})) + .let [empty_profile (is Profile + (# ///.monoid identity)) + with_target (is (-> Profile Profile) + (has ///.#target target)) + with_test (is (-> Profile Profile) + (has ///.#test {.#Some test})) profile (|> empty_profile with_test @@ -84,20 +84,20 @@ [.let [bad_shell (shell.mock (function (_ [actual_environment actual_working_directory actual_command actual_arguments]) {try.#Success - (: (shell.Mock []) - (implementation - (def: (on_read state) - (exception.except shell.no_more_output [])) - (def: (on_error state) - (exception.except shell.no_more_output [])) - (def: (on_write input state) - {try.#Failure "on_write"}) - (def: (on_destroy state) - {try.#Failure "on_destroy"}) - (def: (on_await state) - {try.#Success [state (if (list.any? (text#= "build") actual_arguments) - shell.normal - shell.error)]})))}) + (is (shell.Mock []) + (implementation + (def: (on_read state) + (exception.except shell.no_more_output [])) + (def: (on_error state) + (exception.except shell.no_more_output [])) + (def: (on_write input state) + {try.#Failure "on_write"}) + (def: (on_destroy state) + {try.#Failure "on_destroy"}) + (def: (on_await state) + {try.#Success [state (if (list.any? (text#= "build") actual_arguments) + shell.normal + shell.error)]})))}) [])] _ (/.do! console (program.async (program.mock environment.empty home working_directory)) fs (shell.async bad_shell) resolution diff --git a/stdlib/source/test/aedifex/dependency/deployment.lux b/stdlib/source/test/aedifex/dependency/deployment.lux index c22121755..ed834c759 100644 --- a/stdlib/source/test/aedifex/dependency/deployment.lux +++ b/stdlib/source/test/aedifex/dependency/deployment.lux @@ -66,19 +66,19 @@ (implementation (def: (request method url headers input) (do io.monad - [_ (: (IO Any) - (case [method input] - [{@http.#Put} {.#Some input}] - (atom.update! (dictionary.has url input) cache) - - _ - (in [])))] + [_ (is (IO Any) + (case [method input] + [{@http.#Put} {.#Some input}] + (atom.update! (dictionary.has url input) cache) + + _ + (in [])))] (in {try.#Success ..good_upload}))))) (def: (verify_one expected_deployments address package cache expected_artifact actual_artifact) (-> Nat URL Package (Dictionary URL Binary) Artifact Artifact Bit) - (let [url (: (-> URI URL) - (|>> (format address))) + (let [url (is (-> URI URL) + (|>> (format address))) library_url (url (format (artifact.uri (the artifact.#version expected_artifact) expected_artifact) artifact/extension.lux_library)) @@ -138,9 +138,9 @@ .let [artifact (|> profile (the profile.#identity) maybe.trusted) - dependency (: Dependency - [artifact - artifact/type.lux_library])]] + dependency (is Dependency + [artifact + artifact/type.lux_library])]] (in [dependency artifact package]))) (def: .public test @@ -152,8 +152,8 @@ ($_ _.and (do [! random.monad] [[dependency expected_artifact package] ..bundle - .let [cache (: Cache - (atom.atom (dictionary.empty text.hash))) + .let [cache (is Cache + (atom.atom (dictionary.empty text.hash))) http (..http cache) repository (repository.async (remote.repository http {.#None} address))]] (in (do async.monad @@ -164,9 +164,9 @@ (try#each (verify_one 1 address package cache expected_artifact)) (try.else false)))))) (do [! random.monad] - [.let [hash (: (Hash [Dependency Artifact Package]) - (# hash.functor each (|>> product.right product.left product.left) - text.hash))] + [.let [hash (is (Hash [Dependency Artifact Package]) + (# hash.functor each (|>> product.right product.left product.left) + text.hash))] num_bundles (# ! each (n.% 10) random.nat) bundles (|> ..bundle (random.set hash num_bundles) @@ -175,8 +175,8 @@ (dictionary.has dependency package resolution)) resolution.empty bundles) - cache (: Cache - (atom.atom (dictionary.empty text.hash))) + cache (is Cache + (atom.atom (dictionary.empty text.hash))) http (..http cache) repository (repository.async (remote.repository http {.#None} address))]] (in (do async.monad diff --git a/stdlib/source/test/aedifex/dependency/resolution.lux b/stdlib/source/test/aedifex/dependency/resolution.lux index 5ea995021..c7f81d3c3 100644 --- a/stdlib/source/test/aedifex/dependency/resolution.lux +++ b/stdlib/source/test/aedifex/dependency/resolution.lux @@ -104,16 +104,16 @@ "[1]") (def: (on_download uri state) (if (text.contains? expected uri) - (let [library (: Binary - (|> package - (the ///package.#library) - product.left)) - pom (: Binary - (|> package - (the ///package.#pom) - product.left - (# xml.codec encoded) - (# utf8.codec encoded)))] + (let [library (is Binary + (|> package + (the ///package.#library) + product.left)) + pom (is Binary + (|> package + (the ///package.#pom) + product.left + (# xml.codec encoded) + (# utf8.codec encoded)))] (cond (text.ends_with? ///artifact/extension.lux_library uri) {try.#Success [state library]} diff --git a/stdlib/source/test/aedifex/input.lux b/stdlib/source/test/aedifex/input.lux index dedb9b33c..4a7100296 100644 --- a/stdlib/source/test/aedifex/input.lux +++ b/stdlib/source/test/aedifex/input.lux @@ -46,8 +46,8 @@ (<| (_.covering /._) (do [! random.monad] [expected (# ! each (has //.#parents (list)) $profile.random) - .let [fs (: (file.System Async) - (file.mock (# file.default separator)))]] + .let [fs (is (file.System Async) + (file.mock (# file.default separator)))]] (in (do async.monad [verdict (do //action.monad [.let [profile (|> expected @@ -56,8 +56,8 @@ %.code (# utf8.codec encoded))] _ (# fs write profile //project.file) - actual (: (Async (Try Profile)) - (/.read async.monad fs (list //.default)))] + actual (is (Async (Try Profile)) + (/.read async.monad fs (list //.default)))] (in (# //.equivalence = (|> expected (revised //.#sources ..with_default_source) diff --git a/stdlib/source/test/aedifex/parser.lux b/stdlib/source/test/aedifex/parser.lux index f529c2d0a..af642f65b 100644 --- a/stdlib/source/test/aedifex/parser.lux +++ b/stdlib/source/test/aedifex/parser.lux @@ -56,11 +56,11 @@ (def: with_default_sources (-> //.Profile //.Profile) (revised //.#sources - (: (-> (Set //.Source) (Set //.Source)) - (function (_ sources) - (if (set.empty? sources) - (set.of_list text.hash (list //.default_source)) - sources))))) + (is (-> (Set //.Source) (Set //.Source)) + (function (_ sources) + (if (set.empty? sources) + (set.of_list text.hash (list //.default_source)) + sources))))) (def: with_default_repository (-> //.Profile //.Profile) diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux index 751655065..2cccd5878 100644 --- a/stdlib/source/test/lux.lux +++ b/stdlib/source/test/lux.lux @@ -193,8 +193,8 @@ (type: (Returner a) (/.Interface - (: (-> Any a) - return))) + (is (-> Any a) + return))) (/.implementation: (global_returner value) (All (_ a) (-> a (Returner a))) @@ -210,10 +210,10 @@ Test (do random.monad [expected random.nat - .let [local_returner (: (Returner Nat) - (/.implementation - (def: (return _) - expected)))]] + .let [local_returner (is (Returner Nat) + (/.implementation + (def: (return _) + expected)))]] (_.for [/.Interface] ($_ _.and (_.cover [/.implementation:] @@ -404,22 +404,22 @@ (def: for_macro Test - (let [macro (: /.Macro' - (function (_ tokens lux) - {.#Right [lux (list)]}))] + (let [macro (is /.Macro' + (function (_ tokens lux) + {.#Right [lux (list)]}))] (do random.monad [expected random.nat] (`` (`` ($_ _.and (_.cover [/.Macro'] (|> macro - (: /.Macro') + (is /.Macro') (same? macro))) (_.cover [/.Macro] (|> macro "lux macro" - (: /.Macro) - (: Any) - (same? (: Any macro)))) + (is /.Macro) + (is Any) + (same? (is Any macro)))) (_.cover [/.macro:] (same? expected (..identity_macro expected))) (~~ (for @.old (~~ (as_is)) @@ -452,23 +452,23 @@ <open/0> (template.text [<module/0> "#[0]"])] (and (~~ (template [<input> <module> <referrals>] [(with_expansions [<input>' (macro.final <input>)] - (let [scenario (: (-> Any Bit) - (function (_ _) - ... TODO: Remove this hack once Jython is no longer being used as the Python interpreter. - (`` (for @.python (case (' [<input>']) - (^.` [<module> - ("lux def" (~ [_ {.#Symbol ["" _]}]) [] #0) - (~~ (template.spliced <referrals>))]) - true - - _ - false) - (case (' [<input>']) - (^.` [<module> (~~ (template.spliced <referrals>))]) - true - - _ - false)))))] + (let [scenario (is (-> Any Bit) + (function (_ _) + ... TODO: Remove this hack once Jython is no longer being used as the Python interpreter. + (`` (for @.python (case (' [<input>']) + (^.` [<module> + ("lux def" (~ [_ {.#Symbol ["" _]}]) [] #0) + (~~ (template.spliced <referrals>))]) + true + + _ + false) + (case (' [<input>']) + (^.` [<module> (~~ (template.spliced <referrals>))]) + true + + _ + false)))))] (scenario [])))] [(.using [<module/0>']) @@ -563,30 +563,23 @@ expected/1 existential_type] (<| (_.for [/.Type]) ($_ _.and - (_.cover [/.:] + (_.cover [/.is] (|> expected - (/.: Any) - (same? (/.: Any expected)))) - (_.cover [/.:as] + (/.is Any) + (same? (/.is Any expected)))) + (_.cover [/.as] (|> expected - (/.: Any) - (/.:as /.Nat) + (/.is Any) + (/.as /.Nat) (same? expected))) - (_.cover [/.:expected] + (_.cover [/.as_expected] (|> expected - (/.: Any) - /.:expected - (/.: /.Nat) + (/.is Any) + /.as_expected + (/.is /.Nat) (same? expected))) - (_.cover [/.:let] - (let [[actual_left actual_right] - (: (/.:let [side /.Nat] - [side side]) - [expected_left expected_right])] - (and (same? expected_left actual_left) - (same? expected_right actual_right)))) - (_.cover [/.:of] - (same? /.Nat (/.:of expected))) + (_.cover [/.type_of] + (same? /.Nat (/.type_of expected))) (_.cover [/.Primitive] (case (/.Primitive "foo" [expected/0 expected/1]) (pattern {.#Primitive "foo" (list actual/0 actual/1)}) @@ -626,20 +619,20 @@ false))) (_.cover [/.type:] (exec - (: /.Type ..for_type/variant) - (: /.Type ..for_type/record) - (: /.Type ..for_type/all) + (is /.Type ..for_type/variant) + (is /.Type ..for_type/record) + (is /.Type ..for_type/all) true)) (_.cover [/.Variant] (exec - (: for_type/variant - {#Case/1 expected_left}) + (is for_type/variant + {#Case/1 expected_left}) true)) (_.cover [/.Record] (exec - (: for_type/record - [#slot/0 (n.= expected_left expected_right) - #slot/1 (.rev expected_right)]) + (is for_type/record + [#slot/0 (n.= expected_left expected_right) + #slot/1 (.rev expected_right)]) true)) )))) @@ -649,17 +642,17 @@ [expected random.i64] ($_ _.and (_.cover [/.i64] - (same? (: Any expected) - (: Any (/.i64 expected)))) + (same? (is Any expected) + (is Any (/.i64 expected)))) (_.cover [/.nat] - (same? (: Any expected) - (: Any (/.nat expected)))) + (same? (is Any expected) + (is Any (/.nat expected)))) (_.cover [/.int] - (same? (: Any expected) - (: Any (/.int expected)))) + (same? (is Any expected) + (is Any (/.int expected)))) (_.cover [/.rev] - (same? (: Any expected) - (: Any (/.rev expected)))) + (same? (is Any expected) + (is Any (/.rev expected)))) (_.cover [/.++] (n.= 1 (n.- expected (/.++ expected)))) @@ -674,14 +667,14 @@ [expected_left random.nat expected_right random.nat] (_.cover [/.-> /.function] - (and (let [actual (: (/.-> Nat Nat Nat) - (/.function (_ actual_left actual_right) - (n.* (++ actual_left) (-- actual_right))))] + (and (let [actual (is (/.-> Nat Nat Nat) + (/.function (_ actual_left actual_right) + (n.* (++ actual_left) (-- actual_right))))] (n.= (n.* (++ expected_left) (-- expected_right)) (actual expected_left expected_right))) - (let [actual (: (/.-> [Nat Nat] Nat) - (/.function (_ [actual_left actual_right]) - (n.* (++ actual_left) (-- actual_right))))] + (let [actual (is (/.-> [Nat Nat] Nat) + (/.function (_ [actual_left actual_right]) + (n.* (++ actual_left) (-- actual_right))))] (n.= (n.* (++ expected_left) (-- expected_right)) (actual [expected_left expected_right]))))))) @@ -801,8 +794,8 @@ (/.the #big_left) (n.= expected/b)) (|> sample - ((: (-> (-> Nat Nat) (-> Big Big)) - (/.revised #big_left)) + ((is (-> (-> Nat Nat) (-> Big Big)) + (/.revised #big_left)) (n.+ shift/b)) (/.the #big_left) (n.= expected/b))) @@ -815,8 +808,8 @@ (/.the [#big_right #small_left]) (n.= expected/s)) (|> sample - ((: (-> (-> Nat Nat) (-> Big Big)) - (/.revised [#big_right #small_left])) + ((is (-> (-> Nat Nat) (-> Big Big)) + (/.revised [#big_right #small_left])) (n.+ shift/s)) (/.the [#big_right #small_left]) (n.= expected/s))))) @@ -896,52 +889,52 @@ ($_ _.and (_.cover [/.Either] (and (exec - (: (/.Either Nat Text) - {.#Left left}) + (is (/.Either Nat Text) + {.#Left left}) true) (exec - (: (/.Either Nat Text) - {.#Right right}) + (is (/.Either Nat Text) + {.#Right right}) true))) (_.cover [/.Any] (and (exec - (: /.Any - left) + (is /.Any + left) true) (exec - (: /.Any - right) + (is /.Any + right) true))) (_.cover [/.Nothing] (and (exec - (: (-> /.Any /.Nothing) - (function (_ _) - (undefined))) + (is (-> /.Any /.Nothing) + (function (_ _) + (undefined))) true) (exec - (: (-> /.Any /.Int) - (function (_ _) - (: /.Int (undefined)))) + (is (-> /.Any /.Int) + (function (_ _) + (is /.Int (undefined)))) true))) (_.for [/.__adjusted_quantified_type__] ($_ _.and (_.cover [/.All] - (let [identity (: (/.All (_ a) (-> a a)) - (|>>))] + (let [identity (is (/.All (_ a) (-> a a)) + (|>>))] (and (exec - (: Nat - (identity left)) + (is Nat + (identity left)) true) (exec - (: Text - (identity right)) + (is Text + (identity right)) true)))) (_.cover [/.Ex] - (let [hide (: (/.Ex (_ a) (-> Nat a)) - (|>>))] + (let [hide (is (/.Ex (_ a) (-> Nat a)) + (|>>))] (exec - (: /.Any - (hide left)) + (is /.Any + (hide left)) true))))) (_.cover [/.same?] (let [not_left (atom.atom left) @@ -950,12 +943,12 @@ (/.same? not_left not_left) (not (/.same? left not_left))))) (_.cover [/.Rec] - (let [list (: (/.Rec NList - (Maybe [Nat NList])) - {.#Some [item/0 - {.#Some [item/1 - {.#Some [item/2 - {.#None}]}]}]})] + (let [list (is (/.Rec NList + (Maybe [Nat NList])) + {.#Some [item/0 + {.#Some [item/1 + {.#Some [item/2 + {.#None}]}]}]})] (case list {.#Some [actual/0 {.#Some [actual/1 {.#Some [actual/2 {.#None}]}]}]} (and (same? item/0 actual/0) @@ -1012,10 +1005,10 @@ (/.case [..#left expected_nat ..#right expected_int] [..#left 0 ..#right +0] true _ false) - (/.case (: (Either Nat Int) {.#Left expected_nat}) + (/.case (is (Either Nat Int) {.#Left expected_nat}) {.#Left 0} true _ false) - (/.case (: (Either Nat Int) {.#Right expected_int}) + (/.case (is (Either Nat Int) {.#Right expected_int}) {.#Right +0} true _ false) )) @@ -1154,20 +1147,20 @@ captured/2 (the .#captured scope/2) - local? (: (-> Ref Bit) - (function (_ ref) - (case ref - {.#Local _} true - {.#Captured _} false))) - captured? (: (-> Ref Bit) - (|>> local? not)) - binding? (: (-> (-> Ref Bit) Text Bit) - (function (_ is? name) - (|> captured/2 - (the .#mappings) - (plist.value name) - (maybe#each (|>> product.right is?)) - (maybe.else false)))) + local? (is (-> Ref Bit) + (function (_ ref) + (case ref + {.#Local _} true + {.#Captured _} false))) + captured? (is (-> Ref Bit) + (|>> local? not)) + binding? (is (-> (-> Ref Bit) Text Bit) + (function (_ is? name) + (|> captured/2 + (the .#mappings) + (plist.value name) + (maybe#each (|>> product.right is?)) + (maybe.else false)))) correct_closure! (and (n.= 6 (the .#counter captured/2)) diff --git a/stdlib/source/test/lux/abstract/comonad.lux b/stdlib/source/test/lux/abstract/comonad.lux index 2fb455145..5d5cb6857 100644 --- a/stdlib/source/test/lux/abstract/comonad.lux +++ b/stdlib/source/test/lux/abstract/comonad.lux @@ -1,17 +1,17 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]] - [data - ["[0]" identity {"+" Identity}]] - [math - ["[0]" random] - [number - ["n" nat]]] - ["_" test {"+" Test}]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + [abstract + [monad {"+" do}]] + [data + ["[0]" identity {"+" Identity}]] + [math + ["[0]" random] + [number + ["n" nat]]] + ["_" test {"+" Test}]]] + [\\library + ["[0]" /]]) (def: .public test Test @@ -21,8 +21,8 @@ ($_ _.and (_.cover [/.be] (n.= (++ sample) - (: (Identity Nat) - (/.be identity.comonad - [value (out sample)] - (out (++ value)))))) + (is (Identity Nat) + (/.be identity.comonad + [value (out sample)] + (out (++ value)))))) )))) diff --git a/stdlib/source/test/lux/abstract/comonad/cofree.lux b/stdlib/source/test/lux/abstract/comonad/cofree.lux index 02a722274..eb748e87b 100644 --- a/stdlib/source/test/lux/abstract/comonad/cofree.lux +++ b/stdlib/source/test/lux/abstract/comonad/cofree.lux @@ -1,23 +1,23 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [functor {"+" Functor}] - [comonad {"+" CoMonad}] - [\\specification - ["$[0]" functor {"+" Injection Comparison}] - ["$[0]" comonad]]] - [control - ["//" continuation]] - [data - [collection - ["[0]" list] - ["[0]" stream {"+" Stream} ("[1]#[0]" comonad)]]] - [math - ["[0]" random]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [functor {"+" Functor}] + [comonad {"+" CoMonad}] + [\\specification + ["$[0]" functor {"+" Injection Comparison}] + ["$[0]" comonad]]] + [control + ["//" continuation]] + [data + [collection + ["[0]" list] + ["[0]" stream {"+" Stream} ("[1]#[0]" comonad)]]] + [math + ["[0]" random]]]] + [\\library + ["[0]" /]]) (def: (injection value) (Injection (/.CoFree Stream)) @@ -43,9 +43,9 @@ (_.for [/.CoFree]) ($_ _.and (_.for [/.functor] - ($functor.spec ..injection ..comparison (: (Functor (/.CoFree Stream)) - (/.functor stream.functor)))) + ($functor.spec ..injection ..comparison (is (Functor (/.CoFree Stream)) + (/.functor stream.functor)))) (_.for [/.comonad] - ($comonad.spec ..injection ..comparison (: (CoMonad (/.CoFree Stream)) - (/.comonad stream.functor)))) + ($comonad.spec ..injection ..comparison (is (CoMonad (/.CoFree Stream)) + (/.comonad stream.functor)))) ))) diff --git a/stdlib/source/test/lux/abstract/enum.lux b/stdlib/source/test/lux/abstract/enum.lux index 11056a9a6..a4910e4c3 100644 --- a/stdlib/source/test/lux/abstract/enum.lux +++ b/stdlib/source/test/lux/abstract/enum.lux @@ -1,26 +1,26 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - ["[0]" maybe ("[1]#[0]" functor)]] - [data - ["[0]" product] - [collection - ["[0]" list ("[1]#[0]" mix)]]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" maybe ("[1]#[0]" functor)]] + [data + ["[0]" product] + [collection + ["[0]" list ("[1]#[0]" mix)]]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]]) (def: .public test Test - (let [limit (: (Random Nat) - (# random.monad each (n.% 20) random.nat))] + (let [limit (is (Random Nat) + (# random.monad each (n.% 20) random.nat))] (do random.monad [start limit end limit diff --git a/stdlib/source/test/lux/abstract/equivalence.lux b/stdlib/source/test/lux/abstract/equivalence.lux index db242434c..649d7a96b 100644 --- a/stdlib/source/test/lux/abstract/equivalence.lux +++ b/stdlib/source/test/lux/abstract/equivalence.lux @@ -1,21 +1,21 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [\\specification - [functor - ["$[0]" contravariant]]]] - [data - ["[0]" bit ("[1]#[0]" equivalence)]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat] - ["i" int]]]]] - [\\library - ["[0]" / {"+" Equivalence}]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [\\specification + [functor + ["$[0]" contravariant]]]] + [data + ["[0]" bit ("[1]#[0]" equivalence)]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat] + ["i" int]]]]] + [\\library + ["[0]" / {"+" Equivalence}]]) (def: .public test Test @@ -26,34 +26,34 @@ rightI random.int sample random.nat different (|> random.nat (random.only (|>> (n.= sample) not))) - .let [equivalence (: (Equivalence (Equivalence Nat)) - (implementation - (def: (= left right) - (and (bit#= (# left = leftN leftN) - (# right = leftN leftN)) - (bit#= (# left = rightN rightN) - (# right = rightN rightN)) - (bit#= (# left = leftN rightN) - (# right = leftN rightN))))))]] + .let [equivalence (is (Equivalence (Equivalence Nat)) + (implementation + (def: (= left right) + (and (bit#= (# left = leftN leftN) + (# right = leftN leftN)) + (bit#= (# left = rightN rightN) + (# right = rightN rightN)) + (bit#= (# left = leftN rightN) + (# right = leftN rightN))))))]] (<| (_.covering /._) ($_ _.and (_.for [/.functor] ($contravariant.spec equivalence n.equivalence /.functor)) (_.cover [/.rec] - (let [equivalence (: (Equivalence (List Nat)) - (/.rec (function (_ equivalence) - (implementation - (def: (= left right) - (case [left right] - [{.#End} {.#End}] - true + (let [equivalence (is (Equivalence (List Nat)) + (/.rec (function (_ equivalence) + (implementation + (def: (= left right) + (case [left right] + [{.#End} {.#End}] + true - [{.#Item leftH lefT} {.#Item rightH rightT}] - (and (n.= leftH rightH) - (# equivalence = lefT rightT)) + [{.#Item leftH lefT} {.#Item rightH rightT}] + (and (n.= leftH rightH) + (# equivalence = lefT rightT)) - _ - false))))))] + _ + false))))))] (and (# equivalence = (list sample sample) (list sample sample)) (not (# equivalence = (list sample sample) (list sample))) (not (# equivalence = (list sample sample) (list different different)))))) diff --git a/stdlib/source/test/lux/abstract/hash.lux b/stdlib/source/test/lux/abstract/hash.lux index 635476226..dd0fd6732 100644 --- a/stdlib/source/test/lux/abstract/hash.lux +++ b/stdlib/source/test/lux/abstract/hash.lux @@ -23,15 +23,15 @@ (do random.monad [leftN random.nat rightN random.nat - .let [hash (: (Equivalence (/.Hash Nat)) - (implementation - (def: (= (open "left#[0]") (open "right#[0]")) - (and (bit#= (left#= (left#hash leftN) (left#hash leftN)) - (right#= (right#hash leftN) (right#hash leftN))) - (bit#= (left#= (left#hash rightN) (left#hash rightN)) - (right#= (right#hash rightN) (right#hash rightN))) - (bit#= (left#= (left#hash leftN) (left#hash rightN)) - (right#= (right#hash leftN) (right#hash rightN)))))))]] + .let [hash (is (Equivalence (/.Hash Nat)) + (implementation + (def: (= (open "left#[0]") (open "right#[0]")) + (and (bit#= (left#= (left#hash leftN) (left#hash leftN)) + (right#= (right#hash leftN) (right#hash leftN))) + (bit#= (left#= (left#hash rightN) (left#hash rightN)) + (right#= (right#hash rightN) (right#hash rightN))) + (bit#= (left#= (left#hash leftN) (left#hash rightN)) + (right#= (right#hash leftN) (right#hash rightN)))))))]] (<| (_.covering /._) ($_ _.and (_.for [/.functor] diff --git a/stdlib/source/test/lux/abstract/monad.lux b/stdlib/source/test/lux/abstract/monad.lux index cb5654aed..93d060041 100644 --- a/stdlib/source/test/lux/abstract/monad.lux +++ b/stdlib/source/test/lux/abstract/monad.lux @@ -1,17 +1,17 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [data - ["[0]" identity {"+" Identity}] - [collection - ["[0]" list ("[1]#[0]" functor mix)]]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" / {"+" Monad do}]]) + [library + [lux "*" + ["_" test {"+" Test}] + [data + ["[0]" identity {"+" Identity}] + [collection + ["[0]" list ("[1]#[0]" functor mix)]]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" / {"+" Monad do}]]) (def: .public test Test @@ -22,36 +22,36 @@ ($_ _.and (_.cover [/.do] (n.= (++ mono) - (: (Identity Nat) - (/.do identity.monad - [sample (in mono)] - (in (++ sample)))))) + (is (Identity Nat) + (/.do identity.monad + [sample (in mono)] + (in (++ sample)))))) (_.cover [/.then] (n.= (++ mono) - (: (Identity Nat) - (/.then identity.monad - (|>> ++ (# identity.monad in)) - (# identity.monad in mono))))) + (is (Identity Nat) + (/.then identity.monad + (|>> ++ (# identity.monad in)) + (# identity.monad in mono))))) (_.cover [/.all] (# (list.equivalence n.equivalence) = (list#each ++ poly) (|> poly (list#each (|>> ++ (# identity.monad in))) - (: (List (Identity Nat))) + (is (List (Identity Nat))) (/.all identity.monad) - (: (Identity (List Nat)))))) + (is (Identity (List Nat)))))) (_.cover [/.each] (# (list.equivalence n.equivalence) = (list#each ++ poly) (|> poly (/.each identity.monad (|>> ++ (# identity.monad in))) - (: (Identity (List Nat)))))) + (is (Identity (List Nat)))))) (_.cover [/.only] (# (list.equivalence n.equivalence) = (list.only n.even? poly) (|> poly (/.only identity.monad (|>> n.even? (# identity.monad in))) - (: (Identity (List Nat)))))) + (is (Identity (List Nat)))))) (_.cover [/.mix] (n.= (list#mix n.+ 0 poly) (|> poly @@ -60,5 +60,5 @@ (# identity.monad in (n.+ part whole))) 0) - (: (Identity Nat))))) + (is (Identity Nat))))) )))) diff --git a/stdlib/source/test/lux/abstract/monad/free.lux b/stdlib/source/test/lux/abstract/monad/free.lux index 0afb69708..82bd8e2df 100644 --- a/stdlib/source/test/lux/abstract/monad/free.lux +++ b/stdlib/source/test/lux/abstract/monad/free.lux @@ -1,22 +1,22 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [functor {"+" Functor}] - [apply {"+" Apply}] - [monad {"+" Monad do}] - [\\specification - ["$[0]" functor {"+" Injection Comparison}] - ["$[0]" apply] - ["$[0]" monad]]] - [data - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [math - ["[0]" random]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [functor {"+" Functor}] + [apply {"+" Apply}] + [monad {"+" Monad do}] + [\\specification + ["$[0]" functor {"+" Injection Comparison}] + ["$[0]" apply] + ["$[0]" monad]]] + [data + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [math + ["[0]" random]]]] + [\\library + ["[0]" /]]) (def: injection (Injection (/.Free List)) @@ -46,12 +46,12 @@ (_.for [/.Free]) ($_ _.and (_.for [/.functor] - ($functor.spec ..injection ..comparison (: (Functor (/.Free List)) - (/.functor list.functor)))) + ($functor.spec ..injection ..comparison (is (Functor (/.Free List)) + (/.functor list.functor)))) (_.for [/.apply] - ($apply.spec ..injection ..comparison (: (Apply (/.Free List)) - (/.apply list.functor)))) + ($apply.spec ..injection ..comparison (is (Apply (/.Free List)) + (/.apply list.functor)))) (_.for [/.monad] - ($monad.spec ..injection ..comparison (: (Monad (/.Free List)) - (/.monad list.functor)))) + ($monad.spec ..injection ..comparison (is (Monad (/.Free List)) + (/.monad list.functor)))) ))) diff --git a/stdlib/source/test/lux/abstract/order.lux b/stdlib/source/test/lux/abstract/order.lux index 867e5ec3c..0092ab8bb 100644 --- a/stdlib/source/test/lux/abstract/order.lux +++ b/stdlib/source/test/lux/abstract/order.lux @@ -1,22 +1,22 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [\\specification - [functor - ["$[0]" contravariant]]]] - [data - ["[0]" bit ("[1]#[0]" equivalence)]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat]]]]] - [\\library - ["[0]" / - [// - [equivalence {"+" Equivalence}]]]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [\\specification + [functor + ["$[0]" contravariant]]]] + [data + ["[0]" bit ("[1]#[0]" equivalence)]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat]]]]] + [\\library + ["[0]" / + [// + [equivalence {"+" Equivalence}]]]]) (def: .public test Test @@ -24,15 +24,15 @@ (do random.monad [left random.nat right (|> random.nat (random.only (|>> (n.= left) not))) - .let [equivalence (: (Equivalence (/.Order Nat)) - (implementation - (def: (= leftO rightO) - (and (bit#= (# leftO < left left) - (# rightO < left left)) - (bit#= (# leftO < right right) - (# rightO < right right)) - (bit#= (# leftO < left right) - (# rightO < left right))))))]]) + .let [equivalence (is (Equivalence (/.Order Nat)) + (implementation + (def: (= leftO rightO) + (and (bit#= (# leftO < left left) + (# rightO < left left)) + (bit#= (# leftO < right right) + (# rightO < right right)) + (bit#= (# leftO < left right) + (# rightO < left right))))))]]) ($_ _.and (_.for [/.functor] ($contravariant.spec equivalence n.order /.functor)) diff --git a/stdlib/source/test/lux/abstract/predicate.lux b/stdlib/source/test/lux/abstract/predicate.lux index 379041a60..e61708ed4 100644 --- a/stdlib/source/test/lux/abstract/predicate.lux +++ b/stdlib/source/test/lux/abstract/predicate.lux @@ -1,26 +1,26 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [equivalence {"+" Equivalence}] - [monad {"+" do}] - [\\specification - ["$[0]" monoid] - [functor - ["$[0]" contravariant]]]] - [control - ["[0]" function]] - [data - ["[0]" bit ("[1]#[0]" equivalence)] - [collection - ["[0]" list]]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [equivalence {"+" Equivalence}] + [monad {"+" do}] + [\\specification + ["$[0]" monoid] + [functor + ["$[0]" contravariant]]]] + [control + ["[0]" function]] + [data + ["[0]" bit ("[1]#[0]" equivalence)] + [collection + ["[0]" list]]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]]) (def: (multiple? factor) (-> Nat (/.Predicate Nat)) @@ -34,19 +34,19 @@ (do [! random.monad] [sample random.nat samples (random.list 10 random.nat) - .let [equivalence (: (Equivalence (/.Predicate Nat)) - (implementation - (def: (= left right) - (bit#= (left sample) - (right sample)))))]]) + .let [equivalence (is (Equivalence (/.Predicate Nat)) + (implementation + (def: (= left right) + (bit#= (left sample) + (right sample)))))]]) (_.for [/.Predicate]) ($_ _.and (_.for [/.functor] ($contravariant.spec equivalence (multiple? 2) /.functor)) - (let [generator (: (Random (/.Predicate Nat)) - (|> random.nat - (random.only (|>> (n.= 0) not)) - (# ! each multiple?)))] + (let [generator (is (Random (/.Predicate Nat)) + (|> random.nat + (random.only (|>> (n.= 0) not)) + (# ! each multiple?)))] ($_ _.and (_.for [/.union] ($monoid.spec equivalence /.union generator)) @@ -76,16 +76,16 @@ ((/.difference /3? /2?) sample)))) (_.cover [/.rec] (let [even? (multiple? 2) - any_even? (: (/.Predicate (List Nat)) - (/.rec (function (_ again) - (function (_ values) - (case values - {.#End} - false + any_even? (is (/.Predicate (List Nat)) + (/.rec (function (_ again) + (function (_ values) + (case values + {.#End} + false - {.#Item head tail} - (or (even? head) - (again tail)))))))] + {.#Item head tail} + (or (even? head) + (again tail)))))))] (bit#= (list.any? even? samples) (any_even? samples)))) ))) diff --git a/stdlib/source/test/lux/control/concatenative.lux b/stdlib/source/test/lux/control/concatenative.lux index 85a1f4ac8..f6c5cb00f 100644 --- a/stdlib/source/test/lux/control/concatenative.lux +++ b/stdlib/source/test/lux/control/concatenative.lux @@ -1,23 +1,23 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [data - ["[0]" sum] - ["[0]" bit ("[1]#[0]" equivalence)]] - [macro - ["[0]" template]] - [math - ["[0]" random] - [number - ["n" nat] - ["i" int] - ["r" rev] - ["f" frac]]]]] - [\\library - ["[0]" / {"+" word: => ||>}]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [data + ["[0]" sum] + ["[0]" bit ("[1]#[0]" equivalence)]] + [macro + ["[0]" template]] + [math + ["[0]" random] + [number + ["n" nat] + ["i" int] + ["r" rev] + ["f" frac]]]]] + [\\library + ["[0]" / {"+" word: => ||>}]]) (def: stack_shuffling Test @@ -92,30 +92,30 @@ )))) (template: (!numerical <=> <generator> <only> <arithmetic> <order>) - [(: Test - (with_expansions [<arithmetic>' (template.spliced <arithmetic>) - <order>' (template.spliced <order>)] - (do random.monad - [parameter (|> <generator> (random.only <only>)) - subject <generator>] - (`` ($_ _.and - (~~ (template [<concatenative> <functional>] - [(_.cover [<concatenative>] - (<=> (<functional> parameter subject) - (||> (/.push subject) - (/.push parameter) - <concatenative>)))] + [(is Test + (with_expansions [<arithmetic>' (template.spliced <arithmetic>) + <order>' (template.spliced <order>)] + (do random.monad + [parameter (|> <generator> (random.only <only>)) + subject <generator>] + (`` ($_ _.and + (~~ (template [<concatenative> <functional>] + [(_.cover [<concatenative>] + (<=> (<functional> parameter subject) + (||> (/.push subject) + (/.push parameter) + <concatenative>)))] - <arithmetic>')) - (~~ (template [<concatenative> <functional>] - [(_.cover [<concatenative>] - (bit#= (<functional> parameter subject) - (||> (/.push subject) - (/.push parameter) - <concatenative>)))] + <arithmetic>')) + (~~ (template [<concatenative> <functional>] + [(_.cover [<concatenative>] + (bit#= (<functional> parameter subject) + (||> (/.push subject) + (/.push parameter) + <concatenative>)))] - <order>')) - )))))]) + <order>')) + )))))]) (def: numerical Test @@ -141,10 +141,10 @@ sample random.nat start random.nat .let [distance 10 - |++| (: (/.=> [Nat] [Nat]) - (/.apply/1 ++)) - |test| (: (/.=> [Nat] [Bit]) - (/.apply/1 (|>> (n.- start) (n.< distance))))]] + |++| (is (/.=> [Nat] [Nat]) + (/.apply/1 ++)) + |test| (is (/.=> [Nat] [Bit]) + (/.apply/1 (|>> (n.- start) (n.< distance))))]] ($_ _.and (_.cover [/.call /.apply/1] (n.= (++ sample) @@ -246,21 +246,21 @@ (_.cover [/.loop] (n.= (n.+ distance start) (||> (/.push start) - (/.push (: (/.=> [Nat] [Nat Bit]) - (|>> |++| /.dup |test|))) + (/.push (is (/.=> [Nat] [Nat Bit]) + (|>> |++| /.dup |test|))) /.loop))) (_.cover [/.while] (n.= (n.+ distance start) (||> (/.push start) - (/.push (: (/.=> [Nat] [Nat Bit]) - (|>> /.dup |test|))) + (/.push (is (/.=> [Nat] [Nat Bit]) + (|>> /.dup |test|))) (/.push |++|) /.while))) (_.cover [/.do] (n.= (++ sample) (||> (/.push sample) - (/.push (: (/.=> [] [Bit]) - (|>> (/.push false)))) + (/.push (is (/.=> [] [Bit]) + (|>> (/.push false)))) (/.push |++|) /.do /.while))) (_.cover [/.compose] diff --git a/stdlib/source/test/lux/control/concurrency/actor.lux b/stdlib/source/test/lux/control/concurrency/actor.lux index 5f96bbe35..73ff15702 100644 --- a/stdlib/source/test/lux/control/concurrency/actor.lux +++ b/stdlib/source/test/lux/control/concurrency/actor.lux @@ -49,12 +49,12 @@ Test (do [! random.monad] [initial_state random.nat - .let [as_mail (: (All (_ a) (-> (-> a a) (/.Mail a))) - (function (_ transform) - (function (_ state actor) - (|> state transform {try.#Success} async#in)))) - ++! (: (/.Mail Nat) (as_mail ++)) - --! (: (/.Mail Nat) (as_mail --))]] + .let [as_mail (is (All (_ a) (-> (-> a a) (/.Mail a))) + (function (_ transform) + (function (_ state actor) + (|> state transform {try.#Success} async#in)))) + ++! (is (/.Mail Nat) (as_mail ++)) + --! (is (/.Mail Nat) (as_mail --))]] (<| (_.covering /._) (_.for [/.Actor]) ($_ _.and @@ -82,23 +82,23 @@ (and poisoned_actors_die! cannot_poison_more_than_once!))) - (let [[read write] (: [(Async Text) (Resolver Text)] - (async.async []))] + (let [[read write] (is [(Async Text) (Resolver Text)] + (async.async []))] (in (do async.monad [_ (async.future (do io.monad - [actor (/.spawn! (: (/.Behavior Any Any) - [/.#on_init (|>>) - /.#on_mail (function (_ message state self) - (do [! async.monad] - [outcome (message state self)] - (case outcome - {try.#Failure cause} - (do ! - [_ (async.future (write cause))] - (in outcome)) - - {try.#Success _} - (in outcome))))]) + [actor (/.spawn! (is (/.Behavior Any Any) + [/.#on_init (|>>) + /.#on_mail (function (_ message state self) + (do [! async.monad] + [outcome (message state self)] + (case outcome + {try.#Failure cause} + (do ! + [_ (async.future (write cause))] + (in outcome)) + + {try.#Success _} + (in outcome))))]) [])] (/.poison! actor))) _ (async.delay 100) @@ -133,9 +133,9 @@ {try.#Failure error} (exception.match? /.dead error))))) - (let [die! (: (/.Mail Nat) - (function (_ state actor) - (async#in (exception.except ..got_wrecked []))))] + (let [die! (is (/.Mail Nat) + (function (_ state actor) + (async#in (exception.except ..got_wrecked []))))] (in (do async.monad [result (async.future (do io.monad [actor (/.spawn! /.default initial_state) @@ -202,8 +202,8 @@ events (random.list num_events random.nat) num_observations (# ! each (n.% num_events) random.nat) .let [expected (list.first num_observations events) - sink (: (Atom (Sequence Nat)) - (atom.atom sequence.empty))]] + sink (is (Atom (Sequence Nat)) + (atom.atom sequence.empty))]] (in (do async.monad [agent (async.future (do [! io.monad] diff --git a/stdlib/source/test/lux/control/concurrency/async.lux b/stdlib/source/test/lux/control/concurrency/async.lux index faff80b79..7a61769b8 100644 --- a/stdlib/source/test/lux/control/concurrency/async.lux +++ b/stdlib/source/test/lux/control/concurrency/async.lux @@ -67,8 +67,8 @@ ($monad.spec ..injection ..comparison /.monad)) (in (do /.monad - [.let [[async resolver] (: [(/.Async Nat) (/.Resolver Nat)] - (/.async []))] + [.let [[async resolver] (is [(/.Async Nat) (/.Resolver Nat)] + (/.async []))] resolved? (/.future (resolver expected)) actual async] (_.cover' [/.Async /.Resolver /.async] @@ -134,8 +134,8 @@ (n.+ leftA rightA))))) (in (do /.monad [?actual (/.future (/.value (/.resolved expected))) - .let [[async resolver] (: [(/.Async Nat) (/.Resolver Nat)] - (/.async []))] + .let [[async resolver] (is [(/.Async Nat) (/.Resolver Nat)] + (/.async []))] ?never (/.future (/.value async))] (_.cover' [/.value] (case [?actual ?never] @@ -146,8 +146,8 @@ false)))) (in (do /.monad [yep (/.future (/.resolved? (/.resolved expected))) - .let [[async resolver] (: [(/.Async Nat) (/.Resolver Nat)] - (/.async []))] + .let [[async resolver] (is [(/.Async Nat) (/.Resolver Nat)] + (/.async []))] nope (/.future (/.resolved? async))] (_.cover' [/.resolved?] (and yep @@ -163,8 +163,8 @@ _ false)))) (in (do /.monad - [.let [box (: (Atom Nat) - (atom.atom dummy))] + [.let [box (is (Atom Nat) + (atom.atom dummy))] _ (/.future (/.upon! (function (_ value) (atom.write! value box)) (/.resolved expected))) diff --git a/stdlib/source/test/lux/control/concurrency/frp.lux b/stdlib/source/test/lux/control/concurrency/frp.lux index c7b5922f3..7eb54cf9a 100644 --- a/stdlib/source/test/lux/control/concurrency/frp.lux +++ b/stdlib/source/test/lux/control/concurrency/frp.lux @@ -86,8 +86,8 @@ (_.cover [/.Channel /.Sink /.channel] (case (io.run! (do (try.with io.monad) - [.let [[channel sink] (: [(/.Channel Nat) (/.Sink Nat)] - (/.channel []))] + [.let [[channel sink] (is [(/.Channel Nat) (/.Sink Nat)] + (/.channel []))] _ (# sink feed sample) _ (# sink close)] (in channel))) @@ -107,8 +107,8 @@ (_.cover [/.channel_is_already_closed] (case (io.run! (do (try.with io.monad) - [.let [[channel sink] (: [(/.Channel Nat) (/.Sink Nat)] - (/.channel []))] + [.let [[channel sink] (is [(/.Channel Nat) (/.Sink Nat)] + (/.channel []))] _ (# sink close)] (# sink feed sample))) {try.#Success _} @@ -140,10 +140,10 @@ (list#= (list.only n.even? inputs) output)))) (in (do [! async.monad] - [.let [[?signal !signal] (: [(async.Async Any) (async.Resolver Any)] - (async.async [])) - sink (: (Atom (Sequence Nat)) - (atom.atom sequence.empty))] + [.let [[?signal !signal] (is [(async.Async Any) (async.Resolver Any)] + (async.async [])) + sink (is (Atom (Sequence Nat)) + (atom.atom sequence.empty))] _ (async.future (/.subscribe! (function (_ value) (do [! io.monad] [current (atom.read! sink) @@ -195,7 +195,7 @@ amount_of_polls (# ! each (|>> (n.% 10) ++) random.nat)] ($_ _.and (in (do [! async.monad] - [actual (..take_amount amount_of_polls (/.poll polling_delay (: (IO Nat) (io.io sample)))) + [actual (..take_amount amount_of_polls (/.poll polling_delay (is (IO Nat) (io.io sample)))) .let [correct_values! (list.every? (n.= sample) actual) diff --git a/stdlib/source/test/lux/control/continuation.lux b/stdlib/source/test/lux/control/continuation.lux index 6514b1332..bcf401329 100644 --- a/stdlib/source/test/lux/control/continuation.lux +++ b/stdlib/source/test/lux/control/continuation.lux @@ -68,29 +68,29 @@ (_.cover [/.shift /.reset] (let [(open "_#[0]") /.monad (open "list#[0]") (list.equivalence n.equivalence) - visit (: (-> (List Nat) - (/.Cont (List Nat) (List Nat))) - (function (visit xs) - (case xs - {.#End} - (_#in {.#End}) + visit (is (-> (List Nat) + (/.Cont (List Nat) (List Nat))) + (function (visit xs) + (case xs + {.#End} + (_#in {.#End}) - {.#Item x xs'} - (do [! /.monad] - [output (/.shift (function (_ k) - (do ! - [tail (k xs')] - (in {.#Item x tail}))))] - (visit output)))))] + {.#Item x xs'} + (do [! /.monad] + [output (/.shift (function (_ k) + (do ! + [tail (k xs')] + (in {.#Item x tail}))))] + (visit output)))))] (list#= elems (/.result (/.reset (visit elems)))))) (_.cover [/.continued] (/.continued (same? sample) - (: (/.Cont Nat Bit) - (function (_ next) - (next sample))))) + (is (/.Cont Nat Bit) + (function (_ next) + (next sample))))) (_.cover [/.pending] (/.continued (same? sample) - (: (/.Cont Nat Bit) - (/.pending sample)))) + (is (/.Cont Nat Bit) + (/.pending sample)))) ))) diff --git a/stdlib/source/test/lux/control/exception.lux b/stdlib/source/test/lux/control/exception.lux index 9c778e7b2..ad9ef59fb 100644 --- a/stdlib/source/test/lux/control/exception.lux +++ b/stdlib/source/test/lux/control/exception.lux @@ -95,8 +95,8 @@ {try.#Success _} false {try.#Failure message} (text#= message (/.error ..an_exception []))) (case (/.with ..an_exception [] - (: (Try Nat) - (/.except ..another_exception []))) + (is (Try Nat) + (/.except ..another_exception []))) {try.#Success _} false diff --git a/stdlib/source/test/lux/control/function.lux b/stdlib/source/test/lux/control/function.lux index eed6c9635..b1e00106a 100644 --- a/stdlib/source/test/lux/control/function.lux +++ b/stdlib/source/test/lux/control/function.lux @@ -1,24 +1,24 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [equivalence {"+" Equivalence}] - [monad {"+" do}] - [\\specification - ["$[0]" monoid]]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]] - ["[0]" / "_" - ["[1][0]" contract] - ["[1][0]" memo] - ["[1][0]" mixin] - ["[1][0]" mutual] - ["[1][0]" inline]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [equivalence {"+" Equivalence}] + [monad {"+" do}] + [\\specification + ["$[0]" monoid]]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]] + ["[0]" / "_" + ["[1][0]" contract] + ["[1][0]" memo] + ["[1][0]" mixin] + ["[1][0]" mutual] + ["[1][0]" inline]]) (def: .public test Test @@ -30,13 +30,13 @@ extra (|> random.nat (random.only (|>> (n.= expected) not)))] (<| (_.covering /._) ($_ _.and - (let [equivalence (: (Equivalence (-> Nat Nat)) - (implementation - (def: (= left right) - (n.= (left extra) - (right extra))))) - generator (: (Random (-> Nat Nat)) - (# ! each n.- random.nat))] + (let [equivalence (is (Equivalence (-> Nat Nat)) + (implementation + (def: (= left right) + (n.= (left extra) + (right extra))))) + generator (is (Random (-> Nat Nat)) + (# ! each n.- random.nat))] (_.for [/.monoid] ($monoid.spec equivalence /.monoid generator))) diff --git a/stdlib/source/test/lux/control/function/memo.lux b/stdlib/source/test/lux/control/function/memo.lux index b36688fbb..d1be1c598 100644 --- a/stdlib/source/test/lux/control/function/memo.lux +++ b/stdlib/source/test/lux/control/function/memo.lux @@ -105,13 +105,13 @@ (_.cover [/.memoization] (let [memo (<| //.fixed (//.mixed /.memoization) - (: (//.Mixin Nat (State (Dictionary Nat Nat) Nat)) - (function (factorial delegate again input) - (case input - (^.or 0 1) (# state.monad in 1) - _ (do state.monad - [output' (again (-- input))] - (in (n.* input output'))))))) + (is (//.Mixin Nat (State (Dictionary Nat Nat) Nat)) + (function (factorial delegate again input) + (case input + (^.or 0 1) (# state.monad in 1) + _ (do state.monad + [output' (again (-- input))] + (in (n.* input output'))))))) expected (|> (list.indices input) (list#each ++) (list#mix n.* 1)) diff --git a/stdlib/source/test/lux/control/function/mixin.lux b/stdlib/source/test/lux/control/function/mixin.lux index 7ec7c8c09..9dd982afd 100644 --- a/stdlib/source/test/lux/control/function/mixin.lux +++ b/stdlib/source/test/lux/control/function/mixin.lux @@ -30,16 +30,16 @@ [input (|> random.nat (# ! each (|>> (n.% 6) (n.+ 20)))) dummy random.nat shift (|> random.nat (random.only (|>> (n.= dummy) not))) - .let [equivalence (: (Equivalence (/.Mixin Nat Nat)) - (implementation - (def: (= left right) - (n.= ((/.fixed left) input) - ((/.fixed right) input))))) - generator (: (Random (/.Mixin Nat Nat)) - (do ! - [output random.nat] - (in (function (_ delegate again input) - output)))) + .let [equivalence (is (Equivalence (/.Mixin Nat Nat)) + (implementation + (def: (= left right) + (n.= ((/.fixed left) input) + ((/.fixed right) input))))) + generator (is (Random (/.Mixin Nat Nat)) + (do ! + [output random.nat] + (in (function (_ delegate again input) + output)))) expected (|> (list.indices input) (list#each ++) (list#mix n.* 1))]]) @@ -58,23 +58,23 @@ (n.= expected (factorial input)))) (_.cover [/.mixed] - (let [bottom (: (/.Mixin Nat Nat) - (function (_ delegate again input) - (case input - (^.or 0 1) 1 - _ (delegate input)))) - multiplication (: (/.Mixin Nat Nat) - (function (_ delegate again input) - (n.* input (again (-- input))))) + (let [bottom (is (/.Mixin Nat Nat) + (function (_ delegate again input) + (case input + (^.or 0 1) 1 + _ (delegate input)))) + multiplication (is (/.Mixin Nat Nat) + (function (_ delegate again input) + (n.* input (again (-- input))))) factorial (/.fixed (/.mixed bottom multiplication))] (n.= expected (factorial input)))) (_.cover [/.nothing] - (let [loop (: (/.Mixin Nat Nat) - (function (_ delegate again input) - (case input - (^.or 0 1) 1 - _ (n.* input (delegate (-- input)))))) + (let [loop (is (/.Mixin Nat Nat) + (function (_ delegate again input) + (case input + (^.or 0 1) 1 + _ (n.* input (delegate (-- input)))))) left (/.fixed (/.mixed /.nothing loop)) right (/.fixed (/.mixed loop /.nothing))] (and (n.= expected @@ -82,43 +82,43 @@ (n.= expected (right input))))) (_.cover [/.advice] - (let [bottom (: (/.Mixin Nat Nat) - (function (_ delegate again input) - 1)) - bottom? (: (Predicate Nat) - (function (_ input) - (case input - (^.or 0 1) true - _ false))) - multiplication (: (/.Mixin Nat Nat) - (function (_ delegate again input) - (n.* input (again (-- input))))) + (let [bottom (is (/.Mixin Nat Nat) + (function (_ delegate again input) + 1)) + bottom? (is (Predicate Nat) + (function (_ input) + (case input + (^.or 0 1) true + _ false))) + multiplication (is (/.Mixin Nat Nat) + (function (_ delegate again input) + (n.* input (again (-- input))))) factorial (/.fixed (/.mixed (/.advice bottom? bottom) multiplication))] (n.= expected (factorial input)))) (_.cover [/.before] - (let [implant (: (-> Nat (State Nat [])) - (function (_ input) - (function (_ state) - [shift []]))) - meld (: (/.Mixin Nat (State Nat Nat)) - (function (_ delegate again input) - (function (_ state) - [state (n.+ state input)]))) + (let [implant (is (-> Nat (State Nat [])) + (function (_ input) + (function (_ state) + [shift []]))) + meld (is (/.Mixin Nat (State Nat Nat)) + (function (_ delegate again input) + (function (_ state) + [state (n.+ state input)]))) function (/.fixed (/.mixed (/.before state.monad implant) meld))] (n.= (n.+ shift input) (|> input function (state.result dummy) product.right)))) (_.cover [/.after] - (let [implant (: (-> Nat Nat (State Nat [])) - (function (_ input output) - (function (_ state) - [shift []]))) - meld (: (/.Mixin Nat (State Nat Nat)) - (function (_ delegate again input) - (function (_ state) - [state (n.+ state input)]))) + (let [implant (is (-> Nat Nat (State Nat [])) + (function (_ input output) + (function (_ state) + [shift []]))) + meld (is (/.Mixin Nat (State Nat Nat)) + (function (_ delegate again input) + (function (_ state) + [state (n.+ state input)]))) function (/.fixed (/.mixed (/.after state.monad implant) meld))] (n.= (n.+ dummy input) diff --git a/stdlib/source/test/lux/control/lazy.lux b/stdlib/source/test/lux/control/lazy.lux index 8955a580d..1f1a9f0e1 100644 --- a/stdlib/source/test/lux/control/lazy.lux +++ b/stdlib/source/test/lux/control/lazy.lux @@ -33,9 +33,9 @@ (def: .public test Test - (with_expansions [<eager> (: [Nat Nat] - [(n.+ left right) - (n.* left right)])] + (with_expansions [<eager> (is [Nat Nat] + [(n.+ left right) + (n.* left right)])] (<| (_.covering /._) (do random.monad [left random.nat diff --git a/stdlib/source/test/lux/control/maybe.lux b/stdlib/source/test/lux/control/maybe.lux index 9563e44ce..665577be9 100644 --- a/stdlib/source/test/lux/control/maybe.lux +++ b/stdlib/source/test/lux/control/maybe.lux @@ -66,8 +66,8 @@ value random.nat] (_.cover [/.else] (and (same? default (/.else default - (: (Maybe Nat) - {.#None}))) + (is (Maybe Nat) + {.#None}))) (same? value (/.else default {.#Some value}))))) diff --git a/stdlib/source/test/lux/control/parser.lux b/stdlib/source/test/lux/control/parser.lux index 02da11358..8941a8137 100644 --- a/stdlib/source/test/lux/control/parser.lux +++ b/stdlib/source/test/lux/control/parser.lux @@ -271,8 +271,8 @@ (/.either <code>.nat (<code>.tuple self)))) level_0 (code.nat expected) - level_up (: (-> Code Code) - (|>> list code.tuple))] + level_up (is (-> Code Code) + (|>> list code.tuple))] (and (|> (list level_0) (/.result parser) (match actual (n.= expected actual))) diff --git a/stdlib/source/test/lux/control/parser/binary.lux b/stdlib/source/test/lux/control/parser/binary.lux index 00ff979d9..330349078 100644 --- a/stdlib/source/test/lux/control/parser/binary.lux +++ b/stdlib/source/test/lux/control/parser/binary.lux @@ -99,19 +99,19 @@ (random.list size again))] ($_ random.and ..random_location - (: (Random (Code' (Ann Location))) - ($_ random.or - random.bit - random.nat - random.int - random.rev - random.safe_frac - ..random_text - ..random_symbol - random_sequence - random_sequence - random_sequence - ))))))) + (is (Random (Code' (Ann Location))) + ($_ random.or + random.bit + random.nat + random.int + random.rev + random.safe_frac + ..random_text + ..random_symbol + random_sequence + random_sequence + random_sequence + ))))))) (def: random_type (Random Type) @@ -282,8 +282,8 @@ (_.cover [/.or format.or] (|> expected (format.result (format.or format.bit format.nat)) - (/.result (: (/.Parser (Either Bit Nat)) - (/.or /.bit /.nat))) + (/.result (is (/.Parser (Either Bit Nat)) + (/.or /.bit /.nat))) (!expect (^.multi {try.#Success actual} (# (sum.equivalence bit.equivalence n.equivalence) = expected @@ -296,8 +296,8 @@ (_.cover [/.invalid_tag] (|> [tag value] (format.result (format.and format.bits/8 format.bit)) - (/.result (: (/.Parser (Either Bit Nat)) - (/.or /.bit /.nat))) + (/.result (is (/.Parser (Either Bit Nat)) + (/.or /.bit /.nat))) (!expect (^.multi {try.#Failure error} (exception.match? /.invalid_tag error)))))) (do [! random.monad] @@ -306,12 +306,12 @@ (|> expected (format.result (format.rec (|>> (format.and format.nat) (format.or format.any)))) - (/.result (: (/.Parser (List Nat)) - (/.rec - (function (_ again) - (/.or /.any - (<>.and /.nat - again)))))) + (/.result (is (/.Parser (List Nat)) + (/.rec + (function (_ again) + (/.or /.any + (<>.and /.nat + again)))))) (!expect (^.multi {try.#Success actual} (# (list.equivalence n.equivalence) = expected diff --git a/stdlib/source/test/lux/control/parser/type.lux b/stdlib/source/test/lux/control/parser/type.lux index 0a3bf5945..93020e506 100644 --- a/stdlib/source/test/lux/control/parser/type.lux +++ b/stdlib/source/test/lux/control/parser/type.lux @@ -153,19 +153,19 @@ {.#Parameter 0}) (!expect {try.#Success [quantification##binding argument##binding _]}))) (_.cover [/.argument] - (let [argument? (: (-> Nat Nat Bit) - (function (_ @ expected) - (|> (/.result (<| (/.with_extension quantification) - (/.with_extension argument) - (/.with_extension quantification) - (/.with_extension argument) - (do //.monad - [env /.env - _ /.any] - (in (/.argument env @)))) - not_parameter) - (!expect (^.multi {try.#Success [_ _ _ _ actual]} - (n.= expected actual))))))] + (let [argument? (is (-> Nat Nat Bit) + (function (_ @ expected) + (|> (/.result (<| (/.with_extension quantification) + (/.with_extension argument) + (/.with_extension quantification) + (/.with_extension argument) + (do //.monad + [env /.env + _ /.any] + (in (/.argument env @)))) + not_parameter) + (!expect (^.multi {try.#Success [_ _ _ _ actual]} + (n.= expected actual))))))] (and (argument? 0 2) (argument? 1 3) (argument? 2 0)))) diff --git a/stdlib/source/test/lux/control/parser/xml.lux b/stdlib/source/test/lux/control/parser/xml.lux index 40582948d..c3acb66ba 100644 --- a/stdlib/source/test/lux/control/parser/xml.lux +++ b/stdlib/source/test/lux/control/parser/xml.lux @@ -147,9 +147,9 @@ (/.attribute [expected expected])) {xml.#Text expected}]]) (do [! random.monad] - [.let [node (: (-> xml.Tag (List xml.XML) xml.XML) - (function (_ tag children) - {xml.#Node tag (dictionary.empty symbol.hash) children}))] + [.let [node (is (-> xml.Tag (List xml.XML) xml.XML) + (function (_ tag children) + {xml.#Node tag (dictionary.empty symbol.hash) children}))] parent ..random_tag right ..random_tag wrong (random.only (|>> (symbol#= right) not) diff --git a/stdlib/source/test/lux/control/reader.lux b/stdlib/source/test/lux/control/reader.lux index 7b2c8e43f..c20b2acbe 100644 --- a/stdlib/source/test/lux/control/reader.lux +++ b/stdlib/source/test/lux/control/reader.lux @@ -50,11 +50,11 @@ (/.result sample (/.local (n.* factor) /.read)))) (let [(open "io#[0]") io.monad] (_.cover [/.with /.lifted] - (|> (: (/.Reader Any (IO Nat)) - (do (/.with io.monad) - [a (/.lifted (io#in sample)) - b (in factor)] - (in (n.* b a)))) + (|> (is (/.Reader Any (IO Nat)) + (do (/.with io.monad) + [a (/.lifted (io#in sample)) + b (in factor)] + (in (n.* b a)))) (/.result []) io.run! (n.= (n.* factor sample))))))))) diff --git a/stdlib/source/test/lux/control/region.lux b/stdlib/source/test/lux/control/region.lux index e4492b7f4..3cd12740a 100644 --- a/stdlib/source/test/lux/control/region.lux +++ b/stdlib/source/test/lux/control/region.lux @@ -1,32 +1,32 @@ (.using - [library - [lux "*" - [type {"+" :sharing}] - ["_" test {"+" Test}] - [abstract - [equivalence {"+" Equivalence}] - [functor {"+" Functor}] - [apply {"+" Apply}] - ["[0]" monad {"+" Monad do}] - ["[0]" enum] - [\\specification - ["$[0]" functor {"+" Injection Comparison}] - ["$[0]" apply] - ["$[0]" monad]]] - [control - ["[0]" try {"+" Try}]] - [data - [collection - ["[0]" list]]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" / {"+" Region} - [// - ["[0]" thread {"+" Thread}] - ["[0]" exception {"+" Exception exception:}]]]]) + [library + [lux "*" + [type {"+" sharing}] + ["_" test {"+" Test}] + [abstract + [equivalence {"+" Equivalence}] + [functor {"+" Functor}] + [apply {"+" Apply}] + ["[0]" monad {"+" Monad do}] + ["[0]" enum] + [\\specification + ["$[0]" functor {"+" Injection Comparison}] + ["$[0]" apply] + ["$[0]" monad]]] + [control + ["[0]" try {"+" Try}]] + [data + [collection + ["[0]" list]]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" / {"+" Region} + [// + ["[0]" thread {"+" Thread}] + ["[0]" exception {"+" Exception exception:}]]]]) (exception: oops) @@ -58,18 +58,18 @@ (def: comparison (Comparison (All (_ a) (All (_ ! r) (Region r (Thread !) a)))) (function (_ == left right) - (case [(:sharing [a] - (Equivalence a) - == - - (Try a) - (thread.result (:expected (/.run! thread.monad left)))) - (:sharing [a] - (Equivalence a) - == - - (Try a) - (thread.result (:expected (/.run! thread.monad right))))] + (case [(sharing [a] + (Equivalence a) + == + + (Try a) + (thread.result (as_expected (/.run! thread.monad left)))) + (sharing [a] + (Equivalence a) + == + + (Try a) + (thread.result (as_expected (/.run! thread.monad right))))] [{try.#Success left} {try.#Success right}] (== left right) @@ -84,17 +84,17 @@ [expected_clean_ups (|> random.nat (# ! each (|>> (n.% 100) (n.max 1))))] ($_ _.and (_.for [/.functor] - ($functor.spec ..injection ..comparison (: (All (_ ! r) - (Functor (Region r (thread.Thread !)))) - (/.functor thread.functor)))) + ($functor.spec ..injection ..comparison (is (All (_ ! r) + (Functor (Region r (thread.Thread !)))) + (/.functor thread.functor)))) (_.for [/.apply] - ($apply.spec ..injection ..comparison (: (All (_ ! r) - (Apply (Region r (thread.Thread !)))) - (/.apply thread.monad)))) + ($apply.spec ..injection ..comparison (is (All (_ ! r) + (Apply (Region r (thread.Thread !)))) + (/.apply thread.monad)))) (_.for [/.monad] - ($monad.spec ..injection ..comparison (: (All (_ ! r) - (Monad (Region r (thread.Thread !)))) - (/.monad thread.monad)))) + ($monad.spec ..injection ..comparison (is (All (_ ! r) + (Monad (Region r (thread.Thread !)))) + (/.monad thread.monad)))) (_.cover [/.run!] (thread.result @@ -160,8 +160,8 @@ count_clean_up (function (_ value) (do ! [_ (thread.update! ++ clean_up_counter)] - (in (: (Try Any) - (exception.except ..oops [])))))] + (in (is (Try Any) + (exception.except ..oops [])))))] outcome (/.run! ! (do [! (/.monad !)] [_ (monad.each ! (/.acquire! //@ count_clean_up) diff --git a/stdlib/source/test/lux/control/security/policy.lux b/stdlib/source/test/lux/control/security/policy.lux index 6ced1e85c..6d72ff177 100644 --- a/stdlib/source/test/lux/control/security/policy.lux +++ b/stdlib/source/test/lux/control/security/policy.lux @@ -37,37 +37,37 @@ (type: (Policy %) (Interface - (: (Hash (Password %)) - &hash) + (is (Hash (Password %)) + &hash) - (: (-> Text (Password %)) - password) + (is (-> Text (Password %)) + password) - (: (Privilege Privacy %) - privilege))) + (is (Privilege Privacy %) + privilege))) (def: (policy _) (Ex (_ %) (-> Any (Policy %))) (/.with_policy - (: (Context Privacy Policy) - (function (_ (^.let privilege (open "%[0]"))) - (implementation - (def: &hash - (implementation - (def: &equivalence - (implementation - (def: (= reference sample) - (text#= (%#can_downgrade reference) - (%#can_downgrade sample))))) - (def: hash - (|>> %#can_downgrade - (# text.hash hash))))) - - (def: password - %#can_upgrade) + (is (Context Privacy Policy) + (function (_ (^.let privilege (open "%[0]"))) + (implementation + (def: &hash + (implementation + (def: &equivalence + (implementation + (def: (= reference sample) + (text#= (%#can_downgrade reference) + (%#can_downgrade sample))))) + (def: hash + (|>> %#can_downgrade + (# text.hash hash))))) + + (def: password + %#can_upgrade) - (def: privilege - privilege)))))) + (def: privilege + privilege)))))) (def: .public test Test diff --git a/stdlib/source/test/lux/control/state.lux b/stdlib/source/test/lux/control/state.lux index 9cc2cac76..f7e7161be 100644 --- a/stdlib/source/test/lux/control/state.lux +++ b/stdlib/source/test/lux/control/state.lux @@ -108,11 +108,11 @@ right random.nat] (let [(open "io#[0]") io.monad] (_.cover [/.+State /.with /.lifted /.result'] - (|> (: (/.+State io.IO Nat Nat) - (do (/.with io.monad) - [a (/.lifted io.monad (io#in left)) - b (in right)] - (in (n.+ a b)))) + (|> (is (/.+State io.IO Nat Nat) + (do (/.with io.monad) + [a (/.lifted io.monad (io#in left)) + b (in right)] + (in (n.+ a b)))) (/.result' state) io.run! (pipe.let [state' output'] diff --git a/stdlib/source/test/lux/control/thread.lux b/stdlib/source/test/lux/control/thread.lux index 7e6468a8c..5da8a5e95 100644 --- a/stdlib/source/test/lux/control/thread.lux +++ b/stdlib/source/test/lux/control/thread.lux @@ -1,21 +1,21 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [\\specification - ["$[0]" functor {"+" Injection Comparison}] - ["$[0]" apply] - ["$[0]" monad]]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" / {"+" Thread} - [// - ["[0]" io]]]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [\\specification + ["$[0]" functor {"+" Injection Comparison}] + ["$[0]" apply] + ["$[0]" monad]]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" / {"+" Thread} + [// + ["[0]" io]]]]) (def: (injection value) (Injection (All (_ a !) (Thread ! a))) @@ -59,24 +59,24 @@ ($_ _.and (_.cover [/.read!] (n.= sample - (/.result (: (All (_ !) (Thread ! Nat)) - (do /.monad - [box (/.box sample)] - (/.read! box)))))) + (/.result (is (All (_ !) (Thread ! Nat)) + (do /.monad + [box (/.box sample)] + (/.read! box)))))) (_.cover [/.write!] (n.= factor - (/.result (: (All (_ !) (Thread ! Nat)) - (do /.monad - [box (/.box sample) - _ (/.write! factor box)] - (/.read! box)))))) + (/.result (is (All (_ !) (Thread ! Nat)) + (do /.monad + [box (/.box sample) + _ (/.write! factor box)] + (/.read! box)))))) (_.cover [/.update!] (n.= (n.* factor sample) - (/.result (: (All (_ !) (Thread ! Nat)) - (do /.monad - [box (/.box sample) - old (/.update! (n.* factor) box)] - (/.read! box)))))))) + (/.result (is (All (_ !) (Thread ! Nat)) + (do /.monad + [box (/.box sample) + old (/.update! (n.* factor) box)] + (/.read! box)))))))) )))) diff --git a/stdlib/source/test/lux/control/try.lux b/stdlib/source/test/lux/control/try.lux index a606da407..aeb49df81 100644 --- a/stdlib/source/test/lux/control/try.lux +++ b/stdlib/source/test/lux/control/try.lux @@ -68,7 +68,7 @@ false)) (_.cover [/.maybe] (case [(/.maybe {/.#Success expected}) - (/.maybe (: (/.Try Nat) {/.#Failure error}))] + (/.maybe (is (/.Try Nat) {/.#Failure error}))] [{.#Some actual} {.#None}] (n.= expected actual) @@ -78,7 +78,7 @@ (and (n.= expected (/.else alternative {/.#Success expected})) (n.= alternative - (/.else alternative (: (Try Nat) {/.#Failure error}))))) + (/.else alternative (is (Try Nat) {/.#Failure error}))))) (_.cover [/.with /.lifted] (let [lifted (/.lifted io.monad)] (|> (do (/.with io.monad) diff --git a/stdlib/source/test/lux/data.lux b/stdlib/source/test/lux/data.lux index 631a72b76..07ec343ce 100644 --- a/stdlib/source/test/lux/data.lux +++ b/stdlib/source/test/lux/data.lux @@ -24,10 +24,10 @@ ... TODO: Get rid of this ASAP (template: (!bundle body) - [(: Test - (do random.monad - [_ (in [])] - body))]) + [(is Test + (do random.monad + [_ (in [])] + body))]) (def: format Test diff --git a/stdlib/source/test/lux/data/binary.lux b/stdlib/source/test/lux/data/binary.lux index d179058fd..650ee562a 100644 --- a/stdlib/source/test/lux/data/binary.lux +++ b/stdlib/source/test/lux/data/binary.lux @@ -121,10 +121,10 @@ [3 !.bytes/8 !.with/8!])) (_.cover [!.slice] (let [random_slice (!.slice offset length sample) - idxs (: (List Nat) - (case length - 0 (list) - _ (enum.range n.enum 0 (-- length)))) + idxs (is (List Nat) + (case length + 0 (list) + _ (enum.range n.enum 0 (-- length)))) reader (function (_ binary idx) (!.bytes/1 idx binary))] (and (n.= length (!.size random_slice)) @@ -182,10 +182,10 @@ (..binary_io 3 /.read/64! /.write/64! value)))) (_.cover [/.slice] (let [random_slice (try.trusted (/.slice offset length sample)) - idxs (: (List Nat) - (case length - 0 (list) - _ (enum.range n.enum 0 (-- length)))) + idxs (is (List Nat) + (case length + 0 (list) + _ (enum.range n.enum 0 (-- length)))) reader (function (_ binary idx) (/.read/8! idx binary))] (and (n.= length (/.size random_slice)) diff --git a/stdlib/source/test/lux/data/collection/array.lux b/stdlib/source/test/lux/data/collection/array.lux index b41a178d2..1d0d95f34 100644 --- a/stdlib/source/test/lux/data/collection/array.lux +++ b/stdlib/source/test/lux/data/collection/array.lux @@ -63,11 +63,11 @@ evens (random.array size (random.only n.even? random.nat))] ($_ _.and (let [(open "/#[0]") /.functor - choose (: (-> Nat (Maybe Text)) - (function (_ value) - (if (n.even? value) - {.#Some (# n.decimal encoded value)} - {.#None})))] + choose (is (-> Nat (Maybe Text)) + (function (_ value) + (if (n.even? value) + {.#Some (# n.decimal encoded value)} + {.#None})))] (_.cover [/.one] (case [(|> evens (/#each (# n.decimal encoded)) @@ -144,16 +144,16 @@ (!.each $ it)))) (_.for [!.mix] ($mix.spec ..injection /.equivalence - (: (Mix !.Array) - (function (_ $ init it) - (!.mix (function (_ index item output) - ($ item output)) - init - it))))) + (is (Mix !.Array) + (function (_ $ init it) + (!.mix (function (_ index item output) + ($ item output)) + init + it))))) (_.cover [!.empty !.size] - (n.= size (!.size (: (Array Nat) - (!.empty size))))) + (n.= size (!.size (is (Array Nat) + (!.empty size))))) (_.cover [!.type] (case !.Array (pattern (<| {.#Named (symbol !.Array)} @@ -165,44 +165,44 @@ false)) (_.cover [!.lacks?] (let [the_array (|> (!.empty 2) - (: (Array Nat)) + (is (Array Nat)) (!.has! 0 expected))] (and (not (!.lacks? 0 the_array)) (!.lacks? 1 the_array)))) (_.cover [!.item !.has!] (|> (!.empty 2) - (: (Array Nat)) + (is (Array Nat)) (!.has! 0 expected) (!.item 0) (n.= expected))) (_.cover [!.lacks!] (|> (!.empty 1) - (: (Array Nat)) + (is (Array Nat)) (!.has! 0 expected) (!.lacks! 0) (!.lacks? 0))) (_.cover [!.lacks?] (let [the_array (|> (!.empty 2) - (: (Array Nat)) + (is (Array Nat)) (!.has! 0 expected))] (and (not (!.lacks? 0 the_array)) (!.lacks? 1 the_array)))) (_.cover [!.has?] (let [the_array (|> (!.empty 2) - (: (Array Nat)) + (is (Array Nat)) (!.has! 0 expected))] (and (!.has? 0 the_array) (not (!.has? 1 the_array))))) (_.cover [!.revised!] (|> (!.empty 1) - (: (Array Nat)) + (is (Array Nat)) (!.has! 0 base) (!.revised! 0 (n.+ shift)) (!.item 0) (n.= expected))) (_.cover [!.upsert!] (let [the_array (|> (!.empty 2) - (: (Array Nat)) + (is (Array Nat)) (!.has! 0 base) (!.upsert! 0 dummy (n.+ shift)) (!.upsert! 1 base (n.+ shift)))] @@ -211,8 +211,8 @@ (do ! [occupancy (# ! each (n.% (++ size)) random.nat)] (_.cover [!.occupancy !.vacancy] - (let [the_array (loop [output (: (Array Nat) - (!.empty size)) + (let [the_array (loop [output (is (Array Nat) + (!.empty size)) idx 0] (if (n.< occupancy idx) (again (!.has! idx expected output) @@ -243,8 +243,8 @@ (do ! [amount (# ! each (n.% (++ size)) random.nat)] (_.cover [!.copy!] - (let [copy (: (Array Nat) - (!.empty size))] + (let [copy (is (Array Nat) + (!.empty size))] (exec (!.copy! amount 0 the_array 0 copy) (# (list.equivalence n.equivalence) = (list.first amount (!.list {.#None} the_array)) @@ -263,11 +263,11 @@ (|> the_array (!.list {.#None}) (# (list.equivalence n.equivalence) = evens)))))) - (let [choose (: (-> Nat (Maybe Text)) - (function (_ value) - (if (n.even? value) - {.#Some (# n.decimal encoded value)} - {.#None})))] + (let [choose (is (-> Nat (Maybe Text)) + (function (_ value) + (if (n.even? value) + {.#Some (# n.decimal encoded value)} + {.#None})))] (_.cover [!.one] (|> evens (!.one choose) @@ -320,8 +320,8 @@ ..search (_.cover [/.empty /.size] - (n.= size (/.size (: (Array Nat) - (/.empty size))))) + (n.= size (/.size (is (Array Nat) + (/.empty size))))) (_.cover [/.type_name] (case /.Array (pattern (<| {.#Named (symbol /.Array)} @@ -334,7 +334,7 @@ false)) (_.cover [/.read! /.write!] (let [the_array (|> (/.empty 2) - (: (Array Nat)) + (is (Array Nat)) (/.write! 0 expected))] (case [(/.read! 0 the_array) (/.read! 1 the_array)] @@ -345,7 +345,7 @@ false))) (_.cover [/.delete!] (let [the_array (|> (/.empty 1) - (: (Array Nat)) + (is (Array Nat)) (/.write! 0 expected))] (case [(/.read! 0 the_array) (/.read! 0 (/.delete! 0 the_array))] @@ -356,19 +356,19 @@ false))) (_.cover [/.lacks?] (let [the_array (|> (/.empty 2) - (: (Array Nat)) + (is (Array Nat)) (/.write! 0 expected))] (and (not (/.lacks? 0 the_array)) (/.lacks? 1 the_array)))) (_.cover [/.contains?] (let [the_array (|> (/.empty 2) - (: (Array Nat)) + (is (Array Nat)) (/.write! 0 expected))] (and (/.contains? 0 the_array) (not (/.contains? 1 the_array))))) (_.cover [/.update!] (let [the_array (|> (/.empty 1) - (: (Array Nat)) + (is (Array Nat)) (/.write! 0 base) (/.update! 0 (n.+ shift)))] (case (/.read! 0 the_array) @@ -379,7 +379,7 @@ false))) (_.cover [/.upsert!] (let [the_array (|> (/.empty 2) - (: (Array Nat)) + (is (Array Nat)) (/.write! 0 base) (/.upsert! 0 dummy (n.+ shift)) (/.upsert! 1 base (n.+ shift)))] @@ -394,8 +394,8 @@ (do ! [occupancy (# ! each (n.% (++ size)) random.nat)] (_.cover [/.occupancy /.vacancy] - (let [the_array (loop [output (: (Array Nat) - (/.empty size)) + (let [the_array (loop [output (is (Array Nat) + (/.empty size)) idx 0] (if (n.< occupancy idx) (again (/.write! idx expected output) @@ -426,8 +426,8 @@ (do ! [amount (# ! each (n.% (++ size)) random.nat)] (_.cover [/.copy!] - (let [copy (: (Array Nat) - (/.empty size))] + (let [copy (is (Array Nat) + (/.empty size))] (exec (/.copy! amount 0 the_array 0 copy) (# (list.equivalence n.equivalence) = (list.first amount (/.list {.#None} the_array)) diff --git a/stdlib/source/test/lux/data/collection/dictionary.lux b/stdlib/source/test/lux/data/collection/dictionary.lux index 1054e5248..0a1f9d295 100644 --- a/stdlib/source/test/lux/data/collection/dictionary.lux +++ b/stdlib/source/test/lux/data/collection/dictionary.lux @@ -54,11 +54,11 @@ (do ! [constant random.nat - .let [hash (: (Hash Nat) - (implementation - (def: &equivalence n.equivalence) - (def: (hash _) - constant)))]] + .let [hash (is (Hash Nat) + (implementation + (def: &equivalence n.equivalence) + (def: (hash _) + constant)))]] (_.cover [/.key_hash] (same? hash (/.key_hash (/.empty hash))))) diff --git a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux index 3e628ec45..c20a3b480 100644 --- a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux +++ b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux @@ -57,10 +57,10 @@ (n.< left right)) pairs) sorted_values (list#each product.right sorted_pairs) - (open "list#[0]") (list.equivalence (: (Equivalence [Nat Nat]) - (function (_ [kr vr] [ks vs]) - (and (n.= kr ks) - (n.= vr vs))))) + (open "list#[0]") (list.equivalence (is (Equivalence [Nat Nat]) + (function (_ [kr vr] [ks vs]) + (and (n.= kr ks) + (n.= vr vs))))) (open "/#[0]") (/.equivalence n.equivalence)]] ($_ _.and (_.for [/.equivalence] diff --git a/stdlib/source/test/lux/data/collection/list.lux b/stdlib/source/test/lux/data/collection/list.lux index 88ce2f5b9..c1440d110 100644 --- a/stdlib/source/test/lux/data/collection/list.lux +++ b/stdlib/source/test/lux/data/collection/list.lux @@ -281,12 +281,12 @@ (open "/#[0]") /.functor (open "/#[0]") /.monoid - +/2 (: (-> Nat Nat Nat) - (function (_ left right) - ($_ n.+ left right))) - +/3 (: (-> Nat Nat Nat Nat) - (function (_ left mid right) - ($_ n.+ left mid right)))] + +/2 (is (-> Nat Nat Nat) + (function (_ left right) + ($_ n.+ left right))) + +/3 (is (-> Nat Nat Nat Nat) + (function (_ left mid right) + ($_ n.+ left mid right)))] (do [! random.monad] [sample/0 ..random sample/1 ..random @@ -374,11 +374,11 @@ Test (let [(open "/#[0]") /.functor - choice (: (-> Nat (Maybe Text)) - (function (_ value) - (if (n.even? value) - {.#Some (# n.decimal encoded value)} - {.#None})))] + choice (is (-> Nat (Maybe Text)) + (function (_ value) + (if (n.even? value) + {.#Some (# n.decimal encoded value)} + {.#None})))] (do [! random.monad] [sample ..random] ($_ _.and diff --git a/stdlib/source/test/lux/data/collection/sequence.lux b/stdlib/source/test/lux/data/collection/sequence.lux index 125dfaac9..34e1b13c2 100644 --- a/stdlib/source/test/lux/data/collection/sequence.lux +++ b/stdlib/source/test/lux/data/collection/sequence.lux @@ -116,14 +116,14 @@ (and (/.within_bounds? sample good_index) (not (/.within_bounds? sample bad_index)))) (_.cover [/.index_out_of_bounds] - (let [fails! (: (All (_ a) (-> (Try a) Bit)) - (function (_ situation) - (case situation - {try.#Success member} - false - - {try.#Failure error} - (exception.match? /.index_out_of_bounds error))))] + (let [fails! (is (All (_ a) (-> (Try a) Bit)) + (function (_ situation) + (case situation + {try.#Success member} + false + + {try.#Failure error} + (exception.match? /.index_out_of_bounds error))))] (and (fails! (/.item bad_index sample)) (fails! (/.has bad_index non_member sample)) (fails! (/.revised bad_index ++ sample))))) @@ -195,11 +195,11 @@ (/.size negatives)))))) (_.cover [/.one] (let [(open "/#[0]") /.functor - choice (: (-> Nat (Maybe Text)) - (function (_ value) - (if (n.even? value) - {.#Some (# n.decimal encoded value)} - {.#None})))] + choice (is (-> Nat (Maybe Text)) + (function (_ value) + (if (n.even? value) + {.#Some (# n.decimal encoded value)} + {.#None})))] (case [(|> sample (/.only n.even?) (/#each (# n.decimal encoded)) diff --git a/stdlib/source/test/lux/data/collection/set.lux b/stdlib/source/test/lux/data/collection/set.lux index dee48cc02..0d6f31475 100644 --- a/stdlib/source/test/lux/data/collection/set.lux +++ b/stdlib/source/test/lux/data/collection/set.lux @@ -1,24 +1,24 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [hash {"+" Hash}] - [monad {"+" do}] - [\\specification - ["$[0]" equivalence] - ["$[0]" hash] - ["$[0]" monoid]]] - [data - ["[0]" bit ("[1]#[0]" equivalence)] - [collection - ["[0]" list]]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat]]]]] - [\\library - ["[0]" / ("#[0]" equivalence)]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [hash {"+" Hash}] + [monad {"+" do}] + [\\specification + ["$[0]" equivalence] + ["$[0]" hash] + ["$[0]" monoid]]] + [data + ["[0]" bit ("[1]#[0]" equivalence)] + [collection + ["[0]" list]]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat]]]]] + [\\library + ["[0]" / ("#[0]" equivalence)]]) (def: gen_nat (Random Nat) @@ -53,12 +53,12 @@ (/.empty? (/.empty n.hash))) (do ! [hash (# ! each (function (_ constant) - (: (Hash Nat) - (implementation - (def: &equivalence n.equivalence) - - (def: (hash _) - constant)))) + (is (Hash Nat) + (implementation + (def: &equivalence n.equivalence) + + (def: (hash _) + constant)))) random.nat)] (_.cover [/.member_hash] (same? hash (/.member_hash (/.empty hash))))) diff --git a/stdlib/source/test/lux/data/collection/tree/finger.lux b/stdlib/source/test/lux/data/collection/tree/finger.lux index 804bed4bb..06c77591e 100644 --- a/stdlib/source/test/lux/data/collection/tree/finger.lux +++ b/stdlib/source/test/lux/data/collection/tree/finger.lux @@ -1,32 +1,32 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - ["[0]" maybe ("[1]#[0]" functor)]] - [data - ["[0]" text ("[1]#[0]" equivalence monoid)] - [collection - ["[0]" list ("[1]#[0]" mix)]]] - [math - ["[0]" random] - [number - ["n" nat]]] - [type {"+" :by_example}]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" maybe ("[1]#[0]" functor)]] + [data + ["[0]" text ("[1]#[0]" equivalence monoid)] + [collection + ["[0]" list ("[1]#[0]" mix)]]] + [math + ["[0]" random] + [number + ["n" nat]]] + [type {"+" by_example}]]] + [\\library + ["[0]" /]]) (def: builder (/.builder text.monoid)) (def: :@: - (:by_example [@] - (/.Builder @ Text) - ..builder - - @)) + (by_example [@] + (/.Builder @ Text) + ..builder + + @)) (def: .public test Test diff --git a/stdlib/source/test/lux/data/color/named.lux b/stdlib/source/test/lux/data/color/named.lux index 055c76259..e7be0c11e 100644 --- a/stdlib/source/test/lux/data/color/named.lux +++ b/stdlib/source/test/lux/data/color/named.lux @@ -1,22 +1,22 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [data - [collection - ["[0]" list] - ["[0]" set]]] - [macro - ["[0]" template]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat]]]]] - [\\library - ["[0]" / - ["/[1]" //]]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [data + [collection + ["[0]" list] + ["[0]" set]]] + [macro + ["[0]" template]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat]]]]] + [\\library + ["[0]" / + ["/[1]" //]]]) (with_expansions [<colors> (as_is [letter/a [/.alice_blue @@ -202,9 +202,9 @@ )] (def: all_colors (list.together (`` (list (~~ (template [<definition> <by_letter>] - [((: (-> Any (List //.Color)) - (function (_ _) - (`` (list (~~ (template.spliced <by_letter>)))))) + [((is (-> Any (List //.Color)) + (function (_ _) + (`` (list (~~ (template.spliced <by_letter>)))))) 123)] <colors>)))))) diff --git a/stdlib/source/test/lux/data/format/tar.lux b/stdlib/source/test/lux/data/format/tar.lux index f09796461..d38efe7ec 100644 --- a/stdlib/source/test/lux/data/format/tar.lux +++ b/stdlib/source/test/lux/data/format/tar.lux @@ -205,8 +205,8 @@ (<b>.result /.parser))] (in (case (sequence.list tar) (pattern (list {<tag> [actual_path actual_moment actual_mode actual_ownership actual_content]})) - (let [seconds (: (-> Instant Int) - (|>> instant.relative (duration.ticks duration.second)))] + (let [seconds (is (-> Instant Int) + (|>> instant.relative (duration.ticks duration.second)))] (and (text#= (/.from_path expected_path) (/.from_path actual_path)) (i.= (seconds expected_moment) diff --git a/stdlib/source/test/lux/data/sum.lux b/stdlib/source/test/lux/data/sum.lux index 6dc6eeb9e..6d9e6cc5e 100644 --- a/stdlib/source/test/lux/data/sum.lux +++ b/stdlib/source/test/lux/data/sum.lux @@ -38,32 +38,32 @@ (_.cover [/.left] (|> (/.left expected) - (: (Or Nat Nat)) + (is (Or Nat Nat)) (pipe.case {0 #0 actual} (n.= expected actual) _ false))) (_.cover [/.right] (|> (/.right expected) - (: (Or Nat Nat)) + (is (Or Nat Nat)) (pipe.case {0 #1 actual} (n.= expected actual) _ false))) (_.cover [/.either] (and (|> (/.left expected) - (: (Or Nat Nat)) + (is (Or Nat Nat)) (/.either (n.+ shift) (n.- shift)) (n.= (n.+ shift expected))) (|> (/.right expected) - (: (Or Nat Nat)) + (is (Or Nat Nat)) (/.either (n.+ shift) (n.- shift)) (n.= (n.- shift expected))))) (_.cover [/.then] (and (|> (/.left expected) - (: (Or Nat Nat)) + (is (Or Nat Nat)) (/.then (n.+ shift) (n.- shift)) (pipe.case {0 #0 actual} (n.= (n.+ shift expected) actual) _ false)) (|> (/.right expected) - (: (Or Nat Nat)) + (is (Or Nat Nat)) (/.then (n.+ shift) (n.- shift)) (pipe.case {0 #1 actual} (n.= (n.- shift expected) actual) _ false)))) (do ! @@ -71,8 +71,8 @@ expected (random.list size random.nat)] ($_ _.and (_.cover [/.lefts] - (let [actual (: (List (Or Nat Nat)) - (list#each /.left expected))] + (let [actual (is (List (Or Nat Nat)) + (list#each /.left expected))] (and (# (list.equivalence n.equivalence) = expected (/.lefts actual)) @@ -80,8 +80,8 @@ (list) (/.rights actual))))) (_.cover [/.rights] - (let [actual (: (List (Or Nat Nat)) - (list#each /.right expected))] + (let [actual (is (List (Or Nat Nat)) + (list#each /.right expected))] (and (# (list.equivalence n.equivalence) = expected (/.rights actual)) @@ -94,7 +94,7 @@ (if (n.even? value) (/.left value) (/.right value)))) - (: (List (Or Nat Nat))) + (is (List (Or Nat Nat))) /.partition)] (and (# (list.equivalence n.equivalence) = (list.only n.even? expected) diff --git a/stdlib/source/test/lux/data/text/encoding.lux b/stdlib/source/test/lux/data/text/encoding.lux index c848511a9..c8410b813 100644 --- a/stdlib/source/test/lux/data/text/encoding.lux +++ b/stdlib/source/test/lux/data/text/encoding.lux @@ -1,29 +1,29 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [\\specification - ["$[0]" codec]]] - [control - ["[0]" maybe] - ["[0]" try]] - [data - ["[0]" text ("[1]#[0]" equivalence)] - [collection - ["[0]" list ("[1]#[0]" mix)] - ["[0]" set]]] - [macro - ["[0]" template]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]] - ["[0]" / "_" - ["[1][0]" utf8]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [\\specification + ["$[0]" codec]]] + [control + ["[0]" maybe] + ["[0]" try]] + [data + ["[0]" text ("[1]#[0]" equivalence)] + [collection + ["[0]" list ("[1]#[0]" mix)] + ["[0]" set]]] + [macro + ["[0]" template]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]] + ["[0]" / "_" + ["[1][0]" utf8]]) (with_expansions [<encodings> (as_is [all/a [/.ascii]] @@ -183,9 +183,9 @@ /.koi8_u]] ) <named> (template [<definition> <by_letter>] - [((: (-> Any (List /.Encoding)) - (function (_ _) - (`` (list (~~ (template.spliced <by_letter>)))))) + [((is (-> Any (List /.Encoding)) + (function (_ _) + (`` (list (~~ (template.spliced <by_letter>)))))) [])] <encodings>)] diff --git a/stdlib/source/test/lux/data/text/unicode/block.lux b/stdlib/source/test/lux/data/text/unicode/block.lux index fa2ef3756..b54ec0d9c 100644 --- a/stdlib/source/test/lux/data/text/unicode/block.lux +++ b/stdlib/source/test/lux/data/text/unicode/block.lux @@ -1,26 +1,26 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [\\specification - ["$[0]" equivalence] - ["$[0]" hash] - ["$[0]" monoid]]] - [data - ["[0]" text] - [collection - ["[0]" set] - ["[0]" list]]] - [macro - ["[0]" template]] - [math - ["[0]" random {"+" Random}] - [number {"+" hex} - ["n" nat]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [\\specification + ["$[0]" equivalence] + ["$[0]" hash] + ["$[0]" monoid]]] + [data + ["[0]" text] + [collection + ["[0]" set] + ["[0]" list]]] + [macro + ["[0]" template]] + [math + ["[0]" random {"+" Random}] + [number {"+" hex} + ["n" nat]]]]] + [\\library + ["[0]" /]]) (def: .public random (Random /.Block) @@ -147,9 +147,9 @@ /.basic_latin/lower]] ) <named> (template [<definition> <part>] - [((: (-> Any (List /.Block)) - (function (_ _) - (`` (list (~~ (template.spliced <part>)))))) + [((is (-> Any (List /.Block)) + (function (_ _) + (`` (list (~~ (template.spliced <part>)))))) [])] <blocks>)] diff --git a/stdlib/source/test/lux/debug.lux b/stdlib/source/test/lux/debug.lux index 9f619b3c0..fdf83aaa7 100644 --- a/stdlib/source/test/lux/debug.lux +++ b/stdlib/source/test/lux/debug.lux @@ -90,7 +90,7 @@ ... TODO: Uncomment after switching from the old (tag+last?) to the new (lefts+right?) representation for variants ... (~~ (template [<lefts> <right?> <value> <format>] ... [(|> (/.representation (type (Or Bit Int Frac)) - ... (: (Or Bit Int Frac) + ... (is (Or Bit Int Frac) ... (<lefts> <right?> <value>))) ... (try#each (text#= (format "(" (%.nat <lefts>) ... " " (%.bit <right?>) @@ -171,11 +171,11 @@ (|> (/.representation .Any sample_frac) (try#each (text#= "[]")) (try.else false)) - (|> (/.representation (type (List Nat)) (: (List Nat) (list sample_nat))) + (|> (/.representation (type (List Nat)) (is (List Nat) (list sample_nat))) (try#each (text#= (%.list %.nat (list sample_nat)))) (try.else false)) (~~ (template [<sample>] - [(|> (/.representation (type (Maybe Nat)) (: (Maybe Nat) <sample>)) + [(|> (/.representation (type (Maybe Nat)) (is (Maybe Nat) <sample>)) (try#each (text#= (%.maybe %.nat <sample>))) (try.else false))] @@ -209,7 +209,7 @@ [%.text sample_text] )) (text#= (|> (list sample_bit sample_int sample_frac sample_text) - (: (List Any)) + (is (List Any)) (list#each /.inspection) (text.interposed " ") (text.enclosed ["[" "]"])) @@ -236,8 +236,8 @@ ($_ _.and ..inspection ..representation - (_.cover [/.:hole /.type_hole] - (let [error (: My_Text (..macro_error (/.:hole)))] + (_.cover [/.hole /.type_hole] + (let [error (is My_Text (..macro_error (/.hole)))] (and (exception.match? /.type_hole error) (text.contains? (%.type My_Text) error)))) (do random.monad @@ -257,8 +257,8 @@ (..macro_error (/.here yolo)))) (_.cover [/.private] (exec - (: (/.private /.Inspector) - /.inspection) + (is (/.private /.Inspector) + /.inspection) true)) (_.cover [/.log!] (exec diff --git a/stdlib/source/test/lux/ffi.js.lux b/stdlib/source/test/lux/ffi.js.lux index 2a30d0464..e015ea5e8 100644 --- a/stdlib/source/test/lux/ffi.js.lux +++ b/stdlib/source/test/lux/ffi.js.lux @@ -52,8 +52,8 @@ number (# ! each (|>> (nat.% 100) nat.frac) random.nat) string (random.ascii 5) function (# ! each (function (_ shift) - (: (-> Nat Nat) - (nat.+ shift))) + (is (-> Nat Nat) + (nat.+ shift))) random.nat) ... I64s get compiled as JavaScript objects with a specific structure. object random.nat] @@ -62,7 +62,7 @@ (~~ (template [<type> <value>] [(_.cover [<type>] (exec - (: <type> <value>) + (is <type> <value>) true))] [/.Boolean boolean] @@ -74,9 +74,9 @@ (~~ (template [<type>] [(_.cover [<type>] (exec - (: (Ex (_ a) (/.Object a)) - (: <type> - (:expected []))) + (is (Ex (_ a) (/.Object a)) + (is <type> + (as_expected []))) true))] [/.Function] @@ -87,9 +87,9 @@ )) (_.cover [/.null] (exec - (: Nat (/.null [])) - (: Text (/.null [])) - (: (All (_ a) (-> a a)) (/.null [])) + (is Nat (/.null [])) + (is Text (/.null [])) + (is (All (_ a) (-> a a)) (/.null [])) true)) (_.cover [/.null?] (and (/.null? (/.null [])) @@ -129,9 +129,9 @@ (let [encoding "utf8"] (text#= string (cond /.on_nashorn? - (let [binary (java/lang/String::getBytes encoding (:as java/lang/String string))] + (let [binary (java/lang/String::getBytes encoding (as java/lang/String string))] (|> (java/lang/String::new binary encoding) - (:as Text))) + (as Text))) /.on_node_js? (|> (Buffer::from string encoding) diff --git a/stdlib/source/test/lux/ffi.jvm.lux b/stdlib/source/test/lux/ffi.jvm.lux index 0cc809a70..cab7732cb 100644 --- a/stdlib/source/test/lux/ffi.jvm.lux +++ b/stdlib/source/test/lux/ffi.jvm.lux @@ -58,8 +58,8 @@ (template [<name> <type> <conversion> <lux> <=>] [(def: (<name> left right) (-> <type> <type> Bit) - (<=> (:as <lux> (<conversion> left)) - (:as <lux> (<conversion> right))))] + (<=> (as <lux> (<conversion> left)) + (as <lux> (<conversion> right))))] [boolean#= /.Boolean <| Bit bit#=] [byte#= /.Byte /.byte_to_long Int i#=] @@ -136,8 +136,8 @@ /.of_long (i.= (/.of_long value)))) (_.cover [/.cannot_convert_to_jvm_type] - (let [array (:as (Array Nothing) - (array.empty 1))] + (let [array (as (Array Nothing) + (array.empty 1))] (|> array /.length ..macro_error @@ -146,7 +146,7 @@ (def: for_miscellaneous Test (`` (do [! random.monad] - [sample (# ! each (|>> (:as java/lang/Object)) + [sample (# ! each (|>> (as java/lang/Object)) (random.ascii 1)) boolean (# ! each (|>> /.as_boolean) random.bit) byte (# ! each (|>> /.as_byte) random.int) @@ -179,12 +179,12 @@ (not (/.null? sample)))) (_.cover [/.???] (and (|> (/.??? (/.null)) - (: (Maybe java/lang/Object)) + (is (Maybe java/lang/Object)) (pipe.case {.#None} #1 {.#Some _} #0)) (|> (/.??? sample) - (: (Maybe java/lang/Object)) + (is (Maybe java/lang/Object)) (pipe.case {.#Some _} #1 {.#None} #0)))) @@ -200,11 +200,11 @@ <lux#value> <as> <of> <lux#=>] [(_.cover [<object> <primitive>] (|> <jvm#value> - (: <object>) + (is <object>) "jvm object cast" - (: <primitive>) + (is <primitive>) "jvm object cast" - (: <object>) + (is <object>) (<jvm#=> <jvm#value>))) (_.cover [<as> <of>] (|> <lux#value> @@ -237,11 +237,11 @@ (text#= it)))) (_.cover [/.cannot_cast_to_non_object] (text.contains? (the exception.#label /.cannot_cast_to_non_object) - (macro_error (/.:as boolean (: /.Boolean boolean))))) - (_.cover [/.:as] + (macro_error (/.as boolean (is /.Boolean boolean))))) + (_.cover [/.as] (|> string - (/.:as java/lang/Object) - (same? (:as java/lang/Object string)))) + (/.as java/lang/Object) + (same? (as java/lang/Object string)))) (_.cover [/.type] (and (and (type#= /.Boolean (/.type java/lang/Boolean)) (type#= /.Boolean (/.type boolean))) @@ -309,8 +309,8 @@ java/lang/Long (/.as_long (.int expected)))) example/0! - (same? (: Any expected) - (: Any (test/TestInterface0::actual0 object/0))) + (same? (is Any expected) + (is Any (test/TestInterface0::actual0 object/0))) object/1 (/.object [] [test/TestInterface1] [] @@ -324,8 +324,8 @@ example/1! (and (case (test/TestInterface1::actual1 (/.as_boolean false) object/1) {try.#Success actual} - (same? (: Any expected) - (: Any actual)) + (same? (is Any expected) + (is Any actual)) {try.#Failure error} false) @@ -343,8 +343,8 @@ a input)) example/2! - (same? (: Any expected) - (: Any (test/TestInterface2::actual2 (/.as_long (.int expected)) object/2))) + (same? (is Any expected) + (is Any (test/TestInterface2::actual2 (/.as_long (.int expected)) object/2))) object/3 (/.object [] [(test/TestInterface3 java/lang/Long)] [] @@ -353,8 +353,8 @@ a (/.as_long (.int expected)))) example/3! - (same? (: Any expected) - (: Any (test/TestInterface3::actual3 object/3))) + (same? (is Any expected) + (is Any (test/TestInterface3::actual3 object/3))) example/4! (let [expected (i.+ left right) @@ -558,8 +558,8 @@ (n.= expected (.nat (/.of_long (test/TestInterface2::actual2 (/.as_long (.int expected)) object/2)))) - object/3 (: (test/TestClass3 java/lang/Long) - (test/TestClass3::new (/.as_long (.int expected)))) + object/3 (is (test/TestClass3 java/lang/Long) + (test/TestClass3::new (/.as_long (.int expected)))) example/3! (n.= expected (.nat (/.of_long (test/TestInterface3::actual3 object/3)))) @@ -584,14 +584,14 @@ (i.= expected (/.of_long (test/TestInterface4::actual4 (/.as_long left) (/.as_long right) object/8))))] - .let [random_long (: (Random java/lang/Long) - (# ! each (|>> /.as_long) - random.int))] + .let [random_long (is (Random java/lang/Long) + (# ! each (|>> /.as_long) + random.int))] dummy/0 random_long dummy/1 random_long dummy/2 random_long - .let [object/9 (/.do_to (: (test/TestClass9 java/lang/Long) - (test/TestClass9::new dummy/0)) + .let [object/9 (/.do_to (is (test/TestClass9 java/lang/Long) + (test/TestClass9::new dummy/0)) (test/TestClass9::set_actual9 dummy/1) (test/TestClass9::set_actual9 dummy/2)) diff --git a/stdlib/source/test/lux/ffi.lua.lux b/stdlib/source/test/lux/ffi.lua.lux index 4c0a6aed0..75faa3349 100644 --- a/stdlib/source/test/lux/ffi.lua.lux +++ b/stdlib/source/test/lux/ffi.lua.lux @@ -27,7 +27,7 @@ (~~ (template [<type> <sample>] [(_.cover [<type>] (exec - (: <type> <sample>) + (is <type> <sample>) true))] [/.Boolean boolean] @@ -41,8 +41,8 @@ [(_.cover [<type>] (exec (|> [] - (:as <type>) - (: (Ex (_ a) (/.Object a)))) + (as <type>) + (is (Ex (_ a) (/.Object a)))) true))] [/.Nil] @@ -53,8 +53,8 @@ (|> (/.function (_ [input/0 Nat]) Int (.int input/0)) - (: /.Function) - (: (Ex (_ a) (/.Object a)))) + (is /.Function) + (is (Ex (_ a) (/.Object a)))) true)) (_.cover [/.import:] (case (io.run! (..os/getenv string)) diff --git a/stdlib/source/test/lux/ffi.old.lux b/stdlib/source/test/lux/ffi.old.lux index 39a86642e..f452cf5a1 100644 --- a/stdlib/source/test/lux/ffi.old.lux +++ b/stdlib/source/test/lux/ffi.old.lux @@ -181,11 +181,11 @@ (and (/.null? (/.null)) (not (/.null? sample)))) (_.cover [/.???] - (and (|> (: (Maybe java/lang/Object) (/.??? (/.null))) + (and (|> (is (Maybe java/lang/Object) (/.??? (/.null))) (pipe.case {.#None} #1 _ #0)) - (|> (: (Maybe java/lang/Object) (/.??? sample)) + (|> (is (Maybe java/lang/Object) (/.??? sample)) (pipe.case {.#Some _} #1 _ #0)))) diff --git a/stdlib/source/test/lux/ffi.py.lux b/stdlib/source/test/lux/ffi.py.lux index ec8381e92..b3e8f9fa6 100644 --- a/stdlib/source/test/lux/ffi.py.lux +++ b/stdlib/source/test/lux/ffi.py.lux @@ -30,7 +30,7 @@ (~~ (template [<type> <sample>] [(_.cover [<type>] (exec - (: <type> <sample>) + (is <type> <sample>) true))] [/.Boolean boolean] @@ -44,8 +44,8 @@ [(_.cover [<type>] (exec (|> [] - (:as <type>) - (: (Ex (_ a) (/.Object a)))) + (as <type>) + (is (Ex (_ a) (/.Object a)))) true))] [/.None] @@ -56,8 +56,8 @@ (|> (/.function (_ [input/0 Nat]) Int (.int input/0)) - (: /.Function) - (: (Ex (_ a) (/.Object a)))) + (is /.Function) + (is (Ex (_ a) (/.Object a)))) true)) (_.cover [/.import:] (and (i.= (os::R_OK) (os::R_OK)) diff --git a/stdlib/source/test/lux/ffi.rb.lux b/stdlib/source/test/lux/ffi.rb.lux index 75a89c833..49833b639 100644 --- a/stdlib/source/test/lux/ffi.rb.lux +++ b/stdlib/source/test/lux/ffi.rb.lux @@ -27,7 +27,7 @@ (~~ (template [<type> <sample>] [(_.cover [<type>] (exec - (: <type> <sample>) + (is <type> <sample>) true))] [/.Boolean boolean] @@ -41,8 +41,8 @@ [(_.cover [<type>] (exec (|> [] - (:as <type>) - (: (Ex (_ a) (/.Object a)))) + (as <type>) + (is (Ex (_ a) (/.Object a)))) true))] [/.Nil] diff --git a/stdlib/source/test/lux/locale/language.lux b/stdlib/source/test/lux/locale/language.lux index f3bf54cad..bf61cbc92 100644 --- a/stdlib/source/test/lux/locale/language.lux +++ b/stdlib/source/test/lux/locale/language.lux @@ -35,8 +35,8 @@ [(def: <bundle> Bundle (let [amount (template.amount <languages>) - languages (: (List /.Language) - (`` (list (~~ (template.spliced <languages>)))))] + languages (is (List /.Language) + (`` (list (~~ (template.spliced <languages>)))))] [#amount amount #names (|> languages (list#each /.name) (set.of_list text.hash)) #codes (|> languages (list#each /.code) (set.of_list text.hash)) diff --git a/stdlib/source/test/lux/macro.lux b/stdlib/source/test/lux/macro.lux index 5cb684336..e1927eedb 100644 --- a/stdlib/source/test/lux/macro.lux +++ b/stdlib/source/test/lux/macro.lux @@ -42,8 +42,8 @@ _ false)]) (template: (!global <definition>) - [(: [Text .Global] - [(template.text [<definition>]) {.#Definition [true .Macro <definition>]}])]) + [(is [Text .Global] + [(template.text [<definition>]) {.#Definition [true .Macro <definition>]}])]) (syntax: (pow/2 [number <code>.any]) (in (list (` (n.* (~ number) (~ number)))))) @@ -79,19 +79,19 @@ .#modules (list [macro_module [.#module_hash 0 .#module_aliases (list) - .#definitions (: (List [Text .Global]) - (list (!global /.log_single_expansion!) - (!global /.log_expansion!) - (!global /.log_full_expansion!))) + .#definitions (is (List [Text .Global]) + (list (!global /.log_single_expansion!) + (!global /.log_expansion!) + (!global /.log_full_expansion!))) .#imports (list) .#module_state {.#Active}]] [current_module [.#module_hash 0 .#module_aliases (list) - .#definitions (: (List [Text .Global]) - (list (!global ..pow/2) - (!global ..pow/4) - (!global ..repeated))) + .#definitions (is (List [Text .Global]) + (list (!global ..pow/2) + (!global ..pow/4) + (!global ..repeated))) .#imports (list) .#module_state {.#Active}]]) .#scopes (list) @@ -102,7 +102,7 @@ .#seed seed .#scope_type_vars (list) .#extensions [] - .#eval (:as (-> Type Code (Meta Any)) []) + .#eval (as (-> Type Code (Meta Any)) []) .#host []]]))) (syntax: (iterated [cycle <code>.nat diff --git a/stdlib/source/test/lux/macro/code.lux b/stdlib/source/test/lux/macro/code.lux index ffa65358b..81c17f991 100644 --- a/stdlib/source/test/lux/macro/code.lux +++ b/stdlib/source/test/lux/macro/code.lux @@ -63,8 +63,8 @@ (let [parse (syntax.parse "" syntax.no_aliases (text.size source_code)) - start (: Source - [location.dummy 0 source_code])] + start (is Source + [location.dummy 0 source_code])] (case (parse start) {.#Left [end error]} {try.#Failure error} @@ -76,13 +76,13 @@ (-> [Code Code] (Random [Code Code])) (random.rec (function (_ replacement_simulation) - (let [for_sequence (: (-> (-> (List Code) Code) (Random [Code Code])) - (function (_ to_code) - (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))])))))] + (let [for_sequence (is (-> (-> (List Code) Code) (Random [Code Code])) + (function (_ to_code) + (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/macro/local.lux b/stdlib/source/test/lux/macro/local.lux index b9b996461..88840d364 100644 --- a/stdlib/source/test/lux/macro/local.lux +++ b/stdlib/source/test/lux/macro/local.lux @@ -51,8 +51,8 @@ [pop! (/.push (list [name (..constant constant)])) [module short] (meta.normal name) _ (if pre_remove - (let [remove_macro! (: (-> .Module .Module) - (revised .#definitions (plist.lacks short)))] + (let [remove_macro! (is (-> .Module .Module) + (revised .#definitions (plist.lacks short)))] (function (_ lux) {try.#Success [(revised .#modules (plist.revised module remove_macro!) lux) []]})) diff --git a/stdlib/source/test/lux/macro/pattern.lux b/stdlib/source/test/lux/macro/pattern.lux index d5b7b9dcb..a0d4be149 100644 --- a/stdlib/source/test/lux/macro/pattern.lux +++ b/stdlib/source/test/lux/macro/pattern.lux @@ -60,16 +60,16 @@ (/.or "+0.5" "+1.25") true _ false))) (_.cover [/.let] - (let [expected_pair (: (Pair Nat Int) - [..#left expected_nat ..#right expected_int])] + (let [expected_pair (is (Pair Nat Int) + [..#left expected_nat ..#right expected_int])] (/.case expected_pair (/.let actual_pair (/.pattern (!pair actual_left actual_right))) (and (/.same? expected_pair actual_pair) (/.same? expected_nat actual_left) (/.same? expected_int actual_right))))) (_.cover [/.multi] - (let [expected_pair (: (Pair Nat Int) - [..#left expected_nat ..#right expected_int])] + (let [expected_pair (is (Pair Nat Int) + [..#left expected_nat ..#right expected_int])] (and (/.case expected_pair (/.multi (/.pattern (!pair 0 actual_right)) [actual_right diff --git a/stdlib/source/test/lux/macro/syntax/definition.lux b/stdlib/source/test/lux/macro/syntax/definition.lux index bd8e41b38..d0b3cceb3 100644 --- a/stdlib/source/test/lux/macro/syntax/definition.lux +++ b/stdlib/source/test/lux/macro/syntax/definition.lux @@ -50,7 +50,7 @@ .#seed 0 .#scope_type_vars (list) .#extensions [] - .#eval (:as (-> Type Code (Meta Any)) []) + .#eval (as (-> Type Code (Meta Any)) []) .#host []]) (def: .public test diff --git a/stdlib/source/test/lux/math/logic/fuzzy.lux b/stdlib/source/test/lux/math/logic/fuzzy.lux index 3c7b34b10..a79d72805 100644 --- a/stdlib/source/test/lux/math/logic/fuzzy.lux +++ b/stdlib/source/test/lux/math/logic/fuzzy.lux @@ -339,11 +339,11 @@ (do random.monad [sample random.rev [_ fuzzy] ..gradient - .let [equivalence (: (Equivalence (/.Fuzzy Rev)) - (implementation - (def: (= left right) - (r.= (left sample) - (right sample)))))]] + .let [equivalence (is (Equivalence (/.Fuzzy Rev)) + (implementation + (def: (= left right) + (r.= (left sample) + (right sample)))))]] ($_ _.and (_.for [/.functor] ($contravariant.spec equivalence fuzzy /.functor)) diff --git a/stdlib/source/test/lux/math/modular.lux b/stdlib/source/test/lux/math/modular.lux index e19c662d4..243603132 100644 --- a/stdlib/source/test/lux/math/modular.lux +++ b/stdlib/source/test/lux/math/modular.lux @@ -1,32 +1,32 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - ["[0]" type ("[1]#[0]" equivalence)] - [abstract - [monad {"+" do}] - ["[0]" predicate] - [\\specification - ["$[0]" equivalence] - ["$[0]" order] - ["$[0]" monoid] - ["$[0]" codec]]] - [control - ["[0]" try] - ["[0]" exception]] - [data - ["[0]" product] - ["[0]" bit ("[1]#[0]" equivalence)]] - [math - ["[0]" random {"+" Random}] - [number - ["i" int]]]]] - ["$[0]" // "_" - ["[1]" modulus]] - [\\library - ["[0]" / - ["/[1]" // "_" - ["[1]" modulus]]]]) + [library + [lux "*" + ["_" test {"+" Test}] + ["[0]" type ("[1]#[0]" equivalence)] + [abstract + [monad {"+" do}] + ["[0]" predicate] + [\\specification + ["$[0]" equivalence] + ["$[0]" order] + ["$[0]" monoid] + ["$[0]" codec]]] + [control + ["[0]" try] + ["[0]" exception]] + [data + ["[0]" product] + ["[0]" bit ("[1]#[0]" equivalence)]] + [math + ["[0]" random {"+" Random}] + [number + ["i" int]]]]] + ["$[0]" // "_" + ["[1]" modulus]] + [\\library + ["[0]" / + ["/[1]" // "_" + ["[1]" modulus]]]]) (def: .public (random modulus) (All (_ %) (-> (//.Modulus %) (Random (/.Mod %)))) @@ -72,10 +72,10 @@ {try.#Success _} false)) (_.cover [/.modulus] - (and (type#= (:of (/.modulus subject)) - (:of (/.modulus subject))) - (not (type#= (:of (/.modulus subject)) - (:of (/.modulus param)))))) + (and (type#= (type_of (/.modulus subject)) + (type_of (/.modulus subject))) + (not (type#= (type_of (/.modulus subject)) + (type_of (/.modulus param)))))) (_.cover [/.modular /.value] (/.= subject (/.modular (/.modulus subject) (/.value subject)))) diff --git a/stdlib/source/test/lux/math/number/frac.lux b/stdlib/source/test/lux/math/number/frac.lux index 77453c6f2..9f1064796 100644 --- a/stdlib/source/test/lux/math/number/frac.lux +++ b/stdlib/source/test/lux/math/number/frac.lux @@ -332,10 +332,10 @@ (/.mod left right)))))) )) (with_expansions [<jvm> ($_ _.and - (let [test (: (-> Frac Bit) - (function (_ value) - (n.= (.nat (ffi.of_long (java/lang/Double::doubleToRawLongBits (ffi.as_double value)))) - (/.bits value))))] + (let [test (is (-> Frac Bit) + (function (_ value) + (n.= (.nat (ffi.of_long (java/lang/Double::doubleToRawLongBits (ffi.as_double value)))) + (/.bits value))))] (do random.monad [sample random.frac] (_.cover [/.bits] @@ -356,12 +356,12 @@ )] (for @.old <jvm> @.jvm <jvm> - (let [test (: (-> Frac Bit) - (function (_ expected) - (let [actual (|> expected /.bits /.of_bits)] - (or (/.= expected actual) - (and (/.not_a_number? expected) - (/.not_a_number? actual))))))] + (let [test (is (-> Frac Bit) + (function (_ expected) + (let [actual (|> expected /.bits /.of_bits)] + (or (/.= expected actual) + (and (/.not_a_number? expected) + (/.not_a_number? actual))))))] (do random.monad [sample random.frac] (_.cover [/.bits /.of_bits] diff --git a/stdlib/source/test/lux/math/number/i64.lux b/stdlib/source/test/lux/math/number/i64.lux index 118c94870..561ab0f04 100644 --- a/stdlib/source/test/lux/math/number/i64.lux +++ b/stdlib/source/test/lux/math/number/i64.lux @@ -1,22 +1,22 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [data - ["[0]" bit ("[1]#[0]" equivalence)]] - [abstract - [monad {"+" do}] - [\\specification - ["$[0]" equivalence] - ["$[0]" hash] - ["$[0]" monoid]]] - [math - ["[0]" random {"+" Random}]]]] - [\\library - ["[0]" / ("#[0]" equivalence) - [// {"+" hex} - ["n" nat] - ["i" int]]]]) + [library + [lux "*" + ["_" test {"+" Test}] + [data + ["[0]" bit ("[1]#[0]" equivalence)]] + [abstract + [monad {"+" do}] + [\\specification + ["$[0]" equivalence] + ["$[0]" hash] + ["$[0]" monoid]]] + [math + ["[0]" random {"+" Random}]]]] + [\\library + ["[0]" / ("#[0]" equivalence) + [// {"+" hex} + ["n" nat] + ["i" int]]]]) (def: bit Test @@ -135,10 +135,10 @@ .int ++)] expected (# ! each (i.% limit) random.int) - .let [random (: (All (_ size) - (-> (-> I64 (I64 size)) (Random (I64 size)))) - (function (_ narrow) - (# random.functor each narrow random.i64)))]] + .let [random (is (All (_ size) + (-> (-> I64 (I64 size)) (Random (I64 size)))) + (function (_ narrow) + (# random.functor each narrow random.i64)))]] ($_ _.and ($equivalence.spec (# sub &equivalence) (random (# sub narrow))) (_.cover [/.sub] diff --git a/stdlib/source/test/lux/meta.lux b/stdlib/source/test/lux/meta.lux index 8a4f63425..33e22c581 100644 --- a/stdlib/source/test/lux/meta.lux +++ b/stdlib/source/test/lux/meta.lux @@ -73,7 +73,7 @@ .#seed expected_seed .#scope_type_vars (list) .#extensions [] - .#eval (:as (-> Type Code (Meta Any)) []) + .#eval (as (-> Type Code (Meta Any)) []) .#host []]]] ($_ _.and (_.cover [/.result] @@ -132,19 +132,19 @@ .#seed expected_seed .#scope_type_vars (list) .#extensions [] - .#eval (:as (-> Type Code (Meta Any)) []) + .#eval (as (-> Type Code (Meta Any)) []) .#host []]]] ($_ _.and (_.cover [/.failure] (|> (/.failure expected_error) - (: (Meta Any)) + (is (Meta Any)) (/.result expected_lux) (!expect (^.multi {try.#Failure actual_error} (text#= (location.with location.dummy expected_error) actual_error))))) (_.cover [/.assertion] (and (|> (/.assertion expected_error true) - (: (Meta Any)) + (is (Meta Any)) (/.result expected_lux) (!expect {try.#Success []})) (|> (/.assertion expected_error false) @@ -153,21 +153,21 @@ (text#= expected_error actual_error)))))) (_.cover [/.either] (and (|> (/.either (# /.monad in expected) - (: (Meta Nat) - (/.failure expected_error))) + (is (Meta Nat) + (/.failure expected_error))) (/.result expected_lux) (!expect (^.multi {try.#Success actual} (n.= expected actual)))) - (|> (/.either (: (Meta Nat) - (/.failure expected_error)) + (|> (/.either (is (Meta Nat) + (/.failure expected_error)) (# /.monad in expected)) (/.result expected_lux) (!expect (^.multi {try.#Success actual} (n.= expected actual)))) - (|> (/.either (: (Meta Nat) - (/.failure expected_error)) - (: (Meta Nat) - (/.failure expected_error))) + (|> (/.either (is (Meta Nat) + (/.failure expected_error)) + (is (Meta Nat) + (/.failure expected_error))) (/.result expected_lux) (!expect (^.multi {try.#Failure actual_error} (text#= (location.with location.dummy expected_error) @@ -238,7 +238,7 @@ .#seed expected_seed .#scope_type_vars (list) .#extensions [] - .#eval (:as (-> Type Code (Meta Any)) []) + .#eval (as (-> Type Code (Meta Any)) []) .#host []]]] (<| (_.for [.Module]) ($_ _.and @@ -338,7 +338,7 @@ .#seed expected_seed .#scope_type_vars (list) .#extensions [] - .#eval (:as (-> Type Code (Meta Any)) []) + .#eval (as (-> Type Code (Meta Any)) []) .#host []]]] ($_ _.and (_.cover [/.target] @@ -385,53 +385,53 @@ expected_value (random.either (in .def:) (in .macro:)) .let [expected_lux - (: (-> Bit (Maybe Type) - [(List [Text .Global]) - (List [Text .Global]) - Lux]) - (function (_ exported? def_type) - (let [current_globals (: (List [Text .Global]) - (list [expected_short - {.#Alias [expected_macro_module expected_short]}])) - macro_globals (: (List [Text .Global]) - (case def_type - {.#Some def_type} - (list [expected_short - {.#Definition [exported? def_type expected_value]}]) - - {.#None} - (list)))] - [current_globals - macro_globals - [.#info [.#target "" - .#version "" - .#mode {.#Build} - .#configuration (list)] - .#source [location.dummy 0 ""] - .#location location.dummy - .#current_module {.#Some expected_current_module} - .#modules (list [expected_current_module - [.#module_hash 0 - .#module_aliases (list) - .#definitions current_globals - .#imports (list) - .#module_state {.#Active}]] - [expected_macro_module - [.#module_hash 0 - .#module_aliases (list) - .#definitions macro_globals - .#imports (list) - .#module_state {.#Active}]]) - .#scopes (list) - .#type_context [.#ex_counter 0 - .#var_counter 0 - .#var_bindings (list)] - .#expected {.#None} - .#seed 0 - .#scope_type_vars (list) - .#extensions [] - .#eval (:as (-> Type Code (Meta Any)) []) - .#host []]])))]] + (is (-> Bit (Maybe Type) + [(List [Text .Global]) + (List [Text .Global]) + Lux]) + (function (_ exported? def_type) + (let [current_globals (is (List [Text .Global]) + (list [expected_short + {.#Alias [expected_macro_module expected_short]}])) + macro_globals (is (List [Text .Global]) + (case def_type + {.#Some def_type} + (list [expected_short + {.#Definition [exported? def_type expected_value]}]) + + {.#None} + (list)))] + [current_globals + macro_globals + [.#info [.#target "" + .#version "" + .#mode {.#Build} + .#configuration (list)] + .#source [location.dummy 0 ""] + .#location location.dummy + .#current_module {.#Some expected_current_module} + .#modules (list [expected_current_module + [.#module_hash 0 + .#module_aliases (list) + .#definitions current_globals + .#imports (list) + .#module_state {.#Active}]] + [expected_macro_module + [.#module_hash 0 + .#module_aliases (list) + .#definitions macro_globals + .#imports (list) + .#module_state {.#Active}]]) + .#scopes (list) + .#type_context [.#ex_counter 0 + .#var_counter 0 + .#var_bindings (list)] + .#expected {.#None} + .#seed 0 + .#scope_type_vars (list) + .#extensions [] + .#eval (as (-> Type Code (Meta Any)) []) + .#host []]])))]] ($_ _.and (_.cover [.Global .Alias /.globals] (let [[current_globals macro_globals expected_lux] @@ -501,53 +501,53 @@ expected_value (random.either (in .def:) (in .macro:)) .let [expected_lux - (: (-> Bit (Maybe Type) - [(List [Text .Global]) - (List [Text .Global]) - Lux]) - (function (_ exported? def_type) - (let [current_globals (: (List [Text .Global]) - (list [expected_short - {.#Alias [expected_macro_module expected_short]}])) - macro_globals (: (List [Text .Global]) - (case def_type - {.#Some def_type} - (list [expected_short - {.#Definition [exported? def_type expected_value]}]) - - {.#None} - (list)))] - [current_globals - macro_globals - [.#info [.#target "" - .#version "" - .#mode {.#Build} - .#configuration (list)] - .#source [location.dummy 0 ""] - .#location location.dummy - .#current_module {.#Some expected_current_module} - .#modules (list [expected_current_module - [.#module_hash 0 - .#module_aliases (list) - .#definitions current_globals - .#imports (list) - .#module_state {.#Active}]] - [expected_macro_module - [.#module_hash 0 - .#module_aliases (list) - .#definitions macro_globals - .#imports (list) - .#module_state {.#Active}]]) - .#scopes (list) - .#type_context [.#ex_counter 0 - .#var_counter 0 - .#var_bindings (list)] - .#expected {.#None} - .#seed 0 - .#scope_type_vars (list) - .#extensions [] - .#eval (:as (-> Type Code (Meta Any)) []) - .#host []]])))]] + (is (-> Bit (Maybe Type) + [(List [Text .Global]) + (List [Text .Global]) + Lux]) + (function (_ exported? def_type) + (let [current_globals (is (List [Text .Global]) + (list [expected_short + {.#Alias [expected_macro_module expected_short]}])) + macro_globals (is (List [Text .Global]) + (case def_type + {.#Some def_type} + (list [expected_short + {.#Definition [exported? def_type expected_value]}]) + + {.#None} + (list)))] + [current_globals + macro_globals + [.#info [.#target "" + .#version "" + .#mode {.#Build} + .#configuration (list)] + .#source [location.dummy 0 ""] + .#location location.dummy + .#current_module {.#Some expected_current_module} + .#modules (list [expected_current_module + [.#module_hash 0 + .#module_aliases (list) + .#definitions current_globals + .#imports (list) + .#module_state {.#Active}]] + [expected_macro_module + [.#module_hash 0 + .#module_aliases (list) + .#definitions macro_globals + .#imports (list) + .#module_state {.#Active}]]) + .#scopes (list) + .#type_context [.#ex_counter 0 + .#var_counter 0 + .#var_bindings (list)] + .#expected {.#None} + .#seed 0 + .#scope_type_vars (list) + .#extensions [] + .#eval (as (-> Type Code (Meta Any)) []) + .#host []]])))]] ($_ _.and (_.cover [/.export] (and (let [[current_globals macro_globals expected_lux] @@ -615,7 +615,7 @@ (!expect (^.multi {try.#Success {.#Definition [actual_exported? actual_type actual_value]}} (and (bit#= expected_exported? actual_exported?) (same? expected_type actual_type) - (same? (:as Any expected_value) actual_value))))) + (same? (as Any expected_value) actual_value))))) alias! (|> (/.definition [expected_current_module expected_short]) @@ -650,13 +650,13 @@ (|> (/.type_definition [expected_macro_module expected_short]) (/.result expected_lux) (!expect (^.multi {try.#Success actual_value} - (same? (:as .Type expected_value) actual_value)))) + (same? (as .Type expected_value) actual_value)))) alias! (|> (/.type_definition [expected_current_module expected_short]) (/.result expected_lux) (!expect (^.multi {try.#Success actual_value} - (same? (:as .Type expected_value) actual_value))))] + (same? (as .Type expected_value) actual_value))))] (and definition! alias!))) ))) @@ -674,14 +674,14 @@ .let [random_tag (# ! each (|>> [label_module]) (random.ascii/upper 1)) - random_labels (: (Random [Text (List Text)]) - (do ! - [head (random.ascii/lower 5)] - (|> (random.ascii/lower 5) - (random.only (|>> (text#= head) not)) - (random.set text.hash 3) - (# ! each set.list) - (random.and (in head)))))] + random_labels (is (Random [Text (List Text)]) + (do ! + [head (random.ascii/lower 5)] + (|> (random.ascii/lower 5) + (random.only (|>> (text#= head) not)) + (random.set text.hash 3) + (# ! each set.list) + (random.and (in head)))))] tags_0 random_labels tags_1 (let [set/0 (set.of_list text.hash {.#Item tags_0})] (random.only (|>> {.#Item} @@ -692,46 +692,46 @@ type_1 {.#Primitive name_1 (list)} expected_lux - (: Lux - [.#info [.#target "" - .#version "" - .#mode {.#Build} - .#configuration (list)] - .#source [location.dummy 0 ""] - .#location location.dummy - .#current_module {.#Some current_module} - .#modules (list [current_module - [.#module_hash 0 - .#module_aliases (list) - .#definitions (list) - .#imports (list label_module) - .#module_state {.#Active}]] - [label_module - [.#module_hash 0 - .#module_aliases (list) - .#definitions (list& [name_0 {.#Type [true type_0 {.#Left tags_0}]}] - [name_1 {.#Type [true type_1 {.#Right tags_1}]}] - ($_ list#composite - (|> {.#Item tags_0} - list.enumeration - (list#each (function (_ [index short]) - [short {.#Tag [true type_0 {.#Item tags_0} index]}]))) - (|> {.#Item tags_1} - list.enumeration - (list#each (function (_ [index short]) - [short {.#Slot [true type_1 {.#Item tags_1} index]}]))))) - .#imports (list) - .#module_state {.#Active}]]) - .#scopes (list) - .#type_context [.#ex_counter 0 - .#var_counter 0 - .#var_bindings (list)] - .#expected {.#None} - .#seed 0 - .#scope_type_vars (list) - .#extensions [] - .#eval (:as (-> Type Code (Meta Any)) []) - .#host []])]] + (is Lux + [.#info [.#target "" + .#version "" + .#mode {.#Build} + .#configuration (list)] + .#source [location.dummy 0 ""] + .#location location.dummy + .#current_module {.#Some current_module} + .#modules (list [current_module + [.#module_hash 0 + .#module_aliases (list) + .#definitions (list) + .#imports (list label_module) + .#module_state {.#Active}]] + [label_module + [.#module_hash 0 + .#module_aliases (list) + .#definitions (list& [name_0 {.#Type [true type_0 {.#Left tags_0}]}] + [name_1 {.#Type [true type_1 {.#Right tags_1}]}] + ($_ list#composite + (|> {.#Item tags_0} + list.enumeration + (list#each (function (_ [index short]) + [short {.#Tag [true type_0 {.#Item tags_0} index]}]))) + (|> {.#Item tags_1} + list.enumeration + (list#each (function (_ [index short]) + [short {.#Slot [true type_1 {.#Item tags_1} index]}]))))) + .#imports (list) + .#module_state {.#Active}]]) + .#scopes (list) + .#type_context [.#ex_counter 0 + .#var_counter 0 + .#var_bindings (list)] + .#expected {.#None} + .#seed 0 + .#scope_type_vars (list) + .#extensions [] + .#eval (as (-> Type Code (Meta Any)) []) + .#host []])]] ($_ _.and (_.cover [/.tag_lists] (let [equivalence (list.equivalence @@ -820,9 +820,9 @@ type_3 {.#Primitive name_3 (list)} type_4 {.#Primitive name_4 (list)} - globals (: (List [Text .Global]) - (list [name_4 - {.#Definition [false type_4 []]}])) + globals (is (List [Text .Global]) + (list [name_4 + {.#Definition [false type_4 []]}])) scopes (list [.#name (list) .#inner 0 @@ -844,38 +844,38 @@ .#captured [.#counter 0 .#mappings (list)]])] .let [expected_lux - (: Lux - [.#info [.#target "" - .#version "" - .#mode {.#Build} - .#configuration (list)] - .#source [location.dummy 0 ""] - .#location location.dummy - .#current_module {.#Some current_module} - .#modules (list [current_module - [.#module_hash 0 - .#module_aliases (list) - .#definitions globals - .#imports (list) - .#module_state {.#Active}]]) - .#scopes scopes - .#type_context [.#ex_counter 0 - .#var_counter 0 - .#var_bindings (list)] - .#expected {.#None} - .#seed 0 - .#scope_type_vars (list) - .#extensions [] - .#eval (:as (-> Type Code (Meta Any)) []) - .#host []])]] + (is Lux + [.#info [.#target "" + .#version "" + .#mode {.#Build} + .#configuration (list)] + .#source [location.dummy 0 ""] + .#location location.dummy + .#current_module {.#Some current_module} + .#modules (list [current_module + [.#module_hash 0 + .#module_aliases (list) + .#definitions globals + .#imports (list) + .#module_state {.#Active}]]) + .#scopes scopes + .#type_context [.#ex_counter 0 + .#var_counter 0 + .#var_bindings (list)] + .#expected {.#None} + .#seed 0 + .#scope_type_vars (list) + .#extensions [] + .#eval (as (-> Type Code (Meta Any)) []) + .#host []])]] ($_ _.and (_.cover [.Scope /.locals] - (let [equivalence (: (Equivalence (List (List [Text Type]))) - (list.equivalence + (let [equivalence (is (Equivalence (List (List [Text Type]))) (list.equivalence - (product.equivalence - text.equivalence - type.equivalence))))] + (list.equivalence + (product.equivalence + text.equivalence + type.equivalence))))] (|> /.locals (/.result expected_lux) (try#each (# equivalence = (list (list [name_3 type_3]) @@ -974,7 +974,7 @@ .#seed expected_seed .#scope_type_vars (list) .#extensions [] - .#eval (:as (-> Type Code (Meta Any)) []) + .#eval (as (-> Type Code (Meta Any)) []) .#host []]]] ($_ _.and (_.for [/.functor] @@ -990,7 +990,7 @@ (_.cover [/.lifted] (and (|> expected_error {try.#Failure} - (: (Try Nat)) + (is (Try Nat)) /.lifted (/.result expected_lux) (!expect (^.multi {try.#Failure actual} @@ -998,7 +998,7 @@ actual)))) (|> expected_value {try.#Success} - (: (Try Nat)) + (is (Try Nat)) /.lifted (/.result expected_lux) (!expect (^.multi {try.#Success actual} diff --git a/stdlib/source/test/lux/program.lux b/stdlib/source/test/lux/program.lux index f2aafead6..d780d38c9 100644 --- a/stdlib/source/test/lux/program.lux +++ b/stdlib/source/test/lux/program.lux @@ -35,10 +35,10 @@ (let [(open "list#[0]") (list.equivalence text.equivalence)] (and (with_expansions [<program> (/.program: all_arguments (io.io all_arguments))] - (let [outcome ((: (-> (List Text) (io.IO Any)) - (..actual_program <program>)) + (let [outcome ((is (-> (List Text) (io.IO Any)) + (..actual_program <program>)) inputs)] - (same? (: Any inputs) + (same? (is Any inputs) (io.run! outcome)))) (with_expansions [<program> (/.program: [arg/0 <cli>.any arg/1 <cli>.any @@ -46,25 +46,25 @@ arg/3 <cli>.any arg/4 <cli>.any] (io.io (list arg/4 arg/3 arg/2 arg/1 arg/0)))] - (let [outcome ((: (-> (List Text) (io.IO Any)) - (..actual_program <program>)) + (let [outcome ((is (-> (List Text) (io.IO Any)) + (..actual_program <program>)) inputs)] (list#= (list.reversed inputs) - (:as (List Text) (io.run! outcome))))) + (as (List Text) (io.run! outcome))))) (with_expansions [<program> (/.program: [all_arguments (<>.many <cli>.any)] (io.io all_arguments))] - (let [outcome ((: (-> (List Text) (io.IO Any)) - (..actual_program <program>)) + (let [outcome ((is (-> (List Text) (io.IO Any)) + (..actual_program <program>)) inputs)] (list#= inputs - (:as (List Text) (io.run! outcome))))) + (as (List Text) (io.run! outcome))))) (with_expansions [<program> (/.program: [arg/0 <cli>.any arg/1 <cli>.any arg/2 <cli>.any arg/3 <cli>.any] (io.io []))] - (case (try ((: (-> (List Text) (io.IO Any)) - (..actual_program <program>)) + (case (try ((is (-> (List Text) (io.IO Any)) + (..actual_program <program>)) inputs)) {try.#Success _} false diff --git a/stdlib/source/test/lux/target/js.lux b/stdlib/source/test/lux/target/js.lux index 8f1da42bb..20a49a462 100644 --- a/stdlib/source/test/lux/target/js.lux +++ b/stdlib/source/test/lux/target/js.lux @@ -83,16 +83,16 @@ {.#Some _} false))) (try.else false))) (_.cover [/.boolean] - (expression (|>> (:as Bit) (bit#= boolean)) + (expression (|>> (as Bit) (bit#= boolean)) (/.boolean boolean))) (_.cover [/.number] - (expression (|>> (:as Frac) (f.= number)) + (expression (|>> (as Frac) (f.= number)) (/.number number))) (_.cover [/.int] - (expression (|>> (:as Frac) f.int (i.= int)) + (expression (|>> (as Frac) f.int (i.= int)) (/.int int))) (_.cover [/.string] - (expression (|>> (:as Text) (text#= string)) + (expression (|>> (as Text) (text#= string)) (/.string string))) ))) @@ -105,14 +105,14 @@ (~~ (template [<js> <lux>] [(_.cover [<js>] (let [expected (<lux> left right)] - (expression (|>> (:as Bit) (bit#= expected)) + (expression (|>> (as Bit) (bit#= expected)) (<js> (/.boolean left) (/.boolean right)))))] [/.or .or] [/.and .and] )) (_.cover [/.not] - (expression (|>> (:as Bit) (bit#= (not left))) + (expression (|>> (as Bit) (bit#= (not left))) (/.not (/.boolean left)))) )))) @@ -126,7 +126,7 @@ (~~ (template [<js> <lux>] [(_.cover [<js>] (let [expected (<lux> parameter subject)] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (<js> (/.number parameter) (/.number subject)))))] [/.+ f.+] @@ -138,7 +138,7 @@ (~~ (template [<js> <lux>] [(_.cover [<js>] (let [expected (<lux> parameter subject)] - (expression (|>> (:as Bit) (bit#= expected)) + (expression (|>> (as Bit) (bit#= expected)) (<js> (/.number parameter) (/.number subject)))))] [/.< f.<] @@ -162,7 +162,7 @@ (~~ (template [<js> <lux>] [(_.cover [<js>] (let [expected (<lux> left right)] - (expression (|>> (:as Frac) f.int (i.= expected)) + (expression (|>> (as Frac) f.int (i.= expected)) (<js> (/.int left) (/.int right)))))] [/.bit_or i64.or] @@ -170,35 +170,35 @@ [/.bit_and i64.and] )) (_.cover [/.opposite] - (expression (|>> (:as Frac) f.int (i.= (i.* -1 i32))) + (expression (|>> (as Frac) f.int (i.= (i.* -1 i32))) (/.opposite (/.i32 i32)))) (_.cover [/.i32] - (expression (|>> (:as Frac) f.int (i.= i32)) + (expression (|>> (as Frac) f.int (i.= i32)) (/.i32 i32))) (_.cover [/.to_i32] - (expression (|>> (:as Frac) f.int (i.= i32)) + (expression (|>> (as Frac) f.int (i.= i32)) (/.to_i32 (/.int i32)))) (_.cover [/.left_shift] (let [expected (i64.left_shifted shift i16)] - (expression (|>> (:as Frac) f.int (i.= expected)) + (expression (|>> (as Frac) f.int (i.= expected)) (/.left_shift (/.int (.int shift)) (/.i32 i16))))) (_.cover [/.logic_right_shift] (let [expected (i64.right_shifted shift (as_int/32 i16))] - (expression (|>> (:as Frac) f.int (i.= expected)) + (expression (|>> (as Frac) f.int (i.= expected)) (/.logic_right_shift (/.int (.int shift)) (/.i32 i16))))) (_.cover [/.arithmetic_right_shift] (let [expected (i.right_shifted shift i16)] - (expression (|>> (:as Frac) f.int (i.= expected)) + (expression (|>> (as Frac) f.int (i.= expected)) (/.arithmetic_right_shift (/.int (.int shift)) (/.i32 i16))))) (_.cover [/.bit_not] (let [expected (if (i.< +0 i32) (as_int/32 (i64.not i32)) (i64.not (as_int/32 i32)))] - (expression (|>> (:as Frac) f.int (i.= expected)) + (expression (|>> (as Frac) f.int (i.= expected)) (/.bit_not (/.i32 i32))))) )))) @@ -213,10 +213,10 @@ (maybe.else f.not_a_number))]] ($_ _.and (_.cover [/.array /.at] - (and (expression (|>> (:as Frac) (f.= expected)) + (and (expression (|>> (as Frac) (f.= expected)) (/.at (/.int (.int index)) (/.array (list#each /.number items)))) - (expression (|>> (:as Bit)) + (expression (|>> (as Bit)) (|> (/.array (list#each /.number items)) (/.at (/.int (.int size))) (/.= /.undefined))))) @@ -235,17 +235,17 @@ items (random.list size random.safe_frac)] ($_ _.and (_.cover [/.object /.the] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (/.the field (/.object (list [field (/.number expected)]))))) (let [expected (|> items (list.item index) (maybe.else f.not_a_number))] (_.cover [/.do] - (expression (|>> (:as Frac) f.int (i.= (.int index))) + (expression (|>> (as Frac) f.int (i.= (.int index))) (|> (/.array (list#each /.number items)) (/.do "lastIndexOf" (list (/.number expected))))))) (_.cover [/.undefined] - (expression (|>> (:as Bit)) + (expression (|>> (as Bit)) (|> (/.object (list [field (/.number expected)])) (/.the dummy) (/.= /.undefined)))) @@ -271,34 +271,34 @@ ..test|object (_.cover [/.?] (let [expected (if test then else)] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (/.? (/.boolean test) (/.number then) (/.number else))))) (_.cover [/.not_a_number?] - (and (expression (|>> (:as Bit)) + (and (expression (|>> (as Bit)) (/.not_a_number? (/.number f.not_a_number))) - (expression (|>> (:as Bit) not) + (expression (|>> (as Bit) not) (/.not_a_number? (/.number then))))) (_.cover [/.type_of] - (and (expression (|>> (:as Text) (text#= "boolean")) + (and (expression (|>> (as Text) (text#= "boolean")) (/.type_of (/.boolean boolean))) - (expression (|>> (:as Text) (text#= "number")) + (expression (|>> (as Text) (text#= "number")) (/.type_of (/.number number))) - (expression (|>> (:as Text) (text#= "string")) + (expression (|>> (as Text) (text#= "string")) (/.type_of (/.string string))) - (expression (|>> (:as Text) (text#= "object")) + (expression (|>> (as Text) (text#= "object")) (/.type_of /.null)) - (expression (|>> (:as Text) (text#= "object")) + (expression (|>> (as Text) (text#= "object")) (/.type_of (/.object (list [string (/.number number)])))) - (expression (|>> (:as Text) (text#= "object")) + (expression (|>> (as Text) (text#= "object")) (/.type_of (/.array (list (/.boolean boolean) (/.number number) (/.string string))))) - (expression (|>> (:as Text) (text#= "undefined")) + (expression (|>> (as Text) (text#= "undefined")) (/.type_of /.undefined)))) (_.cover [/.comment] - (expression (|>> (:as Frac) (f.= then)) + (expression (|>> (as Frac) (f.= then)) (/.comment comment (/.number then)))) ))) @@ -314,7 +314,7 @@ (_.for [/.Computation] ..test|computation) (_.cover [/.,] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (/., (/.number dummy) (/.number expected)))) )))) @@ -331,18 +331,18 @@ $local (/.var local)]] ($_ _.and (_.cover [/.var] - (expression (|>> (:as Frac) (f.= number/0)) + (expression (|>> (as Frac) (f.= number/0)) (/.apply/* (/.closure (list $foreign) (/.return $foreign)) (list (/.number number/0))))) (_.cover [/.define] - (expression (|>> (:as Frac) (f.= number/1)) + (expression (|>> (as Frac) (f.= number/1)) (/.apply/* (/.closure (list $foreign) ($_ /.then (/.define $local (/.number number/1)) (/.return $local))) (list (/.number number/0))))) (_.cover [/.declare] - (expression (|>> (:as Frac) (f.= number/1)) + (expression (|>> (as Frac) (f.= number/1)) (/.apply/* (/.closure (list $foreign) ($_ /.then (/.declare $local) @@ -360,13 +360,13 @@ field (random.ascii/upper 10)] ($_ _.and (_.cover [/.set] - (and (expression (|>> (:as Frac) (f.= (f.+ number/0 number/0))) + (and (expression (|>> (as Frac) (f.= (f.+ number/0 number/0))) (/.apply/* (/.closure (list $foreign) ($_ /.then (/.set $foreign (/.+ $foreign $foreign)) (/.return $foreign))) (list (/.number number/0)))) - (expression (|>> (:as Frac) (f.= (f.+ number/0 number/0))) + (expression (|>> (as Frac) (f.= (f.+ number/0 number/0))) (let [@ (/.at (/.int +0) $foreign)] (/.apply/* (/.closure (list $foreign) ($_ /.then @@ -374,7 +374,7 @@ (/.set @ (/.+ @ @)) (/.return @))) (list (/.number number/0))))) - (expression (|>> (:as Frac) (f.= (f.+ number/0 number/0))) + (expression (|>> (as Frac) (f.= (f.+ number/0 number/0))) (let [@ (/.the field $foreign)] (/.apply/* (/.closure (list $foreign) ($_ /.then @@ -383,17 +383,17 @@ (/.return @))) (list (/.number number/0))))))) (_.cover [/.delete] - (and (and (expression (|>> (:as Bit)) + (and (and (expression (|>> (as Bit)) (/.apply/* (/.closure (list) ($_ /.then (/.set $foreign (/.number number/0)) (/.return (/.delete $foreign)))) (list))) - (expression (|>> (:as Bit) not) + (expression (|>> (as Bit) not) (/.apply/* (/.closure (list $foreign) (/.return (/.delete $foreign))) (list (/.number number/0))))) - (expression (|>> (:as Bit)) + (expression (|>> (as Bit)) (let [@ (/.at (/.int +0) $foreign)] (/.apply/* (/.closure (list $foreign) ($_ /.then @@ -401,7 +401,7 @@ (/.return (|> (/.= (/.boolean true) (/.delete @)) (/.and (/.= /.undefined @)))))) (list (/.number number/0))))) - (expression (|>> (:as Bit)) + (expression (|>> (as Bit)) (let [@ (/.the field $foreign)] (/.apply/* (/.closure (list $foreign) ($_ /.then @@ -412,13 +412,13 @@ )) (_.cover [/.Access] (`` (and (~~ (template [<js> <lux>] - [(expression (|>> (:as Frac) f.int (i.= (<lux> int/0))) + [(expression (|>> (as Frac) f.int (i.= (<lux> int/0))) (/.apply/* (/.closure (list $foreign) ($_ /.then (/.statement (<js> $foreign)) (/.return $foreign))) (list (/.int int/0)))) - (expression (|>> (:as Frac) f.int (i.= (<lux> int/0))) + (expression (|>> (as Frac) f.int (i.= (<lux> int/0))) (let [@ (/.at (/.int +0) $foreign)] (/.apply/* (/.closure (list $foreign) ($_ /.then @@ -426,7 +426,7 @@ (/.statement (<js> @)) (/.return @))) (list (/.int int/0))))) - (expression (|>> (:as Frac) f.int (i.= (<lux> int/0))) + (expression (|>> (as Frac) f.int (i.= (<lux> int/0))) (let [@ (/.the field $foreign)] (/.apply/* (/.closure (list $foreign) ($_ /.then @@ -461,7 +461,7 @@ ($_ _.and (_.cover [/.break] (let [expected (i.* (.int expected_inner_iterations) input)] - (expression (|>> (:as Frac) f.int (i.= expected)) + (expression (|>> (as Frac) f.int (i.= expected)) (/.apply/* (/.closure (list $input) ($_ /.then (/.define $inner_index (/.int +0)) @@ -477,7 +477,7 @@ (list (/.int input)))))) (_.cover [/.continue] (let [expected (i.* (.int (n.- expected_inner_iterations full_inner_iterations)) input)] - (expression (|>> (:as Frac) f.int (i.= expected)) + (expression (|>> (as Frac) f.int (i.= expected)) (/.apply/* (/.closure (list $input) ($_ /.then (/.define $inner_index (/.int +0)) @@ -497,7 +497,7 @@ (let [expected (i.* (.int (n.* expected_outer_iterations expected_inner_iterations)) input)] - (expression (|>> (:as Frac) f.int (i.= expected)) + (expression (|>> (as Frac) f.int (i.= expected)) (/.apply/* (/.closure (list $input) ($_ /.then (/.define $output (/.int +0)) @@ -523,7 +523,7 @@ (let [expected (i.* (.int (n.* (n.- expected_outer_iterations full_outer_iterations) (n.- expected_inner_iterations full_inner_iterations))) input)] - (expression (|>> (:as Frac) f.int (i.= expected)) + (expression (|>> (as Frac) f.int (i.= expected)) (/.apply/* (/.closure (list $input) ($_ /.then (/.define $output (/.int +0)) @@ -561,7 +561,7 @@ expected|do_while (i.* (.int (n.max 1 iterations)) input)]] ($_ _.and (_.cover [/.while] - (expression (|>> (:as Frac) f.int (i.= expected|while)) + (expression (|>> (as Frac) f.int (i.= expected|while)) (/.apply/* (/.closure (list $input) ($_ /.then (/.define $index (/.int +0)) @@ -574,7 +574,7 @@ (/.return $output))) (list (/.int input))))) (_.cover [/.do_while] - (expression (|>> (:as Frac) f.int (i.= expected|do_while)) + (expression (|>> (as Frac) f.int (i.= expected|do_while)) (/.apply/* (/.closure (list $input) ($_ /.then (/.define $index (/.int +0)) @@ -587,7 +587,7 @@ (/.return $output))) (list (/.int input))))) (_.cover [/.for] - (expression (|>> (:as Frac) f.int (i.= expected|while)) + (expression (|>> (as Frac) f.int (i.= expected|while)) (/.apply/* (/.closure (list $input) ($_ /.then (/.define $output (/.int +0)) @@ -610,13 +610,13 @@ $ex (# ! each /.var (random.ascii/lower 10))] ($_ _.and (_.cover [/.try] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (/.apply/* (/.closure (list) (/.try (/.return (/.number expected)) [$ex (/.return (/.number dummy))])) (list)))) (_.cover [/.throw] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (/.apply/* (/.closure (list) (/.try ($_ /.then (/.throw (/.number expected)) @@ -636,22 +636,22 @@ $arg/2 (# ! each /.var (random.ascii/lower 12))] (`` ($_ _.and (_.cover [/.apply/1] - (expression (|>> (:as Frac) (f.= number/0)) + (expression (|>> (as Frac) (f.= number/0)) (/.apply/1 (/.closure (list $arg/0) (/.return $arg/0)) (/.number number/0)))) (_.cover [/.apply/2] - (expression (|>> (:as Frac) (f.= ($_ f.+ number/0 number/1))) + (expression (|>> (as Frac) (f.= ($_ f.+ number/0 number/1))) (/.apply/2 (/.closure (list $arg/0 $arg/1) (/.return ($_ /.+ $arg/0 $arg/1))) (/.number number/0) (/.number number/1)))) (_.cover [/.apply/3] - (expression (|>> (:as Frac) (f.= ($_ f.+ number/0 number/1 number/2))) + (expression (|>> (as Frac) (f.= ($_ f.+ number/0 number/1 number/2))) (/.apply/3 (/.closure (list $arg/0 $arg/1 $arg/2) (/.return ($_ /.+ $arg/0 $arg/1 $arg/2))) (/.number number/0) (/.number number/1) (/.number number/2)))) (_.cover [/.apply/*] - (expression (|>> (:as Frac) (f.= ($_ f.+ number/0 number/1 number/2))) + (expression (|>> (as Frac) (f.= ($_ f.+ number/0 number/1 number/2))) (/.apply/* (/.closure (list $arg/0 $arg/1 $arg/2) (/.return ($_ /.+ $arg/0 $arg/1 $arg/2))) (list (/.number number/0) (/.number number/1) @@ -669,18 +669,18 @@ $class (# ! each /.var (random.ascii/upper 4))] ($_ _.and (_.cover [/.closure /.return] - (expression (|>> (:as Frac) (f.= number/0)) + (expression (|>> (as Frac) (f.= number/0)) (/.apply/* (/.closure (list) (/.return (/.number number/0))) (list)))) (_.cover [/.function] - (expression (|>> (:as Frac) f.nat (n.= iterations)) + (expression (|>> (as Frac) f.nat (n.= iterations)) (/.apply/1 (/.function $self (list $arg/0) (/.return (/.? (/.< (/.int (.int iterations)) $arg/0) (/.apply/1 $self (/.+ (/.int +1) $arg/0)) $arg/0))) (/.int +0)))) (_.cover [/.function!] - (expression (|>> (:as Frac) f.nat (n.= iterations)) + (expression (|>> (as Frac) f.nat (n.= iterations)) (/.apply/* (/.closure (list) ($_ /.then (/.function! $self (list $arg/0) @@ -691,7 +691,7 @@ (list)))) (_.cover [/.new] (let [$this (/.var "this")] - (expression (|>> (:as Frac) (f.= number/0)) + (expression (|>> (as Frac) (f.= number/0)) (/.apply/1 (/.closure (list $arg/0) ($_ /.then (/.function! $class (list) @@ -720,14 +720,14 @@ int ..int/16] ($_ _.and (_.cover [/.if] - (expression (|>> (:as Frac) (f.= (if ??? number/0 number/1))) + (expression (|>> (as Frac) (f.= (if ??? number/0 number/1))) (/.apply/* (/.closure (list) (/.if (/.boolean ???) (/.return (/.number number/0)) (/.return (/.number number/1)))) (list)))) (_.cover [/.when] - (expression (|>> (:as Frac) (f.= (if ??? number/0 number/1))) + (expression (|>> (as Frac) (f.= (if ??? number/0 number/1))) (/.apply/* (/.closure (list) ($_ /.then (/.when (/.boolean ???) @@ -738,21 +738,21 @@ (let [number/0' (%.frac number/0) number/1' (%.frac number/1) number/2' (%.frac number/2)] - (and (expression (|>> (:as Text) (text#= number/0')) + (and (expression (|>> (as Text) (text#= number/0')) (/.apply/* (/.closure (list) (/.switch (/.number number/0) (list [(list (/.number number/0)) (/.return (/.string number/0'))] [(list (/.number number/1)) (/.return (/.string number/1'))]) {.#None})) (list))) - (expression (|>> (:as Text) (text#= number/1')) + (expression (|>> (as Text) (text#= number/1')) (/.apply/* (/.closure (list) (/.switch (/.number number/1) (list [(list (/.number number/0)) (/.return (/.string number/0'))] [(list (/.number number/1)) (/.return (/.string number/1'))]) {.#Some (/.return (/.string number/2'))})) (list))) - (expression (|>> (:as Text) (text#= number/2')) + (expression (|>> (as Text) (text#= number/2')) (/.apply/* (/.closure (list) (/.switch (/.number number/2) (list [(list (/.number number/0)) (/.return (/.string number/0'))] @@ -775,7 +775,7 @@ int ..int/16] (`` ($_ _.and (_.cover [/.statement] - (expression (|>> (:as Frac) (f.= number/0)) + (expression (|>> (as Frac) (f.= number/0)) (/.apply/1 (/.closure (list $arg/0) ($_ /.then (/.statement (/.+ $arg/0 $arg/0)) @@ -783,7 +783,7 @@ (/.number number/0)))) (~~ (template [<js> <lux>] [(_.cover [<js>] - (expression (|>> (:as Frac) f.int (i.= (<lux> int))) + (expression (|>> (as Frac) f.int (i.= (<lux> int))) (/.apply/1 (/.closure (list $arg/0) (/.return (/., (<js> $arg/0) $arg/0))) @@ -793,7 +793,7 @@ [/.-- .--] )) (_.cover [/.then] - (expression (|>> (:as Frac) (f.= number/0)) + (expression (|>> (as Frac) (f.= number/0)) (/.apply/2 (/.closure (list $arg/0 $arg/1) ($_ /.then (/.return $arg/0) @@ -801,7 +801,7 @@ (/.number number/0) (/.number number/1)))) (_.cover [/.use_strict] - (and (expression (|>> (:as Frac) (f.= number/0)) + (and (expression (|>> (as Frac) (f.= number/0)) (/.apply/* (/.closure (list) ($_ /.then /.use_strict diff --git a/stdlib/source/test/lux/target/jvm.lux b/stdlib/source/test/lux/target/jvm.lux index 5a919761c..a665a398c 100644 --- a/stdlib/source/test/lux/target/jvm.lux +++ b/stdlib/source/test/lux/target/jvm.lux @@ -162,12 +162,12 @@ (/type.class "java.lang.Boolean" (list))) (def: $Boolean::wrap (/.invokestatic ..$Boolean "valueOf" (/type.method [(list) (list /type.boolean) ..$Boolean (list)]))) -(def: $Boolean::random (:as (Random java/lang/Boolean) random.bit)) +(def: $Boolean::random (as (Random java/lang/Boolean) random.bit)) (def: !false (|> 0 .i64 i32.i32 /.int)) (def: !true (|> 1 .i64 i32.i32 /.int)) (def: ($Boolean::literal value) (-> java/lang/Boolean (Bytecode Any)) - (if (:as Bit value) + (if (as Bit value) ..!true ..!false)) (def: $Boolean::primitive @@ -184,10 +184,10 @@ (/.invokestatic ..$Byte "valueOf" (/type.method [(list) (list /type.byte) ..$Byte (list)]))) (def: $Byte::random (Random java/lang/Byte) - (# random.monad each (|>> (:as java/lang/Long) ffi.long_to_byte) random.int)) + (# random.monad each (|>> (as java/lang/Long) ffi.long_to_byte) random.int)) (def: $Byte::literal (-> java/lang/Byte (Bytecode Any)) - (|>> ffi.byte_to_long (:as I64) i32.i32 /.int)) + (|>> ffi.byte_to_long (as I64) i32.i32 /.int)) (def: $Byte::primitive (Primitive java/lang/Byte) [#unboxed /type.byte @@ -202,10 +202,10 @@ (/.invokestatic ..$Short "valueOf" (/type.method [(list) (list /type.short) ..$Short (list)]))) (def: $Short::random (Random java/lang/Short) - (# random.monad each (|>> (:as java/lang/Long) ffi.long_to_short) random.int)) + (# random.monad each (|>> (as java/lang/Long) ffi.long_to_short) random.int)) (def: $Short::literal (-> java/lang/Short (Bytecode Any)) - (|>> ffi.short_to_long (:as I64) i32.i32 /.int)) + (|>> ffi.short_to_long (as I64) i32.i32 /.int)) (def: $Short::primitive (Primitive java/lang/Short) [#unboxed /type.short @@ -220,10 +220,10 @@ (/.invokestatic ..$Integer "valueOf" (/type.method [(list) (list /type.int) ..$Integer (list)]))) (def: $Integer::random (Random java/lang/Integer) - (# random.monad each (|>> (:as java/lang/Long) ffi.long_to_int) random.int)) + (# random.monad each (|>> (as java/lang/Long) ffi.long_to_int) random.int)) (def: $Integer::literal (-> java/lang/Integer (Bytecode Any)) - (|>> ffi.int_to_long (:as I64) i32.i32 /.int)) + (|>> ffi.int_to_long (as I64) i32.i32 /.int)) (def: $Integer::primitive (Primitive java/lang/Integer) [#unboxed /type.int @@ -234,8 +234,8 @@ (def: $Long (/type.class "java.lang.Long" (list))) (def: $Long::wrap (/.invokestatic ..$Long "valueOf" (/type.method [(list) (list /type.long) ..$Long (list)]))) -(def: $Long::random (:as (Random java/lang/Long) random.int)) -(def: $Long::literal (-> java/lang/Long (Bytecode Any)) (|>> (:as Int) /.long)) +(def: $Long::random (as (Random java/lang/Long) random.int)) +(def: $Long::literal (-> java/lang/Long (Bytecode Any)) (|>> (as Int) /.long)) (def: $Long::primitive (Primitive java/lang/Long) [#unboxed /type.long @@ -249,12 +249,12 @@ (def: $Float::random (Random java/lang/Float) (# random.monad each - (|>> (:as java/lang/Double) ffi.double_to_float) + (|>> (as java/lang/Double) ffi.double_to_float) random.frac)) (def: $Float::literal /.float) (def: valid_float (Random java/lang/Float) - (random.only (|>> ffi.float_to_double (:as Frac) f.not_a_number? not) + (random.only (|>> ffi.float_to_double (as Frac) f.not_a_number? not) ..$Float::random)) (def: $Float::primitive (Primitive java/lang/Float) @@ -266,13 +266,13 @@ (def: $Double (/type.class "java.lang.Double" (list))) (def: $Double::wrap (/.invokestatic ..$Double "valueOf" (/type.method [(list) (list /type.double) ..$Double (list)]))) -(def: $Double::random (:as (Random java/lang/Double) random.frac)) +(def: $Double::random (as (Random java/lang/Double) random.frac)) (def: $Double::literal (-> java/lang/Double (Bytecode Any)) /.double) (def: valid_double (Random java/lang/Double) - (random.only (|>> (:as Frac) f.not_a_number? not) + (random.only (|>> (as Frac) f.not_a_number? not) ..$Double::random)) (def: $Double::primitive (Primitive java/lang/Double) @@ -288,10 +288,10 @@ (/.invokestatic ..$Character "valueOf" (/type.method [(list) (list /type.char) ..$Character (list)]))) (def: $Character::random (Random java/lang/Character) - (# random.monad each (|>> (:as java/lang/Long) ffi.long_to_int ffi.int_to_char) random.int)) + (# random.monad each (|>> (as java/lang/Long) ffi.long_to_int ffi.int_to_char) random.int)) (def: $Character::literal (-> java/lang/Character (Bytecode Any)) - (|>> ffi.char_to_long (:as I64) i32.i32 /.int)) + (|>> ffi.char_to_long (as I64) i32.i32 /.int)) (def: $Character::primitive (Primitive java/lang/Character) [#unboxed /type.char @@ -304,12 +304,12 @@ (/type.class "java.lang.String" (list))) (def: $String::random - (:as (Random java/lang/String) - (random.ascii/alpha 10))) + (as (Random java/lang/String) + (random.ascii/alpha 10))) (def: $String::literal (-> java/lang/String (Bytecode Any)) - (|>> (:as Text) /.string)) + (|>> (as Text) /.string)) (def: $String::primitive (Primitive java/lang/String) @@ -326,10 +326,10 @@ [expected (# ! each (i64.and (i64.mask <bits>)) random.nat)] (<| (_.lifted <message>) (..bytecode (for @.old - (|>> (:as <type>) <to_long> ("jvm leq" expected)) + (|>> (as <type>) <to_long> ("jvm leq" expected)) @.jvm - (|>> (:as <type>) <to_long> "jvm object cast" ("jvm long =" ("jvm object cast" (:as java/lang/Long expected)))))) + (|>> (as <type>) <to_long> "jvm object cast" ("jvm long =" ("jvm object cast" (as java/lang/Long expected)))))) (do /.monad [_ (<push> (|> expected .int <signed> try.trusted))] <wrap>))))] @@ -340,15 +340,15 @@ (template [<name> <type>] [(template: (<name> <old_extension> <new_extension>) - [(: (-> <type> <type> <type>) - (function (_ parameter subject) - (for @.old - (<old_extension> subject parameter) - - @.jvm - ("jvm object cast" - (<new_extension> ("jvm object cast" parameter) - ("jvm object cast" subject))))))])] + [(is (-> <type> <type> <type>) + (function (_ parameter subject) + (for @.old + (<old_extension> subject parameter) + + @.jvm + ("jvm object cast" + (<new_extension> ("jvm object cast" parameter) + ("jvm object cast" subject))))))])] [int/2 java/lang/Integer] [long/2 java/lang/Long] @@ -357,66 +357,66 @@ ) (template: (int+long/2 <old_extension> <new_extension>) - [(: (-> java/lang/Integer java/lang/Long java/lang/Long) - (function (_ parameter subject) - (for @.old - (<old_extension> subject parameter) - - @.jvm - ("jvm object cast" - (<new_extension> ("jvm object cast" parameter) - ("jvm object cast" subject))))))]) + [(is (-> java/lang/Integer java/lang/Long java/lang/Long) + (function (_ parameter subject) + (for @.old + (<old_extension> subject parameter) + + @.jvm + ("jvm object cast" + (<new_extension> ("jvm object cast" parameter) + ("jvm object cast" subject))))))]) (def: int Test - (let [int (: (-> java/lang/Integer (Bytecode Any) (Random Bit)) - (function (_ expected bytecode) - (<| (..bytecode (for @.old - (|>> (:as java/lang/Integer) ("jvm ieq" expected)) - - @.jvm - (|>> (:as java/lang/Integer) "jvm object cast" ("jvm int =" ("jvm object cast" expected))))) - (do /.monad - [_ bytecode] - ..$Integer::wrap)))) - unary (: (-> (-> java/lang/Integer java/lang/Integer) (Bytecode Any) (Random Bit)) - (function (_ reference instruction) - (do random.monad - [subject ..$Integer::random] - (int (reference subject) - (do /.monad - [_ (..$Integer::literal subject)] - instruction))))) - binary (: (-> (-> java/lang/Integer java/lang/Integer java/lang/Integer) - (Bytecode Any) - (Random Bit)) + (let [int (is (-> java/lang/Integer (Bytecode Any) (Random Bit)) + (function (_ expected bytecode) + (<| (..bytecode (for @.old + (|>> (as java/lang/Integer) ("jvm ieq" expected)) + + @.jvm + (|>> (as java/lang/Integer) "jvm object cast" ("jvm int =" ("jvm object cast" expected))))) + (do /.monad + [_ bytecode] + ..$Integer::wrap)))) + unary (is (-> (-> java/lang/Integer java/lang/Integer) (Bytecode Any) (Random Bit)) (function (_ reference instruction) (do random.monad - [parameter ..$Integer::random + [subject ..$Integer::random] + (int (reference subject) + (do /.monad + [_ (..$Integer::literal subject)] + instruction))))) + binary (is (-> (-> java/lang/Integer java/lang/Integer java/lang/Integer) + (Bytecode Any) + (Random Bit)) + (function (_ reference instruction) + (do random.monad + [parameter ..$Integer::random + subject ..$Integer::random] + (int (reference parameter subject) + (do /.monad + [_ (..$Integer::literal subject) + _ (..$Integer::literal parameter)] + instruction))))) + shift (is (-> (-> java/lang/Integer java/lang/Integer java/lang/Integer) (Bytecode Any) (Random Bit)) + (function (_ reference instruction) + (do [! random.monad] + [parameter (# ! each (|>> (n.% 32) .int (as java/lang/Long) ffi.long_to_int) random.nat) subject ..$Integer::random] (int (reference parameter subject) (do /.monad [_ (..$Integer::literal subject) _ (..$Integer::literal parameter)] instruction))))) - shift (: (-> (-> java/lang/Integer java/lang/Integer java/lang/Integer) (Bytecode Any) (Random Bit)) - (function (_ reference instruction) - (do [! random.monad] - [parameter (# ! each (|>> (n.% 32) .int (:as java/lang/Long) ffi.long_to_int) random.nat) - subject ..$Integer::random] - (int (reference parameter subject) - (do /.monad - [_ (..$Integer::literal subject) - _ (..$Integer::literal parameter)] - instruction))))) literal ($_ _.and - (_.lifted "ICONST_M1" (int (ffi.long_to_int (:as java/lang/Long -1)) /.iconst_m1)) - (_.lifted "ICONST_0" (int (ffi.long_to_int (:as java/lang/Long +0)) /.iconst_0)) - (_.lifted "ICONST_1" (int (ffi.long_to_int (:as java/lang/Long +1)) /.iconst_1)) - (_.lifted "ICONST_2" (int (ffi.long_to_int (:as java/lang/Long +2)) /.iconst_2)) - (_.lifted "ICONST_3" (int (ffi.long_to_int (:as java/lang/Long +3)) /.iconst_3)) - (_.lifted "ICONST_4" (int (ffi.long_to_int (:as java/lang/Long +4)) /.iconst_4)) - (_.lifted "ICONST_5" (int (ffi.long_to_int (:as java/lang/Long +5)) /.iconst_5)) + (_.lifted "ICONST_M1" (int (ffi.long_to_int (as java/lang/Long -1)) /.iconst_m1)) + (_.lifted "ICONST_0" (int (ffi.long_to_int (as java/lang/Long +0)) /.iconst_0)) + (_.lifted "ICONST_1" (int (ffi.long_to_int (as java/lang/Long +1)) /.iconst_1)) + (_.lifted "ICONST_2" (int (ffi.long_to_int (as java/lang/Long +2)) /.iconst_2)) + (_.lifted "ICONST_3" (int (ffi.long_to_int (as java/lang/Long +3)) /.iconst_3)) + (_.lifted "ICONST_4" (int (ffi.long_to_int (as java/lang/Long +4)) /.iconst_4)) + (_.lifted "ICONST_5" (int (ffi.long_to_int (as java/lang/Long +5)) /.iconst_5)) (_.lifted "LDC_W/INTEGER" (do random.monad [expected ..$Integer::random] @@ -430,7 +430,7 @@ (_.lifted "INEG" (unary (function (_ value) ((int/2 "jvm isub" "jvm int -") value - (ffi.long_to_int (:as java/lang/Long +0)))) + (ffi.long_to_int (as java/lang/Long +0)))) /.ineg))) bitwise ($_ _.and (_.lifted "IAND" (binary (int/2 "jvm iand" "jvm int and") /.iand)) @@ -450,47 +450,47 @@ (def: long Test - (let [long (: (-> java/lang/Long (Bytecode Any) (Random Bit)) - (function (_ expected bytecode) - (<| (..bytecode (for @.old - (|>> (:as Int) (i.= expected)) - - @.jvm - (|>> (:as java/lang/Long) "jvm object cast" ("jvm long =" ("jvm object cast" expected))))) - (do /.monad - [_ bytecode] - ..$Long::wrap)))) - unary (: (-> (-> java/lang/Long java/lang/Long) (Bytecode Any) (Random Bit)) - (function (_ reference instruction) - (do random.monad - [subject ..$Long::random] - (long (reference subject) - (do /.monad - [_ (..$Long::literal subject)] - instruction))))) - binary (: (-> (-> java/lang/Long java/lang/Long java/lang/Long) (Bytecode Any) (Random Bit)) + (let [long (is (-> java/lang/Long (Bytecode Any) (Random Bit)) + (function (_ expected bytecode) + (<| (..bytecode (for @.old + (|>> (as Int) (i.= expected)) + + @.jvm + (|>> (as java/lang/Long) "jvm object cast" ("jvm long =" ("jvm object cast" expected))))) + (do /.monad + [_ bytecode] + ..$Long::wrap)))) + unary (is (-> (-> java/lang/Long java/lang/Long) (Bytecode Any) (Random Bit)) (function (_ reference instruction) (do random.monad - [parameter ..$Long::random + [subject ..$Long::random] + (long (reference subject) + (do /.monad + [_ (..$Long::literal subject)] + instruction))))) + binary (is (-> (-> java/lang/Long java/lang/Long java/lang/Long) (Bytecode Any) (Random Bit)) + (function (_ reference instruction) + (do random.monad + [parameter ..$Long::random + subject ..$Long::random] + (long (reference parameter subject) + (do /.monad + [_ (..$Long::literal subject) + _ (..$Long::literal parameter)] + instruction))))) + shift (is (-> (-> java/lang/Integer java/lang/Long java/lang/Long) (Bytecode Any) (Random Bit)) + (function (_ reference instruction) + (do [! random.monad] + [parameter (# ! each (|>> (n.% 64) (as java/lang/Long)) random.nat) subject ..$Long::random] - (long (reference parameter subject) + (long (reference (ffi.long_to_int parameter) subject) (do /.monad [_ (..$Long::literal subject) - _ (..$Long::literal parameter)] + _ (..$Integer::literal (ffi.long_to_int parameter))] instruction))))) - shift (: (-> (-> java/lang/Integer java/lang/Long java/lang/Long) (Bytecode Any) (Random Bit)) - (function (_ reference instruction) - (do [! random.monad] - [parameter (# ! each (|>> (n.% 64) (:as java/lang/Long)) random.nat) - subject ..$Long::random] - (long (reference (ffi.long_to_int parameter) subject) - (do /.monad - [_ (..$Long::literal subject) - _ (..$Integer::literal (ffi.long_to_int parameter))] - instruction))))) literal ($_ _.and - (_.lifted "LCONST_0" (long (:as java/lang/Long +0) /.lconst_0)) - (_.lifted "LCONST_1" (long (:as java/lang/Long +1) /.lconst_1)) + (_.lifted "LCONST_0" (long (as java/lang/Long +0) /.lconst_0)) + (_.lifted "LCONST_1" (long (as java/lang/Long +1) /.lconst_1)) (_.lifted "LDC2_W/LONG" (do random.monad [expected ..$Long::random] @@ -504,7 +504,7 @@ (_.lifted "LNEG" (unary (function (_ value) ((long/2 "jvm lsub" "jvm long -") value - (:as java/lang/Long +0))) + (as java/lang/Long +0))) /.lneg))) bitwise ($_ _.and (_.lifted "LAND" (binary (long/2 "jvm land" "jvm long and") /.land)) @@ -517,19 +517,19 @@ (do random.monad [reference ..$Long::random subject ..$Long::random - .let [expected (cond (i.= (:as Int reference) (:as Int subject)) - (:as java/lang/Long +0) + .let [expected (cond (i.= (as Int reference) (as Int subject)) + (as java/lang/Long +0) - (i.> (:as Int reference) (:as Int subject)) - (:as java/lang/Long +1) + (i.> (as Int reference) (as Int subject)) + (as java/lang/Long +1) - ... (i.< (:as Int reference) (:as Int subject)) - (:as java/lang/Long -1))]] + ... (i.< (as Int reference) (as Int subject)) + (as java/lang/Long -1))]] (<| (..bytecode (for @.old - (|>> (:as Int) (i.= expected)) + (|>> (as Int) (i.= expected)) @.jvm - (|>> (:as java/lang/Long) "jvm object cast" ("jvm long =" ("jvm object cast" expected))))) + (|>> (as java/lang/Long) "jvm object cast" ("jvm long =" ("jvm object cast" expected))))) (do /.monad [_ (..$Long::literal subject) _ (..$Long::literal reference) @@ -549,48 +549,48 @@ (def: float Test - (let [float (: (-> java/lang/Float (Bytecode Any) (Random Bit)) - (function (_ expected bytecode) - (<| (..bytecode (for @.old - (function (_ actual) - (or (|> actual (:as java/lang/Float) ("jvm feq" expected)) - (and (f.not_a_number? (:as Frac (ffi.float_to_double expected))) - (f.not_a_number? (:as Frac (ffi.float_to_double (:as java/lang/Float actual))))))) - - @.jvm - (function (_ actual) - (or (|> actual (:as java/lang/Float) "jvm object cast" ("jvm float =" ("jvm object cast" expected))) - (and (f.not_a_number? (:as Frac (ffi.float_to_double expected))) - (f.not_a_number? (:as Frac (ffi.float_to_double (:as java/lang/Float actual))))))))) - (do /.monad - [_ bytecode] - ..$Float::wrap)))) - unary (: (-> (-> java/lang/Float java/lang/Float) - (Bytecode Any) - (Random Bit)) - (function (_ reference instruction) - (do random.monad - [subject ..$Float::random] - (float (reference subject) - (do /.monad - [_ (..$Float::literal subject)] - instruction))))) - binary (: (-> (-> java/lang/Float java/lang/Float java/lang/Float) + (let [float (is (-> java/lang/Float (Bytecode Any) (Random Bit)) + (function (_ expected bytecode) + (<| (..bytecode (for @.old + (function (_ actual) + (or (|> actual (as java/lang/Float) ("jvm feq" expected)) + (and (f.not_a_number? (as Frac (ffi.float_to_double expected))) + (f.not_a_number? (as Frac (ffi.float_to_double (as java/lang/Float actual))))))) + + @.jvm + (function (_ actual) + (or (|> actual (as java/lang/Float) "jvm object cast" ("jvm float =" ("jvm object cast" expected))) + (and (f.not_a_number? (as Frac (ffi.float_to_double expected))) + (f.not_a_number? (as Frac (ffi.float_to_double (as java/lang/Float actual))))))))) + (do /.monad + [_ bytecode] + ..$Float::wrap)))) + unary (is (-> (-> java/lang/Float java/lang/Float) (Bytecode Any) (Random Bit)) (function (_ reference instruction) (do random.monad - [parameter ..$Float::random - subject ..$Float::random] - (float (reference parameter subject) + [subject ..$Float::random] + (float (reference subject) (do /.monad - [_ (..$Float::literal subject) - _ (..$Float::literal parameter)] + [_ (..$Float::literal subject)] instruction))))) + binary (is (-> (-> java/lang/Float java/lang/Float java/lang/Float) + (Bytecode Any) + (Random Bit)) + (function (_ reference instruction) + (do random.monad + [parameter ..$Float::random + subject ..$Float::random] + (float (reference parameter subject) + (do /.monad + [_ (..$Float::literal subject) + _ (..$Float::literal parameter)] + instruction))))) literal ($_ _.and - (_.lifted "FCONST_0" (float (ffi.double_to_float (:as java/lang/Double +0.0)) /.fconst_0)) - (_.lifted "FCONST_1" (float (ffi.double_to_float (:as java/lang/Double +1.0)) /.fconst_1)) - (_.lifted "FCONST_2" (float (ffi.double_to_float (:as java/lang/Double +2.0)) /.fconst_2)) + (_.lifted "FCONST_0" (float (ffi.double_to_float (as java/lang/Double +0.0)) /.fconst_0)) + (_.lifted "FCONST_1" (float (ffi.double_to_float (as java/lang/Double +1.0)) /.fconst_1)) + (_.lifted "FCONST_2" (float (ffi.double_to_float (as java/lang/Double +2.0)) /.fconst_2)) (_.lifted "LDC_W/FLOAT" (do random.monad [expected ..$Float::random] @@ -604,38 +604,38 @@ (_.lifted "FNEG" (unary (function (_ value) ((float/2 "jvm fsub" "jvm float -") value - (ffi.double_to_float (:as java/lang/Double +0.0)))) + (ffi.double_to_float (as java/lang/Double +0.0)))) /.fneg))) - comparison (: (-> (Bytecode Any) (-> java/lang/Float java/lang/Float Bit) (Random Bit)) - (function (_ instruction standard) - (do random.monad - [.let [valid_float (random.only (|>> ffi.float_to_double (:as Frac) f.not_a_number? not) - ..$Float::random)] - reference valid_float - subject valid_float - .let [expected (if (for @.old - ("jvm feq" reference subject) - - @.jvm - ("jvm float =" ("jvm object cast" reference) ("jvm object cast" subject))) - +0 - (if (standard reference subject) - +1 - -1))]] - (<| (..bytecode (|>> (:as Int) (i.= expected))) - (do /.monad - [_ (..$Float::literal subject) - _ (..$Float::literal reference) - _ instruction - _ /.i2l] - ..$Long::wrap))))) - comparison_standard (: (-> java/lang/Float java/lang/Float Bit) - (function (_ reference subject) - (for @.old - ("jvm fgt" subject reference) - - @.jvm - ("jvm float <" ("jvm object cast" subject) ("jvm object cast" reference))))) + comparison (is (-> (Bytecode Any) (-> java/lang/Float java/lang/Float Bit) (Random Bit)) + (function (_ instruction standard) + (do random.monad + [.let [valid_float (random.only (|>> ffi.float_to_double (as Frac) f.not_a_number? not) + ..$Float::random)] + reference valid_float + subject valid_float + .let [expected (if (for @.old + ("jvm feq" reference subject) + + @.jvm + ("jvm float =" ("jvm object cast" reference) ("jvm object cast" subject))) + +0 + (if (standard reference subject) + +1 + -1))]] + (<| (..bytecode (|>> (as Int) (i.= expected))) + (do /.monad + [_ (..$Float::literal subject) + _ (..$Float::literal reference) + _ instruction + _ /.i2l] + ..$Long::wrap))))) + comparison_standard (is (-> java/lang/Float java/lang/Float Bit) + (function (_ reference subject) + (for @.old + ("jvm fgt" subject reference) + + @.jvm + ("jvm float <" ("jvm object cast" subject) ("jvm object cast" reference))))) comparison ($_ _.and (_.lifted "FCMPL" (comparison /.fcmpl comparison_standard)) (_.lifted "FCMPG" (comparison /.fcmpg comparison_standard)))] @@ -650,43 +650,43 @@ (def: double Test - (let [double (: (-> java/lang/Double (Bytecode Any) (Random Bit)) - (function (_ expected bytecode) - (<| (..bytecode (for @.old - (function (_ actual) - (or (|> actual (:as java/lang/Double) ("jvm deq" expected)) - (and (f.not_a_number? (:as Frac expected)) - (f.not_a_number? (:as Frac actual))))) - - @.jvm - (function (_ actual) - (or (|> actual (:as java/lang/Double) "jvm object cast" ("jvm double =" ("jvm object cast" expected))) - (and (f.not_a_number? (:as Frac expected)) - (f.not_a_number? (:as Frac actual))))))) - (do /.monad - [_ bytecode] - ..$Double::wrap)))) - unary (: (-> (-> java/lang/Double java/lang/Double) (Bytecode Any) (Random Bit)) - (function (_ reference instruction) - (do random.monad - [subject ..$Double::random] - (double (reference subject) - (do /.monad - [_ (..$Double::literal subject)] - instruction))))) - binary (: (-> (-> java/lang/Double java/lang/Double java/lang/Double) (Bytecode Any) (Random Bit)) + (let [double (is (-> java/lang/Double (Bytecode Any) (Random Bit)) + (function (_ expected bytecode) + (<| (..bytecode (for @.old + (function (_ actual) + (or (|> actual (as java/lang/Double) ("jvm deq" expected)) + (and (f.not_a_number? (as Frac expected)) + (f.not_a_number? (as Frac actual))))) + + @.jvm + (function (_ actual) + (or (|> actual (as java/lang/Double) "jvm object cast" ("jvm double =" ("jvm object cast" expected))) + (and (f.not_a_number? (as Frac expected)) + (f.not_a_number? (as Frac actual))))))) + (do /.monad + [_ bytecode] + ..$Double::wrap)))) + unary (is (-> (-> java/lang/Double java/lang/Double) (Bytecode Any) (Random Bit)) (function (_ reference instruction) (do random.monad - [parameter ..$Double::random - subject ..$Double::random] - (double (reference parameter subject) + [subject ..$Double::random] + (double (reference subject) (do /.monad - [_ (..$Double::literal subject) - _ (..$Double::literal parameter)] + [_ (..$Double::literal subject)] instruction))))) + binary (is (-> (-> java/lang/Double java/lang/Double java/lang/Double) (Bytecode Any) (Random Bit)) + (function (_ reference instruction) + (do random.monad + [parameter ..$Double::random + subject ..$Double::random] + (double (reference parameter subject) + (do /.monad + [_ (..$Double::literal subject) + _ (..$Double::literal parameter)] + instruction))))) literal ($_ _.and - (_.lifted "DCONST_0" (double (:as java/lang/Double +0.0) /.dconst_0)) - (_.lifted "DCONST_1" (double (:as java/lang/Double +1.0) /.dconst_1)) + (_.lifted "DCONST_0" (double (as java/lang/Double +0.0) /.dconst_0)) + (_.lifted "DCONST_1" (double (as java/lang/Double +1.0) /.dconst_1)) (_.lifted "LDC2_W/DOUBLE" (do random.monad [expected ..$Double::random] @@ -700,37 +700,37 @@ (_.lifted "DNEG" (unary (function (_ value) ((double/2 "jvm dsub" "jvm double -") value - (:as java/lang/Double +0.0))) + (as java/lang/Double +0.0))) /.dneg))) - comparison (: (-> (Bytecode Any) (-> java/lang/Double java/lang/Double Bit) (Random Bit)) - (function (_ instruction standard) - (do random.monad - [reference ..valid_double - subject ..valid_double - .let [expected (if (for @.old - ("jvm deq" reference subject) - - @.jvm - ("jvm double =" ("jvm object cast" reference) ("jvm object cast" subject))) - +0 - (if (standard reference subject) - +1 - -1))]] - (<| (..bytecode (|>> (:as Int) (i.= expected))) - (do /.monad - [_ (..$Double::literal subject) - _ (..$Double::literal reference) - _ instruction - _ /.i2l] - ..$Long::wrap))))) + comparison (is (-> (Bytecode Any) (-> java/lang/Double java/lang/Double Bit) (Random Bit)) + (function (_ instruction standard) + (do random.monad + [reference ..valid_double + subject ..valid_double + .let [expected (if (for @.old + ("jvm deq" reference subject) + + @.jvm + ("jvm double =" ("jvm object cast" reference) ("jvm object cast" subject))) + +0 + (if (standard reference subject) + +1 + -1))]] + (<| (..bytecode (|>> (as Int) (i.= expected))) + (do /.monad + [_ (..$Double::literal subject) + _ (..$Double::literal reference) + _ instruction + _ /.i2l] + ..$Long::wrap))))) ... https://docs.oracle.com/javase/specs/jvms/se7/html/jvms-6.html#jvms-6.5.dcmp_op - comparison_standard (: (-> java/lang/Double java/lang/Double Bit) - (function (_ reference subject) - (for @.old - ("jvm dgt" subject reference) - - @.jvm - ("jvm double <" ("jvm object cast" subject) ("jvm object cast" reference))))) + comparison_standard (is (-> java/lang/Double java/lang/Double Bit) + (function (_ reference subject) + (for @.old + ("jvm dgt" subject reference) + + @.jvm + ("jvm double <" ("jvm object cast" subject) ("jvm object cast" reference))))) comparison ($_ _.and (_.lifted "DCMPL" (comparison /.dcmpl comparison_standard)) (_.lifted "DCMPG" (comparison /.dcmpg comparison_standard)))] @@ -762,14 +762,14 @@ (def: object Test - (let [!object (: (Bytecode Any) - (do /.monad - [_ (/.new ..$Object) - _ /.dup] - (/.invokespecial ..$Object "<init>" (/type.method [(list) (list) /type.void (list)]))))] + (let [!object (is (Bytecode Any) + (do /.monad + [_ (/.new ..$Object) + _ /.dup] + (/.invokespecial ..$Object "<init>" (/type.method [(list) (list) /type.void (list)]))))] ($_ _.and (<| (_.lifted "ACONST_NULL") - (..bytecode (|>> (:as Bit) not)) + (..bytecode (|>> (as Bit) not)) (do /.monad [_ /.aconst_null _ (/.instanceof ..$String)] @@ -777,13 +777,13 @@ (<| (_.lifted "INSTANCEOF") (do random.monad [value ..$String::random]) - (..bytecode (|>> (:as Bit))) + (..bytecode (|>> (as Bit))) (do /.monad - [_ (/.string (:as Text value)) + [_ (/.string (as Text value)) _ (/.instanceof ..$String)] ..$Boolean::wrap)) (<| (_.lifted "NEW & CHECKCAST") - (..bytecode (|>> (:as Bit))) + (..bytecode (|>> (as Bit))) (do /.monad [_ !object _ (/.checkcast ..$Object) @@ -792,9 +792,9 @@ (<| (_.lifted "MONITORENTER & MONITOREXIT") (do random.monad [value ..$String::random]) - (..bytecode (|>> (:as Bit))) + (..bytecode (|>> (as Bit))) (do /.monad - [_ (/.string (:as Text value)) + [_ (/.string (as Text value)) _ /.dup _ /.monitorenter _ /.dup _ /.monitorexit _ (/.instanceof ..$String)] @@ -806,20 +806,20 @@ ($_ _.and (<| (_.lifted "INVOKESTATIC") (do random.monad - [expected (random.only (|>> (:as Frac) f.not_a_number? not) + [expected (random.only (|>> (as Frac) f.not_a_number? not) ..$Double::random)]) (..bytecode (for @.old - (|>> (:as java/lang/Double) ("jvm deq" expected)) + (|>> (as java/lang/Double) ("jvm deq" expected)) @.jvm - (|>> (:as java/lang/Double) "jvm object cast" ("jvm double =" ("jvm object cast" expected))))) + (|>> (as java/lang/Double) "jvm object cast" ("jvm double =" ("jvm object cast" expected))))) (do /.monad [_ (/.double expected)] (/.invokestatic ..$Double "valueOf" (/type.method [(list) (list /type.double) ..$Double (list)])))) (<| (_.lifted "INVOKEVIRTUAL") (do random.monad [expected ..$Double::random]) - (..bytecode (|>> (:as Bit) (bit#= (f.not_a_number? (:as Frac expected))))) + (..bytecode (|>> (as Bit) (bit#= (f.not_a_number? (as Frac expected))))) (do /.monad [_ (/.double expected) _ ..$Double::wrap @@ -827,13 +827,13 @@ ..$Boolean::wrap)) (<| (_.lifted "INVOKESPECIAL") (do random.monad - [expected (random.only (|>> (:as Frac) f.not_a_number? not) + [expected (random.only (|>> (as Frac) f.not_a_number? not) ..$Double::random)]) (..bytecode (for @.old - (|>> (:as java/lang/Double) ("jvm deq" expected)) + (|>> (as java/lang/Double) ("jvm deq" expected)) @.jvm - (|>> (:as java/lang/Double) "jvm object cast" ("jvm double =" ("jvm object cast" expected))))) + (|>> (as java/lang/Double) "jvm object cast" ("jvm double =" ("jvm object cast" expected))))) (do /.monad [_ (/.new ..$Double) _ /.dup @@ -842,9 +842,9 @@ (<| (_.lifted "INVOKEINTERFACE") (do random.monad [subject ..$String::random]) - (..bytecode (|>> (:as Nat) (n.= (text.size (:as Text subject))))) + (..bytecode (|>> (as Nat) (n.= (text.size (as Text subject))))) (do /.monad - [_ (/.string (:as Text subject)) + [_ (/.string (as Text subject)) _ (/.invokeinterface (/type.class "java.lang.CharSequence" (list)) "length" (/type.method [(list) (list) /type.int (list)])) _ /.i2l] ..$Long::wrap)) @@ -856,13 +856,13 @@ [class_name ..class_name part0 ..$Long::random part1 ..$Long::random - .let [expected (: java/lang/Long - (for @.old - ("jvm ladd" part0 part1) - - @.jvm - ("jvm object cast" - ("jvm long +" ("jvm object cast" part0) ("jvm object cast" part1))))) + .let [expected (is java/lang/Long + (for @.old + ("jvm ladd" part0 part1) + + @.jvm + ("jvm object cast" + ("jvm long +" ("jvm object cast" part0) ("jvm object cast" part1))))) $Self (/type.class class_name (list)) class_field "class_field" object_field "object_field" @@ -915,124 +915,124 @@ class (io.run! (/loader.load class_name loader)) method (try (get_method static_method class)) output (java/lang/reflect/Method::invoke (ffi.null) (ffi.array java/lang/Object 0) method)] - (in (:as Int output))) + (in (as Int output))) {try.#Success actual} - (i.= (:as Int expected) (:as Int actual)) + (i.= (as Int expected) (as Int actual)) {try.#Failure error} false)))) (def: array Test - (let [!length (: (-> Nat (Bytecode Any)) - (function (_ size) - (do /.monad - [_ ($Long::literal (:as java/lang/Long size))] - /.l2i))) - ?length (: (Bytecode Any) - (do /.monad - [_ /.arraylength] - /.i2l)) - length (: (-> Nat (Bytecode Any) (Random Bit)) - (function (_ size constructor) - (<| (..bytecode (|>> (:as Nat) (n.= size))) - (do /.monad - [_ (!length size) - _ constructor - _ ?length] - $Long::wrap)))) - write_and_read (: (All (_ a) - (-> Nat (Bytecode Any) - a (-> a (Bytecode Any)) - [(Bytecode Any) (Bytecode Any) (Bytecode Any)] - (-> a Any Bit) - (Random Bit))) - (function (_ size constructor value literal [*store *load *wrap] test) - (let [!index ($Integer::literal (ffi.long_to_int (:as java/lang/Long +0)))] - (<| (..bytecode (test value)) - (do /.monad - [_ (!length size) - _ constructor - _ /.dup _ !index _ (literal value) _ *store - _ /.dup _ !index _ *load] - *wrap))))) - array (: (All (_ a) - (-> (Bytecode Any) (Random a) (-> a (Bytecode Any)) - [(Bytecode Any) (Bytecode Any) (Bytecode Any)] - (-> a Any Bit) - Test)) - (function (_ constructor random literal [*store *load *wrap] test) - (do [! random.monad] - [size (# ! each (|>> (n.% 1024) (n.max 1)) random.nat) - value random] - ($_ _.and - (<| (_.lifted "length") - (length size constructor)) - (<| (_.lifted "write and read") - (write_and_read size constructor value literal [*store *load *wrap] test))))))] + (let [!length (is (-> Nat (Bytecode Any)) + (function (_ size) + (do /.monad + [_ ($Long::literal (as java/lang/Long size))] + /.l2i))) + ?length (is (Bytecode Any) + (do /.monad + [_ /.arraylength] + /.i2l)) + length (is (-> Nat (Bytecode Any) (Random Bit)) + (function (_ size constructor) + (<| (..bytecode (|>> (as Nat) (n.= size))) + (do /.monad + [_ (!length size) + _ constructor + _ ?length] + $Long::wrap)))) + write_and_read (is (All (_ a) + (-> Nat (Bytecode Any) + a (-> a (Bytecode Any)) + [(Bytecode Any) (Bytecode Any) (Bytecode Any)] + (-> a Any Bit) + (Random Bit))) + (function (_ size constructor value literal [*store *load *wrap] test) + (let [!index ($Integer::literal (ffi.long_to_int (as java/lang/Long +0)))] + (<| (..bytecode (test value)) + (do /.monad + [_ (!length size) + _ constructor + _ /.dup _ !index _ (literal value) _ *store + _ /.dup _ !index _ *load] + *wrap))))) + array (is (All (_ a) + (-> (Bytecode Any) (Random a) (-> a (Bytecode Any)) + [(Bytecode Any) (Bytecode Any) (Bytecode Any)] + (-> a Any Bit) + Test)) + (function (_ constructor random literal [*store *load *wrap] test) + (do [! random.monad] + [size (# ! each (|>> (n.% 1024) (n.max 1)) random.nat) + value random] + ($_ _.and + (<| (_.lifted "length") + (length size constructor)) + (<| (_.lifted "write and read") + (write_and_read size constructor value literal [*store *load *wrap] test))))))] ($_ _.and (_.context "boolean" (array (/.newarray /instruction.t_boolean) $Boolean::random $Boolean::literal [/.bastore /.baload $Boolean::wrap] - (function (_ expected) (|>> (:as Bit) (bit#= (:as Bit expected)))))) + (function (_ expected) (|>> (as Bit) (bit#= (as Bit expected)))))) (_.context "byte" (array (/.newarray /instruction.t_byte) $Byte::random $Byte::literal [/.bastore /.baload $Byte::wrap] (function (_ expected) (for @.old - (|>> (:as java/lang/Byte) ffi.byte_to_long ("jvm leq" (ffi.byte_to_long expected))) + (|>> (as java/lang/Byte) ffi.byte_to_long ("jvm leq" (ffi.byte_to_long expected))) @.jvm - (|>> (:as java/lang/Byte) ffi.byte_to_long "jvm object cast" ("jvm long =" ("jvm object cast" (ffi.byte_to_long (:as java/lang/Byte expected))))))))) + (|>> (as java/lang/Byte) ffi.byte_to_long "jvm object cast" ("jvm long =" ("jvm object cast" (ffi.byte_to_long (as java/lang/Byte expected))))))))) (_.context "short" (array (/.newarray /instruction.t_short) $Short::random $Short::literal [/.sastore /.saload $Short::wrap] (function (_ expected) (for @.old - (|>> (:as java/lang/Short) ffi.short_to_long ("jvm leq" (ffi.short_to_long expected))) + (|>> (as java/lang/Short) ffi.short_to_long ("jvm leq" (ffi.short_to_long expected))) @.jvm - (|>> (:as java/lang/Short) ffi.short_to_long "jvm object cast" ("jvm long =" ("jvm object cast" (ffi.short_to_long (:as java/lang/Short expected))))))))) + (|>> (as java/lang/Short) ffi.short_to_long "jvm object cast" ("jvm long =" ("jvm object cast" (ffi.short_to_long (as java/lang/Short expected))))))))) (_.context "int" (array (/.newarray /instruction.t_int) $Integer::random $Integer::literal [/.iastore /.iaload $Integer::wrap] (function (_ expected) (for @.old - (|>> (:as java/lang/Integer) ("jvm ieq" (:as java/lang/Integer expected))) + (|>> (as java/lang/Integer) ("jvm ieq" (as java/lang/Integer expected))) @.jvm - (|>> (:as java/lang/Integer) "jvm object cast" ("jvm int =" ("jvm object cast" (:as java/lang/Integer expected)))))))) + (|>> (as java/lang/Integer) "jvm object cast" ("jvm int =" ("jvm object cast" (as java/lang/Integer expected)))))))) (_.context "long" (array (/.newarray /instruction.t_long) $Long::random $Long::literal [/.lastore /.laload $Long::wrap] (function (_ expected) (for @.old - (|>> (:as java/lang/Long) ("jvm leq" expected)) + (|>> (as java/lang/Long) ("jvm leq" expected)) @.jvm - (|>> (:as java/lang/Long) "jvm object cast" ("jvm long =" ("jvm object cast" (:as java/lang/Long expected)))))))) + (|>> (as java/lang/Long) "jvm object cast" ("jvm long =" ("jvm object cast" (as java/lang/Long expected)))))))) (_.context "float" (array (/.newarray /instruction.t_float) ..valid_float $Float::literal [/.fastore /.faload $Float::wrap] (function (_ expected) (for @.old - (|>> (:as java/lang/Float) ("jvm feq" expected)) + (|>> (as java/lang/Float) ("jvm feq" expected)) @.jvm - (|>> (:as java/lang/Float) "jvm object cast" ("jvm float =" ("jvm object cast" (:as java/lang/Float expected)))))))) + (|>> (as java/lang/Float) "jvm object cast" ("jvm float =" ("jvm object cast" (as java/lang/Float expected)))))))) (_.context "double" (array (/.newarray /instruction.t_double) ..valid_double $Double::literal [/.dastore /.daload $Double::wrap] (function (_ expected) (for @.old - (|>> (:as java/lang/Double) ("jvm deq" expected)) + (|>> (as java/lang/Double) ("jvm deq" expected)) @.jvm - (|>> (:as java/lang/Double) "jvm object cast" ("jvm double =" ("jvm object cast" (:as java/lang/Double expected)))))))) + (|>> (as java/lang/Double) "jvm object cast" ("jvm double =" ("jvm object cast" (as java/lang/Double expected)))))))) (_.context "char" (array (/.newarray /instruction.t_char) $Character::random $Character::literal [/.castore /.caload $Character::wrap] (function (_ expected) (for @.old - (|>> (:as java/lang/Character) ("jvm ceq" expected)) + (|>> (as java/lang/Character) ("jvm ceq" expected)) @.jvm - (|>> (:as java/lang/Character) "jvm object cast" ("jvm char =" ("jvm object cast" (:as java/lang/Character expected)))))))) + (|>> (as java/lang/Character) "jvm object cast" ("jvm char =" ("jvm object cast" (as java/lang/Character expected)))))))) (_.context "object" (array (/.anewarray ..$String) $String::random $String::literal [/.aastore /.aaload /.nop] - (function (_ expected) (|>> (:as Text) (text#= (:as Text expected)))))) + (function (_ expected) (|>> (as Text) (text#= (as Text expected)))))) (<| (_.context "multi") (do [! random.monad] [.let [size (# ! each (|>> (n.% 5) (n.+ 1)) @@ -1041,15 +1041,15 @@ sizesH size sizesT (random.list (-- dimensions) size) .let [type (loop [dimensions dimensions - type (: (Type Object) - ..$Object)] + type (is (Type Object) + ..$Object)] (case dimensions 0 type _ (again (-- dimensions) (/type.array type))))]] (<| (_.lifted "MULTIANEWARRAY") - (..bytecode (|>> (:as Nat) (n.= sizesH))) + (..bytecode (|>> (as Nat) (n.= sizesH))) (do [! /.monad] - [_ (monad.each ! (|>> (:as java/lang/Long) ffi.long_to_int ..$Integer::literal) + [_ (monad.each ! (|>> (as java/lang/Long) ffi.long_to_int ..$Integer::literal) {.#Item sizesH sizesT}) _ (/.multianewarray type (|> dimensions /unsigned.u1 try.trusted)) _ ?length] @@ -1057,27 +1057,27 @@ ))) (template: (!::= <type> <old> <new>) - [(: (-> <type> Any Bit) - (function (_ expected) - (for @.old - (|>> (:as <type>) (<old> expected)) - - @.jvm - (|>> (:as <type>) "jvm object cast" (<new> ("jvm object cast" (:as <type> expected)))))))]) + [(is (-> <type> Any Bit) + (function (_ expected) + (for @.old + (|>> (as <type>) (<old> expected)) + + @.jvm + (|>> (as <type>) "jvm object cast" (<new> ("jvm object cast" (as <type> expected)))))))]) (def: conversion Test - (let [conversion (: (All (_ a z) - (-> (Primitive a) (Primitive z) (Bytecode Any) (-> a z) (-> z Any Bit) (Random Bit))) - (function (_ from to instruction convert test) - (do random.monad - [input (the #random from) - .let [expected (convert input)]] - (..bytecode (test expected) - (do /.monad - [_ ((the #literal from) input) - _ instruction] - (the #wrap to)))))) + (let [conversion (is (All (_ a z) + (-> (Primitive a) (Primitive z) (Bytecode Any) (-> a z) (-> z Any Bit) (Random Bit))) + (function (_ from to instruction convert test) + (do random.monad + [input (the #random from) + .let [expected (convert input)]] + (..bytecode (test expected) + (do /.monad + [_ ((the #literal from) input) + _ instruction] + (the #wrap to)))))) int::= (!::= java/lang/Integer "jvm ieq" "jvm int =") long::= (!::= java/lang/Long "jvm leq" "jvm long =") float::= (!::= java/lang/Float "jvm feq" "jvm float =") @@ -1091,19 +1091,19 @@ (_.lifted "I2B" (conversion ..$Integer::primitive ..$Byte::primitive /.i2b (|>> ffi.int_to_byte) (function (_ expected) (for @.old - (|>> (:as java/lang/Byte) ffi.byte_to_long ("jvm leq" (ffi.byte_to_long expected))) + (|>> (as java/lang/Byte) ffi.byte_to_long ("jvm leq" (ffi.byte_to_long expected))) @.jvm - (|>> (:as java/lang/Byte) ffi.byte_to_long "jvm object cast" ("jvm long =" ("jvm object cast" (ffi.byte_to_long (:as java/lang/Byte expected))))))))) + (|>> (as java/lang/Byte) ffi.byte_to_long "jvm object cast" ("jvm long =" ("jvm object cast" (ffi.byte_to_long (as java/lang/Byte expected))))))))) (_.lifted "I2C" (conversion ..$Integer::primitive ..$Character::primitive /.i2c (|>> ffi.int_to_char) (!::= java/lang/Character "jvm ceq" "jvm char ="))) (_.lifted "I2S" (conversion ..$Integer::primitive ..$Short::primitive /.i2s (|>> ffi.int_to_short) (function (_ expected) (for @.old - (|>> (:as java/lang/Short) ffi.short_to_long ("jvm leq" (ffi.short_to_long expected))) + (|>> (as java/lang/Short) ffi.short_to_long ("jvm leq" (ffi.short_to_long expected))) @.jvm - (|>> (:as java/lang/Short) ffi.short_to_long "jvm object cast" ("jvm long =" ("jvm object cast" (ffi.short_to_long (:as java/lang/Short expected))))))))))) + (|>> (as java/lang/Short) ffi.short_to_long "jvm object cast" ("jvm long =" ("jvm object cast" (ffi.short_to_long (as java/lang/Short expected))))))))))) (<| (_.context "long") ($_ _.and (_.lifted "L2I" (conversion ..$Long::primitive ..$Integer::primitive /.l2i (|>> ffi.long_to_int) int::=)) @@ -1140,21 +1140,21 @@ (def: registry Test - (let [store_and_load (: (All (_ a) - (-> (Random a) (-> a (Bytecode Any)) (Bytecode Any) - [(-> Nat (Bytecode Any)) (-> Nat (Bytecode Any))] - (-> a (-> Any Bit)) - (Random Bit))) - (function (_ random_value literal *wrap [store load] test) - (do [! random.monad] - [expected random_value - register (# ! each (n.% 128) random.nat)] - (<| (..bytecode (test expected)) - (do /.monad - [_ (literal expected) - _ (store register) - _ (load register)] - *wrap)))))] + (let [store_and_load (is (All (_ a) + (-> (Random a) (-> a (Bytecode Any)) (Bytecode Any) + [(-> Nat (Bytecode Any)) (-> Nat (Bytecode Any))] + (-> a (-> Any Bit)) + (Random Bit))) + (function (_ random_value literal *wrap [store load] test) + (do [! random.monad] + [expected random_value + register (# ! each (n.% 128) random.nat)] + (<| (..bytecode (test expected)) + (do /.monad + [_ (literal expected) + _ (store register) + _ (load register)] + *wrap)))))] ($_ _.and (<| (_.context "int") (let [test (!::= java/lang/Integer "jvm ieq" "jvm int =")] @@ -1174,18 +1174,18 @@ [base ..$Byte::random increment (# ! each (|>> (n.% 100) /unsigned.u1 try.trusted) random.nat) - .let [expected (: java/lang/Long - (for @.old - ("jvm ladd" - (ffi.byte_to_long base) - (.int (/unsigned.value increment))) - - @.jvm - ("jvm object cast" - ("jvm long +" - ("jvm object cast" (ffi.byte_to_long base)) - ("jvm object cast" (:as java/lang/Long (/unsigned.value increment)))))))]] - (..bytecode (|>> (:as Int) (i.= (:as Int expected))) + .let [expected (is java/lang/Long + (for @.old + ("jvm ladd" + (ffi.byte_to_long base) + (.int (/unsigned.value increment))) + + @.jvm + ("jvm object cast" + ("jvm long +" + ("jvm object cast" (ffi.byte_to_long base)) + ("jvm object cast" (as java/lang/Long (/unsigned.value increment)))))))]] + (..bytecode (|>> (as Int) (i.= (as Int expected))) (do /.monad [_ (..$Byte::literal base) _ /.istore_0 @@ -1233,9 +1233,9 @@ (_.lifted "DSTORE/DLOAD" (store_and_load ..valid_double ..$Double::literal ..$Double::wrap [/.dstore /.dload] test))))) (<| (_.context "object") - (let [test (: (-> java/lang/String Any Bit) - (function (_ expected actual) - (|> actual (:as Text) (text#= (:as Text expected)))))] + (let [test (is (-> java/lang/String Any Bit) + (function (_ expected actual) + (|> actual (as Text) (text#= (as Text expected)))))] ($_ _.and (_.lifted "ASTORE_0/ALOAD_0" (store_and_load ..$String::random ..$String::literal /.nop [(function.constant /.astore_0) (function.constant /.aload_0)] test)) @@ -1253,8 +1253,8 @@ Test (do random.monad [expected/1 $String::random - .let [object_test (: (-> Any Bit) - (|>> (:as Text) (text#= (:as Text expected/1))))] + .let [object_test (is (-> Any Bit) + (|>> (as Text) (text#= (as Text expected/1))))] dummy/1 $String::random .let [single ($_ _.and (<| (_.lifted "DUP & POP") @@ -1288,8 +1288,8 @@ /.pop)) )] expected/2 $Long::random - .let [long_test (: (-> Any Bit) - (|>> (:as Int) (i.= (:as Int expected/2))))] + .let [long_test (is (-> Any Bit) + (|>> (as Int) (i.= (as Int expected/2))))] dummy/2 $Long::random .let [double ($_ _.and (<| (_.lifted "DUP2") @@ -1336,72 +1336,72 @@ (def: return Test - (let [primitive_return (: (All (_ a) (-> (Primitive a) (Bytecode Any) (Maybe (-> a (Bytecode Any))) (-> a Any Bit) (Random Bit))) - (function (_ primitive return substitute test) - (do random.monad - [class_name ..class_name - primitive_method_name (random.ascii/upper 10) - .let [primitive_method_type (/type.method [(list) (list) (the #unboxed primitive) (list)])] - object_method_name (|> (random.ascii/upper 10) - (random.only (|>> (text#= primitive_method_name) not))) - expected (the #random primitive) - .let [$Self (/type.class class_name (list))]] - (in (case (do try.monad - [class (/class.class /version.v6_0 /class.public - (/name.internal class_name) - {.#None} - (/name.internal "java.lang.Object") - (list) - (list) - (list (/method.method ..method_modifier - primitive_method_name - #0 primitive_method_type - (list) - {.#Some (do /.monad - [_ ((the #literal primitive) expected)] - return)}) - (/method.method ..method_modifier - object_method_name - #0 (/type.method [(list) (list) (the #boxed primitive) (list)]) - (list) - {.#Some (do /.monad - [_ (/.invokestatic $Self primitive_method_name primitive_method_type) - _ (case substitute - {.#None} - (in []) - - {.#Some substitute} - (substitute expected)) - _ (the #wrap primitive)] - /.areturn)})) - (sequence.sequence)) - .let [bytecode (format.result /class.writer class) - loader (/loader.memory (/loader.new_library []))] - _ (/loader.define class_name bytecode loader) - class (io.run! (/loader.load class_name loader)) - method (try (get_method object_method_name class))] - (java/lang/reflect/Method::invoke (ffi.null) (ffi.array java/lang/Object 0) method)) - {try.#Success actual} - (test expected actual) - - {try.#Failure error} - false) - ))))] + (let [primitive_return (is (All (_ a) (-> (Primitive a) (Bytecode Any) (Maybe (-> a (Bytecode Any))) (-> a Any Bit) (Random Bit))) + (function (_ primitive return substitute test) + (do random.monad + [class_name ..class_name + primitive_method_name (random.ascii/upper 10) + .let [primitive_method_type (/type.method [(list) (list) (the #unboxed primitive) (list)])] + object_method_name (|> (random.ascii/upper 10) + (random.only (|>> (text#= primitive_method_name) not))) + expected (the #random primitive) + .let [$Self (/type.class class_name (list))]] + (in (case (do try.monad + [class (/class.class /version.v6_0 /class.public + (/name.internal class_name) + {.#None} + (/name.internal "java.lang.Object") + (list) + (list) + (list (/method.method ..method_modifier + primitive_method_name + #0 primitive_method_type + (list) + {.#Some (do /.monad + [_ ((the #literal primitive) expected)] + return)}) + (/method.method ..method_modifier + object_method_name + #0 (/type.method [(list) (list) (the #boxed primitive) (list)]) + (list) + {.#Some (do /.monad + [_ (/.invokestatic $Self primitive_method_name primitive_method_type) + _ (case substitute + {.#None} + (in []) + + {.#Some substitute} + (substitute expected)) + _ (the #wrap primitive)] + /.areturn)})) + (sequence.sequence)) + .let [bytecode (format.result /class.writer class) + loader (/loader.memory (/loader.new_library []))] + _ (/loader.define class_name bytecode loader) + class (io.run! (/loader.load class_name loader)) + method (try (get_method object_method_name class))] + (java/lang/reflect/Method::invoke (ffi.null) (ffi.array java/lang/Object 0) method)) + {try.#Success actual} + (test expected actual) + + {try.#Failure error} + false) + ))))] ($_ _.and (_.lifted "IRETURN" (primitive_return ..$Integer::primitive /.ireturn {.#None} (!::= java/lang/Integer "jvm ieq" "jvm int ="))) (_.lifted "LRETURN" (primitive_return ..$Long::primitive /.lreturn {.#None} (!::= java/lang/Long "jvm leq" "jvm long ="))) (_.lifted "FRETURN" (primitive_return ..$Float::primitive /.freturn {.#None} (!::= java/lang/Float "jvm feq" "jvm float ="))) (_.lifted "DRETURN" (primitive_return ..$Double::primitive /.dreturn {.#None} (!::= java/lang/Double "jvm deq" "jvm double ="))) - (_.lifted "ARETURN" (primitive_return ..$String::primitive /.areturn {.#None} (function (_ expected actual) (text#= (:as Text expected) (:as Text actual))))) - (_.lifted "RETURN" (primitive_return (: (Primitive java/lang/String) - [#unboxed /type.void - #boxed ..$String - #wrap /.nop - #random ..$String::random - #literal (function.constant /.nop)]) + (_.lifted "ARETURN" (primitive_return ..$String::primitive /.areturn {.#None} (function (_ expected actual) (text#= (as Text expected) (as Text actual))))) + (_.lifted "RETURN" (primitive_return (is (Primitive java/lang/String) + [#unboxed /type.void + #boxed ..$String + #wrap /.nop + #random ..$String::random + #literal (function.constant /.nop)]) /.return {.#Some ..$String::literal} - (function (_ expected actual) (text#= (:as Text expected) (:as Text actual))))) + (function (_ expected actual) (text#= (as Text expected) (as Text actual))))) ))) (def: branching @@ -1409,20 +1409,20 @@ (do random.monad [expected ..$Long::random dummy ..$Long::random - .let [if! (: (-> (-> Label (Bytecode Any)) (Bytecode Any) (Random Bit)) - (function (_ instruction prelude) - (<| (..bytecode ((!::= java/lang/Long "jvm leq" "jvm long =") expected)) - (do /.monad - [@then /.new_label - @end /.new_label - _ prelude - _ (instruction @then) - _ (..$Long::literal dummy) - _ (/.goto @end) - _ (/.set_label @then) - _ (..$Long::literal expected) - _ (/.set_label @end)] - ..$Long::wrap)))) + .let [if! (is (-> (-> Label (Bytecode Any)) (Bytecode Any) (Random Bit)) + (function (_ instruction prelude) + (<| (..bytecode ((!::= java/lang/Long "jvm leq" "jvm long =") expected)) + (do /.monad + [@then /.new_label + @end /.new_label + _ prelude + _ (instruction @then) + _ (..$Long::literal dummy) + _ (/.goto @end) + _ (/.set_label @then) + _ (..$Long::literal expected) + _ (/.set_label @end)] + ..$Long::wrap)))) comparison_against_zero ($_ _.and (_.lifted "IFEQ" (if! /.ifeq /.iconst_0)) (_.lifted "IFNE" (if! /.ifne /.iconst_1)) @@ -1450,11 +1450,11 @@ (_.lifted "IF_ICMPLE" (if! /.if_icmple (do /.monad [_ (..$Integer::literal lesser)] (..$Integer::literal greater)))) (_.lifted "IF_ICMPGT" (if! /.if_icmpgt (do /.monad [_ (..$Integer::literal greater)] (..$Integer::literal lesser)))) (_.lifted "IF_ICMPGE" (if! /.if_icmpge (do /.monad [_ (..$Integer::literal greater)] (..$Integer::literal lesser))))) - new_object (: (Bytecode Any) - (do /.monad - [_ (/.new ..$Object) - _ /.dup] - (/.invokespecial ..$Object "<init>" (/type.method [(list) (list) /type.void (list)])))) + new_object (is (Bytecode Any) + (do /.monad + [_ (/.new ..$Object) + _ /.dup] + (/.invokespecial ..$Object "<init>" (/type.method [(list) (list) /type.void (list)])))) reference_comparison ($_ _.and (_.lifted "IF_ACMPEQ" (if! /.if_acmpeq (do /.monad [_ new_object] /.dup))) (_.lifted "IF_ACMPNE" (if! /.if_acmpne (do /.monad [_ new_object] new_object))) @@ -1471,21 +1471,21 @@ (do random.monad [expected ..$Long::random dummy ..$Long::random - .let [jump (: (-> (-> Label (Bytecode Any)) (Random Bit)) - (function (_ goto) - (<| (..bytecode ((!::= java/lang/Long "jvm leq" "jvm long =") expected)) - (do /.monad - [@skipped /.new_label - @value /.new_label - @end /.new_label - _ (goto @value) - _ (/.set_label @skipped) - _ (..$Long::literal dummy) - _ (goto @end) - _ (/.set_label @value) - _ (..$Long::literal expected) - _ (/.set_label @end)] - ..$Long::wrap))))]] + .let [jump (is (-> (-> Label (Bytecode Any)) (Random Bit)) + (function (_ goto) + (<| (..bytecode ((!::= java/lang/Long "jvm leq" "jvm long =") expected)) + (do /.monad + [@skipped /.new_label + @value /.new_label + @end /.new_label + _ (goto @value) + _ (/.set_label @skipped) + _ (..$Long::literal dummy) + _ (goto @end) + _ (/.set_label @value) + _ (..$Long::literal expected) + _ (/.set_label @end)] + ..$Long::wrap))))]] ($_ _.and (_.lifted "GOTO" (jump /.goto)) (_.lifted "GOTO_W" (jump /.goto_w))))) @@ -1520,7 +1520,7 @@ random.nat) choice (# ! each (n.% options) random.nat) options (|> random.int - (# ! each (|>> (:as java/lang/Long) ffi.long_to_int ffi.int_to_long (:as Int))) + (# ! each (|>> (as java/lang/Long) ffi.long_to_int ffi.int_to_long (as Int))) (random.set i.hash options) (# ! each set.list)) .let [choice (maybe.trusted (list.item choice options))] @@ -1531,7 +1531,7 @@ [@right /.new_label @wrong /.new_label @return /.new_label - _ (..$Integer::literal (ffi.long_to_int (:as java/lang/Long choice))) + _ (..$Integer::literal (ffi.long_to_int (as java/lang/Long choice))) _ (/.lookupswitch @wrong (list#each (function (_ option) [(|> option /signed.s4 try.trusted) (if (i.= choice option) @right @wrong)]) @@ -1618,11 +1618,11 @@ part3 ..$Long::random part4 ..$Long::random .let [expected ($_ i.+ - (:as Int part0) - (:as Int part1) - (:as Int part2) - (:as Int part3) - (:as Int part4)) + (as Int part0) + (as Int part1) + (as Int part2) + (as Int part3) + (as Int part4)) $Concrete (/type.class concrete_class (list)) $Abstract (/type.class abstract_class (list)) $Interface (/type.class interface_class (list)) @@ -1637,15 +1637,15 @@ virtual_method "virtual_method" static_method "static_method" - method (: (-> Text java/lang/Long (Resource Method)) - (function (_ name value) - (/method.method /method.public - name - #0 method::type - (list) - {.#Some (do /.monad - [_ (..$Long::literal value)] - /.lreturn)}))) + method (is (-> Text java/lang/Long (Resource Method)) + (function (_ name value) + (/method.method /method.public + name + #0 method::type + (list) + {.#Some (do /.monad + [_ (..$Long::literal value)] + /.lreturn)}))) interface_bytecode (|> (/class.class /version.v6_0 ($_ /modifier#composite /class.public /class.abstract /class.interface) (/name.internal interface_class) @@ -1679,11 +1679,11 @@ (sequence.sequence)) try.trusted (format.result /class.writer)) - invoke (: (-> (Type Class) Text (Bytecode Any)) - (function (_ class method) - (do /.monad - [_ /.aload_0] - (/.invokevirtual class method method::type)))) + invoke (is (-> (Type Class) Text (Bytecode Any)) + (function (_ class method) + (do /.monad + [_ /.aload_0] + (/.invokevirtual class method method::type)))) concrete_bytecode (|> (/class.class /version.v6_0 /class.public (/name.internal concrete_class) {.#None} @@ -1736,9 +1736,9 @@ class (io.run! (/loader.load concrete_class loader)) method (try (get_method static_method class)) output (java/lang/reflect/Method::invoke (ffi.null) (ffi.array java/lang/Object 0) method)] - (in (:as Int output))) + (in (as Int output))) {try.#Success actual} - (i.= (:as Int expected) (:as Int actual)) + (i.= (as Int expected) (as Int actual)) {try.#Failure error} false)))) diff --git a/stdlib/source/test/lux/target/lua.lux b/stdlib/source/test/lux/target/lua.lux index 84cf47b3f..471aeb03a 100644 --- a/stdlib/source/test/lux/target/lua.lux +++ b/stdlib/source/test/lux/target/lua.lux @@ -60,16 +60,16 @@ {.#None} true {.#Some _} false))) (_.cover [/.boolean] - (expression (|>> (:as Bit) (bit#= boolean)) + (expression (|>> (as Bit) (bit#= boolean)) (/.boolean boolean))) (_.cover [/.int] - (expression (|>> (:as Int) (i.= int)) + (expression (|>> (as Int) (i.= int)) (/.int int))) (_.cover [/.float] - (expression (|>> (:as Frac) (f.= float)) + (expression (|>> (as Frac) (f.= float)) (/.float float))) (_.cover [/.string] - (expression (|>> (:as Text) (text#= string)) + (expression (|>> (as Text) (text#= string)) (/.string string))) ))) @@ -82,14 +82,14 @@ (~~ (template [</> <lux>] [(_.cover [</>] (let [expected (<lux> left right)] - (expression (|>> (:as Bit) (bit#= expected)) + (expression (|>> (as Bit) (bit#= expected)) (</> (/.boolean left) (/.boolean right)))))] [/.or .or] [/.and .and] )) (_.cover [/.not] - (expression (|>> (:as Bit) (bit#= (not left))) + (expression (|>> (as Bit) (bit#= (not left))) (/.not (/.boolean left)))) )))) @@ -117,7 +117,7 @@ (~~ (template [</> <lux>] [(_.cover [</>] (let [expected (<lux> left right)] - (expression (|>> (:as Int) (i.= expected)) + (expression (|>> (as Int) (i.= expected)) (</> (/.int left) (/.int right)))))] [/.bit_or i64.or] @@ -125,16 +125,16 @@ [/.bit_and i64.and] )) (_.cover [/.opposite] - (expression (|>> (:as Int) (i.= (i.- left +0))) + (expression (|>> (as Int) (i.= (i.- left +0))) (/.opposite (/.int left)))) (_.cover [/.bit_shl] (let [expected (i64.left_shifted shift left)] - (expression (|>> (:as Int) (i.= expected)) + (expression (|>> (as Int) (i.= expected)) (/.bit_shl (/.int (.int shift)) (/.int left))))) (_.cover [/.bit_shr] (let [expected (i64.right_shifted shift left)] - (expression (|>> (:as Int) (i.= expected)) + (expression (|>> (as Int) (i.= expected)) (/.bit_shr (/.int (.int shift)) (/.int left))))) (_.cover [/.//] @@ -142,7 +142,7 @@ (i.= +0 (i.% parameter subject))) (i./ parameter subject) (-- (i./ parameter subject)))] - (expression (|>> (:as Int) (i.= expected)) + (expression (|>> (as Int) (i.= expected)) (/.// (/.int parameter) (/.int subject))))) )))) @@ -156,7 +156,7 @@ (~~ (template [</> <lux> <pre>] [(_.cover [</>] (let [expected (<lux> (<pre> parameter) (<pre> subject))] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (</> (/.float (<pre> parameter)) (/.float (<pre> subject))))))] [/.+ f.+ |>] @@ -169,7 +169,7 @@ (~~ (template [</> <lux>] [(_.cover [</>] (let [expected (<lux> parameter subject)] - (expression (|>> (:as Bit) (bit#= expected)) + (expression (|>> (as Bit) (bit#= expected)) (</> (/.float parameter) (/.float subject)))))] [/.< f.<] @@ -188,7 +188,7 @@ .let [expected (format left right)]] ($_ _.and (_.cover [/.concat] - (expression (|>> (:as Text) (text#= expected)) + (expression (|>> (as Text) (text#= expected)) (|> (/.string left) (/.concat (/.string right))))) ))) @@ -204,15 +204,15 @@ maybe.trusted)]] ($_ _.and (_.cover [/.array /.item] - (and (expression (|>> (:as Frac) (f.= expected)) + (and (expression (|>> (as Frac) (f.= expected)) (/.item (/.int (.int (++ index))) (/.array (list#each /.float items)))) - (expression (|>> (:as Bit)) + (expression (|>> (as Bit)) (|> (/.array (list#each /.float items)) (/.item (/.int (.int (++ size)))) (/.= /.nil))))) (_.cover [/.length] - (expression (|>> (:as Int) (i.= (.int size))) + (expression (|>> (as Int) (i.= (.int size))) (/.length (/.array (list#each /.float items))))) ))) @@ -236,14 +236,14 @@ method (random.ascii/upper 6)] ($_ _.and (_.cover [/.table /.the] - (and (expression (|>> (:as Frac) (f.= expected)) + (and (expression (|>> (as Frac) (f.= expected)) (/.the field (/.table (list [field (/.float expected)])))) - (expression (|>> (:as Bit)) + (expression (|>> (as Bit)) (|> (/.table (list [field (/.float expected)])) (/.the non_field) (/.= /.nil))))) (_.cover [/.do /.function] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (|> ($_ /.then (/.local/1 $table (/.table (list [field (/.float expected)]))) (/.function (/.the method $table) (list $self $arg) @@ -276,30 +276,30 @@ ..test|array ..test|table (_.cover [/.type/1] - (and (expression (|>> (:as Text) (text#= "boolean")) + (and (expression (|>> (as Text) (text#= "boolean")) (/.type/1 (/.boolean boolean))) - (expression (|>> (:as Text) (text#= "number")) + (expression (|>> (as Text) (text#= "number")) (/.type/1 (/.int int))) - (expression (|>> (:as Text) (text#= "number")) + (expression (|>> (as Text) (text#= "number")) (/.type/1 (/.float float))) - (expression (|>> (:as Text) (text#= "string")) + (expression (|>> (as Text) (text#= "string")) (/.type/1 (/.string string))) - (expression (|>> (:as Text) (text#= "nil")) + (expression (|>> (as Text) (text#= "nil")) (/.type/1 /.nil)) - (expression (|>> (:as Text) (text#= "table")) + (expression (|>> (as Text) (text#= "table")) (/.type/1 (/.table (list [string (/.float float)])))) - (expression (|>> (:as Text) (text#= "table")) + (expression (|>> (as Text) (text#= "table")) (/.type/1 (/.array (list (/.boolean boolean) (/.float float) (/.string string))))) )) (_.cover [/.require/1] - (expression (|>> (:as Int) (i.= (i.abs int))) + (expression (|>> (as Int) (i.= (i.abs int))) (|> (/.require/1 (/.string "math")) (/.the "abs") (/.apply (list (/.int int)))))) (_.cover [/.comment] - (expression (|>> (:as Frac) (f.= then)) + (expression (|>> (as Frac) (f.= then)) (/.comment comment (/.float then)))) ))) @@ -326,26 +326,26 @@ $local (/.var local)]] ($_ _.and (_.cover [/.var] - (expression (|>> (:as Frac) (f.= float/0)) + (expression (|>> (as Frac) (f.= float/0)) (|> (/.return $foreign) (/.closure (list $foreign)) (/.apply (list (/.float float/0)))))) (_.cover [/.let] - (expression (|>> (:as Frac) (f.= float/1)) + (expression (|>> (as Frac) (f.= float/1)) (|> ($_ /.then (/.let (list $local) (/.float float/1)) (/.return $local)) (/.closure (list $foreign)) (/.apply (list (/.float float/0)))))) (_.cover [/.local/1] - (expression (|>> (:as Frac) (f.= float/1)) + (expression (|>> (as Frac) (f.= float/1)) (|> ($_ /.then (/.local/1 $local (/.float float/1)) (/.return $local)) (/.closure (list $foreign)) (/.apply (list (/.float float/0)))))) (_.cover [/.local] - (expression (|>> (:as Frac) (f.= float/1)) + (expression (|>> (as Frac) (f.= float/1)) (|> ($_ /.then (/.local (list $local)) (/.set (list $local) (/.float float/1)) @@ -366,27 +366,27 @@ field (random.ascii/upper 10)] ($_ _.and (_.cover [/.set] - (expression (|>> (:as Frac) (f.= (f.+ float/0 float/0))) + (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) (|> ($_ /.then (/.set (list $foreign) (/.+ $foreign $foreign)) (/.return $foreign)) (/.closure (list $foreign)) (/.apply (list (/.float float/0)))))) (_.cover [/.multi] - (and (expression (|>> (:as Frac) (f.= float/0)) + (and (expression (|>> (as Frac) (f.= float/0)) (|> ($_ /.then (/.set (list $arg/0 $arg/1) (/.multi (list (/.float float/0) (/.float float/1)))) (/.return $arg/0)) (/.closure (list)) (/.apply (list)))) - (expression (|>> (:as Frac) (f.= float/1)) + (expression (|>> (as Frac) (f.= float/1)) (|> ($_ /.then (/.set (list $arg/0 $arg/1) (/.multi (list (/.float float/0) (/.float float/1)))) (/.return $arg/1)) (/.closure (list)) (/.apply (list)))))) (_.cover [/.Access] - (and (expression (|>> (:as Frac) (f.= (f.+ float/0 float/0))) + (and (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) (let [@ (/.item (/.int +1) $foreign)] (|> ($_ /.then (/.set (list $foreign) (/.array (list $foreign))) @@ -394,7 +394,7 @@ (/.return @)) (/.closure (list $foreign)) (/.apply (list (/.float float/0)))))) - (expression (|>> (:as Frac) (f.= (f.+ float/0 float/0))) + (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) (let [@ (/.the field $foreign)] (|> ($_ /.then (/.set (list $foreign) (/.table (list [field $foreign]))) @@ -424,7 +424,7 @@ expected_iterations (/.int expected_iterations)]] ($_ _.and (_.cover [/.break] - (let [=for_in (expression (|>> (:as Int) (i.= expected)) + (let [=for_in (expression (|>> (as Int) (i.= expected)) (|> ($_ /.then (/.local/1 $output (/.int +0)) (/.for_in (list $index $input) (/.ipairs/1 (/.array (list.repeated full_iterations $input))) @@ -437,7 +437,7 @@ (/.apply (list (/.int input))))) full_iterations (/.int (.int full_iterations)) - =while (expression (|>> (:as Int) (i.= expected)) + =while (expression (|>> (as Int) (i.= expected)) (|> ($_ /.then (/.local/1 $index (/.int +0)) (/.local/1 $output (/.int +0)) @@ -451,7 +451,7 @@ (/.return $output)) (/.closure (list $input)) (/.apply (list (/.int input))))) - =repeat (expression (|>> (:as Int) (i.= expected)) + =repeat (expression (|>> (as Int) (i.= expected)) (|> ($_ /.then (/.local/1 $index (/.int +0)) (/.local/1 $output (/.int +0)) @@ -465,7 +465,7 @@ (/.return $output)) (/.closure (list $input)) (/.apply (list (/.int input))))) - =for_step (expression (|>> (:as Int) (i.= expected)) + =for_step (expression (|>> (as Int) (i.= expected)) (|> ($_ /.then (/.local/1 $output (/.int +0)) (/.for_step $index (/.int +0) full_iterations (/.int +1) @@ -481,7 +481,7 @@ =for_step =for_in))) (_.cover [/.label /.set_label /.go_to] - (expression (|>> (:as Int) (i.= expected)) + (expression (|>> (as Int) (i.= expected)) (|> ($_ /.then (/.local/1 $index (/.int +0)) (/.local/1 $output (/.int +0)) @@ -507,7 +507,7 @@ expected (i.* (.int iterations) input)]] ($_ _.and (_.cover [/.while] - (expression (|>> (:as Int) (i.= expected)) + (expression (|>> (as Int) (i.= expected)) (|> ($_ /.then (/.local/1 $index (/.int +0)) (/.local/1 $output (/.int +0)) @@ -520,7 +520,7 @@ (/.closure (list $input)) (/.apply (list (/.int input)))))) (_.cover [/.repeat] - (expression (|>> (:as Int) (i.= expected)) + (expression (|>> (as Int) (i.= expected)) (|> ($_ /.then (/.local/1 $index (/.int +0)) (/.local/1 $output (/.int +0)) @@ -533,7 +533,7 @@ (/.closure (list $input)) (/.apply (list (/.int input)))))) (_.cover [/.for_step] - (expression (|>> (:as Int) (i.= expected)) + (expression (|>> (as Int) (i.= expected)) (|> ($_ /.then (/.local/1 $output (/.int +0)) (/.for_step $index (/.int +0) (/.int (.int (-- iterations))) (/.int +1) @@ -542,7 +542,7 @@ (/.closure (list $input)) (/.apply (list (/.int input)))))) (_.cover [/.for_in /.ipairs/1] - (expression (|>> (:as Int) (i.= expected)) + (expression (|>> (as Int) (i.= expected)) (|> ($_ /.then (/.local/1 $output (/.int +0)) (/.for_in (list $index $input) (/.ipairs/1 (/.array (list.repeated iterations $input))) @@ -564,7 +564,7 @@ $outcome (# ! each /.var (random.ascii/lower 11))] ($_ _.and (_.cover [/.pcall/1] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (|> ($_ /.then (/.let (list $verdict $outcome) (/.pcall/1 (/.closure (list) (/.return (/.float expected))))) @@ -574,7 +574,7 @@ (/.closure (list)) (/.apply (list))))) (_.cover [/.error/1] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (|> ($_ /.then (/.let (list $verdict $outcome) (/.pcall/1 (/.closure (list) ($_ /.then @@ -586,7 +586,7 @@ (/.closure (list)) (/.apply (list))))) (_.cover [/.error/2] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (|> ($_ /.then (/.let (list $verdict $outcome) (/.pcall/1 (/.closure (list) ($_ /.then @@ -610,11 +610,11 @@ $class (# ! each /.var (random.ascii/upper 4))] ($_ _.and (_.cover [/.closure /.return] - (expression (|>> (:as Frac) (f.= float/0)) + (expression (|>> (as Frac) (f.= float/0)) (/.apply (list) (/.closure (list) (/.return (/.float float/0)))))) (_.cover [/.local_function] - (expression (|>> (:as Int) .nat (n.= iterations)) + (expression (|>> (as Int) .nat (n.= iterations)) (|> ($_ /.then (/.local_function $self (list $arg/0) (/.if (/.< (/.int (.int iterations)) $arg/0) @@ -632,7 +632,7 @@ $arg/2 (# ! each /.var (random.ascii/lower 12))] (`` ($_ _.and (_.cover [/.apply] - (expression (|>> (:as Frac) (f.= ($_ f.+ float/0 float/1 float/2))) + (expression (|>> (as Frac) (f.= ($_ f.+ float/0 float/1 float/2))) (/.apply (list (/.float float/0) (/.float float/1) (/.float float/2)) @@ -648,14 +648,14 @@ ??? random.bit] ($_ _.and (_.cover [/.if] - (expression (|>> (:as Frac) (f.= (if ??? float/0 float/1))) + (expression (|>> (as Frac) (f.= (if ??? float/0 float/1))) (|> (/.if (/.boolean ???) (/.return (/.float float/0)) (/.return (/.float float/1))) (/.closure (list)) (/.apply (list))))) (_.cover [/.when] - (expression (|>> (:as Frac) (f.= (if ??? float/0 float/1))) + (expression (|>> (as Frac) (f.= (if ??? float/0 float/1))) (|> ($_ /.then (/.when (/.boolean ???) (/.return (/.float float/0))) @@ -689,7 +689,7 @@ $arg/1 (# ! each /.var (random.ascii/lower 11))] (`` ($_ _.and (_.cover [/.statement /.then /.print/1] - (expression (|>> (:as Frac) (f.= float/0)) + (expression (|>> (as Frac) (f.= float/0)) (|> ($_ /.then (/.statement (/.print/1 $arg/0)) (/.return $arg/0)) @@ -713,7 +713,7 @@ ($hash.spec /.hash random)) (_.cover [/.manual] - (expression (|>> (:as Int) (i.= expected)) + (expression (|>> (as Int) (i.= expected)) (/.manual (/.code (/.int expected))))) (_.for [/.Expression] ..test|expression) diff --git a/stdlib/source/test/lux/target/python.lux b/stdlib/source/test/lux/target/python.lux index 2a9bdb68e..bca258d5e 100644 --- a/stdlib/source/test/lux/target/python.lux +++ b/stdlib/source/test/lux/target/python.lux @@ -61,22 +61,22 @@ {.#Some _} false))) (try.else false))) (_.cover [/.bool] - (expression (|>> (:as Bit) (bit#= bool)) + (expression (|>> (as Bit) (bit#= bool)) (/.bool bool))) (_.cover [/.int] - (expression (|>> (:as Int) (i.= int)) + (expression (|>> (as Int) (i.= int)) (/.int int))) ... (_.cover [/.long] - ... (expression (|>> (:as Int) (i.= int)) + ... (expression (|>> (as Int) (i.= int)) ... (/.long int))) (_.cover [/.float] - (expression (|>> (:as Frac) (f.= float)) + (expression (|>> (as Frac) (f.= float)) (/.float float))) (_.cover [/.string] - (expression (|>> (:as Text) (text#= string)) + (expression (|>> (as Text) (text#= string)) (/.string string))) (_.cover [/.unicode] - (expression (|>> (:as Text) (text#= string)) + (expression (|>> (as Text) (text#= string)) (/.unicode string))) ))) @@ -89,14 +89,14 @@ (~~ (template [</> <lux>] [(_.cover [</>] (let [expected (<lux> left right)] - (expression (|>> (:as Bit) (bit#= expected)) + (expression (|>> (as Bit) (bit#= expected)) (</> (/.bool left) (/.bool right)))))] [/.or .or] [/.and .and] )) (_.cover [/.not] - (expression (|>> (:as Bit) (bit#= (not left))) + (expression (|>> (as Bit) (bit#= (not left))) (/.not (/.bool left)))) )))) @@ -110,7 +110,7 @@ (~~ (template [</> <lux> <pre>] [(_.cover [</>] (let [expected (<lux> (<pre> parameter) (<pre> subject))] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (</> (/.float (<pre> parameter)) (/.float (<pre> subject))))))] [/.+ f.+ |>] @@ -123,7 +123,7 @@ (~~ (template [</> <lux>] [(_.cover [</>] (let [expected (<lux> parameter subject)] - (expression (|>> (:as Bit) (bit#= expected)) + (expression (|>> (as Bit) (bit#= expected)) (</> (/.float parameter) (/.float subject)))))] [/.< f.<] @@ -133,10 +133,10 @@ [/.= f.=] )) (_.cover [/.float/1] - (expression (|>> (:as Frac) (f.= subject)) + (expression (|>> (as Frac) (f.= subject)) (/.float/1 (/.string (%.frac subject))))) (_.cover [/.repr/1] - (expression (|>> (:as Text) (text#= (text.replaced "+" "" (%.frac subject)))) + (expression (|>> (as Text) (text#= (text.replaced "+" "" (%.frac subject)))) (/.repr/1 (/.float subject)))) )))) @@ -163,7 +163,7 @@ (~~ (template [</> <lux>] [(_.cover [</>] (let [expected (<lux> left right)] - (expression (|>> (:as Frac) f.int (i.= expected)) + (expression (|>> (as Frac) f.int (i.= expected)) (</> (/.int left) (/.int right)))))] [/.bit_or i64.or] @@ -175,34 +175,34 @@ (let [left (.int shift) right (i.* (.int shift) i16) expected (<lux> left right)] - (expression (|>> (:as Int) (i.= expected)) + (expression (|>> (as Int) (i.= expected)) (</> (/.int left) (/.int right)))))] [/.// i./] )) (_.cover [/.opposite] - (expression (|>> (:as Int) (i.= (i.* -1 left))) + (expression (|>> (as Int) (i.= (i.* -1 left))) (/.opposite (/.int left)))) (_.cover [/.bit_shl] (let [expected (i64.left_shifted shift i16)] - (expression (|>> (:as Frac) f.int (i.= expected)) + (expression (|>> (as Frac) f.int (i.= expected)) (/.bit_shl (/.int (.int shift)) (/.int i16))))) (_.cover [/.bit_shr] (let [expected (i.right_shifted shift i16)] - (expression (|>> (:as Frac) f.int (i.= expected)) + (expression (|>> (as Frac) f.int (i.= expected)) (/.bit_shr (/.int (.int shift)) (/.int i16))))) (_.cover [/.int/1] - (expression (|>> (:as Int) (i.= left)) + (expression (|>> (as Int) (i.= left)) (/.int/1 (/.string (%.int left))))) (_.cover [/.str/1] - (expression (|>> (:as Text) (text#= (text.replaced "+" "" (%.int left)))) + (expression (|>> (as Text) (text#= (text.replaced "+" "" (%.int left)))) (/.str/1 (/.int left)))) (_.cover [/.long] - (or (expression (|>> (:as Bit)) + (or (expression (|>> (as Bit)) ..python_3?) - (expression (|>> (:as Int) (i.= left)) + (expression (|>> (as Int) (i.= left)) (/.long left)))) )))) @@ -214,11 +214,11 @@ ($_ _.and (_.cover [/.chr/1 /.ord/1 /.unichr/1 /.unicode/1] - (and (expression (|>> (:as Int) .nat (n.= expected_code)) + (and (expression (|>> (as Int) .nat (n.= expected_code)) (/.? python_3? (/.ord/1 (/.chr/1 (/.int (.int expected_code)))) (/.unicode/1 (/.unichr/1 (/.int (.int expected_code)))))) - (expression (|>> (:as Text) (text#= expected_char)) + (expression (|>> (as Text) (text#= expected_char)) (/.? python_3? (/.chr/1 (/.ord/1 (/.string expected_char))) (/.unichr/1 (/.unicode/1 (/.string expected_char))))))) @@ -242,20 +242,20 @@ (_.for [/.item] ($_ _.and (_.cover [/.list] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (/.item (/.int (.int index)) (/.list (list#each /.float items))))) (_.cover [/.tuple] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (/.item (/.int (.int index)) (/.tuple (list#each /.float items))))))) (_.cover [/.slice /.len/1] - (expression (|>> (:as Int) (i.= (.int plus))) + (expression (|>> (as Int) (i.= (.int plus))) (|> (/.list (list#each /.float items)) (/.slice from to) /.len/1))) (_.cover [/.slice_from] - (expression (|>> (:as Int) (i.= (.int slice_from|size))) + (expression (|>> (as Int) (i.= (.int slice_from|size))) (|> (/.list (list#each /.float items)) (/.slice_from from) /.len/1))) @@ -272,12 +272,12 @@ dummy (/.string dummy)]] ($_ _.and (_.cover [/.dict] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (/.item field (/.dict (list [field (/.float expected)]))))) (_.cover [/.in?] - (and (expression (|>> (:as Bit) not) + (and (expression (|>> (as Bit) not) (/.in? (/.dict (list)) field)) - (expression (|>> (:as Bit)) + (expression (|>> (as Bit)) (/.in? (/.dict (list [field (/.float expected)])) field)))) ))) @@ -304,27 +304,27 @@ ..test|dict (_.cover [/.?] (let [expected (if test then else)] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (/.? (/.bool test) (/.float then) (/.float else))))) (_.cover [/.comment] - (expression (|>> (:as Frac) (f.= then)) + (expression (|>> (as Frac) (f.= then)) (/.comment comment (/.float then)))) (_.cover [/.__import__/1] (expression (function.constant true) (/.__import__/1 (/.string "math")))) (_.cover [/.do] - (expression (|>> (:as Frac) (f.= (math.ceil float))) + (expression (|>> (as Frac) (f.= (math.ceil float))) (|> (/.__import__/1 (/.string "math")) (/.do "ceil" (list (/.float float)))))) (_.cover [/.is] - (and (expression (|>> (:as Bit)) + (and (expression (|>> (as Bit)) (/.apply/* (list (/.string (format string string))) (/.lambda (list $arg/0) (/.is $arg/0 $arg/0)))) - (expression (|>> (:as Bit) not) + (expression (|>> (as Bit) not) (/.apply/* (list (/.string (format string string)) (/.string string)) (/.lambda (list $arg/0 $arg/1) @@ -342,12 +342,12 @@ $arg/2 (# ! each /.var (random.ascii/lower 12))] ($_ _.and (_.cover [/.lambda] - (expression (|>> (:as Frac) (f.= float/0)) + (expression (|>> (as Frac) (f.= float/0)) (/.apply/* (list) (/.lambda (list) (/.float float/0))))) (_.cover [/.apply/*] - (expression (|>> (:as Frac) (f.= ($_ f.+ float/0 float/1 float/2))) + (expression (|>> (as Frac) (f.= ($_ f.+ float/0 float/1 float/2))) (/.apply/* (list (/.float float/0) (/.float float/1) (/.float float/2)) (/.lambda (list $arg/0 $arg/1 $arg/2) ($_ /.+ $arg/0 $arg/1 $arg/2))))) @@ -370,20 +370,20 @@ $choice (# ! each (|>> %.nat (format "c") /.var) random.nat)] ($_ _.and (_.cover [/.Single /.SVar /.var] - (expression (|>> (:as Frac) (f.= expected/0)) + (expression (|>> (as Frac) (f.= expected/0)) (/.apply/* (list (/.float expected/0)) (/.lambda (list $var) $var)))) (_.for [/.Poly /.PVar] ($_ _.and (_.cover [/.poly] - (expression (|>> (:as Frac) (f.= expected/?)) + (expression (|>> (as Frac) (f.= expected/?)) (/.apply/* (list (/.int (.int poly_choice)) (/.float expected/0) (/.float expected/1)) (/.lambda (list $choice (/.poly $var)) (/.item $choice $var))))) (_.cover [/.splat_poly] - (expression (|>> (:as Frac) (f.= expected/?)) + (expression (|>> (as Frac) (f.= expected/?)) (/.apply/* (list (/.int (.int poly_choice)) (/.splat_poly (/.list (list (/.float expected/0) @@ -394,7 +394,7 @@ (_.for [/.Keyword /.KVar] ($_ _.and (_.cover [/.keyword] - (expression (|>> (:as Nat) (n.= 2)) + (expression (|>> (as Nat) (n.= 2)) (/.apply/* (list keyword_choice (/.splat_keyword (/.dict (list [keyword/0 (/.float expected/0)] @@ -402,7 +402,7 @@ (/.lambda (list $choice (/.keyword $var)) (/.len/1 $var))))) (_.cover [/.splat_keyword] - (expression (|>> (:as Frac) (f.= expected/?)) + (expression (|>> (as Frac) (f.= expected/?)) (/.apply/* (list keyword_choice (/.splat_keyword (/.dict (list [keyword/0 (/.float expected/0)] @@ -439,7 +439,7 @@ random.nat) environment (..dict [])] (exec - ("python exec" (/.code (it (/.var $output))) (:expected environment)) + ("python exec" (/.code (it (/.var $output))) (as_expected environment)) (Dict::get $output environment)))) (def: test|access @@ -452,7 +452,7 @@ ($_ _.and (_.cover [/.item] (`` (and (~~ (template [<seq>] - [(expression (|>> (:as Frac) (f.= expected/0)) + [(expression (|>> (as Frac) (f.= expected/0)) (/.item (/.int +0) (<seq> (list (/.float expected/0)))))] @@ -465,10 +465,10 @@ (/.set (list $var/0) (/.list (list (/.float dummy/0)))) (/.set (list (/.item (/.int +0) $var/0)) (/.float expected/0)) (/.set (list $output) (/.item (/.int +0) $var/0))))) - (:as Frac) + (as Frac) (f.= expected/0)) - (expression (|>> (:as Frac) (f.= expected/0)) + (expression (|>> (as Frac) (f.= expected/0)) (/.item field (/.dict (list [field (/.float expected/0)])))) (|> (..statement (function (_ $output) @@ -476,7 +476,7 @@ (/.set (list $var/0) (/.dict (list [field (/.float dummy/0)]))) (/.set (list (/.item field $var/0)) (/.float expected/0)) (/.set (list $output) (/.item field $var/0))))) - (:as Frac) + (as Frac) (f.= expected/0))))) ))) @@ -497,7 +497,7 @@ ($_ /.then (/.set (list $var/0) (/.float expected/0)) (/.set (list $output) $var/0)))) - (:as Frac) + (as Frac) (f.= expected/0))) (_.cover [/.multi] (`` (and (~~ (template [<var> <value>] @@ -506,7 +506,7 @@ ($_ /.then (/.set (list $var/0 $var/1) (/.multi (list (/.float expected/0) (/.float expected/1)))) (/.set (list $output) <var>)))) - (:as Frac) + (as Frac) (f.= <value>))] [$var/0 expected/0] @@ -519,7 +519,7 @@ (/.set (list $var/0) (/.list (list (/.float dummy/0) (/.float expected/0)))) (/.delete (/.item (/.int +0) $var/0)) (/.set (list $output) (/.item (/.int +0) $var/0))))) - (:as Frac) + (as Frac) (f.= expected/0)) (|> (..statement (function (_ $output) @@ -527,7 +527,7 @@ (/.set (list $var/0) (/.list (list (/.float dummy/0) (/.float expected/0)))) (/.delete (/.slice (/.int +0) (/.int +1) $var/0)) (/.set (list $output) (/.item (/.int +0) $var/0))))) - (:as Frac) + (as Frac) (f.= expected/0)) (|> (..statement (function (_ $output) @@ -536,7 +536,7 @@ (/.delete (/.slice_from (/.int +0) $var/0)) (/.statement (/.do "append" (list (/.float expected/0)) $var/0)) (/.set (list $output) (/.item (/.int +0) $var/0))))) - (:as Frac) + (as Frac) (f.= expected/0)) (|> (..statement (function (_ $output) @@ -544,7 +544,7 @@ (/.set (list $var/0) (/.dict (list [field/0 (/.float dummy/0)]))) (/.delete (/.item field/0 $var/0)) (/.set (list $output) (/.in? $var/0 field/0))))) - (:as Bit) + (as Bit) not) (|> (..statement (function (_ $output) @@ -553,7 +553,7 @@ (/.delete $var/0) (/.set (list $output) (/.or (/.in? /.locals/0 (/.string (/.code $var/0))) (/.in? /.globals/0 (/.string (/.code $var/0)))))))) - (:as Bit) + (as Bit) not) )) (_.cover [/.globals/0] @@ -567,7 +567,7 @@ (/.set (list $var/0) (/.float dummy/0)) (/.set (list $output) (/.and $output (/.in? /.globals/0 (/.string (/.code $var/0)))))))) - (:as Bit))) + (as Bit))) (_.cover [/.locals/0] (|> (..statement (function (_ $output) @@ -579,14 +579,14 @@ (/.set (list $var/0) (/.float dummy/0)) (/.set (list $output) (/.and $output (/.in? /.locals/0 (/.string (/.code $var/0)))))))) - (:as Bit))) + (as Bit))) (_.cover [/.import] (|> (..statement (function (_ $output) ($_ /.then (/.import "math") (/.set (list $output) (/.in? /.globals/0 (/.string "math")))))) - (:as Bit))) + (as Bit))) (_.for [/.Access] ..test|access) ))) @@ -620,7 +620,7 @@ (list [/.#classes (list "Exception") /.#exception $ex /.#handler (/.set (list $output) (/.float expected))])))) - (:as Frac) + (as Frac) (f.= expected)) (case (try (..statement (function (_ $output) @@ -661,7 +661,7 @@ $iteration)) ) {.#None})))) - (:as Nat) + (as Nat) (n.= expected)) (|> (..statement (function (_ $output) @@ -676,7 +676,7 @@ $iteration)) ) {.#Some (/.set (list $output) $temp)})))) - (:as Nat) + (as Nat) (n.= expected)))) (_.cover [/.for_in] (|> (..statement @@ -687,7 +687,7 @@ (/.list (list.repeated factor (/.int (.int base)))) (/.set (list $output) (/.+ $iteration $output)))))) - (:as Nat) + (as Nat) (n.= expected))) (_.cover [/.pass] (|> (..statement @@ -704,7 +704,7 @@ $output)) /.pass)) {.#None})))) - (:as Nat) + (as Nat) (n.= expected))) (_.cover [/.continue] (|> (..statement @@ -721,7 +721,7 @@ $output)) /.continue)) {.#None})))) - (:as Nat) + (as Nat) (n.= expected))) (_.cover [/.break] (|> (..statement @@ -738,7 +738,7 @@ (/.set (list $output) (/.+ (/.int (.int base)) $output)))) {.#None})))) - (:as Nat) + (as Nat) (n.= expected))) ))) @@ -760,7 +760,7 @@ (/.def $def (list $input/0) (/.return $input/0)) (/.set (list $output) (/.apply/* (list (/.float expected/0)) $def))))) - (:as Frac) + (as Frac) (f.= expected/0))) (_.cover [/.if] (|> (..statement @@ -771,7 +771,7 @@ (/.return (/.float then)) (/.return (/.float else)))) (/.set (list $output) (/.apply/* (list) $def))))) - (:as Frac) + (as Frac) (f.= expected/?))) (_.cover [/.when /.then] (|> (..statement @@ -783,7 +783,7 @@ (/.return (/.float then))) (/.return (/.float else)))) (/.set (list $output) (/.apply/* (list) $def))))) - (:as Frac) + (as Frac) (f.= expected/?))) (_.cover [/.statement] (|> (..statement @@ -794,14 +794,14 @@ (/.statement (/.+ (/.float expected/0) (/.float expected/0))) (/.return (/.float expected/0)))) (/.set (list $output) (/.apply/* (list) $def))))) - (:as Frac) + (as Frac) (f.= expected/0))) (_.cover [/.exec] (|> (..statement (function (_ $output) (/.exec {.#Some /.globals/0} (/.string (/.code (/.set (list $output) (/.float expected/0))))))) - (:as Frac) + (as Frac) (f.= expected/0))) ..test|exception (_.for [/.Location] @@ -833,7 +833,7 @@ (_.cover [/.code /.manual] (|> (/.manual (/.code expected)) - (: /.Expression) + (is /.Expression) (/#= expected))) (_.for [/.Expression] ..test|expression) diff --git a/stdlib/source/test/lux/target/ruby.lux b/stdlib/source/test/lux/target/ruby.lux index 58cf47c7b..603cded95 100644 --- a/stdlib/source/test/lux/target/ruby.lux +++ b/stdlib/source/test/lux/target/ruby.lux @@ -68,19 +68,19 @@ (_.cover [/.nil] (..nil /.nil)) (_.cover [/.bool] - (expression (|>> (:as Bit) (bit#= bool)) + (expression (|>> (as Bit) (bit#= bool)) (/.bool bool))) (_.cover [/.int] - (expression (|>> (:as Int) (i.= int)) + (expression (|>> (as Int) (i.= int)) (/.int int))) (_.cover [/.float] - (expression (|>> (:as Frac) (f.= float)) + (expression (|>> (as Frac) (f.= float)) (/.float float))) (_.cover [/.string] - (expression (|>> (:as Text) (text#= string)) + (expression (|>> (as Text) (text#= string)) (/.string string))) (_.cover [/.symbol] - (expression (|>> (:as Text) (text#= string)) + (expression (|>> (as Text) (text#= string)) (/.do "id2name" (list) {.#None} (/.symbol string)))) ))) @@ -93,14 +93,14 @@ (~~ (template [</> <lux>] [(_.cover [</>] (let [expected (<lux> left right)] - (expression (|>> (:as Bit) (bit#= expected)) + (expression (|>> (as Bit) (bit#= expected)) (</> (/.bool left) (/.bool right)))))] [/.or .or] [/.and .and] )) (_.cover [/.not] - (expression (|>> (:as Bit) (bit#= (not left))) + (expression (|>> (as Bit) (bit#= (not left))) (/.not (/.bool left)))) )))) @@ -114,7 +114,7 @@ (~~ (template [</> <lux> <pre>] [(_.cover [</>] (let [expected (<lux> (<pre> parameter) (<pre> subject))] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (</> (/.float (<pre> parameter)) (/.float (<pre> subject))))))] [/.+ f.+ |>] @@ -127,7 +127,7 @@ (~~ (template [</> <lux>] [(_.cover [</>] (let [expected (<lux> parameter subject)] - (expression (|>> (:as Bit) (bit#= expected)) + (expression (|>> (as Bit) (bit#= expected)) (</> (/.float parameter) (/.float subject)))))] [/.< f.<] @@ -154,7 +154,7 @@ (~~ (template [</> <lux>] [(_.cover [</>] (let [expected (<lux> left right)] - (expression (|>> (:as Frac) f.int (i.= expected)) + (expression (|>> (as Frac) f.int (i.= expected)) (</> (/.int left) (/.int right)))))] [/.bit_or i64.or] @@ -162,19 +162,19 @@ [/.bit_and i64.and] )) (_.cover [/.bit_not] - (expression (|>> (:as Int) (i.= (i64.not left))) + (expression (|>> (as Int) (i.= (i64.not left))) (/.bit_not (/.int left)))) (_.cover [/.opposite] - (expression (|>> (:as Int) (i.= (i.* -1 left))) + (expression (|>> (as Int) (i.= (i.* -1 left))) (/.opposite (/.int left)))) (_.cover [/.bit_shl] (let [expected (i64.left_shifted shift i16)] - (expression (|>> (:as Frac) f.int (i.= expected)) + (expression (|>> (as Frac) f.int (i.= expected)) (/.bit_shl (/.int (.int shift)) (/.int i16))))) (_.cover [/.bit_shr] (let [expected (i.right_shifted shift i16)] - (expression (|>> (:as Frac) f.int (i.= expected)) + (expression (|>> (as Frac) f.int (i.= expected)) (/.bit_shr (/.int (.int shift)) (/.int i16))))) )))) @@ -194,15 +194,15 @@ from (/.int (.int from))]] ($_ _.and (_.cover [/.array /.item] - (and (expression (|>> (:as Frac) (f.= expected)) + (and (expression (|>> (as Frac) (f.= expected)) (/.item (/.int (.int index)) (/.array (list#each /.float items)))) - (expression (|>> (:as Bit)) + (expression (|>> (as Bit)) (|> (/.array (list#each /.float items)) (/.item (/.int (.int size))) (/.= /.nil))))) (_.cover [/.array_range] - (expression (|>> (:as Int) (i.= (.int (++ plus)))) + (expression (|>> (as Int) (i.= (.int (++ plus)))) (|> (/.array (list#each /.float items)) (/.array_range from to) (/.the "length")))) @@ -219,9 +219,9 @@ dummy (/.string dummy)]] ($_ _.and (_.cover [/.hash] - (and (expression (|>> (:as Frac) (f.= expected)) + (and (expression (|>> (as Frac) (f.= expected)) (/.item field (/.hash (list [field (/.float expected)])))) - (expression (|>> (:as Bit)) + (expression (|>> (as Bit)) (|> (/.hash (list [field (/.float expected)])) (/.item dummy) (/.= /.nil))))) @@ -251,18 +251,18 @@ (/.return (/.+ $arg/0 $arg/0)))]] ($_ _.and (_.cover [/.the] - (expression (|>> (:as Int) (i.= (.int size))) + (expression (|>> (as Int) (i.= (.int size))) (|> (/.array (list#each /.float items)) (/.the "length")))) (_.cover [/.do] (expression (let [expected (|> items (list.item index) (maybe.else f.not_a_number))] - (|>> (:as Frac) (f.= expected))) + (|>> (as Frac) (f.= expected))) (|> (/.array (list#each /.float items)) (/.do "at" (list (/.int (.int index))) {.#None})))) (_.cover [/.class] - (expression (|>> (:as Frac) (f.= (f.+ single single))) + (expression (|>> (as Frac) (f.= (f.+ single single))) (|> ($_ /.then (/.set (list $class) (/.class [/.#parameters (list) /.#body double])) @@ -272,7 +272,7 @@ [(list)] (/.lambda {.#None}) (/.apply_lambda/* (list))))) (_.cover [/.new /.initialize] - (expression (|>> (:as Frac) (f.= single)) + (expression (|>> (as Frac) (f.= single)) (|> ($_ /.then (/.set (list $class) (/.class [/.#parameters (list) /.#body ($_ /.then @@ -287,7 +287,7 @@ [(list)] (/.lambda {.#None}) (/.apply_lambda/* (list))))) (_.cover [/.alias_method/2] - (expression (|>> (:as Frac) (f.= (f.+ single single))) + (expression (|>> (as Frac) (f.= (f.+ single single))) (|> ($_ /.then (/.set (list $class) (/.class [/.#parameters (list) /.#body ($_ /.then @@ -302,7 +302,7 @@ (_.for [/.module] ($_ _.and (_.cover [/.include/1] - (expression (|>> (:as Frac) (f.= (f.+ single single))) + (expression (|>> (as Frac) (f.= (f.+ single single))) (|> ($_ /.then (/.set (list $class) (/.module [/.#parameters (list) /.#body double])) @@ -314,7 +314,7 @@ [(list)] (/.lambda {.#None}) (/.apply_lambda/* (list))))) (_.cover [/.extend/1] - (expression (|>> (:as Frac) (f.= (f.+ single single))) + (expression (|>> (as Frac) (f.= (f.+ single single))) (|> ($_ /.then (/.set (list $class) (/.module [/.#parameters (list) /.#body double])) @@ -340,7 +340,7 @@ (_.for [/.stdout] ($_ _.and (_.cover [/.print/1] - (expression (|>> (:as Text) (text#= expected)) + (expression (|>> (as Text) (text#= expected)) (|> ($_ /.then (/.statement (/.require/1 (/.string "stringio"))) (/.set (list $old) /.stdout) @@ -353,7 +353,7 @@ [(list)] (/.lambda {.#None}) (/.apply_lambda/* (list))))) (_.cover [/.print/2] - (expression (|>> (:as Text) (text#= expected)) + (expression (|>> (as Text) (text#= expected)) (|> ($_ /.then (/.statement (/.require/1 (/.string "stringio"))) (/.set (list $old) /.stdout) @@ -368,7 +368,7 @@ (_.for [/.stdin] ($_ _.and (_.cover [/.gets/0] - (expression (|>> (:as Text) (text#= (format left text.\n))) + (expression (|>> (as Text) (text#= (format left text.\n))) (|> ($_ /.then (/.statement (/.require/1 (/.string "stringio"))) (/.set (list $old) /.stdin) @@ -380,7 +380,7 @@ [(list)] (/.lambda {.#None}) (/.apply_lambda/* (list))))) (_.cover [/.last_string_read] - (expression (|>> (:as Text) (text#= (format right text.\n))) + (expression (|>> (as Text) (text#= (format right text.\n))) (|> ($_ /.then (/.statement (/.require/1 (/.string "stringio"))) (/.set (list $old) /.stdin) @@ -392,7 +392,7 @@ [(list)] (/.lambda {.#None}) (/.apply_lambda/* (list))))) (_.cover [/.last_line_number_read] - (expression (|>> (:as Nat) (n.= 2)) + (expression (|>> (as Nat) (n.= 2)) /.last_line_number_read)) )) ))) @@ -419,12 +419,12 @@ ..test|io (_.cover [/.?] (let [expected (if test then else)] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (/.? (/.bool test) (/.float then) (/.float else))))) (_.cover [/.comment] - (expression (|>> (:as Frac) (f.= then)) + (expression (|>> (as Frac) (f.= then)) (/.comment comment (/.float then)))) ))) @@ -437,7 +437,7 @@ pattern (# ! each /.string (random.ascii/lower 11))] ($_ _.and (_.cover [/.global] - (expression (|>> (:as Text) (text#= "global-variable")) + (expression (|>> (as Text) (text#= "global-variable")) (|> ($_ /.then (/.set (list $global) (/.float float/0)) (/.return (/.defined?/1 $global))) @@ -445,26 +445,26 @@ (/.apply_lambda/* (list))))) (_.cover [/.script_name] (expression (let [file (format (# file.default separator) packager.main_file)] - (|>> (:as Text) + (|>> (as Text) (text.ends_with? file))) /.script_name)) (_.cover [/.input_record_separator] - (expression (|>> (:as Text) + (expression (|>> (as Text) (text#= text.\n)) /.input_record_separator)) (_.cover [/.output_record_separator] (..nil /.output_record_separator)) (_.cover [/.process_id] - (expression (|>> (:as Nat) (n.= 0) not) + (expression (|>> (as Nat) (n.= 0) not) /.process_id)) (_.cover [/.case_insensitivity_flag] - (expression (|>> (:as Bit) (bit#= false)) + (expression (|>> (as Bit) (bit#= false)) /.case_insensitivity_flag)) (_.cover [/.command_line_arguments] - (expression (|>> (:as Int) (i.= +0)) + (expression (|>> (as Int) (i.= +0)) (/.the "length" /.command_line_arguments))) (_.cover [/.last_string_matched] - (expression (|>> (:as Bit)) + (expression (|>> (as Bit)) (|> ($_ /.then (/.statement (|> (/.manual "Regexp") @@ -474,7 +474,7 @@ [(list)] (/.lambda {.#None}) (/.apply_lambda/* (list))))) (_.cover [/.last_regexp_match] - (expression (|>> (:as Bit)) + (expression (|>> (as Bit)) (|> (/.return (|> (/.manual "Regexp") (/.new (list pattern) {.#None}) (/.do "match" (list pattern) {.#None}) @@ -490,12 +490,12 @@ $foreign (# ! each /.local (random.ascii/lower 10))] ($_ _.and (_.cover [/.local] - (expression (|>> (:as Frac) (f.= (f.+ float/0 float/0))) + (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) (|> (/.return (/.+ $foreign $foreign)) [(list $foreign)] (/.lambda {.#None}) (/.apply_lambda/* (list (/.float float/0)))))) (_.cover [/.set] - (expression (|>> (:as Frac) (f.= (f.+ float/0 float/0))) + (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) (|> ($_ /.then (/.set (list $foreign) (/.float float/0)) (/.return (/.+ $foreign $foreign))) @@ -518,7 +518,7 @@ random.nat)] ($_ _.and (_.cover [/.instance] - (expression (|>> (:as Frac) (f.= float/0)) + (expression (|>> (as Frac) (f.= float/0)) (|> ($_ /.then (/.set (list $class) (/.class [/.#parameters (list) /.#body ($_ /.then @@ -533,7 +533,7 @@ [(list)] (/.lambda {.#None}) (/.apply_lambda/* (list))))) (_.cover [/.attr_reader/*] - (expression (|>> (:as Frac) (f.= float/0)) + (expression (|>> (as Frac) (f.= float/0)) (|> ($_ /.then (/.set (list $class) (/.class [/.#parameters (list) /.#body ($_ /.then @@ -547,7 +547,7 @@ [(list)] (/.lambda {.#None}) (/.apply_lambda/* (list))))) (_.cover [/.attr_writer/*] - (expression (|>> (:as Frac) (f.= float/0)) + (expression (|>> (as Frac) (f.= float/0)) (|> ($_ /.then (/.set (list $class) (/.class [/.#parameters (list) /.#body ($_ /.then @@ -563,7 +563,7 @@ [(list)] (/.lambda {.#None}) (/.apply_lambda/* (list))))) (_.cover [/.attr_accessor/*] - (expression (|>> (:as Frac) (f.= float/0)) + (expression (|>> (as Frac) (f.= float/0)) (|> ($_ /.then (/.set (list $class) (/.class [/.#parameters (list) /.#body (/.attr_accessor/* (list instance))])) @@ -590,7 +590,7 @@ random.nat)] ($_ _.and (_.cover [/.static /.class_variable_set /.class_variable_get] - (expression (|>> (:as Int) (i.= int/0)) + (expression (|>> (as Int) (i.= int/0)) (|> ($_ /.then (/.set (list $class) (/.class [/.#parameters (list) /.#body (/.function $method (list) @@ -616,18 +616,18 @@ (<| (_.for [/.LVar*]) ($_ _.and (_.cover [/.variadic] - (expression (|>> (:as Int) .nat (n.= arity)) + (expression (|>> (as Int) .nat (n.= arity)) (|> (/.return (/.the "length" $inputs)) [(list (/.variadic $inputs))] (/.lambda {.#None}) (/.apply_lambda/* vals)))) (_.cover [/.splat] - (expression (|>> (:as Int) .nat (n.= arity)) + (expression (|>> (as Int) .nat (n.= arity)) (|> (/.return (/.the "length" (/.array (list (/.splat $inputs))))) [(list (/.variadic $inputs))] (/.lambda {.#None}) (/.apply_lambda/* vals)))))) (<| (_.for [/.LVar**]) (_.cover [/.variadic_kv /.double_splat] - (expression (|>> (:as Int) .nat (n.= arity)) + (expression (|>> (as Int) .nat (n.= arity)) (|> (/.return (/.the "length" $inputs)) [(list (/.variadic_kv $inputs))] (/.lambda {.#None}) (/.apply_lambda/* (list (/.double_splat (/.hash (list.zipped/2 keys vals))))))))) @@ -642,10 +642,10 @@ $constant (# ! each /.constant (random.ascii/lower 10))] ($_ _.and (_.cover [/.defined?/1] - (and (expression (|>> (:as Bit)) + (and (expression (|>> (as Bit)) (|> (/.defined?/1 $foreign) (/.= /.nil))) - (expression (|>> (:as Text) (text#= "local-variable")) + (expression (|>> (as Text) (text#= "local-variable")) (|> ($_ /.then (/.set (list $foreign) (/.float float/0)) (/.return (/.defined?/1 $foreign))) @@ -653,7 +653,7 @@ (/.apply_lambda/* (list)))))) (_.for [/.CVar] (_.cover [/.constant] - (expression (|>> (:as Text) (text#= "constant")) + (expression (|>> (as Text) (text#= "constant")) (|> ($_ /.then (/.set (list $constant) (/.float float/0)) (/.return (/.defined?/1 $constant))) @@ -680,7 +680,7 @@ (<| (_.for [/.Var]) ..test|var) (_.cover [/.Access] - (and (expression (|>> (:as Frac) (f.= (f.+ float/0 float/0))) + (and (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) (let [@ (/.item (/.int +0) $foreign)] (|> ($_ /.then (/.set (list $foreign) (/.array (list $foreign))) @@ -688,7 +688,7 @@ (/.return @)) [(list $foreign)] (/.lambda {.#None}) (/.apply_lambda/* (list (/.float float/0)))))) - (expression (|>> (:as Frac) (f.= (f.+ float/0 float/0))) + (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) (let [@ (/.item field $foreign)] (|> ($_ /.then (/.set (list $foreign) (/.hash (list [field $foreign]))) @@ -731,7 +731,7 @@ ($_ _.and (_.cover [/.break] (let [expected (i.* (.int expected_inner_iterations) input)] - (expression (|>> (:as Frac) f.int (i.= expected)) + (expression (|>> (as Frac) f.int (i.= expected)) (|> ($_ /.then (/.set (list $inner_index) (/.int +0)) (/.set (list $output) (/.int +0)) @@ -747,7 +747,7 @@ (/.apply_lambda/* (list (/.int input))))))) (_.cover [/.next] (let [expected (i.* (.int (n.- expected_inner_iterations full_inner_iterations)) input)] - (expression (|>> (:as Frac) f.int (i.= expected)) + (expression (|>> (as Frac) f.int (i.= expected)) (|> ($_ /.then (/.set (list $inner_index) (/.int +0)) (/.set (list $output) (/.int +0)) @@ -763,7 +763,7 @@ (/.apply_lambda/* (list (/.int input))))))) (_.cover [/.redo] (let [expected (i.* (.int (n.- expected_inner_iterations full_inner_iterations)) input)] - (expression (|>> (:as Frac) f.int (i.= expected)) + (expression (|>> (as Frac) f.int (i.= expected)) (|> ($_ /.then (/.set (list $inner_index) (/.int +0)) (/.set (list $output) (/.int +0)) @@ -790,7 +790,7 @@ expected (i.* (.int iterations) input)]] ($_ _.and (_.cover [/.while] - (expression (|>> (:as Int) (i.= expected)) + (expression (|>> (as Int) (i.= expected)) (|> ($_ /.then (/.set (list $index) (/.int +0)) (/.set (list $output) (/.int +0)) @@ -803,7 +803,7 @@ [(list $input)] (/.lambda {.#None}) (/.apply_lambda/* (list (/.int input)))))) (_.cover [/.for_in] - (expression (|>> (:as Int) (i.= expected)) + (expression (|>> (as Int) (i.= expected)) (|> ($_ /.then (/.set (list $output) (/.int +0)) (/.for_in $index (/.array (list.repeated iterations (/.int input))) @@ -835,13 +835,13 @@ dummy_tag (/.int dummy_tag)]] ($_ _.and (_.cover [/.begin] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (|> (/.begin (/.return (/.float expected)) (list [(list) $ex (/.return (/.float dummy))])) [(list)] (/.lambda {.#None}) (/.apply_lambda/* (list))))) (_.cover [/.Rescue /.throw/1] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (|> (/.begin ($_ /.then (/.throw/1 (/.string error)) (/.return (/.float dummy))) @@ -849,7 +849,7 @@ [(list)] (/.lambda {.#None}) (/.apply_lambda/* (list))))) (_.cover [/.raise] - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (|> (/.begin ($_ /.then (/.statement (/.raise (/.string error))) (/.return (/.float dummy))) @@ -857,20 +857,20 @@ [(list)] (/.lambda {.#None}) (/.apply_lambda/* (list))))) (_.cover [/.catch /.throw/2] - (and (expression (|>> (:as Frac) (f.= expected)) + (and (expression (|>> (as Frac) (f.= expected)) (<| (/.apply_lambda/* (list)) (/.lambda {.#None}) [(list)] /.return (/.catch expected_tag) [(list)] (/.throw/2 expected_tag (/.float expected)))) - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (<| (/.apply_lambda/* (list)) (/.lambda {.#None}) [(list)] /.return (/.catch expected_tag) [(list)] /.statement (/.catch dummy_tag) [(list)] (/.throw/2 expected_tag (/.float expected)))) - (expression (|>> (:as Frac) (f.= expected)) + (expression (|>> (as Frac) (f.= expected)) (<| (/.apply_lambda/* (list)) (/.lambda {.#None}) [(list)] /.return @@ -878,7 +878,7 @@ /.statement (/.catch expected_tag) [(list)] (/.throw/2 expected_tag (/.float expected)))))) (_.cover [/.latest_error_message] - (expression (|>> (:as Text) (text#= error)) + (expression (|>> (as Text) (text#= error)) (|> (/.begin ($_ /.then (/.statement (/.raise (/.string error))) (/.return (/.float dummy))) @@ -890,12 +890,12 @@ [(list)] (/.lambda {.#None}) (/.apply_lambda/* (list)) ..nil) - (expression (|>> (:as Bit) (bit#= true)) + (expression (|>> (as Bit) (bit#= true)) (|> (/.begin ($_ /.then (/.statement (/.raise (/.string error))) (/.return (/.float dummy))) (list [(list) $ex (/.return ($_ /.and - (/.do "kind_of?" (list (: /.CVar (/.manual "Array"))) {.#None} /.latest_error_location) + (/.do "kind_of?" (list (is /.CVar (/.manual "Array"))) {.#None} /.latest_error_location) (/.> (/.int +0) (/.the "length" /.latest_error_location))))])) [(list)] (/.lambda {.#None}) (/.apply_lambda/* (list)))))) @@ -917,23 +917,23 @@ $arg/2 (# ! each /.local (random.ascii/lower 12))] ($_ _.and (_.cover [/.lambda /.return] - (and (expression (|>> (:as Frac) (f.= float/0)) + (and (expression (|>> (as Frac) (f.= float/0)) (|> (/.return (/.float float/0)) [(list)] (/.lambda {.#None}) (/.apply_lambda/* (list)))) - (expression (|>> (:as Frac) f.nat (n.= iterations)) + (expression (|>> (as Frac) f.nat (n.= iterations)) (|> (/.return (/.? (/.< (/.int (.int iterations)) $arg/0) (/.apply_lambda/* (list (/.+ (/.int +1) $arg/0)) $self) $arg/0)) [(list $arg/0)] (/.lambda {.#Some $self}) (/.apply_lambda/* (list (/.int +0))))))) (_.cover [/.apply_lambda/*] - (expression (|>> (:as Frac) (f.= ($_ f.+ float/0 float/1 float/2))) + (expression (|>> (as Frac) (f.= ($_ f.+ float/0 float/1 float/2))) (|> (/.return ($_ /.+ $arg/0 $arg/1 $arg/2)) [(list $arg/0 $arg/1 $arg/2)] (/.lambda {.#None}) (/.apply_lambda/* (list (/.float float/0) (/.float float/1) (/.float float/2)))))) (_.cover [/.function] - (expression (|>> (:as Frac) f.nat (n.= iterations)) + (expression (|>> (as Frac) f.nat (n.= iterations)) (|> ($_ /.then (/.function $self (list $arg/0) (/.return (/.? (/.< (/.int (.int iterations)) $arg/0) @@ -943,7 +943,7 @@ [(list)] (/.lambda {.#None}) (/.apply_lambda/* (list))))) (_.cover [/.apply/*] - (expression (|>> (:as Frac) (f.= ($_ f.+ float/0 float/1 float/2))) + (expression (|>> (as Frac) (f.= ($_ f.+ float/0 float/1 float/2))) (|> ($_ /.then (/.function $self (list $arg/0 $arg/1 $arg/2) (/.return ($_ /.+ $arg/0 $arg/1 $arg/2))) @@ -970,14 +970,14 @@ ??? random.bit] ($_ _.and (_.cover [/.if] - (expression (|>> (:as Frac) (f.= (if ??? float/0 float/1))) + (expression (|>> (as Frac) (f.= (if ??? float/0 float/1))) (|> (/.if (/.bool ???) (/.return (/.float float/0)) (/.return (/.float float/1))) [(list)] (/.lambda {.#None}) (/.apply_lambda/* (list))))) (_.cover [/.when] - (expression (|>> (:as Frac) (f.= (if ??? float/0 float/1))) + (expression (|>> (as Frac) (f.= (if ??? float/0 float/1))) (|> ($_ /.then (/.when (/.bool ???) (/.return (/.float float/0))) @@ -999,22 +999,22 @@ random.int)] ($_ _.and (_.cover [/.statement] - (expression (|>> (:as Frac) (f.= float/0)) + (expression (|>> (as Frac) (f.= float/0)) (|> ($_ /.then (/.statement (/.+ $arg/0 $arg/0)) (/.return $arg/0)) [(list $arg/0)] (/.lambda {.#None}) (/.apply_lambda/* (list (/.float float/0)))))) (_.cover [/.then] - (expression (|>> (:as Frac) (f.= float/0)) + (expression (|>> (as Frac) (f.= float/0)) (|> ($_ /.then (/.return $arg/0) (/.return $arg/1)) [(list $arg/0 $arg/1)] (/.lambda {.#None}) (/.apply_lambda/* (list (/.float float/0) (/.float float/1)))))) (_.cover [/.require/1] - (let [$JSON (: /.CVar (/.manual "JSON"))] - (expression (|>> (:as Text) (text#= expected)) + (let [$JSON (is /.CVar (/.manual "JSON"))] + (expression (|>> (as Text) (text#= expected)) (|> ($_ /.then (/.statement (/.require/1 (/.string "json"))) (/.return (let [json (/.do "parse" (list $arg/0) {.#None} $JSON)] @@ -1030,13 +1030,13 @@ (def: random_expression (Random /.Expression) - (let [literal (: (Random /.Literal) - ($_ random.either - (random#each /.bool random.bit) - (random#each /.float random.frac) - (random#each /.int random.int) - (random#each /.string (random.ascii/lower 5)) - ))] + (let [literal (is (Random /.Literal) + ($_ random.either + (random#each /.bool random.bit) + (random#each /.float random.frac) + (random#each /.int random.int) + (random#each /.string (random.ascii/lower 5)) + ))] ($_ random.either literal ))) @@ -1053,7 +1053,7 @@ (_.cover [/.code /.manual] (|> (/.manual (/.code expected)) - (: /.Expression) + (is /.Expression) (/#= expected))) (_.for [/.Expression] ..test|expression) diff --git a/stdlib/source/test/lux/test.lux b/stdlib/source/test/lux/test.lux index 4e9638e6d..3e3c8e268 100644 --- a/stdlib/source/test/lux/test.lux +++ b/stdlib/source/test/lux/test.lux @@ -66,8 +66,8 @@ /.Test (do [! random.monad] [seed random.nat - .let [[read write] (: [(async.Async Nat) (async.Resolver Nat)] - (async.async []))] + .let [[read write] (is [(async.Async Nat) (async.Resolver Nat)] + (async.async []))] pre (<| (/.seed seed) (do ! [sample random.nat @@ -101,8 +101,8 @@ (n.= 1 (the /.#failures tally))))))) (do [! random.monad] [expected (# ! each (|>> (n.% 10) ++) random.nat) - .let [counter (: (Atom Nat) - (atom.atom 0))] + .let [counter (is (Atom Nat) + (atom.atom 0))] times_assertion (<| (/.times expected) (do ! [_ (in []) @@ -122,11 +122,11 @@ ($_ /.and (do [! random.monad] [expected (# ! each (|>> (n.% 10) ++) random.nat) - .let [counter (: (Atom Nat) - (atom.atom 0))] + .let [counter (is (Atom Nat) + (atom.atom 0))] assertion (<| /.in_parallel (list.repeated expected) - (: /.Test) + (is /.Test) (do ! [_ (in []) .let [_ (io.run! (atom.update! ++ counter))]] @@ -140,11 +140,11 @@ (n.= 0 (the /.#failures tally))))))) (do [! random.monad] [expected (# ! each (|>> (n.% 10) ++) random.nat) - .let [counter (: (Atom Nat) - (atom.atom 0))] + .let [counter (is (Atom Nat) + (atom.atom 0))] assertion (<| /.in_parallel (list.repeated expected) - (: /.Test) + (is /.Test) (do ! [_ (in []) .let [_ (undefined) diff --git a/stdlib/source/test/lux/time/instant.lux b/stdlib/source/test/lux/time/instant.lux index 12f2ca7c3..77d6e0a1f 100644 --- a/stdlib/source/test/lux/time/instant.lux +++ b/stdlib/source/test/lux/time/instant.lux @@ -69,16 +69,16 @@ [instant random.instant .let [d0 (/.day_of_week instant)]] (_.cover [/.day_of_week] - (let [apply (: (-> (-> Duration Duration) (-> Day Day) Nat Bit) - (function (_ polarity move steps) - (let [day_shift (list#mix (function.constant move) - d0 - (list.repeated steps [])) - instant_shift (|> instant - (/.after (polarity (duration.up steps duration.day))) - /.day_of_week)] - (day#= day_shift - instant_shift))))] + (let [apply (is (-> (-> Duration Duration) (-> Day Day) Nat Bit) + (function (_ polarity move steps) + (let [day_shift (list#mix (function.constant move) + d0 + (list.repeated steps [])) + instant_shift (|> instant + (/.after (polarity (duration.up steps duration.day))) + /.day_of_week)] + (day#= day_shift + instant_shift))))] (and (apply function.identity day#succ 0) (apply function.identity day#succ 1) (apply function.identity day#succ 2) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/coverage.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/coverage.lux index dfd65e1ba..629ffb39f 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/coverage.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/coverage.lux @@ -285,28 +285,28 @@ composes_variants! (let [composes_different_variants! - (let [composes? (: (-> (Maybe Nat) (Maybe Nat) (Maybe Nat) Bit) - (function (_ left right both) - (|> (/.composite {/.#Variant left (dictionary.of_list n.hash (list [tag/0 expected/0]))} - {/.#Variant right (dictionary.of_list n.hash (list [tag/1 expected/1]))}) - (try#each (/#= {/.#Variant both (dictionary.of_list n.hash (list [tag/0 expected/0] - [tag/1 expected/1]))})) - (try.else false))))] + (let [composes? (is (-> (Maybe Nat) (Maybe Nat) (Maybe Nat) Bit) + (function (_ left right both) + (|> (/.composite {/.#Variant left (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant right (dictionary.of_list n.hash (list [tag/1 expected/1]))}) + (try#each (/#= {/.#Variant both (dictionary.of_list n.hash (list [tag/0 expected/0] + [tag/1 expected/1]))})) + (try.else false))))] (and (composes? {.#None} {.#None} {.#None}) (composes? {.#Some arity} {.#None} {.#Some arity}) (composes? {.#None} {.#Some arity} {.#Some arity}) (composes? {.#Some arity} {.#Some arity} {.#Some arity}))) composes_same_variants! - (let [composes? (: (-> (Maybe Nat) (Maybe Nat) (Maybe Nat) Bit) - (function (_ left right both) - (|> (do try.monad - [variant (/.composite {/.#Variant left (dictionary.of_list n.hash (list [tag/0 expected/0]))} - {/.#Variant right (dictionary.of_list n.hash (list [tag/0 expected/1]))}) - expected (/.composite expected/0 expected/1)] - (in (/#= {/.#Variant both (dictionary.of_list n.hash (list [tag/0 expected]))} - variant))) - (try.else false))))] + (let [composes? (is (-> (Maybe Nat) (Maybe Nat) (Maybe Nat) Bit) + (function (_ left right both) + (|> (do try.monad + [variant (/.composite {/.#Variant left (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant right (dictionary.of_list n.hash (list [tag/0 expected/1]))}) + expected (/.composite expected/0 expected/1)] + (in (/#= {/.#Variant both (dictionary.of_list n.hash (list [tag/0 expected]))} + variant))) + (try.else false))))] (and (composes? {.#None} {.#None} {.#None}) (composes? {.#Some arity} {.#None} {.#Some arity}) (composes? {.#None} {.#Some arity} {.#Some arity}) 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 index aa9f91e78..af26cf21c 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/inference.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/inference.lux @@ -232,29 +232,29 @@ [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 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))) + variant?' (is (-> 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 0 (product.left name)) + (/phase#each product.right) + (/phase.result state) + (try.else false)))) + variant? (is (-> 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) @@ -332,26 +332,26 @@ [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 0 (product.left name)) - (/phase#each product.right) - (/phase.result state) - (try.else false)))) + .let [record? (is (-> 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 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 diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/macro.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/macro.lux index af025cb4d..a7fe6be62 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/macro.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/macro.lux @@ -62,8 +62,8 @@ poly (random.list multiplicity $code.random) lux ..random_state - .let [singular (<| (:as Macro) - (: Macro') + .let [singular (<| (as Macro) + (is Macro') (function (_ inputs state) (case (list.item choice inputs) {.#Some it} @@ -71,8 +71,8 @@ {.#None} {try.#Failure expected_error}))) - multiple (<| (:as Macro) - (: Macro') + multiple (<| (as Macro) + (is Macro') (function (_ inputs state) {try.#Success [state (|> inputs (list.repeated multiplicity) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/case.lux index 5fa0d281b..7a36cce34 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/case.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/case.lux @@ -68,20 +68,20 @@ $binding/2 (# ! each code.local_symbol (random.ascii/lower 5))] ($_ _.and (_.cover [/.tuple] - (let [tuple? (: (-> Type Type Bit) - (function (_ :input: :expected:) - (and (|> :input: - /.tuple - (check.result check.fresh_context) - (try#each (|>> product.right (type#= :expected:))) - (try.else false)) - (|> (do check.monad - [[@var :var:] check.var - _ (check.check :var: :input:)] - (/.tuple :var:)) - (check.result check.fresh_context) - (try#each (|>> product.right (type#= :expected:))) - (try.else false)))))] + (let [tuple? (is (-> Type Type Bit) + (function (_ :input: :expected:) + (and (|> :input: + /.tuple + (check.result check.fresh_context) + (try#each (|>> product.right (type#= :expected:))) + (try.else false)) + (|> (do check.monad + [[@var :var:] check.var + _ (check.check :var: :input:)] + (/.tuple :var:)) + (check.result check.fresh_context) + (try#each (|>> product.right (type#= :expected:))) + (try.else false)))))] (and (tuple? input/0 (type.anonymous input/0)) (tuple? (Tuple input/0 input/1 input/2) @@ -144,17 +144,17 @@ (-> Lux Symbol [Type Code] [Type Code] [Type Code] [Code Code Code] [Type Code] [Type Code] [Bit Nat] Bit) (let [state [//extension.#bundle (//extension/analysis.bundle ..eval) //extension.#state lux] - case? (: (-> Code (List [Code Code]) Bit) - (function (_ input branches) - (|> (do //phase.monad - [analysis (|> (/.case ..analysis branches archive.empty input) - (//type.expecting output/0))] - (in true)) - //scope.with - (//module.with 0 module/0) - (//phase#each (|>> product.right product.right)) - (//phase.result state) - (try.else false)))) + case? (is (-> Code (List [Code Code]) Bit) + (function (_ input branches) + (|> (do //phase.monad + [analysis (|> (/.case ..analysis branches archive.empty input) + (//type.expecting output/0))] + (in true)) + //scope.with + (//module.with 0 module/0) + (//phase#each (|>> product.right product.right)) + (//phase.result state) + (try.else false)))) body_types_mismatch! (and (not (case? (code.bit bit/0) (list [(` #0) body/1] @@ -251,17 +251,17 @@ (-> Lux Symbol [Type Code] [Type Code] [Type Code] [Code Code Code] [Type Code] Bit Bit) (let [state [//extension.#bundle (//extension/analysis.bundle ..eval) //extension.#state lux] - redundant? (: (-> Code (List [Code Code]) Bit) - (function (_ input branches) - (|> (do //phase.monad - [analysis (|> (/.case ..analysis branches archive.empty input) - (//type.expecting output/0))] - (in true)) - //scope.with - (//module.with 0 module/0) - (//phase#each (|>> product.right product.right)) - (//phase.result state) - (exception.otherwise (text.contains? (the exception.#label //coverage.redundancy))))))] + redundant? (is (-> Code (List [Code Code]) Bit) + (function (_ input branches) + (|> (do //phase.monad + [analysis (|> (/.case ..analysis branches archive.empty input) + (//type.expecting output/0))] + (in true)) + //scope.with + (//module.with 0 module/0) + (//phase#each (|>> product.right product.right)) + (//phase.result state) + (exception.otherwise (text.contains? (the exception.#label //coverage.redundancy))))))] (and (redundant? (` []) (list [(` []) body/0] [(` []) body/0])) @@ -313,18 +313,18 @@ tag/1 (code.symbol [module/0 tag/1]) tag/2 (code.symbol [module/0 tag/2]) - variant? (: (-> Code (List [Code Code]) Bit) - (function (_ input branches) - (|> (do //phase.monad - [_ (//module.declare_labels false tags/* false :variant:) - analysis (|> (/.case ..analysis branches archive.empty input) - (//type.expecting output/0))] - (in true)) - //scope.with - (//module.with 0 module/0) - (//phase#each (|>> product.right product.right)) - (//phase.result state) - (try.else false)))) + variant? (is (-> Code (List [Code Code]) Bit) + (function (_ input branches) + (|> (do //phase.monad + [_ (//module.declare_labels false tags/* false :variant:) + analysis (|> (/.case ..analysis branches archive.empty input) + (//type.expecting output/0))] + (in true)) + //scope.with + (//module.with 0 module/0) + (//phase#each (|>> product.right product.right)) + (//phase.result state) + (try.else false)))) can_bind! (and (variant? (` {(~ tag/0) (~ simple/0)}) @@ -384,18 +384,18 @@ slot/1 (code.symbol [module/0 slot/1]) slot/2 (code.symbol [module/0 slot/2]) - record? (: (-> Code (List [Code Code]) Bit) - (function (_ input branches) - (|> (do //phase.monad - [_ (//module.declare_labels true slots/* false :record:) - analysis (|> (/.case ..analysis branches archive.empty input) - (//type.expecting output/0))] - (in true)) - //scope.with - (//module.with 0 module/0) - (//phase#each (|>> product.right product.right)) - (//phase.result state) - (try.else false)))) + record? (is (-> Code (List [Code Code]) Bit) + (function (_ input branches) + (|> (do //phase.monad + [_ (//module.declare_labels true slots/* false :record:) + analysis (|> (/.case ..analysis branches archive.empty input) + (//type.expecting output/0))] + (in true)) + //scope.with + (//module.with 0 module/0) + (//phase#each (|>> product.right product.right)) + (//phase.result state) + (try.else false)))) can_bind! (record? (` [(~ slot/0) (~ simple/0) @@ -531,32 +531,32 @@ (//phase.result state) (exception.otherwise (text.contains? (the exception.#label /.empty_branches))))) (_.cover [/.non_exhaustive] - (let [non_exhaustive? (: (-> (List [Code Code]) Bit) - (function (_ branches) - (|> (do //phase.monad - [analysis (|> (/.case ..analysis branches archive.empty simple/0) - (//type.expecting output/0))] - (in false)) - //scope.with - (//module.with 0 module/0) - (//phase#each (|>> product.right product.right)) - (//phase.result state) - (exception.otherwise (text.contains? (the exception.#label /.non_exhaustive))))))] + (let [non_exhaustive? (is (-> (List [Code Code]) Bit) + (function (_ branches) + (|> (do //phase.monad + [analysis (|> (/.case ..analysis branches archive.empty simple/0) + (//type.expecting output/0))] + (in false)) + //scope.with + (//module.with 0 module/0) + (//phase#each (|>> product.right product.right)) + (//phase.result state) + (exception.otherwise (text.contains? (the exception.#label /.non_exhaustive))))))] (and (non_exhaustive? (list [simple/0 body/0])) (not (non_exhaustive? (list [simple/0 body/0] [$binding/0 body/0])))))) (_.cover [/.invalid] - (let [invalid? (: (-> (List [Code Code]) Bit) - (function (_ branches) - (|> (do //phase.monad - [analysis (|> (/.case ..analysis branches archive.empty simple/0) - (//type.expecting output/0))] - (in false)) - //scope.with - (//module.with 0 module/0) - (//phase#each (|>> product.right product.right)) - (//phase.result state) - (exception.otherwise (text.contains? (the exception.#label /.invalid))))))] + (let [invalid? (is (-> (List [Code Code]) Bit) + (function (_ branches) + (|> (do //phase.monad + [analysis (|> (/.case ..analysis branches archive.empty simple/0) + (//type.expecting output/0))] + (in false)) + //scope.with + (//module.with 0 module/0) + (//phase#each (|>> product.right product.right)) + (//phase.result state) + (exception.otherwise (text.contains? (the exception.#label /.invalid))))))] (and (invalid? (list [(` ((~ extension/0) (~ $binding/0) (~ $binding/1) (~ $binding/2))) body/0])) (invalid? (list [(` {(~ extension/0) (~ $binding/0) (~ $binding/1) (~ $binding/2)}) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/complex.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/complex.lux index f6d69fc56..aa0a98c6b 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/complex.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/complex.lux @@ -144,23 +144,23 @@ ($_ _.and (_.cover [/.sum] (let [variantT (type.variant (list#each product.left types/*,terms/*)) - sum? (: (-> Type Nat Bit Code Bit) - (function (_ type lefts right? code) - (|> (do //phase.monad - [analysis (|> (/.sum ..analysis lefts right? archive.empty code) - (//type.expecting type))] - (in (case analysis - (pattern (//analysis.variant [lefts' right?' analysis])) - (and (n.= lefts lefts') - (bit#= right? right?') - (..analysed? code analysis)) - - _ - false))) - (//module.with 0 (product.left name)) - (//phase#each product.right) - (//phase.result state) - (try.else false))))] + sum? (is (-> Type Nat Bit Code Bit) + (function (_ type lefts right? code) + (|> (do //phase.monad + [analysis (|> (/.sum ..analysis lefts right? archive.empty code) + (//type.expecting type))] + (in (case analysis + (pattern (//analysis.variant [lefts' right?' analysis])) + (and (n.= lefts lefts') + (bit#= right? right?') + (..analysed? code analysis)) + + _ + false))) + (//module.with 0 (product.left name)) + (//phase#each product.right) + (//phase.result state) + (try.else false))))] (and (sum? variantT lefts right? tagC) (sum? {.#Named name variantT} lefts right? tagC) (|> (do //phase.monad @@ -187,11 +187,11 @@ (and (sum? (type (Ex (_ a) (Maybe a))) 0 #0 (` [])) (sum? (type (Ex (_ a) (Maybe a))) 0 #1 tagC))))) (_.for [/.cannot_analyse_variant] - (let [failure? (: (All (_ a) (-> (Exception a) (//analysis.Operation Any) Bit)) - (function (_ exception analysis) - (let [it (//phase.result state analysis)] - (and (..failure? /.cannot_analyse_variant it) - (..failure? exception it)))))] + (let [failure? (is (All (_ a) (-> (Exception a) (//analysis.Operation Any) Bit)) + (function (_ exception analysis) + (let [it (//phase.result state analysis)] + (and (..failure? /.cannot_analyse_variant it) + (..failure? exception it)))))] ($_ _.and (_.cover [/.invalid_variant_type] (and (|> (/.sum ..analysis lefts right? archive.empty tagC) @@ -235,43 +235,43 @@ (maybe.else ""))]] ($_ _.and (_.cover [/.variant] - (let [expected_variant? (: (-> Symbol Bit) - (function (_ tag) - (|> (do //phase.monad - [_ (//module.declare_labels false tags false variantT) - analysis (|> (/.variant ..analysis tag archive.empty tagC) - (//type.expecting variantT))] - (in (case analysis - (pattern (//analysis.variant [lefts' right?' analysis])) - (and (n.= lefts lefts') - (bit#= right? right?') - (..analysed? tagC analysis)) - - _ - false))) - (//module.with 0 module) - (//phase#each product.right) - (//phase.result state) - (try.else false)))) - inferred_variant? (: (-> Symbol Bit) - (function (_ tag) - (|> (do //phase.monad - [_ (//module.declare_labels false tags false variantT) - [actualT analysis] (|> (/.variant ..analysis tag archive.empty tagC) - //type.inferring)] - (in (case analysis - (pattern (//analysis.variant [lefts' right?' analysis])) - (and (n.= lefts lefts') - (bit#= right? right?') - (..analysed? tagC analysis) - (type#= variantT actualT)) - - _ - false))) - (//module.with 0 module) - (//phase#each product.right) - (//phase.result state) - (try.else false))))] + (let [expected_variant? (is (-> Symbol Bit) + (function (_ tag) + (|> (do //phase.monad + [_ (//module.declare_labels false tags false variantT) + analysis (|> (/.variant ..analysis tag archive.empty tagC) + (//type.expecting variantT))] + (in (case analysis + (pattern (//analysis.variant [lefts' right?' analysis])) + (and (n.= lefts lefts') + (bit#= right? right?') + (..analysed? tagC analysis)) + + _ + false))) + (//module.with 0 module) + (//phase#each product.right) + (//phase.result state) + (try.else false)))) + inferred_variant? (is (-> Symbol Bit) + (function (_ tag) + (|> (do //phase.monad + [_ (//module.declare_labels false tags false variantT) + [actualT analysis] (|> (/.variant ..analysis tag archive.empty tagC) + //type.inferring)] + (in (case analysis + (pattern (//analysis.variant [lefts' right?' analysis])) + (and (n.= lefts lefts') + (bit#= right? right?') + (..analysed? tagC analysis) + (type#= variantT actualT)) + + _ + false))) + (//module.with 0 module) + (//phase#each product.right) + (//phase.result state) + (try.else false))))] (and (expected_variant? [module tag]) (expected_variant? ["" tag]) (inferred_variant? [module tag]) @@ -300,26 +300,26 @@ expected (list#each product.right types/*,terms/*)]] ($_ _.and (_.cover [/.product] - (let [product? (: (-> Type (List Code) Bit) - (function (_ type expected) - (|> (do //phase.monad - [analysis (|> expected - (/.product ..analysis archive.empty) - (//type.expecting type))] - (in (case analysis - (pattern (//analysis.tuple actual)) - (and (n.= (list.size expected) - (list.size actual)) - (list.every? (function (_ [expected actual]) - (..analysed? expected actual)) - (list.zipped/2 expected actual))) - - _ - false))) - (//module.with 0 module) - (//phase#each product.right) - (//phase.result state) - (try.else false))))] + (let [product? (is (-> Type (List Code) Bit) + (function (_ type expected) + (|> (do //phase.monad + [analysis (|> expected + (/.product ..analysis archive.empty) + (//type.expecting type))] + (in (case analysis + (pattern (//analysis.tuple actual)) + (and (n.= (list.size expected) + (list.size actual)) + (list.every? (function (_ [expected actual]) + (..analysed? expected actual)) + (list.zipped/2 expected actual))) + + _ + false))) + (//module.with 0 module) + (//phase#each product.right) + (//phase.result state) + (try.else false))))] (and (product? productT expected) (product? {.#Named name productT} expected) (product? (type (Ex (_ a) [a a])) (list term/0 term/0)) @@ -408,11 +408,11 @@ (try.else false))))) (_.for [/.cannot_analyse_tuple] (_.cover [/.invalid_tuple_type] - (let [failure? (: (All (_ a) (-> (Exception a) (//analysis.Operation Any) Bit)) - (function (_ exception operation) - (let [it (//phase.result state operation)] - (and (..failure? /.cannot_analyse_tuple it) - (..failure? exception it)))))] + (let [failure? (is (All (_ a) (-> (Exception a) (//analysis.Operation Any) Bit)) + (function (_ exception operation) + (let [it (//phase.result state operation)] + (and (..failure? /.cannot_analyse_tuple it) + (..failure? exception it)))))] (and (|> expected (/.product ..analysis archive.empty) (//type.expecting (|> types/*,terms/* @@ -472,21 +472,21 @@ slots/0)]] ($_ _.and (_.cover [/.normal] - (let [normal? (: (-> (List [Symbol Code]) (List Code) Bit) - (function (_ expected input) - (|> (do //phase.monad - [_ (//module.declare_labels true slots/0 false :record:)] - (/.normal false input)) - (//module.with 0 module) - (//phase#each product.right) - (//phase.result state) - (pipe.case - {try.#Success {.#Some actual}} - (let [(open "list#[0]") (list.equivalence (product.equivalence symbol.equivalence code.equivalence))] - (list#= expected (list.reversed actual))) - - _ - false))))] + (let [normal? (is (-> (List [Symbol Code]) (List Code) Bit) + (function (_ expected input) + (|> (do //phase.monad + [_ (//module.declare_labels true slots/0 false :record:)] + (/.normal false input)) + (//module.with 0 module) + (//phase#each product.right) + (//phase.result state) + (pipe.case + {try.#Success {.#Some actual}} + (let [(open "list#[0]") (list.equivalence (product.equivalence symbol.equivalence code.equivalence))] + (list#= expected (list.reversed actual))) + + _ + false))))] (and (normal? (list) (list)) (normal? expected_record global_record) (normal? expected_record local_record) @@ -501,33 +501,33 @@ (_.cover [/.order] (let [local_record (list.zipped/2 (list#each (|>> [""]) slots/0) tuple) global_record (list.zipped/2 (list#each (|>> [module]) slots/0) tuple) - ordered? (: (-> Bit (List [Symbol Code]) Bit) - (function (_ pattern_matching? input) - (|> (do //phase.monad - [_ (//module.declare_labels true slots/0 false :record:)] - (/.order pattern_matching? input)) - //scope.with - (//module.with 0 module) - (//phase#each (|>> product.right product.right)) - (//phase.result state) - (pipe.case - {try.#Success {.#Some [actual_arity actual_tuple actual_type]}} - (and (n.= arity actual_arity) - (# code.equivalence = (code.tuple tuple) (code.tuple actual_tuple)) - (type#= :record: actual_type)) - - _ - false)))) - unit? (: (-> Bit Bit) - (function (_ pattern_matching?) - (|> (/.order false (list)) - (//phase.result state) - (pipe.case - (pattern {try.#Success {.#Some [0 (list) actual_type]}}) - (same? .Any actual_type) - - _ - false))))] + ordered? (is (-> Bit (List [Symbol Code]) Bit) + (function (_ pattern_matching? input) + (|> (do //phase.monad + [_ (//module.declare_labels true slots/0 false :record:)] + (/.order pattern_matching? input)) + //scope.with + (//module.with 0 module) + (//phase#each (|>> product.right product.right)) + (//phase.result state) + (pipe.case + {try.#Success {.#Some [actual_arity actual_tuple actual_type]}} + (and (n.= arity actual_arity) + (# code.equivalence = (code.tuple tuple) (code.tuple actual_tuple)) + (type#= :record: actual_type)) + + _ + false)))) + unit? (is (-> Bit Bit) + (function (_ pattern_matching?) + (|> (/.order false (list)) + (//phase.result state) + (pipe.case + (pattern {try.#Success {.#Some [0 (list) actual_type]}}) + (same? .Any actual_type) + + _ + false))))] (and (ordered? false global_record) (ordered? false (list.reversed global_record)) (ordered? false local_record) @@ -544,29 +544,29 @@ ... TODO: Test what happens when slots are shadowed by local bindings. ))) (_.cover [/.cannot_repeat_slot] - (let [repeated? (: (-> Bit Bit) - (function (_ pattern_matching?) - (|> (do //phase.monad - [_ (//module.declare_labels true slots/0 false :record:)] - (/.order pattern_matching? (list.repeated arity [[module head_slot/0] head_term/0]))) - (//module.with 0 module) - (//phase#each product.right) - (//phase.result state) - (..failure? /.cannot_repeat_slot))))] + (let [repeated? (is (-> Bit Bit) + (function (_ pattern_matching?) + (|> (do //phase.monad + [_ (//module.declare_labels true slots/0 false :record:)] + (/.order pattern_matching? (list.repeated arity [[module head_slot/0] head_term/0]))) + (//module.with 0 module) + (//phase#each product.right) + (//phase.result state) + (..failure? /.cannot_repeat_slot))))] (and (repeated? false) (repeated? true)))) (_.cover [/.record_size_mismatch] (let [local_record (list.zipped/2 (list#each (|>> [""]) slots/0) tuple) global_record (list.zipped/2 (list#each (|>> [module]) slots/0) tuple) - mismatched? (: (-> Bit (List [Symbol Code]) Bit) - (function (_ pattern_matching? input) - (|> (do //phase.monad - [_ (//module.declare_labels true slots/0 false :record:)] - (/.order pattern_matching? input)) - //scope.with - (//module.with 0 module) - (//phase.result state) - (..failure? /.record_size_mismatch))))] + mismatched? (is (-> Bit (List [Symbol Code]) Bit) + (function (_ pattern_matching? input) + (|> (do //phase.monad + [_ (//module.declare_labels true slots/0 false :record:)] + (/.order pattern_matching? input)) + //scope.with + (//module.with 0 module) + (//phase.result state) + (..failure? /.record_size_mismatch))))] (and (mismatched? false (list.first slice local_record)) (mismatched? false (list#composite local_record (list.first slice local_record))) @@ -577,47 +577,47 @@ (_.cover [/.slot_does_not_belong_to_record] (let [local_record (list.zipped/2 (list#each (|>> [""]) slots/01) tuple) global_record (list.zipped/2 (list#each (|>> [module]) slots/01) tuple) - mismatched? (: (-> Bit (List [Symbol Code]) Bit) - (function (_ pattern_matching? input) - (|> (do //phase.monad - [_ (//module.declare_labels true slots/0 false :record:) - _ (//module.declare_labels true slots/1 false :record:)] - (/.order pattern_matching? input)) - //scope.with - (//module.with 0 module) - (//phase.result state) - (..failure? /.slot_does_not_belong_to_record))))] + mismatched? (is (-> Bit (List [Symbol Code]) Bit) + (function (_ pattern_matching? input) + (|> (do //phase.monad + [_ (//module.declare_labels true slots/0 false :record:) + _ (//module.declare_labels true slots/1 false :record:)] + (/.order pattern_matching? input)) + //scope.with + (//module.with 0 module) + (//phase.result state) + (..failure? /.slot_does_not_belong_to_record))))] (and (mismatched? false local_record) (mismatched? false global_record) (mismatched? true global_record)))) (_.cover [/.record] - (let [record? (: (-> Type (List Text) (List Code) Code Bit) - (function (_ type slots tuple expected) - (|> (do //phase.monad - [_ (//module.declare_labels true slots false type)] - (/.record ..analysis archive.empty tuple)) - (//type.expecting type) - //scope.with - (//module.with 0 module) - (//phase#each (|>> product.right product.right)) - (//phase.result state) - (try#each (analysed? expected)) - (try.else false)))) - inferred? (: (-> (List Code) Bit) - (function (_ record) - (|> (do //phase.monad - [_ (//module.declare_labels true slots/0 false :record:)] - (//type.inferring - (/.record ..analysis archive.empty record))) - //scope.with - (//module.with 0 module) - (//phase#each (|>> product.right product.right)) - (//phase.result state) - (try#each (function (_ [actual_type actual_term]) - (and (same? :record: actual_type) - (analysed? (code.tuple tuple) actual_term)))) - (try.else false))))] + (let [record? (is (-> Type (List Text) (List Code) Code Bit) + (function (_ type slots tuple expected) + (|> (do //phase.monad + [_ (//module.declare_labels true slots false type)] + (/.record ..analysis archive.empty tuple)) + (//type.expecting type) + //scope.with + (//module.with 0 module) + (//phase#each (|>> product.right product.right)) + (//phase.result state) + (try#each (analysed? expected)) + (try.else false)))) + inferred? (is (-> (List Code) Bit) + (function (_ record) + (|> (do //phase.monad + [_ (//module.declare_labels true slots/0 false :record:)] + (//type.inferring + (/.record ..analysis archive.empty record))) + //scope.with + (//module.with 0 module) + (//phase#each (|>> product.right product.right)) + (//phase.result state) + (try#each (function (_ [actual_type actual_term]) + (and (same? :record: actual_type) + (analysed? (code.tuple tuple) actual_term)))) + (try.else false))))] (and (record? {.#Named name .Any} (list) (list) (' [])) (record? {.#Named name type/0} (list) (list term/0) term/0) (record? {.#Named name type/0} (list slot/0) (list term/0) term/0) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/function.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/function.lux index fd60e1de8..a770e05e3 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/function.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/function.lux @@ -82,41 +82,41 @@ $argument/1 (code.local_symbol argument/1)]] ($_ _.and (_.cover [/.function] - (let [function?' (: (-> Type Code (-> [(List Analysis) Analysis] Bit) Bit) - (function (_ function_type output_term ?) - (|> (do //phase.monad - [analysis (|> (/.function ..analysis function/0 argument/0 archive.empty - output_term) - (//type.expecting function_type))] - (in (case analysis - {//analysis.#Function it} - (? it) + (let [function?' (is (-> Type Code (-> [(List Analysis) Analysis] Bit) Bit) + (function (_ function_type output_term ?) + (|> (do //phase.monad + [analysis (|> (/.function ..analysis function/0 argument/0 archive.empty + output_term) + (//type.expecting function_type))] + (in (case analysis + {//analysis.#Function it} + (? it) - _ - false))) - (//module.with 0 module/0) - (//phase#each product.right) - (//phase.result state) - (try.else false)))) - function? (: (-> Type Code Bit) - (function (_ function_type output_term) - (function?' function_type output_term (function.constant true)))) - inferring? (: (-> Type Code Bit) - (function (_ :expected: term) - (|> (do //phase.monad - [[:actual: analysis] (|> (/.function ..analysis function/0 argument/0 archive.empty - term) - //type.inferring)] - (in (case analysis - {//analysis.#Function [actual_env actual_body]} - (type#= :expected: :actual:) + _ + false))) + (//module.with 0 module/0) + (//phase#each product.right) + (//phase.result state) + (try.else false)))) + function? (is (-> Type Code Bit) + (function (_ function_type output_term) + (function?' function_type output_term (function.constant true)))) + inferring? (is (-> Type Code Bit) + (function (_ :expected: term) + (|> (do //phase.monad + [[:actual: analysis] (|> (/.function ..analysis function/0 argument/0 archive.empty + term) + //type.inferring)] + (in (case analysis + {//analysis.#Function [actual_env actual_body]} + (type#= :expected: :actual:) - _ - false))) - (//module.with 0 module/0) - (//phase#each product.right) - (//phase.result state) - (try.else false))))] + _ + false))) + (//module.with 0 module/0) + (//phase#each product.right) + (//phase.result state) + (try.else false))))] (and (function? (-> input/0 output/0) term/0) (function? (-> input/0 input/0) $argument/0) @@ -206,26 +206,26 @@ module/0 (random.ascii/lower 1)] ($_ _.and (_.cover [/.apply] - (let [reification? (: (-> Type (List Code) Type Bit) - (function (_ :abstraction: terms :expected:) - (|> (do //phase.monad - [[:actual: analysis] (|> (/.apply ..analysis terms - :abstraction: - (//analysis.unit) - archive.empty - (' [])) - //type.inferring)] - (in (and (check.subsumes? :expected: :actual:) - (case analysis - {//analysis.#Apply _} - true + (let [reification? (is (-> Type (List Code) Type Bit) + (function (_ :abstraction: terms :expected:) + (|> (do //phase.monad + [[:actual: analysis] (|> (/.apply ..analysis terms + :abstraction: + (//analysis.unit) + archive.empty + (' [])) + //type.inferring)] + (in (and (check.subsumes? :expected: :actual:) + (case analysis + {//analysis.#Apply _} + true - _ - false)))) - (//module.with 0 module/0) - (//phase#each product.right) - (//phase.result state) - (try.else false))))] + _ + false)))) + (//module.with 0 module/0) + (//phase#each product.right) + (//phase.result state) + (try.else false))))] (and (reification? (-> input/0 input/1 output/0) (list term/0 term/1) output/0) (reification? (-> input/0 input/1 output/0) (list term/0) (-> input/1 output/0)) (reification? (All (_ a) (-> a a)) (list term/0) input/0) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/reference.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/reference.lux index d8c5ce4f8..8240bcddc 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/reference.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/reference.lux @@ -168,56 +168,56 @@ can_find_alias! can_find_type!))) (_.cover [/.foreign_module_has_not_been_imported] - (let [scenario (: (-> Type Global Bit) - (function (_ expected_type it) - (|> (do //phase.monad - [_ (//module.with 0 import - (//module.define expected_name it)) - _ (/.reference [import expected_name])] - (in false)) - (//type.expecting expected_type) - (//module.with 0 expected_module) - (//phase#each product.right) - (//phase.result state) - (exception.otherwise (text.contains? (the exception.#label /.foreign_module_has_not_been_imported))) - )))] + (let [scenario (is (-> Type Global Bit) + (function (_ expected_type it) + (|> (do //phase.monad + [_ (//module.with 0 import + (//module.define expected_name it)) + _ (/.reference [import expected_name])] + (in false)) + (//type.expecting expected_type) + (//module.with 0 expected_module) + (//phase#each product.right) + (//phase.result state) + (exception.otherwise (text.contains? (the exception.#label /.foreign_module_has_not_been_imported))) + )))] (and (scenario expected_type {.#Definition [#1 expected_type []]}) (scenario .Type {.#Type [#1 expected_type (if record? {.#Right [expected_label (list)]} {.#Left [expected_label (list)]})]})))) (_.cover [/.definition_has_not_been_exported] - (let [scenario (: (-> Type Global Bit) - (function (_ expected_type it) - (|> (do //phase.monad - [_ (//module.with 0 import - (//module.define expected_name it)) - _ (/.reference [import expected_name])] - (in false)) - (//type.expecting expected_type) - (//module.with 0 expected_module) - (//phase#each product.right) - (//phase.result state) - (exception.otherwise (text.contains? (the exception.#label /.definition_has_not_been_exported))) - )))] + (let [scenario (is (-> Type Global Bit) + (function (_ expected_type it) + (|> (do //phase.monad + [_ (//module.with 0 import + (//module.define expected_name it)) + _ (/.reference [import expected_name])] + (in false)) + (//type.expecting expected_type) + (//module.with 0 expected_module) + (//phase#each product.right) + (//phase.result state) + (exception.otherwise (text.contains? (the exception.#label /.definition_has_not_been_exported))) + )))] (and (scenario expected_type {.#Definition [#0 expected_type []]}) (scenario .Type {.#Type [#0 expected_type (if record? {.#Right [expected_label (list)]} {.#Left [expected_label (list)]})]})))) (_.cover [/.labels_are_not_definitions] - (let [scenario (: (-> Type Global Bit) - (function (_ expected_type it) - (|> (do //phase.monad - [_ (//module.with 0 import - (//module.define expected_label it)) - _ (/.reference [import expected_label])] - (in false)) - (//type.expecting expected_type) - (//module.with 0 expected_module) - (//phase#each product.right) - (//phase.result state) - (exception.otherwise (text.contains? (the exception.#label /.labels_are_not_definitions))))))] + (let [scenario (is (-> Type Global Bit) + (function (_ expected_type it) + (|> (do //phase.monad + [_ (//module.with 0 import + (//module.define expected_label it)) + _ (/.reference [import expected_label])] + (in false)) + (//type.expecting expected_type) + (//module.with 0 expected_module) + (//phase#each product.right) + (//phase.result state) + (exception.otherwise (text.contains? (the exception.#label /.labels_are_not_definitions))))))] (and (scenario expected_type {.#Tag [#1 expected_type (list) 0]}) (scenario expected_type {.#Slot [#1 expected_type (list) 0]})))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/simple.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/simple.lux index ea5d4ebb4..5827be799 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/simple.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/simple.lux @@ -67,14 +67,14 @@ false)))) (template: (analysis? <type> <tag>) - [(: (-> <type> Analysis Bit) - (function (_ expected) - (|>> (pipe.case - (pattern (<tag> actual)) - (same? expected actual) + [(is (-> <type> Analysis Bit) + (function (_ expected) + (|>> (pipe.case + (pattern (<tag> actual)) + (same? expected actual) - _ - false))))]) + _ + false))))]) (def: .public test (<| (_.covering /._) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/extension.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/extension.lux index 1f24840eb..307816a02 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/extension.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/extension.lux @@ -45,48 +45,48 @@ random.int)] ($_ _.and (_.cover [/.read] - (|> (: (/.Operation Int Nat Nat Text) - (/.read %.int)) + (|> (is (/.Operation Int Nat Nat Text) + (/.read %.int)) (# phase.functor each (text#= (%.int state))) (phase.result [/.#bundle /.empty /.#state state]) (try.else false))) (_.cover [/.update] - (|> (: (/.Operation Int Nat Nat Text) - (do phase.monad - [_ (/.update ++)] - (/.read %.int))) + (|> (is (/.Operation Int Nat Nat Text) + (do phase.monad + [_ (/.update ++)] + (/.read %.int))) (# phase.functor each (text#= (%.int (++ state)))) (phase.result [/.#bundle /.empty /.#state state]) (try.else false))) (_.cover [/.temporary] - (|> (: (/.Operation Int Nat Nat Text) - (do phase.monad - [|state'| (/.temporary ++ (/.read %.int)) - |state| (/.read %.int)] - (in (format |state'| " " |state|)))) + (|> (is (/.Operation Int Nat Nat Text) + (do phase.monad + [|state'| (/.temporary ++ (/.read %.int)) + |state| (/.read %.int)] + (in (format |state'| " " |state|)))) (# phase.functor each (text#= (format (%.int (++ state)) " " (%.int state)))) (phase.result [/.#bundle /.empty /.#state state]) (try.else false))) (_.cover [/.with_state] - (|> (: (/.Operation Int Nat Nat Text) - (/.with_state state - (/.read %.int))) + (|> (is (/.Operation Int Nat Nat Text) + (/.with_state state + (/.read %.int))) (# phase.functor each (text#= (%.int state))) (phase.result [/.#bundle /.empty /.#state dummy]) (try.else false))) (_.cover [/.localized] - (|> (: (/.Operation Int Nat Nat Text) - (do phase.monad - [|state| (/.localized %.int - (function (_ _ old) (++ old)) - (text.enclosed ["<" ">"]) - (/.read %.int)) - |state'| (/.read %.int)] - (in (format |state'| " " |state|)))) + (|> (is (/.Operation Int Nat Nat Text) + (do phase.monad + [|state| (/.localized %.int + (function (_ _ old) (++ old)) + (text.enclosed ["<" ">"]) + (/.read %.int)) + |state'| (/.read %.int)] + (in (format |state'| " " |state|)))) (# phase.functor each (text#= (format (%.int (i.+ +2 state)) " " (%.int (i.+ +1 state))))) (phase.result [/.#bundle /.empty @@ -96,7 +96,7 @@ (def: extender /.Extender - (|>> :expected)) + (|>> as_expected)) (def: handler/0 (/.Handler Int Nat Nat) @@ -144,9 +144,9 @@ (def: test|bundle Test - (let [phase (: (/.Phase Int Nat Nat) - (function (_ archive input) - (# phase.monad in (++ input))))] + (let [phase (is (/.Phase Int Nat Nat) + (function (_ archive input) + (# phase.monad in (++ input))))] (do [! random.monad] [state random.int @@ -167,12 +167,12 @@ /.#state state]) (try.else false))) (_.cover [/.Phase] - (let [handler (: (/.Handler Int Nat Nat) - (function (_ @self phase archive inputs) - (let [! phase.monad] - (|> inputs - (monad.each ! (phase archive)) - (# ! each (list#mix n.+ 0))))))] + (let [handler (is (/.Handler Int Nat Nat) + (function (_ @self phase archive inputs) + (let [! phase.monad] + (|> inputs + (monad.each ! (phase archive)) + (# ! each (list#mix n.+ 0))))))] (|> (do phase.monad [_ (/.install extender extension handler)] (/.apply archive.empty phase [extension (list left right)])) @@ -191,9 +191,9 @@ /.#state state]) (try.else false))) (_.cover [/.incorrect_arity] - (let [handler (: (/.Handler Int Nat Nat) - (function (_ @self phase archive inputs) - (phase.except /.incorrect_arity [@self 2 (list.size inputs)])))] + (let [handler (is (/.Handler Int Nat Nat) + (function (_ @self phase archive inputs) + (phase.except /.incorrect_arity [@self 2 (list.size inputs)])))] (|> (do phase.monad [_ (/.install extender extension handler)] (/.apply archive.empty phase [extension (list)])) @@ -206,9 +206,9 @@ _ false)))) (_.cover [/.invalid_syntax] - (let [handler (: (/.Handler Int Nat Nat) - (function (_ @self phase archive inputs) - (phase.except /.invalid_syntax [@self %.nat inputs])))] + (let [handler (is (/.Handler Int Nat Nat) + (function (_ @self phase archive inputs) + (phase.except /.invalid_syntax [@self %.nat inputs])))] (|> (do phase.monad [_ (/.install extender extension handler)] (/.apply archive.empty phase [extension (list left right)])) @@ -244,16 +244,16 @@ (<| (_.for [/.Operation]) ($_ _.and (_.cover [/.lifted] - (and (|> (: (/.Operation Int Nat Nat Nat) - (/.lifted (do phase.monad - [] - (in expected)))) + (and (|> (is (/.Operation Int Nat Nat Nat) + (/.lifted (do phase.monad + [] + (in expected)))) (# phase.functor each (same? expected)) (phase.result [/.#bundle /.empty /.#state state]) (try.else false)) - (|> (: (/.Operation Int Nat Nat Nat) - (/.lifted (phase.lifted {try.#Failure expected_error}))) + (|> (is (/.Operation Int Nat Nat Nat) + (/.lifted (phase.lifted {try.#Failure expected_error}))) (phase.result [/.#bundle /.empty /.#state state]) (pipe.case @@ -266,9 +266,9 @@ (|> (do phase.monad [] (in expected)) - (: (/.Operation Int Nat Nat Nat)) + (is (/.Operation Int Nat Nat Nat)) /.up - (: (phase.Operation Int Nat)) + (is (phase.Operation Int Nat)) (# phase.functor each (same? expected)) (phase.result state) (try.else false))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/case.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/case.lux index ea325ec72..aaa52ad0f 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/case.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/case.lux @@ -87,12 +87,12 @@ inputA //primitive.primitive thenA //primitive.primitive elseA //primitive.primitive - .let [thenB (: Branch - [{analysis.#Simple {analysis.#Bit true}} - thenA]) - elseB (: Branch - [{analysis.#Simple {analysis.#Bit false}} - elseA]) + .let [thenB (is Branch + [{analysis.#Simple {analysis.#Bit true}} + thenA]) + elseB (is Branch + [{analysis.#Simple {analysis.#Bit false}} + elseA]) ifA (if then|else (analysis.case [inputA [thenB (list elseB)]]) (analysis.case [inputA [elseB (list thenB)]]))]] @@ -237,20 +237,20 @@ [value/0 value/1 value/2 value/3 value/4] (random_five text.hash (random.unicode 1)) last_is_right? random.bit [body/0 body/1 body/2 body/3 body/4] (random_five frac.hash random.frac) - .let [path (: (-> Nat Bit Text Frac Path) - (function (_ lefts right? value body) - ($_ {synthesis.#Seq} - (synthesis.path/side (if right? - {.#Right lefts} - {.#Left lefts})) - (synthesis.path/text value) - {synthesis.#Then (synthesis.f64 body)}))) - branch (: (-> Nat Bit Text Frac Branch) - (function (_ lefts right? value body) - [analysis.#when (analysis.pattern/variant [analysis.#lefts lefts - analysis.#right? right? - analysis.#value (analysis.pattern/text value)]) - analysis.#then (analysis.frac body)]))]] + .let [path (is (-> Nat Bit Text Frac Path) + (function (_ lefts right? value body) + ($_ {synthesis.#Seq} + (synthesis.path/side (if right? + {.#Right lefts} + {.#Left lefts})) + (synthesis.path/text value) + {synthesis.#Then (synthesis.f64 body)}))) + branch (is (-> Nat Bit Text Frac Branch) + (function (_ lefts right? value body) + [analysis.#when (analysis.pattern/variant [analysis.#lefts lefts + analysis.#right? right? + analysis.#value (analysis.pattern/text value)]) + analysis.#then (analysis.frac body)]))]] (in [($_ {synthesis.#Alt} (path lefts/0 false value/0 body/0) (path lefts/1 false value/1 body/1) @@ -275,32 +275,32 @@ body/first random.frac body/mid (random.list mid_size random.frac) body/last random.frac - .let [path (: (-> Nat Bit Text Frac Path) - (function (_ lefts right? value body) - (if right? - ($_ {synthesis.#Seq} - (synthesis.path/member (if right? - {.#Right lefts} - {.#Left lefts})) - (synthesis.path/text value) - {synthesis.#Then (synthesis.f64 body)}) - ($_ {synthesis.#Seq} - (synthesis.path/member (if right? - {.#Right lefts} - {.#Left lefts})) - (synthesis.path/text value) - {synthesis.#Pop} - {synthesis.#Then (synthesis.f64 body)})))) - branch (: (-> Nat Bit Text Frac Branch) - (function (_ lefts right? value body) - [analysis.#when (if right? - (analysis.pattern/tuple (list#composite (list.repeated (++ lefts) (analysis.pattern/unit)) - (list (analysis.pattern/text value)))) - (analysis.pattern/tuple ($_ list#composite - (list.repeated lefts (analysis.pattern/unit)) - (list (analysis.pattern/text value) - (analysis.pattern/unit))))) - analysis.#then (analysis.frac body)]))]] + .let [path (is (-> Nat Bit Text Frac Path) + (function (_ lefts right? value body) + (if right? + ($_ {synthesis.#Seq} + (synthesis.path/member (if right? + {.#Right lefts} + {.#Left lefts})) + (synthesis.path/text value) + {synthesis.#Then (synthesis.f64 body)}) + ($_ {synthesis.#Seq} + (synthesis.path/member (if right? + {.#Right lefts} + {.#Left lefts})) + (synthesis.path/text value) + {synthesis.#Pop} + {synthesis.#Then (synthesis.f64 body)})))) + branch (is (-> Nat Bit Text Frac Branch) + (function (_ lefts right? value body) + [analysis.#when (if right? + (analysis.pattern/tuple (list#composite (list.repeated (++ lefts) (analysis.pattern/unit)) + (list (analysis.pattern/text value)))) + (analysis.pattern/tuple ($_ list#composite + (list.repeated lefts (analysis.pattern/unit)) + (list (analysis.pattern/text value) + (analysis.pattern/unit))))) + analysis.#then (analysis.frac body)]))]] (in [(list#mix (function (_ left right) {synthesis.#Alt left right}) (path (++ mid_size) true value/last body/last) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/loop.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/loop.lux index 1f220e13a..84c3873aa 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/loop.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/loop.lux @@ -109,48 +109,48 @@ (def: path (Scenario Path) - (let [pattern (: (Scenario Path) - (.function (again offset arity next) - (`` ($_ random.either - (random#in [next - [//.path/pop - //.path/pop]]) - (~~ (template [<path> <random>] - [(do [! random.monad] - [example (# ! each (|>> <path>) <random>)] - (in [next - [example - example]]))] + (let [pattern (is (Scenario Path) + (.function (again offset arity next) + (`` ($_ random.either + (random#in [next + [//.path/pop + //.path/pop]]) + (~~ (template [<path> <random>] + [(do [! random.monad] + [example (# ! each (|>> <path>) <random>)] + (in [next + [example + example]]))] - [//.path/bit random.bit] - [//.path/i64 (# ! each .i64 random.nat)] - [//.path/f64 random.frac] - [//.path/text (random.unicode 1)] - )) - (~~ (template [<path>] - [(do [! random.monad] - [example (# ! each (|>> <path>) - (random.or random.nat - random.nat))] - (in [next - [example - example]]))] + [//.path/bit random.bit] + [//.path/i64 (# ! each .i64 random.nat)] + [//.path/f64 random.frac] + [//.path/text (random.unicode 1)] + )) + (~~ (template [<path>] + [(do [! random.monad] + [example (# ! each (|>> <path>) + (random.or random.nat + random.nat))] + (in [next + [example + example]]))] - [//.path/side] - [//.path/member] - )) - (random#in [(++ next) - [(//.path/bind (/.register_optimization offset next)) - (//.path/bind next)]]) - )))) - sequential (: (Scenario Path) - (.function (again offset arity next) - (do random.monad - [[next [patternE patternA]] (pattern offset arity next) - [next [bodyE bodyA]] (..reference offset arity next)] - (in [next - [(//.path/seq patternE (//.path/then bodyE)) - (//.path/seq patternA (//.path/then bodyA))]]))))] + [//.path/side] + [//.path/member] + )) + (random#in [(++ next) + [(//.path/bind (/.register_optimization offset next)) + (//.path/bind next)]]) + )))) + sequential (is (Scenario Path) + (.function (again offset arity next) + (do random.monad + [[next [patternE patternA]] (pattern offset arity next) + [next [bodyE bodyA]] (..reference offset arity next)] + (in [next + [(//.path/seq patternE (//.path/then bodyE)) + (//.path/seq patternA (//.path/then bodyA))]]))))] (.function (again offset arity next) (do random.monad [[next [leftE leftA]] (sequential offset arity next) @@ -161,9 +161,9 @@ (def: (branch offset arity next) (Scenario Synthesis) - (let [random_member (: (Random Member) - (random.or random.nat - random.nat))] + (let [random_member (is (Random Member) + (random.or random.nat + random.nat))] ($_ random.either ($_ random.either (do [! random.monad] diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/primitive.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/primitive.lux index 80499a5e2..2de99cd64 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/primitive.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/primitive.lux @@ -31,15 +31,15 @@ (def: .public primitive (Random Analysis) (do r.monad - [primitive (: (Random ////analysis.Primitive) - ($_ r.or - (in []) - r.bit - r.nat - r.int - r.rev - r.frac - (r.unicode 5)))] + [primitive (is (Random ////analysis.Primitive) + ($_ r.or + (in []) + r.bit + r.nat + r.int + r.rev + r.frac + (r.unicode 5)))] (in {////analysis.#Primitive primitive}))) (def: .public (corresponds? analysis synthesis) @@ -51,7 +51,7 @@ (same? (|> expected <post_analysis>) (|> actual <post_synthesis>))] - [////analysis.#Unit (:as Text) ////synthesis.#Text (|>)] + [////analysis.#Unit (as Text) ////synthesis.#Text (|>)] [////analysis.#Bit (|>) ////synthesis.#Bit (|>)] [////analysis.#Nat .i64 ////synthesis.#I64 .i64] [////analysis.#Int .i64 ////synthesis.#I64 .i64] diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/syntax.lux b/stdlib/source/test/lux/tool/compiler/language/lux/syntax.lux index 90d5b825c..c253f7107 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/syntax.lux @@ -1,28 +1,28 @@ (.using - [lux "*" - [abstract/monad {"+" do}] - [data - ["%" text/format {"+" format}] - [number - ["n" nat]]] - ["r" math/random {"+" Random} ("[1]#[0]" monad)] - ["_" test {"+" Test}] - [control - ["[0]" try] - [parser - ["l" text]]] - [data - ["[0]" text] - [collection - ["[0]" list] - ["[0]" dictionary {"+" Dictionary}]]] - [macro - ["[0]" code]] - [meta - ["[0]" location] - ["[0]" symbol]]] - [\\ - ["[0]" /]]) + [lux "*" + [abstract/monad {"+" do}] + [data + ["%" text/format {"+" format}] + [number + ["n" nat]]] + ["r" math/random {"+" Random} ("[1]#[0]" monad)] + ["_" test {"+" Test}] + [control + ["[0]" try] + [parser + ["l" text]]] + [data + ["[0]" text] + [collection + ["[0]" list] + ["[0]" dictionary {"+" Dictionary}]]] + [macro + ["[0]" code]] + [meta + ["[0]" location] + ["[0]" symbol]]] + [\\ + ["[0]" /]]) (def: symbol_part^ (Random Text) @@ -36,37 +36,37 @@ (def: code^ (Random Code) - (let [numeric^ (: (Random Code) + (let [numeric^ (is (Random Code) + ($_ r.either + (|> r.bit (r#each code.bit)) + (|> r.nat (r#each code.nat)) + (|> r.int (r#each code.int)) + (|> r.rev (r#each code.rev)) + (|> r.safe_frac (r#each code.frac)))) + textual^ (is (Random Code) + ($_ r.either + (do r.monad + [size (|> r.nat (r#each (n.% 20)))] + (|> (r.ascii/upper_alpha size) (r#each code.text))) + (|> symbol^ (r#each code.symbol)) + (|> symbol^ (r#each code.tag)))) + simple^ (is (Random Code) ($_ r.either - (|> r.bit (r#each code.bit)) - (|> r.nat (r#each code.nat)) - (|> r.int (r#each code.int)) - (|> r.rev (r#each code.rev)) - (|> r.safe_frac (r#each code.frac)))) - textual^ (: (Random Code) - ($_ r.either - (do r.monad - [size (|> r.nat (r#each (n.% 20)))] - (|> (r.ascii/upper_alpha size) (r#each code.text))) - (|> symbol^ (r#each code.symbol)) - (|> symbol^ (r#each code.tag)))) - simple^ (: (Random Code) - ($_ r.either - numeric^ - textual^))] + numeric^ + textual^))] (r.rec (function (_ code^) (let [multi^ (do r.monad [size (|> r.nat (r#each (n.% 3)))] (r.list size code^)) - composite^ (: (Random Code) - ($_ r.either - (|> multi^ (r#each code.form)) - (|> multi^ (r#each code.tuple)) - (do r.monad - [size (|> r.nat (r#each (n.% 3)))] - (|> (r.list size (r.and code^ code^)) - (r#each code.record)))))] + composite^ (is (Random Code) + ($_ r.either + (|> multi^ (r#each code.form)) + (|> multi^ (r#each code.tuple)) + (do r.monad + [size (|> r.nat (r#each (n.% 3)))] + (|> (r.list size (r.and code^ code^)) + (r#each code.record)))))] ($_ r.either simple^ composite^)))))) diff --git a/stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux b/stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux index e347edf4a..d012390fc 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux @@ -111,12 +111,12 @@ _ false)))))] - [/.definition (: category.Definition [expected_name {.#None}]) /.definitions category.#Definition /.analyser expected_name] + [/.definition (is category.Definition [expected_name {.#None}]) /.definitions category.#Definition /.analyser expected_name] [/.analyser expected_name /.analysers category.#Analyser /.synthesizer expected_name] [/.synthesizer expected_name /.synthesizers category.#Synthesizer /.generator expected_name] [/.generator expected_name /.generators category.#Generator /.directive expected_name] [/.directive expected_name /.directives category.#Directive /.custom expected_name] - [/.custom expected_name /.customs category.#Custom /.definition (: category.Definition [expected_name {.#None}])] + [/.custom expected_name /.customs category.#Custom /.definition (is category.Definition [expected_name {.#None}])] )) (_.cover [/.id] (and (~~ (template [<new> <expected>' <name>] @@ -126,7 +126,7 @@ (maybe#each (same? @expected)) (maybe.else false)))] - [/.definition (: category.Definition [expected_name {.#None}]) product.left] + [/.definition (is category.Definition [expected_name {.#None}]) product.left] [/.analyser expected_name |>] [/.synthesizer expected_name |>] [/.generator expected_name |>] @@ -136,12 +136,12 @@ (_.cover [/.artifacts] (and (~~ (template [<new> <query> <equivalence> <$>] [(let [expected/* (list#each <$> expected_names) - [ids registry] (: [(Sequence artifact.ID) /.Registry] - (list#mix (function (_ expected [ids registry]) - (let [[@new registry] (<new> expected mandatory? expected_dependencies registry)] - [(sequence.suffix @new ids) registry])) - [sequence.empty /.empty] - expected/*)) + [ids registry] (is [(Sequence artifact.ID) /.Registry] + (list#mix (function (_ expected [ids registry]) + (let [[@new registry] (<new> expected mandatory? expected_dependencies registry)] + [(sequence.suffix @new ids) registry])) + [sequence.empty /.empty] + expected/*)) it (/.artifacts registry)] (and (n.= expected_amount (sequence.size it)) (list.every? (function (_ [@it [it dependencies]]) @@ -149,9 +149,9 @@ (list.zipped/2 (sequence.list ids) (sequence.list it))) (# (list.equivalence <equivalence>) = expected/* (<query> registry))))] - [/.definition /.definitions category.definition_equivalence (: (-> Text category.Definition) - (function (_ it) - [it {.#None}]))] + [/.definition /.definitions category.definition_equivalence (is (-> Text category.Definition) + (function (_ it) + [it {.#None}]))] [/.analyser /.analysers text.equivalence (|>>)] [/.synthesizer /.synthesizers text.equivalence (|>>)] [/.generator /.generators text.equivalence (|>>)] @@ -170,7 +170,7 @@ (maybe.else false))) (try.else false)))] - [/.definition (: category.Definition [expected_name {.#None}]) product.left] + [/.definition (is category.Definition [expected_name {.#None}]) product.left] [/.analyser expected_name |>] [/.synthesizer expected_name |>] [/.generator expected_name |>] diff --git a/stdlib/source/test/lux/tool/compiler/meta/cache/purge.lux b/stdlib/source/test/lux/tool/compiler/meta/cache/purge.lux index 700cf75d7..f7e008720 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/cache/purge.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/cache/purge.lux @@ -77,40 +77,40 @@ ($_ _.and (_.cover [/.purge] (and (dictionary.empty? (/.purge (list) (list))) - (let [order (: (dependency.Order Nat) - (list [name/0 id/0 - [archive.#module module/0 - archive.#output (sequence.sequence) - archive.#registry registry.empty]]))] - (and (let [cache (: (List /.Cache) - (list [#1 name/0 id/0 module/0 registry.empty]))] + (let [order (is (dependency.Order Nat) + (list [name/0 id/0 + [archive.#module module/0 + archive.#output (sequence.sequence) + archive.#registry registry.empty]]))] + (and (let [cache (is (List /.Cache) + (list [#1 name/0 id/0 module/0 registry.empty]))] (dictionary.empty? (/.purge cache order))) - (let [cache (: (List /.Cache) - (list [#0 name/0 id/0 module/0 registry.empty]))] + (let [cache (is (List /.Cache) + (list [#0 name/0 id/0 module/0 registry.empty]))] (dictionary.key? (/.purge cache order) name/0)))) - (let [order (: (dependency.Order Nat) - (list [name/0 id/0 - [archive.#module module/0 - archive.#output (sequence.sequence) - archive.#registry registry.empty]] - [name/1 id/1 - [archive.#module module/1 - archive.#output (sequence.sequence) - archive.#registry registry.empty]]))] - (and (let [cache (: (List /.Cache) - (list [#1 name/0 id/0 module/0 registry.empty] - [#1 name/1 id/1 module/1 registry.empty])) + (let [order (is (dependency.Order Nat) + (list [name/0 id/0 + [archive.#module module/0 + archive.#output (sequence.sequence) + archive.#registry registry.empty]] + [name/1 id/1 + [archive.#module module/1 + archive.#output (sequence.sequence) + archive.#registry registry.empty]]))] + (and (let [cache (is (List /.Cache) + (list [#1 name/0 id/0 module/0 registry.empty] + [#1 name/1 id/1 module/1 registry.empty])) purge (/.purge cache order)] (dictionary.empty? purge)) - (let [cache (: (List /.Cache) - (list [#1 name/0 id/0 module/0 registry.empty] - [#0 name/1 id/1 module/1 registry.empty])) + (let [cache (is (List /.Cache) + (list [#1 name/0 id/0 module/0 registry.empty] + [#0 name/1 id/1 module/1 registry.empty])) purge (/.purge cache order)] (and (not (dictionary.key? (/.purge cache order) name/0)) (dictionary.key? (/.purge cache order) name/1))) - (let [cache (: (List /.Cache) - (list [#0 name/0 id/0 module/0 registry.empty] - [#1 name/1 id/1 module/1 registry.empty])) + (let [cache (is (List /.Cache) + (list [#0 name/0 id/0 module/0 registry.empty] + [#1 name/1 id/1 module/1 registry.empty])) purge (/.purge cache order)] (and (dictionary.key? (/.purge cache order) name/0) (dictionary.key? (/.purge cache order) name/1))))))) diff --git a/stdlib/source/test/lux/tool/compiler/meta/export.lux b/stdlib/source/test/lux/tool/compiler/meta/export.lux index 82efdf546..d25da0be5 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/export.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/export.lux @@ -44,8 +44,8 @@ source/1 (random.ascii/lower 2) target (random.ascii/lower 3) - .let [random_file (: (Random file.Path) - (# ! each (text.suffix io.lux_extension) (random.ascii/lower 4)))] + .let [random_file (is (Random file.Path) + (# ! each (text.suffix io.lux_extension) (random.ascii/lower 4)))] file/0' random_file .let [file/0 (format source/0 / file/0')] @@ -53,8 +53,8 @@ file/1' (# ! each (|>> (format dir/0 /)) random_file) .let [file/1 (format source/1 / file/1')] - .let [random_content (: (Random Binary) - (# ! each (|>> %.nat (# utf8.codec encoded)) random.nat))] + .let [random_content (is (Random Binary) + (# ! each (|>> %.nat (# utf8.codec encoded)) random.nat))] content/0 random_content content/1 random_content] ($_ _.and diff --git a/stdlib/source/test/lux/tool/compiler/meta/import.lux b/stdlib/source/test/lux/tool/compiler/meta/import.lux index e601614f6..c01a790ce 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/import.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/import.lux @@ -48,15 +48,15 @@ library/1 (random.ascii/lower 2) .let [/ .module_separator - random_file (: (Random file.Path) - (# ! each (text.suffix io.lux_extension) (random.ascii/lower 3)))] + random_file (is (Random file.Path) + (# ! each (text.suffix io.lux_extension) (random.ascii/lower 3)))] file/0 random_file dir/0 (random.ascii/lower 4) file/1 (# ! each (|>> (format dir/0 /)) random_file) - .let [random_content (: (Random Binary) - (# ! each (|>> %.nat (# utf8.codec encoded)) random.nat))] + .let [random_content (is (Random Binary) + (# ! each (|>> %.nat (# utf8.codec encoded)) random.nat))] now random.instant content/0 random_content content/1 random_content @@ -97,17 +97,17 @@ (in (|> (sequence.sequence {tar.#Directory file/0}) (format.result tar.writer)))) (try.else (binary.empty 0))) - imported? (: (-> /.Import Bit) - (function (_ it) - (and (n.= 2 (dictionary.size it)) - (|> it - (dictionary.value file/0) - (maybe#each (binary#= content/0)) - (maybe.else false)) - (|> it - (dictionary.value file/1) - (maybe#each (binary#= content/1)) - (maybe.else false)))))]] + imported? (is (-> /.Import Bit) + (function (_ it) + (and (n.= 2 (dictionary.size it)) + (|> it + (dictionary.value file/0) + (maybe#each (binary#= content/0)) + (maybe.else false)) + (|> it + (dictionary.value file/1) + (maybe#each (binary#= content/1)) + (maybe.else false)))))]] ($_ _.and (in (do [! async.monad] [it/0 (do (try.with !) diff --git a/stdlib/source/test/lux/tool/compiler/phase.lux b/stdlib/source/test/lux/tool/compiler/phase.lux index 19ec57c3c..ced6edd48 100644 --- a/stdlib/source/test/lux/tool/compiler/phase.lux +++ b/stdlib/source/test/lux/tool/compiler/phase.lux @@ -178,12 +178,12 @@ (try#each (same? expected)) (try.else false))) (_.cover [/.composite] - (let [phase (/.composite (: (/.Phase Nat Int Frac) - (function (_ archive input) - (# /.monad in (i.frac input)))) - (: (/.Phase Rev Frac Text) - (function (_ archive input) - (# /.monad in (%.frac input)))))] + (let [phase (/.composite (is (/.Phase Nat Int Frac) + (function (_ archive input) + (# /.monad in (i.frac input)))) + (is (/.Phase Rev Frac Text) + (function (_ archive input) + (# /.monad in (%.frac input)))))] (|> (phase archive.empty expected) (/.result' [state/0 state/1]) (pipe.case {try.#Success [[state/0' state/1'] actual]} diff --git a/stdlib/source/test/lux/type.lux b/stdlib/source/test/lux/type.lux index c173fdc85..6e19e21a0 100644 --- a/stdlib/source/test/lux/type.lux +++ b/stdlib/source/test/lux/type.lux @@ -51,15 +51,15 @@ (random.rec (function (_ again) (let [pairG (random.and again again) - un_parameterized (: (Random Type) - ($_ random.either - (random#each (|>> {.#Primitive}) (random.and ..short (random.list 0 again))) - (random#each (|>> {.#Primitive}) (random.and ..short (random.list 1 again))) - (random#each (|>> {.#Primitive}) (random.and ..short (random.list 2 again))) - (random#each (|>> {.#Sum}) pairG) - (random#each (|>> {.#Product}) pairG) - (random#each (|>> {.#Function}) pairG) - ))] + un_parameterized (is (Random Type) + ($_ random.either + (random#each (|>> {.#Primitive}) (random.and ..short (random.list 0 again))) + (random#each (|>> {.#Primitive}) (random.and ..short (random.list 1 again))) + (random#each (|>> {.#Primitive}) (random.and ..short (random.list 2 again))) + (random#each (|>> {.#Sum}) pairG) + (random#each (|>> {.#Product}) pairG) + (random#each (|>> {.#Function}) pairG) + ))] (case parameters 0 un_parameterized _ (|> random.nat @@ -195,40 +195,50 @@ (and (not (/.array? element_type)) (/.array? (/.array depth element_type)))) )) - (_.cover [/.:by_example] - (let [example (: (Maybe Nat) - {.#None})] + (_.cover [/.by_example] + (let [example (is (Maybe Nat) + {.#None})] (/#= (.type (List Nat)) - (/.:by_example [a] - (Maybe a) - example - - (List a))))) + (/.by_example [a] + (Maybe a) + example + + (List a))))) (do random.monad [sample random.nat] - (_.cover [/.:log!] + (_.cover [/.log!] (exec - (/.:log! sample) + (/.log! sample) true))) (do random.monad [left random.nat right (random.ascii/lower 1) .let [left,right [left right]]] - (_.cover [/.:as] + (_.cover [/.as] (|> left,right - (/.:as [l r] (And l r) (Or l r)) - (/.:as [l r] (Or l r) (And l r)) + (/.as [l r] (And l r) (Or l r)) + (/.as [l r] (Or l r) (And l r)) (same? left,right)))) (do random.monad [expected random.nat] - (_.cover [/.:sharing] + (_.cover [/.sharing] (n.= expected - (/.:sharing [a] - (I64 a) - expected + (/.sharing [a] + (I64 a) + expected - (I64 a) - (.i64 expected))))) + (I64 a) + (.i64 expected))))) + (do random.monad + [expected_left random.nat + expected_right random.nat] + (_.cover [/.let] + (let [[actual_left actual_right] + (is (/.let [side /.Nat] + [side side]) + [expected_left expected_right])] + (and (same? expected_left actual_left) + (same? expected_right actual_right))))) (do random.monad [.let [(open "/#[0]") /.equivalence] left (..random 0) diff --git a/stdlib/source/test/lux/type/abstract.lux b/stdlib/source/test/lux/type/abstract.lux index 770fc60a4..8bae5b3bc 100644 --- a/stdlib/source/test/lux/type/abstract.lux +++ b/stdlib/source/test/lux/type/abstract.lux @@ -60,43 +60,43 @@ [expected_foo (random.ascii/lower 5) expected_bar random.nat] ($_ _.and - (_.cover [/.:abstraction] - (and (exec (: (g!Foo Text) - (/.:abstraction g!Foo expected_foo)) + (_.cover [/.abstraction] + (and (exec (is (g!Foo Text) + (/.abstraction g!Foo expected_foo)) true) - (exec (: (g!Bar Text) - (/.:abstraction expected_bar)) + (exec (is (g!Bar Text) + (/.abstraction expected_bar)) true))) - (_.cover [/.:representation] + (_.cover [/.representation] (and (|> expected_foo - (/.:abstraction g!Foo) - (: (g!Foo Bit)) - (/.:representation g!Foo) + (/.abstraction g!Foo) + (is (g!Foo Bit)) + (/.representation g!Foo) (text#= expected_foo)) - (|> (/.:abstraction expected_bar) - (: (g!Bar Bit)) - /.:representation + (|> (/.abstraction expected_bar) + (is (g!Bar Bit)) + /.representation (n.= expected_bar)))) - (_.cover [/.:transmutation] + (_.cover [/.transmutation] (and (exec (|> expected_foo - (/.:abstraction g!Foo) - (: (g!Foo .Macro)) - (/.:transmutation g!Foo) - (: (g!Foo .Lux))) + (/.abstraction g!Foo) + (is (g!Foo .Macro)) + (/.transmutation g!Foo) + (is (g!Foo .Lux))) true) - (exec (|> (/.:abstraction expected_bar) - (: (g!Bar .Macro)) - /.:transmutation - (: (g!Bar .Lux))) + (exec (|> (/.abstraction expected_bar) + (is (g!Bar .Macro)) + /.transmutation + (is (g!Bar .Lux))) true))) - (_.cover [/.^:representation] - (and (let [(/.^:representation g!Foo actual_foo) - (: (g!Foo .Module) - (/.:abstraction g!Foo expected_foo))] + (_.cover [/.pattern] + (and (let [(/.pattern g!Foo actual_foo) + (is (g!Foo .Module) + (/.abstraction g!Foo expected_foo))] (text#= expected_foo actual_foo)) - (let [(/.^:representation actual_bar) - (: (g!Bar .Module) - (/.:abstraction expected_bar))] + (let [(/.pattern actual_bar) + (is (g!Bar .Module) + (/.abstraction expected_bar))] (n.= expected_bar actual_bar)))) (_.for [/.Frame] ($_ _.and diff --git a/stdlib/source/test/lux/type/check.lux b/stdlib/source/test/lux/type/check.lux index 05ced5386..37c006732 100644 --- a/stdlib/source/test/lux/type/check.lux +++ b/stdlib/source/test/lux/type/check.lux @@ -140,16 +140,16 @@ [expected (random.ascii/upper 10)] (_.cover [/.failure] (case (/.result /.fresh_context - (: (/.Check Any) - (/.failure expected))) + (is (/.Check Any) + (/.failure expected))) {try.#Success _} false {try.#Failure actual} (same? expected actual)))) (do random.monad [expected (random.ascii/upper 10)] (_.cover [/.assertion] (and (case (/.result /.fresh_context - (: (/.Check Any) - (/.assertion expected true))) + (is (/.Check Any) + (/.assertion expected true))) {try.#Success _} true {try.#Failure actual} false) (case (/.result /.fresh_context (/.assertion expected false)) @@ -157,22 +157,22 @@ {try.#Failure actual} (same? expected actual))))) (_.cover [/.except] (case (/.result /.fresh_context - (: (/.Check Any) - (/.except ..yolo []))) + (is (/.Check Any) + (/.except ..yolo []))) {try.#Success _} false {try.#Failure error} (exception.match? ..yolo error))) - (let [scenario (: (-> (-> Text Bit) Type Type Bit) - (function (_ ? <left> <right>) - (and (|> (/.check <left> <right>) - (: (/.Check Any)) - (/.result /.fresh_context) - (pipe.case {try.#Failure error} (? error) - {try.#Success _} false)) - (|> (/.check <right> <left>) - (: (/.Check Any)) - (/.result /.fresh_context) - (pipe.case {try.#Failure error} (? error) - {try.#Success _} false)))))] + (let [scenario (is (-> (-> Text Bit) Type Type Bit) + (function (_ ? <left> <right>) + (and (|> (/.check <left> <right>) + (is (/.Check Any)) + (/.result /.fresh_context) + (pipe.case {try.#Failure error} (? error) + {try.#Success _} false)) + (|> (/.check <right> <left>) + (is (/.Check Any)) + (/.result /.fresh_context) + (pipe.case {try.#Failure error} (? error) + {try.#Success _} false)))))] ($_ _.and (_.cover [/.type_check_failed] (let [scenario (scenario (exception.match? /.type_check_failed))] diff --git a/stdlib/source/test/lux/type/dynamic.lux b/stdlib/source/test/lux/type/dynamic.lux index b4e8536c5..e5c31c177 100644 --- a/stdlib/source/test/lux/type/dynamic.lux +++ b/stdlib/source/test/lux/type/dynamic.lux @@ -1,21 +1,21 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - ["[0]" try] - ["[0]" exception]] - [data - ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}]]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" try] + ["[0]" exception]] + [data + ["[0]" text ("[1]#[0]" equivalence) + ["%" format {"+" format}]]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]]) (def: .public test Test @@ -24,22 +24,22 @@ (do random.monad [expected random.nat] ($_ _.and - (_.cover [/.:dynamic /.:static] - (case (/.:static Nat (/.:dynamic expected)) + (_.cover [/.dynamic /.static] + (case (/.static Nat (/.dynamic expected)) {try.#Success actual} (n.= expected actual) {try.#Failure _} false)) (_.cover [/.wrong_type] - (case (/.:static Text (/.:dynamic expected)) + (case (/.static Text (/.dynamic expected)) {try.#Success actual} false {try.#Failure error} (exception.match? /.wrong_type error))) (_.cover [/.format] - (case (/.format (/.:dynamic expected)) + (case (/.format (/.dynamic expected)) {try.#Success actual} (text#= (%.nat expected) actual) diff --git a/stdlib/source/test/lux/type/quotient.lux b/stdlib/source/test/lux/type/quotient.lux index a81aff6b6..cb0f8bffe 100644 --- a/stdlib/source/test/lux/type/quotient.lux +++ b/stdlib/source/test/lux/type/quotient.lux @@ -1,20 +1,20 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - ["[0]" monad {"+" do}] - [\\specification - ["$[0]" equivalence]]] - [data - ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}]]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat ("[1]#[0]" equivalence)]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + ["[0]" monad {"+" do}] + [\\specification + ["$[0]" equivalence]]] + [data + ["[0]" text ("[1]#[0]" equivalence) + ["%" format {"+" format}]]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat ("[1]#[0]" equivalence)]]]]] + [\\library + ["[0]" /]]) (def: .public (random class super) (All (_ t c %) (-> (/.Class t c %) (Random t) (Random (/.Quotient t c %)))) @@ -31,8 +31,8 @@ (<| (_.covering /._) (do random.monad [modulus (random.only (n.> 0) random.nat) - .let [class (: (-> Nat Text) - (|>> (n.% modulus) %.nat))] + .let [class (is (-> Nat Text) + (|>> (n.% modulus) %.nat))] value random.nat] ($_ _.and (_.for [/.equivalence] @@ -41,8 +41,8 @@ (_.for [/.Class] (_.cover [/.class] - (same? (: Any class) - (: Any (/.class class))))) + (same? (is Any class) + (is Any (/.class class))))) (_.for [/.Quotient] ($_ _.and (_.cover [/.quotient /.value /.label] @@ -53,8 +53,8 @@ (/.label quotient))))) (_.cover [/.type] (exec - (: ..Mod_10 - (/.quotient ..mod_10_class value)) + (is ..Mod_10 + (/.quotient ..mod_10_class value)) true)) )) )))) diff --git a/stdlib/source/test/lux/type/refinement.lux b/stdlib/source/test/lux/type/refinement.lux index d6bd361ed..2d269d300 100644 --- a/stdlib/source/test/lux/type/refinement.lux +++ b/stdlib/source/test/lux/type/refinement.lux @@ -1,21 +1,21 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [predicate {"+" Predicate}] - [monad {"+" do}]] - [control - ["[0]" maybe ("[1]#[0]" monad)]] - [data - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [math - ["[0]" random] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [predicate {"+" Predicate}] + [monad {"+" do}]] + [control + ["[0]" maybe ("[1]#[0]" monad)]] + [data + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [math + ["[0]" random] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]]) (def: _refiner (/.refiner (n.> 123))) @@ -30,8 +30,8 @@ (do [! random.monad] [raw random.nat modulus (# ! each (|>> (n.% 10) (n.+ 2)) random.nat) - .let [predicate (: (Predicate Nat) - (|>> (n.% modulus) (n.= 0)))] + .let [predicate (is (Predicate Nat) + (|>> (n.% modulus) (n.= 0)))] total_raws (# ! each (|>> (n.% 20) ++) random.nat) raws (random.list total_raws random.nat)] ($_ _.and @@ -84,7 +84,7 @@ expected (list#each /.value actual))))) (_.cover [/.type] - (exec (: (Maybe .._type) - (.._refiner raw)) + (exec (is (Maybe .._type) + (.._refiner raw)) true)) )))) diff --git a/stdlib/source/test/lux/type/resource.lux b/stdlib/source/test/lux/type/resource.lux index 366647d5c..2c6b1eb29 100644 --- a/stdlib/source/test/lux/type/resource.lux +++ b/stdlib/source/test/lux/type/resource.lux @@ -1,30 +1,30 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - ["[0]" meta] - [abstract - ["[0]" monad - [indexed {"+" do}]]] - [control - ["[0]" io {"+" IO}] - ["[0]" try] - ["[0]" exception {"+" Exception}] - [concurrency - ["[0]" async {"+" Async}]] - [parser - ["<[0]>" code]]] - [data - ["[0]" identity {"+" Identity}] - ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}]]] - ["[0]" macro - [syntax {"+" syntax:}] - ["[0]" code]] - [math - ["[0]" random]]]] - [\\library - ["[0]" / {"+" Res}]]) + [library + [lux "*" + ["_" test {"+" Test}] + ["[0]" meta] + [abstract + ["[0]" monad + [indexed {"+" do}]]] + [control + ["[0]" io {"+" IO}] + ["[0]" try] + ["[0]" exception {"+" Exception}] + [concurrency + ["[0]" async {"+" Async}]] + [parser + ["<[0]>" code]]] + [data + ["[0]" identity {"+" Identity}] + ["[0]" text ("[1]#[0]" equivalence) + ["%" format {"+" format}]]] + ["[0]" macro + [syntax {"+" syntax:}] + ["[0]" code]] + [math + ["[0]" random]]]] + [\\library + ["[0]" / {"+" Res}]]) (def: pure Test @@ -37,7 +37,7 @@ (~~ (template [<coverage> <bindings>] [(_.cover <coverage> (<| (text#= (format pre post)) - (: (Identity Text)) + (is (Identity Text)) (/.run! !) (do (/.monad !) <bindings> @@ -80,7 +80,7 @@ [(_.cover <coverage> (<| (text#= (format pre post)) io.run! - (: (IO Text)) + (is (IO Text)) (/.run! !) (do (/.monad !) <bindings> @@ -121,7 +121,7 @@ (`` ($_ _.and (~~ (template [<coverage> <bindings>] [(in (monad.do ! - [outcome (<| (: (Async Text)) + [outcome (<| (is (Async Text)) (/.run! !) (do (/.monad !) <bindings> diff --git a/stdlib/source/test/lux/type/unit.lux b/stdlib/source/test/lux/type/unit.lux index 714ea853b..bfcef3bc6 100644 --- a/stdlib/source/test/lux/type/unit.lux +++ b/stdlib/source/test/lux/type/unit.lux @@ -101,8 +101,8 @@ (# ! each (i.% +1,000)) (# ! each (i.* +1,000,000,000)) (# ! each (# /.meter in))) - .let [(open "meter#[0]") (: (Equivalence (/.Qty /.Meter)) - /.equivalence)] + .let [(open "meter#[0]") (is (Equivalence (/.Qty /.Meter)) + /.equivalence)] unscaled (|> random.int (# ! each (i.% +1,000)) (# ! each (i.* (.int how::to))) @@ -113,9 +113,9 @@ [(_.cover [<type> <scale>] (|> large (# <scale> scale) - (: (/.Qty (<type> /.Meter))) + (is (/.Qty (<type> /.Meter))) (# <scale> de_scale) - (: (/.Qty /.Meter)) + (is (/.Qty /.Meter)) (meter#= large)))] [/.Kilo /.kilo] @@ -126,9 +126,9 @@ [(_.cover [<type> <scale>] (|> small (# <scale> scale) - (: (/.Qty (<type> /.Meter))) + (is (/.Qty (<type> /.Meter))) (# <scale> de_scale) - (: (/.Qty /.Meter)) + (is (/.Qty /.Meter)) (meter#= small)))] [/.Milli /.milli] @@ -136,11 +136,11 @@ [/.Nano /.nano] )) (_.cover [/.re_scaled] - (|> large (: (/.Qty /.Meter)) - (# /.kilo scale) (: (/.Qty (/.Kilo /.Meter))) - (/.re_scaled /.kilo /.milli) (: (/.Qty (/.Milli /.Meter))) - (/.re_scaled /.milli /.kilo) (: (/.Qty (/.Kilo /.Meter))) - (# /.kilo de_scale) (: (/.Qty /.Meter)) + (|> large (is (/.Qty /.Meter)) + (# /.kilo scale) (is (/.Qty (/.Kilo /.Meter))) + (/.re_scaled /.kilo /.milli) (is (/.Qty (/.Milli /.Meter))) + (/.re_scaled /.milli /.kilo) (is (/.Qty (/.Kilo /.Meter))) + (# /.kilo de_scale) (is (/.Qty /.Meter)) (meter#= large))) (_.cover [/.scale:] (and (|> unscaled @@ -156,8 +156,8 @@ Test (do random.monad [.let [zero (# /.meter in +0) - (open "meter#[0]") (: (Equivalence (/.Qty /.Meter)) - /.equivalence)] + (open "meter#[0]") (is (Equivalence (/.Qty /.Meter)) + /.equivalence)] left (random.only (|>> (meter#= zero) not) (..meter 1,000)) right (..meter 1,000) extra (..second 1,000)] @@ -172,8 +172,8 @@ )) (_.cover [/.*] (let [expected (i.* (# /.meter out left) (# /.meter out right)) - actual ((debug.private /.out') (: (/.Qty [/.Meter /.Meter]) - (/.* left right)))] + actual ((debug.private /.out') (is (/.Qty [/.Meter /.Meter]) + (/.* left right)))] (i.= expected actual))) (_.cover [/./] (|> right diff --git a/stdlib/source/test/lux/world/file.lux b/stdlib/source/test/lux/world/file.lux index f494b7705..a7e9de34a 100644 --- a/stdlib/source/test/lux/world/file.lux +++ b/stdlib/source/test/lux/world/file.lux @@ -125,8 +125,8 @@ (def: (fs /) (-> Text (/.System IO)) - (let [disk (: (Atom Disk) - (atom.atom (dictionary.empty text.hash))) + (let [disk (is (Atom Disk) + (atom.atom (dictionary.empty text.hash))) mock (/.mock /)] (implementation (def: separator /) diff --git a/stdlib/source/test/lux/world/file/watch.lux b/stdlib/source/test/lux/world/file/watch.lux index cbdb160d9..53263b27a 100644 --- a/stdlib/source/test/lux/world/file/watch.lux +++ b/stdlib/source/test/lux/world/file/watch.lux @@ -99,8 +99,8 @@ (def: (after_creation! fs watcher expected_path) (-> (//.System Async) (/.Watcher Async) //.Path (Async (Try Bit))) (do (try.with async.monad) - [_ (: (Async (Try Any)) - (//.make_file async.monad fs (binary.empty 0) expected_path)) + [_ (is (Async (Try Any)) + (//.make_file async.monad fs (binary.empty 0) expected_path)) poll/pre (# watcher poll []) poll/post (# watcher poll [])] (in (and (case poll/pre diff --git a/stdlib/source/test/lux/world/input/keyboard.lux b/stdlib/source/test/lux/world/input/keyboard.lux index d378cb0ee..97ebb59ac 100644 --- a/stdlib/source/test/lux/world/input/keyboard.lux +++ b/stdlib/source/test/lux/world/input/keyboard.lux @@ -113,9 +113,9 @@ (def: listing (List /.Key) (list.together (`` (list (~~ (template [<definition> <keys>] - [((: (-> Any (List /.Key)) - (function (_ _) - (`` (list (~~ (template.spliced <keys>)))))) + [((is (-> Any (List /.Key)) + (function (_ _) + (`` (list (~~ (template.spliced <keys>)))))) [])] <groups>)))))) diff --git a/stdlib/source/test/lux/world/net/http/client.lux b/stdlib/source/test/lux/world/net/http/client.lux index 3d4de1e0f..1ab2b0a1d 100644 --- a/stdlib/source/test/lux/world/net/http/client.lux +++ b/stdlib/source/test/lux/world/net/http/client.lux @@ -67,27 +67,27 @@ on_trace random.nat num_headers (# ! each (nat.% 10) random.nat) headers (random.dictionary text.hash num_headers (random.ascii/lower 3) (random.ascii/lower 3)) - .let [mock (: (/.Client IO) - (implementation - (def: (request method url headers data) - (io.io (let [value (case method - {//.#Post} on_post - {//.#Get} on_get - {//.#Put} on_put - {//.#Patch} on_patch - {//.#Delete} on_delete - {//.#Head} on_head - {//.#Connect} on_connect - {//.#Options} on_options - {//.#Trace} on_trace) - data (|> value - (# nat.decimal encoded) - (# utf8.codec encoded))] - {try.#Success [//status.ok - [//.#headers headers - //.#body (function (_ ?wanted_bytes) - (io.io {try.#Success [(binary.size data) - data]}))]]})))))]] + .let [mock (is (/.Client IO) + (implementation + (def: (request method url headers data) + (io.io (let [value (case method + {//.#Post} on_post + {//.#Get} on_get + {//.#Put} on_put + {//.#Patch} on_patch + {//.#Delete} on_delete + {//.#Head} on_head + {//.#Connect} on_connect + {//.#Options} on_options + {//.#Trace} on_trace) + data (|> value + (# nat.decimal encoded) + (# utf8.codec encoded))] + {try.#Success [//status.ok + [//.#headers headers + //.#body (function (_ ?wanted_bytes) + (io.io {try.#Success [(binary.size data) + data]}))]]})))))]] (with_expansions [<cases> (as_is [/.post on_post] [/.get on_get] [/.put on_put] diff --git a/stdlib/source/test/lux/world/net/http/status.lux b/stdlib/source/test/lux/world/net/http/status.lux index 97359a058..f6c5a32ab 100644 --- a/stdlib/source/test/lux/world/net/http/status.lux +++ b/stdlib/source/test/lux/world/net/http/status.lux @@ -1,19 +1,19 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [data - [collection - ["[0]" list] - ["[0]" set {"+" Set}]]] - [macro - ["[0]" template]] - [math - [number - ["n" nat]]]]] - [\\library - ["[0]" / - ["/[1]" //]]]) + [library + [lux "*" + ["_" test {"+" Test}] + [data + [collection + ["[0]" list] + ["[0]" set {"+" Set}]]] + [macro + ["[0]" template]] + [math + [number + ["n" nat]]]]] + [\\library + ["[0]" / + ["/[1]" //]]]) (with_expansions [<categories> (as_is [informational [/.continue @@ -85,9 +85,9 @@ (def: all (List //.Status) (list.together (`` (list (~~ (template [<category> <status+>] - [((: (-> Any (List //.Status)) - (function (_ _) - (`` (list (~~ (template.spliced <status+>)))))) + [((is (-> Any (List //.Status)) + (function (_ _) + (`` (list (~~ (template.spliced <status+>)))))) 123)] <categories>)))))) diff --git a/stdlib/source/test/lux/world/shell.lux b/stdlib/source/test/lux/world/shell.lux index 7d62ad2ca..608af1381 100644 --- a/stdlib/source/test/lux/world/shell.lux +++ b/stdlib/source/test/lux/world/shell.lux @@ -1,32 +1,32 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - ["[0]" try {"+" Try}] - ["[0]" exception {"+" exception:}] - ["[0]" io {"+" IO}] - [concurrency - ["[0]" async {"+" Async}]] - [parser - ["[0]" environment {"+" Environment}]]] - [data - ["[0]" text ("[1]#[0]" equivalence)] - [collection - ["[0]" list]]] - [math - ["[0]" random] - [number - ["n" nat] - ["i" int]]]]] - [\\library - ["[0]" / - [// - [file {"+" Path}]]]] - [\\specification - ["$[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" try {"+" Try}] + ["[0]" exception {"+" exception:}] + ["[0]" io {"+" IO}] + [concurrency + ["[0]" async {"+" Async}]] + [parser + ["[0]" environment {"+" Environment}]]] + [data + ["[0]" text ("[1]#[0]" equivalence)] + [collection + ["[0]" list]]] + [math + ["[0]" random] + [number + ["n" nat] + ["i" int]]]]] + [\\library + ["[0]" / + [// + [file {"+" Path}]]]] + [\\specification + ["$[0]" /]]) (exception: dead) @@ -67,7 +67,7 @@ (def: (execute [environment working_directory command arguments]) (<| io.io {try.#Success} - (: (/.Process IO)) + (is (/.Process IO)) (implementation (def: (read _) (io.io {try.#Success command})) |