[Bug fortran/108680] New: Wrong DTIO arguments with -fdefault-integer-8

2023-02-05 Thread albandil at atlas dot cz via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=108680

Bug ID: 108680
   Summary: Wrong DTIO arguments with -fdefault-integer-8
   Product: gcc
   Version: 13.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: albandil at atlas dot cz
  Target Milestone: ---

Wrong DTIO arguments with -fdefault-integer-8

It seems that gfortran miscompiles the following simple program when
`-fdefault-integer-8` compiler option is used:

module types

type dtype
contains
procedure :: write_formatted
generic, public :: write(formatted) => write_formatted
end type

contains

subroutine write_formatted (this, unit, iotype, v_list, iostat, iomsg)

class(dtype), intent(in):: this
integer,  intent(in):: unit, v_list(:)
character(*), intent(in):: iotype
integer,  intent(out)   :: iostat
character(*), intent(inout) :: iomsg

iostat = 0

print *, 'v_list', v_list

end subroutine write_formatted

end module types


program p

use types, only: dtype

type(dtype) :: data
integer :: u

open (file = 'output.txt', newunit = u, form = 'formatted')
write (u, '(dt(1,2,3))') data
close (u)

end program p

The derived type `dtype` should be given integers 1,2,3 in the v_list parameter
of the `write(formatted)` subroutine, which only echoes them out for feedback.
This works with Intel compilers regardless of the default integer type.
However, the output is wrong if I combine gfortran `-fdefault-integer-8`. The
behaviour is the same with the current git version as well as with GCC release
11.3, so the problem has been around for some time.

$ /opt/gcc-git/bin/gfortran --version | head -n 1
GNU Fortran (GCC) 13.0.1 20230205 (experimental)
$ /opt/gcc-git/bin/gfortran main.f90 
$ ./a.out 
 v_list   1   2   3
$ /opt/gcc-git/bin/gfortran -fdefault-integer-8 main.f90 
$ ./a.out 
 v_list   858993459330

$ gfortran-11 --version | head -n 1
GNU Fortran (SUSE Linux) 11.3.1 20221024 [revision
bd0c76a2329e7fe6d6612c2259647bbb67f5866a]
$ gfortran-11 -fdefault-integer-8 main.f90 
$ ./a.out 
 v_list   858993459330

$ ifx --version | head -n 1
ifx (IFORT) 2023.0.0 20221201
$ ifx -i8 main.f90 
$ ./a.out 
 v_list 1 2 3

$ ifort --version | head -n 1
ifort (IFORT) 2021.8.0 20221119
$ ifort -i8 main.f90 
$ ./a.out 
 v_list 1 2 3

It looks as if the subroutine was actually getting pointers to 4-byte integers
regardless of the switch, because the large value pritned first is actually
composition of the missing 2 and 1:

8589934593 ~ 0010
0001
   ~ 2 1

[Bug fortran/104972] New: Class dummy argument for array of custom types stuck on -fcheck=bounds

2022-03-17 Thread albandil at atlas dot cz via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=104972

Bug ID: 104972
   Summary: Class dummy argument for array of custom types stuck
on -fcheck=bounds
   Product: gcc
   Version: 11.2.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: albandil at atlas dot cz
  Target Milestone: ---

When the following program is compiled with `-fcheck=bounds` using a recent
version of gfortran, it triggers a bogus (?) error:

program test

type vec
integer :: x(3)
end type

type(vec) :: v(2)

call sub(v)

contains

subroutine sub (v)

class(vec), intent(in) :: v(:)

integer :: k, q(3)

q = [ (v(1)%x(k), k = 1, 3) ]   ! <-- fails here

   end subroutine

end program

The error message is

At line 19 of file test.f90
Fortran runtime error: Index '3' of dimension 1 of array 'v%_data%x' above
upper bound of 2

When the lengths of the arrays `x` and `v` in the code are modified, the
message changes as well, but it always appears as if the compiler interchanged
the dimension of `v` and of `x`. I observe this behaviour with the compiler
version on openSUSE Tumbleweeed 20220316

$ gfortran --version
GNU Fortran (SUSE Linux) 11.2.1 20220103 [revision
d4a1d3c4b377f1d4acb34fe1b55b5088a3f293f6]

I also got the same run-time errors when pulling and compiling a recent Git
version of GCC,

$ gfortran --version
GNU Fortran (GCC) 12.0.1 20220310 (experimental)

However, in older versions of the compiler (8, 9 and 10) using the
`-fcheck=bounds` flag with this program works fine. Provided that the code is
syntactically valid as it is, this suggests a compiler regression.

The error goes away also when I replace the keyword `class` with `type`.

[Bug fortran/89039] Logical read from stream file that is neither 0 nor 1

2019-01-24 Thread albandil at atlas dot cz
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89039

--- Comment #2 from Jakub Benda  ---
The quotation from the manual

> Any other integer value results in undefined behavior.

is very explicit. Also, I see that using

ifort -fpscomp logicals

will make ifort compatible with the rest of the world in this regard, so I
agree that the proper flag for this report is INVALID.

Thanks!

[Bug fortran/89039] New: Logical read from stream file that is neither 0 nor 1

2019-01-24 Thread albandil at atlas dot cz
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89039

Bug ID: 89039
   Summary: Logical read from stream file that is neither 0 nor 1
   Product: gcc
   Version: 9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: albandil at atlas dot cz
  Target Milestone: ---

Related to https://gcc.gnu.org/bugzilla/show_bug.cgi?id=22495

Logicals read from an unformatted stream file that are neither 0 nor 1 behave
like this:

print *, b, .not. b

T T

i.e., both they and their negations evaluate to .true.

This reduces portability of stream files. For example, ifort uses -1 as .true.,
but when such stream files are read by gfortran, the nonzero value is not
converted to gfortran's .true.

(Maybe there is nothing that requires it, I don't know.)

[Bug fortran/84674] [7/8/9 Regression] Derived type name change makes a program segfault, removing non_overridable helps

2018-07-29 Thread albandil at atlas dot cz
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84674

--- Comment #3 from Jakub Benda  ---
Bisection points to revision 254427 from 5 November 2017, which adds this chunk
of code to "fortran/resolv.c" (function "resolve_fl_derived", lines
14081-14093):

  /* Generate module vtables subject to their accessibility and their not
 being vtables or pdt templates. If this is not done class declarations
 in external procedures wind up with their own version and so SELECT TYPE
 fails because the vptrs do not have the same address.  */
  if (gfc_option.allow_std & GFC_STD_F2003
  && sym->ns->proc_name
  && sym->ns->proc_name->attr.flavor == FL_MODULE
  && sym->attr.access != ACCESS_PRIVATE
  && !(sym->attr.use_assoc || sym->attr.vtype || sym->attr.pdt_template))
{
  gfc_symbol *vtab = gfc_find_derived_vtab (sym);
  gfc_set_sym_referenced (vtab);
}

When I comment it out, the compiled program works as expected.

[Bug fortran/84674] New: Derived type name change makes a program segfault, removing non_overridable

2018-03-02 Thread albandil at atlas dot cz
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84674

Bug ID: 84674
   Summary: Derived type name change makes a program segfault,
removing non_overridable
   Product: gcc
   Version: 8.0.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: albandil at atlas dot cz
  Target Milestone: ---

Take the program code from
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61284#c0 , change derived type
name "t3" to "DerivedType" (three places in the code) and compile the result by
gfortran 7.3.0. It will compile fine, but result in segmentation fault at
runtime, even though the original code (with "t3") now runs all right.

When the modified code is compiled with gfortran 7.2.0 or ifort 17.0.0, it also
runs well, without crashing.

Finally, when "non_overridable" keyword on line 12 is removed (as indicated in
the commented line 13), the modified program runs well, too, even when compiled
by gfortran 7.3.0.

For reference, here is the failing code:

 module m
  implicit none

  type, abstract :: t1
   integer :: i
  contains
   procedure(i_f), pass(u), deferred :: ff
  end type t1

  type, abstract, extends(t1) :: t2
  contains
   procedure, non_overridable, pass(u) :: ff => f ! Segmentation fault 
   !procedure, pass(u) :: ff => f ! works
  end type t2

  type, extends(t2) :: DerivedType
  end type DerivedType

  abstract interface
   subroutine i_f(u)
import :: t1
class(t1), intent(inout) :: u
   end subroutine i_f
  end interface

 contains

  subroutine f(u)
   class(t2), intent(inout) :: u
u%i = 3*u%i
  end subroutine f

 end module m


 program p

  use m

  implicit none

  class(t1), allocatable :: v

  allocate(DerivedType::v)
  v%i = 2
  call v%ff()
  write(*,*) v%i
 end program p

[Bug libfortran/84529] New: INQUIRE fails on "recycled" internal units

2018-02-23 Thread albandil at atlas dot cz
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84529

Bug ID: 84529
   Summary: INQUIRE fails on "recycled" internal units
   Product: gcc
   Version: 7.3.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: libfortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: albandil at atlas dot cz
  Target Milestone: ---

The following program fails with the error "Inquire statement identifies an
internal file" at the call to INQUIRE.

  program TestRecycleInternalUnit

implicit none

integer :: iunit, ipos
character(len=10) :: sstream

write(sstream,'(I0)') 12345
print *, 'sstream = ', sstream

open(newunit=iunit, file='output.bin', access="stream", form="unformatted")
inquire(iunit,pos=ipos)
print *, 'n = ', ipos
close(iunit)

  end program TestRecycleInternalUnit

I looked into the code of libgfortran/io/open.c (and around) and it seems that
OPEN reuses the cached internal unit (-10 in this case) used for writing to
string. However, the member "internal_unit_kind" of the unit structure is not
reset to 0 in the "st_open" function. This makes the subsequent INQUIRE think
that its argument is an internal unit.

[Bug fortran/84506] New: INQUIRE(pos=) always sets pos=0 with -fdefault-integer-8

2018-02-21 Thread albandil at atlas dot cz
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84506

Bug ID: 84506
   Summary: INQUIRE(pos=) always sets pos=0 with
-fdefault-integer-8
   Product: gcc
   Version: 7.3.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: albandil at atlas dot cz
  Target Milestone: ---

INQUIRE(pos=...) seems to set 'pos' to zero when the unit number is 64bit
integer. This can be illustrated on the following example, which writes four
characters to a stream file and then INQUIRES position:

  program TestInquire

  implicit none

  integer :: iUnit, iPos

  open(newunit=iunit, file='output.txt', access='stream',
position='append', form='unformatted')
  write(iUnit) 'TEXT'
  inquire(iUnit, pos=iPos)

  print *, iPos

  end program TestInquire

The expected output is '5', which can be obtained by compilation using the
command

  gfortran -ffree-form -std=f2008 inquire.f -o inquire

However, when the following command is used to compile the program, the output
is '0':

  gfortran -ffree-form -std=f2008 inquire.f -o inquire -fdefault-integer-8

Both 4-byte and 8-byte mode produce '5' when Intel Fortran Compiler 17.0.1 is
used,

  ifort -free -stand=f08 inquire.f -o inquire
  ifort -free -stand=f08 inquire.f -o inquire -i8