comp.lang.ada
 help / color / mirror / Atom feed
* Re: Ada95 + FORTRAN 77
  1999-09-06  0:00 Ada95 + FORTRAN 77 Preben Randhol
  1999-09-06  0:00 ` Gisle S�lensminde
@ 1999-09-06  0:00 ` lafage8770
  1999-09-06  0:00   ` Matthew Heaney
  1999-09-06  0:00   ` Preben Randhol
  1 sibling, 2 replies; 14+ messages in thread
From: lafage8770 @ 1999-09-06  0:00 UTC (permalink / raw)


In article <m3hfl8ihzd.fsf@kiuk0156.chembio.ntnu.no>,
  Preben Randhol <randhol@pvv.org> wrote:
> I have read (think it was on the net) that one can bind Fortran and
> Ada95 together. Does anybody know if one can use Fortran 77?

Yes, for instance g77 cooperates well with gnat on my GNU/Linux box.

> I have a calculation program written in FORTRAN 77 and want to just
> make a graphical interface to it so that it will be easier to do
> calculations. I want to use Ada95 and GTK+. So I'm wondering if
> anybody know of a working example for the Ada95 - FORTRAN 77
> connection (don't have to be any GUI) that I could look at?

First, I will send you an example which has been given
on this list
(by Sune Falck on Fri, 12 Dec 1997 20:03:46 +0200)
-------------------------------------------------------------------
-- file ftest.adb
with Ada.Text_IO; use Ada.Text_IO;
with Ada.Float_Text_IO; use Ada.Float_Text_IO;
procedure Ftest is

procedure Adder (A : in Float; B: in Float; Sum : out Float);
pragma Import (Fortran, Adder, Link_Name => "adder_");

A : Float := 12.0;
B : Float := 13.0;
Sum : Float;
begin
Adder (A, B, Sum);
Put (A); Put (B); Put ('='); Put (Sum); New_Line;

end Ftest;
-------------------------------------------------------------------
file adder.f:
      SUBROUTINE ADDER (A, B, SUM)
      REAL*4 A
      REAL*4 B
      REAL*4 SUM
      SUM = A + B
      END
-------------------------------------------------------------------
g77 -c adder.f
gnatmake ftest -largs adder.o
... and it works

AND NOW even better: how to pass common ?
(It works, but I do not know if this is the ``proper way''
and would appreciate any comment)

-------------------------------------------------------------------
file common_basic.ads:
with Interfaces.Fortran; use Interfaces.Fortran;

package Common_Basic is
   type Basic_Common is record
      X, Y, Z : Double_Precision;
   end record;
   Basic : Basic_Common;
   pragma Import(Fortran, Basic, Link_Name => "basic_");
end Common_Basic;
-------------------------------------------------------------------
file ada_application.adb:
with Interfaces.Fortran; use Interfaces.Fortran;
with Ada.Text_IO; use Ada.Text_IO;
with Ada.Float_Text_IO; use Ada.Float_Text_IO;

with Common_Basic; use Common_Basic;

procedure Ada_Application is

   procedure Compute(T : in Double_Precision);
   pragma Import(Fortran, Compute, Link_Name => "compute_");

begin
   Basic.X :=1.0;
   Basic.Y :=2.0;
   Basic.Z :=3.0;
   Put(Float(Basic.X));
   Put(Float(Basic.Y));
   Put(Float(Basic.Z));
   New_Line;
   Compute(0.0);
   Put(Float(Basic.X));
   Put(Float(Basic.Y));
   Put(Float(Basic.Z));
   New_Line;
end Ada_Application;
-------------------------------------------------------------------
file compute.f:
      subroutine compute(t)
      implicit none
c      double precision t
      real*8 t
      double precision x,y,z
      common /basic/ x,y,z

      write(*,*)'t : ',t
      write(*,*)'x : ',x
      write(*,*)'y : ',y
      write(*,*)'z : ',z

      z=sqrt(z)

      return
      end
-------------------------------------------------------------------

 g77 -c compute.f
 gnatmake ada_application  -largs compute.o

Et voila !

-------------------------------------------------------------------

--
Vincent Lafage
 ``Qui est un plumeur de faisan ? ''


Sent via Deja.com http://www.deja.com/
Share what you know. Learn what you don't.




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

* Re: Ada95 + FORTRAN 77
  1999-09-06  0:00 Ada95 + FORTRAN 77 Preben Randhol
@ 1999-09-06  0:00 ` Gisle S�lensminde
  1999-09-06  0:00   ` Preben Randhol
  1999-09-06  0:00 ` lafage8770
  1 sibling, 1 reply; 14+ messages in thread
From: Gisle S�lensminde @ 1999-09-06  0:00 UTC (permalink / raw)


In article <m3hfl8ihzd.fsf@kiuk0156.chembio.ntnu.no>, Preben Randhol wrote:
>
>Hello I'm quite new to Ada95. Have started reading John Barnes:
>Programming in Ada 95.
>
>I have read (think it was on the net) that one can bind Fortran and
>Ada95 together. Does anybody know if one can use Fortran 77?
>
>I have a calculation program written in FORTRAN 77 and want to just
>make a graphical interface to it so that it will be easier to do
>calculations. I want to use Ada95 and GTK+. So I'm wondering if
>anybody know of a working example for the Ada95 - FORTRAN 77
>connection (don't have to be any GUI) that I could look at?

There is a binding to the LAPACK Fortran library at the contrib area at
the main site for the GNAT public version.

ftp://cs.nyu.edu/pub/gnat/contrib/lapack-ada/

>
>Thanks in advance.
>
>PS: Ada's verbose syntax threw me back first time I looked at it (a
>year ago or so), but after meddling a bit with C++ I see why verbose
>is better. Also I didn't get GNAT the compiler working on Linux back
>then, now it works like charm :-)
>
>-- 
>Preben Randhol             oO     "Don't think about domination,  think
>[randhol@pvv.org]        .`  ;     about freedom, it doesn't dominate."
>[www.pvv.org/~randhol/]   \ G                  -- RMS, LinuxWorld 1999.
>                           `_) n o m e 


-- 
--
Gisle S�lensminde ( gisle@ii.uib.no )   





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

* Re: Ada95 + FORTRAN 77
  1999-09-06  0:00 ` lafage8770
@ 1999-09-06  0:00   ` Matthew Heaney
  1999-09-06  0:00     ` Robert Dewar
  1999-09-06  0:00   ` Preben Randhol
  1 sibling, 1 reply; 14+ messages in thread
From: Matthew Heaney @ 1999-09-06  0:00 UTC (permalink / raw)


In article <7r07rr$gap$1@nnrp1.deja.com> , lafage8770@my-deja.com  wrote:

> procedure Adder (A : in Float; B: in Float; Sum : out Float);

You should be using the types in Interfaces.Fortran, and you should also
have a pragma Convention.


> pragma Import (Fortran, Adder, Link_Name => "adder_");
>
> A : Float := 12.0;
> B : Float := 13.0;
> Sum : Float;
> begin
> Adder (A, B, Sum);
> Put (A); Put (B); Put ('='); Put (Sum); New_Line;
>
> end Ftest;
> -------------------------------------------------------------------
> file adder.f:
>       SUBROUTINE ADDER (A, B, SUM)
>       REAL*4 A
>       REAL*4 B
>       REAL*4 SUM

The reason you need to use the scalar types declared in Interfaces.Fortran
is that you have no guarantee that REAL*4 is the same as an Ada Float type.


>       SUM = A + B
>       END
> file common_basic.ads:
> with Interfaces.Fortran; use Interfaces.Fortran;
>
> package Common_Basic is
>    type Basic_Common is record
>       X, Y, Z : Double_Precision;
>    end record;
>    Basic : Basic_Common;

You have the scalar types right, but you still need a pragma Convention for
your record type.  Otherwise, how do you know that the representation of the
record on the Ada side matches the rep on the Fortran side?


>    pragma Import(Fortran, Basic, Link_Name => "basic_");
> end Common_Basic;




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

* Re: Ada95 + FORTRAN 77
  1999-09-06  0:00   ` Matthew Heaney
@ 1999-09-06  0:00     ` Robert Dewar
  0 siblings, 0 replies; 14+ messages in thread
From: Robert Dewar @ 1999-09-06  0:00 UTC (permalink / raw)


In article <37d3b7de@news1.prserv.net>,
  "Matthew Heaney" <matthew_heaney@acm.org> wrote:
> In article <7r07rr$gap$1@nnrp1.deja.com> ,
lafage8770@my-deja.com  wrote:
>
> > procedure Adder (A : in Float; B: in Float; Sum : out
Float);
>
> You should be using the types in Interfaces.Fortran, and you
> should also have a pragma Convention.

Although this is true if you want to be sure to write code
that is portable between Ada 95 compilers, it is not really
necessary when using GNAT and g77, because the correspondence
between types (e.g. Real*4 and Float is in fact guaranteed).

It's always a bit of a difficult decision. The use of the types
in the interfaces packages often makes the interface a lot
heavier than it would be otherwise, so you have to make a
decision based on a trade off here.

The use of pragma Convention is a good idea anyway, because

a) it is syntactically light.

b) it warns the reader right away that Fortran is involved

c) if you have a compiler that properly implements annex G,
it also takes care of row- vs column- addressing of multi-dim
arrays.




Sent via Deja.com http://www.deja.com/
Share what you know. Learn what you don't.




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

* Re: Ada95 + FORTRAN 77
  1999-09-06  0:00   ` Preben Randhol
@ 1999-09-06  0:00     ` Robert Dewar
  1999-09-06  0:00       ` Preben Randhol
  1999-09-07  0:00       ` okellogg
  0 siblings, 2 replies; 14+ messages in thread
From: Robert Dewar @ 1999-09-06  0:00 UTC (permalink / raw)


In article <m3so4sgprj.fsf@kiuk0156.chembio.ntnu.no>,
  Preben Randhol <randhol@pvv.org> wrote:
> Thanks! It worked very nice. I also noticed that one have to
be
> careful with the variable types. Changing, in the F77 program,
REAL*4
> to DOUBLE PRECISION resulted in a bug in the output. But when
I added
> Interfaces.Fortran and used Double_Precision it worked fine
again :-)


Well yes, of course you must be careful to have corresponding
types, and typically systems will not be able to check this
in Ada-Fortran interfacing (actually most Fortran compilers
don't even check this in Fortran-Fortran interfacing).

Do if you are using DOUBLE PRECISION in the Fortran program,
you must use Interfaces.Fortran.Double_Precision.

In GNAT, you can simply use Long_Float, and this will always
work, because GNAT always defines

   type Fortran_Integer  is new Integer;
   type Real             is new Float;
   type Double_Precision is new Long_Float;

One other point is to be careful of type Logical in the
Fortran interface. This is defined to be a new Boolean, but
with very unusual (zero/non-zero) semantics.

There are no ACVC tests to ensure that this is done right, and
it is quite a lot of specialized mechanism in the compiler to
deal with this very non-standard Boolean type. So if you rely
on this, be careful to check that your compiler handles this.

The proper handling of Fortran Logical was only recently added
to GNAT (for version 3.12). At the same time, we also
implemented a rather nice feature:

  type C_Bool is new Boolean;
  pragma Convention (C, C_Bool);

the semantics of this boolean will be like C, zero/non-zero,
rather than normal Ada representation semantics. This can make
interfacing to booleans in C quite a bit cleaner and more
abstract (otherwise you have to explicitly treat the C logical
values as integers on the Ada sign with zero/non-zero semantics)

Robert Dewar
Ada Core Technologies


Sent via Deja.com http://www.deja.com/
Share what you know. Learn what you don't.




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

* Re: Ada95 + FORTRAN 77
  1999-09-06  0:00       ` Preben Randhol
@ 1999-09-06  0:00         ` Robert Dewar
  1999-09-07  0:00           ` Preben Randhol
  0 siblings, 1 reply; 14+ messages in thread
From: Robert Dewar @ 1999-09-06  0:00 UTC (permalink / raw)


In article <m3aeqzhp97.fsf@kiuk0156.chembio.ntnu.no>,
  Preben Randhol <randhol@pvv.org> wrote:
> I see, but this will only work when compiled on GNAT and
> reduce portability? I'm new so I don't know if there are any
> other Ada compilers out there. :-)

Well I don't think there are any other Ada 95 compilers
currently available for Linux (I see you are a Linux user),
but sure there are quite a few Ada compilers out there,
from quite a few companies, including Aonix, Rational,
OCS, Irvine, Averstar, Greenhills, and others. The Ada
market is alive and well, with a healthy level of competition,
that works well for vendors and users alike.

Every compiler will provide useful stuff that is not required
by the standard, but is allowed as implementation defined
additions. This may include useful packages, useful attributes
and pragmas, representation clauses that are not required, etc.

For GNAT, some examples of these are

special packages: SPITBOL pattern matching, interfacing between
C streams and Ada I/O, and many others.

attributes: Unrestricted_Access (allowing complete freedom in
use of pointers to functions)

pragmas: Valued_Procedure (allowing interfacing to functions
that have out parameters).

rep clauses: close packing for all component sizes up to 64.

And of course the other category, which is things that are
undefined in the standard (e.g. the relation of Ada and
Fortran Integer), but which may be defined by an implementation
(they are always the same in GNAT).

In any project, you have to understand from the start whether
and to what extent you will tie your hands behind your back
and not use these nice features, in the interests of
portability.

There is no one right answer here. Failure to program portably
when portability is needed can be a costly mistake, but on the
other hand, having to reinvent already invented wheels for the
sake of portability can add a lot of perhaps unnecessary
effort.

One thing that is useful to know is that GNAT is implemented
on almost all standard computers (the MAC is the only notable
exception), so that if you write in GNAT taking advantage of
its capabilities, you can still port your application to any
other hardware without difficulty, and for example, if you
generate an application using GNAT on Linux x86, then exactly
the same features will be available on the Power PC Linux.

Robert Dewar
Ada Core Technologies

P.S. Since Ada Core Technologies was committed to the open
source model and to Linux long before these became the
subject of everyone's attention, it is not surprising that
GNAT is there on Linux first, but it would certainly be nice
to see some competition there, especially if some other Ada
vendor would take the plunge and open source their technology!


Sent via Deja.com http://www.deja.com/
Share what you know. Learn what you don't.




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

* Ada95 + FORTRAN 77
@ 1999-09-06  0:00 Preben Randhol
  1999-09-06  0:00 ` Gisle S�lensminde
  1999-09-06  0:00 ` lafage8770
  0 siblings, 2 replies; 14+ messages in thread
From: Preben Randhol @ 1999-09-06  0:00 UTC (permalink / raw)



Hello I'm quite new to Ada95. Have started reading John Barnes:
Programming in Ada 95.

I have read (think it was on the net) that one can bind Fortran and
Ada95 together. Does anybody know if one can use Fortran 77?

I have a calculation program written in FORTRAN 77 and want to just
make a graphical interface to it so that it will be easier to do
calculations. I want to use Ada95 and GTK+. So I'm wondering if
anybody know of a working example for the Ada95 - FORTRAN 77
connection (don't have to be any GUI) that I could look at?

Thanks in advance.

PS: Ada's verbose syntax threw me back first time I looked at it (a
year ago or so), but after meddling a bit with C++ I see why verbose
is better. Also I didn't get GNAT the compiler working on Linux back
then, now it works like charm :-)

-- 
Preben Randhol             oO     "Don't think about domination,  think
[randhol@pvv.org]        .`  ;     about freedom, it doesn't dominate."
[www.pvv.org/~randhol/]   \ G                  -- RMS, LinuxWorld 1999.
                           `_) n o m e 




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

* Re: Ada95 + FORTRAN 77
  1999-09-06  0:00 ` Gisle S�lensminde
@ 1999-09-06  0:00   ` Preben Randhol
  0 siblings, 0 replies; 14+ messages in thread
From: Preben Randhol @ 1999-09-06  0:00 UTC (permalink / raw)


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

gisle@apal.ii.uib.no (Gisle S�lensminde) writes:

| There is a binding to the LAPACK Fortran library at the contrib area at
| the main site for the GNAT public version.
| 
| ftp://cs.nyu.edu/pub/gnat/contrib/lapack-ada/

Ah lots of examples there, thanks! 

-- 
Preben Randhol             oO     "Don't think about domination,  think
[randhol@pvv.org]        .`  ;     about freedom, it doesn't dominate."
[www.pvv.org/~randhol/]   \ G                  -- RMS, LinuxWorld 1999.
                           `_) n o m e 




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

* Re: Ada95 + FORTRAN 77
  1999-09-06  0:00 ` lafage8770
  1999-09-06  0:00   ` Matthew Heaney
@ 1999-09-06  0:00   ` Preben Randhol
  1999-09-06  0:00     ` Robert Dewar
  1 sibling, 1 reply; 14+ messages in thread
From: Preben Randhol @ 1999-09-06  0:00 UTC (permalink / raw)


lafage8770@my-deja.com writes:

| First, I will send you an example which has been given
| on this list
| (by Sune Falck on Fri, 12 Dec 1997 20:03:46 +0200)

[...]

Thanks! It worked very nice. I also noticed that one have to be
careful with the variable types. Changing, in the F77 program, REAL*4
to DOUBLE PRECISION resulted in a bug in the output. But when I added
Interfaces.Fortran and used Double_Precision it worked fine again :-)

-- 
Preben Randhol             oO     "Don't think about domination,  think
[randhol@pvv.org]        .`  ;     about freedom, it doesn't dominate."
[www.pvv.org/~randhol/]   \ G                  -- RMS, LinuxWorld 1999.
                           `_) n o m e 




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

* Re: Ada95 + FORTRAN 77
  1999-09-06  0:00     ` Robert Dewar
@ 1999-09-06  0:00       ` Preben Randhol
  1999-09-06  0:00         ` Robert Dewar
  1999-09-07  0:00       ` okellogg
  1 sibling, 1 reply; 14+ messages in thread
From: Preben Randhol @ 1999-09-06  0:00 UTC (permalink / raw)


Robert Dewar <dewar@gnat.com> writes:

| Do if you are using DOUBLE PRECISION in the Fortran program,
| you must use Interfaces.Fortran.Double_Precision.
| 
| In GNAT, you can simply use Long_Float, and this will always
| work, because GNAT always defines
| 
|    type Fortran_Integer  is new Integer;
|    type Real             is new Float;
|    type Double_Precision is new Long_Float;

I see, but this will only work when compiled on GNAT and reduce
portability? I'm new so I don't know if there are any other Ada
compilers out there. :-)

-- 
Preben Randhol             oO     "Don't think about domination,  think
[randhol@pvv.org]        .`  ;     about freedom, it doesn't dominate."
[www.pvv.org/~randhol/]   \ G                  -- RMS, LinuxWorld 1999.
                           `_) n o m e 




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

* Re: Ada95 + FORTRAN 77
  1999-09-06  0:00     ` Robert Dewar
  1999-09-06  0:00       ` Preben Randhol
@ 1999-09-07  0:00       ` okellogg
  1999-09-08  0:00         ` Robert Dewar
  1 sibling, 1 reply; 14+ messages in thread
From: okellogg @ 1999-09-07  0:00 UTC (permalink / raw)


In article <7r0u2o$vik$1@nnrp1.deja.com>,
  Robert Dewar <dewar@gnat.com> wrote:
> [...] At the same time, we also
> implemented a rather nice feature:
>
>   type C_Bool is new Boolean;
>   pragma Convention (C, C_Bool);
>

Hey, that's nifty. How about suggesting this for standardization
in Ada-0x ?

Just my $0.02
-- Oliver



Sent via Deja.com http://www.deja.com/
Share what you know. Learn what you don't.




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

* Re: Ada95 + FORTRAN 77
  1999-09-06  0:00         ` Robert Dewar
@ 1999-09-07  0:00           ` Preben Randhol
  1999-09-08  0:00             ` Robert Dewar
  0 siblings, 1 reply; 14+ messages in thread
From: Preben Randhol @ 1999-09-07  0:00 UTC (permalink / raw)


Robert Dewar <dewar@gnat.com> writes:

| Well I don't think there are any other Ada 95 compilers
| currently available for Linux (I see you are a Linux user),

yes :-)

[thank you for careful information]
 
| attributes: Unrestricted_Access (allowing complete freedom in
| use of pointers to functions)

Where do I look to learn more about this feature?
 
| Robert Dewar
| Ada Core Technologies
| 
| P.S. Since Ada Core Technologies was committed to the open
| source model and to Linux long before these became the
| subject of everyone's attention, it is not surprising that
| GNAT is there on Linux first, but it would certainly be nice
| to see some competition there, especially if some other Ada
| vendor would take the plunge and open source their technology!

I agree, but I will at least thank you for doing so!
-- 
Preben Randhol             oO     "Don't think about domination,  think
[randhol@pvv.org]        .`  ;     about freedom, it doesn't dominate."
[www.pvv.org/~randhol/]   \ G                  -- RMS, LinuxWorld 1999.
                           `_) n o m e 




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

* Re: Ada95 + FORTRAN 77
  1999-09-07  0:00           ` Preben Randhol
@ 1999-09-08  0:00             ` Robert Dewar
  0 siblings, 0 replies; 14+ messages in thread
From: Robert Dewar @ 1999-09-08  0:00 UTC (permalink / raw)


In article <m3aeqz89x3.fsf@kiuk0156.chembio.ntnu.no>,
  Preben Randhol <randhol@pvv.org> wrote:
> Robert Dewar <dewar@gnat.com> writes:
>
> | Well I don't think there are any other Ada 95 compilers
> | currently available for Linux (I see you are a Linux user),
>
> yes :-)
>
> [thank you for careful information]

you are welcome!

> | attributes: Unrestricted_Access (allowing complete freedom
in
> | use of pointers to functions)
>
> Where do I look to learn more about this feature?

It is documented in the GNAT programmers manual, which should
be part of your Linux distribution. Here is the relevant
section:

@item Unrestricted_Access
@noindent
The @code{Unrestricted_Access} attribute is similar to
@code{Access}
except that all accessibility and aliased view checks are
omitted. This
is a user-beware attribute.  It is similar to
@code{Address}, for which it is a desirable replacement where
the value
desired is an access type. In other words, its effect is
identical to
first applying the @code{Address} attribute and then doing an
unchecked
conversion to a desired access type. In GNAT, but not
necessarily in
other implementations, the use of static chains for inner level
subprograms means that @code{Unrestricted_Access} applied to a
subprogram yields a value that can be called as long as the
subprogram
is in scope (normal Ada 95 accessibility rules restrict this
usage).

It is prettier in the formatted version, which you should have!
> | P.S. Since Ada Core Technologies was committed to the open
> | source model and to Linux long before these became the
> | subject of everyone's attention, it is not surprising that
> | GNAT is there on Linux first, but it would certainly be nice
> | to see some competition there, especially if some other Ada
> | vendor would take the plunge and open source their
technology!
>
> I agree, but I will at least thank you for doing so!

Well so far it is working well for both us and our customers,
and we are happy to see quite a few serious Ada programmers
adopting GNU/Linux software systems.


Sent via Deja.com http://www.deja.com/
Share what you know. Learn what you don't.




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

* Re: Ada95 + FORTRAN 77
  1999-09-07  0:00       ` okellogg
@ 1999-09-08  0:00         ` Robert Dewar
  0 siblings, 0 replies; 14+ messages in thread
From: Robert Dewar @ 1999-09-08  0:00 UTC (permalink / raw)


In article <7r2hkn$3cb$1@nnrp1.deja.com>,
  okellogg@my-deja.com wrote:
> In article <7r0u2o$vik$1@nnrp1.deja.com>,
>   Robert Dewar <dewar@gnat.com> wrote:
> > [...] At the same time, we also
> > implemented a rather nice feature:
> >
> >   type C_Bool is new Boolean;
> >   pragma Convention (C, C_Bool);
> >
>
> Hey, that's nifty. How about suggesting this for
standardization
> in Ada-0x ?


Ada-0X is nothing more than a possibility right now. Far more
relevant at this stage is to recommend things to the ARG for
possible semi-standarization as recommended extensions, and
I will be happy to send this one along :-)

Robert Dewar
Ada Core Technologies


Sent via Deja.com http://www.deja.com/
Share what you know. Learn what you don't.




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

end of thread, other threads:[~1999-09-08  0:00 UTC | newest]

Thread overview: 14+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
1999-09-06  0:00 Ada95 + FORTRAN 77 Preben Randhol
1999-09-06  0:00 ` Gisle S�lensminde
1999-09-06  0:00   ` Preben Randhol
1999-09-06  0:00 ` lafage8770
1999-09-06  0:00   ` Matthew Heaney
1999-09-06  0:00     ` Robert Dewar
1999-09-06  0:00   ` Preben Randhol
1999-09-06  0:00     ` Robert Dewar
1999-09-06  0:00       ` Preben Randhol
1999-09-06  0:00         ` Robert Dewar
1999-09-07  0:00           ` Preben Randhol
1999-09-08  0:00             ` Robert Dewar
1999-09-07  0:00       ` okellogg
1999-09-08  0:00         ` Robert Dewar

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox