Bug 41242

Summary: [4.5 Regression] PPC call rejected (related to user-defined assignment?)
Product: gcc Reporter: Juergen Reuter <reuter>
Component: fortranAssignee: janus
Status: RESOLVED FIXED    
Severity: normal CC: domob, gcc-bugs, janus
Priority: P3 Keywords: rejects-valid
Version: 4.5.0   
Target Milestone: 4.5.0   
Host: Target:
Build: Known to work:
Known to fail: Last reconfirmed: 2009-09-10 21:09:46
Attachments: Test file for the bug report

Description Juergen Reuter 2009-09-03 11:56:34 UTC
When compiling the following code, gfortran does not correctly recognize a procedure pointer and crashes with the following message:
no_func.f90:59.12:

  n_in  = prc_lib% get_n_in (2)
          1
Error: 'prc_lib' at (1) is not a function

I attach the code and also as attachment:
module iso_varying_string

  implicit none

  type, public :: varying_string
     private
     character(len=1), dimension(:), allocatable :: chars
  end type varying_string

  interface assignment(=)
     module procedure op_assign_VS_CH
  end interface assignment(=)

  public :: assignment(=)

contains

  elemental subroutine op_assign_VS_CH (string, char)
    type(varying_string), intent(out) :: string
    character(len=*), intent(in)      :: char
    integer                           :: i
    allocate(string%chars(LEN(char)))
    forall(i = 1:len(char))
       string%chars(i) = char(i:i)
    end forall
  end subroutine op_assign_VS_CH

end module iso_varying_string



module no_func

  use iso_varying_string, string_t => varying_string !NODEP!
  implicit none
  private

  type :: nf_t
     private
     procedure(prc_get_int), nopass, pointer :: get_n_in  => null ()
  end type nf_t


  abstract interface
     function prc_get_int (pid) result (n)
       import
       integer, intent(in) :: pid
       integer :: n
     end function prc_get_int
  end interface

contains

  subroutine no_func_config (prc_lib)
    type(nf_t), intent(inout), target :: prc_lib
    integer :: n_in
    type(string_t) :: prc_id
    prc_id = "foobar"
    n_in  = prc_lib% get_n_in  (2)
  end subroutine no_func_config

end module no_func
Comment 1 Juergen Reuter 2009-09-03 11:58:57 UTC
Created attachment 18473 [details]
Test file for the bug report
Comment 2 Tobias Burnus 2009-09-04 09:47:55 UTC
Working: 2009-08-21-r150985.tar.gz
Failing: 2009-09-03-r151367.tar.gz

Daniel, I think it might be due to your TBP OPERATOR/ASSIGNMENT patch. While the program fails for:

    prc_id = "foobar"  ! ASSIGNMENT(=) [but no TBP generic]
    n_in  = prc_lib%get_n_in(2) ! Proc-pointer component

it works if one reverses the order, i.e.

    n_in  = prc_lib%get_n_in(2)
    prc_id = "foobar"

which might be an indication that it depends on the walking of the tree or that something else gets corrupt. (valgrind shows no problems.)
Comment 3 Paul Thomas 2009-09-06 07:04:42 UTC
(In reply to comment #2)

Why there is a dependence on the preceding statement, I have no idea.  However, expr_type is not being set to EXPR_PPC, as the following shows (causes lots of failures by the way :-()

Index: gcc/fortran/resolve.c
===================================================================
--- gcc/fortran/resolve.c	(revision 151449)
+++ gcc/fortran/resolve.c	(working copy)
@@ -5101,6 +5101,7 @@
 gfc_resolve_expr (gfc_expr *e)
 {
   gfc_try t;
+  gfc_component *comp;
 
   if (e == NULL)
     return SUCCESS;
@@ -5113,6 +5114,9 @@
 
     case EXPR_FUNCTION:
     case EXPR_VARIABLE:
+      if (gfc_is_proc_ptr_comp (e, &comp)
+	    && (resolve_expr_ppc (e) == SUCCESS))
+	return SUCCESS;
 
       if (check_host_association (e))
 	t = resolve_function (e);

I strongly suspect the patch of code in primary.c (gfc_match_varspec) that deals with these things but I cannot quite see why at the present.

Paul
Comment 4 Paul Thomas 2009-09-07 12:51:52 UTC
(In reply to comment #3)
Note what happens if the critical part is doubled up, thus:

  subroutine no_func_config (prc_lib)
    type(nf_t), intent(inout), target :: prc_lib
    integer :: n_in
    type(string_t) :: prc_id
    prc_id = "foobar"
    n_in  = prc_lib% get_n_in  (1)
    prc_id = "foobar"
    n_in  = prc_lib% get_n_in  (2)
  end subroutine no_func_config

Three errors now appear in the order (2), (1), (2)
If the first prc_id = "foobar" is commented out, we get just (2) or if the second is commented out, we get (1), (2).

Wierd!  I think that this will require Daniel and Janus to go back over their patches in the period concerned or to identify the specific revision.  I will try to do that tonight.

Paul
Comment 5 Paul Thomas 2009-09-09 19:06:21 UTC
(In reply to comment #4)

> Wierd!  I think that this will require Daniel and Janus to go back over their
> patches in the period concerned or to identify the specific revision.  I will
> try to do that tonight.

OK.  It is definitely Daniel's r151140 that has introduced the regression.  Now to try to understand why :-)

Paul
Comment 6 Daniel Kraft 2009-09-09 19:27:55 UTC
(In reply to comment #5)
> OK.  It is definitely Daniel's r151140 that has introduced the regression.  Now
> to try to understand why :-)

If you've no luck with that, I should hopefully find some time over the weekend to look into this problem then...  Looks interesting to me :P
Comment 7 janus 2009-09-10 12:57:06 UTC
This reduced test case shows the same weird behavior as the original:

  type :: nf_t
     procedure(integer), nopass, pointer :: get_n_in
  end type

  interface assignment(=)
     procedure op_assign
  end interface

  type(nf_t) :: prc_lib
  prc_lib = "foobar"
  print *, prc_lib%get_n_in()

contains

  elemental subroutine op_assign (str, ch)
    type(nf_t), intent(out) :: str
    character(len=*), intent(in) :: ch
  end subroutine

end

Looking into it ...
Comment 8 janus 2009-09-10 16:05:43 UTC
Ok, I think I know what's going on here.

Some background: A PPC call is usually parsed as EXPR_PPC, which happens in gfc_match_varspec. At resolution stage this is transformed to an EXPR_FUNCTION (if the PPC is a function), cf. resolve_expr_ppc. Both of this happens correctly for the test case.

The problem here is that the PPC call is resolved twice: The first time the EXPR_PPC is correctly transformed to an EXPR_FUNCTION. The second time this EXPR_FUNCTION is resolved again via resolve_function, which can not handle PPCs and claims the encountered expression is not a function.

This double resolution seems to be caused by the call to 'resolve_code' which is inserted by Daniel's r151140 in resolve_ordinary_assign.

I haven't regtested the following patch, but it makes the test case work:

Index: gcc/fortran/resolve.c
===================================================================
--- gcc/fortran/resolve.c	(revision 151596)
+++ gcc/fortran/resolve.c	(working copy)
@@ -6958,7 +6958,6 @@ resolve_ordinary_assign (gfc_code *code,
 	    && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
 	*rhsptr = gfc_get_parentheses (*rhsptr);
 
-      resolve_code (code, ns);
       return true;
     }

Daniel, do you think this patch is ok, or is there a better way to fix this?
Comment 9 Paul Thomas 2009-09-10 16:21:13 UTC
(In reply to comment #8)

Janus,

> -      resolve_code (code, ns);
>        return true;

I had wondered about the function of that resolve_code.  If it can be safely removed, do it.  Otherwise another variant of my experiment in comment #3 is to remove the codelet;

+      if (gfc_is_proc_ptr_comp (e, &comp)
+           && (resolve_expr_ppc (e) == SUCCESS))
+       return SUCCESS;

Into resolve_function, just before the offending error.

All that said, I would like to understand why it is that the number of errors that you get is equal to the number of interface assignments before the ppc evaluation. That is:

    prc_id = "foobar"
    prc_id = "foobar"
    prc_id = "foobar"
    prc_id = "foobar"
    n_in  = prc_lib% get_n_in  (2)

produces the error 4 times!  I suspect (unless you can argue otherwise :-) ) that there is something really bad going on that we are just papering over

Paul
Comment 10 Daniel Kraft 2009-09-10 16:25:34 UTC
(In reply to comment #8)
> Index: gcc/fortran/resolve.c
> ===================================================================
> --- gcc/fortran/resolve.c       (revision 151596)
> +++ gcc/fortran/resolve.c       (working copy)
> @@ -6958,7 +6958,6 @@ resolve_ordinary_assign (gfc_code *code,
>             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
>         *rhsptr = gfc_get_parentheses (*rhsptr);
> 
> -      resolve_code (code, ns);
>        return true;
>      }
> 
> Daniel, do you think this patch is ok, or is there a better way to fix this?

I think this is ok from the point of view of my patch.  I did introduce it mainly because I thought it is "cleaner" to resolve every piece of code, even though it was not "needed" at that place.  It seems it hurts there, though.

But I also think that maybe fixing the code so that the double resolve is no harm in this case is the better way to go; something like adding a flag that code is from PPCs and shouldn't be resolved and returning early, if there's no other solution...  What do you think?

But otherwise, your patch should also be ok.
Comment 11 janus 2009-09-10 18:04:54 UTC
(In reply to comment #9)
> > -      resolve_code (code, ns);
> >        return true;
> 
> I had wondered about the function of that resolve_code.  If it can be safely
> removed, do it.

Unfortunately, removing it causes ICEs on typebound_operator_3 and ..._4. Will try to see if they can be eliminated.


> Otherwise another variant of my experiment in comment #3 is to
> remove the codelet;
> 
> +      if (gfc_is_proc_ptr_comp (e, &comp)
> +           && (resolve_expr_ppc (e) == SUCCESS))
> +       return SUCCESS;
> 
> Into resolve_function, just before the offending error.

That's a possibility, but it feels a bit like fixing the effects and not the cause.


> All that said, I would like to understand why it is that the number of errors
> that you get is equal to the number of interface assignments before the ppc
> evaluation. That is:
> 
>     prc_id = "foobar"
>     prc_id = "foobar"
>     prc_id = "foobar"
>     prc_id = "foobar"
>     n_in  = prc_lib% get_n_in  (2)
> 
> produces the error 4 times!

This seems to be because the 'resolve_code' call above resolves not only the assignment statement itself, but everything that comes after it. So in this case the PPC call is resolved four extra times!
Comment 12 janus 2009-09-10 18:13:10 UTC
(In reply to comment #10)
> But I also think that maybe fixing the code so that the double resolve is no
> harm in this case is the better way to go; something like adding a flag that
> code is from PPCs and shouldn't be resolved and returning early, if there's no
> other solution...  What do you think?

I think it would be a better practice to resolve everything exactly once (to avoid unnecessary overhead), and it seems that most of resolve.c does stick to this rule (although I'm not completely sure about that). At least I had no problems before with my assumption that PPCs would be resolved just once. Also I'm not sure if multiple resolution could hurt in other places where it is not expected.

Moreover, in this case it is just wrong: Calling resolve_ordinary_assign should just resolve the assignment statement, and not the stuff that comes after it (here: the PPC call).
Comment 13 Paul Thomas 2009-09-10 18:16:12 UTC
(In reply to comment #11)

> This seems to be because the 'resolve_code' call above resolves not only the
> assignment statement itself, but everything that comes after it. So in this
> case the PPC call is resolved four extra times!
> 

Janus,

I twigged that on the way home!  Never, never use resolve_code.... :-)

resolve_code already contains:
      t = SUCCESS;
      if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
	t = gfc_resolve_expr (code->expr1);
      forall_flag = forall_save;

      if (gfc_resolve_expr (code->expr2) == FAILURE)
	t = FAILURE;

Therefore the lhs and rhs are already resolved and nothing more is needed. 

If trunk bootstraps and regtests, commit as "obvious".

Well spotted

Paul

Comment 14 janus 2009-09-10 18:29:15 UTC
> If trunk bootstraps and regtests, commit as "obvious".

As I said, I get two ICEs in the testsuite with the patch from comment #8.


Backtrace for typebound_operator_3.f03:

#0  0x000000000050de83 in generic_sym (sym=0x0) at /home/jweil/gcc45/trunk/gcc/fortran/resolve.c:940
#1  0x000000000050e05d in procedure_kind (sym=0x0) at /home/jweil/gcc45/trunk/gcc/fortran/resolve.c:994
#2  0x0000000000512465 in resolve_call (c=0x28f87d0) at /home/jweil/gcc45/trunk/gcc/fortran/resolve.c:3146
#3  0x000000000051a124 in resolve_code (code=0x28f87d0, ns=0x28d9a60) at /home/jweil/gcc45/trunk/gcc/fortran/resolve.c:7239
#4  0x0000000000522ee4 in resolve_codes (ns=0x28d9a60) at /home/jweil/gcc45/trunk/gcc/fortran/resolve.c:11449
#5  0x0000000000522fcf in gfc_resolve (ns=0x28d9a60) at /home/jweil/gcc45/trunk/gcc/fortran/resolve.c:11476
#6  0x00000000005067ae in gfc_parse_file () at /home/jweil/gcc45/trunk/gcc/fortran/parse.c:3992
#7  0x000000000054225c in gfc_be_parse_file (set_yydebug=0) at /home/jweil/gcc45/trunk/gcc/fortran/f95-lang.c:239
#8  0x000000000099e719 in compile_file () at /home/jweil/gcc45/trunk/gcc/toplev.c:1038
#9  0x00000000009a09c4 in do_compile () at /home/jweil/gcc45/trunk/gcc/toplev.c:2382
#10 0x00000000009a0a85 in toplev_main (argc=2, argv=0x7fff9d3f7808) at /home/jweil/gcc45/trunk/gcc/toplev.c:2424
#11 0x00000000005be403 in main (argc=2, argv=0x7fff9d3f7808) at /home/jweil/gcc45/trunk/gcc/main.c:35


And a similar one for typebound_operator_4.f03:

#0  0x000000000050de83 in generic_sym (sym=0x0) at /home/jweil/gcc45/trunk/gcc/fortran/resolve.c:940
#1  0x000000000050e05d in procedure_kind (sym=0x0) at /home/jweil/gcc45/trunk/gcc/fortran/resolve.c:994
#2  0x0000000000512465 in resolve_call (c=0x2552c20) at /home/jweil/gcc45/trunk/gcc/fortran/resolve.c:3146
#3  0x000000000051a124 in resolve_code (code=0x2552c20, ns=0x2551b80) at /home/jweil/gcc45/trunk/gcc/fortran/resolve.c:7239
#4  0x0000000000522ee4 in resolve_codes (ns=0x2551b80) at /home/jweil/gcc45/trunk/gcc/fortran/resolve.c:11449
#5  0x0000000000522e01 in resolve_codes (ns=0x2548420) at /home/jweil/gcc45/trunk/gcc/fortran/resolve.c:11439
#6  0x0000000000522fcf in gfc_resolve (ns=0x2548420) at /home/jweil/gcc45/trunk/gcc/fortran/resolve.c:11476
#7  0x00000000005067ae in gfc_parse_file () at /home/jweil/gcc45/trunk/gcc/fortran/parse.c:3992
#8  0x000000000054225c in gfc_be_parse_file (set_yydebug=0) at /home/jweil/gcc45/trunk/gcc/fortran/f95-lang.c:239
#9  0x000000000099e719 in compile_file () at /home/jweil/gcc45/trunk/gcc/toplev.c:1038
#10 0x00000000009a09c4 in do_compile () at /home/jweil/gcc45/trunk/gcc/toplev.c:2382
#11 0x00000000009a0a85 in toplev_main (argc=2, argv=0x7fff2da61e78) at /home/jweil/gcc45/trunk/gcc/toplev.c:2424
#12 0x00000000005be403 in main (argc=2, argv=0x7fff2da61e78) at /home/jweil/gcc45/trunk/gcc/main.c:35


At present I fail to see the reason for these, but it seems something goes wrong in resolve_call. Daniel, do you have an idea?
Comment 15 Daniel Kraft 2009-09-10 19:27:10 UTC
I can again only speak for TBPs (operator/assignment and generic ones) here, but those somehow rely on multiple resolution (at least, sort of).  The assignment gets translated into a generic call, and that one must be resolved in turn to find the matching specific binding (and also transform it into an ordinary procedure call, at least for now without dynamic dispatch).

I have to admit that some of the original concept of resolution does escape me, but I believe when we move on to implement more stuff "in the front-end", transforming it as necessary during resolution, it is indeed better to do resolves on anything generated, because we run the (theoretical) risk of propagating some front-end structures to the backend that should have been transformed.  Even if you know for now that some code that is generated does not need resolution, it may well be changed in the future to build a construct that needs; well, maybe not practically, but I hope you see what I mean.

If on the other hand the original point of resolution (I think that's about matching up symtrees/symbols that should refer to the same entity?) does require resolving only once, maybe the real way to go is splitting these "front-end code transformations" into yet another phase; then resolution would carry on just as now with once-per-everything, and the possibly recursive code transformations would be seperate.  Just some thoughts, though.

And to come back to the matter, I think I added two resolve-calls in gfc_extend_assign with my patch:  The one resolving code generated really from a type-bound operator; this one is crucial for my patch to work.  And the one for otherwise generated code, which is (presumably, without further checking in detail) the one Janus' patch removes.  And for this I would have guessed that just removing it is alright, so I also don't see why this introduces the ICEs...  Will look further at this when I find time (at the weekend, hopefully).
Comment 16 janus 2009-09-10 21:09:46 UTC
Ok, here goes an extended patch which fixes the testsuite regressions:

Index: gcc/fortran/resolve.c
===================================================================
--- gcc/fortran/resolve.c	(revision 151596)
+++ gcc/fortran/resolve.c	(working copy)
@@ -6958,7 +6958,6 @@ resolve_ordinary_assign (gfc_code *code,
 	    && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
 	*rhsptr = gfc_get_parentheses (*rhsptr);
 
-      resolve_code (code, ns);
       return true;
     }
 
@@ -7190,7 +7189,12 @@ resolve_code (gfc_code *code, gfc_namesp
 	    break;
 
 	  if (resolve_ordinary_assign (code, ns))
-	    goto call;
+	    {
+	      if (code->op == EXEC_COMPCALL)
+		goto compcall;
+	      else
+		goto call;
+	    }
 
 	  break;
 
@@ -7241,6 +7245,7 @@ resolve_code (gfc_code *code, gfc_namesp
 	  break;
 
 	case EXEC_COMPCALL:
+	compcall:
 	  resolve_typebound_call (code);
 	  break;


The problem with the two failing test cases was that after my removal of the 'resolve_code' line, type-bound assignment operators were still being translated to generic TBP calls (EXPR_COMPCALL), but those were not resolved.

For non-typebound operators there was already a mechanism in place, which would resolve the call that had been generated from an assignment statement (cf. the "goto call" in resolve_code). My patch simply makes this mechanism work for TBOs.

Regtesting now. Will commit if successful (as the patch was already pre-approved by Paul).
Comment 17 janus 2009-09-10 22:47:14 UTC
Subject: Bug 41242

Author: janus
Date: Thu Sep 10 22:47:03 2009
New Revision: 151620

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=151620
Log:
2009-09-11  Janus Weil  <janus@gcc.gnu.org>

	PR fortran/41242
	* resolve.c (resolve_ordinary_assign): Don't call resolve_code,
	to avoid that subsequent codes are resolved more than once.
	(resolve_code): Make sure that type-bound assignment operators are
	resolved correctly.


2009-09-11  Janus Weil  <janus@gcc.gnu.org>

	PR fortran/41242
	* gfortran.dg/proc_ptr_comp_21.f90: New.


Added:
    trunk/gcc/testsuite/gfortran.dg/proc_ptr_comp_21.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/resolve.c
    trunk/gcc/testsuite/ChangeLog

Comment 18 janus 2009-09-10 22:51:07 UTC
Fixed with r151620. Thanks to Juergen for the report.
Comment 19 juergen.reuter@physik.uni-freiburg.de 2009-09-11 11:56:21 UTC
Subject: Re:  [4.5 Regression] PPC call rejected (related to user-defined assignment?)

On Friday 11 September 2009 00:51, janus at gcc dot gnu dot org wrote:
> ------- Comment #18 from janus at gcc dot gnu dot org  2009-09-10 22:51
> ------- Fixed with r151620. Thanks to Juergen for the report.

Hey, Janus!
Muchas gracias fuer die schnelle und gute Arbeit! WHIZARD kompiliert und 
laeuft wieder. Dieser Runtime error ist allerdings immer noch, ich versuche 
dann mal wieder, da mehr rauszubekommen. Ich hatte das zurückgestellt, 
solange WHIZARD net kompilert hatte.
Meinst du, es koennte helfen, wenn ich irgendwann einfach ma nach Giessen 
käme, falls ich net weiterkomme?
Ciao,
	JR

Comment 20 hjl@gcc.gnu.org 2009-09-28 20:39:43 UTC
Subject: Bug 41242

Author: hjl
Date: Mon Sep 28 20:38:53 2009
New Revision: 152250

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=152250
Log:
2009-09-28  H.J. Lu  <hongjiu.lu@intel.com>

	Backport from mainline:
	2009-09-26  Andreas Schwab  <schwab@linux-m68k.org>

	PR c/41476
	* gcc.dg/cond-constqual-1.c: New test.

	2009-09-26  Michael Matz  <matz@suse.de>

	PR lto/40758
	PR middle-end/41470
	* gcc.dg/pr41470.c: New test.

	2009-09-23  Alexandre Oliva  <aoliva@redhat.com>

	PR debug/41248
	* gcc.dg/pr41248.c: New.

	2009-09-22  Alexandre Oliva  <aoliva@redhat.com>

	PR debug/41295
	* gcc.dg/pr41295.c: New.

	2009-09-20  Andrew Pinski  <pinskia@gcc.gnu.org>

	PR middle-end/40642
	* g++.dg/torture/pr40642.C: New testcase.

	2009-09-17  Michael Matz  <matz@suse.de>

	PR middle-end/41347
	* gfortran.dg/pr41347.f90: New test.

	2009-09-16  Michael Matz  <matz@suse.de>

	PR fortran/41212
	* gfortran.dg/pr41212.f90: New test.

	2009-09-11  Michael Matz  <matz@suse.de>

	PR middle-end/41275
	* g++.dg/tree-ssa/pr41275.C: New test.

	2009-09-11  Janus Weil  <janus@gcc.gnu.org>

	PR fortran/41242
	* gfortran.dg/proc_ptr_comp_21.f90: New.

Added:
    branches/gcc-4_4-branch/gcc/testsuite/g++.dg/torture/pr40642.C
      - copied unchanged from r152249, trunk/gcc/testsuite/g++.dg/torture/pr40642.C
    branches/gcc-4_4-branch/gcc/testsuite/g++.dg/tree-ssa/pr41275.C
      - copied unchanged from r152249, trunk/gcc/testsuite/g++.dg/tree-ssa/pr41275.C
    branches/gcc-4_4-branch/gcc/testsuite/gcc.dg/cond-constqual-1.c
      - copied unchanged from r152248, trunk/gcc/testsuite/gcc.dg/cond-constqual-1.c
    branches/gcc-4_4-branch/gcc/testsuite/gcc.dg/pr41248.c
      - copied unchanged from r152248, trunk/gcc/testsuite/gcc.dg/pr41248.c
    branches/gcc-4_4-branch/gcc/testsuite/gcc.dg/pr41295.c
      - copied unchanged from r152249, trunk/gcc/testsuite/gcc.dg/pr41295.c
    branches/gcc-4_4-branch/gcc/testsuite/gcc.dg/pr41470.c
      - copied unchanged from r152248, trunk/gcc/testsuite/gcc.dg/pr41470.c
    branches/gcc-4_4-branch/gcc/testsuite/gfortran.dg/pr41212.f90
      - copied unchanged from r152249, trunk/gcc/testsuite/gfortran.dg/pr41212.f90
    branches/gcc-4_4-branch/gcc/testsuite/gfortran.dg/pr41347.f90
      - copied unchanged from r152249, trunk/gcc/testsuite/gfortran.dg/pr41347.f90
    branches/gcc-4_4-branch/gcc/testsuite/gfortran.dg/proc_ptr_comp_21.f90
      - copied unchanged from r152249, trunk/gcc/testsuite/gfortran.dg/proc_ptr_comp_21.f90
Modified:
    branches/gcc-4_4-branch/gcc/testsuite/ChangeLog