[Bug fortran/97122] Spurious FINAL ... must be in the specification part of a MODULE

2023-05-04 Thread ian_harvey at bigpond dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=97122

--- Comment #6 from Ian Harvey  ---
A module procedure is defined by a module subprogram (F2018 15.2.2.2p3).  A
module subprogram (or any subprogram) is a syntax element (a piece of source
code), equivalent to /module-subprogram/ (see the first sentence of F2018
4.1.5p1).  The things that appear after the CONTAINS in a submodule are module
subprograms (see the definitions of /submodule/ and /module-subprogram-part/).

[Bug fortran/97122] New: Spurious FINAL ... must be in the specification part of a MODULE

2020-09-19 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=97122

Bug ID: 97122
   Summary: Spurious FINAL ... must be in the specification part
of a MODULE
   Product: gcc
   Version: 11.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com
  Target Milestone: ---

When compiling the following, recent master (and 10.2.1) issues an error 

  Error: Derived type declaration with FINAL at (1) must be in the
specification part of a MODULE

There is no such requirement in the language.



MODULE m
  IMPLICIT NONE
  INTERFACE
MODULE SUBROUTINE other
  IMPLICIT NONE
END SUBROUTINE other
  END INTERFACE
END MODULE m

SUBMODULE (m) s
  IMPLICIT NONE
  TYPE :: t
  CONTAINS
FINAL :: p
  END TYPE t
CONTAINS
  SUBROUTINE p(arg)
TYPE(t), INTENT(INOUT) :: arg
  END SUBROUTINE p

  MODULE SUBROUTINE other
  END SUBROUTINE other
END SUBMODULE s



]$ gfortran -v -c 2020-09-20\ final.f90
Using built-in specs.
COLLECT_GCC=gfortran
Target: x86_64-pc-linux-gnu
Configured with: .././src/configure --prefix=/home/MEGMS2/ian/usr/gcc-11.0.0
--enable-languages=c,c++,fortran,lto --enable-libgomp --enable-checking=release
--disable-multilib
Thread model: posix
Supported LTO compression algorithms: zlib
gcc version 11.0.0 20200919 (experimental) (GCC)
COLLECT_GCC_OPTIONS='-v' '-c' '-mtune=generic' '-march=x86-64'
 /home/MEGMS2/ian/usr/gcc-11.0.0/libexec/gcc/x86_64-pc-linux-gnu/11.0.0/f951
2020-09-20 final.f90 -quiet -dumpbase 2020-09-20 final.f90 -dumpbase-ext .f90
-mtune=generic -march=x86-64 -version -fintrinsic-modules-path
/home/MEGMS2/ian/usr/gcc-11.0.0/lib/gcc/x86_64-pc-linux-gnu/11.0.0/finclude
-fpre-include=/usr/include/finclude/math-vector-fortran.h -o /tmp/ccPu3yxp.s
GNU Fortran (GCC) version 11.0.0 20200919 (experimental) (x86_64-pc-linux-gnu)
compiled by GNU C version 11.0.0 20200919 (experimental), GMP version
6.1.2, MPFR version 4.0.2-p9, MPC version 1.1.0, isl version isl-0.16.1-GMP

GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
GNU Fortran2008 (GCC) version 11.0.0 20200919 (experimental)
(x86_64-pc-linux-gnu)
compiled by GNU C version 11.0.0 20200919 (experimental), GMP version
6.1.2, MPFR version 4.0.2-p9, MPC version 1.1.0, isl version isl-0.16.1-GMP

GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
2020-09-20 final.f90:14:10:

   14 | FINAL :: p
  |  1
Error: Derived type declaration with FINAL at (1) must be in the specification
part of a MODULE

[Bug fortran/97036] New: [F2018] ELEMENTAL RECURSIVE subprogram prefix combination rejected

2020-09-12 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=97036

Bug ID: 97036
   Summary: [F2018] ELEMENTAL RECURSIVE subprogram prefix
combination rejected
   Product: gcc
   Version: 11.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com
  Target Milestone: ---

F2018 removed the previous syntax restriction (F2008 C1245) on a subprogram
definition with both ELEMENTAL and RECURSIVE.

  MODULE m
IMPLICIT NONE
  CONTAINS
ELEMENTAL RECURSIVE SUBROUTINE foo
END SUBROUTINE foo
  END MODULE m



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



$ gfortran -c 2020-09-13\ elemental-recursive.f90 -std=f2018
2020-09-13 elemental-recursive.f90:4:22:

4 |   ELEMENTAL RECURSIVE SUBROUTINE foo
  |  1
Error: ELEMENTAL attribute conflicts with RECURSIVE attribute at (1)
2020-09-13 elemental-recursive.f90:5:5:

5 |   END SUBROUTINE foo
  | 1
Error: Expecting END MODULE statement at (1)

[Bug fortran/89646] Spurious actual argument might interfere warning

2019-03-12 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89646

--- Comment #2 from Ian Harvey  ---
The spurious warning is issued regardless of whether warnings are requested or
not (i.e. it is reported with a command line of just `gfortran -c file.f90`). 
The warning is issued even if -Wno-aliasing is explicitly provided.

[Bug fortran/89647] New: Host associated procedure unable to be used as binding target

2019-03-10 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89647

Bug ID: 89647
   Summary: Host associated procedure unable to be used as binding
target
   Product: gcc
   Version: 9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com
  Target Milestone: ---

The following example:

  MODULE m1
IMPLICIT NONE
PUBLIC :: False
PUBLIC :: True
  CONTAINS
FUNCTION False() RESULT(b)
  LOGICAL :: b
  b = .FALSE.
END FUNCTION False

FUNCTION True() RESULT(b)
  LOGICAL :: b
  b = .TRUE.
END FUNCTION True
  END MODULE m1

  MODULE m2
USE m1
IMPLICIT NONE
TYPE, ABSTRACT :: t_parent
CONTAINS
  PROCEDURE(False), DEFERRED, NOPASS :: Binding
END TYPE t_parent
  CONTAINS
SUBROUTINE s
  TYPE, EXTENDS(t_parent) :: t_extension
  CONTAINS
PROCEDURE, NOPASS :: Binding => True
  END TYPE t_extension
END SUBROUTINE s
  END MODULE m2

when compiled with recent trunk (r269545) results in the error:

  binding.f90:28:15:

 28 |   PROCEDURE, NOPASS :: Binding => True
|   1
  Error: ‘true’ must be a module procedure or an external procedure with an
explicit interface at (1)

`True` is a module procedure, and it is available within the scope of the
subroutine by host association.

[Bug fortran/89646] New: Spurious actual argument might interfere warning

2019-03-09 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89646

Bug ID: 89646
   Summary: Spurious actual argument might interfere warning
   Product: gcc
   Version: 9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com
  Target Milestone: ---

The following:

  MODULE m
IMPLICIT NONE
TYPE :: t
END TYPE t
  CONTAINS
SUBROUTINE s
  ! To reproduce, both actual arguments must be TARGET, 
  ! both arguments must be of derived type.
  TYPE(t), TARGET :: a(5)
  TYPE(t), TARGET :: b(5)

  CALL move(a, b)
END SUBROUTINE s

! To reproduce, called procedure must be elemental.
ELEMENTAL SUBROUTINE move(from, to)
  TYPE(t), INTENT(INOUT) :: from
  TYPE(t), INTENT(OUT) :: to
END SUBROUTINE move
  END MODULE m

when compiled with recent trunk (r26545) gives the following spurious warnings:

  argument-interfereb.f90:12:14-17:

 12 | CALL move(a, b)
|  1  2
  Warning: INTENT(INOUT) actual argument at (1) might interfere with actual
argument at (2).
  argument-interfereb.f90:12:14-17:

 12 | CALL move(a, b)
|  2  1
  Warning: INTENT(OUT) actual argument at (1) might interfere with actual
argument at (2).

I suspect that the compiler is trying to warn me about potential aliasing given
the TARGET attribute on the actual arguments, but there is no such aliasing in
this example, and the details required to trigger the warning (arguments must
be derived type, procedure must be elemental) are too specific for this warning
to be useful or intended.

[Bug fortran/89645] New: No IMPLICIT type error with: ASSOCIATE( X => function() )

2019-03-09 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=89645

Bug ID: 89645
   Summary: No IMPLICIT type error with: ASSOCIATE( X =>
function() )
   Product: gcc
   Version: 9.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com
  Target Milestone: ---

The module:

  MODULE m
IMPLICIT NONE
TYPE :: t
  INTEGER :: comp
END TYPE t
  CONTAINS
SUBROUTINE s
  ASSOCIATE(b => fun())
PRINT *, b%comp
  END ASSOCIATE
END SUBROUTINE s

FUNCTION fun() RESULT(r)
  TYPE(t) :: r
  r = t(1)
END FUNCTION fun
  END MODULE m

when compiled with recent trunk (r269545) gives:

  9 |   PRINT *, b%comp
| 1
  Error: Symbol ‘b’ at (1) has no IMPLICIT type

F2003 rules (8.1.4.2) and subsequent standards state for the associate
statement that the entity identified by the associate name assumes the declared
type of the selector.

(This has some similarity to pr60483, which related to structure constructors.)

[Bug fortran/64678] [F03] Expected association error on dependent associate statements

2019-03-09 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64678

Ian Harvey  changed:

   What|Removed |Added

 CC||ian_harvey at bigpond dot com

--- Comment #6 from Ian Harvey  ---
This comes up from time to time in various places...

F2003/F2008 and F2018 all include words in the section on the scope of
statement and construct entities (F2018 19.4) that the "associate names of an
ASSOCIATE construct have the scope of the block", where "the block" is the
chunk of source that is in between the ASSOCIATE and END ASSOCIATE statements,
excluding those delimiting statements (see F2018 R1102).

The original code is non-conforming - the associate name A is not in scope
within the associate statement (versus "the block"), so `A` in the second
association is an implicitly declared variable of type REAL, and a REAL
variable does not have a component or type parameter named `map`.

Current trunk rejects the code with an appropriate error message.

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

2017-01-27 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=60913

Ian Harvey  changed:

   What|Removed |Added

 CC||ian_harvey at bigpond dot com

--- Comment #10 from Ian Harvey  ---
The issue appears to be that code generated by the compiler does not deallocate
the polymorphic allocatable function result when the innermost executable
construct containing the function reference terminates (F2008 6.7.3.2p5).  This
only appears to be the case for when the function result is polymorphic.

Clarifying questions here and elsewhere - this is something that only the
compiler can arrange (it must be "automatic"), as the allocatable
characteristic of the function result is only accessible to the compiler in the
calling scope.  The user does not need to arrange anything - there is nothing
they can arrange.  The presence or absence of a finalizer is not relevant - a
finalizer cannot explicitly deallocate the object that it is finalizing, it can
only explicitly deallocate allocatable sub-objects of the object being
finalized.  The type declaration statements mentioned in #8 are not
particularly relevant, the issue is with the handling of function references.

This may be a simpler example:

MODULE m
  IMPLICIT NONE

  TYPE :: t
INTEGER :: comp
  END TYPE t
CONTAINS
  FUNCTION f(i)
INTEGER, INTENT(IN) :: i
CLASS(t), ALLOCATABLE :: f
ALLOCATE(f)
f%comp = i
  END FUNCTION f

  SUBROUTINE proc(arg)
CLASS(t), INTENT(IN) :: arg
PRINT *, arg%comp
  END SUBROUTINE proc
END MODULE m

PROGRAM p
  USE m
  IMPLICIT NONE
  INTEGER :: i
  DO i = 1, 100
CALL proc(f(i))
! The function result should be deallocated after 
! execution of the above statement completes.
  END DO
END PROGRAM p

~~~

$ gfortran -g -v 2017-01-28\ alloc2.f90 && valgrind --leak-check=full ./a.out
Driving: gfortran -g -v 2017-01-28 alloc2.f90 -l gfortran -l m -shared-libgcc
Using built-in specs.
COLLECT_GCC=gfortran
COLLECT_LTO_WRAPPER=/home/MEGMS2/ian/usr/gcc-7.0.1/libexec/gcc/x86_64-pc-linux-gnu/7.0.1/lto-wrapper
Target: x86_64-pc-linux-gnu
Configured with: .././src/configure --prefix=/home/MEGMS2/ian/usr/gcc-7.0.1
--enable-languages=c,c++,fortran,lto --enable-libgomp --enable-checking=release
Thread model: posix
gcc version 7.0.1 20170120 (experimental) (GCC)
COLLECT_GCC_OPTIONS='-g' '-v' '-shared-libgcc' '-mtune=generic' '-march=x86-64'
 /home/MEGMS2/ian/usr/gcc-7.0.1/libexec/gcc/x86_64-pc-linux-gnu/7.0.1/f951
2017-01-28 alloc2.f90 -quiet -dumpbase 2017-01-28 alloc2.f90 -mtune=generic
-march=x86-64 -auxbase 2017-01-28 alloc2 -g -version -fintrinsic-modules-path
/home/MEGMS2/ian/usr/gcc-7.0.1/lib/gcc/x86_64-pc-linux-gnu/7.0.1/finclude -o
/tmp/ccRZA3YY.s
GNU Fortran (GCC) version 7.0.1 20170120 (experimental) (x86_64-pc-linux-gnu)
compiled by GNU C version 7.0.1 20170120 (experimental), GMP version
6.1.1, MPFR version 3.1.5, MPC version 1.0.2, isl version 0.15
GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
GNU Fortran2008 (GCC) version 7.0.1 20170120 (experimental)
(x86_64-pc-linux-gnu)
compiled by GNU C version 7.0.1 20170120 (experimental), GMP version
6.1.1, MPFR version 3.1.5, MPC version 1.0.2, isl version 0.15
GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
COLLECT_GCC_OPTIONS='-g' '-v' '-shared-libgcc' '-mtune=generic' '-march=x86-64'
 as -v --64 -o /tmp/ccXmIutE.o /tmp/ccRZA3YY.s
GNU assembler version 2.26.1 (x86_64-redhat-linux) using BFD version version
2.26.1-1.fc25
Reading specs from
/home/MEGMS2/ian/usr/gcc-7.0.1/lib/gcc/x86_64-pc-linux-gnu/7.0.1/../../../../lib64/libgfortran.spec
rename spec lib to liborig
COLLECT_GCC_OPTIONS='-g' '-v' '-shared-libgcc' '-mtune=generic' '-march=x86-64'
COMPILER_PATH=/home/MEGMS2/ian/usr/gcc-7.0.1/libexec/gcc/x86_64-pc-linux-gnu/7.0.1/:/home/MEGMS2/ian/usr/gcc-7.0.1/libexec/gcc/x86_64-pc-linux-gnu/7.0.1/:/home/MEGMS2/ian/usr/gcc-7.0.1/libexec/gcc/x86_64-pc-linux-gnu/:/home/MEGMS2/ian/usr/gcc-7.0.1/lib/gcc/x86_64-pc-linux-gnu/7.0.1/:/home/MEGMS2/ian/usr/gcc-7.0.1/lib/gcc/x86_64-pc-linux-gnu/
LIBRARY_PATH=/home/MEGMS2/ian/usr/gcc-7.0.1/lib/gcc/x86_64-pc-linux-gnu/7.0.1/:/home/MEGMS2/ian/usr/gcc-7.0.1/lib/gcc/x86_64-pc-linux-gnu/7.0.1/../../../../lib64/:/lib/../lib64/:/usr/lib/../lib64/:/home/MEGMS2/ian/usr/gcc-7.0.1/lib/gcc/x86_64-pc-linux-gnu/7.0.1/../../../:/lib/:/usr/lib/
COLLECT_GCC_OPTIONS='-g' '-v' '-shared-libgcc' '-mtune=generic' '-march=x86-64'
 /home/MEGMS2/ian/usr/gcc-7.0.1/libexec/gcc/x86_64-pc-linux-gnu/7.0.1/collect2
-plugin
/home/MEGMS2/ian/usr/gcc-7.0.1/libexec/gcc/x86_64-pc-linux-gnu/7.0.1/liblto_plugin.so
-plugin-opt=/home/MEGMS2/ian/usr/gcc-7.0.1/libexec/gcc/x86_64-pc-linux-gnu/7.0.1/lto-wrapper
-plugin-opt=-fresolution=/tmp/ccMep7Yj.res -plugin-opt=-pass-through=-lgcc_s
-plugin-opt=-pass-through=-lgcc -plugin-opt=-pass-through=-lqu

[Bug target/79127] [7 Regression] Error: invalid register for .seh_savexmm in matmul_i4.c

2017-01-19 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79127

Ian Harvey  changed:

   What|Removed |Added

 CC||ian_harvey at bigpond dot com

--- Comment #15 from Ian Harvey  ---
See also pr65782.

[Bug fortran/78670] New: Incorrect file position with namelist read under DTIO

2016-12-04 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=78670

Bug ID: 78670
   Summary: Incorrect file position with namelist read under DTIO
   Product: gcc
   Version: 7.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com
  Target Milestone: ---

When compiled with recent trunk, the attached demonstrates that the position of
a file is incorrect when a user defined derived type input procedure is invoked
to process namelist input.  The character read from the file by the user
defined derived type input procedure appears to be the `=` character that
separates the object designator from the value in the namelist input.  The file
position when the user defined derived type input procedure is invoked should
be after that `=`.

(As a result of picking up the `=` the defined input procedure leaves the file
positioned prior to the value `a`, which then confuses the Fortran runtime and
results in an end of file condition - that's not a problem in itself.)


MODULE m
  IMPLICIT NONE

  TYPE :: t
CHARACTER :: c
  CONTAINS
PROCEDURE :: read_formatted
GENERIC :: READ(FORMATTED) => read_formatted

! Work around for PR78659.
PROCEDURE :: write_formatted
GENERIC :: WRITE(FORMATTED) => write_formatted
  END TYPE t
CONTAINS
  ! Workaround for PR78659.
  SUBROUTINE write_formatted(dtv, unit, iotype, v_list, iostat, iomsg)
CLASS(t), INTENT(IN) :: dtv
INTEGER, INTENT(IN) :: unit
CHARACTER(*), INTENT(IN) :: iotype
INTEGER, INTENT(IN) :: v_list(:)
INTEGER, INTENT(OUT) :: iostat
CHARACTER(*), INTENT(INOUT) :: iomsg

iostat = 0
  END SUBROUTINE write_formatted

  SUBROUTINE read_formatted(dtv, unit, iotype, v_list, iostat, iomsg)
CLASS(t), INTENT(INOUT) :: dtv
INTEGER, INTENT(IN) :: unit
CHARACTER(*), INTENT(IN) :: iotype
INTEGER, INTENT(IN) :: v_list(:)
INTEGER, INTENT(OUT) :: iostat
CHARACTER(*), INTENT(INOUT) :: iomsg

CHARACTER :: ch

dtv%c = ''

DO
  READ (unit, "(A)", IOSTAT=iostat, IOMSG=iomsg) ch
  IF (iostat /= 0) RETURN

  ! for debugging only.
  print "('Got ''',A,)", ch

  ! Store first non-blank
  IF (ch /= '') THEN
dtv%c = ch
RETURN
  END IF
END DO

READ (unit, "(A)", IOSTAT=iostat, IOMSG=iomsg) dtv%c
  END SUBROUTINE read_formatted
END MODULE m

PROGRAM p
  USE m
  IMPLICIT NONE
  TYPE(t) :: x
  NAMELIST /nml/ x
  INTEGER :: unit

  OPEN(NEWUNIT=unit, STATUS='SCRATCH', ACTION='READWRITE')

  WRITE (unit, "(A)") ''
  WRITE (unit, "(A)") 'x = a'
  WRITE (unit, "(A)") '/'

  REWIND (unit)

  READ (unit, nml)
  PRINT *, x%c   ! expect `a`.
END PROGRAM p


$ gfortran -g 2016-12-04\ namelist3.f90 && ./a.out
Got '='
At line 72 of file 2016-12-04 namelist3.f90
Fortran runtime error: End of file

Error termination. Backtrace:
#0  0x7f19aad29321 in nml_get_obj_data
at ../../.././vanilla/libgfortran/io/list_read.c:3494
#1  0x7f19aad31700 in finalize_transfer
at ../../.././vanilla/libgfortran/io/transfer.c:3813
#2  0x40101e in p
at /home/MEGMS2/ian/srv/home/projects/FortranMisc/2016/2016-12-04
namelist3.f90:72
#3  0x4010b5 in main
at /home/MEGMS2/ian/srv/home/projects/FortranMisc/2016/2016-12-04
namelist3.f90:58



(The program is technically non-conforming because it executes an output
statement to an external unit while parent READ statement is active, if
necessary the print statement in read_formatted can be removed and the value of
dtv%c in the read_formatted procedure inspected after a read using a debugger.)

[Bug fortran/59694] [F03] no finalization of an unused variable

2016-12-03 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=59694

--- Comment #3 from Ian Harvey  ---
Why has this been marked as invalid?

[Bug fortran/78662] New: Incorrect parsing of quotes in the char-literal-constant of the DT data descriptor

2016-12-03 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=78662

Bug ID: 78662
   Summary: Incorrect parsing of quotes in the
char-literal-constant of the DT data descriptor
   Product: gcc
   Version: 7.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com
  Target Milestone: ---

The following, when compiled with gfortran recent trunk, generates an error
that indicates that parsing of the optional character literal constant of a DT
edit descriptor is not correctly handling embedded quotes.

MODULE m
  IMPLICIT NONE

  TYPE :: t
CHARACTER :: c
  CONTAINS
PROCEDURE :: write_formatted
GENERIC :: WRITE(FORMATTED) => write_formatted
  END TYPE t
CONTAINS
  SUBROUTINE write_formatted(dtv, unit, iotype, v_list, iostat, iomsg)
CLASS(t), INTENT(IN) :: dtv
INTEGER, INTENT(IN) :: unit
CHARACTER(*), INTENT(IN) :: iotype
INTEGER, INTENT(IN) :: v_list(:)
INTEGER, INTENT(OUT) :: iostat
CHARACTER(*), INTENT(INOUT) :: iomsg

WRITE (unit, "(A)", IOSTAT=iostat, IOMSG=iomsg) iotype
  END SUBROUTINE write_formatted
END MODULE m

PROGRAM p
  USE m
  IMPLICIT NONE

  TYPE(t) :: x
  WRITE (*, "(DT'a''b')") x
END PROGRAM p


$ gfortran 2016-12-03\ dt.f90  && ./a.out
2016-12-03 dt.f90:28:21:

   WRITE (*, "(DT'a''b')") x
 1
Error: Unexpected element ‘'’ in format string at (1)


The delimiter of the inner character literal constant (embedded in the
character literal constant that makes up the entire format specification) is a
single quote - the two single quotes in sequence therefore represent a single
single quote in the value that the inner character literal represents.

A more complicated variant is:

  WRITE (*, '(DT''ab'')') x

The problem also arises with FORMAT statements, which don't have the complexity
associated with having to consider "nested" literals.

  WRITE (*, 100) x
  100 FORMAT(DT'a''b')

[Bug fortran/78661] New: Namelist output missing object designator under DTIO

2016-12-03 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=78661

Bug ID: 78661
   Summary: Namelist output missing object designator under DTIO
   Product: gcc
   Version: 7.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com
  Target Milestone: ---

The following, when compiled with recent trunk (r243219), generates output that
is missing the "name =" part of the name-value subsequence for the object x.

MODULE m
  IMPLICIT NONE

  TYPE :: t
CHARACTER :: c
  CONTAINS
PROCEDURE :: write_formatted
GENERIC :: WRITE(FORMATTED) => write_formatted

! Work around for PR78659.
PROCEDURE :: read_formatted
GENERIC :: READ(FORMATTED) => read_formatted
  END TYPE t
CONTAINS
  SUBROUTINE write_formatted(dtv, unit, iotype, v_list, iostat, iomsg)
CLASS(t), INTENT(IN) :: dtv
INTEGER, INTENT(IN) :: unit
CHARACTER(*), INTENT(IN) :: iotype
INTEGER, INTENT(IN) :: v_list(:)
INTEGER, INTENT(OUT) :: iostat
CHARACTER(*), INTENT(INOUT) :: iomsg

WRITE (unit, "(A)", IOSTAT=iostat, IOMSG=iomsg) dtv%c
  END SUBROUTINE write_formatted

  ! Workaround for PR78659.
  SUBROUTINE read_formatted(dtv, unit, iotype, v_list, iostat, iomsg)
CLASS(t), INTENT(INOUT) :: dtv
INTEGER, INTENT(IN) :: unit
CHARACTER(*), INTENT(IN) :: iotype
INTEGER, INTENT(IN) :: v_list(:)
INTEGER, INTENT(OUT) :: iostat
CHARACTER(*), INTENT(INOUT) :: iomsg

READ (unit, "(A)", IOSTAT=iostat, IOMSG=iomsg) dtv%c
  END SUBROUTINE read_formatted
END MODULE m

PROGRAM p
  USE m
  IMPLICIT NONE
  TYPE(t) :: x
  NAMELIST /nml/ x

  x = t('a')
  WRITE (*, nml)
END PROGRAM p


$ gfortran 2016-12-03\ namelist2.f90 && ./a.out

a
 /


The correct output should be something like:


 x = a
 /


UDDTIO procedures are responsible for writing/reading the value part of the
name-value subsequence, the processor still has responsibility for the name=
part.

[Bug fortran/78659] New: Spurious "requires DTIO" reported against namelist statement

2016-12-02 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=78659

Bug ID: 78659
   Summary: Spurious "requires DTIO" reported against namelist
statement
   Product: gcc
   Version: 7.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com
  Target Milestone: ---

The attached, when compiled with gfortran recent trunk (r243203): 


MODULE ma
  IMPLICIT NONE
  TYPE :: ta
INTEGER, ALLOCATABLE :: array(:)
  END TYPE ta
END MODULE ma

PROGRAM p
  USE ma
  TYPE(ta) :: x
  NAMELIST /nml/ x
END PROGRAM p


results in:


$ gfortran 2016-12-03\ dtio-namelist-1.f90
2016-12-03 dtio-namelist-1.f90:11:15:

   NAMELIST /nml/ x
   1
Error: NAMELIST object ‘x’ in namelist ‘nml’ at (1) has ALLOCATABLE or POINTER
components and thus requires a defined input/output procedure


The error is reported against the namelist statement.  The standard does not
impose such a requirement on the namelist statement itself - the requirement is
imposed on data transfer statements that reference the namelist (F2008
9.6.4.7p2).

A namelist with such an object is not useful, so a warning is perhaps warranted
specifically for the above code, but the current error message causes issues
with useful code, such as:


MODULE mb
  IMPLICIT NONE
  TYPE :: tb
INTEGER, ALLOCATABLE :: array(:)
  CONTAINS
PROCEDURE :: read_formatted
GENERIC :: READ(FORMATTED) => read_formatted
  END TYPE tb
CONTAINS
  SUBROUTINE read_formatted(dtv, unit, iotype, v_list, iostat, iomsg)
CLASS(tb), INTENT(INOUT) :: dtv
INTEGER, INTENT(IN) :: unit
CHARACTER(*), INTENT(IN) :: iotype
INTEGER, INTENT(IN) :: v_list(:)
INTEGER, INTENT(OUT) :: iostat
CHARACTER(*), INTENT(INOUT) :: iomsg

iostat = 0
  END SUBROUTINE read_formatted
END MODULE mb

PROGRAM p
  USE mb
  TYPE(tb) :: y
  NAMELIST /nml/ y
  READ (*, nml)
END PROGRAM p


$ gfortran 2016-12-03\ dtio-namelist-2.f90
2016-12-03 dtio-namelist-2.f90:25:15:

   NAMELIST /nml/ y
   1
Error: NAMELIST object ‘y’ in namelist ‘nml’ at (1) has ALLOCATABLE or POINTER
components and thus requires a defined input/output procedure


The error goes away if a defined output procedure is also provided, but the
standard does not require a defined output procedure for the last example.

[Bug fortran/71796] Link error referencing compiler generated symbol __vtab_xxx

2016-10-26 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=71796

--- Comment #3 from Ian Harvey  ---
If you want a test case that exhibits no run time error upon successful
compilation and linking, then replace the entire main program with an END
statement.

MODULE ma
  IMPLICIT NONE
  PRIVATE

  TYPE, PUBLIC, ABSTRACT :: ta
  END TYPE ta
END MODULE ma

MODULE mb
  IMPLICIT NONE
  PRIVATE

  TYPE, PUBLIC, ABSTRACT :: tb
  CONTAINS
PROCEDURE(b_binding), DEFERRED :: binding
  END TYPE tb

  ABSTRACT INTERFACE
SUBROUTINE b_binding(argb, arga)
  USE ma
  IMPORT :: tb
  IMPLICIT NONE

  CLASS(tb), INTENT(IN) :: argb
  CLASS(ta), INTENT(OUT), ALLOCATABLE :: arga
END SUBROUTINE b_binding
  END INTERFACE
END MODULE mb

MODULE mc
  IMPLICIT NONE
  PRIVATE

  PUBLIC :: subc
CONTAINS
  SUBROUTINE subc
USE mb  !<< Ordering of these statements is significant.
USE ma  !<< Ordering of these statements is significant.

CLASS(ta), ALLOCATABLE :: a
CLASS(tb), ALLOCATABLE :: b
!
CALL b%binding(a)
  END SUBROUTINE subc
END MODULE mc

END ! 

[Bug fortran/71807] New: Internal compiler error with NULL() reference in structure constructor

2016-07-07 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=71807

Bug ID: 71807
   Summary: Internal compiler error with NULL() reference in
structure constructor
   Product: gcc
   Version: 7.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com
  Target Milestone: ---

The following snippet, when compiled with gfortran recent trunk (r238061) or
6.1.1 results in an internal compiler error.

~~

MODULE fold_convert_loc_ice
  IMPLICIT NONE
  PRIVATE

  TYPE, PUBLIC :: ta
PRIVATE
INTEGER :: a_comp
  END TYPE ta

  TYPE, PUBLIC :: tb
TYPE(ta), ALLOCATABLE :: b_comp
  END TYPE tb
CONTAINS
  SUBROUTINE proc
TYPE(tb) :: b

b = tb(null())
  END SUBROUTINE proc
END MODULE fold_convert_loc_ice

~~

$ gfortran -c -v fold_convert_loc_ice.f90
Using built-in specs.
COLLECT_GCC=gfortran
Target: x86_64-pc-linux-gnu
Configured with: .././src/configure --prefix=/home/MEGMS2/ian/usr/gcc-7.0.0
--enable-languages=c,c++,fortran --enable-libgomp --enable-checking=release
Thread model: posix
gcc version 7.0.0 20160706 (experimental) (GCC)
COLLECT_GCC_OPTIONS='-c' '-v' '-mtune=generic' '-march=x86-64'
 /home/MEGMS2/ian/usr/gcc-7.0.0/libexec/gcc/x86_64-pc-linux-gnu/7.0.0/f951
fold_convert_loc_ice.f90 -quiet -dumpbase fold_convert_loc_ice.f90
-mtune=generic -march=x86-64 -auxbase fold_convert_loc_ice -version
-fintrinsic-modules-path
/home/MEGMS2/ian/usr/gcc-7.0.0/lib/gcc/x86_64-pc-linux-gnu/7.0.0/finclude -o
/tmp/cc3kuTzv.s
GNU Fortran (GCC) version 7.0.0 20160706 (experimental) (x86_64-pc-linux-gnu)
compiled by GNU C version 7.0.0 20160704 (experimental), GMP version
6.1.0, MPFR version 3.1.4, MPC version 1.0.2, isl version none
GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
GNU Fortran2008 (GCC) version 7.0.0 20160706 (experimental)
(x86_64-pc-linux-gnu)
compiled by GNU C version 7.0.0 20160704 (experimental), GMP version
6.1.0, MPFR version 3.1.4, MPC version 1.0.2, isl version none
GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
fold_convert_loc_ice.f90:17:0:

 b = tb(null())

internal compiler error: in fold_convert_loc, at fold-const.c:2371
0x833153 fold_convert_loc(unsigned int, tree_node*, tree_node*)
../.././src/gcc/fold-const.c:2371
0x6b6e27 gfc_trans_subcomponent_assign
../.././src/gcc/fortran/trans-expr.c:7250
0x6b6653 gfc_trans_structure_assign(tree_node*, gfc_expr*, bool)
../.././src/gcc/fortran/trans-expr.c:7391
0x6b7dbf gfc_conv_structure(gfc_se*, gfc_expr*, int)
../.././src/gcc/fortran/trans-expr.c:7420
0x6b8e62 gfc_trans_assignment_1
../.././src/gcc/fortran/trans-expr.c:9317
0x682275 trans_code
../.././src/gcc/fortran/trans.c:1678
0x6a6019 gfc_generate_function_code(gfc_namespace*)
../.././src/gcc/fortran/trans-decl.c:6202
0x685a39 gfc_generate_module_code(gfc_namespace*)
../.././src/gcc/fortran/trans.c:2056
0x63d2eb translate_all_program_units
../.././src/gcc/fortran/parse.c:5873
0x63d2eb gfc_parse_file()
../.././src/gcc/fortran/parse.c:6092
0x67ec62 gfc_be_parse_file
../.././src/gcc/fortran/f95-lang.c:198
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See <http://gcc.gnu.org/bugs.html> for instructions.

[Bug fortran/71796] New: Link error referencing compiler generated symbol __vtab_xxx

2016-07-07 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=71796

Bug ID: 71796
   Summary: Link error referencing compiler generated symbol
__vtab_xxx
   Product: gcc
   Version: 7.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com
  Target Milestone: ---

Created attachment 38853
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=38853=edit
Reduced test case program exhibiting the link error

With recent trunk (r238061) The attached program fails to link with undefined
references to `__vtab_ma_Ta.3481`, which appears to be an internally generated
symbol related to the compiler's support for polymorphism.

The error disappears if the order of the USE statements is changed in one of
the scopes as indicated in the test case.  USE statement ordering in a scope is
not supposed to affect source semantics.

$ gfortran -v vtab-link-error.f90
Driving: gfortran -v vtab-link-error.f90 -l gfortran -l m -shared-libgcc
Using built-in specs.
COLLECT_GCC=gfortran
COLLECT_LTO_WRAPPER=/home/MEGMS2/ian/usr/gcc-7.0.0/libexec/gcc/x86_64-pc-linux-gnu/7.0.0/lto-wrapper
Target: x86_64-pc-linux-gnu
Configured with: .././src/configure --prefix=/home/MEGMS2/ian/usr/gcc-7.0.0
--enable-languages=c,c++,fortran --enable-libgomp --enable-checking=release :
(reconfigured) .././src/configure --prefix=/home/MEGMS2/ian/usr/gcc-7.0.0
--enable-libgomp --enable-checking=release --enable-languages=c,c++,fortran,lto
--no-create --no-recursion
Thread model: posix
gcc version 7.0.0 20160706 (experimental) (GCC)
COLLECT_GCC_OPTIONS='-v' '-shared-libgcc' '-mtune=generic' '-march=x86-64'
 /home/MEGMS2/ian/usr/gcc-7.0.0/libexec/gcc/x86_64-pc-linux-gnu/7.0.0/f951
vtab-link-error.f90 -quiet -dumpbase vtab-link-error.f90 -mtune=generic
-march=x86-64 -auxbase vtab-link-error -version -fintrinsic-modules-path
/home/MEGMS2/ian/usr/gcc-7.0.0/lib/gcc/x86_64-pc-linux-gnu/7.0.0/finclude -o
/tmp/cca44wnw.s
GNU Fortran (GCC) version 7.0.0 20160706 (experimental) (x86_64-pc-linux-gnu)
compiled by GNU C version 7.0.0 20160706 (experimental), GMP version
6.1.0, MPFR version 3.1.4, MPC version 1.0.2, isl version none
GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
GNU Fortran2008 (GCC) version 7.0.0 20160706 (experimental)
(x86_64-pc-linux-gnu)
compiled by GNU C version 7.0.0 20160706 (experimental), GMP version
6.1.0, MPFR version 3.1.4, MPC version 1.0.2, isl version none
GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
COLLECT_GCC_OPTIONS='-v' '-shared-libgcc' '-mtune=generic' '-march=x86-64'
 as -v --64 -o /tmp/ccnjfNd7.o /tmp/cca44wnw.s
GNU assembler version 2.26 (x86_64-redhat-linux) using BFD version version
2.26.20160125
Reading specs from
/home/MEGMS2/ian/usr/gcc-7.0.0/lib/gcc/x86_64-pc-linux-gnu/7.0.0/../../../../lib64/libgfortran.spec
rename spec lib to liborig
COLLECT_GCC_OPTIONS='-v' '-shared-libgcc' '-mtune=generic' '-march=x86-64'
COMPILER_PATH=/home/MEGMS2/ian/usr/gcc-7.0.0/libexec/gcc/x86_64-pc-linux-gnu/7.0.0/:/home/MEGMS2/ian/usr/gcc-7.0.0/libexec/gcc/x86_64-pc-linux-gnu/7.0.0/:/home/MEGMS2/ian/usr/gcc-7.0.0/libexec/gcc/x86_64-pc-linux-gnu/:/home/MEGMS2/ian/usr/gcc-7.0.0/lib/gcc/x86_64-pc-linux-gnu/7.0.0/:/home/MEGMS2/ian/usr/gcc-7.0.0/lib/gcc/x86_64-pc-linux-gnu/
LIBRARY_PATH=/home/MEGMS2/ian/usr/gcc-7.0.0/lib/gcc/x86_64-pc-linux-gnu/7.0.0/:/home/MEGMS2/ian/usr/gcc-7.0.0/lib/gcc/x86_64-pc-linux-gnu/7.0.0/../../../../lib64/:/lib/../lib64/:/usr/lib/../lib64/:/home/MEGMS2/ian/usr/gcc-7.0.0/lib/gcc/x86_64-pc-linux-gnu/7.0.0/../../../:/lib/:/usr/lib/
COLLECT_GCC_OPTIONS='-v' '-shared-libgcc' '-mtune=generic' '-march=x86-64'
 /home/MEGMS2/ian/usr/gcc-7.0.0/libexec/gcc/x86_64-pc-linux-gnu/7.0.0/collect2
-plugin
/home/MEGMS2/ian/usr/gcc-7.0.0/libexec/gcc/x86_64-pc-linux-gnu/7.0.0/liblto_plugin.so
-plugin-opt=/home/MEGMS2/ian/usr/gcc-7.0.0/libexec/gcc/x86_64-pc-linux-gnu/7.0.0/lto-wrapper
-plugin-opt=-fresolution=/tmp/cc1JOD5H.res -plugin-opt=-pass-through=-lgcc_s
-plugin-opt=-pass-through=-lgcc -plugin-opt=-pass-through=-lquadmath
-plugin-opt=-pass-through=-lm -plugin-opt=-pass-through=-lgcc_s
-plugin-opt=-pass-through=-lgcc -plugin-opt=-pass-through=-lc
-plugin-opt=-pass-through=-lgcc_s -plugin-opt=-pass-through=-lgcc
--eh-frame-hdr -m elf_x86_64 -dynamic-linker /lib64/ld-linux-x86-64.so.2
/lib/../lib64/crt1.o /lib/../lib64/crti.o
/home/MEGMS2/ian/usr/gcc-7.0.0/lib/gcc/x86_64-pc-linux-gnu/7.0.0/crtbegin.o
-L/home/MEGMS2/ian/usr/gcc-7.0.0/lib/gcc/x86_64-pc-linux-gnu/7.0.0
-L/home/MEGMS2/ian/usr/gcc-7.0.0/lib/gcc/x86_64-pc-linux-gnu/7.0.0/../../../../lib64
-L/lib/../lib64 -L/usr/lib/../lib64
-L/home/MEGMS2/ian/usr/gcc-7.0.0/lib/gcc/x86_64-pc-linux-gnu/7.0.0/../../..
/tmp/ccnjfNd7.o -lgfortran -lm -lgcc_s -lgcc -lquadmath -lm -lgcc_s -lgcc -lc
-lgcc_s -lgcc
/home/MEGMS2/ian/usr/

[Bug fortran/71580] Internal compiler error associated with type bound defined assignment

2016-06-21 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=71580

Ian Harvey  changed:

   What|Removed |Added

 Status|WAITING |RESOLVED
 Resolution|--- |DUPLICATE

--- Comment #2 from Ian Harvey  ---
Likely so.

*** This bug has been marked as a duplicate of bug 70864 ***

[Bug fortran/70864] internal compiler error: in gfc_get_symbol_decl, at fortran/trans-decl.c:1403

2016-06-21 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=70864

Ian Harvey  changed:

   What|Removed |Added

 CC||ian_harvey at bigpond dot com

--- Comment #2 from Ian Harvey  ---
*** Bug 71580 has been marked as a duplicate of this bug. ***

[Bug fortran/71580] New: Internal compiler error associated with type bound defined assignment

2016-06-18 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=71580

Bug ID: 71580
   Summary: Internal compiler error associated with type bound
defined assignment
   Product: gcc
   Version: 7.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com
  Target Milestone: ---

With trunk r237470 the following results in an internal compiler error
(sym->backend_decl is null at trans_decl.c:1420).

MODULE MySharedPointer
  IMPLICIT NONE
  PRIVATE

  PUBLIC :: SharedPointer

  TYPE, PRIVATE :: shared_pointer_impl
  CONTAINS
PROCEDURE, PRIVATE :: assign => ptr_impl_assign
GENERIC :: ASSIGNMENT(=) => assign
  END TYPE shared_pointer_impl

  TYPE :: SharedPointer
PRIVATE
TYPE(shared_pointer_impl) :: impl = shared_pointer_impl()
  END TYPE SharedPointer
CONTAINS
  SUBROUTINE ptr_impl_assign(lhs, rhs)
CLASS(shared_pointer_impl), INTENT(OUT) :: lhs
TYPE(shared_pointer_impl), INTENT(IN) :: rhs
  END SUBROUTINE ptr_impl_assign

  SUBROUTINE evil01_worker(x)
TYPE(SharedPointer) :: x
x = make_ptr()
  END SUBROUTINE evil01_worker

  FUNCTION make_ptr() RESULT(ptr)
TYPE(SharedPointer) :: ptr
  END FUNCTION make_ptr
END MODULE MySharedPointer



$ gfortran -v PolyScalarSharedPointerExample.f90
Driving: gfortran -v PolyScalarSharedPointerExample.f90 -l gfortran -l m
-shared-libgcc
Using built-in specs.
COLLECT_GCC=gfortran
COLLECT_LTO_WRAPPER=/home/MEGMS2/ian/usr/gcc-7.0.0/libexec/gcc/x86_64-pc-linux-gnu/7.0.0/lto-wrapper
Target: x86_64-pc-linux-gnu
Configured with: .././src/configure --prefix=/home/MEGMS2/ian/usr/gcc-7.0.0
--enable-languages=c,c++,fortran --enable-libgomp --enable-checking=release
Thread model: posix
gcc version 7.0.0 20160615 (experimental) (GCC)
COLLECT_GCC_OPTIONS='-v' '-shared-libgcc' '-mtune=generic' '-march=x86-64'
 /home/MEGMS2/ian/usr/gcc-7.0.0/libexec/gcc/x86_64-pc-linux-gnu/7.0.0/f951
PolyScalarSharedPointerExample.f90 -quiet -dumpbase
PolyScalarSharedPointerExample.f90 -mtune=generic -march=x86-64 -auxbase
PolyScalarSharedPointerExample -version -fintrinsic-modules-path
/home/MEGMS2/ian/usr/gcc-7.0.0/lib/gcc/x86_64-pc-linux-gnu/7.0.0/finclude -o
/tmp/ccdBc06e.s
GNU Fortran (GCC) version 7.0.0 20160615 (experimental) (x86_64-pc-linux-gnu)
compiled by GNU C version 7.0.0 20160615 (experimental), GMP version
6.0.0, MPFR version 3.1.3, MPC version 1.0.2, isl version none
GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
GNU Fortran2008 (GCC) version 7.0.0 20160615 (experimental)
(x86_64-pc-linux-gnu)
compiled by GNU C version 7.0.0 20160615 (experimental), GMP version
6.0.0, MPFR version 3.1.3, MPC version 1.0.2, isl version none
GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
PolyScalarSharedPointerExample.f90:30:0:

   END FUNCTION make_ptr

internal compiler error: in gfc_get_symbol_decl, at fortran/trans-decl.c:1420
0x6a1408 gfc_get_symbol_decl(gfc_symbol*)
../.././src/gcc/fortran/trans-decl.c:1420
0x6a370f generate_local_decl
../.././src/gcc/fortran/trans-decl.c:5237
0x66bd2b do_traverse_symtree
../.././src/gcc/fortran/symbol.c:3926
0x6a4372 generate_local_vars
../.././src/gcc/fortran/trans-decl.c:5427
0x6a4372 gfc_generate_function_code(gfc_namespace*)
../.././src/gcc/fortran/trans-decl.c:6106
0x684141 gfc_generate_module_code(gfc_namespace*)
../.././src/gcc/fortran/trans.c:2058
0x63c86b translate_all_program_units
../.././src/gcc/fortran/parse.c:5830
0x63c86b gfc_parse_file()
../.././src/gcc/fortran/parse.c:6049
0x67de02 gfc_be_parse_file
../.././src/gcc/fortran/f95-lang.c:201
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See <http://gcc.gnu.org/bugs.html> for instructions.

[Bug fortran/44265] Link error with reference to parameter array in specification expression

2016-06-18 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=44265

--- Comment #14 from Ian Harvey  ---
I wouldn't know where to start with respect to the internal compiler error.

[Bug fortran/44265] Link error with reference to parameter array in specification expression

2016-06-16 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=44265

--- Comment #10 from Ian Harvey  ---
The patch discussed in #5 applies changes to the wrong location in
trans-decl.c.  Corrected patch attached.  

With this latest patch I see no variation in check-fortran test results.

[Bug fortran/44265] Link error with reference to parameter array in specification expression

2016-06-16 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=44265

--- Comment #9 from Ian Harvey  ---
Created attachment 38708
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=38708=edit
Updated patch against r23740

[Bug fortran/52393] I/O: "READ format" statement with parenthesed default-char-expr

2016-04-06 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=52393

--- Comment #6 from Ian Harvey  ---
The code in #5 is missing the initial parenthesised expression that exposes the
flaw in parsing logic - the left hand operand of the string concatenation needs
to be `('(')`, and not just the string literal.

[Bug fortran/59694] [F03] no finalization of an unused variable

2015-09-07 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=59694

Ian Harvey  changed:

   What|Removed |Added

 CC||ian_harvey at bigpond dot com

--- Comment #1 from Ian Harvey  ---
*** Bug 67472 has been marked as a duplicate of this bug. ***


[Bug fortran/67472] Finalizer not invoked for undefined and unreferenced local variable

2015-09-07 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=67472

Ian Harvey  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |DUPLICATE

--- Comment #2 from Ian Harvey  ---
This is a procedure level local variable variant (vs block level) of pr59694.

*** This bug has been marked as a duplicate of bug 59694 ***


[Bug fortran/37336] [F03] Finish derived-type finalization

2015-09-07 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=37336
Bug 37336 depends on bug 67472, which changed state.

Bug 67472 Summary: Finalizer not invoked for undefined and unreferenced local 
variable
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=67472

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |DUPLICATE


[Bug fortran/67472] New: Finalizer not invoked for undefined and unreferenced local variable

2015-09-06 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=67472

Bug ID: 67472
   Summary: Finalizer not invoked for undefined and unreferenced
local variable
   Product: gcc
   Version: 6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com
  Target Milestone: ---

gfortran recent trunk r227512 does not invoke the finalizer for the local
variable `aa` of the internal procedure `internal`.

module test_final_mod
  implicit none
  type :: my_final
integer :: n = 0
  contains
final :: destroy_scalar
  end type my_final
contains
  subroutine destroy_scalar(self)
type(my_final), intent(inout) :: self
print "(A,I0,A,*(I0,:,', '))",  &
'destroy_scalar executed for object with component value ',  &
self%n
  end subroutine destroy_scalar
end module test_final_mod

program test_internal_proc
  use test_final_mod
  call internal
contains
  subroutine internal
type(my_final) :: aa
  end subroutine internal
end program test_internal_proc

gfortran produces no output, the expected output is:

destroy_scalar executed for object with component value 0

The expected output is generated if the source is changed, such that the local
variable is defined or referenced in the internal procedure.


[Bug fortran/67471] New: Finalizer not invoked for assignment to array section

2015-09-06 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=67471

Bug ID: 67471
   Summary: Finalizer not invoked for assignment to array section
   Product: gcc
   Version: 6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com
  Target Milestone: ---

gfortran recent trunk r227512 does not invoke the finalizer for the intrinsic
assignment (as required by F2008 4.5.6.3p9) to the array section of `b` in the
following example:

module tes_final_mod
  implicit none
  type :: my_final
integer :: n = 0
  contains
final :: destroy_rank1_array
  end type my_final
contains
  subroutine destroy_rank1_array(self)
type(my_final), intent(inout) :: self(:)
if (size(self) /= 0) then
  print "(A,I0,A,*(I0,:,', '))",  &
  'destroy_rank1_array executed for object of size ',  &
  size(self), &
  ' and component values ',  &
  self%n
else
  print "(A)",  &
  'destroy_rank1_array executed for object of size 0'
end if
  end subroutine destroy_rank1_array
end module tes_final_mod

program test_finalizer
  use tes_final_mod
  implicit none
  type(my_final) :: b(4), c(2)

  b%n = 2
  c%n = 3
  b(1:2) = c
end program test_finalizer


No output is generated, while expected output is:

destroy_rank1_array executed for object of size 2 and component values 2,2

See also
https://software.intel.com/en-us/forums/intel-fortran-compiler-for-linux-and-mac-os-x/topic/591918#comment-1838428


[Bug fortran/67451] New: ICE with sourced allocation from coarray.

2015-09-04 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=67451

Bug ID: 67451
   Summary: ICE with sourced allocation from coarray.
   Product: gcc
   Version: 6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com
  Target Milestone: ---

The following, when compiled with trunk r227476, results in a ICE:

  program main
implicit none
type foo
  integer :: bar = 99
end type
class(foo), allocatable :: foobar[:]
class(foo), allocatable :: some_local_object
allocate(foobar[*])
allocate(some_local_object, source=foobar)
  end program

The ICE is associated with the use of a coarray or coindexed object in the
source expression of the allocate statement.



$ gfortran -v -fcoarray=lib 2015-09-04\ sourced-alloc.f90
Driving: gfortran -v -fcoarray=lib 2015-09-04 sourced-alloc.f90 -l gfortran -l
m -shared-libgcc
Using built-in specs.
COLLECT_GCC=gfortran
COLLECT_LTO_WRAPPER=/home/MEGMS2/ian/usr/gcc-6.0.0/libexec/gcc/x86_64-pc-linux-gnu/6.0.0/lto-wrapper
Target: x86_64-pc-linux-gnu
Configured with: .././src/configure --prefix=/home/MEGMS2/ian/usr/gcc-6.0.0
--enable-languages=c,c++,fortran --enable-libgomp --enable-checking=release
Thread model: posix
gcc version 6.0.0 20150903 (experimental) (GCC)
COLLECT_GCC_OPTIONS='-v' '-fcoarray=lib' '-shared-libgcc' '-mtune=generic'
'-march=x86-64'
 /home/MEGMS2/ian/usr/gcc-6.0.0/libexec/gcc/x86_64-pc-linux-gnu/6.0.0/f951
2015-09-04 sourced-alloc.f90 -quiet -dumpbase 2015-09-04 sourced-alloc.f90
-mtune=generic -march=x86-64 -auxbase 2015-09-04 sourced-alloc -version
-fcoarray=lib -fintrinsic-modules-path
/home/MEGMS2/ian/usr/gcc-6.0.0/lib/gcc/x86_64-pc-linux-gnu/6.0.0/finclude -o
/tmp/ccX5BIwU.s
GNU Fortran (GCC) version 6.0.0 20150903 (experimental) (x86_64-pc-linux-gnu)
compiled by GNU C version 6.0.0 20150903 (experimental), GMP version
6.0.0, MPFR version 3.1.2, MPC version 1.0.2
GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
GNU Fortran2008 (GCC) version 6.0.0 20150903 (experimental)
(x86_64-pc-linux-gnu)
compiled by GNU C version 6.0.0 20150903 (experimental), GMP version
6.0.0, MPFR version 3.1.2, MPC version 1.0.2
GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
2015-09-04 sourced-alloc.f90:9:0:

 allocate(some_local_object, source=foobar)
1
internal compiler error: Segmentation fault
0xa1271f crash_signal
../.././src/gcc/toplev.c:352
0x690f9e gfc_class_vptr_get(tree_node*)
../.././src/gcc/fortran/trans-expr.c:153
0x694155 class_vtab_field_get
../.././src/gcc/fortran/trans-expr.c:201
0x694155 gfc_class_vtab_copy_get(tree_node*)
../.././src/gcc/fortran/trans-expr.c:223
0x694155 gfc_copy_class_to_class(tree_node*, tree_node*, tree_node*, bool)
../.././src/gcc/fortran/trans-expr.c:1084
0x6cd11b gfc_trans_allocate(gfc_code*)
../.././src/gcc/fortran/trans-stmt.c:5725
0x66a7e7 trans_code
../.././src/gcc/fortran/trans.c:1798
0x68d6f3 gfc_generate_function_code(gfc_namespace*)
../.././src/gcc/fortran/trans-decl.c:5900
0x627210 translate_all_program_units
../.././src/gcc/fortran/parse.c:5526
0x627210 gfc_parse_file()
../.././src/gcc/fortran/parse.c:5731
0x667ba2 gfc_be_parse_file
../.././src/gcc/fortran/f95-lang.c:209
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See <http://gcc.gnu.org/bugs.html> for instructions.


[Bug fortran/63552] [OOP] Type-bound procedures rejected as actual argument to dummy procedure

2015-01-03 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63552

Ian Harvey ian_harvey at bigpond dot com changed:

   What|Removed |Added

 CC||ian_harvey at bigpond dot com

--- Comment #6 from Ian Harvey ian_harvey at bigpond dot com ---
Note that using a type bound procedure (versus a procedure component) as an
actual argument is an extension to Fortran 2008.


[Bug fortran/63552] [OOP] Type-bound procedures rejected as actual argument to dummy procedure

2015-01-03 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63552

--- Comment #8 from Ian Harvey ian_harvey at bigpond dot com ---
For clarity - there is a difference between a procedure as an actual argument
and a procedure reference (something with parentheses and maybe arguments
following) that is part of an expression that is an actual argument.  See also
definition of procedure reference in 1.3.123.4 - noting reference requires
execution at that point.  A procedure as an actual argument does not require
execution of the procedure at the time of argument association (a procedure
reference may occur later through the corresponding dummy procedure).

The syntax rule for an /actual-arg/ in 14-007r2 is R1225.  None of the child
syntax rules of R1225 permit a type bound procedure, noting that a binding of a
type is not a component of a type.

R1223 in 14-007r2 is only used in the forms of procedure reference
(/function-reference/ or /call-stmt/).  It is not relevant to procedures as
actual arguments.


[Bug fortran/56459] Wrongly rejects TYPE(CHARACTER*1,) (with comma)

2014-12-15 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=56459

Ian Harvey ian_harvey at bigpond dot com changed:

   What|Removed |Added

 CC||ian_harvey at bigpond dot com

--- Comment #2 from Ian Harvey ian_harvey at bigpond dot com ---
As a result of interp f08/0097, F2008 corrigendum three introduced constraint
C406a (In TYPE(intrinsic-type-spec) the intrinsic-type-spec shall not end with
a comma) that makes the original example non-conforming.

It is therefore now correct (and sensible) for the compiler to reject the
example.


[Bug fortran/64324] New: Deferred character specific functions not permitted in generic operator interface

2014-12-15 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64324

Bug ID: 64324
   Summary: Deferred character specific functions not permitted in
generic operator interface
   Product: gcc
   Version: unknown
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com

gfortran built from current trunk rejects the following with Error: User
operator procedure ‘tostring’ at (1) cannot be assumed character length

MODULE m
  IMPLICIT NONE
  INTERFACE OPERATOR(.ToString.)
MODULE PROCEDURE tostring
  END INTERFACE OPERATOR(.ToString.)
CONTAINS
  FUNCTION tostring(arg)
INTEGER, INTENT(IN) :: arg
CHARACTER(:), ALLOCATABLE :: tostring
tostring = '42'
  END FUNCTION tostring
END MODULE m


(The procedure has deferred length, not assumed length.)


$ gfortran -v -c 2014-12-16\ ToString.f90
Using built-in specs.
COLLECT_GCC=gfortran
Target: x86_64-unknown-linux-gnu
Configured with: .././src/configure --prefix=/home/MEGMS2/ian/usr/gcc-5.0.0
--enable-languages=c,c++,fortran --enable-libgomp --enable-checking=release
Thread model: posix
gcc version 5.0.0 20141215 (experimental) (GCC) 

COLLECT_GCC_OPTIONS='-v' '-c' '-mtune=generic' '-march=x86-64'
 /home/MEGMS2/ian/usr/gcc-5.0.0/libexec/gcc/x86_64-unknown-linux-gnu/5.0.0/f951
2014-12-16 ToString.f90 -quiet -dumpbase 2014-12-16 ToString.f90 -mtune=generic
-march=x86-64 -auxbase 2014-12-16 ToString -version -fintrinsic-modules-path
/home/MEGMS2/ian/usr/gcc-5.0.0/lib/gcc/x86_64-unknown-linux-gnu/5.0.0/finclude
-o /tmp/cctex4Ju.s
GNU Fortran (GCC) version 5.0.0 20141215 (experimental)
(x86_64-unknown-linux-gnu)
compiled by GNU C version 5.0.0 20141215 (experimental), GMP version 6.0.0,
MPFR version 3.1.2, MPC version 1.0.2
GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
GNU Fortran (GCC) version 5.0.0 20141215 (experimental)
(x86_64-unknown-linux-gnu)
compiled by GNU C version 5.0.0 20141215 (experimental), GMP version 6.0.0,
MPFR version 3.1.2, MPC version 1.0.2
GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
2014-12-16 ToString.f90:7:2:

   FUNCTION tostring(arg)
  1
Error: User operator procedure ‘tostring’ at (1) cannot be assumed character
length

[Bug fortran/63363] New: No diagnostic for passing function as actual argument to KIND

2014-09-24 Thread ian_harvey at bigpond dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63363

Bug ID: 63363
   Summary: No diagnostic for passing function as actual argument
to KIND
   Product: gcc
   Version: 5.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com

The following (from recent c.l.f discussion) compiles without error with trunk
r215574, despite the actual argument not meeting the requirements for the
argument of the KIND intrinsic (the argument must be a data entity).

INTERFACE
  FUNCTION f()
INTEGER(SELECTED_INT_KIND(4)) :: f
  END FUNCTION f
END INTERFACE

PRINT *, KIND(f)
  END

  ! (just to provide a definition)
  FUNCTION f()
INTEGER(SELECTED_INT_KIND(4)) :: f
  END FUNCTION f 

After compiling (supplying no options) the resulting program, when executed,
prints zero.


[Bug fortran/59202] New: Erroneous argument aliasing with defined assignment

2013-11-19 Thread ian_harvey at bigpond dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=59202

Bug ID: 59202
   Summary: Erroneous argument aliasing with defined assignment
   Product: gcc
   Version: unknown
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com

gfortran build from very recent trunk does not appear to be correctly handling
the case when an object with allocatable components is self assigned and
defined assignment is accessible.

For example:

MODULE DefinedAssignmentModule
  IMPLICIT NONE
  TYPE :: t
INTEGER, ALLOCATABLE :: array(:)
  END TYPE t
  INTERFACE ASSIGNMENT(=)
MODULE PROCEDURE def_assign
  END INTERFACE ASSIGNMENT(=)
CONTAINS
  SUBROUTINE def_assign(lhs, rhs)
TYPE(t), INTENT(OUT) :: lhs   ! Investigate INOUT too.
TYPE(t), INTENT(IN) :: rhs
!*
! Allocation status of lhs and rhs on entry.
PRINT (*(L1,:,1X)), ALLOCATED(lhs%array), ALLOCATED(rhs%array)
! Change allocation status of lhs
IF (ALLOCATED(lhs%array)) DEALLOCATE(lhs%array)
ALLOCATE(lhs%array(5))
! Resulting allocation status of lhs and rhs.
PRINT (1X,*(L1,:,1X)), ALLOCATED(lhs%array), ALLOCATED(rhs%array)
  END SUBROUTINE def_assign
  SUBROUTINE reset(obj)
TYPE(t), INTENT(OUT) :: obj
  END SUBROUTINE reset
END MODULE DefinedAssignmentModule

PROGRAM DefinedAssignmentTest
  USE DefinedAssignmentModule
  IMPLICIT NONE
  TYPE(t) :: a

  ! This...
  a = a

  CALL reset(a)
  ! ...should be equivalent to this...
  CALL def_assign(a, (a))

  CALL reset(a)
  ALLOCATE(a%array(2))
  a = a ! rhs should be allocated on entry.

END PROGRAM DefinedAssignmentTest

results in:

F F
 T T
F F
 T F
F F
 T T

The first two lines indicate that changes to lhs inside the procedure result in
changes to rhs (even though rhs is equivalent to the the value of a
parenthesised expression per F2008 12.4.3.4.3 - hence the two arguments are not
aliased).  

The third and fourth lines indicate that the compiler is correctly handling
explicit passing of a parenthesised expression.  

The fifth and sixth lines indicate that application of INTENT(OUT) to lhs is
affecting rhs on entry to the procedure.


[Bug fortran/58676] New: Intrinsic functions not considered pure actual arguments

2013-10-09 Thread ian_harvey at bigpond dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=58676

Bug ID: 58676
   Summary: Intrinsic functions not considered pure actual
arguments
   Product: gcc
   Version: unknown
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: ian_harvey at bigpond dot com

The following example, when compiled with recent trunk:

MODULE m
  IMPLICIT NONE
CONTAINS
  SUBROUTINE sub(proc)
INTERFACE
  PURE FUNCTION proc(x)
IMPLICIT NONE
REAL, INTENT(IN) :: x
REAL :: proc
  END FUNCTION proc
END INTERFACE
PRINT *, proc(0.0)
  END SUBROUTINE sub
END MODULE m
PROGRAM p
  USE m
  IMPLICIT NONE
  INTRINSIC :: sin
  CALL sub(sin)   !xxx
END PROGRAM p

results in an error Interface mismatch in dummy procedure 'proc' ... :
Mismatch in PURE attribute, which I think (but maybe I've missed something) is
erroneous.

All standard intrinsic functions are pure (13.1p2) and elemental intrinsic
functions may be associated with a dummy procedure (which cannot be elemental)
(12.5.2.9p1) and `sin` is the relevant bullet-less specific for the generic sin
(13.6).

See also http://software.intel.com/en-us/forums/topic/476356 and perhaps
pr41724.


[Bug fortran/52393] Erroneous parse of read statement with parenthesised expression in format

2012-02-27 Thread ian_harvey at bigpond dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=52393

--- Comment #2 from Ian Harvey ian_harvey at bigpond dot com 2012-02-27 
09:28:22 UTC ---
There is no unit number in that /read-stmt/, just a /format/ and one io item. 
This is the second form (per the ordering in the syntax rules from F77 on) of
read that is the companion to the /print-stmt/ (as opposed to the more commonly
seen form that is the companion to a /write-stmt/).  This second form always
reads from the console (or whatever the unit * means), just like PRINT always
writes to the console.

R910
/read-stmt/ is READ ( /io-control-spec-list/ ) [ /input-item-list/ ]

or READ /format/ [ , /input-item-list/ ] ! -- This one.

R915
/format/is /default-char-expr/  ! -- Then this one.

or /label/

or *

The /format/ for this /read-stmt/ is then the /default-char-expr/

  ('('   )// 'A)'

which has a pointlessly parenthesised character literal '(' concatenated with
'A)'.  The result of evaluating that is '(A)', which is a valid format
specification (9.6.2.2p2).

The comma is simply the comma that is required in the /read-stmt/ to separate
the format expression from the /input-item-list/.  The common vendor extension
for the extra comma for the other form of /read-stmt/ is problematic here with
respect to ambiguity.

I've used F2008 references above, but this is all standard F90 (salient parts
are F77 even?).  See c.l.f for discussion of ambiguity issues with F2008.  

I accept that this is somewhat obscure and that the specific example is rather
contrived.


[Bug fortran/52393] I/O: READ format statement with parenthesed default-char-expr

2012-02-27 Thread ian_harvey at bigpond dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=52393

--- Comment #4 from Ian Harvey ian_harvey at bigpond dot com 2012-02-27 
10:30:32 UTC ---
Maybe there's some additional cleverness going on then, because the following
equally contrived example:

PROGRAM ReadMeOne
  IMPLICIT NONE
  CHARACTER(10) :: var
  READ ('(A)'), var
  PRINT *, var
END PROGRAM ReadMeOne

which is again supposed to be the second form of read, when compiled with:

  gfortran -Wall -std=f2003

appears to work!


[Bug fortran/52393] New: Erroneous parse of read statement with parenthesised expression in format

2012-02-26 Thread ian_harvey at bigpond dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=52393

 Bug #: 52393
   Summary: Erroneous parse of read statement with parenthesised
expression in format
Classification: Unclassified
   Product: gcc
   Version: 4.7.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: ian_har...@bigpond.com


With gfortran built from recent trunk revision 184585 on fedora 15 x86_64, the
following example:

PROGRAM ReadMeTwo
  IMPLICIT NONE
  CHARACTER(10) :: var
  READ ('(') // 'A)', var  
  PRINT *, var
END PROGRAM ReadMeTwo

gives:

$ gfortran -Wall -std=f2003 ReadMeTwo.f90
ReadMeTwo.f90:4.12:

  READ ('(') // 'A)', var
1
Error: Expected variable in READ statement at (1)

I think the example is valid fortran and should compile without error.


[Bug fortran/48478] New: Valid array-constructor syntax rejected/invalid accepted

2011-04-06 Thread ian_harvey at bigpond dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=48478

   Summary: Valid array-constructor syntax rejected/invalid
accepted
   Product: gcc
   Version: 4.7.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: ian_har...@bigpond.com


Created attachment 23898
  -- http://gcc.gnu.org/bugzilla/attachment.cgi?id=23898
Demonstrates valid and invalid syntax

gfortran 4.7 compiled from trunk revision 171951 rejects an array constructor
with syntax:

  [ derived_type_name:: ... ]

With -Wall --std=f2003 it accepts without complaint one of the form:

  [ TYPE(derived_type_name):: ... ]

From F2008 draft:

R468: array-constructor  is (/ ac-spec /) 
 or lbracket ac-spec rbracket

R469: ac-specis type-spec ::
 or [type-spec ::] ac-value-list

R402: type-spec  is intrinsic-type-spec
 or derived-type-spec

R453: derived-type-spec  is type-name [(type-param-spec-list)]

It looks like the compiler has confused a type-spec with a
declaration-type-spec, (which does use the TYPE keyword).


[Bug fortran/46952] New: Spurious recursive call error with type bound procedure

2010-12-14 Thread ian_harvey at bigpond dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46952

   Summary: Spurious recursive call error with type bound
procedure
   Product: gcc
   Version: 4.6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: ian_har...@bigpond.com


Created attachment 22759
  -- http://gcc.gnu.org/bugzilla/attachment.cgi?id=22759
Example that generate the error

The attached, using a gfortran 4.6 from November 3 on i686-pc-mingw32,
generates the error SUBROUTINE 'relay_proc' ... cannot be called recursively.
 But I don't think the call is recursive - relay_proc is just the interface for
what gets called, not the actual procedure.

But Intel Fortran 12.0.1.127 also complains, so maybe I'm wrong.


[Bug fortran/46356] New: Erroneous procedure/intent error and ICE for class dummy argument

2010-11-07 Thread ian_harvey at bigpond dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46356

   Summary: Erroneous procedure/intent error and ICE for class
dummy argument
   Product: gcc
   Version: 4.6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: ian_har...@bigpond.com


The following example, when compiled with gfortran 4.6 built from trunk source
166232 (20101103), rejects the following code with a dubious errror (PROCEDURE
attribute conflicts with INTENT attribute in 'pvec') before the compiler dies
with an ICE.

I believe the code is valid F2003.  It, and the subsequent variations below,
are accepted by ifort 11.1.067.  

MODULE procedure_intent_nonsense
  IMPLICIT NONE  
  PRIVATE
  TYPE, PUBLIC :: Parent
INTEGER :: comp
  END TYPE Parent

  TYPE :: ParentVector
INTEGER :: a
! CLASS(Parent), ALLOCATABLE :: a
  END TYPE ParentVector  
CONTAINS   
  SUBROUTINE vector_operation(pvec) 
CLASS(ParentVector), INTENT(INOUT) :: pvec(:)
INTEGER :: i
!---
DO i = 1, SIZE(pvec)
  CALL item_operation(pvec(i))
END DO  
! PRINT *, pvec(1)%a%comp
  END SUBROUTINE vector_operation

  SUBROUTINE item_operation(pvec)  
CLASS(ParentVector), INTENT(INOUT) :: pvec
!TYPE(ParentVector), INTENT(INOUT) :: pvec
  END SUBROUTINE item_operation
END MODULE procedure_intent_nonsense

Variants, which may all be just the result of the compiler thinking the pvec
argument is a procedure...

If the ParentVector component is switched to being the CLASS(Parent) component
and the PRINT statement in vector_operation is uncommented, a syntax error that
appears to be spurious is generated.

Alternatively, if the pvec dummy in item_option is changed to be
non-polymorphic, then two additional errors appear and the ICE disappears.  

One of the additional errors is 'array' argument of 'size' intrinsic at (1)
must be an array, referring to the SIZE intrinsic in the DO statement.  The
argument to the SIZE intrinsic is an array, so this error is spurious.

The other additional error is that there is a type mismatch with the argument
for in the CALL to item_operation (passed CLASS(...) to TYPE(...)).  I believe
this is also spurious.


[Bug fortran/44265] Link error with reference to parameter array in specification expression

2010-10-29 Thread ian_harvey at bigpond dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=44265

--- Comment #2 from Ian Harvey ian_harvey at bigpond dot com 2010-10-29 
23:20:42 UTC ---
Created attachment 22202
  -- http://gcc.gnu.org/bugzilla/attachment.cgi?id=22202
Possible patch for PR44265


[Bug fortran/44265] Link error with reference to parameter array in specification expression

2010-10-29 Thread ian_harvey at bigpond dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=44265

--- Comment #3 from Ian Harvey ian_harvey at bigpond dot com 2010-10-29 
23:32:29 UTC ---
(In reply to comment #2)
 Created attachment 22202 [details]
 Possible patch for PR44265

Apologies - I wrote several paragraphs of reasonably coherent explanation, but
it got lost when I added the attachment.

The attached set of patches introduces a new flag for gfc_symbol that is used
to indicate when an entity is referenced in a specification expression for a
function result; testing of that condition for module procedure local entities
and setting of the flag in resolve.c; and changes to the assembly associated
with the entity such that the object code for calling procedures in other
program units can reference the entity.

The test for the need to export the entity is probably too inclusive.

The assembly name for the entity is of the form
__modname_MOD__procname_PROC_entityname.

Note that -module for a gfc_symbol for a module procedure entity can either be
NULL (when the hosting module is being compiled) or a zero length string (when
a program unit that USE's the module is being compiled).  I am not sure whether
that is by design or accident - I have assumed by design.

Perhaps Tobias had alternative approaches in mind but I am not familiar enough
with the gfortran sources to know what he was talking about.

This does not fix the failed assertion around a non-null -tlink when a
subroutine has an argument whose length uses such a specification expression.


[Bug fortran/44265] New: Link error with reference to parameter array in specification expression

2010-05-24 Thread ian_harvey at bigpond dot com
The following program compiles successfully, but results in an undefined
reference to `___MOD_names' during linking.  It compiles and links successfully
with g95 0.92! (May 31, 2009)and ifort 11.1.065.

Using gfortran built from svn trunk revision 159797.  Command line was simply
gfortran filename.f90.  Some experimentation shows that the problem is
related to the use of an module procedure scoped array parameter in the
specification expression for the function result.  The type of the parameter
array doesn't seem to matter.

MODULE Fruits
  IMPLICIT NONE
  PRIVATE
  PUBLIC :: Get
CONTAINS
  FUNCTION Get(i) RESULT(s)
CHARACTER(*), PARAMETER :: names(3) = [  
'Apple  ',  
'Orange ',  
'Mango  ' ];  
INTEGER, INTENT(IN) :: i
CHARACTER(LEN_TRIM(names(i))) :: s
!
s = names(i)
  END FUNCTION Get
END MODULE Fruits

PROGRAM WheresThatbLinkingConstantGone
  USE Fruits  
  IMPLICIT NONE
  !
  WRITE (*, ('Eat the tasty ',A)) Get(1)
END PROGRAM WheresThatbLinkingConstantGone


-- 
   Summary: Link error with reference to parameter array in
specification expression
   Product: gcc
   Version: 4.6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassigned at gcc dot gnu dot org
ReportedBy: ian_harvey at bigpond dot com
 GCC build triplet: i686-pc-mingw32
  GCC host triplet: i686-pc-mingw32
GCC target triplet: i686-pc-mingw32


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=44265



[Bug libfortran/42996] New: Incorrect length returned from get_command_argument intrinsic

2010-02-08 Thread ian_harvey at bigpond dot com
According to the F2003 standard, the LENGTH argument does not consider any
possible truncation or padding in assigning the command argument value to the
VALUE argument (13.7.42).  However, gfortran appears to use the minimum of the
length of the VALUE argument (if present) and the length of the command
argument.

(svn revision 156557)


-- 
   Summary: Incorrect length returned from get_command_argument
intrinsic
   Product: gcc
   Version: 4.5.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: libfortran
AssignedTo: unassigned at gcc dot gnu dot org
ReportedBy: ian_harvey at bigpond dot com
 GCC build triplet: i686-pc-mingw32
  GCC host triplet: i686-pc-mingw32
GCC target triplet: i686-pc-mingw32


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=42996



[Bug libfortran/42996] Incorrect length returned from get_command_argument intrinsic

2010-02-08 Thread ian_harvey at bigpond dot com


--- Comment #1 from ian_harvey at bigpond dot com  2010-02-08 10:48 ---
Created an attachment (id=19819)
 -- (http://gcc.gnu.org/bugzilla/attachment.cgi?id=19819action=view)
Simple test case

Call the resulting program with an argument longer than one character.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=42996



[Bug fortran/42804] New: ICE with -fcheck=bounds and type bound procedure call on array element

2010-01-19 Thread ian_harvey at bigpond dot com
A segmentation violation occurs in gfc_trans_runtime_error_vararg (trans.c:393)
when compiling with -fcheck=bounds and an expression like the following is
encountered:

call array_of_derived_type(index)%type_bound_proc(args...)

(With svn revision 156036)


-- 
   Summary: ICE with -fcheck=bounds and type bound procedure call on
array element
   Product: gcc
   Version: 4.5.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassigned at gcc dot gnu dot org
ReportedBy: ian_harvey at bigpond dot com
 GCC build triplet: i686-pc-mingw32
  GCC host triplet: i686-pc-mingw32
GCC target triplet: i686-pc-mingw32


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=42804



[Bug fortran/42804] ICE with -fcheck=bounds and type bound procedure call on array element

2010-01-19 Thread ian_harvey at bigpond dot com


--- Comment #1 from ian_harvey at bigpond dot com  2010-01-19 14:06 ---
Created an attachment (id=19655)
 -- (http://gcc.gnu.org/bugzilla/attachment.cgi?id=19655action=view)
Source code that demonstrates the ICE


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=42804



[Bug fortran/42684] New: ICE when interface operator(xx) available through host and use assoc in module procedure

2010-01-10 Thread ian_harvey at bigpond dot com
An internal compiler error (seg fault in gfc_get_default_type (symbol.c:226) -
due argument 'name' being passed in as a null ptr) occurs when two different
specific procedures for an operator (ie defining the same operator, but on
different derived types) are available, when one is available through host
association and the other though use association, in a module procedure (where
the USE is at the module procedure level, and not in the specification part of
the module

This is from compiling the trunk with svn rev 155795.


-- 
   Summary: ICE when interface operator(xx) available through host
and use assoc in module procedure
   Product: gcc
   Version: 4.5.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassigned at gcc dot gnu dot org
ReportedBy: ian_harvey at bigpond dot com
 GCC build triplet: i686-pc-mingw32
  GCC host triplet: i686-pc-mingw32
GCC target triplet: i686-pc-mingw32


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=42684



[Bug fortran/42684] ICE when interface operator(xx) available through host and use assoc in module procedure

2010-01-10 Thread ian_harvey at bigpond dot com


--- Comment #1 from ian_harvey at bigpond dot com  2010-01-10 23:21 ---
Created an attachment (id=19532)
 -- (http://gcc.gnu.org/bugzilla/attachment.cgi?id=19532action=view)
Example source that causes the ICE


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=42684



[Bug fortran/42684] ICE when interface operator(xx) available through host and use assoc in module procedure

2010-01-10 Thread ian_harvey at bigpond dot com


--- Comment #2 from ian_harvey at bigpond dot com  2010-01-11 01:56 ---
Some primitive debugging: As directed by parse_contained, parsing and
subsequent processing of the use statement in other_proc (parse_progunit)
occurs prior to parsing of the add_b function and hence determination of the
characteristics of the add_b symbol.  This use statement processing includes
ambiguous interface checking (gfc_compare_interfaces), which doesn't deal with
the case when the symbol associated with argument s2 is of unknown type
(BT_UNKNOWN) and no name is provided for type resolution.

A source code workaround is to move the USE statement to the specification part
of the module or to reorder the module procedures such that add_b occurs before
other_proc.

The internal error is also generated if the module procedure name given in the
INTERFACE OPERATOR block doesn't exist as a module procedure.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=42684



[Bug fortran/40443] New: Elemental procedure in genericl interface incorrectly selected in preference to specific procedure

2009-06-14 Thread ian_harvey at bigpond dot com
F95 standard section 14.1.2.4.1 (particular Note 14.6) implies to me that when
an elemental and a non-elemental specific procedure in a generic interface both
match a reference, it is the specific instance that should be selected.

The reference selected by gfortran appears to depend on the ordering of
procedures in the generic interface block.  I'd expect the last line of output
from the following to be S, S as a result of selecting the specific procedure
SpecProc.  I get E, E which has come from the elemental procedure.


MODULE SomeOptions
  IMPLICIT NONE  
  INTERFACE ElemSpec
MODULE PROCEDURE ElemProc
MODULE PROCEDURE SpecProc
  END INTERFACE ElemSpec  
  INTERFACE SpecElem
MODULE PROCEDURE SpecProc
MODULE PROCEDURE ElemProc
  END INTERFACE SpecElem
CONTAINS
  ELEMENTAL SUBROUTINE ElemProc(a)  
CHARACTER, INTENT(OUT) :: a
!
a = 'E'
  END SUBROUTINE ElemProc

  SUBROUTINE SpecProc(a)  
CHARACTER, INTENT(OUT) :: a(:)
!
a = 'S'
  END SUBROUTINE SpecProc
END MODULE SomeOptions

PROGRAM MakeAChoice
  USE SomeOptions  
  IMPLICIT NONE
  CHARACTER scalar, array(2)
  !
  CALL ElemSpec(scalar) ! Should choose the elemental (and does)
  WRITE (*, 100) scalar
  CALL ElemSpec(array)  ! Should choose the specific (and does)
  WRITE (*, 100) array
  !
  CALL SpecElem(scalar) ! Should choose the elemental (and does)
  WRITE (*, 100) scalar
  CALL SpecElem(array)  ! Should choose the specific (but doesn't)
  WRITE (*, 100) array  
  !
  100 FORMAT(A,:,', ',A)
END PROGRAM MakeAChoice


gfortran --version
GNU Fortran (GCC) 4.5.0 20090421 (experimental) [trunk revision 146519]


-- 
   Summary: Elemental procedure in genericl interface incorrectly
selected in preference to specific procedure
   Product: gcc
   Version: 4.5.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassigned at gcc dot gnu dot org
ReportedBy: ian_harvey at bigpond dot com
 GCC build triplet: i586-pc-mingw32
  GCC host triplet: i586-pc-mingw32
GCC target triplet: i586-pc-mingw32


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=40443