[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)