+2008-05-04 Thomas Koenig <tkoenig@gcc.gnu.org>
+
+ PR libfortran/35995
+ * gfortran.dg/intrinsic_ifunction_1.f90: New test case.
+
2008-05-04 Andy Hutchinson <hutchinsonandy@aim.com>
* gcc.dg/nested-func-5.c: Skip for target without trampolines.
--- /dev/null
+! { dg-do run }
+! PR 35995 - ifunction.m4 and ifunction_logical.m4 had a bug
+! where zero-sized arguments were not handled correctly.
+! Test case provided by Dick Hendrickson, amended by
+! Thomas Koenig.
+
+ program try_gf0026_etc
+
+ call gf0026( 0, 1)
+ call foo ( 0, 1)
+
+ end program
+
+ SUBROUTINE GF0026(nf0,nf1)
+ LOGICAL LDA(9)
+ INTEGER IDA(NF0,9), iii(9)
+
+ lda = (/ (i/2*2 .eq. I, i=1,9) /)
+ LDA = ALL ( IDA .NE. -1000, 1)
+ if (.not. all(lda)) call abort
+ if (.not. all(ida .ne. -1000)) call abort
+
+ lda = (/ (i/2*2 .eq. I, i=1,9) /)
+ LDA = any ( IDA .NE. -1000, 1)
+ print *, lda !expect FALSE
+ if (any(lda)) call abort
+ print *, any(ida .ne. -1000) !expect FALSE
+ if (any(ida .ne. -1000)) call abort
+
+ iii = 137
+ iii = count ( IDA .NE. -1000, 1)
+ if (any(iii /= 0)) call abort
+ if (count(ida .ne. -1000) /= 0) call abort
+
+ END SUBROUTINE
+
+ subroutine foo (nf0, nf1)
+ integer, dimension(9):: res, iii
+ integer, dimension(nf0,9) :: ida
+ res = (/ (-i, i=1,9) /)
+ res = product (ida, 1)
+ if (any(res /= 1)) call abort
+ end subroutine foo
+2008-05-04 Thomas Koenig <tkoenig@gcc.gnu.org>
+
+ PR libfortran/35995
+ * m4/ifunction_logical.m4: If the extent of "array"
+ is less than zero, set it to zero. Use an explicit
+ flag for breaking out of the main loop to avoid, because
+ the data pointer for "array" may be NULL for an empty
+ array.
+ * m4/ifunction.m4: Likewise.
+ * generated/all_l1.c: Regenerated.
+ * generated/all_l16.c: Regenerated.
+ * generated/all_l2.c: Regenerated.
+ * generated/all_l4.c: Regenerated.
+ * generated/all_l8.c: Regenerated.
+ * generated/any_l1.c: Regenerated.
+ * generated/any_l16.c: Regenerated.
+ * generated/any_l2.c: Regenerated.
+ * generated/any_l4.c: Regenerated.
+ * generated/any_l8.c: Regenerated.
+ * generated/count_16_l.c: Regenerated.
+ * generated/count_1_l.c: Regenerated.
+ * generated/count_2_l.c: Regenerated.
+ * generated/count_4_l.c: Regenerated.
+ * generated/count_8_l.c: Regenerated.
+ * generated/maxloc1_16_i1.c: Regenerated.
+ * generated/maxloc1_16_i16.c: Regenerated.
+ * generated/maxloc1_16_i2.c: Regenerated.
+ * generated/maxloc1_16_i4.c: Regenerated.
+ * generated/maxloc1_16_i8.c: Regenerated.
+ * generated/maxloc1_16_r10.c: Regenerated.
+ * generated/maxloc1_16_r16.c: Regenerated.
+ * generated/maxloc1_16_r4.c: Regenerated.
+ * generated/maxloc1_16_r8.c: Regenerated.
+ * generated/maxloc1_4_i1.c: Regenerated.
+ * generated/maxloc1_4_i16.c: Regenerated.
+ * generated/maxloc1_4_i2.c: Regenerated.
+ * generated/maxloc1_4_i4.c: Regenerated.
+ * generated/maxloc1_4_i8.c: Regenerated.
+ * generated/maxloc1_4_r10.c: Regenerated.
+ * generated/maxloc1_4_r16.c: Regenerated.
+ * generated/maxloc1_4_r4.c: Regenerated.
+ * generated/maxloc1_4_r8.c: Regenerated.
+ * generated/maxloc1_8_i1.c: Regenerated.
+ * generated/maxloc1_8_i16.c: Regenerated.
+ * generated/maxloc1_8_i2.c: Regenerated.
+ * generated/maxloc1_8_i4.c: Regenerated.
+ * generated/maxloc1_8_i8.c: Regenerated.
+ * generated/maxloc1_8_r10.c: Regenerated.
+ * generated/maxloc1_8_r16.c: Regenerated.
+ * generated/maxloc1_8_r4.c: Regenerated.
+ * generated/maxloc1_8_r8.c: Regenerated.
+ * generated/maxval_i1.c: Regenerated.
+ * generated/maxval_i16.c: Regenerated.
+ * generated/maxval_i2.c: Regenerated.
+ * generated/maxval_i4.c: Regenerated.
+ * generated/maxval_i8.c: Regenerated.
+ * generated/maxval_r10.c: Regenerated.
+ * generated/maxval_r16.c: Regenerated.
+ * generated/maxval_r4.c: Regenerated.
+ * generated/maxval_r8.c: Regenerated.
+ * generated/minloc1_16_i1.c: Regenerated.
+ * generated/minloc1_16_i16.c: Regenerated.
+ * generated/minloc1_16_i2.c: Regenerated.
+ * generated/minloc1_16_i4.c: Regenerated.
+ * generated/minloc1_16_i8.c: Regenerated.
+ * generated/minloc1_16_r10.c: Regenerated.
+ * generated/minloc1_16_r16.c: Regenerated.
+ * generated/minloc1_16_r4.c: Regenerated.
+ * generated/minloc1_16_r8.c: Regenerated.
+ * generated/minloc1_4_i1.c: Regenerated.
+ * generated/minloc1_4_i16.c: Regenerated.
+ * generated/minloc1_4_i2.c: Regenerated.
+ * generated/minloc1_4_i4.c: Regenerated.
+ * generated/minloc1_4_i8.c: Regenerated.
+ * generated/minloc1_4_r10.c: Regenerated.
+ * generated/minloc1_4_r16.c: Regenerated.
+ * generated/minloc1_4_r4.c: Regenerated.
+ * generated/minloc1_4_r8.c: Regenerated.
+ * generated/minloc1_8_i1.c: Regenerated.
+ * generated/minloc1_8_i16.c: Regenerated.
+ * generated/minloc1_8_i2.c: Regenerated.
+ * generated/minloc1_8_i4.c: Regenerated.
+ * generated/minloc1_8_i8.c: Regenerated.
+ * generated/minloc1_8_r10.c: Regenerated.
+ * generated/minloc1_8_r16.c: Regenerated.
+ * generated/minloc1_8_r4.c: Regenerated.
+ * generated/minloc1_8_r8.c: Regenerated.
+ * generated/minval_i1.c: Regenerated.
+ * generated/minval_i16.c: Regenerated.
+ * generated/minval_i2.c: Regenerated.
+ * generated/minval_i4.c: Regenerated.
+ * generated/minval_i8.c: Regenerated.
+ * generated/minval_r10.c: Regenerated.
+ * generated/minval_r16.c: Regenerated.
+ * generated/minval_r4.c: Regenerated.
+ * generated/minval_r8.c: Regenerated.
+ * generated/product_c10.c: Regenerated.
+ * generated/product_c16.c: Regenerated.
+ * generated/product_c4.c: Regenerated.
+ * generated/product_c8.c: Regenerated.
+ * generated/product_i1.c: Regenerated.
+ * generated/product_i16.c: Regenerated.
+ * generated/product_i2.c: Regenerated.
+ * generated/product_i4.c: Regenerated.
+ * generated/product_i8.c: Regenerated.
+ * generated/product_r10.c: Regenerated.
+ * generated/product_r16.c: Regenerated.
+ * generated/product_r4.c: Regenerated.
+ * generated/product_r8.c: Regenerated.
+ * generated/sum_c10.c: Regenerated.
+ * generated/sum_c16.c: Regenerated.
+ * generated/sum_c4.c: Regenerated.
+ * generated/sum_c8.c: Regenerated.
+ * generated/sum_i1.c: Regenerated.
+ * generated/sum_i16.c: Regenerated.
+ * generated/sum_i2.c: Regenerated.
+ * generated/sum_i4.c: Regenerated.
+ * generated/sum_i8.c: Regenerated.
+ * generated/sum_r10.c: Regenerated.
+ * generated/sum_r16.c: Regenerated.
+ * generated/sum_r4.c: Regenerated.
+ * generated/sum_r8.c: Regenerated.
+
2008-05-04 Thomas Koenig <tkoenig@gcc.gnu.org>
PR libfortran/35990
index_type delta;
index_type dim;
int src_kind;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
src_kind = GFC_DESCRIPTOR_SIZE (array);
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
+
delta = array->dim[dim].stride * src_kind;
for (n = 0; n < dim; n++)
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_LOGICAL_1 * restrict src;
GFC_LOGICAL_1 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
+ continue_loop = 0;
break;
}
else
index_type delta;
index_type dim;
int src_kind;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
src_kind = GFC_DESCRIPTOR_SIZE (array);
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
+
delta = array->dim[dim].stride * src_kind;
for (n = 0; n < dim; n++)
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_LOGICAL_1 * restrict src;
GFC_LOGICAL_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
+ continue_loop = 0;
break;
}
else
index_type delta;
index_type dim;
int src_kind;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
src_kind = GFC_DESCRIPTOR_SIZE (array);
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
+
delta = array->dim[dim].stride * src_kind;
for (n = 0; n < dim; n++)
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_LOGICAL_1 * restrict src;
GFC_LOGICAL_2 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
+ continue_loop = 0;
break;
}
else
index_type delta;
index_type dim;
int src_kind;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
src_kind = GFC_DESCRIPTOR_SIZE (array);
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
+
delta = array->dim[dim].stride * src_kind;
for (n = 0; n < dim; n++)
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_LOGICAL_1 * restrict src;
GFC_LOGICAL_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
+ continue_loop = 0;
break;
}
else
index_type delta;
index_type dim;
int src_kind;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
src_kind = GFC_DESCRIPTOR_SIZE (array);
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
+
delta = array->dim[dim].stride * src_kind;
for (n = 0; n < dim; n++)
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_LOGICAL_1 * restrict src;
GFC_LOGICAL_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
+ continue_loop = 0;
break;
}
else
index_type delta;
index_type dim;
int src_kind;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
src_kind = GFC_DESCRIPTOR_SIZE (array);
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
+
delta = array->dim[dim].stride * src_kind;
for (n = 0; n < dim; n++)
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_LOGICAL_1 * restrict src;
GFC_LOGICAL_1 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
+ continue_loop = 0;
break;
}
else
index_type delta;
index_type dim;
int src_kind;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
src_kind = GFC_DESCRIPTOR_SIZE (array);
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
+
delta = array->dim[dim].stride * src_kind;
for (n = 0; n < dim; n++)
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_LOGICAL_1 * restrict src;
GFC_LOGICAL_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
+ continue_loop = 0;
break;
}
else
index_type delta;
index_type dim;
int src_kind;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
src_kind = GFC_DESCRIPTOR_SIZE (array);
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
+
delta = array->dim[dim].stride * src_kind;
for (n = 0; n < dim; n++)
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_LOGICAL_1 * restrict src;
GFC_LOGICAL_2 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
+ continue_loop = 0;
break;
}
else
index_type delta;
index_type dim;
int src_kind;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
src_kind = GFC_DESCRIPTOR_SIZE (array);
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
+
delta = array->dim[dim].stride * src_kind;
for (n = 0; n < dim; n++)
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_LOGICAL_1 * restrict src;
GFC_LOGICAL_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
+ continue_loop = 0;
break;
}
else
index_type delta;
index_type dim;
int src_kind;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
src_kind = GFC_DESCRIPTOR_SIZE (array);
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
+
delta = array->dim[dim].stride * src_kind;
for (n = 0; n < dim; n++)
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_LOGICAL_1 * restrict src;
GFC_LOGICAL_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
+ continue_loop = 0;
break;
}
else
index_type delta;
index_type dim;
int src_kind;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
src_kind = GFC_DESCRIPTOR_SIZE (array);
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
+
delta = array->dim[dim].stride * src_kind;
for (n = 0; n < dim; n++)
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_LOGICAL_1 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
+ continue_loop = 0;
break;
}
else
index_type delta;
index_type dim;
int src_kind;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
src_kind = GFC_DESCRIPTOR_SIZE (array);
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
+
delta = array->dim[dim].stride * src_kind;
for (n = 0; n < dim; n++)
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_LOGICAL_1 * restrict src;
GFC_INTEGER_1 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
+ continue_loop = 0;
break;
}
else
index_type delta;
index_type dim;
int src_kind;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
src_kind = GFC_DESCRIPTOR_SIZE (array);
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
+
delta = array->dim[dim].stride * src_kind;
for (n = 0; n < dim; n++)
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_LOGICAL_1 * restrict src;
GFC_INTEGER_2 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
+ continue_loop = 0;
break;
}
else
index_type delta;
index_type dim;
int src_kind;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
src_kind = GFC_DESCRIPTOR_SIZE (array);
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
+
delta = array->dim[dim].stride * src_kind;
for (n = 0; n < dim; n++)
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_LOGICAL_1 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
+ continue_loop = 0;
break;
}
else
index_type delta;
index_type dim;
int src_kind;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
src_kind = GFC_DESCRIPTOR_SIZE (array);
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
+
delta = array->dim[dim].stride * src_kind;
for (n = 0; n < dim; n++)
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_LOGICAL_1 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
+ continue_loop = 0;
break;
}
else
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_1 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_16 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_2 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_4 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_8 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_10 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_16 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_4 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_8 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_1 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_16 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_2 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_4 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_8 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_10 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_16 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_4 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_8 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_1 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_16 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_2 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_4 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_8 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_10 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_16 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_4 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_8 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_1 * restrict src;
GFC_INTEGER_1 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_16 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_2 * restrict src;
GFC_INTEGER_2 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_4 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_8 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_10 * restrict src;
GFC_REAL_10 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_16 * restrict src;
GFC_REAL_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_4 * restrict src;
GFC_REAL_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_8 * restrict src;
GFC_REAL_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_1 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_16 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_2 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_4 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_8 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_10 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_16 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_4 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_8 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_1 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_16 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_2 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_4 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_8 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_10 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_16 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_4 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_8 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_1 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_16 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_2 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_4 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_8 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_10 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_16 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_4 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_8 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_1 * restrict src;
GFC_INTEGER_1 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_16 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_2 * restrict src;
GFC_INTEGER_2 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_4 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_8 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_10 * restrict src;
GFC_REAL_10 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_16 * restrict src;
GFC_REAL_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_4 * restrict src;
GFC_REAL_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_8 * restrict src;
GFC_REAL_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_COMPLEX_10 * restrict src;
GFC_COMPLEX_10 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_COMPLEX_16 * restrict src;
GFC_COMPLEX_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_COMPLEX_4 * restrict src;
GFC_COMPLEX_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_COMPLEX_8 * restrict src;
GFC_COMPLEX_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_1 * restrict src;
GFC_INTEGER_1 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_16 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_2 * restrict src;
GFC_INTEGER_2 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_4 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_8 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_10 * restrict src;
GFC_REAL_10 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_16 * restrict src;
GFC_REAL_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_4 * restrict src;
GFC_REAL_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_8 * restrict src;
GFC_REAL_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_COMPLEX_10 * restrict src;
GFC_COMPLEX_10 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_COMPLEX_16 * restrict src;
GFC_COMPLEX_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_COMPLEX_4 * restrict src;
GFC_COMPLEX_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_COMPLEX_8 * restrict src;
GFC_COMPLEX_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_1 * restrict src;
GFC_INTEGER_1 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_16 * restrict src;
GFC_INTEGER_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_2 * restrict src;
GFC_INTEGER_2 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_4 * restrict src;
GFC_INTEGER_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_INTEGER_8 * restrict src;
GFC_INTEGER_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_10 * restrict src;
GFC_REAL_10 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_16 * restrict src;
GFC_REAL_16 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_4 * restrict src;
GFC_REAL_4 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_REAL_8 * restrict src;
GFC_REAL_8 result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type len;
index_type delta;
index_type dim;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
rank = GFC_DESCRIPTOR_RANK (array) - 1;
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
delta = array->dim[dim].stride;
for (n = 0; n < dim; n++)
base = array->data;
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const atype_name * restrict src;
rtype_name result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
- break;
+ continue_loop = 0;
+ break;
}
else
{
index_type delta;
index_type dim;
int src_kind;
+ int continue_loop;
/* Make dim zero based to avoid confusion. */
dim = (*pdim) - 1;
src_kind = GFC_DESCRIPTOR_SIZE (array);
len = array->dim[dim].ubound + 1 - array->dim[dim].lbound;
+ if (len < 0)
+ len = 0;
+
delta = array->dim[dim].stride * src_kind;
for (n = 0; n < dim; n++)
dest = retarray->data;
- while (base)
+ continue_loop = 1;
+ while (continue_loop)
{
const GFC_LOGICAL_1 * restrict src;
rtype_name result;
if (n == rank)
{
/* Break out of the look. */
- base = NULL;
+ continue_loop = 0;
break;
}
else