public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/31204]  New: wrong code generated with gfortran
@ 2007-03-16 11:28 jv244 at cam dot ac dot uk
  2007-03-16 20:53 ` [Bug fortran/31204] " fxcoudert at gcc dot gnu dot org
                   ` (4 more replies)
  0 siblings, 5 replies; 6+ messages in thread
From: jv244 at cam dot ac dot uk @ 2007-03-16 11:28 UTC (permalink / raw)
  To: gcc-bugs

With a recent gfortran, the following compiles, but generates the wrong
results:

       MODULE mod
       INTEGER, PARAMETER :: jmin(1:10) = (/ (i, i = 1, 10) /)
       CONTAINS

       SUBROUTINE one
         i = 99
       END SUBROUTINE

       SUBROUTINE two
         i=0
         CALL one
         IF (i.NE.0) CALL ABORT()
       END SUBROUTINE

       END MODULE
       USE MOD
       CALL two
       END


-- 
           Summary: wrong code generated with gfortran
           Product: gcc
           Version: 4.3.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: jv244 at cam dot ac dot uk


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


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

* [Bug fortran/31204] wrong code generated with gfortran
  2007-03-16 11:28 [Bug fortran/31204] New: wrong code generated with gfortran jv244 at cam dot ac dot uk
@ 2007-03-16 20:53 ` fxcoudert at gcc dot gnu dot org
  2007-04-06 11:50 ` [Bug fortran/31204] wrong host association of implied loop variable pault at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  4 siblings, 0 replies; 6+ messages in thread
From: fxcoudert at gcc dot gnu dot org @ 2007-03-16 20:53 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from fxcoudert at gcc dot gnu dot org  2007-03-16 20:53 -------
Confirmed.


-- 

fxcoudert at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
           Keywords|                            |wrong-code
      Known to fail|                            |4.1.3 4.2.0 4.3.0
   Last reconfirmed|0000-00-00 00:00:00         |2007-03-16 20:53:01
               date|                            |


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


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

* [Bug fortran/31204] wrong host association of implied loop variable
  2007-03-16 11:28 [Bug fortran/31204] New: wrong code generated with gfortran jv244 at cam dot ac dot uk
  2007-03-16 20:53 ` [Bug fortran/31204] " fxcoudert at gcc dot gnu dot org
@ 2007-04-06 11:50 ` pault at gcc dot gnu dot org
  2007-04-06 17:31 ` patchapp at dberlin dot org
                   ` (2 subsequent siblings)
  4 siblings, 0 replies; 6+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-04-06 11:50 UTC (permalink / raw)
  To: gcc-bugs

[-- Warning: decoded text below may be mangled, UTF-8 assumed --]
[-- Attachment #1: Type: text/plain, Size: 4396 bytes --]



------- Comment #2 from pault at gcc dot gnu dot org  2007-04-06 12:49 -------
This fixes it and half regtests(I got bored with the time that it was taking
with Chug_chugwin.).  I will regest tonight on something more spritely!

Paul

Index: gcc/fortran/decl.c
===================================================================
*** gcc/fortran/decl.c  (révision 123517)
--- gcc/fortran/decl.c  (copie de travail)
*************** build_sym (const char *name, gfc_charlen
*** 769,774 ****
--- 769,777 ----
    if (gfc_copy_attr (&sym->attr, &attr, var_locus) == FAILURE)
      return FAILURE;

+   /* Reset because symbol is not only declared implicitly as an implied
+      do loop index.  */
+   sym->attr.implied_index = 0;
    return SUCCESS;
  }

Index: gcc/fortran/gfortran.h
===================================================================
*** gcc/fortran/gfortran.h      (révision 123516)
--- gcc/fortran/gfortran.h      (copie de travail)
*************** typedef struct
*** 483,489 ****
    /* Variable attributes.  */
    unsigned allocatable:1, dimension:1, external:1, intrinsic:1,
      optional:1, pointer:1, save:1, target:1, value:1, volatile_:1,
!     dummy:1, result:1, assign:1, threadprivate:1, not_always_present:1;

    unsigned data:1,            /* Symbol is named in a DATA statement.  */
      protected:1,              /* Symbol has been marked as protected.  */
--- 483,490 ----
    /* Variable attributes.  */
    unsigned allocatable:1, dimension:1, external:1, intrinsic:1,
      optional:1, pointer:1, save:1, target:1, value:1, volatile_:1,
!     dummy:1, result:1, assign:1, threadprivate:1, not_always_present:1,
!     implied_index:1;

    unsigned data:1,            /* Symbol is named in a DATA statement.  */
      protected:1,              /* Symbol has been marked as protected.  */
Index: gcc/fortran/match.c
===================================================================
*** gcc/fortran/match.c (révision 123516)
--- gcc/fortran/match.c (copie de travail)
*************** gfc_match_iterator (gfc_iterator *iter, 
*** 536,541 ****
--- 536,543 ----
        goto cleanup;
      }

+   var->symtree->n.sym->attr.implied_index = 1;
+ 
    m = init_flag ? gfc_match_init_expr (&e1) : gfc_match_expr (&e1);
    if (m == MATCH_NO)
      goto syntax;
Index: gcc/fortran/primary.c
===================================================================
*** gcc/fortran/primary.c       (révision 123516)
--- gcc/fortran/primary.c       (copie de travail)
*************** gfc_match_rvalue (gfc_expr **result)
*** 2017,2023 ****
--- 2017,2038 ----
    e = NULL;
    where = gfc_current_locus;

+   /* If this is an implicit do loop index and implicitly typed,
+      it should not be host associated.  */
+   if (sym->attr.flavor == FL_VARIABLE
+       && sym->ns != gfc_current_ns
+       && sym->attr.implied_index
+       && sym->attr.implicit_type
+       && !sym->attr.use_assoc)
+     {
+       i = gfc_get_sym_tree (name, NULL, &symtree);
+       if (i)
+       return MATCH_ERROR;
+       sym = symtree->n.sym;
+     }
+ 
    gfc_set_sym_referenced (sym);
+   sym->attr.implied_index = 0;

    if (sym->attr.function && sym->result == sym)
      {
*************** match_variable (gfc_expr **result, int e
*** 2386,2391 ****
--- 2401,2424 ----
    where = gfc_current_locus;

    sym = st->n.sym;
+ 
+   /* If this is an implicit do loop index and implicitly typed,
+      it should not be host associated.  */
+   if (sym->ns != gfc_current_ns
+       && sym->attr.implied_index
+       && sym->attr.implicit_type
+       && !sym->attr.use_assoc)
+     {
+       int i;
+ 
+       i = gfc_get_sym_tree (sym->name, NULL, &st);
+       if (i)
+       return MATCH_ERROR;
+       sym = st->n.sym;
+     }
+ 
+   sym->attr.implied_index = 0;
+ 
    gfc_set_sym_referenced (sym);
    switch (sym->attr.flavor)
      {


-- 

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
   Last reconfirmed|2007-03-16 20:53:01         |2007-04-06 12:49:48
               date|                            |


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


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

* [Bug fortran/31204] wrong host association of implied loop variable
  2007-03-16 11:28 [Bug fortran/31204] New: wrong code generated with gfortran jv244 at cam dot ac dot uk
  2007-03-16 20:53 ` [Bug fortran/31204] " fxcoudert at gcc dot gnu dot org
  2007-04-06 11:50 ` [Bug fortran/31204] wrong host association of implied loop variable pault at gcc dot gnu dot org
@ 2007-04-06 17:31 ` patchapp at dberlin dot org
  2007-04-15 15:28 ` pault at gcc dot gnu dot org
  2007-04-21 22:15 ` pault at gcc dot gnu dot org
  4 siblings, 0 replies; 6+ messages in thread
From: patchapp at dberlin dot org @ 2007-04-06 17:31 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from patchapp at dberlin dot org  2007-04-06 18:30 -------
Subject: Bug number PR31204

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/2007-04/msg00276.html


-- 


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


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

* [Bug fortran/31204] wrong host association of implied loop variable
  2007-03-16 11:28 [Bug fortran/31204] New: wrong code generated with gfortran jv244 at cam dot ac dot uk
                   ` (2 preceding siblings ...)
  2007-04-06 17:31 ` patchapp at dberlin dot org
@ 2007-04-15 15:28 ` pault at gcc dot gnu dot org
  2007-04-21 22:15 ` pault at gcc dot gnu dot org
  4 siblings, 0 replies; 6+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-04-15 15:28 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from pault at gcc dot gnu dot org  2007-04-15 16:28 -------
Subject: Bug 31204

Author: pault
Date: Sun Apr 15 16:28:06 2007
New Revision: 123849

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

        PR fortran/31204
        * primary.c (check_for_implicit_index): New function to check
        that a host associated variable is not an undeclared implied
        do loop index.
        (gfc_match_rvalue, match_variable): Use it and reset the
        implied_index attribute.
        * gfortran.h : Add the implied_index field to symbol_attribute.
        * match.c (gfc_match_iterator): Mark the iterator variable
        with the new attribute.
        * decl.c (build_sym): Reset the new attribute.

2007-04-15  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/31204
        * gfortran.dg/array_constructor_16.f90: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/array_constructor_16.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/decl.c
    trunk/gcc/fortran/match.c
    trunk/gcc/fortran/primary.c
    trunk/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/31204] wrong host association of implied loop variable
  2007-03-16 11:28 [Bug fortran/31204] New: wrong code generated with gfortran jv244 at cam dot ac dot uk
                   ` (3 preceding siblings ...)
  2007-04-15 15:28 ` pault at gcc dot gnu dot org
@ 2007-04-21 22:15 ` pault at gcc dot gnu dot org
  4 siblings, 0 replies; 6+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-04-21 22:15 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from pault at gcc dot gnu dot org  2007-04-21 23:15 -------
fixed on trunk

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|ASSIGNED                    |RESOLVED
         Resolution|                            |FIXED


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


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

end of thread, other threads:[~2007-04-21 22:15 UTC | newest]

Thread overview: 6+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2007-03-16 11:28 [Bug fortran/31204] New: wrong code generated with gfortran jv244 at cam dot ac dot uk
2007-03-16 20:53 ` [Bug fortran/31204] " fxcoudert at gcc dot gnu dot org
2007-04-06 11:50 ` [Bug fortran/31204] wrong host association of implied loop variable pault at gcc dot gnu dot org
2007-04-06 17:31 ` patchapp at dberlin dot org
2007-04-15 15:28 ` pault at gcc dot gnu dot org
2007-04-21 22:15 ` pault 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).