public inbox for gcc-patches@gcc.gnu.org
 help / color / mirror / Atom feed
* [Patch, Fortran] PR 42072: [F03] wrong-code with C_F_PROCPOINTER
@ 2009-11-17 22:39 Janus Weil
  2009-11-18 10:39 ` Paul Richard Thomas
  0 siblings, 1 reply; 7+ messages in thread
From: Janus Weil @ 2009-11-17 22:39 UTC (permalink / raw)
  To: gfortran, gcc-patches

[-- Attachment #1: Type: text/plain, Size: 1454 bytes --]

Hi all,

the attached patch fixes the behavior of C_F_PROCPOINTER if its
procptr argument is itself a dummy argument of another procedure. For
this case I added an additional 'build_fold_indirect_ref_loc', and I
also removed an unneeded 'tmp' variable. The patch was regtested on
x86_64-unknown-linux-gnu with no failures. Ok for trunk?

Two side-notes:

1) About the wrong static decl (cf. comments #3 and #5): I currently
have no idea how this comes about, and why the static prototype is
different from the actual declaration of the function. Does anyone
have an idea?

2) Once again I stumbled over the fact that the ISO_C_BINDING
intrinsics are handled in gfc_conv_procedure_call, in contrast to all
the other intrinsics, which are translated in trans-intrinsic.c. It
seems to me that gfc_conv_procedure_call is not a particularly good
place for this, as it is already a *huge* routine (several hundred
lines), even without the additional clobbering due to these
intrinsics. Is there a special reason that this is done in this very
place, or should we rather move this code to trans-intrinsic.c? (If
the latter, I would open a cleanup PR for this.)

Cheers,
Janus


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

	PR fortran/42072
	* trans-expr.c (gfc_conv_procedure_call): Handle procedure pointer
	dummies which are passed to C_F_PROCPOINTER.


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

	PR fortran/42072
	* gfortran.dg/proc_ptr_8.f90: Extended.

[-- Attachment #2: pr42072.diff --]
[-- Type: text/x-diff, Size: 1928 bytes --]

Index: gcc/testsuite/gfortran.dg/proc_ptr_8.f90
===================================================================
--- gcc/testsuite/gfortran.dg/proc_ptr_8.f90	(revision 154242)
+++ gcc/testsuite/gfortran.dg/proc_ptr_8.f90	(working copy)
@@ -23,12 +23,23 @@ MODULE X
 END MODULE X
 
 USE X
-PROCEDURE(mytype), POINTER :: ptype
+PROCEDURE(mytype), POINTER :: ptype,ptype2
 
 CALL init()
 CALL C_F_PROCPOINTER(funpointer,ptype)
 if (ptype(3) /= 9) call abort()
 
+! the stuff below was added with PR 42072
+call setpointer(ptype2)
+if (ptype2(4) /= 12) call abort()
+
+contains
+
+  subroutine setpointer (p)
+    PROCEDURE(mytype), POINTER :: p
+    CALL C_F_PROCPOINTER(funpointer,p)
+  end subroutine
+
 END
 
 ! { dg-final { cleanup-modules "X" } }
Index: gcc/fortran/trans-expr.c
===================================================================
--- gcc/fortran/trans-expr.c	(revision 154242)
+++ gcc/fortran/trans-expr.c	(working copy)
@@ -2640,14 +2640,17 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol *
 	  gfc_conv_expr (&fptrse, arg->next->expr);
 	  gfc_add_block_to_block (&se->pre, &fptrse.pre);
 	  gfc_add_block_to_block (&se->post, &fptrse.post);
+	  
+	  if (arg->next->expr->symtree->n.sym->attr.proc_pointer
+	      && arg->next->expr->symtree->n.sym->attr.dummy)
+	    fptrse.expr = build_fold_indirect_ref_loc (input_location,
+						       fptrse.expr);
+	  
+	  se->expr = fold_build2 (MODIFY_EXPR, TREE_TYPE (fptrse.expr),
+				  fptrse.expr,
+				  fold_convert (TREE_TYPE (fptrse.expr),
+						cptrse.expr));
 
-	  if (gfc_is_proc_ptr_comp (arg->next->expr, NULL))
-	    tmp = gfc_get_ppc_type (arg->next->expr->ref->u.c.component);
-	  else
-	    tmp = TREE_TYPE (arg->next->expr->symtree->n.sym->backend_decl);
-	  se->expr = fold_build2 (MODIFY_EXPR, tmp, fptrse.expr,
-				  fold_convert (tmp, cptrse.expr));
-
 	  return 0;
 	}
       else if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)

^ permalink raw reply	[flat|nested] 7+ messages in thread

* Re: [Patch, Fortran] PR 42072: [F03] wrong-code with C_F_PROCPOINTER
  2009-11-17 22:39 [Patch, Fortran] PR 42072: [F03] wrong-code with C_F_PROCPOINTER Janus Weil
@ 2009-11-18 10:39 ` Paul Richard Thomas
  2009-11-18 11:55   ` Tobias Burnus
  2009-11-18 14:09   ` Janus Weil
  0 siblings, 2 replies; 7+ messages in thread
From: Paul Richard Thomas @ 2009-11-18 10:39 UTC (permalink / raw)
  To: Janus Weil; +Cc: gfortran, gcc-patches

Janus,

> x86_64-unknown-linux-gnu with no failures. Ok for trunk?

OK for trunk (and fortran-dev :-))
>
> Two side-notes:
>
> 1) About the wrong static decl (cf. comments #3 and #5): I currently
> have no idea how this comes about, and why the static prototype is
> different from the actual declaration of the function. Does anyone
> have an idea?

That is indeed very odd and clearly incorrect.  Could you please raise
a new PR for this?

>
> 2) Once again I stumbled over the fact that the ISO_C_BINDING
> intrinsics are handled in gfc_conv_procedure_call, in contrast to all
> the other intrinsics, which are translated in trans-intrinsic.c. It
> seems to me that gfc_conv_procedure_call is not a particularly good
> place for this, as it is already a *huge* routine (several hundred
> lines), even without the additional clobbering due to these
> intrinsics. Is there a special reason that this is done in this very
> place, or should we rather move this code to trans-intrinsic.c? (If
> the latter, I would open a cleanup PR for this.)


I have been eying gfc_conv_procedure_call with a view to breaking out
the various sections into functions so that its structure becomes
apparent once more.  I have not thought about it much and would
certainly applaud anybody taking it upon themselves to do it.  As
usual, such a task requires identifying the seams such that argument
lists do not become as long as the functions being replaced :-)  As
for doing the ISO_C_BINDING in gfc_conv_procedure_call, I do not have
any opinion, other than to note that the "normal" intrinsics are
different beasts altogether.

Thanks for the fix

Paul


> 2009-11-17  Janus Weil  <janus@gcc.gnu.org>
>
>        PR fortran/42072
>        * trans-expr.c (gfc_conv_procedure_call): Handle procedure pointer
>        dummies which are passed to C_F_PROCPOINTER.
>
>
> 2009-11-17  Janus Weil  <janus@gcc.gnu.org>
>
>        PR fortran/42072
>        * gfortran.dg/proc_ptr_8.f90: Extended.
>



-- 
The knack of flying is learning how to throw yourself at the ground and miss.
       --Hitchhikers Guide to the Galaxy

^ permalink raw reply	[flat|nested] 7+ messages in thread

* Re: [Patch, Fortran] PR 42072: [F03] wrong-code with C_F_PROCPOINTER
  2009-11-18 10:39 ` Paul Richard Thomas
@ 2009-11-18 11:55   ` Tobias Burnus
  2009-11-18 14:09   ` Janus Weil
  1 sibling, 0 replies; 7+ messages in thread
From: Tobias Burnus @ 2009-11-18 11:55 UTC (permalink / raw)
  To: Paul Richard Thomas; +Cc: Janus Weil, gfortran, gcc-patches

On 11/18/2009 11:28 AM, Paul Richard Thomas wrote:
> x86_64-unknown-linux-gnu with no failures. Ok for trunk?
>   
> OK for trunk (and fortran-dev :-))
>   
fortran-dev should automatically pick up the changes from the trunk -
the next time someone does a merge.

I just merged the trunk into fortran-dev as Rev. 154286. The branch
contains all changes from the trunk up to 154283. (Current is Rev. 154286.)

Tobias

^ permalink raw reply	[flat|nested] 7+ messages in thread

* Re: [Patch, Fortran] PR 42072: [F03] wrong-code with C_F_PROCPOINTER
  2009-11-18 10:39 ` Paul Richard Thomas
  2009-11-18 11:55   ` Tobias Burnus
@ 2009-11-18 14:09   ` Janus Weil
  2009-11-18 22:59     ` Janus Weil
  1 sibling, 1 reply; 7+ messages in thread
From: Janus Weil @ 2009-11-18 14:09 UTC (permalink / raw)
  To: Paul Richard Thomas; +Cc: gfortran, gcc-patches

>> x86_64-unknown-linux-gnu with no failures. Ok for trunk?
>
> OK for trunk (and fortran-dev :-))

Thanks. Committed as r154292.


> As for doing the ISO_C_BINDING in gfc_conv_procedure_call, I do not have
> any opinion, other than to note that the "normal" intrinsics are
> different beasts altogether.

Why are they so much different? Regarding the translation, we do
pretty much the same for the ISO_C_BINDING intrinsics as we do for
some of the others, namely replacing the call by some inline code.
E.g. for C_F_PROCPOINTER, we just put in a simple pointer assignment.

Cheers,
Janus


>> 2009-11-17  Janus Weil  <janus@gcc.gnu.org>
>>
>>        PR fortran/42072
>>        * trans-expr.c (gfc_conv_procedure_call): Handle procedure pointer
>>        dummies which are passed to C_F_PROCPOINTER.
>>
>>
>> 2009-11-17  Janus Weil  <janus@gcc.gnu.org>
>>
>>        PR fortran/42072
>>        * gfortran.dg/proc_ptr_8.f90: Extended.
>>
>
>
>
> --
> The knack of flying is learning how to throw yourself at the ground and miss.
>       --Hitchhikers Guide to the Galaxy
>

^ permalink raw reply	[flat|nested] 7+ messages in thread

* Re: [Patch, Fortran] PR 42072: [F03] wrong-code with C_F_PROCPOINTER
  2009-11-18 14:09   ` Janus Weil
@ 2009-11-18 22:59     ` Janus Weil
  2009-11-19  4:28       ` Jerry DeLisle
  0 siblings, 1 reply; 7+ messages in thread
From: Janus Weil @ 2009-11-18 22:59 UTC (permalink / raw)
  To: Paul Richard Thomas; +Cc: gfortran, gcc-patches

[-- Attachment #1: Type: text/plain, Size: 918 bytes --]

>> As for doing the ISO_C_BINDING in gfc_conv_procedure_call, I do not have
>> any opinion, other than to note that the "normal" intrinsics are
>> different beasts altogether.
>
> Why are they so much different? Regarding the translation, we do
> pretty much the same for the ISO_C_BINDING intrinsics as we do for
> some of the others, namely replacing the call by some inline code.
> E.g. for C_F_PROCPOINTER, we just put in a simple pointer assignment.

Well, ok, I can see that they are handled a bit differently in some ways.

The least thing one could do would be to just separate out the
ISO_C_BINDING special handling code from gfc_conv_procedure_call, to
make it less of a monster.

The attachted patch does this by just putting the ISO_C_BINDING stuff
into a separate routine. And it does so without introducing any
regressions in the testsuite (i just checked). Should I commit this to
trunk?

Cheers,
Janus

[-- Attachment #2: pr42072_2.diff --]
[-- Type: text/x-diff, Size: 10035 bytes --]

Index: gcc/fortran/trans-expr.c
===================================================================
--- gcc/fortran/trans-expr.c	(revision 154292)
+++ gcc/fortran/trans-expr.c	(working copy)
@@ -2533,6 +2533,149 @@ conv_arglist_function (gfc_se *se, gfc_expr *expr,
 }
 
 
+/* The following routine generates code for the intrinsic
+   procedures from the ISO_C_BINDING module:
+    * C_LOC           (function)
+    * C_FUNLOC        (function)
+    * C_F_POINTER     (subroutine)
+    * C_F_PROCPOINTER (subroutine)
+    * C_ASSOCIATED    (function)
+   One exception which is not handled here is C_F_POINTER with non-scalar
+   arguments. Returns 1 if the call was replaced by inline code (else: 0).  */
+
+static int
+conv_isocbinding_procedure (gfc_se * se, gfc_symbol * sym,
+			    gfc_actual_arglist * arg)
+{
+  gfc_symbol *fsym;
+  gfc_ss *argss;
+    
+  if (sym->intmod_sym_id == ISOCBINDING_LOC)
+    {
+      if (arg->expr->rank == 0)
+	gfc_conv_expr_reference (se, arg->expr);
+      else
+	{
+	  int f;
+	  /* This is really the actual arg because no formal arglist is
+	      created for C_LOC.	 */
+	  fsym = arg->expr->symtree->n.sym;
+
+	  /* We should want it to do g77 calling convention.  */
+	  f = (fsym != NULL)
+	    && !(fsym->attr.pointer || fsym->attr.allocatable)
+	    && fsym->as->type != AS_ASSUMED_SHAPE;
+	  f = f || !sym->attr.always_explicit;
+      
+	  argss = gfc_walk_expr (arg->expr);
+	  gfc_conv_array_parameter (se, arg->expr, argss, f,
+				    NULL, NULL, NULL);
+	}
+
+      /* TODO -- the following two lines shouldn't be necessary, but
+	they're removed a bug is exposed later in the codepath.
+	This is workaround was thus introduced, but will have to be
+	removed; please see PR 35150 for details about the issue.  */
+      se->expr = convert (pvoid_type_node, se->expr);
+      se->expr = gfc_evaluate_now (se->expr, &se->pre);
+
+      return 1;
+    }
+  else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
+    {
+      arg->expr->ts.type = sym->ts.u.derived->ts.type;
+      arg->expr->ts.f90_type = sym->ts.u.derived->ts.f90_type;
+      arg->expr->ts.kind = sym->ts.u.derived->ts.kind;
+      gfc_conv_expr_reference (se, arg->expr);
+  
+      return 1;
+    }
+  else if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER
+	      && arg->next->expr->rank == 0)
+	    || sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER)
+    {
+      /* Convert c_f_pointer if fptr is a scalar
+	  and convert c_f_procpointer.  */
+      gfc_se cptrse;
+      gfc_se fptrse;
+
+      gfc_init_se (&cptrse, NULL);
+      gfc_conv_expr (&cptrse, arg->expr);
+      gfc_add_block_to_block (&se->pre, &cptrse.pre);
+      gfc_add_block_to_block (&se->post, &cptrse.post);
+
+      gfc_init_se (&fptrse, NULL);
+      if (sym->intmod_sym_id == ISOCBINDING_F_POINTER
+	  || gfc_is_proc_ptr_comp (arg->next->expr, NULL))
+	fptrse.want_pointer = 1;
+
+      gfc_conv_expr (&fptrse, arg->next->expr);
+      gfc_add_block_to_block (&se->pre, &fptrse.pre);
+      gfc_add_block_to_block (&se->post, &fptrse.post);
+      
+      if (arg->next->expr->symtree->n.sym->attr.proc_pointer
+	  && arg->next->expr->symtree->n.sym->attr.dummy)
+	fptrse.expr = build_fold_indirect_ref_loc (input_location,
+						    fptrse.expr);
+      
+      se->expr = fold_build2 (MODIFY_EXPR, TREE_TYPE (fptrse.expr),
+			      fptrse.expr,
+			      fold_convert (TREE_TYPE (fptrse.expr),
+					    cptrse.expr));
+
+      return 1;
+    }
+  else if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
+    {
+      gfc_se arg1se;
+      gfc_se arg2se;
+
+      /* Build the addr_expr for the first argument.  The argument is
+	  already an *address* so we don't need to set want_pointer in
+	  the gfc_se.  */
+      gfc_init_se (&arg1se, NULL);
+      gfc_conv_expr (&arg1se, arg->expr);
+      gfc_add_block_to_block (&se->pre, &arg1se.pre);
+      gfc_add_block_to_block (&se->post, &arg1se.post);
+
+      /* See if we were given two arguments.  */
+      if (arg->next == NULL)
+	/* Only given one arg so generate a null and do a
+	    not-equal comparison against the first arg.  */
+	se->expr = fold_build2 (NE_EXPR, boolean_type_node, arg1se.expr,
+				fold_convert (TREE_TYPE (arg1se.expr),
+					      null_pointer_node));
+      else
+	{
+	  tree eq_expr;
+	  tree not_null_expr;
+	  
+	  /* Given two arguments so build the arg2se from second arg.  */
+	  gfc_init_se (&arg2se, NULL);
+	  gfc_conv_expr (&arg2se, arg->next->expr);
+	  gfc_add_block_to_block (&se->pre, &arg2se.pre);
+	  gfc_add_block_to_block (&se->post, &arg2se.post);
+
+	  /* Generate test to compare that the two args are equal.  */
+	  eq_expr = fold_build2 (EQ_EXPR, boolean_type_node,
+				  arg1se.expr, arg2se.expr);
+	  /* Generate test to ensure that the first arg is not null.  */
+	  not_null_expr = fold_build2 (NE_EXPR, boolean_type_node,
+					arg1se.expr, null_pointer_node);
+
+	  /* Finally, the generated test must check that both arg1 is not
+	      NULL and that it is equal to the second arg.  */
+	  se->expr = fold_build2 (TRUTH_AND_EXPR, boolean_type_node,
+				  not_null_expr, eq_expr);
+	}
+
+      return 1;
+    }
+    
+  return 0;
+}
+
+
 /* Generate code for a procedure call.  Note can return se->post != NULL.
    If se->direct_byref is set then se->expr contains the return parameter.
    Return nonzero, if the call has alternate specifiers.
@@ -2576,131 +2719,10 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol *
   len = NULL_TREE;
   gfc_clear_ts (&ts);
 
-  if (sym->from_intmod == INTMOD_ISO_C_BINDING)
-    {
-      if (sym->intmod_sym_id == ISOCBINDING_LOC)
-	{
-	  if (arg->expr->rank == 0)
-	    gfc_conv_expr_reference (se, arg->expr);
-	  else
-	    {
-	      int f;
-	      /* This is really the actual arg because no formal arglist is
-		 created for C_LOC.	 */
-	      fsym = arg->expr->symtree->n.sym;
+  if (sym->from_intmod == INTMOD_ISO_C_BINDING
+      && conv_isocbinding_procedure (se, sym, arg))
+    return 0;
 
-	      /* We should want it to do g77 calling convention.  */
-	      f = (fsym != NULL)
-		&& !(fsym->attr.pointer || fsym->attr.allocatable)
-		&& fsym->as->type != AS_ASSUMED_SHAPE;
-	      f = f || !sym->attr.always_explicit;
-	  
-	      argss = gfc_walk_expr (arg->expr);
-	      gfc_conv_array_parameter (se, arg->expr, argss, f,
-					NULL, NULL, NULL);
-	    }
-
-	  /* TODO -- the following two lines shouldn't be necessary, but
-	    they're removed a bug is exposed later in the codepath.
-	    This is workaround was thus introduced, but will have to be
-	    removed; please see PR 35150 for details about the issue.  */
-	  se->expr = convert (pvoid_type_node, se->expr);
-	  se->expr = gfc_evaluate_now (se->expr, &se->pre);
-
-	  return 0;
-	}
-      else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
-	{
-	  arg->expr->ts.type = sym->ts.u.derived->ts.type;
-	  arg->expr->ts.f90_type = sym->ts.u.derived->ts.f90_type;
-	  arg->expr->ts.kind = sym->ts.u.derived->ts.kind;
-	  gfc_conv_expr_reference (se, arg->expr);
-      
-	  return 0;
-	}
-      else if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER
-	         && arg->next->expr->rank == 0)
-	       || sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER)
-	{
-	  /* Convert c_f_pointer if fptr is a scalar
-	     and convert c_f_procpointer.  */
-	  gfc_se cptrse;
-	  gfc_se fptrse;
-
-	  gfc_init_se (&cptrse, NULL);
-	  gfc_conv_expr (&cptrse, arg->expr);
-	  gfc_add_block_to_block (&se->pre, &cptrse.pre);
-	  gfc_add_block_to_block (&se->post, &cptrse.post);
-
-	  gfc_init_se (&fptrse, NULL);
-	  if (sym->intmod_sym_id == ISOCBINDING_F_POINTER
-	      || gfc_is_proc_ptr_comp (arg->next->expr, NULL))
-	    fptrse.want_pointer = 1;
-
-	  gfc_conv_expr (&fptrse, arg->next->expr);
-	  gfc_add_block_to_block (&se->pre, &fptrse.pre);
-	  gfc_add_block_to_block (&se->post, &fptrse.post);
-	  
-	  if (arg->next->expr->symtree->n.sym->attr.proc_pointer
-	      && arg->next->expr->symtree->n.sym->attr.dummy)
-	    fptrse.expr = build_fold_indirect_ref_loc (input_location,
-						       fptrse.expr);
-	  
-	  se->expr = fold_build2 (MODIFY_EXPR, TREE_TYPE (fptrse.expr),
-				  fptrse.expr,
-				  fold_convert (TREE_TYPE (fptrse.expr),
-						cptrse.expr));
-
-	  return 0;
-	}
-      else if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
-        {
-	  gfc_se arg1se;
-	  gfc_se arg2se;
-
-	  /* Build the addr_expr for the first argument.  The argument is
-	     already an *address* so we don't need to set want_pointer in
-	     the gfc_se.  */
-	  gfc_init_se (&arg1se, NULL);
-	  gfc_conv_expr (&arg1se, arg->expr);
-	  gfc_add_block_to_block (&se->pre, &arg1se.pre);
-	  gfc_add_block_to_block (&se->post, &arg1se.post);
-
-	  /* See if we were given two arguments.  */
-	  if (arg->next == NULL)
-	    /* Only given one arg so generate a null and do a
-	       not-equal comparison against the first arg.  */
-	    se->expr = fold_build2 (NE_EXPR, boolean_type_node, arg1se.expr,
-				    fold_convert (TREE_TYPE (arg1se.expr),
-						  null_pointer_node));
-	  else
-	    {
-	      tree eq_expr;
-	      tree not_null_expr;
-	      
-	      /* Given two arguments so build the arg2se from second arg.  */
-	      gfc_init_se (&arg2se, NULL);
-	      gfc_conv_expr (&arg2se, arg->next->expr);
-	      gfc_add_block_to_block (&se->pre, &arg2se.pre);
-	      gfc_add_block_to_block (&se->post, &arg2se.post);
-
-	      /* Generate test to compare that the two args are equal.  */
-	      eq_expr = fold_build2 (EQ_EXPR, boolean_type_node,
-				     arg1se.expr, arg2se.expr);
-	      /* Generate test to ensure that the first arg is not null.  */
-	      not_null_expr = fold_build2 (NE_EXPR, boolean_type_node,
-					   arg1se.expr, null_pointer_node);
-
-	      /* Finally, the generated test must check that both arg1 is not
-		 NULL and that it is equal to the second arg.  */
-	      se->expr = fold_build2 (TRUTH_AND_EXPR, boolean_type_node,
-				      not_null_expr, eq_expr);
-	    }
-
-	  return 0;
-	}
-    }
-
   gfc_is_proc_ptr_comp (expr, &comp);
 
   if (se->ss != NULL)

^ permalink raw reply	[flat|nested] 7+ messages in thread

* Re: [Patch, Fortran] PR 42072: [F03] wrong-code with C_F_PROCPOINTER
  2009-11-18 22:59     ` Janus Weil
@ 2009-11-19  4:28       ` Jerry DeLisle
  2009-11-19 10:54         ` Janus Weil
  0 siblings, 1 reply; 7+ messages in thread
From: Jerry DeLisle @ 2009-11-19  4:28 UTC (permalink / raw)
  To: Janus Weil; +Cc: Paul Richard Thomas, gfortran, gcc-patches

On 11/18/2009 02:55 PM, Janus Weil wrote:
>>> As for doing the ISO_C_BINDING in gfc_conv_procedure_call, I do not have
>>> any opinion, other than to note that the "normal" intrinsics are
>>> different beasts altogether.
>>
>> Why are they so much different? Regarding the translation, we do
>> pretty much the same for the ISO_C_BINDING intrinsics as we do for
>> some of the others, namely replacing the call by some inline code.
>> E.g. for C_F_PROCPOINTER, we just put in a simple pointer assignment.
>
> Well, ok, I can see that they are handled a bit differently in some ways.
>
> The least thing one could do would be to just separate out the
> ISO_C_BINDING special handling code from gfc_conv_procedure_call, to
> make it less of a monster.
>
> The attachted patch does this by just putting the ISO_C_BINDING stuff
> into a separate routine. And it does so without introducing any
> regressions in the testsuite (i just checked). Should I commit this to
> trunk?
>
> Cheers,
> Janus

OK after some spelling fixes in the comment. A nit, change to:

+      /* TODO -- the following two lines shouldn't be necessary, but if
+	they're removed, a bug is exposed later in the code path.
+	This workaround was thus introduced, but will have to be
+	removed; please see PR 35150 for details about the issue.  */

Jerry

^ permalink raw reply	[flat|nested] 7+ messages in thread

* Re: [Patch, Fortran] PR 42072: [F03] wrong-code with C_F_PROCPOINTER
  2009-11-19  4:28       ` Jerry DeLisle
@ 2009-11-19 10:54         ` Janus Weil
  0 siblings, 0 replies; 7+ messages in thread
From: Janus Weil @ 2009-11-19 10:54 UTC (permalink / raw)
  To: Jerry DeLisle; +Cc: Paul Richard Thomas, gfortran, gcc-patches

2009/11/19 Jerry DeLisle <jvdelisle@verizon.net>:
> On 11/18/2009 02:55 PM, Janus Weil wrote:
>>>>
>>>> As for doing the ISO_C_BINDING in gfc_conv_procedure_call, I do not have
>>>> any opinion, other than to note that the "normal" intrinsics are
>>>> different beasts altogether.
>>>
>>> Why are they so much different? Regarding the translation, we do
>>> pretty much the same for the ISO_C_BINDING intrinsics as we do for
>>> some of the others, namely replacing the call by some inline code.
>>> E.g. for C_F_PROCPOINTER, we just put in a simple pointer assignment.
>>
>> Well, ok, I can see that they are handled a bit differently in some ways.
>>
>> The least thing one could do would be to just separate out the
>> ISO_C_BINDING special handling code from gfc_conv_procedure_call, to
>> make it less of a monster.
>>
>> The attachted patch does this by just putting the ISO_C_BINDING stuff
>> into a separate routine. And it does so without introducing any
>> regressions in the testsuite (i just checked). Should I commit this to
>> trunk?
>
> OK after some spelling fixes in the comment. A nit, change to:
>
> +      /* TODO -- the following two lines shouldn't be necessary, but if
> +       they're removed, a bug is exposed later in the code path.
> +       This workaround was thus introduced, but will have to be
> +       removed; please see PR 35150 for details about the issue.  */

Committed as r154327 with the spelling fixes (the comment above is not
mine, I just carried it over from gfc_conv_procedure call).

Cheers,
Janus

^ permalink raw reply	[flat|nested] 7+ messages in thread

end of thread, other threads:[~2009-11-19 10:34 UTC | newest]

Thread overview: 7+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2009-11-17 22:39 [Patch, Fortran] PR 42072: [F03] wrong-code with C_F_PROCPOINTER Janus Weil
2009-11-18 10:39 ` Paul Richard Thomas
2009-11-18 11:55   ` Tobias Burnus
2009-11-18 14:09   ` Janus Weil
2009-11-18 22:59     ` Janus Weil
2009-11-19  4:28       ` Jerry DeLisle
2009-11-19 10:54         ` Janus Weil

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).