aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/control
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/control/concatenative.lux7
-rw-r--r--stdlib/source/lux/control/concurrency/actor.lux13
-rw-r--r--stdlib/source/lux/control/exception.lux7
-rw-r--r--stdlib/source/lux/control/parser/type.lux21
-rw-r--r--stdlib/source/lux/control/security/capability.lux7
5 files changed, 32 insertions, 23 deletions
diff --git a/stdlib/source/lux/control/concatenative.lux b/stdlib/source/lux/control/concatenative.lux
index 605539376..2791cce92 100644
--- a/stdlib/source/lux/control/concatenative.lux
+++ b/stdlib/source/lux/control/concatenative.lux
@@ -19,7 +19,8 @@
[syntax (#+ syntax:)
["cs" common
["csr" reader]
- ["csw" writer]]]]]
+ ["csw" writer]
+ ["|.|" export]]]]]
[//
["<>" parser ("#\." monad)
["<c>" code (#+ Parser)]]])
@@ -104,12 +105,12 @@
(wrap (list (` (|> (~! ..begin!) (~+ commands) ((~! ..end!)))))))
(syntax: #export (word:
- {export csr.export}
+ {export |export|.parser}
{name <c>.local-identifier}
{annotations (<>.default cs.empty-annotations csr.annotations)}
type
{commands (<>.some <c>.any)})
- (wrap (list (` (def: (~+ (csw.export export)) (~ (code.local-identifier name))
+ (wrap (list (` (def: (~+ (|export|.write export)) (~ (code.local-identifier name))
(~ (csw.annotations annotations))
(~ type)
(|>> (~+ commands)))))))
diff --git a/stdlib/source/lux/control/concurrency/actor.lux b/stdlib/source/lux/control/concurrency/actor.lux
index f9ab10327..66ea24cd8 100644
--- a/stdlib/source/lux/control/concurrency/actor.lux
+++ b/stdlib/source/lux/control/concurrency/actor.lux
@@ -23,7 +23,8 @@
[syntax (#+ syntax:)
["cs" common
["csr" reader]
- ["csw" writer]]]]
+ ["csw" writer]
+ ["|.|" export]]]]
["." meta (#+ with-gensyms monad)
["." annotation]]
[type (#+ :share)
@@ -300,7 +301,7 @@
(message: #export (read! state self Nat)
(promise.resolved (#try.Success [state state])))))]
(syntax: #export (actor:
- {export csr.export}
+ {export |export|.parser}
{[name vars] actor-decl^}
{annotations (<>.default cs.empty-annotations csr.annotations)}
state-type
@@ -313,10 +314,10 @@
[g!type (meta.gensym (format name "-abstract-type"))
#let [g!actor (code.local-identifier name)
g!vars (list\map code.local-identifier vars)]]
- (wrap (list (` ((~! abstract:) (~+ (csw.export export)) ((~ g!type) (~+ g!vars))
+ (wrap (list (` ((~! abstract:) (~+ (|export|.write export)) ((~ g!type) (~+ g!vars))
(~ state-type)
- (def: (~+ (csw.export export)) (~ g!actor)
+ (def: (~+ (|export|.write export)) (~ g!actor)
(All [(~+ g!vars)]
(..Behavior (~ state-type) ((~ g!type) (~+ g!vars))))
{#..on-init (|>> ((~! abstract.:abstraction) (~ g!type)))
@@ -360,7 +361,7 @@
(<>.and <c>.identifier (\ <>.monad wrap (list)))))
(syntax: #export (message:
- {export csr.export}
+ {export |export|.parser}
{signature signature^}
{annotations (<>.default cs.empty-annotations csr.annotations)}
body)
@@ -381,7 +382,7 @@
g!inputsT (|> (get@ #inputs signature) (list\map product.right))
g!state (|> signature (get@ #state) code.local-identifier)
g!self (|> signature (get@ #self) code.local-identifier)]]
- (wrap (list (` (def: (~+ (csw.export export)) ((~ g!message) (~+ g!inputsC))
+ (wrap (list (` (def: (~+ (|export|.write export)) ((~ g!message) (~+ g!inputsC))
(~ (csw.annotations annotations))
(All [(~+ g!all-vars)]
(-> (~+ g!inputsT)
diff --git a/stdlib/source/lux/control/exception.lux b/stdlib/source/lux/control/exception.lux
index 4257818cf..71bb9ca90 100644
--- a/stdlib/source/lux/control/exception.lux
+++ b/stdlib/source/lux/control/exception.lux
@@ -19,7 +19,8 @@
[syntax (#+ syntax:)
["sc" common
["scr" reader]
- ["scw" writer]]]]]
+ ["scw" writer]
+ ["|.|" export]]]]]
[//
["//" try (#+ Try)]])
@@ -83,7 +84,7 @@
(#//.Success [])
(..throw exception message)))
-(syntax: #export (exception: {export scr.export}
+(syntax: #export (exception: {export |export|.parser}
{t-vars (p.default (list) (s.tuple scr.type-variables))}
{[name inputs] (p.either (p.and s.local-identifier (wrap (list)))
(s.form (p.and s.local-identifier (p.some scr.typed-input))))}
@@ -102,7 +103,7 @@
[current-module meta.current-module-name
#let [descriptor ($_ text\compose "{" current-module "." name "}" text.new-line)
g!self (code.local-identifier name)]]
- (wrap (list (` (def: (~+ (scw.export export))
+ (wrap (list (` (def: (~+ (|export|.write export))
(~ g!self)
(All [(~+ (scw.type-variables t-vars))]
(..Exception [(~+ (list\map (get@ #sc.input-type) inputs))]))
diff --git a/stdlib/source/lux/control/parser/type.lux b/stdlib/source/lux/control/parser/type.lux
index 3ac8f657d..8ed5004fe 100644
--- a/stdlib/source/lux/control/parser/type.lux
+++ b/stdlib/source/lux/control/parser/type.lux
@@ -174,7 +174,7 @@
(do {! //.monad}
[headT any
funcI (\ ! map dictionary.size ..env)
- [num-args non-poly] (local (list headT) polymorphic')
+ [num-args non-poly] (local (list headT) ..polymorphic')
env ..env
#let [funcL (label funcI)
[all-varsL env'] (loop [current-arg 0
@@ -200,11 +200,11 @@
(dictionary.put partial-varI [(#.Parameter partial-varI) partial-varL]))
(#.Cons partial-varL all-varsL))))
[all-varsL env']))]]
- (|> (do !
- [output poly]
- (wrap [funcL all-varsL output]))
+ (<| (with-env env')
(local (list non-poly))
- (with-env env'))))
+ (do !
+ [output poly]
+ (wrap [funcL all-varsL output])))))
(def: #export (function in-poly out-poly)
(All [i o] (-> (Parser i) (Parser o) (Parser [i o])))
@@ -299,12 +299,17 @@
_
(//.fail (exception.construct ..not-named inputT)))))
+(template: (|nothing|)
+ (#.Named ["lux" "Nothing"]
+ (#.UnivQ #.Nil
+ (#.Parameter 1))))
+
(def: #export (recursive poly)
(All [a] (-> (Parser a) (Parser [Code a])))
(do {! //.monad}
[headT any]
(case (type.un-name headT)
- (#.Apply (#.Named ["lux" "Nothing"] _) (#.UnivQ _ headT'))
+ (^ (#.Apply (|nothing|) (#.UnivQ _ headT')))
(do !
[[recT _ output] (|> poly
(with-extension .Nothing)
@@ -321,7 +326,7 @@
[env ..env
headT any]
(case (type.un-name headT)
- (^multi (#.Apply (#.Named ["lux" "Nothing"] _) (#.Parameter funcT-idx))
+ (^multi (^ (#.Apply (|nothing|) (#.Parameter funcT-idx)))
(n.= 0 (adjusted-idx env funcT-idx))
[(dictionary.get 0 env) (#.Some [self-type self-call])])
(wrap self-call)
@@ -333,7 +338,7 @@
(Parser Code)
(do {! //.monad}
[env ..env
- [funcT argsT] (apply (//.and any (//.many any)))
+ [funcT argsT] (..apply (//.and any (//.many any)))
_ (local (list funcT) (..parameter! 0))
allC (let [allT (list& funcT argsT)]
(|> allT
diff --git a/stdlib/source/lux/control/security/capability.lux b/stdlib/source/lux/control/security/capability.lux
index a1272b018..2a4e5427b 100644
--- a/stdlib/source/lux/control/security/capability.lux
+++ b/stdlib/source/lux/control/security/capability.lux
@@ -21,7 +21,8 @@
[syntax (#+ syntax:)
[common
["." reader]
- ["." writer]]]]])
+ ["." writer]
+ ["|.|" export]]]]])
(abstract: #export (Capability brand input output)
(-> input output)
@@ -42,7 +43,7 @@
output))
((:representation capability) input))
- (syntax: #export (capability: {export reader.export}
+ (syntax: #export (capability: {export |export|.parser}
{declaration reader.declaration}
{annotations (<>.maybe reader.annotations)}
{[forge input output] (<c>.form ($_ <>.and <c>.local-identifier <c>.any <c>.any))})
@@ -52,7 +53,7 @@
g!brand (\ ! map (|>> %.code code.text)
(meta.gensym (format (%.name [this-module name]))))
#let [capability (` (..Capability (.primitive (~ g!brand)) (~ input) (~ output)))]]
- (wrap (list (` (type: (~+ (writer.export export))
+ (wrap (list (` (type: (~+ (|export|.write export))
(~ (writer.declaration declaration))
(~ capability)))
(` (def: (~ (code.local-identifier forge))