Skip to content

Commit 0679b2f

Browse files
committed
More cleanup for C++ conversion
1 parent 5dd834c commit 0679b2f

File tree

16 files changed

+167
-169
lines changed

16 files changed

+167
-169
lines changed

tools/flang1/flang1exe/symacc.h

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -181,7 +181,7 @@ typedef struct {
181181
const char *ocnames[OC_MAX + 1];
182182
const char *scnames[SC_MAX + 1];
183183
const char *tynames[TY_MAX + 1];
184-
int i0, i1;
184+
SPTR i0, i1;
185185
int k0, k1;
186186
SPTR flt0, dbl0, quad0;
187187
SPTR fltm0, dblm0, quadm0; /* floating point minus 0 */

tools/flang2/flang2exe/cgmain.cpp

Lines changed: 52 additions & 57 deletions
Original file line numberDiff line numberDiff line change
@@ -311,7 +311,7 @@ static ComplexResultList_t complexResultList;
311311
/* --- static prototypes (exported prototypes belong in cgllvm.h) --- */
312312

313313
static void write_verbose_type(LL_Type *);
314-
static void gen_store_instr(int, TMPS *, LL_Type *);
314+
static void gen_store_instr(SPTR, TMPS *, LL_Type *);
315315
static void fma_rewrite(INSTR_LIST *isns);
316316
static void undo_recip_div(INSTR_LIST *isns);
317317
static char *set_local_sname(int sptr, const char *name);
@@ -325,7 +325,7 @@ static const char *get_atomicrmw_opname(LL_InstrListFlags);
325325
static const char *get_atomic_memory_order_name(int);
326326
static void insert_llvm_memcpy(int, int, OPERAND *, OPERAND *, int, int, int);
327327
static void insert_llvm_memset(int, int, OPERAND *, int, int, int, int);
328-
static int get_call_sptr(int);
328+
static SPTR get_call_sptr(int);
329329
static LL_Type *make_function_type_from_args(LL_Type *return_type,
330330
OPERAND *first_arg_op,
331331
bool is_varargs);
@@ -368,15 +368,14 @@ static void set_csed_operand(OPERAND **, OPERAND *);
368368
static OPERAND **get_csed_operand(int ilix);
369369
static void build_csed_list(int);
370370
static OPERAND *gen_base_addr_operand(int, LL_Type *);
371-
static OPERAND *gen_comp_operand(OPERAND *, ILI_OP, int, int, int, int, int);
372371
static OPERAND *gen_optext_comp_operand(OPERAND *, ILI_OP, int, int, int, int,
373-
int, int, int);
372+
LL_InstrName, int, int);
374373
static OPERAND *gen_sptr(SPTR sptr);
375374
static OPERAND *gen_load(OPERAND *addr, LL_Type *type, LL_InstrListFlags flags);
376375
static void make_store(OPERAND *, OPERAND *, LL_InstrListFlags);
377376
static OPERAND *make_load(int, OPERAND *, LL_Type *, MSZ, unsigned flags);
378377
static OPERAND *convert_operand(OPERAND *convert_op, LL_Type *rslt_type,
379-
int convert_instruction);
378+
LL_InstrName convert_instruction);
380379
static OPERAND *convert_float_size(OPERAND *, LL_Type *);
381380
static int follow_sptr_hashlk(SPTR sptr);
382381
static DTYPE follow_ptr_dtype(DTYPE);
@@ -839,7 +838,7 @@ processOutlinedByConcur(int bih)
839838
++bconcur;
840839

841840
GBL_CURRFUNC = ILI_SymOPND(bili, 1);
842-
display = (SPTR)llvmAddConcurEntryBlk(bbih); // ???
841+
display = llvmAddConcurEntryBlk(bbih);
843842

844843
/* if IL_ECONCUR is always be the first - we can just check the first
845844
* ilt */
@@ -1076,7 +1075,7 @@ store_for_homing(int rIli, int nme)
10761075
static void
10771076
add_external_function_declaration(const char *key, EXFUNC_LIST *exfunc)
10781077
{
1079-
const SPTR sptr = (SPTR)exfunc->sptr; // ???
1078+
const SPTR sptr = exfunc->sptr;
10801079

10811080
if (sptr) {
10821081
LL_ABI_Info *abi =
@@ -2640,7 +2639,7 @@ write_instructions(LL_Module *module)
26402639
switch (i_name) {
26412640
case I_NONE: /* should be a label */
26422641
forceLabel = false;
2643-
sptr = (SPTR)instrs->operands->val.sptr; // ???
2642+
sptr = instrs->operands->val.sptr;
26442643
if (instrs->prev == NULL && sptr == 0) {
26452644
/* entry label we just ignore it*/
26462645
break;
@@ -3221,7 +3220,7 @@ gen_insert_value(OPERAND *aggr, OPERAND *elem, unsigned index)
32213220
}
32223221

32233222
static void
3224-
gen_store_instr(int sptr_lhs, TMPS *tmp, LL_Type *tmp_type)
3223+
gen_store_instr(SPTR sptr_lhs, TMPS *tmp, LL_Type *tmp_type)
32253224
{
32263225
INSTR_LIST *Curr_Instr;
32273226
OPERAND *addr = make_operand();
@@ -3576,7 +3575,7 @@ make_stmt(STMT_Type stmt_type, int ilix, bool deletable, SPTR next_bih_label,
35763575
case STMT_CALL:
35773576
if (getTempMap(ilix))
35783577
return;
3579-
sym = pd_sym = (SPTR)get_call_sptr(ilix); // ???
3578+
sym = pd_sym = get_call_sptr(ilix);
35803579

35813580
if (sym != pd_sym && STYPEG(pd_sym) == ST_PD) {
35823581
switch (PDNUMG(pd_sym)) {
@@ -4995,7 +4994,7 @@ insertLLVMDbgValue(OPERAND *load, LL_MDRef mdnode, SPTR sptr, LL_Type *type)
49954994
static void
49964995
consLoadDebug(OPERAND *ld, OPERAND *addr, LL_Type *type)
49974996
{
4998-
SPTR sptr = (SPTR)addr->val.sptr; // ???
4997+
SPTR sptr = addr->val.sptr;
49994998
if (sptr && need_debug_info(sptr)) {
50004999
LL_DebugInfo *di = cpu_llvm_module->debug_info;
50015000
int fin = BIH_FINDEX(gbl.entbih);
@@ -5449,7 +5448,9 @@ maybe_generate_fma(int ilix, INSTR_LIST *insn)
54495448
{
54505449
int lhs_ili = ILI_OPND(ilix, 1);
54515450
int rhs_ili = ILI_OPND(ilix, 2);
5452-
int matches, opc, isSinglePrec;
5451+
int matches;
5452+
ILI_OP opc;
5453+
int isSinglePrec;
54535454
const char *intrinsicName;
54545455
OPERAND *l_l, *l_r, *l, *r, *binops, *fmaop;
54555456
LL_Type *llTy;
@@ -5509,8 +5510,7 @@ maybe_generate_fma(int ilix, INSTR_LIST *insn)
55095510
#endif
55105511
#else /* not Power/LLVM or X86-64/LLVM */
55115512
/* use the documented LLVM intrinsic: '@llvm.fma.*' */
5512-
fused_multiply_add_canonical_form(insn, matches, (ILI_OP)opc, // ???
5513-
&l, &r, &lhs_ili, &rhs_ili);
5513+
fused_multiply_add_canonical_form(insn, matches, opc, &l, &r, &lhs_ili, &rhs_ili);
55145514
/* llvm.fma ::= madd(l.l * l.r + r), assemble args in the LLVM order */
55155515
l_l = l->tmps->info.idef->operands;
55165516
l_r = l_l->next;
@@ -6003,7 +6003,7 @@ convert_int_size(int ilix, OPERAND *convert_op, LL_Type *rslt_type)
60036003

60046004
static OPERAND *
60056005
convert_operand(OPERAND *convert_op, LL_Type *rslt_type,
6006-
int convert_instruction)
6006+
LL_InstrName convert_instruction)
60076007
{
60086008
LL_Type *ty, *ll_type;
60096009
int size;
@@ -6019,8 +6019,7 @@ convert_operand(OPERAND *convert_op, LL_Type *rslt_type,
60196019
new_tmps = make_tmps();
60206020
ll_type = rslt_type;
60216021
op_tmp = make_tmp_op(ll_type, new_tmps);
6022-
Curr_Instr = gen_instr((LL_InstrName)convert_instruction, // ???
6023-
new_tmps, ll_type, convert_op);
6022+
Curr_Instr = gen_instr(convert_instruction, new_tmps, ll_type, convert_op);
60246023
ad_instr(0, Curr_Instr);
60256024
DBGTRACEOUT1(" returns operand %p", op_tmp)
60266025
return op_tmp;
@@ -6352,28 +6351,24 @@ make_load(int ilix, OPERAND *load_op, LL_Type *rslt_type, MSZ msz,
63526351
return cse_op ? cse_op : operand;
63536352
}
63546353

6355-
/**
6356-
\brief Find the (virtual) function pointer in a JSRA call
6357-
\param ilix the first argument of the \c IL_JSRA
6358-
*/
6359-
int
6354+
SPTR
63606355
find_pointer_to_function(int ilix)
63616356
{
63626357
int addr, addr_acon_ptr;
6363-
int sptr = 0;
6358+
SPTR sptr = SPTR_NULL;
63646359

63656360
addr = ILI_OPND(ilix, 1);
63666361
while (ILI_OPC(addr) == IL_LDA) {
63676362
if (ILI_OPC(ILI_OPND(addr, 1)) == IL_ACON) {
63686363
addr_acon_ptr = ILI_OPND(addr, 1);
6369-
sptr = ILI_OPND(addr_acon_ptr, 1);
6364+
sptr = ILI_SymOPND(addr_acon_ptr, 1);
63706365
if (CONVAL1G(sptr)) {
6371-
sptr = CONVAL1G(sptr);
6366+
sptr = SymConval1(sptr);
63726367
}
63736368
} else if (ILI_OPC(ILI_OPND(addr, 1)) == IL_AADD) {
63746369
if (ILI_OPC(ILI_OPND(ILI_OPND(addr, 1), 1)) == IL_ACON) {
63756370
addr_acon_ptr = ILI_OPND(ILI_OPND(addr, 1), 1);
6376-
sptr = CONVAL1G(ILI_OPND(addr_acon_ptr, 1));
6371+
sptr = SymConval1(ILI_SymOPND(addr_acon_ptr, 1));
63776372
}
63786373
addr = ILI_OPND(addr, 1);
63796374
}
@@ -6383,42 +6378,44 @@ find_pointer_to_function(int ilix)
63836378
return sptr;
63846379
}
63856380

6386-
static int
6381+
static SPTR
63876382
get_call_sptr(int ilix)
63886383
{
6389-
int sptr, addr, addr_acon_ptr;
6384+
SPTR sptr;
6385+
int addr;
6386+
SPTR addr_acon_ptr;
63906387
ILI_OP opc = ILI_OPC(ilix);
63916388

63926389
DBGTRACEIN2(" called with ilix %d (opc=%s)", ilix, IL_NAME(opc))
63936390

63946391
switch (opc) {
63956392
case IL_JSR:
63966393
case IL_QJSR:
6397-
sptr = ILI_OPND(ilix, 1);
6394+
sptr = ILI_SymOPND(ilix, 1);
63986395
break;
63996396
case IL_JSRA:
64006397
addr = ILI_OPND(ilix, 1);
64016398
if (ILI_OPC(addr) == IL_LDA) {
64026399
sptr = find_pointer_to_function(ilix);
64036400
} else if (ILI_OPC(addr) == IL_ACON) {
6404-
addr_acon_ptr = ILI_OPND(addr, 1);
6401+
addr_acon_ptr = ILI_SymOPND(addr, 1);
64056402
if (!CONVAL1G(addr_acon_ptr))
64066403
sptr = addr_acon_ptr;
64076404
else
6408-
sptr = CONVAL1G(addr_acon_ptr);
6405+
sptr = SymConval1(addr_acon_ptr);
64096406
} else if (ILI_OPC(addr) == IL_DFRAR) {
6410-
addr_acon_ptr = ILI_OPND(addr, 1);
6407+
const int addr_acon_ptr = ILI_OPND(addr, 1);
64116408
if (ILI_OPC(addr_acon_ptr) == IL_JSR)
64126409
/* this sptr is the called function, but the DFRAR is
64136410
* returning a function pointer from that sptr, and that
64146411
* returned indirect function sptr is unknown.
64156412
*/
64166413
/* sptr = ILI_OPND(addr_acon_ptr,1); */
6417-
sptr = 0;
6414+
sptr = SPTR_NULL;
64186415
else if (ILI_OPC(addr_acon_ptr) == IL_JSRA)
64196416
return get_call_sptr(addr_acon_ptr);
64206417
else
6421-
assert(0, "get_call_sptr(): indirect call via DFRAR not JSR/JSRA",
6418+
assert(false, "get_call_sptr(): indirect call via DFRAR not JSR/JSRA",
64226419
ILI_OPC(addr_acon_ptr), ERR_Fatal);
64236420
} else {
64246421
assert(false, "get_call_sptr(): indirect call not via LDA/ACON",
@@ -6427,7 +6424,8 @@ get_call_sptr(int ilix)
64276424
break;
64286425
default:
64296426
DBGTRACE2("###get_call_sptr unknown opc %d (%s)", opc, IL_NAME(opc))
6430-
assert(0, "get_call_sptr(): unknown opc", opc, ERR_Fatal);
6427+
assert(false, "get_call_sptr(): unknown opc", opc, ERR_Fatal);
6428+
break;
64316429
}
64326430

64336431
DBGTRACEOUT1(" returns %d", sptr)
@@ -6899,7 +6897,7 @@ gen_call_expr(int ilix, DTYPE ret_dtype, INSTR_LIST *call_instr, int call_sptr)
68996897
op = label_op;
69006898
label_op = make_operand();
69016899
label_op->ot_type = OT_LABEL;
6902-
label_op->val.sptr = throw_label;
6900+
label_op->val.cc = throw_label;
69036901
op->next = label_op;
69046902
}
69056903

@@ -7197,7 +7195,7 @@ gen_copy_operand(OPERAND *opnd)
71977195
* 'dtype' should either be DT_CMPLX or DT_DCMPLX.
71987196
*/
71997197
static OPERAND *
7200-
gen_cmplx_math(int ilix, DTYPE dtype, int itype)
7198+
gen_cmplx_math(int ilix, DTYPE dtype, LL_InstrName itype)
72017199
{
72027200
OPERAND *r1, *r2, *i1, *i2, *rmath, *imath, *res, *c1, *c2, *cse1, *cse2;
72037201
LL_Type *cmplx_type, *cmpnt_type;
@@ -7225,10 +7223,8 @@ gen_cmplx_math(int ilix, DTYPE dtype, int itype)
72257223
r1->next = r2;
72267224
i1->next = i2;
72277225

7228-
rmath = ad_csed_instr((LL_InstrName)itype, // ???
7229-
0, cmpnt_type, r1, InstrListFlagsNull, true);
7230-
imath = ad_csed_instr((LL_InstrName)itype, 0, cmpnt_type, i1,
7231-
InstrListFlagsNull, true);
7226+
rmath = ad_csed_instr(itype, 0, cmpnt_type, r1, InstrListFlagsNull, true);
7227+
imath = ad_csed_instr(itype, 0, cmpnt_type, i1, InstrListFlagsNull, true);
72327228

72337229
/* Build a temp complex in registers and store the mathed values in that */
72347230
res = make_undef_op(cmplx_type);
@@ -7564,6 +7560,14 @@ complex_result_type(ILI_OP opc)
75647560
}
75657561
}
75667562

7563+
INLINE static OPERAND *
7564+
gen_comp_operand(OPERAND *operand, ILI_OP opc, int lhs_ili, int rhs_ili,
7565+
int cc_ili, int cc_type, LL_InstrName itype)
7566+
{
7567+
return gen_optext_comp_operand(operand, opc, lhs_ili, rhs_ili, cc_ili,
7568+
cc_type, itype, 1, 0);
7569+
}
7570+
75677571
OPERAND *
75687572
gen_llvm_expr(int ilix, LL_Type *expected_type)
75697573
{
@@ -7683,7 +7687,7 @@ gen_llvm_expr(int ilix, LL_Type *expected_type)
76837687
} else {
76847688
operand = gen_address_operand(ld_ili, nme_ili, true, NULL, MSZ_ILI_OPND(ilix, 3));
76857689
}
7686-
sptr = (SPTR)basesym_of(nme_ili); // ???
7690+
sptr = basesym_of(nme_ili);
76877691
if ((operand->ll_type->data_type == LL_PTR) ||
76887692
(operand->ll_type->data_type == LL_ARRAY)) {
76897693
DTYPE dtype = DTYPEG(sptr);
@@ -9579,21 +9583,13 @@ vect_llvm_intrinsic_name(int ilix)
95799583
return retc;
95809584
} /* vect_llvm_intrinsic_name */
95819585

9582-
static OPERAND *
9583-
gen_comp_operand(OPERAND *operand, ILI_OP opc, int lhs_ili, int rhs_ili,
9584-
int cc_ili, int cc_type, int itype)
9585-
{
9586-
return gen_optext_comp_operand(operand, opc, lhs_ili, rhs_ili, cc_ili,
9587-
cc_type, itype, 1, 0);
9588-
}
9589-
95909586
/**
95919587
\brief Generate comparison operand. Optionally extending the result.
95929588
\param optext if this is false, do not extend the result to 32 bits.
95939589
*/
95949590
static OPERAND *
95959591
gen_optext_comp_operand(OPERAND *operand, ILI_OP opc, int lhs_ili, int rhs_ili,
9596-
int cc_ili, int cc_type, int itype, int optext,
9592+
int cc_ili, int cc_type, LL_InstrName itype, int optext,
95979593
int ilix)
95989594
{
95999595
LL_Type *expected_type, *op_type;
@@ -9614,8 +9610,7 @@ gen_optext_comp_operand(OPERAND *operand, ILI_OP opc, int lhs_ili, int rhs_ili,
96149610
}
96159611

96169612
/* now make the new binary expression */
9617-
Curr_Instr = gen_instr((LL_InstrName)itype, // ???
9618-
operand->tmps, operand->ll_type, make_operand());
9613+
Curr_Instr = gen_instr(itype, operand->tmps, operand->ll_type, make_operand());
96199614
Curr_Instr->operands->ot_type = OT_CC;
96209615
Curr_Instr->operands->val.cc = convert_to_llvm_cc(cc_ili, cc_type);
96219616
if (opc == IL_VCMPNEQ)
@@ -9695,7 +9690,7 @@ gen_switch(int ilix)
96959690
OPERAND *label = make_target_op(switch_base[sw_elt].clabel);
96969691
OPERAND *value;
96979692
if (is_64bit)
9698-
value = make_constsptr_op(switch_base[sw_elt].val);
9693+
value = make_constsptr_op((SPTR)switch_base[sw_elt].val); // ???
96999694
else
97009695
value = make_constval32_op(switch_base[sw_elt].val);
97019696
/* Remaining switch operands are (value, target) pairs. */
@@ -10437,7 +10432,7 @@ is_blockaddr_store(int ilix, int rhs, int lhs)
1043710432
SPTR gl_sptr;
1043810433
int ili, newnme;
1043910434
int nme = ILI_OPND(ilix, 3);
10440-
int sptr = basesym_of(nme);
10435+
SPTR sptr = basesym_of(nme);
1044110436
SPTR label = SymConval1(ILI_SymOPND(rhs, 1));
1044210437
process_sptr(label);
1044310438
gl_sptr = process_blockaddr_sptr(sptr, label);
@@ -11490,7 +11485,7 @@ gen_address_operand(int addr_op, int nme, bool lda, LL_Type *llt_expected,
1149011485
OPERAND *operand;
1149111486
OPERAND **csed_operand;
1149211487
LL_Type *llt = llt_expected;
11493-
SPTR sptr = (SPTR)basesym_of(nme); // ???
11488+
SPTR sptr = basesym_of(nme);
1149411489
unsigned savedAddressSize = addressElementSize;
1149511490

1149611491
DBGTRACEIN2(" for ilix: %d(%s)", addr_op, IL_NAME(ILI_OPC(addr_op)))
@@ -11499,7 +11494,7 @@ gen_address_operand(int addr_op, int nme, bool lda, LL_Type *llt_expected,
1149911494
if (!llt && !lda && (((int)msz) >= 0)) {
1150011495
llt = make_ptr_lltype(make_type_from_msz(msz));
1150111496
}
11502-
sptr = (SPTR)basesym_of(nme); // ???
11497+
sptr = basesym_of(nme);
1150311498

1150411499
if (llt) {
1150511500
/* do nothing */

tools/flang2/flang2exe/cgmain.h

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -101,9 +101,10 @@ INSTR_LIST *mk_store_instr(OPERAND *val, OPERAND *addr);
101101
DTYPE cg_get_type(int n, TY_KIND v1, int v2);
102102

103103
/**
104-
\brief ...
104+
\brief Find the (virtual) function pointer in a JSRA call
105+
\param ilix the first argument of the \c IL_JSRA
105106
*/
106-
int find_pointer_to_function(int ilix);
107+
SPTR find_pointer_to_function(int ilix);
107108

108109
/**
109110
\brief ...

0 commit comments

Comments
 (0)