public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/25818]  New: Problem with handling optional and entry master arguments
@ 2006-01-17 14:35 jakub at gcc dot gnu dot org
  2006-01-17 16:04 ` [Bug fortran/25818] " pinskia at gcc dot gnu dot org
                   ` (23 more replies)
  0 siblings, 24 replies; 25+ messages in thread
From: jakub at gcc dot gnu dot org @ 2006-01-17 14:35 UTC (permalink / raw)
  To: gcc-bugs

PROGRAM TSBVSL
           CALL NRANIN(54321.)
         END

         SUBROUTINE NRAN(VECTOR,N)
          DIMENSION VECTOR(N)
         DO I=1,N
         VECTOR(I) = RNDM(I)
         END DO
         RETURN
         ENTRY NRANIN (V)
         CALL RDMIN(V)
         RETURN
         END

         SUBROUTINE RDMIN(V)
         END

         REAL FUNCTION RNDM(I)
         RNDM=I
         END

is miscompiled on x86_64-linux at -O and higher.
The problem is that gfc_trans_deferred_vars emits some code e.g. to compute
array argument's ubound and this happens before the entry master switch,
so the the N argument pointer might be NULL.

I think we should:
a) in gfc_sym_type try harder for
   !sym->attr.optional && sym->ns->proc_name->attr.entry_master
   to see whether build_reference_type (type) could be used
   by walking all entries and see if the argument is present in all the entries
   and not optional, then it can be reference_type
b) probably use some flag set for all code emitted before the entry master
switch
   which would cause all parameters to expand to p != NULL ? *p : 0 rather than
   just *p if p is POINTER_TYPE.


-- 
           Summary: Problem with handling optional and entry master
                    arguments
           Product: gcc
           Version: 4.1.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: jakub at gcc dot gnu dot org


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
@ 2006-01-17 16:04 ` pinskia at gcc dot gnu dot org
  2006-07-27 22:38 ` taschna at uni-muenster dot de
                   ` (22 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2006-01-17 16:04 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from pinskia at gcc dot gnu dot org  2006-01-17 16:04 -------
There are a couple of issues here, first there is a missed optimization to sink
the load (there is a bug about that).  In fact this is all related to that bug.

Also there is a front-end bug having the load there in the first place so
confirmed.

If you look to see what causes the two loads to become one, that would be FRE
and that is only because the front-end is saying the first load is not zero.  I
bet we could get into real trouble with real optional arguments if this is not
done correctly.


-- 

pinskia at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |pinskia at gcc dot gnu dot
                   |                            |org
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
           Keywords|                            |wrong-code
   Last reconfirmed|0000-00-00 00:00:00         |2006-01-17 16:04:02
               date|                            |


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
  2006-01-17 16:04 ` [Bug fortran/25818] " pinskia at gcc dot gnu dot org
@ 2006-07-27 22:38 ` taschna at uni-muenster dot de
  2006-07-30 22:47 ` kargl at gcc dot gnu dot org
                   ` (21 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: taschna at uni-muenster dot de @ 2006-07-27 22:38 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from taschna at uni-muenster dot de  2006-07-27 22:38 -------
I'm an absolute beginner in programming gfortran, but the following patch seems
to solve this bug by inserting an if-block into the code in order to prevent
the access to the NULL pointer in case the array is pointing to NULL.

Index: gcc/fortran/trans-array.c
===================================================================
--- gcc/fortran/trans-array.c   (revision 115751)
+++ gcc/fortran/trans-array.c   (working copy)
@@ -3656,7 +3656,9 @@ gfc_trans_g77_array (gfc_symbol * sym, t
   locus loc;
   tree offset;
   tree tmp;
+  tree stmt;  
   stmtblock_t block;
+  bool optional_arg;  

   gfc_get_backend_locus (&loc);
   gfc_set_backend_locus (&sym->declared_at);
@@ -3685,13 +3687,22 @@ gfc_trans_g77_array (gfc_symbol * sym, t
       tmp = convert (TREE_TYPE (parm), GFC_DECL_SAVED_DESCRIPTOR (parm));
       gfc_add_modify_expr (&block, parm, tmp);
     }
-  tmp = gfc_finish_block (&block);
+  stmt = gfc_finish_block (&block);

   gfc_set_backend_locus (&loc);

   gfc_start_block (&block);
   /* Add the initialization code to the start of the function.  */
-  gfc_add_expr_to_block (&block, tmp);
+  optional_arg = (sym->attr.optional
+                 || (sym->ns->proc_name->attr.entry_master
+                     && sym->attr.dummy));
+  if (optional_arg)
+    {
+      tmp = gfc_conv_expr_present (sym);
+      stmt = build3_v (COND_EXPR, tmp, stmt, build_empty_stmt ());
+    }
+  
+  gfc_add_expr_to_block (&block, stmt);
   gfc_add_expr_to_block (&block, body);

   return gfc_finish_block (&block);


-- 


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
  2006-01-17 16:04 ` [Bug fortran/25818] " pinskia at gcc dot gnu dot org
  2006-07-27 22:38 ` taschna at uni-muenster dot de
@ 2006-07-30 22:47 ` kargl at gcc dot gnu dot org
  2006-07-31  6:32 ` taschna at uni-muenster dot de
                   ` (20 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: kargl at gcc dot gnu dot org @ 2006-07-30 22:47 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from kargl at gcc dot gnu dot org  2006-07-30 22:46 -------
(In reply to comment #2)
> I'm an absolute beginner in programming gfortran, but the following
> patch seems to solve this bug by inserting an if-block into the code
> in order to prevent the access to the NULL pointer in case the array
> is pointing to NULL.

Alexander,

Thanks for the patch, but I think it is only covering up the real
problem.  It's more a question of "why is it a NULL pointer?" not
whether we can work around the NULL pointer.  I suspect that some
where in resolve.c, gfortran is not properly setting/propagating
information about optional arguments and entry statements.


-- 


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (2 preceding siblings ...)
  2006-07-30 22:47 ` kargl at gcc dot gnu dot org
@ 2006-07-31  6:32 ` taschna at uni-muenster dot de
  2006-07-31  7:49 ` taschna at uni-muenster dot de
                   ` (19 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: taschna at uni-muenster dot de @ 2006-07-31  6:32 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from taschna at uni-muenster dot de  2006-07-31 06:32 -------
(In reply to comment #3)
Steve,

> Thanks for the patch, but I think it is only covering up the real
> problem.  It's more a question of "why is it a NULL pointer?" not
> whether we can work around the NULL pointer.  I suspect that some
> where in resolve.c, gfortran is not properly setting/propagating
> information about optional arguments and entry statements.

looking at the dump of the original tree below I would say that
it is okay to have the arguments n and vector equal NULL in
case of the call from nranin. The main problem is the code
emitted by gfc_trans_g77_array before the entry master switch.
The best solution in my opionion would be to emit the code in
the block following label L.2, but I didn't know how to do
this. Therefore I propose to do the same as we do in
gfc_trans_dummy_array_bias since revision 86128 (committed by Paul Brook)
and emit an if block surrounding the offending code.

---

MAIN__ ()
{
  _gfortran_set_std (70, 127, 0);
  {
    real4 C.687 = 5.4321e+4;

    nranin (&C.687);
  }


nran (vector, n)
{
  master.0.nran (0, 0B, n, vector);


nranin (v)
{
  master.0.nran (1, v, 0B, 0B);


master.0.nran (__entry, v, n, vector)
{
  int4 i;
  int4 ubound.0;
  int4 size.1;
  int4 D.723;
  bit_size_type D.724;
  <unnamed type> D.725;

  ubound.0 = *n;
  size.1 = NON_LVALUE_EXPR <ubound.0>;
  D.723 = size.1 - 1;
  D.724 = (bit_size_type) (<unnamed type>) size.1 * 32;
  D.725 = (<unnamed type>) size.1 * 4;
  switch (__entry)
    {
      case 0:;
      goto L.2;
      case 1:;
      goto L.4;
    }
  L.2:;
  {
    int4 D.716;

    D.716 = *n;
    i = 1;
    if (i <= D.716)
      {
        while (1)
          {
            {
              logical4 D.720;

              (*vector)[NON_LVALUE_EXPR <i> + -1] = rndm (&i);
              L.5:;
              D.720 = i == D.716;
              i = i + 1;
              if (D.720) goto L.6; else (void) 0;
            }
          }
      }
    else
      {
        (void) 0;
      }
    L.6:;
  }
  goto __return_master.0.nran;
  L.4:;
  rdmin (v);
  goto __return_master.0.nran;
  __return_master.0.nran:;
}


rdmin (v)
{
  (void) 0;


rndm (i)
{
  real4 __result_rndm;

  __result_rndm = (real4) *i;
  return __result_rndm;
}


-- 


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (3 preceding siblings ...)
  2006-07-31  6:32 ` taschna at uni-muenster dot de
@ 2006-07-31  7:49 ` taschna at uni-muenster dot de
  2006-08-21 13:36 ` pault at gcc dot gnu dot org
                   ` (18 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: taschna at uni-muenster dot de @ 2006-07-31  7:49 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from taschna at uni-muenster dot de  2006-07-31 07:49 -------
(In reply to comment #3)
Steve,

> [...]It's more a question of "why is it a NULL pointer?" not
> whether we can work around the NULL pointer.

i finally found Paul's mail corresponding to patch revision
86128: http://gcc.gnu.org/ml/fortran/2004-08/msg00102.html

There he explains the presence of the NULL:
> For each entry point we generate a thunk function which tailcalls the master 
> functions, passing NULL for any arguments which don't exist for that 
> function.

That seems to be the reason for his change in

* trans-array.c (gfc_trans_dummy_array_bias): Treat all args as
        optional when multiple entry points are present.

which I copied for my patch.


-- 


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (4 preceding siblings ...)
  2006-07-31  7:49 ` taschna at uni-muenster dot de
@ 2006-08-21 13:36 ` pault at gcc dot gnu dot org
  2006-09-18 15:33 ` paul dot richard dot thomas at cea dot fr
                   ` (17 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: pault at gcc dot gnu dot org @ 2006-08-21 13:36 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from pault at gcc dot gnu dot org  2006-08-21 13:35 -------
Jakub and co.,

Does the below do it for you?  Instead of passing null, I propose to pass the
address of a longlong containing zero.  This then leaves the normal passing of
NULL to possibly represent a missing optional argument.  It regtests OK.

I am proposing to pass a reference to a zero for unused arguments so that the
hidden, residual use of them in the master_entry does not cause an ICE. 
Otherwise, it doesn't matter how the unused arguments are represented.

Paul

Index: gcc/fortran/trans-decl.c
===================================================================
*** gcc/fortran/trans-decl.c    (revision 116268)
--- gcc/fortran/trans-decl.c    (working copy)
*************** build_entry_thunks (gfc_namespace * ns)
*** 1561,1566 ****
--- 1561,1568 ----
    tree args;
    tree string_args;
    tree tmp;
+   tree zero;
+   bool zero_flag;
    locus old_loc;

    /* This should always be a toplevel function.  */
*************** build_entry_thunks (gfc_namespace * ns)
*** 1580,1585 ****
--- 1582,1590 ----

        gfc_start_block (&body);

+       zero_flag = false;
+       zero = NULL_TREE;
+
        /* Pass extra parameter identifying this entry point.  */
        tmp = build_int_cst (gfc_array_index_type, el->id);
        args = tree_cons (NULL_TREE, tmp, NULL_TREE);
*************** build_entry_thunks (gfc_namespace * ns)
*** 1616,1621 ****
--- 1621,1627 ----
          if (thunk_formal)
            {
              /* Pass the argument.  */
+             /* TODO - missing optional arguments.  */
              DECL_ARTIFICIAL (thunk_formal->sym->backend_decl) = 1;
              args = tree_cons (NULL_TREE, thunk_formal->sym->backend_decl,
                                args);
*************** build_entry_thunks (gfc_namespace * ns)
*** 1627,1634 ****
            }
          else
            {
!             /* Pass NULL for a missing argument.  */
!             args = tree_cons (NULL_TREE, null_pointer_node, args);
              if (formal->sym->ts.type == BT_CHARACTER)
                {
                  tmp = build_int_cst (gfc_charlen_type_node, 0);
--- 1633,1651 ----
            }
          else
            {
!             /* Pass the address of a long zero for any argument that
!                is not used in this thunk.  */
!             if (!zero_flag)
!               {
!                 tmp = build_int_cst (intQI_type_node, 0);
!                 zero = gfc_create_var (intQI_type_node, NULL);
!                 gfc_add_modify_expr (&body, zero, tmp);
!                 zero = fold_convert (pvoid_type_node,
!                                      build_fold_addr_expr (zero));
!                 zero_flag = true;
!               }
!             args = tree_cons (NULL_TREE, zero, args);
!
              if (formal->sym->ts.type == BT_CHARACTER)
                {
                  tmp = build_int_cst (gfc_charlen_type_node, 0);


-- 


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (5 preceding siblings ...)
  2006-08-21 13:36 ` pault at gcc dot gnu dot org
@ 2006-09-18 15:33 ` paul dot richard dot thomas at cea dot fr
  2006-09-29  0:30 ` kargl at gcc dot gnu dot org
                   ` (16 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: paul dot richard dot thomas at cea dot fr @ 2006-09-18 15:33 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from paul dot richard dot thomas at cea dot fr  2006-09-18 15:33 -------
I mixed up my types above; using a gfc_array_index_type seems to
cover every circumstance where missing arguments can be addressed
with legal code.

Regtests on FC5/Athlon.

Index: gcc/fortran/trans-decl.c
===================================================================
*** gcc/fortran/trans-decl.c    (revision 116268)
--- gcc/fortran/trans-decl.c    (working copy)
*************** build_entry_thunks (gfc_namespace * ns)
*** 1561,1566 ****
--- 1561,1568 ----
    tree args;
    tree string_args;
    tree tmp;
+   tree zero;
+   bool zero_flag;
    locus old_loc;

    /* This should always be a toplevel function.  */
*************** build_entry_thunks (gfc_namespace * ns)
*** 1580,1585 ****
--- 1582,1590 ----

        gfc_start_block (&body);

+       zero_flag = false;
+       zero = NULL_TREE;
+
        /* Pass extra parameter identifying this entry point.  */
        tmp = build_int_cst (gfc_array_index_type, el->id);
        args = tree_cons (NULL_TREE, tmp, NULL_TREE);
*************** build_entry_thunks (gfc_namespace * ns)
*** 1616,1621 ****
--- 1621,1627 ----
          if (thunk_formal)
            {
              /* Pass the argument.  */
+             /* TODO - missing optional arguments.  */
              DECL_ARTIFICIAL (thunk_formal->sym->backend_decl) = 1;
              args = tree_cons (NULL_TREE, thunk_formal->sym->backend_decl,
                                args);
*************** build_entry_thunks (gfc_namespace * ns)
*** 1627,1634 ****
            }
          else
            {
!             /* Pass NULL for a missing argument.  */
!             args = tree_cons (NULL_TREE, null_pointer_node, args);
              if (formal->sym->ts.type == BT_CHARACTER)
                {
                  tmp = build_int_cst (gfc_charlen_type_node, 0);
--- 1633,1651 ----
            }
          else
            {
!             /* Pass the address of a long zero for any argument that
!                is not used in this thunk.  */
!             if (!zero_flag)
!               {
!                 tmp = build_int_cst (intQI_type_node, 0);
!                 zero = gfc_create_var (intQI_type_node, NULL);
!                 gfc_add_modify_expr (&body, zero, tmp);
!                 zero = fold_convert (pvoid_type_node,
!                                      build_fold_addr_expr (zero));
!                 zero_flag = true;
!               }
!             args = tree_cons (NULL_TREE, zero, args);
!
              if (formal->sym->ts.type == BT_CHARACTER)
                {
                  tmp = build_int_cst (gfc_charlen_type_node, 0);


-- 


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (6 preceding siblings ...)
  2006-09-18 15:33 ` paul dot richard dot thomas at cea dot fr
@ 2006-09-29  0:30 ` kargl at gcc dot gnu dot org
  2006-10-12 12:31 ` pault at gcc dot gnu dot org
                   ` (15 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: kargl at gcc dot gnu dot org @ 2006-09-29  0:30 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from kargl at gcc dot gnu dot org  2006-09-29 00:30 -------
Paul, Jakub,

Is the patch in comment #7 considered to be the right approach?
I tried applying to my local tree, but a few chunks were rejected.


-- 


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (7 preceding siblings ...)
  2006-09-29  0:30 ` kargl at gcc dot gnu dot org
@ 2006-10-12 12:31 ` pault at gcc dot gnu dot org
  2006-10-12 12:46 ` jakub at gcc dot gnu dot org
                   ` (14 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: pault at gcc dot gnu dot org @ 2006-10-12 12:31 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from pault at gcc dot gnu dot org  2006-10-12 12:31 -------
(In reply to comment #8)
> Paul, Jakub,
> Is the patch in comment #7 considered to be the right approach?
> I tried applying to my local tree, but a few chunks were rejected.

Jakub? What about it?

Paul


-- 


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (8 preceding siblings ...)
  2006-10-12 12:31 ` pault at gcc dot gnu dot org
@ 2006-10-12 12:46 ` jakub at gcc dot gnu dot org
  2006-11-30 11:58 ` pinskia at gcc dot gnu dot org
                   ` (13 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: jakub at gcc dot gnu dot org @ 2006-10-12 12:46 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #10 from jakub at gcc dot gnu dot org  2006-10-12 12:46 -------
No, that sounds wrong.  Not all dummy arguments have such type, so such a
change
just leads to strict aliasing violations and there are also dummy arguments
that
are larger than long.


-- 


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (9 preceding siblings ...)
  2006-10-12 12:46 ` jakub at gcc dot gnu dot org
@ 2006-11-30 11:58 ` pinskia at gcc dot gnu dot org
  2006-11-30 14:25 ` pault at gcc dot gnu dot org
                   ` (12 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2006-11-30 11:58 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #11 from pinskia at gcc dot gnu dot org  2006-11-30 11:58 -------
*** Bug 30025 has been marked as a duplicate of this bug. ***


-- 

pinskia at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |elizabeth dot l dot yip at
                   |                            |boeing dot com


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (10 preceding siblings ...)
  2006-11-30 11:58 ` pinskia at gcc dot gnu dot org
@ 2006-11-30 14:25 ` pault at gcc dot gnu dot org
  2006-11-30 15:52 ` pault at gcc dot gnu dot org
                   ` (11 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: pault at gcc dot gnu dot org @ 2006-11-30 14:25 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #12 from pault at gcc dot gnu dot org  2006-11-30 14:25 -------
(In reply to comment #2)
> I'm an absolute beginner in programming gfortran, but the following patch 

I am coming to the conclusion that your patch is one of three possible
solutions to this and pr30025:
(i) Do as you have done and subject this block of code to be conditional on the
array being present.  We could with some value repsond to Steve's comment by
improving the flagging so that none of the arguments that are always present
are so treated.
(ii) Flag the condition so that in gfc_conv_expr the dummies in the
specification expression are tested if they are present.
(iii) Modify my patch of #6 so that only integer dummies are so treated.  This
works and regtests OK but I do not think that it picks up every possibilty; eg.
where an inquiry function with a missing argument is used in a specification
expression.

All in all, I think that a modified version of your patch would do very nicely.

Thanks

Paul

PS Andrew, we had a mid-air there:-)


-- 


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (11 preceding siblings ...)
  2006-11-30 14:25 ` pault at gcc dot gnu dot org
@ 2006-11-30 15:52 ` pault at gcc dot gnu dot org
  2006-11-30 15:53 ` pault at gcc dot gnu dot org
                   ` (10 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: pault at gcc dot gnu dot org @ 2006-11-30 15:52 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #13 from pault at gcc dot gnu dot org  2006-11-30 15:52 -------
Created an attachment (id=12715)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=12715&action=view)
A development of Alexander Taeschner's patch

It is regtesting as I write; if all is well, I will submit tonight with a
testcase based on pr30025.

Thanks Alexander!

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=25818


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (12 preceding siblings ...)
  2006-11-30 15:52 ` pault at gcc dot gnu dot org
@ 2006-11-30 15:53 ` pault at gcc dot gnu dot org
  2006-12-01 20:24 ` elizabeth dot l dot yip at boeing dot com
                   ` (9 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: pault at gcc dot gnu dot org @ 2006-11-30 15:53 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #13 from pault at gcc dot gnu dot org  2006-11-30 15:52 -------
Created an attachment (id=12715)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=12715&action=view)
A development of Alexander Taeschner's patch

It is regtesting as I write; if all is well, I will submit tonight with a
testcase based on pr30025.

Thanks Alexander!

Paul


------- Comment #14 from pault at gcc dot gnu dot org  2006-11-30 15:52 -------
Created an attachment (id=12716)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=12716&action=view)
A development of Alexander Taeschner's patch

It is regtesting as I write; if all is well, I will submit tonight with a
testcase based on pr30025.

Thanks Alexander!

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=25818


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (13 preceding siblings ...)
  2006-11-30 15:53 ` pault at gcc dot gnu dot org
@ 2006-12-01 20:24 ` elizabeth dot l dot yip at boeing dot com
  2006-12-02 17:56 ` paulthomas2 at wanadoo dot fr
                   ` (8 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: elizabeth dot l dot yip at boeing dot com @ 2006-12-01 20:24 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #15 from elizabeth dot l dot yip at boeing dot com  2006-12-01 20:24 -------
One of my colleaques said my test code in Bug 30025 works on his MAC OS X
system at home.  He has an older version of gfortran.  Here is what he wrote:

It worked using gfortran on my OS X system.

~/src/C_C++ $ gfortran -v
Using built-in specs.
Target: powerpc-apple-darwin7.9.0
Configured with: ../gcc/configure --prefix=/usr/local/gfortran --enable-
languages=c,fortran --with-gmp=/tmp/gfortran-20060129/gfortran_libs --
with-mpfr=/tmp/gfortran-20060129/gfortran_libs --disable-libssp --
disable-libmudflap --disable-nlsThread model: posix gcc version 4.2.0 20060129
(experimental)


-- 


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (14 preceding siblings ...)
  2006-12-01 20:24 ` elizabeth dot l dot yip at boeing dot com
@ 2006-12-02 17:56 ` paulthomas2 at wanadoo dot fr
  2006-12-07  1:37 ` elizabeth dot l dot yip at boeing dot com
                   ` (7 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: paulthomas2 at wanadoo dot fr @ 2006-12-02 17:56 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #16 from paulthomas2 at wanadoo dot fr  2006-12-02 17:56 -------
Subject: Re:  Problem with handling optional and entry
 master arguments

elizabeth dot l dot yip at boeing dot com wrote:
> It worked using gfortran on my OS X system.
>
> ~/src/C_C++ $ gfortran -v
> Using built-in specs.
> Target: powerpc-apple-darwin7.9.0
> Configured with: ../gcc/configure --prefix=/usr/local/gfortran --enable-
> languages=c,fortran --with-gmp=/tmp/gfortran-20060129/gfortran_libs --
> with-mpfr=/tmp/gfortran-20060129/gfortran_libs --disable-libssp --
> disable-libmudflap --disable-nlsThread model: posix gcc version 4.2.0 20060129
> (experimental)
>   
I do not think that anything has changed since that time.  I have 
noticed that several operating systems are kinder when it comes to out 
of frame references.  Your problem is the same as Jakub's but I had a 
hard time to show that his was a problem.... if you know what I mean.

Thanks for the comment - let's fix it so that it lies down and 
stops,.... well bugging us :-)

Paul


-- 


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (15 preceding siblings ...)
  2006-12-02 17:56 ` paulthomas2 at wanadoo dot fr
@ 2006-12-07  1:37 ` elizabeth dot l dot yip at boeing dot com
  2006-12-07 17:34 ` paulthomas2 at wanadoo dot fr
                   ` (6 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: elizabeth dot l dot yip at boeing dot com @ 2006-12-07  1:37 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #17 from elizabeth dot l dot yip at boeing dot com  2006-12-07 01:37 -------
Paul,

I located the following binary and loaded it on my dell 670 (SUSE 9.3):

gfortran -v
Using built-in specs.
Target: x86_64-unknown-linux-gnu
Configured with: ../gcc/configure --prefix=/var/tmp/gfortran-20060627/irun
--enable-languages=c,fortran
Thread model: posix
gcc version 4.2.0 20060627 (experimental)

This versions works for the little code in bug 30025 and also works on my
entire application, which involves OPENMPI and SCALAPACK and the outofcore
solver based on SCALAPACK and various libraries by different authors with very
different styles of coding. (I want to thank the gfortran team!!!)  

We are talking about the same machine and the same operating system.  All the
x86_64 binaries are from  http://quatramaran.ens.fr/~coudert/gfortran.  I am
surprised you said you didn't think anything changed since January 2006.  

By the way, Jakub's code works on the June version without optimization.  It
fails if -O is used.  It fails with "gcc version 4.3.0 20061114" even without
optimization.  

I understand perfectly that you need to fix the bug, and the bug involves much
more than my applications, and I wouldn't feel any better if someone told me an
earlier version of my code works.   I just hope extra information helps.  

Good luck!

Elizabeth


-- 


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (16 preceding siblings ...)
  2006-12-07  1:37 ` elizabeth dot l dot yip at boeing dot com
@ 2006-12-07 17:34 ` paulthomas2 at wanadoo dot fr
  2006-12-09 21:42 ` pault at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: paulthomas2 at wanadoo dot fr @ 2006-12-07 17:34 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #18 from paulthomas2 at wanadoo dot fr  2006-12-07 17:33 -------
Subject: Re:  Problem with handling optional and entry
 master arguments

elizabeth,
>
> We are talking about the same machine and the same operating system.  All the
> x86_64 binaries are from  http://quatramaran.ens.fr/~coudert/gfortran.  I am
> surprised you said you didn't think anything changed since January 2006.
Nothing changed in respect of this bit of code - that it ever works is 
down to luck.  The entry accesses, or tries to access, the value of a 
pointer that is not set.  Use -fdump-tree-original and look at the code 
that is produced.
>  
>
> By the way, Jakub's code works on the June version without optimization.  It
> fails if -O is used.  It fails with "gcc version 4.3.0 20061114" even without
> optimization.
>   
Pure chance, I think.
> I understand perfectly that you need to fix the bug, and the bug involves much
> more than my applications, and I wouldn't feel any better if someone told me an
> earlier version of my code works.   I just hope extra information helps.  
>   
Yes, I am sorry if I seemed grumpy; as the monkey said, "every little 
bit helps..." :-)

The bug is there and could lead to segfaults at random - that I do not like!

Thanks

Paul


-- 


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (17 preceding siblings ...)
  2006-12-07 17:34 ` paulthomas2 at wanadoo dot fr
@ 2006-12-09 21:42 ` pault at gcc dot gnu dot org
  2006-12-22  2:20 ` patchapp at dberlin dot org
                   ` (4 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: pault at gcc dot gnu dot org @ 2006-12-09 21:42 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #19 from pault at gcc dot gnu dot org  2006-12-09 21:42 -------
Promises, promises...
> 
> It is regtesting as I write; if all is well, I will submit tonight with a
> testcase based on pr30025.
> 
I'll come to this just as soon as the interface stuff is a bit more sorted. -
like next weekend.

Paul


-- 


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (18 preceding siblings ...)
  2006-12-09 21:42 ` pault at gcc dot gnu dot org
@ 2006-12-22  2:20 ` patchapp at dberlin dot org
  2006-12-22 20:49 ` pault at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: patchapp at dberlin dot org @ 2006-12-22  2:20 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #20 from patchapp at dberlin dot org  2006-12-22 02:20 -------
Subject: Bug number PR25818

A patch for this bug has been added to the patch tracker.
The mailing list url for the patch is
http://gcc.gnu.org/ml/gcc-patches/2006-12/msg01527.html


-- 


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


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

* [Bug fortran/25818] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (19 preceding siblings ...)
  2006-12-22  2:20 ` patchapp at dberlin dot org
@ 2006-12-22 20:49 ` pault at gcc dot gnu dot org
  2007-01-03 21:27 ` [Bug fortran/25818] [4.2 and 4.1 only] " pault at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: pault at gcc dot gnu dot org @ 2006-12-22 20:49 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #21 from pault at gcc dot gnu dot org  2006-12-22 20:49 -------
Subject: Bug 25818

Author: pault
Date: Fri Dec 22 20:49:00 2006
New Revision: 120155

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=120155
Log:
2006-12-22  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/25818
        * trans-array.c (gfc_trans_g77_array): If the variable is
        optional or not always present, make the statement conditional
        on presence of the argument.
        * gfortran.h : Add symbol_attribute not_always_present.
        * resolve.c (check_argument_lists): New function to check if
        arguments are not present in all entries.

        PR fortran/30084
        * module.c (mio_component_ref): Move treatment of unique name
        variables, during output, to fix_mio_expr.
        (fix_mio_expr): New function that fixes defective expressions
        before they are written to the module file.
        (mio_expr): Call the new function.
        (resolve_entries): Call check_argument_lists.

2006-12-22  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/25818
        * gfortran.dg/entry_array_specs_2.f: New test.

        PR fortran/30084
        * gfortran.dg/nested_modules_6.f90: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/entry_array_specs_2.f
    trunk/gcc/testsuite/gfortran.dg/nested_modules_6.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/gfortran.h
    trunk/gcc/fortran/module.c
    trunk/gcc/fortran/resolve.c
    trunk/gcc/fortran/trans-array.c
    trunk/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/25818] [4.2  and 4.1 only] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (20 preceding siblings ...)
  2006-12-22 20:49 ` pault at gcc dot gnu dot org
@ 2007-01-03 21:27 ` pault at gcc dot gnu dot org
  2007-01-03 21:30 ` [Bug fortran/25818] [4.1 " pault at gcc dot gnu dot org
  2007-01-10 19:06 ` pinskia at gcc dot gnu dot org
  23 siblings, 0 replies; 25+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-01-03 21:27 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #22 from pault at gcc dot gnu dot org  2007-01-03 21:27 -------
Subject: Bug 25818

Author: pault
Date: Wed Jan  3 21:27:17 2007
New Revision: 120399

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=120399
Log:
2007-01-03  Paul Thomas  <pault@gcc.gnu.org>

        Backport from trunk

        PR fortran/25818
        * trans-array.c (gfc_trans_g77_array): If the variable is
        optional or not always present, make the statement conditional
        on presence of the argument.
        * gfortran.h : Add symbol_attribute not_always_present.
        * resolve.c (check_argument_lists): New function to check if
        arguments are not present in all entries.

        PR fortran/30084
        * module.c (mio_component_ref): Move treatment of unique name
        variables, during output, to fix_mio_expr.
        (fix_mio_expr): New function that fixes defective expressions
        before they are written to the module file.
        (mio_expr): Call the new function.
        (resolve_entries): Call check_argument_lists.

2007-01-03  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/25818
        * gfortran.dg/entry_array_specs_2.f: New test.

        PR fortran/30084
        * gfortran.dg/nested_modules_6.f90: New test.

Added:
    branches/gcc-4_2-branch/gcc/testsuite/gfortran.dg/entry_array_specs_2.f
    branches/gcc-4_2-branch/gcc/testsuite/gfortran.dg/nested_modules_6.f90
Modified:
    branches/gcc-4_2-branch/gcc/fortran/ChangeLog
    branches/gcc-4_2-branch/gcc/fortran/gfortran.h
    branches/gcc-4_2-branch/gcc/fortran/module.c
    branches/gcc-4_2-branch/gcc/fortran/resolve.c
    branches/gcc-4_2-branch/gcc/fortran/trans-array.c
    branches/gcc-4_2-branch/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/25818] [4.1 only] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (21 preceding siblings ...)
  2007-01-03 21:27 ` [Bug fortran/25818] [4.2 and 4.1 only] " pault at gcc dot gnu dot org
@ 2007-01-03 21:30 ` pault at gcc dot gnu dot org
  2007-01-10 19:06 ` pinskia at gcc dot gnu dot org
  23 siblings, 0 replies; 25+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-01-03 21:30 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #23 from pault at gcc dot gnu dot org  2007-01-03 21:29 -------
Fixed on trunk and 4.2

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|ASSIGNED                    |RESOLVED
         Resolution|                            |FIXED
            Summary|[4.2  and 4.1 only] Problem |[4.1 only] Problem with
                   |with handling optional and  |handling optional and entry
                   |entry master arguments      |master arguments


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


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

* [Bug fortran/25818] [4.1 only] Problem with handling optional and entry master arguments
  2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
                   ` (22 preceding siblings ...)
  2007-01-03 21:30 ` [Bug fortran/25818] [4.1 " pault at gcc dot gnu dot org
@ 2007-01-10 19:06 ` pinskia at gcc dot gnu dot org
  23 siblings, 0 replies; 25+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2007-01-10 19:06 UTC (permalink / raw)
  To: gcc-bugs



-- 

pinskia at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Target Milestone|---                         |4.2.0


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


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

end of thread, other threads:[~2007-01-10 19:06 UTC | newest]

Thread overview: 25+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2006-01-17 14:35 [Bug fortran/25818] New: Problem with handling optional and entry master arguments jakub at gcc dot gnu dot org
2006-01-17 16:04 ` [Bug fortran/25818] " pinskia at gcc dot gnu dot org
2006-07-27 22:38 ` taschna at uni-muenster dot de
2006-07-30 22:47 ` kargl at gcc dot gnu dot org
2006-07-31  6:32 ` taschna at uni-muenster dot de
2006-07-31  7:49 ` taschna at uni-muenster dot de
2006-08-21 13:36 ` pault at gcc dot gnu dot org
2006-09-18 15:33 ` paul dot richard dot thomas at cea dot fr
2006-09-29  0:30 ` kargl at gcc dot gnu dot org
2006-10-12 12:31 ` pault at gcc dot gnu dot org
2006-10-12 12:46 ` jakub at gcc dot gnu dot org
2006-11-30 11:58 ` pinskia at gcc dot gnu dot org
2006-11-30 14:25 ` pault at gcc dot gnu dot org
2006-11-30 15:52 ` pault at gcc dot gnu dot org
2006-11-30 15:53 ` pault at gcc dot gnu dot org
2006-12-01 20:24 ` elizabeth dot l dot yip at boeing dot com
2006-12-02 17:56 ` paulthomas2 at wanadoo dot fr
2006-12-07  1:37 ` elizabeth dot l dot yip at boeing dot com
2006-12-07 17:34 ` paulthomas2 at wanadoo dot fr
2006-12-09 21:42 ` pault at gcc dot gnu dot org
2006-12-22  2:20 ` patchapp at dberlin dot org
2006-12-22 20:49 ` pault at gcc dot gnu dot org
2007-01-03 21:27 ` [Bug fortran/25818] [4.2 and 4.1 only] " pault at gcc dot gnu dot org
2007-01-03 21:30 ` [Bug fortran/25818] [4.1 " pault at gcc dot gnu dot org
2007-01-10 19:06 ` pinskia at gcc dot gnu dot org

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).