aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/tool
diff options
context:
space:
mode:
authorEduardo Julian2021-07-11 01:51:04 -0400
committerEduardo Julian2021-07-11 01:51:04 -0400
commitabe24425ced15fd784ef6c62d6f186af72b491db (patch)
tree42b6e3cbd179c83fae8941fa4b128b13afc766f5 /stdlib/source/lux/tool
parent4610968193df10af12c91f699fec39aeb3ef703a (diff)
Re-named ":coerce" to ":as" since it technically doesn't do coercions.
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/tool/compiler/default/platform.lux8
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case.lux27
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux2
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux16
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux14
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux2
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/syntax.lux4
-rw-r--r--stdlib/source/lux/tool/compiler/meta/io/archive.lux8
8 files changed, 42 insertions, 39 deletions
diff --git a/stdlib/source/lux/tool/compiler/default/platform.lux b/stdlib/source/lux/tool/compiler/default/platform.lux
index 1e7f643ac..605f1d1e2 100644
--- a/stdlib/source/lux/tool/compiler/default/platform.lux
+++ b/stdlib/source/lux/tool/compiler/default/platform.lux
@@ -80,8 +80,8 @@
## TODO: Get rid of this
(def: monad
- (:coerce (Monad Action)
- (try.with promise.monad)))
+ (:as (Monad Action)
+ (try.with promise.monad)))
(with_expansions [<Platform> (as_is (Platform <type_vars>))
<State+> (as_is (///directive.State+ <type_vars>))
@@ -498,7 +498,7 @@
#extension.state]
(function (_ analysis_state)
(|> analysis_state
- (:coerce .Lux)
+ (:as .Lux)
(update@ #.modules (function (_ current)
(list\compose (list.filter (|>> product.left
(set.member? additions)
@@ -539,7 +539,7 @@
(get@ #static.host_module_extension static)
module)]
(loop [[archive state] [archive state]
- compilation (base_compiler (:coerce ///.Input input))
+ compilation (base_compiler (:as ///.Input input))
all_dependencies (: (List Module)
(list))]
(let [new_dependencies (get@ #///.dependencies compilation)
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case.lux
index f48155088..41fad7934 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/analysis/case.lux
@@ -5,7 +5,7 @@
["." monad (#+ do)]]
[control
["." try]
- ["ex" exception (#+ exception:)]]
+ ["." exception (#+ exception:)]]
[data
["." product]
["." maybe]
@@ -34,23 +34,26 @@
["#" phase]]]]]])
(exception: #export (cannot_match_with_pattern {type Type} {pattern Code})
- (ex.report ["Type" (%.type type)]
- ["Pattern" (%.code pattern)]))
+ (exception.report
+ ["Type" (%.type type)]
+ ["Pattern" (%.code pattern)]))
(exception: #export (sum_has_no_case {case Nat} {type Type})
- (ex.report ["Case" (%.nat case)]
- ["Type" (%.type type)]))
+ (exception.report
+ ["Case" (%.nat case)]
+ ["Type" (%.type type)]))
(exception: #export (not_a_pattern {code Code})
- (ex.report ["Code" (%.code code)]))
+ (exception.report ["Code" (%.code code)]))
(exception: #export (cannot_simplify_for_pattern_matching {type Type})
- (ex.report ["Type" (%.type type)]))
+ (exception.report ["Type" (%.type type)]))
(exception: #export (non_exhaustive_pattern_matching {input Code} {branches (List [Code Code])} {coverage Coverage})
- (ex.report ["Input" (%.code input)]
- ["Branches" (%.code (code.record branches))]
- ["Coverage" (/coverage.%coverage coverage)]))
+ (exception.report
+ ["Input" (%.code input)]
+ ["Branches" (%.code (code.record branches))]
+ ["Coverage" (/coverage.%coverage coverage)]))
(exception: #export (cannot_have_empty_branches {message Text})
message)
@@ -209,8 +212,8 @@
(Operation [(List Pattern) a])))
(function (_ [memberT memberC] then)
(do !
- [[memberP [memberP+ thenA]] ((:coerce (All [a] (-> (Maybe Nat) Type Code (Operation a) (Operation [Pattern a])))
- analyse_pattern)
+ [[memberP [memberP+ thenA]] ((:as (All [a] (-> (Maybe Nat) Type Code (Operation a) (Operation [Pattern a])))
+ analyse_pattern)
#.None memberT memberC then)]
(wrap [(list& memberP memberP+) thenA]))))
(do !
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
index 0c88ae795..66ef65e71 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
@@ -873,7 +873,7 @@
#.None
(if (java/lang/reflect/Modifier::isInterface (java/lang/Class::getModifiers from_class))
- (#.Cons (:coerce java/lang/reflect/Type (ffi.class_for java/lang/Object))
+ (#.Cons (:as java/lang/reflect/Type (ffi.class_for java/lang/Object))
(array.to_list (java/lang/Class::getGenericInterfaces from_class)))
(array.to_list (java/lang/Class::getGenericInterfaces from_class)))))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux
index 8c5cbcd09..a86295b2a 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux
@@ -157,14 +157,14 @@
_
(////analysis.throw ///.invalid_syntax [extension_name %.code argsC+]))))
-(def: (lux::check eval)
+(def: (lux::type::check eval)
(-> Eval Handler)
(function (_ extension_name analyse archive args)
(case args
(^ (list typeC valueC))
(do {! ////.monad}
[count (///.lift meta.count)
- actualT (\ ! map (|>> (:coerce Type))
+ actualT (\ ! map (|>> (:as Type))
(eval archive count Type typeC))
_ (typeA.infer actualT)]
(typeA.with_type actualT
@@ -173,14 +173,14 @@
_
(////analysis.throw ///.incorrect_arity [extension_name 2 (list.size args)]))))
-(def: (lux::coerce eval)
+(def: (lux::type::as eval)
(-> Eval Handler)
(function (_ extension_name analyse archive args)
(case args
(^ (list typeC valueC))
(do {! ////.monad}
[count (///.lift meta.count)
- actualT (\ ! map (|>> (:coerce Type))
+ actualT (\ ! map (|>> (:as Type))
(eval archive count Type typeC))
_ (typeA.infer actualT)
[valueT valueA] (typeA.with_inference
@@ -212,7 +212,7 @@
[input_type (///.lift (meta.find_def (name_of .Macro')))]
(case input_type
(#.Definition [exported? def_type def_data def_value])
- (wrap (:coerce Type def_value))
+ (wrap (:as Type def_value))
(#.Alias real_name)
(recur real_name))))]
@@ -225,10 +225,10 @@
(///bundle.install "syntax char case!" lux::syntax_char_case!)
(///bundle.install "is" lux::is)
(///bundle.install "try" lux::try)
- (///bundle.install "check" (lux::check eval))
- (///bundle.install "coerce" (lux::coerce eval))
+ (///bundle.install "type check" (lux::type::check eval))
+ (///bundle.install "type as" (lux::type::as eval))
(///bundle.install "macro" ..lux::macro)
- (///bundle.install "check type" (..caster .Type .Type))
+ (///bundle.install "type check type" (..caster .Type .Type))
(///bundle.install "in-module" lux::in_module)))
(def: bundle::io
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux
index 4e33cbebc..9e405eb78 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux
@@ -227,7 +227,7 @@
[type valueT value] (..definition archive full_name #.None valueC)
[_ annotationsT annotations] (evaluate! archive Code annotationsC)
_ (/////directive.lift_analysis
- (module.define short_name (#.Right [exported? type (:coerce Code annotations) value])))
+ (module.define short_name (#.Right [exported? type (:as Code annotations) value])))
_ (..refresh expander host_analysis)
_ (..announce_definition! short_name type)]
(wrap /////directive.no_requirements))
@@ -245,12 +245,12 @@
(///.lift meta.current_module_name))
#let [full_name [current_module short_name]]
[_ annotationsT annotations] (evaluate! archive Code annotationsC)
- #let [annotations (:coerce Code annotations)]
+ #let [annotations (:as Code annotations)]
[type valueT value] (..definition archive full_name (#.Some .Type) valueC)
_ (/////directive.lift_analysis
(do phase.monad
[_ (module.define short_name (#.Right [exported? type annotations value]))]
- (module.declare_tags tags exported? (:coerce Type value))))
+ (module.declare_tags tags exported? (:as Type value))))
_ (..refresh expander host_analysis)
_ (..announce_definition! short_name type)]
(wrap /////directive.no_requirements)))]))
@@ -268,7 +268,7 @@
(function (_ extension_name phase archive [annotationsC imports])
(do {! phase.monad}
[[_ annotationsT annotationsV] (evaluate! archive Code annotationsC)
- #let [annotationsV (:coerce Code annotationsV)]
+ #let [annotationsV (:as Code annotationsV)]
_ (/////directive.lift_analysis
(do !
[_ (monad.map ! (function (_ [module alias])
@@ -322,11 +322,11 @@
(^ (list nameC valueC))
(do phase.monad
[[_ _ name] (evaluate! archive Text nameC)
- [_ handlerV] (<definer> archive (:coerce Text name)
+ [_ handlerV] (<definer> archive (:as Text name)
(type <def_type>)
valueC)
_ (<| <scope>
- (///.install extender (:coerce Text name))
+ (///.install extender (:as Text name))
(:share [anchor expression directive]
(Handler anchor expression directive)
handler
@@ -334,7 +334,7 @@
<type>
(:assume handlerV)))
_ (/////directive.lift_generation
- (/////generation.log! (format <description> " " (%.text (:coerce Text name)))))]
+ (/////generation.log! (format <description> " " (%.text (:as Text name)))))]
(wrap /////directive.no_requirements))
_
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux
index b6fb709fb..b23d41726 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux
@@ -109,7 +109,7 @@
_
(let [constantI (if (i.= ..d0-bits
- (java/lang/Double::doubleToRawLongBits (:coerce java/lang/Double value)))
+ (java/lang/Double::doubleToRawLongBits (:as java/lang/Double value)))
_.dconst-0
(_.double value))]
(do _.monad
diff --git a/stdlib/source/lux/tool/compiler/language/lux/syntax.lux b/stdlib/source/lux/tool/compiler/language/lux/syntax.lux
index 488738c00..00d1497a1 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/syntax.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/syntax.lux
@@ -177,8 +177,8 @@
(-> Source (Either [Source Text] [Source a])))
(template: (!with_char+ @source_code_size @source_code @offset @char @else @body)
- (if (!i/< (:coerce Int @source_code_size)
- (:coerce Int @offset))
+ (if (!i/< (:as Int @source_code_size)
+ (:as Int @offset))
(let [@char ("lux text char" @offset @source_code)]
@body)
@else))
diff --git a/stdlib/source/lux/tool/compiler/meta/io/archive.lux b/stdlib/source/lux/tool/compiler/meta/io/archive.lux
index b6bf39c18..1ff603267 100644
--- a/stdlib/source/lux/tool/compiler/meta/io/archive.lux
+++ b/stdlib/source/lux/tool/compiler/meta/io/archive.lux
@@ -255,7 +255,7 @@
(do !
[value (\ host re_load context directive)]
(wrap [definitions
- [(dictionary.put extension (:coerce analysis.Handler value) analysers)
+ [(dictionary.put extension (:as analysis.Handler value) analysers)
synthesizers
generators
directives]]))
@@ -265,7 +265,7 @@
[value (\ host re_load context directive)]
(wrap [definitions
[analysers
- (dictionary.put extension (:coerce synthesis.Handler value) synthesizers)
+ (dictionary.put extension (:as synthesis.Handler value) synthesizers)
generators
directives]]))
@@ -275,7 +275,7 @@
(wrap [definitions
[analysers
synthesizers
- (dictionary.put extension (:coerce generation.Handler value) generators)
+ (dictionary.put extension (:as generation.Handler value) generators)
directives]]))
(#artifact.Directive extension)
@@ -285,7 +285,7 @@
[analysers
synthesizers
generators
- (dictionary.put extension (:coerce directive.Handler value) directives)]]))))
+ (dictionary.put extension (:as directive.Handler value) directives)]]))))
(#try.Success [definitions' bundles'])
(recur input' definitions' bundles')