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.
git-svn-id: svn+ssh://gcc.gnu.org/svn/gcc/trunk@175594
138bc75d-0d04-0410-961f-
82ee72b054a4
+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.
--- /dev/null
+! { 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" } }
+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
if (ret->data == NULL)
{
+ index_type alloc_size;
+
rs = 1;
for (n = 0; n < rdim; n++)
{
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;
}
if (ret->data == NULL)
{
+ index_type alloc_size;
+
rs = 1;
for (n = 0; n < rdim; n++)
{
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;
}
if (ret->data == NULL)
{
+ index_type alloc_size;
+
rs = 1;
for (n = 0; n < rdim; n++)
{
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;
}
if (ret->data == NULL)
{
+ index_type alloc_size;
+
rs = 1;
for (n = 0; n < rdim; n++)
{
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;
}
if (ret->data == NULL)
{
+ index_type alloc_size;
+
rs = 1;
for (n = 0; n < rdim; n++)
{
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;
}
if (ret->data == NULL)
{
+ index_type alloc_size;
+
rs = 1;
for (n = 0; n < rdim; n++)
{
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;
}
if (ret->data == NULL)
{
+ index_type alloc_size;
+
rs = 1;
for (n = 0; n < rdim; n++)
{
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;
}
if (ret->data == NULL)
{
+ index_type alloc_size;
+
rs = 1;
for (n = 0; n < rdim; n++)
{
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;
}
if (ret->data == NULL)
{
+ index_type alloc_size;
+
rs = 1;
for (n = 0; n < rdim; n++)
{
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;
}
if (ret->data == NULL)
{
+ index_type alloc_size;
+
rs = 1;
for (n = 0; n < rdim; n++)
{
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;
}
if (ret->data == NULL)
{
+ index_type alloc_size;
+
rs = 1;
for (n = 0; n < rdim; n++)
{
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;
}
if (ret->data == NULL)
{
+ index_type alloc_size;
+
rs = 1;
for (n = 0; n < rdim; n++)
{
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;
}
if (ret->data == NULL)
{
+ index_type alloc_size;
+
rs = 1;
for (n = 0; n < rdim; n++)
{
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;
}