comp.lang.ada
 help / color / mirror / Atom feed
* Re: Passing procedures as parameters to procedures.
@ 1993-05-05 17:39 Robert Dewar
  0 siblings, 0 replies; 22+ messages in thread
From: Robert Dewar @ 1993-05-05 17:39 UTC (permalink / raw)


Now I've seen it all:

"Of course you can do this in Ada, just use package machine code to construct
the code that you want to execute."

Hmmm! why bother wih Ada/9X, just require Ada/83 compilers to implement
package machine code and we can do anything we like :-)

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-10 22:56 Jack Dean
  0 siblings, 0 replies; 22+ messages in thread
From: Jack Dean @ 1993-05-10 22:56 UTC (permalink / raw)


>>>>> andrewd@winnie.cs.adelaide.edu.au (Andrew Dunstan,,2285592,) writes:
 Andrew> NNTP-Posting-Host: winnie.cs.adelaide.edu.au

 Andrew> As I pointed out in this group about a year ago, there are some things
 Andrew> that you want to be able to do that you just can't with generics. If
 Andrew> anybody can provide me with a good, clean, Ada equivalent of the
 Andrew> following Pascal code, I'll send him/her (first winner only!) a good
 Andrew> bottle of Australian red wine (damn this Beaujolais business!).

 Andrew> procedure a(b : procedure(c : procedure));

 Andrew>   procedure d;	
 Andrew>   begin;
 Andrew>   end;

 Andrew>  begin
 Andrew>    b(d);
 Andrew>  end;


 Andrew> procedure x(y : procedure);
 Andrew> begin
 Andrew>   y;
 Andrew> end;

 Andrew> .
 Andrew> .
 Andrew> .
 Andrew> a(x);
 Andrew> .
 Andrew> .


OK, here is my entry.  The following is legal, portable Ada 83, and it
implement the functional equivalent of procedure pointers.

I'll start off with the Ada equivalent of the Pascal fragment you
provided:

WITH Text_Io;
WITH Procedure_Parameter_Profile;

PROCEDURE Test_Pointer IS

    SUBTYPE Dummy IS Integer;

    PACKAGE D_Proc IS NEW Procedure_Parameter_Profile (Args => Dummy);
    PACKAGE B_Proc IS NEW Procedure_Parameter_Profile (Args => D_Proc.Pointer);

    D_Pointer : D_Proc.Pointer;
    X_Pointer : B_Proc.Pointer;

    PROCEDURE A (B : B_Proc.Pointer) IS
        PROCEDURE D (Ignore : Dummy) IS
        BEGIN
            Text_Io.Put_Line ("In procedure A.D");
        END D;

        PACKAGE D_Designate IS NEW D_Proc.Designate (The_Pointer => D_Pointer,
                                                     Designated_Procedure => D)
;
    BEGIN
        B_Proc.Invoke (The_Procedure => B, With_Args => D_Pointer);
        D_Designate.Leave_Scope;
    END A;

    PROCEDURE X (Y : D_Proc.Pointer) IS
    BEGIN  
        Text_Io.Put_Line ("In Procedure X");
        D_Proc.Invoke (The_Procedure => Y, With_Args => 0);
    END X;

    PACKAGE X_Designate IS NEW B_Proc.Designate (The_Pointer => X_Pointer,
                                                 Designated_Procedure => X);

BEGIN
    A (X_Pointer);

    X_Designate.Leave_Scope;
    Text_Io.Put_Line ("That's all, folks!");
END Test_Pointer;




And now for the magic that makes it work:


GENERIC
    TYPE Args IS PRIVATE;
PACKAGE Procedure_Parameter_Profile IS

    TYPE Id      IS LIMITED PRIVATE;
    TYPE Pointer IS ACCESS Id;


    GENERIC  
        The_Pointer : IN OUT Pointer;
        WITH PROCEDURE Designated_Procedure (The_Args : IN Args);
    PACKAGE Designate IS
        PROCEDURE Leave_Scope;
    END Designate;

    PROCEDURE Invoke (The_Procedure : IN Pointer; --
                      With_Args     : IN Args);

PRIVATE

    Max_Number_Of_Procedure_Pointers : CONSTANT := 20;
    TYPE Id IS RANGE 0 .. Max_Number_Of_Procedure_Pointers;

END Procedure_Parameter_Profile;


and its implementation:


PACKAGE BODY Procedure_Parameter_Profile IS


    Last_Id : Id := 0;


    FUNCTION New_Id RETURN Id IS
    BEGIN  
        Last_Id := Last_Id + 1;
        RETURN Last_Id;
    END New_Id;



    TASK Dispatcher IS  
        ENTRY Invoke (The_Procedure_Pointer : IN Id; With_Args : IN Args);
        ENTRY Wait_For_Start (Id) (The_Args : OUT Args);
        ENTRY Wait_For_Finish (Id);
        ENTRY Signal_Finished (The_Procedure_Pointer : IN Id);
        ENTRY Shutdown;
    END Dispatcher;



    TASK BODY Dispatcher IS
        The_Args : Args;
    BEGIN
        LOOP
            SELECT
                ACCEPT Invoke (The_Procedure_Pointer : IN Id;
                               With_Args             : IN Args) DO
                    ACCEPT Wait_For_Start (The_Procedure_Pointer)
                              (The_Args : OUT Args) DO
                        The_Args := With_Args;
                    END Wait_For_Start;  
                END Invoke;
            OR
                ACCEPT Signal_Finished (The_Procedure_Pointer : IN Id) DO  
                    ACCEPT Wait_For_Finish (The_Procedure_Pointer);
                END Signal_Finished;
            OR
                TERMINATE;
            END SELECT;
        END LOOP;
    END Dispatcher;



    PACKAGE BODY Designate IS

        My_Id : Id;

        TASK Hidden IS
            ENTRY Start;
        END Hidden;

        TASK BODY Hidden IS
            The_Args : Args;
            Continue : Boolean;
        BEGIN  
            ACCEPT Start;
            LOOP
                Dispatcher.Wait_For_Start (My_Id) (The_Args);
                Designated_Procedure (The_Args);
                Dispatcher.Signal_Finished (My_Id);
            END LOOP;
        END Hidden;

        PROCEDURE Leave_Scope IS
        BEGIN
            ABORT Hidden;
            The_pointer := NULL;
        END Leave_Scope;

    BEGIN

        IF The_Pointer = NULL THEN
            The_Pointer     := NEW Id;
            The_Pointer.ALL := New_Id;
        END IF;
        My_Id := The_Pointer.ALL;
        Hidden.Start;
    END Designate;




    PROCEDURE Invoke (The_Procedure : IN Pointer; --
                      With_Args     : IN Args) IS
    BEGIN
        Dispatcher.Invoke (The_Procedure.ALL, With_Args);
        Dispatcher.Wait_For_Finish (The_Procedure.ALL);  
    END Invoke;


END Procedure_Parameter_Profile;



Try it. It works.  I'm ready for my bottle of wine.





--
Jack Dean                         dean@sweetpea.jsc.nasa.gov

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-06  9:39 cis.ohio-state.edu!zaphod.mps.ohio-state.edu!howland.reston.ans.net!darwi
  0 siblings, 0 replies; 22+ messages in thread
From: cis.ohio-state.edu!zaphod.mps.ohio-state.edu!howland.reston.ans.net!darwi @ 1993-05-06  9:39 UTC (permalink / raw)


>From article <dewar.736623350@schonberg>, by dewar@schonberg.NYU.EDU (Robert D
ewar):
> I actually think that in languages at the level of Ada/C etc, the notion of
> pointer to procedure is clearer than the idea of a procedure as a value.
> 
> An interesting note here is that one Algol-68 text book contained in its
> helpful advice the suggestion that it was better to pass procedures by
> reference rather than by value, because it would avoid inefficient copying
> of the code of the procedure. This may be an extreme case, but it is a nice
> indication of the confusion that can be caused by considering procedures as
> values in this level of language.
> 

Fair enough, Robert. I can also think of cases where there could be a
mighty confusion between a function and the value it returns (if this
is a procedural value). 

Still, my feeling is that, in the drive to avoid a profusion of new
reserved words, many, including possible "acess" and "all", have
become very overloaded. I know overloading is in the spirit of Ada :-)
but this is a bit unfortunate.

Syntax, however, is really a minor consideration. The important thing
is expressive power. Procedural objects extend that power very
markedly, but I think my example showed an area where it was missing
in Ada83 and (as Tucker Taft showed in correctly ruling out my
proposed 9X solution to my problem) will be missing in Ada9X. It would
be a pity to be able to say that there is STILL an area where Pascal
has more expressive power than Ada!

(On the subject of the problem I posed, I have changed my mind! It is
not insoluble - in fact I have solved it. Magnus Kempe's "solution",
while not correct, was close enough that, unless I see a correct
solution posted either in this news group or by email to me, I will
send him a (small) bottle of Australian red. Then he can test out
Thomas Jefferson's saying!

However, I have dreamed up a generalised form of this problem that I
still think is insoluble.)

cheers


andrew



#  Andrew Dunstan                   #   There's nothing good or bad   #
#  net:                             #                                 #
#    adunstan@steptoe.adl.csa.oz.au #   but thinking makes it so.     #
#  or: andrewd@cs.adelaide.edu.au   #                                 #

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-06  7:33 cis.ohio-state.edu!zaphod.mps.ohio-state.edu!howland.reston.ans.net!torn!
  0 siblings, 0 replies; 22+ messages in thread
From: cis.ohio-state.edu!zaphod.mps.ohio-state.edu!howland.reston.ans.net!torn! @ 1993-05-06  7:33 UTC (permalink / raw)


In article <1s82kk$dpm@huon.itd.adelaide.edu.au>, andrewd@achilles.cs.adelaide.
edu.au (Andrew Dunstan,,2285592,) writes:
: Unfortunately, my original A is recursive, and in particular it
: is called from with D. (I realise I should have told you this!)

No problem.  Wrap A and D together in a generic package and use a
call-through for X.


generic
  with procedure B;
package Wrap_AD_G is
  procedure D;
  procedure A;
end Wrap_AD_G;

package body Wrap_AD_G is
  procedure D is
  begin
    A; -- indirect recursion is expected: A -> B -> D -> A
  end D;
  
  procedure A is
  begin
    B; -- indirect recursion expected, B expected to use D
    if ... then A; end if; -- direct recursion if you wish
  end A;
end Wrap_AD_G;

procedure X;
package Wrap_AD is new Wrap_AD_G (X);

generic
  with procedure Y;
procedure X_G;
procedure X_G is
begin
  Y;
end X_G;

procedure XD is new X_G (Wrap_AD.D);
procedure X is -- call-through
begin
  XD;
end X;

procedure A renames Wrap_AD.A;

....
A;
....

Any other changing requirements :-) ?
-- 
Magnus Kempe                "No nation was ever drunk when wine was cheap."
magnus@lglsun.epfl.ch                                   -- Thomas Jefferson

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-05 21:35 cis.ohio-state.edu!news.sei.cmu.edu!ajpo.sei.cmu.edu!progers
  0 siblings, 0 replies; 22+ messages in thread
From: cis.ohio-state.edu!news.sei.cmu.edu!ajpo.sei.cmu.edu!progers @ 1993-05-05 21:35 UTC (permalink / raw)


In article <dewar.736623553@schonberg> dewar@schonberg.NYU.EDU (Robert Dewar) w
rites:
>Now I've seen it all:
>
>"Of course you can do this in Ada, just use package machine code to construct
>the code that you want to execute."
>
>Hmmm! why bother wih Ada/9X, just require Ada/83 compilers to implement
>package machine code and we can do anything we like :-)
>

Not that the above is what I said, but perhaps the implicit smiley was too 
subtle.  The intent was to answer the earlier statements that "It can't be 
done.", not to say that the demonstrated approach was desirable as a general 
mechanism. Which is why text was included indicating that 9X was the 
(obviously) preferrable way to go...

pat rogers
progers@ajpo.sei.cmu.edu

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-05 17:35 Robert Dewar
  0 siblings, 0 replies; 22+ messages in thread
From: Robert Dewar @ 1993-05-05 17:35 UTC (permalink / raw)


I actually think that in languages at the level of Ada/C etc, the notion of
pointer to procedure is clearer than the idea of a procedure as a value.

An interesting note here is that one Algol-68 text book contained in its
helpful advice the suggestion that it was better to pass procedures by
reference rather than by value, because it would avoid inefficient copying
of the code of the procedure. This may be an extreme case, but it is a nice
indication of the confusion that can be caused by considering procedures as
values in this level of language.

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-05 16:30 cis.ohio-state.edu!zaphod.mps.ohio-state.edu!magnus.acs.ohio-state.edu!us
  0 siblings, 0 replies; 22+ messages in thread
From: cis.ohio-state.edu!zaphod.mps.ohio-state.edu!magnus.acs.ohio-state.edu!us @ 1993-05-05 16:30 UTC (permalink / raw)


In article <1993May4.221355.13487@evb.com> jgg@evb.com (John Goodsen) writes:

>   In article <1993May3.190746.1043@ee.ubc.ca> luisl@ee.ubc.ca 
>       (luis linares-rojas) writes:
>   >Subject: Procedures/functions as parameters to procedures/functions.
>   >Before commiting myself to any long term commitment with the Ada
>   >language, I've been revising its capabilities.  There is
>   >something that I have not found so far: how to pass a procedure
>   >(or a function) as a parameter to another procedure (or
>   >function).  Or, in the same spirit, how to create an array of
>   >procedures.  The question is: is there a way of doing this in
>   >Ada, and (if so) how?  I'd appreciate any help.
>
>   If you can't wait for Ada 9X and you need dynamic binding of 
>   the procedure to call, then you might also check out how it's
>   currently done in the Xt/Motif bindings which support call by
>   address of Ada procedures from C.  Basically, you 
>   pass the address of an Ada procedure to an external routine 
>   using the 'ADDRESS attribute and have that routine call the Ada routine 
>   that was passed to it.  Of course, this has the usual side effects 
>   of being compiler dependent, etc... but it works in Ada 83.

If you do this, be aware that you may not be able to do this for
nested procedures.  In our compiler, and probably in other Ada
compilers, nested procedures take "hidden" parameters, e.g.:

    procedure A (x : integer) is
       local_variable : integer;
       procedure B (y : integer) is
       begin
          ...
       end B;
    begin
       ...
    end A;

The code for B actually takes two parameters;  the extra parameter is
a frame pointer that allows B to access local variables defined in A
(such as local_variable).  So if you pass B'ADDRESS to a C or
assembly-language routine that tries to call B, you will not get the
desired results.

                               -- Adam
       

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-05 11:40 cis.ohio-state.edu!news.sei.cmu.edu!firth
  0 siblings, 0 replies; 22+ messages in thread
From: cis.ohio-state.edu!news.sei.cmu.edu!firth @ 1993-05-05 11:40 UTC (permalink / raw)


In article <1993May4.183607@di.epfl.ch> Magnus.Kempe@di.epfl.ch (Magnus Kempe) 
writes:
>In article <1993May4.094549.13420@sei.cmu.edu>, firth@sei.cmu.edu (Robert Firt
h) writes:
>: [...] trying to replicate something like the Algol-60
>: 
>: 	real procedure Integrate ( real procedure F; real lwb, upb );
>: 
>: and put it in a library package somewhere.  You can't do it.
>
>Use generics (for simple cases--99.99%):

Well, yes, you can use generics.  Unfortunately, with most Ada
implementations, what you get is, in effect, a type-checked
macroexpansion of the code body.  Apart from its bulk, this
has the problem that any change to the implementation of the
Integrate routine requires every program that uses it to be
recompiled.

In my opinion, this is completely contrary to the concept of
a subroutine library as we have understood it for over thirty
years, and a maintenance headache any reasonable person would
want to avoid.

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-05  9:50 cis.ohio-state.edu!magnus.acs.ohio-state.edu!usenet.ins.cwru.edu!howland.
  0 siblings, 0 replies; 22+ messages in thread
From: cis.ohio-state.edu!magnus.acs.ohio-state.edu!usenet.ins.cwru.edu!howland. @ 1993-05-05  9:50 UTC (permalink / raw)


>From article <1993May4.154040@di.epfl.ch>, by Magnus.Kempe@di.epfl.ch (Magnus 
Kempe):
> : [Pascal code omitted]
> The solution is to make "D" visible.
> package Wrap_AD is
>   procedure D;
>   generic
>     with procedure B;
>   procedure A_G;
> end Wrap_AD;
> package body Wrap_AD is
>   procedure D is begin null; end D;
>   procedure A_G is
>   begin
>     B;
>   end A_G;
> end Wrap_AD;
> generic
>   with procedure Y;
> procedure X_G;
> procedure X_G is
> begin
>   Y;
> end X_G;
> procedure X is new X_G (Wrap_AD.D);
> procedure A is new Wrap_AD.A_G (X);
> ....
> A;
> ....
> 
> 
> Good enough?



Nope! Unfortunately, my original A is recursive, and in particular it
is called from with D. (I realise I should have told you this!) So,
since A must be generic, D must be nested inside it (a generic
procedure can only be called from within itself).

I believe that the problem is insoluble, since B needs to be both
generic (so it can be instantiated with D) and non-generic (so it can
be an actual generic parameter of A).


Good try, though.

BTW, the original code is not mine, and I don't feel that I can post
it on the net without the author's permission (he is currently on
study leave). Trust me that I have faithfully set out the essential
elements of it.




cheers


andrew


#  Andrew Dunstan                   #   There's nothing good or bad   #
#  net:                             #                                 #
#    adunstan@steptoe.adl.csa.oz.au #   but thinking makes it so.     #
#  or: andrewd@cs.adelaide.edu.au   #                                 #

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-04 23:44 cis.ohio-state.edu!magnus.acs.ohio-state.edu!zaphod.mps.ohio-state.edu!ho
  0 siblings, 0 replies; 22+ messages in thread
From: cis.ohio-state.edu!magnus.acs.ohio-state.edu!zaphod.mps.ohio-state.edu!ho @ 1993-05-04 23:44 UTC (permalink / raw)


What amuses in this discussion, is the sub-thread about the
storage management penalties (allegedly?) imposed by procedures-
as-parameters. The amusement stems from the fact that:

********Ada(83) already requires that valid implementations pay
********an even greater penalty than that required by mere
********provedures-as-parameters.

To cut a long story short, read ``Full Functional Programming
in a Declarative Ada Dialect'', in the proceedings of the 1992
TRI-Ada conference (pp. 350-358), by P. Bailes (that's me), D.
Johnston, E. Salzman and L. Wang. The really keen can contact me
for a copy of University of Queensland Department of Computer
Science Technical Report 225 ``First Class Functions for Ada''.

The idea is that function-*valued*-functions, like in functional
programming languages (and not just procedures/functions as
parameters to procedures/functions) are avaialble in Ada through
direct (ie non-interpretive) translation into a complex of tasks.
In other words, Ada tasks require Ada implementations already to
be equipped with all the (heap etc.) storage management facilities
needed to implement a language construct much more ambitious than
this thread has so far contemplated.

The interesting question should therefore be why 9X doesn't have
function-valued-functions - sure, there are lots of sociological
etc. issues that surround a language design, but let's keep this
on a purely technical, almost Platonic, plane. (I've had a few words
with the 9X gurus at TRI-Ada about this, but to my mind inconclusively.)
--
Paul A Bailes
paul@cs.uq.oz.au

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-04 22:13 John Goodsen
  0 siblings, 0 replies; 22+ messages in thread
From: John Goodsen @ 1993-05-04 22:13 UTC (permalink / raw)


In article <1993May3.190746.1043@ee.ubc.ca> luisl@ee.ubc.ca (luis linares-rojas
) writes:
>Subject: Procedures/functions as parameters to procedures/functions.
>Before commiting myself to any long term commitment with the Ada language,
>I've been revising its capabilities.  There is something that I have not
>found so far: how to pass a procedure (or a function) as a parameter to anothe
r
>procedure (or function).  Or, in the same spirit, how to create an array of
>procedures.  The question is: is there a way of doing this in Ada, and (if so)
>how?  I'd appreciate any help.

If you can't wait for Ada 9X and you need dynamic binding of 
the procedure to call, then you might also check out how it's
currently done in the Xt/Motif bindings which support call by
address of Ada procedures from C.  Basically, you 
pass the address of an Ada procedure to an external routine 
using the 'ADDRESS attribute and have that routine call the Ada routine 
that was passed to it.  Of course, this has the usual side effects 
of being compiler dependent, etc... but it works in Ada 83.

As was pointed out in a previous reply,  you'll have this in Ada 9X,
if you can wait that long.


-- 
John Goodsen                EVB Software Engineering, Inc.
jgg@evb.com                    - Ada & Object Oriented Training/Products
(301) 695-6960                 - Ada GUI & Graphics Tools and Training
                               - Software Reuse, Process & Environments

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-04 19:39 cis.ohio-state.edu!pacific.mps.ohio-state.edu!zaphod.mps.ohio-state.edu!m
  0 siblings, 0 replies; 22+ messages in thread
From: cis.ohio-state.edu!pacific.mps.ohio-state.edu!zaphod.mps.ohio-state.edu!m @ 1993-05-04 19:39 UTC (permalink / raw)


Well, it isn't that you cannot do it at all, it just isn't portable (which
it should be, of course, thus 9X), and restrictions do exist.  In particular,
the code that follows only works (on my compiler) for library unit level
parameterless procedures.

Certainly, on some implementations this approach won't work at all, due to 
restrictions regarding 'Address for subprograms (at least one always returns
"address zero").  These restrictions are not universal by any means. 

The following is for Systems Designers 680X0 compilers:

 

with system;
package call_backs is
  subtype parameterless_procedure is system.address;
  procedure sign_in( caller : in parameterless_procedure );
  procedure make_calls;
end call_backs;


with call_by_address;
package body call_backs is

  callers : array(1..255) of parameterless_procedure;

  next : integer range 1 .. 255 := 1;

  procedure sign_in( caller : in parameterless_procedure ) is
  begin
    callers(next) := caller;
    next := next + 1;
  end sign_in;

  procedure make_calls is
  begin
    for K in 1 .. Next-1 loop
      call_by_address( callers(K) );
    end loop;
  end make_calls;

end call_backs;


All well and good, you say, but what is this "call_by_address" procedure?
It uses package Machine_Code to do a JSR to the desired routine, and uses
an implementation-defined mechanism (the pragma) to associate the parameter
(callee) with the register (A0) used in the JSR.  Other implementations 
would use a different format for the JSR and for the parameter association 
mechanism...


with System;
with Machine_Code; 

procedure call_by_address( callee : in system.address ) is
  use Machine_Code;
begin
  EA_INST'( Mode => A0_Indirect, Opcode => JSR );
end call_by_address;

pragma Inline( Call_By_Address );

pragma Call_Sequence_Procedure( unit => call_by_address,
                                parameter_types => (system.address),
                                mechanism => ( Value (A0) )
                              );

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-04 16:41 cis.ohio-state.edu!zaphod.mps.ohio-state.edu!howland.reston.ans.net!ira.u
  0 siblings, 0 replies; 22+ messages in thread
From: cis.ohio-state.edu!zaphod.mps.ohio-state.edu!howland.reston.ans.net!ira.u @ 1993-05-04 16:41 UTC (permalink / raw)


In article <1993May4.094549.13420@sei.cmu.edu>, firth@sei.cmu.edu (Robert Firth
) writes:
: [...] trying to replicate something like the Algol-60
: 
: 	real procedure Integrate ( real procedure F; real lwb, upb );
: 
: and put it in a library package somewhere.  You can't do it.

Use generics (for simple cases--99.99%):

generic
  with
    function F (X : Float)
      return Float;

function Integrate (Lower_Bound, Upper_Bound : Float)
  return Float;


function Sin (X : Float)
  return Float;

function Integrate_Sin is -- Sin many times :-)
  new Integrate (F => Sin);


I am constantly amazed that the power of generics is so widely
underestimated.  I've even heard that some people prefer to use
the C preprocessor to _simulate_ instantiations instead of using
Ada's genericity.  Please say I'm wrong.
-- 
Magnus Kempe                "No nation was ever drunk when wine was cheap."
magnus@lglsun.epfl.ch                                   -- Thomas Jefferson

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-04 16:25 Mark A Biggar
  0 siblings, 0 replies; 22+ messages in thread
From: Mark A Biggar @ 1993-05-04 16:25 UTC (permalink / raw)


In article <1993May4.154040@di.epfl.ch> Magnus.Kempe@di.epfl.ch (Magnus Kempe) 
writes:
>In article <1s5gae$kr4@huon.itd.adelaide.edu.au>, andrewd@winnie.cs.adelaide.e
du.au (Andrew Dunstan,,2285592,) writes:
>: As I pointed out in this group about a year ago, there are some things
>: that you want to be able to do that you just can't with generics. If
>: anybody can provide me with a good, clean, Ada equivalent of the
>: following Pascal code, I'll send him/her (first winner only!) a good
>: bottle of Australian red wine (damn this Beaujolais business!).
>: [Pascal code omitted]
>The solution is to make "D" visible.
>package Wrap_AD is
>  procedure D;
>  generic
>    with procedure B;
>  procedure A_G;
>end Wrap_AD;
>package body Wrap_AD is
>  procedure D is begin null; end D;
>  procedure A_G is
>  begin
>    B;
>  end A_G;
>end Wrap_AD;
>generic
>  with procedure Y;
>procedure X_G;
>procedure X_G is
>begin
>  Y;
>end X_G;
>procedure X is new X_G (Wrap_AD.D);
>procedure A is new Wrap_AD.A_G (X);
>...
>A;
>...
>Two drawbacks: if D needs to access local variables of A_G, these
>variables must be made global (but may be hidden in the body of
>Wrap_A); the parameter B to A_G need not call D, but you may consider
>it a "feature", a more powerful variant.

I think there is a way in Ada9x generics to do this and still keep the
nesting of d with out resorting to access to subprogram types.
If b were to be defined as a generic subprogram inside a generic package,
then by using the new genreic package formals you can instantate a with 
a generic version of b that can be instantiated inside the instantiation of a.

--
Mark Biggar
mab@wdl1.wdl.loral.com

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-04 15:43 Tucker Taft
  0 siblings, 0 replies; 22+ messages in thread
From: Tucker Taft @ 1993-05-04 15:43 UTC (permalink / raw)


In article <1993May4.102922.16895@sei.cmu.edu> 
firth@sei.cmu.edu (Robert Firth) writes:

>In article <C6I9J9.J9E@inmet.camb.inmet.com> 
stt@spock.camb.inmet.com (Tucker Taft) writes:

>. . . There are certainly languages where procedures
>>are first class objects, and can be freely assigned, passed around,
>>returned from functions, etc.  Such languages (e.g. Scheme) typically require
>>garbage collection, and the ability to have the activation record
>>for a subprogram on the heap.  
>
>Well, I've implemented three such languages, and none of them required
>garbage collection, activation records on the heap, or anything one
>tenth as complicated.  There is exactly one semantic problem with
>procedures as first class objects, and its the exact same problem as
>you have with variables as first class objects: references from more
>global entities to more local entities.  The usual simple solutions
>apply.  The simplest, and one made very easy by Ada's abstraction and
>packaging capability, is to rule that nested procedures are not first
>class.  Modula-2 has the same rule, and it made implementation of
>procedure values and variables very straightforward.

Unfortunately, in the example, the procedure was nested.
It is certainly true that if you only want un-nested
procedures to be "first class" then there is no problem.
Based on the example, I presumed the original questioner
was interested in a more general concept of "first class procedures."

Note, also, that the generic "contract" model interacts badly
with restrictions related to nesting.

In any case, I think Robert and I are in general agreement.
You can call these references "subprograms" or "access-to-subprograms,"
but if you want to avoid garbage collection, etc., you have to
live with some limitations on references to nested subprograms.

S. Tucker Taft  stt@inmet.com

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-04 14:29 cis.ohio-state.edu!pacific.mps.ohio-state.edu!linac!uwm.edu!spool.mu.edu!
  0 siblings, 0 replies; 22+ messages in thread
From: cis.ohio-state.edu!pacific.mps.ohio-state.edu!linac!uwm.edu!spool.mu.edu! @ 1993-05-04 14:29 UTC (permalink / raw)


In article <C6I9J9.J9E@inmet.camb.inmet.com> stt@spock.camb.inmet.com (Tucker T
aft) writes:

>One person's "implementation detail" is another person's "fundamental
>semantic model."  There are certainly languages where procedures
>are first class objects, and can be freely assigned, passed around,
>returned from functions, etc.  Such languages (e.g. Scheme) typically require
>garbage collection, and the ability to have the activation record
>for a subprogram on the heap.  

Well, I've implemented three such languages, and none of them required
garbage collection, activation records on the heap, or anything one
tenth as complicated.  There is exactly one semantic problem with
procedures as first class objects, and its the exact same problem as
you have with variables as first class objects: references from more
global entities to more local entities.  The usual simple solutions
apply.  The simplest, and one made very easy by Ada's abstraction and
packaging capability, is to rule that nested procedures are not first
class.  Modula-2 has the same rule, and it made implementation of
procedure values and variables very straightforward.

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-04 13:59 Tucker Taft
  0 siblings, 0 replies; 22+ messages in thread
From: Tucker Taft @ 1993-05-04 13:59 UTC (permalink / raw)


In article <1s5gae$kr4@huon.itd.adelaide.edu.au> 
  andrewd@cs.adelaide.edu.au writes:

>> First Ada9x is adding access to procedure/function types so that is a
>> non-problem in Ada9x.
>
>Yes, and very welcome, too. If any of the 9X heavies can explain to me
>why this has to be done in terms of access types, though, I'd be
>grateful. The fact that this is done in terms of a procedure closure
>is an implementation detail, it seems to me. 

One person's "implementation detail" is another person's "fundamental
semantic model."  There are certainly languages where procedures
are first class objects, and can be freely assigned, passed around,
returned from functions, etc.  Such languages (e.g. Scheme) typically require
garbage collection, and the ability to have the activation record
for a subprogram on the heap.  

This is all well and good, but our view is that Ada 
is not trying to compete with such languages.  Ada has already
been accused of trying to be all things to all people.
Our view is that Ada is intended as a systems programming 
language, where the programmer has complete understanding 
and complete control over the implementation.
It is great if it ends up as a generally useful
language for the implementation of other
kinds of programs, but we believe it is important to
keep a clear focus on our primary market of systems programming.

Little if anything is an "implementation detail" to a systems programmer,
especially a real-time systems programmer.  If a programmer wants
to introduce a level of abstraction, it should be done by defining an
abstract data type (ADT), but it is still important to be able to
implement such an ADT in efficient, concrete terms.

Given the above philosophy, we believe it is appropriate that
the language be consistent with the implementation model.  Clearly
a subprogram "variable" is not a holder for code.  It is a reference
to code.  In Ada 83, storable references are called access values.
It is true that if all we wanted to allow were parameters that
referred to subprograms, there would be no reason to think of them
as access values, since Ada 83 already allows "implicit" references
as part of parameter passing.  But if one is going to have storable
references to code, allowing for arrays of such references, etc., 
it is important that one recognize that these are semantically 
like references (i.e. access values), not like copies.

Furthermore, from the point of view of the semantic model,
it is essential to recognize that there is a possibility of
dangling references (in the absence of heap allocation of 
activation records).  This same problem exists with "normal"
access-to-object values in Ada 9X, because one is allowed to
"point" to declared objects (so long as they are marked "aliased").
It is simpler to associate checks designed to prevent dangling
references with access types in general, rather than having
some with access-to-object types, and some with "subprogram types."

One final reason to avoid the term "subprogram type" -- one would
inevitably relate them to "task type."  But they are completely
different from task types.  A task type is a template for a task.
All instances of a task type are associate with the same code body.
The only difference is the data associated with them.  The analogous
"subprogram type" would have similar properties, and be essentially
useless.  Now one could alternatively argue that task types ought
to be changed, to make them more like the Ada 9X access-to-subprogram types,
specifying only an interface, allowing variables of such a type
to refer to task objects with any associated code body, so long
as they had a matching interface.  Not a bad idea, but then one would
probably want to view them as access-to-task types, since one would
presumably want to have assignable variables of such a type.

In any case, hopefully this rambling discussion exposes some
of the reasons we chose to make them access-to-subprogram types.
As mentioned above, we would agree that "subprogram types" would
make sense if either they were limited to being parameters only,
or if they were truly "first-class" objects with heap allocation
of activation records.  However, the user requirement seemed to be
for an assignable reference to a subprogram, which in our view,
is clearly a better fit for an "access-to-subprogram" type rather
than a "subprogram type."

> . . .
>In Ada9X the answer will look like this:
>
>type d_proc is access procedure;
>type b_proc is access procedure(c : d_proc);
>
>procedure a(b : b_proc) is
>  procedure d is
>  begin
>    null;
>  end;
>begin
>  b(d'access);

I hate to be the one to break the news, but this is not
legal Ada 9X.  Since the access type is declared at the outermost level,
so must be the designated procedure.  Hence, you must declare
"d" outside of "a".  Otherwise, there would be nothing preventing
someone storing away the reference to "d" in some global variable
of type "d_proc," which would become a dangling reference as soon
as "a" returned.  One could move this kind of "accessibility" check
to the assignment to the global, but that would require that
all access-to-subprogram values carry around an "accessiblity level"
indicator of some sort.  It would also mean that the check would
move from being a compile-time check to being a run-time check,
which is always less safe.

Alternatively, one could have two kinds of access-to-subprogram
types, one "limited" and only usable for parameters (no
assignment), and one "nonlimited," permitting assignment, etc.
We considered this, but it was ultimately rejected as unnecessary
complexity.  Perhaps if you had a more complete example showing
how generics can't solve this important class of problems, there
would be more sympathy for providing some mechanism addressing
this issue.

>end;
>
>procedure x(y : d_proc) is
>begin
>  y.all;
>end;
>.
>.
>.
>a(x'access);
>.
>.
>.
>
>BTW, this example comes from real, working and useful Pascal code, not
>(as some might think) from a contest on obfuscated Pascal!

Must "d" be a nested procedure, or was it just the normal Pascal
tendency to nest things?

>Happy programming.
>#  Andrew Dunstan                   #   There's nothing good or bad   #
>#  net:                             #                                 #
>#    adunstan@steptoe.adl.csa.oz.au #   but thinking makes it so.     #
>#  or: andrewd@cs.adelaide.edu.au   #                                 #

S. Tucker Taft    stt@inmet.com
Ada 9X Mapping/Revision Team
Intermetrics, Inc.
Cambridge, MA  02138
USA

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-04 13:45 cis.ohio-state.edu!magnus.acs.ohio-state.edu!usenet.ins.cwru.edu!howland.
  0 siblings, 0 replies; 22+ messages in thread
From: cis.ohio-state.edu!magnus.acs.ohio-state.edu!usenet.ins.cwru.edu!howland. @ 1993-05-04 13:45 UTC (permalink / raw)


In article <1993May3.190746.1043@ee.ubc.ca> luisl@ee.ubc.ca (luis linares-rojas
) writes:

>Before commiting myself to any long term commitment with the Ada language,
>I've been revising its capabilities.  There is something that I have not
>found so far: how to pass a procedure (or a function) as a parameter to anothe
r
>procedure (or function).  Or, in the same spirit, how to create an array of
>procedures.  The question is: is there a way of doing this in Ada, and (if so)
>how?  I'd appreciate any help.

Alas, Ada has no good way to do this, and I doubt you'd want to maintain
code that used any of several bad ways.  I assume for your first problem
you're trying to replicate something like the Algol-60

	real procedure Integrate ( real procedure F; real lwb, upb );

and put it in a library package somewhere.  You can't do it.

The second problem is typified by a finite state machine: you have a
two-dimensional array indexed on [state, input], and each component is
a procedure Action that returns the new state.  And you probably want
to change the actions on the fly.  Nope, you can't do that either.

Sorry; as I see it, either use another language or hold your breath 
until Ada93.

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-04 13:45 cis.ohio-state.edu!pacific.mps.ohio-state.edu!linac!uwm.edu!cs.utexas.edu
  0 siblings, 0 replies; 22+ messages in thread
From: cis.ohio-state.edu!pacific.mps.ohio-state.edu!linac!uwm.edu!cs.utexas.edu @ 1993-05-04 13:45 UTC (permalink / raw)


In article <1s5gae$kr4@huon.itd.adelaide.edu.au>, andrewd@winnie.cs.adelaide.ed
u.au (Andrew Dunstan,,2285592,) writes:
:
: As I pointed out in this group about a year ago, there are some things
: that you want to be able to do that you just can't with generics. If
: anybody can provide me with a good, clean, Ada equivalent of the
: following Pascal code, I'll send him/her (first winner only!) a good
: bottle of Australian red wine (damn this Beaujolais business!).
: [Pascal code omitted]

The solution is to make "D" visible.


package Wrap_AD is

  procedure D;
  
  generic
    with procedure B;
  procedure A_G;

end Wrap_AD;

package body Wrap_AD is

  procedure D is begin null; end D;
  
  procedure A_G is
  begin
    B;
  end A_G;

end Wrap_AD;


generic
  with procedure Y;
procedure X_G;

procedure X_G is
begin
  Y;
end X_G;


procedure X is new X_G (Wrap_AD.D);

procedure A is new Wrap_AD.A_G (X);

...
A;
...


Two drawbacks: if D needs to access local variables of A_G, these
variables must be made global (but may be hidden in the body of
Wrap_A); the parameter B to A_G need not call D, but you may consider
it a "feature", a more powerful variant.

Good enough?
-- 
Magnus Kempe                "No nation was ever drunk when wine was cheap."
magnus@lglsun.epfl.ch                                   -- Thomas Jefferson

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-04 10:25 cis.ohio-state.edu!zaphod.mps.ohio-state.edu!magnus.acs.ohio-state.edu!us
  0 siblings, 0 replies; 22+ messages in thread
From: cis.ohio-state.edu!zaphod.mps.ohio-state.edu!magnus.acs.ohio-state.edu!us @ 1993-05-04 10:25 UTC (permalink / raw)


>From article <1993May3.203627.29250@wdl.loral.com>, by mab@wdl39.wdl.loral.com
 (Mark A Biggar):
> In article <1993May3.190746.1043@ee.ubc.ca> luisl@ee.ubc.ca (luis linares-roj
as) writes:
>>Subject: Procedures/functions as parameters to procedures/functions.
>>Before commiting myself to any long term commitment with the Ada language,
>>I've been revising its capabilities.  There is something that I have not
>>found so far: how to pass a procedure (or a function) as a parameter to anoth
er
>>procedure (or function).  Or, in the same spirit, how to create an array of
>>procedures.  The question is: is there a way of doing this in Ada, and (if so
)

Any good Ada book (e.g. Barnes' "Programming in Ada") would reveal
that you cannot do this directly in Ada83.

> 
> First Ada9x is adding access to procedure/function types so that is a
> non-problem in Ada9x.
> 

Yes, and very welcome, too. If any of the 9X heavies can explain to me
why this has to be done in terms of access types, though, I'd be
grateful. The fact that this is done in terms of a procedure closure
is an implementation detail, it seems to me. Why not just have
something like:

type some_proc is procedure;

.
.
.

some_proc := a_procedure;

Access types in 9X are becoming a bit too overloaded for my liking.
(I'll live with it, though!)


> In Ada83, it is not quit so simple.  First notice that as there is no
> way to dynamicly create procedures at run time, the set of procedures
> (include functions here as well) that could be passed as a parameter or
> used in an array is statically known at compile time.  So for passing
> procedures just compile it up as a generic and locally instantiate the
> generic in the local declarative region where you need to call the
> parameterized routine.  For example, the usual integrate example:
> 
[example omitted]
> Now for the array of pointers case your only option it to write a procedure
> containing a big case statement, but thats functiuonaly equivalent isn't it.
> If you need to change behavior on the fly, just include all possible
> callable procedures in the case statememnt and use a mapping function
> call as the controlling expression for the case statement.
> 
> Suitable inline pragmas and a compiler optimizer that knows how to do goto
> and sub-call chaining, and this can be just as effecient as the original arra
y
> of pointers to procedures.
> 


As I pointed out in this group about a year ago, there are some things
that you want to be able to do that you just can't with generics. If
anybody can provide me with a good, clean, Ada equivalent of the
following Pascal code, I'll send him/her (first winner only!) a good
bottle of Australian red wine (damn this Beaujolais business!).

procedure a(b : procedure(c : procedure));

  procedure d;	
  begin;
  end;

 begin
   b(d);
 end;


procedure x(y : procedure);
begin
  y;
end;

.
.
.
a(x);
.
.


(Of course, I've abstracted away the inessential details).

In Ada9X the answer will look like this:

type d_proc is access procedure;
type b_proc is access procedure(c : d_proc);

procedure a(b : b_proc) is
  procedure d is
  begin
    null;
  end;
begin
  b(d'access);
end;

procedure x(y : d_proc) is
begin
  y.all;
end;
.
.
.
a(x'access);
.
.
.

BTW, this example comes from real, working and useful Pascal code, not
(as some might think) from a contest on obfuscated Pascal!


Happy programming.
#  Andrew Dunstan                   #   There's nothing good or bad   #
#  net:                             #                                 #
#    adunstan@steptoe.adl.csa.oz.au #   but thinking makes it so.     #
#  or: andrewd@cs.adelaide.edu.au   #                                 #

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Re: Passing procedures as parameters to procedures.
@ 1993-05-03 20:36 Mark A Biggar
  0 siblings, 0 replies; 22+ messages in thread
From: Mark A Biggar @ 1993-05-03 20:36 UTC (permalink / raw)


In article <1993May3.190746.1043@ee.ubc.ca> luisl@ee.ubc.ca (luis linares-rojas
) writes:
>Subject: Procedures/functions as parameters to procedures/functions.
>Before commiting myself to any long term commitment with the Ada language,
>I've been revising its capabilities.  There is something that I have not
>found so far: how to pass a procedure (or a function) as a parameter to anothe
r
>procedure (or function).  Or, in the same spirit, how to create an array of
>procedures.  The question is: is there a way of doing this in Ada, and (if so)
>how?  I'd appreciate any help.

First Ada9x is adding access to procedure/function types so that is a
non-problem in Ada9x.

In Ada83, it is not quit so simple.  First notice that as there is no
way to dynamicly create procedures at run time, the set of procedures
(include functions here as well) that could be passed as a parameter or
used in an array is statically known at compile time.  So for passing
procedures just compile it up as a generic and locally instantiate the
generic in the local declarative region where you need to call the
parameterized routine.  For example, the usual integrate example:

generic
with function f(x: float) return float is <>;
function integrate(low: float; high: float);

function integrate(low: float; high: float) is
begin
    ...
end integrate;

function sin(x: float) return float is ...;
function cos(x: float) return float is ...;

Then to use it somewhere just instantiate it like so:

declare
    function int_sin(l: float; h: float) is new integrate(sin);
begin
    ...   -- code that call int_sin
end;

Now for the array of pointers case your only option it to write a procedure
containing a big case statement, but thats functiuonaly equivalent isn't it.
If you need to change behavior on the fly, just include all possible
callable procedures in the case statememnt and use a mapping function
call as the controlling expression for the case statement.

Suitable inline pragmas and a compiler optimizer that knows how to do goto
and sub-call chaining, and this can be just as effecient as the original array
of pointers to procedures.

--
Mark Biggar
mab@wdl1.wdl.loral.com

^ permalink raw reply	[flat|nested] 22+ messages in thread
* Passing procedures as parameters to procedures.
@ 1993-05-03 19:07 cis.ohio-state.edu!magnus.acs.ohio-state.edu!zaphod.mps.ohio-state.edu!ho
  0 siblings, 0 replies; 22+ messages in thread
From: cis.ohio-state.edu!magnus.acs.ohio-state.edu!zaphod.mps.ohio-state.edu!ho @ 1993-05-03 19:07 UTC (permalink / raw)


Subject: Procedures/functions as parameters to procedures/functions.

Before commiting myself to any long term commitment with the Ada language,
I've been revising its capabilities.  There is something that I have not
found so far: how to pass a procedure (or a function) as a parameter to another
procedure (or function).  Or, in the same spirit, how to create an array of
procedures.  The question is: is there a way of doing this in Ada, and (if so)
how?  I'd appreciate any help.

L.R.Linares
Dept. of Electrical Engineering
The University of British Columbia
Vancouver, B.C., Canada

luisl@ee.ubc.ca

-------------------------------------------------------------------------------
-
-- 
+----------------------------------------+
| L.R.Linares                            |
| luisl@ee.ubc.ca                        |
|                                        |
| The University of British Columbia     |
| Department of Electrical Engineering   |
| 2356 Main Mall                         |
| Vancouver, B.C.                        |

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

end of thread, other threads:[~1993-05-10 22:56 UTC | newest]

Thread overview: 22+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
1993-05-05 17:39 Passing procedures as parameters to procedures Robert Dewar
  -- strict thread matches above, loose matches on Subject: below --
1993-05-10 22:56 Jack Dean
1993-05-06  9:39 cis.ohio-state.edu!zaphod.mps.ohio-state.edu!howland.reston.ans.net!darwi
1993-05-06  7:33 cis.ohio-state.edu!zaphod.mps.ohio-state.edu!howland.reston.ans.net!torn!
1993-05-05 21:35 cis.ohio-state.edu!news.sei.cmu.edu!ajpo.sei.cmu.edu!progers
1993-05-05 17:35 Robert Dewar
1993-05-05 16:30 cis.ohio-state.edu!zaphod.mps.ohio-state.edu!magnus.acs.ohio-state.edu!us
1993-05-05 11:40 cis.ohio-state.edu!news.sei.cmu.edu!firth
1993-05-05  9:50 cis.ohio-state.edu!magnus.acs.ohio-state.edu!usenet.ins.cwru.edu!howland.
1993-05-04 23:44 cis.ohio-state.edu!magnus.acs.ohio-state.edu!zaphod.mps.ohio-state.edu!ho
1993-05-04 22:13 John Goodsen
1993-05-04 19:39 cis.ohio-state.edu!pacific.mps.ohio-state.edu!zaphod.mps.ohio-state.edu!m
1993-05-04 16:41 cis.ohio-state.edu!zaphod.mps.ohio-state.edu!howland.reston.ans.net!ira.u
1993-05-04 16:25 Mark A Biggar
1993-05-04 15:43 Tucker Taft
1993-05-04 14:29 cis.ohio-state.edu!pacific.mps.ohio-state.edu!linac!uwm.edu!spool.mu.edu!
1993-05-04 13:59 Tucker Taft
1993-05-04 13:45 cis.ohio-state.edu!magnus.acs.ohio-state.edu!usenet.ins.cwru.edu!howland.
1993-05-04 13:45 cis.ohio-state.edu!pacific.mps.ohio-state.edu!linac!uwm.edu!cs.utexas.edu
1993-05-04 10:25 cis.ohio-state.edu!zaphod.mps.ohio-state.edu!magnus.acs.ohio-state.edu!us
1993-05-03 20:36 Mark A Biggar
1993-05-03 19:07 cis.ohio-state.edu!magnus.acs.ohio-state.edu!zaphod.mps.ohio-state.edu!ho

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