aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/library/lux/target/jvm/bytecode/instruction.lux58
1 files changed, 29 insertions, 29 deletions
diff --git a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
index 9345f2ec2..ca4dfcff6 100644
--- a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
+++ b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux
@@ -44,18 +44,18 @@
(type: .public Estimator
(-> Address Size))
-(def: fixed
+(def fixed
(-> Size Estimator)
function.constant)
(type: .public Instruction
(-> Specification Specification))
-(def: .public empty
+(def .public empty
Instruction
function.identity)
-(def: .public result
+(def .public result
(-> Instruction Specification)
(function.on \\format.no_op))
@@ -63,7 +63,7 @@
Nat)
(with_template [<size> <name>]
- [(def: <name> Size (|> <size> ///unsigned.u2 try.trusted))]
+ [(def <name> Size (|> <size> ///unsigned.u2 try.trusted))]
[1 opcode_size]
[1 register_size]
@@ -73,14 +73,14 @@
[4 integer_size]
)
-(def: (nullary' opcode)
+(def (nullary' opcode)
(-> Opcode Mutation)
(function (_ [offset binary])
[(n.+ (///unsigned.value ..opcode_size)
offset)
(binary.has_8! offset opcode binary)]))
-(def: nullary
+(def nullary
[Estimator (-> Opcode Instruction)]
[(..fixed ..opcode_size)
(function (_ opcode [size mutation])
@@ -89,7 +89,7 @@
(|>> mutation ((nullary' opcode)))])])
(with_template [<name> <size>]
- [(def: <name>
+ [(def <name>
Size
(|> ..opcode_size
(///unsigned.+/2 <size>)
@@ -102,7 +102,7 @@
(with_template [<shift> <name> <inputT> <writer> <unwrap>]
[(with_expansions [<private> (template.symbol ["'" <name>])]
- (def: (<private> opcode input0)
+ (def (<private> opcode input0)
(-> Opcode <inputT> Mutation)
(function (_ [offset binary])
[(n.+ (///unsigned.value <shift>) offset)
@@ -111,7 +111,7 @@
(<writer> (n.+ (///unsigned.value ..opcode_size) offset)
(<unwrap> input0)))]))
- (def: <name>
+ (def <name>
[Estimator (-> Opcode <inputT> Instruction)]
[(..fixed <shift>)
(function (_ opcode input0 [size mutation])
@@ -126,7 +126,7 @@
(with_template [<shift> <name> <inputT> <writer>]
[(with_expansions [<private> (template.symbol ["'" <name>])]
- (def: (<private> opcode input0)
+ (def (<private> opcode input0)
(-> Opcode <inputT> Mutation)
(function (_ [offset binary])
[(n.+ (///unsigned.value <shift>) offset)
@@ -135,7 +135,7 @@
(<writer> (n.+ (///unsigned.value ..opcode_size) offset)
(///signed.value input0)))]))
- (def: <name>
+ (def <name>
[Estimator (-> Opcode <inputT> Instruction)]
[(..fixed <shift>)
(function (_ opcode input0 [size mutation])
@@ -146,13 +146,13 @@
[..size/2 unary/2' S2 binary.has_16!]
)
-(def: size/11
+(def size/11
Size
(|> ..opcode_size
(///unsigned.+/2 ..register_size) try.trusted
(///unsigned.+/2 ..byte_size) try.trusted))
-(def: (binary/11' opcode input0 input1)
+(def (binary/11' opcode input0 input1)
(-> Opcode U1 U1 Mutation)
(function (_ [offset binary])
[(n.+ (///unsigned.value ..size/11) offset)
@@ -163,20 +163,20 @@
(binary.has_8! (n.+ (///unsigned.value ..size/1) offset)
(///unsigned.value input1)))]))
-(def: binary/11
+(def binary/11
[Estimator (-> Opcode U1 U1 Instruction)]
[(..fixed ..size/11)
(function (_ opcode input0 input1 [size mutation])
[(n.+ (///unsigned.value ..size/11) size)
(|>> mutation ((binary/11' opcode input0 input1)))])])
-(def: size/21
+(def size/21
Size
(|> ..opcode_size
(///unsigned.+/2 ..index_size) try.trusted
(///unsigned.+/2 ..byte_size) try.trusted))
-(def: (binary/21' opcode input0 input1)
+(def (binary/21' opcode input0 input1)
(-> Opcode U2 U1 Mutation)
(function (_ [offset binary])
[(n.+ (///unsigned.value ..size/21) offset)
@@ -187,21 +187,21 @@
(binary.has_8! (n.+ (///unsigned.value ..size/2) offset)
(///unsigned.value input1)))]))
-(def: binary/21
+(def binary/21
[Estimator (-> Opcode U2 U1 Instruction)]
[(..fixed ..size/21)
(function (_ opcode input0 input1 [size mutation])
[(n.+ (///unsigned.value ..size/21) size)
(|>> mutation ((binary/21' opcode input0 input1)))])])
-(def: size/211
+(def size/211
Size
(|> ..opcode_size
(///unsigned.+/2 ..index_size) try.trusted
(///unsigned.+/2 ..byte_size) try.trusted
(///unsigned.+/2 ..byte_size) try.trusted))
-(def: (trinary/211' opcode input0 input1 input2)
+(def (trinary/211' opcode input0 input1 input2)
(-> Opcode U2 U1 U1 Mutation)
(function (_ [offset binary])
[(n.+ (///unsigned.value ..size/211) offset)
@@ -214,7 +214,7 @@
(binary.has_8! (n.+ (///unsigned.value ..size/21) offset)
(///unsigned.value input2)))]))
-(def: trinary/211
+(def trinary/211
[Estimator (-> Opcode U2 U1 U1 Instruction)]
[(..fixed ..size/211)
(function (_ opcode input0 input1 input2 [size mutation])
@@ -224,12 +224,12 @@
(primitive .public Primitive_Array_Type
U1
- (def: code
+ (def code
(-> Primitive_Array_Type U1)
(|>> representation))
(with_template [<code> <name>]
- [(def: .public <name>
+ [(def .public <name>
(|> <code> ///unsigned.u1 try.trusted abstraction))]
[04 t_boolean]
@@ -481,7 +481,7 @@
[<input_name>]
<inputs>')]
- (def: .public <name>
+ (def .public <name>
[Estimator (-> [<input_types>] Instruction)]
(let [[estimator <arity>'] <arity>]
[estimator
@@ -564,7 +564,7 @@
[["B9" invokeinterface [[index (Index (Reference Method))] [count U1] [output_count U1]] [(///index.value index) count (try.trusted (///unsigned.u1 0))]]]]
))
-(def: (switch_padding offset)
+(def (switch_padding offset)
(-> Nat Nat)
(let [parameter_start (n.+ (///unsigned.value ..opcode_size)
offset)]
@@ -572,7 +572,7 @@
(n.- (n.% 4 parameter_start)
4))))
-(def: .public tableswitch
+(def .public tableswitch
[(-> Nat Estimator)
(-> S4 Big_Jump [Big_Jump (List Big_Jump)] Instruction)]
(let [estimator (is (-> Nat Estimator)
@@ -636,7 +636,7 @@
size)
(|>> mutation tableswitch_mutation)]))))]))
-(def: .public lookupswitch
+(def .public lookupswitch
[(-> Nat Estimator)
(-> Big_Jump (List [S4 Big_Jump]) Instruction)]
(let [case_size (n.+ (///unsigned.value ..integer_size)
@@ -694,10 +694,10 @@
size)
(|>> mutation lookupswitch_mutation)]))))]))
-(def: .public monoid
+(def .public monoid
(Monoid Instruction)
(implementation
- (def: identity ..empty)
+ (def identity ..empty)
- (def: (composite left right)
+ (def (composite left right)
(|>> left right))))