[Bug fortran/63205] [OOP] Wrongly rejects type = class (for identical declared type)

2016-11-16 Thread janus at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63205

janus at gcc dot gnu.org changed:

   What|Removed |Added

   Target Milestone|--- |5.0

[Bug fortran/63205] [OOP] Wrongly rejects type = class (for identical declared type)

2015-10-10 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63205
Bug 63205 depends on bug 57530, which changed state.

Bug 57530 Summary: [OOP] Wrongly rejects  type_pointer => class_target (which 
have identical declared type)
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=57530

   What|Removed |Added

 Status|WAITING |RESOLVED
 Resolution|--- |FIXED


[Bug fortran/63205] [OOP] Wrongly rejects type = class (for identical declared type)

2015-09-29 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63205

Dominique d'Humieres  changed:

   What|Removed |Added

 Status|REOPENED|RESOLVED
 Resolution|--- |FIXED

--- Comment #15 from Dominique d'Humieres  ---
No feedback for almost six months. Closing as FIXED. Please open new PR(s) for
remaining issue(s).


[Bug fortran/63205] [OOP] Wrongly rejects type = class (for identical declared type)

2015-04-03 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63205

--- Comment #14 from Dominique d'Humieres dominiq at lps dot ens.fr ---
 Reopening, something is wrong with the testcase:(In reply to Paul Thomas
 from comment #11)
  Fixed on trunk, aka 5.0.0

 The added testcase fails with valgrind due to memory errors, please see 
 PR64986.

Since the reported issues have been fixed and the valgrind errors are tracked
by PR64986, I don't see the point to reopen this PR.


[Bug fortran/63205] [OOP] Wrongly rejects type = class (for identical declared type)

2015-02-09 Thread ubizjak at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63205

--- Comment #12 from Uroš Bizjak ubizjak at gmail dot com ---
Reopening, something is wrong with the testcase:(In reply to Paul Thomas from
comment #11)
 Fixed on trunk, aka 5.0.0

The added testcase fails with valgrind due to memory errors, please see
PR64986.

[Bug fortran/63205] [OOP] Wrongly rejects type = class (for identical declared type)

2015-02-09 Thread ubizjak at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63205

Uroš Bizjak ubizjak at gmail dot com changed:

   What|Removed |Added

 Status|RESOLVED|REOPENED
 Resolution|FIXED   |---

--- Comment #13 from Uroš Bizjak ubizjak at gmail dot com ---
(In reply to Paul Thomas from comment #11)

Reopening.

[Bug fortran/63205] [OOP] Wrongly rejects type = class (for identical declared type)

2015-02-06 Thread pault at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63205

--- Comment #10 from Paul Thomas pault at gcc dot gnu.org ---
Author: pault
Date: Fri Feb  6 18:15:01 2015
New Revision: 220482

URL: https://gcc.gnu.org/viewcvs?rev=220482root=gccview=rev
Log:
2015-02-06  Paul Thomas  pa...@gcc.gnu.org

PR fortran/63205
* gfortran.h: Add 'must finalize' field to gfc_expr and
prototypes for gfc_is_alloc_class_scalar_function and for
gfc_is_alloc_class_array_function.
* expr.c (gfc_is_alloc_class_scalar_function,
gfc_is_alloc_class_array_function): New functions.
* trans-array.c (gfc_add_loop_ss_code): Do not move the
expression for allocatable class scalar functions outside the
loop.
(conv_array_index_offset): Cope with deltas being NULL_TREE.
(build_class_array_ref): Do not return with allocatable class
array functions. Add code to pick out the returned class array.
Dereference if necessary and return if not a class object.
(gfc_conv_scalarized_array_ref): Cope with offsets being NULL.
(gfc_walk_function_expr): Return an array ss for the result of
an allocatable class array function.
* trans-expr.c (gfc_conv_subref_array_arg): Remove the assert
that the argument should be a variable. If an allocatable class
array function, set the offset to zero and skip the write-out
loop in this case.
(gfc_conv_procedure_call): Add allocatable class array function
to the assert. Call gfc_conv_subref_array_arg for allocatable
class array function arguments with derived type formal arg..
Add the code for handling allocatable class functions, including
finalization calls to prevent memory leaks.
(arrayfunc_assign_needs_temporary): Return if an allocatable
class array function.
(gfc_trans_assignment_1): Set must_finalize to rhs expression
for allocatable class functions. Set scalar_to_array as needed
for scalar class allocatable functions assigned to an array.
Nullify the allocatable components corresponding the the lhs
derived type so that the finalization does not free them.

2015-02-06  Paul Thomas  pa...@gcc.gnu.org

PR fortran/63205
* gfortran.dg/class_to_type_4.f90: New test

Added:
trunk/gcc/testsuite/gfortran.dg/class_to_type_4.f90
Modified:
trunk/gcc/fortran/ChangeLog
trunk/gcc/fortran/expr.c
trunk/gcc/fortran/gfortran.h
trunk/gcc/fortran/trans-array.c
trunk/gcc/fortran/trans-expr.c
trunk/gcc/testsuite/ChangeLog


[Bug fortran/63205] [OOP] Wrongly rejects type = class (for identical declared type)

2015-02-06 Thread pault at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63205

Paul Thomas pault at gcc dot gnu.org changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #11 from Paul Thomas pault at gcc dot gnu.org ---
Fixed on trunk, aka 5.0.0

Thanks for the report

Paul


[Bug fortran/63205] [OOP] Wrongly rejects type = class (for identical declared type)

2014-12-25 Thread pault at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63205

--- Comment #9 from Paul Thomas pault at gcc dot gnu.org ---
Created attachment 34331
  -- https://gcc.gnu.org/bugzilla/attachment.cgi?id=34331action=edit
A yet more nearly final patch

This patch still has some memory leakage issues... I think.

There are also some peculiarities that need sorting out; most notably the chunk
added to build_class_array_ref does not work more generally as I thought that
it should. I would prefer to understand why and to implement it because it is
so much cleaner than messing with the gfc_expr's.

Anyway, it is getting there and I expect to complete it when I get home in the
New Year. Back to presents and turkey!

Happy holidays

Paul


[Bug fortran/63205] [OOP] Wrongly rejects type = class (for identical declared type)

2014-12-22 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63205

--- Comment #8 from Dominique d'Humieres dominiq at lps dot ens.fr ---
 For the record, I have a patch in my working tree such that
 gfortran.dg/widechar_intrinsics_10.f90 is miscomputed with -m32
 (I did not yet investigate the problem: too many patches in my working tree).

These failures have now disappeared.


[Bug fortran/63205] [OOP] Wrongly rejects type = class (for identical declared type)

2014-12-10 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63205

--- Comment #7 from Dominique d'Humieres dominiq at lps dot ens.fr ---
 Created attachment 34234 [details]
 A near final patch

First, the patch does not apply cleanly on trunk:

File to patch: gcc/fortran/trans-expr.c
patching file gcc/fortran/trans-expr.c
Hunk #1 succeeded at 3783 (offset 5 lines).
Hunk #2 succeeded at 3842 (offset 5 lines).
Hunk #3 succeeded at 3891 (offset 5 lines).
Hunk #4 succeeded at 3920 (offset 5 lines).
Hunk #5 succeeded at 3978 (offset 5 lines).
Hunk #6 succeeded at 4120 (offset 5 lines).
Hunk #7 succeeded at 4714 (offset 5 lines).
Hunk #8 FAILED at 5456.
Hunk #9 succeeded at 7391 (offset 5 lines).
Hunk #10 succeeded at 8267 (offset 5 lines).
Hunk #11 succeeded at 8341 (offset 5 lines).
Hunk #12 succeeded at 8387 (offset 5 lines).
1 out of 12 hunks FAILED -- saving rejects to file gcc/fortran/trans-expr.c.rej

I suspect the problem is spaces/tabs related in the line

gfc_add_block_to_block (se-post, post);

After applying the hunk manually, I bootstrapped and regtested with the patch
for pr60255 without further trouble. The results are posted at

https://gcc.gnu.org/ml/gcc-testresults/2014-12/msg01222.html

and the failures for gfortran.dg/unlimited_polymorphic_1.f03 are not due this
patch, but the one for pr60255.

For the record, I have a patch in my working tree such that
gfortran.dg/widechar_intrinsics_10.f90 is miscomputed with -m32 (I did not yet
investigate the problem: too many patches in my working tree).

Thanks for working on this issue.


[Bug fortran/63205] [OOP] Wrongly rejects type = class (for identical declared type)

2014-12-09 Thread paul.richard.thomas at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63205

paul.richard.thomas at gmail dot com paul.richard.thomas at gmail dot com 
changed:

   What|Removed |Added

  Attachment #33995|0   |1
is obsolete||

--- Comment #6 from paul.richard.thomas at gmail dot com paul.richard.thomas 
at gmail dot com ---
Created attachment 34234
  -- https://gcc.gnu.org/bugzilla/attachment.cgi?id=34234action=edit
A near final patch

This version runs the testcase below without memory leaks. It also bootstraps
and regtests OK.

It still needs some tidying up but it is nearly there after all the struggles
to eliminate memory leaks and with the scalarizer.

Cheers

Paul

program test
  implicit none
  type t
integer :: ii
  end type t
  type, extends(t) :: u
real :: rr
  end type u
  type, extends(t) :: v
real, allocatable :: rr(:)
  end type v
  type, extends(v) :: w
real, allocatable :: rrr(:)
  end type w

  type(t) :: x, y(3)
  type(v) :: a, b(3)

  x = func1() ! scalar to scalar - no alloc comps
  if (x%ii .ne. 77) call abort

  y = func2() ! array to array - no alloc comps
  if (any (y%ii .ne. [1,2,3])) call abort

  y = func1() ! scalar to array - no alloc comps
  if (any (y%ii .ne. 77)) call abort

  x = func3() ! scalar daughter type to scalar - no alloc comps
  if (x%ii .ne. 99) call abort

  y = func4() ! array daughter type to array - no alloc comps
  if (any (y%ii .ne. [3,4,5])) call abort

  a = func5() ! scalar to scalar - alloc comps in parent type
  if (any (a%rr .ne. [10.0,20.0])) call abort

  b = func6() ! array to array - alloc comps in parent type
  if (any (b(3)%rr .ne. [3.0,4.0])) call abort

  a = func7() ! scalar daughter type to scalar - alloc comps in parent type
  if (any (a%rr .ne. [10.0,20.0])) call abort

  b = func8() ! array daughter type to array - alloc comps in parent type
  if (any (b(3)%rr .ne. [3.0,4.0])) call abort

! This is an extension of class_to_type_2.f90's test using a daughter type
! instead of the declared type.
  if (subpr2_array (g ()) .ne. 99 ) call abort
contains

  function func1() result(res)
class(t), allocatable :: res
allocate (res, source = t(77))
  end function func1

  function func2() result(res)
class(t), allocatable :: res(:)
allocate (res(3), source = [u(1,1.0),u(2,2.0),u(3,3.0)])
  end function func2

  function func3() result(res)
class(t), allocatable :: res
allocate (res, source = v(99,[99.0,99.0,99.0]))
  end function func3

  function func4() result(res)
class(t), allocatable :: res(:)
allocate (res(3), source = [v(3,[1.0,2.0]),v(4,[2.0,3.0]),v(5,[3.0,4.0])])
  end function func4

  function func5() result(res)
class(v), allocatable :: res
allocate (res, source = v(3,[10.0,20.0]))
  end function func5

  function func6() result(res)
class(v), allocatable :: res(:)
allocate (res(3), source = [v(3,[1.0,2.0]),v(4,[2.0,3.0]),v(5,[3.0,4.0])])
  end function func6

  function func7() result(res)
class(v), allocatable :: res
allocate (res, source = w(3,[10.0,20.0],[100,200]))
  end function func7

  function func8() result(res)
class(v), allocatable :: res(:)
allocate (res(3), source =
[w(3,[1.0,2.0],[0.0]),w(4,[2.0,3.0],[0.0]),w(5,[3.0,4.0],[0.0])])
  end function func8


  integer function subpr2_array (x)
type(t) :: x(:)
if (any(x(:)%ii /= 55)) call abort
subpr2_array = 99
  end function

  function g () result(res)
integer i
class(t), allocatable :: res(:)
allocate (res(3), source = [(v (1, [1.0,2.0]), i = 1, 3)])
res(:)%ii = 55
  end function g
end program test


[Bug fortran/63205] [OOP] Wrongly rejects type = class (for identical declared type)

2014-11-16 Thread paul.richard.thomas at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63205

paul.richard.thomas at gmail dot com paul.richard.thomas at gmail dot com 
changed:

   What|Removed |Added

  Attachment #33834|0   |1
is obsolete||

--- Comment #4 from paul.richard.thomas at gmail dot com paul.richard.thomas 
at gmail dot com ---
Created attachment 33995
  -- https://gcc.gnu.org/bugzilla/attachment.cgi?id=33995action=edit
Patch that fixes testcase in the comment but causes regressions.

The attached patch runs the testcase below without memory leaks but causes
regressions in:
class_allocate_7.f03
class_to_type_2.f90
typebound_operator_7.f03
typebound_operator_8.f03

All of these are run time errors caused by finalization occurring too soon. The
additions to gfc_conv_procedure_call will have to be moved to
gfc_trans_assignment_1 so that the specific case of class function assignment
to derived type is caught. I will attend to this during this week.

Paul

program test
  implicit none
  type t
integer :: ii
  end type t
  type, extends(t) :: u
real :: rr
  end type u
  type, extends(t) :: v
real, allocatable :: rr(:)
  end type v
  type, extends(v) :: w
real, allocatable :: rrr(:)
  end type w

  type(t) :: x, y(3)
  type(v) :: a, b(3)

  x = func1() ! scalar to scalar - no alloc comps
  print *, x%ii

  y = func2() ! array to array - no alloc comps
  print *, y%ii

  y = func1() ! scalar to array - no alloc comps
  print *, y%ii

  x = func3() ! scalar daughter type to scalar - no alloc comps
  print *, x%ii

  y = func4() ! array daughter type to array - no alloc comps
  print *, y%ii

  a = func5() ! scalar to scalar - alloc comps in parent type
  print *, a%rr

  b = func6() ! array to array - alloc comps in parent type
  print *, b(3)%rr

  a = func7() ! scalar daughter type to scalar - alloc comps in parent type
  print *, a%rr

  b = func8() ! array daughter type to array - alloc comps in parent type
  print *, b(3)%rr

contains

  function func1() result(res)
class(t), allocatable :: res
allocate (res, source = t(77))
  end function func1

  function func2() result(res)
class(t), allocatable :: res(:)
allocate (res(3), source = [u(1,1.0),u(2,2.0),u(3,3.0)])
  end function func2

  function func3() result(res)
class(t), allocatable :: res
allocate (res, source = v(99,[99.0,99.0,99.0]))
  end function func3

  function func4() result(res)
class(t), allocatable :: res(:)
allocate (res(3), source = [v(3,[1.0,2.0]),v(4,[2.0,3.0]),v(5,[3.0,4.0])])
  end function func4

  function func5() result(res)
class(v), allocatable :: res
allocate (res, source = v(3,[10.0,20.0]))
  end function func5

  function func6() result(res)
class(v), allocatable :: res(:)
allocate (res(3), source = [v(3,[1.0,2.0]),v(4,[2.0,3.0]),v(5,[3.0,4.0])])
  end function func6

  function func7() result(res)
class(v), allocatable :: res
allocate (res, source = w(3,[10.0,20.0],[100,200]))
  end function func7

  function func8() result(res)
class(v), allocatable :: res(:)
allocate (res(3), source =
[w(3,[1.0,2.0],[0.0]),w(4,[2.0,3.0],[0.0]),w(5,[3.0,4.0],[0.0])])
  end function func8

end program test


[Bug fortran/63205] [OOP] Wrongly rejects type = class (for identical declared type)

2014-11-16 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63205

--- Comment #5 from Dominique d'Humieres dominiq at lps dot ens.fr ---
 The attached patch runs the testcase below without memory leaks but
 causes regressions in:
 class_allocate_7.f03
 class_to_type_2.f90
 typebound_operator_7.f03
 typebound_operator_8.f03

With the patch in comment 4 I don't see these regressions:

[Book15] build_w/gcc% make -k check-gfortran RUNTESTFLAGS=dg.exp=class*
--target_board=unix'{-m32,-m64}'
...
=== gfortran Summary for unix/-m64 ===

# of expected passes1091
# of unsupported tests2

=== gfortran Summary ===

# of expected passes2182
# of unsupported tests4

[Book15] build_w/gcc% make -k check-gfortran RUNTESTFLAGS=dg.exp=typebound*
--target_board=unix'{-m32,-m64}'
...
=== gfortran Summary for unix/-m64 ===

# of expected passes846
# of expected failures1

=== gfortran Summary ===

# of expected passes1692
# of expected failures2

There is no more ICE for the reduced test in comment 1 (1), but a segmentation
fault. However I doubt the code is valid.

Thanks for the patch. Further testing in progress.


[Bug fortran/63205] [OOP] Wrongly rejects type = class (for identical declared type)

2014-10-28 Thread paul.richard.thomas at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63205

paul.richard.thomas at gmail dot com paul.richard.thomas at gmail dot com 
changed:

   What|Removed |Added

 CC||paul.richard.thomas at gmail 
dot c
   ||om

--- Comment #3 from paul.richard.thomas at gmail dot com paul.richard.thomas 
at gmail dot com ---
Created attachment 33834
  -- https://gcc.gnu.org/bugzilla/attachment.cgi?id=33834action=edit
Very deficient, first order patch

The attached is deficient in a number of ways:
(i) It will not work with a dynamic type result != declared type
(ii) The block in trans-array.c:2549-2560 needs to be moved to somewhere more
appropriate
(iii) Find out why info-delta[] is not set
(iv) dynamic types with allocatable components will have to have those
components deallocated (use _copy with default_init?)

Apart from that, it's a start :-)

Paul


[Bug fortran/63205] [OOP] Wrongly rejects type = class (for identical declared type)

2014-10-27 Thread pault at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63205

Paul Thomas pault at gcc dot gnu.org changed:

   What|Removed |Added

 CC||pault at gcc dot gnu.org
   Assignee|unassigned at gcc dot gnu.org  |pault at gcc dot gnu.org

--- Comment #2 from Paul Thomas pault at gcc dot gnu.org ---
I am well on my way to a fix for all these issues of class assignment to type.

I'll try to post where I have got up to in the next 24 hours.  Getting the
scalarizer to swallow the class array valued functions has been quite a trip
down memory lane :-)

Paul


[Bug fortran/63205] [OOP] Wrongly rejects type = class (for identical declared type)

2014-09-12 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63205

Dominique d'Humieres dominiq at lps dot ens.fr changed:

   What|Removed |Added

 Status|UNCONFIRMED |NEW
   Last reconfirmed||2014-09-12
 Ever confirmed|0   |1

--- Comment #1 from Dominique d'Humieres dominiq at lps dot ens.fr ---
I see two issues with the test assign_11.f90:

(1) an ICE, reduced test

program test
  implicit none
  type t
integer :: ii
  end type t
  type(t) :: y(3)

  y = func2()
contains
  function func2() result(res)
class(t), allocatable :: res(:)
  end function func2
end program test

[Book15] f90/bug% gfc49 pr63205_red.f90
pr63205_red.f90: In function 'test':
pr63205_red.f90:8:0: internal compiler error: in gfc_trans_arrayfunc_assign, at
fortran/trans-expr.c:7369
   y = func2()
 ^

(2) a wrong code, reduced test

module m
  implicit none
  type t
integer :: ii = 55
  end type t
contains
  subroutine sub (from, from2)
class(t) :: from, from2(:)
type(t) :: to, to2(3)

if (from%ii /= 43) call abort()
if (size (from2) /= 3) call abort()
if (any (from2(:)%ii /= [11,22,33])) call abort()

to = from  ! TYPE = CLASS
to2 = from2  ! TYPE = CLASS

print *, to%ii
!if (to%ii /= 43) call abort()
if (any (to2(:)%ii /= [11,22,33])) call abort()
  end subroutine sub
end module m

program test
  use m
  implicit none
  type(t), target :: x
  type(t), target :: y(3)

  x%ii = 43
  y(:)%ii = [11,22,33]
  call sub(x,y)
  x = func1()
  print *, x
!  if (x%ii /= 123) call abort()
  y = func1()
  print *, y
!  if (any (y(:)%ii /= 123)) call abort()
contains
  function func1()
class(t), allocatable :: func1
allocate(func1)
func1%ii = 123
  end function func1
end program test

[Book15] f90/bug% gfc49 pr63205_red_1.f90
[Book15] f90/bug% a.out 
   167182484
   586153984
   586154000   586154000   586154000

Any objection that I open a new PR for the ICE?

 However, only type = class is handled. Still missing is type = class,
 where CLASS is a (coarray) scalar or (coarray) array variable, function or
 an array constructor. See also PR 57530 comment 3.

AFAICT the assignment works for array variable, at least in the to2 context.