aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/target
diff options
context:
space:
mode:
authorEduardo Julian2021-08-18 03:29:15 -0400
committerEduardo Julian2021-08-18 03:29:15 -0400
commite00ba096c8837abe85d366e0c1293c09dbe84d81 (patch)
treedc1f0955d4461ae30bb4945cddd74c462f1aee98 /stdlib/source/library/lux/target
parent3289b9dcf9d5d1c1e5c380e3185065c8fd32535f (diff)
Some bug fixes.
Diffstat (limited to 'stdlib/source/library/lux/target')
-rw-r--r--stdlib/source/library/lux/target/js.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/attribute/code.lux14
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode.lux60
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/environment.lux18
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux4
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/instruction.lux8
-rw-r--r--stdlib/source/library/lux/target/jvm/class.lux10
-rw-r--r--stdlib/source/library/lux/target/jvm/constant/pool.lux4
-rw-r--r--stdlib/source/library/lux/target/jvm/encoding/signed.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/field.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/loader.lux14
-rw-r--r--stdlib/source/library/lux/target/jvm/method.lux8
-rw-r--r--stdlib/source/library/lux/target/jvm/reflection.lux6
-rw-r--r--stdlib/source/library/lux/target/jvm/type/descriptor.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/type/lux.lux2
-rw-r--r--stdlib/source/library/lux/target/jvm/type/signature.lux17
-rw-r--r--stdlib/source/library/lux/target/lua.lux2
-rw-r--r--stdlib/source/library/lux/target/php.lux8
-rw-r--r--stdlib/source/library/lux/target/python.lux8
-rw-r--r--stdlib/source/library/lux/target/r.lux2
-rw-r--r--stdlib/source/library/lux/target/ruby.lux2
-rw-r--r--stdlib/source/library/lux/target/scheme.lux2
22 files changed, 101 insertions, 96 deletions
diff --git a/stdlib/source/library/lux/target/js.lux b/stdlib/source/library/lux/target/js.lux
index 95c49a200..191b5520a 100644
--- a/stdlib/source/library/lux/target/js.lux
+++ b/stdlib/source/library/lux/target/js.lux
@@ -1,6 +1,6 @@
(.module:
[library
- [lux (#- Location Code or and function if cond undefined for comment not int try)
+ [lux (#- Location Code or and function if cond undefined for comment not int try ++ --)
[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 1c1cb95a9..81f487d2d 100644
--- a/stdlib/source/library/lux/target/jvm/attribute/code.lux
+++ b/stdlib/source/library/lux/target/jvm/attribute/code.lux
@@ -37,19 +37,19 @@
... u4 code_length;
///unsigned.bytes/4
... u1 code[code_length];
- (binary.size (get@ #code code))
+ (binary.size (value@ #code code))
... u2 exception_table_length;
///unsigned.bytes/2
... exception_table[exception_table_length];
(|> code
- (get@ #exception_table)
+ (value@ #exception_table)
row.size
(n.* /exception.length))
... u2 attributes_count;
///unsigned.bytes/2
... attribute_info attributes[attributes_count];
(|> code
- (get@ #attributes)
+ (value@ #attributes)
(row\map length)
(row\fold n.+ 0))))
@@ -69,14 +69,14 @@
($_ binaryF\compose
... u2 max_stack;
... u2 max_locals;
- (///limit.writer (get@ #limit code))
+ (///limit.writer (value@ #limit code))
... u4 code_length;
... u1 code[code_length];
- (binaryF.binary/32 (get@ #code code))
+ (binaryF.binary/32 (value@ #code code))
... u2 exception_table_length;
... exception_table[exception_table_length];
- ((binaryF.row/16 /exception.writer) (get@ #exception_table code))
+ ((binaryF.row/16 /exception.writer) (value@ #exception_table code))
... u2 attributes_count;
... attribute_info attributes[attributes_count];
- ((binaryF.row/16 writer) (get@ #attributes code))
+ ((binaryF.row/16 writer) (value@ #attributes code))
))
diff --git a/stdlib/source/library/lux/target/jvm/bytecode.lux b/stdlib/source/library/lux/target/jvm/bytecode.lux
index 87b0a75c5..a97f4a1c2 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode.lux
@@ -105,9 +105,9 @@
(function (_ [pool environment tracker])
(#try.Success [[pool
environment
- (update@ #next inc tracker)]
+ (revised@ #next ++ tracker)]
[..relative_identity
- (get@ #next tracker)]])))
+ (value@ #next tracker)]])))
(exception: .public (label_has_already_been_set {label Label})
(exception.report
@@ -127,16 +127,16 @@
(with_expansions [<success> (as_is (in [[pool
environment
- (update@ #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 (get@ #program_counter tracker)]
- (case (dictionary.value label (get@ #known tracker))
+ (let [@here (value@ #program_counter tracker)]
+ (case (dictionary.value label (value@ #known tracker))
(#.Some [expected (#.Some address)])
(exception.except ..label_has_already_been_set [label])
@@ -148,7 +148,7 @@
#.None
(do try.monad
[[actual environment] (/environment.continue (|> environment
- (get@ #/environment.stack)
+ (value@ #/environment.stack)
(maybe.else /stack.empty))
environment)]
<success>))))))
@@ -175,7 +175,7 @@
(function (_ pool)
(do try.monad
[[[pool environment tracker] [relative output]] (bytecode [pool environment ..fresh])
- [exceptions instruction] (relative (get@ #known tracker))]
+ [exceptions instruction] (relative (value@ #known tracker))]
(in [pool [environment exceptions instruction output]]))))
(def: (step estimator counter)
@@ -188,12 +188,12 @@
(do {! try.monad}
[environment' (|> environment
(/environment.consumes consumption)
- (monad.bind ! (/environment.produces production))
- (monad.bind ! (/environment.has registry)))
- program_counter' (step estimator (get@ #program_counter tracker))]
+ (monad.then ! (/environment.produces production))
+ (monad.then ! (/environment.has registry)))
+ program_counter' (step estimator (value@ #program_counter tracker))]
(in [[pool
environment'
- (set@ #program_counter program_counter' tracker)]
+ (with@ #program_counter program_counter' tracker)]
[(function.constant (in [..no_exceptions (bytecode input)]))
[]]]))))
@@ -721,19 +721,19 @@
(def: (acknowledge_label stack label tracker)
(-> Stack Label Tracker Tracker)
- (case (dictionary.value label (get@ #known tracker))
+ (case (dictionary.value label (value@ #known tracker))
(#.Some _)
tracker
#.None
- (update@ #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 (get@ #program_counter tracker)]
+ (let [@here (value@ #program_counter tracker)]
(do try.monad
[environment' (|> environment
(/environment.consumes <consumption>))
@@ -744,7 +744,7 @@
environment'
(|> tracker
(..acknowledge_label actual label)
- (set@ #program_counter program_counter'))]
+ (with@ #program_counter program_counter'))]
[(function (_ resolver)
(do try.monad
[[expected @to] (..resolve_label label resolver)
@@ -787,14 +787,14 @@
(function (_ [pool environment tracker])
(do try.monad
[actual (/environment.stack environment)
- .let [@here (get@ #program_counter tracker)]
+ .let [@here (value@ #program_counter tracker)]
program_counter' (step estimator @here)]
(in (let [@from @here]
[[pool
(/environment.discontinue environment)
(|> tracker
(..acknowledge_label actual label)
- (set@ #program_counter program_counter'))]
+ (with@ #program_counter program_counter'))]
[(function (_ resolver)
(case (dictionary.value label resolver)
(#.Some [expected (#.Some @to)])
@@ -843,22 +843,22 @@
[environment' (|> environment
(/environment.consumes $1))
actual (/environment.stack environment')
- program_counter' (step (estimator (list.size afterwards)) (get@ #program_counter tracker))]
- (in (let [@from (get@ #program_counter tracker)]
+ program_counter' (step (estimator (list.size afterwards)) (value@ #program_counter tracker))]
+ (in (let [@from (value@ #program_counter tracker)]
[[pool
environment'
(|> (list\fold (..acknowledge_label actual) tracker (list& default at_minimum afterwards))
- (set@ #program_counter program_counter'))]
+ (with@ #program_counter program_counter'))]
[(function (_ resolver)
(let [get (: (-> Label (Maybe [Stack (Maybe Address)]))
(function (_ label)
(dictionary.value label resolver)))]
(case (do {! maybe.monad}
- [@default (|> default get (monad.bind ! product.right))
- @at_minimum (|> at_minimum get (monad.bind ! product.right))
+ [@default (|> default get (monad.then ! product.right))
+ @at_minimum (|> at_minimum get (monad.then ! product.right))
@afterwards (|> afterwards
(monad.map ! get)
- (monad.bind ! (monad.map ! product.right)))]
+ (monad.then ! (monad.map ! product.right)))]
(in [@default @at_minimum @afterwards]))
(#.Some [@default @at_minimum @afterwards])
(do {! try.monad}
@@ -886,21 +886,21 @@
[environment' (|> environment
(/environment.consumes $1))
actual (/environment.stack environment')
- program_counter' (step (estimator (list.size cases)) (get@ #program_counter tracker))]
- (in (let [@from (get@ #program_counter tracker)]
+ program_counter' (step (estimator (list.size cases)) (value@ #program_counter tracker))]
+ (in (let [@from (value@ #program_counter tracker)]
[[pool
environment'
(|> (list\fold (..acknowledge_label actual) tracker (list& default (list\map product.right cases)))
- (set@ #program_counter program_counter'))]
+ (with@ #program_counter program_counter'))]
[(function (_ resolver)
(let [get (: (-> Label (Maybe [Stack (Maybe Address)]))
(function (_ label)
(dictionary.value label resolver)))]
(case (do {! maybe.monad}
- [@default (|> default get (monad.bind ! product.right))
+ [@default (|> default get (monad.then ! product.right))
@cases (|> cases
(monad.map ! (|>> product.right get))
- (monad.bind ! (monad.map ! product.right)))]
+ (monad.then ! (monad.map ! product.right)))]
(in [@default @cases]))
(#.Some [@default @cases])
(do {! try.monad}
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/environment.lux b/stdlib/source/library/lux/target/jvm/bytecode/environment.lux
index 6a09af8fd..54c754dc5 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/environment.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/environment.lux
@@ -51,7 +51,7 @@
(def: .public (stack environment)
(-> Environment (Try Stack))
- (case (get@ #..stack environment)
+ (case (value@ #..stack environment)
(#.Some stack)
(#try.Success stack)
@@ -60,7 +60,7 @@
(def: .public discontinue
(-> Environment Environment)
- (set@ #..stack #.None))
+ (with@ #..stack #.None))
(exception: .public (mismatched_stacks {expected Stack}
{actual Stack})
@@ -70,14 +70,14 @@
(def: .public (continue expected environment)
(-> Stack Environment (Try [Stack Environment]))
- (case (get@ #..stack environment)
+ (case (value@ #..stack environment)
(#.Some actual)
(if (\ /stack.equivalence = expected actual)
(#try.Success [actual environment])
(exception.except ..mismatched_stacks [expected actual]))
#.None
- (#try.Success [expected (set@ #..stack (#.Some expected) environment)])))
+ (#try.Success [expected (with@ #..stack (#.Some expected) environment)])))
(def: .public (consumes amount)
(-> U2 Condition)
@@ -87,7 +87,7 @@
(do try.monad
[previous (..stack environment)
current (/stack.pop amount previous)]
- (in (set@ #..stack (#.Some current) environment)))))
+ (in (with@ #..stack (#.Some current) environment)))))
(def: .public (produces amount)
(-> U2 Condition)
@@ -96,13 +96,13 @@
[previous (..stack environment)
current (/stack.push amount previous)
.let [limit (|> environment
- (get@ [#..limit #/limit.stack])
+ (value@ [#..limit #/limit.stack])
(/stack.max current))]]
(in (|> environment
- (set@ #..stack (#.Some current))
- (set@ [#..limit #/limit.stack] limit))))))
+ (with@ #..stack (#.Some current))
+ (with@ [#..limit #/limit.stack] limit))))))
(def: .public (has registry)
(-> Registry Condition)
- (|>> (update@ [#..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 48bdffd82..d57c07354 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux
@@ -53,6 +53,6 @@
(def: .public (writer limit)
(Writer Limit)
($_ format\compose
- (/stack.writer (get@ #stack limit))
- (/registry.writer (get@ #registry limit))
+ (/stack.writer (value@ #stack limit))
+ (/registry.writer (value@ #registry limit))
))
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
index 7f8638dca..2e21d2a8e 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
@@ -54,7 +54,7 @@
(def: .public result
(-> Instruction Specification)
- (function.apply format.no_op))
+ (function.on format.no_op))
(type: Opcode Nat)
@@ -596,7 +596,7 @@
(///unsigned.value ..integer_size)
(///unsigned.value ..integer_size)
(n.* (///unsigned.value ..big_jump_size)
- (inc amount_of_afterwards)))
+ (++ amount_of_afterwards)))
///unsigned.u2
try.trusted)))]
[estimator
@@ -622,7 +622,7 @@
_ (case padding
3 (do !
[_ (binary.write/8! offset 0 binary)]
- (binary.write/16! (inc offset) 0 binary))
+ (binary.write/16! (++ offset) 0 binary))
2 (binary.write/16! offset 0 binary)
1 (binary.write/8! offset 0 binary)
_ (in binary))
@@ -684,7 +684,7 @@
_ (case padding
3 (do !
[_ (binary.write/8! offset 0 binary)]
- (binary.write/16! (inc offset) 0 binary))
+ (binary.write/16! (++ offset) 0 binary))
2 (binary.write/16! offset 0 binary)
1 (binary.write/8! offset 0 binary)
_ (in binary))
diff --git a/stdlib/source/library/lux/target/jvm/class.lux b/stdlib/source/library/lux/target/jvm/class.lux
index b4cb88ec4..586cc2394 100644
--- a/stdlib/source/library/lux/target/jvm/class.lux
+++ b/stdlib/source/library/lux/target/jvm/class.lux
@@ -76,7 +76,7 @@
(monad.fold ! (function (_ interface @interfaces)
(do !
[@interface (//constant/pool.class interface)]
- (in (row.add @interface @interfaces))))
+ (in (row.suffix @interface @interfaces))))
row.empty
interfaces))]
(in [@this @super @interfaces])))
@@ -95,8 +95,8 @@
(<| (state.result' //constant/pool.empty)
(do //constant/pool.monad
[classes (install_classes this super interfaces)
- =fields (monad.seq //constant/pool.monad fields)
- =methods (monad.seq //constant/pool.monad methods)]
+ =fields (monad.all //constant/pool.monad fields)
+ =methods (monad.all //constant/pool.monad methods)]
(in [classes =fields =methods])))]
(in {#magic //magic.code
#minor_version //version.default_minor
@@ -114,7 +114,7 @@
(Writer Class)
(`` ($_ binaryF\compose
(~~ (template [<writer> <slot>]
- [(<writer> (get@ <slot> class))]
+ [(<writer> (value@ <slot> class))]
[//magic.writer #magic]
[//version.writer #minor_version]
@@ -124,7 +124,7 @@
[//index.writer #this]
[//index.writer #super]))
(~~ (template [<writer> <slot>]
- [((binaryF.row/16 <writer>) (get@ <slot> class))]
+ [((binaryF.row/16 <writer>) (value@ <slot> class))]
[//index.writer #interfaces]
[//field.writer #fields]
diff --git a/stdlib/source/library/lux/target/jvm/constant/pool.lux b/stdlib/source/library/lux/target/jvm/constant/pool.lux
index 2278889b8..346dd0f9e 100644
--- a/stdlib/source/library/lux/target/jvm/constant/pool.lux
+++ b/stdlib/source/library/lux/target/jvm/constant/pool.lux
@@ -53,7 +53,7 @@
(template: (!add <tag> <equivalence> <value>)
[(function (_ [current pool])
(let [<value>' <value>]
- (with_expansions [<try_again> (as_is (recur (.inc idx)))]
+ (with_expansions [<try_again> (as_is (recur (.++ idx)))]
(loop [idx 0]
(case (row.item idx pool)
(#try.Success entry)
@@ -77,7 +77,7 @@
(//unsigned.+/2 @new)
(\ ! map //index.index)))]
(in [[next
- (row.add [current new] pool)]
+ (row.suffix [current new] pool)]
current]))))))))])
(template: (!index <index>)
diff --git a/stdlib/source/library/lux/target/jvm/encoding/signed.lux b/stdlib/source/library/lux/target/jvm/encoding/signed.lux
index 8fed13354..1c03a5c47 100644
--- a/stdlib/source/library/lux/target/jvm/encoding/signed.lux
+++ b/stdlib/source/library/lux/target/jvm/encoding/signed.lux
@@ -58,7 +58,7 @@
(def: .public <maximum>
<name>
- (|> <bytes> (n.* i64.bits_per_byte) dec i64.mask :abstraction))
+ (|> <bytes> (n.* i64.bits_per_byte) -- i64.mask :abstraction))
(def: .public <constructor>
(-> Int (Try <name>))
diff --git a/stdlib/source/library/lux/target/jvm/field.lux b/stdlib/source/library/lux/target/jvm/field.lux
index a9d783621..b8d84170d 100644
--- a/stdlib/source/library/lux/target/jvm/field.lux
+++ b/stdlib/source/library/lux/target/jvm/field.lux
@@ -50,7 +50,7 @@
(Writer Field)
(`` ($_ binaryF\compose
(~~ (template [<writer> <slot>]
- [(<writer> (get@ <slot> field))]
+ [(<writer> (value@ <slot> field))]
[modifier.writer #modifier]
[//index.writer #name]
diff --git a/stdlib/source/library/lux/target/jvm/loader.lux b/stdlib/source/library/lux/target/jvm/loader.lux
index 549fb8b01..3d644cf5d 100644
--- a/stdlib/source/library/lux/target/jvm/loader.lux
+++ b/stdlib/source/library/lux/target/jvm/loader.lux
@@ -66,13 +66,13 @@
(def: java/lang/ClassLoader::defineClass
java/lang/reflect/Method
(let [signature (|> (ffi.array <elemT> 4)
- (ffi.array_write 0 (:as <elemT>
- (ffi.class_for java/lang/String)))
- (ffi.array_write 1 (java/lang/Object::getClass (ffi.array byte 0)))
- (ffi.array_write 2 (:as <elemT>
- (java/lang/Integer::TYPE)))
- (ffi.array_write 3 (:as <elemT>
- (java/lang/Integer::TYPE))))]
+ (ffi.write! 0 (:as <elemT>
+ (ffi.class_for java/lang/String)))
+ (ffi.write! 1 (java/lang/Object::getClass (ffi.array byte 0)))
+ (ffi.write! 2 (:as <elemT>
+ (java/lang/Integer::TYPE)))
+ (ffi.write! 3 (:as <elemT>
+ (java/lang/Integer::TYPE))))]
(do_to (java/lang/Class::getDeclaredMethod "defineClass"
signature
(ffi.class_for java/lang/ClassLoader))
diff --git a/stdlib/source/library/lux/target/jvm/method.lux b/stdlib/source/library/lux/target/jvm/method.lux
index 8c42130d1..e604eb3c2 100644
--- a/stdlib/source/library/lux/target/jvm/method.lux
+++ b/stdlib/source/library/lux/target/jvm/method.lux
@@ -54,7 +54,7 @@
[@name (//constant/pool.utf8 name)
@descriptor (//constant/pool.descriptor (//type.descriptor type))
attributes (|> attributes
- (monad.seq !)
+ (monad.all !)
(\ ! map row.of_list))
attributes (case code
(#.Some code)
@@ -69,11 +69,11 @@
(function (_ _) (#try.Failure error)))
[environment exceptions instruction output] (//bytecode.resolve environment code)
.let [bytecode (|> instruction //bytecode/instruction.result format.instance)]
- @code (//attribute.code {#//attribute/code.limit (get@ #//bytecode/environment.limit environment)
+ @code (//attribute.code {#//attribute/code.limit (value@ #//bytecode/environment.limit environment)
#//attribute/code.code bytecode
#//attribute/code.exception_table exceptions
#//attribute/code.attributes (row.row)})]
- (in (row.add @code attributes)))
+ (in (row.suffix @code attributes)))
#.None
(in attributes))]
@@ -95,7 +95,7 @@
(Writer Method)
(`` ($_ format\compose
(~~ (template [<writer> <slot>]
- [(<writer> (get@ <slot> field))]
+ [(<writer> (value@ <slot> field))]
[//modifier.writer #modifier]
[//index.writer #name]
diff --git a/stdlib/source/library/lux/target/jvm/reflection.lux b/stdlib/source/library/lux/target/jvm/reflection.lux
index f68b6b59d..db554e4fb 100644
--- a/stdlib/source/library/lux/target/jvm/reflection.lux
+++ b/stdlib/source/library/lux/target/jvm/reflection.lux
@@ -132,7 +132,7 @@
(#try.Success class)
(#try.Failure _)
- (exception.except ..unknown_class name)))
+ (exception.except ..unknown_class [name])))
(def: .public (sub? class_loader super sub)
(-> java/lang/ClassLoader External External (Try Bit))
@@ -182,10 +182,10 @@
paramsT)))
_
- (exception.except ..not_a_class raw)))
+ (exception.except ..not_a_class [raw])))
_)
... else
- (exception.except ..cannot_convert_to_a_lux_type reflection)))
+ (exception.except ..cannot_convert_to_a_lux_type [reflection])))
(def: .public (parameter reflection)
(-> java/lang/reflect/Type (Try (/.Type Parameter)))
diff --git a/stdlib/source/library/lux/target/jvm/type/descriptor.lux b/stdlib/source/library/lux/target/jvm/type/descriptor.lux
index 9c0f56021..099a68287 100644
--- a/stdlib/source/library/lux/target/jvm/type/descriptor.lux
+++ b/stdlib/source/library/lux/target/jvm/type/descriptor.lux
@@ -98,7 +98,7 @@
(:abstraction
(format (|> inputs
(list\map ..descriptor)
- text.joined
+ text.together
(text.enclosed ["(" ")"]))
(:representation output))))
diff --git a/stdlib/source/library/lux/target/jvm/type/lux.lux b/stdlib/source/library/lux/target/jvm/type/lux.lux
index a9021109b..99845fa7e 100644
--- a/stdlib/source/library/lux/target/jvm/type/lux.lux
+++ b/stdlib/source/library/lux/target/jvm/type/lux.lux
@@ -135,7 +135,7 @@
(<>.before (<text>.this //signature.parameters_end))
(<>.else (list)))]
(in (do {! check.monad}
- [parameters (monad.seq ! parameters)]
+ [parameters (monad.all ! parameters)]
(in (#.Primitive name parameters)))))
(<>.after (<text>.this //descriptor.class_prefix))
(<>.before (<text>.this //descriptor.class_suffix))))
diff --git a/stdlib/source/library/lux/target/jvm/type/signature.lux b/stdlib/source/library/lux/target/jvm/type/signature.lux
index 683ba1432..7195c4918 100644
--- a/stdlib/source/library/lux/target/jvm/type/signature.lux
+++ b/stdlib/source/library/lux/target/jvm/type/signature.lux
@@ -78,8 +78,13 @@
[upper ..upper_prefix]
)
- (def: .public parameters_start "<")
- (def: .public parameters_end ">")
+ (template [<char> <name>]
+ [(def: .public <name>
+ <char>)]
+
+ ["<" parameters_start]
+ [">" parameters_end]
+ )
(def: .public (class name parameters)
(-> External (List (Signature Parameter)) (Signature Class))
@@ -94,7 +99,7 @@
(format ..parameters_start
(|> parameters
(list\map ..signature)
- text.joined)
+ text.together)
..parameters_end))
//descriptor.class_suffix)))
@@ -130,18 +135,18 @@
(|> type_variables
(list\map (|>> ..var_name
(text.suffix ..class_bound)))
- text.joined
+ text.together
(text.enclosed [..parameters_start
..parameters_end])))
(|> inputs
(list\map ..signature)
- text.joined
+ text.together
(text.enclosed [..arguments_start
..arguments_end]))
(:representation output)
(|> exceptions
(list\map (|>> :representation (format ..exception_prefix)))
- text.joined))))
+ text.together))))
(implementation: .public equivalence
(All [category] (Equivalence (Signature category)))
diff --git a/stdlib/source/library/lux/target/lua.lux b/stdlib/source/library/lux/target/lua.lux
index b79db8fc4..b70cf80f0 100644
--- a/stdlib/source/library/lux/target/lua.lux
+++ b/stdlib/source/library/lux/target/lua.lux
@@ -374,7 +374,7 @@
(syntax: (arity_inputs [arity <code>.nat])
(in (case arity
0 (.list)
- _ (|> (dec arity)
+ _ (|> (-- arity)
(enum.range n.enum 0)
(list\map (|>> %.nat code.local_identifier))))))
diff --git a/stdlib/source/library/lux/target/php.lux b/stdlib/source/library/lux/target/php.lux
index 11aea7808..860c33713 100644
--- a/stdlib/source/library/lux/target/php.lux
+++ b/stdlib/source/library/lux/target/php.lux
@@ -230,7 +230,7 @@
(syntax: (arity_inputs [arity <code>.nat])
(in (case arity
0 (.list)
- _ (|> (dec arity)
+ _ (|> (-- arity)
(enum.range n.enum 0)
(list\map (|>> %.nat code.local_identifier))))))
@@ -481,10 +481,10 @@
(def: (catch except)
(-> Except Text)
- (let [declaration (format (:representation (get@ #class except))
- " " (:representation (get@ #exception except)))]
+ (let [declaration (format (:representation (value@ #class except))
+ " " (:representation (value@ #exception except)))]
(format "catch" (..group declaration) " "
- (..block (:representation (get@ #handler except))))))
+ (..block (:representation (value@ #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 c8a62c58b..06ad85593 100644
--- a/stdlib/source/library/lux/target/python.lux
+++ b/stdlib/source/library/lux/target/python.lux
@@ -243,7 +243,7 @@
(format (:representation func)
(format "(" (|> args
(list\map (function (_ arg) (format (:representation arg) ", ")))
- text.joined)
+ text.together)
(<splat> extra) ")"))))]
[apply_poly splat_poly]
@@ -268,7 +268,7 @@
[do_keyword apply_keyword]
)
- (def: .public (nth idx array)
+ (def: .public (item idx array)
(-> (Expression Any) (Expression Any) Location)
(:abstraction (format (:representation array) "[" (:representation idx) "]")))
@@ -409,7 +409,7 @@
(format text.new_line "except (" (text.interposed ", " (list\map ..code classes))
") as " (:representation exception) ":"
(..nested (:representation catch!)))))
- text.joined))))
+ text.together))))
(template [<name> <keyword> <pre>]
[(def: .public (<name> value)
@@ -460,7 +460,7 @@
(syntax: (arity_inputs [arity <code>.nat])
(in (case arity
0 (.list)
- _ (|> (dec arity)
+ _ (|> (-- arity)
(enum.range n.enum 0)
(list\map (|>> %.nat code.local_identifier))))))
diff --git a/stdlib/source/library/lux/target/r.lux b/stdlib/source/library/lux/target/r.lux
index 15804b77b..d5344a1c9 100644
--- a/stdlib/source/library/lux/target/r.lux
+++ b/stdlib/source/library/lux/target/r.lux
@@ -170,7 +170,7 @@
(let [func (:representation func)
spacing (|> " "
(list.repeated (text.size func))
- text.joined)]
+ text.together)]
(:abstraction
(format func "("
(|> args
diff --git a/stdlib/source/library/lux/target/ruby.lux b/stdlib/source/library/lux/target/ruby.lux
index 032ebb265..954a91d97 100644
--- a/stdlib/source/library/lux/target/ruby.lux
+++ b/stdlib/source/library/lux/target/ruby.lux
@@ -436,7 +436,7 @@
(syntax: (arity_inputs [arity <code>.nat])
(in (case arity
0 (.list)
- _ (|> (dec arity)
+ _ (|> (-- arity)
(enum.range n.enum 0)
(list\map (|>> %.nat code.local_identifier))))))
diff --git a/stdlib/source/library/lux/target/scheme.lux b/stdlib/source/library/lux/target/scheme.lux
index 7e910a91f..4390d9981 100644
--- a/stdlib/source/library/lux/target/scheme.lux
+++ b/stdlib/source/library/lux/target/scheme.lux
@@ -341,7 +341,7 @@
(-> Var Arguments Expression Computation)
(..form (list (..var "define")
(|> arguments
- (update@ #mandatory (|>> (#.Item name)))
+ (revised@ #mandatory (|>> (#.Item name)))
..arguments)
body)))