aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/tool/compiler
diff options
context:
space:
mode:
authorEduardo Julian2021-07-31 02:36:42 -0400
committerEduardo Julian2021-07-31 02:36:42 -0400
commitfa320d22d0d7888feddcabe43a2bc9f1e0335032 (patch)
treed003de8e7e1d5fafadde4e02e37efd111c269411 /stdlib/source/library/lux/tool/compiler
parent9f039e8a0a09e0278547d697efa018cd3fd68672 (diff)
Yet more renamings.
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux84
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux22
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux36
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/phase.lux2
8 files changed, 81 insertions, 81 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
index 8588f52e0..f188f3c7d 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
@@ -473,7 +473,7 @@
(All [e] (-> (Exception e) e Operation))
(..failure (exception.construct exception parameters)))
-(def: #export (assert exception parameters condition)
+(def: #export (assertion exception parameters condition)
(All [e] (-> (Exception e) e Bit (Operation Any)))
(if condition
(\ phase.monad in [])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
index 291cf89c2..b99a93f73 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
@@ -314,8 +314,8 @@
outputTC (monad.map ! (|>> product.left /coverage.determine) outputT)
_ (.case (monad.fold try.monad /coverage.merge outputHC outputTC)
(#try.Success coverage)
- (///.assert non_exhaustive_pattern_matching [inputC branches coverage]
- (/coverage.exhaustive? coverage))
+ (///.assertion non_exhaustive_pattern_matching [inputC branches coverage]
+ (/coverage.exhaustive? coverage))
(#try.Failure error)
(/.failure error))]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux
index eccae999a..0af3736ac 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux
@@ -254,8 +254,8 @@
_
(/.except ..cannot_declare_tags_for_unnamed_type [tags type]))
_ (ensure_undeclared_tags self_name tags)
- _ (///.assert cannot_declare_tags_for_foreign_type [tags type]
- (text\= self_name type_module))]
+ _ (///.assertion cannot_declare_tags_for_foreign_type [tags type]
+ (text\= self_name type_module))]
(///extension.lift
(function (_ state)
(case (|> state (get@ #.modules) (plist.get self_name))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
index 3804bcec2..acaf79ae9 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
@@ -138,11 +138,11 @@
(-> java/lang/ClassLoader External (Operation Any))
(do phase.monad
[class (phase.lift (reflection!.load class_loader name))]
- (phase.assert ..deprecated_class [name]
- (|> class
- java/lang/Class::getDeclaredAnnotations
- reflection!.deprecated?
- not))))
+ (phase.assertion ..deprecated_class [name]
+ (|> class
+ java/lang/Class::getDeclaredAnnotations
+ reflection!.deprecated?
+ not))))
(def: reflection
(All [category]
@@ -930,17 +930,17 @@
## else
(do !
- [_ (phase.assert ..primitives_are_not_objects [from_name]
- (not (dictionary.key? ..boxes from_name)))
- _ (phase.assert ..primitives_are_not_objects [to_name]
- (not (dictionary.key? ..boxes to_name)))
+ [_ (phase.assertion ..primitives_are_not_objects [from_name]
+ (not (dictionary.key? ..boxes from_name)))
+ _ (phase.assertion ..primitives_are_not_objects [to_name]
+ (not (dictionary.key? ..boxes to_name)))
to_class (phase.lift (reflection!.load class_loader to_name))
_ (if (text\= ..inheritance_relationship_type_name from_name)
(in [])
(do !
[from_class (phase.lift (reflection!.load class_loader from_name))]
- (phase.assert ..cannot_cast [fromT toT fromC]
- (java/lang/Class::isAssignableFrom from_class to_class))))]
+ (phase.assertion ..cannot_cast [fromT toT fromC]
+ (java/lang/Class::isAssignableFrom from_class to_class))))]
(loop [[current_name currentT] [from_name fromT]]
(if (text\= to_name current_name)
(in true)
@@ -990,8 +990,8 @@
(do try.monad
[class (reflection!.load class_loader class)]
(reflection!.static_field field class)))
- _ (phase.assert ..deprecated_field [class field]
- (not deprecated?))
+ _ (phase.assertion ..deprecated_field [class field]
+ (not deprecated?))
fieldT (reflection_type luxT.fresh fieldJT)
_ (typeA.infer fieldT)]
(in (<| (#/////analysis.Extension extension_name)
@@ -1011,10 +1011,10 @@
(do try.monad
[class (reflection!.load class_loader class)]
(reflection!.static_field field class)))
- _ (phase.assert ..deprecated_field [class field]
- (not deprecated?))
- _ (phase.assert ..cannot_set_a_final_field [class field]
- (not final?))
+ _ (phase.assertion ..deprecated_field [class field]
+ (not deprecated?))
+ _ (phase.assertion ..cannot_set_a_final_field [class field]
+ (not final?))
fieldT (reflection_type luxT.fresh fieldJT)
valueA (typeA.with_type fieldT
(analyse archive valueC))]
@@ -1038,8 +1038,8 @@
[final? deprecated? fieldJT] (reflection!.virtual_field field class)
mapping (reflection!.correspond class objectT)]
(in [deprecated? mapping fieldJT])))
- _ (phase.assert ..deprecated_field [class field]
- (not deprecated?))
+ _ (phase.assertion ..deprecated_field [class field]
+ (not deprecated?))
fieldT (reflection_type mapping fieldJT)
_ (typeA.infer fieldT)]
(in (<| (#/////analysis.Extension extension_name)
@@ -1064,10 +1064,10 @@
[final? deprecated? fieldJT] (reflection!.virtual_field field class)
mapping (reflection!.correspond class objectT)]
(in [final? deprecated? mapping fieldJT])))
- _ (phase.assert ..deprecated_field [class field]
- (not deprecated?))
- _ (phase.assert ..cannot_set_a_final_field [class field]
- (not final?))
+ _ (phase.assertion ..deprecated_field [class field]
+ (not deprecated?))
+ _ (phase.assertion ..cannot_set_a_final_field [class field]
+ (not final?))
fieldT (reflection_type mapping fieldJT)
valueA (typeA.with_type fieldT
(analyse archive valueC))]
@@ -1376,8 +1376,8 @@
[_ (..ensure_fresh_class! class_loader class)
#let [argsT (list\map product.left argsTC)]
[methodT deprecated? exceptionsT] (..method_candidate class_loader class_tvars class method_tvars method #Static argsT)
- _ (phase.assert ..deprecated_method [class method methodT]
- (not deprecated?))
+ _ (phase.assertion ..deprecated_method [class method methodT]
+ (not deprecated?))
[outputT argsA] (inferenceA.general archive analyse methodT (list\map product.right argsTC))
outputJT (check_return outputT)]
(in (#/////analysis.Extension extension_name (list& (/////analysis.text (..signature (jvm.class class (list))))
@@ -1394,8 +1394,8 @@
[_ (..ensure_fresh_class! class_loader class)
#let [argsT (list\map product.left argsTC)]
[methodT deprecated? exceptionsT] (..method_candidate class_loader class_tvars class method_tvars method #Virtual argsT)
- _ (phase.assert ..deprecated_method [class method methodT]
- (not deprecated?))
+ _ (phase.assertion ..deprecated_method [class method methodT]
+ (not deprecated?))
[outputT allA] (inferenceA.general archive analyse methodT (list& objectC (list\map product.right argsTC)))
#let [[objectA argsA] (case allA
(#.Item objectA argsA)
@@ -1419,8 +1419,8 @@
[_ (..ensure_fresh_class! class_loader class)
#let [argsT (list\map product.left argsTC)]
[methodT deprecated? exceptionsT] (..method_candidate class_loader class_tvars class method_tvars method #Special argsT)
- _ (phase.assert ..deprecated_method [class method methodT]
- (not deprecated?))
+ _ (phase.assertion ..deprecated_method [class method methodT]
+ (not deprecated?))
[outputT argsA] (inferenceA.general archive analyse methodT (list& objectC (list\map product.right argsTC)))
outputJT (check_return outputT)]
(in (#/////analysis.Extension extension_name (list& (/////analysis.text (..signature (jvm.class class (list))))
@@ -1437,11 +1437,11 @@
[_ (..ensure_fresh_class! class_loader class_name)
#let [argsT (list\map product.left argsTC)]
class (phase.lift (reflection!.load class_loader class_name))
- _ (phase.assert non_interface class_name
- (java/lang/reflect/Modifier::isInterface (java/lang/Class::getModifiers class)))
+ _ (phase.assertion non_interface class_name
+ (java/lang/reflect/Modifier::isInterface (java/lang/Class::getModifiers class)))
[methodT deprecated? exceptionsT] (..method_candidate class_loader class_tvars class_name method_tvars method #Interface argsT)
- _ (phase.assert ..deprecated_method [class_name method methodT]
- (not deprecated?))
+ _ (phase.assertion ..deprecated_method [class_name method methodT]
+ (not deprecated?))
[outputT allA] (inferenceA.general archive analyse methodT (list& objectC (list\map product.right argsTC)))
#let [[objectA argsA] (case allA
(#.Item objectA argsA)
@@ -1466,8 +1466,8 @@
[_ (..ensure_fresh_class! class_loader class)
#let [argsT (list\map product.left argsTC)]
[methodT deprecated? exceptionsT] (..constructor_candidate class_loader class_tvars class method_tvars argsT)
- _ (phase.assert ..deprecated_method [class ..constructor_method methodT]
- (not deprecated?))
+ _ (phase.assertion ..deprecated_method [class ..constructor_method methodT]
+ (not deprecated?))
[outputT argsA] (inferenceA.general archive analyse methodT (list\map product.right argsTC))]
(in (#/////analysis.Extension extension_name (list& (/////analysis.text (..signature (jvm.class class (list))))
(decorate_inputs argsT argsA))))))]))
@@ -2064,9 +2064,9 @@
#let [expected_parameters (|> (java/lang/Class::getTypeParameters class)
array.to_list
(list\map (|>> java/lang/reflect/TypeVariable::getName)))]
- _ (phase.assert ..class_parameter_mismatch [expected_parameters actual_parameters]
- (n.= (list.size expected_parameters)
- (list.size actual_parameters)))]
+ _ (phase.assertion ..class_parameter_mismatch [expected_parameters actual_parameters]
+ (n.= (list.size expected_parameters)
+ (list.size actual_parameters)))]
(in (|> (list.zipped/2 expected_parameters actual_parameters)
(list\fold (function (_ [expected actual] mapping)
(case (jvm_parser.var? actual)
@@ -2102,10 +2102,10 @@
methods)
#let [missing_abstract_methods (mismatched_methods overriden_methods required_abstract_methods)
invalid_overriden_methods (mismatched_methods available_methods overriden_methods)]
- _ (phase.assert ..missing_abstract_methods missing_abstract_methods
- (list.empty? missing_abstract_methods))
- _ (phase.assert ..invalid_overriden_methods invalid_overriden_methods
- (list.empty? invalid_overriden_methods))]
+ _ (phase.assertion ..missing_abstract_methods missing_abstract_methods
+ (list.empty? missing_abstract_methods))
+ _ (phase.assertion ..invalid_overriden_methods invalid_overriden_methods
+ (list.empty? invalid_overriden_methods))]
(in [])))
(def: (class::anonymous class_loader)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
index 94fe61c3e..5ac8a93ec 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
@@ -383,23 +383,23 @@
(_.return (..i64 (_.bit_not (_.the ..i64_high_field value))
(_.bit_not (_.the ..i64_low_field value)))))
-(runtime: (i64//negate value)
+(runtime: (i64//opposite value)
(_.return (_.? (i64//= i64//min value)
i64//min
(i64//+ i64//one (i64//not value)))))
(runtime: i64//-one
- (i64//negate i64//one))
+ (i64//opposite i64//one))
(runtime: (i64//of_number value)
(_.return (<| (_.? (_.not_a_number? value)
i64//zero)
- (_.? (_.<= (_.negate i64//2^63) value)
+ (_.? (_.<= (_.opposite i64//2^63) value)
i64//min)
(_.? (|> value (_.+ (_.i32 +1)) (_.>= i64//2^63))
i64//max)
(_.? (|> value (_.< (_.i32 +0)))
- (|> value _.negate i64//of_number i64//negate))
+ (|> value _.opposite i64//of_number i64//opposite))
(..i64 (|> value (_./ i64//2^32) _.to_i32)
(|> value (_.% i64//2^32) _.to_i32)))))
@@ -471,7 +471,7 @@
))
(runtime: (i64//- parameter subject)
- (_.return (i64//+ (i64//negate parameter) subject)))
+ (_.return (i64//+ (i64//opposite parameter) subject)))
(runtime: (i64//* parameter subject)
(let [up_16 (_.left_shift (_.i32 +16))
@@ -577,13 +577,13 @@
[(negative? subject)
(_.return (_.? (negative? parameter)
- (i64/// (i64//negate parameter)
- (i64//negate subject))
- (i64//negate (i64/// parameter
- (i64//negate subject)))))]
+ (i64/// (i64//opposite parameter)
+ (i64//opposite subject))
+ (i64//opposite (i64/// parameter
+ (i64//opposite subject)))))]
[(negative? parameter)
- (_.return (i64//negate (i64/// (i64//negate parameter) subject)))])
+ (_.return (i64//opposite (i64/// (i64//opposite parameter) subject)))])
(with_vars [result remainder]
($_ _.then
(_.define result i64//zero)
@@ -645,7 +645,7 @@
@i64//one
@i64//=
@i64//+
- @i64//negate
+ @i64//opposite
@i64//to_number
@i64//of_number
@i64//-
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux
index dba43659e..0dcaf6ac8 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux
@@ -280,16 +280,16 @@
(_.and (comparison i64_low))
isTRUE?)))
-(runtime: (i64::negate input)
+(runtime: (i64::opposite input)
(_.if (|> input (i64::= i64::min))
i64::min
(|> input i64::not (i64::+ i64::one))))
(runtime: i64::-one
- (i64::negate i64::one))
+ (i64::opposite i64::one))
(runtime: (i64::- param subject)
- (i64::+ (i64::negate param) subject))
+ (i64::+ (i64::opposite param) subject))
(runtime: (i64::< reference sample)
(with_vars [r_? s_?]
@@ -306,12 +306,12 @@
(runtime: (i64::of_float input)
(_.cond (list [(_.apply (list input) (_.var "is.nan"))
i64::zero]
- [(|> input (_.<= (_.negate f2^63)))
+ [(|> input (_.<= (_.opposite f2^63)))
i64::min]
[(|> input (_.+ (_.float +1.0)) (_.>= f2^63))
i64::max]
[(|> input (_.< (_.float +0.0)))
- (|> input _.negate i64::of_float i64::negate)])
+ (|> input _.opposite i64::of_float i64::opposite)])
(i64::new (|> input (_./ f2^32))
(|> input (_.%% f2^32)))))
@@ -325,14 +325,14 @@
negative_param? (|> pH (_.< (_.int +0)))]
(_.cond (list [negative_subject?
(_.if negative_param?
- (i64::* (i64::negate param)
- (i64::negate subject))
- (i64::negate (i64::* param
- (i64::negate subject))))]
+ (i64::* (i64::opposite param)
+ (i64::opposite subject))
+ (i64::opposite (i64::* param
+ (i64::opposite subject))))]
[negative_param?
- (i64::negate (i64::* (i64::negate param)
- subject))])
+ (i64::opposite (i64::* (i64::opposite param)
+ subject))])
($_ _.then
(_.set! sL (|> subject i64_low))
(_.set! pL (|> param i64_low))
@@ -464,17 +464,17 @@
[(negative? subject)
(_.if (negative? param)
- (|> (i64::negate subject)
- (i64::/ (i64::negate param)))
- (|> (i64::negate subject)
+ (|> (i64::opposite subject)
+ (i64::/ (i64::opposite param)))
+ (|> (i64::opposite subject)
(i64::/ param)
- i64::negate))]
+ i64::opposite))]
[(negative? param)
(|> param
- i64::negate
+ i64::opposite
(i64::/ subject)
- i64::negate)])
+ i64::opposite)])
(with_vars [result remainder approximate approximate_result log2 approximate_remainder]
($_ _.then
(_.set! result i64::zero)
@@ -695,7 +695,7 @@
@i64::<
@i64::+
@i64::-
- @i64::negate
+ @i64::opposite
@i64::-one
@i64::unsigned_low
@i64::to_float
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux
index a87745390..a5a8826a0 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux
@@ -271,10 +271,10 @@
(-> Version Binary (Try Archive))
(do try.monad
[[actual next reservations] (<binary>.run ..reader binary)
- _ (exception.assert ..version_mismatch [expected actual]
- (n\= expected actual))
- _ (exception.assert ..corrupt_data []
- (correct_reservations? reservations))]
+ _ (exception.assertion ..version_mismatch [expected actual]
+ (n\= expected actual))
+ _ (exception.assertion ..corrupt_data []
+ (correct_reservations? reservations))]
(in (:abstraction
{#next next
#resolver (list\fold (function (_ [module id] archive)
diff --git a/stdlib/source/library/lux/tool/compiler/phase.lux b/stdlib/source/library/lux/tool/compiler/phase.lux
index 0554592a0..ed4def938 100644
--- a/stdlib/source/library/lux/tool/compiler/phase.lux
+++ b/stdlib/source/library/lux/tool/compiler/phase.lux
@@ -81,7 +81,7 @@
(function (_ state)
(try\map (|>> [state]) error)))
-(syntax: #export (assert exception message test)
+(syntax: #export (assertion exception message test)
(in (list (` (if (~ test)
(\ ..monad (~' in) [])
(..except (~ exception) (~ message)))))))