aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/meta
diff options
context:
space:
mode:
authorEduardo Julian2022-07-10 18:00:23 -0400
committerEduardo Julian2022-07-10 18:00:23 -0400
commit1bbc4251230cee13d46df7b706859e834778aee0 (patch)
tree6e9aa1b7e079ffd01041c510ac201f16a57842e9 /stdlib/source/library/lux/meta
parent7db42ab1b9d3c764772ca63c74bf44bb2b8b8325 (diff)
Removed the need for ,! unquoting.
Diffstat (limited to 'stdlib/source/library/lux/meta')
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/analysis.lux4
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/analysis.lux6
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/analysis/reference.lux26
-rw-r--r--stdlib/source/library/lux/meta/extension.lux12
-rw-r--r--stdlib/source/library/lux/meta/macro.lux8
-rw-r--r--stdlib/source/library/lux/meta/macro/context.lux30
-rw-r--r--stdlib/source/library/lux/meta/macro/syntax.lux22
-rw-r--r--stdlib/source/library/lux/meta/macro/vocabulary.lux26
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/modifier.lux22
-rw-r--r--stdlib/source/library/lux/meta/type.lux12
-rw-r--r--stdlib/source/library/lux/meta/type/dynamic.lux57
-rw-r--r--stdlib/source/library/lux/meta/type/poly.lux24
-rw-r--r--stdlib/source/library/lux/meta/type/primitive.lux4
-rw-r--r--stdlib/source/library/lux/meta/type/quotient.lux2
-rw-r--r--stdlib/source/library/lux/meta/type/refinement.lux2
-rw-r--r--stdlib/source/library/lux/meta/type/resource.lux6
-rw-r--r--stdlib/source/library/lux/meta/type/unit.lux15
-rw-r--r--stdlib/source/library/lux/meta/type/unit/scale.lux22
18 files changed, 155 insertions, 145 deletions
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/analysis.lux b/stdlib/source/library/lux/meta/compiler/language/lux/analysis.lux
index b975614df..4a1b68582 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/analysis.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/analysis.lux
@@ -183,8 +183,8 @@
[variable {reference.#Variable}]
[constant {reference.#Constant}]
- [local ((,! reference.local))]
- [foreign ((,! reference.foreign))]
+ [local reference.local]
+ [foreign reference.foreign]
)
(with_template [<name> <tag>]
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/analysis.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/analysis.lux
index e9ef84319..a65940d6b 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/analysis.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/analysis.lux
@@ -103,14 +103,16 @@
(^.with_template [<tag> <analyser>]
[[_ {<tag> value}]
(<analyser> value)])
- ([.#Symbol /reference.reference]
- [.#Text /simple.text]
+ ([.#Text /simple.text]
[.#Nat /simple.nat]
[.#Bit /simple.bit]
[.#Frac /simple.frac]
[.#Int /simple.int]
[.#Rev /simple.rev])
+ [[quoted_module @line @row] {.#Symbol value}]
+ (/reference.reference quoted_module value)
+
(^.` [(^.,* elems)])
(/complex.record analysis archive elems)
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/analysis/reference.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/analysis/reference.lux
index a232897bb..cbee3c622 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/analysis/reference.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/analysis/reference.lux
@@ -24,10 +24,12 @@
(exception .public (foreign_module_has_not_been_imported [current Text
foreign Text
+ quoted Text
definition Symbol])
(exception.report
(list ["Current" current]
["Foreign" foreign]
+ ["Quoted" quoted]
["Definition" (%.symbol definition)])))
(exception .public (definition_has_not_been_exported [definition Symbol])
@@ -38,14 +40,14 @@
(exception.report
(list ["Label" (%.symbol definition)])))
-(def (definition def_name)
- (-> Symbol (Operation Analysis))
+(def (definition quoted_module def_name)
+ (-> Text Symbol (Operation Analysis))
(with_expansions [<return> (in (|> def_name ///reference.constant {/.#Reference}))]
(do [! ///.monad]
[constant (///extension.lifted (meta.definition def_name))]
(case constant
{.#Alias real_def_name}
- (definition real_def_name)
+ (definition quoted_module real_def_name)
{.#Definition [exported? actualT _]}
(do !
@@ -57,9 +59,10 @@
(if exported?
(do !
[imported! (///extension.lifted (meta.imported_by? ::module current))]
- (if imported!
+ (if (or imported!
+ (text#= quoted_module ::module))
<return>
- (/.except ..foreign_module_has_not_been_imported [current ::module def_name])))
+ (/.except ..foreign_module_has_not_been_imported [current ::module quoted_module def_name])))
(/.except ..definition_has_not_been_exported def_name))))
{.#Type [exported? value labels]}
@@ -72,9 +75,10 @@
(if exported?
(do !
[imported! (///extension.lifted (meta.imported_by? ::module current))]
- (if imported!
+ (if (or imported!
+ (text#= quoted_module ::module))
<return>
- (/.except ..foreign_module_has_not_been_imported [current ::module def_name])))
+ (/.except ..foreign_module_has_not_been_imported [current ::module quoted_module def_name])))
(/.except ..definition_has_not_been_exported def_name))))
{.#Tag _}
@@ -96,8 +100,8 @@
{.#None}
(in {.#None}))))
-(def .public (reference it)
- (-> Symbol (Operation Analysis))
+(def .public (reference quoted_module it)
+ (-> Text Symbol (Operation Analysis))
(case it
["" simple_name]
(do [! ///.monad]
@@ -109,7 +113,7 @@
{.#None}
(do !
[this_module (///extension.lifted meta.current_module_name)]
- (definition [this_module simple_name]))))
+ (definition quoted_module [this_module simple_name]))))
_
- (definition it)))
+ (definition quoted_module it)))
diff --git a/stdlib/source/library/lux/meta/extension.lux b/stdlib/source/library/lux/meta/extension.lux
index 3ab53a44a..f4e7b41d7 100644
--- a/stdlib/source/library/lux/meta/extension.lux
+++ b/stdlib/source/library/lux/meta/extension.lux
@@ -50,17 +50,17 @@
(with_symbols [g!handler g!inputs g!error g!_]
(in (list (` (<extension> (, name)
(.function ((, g!handler) (, g!name) (, g!phase) (, g!archive) (, g!inputs))
- (.case ((,! <result>)
- ((,! monad.do) (,! <>.monad)
- [(,* inputs)
- (, g!_) <end>]
- (.at (,! <>.monad) (,' in) (, body)))
+ (.case (<result>
+ (monad.do <>.monad
+ [(,* inputs)
+ (, g!_) <end>]
+ (.at <>.monad (,' in) (, body)))
(, g!inputs))
{.#Right (, g!_)}
(, g!_)
{.#Left (, g!error)}
- ((,! phase.failure) (, g!error)))
+ (phase.failure (, g!error)))
)))))))))]
[<c>.any <c>.end <c>.and <c>.result "lux def analysis" analysis]
diff --git a/stdlib/source/library/lux/meta/macro.lux b/stdlib/source/library/lux/meta/macro.lux
index c8c3a26fb..0b7bb514a 100644
--- a/stdlib/source/library/lux/meta/macro.lux
+++ b/stdlib/source/library/lux/meta/macro.lux
@@ -28,7 +28,7 @@
(def (local ast)
(-> Code (Meta Text))
(case ast
- [_ {.#Symbol [_ name]}]
+ [_ {.#Symbol ["" name]}]
(at //.monad in name)
_
@@ -49,9 +49,9 @@
.let [symbol_defs (list#conjoint (list#each (is (-> Text (List Code))
(.function (_ name) (list (code.symbol ["" name]) (` (..symbol (, (code.text name)))))))
symbol_names))]]
- (in (list (` ((,! do) (,! //.monad)
- [(,* symbol_defs)]
- (, body))))))
+ (in (list (` (do //.monad
+ [(,* symbol_defs)]
+ (, body))))))
_
(//.failure (..wrong_syntax_error (.symbol ..with_symbols))))))
diff --git a/stdlib/source/library/lux/meta/macro/context.lux b/stdlib/source/library/lux/meta/macro/context.lux
index 99b62e8ab..73cda9cd0 100644
--- a/stdlib/source/library/lux/meta/macro/context.lux
+++ b/stdlib/source/library/lux/meta/macro/context.lux
@@ -46,7 +46,7 @@
(exception .public no_active_context)
-(.def (peek' _ context)
+(.def .public (peek' _ context)
(All (_ a) (-> (Stack a) Symbol (Meta a)))
(do meta.monad
[stack (..global context)]
@@ -61,11 +61,11 @@
(.def .public peek
(syntax (_ [g!it (at ?.monad each code.symbol ?code.global)])
- (in (list (` ((,! ..peek') (, g!it) (.symbol (, g!it))))))))
+ (in (list (` (..peek' (, g!it) (.symbol (, g!it))))))))
(exception .public no_example)
-(.def (search' _ ? context)
+(.def .public (search' _ ? context)
(All (_ a) (-> (Stack a) (Predicate a) Symbol (Meta a)))
(do meta.monad
[stack (..global context)]
@@ -81,7 +81,7 @@
(.def .public search
(syntax (_ [g!context (at ?.monad each code.symbol ?code.global)
g!? ?code.any])
- (in (list (` ((,! ..search') (, g!context) (, g!?) (.symbol (, g!context))))))))
+ (in (list (` (..search' (, g!context) (, g!?) (.symbol (, g!context))))))))
(.def (alter on_definition [@ context])
(-> (-> Definition Definition) Symbol (Meta Any))
@@ -101,7 +101,7 @@
{.#Right [(revised .#modules (property.revised @ on_module) lux)
[]]})))
-(.def (push' _ top)
+(.def .public (push' _ top)
(All (_ a) (-> (Stack a) a Symbol (Meta Any)))
(alter (function (_ [exported? type stack])
(|> stack
@@ -113,7 +113,7 @@
(.def .public push
(syntax (_ [g!context (at ?.monad each code.symbol ?code.global)
g!it ?code.any])
- (in (list (` ((,! ..push') (, g!context) (, g!it) (.symbol (, g!context))))))))
+ (in (list (` (..push' (, g!context) (, g!it) (.symbol (, g!context))))))))
(.def pop'
(-> Symbol (Meta Any))
@@ -144,15 +144,15 @@
(list)))
(` (.def ((, g!expression) (, g!it) (, g!body))
(-> (, context_type) Code (Meta Code))
- ((,! do) (,! meta.monad)
- [(, g!_) ((,! ..push) (, g!context) (, g!it))]
- ((,' in) (` (let [((,' ,') (, g!body)) ((,' ,) (, g!body))
- ((,' ,') (, g!_)) ((,! ..pop) #1 (, g!context))]
- ((,' ,') (, g!body))))))))
+ (do meta.monad
+ [(, g!_) (..push (, g!context) (, g!it))]
+ ((,' in) (` (let [((,' ,') (, g!body)) ((,' ,) (, g!body))
+ ((,' ,') (, g!_)) (..pop #1 (, g!context))]
+ ((,' ,') (, g!body))))))))
(` (.def ((, g!declaration) (, g!it) (, g!body))
(-> (, context_type) Code (Meta (List Code)))
- ((,! do) (,! meta.monad)
- [(, g!_) ((,! ..push) (, g!context) (, g!it))]
- ((,' in) (list (, g!body)
- (` ((,! ..pop) #0 (, g!context))))))))
+ (do meta.monad
+ [(, g!_) (..push (, g!context) (, g!it))]
+ ((,' in) (list (, g!body)
+ (` (..pop #0 (, g!context))))))))
))))))
diff --git a/stdlib/source/library/lux/meta/macro/syntax.lux b/stdlib/source/library/lux/meta/macro/syntax.lux
index 5321db403..aa415eeb8 100644
--- a/stdlib/source/library/lux/meta/macro/syntax.lux
+++ b/stdlib/source/library/lux/meta/macro/syntax.lux
@@ -15,7 +15,7 @@
["</>" \\parser (.only Parser)]]]]]
["[0]" // (.only with_symbols)])
-(def (self_documenting binding parser)
+(def .public (self_documenting binding parser)
(All (_ a) (-> Code (Parser a) (Parser a)))
(function (_ tokens)
(case (parser tokens)
@@ -57,8 +57,8 @@
(is (-> [Code Code] (Meta [Code Code]))
(function (_ [var parser])
(with_expansions [<default> (in [var
- (` ((,! ..self_documenting) (' (, var))
- (, parser)))])]
+ (` (..self_documenting (' (, var))
+ (, parser)))])]
(case var
[_ {.#Symbol ["" _]}]
<default>
@@ -81,19 +81,19 @@
this_module meta.current_module_name
.let [g!name (code.symbol ["" name])]]
(in (list (` (.macro ((, g!name) (, g!tokens) (, g!state))
- (.case ((,! </>.result)
- (is ((,! </>.Parser) (Meta (List Code)))
- ((,! do) (,! <>.monad)
- [(,* (..un_paired vars+parsers))]
- (.at (,! <>.monad) (,' in)
- (is (Meta (List Code))
- (, body)))))
+ (.case (</>.result
+ (is (</>.Parser (Meta (List Code)))
+ (do <>.monad
+ [(,* (..un_paired vars+parsers))]
+ (.at <>.monad (,' in)
+ (is (Meta (List Code))
+ (, body)))))
(, g!tokens))
{try.#Success (, g!body)}
((, g!body) (, g!state))
{try.#Failure (, g!error)}
- {try.#Failure ((,! text.interposed) (,! text.new_line) (list "Invalid syntax:" (, g!error)))})))))))
+ {try.#Failure (text.interposed text.new_line (list "Invalid syntax:" (, g!error)))})))))))
{try.#Failure error}
(meta.failure (//.wrong_syntax_error (symbol ..syntax))))))
diff --git a/stdlib/source/library/lux/meta/macro/vocabulary.lux b/stdlib/source/library/lux/meta/macro/vocabulary.lux
index 73b91c35a..3f54c9db4 100644
--- a/stdlib/source/library/lux/meta/macro/vocabulary.lux
+++ b/stdlib/source/library/lux/meta/macro/vocabulary.lux
@@ -33,21 +33,21 @@
[public|private@macro macro] ..local
[public|private@by_name by_name] ..local])
(//.with_symbols [g!_ g!type g!value]
- (in (list (` ((,! primitive) (, public|private@type) (, type)
- Macro
+ (in (list (` (primitive (, public|private@type) (, type)
+ Macro
- (def (, public|private@micro) (, micro)
- (-> Macro (, type))
- (|>> ((,! abstraction))))
+ (def (, public|private@micro) (, micro)
+ (-> Macro (, type))
+ (|>> abstraction))
- (def (, public|private@macro) (, macro)
- (-> (, type) Macro)
- (|>> ((,! representation))))))
+ (def (, public|private@macro) (, macro)
+ (-> (, type) Macro)
+ (|>> representation))))
(` (def (, public|private@by_name) ((, by_name) (, g!_))
(-> Symbol (Meta Macro))
- ((,! do) (,! ///.monad)
- [[(, g!_) (, g!type) (, g!value)] ((,! ///.export) (, g!_))]
- (if (at (,! type.equivalence) (,' =) (, type) (, g!type))
- ((,' in) ((, macro) (as (, type) (, g!value))))
- ((,! ///.failure) ((,! exception.error) ..invalid_type [(, type) (, g!type)])))))))))))
+ (do ///.monad
+ [[(, g!_) (, g!type) (, g!value)] (///.export (, g!_))]
+ (if (at type.equivalence (,' =) (, type) (, g!type))
+ ((,' in) ((, macro) (as (, type) (, g!value))))
+ (///.failure (exception.error ..invalid_type [(, type) (, g!type)])))))))))))
diff --git a/stdlib/source/library/lux/meta/target/jvm/modifier.lux b/stdlib/source/library/lux/meta/target/jvm/modifier.lux
index 35b9894be..87cbff564 100644
--- a/stdlib/source/library/lux/meta/target/jvm/modifier.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/modifier.lux
@@ -39,14 +39,14 @@
(representation reference)
(representation sample)))))
- (def !wrap
+ (def !abstraction
(template (_ value)
[(|> value
//unsigned.u2
try.trusted
abstraction)]))
- (def !unwrap
+ (def !representation
(template (_ value)
[(|> value
representation
@@ -54,8 +54,8 @@
(def .public (has? sub super)
(All (_ of) (-> (Modifier of) (Modifier of) Bit))
- (let [sub (!unwrap sub)]
- (|> (!unwrap super)
+ (let [sub (!representation sub)]
+ (|> (!representation super)
(i64.and sub)
(at i64.equivalence = sub))))
@@ -63,10 +63,11 @@
(All (_ of) (Monoid (Modifier of)))
(implementation
(def identity
- (!wrap (hex "0000")))
+ (!abstraction (hex "0000")))
(def (composite left right)
- (!wrap (i64.or (!unwrap left) (!unwrap right))))))
+ (!abstraction (i64.or (!representation left)
+ (!representation right))))))
(def .public empty
Modifier
@@ -75,10 +76,6 @@
(def .public format
(All (_ of) (Format (Modifier of)))
(|>> representation //unsigned.format/2))
-
- (def modifier
- (-> Nat Modifier)
- (|>> !wrap))
)
(def .public modifiers
@@ -88,6 +85,9 @@
(in (list (` (with_template [(, g!code) (, g!modifier)]
[(def (,' .public) (, g!modifier)
(..Modifier (, ofT))
- ((,! ..modifier) ((,! number.hex) (, g!code))))]
+ (|> (number.hex (, g!code))
+ //unsigned.u2
+ try.trusted
+ as_expected))]
(,* options))))))))
diff --git a/stdlib/source/library/lux/meta/type.lux b/stdlib/source/library/lux/meta/type.lux
index 42f9f2961..b751e9270 100644
--- a/stdlib/source/library/lux/meta/type.lux
+++ b/stdlib/source/library/lux/meta/type.lux
@@ -499,12 +499,12 @@
(syntax (_ lux [type_vars ..type_parameters
exemplar (..typed lux)
extraction <code>.any])
- (in (list (` (.type_of ((,! ..sharing) [(,* (list#each code.local type_vars))]
- (is (, (the #type exemplar))
- (, (the #expression exemplar)))
- (is (, extraction)
- ... The value of this expression will never be relevant, so it doesn't matter what it is.
- (.as .Nothing [])))))))))
+ (in (list (` (.type_of (..sharing [(,* (list#each code.local type_vars))]
+ (is (, (the #type exemplar))
+ (, (the #expression exemplar)))
+ (is (, extraction)
+ ... The value of this expression will never be relevant, so it doesn't matter what it is.
+ (.as .Nothing [])))))))))
(`` (def .public (replaced before after)
(-> Type Type Type Type)
diff --git a/stdlib/source/library/lux/meta/type/dynamic.lux b/stdlib/source/library/lux/meta/type/dynamic.lux
index 303fbdf63..a10d24530 100644
--- a/stdlib/source/library/lux/meta/type/dynamic.lux
+++ b/stdlib/source/library/lux/meta/type/dynamic.lux
@@ -22,36 +22,31 @@
(list ["Expected" (%.type expected)]
["Actual" (%.type actual)])))
-(primitive .public Dynamic
- [Type Any]
+(with_expansions [<representation> [Type Any]]
+ (primitive .public Dynamic
+ <representation>
+
+ (def .public dynamic
+ (syntax (_ [value <code>.any])
+ (with_symbols [g!value]
+ (in (list (` (.let [(, g!value) (, value)]
+ (as Dynamic [(.type_of (, g!value)) (, g!value)]))))))))
- (def abstraction
- (-> [Type Any] Dynamic)
- (|>> primitive.abstraction))
-
- (def representation
- (-> Dynamic [Type Any])
- (|>> primitive.representation))
+ (def .public static
+ (syntax (_ [type <code>.any
+ value <code>.any])
+ (with_symbols [g!type g!value]
+ (in (list (` (.let [[(, g!type) (, g!value)] (|> (, value)
+ (is Dynamic)
+ (as <representation>))]
+ (.is (try.Try (, type))
+ (.if (.at //.equivalence (,' =)
+ (.type_literal (, type)) (, g!type))
+ {try.#Success (.as (, type) (, g!value))}
+ (exception.except ..wrong_type [(.type_literal (, type)) (, g!type)]))))))))))
- (def .public dynamic
- (syntax (_ [value <code>.any])
- (with_symbols [g!value]
- (in (list (` (.let [(, g!value) (, value)]
- ((,! ..abstraction) [(.type_of (, g!value)) (, g!value)]))))))))
-
- (def .public static
- (syntax (_ [type <code>.any
- value <code>.any])
- (with_symbols [g!type g!value]
- (in (list (` (.let [[(, g!type) (, g!value)] ((,! ..representation) (, value))]
- (.is ((,! try.Try) (, type))
- (.if (.at (,! //.equivalence) (,' =)
- (.type_literal (, type)) (, g!type))
- {try.#Success (.as (, type) (, g!value))}
- ((,! exception.except) ..wrong_type [(.type_literal (, type)) (, g!type)]))))))))))
-
- (def .public (format value)
- (-> Dynamic (Try Text))
- (let [[type value] (primitive.representation value)]
- (debug.representation type value)))
- )
+ (def .public (format value)
+ (-> Dynamic (Try Text))
+ (let [[type value] (primitive.representation value)]
+ (debug.representation type value)))
+ ))
diff --git a/stdlib/source/library/lux/meta/type/poly.lux b/stdlib/source/library/lux/meta/type/poly.lux
index abf1d8c5b..a9a533d94 100644
--- a/stdlib/source/library/lux/meta/type/poly.lux
+++ b/stdlib/source/library/lux/meta/type/poly.lux
@@ -30,19 +30,19 @@
body <code>.any])
(with_symbols [g!_ g!type g!output]
(let [g!name (code.symbol ["" name])]
- (in (.list (` ((,! syntax) ((, g!_) [(, g!type) (,! <code>.any)])
- ((,! do) (,! ///.monad)
- [(, g!type) ((,! ///.eval) .Type (, g!type))]
- (case (is (.Either .Text .Code)
- ((,! <//>.result) ((,! <>.rec)
- (function ((, g!_) (, g!name))
- (, body)))
- (.as .Type (, g!type))))
- {.#Right (, g!output)}
- ((,' in) (.list (, g!output)))
+ (in (.list (` (syntax ((, g!_) [(, g!type) <code>.any])
+ (do ///.monad
+ [(, g!type) (///.eval .Type (, g!type))]
+ (case (is (.Either .Text .Code)
+ (<//>.result (<>.rec
+ (function ((, g!_) (, g!name))
+ (, body)))
+ (.as .Type (, g!type))))
+ {.#Right (, g!output)}
+ ((,' in) (.list (, g!output)))
- {.#Left (, g!output)}
- ((,! ///.failure) (, g!output))))))))))))
+ {.#Left (, g!output)}
+ (///.failure (, g!output))))))))))))
(def .public (code env type)
(-> Env Type Code)
diff --git a/stdlib/source/library/lux/meta/type/primitive.lux b/stdlib/source/library/lux/meta/type/primitive.lux
index 40bcdba68..ea277d239 100644
--- a/stdlib/source/library/lux/meta/type/primitive.lux
+++ b/stdlib/source/library/lux/meta/type/primitive.lux
@@ -52,8 +52,8 @@
{.#None}
..current)]
- (in (list (` ((,! //.as) [(,* type_vars)] (, <from>) (, <to>)
- (, value))))))))]
+ (in (list (` (//.as [(,* type_vars)] (, <from>) (, <to>)
+ (, value))))))))]
[abstraction representation abstraction]
[representation abstraction representation]
diff --git a/stdlib/source/library/lux/meta/type/quotient.lux b/stdlib/source/library/lux/meta/type/quotient.lux
index a872c9992..0687af5ce 100644
--- a/stdlib/source/library/lux/meta/type/quotient.lux
+++ b/stdlib/source/library/lux/meta/type/quotient.lux
@@ -57,7 +57,7 @@
(, g!_)
(.undefined))))
- ... (` ((,! //.by_example) [(, g!t) (, g!c) (, g!%)]
+ ... (` (//.by_example [(, g!t) (, g!c) (, g!%)]
... (is (..Class (, g!t) (, g!c) (, g!%))
... (, class))
... (..Quotient (, g!t) (, g!c) (, g!%))))
diff --git a/stdlib/source/library/lux/meta/type/refinement.lux b/stdlib/source/library/lux/meta/type/refinement.lux
index b08bdd5e9..5b7e939a5 100644
--- a/stdlib/source/library/lux/meta/type/refinement.lux
+++ b/stdlib/source/library/lux/meta/type/refinement.lux
@@ -99,7 +99,7 @@
(, g!_)
(.undefined))))
- ... (` ((,! //.by_example) [(, g!t) (, g!%)]
+ ... (` (//.by_example [(, g!t) (, g!%)]
... (is (..Refiner (, g!t) (, g!%))
... (, refiner))
... (..Refined (, g!t) (, g!%))))
diff --git a/stdlib/source/library/lux/meta/type/resource.lux b/stdlib/source/library/lux/meta/type/resource.lux
index fa159c93f..3e652b8b9 100644
--- a/stdlib/source/library/lux/meta/type/resource.lux
+++ b/stdlib/source/library/lux/meta/type/resource.lux
@@ -132,7 +132,7 @@
(macro.with_symbols [g!_ g!context g!!]
(case swaps
{.#End}
- (in (list (` (,! no_op))))
+ (in (list (` ..no_op)))
{.#Item head tail}
(do [! meta.monad]
@@ -150,7 +150,7 @@
g!inputsT+ (list#each (|>> (,) (..Key ..Commutative) (`)) g!inputs)
g!outputsT+ (list#each (|>> (,) (..Key ..Commutative) (`)) g!outputs)]]
(in (list (` (is (All ((, g!_) (, g!!) (,* g!inputs) (, g!context))
- (-> ((,! monad.Monad) (, g!!))
+ (-> (monad.Monad (, g!!))
(Procedure (, g!!)
[(,* g!inputsT+) (, g!context)]
[(,* g!outputsT+) (, g!context)]
@@ -175,7 +175,7 @@
(list.repeated amount)
(monad.all !))]
(in (list (` (is (All ((, g!_) (, g!!) (,* g!keys) (, g!context))
- (-> ((,! monad.Monad) (, g!!))
+ (-> (monad.Monad (, g!!))
(Procedure (, g!!)
[<from> (, g!context)]
[<to> (, g!context)]
diff --git a/stdlib/source/library/lux/meta/type/unit.lux b/stdlib/source/library/lux/meta/type/unit.lux
index cb8b9c142..e95b261f0 100644
--- a/stdlib/source/library/lux/meta/type/unit.lux
+++ b/stdlib/source/library/lux/meta/type/unit.lux
@@ -85,17 +85,20 @@
(def .public type
(syntax (_ [it <code>.any])
(macro.with_symbols [g!a]
- (in (list (` ((,! //.by_example) [(, g!a)]
- (is (..Unit (, g!a))
- (, it))
- (, g!a))))))))
+ (in (list (` (//.by_example [(, g!a)]
+ (is (..Unit (, g!a))
+ (, it))
+ (, g!a))))))))
(with_template [<unit> <type>]
[(def .public <unit>
(..unit []))
- (.type .public <type>
- (, (..type <unit>)))]
+ (.def .public <type>
+ (let [[module _] (symbol .._)
+ [_ short] (symbol <type>)]
+ {.#Named [module short]
+ (..type <unit>)}))]
[gram Gram]
[meter Meter]
diff --git a/stdlib/source/library/lux/meta/type/unit/scale.lux b/stdlib/source/library/lux/meta/type/unit/scale.lux
index 9d750eea9..9f4f7e1f9 100644
--- a/stdlib/source/library/lux/meta/type/unit/scale.lux
+++ b/stdlib/source/library/lux/meta/type/unit/scale.lux
@@ -52,25 +52,31 @@
(def .public type
(syntax (_ [it <code>.any])
(macro.with_symbols [g!a]
- (in (list (` ((,! ///.by_example) [(, g!a)]
- (is (..Scale (, g!a))
- (, it))
- (, g!a))))))))
+ (in (list (` (///.by_example [(, g!a)]
+ (is (..Scale (, g!a))
+ (, it))
+ (, g!a))))))))
(with_template [<order_of_magnitude> <up> <up_type> <down> <down_type>]
[(def .public <up>
(scale [ratio.#numerator <order_of_magnitude>
ratio.#denominator 1]))
- (.type .public <up_type>
- (, (..type <up>)))
+ (def .public <up_type>
+ (let [[module _] (symbol .._)
+ [_ short] (symbol <up_type>)]
+ {.#Named [module short]
+ (..type <up>)}))
(def .public <down>
(scale [ratio.#numerator 1
ratio.#denominator <order_of_magnitude>]))
- (.type .public <down_type>
- (, (..type <down>)))]
+ (def .public <down_type>
+ (let [[module _] (symbol .._)
+ [_ short] (symbol <down_type>)]
+ {.#Named [module short]
+ (..type <down>)}))]
[ 1,000 kilo Kilo milli Milli]
[ 1,000,000 mega Mega micro Micro]