From 049dcdc0c6dc678786dbf854a20385fb6ef06f9a Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Sun, 12 Feb 2023 02:54:39 -0400 Subject: Added an abstraction for interest rates. --- stdlib/source/test/lux.lux | 29 ---- stdlib/source/test/lux/data/text.lux | 23 ++- stdlib/source/test/lux/debug.lux | 9 +- .../compiler/language/lux/analysis/inference.lux | 38 ++-- .../meta/compiler/language/lux/phase/analysis.lux | 16 +- .../language/lux/phase/analysis/complex.lux | 26 +-- .../language/lux/phase/analysis/function.lux | 8 +- .../compiler/language/lux/phase/analysis/when.lux | 10 +- .../language/lux/phase/extension/analysis/lux.lux | 6 +- .../test/lux/meta/compiler/meta/cli/compiler.lux | 3 +- stdlib/source/test/lux/meta/type.lux | 37 +++- stdlib/source/test/lux/meta/type/check.lux | 56 +++--- stdlib/source/test/lux/meta/type/variance.lux | 16 +- stdlib/source/test/lux/world.lux | 5 +- stdlib/source/test/lux/world/file/extension.lux | 192 ++++++++++++--------- .../test/lux/world/finance/interest/rate.lux | 64 +++++++ 16 files changed, 323 insertions(+), 215 deletions(-) create mode 100644 stdlib/source/test/lux/world/finance/interest/rate.lux (limited to 'stdlib/source/test') diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux index 64ac888ac..5597bded0 100644 --- a/stdlib/source/test/lux.lux +++ b/stdlib/source/test/lux.lux @@ -599,35 +599,6 @@ _ false)) - (_.coverage [/.type_literal] - (and (when (/.type_literal [expected/0 expected/1]) - {.#Product actual/0 actual/1} - (and (same? expected/0 actual/0) - (same? expected/1 actual/1)) - - _ - false) - (when (/.type_literal (/.Or expected/0 expected/1)) - {.#Sum actual/0 actual/1} - (and (same? expected/0 actual/0) - (same? expected/1 actual/1)) - - _ - false) - (when (/.type_literal (-> expected/0 expected/1)) - {.#Function actual/0 actual/1} - (and (same? expected/0 actual/0) - (same? expected/1 actual/1)) - - _ - false) - (when (/.type_literal (expected/0 expected/1)) - {.#Apply actual/1 actual/0} - (and (same? expected/0 actual/0) - (same? expected/1 actual/1)) - - _ - false))) (_.coverage [/.type] (exec (is /.Type ..for_type/variant) diff --git a/stdlib/source/test/lux/data/text.lux b/stdlib/source/test/lux/data/text.lux index fb008dc84..cbe1af77c 100644 --- a/stdlib/source/test/lux/data/text.lux +++ b/stdlib/source/test/lux/data/text.lux @@ -90,15 +90,17 @@ ["[0]" \\format]) (def (equivalence example) - (All (_ a) (-> a (Equivalence (\\format.Format a)))) + (All (_ of) + (-> of + (Equivalence (\\format.Format of)))) (implementation (def (= reference subject) (/#= (reference example) (subject example))))) (def random_contravariant - (Random (Ex (_ a) - [(\\format.Format a) - (Random a)])) + (Random (Ex (_ of) + [(\\format.Format of) + (Random of)])) (all random.either (random#in [\\format.bit random.bit]) (random#in [\\format.nat random.nat]) @@ -153,6 +155,19 @@ [\\format.frac_10 frac.decimal random.frac] [\\format.frac_16 frac.hex random.frac] )) + + (,, (with_template [ ] + [(do random.monad + [it random.safe_frac] + (_.coverage [] + (/.contains? (\\format.int (frac.int ( it))) + ( it))))] + + [\\format.degree frac.degree] + [\\format.percentage frac.percentage] + [\\format.permille frac.permille] + [\\format.permyriad frac.permyriad] + )) ))) (def \\format diff --git a/stdlib/source/test/lux/debug.lux b/stdlib/source/test/lux/debug.lux index 8c89a23b3..fcba3ec1a 100644 --- a/stdlib/source/test/lux/debug.lux +++ b/stdlib/source/test/lux/debug.lux @@ -26,6 +26,7 @@ [number [ratio (.only Ratio)]]] [meta + ["[0]" type] ["[0]" code (.only) ["<[1]>" \\parser]] [macro @@ -86,7 +87,7 @@ [sample_bit random.bit sample_int random.int sample_frac random.frac] - (in (`` (and (when (/.representation (type_literal [Bit Int Frac]) + (in (`` (and (when (/.representation (type.literal [Bit Int Frac]) [sample_bit sample_int sample_frac]) {try.#Success actual} (text#= (format "[" (%.bit sample_bit) @@ -99,7 +100,7 @@ false) ... TODO: Uncomment after switching from the old (tag+last?) to the new (lefts+right?) representation for variants ... (,, (with_template [ ] - ... [(|> (/.representation (type_literal (Or Bit Int Frac)) + ... [(|> (/.representation (type.literal (Or Bit Int Frac)) ... (is (Or Bit Int Frac) ... ( ))) ... (try#each (text#= (format "(" (%.nat ) @@ -181,11 +182,11 @@ (|> (/.representation .Any sample_frac) (try#each (text#= "[]")) (try.else false)) - (|> (/.representation (type_literal (List Nat)) (is (List Nat) (list sample_nat))) + (|> (/.representation (type.literal (List Nat)) (is (List Nat) (list sample_nat))) (try#each (text#= (%.list %.nat (list sample_nat)))) (try.else false)) (,, (with_template [] - [(|> (/.representation (type_literal (Maybe Nat)) (is (Maybe Nat) )) + [(|> (/.representation (type.literal (Maybe Nat)) (is (Maybe Nat) )) (try#each (text#= (%.maybe %.nat ))) (try.else false))] diff --git a/stdlib/source/test/lux/meta/compiler/language/lux/analysis/inference.lux b/stdlib/source/test/lux/meta/compiler/language/lux/analysis/inference.lux index 87b6530d3..b9749422b 100644 --- a/stdlib/source/test/lux/meta/compiler/language/lux/analysis/inference.lux +++ b/stdlib/source/test/lux/meta/compiler/language/lux/analysis/inference.lux @@ -134,7 +134,7 @@ analysis/*)))) (try.else false)) (|> (/.general archive.empty ..analysis - (type_literal (-> type/0 expected)) + (type.literal (-> type/0 expected)) (list term/0)) (//type.expecting expected) (//module.with 0 (product.left name)) @@ -143,7 +143,7 @@ (try#each (|>> product.left (type#= expected))) (try.else false)) (|> (/.general archive.empty ..analysis - (type_literal {.#Named name (-> type/0 expected)}) + (type.literal {.#Named name (-> type/0 expected)}) (list term/0)) (//type.expecting expected) (//module.with 0 (product.left name)) @@ -152,7 +152,7 @@ (try#each (|>> product.left (type#= expected))) (try.else false)) (|> (/.general archive.empty ..analysis - (type_literal (All (_ a) (-> a a))) + (type.literal (All (_ a) (-> a a))) (list term/0)) (//type.expecting type/0) (//module.with 0 (product.left name)) @@ -163,7 +163,7 @@ (try#each (type#= type/0)) (try.else false)) (|> (/.general archive.empty ..analysis - (type_literal ((All (_ a) (-> a a)) type/0)) + (type.literal ((All (_ a) (-> a a)) type/0)) (list term/0)) (//type.expecting type/0) (//module.with 0 (product.left name)) @@ -173,7 +173,7 @@ (try.else false)) (|> (do /phase.monad [[@var varT] (//type.check check.var) - _ (//type.check (check.check varT (type_literal (-> type/0 expected))))] + _ (//type.check (check.check varT (type.literal (-> type/0 expected))))] (/.general archive.empty ..analysis varT (list term/0))) (//type.expecting expected) (//module.with 0 (product.left name)) @@ -184,7 +184,7 @@ (try#each (type#= expected)) (try.else false)) (|> (/.general archive.empty ..analysis - (type_literal (Ex (_ a) (-> a a))) + (type.literal (Ex (_ a) (-> a a))) (list (` (.error# "")))) //type.inferring (//module.with 0 (product.left name)) @@ -207,7 +207,7 @@ (..fails? /.cannot_infer)))) (_.coverage [/.cannot_infer_argument] (|> (/.general archive.empty ..analysis - (type_literal (-> expected expected)) + (type.literal (-> expected expected)) (list term/0)) (//type.expecting expected) (//module.with 0 (product.left name)) @@ -267,11 +267,11 @@ (variant? {.#Named name variantT} lefts right? tagC) cases_independent_of_parameters_conform_to_anything! - (variant? (type_literal (Maybe type/0)) 0 #0 (' [])) + (variant? (type.literal (Maybe type/0)) 0 #0 (' [])) cases_dependent_on_parameters_are_tettered_to_those_parameters! - (and (variant? (type_literal (Maybe type/0)) 0 #1 term/0) - (not (variant? (type_literal (Maybe type/0)) 0 #1 term/1))) + (and (variant? (type.literal (Maybe type/0)) 0 #1 term/0) + (not (variant? (type.literal (Maybe type/0)) 0 #1 term/1))) only_bottom_conforms_to_tags_outside_of_range! (`` (and (,, (with_template [ ] @@ -281,24 +281,24 @@ [#1 (` (.error# ""))])))) can_handle_universal_quantification! - (and (variant?' (type_literal (All (_ a) (Maybe a))) + (and (variant?' (type.literal (All (_ a) (Maybe a))) {.#Some Maybe} 0 #0 (' [])) - (variant?' (type_literal (All (_ a) (Maybe a))) - {.#Some (type_literal (Maybe type/0))} + (variant?' (type.literal (All (_ a) (Maybe a))) + {.#Some (type.literal (Maybe type/0))} 0 #1 term/0) - (not (variant?' (type_literal (All (_ a) (Maybe a))) + (not (variant?' (type.literal (All (_ a) (Maybe a))) {.#Some Maybe} 0 #1 term/0))) existential_types_do_not_affect_independent_cases! - (variant?' (type_literal (Ex (_ a) (Maybe a))) + (variant?' (type.literal (Ex (_ a) (Maybe a))) {.#None} 0 #0 (' [])) existential_types_affect_dependent_cases! (`` (and (,, (with_template [ ] - [(bit#= (variant?' (type_literal (Ex (_ a) (Maybe a))) {.#None} 0 #1 ))] + [(bit#= (variant?' (type.literal (Ex (_ a) (Maybe a))) {.#None} 0 #1 ))] [#0 term/0] [#1 (` (.error# ""))]))))] @@ -415,13 +415,13 @@ ..test|variant ..test|record (_.coverage [/.invalid_type_application] - (and (|> (/.general archive.empty ..analysis (type_literal (type/0 type/1)) (list term/0)) + (and (|> (/.general archive.empty ..analysis (type.literal (type/0 type/1)) (list term/0)) (/phase.result state) (..fails? /.invalid_type_application)) - (|> (/.variant lefts right? (type_literal (type/0 type/1))) + (|> (/.variant lefts right? (type.literal (type/0 type/1))) (/phase.result state) (..fails? /.invalid_type_application)) - (|> (/.record lefts (type_literal (type/0 type/1))) + (|> (/.record lefts (type.literal (type/0 type/1))) (/phase.result state) (..fails? /.invalid_type_application)))) )))) diff --git a/stdlib/source/test/lux/meta/compiler/language/lux/phase/analysis.lux b/stdlib/source/test/lux/meta/compiler/language/lux/phase/analysis.lux index 9557ff88b..2b97e44dc 100644 --- a/stdlib/source/test/lux/meta/compiler/language/lux/phase/analysis.lux +++ b/stdlib/source/test/lux/meta/compiler/language/lux/phase/analysis.lux @@ -232,10 +232,10 @@ (let [state [extension.#bundle (extension/analysis.bundle ..eval) extension.#state lux] :record: {.#Named [module/0 @text] - (type_literal [.Any .Bit .Nat .Int .Rev .Frac .Text])} + (type.literal [.Any .Bit .Nat .Int .Rev .Frac .Text])} slots/* (list @any @bit @nat @int @rev @frac @text) :variant: {.#Named [module/0 @text] - (type_literal (Or .Any .Bit .Nat .Int .Rev .Frac .Text))} + (type.literal (Or .Any .Bit .Nat .Int .Rev .Frac .Text))} tags/* (list @any @bit @nat @int @rev @frac @text) can_analyse_unary! @@ -289,7 +289,7 @@ (|> (do phase.monad [_ (//module.declare_labels true slots/* false :record:) .let [:either: {.#Named [module/0 module/0] - (type_literal (Or .Any :record:))}] + (type.literal (Or .Any :record:))}] _ (//module.declare_labels false (list @left @right) false :either:) [:it: it] (|> (code.variant (list (code.local @left))) (/.phase ..expander archive.empty) @@ -312,7 +312,7 @@ (|> (do phase.monad [_ (//module.declare_labels true slots/* false :record:) .let [:either: {.#Named [module/0 module/0] - (type_literal (Or .Any :record:))}] + (type.literal (Or .Any :record:))}] _ (//module.declare_labels false (list @left @right) false :either:) [:it: it] (|> (code.variant (list (code.local @right) (` []) @@ -366,7 +366,7 @@ (code.text text/0))) (/.phase ..expander archive.empty) //type.inferring)] - (in (and (type#= (type_literal [.Any .Bit .Nat .Int .Rev .Frac .Text]) + (in (and (type#= (type.literal [.Any .Bit .Nat .Int .Rev .Frac .Text]) :it:) (when it (//.tuple (list (//.unit) @@ -396,7 +396,7 @@ (let [state [extension.#bundle (extension/analysis.bundle ..eval) extension.#state lux] :record: {.#Named [module/0 @text] - (type_literal [.Any .Bit .Nat .Int .Rev .Frac .Text])} + (type.literal [.Any .Bit .Nat .Int .Rev .Frac .Text])} slots/* (list @any @bit @nat @int @rev @frac @text)] (|> (do phase.monad [_ (//module.declare_labels true slots/* false :record:) @@ -665,11 +665,11 @@ extension.#state lux] :variant: {.#Named [module/0 module/0] - (type_literal (Or .Any .Bit .Nat .Int .Rev .Frac .Text))} + (type.literal (Or .Any .Bit .Nat .Int .Rev .Frac .Text))} tags/* (list @any @bit @nat @int @rev @frac @text) :record: {.#Named [module/0 module/0] - (type_literal (And .Any .Bit .Nat .Int .Rev .Frac .Text))} + (type.literal (And .Any .Bit .Nat .Int .Rev .Frac .Text))} slots/* (list @any @bit @nat @int @rev @frac @text) simple! diff --git a/stdlib/source/test/lux/meta/compiler/language/lux/phase/analysis/complex.lux b/stdlib/source/test/lux/meta/compiler/language/lux/phase/analysis/complex.lux index ba524b22b..1bfc8b7a7 100644 --- a/stdlib/source/test/lux/meta/compiler/language/lux/phase/analysis/complex.lux +++ b/stdlib/source/test/lux/meta/compiler/language/lux/phase/analysis/complex.lux @@ -184,12 +184,12 @@ (//phase#each product.right) (//phase.result state) (try.else false)) - (and (sum? (type_literal (Maybe tagT)) 0 false (` [])) - (sum? (type_literal (Maybe tagT)) 0 true tagC)) - (and (sum? (type_literal (All (_ a) (Maybe a))) 0 false (` [])) - (not (sum? (type_literal (All (_ a) (Maybe a))) 0 true tagC))) - (and (sum? (type_literal (Ex (_ a) (Maybe a))) 0 false (` [])) - (sum? (type_literal (Ex (_ a) (Maybe a))) 0 true tagC))))) + (and (sum? (type.literal (Maybe tagT)) 0 false (` [])) + (sum? (type.literal (Maybe tagT)) 0 true tagC)) + (and (sum? (type.literal (All (_ a) (Maybe a))) 0 false (` [])) + (not (sum? (type.literal (All (_ a) (Maybe a))) 0 true tagC))) + (and (sum? (type.literal (Ex (_ a) (Maybe a))) 0 false (` [])) + (sum? (type.literal (Ex (_ a) (Maybe a))) 0 true tagC))))) ... (_.for [/.cannot_analyse_variant] ... (let [failure? (is (All (_ a) (-> (Exception a) (//analysis.Operation Any) Bit)) ... (function (_ exception analysis) @@ -204,7 +204,7 @@ ... (|> (do //phase.monad ... [[@var varT] (//type.check check.var)] ... (|> (/.sum ..analysis lefts right? archive.empty tagC) - ... (//type.expecting (type_literal (varT tagT))))) + ... (//type.expecting (type.literal (varT tagT))))) ... (failure? /.invalid_variant_type)))) ... (_.coverage [/.cannot_infer_sum] ... (|> (do //phase.monad @@ -326,9 +326,9 @@ (try.else false))))] (and (product? productT expected) (product? {.#Named name productT} expected) - (product? (type_literal (Ex (_ a) [a a])) (list term/0 term/0)) - (not (product? (type_literal (All (_ a) [a a])) (list term/0 term/0))) - (product? (type_literal (Triple type/0)) (list term/0 term/0 term/0)) + (product? (type.literal (Ex (_ a) [a a])) (list term/0 term/0)) + (not (product? (type.literal (All (_ a) [a a])) (list term/0 term/0))) + (product? (type.literal (Triple type/0)) (list term/0 term/0 term/0)) (|> (do //phase.monad [[@var varT] (//type.check check.var) _ (//type.check (check.check varT productT)) @@ -428,7 +428,7 @@ [[@var varT] (//type.check check.var)] (|> expected (/.product ..analysis archive.empty) - (//type.expecting (type_literal (varT type/0))))) + (//type.expecting (type.literal (varT type/0))))) (failure? /.invalid_tuple_type)))))) ))) @@ -651,13 +651,13 @@ ..test|record (_.coverage [/.not_a_quantified_type] (and (|> (/.sum ..analysis lefts right? archive.empty term/0) - (//type.expecting (type_literal (type/0 type/1))) + (//type.expecting (type.literal (type/0 type/1))) (//phase.result state) (..failure? /.not_a_quantified_type)) (|> types/*,terms/* (list#each product.right) (/.product ..analysis archive.empty) - (//type.expecting (type_literal (type/0 type/1))) + (//type.expecting (type.literal (type/0 type/1))) (//phase.result state) (..failure? /.not_a_quantified_type)))) )))) diff --git a/stdlib/source/test/lux/meta/compiler/language/lux/phase/analysis/function.lux b/stdlib/source/test/lux/meta/compiler/language/lux/phase/analysis/function.lux index 2472c55e3..2dcfc22ca 100644 --- a/stdlib/source/test/lux/meta/compiler/language/lux/phase/analysis/function.lux +++ b/stdlib/source/test/lux/meta/compiler/language/lux/phase/analysis/function.lux @@ -132,11 +132,11 @@ ... (function? (Ex (_ a) (-> a a)) term/0) ... (function? (Rec self (-> input/0 self)) $function/0) - ... (function? (type_literal ((All (_ a) (-> a a)) output/0)) term/0) - ... (not (function? (type_literal ((All (_ a) (-> a a)) output/1)) term/0)) + ... (function? (type.literal ((All (_ a) (-> a a)) output/0)) term/0) + ... (not (function? (type.literal ((All (_ a) (-> a a)) output/1)) term/0)) - ... (function? (type_literal ((Ex (_ a) (-> a a)) output/0)) term/0) - ... (not (function? (type_literal ((Ex (_ a) (-> a a)) output/1)) term/0)) + ... (function? (type.literal ((Ex (_ a) (-> a a)) output/0)) term/0) + ... (not (function? (type.literal ((Ex (_ a) (-> a a)) output/1)) term/0)) ... (function?' (-> input/0 input/1 input/0) (` ([(, $function/1) (, $argument/1)] (, $argument/0))) ... (function (_ [outer body]) diff --git a/stdlib/source/test/lux/meta/compiler/language/lux/phase/analysis/when.lux b/stdlib/source/test/lux/meta/compiler/language/lux/phase/analysis/when.lux index f23e99dac..e42a02e2c 100644 --- a/stdlib/source/test/lux/meta/compiler/language/lux/phase/analysis/when.lux +++ b/stdlib/source/test/lux/meta/compiler/language/lux/phase/analysis/when.lux @@ -97,12 +97,12 @@ (Tuple (All (_ a b c) input/0) (All (_ a b c) input/1) (All (_ a b c) input/2))) - (tuple? (type_literal ((All (_ a b c) (Tuple a b c)) input/0 input/1 input/2)) + (tuple? (type.literal ((All (_ a b c) (Tuple a b c)) input/0 input/1 input/2)) (Tuple input/0 input/1 input/2)) (|> (do check.monad [[@var :var:] check.var _ (check.bind (All (_ a b c) (Tuple a b c)) @var)] - (/.tuple (type_literal (:var: input/0 input/1 input/2)))) + (/.tuple (type.literal (:var: input/0 input/1 input/2)))) (check.result check.fresh_context) (try#each (|>> product.right (type#= (Tuple input/0 input/1 input/2)))) (try.else false)) @@ -127,19 +127,19 @@ (exception.otherwise (text.contains? (the exception.#label /.non_tuple)))) (|> (do check.monad [[@var :var:] check.var - _ (/.tuple (type_literal (:var: input/0 input/1 input/2)))] + _ (/.tuple (type.literal (:var: input/0 input/1 input/2)))] (in false)) (check.result check.fresh_context) (exception.otherwise (text.contains? (the exception.#label /.non_tuple)))) (|> (do check.monad - [_ (/.tuple (type_literal (input/0 input/1 input/2)))] + [_ (/.tuple (type.literal (input/0 input/1 input/2)))] (in false)) (check.result check.fresh_context) (exception.otherwise (text.contains? (the exception.#label /.non_tuple)))) (|> (do check.monad [[@var :var:] check.var _ (check.bind input/0 @var) - _ (/.tuple (type_literal (:var: input/1 input/2)))] + _ (/.tuple (type.literal (:var: input/1 input/2)))] (in false)) (check.result check.fresh_context) (exception.otherwise (text.contains? (the exception.#label /.non_tuple)))))) diff --git a/stdlib/source/test/lux/meta/compiler/language/lux/phase/extension/analysis/lux.lux b/stdlib/source/test/lux/meta/compiler/language/lux/phase/extension/analysis/lux.lux index 66d43c8c6..93ad48d8a 100644 --- a/stdlib/source/test/lux/meta/compiler/language/lux/phase/extension/analysis/lux.lux +++ b/stdlib/source/test/lux/meta/compiler/language/lux/phase/extension/analysis/lux.lux @@ -73,7 +73,7 @@ (_.test "Can 'try' risky IO computations." (check_success+ (` .try#) (list (` (.error# "YOLO"))) - (type_literal (Either Text primT)))) + (type.literal (Either Text primT)))) ))) (def i64 @@ -149,7 +149,7 @@ (_.test "Can convert frac number to text." (check_success+ (symbol .f64_encoded#) (list subjectC) Text)) (_.test "Can convert text to frac number." - (check_success+ (symbol .f64_decoded#) (list encodedC) (type_literal (Maybe Frac)))) + (check_success+ (symbol .f64_decoded#) (list encodedC) (type.literal (Maybe Frac)))) ))) (def text @@ -168,7 +168,7 @@ (_.test "Can concatenate one text to another." (check_success+ (symbol .text_composite#) (list subjectC paramC) Text)) (_.test "Can find the index of a piece of text inside a larger one that (may) contain it." - (check_success+ (symbol .text_index#) (list fromC paramC subjectC) (type_literal (Maybe Nat)))) + (check_success+ (symbol .text_index#) (list fromC paramC subjectC) (type.literal (Maybe Nat)))) (_.test "Can query the size/length of a text." (check_success+ (symbol .text_size#) (list subjectC) Nat)) (_.test "Can obtain the character code of a text at a given index." diff --git a/stdlib/source/test/lux/meta/compiler/meta/cli/compiler.lux b/stdlib/source/test/lux/meta/compiler/meta/cli/compiler.lux index c8de9bc39..e4164032a 100644 --- a/stdlib/source/test/lux/meta/compiler/meta/cli/compiler.lux +++ b/stdlib/source/test/lux/meta/compiler/meta/cli/compiler.lux @@ -37,7 +37,8 @@ (def .public test Test (<| (_.covering /._) - (_.for [/.Compiler]) + (_.for [/.Compiler + /.#definition /.#parameters]) (do [! random.monad] [expected ..random] (all _.and diff --git a/stdlib/source/test/lux/meta/type.lux b/stdlib/source/test/lux/meta/type.lux index 4f02f6fe8..c149f2cc5 100644 --- a/stdlib/source/test/lux/meta/type.lux +++ b/stdlib/source/test/lux/meta/type.lux @@ -237,17 +237,17 @@ [expected ..nominal] (all _.and (_.coverage [\\parser.recursive] - (|> (.type_literal (Rec @ expected)) + (|> (/.literal (Rec @ expected)) (\\parser.result (\\parser.recursive \\parser.any)) (!expect (^.multi {try.#Success [@self actual]} (/#= expected actual))))) (_.coverage [\\parser.recursive_self] - (|> (.type_literal (Rec @ @)) + (|> (/.literal (Rec @ @)) (\\parser.result (\\parser.recursive \\parser.recursive_self)) (!expect (^.multi {try.#Success [@expected @actual]} (same? @expected @actual))))) (_.coverage [\\parser.recursive_call] - (|> (.type_literal (All (self input) (self input))) + (|> (/.literal (All (self input) (self input))) (\\parser.result (\\parser.polymorphic \\parser.recursive_call)) (!expect {try.#Success [@self inputs ???]}))) (_.coverage [\\parser.not_recursive] @@ -512,7 +512,7 @@ (_.coverage [/.by_example] (let [example (is (Maybe Nat) {.#None})] - (/#= (.type_literal (List Nat)) + (/#= (/.literal (List Nat)) (/.by_example [a] (is (Maybe a) example) @@ -563,6 +563,35 @@ (bit#= (/#= left right) (text#= (/.absolute_format left) (/.absolute_format right)))) )) + ... (_.coverage [/.literal] + ... (and (when (/.literal [expected/0 expected/1]) + ... {.#Product actual/0 actual/1} + ... (and (same? expected/0 actual/0) + ... (same? expected/1 actual/1)) + + ... _ + ... false) + ... (when (/.literal (/.Or expected/0 expected/1)) + ... {.#Sum actual/0 actual/1} + ... (and (same? expected/0 actual/0) + ... (same? expected/1 actual/1)) + + ... _ + ... false) + ... (when (/.literal (-> expected/0 expected/1)) + ... {.#Function actual/0 actual/1} + ... (and (same? expected/0 actual/0) + ... (same? expected/1 actual/1)) + + ... _ + ... false) + ... (when (/.literal (expected/0 expected/1)) + ... {.#Apply actual/1 actual/0} + ... (and (same? expected/0 actual/0) + ... (same? expected/1 actual/1)) + + ... _ + ... false))) ..\\parser diff --git a/stdlib/source/test/lux/meta/type/check.lux b/stdlib/source/test/lux/meta/type/check.lux index 7bf4c6647..33469b0b0 100644 --- a/stdlib/source/test/lux/meta/type/check.lux +++ b/stdlib/source/test/lux/meta/type/check.lux @@ -582,28 +582,28 @@ (def (handles_quantification! nominal) (-> Type Bit) (let [universals_satisfy_themselves! - (..succeeds? (/.check (.type_literal (All (_ a) (Maybe a))) - (.type_literal (All (_ a) (Maybe a))))) + (..succeeds? (/.check (//.literal (All (_ a) (Maybe a))) + (//.literal (All (_ a) (Maybe a))))) existentials_satisfy_themselves! - (..succeeds? (/.check (.type_literal (Ex (_ a) (Maybe a))) - (.type_literal (Ex (_ a) (Maybe a))))) + (..succeeds? (/.check (//.literal (Ex (_ a) (Maybe a))) + (//.literal (Ex (_ a) (Maybe a))))) universals_satisfy_particulars! - (..succeeds? (/.check (.type_literal (Maybe nominal)) - (.type_literal (All (_ a) (Maybe a))))) + (..succeeds? (/.check (//.literal (Maybe nominal)) + (//.literal (All (_ a) (Maybe a))))) particulars_do_not_satisfy_universals! - (..fails? (/.check (.type_literal (All (_ a) (Maybe a))) - (.type_literal (Maybe nominal)))) + (..fails? (/.check (//.literal (All (_ a) (Maybe a))) + (//.literal (Maybe nominal)))) particulars_satisfy_existentials! - (..succeeds? (/.check (.type_literal (Ex (_ a) (Maybe a))) - (.type_literal (Maybe nominal)))) + (..succeeds? (/.check (//.literal (Ex (_ a) (Maybe a))) + (//.literal (Maybe nominal)))) existentials_do_not_satisfy_particulars! - (..fails? (/.check (.type_literal (Maybe nominal)) - (.type_literal (Ex (_ a) (Maybe a)))))] + (..fails? (/.check (//.literal (Maybe nominal)) + (//.literal (Ex (_ a) (Maybe a)))))] (and universals_satisfy_themselves! existentials_satisfy_themselves! @@ -641,26 +641,26 @@ (def (handles_application! nominal/0 nominal/1) (-> Type Type Bit) (let [types_flow_through! - (and (..succeeds? (/.check (.type_literal ((All (_ a) a) nominal/0)) + (and (..succeeds? (/.check (//.literal ((All (_ a) a) nominal/0)) nominal/0)) (..succeeds? (/.check nominal/0 - (.type_literal ((All (_ a) a) nominal/0)))) + (//.literal ((All (_ a) a) nominal/0)))) - (..succeeds? (/.check (.type_literal ((Ex (_ a) a) nominal/0)) + (..succeeds? (/.check (//.literal ((Ex (_ a) a) nominal/0)) nominal/0)) (..succeeds? (/.check nominal/0 - (.type_literal ((Ex (_ a) a) nominal/0))))) + (//.literal ((Ex (_ a) a) nominal/0))))) multiple_parameters! - (and (..succeeds? (/.check (.type_literal ((All (_ a b) [a b]) nominal/0 nominal/1)) - (.type_literal [nominal/0 nominal/1]))) - (..succeeds? (/.check (.type_literal [nominal/0 nominal/1]) - (.type_literal ((All (_ a b) [a b]) nominal/0 nominal/1)))) + (and (..succeeds? (/.check (//.literal ((All (_ a b) [a b]) nominal/0 nominal/1)) + (//.literal [nominal/0 nominal/1]))) + (..succeeds? (/.check (//.literal [nominal/0 nominal/1]) + (//.literal ((All (_ a b) [a b]) nominal/0 nominal/1)))) - (..succeeds? (/.check (.type_literal ((Ex (_ a b) [a b]) nominal/0 nominal/1)) - (.type_literal [nominal/0 nominal/1]))) - (..succeeds? (/.check (.type_literal [nominal/0 nominal/1]) - (.type_literal ((Ex (_ a b) [a b]) nominal/0 nominal/1)))))] + (..succeeds? (/.check (//.literal ((Ex (_ a b) [a b]) nominal/0 nominal/1)) + (//.literal [nominal/0 nominal/1]))) + (..succeeds? (/.check (//.literal [nominal/0 nominal/1]) + (//.literal ((Ex (_ a b) [a b]) nominal/0 nominal/1)))))] (and types_flow_through! multiple_parameters!))) @@ -843,10 +843,10 @@ (Random Bit) (do random.monad [example ..clean_type] - (in (and (and (/.subsumes? (.type_literal (List example)) (.type_literal (All (_ a) (List a)))) - (not (/.subsumes? (.type_literal (All (_ a) (List a))) (.type_literal (List example))))) - (and (/.subsumes? (.type_literal (Ex (_ a) (List a))) (.type_literal (List example))) - (not (/.subsumes? (.type_literal (List example)) (.type_literal (Ex (_ a) (List a)))))))))) + (in (and (and (/.subsumes? (//.literal (List example)) (//.literal (All (_ a) (List a)))) + (not (/.subsumes? (//.literal (All (_ a) (List a))) (//.literal (List example))))) + (and (/.subsumes? (//.literal (Ex (_ a) (List a))) (//.literal (List example))) + (not (/.subsumes? (//.literal (List example)) (//.literal (Ex (_ a) (List a)))))))))) (def for_subsumption|named (Random Bit) diff --git a/stdlib/source/test/lux/meta/type/variance.lux b/stdlib/source/test/lux/meta/type/variance.lux index 0c6c106f9..b84e6b122 100644 --- a/stdlib/source/test/lux/meta/type/variance.lux +++ b/stdlib/source/test/lux/meta/type/variance.lux @@ -28,16 +28,16 @@ [expected random.nat]) (all _.and (_.coverage [/.Co] - (and (//check.subsumes? (type_literal (/.Co Super)) (type_literal (/.Co Sub))) - (not (//check.subsumes? (type_literal (/.Co Sub)) (type_literal (/.Co Super)))))) + (and (//check.subsumes? (//.literal (/.Co Super)) (//.literal (/.Co Sub))) + (not (//check.subsumes? (//.literal (/.Co Sub)) (//.literal (/.Co Super)))))) (_.coverage [/.Contra] - (and (//check.subsumes? (type_literal (/.Contra Sub)) (type_literal (/.Contra Super))) - (not (//check.subsumes? (type_literal (/.Contra Super)) (type_literal (/.Contra Sub)))))) + (and (//check.subsumes? (//.literal (/.Contra Sub)) (//.literal (/.Contra Super))) + (not (//check.subsumes? (//.literal (/.Contra Super)) (//.literal (/.Contra Sub)))))) (_.coverage [/.In] - (and (//check.subsumes? (type_literal (/.In Super)) (type_literal (/.In Super))) - (//check.subsumes? (type_literal (/.In Sub)) (type_literal (/.In Sub))) - (not (//check.subsumes? (type_literal (/.In Sub)) (type_literal (/.In Super)))) - (not (//check.subsumes? (type_literal (/.In Super)) (type_literal (/.In Sub)))))) + (and (//check.subsumes? (//.literal (/.In Super)) (//.literal (/.In Super))) + (//check.subsumes? (//.literal (/.In Sub)) (//.literal (/.In Sub))) + (not (//check.subsumes? (//.literal (/.In Sub)) (//.literal (/.In Super)))) + (not (//check.subsumes? (//.literal (/.In Super)) (//.literal (/.In Sub)))))) (_.for [/.Mutable] (all _.and (_.coverage [/.write /.read] diff --git a/stdlib/source/test/lux/world.lux b/stdlib/source/test/lux/world.lux index fe8136b3c..6fd831f0c 100644 --- a/stdlib/source/test/lux/world.lux +++ b/stdlib/source/test/lux/world.lux @@ -22,7 +22,9 @@ ["[1]/[0]" session]] ["[1]/[0]" market ["[1]/[0]" price] - ["[1]/[0]" analysis]]] + ["[1]/[0]" analysis]] + ["[1]/[0]" interest + ["[1]/[0]" rate]]] ["[1][0]" net] ["[1][0]" time] ["[1][0]" locale] @@ -43,6 +45,7 @@ /finance/trade/session.test /finance/market/price.test /finance/market/analysis.test + /finance/interest/rate.test /net.test /time.test diff --git a/stdlib/source/test/lux/world/file/extension.lux b/stdlib/source/test/lux/world/file/extension.lux index 5fe5207a6..4c3a957ce 100644 --- a/stdlib/source/test/lux/world/file/extension.lux +++ b/stdlib/source/test/lux/world/file/extension.lux @@ -23,82 +23,110 @@ [\\library ["[0]" /]]) -(with_expansions [ (these [/.compressed_7z_archive] - - [/.archive] - [/.advanced_audio_coding] - [/.agda_source_code] - [/.android_application_package] - [/.assembler_source_code] - - [/.binary] - [/.bzip2_archive] - [/.blender_project] - - [/.c_source_code] - [/.c++_source_code] - [/.java_class] - [/.dos_program] - [/.c#_source_code] - [/.css] - [/.comma_separated_values] - - [/.d_source_code] - [/.dart_source_code] - - [/.emacs_lisp_source_code] - [/.compiled_emacs_lisp_code] - [/.executable_and_linkable_file] - [/.electronic_publication] - [/.erlang_source_code] - [/.executable_program] - - [/.apophysis_fractal] - - [/.gps_exchange_format] - [/.gzip_compressed_data] - - [/.http_archive_format] - [/.c_header] - [/.html] - - [/.optical_disc_file_system] - - [/.java_archive] - [/.java_source_code] - [/.javascript_source_code] - [/.javascript_object_notation] - - [/.llvm_assembly] - [/.lua_source_code] - [/.lzip_archive] - - [/.markdown] - [/.musical_instrument_digital_interface] - - [/.object_code] - [/.vorbis_audio] - - [/.portable_document_format] - [/.php_source_code] - [/.maven_build_configuration] - [/.postscript_source_code] - [/.python_source_code] - - [/.ruby_source_code] - - [/.scheme_source_code] - [/.unix_shell_script] - [/.structured_query_language] - [/.scalable_vector_graphics] - - [/.tape_archive] - [/.temporary_file] - [/.tab_separated_values] - - [/.yaml] - - [/.zip_archive])] +(with_expansions [ (these [%->d + [/.compressed_7z_archive + + /.archive + /.advanced_audio_coding + /.agda_source_code + /.android_application_package + /.assembler_source_code + + /.binary + /.bzip2_archive + /.blender_project + + /.c_source_code + /.c++_source_code + /.java_class + /.dos_program + /.c#_source_code + /.css + /.comma_separated_values + + /.d_source_code + /.dart_source_code]] + + [e->j + [/.emacs_lisp_source_code + /.compiled_emacs_lisp_code + /.executable_and_linkable_file + /.electronic_publication + /.erlang_source_code + /.executable_program + + /.apophysis_fractal + + /.gps_exchange_format + /.gzip_compressed_data + + /.http_archive_format + /.c_header + /.html + + /.optical_disc_file_system + + /.java_archive + /.java_source_code + /.javascript_source_code + /.javascript_object_notation]] + + [l->p + [/.llvm_assembly + /.lua_source_code + /.lzip_archive + + /.markdown + /.musical_instrument_digital_interface + + /.object_code + /.vorbis_audio + + /.portable_document_format + /.php_source_code + /.maven_build_configuration + /.postscript_source_code + /.python_source_code]] + + [r->z + [/.ruby_source_code + + /.scheme_source_code + /.unix_shell_script + /.structured_query_language + /.scalable_vector_graphics + + /.tape_archive + /.temporary_file + /.tab_separated_values + + /.yaml + + /.zip_archive]])] + (def all_options + (list.together (`` (list (,, (with_template [ ] + [((is (-> Any (List /.Extension)) + (function (_ _) + (`` (list (,, (template.spliced )))))) + 123)] + + )))))) + + (def unique_options + (set.of_list text.hash ..all_options)) + + (def verdict + (n.= (list.size ..all_options) + (set.size ..unique_options))) + + (with_template [ ] + [(def + Test + (_.coverage + ..verdict))] + + ) + (def .public test Test (<| (_.covering /._) @@ -106,14 +134,10 @@ []) (_.for [/.Extension]) (`` (all _.and - (_.coverage [(,, (with_template [] - [] - - ))] - (let [options (list ) - uniques (set.of_list text.hash options)] - (n.= (list.size options) - (set.size uniques)))) + (,, (with_template [ ] + [] + + )) (,, (with_template [ ] [(with_expansions [' (template.spliced )] (`` (_.coverage [(,, (with_template [] diff --git a/stdlib/source/test/lux/world/finance/interest/rate.lux b/stdlib/source/test/lux/world/finance/interest/rate.lux new file mode 100644 index 000000000..8ee6dac21 --- /dev/null +++ b/stdlib/source/test/lux/world/finance/interest/rate.lux @@ -0,0 +1,64 @@ +... This Source Code Form is subject to the terms of the Mozilla Public License, v. 2.0. +... If a copy of the MPL was not distributed with this file, You can obtain one at https://mozilla.org/MPL/2.0/. + +(.require + [library + [lux (.except) + [abstract + [monad (.only do)] + ["[0]" monoid + ["[1]T" \\test]]] + [data + ["[0]" bit (.use "[1]#[0]" equivalence)] + ["[0]" text (.use "[1]#[0]" equivalence)]] + [math + ["[0]" random (.only Random) (.use "[1]#[0]" functor)] + [number + ["n" nat] + ["f" frac]]] + [test + ["_" property (.only Test)]]]] + [\\library + ["[0]" / (.only) + [/// + ["[0]" money (.only) + ["[0]" currency]]]]]) + +(def .public random + (Random /.Rate) + (random#each f.abs random.safe_frac)) + +(def .public test + Test + (<| (_.covering /._) + (do [! random.monad] + [left ..random + right ..random + + money (of ! each (|>> (n.% 1,000) ++) random.nat)]) + (_.for [/.Rate]) + (all _.and + (_.for [/.monoid /.break_even /.compound] + (monoidT.spec f.equivalence /.monoid ..random)) + + (_.coverage [/.format] + (bit#= (f.= left right) + (text#= (/.format left) (/.format right)))) + (_.coverage [/.loss? /.gain? /.break_even?] + (or (and (/.loss? left) + (not (/.gain? left)) + (not (/.break_even? left))) + (and (not (/.loss? left)) + (/.gain? left) + (not (/.break_even? left))) + (and (not (/.loss? left)) + (not (/.gain? left)) + (/.break_even? left)))) + (_.coverage [/.rate] + (and (/.loss? (/.rate (money.money currency.usd money) + (money.money currency.usd (-- money)))) + (/.gain? (/.rate (money.money currency.usd money) + (money.money currency.usd (++ money)))) + (/.break_even? (/.rate (money.money currency.usd money) + (money.money currency.usd money))))) + ))) -- cgit v1.2.3