diff options
Diffstat (limited to '')
-rw-r--r-- | stdlib/source/test/lux/control/parser.lux | 4 | ||||
-rw-r--r-- | stdlib/source/test/lux/control/parser/binary.lux | 392 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/binary.lux | 376 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/format/tar.lux | 6 | ||||
-rw-r--r-- | stdlib/source/test/lux/extension.lux | 20 | ||||
-rw-r--r-- | stdlib/source/test/lux/tool.lux | 7 | ||||
-rw-r--r-- | stdlib/source/test/lux/tool/compiler/language/lux/synthesis.lux (renamed from stdlib/source/test/lux/control/parser/synthesis.lux) | 129 | ||||
-rw-r--r-- | stdlib/source/test/lux/tool/compiler/meta/archive/module/descriptor.lux | 7 | ||||
-rw-r--r-- | stdlib/source/test/lux/tool/compiler/meta/archive/module/document.lux | 7 | ||||
-rw-r--r-- | stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux | 7 | ||||
-rw-r--r-- | stdlib/source/test/lux/tool/compiler/meta/archive/signature.lux | 7 | ||||
-rw-r--r-- | stdlib/source/test/lux/tool/compiler/meta/export.lux | 7 | ||||
-rw-r--r-- | stdlib/source/test/lux/tool/compiler/meta/import.lux | 7 |
13 files changed, 477 insertions, 499 deletions
diff --git a/stdlib/source/test/lux/control/parser.lux b/stdlib/source/test/lux/control/parser.lux index 3b9029fca..cca247004 100644 --- a/stdlib/source/test/lux/control/parser.lux +++ b/stdlib/source/test/lux/control/parser.lux @@ -28,12 +28,10 @@ [\\library ["[0]" / (.only Parser)]] ["[0]" / - ["[1][0]" binary] ["[1][0]" cli] ["[1][0]" code] ["[1][0]" environment] ["[1][0]" json] - ["[1][0]" synthesis] ["[1][0]" tree] ["[1][0]" type] ["[1][0]" xml]]) @@ -384,12 +382,10 @@ ..combinators_1 ..combinators_2 - /binary.test /cli.test /code.test /environment.test /json.test - /synthesis.test /tree.test /type.test /xml.test diff --git a/stdlib/source/test/lux/control/parser/binary.lux b/stdlib/source/test/lux/control/parser/binary.lux deleted file mode 100644 index e8caa2dc9..000000000 --- a/stdlib/source/test/lux/control/parser/binary.lux +++ /dev/null @@ -1,392 +0,0 @@ -(.using - [library - [lux (.except) - ["_" test (.only Test)] - ["[0]" type] - [abstract - [equivalence (.only Equivalence)] - [predicate (.only Predicate)] - [monad (.only do)]] - [control - ["[0]" pipe] - ["[0]" maybe] - ["[0]" try] - ["[0]" exception] - ["<>" parser]] - [data - ["[0]" sum] - ["[0]" bit] - ["[0]" binary (.only) - ["[0]" \\format]] - ["[0]" text (.open: "[1]#[0]" equivalence) - ["%" \\format (.only format)] - [encoding - ["[0]" utf8]]] - [collection - ["[0]" list] - ["[0]" sequence] - ["[0]" set]]] - [macro - ["^" pattern] - ["[0]" code]] - [math - ["[0]" random (.only Random)] - [number - ["n" nat] - ["[0]" i64] - ["[0]" int] - ["[0]" rev] - ["[0]" frac]]] - [meta - ["[0]" symbol]]]] - [\\library - ["[0]" /]]) - -(def: !expect - (template (_ <expectation> <computation>) - [(case <computation> - <expectation> - true - - _ - false)])) - -(def: segment_size 10) - -(def: (utf8_conversion_does_not_alter? value) - (Predicate Text) - (|> value - (at utf8.codec encoded) - (at utf8.codec decoded) - (pipe.case - {try.#Success converted} - (text#= value converted) - - {try.#Failure error} - false))) - -(def: random_text - (Random Text) - (random.only ..utf8_conversion_does_not_alter? - (random.unicode ..segment_size))) - -(def: random_symbol - (Random Symbol) - (random.and ..random_text ..random_text)) - -(def: location_equivalence - (Equivalence Location) - (implementation - (def: (= [expected_module expected_line expected_column] - [sample_module sample_line sample_column]) - (and (text#= expected_module sample_module) - (n.= expected_line sample_line) - (n.= expected_column sample_column))))) - -(def: random_location - (Random Location) - (all random.and - ..random_text - random.nat - random.nat)) - -(def: random_code - (Random Code) - (random.rec - (function (_ again) - (let [random_sequence (do [! random.monad] - [size (at ! each (n.% 2) random.nat)] - (random.list size again))] - (all random.and - ..random_location - (is (Random (Code' (Ann Location))) - (all 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) - (let [(open "[0]") random.monad] - (all random.either - (in .Nat) - (in .List) - (in .Code) - (in .Type)))) - -(def: size - Test - (<| (_.for [/.Size]) - (`` (all _.and - (~~ (with_template [<size> <parser> <format>] - [(do [! random.monad] - [expected (at ! each (i64.and (i64.mask <size>)) - random.nat)] - (_.coverage [<size> <parser> <format>] - (|> (\\format.result <format> expected) - (/.result <parser>) - (!expect (^.multi {try.#Success actual} - (n.= (.nat expected) - (.nat actual)))))))] - - [/.size_8 /.bits_8 \\format.bits_8] - [/.size_16 /.bits_16 \\format.bits_16] - [/.size_32 /.bits_32 \\format.bits_32] - [/.size_64 /.bits_64 \\format.bits_64] - )))))) - -(def: binary - Test - (`` (all _.and - (~~ (with_template [<parser> <format>] - [(do [! random.monad] - [expected (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))] - (_.coverage [<parser> <format>] - (|> (\\format.result <format> expected) - (/.result <parser>) - (!expect (^.multi {try.#Success actual} - (at binary.equivalence = expected actual))))))] - - [/.binary_8 \\format.binary_8] - [/.binary_16 \\format.binary_16] - [/.binary_32 \\format.binary_32] - [/.binary_64 \\format.binary_64] - ))))) - -(def: utf8 - Test - (`` (all _.and - (~~ (with_template [<parser> <format>] - [(do [! random.monad] - [expected (random.ascii ..segment_size)] - (_.coverage [<parser> <format>] - (|> (\\format.result <format> expected) - (/.result <parser>) - (!expect (^.multi {try.#Success actual} - (at text.equivalence = expected actual))))))] - - [/.utf8_8 \\format.utf8_8] - [/.utf8_16 \\format.utf8_16] - [/.utf8_32 \\format.utf8_32] - [/.utf8_64 \\format.utf8_64] - [/.text \\format.text] - ))))) - -(def: sequence - Test - (`` (all _.and - (~~ (with_template [<parser> <format>] - [(do [! random.monad] - [expected (random.sequence ..segment_size random.nat)] - (_.coverage [<parser> <format>] - (|> expected - (\\format.result (<format> \\format.nat)) - (/.result (<parser> /.nat)) - (!expect (^.multi {try.#Success actual} - (at (sequence.equivalence n.equivalence) = expected actual))))))] - - [/.sequence_8 \\format.sequence_8] - [/.sequence_16 \\format.sequence_16] - [/.sequence_32 \\format.sequence_32] - [/.sequence_64 \\format.sequence_64] - ))))) - -(def: simple - Test - (`` (all _.and - (~~ (with_template [<parser> <format> <random> <equivalence>] - [(do [! random.monad] - [expected <random>] - (_.coverage [<parser> <format>] - (|> expected - (\\format.result <format>) - (/.result <parser>) - (!expect (^.multi {try.#Success actual} - (at <equivalence> = expected actual))))))] - - [/.bit \\format.bit random.bit bit.equivalence] - [/.nat \\format.nat random.nat n.equivalence] - [/.int \\format.int random.int int.equivalence] - [/.rev \\format.rev random.rev rev.equivalence])) - (do [! random.monad] - [expected random.frac] - (_.coverage [/.frac \\format.frac] - (|> expected - (\\format.result \\format.frac) - (/.result /.frac) - (!expect (^.multi {try.#Success actual} - (or (at frac.equivalence = expected actual) - (and (frac.not_a_number? expected) - (frac.not_a_number? actual)))))))) - (do [! random.monad] - [expected (at ! each (|>> (i64.and (i64.mask /.size_8)) - (n.max 2)) - random.nat)] - (_.coverage [/.not_a_bit] - (|> expected - (\\format.result \\format.bits_8) - (/.result /.bit) - (!expect (^.multi {try.#Failure error} - (exception.match? /.not_a_bit error)))))) - ))) - -(def: complex - Test - (`` (all _.and - (~~ (with_template [<parser> <format> <random> <equivalence>] - [(do [! random.monad] - [expected <random>] - (_.coverage [<parser> <format>] - (|> expected - (\\format.result <format>) - (/.result <parser>) - (!expect (^.multi {try.#Success actual} - (at <equivalence> = expected actual))))))] - - [/.location \\format.location random_location location_equivalence] - [/.code \\format.code random_code code.equivalence] - [/.type \\format.type random_type type.equivalence] - )) - (~~ (with_template [<parser_coverage> <parser> <coverage_format> <format> <random> <equivalence>] - [(do [! random.monad] - [expected <random>] - (_.coverage [<parser_coverage> <coverage_format>] - (|> expected - (\\format.result <format>) - (/.result <parser>) - (!expect (^.multi {try.#Success actual} - (at <equivalence> = expected actual))))))] - - [/.maybe (/.maybe /.nat) \\format.maybe (\\format.maybe \\format.nat) (random.maybe random.nat) (maybe.equivalence n.equivalence)] - [/.list (/.list /.nat) \\format.list (\\format.list \\format.nat) (random.list ..segment_size random.nat) (list.equivalence n.equivalence)] - [/.set (/.set n.hash /.nat) \\format.set (\\format.set \\format.nat) (random.set n.hash ..segment_size random.nat) set.equivalence] - [/.symbol /.symbol \\format.symbol \\format.symbol ..random_symbol symbol.equivalence])) - (do [! random.monad] - [expected (at ! each (list.repeated ..segment_size) random.nat)] - (_.coverage [/.set_elements_are_not_unique] - (|> expected - (\\format.result (\\format.list \\format.nat)) - (/.result (/.set n.hash /.nat)) - (!expect (^.multi {try.#Failure error} - (exception.match? /.set_elements_are_not_unique error)))))) - (do [! random.monad] - [expected (random.or random.bit random.nat)] - (_.coverage [/.or \\format.or] - (|> expected - (\\format.result (\\format.or \\format.bit \\format.nat)) - (/.result (is (/.Parser (Either Bit Nat)) - (/.or /.bit /.nat))) - (!expect (^.multi {try.#Success actual} - (at (sum.equivalence bit.equivalence n.equivalence) = - expected - actual)))))) - (do [! random.monad] - [tag (at ! each (|>> (i64.and (i64.mask /.size_8)) - (n.max 2)) - random.nat) - value random.bit] - (_.coverage [/.invalid_tag] - (|> [tag value] - (\\format.result (\\format.and \\format.bits_8 \\format.bit)) - (/.result (is (/.Parser (Either Bit Nat)) - (/.or /.bit /.nat))) - (!expect (^.multi {try.#Failure error} - (exception.match? /.invalid_tag error)))))) - (do [! random.monad] - [expected (random.list ..segment_size random.nat)] - (_.coverage [/.rec \\format.rec \\format.and \\format.any] - (|> expected - (\\format.result (\\format.rec (|>> (\\format.and \\format.nat) - (\\format.or \\format.any)))) - (/.result (is (/.Parser (List Nat)) - (/.rec - (function (_ again) - (/.or /.any - (<>.and /.nat - again)))))) - (!expect (^.multi {try.#Success actual} - (at (list.equivalence n.equivalence) = - expected - actual)))))) - ))) - -(def: .public test - Test - (<| (_.covering /._) - (_.for [/.Parser]) - (`` (all _.and - (_.coverage [/.result /.any - \\format.no_op \\format.instance] - (|> (\\format.instance \\format.no_op) - (/.result /.any) - (!expect {try.#Success _}))) - (do [! random.monad] - [data (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))] - (_.coverage [/.binary_was_not_fully_read] - (|> data - (/.result /.any) - (!expect (^.multi {try.#Failure error} - (exception.match? /.binary_was_not_fully_read error)))))) - (do [! random.monad] - [expected (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))] - (_.coverage [/.segment \\format.segment \\format.result] - (|> expected - (\\format.result (\\format.segment ..segment_size)) - (/.result (/.segment ..segment_size)) - (!expect (^.multi {try.#Success actual} - (at binary.equivalence = expected actual)))))) - (do [! random.monad] - [data (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))] - (_.coverage [/.end?] - (|> data - (/.result (do <>.monad - [pre /.end? - _ (/.segment ..segment_size) - post /.end?] - (in (and (not pre) - post)))) - (!expect {try.#Success #1})))) - (do [! random.monad] - [to_read (at ! each (n.% (++ ..segment_size)) random.nat) - data (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))] - (_.coverage [/.Offset /.offset] - (|> data - (/.result (do <>.monad - [start /.offset - _ (/.segment to_read) - offset /.offset - _ (/.segment (n.- to_read ..segment_size)) - nothing_left /.offset] - (in (and (n.= 0 start) - (n.= to_read offset) - (n.= ..segment_size nothing_left))))) - (!expect {try.#Success #1})))) - (do [! random.monad] - [to_read (at ! each (n.% (++ ..segment_size)) random.nat) - data (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))] - (_.coverage [/.remaining] - (|> data - (/.result (do <>.monad - [_ (/.segment to_read) - remaining /.remaining - _ (/.segment (n.- to_read ..segment_size)) - nothing_left /.remaining] - (in (and (n.= ..segment_size - (n.+ to_read remaining)) - (n.= 0 nothing_left))))) - (!expect {try.#Success #1})))) - ..size - ..binary - ..utf8 - ..sequence - ..simple - ..complex - )))) diff --git a/stdlib/source/test/lux/data/binary.lux b/stdlib/source/test/lux/data/binary.lux index 50a3f786f..691b6ff55 100644 --- a/stdlib/source/test/lux/data/binary.lux +++ b/stdlib/source/test/lux/data/binary.lux @@ -3,30 +3,401 @@ [lux (.except) [ffi (.only)] ["_" test (.only Test)] + ["[0]" type] [abstract [equivalence (.only Equivalence)] + [predicate (.only Predicate)] ["[0]" monad (.only do)] ["[0]" enum] [\\specification ["$[0]" equivalence] ["$[0]" monoid]]] [control + ["<>" parser] + ["[0]" pipe] + ["[0]" maybe] ["[0]" try (.only Try)] ["[0]" exception (.only Exception)]] [data + ["[0]" sum] + ["[0]" bit] + ["[0]" text (.open: "[1]#[0]" equivalence) + ["%" \\format (.only format)] + [encoding + ["[0]" utf8]]] [collection ["[0]" list (.open: "[1]#[0]" functor)] + ["[0]" sequence] + ["[0]" set] [array [\\unsafe (.only)]]]] + [macro + ["^" pattern] + ["[0]" code]] [math ["[0]" random (.only Random)] [number ["n" nat] - ["[0]" i64]]]]] + ["[0]" i64] + ["[0]" int] + ["[0]" rev] + ["[0]" frac]]] + [meta + ["[0]" symbol]]]] [\\library ["[0]" / (.only) (.open: "[1]#[0]" equivalence) ["!" \\unsafe] - ["[0]" \\format]]]) + ["[0]" \\format] + ["[0]" \\parser]]]) + +(def: !expect + (template (_ <expectation> <computation>) + [(case <computation> + <expectation> + true + + _ + false)])) + +(def: segment_size 10) + +(def: (utf8_conversion_does_not_alter? value) + (Predicate Text) + (|> value + (at utf8.codec encoded) + (at utf8.codec decoded) + (pipe.case + {try.#Success converted} + (text#= value converted) + + {try.#Failure error} + false))) + +(def: random_text + (Random Text) + (random.only ..utf8_conversion_does_not_alter? + (random.unicode ..segment_size))) + +(def: random_symbol + (Random Symbol) + (random.and ..random_text ..random_text)) + +(def: location_equivalence + (Equivalence Location) + (implementation + (def: (= [expected_module expected_line expected_column] + [sample_module sample_line sample_column]) + (and (text#= expected_module sample_module) + (n.= expected_line sample_line) + (n.= expected_column sample_column))))) + +(def: random_location + (Random Location) + (all random.and + ..random_text + random.nat + random.nat)) + +(def: random_code + (Random Code) + (random.rec + (function (_ again) + (let [random_sequence (do [! random.monad] + [size (at ! each (n.% 2) random.nat)] + (random.list size again))] + (all random.and + ..random_location + (is (Random (Code' (Ann Location))) + (all 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) + (let [(open "[0]") random.monad] + (all random.either + (in .Nat) + (in .List) + (in .Code) + (in .Type)))) + +(def: size + Test + (<| (_.for [\\parser.Size]) + (`` (all _.and + (~~ (with_template [<size> <parser> <format>] + [(do [! random.monad] + [expected (at ! each (i64.and (i64.mask <size>)) + random.nat)] + (_.coverage [<size> <parser> <format>] + (|> (\\format.result <format> expected) + (\\parser.result <parser>) + (!expect (^.multi {try.#Success actual} + (n.= (.nat expected) + (.nat actual)))))))] + + [\\parser.size_8 \\parser.bits_8 \\format.bits_8] + [\\parser.size_16 \\parser.bits_16 \\format.bits_16] + [\\parser.size_32 \\parser.bits_32 \\format.bits_32] + [\\parser.size_64 \\parser.bits_64 \\format.bits_64] + )))))) + +(def: binary + Test + (`` (all _.and + (~~ (with_template [<parser> <format>] + [(do [! random.monad] + [expected (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))] + (_.coverage [<parser> <format>] + (|> (\\format.result <format> expected) + (\\parser.result <parser>) + (!expect (^.multi {try.#Success actual} + (at /.equivalence = expected actual))))))] + + [\\parser.binary_8 \\format.binary_8] + [\\parser.binary_16 \\format.binary_16] + [\\parser.binary_32 \\format.binary_32] + [\\parser.binary_64 \\format.binary_64] + ))))) + +(def: utf8 + Test + (`` (all _.and + (~~ (with_template [<parser> <format>] + [(do [! random.monad] + [expected (random.ascii ..segment_size)] + (_.coverage [<parser> <format>] + (|> (\\format.result <format> expected) + (\\parser.result <parser>) + (!expect (^.multi {try.#Success actual} + (at text.equivalence = expected actual))))))] + + [\\parser.utf8_8 \\format.utf8_8] + [\\parser.utf8_16 \\format.utf8_16] + [\\parser.utf8_32 \\format.utf8_32] + [\\parser.utf8_64 \\format.utf8_64] + [\\parser.text \\format.text] + ))))) + +(def: sequence + Test + (`` (all _.and + (~~ (with_template [<parser> <format>] + [(do [! random.monad] + [expected (random.sequence ..segment_size random.nat)] + (_.coverage [<parser> <format>] + (|> expected + (\\format.result (<format> \\format.nat)) + (\\parser.result (<parser> \\parser.nat)) + (!expect (^.multi {try.#Success actual} + (at (sequence.equivalence n.equivalence) = expected actual))))))] + + [\\parser.sequence_8 \\format.sequence_8] + [\\parser.sequence_16 \\format.sequence_16] + [\\parser.sequence_32 \\format.sequence_32] + [\\parser.sequence_64 \\format.sequence_64] + ))))) + +(def: simple + Test + (`` (all _.and + (~~ (with_template [<parser> <format> <random> <equivalence>] + [(do [! random.monad] + [expected <random>] + (_.coverage [<parser> <format>] + (|> expected + (\\format.result <format>) + (\\parser.result <parser>) + (!expect (^.multi {try.#Success actual} + (at <equivalence> = expected actual))))))] + + [\\parser.bit \\format.bit random.bit bit.equivalence] + [\\parser.nat \\format.nat random.nat n.equivalence] + [\\parser.int \\format.int random.int int.equivalence] + [\\parser.rev \\format.rev random.rev rev.equivalence])) + (do [! random.monad] + [expected random.frac] + (_.coverage [\\parser.frac \\format.frac] + (|> expected + (\\format.result \\format.frac) + (\\parser.result \\parser.frac) + (!expect (^.multi {try.#Success actual} + (or (at frac.equivalence = expected actual) + (and (frac.not_a_number? expected) + (frac.not_a_number? actual)))))))) + (do [! random.monad] + [expected (at ! each (|>> (i64.and (i64.mask \\parser.size_8)) + (n.max 2)) + random.nat)] + (_.coverage [\\parser.not_a_bit] + (|> expected + (\\format.result \\format.bits_8) + (\\parser.result \\parser.bit) + (!expect (^.multi {try.#Failure error} + (exception.match? \\parser.not_a_bit error)))))) + ))) + +(def: complex + Test + (`` (all _.and + (~~ (with_template [<parser> <format> <random> <equivalence>] + [(do [! random.monad] + [expected <random>] + (_.coverage [<parser> <format>] + (|> expected + (\\format.result <format>) + (\\parser.result <parser>) + (!expect (^.multi {try.#Success actual} + (at <equivalence> = expected actual))))))] + + [\\parser.location \\format.location random_location location_equivalence] + [\\parser.code \\format.code random_code code.equivalence] + [\\parser.type \\format.type random_type type.equivalence] + )) + (~~ (with_template [<parser_coverage> <parser> <coverage_format> <format> <random> <equivalence>] + [(do [! random.monad] + [expected <random>] + (_.coverage [<parser_coverage> <coverage_format>] + (|> expected + (\\format.result <format>) + (\\parser.result <parser>) + (!expect (^.multi {try.#Success actual} + (at <equivalence> = expected actual))))))] + + [\\parser.maybe (\\parser.maybe \\parser.nat) \\format.maybe (\\format.maybe \\format.nat) (random.maybe random.nat) (maybe.equivalence n.equivalence)] + [\\parser.list (\\parser.list \\parser.nat) \\format.list (\\format.list \\format.nat) (random.list ..segment_size random.nat) (list.equivalence n.equivalence)] + [\\parser.set (\\parser.set n.hash \\parser.nat) \\format.set (\\format.set \\format.nat) (random.set n.hash ..segment_size random.nat) set.equivalence] + [\\parser.symbol \\parser.symbol \\format.symbol \\format.symbol ..random_symbol symbol.equivalence])) + (do [! random.monad] + [expected (at ! each (list.repeated ..segment_size) random.nat)] + (_.coverage [\\parser.set_elements_are_not_unique] + (|> expected + (\\format.result (\\format.list \\format.nat)) + (\\parser.result (\\parser.set n.hash \\parser.nat)) + (!expect (^.multi {try.#Failure error} + (exception.match? \\parser.set_elements_are_not_unique error)))))) + (do [! random.monad] + [expected (random.or random.bit random.nat)] + (_.coverage [\\parser.or \\format.or] + (|> expected + (\\format.result (\\format.or \\format.bit \\format.nat)) + (\\parser.result (is (\\parser.Parser (Either Bit Nat)) + (\\parser.or \\parser.bit \\parser.nat))) + (!expect (^.multi {try.#Success actual} + (at (sum.equivalence bit.equivalence n.equivalence) = + expected + actual)))))) + (do [! random.monad] + [tag (at ! each (|>> (i64.and (i64.mask \\parser.size_8)) + (n.max 2)) + random.nat) + value random.bit] + (_.coverage [\\parser.invalid_tag] + (|> [tag value] + (\\format.result (\\format.and \\format.bits_8 \\format.bit)) + (\\parser.result (is (\\parser.Parser (Either Bit Nat)) + (\\parser.or \\parser.bit \\parser.nat))) + (!expect (^.multi {try.#Failure error} + (exception.match? \\parser.invalid_tag error)))))) + (do [! random.monad] + [expected (random.list ..segment_size random.nat)] + (_.coverage [\\parser.rec \\format.rec \\format.and \\format.any] + (|> expected + (\\format.result (\\format.rec (|>> (\\format.and \\format.nat) + (\\format.or \\format.any)))) + (\\parser.result (is (\\parser.Parser (List Nat)) + (\\parser.rec + (function (_ again) + (\\parser.or \\parser.any + (<>.and \\parser.nat + again)))))) + (!expect (^.multi {try.#Success actual} + (at (list.equivalence n.equivalence) = + expected + actual)))))) + ))) + +(def: \\parser + Test + (<| (_.covering \\parser._) + (_.for [\\parser.Parser]) + (`` (all _.and + (_.coverage [\\parser.result \\parser.any + \\format.no_op \\format.instance] + (|> (\\format.instance \\format.no_op) + (\\parser.result \\parser.any) + (!expect {try.#Success _}))) + (do [! random.monad] + [data (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))] + (_.coverage [\\parser.binary_was_not_fully_read] + (|> data + (\\parser.result \\parser.any) + (!expect (^.multi {try.#Failure error} + (exception.match? \\parser.binary_was_not_fully_read error)))))) + (do [! random.monad] + [expected (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))] + (_.coverage [\\parser.segment \\format.segment \\format.result] + (|> expected + (\\format.result (\\format.segment ..segment_size)) + (\\parser.result (\\parser.segment ..segment_size)) + (!expect (^.multi {try.#Success actual} + (at /.equivalence = expected actual)))))) + (do [! random.monad] + [data (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))] + (_.coverage [\\parser.end?] + (|> data + (\\parser.result (do <>.monad + [pre \\parser.end? + _ (\\parser.segment ..segment_size) + post \\parser.end?] + (in (and (not pre) + post)))) + (!expect {try.#Success #1})))) + (do [! random.monad] + [to_read (at ! each (n.% (++ ..segment_size)) random.nat) + data (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))] + (_.coverage [\\parser.Offset \\parser.offset] + (|> data + (\\parser.result (do <>.monad + [start \\parser.offset + _ (\\parser.segment to_read) + offset \\parser.offset + _ (\\parser.segment (n.- to_read ..segment_size)) + nothing_left \\parser.offset] + (in (and (n.= 0 start) + (n.= to_read offset) + (n.= ..segment_size nothing_left))))) + (!expect {try.#Success #1})))) + (do [! random.monad] + [to_read (at ! each (n.% (++ ..segment_size)) random.nat) + data (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))] + (_.coverage [\\parser.remaining] + (|> data + (\\parser.result (do <>.monad + [_ (\\parser.segment to_read) + remaining \\parser.remaining + _ (\\parser.segment (n.- to_read ..segment_size)) + nothing_left \\parser.remaining] + (in (and (n.= ..segment_size + (n.+ to_read remaining)) + (n.= 0 nothing_left))))) + (!expect {try.#Success #1})))) + ..size + ..binary + ..utf8 + ..sequence + ..simple + ..complex + )))) (def: equivalence (Equivalence \\format.Specification) @@ -263,4 +634,5 @@ ..test|unsafe ..\\format + ..\\parser )))) diff --git a/stdlib/source/test/lux/data/format/tar.lux b/stdlib/source/test/lux/data/format/tar.lux index ba81d4153..16bf8fb62 100644 --- a/stdlib/source/test/lux/data/format/tar.lux +++ b/stdlib/source/test/lux/data/format/tar.lux @@ -5,14 +5,14 @@ [abstract [monad (.only do)]] [control + ["<>" parser (.only)] ["[0]" maybe] ["[0]" try] - ["[0]" exception] - ["<>" parser (.only) - ["<b>" binary]]] + ["[0]" exception]] [data ["[0]" product] ["[0]" binary (.open: "[1]#[0]" equivalence monoid) + ["<b>" \\parser] ["[0]" \\format]] ["[0]" text (.open: "[1]#[0]" equivalence) ["%" \\format (.only format)] diff --git a/stdlib/source/test/lux/extension.lux b/stdlib/source/test/lux/extension.lux index 70984d45e..30accf1b0 100644 --- a/stdlib/source/test/lux/extension.lux +++ b/stdlib/source/test/lux/extension.lux @@ -21,8 +21,7 @@ [control ["[0]" try (.open: "[1]#[0]" functor)] ["<>" parser (.only) - ["<[0]>" code] - ["<[0]>" synthesis]]] + ["<[0]>" code]]] [data ["[0]" product] ["[0]" binary (.only) @@ -46,12 +45,13 @@ ["[0]" unit]]] [language [lux - ["[0]" synthesis] ["[0]" generation] ["[0]" directive] ["[0]" analysis (.only) ["[0]" type] ["<[1]>" \\parser]] + ["[0]" synthesis (.only) + ["<[1]>" \\parser]] [phase [generation (~~ (.for "JVM" (~~ (.these ["[0]" jvm @@ -159,13 +159,13 @@ (try.else (binary.empty 0)) (try#each (binaryF.result class.writer)) (class.class version.v6_0 class.public - (name.internal $class) - {.#None} - (name.internal "java.lang.Object") - (list) - (list) - (list) - sequence.empty))) + (name.internal $class) + {.#None} + (name.internal "java.lang.Object") + (list) + (list) + (list) + sequence.empty))) @.js (js.comment commentary (js.statement (js.string commentary))) @.python (python.comment commentary diff --git a/stdlib/source/test/lux/tool.lux b/stdlib/source/test/lux/tool.lux index 542b33921..217647f2e 100644 --- a/stdlib/source/test/lux/tool.lux +++ b/stdlib/source/test/lux/tool.lux @@ -12,9 +12,7 @@ [lux ... ["[1][0]" syntax] ["[1][0]" analysis] - ["[1][0]" synthesis - ["[1]/[0]" simple] - ["[1]/[0]" access]] + ["[1][0]" synthesis] ["[1][0]" phase ["[1]/[0]" extension] ["[1]/[0]" analysis] @@ -37,8 +35,7 @@ /reference.test /phase.test /analysis.test - /synthesis/simple.test - /synthesis/access.test + /synthesis.test /meta/archive.test /meta/cli.test /meta/export.test diff --git a/stdlib/source/test/lux/control/parser/synthesis.lux b/stdlib/source/test/lux/tool/compiler/language/lux/synthesis.lux index 9f765d0a5..38d846740 100644 --- a/stdlib/source/test/lux/control/parser/synthesis.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/synthesis.lux @@ -31,8 +31,10 @@ [lux [analysis (.only Environment)] ["[0]" synthesis (.only Synthesis)]]]]]]] - [\\library - ["[0]" /]]) + ["[0]" \\parser] + ["[0]" / + ["[1][0]" simple] + ["[1][0]" access]]) (def: !expect (template (_ <pattern> <value>) @@ -70,24 +72,24 @@ dummy (|> <random> (random.only (|>> (at <equivalence> = expected) not)))] (all _.and (_.coverage [<query>] - (|> (/.result <query> (list (<synthesis> expected))) + (|> (\\parser.result <query> (list (<synthesis> expected))) (!expect (^.multi {try.#Success actual} (at <equivalence> = expected actual))))) (_.coverage [<check>] - (and (|> (/.result (<check> expected) (list (<synthesis> expected))) + (and (|> (\\parser.result (<check> expected) (list (<synthesis> expected))) (!expect {try.#Success _})) - (|> (/.result (<check> expected) (list (<synthesis> dummy))) + (|> (\\parser.result (<check> expected) (list (<synthesis> dummy))) (!expect (^.multi {try.#Failure error} - (exception.match? /.cannot_parse error)))))) + (exception.match? \\parser.cannot_parse error)))))) ))] - [/.bit /.this_bit random.bit synthesis.bit bit.equivalence] - [/.i64 /.this_i64 random.i64 synthesis.i64 i64.equivalence] - [/.f64 /.this_f64 random.safe_frac synthesis.f64 frac.equivalence] - [/.text /.this_text (random.unicode 1) synthesis.text text.equivalence] - [/.local /.this_local random.nat synthesis.variable/local n.equivalence] - [/.foreign /.this_foreign random.nat synthesis.variable/foreign n.equivalence] - [/.constant /.this_constant ..random_constant synthesis.constant symbol.equivalence] + [\\parser.bit \\parser.this_bit random.bit synthesis.bit bit.equivalence] + [\\parser.i64 \\parser.this_i64 random.i64 synthesis.i64 i64.equivalence] + [\\parser.f64 \\parser.this_f64 random.safe_frac synthesis.f64 frac.equivalence] + [\\parser.text \\parser.this_text (random.unicode 1) synthesis.text text.equivalence] + [\\parser.local \\parser.this_local random.nat synthesis.variable/local n.equivalence] + [\\parser.foreign \\parser.this_foreign random.nat synthesis.variable/foreign n.equivalence] + [\\parser.constant \\parser.this_constant ..random_constant synthesis.constant symbol.equivalence] )) ))) @@ -99,107 +101,116 @@ expected_i64 random.i64 expected_f64 random.safe_frac expected_text (random.unicode 1)] - (_.coverage [/.tuple] - (and (|> (/.result (/.tuple (all <>.and /.bit /.i64 /.f64 /.text)) - (list (synthesis.tuple (list (synthesis.bit expected_bit) - (synthesis.i64 expected_i64) - (synthesis.f64 expected_f64) - (synthesis.text expected_text))))) + (_.coverage [\\parser.tuple] + (and (|> (\\parser.result (\\parser.tuple (all <>.and \\parser.bit \\parser.i64 \\parser.f64 \\parser.text)) + (list (synthesis.tuple (list (synthesis.bit expected_bit) + (synthesis.i64 expected_i64) + (synthesis.f64 expected_f64) + (synthesis.text expected_text))))) (!expect (^.multi {try.#Success [actual_bit actual_i64 actual_f64 actual_text]} (and (at bit.equivalence = expected_bit actual_bit) (at i64.equivalence = expected_i64 actual_i64) (at frac.equivalence = expected_f64 actual_f64) (at text.equivalence = expected_text actual_text))))) - (|> (/.result (/.tuple (all <>.and /.bit /.i64 /.f64 /.text)) - (list (synthesis.text expected_text))) + (|> (\\parser.result (\\parser.tuple (all <>.and \\parser.bit \\parser.i64 \\parser.f64 \\parser.text)) + (list (synthesis.text expected_text))) (!expect (^.multi {try.#Failure error} - (exception.match? /.cannot_parse error))))))) + (exception.match? \\parser.cannot_parse error))))))) (do [! random.monad] [arity random.nat expected_environment ..random_environment expected_body (random.unicode 1)] - (_.coverage [/.function] - (and (|> (/.result (/.function arity /.text) - (list (synthesis.function/abstraction [expected_environment arity (synthesis.text expected_body)]))) + (_.coverage [\\parser.function] + (and (|> (\\parser.result (\\parser.function arity \\parser.text) + (list (synthesis.function/abstraction [expected_environment arity (synthesis.text expected_body)]))) (!expect (^.multi {try.#Success [actual_environment actual_body]} (and (at (list.equivalence synthesis.equivalence) = expected_environment actual_environment) (at text.equivalence = expected_body actual_body))))) - (|> (/.result (/.function arity /.text) - (list (synthesis.text expected_body))) + (|> (\\parser.result (\\parser.function arity \\parser.text) + (list (synthesis.text expected_body))) (!expect (^.multi {try.#Failure error} - (exception.match? /.cannot_parse error))))))) + (exception.match? \\parser.cannot_parse error))))))) (do [! random.monad] [arity random.nat expected_environment ..random_environment expected_body (random.unicode 1)] - (_.coverage [/.wrong_arity] - (|> (/.result (/.function (++ arity) /.text) - (list (synthesis.function/abstraction [expected_environment arity (synthesis.text expected_body)]))) + (_.coverage [\\parser.wrong_arity] + (|> (\\parser.result (\\parser.function (++ arity) \\parser.text) + (list (synthesis.function/abstraction [expected_environment arity (synthesis.text expected_body)]))) (!expect (^.multi {try.#Failure error} - (exception.match? /.wrong_arity error)))))) + (exception.match? \\parser.wrong_arity error)))))) (do [! random.monad] [arity (at ! each (|>> (n.% 10) ++) random.nat) expected_offset random.nat expected_inits (random.list arity random.bit) expected_body (random.unicode 1)] - (_.coverage [/.loop] - (and (|> (/.result (/.loop (<>.many /.bit) /.text) - (list (synthesis.loop/scope [expected_offset - (list#each (|>> synthesis.bit) expected_inits) - (synthesis.text expected_body)]))) + (_.coverage [\\parser.loop] + (and (|> (\\parser.result (\\parser.loop (<>.many \\parser.bit) \\parser.text) + (list (synthesis.loop/scope [expected_offset + (list#each (|>> synthesis.bit) expected_inits) + (synthesis.text expected_body)]))) (!expect (^.multi {try.#Success [actual_offset actual_inits actual_body]} (and (at n.equivalence = expected_offset actual_offset) (at (list.equivalence bit.equivalence) = expected_inits actual_inits) (at text.equivalence = expected_body actual_body))))) - (|> (/.result (/.loop (<>.many /.bit) /.text) - (list (synthesis.text expected_body))) + (|> (\\parser.result (\\parser.loop (<>.many \\parser.bit) \\parser.text) + (list (synthesis.text expected_body))) (!expect (^.multi {try.#Failure error} - (exception.match? /.cannot_parse error))))))) + (exception.match? \\parser.cannot_parse error))))))) )) -(def: .public test +(def: \\parser Test - (<| (_.covering /._) - (_.for [/.Parser]) + (<| (_.covering \\parser._) + (_.for [\\parser.Parser]) (all _.and (do [! random.monad] [expected (at ! each (|>> synthesis.i64) random.i64)] - (_.coverage [/.result /.any] - (|> (/.result /.any (list expected)) + (_.coverage [\\parser.result \\parser.any] + (|> (\\parser.result \\parser.any (list expected)) (!expect (^.multi {try.#Success actual} (at synthesis.equivalence = expected actual)))))) - (_.coverage [/.empty_input] - (|> (/.result /.any (list)) + (_.coverage [\\parser.empty_input] + (|> (\\parser.result \\parser.any (list)) (!expect (^.multi {try.#Failure error} - (exception.match? /.empty_input error))))) + (exception.match? \\parser.empty_input error))))) (do [! random.monad] [expected (at ! each (|>> synthesis.i64) random.i64)] - (_.coverage [/.unconsumed_input] - (|> (/.result /.any (list expected expected)) + (_.coverage [\\parser.unconsumed_input] + (|> (\\parser.result \\parser.any (list expected expected)) (!expect (^.multi {try.#Failure error} - (exception.match? /.unconsumed_input error)))))) + (exception.match? \\parser.unconsumed_input error)))))) (do [! random.monad] [dummy (at ! each (|>> synthesis.i64) random.i64)] - (_.coverage [/.end /.expected_empty_input] - (and (|> (/.result /.end (list)) + (_.coverage [\\parser.end \\parser.expected_empty_input] + (and (|> (\\parser.result \\parser.end (list)) (!expect {try.#Success _})) - (|> (/.result /.end (list dummy)) + (|> (\\parser.result \\parser.end (list dummy)) (!expect (^.multi {try.#Failure error} - (exception.match? /.expected_empty_input error))))))) + (exception.match? \\parser.expected_empty_input error))))))) (do [! random.monad] [dummy (at ! each (|>> synthesis.i64) random.i64)] - (_.coverage [/.end?] - (and (|> (/.result /.end? (list)) + (_.coverage [\\parser.end?] + (and (|> (\\parser.result \\parser.end? (list)) (!expect {try.#Success #1})) - (|> (/.result (<>.before /.any /.end?) (list dummy)) + (|> (\\parser.result (<>.before \\parser.any \\parser.end?) (list dummy)) (!expect {try.#Success #0}))))) - (_.for [/.cannot_parse] + (_.for [\\parser.cannot_parse] (all _.and ..simple ..complex )) ))) + +(def: .public test + Test + (all _.and + ..\\parser + + /simple.test + /access.test + )) diff --git a/stdlib/source/test/lux/tool/compiler/meta/archive/module/descriptor.lux b/stdlib/source/test/lux/tool/compiler/meta/archive/module/descriptor.lux index cc9093286..6d2acbc82 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/archive/module/descriptor.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/archive/module/descriptor.lux @@ -7,13 +7,12 @@ [\\specification ["$[0]" equivalence]]] [control - ["[0]" try (.open: "[1]#[0]" functor)] - [parser - ["<[0]>" binary]]] + ["[0]" try (.open: "[1]#[0]" functor)]] [data ["[0]" text (.open: "[1]#[0]" equivalence)] ["[0]" binary - ["[1]" \\format]]] + ["[1]" \\format] + ["<[1]>" \\parser]]] [math ["[0]" random (.only Random) (.open: "[1]#[0]" monad)]]]] [\\library diff --git a/stdlib/source/test/lux/tool/compiler/meta/archive/module/document.lux b/stdlib/source/test/lux/tool/compiler/meta/archive/module/document.lux index e36561063..4f25ec351 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/archive/module/document.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/archive/module/document.lux @@ -7,12 +7,11 @@ [control ["[0]" pipe] ["[0]" try (.open: "[1]#[0]" functor)] - ["[0]" exception] - [parser - ["<[0]>" binary]]] + ["[0]" exception]] [data ["[0]" binary - ["[1]F" \\format]]] + ["[1]F" \\format] + ["<[1]>" \\parser]]] [math ["[0]" random] [number 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 a3dfe0677..3cd46c9c8 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux @@ -6,14 +6,13 @@ [monad (.only do)]] [control ["[0]" maybe (.open: "[1]#[0]" functor)] - ["[0]" try (.open: "[1]#[0]" functor)] - [parser - ["<[0]>" binary]]] + ["[0]" try (.open: "[1]#[0]" functor)]] [data ["[0]" product] ["[0]" text] ["[0]" binary - ["[1]" \\format]] + ["[1]" \\format] + ["<[1]>" \\parser]] [collection ["[0]" sequence (.only Sequence)] ["[0]" set (.only Set)] diff --git a/stdlib/source/test/lux/tool/compiler/meta/archive/signature.lux b/stdlib/source/test/lux/tool/compiler/meta/archive/signature.lux index 15db5b167..2586666ee 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/archive/signature.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/archive/signature.lux @@ -7,14 +7,13 @@ [\\specification ["$[0]" equivalence]]] [control - ["[0]" try (.open: "[1]#[0]" functor)] - [parser - ["<[0]>" binary]]] + ["[0]" try (.open: "[1]#[0]" functor)]] [data ["[0]" bit (.open: "[1]#[0]" equivalence)] ["[0]" text (.open: "[1]#[0]" equivalence)] ["[0]" binary - ["[1]F" \\format]]] + ["[1]F" \\format] + ["<[1]>" \\parser]]] [math ["[0]" random (.only Random)]]]] [\\library diff --git a/stdlib/source/test/lux/tool/compiler/meta/export.lux b/stdlib/source/test/lux/tool/compiler/meta/export.lux index 1fb6d3a2d..134f62058 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/export.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/export.lux @@ -8,15 +8,14 @@ ["[0]" pipe] ["[0]" try (.open: "[1]#[0]" functor)] [concurrency - ["[0]" async]] - [parser - ["<[0]>" binary]]] + ["[0]" async]]] [data ["[0]" product] - ["[0]" binary (.only Binary) (.open: "[1]#[0]" equivalence)] ["[0]" bit (.open: "[1]#[0]" equivalence)] [format ["[0]" tar]] + ["[0]" binary (.only Binary) (.open: "[1]#[0]" equivalence) + ["<[1]>" \\parser]] ["[0]" text (.open: "[1]#[0]" equivalence) ["%" \\format (.only format)] [encoding diff --git a/stdlib/source/test/lux/tool/compiler/meta/import.lux b/stdlib/source/test/lux/tool/compiler/meta/import.lux index c37686e03..c5d2ce2b1 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/import.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/import.lux @@ -9,14 +9,13 @@ ["[0]" try (.open: "[1]#[0]" functor)] ["[0]" exception] [concurrency - ["[0]" async]] - [parser - ["<[0]>" binary]]] + ["[0]" async]]] [data ["[0]" product] ["[0]" bit (.open: "[1]#[0]" equivalence)] ["[0]" binary (.only Binary) (.open: "[1]#[0]" equivalence) - ["[0]" \\format]] + ["[0]" \\format] + ["<[1]>" \\parser]] ["[0]" format ["[0]" tar (.only Tar)]] ["[0]" text (.open: "[1]#[0]" equivalence) |