[Bug fortran/103970] New: Multi-image co_broadcast of derived type with allocatable components fails

2022-01-10 Thread damian at sourceryinstitute dot org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103970

Bug ID: 103970
   Summary: Multi-image co_broadcast of derived type with
allocatable components fails
   Product: gcc
   Version: 11.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

Using gfortran 11.2.0 installed by Homebrew on macOS 12.0.1 to compile the code
below and link against OpenCoarrays 2.9.2 built with MPICH 3.2.0 results in
printing "Test failed." when executed in multiple images.

  implicit none

  type foo_t
integer i
integer, allocatable :: j
  end type

  type(foo_t) foo
  integer, parameter :: source_image = 1

  if (this_image() == source_image)  then
foo = foo_t(2,3)
  else
allocate(foo%j)
  end if
  call co_broadcast(foo, source_image)

  if ((foo%i /= 2) .or. (foo%j /= 3))  error stop "Test failed."
  sync all
  print *, "Test passed."

end

This bug is also summarized in OpenCoarrays issue 727 at
https://github.com/sourceryinstitute/OpenCoarrays/issues/727, where Andre
Vehreschild confirms that the problem is a compiler bug.

[Bug fortran/103054] New: [f18] Gfortran accepts invalid and rejects valid co_reduce argument keyword name

2021-11-02 Thread damian at sourceryinstitute dot org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103054

Bug ID: 103054
   Summary: [f18] Gfortran accepts invalid and rejects valid
co_reduce argument keyword name
   Product: gcc
   Version: 11.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

In TS 18508, the second summy argument to co_reduce had the keyword name
"operator."  In the Fortran 2018 standard, the corresponding argument has the
name "operation."  GFortran accepts the non-standard keyword argument name
"operator" and rejects the standard name "operation."

% cat co_reduce.f90 
  implicit none
  logical :: co_all= .true.
  call co_reduce(co_all, operator=both)
  call co_reduce(co_all, operation=both)
contains
  logical pure function both(lhs,rhs)
logical, intent(in) :: lhs, rhs
both = lhs .and. rhs
  end function
end

⌁74% [rouson:~] % gfortran -fcoarray=single co_reduce.f90 
co_reduce.f90:4:40:

4 |   call co_reduce(co_all, operation=both)
  |1
Error: Cannot find keyword named 'operation' in call to 'co_reduce' at (1)
% gfortran --version
GNU Fortran (Homebrew GCC 11.2.0) 11.2.0

[Bug fortran/98897] Erroneous procedure attribute for associate name

2021-02-22 Thread damian at sourceryinstitute dot org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=98897

--- Comment #8 from Damian Rouson  ---
Thanks, Paul and Tobias!

[Bug fortran/98897] Erroneous procedure attribute for associate name

2021-02-02 Thread damian at sourceryinstitute dot org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=98897

--- Comment #3 from Damian Rouson  ---
Thanks for the quick fix, Paul!   Any chance of this being back-ported to the
10 branch?

[Bug fortran/98897] New: Erroneous procedure attribute for associate name

2021-01-29 Thread damian at sourceryinstitute dot org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=98897

Bug ID: 98897
   Summary: Erroneous procedure attribute for associate name
   Product: gcc
   Version: 11.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

The behavior demonstrated below also occurs if the procedure definition is
moved to a submodule.  Workarounds include (1) declaring "output_data" as a
variable instead of an associate name or (2) making "output" a function
referencing it as such instead of calling it as a subroutine.

% cat bug.f90 
module output_data_m
  implicit none

  type output_data_t
  contains
procedure output
  end type

  interface
module subroutine output(self)
  implicit none
  class(output_data_t) self
end subroutine
  end interface

contains
  module procedure output
  end procedure
end module

  use output_data_m
  implicit none
  associate(output_data => output_data_t())
call output_data%output
  end associate
end

% gfortran bug.f90
bug.f90:24:20:

   24 | call output_data%output
  |1
Error: VARIABLE attribute of ‘output_data’ conflicts with PROCEDURE attribute
at (1)

% gfortran --version
GNU Fortran (GCC) 11.0.0 20201231 (experimental)

[Bug fortran/98253] Conflicting random_seed/random_init results

2020-12-12 Thread damian at sourceryinstitute dot org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=98253

Damian Rouson  changed:

   What|Removed |Added

 Resolution|--- |FIXED
 Status|WAITING |RESOLVED

--- Comment #8 from Damian Rouson  ---
Steve, one more question.  How do you interpret the second sentence in the text
that I originally quoted: "In each execution of the program with the same
execution environment, if the invoking image index value in the initial team is
the same, the value for PUT shall be the same."  This is in 16.9.155 Case (i)
describing the relationship between random_init and random_seed.  I originally
interpreted this quote to mean that each image would use the same seed each
time the program runs, which would be a constraint on the PRNG.  I'm now
thinking that the reference to PUT implies that the user is setting the seed
and this is saying that the program must set the same seed each a given image
executes, but that seems like an odd constraint so I'm probably still horribly
confused.  Feel free to mark this issue as invalid if this is starting to seem
like a waste of time.  I'm just trying to understand.

Either way, an image number is defined for all programs whether or not there
are coarrays anywhere in the program and whether or not the program is ever
executed in multiple images -- for example, this_image() is just an intrinsic
function rather than a (hypothetical) "coarray" intrinsic function.  This point
is most meaningful with a compiler like the Cray compiler, which requires no
special flags to compile a program that invokes this_image().  In some sense,
all Fortran programs are now parallel programs whether the user takes advantage
of that fact in any explicit way or not. I suspect that's the reason that
IMAGE_DISTINCT is not optional. Possibly the committee deemed it better to
require users to specify the desired behavior in multi-image execution. Even
libraries that were never designed in any way to exploit parallelism can be
linked into parallel programs so it seems better to have developers of such a
library specify the desired behavior if their code is ultimately linked into a
parallel program -- analogous to requiring that code be thread-safe even if the
code makes no explicit use of multi-threading.

[Bug fortran/98253] Conflicting random_seed/random_init results

2020-12-12 Thread damian at sourceryinstitute dot org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=98253

--- Comment #7 from Damian Rouson  ---
I agree that it would have been better for image_distinct to be optional.  I
co-hosted the 2018 WG5 meeting at which there were lengthy discussions around
random number generation.  I don't recall whether making that argument optional
was discussed.  I assume it wouldn't break any existing code to make it
optional in a future standard.

[Bug fortran/98253] Conflicting random_seed/random_init results

2020-12-12 Thread damian at sourceryinstitute dot org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=98253

--- Comment #5 from Damian Rouson  ---
Steve, thanks for all the time you put into implementing random_init and
responding to this PR.  My confusion stemmed from the first sentence that I
quoted from the standard. It states that the provided random_init call is
equivalent to a processor-dependent random_seed call so I was attempting to
replace my two random_seed calls with one random_init call. I see now that such
a replacement only works if one knows the correct, processor-dependent seed
values, but I also understand now that it would be pointless to do what I'm
trying to do.  Because the matching seeds would be processor-dependent, the
code wouldn't be portable. 

On a related note, I've been trying over time to evolve away from using
"coarray" as the blanket term for all parallel features.  Fortran now has so
many parallel features that don't necessarily involve coarrays. The
IMAGE_DISTINCT argument is one small example so I don't think IMAGE_DISTINCT
necessarily has anything to do with coarrays, but it does have to do with
multi-image execution.

[Bug fortran/98253] New: Conflicting random_seed/random_init results

2020-12-12 Thread damian at sourceryinstitute dot org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=98253

Bug ID: 98253
   Summary: Conflicting random_seed/random_init results
   Product: gcc
   Version: 11.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

16.9.155 Case (i) in the Fortran 2018 standard states

  CALL RANDOM_INIT (REPEATABLE=true, IMAGE_DISTINCT=true) is equivalent to  
  invoking RANDOM_SEED with a processor-dependent value for PUT that is 
  different on every invoking image. In each execution of the program with 
  the same execution environment, if the invoking image index value in the 
  initial team is the same, the value for PUT shall be the same.

but the two programs below give different results.

% cat random_init.f90
  implicit none
  integer i
  real r
  call random_init(repeatable=.true., image_distinct=.true.)
  do i=1,5
call random_number(r)
print *,r 
  end do
end

% cat random_seed.f90 
  implicit none
  integer i, n
  real r
  call random_seed(size=n)
  call random_seed(put=[(i,i=1,n)])
  do i=1,5
call random_number(r)
print *,r 
  end do
end

% /usr/local/Cellar/gnu/11.0.0/bin/gfortran random_init.f90
% ./a.out
  0.731217086
  0.652637541
  0.381399393
  0.817764997
  0.394176722

% /usr/local/Cellar/gnu/11.0.0/bin/gfortran random_seed.f90 
% ./a.out
  0.471070886
  0.117344737
  0.357547939
  0.318134785
  0.696753800

% /usr/local/Cellar/gnu/11.0.0/bin/gfortran --version
GNU Fortran (GCC) 11.0.0 20200804 (experimental)

[Bug fortran/97864] Homebrew Operator Overload ICE

2020-11-19 Thread damian at sourceryinstitute dot org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=97864

--- Comment #4 from Damian Rouson  ---
The above reduced version produces an ICE with gfortran 11.0.0 2020815 built
from source so this is not specific to Homebrew but is specific to macOS.

[Bug fortran/97864] Homebrew Operator Overload ICE

2020-11-19 Thread damian at sourceryinstitute dot org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=97864

Damian Rouson  changed:

   What|Removed |Added

 CC||damian at sourceryinstitute 
dot or
   ||g

--- Comment #3 from Damian Rouson  ---
Here's a reduced version of the original code, still causing an ICE:

implicit none

type VARYING_STRING
character(len=1), allocatable :: characters(:)
end type

interface operator(==)
procedure character_EQ_String
end interface

print *, stringToChar(var_str("Hello")) == var_str("World") ! causes ice

contains
logical function character_EQ_String(lhs, rhs)
character(len=*), intent(in) :: lhs
type(VARYING_STRING), intent(in) :: rhs
character_EQ_String = lhs == stringToChar(rhs)
end function

function stringToChar(string)
type(VARYING_STRING) string
character(len=size(string%characters)) :: stringToChar
stringToChar = ""
end function

type(VARYING_STRING) function VAR_STR(char)
character(len=*) char
integer i
VAR_STR%characters = [(char(i:i), i = 1, len(char))]
end function
end

[Bug fortran/86117] bogus warning maybe-uninitialized with class(*) and source argument in allocate

2020-09-30 Thread damian at sourceryinstitute dot org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86117

Damian Rouson  changed:

   What|Removed |Added

 CC||damian at sourceryinstitute 
dot or
   ||g

--- Comment #5 from Damian Rouson  ---
Below is an example without the polymorphism employed in the original
submission.  In gfortran 11, the warnings and notes now total 70 lines stemming
from a single executable line.  In my opinion, this volume renders -Wall nearly
unusable because of the time it can take to sift out the truly useful
information from the spurious information.

± cat copious-warnings.f90 
module results_interface
  type results_t
real, allocatable :: output(:)
  end type
contains
  subroutine max_filtered_normalized_distance(rhs)
type(results_t) rhs
real, allocatable :: rhs_filtered(:)
rhs_filtered = rhs%output
  end subroutine
end module

± gfortran -c -Wall copious-warnings.f90 
copious-warnings.f90:9:0:

9 | rhs_filtered = rhs%output
  | 
Warning: ‘rhs_filtered.offset’ is used uninitialized [-Wuninitialized]
copious-warnings.f90:8:40:

8 | real, allocatable :: rhs_filtered(:)
  |^
note: ‘rhs_filtered’ declared here
copious-warnings.f90:9:0:

9 | rhs_filtered = rhs%output
  | 
Warning: ‘rhs_filtered.dim[0].lbound’ is used uninitialized [-Wuninitialized]
copious-warnings.f90:8:40:

8 | real, allocatable :: rhs_filtered(:)
  |^
note: ‘rhs_filtered’ declared here
copious-warnings.f90:9:0:

9 | rhs_filtered = rhs%output
  | 
Warning: ‘rhs_filtered.dim[0].ubound’ is used uninitialized [-Wuninitialized]
copious-warnings.f90:8:40:

8 | real, allocatable :: rhs_filtered(:)
  |^
note: ‘rhs_filtered’ declared here
copious-warnings.f90:9:0:

9 | rhs_filtered = rhs%output
  | 
Warning: ‘rhs_filtered.dim[0].lbound’ may be used uninitialized
[-Wmaybe-uninitialized]
copious-warnings.f90:8:40:

8 | real, allocatable :: rhs_filtered(:)
  |^
note: ‘rhs_filtered’ declared here
copious-warnings.f90:9:0:

9 | rhs_filtered = rhs%output
  | 
Warning: ‘rhs_filtered.dim[0].ubound’ may be used uninitialized
[-Wmaybe-uninitialized]
copious-warnings.f90:8:40:

8 | real, allocatable :: rhs_filtered(:)
  |^
note: ‘rhs_filtered’ declared here
copious-warnings.f90:9:0:

9 | rhs_filtered = rhs%output
  | 
Warning: ‘rhs_filtered.dim[0].ubound’ may be used uninitialized
[-Wmaybe-uninitialized]
copious-warnings.f90:8:40:

8 | real, allocatable :: rhs_filtered(:)
  |^
note: ‘rhs_filtered’ declared here
copious-warnings.f90:9:0:

9 | rhs_filtered = rhs%output
  | 
Warning: ‘rhs_filtered.dim[0].lbound’ may be used uninitialized
[-Wmaybe-uninitialized]
copious-warnings.f90:8:40:

8 | real, allocatable :: rhs_filtered(:)
  |^
note: ‘rhs_filtered’ declared here

± gfortran --version
GNU Fortran (GCC) 11.0.0 20200804 (experimental)

[Bug fortran/97037] New: ICE on user-defined derived-type output of an intermediate ancestor type

2020-09-12 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=97037

Bug ID: 97037
   Summary: ICE on user-defined derived-type output of an
intermediate ancestor type
   Product: gcc
   Version: 11.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

The code below effectively has an abstract parent type ("object"), abstract
child type ("oracle"), and a non-abstract grandchild type ("results_t") in
which the parent has a derived-type output binding, the child has a type-bound
operator(-) associated with a deferred binding ("negative"), and the grandchild
implements both deferred bindings.  An ICE results when attempting to write the
result of the operator.  Presumably the issue is that the grandchild's operator
result must be of the child type.  The child type inherits the derived-type
output binding from the parent, but it doesn't itself explicitly state such a
binding. I lean toward thinking the code is valid, but I haven't yet consulted
the standard.

$ cat uddtio-ice.f90 
module object_interface
  implicit none

  type, abstract :: object
  contains
procedure(write_formatted_interface), deferred :: write_formatted
generic :: write(formatted) => write_formatted
  end type

  abstract interface
subroutine write_formatted_interface(this, unit, iotype, vlist, iostat,
iomsg)
  import object
  implicit none
  class(object), intent(in) :: this
  integer, intent(in) :: unit, vlist(:)
  character(len=*), intent(in) :: iotype
  integer, intent(out) :: iostat
  character(len=*), intent(inout) :: iomsg
end subroutine
  end interface

  type, abstract, extends(object) :: oracle
  contains
procedure(negative_interface), deferred :: negative
generic :: operator(-) => negative
  end type

  abstract interface
function negative_interface(this)
  import oracle
  implicit none
  class(oracle), intent(in) :: this
  class(oracle), allocatable :: negative_interface
end function
  end interface

  type, extends(oracle) :: results_t
  contains
procedure write_formatted
procedure negative
  end type

  interface
module subroutine write_formatted(this, unit, iotype, vlist, iostat, iomsg)
  implicit none
  class(results_t), intent(in) :: this
  integer, intent(in) :: unit, vlist(:)
  character(len=*), intent(in) :: iotype
  integer, intent(out) :: iostat
  character(len=*), intent(inout) :: iomsg
end subroutine
module function negative(this)
  implicit none
  class(results_t), intent(in) :: this
  class(oracle), allocatable :: negative
end function
  end interface
end module

  use object_interface
  write(*,*) -results_t()
end program

$ gfortran -c uddtio-ice.f90 
uddtio-ice.f90:61:0:

   61 |   write(*,*) -results_t()
  | 
internal compiler error: Segmentation fault: 11

$ gfortran --version
GNU Fortran (GCC) 11.0.0 20200804 (experimental)

[Bug fortran/96320] gfortran 8-10 shape mismatch in assumed-length dummy argument character array

2020-08-20 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=96320

--- Comment #24 from Damian Rouson  ---
This appears to be another example of an issue with a module procedure defined
in the same module as its interface body. In this case, the compiler doesn't
recognize a reference to the procedure:

± cat subroutine-call.f90 
module hole_interface
  type hole_t
  contains
procedure set_user_defined
  end type

  interface
module subroutine set_diameter (this)
  class(hole_t) this
end subroutine

module subroutine set_user_defined(this)
  class(hole_t) this
end subroutine
  end interface

contains
  module procedure set_user_defined
  end procedure

  module procedure set_diameter
call this%set_user_defined
  end procedure
end module

  use hole_interface
end

± gfortran subroutine-call.f90 
subroutine-call.f90:26:6:

   26 |   use hole_interface
  |  1
Error: ‘set_user_defined’ must be a module procedure or an external procedure
with an explicit interface at (1)

± gfortran --version
GNU Fortran (GCC) 11.0.0 20200804 (experimental)

[Bug fortran/96320] gfortran 8-10 shape mismatch in assumed-length dummy argument character array

2020-08-14 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=96320

--- Comment #23 from Damian Rouson  ---
A related issue arises if the procedure in question is a pure function as
demonstrated below.  The code compiles cleanly if either
1. The result-spec is absent and the procedure is renamed new_foo in both the
interface body and in the procedure definition, or
2. The interface body is repeated in the procedure definition instead the
"module procedure" syntax.

± cat pure-shape-mismatch.f90 
module foobar
  implicit none

  type foo
integer bar
  end type

  interface
pure module function create() result(new_foo)
  implicit none
  type(foo) new_foo
end function
  end interface

contains
  module procedure create
new_foo%bar = 1
  end procedure
end module 

± gfortran -c pure-shape-mismatch.f90 
pure-shape-mismatch.f90:17:4:

   17 | new_foo%bar = 1
  |1
Error: Variable ‘new_foo’ cannot appear in a variable definition context
(assignment) at (1) in PURE procedure

± gfortran --version
GNU Fortran (GCC) 11.0.0 20200804 (experimental)

[Bug fortran/96320] gfortran 8-10 shape mismatch in assumed-length dummy argument character array

2020-08-03 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=96320

--- Comment #21 from Damian Rouson  ---
Now that the patch fixing this PR has been committed to the trunk, should it be
marked as "Resolved" instead of "Assigned?"

[Bug fortran/96320] gfortran 8-10 shape mismatch in assumed-length dummy argument character array

2020-07-27 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=96320

--- Comment #12 from Damian Rouson  ---
Thanks to each of you for looking at and working on this.

[Bug fortran/96320] gfortran 8-10 shape mismatch in assumed-length dummy argument character array

2020-07-26 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=96320

--- Comment #9 from Damian Rouson  ---
(In reply to Dominique d'Humieres from comment #3)
> 
> Do you mean this is F2008 extension?

Usually I think of "extension" as describing something non-standard.  This is a
standard feature.  I meant simply that it was not allowed before Fortran 2008
introduced submodules. I think the primary purpose of submodules is to
facilitate the separation of interfaces and procedure definitions.  And for
programmers who prefer to not repeat the argument list in two places (and then
have to change it in two places), Fortran 2008 (and 2018) allow the "module
procedure" syntax used in the submitted code.

[Bug fortran/96320] gfortran 8-10 shape mismatch in assumed-length dummy argument character array

2020-07-26 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=96320

--- Comment #7 from Damian Rouson  ---
For context, I nearly always put the procedure definition in a submodule.  In
this case, I'm attempting to use a tool that needs to parse the code and the
tool doesn't support submodules so I moved the procedure definition into the
module.  The workaround is easy: I just eliminate the interface and put all the
argument declarations in the procedure definition.  So this is not an important
bug for me.  It just cost me some time to figure out what the problem was.

[Bug fortran/96320] gfortran 8-10 shape mismatch in assumed-length dummy argument character array

2020-07-26 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=96320

--- Comment #2 from Damian Rouson  ---
Hi Dominique,

> What do you want to do with your test?

I don't understand the question. The submitted code is designed to be a minimal
demonstration of the problem so I don't want to do anything with it other than
demonstrate the problem.  In case you're asking what the original application
was doing, it was for handling command-line arguments.

> Why do you think it is standard conforming?

Fortran 2008 added module subroutine interface bodies specifically to allow
interface bodies in the same scope a the corresponding procedure definitions.
In order to avoid duplication, the standard also allows the procedure
definition to begin with "module procedure" and then to omit all arguments. 
That's what is done in the submitted code.  The code is accepted by the NAG and
Intel compilers.

[Bug fortran/96320] New: gfortran 8-10 shape mismatch in assumed-length dummy argument character array

2020-07-25 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=96320

Bug ID: 96320
   Summary: gfortran 8-10 shape mismatch in assumed-length dummy
argument character array
   Product: gcc
   Version: 10.1.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

The code below compiles cleanly with the NAG Fortran compiler. I believe the
error message is incorrect.  Gfotran 8, 9 and 10 give the same message.

± cat shape-mismatch.f90 
module foobar
  type foo
  contains
procedure, nopass :: bar
  end type
  interface
module subroutine bar(arg)
  character(len=*) arg(:)
end subroutine
  end interface
contains
  module procedure bar
  end procedure
end module

± gfortran -c shape-mismatch.f90 
shape-mismatch.f90:12:22:

   12 |   module procedure bar
  |  1
Error: Shape mismatch in argument 'arg' at (1)

± gfortran --version
GNU Fortran (GCC) 10.1.0

[Bug fortran/94348] gfortran 8/9 reject module procedure definition in same module as function interface

2020-03-31 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=94348

--- Comment #6 from Damian Rouson  ---
Thanks, Tobias!

[Bug fortran/94348] gfortran 8/9 reject module procedure definition in same module as function interface

2020-03-26 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=94348

--- Comment #2 from Damian Rouson  ---
Thanks for the quick reply, Steve. My apologies for not providing any text.  I
dashed this off during a call with the person who reported the problem to me. 
I think the code is legal, but I'm very open to the possibility that I'm wrong
here. It's hard to understand the relevant parts of the standard.   The Intel
compiler accepts the code, but the NAG compiler gives an error message similar
to gfortran, which is a strong hint that it could be invalid code.  What's
confusing is that moving the procedure definition to a submodule works with
gfortran:

$ cat foo.f90 
module foo_module
  implicit none

  interface
 module function foo() result(bar)
   implicit none
   integer bar
 end function
  end interface

end module

submodule(foo_module) foo_submodule
  implicit none
contains
  module procedure foo
bar = 0
  end procedure
end submodule

  use foo_module, only : foo
  implicit none
  print *,foo()
end
$ gfortran foo.f90
$ ./a.out
   0

Thoughts?

[Bug fortran/94348] New: gfortran 8/9 reject module procedure definition in same module as function interface

2020-03-26 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=94348

Bug ID: 94348
   Summary: gfortran 8/9 reject module procedure definition in
same module as function interface
   Product: gcc
   Version: 9.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

$ cat foo.f90 
module foo_module
  implicit none

  interface
 module function foo() result(bar)
   implicit none
   integer bar
 end function
  end interface

contains
  module procedure foo
bar = 0
  end procedure
end module
localhost:modules rouson$ gfortran -c foo.f90 
foo.f90:13:7:

   13 | bar = 0
  |   1
Error: Symbol 'bar' at (1) has no IMPLICIT type
localhost:modules rouson$ gfortran --version
GNU Fortran (Homebrew GCC 9.2.0_3) 9.2.0

[Bug fortran/83118] [8/9/10 Regression] Bad intrinsic assignment of class(*) array component of derived type

2020-02-27 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83118

--- Comment #29 from Damian Rouson  ---
Hi Paul,

The test case works with your patch applied.  Thanks!

Damian

[Bug fortran/93671] gfortran 8-10 ICE on intrinsic assignment to allocatable derived-type component of coarray

2020-02-10 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=93671

--- Comment #1 from Damian Rouson  ---
The submitted code also compiles and executes cleanly with the NAG Fortran
compiler version 7.0.

[Bug fortran/93671] New: gfortran 8-10 ICE on intrinsic assignment to allocatable derived-type component of coarray

2020-02-10 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=93671

Bug ID: 93671
   Summary: gfortran 8-10 ICE on intrinsic assignment to
allocatable derived-type component of coarray
   Product: gcc
   Version: 10.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

The code below generates an internal compiler error (ICE) in gfortran 8.3.0,
9.2.0, and in 10.0.0 dated 20200111.

A more complete demonstration the data structures of interest is shown in the
code example at http://bit.ly/37aHXxG, which works with the Intel Fortran
compiler version 18. I"m not clear on whether the code is standard-conforming,
but the code compiles and executes without error with the Intel compiler
version 18 as does the longer, more complex version at the aforementioned URL
executes without error.

$ cat gfortran-8-10-ice.f90 

  type flux_planes
integer, allocatable :: normals
  end type

  type package
type(flux_planes) surface_fluxes(1)
  end type

  type(package) mail[*], halo_data

  halo_data%surface_fluxes(1)%normals = 1
  mail = halo_data
end

$ gfortran -fcoarray=single gfortran-8-10-ice.f90 
gfortran-8-10-ice.f90:12:0:

   12 |   mail = halo_data
  | 
internal compiler error: Segmentation fault: 11
libbacktrace could not find executable to open

$ gfortran --version
GNU Fortran (GCC) 10.0.0 20200111 (experimental)

[Bug fortran/93158] New: Coarray ICE when module and submodule are in separate files

2020-01-04 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=93158

Bug ID: 93158
   Summary: Coarray ICE when module and submodule are in separate
files
   Product: gcc
   Version: 10.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

The ICE demonstrated below disappears if any one of the following is true:
1. The module and submodule are in the same file, or
2. The coarray is moved from the submodule to the module, or
3. The halo_data component is non-polymorphic.

$ cat surfaces_interface.f90 
module surfaces_interface
  type package
  end type

  type surfaces
class(package), allocatable  :: halo_data
  end type

  interface
module subroutine set_halo_data()
end subroutine
  end interface
end module

$ cat surfaces_implementation.f90 
submodule(surfaces_interface) surfaces_implementation
  type(surfaces) singleton[*]
contains
  module procedure set_halo_data
  end procedure
end submodule

$ gfortran -fcoarray=single -c surfaces_interface.f90
surfaces_implementation.f90 
f951: internal compiler error: in gfc_get_derived_type, at
fortran/trans-types.c:2843
libbacktrace could not find executable to open

$ gfortran --version
GNU Fortran (GCC) 10.0.0 20190926 (experimental)

However, even with fixes 2 and 3 above, an ICE still occurs if all of the
following are true:
1. The halo_data component is made polymorphic, and
2. The subroutine allocates or assigns to the component, and
3. The module and submodule are in a separate file.

$ cat surfaces_interface.f90 
module surfaces_interface
  type package
  end type

  type surfaces
class(package), allocatable :: halo_data
  end type

  type(surfaces) singleton[*]

  interface
module subroutine set_halo_data()
end subroutine
  end interface
end module

$ cat surfaces_implementation.f90 
submodule(surfaces_interface) surfaces_implementation
contains
  module procedure set_halo_data
allocate(package::singleton%halo_data)
  end procedure
end submodule

$ gfortran -fcoarray=single -c surfaces_interface.f90
surfaces_implementation.f90 
surfaces_implementation.f90:4:0:

4 | allocate(package::singleton%halo_data)
  | 
internal compiler error: in gfc_get_derived_type, at fortran/trans-types.c:2843

Issues with file scope appear to be the unifying theme.

[Bug fortran/83118] [8/9/10 Regression] Bad intrinsic assignment of class(*) array component of derived type

2019-11-17 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83118

--- Comment #27 from Damian Rouson  ---
Thanks, Paul!  We'll test the patch.

Damian

[Bug fortran/91513] Non-standard terminology in error message for pointer component assignment in pure procedure

2019-10-13 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=91513

--- Comment #5 from Damian Rouson  ---
Thanks, Steve!

[Bug fortran/91731] Configure error on building MPICH

2019-09-11 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=91731

--- Comment #6 from Damian Rouson  ---
Steve, I'm so incredibly glad you posted the details of your workaround.  
Thank you! I had seen the FCFLAG environment variable, but I hadn't noticed the
FFLAG variable listed just a few lines lower in the output of "configure
--help".  I was pulling my hair out until I noticed that one extra character!

Also, what is -w doing? From your message on the email list, I'm guessing it
converts an error message to a warning.  Is it needed with
-fallow-argument-mismatch?  I don't find -w in the output of "gfortran --help"
and I don't see it mentioned in gfortran's online documentation at
https://gcc.gnu.org/onlinedocs/gfortran/Option-Summary.html.

[Bug fortran/91731] Configure error on building MPICH

2019-09-11 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=91731

--- Comment #5 from Damian Rouson  ---
MPICH must find ISO_Fortran_binding.h in order to build the modern Fortran
bindings that the MPI standard provides through the "mpi_f08" Fortran module. 
Gfortran only started providing ISO_Fortran_binding.h in release 9.1.  In fact,
ISO_Fortran_binding.h was primarily motivated by the need for modern MPI
bindings.  Hopefully someone on the MPICH project will implement more modern
bindings now.  I'll ask when I report this.

[Bug fortran/91731] Configure error on building MPICH

2019-09-11 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=91731

--- Comment #3 from Damian Rouson  ---
So do I need to report this to the MPICH developers or is a gfortran bug?  I
tried "-w -fallow-argument-mismatch" and got the same error message.

[Bug fortran/91731] New: Configure error on building MPICH

2019-09-10 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=91731

Bug ID: 91731
   Summary: Configure error on building MPICH
   Product: gcc
   Version: 10.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

Below is the trailing output of configuring MPICH 3.2, 3.2.1, or 3.3.1 with the
current GCC trunk: 

configure: error: The Fortran compiler /opt/gnu/10.0.0/bin/gfortran will not
compile files that call the same routine with arguments of different types.


I imagine this might be solved by adding the -fallow-argument-mismatch argument
enabled by the gfortran patch posted at
https://gcc.gnu.org/ml/fortran/2019-08/msg00118.html so possibly this can be
closed once that patch hits the trunk. Does GCC 9 have the same issue.  If so,
could the patch be backported to the 9 branch?  Is this indicative of
non-standard code in MPICH? 

Damian

[Bug fortran/91717] ICE on concatenating deferred-length character and character literal

2019-09-09 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=91717

--- Comment #1 from Damian Rouson  ---
FYI, this reproducer was developed by Paul Thomas based on my report that the
gfortran trunk is unable to build the json-fortran repository
(https://jacobwilliams.github.io/json-fortran/).

[Bug fortran/91717] New: ICE on concatenating deferred-length character and character literal

2019-09-09 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=91717

Bug ID: 91717
   Summary: ICE on concatenating deferred-length character and
character literal
   Product: gcc
   Version: 10.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

$cat concat-deferred-len.f90 
  type core
character (len=:), allocatable :: msg
  end type

  type(core) :: my_core

  my_core%msg = my_core%msg//"message"

end
$gfortran concat-deferred-len.f90 
f951: internal compiler error: in gfc_dep_resolver, at
fortran/dependency.c:2284
0x8a087d gfc_dep_resolver(gfc_ref*, gfc_ref*, gfc_reverse*, bool)
   
/home/rouson/Desktop/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/dependency.c:2284
0x8a0a32 gfc_check_dependency(gfc_expr*, gfc_expr*, bool)
   
/home/rouson/Desktop/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/dependency.c:1295
0x943a61 realloc_string_callback
   
/home/rouson/Desktop/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/frontend-passes.c:284
0x946a29 gfc_code_walker(gfc_code**, int (*)(gfc_code**, int*, void*), int
(*)(gfc_expr**, int*, void*), void*)
   
/home/rouson/Desktop/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/frontend-passes.c:5029
0x948082 realloc_strings
   
/home/rouson/Desktop/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/frontend-passes.c:1519
0x94818f gfc_run_passes(gfc_namespace*)
   
/home/rouson/Desktop/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/frontend-passes.c:177
0x86f037 gfc_resolve(gfc_namespace*)
   
/home/rouson/Desktop/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/resolve.c:17148
0x85c3a0 resolve_all_program_units
   
/home/rouson/Desktop/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/parse.c:6192
0x85c3a0 gfc_parse_file()
   
/home/rouson/Desktop/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/parse.c:6439
0x8a83cf gfc_be_parse_file
   
/home/rouson/Desktop/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/f95-lang.c:204
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See <https://gcc.gnu.org/bugs/> for instructions.
$gfortran --version
GNU Fortran (GCC) 10.0.0 20190904 (experimental)

[Bug fortran/91513] New: Non-standard terminology in error message for pointer component assignment in pure procedure

2019-08-21 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=91513

Bug ID: 91513
   Summary: Non-standard terminology in error message for pointer
component assignment in pure procedure
   Product: gcc
   Version: 8.3.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

Based on a quick search, I don't think the Fortran standard uses the term
"impure variable," which makes it difficult to interpret the error message
below.  Above the GCC source code that contains this error message is a
citation to Fortran 2008 C1283. It might be nice to have a more descriptive
error message or at least to a comment to the GCC source that more fully
explains how the constraint is being applied to lead to the error message
below:

$cat impure-variable.f90 
  implicit none
  type ptr
logical, pointer :: bool=>null()
  end type
  type(ptr) :: foo, bar
  bar = f(foo)
contains
  pure function f(x) result(y)
type(ptr), intent(in) :: x
type(ptr) y
y = x
  end function
end
$gfortran-8 impure-variable.f90
impure-variable.f90:11:8:

 y = x
1
Error: The impure variable at (1) is assigned to a derived type variable with a
POINTER component in a PURE procedure (12.6)
$gfortran-8 --version

[Bug fortran/90430] New: [9 Regression] internal procedure target rejected in initialization

2019-05-10 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=90430

Bug ID: 90430
   Summary: [9 Regression] internal procedure target rejected in
initialization
   Product: gcc
   Version: 9.1.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

gfortran 9.1.0 gives an error message when compiling the following code, which
I believe is valid and which gfortran 8.3.0 compiles without error:

$cat internal-procedure-target.f90 
  implicit none
  interface
function f() result(i)
  integer i
end function
  end interface
  procedure(f), pointer :: g=>h
contains
  function h() result(j)
integer j
j=1
  end function
end
$gfortran internal-procedure-target.f90 
internal-procedure-target.f90:7:31:

7 |   procedure(f), pointer :: g=>h
  |   1
Error: Internal procedure ‘h’ is invalid in procedure pointer initialization at
(1)
$gfortran --version
GNU Fortran (GCC) 9.1.0

[Bug fortran/90305] ASSOCIATE with a substring of a deferred-length character selector yields garbage

2019-05-01 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=90305

--- Comment #1 from Damian Rouson  ---
The code gives the expected output "f" with GCC 9.

[Bug fortran/90305] New: ASSOCIATE with a substring of a deferred-length character selector yields garbage

2019-05-01 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=90305

Bug ID: 90305
   Summary: ASSOCIATE with a substring of a deferred-length
character selector yields garbage
   Product: gcc
   Version: 8.3.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

An ASSOCIATE construct with a substring of a deferred-length character selector
yields garbage with gfortran 8.3.0:

$ cat associate.f90 
  character(len=:), allocatable :: string
  string = "f"
  associate( substring => string(:) )
print*,substring
  end associate
end
$ gfortran associate.f90 
$ ./a.out
 P
$ gfortran --version
GNU Fortran (GCC) 8.3.0

[Bug fortran/90133] New: Linker error if no

2019-04-17 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=90133

Bug ID: 90133
   Summary: Linker error if no
   Product: gcc
   Version: 9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

The code below compiles cleanly with -fcoarray=single but generates a linker
error when I use -fcoarray=lib and link to MPICH and OpenCoarrays.  The linking
problem goes away if the "use" statement and "type(event_type)" declaration are
moved to just after the "associate" statement and wrapped in "block/end block",
which leads me to suspect this might be a gfortran bug rather than an
OpenCoarrays bug.  

$ cat link-error.f90
module link_error
contains
  subroutine post_event_in_associate
use iso_fortran_env
type(event_type), save :: e[*]
associate( i => 1 )
  event post(e[1])
end associate
  end
end module
end

$ gfortran \
  
-I/home/rouson/Desktop/Builds/opt/opencoarrays/2.6.1-b480f1d/gnu/9.0.1/include/OpenCoarrays-2.6.1-14-gb480f1d_GNU-9.0.1
\
   -fcoarray=lib \
   -Wl,-rpath \
   -Wl,/home/rouson/Builds/opt/mpich/3.2/gnu/9.0.1/lib \
   -Wl,--enable-new-dtags ${@} \
  
/home/rouson/Desktop/Builds/opt/opencoarrays/2.6.1-b480f1d/gnu/9.0.1/lib/libcaf_mpi.a
\
   /home/rouson/Desktop/Builds/opt/mpich/3.2/gnu/9.0.1/lib/libmpifort.so \
   /home/rouson/Desktop/Builds/opt/mpich/3.2/gnu/9.0.1/lib/libmpi.so \
   link-error.f90
/tmp/ccU8ZmCw.o: In function `_caf_init.1.3907':
link-error.f90:(.text+0x4d): undefined reference to `caf_token.0.3905'
link-error.f90:(.text+0x5c): undefined reference to `_gfortran_caf_register'
/tmp/ccU8ZmCw.o: In function `__link_error_MOD_post_event_in_associate':
link-error.f90:(.text+0x8b): undefined reference to `caf_token.0.3905'
link-error.f90:(.text+0xae): undefined reference to `_gfortran_caf_event_post'
/tmp/ccU8ZmCw.o: In function `main':
link-error.f90:(.text+0xda): undefined reference to `_gfortran_caf_init'
link-error.f90:(.text+0x104): undefined reference to `_gfortran_caf_finalize'
collect2: error: ld returned 1 exit status

$ gfortran --version
GNU Fortran (GCC) 9.0.1 20190318 (experimental)

[Bug fortran/89840] [Coarray] CO_BROADCAST: Missing finalization/deallocation of allocatable components

2019-04-01 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89840

Damian Rouson  changed:

   What|Removed |Added

 Status|WAITING |RESOLVED
 Resolution|--- |INVALID

[Bug fortran/89840] [Coarray] CO_BROADCAST: Missing finalization/deallocation of allocatable components

2019-04-01 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89840

--- Comment #2 from Damian Rouson  ---
The PR was cited in the original description: Bug 64777.  It was closed for
lack of a test cased and the person who closed it suggested opening a new PR if
a test case was provided so I attempted to do so.  Upon consulting the Fortran
2018 standard, however, I see not evidence that first argument of CO_BROADCAST
will be finalized so this PR can be closed.

[Bug fortran/64777] [Coarray] CO_BROADCAST: Finalization/dealloc of alloc components missing

2019-03-26 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64777

Damian Rouson  changed:

   What|Removed |Added

 CC||damian at sourceryinstitute 
dot or
   ||g

--- Comment #3 from Damian Rouson  ---
I just added test case in Bug 89840.

[Bug fortran/89840] New: [Coarray] CO_BROADCAST: Missing finalization/deallocation of allocatable components

2019-03-26 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89840

Bug ID: 89840
   Summary: [Coarray] CO_BROADCAST: Missing
finalization/deallocation of allocatable components
   Product: gcc
   Version: 9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

This report is simply to provide a test case for Bug 64777, which was closed
for lack of a test case.  Because this test cases compiles with OpenCoarrays,
which does not yet support derived-type arguments for co_broadcast, this test
case cannot fully demonstrate the issue, but it seems important to have a test
case that captures the issue for future work once co_broadcast accepts
derived-type arguments.  A more complete test case would also include an
allocatable component inside the derived type:

$cat pr64777.f90 
module foo_module
  implicit none
  type foo
  contains
final :: done
  end type
contains
  subroutine done(this)
type(foo) this
print *,"Finalizing on image ",this_image()
  end subroutine
end module

  use foo_module
  implicit none
  type(foo) bar
  call co_broadcast(bar,source_image=1)
end
$caf pr64777.f90 
$cafrun -n 2 ./a.out
Fortran runtime error on image 1: Unsupported data type in collective: 80

Fortran runtime error on image 2: Unsupported data type in collective: 80

Error: Command:
   `/home/rouson/Builds/opt/mpich/3.2/gnu/9.0.1/bin/mpiexec -n 2 ./a.out`
failed to run.

[Bug fortran/89496] [9 Regression] gcc/fortran/trans-types.c:3015:9: runtime error: member access within null pointer of type 'struct gfc_formal_arglist'

2019-02-28 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89496

Damian Rouson  changed:

   What|Removed |Added

 CC||damian at sourceryinstitute 
dot or
   ||g

--- Comment #7 from Damian Rouson  ---
Thanks for fixing this!  It eliminates an ICE in a legacy code I'm currently
modernizing.

[Bug fortran/84387] Defined output does not work for a derived type that has no components

2019-02-17 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84387

--- Comment #6 from Damian Rouson  ---
I don't see anything in the standard related to the existence or non-existence
of components in derived-type output.  In case it helps, the NAG and Intel
compilers both print "Hello world!" with the submitted code, but the Cray
compiler prints nothing, which matches gfortran's behavior.  I'll contact Cray
technical support to see if they agree it's a bug.

--- Comment #7 from Damian Rouson  ---
I don't see anything in the standard related to the existence or non-existence
of components in derived-type output.  In case it helps, the NAG and Intel
compilers both print "Hello world!" with the submitted code, but the Cray
compiler prints nothing, which matches gfortran's behavior.  I'll contact Cray
technical support to see if they agree it's a bug.

[Bug fortran/84387] Defined output does not work for a derived type that has no components

2019-02-17 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84387

--- Comment #6 from Damian Rouson  ---
I don't see anything in the standard related to the existence or non-existence
of components in derived-type output.  In case it helps, the NAG and Intel
compilers both print "Hello world!" with the submitted code, but the Cray
compiler prints nothing, which matches gfortran's behavior.  I'll contact Cray
technical support to see if they agree it's a bug.

--- Comment #7 from Damian Rouson  ---
I don't see anything in the standard related to the existence or non-existence
of components in derived-type output.  In case it helps, the NAG and Intel
compilers both print "Hello world!" with the submitted code, but the Cray
compiler prints nothing, which matches gfortran's behavior.  I'll contact Cray
technical support to see if they agree it's a bug.

[Bug fortran/84387] Defined output does not work for a derived type that has no components

2019-02-17 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84387

--- Comment #4 from Damian Rouson  ---
I don't agree that the code submitted in this bug report is non-sensical. The
submitted example is very useful for code debugging purposes.   I just spent a
couple of hours trying to isolate this same bug.  Being able to print output
for a type with no components would have saved me the all the time that led to
finding this bug report.

Also, there are many uses for an empty derived type that serves as a
polymorphic hook on which to hang various type-bound procedures where the
choice of which procedure gets executed is determined by the dynamic type of
the passed-object dummy argument.  Moreover, if a type with no components
appears one several objects being output, the user might like to see some text
to know that the type was there.  Such types crop up frequently in the Strategy
object-oriented design pattern.

[Bug fortran/78983] [7/8/9 Regression] ICE with CAF-DT with allocatable member

2019-02-13 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=78983

--- Comment #10 from Damian Rouson  ---
I see no ICE in testing the code from Comment 3 using fortran 7.3.0, 8.2.0, and
9.0.1.  I believe this can be closed.

[Bug fortran/89200] [9 Regression] Erroneous copying of a derived type with a deferred-length character array component

2019-02-05 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89200

--- Comment #4 from Damian Rouson  ---
Thanks, Paul!

[Bug fortran/89200] [9 Regression] Erroneous copying of a derived type with a deferred-length character array component

2019-02-04 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89200

--- Comment #1 from Damian Rouson  ---
gfortran 8.2.0 code gives the correct output:

$gfortran corrupted-component.f90 

$./a.out
 12

$gfortran --version
GNU Fortran (GCC) 8.2.0

[Bug fortran/68241] [meta-bug] [F03] Deferred-length character

2019-02-04 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68241

--- Comment #3 from Damian Rouson  ---
I just created PR89200, on which this meta-bug should depend, but I don't know
how to edit the "Depends on" list.

[Bug fortran/89200] New: Erroneous copying of a derived type with a deferred-length character array component

2019-02-04 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89200

Bug ID: 89200
   Summary: Erroneous copying of a derived type with a
deferred-length character array component
   Product: gcc
   Version: 9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

$cat corrupted-component.f90 
  type foo
character(len=:), allocatable :: string
  end type
  type foo_list
type(foo), allocatable :: entry(:)
  end type
  type(foo_list) list
  list = foo_list([foo('1'), foo('2')])
  print*, list%entry(1)%string, list%entry(2)%string
end

$gfortran corrupted-component.f90 

$./a.out
 11

$gfortran --version
GNU Fortran (GCC) 9.0.1 20190125 (experimental)

The same result obtains if the intrinsic assignment is replaced
by a source allocation of the form

allocate(list%entry, source = [foo('1'), foo('2')] )

[Bug fortran/88076] Shared Memory implementation for Coarrays

2019-01-29 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88076

--- Comment #8 from Damian Rouson  ---
(In reply to Nicolas Koenig from comment #7)

> I actually opted to use multiprocessing with shared memory (shm_open() & co)
> instead of multithreading, since it will be much easier and faster with
> static variables, of which gfortran makes extensive use. Also, it greatly
> simplifies interoperability with OpenMP. 

This sounds like a great choice.  I have no prior familiarity with shm_open(),
but I very much like the idea of simplifying interoperability with OpenMP. 

> The only real downsides I can think of are slower spinup times... 

It will be interesting to compare the performance with MPI.  I also wonder if
this would also someday provide for a hybrid implementation wherein shm_open()
is used within a node and MPI is used across nodes, e.g., maybe images within
a TEAM could use shm_open() to communicate, while any communication between
TEAMs could use MPI.

> 
> I actually think it would be best not to turn it into a separate library but
> instead integrate it into libgfortran. 

I agree. 

> This way, it will not be necessary to
> install a seperate library and thereby make it easier for people to start
> using coarrays. Therefore, it would make sense to use the libgfortran
> descriptors.

> 
> At the moment, sync_all() is called after image creation.

I think that will suffice.

[Bug fortran/85836] [meta-bug] Fortran 2018 support

2019-01-27 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=85836
Bug 85836 depends on bug 84894, which changed state.

Bug 84894 Summary: [F2018] provide ISO_Fortran_binding.h
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84894

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

[Bug fortran/84894] [F2018] provide ISO_Fortran_binding.h

2019-01-27 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84894

Damian Rouson  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #8 from Damian Rouson  ---
I believe commit r267946 fixes this.

[Bug fortran/88076] Shared Memory implementation for Coarrays

2019-01-27 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88076

--- Comment #6 from Damian Rouson  ---
Correction to the end of the first sentence of the final paragraph in Comment
5: "... not join them _until_ the end."

[Bug fortran/88076] Shared Memory implementation for Coarrays

2019-01-27 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88076

--- Comment #5 from Damian Rouson  ---
This is an exciting idea.  When I gave some thought to writing a shared-memory
alternative coarray ABI, it seemed to me that pthreads would be a better choice
than OpenMP.  Part of the problem is that I was considering writing the
implementation in Fortran, and OpenMP lacked support several modern Fortran
features, including several object-oriented programming features.  That of
course won't be an issue for you, however, assuming you're going to write the
implementation in C.  I was going to leverage "forthreads," an open-source
Fortran 20003 interface to pthreads.  One thing that I think would be a major
benefit of having a Fortran implementation of the library is that it greatly
expand the potential community of contributors to include more of the users of
the compiler.

Another important consideration is whether to use the current gfortran
descriptors as arguments in the library functions (as is currently used) or
instead to use the Fortran 2018 CFI descriptors for which Paul recently
committed support.  If you go with the current gfortran descriptors, then there
could be a lot of code to rewrite if gfortran later adopts the standard
descriptors internally.  Paul's recent commit adds functions that can translate
between the gfortran and standard descriptors. I have a volunteer who I'm
hoping will use the translation functions to develop a new, alternative coarray
ABI that accepts the standard descriptors.

On another note mentioned earlier in this PR, I believe it will be necessary to
fork all threads at the beginning of execution and not join them at the end. 
Section 5.3.5 of the Fortran 2018 standard states, "Following the creation of a
fixed number of images, execution begins on each image."  Assuming there is a
one-to-one correspondence between images and threads, I read that as implying
that a fixed number of threads have to be set up before any one thread can
execute.  (Possibly there could also be additional non-image threads that get
forked later also though.)  I recall seeing several interesting papers from
10-15 years ago on SPMD-style programming using threads (OpenMP) so a
literature search on this topic be useful to read.

[Bug fortran/80260] [7/8 Regression] ICE with polymorphic array section actual argument

2019-01-27 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=80260

--- Comment #13 from Damian Rouson  ---
Thanks for the fix!

[Bug fortran/82077] [7/8/9 Regression] ICE on associating polymorphic array dummy with a type-guarded array section

2019-01-27 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82077

--- Comment #11 from Damian Rouson  ---
Thanks, Paul!

[Bug fortran/87659] Memory corruption in array component of intent(in) unlimited polymorphic with optimization

2018-10-19 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87659

--- Comment #1 from Damian Rouson  ---
In initial comment, I meant to write "... bug disappears if the pointer intent
is switched to intent(inout)..."

[Bug fortran/87659] New: Memory corruption in array component of intent(in) unlimited polymorphic with optimization

2018-10-19 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87659

Bug ID: 87659
   Summary: Memory corruption in array component of intent(in)
unlimited polymorphic with optimization
   Product: gcc
   Version: 8.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

The following bug disappears if the pointer intent is switched to intent(out)
or if the optimization level is dropped to -O0:

$ cat all.f90 
module vectors
  implicit none
  type vector
integer, allocatable :: elements(:)
  end type
contains
  subroutine set_elements(input)
class(*), pointer, intent(in) :: input
select type (input)
  type is (vector)
input%elements=[2]
end select
  end subroutine
end module

  implicit none
  call set_vector
contains
  subroutine set_vector()
use vectors
type (vector), target :: v
class(*), pointer :: v_ptr
v_ptr => v
call set_elements ( v_ptr )
select type ( v_ptr )
type is ( vector )
  print *, v%elements(1), '<-- should be 2'
end select
  end subroutine
end
$ gfortran -O1 all.f90 
$ ./a.out
   0 <-- should be 2
$ gfortran --version
GNU Fortran (Homebrew GCC 8.2.0) 8.2.0

[Bug fortran/86906] New: erroneous name clash with renaming in use statement

2018-08-09 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86906

Bug ID: 86906
   Summary: erroneous name clash with renaming in use statement
   Product: gcc
   Version: 8.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

gfortran 6.4, 7.3, and 8.2 all produce the error message below when attempting
to use a renamed type while in the same scope as the variable that motivated
the renaming:

$ cat foo.f90 
module foo
  type config
  end type
end module
  use foo, only: foo_config => config
contains
  subroutine cap
integer config
type(foo_config) extra
  end subroutine
end

$ gfortran foo.f90 
foo.f90:9:26:

 integer config
  2
 type(foo_config) extra
  1
Error: The type ‘config’ cannot be host associated at (1) because it is blocked
by an incompatible object of the same name declared at (2)

$ gfortran --version
GNU Fortran (GCC) 8.2.0

[Bug fortran/86863] New: [OOP][F2008] type-bound module procedure name not recognized

2018-08-05 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86863

Bug ID: 86863
   Summary: [OOP][F2008] type-bound module procedure name not
recognized
   Product: gcc
   Version: 8.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

Gfortran 8.2.0 fails to recognize the public type-bound procedure below. The
error message goes away when "module procedure" is replaced with "subroutine"
and the dummy arguments are declared in the definition of the "set" subroutine.
 With gfortran 7.3.0 and 6.4.0, the code below causes an ICE.


$ cat module-procedure.f90 
module foo
  implicit none
  type bar
  contains
procedure, nopass :: foobar
  end type
contains
  subroutine foobar
  end subroutine
end module

module foobartoo
  implicit none
  interface
module subroutine set(object)
  use foo
  implicit none
  type(bar) object
end subroutine
  end interface
contains
  module procedure set
use foo, only : bar
call object%foobar
  end procedure
end module
rouson@sourcery-VirtualBox:~/Desktop/Builds/frapcon4.1/src/reproducer$ gfortran
-c module-procedure.f90 
module-procedure.f90:24:22:

 call object%foobar
  1
Error: ‘foobar’ at (1) should be a SUBROUTINE
rouson@sourcery-VirtualBox:~/Desktop/Builds/frapcon4.1/src/reproducer$ gfortran
--version
GNU Fortran (GCC) 8.2.0

[Bug fortran/86694] New: gfortran rejects character parameter binding label

2018-07-27 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86694

Bug ID: 86694
   Summary: gfortran rejects character parameter binding label
   Product: gcc
   Version: 8.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

The consensus opinion on the J3 mailing list is that the code below is
standard-conforming. The Intel compiler accepts the code. gfortran 5.5, 6.4,
7.3, and 8.2 generate the error message below.

Damian

$ cat c-name.f90 
character(len=5), parameter :: c_name="c_foo"
interface
  subroutine foo() bind(C,name=c_name)
import c_name
  end subroutine
end interface
end 
$ gfortran -c c-name.f90 
c-name.f90:3:31:

   subroutine foo() bind(C,name=c_name)
   1
Error: Parameter ‘c_name’ at (1) has not been declared or is a variable, which
does not reduce to a constant expression
c-name.f90:4:10:

 import c_name
  1
Error: IMPORT statement at (1) only permitted in an INTERFACE body
c-name.f90:5:5:

   end subroutine
 1
Error: Expecting END INTERFACE statement at (1)
$ gfortran --version
GNU Fortran (GCC) 8.2.0

[Bug fortran/84894] [F2018] provide ISO_Fortran_binding.h

2018-05-23 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84894

--- Comment #6 from Damian Rouson  ---
Sounds good. I agree that it would be great for gfortran to provide
ISO_Fortran_binding.h independently. Hopefully the OpenCoarrays version will be
a useful starting point. My understanding is that it's always ok to copy source
code from a BSD-licensed project such as OpenCoarrays into a GPL-licensed
project so hopefully our implementation saves someone a lot of time.  The only
remaining challenge is to coax the GCC build system into install it.  Obviously
that should be a trivial task for someone with the right knowledge or the
patience to figure it out.  I just don't know who that person is and we did
reach out to several people for help and even got some input, but still
couldn't get it to work.

[Bug fortran/83606] [6/7/8 Regression] co-indexed array RHS yields incorrect result in assignment to vector-indexed LHS

2018-05-23 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83606

--- Comment #12 from Damian Rouson  ---
Thank you, Andre!

[Bug fortran/85836] [meta-bug] Fortran 2018 support

2018-05-23 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=85836
Bug 85836 depends on bug 84894, which changed state.

Bug 84894 Summary: [F2018] provide ISO_Fortran_binding.h
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84894

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |WONTFIX

[Bug fortran/84894] [F2018] provide ISO_Fortran_binding.h

2018-05-23 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84894

Damian Rouson  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |WONTFIX

--- Comment #4 from Damian Rouson  ---
I'm marking this resolved in the sense that the file will be available to
gfortran users who also install OpenCoarrays, which they already have to do to
compile multi-image parallel executable programs.

[Bug fortran/84894] [F2018] provide ISO_Fortran_binding.h

2018-05-23 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84894

--- Comment #3 from Damian Rouson  ---
Oxford University graduate student Daniel Celis Garza has been working on this
for the bulk of his 11-week visit with me, which ends next week. For reasons
motivated largely by the difficulty of coaxing the GCC autotools build system
to install ISO_Fortran_binding.h and build the corresponding functions into a
library, we have decided to develop our own ISO_Fortran_binding.h and
contribute it and the corresponding C function definitions to OpenCoarrays.  A
secondary motivation is that the work can potentially benefit multiple
compilers. 

Daniel is the second developer who has attempted to modifying the GCC build
system for Sourcery Institute.  Both have given up after weeks of effort. 
Hopefully someone with knowledge of the GCC build system will at some point
modify the build system so that it builds OpenCoarrays in a similar manner to
the way in which it builds prerequisites such as MPFR and GMP, then
ISO_Fortran_binding.h and will be made available without users having to
install OpenCoarrays separately after installing gfortran.

[Bug fortran/82275] gfortran rejects valid & accepts invalid reference to dimension-remapped type SELECT TYPE selector

2018-05-23 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82275

--- Comment #9 from Damian Rouson  ---
Thanks, Paul!

Damian

[Bug fortran/85510] Linking error when accessing a coindexed variable inside an associate block

2018-04-23 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=85510

--- Comment #1 from Damian Rouson  ---
As similar error message results if the associate construct is replaced with a
block construct of the form

block
  integer n
  n=1
  print*,i[1]
end block

The error disappears if the 'block' and 'end block' statements are deleted.

[Bug fortran/85510] New: Linking error when accessing a coindexed variable inside an associate block

2018-04-23 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=85510

Bug ID: 85510
   Summary: Linking error when accessing a coindexed variable
inside an associate block
   Product: gcc
   Version: 8.0.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

The code below compiles without error with -fcoarray=single; whereas compiling
with -fcoarray=lib generates the link-time error message shown with the
gfortran 7.2.0 and with the trunk dated 20180412.  The gfortran command comes
from the output of the OpenCoarrays command 'caf --show'. Some of the paths
have been shortened manually for presentation purposes:

$ cat communicate-inside-associate.f90 module foo
contains
  subroutine bar()
integer, save :: i[*]=0
associate(n=>1)
  print*,i[1]
end associate
  end subroutine
end module

use foo
end
$ gfortran -I/opt/opencoarrays/include/OpenCoarrays-2.0.0-26-g840374a_GNU-8.0.1
-fcoarray=lib -Wl,-rpath -Wl,/opt/mpich/3.2/lib -Wl,--enable-new-dtags
communicate-inside-associate.f90 /opt/opencoarrays/lib/libcaf_mpi.a
/opt/mpich/3.2/lib/libmpifort.so /opt/mpich/3.2/lib/libmpi.so
/tmp/ccA8dGYe.o: In function `_caf_init.1.3816':
communicate-inside-associate.f90:(.text+0x4d): undefined reference to
`caf_token.0.3815'
/tmp/ccA8dGYe.o: In function `__foo_MOD_bar':
communicate-inside-associate.f90:(.text+0x153): undefined reference to
`caf_token.0.3815'
collect2: error: ld returned 1 exit status
rouson@sourcery-VirtualBox:~/Desktop/Builds/adhoc/src/gnu/nrc/emulated-collectives$
gfortran --version
GNU Fortran (GCC) 8.0.1 20180412 (experimental)

[Bug fortran/84894] New: [F2018] provide iso_fortran_binding.h

2018-03-15 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84894

Bug ID: 84894
   Summary: [F2018] provide iso_fortran_binding.h
   Product: gcc
   Version: 8.0.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

Fortran 2018 requires that compilers provide an iso_fortran_binding.h C header
file for further interoperability with C.   Such a file was on the fortran-dev
branch in 2013:

https://gcc.gnu.org/viewcvs/gcc/branches/fortran-dev/libgfortran/ISO_Fortran_binding.h.tmpl?=markup#l1

This bug is being submitted to track progress and interest in this feature and
to preserve a link to the above file as a potential starting point.  The lack
of iso_fortran_bindin.h currently blocks MPICH 3.2 from providing gfortran
users the mpi_f08 module that the MPI 3.1 standard requires.

Damian

[Bug fortran/41897] Support TS 29113: "Further Interoperability of Fortran with C"

2018-03-15 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=41897

--- Comment #3 from Damian Rouson  ---
With Fortran 2018 now in Committee Draft (CD) and likely to be published this
year, it probably makes sense to close this bug report.  Any features from TS
29113 that will be in Fortran 2018 have already been incorporated into the CD
and it's possible that the integration process could have led to changes so the
CD would be the more appropriate reference now rather than the TS.

[Bug fortran/84622] New: [F08] gfortran accepts invalid intent(out) polymorphic dummy argument with coarray component

2018-02-28 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84622

Bug ID: 84622
   Summary: [F08] gfortran accepts invalid intent(out) polymorphic
dummy argument with coarray component
   Product: gcc
   Version: 8.0.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

gfortran 7 and 8 accept the following invalid code when the dummy argument is
declared with "class" but give the correct error message when "type" replaces
"class":

  type foo
logical, allocatable :: bar[:]
  end type
contains
  subroutine foobar(this)
class(foo), intent(out) :: this
  end subroutine
end

[Bug fortran/83700] [Meta-bug] Fortran Coarray issues

2018-01-05 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83700

--- Comment #4 from Damian Rouson  ---
(In reply to Dominique d'Humieres from comment #3)
> AFAIR most of (if not all) the PRs are exposed via -fcoarray=lib
> -lcaf_single.

Yes, I meant to write "-fcoarray=lib -lcaf_mpi".  If the errors are
compile-time errors, then it probably doesn't matter, but if they are runtime
errors, then it's important to test both with single-image execution
(-lcaf_single) and multi-image execution (e.g., -caf_mpi).

Also, if anyone is interested in related contract work, let me know.  Most of
the funding Sourcery Institute can contribute have been expended, but one donor
to Sourcery Institute has asked about additional ways to contribute so there
could be opportunities for a small amount of funding.

[Bug fortran/83700] [Meta-bug] Fortran Coarray issues

2018-01-05 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83700

--- Comment #2 from Damian Rouson  ---
Thanks for this!  For anyone looking at this, I'll be glad to assist with
parallel execution testing via -fcoarray=lib.

[Bug fortran/78983] [7/8 Regression] ICE with CAF-DT with allocatable member

2017-12-28 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=78983

--- Comment #6 from Damian Rouson  ---
Using 7.2, I still see an ICE with the reduced example from Comment 3:

$ gfortran -fcoarray=lib -c bug-78983.f90 
bug-78983.f90:24:0:

 end module

internal compiler error: in gfc_conv_descriptor_data_get, at
fortran/trans-array.c:144
Please submit a full bug report,
with preprocessed source if appropriate.
See  for instructions.

[Bug fortran/83606] co-indexed array RHS yields incorrect result in assignment to vector-indexed LHS

2017-12-27 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83606

--- Comment #1 from Damian Rouson  ---
Is this a duplicate of Bug #81773?

[Bug fortran/83606] New: co-indexed array RHS yields incorrect result in assignment to vector-indexed LHS

2017-12-27 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83606

Bug ID: 83606
   Summary: co-indexed array RHS yields incorrect result in
assignment to vector-indexed LHS
   Product: gcc
   Version: 8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

The commands below use MPICH 3.2 installed by GCC 8 trunk dated 20171227. 
Alternatively, the code can be compiled without arguments using the "caf"
script that OpenCoarrays installs.

$ cat vector-subscript.f90
  integer, parameter :: ndim=5
  integer :: i,vec(ndim)=0, res(ndim)[*]=[ (i, i=1, ndim) ]
  vec([ndim,1]) = res(1:2)[1]
  if (vec(1) /= res(2) .or. vec(ndim) /= res(1)) &
print *," wrong result ",vec([ndim,1])," on image ",this_image()
end

$ export
LD_LIBRARY_PATH=/opt/opencoarrays/1.9.3/gnu/8.0.0/lib/:$LD_LIBRARY_PATH

$ export PATH=/opt/mpich/3.2/gnu/8.0.0/bin:$PATH

$ mpifort -fcoarray=lib -L /opt/opencoarrays/1.9.3/gnu/8.0.0/lib/
vector-subscript.f90 -lcaf_mpi

$ mpirun -n 1 ./a.out
  wrong result0   0  on image1

$ mpifort --version
GNU Fortran (GCC) 8.0.0 20171227 (experimental)

[Bug fortran/83319] New: [7/8 Regression] ICE on use of allocatable component in derived type coarray defined in module

2017-12-07 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83319

Bug ID: 83319
   Summary: [7/8 Regression] ICE on use of allocatable component
in derived type coarray defined in module
   Product: gcc
   Version: 7.2.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

Presumably the internal compiler error (ICE) demonstrated below is somehow
related to the known regression in support for allocatable components in
derived type coarrays, which is issue 422 on the OpenCoarrays repository.
OpenCoarrays issue 422, however, generates a runtime error message inside the
coarray ABI, whereas this issue generates a compile-time error message so it's
a compiler-side problem.  Also, OpenCoarrays issue 422 involves communication;
whereas this is much more basic: the ICE appears when I do anything with the
allocatable component so this is an even more serious regression on top of the
already very serious regression described in issue 422.  (Besides allocating
the component as shown below, I also tried a source allocation and an
assignment to it.)  The ICE disappears if the derived type definition is moved
into the main program.

This is somewhat similar to PR 78935, but 78935 was fixed 11 months ago and
this seems sufficiently different to warrant a separate PR rather than
reopening 78935.

This ICE occurs with today's 7 branch, with 7.2.0, and with the trunk dated
20170921.  The code compiles cleanly with GCC 6.4.0.

$ cat allocatable-component-of-dt-coarray.f90 

module foo_module
  implicit none
  type foo
integer, allocatable :: i(:)
  end type
end module

  use foo_module
  implicit none
  type(foo), save :: bar[*]
  allocate(bar%i(1))
end

$ gfortran -fcoarray=lib -c allocatable-component-of-dt-coarray.f90 
allocatable-component-of-dt-coarray.f90:8:0:

   use foo_module

internal compiler error: in gfc_conv_descriptor_token, at
fortran/trans-array.c:305
0x6a9130 gfc_conv_descriptor_token(tree_node*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-7-branch/gcc/fortran/trans-array.c:303
0x6d6858 gfc_trans_structure_assign(tree_node*, gfc_expr*, bool, bool)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-7-branch/gcc/fortran/trans-expr.c:7567
0x6d0b47 gfc_conv_structure(gfc_se*, gfc_expr*, int)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-7-branch/gcc/fortran/trans-expr.c:7686
0x6df17e gfc_trans_assignment_1
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-7-branch/gcc/fortran/trans-expr.c:9984
0x6be5ff generate_coarray_sym_init
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-7-branch/gcc/fortran/trans-decl.c:5188
0x68dc72 do_traverse_symtree
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-7-branch/gcc/fortran/symbol.c:4009
0x6bdc95 generate_coarray_init
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-7-branch/gcc/fortran/trans-decl.c:5238
0x6c9954 gfc_generate_function_code(gfc_namespace*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-7-branch/gcc/fortran/trans-decl.c:6273
0x65b736 translate_all_program_units
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-7-branch/gcc/fortran/parse.c:6074
0x65b736 gfc_parse_file()
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-7-branch/gcc/fortran/parse.c:6274
0x69ff5f gfc_be_parse_file
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-7-branch/gcc/fortran/f95-lang.c:204
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See <https://gcc.gnu.org/bugs/> for instructions.

$ gfortran --version
GNU Fortran (GCC) 7.2.1 20171208

[Bug fortran/82275] gfortran rejects valid & accepts invalid reference to dimension-remapped type SELECT TYPE selector

2017-09-21 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82275

--- Comment #3 from Damian Rouson  ---
Thanks for looking at this.  Once there's a fix, it would be great if it could
be back-ported to GCC 7 as well.

[Bug fortran/82275] New: gfortran rejects valid & accepts invalid reference to dimension-remapped type selector

2017-09-20 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82275

Bug ID: 82275
   Summary: gfortran rejects valid & accepts invalid reference to
dimension-remapped type selector
   Product: gcc
   Version: 8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

$ cat reproducer.f90 
!! Associating a name with a reduced-dimension section of a
!! multidimensional array precludes subsequent use of the name
!! with the appropriately reduced dimensionality and instead
!! requires use of the (invalid) full set of original dimensions.
!! It seems that this only occurs in the presence of type guarding:
  type component
  end type
  type container
class(component), allocatable :: component_array(:,:)
  end type
  type(container) bag
  type(component) section_copy
  allocate(component::bag%component_array(1,1))
  select type(associate_name=>bag%component_array(1,:))
type is (component)
  section_copy = associate_name(1)  ! gfortran 5,6,7,8 reject valid
  section_copy = associate_name(1,1)! gfortran 5,6,7,8 accept invalid
  end select
end

$ gfortran reproducer.f90 
reproducer.f90:16:35:

   section_copy = associate_name(1)  ! gfortran 5,6,7,8 reject valid
   1
Error: Rank mismatch in array reference at (1) (1/2)
rouson@Sourcery-Linux-VM:~/Desktop/Builds/adhoc/src/gnu/nrc/rank-mismatch$
gfortran --version
GNU Fortran (GCC) 8.0.0 20170912 (experimental)

[Bug fortran/34640] ICE when assigning item of a derived-component to a pointer

2017-09-10 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=34640

--- Comment #37 from Damian Rouson  ---
Bravo!

[Bug fortran/82077] New: [7.1 Regression]: ICE on associating polymorphic array dummy with a type-guarded array section

2017-09-01 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82077

Bug ID: 82077
   Summary: [7.1 Regression]: ICE on associating polymorphic array
dummy with a type-guarded array section
   Product: gcc
   Version: 8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

$ cat poly-array-section-arg.f90 
 !! Gfortran 7.1.0 and 8.0.0 20170731 report an ICE when a
 !! polymorphic 1D array dummy argument of a child type is
 !! associated with a type-guarded, 1D section of a 2D
 !! polymorphic array actual argument declared as the parent
 !! type. Gfortran 5.4.0 and 6.4.0 compile the code without
 !! reporting any errors.
type parent
end type parent
type, extends(parent) :: child
end type
class(parent), allocatable :: foo(:,:)
allocate(child::foo(1,1))
select type(foo)
  class is (child)
call gfortran7_ICE(foo(1,:))
end select
contains
subroutine gfortran7_ICE(bar)
  class(child) bar(:)
end subroutine
end

$ gfortran --version
GNU Fortran (GCC) 8.0.0 20170731 (experimental)

$ gfortran poly-array-section-arg.f90 
poly-array-section-arg.f90:15:0:

 call gfortran7_ICE(foo(1,:))

internal compiler error: Segmentation fault
0xd933ef crash_signal
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/toplev.c:338
0x91d09d gfc_conv_scalarized_array_ref
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans-array.c:3228
0x91e284 gfc_conv_array_ref(gfc_se*, gfc_array_ref*, gfc_expr*, locus*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans-array.c:3382
0x94fa1d gfc_conv_variable
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans-expr.c:2680
0x94beea gfc_conv_expr(gfc_se*, gfc_expr*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans-expr.c:7816
0x92b7b6 gfc_conv_expr_descriptor(gfc_se*, gfc_expr*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans-array.c:7138
0x948348 gfc_conv_procedure_call(gfc_se*, gfc_symbol*, gfc_actual_arglist*,
gfc_expr*, vec<tree_node*, va_gc, vl_embed>*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans-expr.c:5319
0x987b7a gfc_trans_call(gfc_code*, bool, tree_node*, tree_node*, bool)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans-stmt.c:406
0x9142e5 trans_code
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans.c:1885
0x98c188 gfc_trans_block_construct(gfc_code*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans-stmt.c:1934
0x914097 trans_code
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans.c:1913
0x984643 gfc_trans_if_1
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans-stmt.c:1434
0x98bc1a gfc_trans_if(gfc_code*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans-stmt.c:1465
0x914107 trans_code
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans.c:1905
0x98e53d gfc_trans_select_type_cases
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans-stmt.c:2532
0x98e53d gfc_trans_select_type(gfc_code*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans-stmt.c:3242
0x914007 trans_code
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans.c:1933
0x98c188 gfc_trans_block_construct(gfc_code*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans-stmt.c:1934
0x914097 trans_code
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans.c:1913
0x93dc68 gfc_generate_function_code(gfc_namespace*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/gcc-teams/gcc/fortran/trans-decl.c:6365
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See <https://gcc.gnu.org/bugs/> for instructions.

[Bug fortran/82065] New: gfortran rejects redundant use of intrinsic module constant

2017-08-31 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82065

Bug ID: 82065
   Summary: gfortran rejects redundant use of intrinsic module
constant
   Product: gcc
   Version: 8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

gfortran 6, 7, and 8 generate compiler error messages when a variable in the 
iso_fortran_env intrinsic model is accessed via use association where it is
also available via host association:

$ cat use-intrinsic-module-twice.f90 
  use iso_fortran_env
  implicit none
  print *, integer_kinds
  call testsub
contains
  subroutine testsub
use iso_fortran_env
print * , integer_kinds
  end subroutine
end

$ gfortran use-intrinsic-module-twice.f90 
/tmp/ccoAKOqk.s: Assembler messages:
/tmp/ccoAKOqk.s:134: Error: symbol `__iso_fortran_env_MOD_integer_kinds' is
already defined

$ gfortran --version
GNU Fortran (GCC) 8.0.0 20170731 (experimental)

[Bug fortran/80260] [7/8 Regression] ICE with polymorphic array section actual argument

2017-05-05 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=80260

--- Comment #3 from Damian Rouson  ---
The same code causes an ICE with the 7.1.0 release. Is there a fix on the 8
branch or any related updates?

[Bug fortran/78640] [F2015] gfortran accepts invalid allocatable polymorphic result in pure function

2017-04-28 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=78640

--- Comment #2 from Damian Rouson  ---
I think this bug just bit gfortran user and Fortran enthusiast Stefano Zhagi.
Is anyone interested in fixing it?

[Bug fortran/80260] New: [7 Regression] ICE with polymorphic array section actual argument

2017-03-30 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=80260

Bug ID: 80260
   Summary: [7 Regression] ICE with polymorphic array section
actual argument
   Product: gcc
   Version: 7.0.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

The code below causes an internal compiler error with gfortran 7.0.1, but
compiles and executes cleanly with gfortran 6.3.0

$ cat foobar.f90 
type foo
end type foo
type, extends(foo) :: bar
end type
contains
subroutine f(x)
  class(foo) x(:,:)
  select type(x)
class is (bar)
  call g(x(1,:))
  end select
end subroutine
subroutine g(y)
  class(bar) y(:)
end subroutine
end

$ gfortran --version
GNU Fortran (GCC) 7.0.1 20170326 (experimental)
-- snip --

$ gfortran foobar.f90 
foobar.f90:10:0:

   call g(x(1,:))

internal compiler error: Segmentation fault
0xbe60ff crash_signal
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/toplev.c:337
0x6c70d9 gfc_conv_scalarized_array_ref
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans-array.c:3229
0x6c8344 gfc_conv_array_ref(gfc_se*, gfc_array_ref*, gfc_expr*, locus*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans-array.c:3397
0x701ffd gfc_conv_variable
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans-expr.c:2680
0x6fdcda gfc_conv_expr(gfc_se*, gfc_expr*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans-expr.c:7805
0x6d7796 gfc_conv_expr_descriptor(gfc_se*, gfc_expr*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans-array.c:7184
0x6fa627 gfc_conv_procedure_call(gfc_se*, gfc_symbol*, gfc_actual_arglist*,
gfc_expr*, vec<tree_node*, va_gc, vl_embed>*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans-expr.c:5319
0x7443ba gfc_trans_call(gfc_code*, bool, tree_node*, tree_node*, bool)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans-stmt.c:406
0x6bc658 trans_code
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans.c:1891
0x748b88 gfc_trans_block_construct(gfc_code*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans-stmt.c:1821
0x6bc407 trans_code
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans.c:1919
0x7403f3 gfc_trans_if_1
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans-stmt.c:1321
0x74859a gfc_trans_if(gfc_code*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans-stmt.c:1352
0x6bc477 trans_code
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans.c:1911
0x74b282 gfc_trans_select_type_cases
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans-stmt.c:2419
0x74b282 gfc_trans_select_type(gfc_code*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans-stmt.c:3130
0x6bc377 trans_code
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans.c:1939
0x748b88 gfc_trans_block_construct(gfc_code*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans-stmt.c:1821
0x6bc407 trans_code
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans.c:1919
0x6ee028 gfc_generate_function_code(gfc_namespace*)
   
/home/rouson/Desktop/Builds/opencoarrays/prerequisites/downloads/trunk/gcc/fortran/trans-decl.c:6332
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See <https://gcc.gnu.org/bugs/> for instructions.

[Bug fortran/79447] [F08] gfortran rejects valid & accepts invalid internal subprogram in a submodule

2017-03-14 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79447

Damian Rouson  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #6 from Damian Rouson  ---
Comment 7 indicates that a patch was applied to the trunk nearly a month ago so
I assumed this can be marked as Resolved/Fixed.

[Bug fortran/34640] ICE when assigning item of a derived-component to a pointer

2017-03-01 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=34640

Damian Rouson  changed:

   What|Removed |Added

 CC||damian at sourceryinstitute 
dot or
   ||g

--- Comment #28 from Damian Rouson  ---
Below is a reduced version of attachment 38089 from the Comment 27.  gfortran
7.0.1 20170205 produces an ICE on whatever is the first line unless the
penultimate line is removed.

$ cat chester.f90 
  type var_tables
 real, pointer :: rvar(:)
  end type 
  type real_vars
 real r
  end type 
  type(var_tables) vtab_r
  type(real_vars),  target :: x(1)
  vtab_r%rvar => x%r ! deleting this pointer association eliminates the ICE
end 

$ gfortran chester.f90 
chester.f90:1:0:

   type var_tables

internal compiler error: Segmentation fault: 11

chester.f90:1:0: internal compiler error: Abort trap: 6
gfortran: internal compiler error: Abort trap: 6 (program f951)

$ $ gfortran --version
GNU Fortran (MacPorts gcc7 7-20170205_0) 7.0.1 20170205 (experimental)

[Bug fortran/79447] [F08] gfortran rejects valid & accepts invalid internal subprogram in a submodule

2017-02-14 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79447

--- Comment #4 from Damian Rouson  ---
Hi Paul,

Thanks for the updates.  My son loves to host garage sales so let us know if
you're getting rid of the "stuff" and we'll drop by. :) Safe travels. 

Damian

[Bug fortran/79447] [F08] gfortran rejects valid & accepts invalid internal subprogram in a submodule

2017-02-09 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79447

--- Comment #1 from Damian Rouson  ---
I just tested with a more recent build (7.0.1 dated 20170205) and see the same
behavior.

[Bug fortran/79447] New: [F08] gfortran rejects valid & accepts invalid internal subprogram submodule

2017-02-09 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79447

Bug ID: 79447
   Summary: [F08] gfortran rejects valid & accepts invalid
internal subprogram submodule
   Product: gcc
   Version: 7.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

A recent build of gfortran 7 doesn’t allow an internal subprogram to be
contained inside a module subprogram when the subprogram is in a submodule and
is implemented with the “module procedure” keywords instead of “module
subroutine”.  See below.  gfortran 6.3.0 exhibits the same behavior.  It would
be great if any fix can also be back-ported to the 6 branch.

ifort 17 compiles the code below without error.  

Damian


$ cat procedure-contains.f90 
module foo_interface
  implicit none
  interface
module subroutine foo()
end subroutine
  end interface
end module foo_interface

submodule(foo_interface) foo_implementation
contains
module procedure foo
contains
  module subroutine bar()
  end subroutine
end procedure
   !end subroutine ! gfortran accepts this invalid workaround
end submodule 

$ gfortran procedure-contains.f90 
procedure-contains.f90:15:7:

 end procedure
   1
Error: Expecting END SUBROUTINE statement at (1)
procedure-contains.f90:17:3:

 end submodule
   1
Error: Expecting END SUBROUTINE statement at (1)
f951: Error: Unexpected end of file in 'procedure-contains.f90'

$ gfortran --version
GNU Fortran (MacPorts gcc7 7-20170108_0) 7.0.0 20170108 (experimental)

[Bug fortran/79330] New: gfortran 5.4.0/6.3.0/7.0.0 misinterpret type of character literal bind(C,name=...)

2017-02-01 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79330

Bug ID: 79330
   Summary: gfortran 5.4.0/6.3.0/7.0.0 misinterpret type of
character literal bind(C,name=...)
   Product: gcc
   Version: 7.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: damian at sourceryinstitute dot org
  Target Milestone: ---

This a gfortran issue appears in the interface body below, but doesn't
disappears if the procedure is implemented without a separate interface body.
Apparently, the compiler is not exposing variables from the host scope into the
interface body.  Dropping the "module" from "module subroutine" and explicitly
importing the constant via "import :: PREFIX" produces the same error:

$ cat caf_openmp.f90 
module caf_openmp_interface
  implicit none
  character(len=*), parameter :: PREFIX="_gfortran_"
  interface 
module subroutine this_image() bind(C,name=PREFIX//"caf_this_image")
  implicit none
end subroutine
  end interface
end module

$ gfortran -c caf_openmp.f90 
caf_openmp.f90:5:47:

 module subroutine this_image() bind(C,name=PREFIX//"caf_this_image")
   1
Error: Operands of string concatenation operator at (1) are
REAL(4)/CHARACTER(1)
caf_openmp.f90:6:19:

   implicit none
   1
Error: Unexpected IMPLICIT NONE statement in INTERFACE block at (1)
caf_openmp.f90:7:7:

 end subroutine
   1
Error: Expecting END INTERFACE statement at (1)

$ gfortran --version
GNU Fortran (MacPorts gcc7 7-20170108_0) 7.0.0 20170108 (experimental)

This was also tested with gfortran 5.4.0 and 6.3.0.  It would be great if any
fix could be backported to the 5 and 6 branches as well.

[Bug fortran/60913] [OOP] Memory leak with allocatable polymorphic function result (in type-bound operator)

2017-01-24 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=60913

--- Comment #6 from Damian Rouson  ---
I don't have any specific knowledge of it being fixed, but there have been two
releases since 6.1.0: the latest is 6.3.0 and 7.1.0 is expected to be released
soon so the current trunk is a nearly releasable state.  In case it helps, both
6.3.0 and a relatively recent build of 7.0.0 are available in the virtual
machine here: www.sourceryinstitute.org/store.

On a separate note, I am in the process of trying to decide about whether I
will continue to use allocatable polymorphic function results because they are
not allowed in pure functions of which I'm a big fan both for code clarity and
potential performance benefits and especially for the ease with which one can
parallelize expressions comprised of operators implemented as pure functions.

Last, FORALL will be declared obsolescent in Fortran 2015.  In the example that
you posted, I recommend considering DO CONCURRENT as a replacement wherever
possible.

Damian

[Bug fortran/78983] [7 Regression] ICE with CAF-DT with allocatable member

2017-01-17 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=78983

Damian Rouson  changed:

   What|Removed |Added

 CC||damian at sourceryinstitute 
dot or
   ||g

--- Comment #3 from Damian Rouson  ---
Here's a simpler demonstration of two problems this bug report identifies:

module node_module
  implicit none
  type node
integer, allocatable :: storage
  end type
contains
  subroutine reallocate_node_storage(some_node)
type(node) :: some_node
allocate(some_node%storage)  ! needs to generate a call to caf_register
  end subroutine
end module

module caf_module
  use node_module
  type caf
type(node), allocatable :: array[:]
  end type
contains
  subroutine allocate_storage(this)
class(caf) :: this
allocate(this%array[*]) !ICE: no token member initialized for node storage
call reallocate_node_storage(this%array)
  end subroutine
end module

[Bug fortran/78935] [7 Regression] ICE on allocating derived type coarray with allocatable components

2016-12-29 Thread damian at sourceryinstitute dot org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=78935

--- Comment #6 from Damian Rouson  ---
Workaround (4) was supposed to be "when both allocations are moved into the
main program."

  1   2   >