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.lux4
-rw-r--r--stdlib/source/library/lux/control/concurrency/actor.lux91
-rw-r--r--stdlib/source/library/lux/control/concurrency/async.lux (renamed from stdlib/source/library/lux/control/concurrency/promise.lux)118
-rw-r--r--stdlib/source/library/lux/control/concurrency/frp.lux78
-rw-r--r--stdlib/source/library/lux/control/concurrency/semaphore.lux34
-rw-r--r--stdlib/source/library/lux/control/concurrency/stm.lux28
-rw-r--r--stdlib/source/library/lux/control/function/mutual.lux16
-rw-r--r--stdlib/source/library/lux/control/parser.lux2
-rw-r--r--stdlib/source/library/lux/control/parser/analysis.lux50
-rw-r--r--stdlib/source/library/lux/control/parser/binary.lux74
-rw-r--r--stdlib/source/library/lux/control/parser/cli.lux3
-rw-r--r--stdlib/source/library/lux/control/parser/json.lux20
-rw-r--r--stdlib/source/library/lux/control/parser/type.lux26
-rw-r--r--stdlib/source/library/lux/control/region.lux4
-rw-r--r--stdlib/source/library/lux/control/remember.lux4
-rw-r--r--stdlib/source/library/lux/control/security/capability.lux6
16 files changed, 293 insertions, 265 deletions
diff --git a/stdlib/source/library/lux/control/concatenative.lux b/stdlib/source/library/lux/control/concatenative.lux
index 3ab6c0f05..0d87210c3 100644
--- a/stdlib/source/library/lux/control/concatenative.lux
+++ b/stdlib/source/library/lux/control/concatenative.lux
@@ -65,8 +65,8 @@
(wrap singleton)
_
- (meta.fail (format "Cannot expand to more than a single AST/Code node:" text.new_line
- (|> expansion (list\map %.code) (text.join_with " ")))))))
+ (meta.failure (format "Cannot expand to more than a single AST/Code node:" text.new_line
+ (|> expansion (list\map %.code) (text.join_with " ")))))))
(syntax: #export (=> {aliases aliases^}
{inputs stack^}
diff --git a/stdlib/source/library/lux/control/concurrency/actor.lux b/stdlib/source/library/lux/control/concurrency/actor.lux
index 355a7885e..b2b619735 100644
--- a/stdlib/source/library/lux/control/concurrency/actor.lux
+++ b/stdlib/source/library/lux/control/concurrency/actor.lux
@@ -1,4 +1,5 @@
-(.module: {#.doc "The actor model of concurrency."}
+(.module:
+ {#.doc "The actor model of concurrency."}
[library
[lux #*
["." debug]
@@ -34,27 +35,27 @@
["." abstract (#+ abstract: :representation :abstraction)]]]]
[//
["." atom (#+ Atom atom)]
- ["." promise (#+ Promise Resolver) ("#\." monad)]
+ ["." async (#+ Async Resolver) ("#\." monad)]
["." frp (#+ Channel)]])
(exception: #export poisoned)
(exception: #export dead)
(with_expansions
- [<Mail> (as_is (-> s (Actor s) (Promise (Try s))))
+ [<Mail> (as_is (-> s (Actor s) (Async (Try s))))
<Obituary> (as_is [Text s (List <Mail>)])
<Mailbox> (as_is (Rec Mailbox
- [(Promise [<Mail> Mailbox])
+ [(Async [<Mail> Mailbox])
(Resolver [<Mail> Mailbox])]))]
(def: (pending [read write])
(All [a]
(-> (Rec Mailbox
- [(Promise [a Mailbox])
+ [(Async [a Mailbox])
(Resolver [a Mailbox])])
(IO (List a))))
(do {! io.monad}
- [current (promise.poll read)]
+ [current (async.poll read)]
(case current
(#.Some [head tail])
(\ ! map (|>> (#.Cons head))
@@ -64,7 +65,7 @@
(wrap #.Nil))))
(abstract: #export (Actor s)
- {#obituary [(Promise <Obituary>)
+ {#obituary [(Async <Obituary>)
(Resolver <Obituary>)]
#mailbox (Atom <Mailbox>)}
@@ -81,7 +82,7 @@
(type: #export (Behavior o s)
{#.doc (doc "An actor's behavior when mail is received and when a fatal error occurs.")}
{#on_init (-> o s)
- #on_mail (-> (Mail s) s (Actor s) (Promise (Try s)))})
+ #on_mail (-> (Mail s) s (Actor s) (Async (Try s)))})
(def: #export (spawn! behavior init)
{#.doc (doc "Given a behavior and initial state, spawns an actor and returns it.")}
@@ -92,11 +93,11 @@
behavior
(Actor s)
- (:abstraction {#obituary (promise.promise [])
- #mailbox (atom (promise.promise []))}))
+ (:abstraction {#obituary (async.async [])
+ #mailbox (atom (async.async []))}))
process (loop [state (on_init init)
[|mailbox| _] (io.run (atom.read (get@ #mailbox (:representation self))))]
- (do {! promise.monad}
+ (do {! async.monad}
[[head tail] |mailbox|
?state' (on_mail head state self)]
(case ?state'
@@ -116,7 +117,7 @@
(All [s] (-> (Actor s) (IO Bit)))
(let [[obituary _] (get@ #obituary (:representation actor))]
(|> obituary
- promise.poll
+ async.poll
(\ io.functor map
(|>> (case> #.None
bit.yes
@@ -127,11 +128,11 @@
(def: #export (obituary actor)
(All [s] (-> (Actor s) (IO (Maybe (Obituary s)))))
(let [[obituary _] (get@ #obituary (:representation actor))]
- (promise.poll obituary)))
+ (async.poll obituary)))
(def: #export await
{#.doc (doc "Await for an actor to end working.")}
- (All [s] (-> (Actor s) (Promise (Obituary s))))
+ (All [s] (-> (Actor s) (Async (Obituary s))))
(|>> :representation
(get@ #obituary)
product.left))
@@ -142,12 +143,12 @@
(do {! io.monad}
[alive? (..alive? actor)]
(if alive?
- (let [entry [mail (promise.promise [])]]
+ (let [entry [mail (async.async [])]]
(do !
[|mailbox|&resolve (atom.read (get@ #mailbox (:representation actor)))]
(loop [[|mailbox| resolve] |mailbox|&resolve]
(do !
- [|mailbox| (promise.poll |mailbox|)]
+ [|mailbox| (async.poll |mailbox|)]
(case |mailbox|
#.None
(do !
@@ -164,39 +165,39 @@
(type: #export (Message s o)
{#.doc (doc "A two-way message sent to an actor, expecting a reply.")}
- (-> s (Actor s) (Promise (Try [s o]))))
+ (-> s (Actor s) (Async (Try [s o]))))
(def: (mail message)
- (All [s o] (-> (Message s o) [(Promise (Try o)) (Mail s)]))
- (let [[promise resolve] (:sharing [s o]
- (Message s o)
- message
-
- [(Promise (Try o))
- (Resolver (Try o))]
- (promise.promise []))]
- [promise
+ (All [s o] (-> (Message s o) [(Async (Try o)) (Mail s)]))
+ (let [[async resolve] (:sharing [s o]
+ (Message s o)
+ message
+
+ [(Async (Try o))
+ (Resolver (Try o))]
+ (async.async []))]
+ [async
(function (_ state self)
- (do {! promise.monad}
+ (do {! async.monad}
[outcome (message state self)]
(case outcome
(#try.Success [state' return])
(exec (io.run (resolve (#try.Success return)))
- (promise.resolved (#try.Success state')))
+ (async.resolved (#try.Success state')))
(#try.Failure error)
(exec (io.run (resolve (#try.Failure error)))
- (promise.resolved (#try.Failure error))))))]))
+ (async.resolved (#try.Failure error))))))]))
(def: #export (tell! message actor)
{#.doc (doc "Communicate with an actor through message-passing.")}
- (All [s o] (-> (Message s o) (Actor s) (Promise (Try o))))
- (let [[promise mail] (..mail message)]
- (do promise.monad
- [outcome (promise.future (..mail! mail actor))]
+ (All [s o] (-> (Message s o) (Actor s) (Async (Try o))))
+ (let [[async mail] (..mail message)]
+ (do async.monad
+ [outcome (async.future (..mail! mail actor))]
(case outcome
(#try.Success)
- promise
+ async
(#try.Failure error)
(wrap (#try.Failure error))))))
@@ -204,7 +205,7 @@
)
(def: (default_on_mail mail state self)
- (All [s] (-> (Mail s) s (Actor s) (Promise (Try s))))
+ (All [s] (-> (Mail s) s (Actor s) (Async (Try s))))
(mail state self))
(def: #export default
@@ -218,7 +219,7 @@
"but allows the actor to handle previous mail.")}
(All [s] (-> (Actor s) (IO (Try Any))))
(..mail! (function (_ state self)
- (promise.resolved (exception.throw ..poisoned [])))
+ (async.resolved (exception.throw ..poisoned [])))
actor))
(def: actor_decl^
@@ -261,7 +262,7 @@
(List a)
((on_mail mail state self)
- (do (try.with promise.monad)
+ (do (try.with async.monad)
[#let [_ (debug.log! "BEFORE")]
output (mail state self)
#let [_ (debug.log! "AFTER")]]
@@ -270,7 +271,7 @@
(message: #export (push {value a} state self)
(List a)
(let [state' (#.Cons value state)]
- (promise.resolved (#try.Success [state' state'])))))
+ (async.resolved (#try.Success [state' state'])))))
(actor: #export Counter
Nat
@@ -278,11 +279,11 @@
(message: #export (count! {increment Nat} state self)
Any
(let [state' (n.+ increment state)]
- (promise.resolved (#try.Success [state' state']))))
+ (async.resolved (#try.Success [state' state']))))
(message: #export (read! state self)
Nat
- (promise.resolved (#try.Success [state state])))))]
+ (async.resolved (#try.Success [state state])))))]
(syntax: #export (actor:
{export |export|.parser}
{[name vars] actor_decl^}
@@ -353,7 +354,7 @@
body)
{#.doc (doc "A message can access the actor's state through the state parameter."
"A message can also access the actor itself through the self parameter."
- "A message's output must be a promise containing a 2-tuple with the updated state and a return value."
+ "A message's output must be an async containing a 2-tuple with the updated state and a return value."
"A message may succeed or fail (in case of failure, the actor dies)."
<examples>)}
@@ -378,10 +379,10 @@
(let [(~ g!state) (:as (~ (get@ #abstract.representation actor_scope))
(~ g!state))]
(|> (~ body)
- (: ((~! promise.Promise) ((~! try.Try) [(~ (get@ #abstract.representation actor_scope))
- (~ output_type)])))
- (:as ((~! promise.Promise) ((~! try.Try) [(~ (get@ #abstract.abstraction actor_scope))
- (~ output_type)]))))))))
+ (: ((~! async.Async) ((~! try.Try) [(~ (get@ #abstract.representation actor_scope))
+ (~ output_type)])))
+ (:as ((~! async.Async) ((~! try.Try) [(~ (get@ #abstract.abstraction actor_scope))
+ (~ output_type)]))))))))
))))))
(type: #export Stop
diff --git a/stdlib/source/library/lux/control/concurrency/promise.lux b/stdlib/source/library/lux/control/concurrency/async.lux
index 24618fa5a..875602eff 100644
--- a/stdlib/source/library/lux/control/concurrency/promise.lux
+++ b/stdlib/source/library/lux/control/concurrency/async.lux
@@ -17,23 +17,23 @@
["." thread]
["." atom (#+ Atom atom)]])
-(abstract: #export (Promise a)
+(abstract: #export (Async a)
(Atom [(Maybe a) (List (-> a (IO Any)))])
{#.doc "Represents values produced by asynchronous computations (unlike IO, which is synchronous)."}
(type: #export (Resolver a)
- {#.doc (doc "The function used to give a value to a promise."
- "Will signal 'true' if the promise has been resolved for the 1st time, 'false' otherwise.")}
+ {#.doc (doc "The function used to give a value to an async."
+ "Will signal 'true' if the async has been resolved for the 1st time, 'false' otherwise.")}
(-> a (IO Bit)))
- (def: (resolver promise)
- {#.doc "Sets a promise's value if it has not been done yet."}
- (All [a] (-> (Promise a) (Resolver a)))
+ (def: (resolver async)
+ {#.doc "Sets an async's value if it has not been done yet."}
+ (All [a] (-> (Async a) (Resolver a)))
(function (resolve value)
- (let [promise (:representation promise)]
+ (let [async (:representation async)]
(do {! io.monad}
- [(^@ old [_value _observers]) (atom.read promise)]
+ [(^@ old [_value _observers]) (atom.read async)]
(case _value
(#.Some _)
(wrap #0)
@@ -41,7 +41,7 @@
#.None
(do !
[#let [new [(#.Some value) #.None]]
- succeeded? (atom.compare_and_swap old new promise)]
+ succeeded? (atom.compare_and_swap old new async)]
(if succeeded?
(do !
[_ (monad.map ! (function (_ f) (f value))
@@ -50,29 +50,29 @@
(resolve value))))))))
(def: #export (resolved value)
- {#.doc (doc "Produces a promise that has already been resolved to the given value.")}
- (All [a] (-> a (Promise a)))
+ {#.doc (doc "Produces an async that has already been resolved to the given value.")}
+ (All [a] (-> a (Async a)))
(:abstraction (atom [(#.Some value) (list)])))
- (def: #export (promise _)
- {#.doc (doc "Creates a fresh promise that has not been resolved yet.")}
- (All [a] (-> Any [(Promise a) (Resolver a)]))
- (let [promise (:abstraction (atom [#.None (list)]))]
- [promise (..resolver promise)]))
+ (def: #export (async _)
+ {#.doc (doc "Creates a fresh async that has not been resolved yet.")}
+ (All [a] (-> Any [(Async a) (Resolver a)]))
+ (let [async (:abstraction (atom [#.None (list)]))]
+ [async (..resolver async)]))
(def: #export poll
- {#.doc "Polls a promise for its value."}
- (All [a] (-> (Promise a) (IO (Maybe a))))
+ {#.doc "Polls an async for its value."}
+ (All [a] (-> (Async a) (IO (Maybe a))))
(|>> :representation
atom.read
(\ io.functor map product.left)))
- (def: #export (await f promise)
- {#.doc (doc "Executes the given function as soon as the promise has been resolved.")}
- (All [a] (-> (-> a (IO Any)) (Promise a) (IO Any)))
+ (def: #export (await 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 [promise (:representation promise)]
- (^@ old [_value _observers]) (atom.read promise)]
+ [#let [async (:representation async)]
+ (^@ old [_value _observers]) (atom.read async)]
(case _value
(#.Some value)
(f value)
@@ -80,15 +80,15 @@
#.None
(let [new [_value (#.Cons f _observers)]]
(do !
- [swapped? (atom.compare_and_swap old new promise)]
+ [swapped? (atom.compare_and_swap old new async)]
(if swapped?
(wrap [])
- (await f (:abstraction promise))))))))
+ (await f (:abstraction async))))))))
)
(def: #export resolved?
- {#.doc "Checks whether a promise's value has already been resolved."}
- (All [a] (-> (Promise a) (IO Bit)))
+ {#.doc "Checks whether an async's value has already been resolved."}
+ (All [a] (-> (Async a) (IO Bit)))
(|>> ..poll
(\ io.functor map
(|>> (case> #.None
@@ -98,47 +98,47 @@
#1)))))
(implementation: #export functor
- (Functor Promise)
+ (Functor Async)
(def: (map f fa)
- (let [[fb resolve] (..promise [])]
+ (let [[fb resolve] (..async [])]
(exec (io.run (..await (|>> f resolve) fa))
fb))))
(implementation: #export apply
- (Apply Promise)
+ (Apply Async)
(def: &functor ..functor)
(def: (apply ff fa)
- (let [[fb resolve] (..promise [])]
+ (let [[fb resolve] (..async [])]
(exec (io.run (..await (function (_ f)
(..await (|>> f resolve) fa))
ff))
fb))))
(implementation: #export monad
- (Monad Promise)
+ (Monad Async)
(def: &functor ..functor)
(def: wrap ..resolved)
(def: (join mma)
- (let [[ma resolve] (promise [])]
+ (let [[ma resolve] (async [])]
(exec (io.run (..await (..await resolve) mma))
ma))))
(def: #export (and left right)
- {#.doc (doc "Combines the results of both promises, in-order.")}
- (All [a b] (-> (Promise a) (Promise b) (Promise [a b])))
+ {#.doc (doc "Combines the results of both asyncs, in-order.")}
+ (All [a b] (-> (Async a) (Async b) (Async [a b])))
(let [[read! write!] (:sharing [a b]
- [(Promise a) (Promise b)]
+ [(Async a) (Async b)]
[left right]
- [(Promise [a b])
+ [(Async [a b])
(Resolver [a b])]
- (..promise []))
+ (..async []))
_ (io.run (..await (function (_ left)
(..await (function (_ right)
(write! [left right]))
@@ -147,13 +147,13 @@
read!))
(def: #export (or left right)
- {#.doc (doc "Yields the results of whichever promise gets resolved first."
+ {#.doc (doc "Yields the results of whichever async gets resolved first."
"You can tell which one was resolved first through pattern-matching.")}
- (All [a b] (-> (Promise a) (Promise b) (Promise (| a b))))
- (let [[a|b resolve] (..promise [])]
+ (All [a b] (-> (Async a) (Async b) (Async (| a b))))
+ (let [[a|b resolve] (..async [])]
(with_expansions
- [<sides> (template [<promise> <tag>]
- [(io.run (await (|>> <tag> resolve) <promise>))]
+ [<sides> (template [<async> <tag>]
+ [(io.run (await (|>> <tag> resolve) <async>))]
[left #.Left]
[right #.Right]
@@ -162,12 +162,12 @@
a|b))))
(def: #export (either left right)
- {#.doc (doc "Yields the results of whichever promise gets resolved first."
+ {#.doc (doc "Yields the results of whichever async gets resolved first."
"You cannot tell which one was resolved first.")}
- (All [a] (-> (Promise a) (Promise a) (Promise a)))
- (let [[left||right resolve] (..promise [])]
- (`` (exec (~~ (template [<promise>]
- [(io.run (await resolve <promise>))]
+ (All [a] (-> (Async a) (Async a) (Async a)))
+ (let [[left||right resolve] (..async [])]
+ (`` (exec (~~ (template [<async>]
+ [(io.run (await resolve <async>))]
[left]
[right]))
@@ -176,8 +176,8 @@
(def: #export (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.")}
- (All [a] (-> Nat (IO a) (Promise a)))
- (let [[!out resolve] (..promise [])]
+ (All [a] (-> Nat (IO a) (Async a)))
+ (let [[!out resolve] (..async [])]
(exec (|> (do io.monad
[value computation]
(resolve value))
@@ -187,21 +187,21 @@
(def: #export future
{#.doc (doc "Runs an I/O computation on its own thread."
- "Returns a promise that will eventually host its result.")}
- (All [a] (-> (IO a) (Promise a)))
+ "Returns an async that will eventually host its result.")}
+ (All [a] (-> (IO a) (Async a)))
(..schedule 0))
(def: #export (delay time_millis value)
{#.doc "Delivers a value after a certain period has passed."}
- (All [a] (-> Nat a (Promise a)))
+ (All [a] (-> Nat a (Async a)))
(..schedule time_millis (io value)))
(def: #export (wait time_millis)
- {#.doc "Returns a promise that will be resolved after the specified amount of milliseconds."}
- (-> Nat (Promise Any))
+ {#.doc "Returns an async that will be resolved after the specified amount of milliseconds."}
+ (-> Nat (Async Any))
(..delay time_millis []))
-(def: #export (time_out time_millis promise)
- {#.doc "Wait for a promise to be resolved within the specified amount of milliseconds."}
- (All [a] (-> Nat (Promise a) (Promise (Maybe a))))
- (..or (wait time_millis) promise))
+(def: #export (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))
diff --git a/stdlib/source/library/lux/control/concurrency/frp.lux b/stdlib/source/library/lux/control/concurrency/frp.lux
index f69a88369..fee1a5dda 100644
--- a/stdlib/source/library/lux/control/concurrency/frp.lux
+++ b/stdlib/source/library/lux/control/concurrency/frp.lux
@@ -16,11 +16,11 @@
abstract]]]
[//
["." atom (#+ Atom)]
- ["." promise (#+ Promise) ("#\." functor)]])
+ ["." async (#+ Async) ("#\." functor)]])
(type: #export (Channel a)
{#.doc "An asynchronous channel to distribute values."}
- (Promise (Maybe [a (Channel a)])))
+ (Async (Maybe [a (Channel a)])))
(exception: #export channel_is_already_closed)
@@ -33,7 +33,7 @@
(def: (sink resolve)
(All [a]
- (-> (promise.Resolver (Maybe [a (Channel a)]))
+ (-> (async.Resolver (Maybe [a (Channel a)]))
(Sink a)))
(let [sink (atom.atom resolve)]
(implementation
@@ -59,12 +59,12 @@
(do {! io.monad}
[current (atom.read sink)
#let [[next resolve_next] (:sharing [a]
- (promise.Resolver (Maybe [a (Channel a)]))
+ (async.Resolver (Maybe [a (Channel a)]))
current
- [(Promise (Maybe [a (Channel a)]))
- (promise.Resolver (Maybe [a (Channel a)]))]
- (promise.promise []))]
+ [(Async (Maybe [a (Channel a)]))
+ (async.Resolver (Maybe [a (Channel a)]))]
+ (async.async []))]
fed? (current (#.Some [value next]))]
(if fed?
## I fed the sink.
@@ -83,14 +83,14 @@
(def: #export (channel _)
{#.doc (doc "Creates a brand-new channel and hands it over, along with the sink to write to it.")}
(All [a] (-> Any [(Channel a) (Sink a)]))
- (let [[promise resolve] (promise.promise [])]
- [promise (..sink resolve)]))
+ (let [[async resolve] (async.async [])]
+ [async (..sink resolve)]))
(implementation: #export functor
(Functor Channel)
(def: (map f)
- (promise\map
+ (async\map
(maybe\map
(function (_ [head tail])
[(f head) (map f tail)])))))
@@ -101,7 +101,7 @@
(def: &functor ..functor)
(def: (apply ff fa)
- (do promise.monad
+ (do async.monad
[cons_f ff
cons_a fa]
(case [cons_f cons_a]
@@ -113,7 +113,7 @@
(def: empty
Channel
- (promise.resolved #.None))
+ (async.resolved #.None))
(implementation: #export monad
(Monad Channel)
@@ -121,13 +121,13 @@
(def: &functor ..functor)
(def: (wrap a)
- (promise.resolved (#.Some [a ..empty])))
+ (async.resolved (#.Some [a ..empty])))
(def: (join mma)
(let [[output sink] (channel [])]
- (exec (: (Promise Any)
+ (exec (: (Async Any)
(loop [mma mma]
- (do {! promise.monad}
+ (do {! async.monad}
[?mma mma]
(case ?mma
(#.Some [ma mma'])
@@ -154,9 +154,9 @@
(def: #export (subscribe subscriber channel)
(All [a] (-> (Subscriber a) (Channel a) (IO Any)))
- (io (exec (: (Promise Any)
+ (io (exec (: (Async Any)
(loop [channel channel]
- (do promise.monad
+ (do async.monad
[cons channel]
(case cons
(#.Some [head tail])
@@ -175,7 +175,7 @@
{#.doc (doc "Produces a new channel based on the old one, only with values"
"that pass the test.")}
(All [a] (-> (-> a Bit) (Channel a) (Channel a)))
- (do promise.monad
+ (do async.monad
[cons channel]
(case cons
(#.Some [head tail])
@@ -187,19 +187,19 @@
#.None
(wrap #.None))))
-(def: #export (of_promise promise)
- {#.doc (doc "A one-element channel containing the output from a promise.")}
- (All [a] (-> (Promise a) (Channel a)))
- (promise\map (function (_ value)
- (#.Some [value ..empty]))
- promise))
+(def: #export (of_async async)
+ {#.doc (doc "A one-element channel containing the output from an async.")}
+ (All [a] (-> (Async a) (Channel a)))
+ (async\map (function (_ value)
+ (#.Some [value ..empty]))
+ async))
(def: #export (fold f init channel)
{#.doc "Asynchronous fold over channels."}
(All [a b]
- (-> (-> b a (Promise a)) a (Channel b)
- (Promise a)))
- (do {! promise.monad}
+ (-> (-> b a (Async a)) a (Channel b)
+ (Async a)))
+ (do {! async.monad}
[cons channel]
(case cons
#.None
@@ -212,9 +212,9 @@
(def: #export (folds f init channel)
(All [a b]
- (-> (-> b a (Promise a)) a (Channel b)
+ (-> (-> b a (Async a)) a (Channel b)
(Channel a)))
- (do {! promise.monad}
+ (do {! async.monad}
[cons channel]
(case cons
#.None
@@ -233,7 +233,7 @@
(do io.monad
[value action
_ (\ sink feed value)]
- (promise.await recur (promise.wait milli_seconds)))))
+ (async.await recur (async.wait milli_seconds)))))
[output sink])))
(def: #export (periodic milli_seconds)
@@ -241,8 +241,8 @@
(..poll milli_seconds (io [])))
(def: #export (iterate f init)
- (All [s o] (-> (-> s (Promise (Maybe [s o]))) s (Channel o)))
- (do promise.monad
+ (All [s o] (-> (-> s (Async (Maybe [s o]))) s (Channel o)))
+ (do async.monad
[?next (f init)]
(case ?next
(#.Some [state output])
@@ -253,7 +253,7 @@
(def: (distinct' equivalence previous channel)
(All [a] (-> (Equivalence a) a (Channel a) (Channel a)))
- (do promise.monad
+ (do async.monad
[cons channel]
(case cons
(#.Some [head tail])
@@ -266,7 +266,7 @@
(def: #export (distinct equivalence channel)
(All [a] (-> (Equivalence a) (Channel a) (Channel a)))
- (do promise.monad
+ (do async.monad
[cons channel]
(case cons
(#.Some [head tail])
@@ -276,8 +276,8 @@
(wrap #.None))))
(def: #export (consume channel)
- (All [a] (-> (Channel a) (Promise (List a))))
- (do {! promise.monad}
+ (All [a] (-> (Channel a) (Async (List a))))
+ (do {! async.monad}
[cons channel]
(case cons
(#.Some [head tail])
@@ -295,6 +295,6 @@
..empty
(#.Cons head tail)
- (promise.resolved (#.Some [head (do promise.monad
- [_ (promise.wait milli_seconds)]
- (sequential milli_seconds tail))]))))
+ (async.resolved (#.Some [head (do async.monad
+ [_ (async.wait 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 821250fb3..56b70bbc1 100644
--- a/stdlib/source/library/lux/control/concurrency/semaphore.lux
+++ b/stdlib/source/library/lux/control/concurrency/semaphore.lux
@@ -22,7 +22,7 @@
["." refinement]]]]
[//
["." atom (#+ Atom)]
- ["." promise (#+ Promise Resolver)]])
+ ["." async (#+ Async Resolver)]])
(type: State
{#max_positions Nat
@@ -48,10 +48,10 @@
(def: #export (wait semaphore)
{#.doc (doc "Wait on a semaphore until there are open positions."
"After finishing your work, you must 'signal' to the semaphore that you're done.")}
- (Ex [k] (-> Semaphore (Promise Any)))
+ (Ex [k] (-> Semaphore (Async Any)))
(let [semaphore (:representation semaphore)
- [signal sink] (: [(Promise Any) (Resolver Any)]
- (promise.promise []))]
+ [signal sink] (: [(Async Any) (Resolver Any)]
+ (async.async []))]
(exec (io.run
(with_expansions [<had_open_position?> (as_is (get@ #open_positions) (i.> -1))]
(do io.monad
@@ -73,9 +73,9 @@
(def: #export (signal semaphore)
{#.doc (doc "Signal to a semaphore that you're done with your work, and that there is a new open position.")}
- (Ex [k] (-> Semaphore (Promise (Try Int))))
+ (Ex [k] (-> Semaphore (Async (Try Int))))
(let [semaphore (:representation semaphore)]
- (promise.future
+ (async.future
(do {! io.monad}
[[pre post] (atom.update (function (_ state)
(if (i.= (.int (get@ #max_positions state))
@@ -108,17 +108,17 @@
(:abstraction (semaphore 1)))
(def: acquire
- (-> Mutex (Promise Any))
+ (-> Mutex (Async Any))
(|>> :representation ..wait))
(def: release
- (-> Mutex (Promise Any))
+ (-> Mutex (Async Any))
(|>> :representation ..signal))
(def: #export (synchronize mutex procedure)
{#.doc (doc "Runs the procedure with exclusive control of the mutex.")}
- (All [a] (-> Mutex (IO (Promise a)) (Promise a)))
- (do promise.monad
+ (All [a] (-> Mutex (IO (Async a)) (Async a)))
+ (do async.monad
[_ (..acquire mutex)
output (io.run procedure)
_ (..release mutex)]
@@ -149,18 +149,18 @@
#end_turnstile (..semaphore 0)}))
(def: (un_block times turnstile)
- (-> Nat Semaphore (Promise Any))
+ (-> Nat Semaphore (Async Any))
(loop [step 0]
(if (n.< times step)
- (do promise.monad
+ (do async.monad
[outcome (..signal turnstile)]
(recur (inc step)))
- (\ promise.monad wrap []))))
+ (\ async.monad wrap []))))
(template [<phase> <update> <goal> <turnstile>]
[(def: (<phase> (^:representation barrier))
- (-> Barrier (Promise Any))
- (do promise.monad
+ (-> Barrier (Async Any))
+ (do async.monad
[#let [limit (refinement.un_refine (get@ #limit barrier))
goal <goal>
[_ count] (io.run (atom.update <update> (get@ #count barrier)))
@@ -175,8 +175,8 @@
(def: #export (block barrier)
{#.doc (doc "Wait on a barrier until all processes have arrived and met the barrier's limit.")}
- (-> Barrier (Promise Any))
- (do promise.monad
+ (-> Barrier (Async Any))
+ (do async.monad
[_ (..start barrier)]
(..end barrier)))
)
diff --git a/stdlib/source/library/lux/control/concurrency/stm.lux b/stdlib/source/library/lux/control/concurrency/stm.lux
index 833dff059..3f912c3de 100644
--- a/stdlib/source/library/lux/control/concurrency/stm.lux
+++ b/stdlib/source/library/lux/control/concurrency/stm.lux
@@ -17,7 +17,7 @@
abstract]]]
[//
["." atom (#+ Atom atom)]
- ["." promise (#+ Promise Resolver)]
+ ["." async (#+ Async Resolver)]
["." frp (#+ Channel Sink)]])
(type: (Observer a)
@@ -200,14 +200,14 @@
(type: (Commit a)
[(STM a)
- (Promise a)
+ (Async a)
(Resolver a)])
(def: pending_commits
(Atom (Rec Commits
- [(Promise [(Ex [a] (Commit a)) Commits])
+ [(Async [(Ex [a] (Commit a)) Commits])
(Resolver [(Ex [a] (Commit a)) Commits])]))
- (atom (promise.promise [])))
+ (atom (async.async [])))
(def: commit_processor_flag
(Atom Bit)
@@ -215,12 +215,12 @@
(def: (issue_commit commit)
(All [a] (-> (Commit a) (IO Any)))
- (let [entry [commit (promise.promise [])]]
+ (let [entry [commit (async.async [])]]
(do {! io.monad}
[|commits|&resolve (atom.read pending_commits)]
(loop [[|commits| resolve] |commits|&resolve]
(do !
- [|commits| (promise.poll |commits|)]
+ [|commits| (async.poll |commits|)]
(case |commits|
#.None
(do io.monad
@@ -252,12 +252,12 @@
[was_first? (atom.compare_and_swap flag #1 commit_processor_flag)]
(if was_first?
(do !
- [[promise resolve] (atom.read pending_commits)]
- (promise.await (function (recur [head [tail _resolve]])
- (do !
- [_ (process_commit head)]
- (promise.await recur tail)))
- promise))
+ [[async resolve] (atom.read pending_commits)]
+ (async.await (function (recur [head [tail _resolve]])
+ (do !
+ [_ (process_commit head)]
+ (async.await recur tail)))
+ async))
(wrap [])))
)))
@@ -265,8 +265,8 @@
{#.doc (doc "Commits a transaction and returns its result (asynchronously)."
"Note that a transaction may be re-run an indeterminate number of times if other transactions involving the same variables successfully commit first."
"For this reason, it's important to note that transactions must be free from side-effects, such as I/O.")}
- (All [a] (-> (STM a) (Promise a)))
- (let [[output resolver] (promise.promise [])]
+ (All [a] (-> (STM a) (Async a)))
+ (let [[output resolver] (async.async [])]
(exec (io.run (do io.monad
[_ init_processor!]
(issue_commit [stm_proc output resolver])))
diff --git a/stdlib/source/library/lux/control/function/mutual.lux b/stdlib/source/library/lux/control/function/mutual.lux
index 4ceaaa61f..97d2c3ac1 100644
--- a/stdlib/source/library/lux/control/function/mutual.lux
+++ b/stdlib/source/library/lux/control/function/mutual.lux
@@ -87,8 +87,8 @@
hidden_names (monad.map ! (//.constant (macro.gensym "mutual_function#"))
functions)
#let [definitions (list\map (..mutual_definition hidden_names g!context)
- (list.zip/2 hidden_names
- functions))
+ (list.zipped/2 hidden_names
+ functions))
context_types (list\map (function (_ mutual)
(` (-> (~ g!context) (~ (get@ #type mutual)))))
functions)
@@ -97,8 +97,8 @@
g!pop (local.push (list\map (function (_ [g!name mutual])
[[here_name (get@ [#declaration #declaration.name] mutual)]
(..macro g!context g!name)])
- (list.zip/2 hidden_names
- functions)))]
+ (list.zipped/2 hidden_names
+ functions)))]
(wrap (list (` (.let [(~ g!context) (: (Rec (~ g!context)
[(~+ context_types)])
[(~+ definitions)])
@@ -153,8 +153,8 @@
hidden_names (monad.map ! (//.constant (macro.gensym "mutual_function#"))
functions)
#let [definitions (list\map (..mutual_definition hidden_names g!context)
- (list.zip/2 hidden_names
- (list\map (get@ #mutual) functions)))
+ (list.zipped/2 hidden_names
+ (list\map (get@ #mutual) functions)))
context_types (list\map (function (_ mutual)
(` (-> (~ g!context) (~ (get@ [#mutual #type] mutual)))))
functions)
@@ -163,8 +163,8 @@
g!pop (local.push (list\map (function (_ [g!name mutual])
[[here_name (get@ [#mutual #declaration #declaration.name] mutual)]
(..macro g!context g!name)])
- (list.zip/2 hidden_names
- functions)))]
+ (list.zipped/2 hidden_names
+ functions)))]
(wrap (list& (` (.def: (~ g!context)
[(~+ (list\map (get@ [#mutual #type]) functions))]
(.let [(~ g!context) (: (Rec (~ g!context)
diff --git a/stdlib/source/library/lux/control/parser.lux b/stdlib/source/library/lux/control/parser.lux
index 3dc90e1d2..d017e9dd4 100644
--- a/stdlib/source/library/lux/control/parser.lux
+++ b/stdlib/source/library/lux/control/parser.lux
@@ -221,7 +221,7 @@
_
(#try.Failure "Expected to fail; yet succeeded."))))
-(def: #export (fail message)
+(def: #export (failure message)
(All [s a] (-> Text (Parser s a)))
(function (_ input)
(#try.Failure message)))
diff --git a/stdlib/source/library/lux/control/parser/analysis.lux b/stdlib/source/library/lux/control/parser/analysis.lux
index cdfb18504..df8d140ab 100644
--- a/stdlib/source/library/lux/control/parser/analysis.lux
+++ b/stdlib/source/library/lux/control/parser/analysis.lux
@@ -13,6 +13,8 @@
["%" format (#+ format)]]
[collection
["." list ("#\." functor)]]]
+ [macro
+ ["." template]]
[math
[number
["." i64]
@@ -47,9 +49,11 @@
["Input" (exception.enumerate /.%analysis input)]))
(type: #export Parser
+ {#.doc (doc "A parser for Lux code analysis nodes.")}
(//.Parser (List Analysis)))
(def: #export (run parser input)
+ {#.doc (doc "Executes a parser and makes sure no inputs go unconsumed.")}
(All [a] (-> (Parser a) (List Analysis) (Try a)))
(case (parser input)
(#try.Failure error)
@@ -62,6 +66,7 @@
(exception.throw ..unconsumed_input unconsumed)))
(def: #export any
+ {#.doc (doc "Matches any value, without discrimination.")}
(Parser Analysis)
(function (_ input)
(case input
@@ -89,27 +94,29 @@
_ false)])))
(template [<query> <assertion> <tag> <type> <eq>]
- [(def: #export <query>
- (Parser <type>)
- (function (_ input)
- (case input
- (^ (list& (<tag> x) input'))
- (#try.Success [input' x])
-
- _
- (exception.throw ..cannot_parse input))))
-
- (def: #export (<assertion> expected)
- (-> <type> (Parser Any))
- (function (_ input)
- (case input
- (^ (list& (<tag> actual) input'))
- (if (\ <eq> = expected actual)
- (#try.Success [input' []])
- (exception.throw ..cannot_parse input))
-
- _
- (exception.throw ..cannot_parse input))))]
+ [(`` (as_is (def: #export <query>
+ {#.doc (doc (~~ (template.text ["Queries for a " <query> " value."])))}
+ (Parser <type>)
+ (function (_ input)
+ (case input
+ (^ (list& (<tag> x) input'))
+ (#try.Success [input' x])
+
+ _
+ (exception.throw ..cannot_parse input))))
+
+ (def: #export (<assertion> expected)
+ {#.doc (doc (~~ (template.text ["Assert a specific " <query> " value."])))}
+ (-> <type> (Parser Any))
+ (function (_ input)
+ (case input
+ (^ (list& (<tag> actual) input'))
+ (if (\ <eq> = expected actual)
+ (#try.Success [input' []])
+ (exception.throw ..cannot_parse input))
+
+ _
+ (exception.throw ..cannot_parse input))))))]
[bit bit! /.bit Bit bit.equivalence]
[nat nat! /.nat Nat nat.equivalence]
@@ -123,6 +130,7 @@
)
(def: #export (tuple parser)
+ {#.doc (doc "Parses only within the context of a tuple's contents.")}
(All [a] (-> (Parser a) (Parser a)))
(function (_ input)
(case input
diff --git a/stdlib/source/library/lux/control/parser/binary.lux b/stdlib/source/library/lux/control/parser/binary.lux
index ec06bec54..f7a2cb94a 100644
--- a/stdlib/source/library/lux/control/parser/binary.lux
+++ b/stdlib/source/library/lux/control/parser/binary.lux
@@ -26,9 +26,12 @@
["." frac]]]]]
["." // ("#\." monad)])
-(type: #export Offset Nat)
+(type: #export Offset
+ {#.doc (doc "An offset for reading within binary data.")}
+ Nat)
(type: #export Parser
+ {#.doc (doc "A parser for raw binary data.")}
(//.Parser [Offset Binary]))
(exception: #export (binary_was_not_fully_read {binary_length Nat} {bytes_read Nat})
@@ -37,6 +40,7 @@
["Bytes read" (%.nat bytes_read)]))
(def: #export (run parser input)
+ {#.doc (doc "Runs a parser and checks that all the binary data was read by it.")}
(All [a] (-> (Parser a) Binary (Try a)))
(case (parser [0 input])
(#try.Failure msg)
@@ -49,21 +53,26 @@
(exception.throw ..binary_was_not_fully_read [length end])))))
(def: #export end?
+ {#.doc (doc "Checks whether there is no more data to read.")}
(Parser Bit)
(function (_ (^@ input [offset data]))
(#try.Success [input (n.= offset (/.size data))])))
(def: #export offset
+ {#.doc (doc "The current offset (i.e. how much data has been read).")}
(Parser Offset)
(function (_ (^@ input [offset data]))
(#try.Success [input offset])))
(def: #export remaining
+ {#.doc (doc "How much of the data remains to be read.")}
(Parser Nat)
(function (_ (^@ input [offset data]))
(#try.Success [input (n.- offset (/.size data))])))
-(type: #export Size Nat)
+(type: #export Size
+ {#.doc (doc "The size of a chunk of data within a binary array.")}
+ Nat)
(def: #export size/8 Size 1)
(def: #export size/16 Size (n.* 2 size/8))
@@ -120,12 +129,14 @@
[1 #.Right right]]))
(def: #export (rec body)
+ {#.doc (doc "Tie the knot for a recursive parser.")}
(All [a] (-> (-> (Parser a) (Parser a)) (Parser a)))
(function (_ input)
(let [parser (body (rec body))]
(parser input))))
(def: #export any
+ {#.doc (doc "Does no parsing, and just returns a dummy value.")}
(Parser Any)
(//\wrap []))
@@ -145,6 +156,7 @@
_ (//.lift (exception.throw ..not_a_bit [value])))))
(def: #export (segment size)
+ {#.doc (doc "Parses a chunk of data of a given size.")}
(-> Nat (Parser Binary))
(function (_ [offset binary])
(case size
@@ -153,36 +165,39 @@
(/.slice offset size)
(\ try.monad map (|>> [[(n.+ size offset) binary]]))))))
-(template [<name> <bits>]
- [(def: #export <name>
- (Parser Binary)
- (do //.monad
- [size (//\map .nat <bits>)]
- (..segment size)))]
-
- [binary/8 ..bits/8]
- [binary/16 ..bits/16]
- [binary/32 ..bits/32]
- [binary/64 ..bits/64]
+(template [<size> <name> <bits>]
+ [(`` (def: #export <name>
+ {#.doc (doc (~~ (template.text ["Parses a block of data prefixed with a size that is " <size> " bytes long."])))}
+ (Parser Binary)
+ (do //.monad
+ [size (//\map .nat <bits>)]
+ (..segment size))))]
+
+ [08 binary/8 ..bits/8]
+ [16 binary/16 ..bits/16]
+ [32 binary/32 ..bits/32]
+ [64 binary/64 ..bits/64]
)
-(template [<name> <binary>]
- [(def: #export <name>
- (Parser Text)
- (do //.monad
- [utf8 <binary>]
- (//.lift (\ utf8.codec decode utf8))))]
-
- [utf8/8 ..binary/8]
- [utf8/16 ..binary/16]
- [utf8/32 ..binary/32]
- [utf8/64 ..binary/64]
+(template [<size> <name> <binary>]
+ [(`` (def: #export <name>
+ {#.doc (doc (~~ (template.text ["Parses a block of (UTF-8 encoded) text prefixed with a size that is " <size> " bytes long."])))}
+ (Parser Text)
+ (do //.monad
+ [utf8 <binary>]
+ (//.lift (\ utf8.codec decode utf8)))))]
+
+ [08 utf8/8 ..binary/8]
+ [16 utf8/16 ..binary/16]
+ [32 utf8/32 ..binary/32]
+ [64 utf8/64 ..binary/64]
)
(def: #export text ..utf8/64)
-(template [<name> <bits>]
+(template [<size> <name> <bits>]
[(def: #export (<name> valueP)
+ {#.doc (doc (~~ (template.text ["Parses a row of values prefixed with a size that is " <size> " bytes long."])))}
(All [v] (-> (Parser v) (Parser (Row v))))
(do //.monad
[amount (: (Parser Nat)
@@ -201,10 +216,10 @@
(row.add value output)))
(//\wrap output)))))]
- [row/8 ..bits/8]
- [row/16 ..bits/16]
- [row/32 ..bits/32]
- [row/64 ..bits/64]
+ [08 row/8 ..bits/8]
+ [16 row/16 ..bits/16]
+ [32 row/32 ..bits/32]
+ [64 row/64 ..bits/64]
)
(def: #export maybe
@@ -212,6 +227,7 @@
(..or ..any))
(def: #export (list value)
+ {#.doc (doc "Parses an arbitrarily long list of values.")}
(All [a] (-> (Parser a) (Parser (List a))))
(..rec
(|>> (//.and value)
diff --git a/stdlib/source/library/lux/control/parser/cli.lux b/stdlib/source/library/lux/control/parser/cli.lux
index 7cacdd086..5a66208b4 100644
--- a/stdlib/source/library/lux/control/parser/cli.lux
+++ b/stdlib/source/library/lux/control/parser/cli.lux
@@ -15,6 +15,7 @@
(//.Parser (List Text) a))
(def: #export (run parser inputs)
+ {#.doc (doc "Executes the parser and verifies that all inputs are processed.")}
(All [a] (-> (Parser a) (List Text) (Try a)))
(case (//.run parser inputs)
(#try.Success [remaining output])
@@ -87,12 +88,14 @@
_ (#try.Failure (format "Unknown parameters: " (text.join_with " " inputs))))))
(def: #export (named name value)
+ {#.doc (doc "Parses a named parameter and yields its value.")}
(All [a] (-> Text (Parser a) (Parser a)))
(|> value
(//.after (..this name))
..somewhere))
(def: #export (parameter [short long] value)
+ {#.doc (doc "Parses a parameter that can have either a short or a long name.")}
(All [a] (-> [Text Text] (Parser a) (Parser a)))
(|> value
(//.after (//.either (..this short) (..this long)))
diff --git a/stdlib/source/library/lux/control/parser/json.lux b/stdlib/source/library/lux/control/parser/json.lux
index 0c53041b9..2e9935480 100644
--- a/stdlib/source/library/lux/control/parser/json.lux
+++ b/stdlib/source/library/lux/control/parser/json.lux
@@ -72,7 +72,7 @@
(wrap value)
_
- (//.fail (exception.construct ..unexpected_value [head])))))]
+ (//.failure (exception.construct ..unexpected_value [head])))))]
[null /.Null #/.Null "null"]
[boolean /.Boolean #/.Boolean "boolean"]
@@ -96,7 +96,7 @@
(wrap (\ <equivalence> = test value))
_
- (//.fail (exception.construct ..unexpected_value [head])))))
+ (//.failure (exception.construct ..unexpected_value [head])))))
(def: #export (<check> test)
{#.doc (code.text ($_ text\compose "Ensures a JSON value is a " <desc> "."))}
@@ -107,10 +107,10 @@
(<tag> value)
(if (\ <equivalence> = test value)
(wrap [])
- (//.fail (exception.construct ..value_mismatch [(<tag> test) (<tag> value)])))
+ (//.failure (exception.construct ..value_mismatch [(<tag> test) (<tag> value)])))
_
- (//.fail (exception.construct ..unexpected_value [head])))))]
+ (//.failure (exception.construct ..unexpected_value [head])))))]
[boolean? boolean! /.Boolean bit.equivalence #/.Boolean "boolean"]
[number? number! /.Number frac.equivalence #/.Number "number"]
@@ -131,7 +131,7 @@
(#/.Array values)
(case (//.run parser (row.to_list values))
(#try.Failure error)
- (//.fail error)
+ (//.failure error)
(#try.Success [remainder output])
(case remainder
@@ -139,10 +139,10 @@
(wrap output)
_
- (//.fail (exception.construct ..unconsumed_input remainder))))
+ (//.failure (exception.construct ..unconsumed_input remainder))))
_
- (//.fail (exception.construct ..unexpected_value [head])))))
+ (//.failure (exception.construct ..unexpected_value [head])))))
(def: #export (object parser)
{#.doc "Parses a JSON object. Use this with the 'field' combinator."}
@@ -158,7 +158,7 @@
list.concat
(//.run parser))
(#try.Failure error)
- (//.fail error)
+ (//.failure error)
(#try.Success [remainder output])
(case remainder
@@ -166,10 +166,10 @@
(wrap output)
_
- (//.fail (exception.construct ..unconsumed_input remainder))))
+ (//.failure (exception.construct ..unconsumed_input remainder))))
_
- (//.fail (exception.construct ..unexpected_value [head])))))
+ (//.failure (exception.construct ..unexpected_value [head])))))
(def: #export (field field_name parser)
{#.doc "Parses a field inside a JSON object. Use this inside the 'object' combinator."}
diff --git a/stdlib/source/library/lux/control/parser/type.lux b/stdlib/source/library/lux/control/parser/type.lux
index 73a4a9e4e..d76254fe8 100644
--- a/stdlib/source/library/lux/control/parser/type.lux
+++ b/stdlib/source/library/lux/control/parser/type.lux
@@ -156,7 +156,7 @@
(let [members (<flattener> (type.anonymous headT))]
(if (n.> 1 (list.size members))
(local members poly)
- (//.fail (exception.construct <exception> headT))))))]
+ (//.failure (exception.construct <exception> headT))))))]
[variant type.flat_variant #.Sum ..not_variant]
[tuple type.flat_tuple #.Product ..not_tuple]
@@ -168,7 +168,7 @@
[headT any
#let [[num_arg bodyT] (type.flat_univ_q (type.anonymous headT))]]
(if (n.= 0 num_arg)
- (//.fail (exception.construct ..not_polymorphic headT))
+ (//.failure (exception.construct ..not_polymorphic headT))
(wrap [num_arg bodyT]))))
(def: #export (polymorphic poly)
@@ -216,7 +216,7 @@
(if (n.> 0 (list.size inputsT))
(//.and (local inputsT in_poly)
(local (list outputT) out_poly))
- (//.fail (exception.construct ..not_function headT)))))
+ (//.failure (exception.construct ..not_function headT)))))
(def: #export (applied poly)
(All [a] (-> (Parser a) (Parser a)))
@@ -224,7 +224,7 @@
[headT any
#let [[funcT paramsT] (type.flat_application (type.anonymous headT))]]
(if (n.= 0 (list.size paramsT))
- (//.fail (exception.construct ..not_application headT))
+ (//.failure (exception.construct ..not_application headT))
(..local (#.Cons funcT paramsT) poly))))
(template [<name> <test>]
@@ -234,7 +234,7 @@
[actual any]
(if (<test> expected actual)
(wrap [])
- (//.fail (exception.construct ..types_do_not_match [expected actual])))))]
+ (//.failure (exception.construct ..types_do_not_match [expected actual])))))]
[exactly type\=]
[sub check.checks?]
@@ -260,10 +260,10 @@
(wrap poly_code)
#.None
- (//.fail (exception.construct ..unknown_parameter headT)))
+ (//.failure (exception.construct ..unknown_parameter headT)))
_
- (//.fail (exception.construct ..not_parameter headT)))))
+ (//.failure (exception.construct ..not_parameter headT)))))
(def: #export (parameter! id)
(-> Nat (Parser Any))
@@ -274,10 +274,10 @@
(#.Parameter idx)
(if (n.= id (adjusted_idx env idx))
(wrap [])
- (//.fail (exception.construct ..wrong_parameter [(#.Parameter id) headT])))
+ (//.failure (exception.construct ..wrong_parameter [(#.Parameter id) headT])))
_
- (//.fail (exception.construct ..not_parameter headT)))))
+ (//.failure (exception.construct ..not_parameter headT)))))
(def: #export existential
(Parser Nat)
@@ -288,7 +288,7 @@
(wrap ex_id)
_
- (//.fail (exception.construct ..not_existential headT)))))
+ (//.failure (exception.construct ..not_existential headT)))))
(def: #export named
(Parser [Name Type])
@@ -299,7 +299,7 @@
(wrap [name anonymousT])
_
- (//.fail (exception.construct ..not_named inputT)))))
+ (//.failure (exception.construct ..not_named inputT)))))
(`` (template: (|nothing|)
(#.Named [(~~ (static .prelude_module)) "Nothing"]
@@ -320,7 +320,7 @@
(wrap [recT output]))
_
- (//.fail (exception.construct ..not_recursive headT)))))
+ (//.failure (exception.construct ..not_recursive headT)))))
(def: #export recursive_self
(Parser Code)
@@ -334,7 +334,7 @@
(wrap self_call)
_
- (//.fail (exception.construct ..not_recursive headT)))))
+ (//.failure (exception.construct ..not_recursive headT)))))
(def: #export recursive_call
(Parser Code)
diff --git a/stdlib/source/library/lux/control/region.lux b/stdlib/source/library/lux/control/region.lux
index ff6247418..83a0fe84d 100644
--- a/stdlib/source/library/lux/control/region.lux
+++ b/stdlib/source/library/lux/control/region.lux
@@ -135,7 +135,7 @@
(#try.Failure error)
(wrap [cleaners (#try.Failure error)]))))))
-(def: #export (fail monad error)
+(def: #export (failure monad error)
(All [! a]
(-> (Monad !) Text
(All [r] (Region r ! a))))
@@ -146,7 +146,7 @@
(All [! e a]
(-> (Monad !) (Exception e) e
(All [r] (Region r ! a))))
- (fail monad (exception.construct exception message)))
+ (failure monad (exception.construct exception message)))
(def: #export (lift monad operation)
(All [! a]
diff --git a/stdlib/source/library/lux/control/remember.lux b/stdlib/source/library/lux/control/remember.lux
index f004f109e..c2cc446ed 100644
--- a/stdlib/source/library/lux/control/remember.lux
+++ b/stdlib/source/library/lux/control/remember.lux
@@ -44,7 +44,7 @@
(wrap date)
(#try.Failure message)
- (<>.fail message)))))
+ (<>.failure message)))))
(syntax: #export (remember {deadline ..deadline} {message <c>.text} {focus (<>.maybe <c>.any)})
(let [now (io.run instant.now)
@@ -56,7 +56,7 @@
#.None
(list)))
- (meta.fail (exception.construct ..must_remember [deadline today message focus])))))
+ (meta.failure (exception.construct ..must_remember [deadline today message focus])))))
(template [<name> <message>]
[(syntax: #export (<name> {deadline ..deadline} {message <c>.text} {focus (<>.maybe <c>.any)})
diff --git a/stdlib/source/library/lux/control/security/capability.lux b/stdlib/source/library/lux/control/security/capability.lux
index 13ae40d15..100eea37e 100644
--- a/stdlib/source/library/lux/control/security/capability.lux
+++ b/stdlib/source/library/lux/control/security/capability.lux
@@ -8,7 +8,7 @@
["<c>" code]]
["." io (#+ IO)]
[concurrency
- ["." promise (#+ Promise)]]]
+ ["." async (#+ Async)]]]
[data
[text
["%" format (#+ format)]]
@@ -66,6 +66,6 @@
(def: #export (async capability)
(All [brand input output]
(-> (Capability brand input (IO output))
- (Capability brand input (Promise output))))
- (..forge (|>> ((:representation capability)) promise.future)))
+ (Capability brand input (Async output))))
+ (..forge (|>> ((:representation capability)) async.future)))
)