[Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression

2011-05-28 Thread neil.n.carlson at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

   Summary: [OOP] gfortran rejects structure constructor
expression
   Product: gcc
   Version: 4.7.0
Status: UNCONFIRMED
  Severity: major
  Priority: P3
 Component: fortran
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: neil.n.carl...@gmail.com


In the following program type-compatible variables are used as an expression in
a structure constructor for an allocatable CLASS(S) component.  In the first
case a TYPE(S) variable is used, and in the second a TYPE(S2), where S2 extends
S.

The program compiles with nagfor 5.2 and (reportedly) with the cray compiler,
but gfortran rejects the code with the error messages:

  Tobj = T(Sobj)
   1
Error: Can't convert TYPE(s) to CLASS(s) at (1)

  Tobj = T(S2obj)
   1
Error: Can't convert TYPE(s2) to CLASS(s) at (1)

===

From the F2008 standard:

For a nonpointer component, the declared type and type parameters of the
component and expr shall conform in the same way as for a variable and expr in
an intrinsic assignment statement (7.2.1.2) [...] (4.5.10p2)

if the variable is polymorphic it shall be type compatible with expr; [...]
(7.2.1.2p1(4))

Also 4.5.10 p6 applies to allocatable components.

===

program main

  type :: S
integer :: n
  end type
  type(S) :: Sobj

  type, extends(S) :: S2
integer :: m
  end type
  type(S2) :: S2obj

  type :: T
class(S), allocatable :: x
  end type
  type(T) :: Tobj

  Sobj = S(1)
  Tobj = T(Sobj)

  S2obj = S2(1,2)
  Tobj = T(S2obj)

end program


[Bug fortran/45786] Relational operators .eq. and == are not recognized as equivalent

2011-05-28 Thread neil.n.carlson at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=45786

--- Comment #7 from neil.n.carlson at gmail dot com 2011-05-28 18:14:04 UTC ---
So what is the status of this defect?   It would appear to be will not fix.


[Bug fortran/49213] [OOP] gfortran rejects structure constructor expression

2011-06-16 Thread neil.n.carlson at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

--- Comment #3 from neil.n.carlson at gmail dot com 2011-06-16 20:35:48 UTC ---
(In reply to comment #1)
 Note: Intrinsic assignments to polymorphic variables are forbidden [...]

This was really about the structure constructor; the assignment was
just to do something with the value, so the example was poor.  Here's
a slightly different version that gets to the heart of what I intended:

program main

  type :: S
integer :: n
  end type
  type(S) :: Sobj

  type, extends(S) :: S2
integer :: m
  end type
  type(S2) :: S2obj

  type :: T
class(S), allocatable :: x
  end type

  Sobj = S(1)
  call pass_it (T(Sobj))

  S2obj = S2(1,2)
  call pass_it (T(S2obj))

contains

  subroutine pass_it (foo)
type(T), intent(in) :: foo
  end subroutine

end program

This gives the same errors:

  call pass_it (T(Sobj))
  1
Error: Can't convert TYPE(s) to CLASS(s) at (1)

  call pass_it (T(S2obj))
  1
Error: Can't convert TYPE(s2) to CLASS(s) at (1)


[Bug fortran/49213] [OOP] gfortran rejects structure constructor expression

2011-06-16 Thread neil.n.carlson at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

--- Comment #4 from neil.n.carlson at gmail dot com 2011-06-16 20:49:32 UTC ---
An intuitive way of viewing (and maybe even implementing I guess) the process
triggered by a structure constructor is as a sequence of assignment statements
for the components of the structure.  But that's not how the (2008) standard
describes what takes place, and so constraints that apply to assignments (like
assigning to a polymorphic) don't apply in this context.


[Bug fortran/49213] [OOP] gfortran rejects structure constructor expression

2011-06-16 Thread neil.n.carlson at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

--- Comment #6 from neil.n.carlson at gmail dot com 2011-06-16 22:12:17 UTC ---
(In reply to comment #5)
 (In reply to comment #4)
  An intuitive way of viewing (and maybe even implementing I guess) the 
  process
  triggered by a structure constructor [...]
 
 I think you are wrong here.
 
 F08:7.2.1.3p13:
 
 An intrinsic assignment where the variable is of derived type [...]

Sorry, I wasn't talking about intrinsic assignment.  I was (unsuccessfully)
trying to talk about what happens when a structure constructor expression,
like T(Sobj) is encountered.  The compiler has to generate a temporary
object of type T and define its components, and what I was trying to say
(and I might be wrong about this) is that this process of defining the
components using the expressions given to the constructor is not like
normal assignment (intrinsic or defined) of derived type objects.
The reason for raising this was that the error messages suggest that
that is how the compiler is viewing it.

Sorry for the confusion.


[Bug fortran/49213] [OOP] gfortran rejects structure constructor expression

2011-06-16 Thread neil.n.carlson at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

--- Comment #7 from neil.n.carlson at gmail dot com 2011-06-16 22:18:14 UTC ---
I want to emphasize again that the error I wanted to report was that gfortran
is rejecting valid structure constructor expressions (see comment 3).  It looks
from you example that there is also an error with assignment, but that's
orthogonal to the constructor error.


[Bug fortran/45786] New: Relational operators .eq. and == are not recognized as equivalent

2010-09-24 Thread neil.n.carlson at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=45786

   Summary: Relational operators .eq. and == are not recognized as
equivalent
   Product: gcc
   Version: 4.6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: neil.n.carl...@gmail.com


The first paragraph of 7.2 in the standard states that The operators , ...
always have the same interpretations as the operators .LT., ...  Consider the
following example:

module foo_type
  private
  public :: foo, operator(==)
  type :: foo
integer :: bar
  end type
  interface operator(.eq.)
module procedure eq_foo
  end interface
contains
  logical function eq_foo (a, b)
type(foo), intent(in) :: a, b
eq_foo = (a%bar == b%bar)
  end function
end module

subroutine use_it (a, b)
  use foo_type
  type(foo) :: a, b
  print *, a == b
end subroutine

The compiler incorrectly complains (essentially) that it has no == operator for
the operands when in fact it should -- it appears that the defined .EQ.
operator is not being treated as the same as == in the module.  Here's the
compiler error:

  print *, a == b
  1
Error: Operands of comparison operator '==' at (1) are TYPE(foo)/TYPE(foo)

-- 
Configure bugmail: http://gcc.gnu.org/bugzilla/userprefs.cgi?tab=email
--- You are receiving this mail because: ---
You are on the CC list for the bug.


[Bug fortran/45786] Relational operators .eq. and == are not recognized as equivalent

2010-09-24 Thread neil.n.carlson at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=45786

--- Comment #2 from neil.n.carlson at gmail dot com 2010-09-25 00:27:24 UTC ---
Note also that the problem isn't restricted to .eq./== ; it appears to occur
with all the other pairs of equivalent operators: .ne./!=, .lt./, etc.  At
least the compiler is consistent :)

-- 
Configure bugmail: http://gcc.gnu.org/bugzilla/userprefs.cgi?tab=email
--- You are receiving this mail because: ---
You are on the CC list for the bug.


[Bug fortran/45794] New: internal compiler error: Segmentation fault

2010-09-25 Thread neil.n.carlson at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=45794

   Summary: internal compiler error: Segmentation fault
   Product: gcc
   Version: 4.6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: neil.n.carl...@gmail.com


The following code causes an internal compiler error with the
current trunk:

$ gfortran --version
GNU Fortran (GCC) 4.6.0 20100924 (experimental)

subroutine foo (vector, mask)
  real :: vector(:)
  logical, optional :: mask(:)
  integer :: loc(1)
  if (present(mask)) then
loc = maxloc(vector, mask)
  end if
end subroutine

$ gfortran -c bug3.f90 
bug3.f90: In function ‘foo’:
bug3.f90:6:0: internal compiler error: Segmentation fault

Note that this bug does not exist in 4.4 (or 4.5 I think).


[Bug fortran/66577] ICE in generate_finalization_wrapper, at fortran/class.c:1567

2015-11-08 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=66577

--- Comment #5 from neil.n.carlson at gmail dot com ---
> Error: Function result 'intsuccess' at (1) cannot have an initializer

> I don't understand.

C506 -- the type specification for a function result cannot have an
initialization.

[Bug fortran/68174] New: Length parameter in character allocation not recognized as a scalar (regression from 5.2)

2015-11-01 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68174

Bug ID: 68174
   Summary: Length parameter in character allocation not
recognized as a scalar (regression from 5.2)
   Product: gcc
   Version: 6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

The following example is rejected by 6.0.0 20151025, but is accepted by 6.0.0
20150906 and 5.2.0.  It is valid Fortran.

% gfortran -c gfortran-bug-20151101A.f90 
gfortran-bug-20151101A.f90:15:25:

   allocate(character(this%maxlen) :: this%mold)
 1
Error: Scalar INTEGER expression expected at (1)

module example

  type :: foo
class(*), allocatable :: mold
integer :: maxlen
  end type

contains

  subroutine pop (this)
class(foo), intent(inout) :: this
select type (uptr => this%mold)
type is (character(*))
  deallocate(this%mold)
  allocate(character(this%maxlen) :: this%mold)
end select
  end subroutine

end module

[Bug fortran/54070] [4.9/5/6 Regression] Wrong code with allocatable deferred-length (array) function results

2015-11-01 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=54070

neil.n.carlson at gmail dot com changed:

   What|Removed |Added

 CC||neil.n.carlson at gmail dot com

--- Comment #19 from neil.n.carlson at gmail dot com ---
What is the status of this issue?  It would appear from comment 18 to be
"fixed" insofar as the the provided examples compile, but is the compiled code
correct?

I'd report the following example as a new bug, but I know it would be
immediately dismissed as a duplicate of this bug.  This dumb little example
compiles with 5.2 and the 20151025 snapshot of 6.0, but in both cases the
generated code is bad as it segfaults on a clearly valid assignment statement.

program main
  character(:), allocatable :: string(:)
  call fubar (string)
contains
  subroutine fubar (string)
character(:), allocatable, intent(out) :: string(:)
allocate(character(5) :: string(2))
print *, 'len(string)=', len(string), ', size(string)=', size(string)
string = 'fubar' ! <== SEGMENTATION FAULT HERE
  end subroutine
end program

Produces this output:

 len(string)=   5 , size(string)=   2

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

Backtrace for this error:
#0  0x7FFB05C4E517
#1  0x7FFB05C4EB5E
#2  0x7FFB0514F95F
#3  0x7FFB051B6EC8
#4  0x400D23 in fubar.3417 at fubar.f90:?
#5  0x400DC9 in MAIN__ at fubar.f90:?
Segmentation fault (core dumped)

[Bug fortran/54070] [4.9/5/6 Regression] Wrong code with allocatable deferred-length (array) function results

2015-11-01 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=54070

--- Comment #23 from neil.n.carlson at gmail dot com ---
Here's an even simpler example with the deferred length character array as a
local variable -- not a function result or dummy argument.  Sure seems as
though the allocate statement itself is what is being mishandled:

program main
  character(:), pointer :: s(:)
  allocate(character(3)::s(2))
  s(1) = 'foo'; s(2) = 'bar'
  print *, s, ' (expect "foobar")'
end program

Compiles with both 5.2 and 6.0 20151025, but both return the wrong result:

 barbar (expect "foobar")

[Bug fortran/66577] ICE in generate_finalization_wrapper, at fortran/class.c:1567

2015-11-07 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=66577

neil.n.carlson at gmail dot com changed:

   What|Removed |Added

 CC||neil.n.carlson at gmail dot com

--- Comment #2 from neil.n.carlson at gmail dot com ---
I'm getting an ICE at the same line in generate_finalization_wrapper with the
following much smaller example:

module json

  type :: array_element
  contains
final :: array_element_delete
  end type

  type, public :: json_array_iterator
type(array_element), pointer :: element
  end type

contains

  subroutine array_element_delete (this)
type(array_element) :: this
  end subroutine

  subroutine array_iter_next (this)
class(json_array_iterator) :: this
  end subroutine

end module

% gfortran -c json.F90 
f951: internal compiler error: in generate_finalization_wrapper, at
fortran/class.c:1567
0x5fbccb generate_finalization_wrapper
../../gcc-5.2.0/gcc/fortran/class.c:1566
0x5fbccb gfc_find_derived_vtab(gfc_symbol*)
../../gcc-5.2.0/gcc/fortran/class.c:2401
0x67ce35 resolve_fl_derived
../../gcc-5.2.0/gcc/fortran/resolve.c:12946
0x6778c7 resolve_symbol
../../gcc-5.2.0/gcc/fortran/resolve.c:13226
0x69014b do_traverse_symtree
../../gcc-5.2.0/gcc/fortran/symbol.c:3646
0x67aa02 resolve_types
../../gcc-5.2.0/gcc/fortran/resolve.c:14973
0x67664f gfc_resolve(gfc_namespace*)
../../gcc-5.2.0/gcc/fortran/resolve.c:15083
0x661f56 gfc_parse_file()
../../gcc-5.2.0/gcc/fortran/parse.c:5476
0x6a15f5 gfc_be_parse_file
../../gcc-5.2.0/gcc/fortran/f95-lang.c:229
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.

This is with 5.2.  But I get the same ICE with 4.9.2 and 6.0 20151025

[Bug fortran/68216] [F2003] IO problem with allocatable, deferred character length arrays

2015-11-06 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68216

--- Comment #5 from neil.n.carlson at gmail dot com ---
Paul, I'm delighted than someone is finally working on this long-standing
problem. I hope you're also taking a look at all the other related PRs that
Dominique pointed out; I suspect that they all share the same core error. 
-Neil

[Bug fortran/67560] New: False positive with -fcheck=recursion

2015-09-12 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=67560

Bug ID: 67560
   Summary: False positive with -fcheck=recursion
   Product: gcc
   Version: 5.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

The following example produces a runtime recursion error during finalization
with -fcheck=recursion.  There is indeed recursion, but the final subroutine is
declared recursive.

module foo
  type :: list
type(list), pointer :: next => null()
  contains
final :: list_delete
  end type
contains
  recursive subroutine list_delete (this)
type(list), intent(inout) :: this
if (associated(this%next)) deallocate(this%next)
  end subroutine
end module foo

program main
  use foo
  type(list), pointer :: x
  allocate(x)
  allocate(x%next)
  deallocate(x)
end program


[Bug fortran/67562] New: Bad result from sourced allocation with class(*) arrays

2015-09-12 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=67562

Bug ID: 67562
   Summary: Bad result from sourced allocation with class(*)
arrays
   Product: gcc
   Version: 5.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

The following example produces incorrect results from the sourced allocation
involving class(*) arrays.  Perhaps the same as 64692, but that is reported as
fixed.

Expected output:
 source=   1   2
 copy= 1   2 (expect same as source)

But getting this:
 source=   1   2
 copy= 2   0 (expect same as source)

module any_vector_type

  type :: any_vector
class(*), allocatable :: x(:)
  end type

  interface any_vector
procedure any_vector_init
  end interface

contains

  function any_vector_init (x) result (this)
class(*), intent(in) :: x(:)
type(any_vector) :: this
call fubar (this, x)
  end function

  subroutine fubar (this, x)
class(any_vector), intent(out) :: this
class(*), intent(in) :: x(:)
allocate(this%x(lbound(x,1):ubound(x,1)), source=x)
select type (x)
type is (integer)
  print *, 'source=', x
end select
select type (y => this%x)
type is (integer)
  print *, 'copy=  ', y, '(expect same as source)'
end select
  end subroutine

end module

program main
  use any_vector_type
  type(any_vector) :: a
  a = any_vector([1,2])
end program


[Bug fortran/67562] Bad result from sourced allocation with class(*) arrays

2015-09-12 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=67562

--- Comment #2 from neil.n.carlson at gmail dot com ---
Please pardon my ignorance (I rarely use gfortran), but is there a 6.0 source
distribution somewhere?  The latest I can find is 5.2.  Are you talking about
the current trunk?  I'm puzzled because the r222361 you reference appears to
predate 5.2 by several months.  I've got a bunch of other gfortran bugs (with
5.2) to chase down, and it looks like much would be wasted effort.


[Bug fortran/67564] New: Segfault on sourced allocattion statement with class(*) arrays

2015-09-13 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=67564

Bug ID: 67564
   Summary: Segfault on sourced allocattion statement with
class(*) arrays
   Product: gcc
   Version: 6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

The following example segfaults on the allocate statement.
Using the trunk version of 20150906.

program main
  type :: any_vector
class(*), allocatable :: x(:)
  end type
  type(any_vector) :: a
  allocate(a%x(2), source=['foo','bar'])
end program

Here's the output:

$ gfortran --version gfortran-bug-20150913A.f90 
GNU Fortran (GCC) 6.0.0 20150906 (experimental)

$ gfortran gfortran-bug-20150913A.f90 
$ ./a.out

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

Backtrace for this error:
#0  0x7F338430C517
#1  0x7F338430CB5E
#2  0x7F338380D95F
#3  0x7F33838677ED
#4  0x400932 in __copy_character_1.3388 at gfortran-bug-20150913A.f90:?
#5  0x400AC6 in MAIN__ at gfortran-bug-20150913A.f90:?
Segmentation fault (core dumped)


[Bug fortran/54070] [4.9/5 Regression] Wrong code with allocatable deferred-length (array) function results

2016-01-18 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=54070

--- Comment #30 from neil.n.carlson at gmail dot com ---
Paul, you've done a lot of great work here (a huge thanks!) and I can confirm
that many of my deferred-length character issues seem to be resolved now with
the trunk (r232457, 1/15/2016).  I'm uncertain though whether you consider this
PR resolved or if you are still working on it (there were lots of examples in
PRs marked as duplicates).  I still have at least one remaining issue with this
trunk version:

class(*), allocatable :: x(:)
allocate(x, source=['foo','bar'])
end

Compiles fine, but produces a run time seg fault:

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

Backtrace for this error:
#0  0x7F85F60F5517
#1  0x7F85F60F5B5E
#2  0x7F85F55F695F
#3  0x7F85F56507ED
#4  0x400932 in __copy_character_1.3416 at bug.f90:?
#5  0x400B91 in MAIN__ at bug.f90:?
Segmentation fault (core dumped)

Should I open another PR for this?

[Bug fortran/54070] [4.9/5 Regression] Wrong code with allocatable deferred-length (array) function results

2016-01-18 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=54070

--- Comment #31 from neil.n.carlson at gmail dot com ---
Sorry, ignore the example of comment 30.  I had already reported this in PR
67564 (not a duplicate of this one).  I'm getting old ...

[Bug fortran/69563] New: Generic TBP incorrectly resolves to elemental

2016-01-29 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=69563

Bug ID: 69563
   Summary: Generic TBP incorrectly resolves to elemental
   Product: gcc
   Version: 6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

In the following example program the call to X%SUB should resolve to SUB_ARRAY,
but instead the compiler tries to resolve it to the elemental SUB_ELEM, but
then emits an error (as it must) because the the THIS argument is not also an
array:

gfortran-bug-20160129.f90:46:8:

   call x%sub ([1,2])
1

Error: Actual argument at (1) for INTENT(INOUT) dummy ‘this’ of ELEMENTAL
subroutine ‘sub_elem’ is a scalar, but another actual argument is an array

Here's the code:

module a_type

  type :: a
integer :: n
  contains
procedure :: sub_elem
procedure :: sub_array
generic :: sub => sub_elem, sub_array
  end type

contains

  elemental subroutine sub_elem (this, arg)
class(a), intent(inout) :: this
integer, intent(in) :: arg
this%n = arg
  end subroutine

  subroutine sub_array (this, arg)
class(a), intent(inout) :: this
integer, intent(in) :: arg(:)
this%n = sum(arg)
  end subroutine

end module

program main

  use a_type
  type(a) :: x, y(2)

  call x%sub ([1,2])
  call y%sub ([1,2])

  print *, x%n, '(expect 3)'
  print *, y%n, '(expect 1 2)'

end program

Interestingly, this similar example, where the generic is not TB, compiles and
runs as expected:

module foo
  interface sub
module procedure sub_elem, sub_array
  end interface
contains
  elemental subroutine sub_elem (a, b)
integer, intent(out) :: a
integer, intent(in)  :: b
a = b
  end subroutine
  subroutine sub_array (a, b)
integer, intent(out) :: a
integer, intent(in)  :: b(:)
a = sum(b)
  end subroutine
end module

program main
  use foo
  integer x, y(2)
  call sub (x, [1,2])
  call sub (y, [1,2])
  print *, x, '(expect 3)'
  print *, y, '(expect 1 2)'
end

[Bug fortran/70312] New: Spurious -Wsurprising warnings for final subroutines

2016-03-19 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=70312

Bug ID: 70312
   Summary: Spurious -Wsurprising warnings for final subroutines
   Product: gcc
   Version: 6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

-Wsurprising issues spurious warnings about final procedures.

module foo_type
  type foo
  contains
final :: foo_delete
  end type
contains
  subroutine foo_delete (this)
type(foo), intent(inout) :: this
  end subroutine
end module

program main
  use foo_type
end program

Compiling with "gfortran -Wsurprising" gives:

gfortran-bug-20160319.f90:13:6:

   use foo_type
  1
Warning: Only array FINAL procedures declared for derived type ‘foo’ defined at
(1), suggest also scalar one [-Wsurprising]

But the final subroutine was a scalar one. Perhaps the intended message was
"Only scalar FINAL ..., suggest also array one"?

Making the subroutine elemental

  elemental subroutine foo_delete (this)
type(foo), intent(inout) :: this(:)
  end subroutine

gives the same warning message, which is also incorrect.

Aside from issuing only valid warning messages, the larger question is how
thorough should -Wsurprising be.  Apart from an elemental final subroutine, one
needs to be provided for scalar and *every* possible rank of array in order to
ensure all possibilities are covered.  Should -Wsurprising be warning for each
and every missing one?

[Bug fortran/70312] Spurious -Wsurprising warnings for final subroutines

2016-03-19 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=70312

neil.n.carlson at gmail dot com changed:

   What|Removed |Added

 Status|UNCONFIRMED |RESOLVED
 Resolution|--- |DUPLICATE

--- Comment #1 from neil.n.carlson at gmail dot com ---
This is a duplicate of PR 58175, but the elemental final procedure should be a
test case for that PR.

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

[Bug fortran/58175] [OOP] Incorrect warning message on scalar finalizer

2016-03-19 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=58175

neil.n.carlson at gmail dot com changed:

   What|Removed |Added

 CC||neil.n.carlson at gmail dot com

--- Comment #8 from neil.n.carlson at gmail dot com ---
*** Bug 70312 has been marked as a duplicate of this bug. ***

[Bug fortran/67564] Segfault on sourced allocattion statement with class(*) arrays

2016-03-21 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=67564

--- Comment #10 from neil.n.carlson at gmail dot com ---
Here's another example, but in this case the bad, source-allocated class(*)
variable is just a local variable.  It is rank-2 however.

character(:), allocatable :: array(:,:)
array = reshape(['foo','bar'],shape=[2,1])
call sub (array)
contains
  subroutine sub (array)
class(*), intent(in) :: array(:,:)
class(*), allocatable :: copy(:,:)
  select type (array)
  type is (character(*))
  print *, len(array), shape(array), array, ' (expect 3 2 1 foobar)'
  end select
allocate(copy, source=array)
  select type (copy)
  type is (character(*))
  print *, len(copy), shape(copy), copy, ' (expect 3 2 1 foobar)'
  end select
  end
end

I'm getting this output.  The result of the copy is corrupt.

   3   2   1 foobar (expect 3 2 1 foobar)
   3   2   1 foob� (expect 3 2 1 foobar)

[Bug fortran/67564] Segfault on sourced allocattion statement with class(*) arrays

2016-03-20 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=67564

--- Comment #9 from neil.n.carlson at gmail dot com ---
I confirm that my original example now runs without error with the current
6-branch.  However this variation, where the allocated unlimited polymorphic
variable is passed back as a return argument, is not working correctly.

class(*), allocatable :: val(:)
call get_value (val)
select type (val)
type is (character(*))
  print *, 'size(val)=', size(val)
  print *, 'len(val)=', len(val)
  print *, 'val=', val
end select
contains
  subroutine get_value (value)
class(*), allocatable, intent(out) :: value(:)
allocate(value, source=['foo','bar'])
  end subroutine
end

Here is the output from running the compiled program:
 size(val)=   2
 len(val)=   0
 val=

The length of the character variable should be 3.  I don't think the problem is
as simple as the length not being assigned properly.  In my actual use case
(much more complicated) attempting to print "val" results in a segmentation
fault.

[Bug fortran/77310] New: ICE on SELECT CASE with associate name

2016-08-21 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=77310

Bug ID: 77310
   Summary: ICE on SELECT CASE with associate name
   Product: gcc
   Version: 6.1.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

The following example triggers an ICE with gfortran 6.1.0:

subroutine ice_example
  type :: inner
integer :: n
  end type
  type :: outer
type(inner), allocatable :: array(:)
  end type
  type(outer) :: var
  associate (n_array => var%array%n)
select case (n_array(1))  ! <== ICE HERE
case default
end select
  end associate
end subroutine

Here is the output I get:

gfortran-bug-20160821.f90:38:0:

 select case (n_array(1))

internal compiler error: in gfc_get_element_type, at fortran/trans-types.c:1181
0x6f1daa gfc_get_element_type(tree_node*)
../../gcc/fortran/trans-types.c:1181
0x6ea705 trans_associate_var
../../gcc/fortran/trans-stmt.c:1581
0x6ea705 gfc_trans_block_construct(gfc_code*)
../../gcc/fortran/trans-stmt.c:1806
0x688977 trans_code
../../gcc/fortran/trans.c:1785
0x6abe8c gfc_generate_function_code(gfc_namespace*)
../../gcc/fortran/trans-decl.c:6154
0x644c50 translate_all_program_units
../../gcc/fortran/parse.c:5613
0x644c50 gfc_parse_file()
../../gcc/fortran/parse.c:5819
0x685cc5 gfc_be_parse_file
../../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.

[Bug fortran/67564] Segfault on sourced allocattion statement with class(*) arrays

2016-09-06 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=67564

--- Comment #11 from neil.n.carlson at gmail dot com ---
Ping

[Bug fortran/79072] [5/6/7 Regression] ICE with class(*) pointer function result and character value

2017-01-13 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79072

--- Comment #3 from neil.n.carlson at gmail dot com ---
Why is this tagged with 'ice-on-invalid-code'?  What is invalid about the code?

[Bug fortran/79072] ICE with class(*) pointer function result and character value

2017-01-13 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79072

--- Comment #5 from neil.n.carlson at gmail dot com ---
Here's a more complete example that avoids the ICE.

It gives correct results with 6.3:
   5 fubar
   5 fubar

But incorrect results with 7.0:
   5 fubar
   0 


program main

  class(*), pointer :: x, y
  allocate(x, source='fubar')

  y => foobar(x)

  select type (y)
  type is (character(*))
print *, len(y), y
  end select

contains

  function foobar(bar) result(foo)
class(*), pointer :: foo, bar
foo => bar
select type (foo)
type is (character(*))
  print *, len(foo), foo
end select
  end function

end program

[Bug fortran/79072] New: ICE with class(*) pointer function result and character value

2017-01-12 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79072

Bug ID: 79072
   Summary: ICE with class(*) pointer function result and
character value
   Product: gcc
   Version: 7.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

This example gives an ICE with the current 7.0 trunk and all 6.x releases:

function foo()
  class(*), pointer :: foo
  character(3), target :: string = 'foo'
  foo => string
  select type (foo)
  type is (character(*))
!print *, foo
  end select
end function

The ICE disappears if either:
1) type is (character(*)) is replaced with integer, for example;
2) the return variable is specified in a result(...) clause.

In the original code that exhibited the compiler bug, the function
returns correct values except for character values, so I expect the
underlying problem involves the unlimited polymorphic pointer
assignment statement and character dynamic types.  I introduced
the select type (which produced the ICE) when debugging. 

Here's the output from the compiler:

$ gfortran -c code.f90 
code.f90:1:0:

 function foo()

internal compiler error: tree check: expected record_type or union_type or
qual_union_type, have function_type in gfc_class_len_get, at
fortran/trans-expr.c:226
0xe75f1c tree_check_failed(tree_node const*, char const*, int, char const*,
...)
../../gcc/tree.c:9814
0x6f03c5 tree_check3(tree_node*, char const*, int, char const*, tree_code,
tree_code, tree_code)
../../gcc/tree.h:3100
0x6f03c5 gfc_class_len_get(tree_node*)
../../gcc/fortran/trans-expr.c:226
0x745cbc trans_associate_var
../../gcc/fortran/trans-stmt.c:1757
0x745cbc gfc_trans_block_construct(gfc_code*)
../../gcc/fortran/trans-stmt.c:1810
0x6ba467 trans_code
../../gcc/fortran/trans.c:1913
0x747c1e gfc_trans_select_type_cases
../../gcc/fortran/trans-stmt.c:2401
0x747c1e gfc_trans_select_type(gfc_code*)
../../gcc/fortran/trans-stmt.c:3112
0x6ba3d7 trans_code
../../gcc/fortran/trans.c:1933
0x745638 gfc_trans_block_construct(gfc_code*)
../../gcc/fortran/trans-stmt.c:1803
0x6ba467 trans_code
../../gcc/fortran/trans.c:1913
0x6eb598 gfc_generate_function_code(gfc_namespace*)
../../gcc/fortran/trans-decl.c:6292
0x672f76 translate_all_program_units
../../gcc/fortran/parse.c:6008
0x672f76 gfc_parse_file()
../../gcc/fortran/parse.c:6208
0x6b6512 gfc_be_parse_file
../../gcc/fortran/f95-lang.c:202
Please submit a full bug report,

[Bug fortran/79072] ICE with class(*) pointer function result and character value

2017-08-12 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79072

--- Comment #8 from neil.n.carlson at gmail dot com ---
Ping.  Is there any interest in fixing this regression?

[Bug fortran/79072] ICE with class(*) pointer function result and character value

2017-05-07 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79072

neil.n.carlson at gmail dot com changed:

   What|Removed |Added

  Known to fail||7.1.0

--- Comment #6 from neil.n.carlson at gmail dot com ---
Comment 1 code example segfaults with the 7.1.0 release (and earlier).

Comment 5 code example gives incorrect results with the 7.1.0 release,
but correct results with 6.3 and 5.2 -- a regression.

[Bug fortran/82996] ICE and segfault with derived type finalization

2017-11-15 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82996

--- Comment #5 from neil.n.carlson at gmail dot com ---
I've built the svn trunk and tested the examples with it.  The ICEs with the
comment 2 and 3 examples are gone, as Dominique found.  The comment 1 example
continues to segfault when executed, as does the comment 2 example now.  The
comment 3 example executes without error.  I think Dominique swapped 2 and 3.

[Bug fortran/82996] New: ICE and segfault with derived type finalization

2017-11-14 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82996

Bug ID: 82996
   Summary: ICE and segfault with derived type finalization
   Product: gcc
   Version: 6.4.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

I'm going to give 3 examples. The first gives a spurious run time segfault. The
others are attempts to work around the problem, but give an internal compiler
error.  These all work fine with the Intel and NAG compilers.

The first example:

module mod

  type foo
integer, pointer :: f(:) => null()
  contains
final :: foo_destroy
  end type

  type bar
type(foo) :: b(2)
  end type

contains

  elemental subroutine foo_destroy(this)
type(foo), intent(inout) :: this
if (associated(this%f)) deallocate(this%f)
  end subroutine

end module

program main

  use mod
  type(bar) :: x
  call sub(x)

contains

  subroutine sub(x)
type(bar), intent(out) :: x
  end subroutine

end program

And the output from running the executable:

$ gfortran -g gfortran-bug-20171114a.f90 
$ ./a.out

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

Backtrace for this error:
#0  0x7f1188b42df7 in ???
#1  0x7f1188b4202d in ???
#2  0x7f118803694f in ???
#3  0x400fa7 in __mod_MOD_foo_destroy
at /home/nnc/Fortran/Bugs/gfortran/tmp/gfortran-bug-20171114a.f90:46
#4  0x400f0f in __mod_MOD___final_mod_Foo
at /home/nnc/Fortran/Bugs/gfortran/tmp/gfortran-bug-20171114a.f90:49
#5  0x400b29 in __mod_MOD___final_mod_Bar
at /home/nnc/Fortran/Bugs/gfortran/tmp/gfortran-bug-20171114a.f90:49
#6  0x401026 in sub
at /home/nnc/Fortran/Bugs/gfortran/tmp/gfortran-bug-20171114a.f90:59
#7  0x40104a in MAIN__
at /home/nnc/Fortran/Bugs/gfortran/tmp/gfortran-bug-20171114a.f90:55
#8  0x401080 in main
at /home/nnc/Fortran/Bugs/gfortran/tmp/gfortran-bug-20171114a.f90:53
Segmentation fault (core dumped)

[Bug fortran/82996] ICE and segfault with derived type finalization

2017-11-14 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82996

--- Comment #2 from neil.n.carlson at gmail dot com ---
In the final example I drop the elemental attribute from the FOO final
procedure and modify the BAR final procedure to loop over the elements of its B
array component.  This too yields an ICE:

f951: internal compiler error: in generate_finalization_wrapper, at
fortran/class.c:1975

module mod

  type foo
integer, pointer :: f(:) => null()
  contains
final :: foo_destroy
  end type

  type bar
type(foo) :: b(2)
  contains
final :: bar_destroy
  end type

contains

  subroutine foo_destroy(this)
type(foo), intent(inout) :: this
if (associated(this%f)) deallocate(this%f)
  end subroutine

  subroutine bar_destroy(this)
type(bar), intent(inout) :: this
integer :: j
do j = 1, size(this%b)
  call foo_destroy(this%b(j))
end do
  end subroutine

end module

program main
  use mod
  type(bar) :: x
  call sub(x)
contains
  subroutine sub(x)
type(bar), intent(out) :: x
  end subroutine
end program

[Bug fortran/82996] ICE and segfault with derived type finalization

2017-11-14 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82996

--- Comment #1 from neil.n.carlson at gmail dot com ---
In the second example, I add a final procedure for BAR (not necessary) and
explicitly call the FOO final procedure on its B component.  This gives an ICE

f951: internal compiler error: in generate_finalization_wrapper, at
fortran/class.c:1975

module mod

  type foo
integer, pointer :: f(:) => null()
  contains
final :: foo_destroy
  end type

  type bar
type(foo) :: b(2)
  contains
final :: bar_destroy
  end type

contains

  elemental subroutine foo_destroy(this)
type(foo), intent(inout) :: this
if (associated(this%f)) deallocate(this%f)
  end subroutine

  subroutine bar_destroy(this)
type(bar), intent(inout) :: this
call foo_destroy(this%b)
  end subroutine

end module

program main
  use mod
  type(bar) :: x
  call sub(x)
contains
  subroutine sub(x)
type(bar), intent(out) :: x
  end subroutine
end program

[Bug fortran/83148] New: [7.2 regression] ICE: crash_signal from toplev.c:325

2017-11-24 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83148

Bug ID: 83148
   Summary: [7.2 regression] ICE: crash_signal from toplev.c:325
   Product: gcc
   Version: 8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

The following example gives an ICE with the current 8.0 trunk, but not with
7.2.1 or 6.4.1.

module fhypre
  use iso_c_binding, only: c_ptr, c_null_ptr
  use iso_c_binding, only: hypre_obj => c_ptr, hypre_null_obj => c_null_ptr
  private
  public :: hypre_obj, hypre_null_obj
end module

module hypre_hybrid_type
  use fhypre
  type hypre_hybrid
type(hypre_obj) :: solver = hypre_null_obj
  end type hypre_hybrid
end module

Here's the traceback

$ gfortran -c gfortran-20171124c.f90
f951: internal compiler error: Segmentation fault
0xd6b98f crash_signal
../../gcc/toplev.c:325
0xfb33fd tree_class_check(tree_node const*, tree_code_class, char const*, int,
char const*)
../../gcc/tree.h:3480
0xfb33fd wi::from_mpz(tree_node const*, __mpz_struct*, bool)
../../gcc/wide-int.cc:244
0x900284 gfc_conv_mpz_to_tree(__mpz_struct*, int)
../../gcc/fortran/trans-const.c:205
0x9008bf gfc_conv_constant(gfc_se*, gfc_expr*)
../../gcc/fortran/trans-const.c:413
0x922b91 gfc_conv_initializer(gfc_expr*, gfc_typespec*, tree_node*, bool, bool,
bool)
../../gcc/fortran/trans-expr.c:6833
0x9231ad gfc_conv_structure(gfc_se*, gfc_expr*, int)
../../gcc/fortran/trans-expr.c:7748
0x922cdf gfc_conv_initializer(gfc_expr*, gfc_typespec*, tree_node*, bool, bool,
bool)
../../gcc/fortran/trans-expr.c:6883
0x90a78b gfc_get_symbol_decl(gfc_symbol*)
../../gcc/fortran/trans-decl.c:1819
0x90d340 gfc_create_module_variable
../../gcc/fortran/trans-decl.c:4943
0x8cf472 do_traverse_symtree
../../gcc/fortran/symbol.c:4157
0x910193 gfc_generate_module_vars(gfc_namespace*)
../../gcc/fortran/trans-decl.c:5415
0x8e88fc gfc_generate_module_code(gfc_namespace*)
../../gcc/fortran/trans.c:2180
0x89cf7b translate_all_program_units
../../gcc/fortran/parse.c:6078
0x89cf7b gfc_parse_file()
../../gcc/fortran/parse.c:6294
0x8e0eaf gfc_be_parse_file
../../gcc/fortran/f95-lang.c:204

[Bug fortran/79929] [7/8 Regression] Bogus Warning: '__builtin_memset': specified size 4294967291 exceeds maximum object size 2147483647

2017-11-24 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79929

Neil Carlson  changed:

   What|Removed |Added

 CC||neil.n.carlson at gmail dot com

--- Comment #22 from Neil Carlson  ---
I'm seeing these warning messages with essentially the same test case as
comment 0 using 8.0 (20171123) at -O1 and higher.

Same warning messages using 7.2.1 but only at -O2 and higher.

Even if these are bogus (I hope), they really need to be gotten rid of.

[Bug fortran/83146] New: ICE on SELECT CASE statement with associate name

2017-11-24 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83146

Bug ID: 83146
   Summary: ICE on SELECT CASE statement with associate name
   Product: gcc
   Version: 8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

The current 8.0 trunk gives an ICE on the following example.  6.4.1 also gives
an ICE.

type foo
  integer n
end type
type bar
  type(foo) array(2)
end type
type(bar) b
associate (n_array => b%array%n)
  select case (n_array(1))
  case default
  end select
end associate
end

Here's the traceback

$ gfortran -c gfortran-20171124.f90 
gfortran-20171124.f90:9:0:

   select case (n_array(1))

internal compiler error: in gfc_get_element_type, at fortran/trans-types.c:1231
0x5a5da8 gfc_get_element_type(tree_node*)
../../gcc/fortran/trans-types.c:1231
0x95d247 trans_associate_var
../../gcc/fortran/trans-stmt.c:1632
0x95d247 gfc_trans_block_construct(gfc_code*)
../../gcc/fortran/trans-stmt.c:1890
0x8e48c7 trans_code
../../gcc/fortran/trans.c:1924
0x90e7a8 gfc_generate_function_code(gfc_namespace*)
../../gcc/fortran/trans-decl.c:6437
0x89d036 translate_all_program_units
../../gcc/fortran/parse.c:6091
0x89d036 gfc_parse_file()
../../gcc/fortran/parse.c:6294
0x8e0eaf gfc_be_parse_file
../../gcc/fortran/f95-lang.c:204

[Bug fortran/83146] ICE on SELECT CASE statement with associate name

2017-11-24 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83146

--- Comment #1 from Neil Carlson  ---
I thought that assigning the select case expression to a temporary integer and
using that variable in the select case statement would be a workaround, but no.
You can put anything unrelated to the associate name in the select case and you
still get an ICE.  It seems the the associate block itself is the problem. 
Here's the tweaked example

type foo
  integer n
end type
type bar
  type(foo) array(2)
end type
type(bar) b
integer :: m=0
associate (n_array => b%array%n)
  select case (m)
  case default
  end select
end associate
end

[Bug fortran/83149] [8 Regression] ICE on SELECT CASE: crash_signal in toplev.c:325

2017-11-24 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83149

--- Comment #2 from Neil Carlson  ---
Here's another example.  The ICE is coming at the same place, toplev.c:325, so
I think it may be the same underlying problem.  Like the original example, the
ICE occurs only when the main program is in a separate file.

module mod1
  integer :: ncells
end module

module mod2
contains
  function get() result(array)
use mod1
real array(ncells)
  end function
end module

With this in a separate file:

use mod2
s = sum(get())
end

Note that the ICE goes away if "use mod1" is moved up to the module scope.
Here's the traceback

$ gfortran gfortran-20171124f.f90 gfortran-20171124f-main.f90 
gfortran-20171124f-main.f90:2:0:

 s = sum(get())

internal compiler error: Segmentation fault
0xd6b98f crash_signal
../../gcc/toplev.c:325
0x90aeeb gfc_finish_var_decl
../../gcc/fortran/trans-decl.c:606
0x90a274 gfc_get_symbol_decl(gfc_symbol*)
../../gcc/fortran/trans-decl.c:1777
0x920387 gfc_conv_variable
../../gcc/fortran/trans-expr.c:2505
0x91c71a gfc_conv_expr(gfc_se*, gfc_expr*)
../../gcc/fortran/trans-expr.c:7860
0x91ea0a gfc_apply_interface_mapping(gfc_interface_mapping*, gfc_se*,
gfc_expr*)
../../gcc/fortran/trans-expr.c:4355
0x8ebd04 gfc_set_loop_bounds_from_array_spec(gfc_interface_mapping*, gfc_se*,
gfc_array_spec*)
../../gcc/fortran/trans-array.c:920
0x91a5b1 gfc_conv_procedure_call(gfc_se*, gfc_symbol*, gfc_actual_arglist*,
gfc_expr*, vec*)
../../gcc/fortran/trans-expr.c:6024
0x91c6fa gfc_conv_expr(gfc_se*, gfc_expr*)
../../gcc/fortran/trans-expr.c:7852
0x8fa083 gfc_add_loop_ss_code
../../gcc/fortran/trans-array.c:2796
0x8faab5 gfc_conv_loop_setup(gfc_loopinfo*, locus*)
../../gcc/fortran/trans-array.c:5097
0x93ad87 gfc_conv_intrinsic_arith
../../gcc/fortran/trans-intrinsic.c:4197
0x93fd3f gfc_conv_intrinsic_function(gfc_se*, gfc_expr*)
../../gcc/fortran/trans-intrinsic.c:9146
0x91c6fa gfc_conv_expr(gfc_se*, gfc_expr*)
../../gcc/fortran/trans-expr.c:7852
0x925065 gfc_trans_assignment_1
../../gcc/fortran/trans-expr.c:10018
0x8e45cf trans_code
../../gcc/fortran/trans.c:1828
0x90e7a8 gfc_generate_function_code(gfc_namespace*)
../../gcc/fortran/trans-decl.c:6437
0x89d036 translate_all_program_units
../../gcc/fortran/parse.c:6091
0x89d036 gfc_parse_file()
../../gcc/fortran/parse.c:6294
0x8e0eaf gfc_be_parse_file
../../gcc/fortran/f95-lang.c:204

[Bug fortran/83149] New: ICE on SELECT CASE: crash_signal in toplev.c:325

2017-11-24 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83149

Bug ID: 83149
   Summary: ICE on SELECT CASE: crash_signal in toplev.c:325
   Product: gcc
   Version: 8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

The current 8.0 trunk gives an ICE on the following example, but only when then
the program units are in two separate files. Works fine with 7.2.1 and 6.4.1.

module mod
  character(8) string
contains
  function get_string() result(s)
character(len_trim(string)) s
s = string
  end function
end module

use mod
string = 'fubar'
select case (get_string())
case default
end select
end

Here's the traceback:

$ gfortran gfortran-20171124e.f90 gfortran-20171124e-main.f90 
gfortran-20171124e-main.f90:3:0:

 select case (get_string())

internal compiler error: Segmentation fault
0xd6b98f crash_signal
../../gcc/toplev.c:325
0x96852e gfc_sym_type(gfc_symbol*)
../../gcc/fortran/trans-types.c:2207
0x968ab7 gfc_get_function_type(gfc_symbol*)
../../gcc/fortran/trans-types.c:2969
0x907aed gfc_get_extern_function_decl(gfc_symbol*)
../../gcc/fortran/trans-decl.c:2126
0x907ffd gfc_get_extern_function_decl(gfc_symbol*)
../../gcc/fortran/trans-decl.c:1974
0x91bb24 conv_function_val
../../gcc/fortran/trans-expr.c:3722
0x91bb24 gfc_conv_procedure_call(gfc_se*, gfc_symbol*, gfc_actual_arglist*,
gfc_expr*, vec<tree_node*, va_gc, vl_embed>*)
../../gcc/fortran/trans-expr.c:6142
0x91c6fa gfc_conv_expr(gfc_se*, gfc_expr*)
../../gcc/fortran/trans-expr.c:7852
0x923a6a gfc_conv_expr_reference(gfc_se*, gfc_expr*)
../../gcc/fortran/trans-expr.c:7952
0x957611 gfc_trans_character_select
../../gcc/fortran/trans-stmt.c:2819
0x95ee1c gfc_trans_select(gfc_code*)
../../gcc/fortran/trans-stmt.c:3158
0x8e48b7 trans_code
../../gcc/fortran/trans.c:1940
0x90e7a8 gfc_generate_function_code(gfc_namespace*)
../../gcc/fortran/trans-decl.c:6437
0x89d036 translate_all_program_units
../../gcc/fortran/parse.c:6091
0x89d036 gfc_parse_file()
../../gcc/fortran/parse.c:6294
0x8e0eaf gfc_be_parse_file
../../gcc/fortran/f95-lang.c:204

[Bug fortran/83149] [8 Regression] ICE on SELECT CASE: crash_signal in toplev.c:325

2017-11-24 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83149

--- Comment #3 from Neil Carlson  ---
Unlike comment 0 code, comment 2 code also gives an ICE with 7.2.1 and 6.4.1

[Bug fortran/83118] Bad intrinsic assignment of class(*) array component of derived type (8.0 regression)

2017-11-22 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83118

--- Comment #1 from Neil Carlson  ---
Note that the incorrect string "b" is not actually 1 character long, but 3
characters: a "b" followed by 2 non-printing characters.  Vim shows them as ^@

[Bug fortran/83146] ICE on SELECT CASE statement with associate name

2017-11-24 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83146

--- Comment #2 from Neil Carlson  ---
Turns out you don't need anything at all in the associate block to get an ICE:

type foo
  integer n
end type
type bar
  type(foo) array(2)
end type
type(bar) b
associate (n_array => b%array%n)
end associate
end

[Bug fortran/49213] [OOP] gfortran rejects structure constructor expression

2017-11-24 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

--- Comment #25 from Neil Carlson  ---
Here's another example similar to those above but even simpler IMHO and
involving a CLASS(*) pointer component

type box
  class(*), pointer :: uptr => null()
end type
integer, target :: n
call sub(box(n))
contains
  subroutine sub(b)
type(box), intent(in) :: b
  end subroutine
end

call sub(box(n))
 1
Error: Can't convert INTEGER(4) to CLASS(*) at (1)

This should work in F2003. GFortran seems to be fundamentally broken when it
comes to derived types with polymorphic pointer components and intrinsic
structure constructors.

[Bug fortran/49213] [OOP] gfortran rejects structure constructor expression

2017-11-24 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

--- Comment #24 from Neil Carlson  ---
Ping.  This bug has been around for over 6 years now.

[Bug fortran/79072] ICE with class(*) pointer function result and character value

2017-11-22 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79072

--- Comment #19 from Neil Carlson  ---
This fixes the code of comment 12 for me.  All the other test cases continue to
work as expected.  This can be closed as "fixed" as far as I'm concerned.
Thanks Paul!

[Bug fortran/83118] New: Bad intrinsic assignment of class(*) array component of derived type (8.0 regression)

2017-11-22 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83118

Bug ID: 83118
   Summary: Bad intrinsic assignment of class(*) array component
of derived type (8.0 regression)
   Product: gcc
   Version: 8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

Intrinsic assignment of a derived type with allocatable CLASS(*) array
component is not being done correctly with version 8.0 when the dynamic type is
CHARACTER.

Version 6.4.1 gives the expected result:

orig=["foo","bar"]
copy=["foo","bar"]


But 8.0 (20171122) gives an incorrect result:

orig=["foo","bar"]
copy=["foo","b"]

Here's the code:

type :: any_vector
  class(*), allocatable :: v(:)
end type
type(any_vector) :: x, y
allocate(x%v,source=['foo','bar'])
select type (v => x%v)
type is (character(*))
  print '("orig=[""",a,''","'',a,''"]'')', v ! expect orig=["foo","bar"]
end select
y = x ! THIS ASSIGNMENT IS NOT BEING DONE CORRECTLY
select type (v => y%v)
type is (character(*))
  print '("copy=[""",a,''","'',a,''"]'')', v ! expect copy=["foo","bar"]
end select
end

[Bug fortran/79072] ICE with class(*) pointer function result and character value

2017-11-20 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79072

--- Comment #16 from neil.n.carlson at gmail dot com ---
I've confirmed Dominique's findings: Code in comments 0, 5, 11 are working now
with Paul's commit (Thanks!), but comment 12 code still gives an ICE.

Should I create a new PR for that example, or is it fine leaving this PR open?

[Bug fortran/79072] ICE with class(*) pointer function result and character value

2017-11-18 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79072

--- Comment #12 from neil.n.carlson at gmail dot com ---
The second adds a select case and print to get at the result value before its
handed back.  This produces an ICE with 6.4.1, 7.2.1, and 8.0.0 (20171028)

character(3), target :: a = 'foo'
class(*), pointer :: b
b => ptr()
select type (b)
type is (character(*))
  print '(3a)', 'b="', b, '" (expect "foo")'
end select
contains
  function ptr()
class(*), pointer :: ptr
ptr => a
select type (ptr)
type is (character(*))
end select
  end function
end

Here's the traceback on 7.2.1:

gfortran-bug-20170812b.f90:46:0:

 character(3), target :: a = 'foo'

internal compiler error: in gfc_advance_chain, at fortran/trans.c:58
0x65d137 gfc_advance_chain(tree_node*, int)
../../gcc/fortran/trans.c:58
0x685eba gfc_class_len_get(tree_node*)
../../gcc/fortran/trans-expr.c:226
0x6c6364 trans_associate_var
../../gcc/fortran/trans-stmt.c:1778
0x6c6364 gfc_trans_block_construct(gfc_code*)
../../gcc/fortran/trans-stmt.c:1831
0x65d6b7 trans_code
../../gcc/fortran/trans.c:1913
0x6c77d9 gfc_trans_select_type_cases
../../gcc/fortran/trans-stmt.c:2422
0x6c77d9 gfc_trans_select_type(gfc_code*)
../../gcc/fortran/trans-stmt.c:3133
0x65d747 trans_code
../../gcc/fortran/trans.c:1933
0x6c5e38 gfc_trans_block_construct(gfc_code*)
../../gcc/fortran/trans-stmt.c:1824
0x65d6b7 trans_code
../../gcc/fortran/trans.c:1913
0x682847 gfc_generate_function_code(gfc_namespace*)
../../gcc/fortran/trans-decl.c:6332
0x682634 gfc_generate_contained_functions
../../gcc/fortran/trans-decl.c:5327
0x682634 gfc_generate_function_code(gfc_namespace*)
../../gcc/fortran/trans-decl.c:6261
0x616eb6 translate_all_program_units
../../gcc/fortran/parse.c:6074
0x616eb6 gfc_parse_file()
../../gcc/fortran/parse.c:6274
0x65a02f gfc_be_parse_file
../../gcc/fortran/f95-lang.c:204

[Bug fortran/79072] ICE with class(*) pointer function result and character value

2017-11-18 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79072

--- Comment #13 from neil.n.carlson at gmail dot com ---
Correction to Comment 11.  That example gives the *correct* result on 6.4.1

[Bug fortran/79072] ICE with class(*) pointer function result and character value

2017-11-18 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79072

--- Comment #11 from neil.n.carlson at gmail dot com ---
Paul, I'm organizing all my bug report examples, and ran across these two test
cases from September that I can't find I ever reported.  They are VERY similar
to the original example I posted, except the ICE occurs in a different file, so
I thought I'd add them here.  I can submit a separate PR if you think it more
appropriate.

The first compiles on 6.4.1, 7.2.1, and 8.0.0 (20171028). But produces an
incorrect result:

b="" (expect "foo")

character(3), target :: a = 'foo'
class(*), pointer :: b
b => ptr()
select type (b)
type is (character(*))
  print '(3a)', 'b="', b, '" (expect "foo")'
end select
contains
  function ptr()
class(*), pointer :: ptr
ptr => a
  end function
end

[Bug fortran/82996] ICE and segfault with derived type finalization

2017-11-16 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82996

--- Comment #8 from neil.n.carlson at gmail dot com ---
> If I remove 'elemental' for 'subroutine foo_destroy', the segfault is gone.

In that case the final procedure doesn't match the array component and wouldn't
be called.  I suspect that is why the segfault is gone.

[Bug fortran/83012] New: Simply contiguous pointer function not recognized as contiguous

2017-11-15 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83012

Bug ID: 83012
   Summary: Simply contiguous pointer function not recognized as
contiguous
   Product: gcc
   Version: 8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

In the following example the pointer assignment "p => x%dataptr()" is rejected
because the compiler does not recognize the function result x%dataptr() as
contiguous when in fact it is simply contiguous by definition.  Note that there
is no error if the dummy variable x is declared as type(x) instead of class(x).

FWIW, the 6.4.1 compiler has no problems with this example.

module mod
  type :: foo
integer, pointer, contiguous :: p(:)
  contains
procedure :: dataptr
  end type
contains
  function dataptr(this) result(dp)
class(foo), intent(in) :: this
integer, pointer, contiguous :: dp(:)
dp => this%p
  end function
end module

subroutine bar(x)
  use mod
  class(foo) :: x
  integer, pointer, contiguous :: p(:)
  p => x%dataptr()
end subroutine

The error message:

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

$ gfortran -c bug.f90 
bug.f90:19:7:

   p => x%dataptr()
   1
Error: Assignment to contiguous pointer from non-contiguous target at (1)

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

2018-05-22 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83118

Neil Carlson  changed:

   What|Removed |Added

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

--- Comment #6 from Neil Carlson  ---
It doesn't fix the test case of comment 4 (which I only gave as a mod to the
comment 0 example).  Here it is explicitly:

type :: any_vector
  class(*), allocatable :: v(:)
end type
type(any_vector) :: x, y
x%v = ['foo','bar']
select type (v => x%v)
type is (character(*))
  print '("orig=[""",a,''","'',a,''"]'')', v ! expect orig=["foo","bar"]
end select
y = x ! THIS ASSIGNMENT IS NOT BEING DONE CORRECTLY
select type (v => y%v)
type is (character(*))
  print '("copy=[""",a,''","'',a,''"]'')', v ! expect copy=["foo","bar"]
end select
end

$ gfortran --version
GNU Fortran (GCC) 8.1.1 20180521

$ gfortran gfortran-20171122b.f90 
$ ./a.out

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

Backtrace for this error:
#0  0x7f249667794f in ???
#1  0x0 in ???
Segmentation fault (core dumped)

[Bug fortran/49213] [OOP] gfortran rejects structure constructor expression

2018-05-22 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

Neil Carlson  changed:

   What|Removed |Added

Version|8.0.1   |8.1.1

--- Comment #27 from Neil Carlson  ---
Still present in 8.1.1 (nearly the 7th anniversary of the initial report!)

[Bug fortran/86100] New: Spurious error with -fcheck=bounds and allocatable class(*) array components

2018-06-10 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=86100

Bug ID: 86100
   Summary: Spurious error with -fcheck=bounds and allocatable
class(*) array components
   Product: gcc
   Version: 8.1.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

When compiled with -fcheck=bounds, the following example gives a spurious
runtime bound mismatch error on the 'b=a' assignment statement:

type any_matrix
  class(*), allocatable :: m(:,:)
end type
type(any_matrix) :: a, b
allocate(a%m, source=reshape([3,5],shape=[1,2]))
b = a ! SPURIOUS RUNTIME ERROR with -fcheck=bounds
end

At line 6 of file gfortran-20180610.f90
Fortran runtime error: Array bound mismatch for dimension 1 of array
'<>' (2/1)

Without the -fcheck=bounds option the assignment executes correctly (checked
via adding code to examine b%m).

There are no problems if the array component is rank-1, or if it is declared
integer instead of class(*). So this issue seems confined to allocatable
class(*) components of rank 2 (or greater?)

[Bug fortran/83149] [8 Regression] ICE on SELECT CASE: crash_signal in toplev.c:325

2017-12-26 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83149

--- Comment #5 from Neil Carlson  ---
I disagree (in part) with comment 4.  Ncells is a valid specification statement
(see 7.1.11, par 2 (4), Fortran 2008).  Its value need not be known at compile
time; only when the get() function is executed.  If the code successfully
compiled then, yes, at run time it is not conforming because ncells was never
assigned a value.

Interestingly if the main program is modified to use mod1 (but still not define
ncells) then the ICE goes away.

use mod1
use mod2
s = sum(get())
end

So perhaps there is something here about mod1 going out of scope.  I forget how
that works, and seem to recall that some new standard was going to drop that
feature of the language.

However that aspect can be side stepped by just turning the main program into a
subprogram

subroutine sub
use mod2
s = sum(get())
end

This still gives an ICE and I believe is valid.  Both NAG and Intel compile
without error, fwtw.

[Bug fortran/84143] New: Intrinsic output of PDT incorrectly includes type parameters

2018-01-30 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84143

Bug ID: 84143
   Summary: Intrinsic output of PDT incorrectly includes type
parameters
   Product: gcc
   Version: 8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

In the continuing theme of the PDT implementation incorrectly regarding type
parameters as components (see PR84119, PR84120, PR84122), the current
implementation includes the type parameters when outputting a PDT:

type foo(k1,l1)
  integer,kind :: k1=1
  integer,len  :: l1=2
  integer :: n=3
end type

type(foo) :: x
character(8) :: string

write(string,'(*(i0))') x ! THIS SHOULD WRITE THE SINGLE DIGIT 3
if (len_trim(string) /= 1) stop 1
end

GFortran is bailing at the STOP 1 because it gets 3 for len_trim(string).
1.3.33 and R435 (F08) define what a component is. Type parameters R431 are
something else, and not included in the intrinsic output of the derived type.

I didn't check, but I'd guess the analogous incorrect thing occurs for input.

[Bug fortran/84120] Syntax for used for PDT constructors is incorrect

2018-01-30 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84120

--- Comment #1 from Neil Carlson  ---
This explains the problem underlying PR82205

[Bug fortran/84189] New: Internal procedure allowed as type bound procedure

2018-02-02 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84189

Bug ID: 84189
   Summary: Internal procedure allowed as type bound procedure
   Product: gcc
   Version: 8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

C465 (F08) prohibits an internal procedure from being a type bound procedure,
but gfortran mistakenly allows it when the TPB has the NOPASS attribute.

The following invalid example should fail to compile, but gfortran compiles it
without error.

module foobar
type :: foo
contains
  procedure, nopass :: bar
end type
contains
  subroutine bar
  end subroutine
end module

Note that the func_result_6.f90 testsuite problem, and perhaps others, use this
type of invalid code.

[Bug fortran/84189] Internal procedure allowed as type bound procedure

2018-02-02 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84189

Neil Carlson  changed:

   What|Removed |Added

 Status|UNCONFIRMED |RESOLVED
 Resolution|--- |INVALID

--- Comment #1 from Neil Carlson  ---
Sorry, this is completely bogus -- lack of sleep is my only excuse.

[Bug fortran/84093] New: Invalid nested derived type constructor not rejected

2018-01-28 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84093

Bug ID: 84093
   Summary: Invalid nested derived type constructor not rejected
   Product: gcc
   Version: 8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

Gfortran allows invalid nested derived type constructors. Consider this
example:

type parent
  integer :: a, b
end type

type, extends(parent) :: child
  real :: x
end type

type(child) :: foo
foo = child(parent(1,2),3.0)

end

Note 4.59 and the preceding paragraphs (in F08 or F15 standard) are clear
that in this example parent(1,2) corresponds to the first component of
child, which is a, and gfortran should reject this illegal code.

The correct constructor must use keywords if one wants to use the parent
constructor:

foo = child(parent=parent(1,2), x=3.0)

Note that the extends_2.f03 testsuite program contains this error.

[Bug fortran/84143] Intrinsic output of PDT incorrectly includes type parameters

2018-01-31 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84143

--- Comment #2 from Neil Carlson  ---
(In reply to Dominique d'Humieres from comment #1)
> 
> gives 0. Should not it be 3?

Yeah. I noticed the same thing myself.  It is 3 if the type parameters are
removed.  I was intending to report it, but I thought I might have seen a
similar PR linked from the PDT meta bug and was going to look again before
doing so.

[Bug fortran/84093] Invalid nested derived type constructor not rejected

2018-01-29 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84093

--- Comment #2 from Neil Carlson  ---
The forced cascade of keyword use is rather annoying, so perhaps someone was
thinking the current gfortran behavior is a useful extension, and it almost is.
But consider this example:

type :: parent
  type(parent), pointer :: next => null()
end type

type, extends(parent) :: child
  integer :: n
end type

type(child) :: c
type(parent), pointer :: p

allocate(p)
allocate(p%next)

c = child(parent=p,n=1)
if (.not.associated(c%next,p%next)) stop 1

c = child(p,1)
if (.not.associated(c%next,p)) stop 2

end

GFortran doesn't distinguish between the two constructor expressions, treating
the second the same as the first, when in fact they are quite different.

[Bug fortran/84122] New: Incorrect statement sequence in PDT definition

2018-01-30 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84122

Bug ID: 84122
   Summary: Incorrect statement sequence in PDT definition
   Product: gcc
   Version: 8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

Here's yet another case of where the PDT implementation has not correctly
distinguished derived type parameters from the components of the type.
(c.f. PR84119 and PR84120)

R425 (F08) defines the sequence of statements in a derived type. First come
type parameter definitions, then optionally the PRIVATE statement, followed by
the definition of the type components.

So this is valid code

module mod
type foo(dim)
  integer,len :: dim
  private
  integer :: array(dim)
end type
end module

But gfortran rejects it with this error:

   private
 1
Error: PRIVATE statement at (1) must precede structure components

as it incorrectly considers the type parameters structure components.

[Bug fortran/84119] New: Type parameter inquiry for PDT returns array instead of scalar

2018-01-29 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84119

Bug ID: 84119
   Summary: Type parameter inquiry for PDT returns array instead
of scalar
   Product: gcc
   Version: 8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

There seems to be a misconception in the implementation of PDT that the type
parameters are (in part) just regular components of the type, so that for

type foo(a)
  integer, len :: a
end type
type(foo(a)) :: array(9)

the type inquiry array%a should give a rank-1 array of size 9. This is
incorrect. Type parameters are not components of the type. The F08 standard
clearly distinguishes between type parameter definition statements and
component definition statements. See R425, R431, R435, and in particular see
Note 6.7 which says "It [array%a, for example] is scalar even if designator is
an array."

Here's a test case that should pass.  GFortran will bail on both stop lines.

type :: vector(dim,kind)
  integer, len :: dim
  integer, kind :: kind
end type
type(vector(3,1)) :: a(10)
if (size(shape(a%dim)) /= 0) stop 1
if (size(shape(a%kind)) /= 0) stop 2
end

[Bug fortran/84120] New: Syntax for used for PDT constructors is incorrect

2018-01-29 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84120

Bug ID: 84120
   Summary: Syntax for used for PDT constructors is incorrect
   Product: gcc
   Version: 8.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

Consider the PDT

type foo(dim)
  integer,len :: dim
  integer :: array(dim)
end type

While investigating how other compilers do on the gfortran testsuite programs,
I discovered that gfortran would use the following syntax for a constructor for
the PDT:

type(foo(2)) :: x
x = foo(2,[1,2])

This is absolutely wrong.  The correct constructor syntax is

x = foo(2)([1,2])

The PDT implementation appears to have the misconception that type parameters
are (in part) regular components, but that is not so, they are two separate
things. See PR84119 for some related references to the standard.  In particular
here, see R455 for the constructor syntax (F08 standard), and R453 for the
derived-type-spec (e.g. "foo(2)"). Note that 1.3.33 defines what a "component"
is, and it does not include type parameters.

To summarize, gfortran works with this invalid example (Intel and NAG properly
reject it)

type foo(dim)
  integer,len :: dim
  integer :: array(dim)
end type
type(foo(:)), allocatable :: x
x = foo(2,[1,2])
if (size(x%array) /= 2) stop 1
if (any(x%array /= [1,2])) stop 2
end

But gfortran rejects this corrected valid example (works with Intel and NAG):

type foo(dim)
  integer,len :: dim
  integer :: array(dim)
end type
type(foo(:)), allocatable :: x
x = foo(2)([1,2])
if (size(x%array) /= 2) stop 1
if (any(x%array /= [1,2])) stop 2
end

 x = foo(2)([1,2])
 1
Error: Invalid character in name at (1)

[Bug fortran/84218] ICE in free_expr0, at fortran/expr.c:451

2018-02-07 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84218

Neil Carlson  changed:

   What|Removed |Added

 CC||neil.n.carlson at gmail dot com

--- Comment #2 from Neil Carlson  ---
Note that the DATA statement

   data (x(j:i), i=1,2,2) /'a'/

is not valid Fortran.  Implied do objects, here x(j:i), are restricted by R538
(F08) to array elements, scalar structure component, or an implied-do.  x(j:i)
is an array section not an array element.  But this may be a language extension
that gfortran supports.

[Bug fortran/84122] Incorrect statement sequence in PDT definition

2018-02-03 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84122

--- Comment #3 from Neil Carlson  ---
Here's a related invalid example that gfortran accepts:

module mod
type foo(dim)
  integer,len,public :: dim
  integer :: array(dim)
end type
end module

PUBLIC/PRIVATE attributes are not valid attributes for a type parameter
definition statement; see R431 and R433 (F08).

Gfortran does reject PRIVATE. but the error message
Error: PRIVATE attribute conflicts with LEN attribute at (1)
together with it allowing PUBLIC seems to betray that the PDT implementation
views type parameters as type components. The issue is not so much that PRIVATE
conflicts with LEN, as that type parameters do not have an accessibility
attribute.

[Bug testsuite/84381] replace non-std 'call abort' by 'stop 1' in gfortran testsuite

2018-02-14 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84381

Neil Carlson  changed:

   What|Removed |Added

 CC||neil.n.carlson at gmail dot com

--- Comment #1 from Neil Carlson  ---
If the replacement could still be done mechanically (beyond my sed scripting
skills), it would be useful to replace occurrences of ABORT with a sequence of
stop statements; i.e., "stop 1", "stop 2", etc. Then a failure would point to a
specific location, and not one of several possible locations.

[Bug fortran/82996] ICE and segfault with derived type finalization

2018-02-17 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82996

--- Comment #9 from Neil Carlson  ---
With today's version (r257782) I'm still seeing the same thing Dominique
reported in comment 7, except that there is no longer any abort -- the programs
terminate successfully (0 exit code) despite the reported runtime error.  I'm
not sure what to make of that.

Example error:

 $ ./a.out
gfortran-20171114a.f90:48: runtime error: member access within misaligned
address 0x0060ab25 for type 'struct foo', which requires 8 byte alignment
0x0060ab25: note: pointer points here
 00 00 00 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00 00 00 00 00  00 00
00 00 00 00 00 00  00
 ^

[Bug fortran/84432] [F08] Detect illegal component initialization in pdt_27.f03

2018-02-18 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84432

Neil Carlson  changed:

   What|Removed |Added

 CC||neil.n.carlson at gmail dot com

--- Comment #2 from Neil Carlson  ---
One of the corrigenda to F2003 (https://wg5-fortran.org/N1801-N1850/N1823.pdf)
added C447a:

"If component-initialization appears, every type parameter and array
bound of the component shall be an initialization expression."

Corresponds to F08:C458, except "initialization" replaces "colon or constant".
Not sure if there is anything significant between the two (probably is).

[Bug fortran/84543] New: undefined reference to __copy_INTEGER_4_.3788

2018-02-24 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84543

Bug ID: 84543
   Summary: undefined reference to __copy_INTEGER_4_.3788
   Product: gcc
   Version: 8.0.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

I stumbled across this problem while reducing an actual error to a minimal test
case (PR84539).  I wasn't going to bother reporting it (it seems a bit too
silly) but reconsidered. Maybe this means something significant to a developer;
I'll let you decide.

$ cat bug.f90
class(*), allocatable :: x
x = 42
end

$ gfortran bug.f90
/tmp/cclHGRhz.o:(.rodata+0x60): undefined reference to `__copy_INTEGER_4_.3788'
collect2: error: ld returned 1 exit status

And similar with a real or character value, and presumably with any of the
kinds that gfortran supports. The link error goes away if you add a TYPE IS
clause for the type of the value; e.g.

class(*), allocatable :: x
x = 42
select type (x)
type is (integer)
end select
end

[Bug fortran/84432] [F08] Detect illegal component initialization in pdt_27.f03

2018-02-24 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84432

--- Comment #5 from Neil Carlson  ---
No, both of those are valid. The constraint is on component initialization, and
type parameters are *not* components.  So something like this would be invalid
by F08:C458

   type t(a)
  integer, len :: a
  character(len=a) :: c = 'foo'
   end type

[Bug fortran/84432] [F08] Detect illegal component initialization in pdt_27.f03

2018-02-24 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84432

--- Comment #6 from Neil Carlson  ---
... and this would also be invalid

   type t(a)
  integer, len :: a = 3
  character(len=a) :: c = 'foo'
   end type

[Bug fortran/49213] [OOP] gfortran rejects structure constructor expression

2018-02-23 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

Neil Carlson  changed:

   What|Removed |Added

Version|4.7.0   |8.0.1

--- Comment #26 from Neil Carlson  ---
Still present in 8.0

[Bug fortran/69563] Generic TBP incorrectly resolves to elemental

2018-02-23 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=69563

Neil Carlson  changed:

   What|Removed |Added

Version|6.0 |8.0.1

--- Comment #2 from Neil Carlson  ---
And still present in 8.0.

[Bug fortran/84539] ICE and segfault with assignment to CLASS(*) array

2018-02-23 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84539

--- Comment #1 from Neil Carlson  ---
And same example but using character data. This compiles but gives a segfault
when run at the assignment statement.

class(*), allocatable :: x(:)
x = ['foo','bar']
select type (x)
type is (character(*))
  if (any(x /= ['foo','bar'])) stop 1
end select
end


$ gfortran -g gfortran-20180223b.f90 
$ ./a.out

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

Backtrace for this error:
#0  0x7f40a5b0894f in ???
#1  0x400853 in MAIN__
at gfortran-20180223b.f90:2
#2  0x4009fd in main
at gfortran-20180223b.f90:7
Segmentation fault (core dumped)

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

2018-02-23 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83118

--- Comment #4 from Neil Carlson  ---
Note that if the sourced allocation in the comment 0 test case

  allocate(x%v,source=['foo','bar'])

is replaced by the equivalent (I think) assignment

  x%v = ['foo','bar']

Then the code produces a run time segfault instead:

$ gfortran --version
GNU Fortran (GCC) 8.0.1 20180224 (experimental)

$ gfortran -g -fbacktrace bug.f90
$ ./a.out

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

Backtrace for this error:
#0  0x7f3c46fda94f in ???
#1  0x0 in ???
Segmentation fault (core dumped)

I think the problems here may be related to the simpler test cases in PR84539
which I just reported.

[Bug fortran/84539] New: ICE and segfault with assignment to CLASS(*) array

2018-02-23 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84539

Bug ID: 84539
   Summary: ICE and segfault with assignment to CLASS(*) array
   Product: gcc
   Version: 8.0.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

Here are some issues with array assignment to an allocatable CLASS(*) array
using the current 8.0 trunk.

class(*), allocatable :: x(:)
x = [4,2]
select type (x)
type is (integer)
  if (any(x /= [4,2])) stop 1
end select
end

$ gfortran -g -fbacktrace gfortran-20180223a.f90 
gfortran-20180223a.f90:1:0:

 class(*), allocatable :: x(:)

Error: conversion of register to a different size
VIEW_CONVERT_EXPR(_1);

_12 = VIEW_CONVERT_EXPR(_1);
gfortran-20180223a.f90:1:0: internal compiler error: verify_gimple failed
0xd2b9bd verify_gimple_in_seq(gimple*)
../../gcc/tree-cfg.c:5247
0xaa7495 gimplify_body(tree_node*, bool)
../../gcc/gimplify.c:12710
0xaa7684 gimplify_function_tree(tree_node*)
../../gcc/gimplify.c:12800
0x925d17 cgraph_node::analyze()
../../gcc/cgraphunit.c:670
0x9286b3 analyze_functions
../../gcc/cgraphunit.c:1131
0x9294a2 symbol_table::finalize_compilation_unit()
../../gcc/cgraphunit.c:2691
Please submit a full bug report,

[Bug fortran/84546] New: [7/8 Regression] Bad sourced allocation of CLASS(*) with source with CLASS(*) component

2018-02-24 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84546

Bug ID: 84546
   Summary: [7/8 Regression] Bad sourced allocation of CLASS(*)
with source with CLASS(*) component
   Product: gcc
   Version: 8.0.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

The following example produces the expected result with 6.4.1, but not with the
latest 7 and 8 trunk.  The correct output is "foobar", but 7/8 produce "foob"

module any_vector_type

  type :: any_vector
class(*), allocatable :: vec(:)
  end type

  interface any_vector
procedure any_vector1
  end interface

contains

  function any_vector1(vec) result(this)
class(*), intent(in) :: vec(:)
type(any_vector) :: this
allocate(this%vec, source=vec)
  end function

end module

program main

  use any_vector_type
  implicit none

  class(*), allocatable :: x
  character(*), parameter :: vec(*) = ['foo','bar']

  allocate(x, source=any_vector(vec))

  select type (x)
  type is (any_vector)
select type (xvec => x%vec)
type is (character(*))
  print *, xvec ! EXPECT "foobar"
  if (any(xvec /= vec)) stop 1
end select
  end select

end program

[Bug fortran/84381] replace non-std 'call abort' by 'stop 1' in gfortran testsuite

2018-02-16 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84381

--- Comment #5 from Neil Carlson  ---
Thomas, I saw you generated a patch with "stop n".  I'd love to see how you did
it -- the regexp and counting magic.

[Bug fortran/79072] ICE with class(*) pointer function result and character value

2018-02-21 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79072

--- Comment #22 from Neil Carlson  ---
I just verified with 8.0 trunk (r257868) that all three of my examples continue
to work as expected.

[Bug fortran/83149] [8 Regression] ICE on SELECT CASE: crash_signal in toplev.c:325

2017-12-26 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=83149

--- Comment #7 from Neil Carlson  ---
Perhaps this modification of comment 2 code is clearer.

Put this in one file:

module mod1
  integer :: ncells
end module

module mod2
contains
  function get() result(array)
use mod1
real array(ncells)
array = 1.0
  end function
end module

And this in another (this is different):

subroutine sub
use mod2
s = sum(get())
end

This gives an ICE when compiled with 8.0.0 (20171222).

NCELLS is a valid specification expression.

A valid full program that calls SUB would have to define NCELLS before doing
so. However it is not required that the compiler know the value of NCELLS at
compile time.

[Bug fortran/84539] ICE and segfault with assignment to CLASS(*) array

2018-08-16 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84539

--- Comment #4 from Neil Carlson  ---
Update with 8.2.0

The ICE is gone, but a run time segfault remains:

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

Backtrace for this error:
#0  0x7f82986c06df in ???
#1  0x400754 in MAIN__
at gfortran-20180223a.f90:2
#2  0x400979 in main
at gfortran-20180223a.f90:7
Segmentation fault (core dumped)

[Bug fortran/84546] [7/8 Regression] Bad sourced allocation of CLASS(*) with source with CLASS(*) component

2018-03-11 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84546

--- Comment #6 from Neil Carlson  ---
Thank you, thank you Paul!

This also fixes my test case for PR83118 which I think must have been due to
the same underlying problem

[Bug fortran/84381] replace non-std 'call abort' by 'stop 1' in gfortran testsuite

2018-03-02 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84381

--- Comment #12 from Neil Carlson  ---
Argh... here's the *correct* patch

diff --git a/literal_character_constant_1.inc
b/literal_character_constant_1.inc
index ba24966..40375cd 100644
--- a/literal_character_constant_1.inc
+++ b/literal_character_constant_1.inc
@@ -9,12 +9,12 @@ c A tab is between 8 and 9.
   write(fil,'(a)') c
 #ifdef LL_NONE
   if(fil.ne. "12345678 9")
- &  call abort
+ &  stop 1
 #else
   if(fil.ne.
  &"1234567  8  9"
  &)
- &  call abort
+ &  stop 2
 #endif
   end

[Bug fortran/84381] replace non-std 'call abort' by 'stop 1' in gfortran testsuite

2018-03-02 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84381

--- Comment #13 from Neil Carlson  ---
And one more missed file due to a line split between the "call" and "abort". 
Here's the patch:

diff --git a/overload_1.f90 b/overload_1.f90
index afd4f81..66fbea4 100644
--- a/overload_1.f90
+++ b/overload_1.f90
@@ -162,8 +162,7 @@ contains
 r2 = (/ a.eq.b, a.ne.b, a.lt.b, a.le.b, a.gt.b, a.ge.b /)
 if (any (r1.neqv.r2)) STOP 1
 if (any (r1.neqv. &
- (/ .false.,.true.,.true., .true., .false.,.false. /) )) call&
- & abort
+ (/ .false.,.true.,.true., .true., .false.,.false. /) )) STOP 3
   end subroutine checkt

   subroutine checku
@@ -177,7 +176,6 @@ contains
 r2 = (/ a.eq.b, a.ne.b, a.lt.b, a.le.b, a.gt.b, a.ge.b /)
 if (any (r1.neqv.r2)) STOP 2
 if (any (r1.neqv. &
- (/ .false.,.true.,.true., .true., .false.,.false. /) )) call&
- & abort
+ (/ .false.,.true.,.true., .true., .false.,.false. /) )) STOP 4
   end subroutine checku
 end program main

[Bug fortran/84381] replace non-std 'call abort' by 'stop 1' in gfortran testsuite

2018-03-02 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=84381

--- Comment #11 from Neil Carlson  ---
One more missed file, an include file included by
literal_character_constant_1_x.F.  Here's the patch:

diff --git a/literal_character_constant_1.inc
b/literal_character_constant_1.inc
index ba24966..8beea79 100644
--- a/literal_character_constant_1.inc
+++ b/literal_character_constant_1.inc
@@ -9,12 +9,12 @@ c A tab is between 8 and 9.
   write(fil,'(a)') c
 #ifdef LL_NONE
   if(fil.ne. "12345678 9")
- &  call abort
+ &  call stop 1
 #else
   if(fil.ne.
  &"1234567  8  9"
  &)
- &  call abort
+ &  call stop 2
 #endif
   end

[Bug fortran/88043] Runtime Error when calling deferred member function

2018-11-15 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88043

--- Comment #1 from Neil Carlson  ---
I've been poking at Zach's example and trimmed it down a bit:

In one file:

module typeA

  implicit none
  private

  type, abstract, public :: A
  contains
procedure :: call_sub
procedure(z), deferred :: sub
  end type

  abstract interface
subroutine z(this)
  import A
  class(A) :: this
end subroutine
  end interface

contains

  subroutine call_sub(this)
class(A) :: this
print *, 'CALL_SUB'
call this%sub
  end subroutine

end module

module typeB

  use typeA
  implicit none
  private

  type, extends(A), public :: B
  contains
procedure, non_overridable :: sub
procedure :: foo
  end type

contains

  subroutine sub(this)
class(B) :: this
print *, 'IN SUB'
  end subroutine

  subroutine foo(this)
class(B) :: this
print *, 'IN FOO!'
  end subroutine

end module

And in a separate file:

use typeB
type, extends(B) :: C
end type
type(C) :: x
call x%call_sub
end

The expected output is

  CALL SUB
  IN SUB

But instead we get

  CALL SUB
  IN FOO!

Remove the PRIVATE statement from typeA module and we get CALL_SUB calling
itself instead of SUB!

[Bug fortran/82996] ICE and segfault with derived type finalization

2018-09-28 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=82996

--- Comment #10 from Neil Carlson  ---
A reader on c.l.f suggested this workaround for the bug. I'm sharing it here
because I think it may help to isolate where the problem is.  The suggestion
was to make the B array component allocatable and allocate it inside SUB. This
allows more control over when its finalizer is called. Here's a modified
version the runs without error (with -fsanitize=address,undefined) and valgrind
shows nothing amiss. (I'm using the 9.0 trunk)

module mod

  type foo
integer, pointer :: f(:) => null()
  contains
final :: foo_destroy
  end type

  type bar
type(foo), allocatable :: b(:)
  end type

contains

  elemental subroutine foo_destroy(this)
type(foo), intent(inout) :: this
if (associated(this%f)) deallocate(this%f)
  end subroutine

end module

program main

  use mod
  type(bar) :: x
  call sub(x) ! x%b not allocated
  call sub(x) ! x%b is allocated

contains

  subroutine sub(x)
type(bar), intent(out) :: x
allocate(x%b(2))
  end subroutine

end program

The interesting thing is that the finalizer works just fine when the %B
component is allocatable and allocated (the second call to SUB), but not when
it is not allocatable.

[Bug fortran/88169] New: Rejects USE rename of namelist group

2018-11-23 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88169

Bug ID: 88169
   Summary: Rejects USE rename of namelist group
   Product: gcc
   Version: 8.2.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: neil.n.carlson at gmail dot com
  Target Milestone: ---

The current 8.2.1 compiler rejects this example,

  module foo_nml
real :: x
namelist /foo/ x
  end module

  program main
use foo_nml, only: bar => foo
x = 42
write(*,nml=bar)
  end program

with this error,

f951: Error: Namelist foo cannot be renamed by USE association to bar

I believe this is valid code. Section 11.2.2 par 2 (F2008) explicitly includes
namelist groups in the list of entities that may be accessed via use
association, and there is no subsequent restriction on a namelist group
appearing in a rename that I could find. FWIW, both the Intel and NAG compilers
accept this code as valid.

[Bug fortran/88169] Rejects USE rename of namelist group

2018-11-23 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88169

--- Comment #4 from Neil Carlson  ---
I think the intent of

C8102 (R868) The namelist-group-name shall not be a name accessed by use
association.

is to say you can't define a namelist with a name accessed by use association.
That seems to fit best with the Note that references it.

However, I suppose it could be taken to mean that a namelist-group cannot be
accessed via use association. But that flies in the face of 14.2.2

  The USE statement provides the means by which a scoping unit accesses named
  data objects, derived types, procedures, abstract interfaces, generic
  identifiers, and namelist groups in a module.

which clearly indicates namelist groups can be accessed by use association.

[Bug fortran/88169] Rejects USE rename of namelist group

2018-11-23 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88169

--- Comment #5 from Neil Carlson  ---
Stated a bit more clearly, the question is, whether in

  The namelist-group-name shall not be a name accessed by use association.

the name (in the scope of the declaration) is accessed by use association,
or the name is accessed in another scope by use association.

[Bug fortran/88169] Rejects USE rename of namelist group

2018-11-24 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88169

--- Comment #9 from Neil Carlson  ---
Actually I think the usage in comment 8 is an intentional extension. There is a
test in the dg test suite that does exactly this if I remember correctly. The
test was namelist_use.f90. I was told that gfortran will give an error if
compiled with something like -std=f95. See
https://github.com/nncarlson/gfortran.dg/issues/3

[Bug fortran/88169] Rejects USE rename of namelist group

2018-11-24 Thread neil.n.carlson at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88169

--- Comment #10 from Neil Carlson  ---
Also a remark about the output of comment 7 just in case someone is thinking it
ought to say "" (like I was expecting/hoping when I started experimenting
with the original example).  13.11.3.1 says

  1 Input for a namelist input statement consists of
(2) the character & followed immediately by the namelist-group-name as
specified in the NAMELIST statement,

and 13.11.4.1 says

  1 The form of the output produced by intrinsic namelist output shall be
suitable for input, [...]

So "" is correct (and what Intel and NAG both do as well).

  1   2   >