[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-08-15 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

Mikael Morin  changed:

   What|Removed |Added

 Status|ASSIGNED|RESOLVED
 Resolution|--- |FIXED

--- Comment #21 from Mikael Morin  ---
The value_9.f90 FAIL is gone after the commit:
https://gcc.gnu.org/pipermail/gcc-testresults/2023-August/793383.html
whereas it was present before:
https://gcc.gnu.org/pipermail/gcc-testresults/2023-August/793371.html

Closing as FIXED.
Thanks to all who contributed to the resolution.

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-08-14 Thread cvs-commit at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

--- Comment #20 from CVS Commits  ---
The master branch has been updated by Mikael Morin :

https://gcc.gnu.org/g:564b637f4a32883cbf3c3019d3cfcf0b0aec9b82

commit r14-3207-g564b637f4a32883cbf3c3019d3cfcf0b0aec9b82
Author: Mikael Morin 
Date:   Mon Aug 14 21:51:54 2023 +0200

fortran: Fix length one character dummy arg type [PR110419]

Revision r14-2171-g8736d6b14a4dfdfb58c80ccd398981b0fb5d00aa
changed the argument passing convention for length 1 value dummy
arguments to pass just the single character by value.  However, the
procedure declarations weren't updated to reflect the change in the
argument types.
This change does the missing argument type update.

The change of argument types generated an internal error in
gfc_conv_string_parameter with value_9.f90.  Indeed, that function is
not prepared for bare character type, so it is updated as well.

The condition guarding the single character argument passing code
is loosened to not exclude non-interoperable kind (this fixes
a regression with c_char_tests_2.f03).

Finally, the constant string argument passing code is updated as well
to extract the single char and pass it instead of passing it as
a length one string.  As the code taking care of non-constant arguments
was already doing this, the condition guarding it is just removed.

With these changes, value_9.f90 passes on 32 bits big-endian powerpc.

PR fortran/110360
PR fortran/110419

gcc/fortran/ChangeLog:

* trans-types.cc (gfc_sym_type): Use a bare character type for
length
one value character dummy arguments.
* trans-expr.cc (gfc_conv_string_parameter): Handle single
character
case.
(gfc_conv_procedure_call): Don't exclude interoperable kinds
from single character handling.  For single character dummy
arguments,
extend the existing handling of non-constant expressions to
constant
expressions.

gcc/testsuite/ChangeLog:

* gfortran.dg/bind_c_usage_13.f03: Update tree dump patterns.

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-08-10 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

Mikael Morin  changed:

   What|Removed |Added

 Status|NEW |ASSIGNED
   Assignee|unassigned at gcc dot gnu.org  |mikael at gcc dot 
gnu.org

--- Comment #19 from Mikael Morin  ---
Patch submitted:
https://gcc.gnu.org/pipermail/fortran/2023-August/059666.html
https://gcc.gnu.org/pipermail/gcc-patches/2023-August/626870.html

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-07-31 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

--- Comment #18 from Mikael Morin  ---
Created attachment 55662
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=55662=edit
Updated tentative patch

This fixes comment #4 as well, but the failure on value_9 remains on 32 bit
powerpc.

It is almost testsuite clean on x86_64.

There is a regression on c_char_tests_2.f03 because there is a hole in the
handling of single char values in gfc_conv_procedure_call.
Length one arguments are handled with:

6436  else if (fsym && fsym->attr.value)
6437{
6438  if (fsym->ts.type == BT_CHARACTER
6439  && fsym->ts.is_c_interop
6440  && fsym->ns->proc_name != NULL
6441  && fsym->ns->proc_name->attr.is_bind_c)
6442{
  // Pass single char value
6447}
6448  else
6449{
6450gfc_conv_expr (, e);
6451

6456if (!fsym->ts.is_c_interop
6457&& gfc_length_one_character_type_p (>ts))
6458  {
// pass single char value


The failing case is when the type is interoperable (character(c_char)), but the
procedure is not bind(c).  So the translation from string to single character
is neither done in the if branch (the procedure is not bind(c)) nor in the if
of the else branch (the type is interoperable).

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-07-30 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

--- Comment #17 from Mikael Morin  ---
Created attachment 55660
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=55660=edit
Update function type patch

This patch changes the dummy argument declaration type.
It changes the dump as follows.

--- m32/pr110419_comment4.f90.005t.original 2023-07-05 13:05:58.743843174
+
+++ pr110419_comment4.f90.005t.original 2023-07-30 19:31:20.880043687 +
@@ -1,5 +1,5 @@
 __attribute__((fn spec (". r w ")))
-void val (character(kind=1)[1:1] & restrict x, character(kind=1)[1:1] c,
integer(kind=4) _x, integer(kind=4) _c)
+void val (character(kind=1)[1:1] & restrict x, character(kind=1) c,
integer(kind=4) _x, integer(kind=4) _c)
 {
   {
 struct __st_parameter_dt dt_parm.0;
@@ -25,7 +25,7 @@
 _gfortran_transfer_character_write (_parm.1, , 1);
 _gfortran_st_write_done (_parm.1);
   }
-  if (c[1]{lb: 1 sz: 1} != (*x)[1]{lb: 1 sz: 1})
+  if ((*x)[1]{lb: 1 sz: 1} != c)
 {
   _gfortran_stop_numeric (1, 0);
 }
@@ -36,7 +36,7 @@
 __attribute__((fn spec (". ")))
 void p ()
 {
-  static void val (character(kind=1)[1:1] & restrict, character(kind=1)[1:1],
integer(kind=4), integer(kind=4));
+  static void val (character(kind=1)[1:1] & restrict, character(kind=1),
integer(kind=4), integer(kind=4));
   static integer(kind=4) a = 65;

   {

It seems to fix comment #4 (both 32 and 64 bits).

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-07-18 Thread dje at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

David Edelsohn  changed:

   What|Removed |Added

 Status|UNCONFIRMED |NEW
 CC||dje at gcc dot gnu.org
   Last reconfirmed||2023-07-18
 Ever confirmed|0   |1

--- Comment #16 from David Edelsohn  ---
As I wrote in issue 110360, the bug appears to be the memory layout and padding
assumed by GFortran that does not take into account endianness.

I have changed val() to print both c and x, and not halt.

  subroutine val (x, c)
character(kind=1), intent(in) :: x  ! control: pass by reference
character(kind=1), value  :: c
print *, "by value(kind=1): ", x
print *, "by value(kind=1): ", c
!if (c /= x)   stop 1
c = "*"
if (c /= "*") stop 2
  end


The output is:

 by value(kind=1): B
 by value(kind=1): B
 by value(kind=1): A
 by value(kind=1): A
 by value(kind=1): A
 by value(kind=1):<- c
 by value(kind=1): A
 by value(kind=1):<- c
 by value(kind=1): A
 by value(kind=1):<- c
 by value(kind=1): 1
 by value(kind=1):<- c
 by value(kind=1): 1
 by value(kind=1):<- c


The assembly language for the first few calls is

# call val  ("B","B")
lwz 31,LC..5(2)  LOAD ADDRESS of x
mr 3,31  COPY address to first parameter
li 6,1
li 5,1
lbzu 4,148(3)LOAD BYTE of c as second parameter
slwi 4,4,24  SHIFT c 24 bits
bl .val.4
# call val  ("A",char(65))
mr 30,31 COPY ADDRESS of x
li 6,1
li 5,1
lbzu 4,152(30)   LOAD BYTE of c as second parameter
slwi 4,4,24  SHIFT c 24 bits
mr 3,30  COPY address of first parameter
bl .val.4
# call val  ("A",char(a))
li 6,1
li 5,1
li 4,65  <- c NOT SHIFTED
mr 3,30  <- x
bl .val.4
# call val  ("A",mychar(65))
li 6,1
li 5,1
li 4,65  <- c NOT SHIFTED
mr 3,30  <- x
bl .val.4
# call val  ("A",mychar(a))
li 6,1
li 5,1
li 4,65  <- c NOT SHIFTED
mr 3,30  <- x
bl .val.4

GFortran is not taking account of endianness for the layout of values in memory
compared to constants loaded into registers.  This isn't an ABI issue of the
target, this is a memory layout and register layout issue of GFortran.

On a big endian system, a character / byte is loaded at the LSB, but GFortran
seems to be comparing it to a memory image with the character / byte stored at
the MSB, which would be correct for little endian.  In some cases, GFortran is
shifting the value and in other cases it is not.

GFortran does not seem to have a consistent view of the memory layout for
characters / bytes loaded into a larger object.

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-07-15 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

--- Comment #15 from Mikael Morin  ---
rs6000_pass_by_reference returns true with -m32, and false with -m64.

So the second argument is passed by reference with -m32, and by value with
-m64.
So the code in val looks right, it is the code in p calling val which isn't.


val is declared as:

void val (character(kind=1)[1:1] & restrict x, character(kind=1)[1:1] c,
integer(kind=8) _x, integer(kind=8) _c)

so the second argument has array type, whereas p calls val with:

void p ()
{
  ...
  character(kind=1) char.5_3;

   :
  ...
  val (&"A"[1]{lb: 1 sz: 1}, char.5_3, 1, 1); [static-chain: ]

so the second actual argument has non-array type.

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-07-06 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

--- Comment #14 from Mikael Morin  ---
The tree optimized dumps are almost the same for 32 and 64 bits.

The expand dumps show more significant differences.


The 64 bits dump shows the register r4 is saved to memory  with:

(insn 3 2 4 2 (set (mem/c:QI (plus:DI (reg/f:DI 111 virtual-incoming-args)
(const_int 8 [0x8])) [10 c+0 S1 A64])
(reg:QI 4 4 [ c ])) "pr110419_comment4.f90":6:16 -1
 (nil))


The 32 bits dump shows:

(insn 3 2 4 2 (set (reg/v:SI 119)
(reg:SI 4 4)) "pr110419_comment4.f90":6:16 -1
 (nil))
(insn 4 3 5 2 (set (reg:QI 120)
(mem/c:QI (reg/v:SI 119) [10 c+0 S1 A8])) "pr110419_comment4.f90":6:16
-1
 (nil))

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-07-06 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

--- Comment #13 from Mikael Morin  ---
Created attachment 55488
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=55488=edit
-m64 rtl final dump at -O0

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-07-06 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

--- Comment #12 from Mikael Morin  ---
Created attachment 55487
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=55487=edit
-m64 rtl expand dump at -O0

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-07-06 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

--- Comment #11 from Mikael Morin  ---
Created attachment 55486
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=55486=edit
-m64tree optimized (at -O0) dump

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-07-05 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

--- Comment #10 from Mikael Morin  ---
The three previous dumps are generated with the example in comment #4.

The problem seems to turn around the val function needing to take the address
of the c argument, which is passed by value.
On powerpc, the value is available in a register. I guess the ABI specifies how
this case is supposed to work?

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-07-05 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

--- Comment #9 from Mikael Morin  ---
Created attachment 55480
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=55480=edit
-m32 final rtl dump at -O0

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-07-05 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

--- Comment #8 from Mikael Morin  ---
Created attachment 55479
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=55479=edit
-m32 rtl exand dump at -O0

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-07-05 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

--- Comment #7 from Mikael Morin  ---
Created attachment 55478
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=55478=edit
-m32 tree optimized (at -O0) dump

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-07-05 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

--- Comment #6 from Mikael Morin  ---
I finally got my access on gcc110 working.

(gdb) r
Starting program: /home/mmorin/gcc-pr110360/pr110360/pr110419_comment4 

Program received signal SIGSEGV, Segmentation fault.
0x1684 in val (x=..., c=..., _x=268635256, _c=268635135) at
pr110419_comment4.f90:6
6 subroutine val (x, c)
(gdb) x/4cb 
0x1abc: 65 'A'  0 '\000'0 '\000'0 '\000'
(gdb) x/4cb   
0xfffef30c: 0 '\000'0 '\000'0 '\000'8 '\b'
(gdb) p _x
$1 = 268635256
(gdb) p _c
$2 = 268635135
(gdb) info registers
r0 0x1804  268437508
r1 0xfffef1a0  4294898080
r2 0xf7fe9e40  4160659008
r3 0x1abc  268438204
r4 0x4165
r5 0x1 1
r6 0x1 1
r7 0x0 0
r8 0xfd60354   265683796
r9 0x1000  268435456
r100xfffef338  4294898488
r110xfffef338  4294898488
r120x24000842  603981890
r130x10028028  268599336
r140x0 0
r150x0 0
r160x0 0
r170x0 0
r180x0 0
r190x0 0
r200x0 0
r210x0 0
r220x0 0
r230x0 0
r240x0 0
r250x0 0
r260x0 0
r270xf7fdf970  4160616816
r280xf7fe  4160618496
r290x0 0
r300x4165
r310xfffef1a0  4294898080
pc 0x1684  0x1684 
msr0xd032  53298
cr 0x24000842  603981890
lr 0x1804  0x1804 
ctr0xfc248a0   264390816
xer0x0 0
fpscr  0x0 0
vscr   0x1 65536
vrsave 0x  -1
orig_r30x1800  268437504
trap   0x300   768
(gdb) p 
$3 = (PTR TO -> ( character*1 )) 0x1abc


The debug info seems to be somewhat broken, but the arguments seem to be passed
to r3, r4, r5, r6 registers and have the right value there.


(gdb) disass
Dump of assembler code for function val:
   0x1664 <+0>: stwur1,-400(r1)
   0x1668 <+4>: mflrr0
   0x166c <+8>: stw r0,404(r1)
   0x1670 <+12>:stw r30,392(r1)
   0x1674 <+16>:stw r31,396(r1)
   0x1678 <+20>:mr  r31,r1
   0x167c <+24>:stw r3,360(r31)
   0x1680 <+28>:mr  r30,r4
=> 0x1684 <+32>:lbz r9,0(r30)
   0x1688 <+36>:stb r9,364(r31)
   0x168c <+40>:stw r5,368(r31)
   0x1690 <+44>:stw r6,372(r31)
   0x1694 <+48>:stw r11,376(r31)
   0x1698 <+52>:lis r9,4096
   0x169c <+56>:addir9,r9,2676

Not sure I read assembly correctly, but looks like we are trying to load the
second argument (available in r4) by reference instead of by value.

I don't know what to look at next.

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-07-02 Thread anlauf at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

--- Comment #5 from anlauf at gcc dot gnu.org ---
The testers show a similar behavior on sparcv9-sun-solaris2.11:
OK at -m64, FAIL at -m32.  Not sure which endianness that is.

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-06-29 Thread anlauf at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

--- Comment #4 from anlauf at gcc dot gnu.org ---
It appears that the issue could be studied with the following code:

program p
  implicit none
  integer :: a = 65
  call val ("A", char(a))
contains
  subroutine val (x, c)
character(kind=1), intent(in) :: x  ! control: pass by reference
character(kind=1), value  :: c
print *, "by reference(kind=1): ", x
print *, "by value(kind=1): ", c
if (c /= x)   stop 1
  end
end

If this works on LE with -m64 and -m32, and also on BE with -m64,
why would it fail on BE with -m32 ?

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-06-29 Thread seurer at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

--- Comment #3 from seurer at gcc dot gnu.org ---
I just tried r14-2190-ge972bdce61cc52 on another BE machine and got:

spawn [open ...]
 by value(kind=1): B
 by value(kind=1): A

Program received signal SIGSEGV: Segmentation fault - invalid memory reference.

Backtrace for this error:
#0  0xf7f603f3 in ???
#1  0x1fcc in ???
#2  0x1adb in ???
#3  0xfa5a81f in ???
#4  0xfa5aa5f in ???
#5  0x in ???
FAIL: gfortran.dg/value_9.f90   -Os  execution test

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-06-29 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

--- Comment #2 from Mikael Morin  ---
(In reply to Mikael Morin from comment #1)
> Harald committed an additional fix to the PR:
> 
Unfortunately, the failure on big endian power remains.
Is the execution output the same as before?

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-06-29 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

Mikael Morin  changed:

   What|Removed |Added

 CC||mikael at gcc dot gnu.org

--- Comment #1 from Mikael Morin  ---
Harald committed an additional fix to the PR:

The master branch has been updated by Harald Anlauf :

https://gcc.gnu.org/g:8736d6b14a4dfdfb58c80ccd398981b0fb5d00aa

commit r14-2171-g8736d6b14a4dfdfb58c80ccd398981b0fb5d00aa
Author: Harald Anlauf 
Date:   Wed Jun 28 22:16:18 2023 +0200

Fortran: ABI for scalar CHARACTER(LEN=1),VALUE dummy argument [PR110360]

gcc/fortran/ChangeLog:

PR fortran/110360
* trans-expr.cc (gfc_conv_procedure_call): For non-constant string
argument passed to CHARACTER(LEN=1),VALUE dummy, ensure proper
dereferencing and truncation of string to length 1.

gcc/testsuite/ChangeLog:

PR fortran/110360
* gfortran.dg/value_9.f90: Add tests for intermediate regression.

[Bug testsuite/110419] [14 regression] new test case gfortran.dg/value_9.f90 in r14-2050-gd130ae8499e0c6 fails

2023-06-27 Thread rguenth at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110419

Richard Biener  changed:

   What|Removed |Added

   Keywords||testsuite-fail
  Component|other   |testsuite
   Target Milestone|--- |14.0