From 1bbc4251230cee13d46df7b706859e834778aee0 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Sun, 10 Jul 2022 18:00:23 -0400 Subject: Removed the need for ,! unquoting. --- stdlib/source/library/lux.lux | 136 +++++++-------- .../library/lux/control/concurrency/thread.lux | 7 +- stdlib/source/library/lux/control/exception.lux | 4 +- .../library/lux/control/function/contract.lux | 10 +- .../source/library/lux/control/function/inline.lux | 6 +- stdlib/source/library/lux/control/io.lux | 6 +- stdlib/source/library/lux/control/lazy.lux | 4 +- stdlib/source/library/lux/control/pipe.lux | 8 +- .../library/lux/control/security/capability.lux | 10 +- .../source/library/lux/data/collection/stream.lux | 2 +- stdlib/source/library/lux/data/format/json.lux | 13 +- stdlib/source/library/lux/data/text/regex.lux | 139 ++++++++------- stdlib/source/library/lux/debug.lux | 4 +- stdlib/source/library/lux/documentation.lux | 183 ++++++++++---------- stdlib/source/library/lux/ffi.jvm.lux | 93 +++++------ stdlib/source/library/lux/ffi.lux | 24 +-- stdlib/source/library/lux/ffi.old.lux | 40 ++--- stdlib/source/library/lux/ffi.php.lux | 20 +-- stdlib/source/library/lux/ffi.scm.lux | 12 +- stdlib/source/library/lux/math/modulus.lux | 2 +- stdlib/source/library/lux/math/number/ratio.lux | 6 +- .../lux/meta/compiler/language/lux/analysis.lux | 4 +- .../meta/compiler/language/lux/phase/analysis.lux | 6 +- .../language/lux/phase/analysis/reference.lux | 26 +-- stdlib/source/library/lux/meta/extension.lux | 12 +- stdlib/source/library/lux/meta/macro.lux | 8 +- stdlib/source/library/lux/meta/macro/context.lux | 30 ++-- stdlib/source/library/lux/meta/macro/syntax.lux | 22 +-- .../source/library/lux/meta/macro/vocabulary.lux | 26 +-- .../library/lux/meta/target/jvm/modifier.lux | 22 +-- stdlib/source/library/lux/meta/type.lux | 12 +- stdlib/source/library/lux/meta/type/dynamic.lux | 57 +++---- stdlib/source/library/lux/meta/type/poly.lux | 24 +-- stdlib/source/library/lux/meta/type/primitive.lux | 4 +- stdlib/source/library/lux/meta/type/quotient.lux | 2 +- stdlib/source/library/lux/meta/type/refinement.lux | 2 +- stdlib/source/library/lux/meta/type/resource.lux | 6 +- stdlib/source/library/lux/meta/type/unit.lux | 15 +- stdlib/source/library/lux/meta/type/unit/scale.lux | 22 ++- stdlib/source/library/lux/program.lux | 20 +-- stdlib/source/library/lux/test.lux | 39 ++--- .../source/polytypic/lux/abstract/equivalence.lux | 38 ++--- stdlib/source/polytypic/lux/abstract/functor.lux | 4 +- stdlib/source/polytypic/lux/data/format/json.lux | 104 ++++++------ stdlib/source/program/compositor.lux | 8 +- .../specification/compositor/generation/common.lux | 11 -- stdlib/source/test/lux.lux | 186 ++++++++++----------- .../language/lux/phase/analysis/reference.lux | 18 +- .../language/lux/phase/extension/analysis/lux.lux | 2 - 49 files changed, 708 insertions(+), 751 deletions(-) (limited to 'stdlib/source') diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux index c13ce6ab0..fa0108157 100644 --- a/stdlib/source/library/lux.lux +++ b/stdlib/source/library/lux.lux @@ -1326,9 +1326,9 @@ (p x))} xs)) -(def' .private (with_location content) - (-> Code Code) - (let' [[module line column] ..dummy_location] +(def' .private (with_location @ content) + (-> Location Code Code) + (let' [[module line column] @] (tuple$ (list (tuple$ (list (text$ module) (nat$ line) (nat$ column))) content)))) @@ -1589,7 +1589,8 @@ (def' .private (untemplated_text value) (-> Text Code) - (with_location (variant$ (list (symbol$ [..prelude "#Text"]) (text$ value))))) + (with_location ..dummy_location + (variant$ (list (symbol$ [..prelude "#Text"]) (text$ value))))) (def' .public UnQuote Type @@ -1902,7 +1903,8 @@ (do meta#monad [=elements (monad#each meta#monad (untemplated replace? subst) elements)] (in (untemplated_list =elements)))) - .let' [[_ output'] (with_location (variant$ (list (symbol$ [..prelude tag]) output)))]] + .let' [[_ output'] (with_location ..dummy_location + (variant$ (list (symbol$ [..prelude tag]) output)))]] (in [@composite output']))) (def' .private untemplated_form @@ -1923,19 +1925,24 @@ (def' .private (untemplated replace? subst token) (-> Bit Text Code ($' Meta Code)) ({[_ [@token {#Bit value}]] - (meta#in (with_location (variant$ (list (symbol$ [..prelude "#Bit"]) (bit$ value))))) + (meta#in (with_location ..dummy_location + (variant$ (list (symbol$ [..prelude "#Bit"]) (bit$ value))))) [_ [@token {#Nat value}]] - (meta#in (with_location (variant$ (list (symbol$ [..prelude "#Nat"]) (nat$ value))))) + (meta#in (with_location ..dummy_location + (variant$ (list (symbol$ [..prelude "#Nat"]) (nat$ value))))) [_ [@token {#Int value}]] - (meta#in (with_location (variant$ (list (symbol$ [..prelude "#Int"]) (int$ value))))) + (meta#in (with_location ..dummy_location + (variant$ (list (symbol$ [..prelude "#Int"]) (int$ value))))) [_ [@token {#Rev value}]] - (meta#in (with_location (variant$ (list (symbol$ [..prelude "#Rev"]) (rev$ value))))) + (meta#in (with_location ..dummy_location + (variant$ (list (symbol$ [..prelude "#Rev"]) (rev$ value))))) [_ [@token {#Frac value}]] - (meta#in (with_location (variant$ (list (symbol$ [..prelude "#Frac"]) (frac$ value))))) + (meta#in (with_location ..dummy_location + (variant$ (list (symbol$ [..prelude "#Frac"]) (frac$ value))))) [_ [@token {#Text value}]] (meta#in (untemplated_text value)) @@ -1951,10 +1958,12 @@ (in [module name])} module) .let' [[module name] real_name]] - (meta#in (with_location (variant$ (list (symbol$ [..prelude "#Symbol"]) (tuple$ (list (text$ module) (text$ name)))))))) + (meta#in (with_location [module 0 0] + (variant$ (list (symbol$ [..prelude "#Symbol"]) (tuple$ (list (text$ module) (text$ name)))))))) [#0 [@token {#Symbol [module name]}]] - (meta#in (with_location (variant$ (list (symbol$ [..prelude "#Symbol"]) (tuple$ (list (text$ module) (text$ name))))))) + (meta#in (with_location @token + (variant$ (list (symbol$ [..prelude "#Symbol"]) (tuple$ (list (text$ module) (text$ name))))))) [#1 [@composite {#Form {#Item [@symbol {#Symbol global}] parameters}}]] (do meta#monad @@ -2056,25 +2065,6 @@ (def' .public but UnQuote ,) -(def' .public ,! - UnQuote - (..unquote - (macro (_ tokens) - ({{#Item [@token dependent] {#End}} - (do meta#monad - [current_module ..current_module_name - independent (untemplated #1 current_module [@token dependent])] - (in (list (with_location (variant$ (list (symbol$ [..prelude "#Form"]) - (untemplated_list (list (untemplated_text "lux in-module") - (untemplated_text current_module) - independent)))))))) - - _ - (failure (wrong_syntax_error [..prelude ",!"]))} - tokens)))) - -(def' .public specifically UnQuote ,!) - (def' .public ,' UnQuote (..unquote @@ -2466,8 +2456,8 @@ (meta#in (list token))} token)) -(def' .private (full_expansion' full_expansion name args) - (-> (-> Code ($' Meta ($' List Code))) Symbol ($' List Code) ($' Meta ($' List Code))) +(def' .private (full_expansion' full_expansion @name name args) + (-> (-> Code ($' Meta ($' List Code))) Location Symbol ($' List Code) ($' Meta ($' List Code))) (do meta#monad [name' (normal name) ?macro (named_macro name')] @@ -2480,7 +2470,7 @@ {#None} (do meta#monad [args' (monad#each meta#monad full_expansion args)] - (in (list (form$ {#Item (symbol$ name) (list#conjoint args')}))))} + (in (list (form$ {#Item [@name {#Symbol name}] (list#conjoint args')}))))} ?macro))) (def' .private (in_module module meta) @@ -2522,42 +2512,31 @@ ..#eval eval]))} lux))) -(def' .private (full_expansion expand_in_module?) - (-> Bit Code ($' Meta ($' List Code))) - (function' again [syntax] - ({[_ {#Form {#Item head tail}}] - ({[_ {#Form {#Item [_ {#Text "lux in-module"}] - {#Item [_ {#Text module}] - {#Item [_ {#Symbol name}] - {#End}}}}}] - (if expand_in_module? - (..in_module module (..full_expansion' again name tail)) - (do meta#monad - [members' (monad#each meta#monad again {#Item head tail})] - (in (list (form$ (list#conjoint members')))))) - - [_ {#Symbol name}] - (..full_expansion' again name tail) - - _ - (do meta#monad - [members' (monad#each meta#monad again {#Item head tail})] - (in (list (form$ (list#conjoint members')))))} - head) - - [_ {#Variant members}] - (do meta#monad - [members' (monad#each meta#monad again members)] - (in (list (variant$ (list#conjoint members'))))) - - [_ {#Tuple members}] - (do meta#monad - [members' (monad#each meta#monad again members)] - (in (list (tuple$ (list#conjoint members'))))) - - _ - (meta#in (list syntax))} - syntax))) +(def' .private (full_expansion syntax) + (-> Code ($' Meta ($' List Code))) + ({[_ {#Form {#Item head tail}}] + ({[@name {#Symbol name}] + (..full_expansion' full_expansion @name name tail) + + _ + (do meta#monad + [members' (monad#each meta#monad full_expansion {#Item head tail})] + (in (list (form$ (list#conjoint members')))))} + head) + + [_ {#Variant members}] + (do meta#monad + [members' (monad#each meta#monad full_expansion members)] + (in (list (variant$ (list#conjoint members'))))) + + [_ {#Tuple members}] + (do meta#monad + [members' (monad#each meta#monad full_expansion members)] + (in (list (tuple$ (list#conjoint members'))))) + + _ + (meta#in (list syntax))} + syntax)) (def' .private (text#encoded original) (-> Text Text) @@ -2740,7 +2719,7 @@ [initialized_quantification? (function' [lux] {#Right [lux (initialized_quantification? lux)]})] (if initialized_quantification? (do meta#monad - [type+ (full_expansion #0 type)] + [type+ (full_expansion type)] ({{#Item type' {#End}} (do meta#monad [type'' (normal_type type')] @@ -2847,7 +2826,7 @@ Code Code (List Code) (Meta (List Code)))) (do meta#monad - [pattern (one_expansion (full_expansion #1 pattern)) + [pattern (one_expansion (full_expansion pattern)) branches (case_expansion branches)] (in (list#partial pattern body branches)))) @@ -4580,7 +4559,7 @@ (list#interposed " ") (list#mix text#composite ""))))))) -(def refer +(def .public refer (macro (_ tokens) (case tokens (list#partial [_ {#Text imported_module}] [_ {#Text alias}] options) @@ -5319,12 +5298,11 @@ (def (refer_code imported_module alias referrals) (-> Text Text (List Referral) Code) - (` ((,! ..refer) - (, (text$ imported_module)) - (, (text$ alias)) - (,* (list#each (function (_ [macro parameters]) - (` ((, (symbol$ macro)) (,* parameters)))) - referrals))))) + (` (..refer (, (text$ imported_module)) + (, (text$ alias)) + (,* (list#each (function (_ [macro parameters]) + (` ((, (symbol$ macro)) (,* parameters)))) + referrals))))) (def .public require (macro (_ _imports) diff --git a/stdlib/source/library/lux/control/concurrency/thread.lux b/stdlib/source/library/lux/control/concurrency/thread.lux index 408b854f8..957a052d1 100644 --- a/stdlib/source/library/lux/control/concurrency/thread.lux +++ b/stdlib/source/library/lux/control/concurrency/thread.lux @@ -2,6 +2,7 @@ [library [lux (.except) ["[0]" ffi] + ["[0]" debug] [abstract ["[0]" monad (.only do)]] [control @@ -113,9 +114,9 @@ (case (try (io.run! action)) {try.#Failure error} (exec - ("lux io log" (all "lux text concat" - "ERROR DURING THREAD EXECUTION:" text.new_line - error)) + (debug.log! (all "lux text concat" + "ERROR DURING THREAD EXECUTION:" text.new_line + error)) []) {try.#Success _} diff --git a/stdlib/source/library/lux/control/exception.lux b/stdlib/source/library/lux/control/exception.lux index 6b2ea833e..f311fdb25 100644 --- a/stdlib/source/library/lux/control/exception.lux +++ b/stdlib/source/library/lux/control/exception.lux @@ -103,8 +103,8 @@ (let [(, g!descriptor) (, (code.text descriptor))] [..#label (, g!descriptor) ..#constructor (function ((, g!self) [(,* (list#each (the |input|.#binding) inputs))]) - ((,! text#composite) (, g!descriptor) - (, (maybe.else (' "") body))))]))))))))) + (at text.monoid (,' composite) (, g!descriptor) + (, (maybe.else (' "") body))))]))))))))) (def .public (report entries) (-> (List [Text Text]) Text) diff --git a/stdlib/source/library/lux/control/function/contract.lux b/stdlib/source/library/lux/control/function/contract.lux index afaee51ee..a5f73c098 100644 --- a/stdlib/source/library/lux/control/function/contract.lux +++ b/stdlib/source/library/lux/control/function/contract.lux @@ -24,7 +24,7 @@ [post_condition_failed] ) -(def (assert! message test) +(def .public (assert! message test) (-> Text Bit []) (if test [] @@ -34,8 +34,8 @@ (syntax (_ [test .any expr .any]) (in (list (` (exec - ((,! ..assert!) (, (code.text (exception.error ..pre_condition_failed test))) - (, test)) + (..assert! (, (code.text (exception.error ..pre_condition_failed test))) + (, test)) (, expr))))))) (def .public post @@ -44,6 +44,6 @@ (with_symbols [g!output] (in (list (` (let [(, g!output) (, expr)] (exec - ((,! ..assert!) (, (code.text (exception.error ..post_condition_failed test))) - ((, test) (, g!output))) + (..assert! (, (code.text (exception.error ..post_condition_failed test))) + ((, test) (, g!output))) (, g!output))))))))) diff --git a/stdlib/source/library/lux/control/function/inline.lux b/stdlib/source/library/lux/control/function/inline.lux index 299e0165f..6d5f3bebf 100644 --- a/stdlib/source/library/lux/control/function/inline.lux +++ b/stdlib/source/library/lux/control/function/inline.lux @@ -45,8 +45,8 @@ g!parameters)))) g!parameters (|> g!parameters (list#each (function (_ parameter) - (list parameter (` (,! .any))))) + (list parameter (` .any)))) list#conjoint)]] (in (list (` (def (, privacy) (, (code.local name)) - ((,! syntax) ((, (code.local name)) [(,* g!parameters)]) - (.at (,! meta.monad) (,' in) (.list (.`' (, inlined)))))))))))) + (syntax ((, (code.local name)) [(,* g!parameters)]) + (.at meta.monad (,' in) (.list (.`' (, inlined)))))))))))) diff --git a/stdlib/source/library/lux/control/io.lux b/stdlib/source/library/lux/control/io.lux index a4789fe50..11993b0b4 100644 --- a/stdlib/source/library/lux/control/io.lux +++ b/stdlib/source/library/lux/control/io.lux @@ -17,7 +17,7 @@ (primitive .public (IO a) (-> Any a) - (def label + (def .public io' (All (_ a) (-> (-> Any a) (IO a))) (|>> abstraction)) @@ -36,8 +36,8 @@ (def .public io (syntax (_ [computation .any]) (with_symbols [g!func g!arg] - (in (list (` ((,! ..label) (function ((, g!func) (, g!arg)) - (, computation))))))))) + (in (list (` (..io' (function ((, g!func) (, g!arg)) + (, computation))))))))) (def .public run! (All (_ a) (-> (IO a) a)) diff --git a/stdlib/source/library/lux/control/lazy.lux b/stdlib/source/library/lux/control/lazy.lux index aaf3aafe6..4636f701a 100644 --- a/stdlib/source/library/lux/control/lazy.lux +++ b/stdlib/source/library/lux/control/lazy.lux @@ -21,7 +21,7 @@ (primitive .public (Lazy a) (-> [] a) - (def (lazy' generator) + (def .public (lazy' generator) (All (_ a) (-> (-> [] a) (Lazy a))) (let [cache (atom.atom (sharing [a] (is (-> [] a) @@ -46,7 +46,7 @@ (def .public lazy (syntax (_ [expression .any]) (with_symbols [g!_] - (in (list (` ((,! ..lazy') (function ((, g!_) (, g!_)) (, expression))))))))) + (in (list (` (..lazy' (function ((, g!_) (, g!_)) (, expression))))))))) (def .public (equivalence (open "_#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (Lazy a)))) diff --git a/stdlib/source/library/lux/control/pipe.lux b/stdlib/source/library/lux/control/pipe.lux index 2198abe8a..54b0fca51 100644 --- a/stdlib/source/library/lux/control/pipe.lux +++ b/stdlib/source/library/lux/control/pipe.lux @@ -93,10 +93,10 @@ (.let [step_bindings (monad.do list.monad [step (list.reversed prev_steps)] (list g!temp (` (|> (, g!temp) (,* step)))))] - (in (list (` ((,! monad.do) (, monad) - [.let [(, g!temp) (, prev)] - (,* step_bindings)] - (|> (, g!temp) (,* last_step))))))) + (in (list (` (monad.do (, monad) + [.let [(, g!temp) (, prev)] + (,* step_bindings)] + (|> (, g!temp) (,* last_step))))))) _ (in (list prev)))))) diff --git a/stdlib/source/library/lux/control/security/capability.lux b/stdlib/source/library/lux/control/security/capability.lux index 434bb215c..24e627960 100644 --- a/stdlib/source/library/lux/control/security/capability.lux +++ b/stdlib/source/library/lux/control/security/capability.lux @@ -26,12 +26,6 @@ (primitive .public (Capability brand input output) (-> input output) - (def capability - (All (_ brand input output) - (-> (-> input output) - (Capability brand input output))) - (|>> abstraction)) - (def .public (use capability input) (All (_ brand input output) (-> (Capability brand input output) @@ -59,12 +53,12 @@ (All ((, g!_) (,* (list#each code.local vars))) (-> (-> (, input) (, output)) (, capability))) - (,! ..capability))) + (|>> as_expected))) )))))) (def .public (async capability) (All (_ brand input output) (-> (Capability brand input (IO output)) (Capability brand input (Async output)))) - (..capability (|>> ((representation capability)) async.future))) + (abstraction (|>> ((representation capability)) async.future))) ) diff --git a/stdlib/source/library/lux/data/collection/stream.lux b/stdlib/source/library/lux/data/collection/stream.lux index 6d9d358e3..3c3a2cb29 100644 --- a/stdlib/source/library/lux/data/collection/stream.lux +++ b/stdlib/source/library/lux/data/collection/stream.lux @@ -137,7 +137,7 @@ (let [body+ (` (let [(,* (|> patterns (list#each (function (_ pattern) (list (` [(, pattern) (, g!stream)]) - (` ((,! //.result) (, g!stream)))))) + (` (//.result (, g!stream)))))) list#conjoint))] (, body)))] (in (list.partial g!stream body+ branches))))))) diff --git a/stdlib/source/library/lux/data/format/json.lux b/stdlib/source/library/lux/data/format/json.lux index a7aecfd6b..895a6931f 100644 --- a/stdlib/source/library/lux/data/format/json.lux +++ b/stdlib/source/library/lux/data/format/json.lux @@ -110,15 +110,14 @@ [code.text ..#String' ..#String]) {#Array' members} - (` {..#Array ((,! sequence.sequence) (,* (sequence.list (sequence#each jsonF members))))}) + (` {..#Array (sequence.sequence (,* (sequence.list (sequence#each jsonF members))))}) {#Object' pairs} - (` {..#Object ((,! dictionary.of_list) - (,! text.hash) - (list (,* (|> pairs - dictionary.entries - (list#each (function (_ [key_name value]) - (` [(, (code.text key_name)) (, (jsonF value))])))))))}) + (` {..#Object (dictionary.of_list text.hash + (list (,* (|> pairs + dictionary.entries + (list#each (function (_ [key_name value]) + (` [(, (code.text key_name)) (, (jsonF value))])))))))}) {#Code' code} code)) diff --git a/stdlib/source/library/lux/data/text/regex.lux b/stdlib/source/library/lux/data/text/regex.lux index 2a5d253a2..e7ee4984a 100644 --- a/stdlib/source/library/lux/data/text/regex.lux +++ b/stdlib/source/library/lux/data/text/regex.lux @@ -1,6 +1,6 @@ (.require [library - [lux (.except pattern) + [lux (.except pattern or) [abstract [monad (.only do)]] [control @@ -38,23 +38,23 @@ .any regex_char^))) -(def (refine^ refinement^ base^) +(def .public (refined refinement^ base^) (All (_ a) (-> (Parser a) (Parser Text) (Parser Text))) (do <>.monad [output base^ _ (.local output refinement^)] (in output))) -(def word^ +(def .public word (Parser Text) (<>.either .alpha_num (.one_of "_"))) -(def (copy reference) +(def .public (copy reference) (-> Text (Parser Text)) (<>.after (.this reference) (<>#in reference))) -(def together^ +(def .public together (-> (Parser (List Text)) (Parser Text)) (at <>.monad each //.together)) @@ -65,7 +65,7 @@ (def symbol_part^ (Parser Text) (do <>.monad - [head (refine^ (.not .decimal) + [head (refined (.not .decimal) symbol_char^) tail (.some symbol_char^)] (in (format head tail)))) @@ -82,7 +82,7 @@ (-> Text (Parser Code)) (do <>.monad [symbol (.enclosed ["\@<" ">"] (symbol^ current_module))] - (in (` (is ((,! .Parser) Text) (, (code.symbol symbol))))))) + (in (` (is (.Parser Text) (, (code.symbol symbol))))))) (def re_range^ (Parser Code) @@ -90,19 +90,19 @@ [from (|> regex_char^ (at ! each (|>> (//.char 0) maybe.trusted))) _ (.this "-") to (|> regex_char^ (at ! each (|>> (//.char 0) maybe.trusted)))] - (in (` ((,! .range) (, (code.nat from)) (, (code.nat to))))))) + (in (` (.range (, (code.nat from)) (, (code.nat to))))))) (def re_char^ (Parser Code) (do <>.monad [char escaped_char^] - (in (` ((,! ..copy) (, (code.text char))))))) + (in (` (..copy (, (code.text char))))))) (def re_options^ (Parser Code) (do <>.monad [options (.many escaped_char^)] - (in (` ((,! .one_of) (, (code.text options))))))) + (in (` (.one_of (, (code.text options))))))) (def re_user_class^' (Parser Code) @@ -112,8 +112,8 @@ re_range^ re_options^))] (in (case negate? - {.#Some _} (` ((,! .not) (all ((,! <>.either)) (,* parts)))) - {.#None} (` (all ((,! <>.either)) (,* parts))))))) + {.#Some _} (` (.not (all <>.either (,* parts)))) + {.#None} (` (all <>.either (,* parts))))))) (def re_user_class^ (Parser Code) @@ -123,64 +123,64 @@ (.enclosed ["[" "]"] ..re_user_class^')))] (in (list#mix (function (_ refinement base) - (` ((,! refine^) (, refinement) (, base)))) + (` (refined (, refinement) (, base)))) init rest)))) -(def blank^ +(def .public blank (Parser Text) (.one_of (format " " //.tab))) -(def ascii^ +(def .public ascii (Parser Text) (.range (hex "0") (hex "7F"))) -(def control^ +(def .public control (Parser Text) (<>.either (.range (hex "0") (hex "1F")) (.one_of (//.of_char (hex "7F"))))) -(def punct^ +(def .public punctuation (Parser Text) (.one_of (format "!#$%&'()*+,-./:;<=>?@[\]^_`{|}~" //.double_quote))) -(def graph^ +(def .public graph (Parser Text) - (<>.either punct^ .alpha_num)) + (<>.either punctuation .alpha_num)) -(def print^ +(def .public print (Parser Text) - (<>.either graph^ - (.one_of (//.of_char (hex "20"))))) + (<>.either graph + (.one_of //.space))) (def re_system_class^ (Parser Code) (do <>.monad [] (all <>.either - (<>.after (.this ".") (in (` (,! .any)))) - (<>.after (.this "\d") (in (` (,! .decimal)))) - (<>.after (.this "\D") (in (` ((,! .not) (,! .decimal))))) - (<>.after (.this "\s") (in (` (,! .space)))) - (<>.after (.this "\S") (in (` ((,! .not) (,! .space))))) - (<>.after (.this "\w") (in (` (,! word^)))) - (<>.after (.this "\W") (in (` ((,! .not) (,! word^))))) - - (<>.after (.this "\p{Lower}") (in (` (,! .lower)))) - (<>.after (.this "\p{Upper}") (in (` (,! .upper)))) - (<>.after (.this "\p{Alpha}") (in (` (,! .alpha)))) - (<>.after (.this "\p{Digit}") (in (` (,! .decimal)))) - (<>.after (.this "\p{Alnum}") (in (` (,! .alpha_num)))) - (<>.after (.this "\p{Space}") (in (` (,! .space)))) - (<>.after (.this "\p{HexDigit}") (in (` (,! .hexadecimal)))) - (<>.after (.this "\p{OctDigit}") (in (` (,! .octal)))) - (<>.after (.this "\p{Blank}") (in (` (,! blank^)))) - (<>.after (.this "\p{ASCII}") (in (` (,! ascii^)))) - (<>.after (.this "\p{Contrl}") (in (` (,! control^)))) - (<>.after (.this "\p{Punct}") (in (` (,! punct^)))) - (<>.after (.this "\p{Graph}") (in (` (,! graph^)))) - (<>.after (.this "\p{Print}") (in (` (,! print^)))) + (<>.after (.this ".") (in (` .any))) + (<>.after (.this "\d") (in (` .decimal))) + (<>.after (.this "\D") (in (` (.not .decimal)))) + (<>.after (.this "\s") (in (` .space))) + (<>.after (.this "\S") (in (` (.not .space)))) + (<>.after (.this "\w") (in (` word))) + (<>.after (.this "\W") (in (` (.not word)))) + + (<>.after (.this "\p{Lower}") (in (` .lower))) + (<>.after (.this "\p{Upper}") (in (` .upper))) + (<>.after (.this "\p{Alpha}") (in (` .alpha))) + (<>.after (.this "\p{Digit}") (in (` .decimal))) + (<>.after (.this "\p{Alnum}") (in (` .alpha_num))) + (<>.after (.this "\p{Space}") (in (` .space))) + (<>.after (.this "\p{HexDigit}") (in (` .hexadecimal))) + (<>.after (.this "\p{OctDigit}") (in (` .octal))) + (<>.after (.this "\p{Blank}") (in (` blank))) + (<>.after (.this "\p{ASCII}") (in (` ascii))) + (<>.after (.this "\p{Contrl}") (in (` control))) + (<>.after (.this "\p{Punct}") (in (` punctuation))) + (<>.after (.this "\p{Graph}") (in (` graph))) + (<>.after (.this "\p{Print}") (in (` print))) ))) (def re_class^ @@ -198,12 +198,12 @@ (<>.either (do <>.monad [_ (.this "\") id number^] - (in (` ((,! ..copy) (, (code.symbol ["" (n#encoded id)])))))) + (in (` (..copy (, (code.symbol ["" (n#encoded id)])))))) (do <>.monad [_ (.this "\k<") captured_symbol symbol_part^ _ (.this ">")] - (in (` ((,! ..copy) (, (code.symbol ["" captured_symbol])))))))) + (in (` (..copy (, (code.symbol ["" captured_symbol])))))))) (def (re_simple^ current_module) (-> Text (Parser Code)) @@ -221,14 +221,14 @@ quantifier (.one_of "?*+")] (case quantifier "?" - (in (` ((,! <>.else) "" (, base)))) + (in (` (<>.else "" (, base)))) "*" - (in (` ((,! together^) ((,! <>.some) (, base))))) + (in (` (together (<>.some (, base))))) ... "+" _ - (in (` ((,! together^) ((,! <>.many) (, base))))) + (in (` (together (<>.many (, base))))) ))) (exception .public (incorrect_quantification [from Nat @@ -247,19 +247,18 @@ [[from to] (<>.and number^ (<>.after (.this ",") number^)) _ (<>.assertion (exception.error ..incorrect_quantification [from to]) (n.<= to from))] - (in (` ((,! together^) ((,! <>.between) - (, (code.nat from)) - (, (code.nat (n.- from to))) - (, base)))))) + (in (` (together (<>.between (, (code.nat from)) + (, (code.nat (n.- from to))) + (, base)))))) (do ! [limit (<>.after (.this ",") number^)] - (in (` ((,! together^) ((,! <>.at_most) (, (code.nat limit)) (, base)))))) + (in (` (together (<>.at_most (, (code.nat limit)) (, base)))))) (do ! [limit (<>.before (.this ",") number^)] - (in (` ((,! together^) ((,! <>.at_least) (, (code.nat limit)) (, base)))))) + (in (` (together (<>.at_least (, (code.nat limit)) (, base)))))) (do ! [limit number^] - (in (` ((,! together^) ((,! <>.exactly) (, (code.nat limit)) (, base)))))))))) + (in (` (together (<>.exactly (, (code.nat limit)) (, base)))))))))) (def (re_quantified^ current_module) (-> Text (Parser Code)) @@ -297,7 +296,7 @@ [idx names (list.partial (list g!temp complex - (` .let) (` [(, g!total) (at (,! //.monoid) (,' composite) (, g!total) (, g!temp))])) + (` .let) (` [(, g!total) (at //.monoid (,' composite) (, g!total) (, g!temp))])) steps)] {.#Right [{#Capturing [?name num_captures]} scoped]} @@ -308,12 +307,12 @@ {.#None} [(++ idx) (code.symbol ["" (n#encoded idx)])]) access (if (n.> 0 num_captures) - (` ((,! product.left) (, name!))) + (` (product.left (, name!))) name!)] [idx! (list.partial name! names) (list.partial (list name! scoped - (` .let) (` [(, g!total) (at (,! //.monoid) (,' composite) (, g!total) (, access))])) + (` .let) (` [(, g!total) (at //.monoid (,' composite) (, g!total) (, access))])) steps)]) ))) [0 @@ -323,17 +322,17 @@ (in [(if capturing? (list.size names) 0) - (` ((,! do) (,! <>.monad) - [.let [(, g!total) ""] - (,* (|> steps list.reversed list#conjoint))] - ((, (' in)) [(, g!total) (,* (list.reversed names))])))]) + (` (do <>.monad + [.let [(, g!total) ""] + (,* (|> steps list.reversed list#conjoint))] + ((, (' in)) [(, g!total) (,* (list.reversed names))])))]) )) -(def (unflatten^ lexer) +(def .public (alternative lexer) (-> (Parser Text) (Parser [Text Any])) (<>.and lexer (at <>.monad in []))) -(def (|||^ left right) +(def .public (or left right) (All (_ l r) (-> (Parser [Text l]) (Parser [Text r]) (Parser [Text (Or l r)]))) (function (_ input) (case (left input) @@ -348,7 +347,7 @@ {try.#Failure error} {try.#Failure error})))) -(def (|||_^ left right) +(def .public (either left right) (All (_ l r) (-> (Parser [Text l]) (Parser [Text r]) (Parser Text))) (function (_ input) (case (left input) @@ -367,7 +366,7 @@ (-> [Nat Code] Code) (if (n.> 0 num_captures) alt - (` ((,! unflatten^) (, alt))))) + (` (..alternative (, alt))))) (def (re_alternative^ capturing? re_scoped^ current_module) (-> Bit @@ -382,8 +381,8 @@ (in head) (in [(list#mix n.max (product.left head) (list#each product.left tail)) (` (all ((, (if capturing? - (` (,! |||^)) - (` (,! |||_^))))) + (` ..or) + (` ..either)))) (, (prep_alternative head)) (,* (list#each prep_alternative tail))))])))) @@ -435,7 +434,7 @@ branches (<>.many .any)]) (with_symbols [g!temp] (in (list.partial (` (^.multi (, g!temp) - [((,! .result) (..regex (, (code.text pattern))) (, g!temp)) + [(.result (..regex (, (code.text pattern))) (, g!temp)) {try.#Success (, (maybe.else g!temp bindings))}])) body branches)))))) diff --git a/stdlib/source/library/lux/debug.lux b/stdlib/source/library/lux/debug.lux index 47046fadc..a4866a106 100644 --- a/stdlib/source/library/lux/debug.lux +++ b/stdlib/source/library/lux/debug.lux @@ -591,12 +591,12 @@ targets)))] (in (list (` (..log! ("lux text concat" (, (code.text (%.format (%.location location) text.new_line))) - ((,! exception.report) + (exception.report (.list (,* (|> targets (list#each (function (_ [name format]) (let [format (case format {.#None} - (` (,! ..inspection)) + (` ..inspection) {.#Some format} format)] diff --git a/stdlib/source/library/lux/documentation.lux b/stdlib/source/library/lux/documentation.lux index 73dbbcd63..cf2aa5adc 100644 --- a/stdlib/source/library/lux/documentation.lux +++ b/stdlib/source/library/lux/documentation.lux @@ -1,6 +1,6 @@ (.require [library - [lux (.except Definition Module type) + [lux (.except Definition Module) [abstract [monad (.only do)] ["[0]" enum]] @@ -28,7 +28,8 @@ ["[0]" macro (.only) [syntax (.only syntax)] ["^" pattern] - ["[0]" template]] + ["[0]" template] + ["[0]" expansion]] [compiler [language [lux @@ -133,15 +134,12 @@ Text (format \n \n)) -(def single_line_comment - (-> Text Text) - (text.prefix "... ")) (def (fragment_documentation module fragment) (-> Text Fragment Text) (case fragment {#Comment comment} - (..single_line_comment comment) + (format "... " comment) {#Code example} (let [reference_column (..reference_column example) @@ -251,11 +249,11 @@ {.#Parameter idx} (parameter_name [type_function_name (list)] level idx) - (^.with_template [
 ]
+    (^.with_template []
       [{ id}
-       (format 
 (%.nat id) )])
-    ([.#Var "⌈" "⌋"]
-     [.#Ex  "⟨" "⟩"])
+       (%.type type)])
+    ([.#Var]
+     [.#Ex])
 
     (^.with_template [  ]
       [{ _}
@@ -297,7 +295,7 @@
           (%.symbol [_module _name]))
     ))
 
-(def type
+(def .public type_documentation
   (-> Text Type Text)
   (%type' (-- 0) "?" true))
 
@@ -435,7 +433,7 @@
             (%.symbol [_module _name]))
       )))
 
-(def (type_definition module [name parameters] tags type)
+(def .public (type_definition module [name parameters] tags type)
   (-> Text [Text (List Text)] (List Text) Type Text)
   (let [arity (list.size parameters)]
     (case (parameterized_type arity type)
@@ -443,7 +441,7 @@
       (type_definition' true (-- arity) arity [name parameters] tags module type)
 
       {.#None}
-      (..type module type))))
+      (type_documentation module type))))
 
 (def description
   (Parser (Maybe Code))
@@ -504,53 +502,51 @@
       [.let [g!module (code.text (product.left name))]
        [[_ def_type def_value]] (meta.export name)
        tags (meta.tags_of name)]
-      (with_expansions [<\n> (,! text.\n)]
-        (macro.with_symbols [g!type]
-          (in (list (` (all ((,! md.then))
-                            ... Name
-                            (<| ((,! md.heading/3))
-                                (, (code.text (%.code (let [g!name (|> name product.right code.local)]
-                                                        (case parameters
-                                                          {.#End}
-                                                          g!name
-
-                                                          _
-                                                          (` ((, g!name) (,* (list#each code.local parameters))))))))))
-                            ... Type
-                            (let [(, g!type) ("lux in-module"
-                                              (, g!module)
-                                              (.type_of (, (code.symbol name))))]
-                              ((,! md.code) "clojure"
-                               (, (if (type#= .Type def_type)
-                                    (` (|> (, (code.symbol name))
-                                           (as .Type)
-                                           ((,! type.anonymous))
-                                           ((,! ..type_definition)
+      (macro.with_symbols [g!type]
+        (in (list (` (all md.then
+                          ... Name
+                          (<| (md.heading/3)
+                              (, (code.text (%.code (let [g!name (|> name product.right code.local)]
+                                                      (case parameters
+                                                        {.#End}
+                                                        g!name
+
+                                                        _
+                                                        (` ((, g!name) (,* (list#each code.local parameters))))))))))
+                          ... Type
+                          (let [(, g!type) ("lux in-module"
                                             (, g!module)
-                                            [(, (code.text (product.right name))) (list (,* (list#each code.text parameters)))]
-                                            (.list (,* (|> tags
-                                                           (maybe.else (list))
-                                                           (list#each (|>> product.right code.text))))))
-                                           ((,! %.format)
-                                            ((,! ..single_line_comment) ((,! ..type) (, g!module) (, g!type)))
-                                            <\n>)))
-                                    (` ((,! ..type) (, g!module) (, g!type))))))))
-                       ))))))))
+                                            (.type_of (, (code.symbol name))))]
+                            (md.code "clojure"
+                                     (, (if (type#= .Type def_type)
+                                          (` (|> (, (code.symbol name))
+                                                 (as .Type)
+                                                 type.anonymous
+                                                 (..type_definition
+                                                  (, g!module)
+                                                  [(, (code.text (product.right name))) (list (,* (list#each code.text parameters)))]
+                                                  (.list (,* (|> tags
+                                                                 (maybe.else (list))
+                                                                 (list#each (|>> product.right code.text))))))
+                                                 (%.format "... " (type_documentation (, g!module) (, g!type)) text.\n)))
+                                          (` (type_documentation (, g!module) (, g!type))))))))
+                     )))))))
 
 (def definition_documentation
   (syntax (_ [[name parameters] ..declaration
               description ..description
               examples (<>.some ..example)])
-    (with_expansions [<\n> (,! text.\n)]
-      (in (list (` (all ((,! md.then))
-                        ((,! ..minimal_definition_documentation)
-                         ((, (code.symbol name))
-                          (,* (list#each code.local parameters))))
+    (do meta.monad
+      [minimal (expansion.single (` (..minimal_definition_documentation
+                                     ((, (code.symbol name))
+                                      (,* (list#each code.local parameters))))))]
+      (in (list (` (all md.then
+                        (,* minimal)
                         ... Description
                         (,* (case description
                               {.#Some description}
-                              (list (` (<| ((,! md.paragraph))
-                                           ((,! md.text))
+                              (list (` (<| md.paragraph
+                                           md.text
                                            (, description))))
                               
                               {.#None}
@@ -561,11 +557,10 @@
                               (list)
                               
                               _
-                              (list (` (<| ((,! md.code) "clojure")
-                                           ((,! %.format)
-                                            (,* (|> examples
-                                                    (list#each (..example_documentation (product.left name)))
-                                                    (list.interposed ..example_separator))))))))))
+                              (list (` (<| (md.code "clojure")
+                                           (%.format (,* (|> examples
+                                                             (list#each (..example_documentation (product.left name)))
+                                                             (list.interposed ..example_separator))))))))))
                    ))))))
 
 (.type .public Definition
@@ -583,21 +578,23 @@
 (def .public definition
   (syntax (_ [[name parameters] ..declaration
               extra (<>.some .any)])
-    (macro.with_symbols [g!_]
-      (let [[_ short] name]
-        (in (list (` (.let [(, g!_) (.is (.-> .Any (.List ..Definition))
-                                         (.function ((, g!_) (, g!_))
-                                           (.list [..#definition (, (code.text short))
-                                                   ..#documentation ((, (case extra
-                                                                          (list)
-                                                                          (` (,! ..minimal_definition_documentation))
-
-                                                                          _
-                                                                          (` (,! ..definition_documentation))))
-                                                                     ((, (code.symbol name))
-                                                                      (,* (list#each code.local parameters)))
-                                                                     (,* extra))])))]
-                       ((, g!_) [])))))))))
+    (do meta.monad
+      [documentation (expansion.single (` ((, (case extra
+                                                (list)
+                                                (` ..minimal_definition_documentation)
+
+                                                _
+                                                (` ..definition_documentation)))
+                                           ((, (code.symbol name))
+                                            (,* (list#each code.local parameters)))
+                                           (,* extra))))]
+      (macro.with_symbols [g!_]
+        (let [[_ short] name]
+          (in (list (` (.let [(, g!_) (.is (.-> .Any (.List ..Definition))
+                                           (.function ((, g!_) (, g!_))
+                                             (.list [..#definition (, (code.text short))
+                                                     ..#documentation (,* documentation)])))]
+                         ((, g!_) []))))))))))
 
 (def definitions_documentation
   (-> (List Definition) (Markdown Block))
@@ -619,30 +616,26 @@
                 _ (format aggregate ..expected_separator short)))
             ""))
 
-(def expected
-  (-> Text (Set Text))
-  (|>> (text.all_split_by ..expected_separator)
-       (set.of_list text.hash)))
-
-(def .public module
-  (syntax (_ [[name _] ..qualified_symbol
-              description .any
-              definitions (.tuple (<>.some .any))
-              subs (.tuple (<>.some .any))])
-    (do meta.monad
-      [expected (meta.exports name)]
-      (in (list (` (is (List Module)
-                       ((,! list.partial) [..#module (, (code.text name))
-                                           ..#description (, description)
-                                           ..#expected ((,! ..expected)
-                                                        (, (code.text (|> expected
-                                                                          (list#each product.left)
-                                                                          ..expected_format))))
-                                           ..#definitions ((,! list.together) (list (,* definitions)))]
-                        (all (at (,! list.monoid) (,' composite))
-                             (is (List Module)
-                                 (at (,! list.monoid) (,' identity)))
-                             (,* subs))))))))))
+(`` (def .public module
+      (syntax (_ [[name _] ..qualified_symbol
+                  description .any
+                  definitions (.tuple (<>.some .any))
+                  subs (.tuple (<>.some .any))])
+        (do meta.monad
+          [expected (meta.exports name)]
+          (in (list (` (is (List Module)
+                           (list.partial [..#module (, (code.text name))
+                                          ..#description (, description)
+                                          ..#expected (|> (, (code.text (|> expected
+                                                                            (list#each product.left)
+                                                                            ..expected_format)))
+                                                          (text.all_split_by (,, (static ..expected_separator)))
+                                                          (set.of_list text.hash))
+                                          ..#definitions (list.together (list (,* definitions)))]
+                                         (all (at list.monoid (,' composite))
+                                              (is (List Module)
+                                                  (at list.monoid (,' identity)))
+                                              (,* subs)))))))))))
 
 (def listing
   (-> (List Text) (Markdown Block))
diff --git a/stdlib/source/library/lux/ffi.jvm.lux b/stdlib/source/library/lux/ffi.jvm.lux
index f87ee7be3..1f40f0d76 100644
--- a/stdlib/source/library/lux/ffi.jvm.lux
+++ b/stdlib/source/library/lux/ffi.jvm.lux
@@ -389,7 +389,7 @@
                    (` {.#Primitive (, (code.text (..reflection (jvm.array elementT)))) {.#End}})
                    
                    {.#None}
-                   (` ((,! array.Array) (, (value_type elementT)))))]))
+                   (` (array.Array (, (value_type elementT)))))]))
           ... else
           (undefined)
           )))
@@ -1018,7 +1018,7 @@
         (, (return$ #method_output))
         [(,* (list#each class$ #method_exs))]))))
 
-(def with_super
+(def .public with_super
   (syntax (_ [declaration,method (.tuple
                                   (all <>.and
                                        (.then parser.declaration' .text)
@@ -1095,7 +1095,7 @@
                              type value^^]
                             (in [[name pm anns] {#VariableField [sm static? type]}])))))
 
-(def with_get|set
+(def .public with_get|set
   (syntax (_ [declaration,fields (.tuple
                                   (all <>.and
                                        .text
@@ -1190,7 +1190,7 @@
 (context.def [call_context call_expression call_declaration]
   Call)
 
-(def with_call
+(def .public with_call
   (syntax (_ [declaration,methods (.tuple
                                    (all <>.and
                                         (.then parser.declaration' .text)
@@ -1252,8 +1252,8 @@
                           (list)
 
                           virtual_methods
-                          (list (` ((,! ..with_call) [(, (declaration$ (jvm.declaration fully_qualified_class_name class_vars)))
-                                                      [(,* (list#each method_decl$$ virtual_methods))]]))))]
+                          (list (` (..with_call [(, (declaration$ (jvm.declaration fully_qualified_class_name class_vars)))
+                                                 [(,* (list#each method_decl$$ virtual_methods))]]))))]
     (case method_def
       {#ConstructorMethod strict_fp? type_vars self_name arguments constructor_args body exs}
       (meta#in (` ("init"
@@ -1265,8 +1265,8 @@
                    (, (code.text self_name))
                    [(,* (list#each argument$ arguments))]
                    [(,* (list#each constructor_arg$ constructor_args))]
-                   (<| ((,! ..with_get|set) [(, (code.text fully_qualified_class_name))
-                                             [(,* (list#each field_decl$ fields))]])
+                   (<| (..with_get|set [(, (code.text fully_qualified_class_name))
+                                        [(,* (list#each field_decl$ fields))]])
                        (,* virtual_methods)
                        (, body))
                    )))
@@ -1283,8 +1283,8 @@
                    [(,* (list#each argument$ arguments))]
                    (, (return$ return_type))
                    [(,* (list#each class$ exs))]
-                   (<| ((,! ..with_get|set) [(, (code.text fully_qualified_class_name))
-                                             [(,* (list#each field_decl$ fields))]])
+                   (<| (..with_get|set [(, (code.text fully_qualified_class_name))
+                                        [(,* (list#each field_decl$ fields))]])
                        (,* virtual_methods)
                        (, body))
                    )))
@@ -1302,14 +1302,14 @@
                 [(,* (list#each argument$ expected_arguments))]
                 (, (return$ return_type))
                 [(,* (list#each class$ exs))]
-                (<| ((,! ..with_super) [(, (declaration$ declaration))
-                                        (, (method_decl$$ [method_declaration
-                                                           [#method_tvars  type_vars
-                                                            #method_inputs (list#each product.right expected_arguments)
-                                                            #method_output return_type
-                                                            #method_exs    exs]]))])
-                    ((,! ..with_get|set) [(, (code.text fully_qualified_class_name))
-                                          [(,* (list#each field_decl$ fields))]])
+                (<| (..with_super [(, (declaration$ declaration))
+                                   (, (method_decl$$ [method_declaration
+                                                      [#method_tvars  type_vars
+                                                       #method_inputs (list#each product.right expected_arguments)
+                                                       #method_output return_type
+                                                       #method_exs    exs]]))])
+                    (..with_get|set [(, (code.text fully_qualified_class_name))
+                                     [(,* (list#each field_decl$ fields))]])
                     (,* virtual_methods)
                     (, body))
                 ))))
@@ -1558,7 +1558,7 @@
        return_term))]
 
   [with_return_try #import_member_try? (` (.try (, return_term)))]
-  [with_return_io  #import_member_io?  (` ((,! io.io) (, return_term)))]
+  [with_return_io  #import_member_io?  (` (io.io (, return_term)))]
   )
 
 (with_template [   ]
@@ -1630,7 +1630,7 @@
       (list#each (function (_ [class [maybe? input]])
                    (|> (if maybe?
                          (` (.is (.Primitive (, (code.text (..reflection class))))
-                                 ((,! !!!) (, (..un_quoted input)))))
+                                 (!!! (, (..un_quoted input)))))
                          (..un_quoted input))
                        [class]
                        (with_automatic_input_conversion mode))))))
@@ -1644,7 +1644,7 @@
 (def syntax_inputs
   (-> (List Code) (List Code))
   (|>> (list#each (function (_ name)
-                    (list name (` (,! .any)))))
+                    (list name (` .any))))
        list#conjoint))
 
 (exception .public (cannot_write_to_field [class Text
@@ -1694,8 +1694,8 @@
                                (with_return_try member)
                                (with_return_io member))]]
         (in (list (` (def (, def_name)
-                       ((,! syntax) ((, def_name) [(,* (syntax_inputs (list#each product.right arg_function_inputs)))])
-                        ((,' in) (.list (.` (, jvm_interop))))))))))
+                       (syntax ((, def_name) [(,* (syntax_inputs (list#each product.right arg_function_inputs)))])
+                         ((,' in) (.list (.` (, jvm_interop))))))))))
 
       {#MethodDecl [commons method]}
       (with_symbols [g!obj]
@@ -1749,9 +1749,9 @@
                                         (with_return_try member)
                                         (with_return_io member))))]]
           (in (list (` (def (, def_name)
-                         ((,! syntax) ((, def_name) [(,* (syntax_inputs (list#each product.right arg_function_inputs)))
-                                                     (,* (syntax_inputs object_ast))])
-                          ((,' in) (.list (.` (, jvm_interop)))))))))))
+                         (syntax ((, def_name) [(,* (syntax_inputs (list#each product.right arg_function_inputs)))
+                                                (,* (syntax_inputs object_ast))])
+                           ((,' in) (.list (.` (, jvm_interop)))))))))))
 
       {#FieldAccessDecl fad}
       (do meta.monad
@@ -1764,16 +1764,16 @@
                                        (get_static_field full_name _#import_field_name)
                                        (get_virtual_field full_name _#import_field_name (..un_quoted g!obj)))])
                     getter_body (if _#import_field_maybe?
-                                  (` ((,! ???) (, getter_body)))
+                                  (` (??? (, getter_body)))
                                   getter_body)
                     getter_body (if _#import_field_setter?
-                                  (` ((,! io.io) (, getter_body)))
+                                  (` (io.io (, getter_body)))
                                   getter_body)
                     
                     setter_value (|> [_#import_field_type (..un_quoted g!value)]
                                      (with_automatic_input_conversion _#import_field_mode))
                     setter_value (if _#import_field_maybe?
-                                   (` ((,! !!!) (, setter_value)))
+                                   (` (!!! (, setter_value)))
                                    setter_value)
                     setter_command (if _#import_field_static? "jvm member put static" "jvm member put virtual")
                     g!obj+ (.is (List Code)
@@ -1782,33 +1782,32 @@
                                   (list (..un_quoted g!obj))))
 
                     parser (let [write (if _#import_field_static?
-                                         (` (,! .any))
-                                         (` ((,! <>.and)
-                                             (,! .any)
-                                             (,! .any))))
+                                         (` .any)
+                                         (` (<>.and .any
+                                                    .any)))
                                  read (if _#import_field_static?
-                                        (` (,! .end))
-                                        (` (,! .any)))]
-                             (` ((,! <>.or) (, write) (, read))))
+                                        (` .end)
+                                        (` .any))]
+                             (` (<>.or (, write) (, read))))
                     write (list (if _#import_field_static?
                                   (` {.#Left [(, g!value)]})
                                   (` {.#Left [(, g!value) (, g!obj)]}))
                                 (if _#import_field_setter?
-                                  (` ((,' in) (.list (.` ((,! io.io) ((, (code.text setter_command))
-                                                                      (, (code.text full_name))
-                                                                      (, (code.text _#import_field_name))
-                                                                      (, setter_value)
-                                                                      (,* g!obj+)))))))
-                                  (` ((,! meta.failure) (, (code.text (exception.error ..cannot_write_to_field [full_name _#import_field_name])))))))
+                                  (` ((,' in) (.list (.` (io.io ((, (code.text setter_command))
+                                                                 (, (code.text full_name))
+                                                                 (, (code.text _#import_field_name))
+                                                                 (, setter_value)
+                                                                 (,* g!obj+)))))))
+                                  (` (meta.failure (, (code.text (exception.error ..cannot_write_to_field [full_name _#import_field_name])))))))
                     read (list (if _#import_field_static?
                                  (` {.#Right []})
                                  (` {.#Right [(, g!obj)]}))
                                (` ((,' in) (.list (.` (, getter_body))))))]
                 (list (` (def (, g!name)
-                           ((,! syntax) ((, g!name) [(, write|read) (, parser)])
-                            (case (, write|read)
-                              (,* write)
-                              (,* read))))))))))
+                           (syntax ((, g!name) [(, write|read) (, parser)])
+                             (case (, write|read)
+                               (,* write)
+                               (,* read))))))))))
       )))
 
 (def (member_import$ vars kind class [import_format member])
@@ -1878,7 +1877,7 @@
                       [jvm.double  "jvm array new double"]
                       [jvm.char    "jvm array new char"]))
                 ... else
-                (in (list (` (.as ((,! array.Array) (, (value_type {#ManualPrM} type)))
+                (in (list (` (.as (array.Array (, (value_type {#ManualPrM} type)))
                                   (.is (, (value_type {#ManualPrM} (jvm.array type)))
                                        ("jvm array new object" (, g!size))))))))))))
 
diff --git a/stdlib/source/library/lux/ffi.lux b/stdlib/source/library/lux/ffi.lux
index fdbdde871..92c342750 100644
--- a/stdlib/source/library/lux/ffi.lux
+++ b/stdlib/source/library/lux/ffi.lux
@@ -349,7 +349,7 @@
                  (` (.Either .Text (, :it:)))
                  :it:)]
       (if (the #io? input)
-        (` ((,! io.IO) (, :it:)))
+        (` (io.IO (, :it:)))
         :it:)))
 
   (def (input_term input term)
@@ -358,7 +358,7 @@
                  (` (.try (, term)))
                  term)]
       (if (the #io? input)
-        (` ((,! io.io) (, term)))
+        (` (io.io (, term)))
         term)))
 
   (def (procedure_definition import! source it)
@@ -474,16 +474,16 @@
                    code.local)
           :field: (the #anonymous it)]
       (` (def (, g!it)
-           ((,! syntax) ((, g!it) [])
-            (.at (,! meta.monad) (,' in)
-                 (.list (`' (.exec
-                              (,* import!)
-                              (.as (, (..output_type :field:))
-                                   (, (<| (lux_optional :field:)
-                                          (for @.js (` ( (, (code.text (%.format (..host_path class_name) "." field)))))
-                                               @.ruby (` ( (, (code.text (%.format (..host_path class_name) "::" field)))))
-                                               (` ( (, (code.text field))
-                                                         (, (..imported class_name)))))))))))))))))
+           (syntax ((, g!it) [])
+             (.at meta.monad (,' in)
+                  (.list (`' (.exec
+                               (,* import!)
+                               (.as (, (..output_type :field:))
+                                    (, (<| (lux_optional :field:)
+                                           (for @.js (` ( (, (code.text (%.format (..host_path class_name) "." field)))))
+                                                @.ruby (` ( (, (code.text (%.format (..host_path class_name) "::" field)))))
+                                                (` ( (, (code.text field))
+                                                          (, (..imported class_name)))))))))))))))))
 
   (def (virtual_field_definition [class_name class_parameters] alias namespace it)
     (-> Declaration Alias Namespace (Named Output) Code)
diff --git a/stdlib/source/library/lux/ffi.old.lux b/stdlib/source/library/lux/ffi.old.lux
index e9385c61a..d0a3132c7 100644
--- a/stdlib/source/library/lux/ffi.old.lux
+++ b/stdlib/source/library/lux/ffi.old.lux
@@ -364,7 +364,7 @@
 
     {#GenericArray param}
     (let [=param (class_type' mode type_params #1 param)]
-      (` ((,! array.Array) (, =param))))
+      (` (array.Array (, =param))))
 
     (^.or {#GenericWildcard {.#None}}
           {#GenericWildcard {.#Some [{#LowerBound} _]}})
@@ -1408,7 +1408,7 @@
        return_term))]
 
   [decorate_return_try #import_member_try? (` (.try (, return_term)))]
-  [decorate_return_io  #import_member_io?  (` ((,! io.io) (, return_term)))]
+  [decorate_return_io  #import_member_io?  (` (io.io (, return_term)))]
   )
 
 (def (free_type_param? [name bounds])
@@ -1444,7 +1444,7 @@
   (|> inputs
       (list#each (function (_ [maybe? input])
                    (if maybe?
-                     (` ((,! !!!) (, (un_quote input))))
+                     (` (!!! (, (un_quote input))))
                      (un_quote input))))
       (list.zipped_2 classes)
       (list#each (auto_convert_input mode))))
@@ -1458,7 +1458,7 @@
 (def syntax_inputs
   (-> (List Code) (List Code))
   (|>> (list#each (function (_ name)
-                    (list name (` (,! .any)))))
+                    (list name (` .any))))
        list#conjoint))
 
 (def (member_def_interop type_params kind class [arg_function_inputs arg_classes arg_types] member method_prefix import_format)
@@ -1500,8 +1500,8 @@
                                (decorate_return_try member)
                                (decorate_return_io member))]]
         (in (list (` (def (, def_name)
-                       ((,! syntax) ((, def_name) [(,* (syntax_inputs (list#each product.right arg_function_inputs)))])
-                        ((,' in) (.list (.` (, jvm_interop))))))))))
+                       (syntax ((, def_name) [(,* (syntax_inputs (list#each product.right arg_function_inputs)))])
+                         ((,' in) (.list (.` (, jvm_interop))))))))))
 
       {#MethodDecl [commons method]}
       (with_symbols [g!obj]
@@ -1534,9 +1534,9 @@
                                  (decorate_return_try member)
                                  (decorate_return_io member))]]
           (in (list (` (def (, def_name)
-                         ((,! syntax) ((, def_name) [(,* (syntax_inputs (list#each product.right arg_function_inputs)))
-                                                     (,* (syntax_inputs object_ast))])
-                          ((,' in) (.list (.` (, jvm_interop)))))))))))
+                         (syntax ((, def_name) [(,* (syntax_inputs (list#each product.right arg_function_inputs)))
+                                                (,* (syntax_inputs object_ast))])
+                           ((,' in) (.list (.` (, jvm_interop)))))))))))
 
       {#FieldAccessDecl fad}
       (do meta.monad
@@ -1555,7 +1555,7 @@
          getter_interop (with_symbols [g!obj]
                           (let [getter_call (if #import_field_static?
                                               (` ((, getter_name) []))
-                                              (` ((, getter_name) [(, g!obj) (,! .any)])))
+                                              (` ((, getter_name) [(, g!obj) .any])))
                                 getter_body (<| (auto_convert_output #import_field_mode)
                                                 [(simple_class$ (list) #import_field_type)
                                                  (if #import_field_static?
@@ -1564,25 +1564,25 @@
                                                    (let [jvm_extension (code.text (format "jvm getfield" ":" full_name ":" #import_field_name))]
                                                      (` ((, jvm_extension) (, (un_quote g!obj))))))])
                                 getter_body (if #import_field_maybe?
-                                              (` ((,! ???) (, getter_body)))
+                                              (` (??? (, getter_body)))
                                               getter_body)
                                 getter_body (if #import_field_setter?
-                                              (` ((,! io.io) (, getter_body)))
+                                              (` (io.io (, getter_body)))
                                               getter_body)]
                             (in (` (def (, getter_name)
-                                     ((,! syntax) (, getter_call)
-                                      ((,' in) (.list (.` (, getter_body))))))))))
+                                     (syntax (, getter_call)
+                                       ((,' in) (.list (.` (, getter_body))))))))))
          setter_interop (.is (Meta (List Code))
                              (if #import_field_setter?
                                (with_symbols [g!obj g!value]
                                  (let [setter_call (if #import_field_static?
-                                                     (` ((, setter_name) [(, g!value) (,! .any)]))
-                                                     (` ((, setter_name) [(, g!value) (,! .any)
-                                                                          (, g!obj) (,! .any)])))
+                                                     (` ((, setter_name) [(, g!value) .any]))
+                                                     (` ((, setter_name) [(, g!value) .any
+                                                                          (, g!obj) .any])))
                                        setter_value (auto_convert_input #import_field_mode
                                                                         [(simple_class$ (list) #import_field_type) (un_quote g!value)])
                                        setter_value (if #import_field_maybe?
-                                                      (` ((,! !!!) (, setter_value)))
+                                                      (` (!!! (, setter_value)))
                                                       setter_value)
                                        setter_command (format (if #import_field_static? "jvm putstatic" "jvm putfield")
                                                               ":" full_name ":" #import_field_name)
@@ -1591,8 +1591,8 @@
                                                      (list)
                                                      (list (un_quote g!obj))))]
                                    (in (list (` (def (, setter_name)
-                                                  ((,! syntax) (, setter_call)
-                                                   ((,' in) (.list (.` ((,! io.io) ((, (code.text setter_command)) (,* g!obj+) (, setter_value)))))))))))))
+                                                  (syntax (, setter_call)
+                                                    ((,' in) (.list (.` (io.io ((, (code.text setter_command)) (,* g!obj+) (, setter_value)))))))))))))
                                (in (list))))]
         (in (list.partial getter_interop setter_interop)))
       )))
diff --git a/stdlib/source/library/lux/ffi.php.lux b/stdlib/source/library/lux/ffi.php.lux
index ecc9a836d..d891daf44 100644
--- a/stdlib/source/library/lux/ffi.php.lux
+++ b/stdlib/source/library/lux/ffi.php.lux
@@ -194,18 +194,18 @@
 
     ...                   {.#Left error}
     ...                   (recover_from_failure error)))}
-    (in (list (` ("lux try" ((,! io.io) (, expression))))))))
+    (in (list (` ("lux try" (io.io (, expression))))))))
 
 (def (with_io with? without)
   (-> Bit Code Code)
   (if with?
-    (` ((,! io.io) (, without)))
+    (` (io.io (, without)))
     without))
 
 (def (io_type io? rawT)
   (-> Bit Code Code)
   (if io?
-    (` ((,! io.IO) (, rawT)))
+    (` (io.IO (, rawT)))
     rawT))
 
 (def (with_try with? without_try)
@@ -259,10 +259,10 @@
                                              (let [g!field (qualify (maybe.else field alias))]
                                                (if static?
                                                  (` (def (, g!field)
-                                                      ((,! syntax) ((, g!field) [])
-                                                       (at (,! meta.monad) (,' in)
-                                                           (list (` (.as (, (nullable_type fieldT))
-                                                                         ("php constant" (, (code.text (%.format class "::" field)))))))))))
+                                                      (syntax ((, g!field) [])
+                                                        (at meta.monad (,' in)
+                                                            (list (` (.as (, (nullable_type fieldT))
+                                                                          ("php constant" (, (code.text (%.format class "::" field)))))))))))
                                                  (` (def ((, g!field) (, g!object))
                                                       (-> (, g!type)
                                                           (, (nullable_type fieldT)))
@@ -317,7 +317,7 @@
         (let [imported (` ("php constant" (, (code.text name))))
               g!name (code.local (maybe.else name alias))]
           (in (list (` (def (, g!name)
-                         ((,! syntax) ((, g!name) [])
-                          (at (,! meta.monad) (,' in)
-                              (list (` (.as (, (nullable_type fieldT)) (, imported)))))))))))
+                         (syntax ((, g!name) [])
+                           (at meta.monad (,' in)
+                               (list (` (.as (, (nullable_type fieldT)) (, imported)))))))))))
         ))))
diff --git a/stdlib/source/library/lux/ffi.scm.lux b/stdlib/source/library/lux/ffi.scm.lux
index 602b72ea3..b7ed29d92 100644
--- a/stdlib/source/library/lux/ffi.scm.lux
+++ b/stdlib/source/library/lux/ffi.scm.lux
@@ -159,18 +159,18 @@
 
     ...                   {.#Left error}
     ...                   (recover_from_failure error)))}
-    (in (list (` ("lux try" ((,! io.io) (, expression))))))))
+    (in (list (` ("lux try" (io.io (, expression))))))))
 
 (def (with_io with? without)
   (-> Bit Code Code)
   (if with?
-    (` ((,! io.io) (, without)))
+    (` (io.io (, without)))
     without))
 
 (def (io_type io? rawT)
   (-> Bit Code Code)
   (if io?
-    (` ((,! io.IO) (, rawT)))
+    (` (io.IO (, rawT)))
     rawT))
 
 (def (with_try with? without_try)
@@ -220,7 +220,7 @@
         (let [imported (` ("scheme constant" (, (code.text name))))
               g!name (code.local (maybe.else name alias))]
           (in (list (` (def (, g!name)
-                         ((,! syntax) ((, g!name) [])
-                          (at (,! meta.monad) (,' in)
-                              (list (` (.as (, (nilable_type fieldT)) (, imported)))))))))))
+                         (syntax ((, g!name) [])
+                           (at meta.monad (,' in)
+                               (list (` (.as (, (nilable_type fieldT)) (, imported)))))))))))
         ))))
diff --git a/stdlib/source/library/lux/math/modulus.lux b/stdlib/source/library/lux/math/modulus.lux
index fea4f576f..effc03dd9 100644
--- a/stdlib/source/library/lux/math/modulus.lux
+++ b/stdlib/source/library/lux/math/modulus.lux
@@ -50,4 +50,4 @@
     (meta.lifted
      (do try.monad
        [_ (..modulus divisor)]
-       (in (list (` ((,! try.trusted) (..modulus (, (code.int divisor)))))))))))
+       (in (list (` (try.trusted (..modulus (, (code.int divisor)))))))))))
diff --git a/stdlib/source/library/lux/math/number/ratio.lux b/stdlib/source/library/lux/math/number/ratio.lux
index e521bddf9..b81667def 100644
--- a/stdlib/source/library/lux/math/number/ratio.lux
+++ b/stdlib/source/library/lux/math/number/ratio.lux
@@ -34,7 +34,7 @@
     1 {.#Some (the #numerator value)}
     _ {.#None}))
 
-(def (normal (open "_[0]"))
+(def .public (normal (open "_[0]"))
   (-> Ratio Ratio)
   (let [common (n.gcd _#numerator _#denominator)]
     [..#numerator (n./ common _#numerator)
@@ -43,8 +43,8 @@
 (def .public ratio
   (syntax (_ [numerator .any
               ?denominator (<>.maybe .any)])
-    (in (list (` ((,! ..normal) [..#numerator (, numerator)
-                                 ..#denominator (, (maybe.else (' 1) ?denominator))]))))))
+    (in (list (` (normal [..#numerator (, numerator)
+                          ..#denominator (, (maybe.else (' 1) ?denominator))]))))))
 
 (def .public (= parameter subject)
   (-> Ratio Ratio Bit)
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 [ ]
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 [ ]
             [[_ { value}]
              ( 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 [ (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))
                   
-                  (/.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))
                   
-                  (/.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 (` ( (, name)
                                      (.function ((, g!handler) (, g!name) (, g!phase) (, g!archive) (, g!inputs))
-                                       (.case ((,! )
-                                               ((,! monad.do) (,! <>.monad)
-                                                [(,* inputs)
-                                                 (, g!_) ]
-                                                (.at (,! <>.monad) (,' in) (, body)))
+                                       (.case (
+                                               (monad.do <>.monad
+                                                 [(,* inputs)
+                                                  (, g!_) ]
+                                                 (.at <>.monad (,' in) (, body)))
                                                (, g!inputs))
                                          {.#Right (, g!_)}
                                          (, g!_)
 
                                          {.#Left (, g!error)}
-                                         ((,! phase.failure) (, g!error)))
+                                         (phase.failure (, g!error)))
                                        )))))))))]
 
   [.any .end .and .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 [ (in [var
-                                                                             (` ((,! ..self_documenting) (' (, var))
-                                                                                 (, parser)))])]
+                                                                             (` (..self_documenting (' (, var))
+                                                                                                    (, parser)))])]
                                               (case var
                                                 [_ {.#Symbol ["" _]}]
                                                 
@@ -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 .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 [ [Type Any]]
+  (primitive .public Dynamic
+    
+    
+    (def .public dynamic
+      (syntax (_ [value .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 .any
+                  value .any])
+        (with_symbols [g!type g!value]
+          (in (list (` (.let [[(, g!type) (, g!value)] (|> (, value)
+                                                           (is Dynamic)
+                                                           (as ))]
+                         (.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 .any])
-      (with_symbols [g!value]
-        (in (list (` (.let [(, g!value) (, value)]
-                       ((,! ..abstraction) [(.type_of (, g!value)) (, g!value)]))))))))
-
-  (def .public static
-    (syntax (_ [type .any
-                value .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 .any])
     (with_symbols [g!_ g!type g!output]
       (let [g!name (code.symbol ["" name])]
-        (in (.list (` ((,! syntax) ((, g!_) [(, g!type) (,! .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) .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)] (, ) (, )
-                       (, value))))))))]
+         (in (list (` (//.as [(,* type_vars)] (, ) (, )
+                             (, 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!!)
                                              [ (, g!context)]
                                              [ (, 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 .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 [ ]
   [(def .public 
      (..unit []))
    
-   (.type .public 
-     (, (..type )))]
+   (.def .public 
+     (let [[module _] (symbol .._)
+           [_ short] (symbol )]
+       {.#Named [module short]
+                (..type )}))]
 
   [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 .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 [    ]
   [(def .public 
      (scale [ratio.#numerator 
              ratio.#denominator 1]))
    
-   (.type .public 
-     (, (..type )))
+   (def .public 
+     (let [[module _] (symbol .._)
+           [_ short] (symbol )]
+       {.#Named [module short]
+                (..type )}))
    
    (def .public 
      (scale [ratio.#numerator 1
              ratio.#denominator ]))
    
-   (.type .public 
-     (, (..type )))]
+   (def .public 
+     (let [[module _] (symbol .._)
+           [_ short] (symbol )]
+       {.#Named [module short]
+                (..type )}))]
 
   [        1,000 kilo Kilo milli Milli]
   [    1,000,000 mega Mega micro Micro]
diff --git a/stdlib/source/library/lux/program.lux b/stdlib/source/library/lux/program.lux
index acfe5a74c..794dcbcc8 100644
--- a/stdlib/source/library/lux/program.lux
+++ b/stdlib/source/library/lux/program.lux
@@ -38,10 +38,10 @@
                                            @.js body
                                            @.python body
                                            ... else
-                                           (` ((,! do) (,! io.monad)
-                                               [(, g!output) (, body)
-                                                (, g!_) (,! thread.run!)]
-                                               ((,' in) (, g!output)))))]
+                                           (` (do io.monad
+                                                [(, g!output) (, body)
+                                                 (, g!_) thread.run!]
+                                                ((,' in) (, g!output)))))]
         (in (list (` (is Program
                          (, (case args
                               {#Raw args}
@@ -50,12 +50,12 @@
                               
                               {#Parsed args}
                               (` (.function ((, g!program) (, g!args))
-                                   (case ((,! .result) (.is (,! (.Parser (io.IO .Any)))
-                                                               ((,! do) (,! <>.monad)
-                                                                [(,* args)
-                                                                 (, g!_) (,! .end)]
-                                                                ((,' in) (, initialization+event_loop))))
-                                          (, g!args))
+                                   (case (.result (.is (.Parser (io.IO .Any))
+                                                          (do <>.monad
+                                                            [(,* args)
+                                                             (, g!_) .end]
+                                                            ((,' in) (, initialization+event_loop))))
+                                                     (, g!args))
                                      {.#Right (, g!output)}
                                      (, g!output)
 
diff --git a/stdlib/source/library/lux/test.lux b/stdlib/source/library/lux/test.lux
index e6690c522..5c3b9451e 100644
--- a/stdlib/source/library/lux/test.lux
+++ b/stdlib/source/library/lux/test.lux
@@ -272,7 +272,7 @@
   (%.Format Symbol)
   (|>> %.symbol (format ..clean_up_marker)))
 
-(def (|coverage'| coverage condition)
+(def .public (with_coverage' coverage condition)
   (-> (List Symbol) Bit Assertion)
   (let [message (|> coverage
                     (list#each ..coverage_format)
@@ -283,12 +283,12 @@
                       [(revised #actual_coverage (set.union coverage) tally)
                        documentation])))))
 
-(def (|coverage| coverage condition)
+(def .public (with_coverage coverage condition)
   (-> (List Symbol) Bit Test)
-  (|> (..|coverage'| coverage condition)
+  (|> (..with_coverage' coverage condition)
       random#in))
 
-(def (|for| coverage test)
+(def .public (for' coverage test)
   (-> (List Symbol) Test Test)
   (let [context (|> coverage
                     (list#each ..coverage_format)
@@ -304,7 +304,7 @@
   (code.tuple (list (code.text (symbol.module symbol))
                     (code.text (symbol.short symbol)))))
 
-(def reference
+(def .public reference
   (syntax (_ [name .symbol])
     (do meta.monad
       [_ (meta.export name)]
@@ -338,29 +338,27 @@
      (syntax (_ [coverage (.tuple (<>.many .any))
                  condition .any])
        (let [coverage (list#each (function (_ definition)
-                                   (` ((,! ..reference) (, definition))))
+                                   (` (..reference (, definition))))
                                  coverage)]
-         (in (list (` ((,! )
-                       (is (.List .Symbol)
-                           (.list (,* coverage)))
-                       (, condition))))))))]
+         (in (list (` ( (is (.List .Symbol)
+                                      (.list (,* coverage)))
+                                  (, condition))))))))]
 
-  [coverage' ..|coverage'|]
-  [coverage ..|coverage|]
+  [coverage' ..with_coverage']
+  [coverage ..with_coverage]
   )
 
 (def .public for
   (syntax (_ [coverage (.tuple (<>.many .any))
               test .any])
     (let [coverage (list#each (function (_ definition)
-                                (` ((,! ..reference) (, definition))))
+                                (` (..reference (, definition))))
                               coverage)]
-      (in (list (` ((,! ..|for|)
-                    (is (.List .Symbol)
-                        (.list (,* coverage)))
-                    (, test))))))))
+      (in (list (` (..for' (is (.List .Symbol)
+                               (.list (,* coverage)))
+                           (, test))))))))
 
-(def (covering' module coverage test)
+(def .public (covering' module coverage test)
   (-> Text Text Test Test)
   (let [coverage (..coverage_definitions module coverage)]
     (|> (..context' module test)
@@ -383,10 +381,7 @@
                                         aggregate))
                                     {.#End})
                           ..encoded_coverage)]]
-      (in (list (` ((,! ..covering')
-                    (, (code.text module))
-                    (, (code.text coverage))
-                    (, test))))))))
+      (in (list (` (..covering' (, (code.text module)) (, (code.text coverage)) (, test))))))))
 
 (exception .public (error_during_execution [error Text])
   (exception.report
diff --git a/stdlib/source/polytypic/lux/abstract/equivalence.lux b/stdlib/source/polytypic/lux/abstract/equivalence.lux
index 64c684936..8de4a0a7a 100644
--- a/stdlib/source/polytypic/lux/abstract/equivalence.lux
+++ b/stdlib/source/polytypic/lux/abstract/equivalence.lux
@@ -49,7 +49,7 @@
            inputT .next
            .let [@Equivalence (is (-> Type Code)
                                   (function (_ type)
-                                    (` ((,! /.Equivalence) (, (poly.code *env* type))))))]]
+                                    (` (/.Equivalence (, (poly.code *env* type))))))]]
           (all <>.either
                ... Basic types
                (,, (with_template [ ]
@@ -59,12 +59,12 @@
                                    ))))]
 
                      [(.exactly Any) (function ((, g!_) (, g!_) (, g!_)) #1)]
-                     [(.sub Bit)     (,! bit.equivalence)]
-                     [(.sub Nat)     (,! nat.equivalence)]
-                     [(.sub Int)     (,! int.equivalence)]
-                     [(.sub Rev)     (,! rev.equivalence)]
-                     [(.sub Frac)    (,! frac.equivalence)]
-                     [(.sub Text)    (,! text.equivalence)]))
+                     [(.sub Bit)     bit.equivalence]
+                     [(.sub Nat)     nat.equivalence]
+                     [(.sub Int)     int.equivalence]
+                     [(.sub Rev)     rev.equivalence]
+                     [(.sub Frac)    frac.equivalence]
+                     [(.sub Text)    text.equivalence]))
                ... Composite types
                (,, (with_template [ ]
                      [(do !
@@ -73,13 +73,13 @@
                         (in (` (is (, (@Equivalence inputT))
                                    ( (, argC))))))]
 
-                     [.Maybe            (,! maybe.equivalence)]
-                     [.List             (,! list.equivalence)]
-                     [sequence.Sequence (,! sequence.equivalence)]
-                     [array.Array       (,! array.equivalence)]
-                     [queue.Queue       (,! queue.equivalence)]
-                     [set.Set           (,! set.equivalence)]
-                     [tree.Tree         (,! tree.equivalence)]
+                     [.Maybe            maybe.equivalence]
+                     [.List             list.equivalence]
+                     [sequence.Sequence sequence.equivalence]
+                     [array.Array       array.equivalence]
+                     [queue.Queue       queue.equivalence]
+                     [set.Set           set.equivalence]
+                     [tree.Tree         tree.equivalence]
                      ))
                (do !
                  [[_ _ valC] (.applied (all <>.and
@@ -87,7 +87,7 @@
                                                   .any
                                                   equivalence))]
                  (in (` (is (, (@Equivalence inputT))
-                            ((,! dictionary.equivalence) (, valC))))))
+                            (dictionary.equivalence (, valC))))))
                ... Models
                (,, (with_template [ ]
                      [(do !
@@ -144,8 +144,8 @@
                  [[g!self bodyC] (.recursive equivalence)
                   .let [g!_ (code.local "_____________")]]
                  (in (` (is (, (@Equivalence inputT))
-                            ((,! /.rec) (.function ((, g!_) (, g!self))
-                                          (, bodyC)))))))
+                            (/.rec (.function ((, g!_) (, g!self))
+                                     (, bodyC)))))))
                .recursive_self
                ... Type applications
                (do !
@@ -157,8 +157,8 @@
                (do !
                  [[funcC varsC bodyC] (.polymorphic equivalence)]
                  (in (` (is (All ((, g!_) (,* varsC))
-                              (-> (,* (list#each (|>> (,) ((,! /.Equivalence)) (`)) varsC))
-                                  ((,! /.Equivalence) ((, (poly.code *env* inputT)) (,* varsC)))))
+                              (-> (,* (list#each (|>> (,) (/.Equivalence) (`)) varsC))
+                                  (/.Equivalence ((, (poly.code *env* inputT)) (,* varsC)))))
                             (function ((, funcC) (,* varsC))
                               (, bodyC))))))
                .recursive_call
diff --git a/stdlib/source/polytypic/lux/abstract/functor.lux b/stdlib/source/polytypic/lux/abstract/functor.lux
index 43b8b2902..31a53d407 100644
--- a/stdlib/source/polytypic/lux/abstract/functor.lux
+++ b/stdlib/source/polytypic/lux/abstract/functor.lux
@@ -37,10 +37,10 @@
        .let [@Functor (is (-> Type Code)
                           (function (_ unwrappedT)
                             (if (n.= 1 num_vars)
-                              (` ((,! /.Functor) (, (poly.code *env* unwrappedT))))
+                              (` (/.Functor (, (poly.code *env* unwrappedT))))
                               (let [paramsC (|> num_vars -- list.indices (list#each (|>> %.nat code.local)))]
                                 (` (All ((, g!_) (,* paramsC))
-                                     ((,! /.Functor) ((, (poly.code *env* unwrappedT)) (,* paramsC)))))))))
+                                     (/.Functor ((, (poly.code *env* unwrappedT)) (,* paramsC)))))))))
              Arg (is (-> Code (.Parser Code))
                         (function (Arg valueC)
                           (all <>.either
diff --git a/stdlib/source/polytypic/lux/data/format/json.lux b/stdlib/source/polytypic/lux/data/format/json.lux
index c68d521ce..53eba2b21 100644
--- a/stdlib/source/polytypic/lux/data/format/json.lux
+++ b/stdlib/source/polytypic/lux/data/format/json.lux
@@ -23,11 +23,12 @@
      ["[0]" i64]
      ["[0]" int]
      ["[0]" frac]]]
-   [meta
+   ["[0]" meta (.only)
     ["[0]" code (.only)
      ["<[1]>" \\parser]]
     [macro
-     [syntax (.only syntax)]]
+     [syntax (.only syntax)]
+     ["[0]" expansion]]
     ["[0]" type (.only)
      ["<[1]>" \\parser]
      ["[0]" unit]
@@ -46,7 +47,7 @@
   (-> Nat Frac)
   (|>> .int int.frac))
 
-(def (rec_encoded non_rec)
+(def .public (rec_encoded non_rec)
   (All (_ a) (-> (-> (-> a JSON)
                      (-> a JSON))
                  (-> a JSON)))
@@ -56,7 +57,7 @@
 (def low_mask Nat (|> 1 (i64.left_shifted 32) --))
 (def high_mask Nat (|> low_mask (i64.left_shifted 32)))
 
-(def nat_codec
+(def .public nat_codec
   (codec.Codec JSON Nat)
   (implementation
    (def (encoded input)
@@ -72,7 +73,7 @@
                     (in (n.+ (|> high frac.int .nat (i64.left_shifted 32))
                              (|> low frac.int .nat)))))))))
 
-(def int_codec
+(def .public int_codec
   (codec.Codec JSON Int)
   (implementation
    (def encoded
@@ -81,14 +82,14 @@
      (|>> (at nat_codec decoded) (at try.functor each (|>> .int))))))
 
 ... Builds a JSON generator for potentially inexistent values.
-(def (nullable format)
+(def .public (nullable format)
   (All (_ a) (-> (-> a JSON) (-> (Maybe a) JSON)))
   (function (_ elem)
     (case elem
       {.#None}       {/.#Null}
       {.#Some value} (format value))))
 
-(def measure_codec
+(def .public measure_codec
   (All (_ unit)
     (codec.Codec JSON (unit.Measure unit)))
   (implementation
@@ -111,15 +112,15 @@
 
                  [(.exactly Any) (function ((, g!_) (, (code.symbol ["" "0"]))) {/.#Null})]
                  [(.sub Bit)     (|>> {/.#Boolean})]
-                 [(.sub Nat)     (at (,! ..nat_codec) (,' encoded))]
-                 [(.sub Int)     (at (,! ..int_codec) (,' encoded))]
+                 [(.sub Nat)     (at ..nat_codec (,' encoded))]
+                 [(.sub Int)     (at ..int_codec (,' encoded))]
                  [(.sub Frac)    (|>> {/.#Number})]
                  [(.sub Text)    (|>> {/.#String})])