Skip to content

Commit

Permalink
Merge pull request #499 from ThePortlandGroup/nv_stage
Browse files Browse the repository at this point in the history
Pull 2018-06-08T04-58 Recent NVIDIA Changes
  • Loading branch information
sscalpone authored Jun 8, 2018
2 parents 50c31d9 + e6227a1 commit 4f8ff41
Show file tree
Hide file tree
Showing 62 changed files with 829 additions and 880 deletions.
14 changes: 7 additions & 7 deletions tools/flang1/flang1exe/findloop.c
Original file line number Diff line number Diff line change
Expand Up @@ -524,7 +524,7 @@ top_sort(void)
if (OPTDBG(9, 8))
fprintf(gbl.dbgfil, " innermost loop %d\n", k);
}
assert(r != n, "top_sort: wrong qlink", r, 3);
assert(r != n, "top_sort: wrong qlink", r, ERR_Severe);

/*
* Go through the relations and create the order - this continues until
Expand All @@ -541,7 +541,7 @@ top_sort(void)
if (--COUNT(SUCC(p)) == 0)
r = QLINK(r) = SUCC(p);
}
assert(n == 1, "wrong top_sort", n, 3);
assert(n == 1, "wrong top_sort", n, ERR_Severe);

/* free up the top array and the area used for the successors */

Expand Down Expand Up @@ -1103,7 +1103,7 @@ convert_loop(int loop)
* label referenced is the one which labels the new head
*/
tmp = ILT_NEXT(tmp);
assert(tmp == BIH_ILTLAST(tailbih), "convert_loop: wrong last ilt", tmp, 3);
assert(tmp == BIH_ILTLAST(tailbih), "convert_loop: wrong last ilt", tmp, ERR_Severe);
new_tree = rewr_ili((int)ILT_ILIP(br_ilt), 1, 1);
ILT_ILIP(tmp) = compl_br((int)new_tree, label);
if (OPTDBG(9, 8))
Expand Down Expand Up @@ -1141,7 +1141,7 @@ convert_loop(int loop)
break;
}
}
assert(p != PSI_P_NULL, "convert_loop: head not succ of tail", tail, 3);
assert(p != PSI_P_NULL, "convert_loop: head not succ of tail", tail, ERR_Severe);

/*
* remove tail from the predecessor list of head and add tail to the
Expand All @@ -1160,7 +1160,7 @@ convert_loop(int loop)
}
q = p;
}
assert(p != PSI_P_NULL, "convert_loop: tail not pred of head", head, 3);
assert(p != PSI_P_NULL, "convert_loop: tail not pred of head", head, ERR_Severe);
BIH_FT(tailbih) = 1;

/*
Expand Down Expand Up @@ -1241,7 +1241,7 @@ reorder_dfn_loops()
}
#if DEBUG
if (n != opt.nloops) {
interr("reorder_dfn_loops: wrong number of loops", n, 3);
interr("reorder_dfn_loops: wrong number of loops", n, ERR_Severe);
}
#endif
} /* reorder_dfn_loops */
Expand Down Expand Up @@ -1277,7 +1277,7 @@ reorderloops()
}
#if DEBUG
if (n != opt.nloops) {
interr("reorderloops: wrong number of loops", n, 3);
interr("reorderloops: wrong number of loops", n, ERR_Severe);
}
#endif
} /* reorderloops */
Expand Down
36 changes: 18 additions & 18 deletions tools/flang1/flang1exe/pointsto.c
Original file line number Diff line number Diff line change
Expand Up @@ -839,7 +839,7 @@ is_source_global(int psdx)
break;
default:
/* real error */
interr("bad PTE type", TPTE_TYPE(ptex), 4);
interr("bad PTE type", TPTE_TYPE(ptex), ERR_Fatal);
return TRUE;
}
}
Expand Down Expand Up @@ -940,7 +940,7 @@ is_source_nonlocal(int psdx)
break;
default:
/* real error */
interr("bad PTE type", TPTE_TYPE(ptex), 2);
interr("bad PTE type", TPTE_TYPE(ptex), ERR_Warning);
return TRUE;
}
}
Expand Down Expand Up @@ -1658,7 +1658,7 @@ make_init_assignment(int v, int sourcesptr, int stars, int targettype,
ASNEXT(asx) = 0;
break;
default:
interr("bad target type", targettype, 4);
interr("bad target type", targettype, ERR_Fatal);
return;
}
if (asx) {
Expand Down Expand Up @@ -1806,7 +1806,7 @@ mark_apte_targets(int psdx)
break;
default:
/* real error */
interr("bad PTE type", TPTE_TYPE(ptex), 2);
interr("bad PTE type", TPTE_TYPE(ptex), ERR_Warning);
break;
}
}
Expand All @@ -1820,7 +1820,7 @@ mark_apte_targets(int psdx)
case TT_UNK:
case TT_UNINIT:
default:
interr("bad PSD type", PSD_TYPE(psdx), 4);
interr("bad PSD type", PSD_TYPE(psdx), ERR_Fatal);
break;
}
} /* mark_apte_targets */
Expand Down Expand Up @@ -1872,7 +1872,7 @@ might_target(int psdx)
break;
default:
/* real error */
interr("bad PTE type", TPTE_TYPE(ptex), 2);
interr("bad PTE type", TPTE_TYPE(ptex), ERR_Warning);
return TRUE;
}
}
Expand Down Expand Up @@ -2255,7 +2255,7 @@ effective_rhs(int psdx)
return ptelistx;
default:
/* real error */
interr("pointsto: unknown RHS type in assignment", PSD_TYPE(psdx), 4);
interr("pointsto: unknown RHS type in assignment", PSD_TYPE(psdx), ERR_Fatal);
return TPTE_UNK;
}
} /* effective_rhs */
Expand Down Expand Up @@ -2315,12 +2315,12 @@ interpret(int asx)
break;
case TT_MEM:
/* not used yet */
interr("pointsto: unknown LHS type in assignment", PSD_TYPE(lhspsdx), 2);
interr("pointsto: unknown LHS type in assignment", PSD_TYPE(lhspsdx), ERR_Warning);
unk_all();
break;
default:
/* real error */
interr("pointsto: unknown LHS type in assignment", PSD_TYPE(lhspsdx), 4);
interr("pointsto: unknown LHS type in assignment", PSD_TYPE(lhspsdx), ERR_Fatal);
unk_all();
break;
}
Expand Down Expand Up @@ -2351,12 +2351,12 @@ interpret(int asx)
break;
case TT_MEM:
/* not used yet */
interr("pointsto: unknown LHS type in assignment", PSD_TYPE(lhspsdx), 2);
interr("pointsto: unknown LHS type in assignment", PSD_TYPE(lhspsdx), ERR_Warning);
unk_all();
break;
default:
/* real error */
interr("pointsto: unknown LHS type in assignment", PSD_TYPE(lhspsdx), 4);
interr("pointsto: unknown LHS type in assignment", PSD_TYPE(lhspsdx), ERR_Fatal);
unk_all();
break;
}
Expand Down Expand Up @@ -2459,12 +2459,12 @@ interpret(int asx)
break;
case TT_MEM:
/* ### really want to handle member LHS types */
interr("pointsto: unknown LHS type in assignment", PSD_TYPE(lhspsdx), 2);
interr("pointsto: unknown LHS type in assignment", PSD_TYPE(lhspsdx), ERR_Warning);
Trace(("unknown LHS type in assignment"));
break;
default:
/* real error */
interr("pointsto: unknown LHS type in assignment", PSD_TYPE(lhspsdx), 4);
interr("pointsto: unknown LHS type in assignment", PSD_TYPE(lhspsdx), ERR_Fatal);
Trace(("unknown LHS type in assignment"));
break;
}
Expand Down Expand Up @@ -2516,12 +2516,12 @@ interpret(int asx)
break;
case TT_MEM:
/* ### really want to handle member LHS types */
interr("pointsto: unknown LHS type in assignment", PSD_TYPE(lhspsdx), 2);
interr("pointsto: unknown LHS type in assignment", PSD_TYPE(lhspsdx), ERR_Warning);
Trace(("unknown LHS type in assignment"));
break;
default:
/* real error */
interr("pointsto: unknown LHS type in assignment", PSD_TYPE(lhspsdx), 4);
interr("pointsto: unknown LHS type in assignment", PSD_TYPE(lhspsdx), ERR_Fatal);
Trace(("unknown LHS type in assignment"));
break;
}
Expand Down Expand Up @@ -2604,7 +2604,7 @@ imprecise_match(int lptex, int ptex)
return ptex;
default:
/* real error */
interr("pointsto: unknown TPTE target type", TPTE_TYPE(lptex), 4);
interr("pointsto: unknown TPTE target type", TPTE_TYPE(lptex), ERR_Fatal);
return 0;
}
} else {
Expand Down Expand Up @@ -2860,7 +2860,7 @@ check_pte(char *ch)
}
if (bad) {
/* real error, consistency check failure */
interr(ch, 0, 4);
interr(ch, 0, ERR_Fatal);
}
} /* check_pte */
#endif
Expand Down Expand Up @@ -4400,7 +4400,7 @@ points_to(void)
}
if (asx > 0) {
/* real error, didn't finish assignments from previous block */
interr("pointsto: didn't finish all symbolic assignments", asx, 4);
interr("pointsto: didn't finish all symbolic assignments", asx, ERR_Fatal);
}
#if DEBUG
if (DBGBIT(TRACEFLAG, TRACEBIT)) {
Expand Down
27 changes: 13 additions & 14 deletions tools/flang1/flang1exe/symacc.c
Original file line number Diff line number Diff line change
Expand Up @@ -50,26 +50,26 @@ sym_init_first(void)
int i;

int sizeof_SYM = sizeof(SYM) / sizeof(INT);
assert(sizeof_SYM == 44, "bad SYM size", sizeof_SYM, 4);
assert(sizeof_SYM == 44, "bad SYM size", sizeof_SYM, ERR_Fatal);

if (stb.stg_base == NULL) {
STG_ALLOC(stb, 1000);
assert(stb.stg_base, "sym_init: no room for symtab", stb.stg_size, 4);
assert(stb.stg_base, "sym_init: no room for symtab", stb.stg_size, ERR_Fatal);
stb.n_size = 5024;
NEW(stb.n_base, char, stb.n_size);
assert(stb.n_base, "sym_init: no room for namtab", stb.n_size, 4);
assert(stb.n_base, "sym_init: no room for namtab", stb.n_size, ERR_Fatal);
stb.n_base[0] = 0;
STG_ALLOC(stb.dt, 400);
assert(stb.dt.stg_base, "sym_init: no room for dtypes", stb.dt.stg_size, 4);
assert(stb.dt.stg_base, "sym_init: no room for dtypes", stb.dt.stg_size, ERR_Fatal);
stb.w_size = 32;
NEW(stb.w_base, INT, stb.w_size);
assert(stb.w_base, "sym_init: no room for wtab", stb.w_size, 4);
assert(stb.w_base, "sym_init: no room for wtab", stb.w_size, ERR_Fatal);
}

stb.namavl = 1;
stb.wrdavl = 0;
for (i = 0; i <= HASHSIZE; i++)
stb.hashtb[i] = 0;
stb.hashtb[i] = SPTR_NULL;

DT_INT = DT_INT4;
DT_REAL = DT_REAL4;
Expand Down Expand Up @@ -133,8 +133,7 @@ lookupsym(const char *name, int olength)

return sptr;
}

return 0;
return SPTR_NULL;
} /* lookupsym */

/** \brief Issue diagnostic for identifer that is too long.
Expand Down Expand Up @@ -462,27 +461,27 @@ is_cimag_flt0(SPTR sptr)
bool
is_cmplx_dbl0(SPTR sptr)
{
if (is_dbl0(CONVAL1G(sptr)) && is_dbl0(CONVAL2G(sptr)))
return true;
return false;
return is_dbl0((SPTR)CONVAL1G(sptr)) && // ???
is_dbl0((SPTR)CONVAL2G(sptr)); // ???
}

bool
is_cmplx_quad0(SPTR sptr)
{
return is_quad0(CONVAL1G(sptr)) && is_quad0(CONVAL2G(sptr));
return is_quad0((SPTR)CONVAL1G(sptr)) && // ???
is_quad0((SPTR)CONVAL2G(sptr)); // ???
}

void
symini_errfatal(int n)
{
errfatal(n);
errfatal((error_code_t)n);
}

void
symini_error(int n, int s, int l, const char *c1, const char *c2)
{
error(n, s, l, c1, c2);
error((error_code_t)n, (enum error_severity)s, l, c1, c2);
}

void
Expand Down
10 changes: 5 additions & 5 deletions tools/flang2/flang2exe/asm_anno.c
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
/*
* Copyright (c) 2017, NVIDIA CORPORATION. All rights reserved.
* Copyright (c) 2002-2018, NVIDIA CORPORATION. All rights reserved.
*
* Licensed under the Apache License, Version 2.0 (the "License");
* you may not use this file except in compliance with the License.
Expand Down Expand Up @@ -118,7 +118,7 @@ annomod_initx(ANNO *ahead)

if (modcnt == 0) {
if ((fanno = fopen(SOURCE_FILE, "rb")) == NULL) {
error(2, 2, 0, SOURCE_FILE, CNULL);
error(2, ERR_Warning, 0, SOURCE_FILE, CNULL);
return ahead;
}
} else if (fanno == NULL)
Expand Down Expand Up @@ -188,7 +188,7 @@ annomod_initx(ANNO *ahead)
}
}

assert(cnt == cnt1, "annomod_init: cnt != cnt1 :", cnt1, 3);
assert(cnt == cnt1, "annomod_init: cnt != cnt1 :", cnt1, ERR_Severe);

/* ********
* step 3:
Expand Down Expand Up @@ -378,7 +378,7 @@ annomod_asm(int blkno)

if (amod->bihd != blkno) {
#if DEBUG
interr("Inconsistent anno records for blkno: ", blkno, 1);
interr("Inconsistent anno records for blkno: ", blkno, ERR_Informational);
#endif
flg.anno = 0;
return;
Expand All @@ -387,7 +387,7 @@ annomod_asm(int blkno)
again:
lanno.curpos = ftell(fanno);
if (lanno.curpos < 0) {
interr("annomod_asm(): cannot ftell into source for module:", modcnt, 2);
interr("annomod_asm(): cannot ftell into source for module:", modcnt, ERR_Warning);
amod = NULL;
return;
}
Expand Down
4 changes: 3 additions & 1 deletion tools/flang2/flang2exe/bih.h
Original file line number Diff line number Diff line change
Expand Up @@ -18,13 +18,15 @@
#ifndef BIH_H_
#define BIH_H_

#include "symtab.h"

/**
\file
\brief BIH data structures and definitions
*/

typedef struct {
int label;
SPTR label;
int lineno;
union {
UINT all;
Expand Down
12 changes: 6 additions & 6 deletions tools/flang2/flang2exe/bihutil.c
Original file line number Diff line number Diff line change
Expand Up @@ -62,8 +62,8 @@ bih_init(void)
bihb.stg_max = 0;
#if DEBUG
assert(((char *)&BIH_BLKCNT(0) - (char *)&bihb.stg_base[0]) % 8 == 0,
"offset of BIH_BLKCNT must be a multiple of 8", 0, 4);
assert(sizeof(BIH) % 8 == 0, "size of BIH must be a multiple of 8", 0, 4);
"offset of BIH_BLKCNT must be a multiple of 8", 0, ERR_Fatal);
assert(sizeof(BIH) % 8 == 0, "size of BIH must be a multiple of 8", 0, ERR_Fatal);
#endif
}

Expand Down Expand Up @@ -96,7 +96,7 @@ exp_addbih(int after)
p->next = BIH_NEXT(after);
BIH_NEXT(after) = i;
BIH_PREV(p->next) = i;
p->label = 0;
p->label = SPTR_NULL;
p->lineno = 0;
p->flags.all = 0;
p->flags2.all = 0;
Expand Down Expand Up @@ -141,7 +141,7 @@ addnewbih(int after, int flags, int fih)
p->next = next;
BIH_PREV(next) = i;
}
p->label = 0;
p->label = SPTR_NULL;
p->lineno = 0;
p->flags.all = 0;
p->flags2.all = 0;
Expand Down Expand Up @@ -287,7 +287,7 @@ merge_bih(int curbih)
return 0;
}
ILIBLKP(label, 0);
BIH_LABEL(nextbih) = 0;
BIH_LABEL(nextbih) = SPTR_NULL;
}

firstilt = BIH_ILTFIRST(nextbih);
Expand Down Expand Up @@ -339,7 +339,7 @@ merge_bih(int curbih)

#if DEBUG
assert((BIH_PARSECT(curbih) ^ BIH_PARSECT(nextbih)) == 0,
"merge_bih:parsect,nonparsect", curbih, 3);
"merge_bih:parsect,nonparsect", curbih, ERR_Severe);
#endif

wrilts(curbih);
Expand Down
Loading

0 comments on commit 4f8ff41

Please sign in to comment.