aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/target
diff options
context:
space:
mode:
authorEduardo Julian2019-07-26 21:23:27 -0400
committerEduardo Julian2019-07-26 21:23:27 -0400
commita0889b2ee76c1ae7a9a5bbe2eec9f051b4f341e4 (patch)
tree08df3db7f8fffad6360a476d20db1d40b36c85cb /stdlib/source/lux/target
parent78fd01f7e6688448bbd710336d4d7b1c35ae058a (diff)
No more "n/"-prefixed functions.
Diffstat (limited to 'stdlib/source/lux/target')
-rw-r--r--stdlib/source/lux/target/jvm/attribute.lux8
-rw-r--r--stdlib/source/lux/target/jvm/attribute/code.lux8
-rw-r--r--stdlib/source/lux/target/jvm/attribute/code/exception.lux4
-rw-r--r--stdlib/source/lux/target/jvm/constant/pool.lux7
-rw-r--r--stdlib/source/lux/target/jvm/encoding/signed.lux7
-rw-r--r--stdlib/source/lux/target/jvm/encoding/unsigned.lux11
-rw-r--r--stdlib/source/lux/target/jvm/instruction.lux8
-rw-r--r--stdlib/source/lux/target/jvm/instruction/bytecode.lux41
-rw-r--r--stdlib/source/lux/target/jvm/instruction/condition.lux13
-rw-r--r--stdlib/source/lux/target/jvm/instruction/resources.lux4
-rw-r--r--stdlib/source/lux/target/jvm/reflection.lux4
11 files changed, 65 insertions, 50 deletions
diff --git a/stdlib/source/lux/target/jvm/attribute.lux b/stdlib/source/lux/target/jvm/attribute.lux
index fef8598e8..236ecf608 100644
--- a/stdlib/source/lux/target/jvm/attribute.lux
+++ b/stdlib/source/lux/target/jvm/attribute.lux
@@ -9,6 +9,8 @@
["." exception (#+ exception:)]]
[data
["." product]
+ [number
+ ["n" nat]]
[format
[".F" binary (#+ Writer) ("#@." monoid)]]]]
["." // #_
@@ -43,7 +45,7 @@
(let [[nameS nameT] (//index.writer name)
[lengthS lengthT] (//unsigned.u4-writer length)
[infoS infoT] (writer info)]
- [($_ n/+ nameS lengthS infoS)
+ [($_ n.+ nameS lengthS infoS)
(|>> nameT lengthT infoT)])))
(with-expansions [<Code> (as-is (/code.Code Attribute))]
@@ -64,7 +66,7 @@
(info-equivalence (/code.equivalence equivalence))))))
(def: fixed-attribute-length
- ($_ n/+
+ ($_ n.+
## u2 attribute_name_index;
//unsigned.u2-bytes
## u4 attribute_length;
@@ -76,7 +78,7 @@
(case attribute
(^template [<tag>]
(<tag> [name length info])
- (|> length //unsigned.nat .nat (n/+ fixed-attribute-length)))
+ (|> length //unsigned.nat .nat (n.+ fixed-attribute-length)))
([#Constant] [#Code])))
(def: constant-name "ConstantValue")
diff --git a/stdlib/source/lux/target/jvm/attribute/code.lux b/stdlib/source/lux/target/jvm/attribute/code.lux
index 61c19ccfa..0bf1bec4e 100644
--- a/stdlib/source/lux/target/jvm/attribute/code.lux
+++ b/stdlib/source/lux/target/jvm/attribute/code.lux
@@ -5,6 +5,8 @@
["." equivalence (#+ Equivalence)]]
[data
["." binary (#+ Binary)]
+ [number
+ ["n" nat]]
[format
[".F" binary (#+ Writer) ("#@." monoid)]]
[collection
@@ -25,7 +27,7 @@
(def: #export (length length code)
(All [Attribute] (-> (-> Attribute Nat) (Code Attribute) Nat))
- ($_ n/+
+ ($_ n.+
## u2 max_stack;
## u2 max_locals;
///resources.length
@@ -39,14 +41,14 @@
(|> code
(get@ #exception-table)
row.size
- (n/* /exception.length))
+ (n.* /exception.length))
## u2 attributes_count;
///unsigned.u2-bytes
## attribute_info attributes[attributes_count];
(|> code
(get@ #attributes)
(row@map length)
- (row@fold n/+ 0))))
+ (row@fold n.+ 0))))
(def: #export (equivalence attribute-equivalence)
(All [attribute]
diff --git a/stdlib/source/lux/target/jvm/attribute/code/exception.lux b/stdlib/source/lux/target/jvm/attribute/code/exception.lux
index b291baf3e..17111c251 100644
--- a/stdlib/source/lux/target/jvm/attribute/code/exception.lux
+++ b/stdlib/source/lux/target/jvm/attribute/code/exception.lux
@@ -3,6 +3,8 @@
[abstract
["." equivalence (#+ Equivalence)]]
[data
+ [number
+ ["n" nat]]
[format
[".F" binary (#+ Writer)]]]]
["." // #_
@@ -32,7 +34,7 @@
## https://docs.oracle.com/javase/specs/jvms/se8/html/jvms-4.html#jvms-4.7.3
(def: #export length
Nat
- ($_ n/+
+ ($_ n.+
## u2 start_pc;
////unsigned.u2-bytes
## u2 end_pc;
diff --git a/stdlib/source/lux/target/jvm/constant/pool.lux b/stdlib/source/lux/target/jvm/constant/pool.lux
index 6db92879c..bd8b7cb3d 100644
--- a/stdlib/source/lux/target/jvm/constant/pool.lux
+++ b/stdlib/source/lux/target/jvm/constant/pool.lux
@@ -11,6 +11,7 @@
[data
[number
["." i32]
+ ["n" nat]
["." int]
["." frac]]
["." text
@@ -85,10 +86,10 @@
(#.Some [index entry])
(let [index' (!raw-index index)
<index>' (!raw-index <index>)]
- (cond (n/< index' <index>')
+ (cond (n.< index' <index>')
(recur (inc idx))
- (n/= index' <index>')
+ (n.= index' <index>')
(case entry
(<tag> value)
[[next pool] (#try.Success value)]
@@ -96,7 +97,7 @@
_
[[next pool] (exception.throw ..invalid-constant [<index> (name-of <tag>)])])
- ## (n/> index' <index>')
+ ## (n.> index' <index>')
<failure>))
#.None
diff --git a/stdlib/source/lux/target/jvm/encoding/signed.lux b/stdlib/source/lux/target/jvm/encoding/signed.lux
index fb684847b..3609142a3 100644
--- a/stdlib/source/lux/target/jvm/encoding/signed.lux
+++ b/stdlib/source/lux/target/jvm/encoding/signed.lux
@@ -6,6 +6,7 @@
[data
[number
["." i64]
+ ["n" nat]
["i" int]]
[format
[".F" binary (#+ Writer)]]]
@@ -43,16 +44,16 @@
(def: #export <max>
<name>
- (|> <bytes> (n/* i64.bits-per-byte) dec i64.mask :abstraction))
+ (|> <bytes> (n.* i64.bits-per-byte) dec i64.mask :abstraction))
(def: #export <constructor>
(-> Int <name>)
- (let [limit (|> <bytes> (n/* i64.bits-per-byte) i64.mask .nat)]
+ (let [limit (|> <bytes> (n.* i64.bits-per-byte) i64.mask .nat)]
(|>> (i64.and limit) :abstraction)))
(def: #export (<+> parameter subject)
(-> <name> <name> <name>)
- (let [limit (|> <bytes> (n/* i64.bits-per-byte) i64.mask .nat)]
+ (let [limit (|> <bytes> (n.* i64.bits-per-byte) i64.mask .nat)]
(:abstraction
(i64.and limit
(i.+ (:representation parameter)
diff --git a/stdlib/source/lux/target/jvm/encoding/unsigned.lux b/stdlib/source/lux/target/jvm/encoding/unsigned.lux
index b0b8ff312..56885d576 100644
--- a/stdlib/source/lux/target/jvm/encoding/unsigned.lux
+++ b/stdlib/source/lux/target/jvm/encoding/unsigned.lux
@@ -5,7 +5,8 @@
[order (#+ Order)]]
[data
[number
- ["." i64]]
+ ["." i64]
+ ["n" nat]]
[format
[".F" binary (#+ Writer)]]]
[macro
@@ -24,14 +25,14 @@
(structure: #export equivalence
(All [brand] (Equivalence (Unsigned brand)))
(def: (= reference sample)
- (n/= (:representation reference) (:representation sample))))
+ (n.= (:representation reference) (:representation sample))))
(structure: #export order
(All [brand] (Order (Unsigned brand)))
(def: &equivalence ..equivalence)
(def: (< reference sample)
- (n/< (:representation reference) (:representation sample))))
+ (n.< (:representation reference) (:representation sample))))
(template [<bytes> <name> <size> <constructor> <max> <+>]
[(with-expansions [<raw> (template.identifier [<name> "'"])]
@@ -42,7 +43,7 @@
(def: #export <max>
<name>
- (|> <bytes> (n/* i64.bits-per-byte) i64.mask :abstraction))
+ (|> <bytes> (n.* i64.bits-per-byte) i64.mask :abstraction))
(def: #export <constructor>
(-> Nat <name>)
@@ -52,7 +53,7 @@
(-> <name> <name> <name>)
(:abstraction
(i64.and (:representation <max>)
- (n/+ (:representation parameter)
+ (n.+ (:representation parameter)
(:representation subject)))))]
[1 U1 u1-bytes u1 max-u1 u1/+]
diff --git a/stdlib/source/lux/target/jvm/instruction.lux b/stdlib/source/lux/target/jvm/instruction.lux
index ac4732e12..02057202b 100644
--- a/stdlib/source/lux/target/jvm/instruction.lux
+++ b/stdlib/source/lux/target/jvm/instruction.lux
@@ -13,7 +13,7 @@
[text
["%" format (#+ format)]]
[number
- ["." nat]
+ ["n" nat]
["i" int]]
[collection
["." list ("#@." functor fold)]
@@ -47,7 +47,7 @@
Tracker
{#program-counter 0
#next-label 0
- #known-labels (dictionary.new nat.hash)})
+ #known-labels (dictionary.new n.hash)})
(type: #export Partial
(-> Resolver (Try Bytecode)))
@@ -365,8 +365,8 @@
(def: (jump @from @to)
(-> Address Address (Either Jump Big-Jump))
- (let [jump (.int (n/- @to @from))
- big? (n/> (//unsigned.nat //unsigned.max-u2)
+ (let [jump (.int (n.- @to @from))
+ big? (n.> (//unsigned.nat //unsigned.max-u2)
(.nat (i.* (if (i.>= +0 jump)
+1
-1)
diff --git a/stdlib/source/lux/target/jvm/instruction/bytecode.lux b/stdlib/source/lux/target/jvm/instruction/bytecode.lux
index bef2628f6..8a51097b7 100644
--- a/stdlib/source/lux/target/jvm/instruction/bytecode.lux
+++ b/stdlib/source/lux/target/jvm/instruction/bytecode.lux
@@ -7,8 +7,9 @@
["." try (#+ Try)]
["." exception (#+ exception:)]]
[data
- [number (#+ hex)]
["." binary]
+ [number (#+ hex)
+ ["n" nat]]
[text
["%" format (#+ format)]]
[format
@@ -53,13 +54,13 @@
(def: (nullary' code)
(-> Code Mutation)
(function (_ [offset binary])
- [(n/+ 1 offset)
+ [(n.+ 1 offset)
(try.assume
(binary.write/8 offset code binary))]))
(def: (nullary code [size mutation])
(-> Code (-> Specification Specification))
- [(n/+ 1 size)
+ [(n.+ 1 size)
(|>> mutation ((nullary' code)))])
(template [<shift> <name> <inputT> <writer> <unwrap>]
@@ -67,15 +68,15 @@
(def: (<private> code input0)
(-> Code <inputT> Mutation)
(function (_ [offset binary])
- [(n/+ <shift> offset)
+ [(n.+ <shift> offset)
(try.assume
(do try.monad
[_ (binary.write/8 offset code binary)]
- (<writer> (n/+ 1 offset) (<unwrap> input0) binary)))]))
+ (<writer> (n.+ 1 offset) (<unwrap> input0) binary)))]))
(def: (<name> code input0 [size mutation])
(-> Code <inputT> (-> Specification Specification))
- [(n/+ <shift> size)
+ [(n.+ <shift> size)
(|>> mutation ((<private> code input0)))]))]
[2 unary/1 U1 binary.write/8 ///unsigned.nat]
@@ -87,47 +88,47 @@
(def: (binary/11' code input0 input1)
(-> Code U1 U1 Mutation)
(function (_ [offset binary])
- [(n/+ 3 offset)
+ [(n.+ 3 offset)
(try.assume
(do try.monad
[_ (binary.write/8 offset code binary)
- _ (binary.write/8 (n/+ 1 offset) (///unsigned.nat input0) binary)]
- (binary.write/8 (n/+ 2 offset) (///unsigned.nat input1) binary)))]))
+ _ (binary.write/8 (n.+ 1 offset) (///unsigned.nat input0) binary)]
+ (binary.write/8 (n.+ 2 offset) (///unsigned.nat input1) binary)))]))
(def: (binary/11 code input0 input1 [size mutation])
(-> Code U1 U1 (-> Specification Specification))
- [(n/+ 3 size)
+ [(n.+ 3 size)
(|>> mutation ((binary/11' code input0 input1)))])
(def: (binary/21' code input0 input1)
(-> Code U2 U1 Mutation)
(function (_ [offset binary])
- [(n/+ 4 offset)
+ [(n.+ 4 offset)
(try.assume
(do try.monad
[_ (binary.write/8 offset code binary)
- _ (binary.write/16 (n/+ 1 offset) (///unsigned.nat input0) binary)]
- (binary.write/8 (n/+ 3 offset) (///unsigned.nat input1) binary)))]))
+ _ (binary.write/16 (n.+ 1 offset) (///unsigned.nat input0) binary)]
+ (binary.write/8 (n.+ 3 offset) (///unsigned.nat input1) binary)))]))
(def: (binary/21 code input0 input1 [size mutation])
(-> Code U2 U1 (-> Specification Specification))
- [(n/+ 4 size)
+ [(n.+ 4 size)
(|>> mutation ((binary/21' code input0 input1)))])
(def: (trinary/211' code input0 input1 input2)
(-> Code U2 U1 U1 Mutation)
(function (_ [offset binary])
- [(n/+ 5 offset)
+ [(n.+ 5 offset)
(try.assume
(do try.monad
[_ (binary.write/8 offset code binary)
- _ (binary.write/16 (n/+ 1 offset) (///unsigned.nat input0) binary)
- _ (binary.write/8 (n/+ 3 offset) (///unsigned.nat input1) binary)]
- (binary.write/8 (n/+ 4 offset) (///unsigned.nat input2) binary)))]))
+ _ (binary.write/16 (n.+ 1 offset) (///unsigned.nat input0) binary)
+ _ (binary.write/8 (n.+ 3 offset) (///unsigned.nat input1) binary)]
+ (binary.write/8 (n.+ 4 offset) (///unsigned.nat input2) binary)))]))
(def: (trinary/211 code input0 input1 input2 [size mutation])
(-> Code U2 U1 U1 (-> Specification Specification))
- [(n/+ 5 size)
+ [(n.+ 5 size)
(|>> mutation ((trinary/211' code input0 input1 input2)))])
(abstract: #export Primitive-Array-Type
@@ -483,7 +484,7 @@
(def: identity ..nop)
(def: (compose [left-size left] [right-size right])
- [(n/+ left-size right-size)
+ [(n.+ left-size right-size)
(function (_ input)
(do try.monad
[temp (left input)]
diff --git a/stdlib/source/lux/target/jvm/instruction/condition.lux b/stdlib/source/lux/target/jvm/instruction/condition.lux
index 04bb8c60b..82c709800 100644
--- a/stdlib/source/lux/target/jvm/instruction/condition.lux
+++ b/stdlib/source/lux/target/jvm/instruction/condition.lux
@@ -7,8 +7,9 @@
["." try (#+ Try)]
["." exception (#+ exception:)]]
[data
- [number (#+ hex)]
["." binary]
+ [number (#+ hex)
+ ["n" nat]]
[text
["%" format (#+ format)]]
[format
@@ -44,9 +45,9 @@
(def: #export (produces amount env)
(-> Nat Condition)
- (let [stack (n/+ amount
+ (let [stack (n.+ amount
(///unsigned.nat (get@ #stack env)))
- max-stack (n/max stack
+ max-stack (n.max stack
(///unsigned.nat (get@ [#resources #//resources.max-stack] env)))]
(|> env
(set@ #stack (///unsigned.u2 stack))
@@ -62,9 +63,9 @@
(def: #export (consumes wanted-pops env)
(-> Nat Condition)
(let [stack-size (///unsigned.nat (get@ #stack env))]
- (if (n/<= stack-size wanted-pops)
+ (if (n.<= stack-size wanted-pops)
(#try.Success (update@ #stack
- (|>> ///unsigned.nat (n/- wanted-pops) ///unsigned.u2)
+ (|>> ///unsigned.nat (n.- wanted-pops) ///unsigned.u2)
env))
(exception.throw ..cannot-pop-stack [stack-size wanted-pops]))))
@@ -72,7 +73,7 @@
(def: #export (has-local local environment)
(-> Local Condition)
- (let [max-locals (n/max (///unsigned.nat (get@ [#resources #//resources.max-locals] environment))
+ (let [max-locals (n.max (///unsigned.nat (get@ [#resources #//resources.max-locals] environment))
(///unsigned.nat local))]
(|> environment
(set@ [#resources #//resources.max-locals]
diff --git a/stdlib/source/lux/target/jvm/instruction/resources.lux b/stdlib/source/lux/target/jvm/instruction/resources.lux
index fa83c4071..c7d741a1d 100644
--- a/stdlib/source/lux/target/jvm/instruction/resources.lux
+++ b/stdlib/source/lux/target/jvm/instruction/resources.lux
@@ -3,6 +3,8 @@
[abstract
["." equivalence (#+ Equivalence)]]
[data
+ [number
+ ["n" nat]]
[format
[".F" binary (#+ Writer) ("#@." monoid)]]]]
["." /// #_
@@ -19,7 +21,7 @@
#max-locals (///unsigned.u2 0)})
(def: #export length
- ($_ n/+
+ ($_ n.+
## u2 max_stack;
///unsigned.u2-bytes
## u2 max_locals;
diff --git a/stdlib/source/lux/target/jvm/reflection.lux b/stdlib/source/lux/target/jvm/reflection.lux
index e52395dc3..89f759dcb 100644
--- a/stdlib/source/lux/target/jvm/reflection.lux
+++ b/stdlib/source/lux/target/jvm/reflection.lux
@@ -10,6 +10,8 @@
[parser
["<t>" text]]]
[data
+ [number
+ ["n" nat]]
["." text ("#@." equivalence)
["%" format (#+ format)]]
[collection
@@ -264,7 +266,7 @@
num-class-params (list.size class-params)
num-type-params (list.size params)]
(if (text@= class-name name)
- (if (n/= num-class-params num-type-params)
+ (if (n.= num-class-params num-type-params)
(|> params
(list.zip2 (list@map (|>> java/lang/reflect/TypeVariable::getName)
class-params))