From bfacc0c96e56eedf788aba44bd8ad2848a35c390 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Fri, 16 Jul 2021 02:23:00 -0400 Subject: Fixed some inconsistent naming. --- stdlib/source/library/lux.lux | 34 ++++------- stdlib/source/library/lux/abstract/fold.lux | 2 +- .../source/library/lux/control/function/memo.lux | 6 +- .../source/library/lux/control/function/mixin.lux | 2 +- stdlib/source/library/lux/control/parser/tree.lux | 4 +- stdlib/source/library/lux/control/state.lux | 2 +- stdlib/source/library/lux/data/collection/bits.lux | 36 ++++++------ .../library/lux/data/collection/dictionary.lux | 8 +-- stdlib/source/library/lux/data/collection/tree.lux | 6 +- .../library/lux/data/collection/tree/zipper.lux | 26 ++++----- stdlib/source/library/lux/data/maybe.lux | 2 +- stdlib/source/library/lux/ffi.old.lux | 54 +++++++++--------- stdlib/source/library/lux/ffi.rb.lux | 2 +- stdlib/source/library/lux/math/number/int.lux | 2 +- stdlib/source/library/lux/math/number/nat.lux | 28 ++++----- stdlib/source/library/lux/time/year.lux | 18 +++--- .../lux/phase/extension/generation/jvm/host.lux | 2 +- .../lux/tool/compiler/meta/archive/document.lux | 4 +- .../library/lux/world/output/video/resolution.lux | 2 +- stdlib/source/program/aedifex/artifact/time.lux | 6 ++ .../compositor/generation/structure.lux | 2 +- .../source/specification/lux/abstract/comonad.lux | 8 +-- stdlib/source/specification/lux/abstract/monad.lux | 8 +-- stdlib/source/test/aedifex/artifact.lux | 14 ++++- stdlib/source/test/aedifex/artifact/extension.lux | 8 ++- stdlib/source/test/aedifex/artifact/time.lux | 12 ++++ stdlib/source/test/lux/abstract/fold.lux | 4 +- stdlib/source/test/lux/control/exception.lux | 66 +++++++++++----------- stdlib/source/test/lux/control/function/mixin.lux | 4 +- stdlib/source/test/lux/control/parser/tree.lux | 4 +- .../test/lux/control/security/capability.lux | 20 +++---- stdlib/source/test/lux/control/state.lux | 20 +++---- stdlib/source/test/lux/data/collection/bits.lux | 4 +- stdlib/source/test/lux/data/collection/tree.lux | 12 ++-- .../test/lux/data/collection/tree/zipper.lux | 10 ++-- stdlib/source/test/lux/data/maybe.lux | 4 +- stdlib/source/test/lux/ffi.lua.lux | 4 +- stdlib/source/test/lux/ffi.rb.lux | 49 ++++++++++++---- stdlib/source/test/lux/math/modular.lux | 6 +- stdlib/source/test/lux/math/number/int.lux | 4 +- stdlib/source/test/lux/math/number/nat.lux | 4 +- stdlib/source/test/lux/time/year.lux | 4 +- .../compiler/language/lux/phase/analysis/case.lux | 4 +- .../language/lux/phase/analysis/structure.lux | 4 +- .../compiler/language/lux/phase/synthesis/case.lux | 2 +- .../test/lux/world/output/video/resolution.lux | 2 +- 46 files changed, 287 insertions(+), 242 deletions(-) (limited to 'stdlib/source') diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux index 9b01303ea..6d1f82632 100644 --- a/stdlib/source/library/lux.lux +++ b/stdlib/source/library/lux.lux @@ -2052,7 +2052,7 @@ #None} x)) -(def:''' (tuple->list tuple) +(def:''' (tuple_to_list tuple) #Nil (-> Code ($' Maybe ($' List Code))) ({[_ (#Tuple members)] @@ -2161,7 +2161,7 @@ _ (fail "Wrong syntax for template")} [(monad\map maybe_monad get_short bindings) - (monad\map maybe_monad tuple->list data)]) + (monad\map maybe_monad tuple_to_list data)]) _ (fail "Wrong syntax for template")} @@ -3294,8 +3294,7 @@ (#Cons x xs') (if ("lux i64 =" 0 idx) (#Some x) - (nth ("lux i64 -" 1 idx) xs') - ))) + (nth ("lux i64 -" 1 idx) xs')))) (def: (beta_reduce env type) (-> (List Type) Type Type) @@ -4839,7 +4838,7 @@ (case (: (Maybe (List Code)) (do maybe_monad [bindings' (monad\map maybe_monad get_short bindings) - data' (monad\map maybe_monad tuple->list data)] + data' (monad\map maybe_monad tuple_to_list data)] (let [num_bindings (list\size bindings')] (if (every? (|>> ("lux i64 =" num_bindings)) (list\map list\size data')) @@ -4943,7 +4942,7 @@ (-> (List [Code Code]) (List Code)) (|>> (list\map rejoin_pair) list\join)) -(def: (doc_example->Text prev_location baseline example) +(def: (doc_example_to_text prev_location baseline example) (-> Location Nat Code [Location Text]) (case example (^template [ ] @@ -4963,7 +4962,7 @@ (^template [ ] [[group_location ( parts)] (let [[group_location' parts_text] (list\fold (function (_ part [last_location text_accum]) - (let [[part_location part_text] (doc_example->Text last_location baseline part)] + (let [[part_location part_text] (doc_example_to_text last_location baseline part)] [part_location (text\compose text_accum part_text)])) [(delim_update_location group_location) ""] ( parts))] @@ -4977,14 +4976,14 @@ [#Record "{" "}" rejoin_all_pairs]) [new_location (#Rev value)] - ("lux io error" "@doc_example->Text Undefined behavior.") + ("lux io error" "@doc_example_to_text Undefined behavior.") )) (def: (with_baseline baseline [file line column]) (-> Nat Location Location) [file line baseline]) -(def: (doc_fragment->Text fragment) +(def: (doc_fragment_to_text fragment) (-> Doc_Fragment Text) (case fragment (#Doc_Comment comment) @@ -4996,7 +4995,7 @@ (#Doc_Example example) (let [baseline (find_baseline_column example) [location _] example - [_ text] (doc_example->Text (with_baseline baseline location) baseline example)] + [_ text] (doc_example_to_text (with_baseline baseline location) baseline example)] (text\compose text __paragraph)))) (macro: #export (doc tokens) @@ -5013,7 +5012,7 @@ " x)))"))} (return (list (` [(~ location_code) (#.Text (~ (|> tokens - (list\map (|>> identify_doc_fragment doc_fragment->Text)) + (list\map (|>> identify_doc_fragment doc_fragment_to_text)) (text\join_with "") text$)))])))) @@ -5451,17 +5450,6 @@ (#Right state scope_type_vars) )) -(def: (list_at idx xs) - (All [a] (-> Nat (List a) (Maybe a))) - (case xs - #Nil - #None - - (#Cons x xs') - (if ("lux i64 =" 0 idx) - (#Some x) - (list_at (dec idx) xs')))) - (macro: #export ($ tokens) {#.doc (doc "Allows you to refer to the type-variables in a polymorphic function's type, by their index." "In the example below, 0 corresponds to the 'a' variable." @@ -5475,7 +5463,7 @@ (^ (list [_ (#Nat idx)])) (do meta_monad [stvs get_scope_type_vars] - (case (list_at idx (list\reverse stvs)) + (case (..nth idx (list\reverse stvs)) (#Some var_id) (wrap (list (` (#Ex (~ (nat$ var_id)))))) diff --git a/stdlib/source/library/lux/abstract/fold.lux b/stdlib/source/library/lux/abstract/fold.lux index 168d743be..58059e634 100644 --- a/stdlib/source/library/lux/abstract/fold.lux +++ b/stdlib/source/library/lux/abstract/fold.lux @@ -10,7 +10,7 @@ (-> (-> b a a) a (F b) a)) fold)) -(def: #export (with-monoid monoid fold value) +(def: #export (with_monoid monoid fold value) (All [F a] (-> (Monoid a) (Fold F) (F a) a)) (let [(^open "/\.") monoid] diff --git a/stdlib/source/library/lux/control/function/memo.lux b/stdlib/source/library/lux/control/function/memo.lux index 5ab6c2b3b..4c50a0695 100644 --- a/stdlib/source/library/lux/control/function/memo.lux +++ b/stdlib/source/library/lux/control/function/memo.lux @@ -41,7 +41,7 @@ (All [i o] (:let [Memory (Dictionary i o)] (-> (Memo i o) (-> [Memory i] [Memory o])))) - (let [memo (//.mixin (//.inherit ..memoization (//.from-recursive memo)))] + (let [memo (//.mixin (//.inherit ..memoization (//.from_recursive memo)))] (function (_ [memory input]) (|> input memo (state.run memory))))) @@ -50,7 +50,7 @@ "Memoized results will be re-used during recursive invocations, but cannot be accessed after the main invocation has ended.")} (All [i o] (-> (Hash i) (Memo i o) (-> i o))) - (let [memo (//.mixin (//.inherit ..memoization (//.from-recursive memo))) + (let [memo (//.mixin (//.inherit ..memoization (//.from_recursive memo))) empty (dictionary.new hash)] (|>> memo (state.run empty) product.right))) @@ -59,6 +59,6 @@ "This is useful as a test control when measuring the effect of using memoization.")} (All [i o] (-> (Hash i) (Memo i o) (-> i o))) - (let [memo (//.mixin (//.from-recursive memo)) + (let [memo (//.mixin (//.from_recursive memo)) empty (dictionary.new hash)] (|>> memo (state.run empty) product.right))) diff --git a/stdlib/source/library/lux/control/function/mixin.lux b/stdlib/source/library/lux/control/function/mixin.lux index f70b2f9c3..8c3443339 100644 --- a/stdlib/source/library/lux/control/function/mixin.lux +++ b/stdlib/source/library/lux/control/function/mixin.lux @@ -58,7 +58,7 @@ (type: #export (Recursive i o) (-> (-> i o) (-> i o))) -(def: #export (from-recursive recursive) +(def: #export (from_recursive recursive) (All [i o] (-> (Recursive i o) (Mixin i o))) (function (_ delegate recur) (recursive recur))) diff --git a/stdlib/source/library/lux/control/parser/tree.lux b/stdlib/source/library/lux/control/parser/tree.lux index 5834c69e8..6f2080628 100644 --- a/stdlib/source/library/lux/control/parser/tree.lux +++ b/stdlib/source/library/lux/control/parser/tree.lux @@ -30,7 +30,7 @@ (function (_ zipper) (#try.Success [zipper (zipper.value zipper)]))) -(exception: #export cannot-move-further) +(exception: #export cannot_move_further) (template [ ] [(def: #export @@ -38,7 +38,7 @@ (function (_ zipper) (case ( zipper) #.None - (exception.throw ..cannot-move-further []) + (exception.throw ..cannot_move_further []) (#.Some next) (#try.Success [next []]))))] diff --git a/stdlib/source/library/lux/control/state.lux b/stdlib/source/library/lux/control/state.lux index ef0e2dbb7..b39690469 100644 --- a/stdlib/source/library/lux/control/state.lux +++ b/stdlib/source/library/lux/control/state.lux @@ -89,7 +89,7 @@ (while condition body)) (wrap [])))) -(def: #export (do-while condition body) +(def: #export (do_while condition body) (All [s] (-> (State s Bit) (State s Any) (State s Any))) (do ..monad [_ body] diff --git a/stdlib/source/library/lux/data/collection/bits.lux b/stdlib/source/library/lux/data/collection/bits.lux index 63e90f7c8..c90cff48c 100644 --- a/stdlib/source/library/lux/data/collection/bits.lux +++ b/stdlib/source/library/lux/data/collection/bits.lux @@ -17,13 +17,13 @@ (type: #export Chunk I64) -(def: #export chunk-size +(def: #export chunk_size i64.width) (type: #export Bits (Array Chunk)) -(def: empty-chunk +(def: empty_chunk Chunk (.i64 0)) @@ -40,7 +40,7 @@ (def: #export (capacity bits) (-> Bits Nat) - (|> bits array.size (n.* chunk-size))) + (|> bits array.size (n.* chunk_size))) (def: #export empty? (-> Bits Bit) @@ -48,38 +48,38 @@ (def: #export (get index bits) (-> Nat Bits Bit) - (let [[chunk-index bit-index] (n./% chunk-size index)] - (.and (n.< (array.size bits) chunk-index) - (|> (array.read chunk-index bits) - (maybe.default empty-chunk) - (i64.set? bit-index))))) + (let [[chunk_index bit_index] (n./% chunk_size index)] + (.and (n.< (array.size bits) chunk_index) + (|> (array.read chunk_index bits) + (maybe.default empty_chunk) + (i64.set? bit_index))))) (def: (chunk idx bits) (-> Nat Bits Chunk) (if (n.< (array.size bits) idx) - (|> bits (array.read idx) (maybe.default empty-chunk)) - empty-chunk)) + (|> bits (array.read idx) (maybe.default empty_chunk)) + empty_chunk)) (template [ ] [(def: #export ( index input) (-> Nat Bits Bits) - (let [[chunk-index bit-index] (n./% chunk-size index)] - (loop [size|output (n.max (inc chunk-index) + (let [[chunk_index bit_index] (n./% chunk_size index)] + (loop [size|output (n.max (inc chunk_index) (array.size input)) output ..empty] (let [idx|output (dec size|output)] (if (n.> 0 size|output) (case (|> (..chunk idx|output input) - (cond> [(new> (n.= chunk-index idx|output) [])] - [( bit-index)] + (cond> [(new> (n.= chunk_index idx|output) [])] + [( bit_index)] ## else []) .nat) 0 - ## TODO: Remove 'no-op' once new-luxc is the official compiler. - (let [no-op (recur (dec size|output) output)] - no-op) + ## TODO: Remove 'no_op' once new-luxc is the official compiler. + (let [no_op (recur (dec size|output) output)] + no_op) chunk (|> (if (is? ..empty output) @@ -102,7 +102,7 @@ (if (n.< chunks idx) (.or (|> (..chunk idx sample) (i64.and (..chunk idx reference)) - ("lux i64 =" empty-chunk) + ("lux i64 =" empty_chunk) .not) (recur (inc idx))) #0)))) diff --git a/stdlib/source/library/lux/data/collection/dictionary.lux b/stdlib/source/library/lux/data/collection/dictionary.lux index 3ae286db8..02d733d80 100644 --- a/stdlib/source/library/lux/data/collection/dictionary.lux +++ b/stdlib/source/library/lux/data/collection/dictionary.lux @@ -174,14 +174,14 @@ (i64.right_shift level hash))) ## A mechanism to go from indices to bit-positions. -(def: (->bit_position index) +(def: (to_bit_position index) (-> Index BitPosition) (i64.left_shift index 1)) ## The bit-position within a base that a given hash-code would have. (def: (bit_position level hash) (-> Level Hash_Code BitPosition) - (->bit_position (level_index level hash))) + (to_bit_position (level_index level hash))) (def: (bit_position_is_set? bit bitmap) (-> BitPosition BitMap Bit) @@ -241,7 +241,7 @@ (#.Some sub_node) (if (n.= except_idx idx) [insertion_idx node] [(inc insertion_idx) - [(set_bit_position (->bit_position idx) bitmap) + [(set_bit_position (to_bit_position idx) bitmap) (array.write! insertion_idx (#.Left sub_node) base)]]) ))) [0 [clean_bitmap @@ -259,7 +259,7 @@ BitMap (Base k v) (Array (Node k v)))) (product.right (list\fold (function (_ hierarchy_idx (^@ default [base_idx h_array])) - (if (bit_position_is_set? (->bit_position hierarchy_idx) + (if (bit_position_is_set? (to_bit_position hierarchy_idx) bitmap) [(inc base_idx) (case (array.read base_idx base) diff --git a/stdlib/source/library/lux/data/collection/tree.lux b/stdlib/source/library/lux/data/collection/tree.lux index f6b3746e7..6ed986476 100644 --- a/stdlib/source/library/lux/data/collection/tree.lux +++ b/stdlib/source/library/lux/data/collection/tree.lux @@ -35,11 +35,11 @@ {#value value #children children}) -(type: #rec Tree-Code - [Code (List Tree-Code)]) +(type: #rec Tree_Code + [Code (List Tree_Code)]) (def: tree^ - (Parser Tree-Code) + (Parser Tree_Code) (|> (|>> <>.some .record (<>.and .any)) diff --git a/stdlib/source/library/lux/data/collection/tree/zipper.lux b/stdlib/source/library/lux/data/collection/tree/zipper.lux index bb36e3e38..942ca5c09 100644 --- a/stdlib/source/library/lux/data/collection/tree/zipper.lux +++ b/stdlib/source/library/lux/data/collection/tree/zipper.lux @@ -112,7 +112,7 @@ rights)) parent)))))) -(template [ ] +(template [ ] [(def: #export ( zipper) (All [a] (-> (Zipper a) (Maybe (Zipper a)))) (case (get@ #family zipper) @@ -122,12 +122,12 @@ (#.Some (for {@.old {#family (#.Some (|> family (set@ side') - (update@ (|>> (#.Cons (get@ #node zipper)))))) + (update@ (|>> (#.Cons (get@ #node zipper)))))) #node next}} (let [move (: (All [a] (-> (List (Tree a)) (Zipper a) (Family Zipper a) (Family Zipper a))) (function (_ side' zipper) (|>> (set@ side') - (update@ (|>> (#.Cons (get@ #node zipper)))))))] + (update@ (|>> (#.Cons (get@ #node zipper)))))))] {#family (#.Some (move side' zipper family)) #node next}))) @@ -151,13 +151,13 @@ (#.Cons last prevs) (#.Some (for {@.old {#family (#.Some (|> family (set@ #.Nil) - (update@ (|>> (#.Cons (get@ #node zipper)) + (update@ (|>> (#.Cons (get@ #node zipper)) (list\compose prevs))))) #node last}} (let [move (: (All [a] (-> (List (Tree a)) (Zipper a) (Family Zipper a) (Family Zipper a))) (function (_ prevs zipper) (|>> (set@ #.Nil) - (update@ (|>> (#.Cons (get@ #node zipper)) + (update@ (|>> (#.Cons (get@ #node zipper)) (list\compose prevs))))))] {#family (#.Some (move prevs zipper family)) #node last}))))))] @@ -281,8 +281,8 @@ (#.Some (update@ (|>> (#.Cons (//.leaf value))) family)) zipper))))] - [insert-left #lefts] - [insert-right #rights] + [insert_left #lefts] + [insert_right #rights] ) (implementation: #export functor @@ -304,15 +304,15 @@ (def: unwrap (get@ [#node #//.value])) (def: (split (^slots [#family #node])) - (let [tree-splitter (: (All [a] (-> (Tree a) (Tree (Zipper a)))) - (function (tree-splitter tree) + (let [tree_splitter (: (All [a] (-> (Tree a) (Tree (Zipper a)))) + (function (tree_splitter tree) {#//.value (..zip tree) #//.children (|> tree (get@ #//.children) - (list\map tree-splitter))}))] + (list\map tree_splitter))}))] {#family (maybe\map (function (_ (^slots [#parent #lefts #rights])) {#parent (split parent) - #lefts (list\map tree-splitter lefts) - #rights (list\map tree-splitter rights)}) + #lefts (list\map tree_splitter lefts) + #rights (list\map tree_splitter rights)}) family) - #node (tree-splitter node)}))) + #node (tree_splitter node)}))) diff --git a/stdlib/source/library/lux/data/maybe.lux b/stdlib/source/library/lux/data/maybe.lux index d7f010f13..ed6a875ce 100644 --- a/stdlib/source/library/lux/data/maybe.lux +++ b/stdlib/source/library/lux/data/maybe.lux @@ -141,7 +141,7 @@ (All [a] (-> (Maybe a) a)) (|>> (..default (undefined)))) -(def: #export (to-list value) +(def: #export (to_list value) (All [a] (-> (Maybe a) (List a))) (case value #.None diff --git a/stdlib/source/library/lux/ffi.old.lux b/stdlib/source/library/lux/ffi.old.lux index fdb5d1412..c8de0eb03 100644 --- a/stdlib/source/library/lux/ffi.old.lux +++ b/stdlib/source/library/lux/ffi.old.lux @@ -424,7 +424,7 @@ ast' ast')) -(def: (parser->replacer p ast) +(def: (parser_to_replacer p ast) (-> (Parser Code) (-> Code Code)) (case (<>.run p (list ast)) (#.Right [#.Nil ast']) @@ -434,7 +434,7 @@ ast )) -(def: (field->parser class_name [[field_name _ _] field]) +(def: (field_to_parser class_name [[field_name _ _] field]) (-> Text [Member_Declaration FieldDecl] (Parser Code)) (case field (#ConstantField _) @@ -481,7 +481,7 @@ [make_virtual_method_parser "jvm invokevirtual"] ) -(def: (method->parser params class_name [[method_name _ _] meth_def]) +(def: (method_to_parser params class_name [[method_name _ _] meth_def]) (-> (List Type_Parameter) Text [Member_Declaration Method_Definition] (Parser Code)) (case meth_def (#ConstructorMethod strict? type_vars args constructor_args return_expr exs) @@ -1092,16 +1092,16 @@ (~ body)))))))) (#OverridenMethod strict_fp? class_decl type_vars this_name arg_decls return_type body exs) - (let [super_replacer (parser->replacer (.form (do <>.monad - [_ (.this! (' ::super!)) - args (.tuple (<>.exactly (list.size arg_decls) .any)) - #let [arg_decls' (: (List Text) (list\map (|>> product.right (simple_class$ (list))) - arg_decls))]] - (wrap (`' ((~ (code.text (format "jvm invokespecial" - ":" (get@ #super_class_name super_class) - ":" name - ":" (text.join_with "," arg_decls')))) - (~' _jvm_this) (~+ args)))))))] + (let [super_replacer (parser_to_replacer (.form (do <>.monad + [_ (.this! (' ::super!)) + args (.tuple (<>.exactly (list.size arg_decls) .any)) + #let [arg_decls' (: (List Text) (list\map (|>> product.right (simple_class$ (list))) + arg_decls))]] + (wrap (`' ((~ (code.text (format "jvm invokespecial" + ":" (get@ #super_class_name super_class) + ":" name + ":" (text.join_with "," arg_decls')))) + (~' _jvm_this) (~+ args)))))))] (with_parens (spaced (list "override" (class_decl$ class_decl) @@ -1210,11 +1210,11 @@ (do meta.monad [current_module meta.current_module_name #let [fully_qualified_class_name (format (sanitize current_module) "." full_class_name) - field_parsers (list\map (field->parser fully_qualified_class_name) fields) - method_parsers (list\map (method->parser (product.right class_decl) fully_qualified_class_name) methods) - replacer (parser->replacer (list\fold <>.either - (<>.fail "") - (list\compose field_parsers method_parsers))) + field_parsers (list\map (field_to_parser fully_qualified_class_name) fields) + method_parsers (list\map (method_to_parser (product.right class_decl) fully_qualified_class_name) methods) + replacer (parser_to_replacer (list\fold <>.either + (<>.fail "") + (list\compose field_parsers method_parsers))) def_code (format "jvm class:" (spaced (list (class_decl$ class_decl) (super_class_decl$ super) @@ -1449,7 +1449,7 @@ #.Nil #1 _ #0)) -(def: (type_param->type_arg [name _]) +(def: (type_param_to_type_arg [name _]) (-> Type_Parameter Code) (code.identifier ["" name])) @@ -1498,7 +1498,7 @@ full_name (sanitize full_name) all_params (|> (member_type_vars class_tvars member) (list.filter free_type_param?) - (list\map type_param->type_arg))] + (list\map type_param_to_type_arg))] (case member (#EnumDecl enum_members) (do {! meta.monad} @@ -1510,7 +1510,7 @@ _ (let [=class_tvars (|> class_tvars (list.filter free_type_param?) - (list\map type_param->type_arg))] + (list\map type_param_to_type_arg))] (` (All [(~+ =class_tvars)] (primitive (~ (code.text full_name)) [(~+ =class_tvars)])))))) getter_interop (: (-> Text Code) (function (_ name) @@ -1576,7 +1576,7 @@ tvar_asts (: (List Code) (|> class_tvars (list.filter free_type_param?) - (list\map type_param->type_arg))) + (list\map type_param_to_type_arg))) getter_name (code.identifier ["" (..import_name import_format method_prefix import_field_name)]) setter_name (code.identifier ["" (..import_name import_format method_prefix (format import_field_name "!"))])] getter_interop (with_gensyms [g!obj] @@ -1740,7 +1740,7 @@ (array_length my_array))} (wrap (list (` ("jvm arraylength" (~ array)))))) -(def: (type->class_name type) +(def: (type_to_class_name type) (-> Type (Meta Text)) (if (type\= Any type) (\ meta.monad wrap "java.lang.Object") @@ -1754,10 +1754,10 @@ (meta.fail (format "Cannot apply type: " (type.format F) " to " (type.format A))) (#.Some type') - (type->class_name type')) + (type_to_class_name type')) (#.Named _ type') - (type->class_name type') + (type_to_class_name type') _ (meta.fail (format "Cannot convert to JvmType: " (type.format type)))))) @@ -1769,7 +1769,7 @@ [_ (#.Identifier array_name)] (do meta.monad [array_type (meta.find_type array_name) - array_jvm_type (type->class_name array_type)] + array_jvm_type (type_to_class_name array_type)] (case array_jvm_type (^template [ ] [ @@ -1798,7 +1798,7 @@ [_ (#.Identifier array_name)] (do meta.monad [array_type (meta.find_type array_name) - array_jvm_type (type->class_name array_type)] + array_jvm_type (type_to_class_name array_type)] (case array_jvm_type (^template [ ] [ diff --git a/stdlib/source/library/lux/ffi.rb.lux b/stdlib/source/library/lux/ffi.rb.lux index 511351bad..f3f483e23 100644 --- a/stdlib/source/library/lux/ffi.rb.lux +++ b/stdlib/source/library/lux/ffi.rb.lux @@ -27,7 +27,7 @@ (template [] [(with_expansions [ (template.identifier [ "'"])] - (abstract: #export Any) + (abstract: Any) (type: #export (..Object )))] diff --git a/stdlib/source/library/lux/math/number/int.lux b/stdlib/source/library/lux/math/number/int.lux index c72c31e16..b5806e0db 100644 --- a/stdlib/source/library/lux/math/number/int.lux +++ b/stdlib/source/library/lux/math/number/int.lux @@ -131,7 +131,7 @@ +0 a _ (gcd b (..% b a)))) -(def: #export (co-prime? a b) +(def: #export (co_prime? a b) (-> Int Int Bit) (..= +1 (..gcd a b))) diff --git a/stdlib/source/library/lux/math/number/nat.lux b/stdlib/source/library/lux/math/number/nat.lux index 52e252c84..ebec1b4e9 100644 --- a/stdlib/source/library/lux/math/number/nat.lux +++ b/stdlib/source/library/lux/math/number/nat.lux @@ -130,7 +130,7 @@ 0 a _ (gcd b (..% b a)))) -(def: #export (co-prime? a b) +(def: #export (co_prime? a b) (-> Nat Nat Bit) (..= 1 (..gcd a b))) @@ -194,21 +194,21 @@ [maximum ..max (\ ..interval bottom)] ) -(def: (binary-character value) +(def: (binary_character value) (-> Nat Text) (case value 0 "0" 1 "1" _ (undefined))) -(def: (binary-value digit) +(def: (binary_value digit) (-> Nat (Maybe Nat)) (case digit (^ (char "0")) (#.Some 0) (^ (char "1")) (#.Some 1) _ #.None)) -(def: (octal-character value) +(def: (octal_character value) (-> Nat Text) (case value 0 "0" @@ -221,7 +221,7 @@ 7 "7" _ (undefined))) -(def: (octal-value digit) +(def: (octal_value digit) (-> Nat (Maybe Nat)) (case digit (^ (char "0")) (#.Some 0) @@ -234,7 +234,7 @@ (^ (char "7")) (#.Some 7) _ #.None)) -(def: (decimal-character value) +(def: (decimal_character value) (-> Nat Text) (case value 0 "0" @@ -249,7 +249,7 @@ 9 "9" _ (undefined))) -(def: (decimal-value digit) +(def: (decimal_value digit) (-> Nat (Maybe Nat)) (case digit (^ (char "0")) (#.Some 0) @@ -264,7 +264,7 @@ (^ (char "9")) (#.Some 9) _ #.None)) -(def: (hexadecimal-character value) +(def: (hexadecimal_character value) (-> Nat Text) (case value 0 "0" @@ -285,7 +285,7 @@ 15 "F" _ (undefined))) -(def: (hexadecimal-value digit) +(def: (hexadecimal_value digit) (-> Nat (Maybe Nat)) (case digit (^template [ ] @@ -336,9 +336,9 @@ (#try.Success output))) (#try.Failure ("lux text concat" repr))))))] - [1 binary binary-character binary-value "Invalid binary syntax for Nat: "] - [3 octal octal-character octal-value "Invalid octal syntax for Nat: "] - [4 hex hexadecimal-character hexadecimal-value "Invalid hexadecimal syntax for Nat: "] + [1 binary binary_character binary_value "Invalid binary syntax for Nat: "] + [3 octal octal_character octal_value "Invalid octal syntax for Nat: "] + [4 hex hexadecimal_character hexadecimal_value "Invalid hexadecimal syntax for Nat: "] ) (implementation: #export decimal @@ -347,7 +347,7 @@ (def: (encode value) (loop [input value output ""] - (let [digit (decimal-character (..% 10 input)) + (let [digit (decimal_character (..% 10 input)) output' ("lux text concat" digit output)] (case (../ 10 input) 0 @@ -363,7 +363,7 @@ (loop [idx 0 output 0] (if (..< input-size idx) - (case (decimal-value ("lux text char" idx repr)) + (case (decimal_value ("lux text char" idx repr)) #.None diff --git a/stdlib/source/library/lux/time/year.lux b/stdlib/source/library/lux/time/year.lux index 95280df9c..b3f3e7ecf 100644 --- a/stdlib/source/library/lux/time/year.lux +++ b/stdlib/source/library/lux/time/year.lux @@ -32,7 +32,7 @@ year (dec year))) -(exception: #export there-is-no-year-0) +(exception: #export there_is_no_year_0) (abstract: #export Year Int @@ -40,7 +40,7 @@ (def: #export (year value) (-> Int (Try Year)) (case value - +0 (exception.throw ..there-is-no-year-0 []) + +0 (exception.throw ..there_is_no_year_0 []) _ (#try.Success (:abstraction (..internal value))))) (def: #export value @@ -80,9 +80,9 @@ (or (not (..divisible? (.int ..century) year)) (..divisible? (.int ..era) year))))) -(def: (with-year-0-leap year days) - (let [after-year-0? (i.> +0 year)] - (if after-year-0? +(def: (with_year_0_leap year days) + (let [after_year_0? (i.> +0 year)] + (if after_year_0? (i.+ +1 days) days))) @@ -100,7 +100,7 @@ [i.- ..century] [i.+ ..era] )) - (..with-year-0-leap year))))) + (..with_year_0_leap year))))) (def: (encode year) (-> Year Text) @@ -114,10 +114,10 @@ (do {! <>.monad} [sign (<>.or (.this "-") (wrap [])) digits (.many .decimal) - raw-year (<>.codec i.decimal (wrap (text\compose "+" digits)))] + raw_year (<>.codec i.decimal (wrap (text\compose "+" digits)))] (<>.lift (..year (case sign - (#.Left _) (i.* -1 raw-year) - (#.Right _) raw-year))))) + (#.Left _) (i.* -1 raw_year) + (#.Right _) raw_year))))) (implementation: #export codec {#.doc (doc "Based on ISO 8601." diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux index b46934a86..079fc96ec 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux @@ -1021,7 +1021,7 @@ list\join ## Remove duplicates. (set.from-list //////synthesis.hash) - set.to-list) + set.to_list) global-mapping (|> total-environment ## Give them names as "foreign" variables. list.enumeration diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux index ea5ce1006..39edd668e 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux @@ -20,7 +20,7 @@ ["." key (#+ Key)] [descriptor (#+ Module)]]) -(exception: #export (invalid-signature {expected Signature} {actual Signature}) +(exception: #export (invalid_signature {expected Signature} {actual Signature}) (exception.report ["Expected" (signature.description expected)] ["Actual" (signature.description actual)])) @@ -41,7 +41,7 @@ e (:assume document//content))) - (exception.throw ..invalid-signature [(key.signature key) + (exception.throw ..invalid_signature [(key.signature key) document//signature])))) (def: #export (write key content) diff --git a/stdlib/source/library/lux/world/output/video/resolution.lux b/stdlib/source/library/lux/world/output/video/resolution.lux index 24f48182c..8822c268c 100644 --- a/stdlib/source/library/lux/world/output/video/resolution.lux +++ b/stdlib/source/library/lux/world/output/video/resolution.lux @@ -43,5 +43,5 @@ [fhd 1920 1080] [wuxga 1920 1200] [wqhd 2560 1440] - [uhd-4k 3840 2160] + [uhd_4k 3840 2160] ) diff --git a/stdlib/source/program/aedifex/artifact/time.lux b/stdlib/source/program/aedifex/artifact/time.lux index 41ee0d418..ec7ddc4a9 100644 --- a/stdlib/source/program/aedifex/artifact/time.lux +++ b/stdlib/source/program/aedifex/artifact/time.lux @@ -26,6 +26,12 @@ Time [/date.epoch time.midnight]) +(def: #export (instant time) + (-> Time Instant) + (let [[date time] time] + (instant.from_date_time (/date.value date) + time))) + (def: #export (from_instant instant) (-> Instant (Try Time)) (do try.monad diff --git a/stdlib/source/specification/compositor/generation/structure.lux b/stdlib/source/specification/compositor/generation/structure.lux index 7c45d2a9b..c8482aff2 100644 --- a/stdlib/source/specification/compositor/generation/structure.lux +++ b/stdlib/source/specification/compositor/generation/structure.lux @@ -76,7 +76,7 @@ (and (n.= size (array.size tuple-out)) (list.every? (function (_ [left right]) (i.= left (:as Int right))) - (list.zip/2 tuple-in (array.to-list tuple-out))))) + (list.zip/2 tuple-in (array.to_list tuple-out))))) (#try.Failure _) false))))) diff --git a/stdlib/source/specification/lux/abstract/comonad.lux b/stdlib/source/specification/lux/abstract/comonad.lux index 85d00b8f2..d4532a70b 100644 --- a/stdlib/source/specification/lux/abstract/comonad.lux +++ b/stdlib/source/specification/lux/abstract/comonad.lux @@ -13,7 +13,7 @@ [// [functor (#+ Injection Comparison)]]) -(def: (left-identity injection (^open "_//.")) +(def: (left_identity injection (^open "_//.")) (All [f] (-> (Injection f) (CoMonad f) Test)) (do {! random.monad} [sample random.nat @@ -25,7 +25,7 @@ (n.= (morphism start) (|> start _//split (_//map morphism) _//unwrap))))) -(def: (right-identity injection comparison (^open "_//.")) +(def: (right_identity injection comparison (^open "_//.")) (All [f] (-> (Injection f) (Comparison f) (CoMonad f) Test)) (do random.monad [sample random.nat @@ -55,7 +55,7 @@ (All [f] (-> (Injection f) (Comparison f) (CoMonad f) Test)) (<| (_.for [/.CoMonad]) ($_ _.and - (..left-identity injection subject) - (..right-identity injection comparison subject) + (..left_identity injection subject) + (..right_identity injection comparison subject) (..associativity injection comparison subject) ))) diff --git a/stdlib/source/specification/lux/abstract/monad.lux b/stdlib/source/specification/lux/abstract/monad.lux index 869eb24c7..bc1b643f2 100644 --- a/stdlib/source/specification/lux/abstract/monad.lux +++ b/stdlib/source/specification/lux/abstract/monad.lux @@ -11,7 +11,7 @@ [// [functor (#+ Injection Comparison)]]) -(def: (left-identity injection comparison (^open "_//.")) +(def: (left_identity injection comparison (^open "_//.")) (All [f] (-> (Injection f) (Comparison f) (/.Monad f) Test)) (do {! random.monad} [sample random.nat @@ -23,7 +23,7 @@ (|> (injection sample) (_//map morphism) _//join) (morphism sample))))) -(def: (right-identity injection comparison (^open "_//.")) +(def: (right_identity injection comparison (^open "_//.")) (All [f] (-> (Injection f) (Comparison f) (/.Monad f) Test)) (do random.monad [sample random.nat] @@ -51,7 +51,7 @@ (All [f] (-> (Injection f) (Comparison f) (/.Monad f) Test)) (<| (_.for [/.Monad]) ($_ _.and - (..left-identity injection comparison monad) - (..right-identity injection comparison monad) + (..left_identity injection comparison monad) + (..right_identity injection comparison monad) (..associativity injection comparison monad) ))) diff --git a/stdlib/source/test/aedifex/artifact.lux b/stdlib/source/test/aedifex/artifact.lux index 6afbbf27c..ce0af7e7f 100644 --- a/stdlib/source/test/aedifex/artifact.lux +++ b/stdlib/source/test/aedifex/artifact.lux @@ -6,7 +6,9 @@ [monad (#+ do)] [hash (#+ Hash)] [\\specification - ["$." equivalence]]] + ["$." equivalence] + ["$." order] + ["$." hash]]] [control [concurrency [promise (#+ Promise)]]] @@ -37,11 +39,21 @@ (def: #export test Test (<| (_.covering /._) + (do random.monad + [sample ..random]) (_.for [/.Group /.Name /.Version /.Artifact] ($_ _.and (_.for [/.equivalence] ($equivalence.spec /.equivalence ..random)) + (_.for [/.order] + ($order.spec /.order ..random)) + (_.for [/.hash] + ($hash.spec /.hash ..random)) + + (_.cover [/.format /.identity] + (and (text.ends_with? (/.identity sample) (/.format sample)) + (not (text\= (/.identity sample) (/.format sample))))) /extension.test /snapshot.test diff --git a/stdlib/source/test/aedifex/artifact/extension.lux b/stdlib/source/test/aedifex/artifact/extension.lux index fd28c5d92..b8a2144aa 100644 --- a/stdlib/source/test/aedifex/artifact/extension.lux +++ b/stdlib/source/test/aedifex/artifact/extension.lux @@ -29,10 +29,12 @@ uniques (set.from_list text.hash options)] (n.= (list.size options) (set.size uniques)))) - (_.cover [/.extension] + (_.cover [/.extension /.type] (`` (and (~~ (template [ ] - [(text\= - (/.extension ))] + [(and (text\= + (/.extension )) + (text\= + (/.type (/.extension ))))] [//.lux_library /.lux_library] [//.jvm_library /.jvm_library] diff --git a/stdlib/source/test/aedifex/artifact/time.lux b/stdlib/source/test/aedifex/artifact/time.lux index f69566096..131155500 100644 --- a/stdlib/source/test/aedifex/artifact/time.lux +++ b/stdlib/source/test/aedifex/artifact/time.lux @@ -10,6 +10,8 @@ ["." try ("#\." functor)] [parser ["<.>" text]]] + [time + ["." instant ("#\." equivalence)]] [math ["." random (#+ Random)] [number @@ -43,6 +45,16 @@ (.run /.parser) (try\map (\ /.equivalence = expected)) (try.default false)))) + (do random.monad + [expected ..random] + (_.cover [/.instant /.from_instant] + (|> expected + /.instant + /.from_instant + (try\map (\ /.equivalence = expected)) + (try.default false)))) + (_.cover [/.epoch] + (instant\= instant.epoch (/.instant /.epoch))) /date.test /time.test diff --git a/stdlib/source/test/lux/abstract/fold.lux b/stdlib/source/test/lux/abstract/fold.lux index 787a8a03d..a07a19870 100644 --- a/stdlib/source/test/lux/abstract/fold.lux +++ b/stdlib/source/test/lux/abstract/fold.lux @@ -20,7 +20,7 @@ [samples (random.list 10 random.nat)] (<| (_.covering /._) ($_ _.and - (_.cover [/.with-monoid] + (_.cover [/.with_monoid] (n.= (\ list.fold fold (\ n.addition compose) (\ n.addition identity) samples) - (/.with-monoid n.addition list.fold samples))) + (/.with_monoid n.addition list.fold samples))) )))) diff --git a/stdlib/source/test/lux/control/exception.lux b/stdlib/source/test/lux/control/exception.lux index f62ad9271..534d03252 100644 --- a/stdlib/source/test/lux/control/exception.lux +++ b/stdlib/source/test/lux/control/exception.lux @@ -16,11 +16,11 @@ [// ["." try (#+ Try)]]]]) -(exception: an-exception) -(exception: another-exception) +(exception: an_exception) +(exception: another_exception) (def: label "YOLO") -(exception: (custom-exception {value Nat}) +(exception: (custom_exception {value Nat}) (/.report [label (%.nat value)])) (def: #export test @@ -28,12 +28,12 @@ (do {! random.monad} [expected random.nat wrong (|> random.nat (random.filter (|>> (n.= expected) not))) - assertion-succeeded? random.bit - #let [report-element (\ ! map %.nat random.nat)] - field0 report-element - value0 report-element - field1 report-element - value1 report-element] + assertion_succeeded? random.bit + #let [report_element (\ ! map %.nat random.nat)] + field0 report_element + value0 report_element + field1 report_element + value1 report_element] (<| (_.covering /._) (_.for [/.Exception]) ($_ _.and @@ -42,41 +42,41 @@ (#try.Success actual) (n.= expected actual) (#try.Failure _) false)) (_.cover [/.throw] - (case (/.throw ..an-exception []) + (case (/.throw ..an_exception []) (#try.Success _) false (#try.Failure _) true)) (_.cover [/.construct] - (case (/.throw ..an-exception []) + (case (/.throw ..an_exception []) (#try.Success _) false (#try.Failure message) - (text\= message (/.construct ..an-exception [])))) + (text\= message (/.construct ..an_exception [])))) (_.cover [/.match?] - (/.match? ..an-exception - (/.construct ..an-exception []))) + (/.match? ..an_exception + (/.construct ..an_exception []))) (_.cover [/.assert] - (case (/.assert ..an-exception [] assertion-succeeded?) + (case (/.assert ..an_exception [] assertion_succeeded?) (#try.Success _) - assertion-succeeded? + assertion_succeeded? (#try.Failure message) - (and (not assertion-succeeded?) - (text\= message (/.construct ..an-exception []))))) + (and (not assertion_succeeded?) + (text\= message (/.construct ..an_exception []))))) (_.cover [/.catch] (and (n.= expected - (|> (/.throw ..an-exception []) - (/.catch ..an-exception (function (_ ex) expected)) + (|> (/.throw ..an_exception []) + (/.catch ..an_exception (function (_ ex) expected)) (/.otherwise (function (_ ex) wrong)))) (n.= expected - (|> (/.throw ..another-exception []) - (/.catch ..an-exception (function (_ ex) wrong)) - (/.catch ..another-exception (function (_ ex) expected)) + (|> (/.throw ..another_exception []) + (/.catch ..an_exception (function (_ ex) wrong)) + (/.catch ..another_exception (function (_ ex) expected)) (/.otherwise (function (_ ex) wrong)))))) (_.cover [/.otherwise] (n.= expected - (|> (/.throw ..another-exception []) - (/.catch ..an-exception (function (_ ex) wrong)) + (|> (/.throw ..another_exception []) + (/.catch ..an_exception (function (_ ex) wrong)) (/.otherwise (function (_ ex) expected))))) (_.cover [/.report] (let [report (/.report [field0 value0] @@ -92,23 +92,23 @@ (text.contains? field1 enumeration) (text.contains? value1 enumeration)))) (_.cover [/.with] - (and (case (/.with ..an-exception [] (#try.Success expected)) + (and (case (/.with ..an_exception [] (#try.Success expected)) (#try.Success actual) (n.= expected actual) (#try.Failure _) false) - (case (/.with ..an-exception [] (#try.Failure "")) + (case (/.with ..an_exception [] (#try.Failure "")) (#try.Success _) false - (#try.Failure message) (text\= message (/.construct ..an-exception []))) - (case (/.with ..an-exception [] + (#try.Failure message) (text\= message (/.construct ..an_exception []))) + (case (/.with ..an_exception [] (: (Try Nat) - (/.throw ..another-exception []))) + (/.throw ..another_exception []))) (#try.Success _) false (#try.Failure message) - (and (text.contains? (/.construct ..an-exception []) message) - (text.contains? (/.construct ..another-exception []) message))))) + (and (text.contains? (/.construct ..an_exception []) message) + (text.contains? (/.construct ..another_exception []) message))))) (_.cover [/.exception:] - (case (/.throw ..custom-exception [expected]) + (case (/.throw ..custom_exception [expected]) (#try.Success _) false diff --git a/stdlib/source/test/lux/control/function/mixin.lux b/stdlib/source/test/lux/control/function/mixin.lux index 339216526..31b1e338d 100644 --- a/stdlib/source/test/lux/control/function/mixin.lux +++ b/stdlib/source/test/lux/control/function/mixin.lux @@ -123,9 +123,9 @@ (|> input function (state.run dummy) product.right)))) )) (_.for [/.Recursive] - (_.cover [/.from-recursive] + (_.cover [/.from_recursive] (let [factorial (/.mixin - (/.from-recursive + (/.from_recursive (function (_ recur input) (case input (^or 0 1) 1 diff --git a/stdlib/source/test/lux/control/parser/tree.lux b/stdlib/source/test/lux/control/parser/tree.lux index 62c4ab04e..e330464b4 100644 --- a/stdlib/source/test/lux/control/parser/tree.lux +++ b/stdlib/source/test/lux/control/parser/tree.lux @@ -159,12 +159,12 @@ (tree.leaf dummy)))) (do {! random.monad} [dummy random.nat] - (_.cover [/.cannot-move-further] + (_.cover [/.cannot_move_further] (`` (and (~~ (template [] [(|> (/.run (tree.leaf dummy)) (!expect (^multi (#try.Failure error) - (exception.match? /.cannot-move-further error))))] + (exception.match? /.cannot_move_further error))))] [/.down] [/.up] [/.right] [/.left] diff --git a/stdlib/source/test/lux/control/security/capability.lux b/stdlib/source/test/lux/control/security/capability.lux index 2798c21b2..ec2d91d20 100644 --- a/stdlib/source/test/lux/control/security/capability.lux +++ b/stdlib/source/test/lux/control/security/capability.lux @@ -15,11 +15,11 @@ [\\library ["." /]]) -(/.capability: (Can-Shift a) - (can-shift [a Nat] [a Nat])) +(/.capability: (Can_Shift a) + (can_shift [a Nat] [a Nat])) -(/.capability: Can-IO - (can-io [] (IO Nat))) +(/.capability: Can_IO + (can_io [] (IO Nat))) (def: #export test Test @@ -28,16 +28,16 @@ [shift random.nat base random.nat #let [expected (n.+ shift base)] - pass-through (random.ascii 1)] + pass_through (random.ascii 1)] (_.for [/.Capability] ($_ _.and (_.cover [/.capability: /.use] - (let [capability (..can-shift (function (_ [no-op raw]) - [no-op (n.+ shift raw)])) - [untouched actual] (/.use capability [pass-through base])] - (and (is? pass-through untouched) + (let [capability (..can_shift (function (_ [no_op raw]) + [no_op (n.+ shift raw)])) + [untouched actual] (/.use capability [pass_through base])] + (and (is? pass_through untouched) (n.= expected actual)))) - (wrap (let [capability (..can-io (function (_ _) (io.io expected)))] + (wrap (let [capability (..can_io (function (_ _) (io.io expected)))] (do promise.monad [actual (/.use (/.async capability) [])] (_.cover' [/.async] diff --git a/stdlib/source/test/lux/control/state.lux b/stdlib/source/test/lux/control/state.lux index 53622408d..a037f8a91 100644 --- a/stdlib/source/test/lux/control/state.lux +++ b/stdlib/source/test/lux/control/state.lux @@ -20,7 +20,7 @@ [\\library ["." / (#+ State)]]) -(def: (with-conditions [state output] computation) +(def: (with_conditions [state output] computation) (-> [Nat Nat] (State Nat Nat) Bit) (|> computation (/.run state) @@ -33,23 +33,23 @@ value random.nat] ($_ _.and (_.cover [/.State /.get] - (with-conditions [state state] + (with_conditions [state state] /.get)) (_.cover [/.put] - (with-conditions [state value] + (with_conditions [state value] (do /.monad [_ (/.put value)] /.get))) (_.cover [/.update] - (with-conditions [state (n.* value state)] + (with_conditions [state (n.* value state)] (do /.monad [_ (/.update (n.* value))] /.get))) (_.cover [/.use] - (with-conditions [state (inc state)] + (with_conditions [state (inc state)] (/.use inc))) (_.cover [/.local] - (with-conditions [state (n.* value state)] + (with_conditions [state (n.* value state)] (/.local (n.* value) /.get))) ))) @@ -92,8 +92,8 @@ (/.run 0) (let> [state' output'] (n.= limit state')))) - (_.cover [/.do-while] - (|> (/.do-while condition (/.update inc)) + (_.cover [/.do_while] + (|> (/.do_while condition (/.update inc)) (/.run 0) (let> [state' output'] (or (n.= limit state') @@ -101,7 +101,7 @@ (n.= 1 state')))))) ))) -(def: monad-transformer +(def: monad_transformer Test (do random.monad [state random.nat @@ -128,4 +128,4 @@ ..basics ..structures ..loops - ..monad-transformer))) + ..monad_transformer))) diff --git a/stdlib/source/test/lux/data/collection/bits.lux b/stdlib/source/test/lux/data/collection/bits.lux index bc59e6b34..3e8b89d2a 100644 --- a/stdlib/source/test/lux/data/collection/bits.lux +++ b/stdlib/source/test/lux/data/collection/bits.lux @@ -59,12 +59,12 @@ (_.cover [/.flip] (and (|> /.empty (/.flip idx) (/.get idx)) (|> /.empty (/.flip idx) (/.flip idx) (/.get idx) not))) - (_.cover [/.Chunk /.capacity /.chunk-size] + (_.cover [/.Chunk /.capacity /.chunk_size] (and (n.= 0 (/.capacity /.empty)) (|> /.empty (/.set idx) /.capacity (n.- idx) (predicate.unite (n.>= 0) - (n.< /.chunk-size))) + (n.< /.chunk_size))) (let [grown (/.flip idx /.empty)] (and (n.> 0 (/.capacity grown)) (is? /.empty (/.flip idx grown)))))) diff --git a/stdlib/source/test/lux/data/collection/tree.lux b/stdlib/source/test/lux/data/collection/tree.lux index ff281844a..a610fdef5 100644 --- a/stdlib/source/test/lux/data/collection/tree.lux +++ b/stdlib/source/test/lux/data/collection/tree.lux @@ -19,12 +19,12 @@ [\\library ["." / (#+ Tree)]]) -(def: #export (tree gen-value) +(def: #export (tree gen_value) (All [a] (-> (Random a) (Random [Nat (Tree a)]))) (do {! random.monad} - [value gen-value - num-children (\ ! map (n.% 2) random.nat) - children (random.list num-children (tree gen-value))] + [value gen_value + num_children (\ ! map (n.% 2) random.nat) + children (random.list num_children (tree gen_value))] (wrap [(|> children (list\map product.left) (list\fold n.+ 1)) @@ -58,8 +58,8 @@ (/.flatten (/.leaf expected))))) (do {! random.monad} [value random.nat - num-children (\ ! map (n.% 3) random.nat) - children (random.list num-children random.nat)] + num_children (\ ! map (n.% 3) random.nat) + children (random.list num_children random.nat)] (_.cover [/.branch] (\ (list.equivalence n.equivalence) = (list& value children) diff --git a/stdlib/source/test/lux/data/collection/tree/zipper.lux b/stdlib/source/test/lux/data/collection/tree/zipper.lux index 06e53f225..d04b3b8e9 100644 --- a/stdlib/source/test/lux/data/collection/tree/zipper.lux +++ b/stdlib/source/test/lux/data/collection/tree/zipper.lux @@ -231,21 +231,21 @@ [/.right] [/.value (n.= dummy) wrap]) (maybe.default false))))) - (_.cover [/.insert-left] + (_.cover [/.insert_left] (|> (tree.branch dummy (list (tree.leaf dummy))) /.zip (do> maybe.monad [/.down] - [(/.insert-left expected)] + [(/.insert_left expected)] [/.left] [/.value (n.= expected) wrap]) (maybe.default false))) - (_.cover [/.insert-right] + (_.cover [/.insert_right] (|> (tree.branch dummy (list (tree.leaf dummy))) /.zip (do> maybe.monad [/.down] - [(/.insert-right expected)] + [(/.insert_right expected)] [/.right] [/.value (n.= expected) wrap]) (maybe.default false))) @@ -254,7 +254,7 @@ /.zip (do> maybe.monad [/.down] - [(/.insert-left expected)] + [(/.insert_left expected)] [/.remove] [/.value (n.= expected) wrap]) (maybe.default false))) diff --git a/stdlib/source/test/lux/data/maybe.lux b/stdlib/source/test/lux/data/maybe.lux index 4f5accd9b..899541f37 100644 --- a/stdlib/source/test/lux/data/maybe.lux +++ b/stdlib/source/test/lux/data/maybe.lux @@ -75,8 +75,8 @@ (is? value (/.assume (#.Some value))))) (do random.monad [value random.nat] - (_.cover [/.to-list] + (_.cover [/.to_list] (\ (list.equivalence n.equivalence) = (list value) - (/.to-list (#.Some value))))) + (/.to_list (#.Some value))))) ))) diff --git a/stdlib/source/test/lux/ffi.lua.lux b/stdlib/source/test/lux/ffi.lua.lux index a1f181edc..963d45387 100644 --- a/stdlib/source/test/lux/ffi.lua.lux +++ b/stdlib/source/test/lux/ffi.lua.lux @@ -7,9 +7,7 @@ [control ["." io]] [math - ["." random] - [number - ["i" int]]]]] + ["." random]]]] [\\library ["." /]]) diff --git a/stdlib/source/test/lux/ffi.rb.lux b/stdlib/source/test/lux/ffi.rb.lux index c8d4ea6d5..0b57aee7e 100644 --- a/stdlib/source/test/lux/ffi.rb.lux +++ b/stdlib/source/test/lux/ffi.rb.lux @@ -4,22 +4,49 @@ ["_" test (#+ Test)] [abstract [monad (#+ do)]] - [control - ["." try]] - [data - ["." text ("#\." equivalence)]] [math - ["." random (#+ Random)] - [number - ["." nat] - ["." frac]]]]] + ["." random]]]] [\\library ["." /]]) +(/.import: File + ["#::." + (#static SEPARATOR /.String)]) + (def: #export test Test (do {! random.monad} - [] + [boolean random.bit + integer random.int + float random.frac + string (random.ascii/lower 1)] (<| (_.covering /._) - (_.test "TBD" - true)))) + (`` ($_ _.and + (~~ (template [ ] + [(_.cover [] + (exec + (: ) + true))] + + [/.Boolean boolean] + [/.Integer integer] + [/.Float float] + [/.String string] + )) + (_.for [/.Object] + ($_ _.and + (~~ (template [] + [(_.cover [] + (exec + (|> [] + (:as ) + (: (Ex [a] (/.Object a)))) + true))] + + [/.Nil] + [/.Function] + )))) + (_.cover [/.import:] + (is? (..File::SEPARATOR) + (..File::SEPARATOR))) + ))))) diff --git a/stdlib/source/test/lux/math/modular.lux b/stdlib/source/test/lux/math/modular.lux index 090481806..40a091008 100644 --- a/stdlib/source/test/lux/math/modular.lux +++ b/stdlib/source/test/lux/math/modular.lux @@ -93,17 +93,17 @@ (/.- zero subject))))) (_.cover [/.inverse] (let [one (/.modular (/.modulus subject) +1) - co-prime? (i.co-prime? (//.divisor (/.modulus subject)) + co_prime? (i.co_prime? (//.divisor (/.modulus subject)) (/.value subject))] (case (/.inverse subject) (#.Some subject^-1) - (and co-prime? + (and co_prime? (|> subject (/.* subject^-1) (/.= one))) #.None - (not co-prime?)))) + (not co_prime?)))) (_.cover [/.adapter] (<| (try.default false) (do try.monad diff --git a/stdlib/source/test/lux/math/number/int.lux b/stdlib/source/test/lux/math/number/int.lux index 9b650e795..1d95a10e5 100644 --- a/stdlib/source/test/lux/math/number/int.lux +++ b/stdlib/source/test/lux/math/number/int.lux @@ -158,9 +158,9 @@ (/.* right_k right)))] (and same_gcd! bezout_identity!))) - (_.cover [/.co-prime?] + (_.cover [/.co_prime?] (bit\= (/.= +1 (/.gcd left right)) - (/.co-prime? left right))) + (/.co_prime? left right))) (_.cover [/.lcm] (let [lcm (/.lcm left right)] (and (/.= +0 (/.% left lcm)) diff --git a/stdlib/source/test/lux/math/number/nat.lux b/stdlib/source/test/lux/math/number/nat.lux index 9577b25db..c9bb2102b 100644 --- a/stdlib/source/test/lux/math/number/nat.lux +++ b/stdlib/source/test/lux/math/number/nat.lux @@ -112,9 +112,9 @@ (let [gcd (/.gcd left right)] (and (/.= 0 (/.% gcd left)) (/.= 0 (/.% gcd right))))) - (_.cover [/.co-prime?] + (_.cover [/.co_prime?] (bit\= (/.= 1 (/.gcd left right)) - (/.co-prime? left right))) + (/.co_prime? left right))) (_.cover [/.lcm] (let [lcm (/.lcm left right)] (and (/.= 0 (/.% left lcm)) diff --git a/stdlib/source/test/lux/time/year.lux b/stdlib/source/test/lux/time/year.lux index b1e2691db..d97eb8334 100644 --- a/stdlib/source/test/lux/time/year.lux +++ b/stdlib/source/test/lux/time/year.lux @@ -62,13 +62,13 @@ (#try.Failure _) (i.= +0 expected))) )) - (_.cover [/.there-is-no-year-0] + (_.cover [/.there_is_no_year_0] (case (/.year +0) (#try.Success _) false (#try.Failure error) - (exception.match? /.there-is-no-year-0 error))) + (exception.match? /.there_is_no_year_0 error))) (_.cover [/.days] (n.= (.nat (//duration.query //duration.day //duration.normal_year)) /.days)) 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 a1d16b40b..44807af9d 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 @@ -144,8 +144,8 @@ variant-name (r.unicode 5) record-name (|> (r.unicode 5) (r.filter (|>> (text\= variant-name) not))) size (|> r.nat (\ ! map (|>> (n.% 10) (n.max 2)))) - variant-tags (|> (r.set text.hash size (r.unicode 5)) (\ ! map set.to-list)) - record-tags (|> (r.set text.hash size (r.unicode 5)) (\ ! map set.to-list)) + variant-tags (|> (r.set text.hash size (r.unicode 5)) (\ ! map set.to_list)) + record-tags (|> (r.set text.hash size (r.unicode 5)) (\ ! map set.to_list)) primitivesTC (r.list size _primitive.primitive) #let [primitivesT (list\map product.left primitivesTC) primitivesC (list\map product.right primitivesTC) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/structure.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/structure.lux index 2f0f5d810..d263e3f0d 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/structure.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/structure.lux @@ -231,7 +231,7 @@ (def: variant (do {! r.monad} [size (|> r.nat (\ ! map (|>> (n.% 10) (n.max 2)))) - tags (|> (r.set text.hash size (r.unicode 5)) (\ ! map set.to-list)) + tags (|> (r.set text.hash size (r.unicode 5)) (\ ! map set.to_list)) choice (|> r.nat (\ ! map (n.% size))) other-choice (|> r.nat (\ ! map (n.% size)) (r.filter (|>> (n.= choice) not))) primitives (r.list size _primitive.primitive) @@ -277,7 +277,7 @@ (def: record (do {! r.monad} [size (|> r.nat (\ ! map (|>> (n.% 10) (n.max 2)))) - tags (|> (r.set text.hash size (r.unicode 5)) (\ ! map set.to-list)) + tags (|> (r.set text.hash size (r.unicode 5)) (\ ! map set.to_list)) primitives (r.list size _primitive.primitive) module-name (r.unicode 5) type-name (r.unicode 5) 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 7cce92462..0a7a9d9c5 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 @@ -184,7 +184,7 @@ (All [a] (-> (Hash a) (Random a) (Random [a a a a a]))) (|> random-element (random.set hash 5) - (\ random.monad map (|>> set.to-list + (\ random.monad map (|>> set.to_list (case> (^ (list s0 s1 s2 s3 s4)) [s0 s1 s2 s3 s4] diff --git a/stdlib/source/test/lux/world/output/video/resolution.lux b/stdlib/source/test/lux/world/output/video/resolution.lux index 671b1952c..a063a23bf 100644 --- a/stdlib/source/test/lux/world/output/video/resolution.lux +++ b/stdlib/source/test/lux/world/output/video/resolution.lux @@ -33,7 +33,7 @@ /.fhd /.wuxga /.wqhd - /.uhd-4k)] + /.uhd_4k)] (def: listing (List /.Resolution) (list )) -- cgit v1.2.3