[Bug fortran/115700] New: [10/11/12/13/14 regression] Bogus warning for associate with assumed-length character array

2024-06-28 Thread zed.three at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=115700

Bug ID: 115700
   Summary: [10/11/12/13/14 regression] Bogus warning for
associate with assumed-length character array
   Product: gcc
   Version: 10.4.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: zed.three at gmail dot com
  Target Milestone: ---

The following MVCE has a bogus "used uninitialised" warning from the associate
variable "tmp":

subroutine mvce(x)
  implicit none
  character(len=*), dimension(:), intent(in) :: x
  associate(tmp=>x) ! Bogus warning here
  end associate
end subroutine mvce

Compile with `-Wuninitialized`

(in action on Compiler Explorer: https://godbolt.org/z/hjafKaGsd)

This works on 10.3 and 11.2, with the warning appearing in 10.4 and 11.3
onwards.

Possibly related to PR fortran/104228 ?

[Bug fortran/111880] [9/10/11/12/13] False positive warning of obsolescent COMMON block with Fortran submodule

2023-10-19 Thread zed.three at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=111880

--- Comment #2 from zed.three at gmail dot com ---
The common block is in 'third_party_module', rather than 'foo', unless you mean
that it is visible from 'foo'? It is still a surprising warning in this
location at any rate!

[Bug fortran/111880] New: [9/10/11/12/13] False positive warning of obsolescent COMMON block with Fortran submodule

2023-10-19 Thread zed.three at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=111880

Bug ID: 111880
   Summary: [9/10/11/12/13] False positive warning of obsolescent
COMMON block with Fortran submodule
   Product: gcc
   Version: 13.2.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: zed.three at gmail dot com
  Target Milestone: ---

Created attachment 56152
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=56152=edit
Minimal source code demonstrating issue.

Compiler Explorer link with complete reproducer:
https://godbolt.org/z/dd45enhWe

  module third_party_module
integer :: some_param
common /not_my_code/ some_param
  end module third_party_module

  module foo
use third_party_module
interface
  module subroutine bar()
  end subroutine bar
end interface
  end module foo

  submodule (foo) foo_submod
  contains
module procedure bar
end procedure bar
  end submodule foo_submod


Compiling the above minimal program like:

  gfortran -std=f2018 -c foo.f90


gives the following warnings:

  foo.f90:3:22:

  3 |   common /not_my_code/ some_param
|  1
  Warning: Fortran 2018 obsolescent feature: COMMON block at (1)
  foo.f90:14:14:

 14 | submodule (foo) foo_submod
|  1
  Warning: Fortran 2018 obsolescent feature: COMMON block at (1)


The first warning is expected, but the second one is a false positive. I came
across this when building with a library outside of my control, so I cannot
remove the problem common block (actually this was with MPI, and it happens
with all the major implementations as the common block is required for
technical reasons).


If the submodule is removed, the extra warning disappears. The warning also
appears when building the submodule separately (in a different file and having
already built the parent module).

It also only appears to be this warning, and not other F2018 obsolescent
feature warnings (e.g. labeled DO statements), or other warnings enabled at
`-Wall` for instance.

[Bug fortran/110585] New: ICE in gfc_compare_expr for findloc with complex literal array

2023-07-07 Thread zed.three at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110585

Bug ID: 110585
   Summary: ICE in gfc_compare_expr for findloc with complex
literal array
   Product: gcc
   Version: 9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: zed.three at gmail dot com
  Target Milestone: ---

Created attachment 55497
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=55497=edit
MVCE for findloc ICE with complex literal array

The following MVCE gives an ICE in gfortran 9-13 and trunk:


program mvce
  implicit none
  print*,findloc([(1.0,0.0), (2.0,1.0)], (2.0,0.0))
end program mvce


Backtrace on trunk:


f951: internal compiler error: gfc_compare_expr(): Bad basic type
0xa1a997 gfc_internal_error(char const*, ...)
???:0
0x9e0cff gfc_compare_expr(gfc_expr*, gfc_expr*, gfc_intrinsic_op)
???:0
0xaba5a9 gfc_simplify_findloc(gfc_expr*, gfc_expr*, gfc_expr*, gfc_expr*,
gfc_expr*, gfc_expr*)
???:0
0xa3ab0a gfc_intrinsic_func_interface(gfc_expr*, int)
???:0
0xa9be0b gfc_resolve_code(gfc_code*, gfc_namespace*)
???:0
0xa9a9ab gfc_resolve_blocks(gfc_code*, gfc_namespace*)
???:0
0xa9ac97 gfc_resolve_code(gfc_code*, gfc_namespace*)
???:0
0xa84f30 gfc_parse_file()
???:0


Compiler Explorer reproducer: https://godbolt.org/z/bdsehGfxc

Changing the first argument to a variable (that is, not a literal array), or
changing the type of the elements and needle to real or integer works fine.

[Bug fortran/110288] New: [11/12/13] Regression: segfault in findloc with allocatable array of allocatable characters

2023-06-16 Thread zed.three at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110288

Bug ID: 110288
   Summary: [11/12/13] Regression: segfault in findloc with
allocatable array of allocatable characters
   Product: gcc
   Version: 11.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: zed.three at gmail dot com
  Target Milestone: ---

Created attachment 55350
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=55350=edit
Minimal example source code

The following program crashes with a segfault "invalid memory reference" inside
`findloc`:

  program test
character(len=:), allocatable, dimension(:) :: array
array = ["bb", "bb"]
print*, findloc(array, "aa", dim=1)
  end program

Compiler Explorer example: https://godbolt.org/z/Evrnose5o

The same program works in gfortran 10.4, crashes in 11+, including trunk (GNU
Fortran
(Compiler-Explorer-Build-gcc-7ff793415f55fa9a92f348fecb8c75ac8acc8b87-binutils-2.40)
14.0.0 20230616 (experimental)).

A minimum of two elements in the array are required, and it must be
allocatable, but it doesn't matter if the element is in `array` or not.

[Bug libstdc++/109568] [12/13/14 Regression] Spurious "potential null pointer dereference" in shared_ptr_base.h with "-O1"

2023-04-20 Thread zed.three at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109568

--- Comment #5 from zed.three at gmail dot com ---
Ah ok, I see the whole thing now. It still feels like a confusing warning, but
it seems reasonable that there isn't much that can be done about it.

[Bug libstdc++/109568] [12/13/14 Regression] Spurious "potential null pointer dereference" in shared_ptr_base.h with "-O1"

2023-04-20 Thread zed.three at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109568

--- Comment #3 from zed.three at gmail dot com ---
Ah, I see what you mean. Putting in a guard clause

if (!var_ref) return false;

does indeed silence the warning.

But should the warning not be on the `var_ref->empty()` call itself then,
instead of inside `shared_ptr::operator==`? I guess that it's ultimately
triggered by the implicit `this` in accessing `_M_ptr`, but it would be more
obvious it it were bubbled up to `var_ref`

[Bug libstdc++/109568] New: [12/13 Regression] Spurious "potential null pointer dereference" in shared_ptr_base.h with "-O1"

2023-04-20 Thread zed.three at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109568

Bug ID: 109568
   Summary: [12/13 Regression] Spurious "potential null pointer
dereference" in shared_ptr_base.h with "-O1"
   Product: gcc
   Version: 12.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: libstdc++
  Assignee: unassigned at gcc dot gnu.org
  Reporter: zed.three at gmail dot com
  Target Milestone: ---

The following MVCE gives a warning about a potential null dereference in
operator== in shared_ptr_base.h:


#include 

struct Base {
virtual ~Base() = default;
bool empty() { return ptr == nullptr; }
std::shared_ptr ptr{nullptr};
};

struct Derived : public Base {};

bool empty(Base* var) {
auto* var_ref = dynamic_cast(var);
if (var_ref->empty()) return false;
return true;
}

Compiler Explorer link: https://godbolt.org/z/Tqrdo61Ks

Warning:

  In file included from
/opt/compiler-explorer/gcc-12.2.0/include/c++/12.2.0/bits/shared_ptr.h:53,
   from
/opt/compiler-explorer/gcc-12.2.0/include/c++/12.2.0/memory:77,
   from :1:
  In member function 'std::__shared_ptr<_Tp, _Lp>::operator bool() const [with
_Tp = int; __gnu_cxx::_Lock_policy _Lp = __gnu_cxx::_S_atomic]',
  inlined from 'bool std::operator==(const shared_ptr<_Tp>&, nullptr_t)
[with _Tp = int]' at
/opt/compiler-explorer/gcc-12.2.0/include/c++/12.2.0/bits/shared_ptr.h:562:14,
  inlined from 'bool Base::empty() const' at :5:46,
  inlined from 'bool empty(Base*)' at :12:23:
 
/opt/compiler-explorer/gcc-12.2.0/include/c++/12.2.0/bits/shared_ptr_base.h:1670:16:
error: potential null pointer dereference [-Werror=null-dereference]
   1670 |   { return _M_ptr != nullptr; }
|   

This requires at least -O1 and appears in GCC 12.1 onwards. The `dynamic_cast`
also appears to be necessary, as `std::shared_ptr{nullptr} == nullptr`
doesn't trigger the warning.

[Bug fortran/105658] New: Passing array component to unlimited polymorphic routine passes wrong slice

2022-05-19 Thread zed.three at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=105658

Bug ID: 105658
   Summary: Passing array component to unlimited polymorphic
routine passes wrong slice
   Product: gcc
   Version: 12.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: zed.three at gmail dot com
  Target Milestone: ---

The following program:

program f
implicit none

type :: foo
integer :: member1
integer :: member2
end type foo

type(foo), dimension(3) :: thing = [foo(1, 2), foo(3, 4), foo(5, 6)]

call print_poly(thing%member1)
call print_int(thing%member1)

contains
subroutine print_poly(array)
class(*), dimension(:), intent(in) :: array

select type(array)
type is (integer)
print*, array
end select
end subroutine

subroutine print_int(array)
integer, dimension(:), intent(in) :: array

print*, array
end subroutine
end program f

prints:

   1   2   3
   1   3   5

when we would expect:

   1   3   5
   1   3   5

Adding `-fcheck=all`, we get the warning "Fortran runtime warning: An array
temporary was created" _only_ for the call to `print_int`.

Adding an extra set of parentheses to the `print_poly` call (`call
print_poly((thing%member1))` gives the expected behaviour, I guess because it's
forcing an array temporary?

This behaviour is present in 4.9.4 through to the trunk currently available on
Compiler Explorer
((Compiler-Explorer-Build-gcc-7da9a089608b0ca09683332ce014fb6184842724-binutils-2.38)
13.0.0 20220518 (experimental))

[Bug fortran/91300] Wrong runtime error message with allocate and errmsg=

2019-07-31 Thread zed.three at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=91300

--- Comment #2 from zed.three at gmail dot com ---
Forgive me, but what is stupid here? The perceived wisdom is that it is best
practice to always use `stat` with `allocate`, and the addition of `errmsg` now
gives us something portable to hopefully get a sensible error message.
Unfortunately, the error message is not correct here.

If you mean trying to allocate a 1D array that is huge(1) -- this is just a
large enough value that it's likely to fail due to not enough memory on most
machines, as it's about 17GB. A 5D array of real64s of size 64x64x64x64x64 is
8GB, which is definitely not an unrealistic size. That's only 2x10^9 points.

I'm certainly not saying this is a show-stopper, but I don't think it's at all
stupid to expect useful error messages.

[Bug fortran/91300] New: Wrong runtime error message with allocate and errmsg=

2019-07-30 Thread zed.three at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=91300

Bug ID: 91300
   Summary: Wrong runtime error message with allocate and errmsg=
   Product: gcc
   Version: 9.1.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: zed.three at gmail dot com
  Target Milestone: ---

Created attachment 46644
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=46644=edit
MVCE for wrong runtime error message from allocate

The following two allocates give different error messages:

use, intrinsic :: iso_fortran_env, only : real64, int64
integer(int64), parameter :: bignumber = huge(1) * 2
real(real64), allocatable :: bigarray(:)

allocate(bigarray(bignumber))
allocate(bigarray(bignumber), stat=stat, errmsg=errmsg)

The first `allocate` terminates with the following message:

Operating system error: Cannot allocate memory
Allocation would exceed memory limit

(followed by a backtrace). The second `allocate` puts the following in
`errmsg`:

Attempt to allocate an allocated object

which is not correct.

I've attached a full MVCE. Uncomment line 10 to see the correct error message.

Also note that if you do attempt to allocate an allocated object, the value of
`stat` is the same as if you attempted to allocate too much memory, but from
looking in trans.c and trans-stmt.c, I think that is a separate issue.

[Bug fortran/80477] [OOP] Polymorphic function result generates memory leak

2018-12-16 Thread zed.three at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=80477

zed.three at gmail dot com changed:

   What|Removed |Added

 CC||zed.three at gmail dot com

--- Comment #26 from zed.three at gmail dot com ---
Thank you for looking at the finalisation stuff, Paul, it's really appreciated!

It wasn't clear to me from the patch notes if you expect the following to be
fixed:

  subroutine assign_a_type(lhs, rhs)
class(a_type_t), intent(inout) :: lhs
class(a_type_t), intent(in):: rhs
lhs%x = rhs%x
  end subroutine assign_a_type

or 

  class(a_type_t), allocatable :: c
  c = add_a_type(a, b)

These still generate memory leaks (detected using -fsanitize=address)

I'm using trunk (r267184, git bf96f3)

I've been trying to dig into the code myself, mostly as a learning exercise. Am
I right in thinking that gfc_conv_procedure_call handles the whole statement?
i.e. that finalisation both of the lhs and function result are (or should be)
done here?

[Bug c++/86025] New: ICE with -Wduplicated-branches and OpenMP critical

2018-06-01 Thread zed.three at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86025

Bug ID: 86025
   Summary: ICE with -Wduplicated-branches and OpenMP critical
   Product: gcc
   Version: 8.0.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: c++
  Assignee: unassigned at gcc dot gnu.org
  Reporter: zed.three at gmail dot com
  Target Milestone: ---

Created attachment 44221
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=44221=edit
Preprocessed output

Compiling the following MVCE with "-Wduplicated-branches -fopenmp" causes an
ICE.
I've checked with 7.3.1 and 8.0.1. It's very similar to 79672, but with a
different pragma.
Dropping "(foo)" makes the ICE go away.

#include 

void foo() {
  if (false) {
#pragma omp parallel
#pragma omp critical (foo)
if (false) {
}
  }
}

Output:

Using built-in specs.
COLLECT_GCC=g++-8
OFFLOAD_TARGET_NAMES=hsa:nvptx-none
Target: x86_64-suse-linux
Configured with: ../configure --prefix=/usr --infodir=/usr/share/info
--mandir=/usr/share/man --libdir=/usr/lib64 --libexecdir=/usr/lib64
--enable-languages=c,c++,objc,fortran,obj-c++,ada,go
--enable-offload-targets=hsa,nvptx-none=/usr/nvptx-none, --without-cuda-driver
--enable-checking=release --disable-werror
--with-gxx-include-dir=/usr/include/c++/8 --enable-ssp --disable-libssp
--disable-libvtv --disable-cet --disable-libcc1 --enable-plugin
--with-bugurl=http://bugs.opensuse.org/ --with-pkgversion='SUSE Linux'
--with-slibdir=/lib64 --with-system-zlib --enable-__cxa_atexit
--enable-libstdcxx-allocator=new --disable-libstdcxx-pch
--enable-version-specific-runtime-libs --with-gcc-major-version-only
--enable-linker-build-id --enable-linux-futex --enable-gnu-indirect-function
--program-suffix=-8 --without-system-libunwind --enable-multilib
--with-arch-32=x86-64 --with-tune=generic --build=x86_64-suse-linux
--host=x86_64-suse-linux
Thread model: posix
gcc version 8.0.1 20180425 (prerelease) [gcc-8-branch revision 259638] (SUSE
Linux) 
COLLECT_GCC_OPTIONS='-v' '-save-temps' '-c' '-Wduplicated-branches' '-fopenmp'
'-shared-libgcc' '-mtune=generic' '-march=x86-64' '-pthread'
 /usr/lib64/gcc/x86_64-suse-linux/8/cc1plus -E -quiet -v -D_GNU_SOURCE
-D_REENTRANT gcc_crash.cxx -mtune=generic -march=x86-64 -Wduplicated-branches
-fopenmp -fpch-preprocess -o gcc_crash.ii
#include "..." search starts here:
#include <...> search starts here:
 /usr/include/c++/8
 /usr/include/c++/8/x86_64-suse-linux
 /usr/include/c++/8/backward
 /usr/lib64/gcc/x86_64-suse-linux/8/include
 /usr/local/include
 /usr/lib64/gcc/x86_64-suse-linux/8/include-fixed
 /usr/lib64/gcc/x86_64-suse-linux/8/../../../../x86_64-suse-linux/include
 /usr/include
End of search list.
COLLECT_GCC_OPTIONS='-v' '-save-temps' '-c' '-Wduplicated-branches' '-fopenmp'
'-shared-libgcc' '-mtune=generic' '-march=x86-64' '-pthread'
 /usr/lib64/gcc/x86_64-suse-linux/8/cc1plus -fpreprocessed gcc_crash.ii -quiet
-dumpbase gcc_crash.cxx -mtune=generic -march=x86-64 -auxbase gcc_crash
-Wduplicated-branches -version -fopenmp -o gcc_crash.s
GNU C++14 (SUSE Linux) version 8.0.1 20180425 (prerelease) [gcc-8-branch
revision 259638] (x86_64-suse-linux)
compiled by GNU C version 8.0.1 20180425 (prerelease) [gcc-8-branch
revision 259638], GMP version 6.1.2, MPFR version 4.0.1-p6, MPC version 1.1.0,
isl version isl-0.19-GMP

GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
GNU C++14 (SUSE Linux) version 8.0.1 20180425 (prerelease) [gcc-8-branch
revision 259638] (x86_64-suse-linux)
compiled by GNU C version 8.0.1 20180425 (prerelease) [gcc-8-branch
revision 259638], GMP version 6.1.2, MPFR version 4.0.1-p6, MPC version 1.1.0,
isl version isl-0.19-GMP

GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
Compiler executable checksum: ca1e18c23ccd29ea8279af847a2b27d0
gcc_crash.cxx: In function ‘void foo()’:
gcc_crash.cxx:10:1: internal compiler error: in add_expr, at tree.c:7417
 }
 ^
Please submit a full bug report,
with preprocessed source if appropriate.
See <http://bugs.opensuse.org/> for instructions.

[Bug fortran/80392] New: ICE with allocatable polymorphic function result in a procedure pointer component

2017-04-11 Thread zed.three at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=80392

Bug ID: 80392
   Summary: ICE with allocatable polymorphic function result in a
procedure pointer component
   Product: gcc
   Version: 7.0.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: zed.three at gmail dot com
  Target Milestone: ---

Very similar to https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68196
and https://gcc.gnu.org/bugzilla/show_bug.cgi?id=56385
but making the function result polymorphic:

module mwe

  implicit none

  type :: MyType
 procedure(my_op), nopass, pointer :: op
  end type MyType

  abstract interface
 function my_op() result(foo)
   import
   class(MyType), allocatable :: foo
 end function my_op
 ! Replacing with subroutine works
 ! subroutine my_op(foo)
 !   import :: MyType
 !   class(MyType), allocatable :: foo
 ! end subroutine my_op
  end interface

contains

  subroutine bad_sub(op)
procedure(my_op) :: op
  end subroutine bad_sub

end module mwe

With gfortran 4.8.5, 5.4.1, and 6.2.1, I get the following error (which I think
might be wrong as well?):

mwe.f90:23:23:

   subroutine bad_sub(op)
   1
Error: CLASS variable ‘op’ at (1) must be dummy, allocatable or pointer

With gfortran 7.0.1, I get an ICE:

gfortran-7: internal compiler error: Segmentation fault (program f951)

I also get an ICE with 5.4.1 and 6.2.1 (but not 4.8.5) if I remove the
`bad_sub` implementation.

Changing the interface to the commented-out subroutine instead of a function,
and everything works. Also, changing foo to be a pointer rather than
allocatable makes the ICE go away.

[Bug fortran/71623] [5/6/7 Regression] Segfault when allocating deferred-length characters to size of a pointer

2016-06-24 Thread zed.three at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=71623

--- Comment #3 from zed.three at gmail dot com ---
Changing the pointer to an allocatable array results in the same behaviour:

$ cat allocate_size_mvce.f90
program allocatemvce
  implicit none
  character(len=:), allocatable :: string
  integer, dimension(4), target :: array = [1,2,3,4]
  integer, dimension(:), allocatable :: array_alloc
  integer :: alloc_size

  allocate(array_alloc(size(array)))
  allocate(character(len=size(array_alloc))::string)

  ! The following works:
  ! alloc_size = size(array_alloc)
  ! allocate(character(len=alloc_size)::string)

end program allocatemvce

---

In both cases, using -fdump-tree-original to see the IR reveals the
uninitialised variable:

1) For gfortran-4.8, we have something like this:

D.1892 = _ptr;
D.1893 = (integer(kind=4)) MAX_EXPR <(D.1892->dim[0].ubound -
D.1892->dim[0].lbound) + 1, 0>;
...
D.1894 = (unsigned long) D.1893;
string = (character(kind=1)[1:.string] *) __builtin_malloc (MAX_EXPR
<D.1894, 1>);

2) Whereas for gfortran-6, we get:

struct array1_integer(kind=4) * D.3395;
...
D.3396 = (unsigned long) (integer(kind=4)) MAX_EXPR
<(D.3395->dim[0].ubound - D.3395->dim[0].lbound) + 1, 0>;
string = (character(kind=1)[1:.string] *) __builtin_malloc (MAX_EXPR
<D.3396, 1>);

   and D.3395 is never assigned to.

---

When using "product(shape)", as in Gerhard's example, examining the IR shows
that product(shape(array_ptr)) is never calculated in gfortran-6:

1) For gfortran-4.8, we can see:
_gfortran_shape_4 (, D.1893);
{
  integer(kind=8) S.3;

  S.3 = 0;
  while (1)
{
  if (S.3 > 0) goto L.1;
  val.0 = (*(integer(kind=4)[1] * restrict) atmp.1.data)[S.3] *
val.0;
  S.3 = S.3 + 1;
}
  L.1:;
}
   which is clearly calculating product(shape(array_ptr))

2) For gfortran-6, nothing like that appears at all, and __builtin_malloc is
called with val.0 uninitialised.

---

Replacing "size(array_ptr)" in the original example with "mysize(array_ptr)",
which is defined as

  integer function mysize(ptr)
integer, dimension(:), pointer :: ptr
mysize = size(ptr)
  end function mysize

This results in the correct behaviour. In the IR for 6, we essentially get

  string = (character(kind=1)[1:.string] *) __builtin_malloc (MAX_EXPR
<(unsigned long) mysize (_ptr), 1>);

---

Finally, if we replace "size(array_ptr)" with "size(array)", the IR is

  string = (character(kind=1)[1:.string] *) __builtin_malloc (4);

and no intermediate variables are generated (i.e. it directly uses the value of
size(array)).

---

My best guess then is that in gfortran > 5 calls to intrinsics are being elided
in allocating deferred-len characters. That's just a guess though. I'm
currently trying to get my bearings in the gfortran source code to understand
what's going on.

[Bug fortran/71623] New: Segfault when allocating deferred-length characters to size of a pointer

2016-06-22 Thread zed.three at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=71623

Bug ID: 71623
   Summary: Segfault when allocating deferred-length characters to
size of a pointer
   Product: gcc
   Version: 6.1.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: zed.three at gmail dot com
  Target Milestone: ---

Created attachment 38748
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=38748=edit
MVCE for allocation bug

When running the attached MVCE with gfortran 5.4.0 and 6.1.1 (20160615
[gcc-6-branch revision 237474]), there's a segfault on the line:

 allocate(character(len=size(array_ptr))::string)

but not on

 allocate(character(len=size(array))::string)

or

 allocate(character(len=ptr_size)::string)

where array_ptr => array, and ptr_size = size(array_ptr).

This works in 4.9.0 and 4.8.3, as well as ifort 14.