aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/control
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/control/concatenative.lux6
-rw-r--r--stdlib/source/lux/control/concurrency/actor.lux10
-rw-r--r--stdlib/source/lux/control/concurrency/frp.lux12
-rw-r--r--stdlib/source/lux/control/concurrency/process.lux2
-rw-r--r--stdlib/source/lux/control/concurrency/promise.lux2
-rw-r--r--stdlib/source/lux/control/concurrency/semaphore.lux2
-rw-r--r--stdlib/source/lux/control/concurrency/stm.lux8
-rw-r--r--stdlib/source/lux/control/exception.lux2
-rw-r--r--stdlib/source/lux/control/function/memo.lux2
-rw-r--r--stdlib/source/lux/control/parser.lux2
-rw-r--r--stdlib/source/lux/control/parser/binary.lux2
-rw-r--r--stdlib/source/lux/control/parser/type.lux6
-rw-r--r--stdlib/source/lux/control/region.lux2
-rw-r--r--stdlib/source/lux/control/security/capability.lux2
-rw-r--r--stdlib/source/lux/control/state.lux2
15 files changed, 31 insertions, 31 deletions
diff --git a/stdlib/source/lux/control/concatenative.lux b/stdlib/source/lux/control/concatenative.lux
index 0b6786c23..48c7cf2eb 100644
--- a/stdlib/source/lux/control/concatenative.lux
+++ b/stdlib/source/lux/control/concatenative.lux
@@ -77,7 +77,7 @@
(case [(|> inputs (get@ #bottom) (maybe@map (|>> code.nat (~) #.Parameter (`))))
(|> outputs (get@ #bottom) (maybe@map (|>> code.nat (~) #.Parameter (`))))]
[(#.Some bottomI) (#.Some bottomO)]
- (monad.do @
+ (monad.do macro.monad
[inputC (singleton (macro.expand-all (stack-fold (get@ #top inputs) bottomI)))
outputC (singleton (macro.expand-all (stack-fold (get@ #top outputs) bottomO)))]
(wrap (list (` (-> (~ (de-alias inputC))
@@ -85,7 +85,7 @@
[?bottomI ?bottomO]
(with-gensyms [g!stack]
- (monad.do @
+ (monad.do macro.monad
[inputC (singleton (macro.expand-all (stack-fold (get@ #top inputs) (maybe.default g!stack ?bottomI))))
outputC (singleton (macro.expand-all (stack-fold (get@ #top outputs) (maybe.default g!stack ?bottomO))))]
(wrap (list (` (All [(~ g!stack)]
@@ -115,7 +115,7 @@
(syntax: #export (apply {arity (|> <c>.nat (<>.filter (n.> 0)))})
(with-gensyms [g! g!func g!stack g!output]
- (monad.do @
+ (monad.do {@ macro.monad}
[g!inputs (|> (macro.gensym "input") (list.repeat arity) (monad.seq @))]
(wrap (list (` (: (All [(~+ g!inputs) (~ g!output)]
(-> (-> (~+ g!inputs) (~ g!output))
diff --git a/stdlib/source/lux/control/concurrency/actor.lux b/stdlib/source/lux/control/concurrency/actor.lux
index 0f38c4c3d..a790fa89c 100644
--- a/stdlib/source/lux/control/concurrency/actor.lux
+++ b/stdlib/source/lux/control/concurrency/actor.lux
@@ -51,7 +51,7 @@
[(Promise [a Mailbox])
(Resolver [a Mailbox])])
(IO (List a))))
- (do io.monad
+ (do {@ io.monad}
[current (promise.poll read)]
(case current
(#.Some [head tail])
@@ -97,7 +97,7 @@
(promise.promise []))
process (loop [state init
[|mailbox| _] (io.run (atom.read (get@ #mailbox (:representation self))))]
- (do promise.monad
+ (do {@ promise.monad}
[[head tail] |mailbox|
?state' (handle head state self)]
(case ?state'
@@ -135,7 +135,7 @@
(def: #export (send message actor)
{#.doc "Communicate with an actor through message passing."}
(All [s] (-> (Message s) (Actor s) (IO Bit)))
- (do io.monad
+ (do {@ io.monad}
[alive? (..alive? actor)]
(if alive?
(let [entry [message (promise.promise [])]]
@@ -266,7 +266,7 @@
#let [_ (log! "AFTER")]]
(wrap output)))))}
(with-gensyms [g!_ g!init]
- (do @
+ (do macro.monad
[module macro.current-module-name
#let [g!type (code.local-identifier (state-name _name))
g!behavior (code.local-identifier (behavior-name _name))
@@ -356,7 +356,7 @@
(let [state' (#.Cons value state)]
(promise.resolved (#try.Success [state' state'])))))}
(with-gensyms [g!_ g!return g!error g!task g!sent? g!resolve]
- (do @
+ (do macro.monad
[current-module macro.current-module-name
actor-name (resolve-actor actor-name)
#let [message-name [current-module (get@ #name signature)]
diff --git a/stdlib/source/lux/control/concurrency/frp.lux b/stdlib/source/lux/control/concurrency/frp.lux
index 17ae28f41..2850f454f 100644
--- a/stdlib/source/lux/control/concurrency/frp.lux
+++ b/stdlib/source/lux/control/concurrency/frp.lux
@@ -40,7 +40,7 @@
(structure
(def: close
(loop [_ []]
- (do io.monad
+ (do {@ io.monad}
[current (atom.read sink)
stopped? (current #.None)]
(if stopped?
@@ -57,7 +57,7 @@
(def: (feed value)
(loop [_ []]
- (do io.monad
+ (do {@ io.monad}
[current (atom.read sink)
#let [[next resolve-next] (:share [a]
{(promise.Resolver (Maybe [a (Channel a)]))
@@ -124,7 +124,7 @@
(let [[output sink] (channel [])]
(exec (: (Promise Any)
(loop [mma mma]
- (do promise.monad
+ (do {@ promise.monad}
[?mma mma]
(case ?mma
(#.Some [ma mma'])
@@ -185,7 +185,7 @@
(All [a b]
(-> (-> b a (Promise a)) a (Channel b)
(Promise a)))
- (do promise.monad
+ (do {@ promise.monad}
[cons channel]
(case cons
#.None
@@ -201,7 +201,7 @@
(All [a b]
(-> (-> b a (Promise a)) a (Channel b)
(Channel a)))
- (do promise.monad
+ (do {@ promise.monad}
[cons channel]
(case cons
#.None
@@ -265,7 +265,7 @@
(def: #export (consume channel)
{#.doc "Reads the entirety of a channel's content and returns it as a list."}
(All [a] (-> (Channel a) (Promise (List a))))
- (do promise.monad
+ (do {@ promise.monad}
[cons channel]
(case cons
(#.Some [head tail])
diff --git a/stdlib/source/lux/control/concurrency/process.lux b/stdlib/source/lux/control/concurrency/process.lux
index d31edfb59..2060233e3 100644
--- a/stdlib/source/lux/control/concurrency/process.lux
+++ b/stdlib/source/lux/control/concurrency/process.lux
@@ -132,7 +132,7 @@
(def: #export run!
(IO Any)
(loop [_ []]
- (do io.monad
+ (do {@ io.monad}
[processes (atom.read runner)]
(case processes
## And... we're done!
diff --git a/stdlib/source/lux/control/concurrency/promise.lux b/stdlib/source/lux/control/concurrency/promise.lux
index def999622..a0461e2c1 100644
--- a/stdlib/source/lux/control/concurrency/promise.lux
+++ b/stdlib/source/lux/control/concurrency/promise.lux
@@ -28,7 +28,7 @@
(All [a] (-> (Promise a) (Resolver a)))
(function (resolve value)
(let [promise (:representation promise)]
- (do io.monad
+ (do {@ io.monad}
[(^@ old [_value _observers]) (atom.read promise)]
(case _value
(#.Some _)
diff --git a/stdlib/source/lux/control/concurrency/semaphore.lux b/stdlib/source/lux/control/concurrency/semaphore.lux
index 39bac32a1..c69859138 100644
--- a/stdlib/source/lux/control/concurrency/semaphore.lux
+++ b/stdlib/source/lux/control/concurrency/semaphore.lux
@@ -76,7 +76,7 @@
(let [semaphore (:representation semaphore)]
(promise.future
(loop [_ []]
- (do io.monad
+ (do {@ io.monad}
[state (atom.read semaphore)
#let [[?sink state' maxed-out?] (: [(Maybe (Resolver Any)) State Bit]
(case (queue.peek (get@ #waiting-list state))
diff --git a/stdlib/source/lux/control/concurrency/stm.lux b/stdlib/source/lux/control/concurrency/stm.lux
index 3065d8033..3c4c26f59 100644
--- a/stdlib/source/lux/control/concurrency/stm.lux
+++ b/stdlib/source/lux/control/concurrency/stm.lux
@@ -46,7 +46,7 @@
(def: (write! new-value var)
(All [a] (-> a (Var a) (IO Any)))
- (do io.monad
+ (do {@ io.monad}
[#let [var' (:representation var)]
(^@ old [old-value observers]) (atom.read var')
succeeded? (atom.compare-and-swap old [new-value observers] var')]
@@ -216,7 +216,7 @@
(def: (issue-commit commit)
(All [a] (-> (Commit a) (IO Any)))
(let [entry [commit (promise.promise [])]]
- (do io.monad
+ (do {@ io.monad}
[|commits|&resolve (atom.read pending-commits)]
(loop [[|commits| resolve] |commits|&resolve]
(do @
@@ -237,14 +237,14 @@
(let [[stm-proc output resolve] commit
[finished-tx value] (stm-proc fresh-tx)]
(if (can-commit? finished-tx)
- (do io.monad
+ (do {@ io.monad}
[_ (monad.map @ commit-var! finished-tx)]
(resolve value))
(issue-commit commit))))
(def: init-processor!
(IO Any)
- (do io.monad
+ (do {@ io.monad}
[flag (atom.read commit-processor-flag)]
(if flag
(wrap [])
diff --git a/stdlib/source/lux/control/exception.lux b/stdlib/source/lux/control/exception.lux
index 211976aa2..8cc4dfe94 100644
--- a/stdlib/source/lux/control/exception.lux
+++ b/stdlib/source/lux/control/exception.lux
@@ -97,7 +97,7 @@
(exception: #export [optional type variables] (some-exception {optional Text} {arguments Int})
optional-body))}
(macro.with-gensyms [g!descriptor]
- (do @
+ (do macro.monad
[current-module macro.current-module-name
#let [descriptor ($_ text@compose "{" current-module "." name "}" text.new-line)
g!self (code.local-identifier name)]]
diff --git a/stdlib/source/lux/control/function/memo.lux b/stdlib/source/lux/control/function/memo.lux
index 253506508..fb6456699 100644
--- a/stdlib/source/lux/control/function/memo.lux
+++ b/stdlib/source/lux/control/function/memo.lux
@@ -20,7 +20,7 @@
(Mixin (-> i (State (Dictionary i o) o))))
(function (_ delegate recur)
(function (_ input)
- (do state.monad
+ (do {@ state.monad}
[memory state.get]
(case (dictionary.get input memory)
(#.Some output)
diff --git a/stdlib/source/lux/control/parser.lux b/stdlib/source/lux/control/parser.lux
index 6187a4d4f..88eefcdaf 100644
--- a/stdlib/source/lux/control/parser.lux
+++ b/stdlib/source/lux/control/parser.lux
@@ -200,7 +200,7 @@
(def: #export (sep-by sep p)
{#.doc "Parsers instances of 'p' that are separated by instances of 'sep'."}
(All [s a b] (-> (Parser s b) (Parser s a) (Parser s (List a))))
- (do ..monad
+ (do {@ ..monad}
[?x (maybe p)]
(case ?x
#.None
diff --git a/stdlib/source/lux/control/parser/binary.lux b/stdlib/source/lux/control/parser/binary.lux
index 137094340..b2a1b1b52 100644
--- a/stdlib/source/lux/control/parser/binary.lux
+++ b/stdlib/source/lux/control/parser/binary.lux
@@ -87,7 +87,7 @@
["Tag value" (%.nat byte)]))
(template: (!variant <case>+)
- (do //.monad
+ (do {@ //.monad}
[flag (: (Parser Nat)
..bits/8)]
(`` (case flag
diff --git a/stdlib/source/lux/control/parser/type.lux b/stdlib/source/lux/control/parser/type.lux
index dc3f101f3..d95c1c115 100644
--- a/stdlib/source/lux/control/parser/type.lux
+++ b/stdlib/source/lux/control/parser/type.lux
@@ -168,7 +168,7 @@
(def: #export (polymorphic poly)
(All [a] (-> (Parser a) (Parser [Code (List Code) a])))
- (do //.monad
+ (do {@ //.monad}
[headT any
funcI (:: @ map dictionary.size ..env)
[num-args non-poly] (local (list headT) polymorphic')
@@ -298,7 +298,7 @@
(def: #export (recursive poly)
(All [a] (-> (Parser a) (Parser [Code a])))
- (do //.monad
+ (do {@ //.monad}
[headT any]
(case (type.un-name headT)
(#.Apply (#.Named ["lux" "Nothing"] _) (#.UnivQ _ headT'))
@@ -328,7 +328,7 @@
(def: #export recursive-call
(Parser Code)
- (do //.monad
+ (do {@ //.monad}
[env ..env
[funcT argsT] (apply (//.and any (//.many any)))
_ (local (list funcT) (..parameter! 0))
diff --git a/stdlib/source/lux/control/region.lux b/stdlib/source/lux/control/region.lux
index 23f3888b3..332546685 100644
--- a/stdlib/source/lux/control/region.lux
+++ b/stdlib/source/lux/control/region.lux
@@ -54,7 +54,7 @@
(All [m a]
(-> (Monad m) (All [r] (Region r m a))
(m (Try a))))
- (do Monad<m>
+ (do {@ Monad<m>}
[[cleaners output] (computation [[] (list)])
results (monad.map @ (function (_ cleaner) (cleaner []))
cleaners)]
diff --git a/stdlib/source/lux/control/security/capability.lux b/stdlib/source/lux/control/security/capability.lux
index d33f0f0e6..69cea5b19 100644
--- a/stdlib/source/lux/control/security/capability.lux
+++ b/stdlib/source/lux/control/security/capability.lux
@@ -46,7 +46,7 @@
{declaration reader.declaration}
{annotations (p.maybe reader.annotations)}
{[forge input output] (s.form ($_ p.and s.local-identifier s.any s.any))})
- (do @
+ (do {@ macro.monad}
[this-module macro.current-module-name
#let [[name vars] declaration]
g!brand (:: @ map (|>> %.code code.text)
diff --git a/stdlib/source/lux/control/state.lux b/stdlib/source/lux/control/state.lux
index b4e958c6b..d42408984 100644
--- a/stdlib/source/lux/control/state.lux
+++ b/stdlib/source/lux/control/state.lux
@@ -80,7 +80,7 @@
(def: #export (while condition body)
(All [s] (-> (State s Bit) (State s Any) (State s Any)))
- (do ..monad
+ (do {@ ..monad}
[execute? condition]
(if execute?
(do @