public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/33686]  New: FORALL loop gives wrong result
@ 2007-10-08  7:17 enok at lysator dot liu dot se
  2007-10-08  9:13 ` [Bug fortran/33686] " pinskia at gcc dot gnu dot org
                   ` (13 more replies)
  0 siblings, 14 replies; 15+ messages in thread
From: enok at lysator dot liu dot se @ 2007-10-08  7:17 UTC (permalink / raw)
  To: gcc-bugs

A simple program that is supposed to invert a permutation P gives wrong result
with gfortran 4.2.1. A quite recent trunk 4.3 gfortran also gave wrong result.
See also discussion in comp.lang.fortran subject "Most elegant syntax for
inverting a permutation?". The concensus seems to be that this forall construct
should work according to the standard.

PROGRAM TST
  IMPLICIT NONE

  INTEGER :: P(4),I
  P = (/2,4,1,3/)
  FORALL(I=1:4)
    P(P(I)) = I
  END FORALL
  PRINT *, P

END PROGRAM TST

enok@home:~/> gfortran421 -o tst tst.f90 -static && ./tst
           3           1           4           3
enok@home:~/> ifort -o tst tst.f90 && ./tst
tst.f90(5): (col. 3) remark: LOOP WAS VECTORIZED.
           3           1           4           2
enok@home:~/>


-- 
           Summary: FORALL loop gives wrong result
           Product: gcc
           Version: 4.2.1
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: enok at lysator dot liu dot se
 GCC build triplet: x86_64-unknown-linux-gnu
  GCC host triplet: x86_64-unknown-linux-gnu
GCC target triplet: x86_64-unknown-linux-gnu


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


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

* [Bug fortran/33686] FORALL loop gives wrong result
  2007-10-08  7:17 [Bug fortran/33686] New: FORALL loop gives wrong result enok at lysator dot liu dot se
@ 2007-10-08  9:13 ` pinskia at gcc dot gnu dot org
  2007-10-08  9:42 ` enok at lysator dot liu dot se
                   ` (12 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2007-10-08  9:13 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from pinskia at gcc dot gnu dot org  2007-10-08 09:13 -------
I thought modifying a variable while acessing the same one in a forall loop was
undefined behavior. 


-- 


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


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

* [Bug fortran/33686] FORALL loop gives wrong result
  2007-10-08  7:17 [Bug fortran/33686] New: FORALL loop gives wrong result enok at lysator dot liu dot se
  2007-10-08  9:13 ` [Bug fortran/33686] " pinskia at gcc dot gnu dot org
@ 2007-10-08  9:42 ` enok at lysator dot liu dot se
  2007-10-08 11:28 ` burnus at gcc dot gnu dot org
                   ` (11 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: enok at lysator dot liu dot se @ 2007-10-08  9:42 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from enok at lysator dot liu dot se  2007-10-08 09:42 -------
Do you mean the fact that assignment expressions within a forall loop may be
executed in any order? But within a single assignment it seems that the right
hand side and any expressions within the left hand side must be evaluated
before any assignments take place. I quote Dick Hendrickson in
comp.lang.fortran in the thread "Most elegant syntax for inverting a
permutation?":

The form of an assignment statement is
     variable = expr

In 7.4.4.2.3, execution of FORALL, it says
"Execution of a forall-assignment-stmt that is an assignment-stmt causes
the evaluation of expr and all expressions within variable for all
active combinations of index-name values. These evaluations may be
done in any order. After all these evaluations have been performed, each
expr value is assigned to the corresponding variable. The assignments
may occur in any order."

In 7.4.1.3  interpretation of intrinsic assignment, it says
"Execution of an intrinsic assignment causes, in effect, the evaluation
of the expression expr and all expressions within variable (7.1.8), the
possible conversion of expr to the type and type parameters
of variable (Table 7.9), and the definition of variable with the
resulting value. The execution of the assignment shall have the same
effect as if the evaluation of all operations in expr and variable
occurred before any portion of variable is defined by the assignment."


-- 


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


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

* [Bug fortran/33686] FORALL loop gives wrong result
  2007-10-08  7:17 [Bug fortran/33686] New: FORALL loop gives wrong result enok at lysator dot liu dot se
  2007-10-08  9:13 ` [Bug fortran/33686] " pinskia at gcc dot gnu dot org
  2007-10-08  9:42 ` enok at lysator dot liu dot se
@ 2007-10-08 11:28 ` burnus at gcc dot gnu dot org
  2007-10-08 12:05 ` dominiq at lps dot ens dot fr
                   ` (10 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-10-08 11:28 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from burnus at gcc dot gnu dot org  2007-10-08 11:28 -------
> A simple program that is supposed to invert a permutation P gives wrong result
> with gfortran 4.2.1. A quite recent trunk 4.3 gfortran also gave wrong result.

I get 3, 1, 4, 3 with:
- NAG f95
- g95
- openf95
- gfortran 4.1.3 20070724; 4.2.1; 4.2.2 20070927; 4.3.0 20071008 [Rev.129121]

and 3, 1, 4, 2 with:
- ifort 9.1 and 10.0
- sunf95 (Sunstudio 11 and 12)

Now we need only to find out which compiler is right and whether the program
itself is valid. Cf. also
http://groups.google.com/group/comp.lang.fortran/browse_thread/thread/4537f1930bd87acb


-- 

burnus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |burnus at gcc dot gnu dot
                   |                            |org


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


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

* [Bug fortran/33686] FORALL loop gives wrong result
  2007-10-08  7:17 [Bug fortran/33686] New: FORALL loop gives wrong result enok at lysator dot liu dot se
                   ` (2 preceding siblings ...)
  2007-10-08 11:28 ` burnus at gcc dot gnu dot org
@ 2007-10-08 12:05 ` dominiq at lps dot ens dot fr
  2007-10-08 12:16 ` burnus at gcc dot gnu dot org
                   ` (9 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: dominiq at lps dot ens dot fr @ 2007-10-08 12:05 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from dominiq at lps dot ens dot fr  2007-10-08 12:05 -------
You can add xlf to the (3, 1, 4, 2) list. I think this is the right answer.
The following code

PROGRAM TST
  IMPLICIT NONE

  INTEGER :: P(4),Q(4),I
  P = (/2,4,1,3/)
  FORALL(I=1:4)
    Q(P(I)) = I
  END FORALL
  PRINT *, Q

  do I=1,4
    Q(P(I)) = I
  END  do
  PRINT *, Q

  do I=4,1,-1
    Q(P(I)) = I
  END  do
  PRINT *, Q

  FORALL(I=1:4)
    P(P(I)) = I
  END FORALL
  PRINT *, P

  do I=1,4
    P(P(I)) = I
  END  do
  PRINT *, P

  do I=4,1,-1
    P(P(I)) = I
  END  do
  PRINT *, P

END PROGRAM TST

gives with gfortran

           3           1           4           2
           3           1           4           2
           3           1           4           2
           3           1           4           3
           3           1           4           3
           2           1           4           3

My understanding of the FORALL construct is that it is equivalent to any of the
first three loops, followed by P=Q, i.e., P is changed only when all the Q's
have been computed.  Comparing the fourth and fifth lines show that P is
changed within the FORALL before all the rhs has been visited and the sixth
line shows that this depends on the order of their computation.

Note that the code is valid only if P is a permutation. Would it contains a
single repetition, say (/2,4,1,2/), it would be invalid because Q(2) depends on
the order (4 for the first do loop, 1 for the second).


-- 


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


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

* [Bug fortran/33686] FORALL loop gives wrong result
  2007-10-08  7:17 [Bug fortran/33686] New: FORALL loop gives wrong result enok at lysator dot liu dot se
                   ` (3 preceding siblings ...)
  2007-10-08 12:05 ` dominiq at lps dot ens dot fr
@ 2007-10-08 12:16 ` burnus at gcc dot gnu dot org
  2007-10-08 19:03 ` pault at gcc dot gnu dot org
                   ` (8 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-10-08 12:16 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from burnus at gcc dot gnu dot org  2007-10-08 12:15 -------
> Now we need only to find out which compiler is right and whether the program
> itself is valid.
After some contemplating, I agree that the program is valid (let's see whether
NAG's support agrees as well).


-- 

burnus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
OtherBugsDependingO|                            |32834
              nThis|                            |
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
  GCC build triplet|x86_64-unknown-linux-gnu    |
   GCC host triplet|x86_64-unknown-linux-gnu    |
 GCC target triplet|x86_64-unknown-linux-gnu    |
           Keywords|                            |wrong-code
      Known to fail|                            |4.1.3 4.2.1 4.3.0
   Last reconfirmed|0000-00-00 00:00:00         |2007-10-08 12:15:58
               date|                            |


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


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

* [Bug fortran/33686] FORALL loop gives wrong result
  2007-10-08  7:17 [Bug fortran/33686] New: FORALL loop gives wrong result enok at lysator dot liu dot se
                   ` (4 preceding siblings ...)
  2007-10-08 12:16 ` burnus at gcc dot gnu dot org
@ 2007-10-08 19:03 ` pault at gcc dot gnu dot org
  2007-10-08 20:03 ` pault at gcc dot gnu dot org
                   ` (7 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-10-08 19:03 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from pault at gcc dot gnu dot org  2007-10-08 19:03 -------
(In reply to comment #5)
> > Now we need only to find out which compiler is right and whether the program
> > itself is valid.
> After some contemplating, I agree that the program is valid (let's see whether
> NAG's support agrees as well).
> 
Dick Hendrickson was quite right.  The standard is unequivocal that not only is
this valid code but the dependency has to be resolved.

Cheers

Paul


-- 


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


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

* [Bug fortran/33686] FORALL loop gives wrong result
  2007-10-08  7:17 [Bug fortran/33686] New: FORALL loop gives wrong result enok at lysator dot liu dot se
                   ` (5 preceding siblings ...)
  2007-10-08 19:03 ` pault at gcc dot gnu dot org
@ 2007-10-08 20:03 ` pault at gcc dot gnu dot org
  2007-10-10  6:50 ` pault at gcc dot gnu dot org
                   ` (6 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-10-08 20:03 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from pault at gcc dot gnu dot org  2007-10-08 20:02 -------
(In reply to comment #6)
Oh dear, oh dear, we are going to have to implement

PROGRAM TST
  IMPLICIT NONE

  INTEGER :: P(4),I
  integer, allocatable :: Q(:)
  P = (/2,4,1,3/)
  allocate (Q(size(P)))
  FORALL(I=1:4)
    Q(P(I)) = I
  END FORALL
  P = Q
  deallocate (Q)
  PRINT *, P

END PROGRAM TST

when the dependency is detected.  In fact, this should not be too bad. It can
be entirely enclosed within trans-stmt.c(generate_loop_for_temp_to_lhs). I have
some hotel room time coming up....

Paul


-- 


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


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

* [Bug fortran/33686] FORALL loop gives wrong result
  2007-10-08  7:17 [Bug fortran/33686] New: FORALL loop gives wrong result enok at lysator dot liu dot se
                   ` (6 preceding siblings ...)
  2007-10-08 20:03 ` pault at gcc dot gnu dot org
@ 2007-10-10  6:50 ` pault at gcc dot gnu dot org
  2007-10-10  9:35 ` dominiq at lps dot ens dot fr
                   ` (5 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-10-10  6:50 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from pault at gcc dot gnu dot org  2007-10-10 06:50 -------
(In reply to comment #7)
Hmmm, that's not right, is it?  It should be
PROGRAM TST
  IMPLICIT NONE

  INTEGER :: P(4),I
  integer, allocatable :: Q(:)
  P = (/2,4,1,3/)
  allocate (Q(size(P)))
  Q = P
  FORALL(I=1:4)
    P(Q(I)) = I
  END FORALL
  deallocate (Q)
  PRINT *, P

END PROGRAM TST


-- 


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


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

* [Bug fortran/33686] FORALL loop gives wrong result
  2007-10-08  7:17 [Bug fortran/33686] New: FORALL loop gives wrong result enok at lysator dot liu dot se
                   ` (7 preceding siblings ...)
  2007-10-10  6:50 ` pault at gcc dot gnu dot org
@ 2007-10-10  9:35 ` dominiq at lps dot ens dot fr
  2007-10-12 13:26 ` pault at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: dominiq at lps dot ens dot fr @ 2007-10-10  9:35 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from dominiq at lps dot ens dot fr  2007-10-10 09:35 -------
Are the codes in #7 and #8 supposed to behave differently?


-- 


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


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

* [Bug fortran/33686] FORALL loop gives wrong result
  2007-10-08  7:17 [Bug fortran/33686] New: FORALL loop gives wrong result enok at lysator dot liu dot se
                   ` (8 preceding siblings ...)
  2007-10-10  9:35 ` dominiq at lps dot ens dot fr
@ 2007-10-12 13:26 ` pault at gcc dot gnu dot org
  2007-10-12 13:47 ` dominiq at lps dot ens dot fr
                   ` (3 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-10-12 13:26 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #10 from pault at gcc dot gnu dot org  2007-10-12 13:26 -------
(In reply to comment #9)
> Are the codes in #7 and #8 supposed to behave differently?


In the case where the FORALL only fills part of the array P, yes.

Paul

PS I am just about to prepare a corresponding PR for assignments.


-- 


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


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

* [Bug fortran/33686] FORALL loop gives wrong result
  2007-10-08  7:17 [Bug fortran/33686] New: FORALL loop gives wrong result enok at lysator dot liu dot se
                   ` (9 preceding siblings ...)
  2007-10-12 13:26 ` pault at gcc dot gnu dot org
@ 2007-10-12 13:47 ` dominiq at lps dot ens dot fr
  2007-10-24 10:00 ` pault at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: dominiq at lps dot ens dot fr @ 2007-10-12 13:47 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #11 from dominiq at lps dot ens dot fr  2007-10-12 13:47 -------
> In the case where the FORALL only fills part of the array P, yes.

If you mean, say "FORALL(I=2:3)", you are right! I overlooked this possibility.


-- 


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


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

* [Bug fortran/33686] FORALL loop gives wrong result
  2007-10-08  7:17 [Bug fortran/33686] New: FORALL loop gives wrong result enok at lysator dot liu dot se
                   ` (10 preceding siblings ...)
  2007-10-12 13:47 ` dominiq at lps dot ens dot fr
@ 2007-10-24 10:00 ` pault at gcc dot gnu dot org
  2007-10-29 14:14 ` burnus at gcc dot gnu dot org
  2007-10-29 14:15 ` burnus at gcc dot gnu dot org
  13 siblings, 0 replies; 15+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-10-24 10:00 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #12 from pault at gcc dot gnu dot org  2007-10-24 10:00 -------
I have prototype fix for this which works OK and does not break anything.  It
copies 'p' to a temporary before the FORALL and uses the temporary for the
references.  This method will also cure the problem with character substring
dependences but I have not tested it yet.

This fix will not be very efficient in cases where the FORALL only visits a
small subsection of the 'value' variable but I can see no straightforward of
handling the generality of dependences in the 'value' references.

Watch this space - a "one size fits all" patch for the FORALL and assignment
woes is on its way.

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
   Last reconfirmed|2007-10-08 12:15:58         |2007-10-24 10:00:19
               date|                            |


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


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

* [Bug fortran/33686] FORALL loop gives wrong result
  2007-10-08  7:17 [Bug fortran/33686] New: FORALL loop gives wrong result enok at lysator dot liu dot se
                   ` (11 preceding siblings ...)
  2007-10-24 10:00 ` pault at gcc dot gnu dot org
@ 2007-10-29 14:14 ` burnus at gcc dot gnu dot org
  2007-10-29 14:15 ` burnus at gcc dot gnu dot org
  13 siblings, 0 replies; 15+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-10-29 14:14 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #13 from burnus at gcc dot gnu dot org  2007-10-29 14:14 -------
Subject: Bug 33686

Author: burnus
Date: Mon Oct 29 14:13:44 2007
New Revision: 129720

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

        PR fortran/31217
        PR fortran/33811
        PR fortran/33686
        * trans-array.c (gfc_conv_loop_setup): Send a complete type to
        gfc_trans_create_temp_array if the temporary is character.
        * trans-stmt.c (gfc_trans_assign_need_temp): Do likewise for
        allocate_temp_for_forall_nest.
        (forall_replace): New function.
        (forall_replace_symtree): New function.
        (forall_restore): New function.
        (forall_restore_symtree): New function.
        (forall_make_variable_temp): New function.
        (check_forall_dependencies): New function.
        (cleanup_forall_symtrees): New function.
        gfc_trans_forall_1): Add and initialize pre and post blocks.
        Call check_forall_dependencies to check for all dependencies
        and either trigger second forall block to copy temporary or
        copy lval, outside the forall construct and replace all
        dependent references. After assignment clean-up and coalesce
        the blocks at the end of the function.
        * gfortran.h : Add prototypes for gfc_traverse_expr and
        find_forall_index.
        expr.c (gfc_traverse_expr): New function to traverse expression
        and visit all subexpressions, under control of a logical flag,
        a symbol and an integer pointer. The slave function is caller
        defined and is only called on EXPR_VARIABLE.
        (expr_set_symbols_referenced): Called by above to set symbols
        referenced.
        (gfc_expr_set_symbols_referenced): Rework of this function to
        use two new functions above.
        * resolve.c (find_forall_index): Rework with gfc_traverse_expr,
        using forall_index.
        (forall_index): New function used by previous.
        * dependency.c (gfc_check_dependency): Use gfc_dep_resolver for
        all references, not just REF_ARRAY.
        (gfc_dep_resolver): Correct the logic for substrings so that
        overlapping arrays are handled correctly.

2007-10-29 Paul Thomas <pault@gcc.gnu.org>

        PR fortran/31217
        PR fortran/33811
        * gfortran.dg/forall_12.f90: New test.

        PR fortran/33686
        * gfortran.dg/forall_13.f90: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/forall_12.f90
    trunk/gcc/testsuite/gfortran.dg/forall_13.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/dependency.c
    trunk/gcc/fortran/expr.c
    trunk/gcc/fortran/gfortran.h
    trunk/gcc/fortran/resolve.c
    trunk/gcc/fortran/trans-array.c
    trunk/gcc/fortran/trans-stmt.c
    trunk/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/33686] FORALL loop gives wrong result
  2007-10-08  7:17 [Bug fortran/33686] New: FORALL loop gives wrong result enok at lysator dot liu dot se
                   ` (12 preceding siblings ...)
  2007-10-29 14:14 ` burnus at gcc dot gnu dot org
@ 2007-10-29 14:15 ` burnus at gcc dot gnu dot org
  13 siblings, 0 replies; 15+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-10-29 14:15 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #14 from burnus at gcc dot gnu dot org  2007-10-29 14:15 -------
Fixed on the trunk (4.3.0).


-- 

burnus at gcc dot gnu dot org changed:

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


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


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

end of thread, other threads:[~2007-10-29 14:15 UTC | newest]

Thread overview: 15+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2007-10-08  7:17 [Bug fortran/33686] New: FORALL loop gives wrong result enok at lysator dot liu dot se
2007-10-08  9:13 ` [Bug fortran/33686] " pinskia at gcc dot gnu dot org
2007-10-08  9:42 ` enok at lysator dot liu dot se
2007-10-08 11:28 ` burnus at gcc dot gnu dot org
2007-10-08 12:05 ` dominiq at lps dot ens dot fr
2007-10-08 12:16 ` burnus at gcc dot gnu dot org
2007-10-08 19:03 ` pault at gcc dot gnu dot org
2007-10-08 20:03 ` pault at gcc dot gnu dot org
2007-10-10  6:50 ` pault at gcc dot gnu dot org
2007-10-10  9:35 ` dominiq at lps dot ens dot fr
2007-10-12 13:26 ` pault at gcc dot gnu dot org
2007-10-12 13:47 ` dominiq at lps dot ens dot fr
2007-10-24 10:00 ` pault at gcc dot gnu dot org
2007-10-29 14:14 ` burnus at gcc dot gnu dot org
2007-10-29 14:15 ` burnus 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).