aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/control
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/control')
-rw-r--r--stdlib/source/library/lux/control/concatenative.lux4
-rw-r--r--stdlib/source/library/lux/control/concurrency/actor.lux20
-rw-r--r--stdlib/source/library/lux/control/concurrency/async.lux50
-rw-r--r--stdlib/source/library/lux/control/concurrency/atom.lux14
-rw-r--r--stdlib/source/library/lux/control/concurrency/frp.lux34
-rw-r--r--stdlib/source/library/lux/control/concurrency/semaphore.lux30
-rw-r--r--stdlib/source/library/lux/control/concurrency/stm.lux32
-rw-r--r--stdlib/source/library/lux/control/concurrency/thread.lux28
-rw-r--r--stdlib/source/library/lux/control/exception.lux23
-rw-r--r--stdlib/source/library/lux/control/function/memo.lux4
-rw-r--r--stdlib/source/library/lux/control/function/mixin.lux4
-rw-r--r--stdlib/source/library/lux/control/io.lux2
-rw-r--r--stdlib/source/library/lux/control/parser/binary.lux8
-rw-r--r--stdlib/source/library/lux/control/parser/environment.lux2
-rw-r--r--stdlib/source/library/lux/control/security/capability.lux22
-rw-r--r--stdlib/source/library/lux/control/try.lux2
-rw-r--r--stdlib/source/library/lux/control/writer.lux2
17 files changed, 139 insertions, 142 deletions
diff --git a/stdlib/source/library/lux/control/concatenative.lux b/stdlib/source/library/lux/control/concatenative.lux
index 3005596ee..91dd6740d 100644
--- a/stdlib/source/library/lux/control/concatenative.lux
+++ b/stdlib/source/library/lux/control/concatenative.lux
@@ -82,7 +82,7 @@
___a [Bit then else] ___z)))}
(let [de_alias (function (_ aliased)
(list\fold (function (_ [from to] pre)
- (code.replace (code.local_identifier from) to pre))
+ (code.replaced (code.local_identifier from) to pre))
aliased
aliases))]
(case [(|> inputs (get@ #bottom) (maybe\map (|>> code.nat (~) #.Parameter (`))))
@@ -152,7 +152,7 @@
((apply 1) inc)))}
(with_gensyms [g! g!func g!stack g!output]
(monad.do {! meta.monad}
- [g!inputs (|> (macro.gensym "input") (list.repeat arity) (monad.seq !))]
+ [g!inputs (|> (macro.gensym "input") (list.repeated arity) (monad.seq !))]
(in (list (` (: (All [(~+ g!inputs) (~ g!output)]
(-> (-> (~+ g!inputs) (~ g!output))
(=> [(~+ g!inputs)] [(~ g!output)])))
diff --git a/stdlib/source/library/lux/control/concurrency/actor.lux b/stdlib/source/library/lux/control/concurrency/actor.lux
index 74dab7eda..ee3a1e5d3 100644
--- a/stdlib/source/library/lux/control/concurrency/actor.lux
+++ b/stdlib/source/library/lux/control/concurrency/actor.lux
@@ -95,7 +95,7 @@
(:abstraction {#obituary (async.async [])
#mailbox (atom (async.async []))}))
process (loop [state (on_init init)
- [|mailbox| _] (io.run (atom.read (get@ #mailbox (:representation self))))]
+ [|mailbox| _] (io.run (atom.read! (get@ #mailbox (:representation self))))]
(do {! async.monad}
[[head tail] |mailbox|
?state' (on_mail head state self)]
@@ -124,13 +124,13 @@
_
bit.no))))))
- (def: .public (obituary actor)
+ (def: .public (obituary' actor)
(All [s] (-> (Actor s) (IO (Maybe (Obituary s)))))
(let [[obituary _] (get@ #obituary (:representation actor))]
(async.poll obituary)))
- (def: .public await
- {#.doc (doc "Await for an actor to end working.")}
+ (def: .public obituary
+ {#.doc (doc "Await for an actor to stop working.")}
(All [s] (-> (Actor s) (Async (Obituary s))))
(|>> :representation
(get@ #obituary)
@@ -144,7 +144,7 @@
(if alive?
(let [entry [mail (async.async [])]]
(do !
- [|mailbox|&resolve (atom.read (get@ #mailbox (:representation actor)))]
+ [|mailbox|&resolve (atom.read! (get@ #mailbox (:representation actor)))]
(loop [[|mailbox| resolve] |mailbox|&resolve]
(do !
[|mailbox| (async.poll |mailbox|)]
@@ -154,8 +154,8 @@
[resolved? (resolve entry)]
(if resolved?
(do !
- [_ (atom.write (product.right entry) (get@ #mailbox (:representation actor)))]
- (in (exception.return [])))
+ [_ (atom.write! (product.right entry) (get@ #mailbox (:representation actor)))]
+ (in (#try.Success [])))
(recur |mailbox|&resolve)))
(#.Some [_ |mailbox|'])
@@ -411,7 +411,7 @@
(def: continue! true)
(def: stop! false)
-(def: .public (observe action channel actor)
+(def: .public (observe! action channel actor)
{#.doc (doc "Use an actor to observe a channel by transforming each datum"
"flowing through the channel into mail the actor can process."
"Can stop observing the channel by executing the Stop value.")}
@@ -419,10 +419,10 @@
(let [signal (: (Atom Bit)
(atom.atom ..continue!))
stop (: Stop
- (atom.write ..stop! signal))]
+ (atom.write! ..stop! signal))]
(frp.subscribe (function (_ event)
(do {! io.monad}
- [continue? (atom.read signal)]
+ [continue? (atom.read! signal)]
(if continue?
(|> actor
(..mail! (action event stop))
diff --git a/stdlib/source/library/lux/control/concurrency/async.lux b/stdlib/source/library/lux/control/concurrency/async.lux
index cc1757a31..72736ef94 100644
--- a/stdlib/source/library/lux/control/concurrency/async.lux
+++ b/stdlib/source/library/lux/control/concurrency/async.lux
@@ -33,7 +33,7 @@
(function (resolve value)
(let [async (:representation async)]
(do {! io.monad}
- [(^@ old [_value _observers]) (atom.read async)]
+ [(^@ old [_value _observers]) (atom.read! async)]
(case _value
(#.Some _)
(in #0)
@@ -41,7 +41,7 @@
#.None
(do !
[.let [new [(#.Some value) #.None]]
- succeeded? (atom.compare_and_swap old new async)]
+ succeeded? (atom.compare_and_swap! old new async)]
(if succeeded?
(do !
[_ (monad.map ! (function (_ f) (f value))
@@ -64,15 +64,15 @@
{#.doc "Polls an async for its value."}
(All [a] (-> (Async a) (IO (Maybe a))))
(|>> :representation
- atom.read
+ atom.read!
(\ io.functor map product.left)))
- (def: .public (await f async)
+ (def: .public (upon! f async)
{#.doc (doc "Executes the given function as soon as the async has been resolved.")}
(All [a] (-> (-> a (IO Any)) (Async a) (IO Any)))
(do {! io.monad}
[.let [async (:representation async)]
- (^@ old [_value _observers]) (atom.read async)]
+ (^@ old [_value _observers]) (atom.read! async)]
(case _value
(#.Some value)
(f value)
@@ -80,10 +80,10 @@
#.None
(let [new [_value (#.Item f _observers)]]
(do !
- [swapped? (atom.compare_and_swap old new async)]
+ [swapped? (atom.compare_and_swap! old new async)]
(if swapped?
(in [])
- (await f (:abstraction async))))))))
+ (upon! f (:abstraction async))))))))
)
(def: .public resolved?
@@ -102,7 +102,7 @@
(def: (map f fa)
(let [[fb resolve] (..async [])]
- (exec (io.run (..await (|>> f resolve) fa))
+ (exec (io.run (..upon! (|>> f resolve) fa))
fb))))
(implementation: .public apply
@@ -112,8 +112,8 @@
(def: (apply ff fa)
(let [[fb resolve] (..async [])]
- (exec (io.run (..await (function (_ f)
- (..await (|>> f resolve) fa))
+ (exec (io.run (..upon! (function (_ f)
+ (..upon! (|>> f resolve) fa))
ff))
fb))))
@@ -126,7 +126,7 @@
(def: (join mma)
(let [[ma resolve] (async [])]
- (exec (io.run (..await (..await resolve) mma))
+ (exec (io.run (..upon! (..upon! resolve) mma))
ma))))
(def: .public (and left right)
@@ -139,8 +139,8 @@
[(Async [a b])
(Resolver [a b])]
(..async []))
- _ (io.run (..await (function (_ left)
- (..await (function (_ right)
+ _ (io.run (..upon! (function (_ left)
+ (..upon! (function (_ right)
(write! [left right]))
right))
left))]
@@ -153,7 +153,7 @@
(let [[a|b resolve] (..async [])]
(with_expansions
[<sides> (template [<async> <tag>]
- [(io.run (await (|>> <tag> resolve) <async>))]
+ [(io.run (upon! (|>> <tag> resolve) <async>))]
[left #.Left]
[right #.Right]
@@ -167,21 +167,21 @@
(All [a] (-> (Async a) (Async a) (Async a)))
(let [[left||right resolve] (..async [])]
(`` (exec (~~ (template [<async>]
- [(io.run (await resolve <async>))]
+ [(io.run (upon! resolve <async>))]
[left]
[right]))
left||right))))
-(def: .public (schedule millis_delay computation)
+(def: .public (schedule! millis_delay computation)
{#.doc (doc "Runs an I/O computation on its own thread (after a specified delay)."
- "Returns a aromise that will eventually host its result.")}
+ "Returns an async that will eventually host its result.")}
(All [a] (-> Nat (IO a) (Async a)))
(let [[!out resolve] (..async [])]
(exec (|> (do io.monad
[value computation]
(resolve value))
- (thread.schedule millis_delay)
+ (thread.schedule! millis_delay)
io.run)
!out)))
@@ -189,19 +189,19 @@
{#.doc (doc "Runs an I/O computation on its own thread."
"Returns an async that will eventually host its result.")}
(All [a] (-> (IO a) (Async a)))
- (..schedule 0))
+ (..schedule! 0))
-(def: .public (delay time_millis value)
+(def: .public (delayed time_millis value)
{#.doc "Delivers a value after a certain period has passed."}
(All [a] (-> Nat a (Async a)))
- (..schedule time_millis (io value)))
+ (..schedule! time_millis (io value)))
-(def: .public (wait time_millis)
- {#.doc "Returns an async that will be resolved after the specified amount of milliseconds."}
+(def: .public (delay time_millis)
+ {#.doc "An async that will be resolved after the specified amount of milliseconds."}
(-> Nat (Async Any))
- (..delay time_millis []))
+ (..delayed time_millis []))
(def: .public (time_out time_millis async)
{#.doc "Wait for an async to be resolved within the specified amount of milliseconds."}
(All [a] (-> Nat (Async a) (Async (Maybe a))))
- (..or (wait time_millis) async))
+ (..or (..delay time_millis) async))
diff --git a/stdlib/source/library/lux/control/concurrency/atom.lux b/stdlib/source/library/lux/control/concurrency/atom.lux
index c6c993561..a607fa8d3 100644
--- a/stdlib/source/library/lux/control/concurrency/atom.lux
+++ b/stdlib/source/library/lux/control/concurrency/atom.lux
@@ -61,14 +61,14 @@
@.jvm <jvm>}
(<write> 0 value (<new> 1))))))
- (def: .public (read atom)
+ (def: .public (read! atom)
(All [a] (-> (Atom a) (IO a)))
(io (with_expansions [<jvm> (java/util/concurrent/atomic/AtomicReference::get (:representation atom))]
(for {@.old <jvm>
@.jvm <jvm>}
(<read> 0 (:representation atom))))))
- (def: .public (compare_and_swap current new atom)
+ (def: .public (compare_and_swap! current new atom)
{#.doc (doc "Only mutates an atom if you can present its current value."
"That guarantees that atom was not updated since you last read from it.")}
(All [a] (-> a a (Atom a) (IO Bit)))
@@ -82,24 +82,24 @@
false))))))
))
-(def: .public (update f atom)
+(def: .public (update! f atom)
{#.doc (doc "Updates an atom by applying a function to its current value."
"If it fails to update it (because some other process wrote to it first), it will retry until it succeeds."
"The retries will be done with the new values of the atom, as they show up.")}
(All [a] (-> (-> a a) (Atom a) (IO [a a])))
(loop [_ []]
(do io.monad
- [old (read atom)
+ [old (read! atom)
.let [new (f old)]
- swapped? (..compare_and_swap old new atom)]
+ swapped? (compare_and_swap! old new atom)]
(if swapped?
(in [old new])
(recur [])))))
-(def: .public (write value atom)
+(def: .public (write! value atom)
{#.doc (doc "Writes the given value to an atom."
"If it fails to write it (because some other process wrote to it first), it will retry until it succeeds.")}
(All [a] (-> a (Atom a) (IO a)))
(|> atom
- (..update (function.constant value))
+ (..update! (function.constant value))
(io\map product.left)))
diff --git a/stdlib/source/library/lux/control/concurrency/frp.lux b/stdlib/source/library/lux/control/concurrency/frp.lux
index 3b1a0a4bd..7d22b5924 100644
--- a/stdlib/source/library/lux/control/concurrency/frp.lux
+++ b/stdlib/source/library/lux/control/concurrency/frp.lux
@@ -40,24 +40,24 @@
(def: close
(loop [_ []]
(do {! io.monad}
- [current (atom.read sink)
+ [current (atom.read! sink)
stopped? (current #.None)]
(if stopped?
- ## I closed the sink.
- (in (exception.return []))
- ## Someone else interacted with the sink.
+ ... I closed the sink.
+ (in (#try.Success []))
+ ... Someone else interacted with the sink.
(do !
- [latter (atom.read sink)]
+ [latter (atom.read! sink)]
(if (is? current latter)
- ## Someone else closed the sink.
+ ... Someone else closed the sink.
(in (exception.except ..channel_is_already_closed []))
- ## Someone else fed the sink while I was closing it.
+ ... Someone else fed the sink while I was closing it.
(recur [])))))))
(def: (feed value)
(loop [_ []]
(do {! io.monad}
- [current (atom.read sink)
+ [current (atom.read! sink)
.let [[next resolve_next] (:sharing [a]
(async.Resolver (Maybe [a (Channel a)]))
current
@@ -67,17 +67,17 @@
(async.async []))]
fed? (current (#.Some [value next]))]
(if fed?
- ## I fed the sink.
+ ... I fed the sink.
(do !
- [_ (atom.compare_and_swap current resolve_next sink)]
- (in (exception.return [])))
- ## Someone else interacted with the sink.
+ [_ (atom.compare_and_swap! current resolve_next sink)]
+ (in (#try.Success [])))
+ ... Someone else interacted with the sink.
(do !
- [latter (atom.read sink)]
+ [latter (atom.read! sink)]
(if (is? current latter)
- ## Someone else closed the sink while I was feeding it.
+ ... Someone else closed the sink while I was feeding it.
(in (exception.except ..channel_is_already_closed []))
- ## Someone else fed the sink.
+ ... Someone else fed the sink.
(recur []))))))))))
(def: .public (channel _)
@@ -233,7 +233,7 @@
(do io.monad
[value action
_ (\ sink feed value)]
- (async.await recur (async.wait milli_seconds)))))
+ (async.upon! recur (async.delay milli_seconds)))))
[output sink])))
(def: .public (periodic milli_seconds)
@@ -296,5 +296,5 @@
(#.Item head tail)
(async.resolved (#.Some [head (do async.monad
- [_ (async.wait milli_seconds)]
+ [_ (async.delay milli_seconds)]
(sequential milli_seconds tail))]))))
diff --git a/stdlib/source/library/lux/control/concurrency/semaphore.lux b/stdlib/source/library/lux/control/concurrency/semaphore.lux
index f01af9336..046651c1b 100644
--- a/stdlib/source/library/lux/control/concurrency/semaphore.lux
+++ b/stdlib/source/library/lux/control/concurrency/semaphore.lux
@@ -55,11 +55,11 @@
(exec (io.run
(with_expansions [<had_open_position?> (as_is (get@ #open_positions) (i.> -1))]
(do io.monad
- [[_ state'] (atom.update (|>> (update@ #open_positions dec)
- (if> [<had_open_position?>]
- []
- [(update@ #waiting_list (queue.push sink))]))
- semaphore)]
+ [[_ state'] (atom.update! (|>> (update@ #open_positions dec)
+ (if> [<had_open_position?>]
+ []
+ [(update@ #waiting_list (queue.push sink))]))
+ semaphore)]
(with_expansions [<go_ahead> (sink [])
<get_in_line> (in false)]
(if (|> state' <had_open_position?>)
@@ -77,14 +77,14 @@
(let [semaphore (:representation semaphore)]
(async.future
(do {! io.monad}
- [[pre post] (atom.update (function (_ state)
- (if (i.= (.int (get@ #max_positions state))
- (get@ #open_positions state))
- state
- (|> state
- (update@ #open_positions inc)
- (update@ #waiting_list queue.pop))))
- semaphore)]
+ [[pre post] (atom.update! (function (_ state)
+ (if (i.= (.int (get@ #max_positions state))
+ (get@ #open_positions state))
+ state
+ (|> state
+ (update@ #open_positions inc)
+ (update@ #waiting_list queue.pop))))
+ semaphore)]
(if (is? pre post)
(in (exception.except ..semaphore_is_maxed_out [(get@ #max_positions pre)]))
(do !
@@ -127,7 +127,7 @@
(def: .public limit
{#.doc (doc "Produce a limit for a barrier.")}
- (refinement.refinement (n.> 0)))
+ (refinement.refiner (n.> 0)))
(type: .public Limit
{#.doc (doc "A limit for barriers.")}
@@ -163,7 +163,7 @@
(do async.monad
[.let [limit (refinement.value (get@ #limit barrier))
goal <goal>
- [_ count] (io.run (atom.update <update> (get@ #count barrier)))
+ [_ count] (io.run (atom.update! <update> (get@ #count barrier)))
reached? (n.= goal count)]]
(if reached?
(..un_block (dec limit) (get@ <turnstile> barrier))
diff --git a/stdlib/source/library/lux/control/concurrency/stm.lux b/stdlib/source/library/lux/control/concurrency/stm.lux
index 6308a2c84..1ad5d9ac0 100644
--- a/stdlib/source/library/lux/control/concurrency/stm.lux
+++ b/stdlib/source/library/lux/control/concurrency/stm.lux
@@ -35,22 +35,22 @@
(def: read!
(All [a] (-> (Var a) a))
- (|>> :representation atom.read io.run product.left))
+ (|>> :representation atom.read! io.run product.left))
(def: (un_follow sink var)
(All [a] (-> (Sink a) (Var a) (IO Any)))
(do io.monad
- [_ (atom.update (function (_ [value observers])
- [value (list.only (|>> (is? sink) not) observers)])
- (:representation var))]
+ [_ (atom.update! (function (_ [value observers])
+ [value (list.only (|>> (is? sink) not) observers)])
+ (:representation var))]
(in [])))
(def: (write! new_value var)
(All [a] (-> a (Var a) (IO Any)))
(do {! io.monad}
[.let [var' (:representation var)]
- (^@ old [old_value observers]) (atom.read var')
- succeeded? (atom.compare_and_swap old [new_value observers] var')]
+ (^@ old [old_value observers]) (atom.read! var')
+ succeeded? (atom.compare_and_swap! old [new_value observers] var')]
(if succeeded?
(do !
[_ (monad.map ! (function (_ sink)
@@ -71,9 +71,9 @@
(All [a] (-> (Var a) (IO [(Channel a) (Sink a)])))
(do io.monad
[.let [[channel sink] (frp.channel [])]
- _ (atom.update (function (_ [value observers])
- [value (#.Item sink observers)])
- (:representation target))]
+ _ (atom.update! (function (_ [value observers])
+ [value (#.Item sink observers)])
+ (:representation target))]
(in [channel sink])))
)
@@ -217,7 +217,7 @@
(All [a] (-> (Commit a) (IO Any)))
(let [entry [commit (async.async [])]]
(do {! io.monad}
- [|commits|&resolve (atom.read pending_commits)]
+ [|commits|&resolve (atom.read! pending_commits)]
(loop [[|commits| resolve] |commits|&resolve]
(do !
[|commits| (async.poll |commits|)]
@@ -226,7 +226,7 @@
(do io.monad
[resolved? (resolve entry)]
(if resolved?
- (atom.write (product.right entry) pending_commits)
+ (atom.write! (product.right entry) pending_commits)
(recur |commits|&resolve)))
(#.Some [head tail])
@@ -245,18 +245,18 @@
(def: init_processor!
(IO Any)
(do {! io.monad}
- [flag (atom.read commit_processor_flag)]
+ [flag (atom.read! commit_processor_flag)]
(if flag
(in [])
(do !
- [was_first? (atom.compare_and_swap flag #1 commit_processor_flag)]
+ [was_first? (atom.compare_and_swap! flag #1 commit_processor_flag)]
(if was_first?
(do !
- [[async resolve] (atom.read pending_commits)]
- (async.await (function (recur [head [tail _resolve]])
+ [[async resolve] (atom.read! pending_commits)]
+ (async.upon! (function (recur [head [tail _resolve]])
(do !
[_ (process_commit head)]
- (async.await recur tail)))
+ (async.upon! recur tail)))
async))
(in [])))
)))
diff --git a/stdlib/source/library/lux/control/concurrency/thread.lux b/stdlib/source/library/lux/control/concurrency/thread.lux
index 8c3a273d4..767107af7 100644
--- a/stdlib/source/library/lux/control/concurrency/thread.lux
+++ b/stdlib/source/library/lux/control/concurrency/thread.lux
@@ -57,7 +57,7 @@
(new [ffi.Float ffi.Function])
(start [] #io #? Any)])}
- ## Default
+ ... Default
(type: Thread
{#creation Nat
#delay Nat
@@ -72,7 +72,7 @@
.nat)]
(for {@.old <jvm>
@.jvm <jvm>}
- ## Default
+ ... Default
1)))
(with_expansions [<jvm> (as_is (def: runner
@@ -83,7 +83,7 @@
@.js (as_is)
@.python (as_is)}
- ## Default
+ ... Default
(def: runner
(Atom (List Thread))
(atom.atom (list)))))
@@ -101,7 +101,7 @@
(#try.Success _)
[]))
-(def: .public (schedule milli_seconds action)
+(def: .public (schedule! milli_seconds action)
{#.doc (doc "Executes an I/O procedure after some milli-seconds.")}
(-> Nat (IO Any) (IO Any))
(with_expansions [<jvm> (as_is (let [runnable (ffi.object [] [java/lang/Runnable]
@@ -127,13 +127,13 @@
(threading/Timer::start []))]
(in []))}
- ## Default
+ ... Default
(do {! io.monad}
[now (\ ! map (|>> instant.millis .nat) instant.now)
- _ (atom.update (|>> (#.Item {#creation now
- #delay milli_seconds
- #action action}))
- ..runner)]
+ _ (atom.update! (|>> (#.Item {#creation now
+ #delay milli_seconds
+ #action action}))
+ ..runner)]
(in [])))))
(for {@.old (as_is)
@@ -141,18 +141,18 @@
@.js (as_is)
@.python (as_is)}
- ## Default
+ ... Default
(as_is (exception: .public cannot_continue_running_threads)
- ## https://en.wikipedia.org/wiki/Event_loop
+ ... https://en.wikipedia.org/wiki/Event_loop
(def: .public run!
{#.doc (doc "Starts the event-loop.")}
(IO Any)
(loop [_ []]
(do {! io.monad}
- [threads (atom.read ..runner)]
+ [threads (atom.read! ..runner)]
(case threads
- ## And... we're done!
+ ... And... we're done!
#.End
(in [])
@@ -164,7 +164,7 @@
(n.+ (get@ #delay thread))
(n.<= now)))
threads)]
- swapped? (atom.compare_and_swap threads pending ..runner)]
+ swapped? (atom.compare_and_swap! threads pending ..runner)]
(if swapped?
(do !
[_ (monad.map ! (|>> (get@ #action) ..execute! io.io) ready)]
diff --git a/stdlib/source/library/lux/control/exception.lux b/stdlib/source/library/lux/control/exception.lux
index a7d5a5871..1edd4bc04 100644
--- a/stdlib/source/library/lux/control/exception.lux
+++ b/stdlib/source/library/lux/control/exception.lux
@@ -37,7 +37,7 @@
(All [e] (-> (Exception e) Text Bit))
(text.starts_with? (get@ #label exception) error))
-(def: .public (catch exception then try)
+(def: .public (when exception then try)
{#.doc (doc "If a particular exception is detected on a possibly-erroneous value, handle it."
"If no exception was detected, or a different one from the one being checked, then pass along the original value.")}
(All [e a]
@@ -67,11 +67,6 @@
(#//.Failure error)
(else error)))
-(def: .public (return value)
- {#.doc "A way to lift normal values into the error-handling context."}
- (All [a] (-> a (Try a)))
- (#//.Success value))
-
(def: .public (error exception message)
{#.doc "Constructs an error message from an exception."}
(All [e] (-> (Exception e) e Text))
@@ -135,18 +130,18 @@
0
entries)
on_new_line (|> " "
- (list.repeat (n.+ (text.size header_separator)
- largest_header_size))
+ (list.repeated (n.+ (text.size header_separator)
+ largest_header_size))
(text.join_with "")
(text\compose text.new_line))
on_entry (: (-> [Text Text] Text)
(function (_ [header message])
(let [padding (|> " "
- (list.repeat (n.- (text.size header)
- largest_header_size))
+ (list.repeated (n.- (text.size header)
+ largest_header_size))
(text.join_with ""))]
(|> message
- (text.replace_all text.new_line on_new_line)
+ (text.replaced text.new_line on_new_line)
($_ text\compose padding header header_separator)))))]
(case entries
#.End
@@ -186,13 +181,13 @@
(def: separator
(let [gap ($_ "lux text concat" text.new_line text.new_line)
- horizontal_line (|> "-" (list.repeat 64) (text.join_with ""))]
+ horizontal_line (|> "-" (list.repeated 64) (text.join_with ""))]
($_ "lux text concat"
gap
horizontal_line
gap)))
-(def: (decorate prelude error)
+(def: (decorated prelude error)
(-> Text Text Text)
($_ "lux text concat"
prelude
@@ -209,7 +204,7 @@
(..error exception message)
_
- (..decorate (..error exception message) error)))
+ (..decorated (..error exception message) error)))
success
success))
diff --git a/stdlib/source/library/lux/control/function/memo.lux b/stdlib/source/library/lux/control/function/memo.lux
index 311f1e433..87131ad57 100644
--- a/stdlib/source/library/lux/control/function/memo.lux
+++ b/stdlib/source/library/lux/control/function/memo.lux
@@ -1,5 +1,5 @@
-## Inspired by;
-## "The Different Aspects of Monads and Mixins" by Bruno C. d. S. Oliveira
+... Inspired by;
+... "The Different Aspects of Monads and Mixins" by Bruno C. d. S. Oliveira
(.module:
[library
diff --git a/stdlib/source/library/lux/control/function/mixin.lux b/stdlib/source/library/lux/control/function/mixin.lux
index 50e26ef55..25ca0240b 100644
--- a/stdlib/source/library/lux/control/function/mixin.lux
+++ b/stdlib/source/library/lux/control/function/mixin.lux
@@ -1,5 +1,5 @@
-## Inspired by;
-## "The Different Aspects of Monads and Mixins" by Bruno C. d. S. Oliveira
+... Inspired by;
+... "The Different Aspects of Monads and Mixins" by Bruno C. d. S. Oliveira
(.module:
[library
diff --git a/stdlib/source/library/lux/control/io.lux b/stdlib/source/library/lux/control/io.lux
index 843170c4c..801be1c2a 100644
--- a/stdlib/source/library/lux/control/io.lux
+++ b/stdlib/source/library/lux/control/io.lux
@@ -30,7 +30,7 @@
computation)))])
(template: (!run io)
- ## creatio ex nihilo
+ ... creatio ex nihilo
[((:representation io) [])])
(syntax: .public (io computation)
diff --git a/stdlib/source/library/lux/control/parser/binary.lux b/stdlib/source/library/lux/control/parser/binary.lux
index fe10ed1ee..1018e7683 100644
--- a/stdlib/source/library/lux/control/parser/binary.lux
+++ b/stdlib/source/library/lux/control/parser/binary.lux
@@ -90,10 +90,10 @@
(#try.Failure error)
(#try.Failure error))))]
- [bits/8 ..size/8 /.read/8]
- [bits/16 ..size/16 /.read/16]
- [bits/32 ..size/32 /.read/32]
- [bits/64 ..size/64 /.read/64]
+ [bits/8 ..size/8 /.read/8!]
+ [bits/16 ..size/16 /.read/16!]
+ [bits/32 ..size/32 /.read/32!]
+ [bits/64 ..size/64 /.read/64!]
)
(template [<name> <type>]
diff --git a/stdlib/source/library/lux/control/parser/environment.lux b/stdlib/source/library/lux/control/parser/environment.lux
index fe7c0ea59..b83ef9165 100644
--- a/stdlib/source/library/lux/control/parser/environment.lux
+++ b/stdlib/source/library/lux/control/parser/environment.lux
@@ -38,7 +38,7 @@
(function (_ environment)
(case (dictionary.get name environment)
(#.Some value)
- (exception.return [environment value])
+ (#try.Success [environment value])
#.None
(exception.except ..unknown_property [name]))))
diff --git a/stdlib/source/library/lux/control/security/capability.lux b/stdlib/source/library/lux/control/security/capability.lux
index 4834e172c..b0123dc68 100644
--- a/stdlib/source/library/lux/control/security/capability.lux
+++ b/stdlib/source/library/lux/control/security/capability.lux
@@ -4,9 +4,9 @@
[abstract
[monad (#+ do)]]
[control
+ ["." io (#+ IO)]
["<>" parser
["<c>" code]]
- ["." io (#+ IO)]
[concurrency
["." async (#+ Async)]]]
[data
@@ -30,7 +30,7 @@
(-> input output)
- (def: forge
+ (def: capability
(All [brand input output]
(-> (-> input output)
(Capability brand input output)))
@@ -44,10 +44,12 @@
output))
((:representation capability) input))
- (syntax: .public (capability: {export |export|.parser}
- {declaration |declaration|.parser}
- {annotations (<>.maybe |annotations|.parser)}
- {[forge input output] (<c>.form ($_ <>.and <c>.local_identifier <c>.any <c>.any))})
+ (syntax: .public (capability: {[export_policy declaration annotations [forger input output]]
+ (|export|.parser
+ ($_ <>.and
+ |declaration|.parser
+ (<>.maybe |annotations|.parser)
+ (<c>.form ($_ <>.and <c>.local_identifier <c>.any <c>.any))))})
{#.doc (doc "Defines a capability as a unique type, and a constructor for instances."
(capability: (Can_Duplicate a)
@@ -64,14 +66,14 @@
g!brand (\ ! map (|>> %.code code.text)
(macro.gensym (format (%.name [this_module name]))))
.let [capability (` (..Capability (.primitive (~ g!brand)) (~ input) (~ output)))]]
- (in (list (` (type: (~+ (|export|.format export))
+ (in (list (` (type: (~ export_policy)
(~ (|declaration|.format declaration))
(~ capability)))
- (` (def: (~ (code.local_identifier forge))
+ (` (def: (~ (code.local_identifier forger))
(All [(~+ (list\map code.local_identifier vars))]
(-> (-> (~ input) (~ output))
(~ capability)))
- (~! ..forge)))
+ (~! ..capability)))
))))
(def: .public (async capability)
@@ -79,5 +81,5 @@
(All [brand input output]
(-> (Capability brand input (IO output))
(Capability brand input (Async output))))
- (..forge (|>> ((:representation capability)) async.future)))
+ (..capability (|>> ((:representation capability)) async.future)))
)
diff --git a/stdlib/source/library/lux/control/try.lux b/stdlib/source/library/lux/control/try.lux
index fa02b452a..6d547f778 100644
--- a/stdlib/source/library/lux/control/try.lux
+++ b/stdlib/source/library/lux/control/try.lux
@@ -61,7 +61,7 @@
(implementation: .public (with monad)
{#.doc (doc "Enhances a monad with error-handling functionality.")}
- ## TODO: Replace (All [a] (! (Try a))) with (functor.Then ! Try)
+ ... TODO: Replace (All [a] (! (Try a))) with (functor.Then ! Try)
(All [!] (-> (Monad !) (Monad (All [a] (! (Try a))))))
(def: &functor
diff --git a/stdlib/source/library/lux/control/writer.lux b/stdlib/source/library/lux/control/writer.lux
index b4ea701cb..c02d6f8bb 100644
--- a/stdlib/source/library/lux/control/writer.lux
+++ b/stdlib/source/library/lux/control/writer.lux
@@ -67,7 +67,7 @@
[[l1 Mla] (for {@.old
(: ((:parameter 1) (Writer (:parameter 0) ((:parameter 1) (Writer (:parameter 0) (:parameter 2)))))
MlMla)}
- ## On new compiler
+ ... On new compiler
MlMla)
[l2 a] Mla]
(in [(\ monoid compose l1 l2) a]))))