(.using [library [lux "*" ["_" test {"+" Test}] ["[0]" type] [abstract [equivalence {"+" Equivalence}] [predicate {"+" Predicate}] [monad {"+" do}]] [control ["[0]" pipe] ["[0]" maybe] ["[0]" try] ["[0]" exception] ["<>" parser]] [data ["[0]" binary] ["[0]" sum] ["[0]" bit] ["[0]" text ("[1]#[0]" equivalence) ["%" format {"+" format}] [encoding ["[0]" utf8]]] ["[0]" format "_" ["[1]" binary]] [collection ["[0]" list] ["[0]" sequence] ["[0]" set]]] [macro ["^" pattern] ["[0]" code]] [math ["[0]" random {"+" Random}] [number ["n" nat] ["[0]" i64] ["[0]" int] ["[0]" rev] ["[0]" frac]]] [meta ["[0]" symbol]]]] [\\library ["[0]" /]]) (template: (!expect ) [(case true _ false)]) (def: segment_size 10) (def: (utf8_conversion_does_not_alter? value) (Predicate Text) (|> value (# utf8.codec encoded) (# 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)) (implementation: location_equivalence (Equivalence Location) (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) ($_ random.and ..random_text random.nat random.nat)) (def: random_code (Random Code) (random.rec (function (_ again) (let [random_sequence (do [! random.monad] [size (# ! each (n.% 2) random.nat)] (random.list size again))] ($_ random.and ..random_location (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) (let [(open "[0]") random.monad] ($_ random.either (in .Nat) (in .List) (in .Code) (in .Type)))) (def: size Test (<| (_.for [/.Size]) (`` ($_ _.and (~~ (template [ ] [(do [! random.monad] [expected (# ! each (i64.and (i64.mask )) random.nat)] (_.cover [ ] (|> (format.result expected) (/.result ) (!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 (`` ($_ _.and (~~ (template [ ] [(do [! random.monad] [expected (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))] (_.cover [ ] (|> (format.result expected) (/.result ) (!expect (^.multi {try.#Success actual} (# 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 (`` ($_ _.and (~~ (template [ ] [(do [! random.monad] [expected (random.ascii ..segment_size)] (_.cover [ ] (|> (format.result expected) (/.result ) (!expect (^.multi {try.#Success actual} (# 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 (`` ($_ _.and (~~ (template [ ] [(do [! random.monad] [expected (random.sequence ..segment_size random.nat)] (_.cover [ ] (|> expected (format.result ( format.nat)) (/.result ( /.nat)) (!expect (^.multi {try.#Success actual} (# (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 (`` ($_ _.and (~~ (template [ ] [(do [! random.monad] [expected ] (_.cover [ ] (|> expected (format.result ) (/.result ) (!expect (^.multi {try.#Success actual} (# = 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] (_.cover [/.frac format.frac] (|> expected (format.result format.frac) (/.result /.frac) (!expect (^.multi {try.#Success actual} (or (# frac.equivalence = expected actual) (and (frac.not_a_number? expected) (frac.not_a_number? actual)))))))) (do [! random.monad] [expected (# ! each (|>> (i64.and (i64.mask /.size_8)) (n.max 2)) random.nat)] (_.cover [/.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 (`` ($_ _.and (~~ (template [ ] [(do [! random.monad] [expected ] (_.cover [ ] (|> expected (format.result ) (/.result ) (!expect (^.multi {try.#Success actual} (# = expected actual))))))] [/.location format.location random_location location_equivalence] [/.code format.code random_code code.equivalence] [/.type format.type random_type type.equivalence] )) (~~ (template [ ] [(do [! random.monad] [expected ] (_.cover [ ] (|> expected (format.result ) (/.result ) (!expect (^.multi {try.#Success actual} (# = 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 (# ! each (list.repeated ..segment_size) random.nat)] (_.cover [/.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)] (_.cover [/.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} (# (sum.equivalence bit.equivalence n.equivalence) = expected actual)))))) (do [! random.monad] [tag (# ! each (|>> (i64.and (i64.mask /.size_8)) (n.max 2)) random.nat) value random.bit] (_.cover [/.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)] (_.cover [/.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} (# (list.equivalence n.equivalence) = expected actual)))))) ))) (def: .public test Test (<| (_.covering /._) (_.for [/.Parser]) (`` ($_ _.and (_.cover [/.result /.any format.no_op format.instance] (|> (format.instance format.no_op) (/.result /.any) (!expect {try.#Success _}))) (do [! random.monad] [data (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))] (_.cover [/.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 (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))] (_.cover [/.segment format.segment format.result] (|> expected (format.result (format.segment ..segment_size)) (/.result (/.segment ..segment_size)) (!expect (^.multi {try.#Success actual} (# binary.equivalence = expected actual)))))) (do [! random.monad] [data (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))] (_.cover [/.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 (# ! each (n.% (++ ..segment_size)) random.nat) data (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))] (_.cover [/.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 (# ! each (n.% (++ ..segment_size)) random.nat) data (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))] (_.cover [/.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 ))))