aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/compiler/default/phase
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/lux/compiler/default/phase')
-rw-r--r--stdlib/source/lux/compiler/default/phase/analysis.lux14
-rw-r--r--stdlib/source/lux/compiler/default/phase/analysis/case/coverage.lux4
-rw-r--r--stdlib/source/lux/compiler/default/phase/analysis/inference.lux12
-rw-r--r--stdlib/source/lux/compiler/default/phase/analysis/scope.lux6
-rw-r--r--stdlib/source/lux/compiler/default/phase/analysis/structure.lux2
-rw-r--r--stdlib/source/lux/compiler/default/phase/extension/analysis/common.lux10
-rw-r--r--stdlib/source/lux/compiler/default/phase/extension/analysis/host.jvm.lux50
-rw-r--r--stdlib/source/lux/compiler/default/phase/synthesis.lux4
-rw-r--r--stdlib/source/lux/compiler/default/phase/synthesis/expression.lux6
-rw-r--r--stdlib/source/lux/compiler/default/phase/synthesis/function.lux10
-rw-r--r--stdlib/source/lux/compiler/default/phase/synthesis/loop.lux2
-rw-r--r--stdlib/source/lux/compiler/default/phase/translation.lux6
-rw-r--r--stdlib/source/lux/compiler/default/phase/translation/scheme/extension/common.jvm.lux18
-rw-r--r--stdlib/source/lux/compiler/default/phase/translation/scheme/function.jvm.lux4
-rw-r--r--stdlib/source/lux/compiler/default/phase/translation/scheme/runtime.jvm.lux8
15 files changed, 78 insertions, 78 deletions
diff --git a/stdlib/source/lux/compiler/default/phase/analysis.lux b/stdlib/source/lux/compiler/default/phase/analysis.lux
index 182e3c321..ff540cded 100644
--- a/stdlib/source/lux/compiler/default/phase/analysis.lux
+++ b/stdlib/source/lux/compiler/default/phase/analysis.lux
@@ -107,7 +107,7 @@
(n/= (dec size) tag))
(template: #export (no-op value)
- (|> +1 #reference.Local #reference.Variable #..Reference
+ (|> |1 #reference.Local #reference.Variable #..Reference
(#..Function (list))
(#..Apply value)))
@@ -117,11 +117,11 @@
(let [left (function.constant (|>> #.Left #Sum <structure>))
right (|>> #.Right #Sum <structure>)]
(if (last? size tag)
- (if (n/= +1 tag)
+ (if (n/= |1 tag)
(right value)
(list/fold left
(right value)
- (list.n/range +0 (n/- +2 tag))))
+ (list.n/range |0 (n/- |2 tag))))
(list/fold left
(case value
(<structure> (#Sum _))
@@ -129,7 +129,7 @@
_
value)
- (list.n/range +0 tag)))))]
+ (list.n/range |0 tag)))))]
[sum-analysis Analysis #Structure no-op]
[sum-pattern Pattern #Complex id]
@@ -174,7 +174,7 @@
(do-template [<name> <type> <tag>]
[(def: #export (<name> value)
(-> <type> (Maybe (Variant <type>)))
- (loop [lefts +0
+ (loop [lefts |0
variantA value]
(case variantA
(<tag> (#Sum (#.Left valueA)))
@@ -238,13 +238,13 @@
(def: fresh-bindings
(All [k v] (Bindings k v))
- {#.counter +0
+ {#.counter |0
#.mappings (list)})
(def: fresh-scope
Scope
{#.name (list)
- #.inner +0
+ #.inner |0
#.locals fresh-bindings
#.captured fresh-bindings})
diff --git a/stdlib/source/lux/compiler/default/phase/analysis/case/coverage.lux b/stdlib/source/lux/compiler/default/phase/analysis/case/coverage.lux
index 24ded5476..716c11bf1 100644
--- a/stdlib/source/lux/compiler/default/phase/analysis/case/coverage.lux
+++ b/stdlib/source/lux/compiler/default/phase/analysis/case/coverage.lux
@@ -19,11 +19,11 @@
(def: cases
(-> (Maybe Nat) Nat)
- (|>> (maybe.default +0)))
+ (|>> (maybe.default |0)))
(def: (variant sum-side)
(-> (Either Pattern Pattern) (Variant Pattern))
- (loop [lefts +0
+ (loop [lefts |0
variantP sum-side]
(case variantP
(#.Left valueP)
diff --git a/stdlib/source/lux/compiler/default/phase/analysis/inference.lux b/stdlib/source/lux/compiler/default/phase/analysis/inference.lux
index 91e28a4ca..1676c0cf7 100644
--- a/stdlib/source/lux/compiler/default/phase/analysis/inference.lux
+++ b/stdlib/source/lux/compiler/default/phase/analysis/inference.lux
@@ -70,7 +70,7 @@
(^template [<tag>]
(<tag> env quantified)
(<tag> (list/map (replace parameter-idx replacement) env)
- (replace (n/+ +2 parameter-idx) replacement quantified)))
+ (replace (n/+ |2 parameter-idx) replacement quantified)))
([#.UnivQ]
[#.ExQ])
@@ -199,7 +199,7 @@
## Turns a variant type into the kind of function type suitable for inference.
(def: #export (variant tag expected-size inferT)
(-> Nat Nat Type (Operation Type))
- (loop [depth +0
+ (loop [depth |0
currentT inferT]
(case currentT
(#.Named name unnamedT)
@@ -224,9 +224,9 @@
(n/< boundary tag)))
(case (list.nth tag cases)
(#.Some caseT)
- (operation/wrap (if (n/= +0 depth)
+ (operation/wrap (if (n/= |0 depth)
(type.function (list caseT) currentT)
- (let [replace' (replace (|> depth dec (n/* +2)) inferT)]
+ (let [replace' (replace (|> depth dec (n/* |2)) inferT)]
(type.function (list (replace' caseT))
(replace' currentT)))))
@@ -238,9 +238,9 @@
(n/= boundary tag)
(let [caseT (type.variant (list.drop boundary cases))]
- (operation/wrap (if (n/= +0 depth)
+ (operation/wrap (if (n/= |0 depth)
(type.function (list caseT) currentT)
- (let [replace' (replace (|> depth dec (n/* +2)) inferT)]
+ (let [replace' (replace (|> depth dec (n/* |2)) inferT)]
(type.function (list (replace' caseT))
(replace' currentT))))))
diff --git a/stdlib/source/lux/compiler/default/phase/analysis/scope.lux b/stdlib/source/lux/compiler/default/phase/analysis/scope.lux
index a3f7e926c..6b6896674 100644
--- a/stdlib/source/lux/compiler/default/phase/analysis/scope.lux
+++ b/stdlib/source/lux/compiler/default/phase/analysis/scope.lux
@@ -43,7 +43,7 @@
(def: (captured name scope)
(-> Text Scope (Maybe [Type Variable]))
- (loop [idx +0
+ (loop [idx |0
mappings (get@ [#.captured #.mappings] scope)]
(case mappings
#.Nil
@@ -133,7 +133,7 @@
(do-template [<name> <val-type>]
[(def: <name>
(Bindings Text [Type <val-type>])
- {#.counter +0
+ {#.counter |0
#.mappings (list)})]
[init-locals Nat]
@@ -143,7 +143,7 @@
(def: (scope parent-name child-name)
(-> (List Text) Text Scope)
{#.name (list& child-name parent-name)
- #.inner +0
+ #.inner |0
#.locals init-locals
#.captured init-captured})
diff --git a/stdlib/source/lux/compiler/default/phase/analysis/structure.lux b/stdlib/source/lux/compiler/default/phase/analysis/structure.lux
index e4d6159fc..26a91dff6 100644
--- a/stdlib/source/lux/compiler/default/phase/analysis/structure.lux
+++ b/stdlib/source/lux/compiler/default/phase/analysis/structure.lux
@@ -312,7 +312,7 @@
_ (if (n/= size-ts size-record)
(wrap [])
(///.throw record-size-mismatch [size-ts size-record recordT record]))
- #let [tuple-range (list.n/range +0 (dec size-ts))
+ #let [tuple-range (list.n/range |0 (dec size-ts))
tag->idx (dict.from-list name.Hash<Name> (list.zip2 tag-set tuple-range))]
idx->val (monad.fold @
(function (_ [key val] idx->val)
diff --git a/stdlib/source/lux/compiler/default/phase/extension/analysis/common.lux b/stdlib/source/lux/compiler/default/phase/extension/analysis/common.lux
index 2817fd55d..d5ff4a085 100644
--- a/stdlib/source/lux/compiler/default/phase/extension/analysis/common.lux
+++ b/stdlib/source/lux/compiler/default/phase/extension/analysis/common.lux
@@ -82,7 +82,7 @@
(wrap (#analysis.Extension extension-name (list opA))))
_
- (////.throw bundle.incorrect-arity [extension-name +1 (list.size args)]))))
+ (////.throw bundle.incorrect-arity [extension-name |1 (list.size args)]))))
(def: lux::in-module
Handler
@@ -108,7 +108,7 @@
## (analyse valueC)))
## _
-## (////.throw bundle.incorrect-arity [extension-name +2 (list.size args)]))))]
+## (////.throw bundle.incorrect-arity [extension-name |2 (list.size args)]))))]
## [lux::check (:coerce Type actualT)]
## [lux::coerce Any]
@@ -126,7 +126,7 @@
(wrap valueA))
_
- (////.throw bundle.incorrect-arity [extension-name +1 (list.size args)]))))
+ (////.throw bundle.incorrect-arity [extension-name |1 (list.size args)]))))
(def: bundle::lux
Bundle
@@ -275,7 +275,7 @@
(wrap (#analysis.Extension extension-name (list initA))))
_
- (////.throw bundle.incorrect-arity [extension-name +1 (list.size args)]))))
+ (////.throw bundle.incorrect-arity [extension-name |1 (list.size args)]))))
(def: atom::read
Handler
@@ -315,7 +315,7 @@
(wrap (#analysis.Extension extension-name (list initA))))
_
- (////.throw bundle.incorrect-arity [extension-name +1 (list.size args)]))))
+ (////.throw bundle.incorrect-arity [extension-name |1 (list.size args)]))))
(def: box::read
Handler
diff --git a/stdlib/source/lux/compiler/default/phase/extension/analysis/host.jvm.lux b/stdlib/source/lux/compiler/default/phase/extension/analysis/host.jvm.lux
index 7f63118ea..9e4cd2e7e 100644
--- a/stdlib/source/lux/compiler/default/phase/extension/analysis/host.jvm.lux
+++ b/stdlib/source/lux/compiler/default/phase/extension/analysis/host.jvm.lux
@@ -231,7 +231,7 @@
(wrap (#analysis.Extension extension-name (list arrayA))))
_
- (////.throw bundle.incorrect-arity [extension-name +1 (list.size args)]))))
+ (////.throw bundle.incorrect-arity [extension-name |1 (list.size args)]))))
(def: array::new
Handler
@@ -244,7 +244,7 @@
expectedT (///.lift macro.expected-type)
[level elem-class] (: (Operation [Nat Text])
(loop [analysisT expectedT
- level +0]
+ level |0]
(case analysisT
(#.Apply inputT funcT)
(case (type.apply (list inputT) funcT)
@@ -262,7 +262,7 @@
_
(////.throw non-array expectedT))))
- _ (if (n/> +0 level)
+ _ (if (n/> |0 level)
(wrap [])
(////.throw non-array expectedT))]
(wrap (#analysis.Extension extension-name (list (analysis.nat (dec level))
@@ -270,7 +270,7 @@
lengthA))))
_
- (////.throw bundle.incorrect-arity [extension-name +1 (list.size args)]))))
+ (////.throw bundle.incorrect-arity [extension-name |1 (list.size args)]))))
(def: (check-jvm objectT)
(-> Type (Operation Text))
@@ -344,7 +344,7 @@
(wrap (#analysis.Extension extension-name (list (analysis.text elem-class) idxA arrayA))))
_
- (////.throw bundle.incorrect-arity [extension-name +2 (list.size args)]))))
+ (////.throw bundle.incorrect-arity [extension-name |2 (list.size args)]))))
(def: array::write
Handler
@@ -366,7 +366,7 @@
(wrap (#analysis.Extension extension-name (list (analysis.text elem-class) idxA valueA arrayA))))
_
- (////.throw bundle.incorrect-arity [extension-name +3 (list.size args)]))))
+ (////.throw bundle.incorrect-arity [extension-name |3 (list.size args)]))))
(def: bundle::array
Bundle
@@ -389,7 +389,7 @@
(wrap (#analysis.Extension extension-name (list))))
_
- (////.throw bundle.incorrect-arity [extension-name +0 (list.size args)]))))
+ (////.throw bundle.incorrect-arity [extension-name |0 (list.size args)]))))
(def: object::null?
Handler
@@ -404,7 +404,7 @@
(wrap (#analysis.Extension extension-name (list objectA))))
_
- (////.throw bundle.incorrect-arity [extension-name +1 (list.size args)]))))
+ (////.throw bundle.incorrect-arity [extension-name |1 (list.size args)]))))
(def: object::synchronized
Handler
@@ -419,7 +419,7 @@
(wrap (#analysis.Extension extension-name (list monitorA exprA))))
_
- (////.throw bundle.incorrect-arity [extension-name +2 (list.size args)]))))
+ (////.throw bundle.incorrect-arity [extension-name |2 (list.size args)]))))
(host.import: java/lang/Object
(equals [Object] boolean))
@@ -516,7 +516,7 @@
(wrap (#analysis.Extension extension-name (list exceptionA))))
_
- (////.throw bundle.incorrect-arity [extension-name +1 (list.size args)]))))
+ (////.throw bundle.incorrect-arity [extension-name |1 (list.size args)]))))
(def: object::class
Handler
@@ -534,7 +534,7 @@
(////.throw bundle.invalid-syntax extension-name))
_
- (////.throw bundle.incorrect-arity [extension-name +1 (list.size args)]))))
+ (////.throw bundle.incorrect-arity [extension-name |1 (list.size args)]))))
(def: object::instance?
Handler
@@ -557,7 +557,7 @@
(////.throw bundle.invalid-syntax extension-name))
_
- (////.throw bundle.incorrect-arity [extension-name +2 (list.size args)]))))
+ (////.throw bundle.incorrect-arity [extension-name |2 (list.size args)]))))
(def: (java-type-to-class jvm-type)
(-> java/lang/reflect/Type (Operation Text))
@@ -588,8 +588,8 @@
(host.instance? WildcardType java-type)
(let [java-type (:coerce WildcardType java-type)]
- (case [(array.read +0 (WildcardType::getUpperBounds [] java-type))
- (array.read +0 (WildcardType::getLowerBounds [] java-type))]
+ (case [(array.read |0 (WildcardType::getUpperBounds [] java-type))
+ (array.read |0 (WildcardType::getLowerBounds [] java-type))]
(^or [(#.Some bound) _] [_ (#.Some bound)])
(java-type-to-lux-type mappings bound)
@@ -600,13 +600,13 @@
(let [java-type (:coerce (Class Object) java-type)
class-name (Class::getName [] java-type)]
(operation/wrap (case (array.size (Class::getTypeParameters [] java-type))
- +0
+ |0
(#.Primitive class-name (list))
arity
- (|> (list.n/range +0 (dec arity))
+ (|> (list.n/range |0 (dec arity))
list.reverse
- (list/map (|>> (n/* +2) inc #.Parameter))
+ (list/map (|>> (n/* |2) inc #.Parameter))
(#.Primitive class-name)
(type.univ-q arity)))))
@@ -831,7 +831,7 @@
(////.throw bundle.invalid-syntax extension-name))
_
- (////.throw bundle.incorrect-arity [extension-name +2 (list.size args)]))))
+ (////.throw bundle.incorrect-arity [extension-name |2 (list.size args)]))))
(def: static::put
Handler
@@ -853,7 +853,7 @@
(////.throw bundle.invalid-syntax extension-name))
_
- (////.throw bundle.incorrect-arity [extension-name +3 (list.size args)]))))
+ (////.throw bundle.incorrect-arity [extension-name |3 (list.size args)]))))
(def: virtual::get
Handler
@@ -872,7 +872,7 @@
(////.throw bundle.invalid-syntax extension-name))
_
- (////.throw bundle.incorrect-arity [extension-name +3 (list.size args)]))))
+ (////.throw bundle.incorrect-arity [extension-name |3 (list.size args)]))))
(def: virtual::put
Handler
@@ -896,7 +896,7 @@
(////.throw bundle.invalid-syntax extension-name))
_
- (////.throw bundle.incorrect-arity [extension-name +4 (list.size args)]))))
+ (////.throw bundle.incorrect-arity [extension-name |4 (list.size args)]))))
(def: (java-type-to-parameter type)
(-> java/lang/reflect/Type (Operation Text))
@@ -970,11 +970,11 @@
(def: idx-to-parameter
(-> Nat Type)
- (|>> (n/* +2) inc #.Parameter))
+ (|>> (n/* |2) inc #.Parameter))
(def: (type-vars amount offset)
(-> Nat Nat (List Type))
- (if (n/= +0 amount)
+ (if (n/= |0 amount)
(list)
(|> (list.n/range offset (|> amount dec (n/+ offset)))
(list/map idx-to-parameter))))
@@ -998,7 +998,7 @@
num-method-tvars (list.size method-tvars)
all-tvars (list/compose owner-tvars method-tvars)
num-all-tvars (list.size all-tvars)
- owner-tvarsT (type-vars num-owner-tvars +0)
+ owner-tvarsT (type-vars num-owner-tvars |0)
method-tvarsT (type-vars num-method-tvars num-owner-tvars)
mappings (: Mappings
(if (list.empty? all-tvars)
@@ -1086,7 +1086,7 @@
num-owner-tvars (list.size owner-tvars)
all-tvars (list/compose owner-tvars constructor-tvars)
num-all-tvars (list.size all-tvars)
- owner-tvarsT (type-vars num-owner-tvars +0)
+ owner-tvarsT (type-vars num-owner-tvars |0)
constructor-tvarsT (type-vars num-all-tvars num-owner-tvars)
mappings (: Mappings
(if (list.empty? all-tvars)
diff --git a/stdlib/source/lux/compiler/default/phase/synthesis.lux b/stdlib/source/lux/compiler/default/phase/synthesis.lux
index 8deb48ba8..28392eafd 100644
--- a/stdlib/source/lux/compiler/default/phase/synthesis.lux
+++ b/stdlib/source/lux/compiler/default/phase/synthesis.lux
@@ -25,10 +25,10 @@
(def: #export init
State
- {#scope-arity +0
+ {#scope-arity |0
#resolver fresh-resolver
#direct? #0
- #locals +0})
+ #locals |0})
(type: #export Primitive
(#Bit Bit)
diff --git a/stdlib/source/lux/compiler/default/phase/synthesis/expression.lux b/stdlib/source/lux/compiler/default/phase/synthesis/expression.lux
index edb2cc034..0ab38afac 100644
--- a/stdlib/source/lux/compiler/default/phase/synthesis/expression.lux
+++ b/stdlib/source/lux/compiler/default/phase/synthesis/expression.lux
@@ -67,11 +67,11 @@
(do @
[arity //.scope-arity]
(wrap (if (function.nested? arity)
- (if (n/= +0 register)
+ (if (n/= |0 register)
(|> (dec arity)
- (list.n/range +1)
+ (list.n/range |1)
(list/map (|>> //.variable/local))
- [(//.variable/local +0)]
+ [(//.variable/local |0)]
//.function/apply)
(#//.Reference (#reference.Variable (function.adjust arity #0 var))))
(#//.Reference (#reference.Variable var)))))
diff --git a/stdlib/source/lux/compiler/default/phase/synthesis/function.lux b/stdlib/source/lux/compiler/default/phase/synthesis/function.lux
index 397ca2449..b7dd22f70 100644
--- a/stdlib/source/lux/compiler/default/phase/synthesis/function.lux
+++ b/stdlib/source/lux/compiler/default/phase/synthesis/function.lux
@@ -20,7 +20,7 @@
(def: #export nested?
(-> Arity Bit)
- (n/> +1))
+ (n/> |1))
(def: #export (adjust up-arity after? var)
(-> Arity Bit Variable Variable)
@@ -90,7 +90,7 @@
resolver //.resolver
#let [function-arity (if direct?
(inc arity)
- +1)
+ |1)
up-environment (if (nested? arity)
(list/map (.function (_ closure)
(case (dict.get closure resolver)
@@ -107,7 +107,7 @@
(list)
_
- (|> (list.size environment) dec (list.n/range +0)
+ (|> (list.size environment) dec (list.n/range |0)
(list/map (|>> #reference.Foreign)))))
resolver' (if (and (nested? function-arity)
direct?)
@@ -129,6 +129,6 @@
..return))
_
- (|> (prepare function-arity +1 bodyS)
- (maybe/map (|>> [up-environment +1] //.function/abstraction))
+ (|> (prepare function-arity |1 bodyS)
+ (maybe/map (|>> [up-environment |1] //.function/abstraction))
..return))))
diff --git a/stdlib/source/lux/compiler/default/phase/synthesis/loop.lux b/stdlib/source/lux/compiler/default/phase/synthesis/loop.lux
index bfa69c7c6..4bae596c3 100644
--- a/stdlib/source/lux/compiler/default/phase/synthesis/loop.lux
+++ b/stdlib/source/lux/compiler/default/phase/synthesis/loop.lux
@@ -27,7 +27,7 @@
#.None #0))
(template: #export (self)
- (#//.Reference (reference.local +0)))
+ (#//.Reference (reference.local |0)))
(template: (recursive-apply args)
(#//.Apply (self) args))
diff --git a/stdlib/source/lux/compiler/default/phase/translation.lux b/stdlib/source/lux/compiler/default/phase/translation.lux
index f9b5dfbb4..ec67565d6 100644
--- a/stdlib/source/lux/compiler/default/phase/translation.lux
+++ b/stdlib/source/lux/compiler/default/phase/translation.lux
@@ -76,12 +76,12 @@
(-> (Host expression statement)
(..State anchor expression statement)))
{#context {#scope-name ""
- #inner-functions +0}
+ #inner-functions |0}
#anchor #.None
#host host
#buffer #.None
#artifacts (dict.new text.Hash<Text>)
- #counter +0})
+ #counter |0})
(def: #export (with-context expr)
(All [anchor expression statement output]
@@ -90,7 +90,7 @@
(function (_ [bundle state])
(let [[old-scope old-inner] (get@ #context state)
new-scope (format old-scope "c___" (%i (.int old-inner)))]
- (case (expr [bundle (set@ #context [new-scope +0] state)])
+ (case (expr [bundle (set@ #context [new-scope |0] state)])
(#error.Success [[bundle' state'] output])
(#error.Success [[bundle' (set@ #context [old-scope (inc old-inner)] state')]
[new-scope output]])
diff --git a/stdlib/source/lux/compiler/default/phase/translation/scheme/extension/common.jvm.lux b/stdlib/source/lux/compiler/default/phase/translation/scheme/extension/common.jvm.lux
index fb03f3788..10a893f09 100644
--- a/stdlib/source/lux/compiler/default/phase/translation/scheme/extension/common.jvm.lux
+++ b/stdlib/source/lux/compiler/default/phase/translation/scheme/extension/common.jvm.lux
@@ -30,10 +30,10 @@
(syntax: (Vector {size s.nat} elemT)
(wrap (list (` [(~+ (list.repeat size elemT))]))))
-(type: #export Nullary (-> (Vector +0 Expression) Computation))
-(type: #export Unary (-> (Vector +1 Expression) Computation))
-(type: #export Binary (-> (Vector +2 Expression) Computation))
-(type: #export Trinary (-> (Vector +3 Expression) Computation))
+(type: #export Nullary (-> (Vector |0 Expression) Computation))
+(type: #export Unary (-> (Vector |1 Expression) Computation))
+(type: #export Binary (-> (Vector |2 Expression) Computation))
+(type: #export Trinary (-> (Vector |3 Expression) Computation))
(type: #export Variadic (-> (List Expression) Computation))
## [Utils]
@@ -55,12 +55,12 @@
((~' wrap) ((~ g!extension) [(~+ g!input+)])))
(~' _)
- (/////.throw bundle.incorrect-arity [(~ g!name) +1 (list.size (~ g!inputs))]))))))))))
+ (/////.throw bundle.incorrect-arity [(~ g!name) |1 (list.size (~ g!inputs))]))))))))))
-(arity: nullary +0)
-(arity: unary +1)
-(arity: binary +2)
-(arity: trinary +3)
+(arity: nullary |0)
+(arity: unary |1)
+(arity: binary |2)
+(arity: trinary |3)
(def: #export (variadic extension)
(-> Variadic Handler)
diff --git a/stdlib/source/lux/compiler/default/phase/translation/scheme/function.jvm.lux b/stdlib/source/lux/compiler/default/phase/translation/scheme/function.jvm.lux
index 113f6b325..437c92520 100644
--- a/stdlib/source/lux/compiler/default/phase/translation/scheme/function.jvm.lux
+++ b/stdlib/source/lux/compiler/default/phase/translation/scheme/function.jvm.lux
@@ -70,8 +70,8 @@
(_.letrec (list [@function (_.lambda [(list) (#.Some @curried)]
(_.let (list [@num-args (_.length/1 @curried)])
(<| (_.if (|> @num-args (_.=/2 arityO))
- (<| (_.let (list [(reference.local' +0) @function]))
- (_.let-values (list [[(|> (list.n/range +0 (dec arity))
+ (<| (_.let (list [(reference.local' |0) @function]))
+ (_.let-values (list [[(|> (list.n/range |0 (dec arity))
(list/map ..input))
#.None]
(_.apply/2 (_.global "apply") (_.global "values") @curried)]))
diff --git a/stdlib/source/lux/compiler/default/phase/translation/scheme/runtime.jvm.lux b/stdlib/source/lux/compiler/default/phase/translation/scheme/runtime.jvm.lux
index 607d922e4..a2c9e31da 100644
--- a/stdlib/source/lux/compiler/default/phase/translation/scheme/runtime.jvm.lux
+++ b/stdlib/source/lux/compiler/default/phase/translation/scheme/runtime.jvm.lux
@@ -58,19 +58,19 @@
(def: #export none
Computation
- (variant [+0 #0 ..unit]))
+ (variant [|0 #0 ..unit]))
(def: #export some
(-> Expression Computation)
- (|>> [+0 #1] ..variant))
+ (|>> [|0 #1] ..variant))
(def: #export left
(-> Expression Computation)
- (|>> [+0 #0] ..variant))
+ (|>> [|0 #0] ..variant))
(def: #export right
(-> Expression Computation)
- (|>> [+0 #1] ..variant))
+ (|>> [|0 #1] ..variant))
(def: declaration
(s.Syntax [Text (List Text)])