aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/target/jvm/bytecode/instruction.lux
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/target/jvm/bytecode/instruction.lux402
1 files changed, 201 insertions, 201 deletions
diff --git a/stdlib/source/lux/target/jvm/bytecode/instruction.lux b/stdlib/source/lux/target/jvm/bytecode/instruction.lux
index f72314163..91bba4ec3 100644
--- a/stdlib/source/lux/target/jvm/bytecode/instruction.lux
+++ b/stdlib/source/lux/target/jvm/bytecode/instruction.lux
@@ -21,7 +21,7 @@
abstract]]
["." // #_
["#." address (#+ Address)]
- ["#." jump (#+ Jump Big-Jump)]
+ ["#." jump (#+ Jump Big_Jump)]
[environment
[limit
[registry (#+ Register)]]]
@@ -52,50 +52,50 @@
(def: #export run
(-> Instruction Specification)
- (function.apply format.no-op))
+ (function.apply format.no_op))
(type: Opcode Nat)
(template [<name> <size>]
[(def: <name> Size (|> <size> ///unsigned.u2 try.assume))]
- [opcode-size 1]
- [register-size 1]
- [byte-size 1]
- [index-size 2]
- [big-jump-size 4]
- [integer-size 4]
+ [opcode_size 1]
+ [register_size 1]
+ [byte_size 1]
+ [index_size 2]
+ [big_jump_size 4]
+ [integer_size 4]
)
(def: (nullary' opcode)
(-> Opcode Mutation)
(function (_ [offset binary])
- [(n.+ (///unsigned.value ..opcode-size)
+ [(n.+ (///unsigned.value ..opcode_size)
offset)
(try.assume
(binary.write/8 offset opcode binary))]))
(def: nullary
[Estimator (-> Opcode Instruction)]
- [(..fixed ..opcode-size)
+ [(..fixed ..opcode_size)
(function (_ opcode [size mutation])
- [(n.+ (///unsigned.value ..opcode-size)
+ [(n.+ (///unsigned.value ..opcode_size)
size)
(|>> mutation ((nullary' opcode)))])])
(template [<name> <size>]
[(def: <name>
Size
- (|> ..opcode-size
+ (|> ..opcode_size
(///unsigned.+/2 <size>) try.assume))]
- [size/1 ..register-size]
- [size/2 ..index-size]
- [size/4 ..big-jump-size]
+ [size/1 ..register_size]
+ [size/2 ..index_size]
+ [size/4 ..big_jump_size]
)
(template [<shift> <name> <inputT> <writer> <unwrap>]
- [(with-expansions [<private> (template.identifier ["'" <name>])]
+ [(with_expansions [<private> (template.identifier ["'" <name>])]
(def: (<private> opcode input0)
(-> Opcode <inputT> Mutation)
(function (_ [offset binary])
@@ -103,7 +103,7 @@
(try.assume
(do try.monad
[_ (binary.write/8 offset opcode binary)]
- (<writer> (n.+ (///unsigned.value ..opcode-size) offset)
+ (<writer> (n.+ (///unsigned.value ..opcode_size) offset)
(<unwrap> input0)
binary)))]))
@@ -117,11 +117,11 @@
[..size/1 unary/1 U1 binary.write/8 ///unsigned.value]
[..size/2 unary/2 U2 binary.write/16 ///unsigned.value]
[..size/2 jump/2 Jump binary.write/16 ///signed.value]
- [..size/4 jump/4 Big-Jump binary.write/32 ///signed.value]
+ [..size/4 jump/4 Big_Jump binary.write/32 ///signed.value]
)
(template [<shift> <name> <inputT> <writer>]
- [(with-expansions [<private> (template.identifier ["'" <name>])]
+ [(with_expansions [<private> (template.identifier ["'" <name>])]
(def: (<private> opcode input0)
(-> Opcode <inputT> Mutation)
(function (_ [offset binary])
@@ -129,7 +129,7 @@
(try.assume
(do try.monad
[_ (binary.write/8 offset opcode binary)]
- (<writer> (n.+ (///unsigned.value ..opcode-size) offset)
+ (<writer> (n.+ (///unsigned.value ..opcode_size) offset)
(///signed.value input0)
binary)))]))
@@ -146,9 +146,9 @@
(def: size/11
Size
- (|> ..opcode-size
- (///unsigned.+/2 ..register-size) try.assume
- (///unsigned.+/2 ..byte-size) try.assume))
+ (|> ..opcode_size
+ (///unsigned.+/2 ..register_size) try.assume
+ (///unsigned.+/2 ..byte_size) try.assume))
(def: (binary/11' opcode input0 input1)
(-> Opcode U1 U1 Mutation)
@@ -157,7 +157,7 @@
(try.assume
(do try.monad
[_ (binary.write/8 offset opcode binary)
- _ (binary.write/8 (n.+ (///unsigned.value ..opcode-size) offset)
+ _ (binary.write/8 (n.+ (///unsigned.value ..opcode_size) offset)
(///unsigned.value input0)
binary)]
(binary.write/8 (n.+ (///unsigned.value ..size/1) offset)
@@ -173,9 +173,9 @@
(def: size/21
Size
- (|> ..opcode-size
- (///unsigned.+/2 ..index-size) try.assume
- (///unsigned.+/2 ..byte-size) try.assume))
+ (|> ..opcode_size
+ (///unsigned.+/2 ..index_size) try.assume
+ (///unsigned.+/2 ..byte_size) try.assume))
(def: (binary/21' opcode input0 input1)
(-> Opcode U2 U1 Mutation)
@@ -184,7 +184,7 @@
(try.assume
(do try.monad
[_ (binary.write/8 offset opcode binary)
- _ (binary.write/16 (n.+ (///unsigned.value ..opcode-size) offset)
+ _ (binary.write/16 (n.+ (///unsigned.value ..opcode_size) offset)
(///unsigned.value input0)
binary)]
(binary.write/8 (n.+ (///unsigned.value ..size/2) offset)
@@ -200,10 +200,10 @@
(def: size/211
Size
- (|> ..opcode-size
- (///unsigned.+/2 ..index-size) try.assume
- (///unsigned.+/2 ..byte-size) try.assume
- (///unsigned.+/2 ..byte-size) try.assume))
+ (|> ..opcode_size
+ (///unsigned.+/2 ..index_size) try.assume
+ (///unsigned.+/2 ..byte_size) try.assume
+ (///unsigned.+/2 ..byte_size) try.assume))
(def: (trinary/211' opcode input0 input1 input2)
(-> Opcode U2 U1 U1 Mutation)
@@ -212,7 +212,7 @@
(try.assume
(do try.monad
[_ (binary.write/8 offset opcode binary)
- _ (binary.write/16 (n.+ (///unsigned.value ..opcode-size) offset)
+ _ (binary.write/16 (n.+ (///unsigned.value ..opcode_size) offset)
(///unsigned.value input0)
binary)
_ (binary.write/8 (n.+ (///unsigned.value ..size/2) offset)
@@ -229,50 +229,50 @@
[(n.+ (///unsigned.value ..size/211) size)
(|>> mutation ((trinary/211' opcode input0 input1 input2)))])])
-(abstract: #export Primitive-Array-Type
+(abstract: #export Primitive_Array_Type
U1
(def: code
- (-> Primitive-Array-Type U1)
+ (-> Primitive_Array_Type U1)
(|>> :representation))
(template [<code> <name>]
[(def: #export <name> (|> <code> ///unsigned.u1 try.assume :abstraction))]
- [04 t-boolean]
- [05 t-char]
- [06 t-float]
- [07 t-double]
- [08 t-byte]
- [09 t-short]
- [10 t-int]
- [11 t-long]
+ [04 t_boolean]
+ [05 t_char]
+ [06 t_float]
+ [07 t_double]
+ [08 t_byte]
+ [09 t_short]
+ [10 t_int]
+ [11 t_long]
))
## https://docs.oracle.com/javase/specs/jvms/se8/html/jvms-6.html#jvms-6.5
-(with-expansions [<constants> (template [<code> <name>]
+(with_expansions [<constants> (template [<code> <name>]
[[<code> <name> [] []]]
- ["01" aconst-null]
+ ["01" aconst_null]
- ["02" iconst-m1]
- ["03" iconst-0]
- ["04" iconst-1]
- ["05" iconst-2]
- ["06" iconst-3]
- ["07" iconst-4]
- ["08" iconst-5]
+ ["02" iconst_m1]
+ ["03" iconst_0]
+ ["04" iconst_1]
+ ["05" iconst_2]
+ ["06" iconst_3]
+ ["07" iconst_4]
+ ["08" iconst_5]
- ["09" lconst-0]
- ["0A" lconst-1]
+ ["09" lconst_0]
+ ["0A" lconst_1]
- ["0B" fconst-0]
- ["0C" fconst-1]
- ["0D" fconst-2]
+ ["0B" fconst_0]
+ ["0C" fconst_1]
+ ["0D" fconst_2]
- ["0E" dconst-0]
- ["0F" dconst-1])
- <register-loads> (template [<code> <name>]
+ ["0E" dconst_0]
+ ["0F" dconst_1])
+ <register_loads> (template [<code> <name>]
[[<code> <name> [[register Register]] [register]]]
["15" iload]
@@ -280,34 +280,34 @@
["17" fload]
["18" dload]
["19" aload])
- <simple-register-loads> (template [<code> <name>]
+ <simple_register_loads> (template [<code> <name>]
[[<code> <name> [] []]]
- ["1A" iload-0]
- ["1B" iload-1]
- ["1C" iload-2]
- ["1D" iload-3]
+ ["1A" iload_0]
+ ["1B" iload_1]
+ ["1C" iload_2]
+ ["1D" iload_3]
- ["1E" lload-0]
- ["1F" lload-1]
- ["20" lload-2]
- ["21" lload-3]
+ ["1E" lload_0]
+ ["1F" lload_1]
+ ["20" lload_2]
+ ["21" lload_3]
- ["22" fload-0]
- ["23" fload-1]
- ["24" fload-2]
- ["25" fload-3]
+ ["22" fload_0]
+ ["23" fload_1]
+ ["24" fload_2]
+ ["25" fload_3]
- ["26" dload-0]
- ["27" dload-1]
- ["28" dload-2]
- ["29" dload-3]
+ ["26" dload_0]
+ ["27" dload_1]
+ ["28" dload_2]
+ ["29" dload_3]
- ["2A" aload-0]
- ["2B" aload-1]
- ["2C" aload-2]
- ["2D" aload-3])
- <register-stores> (template [<code> <name>]
+ ["2A" aload_0]
+ ["2B" aload_1]
+ ["2C" aload_2]
+ ["2D" aload_3])
+ <register_stores> (template [<code> <name>]
[[<code> <name> [[register Register]] [register]]]
["36" istore]
@@ -315,34 +315,34 @@
["38" fstore]
["39" dstore]
["3A" astore])
- <simple-register-stores> (template [<code> <name>]
+ <simple_register_stores> (template [<code> <name>]
[[<code> <name> [] []]]
- ["3B" istore-0]
- ["3C" istore-1]
- ["3D" istore-2]
- ["3E" istore-3]
-
- ["3F" lstore-0]
- ["40" lstore-1]
- ["41" lstore-2]
- ["42" lstore-3]
-
- ["43" fstore-0]
- ["44" fstore-1]
- ["45" fstore-2]
- ["46" fstore-3]
-
- ["47" dstore-0]
- ["48" dstore-1]
- ["49" dstore-2]
- ["4A" dstore-3]
+ ["3B" istore_0]
+ ["3C" istore_1]
+ ["3D" istore_2]
+ ["3E" istore_3]
+
+ ["3F" lstore_0]
+ ["40" lstore_1]
+ ["41" lstore_2]
+ ["42" lstore_3]
+
+ ["43" fstore_0]
+ ["44" fstore_1]
+ ["45" fstore_2]
+ ["46" fstore_3]
+
+ ["47" dstore_0]
+ ["48" dstore_1]
+ ["49" dstore_2]
+ ["4A" dstore_3]
- ["4B" astore-0]
- ["4C" astore-1]
- ["4D" astore-2]
- ["4E" astore-3])
- <array-loads> (template [<code> <name>]
+ ["4B" astore_0]
+ ["4C" astore_1]
+ ["4D" astore_2]
+ ["4E" astore_3])
+ <array_loads> (template [<code> <name>]
[[<code> <name> [] []]]
["2E" iaload]
@@ -353,7 +353,7 @@
["33" baload]
["34" caload]
["35" saload])
- <array-stores> (template [<code> <name>]
+ <array_stores> (template [<code> <name>]
[[<code> <name> [] []]]
["4f" iastore]
@@ -454,15 +454,15 @@
["9D" ifgt]
["9E" ifle]
- ["9F" if-icmpeq]
- ["A0" if-icmpne]
- ["A1" if-icmplt]
- ["A2" if-icmpge]
- ["A3" if-icmpgt]
- ["A4" if-icmple]
+ ["9F" if_icmpeq]
+ ["A0" if_icmpne]
+ ["A1" if_icmplt]
+ ["A2" if_icmpge]
+ ["A3" if_icmpgt]
+ ["A4" if_icmple]
- ["A5" if-acmpeq]
- ["A6" if-acmpne]
+ ["A5" if_acmpeq]
+ ["A6" if_acmpne]
["A7" goto]
["A8" jsr]
@@ -477,23 +477,23 @@
["B4" getfield/1] ["B4" getfield/2]
["B5" putfield/1] ["B5" putfield/2])]
(template [<arity> <definitions>]
- [(with-expansions [<definitions>' (template.splice <definitions>)]
- (template [<code> <name> <instruction-inputs> <arity-inputs>]
- [(with-expansions [<inputs>' (template.splice <instruction-inputs>)
- <input-types> (template [<input-name> <input-type>]
- [<input-type>]
+ [(with_expansions [<definitions>' (template.splice <definitions>)]
+ (template [<code> <name> <instruction_inputs> <arity_inputs>]
+ [(with_expansions [<inputs>' (template.splice <instruction_inputs>)
+ <input_types> (template [<input_name> <input_type>]
+ [<input_type>]
<inputs>')
- <input-names> (template [<input-name> <input-type>]
- [<input-name>]
+ <input_names> (template [<input_name> <input_type>]
+ [<input_name>]
<inputs>')]
(def: #export <name>
- [Estimator (-> [<input-types>] Instruction)]
+ [Estimator (-> [<input_types>] Instruction)]
(let [[estimator <arity>'] <arity>]
[estimator
- (function (_ [<input-names>])
- (`` (<arity>' (hex <code>) (~~ (template.splice <arity-inputs>)))))])))]
+ (function (_ [<input_names>])
+ (`` (<arity>' (hex <code>) (~~ (template.splice <arity_inputs>)))))])))]
<definitions>'
))]
@@ -504,16 +504,16 @@
["57" pop [] []]
["58" pop2 [] []]
["59" dup [] []]
- ["5A" dup-x1 [] []]
- ["5B" dup-x2 [] []]
+ ["5A" dup_x1 [] []]
+ ["5B" dup_x2 [] []]
["5C" dup2 [] []]
- ["5D" dup2-x1 [] []]
- ["5E" dup2-x2 [] []]
+ ["5D" dup2_x1 [] []]
+ ["5E" dup2_x2 [] []]
["5F" swap [] []]
- <simple-register-loads>
- <array-loads>
- <simple-register-stores>
- <array-stores>
+ <simple_register_loads>
+ <array_loads>
+ <simple_register_stores>
+ <array_stores>
<arithmetic>
["79" lshl [] []]
["7B" lshr [] []]
@@ -528,28 +528,28 @@
[..unary/1
[["12" ldc [[index U1]] [index]]
- <register-loads>
- <register-stores>
+ <register_loads>
+ <register_stores>
["A9" ret [[register Register]] [register]]
- ["BC" newarray [[type Primitive-Array-Type]] [(..code type)]]]]
+ ["BC" newarray [[type Primitive_Array_Type]] [(..code type)]]]]
[..unary/1'
[["10" bipush [[byte S1]] [byte]]]]
[..unary/2
- [["13" ldc-w/integer [[index (Index ///constant.Integer)]] [(///index.value index)]]
- ["13" ldc-w/float [[index (Index ///constant.Float)]] [(///index.value index)]]
- ["13" ldc-w/string [[index (Index ///constant.String)]] [(///index.value index)]]
- ["14" ldc2-w/long [[index (Index ///constant.Long)]] [(///index.value index)]]
- ["14" ldc2-w/double [[index (Index ///constant.Double)]] [(///index.value index)]]
+ [["13" ldc_w/integer [[index (Index ///constant.Integer)]] [(///index.value index)]]
+ ["13" ldc_w/float [[index (Index ///constant.Float)]] [(///index.value index)]]
+ ["13" ldc_w/string [[index (Index ///constant.String)]] [(///index.value index)]]
+ ["14" ldc2_w/long [[index (Index ///constant.Long)]] [(///index.value index)]]
+ ["14" ldc2_w/double [[index (Index ///constant.Double)]] [(///index.value index)]]
<fields>
["BB" new [[index (Index Class)]] [(///index.value index)]]
["BD" anewarray [[index (Index Class)]] [(///index.value index)]]
["C0" checkcast [[index (Index Class)]] [(///index.value index)]]
["C1" instanceof [[index (Index Class)]] [(///index.value index)]]
- ["B6" invokevirtual [[index (Index (Reference Method))] [count U1] [output-count U1]] [(///index.value index)]]
- ["B7" invokespecial [[index (Index (Reference Method))] [count U1] [output-count U1]] [(///index.value index)]]
- ["B8" invokestatic [[index (Index (Reference Method))] [count U1] [output-count U1]] [(///index.value index)]]]]
+ ["B6" invokevirtual [[index (Index (Reference Method))] [count U1] [output_count U1]] [(///index.value index)]]
+ ["B7" invokespecial [[index (Index (Reference Method))] [count U1] [output_count U1]] [(///index.value index)]]
+ ["B8" invokestatic [[index (Index (Reference Method))] [count U1] [output_count U1]] [(///index.value index)]]]]
[..unary/2'
[["11" sipush [[short S2]] [short]]]]
@@ -558,8 +558,8 @@
[<jumps>]]
[..jump/4
- [["C8" goto-w [[jump Big-Jump]] [jump]]
- ["C9" jsr-w [[jump Big-Jump]] [jump]]]]
+ [["C8" goto_w [[jump Big_Jump]] [jump]]
+ ["C9" jsr_w [[jump Big_Jump]] [jump]]]]
[..binary/11
[["84" iinc [[register Register] [byte U1]] [register byte]]]]
@@ -568,52 +568,52 @@
[["C5" multianewarray [[index (Index Class)] [count U1]] [(///index.value index) count]]]]
[..trinary/211
- [["B9" invokeinterface [[index (Index (Reference Method))] [count U1] [output-count U1]] [(///index.value index) count (try.assume (///unsigned.u1 0))]]]]
+ [["B9" invokeinterface [[index (Index (Reference Method))] [count U1] [output_count U1]] [(///index.value index) count (try.assume (///unsigned.u1 0))]]]]
))
-(def: (switch-padding offset)
+(def: (switch_padding offset)
(-> Nat Nat)
- (let [parameter-start (n.+ (///unsigned.value ..opcode-size)
+ (let [parameter_start (n.+ (///unsigned.value ..opcode_size)
offset)]
(n.% 4
- (n.- (n.% 4 parameter-start)
+ (n.- (n.% 4 parameter_start)
4))))
(def: #export tableswitch
[(-> Nat Estimator)
- (-> S4 Big-Jump [Big-Jump (List Big-Jump)] Instruction)]
+ (-> S4 Big_Jump [Big_Jump (List Big_Jump)] Instruction)]
(let [estimator (: (-> Nat Estimator)
- (function (_ amount-of-afterwards offset)
+ (function (_ amount_of_afterwards offset)
(|> ($_ n.+
- (///unsigned.value ..opcode-size)
- (switch-padding (///unsigned.value (//address.value offset)))
- (///unsigned.value ..big-jump-size)
- (///unsigned.value ..integer-size)
- (///unsigned.value ..integer-size)
- (n.* (///unsigned.value ..big-jump-size)
- (inc amount-of-afterwards)))
+ (///unsigned.value ..opcode_size)
+ (switch_padding (///unsigned.value (//address.value offset)))
+ (///unsigned.value ..big_jump_size)
+ (///unsigned.value ..integer_size)
+ (///unsigned.value ..integer_size)
+ (n.* (///unsigned.value ..big_jump_size)
+ (inc amount_of_afterwards)))
///unsigned.u2
try.assume)))]
[estimator
- (function (_ minimum default [at-minimum afterwards])
- (let [amount-of-afterwards (list.size afterwards)
- estimator (estimator amount-of-afterwards)]
+ (function (_ minimum default [at_minimum afterwards])
+ (let [amount_of_afterwards (list.size afterwards)
+ estimator (estimator amount_of_afterwards)]
(function (_ [size mutation])
- (let [padding (switch-padding size)
- tableswitch-size (try.assume
+ (let [padding (switch_padding size)
+ tableswitch_size (try.assume
(do {! try.monad}
[size (///unsigned.u2 size)]
(\ ! map (|>> estimator ///unsigned.value)
(//address.move size //address.start))))
- tableswitch-mutation (: Mutation
+ tableswitch_mutation (: Mutation
(function (_ [offset binary])
- [(n.+ tableswitch-size offset)
+ [(n.+ tableswitch_size offset)
(try.assume
(do {! try.monad}
- [amount-of-afterwards (|> amount-of-afterwards .int ///signed.s4)
- maximum (///signed.+/4 minimum amount-of-afterwards)
+ [amount_of_afterwards (|> amount_of_afterwards .int ///signed.s4)
+ maximum (///signed.+/4 minimum amount_of_afterwards)
_ (binary.write/8 offset (hex "AA") binary)
- #let [offset (n.+ (///unsigned.value ..opcode-size) offset)]
+ #let [offset (n.+ (///unsigned.value ..opcode_size) offset)]
_ (case padding
3 (do !
[_ (binary.write/8 offset 0 binary)]
@@ -623,13 +623,13 @@
_ (wrap binary))
#let [offset (n.+ padding offset)]
_ (binary.write/32 offset (///signed.value default) binary)
- #let [offset (n.+ (///unsigned.value ..big-jump-size) offset)]
+ #let [offset (n.+ (///unsigned.value ..big_jump_size) offset)]
_ (binary.write/32 offset (///signed.value minimum) binary)
- #let [offset (n.+ (///unsigned.value ..integer-size) offset)]
+ #let [offset (n.+ (///unsigned.value ..integer_size) offset)]
_ (binary.write/32 offset (///signed.value maximum) binary)]
- (loop [offset (n.+ (///unsigned.value ..integer-size) offset)
- afterwards (: (List Big-Jump)
- (#.Cons at-minimum afterwards))]
+ (loop [offset (n.+ (///unsigned.value ..integer_size) offset)
+ afterwards (: (List Big_Jump)
+ (#.Cons at_minimum afterwards))]
(case afterwards
#.Nil
(wrap binary)
@@ -637,45 +637,45 @@
(#.Cons head tail)
(do !
[_ (binary.write/32 offset (///signed.value head) binary)]
- (recur (n.+ (///unsigned.value ..big-jump-size) offset)
+ (recur (n.+ (///unsigned.value ..big_jump_size) offset)
tail))))))]))]
- [(n.+ tableswitch-size
+ [(n.+ tableswitch_size
size)
- (|>> mutation tableswitch-mutation)]))))]))
+ (|>> mutation tableswitch_mutation)]))))]))
(def: #export lookupswitch
[(-> Nat Estimator)
- (-> Big-Jump (List [S4 Big-Jump]) Instruction)]
- (let [case-size (n.+ (///unsigned.value ..integer-size)
- (///unsigned.value ..big-jump-size))
+ (-> Big_Jump (List [S4 Big_Jump]) Instruction)]
+ (let [case_size (n.+ (///unsigned.value ..integer_size)
+ (///unsigned.value ..big_jump_size))
estimator (: (-> Nat Estimator)
- (function (_ amount-of-cases offset)
+ (function (_ amount_of_cases offset)
(|> ($_ n.+
- (///unsigned.value ..opcode-size)
- (switch-padding (///unsigned.value (//address.value offset)))
- (///unsigned.value ..big-jump-size)
- (///unsigned.value ..integer-size)
- (n.* amount-of-cases case-size))
+ (///unsigned.value ..opcode_size)
+ (switch_padding (///unsigned.value (//address.value offset)))
+ (///unsigned.value ..big_jump_size)
+ (///unsigned.value ..integer_size)
+ (n.* amount_of_cases case_size))
///unsigned.u2
try.assume)))]
[estimator
(function (_ default cases)
- (let [amount-of-cases (list.size cases)
- estimator (estimator amount-of-cases)]
+ (let [amount_of_cases (list.size cases)
+ estimator (estimator amount_of_cases)]
(function (_ [size mutation])
- (let [padding (switch-padding size)
- lookupswitch-size (try.assume
+ (let [padding (switch_padding size)
+ lookupswitch_size (try.assume
(do {! try.monad}
[size (///unsigned.u2 size)]
(\ ! map (|>> estimator ///unsigned.value)
(//address.move size //address.start))))
- lookupswitch-mutation (: Mutation
+ lookupswitch_mutation (: Mutation
(function (_ [offset binary])
- [(n.+ lookupswitch-size offset)
+ [(n.+ lookupswitch_size offset)
(try.assume
(do {! try.monad}
[_ (binary.write/8 offset (hex "AB") binary)
- #let [offset (n.+ (///unsigned.value ..opcode-size) offset)]
+ #let [offset (n.+ (///unsigned.value ..opcode_size) offset)]
_ (case padding
3 (do !
[_ (binary.write/8 offset 0 binary)]
@@ -685,9 +685,9 @@
_ (wrap binary))
#let [offset (n.+ padding offset)]
_ (binary.write/32 offset (///signed.value default) binary)
- #let [offset (n.+ (///unsigned.value ..big-jump-size) offset)]
- _ (binary.write/32 offset amount-of-cases binary)]
- (loop [offset (n.+ (///unsigned.value ..integer-size) offset)
+ #let [offset (n.+ (///unsigned.value ..big_jump_size) offset)]
+ _ (binary.write/32 offset amount_of_cases binary)]
+ (loop [offset (n.+ (///unsigned.value ..integer_size) offset)
cases cases]
(case cases
#.Nil
@@ -696,12 +696,12 @@
(#.Cons [value jump] tail)
(do !
[_ (binary.write/32 offset (///signed.value value) binary)
- _ (binary.write/32 (n.+ (///unsigned.value ..integer-size) offset) (///signed.value jump) binary)]
- (recur (n.+ case-size offset)
+ _ (binary.write/32 (n.+ (///unsigned.value ..integer_size) offset) (///signed.value jump) binary)]
+ (recur (n.+ case_size offset)
tail))))))]))]
- [(n.+ lookupswitch-size
+ [(n.+ lookupswitch_size
size)
- (|>> mutation lookupswitch-mutation)]))))]))
+ (|>> mutation lookupswitch_mutation)]))))]))
(structure: #export monoid
(Monoid Instruction)