[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-20 Thread pault at gcc dot gnu dot org


--- Comment #23 from pault at gcc dot gnu dot org  2010-04-20 06:19 ---
Created an attachment (id=20433)
 -- (http://gcc.gnu.org/bugzilla/attachment.cgi?id=20433action=view)
fix for this PR and PR43266

The attached is what I intend to submit tonight, unless somebody approves it in
the mean time.  Obviously, the patch needs ChangeLogs.

Also included is the fix for PR43266, which was first posted on March 27 and is
very 'obvious'.

Bootstrapped and regtested on FC9/x86_64 and RHEL5.4/i686

OK?


-- 

pault at gcc dot gnu dot org changed:

   What|Removed |Added

  Attachment #20429|0   |1
is obsolete||


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-20 Thread dominiq at lps dot ens dot fr


--- Comment #24 from dominiq at lps dot ens dot fr  2010-04-20 09:18 ---
The patch in comment #23 works fine on my tests. Thanks for it.

 Also included is the fix for PR43266, which was first posted on March 27 and 
 is
 very 'obvious'.

Note for the record that it gives an additional error for PR43266 instead of
the ICE:

pr43266.f90:37.25:

   CALL obj%middle%proc_b
 1
Error: 'proc_b' at (1) should be a SUBROUTINE


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-20 Thread paul dot richard dot thomas at gmail dot com


--- Comment #25 from paul dot richard dot thomas at gmail dot com  
2010-04-20 09:31 ---
Subject: Re:  [4.5/4.6 Regression] ICE: segmentation fault 
in mio_expr

Dominiq,

 Note for the record that it gives an additional error for PR43266 instead of
 the ICE:

 pr43266.f90:37.25:

   CALL obj%middle%proc_b
                         1
 Error: 'proc_b' at (1) should be a SUBROUTINE


Yes, indeed.  This appears in the testcase and results from the module
not being written.

Paul


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-20 Thread pault at gcc dot gnu dot org


--- Comment #26 from pault at gcc dot gnu dot org  2010-04-20 19:07 ---
Subject: Bug 43227

Author: pault
Date: Tue Apr 20 19:07:14 2010
New Revision: 158570

URL: http://gcc.gnu.org/viewcvs?root=gccview=revrev=158570
Log:
2010-04-20  Paul Thomas  pa...@gcc.gnu.org

PR fortran/43227
* resolve.c (resolve_fl_derived): If a component character
length has not been resolved, do so now.
(resolve_symbol): The same as above for a symbol character
length.
* trans-decl.c (gfc_create_module_variable): A 'length' decl is
not needed for a character valued, procedure pointer.

PR fortran/43266
* resolve.c (ensure_not_abstract_walker): If 'overriding' is
not found, return FAILURE rather than ICEing.

2010-04-20  Paul Thomas  pa...@gcc.gnu.org

PR fortran/43227
* gfortran.dg/proc_decl_23.f90: New test.

PR fortran/43266
* gfortran.dg/abstract_type_6.f03: New test.

Added:
trunk/gcc/testsuite/gfortran.dg/abstract_type_6.f03
trunk/gcc/testsuite/gfortran.dg/proc_decl_23.f90
Modified:
trunk/gcc/fortran/ChangeLog
trunk/gcc/fortran/resolve.c
trunk/gcc/fortran/trans-decl.c
trunk/gcc/testsuite/ChangeLog


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-19 Thread pault at gcc dot gnu dot org


--- Comment #9 from pault at gcc dot gnu dot org  2010-04-19 12:12 ---
I decided to take a look at this during lunchtime today.  The source that I had
to hand is the 20091203 4.5.0 snapshot.  To my astonishment, this does not show
the problem.  I have had a quick look at the intervening gcc-cvs postings but
cannot identify the source of the regression yet.  Janus's patch of 20091211 is
NOT the cause.

Paul  


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-19 Thread dominiq at lps dot ens dot fr


--- Comment #10 from dominiq at lps dot ens dot fr  2010-04-19 12:33 ---
 I decided to take a look at this during lunchtime today.  The source that I 
 had
 to hand is the 20091203 4.5.0 snapshot.  To my astonishment, this does not 
 show
 the problem.  I have had a quick look at the intervening gcc-cvs postings but
 cannot identify the source of the regression yet.  Janus's patch of 20091211 
 is
 NOT the cause.

AFAICR the problem is specific to the fortran-dev branch. From my logs and my
habits, I suspect that it was introduced between revisions 156573 (Feb  7 2010)
and 157148 (probably at or after r157133, i.e. on or after Mon Mar  1 09:23:35
2010).


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-19 Thread janus at gcc dot gnu dot org


--- Comment #11 from janus at gcc dot gnu dot org  2010-04-19 12:51 ---
(In reply to comment #10)
 AFAICR the problem is specific to the fortran-dev branch.

No, this is definitely not the case! Only the failure of comment #0 is specific
to the branch. However, this failure is caused by an underlying problem with
procedure pointers, which is also present in the 4.5 release (see comment #3).

When searching for the origin of the regression, one should use the test case
in comment #3 and look at the 4.5 trunk.


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-19 Thread dominiq at lps dot ens dot fr


--- Comment #12 from dominiq at lps dot ens dot fr  2010-04-19 13:06 ---
 When searching for the origin of the regression, one should use the test case
 in comment #3 and look at the 4.5 trunk.

I keep forgetting this test!-(on i686-apple-darwin9, it compiles at revision
147438, 20090512, and fails at revision 150825, 20090817).


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-19 Thread janus at gcc dot gnu dot org


--- Comment #13 from janus at gcc dot gnu dot org  2010-04-19 13:21 ---

 I keep forgetting this test!-(on i686-apple-darwin9, it compiles at revision
 147438, 20090512, and fails at revision 150825, 20090817).

That's a start. I can see two (hypothetical) candidates in this range:

 * r150725
 * r150823

Will try to find out if one of these is the culprit.


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-19 Thread janus at gcc dot gnu dot org


--- Comment #14 from janus at gcc dot gnu dot org  2010-04-19 13:46 ---
(In reply to comment #13)
  I keep forgetting this test!-(on i686-apple-darwin9, it compiles at revision
  147438, 20090512, and fails at revision 150825, 20090817).
 
 That's a start. I can see two (hypothetical) candidates in this range:
 
  * r150725
  * r150823

I just checked r150724, which also fails. This means that both my guesses were
wrong. But at least it bring us down to the range 147438:150724 (which is still
three months of development).


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-19 Thread dominiq at lps dot ens dot fr


--- Comment #15 from dominiq at lps dot ens dot fr  2010-04-19 13:54 ---
 I just checked r150724, which also fails. This means that both my guesses were
 wrong. But at least it bring us down to the range 147438:150724 (which is 
 still
 three months of development).

I don't have access to IRC from my office desk. If you have access to it, you
may ping Tobias and Jerry to ask them to look to their archives for something
in between.


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-19 Thread burnus at gcc dot gnu dot org


--- Comment #16 from burnus at gcc dot gnu dot org  2010-04-19 15:13 ---
Works: 2009-07-24-r150035
Fails: 2009-07-29-r150196

(Both trees were _not_ clean, but the first has the same patches as the second
one, plus one more - thus, it is rather likely that the regression range is
still correct.)


I think the culprit is:

Date: Sat Jul 25 11:56:35 2009
New Revision: 150078
URL: http://gcc.gnu.org/viewcvs?root=gccview=revrev=150078

2009-07-25  Janus Weil  ja...@gcc.gnu.org

PR fortran/39630
* decl.c (match_ppc_decl): Implement the PASS attribute for procedure
pointer components.
[...]
* module.c (MOD_VERSION): Bump module version.
(binding_ppc): New string constants.
(mio_component): Only use formal args if component is a procedure
pointer and add 'tb' member.
(mio_typebound_proc): Include pass_arg and take care of procedure
pointer components.
[...]


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-19 Thread janus at gcc dot gnu dot org


--- Comment #17 from janus at gcc dot gnu dot org  2010-04-19 18:47 ---
(In reply to comment #16)
 I think the culprit is:
 
 Date: Sat Jul 25 11:56:35 2009
 New Revision: 150078
 URL: http://gcc.gnu.org/viewcvs?root=gccview=revrev=150078

Close, but not quite :)

It's actually r150047, as I just found out. However, this revision only
introduces the first ICE in the test case:

module m_string

  procedure(string_to_char) :: char1! ICE #1

!   procedure(string_to_char),pointer :: char2  ! ICE #2

!   type t_string
! procedure(string_to_char),pointer,nopass :: char3 ! ICE #3
!   end type t_string

contains

  function string_to_char (s) result(res)
character, dimension(:), intent(in) :: s
character(len=size(s)) :: res
  end function string_to_char

end module m_string


The second one is already there at r150046. For this I found a window of
147438:148816 up to now. Will try to find out more.


The third ICE is not present at 150047, but is apparently masked by another
error:

character(len=size(s)) :: res
  1
Error: Character length of component 'char3' needs to be a constant
specification expression at (1)


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-19 Thread pault at gcc dot gnu dot org


--- Comment #18 from pault at gcc dot gnu dot org  2010-04-19 18:48 ---
(In reply to comment #16)
I sort of doubt it.  The problem arises because mio_symbol crashes in writing
the character length of the procedure symbol:

Breakpoint 1, mio_symbol (sym=0x9d02370)
at ../../fortran-dev/gcc/fortran/module.c:3560
3560  mio_typespec (sym-ts);
(gdb) print sym-name
$1 = 0xb7c8c9f0 char1
(gdb) print sym-ts.u.cl
$2 = (gfc_charlen *) 0x9d04400
(gdb) print *sym-ts.u.cl
$3 = {length = 0x9d04420, next = 0x0, length_from_typespec = 0 '\0', 
  backend_decl = 0x0, passed_length = 0x0, resolved = 0}
(gdb) print *sym-ts.interface-ts.u.cl
$4 = {length = 0x9d03000, next = 0x9cb6be8, length_from_typespec = 0 '\0', 
  backend_decl = 0x0, passed_length = 0x0, resolved = 1}
(gdb) 

Note that the interface character length has been resolved, whereas the
procedure character length has not.  This is why my patch of #7 works.  I
believe that the problem must lie in resolve.c.  For some reason, the symbol's
own character length expression is not being resolved.

Paul


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-19 Thread dominiq at lps dot ens dot fr


--- Comment #19 from dominiq at lps dot ens dot fr  2010-04-19 20:13 ---
Note that the patch in comment #7 fixes the test in comment #3 when the 'type
t_string' block is uncommented. But there is still a Segmentation fault when
the line

!   procedure(string_to_char),pointer :: char2  ! segfault

is uncommented.


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-19 Thread pault at gcc dot gnu dot org


--- Comment #20 from pault at gcc dot gnu dot org  2010-04-19 21:16 ---
Created an attachment (id=20429)
 -- (http://gcc.gnu.org/bugzilla/attachment.cgi?id=20429action=view)
A provisional fix for the PR

This needs cleaning up and FAILUREs of the gfc_resolve_expr's need dealing
with.

Once this is done and a testcase fabricated, I will submit it - tomorrow
morning, I guess.

BTW It bootstraps and regtests on trunk.

Paul 


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-19 Thread janus at gcc dot gnu dot org


--- Comment #21 from janus at gcc dot gnu dot org  2010-04-19 21:34 ---
(In reply to comment #20)
 Created an attachment (id=20429)
 -- (http://gcc.gnu.org/bugzilla/attachment.cgi?id=20429action=view) [edit]
 A provisional fix for the PR


Yes, the following parts are approved (they're exactly what I had in mind):

@@ -10292,6 +10298,8 @@
{
  c-ts.u.cl = gfc_new_charlen (sym-ns, ifc-ts.u.cl);
  gfc_expr_replace_comp (c-ts.u.cl-length, c);
+ if (c-ts.u.cl-length  !c-ts.u.cl-resolved)
+   gfc_resolve_expr (c-ts.u.cl-length);
}
}
  else if (c-ts.interface-name[0] != '\0'  !sym-attr.vtype)
@@ -10805,6 +10813,8 @@
{
  sym-ts.u.cl = gfc_new_charlen (sym-ns, ifc-ts.u.cl);
  gfc_expr_replace_symbols (sym-ts.u.cl-length, sym);
+ if (sym-ts.u.cl-length  !sym-ts.u.cl-resolved)
+   gfc_resolve_expr (sym-ts.u.cl-length);
}
}
   else if (sym-ts.interface-name[0] != '\0')


Could you explain what the other stuff is needed for? I currently fail to see
that.


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-19 Thread pault at gcc dot gnu dot org


--- Comment #22 from pault at gcc dot gnu dot org  2010-04-20 05:00 ---
(In reply to comment #21)

 
 Could you explain what the other stuff is needed for? I currently fail to see
 that.
 

Ignore the first bit in resolve.c,

The change to trans-decl.c fixes the second segfault.  The procedure pointers
do not need a character length to do their job.  So rather than making a decl
for it, we just charge through.  It needs a gcc_assert to make sure that we
don't let everything through.

Watch this space!

Paul


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-18 Thread dominiq at lps dot ens dot fr


--- Comment #4 from dominiq at lps dot ens dot fr  2010-04-18 11:48 ---
Marked as a 4.5/4.6 regression.


-- 

dominiq at lps dot ens dot fr changed:

   What|Removed |Added

Summary|[4.5 Regression] ICE:   |[4.5/4.6 Regression] ICE:
   |segmentation fault in   |segmentation fault in
   |mio_expr|mio_expr


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-18 Thread dominiq at lps dot ens dot fr


--- Comment #5 from dominiq at lps dot ens dot fr  2010-04-18 16:18 ---
What about pr42274? Is it a duplicate or not?


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-18 Thread janus at gcc dot gnu dot org


--- Comment #6 from janus at gcc dot gnu dot org  2010-04-18 16:42 ---
(In reply to comment #5)
 What about pr42274? Is it a duplicate or not?

I don't think so.


-- 


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-18 Thread pault at gcc dot gnu dot org


--- Comment #7 from pault at gcc dot gnu dot org  2010-04-18 17:33 ---
Created an attachment (id=20410)
 -- (http://gcc.gnu.org/bugzilla/attachment.cgi?id=20410action=view)
Fix for the problem

This needs to be regtested but I believe it to be bombproof.

However, I should attempt to find out why the resolution is not being done else
where.

Paul


-- 

pault at gcc dot gnu dot org changed:

   What|Removed |Added

 AssignedTo|unassigned at gcc dot gnu   |pault at gcc dot gnu dot org
   |dot org |
 Status|NEW |ASSIGNED


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



[Bug fortran/43227] [4.5/4.6 Regression] ICE: segmentation fault in mio_expr

2010-04-18 Thread pault at gcc dot gnu dot org


--- Comment #8 from pault at gcc dot gnu dot org  2010-04-18 18:30 ---
(In reply to comment #6)
 (In reply to comment #5)
  What about pr42274? Is it a duplicate or not?
 
 I don't think so.
 

My patch fixes pr42274 comment #9 but not the main part of it.  Janus is quite
right that the bugs are different.

The patch regtests OK, as expected.  I will do some investigating as to the
right place to do the resolution.  module.c does not look right :-)


Cheers

Paul
Cheers

Paul


-- 


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