re PR fortran/49479 (reshape / optionals / zero sized arrays)
2011-06-28 Thomas Koenig <tkoenig@gcc.gnu.org> PR fortran/49479 * m4/reshape.m4: If source allocation is smaller than one, set it to one. * intrinsics/reshape_generic.c: Likewise. * generated/reshape_r16.c: Regenerated. * generated/reshape_c4.c: Regenerated. * generated/reshape_c16.c: Regenerated. * generated/reshape_c8.c: Regenerated. * generated/reshape_r4.c: Regenerated. * generated/reshape_i4.c: Regenerated. * generated/reshape_r10.c: Regenerated. * generated/reshape_r8.c: Regenerated. * generated/reshape_c10.c: Regenerated. * generated/reshape_i8.c: Regenerated. * generated/reshape_i16.c: Regenerated. 2011-06-28 Thomas Koenig <tkoenig@gcc.gnu.org> PR fortran/49479 * gfortran.dg/reshape_zerosize_3.f90: New test. From-SVN: r175594
This commit is contained in:
parent
6138f9bd87
commit
19b76346c0
@ -1,3 +1,8 @@
|
||||
2011-06-28 Thomas Koenig <tkoenig@gcc.gnu.org>
|
||||
|
||||
PR fortran/49479
|
||||
* gfortran.dg/reshape_zerosize_3.f90: New test.
|
||||
|
||||
2011-06-28 Janis Johnson <janisjo@codesourcery.com>
|
||||
|
||||
* gcc.target/arm/vfp-ldmdbs.c: Skip for soft float.
|
||||
|
43
gcc/testsuite/gfortran.dg/reshape_zerosize_3.f90
Normal file
43
gcc/testsuite/gfortran.dg/reshape_zerosize_3.f90
Normal file
@ -0,0 +1,43 @@
|
||||
! { dg-do run }
|
||||
! PR 49479 - this used not to print anything.
|
||||
! Test case by Joost VandeVondele.
|
||||
MODULE M1
|
||||
IMPLICIT NONE
|
||||
type foo
|
||||
character(len=5) :: x
|
||||
end type foo
|
||||
CONTAINS
|
||||
SUBROUTINE S1(data)
|
||||
INTEGER, DIMENSION(:), INTENT(IN), &
|
||||
OPTIONAL :: DATA
|
||||
character(20) :: line
|
||||
IF (.not. PRESENT(data)) call abort
|
||||
write (unit=line,fmt='(I5)') size(data)
|
||||
if (line /= ' 0 ') call abort
|
||||
END SUBROUTINE S1
|
||||
|
||||
subroutine s_type(data)
|
||||
type(foo), dimension(:), intent(in), optional :: data
|
||||
character(20) :: line
|
||||
IF (.not. PRESENT(data)) call abort
|
||||
write (unit=line,fmt='(I5)') size(data)
|
||||
if (line /= ' 0 ') call abort
|
||||
end subroutine s_type
|
||||
|
||||
SUBROUTINE S2(N)
|
||||
INTEGER :: N
|
||||
INTEGER, ALLOCATABLE, DIMENSION(:, :) :: blki
|
||||
type(foo), allocatable, dimension(:, :) :: bar
|
||||
ALLOCATE(blki(3,N))
|
||||
allocate (bar(3,n))
|
||||
blki=0
|
||||
CALL S1(RESHAPE(blki,(/3*N/)))
|
||||
call s_type(reshape(bar, (/3*N/)))
|
||||
END SUBROUTINE S2
|
||||
|
||||
END MODULE M1
|
||||
|
||||
USE M1
|
||||
CALL S2(0)
|
||||
END
|
||||
! { dg-final { cleanup-modules "m1" } }
|
@ -1,3 +1,21 @@
|
||||
2011-06-28 Thomas Koenig <tkoenig@gcc.gnu.org>
|
||||
|
||||
PR fortran/49479
|
||||
* m4/reshape.m4: If source allocation is smaller than one, set it
|
||||
to one.
|
||||
* intrinsics/reshape_generic.c: Likewise.
|
||||
* generated/reshape_r16.c: Regenerated.
|
||||
* generated/reshape_c4.c: Regenerated.
|
||||
* generated/reshape_c16.c: Regenerated.
|
||||
* generated/reshape_c8.c: Regenerated.
|
||||
* generated/reshape_r4.c: Regenerated.
|
||||
* generated/reshape_i4.c: Regenerated.
|
||||
* generated/reshape_r10.c: Regenerated.
|
||||
* generated/reshape_r8.c: Regenerated.
|
||||
* generated/reshape_c10.c: Regenerated.
|
||||
* generated/reshape_i8.c: Regenerated.
|
||||
* generated/reshape_i16.c: Regenerated.
|
||||
|
||||
2011-06-18 Janne Blomqvist <jb@gcc.gnu.org>
|
||||
|
||||
PR libfortran/49296
|
||||
|
@ -97,6 +97,8 @@ reshape_c10 (gfc_array_c10 * const restrict ret,
|
||||
|
||||
if (ret->data == NULL)
|
||||
{
|
||||
index_type alloc_size;
|
||||
|
||||
rs = 1;
|
||||
for (n = 0; n < rdim; n++)
|
||||
{
|
||||
@ -107,7 +109,13 @@ reshape_c10 (gfc_array_c10 * const restrict ret,
|
||||
rs *= rex;
|
||||
}
|
||||
ret->offset = 0;
|
||||
ret->data = internal_malloc_size ( rs * sizeof (GFC_COMPLEX_10));
|
||||
|
||||
if (unlikely (rs < 1))
|
||||
alloc_size = 1;
|
||||
else
|
||||
alloc_size = rs * sizeof (GFC_COMPLEX_10);
|
||||
|
||||
ret->data = internal_malloc_size (alloc_size);
|
||||
ret->dtype = (source->dtype & ~GFC_DTYPE_RANK_MASK) | rdim;
|
||||
}
|
||||
|
||||
|
@ -97,6 +97,8 @@ reshape_c16 (gfc_array_c16 * const restrict ret,
|
||||
|
||||
if (ret->data == NULL)
|
||||
{
|
||||
index_type alloc_size;
|
||||
|
||||
rs = 1;
|
||||
for (n = 0; n < rdim; n++)
|
||||
{
|
||||
@ -107,7 +109,13 @@ reshape_c16 (gfc_array_c16 * const restrict ret,
|
||||
rs *= rex;
|
||||
}
|
||||
ret->offset = 0;
|
||||
ret->data = internal_malloc_size ( rs * sizeof (GFC_COMPLEX_16));
|
||||
|
||||
if (unlikely (rs < 1))
|
||||
alloc_size = 1;
|
||||
else
|
||||
alloc_size = rs * sizeof (GFC_COMPLEX_16);
|
||||
|
||||
ret->data = internal_malloc_size (alloc_size);
|
||||
ret->dtype = (source->dtype & ~GFC_DTYPE_RANK_MASK) | rdim;
|
||||
}
|
||||
|
||||
|
@ -97,6 +97,8 @@ reshape_c4 (gfc_array_c4 * const restrict ret,
|
||||
|
||||
if (ret->data == NULL)
|
||||
{
|
||||
index_type alloc_size;
|
||||
|
||||
rs = 1;
|
||||
for (n = 0; n < rdim; n++)
|
||||
{
|
||||
@ -107,7 +109,13 @@ reshape_c4 (gfc_array_c4 * const restrict ret,
|
||||
rs *= rex;
|
||||
}
|
||||
ret->offset = 0;
|
||||
ret->data = internal_malloc_size ( rs * sizeof (GFC_COMPLEX_4));
|
||||
|
||||
if (unlikely (rs < 1))
|
||||
alloc_size = 1;
|
||||
else
|
||||
alloc_size = rs * sizeof (GFC_COMPLEX_4);
|
||||
|
||||
ret->data = internal_malloc_size (alloc_size);
|
||||
ret->dtype = (source->dtype & ~GFC_DTYPE_RANK_MASK) | rdim;
|
||||
}
|
||||
|
||||
|
@ -97,6 +97,8 @@ reshape_c8 (gfc_array_c8 * const restrict ret,
|
||||
|
||||
if (ret->data == NULL)
|
||||
{
|
||||
index_type alloc_size;
|
||||
|
||||
rs = 1;
|
||||
for (n = 0; n < rdim; n++)
|
||||
{
|
||||
@ -107,7 +109,13 @@ reshape_c8 (gfc_array_c8 * const restrict ret,
|
||||
rs *= rex;
|
||||
}
|
||||
ret->offset = 0;
|
||||
ret->data = internal_malloc_size ( rs * sizeof (GFC_COMPLEX_8));
|
||||
|
||||
if (unlikely (rs < 1))
|
||||
alloc_size = 1;
|
||||
else
|
||||
alloc_size = rs * sizeof (GFC_COMPLEX_8);
|
||||
|
||||
ret->data = internal_malloc_size (alloc_size);
|
||||
ret->dtype = (source->dtype & ~GFC_DTYPE_RANK_MASK) | rdim;
|
||||
}
|
||||
|
||||
|
@ -97,6 +97,8 @@ reshape_16 (gfc_array_i16 * const restrict ret,
|
||||
|
||||
if (ret->data == NULL)
|
||||
{
|
||||
index_type alloc_size;
|
||||
|
||||
rs = 1;
|
||||
for (n = 0; n < rdim; n++)
|
||||
{
|
||||
@ -107,7 +109,13 @@ reshape_16 (gfc_array_i16 * const restrict ret,
|
||||
rs *= rex;
|
||||
}
|
||||
ret->offset = 0;
|
||||
ret->data = internal_malloc_size ( rs * sizeof (GFC_INTEGER_16));
|
||||
|
||||
if (unlikely (rs < 1))
|
||||
alloc_size = 1;
|
||||
else
|
||||
alloc_size = rs * sizeof (GFC_INTEGER_16);
|
||||
|
||||
ret->data = internal_malloc_size (alloc_size);
|
||||
ret->dtype = (source->dtype & ~GFC_DTYPE_RANK_MASK) | rdim;
|
||||
}
|
||||
|
||||
|
@ -97,6 +97,8 @@ reshape_4 (gfc_array_i4 * const restrict ret,
|
||||
|
||||
if (ret->data == NULL)
|
||||
{
|
||||
index_type alloc_size;
|
||||
|
||||
rs = 1;
|
||||
for (n = 0; n < rdim; n++)
|
||||
{
|
||||
@ -107,7 +109,13 @@ reshape_4 (gfc_array_i4 * const restrict ret,
|
||||
rs *= rex;
|
||||
}
|
||||
ret->offset = 0;
|
||||
ret->data = internal_malloc_size ( rs * sizeof (GFC_INTEGER_4));
|
||||
|
||||
if (unlikely (rs < 1))
|
||||
alloc_size = 1;
|
||||
else
|
||||
alloc_size = rs * sizeof (GFC_INTEGER_4);
|
||||
|
||||
ret->data = internal_malloc_size (alloc_size);
|
||||
ret->dtype = (source->dtype & ~GFC_DTYPE_RANK_MASK) | rdim;
|
||||
}
|
||||
|
||||
|
@ -97,6 +97,8 @@ reshape_8 (gfc_array_i8 * const restrict ret,
|
||||
|
||||
if (ret->data == NULL)
|
||||
{
|
||||
index_type alloc_size;
|
||||
|
||||
rs = 1;
|
||||
for (n = 0; n < rdim; n++)
|
||||
{
|
||||
@ -107,7 +109,13 @@ reshape_8 (gfc_array_i8 * const restrict ret,
|
||||
rs *= rex;
|
||||
}
|
||||
ret->offset = 0;
|
||||
ret->data = internal_malloc_size ( rs * sizeof (GFC_INTEGER_8));
|
||||
|
||||
if (unlikely (rs < 1))
|
||||
alloc_size = 1;
|
||||
else
|
||||
alloc_size = rs * sizeof (GFC_INTEGER_8);
|
||||
|
||||
ret->data = internal_malloc_size (alloc_size);
|
||||
ret->dtype = (source->dtype & ~GFC_DTYPE_RANK_MASK) | rdim;
|
||||
}
|
||||
|
||||
|
@ -97,6 +97,8 @@ reshape_r10 (gfc_array_r10 * const restrict ret,
|
||||
|
||||
if (ret->data == NULL)
|
||||
{
|
||||
index_type alloc_size;
|
||||
|
||||
rs = 1;
|
||||
for (n = 0; n < rdim; n++)
|
||||
{
|
||||
@ -107,7 +109,13 @@ reshape_r10 (gfc_array_r10 * const restrict ret,
|
||||
rs *= rex;
|
||||
}
|
||||
ret->offset = 0;
|
||||
ret->data = internal_malloc_size ( rs * sizeof (GFC_REAL_10));
|
||||
|
||||
if (unlikely (rs < 1))
|
||||
alloc_size = 1;
|
||||
else
|
||||
alloc_size = rs * sizeof (GFC_REAL_10);
|
||||
|
||||
ret->data = internal_malloc_size (alloc_size);
|
||||
ret->dtype = (source->dtype & ~GFC_DTYPE_RANK_MASK) | rdim;
|
||||
}
|
||||
|
||||
|
@ -97,6 +97,8 @@ reshape_r16 (gfc_array_r16 * const restrict ret,
|
||||
|
||||
if (ret->data == NULL)
|
||||
{
|
||||
index_type alloc_size;
|
||||
|
||||
rs = 1;
|
||||
for (n = 0; n < rdim; n++)
|
||||
{
|
||||
@ -107,7 +109,13 @@ reshape_r16 (gfc_array_r16 * const restrict ret,
|
||||
rs *= rex;
|
||||
}
|
||||
ret->offset = 0;
|
||||
ret->data = internal_malloc_size ( rs * sizeof (GFC_REAL_16));
|
||||
|
||||
if (unlikely (rs < 1))
|
||||
alloc_size = 1;
|
||||
else
|
||||
alloc_size = rs * sizeof (GFC_REAL_16);
|
||||
|
||||
ret->data = internal_malloc_size (alloc_size);
|
||||
ret->dtype = (source->dtype & ~GFC_DTYPE_RANK_MASK) | rdim;
|
||||
}
|
||||
|
||||
|
@ -97,6 +97,8 @@ reshape_r4 (gfc_array_r4 * const restrict ret,
|
||||
|
||||
if (ret->data == NULL)
|
||||
{
|
||||
index_type alloc_size;
|
||||
|
||||
rs = 1;
|
||||
for (n = 0; n < rdim; n++)
|
||||
{
|
||||
@ -107,7 +109,13 @@ reshape_r4 (gfc_array_r4 * const restrict ret,
|
||||
rs *= rex;
|
||||
}
|
||||
ret->offset = 0;
|
||||
ret->data = internal_malloc_size ( rs * sizeof (GFC_REAL_4));
|
||||
|
||||
if (unlikely (rs < 1))
|
||||
alloc_size = 1;
|
||||
else
|
||||
alloc_size = rs * sizeof (GFC_REAL_4);
|
||||
|
||||
ret->data = internal_malloc_size (alloc_size);
|
||||
ret->dtype = (source->dtype & ~GFC_DTYPE_RANK_MASK) | rdim;
|
||||
}
|
||||
|
||||
|
@ -97,6 +97,8 @@ reshape_r8 (gfc_array_r8 * const restrict ret,
|
||||
|
||||
if (ret->data == NULL)
|
||||
{
|
||||
index_type alloc_size;
|
||||
|
||||
rs = 1;
|
||||
for (n = 0; n < rdim; n++)
|
||||
{
|
||||
@ -107,7 +109,13 @@ reshape_r8 (gfc_array_r8 * const restrict ret,
|
||||
rs *= rex;
|
||||
}
|
||||
ret->offset = 0;
|
||||
ret->data = internal_malloc_size ( rs * sizeof (GFC_REAL_8));
|
||||
|
||||
if (unlikely (rs < 1))
|
||||
alloc_size = 1;
|
||||
else
|
||||
alloc_size = rs * sizeof (GFC_REAL_8);
|
||||
|
||||
ret->data = internal_malloc_size (alloc_size);
|
||||
ret->dtype = (source->dtype & ~GFC_DTYPE_RANK_MASK) | rdim;
|
||||
}
|
||||
|
||||
|
@ -85,6 +85,8 @@ reshape_internal (parray *ret, parray *source, shape_type *shape,
|
||||
|
||||
if (ret->data == NULL)
|
||||
{
|
||||
index_type alloc_size;
|
||||
|
||||
rs = 1;
|
||||
for (n = 0; n < rdim; n++)
|
||||
{
|
||||
@ -95,7 +97,14 @@ reshape_internal (parray *ret, parray *source, shape_type *shape,
|
||||
rs *= rex;
|
||||
}
|
||||
ret->offset = 0;
|
||||
ret->data = internal_malloc_size ( rs * size );
|
||||
|
||||
if (unlikely (rs < 1))
|
||||
alloc_size = 1;
|
||||
else
|
||||
alloc_size = rs * size;
|
||||
|
||||
ret->data = internal_malloc_size (alloc_size);
|
||||
|
||||
ret->dtype = (source->dtype & ~GFC_DTYPE_RANK_MASK) | rdim;
|
||||
}
|
||||
|
||||
|
@ -101,6 +101,8 @@ reshape_'rtype_ccode` ('rtype` * const restrict ret,
|
||||
|
||||
if (ret->data == NULL)
|
||||
{
|
||||
index_type alloc_size;
|
||||
|
||||
rs = 1;
|
||||
for (n = 0; n < rdim; n++)
|
||||
{
|
||||
@ -111,7 +113,13 @@ reshape_'rtype_ccode` ('rtype` * const restrict ret,
|
||||
rs *= rex;
|
||||
}
|
||||
ret->offset = 0;
|
||||
ret->data = internal_malloc_size ( rs * sizeof ('rtype_name`));
|
||||
|
||||
if (unlikely (rs < 1))
|
||||
alloc_size = 1;
|
||||
else
|
||||
alloc_size = rs * sizeof ('rtype_name`);
|
||||
|
||||
ret->data = internal_malloc_size (alloc_size);
|
||||
ret->dtype = (source->dtype & ~GFC_DTYPE_RANK_MASK) | rdim;
|
||||
}
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user