public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/41872]  New: wrong-code: No auto-deallocation for INTENT(OUT) allocatable scalars
@ 2009-10-29 21:58 burnus at gcc dot gnu dot org
  2009-10-29 22:52 ` [Bug fortran/41872] " burnus at gcc dot gnu dot org
                   ` (12 more replies)
  0 siblings, 13 replies; 14+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-10-29 21:58 UTC (permalink / raw)
  To: gcc-bugs

The following programs shows that the automatic deallocation is not applied to
allocatable INTENT(OUT) scalar dummies. It works for array arguments.

Note: For optional arguments, one needs to make sure that the deallocation only
happens if the variable is present, cf. PR 41850.

program test
  implicit none
  integer, allocatable :: a
  allocate(a)
  call foo(a)
  if(.not. allocated(a)) call abort()
  if (a /= 5) call abort()
contains
  subroutine foo(a)
    integer, allocatable, intent(out) :: a
    if(allocated(a)) call abort()
    allocate(a)
    a = 5
  end subroutine foo
end program test


-- 
           Summary: wrong-code: No auto-deallocation for INTENT(OUT)
                    allocatable scalars
           Product: gcc
           Version: 4.5.0
            Status: UNCONFIRMED
          Keywords: wrong-code
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: burnus at gcc dot gnu dot org


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


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

* [Bug fortran/41872] wrong-code: No auto-deallocation for INTENT(OUT) allocatable scalars
  2009-10-29 21:58 [Bug fortran/41872] New: wrong-code: No auto-deallocation for INTENT(OUT) allocatable scalars burnus at gcc dot gnu dot org
@ 2009-10-29 22:52 ` burnus at gcc dot gnu dot org
  2009-10-30 22:26 ` burnus at gcc dot gnu dot org
                   ` (11 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-10-29 22:52 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from burnus at gcc dot gnu dot org  2009-10-29 22:52 -------
Note: For arrays, the following block of trans-expr.c is used:

              /* If an ALLOCATABLE dummy argument has INTENT(OUT) and is
                 allocated on entry, it must be deallocated.  */
              if (fsym && fsym->attr.allocatable
                  && fsym->attr.intent == INTENT_OUT)


-- 


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


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

* [Bug fortran/41872] wrong-code: No auto-deallocation for INTENT(OUT) allocatable scalars
  2009-10-29 21:58 [Bug fortran/41872] New: wrong-code: No auto-deallocation for INTENT(OUT) allocatable scalars burnus at gcc dot gnu dot org
  2009-10-29 22:52 ` [Bug fortran/41872] " burnus at gcc dot gnu dot org
@ 2009-10-30 22:26 ` burnus at gcc dot gnu dot org
  2009-11-01 16:08 ` [Bug fortran/41872] wrong-code: Issues with " burnus at gcc dot gnu dot org
                   ` (10 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-10-30 22:26 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from burnus at gcc dot gnu dot org  2009-10-30 22:26 -------
Other things to check:
- Allocate/deallocate: works? Gives an error when needed?
- Allocatable DT with allocatable components (init when allocating; auto
dealloc when going out of scope and for intent(out))
- Default init with NULL pointer
- passing to allocatable dummies
- optional dummies
- intent(out)
- Adding tests ...


-- 


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


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

* [Bug fortran/41872] wrong-code: Issues with allocatable scalars
  2009-10-29 21:58 [Bug fortran/41872] New: wrong-code: No auto-deallocation for INTENT(OUT) allocatable scalars burnus at gcc dot gnu dot org
  2009-10-29 22:52 ` [Bug fortran/41872] " burnus at gcc dot gnu dot org
  2009-10-30 22:26 ` burnus at gcc dot gnu dot org
@ 2009-11-01 16:08 ` burnus at gcc dot gnu dot org
  2009-11-01 17:47 ` burnus at gcc dot gnu dot org
                   ` (9 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-11-01 16:08 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from burnus at gcc dot gnu dot org  2009-11-01 16:08 -------
First patch: http://gcc.gnu.org/ml/fortran/2009-11/msg00001.html

TODO:

* For ALLOCATABLE, OPTIONAL" dummies: If the argument is present but not
allocated, "PRESENT()" returns false. As test case add the lines
  deallocate(b)
  call checkOptional(.true., .false., 7482, b)
at the end of the main program of allocatable_scalar_4.f90 (cf. patch).

* Explicit Allocate/Deallocate calls do not fail if the variable is already
(de)allocated.

To check:
> - Default init with NULL pointer
> - Allocatable DT with allocatable components (init when allocating; auto
> dealloc when going out of scope and for intent(out))

The following program fails:

subroutine test()
  integer, allocatable, save :: a
  if(.not. allocated(a)) then
    allocate(a)
    a = 42
  else
    if (.not. allocated(a)) call abort()
    if (a /= 42) call abort()
  end if
end subroutine test

call test()
call test()
end


-- 

burnus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
            Summary|wrong-code: No auto-        |wrong-code: Issues with
                   |deallocation for INTENT(OUT)|allocatable scalars
                   |allocatable scalars         |


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


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

* [Bug fortran/41872] wrong-code: Issues with allocatable scalars
  2009-10-29 21:58 [Bug fortran/41872] New: wrong-code: No auto-deallocation for INTENT(OUT) allocatable scalars burnus at gcc dot gnu dot org
                   ` (2 preceding siblings ...)
  2009-11-01 16:08 ` [Bug fortran/41872] wrong-code: Issues with " burnus at gcc dot gnu dot org
@ 2009-11-01 17:47 ` burnus at gcc dot gnu dot org
  2009-11-01 20:47 ` burnus at gcc dot gnu dot org
                   ` (8 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-11-01 17:47 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from burnus at gcc dot gnu dot org  2009-11-01 17:47 -------
Subject: Bug 41872

Author: burnus
Date: Sun Nov  1 17:46:50 2009
New Revision: 153795

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=153795
Log:
2009-11-01  Tobias Burnus  <burnus@net-b.de>                                    

        PR fortran/41872
        * trans-decl.c (gfc_trans_deferred_vars): Do not nullify
        autodeallocated allocatable scalars at the end of scope.
        (gfc_generate_function_code): Fix indention.
        * trans-expr.c (gfc_conv_procedure_call): For allocatable
        scalars, fix calling by reference and autodeallocating
        of intent out variables.

2009-11-01  Tobias Burnus  <burnus@net-b.de>

        PR fortran/41872
        * gfortran.dg/allocatable_scalar_4.f90: New test.


Added:
    trunk/gcc/testsuite/gfortran.dg/allocatable_scalar_4.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/trans-decl.c
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/41872] wrong-code: Issues with allocatable scalars
  2009-10-29 21:58 [Bug fortran/41872] New: wrong-code: No auto-deallocation for INTENT(OUT) allocatable scalars burnus at gcc dot gnu dot org
                   ` (3 preceding siblings ...)
  2009-11-01 17:47 ` burnus at gcc dot gnu dot org
@ 2009-11-01 20:47 ` burnus at gcc dot gnu dot org
  2009-12-15  3:02 ` jvdelisle at gcc dot gnu dot org
                   ` (7 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-11-01 20:47 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from burnus at gcc dot gnu dot org  2009-11-01 20:46 -------
SAVE problem: Simply adding (!sym->attr.save && (... || ...)) to
gfc_trans_deferred_vars does not work as one then reaches "unreachable()"; one 
should check where SAVE is handles for allocatable arrays, which is presumably
before gfc_trans_deferred_vars is called.

 * * *

Need to add a test for:
  integer, allocatable :: a
  allocate(a)
  deallocate(a)
  deallocate(a) ! ERROR
  end
(This works already.)

And a test for
  integer, allocatable :: a
  allocate(a)
  allocate(a) ! ERROR
  end
which doesn't work. (If it were, the following would not happen.)

There is no default initialization to NULL; thus the following crashes:
  integer, allocatable :: a
  if (allocated(a)) call abort()
  end

 * * *

One needs to also add tests for TYPE (incl. default initializer), for CLASS,
and for TYPE/CLASS with allocatable components. (SAVE, optional, intent(out),
allocate/deallocate statements, automatic deallocation...) 


-- 


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


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

* [Bug fortran/41872] wrong-code: Issues with allocatable scalars
  2009-10-29 21:58 [Bug fortran/41872] New: wrong-code: No auto-deallocation for INTENT(OUT) allocatable scalars burnus at gcc dot gnu dot org
                   ` (4 preceding siblings ...)
  2009-11-01 20:47 ` burnus at gcc dot gnu dot org
@ 2009-12-15  3:02 ` jvdelisle at gcc dot gnu dot org
  2009-12-30  0:20 ` burnus at gcc dot gnu dot org
                   ` (6 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: jvdelisle at gcc dot gnu dot org @ 2009-12-15  3:02 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from jvdelisle at gcc dot gnu dot org  2009-12-15 03:02 -------
I have started looking at this.


-- 


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


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

* [Bug fortran/41872] wrong-code: Issues with allocatable scalars
  2009-10-29 21:58 [Bug fortran/41872] New: wrong-code: No auto-deallocation for INTENT(OUT) allocatable scalars burnus at gcc dot gnu dot org
                   ` (5 preceding siblings ...)
  2009-12-15  3:02 ` jvdelisle at gcc dot gnu dot org
@ 2009-12-30  0:20 ` burnus at gcc dot gnu dot org
  2009-12-30 20:50 ` burnus at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-12-30  0:20 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from burnus at gcc dot gnu dot org  2009-12-30 00:20 -------
Created an attachment (id=19421)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=19421&action=view)
Patch

- Nullifies local variables
- Fixes double-allocation check in ALLOCATE statement

TODO:
- INTENT(OUT) variables do not get initialized
- SAVED local variables are (probably) mishandled
- Check whether other things such as allocatable scalar components,
(absent/present) optional dummys etc. work.


-- 


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


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

* [Bug fortran/41872] wrong-code: Issues with allocatable scalars
  2009-10-29 21:58 [Bug fortran/41872] New: wrong-code: No auto-deallocation for INTENT(OUT) allocatable scalars burnus at gcc dot gnu dot org
                   ` (6 preceding siblings ...)
  2009-12-30  0:20 ` burnus at gcc dot gnu dot org
@ 2009-12-30 20:50 ` burnus at gcc dot gnu dot org
  2010-01-04  7:31 ` burnus at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-12-30 20:50 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from burnus at gcc dot gnu dot org  2009-12-30 20:50 -------
TODO:
> - SAVED local variables are (probably) mishandled
> - Check whether other things such as allocatable scalar components,
> (absent/present) optional dummys etc. work.
- allocatable-scalar returning functions as actual argument
- character-returning actual arguments

Check whether the following patch is needed or nonsense:

--- gcc/fortran/trans-expr.c    (Revision 155510)
+++ gcc/fortran/trans-expr.c
@@ -1905,7 +1905,7 @@ gfc_add_interface_mapping (gfc_interface
     {
       tmp = gfc_get_character_type_len (sym->ts.kind, NULL);
       tmp = build_pointer_type (tmp);
-      if (sym->attr.pointer)
+      if (sym->attr.pointer || sym->attr.allocatable)
         value = build_fold_indirect_ref_loc (input_location,
                                         se->expr);
       else
@@ -4478,10 +4479,12 @@ gfc_conv_expr_reference (gfc_se * se, gf

   if (expr->expr_type == EXPR_FUNCTION
       && ((expr->value.function.esym
-          && expr->value.function.esym->result->attr.pointer
+          && (expr->value.function.esym->result->attr.pointer
+              || expr->value.function.esym->result->attr.allocatable)
           && !expr->value.function.esym->result->attr.dimension)
          || (!expr->value.function.esym
-             && expr->symtree->n.sym->attr.pointer
+             && (expr->symtree->n.sym->attr.pointer
+                 || expr->symtree->n.sym->attr.allocatable)
              && !expr->symtree->n.sym->attr.dimension)))
     {
       se->want_pointer = 1;


-- 


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


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

* [Bug fortran/41872] wrong-code: Issues with allocatable scalars
  2009-10-29 21:58 [Bug fortran/41872] New: wrong-code: No auto-deallocation for INTENT(OUT) allocatable scalars burnus at gcc dot gnu dot org
                   ` (7 preceding siblings ...)
  2009-12-30 20:50 ` burnus at gcc dot gnu dot org
@ 2010-01-04  7:31 ` burnus at gcc dot gnu dot org
  2010-01-04  7:43 ` burnus at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: burnus at gcc dot gnu dot org @ 2010-01-04  7:31 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from burnus at gcc dot gnu dot org  2010-01-04 07:31 -------
Subject: Bug 41872

Author: burnus
Date: Mon Jan  4 07:30:49 2010
New Revision: 155606

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=155606
Log:
2009-01-04  Tobias Burnus  <burnus@net-b.de>

        PR fortran/41872
        * trans-expr.c (gfc_conv_procedure_call): Add indirect ref
        for functions returning allocatable scalars.
        * trans-stmt.c (gfc_trans_allocate): Emmit error when
        reallocating an allocatable scalar.
        * trans.c (gfc_allocate_with_status): Fix pseudocode syntax
        in comment.
        * trans-decl.c (gfc_trans_deferred_vars): Nullify local
        allocatable scalars.
        (gfc_generate_function_code): Nullify result variable for
        allocatable scalars.

        PR fortran/40849
        * module.c (gfc_use_module): Fix warning string to allow
        for translation.

        PR fortran/42517
        * invoke.texi (-fcheck=recursion): Mention that the checking
        is also disabled for -frecursive.
        * trans-decl.c (gfc_generate_function_code): Disable
        -fcheck=recursion when -frecursive is used.

        * intrinsic.texi (iso_c_binding): Improve wording.

2009-01-04  Tobias Burnus  <burnus@net-b.de>

        PR fortran/41872
        * gfortran.dg/allocatable_scalar_5.f90: New test.
        * gfortran.dg/allocatable_scalar_6.f90: New test.


Added:
    trunk/gcc/testsuite/gfortran.dg/allocatable_scalar_5.f90
    trunk/gcc/testsuite/gfortran.dg/allocatable_scalar_6.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/intrinsic.texi
    trunk/gcc/fortran/invoke.texi
    trunk/gcc/fortran/module.c
    trunk/gcc/fortran/trans-decl.c
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/fortran/trans-stmt.c
    trunk/gcc/fortran/trans.c
    trunk/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/41872] wrong-code: Issues with allocatable scalars
  2009-10-29 21:58 [Bug fortran/41872] New: wrong-code: No auto-deallocation for INTENT(OUT) allocatable scalars burnus at gcc dot gnu dot org
                   ` (8 preceding siblings ...)
  2010-01-04  7:31 ` burnus at gcc dot gnu dot org
@ 2010-01-04  7:43 ` burnus at gcc dot gnu dot org
  2010-01-05  7:19 ` burnus at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: burnus at gcc dot gnu dot org @ 2010-01-04  7:43 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #10 from burnus at gcc dot gnu dot org  2010-01-04 07:43 -------
Still TO DO:
 - SAVED local variables are (probably) mishandled
 - Check whether other things such as allocatable scalar components,
 (absent/present) optional dummys etc. work.
- allocatable-scalar returning functions as actual argument
- character-returning actual arguments


-- 


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


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

* [Bug fortran/41872] wrong-code: Issues with allocatable scalars
  2009-10-29 21:58 [Bug fortran/41872] New: wrong-code: No auto-deallocation for INTENT(OUT) allocatable scalars burnus at gcc dot gnu dot org
                   ` (9 preceding siblings ...)
  2010-01-04  7:43 ` burnus at gcc dot gnu dot org
@ 2010-01-05  7:19 ` burnus at gcc dot gnu dot org
  2010-01-07  8:10 ` burnus at gcc dot gnu dot org
  2010-01-07  8:12 ` burnus at gcc dot gnu dot org
  12 siblings, 0 replies; 14+ messages in thread
From: burnus at gcc dot gnu dot org @ 2010-01-05  7:19 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #11 from burnus at gcc dot gnu dot org  2010-01-05 07:19 -------
Subject: Bug 41872

Author: burnus
Date: Tue Jan  5 07:19:30 2010
New Revision: 155639

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=155639
Log:
2010-01-05  Tobias Burnus  <burnus@net-b.de>

        PR fortran/41872
        * trans-expr.c (gfc_conv_procedure_call): Nullify
        return value for allocatable-scalar character functions.

2010-01-05  Tobias Burnus  <burnus@net-b.de>

        PR fortran/41872
        * gfortran.dg/allocatable_scalar_8.f90: New.


Added:
    trunk/gcc/testsuite/gfortran.dg/allocatable_scalar_8.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/41872] wrong-code: Issues with allocatable scalars
  2009-10-29 21:58 [Bug fortran/41872] New: wrong-code: No auto-deallocation for INTENT(OUT) allocatable scalars burnus at gcc dot gnu dot org
                   ` (10 preceding siblings ...)
  2010-01-05  7:19 ` burnus at gcc dot gnu dot org
@ 2010-01-07  8:10 ` burnus at gcc dot gnu dot org
  2010-01-07  8:12 ` burnus at gcc dot gnu dot org
  12 siblings, 0 replies; 14+ messages in thread
From: burnus at gcc dot gnu dot org @ 2010-01-07  8:10 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #12 from burnus at gcc dot gnu dot org  2010-01-07 08:10 -------
Subject: Bug 41872

Author: burnus
Date: Thu Jan  7 08:09:51 2010
New Revision: 155687

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=155687
Log:
2010-01-07  Tobias Burnus  <burnus@net-b.de>

        PR fortran/41872
        * trans-decl.c (gfc_trans_deferred_vars): Don't initialize
        allocatable scalars with SAVE attribute.

2010-01-07  Tobias Burnus  <burnus@net-b.de>

        PR fortran/41872
        * gfortran.dg/allocatable_scalar_7.f90: New test.


Added:
    trunk/gcc/testsuite/gfortran.dg/allocatable_scalar_7.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/trans-decl.c
    trunk/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/41872] wrong-code: Issues with allocatable scalars
  2009-10-29 21:58 [Bug fortran/41872] New: wrong-code: No auto-deallocation for INTENT(OUT) allocatable scalars burnus at gcc dot gnu dot org
                   ` (11 preceding siblings ...)
  2010-01-07  8:10 ` burnus at gcc dot gnu dot org
@ 2010-01-07  8:12 ` burnus at gcc dot gnu dot org
  12 siblings, 0 replies; 14+ messages in thread
From: burnus at gcc dot gnu dot org @ 2010-01-07  8:12 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #13 from burnus at gcc dot gnu dot org  2010-01-07 08:12 -------
Hopefully, all issues are now fixed. Thus:

Mark as FIXED.


-- 

burnus at gcc dot gnu dot org changed:

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


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


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

end of thread, other threads:[~2010-01-07  8:12 UTC | newest]

Thread overview: 14+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2009-10-29 21:58 [Bug fortran/41872] New: wrong-code: No auto-deallocation for INTENT(OUT) allocatable scalars burnus at gcc dot gnu dot org
2009-10-29 22:52 ` [Bug fortran/41872] " burnus at gcc dot gnu dot org
2009-10-30 22:26 ` burnus at gcc dot gnu dot org
2009-11-01 16:08 ` [Bug fortran/41872] wrong-code: Issues with " burnus at gcc dot gnu dot org
2009-11-01 17:47 ` burnus at gcc dot gnu dot org
2009-11-01 20:47 ` burnus at gcc dot gnu dot org
2009-12-15  3:02 ` jvdelisle at gcc dot gnu dot org
2009-12-30  0:20 ` burnus at gcc dot gnu dot org
2009-12-30 20:50 ` burnus at gcc dot gnu dot org
2010-01-04  7:31 ` burnus at gcc dot gnu dot org
2010-01-04  7:43 ` burnus at gcc dot gnu dot org
2010-01-05  7:19 ` burnus at gcc dot gnu dot org
2010-01-07  8:10 ` burnus at gcc dot gnu dot org
2010-01-07  8:12 ` 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).