public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/59560] New: Resolution generic procedure of derived types fail
@ 2013-12-19 13:29 klaas_giesbertz at hotmail dot com
  2013-12-19 13:35 ` [Bug fortran/59560] " klaas_giesbertz at hotmail dot com
                   ` (13 more replies)
  0 siblings, 14 replies; 15+ messages in thread
From: klaas_giesbertz at hotmail dot com @ 2013-12-19 13:29 UTC (permalink / raw)
  To: gcc-bugs

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

            Bug ID: 59560
           Summary: Resolution generic procedure of derived types fail
           Product: gcc
           Version: 4.8.2
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: klaas_giesbertz at hotmail dot com

I want to achieve some more complicated structure in fortran2008 and I am not
sure how to do it according to the standard. So I am even not sure if it is a
bug, or simply not possible with fortran2008.

I want to make a base class, preferably an abstract one, which promises a
subroutine which operates on TWO arguments of this base class. The derived
class should implement this and there is some other class using this procedure
which only knows about the base class. This was actually possible with gcc 4.7
by declaring both arguments of the subroutine as class. As an example, consider
the following program (sorry, quite lengthy due to the several classes):

module BaseModule
  implicit none
  private

  type, public, abstract :: BaseClass
  contains
    procedure(FuncAbstr), deferred :: Func
  end type

  abstract interface
    subroutine FuncAbstr(self, other)
      import
      class(BaseClass), intent(inout) :: self
      class(BaseClass), intent(in)    :: other
    end subroutine
  end interface
end module

module UseBaseModule
  use BaseModule
  implicit none
  private

  type, public :: UseBaseClass
    class(BaseClass), pointer :: base => null()
  contains
    procedure :: Init
    procedure :: CallFunc
  end type

contains

  subroutine Init(self, base)
    class(UseBaseClass),       intent(inout) :: self
    class(BaseClass), pointer, intent(in)    :: base

    self%base => base
  end subroutine

  subroutine CallFunc(self)
    class(UseBaseClass), intent(inout) :: self
    class(BaseClass), allocatable :: newBase

    allocate(newBase, mold=self%base)

    call newBase%Func(self%base)
  end subroutine
end module

module DerivedModule
  use BaseModule
  implicit none
  private

  type, public, extends(BaseClass) :: DerivedClass
    real :: x
  contains
    procedure :: Func
  end type

contains

  subroutine Func(self, other)
    class(DerivedClass), intent(inout) :: self
    class(DerivedClass), intent(in)    :: other

    self%x = other%x
    write(*,*) 'Derived Func called'
  end subroutine

end module

program Test
  use BaseModule
  use UseBaseModule
  use DerivedModule
  implicit none

  class(BaseClass), allocatable :: derived
  type(UseBaseClass) :: useBase

  allocate(DerivedClass :: derived)

  call useBase%Init(derived)
  call useBase%CallFunc()
end program


This code compiles and runs correctly with gcc4.7.3, but gcc4.8.2 gives the
following compile error:

Test1.f08:58.13:

procedure :: Func
             1
Error: Argument mismatch for the overriding procedure 'func' at (1): Type/rank
mismatch in argument 'other'

and some more which are not relevant.

I actually do not even know if this code is supposed to compile, since it is
not clear to me if such kind of overloading is allowed by the fortran standard.

One way around this problem might be to give up the possibility to use an
abstract type and to use a generic interface with an explicit type for the 2nd
argument of the subroutine. The type is now required to facilite the resolution
of the generic subroutine. However, this generic subroutine is not correctly
resolved. As an example consider the following code (again quite lengthy,
sorry):

module BaseModule
  implicit none
  private

  type, public :: BaseClass
  contains
    procedure :: BaseFunc
    generic   :: Func => BaseFunc
  end type

contains

  subroutine BaseFunc(self, other)
    class(BaseClass), intent(inout) :: self
    type(BaseClass),  intent(in)    :: other

    write(*,*) 'Base Func called'
  end subroutine

end module

module DerivedModule
  use BaseModule
  implicit none
  private

  type, public, extends(BaseClass) :: DerivedClass
    real :: x
  contains
    procedure :: DerivedFunc
    generic   :: Func => DerivedFunc !Extend generic Func
  end type

contains

  subroutine DerivedFunc(self, other)
    class(DerivedClass), intent(inout) :: self
    type(DerivedClass),  intent(in)    :: other

    self%x = other%x
    write(*,*) 'Derived Func called'
  end subroutine

end module

module UseBaseModule
  use BaseModule
  implicit none
  private

  type, public :: UseBaseClass
    class(BaseClass), pointer :: base => null()
  contains
    procedure :: Init
    procedure :: CallFunc
  end type

contains

  subroutine Init(self, base)
    class(UseBaseClass),      intent(inout) :: self
    class(BaseClass), target, intent(in)    :: base

    self%base => base
  end subroutine

  subroutine CallFunc(self)
    class(UseBaseClass), intent(in) :: self
    class(BaseClass), allocatable :: newBase

    allocate(newBase, mold=self%base)

    call newBase%Func(self%base)
  end subroutine
end module

program Test
  use DerivedModule
  use UseBaseModule
  implicit none

  type(DerivedClass) :: derived
  type(UseBaseClass) :: useBase

  call useBase%Init(derived)
  call useBase%CallFunc()
end program

This code compiles both with gcc4.7.3 and gcc4.8.2 and gives in both cases the
incorrect output:
Base Func called
It should have called the DerivedFunc instead. Building a double block of
select types around it solves the problem, but the UseBase needs to know about
the Derived as well to do this, which is not desirable.

Hope someone can help me out.
Klaas Giesbertz


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

* [Bug fortran/59560] Resolution generic procedure of derived types fail
  2013-12-19 13:29 [Bug fortran/59560] New: Resolution generic procedure of derived types fail klaas_giesbertz at hotmail dot com
@ 2013-12-19 13:35 ` klaas_giesbertz at hotmail dot com
  2013-12-19 16:44 ` janus at gcc dot gnu.org
                   ` (12 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: klaas_giesbertz at hotmail dot com @ 2013-12-19 13:35 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #1 from klaas_giesbertz at hotmail dot com ---
Sorry, the 2nd argument of Init of UseBase in the 1st test should have been
target instead of pointer. In that case 'program Test' becomes the same as in
the 2nd test.


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

* [Bug fortran/59560] Resolution generic procedure of derived types fail
  2013-12-19 13:29 [Bug fortran/59560] New: Resolution generic procedure of derived types fail klaas_giesbertz at hotmail dot com
  2013-12-19 13:35 ` [Bug fortran/59560] " klaas_giesbertz at hotmail dot com
@ 2013-12-19 16:44 ` janus at gcc dot gnu.org
  2013-12-19 16:57 ` janus at gcc dot gnu.org
                   ` (11 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: janus at gcc dot gnu.org @ 2013-12-19 16:44 UTC (permalink / raw)
  To: gcc-bugs

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

janus at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |janus at gcc dot gnu.org

--- Comment #2 from janus at gcc dot gnu.org ---
(In reply to klaas_giesbertz from comment #0)
> This code compiles and runs correctly with gcc4.7.3, but gcc4.8.2 gives the
> following compile error:
> 
> Test1.f08:58.13:
> 
> procedure :: Func
>              1
> Error: Argument mismatch for the overriding procedure 'func' at (1):
> Type/rank mismatch in argument 'other'

For your first example, I get this error with all version from 4.6 to trunk
(with slight variations in the wording). Are you sure the code you posted is
what you compiled with 4.7?


> I actually do not even know if this code is supposed to compile, since it is
> not clear to me if such kind of overloading is allowed by the fortran
> standard.

I think the error is correct. The Fortran standard does not allow this.


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

* [Bug fortran/59560] Resolution generic procedure of derived types fail
  2013-12-19 13:29 [Bug fortran/59560] New: Resolution generic procedure of derived types fail klaas_giesbertz at hotmail dot com
  2013-12-19 13:35 ` [Bug fortran/59560] " klaas_giesbertz at hotmail dot com
  2013-12-19 16:44 ` janus at gcc dot gnu.org
@ 2013-12-19 16:57 ` janus at gcc dot gnu.org
  2013-12-19 17:12 ` klaas_giesbertz at hotmail dot com
                   ` (10 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: janus at gcc dot gnu.org @ 2013-12-19 16:57 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #3 from janus at gcc dot gnu.org ---
(In reply to klaas_giesbertz from comment #0)
> This code compiles both with gcc4.7.3 and gcc4.8.2 and gives in both cases
> the incorrect output:
> Base Func called
> It should have called the DerivedFunc instead.

The second example is a bit tricky.

Note that the resolution of your generic 'Func' happens at compile time and
only based on the declared type -- the dynamic type of the objects does not
matter at all.

I would say the behavior here is ok as well.


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

* [Bug fortran/59560] Resolution generic procedure of derived types fail
  2013-12-19 13:29 [Bug fortran/59560] New: Resolution generic procedure of derived types fail klaas_giesbertz at hotmail dot com
                   ` (2 preceding siblings ...)
  2013-12-19 16:57 ` janus at gcc dot gnu.org
@ 2013-12-19 17:12 ` klaas_giesbertz at hotmail dot com
  2013-12-19 17:32 ` janus at gcc dot gnu.org
                   ` (9 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: klaas_giesbertz at hotmail dot com @ 2013-12-19 17:12 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #4 from klaas_giesbertz at hotmail dot com ---
In reply to Comment2&3 (Janus):

I have copied it back from my post and it still compiles with my gfortran4.7.3.
Could it have something to do with my build of gcc? I used macports to install
it on my machine, so I am not fully aware of the dependencies. Would be strange
though. Anyway, it is wrong fortran, so it should not work.

A 'select type' could make the distinction, so 'select type' works dynamically,
but the generic works statically. Confusing. So you would say that this kind of
functionality is out of reach for fortran2008? Do you have any idea for a
different solution? I know this is not the place to ask, but I would be
grateful for some help.


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

* [Bug fortran/59560] Resolution generic procedure of derived types fail
  2013-12-19 13:29 [Bug fortran/59560] New: Resolution generic procedure of derived types fail klaas_giesbertz at hotmail dot com
                   ` (3 preceding siblings ...)
  2013-12-19 17:12 ` klaas_giesbertz at hotmail dot com
@ 2013-12-19 17:32 ` janus at gcc dot gnu.org
  2013-12-19 17:44 ` dominiq at lps dot ens.fr
                   ` (8 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: janus at gcc dot gnu.org @ 2013-12-19 17:32 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #5 from janus at gcc dot gnu.org ---
(In reply to klaas_giesbertz from comment #4)
> I have copied it back from my post and it still compiles with my
> gfortran4.7.3. Could it have something to do with my build of gcc?

Hopefully not, but it might have to do with the exact version. I just tried it
with the most recent branch build:

gcc version 4.7.4 20131219 (prerelease) [gcc-4_7-branch revision 206127] (GCC)

(which yields the same result as the 4.7.3 version provided by Ubuntu, namely
rejecting the test case).

What does "gfortran -v" show in your case?


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

* [Bug fortran/59560] Resolution generic procedure of derived types fail
  2013-12-19 13:29 [Bug fortran/59560] New: Resolution generic procedure of derived types fail klaas_giesbertz at hotmail dot com
                   ` (4 preceding siblings ...)
  2013-12-19 17:32 ` janus at gcc dot gnu.org
@ 2013-12-19 17:44 ` dominiq at lps dot ens.fr
  2013-12-19 18:10 ` janus at gcc dot gnu.org
                   ` (7 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-12-19 17:44 UTC (permalink / raw)
  To: gcc-bugs

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

Dominique d'Humieres <dominiq at lps dot ens.fr> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2013-12-19
     Ever confirmed|0                           |1

--- Comment #6 from Dominique d'Humieres <dominiq at lps dot ens.fr> ---
The test in comment 0 compiles with 4.7.3 and gives at run time

 Derived Func called

And I confirm the reported behavior for the rest of the posts.


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

* [Bug fortran/59560] Resolution generic procedure of derived types fail
  2013-12-19 13:29 [Bug fortran/59560] New: Resolution generic procedure of derived types fail klaas_giesbertz at hotmail dot com
                   ` (5 preceding siblings ...)
  2013-12-19 17:44 ` dominiq at lps dot ens.fr
@ 2013-12-19 18:10 ` janus at gcc dot gnu.org
  2013-12-19 18:13 ` janus at gcc dot gnu.org
                   ` (6 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: janus at gcc dot gnu.org @ 2013-12-19 18:10 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #7 from janus at gcc dot gnu.org ---
(In reply to Dominique d'Humieres from comment #6)
> The test in comment 0 compiles with 4.7.3 and gives at run time

Is this with the proper 4.7.3 release or some 4.7 branch build? Can you give
the excact version (gfortran -v)? As mentioned in comment 5, it is being
rejected with a current 4.7 branch build for me. Some commit on the 4.7 branch
might have affected the behavior?


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

* [Bug fortran/59560] Resolution generic procedure of derived types fail
  2013-12-19 13:29 [Bug fortran/59560] New: Resolution generic procedure of derived types fail klaas_giesbertz at hotmail dot com
                   ` (6 preceding siblings ...)
  2013-12-19 18:10 ` janus at gcc dot gnu.org
@ 2013-12-19 18:13 ` janus at gcc dot gnu.org
  2013-12-19 18:26 ` dominiq at lps dot ens.fr
                   ` (5 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: janus at gcc dot gnu.org @ 2013-12-19 18:13 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #8 from janus at gcc dot gnu.org ---
(In reply to janus from comment #7)
> Some commit on the 4.7
> branch might have affected the behavior?

After a quick look into the ChangeLog, I already have a suspicion:


2013-06-01  Janus Weil  <janus@gcc.gnu.org>
        Tobias Burnus  <burnus@net-b.de>

    PR fortran/57217
    * interface.c (check_dummy_characteristics): Symmetrize type check.


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

* [Bug fortran/59560] Resolution generic procedure of derived types fail
  2013-12-19 13:29 [Bug fortran/59560] New: Resolution generic procedure of derived types fail klaas_giesbertz at hotmail dot com
                   ` (7 preceding siblings ...)
  2013-12-19 18:13 ` janus at gcc dot gnu.org
@ 2013-12-19 18:26 ` dominiq at lps dot ens.fr
  2013-12-19 18:29 ` janus at gcc dot gnu.org
                   ` (4 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-12-19 18:26 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #9 from Dominique d'Humieres <dominiq at lps dot ens.fr> ---
When I say 4.7.3 it means the 4.7.3 release, otherwise I give the revision
number or the date if the former is not available.


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

* [Bug fortran/59560] Resolution generic procedure of derived types fail
  2013-12-19 13:29 [Bug fortran/59560] New: Resolution generic procedure of derived types fail klaas_giesbertz at hotmail dot com
                   ` (8 preceding siblings ...)
  2013-12-19 18:26 ` dominiq at lps dot ens.fr
@ 2013-12-19 18:29 ` janus at gcc dot gnu.org
  2014-01-08 11:04 ` klaas_giesbertz at hotmail dot com
                   ` (3 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: janus at gcc dot gnu.org @ 2013-12-19 18:29 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #10 from janus at gcc dot gnu.org ---
(In reply to Dominique d'Humieres from comment #9)
> When I say 4.7.3 it means the 4.7.3 release, otherwise I give the revision
> number or the date if the former is not available.

Ok, that matches my suspicion (as that commit was after the 4.7.3 release).


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

* [Bug fortran/59560] Resolution generic procedure of derived types fail
  2013-12-19 13:29 [Bug fortran/59560] New: Resolution generic procedure of derived types fail klaas_giesbertz at hotmail dot com
                   ` (9 preceding siblings ...)
  2013-12-19 18:29 ` janus at gcc dot gnu.org
@ 2014-01-08 11:04 ` klaas_giesbertz at hotmail dot com
  2014-01-08 11:14 ` janus at gcc dot gnu.org
                   ` (2 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: klaas_giesbertz at hotmail dot com @ 2014-01-08 11:04 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #11 from klaas_giesbertz at hotmail dot com ---
Finally figured out how to make it work. I guess this is what the class(*) is
useful for. Using class(*) I can simply overload Func and its resolution
becomes dynamic. I consider the class(*) quite an overkill, but it works.

So the Base and Derived Modules now become

module BaseModule
  implicit none
  private

  type, public :: BaseClass
  contains
    procedure :: Func
  end type

contains

  subroutine Func(self, other)
    class(BaseClass), intent(inout) :: self
    class(*),         intent(in)    :: other

    write(*,*) 'Base Func called'
  end subroutine

end module

module DerivedModule
  use BaseModule
  implicit none
  private

  type, public, extends(BaseClass) :: DerivedClass
    real :: x
  contains
    procedure :: Func
  end type

contains

  subroutine Func(self, other)
    class(DerivedClass), intent(inout) :: self
    class(*),            intent(in)    :: other

    write(*,*) 'Derived Func called'

    select type(bla => other)
      class is (DerivedClass)
        write(*,*) 'DerivedClass found'
      class default
        write(*,*) 'Bad luck'
    end select
  end subroutine

end module


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

* [Bug fortran/59560] Resolution generic procedure of derived types fail
  2013-12-19 13:29 [Bug fortran/59560] New: Resolution generic procedure of derived types fail klaas_giesbertz at hotmail dot com
                   ` (10 preceding siblings ...)
  2014-01-08 11:04 ` klaas_giesbertz at hotmail dot com
@ 2014-01-08 11:14 ` janus at gcc dot gnu.org
  2014-01-08 11:42 ` klaas_giesbertz at hotmail dot com
  2014-01-08 12:06 ` janus at gcc dot gnu.org
  13 siblings, 0 replies; 15+ messages in thread
From: janus at gcc dot gnu.org @ 2014-01-08 11:14 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #12 from janus at gcc dot gnu.org ---
(In reply to klaas_giesbertz from comment #11)
> Finally figured out how to make it work. I guess this is what the class(*)
> is useful for. Using class(*) I can simply overload Func and its resolution
> becomes dynamic. I consider the class(*) quite an overkill, but it works.

I don't think you need unlimited polymorphism, i.e. class(*), for what you're
trying to do. It should be enough to declare the 'other' argument as
'class(BaseClass)' in both cases.


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

* [Bug fortran/59560] Resolution generic procedure of derived types fail
  2013-12-19 13:29 [Bug fortran/59560] New: Resolution generic procedure of derived types fail klaas_giesbertz at hotmail dot com
                   ` (11 preceding siblings ...)
  2014-01-08 11:14 ` janus at gcc dot gnu.org
@ 2014-01-08 11:42 ` klaas_giesbertz at hotmail dot com
  2014-01-08 12:06 ` janus at gcc dot gnu.org
  13 siblings, 0 replies; 15+ messages in thread
From: klaas_giesbertz at hotmail dot com @ 2014-01-08 11:42 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #13 from klaas_giesbertz at hotmail dot com ---
You are right! Thanks a lot.


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

* [Bug fortran/59560] Resolution generic procedure of derived types fail
  2013-12-19 13:29 [Bug fortran/59560] New: Resolution generic procedure of derived types fail klaas_giesbertz at hotmail dot com
                   ` (12 preceding siblings ...)
  2014-01-08 11:42 ` klaas_giesbertz at hotmail dot com
@ 2014-01-08 12:06 ` janus at gcc dot gnu.org
  13 siblings, 0 replies; 15+ messages in thread
From: janus at gcc dot gnu.org @ 2014-01-08 12:06 UTC (permalink / raw)
  To: gcc-bugs

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

janus at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|NEW                         |RESOLVED
         Resolution|---                         |INVALID

--- Comment #14 from janus at gcc dot gnu.org ---
In any case I will close this PR now, since I don't see any problems with
gfortran's behavior on the test cases reported here.


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

end of thread, other threads:[~2014-01-08 12:06 UTC | newest]

Thread overview: 15+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2013-12-19 13:29 [Bug fortran/59560] New: Resolution generic procedure of derived types fail klaas_giesbertz at hotmail dot com
2013-12-19 13:35 ` [Bug fortran/59560] " klaas_giesbertz at hotmail dot com
2013-12-19 16:44 ` janus at gcc dot gnu.org
2013-12-19 16:57 ` janus at gcc dot gnu.org
2013-12-19 17:12 ` klaas_giesbertz at hotmail dot com
2013-12-19 17:32 ` janus at gcc dot gnu.org
2013-12-19 17:44 ` dominiq at lps dot ens.fr
2013-12-19 18:10 ` janus at gcc dot gnu.org
2013-12-19 18:13 ` janus at gcc dot gnu.org
2013-12-19 18:26 ` dominiq at lps dot ens.fr
2013-12-19 18:29 ` janus at gcc dot gnu.org
2014-01-08 11:04 ` klaas_giesbertz at hotmail dot com
2014-01-08 11:14 ` janus at gcc dot gnu.org
2014-01-08 11:42 ` klaas_giesbertz at hotmail dot com
2014-01-08 12:06 ` janus at gcc dot gnu.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).