aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library')
-rw-r--r--stdlib/source/library/lux.lux50
-rw-r--r--stdlib/source/library/lux/abstract/apply.lux16
-rw-r--r--stdlib/source/library/lux/abstract/interval.lux18
-rw-r--r--stdlib/source/library/lux/control/concatenative.lux64
-rw-r--r--stdlib/source/library/lux/control/concurrency/actor.lux108
-rw-r--r--stdlib/source/library/lux/control/concurrency/async.lux38
-rw-r--r--stdlib/source/library/lux/control/concurrency/semaphore.lux76
-rw-r--r--stdlib/source/library/lux/control/concurrency/stm.lux42
-rw-r--r--stdlib/source/library/lux/control/concurrency/thread.lux6
-rw-r--r--stdlib/source/library/lux/control/exception.lux62
-rw-r--r--stdlib/source/library/lux/control/function/mutual.lux82
-rw-r--r--stdlib/source/library/lux/control/maybe.lux2
-rw-r--r--stdlib/source/library/lux/control/parser/binary.lux58
-rw-r--r--stdlib/source/library/lux/control/parser/text.lux50
-rw-r--r--stdlib/source/library/lux/control/reader.lux19
-rw-r--r--stdlib/source/library/lux/control/region.lux34
-rw-r--r--stdlib/source/library/lux/control/try.lux21
-rw-r--r--stdlib/source/library/lux/control/writer.lux18
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary.lux18
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary/ordered.lux450
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary/plist.lux2
-rw-r--r--stdlib/source/library/lux/data/collection/list.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/queue.lux44
-rw-r--r--stdlib/source/library/lux/data/collection/sequence.lux100
-rw-r--r--stdlib/source/library/lux/data/collection/set.lux32
-rw-r--r--stdlib/source/library/lux/data/collection/set/multi.lux36
-rw-r--r--stdlib/source/library/lux/data/collection/set/ordered.lux28
-rw-r--r--stdlib/source/library/lux/data/collection/tree.lux48
-rw-r--r--stdlib/source/library/lux/data/collection/tree/finger.lux34
-rw-r--r--stdlib/source/library/lux/data/collection/tree/zipper.lux142
-rw-r--r--stdlib/source/library/lux/data/format/css.lux20
-rw-r--r--stdlib/source/library/lux/data/format/css/value.lux2
-rw-r--r--stdlib/source/library/lux/data/format/json.lux2
-rw-r--r--stdlib/source/library/lux/data/format/tar.lux42
-rw-r--r--stdlib/source/library/lux/data/store.lux18
-rw-r--r--stdlib/source/library/lux/data/text/unicode/block.lux34
-rw-r--r--stdlib/source/library/lux/data/trace.lux24
-rw-r--r--stdlib/source/library/lux/documentation.lux104
-rw-r--r--stdlib/source/library/lux/ffi.jvm.lux34
-rw-r--r--stdlib/source/library/lux/ffi.lux116
-rw-r--r--stdlib/source/library/lux/ffi.old.lux32
-rw-r--r--stdlib/source/library/lux/locale/language.lux24
-rw-r--r--stdlib/source/library/lux/locale/territory.lux26
-rw-r--r--stdlib/source/library/lux/macro/local.lux48
-rw-r--r--stdlib/source/library/lux/macro/syntax/declaration.lux32
-rw-r--r--stdlib/source/library/lux/macro/syntax/definition.lux54
-rw-r--r--stdlib/source/library/lux/macro/syntax/input.lux30
-rw-r--r--stdlib/source/library/lux/macro/template.lux56
-rw-r--r--stdlib/source/library/lux/math/number/complex.lux110
-rw-r--r--stdlib/source/library/lux/math/number/ratio.lux82
-rw-r--r--stdlib/source/library/lux/meta.lux72
-rw-r--r--stdlib/source/library/lux/meta/location.lux14
-rw-r--r--stdlib/source/library/lux/target/js.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/attribute/code.lux58
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode.lux52
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/environment.lux52
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux44
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux44
-rw-r--r--stdlib/source/library/lux/target/jvm/class.lux4
-rw-r--r--stdlib/source/library/lux/target/jvm/field.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/method.lux4
-rw-r--r--stdlib/source/library/lux/target/lua.lux2
-rw-r--r--stdlib/source/library/lux/target/php.lux58
-rw-r--r--stdlib/source/library/lux/target/python.lux2
-rw-r--r--stdlib/source/library/lux/target/ruby.lux6
-rw-r--r--stdlib/source/library/lux/target/scheme.lux44
-rw-r--r--stdlib/source/library/lux/test.lux40
-rw-r--r--stdlib/source/library/lux/time.lux54
-rw-r--r--stdlib/source/library/lux/time/date.lux90
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/init.lux22
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/platform.lux146
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux24
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux60
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux64
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux16
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/directive.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/generation.lux98
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux12
-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/directive/jvm.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux48
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux66
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux64
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux46
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux14
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/member.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/side.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive.lux48
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux32
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/cache.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/cache/artifact.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/cache/dependency/module.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux14
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/io/archive.lux26
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux88
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager/script.lux2
-rw-r--r--stdlib/source/library/lux/tool/interpreter.lux104
-rw-r--r--stdlib/source/library/lux/type.lux12
-rw-r--r--stdlib/source/library/lux/type/abstract.lux60
-rw-r--r--stdlib/source/library/lux/type/check.lux50
-rw-r--r--stdlib/source/library/lux/type/implicit.lux56
-rw-r--r--stdlib/source/library/lux/type/quotient.lux24
-rw-r--r--stdlib/source/library/lux/type/refinement.lux24
-rw-r--r--stdlib/source/library/lux/world/db/jdbc.lux60
-rw-r--r--stdlib/source/library/lux/world/file.lux18
-rw-r--r--stdlib/source/library/lux/world/file/watch.lux66
-rw-r--r--stdlib/source/library/lux/world/net/http/client.lux68
-rw-r--r--stdlib/source/library/lux/world/net/http/request.lux78
-rw-r--r--stdlib/source/library/lux/world/net/http/response.lux46
-rw-r--r--stdlib/source/library/lux/world/net/http/route.lux44
-rw-r--r--stdlib/source/library/lux/world/program.lux3
128 files changed, 2483 insertions, 2480 deletions
diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux
index 657bc4faa..09f0a9e4c 100644
--- a/stdlib/source/library/lux.lux
+++ b/stdlib/source/library/lux.lux
@@ -3965,7 +3965,7 @@
(-> (List a) (List [Nat a])))
(enumeration' 0 xs))
-(macro: .public (value@ tokens)
+(macro: .public (the tokens)
(case tokens
(^ (list [_ {#Symbol slot'}] record))
(do meta_monad
@@ -3988,12 +3988,12 @@
(meta#in (list (` ({(~ pattern) (~ g!output)} (~ record))))))
_
- (failure "value@ can only use records.")))
+ (failure "the can only use records.")))
(^ (list [_ {#Tuple slots}] record))
(meta#in (list (list#mix (: (-> Code Code Code)
(function (_ slot inner)
- (` (..value@ (~ slot) (~ inner)))))
+ (` (..the (~ slot) (~ inner)))))
record
slots)))
@@ -4001,10 +4001,10 @@
(do meta_monad
[g!_ (..generated_symbol "_")
g!record (..generated_symbol "record")]
- (in (list (` (function ((~ g!_) (~ g!record)) (..value@ (~ selector) (~ g!record)))))))
+ (in (list (` (function ((~ g!_) (~ g!record)) (..the (~ selector) (~ g!record)))))))
_
- (failure "Wrong syntax for value@")))
+ (failure "Wrong syntax for the")))
(def: (open_declaration alias tags my_tag_index [module short] source type)
(-> Text (List Symbol) Nat Symbol Code Type (Meta (List Code)))
@@ -4200,7 +4200,7 @@
_
(failure "Wrong syntax for #")))
-(macro: .public (with@ tokens)
+(macro: .public (has tokens)
(case tokens
(^ (list [_ {#Symbol slot'}] value record))
(do meta_monad
@@ -4236,12 +4236,12 @@
(meta#in (list (` ({(~ pattern) (~ output)} (~ record)))))))
_
- (failure "with@ can only use records.")))
+ (failure "has can only use records.")))
(^ (list [_ {#Tuple slots}] value record))
(case slots
{#End}
- (failure "Wrong syntax for with@")
+ (failure "Wrong syntax for has")
_
(do meta_monad
@@ -4252,12 +4252,12 @@
.let [pairs (zipped/2 slots bindings)
update_expr (list#mix (: (-> [Code Code] Code Code)
(function (_ [s b] v)
- (` (..with@ (~ s) (~ v) (~ b)))))
+ (` (..has (~ s) (~ v) (~ b)))))
value
(list#reversed pairs))
[_ accesses'] (list#mix (: (-> [Code Code] [Code (List (List Code))] [Code (List (List Code))])
(function (_ [new_slot new_binding] [old_record accesses'])
- [(` (value@ (~ new_slot) (~ new_binding)))
+ [(` (the (~ new_slot) (~ new_binding)))
{#Item (list new_binding old_record) accesses'}]))
[record (: (List (List Code)) {#End})]
pairs)
@@ -4270,7 +4270,7 @@
[g!_ (..generated_symbol "_")
g!record (..generated_symbol "record")]
(in (list (` (function ((~ g!_) (~ g!record))
- (..with@ (~ selector) (~ value) (~ g!record)))))))
+ (..has (~ selector) (~ value) (~ g!record)))))))
(^ (list selector))
(do meta_monad
@@ -4278,12 +4278,12 @@
g!value (..generated_symbol "value")
g!record (..generated_symbol "record")]
(in (list (` (function ((~ g!_) (~ g!value) (~ g!record))
- (..with@ (~ selector) (~ g!value) (~ g!record)))))))
+ (..has (~ selector) (~ g!value) (~ g!record)))))))
_
- (failure "Wrong syntax for with@")))
+ (failure "Wrong syntax for has")))
-(macro: .public (revised@ tokens)
+(macro: .public (revised tokens)
(case tokens
(^ (list [_ {#Symbol slot'}] fun record))
(do meta_monad
@@ -4319,27 +4319,27 @@
(meta#in (list (` ({(~ pattern) (~ output)} (~ record)))))))
_
- (failure "revised@ can only use records.")))
+ (failure "revised can only use records.")))
(^ (list [_ {#Tuple slots}] fun record))
(case slots
{#End}
- (failure "Wrong syntax for revised@")
+ (failure "Wrong syntax for revised")
_
(do meta_monad
[g!record (..generated_symbol "record")
g!temp (..generated_symbol "temp")]
(in (list (` (let [(~ g!record) (~ record)
- (~ g!temp) (value@ [(~+ slots)] (~ g!record))]
- (with@ [(~+ slots)] ((~ fun) (~ g!temp)) (~ g!record))))))))
+ (~ g!temp) (the [(~+ slots)] (~ g!record))]
+ (has [(~+ slots)] ((~ fun) (~ g!temp)) (~ g!record))))))))
(^ (list selector fun))
(do meta_monad
[g!_ (..generated_symbol "_")
g!record (..generated_symbol "record")]
(in (list (` (function ((~ g!_) (~ g!record))
- (..revised@ (~ selector) (~ fun) (~ g!record)))))))
+ (..revised (~ selector) (~ fun) (~ g!record)))))))
(^ (list selector))
(do meta_monad
@@ -4347,10 +4347,10 @@
g!fun (..generated_symbol "fun")
g!record (..generated_symbol "record")]
(in (list (` (function ((~ g!_) (~ g!fun) (~ g!record))
- (..revised@ (~ selector) (~ g!fun) (~ g!record)))))))
+ (..revised (~ selector) (~ g!fun) (~ g!record)))))))
_
- (failure "Wrong syntax for revised@")))
+ (failure "Wrong syntax for revised")))
(macro: .public (^template tokens)
(case tokens
@@ -4704,7 +4704,7 @@
(-> a a Bit))
("lux is" reference sample))
-(macro: .public (^@ tokens)
+(macro: .public (^let tokens)
(case tokens
(^ (list& [_meta {#Form (list [_ {#Symbol ["" name]}] pattern)}] body branches))
(let [g!whole (local_symbol$ name)]
@@ -4713,7 +4713,7 @@
branches)))
_
- (failure (..wrong_syntax_error (symbol ..^@)))))
+ (failure (..wrong_syntax_error (symbol ..^let)))))
(macro: .public (^|> tokens)
(case tokens
@@ -4740,7 +4740,7 @@
(def: location
(Meta Location)
(function (_ compiler)
- {#Right [compiler (value@ #location compiler)]}))
+ {#Right [compiler (the #location compiler)]}))
(macro: .public (undefined tokens)
(case tokens
@@ -4835,7 +4835,7 @@
(def: target
(Meta Text)
(function (_ compiler)
- {#Right [compiler (value@ [#info #target] compiler)]}))
+ {#Right [compiler (the [#info #target] compiler)]}))
(def: (platform_name choice)
(-> Code (Meta Text))
diff --git a/stdlib/source/library/lux/abstract/apply.lux b/stdlib/source/library/lux/abstract/apply.lux
index 8b3762485..a7cc3d764 100644
--- a/stdlib/source/library/lux/abstract/apply.lux
+++ b/stdlib/source/library/lux/abstract/apply.lux
@@ -1,10 +1,10 @@
(.using
- [library
- [lux "*"
- ["@" target]]]
- [//
- [monad {"+" Monad}]
- ["[0]" functor {"+" Functor}]])
+ [library
+ [lux "*"
+ ["@" target]]]
+ [//
+ [monad {"+" Monad do}]
+ ["[0]" functor {"+" Functor}]])
(type: .public (Apply f)
(Interface
@@ -21,8 +21,8 @@
(Apply (All (_ a) (F (G a))))))
(def: &functor
- (functor.composite (value@ &functor f_apply)
- (value@ &functor g_apply)))
+ (functor.composite (the &functor f_apply)
+ (the &functor g_apply)))
(def: (on fgx fgf)
... TODO: Switch from this version to the one below (in comments) ASAP.
diff --git a/stdlib/source/library/lux/abstract/interval.lux b/stdlib/source/library/lux/abstract/interval.lux
index 829c3ca5b..d16e140de 100644
--- a/stdlib/source/library/lux/abstract/interval.lux
+++ b/stdlib/source/library/lux/abstract/interval.lux
@@ -1,11 +1,11 @@
... https://en.wikipedia.org/wiki/Interval_(mathematics)
(.using
- [library
- [lux "*"]]
- [//
- [equivalence {"+" Equivalence}]
- ["[0]" order]
- [enum {"+" Enum}]])
+ [library
+ [lux "*"]]
+ [//
+ [equivalence {"+" Equivalence}]
+ ["[0]" order]
+ [enum {"+" Enum}]])
(type: .public (Interval a)
(Interface
@@ -76,21 +76,21 @@
(implementation: .public (union left right)
(All (_ a) (-> (Interval a) (Interval a) (Interval a)))
- (def: &enum (value@ &enum right))
+ (def: &enum (the &enum right))
(def: bottom (order.min (# right &order) (# left bottom) (# right bottom)))
(def: top (order.max (# right &order) (# left top) (# right top))))
(implementation: .public (intersection left right)
(All (_ a) (-> (Interval a) (Interval a) (Interval a)))
- (def: &enum (value@ &enum right))
+ (def: &enum (the &enum right))
(def: bottom (order.max (# right &order) (# left bottom) (# right bottom)))
(def: top (order.min (# right &order) (# left top) (# right top))))
(implementation: .public (complement interval)
(All (_ a) (-> (Interval a) (Interval a)))
- (def: &enum (value@ &enum interval))
+ (def: &enum (the &enum interval))
(def: bottom (# interval succ (# interval top)))
(def: top (# interval pred (# interval bottom))))
diff --git a/stdlib/source/library/lux/control/concatenative.lux b/stdlib/source/library/lux/control/concatenative.lux
index 85d5e6ee2..84383bba4 100644
--- a/stdlib/source/library/lux/control/concatenative.lux
+++ b/stdlib/source/library/lux/control/concatenative.lux
@@ -1,30 +1,30 @@
(.using
- [library
- [lux {"-" Alias if loop}
- ["[0]" meta]
- [abstract
- ["[0]" monad]]
- [control
- ["[0]" maybe ("[1]#[0]" monad)]]
- [data
- ["[0]" text
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" mix functor)]]]
- ["[0]" macro {"+" with_symbols}
- ["[0]" code]
- ["[0]" template]
- [syntax {"+" syntax:}
- ["|[0]|" export]]]
- [math
- [number
- ["n" nat]
- ["i" int]
- ["r" rev]
- ["f" frac]]]]]
- [//
- ["<>" parser ("[1]#[0]" monad)
- ["<[0]>" code {"+" Parser}]]])
+ [library
+ [lux {"-" Alias if loop}
+ ["[0]" meta]
+ [abstract
+ ["[0]" monad]]
+ [control
+ ["[0]" maybe ("[1]#[0]" monad)]]
+ [data
+ ["[0]" text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" mix functor)]]]
+ ["[0]" macro {"+" with_symbols}
+ ["[0]" code]
+ ["[0]" template]
+ [syntax {"+" syntax:}
+ ["|[0]|" export]]]
+ [math
+ [number
+ ["n" nat]
+ ["i" int]
+ ["r" rev]
+ ["f" frac]]]]]
+ [//
+ ["<>" parser ("[1]#[0]" monad)
+ ["<[0]>" code {"+" Parser}]]])
(type: Alias
[Text Code])
@@ -85,20 +85,20 @@
(code.replaced (code.local_symbol from) to pre))
aliased
aliases))]
- (case [(value@ #bottom inputs)
- (value@ #bottom outputs)]
+ (case [(the #bottom inputs)
+ (the #bottom outputs)]
[{.#Some bottomI} {.#Some bottomO}]
(monad.do meta.monad
- [inputC (singleton (macro.full_expansion (stack_mix (value@ #top inputs) bottomI)))
- outputC (singleton (macro.full_expansion (stack_mix (value@ #top outputs) bottomO)))]
+ [inputC (singleton (macro.full_expansion (stack_mix (the #top inputs) bottomI)))
+ outputC (singleton (macro.full_expansion (stack_mix (the #top outputs) bottomO)))]
(in (list (` (-> (~ (de_alias inputC))
(~ (de_alias outputC)))))))
[?bottomI ?bottomO]
(with_symbols [g!stack]
(monad.do meta.monad
- [inputC (singleton (macro.full_expansion (stack_mix (value@ #top inputs) (maybe.else g!stack ?bottomI))))
- outputC (singleton (macro.full_expansion (stack_mix (value@ #top outputs) (maybe.else g!stack ?bottomO))))]
+ [inputC (singleton (macro.full_expansion (stack_mix (the #top inputs) (maybe.else g!stack ?bottomI))))
+ outputC (singleton (macro.full_expansion (stack_mix (the #top outputs) (maybe.else g!stack ?bottomO))))]
(with_symbols [g!_]
(in (list (` (All ((~ g!_) (~ g!stack))
(-> (~ (de_alias inputC))
diff --git a/stdlib/source/library/lux/control/concurrency/actor.lux b/stdlib/source/library/lux/control/concurrency/actor.lux
index ded23e008..d534c198c 100644
--- a/stdlib/source/library/lux/control/concurrency/actor.lux
+++ b/stdlib/source/library/lux/control/concurrency/actor.lux
@@ -1,39 +1,39 @@
(.using
- [library
- [lux "*"
- ["[0]" debug]
- [abstract
- monad]
- [control
- [pipe {"+" case>}]
- ["[0]" function]
- ["[0]" try {"+" Try}]
- ["[0]" exception {"+" exception:}]
- ["[0]" io {"+" IO io}]
- ["<>" parser ("[1]#[0]" monad)
- ["<[0]>" code {"+" Parser}]]]
- [data
- ["[0]" bit]
- ["[0]" product]
- [text
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" monoid monad)]]]
- ["[0]" macro {"+" with_symbols}
- ["[0]" code]
- [syntax {"+" syntax:}
- ["|[0]|" input]
- ["|[0]|" export]]]
- [math
- [number
- ["n" nat]]]
- ["[0]" meta {"+" monad}]
- [type {"+" :sharing}
- ["[0]" abstract {"+" abstract: :representation :abstraction}]]]]
- [//
- ["[0]" atom {"+" Atom atom}]
- ["[0]" async {"+" Async Resolver} ("[1]#[0]" monad)]
- ["[0]" frp {"+" Channel}]])
+ [library
+ [lux "*"
+ ["[0]" debug]
+ [abstract
+ monad]
+ [control
+ [pipe {"+" case>}]
+ ["[0]" function]
+ ["[0]" try {"+" Try}]
+ ["[0]" exception {"+" exception:}]
+ ["[0]" io {"+" IO io}]
+ ["<>" parser ("[1]#[0]" monad)
+ ["<[0]>" code {"+" Parser}]]]
+ [data
+ ["[0]" bit]
+ ["[0]" product]
+ [text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" monoid monad)]]]
+ ["[0]" macro {"+" with_symbols}
+ ["[0]" code]
+ [syntax {"+" syntax:}
+ ["|[0]|" input]
+ ["|[0]|" export]]]
+ [math
+ [number
+ ["n" nat]]]
+ ["[0]" meta {"+" monad}]
+ [type {"+" :sharing}
+ ["[0]" abstract {"+" abstract: :representation :abstraction}]]]]
+ [//
+ ["[0]" atom {"+" Atom atom}]
+ ["[0]" async {"+" Async Resolver} ("[1]#[0]" monad)]
+ ["[0]" frp {"+" Channel}]])
(exception: .public poisoned)
(exception: .public dead)
@@ -89,13 +89,13 @@
(:abstraction [#obituary (async.async [])
#mailbox (atom (async.async []))]))
process (loop [state (on_init init)
- [|mailbox| _] (io.run! (atom.read! (value@ #mailbox (:representation self))))]
+ [|mailbox| _] (io.run! (atom.read! (the #mailbox (:representation self))))]
(do [! async.monad]
[[head tail] |mailbox|
?state' (on_mail head state self)]
(case ?state'
{try.#Failure error}
- (let [[_ resolve] (value@ #obituary (:representation self))]
+ (let [[_ resolve] (the #obituary (:representation self))]
(exec (io.run!
(do io.monad
[pending (..pending tail)]
@@ -108,7 +108,7 @@
(def: .public (alive? actor)
(All (_ s) (-> (Actor s) (IO Bit)))
- (let [[obituary _] (value@ #obituary (:representation actor))]
+ (let [[obituary _] (the #obituary (:representation actor))]
(|> obituary
async.value
(# io.functor each
@@ -120,13 +120,13 @@
(def: .public (obituary' actor)
(All (_ s) (-> (Actor s) (IO (Maybe (Obituary s)))))
- (let [[obituary _] (value@ #obituary (:representation actor))]
+ (let [[obituary _] (the #obituary (:representation actor))]
(async.value obituary)))
(def: .public obituary
(All (_ s) (-> (Actor s) (Async (Obituary s))))
(|>> :representation
- (value@ #obituary)
+ (the #obituary)
product.left))
(def: .public (mail! mail actor)
@@ -136,7 +136,7 @@
(if alive?
(let [entry [mail (async.async [])]]
(do !
- [|mailbox|&resolve (atom.read! (value@ #mailbox (:representation actor)))]
+ [|mailbox|&resolve (atom.read! (the #mailbox (:representation actor)))]
(loop [[|mailbox| resolve] |mailbox|&resolve]
(do !
[|mailbox| (async.value |mailbox|)]
@@ -146,7 +146,7 @@
[resolved? (resolve entry)]
(if resolved?
(do !
- [_ (atom.write! (product.right entry) (value@ #mailbox (:representation actor)))]
+ [_ (atom.write! (product.right entry) (the #mailbox (:representation actor)))]
(in {try.#Success []}))
(again |mailbox|&resolve)))
@@ -319,26 +319,26 @@
(with_symbols [g!_ g!return]
(do meta.monad
[actor_scope abstract.current
- .let [g!type (code.local_symbol (value@ abstract.#name actor_scope))
- g!message (code.local_symbol (value@ #name signature))
- g!actor_vars (value@ abstract.#type_vars actor_scope)
- g!all_vars (|> signature (value@ #vars) (list#each code.local_symbol) (list#composite g!actor_vars))
- g!inputsC (|> signature (value@ #inputs) (list#each product.left))
- g!inputsT (|> signature (value@ #inputs) (list#each product.right))
- g!state (|> signature (value@ #state) code.local_symbol)
- g!self (|> signature (value@ #self) code.local_symbol)]]
+ .let [g!type (code.local_symbol (the abstract.#name actor_scope))
+ g!message (code.local_symbol (the #name signature))
+ g!actor_vars (the abstract.#type_vars actor_scope)
+ g!all_vars (|> signature (the #vars) (list#each code.local_symbol) (list#composite g!actor_vars))
+ g!inputsC (|> signature (the #inputs) (list#each product.left))
+ g!inputsT (|> signature (the #inputs) (list#each product.right))
+ g!state (|> signature (the #state) code.local_symbol)
+ g!self (|> signature (the #self) code.local_symbol)]]
(in (list (` (def: (~ export_policy) ((~ g!message) (~+ g!inputsC))
(All ((~ g!_) (~+ g!all_vars))
(-> (~+ g!inputsT)
- (..Message (~ (value@ abstract.#abstraction actor_scope))
+ (..Message (~ (the abstract.#abstraction actor_scope))
(~ output_type))))
(function ((~ g!_) (~ g!state) (~ g!self))
- (let [(~ g!state) (:as (~ (value@ abstract.#representation actor_scope))
+ (let [(~ g!state) (:as (~ (the abstract.#representation actor_scope))
(~ g!state))]
(|> (~ body)
- (: ((~! async.Async) ((~! try.Try) [(~ (value@ abstract.#representation actor_scope))
+ (: ((~! async.Async) ((~! try.Try) [(~ (the abstract.#representation actor_scope))
(~ output_type)])))
- (:as ((~! async.Async) ((~! try.Try) [(~ (value@ abstract.#abstraction actor_scope))
+ (:as ((~! async.Async) ((~! try.Try) [(~ (the abstract.#abstraction actor_scope))
(~ output_type)]))))))))
)))))
diff --git a/stdlib/source/library/lux/control/concurrency/async.lux b/stdlib/source/library/lux/control/concurrency/async.lux
index e19682691..b131ddd1e 100644
--- a/stdlib/source/library/lux/control/concurrency/async.lux
+++ b/stdlib/source/library/lux/control/concurrency/async.lux
@@ -1,21 +1,21 @@
(.using
- [library
- [lux {"-" and or}
- [abstract
- [functor {"+" Functor}]
- [apply {"+" Apply}]
- ["[0]" monad {"+" Monad do}]]
- [control
- [pipe {"+" case>}]
- ["[0]" function]
- ["[0]" io {"+" IO io}]]
- [data
- ["[0]" product]]
- [type {"+" :sharing}
- abstract]]]
- [//
- ["[0]" thread]
- ["[0]" atom {"+" Atom atom}]])
+ [library
+ [lux {"-" and or}
+ [abstract
+ [functor {"+" Functor}]
+ [apply {"+" Apply}]
+ ["[0]" monad {"+" Monad do}]]
+ [control
+ [pipe {"+" case>}]
+ ["[0]" function]
+ ["[0]" io {"+" IO io}]]
+ [data
+ ["[0]" product]]
+ [type {"+" :sharing}
+ abstract]]]
+ [//
+ ["[0]" thread]
+ ["[0]" atom {"+" Atom atom}]])
(abstract: .public (Async a)
(Atom [(Maybe a) (List (-> a (IO Any)))])
@@ -29,7 +29,7 @@
(function (resolve value)
(let [async (:representation async)]
(do [! io.monad]
- [(^@ old [_value _observers]) (atom.read! async)]
+ [(^let old [_value _observers]) (atom.read! async)]
(case _value
{.#Some _}
(in #0)
@@ -64,7 +64,7 @@
(All (_ a) (-> (-> a (IO Any)) (Async a) (IO Any)))
(do [! io.monad]
[.let [async (:representation async)]
- (^@ old [_value _observers]) (atom.read! async)]
+ (^let old [_value _observers]) (atom.read! async)]
(case _value
{.#Some value}
(f value)
diff --git a/stdlib/source/library/lux/control/concurrency/semaphore.lux b/stdlib/source/library/lux/control/concurrency/semaphore.lux
index 56ab29a03..58e664966 100644
--- a/stdlib/source/library/lux/control/concurrency/semaphore.lux
+++ b/stdlib/source/library/lux/control/concurrency/semaphore.lux
@@ -1,28 +1,28 @@
(.using
- [library
- [lux "*"
- [abstract
- [monad {"+" do}]]
- [control
- [pipe {"+" if>}]
- ["[0]" io {"+" IO}]
- ["[0]" try {"+" Try}]
- ["[0]" exception {"+" exception:}]]
- [data
- [text
- ["%" format {"+" format}]]
- [collection
- ["[0]" queue {"+" Queue}]]]
- [math
- [number
- ["n" nat]
- ["i" int]]]
- [type
- abstract
- ["[0]" refinement]]]]
- [//
- ["[0]" atom {"+" Atom}]
- ["[0]" async {"+" Async Resolver}]])
+ [library
+ [lux "*"
+ [abstract
+ [monad {"+" do}]]
+ [control
+ [pipe {"+" if>}]
+ ["[0]" io {"+" IO}]
+ ["[0]" try {"+" Try}]
+ ["[0]" exception {"+" exception:}]]
+ [data
+ [text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" queue {"+" Queue}]]]
+ [math
+ [number
+ ["n" nat]
+ ["i" int]]]
+ [type
+ abstract
+ ["[0]" refinement]]]]
+ [//
+ ["[0]" atom {"+" Atom}]
+ ["[0]" async {"+" Async Resolver}]])
(type: State
(Record
@@ -51,12 +51,12 @@
(async.async []))]
(exec
(io.run!
- (with_expansions [<had_open_position?> (as_is (value@ #open_positions) (i.> -1))]
+ (with_expansions [<had_open_position?> (as_is (the #open_positions) (i.> -1))]
(do io.monad
- [[_ state'] (atom.update! (|>> (revised@ #open_positions --)
+ [[_ state'] (atom.update! (|>> (revised #open_positions --)
(if> [<had_open_position?>]
[]
- [(revised@ #waiting_list (queue.end sink))]))
+ [(revised #waiting_list (queue.end sink))]))
semaphore)]
(with_expansions [<go_ahead> (sink [])
<get_in_line> (in false)]
@@ -75,23 +75,23 @@
(async.future
(do [! io.monad]
[[pre post] (atom.update! (function (_ state)
- (if (i.= (.int (value@ #max_positions state))
- (value@ #open_positions state))
+ (if (i.= (.int (the #max_positions state))
+ (the #open_positions state))
state
(|> state
- (revised@ #open_positions ++)
- (revised@ #waiting_list queue.next))))
+ (revised #open_positions ++)
+ (revised #waiting_list queue.next))))
semaphore)]
(if (same? pre post)
- (in (exception.except ..semaphore_is_maxed_out [(value@ #max_positions pre)]))
+ (in (exception.except ..semaphore_is_maxed_out [(the #max_positions pre)]))
(do !
- [_ (case (queue.front (value@ #waiting_list pre))
+ [_ (case (queue.front (the #waiting_list pre))
{.#None}
(in true)
{.#Some sink}
(sink []))]
- (in {try.#Success (value@ #open_positions post)})))))))
+ (in {try.#Success (the #open_positions post)})))))))
)
(abstract: .public Mutex
@@ -151,13 +151,13 @@
[(def: (<phase> (^:representation barrier))
(-> Barrier (Async Any))
(do async.monad
- [.let [limit (refinement.value (value@ #limit barrier))
+ [.let [limit (refinement.value (the #limit barrier))
goal <goal>
- [_ count] (io.run! (atom.update! <update> (value@ #count barrier)))
+ [_ count] (io.run! (atom.update! <update> (the #count barrier)))
reached? (n.= goal count)]]
(if reached?
- (..un_block! (-- limit) (value@ <turnstile> barrier))
- (..wait! (value@ <turnstile> barrier)))))]
+ (..un_block! (-- limit) (the <turnstile> barrier))
+ (..wait! (the <turnstile> barrier)))))]
[start! ++ limit #start_turnstile]
[end! -- 0 #end_turnstile]
diff --git a/stdlib/source/library/lux/control/concurrency/stm.lux b/stdlib/source/library/lux/control/concurrency/stm.lux
index c4ebebad4..22ebc470e 100644
--- a/stdlib/source/library/lux/control/concurrency/stm.lux
+++ b/stdlib/source/library/lux/control/concurrency/stm.lux
@@ -1,24 +1,24 @@
(.using
- [library
- [lux "*"
- [abstract
- [functor {"+" Functor}]
- [apply {"+" Apply}]
- ["[0]" monad {"+" Monad do}]]
- [control
- ["[0]" io {"+" IO io}]
- ["[0]" maybe]
- ["[0]" try]]
- [data
- ["[0]" product]
- [collection
- ["[0]" list]]]
- [type
- abstract]]]
- [//
- ["[0]" atom {"+" Atom atom}]
- ["[0]" async {"+" Async Resolver}]
- ["[0]" frp {"+" Channel Sink}]])
+ [library
+ [lux "*"
+ [abstract
+ [functor {"+" Functor}]
+ [apply {"+" Apply}]
+ ["[0]" monad {"+" Monad do}]]
+ [control
+ ["[0]" io {"+" IO io}]
+ ["[0]" maybe]
+ ["[0]" try]]
+ [data
+ ["[0]" product]
+ [collection
+ ["[0]" list]]]
+ [type
+ abstract]]]
+ [//
+ ["[0]" atom {"+" Atom atom}]
+ ["[0]" async {"+" Async Resolver}]
+ ["[0]" frp {"+" Channel Sink}]])
(type: (Observer a)
(-> a (IO Any)))
@@ -46,7 +46,7 @@
(All (_ a) (-> a (Var a) (IO Any)))
(do [! io.monad]
[.let [var' (:representation var)]
- (^@ old [old_value observers]) (atom.read! var')
+ (^let old [old_value observers]) (atom.read! var')
succeeded? (atom.compare_and_swap! old [new_value observers] var')]
(if succeeded?
(do !
diff --git a/stdlib/source/library/lux/control/concurrency/thread.lux b/stdlib/source/library/lux/control/concurrency/thread.lux
index 0f5c30601..bfb4dc24f 100644
--- a/stdlib/source/library/lux/control/concurrency/thread.lux
+++ b/stdlib/source/library/lux/control/concurrency/thread.lux
@@ -178,14 +178,14 @@
(do !
[now (# ! each (|>> instant.millis .nat) instant.now)
.let [[ready pending] (list.partition (function (_ thread)
- (|> (value@ #creation thread)
- (n.+ (value@ #delay thread))
+ (|> (the #creation thread)
+ (n.+ (the #delay thread))
(n.<= now)))
threads)]
swapped? (atom.compare_and_swap! threads pending ..runner)]
(if swapped?
(do !
- [_ (monad.each ! (|>> (value@ #action) ..execute! io.io) ready)]
+ [_ (monad.each ! (|>> (the #action) ..execute! io.io) ready)]
(again []))
(panic! (exception.error ..cannot_continue_running_threads []))))
)))))))
diff --git a/stdlib/source/library/lux/control/exception.lux b/stdlib/source/library/lux/control/exception.lux
index 5e78a155e..942ebbfd8 100644
--- a/stdlib/source/library/lux/control/exception.lux
+++ b/stdlib/source/library/lux/control/exception.lux
@@ -1,30 +1,30 @@
(.using
- [library
- [lux "*"
- ["[0]" macro]
- ["[0]" meta]
- [abstract
- [monad {"+" do}]]
- [control
- ["[0]" maybe]
- ["<>" parser ("[1]#[0]" monad)
- ["<[0]>" code {"+" Parser}]]]
- [data
- ["[0]" product]
- ["[0]" text ("[1]#[0]" monoid)]
- [collection
- ["[0]" list ("[1]#[0]" functor mix)]]]
- [macro
- ["[0]" code]
- [syntax {"+" syntax:}
- ["|[0]|" input]
- ["[0]" type "_"
- ["|[1]_[0]|" variable]]]]
- [math
- [number
- ["n" nat ("[1]#[0]" decimal)]]]]]
- [//
- ["//" try {"+" Try}]])
+ [library
+ [lux "*"
+ ["[0]" macro]
+ ["[0]" meta]
+ [abstract
+ [monad {"+" do}]]
+ [control
+ ["[0]" maybe]
+ ["<>" parser ("[1]#[0]" monad)
+ ["<[0]>" code {"+" Parser}]]]
+ [data
+ ["[0]" product]
+ ["[0]" text ("[1]#[0]" monoid)]
+ [collection
+ ["[0]" list ("[1]#[0]" functor mix)]]]
+ [macro
+ ["[0]" code]
+ [syntax {"+" syntax:}
+ ["|[0]|" input]
+ ["[0]" type "_"
+ ["|[1]_[0]|" variable]]]]
+ [math
+ [number
+ ["n" nat ("[1]#[0]" decimal)]]]]]
+ [//
+ ["//" try {"+" Try}]])
(type: .public (Exception a)
(Record
@@ -33,7 +33,7 @@
(def: .public (match? exception error)
(All (_ e) (-> (Exception e) Text Bit))
- (text.starts_with? (value@ #label exception) error))
+ (text.starts_with? (the #label exception) error))
(def: .public (when exception then try)
(All (_ e a)
@@ -44,7 +44,7 @@
{//.#Success output}
{//.#Failure error}
- (let [reference (value@ #label exception)]
+ (let [reference (the #label exception)]
(if (text.starts_with? reference error)
{//.#Success (|> error
(text.clip_since (text.size reference))
@@ -64,7 +64,7 @@
(def: .public (error exception message)
(All (_ e) (-> (Exception e) e Text))
- ((value@ ..#constructor exception) message))
+ ((the ..#constructor exception) message))
(def: .public (except exception message)
(All (_ e a) (-> (Exception e) e (Try a)))
@@ -99,10 +99,10 @@
(in (list (` (def: (~ export_policy)
(~ g!self)
(All ((~ g!_) (~+ (list#each |type_variable|.format t_vars)))
- (..Exception [(~+ (list#each (value@ |input|.#type) inputs))]))
+ (..Exception [(~+ (list#each (the |input|.#type) inputs))]))
(let [(~ g!descriptor) (~ (code.text descriptor))]
[..#label (~ g!descriptor)
- ..#constructor (function ((~ g!self) [(~+ (list#each (value@ |input|.#binding) inputs))])
+ ..#constructor (function ((~ g!self) [(~+ (list#each (the |input|.#binding) inputs))])
((~! text#composite) (~ g!descriptor)
(~ (maybe.else (' "") body))))]))))))))
diff --git a/stdlib/source/library/lux/control/function/mutual.lux b/stdlib/source/library/lux/control/function/mutual.lux
index b59578d3a..102457383 100644
--- a/stdlib/source/library/lux/control/function/mutual.lux
+++ b/stdlib/source/library/lux/control/function/mutual.lux
@@ -1,28 +1,28 @@
(.using
- [library
- [lux {"-" Definition let def: macro}
- ["[0]" meta]
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- ["[0]" try {"+" Try}]
- ["[0]" exception {"+" exception:}]
- ["<>" parser ("[1]#[0]" monad)
- ["<[0]>" code {"+" Parser}]]]
- [data
- ["[0]" product]
- [text
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" functor)]
- [dictionary
- ["[0]" plist {"+" PList}]]]]
- ["[0]" macro
- ["[0]" local]
- ["[0]" code]
- [syntax {"+" syntax:}
- ["[0]" declaration {"+" Declaration}]]]]]
- ["[0]" //])
+ [library
+ [lux {"-" Definition let def: macro}
+ ["[0]" meta]
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ ["[0]" try {"+" Try}]
+ ["[0]" exception {"+" exception:}]
+ ["<>" parser ("[1]#[0]" monad)
+ ["<[0]>" code {"+" Parser}]]]
+ [data
+ ["[0]" product]
+ [text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor)]
+ [dictionary
+ ["[0]" plist {"+" PList}]]]]
+ ["[0]" macro
+ ["[0]" local]
+ ["[0]" code]
+ [syntax {"+" syntax:}
+ ["[0]" declaration {"+" Declaration}]]]]]
+ ["[0]" //])
(type: Mutual
(Record
@@ -42,8 +42,8 @@
(-> (List Code) Code [Code Mutual] Code)
(` (function ((~ g!name) (~ g!context))
(.let [[(~+ context)] (~ g!context)]
- (function (~ (declaration.format (value@ #declaration mutual)))
- (~ (value@ #body mutual)))))))
+ (function (~ (declaration.format (the #declaration mutual)))
+ (~ (the #body mutual)))))))
(.def: (macro g!context g!self)
(-> Code Code Macro)
@@ -59,10 +59,10 @@
(in (list body))
{.#Item mutual {.#End}}
- (.let [g!name (|> mutual (value@ [#declaration declaration.#name]) code.local_symbol)]
- (in (list (` (.let [(~ g!name) (: (~ (value@ #type mutual))
- (function (~ (declaration.format (value@ #declaration mutual)))
- (~ (value@ #body mutual))))]
+ (.let [g!name (|> mutual (the [#declaration declaration.#name]) code.local_symbol)]
+ (in (list (` (.let [(~ g!name) (: (~ (the #type mutual))
+ (function (~ (declaration.format (the #declaration mutual)))
+ (~ (the #body mutual))))]
(~ body))))))
_
@@ -75,12 +75,12 @@
(list.zipped/2 hidden_names
functions))
context_types (list#each (function (_ mutual)
- (` (-> (~ g!context) (~ (value@ #type mutual)))))
+ (` (-> (~ g!context) (~ (the #type mutual)))))
functions)
- user_names (list#each (|>> (value@ [#declaration declaration.#name]) code.local_symbol)
+ user_names (list#each (|>> (the [#declaration declaration.#name]) code.local_symbol)
functions)]
g!pop (local.push (list#each (function (_ [g!name mutual])
- [[here_name (value@ [#declaration declaration.#name] mutual)]
+ [[here_name (the [#declaration declaration.#name] mutual)]
(..macro g!context g!name)])
(list.zipped/2 hidden_names
functions)))]
@@ -125,19 +125,19 @@
functions)
.let [definitions (list#each (..mutual_definition hidden_names g!context)
(list.zipped/2 hidden_names
- (list#each (value@ #mutual) functions)))
+ (list#each (the #mutual) functions)))
context_types (list#each (function (_ mutual)
- (` (-> (~ g!context) (~ (value@ [#mutual #type] mutual)))))
+ (` (-> (~ g!context) (~ (the [#mutual #type] mutual)))))
functions)
- user_names (list#each (|>> (value@ [#mutual #declaration declaration.#name]) code.local_symbol)
+ user_names (list#each (|>> (the [#mutual #declaration declaration.#name]) code.local_symbol)
functions)]
g!pop (local.push (list#each (function (_ [g!name mutual])
- [[here_name (value@ [#mutual #declaration declaration.#name] mutual)]
+ [[here_name (the [#mutual #declaration declaration.#name] mutual)]
(..macro g!context g!name)])
(list.zipped/2 hidden_names
functions)))]
(in (list& (` (.def: (~ g!context)
- [(~+ (list#each (value@ [#mutual #type]) functions))]
+ [(~+ (list#each (the [#mutual #type]) functions))]
(.let [(~ g!context) (: (Rec (~ g!context)
[(~+ context_types)])
[(~+ definitions)])
@@ -147,11 +147,11 @@
user_names))])))
g!pop
(list#each (function (_ mutual)
- (.let [g!name (|> mutual (value@ [#mutual #declaration declaration.#name]) code.local_symbol)]
+ (.let [g!name (|> mutual (the [#mutual #declaration declaration.#name]) code.local_symbol)]
(` (.def:
- (~ (value@ #export_policy mutual))
+ (~ (the #export_policy mutual))
(~ g!name)
- (~ (value@ [#mutual #type] mutual))
+ (~ (the [#mutual #type] mutual))
(.let [[(~+ user_names)] (~ g!context)]
(~ g!name))))))
functions)))))))
diff --git a/stdlib/source/library/lux/control/maybe.lux b/stdlib/source/library/lux/control/maybe.lux
index af48067c5..386548905 100644
--- a/stdlib/source/library/lux/control/maybe.lux
+++ b/stdlib/source/library/lux/control/maybe.lux
@@ -103,7 +103,7 @@
(All (_ M) (-> (Monad M) (Monad (All (_ a) (M (Maybe a))))))
(def: &functor
- (functor.composite (value@ monad.&functor monad)
+ (functor.composite (the monad.&functor monad)
..functor))
(def: in
diff --git a/stdlib/source/library/lux/control/parser/binary.lux b/stdlib/source/library/lux/control/parser/binary.lux
index f2b2e7f5d..a3430e4d7 100644
--- a/stdlib/source/library/lux/control/parser/binary.lux
+++ b/stdlib/source/library/lux/control/parser/binary.lux
@@ -1,30 +1,30 @@
(.using
- [library
- [lux {"-" and or nat int rev list type symbol}
- [type {"+" :sharing}]
- [abstract
- [hash {"+" Hash}]
- [monad {"+" do}]]
- [control
- ["[0]" try {"+" Try}]
- ["[0]" exception {"+" exception:}]]
- [data
- ["/" binary {"+" Binary}]
- [text
- ["%" format {"+" format}]
- [encoding
- ["[0]" utf8]]]
- [collection
- ["[0]" list]
- ["[0]" sequence {"+" Sequence}]
- ["[0]" set {"+" Set}]]]
- [macro
- ["[0]" template]]
- [math
- [number
- ["n" nat]
- ["[0]" frac]]]]]
- ["[0]" // ("[1]#[0]" monad)])
+ [library
+ [lux {"-" and or nat int rev list type symbol}
+ [type {"+" :sharing}]
+ [abstract
+ [hash {"+" Hash}]
+ [monad {"+" do}]]
+ [control
+ ["[0]" try {"+" Try}]
+ ["[0]" exception {"+" exception:}]]
+ [data
+ ["/" binary {"+" Binary}]
+ [text
+ ["%" format {"+" format}]
+ [encoding
+ ["[0]" utf8]]]
+ [collection
+ ["[0]" list]
+ ["[0]" sequence {"+" Sequence}]
+ ["[0]" set {"+" Set}]]]
+ [macro
+ ["[0]" template]]
+ [math
+ [number
+ ["n" nat]
+ ["[0]" frac]]]]]
+ ["[0]" // ("[1]#[0]" monad)])
(type: .public Offset
Nat)
@@ -52,17 +52,17 @@
(def: .public end?
(Parser Bit)
- (function (_ (^@ input [offset data]))
+ (function (_ (^let input [offset data]))
{try.#Success [input (n.= offset (/.size data))]}))
(def: .public offset
(Parser Offset)
- (function (_ (^@ input [offset data]))
+ (function (_ (^let input [offset data]))
{try.#Success [input offset]}))
(def: .public remaining
(Parser Nat)
- (function (_ (^@ input [offset data]))
+ (function (_ (^let input [offset data]))
{try.#Success [input (n.- offset (/.size data))]}))
(type: .public Size
diff --git a/stdlib/source/library/lux/control/parser/text.lux b/stdlib/source/library/lux/control/parser/text.lux
index de79a42b5..8fe67d90f 100644
--- a/stdlib/source/library/lux/control/parser/text.lux
+++ b/stdlib/source/library/lux/control/parser/text.lux
@@ -1,24 +1,24 @@
(.using
- [library
- [lux {"-" and not local}
- [abstract
- [monad {"+" Monad do}]]
- [control
- ["[0]" maybe]
- ["[0]" try {"+" Try}]
- ["[0]" exception {"+" exception:}]]
- [data
- ["/" text {"+" Char} ("[1]#[0]" monoid)]
- ["[0]" product]
- [collection
- ["[0]" list ("[1]#[0]" mix)]]]
- [macro
- ["[0]" code]
- ["[0]" template]]
- [math
- [number
- ["n" nat ("[1]#[0]" decimal)]]]]]
- ["[0]" //])
+ [library
+ [lux {"-" and not local}
+ [abstract
+ [monad {"+" Monad do}]]
+ [control
+ ["[0]" maybe]
+ ["[0]" try {"+" Try}]
+ ["[0]" exception {"+" exception:}]]
+ [data
+ ["/" text {"+" Char} ("[1]#[0]" monoid)]
+ ["[0]" product]
+ [collection
+ ["[0]" list ("[1]#[0]" mix)]]]
+ [macro
+ ["[0]" code]
+ ["[0]" template]]
+ [math
+ [number
+ ["n" nat ("[1]#[0]" decimal)]]]]]
+ ["[0]" //])
(type: .public Offset
Nat)
@@ -68,7 +68,7 @@
(def: .public offset
(Parser Offset)
- (function (_ (^@ input [offset tape]))
+ (function (_ (^let input [offset tape]))
{try.#Success [input offset]}))
(def: (with_slices parser)
@@ -139,14 +139,14 @@
(def: .public end!
(Parser Any)
- (function (_ (^@ input [offset tape]))
+ (function (_ (^let input [offset tape]))
(if (n.= offset (/.size tape))
{try.#Success [input []]}
(exception.except ..unconsumed_input input))))
(def: .public next
(Parser Text)
- (function (_ (^@ input [offset tape]))
+ (function (_ (^let input [offset tape]))
(case (/.char offset tape)
{.#Some output}
{try.#Success [input (/.of_char output)]}
@@ -156,7 +156,7 @@
(def: .public remaining
(Parser Text)
- (function (_ (^@ input [offset tape]))
+ (function (_ (^let input [offset tape]))
{try.#Success [input (..left_over offset tape)]}))
(def: .public (range bottom top)
@@ -350,7 +350,7 @@
(-> (Parser Slice) (Parser Text))
(do //.monad
[[basis distance] parser]
- (function (_ (^@ input [offset tape]))
+ (function (_ (^let input [offset tape]))
(case (/.clip basis distance tape)
{.#Some output}
{try.#Success [input output]}
diff --git a/stdlib/source/library/lux/control/reader.lux b/stdlib/source/library/lux/control/reader.lux
index bac66ac07..6a81806ac 100644
--- a/stdlib/source/library/lux/control/reader.lux
+++ b/stdlib/source/library/lux/control/reader.lux
@@ -1,10 +1,11 @@
(.using
- [library
- [lux {"-" local}
- [abstract
- [apply {"+" Apply}]
- ["[0]" functor {"+" Functor}]
- ["[0]" monad {"+" Monad do}]]]])
+ [library
+ [lux {"-" local}
+ ["@" target]
+ [abstract
+ [apply {"+" Apply}]
+ ["[0]" functor {"+" Functor}]
+ ["[0]" monad {"+" Monad do}]]]])
(type: .public (Reader r a)
(-> r a))
@@ -50,10 +51,10 @@
(mma env env))))
(implementation: .public (with monad)
- (All (_ M) (-> (Monad M) (All (_ e) (Monad (All (_ a) (Reader e (M a)))))))
+ (All (_ !) (-> (Monad !) (All (_ e) (Monad (All (_ a) (Reader e (! a)))))))
(def: &functor
- (functor.composite ..functor (value@ monad.&functor monad)))
+ (functor.composite ..functor (the monad.&functor monad)))
(def: in
(|>> (# monad in)
@@ -66,5 +67,5 @@
(result env eMa)))))
(def: .public lifted
- (All (_ M e a) (-> (M a) (Reader e (M a))))
+ (All (_ ! e a) (-> (! a) (Reader e (! a))))
(# ..monad in))
diff --git a/stdlib/source/library/lux/control/region.lux b/stdlib/source/library/lux/control/region.lux
index a0297e569..0aa7d8939 100644
--- a/stdlib/source/library/lux/control/region.lux
+++ b/stdlib/source/library/lux/control/region.lux
@@ -1,19 +1,19 @@
(.using
- [library
- [lux "*"
- [abstract
- [functor {"+" Functor}]
- [apply {"+" Apply}]
- ["[0]" monad {"+" Monad do}]]
- [control
- ["[0]" try {"+" Try}]]
- [data
- ["[0]" text
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" mix)]]]]]
- [//
- ["[0]" exception {"+" Exception exception:}]])
+ [library
+ [lux "*"
+ [abstract
+ [functor {"+" Functor}]
+ [apply {"+" Apply}]
+ ["[0]" monad {"+" Monad do}]]
+ [control
+ ["[0]" try {"+" Try}]]
+ [data
+ ["[0]" text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" mix)]]]]]
+ [//
+ ["[0]" exception {"+" Exception exception:}]])
(type: (Cleaner r !)
(-> r (! (Try Any))))
@@ -93,7 +93,7 @@
(All (_ r) (Apply (Region r !)))))
(def: &functor
- (..functor (value@ monad.&functor super)))
+ (..functor (the monad.&functor super)))
(def: (on fa ff)
(function (_ [region cleaners])
@@ -118,7 +118,7 @@
(All (_ r) (Monad (Region r !)))))
(def: &functor
- (..functor (value@ monad.&functor super)))
+ (..functor (the monad.&functor super)))
(def: (in value)
(function (_ [region cleaners])
diff --git a/stdlib/source/library/lux/control/try.lux b/stdlib/source/library/lux/control/try.lux
index a82b72d33..d1722f394 100644
--- a/stdlib/source/library/lux/control/try.lux
+++ b/stdlib/source/library/lux/control/try.lux
@@ -1,13 +1,14 @@
(.using
- [library
- [lux "*"
- [abstract
- [apply {"+" Apply}]
- [equivalence {"+" Equivalence}]
- ["[0]" functor {"+" Functor}]
- ["[0]" monad {"+" Monad do}]]
- [meta
- ["[0]" location]]]])
+ [library
+ [lux "*"
+ ["@" target]
+ [abstract
+ [apply {"+" Apply}]
+ [equivalence {"+" Equivalence}]
+ ["[0]" functor {"+" Functor}]
+ ["[0]" monad {"+" Monad do}]]
+ [meta
+ ["[0]" location]]]])
(type: .public (Try a)
(Variant
@@ -68,7 +69,7 @@
(All (_ !) (-> (Monad !) (Monad (All (_ a) (! (Try a))))))
(def: &functor
- (functor.composite (value@ monad.&functor monad)
+ (functor.composite (the monad.&functor monad)
..functor))
(def: in
diff --git a/stdlib/source/library/lux/control/writer.lux b/stdlib/source/library/lux/control/writer.lux
index 5b01af67b..06676e8eb 100644
--- a/stdlib/source/library/lux/control/writer.lux
+++ b/stdlib/source/library/lux/control/writer.lux
@@ -1,12 +1,12 @@
(.using
- [library
- [lux "*"
- ["@" target]
- [abstract
- [monoid {"+" Monoid}]
- [apply {"+" Apply}]
- ["[0]" functor {"+" Functor}]
- ["[0]" monad {"+" Monad do}]]]])
+ [library
+ [lux "*"
+ ["@" target]
+ [abstract
+ [monoid {"+" Monoid}]
+ [apply {"+" Apply}]
+ ["[0]" functor {"+" Functor}]
+ ["[0]" monad {"+" Monad do}]]]])
(type: .public (Writer log value)
(Record
@@ -53,7 +53,7 @@
(All (_ l M) (-> (Monoid l) (Monad M) (Monad (All (_ a) (M (Writer l a))))))
(def: &functor
- (functor.composite (value@ monad.&functor monad)
+ (functor.composite (the monad.&functor monad)
..functor))
(def: in
diff --git a/stdlib/source/library/lux/data/collection/dictionary.lux b/stdlib/source/library/lux/data/collection/dictionary.lux
index e61a79230..6ff9c51fe 100644
--- a/stdlib/source/library/lux/data/collection/dictionary.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary.lux
@@ -1,6 +1,6 @@
(.using
[library
- [lux "*"
+ [lux {"-" has revised}
[abstract
[hash {"+" Hash}]
[equivalence {"+" Equivalence}]
@@ -263,7 +263,7 @@
(Hash k) Level
Bit_Map (Base k v)
(Array (Node k v))))
- (product.right (list#mix (function (_ hierarchy_idx (^@ default [base_idx h_array]))
+ (product.right (list#mix (function (_ hierarchy_idx (^let default [base_idx h_array]))
(if (with_bit_position? (to_bit_position hierarchy_idx)
bitmap)
[(++ base_idx)
@@ -564,7 +564,7 @@
(def: .public key_hash
(All (_ k v) (-> (Dictionary k v) (Hash k)))
- (value@ ..#hash))
+ (the ..#hash))
(def: .public (empty key_hash)
(All (_ k v) (-> (Hash k) (Dictionary k v)))
@@ -618,7 +618,7 @@
(def: .public size
(All (_ k v) (-> (Dictionary k v) Nat))
- (|>> (value@ #root) ..node#size))
+ (|>> (the #root) ..node#size))
(def: .public empty?
(All (_ k v) (-> (Dictionary k v) Bit))
@@ -626,7 +626,7 @@
(def: .public entries
(All (_ k v) (-> (Dictionary k v) (List [k v])))
- (|>> (value@ #root) ..node#entries))
+ (|>> (the #root) ..node#entries))
(def: .public (of_list key_hash kvs)
(All (_ k v) (-> (Hash k) (List [k v]) (Dictionary k v)))
@@ -638,7 +638,7 @@
(template [<side> <name>]
[(def: .public <name>
(All (_ k v) (-> (Dictionary k v) (List <side>)))
- (|>> (value@ #root)
+ (|>> (the #root)
(node#mix (function (_ [k v] bundle)
{.#Item <side> bundle})
{.#End})))]
@@ -652,7 +652,7 @@
(node#mix (function (_ [key val] dict)
(has key val dict))
dict1
- (value@ #root dict2)))
+ (the #root dict2)))
(def: .public (merged_with f dict2 dict1)
(All (_ k v) (-> (-> v v v) (Dictionary k v) (Dictionary k v) (Dictionary k v)))
@@ -664,7 +664,7 @@
{.#Some val1}
(has key (f val2 val1) dict)))
dict1
- (value@ #root dict2)))
+ (the #root dict2)))
(def: .public (re_bound from_key to_key dict)
(All (_ k v) (-> k k (Dictionary k v) (Dictionary k v)))
@@ -729,4 +729,4 @@
(All (_ k) (Functor (Dictionary k)))
(def: (each f fa)
- (revised@ #root (# ..node_functor each f) fa)))
+ (.revised #root (# ..node_functor each f) fa)))
diff --git a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
index 7437962f6..13f9c1568 100644
--- a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
@@ -1,19 +1,19 @@
(.using
- [library
- [lux "*"
- [abstract
- equivalence
- [monad {"+" Monad do}]
- ["[0]" order {"+" Order}]]
- [control
- ["[0]" maybe]]
- [data
- ["p" product]
- [collection
- ["[0]" list ("[1]#[0]" monoid mix)]]]
- [math
- [number
- ["n" nat]]]]])
+ [library
+ [lux {"-" has revised}
+ [abstract
+ equivalence
+ [monad {"+" Monad do}]
+ ["[0]" order {"+" Order}]]
+ [control
+ ["[0]" maybe]]
+ [data
+ ["p" product]
+ [collection
+ ["[0]" list ("[1]#[0]" monoid mix)]]]
+ [math
+ [number
+ ["n" nat]]]]])
(def: error_message
"Invariant violation")
@@ -58,59 +58,59 @@
... TODO: Must improve it as soon as bug is fixed.
(def: .public (value key dict)
(All (_ k v) (-> k (Dictionary k v) (Maybe v)))
- (let [... (^open "_#[0]") (value@ #&order dict)
+ (let [... (^open "_#[0]") (the #&order dict)
]
- (loop [node (value@ #root dict)]
+ (loop [node (the #root dict)]
(case node
{.#None}
{.#None}
{.#Some node}
- (let [node_key (value@ #key node)]
+ (let [node_key (the #key node)]
(cond (# dict = node_key key)
... (_#= node_key key)
- {.#Some (value@ #value node)}
+ {.#Some (the #value node)}
(# dict < node_key key)
... (_#< node_key key)
- (again (value@ #left node))
+ (again (the #left node))
- ... (_#> (value@ #key node) key)
- (again (value@ #right node))))
+ ... (_#> (the #key node) key)
+ (again (the #right node))))
))))
... TODO: Doing inneficient access of Order functions due to compiler bug.
... TODO: Must improve it as soon as bug is fixed.
(def: .public (key? dict key)
(All (_ k v) (-> (Dictionary k v) k Bit))
- (let [... (^open "_#[0]") (value@ #&order dict)
+ (let [... (^open "_#[0]") (the #&order dict)
]
- (loop [node (value@ #root dict)]
+ (loop [node (the #root dict)]
(case node
{.#None}
#0
{.#Some node}
- (let [node_key (value@ #key node)]
+ (let [node_key (the #key node)]
(or (# dict = node_key key)
... (_#= node_key key)
(if (# dict < node_key key)
... (_#< node_key key)
- (again (value@ #left node))
- (again (value@ #right node)))))))))
+ (again (the #left node))
+ (again (the #right node)))))))))
(template [<name> <side>]
[(def: .public (<name> dict)
(All (_ k v) (-> (Dictionary k v) (Maybe v)))
- (case (value@ #root dict)
+ (case (the #root dict)
{.#None}
{.#None}
{.#Some node}
(loop [node node]
- (case (value@ <side> node)
+ (case (the <side> node)
{.#None}
- {.#Some (value@ #value node)}
+ {.#Some (the #value node)}
{.#Some side}
(again side)))))]
@@ -121,14 +121,14 @@
(def: .public (size dict)
(All (_ k v) (-> (Dictionary k v) Nat))
- (loop [node (value@ #root dict)]
+ (loop [node (the #root dict)]
(case node
{.#None}
0
{.#Some node}
- (++ (n.+ (again (value@ #left node))
- (again (value@ #right node)))))))
+ (++ (n.+ (again (the #left node))
+ (again (the #right node)))))))
(def: .public empty?
(All (_ k v) (-> (Dictionary k v) Bit))
@@ -137,9 +137,9 @@
(template [<name> <other_color> <self_color> <no_change>]
[(def: (<name> self)
(All (_ k v) (-> (Node k v) (Node k v)))
- (case (value@ #color self)
+ (case (the #color self)
{<other_color>}
- (with@ #color {<self_color>} self)
+ (.has #color {<self_color>} self)
{<self_color>}
<no_change>
@@ -151,46 +151,46 @@
(def: (with_left addition center)
(All (_ k v) (-> (Node k v) (Node k v) (Node k v)))
- (case (value@ #color center)
+ (case (the #color center)
{#Red}
- (red (value@ #key center)
- (value@ #value center)
+ (red (the #key center)
+ (the #value center)
{.#Some addition}
- (value@ #right center))
+ (the #right center))
{#Black}
(with_expansions
- [<default_behavior> (as_is (black (value@ #key center)
- (value@ #value center)
+ [<default_behavior> (as_is (black (the #key center)
+ (the #value center)
{.#Some addition}
- (value@ #right center)))]
- (case (value@ #color addition)
+ (the #right center)))]
+ (case (the #color addition)
{#Red}
- (case (value@ #left addition)
+ (case (the #left addition)
(^multi {.#Some left}
- [(value@ #color left) {#Red}])
- (red (value@ #key addition)
- (value@ #value addition)
+ [(the #color left) {#Red}])
+ (red (the #key addition)
+ (the #value addition)
{.#Some (blackened left)}
- {.#Some (black (value@ #key center)
- (value@ #value center)
- (value@ #right addition)
- (value@ #right center))})
+ {.#Some (black (the #key center)
+ (the #value center)
+ (the #right addition)
+ (the #right center))})
_
- (case (value@ #right addition)
+ (case (the #right addition)
(^multi {.#Some right}
- [(value@ #color right) {#Red}])
- (red (value@ #key right)
- (value@ #value right)
- {.#Some (black (value@ #key addition)
- (value@ #value addition)
- (value@ #left addition)
- (value@ #left right))}
- {.#Some (black (value@ #key center)
- (value@ #value center)
- (value@ #right right)
- (value@ #right center))})
+ [(the #color right) {#Red}])
+ (red (the #key right)
+ (the #value right)
+ {.#Some (black (the #key addition)
+ (the #value addition)
+ (the #left addition)
+ (the #left right))}
+ {.#Some (black (the #key center)
+ (the #value center)
+ (the #right right)
+ (the #right center))})
_
<default_behavior>))
@@ -200,46 +200,46 @@
(def: (with_right addition center)
(All (_ k v) (-> (Node k v) (Node k v) (Node k v)))
- (case (value@ #color center)
+ (case (the #color center)
{#Red}
- (red (value@ #key center)
- (value@ #value center)
- (value@ #left center)
+ (red (the #key center)
+ (the #value center)
+ (the #left center)
{.#Some addition})
{#Black}
(with_expansions
- [<default_behavior> (as_is (black (value@ #key center)
- (value@ #value center)
- (value@ #left center)
+ [<default_behavior> (as_is (black (the #key center)
+ (the #value center)
+ (the #left center)
{.#Some addition}))]
- (case (value@ #color addition)
+ (case (the #color addition)
{#Red}
- (case (value@ #right addition)
+ (case (the #right addition)
(^multi {.#Some right}
- [(value@ #color right) {#Red}])
- (red (value@ #key addition)
- (value@ #value addition)
- {.#Some (black (value@ #key center)
- (value@ #value center)
- (value@ #left center)
- (value@ #left addition))}
+ [(the #color right) {#Red}])
+ (red (the #key addition)
+ (the #value addition)
+ {.#Some (black (the #key center)
+ (the #value center)
+ (the #left center)
+ (the #left addition))}
{.#Some (blackened right)})
_
- (case (value@ #left addition)
+ (case (the #left addition)
(^multi {.#Some left}
- [(value@ #color left) {#Red}])
- (red (value@ #key left)
- (value@ #value left)
- {.#Some (black (value@ #key center)
- (value@ #value center)
- (value@ #left center)
- (value@ #left left))}
- {.#Some (black (value@ #key addition)
- (value@ #value addition)
- (value@ #right left)
- (value@ #right addition))})
+ [(the #color left) {#Red}])
+ (red (the #key left)
+ (the #value left)
+ {.#Some (black (the #key center)
+ (the #value center)
+ (the #left center)
+ (the #left left))}
+ {.#Some (black (the #key addition)
+ (the #value addition)
+ (the #right left)
+ (the #right addition))})
_
<default_behavior>))
@@ -249,17 +249,17 @@
(def: .public (has key value dict)
(All (_ k v) (-> k v (Dictionary k v) (Dictionary k v)))
- (let [(^open "_#[0]") (value@ #&order dict)
- root' (loop [?root (value@ #root dict)]
+ (let [(^open "_#[0]") (the #&order dict)
+ root' (loop [?root (the #root dict)]
(case ?root
{.#None}
{.#Some (red key value {.#None} {.#None})}
{.#Some root}
- (let [reference (value@ #key root)]
+ (let [reference (the #key root)]
(`` (cond (~~ (template [<comp> <tag> <add>]
[(<comp> reference key)
- (let [side_root (value@ <tag> root)
+ (let [side_root (the <tag> root)
outcome (again side_root)]
(if (same? side_root outcome)
?root
@@ -267,39 +267,39 @@
root)}))]
[_#< #left ..with_left]
- [(order.> (value@ #&order dict)) #right ..with_right]
+ [(order.> (the #&order dict)) #right ..with_right]
))
... (_#= reference key)
- {.#Some (with@ #value value root)}
+ {.#Some (.has #value value root)}
)))
))]
- (with@ #root root' dict)))
+ (.has #root root' dict)))
(def: (left_balanced key value ?left ?right)
(All (_ k v) (-> k v (Maybe (Node k v)) (Maybe (Node k v)) (Node k v)))
(case ?left
(^multi {.#Some left}
- [(value@ #color left) {#Red}]
- [(value@ #left left) {.#Some left>>left}]
- [(value@ #color left>>left) {#Red}])
- (red (value@ #key left)
- (value@ #value left)
+ [(the #color left) {#Red}]
+ [(the #left left) {.#Some left>>left}]
+ [(the #color left>>left) {#Red}])
+ (red (the #key left)
+ (the #value left)
{.#Some (blackened left>>left)}
- {.#Some (black key value (value@ #right left) ?right)})
+ {.#Some (black key value (the #right left) ?right)})
(^multi {.#Some left}
- [(value@ #color left) {#Red}]
- [(value@ #right left) {.#Some left>>right}]
- [(value@ #color left>>right) {#Red}])
- (red (value@ #key left>>right)
- (value@ #value left>>right)
- {.#Some (black (value@ #key left)
- (value@ #value left)
- (value@ #left left)
- (value@ #left left>>right))}
+ [(the #color left) {#Red}]
+ [(the #right left) {.#Some left>>right}]
+ [(the #color left>>right) {#Red}])
+ (red (the #key left>>right)
+ (the #value left>>right)
+ {.#Some (black (the #key left)
+ (the #value left)
+ (the #left left)
+ (the #left left>>right))}
{.#Some (black key value
- (value@ #right left>>right)
+ (the #right left>>right)
?right)})
_
@@ -309,25 +309,25 @@
(All (_ k v) (-> k v (Maybe (Node k v)) (Maybe (Node k v)) (Node k v)))
(case ?right
(^multi {.#Some right}
- [(value@ #color right) {#Red}]
- [(value@ #right right) {.#Some right>>right}]
- [(value@ #color right>>right) {#Red}])
- (red (value@ #key right)
- (value@ #value right)
- {.#Some (black key value ?left (value@ #left right))}
+ [(the #color right) {#Red}]
+ [(the #right right) {.#Some right>>right}]
+ [(the #color right>>right) {#Red}])
+ (red (the #key right)
+ (the #value right)
+ {.#Some (black key value ?left (the #left right))}
{.#Some (blackened right>>right)})
(^multi {.#Some right}
- [(value@ #color right) {#Red}]
- [(value@ #left right) {.#Some right>>left}]
- [(value@ #color right>>left) {#Red}])
- (red (value@ #key right>>left)
- (value@ #value right>>left)
- {.#Some (black key value ?left (value@ #left right>>left))}
- {.#Some (black (value@ #key right)
- (value@ #value right)
- (value@ #right right>>left)
- (value@ #right right))})
+ [(the #color right) {#Red}]
+ [(the #left right) {.#Some right>>left}]
+ [(the #color right>>left) {#Red}])
+ (red (the #key right>>left)
+ (the #value right>>left)
+ {.#Some (black key value ?left (the #left right>>left))}
+ {.#Some (black (the #key right)
+ (the #value right)
+ (the #right right>>left)
+ (the #right right))})
_
(black key value ?left ?right)))
@@ -336,26 +336,26 @@
(All (_ k v) (-> k v (Maybe (Node k v)) (Maybe (Node k v)) (Node k v)))
(case ?left
(^multi {.#Some left}
- [(value@ #color left) {#Red}])
+ [(the #color left) {#Red}])
(red key value {.#Some (blackened left)} ?right)
_
(case ?right
(^multi {.#Some right}
- [(value@ #color right) {#Black}])
+ [(the #color right) {#Black}])
(right_balanced key value ?left {.#Some (reddened right)})
(^multi {.#Some right}
- [(value@ #color right) {#Red}]
- [(value@ #left right) {.#Some right>>left}]
- [(value@ #color right>>left) {#Black}])
- (red (value@ #key right>>left)
- (value@ #value right>>left)
- {.#Some (black key value ?left (value@ #left right>>left))}
- {.#Some (right_balanced (value@ #key right)
- (value@ #value right)
- (value@ #right right>>left)
- (# maybe.functor each reddened (value@ #right right)))})
+ [(the #color right) {#Red}]
+ [(the #left right) {.#Some right>>left}]
+ [(the #color right>>left) {#Black}])
+ (red (the #key right>>left)
+ (the #value right>>left)
+ {.#Some (black key value ?left (the #left right>>left))}
+ {.#Some (right_balanced (the #key right)
+ (the #value right)
+ (the #right right>>left)
+ (# maybe.functor each reddened (the #right right)))})
_
(panic! error_message))
@@ -365,26 +365,26 @@
(All (_ k v) (-> k v (Maybe (Node k v)) (Maybe (Node k v)) (Node k v)))
(case ?right
(^multi {.#Some right}
- [(value@ #color right) {#Red}])
+ [(the #color right) {#Red}])
(red key value ?left {.#Some (blackened right)})
_
(case ?left
(^multi {.#Some left}
- [(value@ #color left) {#Black}])
+ [(the #color left) {#Black}])
(left_balanced key value {.#Some (reddened left)} ?right)
(^multi {.#Some left}
- [(value@ #color left) {#Red}]
- [(value@ #right left) {.#Some left>>right}]
- [(value@ #color left>>right) {#Black}])
- (red (value@ #key left>>right)
- (value@ #value left>>right)
- {.#Some (left_balanced (value@ #key left)
- (value@ #value left)
- (# maybe.functor each reddened (value@ #left left))
- (value@ #left left>>right))}
- {.#Some (black key value (value@ #right left>>right) ?right)})
+ [(the #color left) {#Red}]
+ [(the #right left) {.#Some left>>right}]
+ [(the #color left>>right) {#Black}])
+ (red (the #key left>>right)
+ (the #value left>>right)
+ {.#Some (left_balanced (the #key left)
+ (the #value left)
+ (# maybe.functor each reddened (the #left left))
+ (the #left left>>right))}
+ {.#Some (black key value (the #right left>>right) ?right)})
_
(panic! error_message)
@@ -400,70 +400,70 @@
?left
[{.#Some left} {.#Some right}]
- (case [(value@ #color left) (value@ #color right)]
+ (case [(the #color left) (the #color right)]
[{#Red} {#Red}]
(do maybe.monad
- [fused (prepended (value@ #right left) (value@ #right right))]
- (case (value@ #color fused)
+ [fused (prepended (the #right left) (the #right right))]
+ (case (the #color fused)
{#Red}
- (in (red (value@ #key fused)
- (value@ #value fused)
- {.#Some (red (value@ #key left)
- (value@ #value left)
- (value@ #left left)
- (value@ #left fused))}
- {.#Some (red (value@ #key right)
- (value@ #value right)
- (value@ #right fused)
- (value@ #right right))}))
+ (in (red (the #key fused)
+ (the #value fused)
+ {.#Some (red (the #key left)
+ (the #value left)
+ (the #left left)
+ (the #left fused))}
+ {.#Some (red (the #key right)
+ (the #value right)
+ (the #right fused)
+ (the #right right))}))
{#Black}
- (in (red (value@ #key left)
- (value@ #value left)
- (value@ #left left)
- {.#Some (red (value@ #key right)
- (value@ #value right)
+ (in (red (the #key left)
+ (the #value left)
+ (the #left left)
+ {.#Some (red (the #key right)
+ (the #value right)
{.#Some fused}
- (value@ #right right))}))))
+ (the #right right))}))))
[{#Red} {#Black}]
- {.#Some (red (value@ #key left)
- (value@ #value left)
- (value@ #left left)
- (prepended (value@ #right left)
+ {.#Some (red (the #key left)
+ (the #value left)
+ (the #left left)
+ (prepended (the #right left)
?right))}
[{#Black} {#Red}]
- {.#Some (red (value@ #key right)
- (value@ #value right)
+ {.#Some (red (the #key right)
+ (the #value right)
(prepended ?left
- (value@ #left right))
- (value@ #right right))}
+ (the #left right))
+ (the #right right))}
[{#Black} {#Black}]
(do maybe.monad
- [fused (prepended (value@ #right left) (value@ #left right))]
- (case (value@ #color fused)
+ [fused (prepended (the #right left) (the #left right))]
+ (case (the #color fused)
{#Red}
- (in (red (value@ #key fused)
- (value@ #value fused)
- {.#Some (black (value@ #key left)
- (value@ #value left)
- (value@ #left left)
- (value@ #left fused))}
- {.#Some (black (value@ #key right)
- (value@ #value right)
- (value@ #right fused)
- (value@ #right right))}))
+ (in (red (the #key fused)
+ (the #value fused)
+ {.#Some (black (the #key left)
+ (the #value left)
+ (the #left left)
+ (the #left fused))}
+ {.#Some (black (the #key right)
+ (the #value right)
+ (the #right fused)
+ (the #right right))}))
{#Black}
- (in (without_left (value@ #key left)
- (value@ #value left)
- (value@ #left left)
- {.#Some (black (value@ #key right)
- (value@ #value right)
+ (in (without_left (the #key left)
+ (the #value left)
+ (the #left left)
+ {.#Some (black (the #key right)
+ (the #value right)
{.#Some fused}
- (value@ #right right))}))
+ (the #right right))}))
))
)
@@ -472,42 +472,42 @@
(def: .public (lacks key dict)
(All (_ k v) (-> k (Dictionary k v) (Dictionary k v)))
- (let [(^open "_#[0]") (value@ #&order dict)
- [?root found?] (loop [?root (value@ #root dict)]
+ (let [(^open "_#[0]") (the #&order dict)
+ [?root found?] (loop [?root (the #root dict)]
(case ?root
{.#Some root}
- (let [root_key (value@ #key root)
- root_val (value@ #value root)]
+ (let [root_key (the #key root)
+ root_val (the #value root)]
(if (_#= root_key key)
- [(prepended (value@ #left root)
- (value@ #right root))
+ [(prepended (the #left root)
+ (the #right root))
#1]
(let [go_left? (_#< root_key key)]
(case (again (if go_left?
- (value@ #left root)
- (value@ #right root)))
+ (the #left root)
+ (the #right root)))
[{.#None} #0]
[{.#None} #0]
[side_outcome _]
(if go_left?
- (case (value@ #left root)
+ (case (the #left root)
(^multi {.#Some left}
- [(value@ #color left) {#Black}])
- [{.#Some (without_left root_key root_val side_outcome (value@ #right root))}
+ [(the #color left) {#Black}])
+ [{.#Some (without_left root_key root_val side_outcome (the #right root))}
#0]
_
- [{.#Some (red root_key root_val side_outcome (value@ #right root))}
+ [{.#Some (red root_key root_val side_outcome (the #right root))}
#0])
- (case (value@ #right root)
+ (case (the #right root)
(^multi {.#Some right}
- [(value@ #color right) {#Black}])
- [{.#Some (without_right root_key root_val (value@ #left root) side_outcome)}
+ [(the #color right) {#Black}])
+ [{.#Some (without_right root_key root_val (the #left root) side_outcome)}
#0]
_
- [{.#Some (red root_key root_val (value@ #left root) side_outcome)}
+ [{.#Some (red root_key root_val (the #left root) side_outcome)}
#0])
)))
))
@@ -518,11 +518,11 @@
(case ?root
{.#None}
(if found?
- (with@ #root ?root dict)
+ (.has #root ?root dict)
dict)
{.#Some root}
- (with@ #root {.#Some (blackened root)} dict)
+ (.has #root {.#Some (blackened root)} dict)
)))
(def: .public (revised key transform dict)
@@ -537,34 +537,34 @@
(def: .public (of_list order list)
(All (_ k v) (-> (Order k) (List [k v]) (Dictionary k v)))
(list#mix (function (_ [key value] dict)
- (has key value dict))
+ (..has key value dict))
(empty order)
list))
(template [<name> <type> <output>]
[(def: .public (<name> dict)
(All (_ k v) (-> (Dictionary k v) (List <type>)))
- (loop [node (value@ #root dict)]
+ (loop [node (the #root dict)]
(case node
{.#None}
(list)
{.#Some node'}
($_ list#composite
- (again (value@ #left node'))
+ (again (the #left node'))
(list <output>)
- (again (value@ #right node'))))))]
+ (again (the #right node'))))))]
- [entries [k v] [(value@ #key node') (value@ #value node')]]
- [keys k (value@ #key node')]
- [values v (value@ #value node')]
+ [entries [k v] [(the #key node') (the #value node')]]
+ [keys k (the #key node')]
+ [values v (the #value node')]
)
(implementation: .public (equivalence (^open ",#[0]"))
(All (_ k v) (-> (Equivalence v) (Equivalence (Dictionary k v))))
(def: (= reference sample)
- (let [(^open "/#[0]") (value@ #&order reference)]
+ (let [(^open "/#[0]") (the #&order reference)]
(loop [entriesR (entries reference)
entriesS (entries sample)]
(case [entriesR entriesS]
diff --git a/stdlib/source/library/lux/data/collection/dictionary/plist.lux b/stdlib/source/library/lux/data/collection/dictionary/plist.lux
index 6ba497f34..5417fca5d 100644
--- a/stdlib/source/library/lux/data/collection/dictionary/plist.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary/plist.lux
@@ -1,6 +1,6 @@
(.using
[library
- [lux "*"
+ [lux {"-" has revised}
[abstract
[equivalence {"+" Equivalence}]
[monoid {"+" Monoid}]]
diff --git a/stdlib/source/library/lux/data/collection/list.lux b/stdlib/source/library/lux/data/collection/list.lux
index e5130f985..41e616a8e 100644
--- a/stdlib/source/library/lux/data/collection/list.lux
+++ b/stdlib/source/library/lux/data/collection/list.lux
@@ -1,6 +1,6 @@
(.using
[library
- [lux "*"
+ [lux {"-" revised}
["@" target]
[abstract
[monoid {"+" Monoid}]
@@ -575,7 +575,7 @@
(All (_ M) (-> (Monad M) (Monad (All (_ a) (M (List a))))))
(def: &functor
- (functor.composite (value@ monad.&functor monad)
+ (functor.composite (the monad.&functor monad)
..functor))
(def: in
diff --git a/stdlib/source/library/lux/data/collection/queue.lux b/stdlib/source/library/lux/data/collection/queue.lux
index e8ed4c145..81eb6092c 100644
--- a/stdlib/source/library/lux/data/collection/queue.lux
+++ b/stdlib/source/library/lux/data/collection/queue.lux
@@ -1,15 +1,15 @@
(.using
- [library
- [lux {"-" list}
- [abstract
- [equivalence {"+" Equivalence}]
- [functor {"+" Functor}]]
- [data
- [collection
- ["[0]" list ("[1]#[0]" monoid functor)]]]
- [math
- [number
- ["n" nat]]]]])
+ [library
+ [lux {"-" list}
+ [abstract
+ [equivalence {"+" Equivalence}]
+ [functor {"+" Functor}]]
+ [data
+ [collection
+ ["[0]" list ("[1]#[0]" monoid functor)]]]
+ [math
+ [number
+ ["n" nat]]]]])
(type: .public (Queue a)
(Record
@@ -33,7 +33,7 @@
(def: .public front
(All (_ a) (-> (Queue a) (Maybe a)))
- (|>> (value@ #front) list.head))
+ (|>> (the #front) list.head))
(def: .public (size queue)
(All (_ a) (-> (Queue a) Nat))
@@ -43,7 +43,7 @@
(def: .public empty?
(All (_ a) (-> (Queue a) Bit))
- (|>> (value@ #front) list.empty?))
+ (|>> (the #front) list.empty?))
(def: .public (member? equivalence queue member)
(All (_ a) (-> (Equivalence a) (Queue a) a Bit))
@@ -53,7 +53,7 @@
(def: .public (next queue)
(All (_ a) (-> (Queue a) (Queue a)))
- (case (value@ #front queue)
+ (case (the #front queue)
... Empty...
(^ (.list))
queue
@@ -61,22 +61,22 @@
... Front has dried up...
(^ (.list _))
(|> queue
- (with@ #front (list.reversed (value@ #rear queue)))
- (with@ #rear (.list)))
+ (has #front (list.reversed (the #rear queue)))
+ (has #rear (.list)))
... Consume front!
(^ (.list& _ front'))
(|> queue
- (with@ #front front'))))
+ (has #front front'))))
(def: .public (end val queue)
(All (_ a) (-> a (Queue a) (Queue a)))
- (case (value@ #front queue)
+ (case (the #front queue)
{.#End}
- (with@ #front (.list val) queue)
+ (has #front (.list val) queue)
_
- (revised@ #rear (|>> {.#Item val}) queue)))
+ (revised #rear (|>> {.#Item val}) queue)))
(implementation: .public (equivalence super)
(All (_ a) (-> (Equivalence a) (Equivalence (Queue a))))
@@ -90,5 +90,5 @@
(Functor Queue)
(def: (each f fa)
- [#front (|> fa (value@ #front) (list#each f))
- #rear (|> fa (value@ #rear) (list#each f))]))
+ [#front (|> fa (the #front) (list#each f))
+ #rear (|> fa (the #rear) (list#each f))]))
diff --git a/stdlib/source/library/lux/data/collection/sequence.lux b/stdlib/source/library/lux/data/collection/sequence.lux
index 01a33b7c7..4c935a3d4 100644
--- a/stdlib/source/library/lux/data/collection/sequence.lux
+++ b/stdlib/source/library/lux/data/collection/sequence.lux
@@ -3,7 +3,7 @@
... https://hypirion.com/musings/understanding-persistent-vector-pt-3
(.using
[library
- [lux {"-" list}
+ [lux {"-" list has revised}
["@" target]
[abstract
[functor {"+" Functor}]
@@ -205,58 +205,58 @@
(def: .public (size sequence)
(All (_ a) (-> (Sequence a) Nat))
- (value@ #size sequence))
+ (the #size sequence))
(def: .public (suffix val sequence)
(All (_ a) (-> a (Sequence a) (Sequence a)))
... Check if there is room in the tail.
- (let [sequence_size (value@ #size sequence)]
+ (let [sequence_size (the #size sequence)]
(if (|> sequence_size (n.- (tail_off sequence_size)) (n.< full_node_size))
... If so, append to it.
(|> sequence
- (revised@ #size ++)
- (revised@ #tail (..expanded_tail val)))
+ (.revised #size ++)
+ (.revised #tail (..expanded_tail val)))
... Otherwise, push tail into the tree
... --------------------------------------------------------
... Will the root experience an overflow with this addition?
- (|> (if (n.> (i64.left_shifted (value@ #level sequence) 1)
+ (|> (if (n.> (i64.left_shifted (the #level sequence) 1)
(i64.right_shifted branching_exponent sequence_size))
... If so, a brand-new root must be established, that is
... 1-level taller.
(|> sequence
- (with@ #root (|> (`` (: (Hierarchy (~~ (:of val)))
- (empty_hierarchy [])))
- (array.has! 0 {#Hierarchy (value@ #root sequence)})
- (array.has! 1 (..path (value@ #level sequence) (value@ #tail sequence)))))
- (revised@ #level level_up))
+ (.has #root (|> (`` (: (Hierarchy (~~ (:of val)))
+ (empty_hierarchy [])))
+ (array.has! 0 {#Hierarchy (the #root sequence)})
+ (array.has! 1 (..path (the #level sequence) (the #tail sequence)))))
+ (.revised #level level_up))
... Otherwise, just push the current tail onto the root.
(|> sequence
- (revised@ #root (..with_tail sequence_size (value@ #level sequence) (value@ #tail sequence)))))
+ (.revised #root (..with_tail sequence_size (the #level sequence) (the #tail sequence)))))
... Finally, update the size of the sequence and grow a new
... tail with the new element as it's sole member.
- (revised@ #size ++)
- (with@ #tail (..tail val)))
+ (.revised #size ++)
+ (.has #tail (..tail val)))
)))
(exception: incorrect_sequence_structure)
(exception: .public [a] (index_out_of_bounds [sequence (Sequence a)
index Nat])
- (exception.report ["Size" (# n.decimal encoded (value@ #size sequence))]
+ (exception.report ["Size" (# n.decimal encoded (the #size sequence))]
["Index" (# n.decimal encoded index)]))
(exception: base_was_not_found)
(def: .public (within_bounds? sequence idx)
(All (_ a) (-> (Sequence a) Nat Bit))
- (n.< (value@ #size sequence) idx))
+ (n.< (the #size sequence) idx))
(def: (base_for idx sequence)
(All (_ a) (-> Index (Sequence a) (Try (Base a))))
(if (within_bounds? sequence idx)
- (if (n.< (tail_off (value@ #size sequence)) idx)
- (loop [level (value@ #level sequence)
- hierarchy (value@ #root sequence)]
+ (if (n.< (tail_off (the #size sequence)) idx)
+ (loop [level (the #level sequence)
+ hierarchy (the #root sequence)]
(let [index (branch_idx (i64.right_shifted level idx))]
(if (array.lacks? index hierarchy)
(exception.except ..base_was_not_found [])
@@ -270,7 +270,7 @@
_
(exception.except ..incorrect_sequence_structure [])))))
- {try.#Success (value@ #tail sequence)})
+ {try.#Success (the #tail sequence)})
(exception.except ..index_out_of_bounds [sequence idx])))
(def: .public (item idx sequence)
@@ -284,12 +284,12 @@
(def: .public (has idx val sequence)
(All (_ a) (-> Nat a (Sequence a) (Try (Sequence a))))
- (let [sequence_size (value@ #size sequence)]
+ (let [sequence_size (the #size sequence)]
(if (within_bounds? sequence idx)
{try.#Success (if (n.< (tail_off sequence_size) idx)
- (revised@ #root (hierarchy#has (value@ #level sequence) idx val)
+ (.revised #root (hierarchy#has (the #level sequence) idx val)
sequence)
- (revised@ #tail (`` (: (-> (Base (~~ (:of val)))
+ (.revised #tail (`` (: (-> (Base (~~ (:of val)))
(Base (~~ (:of val))))
(|>> array.clone (array.has! (branch_idx idx) val))))
sequence))}
@@ -303,7 +303,7 @@
(def: .public (prefix sequence)
(All (_ a) (-> (Sequence a) (Sequence a)))
- (case (value@ #size sequence)
+ (case (the #size sequence)
0
empty
@@ -312,19 +312,19 @@
sequence_size
(if (|> sequence_size (n.- (tail_off sequence_size)) (n.> 1))
- (let [old_tail (value@ #tail sequence)
+ (let [old_tail (the #tail sequence)
new_tail_size (-- (array.size old_tail))]
(|> sequence
- (revised@ #size --)
- (with@ #tail (|> (array.empty new_tail_size)
- (array.copy! new_tail_size 0 old_tail 0)))))
+ (.revised #size --)
+ (.has #tail (|> (array.empty new_tail_size)
+ (array.copy! new_tail_size 0 old_tail 0)))))
(maybe.trusted
(do maybe.monad
[new_tail (base_for (n.- 2 sequence_size) sequence)
- .let [[level' root'] (let [init_level (value@ #level sequence)]
+ .let [[level' root'] (let [init_level (the #level sequence)]
(loop [level init_level
root (maybe.else (empty_hierarchy [])
- (without_tail sequence_size init_level (value@ #root sequence)))]
+ (without_tail sequence_size init_level (the #root sequence)))]
(with_expansions [<else> [level root]]
(if (n.> branching_exponent level)
(if (array.lacks? 1 root)
@@ -340,16 +340,16 @@
<else>)
<else>))))]]
(in (|> sequence
- (revised@ #size --)
- (with@ #level level')
- (with@ #root root')
- (with@ #tail new_tail))))))
+ (.revised #size --)
+ (.has #level level')
+ (.has #root root')
+ (.has #tail new_tail))))))
))
(def: .public (list sequence)
(All (_ a) (-> (Sequence a) (List a)))
- (list#composite (node#list {#Hierarchy (value@ #root sequence)})
- (node#list {#Base (value@ #tail sequence)})))
+ (list#composite (node#list {#Hierarchy (the #root sequence)})
+ (node#list {#Base (the #tail sequence)})))
(def: .public of_list
(All (_ a) (-> (List a) (Sequence a)))
@@ -361,7 +361,7 @@
(def: .public empty?
(All (_ a) (-> (Sequence a) Bit))
- (|>> (value@ #size) (n.= 0)))
+ (|>> (the #size) (n.= 0)))
(syntax: .public (sequence [elems (<>.some <code>.any)])
(in (.list (` (..of_list (.list (~+ elems)))))))
@@ -384,12 +384,12 @@
(All (_ a) (-> (Equivalence a) (Equivalence (Sequence a))))
(def: (= v1 v2)
- (and (n.= (value@ #size v1) (value@ #size v2))
+ (and (n.= (the #size v1) (the #size v2))
(let [(^open "node#[0]") (node_equivalence //#=)]
- (and (node#= {#Base (value@ #tail v1)}
- {#Base (value@ #tail v2)})
- (node#= {#Hierarchy (value@ #root v1)}
- {#Hierarchy (value@ #root v2)}))))))
+ (and (node#= {#Base (the #tail v1)}
+ {#Base (the #tail v2)})
+ (node#= {#Hierarchy (the #root v1)}
+ {#Hierarchy (the #root v2)}))))))
(implementation: node_mix
(Mix Node)
@@ -414,8 +414,8 @@
(mix $
(mix $
init
- {#Hierarchy (value@ #root xs)})
- {#Base (value@ #tail xs)}))))
+ {#Hierarchy (the #root xs)})
+ {#Base (the #tail xs)}))))
(implementation: .public monoid
(All (_ a) (Monoid (Sequence a)))
@@ -440,12 +440,12 @@
(Functor Sequence)
(def: (each $ xs)
- [#level (value@ #level xs)
- #size (value@ #size xs)
+ [#level (the #level xs)
+ #size (the #size xs)
#root (let [... TODO: This binding was established to get around a compilation error. Fix and inline!
$ (# node_functor each $)]
- (|> xs (value@ #root) (array.each $)))
- #tail (|> xs (value@ #tail) (array.each $))]))
+ (|> xs (the #root) (array.each $)))
+ #tail (|> xs (the #tail) (array.each $))]))
(implementation: .public apply
(Apply Sequence)
@@ -526,11 +526,11 @@
(case (let [... TODO: This binding was established to get around a compilation error. Fix and inline!
check (..one|node check)]
(|> items
- (value@ #root)
+ (the #root)
(array.one check)))
{.#None}
(|> items
- (value@ #tail)
+ (the #tail)
(array.one check))
output
diff --git a/stdlib/source/library/lux/data/collection/set.lux b/stdlib/source/library/lux/data/collection/set.lux
index ac443315f..ee9d8f345 100644
--- a/stdlib/source/library/lux/data/collection/set.lux
+++ b/stdlib/source/library/lux/data/collection/set.lux
@@ -1,19 +1,19 @@
(.using
- [library
- [lux {"-" list}
- [abstract
- [equivalence {"+" Equivalence}]
- [hash {"+" Hash}]
- [predicate {"+" Predicate}]
- [monoid {"+" Monoid}]]
- [data
- [collection
- ["[0]" list ("[1]#[0]" mix)]]]
- [math
- [number
- ["n" nat]]]]]
- ["[0]" // "_"
- ["[1]" dictionary {"+" Dictionary}]])
+ [library
+ [lux {"-" has list}
+ [abstract
+ [equivalence {"+" Equivalence}]
+ [hash {"+" Hash}]
+ [predicate {"+" Predicate}]
+ [monoid {"+" Monoid}]]
+ [data
+ [collection
+ ["[0]" list ("[1]#[0]" mix)]]]
+ [math
+ [number
+ ["n" nat]]]]]
+ ["[0]" // "_"
+ ["[1]" dictionary {"+" Dictionary}]])
(type: .public (Set a)
(Dictionary a Any))
@@ -62,7 +62,7 @@
(implementation: .public equivalence
(All (_ a) (Equivalence (Set a)))
- (def: (= (^@ reference [hash _]) sample)
+ (def: (= (^let reference [hash _]) sample)
(and (n.= (..size reference)
(..size sample))
(list.every? (..member? reference)
diff --git a/stdlib/source/library/lux/data/collection/set/multi.lux b/stdlib/source/library/lux/data/collection/set/multi.lux
index 505fac514..57c40d2fa 100644
--- a/stdlib/source/library/lux/data/collection/set/multi.lux
+++ b/stdlib/source/library/lux/data/collection/set/multi.lux
@@ -1,22 +1,22 @@
... https://en.wikipedia.org/wiki/Multiset
(.using
- [library
- [lux {"-" list}
- [abstract
- [equivalence {"+" Equivalence}]
- [hash {"+" Hash}]]
- [control
- ["[0]" function]
- ["[0]" maybe]]
- [math
- [number
- ["n" nat]]]
- [type
- [abstract {"+" abstract: :abstraction :representation ^:representation}]]]]
- ["[0]" //
- [//
- ["[0]" list ("[1]#[0]" mix monoid)]
- ["[0]" dictionary {"+" Dictionary}]]])
+ [library
+ [lux {"-" has list}
+ [abstract
+ [equivalence {"+" Equivalence}]
+ [hash {"+" Hash}]]
+ [control
+ ["[0]" function]
+ ["[0]" maybe]]
+ [math
+ [number
+ ["n" nat]]]
+ [type
+ [abstract {"+" abstract: :abstraction :representation ^:representation}]]]]
+ ["[0]" //
+ [//
+ ["[0]" list ("[1]#[0]" mix monoid)]
+ ["[0]" dictionary {"+" Dictionary}]]])
(abstract: .public (Set a)
(Dictionary a Nat)
@@ -104,7 +104,7 @@
(def: .public (support set)
(All (_ a) (-> (Set a) (//.Set a)))
- (let [(^@ set [hash _]) (:representation set)]
+ (let [(^let set [hash _]) (:representation set)]
(|> set
dictionary.keys
(//.of_list hash))))
diff --git a/stdlib/source/library/lux/data/collection/set/ordered.lux b/stdlib/source/library/lux/data/collection/set/ordered.lux
index e97e0d6dd..5827e0993 100644
--- a/stdlib/source/library/lux/data/collection/set/ordered.lux
+++ b/stdlib/source/library/lux/data/collection/set/ordered.lux
@@ -1,16 +1,16 @@
(.using
- [library
- [lux {"-" list}
- [abstract
- [equivalence {"+" Equivalence}]
- [order {"+" Order}]]
- [data
- [collection
- ["[0]" list ("[1]#[0]" mix)]
- [dictionary
- ["/" ordered]]]]
- [type
- abstract]]])
+ [library
+ [lux {"-" has list}
+ [abstract
+ [equivalence {"+" Equivalence}]
+ [order {"+" Order}]]
+ [data
+ [collection
+ ["[0]" list ("[1]#[0]" mix)]
+ [dictionary
+ ["/" ordered]]]]
+ [type
+ abstract]]])
(abstract: .public (Set a)
(/.Dictionary a a)
@@ -58,13 +58,13 @@
(All (_ a) (-> (Set a) (Set a) (Set a)))
(|> (..list right)
(list.only (..member? left))
- (..of_list (value@ /.#&order (:representation right)))))
+ (..of_list (the /.#&order (:representation right)))))
(def: .public (difference param subject)
(All (_ a) (-> (Set a) (Set a) (Set a)))
(|> (..list subject)
(list.only (|>> (..member? param) not))
- (..of_list (value@ /.#&order (:representation subject)))))
+ (..of_list (the /.#&order (:representation subject)))))
(implementation: .public equivalence
(All (_ a) (Equivalence (Set a)))
diff --git a/stdlib/source/library/lux/data/collection/tree.lux b/stdlib/source/library/lux/data/collection/tree.lux
index d231e5d18..b0940209e 100644
--- a/stdlib/source/library/lux/data/collection/tree.lux
+++ b/stdlib/source/library/lux/data/collection/tree.lux
@@ -1,20 +1,20 @@
(.using
- [library
- [lux "*"
- [abstract
- [functor {"+" Functor}]
- [equivalence {"+" Equivalence}]
- [mix {"+" Mix}]
- [monad {"+" do}]]
- [control
- ["<>" parser
- ["<[0]>" code {"+" Parser}]]]
- [data
- [collection
- ["[0]" list ("[1]#[0]" monad mix)]]]
- [macro
- [syntax {"+" syntax:}]
- ["[0]" code]]]])
+ [library
+ [lux "*"
+ [abstract
+ [functor {"+" Functor}]
+ [equivalence {"+" Equivalence}]
+ [mix {"+" Mix}]
+ [monad {"+" do}]]
+ [control
+ ["<>" parser
+ ["<[0]>" code {"+" Parser}]]]
+ [data
+ [collection
+ ["[0]" list ("[1]#[0]" monad mix)]]]
+ [macro
+ [syntax {"+" syntax:}]
+ ["[0]" code]]]])
(type: .public (Tree a)
(Record
@@ -24,10 +24,10 @@
(def: .public (flat tree)
(All (_ a) (-> (Tree a) (List a)))
(|> tree
- (value@ #children)
+ (the #children)
(list#each flat)
list#conjoint
- {.#Item (value@ #value tree)}))
+ {.#Item (the #value tree)}))
(def: .public (leaf value)
(All (_ a) (-> a (Tree a)))
@@ -63,22 +63,22 @@
(All (_ a) (-> (Equivalence a) (Equivalence (Tree a))))
(def: (= tx ty)
- (and (# super = (value@ #value tx) (value@ #value ty))
- (# (list.equivalence (equivalence super)) = (value@ #children tx) (value@ #children ty)))))
+ (and (# super = (the #value tx) (the #value ty))
+ (# (list.equivalence (equivalence super)) = (the #children tx) (the #children ty)))))
(implementation: .public functor
(Functor Tree)
(def: (each f fa)
- [#value (f (value@ #value fa))
+ [#value (f (the #value fa))
#children (list#each (each f)
- (value@ #children fa))]))
+ (the #children fa))]))
(implementation: .public mix
(Mix Tree)
(def: (mix f init tree)
(list#mix (function (_ tree' init') (mix f init' tree'))
- (f (value@ #value tree)
+ (f (the #value tree)
init)
- (value@ #children tree))))
+ (the #children tree))))
diff --git a/stdlib/source/library/lux/data/collection/tree/finger.lux b/stdlib/source/library/lux/data/collection/tree/finger.lux
index 7c8a244b1..a7bf860b4 100644
--- a/stdlib/source/library/lux/data/collection/tree/finger.lux
+++ b/stdlib/source/library/lux/data/collection/tree/finger.lux
@@ -1,14 +1,14 @@
(.using
- [library
- [lux "*"
- [abstract
- [predicate {"+" Predicate}]
- ["[0]" monoid {"+" Monoid}]]
- [data
- [collection
- ["[0]" list ("[1]#[0]" monoid)]]]
- [type
- [abstract {"+" abstract: :abstraction :representation}]]]])
+ [library
+ [lux "*"
+ [abstract
+ [predicate {"+" Predicate}]
+ ["[0]" monoid {"+" Monoid}]]
+ [data
+ [collection
+ ["[0]" list ("[1]#[0]" monoid)]]]
+ [type
+ [abstract {"+" abstract: :abstraction :representation}]]]])
... https://en.wikipedia.org/wiki/Finger_tree
(abstract: .public (Tree @ t v)
@@ -32,7 +32,7 @@
(template [<name> <tag> <output>]
[(def: .public <name>
(All (_ @ t v) (-> (Tree @ t v) <output>))
- (|>> :representation (value@ <tag>)))]
+ (|>> :representation (the <tag>)))]
[tag #tag t]
[root #root (Either v [(Tree @ t v) (Tree @ t v)])]
@@ -55,7 +55,7 @@
(def: .public (value tree)
(All (_ @ t v) (-> (Tree @ t v) v))
- (case (value@ #root (:representation tree))
+ (case (the #root (:representation tree))
{0 #0 value}
value
@@ -64,9 +64,9 @@
(def: .public (tags tree)
(All (_ @ t v) (-> (Tree @ t v) (List t)))
- (case (value@ #root (:representation tree))
+ (case (the #root (:representation tree))
{0 #0 value}
- (list (value@ #tag (:representation tree)))
+ (list (the #tag (:representation tree)))
{0 #1 [left right]}
(list#composite (tags left)
@@ -74,7 +74,7 @@
(def: .public (values tree)
(All (_ @ t v) (-> (Tree @ t v) (List v)))
- (case (value@ #root (:representation tree))
+ (case (the #root (:representation tree))
{0 #0 value}
(list value)
@@ -96,8 +96,8 @@
{0 #1 [left right]}
(let [shifted_tag (tag//composite _tag (..tag left))]
(if (predicate shifted_tag)
- (again _tag (value@ #root (:representation left)))
- (again shifted_tag (value@ #root (:representation right))))))))
+ (again _tag (the #root (:representation left)))
+ (again shifted_tag (the #root (:representation right))))))))
{.#None})))
)
diff --git a/stdlib/source/library/lux/data/collection/tree/zipper.lux b/stdlib/source/library/lux/data/collection/tree/zipper.lux
index ea6ca7119..108a486d2 100644
--- a/stdlib/source/library/lux/data/collection/tree/zipper.lux
+++ b/stdlib/source/library/lux/data/collection/tree/zipper.lux
@@ -1,21 +1,21 @@
(.using
- [library
- [lux "*"
- ["@" target]
- [abstract
- [functor {"+" Functor}]
- [comonad {"+" CoMonad}]
- [monad {"+" do}]
- [equivalence {"+" Equivalence}]]
- [control
- ["[0]" maybe ("[1]#[0]" monad)]]
- [data
- ["[0]" product]
- [text
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" functor monoid)]]]]]
- ["[0]" // {"+" Tree} ("[1]#[0]" functor)])
+ [library
+ [lux "*"
+ ["@" target]
+ [abstract
+ [functor {"+" Functor}]
+ [comonad {"+" CoMonad}]
+ [monad {"+" do}]
+ [equivalence {"+" Equivalence}]]
+ [control
+ ["[0]" maybe ("[1]#[0]" monad)]]
+ [data
+ ["[0]" product]
+ [text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor monoid)]]]]]
+ ["[0]" // {"+" Tree} ("[1]#[0]" functor)])
(type: (Family Zipper a)
(Record
@@ -51,23 +51,23 @@
(def: .public tree
(All (_ a) (-> (Zipper a) (Tree a)))
- (value@ #node))
+ (the #node))
(def: .public value
(All (_ a) (-> (Zipper a) a))
- (value@ [#node //.#value]))
+ (the [#node //.#value]))
(def: .public (set value zipper)
(All (_ a) (-> a (Zipper a) (Zipper a)))
- (with@ [#node //.#value] value zipper))
+ (has [#node //.#value] value zipper))
(def: .public (update transform zipper)
(All (_ a) (-> (-> a a) (Zipper a) (Zipper a)))
- (revised@ [#node //.#value] transform zipper))
+ (revised [#node //.#value] transform zipper))
(def: children
(All (_ a) (-> (Zipper a) (List (Tree a))))
- (value@ [#node //.#children]))
+ (the [#node //.#children]))
(def: .public leaf?
(All (_ a) (-> (Zipper a) Bit))
@@ -79,7 +79,7 @@
(def: .public (start? zipper)
(All (_ a) (-> (Zipper a) Bit))
- (case (value@ #family zipper)
+ (case (the #family zipper)
{.#None}
true
@@ -93,7 +93,7 @@
{.#None}
{.#Item head tail}
- {.#Some [#family {.#Some [#parent (with@ [#node //.#children] (list) zipper)
+ {.#Some [#family {.#Some [#parent (has [#node //.#children] (list) zipper)
#lefts {.#End}
#rights tail]}
#node head]}))
@@ -101,37 +101,37 @@
(def: .public (up zipper)
(All (_ a) (-> (Zipper a) (Maybe (Zipper a))))
(do maybe.monad
- [family (value@ #family zipper)]
+ [family (the #family zipper)]
(in (let [(^open "_[0]") family]
(for [@.old
- (revised@ #node (: (-> (Tree (:parameter 0))
- (Tree (:parameter 0)))
- (with@ //.#children (list#composite (list.reversed _#lefts)
- {.#Item (value@ #node zipper)
- _#rights})))
- _#parent)]
- (with@ [#node //.#children]
- (list#composite (list.reversed _#lefts)
- {.#Item (value@ #node zipper)
- _#rights})
- _#parent))))))
+ (revised #node (: (-> (Tree (:parameter 0))
+ (Tree (:parameter 0)))
+ (has //.#children (list#composite (list.reversed _#lefts)
+ {.#Item (the #node zipper)
+ _#rights})))
+ _#parent)]
+ (has [#node //.#children]
+ (list#composite (list.reversed _#lefts)
+ {.#Item (the #node zipper)
+ _#rights})
+ _#parent))))))
(template [<one> <all> <side> <op_side>]
[(def: .public (<one> zipper)
(All (_ a) (-> (Zipper a) (Maybe (Zipper a))))
- (case (value@ #family zipper)
+ (case (the #family zipper)
{.#Some family}
- (case (value@ <side> family)
+ (case (the <side> family)
{.#Item next side'}
{.#Some (for [@.old
[#family {.#Some (|> family
- (with@ <side> side')
- (revised@ <op_side> (|>> {.#Item (value@ #node zipper)})))}
+ (has <side> side')
+ (revised <op_side> (|>> {.#Item (the #node zipper)})))}
#node next]]
(let [move (: (All (_ a) (-> (List (Tree a)) (Zipper a) (Family Zipper a) (Family Zipper a)))
(function (_ side' zipper)
- (|>> (with@ <side> side')
- (revised@ <op_side> (|>> {.#Item (value@ #node zipper)})))))]
+ (|>> (has <side> side')
+ (revised <op_side> (|>> {.#Item (the #node zipper)})))))]
[#family {.#Some (move side' zipper family)}
#node next]))}
@@ -143,26 +143,26 @@
(def: .public (<all> zipper)
(All (_ a) (-> (Zipper a) (Maybe (Zipper a))))
- (case (value@ #family zipper)
+ (case (the #family zipper)
{.#None}
{.#None}
{.#Some family}
- (case (list.reversed (value@ <side> family))
+ (case (list.reversed (the <side> family))
{.#End}
{.#None}
{.#Item last prevs}
{.#Some (for [@.old [#family {.#Some (|> family
- (with@ <side> {.#End})
- (revised@ <op_side> (|>> {.#Item (value@ #node zipper)}
- (list#composite prevs))))}
+ (has <side> {.#End})
+ (revised <op_side> (|>> {.#Item (the #node zipper)}
+ (list#composite prevs))))}
#node last]]
(let [move (: (All (_ a) (-> (List (Tree a)) (Zipper a) (Family Zipper a) (Family Zipper a)))
(function (_ prevs zipper)
- (|>> (with@ <side> {.#End})
- (revised@ <op_side> (|>> {.#Item (value@ #node zipper)}
- (list#composite prevs))))))]
+ (|>> (has <side> {.#End})
+ (revised <op_side> (|>> {.#Item (the #node zipper)}
+ (list#composite prevs))))))]
[#family {.#Some (move prevs zipper family)}
#node last]))})))]
@@ -246,44 +246,44 @@
(def: .public (interpose value zipper)
(All (_ a) (-> a (Zipper a) (Zipper a)))
- (revised@ [#node //.#children]
- (|>> (//.branch value) list)
- zipper))
+ (revised [#node //.#children]
+ (|>> (//.branch value) list)
+ zipper))
(def: .public (adopt value zipper)
(All (_ a) (-> a (Zipper a) (Zipper a)))
- (revised@ [#node //.#children]
- (|>> {.#Item (//.leaf value)})
- zipper))
+ (revised [#node //.#children]
+ (|>> {.#Item (//.leaf value)})
+ zipper))
(def: .public (remove zipper)
(All (_ a) (-> (Zipper a) (Maybe (Zipper a))))
(do maybe.monad
- [family (value@ #family zipper)]
- (case (value@ #lefts family)
+ [family (the #family zipper)]
+ (case (the #lefts family)
{.#End}
- (in (with@ [#node //.#children]
- (value@ #rights family)
- (value@ #parent family)))
+ (in (has [#node //.#children]
+ (the #rights family)
+ (the #parent family)))
{.#Item next side}
(in (|> zipper
- (with@ #family (|> family
- (with@ #lefts side)
- {.#Some}))
- (with@ #node next))))))
+ (has #family (|> family
+ (has #lefts side)
+ {.#Some}))
+ (has #node next))))))
(template [<name> <side>]
[(def: .public (<name> value zipper)
(All (_ a) (-> a (Zipper a) (Maybe (Zipper a))))
- (case (value@ #family zipper)
+ (case (the #family zipper)
{.#None}
{.#None}
{.#Some family}
- {.#Some (with@ #family
- {.#Some (revised@ <side> (|>> {.#Item (//.leaf value)}) family)}
- zipper)}))]
+ {.#Some (has #family
+ {.#Some (revised <side> (|>> {.#Item (//.leaf value)}) family)}
+ zipper)}))]
[insert_left #lefts]
[insert_right #rights]
@@ -307,14 +307,14 @@
..functor)
(def: out
- (value@ [#node //.#value]))
+ (the [#node //.#value]))
(def: (disjoint (^open "_[0]"))
(let [tree_splitter (: (All (_ a) (-> (Tree a) (Tree (Zipper a))))
(function (tree_splitter tree)
[//.#value (..zipper tree)
//.#children (|> tree
- (value@ //.#children)
+ (the //.#children)
(list#each tree_splitter))]))]
[#family (maybe#each (function (_ (^open "_[0]"))
[..#parent (disjoint _#parent)
diff --git a/stdlib/source/library/lux/data/format/css.lux b/stdlib/source/library/lux/data/format/css.lux
index f4dd728df..649e50f5d 100644
--- a/stdlib/source/library/lux/data/format/css.lux
+++ b/stdlib/source/library/lux/data/format/css.lux
@@ -54,19 +54,19 @@
(def: .public (font font)
(-> Font (CSS Special))
- (let [with_unicode (case (value@ /font.#unicode_range font)
+ (let [with_unicode (case (the /font.#unicode_range font)
{.#Some unicode_range}
- (let [unicode_range' (format "U+" (# nat.hex encoded (value@ /font.#start unicode_range))
- "-" (# nat.hex encoded (value@ /font.#end unicode_range)))]
+ (let [unicode_range' (format "U+" (# nat.hex encoded (the /font.#start unicode_range))
+ "-" (# nat.hex encoded (the /font.#end unicode_range)))]
(list ["unicode-range" unicode_range']))
{.#None}
(list))]
- (|> (list& ["font-family" (value@ /font.#family font)]
- ["src" (format "url(" (value@ /font.#source font) ")")]
- ["font-stretch" (|> font (value@ /font.#stretch) (maybe.else /value.normal_stretch) /value.value)]
- ["font-style" (|> font (value@ /font.#style) (maybe.else /value.normal_style) /value.value)]
- ["font-weight" (|> font (value@ /font.#weight) (maybe.else /value.normal_weight) /value.value)]
+ (|> (list& ["font-family" (the /font.#family font)]
+ ["src" (format "url(" (the /font.#source font) ")")]
+ ["font-stretch" (|> font (the /font.#stretch) (maybe.else /value.normal_stretch) /value.value)]
+ ["font-style" (|> font (the /font.#style) (maybe.else /value.normal_style) /value.value)]
+ ["font-weight" (|> font (the /font.#weight) (maybe.else /value.normal_weight) /value.value)]
with_unicode)
(list#each (function (_ [property value])
(format property ": " value ";")))
@@ -99,8 +99,8 @@
(:abstraction (format "@keyframes " (/value.value animation) " {"
(|> frames
(list#each (function (_ frame)
- (format (/value.value (value@ #when frame)) " {"
- (/style.inline (/style.style (value@ #what frame)))
+ (format (/value.value (the #when frame)) " {"
+ (/style.inline (/style.style (the #what frame)))
"}")))
(text.interposed ..separator))
"}")))
diff --git a/stdlib/source/library/lux/data/format/css/value.lux b/stdlib/source/library/lux/data/format/css/value.lux
index 9b2de87f3..4dd831528 100644
--- a/stdlib/source/library/lux/data/format/css/value.lux
+++ b/stdlib/source/library/lux/data/format/css/value.lux
@@ -1115,7 +1115,7 @@
(def: .public (clip rectangle)
(-> Rectangle (Value Clip))
(`` (..apply "rect" (list (~~ (template [<side>]
- [(:representation (value@ <side> rectangle))]
+ [(:representation (the <side> rectangle))]
[#top] [#right] [#bottom] [#left]))))))
diff --git a/stdlib/source/library/lux/data/format/json.lux b/stdlib/source/library/lux/data/format/json.lux
index 49686f9fa..315665921 100644
--- a/stdlib/source/library/lux/data/format/json.lux
+++ b/stdlib/source/library/lux/data/format/json.lux
@@ -1,6 +1,6 @@
(.using
[library
- [lux "*"
+ [lux {"-" has}
["[0]" meta {"+" monad}]
[abstract
[equivalence {"+" Equivalence}]
diff --git a/stdlib/source/library/lux/data/format/tar.lux b/stdlib/source/library/lux/data/format/tar.lux
index c4962a187..8e51999b3 100644
--- a/stdlib/source/library/lux/data/format/tar.lux
+++ b/stdlib/source/library/lux/data/format/tar.lux
@@ -637,11 +637,11 @@
(def: (header_writer header)
(Writer Header)
(let [checksum (|> header
- (with@ #checksum ..dummy_checksum)
+ (has #checksum ..dummy_checksum)
(format.result ..header_writer')
..checksum_code)]
(|> header
- (with@ #checksum checksum)
+ (has #checksum checksum)
(format.result ..header_writer')
(format.segment ..block_size))))
@@ -661,16 +661,16 @@
(format.segment (..rounded_content_size size)))]
(writer [[#path path
#mode mode
- #user_id (value@ [#user #id] ownership)
- #group_id (value@ [#group #id] ownership)
+ #user_id (the [#user #id] ownership)
+ #group_id (the [#group #id] ownership)
#size size
#modification_time (..modification_time modification_time)
#checksum ..dummy_checksum
#link_flag link_flag
#link_name ..no_path
#magic ..ustar
- #user_name (value@ [#user #name] ownership)
- #group_name (value@ [#group #name] ownership)
+ #user_name (the [#user #name] ownership)
+ #group_name (the [#group #name] ownership)
#major_device ..no_device
#minor_device ..no_device]
content]))))
@@ -806,41 +806,41 @@
(def: (file_parser header)
(-> Header (Parser File))
(do <>.monad
- [.let [size (value@ #size header)
+ [.let [size (the #size header)
rounded_size (..rounded_content_size size)]
content (<binary>.segment (..from_big size))
content (<>.lifted (..content content))
_ (<binary>.segment (n.- (..from_big size) rounded_size))]
- (in [(value@ #path header)
+ (in [(the #path header)
(|> header
- (value@ #modification_time)
+ (the #modification_time)
..from_big
.int
duration.of_millis
(duration.up (|> duration.second duration.millis .nat))
instant.absolute)
- (value@ #mode header)
- [#user [#name (value@ #user_name header)
- #id (value@ #user_id header)]
- #group [#name (value@ #group_name header)
- #id (value@ #group_id header)]]
+ (the #mode header)
+ [#user [#name (the #user_name header)
+ #id (the #user_id header)]
+ #group [#name (the #group_name header)
+ #id (the #group_id header)]]
content])))
(def: entry_parser
(Parser Entry)
(do [! <>.monad]
[header ..header_parser]
- (cond (same? ..contiguous (value@ #link_flag header))
+ (cond (same? ..contiguous (the #link_flag header))
(# ! each (|>> {..#Contiguous}) (..file_parser header))
- (same? ..symbolic_link (value@ #link_flag header))
- (in {..#Symbolic_Link (value@ #link_name header)})
+ (same? ..symbolic_link (the #link_flag header))
+ (in {..#Symbolic_Link (the #link_name header)})
- (same? ..directory (value@ #link_flag header))
- (in {..#Directory (value@ #path header)})
+ (same? ..directory (the #link_flag header))
+ (in {..#Directory (the #path header)})
- ... (or (same? ..normal (value@ #link_flag header))
- ... (same? ..old_normal (value@ #link_flag header)))
+ ... (or (same? ..normal (the #link_flag header))
+ ... (same? ..old_normal (the #link_flag header)))
(# ! each (|>> {..#Normal}) (..file_parser header)))))
... It's safe to implement the parser this way because the range of values for Nat is 2^64
diff --git a/stdlib/source/library/lux/data/store.lux b/stdlib/source/library/lux/data/store.lux
index 11c9580d0..a30bdf0c4 100644
--- a/stdlib/source/library/lux/data/store.lux
+++ b/stdlib/source/library/lux/data/store.lux
@@ -1,11 +1,11 @@
(.using
- [library
- [lux "*"
- [abstract
- [functor {"+" Functor}]
- comonad]
- [type
- implicit]]])
+ [library
+ [lux "*"
+ [abstract
+ [functor {"+" Functor}]
+ comonad]
+ [type
+ implicit]]])
(type: .public (Store s a)
(Record
@@ -14,8 +14,8 @@
(def: (extend f wa)
(All (_ s a b) (-> (-> (Store s a) b) (Store s a) (Store s b)))
- [#cursor (value@ #cursor wa)
- #peek (function (_ s) (f (with@ #cursor s wa)))])
+ [#cursor (the #cursor wa)
+ #peek (function (_ s) (f (has #cursor s wa)))])
(implementation: .public functor
(All (_ s) (Functor (Store s)))
diff --git a/stdlib/source/library/lux/data/text/unicode/block.lux b/stdlib/source/library/lux/data/text/unicode/block.lux
index f71030258..feab490e3 100644
--- a/stdlib/source/library/lux/data/text/unicode/block.lux
+++ b/stdlib/source/library/lux/data/text/unicode/block.lux
@@ -1,18 +1,18 @@
(.using
- [library
- [lux "*"
- [abstract
- [equivalence {"+" Equivalence}]
- [hash {"+" Hash}]
- [monoid {"+" Monoid}]
- ["[0]" interval {"+" Interval}]]
- [math
- [number {"+" hex}
- ["n" nat ("[1]#[0]" interval)]
- ["[0]" i64]]]
- [type
- abstract]]]
- [/// {"+" Char}])
+ [library
+ [lux "*"
+ [abstract
+ [equivalence {"+" Equivalence}]
+ [hash {"+" Hash}]
+ [monoid {"+" Monoid}]
+ ["[0]" interval {"+" Interval}]]
+ [math
+ [number {"+" hex}
+ ["n" nat ("[1]#[0]" interval)]
+ ["[0]" i64]]]
+ [type
+ abstract]]]
+ [/// {"+" Char}])
(abstract: .public Block
(Interval Char)
@@ -41,7 +41,7 @@
(template [<name> <slot>]
[(def: .public <name>
(-> Block Char)
- (|>> :representation (value@ <slot>)))]
+ (|>> :representation (the <slot>)))]
[start interval.bottom]
[end interval.top]
@@ -49,8 +49,8 @@
(def: .public (size block)
(-> Block Nat)
- (let [start (value@ interval.bottom (:representation block))
- end (value@ interval.top (:representation block))]
+ (let [start (the interval.bottom (:representation block))
+ end (the interval.top (:representation block))]
(|> end (n.- start) ++)))
(def: .public (within? block char)
diff --git a/stdlib/source/library/lux/data/trace.lux b/stdlib/source/library/lux/data/trace.lux
index 52e30470f..23c9fa00b 100644
--- a/stdlib/source/library/lux/data/trace.lux
+++ b/stdlib/source/library/lux/data/trace.lux
@@ -1,11 +1,11 @@
(.using
- [library
- [lux "*"
- [abstract
- ["[0]" monoid {"+" Monoid}]
- [functor {"+" Functor}]
- comonad]
- function]])
+ [library
+ [lux "*"
+ [abstract
+ ["[0]" monoid {"+" Monoid}]
+ [functor {"+" Functor}]
+ comonad]
+ function]])
(type: .public (Trace t a)
(Record
@@ -16,7 +16,7 @@
(All (_ t) (Functor (Trace t)))
(def: (each f fa)
- (revised@ #trace (composite f) fa)))
+ (revised #trace (composite f) fa)))
(implementation: .public comonad
(All (_ t) (CoMonad (Trace t)))
@@ -24,16 +24,16 @@
(def: &functor ..functor)
(def: (out wa)
- ((value@ #trace wa)
- (value@ [#monoid monoid.#identity] wa)))
+ ((the #trace wa)
+ (the [#monoid monoid.#identity] wa)))
(def: (disjoint wa)
- (let [monoid (value@ #monoid wa)]
+ (let [monoid (the #monoid wa)]
[#monoid monoid
#trace (function (_ t1)
[#monoid monoid
#trace (function (_ t2)
- ((value@ #trace wa)
+ ((the #trace wa)
(# monoid composite t1 t2)))])])))
(def: .public (result context tracer)
diff --git a/stdlib/source/library/lux/documentation.lux b/stdlib/source/library/lux/documentation.lux
index 2e2b7e65e..676746bd5 100644
--- a/stdlib/source/library/lux/documentation.lux
+++ b/stdlib/source/library/lux/documentation.lux
@@ -1,38 +1,38 @@
(.using
- [library
- [lux {"-" Definition Module type}
- ["[0]" meta]
- ["[0]" type ("[1]#[0]" equivalence)]
- [abstract
- [monad {"+" do}]
- ["[0]" enum]]
- [control
- ["[0]" maybe ("[1]#[0]" functor)]
- ["[0]" exception {"+" exception:}]
- ["<>" parser ("[1]#[0]" monad)
- ["<[0]>" code {"+" Parser}]]]
- [data
- ["[0]" product]
- ["[0]" text {"+" \n} ("[1]#[0]" order)
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" monad mix monoid)]
- ["[0]" set {"+" Set}]
- ["[0]" stream {"+" Stream}]]
- [format
- ["md" markdown {"+" Markdown Block}]]]
- ["[0]" macro
- [syntax {"+" syntax:}]
- ["[0]" code]
- ["[0]" template]]
- [math
- [number
- ["n" nat]]]
- [tool
- [compiler
- [language
- [lux
- ["[0]" syntax]]]]]]])
+ [library
+ [lux {"-" Definition Module type}
+ ["[0]" meta]
+ ["[0]" type ("[1]#[0]" equivalence)]
+ [abstract
+ [monad {"+" do}]
+ ["[0]" enum]]
+ [control
+ ["[0]" maybe ("[1]#[0]" functor)]
+ ["[0]" exception {"+" exception:}]
+ ["<>" parser ("[1]#[0]" monad)
+ ["<[0]>" code {"+" Parser}]]]
+ [data
+ ["[0]" product]
+ ["[0]" text {"+" \n} ("[1]#[0]" order)
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" monad mix monoid)]
+ ["[0]" set {"+" Set}]
+ ["[0]" stream {"+" Stream}]]
+ [format
+ ["md" markdown {"+" Markdown Block}]]]
+ ["[0]" macro
+ [syntax {"+" syntax:}]
+ ["[0]" code]
+ ["[0]" template]]
+ [math
+ [number
+ ["n" nat]]]
+ [tool
+ [compiler
+ [language
+ [lux
+ ["[0]" syntax]]]]]]])
(template: (|recursion_dummy|)
[{.#Primitive "" {.#End}}])
@@ -96,14 +96,14 @@
... else
(%.symbol [module short]))]
- [(revised@ .#column (n.+ (text.size documentation)) new_location)
+ [(revised .#column (n.+ (text.size documentation)) new_location)
(format (padding reference_column old_location new_location)
documentation)])
(^template [<tag> <format>]
[[new_location {<tag> value}]
(let [documentation (`` (|> value (~~ (template.spliced <format>))))]
- [(revised@ .#column (n.+ (text.size documentation)) new_location)
+ [(revised .#column (n.+ (text.size documentation)) new_location)
(format (padding reference_column old_location new_location)
documentation)])])
([.#Bit [%.bit]]
@@ -118,9 +118,9 @@
(let [[group_location' members_documentation] (list#mix (function (_ part [last_location text_accum])
(let [[member_location member_documentation] (code_documentation expected_module last_location reference_column part)]
[member_location (format text_accum member_documentation)]))
- [(revised@ .#column ++ group_location) ""]
+ [(revised .#column ++ group_location) ""]
members)]
- [(revised@ .#column ++ group_location')
+ [(revised .#column ++ group_location')
(format (padding reference_column old_location group_location)
|<| members_documentation |>|)])])
([syntax.open_form syntax.close_form .#Form]
@@ -146,7 +146,7 @@
(let [reference_column (..reference_column example)
[location _] example]
(|> example
- (..code_documentation module (with@ .#column reference_column location) reference_column)
+ (..code_documentation module (has .#column reference_column location) reference_column)
product.right))))
(def: parameter_name_options "abcdefghijklmnopqrstuvwxyz")
@@ -601,9 +601,9 @@
(def: definitions_documentation
(-> (List Definition) (Markdown Block))
(|>> (list.sorted (function (_ left right)
- (text#< (value@ #definition right)
- (value@ #definition left))))
- (list#each (value@ #documentation))
+ (text#< (the #definition right)
+ (the #definition left))))
+ (list#each (the #documentation))
(list#mix md.then md.empty)))
(def: expected_separator
@@ -655,9 +655,9 @@
(let [(^open "_[0]") module]
($_ md.then
... Name
- (md.heading/1 (value@ #module module))
+ (md.heading/1 (the #module module))
... Description
- (case (value@ #description module)
+ (case (the #description module)
"" md.empty
description (<| md.paragraph
md.text
@@ -665,15 +665,15 @@
... Definitions
(md.heading/2 "Definitions")
(|> module
- (value@ #definitions)
- (list.only (|>> (value@ #definition)
+ (the #definitions)
+ (list.only (|>> (the #definition)
(set.member? _#expected)))
..definitions_documentation)
... Missing documentation
(case (|> module
- (value@ #definitions)
+ (the #definitions)
(list#mix (function (_ definition missing)
- (set.lacks (value@ #definition definition) missing))
+ (set.lacks (the #definition definition) missing))
_#expected)
set.list)
{.#End}
@@ -685,11 +685,11 @@
(..listing missing)))
... Un-expected documentation
(case (|> module
- (value@ #definitions)
- (list.only (|>> (value@ #definition)
+ (the #definitions)
+ (list.only (|>> (the #definition)
(set.member? _#expected)
not))
- (list#each (value@ #definition)))
+ (list#each (the #definition)))
{.#End}
md.empty
@@ -702,7 +702,7 @@
(def: .public documentation
(-> (List Module) Text)
(|>> (list.sorted (function (_ left right)
- (text#< (value@ #module right) (value@ #module left))))
+ (text#< (the #module right) (the #module left))))
(list#each ..module_documentation)
(list.interposed md.horizontal_rule)
(list#mix md.then (: (Markdown Block) md.empty))
diff --git a/stdlib/source/library/lux/ffi.jvm.lux b/stdlib/source/library/lux/ffi.jvm.lux
index a1d5abe96..5720c4dff 100644
--- a/stdlib/source/library/lux/ffi.jvm.lux
+++ b/stdlib/source/library/lux/ffi.jvm.lux
@@ -1326,15 +1326,15 @@
(-> (List (Type Var)) Import_Member_Declaration (List (Type Var)))
(case member
{#ConstructorDecl [commons _]}
- (list#composite class_tvars (value@ #import_member_tvars commons))
+ (list#composite class_tvars (the #import_member_tvars commons))
{#MethodDecl [commons _]}
- (case (value@ #import_member_kind commons)
+ (case (the #import_member_kind commons)
{#StaticIMK}
- (value@ #import_member_tvars commons)
+ (the #import_member_tvars commons)
_
- (list#composite class_tvars (value@ #import_member_tvars commons)))
+ (list#composite class_tvars (the #import_member_tvars commons)))
_
class_tvars))
@@ -1354,7 +1354,7 @@
.let [input_jvm_types (list#each product.right #import_member_args)
arg_types (list#each (: (-> [Bit (Type Value)] Code)
(function (_ [maybe? arg])
- (let [arg_type (value_type (value@ #import_member_mode commons) arg)]
+ (let [arg_type (value_type (the #import_member_mode commons) arg)]
(if maybe?
(` (Maybe (~ arg_type)))
arg_type))))
@@ -1372,7 +1372,7 @@
(dictionary.key? ..boxes unboxed))
return_term
- (value@ #import_member_maybe? commons)
+ (the #import_member_maybe? commons)
(` (??? (~ return_term)))
... else
@@ -1391,7 +1391,7 @@
(-> Import_Member_Declaration Code Code)
(case member
(^or {#ConstructorDecl [commons _]} {#MethodDecl [commons _]})
- (if (value@ <tag> commons)
+ (if (the <tag> commons)
<term_trans>
return_term)
@@ -1515,16 +1515,16 @@
{#ConstructorDecl [commons _]}
(do meta.monad
[.let [classT (jvm.class full_name (list))
- def_name (code.symbol ["" (..import_name import_format method_prefix (value@ #import_member_alias commons))])
+ def_name (code.symbol ["" (..import_name import_format method_prefix (the #import_member_alias commons))])
jvm_interop (|> [classT
(` ("jvm member invoke constructor"
[(~+ (list#each ..var$ class_tvars))]
(~ (code.text full_name))
- [(~+ (list#each ..var$ (value@ #import_member_tvars commons)))]
- (~+ (|> (jvm_invoke_inputs (value@ #import_member_mode commons) input_jvm_types arg_function_inputs)
+ [(~+ (list#each ..var$ (the #import_member_tvars commons)))]
+ (~+ (|> (jvm_invoke_inputs (the #import_member_mode commons) input_jvm_types arg_function_inputs)
(list.zipped/2 input_jvm_types)
(list#each ..decorate_input)))))]
- (with_automatic_output_conversion (value@ #import_member_mode commons))
+ (with_automatic_output_conversion (the #import_member_mode commons))
(with_return_maybe member true classT)
(with_return_try member)
(with_return_io member))]]
@@ -1534,7 +1534,7 @@
{#MethodDecl [commons method]}
(with_symbols [g!obj]
(do meta.monad
- [.let [def_name (code.symbol ["" (..import_name import_format method_prefix (value@ #import_member_alias commons))])
+ [.let [def_name (code.symbol ["" (..import_name import_format method_prefix (the #import_member_alias commons))])
(^open "[0]") commons
(^open "[0]") method
[jvm_op object_ast] (: [Text (List Code)]
@@ -1553,18 +1553,18 @@
["jvm member invoke interface"
(list g!obj)]
)))
- method_return (value@ #import_method_return method)
+ method_return (the #import_method_return method)
callC (: Code
(` ((~ (code.text jvm_op))
[(~+ (list#each ..var$ class_tvars))]
(~ (code.text full_name))
(~ (code.text #import_method_name))
- [(~+ (list#each ..var$ (value@ #import_member_tvars commons)))]
+ [(~+ (list#each ..var$ (the #import_member_tvars commons)))]
(~+ (|> object_ast
(list#each ..un_quoted)
(list.zipped/2 (list (jvm.class full_name (list))))
- (list#each (with_automatic_input_conversion (value@ #import_member_mode commons)))))
- (~+ (|> (jvm_invoke_inputs (value@ #import_member_mode commons) input_jvm_types arg_function_inputs)
+ (list#each (with_automatic_input_conversion (the #import_member_mode commons)))))
+ (~+ (|> (jvm_invoke_inputs (the #import_member_mode commons) input_jvm_types arg_function_inputs)
(list.zipped/2 input_jvm_types)
(list#each ..decorate_input))))))
jvm_interop (: Code
@@ -1572,7 +1572,7 @@
{.#Left method_return}
(|> [method_return
callC]
- (with_automatic_output_conversion (value@ #import_member_mode commons))
+ (with_automatic_output_conversion (the #import_member_mode commons))
(with_return_maybe member false method_return)
(with_return_try member)
(with_return_io member))
diff --git a/stdlib/source/library/lux/ffi.lux b/stdlib/source/library/lux/ffi.lux
index 7d1f709a4..7a1debe9c 100644
--- a/stdlib/source/library/lux/ffi.lux
+++ b/stdlib/source/library/lux/ffi.lux
@@ -171,7 +171,7 @@
(def: constructor
(Parser Constructor)
(<| <code>.form
- (..generalized (with@ [#anonymous #variables]))
+ (..generalized (has [#anonymous #variables]))
(<>.after (<code>.this! (' new)))
(..anonymous ..input)))
@@ -212,7 +212,7 @@
(def: procedure
(Parser (Named Procedure))
- (<| (..generalized (with@ [#anonymous #input #variables]))
+ (<| (..generalized (has [#anonymous #input #variables]))
..named
($_ <>.and
..input
@@ -255,9 +255,9 @@
(def: (output_type it)
(-> Optional Code)
- (if (value@ #optional? it)
- (` (.Maybe (~ (value@ #mandatory it))))
- (value@ #mandatory it)))
+ (if (the #optional? it)
+ (` (.Maybe (~ (the #mandatory it))))
+ (the #mandatory it)))
(`` (template [<lux_it> <host_it>
<lux_?> <host_?>]
@@ -273,19 +273,19 @@
(as_is (def: g!it' (' g!it))
(def: (host_optional it)
(-> Optional Code)
- (.if (.value@ #optional? it)
- (` (.case (~ (value@ #mandatory it))
+ (.if (.the #optional? it)
+ (` (.case (~ (the #mandatory it))
{.#Some (~ g!it')}
(~ g!it')
{.#None}
(<host_it>)))
- (value@ #mandatory it)))
+ (the #mandatory it)))
(def: (lux_optional it output)
(-> Optional Code Code)
(` (.let [(~ g!it') (~ output)]
- (~ (if (value@ #optional? it)
+ (~ (if (the #optional? it)
(` (.if (<host_?> (~ g!it'))
{.#None}
{.#Some (~ g!it')}))
@@ -342,32 +342,32 @@
(def: (input_type input :it:)
(-> Input Code Code)
- (let [:it: (if (value@ #try? input)
+ (let [:it: (if (the #try? input)
(` (.Either .Text (~ :it:)))
:it:)]
- (if (value@ #io? input)
+ (if (the #io? input)
(` ((~! io.IO) (~ :it:)))
:it:)))
(def: (input_term input term)
(-> Input Code Code)
- (let [term (if (value@ #try? input)
+ (let [term (if (the #try? input)
(` (.try (~ term)))
term)]
- (if (value@ #io? input)
+ (if (the #io? input)
(` ((~! io.io) (~ term)))
term)))
(def: (procedure_definition import! source it)
(-> (List Code) Code (Named Procedure) Code)
- (let [g!it (|> (value@ #alias it)
- (maybe.else (value@ #name it))
+ (let [g!it (|> (the #alias it)
+ (maybe.else (the #name it))
code.local_symbol)
- g!variables (list#each code.local_symbol (value@ [#anonymous #input #variables] it))
- input (value@ [#anonymous #input] it)
- :parameters: (value@ #parameters input)
+ g!variables (list#each code.local_symbol (the [#anonymous #input #variables] it))
+ input (the [#anonymous #input] it)
+ :parameters: (the #parameters input)
g!parameters (..parameters :parameters:)
- :output: (value@ [#anonymous #output] it)
+ :output: (the [#anonymous #output] it)
:input:/* (case :parameters:
{.#End}
(list (` []))
@@ -376,7 +376,7 @@
(list#each ..output_type :parameters:))]
(` (.def: ((~ g!it) (~+ (case g!parameters
{.#End} (list g!it)
- _ (list#each (value@ #mandatory) g!parameters))))
+ _ (list#each (the #mandatory) g!parameters))))
(.All ((~ g!it) (~+ g!variables))
(-> (~+ :input:/*)
(~ (|> :output:
@@ -418,37 +418,37 @@
(def: (global_definition import! it)
(-> (List Code) Global Code)
- (let [g!name (|> (value@ #alias it)
- (maybe.else (value@ #name it))
+ (let [g!name (|> (the #alias it)
+ (maybe.else (the #name it))
code.local_symbol)
- :output: (value@ #anonymous it)]
+ :output: (the #anonymous it)]
(` (.def: (~ g!name)
(~ (..output_type :output:))
(.exec
(~+ import!)
(.:expected
(~ (<| (lux_optional :output:)
- (` (<constant> (~ (code.text (..host_path (value@ #name it))))))))))))))
+ (` (<constant> (~ (code.text (..host_path (the #name it))))))))))))))
(for [@.lua (as_is)
@.ruby (as_is)]
(def: (constructor_definition [class_name class_parameters] alias namespace it)
(-> Declaration Alias Namespace Constructor Code)
(let [g!it (|> it
- (value@ #alias)
+ (the #alias)
(maybe.else "new")
(..namespaced namespace class_name alias)
code.local_symbol)
- input (value@ #anonymous it)
- g!input_variables (list#each code.local_symbol (value@ #variables input))
- :parameters: (value@ #parameters input)
+ input (the #anonymous it)
+ g!input_variables (list#each code.local_symbol (the #variables input))
+ :parameters: (the #parameters input)
g!parameters (..parameters :parameters:)
g!class_variables (list#each code.local_symbol class_parameters)
g!class (` ((~ (code.local_symbol (maybe.else class_name alias))) (~+ g!class_variables)))
:output: [#optional? false #mandatory g!class]]
(` (.def: ((~ g!it) (~+ (case g!parameters
{.#End} (list g!it)
- _ (list#each (value@ #mandatory) g!parameters))))
+ _ (list#each (the #mandatory) g!parameters))))
(.All ((~ g!it) (~+ g!class_variables) (~+ g!input_variables))
(.-> (~+ (list#each ..output_type :parameters:))
(~ (|> :output:
@@ -464,12 +464,12 @@
(def: (static_field_definition import! [class_name class_parameters] alias namespace it)
(-> (List Code) Declaration Alias Namespace (Named Output) Code)
- (let [field (value@ #name it)
- g!it (|> (value@ #alias it)
+ (let [field (the #name it)
+ g!it (|> (the #alias it)
(maybe.else field)
(..namespaced namespace class_name alias)
code.local_symbol)
- :field: (value@ #anonymous it)]
+ :field: (the #anonymous it)]
(` ((~! syntax:) ((~ g!it) [])
(.# (~! meta.monad) (~' in)
(.list (`' (.exec
@@ -483,13 +483,13 @@
(def: (virtual_field_definition [class_name class_parameters] alias namespace it)
(-> Declaration Alias Namespace (Named Output) Code)
- (let [name (value@ #name it)
- g!it (|> (value@ #alias it)
+ (let [name (the #name it)
+ g!it (|> (the #alias it)
(maybe.else name)
(..namespaced namespace class_name alias)
code.local_symbol)
path (%.format (..host_path class_name) "." name)
- :field: (value@ #anonymous it)
+ :field: (the #anonymous it)
g!variables (list#each code.local_symbol class_parameters)
g!class (` ((~ (code.local_symbol (maybe.else class_name alias))) (~+ g!variables)))]
(` (.def: ((~ g!it) (~ g!it))
@@ -502,18 +502,18 @@
(def: (field_definition import! class alias namespace it)
(-> (List Code) Declaration Alias Namespace Field Code)
- (if (value@ #static? it)
- (..static_field_definition import! class alias namespace (value@ #member it))
- (..virtual_field_definition class alias namespace (value@ #member it))))
+ (if (the #static? it)
+ (..static_field_definition import! class alias namespace (the #member it))
+ (..virtual_field_definition class alias namespace (the #member it))))
(def: (static_method_definition import! [class_name class_parameters] alias namespace it)
(-> (List Code) Declaration Alias Namespace (Named Procedure) Code)
- (let [method (value@ #name it)
- name (|> (value@ #alias it)
- (maybe.else (value@ #name it))
+ (let [method (the #name it)
+ name (|> (the #alias it)
+ (maybe.else (the #name it))
(..namespaced namespace class_name alias))]
(|> it
- (with@ #alias {.#Some name})
+ (has #alias {.#Some name})
(..procedure_definition import!
(for [@.js (` (<constant> (~ (code.text (%.format (..host_path class_name) "." method)))))
@.ruby (` (<constant> (~ (code.text (%.format (..host_path class_name) "::" method)))))]
@@ -523,20 +523,20 @@
(def: (virtual_method_definition [class_name class_parameters] alias namespace it)
(-> Declaration Alias Namespace (Named Procedure) Code)
- (let [method (value@ #name it)
- g!it (|> (value@ #alias it)
+ (let [method (the #name it)
+ g!it (|> (the #alias it)
(maybe.else method)
(..namespaced namespace class_name alias)
code.local_symbol)
- procedure (value@ #anonymous it)
- input (value@ #input procedure)
- g!input_variables (list#each code.local_symbol (value@ #variables input))
- :parameters: (value@ #parameters input)
+ procedure (the #anonymous it)
+ input (the #input procedure)
+ g!input_variables (list#each code.local_symbol (the #variables input))
+ :parameters: (the #parameters input)
g!parameters (..parameters :parameters:)
g!class_variables (list#each code.local_symbol class_parameters)
g!class (` ((~ (code.local_symbol (maybe.else class_name alias))) (~+ g!class_variables)))
- :output: (value@ #output procedure)]
- (` (.def: ((~ g!it) (~+ (list#each (value@ #mandatory) g!parameters)) (~ g!it))
+ :output: (the #output procedure)]
+ (` (.def: ((~ g!it) (~+ (list#each (the #mandatory) g!parameters)) (~ g!it))
(.All ((~ g!it) (~+ g!class_variables) (~+ g!input_variables))
(.-> (~+ (list#each ..output_type :parameters:))
(~ g!class)
@@ -552,9 +552,9 @@
(def: (method_definition import! class alias namespace it)
(-> (List Code) Declaration Alias Namespace Method Code)
- (if (value@ #static? it)
- (static_method_definition import! class alias namespace (value@ #member it))
- (virtual_method_definition class alias namespace (value@ #member it))))
+ (if (the #static? it)
+ (static_method_definition import! class alias namespace (the #member it))
+ (virtual_method_definition class alias namespace (the #member it))))
(syntax: .public (import: [host_module (<>.maybe <code>.text)
it ..import])
@@ -571,14 +571,14 @@
{#Procedure it}
(in (list (..procedure_definition host_module_import!
- (` (<constant> (~ (code.text (..host_path (value@ #name it))))))
+ (` (<constant> (~ (code.text (..host_path (the #name it))))))
it)))
{#Class it}
- (let [class (value@ #declaration it)
- alias (value@ #class_alias it)
+ (let [class (the #declaration it)
+ alias (the #class_alias it)
[class_name class_parameters] class
- namespace (value@ #namespace it)
+ namespace (the #namespace it)
g!class_variables (list#each code.local_symbol class_parameters)
declaration (` ((~ (code.local_symbol (maybe.else class_name alias)))
(~+ g!class_variables)))]
@@ -597,7 +597,7 @@
{#Method it}
(..method_definition host_module_import! class alias namespace it)))))
- (value@ #members it)))))
+ (the #members it)))))
)))
(for [@.ruby (as_is)]
diff --git a/stdlib/source/library/lux/ffi.old.lux b/stdlib/source/library/lux/ffi.old.lux
index 0a6acfa83..43a327049 100644
--- a/stdlib/source/library/lux/ffi.old.lux
+++ b/stdlib/source/library/lux/ffi.old.lux
@@ -1137,7 +1137,7 @@
.let [arg_decls' (: (List Text) (list#each (|>> product.right (simple_class$ (list)))
arg_decls))]]
(in (`' ((~ (code.text (format "jvm invokespecial"
- ":" (value@ #super_class_name super_class)
+ ":" (the #super_class_name super_class)
":" name
":" (text.interposed "," arg_decls'))))
(~' _jvm_this) (~+ args)))))))]
@@ -1330,15 +1330,15 @@
(-> (List Type_Parameter) Import_Member_Declaration (List Type_Parameter))
(case member
{#ConstructorDecl [commons _]}
- (list#composite class_tvars (value@ #import_member_tvars commons))
+ (list#composite class_tvars (the #import_member_tvars commons))
{#MethodDecl [commons _]}
- (case (value@ #import_member_kind commons)
+ (case (the #import_member_kind commons)
{#StaticIMK}
- (value@ #import_member_tvars commons)
+ (the #import_member_tvars commons)
_
- (list#composite class_tvars (value@ #import_member_tvars commons)))
+ (list#composite class_tvars (the #import_member_tvars commons)))
_
class_tvars))
@@ -1360,7 +1360,7 @@
#import_member_args))
arg_types (list#each (: (-> [Bit GenericType] Code)
(function (_ [maybe? arg])
- (let [arg_type (class_type (value@ #import_member_mode commons) type_params arg)]
+ (let [arg_type (class_type (the #import_member_mode commons) type_params arg)]
(if maybe?
(` (Maybe (~ arg_type)))
arg_type))))
@@ -1374,7 +1374,7 @@
(-> Class_Declaration Import_Member_Declaration Code Code)
(case member
(^or {#ConstructorDecl [commons _]} {#MethodDecl [commons _]})
- (if (value@ #import_member_maybe? commons)
+ (if (the #import_member_maybe? commons)
(` (??? (~ return_term)))
(let [g!temp (` ((~' ~') (~ (code.symbol ["" " Ω "]))))]
(` (let [(~ g!temp) (~ return_term)]
@@ -1382,8 +1382,8 @@
(~ g!temp))))
(~ g!temp)
(panic! (~ (code.text (format "Cannot produce null references from method calls @ "
- (value@ #class_name class)
- "." (value@ #import_member_alias commons))))))))))
+ (the #class_name class)
+ "." (the #import_member_alias commons))))))))))
_
return_term))
@@ -1393,7 +1393,7 @@
(-> Import_Member_Declaration Code Code)
(case member
(^or {#ConstructorDecl [commons _]} {#MethodDecl [commons _]})
- (if (value@ <tag> commons)
+ (if (the <tag> commons)
<term_trans>
return_term)
@@ -1485,10 +1485,10 @@
{#ConstructorDecl [commons _]}
(do meta.monad
- [.let [def_name (code.symbol ["" (..import_name import_format method_prefix (value@ #import_member_alias commons))])
+ [.let [def_name (code.symbol ["" (..import_name import_format method_prefix (the #import_member_alias commons))])
jvm_extension (code.text (format "jvm new" ":" full_name ":" (text.interposed "," arg_classes)))
jvm_interop (|> (` ((~ jvm_extension)
- (~+ (jvm_extension_inputs (value@ #import_member_mode commons) arg_classes arg_function_inputs))))
+ (~+ (jvm_extension_inputs (the #import_member_mode commons) arg_classes arg_function_inputs))))
(decorate_return_maybe class member)
(decorate_return_try member)
(decorate_return_io member))]]
@@ -1498,7 +1498,7 @@
{#MethodDecl [commons method]}
(with_symbols [g!obj]
(do meta.monad
- [.let [def_name (code.symbol ["" (..import_name import_format method_prefix (value@ #import_member_alias commons))])
+ [.let [def_name (code.symbol ["" (..import_name import_format method_prefix (the #import_member_alias commons))])
(^open "[0]") commons
(^open "[0]") method
[jvm_op object_ast] (: [Text (List Code)]
@@ -1518,10 +1518,10 @@
(list g!obj)]
)))
jvm_extension (code.text (format "jvm " jvm_op ":" full_name ":" #import_method_name ":" (text.interposed "," arg_classes)))
- jvm_interop (|> [(simple_class$ (list) (value@ #import_method_return method))
+ jvm_interop (|> [(simple_class$ (list) (the #import_method_return method))
(` ((~ jvm_extension) (~+ (list#each un_quote object_ast))
- (~+ (jvm_extension_inputs (value@ #import_member_mode commons) arg_classes arg_function_inputs))))]
- (auto_convert_output (value@ #import_member_mode commons))
+ (~+ (jvm_extension_inputs (the #import_member_mode commons) arg_classes arg_function_inputs))))]
+ (auto_convert_output (the #import_member_mode commons))
(decorate_return_maybe class member)
(decorate_return_try member)
(decorate_return_io member))]]
diff --git a/stdlib/source/library/lux/locale/language.lux b/stdlib/source/library/lux/locale/language.lux
index 6074d9dde..50604e065 100644
--- a/stdlib/source/library/lux/locale/language.lux
+++ b/stdlib/source/library/lux/locale/language.lux
@@ -1,15 +1,15 @@
(.using
- [library
- [lux "*"
- [abstract
- [equivalence {"+" Equivalence}]
- [hash {"+" Hash}]]
- [data
- ["[0]" text]]
- [type
- abstract]
- [macro
- ["[0]" template]]]])
+ [library
+ [lux "*"
+ [abstract
+ [equivalence {"+" Equivalence}]
+ [hash {"+" Hash}]]
+ [data
+ ["[0]" text]]
+ [type
+ abstract]
+ [macro
+ ["[0]" template]]]])
... https://en.wikipedia.org/wiki/List_of_ISO_639-2_codes
(abstract: .public Language
@@ -20,7 +20,7 @@
(template [<name> <tag>]
[(def: .public <name>
(-> Language Text)
- (|>> :representation (value@ <tag>)))]
+ (|>> :representation (the <tag>)))]
[name #name]
[code #code]
diff --git a/stdlib/source/library/lux/locale/territory.lux b/stdlib/source/library/lux/locale/territory.lux
index 14a1df61a..8df6f861d 100644
--- a/stdlib/source/library/lux/locale/territory.lux
+++ b/stdlib/source/library/lux/locale/territory.lux
@@ -1,15 +1,15 @@
(.using
- [library
- [lux "*"
- [abstract
- [equivalence {"+" Equivalence}]
- [hash {"+" Hash}]]
- [data
- ["[0]" text]]
- [type
- abstract]
- [macro
- ["[0]" template]]]])
+ [library
+ [lux "*"
+ [abstract
+ [equivalence {"+" Equivalence}]
+ [hash {"+" Hash}]]
+ [data
+ ["[0]" text]]
+ [type
+ abstract]
+ [macro
+ ["[0]" template]]]])
... https://en.wikipedia.org/wiki/ISO_3166-1
(abstract: .public Territory
@@ -23,7 +23,7 @@
[(def: .public <name>
(-> Territory <type>)
(|>> :representation
- (value@ <field>)))]
+ (the <field>)))]
[name #name Text]
[short_code #short Text]
@@ -308,6 +308,6 @@
(def: hash
(|>> :representation
- (value@ #long)
+ (the #long)
(# text.hash hash))))
)
diff --git a/stdlib/source/library/lux/macro/local.lux b/stdlib/source/library/lux/macro/local.lux
index 55495bc08..a01e438de 100644
--- a/stdlib/source/library/lux/macro/local.lux
+++ b/stdlib/source/library/lux/macro/local.lux
@@ -1,21 +1,21 @@
(.using
- [library
- [lux "*"
- ["[0]" meta]
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- ["[0]" try {"+" Try}]
- ["[0]" exception {"+" exception:}]]
- [data
- ["[0]" product]
- ["[0]" text]
- [collection
- ["[0]" list ("[1]#[0]" functor)]
- [dictionary
- ["[0]" plist {"+" PList}]]]]]]
- ["[0]" //
- ["[1][0]" code]])
+ [library
+ [lux "*"
+ ["[0]" meta]
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ ["[0]" try {"+" Try}]
+ ["[0]" exception {"+" exception:}]]
+ [data
+ ["[0]" product]
+ ["[0]" text]
+ [collection
+ ["[0]" list ("[1]#[0]" functor)]
+ [dictionary
+ ["[0]" plist {"+" PList}]]]]]]
+ ["[0]" //
+ ["[1][0]" code]])
(exception: .public (unknown_module [module Text])
(exception.report
@@ -35,11 +35,11 @@
(def: (with_module name body)
(All (_ a) (-> Text (-> Module (Try [Module a])) (Meta a)))
(function (_ compiler)
- (case (|> compiler (value@ .#modules) (plist.value name))
+ (case (|> compiler (the .#modules) (plist.value name))
{.#Some module}
(case (body module)
{try.#Success [module' output]}
- {try.#Success [(revised@ .#modules (plist.has name module') compiler)
+ {try.#Success [(revised .#modules (plist.has name module') compiler)
output]}
{try.#Failure error}
@@ -57,9 +57,9 @@
(plist.has definition_name definition))]]
(..with_module module_name
(function (_ module)
- (case (|> module (value@ .#definitions) (plist.value definition_name))
+ (case (|> module (the .#definitions) (plist.value definition_name))
{.#None}
- {try.#Success [(revised@ .#definitions add_macro! module)
+ {try.#Success [(revised .#definitions add_macro! module)
[]]}
{.#Some _}
@@ -73,9 +73,9 @@
(plist.lacks definition_name))]]
(..with_module module_name
(function (_ module)
- (case (|> module (value@ .#definitions) (plist.value definition_name))
+ (case (|> module (the .#definitions) (plist.value definition_name))
{.#Some _}
- {try.#Success [(revised@ .#definitions lacks_macro! module)
+ {try.#Success [(revised .#definitions lacks_macro! module)
[]]}
{.#None}
@@ -89,7 +89,7 @@
[_ (monad.each ! ..pop_one macros)
_ (..pop_one self)
compiler meta.compiler_state]
- (in (case (value@ .#expected compiler)
+ (in (case (the .#expected compiler)
{.#Some _}
(list (' []))
diff --git a/stdlib/source/library/lux/macro/syntax/declaration.lux b/stdlib/source/library/lux/macro/syntax/declaration.lux
index ee4e68150..d817fa193 100644
--- a/stdlib/source/library/lux/macro/syntax/declaration.lux
+++ b/stdlib/source/library/lux/macro/syntax/declaration.lux
@@ -1,18 +1,18 @@
(.using
- [library
- [lux "*"
- [abstract
- [equivalence {"+" Equivalence}]]
- [control
- ["<>" parser ("[1]#[0]" monad)
- ["<[0]>" code {"+" Parser}]]]
- [data
- ["[0]" product]
- ["[0]" text]
- [collection
- ["[0]" list ("[1]#[0]" functor)]]]
- [macro
- ["[0]" code]]]])
+ [library
+ [lux "*"
+ [abstract
+ [equivalence {"+" Equivalence}]]
+ [control
+ ["<>" parser ("[1]#[0]" monad)
+ ["<[0]>" code {"+" Parser}]]]
+ [data
+ ["[0]" product]
+ ["[0]" text]
+ [collection
+ ["[0]" list ("[1]#[0]" functor)]]]
+ [macro
+ ["[0]" code]]]])
(type: .public Declaration
(Record
@@ -35,8 +35,8 @@
(def: .public (format value)
(-> Declaration Code)
- (let [g!name (code.local_symbol (value@ #name value))]
- (case (value@ #arguments value)
+ (let [g!name (code.local_symbol (the #name value))]
+ (case (the #arguments value)
{.#End}
g!name
diff --git a/stdlib/source/library/lux/macro/syntax/definition.lux b/stdlib/source/library/lux/macro/syntax/definition.lux
index d35d48d9b..6d84be918 100644
--- a/stdlib/source/library/lux/macro/syntax/definition.lux
+++ b/stdlib/source/library/lux/macro/syntax/definition.lux
@@ -1,27 +1,27 @@
(.using
- [library
- [lux {"-" Definition}
- [abstract
- [equivalence {"+" Equivalence}]
- [monad {"+" do}]]
- [control
- ["[0]" exception {"+" exception:}]
- ["<>" parser
- ["<[0]>" code {"+" Parser}]]]
- [data
- ["[0]" sum]
- ["[0]" product]
- ["[0]" bit]
- ["[0]" text
- ["%" format]]
- [collection
- ["[0]" list]]]
- ["[0]" macro
- ["[0]" code]]
- ["[0]" meta
- ["[0]" location]]]]
- ["[0]" //
- ["[1][0]" check {"+" Check}]])
+ [library
+ [lux {"-" Definition}
+ [abstract
+ [equivalence {"+" Equivalence}]
+ [monad {"+" do}]]
+ [control
+ ["[0]" exception {"+" exception:}]
+ ["<>" parser
+ ["<[0]>" code {"+" Parser}]]]
+ [data
+ ["[0]" sum]
+ ["[0]" product]
+ ["[0]" bit]
+ ["[0]" text
+ ["%" format]]
+ [collection
+ ["[0]" list]]]
+ ["[0]" macro
+ ["[0]" code]]
+ ["[0]" meta
+ ["[0]" location]]]]
+ ["[0]" //
+ ["[1][0]" check {"+" Check}]])
(type: .public Definition
(Record
@@ -46,9 +46,9 @@
(def: dummy
Code
- (` [.#module (~ (code.text (value@ .#module location.dummy)))
- .#line (~ (code.nat (value@ .#line location.dummy)))
- .#column (~ (code.nat (value@ .#column location.dummy)))]))
+ (` [.#module (~ (code.text (the .#module location.dummy)))
+ .#line (~ (code.nat (the .#line location.dummy)))
+ .#column (~ (code.nat (the .#column location.dummy)))]))
(def: .public (format (^open "_[0]"))
(-> Definition Code)
@@ -88,7 +88,7 @@
(-> Lux (Parser Definition))
(do <>.monad
[definition (..parser compiler)
- _ (case (value@ #value definition)
+ _ (case (the #value definition)
{.#Left _}
(in [])
diff --git a/stdlib/source/library/lux/macro/syntax/input.lux b/stdlib/source/library/lux/macro/syntax/input.lux
index 2b59fce16..6d7d8c357 100644
--- a/stdlib/source/library/lux/macro/syntax/input.lux
+++ b/stdlib/source/library/lux/macro/syntax/input.lux
@@ -1,17 +1,17 @@
(.using
- [library
- [lux "*"
- [abstract
- [equivalence {"+" Equivalence}]]
- [control
- ["<>" parser
- ["<[0]>" code {"+" Parser}]]]
- [data
- ["[0]" product]
- [collection
- ["[0]" list ("[1]#[0]" monad)]]]
- [macro
- ["[0]" code]]]])
+ [library
+ [lux "*"
+ [abstract
+ [equivalence {"+" Equivalence}]]
+ [control
+ ["<>" parser
+ ["<[0]>" code {"+" Parser}]]]
+ [data
+ ["[0]" product]
+ [collection
+ ["[0]" list ("[1]#[0]" monad)]]]
+ [macro
+ ["[0]" code]]]])
(type: .public Input
(Record
@@ -28,8 +28,8 @@
(def: .public format
(-> (List Input) Code)
(|>> (list#each (function (_ value)
- (list (value@ #binding value)
- (value@ #type value))))
+ (list (the #binding value)
+ (the #type value))))
list#conjoint
code.tuple))
diff --git a/stdlib/source/library/lux/macro/template.lux b/stdlib/source/library/lux/macro/template.lux
index 57373d640..9e5db759a 100644
--- a/stdlib/source/library/lux/macro/template.lux
+++ b/stdlib/source/library/lux/macro/template.lux
@@ -1,30 +1,30 @@
(.using
- [library
- [lux {"-" let local macro symbol}
- ["[0]" meta]
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- ["[0]" try {"+" Try}]
- ["[0]" exception {"+" exception:}]
- ["<>" parser ("[1]#[0]" functor)
- ["<[0]>" code {"+" Parser}]]]
- [data
- ["[0]" bit ("[1]#[0]" codec)]
- ["[0]" text]
- [collection
- ["[0]" list ("[1]#[0]" monad)]
- ["[0]" dictionary {"+" Dictionary}]]]
- [math
- [number
- ["[0]" nat ("[1]#[0]" decimal)]
- ["[0]" int ("[1]#[0]" decimal)]
- ["[0]" rev ("[1]#[0]" decimal)]
- ["[0]" frac ("[1]#[0]" decimal)]]]]]
- ["[0]" //
- [syntax {"+" syntax:}]
- ["[0]" code]
- ["[0]" local]])
+ [library
+ [lux {"-" let local macro symbol}
+ ["[0]" meta]
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ ["[0]" try {"+" Try}]
+ ["[0]" exception {"+" exception:}]
+ ["<>" parser ("[1]#[0]" functor)
+ ["<[0]>" code {"+" Parser}]]]
+ [data
+ ["[0]" bit ("[1]#[0]" codec)]
+ ["[0]" text]
+ [collection
+ ["[0]" list ("[1]#[0]" monad)]
+ ["[0]" dictionary {"+" Dictionary}]]]
+ [math
+ [number
+ ["[0]" nat ("[1]#[0]" decimal)]
+ ["[0]" int ("[1]#[0]" decimal)]
+ ["[0]" rev ("[1]#[0]" decimal)]
+ ["[0]" frac ("[1]#[0]" decimal)]]]]]
+ ["[0]" //
+ [syntax {"+" syntax:}]
+ ["[0]" code]
+ ["[0]" local]])
(syntax: .public (spliced [parts (<code>.tuple (<>.some <code>.any))])
(in parts))
@@ -156,14 +156,14 @@
[here_name meta.current_module_name
expression? (: (Meta Bit)
(function (_ lux)
- {try.#Success [lux (case (value@ .#expected lux)
+ {try.#Success [lux (case (the .#expected lux)
{.#None}
false
{.#Some _}
true)]}))
g!pop (local.push (list#each (function (_ local)
- [[here_name (value@ #name local)]
+ [[here_name (the #name local)]
(..macro local)])
locals))]
(if expression?
diff --git a/stdlib/source/library/lux/math/number/complex.lux b/stdlib/source/library/lux/math/number/complex.lux
index 636a77838..b1c14d1bb 100644
--- a/stdlib/source/library/lux/math/number/complex.lux
+++ b/stdlib/source/library/lux/math/number/complex.lux
@@ -1,26 +1,26 @@
(.using
- [library
- [lux "*"
- ["[0]" math]
- [abstract
- [equivalence {"+" Equivalence}]
- [codec {"+" Codec}]
- ["M" monad {"+" Monad do}]]
- [control
- ["[0]" maybe]
- ["<>" parser
- ["<[0]>" code {"+" Parser}]]]
- [data
- [collection
- ["[0]" list ("[1]#[0]" functor)]]]
- [macro
- [syntax {"+" syntax:}]
- ["[0]" code]]
- [math
- [number
- ["n" nat]
- ["f" frac]
- ["[0]" int]]]]])
+ [library
+ [lux "*"
+ ["[0]" math]
+ [abstract
+ [equivalence {"+" Equivalence}]
+ [codec {"+" Codec}]
+ ["M" monad {"+" Monad do}]]
+ [control
+ ["[0]" maybe]
+ ["<>" parser
+ ["<[0]>" code {"+" Parser}]]]
+ [data
+ [collection
+ ["[0]" list ("[1]#[0]" functor)]]]
+ [macro
+ [syntax {"+" syntax:}]
+ ["[0]" code]]
+ [math
+ [number
+ ["n" nat]
+ ["f" frac]
+ ["[0]" int]]]]])
(type: .public Complex
(Record
@@ -50,23 +50,23 @@
(def: .public (not_a_number? complex)
(-> Complex Bit)
- (or (f.not_a_number? (value@ #real complex))
- (f.not_a_number? (value@ #imaginary complex))))
+ (or (f.not_a_number? (the #real complex))
+ (f.not_a_number? (the #imaginary complex))))
(def: .public (= param input)
(-> Complex Complex Bit)
- (and (f.= (value@ #real param)
- (value@ #real input))
- (f.= (value@ #imaginary param)
- (value@ #imaginary input))))
+ (and (f.= (the #real param)
+ (the #real input))
+ (f.= (the #imaginary param)
+ (the #imaginary input))))
(template [<name> <op>]
[(def: .public (<name> param input)
(-> Complex Complex Complex)
- [#real (<op> (value@ #real param)
- (value@ #real input))
- #imaginary (<op> (value@ #imaginary param)
- (value@ #imaginary input))])]
+ [#real (<op> (the #real param)
+ (the #real input))
+ #imaginary (<op> (the #imaginary param)
+ (the #imaginary input))])]
[+ f.+]
[- f.-]
@@ -80,8 +80,8 @@
(template [<name> <transform>]
[(def: .public <name>
(-> Complex Complex)
- (|>> (revised@ #real <transform>)
- (revised@ #imaginary <transform>)))]
+ (|>> (revised #real <transform>)
+ (revised #imaginary <transform>)))]
[opposite f.opposite]
[signum f.signum]
@@ -89,25 +89,25 @@
(def: .public conjugate
(-> Complex Complex)
- (revised@ #imaginary f.opposite))
+ (revised #imaginary f.opposite))
(def: .public (*' param input)
(-> Frac Complex Complex)
[#real (f.* param
- (value@ #real input))
+ (the #real input))
#imaginary (f.* param
- (value@ #imaginary input))])
+ (the #imaginary input))])
(def: .public (* param input)
(-> Complex Complex Complex)
- [#real (f.- (f.* (value@ #imaginary param)
- (value@ #imaginary input))
- (f.* (value@ #real param)
- (value@ #real input)))
- #imaginary (f.+ (f.* (value@ #real param)
- (value@ #imaginary input))
- (f.* (value@ #imaginary param)
- (value@ #real input)))])
+ [#real (f.- (f.* (the #imaginary param)
+ (the #imaginary input))
+ (f.* (the #real param)
+ (the #real input)))
+ #imaginary (f.+ (f.* (the #real param)
+ (the #imaginary input))
+ (f.* (the #imaginary param)
+ (the #real input)))])
(def: .public (/ param input)
(-> Complex Complex Complex)
@@ -116,12 +116,12 @@
(f.abs #real))
(let [quot (f./ #imaginary #real)
denom (|> #real (f.* quot) (f.+ #imaginary))]
- [..#real (|> (value@ ..#real input) (f.* quot) (f.+ (value@ ..#imaginary input)) (f./ denom))
- ..#imaginary (|> (value@ ..#imaginary input) (f.* quot) (f.- (value@ ..#real input)) (f./ denom))])
+ [..#real (|> (the ..#real input) (f.* quot) (f.+ (the ..#imaginary input)) (f./ denom))
+ ..#imaginary (|> (the ..#imaginary input) (f.* quot) (f.- (the ..#real input)) (f./ denom))])
(let [quot (f./ #real #imaginary)
denom (|> #imaginary (f.* quot) (f.+ #real))]
- [..#real (|> (value@ ..#imaginary input) (f.* quot) (f.+ (value@ ..#real input)) (f./ denom))
- ..#imaginary (|> (value@ ..#imaginary input) (f.- (f.* quot (value@ ..#real input))) (f./ denom))]))))
+ [..#real (|> (the ..#imaginary input) (f.* quot) (f.+ (the ..#real input)) (f./ denom))
+ ..#imaginary (|> (the ..#imaginary input) (f.- (f.* quot (the ..#real input))) (f./ denom))]))))
(def: .public (/' param subject)
(-> Frac Complex Complex)
@@ -133,8 +133,8 @@
(-> Complex Complex Complex)
(let [scaled (/ param input)
quotient (|> scaled
- (revised@ #real math.floor)
- (revised@ #imaginary math.floor))]
+ (revised #real math.floor)
+ (revised #imaginary math.floor))]
(- (* quotient param)
input)))
@@ -311,8 +311,8 @@
(def: .public (approximately? margin_of_error standard value)
(-> Frac Complex Complex Bit)
(and (f.approximately? margin_of_error
- (value@ ..#real standard)
- (value@ ..#real value))
+ (the ..#real standard)
+ (the ..#real value))
(f.approximately? margin_of_error
- (value@ ..#imaginary standard)
- (value@ ..#imaginary value))))
+ (the ..#imaginary standard)
+ (the ..#imaginary value))))
diff --git a/stdlib/source/library/lux/math/number/ratio.lux b/stdlib/source/library/lux/math/number/ratio.lux
index b1cd62a3c..93bdca39e 100644
--- a/stdlib/source/library/lux/math/number/ratio.lux
+++ b/stdlib/source/library/lux/math/number/ratio.lux
@@ -1,26 +1,26 @@
(.using
- [library
- [lux {"-" nat}
- [abstract
- [equivalence {"+" Equivalence}]
- [order {"+" Order}]
- [monoid {"+" Monoid}]
- [codec {"+" Codec}]
- [monad {"+" do}]]
- [control
- ["[0]" function]
- ["[0]" maybe]
- ["[0]" try]
- ["<>" parser
- ["<[0]>" code {"+" Parser}]]]
- [data
- ["[0]" product]
- ["[0]" text ("[1]#[0]" monoid)]]
- [macro
- [syntax {"+" syntax:}]
- ["[0]" code]]]]
- [//
- ["n" nat ("[1]#[0]" decimal)]])
+ [library
+ [lux {"-" nat}
+ [abstract
+ [equivalence {"+" Equivalence}]
+ [order {"+" Order}]
+ [monoid {"+" Monoid}]
+ [codec {"+" Codec}]
+ [monad {"+" do}]]
+ [control
+ ["[0]" function]
+ ["[0]" maybe]
+ ["[0]" try]
+ ["<>" parser
+ ["<[0]>" code {"+" Parser}]]]
+ [data
+ ["[0]" product]
+ ["[0]" text ("[1]#[0]" monoid)]]
+ [macro
+ [syntax {"+" syntax:}]
+ ["[0]" code]]]]
+ [//
+ ["n" nat ("[1]#[0]" decimal)]])
(type: .public Ratio
(Record
@@ -29,8 +29,8 @@
(def: .public (nat value)
(-> Ratio (Maybe Nat))
- (case (value@ #denominator value)
- 1 {.#Some (value@ #numerator value)}
+ (case (the #denominator value)
+ 1 {.#Some (the #numerator value)}
_ {.#None}))
(def: (normal (^open "_[0]"))
@@ -46,10 +46,10 @@
(def: .public (= parameter subject)
(-> Ratio Ratio Bit)
- (and (n.= (value@ #numerator parameter)
- (value@ #numerator subject))
- (n.= (value@ #denominator parameter)
- (value@ #denominator subject))))
+ (and (n.= (the #numerator parameter)
+ (the #numerator subject))
+ (n.= (the #denominator parameter)
+ (the #denominator subject))))
(implementation: .public equivalence
(Equivalence Ratio)
@@ -58,10 +58,10 @@
(def: (equalized parameter subject)
(-> Ratio Ratio [Nat Nat])
- [(n.* (value@ #denominator subject)
- (value@ #numerator parameter))
- (n.* (value@ #denominator parameter)
- (value@ #numerator subject))])
+ [(n.* (the #denominator subject)
+ (the #numerator parameter))
+ (n.* (the #denominator parameter)
+ (the #numerator subject))])
(def: .public (< parameter subject)
(-> Ratio Ratio Bit)
@@ -92,22 +92,22 @@
(-> Ratio Ratio Ratio)
(let [[parameter' subject'] (..equalized parameter subject)]
(normal [(n.+ parameter' subject')
- (n.* (value@ #denominator parameter)
- (value@ #denominator subject))])))
+ (n.* (the #denominator parameter)
+ (the #denominator subject))])))
(def: .public (- parameter subject)
(-> Ratio Ratio Ratio)
(let [[parameter' subject'] (..equalized parameter subject)]
(normal [(n.- parameter' subject')
- (n.* (value@ #denominator parameter)
- (value@ #denominator subject))])))
+ (n.* (the #denominator parameter)
+ (the #denominator subject))])))
(def: .public (* parameter subject)
(-> Ratio Ratio Ratio)
- (normal [(n.* (value@ #numerator parameter)
- (value@ #numerator subject))
- (n.* (value@ #denominator parameter)
- (value@ #denominator subject))]))
+ (normal [(n.* (the #numerator parameter)
+ (the #numerator subject))
+ (n.* (the #denominator parameter)
+ (the #denominator subject))]))
(def: .public (/ parameter subject)
(-> Ratio Ratio Ratio)
@@ -118,7 +118,7 @@
(-> Ratio Ratio Ratio)
(let [[parameter' subject'] (..equalized parameter subject)
quot (n./ parameter' subject')]
- (..- (revised@ #numerator (n.* quot) parameter)
+ (..- (revised #numerator (n.* quot) parameter)
subject)))
(def: .public (reciprocal (^open "_[0]"))
diff --git a/stdlib/source/library/lux/meta.lux b/stdlib/source/library/lux/meta.lux
index 8bf80bce5..5f6dad623 100644
--- a/stdlib/source/library/lux/meta.lux
+++ b/stdlib/source/library/lux/meta.lux
@@ -112,12 +112,12 @@
(All (_ a)
(-> Text (Meta a)))
(function (_ state)
- {try.#Failure (location.with (value@ .#location state) error)}))
+ {try.#Failure (location.with (the .#location state) error)}))
(def: .public (module name)
(-> Text (Meta Module))
(function (_ lux)
- (case (plist.value name (value@ .#modules lux))
+ (case (plist.value name (the .#modules lux))
{.#Some module}
{try.#Success [lux module]}
@@ -127,7 +127,7 @@
(def: .public current_module_name
(Meta Text)
(function (_ lux)
- (case (value@ .#current_module lux)
+ (case (the .#current_module lux)
{.#Some current_module}
{try.#Success [lux current_module]}
@@ -173,7 +173,7 @@
{.#None}
{try.#Success [_ this_module]}
- (let [modules (value@ .#modules lux)]
+ (let [modules (the .#modules lux)]
(loop [module module
name name]
(do maybe.monad
@@ -181,7 +181,7 @@
definition (: (Maybe Global)
(|> $module
(: Module)
- (value@ .#definitions)
+ (the .#definitions)
(plist.value name)))]
(case definition
{.#Alias [r_module r_name]}
@@ -204,13 +204,13 @@
(def: .public seed
(Meta Nat)
(function (_ lux)
- {try.#Success [(revised@ .#seed ++ lux)
- (value@ .#seed lux)]}))
+ {try.#Success [(revised .#seed ++ lux)
+ (the .#seed lux)]}))
(def: .public (module_exists? module)
(-> Text (Meta Bit))
(function (_ lux)
- {try.#Success [lux (case (plist.value module (value@ .#modules lux))
+ {try.#Success [lux (case (plist.value module (the .#modules lux))
{.#Some _}
#1
@@ -241,7 +241,7 @@
{.#Var var}
(function (_ lux)
(case (|> lux
- (value@ [.#type_context .#var_bindings])
+ (the [.#type_context .#var_bindings])
(type_variable var))
(^or {.#None} {.#Some {.#Var _}})
{try.#Success [lux type]}
@@ -260,15 +260,15 @@
(case (do maybe.monad
[scope (list.example (function (_ env)
(or (list.any? test (: (List [Text [Type Any]])
- (value@ [.#locals .#mappings] env)))
+ (the [.#locals .#mappings] env)))
(list.any? test (: (List [Text [Type Any]])
- (value@ [.#captured .#mappings] env)))))
- (value@ .#scopes lux))
+ (the [.#captured .#mappings] env)))))
+ (the .#scopes lux))
[_ [type _]] (on_either (list.example test)
(: (List [Text [Type Any]])
- (value@ [.#locals .#mappings] scope))
+ (the [.#locals .#mappings] scope))
(: (List [Text [Type Any]])
- (value@ [.#captured .#mappings] scope)))]
+ (the [.#captured .#mappings] scope)))]
(in type))
{.#Some var_type}
((clean_type var_type) lux)
@@ -301,28 +301,28 @@
(case (: (Maybe Global)
(do maybe.monad
[(^open "[0]") (|> lux
- (value@ .#modules)
+ (the .#modules)
(plist.value normal_module))]
(plist.value normal_short #definitions)))
{.#Some definition}
{try.#Success [lux definition]}
_
- (let [current_module (|> lux (value@ .#current_module) (maybe.else "???"))
+ (let [current_module (|> lux (the .#current_module) (maybe.else "???"))
all_known_modules (|> lux
- (value@ .#modules)
+ (the .#modules)
(list#each product.left)
..module_listing)]
{try.#Failure ($_ text#composite
"Unknown definition: " (symbol#encoded name) text.new_line
" Current module: " current_module text.new_line
- (case (plist.value current_module (value@ .#modules lux))
+ (case (plist.value current_module (the .#modules lux))
{.#Some this_module}
(let [candidates (|> lux
- (value@ .#modules)
+ (the .#modules)
(list#each (function (_ [module_name module])
(|> module
- (value@ .#definitions)
+ (the .#definitions)
(list.all (function (_ [def_name global])
(case global
(^or {.#Definition [exported? _]}
@@ -344,10 +344,10 @@
(list.sorted text#<)
(text.interposed ..listing_separator))
imports (|> this_module
- (value@ .#imports)
+ (the .#imports)
..module_listing)
aliases (|> this_module
- (value@ .#module_aliases)
+ (the .#module_aliases)
(list#each (function (_ [alias real]) ($_ text#composite alias " => " real)))
(list.sorted text#<)
(text.interposed ..listing_separator))]
@@ -454,12 +454,12 @@
(def: .public (globals module)
(-> Text (Meta (List [Text Global])))
(function (_ lux)
- (case (plist.value module (value@ .#modules lux))
+ (case (plist.value module (the .#modules lux))
{.#None}
{try.#Failure ($_ text#composite "Unknown module: " module)}
{.#Some module}
- {try.#Success [lux (value@ .#definitions module)]})))
+ {try.#Success [lux (the .#definitions module)]})))
(def: .public (definitions module)
(-> Text (Meta (List [Text Definition])))
@@ -496,7 +496,7 @@
(Meta (List [Text Module]))
(function (_ lux)
(|> lux
- (value@ .#modules)
+ (the .#modules)
[lux]
{try.#Success})))
@@ -505,7 +505,7 @@
(do ..monad
[.let [[module_name name] type_name]
module (..module module_name)]
- (case (plist.value name (value@ .#definitions module))
+ (case (plist.value name (the .#definitions module))
{.#Some {.#Type [exported? type labels]}}
(case labels
(^or {.#Left labels}
@@ -519,12 +519,12 @@
(def: .public location
(Meta Location)
(function (_ lux)
- {try.#Success [lux (value@ .#location lux)]}))
+ {try.#Success [lux (the .#location lux)]}))
(def: .public expected_type
(Meta Type)
(function (_ lux)
- (case (value@ .#expected lux)
+ (case (the .#expected lux)
{.#Some type}
{try.#Success [lux type]}
@@ -546,7 +546,7 @@
(def: .public (imported? import)
(-> Text (Meta Bit))
(# ..functor each
- (|>> (value@ .#imports) (list.any? (text#= import)))
+ (|>> (the .#imports) (list.any? (text#= import)))
..current_module))
(template [<name> <tag> <description>]
@@ -556,7 +556,7 @@
[.let [[module name] label_name]
=module (..module module)
this_module_name ..current_module_name]
- (case (plist.value name (value@ .#definitions =module))
+ (case (plist.value name (the .#definitions =module))
{.#Some {<tag> [exported? type group idx]}}
(if (or (text#= this_module_name module)
exported?)
@@ -593,18 +593,18 @@
_
{.#None}))
- (value@ .#definitions =module)))))
+ (the .#definitions =module)))))
(def: .public locals
(Meta (List (List [Text Type])))
(function (_ lux)
- (case (list.inits (value@ .#scopes lux))
+ (case (list.inits (the .#scopes lux))
{.#None}
{try.#Failure "No local environment"}
{.#Some scopes}
{try.#Success [lux
- (list#each (|>> (value@ [.#locals .#mappings])
+ (list#each (|>> (the [.#locals .#mappings])
(list#each (function (_ [name [type _]])
[name type])))
scopes)]})))
@@ -637,7 +637,7 @@
(def: .public type_context
(Meta Type_Context)
(function (_ lux)
- {try.#Success [lux (value@ .#type_context lux)]}))
+ {try.#Success [lux (the .#type_context lux)]}))
(def: .public (lifted result)
(All (_ a) (-> (Try a) (Meta a)))
@@ -651,7 +651,7 @@
(def: .public (eval type code)
(-> Type Code (Meta Any))
(do [! ..monad]
- [eval (# ! each (value@ .#eval)
+ [eval (# ! each (the .#eval)
..compiler_state)]
(eval type code)))
@@ -670,7 +670,7 @@
(Meta <type>)
(function (_ lux)
{try.#Success [lux
- (value@ [.#info <slot>] lux)]}))]
+ (the [.#info <slot>] lux)]}))]
[Text target .#target]
[Text version .#version]
diff --git a/stdlib/source/library/lux/meta/location.lux b/stdlib/source/library/lux/meta/location.lux
index 1c2908972..1080669a2 100644
--- a/stdlib/source/library/lux/meta/location.lux
+++ b/stdlib/source/library/lux/meta/location.lux
@@ -8,9 +8,9 @@
(Equivalence Location)
(def: (= reference subject)
- (and ("lux text =" (value@ .#module reference) (value@ .#module subject))
- ("lux i64 =" (value@ .#line reference) (value@ .#line subject))
- ("lux i64 =" (value@ .#column reference) (value@ .#column subject)))))
+ (and ("lux text =" (the .#module reference) (the .#module subject))
+ ("lux i64 =" (the .#line reference) (the .#line subject))
+ ("lux i64 =" (the .#column reference) (the .#column subject)))))
(def: .public dummy
Location
@@ -21,12 +21,12 @@
(macro: .public (here tokens compiler)
(case tokens
{.#End}
- (let [location (value@ .#location compiler)]
+ (let [location (the .#location compiler)]
{.#Right [compiler
(list (` (.: .Location
- [.#module (~ [..dummy {.#Text (value@ .#module location)}])
- .#line (~ [..dummy {.#Nat (value@ .#line location)}])
- .#column (~ [..dummy {.#Nat (value@ .#column location)}])])))]})
+ [.#module (~ [..dummy {.#Text (the .#module location)}])
+ .#line (~ [..dummy {.#Nat (the .#line location)}])
+ .#column (~ [..dummy {.#Nat (the .#column location)}])])))]})
_
{.#Left (`` (("lux in-module" (~~ (static .prelude_module)) wrong_syntax_error) (symbol ..here)))}))
diff --git a/stdlib/source/library/lux/target/js.lux b/stdlib/source/library/lux/target/js.lux
index 2e12d2c19..b3f54a375 100644
--- a/stdlib/source/library/lux/target/js.lux
+++ b/stdlib/source/library/lux/target/js.lux
@@ -1,6 +1,6 @@
(.using
[library
- [lux {"-" Location Code Label or and function if undefined for comment not int try ++ --}
+ [lux {"-" Location Code Label or and function if undefined for comment not int try ++ -- the}
[control
[pipe {"+" case>}]]
[data
diff --git a/stdlib/source/library/lux/target/jvm/attribute/code.lux b/stdlib/source/library/lux/target/jvm/attribute/code.lux
index 2526ae6bf..f7619a587 100644
--- a/stdlib/source/library/lux/target/jvm/attribute/code.lux
+++ b/stdlib/source/library/lux/target/jvm/attribute/code.lux
@@ -1,26 +1,26 @@
(.using
- [library
- [lux {"-" Code}
- [abstract
- [equivalence {"+" Equivalence}]]
- [data
- ["[0]" product]
- ["[0]" binary {"+" Binary}]
- [format
- ["[0]F" binary {"+" Writer} ("[1]#[0]" monoid)]]
- [collection
- ["[0]" sequence {"+" Sequence} ("[1]#[0]" functor mix)]]]
- [math
- [number
- ["n" nat]]]]]
- ["[0]" /// "_"
- [bytecode
- [environment
- ["[1][0]" limit {"+" Limit}]]]
- [encoding
- ["[1][0]" unsigned {"+" U2}]]]
- ["[0]" / "_"
- ["[1][0]" exception {"+" Exception}]])
+ [library
+ [lux {"-" Code}
+ [abstract
+ [equivalence {"+" Equivalence}]]
+ [data
+ ["[0]" product]
+ ["[0]" binary {"+" Binary}]
+ [format
+ ["[0]F" binary {"+" Writer} ("[1]#[0]" monoid)]]
+ [collection
+ ["[0]" sequence {"+" Sequence} ("[1]#[0]" functor mix)]]]
+ [math
+ [number
+ ["n" nat]]]]]
+ ["[0]" /// "_"
+ [bytecode
+ [environment
+ ["[1][0]" limit {"+" Limit}]]]
+ [encoding
+ ["[1][0]" unsigned {"+" U2}]]]
+ ["[0]" / "_"
+ ["[1][0]" exception {"+" Exception}]])
(type: .public (Code Attribute)
(Record
@@ -38,19 +38,19 @@
... u4 code_length;
///unsigned.bytes/4
... u1 code[code_length];
- (binary.size (value@ #code code))
+ (binary.size (the #code code))
... u2 exception_table_length;
///unsigned.bytes/2
... exception_table[exception_table_length];
(|> code
- (value@ #exception_table)
+ (the #exception_table)
sequence.size
(n.* /exception.length))
... u2 attributes_count;
///unsigned.bytes/2
... attribute_info attributes[attributes_count];
(|> code
- (value@ #attributes)
+ (the #attributes)
(sequence#each length)
(sequence#mix n.+ 0))))
@@ -70,14 +70,14 @@
($_ binaryF#composite
... u2 max_stack;
... u2 max_locals;
- (///limit.writer (value@ #limit code))
+ (///limit.writer (the #limit code))
... u4 code_length;
... u1 code[code_length];
- (binaryF.binary/32 (value@ #code code))
+ (binaryF.binary/32 (the #code code))
... u2 exception_table_length;
... exception_table[exception_table_length];
- ((binaryF.sequence/16 /exception.writer) (value@ #exception_table code))
+ ((binaryF.sequence/16 /exception.writer) (the #exception_table code))
... u2 attributes_count;
... attribute_info attributes[attributes_count];
- ((binaryF.sequence/16 writer) (value@ #attributes code))
+ ((binaryF.sequence/16 writer) (the #attributes code))
))
diff --git a/stdlib/source/library/lux/target/jvm/bytecode.lux b/stdlib/source/library/lux/target/jvm/bytecode.lux
index 55e9fa71f..29d93fad0 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode.lux
@@ -121,9 +121,9 @@
(function (_ [pool environment tracker])
{try.#Success [[pool
environment
- (revised@ #next ++ tracker)]
+ (revised #next ++ tracker)]
[..relative#identity
- (value@ #next tracker)]]}))
+ (the #next tracker)]]}))
(exception: .public (label_has_already_been_set [label Label])
(exception.report
@@ -147,7 +147,7 @@
(let [[pool environment tracker] state]
{try.#Success [state
[..relative#identity
- (case (dictionary.value label (value@ #known tracker))
+ (case (dictionary.value label (the #known tracker))
{.#Some [expected {.#Some address}]}
{.#Some [expected address]}
@@ -160,7 +160,7 @@
(let [[pool environment tracker] state]
{try.#Success [state
[..relative#identity
- (case (dictionary.value label (value@ #known tracker))
+ (case (dictionary.value label (the #known tracker))
{.#Some [expected {.#None}]}
{.#Some expected}
@@ -173,20 +173,20 @@
(let [[pool environment tracker] state]
{try.#Success [state
[..relative#identity
- (value@ /environment.#stack environment)]]})))
+ (the /environment.#stack environment)]]})))
(with_expansions [<success> (as_is (try|in [[pool
environment
- (revised@ #known
- (dictionary.has label [actual {.#Some @here}])
- tracker)]
+ (revised #known
+ (dictionary.has label [actual {.#Some @here}])
+ tracker)]
[..relative#identity
[]]]))]
(def: .public (set_label label)
(-> Label (Bytecode Any))
(function (_ [pool environment tracker])
- (let [@here (value@ #program_counter tracker)]
- (case (dictionary.value label (value@ #known tracker))
+ (let [@here (the #program_counter tracker)]
+ (case (dictionary.value label (the #known tracker))
{.#Some [expected {.#Some address}]}
(exception.except ..label_has_already_been_set [label])
@@ -197,7 +197,7 @@
... {.#None}
_
(<| (try|do [actual environment] (/environment.continue (|> environment
- (value@ /environment.#stack)
+ (the /environment.#stack)
(maybe.else /stack.empty))
environment))
<success>))))))
@@ -276,7 +276,7 @@
(All (_ a) (-> Environment (Bytecode a) (Resource [Environment (Sequence Exception) Instruction a])))
(function (_ pool)
(<| (try|do [[pool environment tracker] [relative output]] (bytecode [pool environment ..fresh]))
- (try|do [exceptions instruction] (relative (value@ #known tracker)))
+ (try|do [exceptions instruction] (relative (the #known tracker)))
(try|in [pool [environment exceptions instruction output]]))))
(def: (step estimator counter)
@@ -291,10 +291,10 @@
(monad.then try.monad (|>> (/environment.produces production)
(try#each (/environment.has registry))
try#conjoint))))
- (try|do program_counter' (step estimator (value@ #program_counter tracker)))
+ (try|do program_counter' (step estimator (the #program_counter tracker)))
(try|in [[pool
environment'
- (with@ #program_counter program_counter' tracker)]
+ (has #program_counter program_counter' tracker)]
[(function (_ _)
(try|in [..no_exceptions (bytecode input)]))
[]]]))))
@@ -823,20 +823,20 @@
(def: (acknowledge_label stack label tracker)
(-> Stack Label Tracker Tracker)
- (case (dictionary.value label (value@ #known tracker))
+ (case (dictionary.value label (the #known tracker))
{.#Some _}
tracker
... {.#None}
_
- (revised@ #known (dictionary.has label [stack {.#None}]) tracker)))
+ (revised #known (dictionary.has label [stack {.#None}]) tracker)))
(template [<consumption> <name> <instruction>]
[(def: .public (<name> label)
(-> Label (Bytecode Any))
(let [[estimator bytecode] <instruction>]
(function (_ [pool environment tracker])
- (<| (let [@here (value@ #program_counter tracker)])
+ (<| (let [@here (the #program_counter tracker)])
(try|do environment' (|> environment
(/environment.consumes <consumption>)))
(try|do actual (/environment.stack environment'))
@@ -846,7 +846,7 @@
environment'
(|> tracker
(..acknowledge_label actual label)
- (with@ #program_counter program_counter'))]
+ (has #program_counter program_counter'))]
[(function (_ resolver)
(<| (try|do [expected @to] (..resolve_label label resolver))
(try|do _ (exception.assertion ..mismatched_environments [(symbol <instruction>) label @here expected actual]
@@ -887,14 +887,14 @@
(let [[estimator bytecode] <instruction>]
(function (_ [pool environment tracker])
(<| (try|do actual (/environment.stack environment))
- (let [@here (value@ #program_counter tracker)])
+ (let [@here (the #program_counter tracker)])
(try|do program_counter' (step estimator @here))
(try|in (let [@from @here]
[[pool
(/environment.discontinue environment)
(|> tracker
(..acknowledge_label actual label)
- (with@ #program_counter program_counter'))]
+ (has #program_counter program_counter'))]
[(function (_ resolver)
(case (dictionary.value label resolver)
{.#Some [expected {.#Some @to}]}
@@ -942,12 +942,12 @@
(<| (try|do environment' (|> environment
(/environment.consumes $1)))
(try|do actual (/environment.stack environment'))
- (try|do program_counter' (step (estimator (list.size afterwards)) (value@ #program_counter tracker)))
- (try|in (let [@from (value@ #program_counter tracker)]
+ (try|do program_counter' (step (estimator (list.size afterwards)) (the #program_counter tracker)))
+ (try|in (let [@from (the #program_counter tracker)]
[[pool
environment'
(|> (list#mix (..acknowledge_label actual) tracker (list& default at_minimum afterwards))
- (with@ #program_counter program_counter'))]
+ (has #program_counter program_counter'))]
[(function (_ resolver)
(let [get (: (-> Label (Maybe [Stack (Maybe Address)]))
(function (_ label)
@@ -984,12 +984,12 @@
(<| (try|do environment' (|> environment
(/environment.consumes $1)))
(try|do actual (/environment.stack environment'))
- (try|do program_counter' (step (estimator (list.size cases)) (value@ #program_counter tracker)))
- (try|in (let [@from (value@ #program_counter tracker)]
+ (try|do program_counter' (step (estimator (list.size cases)) (the #program_counter tracker)))
+ (try|in (let [@from (the #program_counter tracker)]
[[pool
environment'
(|> (list#mix (..acknowledge_label actual) tracker (list& default (list#each product.right cases)))
- (with@ #program_counter program_counter'))]
+ (has #program_counter program_counter'))]
[(function (_ resolver)
(let [get (: (-> Label (Maybe [Stack (Maybe Address)]))
(function (_ label)
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/environment.lux b/stdlib/source/library/lux/target/jvm/bytecode/environment.lux
index 3e6f60b30..222bd7c0e 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/environment.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/environment.lux
@@ -1,21 +1,21 @@
(.using
- [library
- [lux {"-" Type static}
- [abstract
- [monad {"+" do}]
- [monoid {"+" Monoid}]]
- [control
- ["[0]" try {"+" Try}]
- ["[0]" exception {"+" exception:}]]]]
- [/
- ["/[0]" limit {"+" Limit}
- ["/[0]" stack {"+" Stack}]
- ["/[0]" registry {"+" Registry}]]
- [///
- [encoding
- [unsigned {"+" U2}]]
- [type {"+" Type}
- [category {"+" Method}]]]])
+ [library
+ [lux {"-" Type static has}
+ [abstract
+ [monad {"+" do}]
+ [monoid {"+" Monoid}]]
+ [control
+ ["[0]" try {"+" Try}]
+ ["[0]" exception {"+" exception:}]]]]
+ [/
+ ["/[0]" limit {"+" Limit}
+ ["/[0]" stack {"+" Stack}]
+ ["/[0]" registry {"+" Registry}]]
+ [///
+ [encoding
+ [unsigned {"+" U2}]]
+ [type {"+" Type}
+ [category {"+" Method}]]]])
(type: .public Environment
(Record
@@ -53,7 +53,7 @@
(def: .public (stack environment)
(-> Environment (Try Stack))
- (case (value@ ..#stack environment)
+ (case (the ..#stack environment)
{.#Some stack}
{try.#Success stack}
@@ -62,7 +62,7 @@
(def: .public discontinue
(-> Environment Environment)
- (with@ ..#stack {.#None}))
+ (.has ..#stack {.#None}))
(exception: .public (mismatched_stacks [expected Stack
actual Stack])
@@ -72,14 +72,14 @@
(def: .public (continue expected environment)
(-> Stack Environment (Try [Stack Environment]))
- (case (value@ ..#stack environment)
+ (case (the ..#stack environment)
{.#Some actual}
(if (# /stack.equivalence = expected actual)
{try.#Success [actual environment]}
(exception.except ..mismatched_stacks [expected actual]))
{.#None}
- {try.#Success [expected (with@ ..#stack {.#Some expected} environment)]}))
+ {try.#Success [expected (.has ..#stack {.#Some expected} environment)]}))
(def: .public (consumes amount)
(-> U2 Condition)
@@ -89,7 +89,7 @@
(do try.monad
[previous (..stack environment)
current (/stack.pop amount previous)]
- (in (with@ ..#stack {.#Some current} environment)))))
+ (in (.has ..#stack {.#Some current} environment)))))
(def: .public (produces amount)
(-> U2 Condition)
@@ -98,13 +98,13 @@
[previous (..stack environment)
current (/stack.push amount previous)
.let [limit (|> environment
- (value@ [..#limit /limit.#stack])
+ (the [..#limit /limit.#stack])
(/stack.max current))]]
(in (|> environment
- (with@ ..#stack {.#Some current})
- (with@ [..#limit /limit.#stack] limit))))))
+ (.has ..#stack {.#Some current})
+ (.has [..#limit /limit.#stack] limit))))))
(def: .public (has registry)
(-> Registry Condition)
- (|>> (revised@ [..#limit /limit.#registry] (/registry.has registry))
+ (|>> (revised [..#limit /limit.#registry] (/registry.has registry))
{try.#Success}))
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux
index e27137cbc..3d3bb2d8d 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux
@@ -1,24 +1,24 @@
(.using
- [library
- [lux {"-" Type static}
- [abstract
- [monad {"+" do}]
- [equivalence {"+" Equivalence}]]
- [control
- ["[0]" try {"+" Try}]]
- [data
- ["[0]" product]
- ["[0]" format "_"
- ["[1]" binary {"+" Writer} ("[1]#[0]" monoid)]]]
- [math
- [number
- ["n" nat]]]]]
- ["[0]" / "_"
- ["[1][0]" stack {"+" Stack}]
- ["[1][0]" registry {"+" Registry}]
- [////
- [type {"+" Type}
- [category {"+" Method}]]]])
+ [library
+ [lux {"-" Type static}
+ [abstract
+ [monad {"+" do}]
+ [equivalence {"+" Equivalence}]]
+ [control
+ ["[0]" try {"+" Try}]]
+ [data
+ ["[0]" product]
+ ["[0]" format "_"
+ ["[1]" binary {"+" Writer} ("[1]#[0]" monoid)]]]
+ [math
+ [number
+ ["n" nat]]]]]
+ ["[0]" / "_"
+ ["[1][0]" stack {"+" Stack}]
+ ["[1][0]" registry {"+" Registry}]
+ [////
+ [type {"+" Type}
+ [category {"+" Method}]]]])
(type: .public Limit
(Record
@@ -54,6 +54,6 @@
(def: .public (writer limit)
(Writer Limit)
($_ format#composite
- (/stack.writer (value@ #stack limit))
- (/registry.writer (value@ #registry limit))
+ (/stack.writer (the #stack limit))
+ (/registry.writer (the #registry limit))
))
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux
index f2ead2686..4f42ccffc 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux
@@ -1,26 +1,26 @@
(.using
- [library
- [lux {"-" Type for static}
- [abstract
- ["[0]" equivalence {"+" Equivalence}]]
- [control
- ["[0]" try {"+" Try} ("[1]#[0]" functor)]]
- [data
- [format
- [binary {"+" Writer}]]
- [collection
- ["[0]" list ("[1]#[0]" functor mix)]]]
- [math
- [number
- ["n" nat]]]
- [type
- abstract]]]
- ["[0]" ///// "_"
- [encoding
- ["[1][0]" unsigned {"+" U1 U2}]]
- ["[1][0]" type {"+" Type}
- [category {"+" Method}]
- ["[1]/[0]" parser]]])
+ [library
+ [lux {"-" Type for static has}
+ [abstract
+ ["[0]" equivalence {"+" Equivalence}]]
+ [control
+ ["[0]" try {"+" Try} ("[1]#[0]" functor)]]
+ [data
+ [format
+ [binary {"+" Writer}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor mix)]]]
+ [math
+ [number
+ ["n" nat]]]
+ [type
+ abstract]]]
+ ["[0]" ///// "_"
+ [encoding
+ ["[1][0]" unsigned {"+" U1 U2}]]
+ ["[1][0]" type {"+" Type}
+ [category {"+" Method}]
+ ["[1]/[0]" parser]]])
(type: .public Register
U1)
diff --git a/stdlib/source/library/lux/target/jvm/class.lux b/stdlib/source/library/lux/target/jvm/class.lux
index 2235046e9..73966259f 100644
--- a/stdlib/source/library/lux/target/jvm/class.lux
+++ b/stdlib/source/library/lux/target/jvm/class.lux
@@ -130,7 +130,7 @@
(Writer Class)
(`` ($_ binaryF#composite
(~~ (template [<writer> <slot>]
- [(<writer> (value@ <slot> class))]
+ [(<writer> (the <slot> class))]
[//magic.writer #magic]
[//version.writer #minor_version]
@@ -140,7 +140,7 @@
[//index.writer #this]
[//index.writer #super]))
(~~ (template [<writer> <slot>]
- [((binaryF.sequence/16 <writer>) (value@ <slot> class))]
+ [((binaryF.sequence/16 <writer>) (the <slot> class))]
[//index.writer #interfaces]
[//field.writer #fields]
diff --git a/stdlib/source/library/lux/target/jvm/field.lux b/stdlib/source/library/lux/target/jvm/field.lux
index 494583650..ab2ef722c 100644
--- a/stdlib/source/library/lux/target/jvm/field.lux
+++ b/stdlib/source/library/lux/target/jvm/field.lux
@@ -52,7 +52,7 @@
(Writer Field)
(`` ($_ binaryF#composite
(~~ (template [<writer> <slot>]
- [(<writer> (value@ <slot> field))]
+ [(<writer> (the <slot> field))]
[modifier.writer #modifier]
[//index.writer #name]
diff --git a/stdlib/source/library/lux/target/jvm/method.lux b/stdlib/source/library/lux/target/jvm/method.lux
index c5011887a..264e6d475 100644
--- a/stdlib/source/library/lux/target/jvm/method.lux
+++ b/stdlib/source/library/lux/target/jvm/method.lux
@@ -74,7 +74,7 @@
(function (_ _) {try.#Failure error}))
[environment exceptions instruction output] (//bytecode.resolve environment code)
.let [bytecode (|> instruction //instruction.result format.instance)]
- @code (//attribute.code [//code.#limit (value@ //environment.#limit environment)
+ @code (//attribute.code [//code.#limit (the //environment.#limit environment)
//code.#code bytecode
//code.#exception_table exceptions
//code.#attributes (sequence.sequence)])]
@@ -100,7 +100,7 @@
(Writer Method)
(`` ($_ format#composite
(~~ (template [<writer> <slot>]
- [(<writer> (value@ <slot> field))]
+ [(<writer> (the <slot> field))]
[//modifier.writer #modifier]
[//index.writer #name]
diff --git a/stdlib/source/library/lux/target/lua.lux b/stdlib/source/library/lux/target/lua.lux
index c99893692..ed2e1087f 100644
--- a/stdlib/source/library/lux/target/lua.lux
+++ b/stdlib/source/library/lux/target/lua.lux
@@ -1,6 +1,6 @@
(.using
[library
- [lux {"-" Location Code Label int if function or and not let ^ local comment}
+ [lux {"-" Location Code Label int if function or and not let ^ local comment the}
["@" target]
[abstract
[equivalence {"+" Equivalence}]
diff --git a/stdlib/source/library/lux/target/php.lux b/stdlib/source/library/lux/target/php.lux
index f02eafd89..b23ac1b98 100644
--- a/stdlib/source/library/lux/target/php.lux
+++ b/stdlib/source/library/lux/target/php.lux
@@ -1,30 +1,30 @@
(.using
- [library
- [lux {"-" Location Code Global Label static int if cond or and not comment for try global}
- ["@" target]
- [abstract
- [equivalence {"+" Equivalence}]
- [hash {"+" Hash}]
- ["[0]" enum]]
- [control
- [pipe {"+" case> cond> new>}]
- [parser
- ["<[0]>" code]]]
- [data
- ["[0]" text
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" functor mix)]]]
- [macro
- [syntax {"+" syntax:}]
- ["[0]" template]
- ["[0]" code]]
- [math
- [number
- ["n" nat]
- ["f" frac]]]
- [type
- abstract]]])
+ [library
+ [lux {"-" Location Code Global Label static int if cond or and not comment for try global the}
+ ["@" target]
+ [abstract
+ [equivalence {"+" Equivalence}]
+ [hash {"+" Hash}]
+ ["[0]" enum]]
+ [control
+ [pipe {"+" case> cond> new>}]
+ [parser
+ ["<[0]>" code]]]
+ [data
+ ["[0]" text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor mix)]]]
+ [macro
+ [syntax {"+" syntax:}]
+ ["[0]" template]
+ ["[0]" code]]
+ [math
+ [number
+ ["n" nat]
+ ["f" frac]]]
+ [type
+ abstract]]])
(def: input_separator ", ")
(def: statement_suffix ";")
@@ -486,10 +486,10 @@
(def: (catch except)
(-> Except Text)
- (let [declaration (format (:representation (value@ #class except))
- " " (:representation (value@ #exception except)))]
+ (let [declaration (format (:representation (.the #class except))
+ " " (:representation (.the #exception except)))]
(format "catch" (..group declaration) " "
- (..block (:representation (value@ #handler except))))))
+ (..block (:representation (.the #handler except))))))
(def: .public (try body! excepts)
(-> Statement (List Except) Statement)
diff --git a/stdlib/source/library/lux/target/python.lux b/stdlib/source/library/lux/target/python.lux
index bd3d68711..237baadd7 100644
--- a/stdlib/source/library/lux/target/python.lux
+++ b/stdlib/source/library/lux/target/python.lux
@@ -1,6 +1,6 @@
(.using
[library
- [lux {"-" Location Code not or and list if int comment exec try}
+ [lux {"-" Location Code not or and list if int comment exec try the}
["@" target]
["[0]" ffi]
[abstract
diff --git a/stdlib/source/library/lux/target/ruby.lux b/stdlib/source/library/lux/target/ruby.lux
index c197f6a64..b965a3296 100644
--- a/stdlib/source/library/lux/target/ruby.lux
+++ b/stdlib/source/library/lux/target/ruby.lux
@@ -1,6 +1,6 @@
(.using
[library
- [lux {"-" Location Code static int if function or and not comment local global symbol}
+ [lux {"-" Location Code static int if function or and not comment local global symbol the}
["@" target]
[abstract
[equivalence {"+" Equivalence}]
@@ -233,11 +233,11 @@
(def: (block it)
(-> Block Text)
- (|> (format (|> (value@ #parameters it)
+ (|> (format (|> (.the #parameters it)
(list#each (|>> :representation))
(text.interposed ..input_separator)
(text.enclosed' "|"))
- (..nested (:representation (value@ #body it))))
+ (..nested (:representation (.the #body it))))
(text.enclosed ["{" "}"])))
(def: .public (apply/* arguments block func)
diff --git a/stdlib/source/library/lux/target/scheme.lux b/stdlib/source/library/lux/target/scheme.lux
index f1ad798e7..5a90ecbe4 100644
--- a/stdlib/source/library/lux/target/scheme.lux
+++ b/stdlib/source/library/lux/target/scheme.lux
@@ -1,25 +1,25 @@
(.using
- [library
- [lux {"-" Code int or and if cond let symbol}
- ["@" target]
- [abstract
- [equivalence {"+" Equivalence}]
- [hash {"+" Hash}]]
- [control
- [pipe {"+" new> cond> case>}]]
- [data
- ["[0]" text
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" functor monoid)]]]
- [macro
- ["[0]" template]]
- [math
- [number
- ["n" nat]
- ["f" frac]]]
- [type
- abstract]]])
+ [library
+ [lux {"-" Code int or and if cond let symbol}
+ ["@" target]
+ [abstract
+ [equivalence {"+" Equivalence}]
+ [hash {"+" Hash}]]
+ [control
+ [pipe {"+" new> cond> case>}]]
+ [data
+ ["[0]" text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor monoid)]]]
+ [macro
+ ["[0]" template]]
+ [math
+ [number
+ ["n" nat]
+ ["f" frac]]]
+ [type
+ abstract]]])
... Added the carriage return for better Windows compatibility.
(def: \n+
@@ -345,7 +345,7 @@
(-> Var Arguments Expression Computation)
(..form (list (..var "define")
(|> arguments
- (revised@ #mandatory (|>> {.#Item name}))
+ (revised #mandatory (|>> {.#Item name}))
..arguments)
body)))
diff --git a/stdlib/source/library/lux/test.lux b/stdlib/source/library/lux/test.lux
index d9555ec44..ad817a70b 100644
--- a/stdlib/source/library/lux/test.lux
+++ b/stdlib/source/library/lux/test.lux
@@ -51,12 +51,12 @@
(def: (total parameter subject)
(-> Tally Tally Tally)
- [#successes (n.+ (value@ #successes parameter) (value@ #successes subject))
- #failures (n.+ (value@ #failures parameter) (value@ #failures subject))
- #expected_coverage (set.union (value@ #expected_coverage parameter)
- (value@ #expected_coverage subject))
- #actual_coverage (set.union (value@ #actual_coverage parameter)
- (value@ #actual_coverage subject))])
+ [#successes (n.+ (the #successes parameter) (the #successes subject))
+ #failures (n.+ (the #failures parameter) (the #failures subject))
+ #expected_coverage (set.union (the #expected_coverage parameter)
+ (the #expected_coverage subject))
+ #actual_coverage (set.union (the #actual_coverage parameter)
+ (the #actual_coverage subject))])
(def: start
Tally
@@ -68,7 +68,7 @@
(template [<name> <category>]
[(def: <name>
Tally
- (revised@ <category> .++ ..start))]
+ (revised <category> .++ ..start))]
[success_tally #successes]
[failure_tally #failures]
@@ -157,7 +157,7 @@
(def: failed?
(-> Tally Bit)
- (|>> (value@ #failures) (n.> 0)))
+ (|>> (the #failures) (n.> 0)))
(def: (times_failure seed documentation)
(-> Seed Text Text)
@@ -187,20 +187,20 @@
(def: (description duration tally)
(-> Duration Tally Text)
- (let [successes (value@ #successes tally)
- failures (value@ #failures tally)
- missing (set.difference (value@ #actual_coverage tally)
- (value@ #expected_coverage tally))
- unexpected (set.difference (value@ #expected_coverage tally)
- (value@ #actual_coverage tally))
+ (let [successes (the #successes tally)
+ failures (the #failures tally)
+ missing (set.difference (the #actual_coverage tally)
+ (the #expected_coverage tally))
+ unexpected (set.difference (the #expected_coverage tally)
+ (the #actual_coverage tally))
report (: (-> (Set Symbol) Text)
(|>> set.list
(list.sorted (# symbol.order <))
(exception.listing %.symbol)))
- expected_definitions_to_cover (set.size (value@ #expected_coverage tally))
+ expected_definitions_to_cover (set.size (the #expected_coverage tally))
unexpected_definitions_covered (set.size unexpected)
actual_definitions_covered (n.- unexpected_definitions_covered
- (set.size (value@ #actual_coverage tally)))
+ (set.size (the #actual_coverage tally)))
coverage (case expected_definitions_to_cover
0 "N/A"
expected (let [missing_ratio (f./ (n.frac expected)
@@ -260,7 +260,7 @@
(console.write_line report console))]
<else>))]
(async.future (# program.default exit
- (case (value@ #failures tally)
+ (case (the #failures tally)
0 ..success_exit_code
_ ..failure_exit_code)))))
@@ -280,7 +280,7 @@
coverage (set.of_list symbol.hash coverage)]
(|> (..assertion message condition)
(async#each (function (_ [tally documentation])
- [(revised@ #actual_coverage (set.union coverage) tally)
+ [(revised #actual_coverage (set.union coverage) tally)
documentation])))))
(def: (|cover| coverage condition)
@@ -295,7 +295,7 @@
(text.interposed ..definition_separator))
coverage (set.of_list symbol.hash coverage)]
(random#each (async#each (function (_ [tally documentation])
- [(revised@ #actual_coverage (set.union coverage) tally)
+ [(revised #actual_coverage (set.union coverage) tally)
documentation]))
(..context' context test))))
@@ -362,7 +362,7 @@
(let [coverage (..coverage module coverage)]
(|> (..context' module test)
(random#each (async#each (function (_ [tally documentation])
- [(revised@ #expected_coverage (set.union coverage) tally)
+ [(revised #expected_coverage (set.union coverage) tally)
(|> documentation
(text.replaced (format ..clean_up_marker module symbol.separator) "")
(text.replaced ..clean_up_marker ""))]))))))
diff --git a/stdlib/source/library/lux/time.lux b/stdlib/source/library/lux/time.lux
index 9a5b3ce93..debab4ab4 100644
--- a/stdlib/source/library/lux/time.lux
+++ b/stdlib/source/library/lux/time.lux
@@ -1,27 +1,27 @@
(.using
- [library
- [lux "*"
- [abstract
- [equivalence {"+" Equivalence}]
- [order {"+" Order}]
- [enum {"+" Enum}]
- [codec {"+" Codec}]
- [monad {"+" Monad do}]]
- [control
- [pipe {"+" case>}]
- ["[0]" try {"+" Try}]
- ["[0]" exception {"+" exception:}]
- ["<>" parser
- ["<[0]>" text {"+" Parser}]]]
- [data
- ["[0]" text ("[1]#[0]" monoid)]]
- [math
- [number
- ["n" nat ("[1]#[0]" decimal)]]]
- [type
- abstract]]]
- [/
- ["[0]" duration {"+" Duration}]])
+ [library
+ [lux "*"
+ [abstract
+ [equivalence {"+" Equivalence}]
+ [order {"+" Order}]
+ [enum {"+" Enum}]
+ [codec {"+" Codec}]
+ [monad {"+" Monad do}]]
+ [control
+ [pipe {"+" case>}]
+ ["[0]" try {"+" Try}]
+ ["[0]" exception {"+" exception:}]
+ ["<>" parser
+ ["<[0]>" text {"+" Parser}]]]
+ [data
+ ["[0]" text ("[1]#[0]" monoid)]]
+ [math
+ [number
+ ["n" nat ("[1]#[0]" decimal)]]]
+ [type
+ abstract]]]
+ [/
+ ["[0]" duration {"+" Duration}]])
(template [<name> <singular> <plural>]
[(def: .public <name>
@@ -189,10 +189,10 @@
(def: .public (time clock)
(-> Clock (Try Time))
(|> ($_ duration.merged
- (duration.up (value@ #hour clock) duration.hour)
- (duration.up (value@ #minute clock) duration.minute)
- (duration.up (value@ #second clock) duration.second)
- (duration.of_millis (.int (value@ #milli_second clock))))
+ (duration.up (the #hour clock) duration.hour)
+ (duration.up (the #minute clock) duration.minute)
+ (duration.up (the #second clock) duration.second)
+ (duration.of_millis (.int (the #milli_second clock))))
duration.millis
.nat
..of_millis))
diff --git a/stdlib/source/library/lux/time/date.lux b/stdlib/source/library/lux/time/date.lux
index 6fcd9a73b..e32440153 100644
--- a/stdlib/source/library/lux/time/date.lux
+++ b/stdlib/source/library/lux/time/date.lux
@@ -1,32 +1,32 @@
(.using
- [library
- [lux "*"
- [abstract
- [equivalence {"+" Equivalence}]
- [order {"+" Order}]
- [enum {"+" Enum}]
- [codec {"+" Codec}]
- [monad {"+" do}]]
- [control
- ["[0]" maybe]
- ["[0]" try {"+" Try}]
- ["[0]" exception {"+" exception:}]
- ["<>" parser
- ["<[0]>" text {"+" Parser}]]]
- [data
- ["[0]" text ("[1]#[0]" monoid)]
- [collection
- ["[0]" list ("[1]#[0]" mix)]
- ["[0]" dictionary {"+" Dictionary}]]]
- [math
- [number
- ["n" nat ("[1]#[0]" decimal)]
- ["i" int]]]
- [type
- abstract]]]
- ["[0]" // "_"
- ["[1][0]" year {"+" Year}]
- ["[1][0]" month {"+" Month}]])
+ [library
+ [lux "*"
+ [abstract
+ [equivalence {"+" Equivalence}]
+ [order {"+" Order}]
+ [enum {"+" Enum}]
+ [codec {"+" Codec}]
+ [monad {"+" do}]]
+ [control
+ ["[0]" maybe]
+ ["[0]" try {"+" Try}]
+ ["[0]" exception {"+" exception:}]
+ ["<>" parser
+ ["<[0]>" text {"+" Parser}]]]
+ [data
+ ["[0]" text ("[1]#[0]" monoid)]
+ [collection
+ ["[0]" list ("[1]#[0]" mix)]
+ ["[0]" dictionary {"+" Dictionary}]]]
+ [math
+ [number
+ ["n" nat ("[1]#[0]" decimal)]
+ ["i" int]]]
+ [type
+ abstract]]]
+ ["[0]" // "_"
+ ["[1][0]" year {"+" Year}]
+ ["[1][0]" month {"+" Month}]])
(def: month_by_number
(Dictionary Nat Month)
@@ -95,7 +95,7 @@
(template [<name> <type> <field>]
[(def: .public <name>
(-> Date <type>)
- (|>> :representation (value@ <field>)))]
+ (|>> :representation (the <field>)))]
[year Year #year]
[month Month #month]
@@ -109,13 +109,13 @@
(let [reference (:representation reference)
sample (:representation sample)]
(and (# //year.equivalence =
- (value@ #year reference)
- (value@ #year sample))
+ (the #year reference)
+ (the #year sample))
(# //month.equivalence =
- (value@ #month reference)
- (value@ #month sample))
- (n.= (value@ #day reference)
- (value@ #day sample))))))
+ (the #month reference)
+ (the #month sample))
+ (n.= (the #day reference)
+ (the #day sample))))))
(implementation: .public order
(Order Date)
@@ -126,19 +126,19 @@
(let [reference (:representation reference)
sample (:representation sample)]
(or (# //year.order <
- (value@ #year reference)
- (value@ #year sample))
+ (the #year reference)
+ (the #year sample))
(and (# //year.equivalence =
- (value@ #year reference)
- (value@ #year sample))
+ (the #year reference)
+ (the #year sample))
(or (# //month.order <
- (value@ #month reference)
- (value@ #month sample))
+ (the #month reference)
+ (the #month sample))
(and (# //month.order =
- (value@ #month reference)
- (value@ #month sample))
- (n.< (value@ #day reference)
- (value@ #day sample)))))))))
+ (the #month reference)
+ (the #month sample))
+ (n.< (the #day reference)
+ (the #day sample)))))))))
)
(def: section_parser
diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux
index 7f815abf9..48a1fb475 100644
--- a/stdlib/source/library/lux/tool/compiler/default/init.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/init.lux
@@ -110,8 +110,8 @@
{.#Right [source' output]}
(let [[location _] output]
{try.#Success [[bundle (|> compiler
- (with@ .#source source')
- (with@ .#location location))]
+ (has .#source source')
+ (has .#location location))]
[source' output]]}))))
(type: (Operation a)
@@ -128,13 +128,13 @@
(///directive.Operation anchor expression directive
[Source (Payload directive)])))
(do ///phase.monad
- [.let [module (value@ ///.#module input)]
+ [.let [module (the ///.#module input)]
_ (///directive.set_current_module module)]
(///directive.lifted_analysis
(do [! ///phase.monad]
[_ (moduleA.create hash module)
_ (monad.each ! moduleA.import dependencies)
- .let [source (///analysis.source (value@ ///.#module input) (value@ ///.#code input))]
+ .let [source (///analysis.source (the ///.#module input) (the ///.#code input))]
_ (///analysis.set_source_code source)]
(in [source [///generation.empty_buffer
registry.empty]])))))
@@ -223,13 +223,13 @@
(def: (default_dependencies prelude input)
(-> descriptor.Module ///.Input (List descriptor.Module))
(list& descriptor.runtime
- (if (text#= prelude (value@ ///.#module input))
+ (if (text#= prelude (the ///.#module input))
(list)
(list prelude))))
(def: module_aliases
(-> .Module Aliases)
- (|>> (value@ .#module_aliases) (dictionary.of_list text.hash)))
+ (|>> (the .#module_aliases) (dictionary.of_list text.hash)))
(def: .public (compiler wrapper expander prelude write_directive)
(All (_ anchor expression directive)
@@ -241,10 +241,10 @@
[///.#dependencies dependencies
///.#process (function (_ state archive)
(do [! try.monad]
- [.let [hash (text#hash (value@ ///.#code input))]
+ [.let [hash (text#hash (the ///.#code input))]
[state [source buffer]] (<| (///phase.result' state)
(..begin dependencies hash input))
- .let [module (value@ ///.#module input)]]
+ .let [module (the ///.#module input)]]
(loop [iteration (<| (///phase.result' state)
(..iteration wrapper archive expander module source buffer ///syntax.no_aliases))]
(do !
@@ -255,7 +255,7 @@
[[state [analysis_module [final_buffer final_registry]]] (///phase.result' state (..end module))
.let [descriptor [descriptor.#hash hash
descriptor.#name module
- descriptor.#file (value@ ///.#file input)
+ descriptor.#file (the ///.#file input)
descriptor.#references (set.of_list text.hash dependencies)
descriptor.#state {.#Compiled}]]]
(in [state
@@ -271,7 +271,7 @@
(let [[temporary_buffer temporary_registry] temporary_payload]
(in [state
{.#Left [///.#dependencies (|> requirements
- (value@ ///directive.#imports)
+ (the ///directive.#imports)
(list#each product.left))
///.#process (function (_ state archive)
(again (<| (///phase.result' state)
@@ -285,7 +285,7 @@
_ (///directive.lifted_generation
(///generation.set_registry temporary_registry))
_ (|> requirements
- (value@ ///directive.#referrals)
+ (the ///directive.#referrals)
(monad.each ! (execute! archive)))
temporary_payload (..get_current_payload temporary_payload)]
(..iteration wrapper archive expander module source temporary_payload (..module_aliases analysis_module))))))]}]))
diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux
index 6aa9f8b77..1bccf29e7 100644
--- a/stdlib/source/library/lux/tool/compiler/default/platform.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux
@@ -112,7 +112,7 @@
(All (_ <type_vars> document)
(-> context.Context <Platform> module.ID (Key document) (Writer document) (archive.Entry document)
(Async (Try Any))))
- (let [system (value@ #&file_system platform)
+ (let [system (the #&file_system platform)
write_artifact! (: (-> [artifact.ID (Maybe Text) Binary] (Action Any))
(function (_ [artifact_id custom content])
(cache/artifact.cache! system context @module artifact_id content)))]
@@ -120,22 +120,22 @@
[_ (: (Async (Try Any))
(cache/module.enable! async.monad system context @module))
_ (for [@.python (|> entry
- (value@ archive.#output)
+ (the archive.#output)
sequence.list
(list.sub 128)
(monad.each ! (monad.each ! write_artifact!))
(: (Action (List (List Any)))))]
(|> entry
- (value@ archive.#output)
+ (the archive.#output)
sequence.list
(monad.each ..monad write_artifact!)
(: (Action (List Any)))))
document (# async.monad in
- (document.marked? key (value@ [archive.#module module.#document] entry)))]
+ (document.marked? key (the [archive.#module module.#document] entry)))]
(|> [(|> entry
- (value@ archive.#module)
- (with@ module.#document document))
- (value@ archive.#registry entry)]
+ (the archive.#module)
+ (has module.#document document))
+ (the archive.#registry entry)]
(_.result (..writer format))
(cache/module.cache! system context @module)))))
@@ -151,7 +151,7 @@
(-> <Platform> (///generation.Operation <type_vars> [Registry Output])))
(do ///phase.monad
[_ ..initialize_buffer!]
- (value@ #runtime platform)))
+ (the #runtime platform)))
(def: runtime_descriptor
Descriptor
@@ -226,7 +226,7 @@
(All (_ <type_vars>)
(-> Archive <Platform> <State+> (Try [<State+> ///phase.Wrapper])))
(|> archive
- ((value@ #phase_wrapper platform))
+ ((the #phase_wrapper platform))
///directive.lifted_generation
(///phase.result' state)))
@@ -262,17 +262,17 @@
Import (List _io.Context) Configuration
(Async (Try [<State+> Archive ///phase.Wrapper]))))
(do [! (try.with async.monad)]
- [.let [state (//init.state (value@ context.#host context)
+ [.let [state (//init.state (the context.#host context)
module
compilation_configuration
expander
host_analysis
- (value@ #host platform)
- (value@ #phase platform)
+ (the #host platform)
+ (the #phase platform)
generation_bundle)]
_ (: (Async (Try Any))
- (cache.enable! async.monad (value@ #&file_system platform) context))
- [archive analysis_state bundles] (ioW.thaw (list) compilation_configuration (value@ #host platform) (value@ #&file_system platform) context import compilation_sources)
+ (cache.enable! async.monad (the #&file_system platform) context))
+ [archive analysis_state bundles] (ioW.thaw (list) compilation_configuration (the #host platform) (the #&file_system platform) context import compilation_sources)
.let [with_missing_extensions
(: (All (_ <type_vars>)
(-> <Platform> (Program expression directive) <State+>
@@ -306,11 +306,11 @@
(def: (module_compilation_log module)
(All (_ <type_vars>)
(-> descriptor.Module <State+> Text))
- (|>> (value@ [extension.#state
- ///directive.#generation
- ///directive.#state
- extension.#state
- ///generation.#log])
+ (|>> (the [extension.#state
+ ///directive.#generation
+ ///directive.#state
+ extension.#state
+ ///generation.#log])
(sequence#mix (function (_ right left)
(format left ..compilation_log_separator right))
module)))
@@ -318,12 +318,12 @@
(def: with_reset_log
(All (_ <type_vars>)
(-> <State+> <State+>))
- (with@ [extension.#state
- ///directive.#generation
- ///directive.#state
- extension.#state
- ///generation.#log]
- sequence.empty))
+ (has [extension.#state
+ ///directive.#generation
+ ///directive.#state
+ extension.#state
+ ///generation.#log]
+ sequence.empty))
(def: empty
(Set descriptor.Module)
@@ -351,8 +351,8 @@
lens
(dictionary.value module)
(maybe.else ..empty))))
- transitive_depends_on (transitive_dependency (value@ #depends_on) import)
- transitive_depended_by (transitive_dependency (value@ #depended_by) module)
+ transitive_depends_on (transitive_dependency (the #depends_on) import)
+ transitive_depended_by (transitive_dependency (the #depended_by) module)
update_dependence (: (-> [descriptor.Module (Set descriptor.Module)] [descriptor.Module (Set descriptor.Module)]
(-> Mapping Mapping))
(function (_ [source forward] [target backward])
@@ -366,14 +366,14 @@
with_dependence+transitives
(set.list backward))))))]
(|> dependence
- (revised@ #depends_on
- (update_dependence
- [module transitive_depends_on]
- [import transitive_depended_by]))
- (revised@ #depended_by
- ((function.flipped update_dependence)
- [module transitive_depends_on]
- [import transitive_depended_by])))))
+ (revised #depends_on
+ (update_dependence
+ [module transitive_depends_on]
+ [import transitive_depended_by]))
+ (revised #depended_by
+ ((function.flipped update_dependence)
+ [module transitive_depends_on]
+ [import transitive_depended_by])))))
(def: (circular_dependency? module import dependence)
(-> descriptor.Module descriptor.Module Dependence Bit)
@@ -384,8 +384,8 @@
(dictionary.value from)
(maybe.else ..empty))]
(set.member? targets to))))]
- (or (dependence? import (value@ #depends_on) module)
- (dependence? module (value@ #depended_by) import))))
+ (or (dependence? import (the #depends_on) module)
+ (dependence? module (the #depended_by) import))))
(exception: .public (module_cannot_import_itself [module descriptor.Module])
(exception.report
@@ -444,8 +444,8 @@
(All (_ <type_vars>)
(-> <State+> <State+> (Try <State+>)))
(do try.monad
- [inherited (with_extensions (value@ <path> from) (value@ <path> state))]
- (in (with@ <path> inherited state))))]
+ [inherited (with_extensions (the <path> from) (the <path> state))]
+ (in (has <path> inherited state))))]
[with_analysis_extensions [extension.#state ///directive.#analysis ///directive.#state extension.#bundle]]
[with_synthesis_extensions [extension.#state ///directive.#synthesis ///directive.#state extension.#bundle]]
@@ -593,7 +593,7 @@
(do !
[entry (archive.find module archive)
lux_module (|> entry
- (value@ [archive.#module module.#document])
+ (the [archive.#module module.#document])
(document.content $.key))]
(in [module lux_module])))
(archive.archived archive))
@@ -602,21 +602,21 @@
(set.of_list text.hash))
with_modules (: (All (_ <type_vars>)
(-> <State+> <State+>))
- (revised@ [extension.#state
- ///directive.#analysis
- ///directive.#state
- extension.#state]
- (: (All (_ a) (-> a a))
- (function (_ analysis_state)
- (|> analysis_state
- (:as .Lux)
- (revised@ .#modules (function (_ current)
- (list#composite (list.only (|>> product.left
- (set.member? additions)
- not)
- current)
- modules)))
- :expected)))))]
+ (revised [extension.#state
+ ///directive.#analysis
+ ///directive.#state
+ extension.#state]
+ (: (All (_ a) (-> a a))
+ (function (_ analysis_state)
+ (|> analysis_state
+ (:as .Lux)
+ (revised .#modules (function (_ current)
+ (list#composite (list.only (|>> product.left
+ (set.member? additions)
+ not)
+ current)
+ modules)))
+ :expected)))))]
state (monad.mix ! with_all_extensions state extended_states)]
(in (with_modules state))))
@@ -687,7 +687,7 @@
(-> descriptor.Module Lux_Context (///.Compilation <State+> .Module Any)
(Try [<State+> (Either (///.Compilation <State+> .Module Any)
(archive.Entry Any))])))
- ((value@ ///.#process compilation)
+ ((the ///.#process compilation)
... TODO: The "///directive.set_current_module" below shouldn't be necessary. Remove it ASAP.
... TODO: The context shouldn't need to be re-set either.
(|> (///directive.set_current_module module)
@@ -700,7 +700,7 @@
(All (_ <type_vars>)
(-> ///phase.Wrapper Expander <Platform>
(///.Compiler <State+> .Module Any)))
- (let [instancer (//init.compiler phase_wrapper expander syntax.prelude (value@ #write platform))]
+ (let [instancer (//init.compiler phase_wrapper expander syntax.prelude (the #write platform))]
(instancer $.key (list))))
(def: (custom_compiler import context platform compilation_sources compiler
@@ -716,10 +716,10 @@
all_dependencies (: (Set descriptor.Module)
(set.of_list text.hash (list)))]
(do [! (try.with async.monad)]
- [.let [new_dependencies (value@ ///.#dependencies compilation)
+ [.let [new_dependencies (the ///.#dependencies compilation)
[all_dependencies duplicates] (with_new_dependencies new_dependencies all_dependencies)]
[archive _] (any|after_imports customs import! module duplicates new_dependencies archive)]
- (case ((value@ ///.#process compilation) state archive)
+ (case ((the ///.#process compilation) state archive)
{try.#Success [state more|done]}
(case more|done
{.#Left more}
@@ -734,7 +734,7 @@
{.#Right entry}
(do !
- [.let [entry (with@ [archive.#module module.#descriptor descriptor.#references] all_dependencies entry)]
+ [.let [entry (has [archive.#module module.#descriptor descriptor.#references] all_dependencies entry)]
_ (..cache_module context platform @module custom_key custom_format entry)]
(async#in (do try.monad
[archive (archive.has module entry archive)]
@@ -742,7 +742,7 @@
{try.#Failure error}
(do !
- [_ (cache/archive.cache! (value@ #&file_system platform) context archive)]
+ [_ (cache/archive.cache! (the #&file_system platform) context archive)]
(async#in {try.#Failure error})))))))
(def: (lux_compiler import context platform compilation_sources compiler compilation)
@@ -756,7 +756,7 @@
all_dependencies (: (Set descriptor.Module)
(set.of_list text.hash (list)))]
(do [! (try.with async.monad)]
- [.let [new_dependencies (value@ ///.#dependencies compilation)
+ [.let [new_dependencies (the ///.#dependencies compilation)
[all_dependencies duplicates] (with_new_dependencies new_dependencies all_dependencies)]
[archive state] (lux|after_imports customs import! module duplicates new_dependencies [archive state])]
(case (next_compilation module [archive state] compilation)
@@ -783,7 +783,7 @@
{.#Some console}
(console.write_line report console))]
<else>)))
- .let [entry (with@ [archive.#module module.#descriptor descriptor.#references] all_dependencies entry)]
+ .let [entry (has [archive.#module module.#descriptor descriptor.#references] all_dependencies entry)]
_ (..cache_module context platform @module $.key $.writer (:as (archive.Entry .Module) entry))]
(async#in (do try.monad
[archive (archive.has module entry archive)]
@@ -792,7 +792,7 @@
{try.#Failure error}
(do !
- [_ (cache/archive.cache! (value@ #&file_system platform) context archive)]
+ [_ (cache/archive.cache! (the #&file_system platform) context archive)]
(async#in {try.#Failure error})))))))
(for [@.old (as_is (def: Fake_State
@@ -814,11 +814,11 @@
Lux_Compiler))
(function (_ all_customs importer import! @module [archive lux_state] module)
(do [! (try.with async.monad)]
- [input (io.read (value@ #&file_system platform)
+ [input (io.read (the #&file_system platform)
importer
import
compilation_sources
- (value@ context.#host_module_extension context)
+ (the context.#host_module_extension context)
module)]
(loop [customs (for [@.old (:as (List (///.Custom Fake_State Fake_Document Fake_Object))
all_customs)]
@@ -854,22 +854,22 @@
(def: (custom import! it)
(All (_ <type_vars>)
(-> Lux_Importer compiler.Compiler (Async (Try [Lux_Context (List Text) Any]))))
- (let [/#definition (value@ compiler.#definition it)
+ (let [/#definition (the compiler.#definition it)
[/#module /#name] /#definition]
(do ..monad
[context (import! (list) descriptor.runtime /#module)
.let [[archive state] context
- meta_state (value@ [extension.#state
- ///directive.#analysis
- ///directive.#state
- extension.#state]
- state)]
+ meta_state (the [extension.#state
+ ///directive.#analysis
+ ///directive.#state
+ extension.#state]
+ state)]
[_ /#type /#value] (|> /#definition
meta.export
(meta.result meta_state)
async#in)]
(async#in (if (check.subsumes? ..Custom /#type)
- {try.#Success [context (value@ compiler.#parameters it) /#value]}
+ {try.#Success [context (the compiler.#parameters it) /#value]}
(exception.except ..invalid_custom_compiler [/#definition /#type]))))))
(def: .public (compile lux_compiler phase_wrapper import file_context expander platform compilation context)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
index 650842124..1828747ab 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux
@@ -252,10 +252,10 @@
(def: .public (with_source_code source action)
(All (_ a) (-> Source (Operation a) (Operation a)))
(function (_ [bundle state])
- (let [old_source (value@ .#source state)]
- (.case (action [bundle (with@ .#source source state)])
+ (let [old_source (the .#source state)]
+ (.case (action [bundle (has .#source source state)])
{try.#Success [[bundle' state'] output]}
- {try.#Success [[bundle' (with@ .#source old_source state')]
+ {try.#Success [[bundle' (has .#source old_source state')]
output]}
failure
@@ -263,8 +263,8 @@
(def: .public (with_current_module name)
(All (_ a) (-> Text (Operation a) (Operation a)))
- (extension.localized (value@ .#current_module)
- (with@ .#current_module)
+ (extension.localized (the .#current_module)
+ (has .#current_module)
(function.constant {.#Some name})))
(def: .public (with_location location action)
@@ -272,10 +272,10 @@
(if (text#= "" (product.left location))
action
(function (_ [bundle state])
- (let [old_location (value@ .#location state)]
- (.case (action [bundle (with@ .#location location state)])
+ (let [old_location (the .#location state)]
+ (.case (action [bundle (has .#location location state)])
{try.#Success [[bundle' state'] output]}
- {try.#Success [[bundle' (with@ .#location old_location state')]
+ {try.#Success [[bundle' (has .#location old_location state')]
output]}
failure
@@ -289,14 +289,14 @@
(def: .public (failure error)
(-> Text Operation)
(function (_ [bundle state])
- {try.#Failure (located (value@ .#location state) error)}))
+ {try.#Failure (located (the .#location state) error)}))
(def: .public (of_try it)
(All (_ a) (-> (Try a) (Operation a)))
(function (_ [bundle state])
(.case it
{try.#Failure error}
- {try.#Failure (located (value@ .#location state) error)}
+ {try.#Failure (located (the .#location state) error)}
{try.#Success it}
{try.#Success [[bundle state] it]})))
@@ -318,7 +318,7 @@
(action bundle,state))
{try.#Failure error}
(let [[bundle state] bundle,state]
- {try.#Failure (located (value@ .#location state) error)})
+ {try.#Failure (located (the .#location state) error)})
success
success)))
@@ -332,7 +332,7 @@
(template [<name> <type> <field> <value>]
[(def: .public (<name> value)
(-> <type> (Operation Any))
- (extension.update (with@ <field> <value>)))]
+ (extension.update (has <field> <value>)))]
[set_source_code Source .#source value]
[set_current_module Text .#current_module {.#Some value}]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux
index a3084664d..39fcf63e7 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux
@@ -83,13 +83,13 @@
(do ///.monad
[self_name meta.current_module_name]
(function (_ state)
- {try.#Success [(revised@ .#modules
- (plist.revised self_name (revised@ .#imports (function (_ current)
- (if (list.any? (text#= module)
- current)
- current
- {.#Item module current}))))
- state)
+ {try.#Success [(revised .#modules
+ (plist.revised self_name (revised .#imports (function (_ current)
+ (if (list.any? (text#= module)
+ current)
+ current
+ {.#Item module current}))))
+ state)
[]]}))))
(def: .public (alias alias module)
@@ -98,10 +98,10 @@
(do ///.monad
[self_name meta.current_module_name]
(function (_ state)
- {try.#Success [(revised@ .#modules
- (plist.revised self_name (revised@ .#module_aliases (: (-> (List [Text Text]) (List [Text Text]))
- (|>> {.#Item [alias module]}))))
- state)
+ {try.#Success [(revised .#modules
+ (plist.revised self_name (revised .#module_aliases (: (-> (List [Text Text]) (List [Text Text]))
+ (|>> {.#Item [alias module]}))))
+ state)
[]]}))))
(def: .public (exists? module)
@@ -109,7 +109,7 @@
(///extension.lifted
(function (_ state)
(|> state
- (value@ .#modules)
+ (the .#modules)
(plist.value module)
(case> {.#Some _} #1 {.#None} #0)
[state] {try.#Success}))))
@@ -121,15 +121,15 @@
[self_name meta.current_module_name
self meta.current_module]
(function (_ state)
- (case (plist.value name (value@ .#definitions self))
+ (case (plist.value name (the .#definitions self))
{.#None}
- {try.#Success [(revised@ .#modules
- (plist.has self_name
- (revised@ .#definitions
- (: (-> (List [Text Global]) (List [Text Global]))
- (|>> {.#Item [name definition]}))
- self))
- state)
+ {try.#Success [(revised .#modules
+ (plist.has self_name
+ (revised .#definitions
+ (: (-> (List [Text Global]) (List [Text Global]))
+ (|>> {.#Item [name definition]}))
+ self))
+ state)
[]]}
{.#Some already_existing}
@@ -140,9 +140,9 @@
(-> Nat Text (Operation Any))
(///extension.lifted
(function (_ state)
- {try.#Success [(revised@ .#modules
- (plist.has name (..empty hash))
- state)
+ {try.#Success [(revised .#modules
+ (plist.has name (..empty hash))
+ state)
[]]})))
(def: .public (with hash name action)
@@ -159,15 +159,15 @@
(-> Text (Operation Any))
(///extension.lifted
(function (_ state)
- (case (|> state (value@ .#modules) (plist.value module_name))
+ (case (|> state (the .#modules) (plist.value module_name))
{.#Some module}
- (let [active? (case (value@ .#module_state module)
+ (let [active? (case (the .#module_state module)
{.#Active} #1
_ #0)]
(if active?
- {try.#Success [(revised@ .#modules
- (plist.has module_name (with@ .#module_state {<tag>} module))
- state)
+ {try.#Success [(revised .#modules
+ (plist.has module_name (has .#module_state {<tag>} module))
+ state)
[]]}
((///extension.up (/.except ..can_only_change_state_of_active_module [module_name {<tag>}]))
state)))
@@ -180,10 +180,10 @@
(-> Text (Operation Bit))
(///extension.lifted
(function (_ state)
- (case (|> state (value@ .#modules) (plist.value module_name))
+ (case (|> state (the .#modules) (plist.value module_name))
{.#Some module}
{try.#Success [state
- (case (value@ .#module_state module)
+ (case (the .#module_state module)
{<tag>} #1
_ #0)]}
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux
index d3187458a..42ccf412d 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux
@@ -32,13 +32,13 @@
(def: (local? name scope)
(-> Text Scope Bit)
(|> scope
- (value@ [.#locals .#mappings])
+ (the [.#locals .#mappings])
(plist.contains? name)))
(def: (local name scope)
(-> Text Scope (Maybe [Type Variable]))
(|> scope
- (value@ [.#locals .#mappings])
+ (the [.#locals .#mappings])
(plist.value name)
(maybe#each (function (_ [type value])
[type {variable.#Local value}]))))
@@ -46,13 +46,13 @@
(def: (captured? name scope)
(-> Text Scope Bit)
(|> scope
- (value@ [.#captured .#mappings])
+ (the [.#captured .#mappings])
(plist.contains? name)))
(def: (captured name scope)
(-> Text Scope (Maybe [Type Variable]))
(loop [idx 0
- mappings (value@ [.#captured .#mappings] scope)]
+ mappings (the [.#captured .#mappings] scope)]
(case mappings
{.#Item [_name [_source_type _source_ref]] mappings'}
(if (text#= name _name)
@@ -81,7 +81,7 @@
(extension.lifted
(function (_ state)
(let [[inner outer] (|> state
- (value@ .#scopes)
+ (the .#scopes)
(list.split_when (|>> (reference? name))))]
(case outer
{.#End}
@@ -92,17 +92,17 @@
(..reference name top_outer))
[ref inner'] (list#mix (: (-> Scope [Variable (List Scope)] [Variable (List Scope)])
(function (_ scope ref+inner)
- [{variable.#Foreign (value@ [.#captured .#counter] scope)}
- {.#Item (revised@ .#captured
- (: (-> Foreign Foreign)
- (|>> (revised@ .#counter ++)
- (revised@ .#mappings (plist.has name [ref_type (product.left ref+inner)]))))
- scope)
+ [{variable.#Foreign (the [.#captured .#counter] scope)}
+ {.#Item (revised .#captured
+ (: (-> Foreign Foreign)
+ (|>> (revised .#counter ++)
+ (revised .#mappings (plist.has name [ref_type (product.left ref+inner)]))))
+ scope)
(product.right ref+inner)}]))
[init_ref {.#End}]
(list.reversed inner))
scopes (list#composite inner' outer)]
- {.#Right [(with@ .#scopes scopes state)
+ {.#Right [(has .#scopes scopes state)
{.#Some [ref_type ref]}]})
)))))
@@ -112,23 +112,23 @@
(def: .public (with_local [name type] action)
(All (_ a) (-> [Text Type] (Operation a) (Operation a)))
(function (_ [bundle state])
- (case (value@ .#scopes state)
+ (case (the .#scopes state)
{.#Item head tail}
- (let [old_mappings (value@ [.#locals .#mappings] head)
- new_var_id (value@ [.#locals .#counter] head)
- new_head (revised@ .#locals
- (: (-> Local Local)
- (|>> (revised@ .#counter ++)
- (revised@ .#mappings (plist.has name [type new_var_id]))))
- head)]
- (case (phase.result' [bundle (with@ .#scopes {.#Item new_head tail} state)]
+ (let [old_mappings (the [.#locals .#mappings] head)
+ new_var_id (the [.#locals .#counter] head)
+ new_head (revised .#locals
+ (: (-> Local Local)
+ (|>> (revised .#counter ++)
+ (revised .#mappings (plist.has name [type new_var_id]))))
+ head)]
+ (case (phase.result' [bundle (has .#scopes {.#Item new_head tail} state)]
action)
{try.#Success [[bundle' state'] output]}
- (case (value@ .#scopes state')
+ (case (the .#scopes state')
{.#Item head' tail'}
- (let [scopes' {.#Item (with@ .#locals (value@ .#locals head) head')
+ (let [scopes' {.#Item (has .#locals (the .#locals head) head')
tail'}]
- {try.#Success [[bundle' (with@ .#scopes scopes' state')]
+ {try.#Success [[bundle' (has .#scopes scopes' state')]
output]})
_
@@ -153,9 +153,9 @@
(def: .public (reset action)
(All (_ a) (-> (Operation a) (Operation a)))
(function (_ [bundle state])
- (case (action [bundle (with@ .#scopes (list ..empty) state)])
+ (case (action [bundle (has .#scopes (list ..empty) state)])
{try.#Success [[bundle' state'] output]}
- {try.#Success [[bundle' (with@ .#scopes (value@ .#scopes state) state')]
+ {try.#Success [[bundle' (has .#scopes (the .#scopes state) state')]
output]}
failure
@@ -164,11 +164,11 @@
(def: .public (with action)
(All (_ a) (-> (Operation a) (Operation [Scope a])))
(function (_ [bundle state])
- (case (action [bundle (revised@ .#scopes (|>> {.#Item ..empty}) state)])
+ (case (action [bundle (revised .#scopes (|>> {.#Item ..empty}) state)])
{try.#Success [[bundle' state'] output]}
- (case (value@ .#scopes state')
+ (case (the .#scopes state')
{.#Item head tail}
- {try.#Success [[bundle' (with@ .#scopes tail state')]
+ {try.#Success [[bundle' (has .#scopes tail state')]
[head output]]}
{.#End}
@@ -181,14 +181,14 @@
(Operation Register)
(extension.lifted
(function (_ state)
- (case (value@ .#scopes state)
+ (case (the .#scopes state)
{.#Item top _}
- {try.#Success [state (value@ [.#locals .#counter] top)]}
+ {try.#Success [state (the [.#locals .#counter] top)]}
{.#End}
(exception.except ..no_scope [])))))
(def: .public environment
(-> Scope (Environment Variable))
- (|>> (value@ [.#captured .#mappings])
+ (|>> (the [.#captured .#mappings])
(list#each (function (_ [_ [_ ref]]) ref))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux
index e8f045d1e..f8002874f 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux
@@ -26,10 +26,10 @@
(def: .public (check action)
(All (_ a) (-> (Check a) (Operation a)))
- (function (_ (^@ stateE [bundle state]))
- (case (action (value@ .#type_context state))
+ (function (_ (^let stateE [bundle state]))
+ (case (action (the .#type_context state))
{try.#Success [context' output]}
- {try.#Success [[bundle (with@ .#type_context context' state)]
+ {try.#Success [[bundle (has .#type_context context' state)]
output]}
{try.#Failure error}
@@ -60,12 +60,12 @@
(def: .public (expecting expected)
(All (_ a) (-> Type (Operation a) (Operation a)))
- (extension.localized (value@ .#expected) (with@ .#expected)
+ (extension.localized (the .#expected) (has .#expected)
(function.constant {.#Some expected})))
(def: .public fresh
(All (_ a) (-> (Operation a) (Operation a)))
- (extension.localized (value@ .#type_context) (with@ .#type_context)
+ (extension.localized (the .#type_context) (has .#type_context)
(function.constant check.fresh_context)))
(def: .public (inference actualT)
@@ -78,8 +78,8 @@
... [pre check.context
... it (check.check expectedT actualT)
... post check.context
- ... .let [pre#var_counter (value@ .#var_counter pre)]]
- ... (if (n.< (value@ .#var_counter post)
+ ... .let [pre#var_counter (the .#var_counter pre)]]
+ ... (if (n.< (the .#var_counter post)
... pre#var_counter)
... (do !
... [.let [new! (: (-> [Nat (Maybe Type)] (Maybe Nat))
@@ -88,7 +88,7 @@
... {.#Some id}
... {.#None})))
... new_vars (|> post
- ... (value@ .#var_bindings)
+ ... (the .#var_bindings)
... (list.all new!))]
... _ (monad.each ! (function (_ @new)
... (do !
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux
index 94b7a7894..d9bf832a3 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux
@@ -52,8 +52,8 @@
(def: .public (merge_requirements left right)
(-> Requirements Requirements Requirements)
- [#imports (list#composite (value@ #imports left) (value@ #imports right))
- #referrals (list#composite (value@ #referrals left) (value@ #referrals right))])
+ [#imports (list#composite (the #imports left) (the #imports right))
+ #referrals (list#composite (the #referrals left) (the #referrals right))])
(template [<special> <general>]
[(type: .public (<special> anchor expression directive)
@@ -71,7 +71,7 @@
(All (_ anchor expression directive)
(Operation anchor expression directive <phase>))
(function (_ [bundle state])
- {try.#Success [[bundle state] (value@ [<component> ..#phase] state)]}))]
+ {try.#Success [[bundle state] (the [<component> ..#phase] state)]}))]
[analysis ..#analysis analysis.Phase]
[synthesis ..#synthesis synthesis.Phase]
@@ -83,8 +83,8 @@
(All (_ anchor expression directive output)
(-> (<operation> output)
(Operation anchor expression directive output)))
- (|>> (phase.sub [(value@ [<component> ..#state])
- (with@ [<component> ..#state])])
+ (|>> (phase.sub [(the [<component> ..#state])
+ (has [<component> ..#state])])
extension.lifted))]
[lifted_analysis ..#analysis analysis.Operation]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux
index 2953b2886..e439110f9 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux
@@ -124,9 +124,9 @@
(All (_ anchor expression directive output) <with_type>)
(function (_ body)
(function (_ [bundle state])
- (case (body [bundle (with@ <tag> {.#Some <with_value>} state)])
+ (case (body [bundle (has <tag> {.#Some <with_value>} state)])
{try.#Success [[bundle' state'] output]}
- {try.#Success [[bundle' (with@ <tag> (value@ <tag> state) state')]
+ {try.#Success [[bundle' (has <tag> (the <tag> state) state')]
output]}
{try.#Failure error}
@@ -135,8 +135,8 @@
(def: .public <get>
(All (_ anchor expression directive)
(Operation anchor expression directive <get_type>))
- (function (_ (^@ stateE [bundle state]))
- (case (value@ <tag> state)
+ (function (_ (^let stateE [bundle state]))
+ (case (the <tag> state)
{.#Some output}
{try.#Success [stateE output]}
@@ -147,7 +147,7 @@
(All (_ anchor expression directive)
(-> <get_type> (Operation anchor expression directive Any)))
(function (_ [bundle state])
- {try.#Success [[bundle (with@ <tag> {.#Some value} state)]
+ {try.#Success [[bundle (has <tag> {.#Some value} state)]
[]]}))]
[#anchor
@@ -168,22 +168,22 @@
(def: .public get_registry
(All (_ anchor expression directive)
(Operation anchor expression directive Registry))
- (function (_ (^@ stateE [bundle state]))
- {try.#Success [stateE (value@ #registry state)]}))
+ (function (_ (^let stateE [bundle state]))
+ {try.#Success [stateE (the #registry state)]}))
(def: .public (set_registry value)
(All (_ anchor expression directive)
(-> Registry (Operation anchor expression directive Any)))
(function (_ [bundle state])
- {try.#Success [[bundle (with@ #registry value state)]
+ {try.#Success [[bundle (has #registry value state)]
[]]}))
(def: .public next
(All (_ anchor expression directive)
(Operation anchor expression directive Nat))
(do phase.monad
- [count (extension.read (value@ #counter))
- _ (extension.update (revised@ #counter ++))]
+ [count (extension.read (the #counter))
+ _ (extension.update (revised #counter ++))]
(in count)))
(def: .public (symbol prefix)
@@ -194,18 +194,18 @@
(def: .public (enter_module module)
(All (_ anchor expression directive)
(-> descriptor.Module (Operation anchor expression directive Any)))
- (extension.update (with@ #module module)))
+ (extension.update (has #module module)))
(def: .public module
(All (_ anchor expression directive)
(Operation anchor expression directive descriptor.Module))
- (extension.read (value@ #module)))
+ (extension.read (the #module)))
(def: .public (evaluate! label code)
(All (_ anchor expression directive)
(-> unit.ID [(Maybe unit.ID) expression] (Operation anchor expression directive Any)))
- (function (_ (^@ state+ [bundle state]))
- (case (# (value@ #host state) evaluate label code)
+ (function (_ (^let state+ [bundle state]))
+ (case (# (the #host state) evaluate label code)
{try.#Success output}
{try.#Success [state+ output]}
@@ -215,8 +215,8 @@
(def: .public (execute! code)
(All (_ anchor expression directive)
(-> directive (Operation anchor expression directive Any)))
- (function (_ (^@ state+ [bundle state]))
- (case (# (value@ #host state) execute code)
+ (function (_ (^let state+ [bundle state]))
+ (case (# (the #host state) execute code)
{try.#Success output}
{try.#Success [state+ output]}
@@ -226,8 +226,8 @@
(def: .public (define! context custom code)
(All (_ anchor expression directive)
(-> unit.ID (Maybe Text) [(Maybe unit.ID) expression] (Operation anchor expression directive [Text Any directive])))
- (function (_ (^@ stateE [bundle state]))
- (case (# (value@ #host state) define context custom code)
+ (function (_ (^let stateE [bundle state]))
+ (case (# (the #host state) define context custom code)
{try.#Success output}
{try.#Success [stateE output]}
@@ -238,13 +238,13 @@
(All (_ anchor expression directive)
(-> artifact.ID (Maybe Text) directive (Operation anchor expression directive Any)))
(do [! phase.monad]
- [?buffer (extension.read (value@ #buffer))]
+ [?buffer (extension.read (the #buffer))]
(case ?buffer
{.#Some buffer}
... TODO: Optimize by no longer checking for overwrites...
(if (sequence.any? (|>> product.left (n.= artifact_id)) buffer)
(phase.except ..cannot_overwrite_output [artifact_id])
- (extension.update (with@ #buffer {.#Some (sequence.suffix [artifact_id custom code] buffer)})))
+ (extension.update (has #buffer {.#Some (sequence.suffix [artifact_id custom code] buffer)})))
{.#None}
(phase.except ..no_buffer_for_saving_code [artifact_id]))))
@@ -253,9 +253,9 @@
[(`` (def: .public (<name> it (~~ (template.spliced <inputs>)) dependencies)
(All (_ anchor expression directive)
(-> <type> (~~ (template.spliced <input_types>)) (Set unit.ID) (Operation anchor expression directive artifact.ID)))
- (function (_ (^@ stateE [bundle state]))
- (let [[id registry'] (<artifact> it <mandatory?> dependencies (value@ #registry state))]
- {try.#Success [[bundle (with@ #registry registry' state)]
+ (function (_ (^let stateE [bundle state]))
+ (let [[id registry'] (<artifact> it <mandatory?> dependencies (the #registry state))]
+ {try.#Success [[bundle (has #registry registry' state)]
id]}))))]
[category.Definition mandatory? [mandatory?] [Bit] learn registry.definition]
@@ -276,12 +276,12 @@
(def: .public (remember archive name)
(All (_ anchor expression directive)
(-> Archive Symbol (Operation anchor expression directive unit.ID)))
- (function (_ (^@ stateE [bundle state]))
+ (function (_ (^let stateE [bundle state]))
(let [[_module _name] name]
(do try.monad
[@module (archive.id _module archive)
- registry (if (text#= (value@ #module state) _module)
- {try.#Success (value@ #registry state)}
+ registry (if (text#= (the #module state) _module)
+ {try.#Success (the #registry state)}
(do try.monad
[[_module output registry] (archive.find _module archive)]
{try.#Success registry}))]
@@ -295,12 +295,12 @@
(def: .public (definition archive name)
(All (_ anchor expression directive)
(-> Archive Symbol (Operation anchor expression directive [unit.ID (Maybe category.Definition)])))
- (function (_ (^@ stateE [bundle state]))
+ (function (_ (^let stateE [bundle state]))
(let [[_module _name] name]
(do try.monad
[@module (archive.id _module archive)
- registry (if (text#= (value@ #module state) _module)
- {try.#Success (value@ #registry state)}
+ registry (if (text#= (the #module state) _module)
+ {try.#Success (the #registry state)}
(do try.monad
[[_module output registry] (archive.find _module archive)]
{try.#Success registry}))]
@@ -316,7 +316,7 @@
(def: .public (module_id module archive)
(All (_ anchor expression directive)
(-> descriptor.Module Archive (Operation anchor expression directive module.ID)))
- (function (_ (^@ stateE [bundle state]))
+ (function (_ (^let stateE [bundle state]))
(do try.monad
[@module (archive.id module archive)]
(in [stateE @module]))))
@@ -324,14 +324,14 @@
(def: .public (context archive)
(All (_ anchor expression directive)
(-> Archive (Operation anchor expression directive unit.ID)))
- (function (_ (^@ stateE [bundle state]))
- (case (value@ #context state)
+ (function (_ (^let stateE [bundle state]))
+ (case (the #context state)
{.#None}
(exception.except ..no_context [])
{.#Some id}
(do try.monad
- [@module (archive.id (value@ #module state) archive)]
+ [@module (archive.id (the #module state) archive)]
(in [stateE [@module id]])))))
(def: .public (with_context @artifact body)
@@ -341,8 +341,8 @@
(Operation anchor expression directive a)))
(function (_ [bundle state])
(do try.monad
- [[[bundle' state'] output] (body [bundle (with@ #context {.#Some @artifact} state)])]
- (in [[bundle' (with@ #context (value@ #context state) state')]
+ [[[bundle' state'] output] (body [bundle (has #context {.#Some @artifact} state)])]
+ (in [[bundle' (has #context (the #context state) state')]
output]))))
(def: .public (with_registry_shift shift body)
@@ -352,24 +352,24 @@
(Operation anchor expression directive a)))
(function (_ [bundle state])
(do try.monad
- [[[bundle' state'] output] (body [bundle (with@ #registry_shift shift state)])]
- (in [[bundle' (with@ #registry_shift (value@ #registry_shift state) state')]
+ [[[bundle' state'] output] (body [bundle (has #registry_shift shift state)])]
+ (in [[bundle' (has #registry_shift (the #registry_shift state) state')]
output]))))
(def: .public (with_new_context archive dependencies body)
(All (_ anchor expression directive a)
(-> Archive (Set unit.ID) (Operation anchor expression directive a)
(Operation anchor expression directive [unit.ID a])))
- (function (_ (^@ stateE [bundle state]))
- (let [[@artifact registry'] (registry.resource false dependencies (value@ #registry state))
- @artifact (n.+ @artifact (value@ #registry_shift state))]
+ (function (_ (^let stateE [bundle state]))
+ (let [[@artifact registry'] (registry.resource false dependencies (the #registry state))
+ @artifact (n.+ @artifact (the #registry_shift state))]
(do try.monad
[[[bundle' state'] output] (body [bundle (|> state
- (with@ #registry registry')
- (with@ #context {.#Some @artifact})
- (revised@ #interim_artifacts (|>> {.#Item @artifact})))])
- @module (archive.id (value@ #module state) archive)]
- (in [[bundle' (with@ #context (value@ #context state) state')]
+ (has #registry registry')
+ (has #context {.#Some @artifact})
+ (revised #interim_artifacts (|>> {.#Item @artifact})))])
+ @module (archive.id (the #module state) archive)]
+ (in [[bundle' (has #context (the #context state) state')]
[[@module @artifact]
output]])))))
@@ -378,7 +378,7 @@
(-> Text (Operation anchor expression directive Any)))
(function (_ [bundle state])
{try.#Success [[bundle
- (revised@ #log (sequence.suffix message) state)]
+ (revised #log (sequence.suffix message) state)]
[]]}))
(def: .public (with_interim_artifacts archive body)
@@ -386,12 +386,12 @@
(-> Archive (Operation anchor expression directive a)
(Operation anchor expression directive [(List unit.ID) a])))
(do phase.monad
- [module (extension.read (value@ #module))]
+ [module (extension.read (the #module))]
(function (_ state+)
(do try.monad
[@module (archive.id module archive)
[[bundle' state'] output] (body state+)]
(in [[bundle'
- (with@ #interim_artifacts (list) state')]
- [(list#each (|>> [@module]) (value@ #interim_artifacts state'))
+ (has #interim_artifacts (list) state')]
+ [(list#each (|>> [@module]) (the #interim_artifacts state'))
output]])))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux
index 7b24ab177..f38a33f0d 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux
@@ -48,7 +48,7 @@
{.#Definition [exported? actualT _]}
(do !
[_ (/type.inference actualT)
- (^@ def_name [::module ::name]) (///extension.lifted (meta.normal def_name))
+ (^let def_name [::module ::name]) (///extension.lifted (meta.normal def_name))
current (///extension.lifted meta.current_module_name)]
(if (text#= current ::module)
<return>
@@ -63,7 +63,7 @@
{.#Type [exported? value labels]}
(do !
[_ (/type.inference .Type)
- (^@ def_name [::module ::name]) (///extension.lifted (meta.normal def_name))
+ (^let def_name [::module ::name]) (///extension.lifted (meta.normal def_name))
current (///extension.lifted meta.current_module_name)]
(if (text#= current ::module)
<return>
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux
index 670b54765..f5be4859f 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux
@@ -82,13 +82,13 @@
(do [! //.monad]
[state //.state
.let [compiler_eval (meta_eval archive
- (value@ [//extension.#state /.#analysis /.#state //extension.#bundle] state)
+ (the [//extension.#state /.#analysis /.#state //extension.#bundle] state)
(evaluation.evaluator expander
- (value@ [//extension.#state /.#synthesis /.#state] state)
- (value@ [//extension.#state /.#generation /.#state] state)
- (value@ [//extension.#state /.#generation /.#phase] state)))
+ (the [//extension.#state /.#synthesis /.#state] state)
+ (the [//extension.#state /.#generation /.#state] state)
+ (the [//extension.#state /.#generation /.#phase] state)))
extension_eval (:as Eval (wrapper (:expected compiler_eval)))]
- _ (//.with (with@ [//extension.#state /.#analysis /.#state //extension.#state .#eval] extension_eval state))]
+ _ (//.with (has [//extension.#state /.#analysis /.#state //extension.#state .#eval] extension_eval state))]
(case code
(^ [_ {.#Form (list& [_ {.#Text name}] inputs)}])
(//extension.apply archive again [name inputs])
@@ -116,7 +116,7 @@
(case expansion
(^ (list& <lux_def_module> referrals))
(|> (again archive <lux_def_module>)
- (# ! each (revised@ /.#referrals (list#composite referrals))))
+ (# ! each (revised /.#referrals (list#composite referrals))))
_
(..requiring again archive expansion)))
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 0f1848eff..b4e91c905 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
@@ -117,7 +117,7 @@
(def: .public (apply archive phase [name parameters])
(All (_ s i o)
(-> Archive (Phase s i o) (Extension i) (Operation s i o o)))
- (function (_ (^@ stateE [bundle state]))
+ (function (_ (^let stateE [bundle state]))
(case (dictionary.value name bundle)
{.#Some handler}
(((handler name phase) archive parameters)
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 3374c4ba4..a69d511f3 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
@@ -894,9 +894,9 @@
selfT {.#Primitive name (list#each product.right parameters)}]
state (extension.lifted phase.state)
methods (monad.each ! (..method_definition archive super interfaces [mapping selfT]
- [(value@ [directive.#analysis directive.#phase] state)
- (value@ [directive.#synthesis directive.#phase] state)
- (value@ [directive.#generation directive.#phase] state)])
+ [(the [directive.#analysis directive.#phase] state)
+ (the [directive.#synthesis directive.#phase] state)
+ (the [directive.#generation directive.#phase] state)])
methods)
.let [all_dependencies (cache.all (list#each product.left methods))]
bytecode (<| (# ! each (format.result class.writer))
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 889d400b0..3680787de 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
@@ -99,9 +99,9 @@
(-> Archive Type Code (Operation anchor expression directive [Type expression Any])))
(do phase.monad
[state (///.lifted phase.state)
- .let [analyse (value@ [/////directive.#analysis /////directive.#phase] state)
- synthesize (value@ [/////directive.#synthesis /////directive.#phase] state)
- generate (value@ [/////directive.#generation /////directive.#phase] state)]
+ .let [analyse (the [/////directive.#analysis /////directive.#phase] state)
+ synthesize (the [/////directive.#synthesis /////directive.#phase] state)
+ generate (the [/////directive.#generation /////directive.#phase] state)]
[_ codeA] (<| /////directive.lifted_analysis
scope.with
typeA.fresh
@@ -145,9 +145,9 @@
(Operation anchor expression directive [Type expression Any])))
(do [! phase.monad]
[state (///.lifted phase.state)
- .let [analyse (value@ [/////directive.#analysis /////directive.#phase] state)
- synthesize (value@ [/////directive.#synthesis /////directive.#phase] state)
- generate (value@ [/////directive.#generation /////directive.#phase] state)]
+ .let [analyse (the [/////directive.#analysis /////directive.#phase] state)
+ synthesize (the [/////directive.#synthesis /////directive.#phase] state)
+ generate (the [/////directive.#generation /////directive.#phase] state)]
[_ code//type codeA] (/////directive.lifted_analysis
(scope.with
(typeA.fresh
@@ -198,9 +198,9 @@
(Operation anchor expression directive [expression Any])))
(do phase.monad
[state (///.lifted phase.state)
- .let [analyse (value@ [/////directive.#analysis /////directive.#phase] state)
- synthesize (value@ [/////directive.#synthesis /////directive.#phase] state)
- generate (value@ [/////directive.#generation /////directive.#phase] state)]
+ .let [analyse (the [/////directive.#analysis /////directive.#phase] state)
+ synthesize (the [/////directive.#synthesis /////directive.#phase] state)
+ generate (the [/////directive.#generation /////directive.#phase] state)]
[_ codeA] (<| /////directive.lifted_analysis
scope.with
typeA.fresh
@@ -223,17 +223,17 @@
(do phase.monad
[[bundle state] phase.state
.let [eval (/////analysis/evaluation.evaluator expander
- (value@ [/////directive.#synthesis /////directive.#state] state)
- (value@ [/////directive.#generation /////directive.#state] state)
- (value@ [/////directive.#generation /////directive.#phase] state))
- previous_analysis_extensions (value@ [/////directive.#analysis /////directive.#state ///.#bundle] state)]]
+ (the [/////directive.#synthesis /////directive.#state] state)
+ (the [/////directive.#generation /////directive.#state] state)
+ (the [/////directive.#generation /////directive.#phase] state))
+ previous_analysis_extensions (the [/////directive.#analysis /////directive.#state ///.#bundle] state)]]
(phase.with [bundle
- (revised@ [/////directive.#analysis /////directive.#state]
- (: (-> /////analysis.State+ /////analysis.State+)
- (|>> product.right
- [(|> previous_analysis_extensions
- (dictionary.merged (///analysis.bundle eval host_analysis)))]))
- state)])))
+ (revised [/////directive.#analysis /////directive.#state]
+ (: (-> /////analysis.State+ /////analysis.State+)
+ (|>> product.right
+ [(|> previous_analysis_extensions
+ (dictionary.merged (///analysis.bundle eval host_analysis)))]))
+ state)])))
(def: (announce_definition! short type)
(All (_ anchor expression directive)
@@ -369,8 +369,8 @@
(function (_ extension_name phase archive [alias def_name])
(do phase.monad
[_ (///.lifted
- (phase.sub [(value@ [/////directive.#analysis /////directive.#state])
- (with@ [/////directive.#analysis /////directive.#state])]
+ (phase.sub [(the [/////directive.#analysis /////directive.#state])
+ (has [/////directive.#analysis /////directive.#state])]
(define_alias alias def_name)))]
(in /////directive.no_requirements)))]))
@@ -522,9 +522,9 @@
(^ (list programC))
(do phase.monad
[state (///.lifted phase.state)
- .let [analyse (value@ [/////directive.#analysis /////directive.#phase] state)
- synthesize (value@ [/////directive.#synthesis /////directive.#phase] state)
- generate (value@ [/////directive.#generation /////directive.#phase] state)]
+ .let [analyse (the [/////directive.#analysis /////directive.#phase] state)
+ synthesize (the [/////directive.#synthesis /////directive.#phase] state)
+ generate (the [/////directive.#generation /////directive.#phase] state)]
programS (prepare_program archive analyse synthesize programC)
current_module (/////directive.lifted_analysis
(///.lifted meta.current_module_name))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux
index 0f063ea82..09ab89d42 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux
@@ -1,39 +1,39 @@
(.using
- [library
- [lux {"-" case let if}
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- ["[0]" exception {"+" exception:}]]
- [data
- ["[0]" text
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" functor mix monoid)]
- ["[0]" set]]]
- [math
- [number
- ["n" nat]]]
- [target
- ["_" common_lisp {"+" Expression Var/1}]]]]
- ["[0]" // "_"
- ["[1][0]" runtime {"+" Operation Phase Generator}]
+ [library
+ [lux {"-" case let if}
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ ["[0]" exception {"+" exception:}]]
+ [data
+ ["[0]" text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor mix monoid)]
+ ["[0]" set]]]
+ [math
+ [number
+ ["n" nat]]]
+ [target
+ ["_" common_lisp {"+" Expression Var/1}]]]]
+ ["[0]" // "_"
+ ["[1][0]" runtime {"+" Operation Phase Generator}]
+ ["[1][0]" reference]
+ ["[1][0]" primitive]
+ ["/[1]" // "_"
["[1][0]" reference]
- ["[1][0]" primitive]
["/[1]" // "_"
- ["[1][0]" reference]
+ ["[1][0]" synthesis "_"
+ ["[1]/[0]" case]]
["/[1]" // "_"
- ["[1][0]" synthesis "_"
- ["[1]/[0]" case]]
- ["/[1]" // "_"
- ["[1][0]" synthesis {"+" Member Synthesis Path}]
- ["[1][0]" generation]
- ["//[1]" /// "_"
- [reference
- ["[1][0]" variable {"+" Register}]]
- ["[1][0]" phase ("[1]#[0]" monad)]
- [meta
- [archive {"+" Archive}]]]]]]])
+ ["[1][0]" synthesis {"+" Member Synthesis Path}]
+ ["[1][0]" generation]
+ ["//[1]" /// "_"
+ [reference
+ ["[1][0]" variable {"+" Register}]]
+ ["[1][0]" phase ("[1]#[0]" monad)]
+ [meta
+ [archive {"+" Archive}]]]]]]])
(def: .public register
(-> Register Var/1)
@@ -248,7 +248,7 @@
pattern_matching! (pattern_matching $output expression archive pathP)
.let [storage (|> pathP
////synthesis/case.storage
- (value@ ////synthesis/case.#bindings)
+ (the ////synthesis/case.#bindings)
set.list
(list#each (function (_ register)
[(..register register)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux
index 4a5ee59f0..c90729050 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux
@@ -97,9 +97,9 @@
(do ///////phase.monad
[valueO (expression archive valueS)]
(in (list#mix (function (_ side source)
- (.let [method (.if (value@ member.#right? side)
- (//runtime.tuple//right (_.i32 (.int (value@ member.#lefts side))))
- (//runtime.tuple//left (_.i32 (.int (value@ member.#lefts side)))))]
+ (.let [method (.if (the member.#right? side)
+ (//runtime.tuple//right (_.i32 (.int (the member.#lefts side))))
+ (//runtime.tuple//left (_.i32 (.int (the member.#lefts side)))))]
(method source)))
valueO
(list.reversed pathP)))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux
index 325700c72..6504a5f55 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux
@@ -300,9 +300,9 @@
(do phase.monad
[record! (phase archive recordS)]
(in (list#mix (function (_ step so_far!)
- (.let [next! (.if (value@ member.#right? step)
- (..right_projection (value@ member.#lefts step))
- (..left_projection (value@ member.#lefts step)))]
+ (.let [next! (.if (the member.#right? step)
+ (..right_projection (the member.#lefts step))
+ (..left_projection (the member.#lefts step)))]
($_ _.composite
so_far!
next!)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux
index 1ad5f6df6..7e879516a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux
@@ -83,9 +83,9 @@
(do ///////phase.monad
[valueO (expression archive valueS)]
(in (list#mix (function (_ side source)
- (.let [method (.if (value@ member.#right? side)
- (//runtime.tuple//right (_.int (.int (value@ member.#lefts side))))
- (//runtime.tuple//left (_.int (.int (value@ member.#lefts side)))))]
+ (.let [method (.if (the member.#right? side)
+ (//runtime.tuple//right (_.int (.int (the member.#lefts side))))
+ (//runtime.tuple//left (_.int (.int (the member.#lefts side)))))]
(method source)))
valueO
(list.reversed pathP)))))
@@ -271,7 +271,7 @@
(def: .public dependencies
(-> Path (List Var))
(|>> ////synthesis/case.storage
- (value@ ////synthesis/case.#dependencies)
+ (the ////synthesis/case.#dependencies)
set.list
(list#each (function (_ variable)
(.case variable
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux
index d65c81d6a..54685bfff 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux
@@ -1,38 +1,38 @@
(.using
- [library
- [lux {"-" case let if}
- [abstract
- ["[0]" monad {"+" do}]]
- [data
- ["[0]" product]
- ["[0]" text
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" functor mix)]
- ["[0]" set]]]
- [math
- [number
- ["i" int]]]
- [target
- ["_" php {"+" Expression Var Statement}]]]]
- ["[0]" // "_"
- ["[1][0]" runtime {"+" Operation Phase Phase! Generator Generator!}]
+ [library
+ [lux {"-" case let if}
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [data
+ ["[0]" product]
+ ["[0]" text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor mix)]
+ ["[0]" set]]]
+ [math
+ [number
+ ["i" int]]]
+ [target
+ ["_" php {"+" Expression Var Statement}]]]]
+ ["[0]" // "_"
+ ["[1][0]" runtime {"+" Operation Phase Phase! Generator Generator!}]
+ ["[1][0]" reference]
+ ["[1][0]" primitive]
+ ["/[1]" // "_"
["[1][0]" reference]
- ["[1][0]" primitive]
["/[1]" // "_"
- ["[1][0]" reference]
+ ["[1][0]" synthesis "_"
+ ["[1]/[0]" case]]
["/[1]" // "_"
- ["[1][0]" synthesis "_"
- ["[1]/[0]" case]]
- ["/[1]" // "_"
- ["[1][0]" synthesis {"+" Member Synthesis Path}]
- ["[1][0]" generation]
- ["//[1]" /// "_"
- [reference
- ["[1][0]" variable {"+" Register}]]
- ["[1][0]" phase ("[1]#[0]" monad)]
- [meta
- [archive {"+" Archive}]]]]]]])
+ ["[1][0]" synthesis {"+" Member Synthesis Path}]
+ ["[1][0]" generation]
+ ["//[1]" /// "_"
+ [reference
+ ["[1][0]" variable {"+" Register}]]
+ ["[1][0]" phase ("[1]#[0]" monad)]
+ [meta
+ [archive {"+" Archive}]]]]]]])
(def: .public register
(-> Register Var)
@@ -260,7 +260,7 @@
(def: .public dependencies
(-> Path (List Var))
(|>> ////synthesis/case.storage
- (value@ ////synthesis/case.#dependencies)
+ (the ////synthesis/case.#dependencies)
set.list
(list#each (function (_ variable)
(.case variable
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux
index 8b10f2833..bfb3ebdc8 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux
@@ -110,10 +110,10 @@
(do ///////phase.monad
[valueO (expression archive valueS)]
(in (list#mix (function (_ side source)
- (.let [method (.if (value@ member.#right? side)
+ (.let [method (.if (the member.#right? side)
//runtime.tuple::right
//runtime.tuple::left)]
- (method (_.int (.int (value@ member.#lefts side)))
+ (method (_.int (.int (the member.#lefts side)))
source)))
valueO
(list.reversed pathP)))))
@@ -320,7 +320,7 @@
(def: .public dependencies
(-> Path (List SVar))
(|>> case.storage
- (value@ case.#dependencies)
+ (the case.#dependencies)
set.list
(list#each (function (_ variable)
(.case variable
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux
index ec725005a..d4abe4b2b 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux
@@ -111,9 +111,9 @@
(do ///////phase.monad
[valueO (expression archive valueS)]
(in (list#mix (function (_ side source)
- (.let [method (.if (value@ member.#right? side)
- (//runtime.tuple//right (_.int (.int (value@ member.#lefts side))))
- (//runtime.tuple//left (_.int (.int (value@ member.#lefts side)))))]
+ (.let [method (.if (the member.#right? side)
+ (//runtime.tuple//right (_.int (.int (the member.#lefts side))))
+ (//runtime.tuple//left (_.int (.int (the member.#lefts side)))))]
(method source)))
valueO
(list.reversed pathP)))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux
index d711e963a..ae74e45f3 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux
@@ -62,8 +62,8 @@
(case structure
{///complex.#Variant variant}
(do phase.monad
- [valueS (optimization' (value@ ///complex.#value variant))]
- (in (/.variant (with@ ///complex.#value valueS variant))))
+ [valueS (optimization' (the ///complex.#value variant))]
+ (in (/.variant (has ///complex.#value valueS variant))))
{///complex.#Tuple tuple}
(|> tuple
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 ebab6fe8a..1bf6357f7 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
@@ -371,8 +371,8 @@
path_storage
(^ (/.path/bind register))
- (revised@ #bindings (set.has register)
- path_storage)
+ (revised #bindings (set.has register)
+ path_storage)
{/.#Bit_Fork _ default otherwise}
(|> (case otherwise
@@ -410,12 +410,12 @@
(list#mix for_synthesis synthesis_storage members)
{/.#Reference {///reference.#Variable {///reference/variable.#Local register}}}
- (if (set.member? (value@ #bindings synthesis_storage) register)
+ (if (set.member? (the #bindings synthesis_storage) register)
synthesis_storage
- (revised@ #dependencies (set.has {///reference/variable.#Local register}) synthesis_storage))
+ (revised #dependencies (set.has {///reference/variable.#Local register}) synthesis_storage))
{/.#Reference {///reference.#Variable var}}
- (revised@ #dependencies (set.has var) synthesis_storage)
+ (revised #dependencies (set.has var) synthesis_storage)
(^ (/.function/apply [functionS argsS]))
(list#mix for_synthesis synthesis_storage {.#Item functionS argsS})
@@ -424,20 +424,20 @@
(list#mix for_synthesis synthesis_storage environment)
(^ (/.branch/case [inputS pathS]))
- (revised@ #dependencies
- (set.union (value@ #dependencies (for_path pathS synthesis_storage)))
- (for_synthesis inputS synthesis_storage))
+ (revised #dependencies
+ (set.union (the #dependencies (for_path pathS synthesis_storage)))
+ (for_synthesis inputS synthesis_storage))
(^ (/.branch/exec [before after]))
(list#mix for_synthesis synthesis_storage (list before after))
(^ (/.branch/let [inputS register exprS]))
- (revised@ #dependencies
- (set.union (|> synthesis_storage
- (revised@ #bindings (set.has register))
- (for_synthesis exprS)
- (value@ #dependencies)))
- (for_synthesis inputS synthesis_storage))
+ (revised #dependencies
+ (set.union (|> synthesis_storage
+ (revised #bindings (set.has register))
+ (for_synthesis exprS)
+ (the #dependencies)))
+ (for_synthesis inputS synthesis_storage))
(^ (/.branch/if [testS thenS elseS]))
(list#mix for_synthesis synthesis_storage (list testS thenS elseS))
@@ -446,15 +446,15 @@
(for_synthesis whole synthesis_storage)
(^ (/.loop/scope [start initsS+ iterationS]))
- (revised@ #dependencies
- (set.union (|> synthesis_storage
- (revised@ #bindings (set.union (|> initsS+
- list.enumeration
- (list#each (|>> product.left (n.+ start)))
- (set.of_list n.hash))))
- (for_synthesis iterationS)
- (value@ #dependencies)))
- (list#mix for_synthesis synthesis_storage initsS+))
+ (revised #dependencies
+ (set.union (|> synthesis_storage
+ (revised #bindings (set.union (|> initsS+
+ list.enumeration
+ (list#each (|>> product.left (n.+ start)))
+ (set.of_list n.hash))))
+ (for_synthesis iterationS)
+ (the #dependencies)))
+ (list#mix for_synthesis synthesis_storage initsS+))
(^ (/.loop/again replacementsS+))
(list#mix for_synthesis synthesis_storage replacementsS+)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux
index 8e37a6714..c08117adc 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux
@@ -57,7 +57,7 @@
(with_expansions [<apply> (as_is (/.function/apply [funcS argsS]))]
(case funcS
(^ (/.function/abstraction functionS))
- (if (n.= (value@ /.#arity functionS)
+ (if (n.= (the /.#arity functionS)
(list.size argsS))
(do !
[locals /.locals]
@@ -279,7 +279,7 @@
(case (//loop.optimization false 1 (list) abstraction)
{.#Some [startL initsL bodyL]}
[/.#environment environment
- /.#arity (value@ /.#arity abstraction)
+ /.#arity (the /.#arity abstraction)
/.#body (/.loop/scope [startL initsL bodyL])]
{.#None}
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux
index 75ddb63b0..f3d6b8b68 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux
@@ -87,9 +87,9 @@
(case structure
{analysis/complex.#Variant variant}
(do maybe.monad
- [value' (|> variant (value@ analysis/complex.#value) (again false))]
+ [value' (|> variant (the analysis/complex.#value) (again false))]
(in (|> variant
- (with@ analysis/complex.#value value')
+ (has analysis/complex.#value value')
/.variant)))
{analysis/complex.#Tuple tuple}
@@ -148,10 +148,10 @@
(^ (/.loop/scope scope))
(do [! maybe.monad]
[inits' (|> scope
- (value@ /.#inits)
+ (the /.#inits)
(monad.each ! (again false)))
- iteration' (again return? (value@ /.#iteration scope))]
- (in (/.loop/scope [/.#start (|> scope (value@ /.#start) (register_optimization offset))
+ iteration' (again return? (the /.#iteration scope))]
+ (in (/.loop/scope [/.#start (|> scope (the /.#start) (register_optimization offset))
/.#inits inits'
/.#iteration iteration'])))
@@ -211,6 +211,6 @@
(def: .public (optimization true_loop? offset inits functionS)
(-> Bit Register (List Synthesis) Abstraction (Maybe [Register (List Synthesis) Synthesis]))
- (|> (value@ /.#body functionS)
- (body_optimization true_loop? offset (value@ /.#environment functionS) (value@ /.#arity functionS))
+ (|> (the /.#body functionS)
+ (body_optimization true_loop? offset (the /.#environment functionS) (the /.#arity functionS))
(maybe#each (|>> [offset inits]))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux
index 1108cfbc4..0b1d000b4 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux
@@ -205,7 +205,7 @@
(:expected <<otherwise>>))])
(template: (!horizontal where offset source_code)
- [[(revised@ .#column ++ where)
+ [[(revised .#column ++ where)
(!++ offset)
source_code]])
@@ -264,7 +264,7 @@
(<| (let [g!content (!clip offset g!end source_code)])
(!guarantee_no_new_lines where offset source_code g!content)
{.#Right [[(let [size (!n/- offset g!end)]
- (revised@ .#column (|>> (!n/+ size) (!n/+ 2)) where))
+ (revised .#column (|>> (!n/+ size) (!n/+ 2)) where))
(!++ g!end)
source_code]
[where
@@ -410,7 +410,7 @@
(signed_parser source_code//size offset where (!++/2 offset) source_code)
(!full_symbol_parser offset [where (!++ offset) source_code] where @aliases .#Symbol)))])
-(with_expansions [<output> {.#Right [[(revised@ .#column (|>> (!n/+ (!n/- start end))) where)
+(with_expansions [<output> {.#Right [[(revised .#column (|>> (!n/+ (!n/- start end))) where)
end
source_code]
(!clip start end source_code)]}]
@@ -483,7 +483,7 @@
(def: (bit_syntax value [where offset/0 source_code])
(-> Bit (Parser Code))
- {.#Right [[(revised@ .#column (|>> !++/2) where)
+ {.#Right [[(revised .#column (|>> !++/2) where)
(!++/2 offset/0)
source_code]
[where {.#Bit value}]]})
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux
index 819c44a5f..1d8b9e6d3 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux
@@ -203,11 +203,11 @@
(template [<with> <query> <tag> <type>]
[(def: .public (<with> value)
(-> <type> (All (_ a) (-> (Operation a) (Operation a))))
- (extension.temporary (with@ <tag> value)))
+ (extension.temporary (has <tag> value)))
(def: .public <query>
(Operation <type>)
- (extension.read (value@ <tag>)))]
+ (extension.read (the <tag>)))]
[with_locals locals #locals Nat]
[with_currying? currying? #currying? Bit]
@@ -383,12 +383,12 @@
{#Loop loop}
(case loop
{#Scope scope}
- (|> (format (%.nat (value@ #start scope))
- " " (|> (value@ #inits scope)
+ (|> (format (%.nat (the #start scope))
+ " " (|> (the #inits scope)
(list#each %synthesis)
(text.interposed " ")
(text.enclosed ["[" "]"]))
- " " (%synthesis (value@ #iteration scope)))
+ " " (%synthesis (the #iteration scope)))
(text.enclosed ["{#loop " "}"]))
{#Again args}
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/member.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/member.lux
index 4e1ed910b..e6c9fb680 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/member.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/member.lux
@@ -20,7 +20,7 @@
(def: .public (format it)
(%.Format Member)
- (%.format "[" (%.nat (value@ #lefts it)) " " (%.bit (value@ #right? it)) "]"))
+ (%.format "[" (%.nat (the #lefts it)) " " (%.bit (the #right? it)) "]"))
(def: .public hash
(Hash Member)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/side.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/side.lux
index dd9bf4223..045681ac2 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/side.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/side.lux
@@ -20,7 +20,7 @@
(def: .public (format it)
(%.Format Side)
- (%.format "{" (%.nat (value@ #lefts it)) " " (%.bit (value@ #right? it)) "}"))
+ (%.format "{" (%.nat (the #lefts it)) " " (%.bit (the #right? it)) "}"))
(def: .public hash
(Hash Side)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux
index 4ec08ed90..a63bde0a1 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux
@@ -1,6 +1,6 @@
(.using
[library
- [lux {"-" Module}
+ [lux {"-" Module has}
[abstract
["[0]" equivalence {"+" Equivalence}]
["[0]" monad {"+" do}]]
@@ -79,7 +79,7 @@
(def: next
(-> Archive module.ID)
- (|>> :representation (value@ #next)))
+ (|>> :representation (the #next)))
(def: .public empty
Archive
@@ -108,8 +108,8 @@
{try.#Success [/#next
(|> archive
:representation
- (revised@ #resolver (dictionary.has module [/#next (: (Maybe (Entry Any)) {.#None})]))
- (revised@ #next ++)
+ (revised #resolver (dictionary.has module [/#next (: (Maybe (Entry Any)) {.#None})]))
+ (revised #next ++)
:abstraction)]})))
(def: .public (has module entry archive)
@@ -119,15 +119,15 @@
{.#Some [id {.#None}]}
{try.#Success (|> archive
:representation
- (revised@ ..#resolver (dictionary.has module [id {.#Some entry}]))
+ (revised ..#resolver (dictionary.has module [id {.#Some entry}]))
:abstraction)}
{.#Some [id {.#Some [existing_module existing_output existing_registry]}]}
- (if (same? (value@ module.#document existing_module)
- (value@ [#module module.#document] entry))
+ (if (same? (the module.#document existing_module)
+ (the [#module module.#document] entry))
... TODO: Find out why this code allows for the same module to be added more than once. It looks fishy...
{try.#Success archive}
- (exception.except ..cannot_replace_document [module (value@ module.#document existing_module) (value@ [#module module.#document] entry)]))
+ (exception.except ..cannot_replace_document [module (the module.#document existing_module) (the [#module module.#document] entry)]))
{.#None}
(exception.except ..module_must_be_reserved_before_it_can_be_added [module]))))
@@ -135,7 +135,7 @@
(def: .public entries
(-> Archive (List [descriptor.Module [module.ID (Entry Any)]]))
(|>> :representation
- (value@ #resolver)
+ (the #resolver)
dictionary.entries
(list.all (function (_ [module [module_id entry]])
(# maybe.monad each (|>> [module_id] [module]) entry)))))
@@ -165,7 +165,7 @@
(def: .public archived
(-> Archive (List descriptor.Module))
(|>> :representation
- (value@ #resolver)
+ (the #resolver)
dictionary.entries
(list.all (function (_ [module [id descriptor+document]])
(case descriptor+document
@@ -185,13 +185,13 @@
(def: .public reserved
(-> Archive (List descriptor.Module))
(|>> :representation
- (value@ #resolver)
+ (the #resolver)
dictionary.keys))
(def: .public reservations
(-> Archive (List [descriptor.Module module.ID]))
(|>> :representation
- (value@ #resolver)
+ (the #resolver)
dictionary.entries
(list#each (function (_ [module [id _]])
[module id]))))
@@ -201,17 +201,17 @@
(let [[+next +resolver] (:representation additions)]
(|> archive
:representation
- (revised@ #next (n.max +next))
- (revised@ #resolver (function (_ resolver)
- (list#mix (function (_ [module [id entry]] resolver)
- (case entry
- {.#Some _}
- (dictionary.has module [id entry] resolver)
-
- {.#None}
- resolver))
- resolver
- (dictionary.entries +resolver))))
+ (revised #next (n.max +next))
+ (revised #resolver (function (_ resolver)
+ (list#mix (function (_ [module [id entry]] resolver)
+ (case entry
+ {.#Some _}
+ (dictionary.has module [id entry] resolver)
+
+ {.#None}
+ resolver))
+ resolver
+ (dictionary.entries +resolver))))
:abstraction)))
(type: Reservation
@@ -262,6 +262,6 @@
[#next next
#resolver (list#mix (function (_ [module id] archive)
(dictionary.has module [id (: (Maybe (Entry Any)) {.#None})] archive))
- (value@ #resolver (:representation ..empty))
+ (the #resolver (:representation ..empty))
reservations)]))))
)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux
index 144895928..9a97cc0ec 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux
@@ -58,7 +58,7 @@
(def: .public signature
(-> (Document Any) Signature)
- (|>> :representation (value@ #signature)))
+ (|>> :representation (the #signature)))
(def: .public (writer content)
(All (_ d) (-> (Writer d) (Writer (Document d))))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux
index 6489b6fb7..be3619845 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux
@@ -39,7 +39,7 @@
(def: .public artifacts
(-> Registry (Sequence [Artifact (Set unit.ID)]))
- (|>> :representation (value@ #artifacts)))
+ (|>> :representation (the #artifacts)))
(def: next
(-> Registry ID)
@@ -51,10 +51,10 @@
[id
(|> registry
:representation
- (revised@ #artifacts (sequence.suffix [[//.#id id
- //.#category {//category.#Anonymous}
- //.#mandatory? mandatory?]
- dependencies]))
+ (revised #artifacts (sequence.suffix [[//.#id id
+ //.#category {//category.#Anonymous}
+ //.#mandatory? mandatory?]
+ dependencies]))
:abstraction)]))
(template [<tag> <create> <fetch> <type> <name> <+resolver>]
@@ -64,21 +64,21 @@
[id
(|> registry
:representation
- (revised@ #artifacts (sequence.suffix [[//.#id id
- //.#category {<tag> it}
- //.#mandatory? mandatory?]
- dependencies]))
- (revised@ #resolver (dictionary.has (<name> it) [id (: (Maybe //category.Definition) <+resolver>)]))
+ (revised #artifacts (sequence.suffix [[//.#id id
+ //.#category {<tag> it}
+ //.#mandatory? mandatory?]
+ dependencies]))
+ (revised #resolver (dictionary.has (<name> it) [id (: (Maybe //category.Definition) <+resolver>)]))
:abstraction)]))
(def: .public (<fetch> registry)
(-> Registry (List <type>))
(|> registry
:representation
- (value@ #artifacts)
+ (the #artifacts)
sequence.list
(list.all (|>> product.left
- (value@ //.#category)
+ (the //.#category)
(case> {<tag> it} {.#Some it}
_ {.#None})))))]
@@ -94,7 +94,7 @@
(def: .public (find_definition name registry)
(-> Text Registry (Maybe [ID (Maybe //category.Definition)]))
(|> (:representation registry)
- (value@ #resolver)
+ (the #resolver)
(dictionary.value name)))
(def: .public (id name registry)
@@ -134,10 +134,10 @@
artifacts (: (Writer (Sequence [Category Bit (Set unit.ID)]))
(binary.sequence/64 ($_ binary.and category mandatory? dependencies)))]
(|>> :representation
- (value@ #artifacts)
+ (the #artifacts)
(sequence#each (function (_ [it dependencies])
- [(value@ //.#category it)
- (value@ //.#mandatory? it)
+ [(the //.#category it)
+ (the //.#mandatory? it)
dependencies]))
artifacts)))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux
index 533ed6cb0..235913727 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux
@@ -33,7 +33,7 @@
(def: .public (description signature)
(-> Signature Text)
- (format (%.symbol (value@ #name signature)) " " (version.format (value@ #version signature))))
+ (format (%.symbol (the #name signature)) " " (version.format (the #version signature))))
(def: .public writer
(Writer Signature)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux
index ed2e00876..9412bbb0b 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux
@@ -38,6 +38,6 @@
(def: .public (format it)
(%.Format ID)
- (%.format (%.nat (value@ #module it))
+ (%.format (%.nat (the #module it))
"."
- (%.nat (value@ #artifact it))))
+ (%.nat (the #artifact it))))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache.lux b/stdlib/source/library/lux/tool/compiler/meta/cache.lux
index 6b4194359..72470f228 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/cache.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/cache.lux
@@ -18,8 +18,8 @@
(def: .public (path fs context)
(All (_ !) (-> (file.System !) Context file.Path))
(let [/ (# fs separator)]
- (format (value@ context.#target context)
- / (value@ context.#host context)
+ (format (the context.#target context)
+ / (the context.#host context)
/ (version.format //.version))))
(def: .public (enabled? fs context)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/artifact.lux
index fd63495d1..ca2689c18 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/cache/artifact.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/cache/artifact.lux
@@ -26,7 +26,7 @@
(format (//module.path fs context @module)
(# fs separator)
(%.nat @artifact)
- (value@ context.#artifact_extension context)))
+ (the context.#artifact_extension context)))
(def: .public (cache fs context @module @artifact)
(All (_ !)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux
index 9bce830d6..f1c4a4806 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux
@@ -83,7 +83,7 @@
(case value
{analysis/complex.#Variant value}
(|> value
- (value@ analysis/complex.#value)
+ (the analysis/complex.#value)
references)
{analysis/complex.#Tuple value}
@@ -131,7 +131,7 @@
(case value
{synthesis.#Scope value}
(|> value
- (value@ synthesis.#iteration)
+ (the synthesis.#iteration)
references)
{synthesis.#Again value}
@@ -143,7 +143,7 @@
(case value
{synthesis.#Abstraction value}
(|> value
- (value@ synthesis.#body)
+ (the synthesis.#body)
references)
{synthesis.#Apply function arguments}
@@ -193,8 +193,8 @@
registry.artifacts
sequence.list
(list#each (function (_ [artifact dependencies])
- [[module_id (value@ artifact.#id artifact)]
- (value@ artifact.#mandatory? artifact)
+ [[module_id (the artifact.#id artifact)]
+ (the artifact.#mandatory? artifact)
dependencies])))))
list.together
(list#mix (function (_ [artifact_id mandatory? dependencies]
diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/module.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/module.lux
index 01c37431f..4fd7fdebf 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/module.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/module.lux
@@ -59,7 +59,7 @@
(do [! state.monad]
[.let [parents (case (archive.find module archive)
{try.#Success [module output registry]}
- (value@ [module.#descriptor descriptor.#references] module)
+ (the [module.#descriptor descriptor.#references] module)
{try.#Failure error}
..fresh)]
@@ -95,5 +95,5 @@
(do try.monad
[module_id (archive.id module archive)
entry (archive.find module archive)
- document (document.marked? key (value@ [archive.#module module.#document] entry))]
- (in [module [module_id (with@ [archive.#module module.#document] document entry)]])))))))
+ document (document.marked? key (the [archive.#module module.#document] entry))]
+ (in [module [module_id (has [archive.#module module.#document] document entry)]])))))))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux
index c5f2f577a..e393253e1 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux
@@ -50,12 +50,12 @@
(def: .public (valid? expected actual)
(-> Descriptor Input Bit)
- (and (text#= (value@ descriptor.#name expected)
- (value@ ////.#module actual))
- (text#= (value@ descriptor.#file expected)
- (value@ ////.#file actual))
- (n.= (value@ descriptor.#hash expected)
- (value@ ////.#hash actual))))
+ (and (text#= (the descriptor.#name expected)
+ (the ////.#module actual))
+ (text#= (the descriptor.#file expected)
+ (the ////.#file actual))
+ (n.= (the descriptor.#hash expected)
+ (the ////.#hash actual))))
(def: initial
(-> (List Cache) Purge)
@@ -73,7 +73,7 @@
(if (purged? module_name)
purge
(if (|> entry
- (value@ [archive.#module module.#descriptor descriptor.#references])
+ (the [archive.#module module.#descriptor descriptor.#references])
set.list
(list.any? purged?))
(dictionary.has module_name @module purge)
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 212006bbe..a807e083c 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
@@ -81,11 +81,11 @@
(do !
[entry (archive.find module archive)
content (|> entry
- (value@ [archive.#module module.#document])
+ (the [archive.#module module.#document])
(document.content $.key))]
(in [module content])))
(archive.archived archive)))]
- (in (with@ .#modules modules (fresh_analysis_state host configuration)))))
+ (in (has .#modules modules (fresh_analysis_state host configuration)))))
(type: Definitions (Dictionary Text Any))
(type: Analysers (Dictionary Text analysis.Handler))
@@ -240,8 +240,8 @@
try.of_maybe
(# ! each (function (_ def_value)
[def_name {.#Type [exported? (:as .Type def_value) labels]}])))))
- (value@ .#definitions content))]
- (in [(document.document $.key (with@ .#definitions definitions content))
+ (the .#definitions content))]
+ (in [(document.document $.key (has .#definitions definitions content))
bundles])))
(def: (load_definitions fs context @module host_environment entry)
@@ -252,13 +252,13 @@
(do (try.with async.monad)
[actual (: (Async (Try (Dictionary Text Binary)))
(cache/module.artifacts async.monad fs context @module))
- .let [expected (registry.artifacts (value@ archive.#registry entry))]
- [document bundles output] (|> (value@ [archive.#module module.#document] entry)
- (loaded_document (value@ context.#artifact_extension context) host_environment @module expected actual)
+ .let [expected (registry.artifacts (the archive.#registry entry))]
+ [document bundles output] (|> (the [archive.#module module.#document] entry)
+ (loaded_document (the context.#artifact_extension context) host_environment @module expected actual)
async#in)]
(in [(|> entry
- (with@ [archive.#module module.#document] document)
- (with@ archive.#output output))
+ (has [archive.#module module.#document] document)
+ (has archive.#output output))
bundles])))
(def: pseudo_module
@@ -291,8 +291,8 @@
(if (text#= descriptor.runtime module_name)
(in [true <cache>])
(do !
- [input (//context.read fs ..pseudo_module import contexts (value@ context.#host_module_extension context) module_name)]
- (in [(cache/purge.valid? (value@ module.#descriptor module) input) <cache>]))))))
+ [input (//context.read fs ..pseudo_module import contexts (the context.#host_module_extension context) module_name)]
+ (in [(cache/purge.valid? (the module.#descriptor module) input) <cache>]))))))
(def: (pre_loaded_caches customs fs context import contexts archive)
(-> (List Custom) (file.System Async) Context Import (List //.Context) Archive
@@ -354,7 +354,7 @@
(archive.has module entry archive))
archive
loaded_caches)
- analysis_state (..analysis_state (value@ context.#host context) configuration archive)]
+ analysis_state (..analysis_state (the context.#host context) configuration archive)]
(in [archive
analysis_state
(list#mix (function (_ [_ [+analysers +synthesizers +generators +directives]]
@@ -380,5 +380,5 @@
{try.#Failure error}
(in {try.#Success [archive.empty
- (fresh_analysis_state (value@ context.#host context) configuration)
+ (fresh_analysis_state (the context.#host context) configuration)
..empty_bundles]}))))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager.lux b/stdlib/source/library/lux/tool/compiler/meta/packager.lux
index 5b0bd0438..a92bdbbe1 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager.lux
@@ -37,8 +37,8 @@
(-> (cache/module.Order Any) Order)
(list#each (function (_ [module [module_id entry]])
(|> entry
- (value@ archive.#registry)
+ (the archive.#registry)
registry.artifacts
sequence.list
- (list#each (|>> product.left (value@ artifact.#id)))
+ (list#each (|>> product.left (the artifact.#id)))
[module_id]))))
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 99c9a316b..4e1c841b5 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
@@ -152,7 +152,7 @@
(maybe#each (|>> name.internal name.read))
(maybe.else (runtime.class_name [module artifact]))
(text.replaced "." "/")
- (text.suffix (value@ context.#artifact_extension static)))]
+ (text.suffix (the context.#artifact_extension static)))]
(do try.monad
[_ (java/util/jar/JarOutputStream::putNextEntry (java/util/jar/JarEntry::new class_path) sink)]
(in (do_to sink
@@ -266,7 +266,7 @@
.let [buffer (java/io/ByteArrayOutputStream::new (ffi.as_int (.int ..mebi_byte)))]
sink (|> order
(list#each (function (_ [module [module_id entry]])
- [module_id (value@ archive.#output entry)]))
+ [module_id (the archive.#output entry)]))
(monad.mix ! (..write_module static necessary_dependencies)
(java/util/jar/JarOutputStream::new buffer (..manifest program))))
[entries duplicates sink] (|> host_dependencies
diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux
index 85eb525cf..df7f11ce0 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux
@@ -85,7 +85,7 @@
(Try (List [module.ID [Text Binary]])))
(do [! try.monad]
[bundle (: (Try (Maybe _.Statement))
- (..bundle_module module module_id necessary_dependencies (value@ archive.#output entry)))]
+ (..bundle_module module module_id necessary_dependencies (the archive.#output entry)))]
(case bundle
{.#None}
(in sink)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux
index f46a71e8e..f1dfb0189 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux
@@ -1,48 +1,48 @@
(.using
- [library
- [lux {"-" Module}
- [type {"+" :sharing}]
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- ["[0]" try {"+" Try}]]
- [data
- [binary {"+" Binary}]
- ["[0]" product]
- ["[0]" text
- ["%" format {"+" format}]
- ["[0]" encoding]]
- [collection
- ["[0]" sequence]
- ["[0]" list ("[1]#[0]" functor mix)]
- ["[0]" dictionary {"+" Dictionary}]
- ["[0]" set]]
- [format
- ["[0]" tar]
- ["[0]" binary]]]
- [target
- ["_" scheme]]
- [time
- ["[0]" instant {"+" Instant}]]
- [world
- ["[0]" file]]]]
- [program
- [compositor
- ["[0]" static {"+" Static}]]]
- ["[0]" // {"+" Packager}
+ [library
+ [lux {"-" Module}
+ [type {"+" :sharing}]
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ ["[0]" try {"+" Try}]]
+ [data
+ [binary {"+" Binary}]
+ ["[0]" product]
+ ["[0]" text
+ ["%" format {"+" format}]
+ ["[0]" encoding]]
+ [collection
+ ["[0]" sequence]
+ ["[0]" list ("[1]#[0]" functor mix)]
+ ["[0]" dictionary {"+" Dictionary}]
+ ["[0]" set]]
+ [format
+ ["[0]" tar]
+ ["[0]" binary]]]
+ [target
+ ["_" scheme]]
+ [time
+ ["[0]" instant {"+" Instant}]]
+ [world
+ ["[0]" file]]]]
+ [program
+ [compositor
+ ["[0]" static {"+" Static}]]]
+ ["[0]" // {"+" Packager}
+ [//
+ ["[0]" archive {"+" Output}
+ ["[0]" descriptor {"+" Module Descriptor}]
+ ["[0]" artifact]
+ ["[0]" document {"+" Document}]]
+ [cache
+ ["[0]" dependency]]
+ ["[0]" io "_"
+ ["[1]" archive]]
[//
- ["[0]" archive {"+" Output}
- ["[0]" descriptor {"+" Module Descriptor}]
- ["[0]" artifact]
- ["[0]" document {"+" Document}]]
- [cache
- ["[0]" dependency]]
- ["[0]" io "_"
- ["[1]" archive]]
- [//
- [language
- ["$" lux
- [generation {"+" Context}]]]]]])
+ [language
+ ["$" lux
+ [generation {"+" Context}]]]]]])
... TODO: Delete ASAP
(type: (Action ! a)
@@ -104,7 +104,7 @@
(..bundle_module output))
entry_content (: (Try tar.Content)
(|> descriptor
- (value@ descriptor.#references)
+ (the descriptor.#references)
set.list
(list.all (function (_ module) (dictionary.value module mapping)))
(list#each (|>> ..module_file _.string _.load_relative/1))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux
index f3cc4f7a0..1b867cd4f 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux
@@ -71,7 +71,7 @@
order (cache/module.load_order $.key archive)]
(|> order
(list#each (function (_ [module [module_id entry]])
- [module_id (value@ archive.#output entry)]))
+ [module_id (the archive.#output entry)]))
(monad.mix ! (..write_module necessary_dependencies sequence) header)
(# ! each (|>> scope
code
diff --git a/stdlib/source/library/lux/tool/interpreter.lux b/stdlib/source/library/lux/tool/interpreter.lux
index 8cf01011c..a5e907a52 100644
--- a/stdlib/source/library/lux/tool/interpreter.lux
+++ b/stdlib/source/library/lux/tool/interpreter.lux
@@ -1,33 +1,33 @@
(.using
- [library
- [lux "*"
- [control
- [monad {"+" Monad do}]
- ["[0]" try {"+" Try}]
- ["ex" exception {"+" exception:}]]
- [data
- ["[0]" text ("[1]#[0]" equivalence)
- ["%" format {"+" format}]]]
- [type {"+" :sharing}
- ["[0]" check]]
- [compiler
- ["[0]" phase
- ["[0]" analysis
- ["[0]" module]
- ["[0]" type]]
- ["[0]" generation]
- ["[0]" directive {"+" State+ Operation}
- ["[0]" total]]
- ["[0]" extension]]
- ["[0]" default
- ["[0]" syntax]
- ["[0]" platform {"+" Platform}]
- ["[0]" init]]
- ["[0]" cli {"+" Configuration}]]
- [world
- ["[0]" file {"+" File}]
- ["[0]" console {"+" Console}]]]]
- ["[0]" /type])
+ [library
+ [lux "*"
+ [control
+ [monad {"+" Monad do}]
+ ["[0]" try {"+" Try}]
+ ["ex" exception {"+" exception:}]]
+ [data
+ ["[0]" text ("[1]#[0]" equivalence)
+ ["%" format {"+" format}]]]
+ [type {"+" :sharing}
+ ["[0]" check]]
+ [compiler
+ ["[0]" phase
+ ["[0]" analysis
+ ["[0]" module]
+ ["[0]" type]]
+ ["[0]" generation]
+ ["[0]" directive {"+" State+ Operation}
+ ["[0]" total]]
+ ["[0]" extension]]
+ ["[0]" default
+ ["[0]" syntax]
+ ["[0]" platform {"+" Platform}]
+ ["[0]" init]]
+ ["[0]" cli {"+" Configuration}]]
+ [world
+ ["[0]" file {"+" File}]
+ ["[0]" console {"+" Console}]]]]
+ ["[0]" /type])
(exception: .public (error [message Text])
message)
@@ -75,14 +75,14 @@
(do Monad<!>
[state (platform.initialize platform generation_bundle)
state (platform.compile platform
- (with@ cli.#module syntax.prelude configuration)
- (with@ [extension.#state
- directive.#analysis directive.#state
- extension.#state
- .#info .#mode]
- {.#Interpreter}
- state))
- [state _] (# (value@ platform.#file_system platform)
+ (has cli.#module syntax.prelude configuration)
+ (has [extension.#state
+ directive.#analysis directive.#state
+ extension.#state
+ .#info .#mode]
+ {.#Interpreter}
+ state))
+ [state _] (# (the platform.#file_system platform)
lift (phase.result' state enter_module))
_ (# Console<!> write ..welcome_message)]
(in state)))
@@ -102,9 +102,9 @@
(-> Code <Interpretation>))
(do [! phase.monad]
[state (extension.lifted phase.state)
- .let [analyse (value@ [directive.#analysis directive.#phase] state)
- synthesize (value@ [directive.#synthesis directive.#phase] state)
- generate (value@ [directive.#generation directive.#phase] state)]
+ .let [analyse (the [directive.#analysis directive.#phase] state)
+ synthesize (the [directive.#synthesis directive.#phase] state)
+ generate (the [directive.#generation directive.#phase] state)]
[_ codeT codeA] (directive.lifted_analysis
(analysis.with_scope
(type.with_fresh_env
@@ -156,10 +156,10 @@
(do phase.monad
[[codeT codeV] (interpret configuration code)
state phase.state]
- (in (/type.represent (value@ [extension.#state
- directive.#analysis directive.#state
- extension.#state]
- state)
+ (in (/type.represent (the [extension.#state
+ directive.#analysis directive.#state
+ extension.#state]
+ state)
codeT
codeV))))
@@ -174,15 +174,15 @@
(All (_ anchor expression directive)
(-> <Context> (Try [<Context> Text])))
(do try.monad
- [.let [[_where _offset _code] (value@ #source context)]
- [source' input] (syntax.parse ..module syntax.no_aliases (text.size _code) (value@ #source context))
+ [.let [[_where _offset _code] (the #source context)]
+ [source' input] (syntax.parse ..module syntax.no_aliases (text.size _code) (the #source context))
[state' representation] (let [... TODO: Simplify ASAP
state (:sharing [anchor expression directive]
<Context>
context
(State+ anchor expression directive)
- (value@ #state context))]
+ (the #state context))]
(<| (phase.result' state)
... TODO: Simplify ASAP
(:sharing [anchor expression directive]
@@ -190,10 +190,10 @@
context
(Operation anchor expression directive Text)
- (execute (value@ #configuration context) input))))]
+ (execute (the #configuration context) input))))]
(in [(|> context
- (with@ #state state')
- (with@ #source source'))
+ (has #state state')
+ (has #source source'))
representation]))))
(def: .public (run! Monad<!> Console<!> platform configuration generation_bundle)
@@ -217,7 +217,7 @@
(if (and (not multi_line?)
(text#= ..exit_command line))
(# Console<!> write ..farewell_message)
- (case (read_eval_print (revised@ #source (add_line line) context))
+ (case (read_eval_print (revised #source (add_line line) context))
{try.#Success [context' representation]}
(do !
[_ (# Console<!> write representation)]
@@ -227,5 +227,5 @@
(if (ex.match? syntax.end_of_file error)
(again context #1)
(exec (log! (ex.error ..error error))
- (again (with@ #source ..fresh_source context) #0))))))
+ (again (has #source ..fresh_source context) #0))))))
)))
diff --git a/stdlib/source/library/lux/type.lux b/stdlib/source/library/lux/type.lux
index ac81fe26b..cd1aaa867 100644
--- a/stdlib/source/library/lux/type.lux
+++ b/stdlib/source/library/lux/type.lux
@@ -447,12 +447,12 @@
computation ..typed])
(macro.with_symbols [g!_]
(let [typeC (` (All ((~ g!_) (~+ (list#each code.local_symbol type_vars)))
- (-> (~ (value@ #type exemplar))
- (~ (value@ #type computation)))))
+ (-> (~ (the #type exemplar))
+ (~ (the #type computation)))))
shareC (` (: (~ typeC)
(.function ((~ g!_) (~ g!_))
- (~ (value@ #expression computation)))))]
- (in (list (` ((~ shareC) (~ (value@ #expression exemplar)))))))))
+ (~ (the #expression computation)))))]
+ (in (list (` ((~ shareC) (~ (the #expression exemplar)))))))))
(syntax: .public (:by_example [type_vars ..type_parameters
exemplar ..typed
@@ -460,8 +460,8 @@
(in (list (` (:of ((~! ..:sharing)
[(~+ (list#each code.local_symbol type_vars))]
- (~ (value@ #type exemplar))
- (~ (value@ #expression exemplar))
+ (~ (the #type exemplar))
+ (~ (the #expression exemplar))
(~ extraction)
... The value of this expression will never be relevant, so it doesn't matter what it is.
diff --git a/stdlib/source/library/lux/type/abstract.lux b/stdlib/source/library/lux/type/abstract.lux
index f70175de2..77ca88bee 100644
--- a/stdlib/source/library/lux/type/abstract.lux
+++ b/stdlib/source/library/lux/type/abstract.lux
@@ -1,24 +1,24 @@
(.using
- [library
- [lux "*"
- ["[0]" meta]
- [abstract
- [monad {"+" Monad do}]]
- [control
- ["[0]" exception {"+" exception:}]
- ["<>" parser ("[1]#[0]" monad)
- ["<[0]>" code {"+" Parser}]]]
- [data
- ["[0]" text ("[1]#[0]" equivalence monoid)]
- [collection
- ["[0]" list ("[1]#[0]" functor monoid)]]]
- [macro
- ["[0]" code]
- [syntax {"+" syntax:}
- ["|[0]|" export]]]
- [meta
- ["[0]" symbol ("[1]#[0]" codec)]]]]
- ["[0]" //])
+ [library
+ [lux "*"
+ ["[0]" meta]
+ [abstract
+ [monad {"+" Monad do}]]
+ [control
+ ["[0]" exception {"+" exception:}]
+ ["<>" parser ("[1]#[0]" monad)
+ ["<[0]>" code {"+" Parser}]]]
+ [data
+ ["[0]" text ("[1]#[0]" equivalence monoid)]
+ [collection
+ ["[0]" list ("[1]#[0]" functor monoid)]]]
+ [macro
+ ["[0]" code]
+ [syntax {"+" syntax:}
+ ["|[0]|" export]]]
+ [meta
+ ["[0]" symbol ("[1]#[0]" codec)]]]]
+ ["[0]" //])
(type: Stack
List)
@@ -73,7 +73,7 @@
(def: (peek_frames reference definition_reference source)
(-> Text Text (List [Text Module]) (Stack Frame))
(!peek source reference
- (peek_frames_definition definition_reference (value@ .#definitions head))))
+ (peek_frames_definition definition_reference (the .#definitions head))))
(exception: .public no_active_frames)
@@ -81,7 +81,7 @@
(-> (Maybe Text) (Meta Frame))
(function (_ compiler)
(let [[reference definition_reference] (symbol ..frames)
- current_frames (peek_frames reference definition_reference (value@ .#modules compiler))]
+ current_frames (peek_frames reference definition_reference (the .#modules compiler))]
(case (case frame
{.#Some frame}
(list.example (function (_ [actual _])
@@ -135,14 +135,14 @@
(def: (push_frame [module_reference definition_reference] frame source)
(-> Symbol Frame (List [Text Module]) (List [Text Module]))
(!push source module_reference
- (revised@ .#definitions (push_frame_definition definition_reference frame) head)))
+ (revised .#definitions (push_frame_definition definition_reference frame) head)))
(def: (push! frame)
(-> Frame (Meta Any))
(function (_ compiler)
- {.#Right [(revised@ .#modules
- (..push_frame (symbol ..frames) frame)
- compiler)
+ {.#Right [(revised .#modules
+ (..push_frame (symbol ..frames) frame)
+ compiler)
[]]}))
(def: (pop_frame_definition reference source)
@@ -169,13 +169,13 @@
(def: (pop_frame [module_reference definition_reference] source)
(-> Symbol (List [Text Module]) (List [Text Module]))
(!push source module_reference
- (|> head (revised@ .#definitions (pop_frame_definition definition_reference)))))
+ (|> head (revised .#definitions (pop_frame_definition definition_reference)))))
(syntax: (pop! [])
(function (_ compiler)
- {.#Right [(revised@ .#modules
- (..pop_frame (symbol ..frames))
- compiler)
+ {.#Right [(revised .#modules
+ (..pop_frame (symbol ..frames))
+ compiler)
(list)]}))
(def: cast
diff --git a/stdlib/source/library/lux/type/check.lux b/stdlib/source/library/lux/type/check.lux
index 785e321fb..e7ed19839 100644
--- a/stdlib/source/library/lux/type/check.lux
+++ b/stdlib/source/library/lux/type/check.lux
@@ -188,15 +188,15 @@
(def: .public existential
(Check [Nat Type])
(function (_ context)
- (let [id (value@ .#ex_counter context)]
- {try.#Success [(revised@ .#ex_counter ++ context)
+ (let [id (the .#ex_counter context)]
+ {try.#Success [(revised .#ex_counter ++ context)
[id {.#Ex id}]]})))
(template [<name> <outputT> <fail> <succeed>]
[(def: .public (<name> id)
(-> Var (Check <outputT>))
(function (_ context)
- (case (|> context (value@ .#var_bindings) (var::get id))
+ (case (|> context (the .#var_bindings) (var::get id))
(^or {.#Some {.#Some {.#Var _}}}
{.#Some {.#None}})
{try.#Success [context <fail>]}
@@ -225,7 +225,7 @@
(def: (bound id)
(-> Var (Check Type))
(function (_ context)
- (case (|> context (value@ .#var_bindings) (var::get id))
+ (case (|> context (the .#var_bindings) (var::get id))
{.#Some {.#Some bound}}
{try.#Success [context bound]}
@@ -238,9 +238,9 @@
(def: .public (bind type id)
(-> Type Var (Check Any))
(function (_ context)
- (case (|> context (value@ .#var_bindings) (var::get id))
+ (case (|> context (the .#var_bindings) (var::get id))
{.#Some {.#None}}
- {try.#Success [(revised@ .#var_bindings (var::put id {.#Some type}) context)
+ {try.#Success [(revised .#var_bindings (var::put id {.#Some type}) context)
[]]}
{.#Some {.#Some bound}}
@@ -252,9 +252,9 @@
(def: (re_bind' ?type id)
(-> (Maybe Type) Var (Check Any))
(function (_ context)
- (case (|> context (value@ .#var_bindings) (var::get id))
+ (case (|> context (the .#var_bindings) (var::get id))
{.#Some _}
- {try.#Success [(revised@ .#var_bindings (var::put id ?type) context)
+ {try.#Success [(revised .#var_bindings (var::put id ?type) context)
[]]}
_
@@ -267,10 +267,10 @@
(def: .public var
(Check [Var Type])
(function (_ context)
- (let [id (value@ .#var_counter context)]
+ (let [id (the .#var_counter context)]
{try.#Success [(|> context
- (revised@ .#var_counter ++)
- (revised@ .#var_bindings (var::new id)))
+ (revised .#var_counter ++)
+ (revised .#var_bindings (var::new id)))
[id {.#Var id}]]})))
(def: (on argT funcT)
@@ -304,7 +304,7 @@
(function (_ context)
(loop [current start
output (list start)]
- (case (|> context (value@ .#var_bindings) (var::get current))
+ (case (|> context (the .#var_bindings) (var::get current))
{.#Some {.#Some type}}
(case type
{.#Var next}
@@ -363,19 +363,19 @@
(def: (erase! @)
(-> Var (Check Any))
(function (_ context)
- {try.#Success [(revised@ .#var_bindings
- (list#mix (: (:let [binding [Nat (Maybe Type)]]
- (-> binding
- (List binding)
- (List binding)))
- (function (_ in out)
- (let [[@var :var:] in]
- (if (n.= @ @var)
- out
- (list& in out)))))
- (: (List [Nat (Maybe Type)])
- (list)))
- context)
+ {try.#Success [(revised .#var_bindings
+ (list#mix (: (:let [binding [Nat (Maybe Type)]]
+ (-> binding
+ (List binding)
+ (List binding)))
+ (function (_ in out)
+ (let [[@var :var:] in]
+ (if (n.= @ @var)
+ out
+ (list& in out)))))
+ (: (List [Nat (Maybe Type)])
+ (list)))
+ context)
[]]}))
(def: .public (forget! @)
diff --git a/stdlib/source/library/lux/type/implicit.lux b/stdlib/source/library/lux/type/implicit.lux
index bd4ac94b0..25678f37a 100644
--- a/stdlib/source/library/lux/type/implicit.lux
+++ b/stdlib/source/library/lux/type/implicit.lux
@@ -1,35 +1,35 @@
(.using
- [library
- [lux "*"
- [abstract
- ["[0]" monad {"+" do}]
- ["[0]" equivalence]]
- [control
- ["[0]" maybe]
- ["[0]" try]
- ["<>" parser
- ["<[0]>" code {"+" Parser}]]]
- [data
- ["[0]" product]
- ["[0]" text ("[1]#[0]" equivalence)
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" monad mix)]
- ["[0]" dictionary {"+" Dictionary}]]]
- ["[0]" macro
- ["[0]" code]
- [syntax {"+" syntax:}]]
- [math
- ["[0]" number
- ["n" nat]]]
- ["[0]" meta]
- ["[0]" type ("[1]#[0]" equivalence)
- ["[0]" check {"+" Check}]]]])
+ [library
+ [lux "*"
+ [abstract
+ ["[0]" monad {"+" do}]
+ ["[0]" equivalence]]
+ [control
+ ["[0]" maybe]
+ ["[0]" try]
+ ["<>" parser
+ ["<[0]>" code {"+" Parser}]]]
+ [data
+ ["[0]" product]
+ ["[0]" text ("[1]#[0]" equivalence)
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" monad mix)]
+ ["[0]" dictionary {"+" Dictionary}]]]
+ ["[0]" macro
+ ["[0]" code]
+ [syntax {"+" syntax:}]]
+ [math
+ ["[0]" number
+ ["n" nat]]]
+ ["[0]" meta]
+ ["[0]" type ("[1]#[0]" equivalence)
+ ["[0]" check {"+" Check}]]]])
(def: (type_var id env)
(-> Nat Type_Context (Meta Type))
(case (list.example (|>> product.left (n.= id))
- (value@ .#var_bindings env))
+ (the .#var_bindings env))
{.#Some [_ {.#Some type}]}
(case type
{.#Var id'}
@@ -52,7 +52,7 @@
compiler meta.compiler_state]
(case raw_type
{.#Var id}
- (type_var id (value@ .#type_context compiler))
+ (type_var id (the .#type_context compiler))
_
(in raw_type))))
diff --git a/stdlib/source/library/lux/type/quotient.lux b/stdlib/source/library/lux/type/quotient.lux
index b43d5035e..591734219 100644
--- a/stdlib/source/library/lux/type/quotient.lux
+++ b/stdlib/source/library/lux/type/quotient.lux
@@ -1,15 +1,15 @@
(.using
- [library
- [lux {"-" type}
- [abstract
- [equivalence {"+" Equivalence}]]
- [control
- [parser
- ["<[0]>" code]]]
- [macro {"+" with_symbols}
- [syntax {"+" syntax:}]]
- ["[0]" type
- abstract]]])
+ [library
+ [lux {"-" type}
+ [abstract
+ [equivalence {"+" Equivalence}]]
+ [control
+ [parser
+ ["<[0]>" code]]]
+ [macro {"+" with_symbols}
+ [syntax {"+" syntax:}]]
+ ["[0]" type
+ abstract]]])
(abstract: .public (Class t c %)
(-> t c)
@@ -35,7 +35,7 @@
(template [<name> <output> <slot>]
[(def: .public <name>
(All (_ t c %) (-> (Quotient t c %) <output>))
- (|>> :representation (value@ <slot>)))]
+ (|>> :representation (the <slot>)))]
[value t #value]
[label c #label]
diff --git a/stdlib/source/library/lux/type/refinement.lux b/stdlib/source/library/lux/type/refinement.lux
index 194a63b2d..df4fc8d3c 100644
--- a/stdlib/source/library/lux/type/refinement.lux
+++ b/stdlib/source/library/lux/type/refinement.lux
@@ -1,15 +1,15 @@
(.using
- [library
- [lux {"-" type}
- [abstract
- [predicate {"+" Predicate}]]
- [control
- [parser
- ["<[0]>" code]]]
- ["[0]" macro
- [syntax {"+" syntax:}]]
- ["[0]" type
- abstract]]])
+ [library
+ [lux {"-" type}
+ [abstract
+ [predicate {"+" Predicate}]]
+ [control
+ [parser
+ ["<[0]>" code]]]
+ ["[0]" macro
+ [syntax {"+" syntax:}]]
+ ["[0]" type
+ abstract]]])
(abstract: .public (Refined t %)
(Record
@@ -32,7 +32,7 @@
(template [<name> <output> <slot>]
[(def: .public <name>
(All (_ t %) (-> (Refined t %) <output>))
- (|>> :representation (value@ <slot>)))]
+ (|>> :representation (the <slot>)))]
[value t #value]
[predicate (Predicate t) #predicate]
diff --git a/stdlib/source/library/lux/world/db/jdbc.lux b/stdlib/source/library/lux/world/db/jdbc.lux
index beb4d8bce..25a29b3b3 100644
--- a/stdlib/source/library/lux/world/db/jdbc.lux
+++ b/stdlib/source/library/lux/world/db/jdbc.lux
@@ -1,29 +1,29 @@
(.using
- [library
- [lux {"-" and int}
- [control
- [functor {"+" Functor}]
- [apply {"+" Apply}]
- [monad {"+" Monad do}]
- ["[0]" try {"+" Try}]
- ["ex" exception]
- [concurrency
- ["[0]" async {"+" Async} ("[1]#[0]" monad)]]
- [security
- ["!" capability {"+" capability:}]]]
- [data
- ["[0]" product]
- [text
- ["%" format {"+" format}]]]
- ["[0]" io {"+" IO}]
- [world
- [net {"+" URL}]]
- [host {"+" import:}]]]
- [//
- ["[0]" sql]]
- ["[0]" / "_"
- ["[1][0]" input {"+" Input}]
- ["[1][0]" output {"+" Output}]])
+ [library
+ [lux {"-" and int}
+ [control
+ [functor {"+" Functor}]
+ [apply {"+" Apply}]
+ [monad {"+" Monad do}]
+ ["[0]" try {"+" Try}]
+ ["ex" exception]
+ [concurrency
+ ["[0]" async {"+" Async} ("[1]#[0]" monad)]]
+ [security
+ ["!" capability {"+" capability:}]]]
+ [data
+ ["[0]" product]
+ [text
+ ["%" format {"+" format}]]]
+ ["[0]" io {"+" IO}]
+ [world
+ [net {"+" URL}]]
+ [host {"+" import:}]]]
+ [//
+ ["[0]" sql]]
+ ["[0]" / "_"
+ ["[1][0]" input {"+" Input}]
+ ["[1][0]" output {"+" Output}]])
(import: java/lang/String)
@@ -96,10 +96,10 @@
(-> java/sql/PreparedStatement (IO (Try a)))
(IO (Try a))))
(do (try.with io.monad)
- [prepared (io.io (java/sql/Connection::prepareStatement (sql.sql (value@ #sql statement))
+ [prepared (io.io (java/sql/Connection::prepareStatement (sql.sql (the #sql statement))
(java/sql/Statement::RETURN_GENERATED_KEYS)
conn))
- _ (io.io ((value@ #input statement) (value@ #value statement) [1 prepared]))
+ _ (io.io ((the #input statement) (the #value statement) [1 prepared]))
result (action prepared)
_ (java/sql/Statement::close prepared)]
(in result)))
@@ -118,9 +118,9 @@
(def: .public (connect creds)
(-> Credentials (IO (Try (DB IO))))
(do (try.with io.monad)
- [connection (java/sql/DriverManager::getConnection (value@ #url creds)
- (value@ #user creds)
- (value@ #password creds))]
+ [connection (java/sql/DriverManager::getConnection (the #url creds)
+ (the #user creds)
+ (the #password creds))]
(in (: (DB IO)
(implementation
(def: execute
diff --git a/stdlib/source/library/lux/world/file.lux b/stdlib/source/library/lux/world/file.lux
index cf1a5fc83..aa1598254 100644
--- a/stdlib/source/library/lux/world/file.lux
+++ b/stdlib/source/library/lux/world/file.lux
@@ -1026,8 +1026,8 @@
[{.#Left file} {.#End}]
{try.#Success (dictionary.has head
{.#Left (|> file
- (with@ #mock_last_modified now)
- (with@ #mock_content content))}
+ (has #mock_last_modified now)
+ (has #mock_content content))}
directory)}
[{.#Right sub_directory} {.#Item _}]
@@ -1204,7 +1204,7 @@
(in (|> |store|
(..retrieve_mock_file! separator path)
(try#each (|>> product.right
- (value@ #mock_content)
+ (the #mock_content)
binary.size)))))))
(def: (last_modified path)
@@ -1214,7 +1214,7 @@
(in (|> |store|
(..retrieve_mock_file! separator path)
(try#each (|>> product.right
- (value@ #mock_last_modified))))))))
+ (the #mock_last_modified))))))))
(def: (can_execute? path)
(stm.commit!
@@ -1223,7 +1223,7 @@
(in (|> |store|
(..retrieve_mock_file! separator path)
(try#each (|>> product.right
- (value@ #mock_can_execute))))))))
+ (the #mock_can_execute))))))))
(def: (read path)
(stm.commit!
@@ -1232,7 +1232,7 @@
(in (|> |store|
(..retrieve_mock_file! separator path)
(try#each (|>> product.right
- (value@ #mock_content))))))))
+ (the #mock_content))))))))
(def: (delete path)
(stm.commit!
@@ -1243,7 +1243,7 @@
(..attempt! (function (_ |store|)
(do try.monad
[[name file] (..retrieve_mock_file! separator path |store|)]
- (..update_mock_file! separator path now (value@ #mock_content file) |store|)))
+ (..update_mock_file! separator path now (the #mock_content file) |store|)))
store)))
(def: (write content path)
@@ -1261,7 +1261,7 @@
[[name file] (..retrieve_mock_file! separator path |store|)]
(..update_mock_file! separator path now
(# binary.monoid composite
- (value@ #mock_content file)
+ (the #mock_content file)
content)
|store|)))
store))))
@@ -1273,7 +1273,7 @@
(case (do try.monad
[[name file] (..retrieve_mock_file! separator origin |store|)
|store| (..delete_mock_node! separator origin |store|)]
- (..update_mock_file! separator destination (value@ #mock_last_modified file) (value@ #mock_content file) |store|))
+ (..update_mock_file! separator destination (the #mock_last_modified file) (the #mock_content file) |store|))
{try.#Success |store|}
(do !
[_ (stm.write |store| store)]
diff --git a/stdlib/source/library/lux/world/file/watch.lux b/stdlib/source/library/lux/world/file/watch.lux
index c26923c54..5ad94c22e 100644
--- a/stdlib/source/library/lux/world/file/watch.lux
+++ b/stdlib/source/library/lux/world/file/watch.lux
@@ -1,36 +1,36 @@
(.using
- [library
- [lux "*"
- ["@" target]
- ["[0]" ffi {"+" import:}]
- [abstract
- [predicate {"+" Predicate}]
- ["[0]" monad {"+" do}]]
- [control
- ["[0]" io {"+" IO}]
- ["[0]" maybe]
- ["[0]" try {"+" Try}]
- ["[0]" exception {"+" exception:}]
- [concurrency
- ["[0]" async {"+" Async}]
- ["[0]" stm {"+" STM Var}]]]
- [data
- ["[0]" product]
- ["[0]" text
- ["%" format {"+" format}]]
- [collection
- ["[0]" dictionary {"+" Dictionary}]
- ["[0]" list ("[1]#[0]" functor monoid mix)]
- ["[0]" set]
- ["[0]" array]]]
- [math
- [number
- ["n" nat]]]
- [time
- ["[0]" instant {"+" Instant} ("[1]#[0]" equivalence)]]
- [type
- [abstract {"+" abstract: :representation :abstraction}]]]]
- ["[0]" //])
+ [library
+ [lux "*"
+ ["@" target]
+ ["[0]" ffi {"+" import:}]
+ [abstract
+ [predicate {"+" Predicate}]
+ ["[0]" monad {"+" do}]]
+ [control
+ ["[0]" io {"+" IO}]
+ ["[0]" maybe]
+ ["[0]" try {"+" Try}]
+ ["[0]" exception {"+" exception:}]
+ [concurrency
+ ["[0]" async {"+" Async}]
+ ["[0]" stm {"+" STM Var}]]]
+ [data
+ ["[0]" product]
+ ["[0]" text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" dictionary {"+" Dictionary}]
+ ["[0]" list ("[1]#[0]" functor monoid mix)]
+ ["[0]" set]
+ ["[0]" array]]]
+ [math
+ [number
+ ["n" nat]]]
+ [time
+ ["[0]" instant {"+" Instant} ("[1]#[0]" equivalence)]]
+ [type
+ [abstract {"+" abstract: :representation :abstraction}]]]]
+ ["[0]" //])
(abstract: .public Concern
(Record
@@ -55,7 +55,7 @@
(def: .public <predicate>
(Predicate Concern)
- (|>> :representation (value@ <event>)))]
+ (|>> :representation (the <event>)))]
[creation creation? #creation
true false false]
diff --git a/stdlib/source/library/lux/world/net/http/client.lux b/stdlib/source/library/lux/world/net/http/client.lux
index 9dd11a62f..85e9c2cbd 100644
--- a/stdlib/source/library/lux/world/net/http/client.lux
+++ b/stdlib/source/library/lux/world/net/http/client.lux
@@ -1,34 +1,34 @@
(.using
- [library
- [lux "*"
- ["@" target]
- ["[0]" ffi]
- [abstract
- ["[0]" monad {"+" do}]]
- [control
- [pipe {"+" case>}]
- ["[0]" io {"+" IO}]
- ["[0]" maybe ("[1]#[0]" functor)]
- ["[0]" try {"+" Try}]
- [concurrency
- ["[0]" async {"+" Async}]]
- [parser
- ["<[0]>" code]]]
- [data
- ["[0]" binary {"+" Binary}]
- ["[0]" text]
- [collection
- ["[0]" dictionary]]]
- [macro
- [syntax {"+" syntax:}]
- ["[0]" code]
- ["[0]" template]]
- [math
- [number
- ["n" nat]
- ["i" int]]]]]
- ["[0]" //
- [// {"+" URL}]])
+ [library
+ [lux "*"
+ ["@" target]
+ ["[0]" ffi]
+ [abstract
+ ["[0]" monad {"+" do}]]
+ [control
+ [pipe {"+" case>}]
+ ["[0]" io {"+" IO}]
+ ["[0]" maybe ("[1]#[0]" functor)]
+ ["[0]" try {"+" Try}]
+ [concurrency
+ ["[0]" async {"+" Async}]]
+ [parser
+ ["<[0]>" code]]]
+ [data
+ ["[0]" binary {"+" Binary}]
+ ["[0]" text]
+ [collection
+ ["[0]" dictionary]]]
+ [macro
+ [syntax {"+" syntax:}]
+ ["[0]" code]
+ ["[0]" template]]
+ [math
+ [number
+ ["n" nat]
+ ["i" int]]]]]
+ ["[0]" //
+ [// {"+" URL}]])
(type: .public (Client !)
(Interface
@@ -227,10 +227,10 @@
async.future
(# async.monad each
(|>> (case> {try.#Success [status message]}
- {try.#Success [status (revised@ //.#body (: (-> (//.Body IO) (//.Body Async))
- (function (_ body)
- (|>> body async.future)))
- message)]}
+ {try.#Success [status (revised //.#body (: (-> (//.Body IO) (//.Body Async))
+ (function (_ body)
+ (|>> body async.future)))
+ message)]}
{try.#Failure error}
{try.#Failure error}))))))
diff --git a/stdlib/source/library/lux/world/net/http/request.lux b/stdlib/source/library/lux/world/net/http/request.lux
index 6bc72ff50..a7a29eaca 100644
--- a/stdlib/source/library/lux/world/net/http/request.lux
+++ b/stdlib/source/library/lux/world/net/http/request.lux
@@ -1,33 +1,33 @@
(.using
- [library
- [lux "*"
- [control
- pipe
- ["[0]" monad {"+" do}]
- ["[0]" maybe]
- ["[0]" try {"+" Try}]
- [concurrency
- ["[0]" async {"+" Async}]
- ["[0]" frp]]
- [parser
- ["<[0]>" json]]]
- [data
- ["[0]" number
- ["n" nat]]
- ["[0]" text
- ["[0]" encoding]]
- [format
- ["[0]" json {"+" JSON}]
- ["[0]" context {"+" Context Property}]]
- [collection
- ["[0]" list ("[1]#[0]" functor mix)]
- ["[0]" dictionary]]]
- [world
- ["[0]" binary {"+" Binary}]]]]
- ["[0]" // {"+" Body Response Server}
- ["[1][0]" response]
- ["[1][0]" query]
- ["[1][0]" cookie]])
+ [library
+ [lux "*"
+ [control
+ pipe
+ ["[0]" monad {"+" do}]
+ ["[0]" maybe]
+ ["[0]" try {"+" Try}]
+ [concurrency
+ ["[0]" async {"+" Async}]
+ ["[0]" frp]]
+ [parser
+ ["<[0]>" json]]]
+ [data
+ ["[0]" number
+ ["n" nat]]
+ ["[0]" text
+ ["[0]" encoding]]
+ [format
+ ["[0]" json {"+" JSON}]
+ ["[0]" context {"+" Context Property}]]
+ [collection
+ ["[0]" list ("[1]#[0]" functor mix)]
+ ["[0]" dictionary]]]
+ [world
+ ["[0]" binary {"+" Binary}]]]]
+ ["[0]" // {"+" Body Response Server}
+ ["[1][0]" response]
+ ["[1][0]" query]
+ ["[1][0]" cookie]])
(def: (merge inputs)
(-> (List Binary) Binary)
@@ -54,9 +54,9 @@
(def: .public (json reader server)
(All (_ a) (-> (<json>.Reader a) (-> a Server) Server))
- (function (_ (^@ request [identification protocol resource message]))
+ (function (_ (^let request [identification protocol resource message]))
(do async.monad
- [?raw (read_text_body (value@ //.#body message))]
+ [?raw (read_text_body (the //.#body message))]
(case (do try.monad
[raw ?raw
content (# json.codec decoded raw)]
@@ -69,9 +69,9 @@
(def: .public (text server)
(-> (-> Text Server) Server)
- (function (_ (^@ request [identification protocol resource message]))
+ (function (_ (^let request [identification protocol resource message]))
(do async.monad
- [?raw (read_text_body (value@ //.#body message))]
+ [?raw (read_text_body (the //.#body message))]
(case ?raw
{try.#Success content}
(server content request)
@@ -82,14 +82,14 @@
(def: .public (query property server)
(All (_ a) (-> (Property a) (-> a Server) Server))
(function (_ [identification protocol resource message])
- (let [full (value@ //.#uri resource)
+ (let [full (the //.#uri resource)
[uri query] (|> full
(text.split_by "?")
(maybe.else [full ""]))]
(case (do try.monad
[query (//query.parameters query)
input (context.result query property)]
- (in [[identification protocol (with@ //.#uri uri resource) message]
+ (in [[identification protocol (has //.#uri uri resource) message]
input]))
{try.#Success [request input]}
(server input request)
@@ -99,9 +99,9 @@
(def: .public (form property server)
(All (_ a) (-> (Property a) (-> a Server) Server))
- (function (_ (^@ request [identification protocol resource message]))
+ (function (_ (^let request [identification protocol resource message]))
(do async.monad
- [?body (read_text_body (value@ //.#body message))]
+ [?body (read_text_body (the //.#body message))]
(case (do try.monad
[body ?body
form (//query.parameters body)]
@@ -114,9 +114,9 @@
(def: .public (cookies property server)
(All (_ a) (-> (Property a) (-> a Server) Server))
- (function (_ (^@ request [identification protocol resource message]))
+ (function (_ (^let request [identification protocol resource message]))
(case (do try.monad
- [cookies (|> (value@ //.#headers message)
+ [cookies (|> (the //.#headers message)
(dictionary.value "Cookie")
(maybe.else "")
//cookie.get)]
diff --git a/stdlib/source/library/lux/world/net/http/response.lux b/stdlib/source/library/lux/world/net/http/response.lux
index b19571a45..eeb67bcde 100644
--- a/stdlib/source/library/lux/world/net/http/response.lux
+++ b/stdlib/source/library/lux/world/net/http/response.lux
@@ -1,26 +1,26 @@
(.using
- [library
- [lux {"-" static}
- [control
- [concurrency
- ["[0]" async]
- ["[0]" frp ("[1]#[0]" monad)]]]
- [data
- ["[0]" text
- ["[0]" encoding]]
- [format
- ["[0]" html]
- ["[0]" css {"+" CSS}]
- ["[0]" context]
- ["[0]" json {"+" JSON} ("[1]#[0]" codec)]]]
- ["[0]" io]
- [world
- ["[0]" binary {"+" Binary}]]]]
- ["[0]" // {"+" Status Body Response Server}
- ["[0]" status]
- ["[0]" mime {"+" MIME}]
- ["[0]" header]
- [// {"+" URL}]])
+ [library
+ [lux {"-" static}
+ [control
+ [concurrency
+ ["[0]" async]
+ ["[0]" frp ("[1]#[0]" monad)]]]
+ [data
+ ["[0]" text
+ ["[0]" encoding]]
+ [format
+ ["[0]" html]
+ ["[0]" css {"+" CSS}]
+ ["[0]" context]
+ ["[0]" json {"+" JSON} ("[1]#[0]" codec)]]]
+ ["[0]" io]
+ [world
+ ["[0]" binary {"+" Binary}]]]]
+ ["[0]" // {"+" Status Body Response Server}
+ ["[0]" status]
+ ["[0]" mime {"+" MIME}]
+ ["[0]" header]
+ [// {"+" URL}]])
(def: .public (static response)
(-> Response Server)
@@ -40,7 +40,7 @@
(def: .public (temporary_redirect to)
(-> URL Response)
(let [[status message] (..empty status.temporary_redirect)]
- [status (revised@ //.#headers (header.location to) message)]))
+ [status (revised //.#headers (header.location to) message)]))
(def: .public not_found
Response
diff --git a/stdlib/source/library/lux/world/net/http/route.lux b/stdlib/source/library/lux/world/net/http/route.lux
index 9da7710ac..e882c126c 100644
--- a/stdlib/source/library/lux/world/net/http/route.lux
+++ b/stdlib/source/library/lux/world/net/http/route.lux
@@ -1,24 +1,24 @@
(.using
- [library
- [lux {"-" or}
- [control
- [monad {"+" do}]
- ["[0]" maybe]
- [concurrency
- ["[0]" async]]]
- [data
- ["[0]" text]
- [number
- ["n" nat]]]]]
- ["[0]" // {"+" URI Server}
- ["[1][0]" status]
- ["[1][0]" response]])
+ [library
+ [lux {"-" or}
+ [control
+ [monad {"+" do}]
+ ["[0]" maybe]
+ [concurrency
+ ["[0]" async]]]
+ [data
+ ["[0]" text]
+ [number
+ ["n" nat]]]]]
+ ["[0]" // {"+" URI Server}
+ ["[1][0]" status]
+ ["[1][0]" response]])
(template [<scheme> <name>]
[(def: .public (<name> server)
(-> Server Server)
- (function (_ (^@ request [identification protocol resource message]))
- (case (value@ //.#scheme protocol)
+ (function (_ (^let request [identification protocol resource message]))
+ (case (the //.#scheme protocol)
{<scheme>}
(server request)
@@ -32,8 +32,8 @@
(template [<method> <name>]
[(def: .public (<name> server)
(-> Server Server)
- (function (_ (^@ request [identification protocol resource message]))
- (case (value@ //.#method resource)
+ (function (_ (^let request [identification protocol resource message]))
+ (case (the //.#method resource)
{<method>}
(server request)
@@ -54,12 +54,12 @@
(def: .public (uri path server)
(-> URI Server Server)
(function (_ [identification protocol resource message])
- (if (text.starts_with? path (value@ //.#uri resource))
+ (if (text.starts_with? path (the //.#uri resource))
(server [identification
protocol
- (revised@ //.#uri
- (|>> (text.clip_since (text.size path)) maybe.trusted)
- resource)
+ (revised //.#uri
+ (|>> (text.clip_since (text.size path)) maybe.trusted)
+ resource)
message])
(async.resolved //response.not_found))))
diff --git a/stdlib/source/library/lux/world/program.lux b/stdlib/source/library/lux/world/program.lux
index 7ec1fbd68..cb3c96f19 100644
--- a/stdlib/source/library/lux/world/program.lux
+++ b/stdlib/source/library/lux/world/program.lux
@@ -24,7 +24,8 @@
["[0]" dictionary {"+" Dictionary}]
["[0]" list ("[1]#[0]" functor)]]]
["[0]" ffi {"+" import:}
- (~~ (.for ["JavaScript" (~~ (.as_is ["[0]" node_js]))]
+ (~~ (.for ["JavaScript" (~~ (.as_is ["[0]" node_js]))
+ "{old}" (~~ (.as_is ["node_js" //math]))]
(~~ (.as_is))))]
["[0]" macro
["[0]" template]]