• Home
  • Line#
  • Scopes#
  • Navigate#
  • Raw
  • Download
1# Copyright (c) 2024-2025 Huawei Device Co., Ltd.
2# Licensed under the Apache License, Version 2.0 (the "License");
3# you may not use this file except in compliance with the License.
4# You may obtain a copy of the License at
5#
6# http://www.apache.org/licenses/LICENSE-2.0
7#
8# Unless required by applicable law or agreed to in writing, software
9# distributed under the License is distributed on an "AS IS" BASIS,
10# WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
11# See the License for the specific language governing permissions and
12# limitations under the License.
13
14Instruction.class_eval do
15  def src_acc_kind
16    op = acc_and_operands.select { |op| op.acc? && op.src? }.first
17    raise "There is no src acc for #{mnemonic}" unless op
18    data_kind_helper(op)
19  end
20
21  def dst_acc_kind
22    op = acc_and_operands.select { |op| op.acc? && op.dst? }.first
23    raise "There is no dst acc for #{mnemonic}" unless op
24    data_kind_helper(op)
25  end
26
27  private
28  # return one of 32, 64, 'ref'
29  def data_kind_helper(op)
30    m = /[fiub](?<size>\d+)/.match(op.type)
31    if m
32      size = m[:size].to_i
33      if size == 64
34        return 64
35      else
36        return 32
37      end
38    end
39    return 'ref' if op.type == 'ref'
40    raise "Unexpected operand type #{op.type} in data_kind_helper"
41  end
42end
43
44def instruction_hash
45  unless defined? @instruction_hash
46    @instruction_hash = Hash.new { |_, key| raise "No instruction with '#{key}' mnemonic" }
47    Panda.instructions.each { |insn| @instruction_hash[insn.mnemonic] = insn }
48  end
49  @instruction_hash
50end
51
52# Classes for bytecode description
53Visitor = Struct.new(:ir_op, :cpp, :switch)
54Switch = Struct.new(:expr, :cases) do
55  def encode
56    res = "switch (#{expr}) {\n"
57    cases.each do |c|
58      res << c.encode
59    end
60    res << "default:
61std::cerr << \"Codegen for \" << compiler::GetOpcodeString(inst->GetOpcode()) << \" failed\\n\";
62enc->success_ = false;
63}"
64    res
65  end
66
67  def check_width
68    res = "switch (#{expr}) {\n"
69    cases.each do |c|
70      res << c.check_width
71    end
72    res << "default:
73    std::cerr << \"CheckWidth for \" << compiler::GetOpcodeString(inst->GetOpcode()) << \" failed\\n\";
74re->success_ = false;
75}"
76    res
77  end
78end
79
80Case = Struct.new(:types, :node) do
81  def proxy(method)
82    res = types.map { |type| "case #{type}:" }.join("\n")
83    res << " {\n"
84    res << node.send(method)
85    res << "break;\n}\n"
86    res
87  end
88
89  def encode
90    proxy(:encode)
91  end
92
93  def check_width
94    proxy(:check_width)
95  end
96end
97
98Leaf = Struct.new(:instruction, :args) do
99  def encode
100    res = ""
101    args_str = args.join(",\n")
102    if instruction.acc_read?
103      res << do_lda(instruction)
104      res << "\n"
105    end
106    res << "enc->result_.emplace_back(pandasm::Create_#{instruction.asm_token}(\n"
107    res << args_str
108    res << "\n));\n"
109    if instruction.acc_write?
110      res << do_sta(instruction)
111      res << "\n"
112    end
113    res
114  end
115
116  def check_width
117    reg = instruction.operands.select(&:reg?).first
118    if reg
119      "re->Check#{reg.width}Width(inst);\n"
120    else
121      "return;\n"
122    end
123  end
124end
125
126If = Struct.new(:condition, :true_expr, :false_expr) do
127  def proxy(method)
128    res = "if (#{condition}) {\n"
129    res << true_expr.send(method)
130    res << "} else {\n"
131    res << false_expr.send(method)
132    res << "}\n"
133    res
134  end
135
136  def encode
137    proxy(:encode)
138  end
139
140  def check_width
141    proxy(:check_width)
142  end
143end
144
145Empty = Struct.new(:dummy) do
146  def encode; end
147  def check_width; end
148end
149
150
151def visit(ir_op, cpp = nil)
152  @table ||= []
153  @table << Visitor.new(ir_op, cpp, yield)
154end
155
156def visitors
157  @table
158end
159
160def switch(expr, cases)
161  Switch.new(expr, cases)
162end
163
164def plain(opcode, *args)
165  Leaf.new(instruction_hash[opcode], args.to_a)
166end
167
168def empty
169  Empty.new
170end
171
172def if_(condition, true_expr, false_expr)
173  If.new(condition, true_expr, false_expr)
174end
175
176def prefixed_case(prefix, types, node)
177  types = types.map { |t| "#{prefix}#{t}" }
178  Case.new(types, node)
179end
180
181def case_(types, opcode, *args)
182  prefixed_case("compiler::DataType::", types, plain(opcode, *args))
183end
184
185def cc_case(types, opcode, *args)
186  prefixed_case("compiler::CC_", types, plain(opcode, *args))
187end
188
189def case_switch(types, condition, inner_cases)
190  prefixed_case("compiler::DataType::", types, switch(condition, inner_cases))
191end
192
193def case_value(value, node)
194  Case.new([value], node)
195end
196
197def case_true(opcode, *args)
198  case_value('1', plain(opcode, *args))
199end
200
201def case_true_node(node)
202  case_value('1', node)
203end
204
205def case_false(opcode, *args)
206  case_value('0', plain(opcode, *args))
207end
208
209def case_false_node(node)
210  case_value('0', node)
211end
212
213def generate_arith_op(op)
214  switch("static_cast<int>(#{dst_r} != #{r(0)} && #{dst_r} != #{r(1)})",
215    [case_true(op, r(0), r(1)),
216     case_false_node(is_commutative?(op) ?
217      if_("#{dst_r} == #{r(0)}",
218        plain("#{op}v", r(0), r(1)),
219        plain("#{op}v", r(1), r(0))) :
220      plain(op, r(0), r(1))
221     )
222    ]
223  )
224end
225
226# Type/cc cases for instruction selection
227def i32_types
228  @i32_types ||= %w[BOOL UINT8 INT8 UINT16 INT16 UINT32 INT32]
229end
230
231def i64_types
232  @i64_types ||= %w[INT64 UINT64]
233end
234
235def f32_types
236  @f32_types ||= %w[FLOAT32]
237end
238
239def f64_types
240  @f64_types ||= %w[FLOAT64]
241end
242
243def b64_types
244  @b64_types ||= i64_types + f64_types
245end
246
247def b32_types
248  @b32_types ||= i32_types + f32_types
249end
250
251def void_types
252  @void_types ||= %w[VOID]
253end
254
255def cc_cases
256  @cc_cases ||= %w[EQ NE LT LE GT GE]
257end
258
259# Switch condition printers
260def type
261  'inst->GetType()'
262end
263
264def src_type
265  'inst->GetInputType(0)'
266end
267
268# we could use switch on 'bool' type for if-else purposes, but that hurts clang_tidy
269def is_acc?(reg)
270  "#{reg} == compiler::GetAccReg()"
271end
272
273def is_not_acc?(reg)
274  "#{reg} != compiler::GetAccReg()"
275end
276
277def is_compact?(reg)
278  "#{reg} < NUM_COMPACTLY_ENCODED_REGS"
279end
280
281def is_not_compact?(reg)
282  "#{reg} >= NUM_COMPACTLY_ENCODED_REGS"
283end
284
285def is_fcmpg?
286  'static_cast<int>(inst->IsFcmpg())'
287end
288
289def is_inci?
290  "static_cast<int>(CanConvertToIncI(inst))"
291end
292
293def is_commutative?(op)
294  ["add", "mul", "and", "or", "xor"].include?(op)
295end
296
297def is_arith_iv?
298  "#{is_not_acc?(r(0))} && #{is_not_acc?(dst_r)} && (#{is_compact?(r(0))} || #{is_compact?(dst_r)})"
299end
300
301def cast_to_int(val)
302  "static_cast<int>(#{val})"
303end
304
305# Operand printers
306def dst_r
307  'inst->GetDstReg()'
308end
309
310def r(num)
311  "inst->GetSrcReg(#{num})"
312end
313
314def imm
315  'static_cast<int32_t>(inst->GetImm() & 0xffffffff)'
316end
317
318def label
319  'LabelName(inst->GetBasicBlock()->GetTrueSuccessor()->GetId())'
320end
321
322def string_id
323  'enc->irInterface_->GetStringIdByOffset(inst->GetImm(0))'
324end
325
326def literalarray_id
327  'enc->irInterface_->GetLiteralArrayIdByOffset(inst->GetImm(0))'
328end
329
330def type_id(idx)
331  "enc->irInterface_->GetTypeIdByOffset(inst->GetImm(#{idx}))"
332end
333
334def field_id
335  'enc->irInterface_->GetFieldIdByOffset(inst->GetTypeId())'
336end
337
338# Lda/Sta printers
339def do_lda(instruction)
340  lda = case instruction.src_acc_kind
341        when 32
342          instruction_hash['lda']
343        when 64
344          instruction_hash['lda.64']
345        when 'ref'
346          instruction_hash['lda.obj']
347        end
348  reg_num = 0
349  "if (inst->GetSrcReg(#{reg_num}) != compiler::GetAccReg()) {
350    enc->result_.emplace_back(pandasm::Create_#{lda.asm_token}(inst->GetSrcReg(#{reg_num})));
351  }"
352end
353
354def do_sta(instruction)
355  sta = case instruction.dst_acc_kind
356        when 32
357          instruction_hash['sta']
358        when 64
359          instruction_hash['sta.64']
360        when 'ref'
361          instruction_hash['sta.obj']
362        end
363  "if (inst->GetDstReg() != compiler::GetAccReg()) {
364    enc->result_.emplace_back(pandasm::Create_#{sta.asm_token}(inst->GetDstReg()));
365  }"
366end
367
368# Misc printers
369def visitor_sig(op_name, with_class = true)
370  "void #{'CodeGenStatic::' if with_class}Visit#{op_name}(GraphVisitor* v, Inst* instBase)"
371end
372
373# Bytecode description itself
374
375# Wrap all `insn` declaration in a function to call from template
376# (because Panda::instructions is initialized only in templates)
377def call_me_from_template
378  %w[And Xor Or Shl Shr AShr].each do |op|
379    visit(op) do
380      op = op.downcase
381      switch(type,
382        [case_switch(i32_types, cast_to_int(is_not_compact?(r(0))),
383          [case_true_node(if_(is_acc?(dst_r),
384            plain("#{op}2", r(1)),
385            plain("#{op}2v", dst_r, r(1)))),
386           case_false_node(if_("#{is_compact?(dst_r)}",
387            generate_arith_op(op),
388            plain(op, r(0), r(1))))]),
389         case_switch(i64_types, cast_to_int(is_acc?(dst_r)),
390          [case_true("#{op}2.64", r(1)),
391           case_false("#{op}2v.64", dst_r, r(1))])]
392      )
393    end
394  end
395
396  %w[add sub mul div mod].each do |op|
397    visit(op.capitalize) do
398      switch(type,
399        [case_switch(i32_types, cast_to_int(is_not_compact?(r(0))),
400          [case_true_node(if_(is_acc?(dst_r),
401            plain("#{op}2", r(1)),
402            plain("#{op}2v", dst_r, r(1)))),
403           case_false_node(if_("#{is_compact?(dst_r)}",
404            generate_arith_op(op),
405            plain(op, r(0), r(1))))]),
406         case_switch(i64_types, cast_to_int(is_acc?(dst_r)),
407          [case_true("#{op}2.64", r(1)),
408           case_false("#{op}2v.64", dst_r, r(1))]),
409         case_switch(f32_types, cast_to_int(is_acc?(dst_r)),
410          [case_true("f#{op}2", r(1)),
411           case_false("f#{op}2v", dst_r, r(1))]),
412         case_switch(f64_types, cast_to_int(is_acc?(dst_r)),
413          [case_true("f#{op}2.64", r(1)),
414           case_false("f#{op}2v.64", dst_r, r(1))])]
415      )
416    end
417  end
418
419  visit('AddI') do
420    switch(type,
421      [case_switch(i32_types, is_inci?,
422         [case_true('inci', r(0), imm),
423          case_false_node(if_(is_arith_iv?,
424            plain("addiv", dst_r, r(0), imm),
425            plain("addi", imm)))])]
426    )
427  end
428
429  visit('SubI') do
430    switch(type,
431      [case_switch(i32_types, is_inci?,
432         [case_true('inci', r(0), "-(#{imm})"),
433          case_false_node(if_(is_arith_iv?,
434            plain("subiv", dst_r, r(0), imm),
435            plain("subi", imm)))])]
436    )
437  end
438
439  visit('Not') do
440    switch(type,
441      [case_(i32_types, 'not'),
442       case_(i64_types, 'not.64')]
443    )
444  end
445
446  visit('Neg') do
447    switch(type,
448      [case_(i32_types, 'neg'),
449       case_(i64_types, 'neg.64'),
450       case_(f32_types, 'fneg'),
451       case_(f64_types, 'fneg.64')]
452    )
453  end
454
455  visit('Cmp') do
456    switch('inst->GetOperandsType()',
457      [case_(%w[UINT8 UINT16 UINT32], 'ucmp', r(1)),
458       case_(%w[INT64], 'cmp.64', r(1)),
459       case_(%w[UINT64], 'ucmp.64', r(1)),
460       case_switch(['FLOAT32'], is_fcmpg?,
461                     [case_true('fcmpg', r(1)),
462                      case_false('fcmpl', r(1))]),
463       case_switch(['FLOAT64'], is_fcmpg?,
464                     [case_true('fcmpg.64', r(1)),
465                      case_false('fcmpl.64', r(1))])]
466    )
467  end
468
469  visit('ReturnVoid') do
470    plain('return.void')
471  end
472
473  visit('ThrowIntrinsic') do
474    plain('throw', r(0))
475  end
476
477  visit('NullPtr') do
478    switch(cast_to_int(is_acc?(dst_r)),
479      [case_true('lda.null'),
480       case_false('mov.null', dst_r)]
481    )
482  end
483
484  visit('LoadConstArrayIntrinsic') do
485    plain('lda.const', dst_r, literalarray_id)
486  end
487
488  visit('LoadStringIntrinsic') do
489    plain('lda.str', string_id)
490  end
491
492  visit('NewArrayIntrinsic') do
493    plain('newarr', dst_r, r(0), type_id(0))
494  end
495
496  visit('LenArray') do
497    plain('lenarr', r(0))
498  end
499
500  visit('LoadArrayIntrinsic') do
501    switch(type,
502      [case_(['INT8'], 'ldarr.8', r(1)),
503       case_(['UINT8'], 'ldarru.16', r(1)),
504       case_(['INT16'], 'ldarr.16', r(1)),
505       case_(['UINT16'], 'ldarru.16', r(1)),
506       case_(['INT32', 'UINT32'], 'ldarr', r(1)),
507       case_(['INT64', 'UINT64'], 'ldarr.64', r(1)),
508       case_(['REFERENCE'], 'ldarr.obj', r(1)),
509       case_(['FLOAT32'], 'fldarr.32', r(1)),
510       case_(['FLOAT64'], 'fldarr.64', r(1))]
511    )
512  end
513
514  visit('StoreArrayIntrinsic') do
515    switch(type,
516      [case_(['INT8', 'UINT8'], 'starr.8', r(1), r(2)),
517       case_(['INT16', 'UINT16'], 'starr.16', r(1), r(2)),
518       case_(['INT32', 'UINT32'], 'starr', r(1), r(2)),
519       case_(['INT64', 'UINT64'], 'starr.64', r(1), r(2)),
520       case_(['REFERENCE'], 'starr.obj', r(1), r(2)),
521       case_(['FLOAT32'], 'fstarr.32', r(1), r(2)),
522       case_(['FLOAT64'], 'fstarr.64', r(1), r(2))]
523    )
524  end
525
526  visit('CheckCastIntrinsic') do
527    plain('checkcast', type_id(0))
528  end
529
530  visit('IsInstanceIntrinsic') do
531    plain('isinstance', type_id(0))
532  end
533
534  visit('NewObjectIntrinsic') do
535    plain('newobj', dst_r, type_id(0))
536  end
537
538  visit('IsNullValueIntrinsic') do
539    plain('ets.isnullvalue')
540  end
541
542  # Empty visitors for IR instructions we want to ignore
543  # (Add missing IRs on demand)
544  %w[NullCheck BoundsCheck ZeroCheck NegativeCheck SafePoint
545     InitClass SaveStateDeoptimize RefTypeCheck Phi
546     Try SaveState LoadClass LoadAndInitClass Parameter LoadRuntimeClass].each do |op|
547    visit(op) do
548      empty
549    end
550  end
551
552  %w[MulI DivI ModI ShlI ShrI AShrI AndI OrI XorI].each do |op|
553    visit(op) do
554      switch(type,
555         [case_switch(i32_types, cast_to_int(is_arith_iv?),
556          [case_true("#{op.downcase}v", dst_r, r(0), imm),
557           case_false("#{op.downcase}", imm)])]
558      )
559    end
560  end
561end
562