aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/control
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/library/lux/control/concatenative.lux26
-rw-r--r--stdlib/source/library/lux/control/concurrency/async.lux2
-rw-r--r--stdlib/source/library/lux/control/concurrency/atom.lux2
-rw-r--r--stdlib/source/library/lux/control/concurrency/semaphore.lux2
-rw-r--r--stdlib/source/library/lux/control/continuation.lux2
-rw-r--r--stdlib/source/library/lux/control/exception.lux22
-rw-r--r--stdlib/source/library/lux/control/function/contract.lux14
-rw-r--r--stdlib/source/library/lux/control/function/inline.lux20
-rw-r--r--stdlib/source/library/lux/control/function/mutual.lux72
-rw-r--r--stdlib/source/library/lux/control/io.lux4
-rw-r--r--stdlib/source/library/lux/control/lazy.lux2
-rw-r--r--stdlib/source/library/lux/control/maybe.lux14
-rw-r--r--stdlib/source/library/lux/control/pipe.lux58
-rw-r--r--stdlib/source/library/lux/control/remember.lux6
-rw-r--r--stdlib/source/library/lux/control/security/capability.lux18
-rw-r--r--stdlib/source/library/lux/control/security/policy.lux6
-rw-r--r--stdlib/source/library/lux/control/try.lux20
17 files changed, 145 insertions, 145 deletions
diff --git a/stdlib/source/library/lux/control/concatenative.lux b/stdlib/source/library/lux/control/concatenative.lux
index 795d387cb..ac78d307a 100644
--- a/stdlib/source/library/lux/control/concatenative.lux
+++ b/stdlib/source/library/lux/control/concatenative.lux
@@ -50,7 +50,7 @@
(def (stack_type tops bottom)
(-> (List Code) Code Code)
(list#mix (function (_ top bottom)
- (` [(~ bottom) (~ top)]))
+ (` [(, bottom) (, top)]))
bottom
tops))
@@ -64,11 +64,11 @@
output_stack (stack_type (the #top outputs) output_bottom)]
(in (list (.if (or (same? common_bottom input_bottom)
(same? common_bottom output_bottom))
- (` (All ((~ g!_) (~ common_bottom))
- (-> (~ input_stack)
- (~ output_stack))))
- (` (-> (~ input_stack)
- (~ output_stack))))))))))
+ (` (All ((, g!_) (, common_bottom))
+ (-> (, input_stack)
+ (, output_stack))))
+ (` (-> (, input_stack)
+ (, output_stack))))))))))
(def .public (value it)
(All (_ ,,, a)
@@ -82,15 +82,15 @@
(with_symbols [g!_ g!func g!stack g!output]
(monad.do [! meta.monad]
[g!inputs (|> (macro.symbol "input") (list.repeated arity) (monad.all !))]
- (in (list (` (is (All ((~ g!_) (~+ g!inputs) (~ g!output))
- (-> (-> (~+ g!inputs) (~ g!output))
- (=> [(~+ g!inputs)] [(~ g!output)])))
- (function ((~ g!_) (~ g!func))
- (function ((~ g!_) (~ (stack_type g!inputs g!stack)))
- [(~ g!stack) ((~ g!func) (~+ g!inputs))]))))))))))
+ (in (list (` (is (All ((, g!_) (,* g!inputs) (, g!output))
+ (-> (-> (,* g!inputs) (, g!output))
+ (=> [(,* g!inputs)] [(, g!output)])))
+ (function ((, g!_) (, g!func))
+ (function ((, g!_) (, (stack_type g!inputs g!stack)))
+ [(, g!stack) ((, g!func) (,* g!inputs))]))))))))))
(with_template [<arity>]
- [(`` (def .public (~~ (template.symbol ["apply_" <arity>]))
+ [(`` (def .public (,, (template.symbol ["apply_" <arity>]))
(..apply <arity>)))]
[1] [2] [3] [4]
diff --git a/stdlib/source/library/lux/control/concurrency/async.lux b/stdlib/source/library/lux/control/concurrency/async.lux
index 0098f0f1b..37ab82cbe 100644
--- a/stdlib/source/library/lux/control/concurrency/async.lux
+++ b/stdlib/source/library/lux/control/concurrency/async.lux
@@ -186,7 +186,7 @@
(is [(Async a) (Resolver a)]
(..async [])))]
(`` (exec
- (~~ (with_template [<async>]
+ (,, (with_template [<async>]
[(io.run! (upon! resolve <async>))]
[left]
diff --git a/stdlib/source/library/lux/control/concurrency/atom.lux b/stdlib/source/library/lux/control/concurrency/atom.lux
index 3c81d2841..4ba43632f 100644
--- a/stdlib/source/library/lux/control/concurrency/atom.lux
+++ b/stdlib/source/library/lux/control/concurrency/atom.lux
@@ -58,7 +58,7 @@
(All (_ r w) (-> r w (Atom' r w) (IO Bit)))
(io.io (for @.old (ffi.of_boolean
(java/util/concurrent/atomic/AtomicReference::compareAndSet (variance.write
- (`` (as (~~ (type_of new))
+ (`` (as (,, (type_of new))
current)))
(variance.write new)
(representation atom)))
diff --git a/stdlib/source/library/lux/control/concurrency/semaphore.lux b/stdlib/source/library/lux/control/concurrency/semaphore.lux
index 2b6b0692f..d9ba28ef1 100644
--- a/stdlib/source/library/lux/control/concurrency/semaphore.lux
+++ b/stdlib/source/library/lux/control/concurrency/semaphore.lux
@@ -123,7 +123,7 @@
(refinement.refiner (n.> 0)))
(type .public Limit
- (~ (refinement.type limit)))
+ (, (refinement.type limit)))
(primitive .public Barrier
(Record
diff --git a/stdlib/source/library/lux/control/continuation.lux b/stdlib/source/library/lux/control/continuation.lux
index 8a398b377..756804d7d 100644
--- a/stdlib/source/library/lux/control/continuation.lux
+++ b/stdlib/source/library/lux/control/continuation.lux
@@ -36,7 +36,7 @@
(def .public pending
(syntax (_ [expr <code>.any])
(with_symbols [g!_ g!k]
- (in (list (` (.function ((~ g!_) (~ g!k)) ((~ g!k) (~ expr)))))))))
+ (in (list (` (.function ((, g!_) (, g!k)) ((, g!k) (, expr)))))))))
(def .public (reset scope)
(All (_ i o) (-> (Cont i i) (Cont i o)))
diff --git a/stdlib/source/library/lux/control/exception.lux b/stdlib/source/library/lux/control/exception.lux
index 073db8397..cf9c51105 100644
--- a/stdlib/source/library/lux/control/exception.lux
+++ b/stdlib/source/library/lux/control/exception.lux
@@ -96,15 +96,15 @@
[current_module meta.current_module_name
.let [descriptor (all text#composite "{" current_module "." name "}" text.new_line)
g!self (code.local name)]]
- (in (list (` (def (~ export_policy)
- (~ g!self)
- (All ((~ g!_) (~+ (list#each |type_variable|.format t_vars)))
- (..Exception [(~+ (list#each (the |input|.#type) inputs))]))
- (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))))])))))))))
+ (in (list (` (def (, export_policy)
+ (, g!self)
+ (All ((, g!_) (,* (list#each |type_variable|.format t_vars)))
+ (..Exception [(,* (list#each (the |input|.#type) inputs))]))
+ (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))))])))))))))
(def (report' entries)
(-> (List [Text Text]) Text)
@@ -139,9 +139,9 @@
(def .public report
(syntax (_ [entries (<>.many (<>.and <code>.any <code>.any))])
- (in (list (` ((~! ..report') (list (~+ (|> entries
+ (in (list (` ((,! ..report') (list (,* (|> entries
(list#each (function (_ [header message])
- (` [(~ header) (~ message)]))))))))))))
+ (` [(, header) (, message)]))))))))))))
(def .public (listing format entries)
(All (_ a)
diff --git a/stdlib/source/library/lux/control/function/contract.lux b/stdlib/source/library/lux/control/function/contract.lux
index bb6ef6731..7b093341f 100644
--- a/stdlib/source/library/lux/control/function/contract.lux
+++ b/stdlib/source/library/lux/control/function/contract.lux
@@ -34,16 +34,16 @@
(syntax (_ [test <code>.any
expr <code>.any])
(in (list (` (exec
- ((~! ..assert!) (~ (code.text (exception.error ..pre_condition_failed test)))
- (~ test))
- (~ expr)))))))
+ ((,! ..assert!) (, (code.text (exception.error ..pre_condition_failed test)))
+ (, test))
+ (, expr)))))))
(def .public post
(syntax (_ [test <code>.any
expr <code>.any])
(with_symbols [g!output]
- (in (list (` (let [(~ g!output) (~ expr)]
+ (in (list (` (let [(, g!output) (, expr)]
(exec
- ((~! ..assert!) (~ (code.text (exception.error ..post_condition_failed test)))
- ((~ test) (~ g!output)))
- (~ 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 0564edc3d..135674144 100644
--- a/stdlib/source/library/lux/control/function/inline.lux
+++ b/stdlib/source/library/lux/control/function/inline.lux
@@ -36,17 +36,17 @@
(list.repeated (list.size parameters))
(monad.all !))
.let [inlined (` (("lux in-module"
- (~ (code.text @))
- (.is (~ type)
- (.function ((~ (code.local name)) (~+ parameters))
- (~ term))))
- (~+ (list#each (function (_ g!parameter)
- (` ((~' ~) (~ g!parameter))))
+ (, (code.text @))
+ (.is (, type)
+ (.function ((, (code.local name)) (,* parameters))
+ (, term))))
+ (,* (list#each (function (_ g!parameter)
+ (` ((,' ,) (, g!parameter))))
g!parameters))))
g!parameters (|> g!parameters
(list#each (function (_ parameter)
- (list parameter (` (~! <code>.any)))))
+ (list parameter (` (,! <code>.any)))))
list#conjoint)]]
- (in (list (` (def (~ privacy) (~ (code.local name))
- ((~! syntax) ((~ (code.local name)) [(~+ g!parameters)])
- (.at (~! meta.monad) (~' in) (.list (.`' (~ inlined))))))))))))
+ (in (list (` (def (, privacy) (, (code.local name))
+ ((,! syntax) ((, (code.local name)) [(,* g!parameters)])
+ (.at (,! meta.monad) (,' in) (.list (.`' (, inlined))))))))))))
diff --git a/stdlib/source/library/lux/control/function/mutual.lux b/stdlib/source/library/lux/control/function/mutual.lux
index f00643060..0dcf766f5 100644
--- a/stdlib/source/library/lux/control/function/mutual.lux
+++ b/stdlib/source/library/lux/control/function/mutual.lux
@@ -37,17 +37,17 @@
(.def (mutual_definition context g!context [g!name mutual])
(-> (List Code) Code [Code Mutual] Code)
- (` (function ((~ g!name) (~ g!context))
- (.let [[(~+ context)] (~ g!context)]
- (function (~ (declaration.format (the #declaration mutual)))
- (~ (the #body mutual)))))))
+ (` (function ((, g!name) (, g!context))
+ (.let [[(,* context)] (, g!context)]
+ (function (, (declaration.format (the #declaration mutual)))
+ (, (the #body mutual)))))))
(.def (macro g!context g!self)
(-> Code Code Macro)
(<| (as Macro)
(is Macro')
(function (_ parameters)
- (at meta.monad in (list (` (((~ g!self) (~ g!context)) (~+ parameters))))))))
+ (at meta.monad in (list (` (((, g!self) (, g!context)) (,* parameters))))))))
(.def .public let
(syntax (_ [functions (<code>.tuple (<>.some ..mutual))
@@ -58,10 +58,10 @@
{.#Item mutual {.#End}}
(.let [g!name (|> mutual (the [#declaration declaration.#name]) code.local)]
- (in (list (` (.let [(~ g!name) (is (~ (the #type mutual))
- (function (~ (declaration.format (the #declaration mutual)))
- (~ (the #body mutual))))]
- (~ body))))))
+ (in (list (` (.let [(, g!name) (is (, (the #type mutual))
+ (function (, (declaration.format (the #declaration mutual)))
+ (, (the #body mutual))))]
+ (, body))))))
_
(macro.with_symbols [g!context g!output]
@@ -73,7 +73,7 @@
(list.zipped_2 hidden_names
functions))
context_types (list#each (function (_ mutual)
- (` (-> (~ g!context) (~ (the #type mutual)))))
+ (` (-> (, g!context) (, (the #type mutual)))))
functions)
user_names (list#each (|>> (the [#declaration declaration.#name]) code.local)
functions)]
@@ -82,16 +82,16 @@
(..macro g!context g!name)])
(list.zipped_2 hidden_names
functions)))]
- (in (list (` (.let [(~ g!context) (is (Rec (~ g!context)
- [(~+ context_types)])
- [(~+ definitions)])
- [(~+ user_names)] (.let [[(~+ user_names)] (~ g!context)]
- [(~+ (list#each (function (_ g!name)
- (` ((~ g!name) (~ g!context))))
+ (in (list (` (.let [(, g!context) (is (Rec (, g!context)
+ [(,* context_types)])
+ [(,* definitions)])
+ [(,* user_names)] (.let [[(,* user_names)] (, g!context)]
+ [(,* (list#each (function (_ g!name)
+ (` ((, g!name) (, g!context))))
user_names))])
- (~ g!output) (~ body)]
- (exec (~ g!pop)
- (~ g!output)))))))))))
+ (, g!output) (, body)]
+ (exec (, g!pop)
+ (, g!output)))))))))))
(type Definition
(Record
@@ -112,9 +112,9 @@
{.#Item definition {.#End}}
(.let [(open "_[0]") definition
(open "_[0]") _#mutual]
- (in (list (` (.def (~ _#export_policy) (~ (declaration.format _#declaration))
- (~ _#type)
- (~ _#body))))))
+ (in (list (` (.def (, _#export_policy) (, (declaration.format _#declaration))
+ (, _#type)
+ (, _#body))))))
_
(macro.with_symbols [g!context g!output]
@@ -126,7 +126,7 @@
(list.zipped_2 hidden_names
(list#each (the #mutual) functions)))
context_types (list#each (function (_ mutual)
- (` (-> (~ g!context) (~ (the [#mutual #type] mutual)))))
+ (` (-> (, g!context) (, (the [#mutual #type] mutual)))))
functions)
user_names (list#each (|>> (the [#mutual #declaration declaration.#name]) code.local)
functions)]
@@ -135,22 +135,22 @@
(..macro g!context g!name)])
(list.zipped_2 hidden_names
functions)))]
- (in (list.partial (` (.def (~ g!context)
- [(~+ (list#each (the [#mutual #type]) functions))]
- (.let [(~ g!context) (is (Rec (~ g!context)
- [(~+ context_types)])
- [(~+ definitions)])
- [(~+ user_names)] (~ g!context)]
- [(~+ (list#each (function (_ g!name)
- (` ((~ g!name) (~ g!context))))
+ (in (list.partial (` (.def (, g!context)
+ [(,* (list#each (the [#mutual #type]) functions))]
+ (.let [(, g!context) (is (Rec (, g!context)
+ [(,* context_types)])
+ [(,* definitions)])
+ [(,* user_names)] (, g!context)]
+ [(,* (list#each (function (_ g!name)
+ (` ((, g!name) (, g!context))))
user_names))])))
g!pop
(list#each (function (_ mutual)
(.let [g!name (|> mutual (the [#mutual #declaration declaration.#name]) code.local)]
(` (.def
- (~ (the #export_policy mutual))
- (~ g!name)
- (~ (the [#mutual #type] mutual))
- (.let [[(~+ user_names)] (~ g!context)]
- (~ g!name))))))
+ (, (the #export_policy mutual))
+ (, g!name)
+ (, (the [#mutual #type] mutual))
+ (.let [[(,* user_names)] (, g!context)]
+ (, g!name))))))
functions))))))))
diff --git a/stdlib/source/library/lux/control/io.lux b/stdlib/source/library/lux/control/io.lux
index bd0e441e2..318c96682 100644
--- a/stdlib/source/library/lux/control/io.lux
+++ b/stdlib/source/library/lux/control/io.lux
@@ -36,8 +36,8 @@
(def .public io
(syntax (_ [computation <code>.any])
(with_symbols [g!func g!arg]
- (in (list (` ((~! ..label) (function ((~ g!func) (~ g!arg))
- (~ computation)))))))))
+ (in (list (` ((,! ..label) (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 857fdccff..b280b48e0 100644
--- a/stdlib/source/library/lux/control/lazy.lux
+++ b/stdlib/source/library/lux/control/lazy.lux
@@ -46,7 +46,7 @@
(def .public lazy
(syntax (_ [expression <code>.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/maybe.lux b/stdlib/source/library/lux/control/maybe.lux
index e703c718f..15daadb8b 100644
--- a/stdlib/source/library/lux/control/maybe.lux
+++ b/stdlib/source/library/lux/control/maybe.lux
@@ -130,13 +130,13 @@
(case tokens
(pattern (.list else maybe))
(let [g!temp (is Code [location.dummy {.#Symbol ["" ""]}])]
- {.#Right [state (.list (` (.case (~ maybe)
- {.#Some (~ g!temp)}
- (~ g!temp)
+ {.#Right [state (.list (` (.case (, maybe)
+ {.#Some (, g!temp)}
+ (, g!temp)
... {.#None}
- (~ g!temp)
- (~ else))))]})
+ (, g!temp)
+ (, else))))]})
_
{.#Left "Wrong syntax for 'else'"})))
@@ -159,8 +159,8 @@
(macro (_ tokens state)
(case tokens
(pattern (.list test then))
- {.#Right [state (.list (` (.if (~ test)
- (~ then)
+ {.#Right [state (.list (` (.if (, test)
+ (, then)
{.#None})))]}
_
diff --git a/stdlib/source/library/lux/control/pipe.lux b/stdlib/source/library/lux/control/pipe.lux
index cdd6589b8..b16b4a167 100644
--- a/stdlib/source/library/lux/control/pipe.lux
+++ b/stdlib/source/library/lux/control/pipe.lux
@@ -28,14 +28,14 @@
(syntax (_ [start <code>.any
body ..body
prev <code>.any])
- (in (list (` (|> (~ start) (~+ body)))))))
+ (in (list (` (|> (, start) (,* body)))))))
(def .public let
(syntax (_ [binding <code>.any
body <code>.any
prev <code>.any])
- (in (list (` (.let [(~ binding) (~ prev)]
- (~ body)))))))
+ (in (list (` (.let [(, binding) (, prev)]
+ (, body)))))))
(def _reversed_
(Parser Any)
@@ -49,39 +49,39 @@
_ _reversed_
branches (<>.some (<>.and ..body ..body))])
(with_symbols [g!temp]
- (in (list (` (.let [(~ g!temp) (~ prev)]
- (.cond (~+ (monad.do list.monad
+ (in (list (` (.let [(, g!temp) (, prev)]
+ (.cond (,* (monad.do list.monad
[[test then] branches]
- (list (` (|> (~ g!temp) (~+ test)))
- (` (|> (~ g!temp) (~+ then))))))
- (|> (~ g!temp) (~+ else))))))))))
+ (list (` (|> (, g!temp) (,* test)))
+ (` (|> (, g!temp) (,* then))))))
+ (|> (, g!temp) (,* else))))))))))
(def .public if
(syntax (_ [test ..body
then ..body
else ..body
prev <code>.any])
- (in (list (` (..cond [(~+ test)] [(~+ then)]
- [(~+ else)]
- (~ prev)))))))
+ (in (list (` (..cond [(,* test)] [(,* then)]
+ [(,* else)]
+ (, prev)))))))
(def .public when
(syntax (_ [test ..body
then ..body
prev <code>.any])
- (in (list (` (..cond [(~+ test)] [(~+ then)]
+ (in (list (` (..cond [(,* test)] [(,* then)]
[]
- (~ prev)))))))
+ (, prev)))))))
(def .public while
(syntax (_ [test ..body
then ..body
prev <code>.any])
(with_symbols [g!temp g!again]
- (in (list (` (.loop ((~ g!again) [(~ g!temp) (~ prev)])
- (.if (|> (~ g!temp) (~+ test))
- ((~ g!again) (|> (~ g!temp) (~+ then)))
- (~ g!temp)))))))))
+ (in (list (` (.loop ((, g!again) [(, g!temp) (, prev)])
+ (.if (|> (, g!temp) (,* test))
+ ((, g!again) (|> (, g!temp) (,* then)))
+ (, g!temp)))))))))
(def .public do
(syntax (_ [monad <code>.any
@@ -92,11 +92,11 @@
(pattern (list.partial last_step prev_steps))
(.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)))))))
+ (list g!temp (` (|> (, g!temp) (,* step)))))]
+ (in (list (` ((,! monad.do) (, monad)
+ [.let [(, g!temp) (, prev)]
+ (,* step_bindings)]
+ (|> (, g!temp) (,* last_step)))))))
_
(in (list prev))))))
@@ -105,22 +105,22 @@
(syntax (_ [body ..body
prev <code>.any])
(with_symbols [g!temp]
- (in (list (` (.let [(~ g!temp) (~ prev)]
- (.exec (|> (~ g!temp) (~+ body))
- (~ g!temp)))))))))
+ (in (list (` (.let [(, g!temp) (, prev)]
+ (.exec (|> (, g!temp) (,* body))
+ (, g!temp)))))))))
(def .public tuple
(syntax (_ [paths (<>.many ..body)
prev <code>.any])
(with_symbols [g!temp]
- (in (list (` (.let [(~ g!temp) (~ prev)]
- [(~+ (list#each (function (_ body) (` (|> (~ g!temp) (~+ body))))
+ (in (list (` (.let [(, g!temp) (, prev)]
+ [(,* (list#each (function (_ body) (` (|> (, g!temp) (,* body))))
paths))])))))))
(def .public case
(syntax (_ [branches (<>.many (<>.and <code>.any <code>.any))
prev <code>.any])
- (in (list (` (.case (~ prev)
- (~+ (|> branches
+ (in (list (` (.case (, prev)
+ (,* (|> branches
(list#each (function (_ [pattern body]) (list pattern body)))
list#conjoint))))))))
diff --git a/stdlib/source/library/lux/control/remember.lux b/stdlib/source/library/lux/control/remember.lux
index 227a7bd4b..5165e2800 100644
--- a/stdlib/source/library/lux/control/remember.lux
+++ b/stdlib/source/library/lux/control/remember.lux
@@ -70,9 +70,9 @@
(syntax (_ [deadline ..deadline
message <code>.text
focus (<>.maybe <code>.any)])
- (in (list (` (..remember (~ (code.text (%.date deadline)))
- (~ (code.text (format <message> " " message)))
- (~+ (case focus
+ (in (list (` (..remember (, (code.text (%.date deadline)))
+ (, (code.text (format <message> " " message)))
+ (,* (case focus
{.#Some focus}
(list focus)
diff --git a/stdlib/source/library/lux/control/security/capability.lux b/stdlib/source/library/lux/control/security/capability.lux
index 2a8627855..1a2cb4ed3 100644
--- a/stdlib/source/library/lux/control/security/capability.lux
+++ b/stdlib/source/library/lux/control/security/capability.lux
@@ -52,15 +52,15 @@
.let [[name vars] declaration]
g!brand (at ! each (|>> %.code code.text)
(macro.symbol (format (%.symbol [this_module name]))))
- .let [capability (` (..Capability (.Primitive (~ g!brand)) (~ input) (~ output)))]]
- (in (list (` (type (~ export_policy)
- (~ (|declaration|.format declaration))
- (~ capability)))
- (` (def (~ (code.local forger))
- (All ((~ g!_) (~+ (list#each code.local vars)))
- (-> (-> (~ input) (~ output))
- (~ capability)))
- (~! ..capability)))
+ .let [capability (` (..Capability (.Primitive (, g!brand)) (, input) (, output)))]]
+ (in (list (` (type (, export_policy)
+ (, (|declaration|.format declaration))
+ (, capability)))
+ (` (def (, (code.local forger))
+ (All ((, g!_) (,* (list#each code.local vars)))
+ (-> (-> (, input) (, output))
+ (, capability)))
+ (,! ..capability)))
))))))
(def .public (async capability)
diff --git a/stdlib/source/library/lux/control/security/policy.lux b/stdlib/source/library/lux/control/security/policy.lux
index 2aa55af59..58c895a05 100644
--- a/stdlib/source/library/lux/control/security/policy.lux
+++ b/stdlib/source/library/lux/control/security/policy.lux
@@ -56,13 +56,13 @@
(constructor (All (_ value) (Policy brand value label))))))
(def .public functor
- (~ (..of_policy Functor))
+ (, (..of_policy Functor))
(implementation
(def (each f fa)
(|> fa representation f abstraction))))
(def .public apply
- (~ (..of_policy Apply))
+ (, (..of_policy Apply))
(implementation
(def functor ..functor)
@@ -70,7 +70,7 @@
(abstraction ((representation ff) (representation fa))))))
(def .public monad
- (~ (..of_policy Monad))
+ (, (..of_policy Monad))
(implementation
(def functor ..functor)
(def in (|>> abstraction))
diff --git a/stdlib/source/library/lux/control/try.lux b/stdlib/source/library/lux/control/try.lux
index 794b00f7c..2e86903c7 100644
--- a/stdlib/source/library/lux/control/try.lux
+++ b/stdlib/source/library/lux/control/try.lux
@@ -135,20 +135,20 @@
{#Success value}
{.#None}
- {#Failure (`` (("lux in-module" (~~ (static .prelude)) .symbol#encoded)
+ {#Failure (`` (("lux in-module" (,, (static .prelude)) .symbol#encoded)
(symbol ..of_maybe)))}))
(def .public else
(macro (_ tokens compiler)
(case tokens
(pattern (list else try))
- {#Success [compiler (list (` (case (~ try)
- {..#Success (~' g!temp)}
- (~' g!temp)
+ {#Success [compiler (list (` (case (, try)
+ {..#Success (,' g!temp)}
+ (,' g!temp)
- ... {..#Failure (~' g!temp)}
- (~' g!temp)
- (~ else))))]}
+ ... {..#Failure (,' g!temp)}
+ (,' g!temp)
+ (, else))))]}
_
{#Failure "Wrong syntax for 'else'"})))
@@ -159,9 +159,9 @@
(pattern (.list test then))
(let [code#encoded ("lux in-module" "library/lux" .code#encoded)
text$ ("lux in-module" "library/lux" .text$)]
- {.#Right [state (.list (` (.if (~ test)
- (~ then)
- {..#Failure (~ (text$ (all "lux text concat"
+ {.#Right [state (.list (` (.if (, test)
+ (, then)
+ {..#Failure (, (text$ (all "lux text concat"
"[" (code#encoded (` .when)) "]"
" " "Invalid condition:")))})))]})