aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library
diff options
context:
space:
mode:
authorEduardo Julian2021-08-12 03:12:42 -0400
committerEduardo Julian2021-08-12 03:12:42 -0400
commit17629d66062b88b040a2397032f6c08361a5f3a7 (patch)
treebdc6110750b895667b9e45da5e46bec9609f9a7c /stdlib/source/library
parenta62ce3f9c2b605e0033f4772b0f64c4525de4d86 (diff)
Improved binding syntax for "syntax:".
Diffstat (limited to 'stdlib/source/library')
-rw-r--r--stdlib/source/library/lux.lux13
-rw-r--r--stdlib/source/library/lux/abstract/monad/indexed.lux6
-rw-r--r--stdlib/source/library/lux/control/concatenative.lux13
-rw-r--r--stdlib/source/library/lux/control/concurrency/actor.lux36
-rw-r--r--stdlib/source/library/lux/control/concurrency/async.lux24
-rw-r--r--stdlib/source/library/lux/control/concurrency/frp.lux106
-rw-r--r--stdlib/source/library/lux/control/concurrency/semaphore.lux36
-rw-r--r--stdlib/source/library/lux/control/concurrency/stm.lux27
-rw-r--r--stdlib/source/library/lux/control/continuation.lux4
-rw-r--r--stdlib/source/library/lux/control/exception.lux4
-rw-r--r--stdlib/source/library/lux/control/function/contract.lux10
-rw-r--r--stdlib/source/library/lux/control/function/memo.lux2
-rw-r--r--stdlib/source/library/lux/control/function/mutual.lux6
-rw-r--r--stdlib/source/library/lux/control/io.lux4
-rw-r--r--stdlib/source/library/lux/control/lazy.lux4
-rw-r--r--stdlib/source/library/lux/control/parser/json.lux2
-rw-r--r--stdlib/source/library/lux/control/parser/text.lux6
-rw-r--r--stdlib/source/library/lux/control/parser/type.lux10
-rw-r--r--stdlib/source/library/lux/control/pipe.lux63
-rw-r--r--stdlib/source/library/lux/control/reader.lux2
-rw-r--r--stdlib/source/library/lux/control/remember.lux8
-rw-r--r--stdlib/source/library/lux/control/security/capability.lux4
-rw-r--r--stdlib/source/library/lux/control/writer.lux16
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary.lux114
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary/ordered.lux10
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary/plist.lux12
-rw-r--r--stdlib/source/library/lux/data/collection/list.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/row.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/sequence.lux6
-rw-r--r--stdlib/source/library/lux/data/collection/set.lux12
-rw-r--r--stdlib/source/library/lux/data/collection/set/multi.lux14
-rw-r--r--stdlib/source/library/lux/data/collection/set/ordered.lux12
-rw-r--r--stdlib/source/library/lux/data/collection/tree.lux2
-rw-r--r--stdlib/source/library/lux/data/color.lux4
-rw-r--r--stdlib/source/library/lux/data/color/named.lux8
-rw-r--r--stdlib/source/library/lux/data/format/css/property.lux2
-rw-r--r--stdlib/source/library/lux/data/format/css/query.lux2
-rw-r--r--stdlib/source/library/lux/data/format/css/value.lux2
-rw-r--r--stdlib/source/library/lux/data/format/json.lux7
-rw-r--r--stdlib/source/library/lux/data/text.lux6
-rw-r--r--stdlib/source/library/lux/data/text/escape.lux2
-rw-r--r--stdlib/source/library/lux/data/text/format.lux4
-rw-r--r--stdlib/source/library/lux/data/text/regex.lux8
-rw-r--r--stdlib/source/library/lux/data/text/unicode/block.lux2
-rw-r--r--stdlib/source/library/lux/debug.lux49
-rw-r--r--stdlib/source/library/lux/extension.lux5
-rw-r--r--stdlib/source/library/lux/ffi.js.lux33
-rw-r--r--stdlib/source/library/lux/ffi.jvm.lux133
-rw-r--r--stdlib/source/library/lux/ffi.lua.lux19
-rw-r--r--stdlib/source/library/lux/ffi.old.lux111
-rw-r--r--stdlib/source/library/lux/ffi.php.lux8
-rw-r--r--stdlib/source/library/lux/ffi.py.lux37
-rw-r--r--stdlib/source/library/lux/ffi.rb.lux31
-rw-r--r--stdlib/source/library/lux/ffi.scm.lux4
-rw-r--r--stdlib/source/library/lux/locale.lux2
-rw-r--r--stdlib/source/library/lux/macro.lux7
-rw-r--r--stdlib/source/library/lux/macro/local.lux10
-rw-r--r--stdlib/source/library/lux/macro/poly.lux7
-rw-r--r--stdlib/source/library/lux/macro/syntax.lux61
-rw-r--r--stdlib/source/library/lux/macro/template.lux18
-rw-r--r--stdlib/source/library/lux/math/infix.lux2
-rw-r--r--stdlib/source/library/lux/math/modulus.lux2
-rw-r--r--stdlib/source/library/lux/math/number/complex.lux3
-rw-r--r--stdlib/source/library/lux/math/number/ratio.lux3
-rw-r--r--stdlib/source/library/lux/math/random.lux4
-rw-r--r--stdlib/source/library/lux/meta.lux16
-rw-r--r--stdlib/source/library/lux/program.lux5
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode.lux4
-rw-r--r--stdlib/source/library/lux/target/jvm/loader.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/modifier.lux5
-rw-r--r--stdlib/source/library/lux/target/jvm/reflection.lux2
-rw-r--r--stdlib/source/library/lux/target/lua.lux4
-rw-r--r--stdlib/source/library/lux/target/php.lux4
-rw-r--r--stdlib/source/library/lux/target/python.lux4
-rw-r--r--stdlib/source/library/lux/target/r.lux4
-rw-r--r--stdlib/source/library/lux/target/ruby.lux4
-rw-r--r--stdlib/source/library/lux/test.lux20
-rw-r--r--stdlib/source/library/lux/time/date.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/platform.lux20
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux36
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux18
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux9
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux12
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/io/archive.lux16
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/phase.lux6
-rw-r--r--stdlib/source/library/lux/type.lux26
-rw-r--r--stdlib/source/library/lux/type/abstract.lux17
-rw-r--r--stdlib/source/library/lux/type/check.lux4
-rw-r--r--stdlib/source/library/lux/type/dynamic.lux18
-rw-r--r--stdlib/source/library/lux/type/implicit.lux12
-rw-r--r--stdlib/source/library/lux/type/quotient.lux5
-rw-r--r--stdlib/source/library/lux/type/refinement.lux5
-rw-r--r--stdlib/source/library/lux/type/resource.lux6
-rw-r--r--stdlib/source/library/lux/type/unit.lux10
-rw-r--r--stdlib/source/library/lux/world/file.lux16
-rw-r--r--stdlib/source/library/lux/world/file/watch.lux26
-rw-r--r--stdlib/source/library/lux/world/net/http/client.lux6
-rw-r--r--stdlib/source/library/lux/world/net/http/cookie.lux4
-rw-r--r--stdlib/source/library/lux/world/net/http/header.lux8
-rw-r--r--stdlib/source/library/lux/world/net/http/query.lux4
-rw-r--r--stdlib/source/library/lux/world/net/http/request.lux2
-rw-r--r--stdlib/source/library/lux/world/net/http/status.lux2
-rw-r--r--stdlib/source/library/lux/world/output/video/resolution.lux2
-rw-r--r--stdlib/source/library/lux/world/program.lux5
-rw-r--r--stdlib/source/library/lux/world/shell.lux9
128 files changed, 965 insertions, 779 deletions
diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux
index 9034ba1fd..8b03f390b 100644
--- a/stdlib/source/library/lux.lux
+++ b/stdlib/source/library/lux.lux
@@ -1666,19 +1666,6 @@
#None}
plist))
-(def:''' .private (put k v dict)
- #End
- (All [a]
- (-> Text a ($' PList a) ($' PList a)))
- ({#End
- (list [k v])
-
- (#Item [[k' v'] dict'])
- (if (text\= k k')
- (#Item [[k' v] dict'])
- (#Item [[k' v'] (put k v dict')]))}
- dict))
-
(def:''' .private (text\compose x y)
#End
(-> Text Text Text)
diff --git a/stdlib/source/library/lux/abstract/monad/indexed.lux b/stdlib/source/library/lux/abstract/monad/indexed.lux
index 2c2700f8d..9f64ec76d 100644
--- a/stdlib/source/library/lux/abstract/monad/indexed.lux
+++ b/stdlib/source/library/lux/abstract/monad/indexed.lux
@@ -59,9 +59,9 @@
(\ <>.monad map (|>> [#.None])
<code>.any)))
-(syntax: .public (do {[?name monad] ..named_monad}
- {context (<code>.tuple (<>.some context))}
- expression)
+(syntax: .public (do [[?name monad] ..named_monad
+ context (<code>.tuple (<>.some context))
+ expression <code>.any])
(macro.with_identifiers [g!_ g!bind]
(let [body (list\fold (function (_ context next)
(case context
diff --git a/stdlib/source/library/lux/control/concatenative.lux b/stdlib/source/library/lux/control/concatenative.lux
index 554e6b21d..622bb213b 100644
--- a/stdlib/source/library/lux/control/concatenative.lux
+++ b/stdlib/source/library/lux/control/concatenative.lux
@@ -69,9 +69,9 @@
(meta.failure (format "Cannot expand to more than a single AST/Code node:" text.new_line
(|> expansion (list\map %.code) (text.join_with " ")))))))
-(syntax: .public (=> {aliases aliases^}
- {inputs stack^}
- {outputs stack^})
+(syntax: .public (=> [aliases aliases^
+ inputs stack^
+ outputs stack^])
{#.doc (example "Concatenative function types."
(=> [Nat] [Nat])
(All [a] (-> a (=> [] [a])))
@@ -111,7 +111,7 @@
(function (_ [_ top])
top))
-(syntax: .public (||> {commands (<>.some <code>.any)})
+(syntax: .public (||> [commands (<>.some <code>.any)])
{#.doc (example "A self-contained sequence of concatenative instructions."
(is? value
(||> (..push sample)))
@@ -134,8 +134,7 @@
(<>.and (<>\in (` .private)) private)
)))
-(syntax: .public (word:
- {[export_policy name annotations type commands] ..word})
+(syntax: .public (word: [[export_policy name annotations type commands] ..word])
{#.doc (example "A named concatenative function."
(word: square
(=> [Nat] [Nat])
@@ -147,7 +146,7 @@
(~ type)
(|>> (~+ commands)))))))
-(syntax: .public (apply {arity (<>.only (n.> 0) <code>.nat)})
+(syntax: .public (apply [arity (<>.only (n.> 0) <code>.nat)])
{#.doc (example "A generator for functions that turn arity N functions into arity N concatenative functions."
(: (=> [Nat] [Nat])
((apply 1) inc)))}
diff --git a/stdlib/source/library/lux/control/concurrency/actor.lux b/stdlib/source/library/lux/control/concurrency/actor.lux
index 84d41564c..1557a9f89 100644
--- a/stdlib/source/library/lux/control/concurrency/actor.lux
+++ b/stdlib/source/library/lux/control/concurrency/actor.lux
@@ -54,7 +54,7 @@
(Resolver [a Mailbox])])
(IO (List a))))
(do {! io.monad}
- [current (async.poll read)]
+ [current (async.value read)]
(case current
(#.Some [head tail])
(\ ! map (|>> (#.Item head))
@@ -116,7 +116,7 @@
(All [s] (-> (Actor s) (IO Bit)))
(let [[obituary _] (get@ #obituary (:representation actor))]
(|> obituary
- async.poll
+ async.value
(\ io.functor map
(|>> (case> #.None
bit.yes
@@ -127,7 +127,7 @@
(def: .public (obituary' actor)
(All [s] (-> (Actor s) (IO (Maybe (Obituary s)))))
(let [[obituary _] (get@ #obituary (:representation actor))]
- (async.poll obituary)))
+ (async.value obituary)))
(def: .public obituary
{#.doc (example "Await for an actor to stop working.")}
@@ -147,7 +147,7 @@
[|mailbox|&resolve (atom.read! (get@ #mailbox (:representation actor)))]
(loop [[|mailbox| resolve] |mailbox|&resolve]
(do !
- [|mailbox| (async.poll |mailbox|)]
+ [|mailbox| (async.value |mailbox|)]
(case |mailbox|
#.None
(do !
@@ -300,8 +300,7 @@
(message: .public (read! state self)
Nat
(async.resolved (#try.Success [state state])))))]
- (syntax: .public (actor:
- {[export_policy [name vars] annotations state_type [?on_mail messages]] ..actorP})
+ (syntax: .public (actor: [[export_policy [name vars] annotations state_type [?on_mail messages]] ..actorP])
{#.doc (example "Defines a named actor, with its behavior and internal state."
"Messages for the actor must be defined after the on_mail handler."
<examples>)}
@@ -323,8 +322,8 @@
(~+ messages))))))))
- (syntax: .public (actor {[state_type init] (<code>.record (<>.and <code>.any <code>.any))}
- {[?on_mail messages] behavior^})
+ (syntax: .public (actor [[state_type init] (<code>.record (<>.and <code>.any <code>.any))
+ [?on_mail messages] behavior^])
{#.doc (example "Defines an anonymous actor, with its behavior and internal state."
"Messages for the actor must be defined after the on_mail handler."
(actor {Nat
@@ -371,8 +370,7 @@
(<>.and <code>.any private)
(<>.and (<>\in (` .private)) private))))
- (syntax: .public (message:
- {[export_policy signature annotations output_type body] ..messageP})
+ (syntax: .public (message: [[export_policy signature annotations output_type body] ..messageP])
{#.doc (example "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 an async containing a 2-tuple with the updated state and a return value."
@@ -422,12 +420,12 @@
(atom.atom ..continue!))
stop (: Stop
(atom.write! ..stop! signal))]
- (frp.subscribe (function (_ event)
- (do {! io.monad}
- [continue? (atom.read! signal)]
- (if continue?
- (|> actor
- (..mail! (action event stop))
- (\ ! map try.maybe))
- (in #.None))))
- channel)))
+ (frp.subscribe! (function (_ event)
+ (do {! io.monad}
+ [continue? (atom.read! signal)]
+ (if continue?
+ (|> actor
+ (..mail! (action event stop))
+ (\ ! map try.maybe))
+ (in #.None))))
+ channel)))
diff --git a/stdlib/source/library/lux/control/concurrency/async.lux b/stdlib/source/library/lux/control/concurrency/async.lux
index 35ab37cac..32f1913b6 100644
--- a/stdlib/source/library/lux/control/concurrency/async.lux
+++ b/stdlib/source/library/lux/control/concurrency/async.lux
@@ -60,7 +60,7 @@
(let [async (:abstraction (atom [#.None (list)]))]
[async (..resolver async)]))
- (def: .public poll
+ (def: .public value
{#.doc "Polls an async for its value."}
(All [a] (-> (Async a) (IO (Maybe a))))
(|>> :representation
@@ -89,7 +89,7 @@
(def: .public resolved?
{#.doc "Checks whether an async's value has already been resolved."}
(All [a] (-> (Async a) (IO Bit)))
- (|>> ..poll
+ (|>> ..value
(\ io.functor map
(|>> (case> #.None
#0
@@ -178,7 +178,7 @@
[right]))
left||right))))
-(def: .public (schedule! millis_delay computation)
+(def: .public (schedule! milli_seconds computation)
{#.doc (example "Runs an I/O computation on its own thread (after a specified delay)."
"Returns an async that will eventually host its result.")}
(All [a] (-> Nat (IO a) (Async a)))
@@ -187,7 +187,7 @@
(|> (do io.monad
[value computation]
(resolve value))
- (thread.schedule! millis_delay)
+ (thread.schedule! milli_seconds)
io.run!)
!out)))
@@ -197,17 +197,17 @@
(All [a] (-> (IO a) (Async a)))
(..schedule! 0))
-(def: .public (delayed time_millis value)
+(def: .public (delayed milli_seconds value)
{#.doc "Delivers a value after a certain period has passed."}
(All [a] (-> Nat a (Async a)))
- (..schedule! time_millis (io value)))
+ (..schedule! milli_seconds (io value)))
-(def: .public (delay time_millis)
- {#.doc "An async that will be resolved after the specified amount of milliseconds."}
+(def: .public (delay milli_seconds)
+ {#.doc "An async that will be resolved after the specified amount of milli-seconds."}
(-> Nat (Async Any))
- (..delayed time_millis []))
+ (..delayed milli_seconds []))
-(def: .public (time_out time_millis async)
- {#.doc "Wait for an async to be resolved within the specified amount of milliseconds."}
+(def: .public (time_out milli_seconds async)
+ {#.doc "Wait for an async to be resolved within the specified amount of milli-seconds."}
(All [a] (-> Nat (Async a) (Async (Maybe a))))
- (..or (..delay time_millis) async))
+ (..or (..delay milli_seconds) async))
diff --git a/stdlib/source/library/lux/control/concurrency/frp.lux b/stdlib/source/library/lux/control/concurrency/frp.lux
index 32cc8118a..97ed9bf6c 100644
--- a/stdlib/source/library/lux/control/concurrency/frp.lux
+++ b/stdlib/source/library/lux/control/concurrency/frp.lux
@@ -1,6 +1,6 @@
(.module:
[library
- [lux #*
+ [lux (#- list)
[abstract
[equivalence (#+ Equivalence)]
[functor (#+ Functor)]
@@ -124,50 +124,53 @@
(def: (join mma)
(let [[output sink] (channel [])]
- (exec (: (Async Any)
- (loop [mma mma]
- (do {! async.monad}
- [?mma mma]
- (case ?mma
- (#.Some [ma mma'])
- (do !
- [_ (loop [ma ma]
- (do !
- [?ma ma]
- (case ?ma
- (#.Some [a ma'])
- (exec (io.run! (\ sink feed a))
- (recur ma'))
-
- #.None
- (in []))))]
- (recur mma'))
-
- #.None
- (in (: Any (io.run! (\ sink close))))))))
+ (exec
+ (: (Async Any)
+ (loop [mma mma]
+ (do {! async.monad}
+ [?mma mma]
+ (case ?mma
+ (#.Some [ma mma'])
+ (do !
+ [_ (loop [ma ma]
+ (do !
+ [?ma ma]
+ (case ?ma
+ (#.Some [a ma'])
+ (exec
+ (io.run! (\ sink feed a))
+ (recur ma'))
+
+ #.None
+ (in []))))]
+ (recur mma'))
+
+ #.None
+ (in (: Any (io.run! (\ sink close))))))))
output))))
(type: .public (Subscriber a)
{#.doc (example "A function that can receive every value fed into a channel.")}
(-> a (IO (Maybe Any))))
-(def: .public (subscribe subscriber channel)
+(def: .public (subscribe! subscriber channel)
(All [a] (-> (Subscriber a) (Channel a) (IO Any)))
- (io (exec (: (Async Any)
- (loop [channel channel]
- (do async.monad
- [item channel]
- (case item
- (#.Some [head tail])
- (case (io.run! (subscriber head))
- (#.Some _)
- (recur tail)
-
- #.None
- (in []))
-
- #.None
- (in [])))))
+ (io (exec
+ (: (Async Any)
+ (loop [channel channel]
+ (do async.monad
+ [item channel]
+ (case item
+ (#.Some [head tail])
+ (case (io.run! (subscriber head))
+ (#.Some _)
+ (recur tail)
+
+ #.None
+ (in []))
+
+ #.None
+ (in [])))))
[])))
(def: .public (only pass? channel)
@@ -228,11 +231,12 @@
(All [a]
(-> Nat (IO a) [(Channel a) (Sink a)]))
(let [[output sink] (channel [])]
- (exec (io.run! (loop [_ []]
- (do io.monad
- [value action
- _ (\ sink feed value)]
- (async.upon! recur (async.delay milli_seconds)))))
+ (exec
+ (io.run! (loop [_ []]
+ (do io.monad
+ [value action
+ _ (\ sink feed value)]
+ (async.upon! recur (async.delay milli_seconds)))))
[output sink])))
(def: .public (periodic milli_seconds)
@@ -267,21 +271,21 @@
(All [a] (-> (Equivalence a) (Channel a) (Channel a)))
(do async.monad
[item channel]
- (case item
- (#.Some [head tail])
- (in (#.Some [head (distinct' equivalence head tail)]))
-
- #.None
- (in #.None))))
+ (in (case item
+ (#.Some [head tail])
+ (#.Some [head (distinct' equivalence head tail)])
+
+ #.None
+ #.None))))
-(def: .public (consume channel)
+(def: .public (list channel)
(All [a] (-> (Channel a) (Async (List a))))
(do {! async.monad}
[item channel]
(case item
(#.Some [head tail])
(\ ! map (|>> (#.Item head))
- (consume tail))
+ (list tail))
#.None
(in #.End))))
diff --git a/stdlib/source/library/lux/control/concurrency/semaphore.lux b/stdlib/source/library/lux/control/concurrency/semaphore.lux
index 06bb81b4e..55d87e6cd 100644
--- a/stdlib/source/library/lux/control/concurrency/semaphore.lux
+++ b/stdlib/source/library/lux/control/concurrency/semaphore.lux
@@ -45,7 +45,7 @@
#open_positions (.int max_positions)
#waiting_list queue.empty}))))
- (def: .public (wait semaphore)
+ (def: .public (wait! semaphore)
{#.doc (example "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 (Async Any)))
@@ -71,7 +71,7 @@
(exception.report
["Max Positions" (%.nat max_positions)]))
- (def: .public (signal semaphore)
+ (def: .public (signal! semaphore)
{#.doc (example "Signal to a semaphore that you're done with your work, and that there is a new open position.")}
(Ex [k] (-> Semaphore (Async (Try Int))))
(let [semaphore (:representation semaphore)]
@@ -107,21 +107,21 @@
(-> Any Mutex)
(:abstraction (semaphore 1)))
- (def: acquire
+ (def: acquire!
(-> Mutex (Async Any))
- (|>> :representation ..wait))
+ (|>> :representation ..wait!))
- (def: release
+ (def: release!
(-> Mutex (Async Any))
- (|>> :representation ..signal))
+ (|>> :representation ..signal!))
- (def: .public (synchronize mutex procedure)
+ (def: .public (synchronize! mutex procedure)
{#.doc (example "Runs the procedure with exclusive control of the mutex.")}
(All [a] (-> Mutex (IO (Async a)) (Async a)))
(do async.monad
- [_ (..acquire mutex)
+ [_ (..acquire! mutex)
output (io.run! procedure)
- _ (..release mutex)]
+ _ (..release! mutex)]
(in output)))
)
@@ -148,12 +148,12 @@
#start_turnstile (..semaphore 0)
#end_turnstile (..semaphore 0)}))
- (def: (un_block times turnstile)
+ (def: (un_block! times turnstile)
(-> Nat Semaphore (Async Any))
(loop [step 0]
(if (n.< times step)
(do async.monad
- [outcome (..signal turnstile)]
+ [outcome (..signal! turnstile)]
(recur (inc step)))
(\ async.monad in []))))
@@ -166,17 +166,17 @@
[_ count] (io.run! (atom.update! <update> (get@ #count barrier)))
reached? (n.= goal count)]]
(if reached?
- (..un_block (dec limit) (get@ <turnstile> barrier))
- (..wait (get@ <turnstile> barrier)))))]
+ (..un_block! (dec limit) (get@ <turnstile> barrier))
+ (..wait! (get@ <turnstile> barrier)))))]
- [start inc limit #start_turnstile]
- [end dec 0 #end_turnstile]
+ [start! inc limit #start_turnstile]
+ [end! dec 0 #end_turnstile]
)
- (def: .public (block barrier)
+ (def: .public (block! barrier)
{#.doc (example "Wait on a barrier until all processes have arrived and met the barrier's limit.")}
(-> Barrier (Async Any))
(do async.monad
- [_ (..start barrier)]
- (..end barrier)))
+ [_ (..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 321e8bfa8..e76d80b6a 100644
--- a/stdlib/source/library/lux/control/concurrency/stm.lux
+++ b/stdlib/source/library/lux/control/concurrency/stm.lux
@@ -112,7 +112,7 @@
[(#.Item [var value value] tx)
value]))))
-(def: (update_tx_value var value tx)
+(def: (with_updated_var var value tx)
(All [a] (-> (Var a) a Tx Tx))
(case tx
#.End
@@ -128,14 +128,14 @@
(#.Item {#var _var
#original _original
#current _current}
- (update_tx_value var value tx')))))
+ (with_updated_var var value tx')))))
(def: .public (write value var)
(All [a] (-> a (Var a) (STM Any)))
(function (_ tx)
(case (var_value var tx)
(#.Some _)
- [(update_tx_value var value tx)
+ [(with_updated_var var value tx)
[]]
#.None
@@ -213,14 +213,14 @@
(Atom Bit)
(atom #0))
-(def: (issue_commit commit)
+(def: (issue_commit! commit)
(All [a] (-> (Commit a) (IO Any)))
(let [entry [commit (async.async [])]]
(do {! io.monad}
[|commits|&resolve (atom.read! pending_commits)]
(loop [[|commits| resolve] |commits|&resolve]
(do !
- [|commits| (async.poll |commits|)]
+ [|commits| (async.value |commits|)]
(case |commits|
#.None
(do io.monad
@@ -232,17 +232,17 @@
(#.Some [head tail])
(recur tail)))))))
-(def: (process_commit commit)
+(def: (process_commit! commit)
(All [a] (-> (Commit a) (IO Any)))
(let [[stm_proc output resolve] commit
[finished_tx value] (stm_proc fresh_tx)]
(if (can_commit? finished_tx)
(do {! io.monad}
- [_ (monad.map ! commit_var! finished_tx)]
+ [_ (monad.map ! ..commit_var! finished_tx)]
(resolve value))
- (issue_commit commit))))
+ (..issue_commit! commit))))
-(def: init_processor!
+(def: start_commit_processor!
(IO Any)
(do {! io.monad}
[flag (atom.read! commit_processor_flag)]
@@ -255,7 +255,7 @@
[[async resolve] (atom.read! pending_commits)]
(async.upon! (function (recur [head [tail _resolve]])
(do !
- [_ (process_commit head)]
+ [_ (..process_commit! head)]
(async.upon! recur tail)))
async))
(in [])))
@@ -267,7 +267,8 @@
"For this reason, it's important to note that transactions must be free from side-effects, such as I/O.")}
(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])))
+ (exec
+ (io.run! (do io.monad
+ [_ ..start_commit_processor!]
+ (..issue_commit! [stm_proc output resolver])))
output)))
diff --git a/stdlib/source/library/lux/control/continuation.lux b/stdlib/source/library/lux/control/continuation.lux
index 7a46ed8a7..e9b702f55 100644
--- a/stdlib/source/library/lux/control/continuation.lux
+++ b/stdlib/source/library/lux/control/continuation.lux
@@ -8,7 +8,7 @@
[control
["." function]
[parser
- ["s" code]]]
+ ["<.>" code]]]
[macro (#+ with_identifiers)
[syntax (#+ syntax:)]
["." code]]]])
@@ -37,7 +37,7 @@
(f (function (_ a) (function (_ _) (k a)))
k)))
-(syntax: .public (pending expr)
+(syntax: .public (pending [expr <code>.any])
{#.doc (example "Turns any expression into a function that is pending a continuation."
(pending (some_function some_input)))}
(with_identifiers [g!_ g!k]
diff --git a/stdlib/source/library/lux/control/exception.lux b/stdlib/source/library/lux/control/exception.lux
index ee5fd753a..9a9e7f845 100644
--- a/stdlib/source/library/lux/control/exception.lux
+++ b/stdlib/source/library/lux/control/exception.lux
@@ -97,7 +97,7 @@
(<>.and (<>\in (` .private)) private)
)))
-(syntax: .public (exception: {[export_policy t_vars [name inputs] body] ..exception})
+(syntax: .public (exception: [[export_policy t_vars [name inputs] body] ..exception])
{#.doc (example "Define a new exception type."
"It mostly just serves as a way to tag error messages for later catching."
""
@@ -153,7 +153,7 @@
(on_entry head)
tail))))
-(syntax: .public (report {entries (<>.many (<code>.tuple (<>.and <code>.any <code>.any)))})
+(syntax: .public (report [entries (<>.many (<code>.tuple (<>.and <code>.any <code>.any)))])
{#.doc (example "An error report."
(: Text
(report ["Row 0" value/0]
diff --git a/stdlib/source/library/lux/control/function/contract.lux b/stdlib/source/library/lux/control/function/contract.lux
index ce62f8c45..0fb706a14 100644
--- a/stdlib/source/library/lux/control/function/contract.lux
+++ b/stdlib/source/library/lux/control/function/contract.lux
@@ -2,7 +2,9 @@
[library
[lux #*
[control
- ["." exception (#+ exception:)]]
+ ["." exception (#+ exception:)]
+ [parser
+ ["<.>" code]]]
[data
[text
["%" format (#+ format)]]]
@@ -28,7 +30,8 @@
[]
(panic! message)))
-(syntax: .public (pre test expr)
+(syntax: .public (pre [test <code>.any
+ expr <code>.any])
{#.doc (example "Pre-conditions."
"Given a test and an expression to run, only runs the expression if the test passes."
"Otherwise, an error is raised."
@@ -39,7 +42,8 @@
(~ test))
(~ expr))))))
-(syntax: .public (post test expr)
+(syntax: .public (post [test <code>.any
+ expr <code>.any])
{#.doc (example "Post-conditions."
"Given a predicate and an expression to run, evaluates the expression and then tests the output with the predicate."
"If the predicate returns #1, returns the value of the expression."
diff --git a/stdlib/source/library/lux/control/function/memo.lux b/stdlib/source/library/lux/control/function/memo.lux
index 924ec4c00..ae8c4e9bf 100644
--- a/stdlib/source/library/lux/control/function/memo.lux
+++ b/stdlib/source/library/lux/control/function/memo.lux
@@ -29,7 +29,7 @@
#.None
(do !
[output (delegate input)
- _ (state.update (dictionary.put input output))]
+ _ (state.update (dictionary.has input output))]
(in output)))))))
(type: .public (Memo i o)
diff --git a/stdlib/source/library/lux/control/function/mutual.lux b/stdlib/source/library/lux/control/function/mutual.lux
index e9cac3871..fd36ac10b 100644
--- a/stdlib/source/library/lux/control/function/mutual.lux
+++ b/stdlib/source/library/lux/control/function/mutual.lux
@@ -52,8 +52,8 @@
(function (_ parameters)
(\ meta.monad in (list (` (((~ g!self) (~ g!context)) (~+ parameters))))))))
-(syntax: .public (let {functions (<code>.tuple (<>.some ..mutual))}
- body)
+(syntax: .public (let [functions (<code>.tuple (<>.some ..mutual))
+ body <code>.any])
{#.doc (example "Locally-defined mutually-recursive functions."
(let [(even? number)
(-> Nat Bit)
@@ -118,7 +118,7 @@
(<code>.tuple (<>.either (<>.and <code>.any ..mutual)
(<>.and (<>\in (` .private)) ..mutual))))
-(syntax: .public (def: {functions (<>.many ..definition)})
+(syntax: .public (def: [functions (<>.many ..definition)])
{#.doc (example "Globally-defined mutually-recursive functions."
(def:
[.public (even? number)
diff --git a/stdlib/source/library/lux/control/io.lux b/stdlib/source/library/lux/control/io.lux
index bcb0f4d8c..321b7159e 100644
--- a/stdlib/source/library/lux/control/io.lux
+++ b/stdlib/source/library/lux/control/io.lux
@@ -8,7 +8,7 @@
[monad (#+ Monad do)]]
[control
[parser
- ["s" code]]]
+ ["<.>" code]]]
[type
abstract]
[macro (#+ with_identifiers)
@@ -33,7 +33,7 @@
... creatio ex nihilo
[((:representation io) [])])
- (syntax: .public (io computation)
+ (syntax: .public (io [computation <code>.any])
{#.doc (example "Delays the evaluation of an expression, by wrapping it in an IO 'thunk'."
"Great for wrapping effectful computations (which will not be performed until the IO is 'run!')."
(io (exec
diff --git a/stdlib/source/library/lux/control/lazy.lux b/stdlib/source/library/lux/control/lazy.lux
index 677832ebd..dec12c5f5 100644
--- a/stdlib/source/library/lux/control/lazy.lux
+++ b/stdlib/source/library/lux/control/lazy.lux
@@ -9,7 +9,7 @@
[control
["." io]
[parser
- ["s" code]]
+ ["<.>" code]]
[concurrency
["." atom]]]
[macro (#+ with_identifiers)
@@ -41,7 +41,7 @@
(All [a] (-> (Lazy a) a))
((:representation lazy) [])))
-(syntax: .public (lazy expression)
+(syntax: .public (lazy [expression <code>.any])
{#.doc (example "Specifies a lazy value by providing the expression that computes it.")}
(with_identifiers [g!_]
(in (list (` ((~! lazy') (function ((~ g!_) (~ g!_)) (~ expression))))))))
diff --git a/stdlib/source/library/lux/control/parser/json.lux b/stdlib/source/library/lux/control/parser/json.lux
index 133f78332..51c3cc2bf 100644
--- a/stdlib/source/library/lux/control/parser/json.lux
+++ b/stdlib/source/library/lux/control/parser/json.lux
@@ -159,7 +159,7 @@
dictionary.entries
(list\map (function (_ [key value])
(list (#/.String key) value)))
- list.concat
+ list.joined
(//.result parser))
(#try.Failure error)
(//.failure error)
diff --git a/stdlib/source/library/lux/control/parser/text.lux b/stdlib/source/library/lux/control/parser/text.lux
index 8d314634c..8ca2af321 100644
--- a/stdlib/source/library/lux/control/parser/text.lux
+++ b/stdlib/source/library/lux/control/parser/text.lux
@@ -302,7 +302,7 @@
[(def: .public (<name> parser)
{#.doc (code.text ($_ /\compose "Yields " <doc_modifier> " characters as a single continuous text (as a slice)."))}
(-> (Parser Text) (Parser Text))
- (|> parser <base> (\ //.monad map /.concat)))]
+ (|> parser <base> (\ //.monad map /.joined)))]
[some //.some "some"]
[many //.many "many"]
@@ -324,7 +324,7 @@
(-> Nat (Parser Text) (Parser Text))
(|> parser
(<base> amount)
- (\ //.monad map /.concat)))]
+ (\ //.monad map /.joined)))]
[exactly //.exactly "exactly"]
[at_most //.at_most "at most"]
@@ -347,7 +347,7 @@
(-> Nat Nat (Parser Text) (Parser Text))
(|> parser
(//.between minimum additional)
- (\ //.monad map /.concat)))
+ (\ //.monad map /.joined)))
(def: .public (between! minimum additional parser)
(-> Nat Nat (Parser Slice) (Parser Slice))
diff --git a/stdlib/source/library/lux/control/parser/type.lux b/stdlib/source/library/lux/control/parser/type.lux
index aaebfb594..964513f24 100644
--- a/stdlib/source/library/lux/control/parser/type.lux
+++ b/stdlib/source/library/lux/control/parser/type.lux
@@ -152,7 +152,7 @@
(let [current_id (dictionary.size env)
g!var (label current_id)]
(case (//.result poly
- [(dictionary.put current_id [type g!var] env)
+ [(dictionary.has current_id [type g!var] env)
inputs])
(#try.Failure error)
(#try.Failure error)
@@ -200,8 +200,8 @@
(let [varL (label (inc funcI))]
(recur (inc current_arg)
(|> env'
- (dictionary.put funcI [headT funcL])
- (dictionary.put (inc funcI) [(#.Parameter (inc funcI)) varL]))
+ (dictionary.has funcI [headT funcL])
+ (dictionary.has (inc funcI) [(#.Parameter (inc funcI)) varL]))
(#.Item varL all_varsL)))
(let [partialI (|> current_arg (n.* 2) (n.+ funcI))
partial_varI (inc partialI)
@@ -211,8 +211,8 @@
list.reversed))))]
(recur (inc current_arg)
(|> env'
- (dictionary.put partialI [.Nothing partialC])
- (dictionary.put partial_varI [(#.Parameter partial_varI) partial_varL]))
+ (dictionary.has partialI [.Nothing partialC])
+ (dictionary.has partial_varI [(#.Parameter partial_varI) partial_varL]))
(#.Item partial_varL all_varsL))))
[all_varsL env']))]]
(<| (with_env env')
diff --git a/stdlib/source/library/lux/control/pipe.lux b/stdlib/source/library/lux/control/pipe.lux
index 07f38e15e..4d31c2035 100644
--- a/stdlib/source/library/lux/control/pipe.lux
+++ b/stdlib/source/library/lux/control/pipe.lux
@@ -5,9 +5,9 @@
[abstract
[monad (#+ do)]]
[control
- ["e" try]
- ["p" parser
- ["s" code (#+ Parser)]]]
+ ["." try]
+ ["<>" parser
+ ["<.>" code (#+ Parser)]]]
[data
["." identity]
[collection
@@ -22,11 +22,11 @@
(def: body^
(Parser (List Code))
- (s.tuple (p.some s.any)))
+ (<code>.tuple (<>.some <code>.any)))
-(syntax: .public (new> start
- {body body^}
- prev)
+(syntax: .public (new> [start <code>.any
+ body body^
+ prev <code>.any])
{#.doc (example "Ignores the piped argument, and begins a new pipe."
(n.= 1
(|> 20
@@ -35,7 +35,9 @@
(new> 0 [inc]))))}
(in (list (` (|> (~ start) (~+ body))))))
-(syntax: .public (let> binding body prev)
+(syntax: .public (let> [binding <code>.any
+ body <code>.any
+ prev <code>.any])
{#.doc (example "Gives a name to the piped-argument, within the given expression."
(n.= 10
(|> 5
@@ -46,13 +48,13 @@
(def: _reversed_
(Parser Any)
(function (_ tokens)
- (#e.Success [(list.reversed tokens) []])))
+ (#try.Success [(list.reversed tokens) []])))
-(syntax: .public (cond> {_ _reversed_}
- prev
- {else body^}
- {_ _reversed_}
- {branches (p.some (p.and body^ body^))})
+(syntax: .public (cond> [_ _reversed_
+ prev <code>.any
+ else body^
+ _ _reversed_
+ branches (<>.some (<>.and body^ body^))])
{#.doc (example "Branching for pipes."
"Both the tests and the bodies are piped-code, and must be given inside a tuple."
(|> +5
@@ -67,7 +69,10 @@
(` (|> (~ g!temp) (~+ then))))))
(|> (~ g!temp) (~+ else)))))))))
-(syntax: .public (if> {test body^} {then body^} {else body^} prev)
+(syntax: .public (if> [test body^
+ then body^
+ else body^
+ prev <code>.any])
{#.doc (example "If-branching."
(is? (if (n.even? sample)
"even"
@@ -80,7 +85,9 @@
[(~+ else)]
(~ prev))))))
-(syntax: .public (when> {test body^} {then body^} prev)
+(syntax: .public (when> [test body^
+ then body^
+ prev <code>.any])
{#.doc (example "Only execute the body when the test passes."
(is? (if (n.even? sample)
(n.* 2 sample)
@@ -92,9 +99,9 @@
[]
(~ prev))))))
-(syntax: .public (loop> {test body^}
- {then body^}
- prev)
+(syntax: .public (loop> [test body^
+ then body^
+ prev <code>.any])
{#.doc (example "Loops for pipes."
"Both the testing and calculating steps are pipes and must be given inside tuples."
(|> +1
@@ -106,9 +113,9 @@
((~' recur) (|> (~ g!temp) (~+ then)))
(~ g!temp))))))))
-(syntax: .public (do> monad
- {steps (p.some body^)}
- prev)
+(syntax: .public (do> [monad <code>.any
+ steps (<>.some body^)
+ prev <code>.any])
{#.doc (example "Monadic pipes."
"Each steps in the monadic computation is a pipe and must be given inside a tuple."
(|> +5
@@ -130,8 +137,8 @@
_
(in (list prev)))))
-(syntax: .public (exec> {body body^}
- prev)
+(syntax: .public (exec> [body body^
+ prev <code>.any])
{#.doc (example "Non-updating pipes."
"Will generate piped computations, but their results will not be used in the larger scope."
(|> +5
@@ -142,8 +149,8 @@
(exec (|> (~ g!temp) (~+ body))
(~ g!temp))))))))
-(syntax: .public (tuple> {paths (p.many body^)}
- prev)
+(syntax: .public (tuple> [paths (<>.many body^)
+ prev <code>.any])
{#.doc (example "Parallel branching for pipes."
"Allows to run multiple pipelines for a value and gives you a tuple of the outputs."
(|> +5
@@ -156,8 +163,8 @@
[(~+ (list\map (function (_ body) (` (|> (~ g!temp) (~+ body))))
paths))]))))))
-(syntax: .public (case> {branches (p.many (p.and s.any s.any))}
- prev)
+(syntax: .public (case> [branches (<>.many (<>.and <code>.any <code>.any))
+ prev <code>.any])
{#.doc (example "Pattern-matching for pipes."
"The bodies of each branch are NOT pipes; just regular values."
(|> +5
diff --git a/stdlib/source/library/lux/control/reader.lux b/stdlib/source/library/lux/control/reader.lux
index b2e5b9399..73737cb54 100644
--- a/stdlib/source/library/lux/control/reader.lux
+++ b/stdlib/source/library/lux/control/reader.lux
@@ -10,7 +10,7 @@
{#.doc "Computations that have access to some environmental value."}
(-> r a))
-(def: .public ask
+(def: .public read
{#.doc "Get the environment."}
(All [r] (Reader r r))
(function (_ env) env))
diff --git a/stdlib/source/library/lux/control/remember.lux b/stdlib/source/library/lux/control/remember.lux
index f4f9c4213..25b595b63 100644
--- a/stdlib/source/library/lux/control/remember.lux
+++ b/stdlib/source/library/lux/control/remember.lux
@@ -47,7 +47,9 @@
(#try.Failure message)
(<>.failure message)))))
-(syntax: .public (remember {deadline ..deadline} {message <c>.text} {focus (<>.maybe <c>.any)})
+(syntax: .public (remember [deadline ..deadline
+ message <c>.text
+ focus (<>.maybe <c>.any)])
{#.doc (example "A message with an expiration date."
"Can have an optional piece of code to focus on."
(remember "2022-04-01"
@@ -67,7 +69,9 @@
(meta.failure (exception.error ..must_remember [deadline today message focus])))))
(template [<name> <message>]
- [(`` (syntax: .public (<name> {deadline ..deadline} {message <c>.text} {focus (<>.maybe <c>.any)})
+ [(`` (syntax: .public (<name> [deadline ..deadline
+ message <c>.text
+ focus (<>.maybe <c>.any)])
{#.doc (example (~~ (template.text ["A " <message> " message with an expiration date."]))
"Can have an optional piece of code to focus on."
(<name> "2022-04-01"
diff --git a/stdlib/source/library/lux/control/security/capability.lux b/stdlib/source/library/lux/control/security/capability.lux
index bf689a80c..cebf0534e 100644
--- a/stdlib/source/library/lux/control/security/capability.lux
+++ b/stdlib/source/library/lux/control/security/capability.lux
@@ -44,12 +44,12 @@
output))
((:representation capability) input))
- (syntax: .public (capability: {[export_policy declaration annotations [forger input output]]
+ (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))))})
+ (<c>.form ($_ <>.and <c>.local_identifier <c>.any <c>.any))))])
{#.doc (example "Defines a capability as a unique type, and a constructor for instances."
(capability: (Can_Duplicate a)
diff --git a/stdlib/source/library/lux/control/writer.lux b/stdlib/source/library/lux/control/writer.lux
index 7ac976d6b..fe7511a68 100644
--- a/stdlib/source/library/lux/control/writer.lux
+++ b/stdlib/source/library/lux/control/writer.lux
@@ -8,15 +8,15 @@
["." functor (#+ Functor)]
["." monad (#+ Monad do)]]]])
-(type: .public (Writer l a)
- {#.doc "Represents a value with an associated 'log' value to record arbitrary information."}
- {#log l
- #value a})
+(type: .public (Writer log value)
+ {#.doc "Represents a value with an associated 'log' to record arbitrary information."}
+ {#log log
+ #value value})
-(def: .public (write l)
- {#.doc "Set the log to a particular value."}
- (All [l] (-> l (Writer l Any)))
- [l []])
+(def: .public (write message)
+ {#.doc "Write a value to the log."}
+ (All [log] (-> log (Writer log Any)))
+ [message []])
(implementation: .public functor
(All [l]
diff --git a/stdlib/source/library/lux/data/collection/dictionary.lux b/stdlib/source/library/lux/data/collection/dictionary.lux
index e86eb437b..3d0e729ce 100644
--- a/stdlib/source/library/lux/data/collection/dictionary.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary.lux
@@ -139,7 +139,7 @@
(array.copy! (n.- idx old_size) idx old_array (inc idx)))))
... Creates a copy of an array with an index set to a particular value.
-(def: (update! idx value array)
+(def: (revised! idx value array)
(All [a] (-> Index a (Array a) (Array a)))
(|> array array.clone (array.write! idx value)))
@@ -149,7 +149,7 @@
(|> array array.clone (array.delete! idx)))
... Shrinks a copy of the array by removing the space at index.
-(def: (remove! idx array)
+(def: (lacks! idx array)
(All [a] (-> Index (Array a) (Array a)))
(let [new_size (dec (array.size array))]
(|> (array.empty new_size)
@@ -254,7 +254,7 @@
(List Index)
(list.indices hierarchy_nodes_size))
-(def: (promotion put' key_hash level bitmap base)
+(def: (promotion has' key_hash level bitmap base)
(All [k v]
(-> (-> Level Hash_Code k v (Hash k) (Node k v) (Node k v))
(Hash k) Level
@@ -270,7 +270,7 @@
(#.Some (#.Right [key' val']))
(array.write! hierarchy_idx
- (put' (level_up level) (\ key_hash hash key') key' val' key_hash empty_node)
+ (has' (level_up level) (\ key_hash hash key') key' val' key_hash empty_node)
h_array)
#.None
@@ -292,7 +292,7 @@
_
#0)))
-(def: (put' level hash key val key_hash node)
+(def: (has' level hash key val key_hash node)
(All [k v] (-> Level Hash_Code k v (Hash k) (Node k v) (Node k v)))
(case node
... For #Hierarchy nodes, check whether one can add the element to
@@ -306,8 +306,8 @@
_
[(inc _size) empty_node])]
(#Hierarchy _size'
- (update! idx (put' (level_up level) hash key val key_hash sub_node)
- hierarchy)))
+ (revised! idx (has' (level_up level) hash key val key_hash sub_node)
+ hierarchy)))
... For #Base nodes, check if the corresponding Bit_Position has
... already been used.
@@ -319,35 +319,35 @@
(case (array.read idx base)
... If it's being used by a node, add the KV to it.
(#.Some (#.Left sub_node))
- (let [sub_node' (put' (level_up level) hash key val key_hash sub_node)]
- (#Base bitmap (update! idx (#.Left sub_node') base)))
+ (let [sub_node' (has' (level_up level) hash key val key_hash sub_node)]
+ (#Base bitmap (revised! idx (#.Left sub_node') base)))
... Otherwise, if it's being used by a KV, compare the keys.
(#.Some (#.Right key' val'))
(if (\ key_hash = key key')
... If the same key is found, replace the value.
- (#Base bitmap (update! idx (#.Right key val) base))
+ (#Base bitmap (revised! idx (#.Right key val) base))
... Otherwise, compare the hashes of the keys.
- (#Base bitmap (update! idx
- (#.Left (let [hash' (\ key_hash hash key')]
- (if (n.= hash hash')
- ... If the hashes are
- ... the same, a new
- ... #Collisions node
- ... is added.
- (#Collisions hash (|> (array.empty 2)
- (array.write! 0 [key' val'])
- (array.write! 1 [key val])))
- ... Otherwise, one can
- ... just keep using
- ... #Base nodes, so
- ... add both KV-pairs
- ... to the empty one.
- (let [next_level (level_up level)]
- (|> empty_node
- (put' next_level hash' key' val' key_hash)
- (put' next_level hash key val key_hash))))))
- base)))
+ (#Base bitmap (revised! idx
+ (#.Left (let [hash' (\ key_hash hash key')]
+ (if (n.= hash hash')
+ ... If the hashes are
+ ... the same, a new
+ ... #Collisions node
+ ... is added.
+ (#Collisions hash (|> (array.empty 2)
+ (array.write! 0 [key' val'])
+ (array.write! 1 [key val])))
+ ... Otherwise, one can
+ ... just keep using
+ ... #Base nodes, so
+ ... add both KV-pairs
+ ... to the empty one.
+ (let [next_level (level_up level)]
+ (|> empty_node
+ (has' next_level hash' key' val' key_hash)
+ (has' next_level hash key val key_hash))))))
+ base)))
#.None
(undefined)))
@@ -359,9 +359,9 @@
... KV-pair as a singleton node to it.
(#Hierarchy (inc base_count)
(|> base
- (promotion put' key_hash level bitmap)
+ (promotion has' key_hash level bitmap)
(array.write! (level_index level hash)
- (put' (level_up level) hash key val key_hash empty_node))))
+ (has' (level_up level) hash key val key_hash empty_node))))
... Otherwise, just resize the #Base node to accommodate the
... new KV-pair.
(#Base (with_bit_position bit bitmap)
@@ -376,7 +376,7 @@
... If the key was already present in the collisions-list, its
... value gets updated.
(#.Some coll_idx)
- (#Collisions _hash (update! coll_idx [key val] _colls))
+ (#Collisions _hash (revised! coll_idx [key val] _colls))
... Otherwise, the KV-pair is added to the collisions-list.
#.None
@@ -386,10 +386,10 @@
(|> (#Base (level_bit_position level _hash)
(|> (array.empty 1)
(array.write! 0 (#.Left node))))
- (put' level hash key val key_hash)))
+ (has' level hash key val key_hash)))
))
-(def: (remove' level hash key key_hash node)
+(def: (lacks' level hash key key_hash node)
(All [k v] (-> Level Hash_Code k (Hash k) (Node k v) (Node k v)))
(case node
... For #Hierarchy nodes, find out if there's a valid sub-node for
@@ -403,7 +403,7 @@
... But if there is, try to remove the key from the sub-node.
(#.Some sub_node)
- (let [sub_node' (remove' (level_up level) hash key key_hash sub_node)]
+ (let [sub_node' (lacks' (level_up level) hash key key_hash sub_node)]
... Then check if a removal was actually done.
(if (is? sub_node sub_node')
... If not, then there's nothing to change here either.
@@ -418,7 +418,7 @@
(#Hierarchy (dec h_size) (vacant! idx h_array)))
... But if the sub_removal yielded a non_empty node, then
... just update the hiearchy branch.
- (#Hierarchy h_size (update! idx sub_node' h_array)))))))
+ (#Hierarchy h_size (revised! idx sub_node' h_array)))))))
... For #Base nodes, check whether the Bit_Position is set.
(#Base bitmap base)
@@ -429,7 +429,7 @@
... If set, check if it's a sub_node, and remove the KV
... from it.
(#.Some (#.Left sub_node))
- (let [sub_node' (remove' (level_up level) hash key key_hash sub_node)]
+ (let [sub_node' (lacks' (level_up level) hash key key_hash sub_node)]
... Verify that it was removed.
(if (is? sub_node sub_node')
... If not, there's also nothing to change here.
@@ -443,11 +443,11 @@
... But if not, then just unset the position and
... remove the node.
(#Base (without_bit_position bit bitmap)
- (remove! idx base)))
+ (lacks! idx base)))
... But, if it did not come out empty, then the
... position is kept, and the node gets updated.
(#Base bitmap
- (update! idx (#.Left sub_node') base)))))
+ (revised! idx (#.Left sub_node') base)))))
... If, however, there was a KV-pair instead of a sub-node.
(#.Some (#.Right [key' val']))
@@ -455,7 +455,7 @@
(if (\ key_hash = key key')
... If so, remove the KV-pair and unset the Bit_Position.
(#Base (without_bit_position bit bitmap)
- (remove! idx base))
+ (lacks! idx base))
... Otherwise, there's nothing to remove.
node)
@@ -478,7 +478,7 @@
... an empty node.
empty_node
... Otherwise, just shrink the array by removing the KV-pair.
- (#Collisions _hash (remove! idx _colls))))
+ (#Collisions _hash (lacks! idx _colls))))
))
(def: (get' level hash key key_hash node)
@@ -570,15 +570,15 @@
{#hash key_hash
#root empty_node})
-(def: .public (put key val dict)
+(def: .public (has key val dict)
(All [k v] (-> k v (Dictionary k v) (Dictionary k v)))
(let [[key_hash node] dict]
- [key_hash (put' root_level (\ key_hash hash key) key val key_hash node)]))
+ [key_hash (has' root_level (\ key_hash hash key) key val key_hash node)]))
-(def: .public (remove key dict)
+(def: .public (lacks key dict)
(All [k v] (-> k (Dictionary k v) (Dictionary k v)))
(let [[key_hash node] dict]
- [key_hash (remove' root_level (\ key_hash hash key) key key_hash node)]))
+ [key_hash (lacks' root_level (\ key_hash hash key) key key_hash node)]))
(def: .public (get key dict)
(All [k v] (-> k (Dictionary k v) (Maybe v)))
@@ -597,10 +597,10 @@
{#.doc "Only puts the KV-pair if the key is not already present."}
(All [k v] (-> k v (Dictionary k v) (Try (Dictionary k v))))
(case (get key dict)
- #.None (#try.Success (put key val dict))
+ #.None (#try.Success (has key val dict))
(#.Some _) (exception.except ..key_already_exists [])))
-(def: .public (update key f dict)
+(def: .public (revised key f dict)
{#.doc "Transforms the value located at key (if available), using the given function."}
(All [k v] (-> k (-> v v) (Dictionary k v) (Dictionary k v)))
(case (get key dict)
@@ -608,13 +608,13 @@
dict
(#.Some val)
- (put key (f val) dict)))
+ (has key (f val) dict)))
(def: .public (upsert key default f dict)
{#.doc (example "Updates the value at the key; if it exists."
"Otherwise, puts a value by applying the function to a default.")}
(All [k v] (-> k v (-> v v) (Dictionary k v) (Dictionary k v)))
- (..put key
+ (..has key
(f (maybe.else default
(..get key dict)))
dict))
@@ -634,7 +634,7 @@
(def: .public (of_list key_hash kvs)
(All [k v] (-> (Hash k) (List [k v]) (Dictionary k v)))
(list\fold (function (_ [k v] dict)
- (..put k v dict))
+ (..has k v dict))
(empty key_hash)
kvs))
@@ -654,7 +654,7 @@
{#.doc (example "Merges 2 dictionaries."
"If any collisions with keys occur, the values of dict2 will overwrite those of dict1.")}
(All [k v] (-> (Dictionary k v) (Dictionary k v) (Dictionary k v)))
- (list\fold (function (_ [key val] dict) (put key val dict))
+ (list\fold (function (_ [key val] dict) (has key val dict))
dict1
(entries dict2)))
@@ -665,10 +665,10 @@
(list\fold (function (_ [key val2] dict)
(case (get key dict)
#.None
- (put key val2 dict)
+ (has key val2 dict)
(#.Some val1)
- (put key (f val2 val1) dict)))
+ (has key (f val2 val1) dict)))
dict1
(entries dict2)))
@@ -681,8 +681,8 @@
(#.Some val)
(|> dict
- (remove from_key)
- (put to_key val))))
+ (lacks from_key)
+ (has to_key val))))
(def: .public (sub keys dict)
{#.doc "A sub-dictionary, with only the specified keys."}
@@ -691,7 +691,7 @@
(list\fold (function (_ key new_dict)
(case (get key dict)
#.None new_dict
- (#.Some val) (put key val new_dict)))
+ (#.Some val) (has key val new_dict)))
(empty key_hash)
keys)))
diff --git a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
index 6d343f573..d4516f8d1 100644
--- a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
@@ -250,7 +250,7 @@
#Black
<default_behavior>))))
-(def: .public (put key value dict)
+(def: .public (has key value dict)
(All [k v] (-> k v (Dictionary k v) (Dictionary k v)))
(let [(^open "_\.") (get@ #&order dict)
root' (loop [?root (get@ #root dict)]
@@ -473,7 +473,7 @@
_
(undefined)))
-(def: .public (remove key dict)
+(def: .public (lacks key dict)
(All [k v] (-> k (Dictionary k v) (Dictionary k v)))
(let [(^open "_\.") (get@ #&order dict)
[?root found?] (loop [?root (get@ #root dict)]
@@ -528,11 +528,11 @@
(set@ #root (#.Some (blackened root)) dict)
)))
-(def: .public (update key transform dict)
+(def: .public (revised key transform dict)
(All [k v] (-> k (-> v v) (Dictionary k v) (Dictionary k v)))
(case (..get key dict)
(#.Some old)
- (..put key (transform old) dict)
+ (..has key (transform old) dict)
#.None
dict))
@@ -540,7 +540,7 @@
(def: .public (of_list order list)
(All [k v] (-> (Order k) (List [k v]) (Dictionary k v)))
(list\fold (function (_ [key value] dict)
- (put key value dict))
+ (has key value dict))
(empty order)
list))
diff --git a/stdlib/source/library/lux/data/collection/dictionary/plist.lux b/stdlib/source/library/lux/data/collection/dictionary/plist.lux
index a251109f4..88ea21f79 100644
--- a/stdlib/source/library/lux/data/collection/dictionary/plist.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary/plist.lux
@@ -59,7 +59,7 @@
#.None
false))
-(def: .public (put key val properties)
+(def: .public (has key val properties)
(All [a] (-> Text a (PList a) (PList a)))
(case properties
#.End
@@ -70,9 +70,9 @@
(#.Item [key val]
properties')
(#.Item [k' v']
- (put key val properties')))))
+ (has key val properties')))))
-(def: .public (update key f properties)
+(def: .public (revised key f properties)
(All [a] (-> Text (-> a a) (PList a) (PList a)))
(case properties
#.End
@@ -81,9 +81,9 @@
(#.Item [k' v'] properties')
(if (text\= key k')
(#.Item [k' (f v')] properties')
- (#.Item [k' v'] (update key f properties')))))
+ (#.Item [k' v'] (revised key f properties')))))
-(def: .public (remove key properties)
+(def: .public (lacks key properties)
(All [a] (-> Text (PList a) (PList a)))
(case properties
#.End
@@ -93,7 +93,7 @@
(if (text\= key k')
properties'
(#.Item [k' v']
- (remove key properties')))))
+ (lacks key properties')))))
(def: .public equivalence
(All [a] (-> (Equivalence a) (Equivalence (PList a))))
diff --git a/stdlib/source/library/lux/data/collection/list.lux b/stdlib/source/library/lux/data/collection/list.lux
index fc57c691a..6174f1ea6 100644
--- a/stdlib/source/library/lux/data/collection/list.lux
+++ b/stdlib/source/library/lux/data/collection/list.lux
@@ -583,7 +583,7 @@
(#.Some (#.Item x tail)))
))
-(def: .public concat
+(def: .public joined
{#.doc (example "The sequential combination of all the lists.")}
(All [a] (-> (List (List a)) (List a)))
(\ ..monad join))
@@ -604,7 +604,7 @@
(: ((:parameter 0) (List (List (:parameter 1))))
(monad.seq ! lMla))}
(monad.seq ! lMla))]
- (in (concat lla)))))
+ (in (..joined lla)))))
(def: .public (lift monad)
{#.doc (example "Wraps a monadic value with List machinery.")}
diff --git a/stdlib/source/library/lux/data/collection/row.lux b/stdlib/source/library/lux/data/collection/row.lux
index 2a6a1020d..c36a5377e 100644
--- a/stdlib/source/library/lux/data/collection/row.lux
+++ b/stdlib/source/library/lux/data/collection/row.lux
@@ -293,7 +293,7 @@
row)))
(exception.except ..index_out_of_bounds [row idx]))))
-(def: .public (update idx f row)
+(def: .public (revised idx f row)
(All [a] (-> Nat (-> a a) (Row a) (Try (Row a))))
(do try.monad
[val (..item idx row)]
@@ -358,7 +358,7 @@
(All [a] (-> (Row a) Bit))
(|>> (get@ #size) (n.= 0)))
-(syntax: .public (row {elems (p.some s.any)})
+(syntax: .public (row [elems (p.some s.any)])
{#.doc (example "Row literals."
(row 12 34 56 78 90))}
(in (.list (` (..of_list (.list (~+ elems)))))))
diff --git a/stdlib/source/library/lux/data/collection/sequence.lux b/stdlib/source/library/lux/data/collection/sequence.lux
index f26f57d97..c8049c3b3 100644
--- a/stdlib/source/library/lux/data/collection/sequence.lux
+++ b/stdlib/source/library/lux/data/collection/sequence.lux
@@ -137,9 +137,9 @@
(let [[head tail] (//.result wa)]
(//.pending [wa (split tail)]))))
-(syntax: .public (^sequence& {patterns (<code>.form (<>.many <code>.any))}
- body
- {branches (<>.some <code>.any)})
+(syntax: .public (^sequence& [patterns (<code>.form (<>.many <code>.any))
+ body <code>.any
+ branches (<>.some <code>.any)])
{#.doc (example "Allows destructuring of sequences in pattern-matching expressions."
"Caveat emptor: Only use it for destructuring, and not for testing values within the sequences."
(let [(^sequence& x y z _tail) (some_sequence_func +1 +2 +3)]
diff --git a/stdlib/source/library/lux/data/collection/set.lux b/stdlib/source/library/lux/data/collection/set.lux
index f3ccdc7fb..bd18afe96 100644
--- a/stdlib/source/library/lux/data/collection/set.lux
+++ b/stdlib/source/library/lux/data/collection/set.lux
@@ -32,13 +32,13 @@
(All [a] (-> (Set a) Nat))
//.size)
-(def: .public (add elem set)
+(def: .public (has elem set)
(All [a] (-> a (Set a) (Set a)))
- (|> set (//.put elem [])))
+ (|> set (//.has elem [])))
-(def: .public remove
+(def: .public lacks
(All [a] (-> a (Set a) (Set a)))
- //.remove)
+ //.lacks)
(def: .public member?
(All [a] (-> (Set a) a Bit))
@@ -54,7 +54,7 @@
(def: .public (difference sub base)
(All [a] (-> (Set a) (Set a) (Set a)))
- (list\fold ..remove base (..list sub)))
+ (list\fold ..lacks base (..list sub)))
(def: .public (intersection filter base)
(All [a] (-> (Set a) (Set a) (Set a)))
@@ -92,7 +92,7 @@
(def: .public (of_list hash elements)
(All [a] (-> (Hash a) (List a) (Set a)))
- (list\fold ..add (..empty hash) elements))
+ (list\fold ..has (..empty hash) elements))
(def: .public (sub? super sub)
(All [a] (-> (Set a) (Set a) Bit))
diff --git a/stdlib/source/library/lux/data/collection/set/multi.lux b/stdlib/source/library/lux/data/collection/set/multi.lux
index 4131578c1..8211134e1 100644
--- a/stdlib/source/library/lux/data/collection/set/multi.lux
+++ b/stdlib/source/library/lux/data/collection/set/multi.lux
@@ -31,7 +31,7 @@
(All [a] (-> (Set a) Nat))
(|>> :representation dictionary.values (list\fold n.+ 0)))
- (def: .public (add multiplicity elem set)
+ (def: .public (has multiplicity elem set)
(All [a] (-> Nat a (Set a) (Set a)))
(case multiplicity
0 set
@@ -40,7 +40,7 @@
(dictionary.upsert elem 0 (n.+ multiplicity))
:abstraction)))
- (def: .public (remove multiplicity elem set)
+ (def: .public (lacks multiplicity elem set)
(All [a] (-> Nat a (Set a) (Set a)))
(case multiplicity
0 set
@@ -48,8 +48,8 @@
(#.Some current)
(:abstraction
(if (n.> multiplicity current)
- (dictionary.update elem (n.- multiplicity) (:representation set))
- (dictionary.remove elem (:representation set))))
+ (dictionary.revised elem (n.- multiplicity) (:representation set))
+ (dictionary.lacks elem (:representation set))))
#.None
set)))
@@ -78,7 +78,7 @@
(def: .public (intersection parameter (^:representation subject))
(All [a] (-> (Set a) (Set a) (Set a)))
(list\fold (function (_ [elem multiplicity] output)
- (..add (n.min (..multiplicity parameter elem)
+ (..has (n.min (..multiplicity parameter elem)
multiplicity)
elem
output))
@@ -91,7 +91,7 @@
:representation
dictionary.entries
(list\fold (function (_ [elem multiplicity] output)
- (..remove multiplicity elem output))
+ (..lacks multiplicity elem output))
subject)))
(def: .public (sub? reference subject)
@@ -149,7 +149,7 @@
(def: .public (of_list hash subject)
(All [a] (-> (Hash a) (List a) (Set a)))
- (list\fold (..add 1) (..empty hash) subject))
+ (list\fold (..has 1) (..empty hash) subject))
(def: .public (of_set subject)
(All [a] (-> (//.Set a) (Set a)))
diff --git a/stdlib/source/library/lux/data/collection/set/ordered.lux b/stdlib/source/library/lux/data/collection/set/ordered.lux
index e69dba5fe..6ef570c31 100644
--- a/stdlib/source/library/lux/data/collection/set/ordered.lux
+++ b/stdlib/source/library/lux/data/collection/set/ordered.lux
@@ -36,13 +36,13 @@
[Bit empty? /.empty?]
)
- (def: .public (add elem set)
+ (def: .public (has elem set)
(All [a] (-> a (Set a) (Set a)))
- (|> set :representation (/.put elem elem) :abstraction))
+ (|> set :representation (/.has elem elem) :abstraction))
- (def: .public (remove elem set)
+ (def: .public (lacks elem set)
(All [a] (-> a (Set a) (Set a)))
- (|> set :representation (/.remove elem) :abstraction))
+ (|> set :representation (/.lacks elem) :abstraction))
(def: .public list
(All [a] (-> (Set a) (List a)))
@@ -50,11 +50,11 @@
(def: .public (of_list &order list)
(All [a] (-> (Order a) (List a) (Set a)))
- (list\fold add (..empty &order) list))
+ (list\fold has (..empty &order) list))
(def: .public (union left right)
(All [a] (-> (Set a) (Set a) (Set a)))
- (list\fold ..add right (..list left)))
+ (list\fold ..has right (..list left)))
(def: .public (intersection left right)
(All [a] (-> (Set a) (Set a) (Set a)))
diff --git a/stdlib/source/library/lux/data/collection/tree.lux b/stdlib/source/library/lux/data/collection/tree.lux
index 69043cb63..451fc6143 100644
--- a/stdlib/source/library/lux/data/collection/tree.lux
+++ b/stdlib/source/library/lux/data/collection/tree.lux
@@ -54,7 +54,7 @@
(<>.else (list))
(<>.and <code>.any)))
-(syntax: .public (tree {root tree^})
+(syntax: .public (tree [root tree^])
{#.doc (example "Tree literals."
(: (Tree Nat)
(tree 12
diff --git a/stdlib/source/library/lux/data/color.lux b/stdlib/source/library/lux/data/color.lux
index 673e74e60..19cdb0b66 100644
--- a/stdlib/source/library/lux/data/color.lux
+++ b/stdlib/source/library/lux/data/color.lux
@@ -360,7 +360,7 @@
+0.0
luminance])))
-(syntax: (color_scheme_documentation {name <code>.local_identifier})
+(syntax: (color_scheme_documentation [name <code>.local_identifier])
(let [name (text.replaced "_" "-" name)
g!documentation (code.text (format "A " name " color scheme."))]
(in (list (` {#.doc (.example (~ g!documentation))})))))
@@ -409,7 +409,7 @@
(type: .public Palette
(-> Spread Nat Color (List Color)))
-(syntax: (palette_documentation {name <code>.local_identifier})
+(syntax: (palette_documentation [name <code>.local_identifier])
(let [name (text.replaced "_" "-" name)
g!documentation (code.text (format "A " name " palette."))]
(in (list (` {#.doc (.example (~ g!documentation))})))))
diff --git a/stdlib/source/library/lux/data/color/named.lux b/stdlib/source/library/lux/data/color/named.lux
index 32e395bb1..f94dacd1a 100644
--- a/stdlib/source/library/lux/data/color/named.lux
+++ b/stdlib/source/library/lux/data/color/named.lux
@@ -14,10 +14,10 @@
[number (#+ hex)]]]]
["." // (#+ Color)])
-(syntax: (documentation {<red> <code>.text}
- {<green> <code>.text}
- {<blue> <code>.text}
- {<name> <code>.local_identifier})
+(syntax: (documentation [<red> <code>.text
+ <green> <code>.text
+ <blue> <code>.text
+ <name> <code>.local_identifier])
(|> <name>
(text.replaced "_" " ")
(format <red> <green> <blue> " | ")
diff --git a/stdlib/source/library/lux/data/format/css/property.lux b/stdlib/source/library/lux/data/format/css/property.lux
index 3c9bfbb3e..0bb70c48d 100644
--- a/stdlib/source/library/lux/data/format/css/property.lux
+++ b/stdlib/source/library/lux/data/format/css/property.lux
@@ -52,7 +52,7 @@
White_Space Word_Break Word_Wrap Writing_Mode
Z_Index)]])
-(syntax: (text_identifier {identifier s.text})
+(syntax: (text_identifier [identifier s.text])
(in (list (code.local_identifier (text.replaced "-" "_" identifier)))))
(abstract: .public (Property brand)
diff --git a/stdlib/source/library/lux/data/format/css/query.lux b/stdlib/source/library/lux/data/format/css/query.lux
index 698938f15..3743b7033 100644
--- a/stdlib/source/library/lux/data/format/css/query.lux
+++ b/stdlib/source/library/lux/data/format/css/query.lux
@@ -21,7 +21,7 @@
Pointer Hover
Light Scripting Motion Color_Scheme)]])
-(syntax: (text_identifier {identifier s.text})
+(syntax: (text_identifier [identifier s.text])
(in (list (code.local_identifier (text.replaced "-" "_" identifier)))))
(abstract: .public Media
diff --git a/stdlib/source/library/lux/data/format/css/value.lux b/stdlib/source/library/lux/data/format/css/value.lux
index 6b36f1443..a39469994 100644
--- a/stdlib/source/library/lux/data/format/css/value.lux
+++ b/stdlib/source/library/lux/data/format/css/value.lux
@@ -28,7 +28,7 @@
[//
[selector (#+ Label)]])
-(syntax: (text_identifier {identifier s.text})
+(syntax: (text_identifier [identifier s.text])
(in (list (code.local_identifier (text.replaced "-" "_" identifier)))))
(template: (enumeration: <abstraction> <representation> <out> <sample>+ <definition>+)
diff --git a/stdlib/source/library/lux/data/format/json.lux b/stdlib/source/library/lux/data/format/json.lux
index 5d678fb2c..55b1cd6e0 100644
--- a/stdlib/source/library/lux/data/format/json.lux
+++ b/stdlib/source/library/lux/data/format/json.lux
@@ -14,7 +14,8 @@
["." maybe]
["." try (#+ Try)]
["<>" parser ("#\." monad)
- ["<.>" text (#+ Parser)]]]
+ ["<.>" text (#+ Parser)]
+ ["<.>" code]]]
[data
["." bit]
["." product]
@@ -66,7 +67,7 @@
(-> (List [String JSON]) JSON)
(|>> (dictionary.of_list text.hash) #..Object))
-(syntax: .public (json token)
+(syntax: .public (json [token <code>.any])
{#.doc (example "A simple way to produce JSON literals."
(json #null)
(json #1)
@@ -139,7 +140,7 @@
(-> String JSON JSON (Try JSON))
(case json
(#Object obj)
- (#try.Success (#Object (dictionary.put key value obj)))
+ (#try.Success (#Object (dictionary.has key value obj)))
_
(#try.Failure ($_ text\compose "Cannot set field '" key "' on a non-object."))))
diff --git a/stdlib/source/library/lux/data/text.lux b/stdlib/source/library/lux/data/text.lux
index a1048d638..1d3bd0a57 100644
--- a/stdlib/source/library/lux/data/text.lux
+++ b/stdlib/source/library/lux/data/text.lux
@@ -291,7 +291,7 @@
(n.+ ("lux text char" index input))))
hash))))))
-(def: .public concat
+(def: .public joined
(-> (List Text) Text)
(let [(^open ".") ..monoid]
(|>> list.reversed
@@ -299,7 +299,9 @@
(def: .public (join_with separator texts)
(-> Text (List Text) Text)
- (|> texts (list.interposed separator) concat))
+ (case separator
+ "" (..joined texts)
+ _ (|> texts (list.interposed separator) ..joined)))
(def: .public (empty? text)
(-> Text Bit)
diff --git a/stdlib/source/library/lux/data/text/escape.lux b/stdlib/source/library/lux/data/text/escape.lux
index a8e2c79cc..fe56f754b 100644
--- a/stdlib/source/library/lux/data/text/escape.lux
+++ b/stdlib/source/library/lux/data/text/escape.lux
@@ -238,7 +238,7 @@
"" current
_ (format previous current))))))
-(syntax: .public (literal {literal <code>.text})
+(syntax: .public (literal [literal <code>.text])
{#.doc (example "If given a escaped text literal, expands to an un-escaped version.")}
(case (..un_escaped literal)
(#try.Success un_escaped)
diff --git a/stdlib/source/library/lux/data/text/format.lux b/stdlib/source/library/lux/data/text/format.lux
index 612928a26..3438e3f96 100644
--- a/stdlib/source/library/lux/data/text/format.lux
+++ b/stdlib/source/library/lux/data/text/format.lux
@@ -7,7 +7,7 @@
["." contravariant]]]
[control
["<>" parser
- ["<c>" code (#+ Parser)]]]
+ ["<.>" code (#+ Parser)]]]
[data
["." bit]
["." name]
@@ -49,7 +49,7 @@
(def: (map f fb)
(|>> f fb)))
-(syntax: .public (format {fragments (<>.many <c>.any)})
+(syntax: .public (format [fragments (<>.many <code>.any)])
{#.doc (example "Text interpolation."
(format "Static part " (text static) " does not match URI: " uri))}
(in (.list (` ($_ "lux text concat" (~+ fragments))))))
diff --git a/stdlib/source/library/lux/data/text/regex.lux b/stdlib/source/library/lux/data/text/regex.lux
index a81b28c5a..795bee383 100644
--- a/stdlib/source/library/lux/data/text/regex.lux
+++ b/stdlib/source/library/lux/data/text/regex.lux
@@ -411,7 +411,7 @@
(-> Text (Parser Code))
(\ <>.monad map product.right (re_alternative^ #1 re_scoped^ current_module)))
-(syntax: .public (regex {pattern <code>.text})
+(syntax: .public (regex [pattern <code>.text])
{#.doc (example "Create lexers using regular-expression syntax."
"For example:"
@@ -482,9 +482,9 @@
(in (list regex))
)))
-(syntax: .public (^regex {[pattern bindings] (<code>.form (<>.and <code>.text (<>.maybe <code>.any)))}
- body
- {branches (<>.many <code>.any)})
+(syntax: .public (^regex [[pattern bindings] (<code>.form (<>.and <code>.text (<>.maybe <code>.any)))
+ body <code>.any
+ branches (<>.many <code>.any)])
{#.doc (example "Allows you to test text against regular expressions."
(case some_text
(^regex "(\d{3})-(\d{3})-(\d{4})"
diff --git a/stdlib/source/library/lux/data/text/unicode/block.lux b/stdlib/source/library/lux/data/text/unicode/block.lux
index 16f8ba47a..deb289a22 100644
--- a/stdlib/source/library/lux/data/text/unicode/block.lux
+++ b/stdlib/source/library/lux/data/text/unicode/block.lux
@@ -80,7 +80,7 @@
(i64.or (i64.left_shifted 32 (..start value))
(..end value))))
-(syntax: (block_name {name <code>.local_identifier})
+(syntax: (block_name [name <code>.local_identifier])
(in (list (code.text (///.replaced "_" " " name)))))
(template [<name> <start> <end>]
diff --git a/stdlib/source/library/lux/debug.lux b/stdlib/source/library/lux/debug.lux
index 45fdba0d2..6039bbcd8 100644
--- a/stdlib/source/library/lux/debug.lux
+++ b/stdlib/source/library/lux/debug.lux
@@ -141,6 +141,7 @@
(text.enclosed ["[" "]"])))))
(def: .public (inspection value)
+ {#.doc (example "A best-effort attempt to generate a textual representation of a value, without knowing its type.")}
Inspector
(with_expansions [<jvm> (let [object (:as java/lang/Object value)]
(`` (<| (~~ (template [<class> <processing>]
@@ -512,6 +513,7 @@
))))
(def: .public (representation type value)
+ {#.doc (example "A best-effort attempt to generate a textual representation of a value, while knowing its type.")}
(-> Type Any (Try Text))
(case (<type>.result ..representation_parser type)
(#try.Success representation)
@@ -520,14 +522,21 @@
(#try.Failure _)
(exception.except ..cannot_represent_value type)))
-(syntax: .public (private {definition <code>.identifier})
+(syntax: .public (private [definition <code>.identifier])
+ {#.doc (example "Allows access to un-exported definitions in other modules."
+ "Module A"
+ (def: .private (secret_definition input)
+ (-> ??? ???)
+ (foo (bar (baz input))))
+ "Module B"
+ ((..private secret_definition) my_input))}
(let [[module _] definition]
(in (list (` ("lux in-module"
(~ (code.text module))
(~ (code.identifier definition))))))))
(def: .public (log! message)
- {#.doc "Logs message to standard output."}
+ {#.doc "Prints/writes a message to standard output."}
(-> Text Any)
("lux io log" message))
@@ -536,7 +545,12 @@
["Location" (%.location location)]
["Type" (%.type type)]))
-(syntax: .public (:hole)
+(syntax: .public (:hole [])
+ {#.doc (example "A typed 'hole'."
+ "Reveals the type expected of the expression that should go in the hole."
+ (: (-> Nat Text)
+ (function (_ number)
+ (:hole))))}
(do meta.monad
[location meta.location
expectedT meta.expected_type]
@@ -556,15 +570,38 @@
(exception.report
["Name" (%.text name)]))
-(syntax: .public (here {targets (: (<code>.Parser (List Target))
+(syntax: .public (here [targets (: (<code>.Parser (List Target))
(|> ..target
<>.some
- (<>.else (list))))})
+ (<>.else (list))))])
+ {#.doc (example "Shows the names and values of local bindings available around the call to 'here'."
+ (let [foo 123
+ bar +456
+ baz +789.0]
+ (: Any
+ (here)))
+ "=>"
+ "foo: +123"
+ "bar: +456"
+ "baz: +789.0"
+ []
+
+ "Can optionally be given a list of definitions to focus on."
+ "These definitions to focus on can include custom format to represent the values."
+ (let [foo 123
+ bar +456
+ baz +789.0]
+ (: Any
+ (here {foo %.nat} baz)))
+ "=>"
+ "foo: 123"
+ "baz: +789.0"
+ [])}
(do {! meta.monad}
[location meta.location
locals meta.locals
.let [environment (|> locals
- list.concat
+ list.joined
... The list is reversed to make sure that, when building the dictionary,
... later bindings overshadow earlier ones if they have the same name.
list.reversed
diff --git a/stdlib/source/library/lux/extension.lux b/stdlib/source/library/lux/extension.lux
index 4a97254e9..0f81e4bda 100644
--- a/stdlib/source/library/lux/extension.lux
+++ b/stdlib/source/library/lux/extension.lux
@@ -57,9 +57,8 @@
(<>.some (..input default)))))
(template [<any> <end> <and> <result> <extension> <name>]
- [(syntax: .public (<name>
- {[name extension phase archive inputs] (..declaration (` <any>))}
- body)
+ [(syntax: .public (<name> [[name extension phase archive inputs] (..declaration (` <any>))
+ body <c>.any])
(let [g!parser (case (list\map product.right inputs)
#.End
(` <end>)
diff --git a/stdlib/source/library/lux/ffi.js.lux b/stdlib/source/library/lux/ffi.js.lux
index ef3837e6c..9913664af 100644
--- a/stdlib/source/library/lux/ffi.js.lux
+++ b/stdlib/source/library/lux/ffi.js.lux
@@ -150,6 +150,7 @@
input))
(def: .public (null _)
+ {#.doc (example "The null pointer.")}
(-> Any Nothing)
(:assume ("js object null")))
@@ -232,7 +233,19 @@
("js constant" (~ (code.text source)))
(~+ (list\map (with_null g!temp) g!inputs)))))))))))
-(syntax: .public (import: {import ..import})
+(syntax: .public (import: [import ..import])
+ {#.doc (example "Easily import types, methods, functions and constants."
+ (import: Uint8Array)
+
+ (import: TextEncoder
+ ["#::."
+ (new [..String])
+ (encode [..String] Uint8Array)])
+
+ (import: TextDecoder
+ ["#::."
+ (new [..String])
+ (decode [..String] String)]))}
(with_identifiers [g!temp]
(case import
(#Class [[class_name class_parameters] format members])
@@ -265,7 +278,7 @@
(#Field [static? field fieldT])
(if static?
- (` ((~! syntax:) ((~ (qualify field)))
+ (` ((~! syntax:) ((~ (qualify field)) [])
(\ (~! meta.monad) (~' in)
(list (` (.:as (~ (nullable_type fieldT))
("js constant" (~ (code.text (%.format real_class "." field))))))))))
@@ -320,10 +333,17 @@
)))
(template: .public (type_of object)
+ {#.doc (example "The type of an object, as text."
+ (and (= "boolean" (type_of #1))
+ (= "number" (type_of +123.456))
+ (= "string" (type_of "789"))
+ (= "function" (type_of (function (_ value) value)))))}
("js type-of" object))
-(syntax: .public (constant type
- {[head tail] (<code>.tuple (<>.and <code>.local_identifier (<>.some <code>.local_identifier)))})
+(syntax: .public (constant [type <code>.any
+ [head tail] (<code>.tuple (<>.and <code>.local_identifier (<>.some <code>.local_identifier)))])
+ {#.doc (example "Allows using definitions from the JavaScript host platform."
+ (constant .Frac [Math PI]))}
(with_identifiers [g!_]
(let [constant (` ("js constant" (~ (code.text head))))]
(case tail
@@ -380,6 +400,11 @@
false))
(template: .public (closure <inputs> <output>)
+ {#.doc (example "Allows defining closures/anonymous-functions in the form that JavaScript expects."
+ "This is useful for adapting Lux functions for usage by JavaScript code."
+ (: ..Function
+ (closure [left right]
+ (do_something (:as Foo left) (:as Bar right)))))}
(.:as ..Function
(`` ("js function"
(~~ (template.amount <inputs>))
diff --git a/stdlib/source/library/lux/ffi.jvm.lux b/stdlib/source/library/lux/ffi.jvm.lux
index 1b0133aa8..4be059a82 100644
--- a/stdlib/source/library/lux/ffi.jvm.lux
+++ b/stdlib/source/library/lux/ffi.jvm.lux
@@ -55,9 +55,10 @@
(|>> type.reflection reflection.reflection))
(template [<name> <class>]
- [(def: .public <name>
- .Type
- (#.Primitive <class> #.End))]
+ [(`` (def: .public <name>
+ {#.doc (example (~~ (template.text ["The type of a (boxed) " <name> " object."])))}
+ .Type
+ (#.Primitive <class> #.End)))]
[Boolean box.boolean]
[Byte box.byte]
@@ -70,9 +71,10 @@
)
(template [<name> <class>]
- [(def: .public <name>
- .Type
- (#.Primitive (reflection.reflection <class>) #.End))]
+ [(`` (def: .public <name>
+ {#.doc (example (~~ (template.text ["The type of an (unboxed) " <name> " value."])))}
+ .Type
+ (#.Primitive (reflection.reflection <class>) #.End)))]
... Primitives
[boolean reflection.boolean]
@@ -1199,17 +1201,16 @@
(Type Class)
(type.class "java.lang.Object" (list)))
-(syntax: .public (class:
- {.let [! <>.monad]}
- {im inheritance_modifier^}
- {[full_class_name class_vars] (\ ! map parser.declaration ..declaration^)}
- {super (<>.else $Object
- (class^ class_vars))}
- {interfaces (<>.else (list)
- (<code>.tuple (<>.some (class^ class_vars))))}
- {annotations ..annotations^}
- {fields (<>.some (..field_decl^ class_vars))}
- {methods (<>.some (..method_def^ class_vars))})
+(syntax: .public (class: [.let [! <>.monad]
+ im inheritance_modifier^
+ [full_class_name class_vars] (\ ! map parser.declaration ..declaration^)
+ super (<>.else $Object
+ (class^ class_vars))
+ interfaces (<>.else (list)
+ (<code>.tuple (<>.some (class^ class_vars))))
+ annotations ..annotations^
+ fields (<>.some (..field_decl^ class_vars))
+ methods (<>.some (..method_def^ class_vars))])
{#.doc (example "Allows defining JVM classes in Lux code."
"For example:"
(class: #final (TestClass A) [Runnable]
@@ -1256,13 +1257,12 @@
[(~+ (list\map field_decl$ fields))]
[(~+ (list\map (method_def$ fully_qualified_class_name method_parser super fields) methods))]))))))
-(syntax: .public (interface:
- {.let [! <>.monad]}
- {[full_class_name class_vars] (\ ! map parser.declaration ..declaration^)}
- {supers (<>.else (list)
- (<code>.tuple (<>.some (class^ class_vars))))}
- {annotations ..annotations^}
- {members (<>.some (..method_decl^ class_vars))})
+(syntax: .public (interface: [.let [! <>.monad]
+ [full_class_name class_vars] (\ ! map parser.declaration ..declaration^)
+ supers (<>.else (list)
+ (<code>.tuple (<>.some (class^ class_vars))))
+ annotations ..annotations^
+ members (<>.some (..method_decl^ class_vars))])
{#.doc (example "Allows defining JVM interfaces."
(interface: TestInterface
([] foo [boolean String] void #throws [Exception])))}
@@ -1272,14 +1272,13 @@
[(~+ (list\map annotation$ annotations))]
(~+ (list\map method_decl$ members)))))))
-(syntax: .public (object
- {class_vars ..vars^}
- {super (<>.else $Object
- (class^ class_vars))}
- {interfaces (<>.else (list)
- (<code>.tuple (<>.some (class^ class_vars))))}
- {constructor_args (..constructor_args^ class_vars)}
- {methods (<>.some ..overriden_method_def^)})
+(syntax: .public (object [class_vars ..vars^
+ super (<>.else $Object
+ (class^ class_vars))
+ interfaces (<>.else (list)
+ (<code>.tuple (<>.some (class^ class_vars))))
+ constructor_args (..constructor_args^ class_vars)
+ methods (<>.some ..overriden_method_def^)])
{#.doc (example "Allows defining anonymous classes."
"The 1st tuple corresponds to class-level type-variables."
"The 2nd tuple corresponds to parent interfaces."
@@ -1298,13 +1297,13 @@
[(~+ (list\map constructor_arg$ constructor_args))]
[(~+ (list\map (method_def$ "" (<>.failure "") super (list)) methods))])))))
-(syntax: .public (null)
- {#.doc (example "Null object reference."
+(syntax: .public (null [])
+ {#.doc (example "The null pointer."
(null))}
(in (list (` ("jvm object null")))))
(def: .public (null? obj)
- {#.doc (example "Test for null object reference."
+ {#.doc (example "Test for the null pointer."
(= (null? (null))
true)
(= (null? "YOLO")
@@ -1312,7 +1311,7 @@
(-> (primitive "java.lang.Object") Bit)
("jvm object null?" obj))
-(syntax: .public (??? expr)
+(syntax: .public (??? [expr <code>.any])
{#.doc (example "Takes a (potentially null) ObjectType reference and creates a (Maybe ObjectType) for it."
(= (??? (: java/lang/String (null)))
#.None)
@@ -1324,7 +1323,7 @@
#.None
(#.Some (~ g!temp)))))))))
-(syntax: .public (!!! expr)
+(syntax: .public (!!! [expr <code>.any])
{#.doc (example "Takes a (Maybe ObjectType) and returns a ObjectType."
"A #.None would get translated into a (null)."
(= (null)
@@ -1339,8 +1338,8 @@
("jvm object null")}
(~ expr)))))))
-(syntax: .public (check {class (..type^ (list))}
- {unchecked (<>.maybe <code>.any)})
+(syntax: .public (check [class (..type^ (list))
+ unchecked (<>.maybe <code>.any)])
{#.doc (example "Checks whether an object is an instance of a particular class."
"Caveat emptor: Cannot check for polymorphism, so avoid using parameterized classes."
(case (check String "YOLO")
@@ -1366,7 +1365,8 @@
(~ check_code))))))
))))
-(syntax: .public (synchronized lock body)
+(syntax: .public (synchronized [lock <code>.any
+ body <code>.any])
{#.doc (example "Evaluates body, while holding a lock on a given object."
(synchronized object_to_be_locked
(exec (do_something ___)
@@ -1374,7 +1374,8 @@
(finish_the_computation ___))))}
(in (list (` ("jvm object synchronized" (~ lock) (~ body))))))
-(syntax: .public (do_to obj {methods (<>.some partial_call^)})
+(syntax: .public (do_to [obj <code>.any
+ methods (<>.some partial_call^)])
{#.doc (example "Call a variety of methods on an object. Then, return the object."
(do_to object
(ClassName::method1 arg0 arg1 arg2)
@@ -1565,6 +1566,12 @@
(text.replaced "#" class)
(text.replaced "." member)))
+(def: syntax_inputs
+ (-> (List Code) (List Code))
+ (|>> (list\map (function (_ name)
+ (list name (` (~! <code>.any)))))
+ list\join))
+
(def: (member_def_interop vars kind class [arg_function_inputs input_jvm_types arg_types] member method_prefix import_format)
(-> (List (Type Var)) Class_Kind (Type Declaration) [(List [Bit Code]) (List (Type Value)) (List Code)] Import_Member_Declaration Text Text (Meta (List Code)))
(let [[full_name class_tvars] (parser.declaration class)]
@@ -1603,7 +1610,7 @@
(with_return_maybe member true classT)
(with_return_try member)
(with_return_io member))]]
- (in (list (` ((~! syntax:) ((~ def_name) (~+ (list\map product.right arg_function_inputs)))
+ (in (list (` ((~! syntax:) ((~ def_name) [(~+ (syntax_inputs (list\map product.right arg_function_inputs)))])
((~' in) (.list (.` (~ jvm_interop)))))))))
(#MethodDecl [commons method])
@@ -1657,7 +1664,8 @@
(|> callC
(with_return_try member)
(with_return_io member))))]]
- (in (list (` ((~! syntax:) ((~ def_name) (~+ (list\map product.right arg_function_inputs)) (~+ object_ast))
+ (in (list (` ((~! syntax:) ((~ def_name) [(~+ (syntax_inputs (list\map product.right arg_function_inputs)))
+ (~+ (syntax_inputs object_ast))])
((~' in) (.list (.` (~ jvm_interop))))))))))
(#FieldAccessDecl fad)
@@ -1667,8 +1675,8 @@
setter_name (code.identifier ["" (..import_name import_format method_prefix (format import_field_name "!"))])]
getter_interop (with_identifiers [g!obj]
(let [getter_call (if import_field_static?
- (` ((~ getter_name)))
- (` ((~ getter_name) (~ g!obj))))
+ (` ((~ getter_name) []))
+ (` ((~ getter_name) [(~ g!obj) (~! <code>.any)])))
getter_body (<| (with_automatic_output_conversion import_field_mode)
[import_field_type
(if import_field_static?
@@ -1686,8 +1694,9 @@
(if import_field_setter?
(with_identifiers [g!obj g!value]
(let [setter_call (if import_field_static?
- (` ((~ setter_name) (~ g!value)))
- (` ((~ setter_name) (~ g!value) (~ g!obj))))
+ (` ((~ setter_name) [(~ g!value) (~! <code>.any)]))
+ (` ((~ setter_name) [(~ g!value) (~! <code>.any)
+ (~ g!obj) (~! <code>.any)])))
setter_value (|> [import_field_type (..un_quoted g!value)]
(with_automatic_input_conversion import_field_mode))
setter_value (if import_field_maybe?
@@ -1739,10 +1748,9 @@
(#.Left _)
(meta.failure (format "Unknown class: " class_name)))))
-(syntax: .public (import:
- {declaration ..declaration^}
- {.let [[class_name class_type_vars] (parser.declaration declaration)]}
- {bundles (<>.some (..bundle class_type_vars))})
+(syntax: .public (import: [declaration ..declaration^
+ .let [[class_name class_type_vars] (parser.declaration declaration)]
+ bundles (<>.some (..bundle class_type_vars))])
{#.doc (example "Allows importing JVM classes, and using them as types."
"Their methods, fields and enum options can also be imported."
(import: java/lang/Object
@@ -1799,12 +1807,12 @@
=members (|> bundles
(list\map (function (_ [import_format members])
(list\map (|>> [import_format]) members)))
- list.concat
+ list.joined
(monad.map ! (member_import$ class_type_vars kind declaration)))]
(in (list& (class_import$ declaration) (list\join =members)))))
-(syntax: .public (array {type (..type^ (list))}
- size)
+(syntax: .public (array [type (..type^ (list))
+ size <code>.any])
{#.doc (example "Create an array of the given type, with the given size."
(array java/lang/Object 10))}
(let [g!size (` (|> (~ size)
@@ -1923,7 +1931,7 @@
_
<failure>))))
-(syntax: .public (array_length array)
+(syntax: .public (array_length [array <code>.any])
{#.doc (example "Gives the length of an array."
(array_length my_array))}
(case array
@@ -1959,7 +1967,8 @@
(in (list (` (let [(~ g!array) (~ array)]
(..array_length (~ g!array)))))))))
-(syntax: .public (array_read idx array)
+(syntax: .public (array_read [idx <code>.any
+ array <code>.any])
{#.doc (example "Loads an element from an array."
(array_read 10 my_array))}
(case array
@@ -1997,7 +2006,9 @@
(in (list (` (let [(~ g!array) (~ array)]
(..array_read (~ idx) (~ g!array)))))))))
-(syntax: .public (array_write idx value array)
+(syntax: .public (array_write [idx <code>.any
+ value <code>.any
+ array <code>.any])
{#.doc (example "Stores an element into an array."
(array_write 10 my_object my_array))}
(case array
@@ -2036,12 +2047,12 @@
(in (list (` (let [(~ g!array) (~ array)]
(..array_write (~ idx) (~ value) (~ g!array)))))))))
-(syntax: .public (class_for {type (..type^ (list))})
+(syntax: .public (class_for [type (..type^ (list))])
{#.doc (example "Loads the class as a java.lang.Class object."
(class_for java/lang/String))}
(in (list (` ("jvm object class" (~ (code.text (..reflection type))))))))
-(syntax: .public (type {type (..type^ (list))})
+(syntax: .public (type [type (..type^ (list))])
(in (list (..value_type #ManualPrM type))))
(exception: .public (cannot_cast_to_non_object {type (Type Value)})
@@ -2049,8 +2060,8 @@
["Signature" (..signature type)]
["Reflection" (..reflection type)]))
-(syntax: .public (:cast {type (..type^ (list))}
- object)
+(syntax: .public (:cast [type (..type^ (list))
+ object <code>.any])
(case [(parser.array? type)
(parser.class? type)]
(^or [(#.Some _) _] [_ (#.Some _)])
diff --git a/stdlib/source/library/lux/ffi.lua.lux b/stdlib/source/library/lux/ffi.lua.lux
index 8370a58d4..d2a062257 100644
--- a/stdlib/source/library/lux/ffi.lua.lux
+++ b/stdlib/source/library/lux/ffi.lua.lux
@@ -23,11 +23,13 @@
["." code]
["." template]]]])
-(abstract: .public (Object brand) Any)
+(abstract: .public (Object brand)
+ {}
+ Any)
(template [<name>]
[(with_expansions [<brand> (template.identifier [<name> "'"])]
- (abstract: <brand> Any)
+ (abstract: <brand> {} Any)
(type: .public <name>
(..Object <brand>)))]
@@ -212,7 +214,9 @@
(:as ..Function (~ source))
(~+ (list\map (with_nil g!temp) g!inputs)))))))))))
-(syntax: .public (import: {import ..import})
+(syntax: .public (import: [import ..import])
+ {#.doc (example "Easily import types, methods, functions and constants."
+ (import: (os/getenv [..String] #io #? ..String)))}
(with_identifiers [g!temp]
(case import
(#Class [class format members])
@@ -241,7 +245,7 @@
(case member
(#Field [static? field fieldT])
(if static?
- (` ((~! syntax:) ((~ (qualify field)))
+ (` ((~! syntax:) ((~ (qualify field)) [])
(\ (~! meta.monad) (~' in)
(list (` (.:as (~ (nilable_type fieldT))
("lua object get" (~ (code.text field))
@@ -296,13 +300,18 @@
outputT)))
(#Constant [_ name fieldT])
- (in (list (` ((~! syntax:) ((~ (code.local_identifier name)))
+ (in (list (` ((~! syntax:) ((~ (code.local_identifier name)) [])
(\ (~! meta.monad) (~' in)
(list (` (.:as (~ (nilable_type fieldT))
("lua constant" (~ (code.text (text.replaced "/" "." name))))))))))))
)))
(template: .public (closure <inputs> <output>)
+ {#.doc (example "Allows defining closures/anonymous-functions in the form that Lua expects."
+ "This is useful for adapting Lux functions for usage by Lua code."
+ (: ..Function
+ (closure [left right]
+ (do_something (:as Foo left) (:as Bar right)))))}
(.:as ..Function
(`` ("lua function"
(~~ (template.amount <inputs>))
diff --git a/stdlib/source/library/lux/ffi.old.lux b/stdlib/source/library/lux/ffi.old.lux
index 3413ee442..da538d4c7 100644
--- a/stdlib/source/library/lux/ffi.old.lux
+++ b/stdlib/source/library/lux/ffi.old.lux
@@ -1165,18 +1165,17 @@
{#super_class_name "java/lang/Object"
#super_class_params (list)})
-(syntax: .public (class:
- {im inheritance_modifier^}
- {class_decl ..class_decl^}
- {.let [full_class_name (product.left class_decl)]}
- {.let [class_vars (product.right class_decl)]}
- {super (<>.else object_super_class
- (..super_class_decl^ class_vars))}
- {interfaces (<>.else (list)
- (<code>.tuple (<>.some (..super_class_decl^ class_vars))))}
- {annotations ..annotations^}
- {fields (<>.some (..field_decl^ class_vars))}
- {methods (<>.some (..method_def^ class_vars))})
+(syntax: .public (class: [im inheritance_modifier^
+ class_decl ..class_decl^
+ .let [full_class_name (product.left class_decl)]
+ .let [class_vars (product.right class_decl)]
+ super (<>.else object_super_class
+ (..super_class_decl^ class_vars))
+ interfaces (<>.else (list)
+ (<code>.tuple (<>.some (..super_class_decl^ class_vars))))
+ annotations ..annotations^
+ fields (<>.some (..field_decl^ class_vars))
+ methods (<>.some (..method_def^ class_vars))])
{#.doc (example "Allows defining JVM classes in Lux code."
"For example:"
(class: #final (TestClass A) [Runnable]
@@ -1225,13 +1224,12 @@
(with_brackets (spaced (list\map (method_def$ replacer super) methods))))))]]
(in (list (` ((~ (code.text def_code))))))))
-(syntax: .public (interface:
- {class_decl ..class_decl^}
- {.let [class_vars (product.right class_decl)]}
- {supers (<>.else (list)
- (<code>.tuple (<>.some (..super_class_decl^ class_vars))))}
- {annotations ..annotations^}
- {members (<>.some (..method_decl^ class_vars))})
+(syntax: .public (interface: [class_decl ..class_decl^
+ .let [class_vars (product.right class_decl)]
+ supers (<>.else (list)
+ (<code>.tuple (<>.some (..super_class_decl^ class_vars))))
+ annotations ..annotations^
+ members (<>.some (..method_decl^ class_vars))])
{#.doc (example "Allows defining JVM interfaces."
(interface: TestInterface
([] foo [boolean String] void #throws [Exception])))}
@@ -1243,14 +1241,13 @@
(in (list (` ((~ (code.text def_code))))))
))
-(syntax: .public (object
- {class_vars (<code>.tuple (<>.some ..type_param^))}
- {super (<>.else object_super_class
- (..super_class_decl^ class_vars))}
- {interfaces (<>.else (list)
- (<code>.tuple (<>.some (..super_class_decl^ class_vars))))}
- {constructor_args (..constructor_args^ class_vars)}
- {methods (<>.some ..overriden_method_def^)})
+(syntax: .public (object [class_vars (<code>.tuple (<>.some ..type_param^))
+ super (<>.else object_super_class
+ (..super_class_decl^ class_vars))
+ interfaces (<>.else (list)
+ (<code>.tuple (<>.some (..super_class_decl^ class_vars))))
+ constructor_args (..constructor_args^ class_vars)
+ methods (<>.some ..overriden_method_def^)])
{#.doc (example "Allows defining anonymous classes."
"The 1st tuple corresponds to class-level type-variables."
"The 2nd tuple corresponds to parent interfaces."
@@ -1269,7 +1266,7 @@
(with_brackets (spaced (list\map (method_def$ function.identity super) methods))))))]
(in (list (` ((~ (code.text def_code))))))))
-(syntax: .public (null)
+(syntax: .public (null [])
{#.doc (example "Null object reference."
(null))}
(in (list (` ("jvm object null")))))
@@ -1283,7 +1280,7 @@
(-> (primitive "java.lang.Object") Bit)
("jvm object null?" obj))
-(syntax: .public (??? expr)
+(syntax: .public (??? [expr <code>.any])
{#.doc (example "Takes a (potentially null) ObjectType reference and creates a (Maybe ObjectType) for it."
(= (??? (: java/lang/String (null)))
#.None)
@@ -1295,7 +1292,7 @@
#.None
(#.Some (~ g!temp)))))))))
-(syntax: .public (!!! expr)
+(syntax: .public (!!! [expr <code>.any])
{#.doc (example "Takes a (Maybe ObjectType) and returns a ObjectType."
"A #.None would get translated into a (null)."
(= (null)
@@ -1310,8 +1307,8 @@
("jvm object null")}
(~ expr)))))))
-(syntax: .public (check {class (..generic_type^ (list))}
- {unchecked (<>.maybe <code>.any)})
+(syntax: .public (check [class (..generic_type^ (list))
+ unchecked (<>.maybe <code>.any)])
{#.doc (example "Checks whether an object is an instance of a particular class."
"Caveat emptor: Cannot check for polymorphism, so avoid using parameterized classes."
(case (check java/lang/String "YOLO")
@@ -1337,7 +1334,8 @@
(~ check_code))))))
))))
-(syntax: .public (synchronized lock body)
+(syntax: .public (synchronized [lock <code>.any
+ body <code>.any])
{#.doc (example "Evaluates body, while holding a lock on a given object."
(synchronized object_to_be_locked
(exec (do_something ___)
@@ -1345,7 +1343,8 @@
(finish_the_computation ___))))}
(in (list (` ("jvm object synchronized" (~ lock) (~ body))))))
-(syntax: .public (do_to obj {methods (<>.some partial_call^)})
+(syntax: .public (do_to [obj <code>.any
+ methods (<>.some partial_call^)])
{#.doc (example "Call a variety of methods on an object. Then, return the object."
(do_to object
(ClassName::method1 arg0 arg1 arg2)
@@ -1492,6 +1491,12 @@
(text.replaced "#" class)
(text.replaced "." member)))
+(def: syntax_inputs
+ (-> (List Code) (List Code))
+ (|>> (list\map (function (_ name)
+ (list name (` (~! <code>.any)))))
+ list\join))
+
(def: (member_def_interop type_params kind class [arg_function_inputs arg_classes arg_types] member method_prefix import_format)
(-> (List Type_Parameter) Class_Kind Class_Declaration [(List [Bit Code]) (List Text) (List Code)] Import_Member_Declaration Text Text (Meta (List Code)))
(let [[full_name class_tvars] class
@@ -1529,7 +1534,7 @@
(decorate_return_maybe class member)
(decorate_return_try member)
(decorate_return_io member))]]
- (in (list (` ((~! syntax:) ((~ def_name) (~+ (list\map product.right arg_function_inputs)))
+ (in (list (` ((~! syntax:) ((~ def_name) [(~+ (syntax_inputs (list\map product.right arg_function_inputs)))])
((~' in) (.list (.` (~ jvm_interop)))))))))
(#MethodDecl [commons method])
@@ -1562,7 +1567,8 @@
(decorate_return_maybe class member)
(decorate_return_try member)
(decorate_return_io member))]]
- (in (list (` ((~! syntax:) ((~ def_name) (~+ (list\map product.right arg_function_inputs)) (~+ object_ast))
+ (in (list (` ((~! syntax:) ((~ def_name) [(~+ (syntax_inputs (list\map product.right arg_function_inputs)))
+ (~+ (syntax_inputs object_ast))])
((~' in) (.list (.` (~ jvm_interop))))))))))
(#FieldAccessDecl fad)
@@ -1581,8 +1587,8 @@
setter_name (code.identifier ["" (..import_name import_format method_prefix (format import_field_name "!"))])]
getter_interop (with_identifiers [g!obj]
(let [getter_call (if import_field_static?
- (` ((~ getter_name)))
- (` ((~ getter_name) (~ g!obj))))
+ (` ((~ getter_name) []))
+ (` ((~ getter_name) [(~ g!obj) (~! <code>.any)])))
getter_body (<| (auto_convert_output import_field_mode)
[(simple_class$ (list) import_field_type)
(if import_field_static?
@@ -1602,8 +1608,9 @@
(if import_field_setter?
(with_identifiers [g!obj g!value]
(let [setter_call (if import_field_static?
- (` ((~ setter_name) (~ g!value)))
- (` ((~ setter_name) (~ g!value) (~ g!obj))))
+ (` ((~ setter_name) [(~ g!value) (~! <code>.any)]))
+ (` ((~ setter_name) [(~ g!value) (~! <code>.any)
+ (~ g!obj) (~! <code>.any)])))
setter_value (auto_convert_input import_field_mode
[(simple_class$ (list) import_field_type) (un_quote g!value)])
setter_value (if import_field_maybe?
@@ -1652,9 +1659,8 @@
(meta.failure (format "Cannot load class: " class_name text.new_line
error)))))
-(syntax: .public (import:
- {class_decl ..class_decl^}
- {bundles (<>.some (..bundle (product.right class_decl)))})
+(syntax: .public (import: [class_decl ..class_decl^
+ bundles (<>.some (..bundle (product.right class_decl)))])
{#.doc (example "Allows importing JVM classes, and using them as types."
"Their methods, fields and enum options can also be imported."
(import: java/lang/Object
@@ -1711,12 +1717,12 @@
=members (|> bundles
(list\map (function (_ [import_format members])
(list\map (|>> [import_format]) members)))
- list.concat
+ list.joined
(monad.map ! (member_import$ (product.right class_decl) kind class_decl)))]
(in (list& (class_import$ class_decl) (list\join =members)))))
-(syntax: .public (array {type (..generic_type^ (list))}
- size)
+(syntax: .public (array [type (..generic_type^ (list))
+ size <code>.any])
{#.doc (example "Create an array of the given type, with the given size."
(array java/lang/Object 10))}
(case type
@@ -1735,7 +1741,7 @@
_
(in (list (` ("jvm anewarray" (~ (code.text (generic_type$ type))) (~ size)))))))
-(syntax: .public (array_length array)
+(syntax: .public (array_length [array <code>.any])
{#.doc (example "Gives the length of an array."
(array_length my_array))}
(in (list (` ("jvm arraylength" (~ array))))))
@@ -1762,7 +1768,8 @@
_
(meta.failure (format "Cannot convert to JvmType: " (type.format type))))))
-(syntax: .public (array_read idx array)
+(syntax: .public (array_read [idx <code>.any
+ array <code>.any])
{#.doc (example "Loads an element from an array."
(array_read 10 my_array))}
(case array
@@ -1791,7 +1798,9 @@
(in (list (` (let [(~ g!array) (~ array)]
(..array_read (~ idx) (~ g!array)))))))))
-(syntax: .public (array_write idx value array)
+(syntax: .public (array_write [idx <code>.any
+ value <code>.any
+ array <code>.any])
{#.doc (example "Stores an element into an array."
(array_write 10 my_object my_array))}
(case array
@@ -1820,10 +1829,10 @@
(in (list (` (let [(~ g!array) (~ array)]
(..array_write (~ idx) (~ value) (~ g!array)))))))))
-(syntax: .public (class_for {type (..generic_type^ (list))})
+(syntax: .public (class_for [type (..generic_type^ (list))])
{#.doc (example "Loads the class as a java.lang.Class object."
(class_for java/lang/String))}
(in (list (` ("jvm object class" (~ (code.text (simple_class$ (list) type))))))))
-(syntax: .public (type {type (..generic_type^ (list))})
+(syntax: .public (type [type (..generic_type^ (list))])
(in (list (..class_type #ManualPrM (list) type))))
diff --git a/stdlib/source/library/lux/ffi.php.lux b/stdlib/source/library/lux/ffi.php.lux
index 6b4ffc631..c29e16c9a 100644
--- a/stdlib/source/library/lux/ffi.php.lux
+++ b/stdlib/source/library/lux/ffi.php.lux
@@ -182,7 +182,7 @@
..constant
))
-(syntax: .public (try expression)
+(syntax: .public (try [expression <code>.any])
{#.doc (example (case (try (risky_computation input))
(#.Right success)
(do_something success)
@@ -232,7 +232,7 @@
(:as ..Function (~ source))
(~+ (list\map (with_null g!temp) g!inputs)))))))))))
-(syntax: .public (import: {import ..import})
+(syntax: .public (import: [import ..import])
(with_identifiers [g!temp]
(case import
(#Class [class alias format members])
@@ -251,7 +251,7 @@
(case member
(#Field [static? field alias fieldT])
(if static?
- (` ((~! syntax:) ((~ (qualify (maybe.else field alias))))
+ (` ((~! syntax:) ((~ (qualify (maybe.else field alias))) [])
(\ (~! meta.monad) (~' in)
(list (` (.:as (~ (nullable_type fieldT))
("php constant" (~ (code.text (%.format class "::" field))))))))))
@@ -308,7 +308,7 @@
(#Constant [_ name alias fieldT])
(let [imported (` ("php constant" (~ (code.text name))))]
- (in (list (` ((~! syntax:) ((~ (code.local_identifier (maybe.else name alias))))
+ (in (list (` ((~! syntax:) ((~ (code.local_identifier (maybe.else name alias))) [])
(\ (~! meta.monad) (~' in)
(list (` (.:as (~ (nullable_type fieldT)) (~ imported))))))))))
)))
diff --git a/stdlib/source/library/lux/ffi.py.lux b/stdlib/source/library/lux/ffi.py.lux
index 93eaf6ccc..70b9fe281 100644
--- a/stdlib/source/library/lux/ffi.py.lux
+++ b/stdlib/source/library/lux/ffi.py.lux
@@ -23,11 +23,13 @@
["." code]
["." template]]]])
-(abstract: .public (Object brand) Any)
+(abstract: .public (Object brand)
+ {}
+ Any)
(template [<name>]
[(with_expansions [<brand> (template.identifier [<name> "'"])]
- (abstract: <brand> Any)
+ (abstract: <brand> {} Any)
(type: .public <name>
(..Object <brand>)))]
@@ -212,7 +214,29 @@
(:as ..Function (~ source))
(~+ (list\map (with_none g!temp) g!inputs)))))))))))
-(syntax: .public (import: {import ..import})
+(syntax: .public (import: [import ..import])
+ {#.doc (example "Easily import types, methods, functions and constants."
+ (import: os
+ ["#::."
+ (#static F_OK ..Integer)
+ (#static R_OK ..Integer)
+ (#static W_OK ..Integer)
+ (#static X_OK ..Integer)
+
+ (#static mkdir [..String] #io #try #? Any)
+ (#static access [..String ..Integer] #io #try ..Boolean)
+ (#static remove [..String] #io #try #? Any)
+ (#static rmdir [..String] #io #try #? Any)
+ (#static rename [..String ..String] #io #try #? Any)
+ (#static listdir [..String] #io #try (Array ..String))])
+
+ (import: os/path
+ ["#::."
+ (#static isfile [..String] #io #try ..Boolean)
+ (#static isdir [..String] #io #try ..Boolean)
+ (#static sep ..String)
+ (#static getsize [..String] #io #try ..Integer)
+ (#static getmtime [..String] #io #try ..Float)]))}
(with_identifiers [g!temp]
(case import
(#Class [class format members])
@@ -252,7 +276,7 @@
(#Field [static? field fieldT])
(if static?
- (` ((~! syntax:) ((~ (qualify field)))
+ (` ((~! syntax:) ((~ (qualify field)) [])
(\ (~! meta.monad) (~' in)
(list (` (.:as (~ (noneable_type fieldT))
("python object get" (~ (code.text field))
@@ -308,6 +332,11 @@
)))
(template: .public (lambda <inputs> <output>)
+ {#.doc (example "Allows defining closures/anonymous-functions in the form that Python expects."
+ "This is useful for adapting Lux functions for usage by Python code."
+ (: ..Function
+ (lambda [left right]
+ (do_something (:as Foo left) (:as Bar right)))))}
(.:as ..Function
(`` ("python function"
(~~ (template.amount <inputs>))
diff --git a/stdlib/source/library/lux/ffi.rb.lux b/stdlib/source/library/lux/ffi.rb.lux
index 8bffde0d6..b0d3a5c9b 100644
--- a/stdlib/source/library/lux/ffi.rb.lux
+++ b/stdlib/source/library/lux/ffi.rb.lux
@@ -23,11 +23,13 @@
["." code]
["." template]]]])
-(abstract: .public (Object brand) Any)
+(abstract: .public (Object brand)
+ {}
+ Any)
(template [<name>]
[(with_expansions [<brand> (template.identifier [<name> "'"])]
- (abstract: <brand> Any)
+ (abstract: <brand> {} Any)
(type: .public <name>
(..Object <brand>)))]
@@ -225,7 +227,26 @@
(:as ..Function (~ source))
(~+ (list\map (with_nil g!temp) g!inputs)))))))))))
-(syntax: .public (import: {[?module import] ..import})
+(syntax: .public (import: [[?module import] ..import])
+ {#.doc (example "Easily import types, methods, functions and constants."
+ (import: Stat
+ ["#::."
+ (executable? [] Bit)
+ (size Int)])
+
+ (import: File #as RubyFile
+ ["#::."
+ (#static SEPARATOR ..String)
+ (#static open [Path ..String] #io #try RubyFile)
+ (#static stat [Path] #io #try Stat)
+ (#static delete [Path] #io #try Int)
+ (#static file? [Path] #io #try Bit)
+ (#static directory? [Path] #io #try Bit)
+
+ (read [] #io #try Binary)
+ (write [Binary] #io #try Int)
+ (flush [] #io #try #? Any)
+ (close [] #io #try #? Any)]))}
(with_identifiers [g!temp]
(case import
(#Class [class alias format members])
@@ -251,7 +272,7 @@
(case member
(#Field [static? field alias fieldT])
(if static?
- (` ((~! syntax:) ((~ (qualify (maybe.else field alias))))
+ (` ((~! syntax:) ((~ (qualify (maybe.else field alias))) [])
(\ (~! meta.monad) (~' in)
(list (` (.:as (~ (nilable_type fieldT))
(.exec
@@ -326,7 +347,7 @@
#.None
(list)))
("ruby constant" (~ (code.text name)))))]
- (in (list (` ((~! syntax:) ((~ (code.local_identifier (maybe.else name alias))))
+ (in (list (` ((~! syntax:) ((~ (code.local_identifier (maybe.else name alias))) [])
(\ (~! meta.monad) (~' in)
(list (` (.:as (~ (nilable_type fieldT)) (~ imported))))))))))
)))
diff --git a/stdlib/source/library/lux/ffi.scm.lux b/stdlib/source/library/lux/ffi.scm.lux
index 6a1e79cec..fe845f74d 100644
--- a/stdlib/source/library/lux/ffi.scm.lux
+++ b/stdlib/source/library/lux/ffi.scm.lux
@@ -149,7 +149,7 @@
..constant
))
-(syntax: .public (try expression)
+(syntax: .public (try [expression <code>.any])
{#.doc (example (case (try (risky_computation input))
(#.Right success)
(do_something success)
@@ -199,7 +199,7 @@
(:as ..Function (~ source))
(~+ (list\map (with_nil g!temp) g!inputs)))))))))))
-(syntax: .public (import: {import ..import})
+(syntax: .public (import: [import ..import])
(with_identifiers [g!temp]
(case import
(#Function [name alias inputsT io? try? outputT])
diff --git a/stdlib/source/library/lux/locale.lux b/stdlib/source/library/lux/locale.lux
index 39befd846..5ff8380b5 100644
--- a/stdlib/source/library/lux/locale.lux
+++ b/stdlib/source/library/lux/locale.lux
@@ -17,7 +17,7 @@
["." territory (#+ Territory)]])
(abstract: .public Locale
- {}
+ {#.doc (example "A description of a locale; with territory, (optional) language, and (optional) text-encoding.")}
Text
diff --git a/stdlib/source/library/lux/macro.lux b/stdlib/source/library/lux/macro.lux
index c05d45cde..b95b6983b 100644
--- a/stdlib/source/library/lux/macro.lux
+++ b/stdlib/source/library/lux/macro.lux
@@ -127,13 +127,16 @@
(//.failure (text\compose "Code is not a local identifier: " (code.format ast)))))
(def: .public wrong_syntax_error
+ {#.doc (example "A generic error message for macro syntax failures.")}
(-> Name Text)
(|>> name\encode
- (text\compose "Wrong syntax for ")))
+ (text.prefix (text\compose "Wrong syntax for " text.\''))
+ (text.suffix (text\compose text.\'' "."))))
(macro: .public (with_identifiers tokens)
{#.doc (example "Creates new identifiers and offers them to the body expression."
- (syntax: .public (synchronized lock body)
+ (syntax: .public (synchronized [lock any
+ body any])
(with_identifiers [g!lock g!body g!_]
(in (list (` (let [(~ g!lock) (~ lock)
(~ g!_) ("jvm monitorenter" (~ g!lock))
diff --git a/stdlib/source/library/lux/macro/local.lux b/stdlib/source/library/lux/macro/local.lux
index 67434aa09..03eab5adc 100644
--- a/stdlib/source/library/lux/macro/local.lux
+++ b/stdlib/source/library/lux/macro/local.lux
@@ -38,7 +38,7 @@
(#.Some module)
(case (body module)
(#try.Success [module' output])
- (#try.Success [(update@ #.modules (plist.put name module') compiler)
+ (#try.Success [(update@ #.modules (plist.has name module') compiler)
output])
(#try.Failure error)
@@ -53,7 +53,7 @@
[[module_name definition_name] (meta.normal name)
.let [definition (: Global (#.Definition [false .Macro (' {}) macro]))
add_macro! (: (-> (PList Global) (PList Global))
- (plist.put definition_name definition))]]
+ (plist.has definition_name definition))]]
(..with_module module_name
(function (_ module)
(case (|> module (get@ #.definitions) (plist.get definition_name))
@@ -68,13 +68,13 @@
(-> Name (Meta Any))
(do meta.monad
[[module_name definition_name] (meta.normal name)
- .let [remove_macro! (: (-> (PList Global) (PList Global))
- (plist.remove definition_name))]]
+ .let [lacks_macro! (: (-> (PList Global) (PList Global))
+ (plist.lacks definition_name))]]
(..with_module module_name
(function (_ module)
(case (|> module (get@ #.definitions) (plist.get definition_name))
(#.Some _)
- (#try.Success [(update@ #.definitions remove_macro! module)
+ (#try.Success [(update@ #.definitions lacks_macro! module)
[]])
#.None
diff --git a/stdlib/source/library/lux/macro/poly.lux b/stdlib/source/library/lux/macro/poly.lux
index 7c79dd3d7..a32a2e5d8 100644
--- a/stdlib/source/library/lux/macro/poly.lux
+++ b/stdlib/source/library/lux/macro/poly.lux
@@ -31,10 +31,10 @@
(<>.either (<>.and <code>.any private)
(<>.and (<>\in (` .private)) private))))
-(syntax: .public (poly: {[export_policy name body] ..polyP})
+(syntax: .public (poly: [[export_policy name body] ..polyP])
(with_identifiers [g!_ g!type g!output]
(let [g!name (code.identifier ["" name])]
- (in (.list (` ((~! syntax:) (~ export_policy) ((~ g!name) {(~ g!type) (~! <code>.identifier)})
+ (in (.list (` ((~! syntax:) (~ export_policy) ((~ g!name) [(~ g!type) (~! <code>.identifier)])
((~! do) (~! meta.monad)
[(~ g!type) ((~! meta.type_definition) (~ g!type))]
(case (: (.Either .Text .Code)
@@ -57,8 +57,7 @@
(<>.either (<>.and <code>.any private)
(<>.and (<>\in (` .private)) private))))
-(syntax: .public (derived: {[export_policy name [poly_func poly_args] ?custom_impl]
- ..derivedP})
+(syntax: .public (derived: [[export_policy name [poly_func poly_args] ?custom_impl] ..derivedP])
(do {! meta.monad}
[poly_args (monad.map ! meta.normal poly_args)
.let [impl (case ?custom_impl
diff --git a/stdlib/source/library/lux/macro/syntax.lux b/stdlib/source/library/lux/macro/syntax.lux
index 0a3e28707..2067663ad 100644
--- a/stdlib/source/library/lux/macro/syntax.lux
+++ b/stdlib/source/library/lux/macro/syntax.lux
@@ -46,12 +46,12 @@
"The inputs to the macro can be parsed in complex ways through the use of syntax parsers."
"The macro body is also (implicitly) run in the Meta monad, to save some typing."
"Also, the compiler state can be accessed through the *lux* binding."
- (syntax: .public (object {.let [imports (class_imports *lux*)]}
- {.let [class_vars (list)]}
- {super (opt (super_class_decl^ imports class_vars))}
- {interfaces (tuple (some (super_class_decl^ imports class_vars)))}
- {constructor_args (constructor_args^ imports class_vars)}
- {methods (some (overriden_method_def^ imports))})
+ (syntax: .public (object [.let [imports (class_imports *lux*)]
+ .let [class_vars (list)]
+ super (opt (super_class_decl^ imports class_vars))
+ interfaces (tuple (some (super_class_decl^ imports class_vars)))
+ constructor_args (constructor_args^ imports class_vars)
+ methods (some (overriden_method_def^ imports))])
(let [def_code ($_ text\compose "anon-class:"
(spaced (list (super_class_decl$ (maybe.else object_super_class super))
(with_brackets (spaced (list\map super_class_decl$ interfaces)))
@@ -61,21 +61,21 @@
(let [?parts (: (Maybe [Code Text (List Code) Code Code])
(case tokens
(^ (list export_policy
- [_ (#.Form (list& [_ (#.Identifier ["" name])] args))]
+ [_ (#.Form (list [_ (#.Identifier ["" name])] [_ (#.Tuple args)]))]
body))
(#.Some [export_policy name args (` {}) body])
(^ (list export_policy
- [_ (#.Form (list& [_ (#.Identifier ["" name])] args))]
+ [_ (#.Form (list [_ (#.Identifier ["" name])] [_ (#.Tuple args)]))]
meta_data
body))
(#.Some [export_policy name args meta_data body])
- (^ (list [_ (#.Form (list& [_ (#.Identifier ["" name])] args))]
+ (^ (list [_ (#.Form (list [_ (#.Identifier ["" name])] [_ (#.Tuple args)]))]
body))
(#.Some [(` .private) name args (` {}) body])
- (^ (list [_ (#.Form (list& [_ (#.Identifier ["" name])] args))]
+ (^ (list [_ (#.Form (list [_ (#.Identifier ["" name])] [_ (#.Tuple args)]))]
meta_data
body))
(#.Some [(` .private) name args meta_data body])
@@ -86,32 +86,25 @@
(#.Some [export_policy name args meta body])
(with_identifiers [g!tokens g!body g!error]
(do {! meta.monad}
- [vars+parsers (monad.map !
- (: (-> Code (Meta [Code Code]))
- (function (_ arg)
- (case arg
- (^ [_ (#.Record (list [var parser]))])
- (with_expansions [<default> (in [var
- (` ((~! ..self_documenting) (' (~ var))
- (~ parser)))])]
- (case var
- [_ (#.Identifier ["" _])]
- <default>
+ [_ (if (|> args list.size nat.even?)
+ (in [])
+ (meta.failure "Syntax pattern expects pairs of bindings and code-parsers."))
+ vars+parsers (monad.map !
+ (: (-> [Code Code] (Meta [Code Code]))
+ (function (_ [var parser])
+ (with_expansions [<default> (in [var
+ (` ((~! ..self_documenting) (' (~ var))
+ (~ parser)))])]
+ (case var
+ [_ (#.Identifier ["" _])]
+ <default>
- [_ (#.Identifier _)]
- (in [var parser])
+ [_ (#.Identifier _)]
+ (in [var parser])
- _
- <default>))
-
- [_ (#.Identifier var_name)]
- (in [arg
- (` ((~! ..self_documenting) (' (~ arg))
- (~! </>.any)))])
-
- _
- (meta.failure "Syntax pattern expects records or identifiers."))))
- args)
+ _
+ <default>))))
+ (list.pairs args))
this_module meta.current_module_name
.let [g!state (code.identifier ["" "*lux*"])
error_msg (code.text (macro.wrong_syntax_error [this_module name]))]]
diff --git a/stdlib/source/library/lux/macro/template.lux b/stdlib/source/library/lux/macro/template.lux
index e3651d36e..2f72ef96a 100644
--- a/stdlib/source/library/lux/macro/template.lux
+++ b/stdlib/source/library/lux/macro/template.lux
@@ -26,14 +26,14 @@
["." code]
["." local]])
-(syntax: .public (spliced {parts (<code>.tuple (<>.some <code>.any))})
+(syntax: .public (spliced [parts (<code>.tuple (<>.some <code>.any))])
(in parts))
-(syntax: .public (amount {parts (<code>.tuple (<>.some <code>.any))})
+(syntax: .public (amount [parts (<code>.tuple (<>.some <code>.any))])
(in (list (code.nat (list.size parts)))))
-(syntax: .public (with_locals {locals (<code>.tuple (<>.some <code>.local_identifier))}
- body)
+(syntax: .public (with_locals [locals (<code>.tuple (<>.some <code>.local_identifier))
+ body <code>.any])
(do {! meta.monad}
[g!locals (|> locals
(list\map //.identifier)
@@ -79,12 +79,12 @@
(-> Bit (Parser (List Text)))
(<code>.tuple (<>.many (..snippet module_side?))))
-(syntax: .public (text {simple (..part false)})
+(syntax: .public (text [simple (..part false)])
(in (list (|> simple (text.join_with "") code.text))))
(template [<name> <simple> <complex>]
- [(syntax: .public (<name> {name (<>.or (<>.and (..part true) (..part false))
- (..part false))})
+ [(syntax: .public (<name> [name (<>.or (<>.and (..part true) (..part false))
+ (..part false))])
(case name
(#.Left [simple complex])
(in (list (<complex> [(text.join_with "" simple)
@@ -160,8 +160,8 @@
#parameters parameters
#template template})))
-(syntax: .public (let {locals (<code>.tuple (<>.some ..local))}
- body)
+(syntax: .public (let [locals (<code>.tuple (<>.some ..local))
+ body <code>.any])
(do meta.monad
[here_name meta.current_module_name
expression? (: (Meta Bit)
diff --git a/stdlib/source/library/lux/math/infix.lux b/stdlib/source/library/lux/math/infix.lux
index a04cf8944..12611788f 100644
--- a/stdlib/source/library/lux/math/infix.lux
+++ b/stdlib/source/library/lux/math/infix.lux
@@ -84,7 +84,7 @@
(#Binary left op right)
(` ((~ op) (~ (prefix right)) (~ (prefix left))))))
-(syntax: .public (infix {expr ..expression})
+(syntax: .public (infix [expr ..expression])
{#.doc (example "Infix math syntax."
(infix [x i.* +10])
(infix [[x i.+ y] i.* [x i.- y]])
diff --git a/stdlib/source/library/lux/math/modulus.lux b/stdlib/source/library/lux/math/modulus.lux
index 434535443..92d9a5903 100644
--- a/stdlib/source/library/lux/math/modulus.lux
+++ b/stdlib/source/library/lux/math/modulus.lux
@@ -49,7 +49,7 @@
(i.= +0)))
)
-(syntax: .public (literal {divisor <code>.int})
+(syntax: .public (literal [divisor <code>.int])
{#.doc (example "Success!"
(literal 123)
diff --git a/stdlib/source/library/lux/math/number/complex.lux b/stdlib/source/library/lux/math/number/complex.lux
index ba63fec12..1615bf633 100644
--- a/stdlib/source/library/lux/math/number/complex.lux
+++ b/stdlib/source/library/lux/math/number/complex.lux
@@ -28,7 +28,8 @@
{#real Frac
#imaginary Frac})
-(syntax: .public (complex real {?imaginary (<>.maybe <code>.any)})
+(syntax: .public (complex [real <code>.any
+ ?imaginary (<>.maybe <code>.any)])
{#.doc (example "Complex literals."
(complex real imaginary)
"The imaginary part can be omitted if it's +0.0."
diff --git a/stdlib/source/library/lux/math/number/ratio.lux b/stdlib/source/library/lux/math/number/ratio.lux
index bf0b2eff2..f6307b4bf 100644
--- a/stdlib/source/library/lux/math/number/ratio.lux
+++ b/stdlib/source/library/lux/math/number/ratio.lux
@@ -40,7 +40,8 @@
{#numerator (n./ common numerator)
#denominator (n./ common denominator)}))
-(syntax: .public (ratio numerator {?denominator (<>.maybe <code>.any)})
+(syntax: .public (ratio [numerator <code>.any
+ ?denominator (<>.maybe <code>.any)])
{#.doc (example "Rational literals."
(ratio numerator denominator)
"The denominator can be omitted if it is 1."
diff --git a/stdlib/source/library/lux/math/random.lux b/stdlib/source/library/lux/math/random.lux
index 2757d62e8..2ba47c5cd 100644
--- a/stdlib/source/library/lux/math/random.lux
+++ b/stdlib/source/library/lux/math/random.lux
@@ -279,7 +279,7 @@
(loop [_ []]
(do !
[x value_gen
- .let [xs+ (set.add x xs)]]
+ .let [xs+ (set.has x xs)]]
(if (n.= size (set.size xs+))
(in xs+)
(recur [])))))
@@ -294,7 +294,7 @@
(do !
[k key_gen
v value_gen
- .let [kv+ (dictionary.put k v kv)]]
+ .let [kv+ (dictionary.has k v kv)]]
(if (n.= size (dictionary.size kv+))
(in kv+)
(recur [])))))
diff --git a/stdlib/source/library/lux/meta.lux b/stdlib/source/library/lux/meta.lux
index 6c2d013c9..2b9465aca 100644
--- a/stdlib/source/library/lux/meta.lux
+++ b/stdlib/source/library/lux/meta.lux
@@ -11,7 +11,7 @@
["." try (#+ Try)]]
[data
["." product]
- ["." text ("#\." monoid equivalence)]
+ ["." text ("#\." monoid order)]
["." name ("#\." codec equivalence)]
[collection
["." list ("#\." monoid monad)]
@@ -292,7 +292,12 @@
_
(let [current_module (|> compiler (get@ #.current_module) (maybe.else "???"))
- separator ($_ text\compose text.new_line " ")]
+ separator ($_ text\compose text.new_line " ")
+ all_known_modules (|> compiler
+ (get@ #.modules)
+ (list\map product.left)
+ (list.sorted text\<)
+ (text.join_with separator))]
(#try.Failure ($_ text\compose
"Unknown definition: " (name\encode name) text.new_line
" Current module: " current_module text.new_line
@@ -313,14 +318,17 @@
(#.Alias _)
#.None))))))
- list.concat
+ list.joined
+ (list.sorted text\<)
(text.join_with separator))
imports (|> this_module
(get@ #.imports)
+ (list.sorted text\<)
(text.join_with separator))
aliases (|> this_module
(get@ #.module_aliases)
(list\map (function (_ [alias real]) ($_ text\compose alias " => " real)))
+ (list.sorted text\<)
(text.join_with separator))]
($_ text\compose
" Candidates: " candidates text.new_line
@@ -329,7 +337,7 @@
_
"")
- " All known modules: " (|> compiler (get@ #.modules) (list\map product.left) (text.join_with separator)) text.new_line)))))))
+ " All known modules: " all_known_modules text.new_line)))))))
(def: .public (export name)
{#.doc "Looks-up a definition's type in the available modules (including the current one)."}
diff --git a/stdlib/source/library/lux/program.lux b/stdlib/source/library/lux/program.lux
index 20939ab03..e0a95d916 100644
--- a/stdlib/source/library/lux/program.lux
+++ b/stdlib/source/library/lux/program.lux
@@ -31,9 +31,8 @@
(in [(code.identifier ["" name]) (` (~! <cli>.any))]))
(<code>.record (<>.and <code>.any <code>.any)))))))
-(syntax: .public (program:
- {args ..arguments^}
- body)
+(syntax: .public (program: [args ..arguments^
+ body <code>.any])
{#.doc (example "Defines the entry-point to a program (similar to the 'main' function/method in other programming languages)."
"Can take a list of all the input parameters to the program."
"Or, can destructure them using CLI-option combinators from the lux/control/parser/cli module."
diff --git a/stdlib/source/library/lux/target/jvm/bytecode.lux b/stdlib/source/library/lux/target/jvm/bytecode.lux
index 13363a06f..04524741f 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode.lux
@@ -128,7 +128,7 @@
(with_expansions [<success> (as_is (in [[pool
environment
(update@ #known
- (dictionary.put label [actual (#.Some @here)])
+ (dictionary.has label [actual (#.Some @here)])
tracker)]
[..relative_identity
[]]]))]
@@ -726,7 +726,7 @@
tracker
#.None
- (update@ #known (dictionary.put label [stack #.None]) tracker)))
+ (update@ #known (dictionary.has label [stack #.None]) tracker)))
(template [<consumption> <name> <instruction>]
[(def: .public (<name> label)
diff --git a/stdlib/source/library/lux/target/jvm/loader.lux b/stdlib/source/library/lux/target/jvm/loader.lux
index 892d1e1ee..214f0b456 100644
--- a/stdlib/source/library/lux/target/jvm/loader.lux
+++ b/stdlib/source/library/lux/target/jvm/loader.lux
@@ -133,7 +133,7 @@
(if (dictionary.key? library' name)
(in (exception.except ..already_stored name))
(do !
- [_ (atom.update! (dictionary.put name bytecode) library)]
+ [_ (atom.update! (dictionary.has name bytecode) library)]
(in (#try.Success []))))))
(def: .public (load name loader)
diff --git a/stdlib/source/library/lux/target/jvm/modifier.lux b/stdlib/source/library/lux/target/jvm/modifier.lux
index 8689834c4..523a9a722 100644
--- a/stdlib/source/library/lux/target/jvm/modifier.lux
+++ b/stdlib/source/library/lux/target/jvm/modifier.lux
@@ -7,7 +7,7 @@
[control
["." try]
["<>" parser
- ["<c>" code]]]
+ ["<.>" code]]]
[data
[format
[".F" binary (#+ Writer)]]]
@@ -80,7 +80,8 @@
(|>> !wrap))
)
-(syntax: .public (modifiers: ofT {options (<>.many <c>.any)})
+(syntax: .public (modifiers: [ofT <code>.any
+ options (<>.many <code>.any)])
(with_identifiers [g!modifier g!code]
(in (list (` (template [(~ g!code) (~ g!modifier)]
[(def: (~' .public) (~ g!modifier)
diff --git a/stdlib/source/library/lux/target/jvm/reflection.lux b/stdlib/source/library/lux/target/jvm/reflection.lux
index eb219a297..e0c21a435 100644
--- a/stdlib/source/library/lux/target/jvm/reflection.lux
+++ b/stdlib/source/library/lux/target/jvm/reflection.lux
@@ -306,7 +306,7 @@
(list.zipped/2 (list\map (|>> java/lang/reflect/TypeVariable::getName)
class_params))
(list\fold (function (_ [name paramT] mapping)
- (dictionary.put name paramT mapping))
+ (dictionary.has name paramT mapping))
/lux.fresh)
#try.Success)
(exception.except ..type_parameter_mismatch [num_class_params num_type_params class type]))
diff --git a/stdlib/source/library/lux/target/lua.lux b/stdlib/source/library/lux/target/lua.lux
index 756efc949..0bf872340 100644
--- a/stdlib/source/library/lux/target/lua.lux
+++ b/stdlib/source/library/lux/target/lua.lux
@@ -371,14 +371,14 @@
else!
(list.reversed clauses)))
-(syntax: (arity_inputs {arity <code>.nat})
+(syntax: (arity_inputs [arity <code>.nat])
(in (case arity
0 (.list)
_ (|> (dec arity)
(enum.range n.enum 0)
(list\map (|>> %.nat code.local_identifier))))))
-(syntax: (arity_types {arity <code>.nat})
+(syntax: (arity_types [arity <code>.nat])
(in (list.repeated arity (` ..Expression))))
(template [<arity> <function>+]
diff --git a/stdlib/source/library/lux/target/php.lux b/stdlib/source/library/lux/target/php.lux
index 98ab82bca..16ebbe5af 100644
--- a/stdlib/source/library/lux/target/php.lux
+++ b/stdlib/source/library/lux/target/php.lux
@@ -227,14 +227,14 @@
..group
:abstraction)))
- (syntax: (arity_inputs {arity <code>.nat})
+ (syntax: (arity_inputs [arity <code>.nat])
(in (case arity
0 (.list)
_ (|> (dec arity)
(enum.range n.enum 0)
(list\map (|>> %.nat code.local_identifier))))))
- (syntax: (arity_types {arity <code>.nat})
+ (syntax: (arity_types [arity <code>.nat])
(in (list.repeated arity (` ..Expression))))
(template [<arity> <function>+]
diff --git a/stdlib/source/library/lux/target/python.lux b/stdlib/source/library/lux/target/python.lux
index 6b578ada2..4fd525f46 100644
--- a/stdlib/source/library/lux/target/python.lux
+++ b/stdlib/source/library/lux/target/python.lux
@@ -457,14 +457,14 @@
else!
(list.reversed clauses)))
-(syntax: (arity_inputs {arity <code>.nat})
+(syntax: (arity_inputs [arity <code>.nat])
(in (case arity
0 (.list)
_ (|> (dec arity)
(enum.range n.enum 0)
(list\map (|>> %.nat code.local_identifier))))))
-(syntax: (arity_types {arity <code>.nat})
+(syntax: (arity_types [arity <code>.nat])
(in (list.repeated arity (` (Expression Any)))))
(template [<arity> <function>+]
diff --git a/stdlib/source/library/lux/target/r.lux b/stdlib/source/library/lux/target/r.lux
index d0a5f7b58..a41440b7a 100644
--- a/stdlib/source/library/lux/target/r.lux
+++ b/stdlib/source/library/lux/target/r.lux
@@ -203,14 +203,14 @@
kw_args))
")"))))
- (syntax: (arity_inputs {arity <code>.nat})
+ (syntax: (arity_inputs [arity <code>.nat])
(in (case arity
0 (.list)
_ (|> arity
list.indices
(list\map (|>> %.nat code.local_identifier))))))
- (syntax: (arity_types {arity <code>.nat})
+ (syntax: (arity_types [arity <code>.nat])
(in (list.repeated arity (` ..Expression))))
(template [<arity> <function>+]
diff --git a/stdlib/source/library/lux/target/ruby.lux b/stdlib/source/library/lux/target/ruby.lux
index d56ce5936..b717ef7cb 100644
--- a/stdlib/source/library/lux/target/ruby.lux
+++ b/stdlib/source/library/lux/target/ruby.lux
@@ -433,14 +433,14 @@
else!
(list.reversed clauses)))
-(syntax: (arity_inputs {arity <code>.nat})
+(syntax: (arity_inputs [arity <code>.nat])
(in (case arity
0 (.list)
_ (|> (dec arity)
(enum.range n.enum 0)
(list\map (|>> %.nat code.local_identifier))))))
-(syntax: (arity_types {arity <code>.nat})
+(syntax: (arity_types [arity <code>.nat])
(in (list.repeated arity (` ..Expression))))
(template [<arity> <function>+]
diff --git a/stdlib/source/library/lux/test.lux b/stdlib/source/library/lux/test.lux
index 310243fc4..9fae1bd7e 100644
--- a/stdlib/source/library/lux/test.lux
+++ b/stdlib/source/library/lux/test.lux
@@ -289,7 +289,7 @@
(code.tuple (list (code.text (name.module name))
(code.text (name.short name)))))
-(syntax: (reference {name <code>.identifier})
+(syntax: (reference [name <code>.identifier])
(do meta.monad
[_ (meta.export name)]
(in (list (name_code name)))))
@@ -312,14 +312,14 @@
output (set.of_list name.hash (list))]
(case (text.split_with ..coverage_separator remaining)
(#.Some [head tail])
- (recur tail (set.add [module head] output))
+ (recur tail (set.has [module head] output))
#.None
- (set.add [module remaining] output))))
+ (set.has [module remaining] output))))
(template [<macro> <function>]
- [(syntax: .public (<macro> {coverage (<code>.tuple (<>.many <code>.any))}
- condition)
+ [(syntax: .public (<macro> [coverage (<code>.tuple (<>.many <code>.any))
+ condition <code>.any])
(let [coverage (list\map (function (_ definition)
(` ((~! ..reference) (~ definition))))
coverage)]
@@ -332,8 +332,8 @@
[cover ..|cover|]
)
-(syntax: .public (for {coverage (<code>.tuple (<>.many <code>.any))}
- test)
+(syntax: .public (for [coverage (<code>.tuple (<>.many <code>.any))
+ test <code>.any])
(let [coverage (list\map (function (_ definition)
(` ((~! ..reference) (~ definition))))
coverage)]
@@ -350,8 +350,8 @@
[(update@ #expected_coverage (set.union coverage) tally)
documentation]))))))
-(syntax: .public (covering {module <code>.identifier}
- test)
+(syntax: .public (covering [module <code>.identifier
+ test <code>.any])
(do meta.monad
[.let [module (name.module module)]
definitions (meta.definitions module)
@@ -403,7 +403,7 @@
(function (_ [index test])
(async.upon! (function (_ assertion)
(do io.monad
- [[_ results] (atom.update! (dictionary.put index assertion) state)]
+ [[_ results] (atom.update! (dictionary.has index assertion) state)]
(if (n.= expected_tests (dictionary.size results))
(let [assertions (|> results
dictionary.entries
diff --git a/stdlib/source/library/lux/time/date.lux b/stdlib/source/library/lux/time/date.lux
index 402700a81..a2a455fa1 100644
--- a/stdlib/source/library/lux/time/date.lux
+++ b/stdlib/source/library/lux/time/date.lux
@@ -31,7 +31,7 @@
(def: month_by_number
(Dictionary Nat Month)
(list\fold (function (_ month mapping)
- (dictionary.put (//month.number month) month mapping))
+ (dictionary.has (//month.number month) month mapping))
(dictionary.empty n.hash)
//month.year))
diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux
index e5ed96552..98d910b10 100644
--- a/stdlib/source/library/lux/tool/compiler/default/platform.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux
@@ -154,10 +154,10 @@
(..compile_runtime! platform))
.let [[descriptor document] [(..runtime_descriptor registry) ..runtime_document]]
archive (///phase.lift (if (archive.reserved? archive archive.runtime_module)
- (archive.add archive.runtime_module [descriptor document payload] archive)
+ (archive.has archive.runtime_module [descriptor document payload] archive)
(do try.monad
[[_ archive] (archive.reserve archive.runtime_module archive)]
- (archive.add archive.runtime_module [descriptor document payload] archive))))]
+ (archive.has archive.runtime_module [descriptor document payload] archive))))]
(in [archive [descriptor document payload]])))
(def: (initialize_state extender
@@ -328,10 +328,10 @@
(function (_ mapping)
(let [with_dependence+transitives
(|> mapping
- (dictionary.upsert source ..empty (set.add target))
- (dictionary.update source (set.union forward)))]
+ (dictionary.upsert source ..empty (set.has target))
+ (dictionary.revised source (set.union forward)))]
(list\fold (function (_ previous)
- (dictionary.upsert previous ..empty (set.add target)))
+ (dictionary.upsert previous ..empty (set.has target)))
with_dependence+transitives
(set.list backward))))))]
(|> dependence
@@ -454,7 +454,7 @@
<Pending>
(async.async []))]
- _ (stm.update (dictionary.put module [return signal]) pending)]
+ _ (stm.update (dictionary.has module [return signal]) pending)]
(in [return
(#.Some [[archive state]
module_id
@@ -566,10 +566,10 @@
(if (set.member? all new)
(if (text\= .prelude_module new)
(if seen_prelude?
- [all (set.add new duplicates) seen_prelude?]
+ [all (set.has new duplicates) seen_prelude?]
[all duplicates true])
- [all (set.add new duplicates) seen_prelude?])
- [(set.add new all) duplicates seen_prelude?]))
+ [all (set.has new duplicates) seen_prelude?])
+ [(set.has new all) duplicates seen_prelude?]))
(: [(Set Module) (Set Module) Bit]
[all_dependencies ..empty (set.empty? all_dependencies)])
new_dependencies))]
@@ -607,7 +607,7 @@
[.let [_ (debug.log! (..module_compilation_log module state))
descriptor (set@ #descriptor.references all_dependencies descriptor)]
_ (..cache_module static platform module_id [descriptor document output])]
- (case (archive.add module [descriptor document output] archive)
+ (case (archive.has module [descriptor document output] archive)
(#try.Success archive)
(in [archive
(..with_reset_log state)])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux
index 5a47352b4..d43a937b1 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux
@@ -152,7 +152,7 @@
(#.Some idx)
#.None)
(|> (dictionary.empty n.hash)
- (dictionary.put idx value_coverage)))))))
+ (dictionary.has idx value_coverage)))))))
(def: (xor left right)
(-> Bit Bit Bit)
@@ -249,10 +249,10 @@
(#.Some coverageSF)
(do !
[coverageM (merged coverageA coverageSF)]
- (in (dictionary.put tagA coverageM casesSF')))
+ (in (dictionary.has tagA coverageM casesSF')))
#.None
- (in (dictionary.put tagA coverageA casesSF'))))
+ (in (dictionary.has tagA coverageA casesSF'))))
casesSF (dictionary.entries casesA))]
(in (if (and (or (known_cases? addition_cases)
(known_cases? so_far_cases))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux
index 4bdb708bd..c0249441c 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux
@@ -88,7 +88,7 @@
#.None
(function (_ state)
(#try.Success [(update@ #.modules
- (plist.put self_name (set@ #.module_annotations (#.Some annotations) self))
+ (plist.has self_name (set@ #.module_annotations (#.Some annotations) self))
state)
[]]))
@@ -102,11 +102,11 @@
[self_name meta.current_module_name]
(function (_ state)
(#try.Success [(update@ #.modules
- (plist.update self_name (update@ #.imports (function (_ current)
- (if (list.any? (text\= module)
- current)
- current
- (#.Item module current)))))
+ (plist.revised self_name (update@ #.imports (function (_ current)
+ (if (list.any? (text\= module)
+ current)
+ current
+ (#.Item module current)))))
state)
[]])))))
@@ -117,8 +117,8 @@
[self_name meta.current_module_name]
(function (_ state)
(#try.Success [(update@ #.modules
- (plist.update self_name (update@ #.module_aliases (: (-> (List [Text Text]) (List [Text Text]))
- (|>> (#.Item [alias module])))))
+ (plist.revised self_name (update@ #.module_aliases (: (-> (List [Text Text]) (List [Text Text]))
+ (|>> (#.Item [alias module])))))
state)
[]])))))
@@ -142,7 +142,7 @@
(case (plist.get name (get@ #.definitions self))
#.None
(#try.Success [(update@ #.modules
- (plist.put self_name
+ (plist.has self_name
(update@ #.definitions
(: (-> (List [Text Global]) (List [Text Global]))
(|>> (#.Item [name definition])))
@@ -158,7 +158,7 @@
(///extension.lift
(function (_ state)
(#try.Success [(update@ #.modules
- (plist.put name (..empty hash))
+ (plist.has name (..empty hash))
state)
[]]))))
@@ -183,7 +183,7 @@
_ #0)]
(if active?
(#try.Success [(update@ #.modules
- (plist.put module_name (set@ #.module_state <tag> module))
+ (plist.has module_name (set@ #.module_state <tag> module))
state)
[]])
((/.except' can_only_change_state_of_active_module [module_name <tag>])
@@ -262,13 +262,13 @@
(#.Some module)
(let [namespaced_tags (list\map (|>> [self_name]) tags)]
(#try.Success [(update@ #.modules
- (plist.update self_name
- (|>> (update@ #.tags (function (_ tag_bindings)
- (list\fold (function (_ [idx tag] table)
- (plist.put tag [idx namespaced_tags exported? type] table))
- tag_bindings
- (list.enumeration tags))))
- (update@ #.types (plist.put type_name [namespaced_tags exported? type]))))
+ (plist.revised self_name
+ (|>> (update@ #.tags (function (_ tag_bindings)
+ (list\fold (function (_ [idx tag] table)
+ (plist.has tag [idx namespaced_tags exported? type] table))
+ tag_bindings
+ (list.enumeration tags))))
+ (update@ #.types (plist.has type_name [namespaced_tags exported? type]))))
state)
[]]))
#.None
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux
index 351c396e0..f379a9692 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux
@@ -93,7 +93,7 @@
(#.Item (update@ #.captured
(: (-> Foreign Foreign)
(|>> (update@ #.counter inc)
- (update@ #.mappings (plist.put name [ref_type (product.left ref+inner)]))))
+ (update@ #.mappings (plist.has name [ref_type (product.left ref+inner)]))))
scope)
(product.right ref+inner))]))
[init_ref #.End]
@@ -116,7 +116,7 @@
new_head (update@ #.locals
(: (-> Local Local)
(|>> (update@ #.counter inc)
- (update@ #.mappings (plist.put name [type new_var_id]))))
+ (update@ #.mappings (plist.has name [type new_var_id]))))
head)]
(case (///.result' [bundle (set@ #.scopes (#.Item new_head tail) state)]
action)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux
index f5f5d89c8..e123fab83 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux
@@ -324,7 +324,7 @@
(#.Some idx)
(if (dictionary.key? idx->val idx)
(/.except ..cannot_repeat_tag [key record])
- (in (dictionary.put idx val idx->val)))
+ (in (dictionary.has idx val idx->val)))
#.None
(/.except ..tag_does_not_belong_to_record [key recordT]))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux
index 3142451e4..bfb776fcd 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux
@@ -92,7 +92,7 @@
(function (_ [bundle state])
(case (dictionary.get name bundle)
#.None
- (#try.Success [[(dictionary.put name (extender handler) bundle) state]
+ (#try.Success [[(dictionary.has name (extender handler) bundle) state]
[]])
_
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
index 27ce292a0..4ef27d1d8 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
@@ -1933,7 +1933,7 @@
(in [var exT])))
vars)]
(in (list\fold (function (_ [varJ varT] mapping)
- (dictionary.put (jvm_parser.name varJ) varT mapping))
+ (dictionary.has (jvm_parser.name varJ) varT mapping))
mapping
pairings))))
@@ -1942,7 +1942,7 @@
(do phase.monad
[override_mapping (..override_mapping mapping supers parent_type)]
(in (list\fold (function (_ [super_var bound_type] mapping)
- (dictionary.put super_var bound_type mapping))
+ (dictionary.has super_var bound_type mapping))
mapping
override_mapping))))
@@ -2071,7 +2071,7 @@
(list\fold (function (_ [expected actual] mapping)
(case (jvm_parser.var? actual)
(#.Some actual)
- (dictionary.put actual expected mapping)
+ (dictionary.has actual expected mapping)
#.None
mapping))
@@ -2128,7 +2128,7 @@
parameters (typeA.with_env
(..parameter_types parameters))
.let [mapping (list\fold (function (_ [parameterJ parameterT] mapping)
- (dictionary.put (jvm_parser.name parameterJ)
+ (dictionary.has (jvm_parser.name parameterJ)
parameterT
mapping))
luxT.fresh
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux
index a6ce28fc1..3e6c7a0ef 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux
@@ -19,7 +19,7 @@
(All [s i o]
(-> Text (Handler s i o)
(-> (Bundle s i o) (Bundle s i o))))
- (dictionary.put name anonymous))
+ (dictionary.has name anonymous))
(def: .public (prefix prefix)
(All [s i o]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux
index 505ae3bd3..04e197099 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux
@@ -264,7 +264,7 @@
(typeA.with_env
(jvm.parameter_types parameters)))
.let [mapping (list\fold (function (_ [parameterJ parameterT] mapping)
- (dictionary.put (parser.name parameterJ) parameterT mapping))
+ (dictionary.has (parser.name parameterJ) parameterT mapping))
luxT.fresh
parameters)]
super_classT (directive.lift_analysis
@@ -303,5 +303,5 @@
(<| (bundle.prefix "jvm")
(|> bundle.empty
... TODO: Finish handling methods and un-comment.
- ... (dictionary.put "class" jvm::class)
+ ... (dictionary.has "class" jvm::class)
)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux
index 6e3ca3a70..1cba80e10 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux
@@ -429,14 +429,14 @@
(Bundle anchor expression directive)))
(<| (///bundle.prefix "def")
(|> ///bundle.empty
- (dictionary.put "module" def::module)
- (dictionary.put "alias" def::alias)
- (dictionary.put "type tagged" (def::type_tagged expander host_analysis))
- (dictionary.put "analysis" (def::analysis anchorT,expressionT,directiveT extender))
- (dictionary.put "synthesis" (def::synthesis anchorT,expressionT,directiveT extender))
- (dictionary.put "generation" (def::generation anchorT,expressionT,directiveT extender))
- (dictionary.put "directive" (def::directive anchorT,expressionT,directiveT extender))
- (dictionary.put "program" (def::program program))
+ (dictionary.has "module" def::module)
+ (dictionary.has "alias" def::alias)
+ (dictionary.has "type tagged" (def::type_tagged expander host_analysis))
+ (dictionary.has "analysis" (def::analysis anchorT,expressionT,directiveT extender))
+ (dictionary.has "synthesis" (def::synthesis anchorT,expressionT,directiveT extender))
+ (dictionary.has "generation" (def::generation anchorT,expressionT,directiveT extender))
+ (dictionary.has "directive" (def::directive anchorT,expressionT,directiveT extender))
+ (dictionary.has "program" (def::program program))
)))
(def: .public (bundle expander host_analysis program anchorT,expressionT,directiveT extender)
@@ -449,5 +449,5 @@
(Bundle anchor expression directive)))
(<| (///bundle.prefix "lux")
(|> ///bundle.empty
- (dictionary.put "def" (lux::def expander host_analysis))
+ (dictionary.has "def" (lux::def expander host_analysis))
(dictionary.merged (..bundle::def expander host_analysis program anchorT,expressionT,directiveT extender)))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux
index 957407cc8..c4059fc35 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux
@@ -84,7 +84,7 @@
.let [foreigns (|> conditionals
(list\map (|>> product.right synthesis.path/then //case.dependencies))
(list& (//case.dependencies (synthesis.path/then else)))
- list.concat
+ list.joined
(set.of_list _.hash)
set.list)
@expression (_.constant (reference.artifact [context_module context_artifact]))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux
index 172a4d13c..db8c9b18e 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux
@@ -87,8 +87,8 @@
(-> (Expression Any) (Computation Any))
(|>> [1 #1] ..variant))
-(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))}
- body)
+(syntax: .public (with_vars [vars (<code>.tuple (<>.some <code>.local_identifier))
+ body <code>.any])
(do {! meta.monad}
[ids (monad.seq ! (list.repeated (list.size vars) meta.seed))]
(in (list (` (let [(~+ (|> vars
@@ -96,13 +96,13 @@
(list\map (function (_ [id var])
(list (code.local_identifier var)
(` (_.var (~ (code.text (format "v" (%.nat id)))))))))
- list.concat))]
+ list.joined))]
(~ body)))))))
-(syntax: (runtime: {declaration (<>.or <code>.local_identifier
+(syntax: (runtime: [declaration (<>.or <code>.local_identifier
(<code>.form (<>.and <code>.local_identifier
- (<>.some <code>.local_identifier))))}
- code)
+ (<>.some <code>.local_identifier))))
+ code <code>.any])
(do meta.monad
[runtime_id meta.seed]
(macro.with_identifiers [g!_]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux
index aeeb17528..b59e5ce37 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux
@@ -21,7 +21,8 @@
[///
["#" phase]]]])
-(syntax: (Vector {size s.nat} elemT)
+(syntax: (Vector [size s.nat
+ elemT <code>.any])
(in (list (` [(~+ (list.repeated size elemT))]))))
(type: .public (Nullary of) (-> (Vector 0 of) of))
@@ -30,7 +31,9 @@
(type: .public (Trinary of) (-> (Vector 3 of) of))
(type: .public (Variadic of) (-> (List of) of))
-(syntax: (arity: {arity s.nat} {name s.local_identifier} type)
+(syntax: (arity: [arity s.nat
+ name s.local_identifier
+ type <code>.any])
(with_identifiers [g!_ g!extension g!name g!phase g!archive g!inputs g!of g!anchor g!expression g!directive]
(do {! meta.monad}
[g!input+ (monad.seq ! (list.repeated arity (macro.identifier "input")))]
@@ -45,7 +48,7 @@
[(~+ (|> g!input+
(list\map (function (_ g!input)
(list g!input (` ((~ g!phase) (~ g!archive) (~ g!input))))))
- list.concat))]
+ list.joined))]
((~' in) ((~ g!extension) [(~+ g!input+)])))
(~' _)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
index 84e546a41..57916d38a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
@@ -85,8 +85,8 @@
(-> Var (-> Var Expression) Statement)
(_.define name (definition name)))
-(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))}
- body)
+(syntax: .public (with_vars [vars (<code>.tuple (<>.some <code>.local_identifier))
+ body <code>.any])
(do {! meta.monad}
[ids (monad.seq ! (list.repeated (list.size vars) meta.seed))]
(in (list (` (let [(~+ (|> vars
@@ -94,13 +94,13 @@
(list\map (function (_ [id var])
(list (code.local_identifier var)
(` (_.var (~ (code.text (format "v" (%.nat id)))))))))
- list.concat))]
+ list.joined))]
(~ body)))))))
-(syntax: (runtime: {declaration (<>.or <code>.local_identifier
+(syntax: (runtime: [declaration (<>.or <code>.local_identifier
(<code>.form (<>.and <code>.local_identifier
- (<>.some <code>.local_identifier))))}
- code)
+ (<>.some <code>.local_identifier))))
+ code <code>.any])
(macro.with_identifiers [g!_ runtime]
(let [runtime_name (` (_.var (~ (code.text (%.code runtime)))))]
(case declaration
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux
index 5ba5d0f5e..a1c3d7ca2 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux
@@ -102,8 +102,8 @@
(-> Var (-> Var Statement) Statement)
(definition name))
-(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))}
- body)
+(syntax: .public (with_vars [vars (<code>.tuple (<>.some <code>.local_identifier))
+ body <code>.any])
(do {! meta.monad}
[ids (monad.seq ! (list.repeated (list.size vars) meta.seed))]
(in (list (` (let [(~+ (|> vars
@@ -111,16 +111,16 @@
(list\map (function (_ [id var])
(list (code.local_identifier var)
(` (_.var (~ (code.text (format "v" (%.nat id)))))))))
- list.concat))]
+ list.joined))]
(~ body)))))))
(def: module_id
0)
-(syntax: (runtime: {declaration (<>.or <code>.local_identifier
+(syntax: (runtime: [declaration (<>.or <code>.local_identifier
(<code>.form (<>.and <code>.local_identifier
- (<>.some <code>.local_identifier))))}
- code)
+ (<>.some <code>.local_identifier))))
+ code <code>.any])
(do meta.monad
[runtime_id meta.seed]
(macro.with_identifiers [g!_]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux
index 62238c960..6f69ba6e6 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux
@@ -70,8 +70,8 @@
(-> Constant (-> Constant Statement) Statement)
(definition name))
-(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))}
- body)
+(syntax: .public (with_vars [vars (<code>.tuple (<>.some <code>.local_identifier))
+ body <code>.any])
(do {! meta.monad}
[ids (monad.seq ! (list.repeated (list.size vars) meta.seed))]
(in (list (` (let [(~+ (|> vars
@@ -79,16 +79,16 @@
(list\map (function (_ [id var])
(list (code.local_identifier var)
(` (_.var (~ (code.text (format "v" (%.nat id)))))))))
- list.concat))]
+ list.joined))]
(~ body)))))))
(def: module_id
0)
-(syntax: (runtime: {declaration (<>.or <code>.local_identifier
+(syntax: (runtime: [declaration (<>.or <code>.local_identifier
(<code>.form (<>.and <code>.local_identifier
- (<>.some <code>.local_identifier))))}
- code)
+ (<>.some <code>.local_identifier))))
+ code <code>.any])
(do meta.monad
[runtime_id meta.seed]
(macro.with_identifiers [g!_]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux
index 360d33002..e26aca84a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux
@@ -109,8 +109,8 @@
(-> SVar (-> SVar (Statement Any)) (Statement Any))
(definition name))
-(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))}
- body)
+(syntax: .public (with_vars [vars (<code>.tuple (<>.some <code>.local_identifier))
+ body <code>.any])
(do {! meta.monad}
[ids (monad.seq ! (list.repeated (list.size vars) meta.seed))]
(in (list (` (let [(~+ (|> vars
@@ -118,13 +118,13 @@
(list\map (function (_ [id var])
(list (code.local_identifier var)
(` (_.var (~ (code.text (format "v" (%.nat id)))))))))
- list.concat))]
+ list.joined))]
(~ body)))))))
-(syntax: (runtime: {declaration (<>.or <code>.local_identifier
+(syntax: (runtime: [declaration (<>.or <code>.local_identifier
(<code>.form (<>.and <code>.local_identifier
- (<>.some <code>.local_identifier))))}
- code)
+ (<>.some <code>.local_identifier))))
+ code <code>.any])
(case declaration
(#.Left name)
(macro.with_identifiers [g!_]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux
index 18de8ffef..e6134cb95 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux
@@ -34,7 +34,8 @@
(type: .public Bundle
(Dict Text Proc))
-(syntax: (Vector {size s.nat} elemT)
+(syntax: (Vector [{size s.nat}
+ elemT <code>.any])
(in (list (` [(~+ (list.repeated size elemT))]))))
(type: .public Nullary (-> (Vector +0 Expression) Expression))
@@ -47,7 +48,7 @@
(def: .public (install name unnamed)
(-> Text (-> Text Proc)
(-> Bundle Bundle))
- (dict.put name (unnamed name)))
+ (dict.has name (unnamed name)))
(def: .public (prefix prefix bundle)
(-> Text Bundle Bundle)
@@ -62,7 +63,8 @@
"Expected: " (|> expected .int %i) "\n"
" Actual: " (|> actual .int %i)))
-(syntax: (arity: {name s.local_identifier} {arity s.nat})
+(syntax: (arity: [name s.local_identifier
+ arity s.nat])
(with_identifiers [g!_ g!proc g!name g!translate g!inputs]
(do {@ macro.monad}
[g!input+ (monad.seq @ (list.repeated arity (macro.identifier "input")))]
@@ -77,7 +79,7 @@
[(~+ (|> g!input+
(list/map (function (_ g!input)
(list g!input (` ((~ g!translate) (~ g!input))))))
- list.concat))]
+ list.joined))]
((~' in) ((~ g!proc) [(~+ g!input+)])))
(~' _)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux
index 1bcb51d73..36e86df65 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux
@@ -76,8 +76,8 @@
... else
(.int input)))
-(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))}
- body)
+(syntax: .public (with_vars [vars (<code>.tuple (<>.some <code>.local_identifier))
+ body <code>.any])
(do {! meta.monad}
[ids (monad.seq ! (list.repeated (list.size vars) meta.seed))]
(in (list (` (let [(~+ (|> vars
@@ -85,13 +85,13 @@
(list\map (function (_ [id var])
(list (code.local_identifier var)
(` (_.var (~ (code.text (format "v" (%.nat id)))))))))
- list.concat))]
+ list.joined))]
(~ body)))))))
-(syntax: (runtime: {declaration (<>.or <code>.local_identifier
+(syntax: (runtime: [declaration (<>.or <code>.local_identifier
(<code>.form (<>.and <code>.local_identifier
- (<>.some <code>.local_identifier))))}
- code)
+ (<>.some <code>.local_identifier))))
+ code <code>.any])
(do meta.monad
[runtime_id meta.seed]
(macro.with_identifiers [g!_]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux
index 424d8b14b..1bcb1d528 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux
@@ -71,8 +71,8 @@
(-> LVar (-> LVar Statement) Statement)
(definition name))
-(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))}
- body)
+(syntax: .public (with_vars [vars (<code>.tuple (<>.some <code>.local_identifier))
+ body <code>.any])
(do {! meta.monad}
[ids (monad.seq ! (list.repeated (list.size vars) meta.seed))]
(in (list (` (let [(~+ (|> vars
@@ -80,16 +80,16 @@
(list\map (function (_ [id var])
(list (code.local_identifier var)
(` (_.local (~ (code.text (format "v" (%.nat id)))))))))
- list.concat))]
+ list.joined))]
(~ body)))))))
(def: module_id
0)
-(syntax: (runtime: {declaration (<>.or <code>.local_identifier
+(syntax: (runtime: [declaration (<>.or <code>.local_identifier
(<code>.form (<>.and <code>.local_identifier
- (<>.some <code>.local_identifier))))}
- code)
+ (<>.some <code>.local_identifier))))
+ code <code>.any])
(do meta.monad
[runtime_id meta.seed]
(macro.with_identifiers [g!_]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux
index c6d6f4da8..c52ecd6dd 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux
@@ -6,7 +6,7 @@
[control
["ex" exception (#+ exception:)]
[parser
- ["s" code]]]
+ ["<.>" code]]]
[data
["." product]
["." text]
@@ -28,7 +28,8 @@
["#/" // #_
["#." synthesis (#+ Synthesis)]]]])
-(syntax: (Vector {size s.nat} elemT)
+(syntax: (Vector [size <code>.nat
+ elemT <code>.any])
(in (list (` [(~+ (list.repeated size elemT))]))))
(type: .public Nullary (-> (Vector 0 Expression) Computation))
@@ -37,7 +38,8 @@
(type: .public Trinary (-> (Vector 3 Expression) Computation))
(type: .public Variadic (-> (List Expression) Computation))
-(syntax: (arity: {name s.local_identifier} {arity s.nat})
+(syntax: (arity: [name <code>.local_identifier
+ arity <code>.nat])
(with_identifiers [g!_ g!extension g!name g!phase g!inputs]
(do {! macro.monad}
[g!input+ (monad.seq ! (list.repeated arity (macro.identifier "input")))]
@@ -51,7 +53,7 @@
[(~+ (|> g!input+
(list\map (function (_ g!input)
(list g!input (` ((~ g!phase) (~ g!input))))))
- list.concat))]
+ list.joined))]
((~' in) ((~ g!extension) [(~+ g!input+)])))
(~' _)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux
index f5f293f92..95dfef826 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux
@@ -58,8 +58,8 @@
(def: .public unit
(_.string /////synthesis.unit))
-(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))}
- body)
+(syntax: .public (with_vars [vars (<code>.tuple (<>.some <code>.local_identifier))
+ body <code>.any])
(do {! meta.monad}
[ids (monad.seq ! (list.repeated (list.size vars) meta.seed))]
(in (list (` (let [(~+ (|> vars
@@ -67,13 +67,13 @@
(list\map (function (_ [id var])
(list (code.local_identifier var)
(` (_.var (~ (code.text (format "v" (%.nat id)))))))))
- list.concat))]
+ list.joined))]
(~ body)))))))
-(syntax: (runtime: {declaration (<>.or <code>.local_identifier
+(syntax: (runtime: [declaration (<>.or <code>.local_identifier
(<code>.form (<>.and <code>.local_identifier
- (<>.some <code>.local_identifier))))}
- code)
+ (<>.some <code>.local_identifier))))
+ code <code>.any])
(do meta.monad
[runtime_id meta.seed]
(macro.with_identifiers [g!_]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux
index 875b2ca60..7f2666d8b 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux
@@ -341,7 +341,7 @@
path_storage
(^ (/.path/bind register))
- (update@ #bindings (set.add register)
+ (update@ #bindings (set.has register)
path_storage)
(#/.Bit_Fork _ default otherwise)
@@ -378,10 +378,10 @@
(#/.Reference (#///reference.Variable (#///reference/variable.Local register)))
(if (set.member? (get@ #bindings synthesis_storage) register)
synthesis_storage
- (update@ #dependencies (set.add (#///reference/variable.Local register)) synthesis_storage))
+ (update@ #dependencies (set.has (#///reference/variable.Local register)) synthesis_storage))
(#/.Reference (#///reference.Variable var))
- (update@ #dependencies (set.add var) synthesis_storage)
+ (update@ #dependencies (set.has var) synthesis_storage)
(^ (/.function/apply [functionS argsS]))
(list\fold for_synthesis synthesis_storage (#.Item functionS argsS))
@@ -397,7 +397,7 @@
(^ (/.branch/let [inputS register exprS]))
(update@ #dependencies
(set.union (|> synthesis_storage
- (update@ #bindings (set.add register))
+ (update@ #bindings (set.has register))
(for_synthesis exprS)
(get@ #dependencies)))
(for_synthesis inputS synthesis_storage))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux
index 41d618cc3..29ee68fac 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux
@@ -182,7 +182,7 @@
(let [extension (|> amount list.indices (list\map (n.+ offset)))]
[extension
(list\fold (function (_ register redundancy)
- (dictionary.put register ..necessary! redundancy))
+ (dictionary.has register ..necessary! redundancy))
redundancy
extension)]))
@@ -221,7 +221,7 @@
(-> Register Redundancy (Try Redundancy))
(case (dictionary.get register redundancy)
#.None
- (#try.Success (dictionary.put register ..redundant! redundancy))
+ (#try.Success (dictionary.has register ..redundant! redundancy))
(#.Some _)
(exception.except ..redundant_declaration [register])))
@@ -233,7 +233,7 @@
(exception.except ..unknown_register [register])
(#.Some _)
- (#try.Success (dictionary.put register ..necessary! redundancy))))
+ (#try.Success (dictionary.has register ..necessary! redundancy))))
(def: (format redundancy)
(%.Format Redundancy)
@@ -310,7 +310,7 @@
(and (set.member? bindings register)
redundant?)))
(list\map product.left))]]
- (in [(list\fold dictionary.remove redundancy (set.list bindings))
+ (in [(list\fold dictionary.lacks redundancy (set.list bindings))
(|> redundants
(list.sorted n.>)
(list\fold (..remove_local_from_path ..remove_local) (#/.Seq pre post)))]))
@@ -370,7 +370,7 @@
.let [redundant? (|> redundancy
(dictionary.get register)
(maybe.else ..necessary!))]]
- (in [(dictionary.remove register redundancy)
+ (in [(dictionary.lacks register redundancy)
(#/.Control (if redundant?
(#/.Branch (#/.Case input
(#/.Seq #/.Pop
@@ -405,7 +405,7 @@
[[redundancy inits] (..list_optimization optimization' [redundancy inits])
.let [[extension redundancy] (..extended start (list.size inits) redundancy)]
[redundancy iteration] (optimization' [redundancy iteration])]
- (in [(list\fold dictionary.remove redundancy extension)
+ (in [(list\fold dictionary.lacks redundancy extension)
(#/.Control (#/.Loop (#/.Scope [start inits iteration])))]))
(#/.Recur resets)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux
index 348a7ced9..1d605c120 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux
@@ -111,18 +111,18 @@
(#try.Success [next
(|> archive
:representation
- (update@ #..resolver (dictionary.put module [next #.None]))
+ (update@ #..resolver (dictionary.has module [next #.None]))
(update@ #..next inc)
:abstraction)]))))
- (def: .public (add module [descriptor document output] archive)
+ (def: .public (has module [descriptor document output] archive)
(-> Module [Descriptor (Document Any) Output] Archive (Try Archive))
(let [(^slots [#..resolver]) (:representation archive)]
(case (dictionary.get module resolver)
(#.Some [id #.None])
(#try.Success (|> archive
:representation
- (update@ #..resolver (dictionary.put module [id (#.Some [descriptor document output])]))
+ (update@ #..resolver (dictionary.has module [id (#.Some [descriptor document output])]))
:abstraction))
(#.Some [id (#.Some [existing_descriptor existing_document existing_output])])
@@ -201,7 +201,7 @@
(list\fold (function (_ [module [id entry]] resolver)
(case entry
(#.Some _)
- (dictionary.put module [id entry] resolver)
+ (dictionary.has module [id entry] resolver)
#.None
resolver))
@@ -280,7 +280,7 @@
(in (:abstraction
{#next next
#resolver (list\fold (function (_ [module id] archive)
- (dictionary.put module [id #.None] archive))
+ (dictionary.has module [id #.None] archive))
(get@ #resolver (:representation ..empty))
reservations)}))))
)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux
index 11aa363fd..e4240e404 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux
@@ -75,7 +75,7 @@
:representation
(update@ #artifacts (row.add {#id id
#category (<tag> name)}))
- (update@ #resolver (dictionary.put name id))
+ (update@ #resolver (dictionary.has name id))
:abstraction)]))
(def: .public (<fetch> registry)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux
index 66a903ca1..fc6c26067 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux
@@ -47,7 +47,7 @@
(def: .public graph
(-> (List Dependency) Graph)
(list\fold (function (_ [module imports] graph)
- (dictionary.put module imports graph))
+ (dictionary.has module imports graph))
..empty))
(def: (ancestry archive)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
index a87c3840b..a1f263f05 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
@@ -251,7 +251,7 @@
output])
(do !
[value (\ host re_load context #.None directive)]
- (in [(dictionary.put name value definitions)
+ (in [(dictionary.has name value definitions)
[analysers
synthesizers
generators
@@ -263,7 +263,7 @@
[.let [output (row.add [artifact_id #.None data] output)]
value (\ host re_load context #.None directive)]
(in [definitions
- [(dictionary.put extension (:as analysis.Handler value) analysers)
+ [(dictionary.has extension (:as analysis.Handler value) analysers)
synthesizers
generators
directives]
@@ -275,7 +275,7 @@
value (\ host re_load context #.None directive)]
(in [definitions
[analysers
- (dictionary.put extension (:as synthesis.Handler value) synthesizers)
+ (dictionary.has extension (:as synthesis.Handler value) synthesizers)
generators
directives]
output]))
@@ -287,7 +287,7 @@
(in [definitions
[analysers
synthesizers
- (dictionary.put extension (:as generation.Handler value) generators)
+ (dictionary.has extension (:as generation.Handler value) generators)
directives]
output]))
@@ -299,7 +299,7 @@
[analysers
synthesizers
generators
- (dictionary.put extension (:as directive.Handler value) directives)]
+ (dictionary.has extension (:as directive.Handler value) directives)]
output]))
(#artifact.Custom name)
@@ -393,7 +393,7 @@
(get@ #descriptor.references)
set.list
(list.any? purged?))
- (dictionary.put module_name module_id purge)
+ (dictionary.has module_name module_id purge)
purge))))
(..initial_purge caches)
load_order))
@@ -424,7 +424,7 @@
(list\map product.right)
(monad.fold try.monad
(function (_ [module [module_id [descriptor document]]] archive)
- (archive.add module [descriptor document (: Output row.empty)] archive))
+ (archive.has module [descriptor document (: Output row.empty)] archive))
archive)
(\ try.monad map (dependency.load_order $.key))
(\ try.monad join)
@@ -444,7 +444,7 @@
(do {! try.monad}
[archive (monad.fold !
(function (_ [[module descriptor,document,output] _bundle] archive)
- (archive.add module descriptor,document,output archive))
+ (archive.has module descriptor,document,output archive))
archive
loaded_caches)
analysis_state (..analysis_state (get@ #static.host static) archive)]
diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
index 993b2264d..06ef9b25b 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
@@ -227,12 +227,12 @@
(case (java/util/jar/JarOutputStream::putNextEntry (java/util/jar/JarEntry::new entry_path) sink)
(#try.Failure error)
(recur entries
- (set.add entry_path duplicates)
+ (set.has entry_path duplicates)
sink)
(#try.Success _)
(let [[entry_size entry_data] (read_jar_entry entry input)]
- (recur (set.add entry_path entries)
+ (recur (set.has entry_path entries)
duplicates
(do_to sink
(java/util/zip/ZipOutputStream::write entry_data +0 (.int entry_size))
diff --git a/stdlib/source/library/lux/tool/compiler/phase.lux b/stdlib/source/library/lux/tool/compiler/phase.lux
index 5bfdac402..d1cecbe50 100644
--- a/stdlib/source/library/lux/tool/compiler/phase.lux
+++ b/stdlib/source/library/lux/tool/compiler/phase.lux
@@ -10,7 +10,7 @@
["ex" exception (#+ Exception exception:)]
["." io]
[parser
- ["s" code]]]
+ ["<.>" code]]]
[data
["." product]
["." text
@@ -81,7 +81,9 @@
(function (_ state)
(try\map (|>> [state]) error)))
-(syntax: .public (assertion exception message test)
+(syntax: .public (assertion [exception <code>.any
+ message <code>.any
+ test <code>.any])
(in (list (` (if (~ test)
(\ ..monad (~' in) [])
(..except (~ exception) (~ message)))))))
diff --git a/stdlib/source/library/lux/type.lux b/stdlib/source/library/lux/type.lux
index 7a93c29dd..521ec2e8a 100644
--- a/stdlib/source/library/lux/type.lux
+++ b/stdlib/source/library/lux/type.lux
@@ -380,16 +380,16 @@
product.left
(n.> 0)))
-(syntax: (new_secret_marker)
+(syntax: (new_secret_marker [])
(macro.with_identifiers [g!_secret_marker_]
(in (list g!_secret_marker_))))
(def: secret_marker
(`` (name_of (~~ (new_secret_marker)))))
-(syntax: .public (:log! {input (<>.or (<>.and <code>.identifier
+(syntax: .public (:log! [input (<>.or (<>.and <code>.identifier
(<>.maybe (<>.after (<code>.identifier! ..secret_marker) <code>.any)))
- <code>.any)})
+ <code>.any)])
(case input
(#.Left [valueN valueC])
(do meta.monad
@@ -417,10 +417,10 @@
(Parser (List Text))
(<code>.tuple (<>.some <code>.local_identifier)))
-(syntax: .public (:cast {type_vars type_parameters}
- input
- output
- {value (<>.maybe <code>.any)})
+(syntax: .public (:cast [type_vars type_parameters
+ input <code>.any
+ output <code>.any
+ value (<>.maybe <code>.any)])
(let [casterC (` (: (All [(~+ (list\map code.local_identifier type_vars))]
(-> (~ input) (~ output)))
(|>> :assume)))]
@@ -440,9 +440,9 @@
(<>.and <code>.any <code>.any))
... TODO: Make sure the generated code always gets optimized away.
-(syntax: .public (:sharing {type_vars ..type_parameters}
- {exemplar ..typed}
- {computation ..typed})
+(syntax: .public (:sharing [type_vars ..type_parameters
+ exemplar ..typed
+ computation ..typed])
(macro.with_identifiers [g!_]
(let [shareC (` (: (All [(~+ (list\map code.local_identifier type_vars))]
(-> (~ (get@ #type exemplar))
@@ -451,9 +451,9 @@
(~ (get@ #expression computation)))))]
(in (list (` ((~ shareC) (~ (get@ #expression exemplar)))))))))
-(syntax: .public (:by_example {type_vars ..type_parameters}
- {exemplar ..typed}
- {extraction <code>.any})
+(syntax: .public (:by_example [type_vars ..type_parameters
+ exemplar ..typed
+ extraction <code>.any])
(in (list (` (:of ((~! :sharing)
[(~+ (list\map code.local_identifier type_vars))]
diff --git a/stdlib/source/library/lux/type/abstract.lux b/stdlib/source/library/lux/type/abstract.lux
index 84a2b2942..90332bf08 100644
--- a/stdlib/source/library/lux/type/abstract.lux
+++ b/stdlib/source/library/lux/type/abstract.lux
@@ -165,7 +165,7 @@
(!push source module_reference
(|> head (update@ #.definitions (pop_frame_definition definition_reference)))))
-(syntax: (pop!)
+(syntax: (pop! [])
(function (_ compiler)
(#.Right [(update@ #.modules
(..pop_frame (name_of ..frames))
@@ -178,7 +178,7 @@
(<>.and (<>\in #.None) <code>.any)))
(template [<name> <from> <to>]
- [(syntax: .public (<name> {[frame value] ..cast})
+ [(syntax: .public (<name> [[frame value] ..cast])
{#.doc (example "Type-casting macro for abstract/nominal types."
(: <to>
(<name> (: <from>
@@ -226,9 +226,8 @@
... TODO: Make sure the generated code always gets optimized away.
... (This applies to uses of ":abstraction" and ":representation")
-(syntax: .public (abstract:
- {[export_policy [name type_vars] annotations representation_type primitives]
- ..abstract})
+(syntax: .public (abstract: [[export_policy [name type_vars] annotations representation_type primitives]
+ ..abstract])
{#.doc (example "Define abstract/nominal types which hide their representation details."
"You can convert between the abstraction and its representation selectively to access the value, while hiding it from others."
(abstract: String
@@ -336,7 +335,7 @@
(<>.or (<>.and <code>.any parser)
parser))
-(syntax: .public (:transmutation {selection (..selection <code>.any)})
+(syntax: .public (:transmutation [selection (..selection <code>.any)])
{#.doc (example "Transmutes an abstract/nominal type's phantom types."
(abstract: (JavaScript a)
{}
@@ -362,9 +361,9 @@
(#Current value)
(in (list (` (.|> (~ value) ..:representation ..:abstraction))))))
-(syntax: .public (^:representation {selection (<code>.form (..selection <code>.local_identifier))}
- body
- {branches (<>.some <code>.any)})
+(syntax: .public (^:representation [selection (<code>.form (..selection <code>.local_identifier))
+ body <code>.any
+ branches (<>.some <code>.any)])
{#.doc (example "Pattern-matching macro to easily extract a representation."
(def: (computation abstraction)
(All [a] (-> (Abstract a) ???))
diff --git a/stdlib/source/library/lux/type/check.lux b/stdlib/source/library/lux/type/check.lux
index 10fe700e8..2048e1159 100644
--- a/stdlib/source/library/lux/type/check.lux
+++ b/stdlib/source/library/lux/type/check.lux
@@ -310,14 +310,14 @@
(-> Var (Check Ring))
(function (_ context)
(loop [current start
- output (set.add start empty_ring)]
+ output (set.has start empty_ring)]
(case (|> context (get@ #.var_bindings) (var::get current))
(#.Some (#.Some type))
(case type
(#.Var post)
(if (!n\= start post)
(#try.Success [context output])
- (recur post (set.add post output)))
+ (recur post (set.has post output)))
_
(#try.Success [context empty_ring]))
diff --git a/stdlib/source/library/lux/type/dynamic.lux b/stdlib/source/library/lux/type/dynamic.lux
index db594d293..f2f28fdf2 100644
--- a/stdlib/source/library/lux/type/dynamic.lux
+++ b/stdlib/source/library/lux/type/dynamic.lux
@@ -4,7 +4,9 @@
["." debug]
[control
["." try (#+ Try)]
- ["." exception (#+ exception:)]]
+ ["." exception (#+ exception:)]
+ [parser
+ ["<.>" code]]]
[data
[text
["%" format]]]
@@ -23,17 +25,23 @@
[Type Any]
- (def: abstraction (-> [Type Any] Dynamic) (|>> :abstraction))
- (def: representation (-> Dynamic [Type Any]) (|>> :representation))
+ (def: abstraction
+ (-> [Type Any] Dynamic)
+ (|>> :abstraction))
+
+ (def: representation
+ (-> Dynamic [Type Any])
+ (|>> :representation))
- (syntax: .public (:dynamic value)
+ (syntax: .public (:dynamic [value <code>.any])
{#.doc (example (: Dynamic
(:dynamic 123)))}
(with_identifiers [g!value]
(in (list (` (let [(~ g!value) (~ value)]
((~! ..abstraction) [(:of (~ g!value)) (~ g!value)])))))))
- (syntax: .public (:static type value)
+ (syntax: .public (:static [type <code>.any
+ value <code>.any])
{#.doc (example (: (try.Try Nat)
(:static Nat (:dynamic 123))))}
(with_identifiers [g!type g!value]
diff --git a/stdlib/source/library/lux/type/implicit.lux b/stdlib/source/library/lux/type/implicit.lux
index d9e962ba2..957f7deb2 100644
--- a/stdlib/source/library/lux/type/implicit.lux
+++ b/stdlib/source/library/lux/type/implicit.lux
@@ -313,10 +313,9 @@
_
(` ((~ (code.identifier constructor)) (~+ (list\map instance$ dependencies))))))
-(syntax: .public (\\
- {member <code>.identifier}
- {args (<>.or (<>.and (<>.some <code>.identifier) <code>.end!)
- (<>.and (<>.some <code>.any) <code>.end!))})
+(syntax: .public (\\ [member <code>.identifier
+ args (<>.or (<>.and (<>.some <code>.identifier) <code>.end!)
+ (<>.and (<>.some <code>.any) <code>.end!))])
{#.doc (example "Automatic implementation selection (for type-class style polymorphism)."
"This feature layers type-class style polymorphism on top of Lux's signatures and implementations."
"When calling a polymorphic function, or using a polymorphic constant,"
@@ -380,7 +379,8 @@
(Parser (List Code))
(<code>.tuple (<>.many <code>.any)))
-(syntax: .public (with {implementations ..implicits} body)
+(syntax: .public (with [implementations ..implicits
+ body <code>.any])
{#.doc (example "Establish lexical bindings for implementations that will be prioritized over non-lexically-bound implementations."
(with [n.addition]
(n.= (\ n.addition compose left right)
@@ -393,7 +393,7 @@
list\join))]
(~ body)))))))
-(syntax: .public (implicit: {implementations ..implicits})
+(syntax: .public (implicit: [implementations ..implicits])
{#.doc (example "Establish local definitions for implementations that will be prioritized over foreign definitions."
(implicit: [n.multiplication])
diff --git a/stdlib/source/library/lux/type/quotient.lux b/stdlib/source/library/lux/type/quotient.lux
index a2ac468af..0006d9dbd 100644
--- a/stdlib/source/library/lux/type/quotient.lux
+++ b/stdlib/source/library/lux/type/quotient.lux
@@ -3,6 +3,9 @@
[lux (#- type)
[abstract
[equivalence (#+ Equivalence)]]
+ [control
+ [parser
+ ["<.>" code]]]
[macro (#+ with_identifiers)
[syntax (#+ syntax:)]]
["." type
@@ -45,7 +48,7 @@
)
)
-(syntax: .public (type class)
+(syntax: .public (type [class <code>.any])
{#.doc (example "The Quotient type associated with a Class type."
(def: even
(class even?))
diff --git a/stdlib/source/library/lux/type/refinement.lux b/stdlib/source/library/lux/type/refinement.lux
index 78e289e4a..c171f3b3e 100644
--- a/stdlib/source/library/lux/type/refinement.lux
+++ b/stdlib/source/library/lux/type/refinement.lux
@@ -3,6 +3,9 @@
[lux (#- type)
[abstract
[predicate (#+ Predicate)]]
+ [control
+ [parser
+ ["<.>" code]]]
["." macro
[syntax (#+ syntax:)]]
["." type
@@ -86,7 +89,7 @@
[yes
(#.Item head no)]))))
-(syntax: .public (type refiner)
+(syntax: .public (type [refiner <code>.any])
{#.doc (example "The Refined type associated with a Refiner type."
(def: even
(refiner even?))
diff --git a/stdlib/source/library/lux/type/resource.lux b/stdlib/source/library/lux/type/resource.lux
index 9ecd67608..1dea469da 100644
--- a/stdlib/source/library/lux/type/resource.lux
+++ b/stdlib/source/library/lux/type/resource.lux
@@ -139,7 +139,7 @@
[head <code>.nat
_ (<>.assertion (exception.error ..index_cannot_be_repeated head)
(not (set.member? seen head)))
- tail (recur (set.add head seen))]
+ tail (recur (set.has head seen))]
(in (list& head tail))))))))
(def: (no_op monad)
@@ -147,7 +147,7 @@
(function (_ context)
(\ monad in [context []])))
-(syntax: .public (exchange {swaps ..indices})
+(syntax: .public (exchange [swaps ..indices])
{#.doc (example "A function that can exchange the keys for resource, so long as they are commutative."
"This keys will be placed at the front of the keyring in the order they are specified."
"The specific keys must be specified based of their index into the current keyring."
@@ -196,7 +196,7 @@
(in raw)))
(template [<name> <from> <to>]
- [(syntax: .public (<name> {amount ..amount})
+ [(syntax: .public (<name> [amount ..amount])
{#.doc (example "Group/un-group keys in the keyring into/out-of tuples."
(do (..monad !)
[res|left (/.commutative ! pre)
diff --git a/stdlib/source/library/lux/type/unit.lux b/stdlib/source/library/lux/type/unit.lux
index 511bbbb33..fcbfe0711 100644
--- a/stdlib/source/library/lux/type/unit.lux
+++ b/stdlib/source/library/lux/type/unit.lux
@@ -89,12 +89,12 @@
(-> Pure Int)
..out)
-(syntax: .public (unit: {[export_policy type_name unit_name annotations]
+(syntax: .public (unit: [[export_policy type_name unit_name annotations]
(|export|.parser
($_ <>.and
<code>.local_identifier
<code>.local_identifier
- (<>.else |annotations|.empty |annotations|.parser)))})
+ (<>.else |annotations|.empty |annotations|.parser)))])
{#.doc (example "Define a unit of measurement."
"Both the name of the type, and the name of the Unit implementation must be specified."
(unit: .public Feet feet
@@ -124,13 +124,13 @@
(n.> 0 denominator))]
(in [numerator denominator]))))
-(syntax: .public (scale: {[export_policy type_name scale_name ratio annotations]
+(syntax: .public (scale: [[export_policy type_name scale_name ratio annotations]
(|export|.parser
($_ <>.and
<code>.local_identifier
<code>.local_identifier
..scale
- (<>.else |annotations|.empty |annotations|.parser)))})
+ (<>.else |annotations|.empty |annotations|.parser)))])
{#.doc (example "Define a scale of magnitude."
(scale: .public Bajillion bajillion
[1 1,234,567,890]
@@ -170,7 +170,7 @@
(i./ (.int denominator))
in)))
-(syntax: (implementation_name {type_name <code>.local_identifier})
+(syntax: (implementation_name [type_name <code>.local_identifier])
(in (list (code.local_identifier (text.lower_cased type_name)))))
(template [<type> <from> <to>]
diff --git a/stdlib/source/library/lux/world/file.lux b/stdlib/source/library/lux/world/file.lux
index 19dde66f4..b0ae0d400 100644
--- a/stdlib/source/library/lux/world/file.lux
+++ b/stdlib/source/library/lux/world/file.lux
@@ -1045,7 +1045,7 @@
#.None
(case tail
#.End
- (#try.Success (dictionary.put head
+ (#try.Success (dictionary.has head
(#.Left {#mock_last_modified now
#mock_can_execute false
#mock_content content})
@@ -1057,7 +1057,7 @@
(#.Some node)
(case [node tail]
[(#.Left file) #.End]
- (#try.Success (dictionary.put head
+ (#try.Success (dictionary.has head
(#.Left (|> file
(set@ #mock_last_modified now)
(set@ #mock_content content)))
@@ -1066,7 +1066,7 @@
[(#.Right sub_directory) (#.Item _)]
(do try.monad
[sub_directory (recur sub_directory tail)]
- (in (dictionary.put head (#.Right sub_directory) directory)))
+ (in (dictionary.has head (#.Right sub_directory) directory)))
_
(exception.except ..cannot_find_file [path])))
@@ -1089,11 +1089,11 @@
#.End
(case node
(#.Left file)
- (#try.Success (dictionary.remove head directory))
+ (#try.Success (dictionary.lacks head directory))
(#.Right sub_directory)
(if (dictionary.empty? sub_directory)
- (#try.Success (dictionary.remove head directory))
+ (#try.Success (dictionary.lacks head directory))
(exception.except ..cannot_delete [path])))
(#.Item _)
@@ -1104,7 +1104,7 @@
(#.Right sub_directory)
(do try.monad
[sub_directory' (recur sub_directory tail)]
- (in (dictionary.put head (#.Right sub_directory') directory))))))
+ (in (dictionary.has head (#.Right sub_directory') directory))))))
#.End
(exception.except ..cannot_delete [path]))))
@@ -1132,7 +1132,7 @@
#.None
(case tail
#.End
- (#try.Success (dictionary.put head (#.Right ..empty_mock) directory))
+ (#try.Success (dictionary.has head (#.Right ..empty_mock) directory))
(#.Item _)
(exception.except ..cannot_make_directory [path]))
@@ -1142,7 +1142,7 @@
[(#.Right sub_directory) (#.Item _)]
(do try.monad
[sub_directory (recur sub_directory tail)]
- (in (dictionary.put head (#.Right sub_directory) directory)))
+ (in (dictionary.has head (#.Right sub_directory) directory)))
_
(exception.except ..cannot_make_directory [path])))
diff --git a/stdlib/source/library/lux/world/file/watch.lux b/stdlib/source/library/lux/world/file/watch.lux
index e3d26e30c..c7642f6b5 100644
--- a/stdlib/source/library/lux/world/file/watch.lux
+++ b/stdlib/source/library/lux/world/file/watch.lux
@@ -116,7 +116,7 @@
(case (dictionary.get path @tracker)
(#.Some [old_concern last_modified])
(do !
- [_ (stm.update (dictionary.put path [new_concern last_modified]) tracker)]
+ [_ (stm.update (dictionary.has path [new_concern last_modified]) tracker)]
(in true))
#.None
@@ -130,12 +130,12 @@
(function (_ file tracker)
(do !
[last_modified (\ fs last_modified file)]
- (in (dictionary.put file last_modified tracker))))
+ (in (dictionary.has file last_modified tracker))))
(: File_Tracker
(dictionary.empty text.hash))
files)))
-(def: (poll_files fs directory)
+(def: (available_files fs directory)
(-> (//.System Async) //.Path (Async (Try (List [//.Path Instant]))))
(do {! (try.with async.monad)}
[files (\ fs directory_files directory)]
@@ -145,14 +145,14 @@
(\ ! map (|>> [file]))))
files)))
-(def: (poll_directory_changes fs [directory [concern file_tracker]])
+(def: (available_directory_changes fs [directory [concern file_tracker]])
(-> (//.System Async) [//.Path [Concern File_Tracker]]
(Async (Try [[//.Path [Concern File_Tracker]]
[(List [//.Path Instant])
(List [//.Path Instant Instant])
(List //.Path)]])))
(do {! (try.with async.monad)}
- [current_files (..poll_files fs directory)
+ [current_files (..available_files fs directory)
.let [creations (if (..creation? concern)
(list.only (|>> product.left (dictionary.key? file_tracker) not)
current_files)
@@ -172,13 +172,13 @@
current_files)]]
(in [[directory
[concern
- (let [with_deletions (list\fold dictionary.remove file_tracker deletions)
+ (let [with_deletions (list\fold dictionary.lacks file_tracker deletions)
with_creations (list\fold (function (_ [path last_modified] tracker)
- (dictionary.put path last_modified tracker))
+ (dictionary.has path last_modified tracker))
with_deletions
creations)
with_modifications (list\fold (function (_ [path previous_modification current_modification] tracker)
- (dictionary.put path current_modification tracker))
+ (dictionary.has path current_modification tracker))
with_creations
modifications)]
with_modifications)]]
@@ -204,7 +204,7 @@
(do (try.with !)
[file_tracker (..file_tracker fs path)]
(do !
- [_ (stm.commit (stm.update (dictionary.put path [new_concern file_tracker]) tracker))]
+ [_ (stm.commit (stm.update (dictionary.has path [new_concern file_tracker]) tracker))]
(in (#try.Success []))))))
(in (exception.except ..cannot_poll_a_non_existent_directory [path])))))
(def: (concern path)
@@ -224,7 +224,7 @@
(case (dictionary.get path @tracker)
(#.Some [concern file_tracker])
(do !
- [_ (stm.update (dictionary.remove path) tracker)]
+ [_ (stm.update (dictionary.lacks path) tracker)]
(in (#try.Success concern)))
#.None
@@ -235,7 +235,7 @@
(do {! (try.with async.monad)}
[changes (|> @tracker
dictionary.entries
- (monad.map ! (..poll_directory_changes fs)))
+ (monad.map ! (..available_directory_changes fs)))
_ (do async.monad
[_ (stm.commit (stm.write (|> changes
(list\map product.left)
@@ -431,7 +431,7 @@
(do !
[_ (async.future
(java/nio/file/WatchKey::cancel key))
- _ (stm.commit (stm.update (dictionary.remove path) tracker))]
+ _ (stm.commit (stm.update (dictionary.lacks path) tracker))]
(in (#try.Success concern)))
#.None
@@ -447,7 +447,7 @@
watcher
path)]
(do async.monad
- [_ (stm.commit (stm.update (dictionary.put path [concern key]) tracker))]
+ [_ (stm.commit (stm.update (dictionary.has path [concern key]) tracker))]
(in (#try.Success []))))))
(def: (concern path)
(do async.monad
diff --git a/stdlib/source/library/lux/world/net/http/client.lux b/stdlib/source/library/lux/world/net/http/client.lux
index 6b2d9eb99..167d87c88 100644
--- a/stdlib/source/library/lux/world/net/http/client.lux
+++ b/stdlib/source/library/lux/world/net/http/client.lux
@@ -37,10 +37,10 @@
(! (Try (//.Response !))))
request))
-(syntax: (method_name {[_ name] <code>.tag})
+(syntax: (method_name [[_ name] <code>.tag])
(in (list (code.text (text.upper_cased name)))))
-(syntax: (method_function {[_ name] <code>.tag})
+(syntax: (method_function [[_ name] <code>.tag])
(in (list (code.local_identifier (text.lower_cased name)))))
(template [<method>]
@@ -183,7 +183,7 @@
(do !
[?value (java/net/URLConnection::getHeaderField index connection)]
(recur (inc index)
- (dictionary.put name (maybe.else "" ?value) headers)))
+ (dictionary.has name (maybe.else "" ?value) headers)))
#.None
(in headers)))))
diff --git a/stdlib/source/library/lux/world/net/http/cookie.lux b/stdlib/source/library/lux/world/net/http/cookie.lux
index a138f556c..c9673ed31 100644
--- a/stdlib/source/library/lux/world/net/http/cookie.lux
+++ b/stdlib/source/library/lux/world/net/http/cookie.lux
@@ -30,7 +30,7 @@
(def: .public (set name value)
(-> Text Text Header)
- (header.add "Set-Cookie" (format name "=" value)))
+ (header.has "Set-Cookie" (format name "=" value)))
(def: .public (max_age duration)
(-> Duration Directive)
@@ -73,7 +73,7 @@
[key (l.slice (l.many! (l.none_of! "=")))
_ (l.this "=")
value (l.slice (l.many! (l.none_of! ";")))]
- (in (dictionary.put key value context))))
+ (in (dictionary.has key value context))))
(def: (cookies context)
(-> Context (Parser Context))
diff --git a/stdlib/source/library/lux/world/net/http/header.lux b/stdlib/source/library/lux/world/net/http/header.lux
index 6f8d92cc2..76e96c815 100644
--- a/stdlib/source/library/lux/world/net/http/header.lux
+++ b/stdlib/source/library/lux/world/net/http/header.lux
@@ -12,7 +12,7 @@
["." mime (#+ MIME)]
[// (#+ URL)]])
-(def: .public (add name value)
+(def: .public (has name value)
(-> Text Text Header)
(dictionary.upsert name ""
(|>> (case>
@@ -24,12 +24,12 @@
(def: .public content_length
(-> Nat Header)
- (|>> %.nat (..add "Content-Length")))
+ (|>> %.nat (..has "Content-Length")))
(def: .public content_type
(-> MIME Header)
- (|>> mime.name (..add "Content-Type")))
+ (|>> mime.name (..has "Content-Type")))
(def: .public location
(-> URL Header)
- (..add "Location"))
+ (..has "Location"))
diff --git a/stdlib/source/library/lux/world/net/http/query.lux b/stdlib/source/library/lux/world/net/http/query.lux
index 86ee79c2b..0fc879552 100644
--- a/stdlib/source/library/lux/world/net/http/query.lux
+++ b/stdlib/source/library/lux/world/net/http/query.lux
@@ -51,12 +51,12 @@
(p.either (do !
[_ (l.this "=")
value ..component]
- (form (dictionary.put key value context)))
+ (form (dictionary.has key value context)))
(do !
[_ ($_ p.or
(l.one_of "&;")
l.end)]
- (form (dictionary.put key "" context)))))
+ (form (dictionary.has key "" context)))))
... if invalid form data, just stop parsing...
(\ p.monad in context)))
diff --git a/stdlib/source/library/lux/world/net/http/request.lux b/stdlib/source/library/lux/world/net/http/request.lux
index b934e01d5..92b399f28 100644
--- a/stdlib/source/library/lux/world/net/http/request.lux
+++ b/stdlib/source/library/lux/world/net/http/request.lux
@@ -47,7 +47,7 @@
(def: (read_text_body body)
(-> Body (Async (Try Text)))
(do async.monad
- [blobs (frp.consume body)]
+ [blobs (frp.list body)]
(in (\ encoding.utf8 decode (merge blobs)))))
(def: failure (//response.bad_request ""))
diff --git a/stdlib/source/library/lux/world/net/http/status.lux b/stdlib/source/library/lux/world/net/http/status.lux
index 57a88ef09..b0111e660 100644
--- a/stdlib/source/library/lux/world/net/http/status.lux
+++ b/stdlib/source/library/lux/world/net/http/status.lux
@@ -12,7 +12,7 @@
["." template]]]]
[// (#+ Status)])
-(syntax: (status_description {name <code>.local_identifier})
+(syntax: (status_description [name <code>.local_identifier])
(in (list (code.text (text.replaced "_" " " name)))))
... https://en.wikipedia.org/wiki/List_of_HTTP_status_codes
diff --git a/stdlib/source/library/lux/world/output/video/resolution.lux b/stdlib/source/library/lux/world/output/video/resolution.lux
index bbe7bdd74..08b5f1a3f 100644
--- a/stdlib/source/library/lux/world/output/video/resolution.lux
+++ b/stdlib/source/library/lux/world/output/video/resolution.lux
@@ -31,7 +31,7 @@
(Equivalence Resolution)
(\ ..hash &equivalence))
-(syntax: (description {name <code>.local_identifier})
+(syntax: (description [name <code>.local_identifier])
(in (list (|> name
(text.replaced "/" " ")
(text.replaced "_" " ")
diff --git a/stdlib/source/library/lux/world/program.lux b/stdlib/source/library/lux/world/program.lux
index ea1ecc83b..5c9735c51 100644
--- a/stdlib/source/library/lux/world/program.lux
+++ b/stdlib/source/library/lux/world/program.lux
@@ -40,6 +40,8 @@
["Name" (%.text name)]))
(interface: .public (Program !)
+ {#.doc (example "Access to ambient program data and the capacity to exit the program.")}
+
(: (-> Any (! (List Text)))
available_variables)
(: (-> Text (! (Try Text)))
@@ -52,6 +54,7 @@
exit))
(def: .public (environment monad program)
+ {#.doc (example "Assembles the environment variables available to the program.")}
(All [!] (-> (Monad !) (Program !) (! Environment)))
(do {! monad}
[variables (\ program available_variables [])
@@ -343,7 +346,7 @@
... (in output)
... (let [entry (..head input)]
... (recur (..tail input)
- ... (dictionary.put (..car entry) (..cdr entry) output))))))
+ ... (dictionary.has (..car entry) (..cdr entry) output))))))
})))
(def: (variable name)
diff --git a/stdlib/source/library/lux/world/shell.lux b/stdlib/source/library/lux/world/shell.lux
index a09be98bb..429c46897 100644
--- a/stdlib/source/library/lux/world/shell.lux
+++ b/stdlib/source/library/lux/world/shell.lux
@@ -34,6 +34,7 @@
[file (#+ Path)]])
(type: .public Exit
+ {#.doc (example "A program exit code.")}
Int)
(template [<code> <name>]
@@ -46,6 +47,8 @@
)
(interface: .public (Process !)
+ {#.doc (example "The means for communicating with a program/process being executed by the operating system.")}
+
(: (-> [] (! (Try Text)))
read)
(: (-> [] (! (Try Text)))
@@ -73,12 +76,16 @@
)))))
(type: .public Command
+ {#.doc (example "A command that can be executed by the operating system.")}
Text)
(type: .public Argument
+ {#.doc (example "A parameter for a command.")}
Text)
(interface: .public (Shell !)
+ {#.doc (example "The means for issuing commands to the operating system.")}
+
(: (-> [Environment Path Command (List Argument)] (! (Try (Process !))))
execute))
@@ -307,6 +314,8 @@
(as_is)))
(interface: .public (Mock s)
+ {#.doc (example "A simulated process.")}
+
(: (-> s (Try [s Text]))
on_read)
(: (-> s (Try [s Text]))