(.with_expansions [' (.for {"{old}" (.as_is ["#/." jvm]) "JVM" (.as_is ["#/." jvm])} (.as_is)) '] (.module: ["/" lux #* [program (#+ program:)] ["_" test (#+ Test)] ["@" target] [abstract [monad (#+ do)] [predicate (#+ Predicate)]] [control ["." io (#+ io)]] [data ["." name] [text ["%" format (#+ format)]]] ["." math ["." random (#+ Random) ("#\." functor)] [number ["n" nat] ["i" int] ["r" rev] ["f" frac] ["." i64]]]] ## TODO: Must have 100% coverage on tests. ["." / #_ ["#." abstract] ["#." control] ["#." data] ["#." locale] ["#." macro] ["#." math] ["#." meta] ["#." time] ## ["#." tool] ## TODO: Update & expand tests for this ["#." type] ["#." world] ["#." host] ["#." extension] ["#." target #_ ]])) ## TODO: Get rid of this ASAP (template: (!bundle body) (: Test (do random.monad [_ (wrap [])] body))) (def: identity Test (do {! random.monad} [self (random.unicode 1)] ($_ _.and (_.test "Every value is identical to itself." (is? self self)) (do ! [other (random.unicode 1)] (_.test "Values created separately can't be identical." (not (is? self other)))) ))) (def: increment_and_decrement Test (do random.monad [value random.i64] ($_ _.and (_.test "'inc' and 'dec' are opposites." (and (|> value inc dec (n.= value)) (|> value dec inc (n.= value)))) (_.test "'inc' and 'dec' shift the number by 1." (and (|> (inc value) (n.- value) (n.= 1)) (|> value (n.- (dec value)) (n.= 1))))))) (def: (check_neighbors has_property? value) (All [a] (-> (Predicate (I64 a)) (I64 a) Bit)) (and (|> value inc has_property?) (|> value dec has_property?))) (def: (even_or_odd rand_gen even? odd?) (All [a] (-> (Random (I64 a)) (Predicate (I64 a)) (Predicate (I64 a)) Test)) (do random.monad [value rand_gen] ($_ _.and (_.test "Every number is either even or odd." (if (even? value) (not (odd? value)) (odd? value))) (_.test "Every odd/even number is surrounded by two of the other kind." (if (even? value) (check_neighbors odd? value) (check_neighbors even? value)))))) (type: (Equivalence a) (-> a a Bit)) (def: (conversion rand_gen forward backward =) (All [a b] (-> (Random a) (-> a b) (-> b a) (Equivalence a) Test)) (do random.monad [value rand_gen] (_.test "Can convert between types in a lossless way." (|> value forward backward (= value))))) (def: frac_rev (Random Rev) (let [bits_to_ignore 11] (\ random.functor map (i64.left_shift bits_to_ignore) random.rev))) (def: prelude_macros Test ($_ _.and (do random.monad [factor (random\map (|>> (n.% 10) (n.max 1)) random.nat) iterations (random\map (n.% 10) random.nat) #let [expected (n.* factor iterations)]] (_.test "Can write loops." (n.= expected (loop [counter 0 value 0] (if (n.< iterations counter) (recur (inc counter) (n.+ factor value)) value))))) (do random.monad [first random.nat second random.nat third random.nat] (_.test "Can create lists easily through macros." (and (case (list first second third) (#.Cons first' (#.Cons second' (#.Cons third' #.Nil))) (and (n.= first first') (n.= second second') (n.= third third')) _ false) (case (list& first (list second third)) (#.Cons first' (#.Cons second' (#.Cons third' #.Nil))) (and (n.= first first') (n.= second second') (n.= third third')) _ false) (case (list& first second (list third)) (#.Cons first' (#.Cons second' (#.Cons third' #.Nil))) (and (n.= first first') (n.= second second') (n.= third third')) _ false)))) )) (template: (quadrance cat0 cat1) (n.+ (n.* cat0 cat0) (n.* cat1 cat1))) (def: templates Test (do random.monad [cat0 random.nat cat1 random.nat] (_.test "Template application is a stand-in for the templated code." (n.= (n.+ (n.* cat0 cat0) (n.* cat1 cat1)) (quadrance cat0 cat1))))) (def: cross_platform_support Test (do random.monad [on_default random.nat on_fake_host random.nat on_valid_host random.nat] ($_ _.and (_.test "Can provide default in case there is no particular host/platform support." (n.= on_default (for {"" on_fake_host} on_default))) (_.test "Can pick code depending on the host/platform being targeted." (n.= on_valid_host (for {@.old on_valid_host @.jvm on_valid_host @.js on_valid_host @.python on_valid_host @.lua on_valid_host @.ruby on_valid_host @.php on_valid_host} on_default)))))) (def: conversion_tests Test (`` ($_ _.and (~~ (template [<=> ] [(<| (_.context (format (%.name (name_of )) " " (%.name (name_of )))) (..conversion <=>))] [i.= .nat .int (random\map (i.% +1,000,000) random.int)] [n.= .int .nat (random\map (n.% 1,000,000) random.nat)] ))))) (def: sub_tests Test (let [tail (: (List Test) (for {@.old (list)} (list /extension.test)))] (_.in_parallel (list& /abstract.test /control.test /data.test /locale.test /macro.test /math.test /meta.test /time.test ## /tool.test /type.test /world.test /host.test (for {@.jvm (#.Cons /target/jvm.test tail) @.old (#.Cons /target/jvm.test tail)} tail) )))) (def: test Test (<| (_.context (name.module (name_of /._))) ($_ _.and (<| (_.context "Identity.") ..identity) (<| (_.context "Increment & decrement.") ..increment_and_decrement) (<| (_.context "Even or odd.") ($_ _.and (<| (_.context "Natural numbers.") (..even_or_odd random.nat n.even? n.odd?)) (<| (_.context "Integers.") (..even_or_odd random.int i.even? i.odd?)))) (<| (_.context "Conversion.") ..conversion_tests) (<| (_.context "Prelude macros.") ..prelude_macros) (<| (_.context "Templates.") ..templates) (<| (_.context "Cross-platform support.") ..cross_platform_support) ..sub_tests ))) (program: args (<| io _.run! (_.times 100) ..test))