comp.lang.ada
 help / color / mirror / Atom feed
* SOLVED! Decoupled Mutual Recursion Challenger
@ 1994-10-12 22:49 John Volan
  1994-10-17 15:48 ` John Volan
  0 siblings, 1 reply; 45+ messages in thread
From: John Volan @ 1994-10-12 22:49 UTC (permalink / raw)


[Okay, I give in.  Nobody seems to want to bite on this one, and a lot of
people seem to be waiting with baited breath.  Well, fine.  Here goes ... 
Oh, by the way, *LONG POST WARNING* -- as if I needed to tell you! :-) ]

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

DECOUPLED MUTUAL RECURSION CHALLENGER -- SOLVED!
------------------------------------------------

Yes, folks, there *is* an ANSWER.  A simple, elegant ANSWER.  (No,
it's not "42".  This in only Ada, after all, not Life, the Universe,
and Everything. :-)

In a word, the solution is: GENERICS.

Think about it.  What are generics, really?  Loosely speaking,
generics are "incomplete" pieces of code, with "blanks" that need to
be "filled in" later.  This makes them ideal for two very important
uses, one which is well-known and much ballyhoo-ed, and another which
gets very little press at all:

(1) REUSE -- Just fill in the blanks as many times as you like!

(2) DEFERRED COUPLING -- Just write whatever you can now, and worry about
    filling in the blanks later, when you know more.

Isn't the problem of decoupled mutual recursion just a case of
deferred coupling?  Consider: We need to be able to establish some
kind of type that can express the "identity" of objects of a given
class, even before the interface for that class has been defined.  It
doesn't matter if this "identity" type is "opaque", as long as it will
be possible to convert that "opaque identity" into a "transparent"
identity (say, a pointer type) -- *eventually*, once we've had a chance
to establish the interface for the class.

Here's my solution, and it takes advantage of both applications of
generics -- reuse as well as deferred coupling: 

First, we need to establish the following support package:

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

    generic                  -- Note: Ada allows parameterless generics!
    package Identity is

      -- Identity.Value
      type Value is private; 

      -- Each instantiation of this package establishes a new Identity.Value
      -- type for (presumably) a new class of object.  At first, this type
      -- is "opaque": the only operations available for it are assignment 
      -- ( ":=" ) and predefined equality and inequality ( "=" and "/=" ).
      -- However, because of the nested generic package below, each such
      -- type has the *potential* to be translatable into some "transparent"
      -- pointer type -- eventually.  But at this point, there is no
      -- way to actually generate any Identity.Value other than Identity.None.

      -- Identity.None    
      None : constant Identity.Value;

      -- NOTE: Identity.Value objects are guaranteed to be default-initialized
      -- to the value Identity.None, mimicking the default initialization 
      -- of access types to the value null.
    
      -- Identity.Translation
      generic
        type Object (<>) is limited private; -- matches any type
        type Pointer is access Object;
      package Translation is

        -- This nested generic allows us to establish a translation between
        -- an "opaque" Identity.Value type and some "transparent" Pointer
        -- type ... *later*.  Once instantiated, it becomes possible to generate
        -- Identity.Values other than Identity.None, but only by translating
        -- from Pointer values designating the given Object type.

        -- NOTE: Only one instantiation of this package will be allowed (per
        -- instantiation of the outer package).  Any attempt to establish
        -- more than one Translation for a given Identity.Value type will
        -- raise Standard.Program_Error on elaboration.  By admitting only
        -- one valid Translation, we can guarantee type safety: the only
        -- Pointers that we can get out of Identity.Values will be the
        -- Pointers that we actually put into them.

        -- Identity.Translation.To_Pointer
        function To_Pointer (The_Identity : in Identity.Value) return Pointer;
        pragma Inline (To_Pointer);

        -- Identity.Translation.To_Identity
        function To_Identity (The_Pointer : in Pointer) return Identity.Value;
        pragma Inline (To_Identity);

      end Translation;
    
    private -- Identity

      ... more about the implementation in a while ...

    end Identity;

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

Before looking at a possible implementation of this support package,
let's first take a look at how we might make use of it.

First, for every class that you want to introduce into a system, write
an instantiation of the Identity package:

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

    with Identity;
    package Employee_Identity is new Identity;

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

    with Identity;
    package Manager_Identity is new Identity;

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

    with Identity;
    package Office_Identity is new Identity;

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

    with Identity;
    package Project_Identity is new Identity;

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

    with Identity;
    package Building_Identity is new Identity;

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

    ... etc.  (Note: these are all separately-compilable library units.)


In effect, this "forward declares" each class.  Note that this takes very
little work to do: a couple of lines of code for each class.

Later, you can procede with writing your package specs for each class.  Each
package spec can make use of the opaque identity packages for any other classes
that it is associated with.  Additionally, each package spec should provide an
instantiation of the Translation generic for its corresponding Identity.Value
type.  (Note that this only costs four lines of code per class.)

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

    with Office_Identity;
    with Employee_Identity;
    ...

    package Office is

      -- Office.Object
      type Object is tagged limited private;

      -- Office.Pointer
      type Pointer is access all Office.Object'Class;

      -- Office.None
      None : constant Office.Pointer := null;

      -- Office.Translation
      package Translation is new
        Office_Identity.Translation
          (Object  => Office.Object'Class,
           Pointer => Office.Pointer);

      ----------------------------------------
      -- Primitives supporting association
      -- Office--occupied_by--Employee
      ----------------------------------------

      -- Office.Occupant_Employee_Of
      function Occupant_Employee_Of
        (The_Office : in Office.Object'Class) 
        return Employee_Identity.Value;

      -- Office.Associate_With_Occupant_Employee
      proccedure Associate_With_Occupant_Employee
        (The_Office   : in out Office.Object'Class;
         New_Employee : in     Employee_Identity.Value);
        -- mutually recursive with:
        -- Employee.Associate_With_Occupied_Office

      -- Office.Dissociate_From_Occupant_Employee
      proccedure Dissociate_From_Occupant_Employee
        (The_Office   : in out Office.Object'Class);
        -- mutually recursive with:
        -- Employee.Dissociate_From_Occupied_Office

      ... -- other primitives

    private -- Office

      -- Office.Object
      type Object is tagged limited
        record
          ...
          Its_Occupant_Employee : Employee_Identity.Value;
          ... -- other components
        end record;

    end Office;

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

It's even possible for a class to be mutually-recursive with one of
its own subclasses:

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

    with Employee_Identity;
    with Office_Identity;
    with Manager_Identity; -- Manager will (eventually) inherit from Employee
    ...

    package Employee is

      -- Employee.Object
      type Object is abstract tagged limited private;

      -- Employee.Pointer
      type Pointer is access all Employee.Object'Class;

      -- Employee.None
      None : constant Employee.Pointer := null;

      -- Employee.Translation
      package Translation is new 
        Employee_Identity.Translation 
          (Object  => Employee.Object'Class, 
           Pointer => Employee.Pointer);

      ----------------------------------------
      -- Primitives supporting association 
      -- Employee--occupies--Office
      ----------------------------------------

      -- Employee.Occupied_Office_Of
      function Occupied_Office_Of
        (The_Employee : in Employee.Object'Class) 
        return Office_Identity.Value;

      -- Employee.Associate_With_Occupied_Office
      procedure Associate_With_Occupied_Office
        (The_Employee : in out Employee.Object'Class;
         New_Office   : in     Office_Identity.Value);
        -- mutually recursive with:
        -- Office.Associate_With_Occupant_Employee

      -- Employee.Dissociate_From_Occupied_Office
      procedure Dissociate_From_Occupied_Office
        (The_Employee : in out Employee.Object'Class);
        -- mutually recursive with:
        -- Office.Dissociate_From_Occupant_Employee

      ----------------------------------------
      -- Primitives supporting association
      -- Employee--supervised_by--Manager
      ----------------------------------------

      -- Employee.Supervising_Manager_Of
      function Supervising_Manager_Of
        (The_Employee : in Employee.Object'Class) 
        return Manager_Identity.Value;

      -- Employee.Associate_With_Supervising_Manager
      procedure Associate_With_Supervising_Manager
        (The_Employee : in out Employee.Object'Class;
         New_Manager  : in     Manager_Identity.Value);
        -- mutually recursive with:
        -- Manager.Associate_With_Subordinate_Employee

      -- Employee.Dissociate_From_Supervising_Manager
      procedure Dissociate_From_Supervising_Manager
        (The_Employee : in out Employee.Object'Class);
        -- mutually recursive with:
        -- Manager.Dissociate_From_Subordinate_Employee

      ... -- other primitives

    private -- Employee

      -- Employee.Object
      type Object is abstract tagged
        record
          ...
          Its_Occupied_Office     : Office_Identity.Value;
          Its_Supervising_Manager : Manager_Identity.Value;
          ... -- other components
        end record;

    end Employee;

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

    with Manager_Identity;       -- To support associations with cardinality > 1
    with Employee_Identity;      -- assume that generic Identity package has
    with Employee_Identity.Set;  -- generic child package Identity.Set, which
    with Project_Identity;       -- can be instantiated to provide Set.Object
    with Project_Identity.Set;   -- types representing sets of identities.
    ...

    with Employee; -- Manager will inherit from Employee.  (Actually, this means
                   -- that Manager can forgo the use of Employee_Identity, but
                   -- for the sake of uniformity, I'll keep to the pattern.)

    package Manager is

      -- Manager.Object
      type Object is new Employee.Object with private;

      -- Manager.Pointer
      type Pointer is access all Manager.Object'Class;

      -- Manager.None
      None : constant Manager.Pointer := null;

      -- Manager.Translation
      package Translation is new
        Manager_Identity.Translation
          (Object  => Manager.Object'Class,
           Pointer => Manager.Pointer);

      ----------------------------------------
      -- Primitives supporting association:
      -- Manager--coordinates--Project(s)
      ----------------------------------------

      -- Manager.Coordinated_Projects_Of
      function Coordinated_Projects_Of
        (The_Manager : in Manager.Object'Class)
        return Project_Identity.Set.Object;

      -- Manager.Is_Associated_With_Coordinated_Project
      function Is_Associated_With_Coordinated_Project
        (The_Manager : in Manager.Object'Class;
         The_Project : in Project_Identity.Value) return Boolean;

      -- Manager.Associate_With_Coordinated_Project
      procedure Associate_With_Coordinated_Project
        (The_Manager : in out Manager.Object'Class;
         New_Project : in     Project_Identity.Value);
        -- mutually recursive with:
        -- Project.Associate_With_Coordinating_Manager

      -- Manager.Dissociate_From_Coordinated_Project
      procedure Dissociate_From_Coordinated_Project
        (The_Manager : in out Manager.Object'Class;
         Old_Project : in     Project_Identity.Value);
        -- mutually recursive with:
        -- Project.Dissociate_From_Coordinating_Manager

      ----------------------------------------
      -- Primitives supporting association
      -- Manager--supervises--Employee(s)
      ----------------------------------------

      -- Manager.Subordinate_Employees_Of
      function Subordinate_Employees_Of
        (The_Manager : in Manager.Object'Class)
        return Employee_Identity.Set.Object;

      -- Manager.Is_Associated_With_Subordinate_Employee
      function Is_Associated_With_Subordinate_Employee
        (The_Manager  : in Manager.Object'Class;
         The_Employee : in Employee_Identity.Value) return Boolean;

      -- Manager.Associate_With_Subordinate_Employee
      procedure Associate_With_Subordinate_Employee
        (The_Manager  : in out Manager.Object'Class;
         New_Employee : in     Employee_Identity.Value);
        -- mutually recursive with:
        -- Employee.Associate_With_Supervising_Manager

      -- Manager.Dissociate_From_Subordinate_Employee
      procedure Dissociate_From_Subordinate_Employee
        (The_Manager  : in out Manager.Object'Class;
         Old_Employee : in     Employee_Identity.Value);
        -- mutually recursive with:
        -- Employee.Dissociate_From_Supervising_Manager

      .... -- other primitives

    private -- Manager

      -- Manager.Object
      type Object is new Employee.Object with
        record
          ...
          Its_Coordinated_Projects  : Project_Identity.Set.Object;
          Its_Subordinate_Employees : Employee_Identity.Set.Object;
          ... -- other components
        end record;

    end Manager;
    
    ----------------------------------------------------------------------

The bodies of these packages can import each other's specs.  Since
each package spec provides a Translation facility for its
corresponding Identity.Value type, the package bodies can make
use of each other's Translation facilities whenever necessary.
For instance:

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

    with Employee;
    ...

    package body Office is

      ----------------------------------------
      -- Primitives supporting association
      -- Office--occupied_by--Employee
      ----------------------------------------

      ----------------------------------------
      -- Office.Occupant_Employee_Of
      ----------------------------------------

      function Occupant_Employee_Of
        (The_Office : in Office.Object'Class) 
        return Employee_Identity.Value is
      begin
        return The_Office.Its_Occupant_Employee;
      end Occupant_Employee_Of;


      ----------------------------------------
      -- Office.Associate_With_Occupant_Employee
      --   mutually recursive with:
      --   Employee.Associate_With_Occupied_Office
      ----------------------------------------

      proccedure Associate_With_Occupant_Employee
        (The_Office   : in out Office.Object'Class;
         New_Employee : in     Employee_Identity.Value)
      is
        use type Employee_Identity.Value;
      begin
        if New_Employee /= Employee_Identity.None and then
           New_Employee /= The_Office.Its_Occupant_Employee
        then

          Office.Dissociate_From_Occupant_Employee (The_Office);

          The_Office.Its_Occupant_Employee := New_Employee;

          Employee.Associate_With_Occupied_Office
          ( The_Employee => Employee.Translation.To_Pointer(New_Employee).all,
            New_Office   => Office.Translation.To_Identity(The_Office'Access) );

                            -- Okay, if you really want to shorten these
                            -- expressions, you could throw in some use-clauses.
                            -- But my feeling is that this style is very
                            -- readable as is.

        end if;
      end Associate_With_Occupant_Employee;


      ----------------------------------------
      -- Office.Dissociate_From_Occupant_Employee
      --   mutually recursive with:
      --   Employee.Dissociate_From_Occupied_Office
      ----------------------------------------

      proccedure Dissociate_From_Occupant_Employee
        (The_Office   : in out Office.Object'Class)
      is
        use type Employee_Identity.Value;

        Old_Employee : constant Employee_Identity.Value :=
          The_Office.Its_Occupant_Employee;

      begin
        if Old_Employee /= Employee_Identity.None then

          The_Office.Its_Occupant_Employee := Employee_Identity.None;

          Employee.Dissociate_From_Occupied_Office
          ( The_Employee => Employee.Translation.To_Pointer(Old_Employee).all );

        end if;
      end Dissociate_From_Ocupant_Employee;


      ... -- other primitives

    end Office;

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

(The bodies of Employee, Manager, Project, etc. would be similar.)

Thus, looking at the dependencies between compilation units, it's clear
that this scheme achieves the Identity/Interface/Implementation Trichotomy:

              +--------+           +--------+           +--------+
              |Manager |           |Employee|           | Office |
              |Identity|<--_   _-->|Identity|<--_   _-->|Identity|
              +--------+    \ /    +--------+    \ /    +--------+
                             X                    X               
              +--------+    / \    +--------+    / \    +--------+
              |Manager |___/   \___|Employee|___/   \___| Office |
              |        |--INHERIT->|        |           |        |
              |  Spec  |<--_   _-->|  Spec  |<--_   _-->|  Spec  |
              +--------+    \ /    +--------+    \ /    +--------+
                             X                    X               
              +--------+    / \    +--------+    / \    +--------+
              |Manager |___/   \___|Employee|___/   \___| Office |
              |        |           |        |           |        |
              |  Body  |           |  Body  |           |  Body  |
              +--------+           +--------+           +--------+

                       (Where -----> indicates dependency)

Note that this scheme holds up even where we have a generalization/
specialization relationship:  Manager can still inherit from Employee,
even though Employee depends on Manager_Identity.

To show the benefits of decoupling, let's see what happens when we add 
a new class (Project) and a new association (Manager--coordinates--Project).
The above diagram becomes:


    ##########           +--------+           +--------+           +--------+
    #Project #           |Manager |           |Employee|           | Office |
    #Identity#<--_   _-->|Identity|<--_   _-->|Identity|<--_   _-->|Identity|
    ##########    \ /    +--------+    \ /    +--------+    \ /    +--------+
                   X                    X                    X               
    ##########    / \    ##########    / \    +--------+    / \    +--------+
    #Project #___/   \___#Manager #___/   \___|Employee|___/   \___| Office |
    #        #           #        #--INHERIT->|        |           |        |
    #  Spec  #<--_   _-->#  Spec  #<--_   _-->|  Spec  |<--_   _-->|  Spec  |
    ##########    \ /    ##########    \ /    +--------+    \ /    +--------+
                   X                    X                    X               
    ##########    / \    ##########    / \    @@@@@@@@@@    / \    +--------+
    #Project #___/   \___#Manager #___/   \___@Employee@___/   \___| Office |
    #        #           #        #           @        @           |        |
    #  Body  #           #  Body  #           @  Body  @           |  Body  |
    ##########           ##########           @@@@@@@@@@           +--------+


           ####
    Where  #  #  =  compilation unit that must be written or modified
           ####

           @@@@
           @  @  =  compilation unit that must be recompiled (but not modified)
           @@@@

           +--+
           |  |  =  compilation unit that is unaffected by the change
           +--+

As you can see, we need to write or modify the package specs and
package bodies for the classes involved in the association: Project
and Manager.  And, because the spec of package Manager is changed, the
package bodies for other classes associated with Manager, such as
Employee, have to be recompiled, although they do not need to be
modified.  But, because *Manager_Identity* is not touched, the package
*specs* for classes such as Employee not only do not need to be
modified but they do not even need to be recompiled.  Classes beyond
the immediate vicinity of Manager and Project (for instance, Office)
are not affected at all.

Now let's go back and consider how to implement the Identity package.
To implement the Identity.Value type, all we need is some kind of
"black box" that is guaranteed to be the same storage size as an
access type.  Almost anything would do, but System.Address seems the
most convenient for this purpose.

(Er ... I've been scouring the RM9X 5.0 and much to my surprise I can't
seem to find positive confirmation for the fact that System.Address will
have the same bit-representation as access types.  Tucker, if you're
listening, can you give me a hand here?)

Revisiting the Identity package spec, here's how we could fill in the
private part:

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

    with System;

    generic
    package Identity is

      ... -- public part as shown above

    private -- Identity
    
      -- Identity.Value
      type Value is
        record
          Its_Address : System.Address := System.Null_Address;
        end record;

      -- Identity.None      
      None : constant Identity.Value := (Its_Address => System.Null_Address);

    end Identity;

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

I considered just deriving Identity.Value directly from System.Address:

      -- Identity.Value
      type Value is new System.Address;

      -- Identity.None
      None : constant Identity.Value := Identity.Value (System.Null_Address);

However, the record type is preferable because it allows for default
initialization.  That way, Identity.Values can mimick the way access
types are always automatically initialized to null.

In the package body, we're going to need to make use of
Unchecked_Conversions between System.Address and the given Pointer
type.  At first blush, this might seen like a violation of
type-safety.  But it really isn't, because those Addresses are never
going to be used *as* Addresses.  They're just "black boxes" for
holding Pointer values opaquely.  Pointers go in, and Pointers come
out, period.  And only one kind of Pointer at that -- as long as we
can guarantee that only one instantiation of Translation (per Identity
instantiation) will be allowed within a single program.

Here's a possible implementation of the Identity package body:

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

    with Ada.Unchecked_Conversion;

    package body Identity is

      One_Translation_Registered_Already : Boolean := False;

      -- This flag helps guarantee type-safety, by allowing us to
      -- establish only one Translation for a given instantiation of
      -- Identity.

      -----------------------
      -- Identity.Translation
      -----------------------

      package body Translation is

        function Address_To_Pointer is new 
          Ada.Unchecked_Conversion (System.Address, Pointer);

        function Pointer_To_Address is new
          Ada.Unchecked_Conversion (Pointer, System.Address);

        -- Alternatively, an instantiation of the generic package
        -- System.Storage_Elements.Address_To_Access_Conversions 
        -- could be used.  But Unchecked_Conversion is sufficient,
        -- because we never really use an Identity.Value's Address 
        -- component *as* an Address.  As long as the bit-pattern
        -- of the original Pointer value is preserved, it doesn't
        -- matter whether its interpretation as an Address makes
        -- any semantic sense.

        ----------------------------------
        -- Identity.Translation.To_Pointer
        ----------------------------------

        function To_Pointer (The_Identity : in Identity.Value) 
          return Pointer is
        begin
          return Address_To_Pointer (The_Identity.Its_Address);
        end To_Pointer;

        -----------------------------------
        -- Identity.Translation.To_Identity
        -----------------------------------

        function To_Identity (The_Pointer : in Pointer) 
          return Identity.Value is
        begin
          return (Its_Address => Pointer_To_Address (The_Pointer));
        end To_Identity;


        -- Note: Unchecked_Conversions are intrinsic, and both of the
        -- functions To_Pointer and To_Identity are inlined.  So it is 
        -- conceivable that an optimizing compiler can reduce the cost
        -- calling these functions to *zero*.


      begin -- Translation

        -- On elaboration of an instantiation of this nested generic,
        -- confirm that this instantiation is the only one:

        if One_Translation_Registered_Already then
          raise Standard.Program_Error;
        else
          One_Translation_Registered_Already := True;
        end if;

        -- For the final delivery of a fully-tested system, even this
        -- validity check could be eliminated.  (Substitute an alternate
        -- body for package Identity without this check, and then
        -- recompile the world.)

      end Translation;

    end Identity;

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

And there you have it.  No more "withing" problem.  And we didn't have
to replace it with an "inheritance collision" problem, where competing
uses for inheritance interfere with each other.  Ada9X's inheritance
mechanism is available to do what inheritance was always meant to do:
support generalization/specialization relationships that come from the
*problem* domain.  Mutual recursion is being achieved in a decoupled
way while still preserving type-safety -- but it's Ada's generic
facilities that are providing the decoupling.  By coming up with a
*reusable* solution as well, we have effectively "extended" the
language -- without actually having to do violence to the definition
of the language itself.  Remember the mantra: "Ada's already expressive
enough!"

There's room for a lot of variation with this technique.  For
instance, you could combine it with child units: If the association
operations don't need to be primitives, you could off-load them to
child packages, where the transparent Pointer types for both classes
are available.  Yet, as an *implementation* choice, you can keep the
opaque Identity values within the tagged record types.  The child
packages could take care of using the appropriate Translations to
convert between hidden Identity values and published Pointer values.

More broadly, I hope that the whole idea of using generics for
"deferred coupling" will open up a lot of interesting possibilities
for you folks out there, not just for this particular problem,
but for many others as well.

Happy OOPing!

-- John Volan

--------------------------------------------------------------------------------
--  Me : Person := (Name                => "John Volan",
--                  Company             => "Raytheon Missile Systems Division",
--                  E_Mail_Address      => "jgv@swl.msd.ray.com",
--                  Affiliation         => "Enthusiastic member of Team Ada!",
--                  Humorous_Disclaimer => "These opinions are undefined " &
--                                         "by my employer and therefore " &
--                                         "any use of them would be "     &
--                                         "totally erroneous.");
--------------------------------------------------------------------------------




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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-12 22:49 SOLVED! Decoupled Mutual Recursion Challenger John Volan
@ 1994-10-17 15:48 ` John Volan
  1994-10-17 17:55   ` Bob Duff
  1994-10-17 22:54   ` Cyrille Comar
  0 siblings, 2 replies; 45+ messages in thread
From: John Volan @ 1994-10-17 15:48 UTC (permalink / raw)


In article <1994Oct12.224944.25566@swlvx2.msd.ray.com> I (John Volan) wrote:

> Now let's go back and consider how to implement the Identity package.
> To implement the Identity.Value type, all we need is some kind of
> "black box" that is guaranteed to be the same storage size as an
> access type.  Almost anything would do, but System.Address seems the
> most convenient for this purpose.

> (Er ... I've been scouring the RM9X 5.0 and much to my surprise I can't
> seem to find positive confirmation for the fact that System.Address will
> have the same bit-representation as access types.  Tucker, if you're
> listening, can you give me a hand here?)

Actually, there wasn't any need to involve System.Address after all.
A better solution would be to just declare Identity.Value as an access
type pointing to some "dummy" designated type. 

[Thanks to Tim Coslet for pointing out this possibility to me.]

Here's an improved spec for package Identity.  The public part is
identical to my previous solution, so it still provides a reusable
way of achieving mutual recursion in a decoupled fashion:

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

    generic
    package Identity is

      -- Identity.Value
      type Value is private; 

      -- Identity.None    
      None : constant Identity.Value;

      -- Identity.Translation
      generic
        type Object (<>) is limited private; -- matches any type
        type Pointer is access Object;
      package Translation is

        -- Identity.Translation.To_Pointer
        function To_Pointer (The_Identity : in Identity.Value) return Pointer;
        pragma Inline (To_Pointer);

        -- Identity.Translation.To_Identity
        function To_Identity (The_Pointer : in Pointer) return Identity.Value;
        pragma Inline (To_Identity);

      end Translation;
    
    private -- Identity

      type Void is null record; -- "dummy" designated type
    
      -- Identity.Value
      type Value is access Void;

      -- Identity.None      
      None : constant Identity.Value := null;

    end Identity;

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

Implementing Identity.Value an access-to-dummy-Void-type has the
following advantages:

(1) It avoids portability problems.  It's conceivable that a given Ada
compiler might not implement System.Address the same as access types.
However, it is a safe bet that all access types will be implemented
the same way (within a given Ada implementation).

(2) It avoids coupling the Identity package to package System.

(3) It still preserves type-safety, because an Identity.Value will
never actually be used *as* an access-to-dummy-Void.  (Identity.Value
is still a "black box", after all.)

(4) The default initialization of Identity.Values to Identity.None
is implemented directly in terms of the default initialization of
access types to null.  There's no need to muck around with a record
type.

(5) The bodies of the Translation functions can be implemented
directly as instantiations of Unchecked_Conversion, since Ada9X allows
renaming declarations to act as subprogram bodies:

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

    with Ada.Unchecked_Conversion;

    package body Identity is

      One_Translation_Registered_Already : Boolean := False;

      -----------------------
      -- Identity.Translation
      -----------------------

      package body Translation is

        function Identity_To_Pointer is new 
          Ada.Unchecked_Conversion (Identity.Value, Pointer);

        function Pointer_To_Identity is new
          Ada.Unchecked_Conversion (Pointer, Identity.Value);

        ----------------------------------
        -- Identity.Translation.To_Pointer
        ----------------------------------

        function To_Pointer (The_Identity : in Identity.Value) return Pointer
          renames Identity_To_Pointer;

        -----------------------------------
        -- Identity.Translation.To_Identity
        -----------------------------------

        function To_Identity (The_Pointer : in Pointer) return Identity.Value
          renames Pointer_To_Identity;

        -- Since To_Pointer and To_Identity are really just instantiations of
        -- Unchecked_Conversion, and since Unchecked_Conversion is intrinsic,
        -- the cost of calling these subprograms very likely will be *zero*.

      begin -- Translation
        if One_Translation_Registered_Already then
          raise Standard.Program_Error;
        else
          One_Translation_Registered_Already := True;
        end if;
      end Translation;

    end Identity;

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

(Well, folks, it just keeps looking better and better ... :-)

--John Volan

--------------------------------------------------------------------------------
--  Me : Person := (Name                => "John Volan",
--                  Company             => "Raytheon Missile Systems Division",
--                  E_Mail_Address      => "jgv@swl.msd.ray.com",
--                  Affiliation         => "Enthusiastic member of Team Ada!",
--                  Humorous_Disclaimer => "These opinions are undefined " &
--                                         "by my employer and therefore " &
--                                         "any use of them would be "     &
--                                         "totally erroneous.");
--------------------------------------------------------------------------------





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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-17 15:48 ` John Volan
@ 1994-10-17 17:55   ` Bob Duff
  1994-10-17 20:52     ` John Volan
  1994-10-17 22:54   ` Cyrille Comar
  1 sibling, 1 reply; 45+ messages in thread
From: Bob Duff @ 1994-10-17 17:55 UTC (permalink / raw)


In article <1994Oct17.154812.9104@swlvx2.msd.ray.com>,
John Volan <jgv@swl.msd.ray.com> wrote:
>In article <1994Oct12.224944.25566@swlvx2.msd.ray.com> I (John Volan) wrote:
>> (Er ... I've been scouring the RM9X 5.0 and much to my surprise I can't
>> seem to find positive confirmation for the fact that System.Address will
>> have the same bit-representation as access types.  Tucker, if you're
>> listening, can you give me a hand here?)
>
>Actually, there wasn't any need to involve System.Address after all.
>A better solution would be to just declare Identity.Value as an access
>type pointing to some "dummy" designated type. 

There is no requirement that type Address have the same representation
as an access type.  In fact, there is no requirement that one access
type have the same representation as another access type.  There are, in
fact, compilers that take advantage of this.  I believe that GNAT, for
example, stores access-to-unconstrained-arrray differently from
access-to-integer.

However, there are some conversions operations back and forth between
Address and any given access type.  See RM9X-13.7.1;5.0.  These aren't
completely portable, either, but they are likely to be in the "simple"
cases.

- Bob
-- 
Bob Duff                                bobduff@inmet.com
Oak Tree Software, Inc.
Ada 9X Mapping/Revision Team (Intermetrics, Inc.)



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-17 17:55   ` Bob Duff
@ 1994-10-17 20:52     ` John Volan
  1994-10-17 22:10       ` Bob Duff
  0 siblings, 1 reply; 45+ messages in thread
From: John Volan @ 1994-10-17 20:52 UTC (permalink / raw)


bobduff@dsd.camb.inmet.com (Bob Duff) writes:

>There is no requirement that type Address have the same representation
                                                         ^^^^^^^^^^^^^^
>as an access type.  In fact, there is no requirement that one access
>type have the same representation as another access type.  There are, in
                    ^^^^^^^^^^^^^^
>fact, compilers that take advantage of this.  I believe that GNAT, for
>example, stores access-to-unconstrained-arrray differently from
>access-to-integer.

I guess the question really hinges on the meaning of the word
"representation".  When you say that two access types may be "stored
differently", do you mean that the number of bits used to store an
access type can be different, or do you only mean that the *contents*
of those bits might be interpreted differently?

All I really need is the relatively weak guarantee that all access types
occupy the same number of bits, i.e.:

    A1'Size = A2'Size, for any two access types A1 and A2

(And perhaps this size is the same as System.Address'Size, but I don't
even need that guarantee.)  If it's reasonably portable to assume
that all access types occupy the same number of bits, then we can have
a "dummy" access type act as a "black box" to store the bit-pattern
of any other access type, via Unchecked_Conversion.  In other words,
can we guarantee the following:

    To_A1 (To_A2 (V1)) = V1

where V1 is any value of access type A1, and

    function To_A1 is new Ada.Unchecked_Conversion (A2, A1);   
    function To_A2 is new Ada.Unchecked_Conversion (A1, A2);   

That's all that my Identity package needs.

I do *not* need the much stronger guarantee that the *contents* of an
address value be equivalent to the *contents* of a corresponding
access value, i.e.:

    For any object X of some designated type D:

        X'Access = X'Address

Evidently, Ada makes no such guarantee.  (For instance, X'Access might
be an offset in longwords from the start of some storage pool, while
X'Address might be an offset in storage units from the start of
memory.  Or, if D is an unconstrained array type, X'Address might be
the location where the first component of X resides, whereas X'Access
might be the location where the "dope" of X begins.  I take it that
the possibility of these kinds of variances are the rationale for the
package System.Storage_Units.Address_To_Access_Conversions in
RM9X-13.7.1;5.0.)  

At any rate, this stronger guarantee is *not* a requirement of my
Identity package, whether you go with the System.Address implementation
or the access-to-dummy-type implementation.  All we need is a portable
way to "opaquely" store the bits of an access value.

-- John Volan

--------------------------------------------------------------------------------
--  Me : Person := (Name                => "John Volan",
--                  Company             => "Raytheon Missile Systems Division",
--                  E_Mail_Address      => "jgv@swl.msd.ray.com",
--                  Affiliation         => "Enthusiastic member of Team Ada!",
--                  Humorous_Disclaimer => "These opinions are undefined " &
--                                         "by my employer and therefore " &
--                                         "any use of them would be "     &
--                                         "totally erroneous.");
--------------------------------------------------------------------------------




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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-17 20:52     ` John Volan
@ 1994-10-17 22:10       ` Bob Duff
  1994-10-18 22:17         ` John Volan
  0 siblings, 1 reply; 45+ messages in thread
From: Bob Duff @ 1994-10-17 22:10 UTC (permalink / raw)


In article <1994Oct17.205244.17450@swlvx2.msd.ray.com>,
John Volan <jgv@swl.msd.ray.com> wrote:
>bobduff@dsd.camb.inmet.com (Bob Duff) writes:
>
>>There is no requirement that type Address have the same representation
>                                                         ^^^^^^^^^^^^^^
>>as an access type.  In fact, there is no requirement that one access
>>type have the same representation as another access type.  There are, in
>                    ^^^^^^^^^^^^^^
>>fact, compilers that take advantage of this.  I believe that GNAT, for
>>example, stores access-to-unconstrained-arrray differently from
>>access-to-integer.
>
>I guess the question really hinges on the meaning of the word
>"representation".  When you say that two access types may be "stored
>differently", do you mean that the number of bits used to store an
>access type can be different, or do you only mean that the *contents*
>of those bits might be interpreted differently?

I meant both.  The number of bits can be different, and the meaning of
those bits can be different.

>All I really need is the relatively weak guarantee that all access types
>occupy the same number of bits, i.e.:
>
>    A1'Size = A2'Size, for any two access types A1 and A2

Sorry.  Ada makes no such guarantee.  In practice, you might be able to
write portable code across *many* (but not all) implementations,
especially if you're willing to restrict the designated type of the
access type.  After all, most implementations don't read the phase of
the moon clock to decide how many bits to use for a give type.

>(And perhaps this size is the same as System.Address'Size, but I don't
>even need that guarantee.)  If it's reasonably portable to assume
>that all access types occupy the same number of bits, then we can have
>a "dummy" access type act as a "black box" to store the bit-pattern
>of any other access type, via Unchecked_Conversion.  In other words,
>can we guarantee the following:
>
>    To_A1 (To_A2 (V1)) = V1
>
>where V1 is any value of access type A1, and
>
>    function To_A1 is new Ada.Unchecked_Conversion (A2, A1);   
>    function To_A2 is new Ada.Unchecked_Conversion (A1, A2);   
>
>That's all that my Identity package needs.

I'm not real clear on what you're trying to do, so I don't have much
useful advice here.  Perhaps Address_To_Access_Conversions would be of
some help?

>I do *not* need the much stronger guarantee that the *contents* of an
>address value be equivalent to the *contents* of a corresponding
>access value, i.e.:
>
>    For any object X of some designated type D:
>
>        X'Access = X'Address
>
>Evidently, Ada makes no such guarantee.  (For instance, X'Access might
>be an offset in longwords from the start of some storage pool, while
>X'Address might be an offset in storage units from the start of
>memory.

Right.  But one of those offsets might fit in 16 bits, while the other
fits in 32 bits.

> ...Or, if D is an unconstrained array type, X'Address might be
>the location where the first component of X resides, whereas X'Access
>might be the location where the "dope" of X begins.  I take it that
>the possibility of these kinds of variances are the rationale for the
>package System.Storage_Units.Address_To_Access_Conversions in
>RM9X-13.7.1;5.0.)  

Yes.

>At any rate, this stronger guarantee is *not* a requirement of my
>Identity package, whether you go with the System.Address implementation
>or the access-to-dummy-type implementation.  All we need is a portable
>way to "opaquely" store the bits of an access value.

GNAT stores an access-to-unconstrained array as a pair consisting of
address-of-dope, address-of-data.  So these things are twice the size of
other access types.  (One could imagine doing something similar for
discriminated and/or tagged types, but I don't think GNAT does.)  In the
unc-array case, the address-of-data is actually the address of the
zero-th element of the array (even if the array has no such element),
which makes indexing operations faster, because there's no need to fetch
the lower bound and subtract.

I'm not *sure* of the details of the GNAT implementation -- Robert,
please correct me if I'm wrong.

Another implementation I've heard about (from Rational, I think?),
creates a separate storage pool for every access type, and uses various
virtual memory tricks to make that efficient.  Access types end up being
represented in various numbers of bits, I believe.

Nonetheless, *most* implementations implement *most* access types as an
address, so in *many* cases, your code will work.  But you can't count
on it being portable in all cases.

- Bob
-- 
Bob Duff                                bobduff@inmet.com
Oak Tree Software, Inc.
Ada 9X Mapping/Revision Team (Intermetrics, Inc.)



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-17 15:48 ` John Volan
  1994-10-17 17:55   ` Bob Duff
@ 1994-10-17 22:54   ` Cyrille Comar
  1 sibling, 0 replies; 45+ messages in thread
From: Cyrille Comar @ 1994-10-17 22:54 UTC (permalink / raw)


jgv@swl.msd.ray.com (John Volan) writes:
: In article <1994Oct12.224944.25566@swlvx2.msd.ray.com> I (John Volan) wrote:
: 
: (1) It avoids portability problems.  It's conceivable that a given Ada
: compiler might not implement System.Address the same as access types.
: However, it is a safe bet that all access types will be implemented
: the same way (within a given Ada implementation).

I didn't follow the thread very much so maybe it is not relevant in this
context but it is all BUT safe to bet that all access types will be implemented
the same way within a given implementation...
for instance access to unconstrained arrays are fat pointers for GNAT and thus
completely different than access to constrain objects. furthermore, Pool
specific access types can take advantage of the specificity of their pool and
may completely differ from one pool to the other.
It is probably safe to state that general access types whose designated type
is constrained are likely to be implemented the same way in a given
implementation, but I'm not completely sure 
-- 
------------------------------------------------------------------------
Cyrille Comar,                                  E-mail: comar@cs.nyu.edu
Gnat Project                                    US phone: (212) 998-3489




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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-17 22:10       ` Bob Duff
@ 1994-10-18 22:17         ` John Volan
  1994-10-19  1:01           ` Bob Duff
       [not found]           ` <CxwGJF.FwB@ois.com>
  0 siblings, 2 replies; 45+ messages in thread
From: John Volan @ 1994-10-18 22:17 UTC (permalink / raw)


bobduff@dsd.camb.inmet.com (Bob Duff) writes:

>In article <1994Oct17.205244.17450@swlvx2.msd.ray.com>,
>John Volan <jgv@swl.msd.ray.com> wrote:
>>
>>I guess the question really hinges on the meaning of the word
>>"representation".  When you say that two access types may be "stored
>>differently", do you mean that the number of bits used to store an
>>access type can be different, or do you only mean that the *contents*
>>of those bits might be interpreted differently?

>I meant both.  The number of bits can be different, and the meaning of
>those bits can be different.

>>All I really need is the relatively weak guarantee that all access types
>>occupy the same number of bits, i.e.:
>>
>>    A1'Size = A2'Size, for any two access types A1 and A2

>Sorry.  Ada makes no such guarantee.  In practice, you might be able to
>write portable code across *many* (but not all) implementations,
>especially if you're willing to restrict the designated type of the
>access type.  After all, most implementations don't read the phase of
>the moon clock to decide how many bits to use for a give type.

Right, I was kind of figuring that.  In the original "contract" for my
Identity package, I was trying to be as general as possible:

      -- Identity.Translation
      generic
        type Object (<>) is limited private; -- matches any type
        type Pointer is access Object;
      package Translation is ...

But now it looks like this is just too general to be portable.
However, making it this general was just a gratuitous freebie.  I
threw it in because I couldn't see any reason not to -- but now I do
see the reason.  At any rate, there is some room to back off: The
original intent was to be able to "opaquely" store pointers
designating what would (eventually) be tagged record types -- most
likely class-wide types, and most likely only *definite* tagged record
types.  So it would not hurt things very much if wee restricted the
contract to only support pointers designating definite, class-wide
tagged record types:

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

    generic
    package Identity is

      -- Identity.Value
      type Value is private; 

      -- Identity.None    
      None : constant Identity.Value;

      -- Identity.Translation
      generic
               -- Only definite types (no discriminants)
               -- vv 
        type Object is abstract tagged limited private;
                    -- ^^^^^^^^^^^^^^^
                    -- Only tagged types (but any abstract or non-abstract)
        type Pointer is access Object'Class;
                            -- ^^^^^^^^^^^^
                            -- Only access to class-wide types.
      package Translation is

        -- Identity.Translation.To_Pointer
        function To_Pointer (The_Identity : in Identity.Value) return Pointer;
        pragma Inline (To_Pointer);

        -- Identity.Translation.To_Identity
        function To_Identity (The_Pointer : in Pointer) return Identity.Value;
        pragma Inline (To_Identity);

      end Translation;
    
    private -- Identity

      type Void is abstract tagged null record; -- "dummy" designated type
    
      -- Identity.Value
      type Value is access Void'Class;
                 -- ^^^^^^^^^^^^^^^^^
                 -- An access-to-classwide-definite-tagged-type,
                 -- so likely to be implemented the same as other
                 -- access-to-classwide-definite-tagged-types.

      -- Identity.None      
      None : constant Identity.Value := null;
	
    end Identity;

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

(Perhaps an alternate package, say, "Indefinite_Identity", could support
pointers designating classwide indefinite tagged record types.)

In the body of this version of package Identity, we might be able to
get away with doing Unchecked_Conversions.  But I guess even this
might be playing the odds:

>Another implementation I've heard about (from Rational, I think?),
>creates a separate storage pool for every access type, and uses various
>virtual memory tricks to make that efficient.  Access types end up being
>represented in various numbers of bits, I believe.

So, depending on what pools the clients store their tagged types in,
even the above scheme might not turn out to be portable.

[snip]

>I'm not real clear on what you're trying to do, so I don't have much
>useful advice here.  Perhaps Address_To_Access_Conversions would be of
>some help?

I did consider that as a possibility at first, but I was still working
under the assumption (obsolete, I guess) that X'Address = X'Access, or
at least X'Address'Size = X'Access'Size.  Now I would say that using
Address_To_Access_Conversions is a possibility ...  *except*: Looking
more closely at that package, I'm now noticing that the Object_Pointer
type isn't a generic *parameter*.  Rather, it's in the public part of
the package:

    generic
      type Object (<>) is limited private;
    package Address_To_Access_Conversion is
      type Object_Pointer is access all Object;
      ...

In other words, this package provides a *new* access type into which
address values can be converted.  It's *not* providing the capability
to convert some *arbitrary* access type into addresses.  (It's called
"Address_To_Access_Conversions" after all.)  So at this point, I'm not
sure how I could use this to implement the Identity package.  It seems
like the Identity package would have to provide not only the "opaque"
identity type but also the "transparent" Pointer type.  (In my
original formulation, it was the class packages themselves that
provided the Pointer types, along with the Object types.)  But I don't
see how the Identity package could supply the Pointer type as a
visible access type and still keep the opaque identity type private,
if the Pointer type now has to come from an instantiation of
Address_To_Access_Conversions.  This seems like a "chicken and egg"
problem -- which is ironic, since that's precisely the kind of problem
that the Identity package was supposed to solve in the first place!

However, there are other alternatives, as long as we're willing to
impose certain (relatively reasonable) restrictions on the use of the
Identity package.  For instance, the Identity package could assume
that all classes that want to participate in decoupled mutual
recursion have to inherit from some root Universal abstract class:

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

    package Universal is

      -- Universal.Object
      type Object is abstract tagged null record;
      -- or perhaps: abstract new Ada.Finalization.Limited_Controlled
      --               with null record;

      -- Universal.Pointer
      type Pointer is access all Universal.Object'Class;

      -- Universal.None
      None : constant Universal.Pointer := null;

    end Universal;

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

    with Universal;

    generic
    package Identity is

      -- Identity.Value
      type Value is private; 

      -- Identity.None    
      None : constant Identity.Value;

      -- Identity.Translation
      generic
        type Object is abstract new Universal.Object with private;
                    -- ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
                    -- Actual must be some subclass of Universal.Object
                    -- (but may be abstract or non-abstract)
        type Pointer is access Object'Class;
      package Translation is

        -- Identity.Translation.To_Pointer
        function To_Pointer (The_Identity : in Identity.Value) return Pointer;
        pragma Inline (To_Pointer);

        -- Identity.Translation.To_Identity
        function To_Identity (The_Pointer : in Pointer) return Identity.Value;
        pragma Inline (To_Identity);

      end Translation;
    
    private -- Identity

      -- Identity.Value
      type Value is new Universal.Pointer;
                 -- ^^^^^^^^^^^^^^^^^^^^^

      -- Identity.None      
      None : constant Identity.Value := null;

    end Identity;

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

Then the we can implement the Identity.Translation package in terms of
safe "narrowing" and "widening" type conversions:

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

    package body Identity is

      -----------------------
      -- Identity.Translation
      -----------------------

      package body Translation is

        ----------------------------------
        -- Identity.Translation.To_Pointer
        ----------------------------------

        function To_Pointer (The_Identity : in Identity.Value) return Pointer is
        begin
          return Pointer (Universal.Pointer (The_Identity));
                       -- ^^^^^^^^^^^^^^^^^
                       -- Hmm... do I even need this?
        end To_Pointer;   

        -----------------------------------
        -- Identity.Translation.To_Identity
        -----------------------------------

        function To_Identity (The_Pointer : in Pointer) return Identity.Value is
        begin
          return Identity.Value (Universal.Pointer (The_Pointer));
                              -- ^^^^^^^^^^^^^^^^^
                              -- Hmm... do I even need this?
        end To_Identity;

      end Translation;
    
    end Identity;

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

I assume that such type-conversions are totally portable.  

(Are there any holes in this? Does deriving type Identity.Value from
Universal.Pointer get in the way of doing "narrowing" and "widening"?
If it does, we could get around that by implementing the Value type as
a record instead:

      -- Identity.Value
      type Value is
        record
          Its_Pointer : Universal.Pointer;
        end record;

      -- Identity.None
      None : constant Identity.Value := (Its_Pointer => Universal.None);

That way, we're always dealing cleanly with a Universal.Pointer.)

Of course, given this new contract for the Identity package, classes
participating in decoupled mutual recursion would have to inherit from
Universal:

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

    with Universal;
    with Office_Identity;
    with Employee_Identity;
    ...
    package Office is

      -- Office.Object
      type Object is new Universal.Object with private;
                  -- ^^^^^^^^^^^^^^^^^^^^

      -- Office.Pointer
      type Pointer is access all Office.Object'Class;

      -- Office.None
      None : constant Office.Pointer := null;

      -- Office.Translation
      package Translation is new
        Office_Identity.Translation
          (Object  => Office.Object,
           Pointer => Office.Pointer);

      ...

    end Office;

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

This is a bit of a restriction, but not too unreasonable.  In fact,
there may be other reasons for introducing a root Universal class
anyway.  Other object-oriented "infrastructures" often do something
similar.

For instance, consider Bill Beckwith's CORBA IDL-to-Ada9X translation.
That scheme included a "universal" Corba.Ref type and Corba.Object
type, from which all IDL Ref and Object types would be derived.
Unfortunately (IMHO), this scheme achieves decoupled mutual recursion
by exploiting inheritance as the mechanism for decoupling.  I would
argue that such a scheme falls into the trap of "inheritance
collision", where one usage of inheritance (providing alternate
programming-interface views for a single class of real-world entities)
gets in the way of the "customary" use of inheritance (supporting
generalization-specialization relationships between different classes
of real-world entities).

Luckily, I think that this problem can be solved quite neatly by
introducing something very similar to my Identity package.  In that
way, the IDL-to-Ada9X mapping could exploit generics, rather than
inheritance, as the way to achieve decoupled mutual recursion.
Meanwhile, inheritance would still be available for its customary
role in supporting generalization-specialization relationships:

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

    with Ada.Finalization;

    package Corba is

      -- Corba.Object
      type Object is tagged ...

      -- Corba.Ref
      type Ref is tagged ...

      -- Corba.Nothing
      Nothing : constant Ref;

      -- Corba.Identity
      generic
      package Identity is

        -- Corba.Identity.Value
        type Value is private;

        -- Corba.Identity.None
        None : constant Identity.Value;

        -- Corba.Identity.Translation
        generic
          type Ref is new Corba.Ref with private;
        package Translation is
          function To_Ref (The_Identity : in Identity.Value) return Ref;
          function To_Identity (The_Ref : in Ref) return Identity.Value;
        end Translation;

      private -- Corba.Identity

        -- Corba.Identity.Value
        type Value is new Corba.Ref with null record;

        -- Corba.Identity.None
        None : constant Identity.Value := Identity.Value (Corba.Nothing);

      end Identity;

    private -- Corba

      ...

    end Corba;

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

    with Corba;
    package Egg_Identity is new Corba.Identity;

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

    with Corba;
    package Chicken_Identity is new Corba.Identity;

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

    with Corba;
    package Rooster_Identity is new Corba.Identity;

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

    with Corba;
    with Egg_Identity;
    with Chicken_Identity;

    package Egg is

      -- Egg.Ref
      type Ref is new Corba.Ref with null record;

      -- Egg.None
      None : constant Egg.Ref := Egg.Ref (Corba.Nothing);

      package Translation is new 
        Egg_Identity.Translation (Ref => Egg.Ref);

      -- Egg.Hatch_Chicken
      function Hatch_Chicken (The_Egg : in Egg.Ref) 
        return Chicken_Identity.Value;

    end Egg;

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

    with Corba;
    with Chicken_Identity;
    with Egg_Identity;
    with Rooster_Identity; -- Rooster will (eventually) inherit from Chicken

    package Chicken is

      -- Chicken.Ref
      type Ref is new Corba.Ref with null record;

      -- Chicken.None
      None : constant Chicken.Ref := Chicken.Ref (Corba.Nothing);

      package Translation is new
        Chicken_Identity.Translation (Ref => Chicken.Ref);

      -- Chicken.Lay_Egg
      function Lay_Egg (The_Chicken : in Chicken.Ref) 
        return Egg_Identity.Value;

      -- Chicken.Mate_With_Rooster
      procedure Mate_With_Rooster
        (The_Chicken : in Chicken.Ref;
         The_Rooster : in Rooster_Identity.Value);

      -- *Ahem*.  Well, maybe these operations a more appropriate for 
      -- class *Hen* (which, like Rooster, would be a *subclass* of 
      -- Chicken ;-).  But bear with me -- I'm just trying to show an 
      -- example of the Decoupled Mutual Recursion Challenge that I 
      -- originally posed.

    end Chicken;

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

    with Chicken;  -- Rooster inherits from Chicken
    with Rooster_Identity;
    with Chicken_Identity;

    package Rooster is

      -- Rooster.Ref
      type Ref is new Chicken.Ref with null record;

      -- Rooster.None
      None : constant Rooster.Ref := Rooster.Ref (Chicken.None);

      -- Rooster.Translation
      package Translation is new
        Rooster_Identity.Translation (Ref => Rooster.Ref);

      -- Rooster.Mate_With_Chicken
      procedure Mate_With_Chicken
        (The_Rooster : in Rooster.Ref;
         The_Chicken : in Chicken_Identity.Value);

      -- *Ahem*.  Well, maybe this ought to be Mate_With_Hen, but you
      -- get the idea ... :-)

    end Rooster;

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

    with Corba;
    with Chicken;

    package Egg.Impl is

      -- Egg.Impl.Object
      type Object is new Corba.Object with ...

      -- Egg.Impl.Lay_Chicken
      function Hatch_Chicken (The_Egg : in out Egg.Impl.Object'Class)
        return Chicken.Ref'Class;

    end Egg.Impl;

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

    with Corba;
    with Egg;
    with Rooster;

    package Chicken.Impl is

      -- Chicken.Impl.Object
      type Object is new Corba.Object with ...

      -- Chicken.Impl.Lay_Egg
      function Lay_Egg (The_Chicken : in out Chicken.Impl.Object'Class)
        return Egg.Ref'Class;

      -- Chicken.Impl.Mate_With_Rooster
      procedure Mate_With_Rooster
        (The_Chicken : in out Chicken.Impl.Object'Class;
         The_Rooster : in     Rooster.Ref'Class);

    end Chicken.Impl;

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

    with Chicken.Impl; -- Rooster implementation inherits from Chicken impl.

    package Rooster.Impl is

      -- Rooster.Impl.Object
      type Object is new Chicken.Impl.Object with ...

      -- Rooster.Impl.Mate_With_Chicken
      procedure Mate_With_Chicken
        (The_Rooster : in out Rooster.Impl.Object'Class;
         The_Chicken : in     Chicken.Ref'Class);

    end Rooster.Impl;

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

Bill Beckwith, if you're listening, what do you think?

-- John Volan

--------------------------------------------------------------------------------
--  Me : Person := (Name                => "John Volan",
--                  Company             => "Raytheon Missile Systems Division",
--                  E_Mail_Address      => "jgv@swl.msd.ray.com",
--                  Affiliation         => "Enthusiastic member of Team Ada!",
--                  Humorous_Disclaimer => "These opinions are undefined " &
--                                         "by my employer and therefore " &
--                                         "any use of them would be "     &
--                                         "totally erroneous.");
--------------------------------------------------------------------------------






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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-18 22:17         ` John Volan
@ 1994-10-19  1:01           ` Bob Duff
  1994-10-19  4:45             ` Jay Martin
       [not found]           ` <CxwGJF.FwB@ois.com>
  1 sibling, 1 reply; 45+ messages in thread
From: Bob Duff @ 1994-10-19  1:01 UTC (permalink / raw)


In article <1994Oct18.221751.15457@swlvx2.msd.ray.com>,
John Volan <jgv@swl.msd.ray.com> wrote:
>However, making it this general was just a gratuitous freebie.  I
>threw it in because I couldn't see any reason not to -- but now I do
>see the reason.  At any rate, there is some room to back off: The
>original intent was to be able to "opaquely" store pointers
>designating what would (eventually) be tagged record types -- most
>likely class-wide types, and most likely only *definite* tagged record
>types.  So it would not hurt things very much if wee restricted the
>contract to only support pointers designating definite, class-wide
>tagged record types:

You probably have a higher probability of being portable to more
compilers if you use general access types.  Say "access all" instead of
just "access".  The reason is that the latter is pool-specific, and the
compiler very well might take advantage of specific properties of that
storage pool.  If you use general access types (access all), then the
compiler is less likely to play games on you.

>        type Pointer is access Object'Class;

Better say:

    type Pointer is access all Object'Class;
                           ^^^

>>Another implementation I've heard about (from Rational, I think?),
>>creates a separate storage pool for every access type, and uses various
>>virtual memory tricks to make that efficient.  Access types end up being
>>represented in various numbers of bits, I believe.
>
>So, depending on what pools the clients store their tagged types in,
>even the above scheme might not turn out to be portable.

If you use general access types, you will probably defeat such
cleverness in the compiler.  (No guarantees, though.)

>    generic
>      type Object (<>) is limited private;
>    package Address_To_Access_Conversion is
>      type Object_Pointer is access all Object;
>      ...
>
>In other words, this package provides a *new* access type into which
>address values can be converted.  It's *not* providing the capability
>to convert some *arbitrary* access type into addresses.

Explicit type conversions between general access types are allowed in
certain circumstances.  Check out the RM for details.

>This is a bit of a restriction, but not too unreasonable.  In fact,
>there may be other reasons for introducing a root Universal class
>anyway.  Other object-oriented "infrastructures" often do something
>similar.

Yes.  In Smalltalk and some other languages, there's a class that's the
mother of all classes.

- Bob
-- 
Bob Duff                                bobduff@inmet.com
Oak Tree Software, Inc.
Ada 9X Mapping/Revision Team (Intermetrics, Inc.)



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-19  1:01           ` Bob Duff
@ 1994-10-19  4:45             ` Jay Martin
  1994-10-19 14:38               ` Mark A Biggar
  1994-10-20 11:25               ` Robb Nebbe
  0 siblings, 2 replies; 45+ messages in thread
From: Jay Martin @ 1994-10-19  4:45 UTC (permalink / raw)


With all these ugly workarounds it looks like we must have a
language extension to Ada to handle mutual dependencies.
Otherwise Ada9x is a "joke".  Of course if there is no way that Ada
will be extended quickly, it will be a "joke" anyway.  Hopefully C++
has taught language designers/standardizers something.


The extension would be of the form:

package forward X is
  type XType;
  type XPtrType is access XType;
end X;

And would be severely resticted to only allow for incomplete types
declaration and access types to incomplete types.  These of course
would have to be repeated/elaborated in the package spec.

Thus, there would be a third package part in Ada compilation libraries
(Spec and body being the other two).  What it does is tells the Ada
compiler to not give an error if these yet to be specified types are
used in a spec.  

So basically a programmer could compile the forwards first, then the
specs and finally the bodies into the Ada library.  (GNAT looney
tunes "#include the spec" implementation of the Ada library
would place all the withed package's forwards before their specs
when compiling.) 

Of course, you couldn't directly declare incomplete objects in the private
parts of specs.   An elegant way of handling this (which would
be too obese to put in ada) would be to have a separately compiled
"package representation" part of a package which would basically
remove the private part of spec out of the spec.  For example:

with X; 
package representation Y is
  type YType is
   record
     P1:integer;
     P2:X.XType;
   end record;
end X; 

Its neat because it removes implementation details from the spec 
where they never belonged and allows for mutually recursive types to
be directly included into the abstract data type (instead of having a
pointer to it).

Jay













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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-19  4:45             ` Jay Martin
@ 1994-10-19 14:38               ` Mark A Biggar
       [not found]                 ` <38fi4r$l81@oahu.cs.ucla.edu>
  1994-10-20 11:25               ` Robb Nebbe
  1 sibling, 1 reply; 45+ messages in thread
From: Mark A Biggar @ 1994-10-19 14:38 UTC (permalink / raw)


In article <38289r$79m@oahu.cs.ucla.edu> jmartin@oahu.cs.ucla.edu (Jay Martin) writes:
>With all these ugly workarounds it looks like we must have a
>language extension to Ada to handle mutual dependencies.
>Otherwise Ada9x is a "joke".  Of course if there is no way that Ada
>will be extended quickly, it will be a "joke" anyway.  Hopefully C++
>has taught language designers/standardizers something.
>The extension would be of the form:
>
>package forward X is
>  type XType;
>  type XPtrType is access XType;
>end X;
>
>And would be severely resticted to only allow for incomplete types
>declaration and access types to incomplete types.  These of course
>would have to be repeated/elaborated in the package spec.

This is going back to a "One True Way" of OOP again.  What's so ugly about:

package Forward_X is
    type X_Parent is abstract tagged null record;
    type X_Ptr_Type is access all X_parent;
end Forward_X;

Especially when supported bu generics like John is proposing.

>Thus, there would be a third package part in Ada compilation libraries
>(Spec and body being the other two).  What it does is tells the Ada
>compiler to not give an error if these yet to be specified types are
>used in a spec.  
>So basically a programmer could compile the forwards first, then the
>specs and finally the bodies into the Ada library.  (GNAT looney
>tunes "#include the spec" implementation of the Ada library
>would place all the withed package's forwards before their specs
>when compiling.) 
>Of course, you couldn't directly declare incomplete objects in the private
>parts of specs.   An elegant way of handling this (which would
>be too obese to put in ada) would be to have a separately compiled
>"package representation" part of a package which would basically
>remove the private part of spec out of the spec.  For example:
>with X; 
>package representation Y is
>  type YType is
>   record
>     P1:integer;
>     P2:X.XType;
>   end record;
>end X; 
>Its neat because it removes implementation details from the spec 
>where they never belonged and allows for mutually recursive types to
>be directly included into the abstract data type (instead of having a
>pointer to it).

But this would still require the compliation of both spec and "representation"
parts before you could compile anything that depended on the package.
Totally revamping the package scheme just to increase the eligence of 
a boundary case (especially when there are reasonable workarounds) is
unproductive.

--
Mark Biggar
mab@wdl.loral.com







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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
       [not found]           ` <CxwGJF.FwB@ois.com>
@ 1994-10-19 16:35             ` John Volan
  0 siblings, 0 replies; 45+ messages in thread
From: John Volan @ 1994-10-19 16:35 UTC (permalink / raw)


beckwb@ois.com (R. William Beckwith) writes:

>John Volan (jgv@swl.msd.ray.com) wrote:

>: I would
>: argue that such a scheme falls into the trap of "inheritance
>: collision", where one usage of inheritance (providing alternate
>: programming-interface views for a single class of real-world entities)
>: gets in the way of the "customary" use of inheritance (supporting
>: generalization-specialization relationships between different classes
>: of real-world entities).

>It shouldn't because we are just added an intermediate level of
>inheritance between each "customary" use of inheritance.  

Doing that will work -- until we have to establish a mutually
recursive association between a class and *one of its own subclasses*.
That was the "acid test" that I posed in my original "Challenge".
Consider the Rooster class in my (admittedly bizarre) example.  The
Rooster class must somehow be "forward declared" before the spec of
the Chicken class so that the Chicken class can include Rooster-related
primitive operations. But ultimately, the Rooster class must *inherit*
from the Chicken class.  How can the Rooster interface be *derived* from
the forwarded Rooster declaration, *and* also inherit from the Chicken
interface?  This is what I've been calling "inheritance collision."

>But,
>the effect of this is that you don't achieve true decoupling.

Well, maybe we're using different definitions of "decoupling", because
I'd say that your original scheme *did* in fact achieve decoupling --
except that it breaks down when pushed to the limit, because of
"inheritance collision".  That's why I'd encourage you to use
generics for decoupling, rather than inheritance.

By the way, folks, an association between a class and one of its own
subclasses is *not* a rare or obscure occurrence, in fact it happens
all the time.  Consider, for instance, a file system, where a
"directory" is a kind of "file" that can contain other "files"
(including other "directories").  Another example is an
object-oriented drawing editor that allows "grouping" of drawable
objects.  A "group" is itself a kind of "drawable object" that
contains other "drawable objects" (including, perhaps, other
"groups").  There are many other similar situations.  Not all of these
associations have to be implemented in a mutually-recursive way,
necessarily, but being able to make even these associations mutually
recursive *and* decoupled is the ultimate test of any scheme for
decoupled mutual recursion, IMHO.

-- John Volan

--------------------------------------------------------------------------------
--  Me : Person := (Name                => "John Volan",
--                  Company             => "Raytheon Missile Systems Division",
--                  E_Mail_Address      => "jgv@swl.msd.ray.com",
--                  Affiliation         => "Enthusiastic member of Team Ada!",
--                  Humorous_Disclaimer => "These opinions are undefined " &
--                                         "by my employer and therefore " &
--                                         "any use of them would be "     &
--                                         "totally erroneous.");
--------------------------------------------------------------------------------




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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-19  4:45             ` Jay Martin
  1994-10-19 14:38               ` Mark A Biggar
@ 1994-10-20 11:25               ` Robb Nebbe
  1994-10-20 19:19                 ` John Volan
                                   ` (2 more replies)
  1 sibling, 3 replies; 45+ messages in thread
From: Robb Nebbe @ 1994-10-20 11:25 UTC (permalink / raw)


In article <38289r$79m@oahu.cs.ucla.edu>, jmartin@oahu.cs.ucla.edu (Jay Martin) writes:
|> With all these ugly workarounds it looks like we must have a
|> language extension to Ada to handle mutual dependencies.
|> Otherwise Ada9x is a "joke".  Of course if there is no way that Ada
|> will be extended quickly, it will be a "joke" anyway.  Hopefully C++
|> has taught language designers/standardizers something.
|> 

As an analogy consider a wall as representing a programming problem
and a language as providing a way to get to the other side. What you
have seen is a lot of "ugly workarounds" to go through the wall.
I saw at least one suggestion to go over the wall and another to
go around the wall but both were refused. Why? because the goal
had ceased being "getting to the other side" but instead had become
"going through the wall".

- Robb Nebbe

P.S. the fact that some langauges provide a tool that will cut a
hole in the wall and install a door to the otherside may lead
some to believe that it is a good idea to go through the wall.
They must first answer the question "Why was the wall there in
the first place?"



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-20 11:25               ` Robb Nebbe
@ 1994-10-20 19:19                 ` John Volan
  1994-10-26  0:07                 ` Mark S. Hathaway
  1994-10-26 18:48                 ` gamache
  2 siblings, 0 replies; 45+ messages in thread
From: John Volan @ 1994-10-20 19:19 UTC (permalink / raw)


Robb.Nebbe@di.epfl.ch (Robb Nebbe) writes:

>As an analogy consider a wall as representing a programming problem
>and a language as providing a way to get to the other side. What you
>have seen is a lot of "ugly workarounds" to go through the wall.
>I saw at least one suggestion to go over the wall and another to
>go around the wall but both were refused. Why? because the goal
>had ceased being "getting to the other side" but instead had become
>"going through the wall".

Well, Robb, the goal (in my mind) was always to get *through* the
wall, not to go around it.  Several folks misunderstood my question to
be how to get around the wall, but, at least for me, the goal didn't
"cease" to be one thing and turn into another.  Also, to be fair, I
didn't really "reject" those alternatives, I merely said that they
didn't meet my goal.  I think that I was careful to accept those
alternatives for what they were worth: They are useful for certain
applications (but not perhaps the application I had in mind).  I agree,
sometimes, for some applications, all that is needed is a sidewalk.

>- Robb Nebbe

>P.S. the fact that some langauges provide a tool that will cut a
>hole in the wall and install a door to the otherside may lead
>some to believe that it is a good idea to go through the wall.
>They must first answer the question "Why was the wall there in
>the first place?"

Ah, well, that is an interesting question.  If the wall truly serves
no purpose, then yes, I could see how going around it, or climbing
over it, or even demolishing it entirely, would be preferable to
taking the trouble to cut that hole and install that door.

But what if the wall were the side of a *building*?  Such a wall
serves a very definite purpose: It separates the interior of the
building from everything exterior to it, including things like weather
and wild animals.  It also separates the building from all the other
buildings in the city.  

If one's goal is to find a convenient way to get *inside* the
building, and not simply to take a stroll around it, then it is
pointless to suggest going "around" the wall.  Certainly, it is even
more ridiculous to suggest climbing *over* the building!  But I think
the proprietors of the building would be a tad miffed if one were to
suggest *demolishing* the wall.  And, in a large city full of
buildings, I don't think it is practical to suggest eliminating all
walls entirely simply because the citizenry need to be able to go from
one establishment to another in the course of their daily business.
Luckily, "arcologies" are still stuff of science fiction, or the
fevered dreams of former Soviet city planners.  No, one just has to
face the fact that walls are occasionally very valuable things, and
having a door in the middle of a wall might just be exactly what is
wanted.  Especially if it's strategically placed to offer convenient
access to those who have legitimate reasons for entering and exiting
the building, but properly guarded against those who do not.

Now, if your building material (programming language) is a relatively
flimsy substance such as paper or rawhide or canvas, it may be quite
easy to take a knife and cut yourself a nice, serviceable door-flap
any time you want.  On the other hand, if your wall is made of wood or
brick or concrete, then yes, it does take a bit of sweat to saw or
drill yourself a hole.  Some folks who are used to roughing it in the
wild in tents (and damn proud of it too!) might find all that effort
ludicrous.  A few of those folks might even suggest the use of
dynamite -- but results are not guaranteed.  

However, there may be other people in this world who have learned how
to work with stronger materials, and who are appreciative of having a
nice, sound roof over their heads when the weather gets rough.  Such
people might not see the effort of cutting the hole as a waste at all.
In fact, being conscientious civil engineers, they might even take the
trouble to finish off the edges of the hole, install a lintel,
baseplate, and hinges, mount the door, and, as an added courtesy to
the client, include a doorknob and a deadbolt.  Is that an "ugly
workaround"?  Only if it leaks in the rain!

Analogies are lovely things, but they can be double-edged swords :-)

--John Volan

--------------------------------------------------------------------------------
--  Me : Person := (Name                => "John Volan",
--                  Company             => "Raytheon Missile Systems Division",
--                  E_Mail_Address      => "jgv@swl.msd.ray.com",
--                  Affiliation         => "Enthusiastic member of Team Ada!",
--                  Humorous_Disclaimer => "These opinions are undefined " &
--                                         "by my employer and therefore " &
--                                         "any use of them would be "     &
--                                         "totally erroneous.");
--------------------------------------------------------------------------------




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

* Mutual Recursion Challenge
       [not found]                 ` <38fi4r$l81@oahu.cs.ucla.edu>
@ 1994-10-24 11:49                   ` Robert I. Eachus
  1994-10-24 20:32                     ` John Volan
  1994-10-24 17:42                   ` SOLVED! Decoupled Mutual Recursion Challenger John Volan
  1 sibling, 1 reply; 45+ messages in thread
From: Robert I. Eachus @ 1994-10-24 11:49 UTC (permalink / raw)


In article <38fi4r$l81@oahu.cs.ucla.edu> jmartin@oahu.cs.ucla.edu (Jay Martin) writes:

  > All in all this method seems to have alot of programming and
  > conceptual overhead.  Also there will probably have to be a
  > section in every decent Ada9x programming book explaining this
  > method.

    I hope not.

    There are many features in Ada 9X which lead to a better approach
to OOP.  In particular, the mindset problem here is that the mutual
recursion must be between peers.  Ada 9X does a nice job on recursion
between objects at different levels of abstraction, and most of
difficulty in the examples comes from constructing two types at the
same level of abstraction and in different packages.

    In my (so far limited, as is everyone's) experience in Ada 9X, you
are much more likely to be adding an abstraction, using a generic
mixins, when the need for recursion occurs.  In those cases, all the
baggage discussed is either there for other reasons or not necessary.
It may seem that creating a dozen abstract types which are only there
as placeholders is a problem, but in fact the only problem I have
found with it is coming up with names.  (The best strategy I have
found is to use the base class name joined with the generic package
name as the name of the package instance:

    package Persons_Office_Assignment is new Office_Assignment(Person);

    and elsewhere:

    package Office_Staff_Assignment is new Staff_Assignment(Office);

    As this particular instantiation should make clear, package
Staff_Assignment may also be used to add staff to projects, to
departments, etc.  And in fact it might be better to have the
assignment package defined as a double generic as a much higher level
and instanced down, or just as a generic with two type parameters as
suggested earlier in this discussion.  (In such a model, Person and
Office would be instances of Objects, and Assignment would create a
relationship.)

--

					Robert I. Eachus

with Standard_Disclaimer;
use  Standard_Disclaimer;
function Message (Text: in Clever_Ideas) return Better_Ideas is...



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
       [not found]                 ` <38fi4r$l81@oahu.cs.ucla.edu>
  1994-10-24 11:49                   ` Mutual Recursion Challenge Robert I. Eachus
@ 1994-10-24 17:42                   ` John Volan
  1994-10-24 22:37                     ` Jay Martin
  1 sibling, 1 reply; 45+ messages in thread
From: John Volan @ 1994-10-24 17:42 UTC (permalink / raw)


jmartin@oahu.cs.ucla.edu (Jay Martin) writes:

>>But this would still require the compliation of both spec and "representation"
>>parts before you could compile anything that depended on the package.
>>Totally revamping the package scheme just to increase the eligence of 
>>a boundary case (especially when there are reasonable workarounds) is
>>unproductive.

>>Mark Biggar
>>mab@wdl.loral.com

>I don't think that removing implementation details from the spec
>is a boundary case.  Note that I wrote that I thought a 
>representation part was too excessive an extension. I was just
>putting it out as an interesting idea taking separation of packages
>to an extreme.

Here, I agree with Mark Biggar.  The workaround (introducing another
level of indirection and hiding the actual object-structure type in
the package body) is a perfectly reasonable solution that gives you
exactly what you need, and it is preferable to a major change in the
language definition.  (It also happens to be similar to the way this
would be solved in C++.)  You could even combine this with a strategic
use of private child units to give you something similar to your
"package representation" construct.

>But I don't feel that package "forwards" are excessive (should be
>minimally easy to implement) and it allows the programmer to directly
>express what he wants to do.

Don't underestimate the complexities involved here.  Your "package
forward" idea is essentially identical to the "package abstract"
concept I suggested a while back (although my proposal didn't require
any new Ada reserved-words :-).  When I presented the idea of "package
abstracts", I at least considered some of the issues they raise:

1. Is a package abstract an optional feature, or are you compelled to
   precede every package spec with a package abstract?  If optional,
   how do you distinguish a package spec that has a preceding abstract
   from one that does not?  Or are we creating a situation analogous to
   the Ada83 problem of an "optional body for a bodiless package spec"?

2. How do you distinguish a "with"-clause that only imports a package
   abstract from one that imports the whole package spec?

3. Can a package-with-abstract be generic?  If so, where does the generic
   clause go?  How do you instantiate such a beast?  What impact does this
   have on the whole generic contract scheme?

4. This is much too late for 9X, and has to be left for 0X, if it goes
   anywhere at all.  Even if all the difficulties can be ironed out, is
   this feature worth the added compiler complexity, when there are
   reusable workarounds that already effectively extend the language?

>One point that I am making is that the
>Ada compilation scheme of compiling into a library in dependency
>order in a complete fail-safe way is not inherently incompatable with
>direct support for mutual recursion of objects.  This scheme is 
>inherently better than the brain-dead method of simple source code 
>insertion with every include file's code surrounded by "ifdefs" using
>preprocessor variables to prevent multiple inclusions. 

Violent agreement here! :-)

>  Mutual recursion is common from my experiences with Ada and other
>object oriented languages.  An example is: 

[snip description of a class X and a manager class which points to
class X, but class X also needs a pointer back to the manager class
because an X needs to notify its manager about certain events]

I agree, this is a common situation.

Back to Mark Biggar:

>>This is going back to a "One True Way" of OOP again.  What's so ugly about:

>>package Forward_X is
>>    type X_Parent is abstract tagged null record;
>>    type X_Ptr_Type is access all X_parent;
>>end Forward_X;

>>Especially when supported bu generics like John is proposing.

>I found the complexity of John's method alittle overwhelming and was
>turned off by the use of unchecked_conversion and generics.  

Hmmm ... in reality, I don't think my "decoupling-via-generics"
technique is any more complex than the "decoupling-via-inheritance"
technique.  Perhaps I was a bit too thorough in spelling out how my
technique worked and how you could use it, and that might have given
the impression of greater complexity.  But I think, if you actually
work out a complete example using either technique, you will see a
similar degree of complexity.  (In fact, you [Jay Martin] did flesh
out an example of decoupling-via-inheritance later in your post, and
you make the point that it seems pretty complex.)

In fact, in actual usage, I believe my decoupling-via-generics scheme
turns out to be *less* complex than the decoupling-via-inheritance
scheme.  There's less code that an end-user has to write to introduce
the "forwarding" declaration for a class, because it's just an
instantiation of a reusable generic package.  More to the point, my
technique avoids the "inheritance collision" problem (competing usages
of inheritance interfering with each other), because it divorces the
decoupling issue from inheritance.  Thus, my technique reserves
inheritance for its most "customary" use: supporting
generalization/specialization relationships from the problem domain.
No intervening levels of abstract types intrude to clutter this up, so
the resulting code is easier to understand.

Jay, why were you turned off by the use of generics?  Personally, 
I think generics are very elegant and powerful tools for solving a
lot of programming problems (especially thorny ones like this).
I tend to think a lot of people overlook the power of generics
when they program, and this is unfortunate.

As for the use of Unchecked_Conversion, realize that that was just one
of several possible ways of *implementing* my technique.  My generic
Identity package attempts to support the notion of "opaque identity"
in a completely abstract way: From an end-user's perspective, the
Identity.Value type is just a "black box".  It's just this private
type that can somehow be translated "magically" into some pointer type
which the user can define at a later time.  How the Identity.Value
type is actually implemented is completely immaterial, as long as it
works.

I could have waved my hands here, leaving everybody twisting in the
wind as to exactly how to implement this private type.  But I felt
obligated to provide at least one possible implementation.  True, I
started off with Unchecked_Conversion, and that wasn't very "pretty",
but at least it was hidden away as an implementation detail.  It's
"under the hood," so to speak, so whether it's pretty or not doesn't
matter to the clients of the abstraction.  (Look under the hood of
your own car.  Is what you find there "pretty"?  Even if it isn't,
does it matter to you when you're behind the wheel?)

But there are many other possible implementations, each involving
different degrees of portability, balanced against different
fine-tunings of the generalness of the generic contract.  In fact, one
of those possible implementations exploits *inheritance* to implement
the decoupling!  The Identity.Value type could be derived from a
class-wide "Universal.Pointer" type that designates objects of a
"Universal.Object" type.  All participating object types have to be
derived, directly or indirectly, from that Universal.Object type, but
this is not an unreasonable restriction.  That way, the translations
between "opaque" Identities and "transparent" Pointers can exploit
type-casting operations (including "narrowing" and "widening") that
are totally type-safe and portable.  But remember that this use of
inheritance is completely encapsulated as an implementation detail
inside the Identity package.  So, in particular, it does *not* result
in "inheritance collision."

>I posted
>a global variable solution as sort of a joke.  

Well, we'll leave it at that ... :-)

>And I am not persuaded
>by the idea of putting everything in the same package. 

Nor am I.  Thus my twisting of Robb Nebbe's "door-through-a-wall"
analogy: If you have only two buildings that people need to go
between, it might seem practical at first to simply break down the
intervening walls and merge the two buildings, rather than go to the
trouble of installing doors.  But carry that strategy out to an entire
city and what do you have?  One huge building with no walls anywhere?
(Note: Even shopping malls and skyscrapers have walls inside them.
More to the point, try to imagine a skyscraper without *floors*! :-)

>Using tagged types looks like the best way. 

I disagree, I think generics are the best way to achieve decoupling.

>But I have qualms about using
>abstract types for this purpose because abstract type doesn't really
>represent an dynamic abstract type but it represents a workaround
>trick. Its a type we can put in the spec so we can pass it in and
>then type convert it to the proper type.

I agree entirely here.  Moreover, I object to
decoupling-via-inheritance because of its "collision" with the more
"customary" use of inheritance.  But if a solution must use some
"workaround" that requires a "trick", isn't it a nicer to distill the
workaround to its essential abstraction, and then hide the
"trickiness" of it as an implementation detail, as I do with my
Identity generic?

>Every new Ada9x programmer
>will have to butt his head up against this problem and then learn this
>ugly trick (or idiom (nicer)).  This makes the language harder to learn
>and less elegant. 

Hmm... beauty (and ugliness) is in the eye of the beholder.  I kind of
agree with you that decoupling-via-inheritance is rather "ugly", but
I'd shy away from using that as an argument against it as a technique.
Other folks may reasonably complain that such an argument is based on
subjective taste and not on sound engineering reasoning.  But I've
already objected to decoupling-via-inheritance along other lines that
are not purely subjective: The use of inheritance to do decoupling can
"collide" with the use of inheritance for problem-domain
generalization/specialization.  This can be seen most clearly in any
situation that constitutes my "Challenge": wherever a class and *one
of its own subclasses* has a mutually-recursive relationship.

Personally, I think my solution of decoupling-via-generics is quite
elegant ... but of course, I'm bound to think that! :-)

>Lets look at the example:

[snip example showing use of decoupling-via-inheritance technique]

>All in all this method seems to have alot of programming and conceptual
>overhead.  Also there will probably have to be a section in every
>decent Ada9x programming book explaining this method.
>                                                     w
>Jay

Yes, this "learning-curve" is a drawback of the
decoupling-via-inheritance technique.  For that matter, it's also a
drawback of my decoupling-via-generics technique.  Even a concept such
as "package forwards" or "package abstracts" would present a certain
amount of complexity that would need to be learned and understood.  In
fact, even if you give up on decoupling entirely, and just put your
mutually-recursive types in the same package, you still have to deal
with using incomplete type declarations to forward declare at least
one of the types.

So how much of this learning-curve is due to the nature of these
various solutions, and how much to the nature of the problem itself?
Isn't the whole idea of mutual recursion itself a tricky one to grasp,
regardless of how it's rendered in a programming language?  The only
way to "simplify" it as a programming issue would be to *obscure* the
issue, the way Eiffel or Smalltalk do: Instead of explicitly stating
dependencies, you just mention other classes anywhere in your class's
interface or implementation, and the programming environment takes
care of any nasty mutual recursions for you, whether you realize that
they're there or not. 

Is it better for a programmer to be *unaware* of these situations?  Or,
supposing the original programmer is fully aware of the mutual recursions,
wouldn't it be a good idea to make those mutual recursions very obvious
to other folks who have to read the code (such as future maintainers)?
At least, with my decoupling-via-generics technique, you have a clear
signpost indicating that decoupled mutual recursion may be present.
Whenever you see a context clause that says

    with Identity;

or later, wherever you see something like:

    with Employee_Identity;
    with Office_Identity;
    ...

you know that mutual recursion lies ahead.

-- John Volan

--------------------------------------------------------------------------------
--  Me : Person := (Name                => "John Volan",
--                  Company             => "Raytheon Missile Systems Division",
--                  E_Mail_Address      => "jgv@swl.msd.ray.com",
--                  Affiliation         => "Enthusiastic member of Team Ada!",
--                  Humorous_Disclaimer => "These opinions are undefined " &
--                                         "by my employer and therefore " &
--                                         "any use of them would be "     &
--                                         "totally erroneous.");
--------------------------------------------------------------------------------



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

* Re: Mutual Recursion Challenge
  1994-10-24 11:49                   ` Mutual Recursion Challenge Robert I. Eachus
@ 1994-10-24 20:32                     ` John Volan
  1994-10-26 11:42                       ` Generic association example (was Re: Mutual Recursion Challenge) Robert I. Eachus
  0 siblings, 1 reply; 45+ messages in thread
From: John Volan @ 1994-10-24 20:32 UTC (permalink / raw)


eachus@spectre.mitre.org (Robert I. Eachus) writes:

>    There are many features in Ada 9X which lead to a better approach
>to OOP.  In particular, the mindset problem here is that the mutual
>recursion must be between peers.  Ada 9X does a nice job on recursion
>between objects at different levels of abstraction, and most of
>difficulty in the examples comes from constructing two types at the
>same level of abstraction and in different packages.

>    In my (so far limited, as is everyone's) experience in Ada 9X, you
>are much more likely to be adding an abstraction, using a generic
>mixins, when the need for recursion occurs.  In those cases, all the
>baggage discussed is either there for other reasons or not necessary.

Could you clarify this a bit, and elaborate on how using mixins would
work here?  I think I understand what you're driving at, but perhaps
other folks won't.  What, precisely, do you mean by the "baggage" that
would be there anyway?  Also, how well does the mixin technique really
scale up, when you imagine many classes, many associations, and each
class participating in many associations?

>It may seem that creating a dozen abstract types which are only there
>as placeholders is a problem, but in fact the only problem I have
>found with it is coming up with names.  (The best strategy I have
>found is to use the base class name joined with the generic package
>name as the name of the package instance:

>    package Persons_Office_Assignment is new Office_Assignment(Person);

>    and elsewhere:

>    package Office_Staff_Assignment is new Staff_Assignment(Office);

>    As this particular instantiation should make clear, package
>Staff_Assignment may also be used to add staff to projects, to
>departments, etc.

I take it that Persons_Office_Assignment would declare a derived type
inheriting from Person, with an extension supporting the association
with Office.  Likewise, Office_Staff_Assignment would declare a
derived type inheriting from Office, with an extension supporting the
association with Person.  One problem I see with this particular
formulation is that a Person-who-can-occupy-an-Office can point to any
Office, not necessarily only an Office-that-can-be-occupied; likewise,
an Office-that-can-be-occupied can point to any Person, not
necessarily only a Person-who-can-occupy-an-Office.  Is there a way
of putting this together that guarantees the invariant that if a
Person occupies an Office, then that Office is occupied by that
Person?

>And in fact it might be better to have the
>assignment package defined as a double generic as a much higher level
>and instanced down, or just as a generic with two type parameters as
>suggested earlier in this discussion.  (In such a model, Person and
>Office would be instances of Objects, and Assignment would create a
>relationship.)

Do you mean something like this?

    generic
      type Former_Base is tagged limited private;
      type Latter_Base is tagged limited private;
    package One_To_One_Association is

      type Former is new Former_Base with private;
      type Former_Pointer is access all Former'Class;

      type Latter is new Latter_Base with private;
      type Latter_Pointer is access all Latter'Class;

      ... -- Subprograms supporting association.  Some may be primitives for
          -- either Latter or Former type, but none may be primitive for both.

    private

      type Former is new Former_Base with
        record
          Its_Latter : Latter_Pointer;
        end record;

      type Latter is new Latter_Base with
        record
          Its_Former : Former_Pointer;
        end record;

   end One_To_One_Association;

There would be something similar for One_To_Many_Association and
Many_To_Many_Association.  Then we could instantiate it something
like this:

   package Person is
     type Object is tagged limited private;
     ... -- primitives for ordinary attributes not involving associations
   end Person;

   package Office is
     type Object is tagged limited private;
     ... -- primitives for ordinary attributes not involving associations
   end Office;

   package Building is
     type Object is tagged limited private;
     ... -- primitives for ordinary attributes not involving associations
   end Building;

   ... etc.

   with Person;
   with Office;
   with One_To_One_Association;
   package Person_Occupies_Office is new
     One_To_One_Association (Person.Object, Office.Object);

   with Person_Occupies_Office;
   with Building;
   package Building_Contains_Office is new
     One_To_Many_Association (Building.Object, Person_Occupies_Office.Latter);

   ... etc.

   with Building_Contains_Office;
   package Total_Office is
     type Object is new Building_Contains_Office.Latter with null record;
   end Total_Office;

   with Building_Contains_Office;
   package Total_Building is
     type Object is new Building_Contains_Office.Former with null record;
   end Total_Buidling;

   with Person_Occupies_Office;
   package Total_Person is
     type Object is new Person_Occupies_Office.Former;
   end Total_Person;

   ... etc.

Of course, the actual immediate parent type for each "Total" object
type would depend on the particular mix of classes and associations in
the specific application.  If the requirements of the problem changed
to add a new association to a class, we'd have to change where the
given "Total" type derived from.

And now for the "acid test":  Can this technique meet the "Challenge"
of getting a class into a mutually-recursive association with one of its
own subclasses?

    with Person_Occupies_Office;
    package Manager is
      type Object is new Person_Occupies_Office.Former with private;
      ... -- primitives for ordinary attributes not involving associations
    end Manager;

    with Person_Occupies_Office;
    with Manager;
    with One_To_Many_Association;
    package Manager_Supervises_Person is new
      One_To_Many_Association (Manager.Object, Person_Occupies_Office.Former);


    with Manager_Supervises_Person;
    package Total_Manager is
      type Object is new Manager_Supervises_Person.Former with null record;
    end Total_Manager;

    -- Oh, and now we have to change how we define Total_Person:

    with Manager_Supervises_Person;
    package Total_Person is
      type Object is new Manager_Supervises_Person.Latter with null record;
    end Total_Person;

But there's a problem here: Total_Manager.Object inherits from
Manager_Supervises_Person.Former, which inherits from Manager.Object,
which inherits from Person_Occupies_Office.Former.  But
Total_Manager.Object does not inherit from
Manager_Supervises_Person.Latter.  So a Total_Person can have a
supervising Manager, but a Total_Manager is not a Total_Person, so it
cannot have a supervising Manager of its own.  It looks like this
mixin technique results in "inheritance collision".  Is there a way
around this?

At the very least, this mixin technique seems a very confusing way to
build up classes.  Even barring any "Challenging" situation, my gut
feeling is that this technique sooner or later will collapse under its
own weight.  But at this point, I can't prove this rigorously.  One
thing that bothers me is that you have to pick some arbitrary order to
build up all the associations, so that in the end the total view of
each class includes all the associations it will participate in.  This
introduces arbitrary dependencies among the association instantiations
that don't seem to mean anything within the problem domain, but which
might have a detrimental impact on the software's resilience in the
face of requirements change.

If I'm totally mixed-up about mixins :-), please help me out.  Thanks.

-- John Volan

--------------------------------------------------------------------------------
--  Me : Person := (Name                => "John Volan",
--                  Company             => "Raytheon Missile Systems Division",
--                  E_Mail_Address      => "jgv@swl.msd.ray.com",
--                  Affiliation         => "Enthusiastic member of Team Ada!",
--                  Humorous_Disclaimer => "These opinions are undefined " &
--                                         "by my employer and therefore " &
--                                         "any use of them would be "     &
--                                         "totally erroneous.");
--------------------------------------------------------------------------------



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-24 17:42                   ` SOLVED! Decoupled Mutual Recursion Challenger John Volan
@ 1994-10-24 22:37                     ` Jay Martin
  1994-10-25  5:47                       ` Matt Kennel
  1994-10-25 15:54                       ` John Volan
  0 siblings, 2 replies; 45+ messages in thread
From: Jay Martin @ 1994-10-24 22:37 UTC (permalink / raw)


jgv@swl.msd.ray.com (John Volan) writes:

>Don't underestimate the complexities involved here.  Your "package
>forward" idea is essentially identical to the "package abstract"
>concept I suggested a while back (although my proposal didn't require
>any new Ada reserved-words :-).  When I presented the idea of "package
>abstracts", I at least considered some of the issues they raise:

>1. Is a package abstract an optional feature, or are you compelled to
>   precede every package spec with a package abstract?  If optional,
>   how do you distinguish a package spec that has a preceding abstract
>   from one that does not?  Or are we creating a situation analogous to
>   the Ada83 problem of an "optional body for a bodiless package spec"?

>2. How do you distinguish a "with"-clause that only imports a package
>   abstract from one that imports the whole package spec?

>3. Can a package-with-abstract be generic?  If so, where does the generic
>   clause go?  How do you instantiate such a beast?  What impact does this
>   have on the whole generic contract scheme?

>4. This is much too late for 9X, and has to be left for 0X, if it goes
>   anywhere at all.  Even if all the difficulties can be ironed out, is
>   this feature worth the added compiler complexity, when there are
>   reusable workarounds that already effectively extend the language?

1. Optional, No, No.
2. No.
3. No.
4. Who cares. If the standard can't be easily modified as was the
   case for Ada83 then Ada9x is dead.  The Compiler complexity is trivial,
  the language would be cleaner.


Ada9x is too obese and is being too effected by trying to be an
"elegant" (rigid) extension of obese Ada83.  I really don't understand
why can't some clown spend a few minutes to come up with a cleaner
smaller (more minimalist) Ada style language.  My theory of why CS is
not coming up with one is: (1) Most Computer Scientists are
masturbating on useless theoretic, pseudo "huge breakthroughs" and
"scientific" things.  Language design requires them to sink into the
abyss of unholy "social science" and the law of the lowest common
denominator.  (2) Even if one did, political jealousy and power games
within the Computer Science community would not allow them to
recognize, except, support and then champion a really good and
software engineering efficient language.

(Can't do anything other than rant now (got to fix bugs)) Jay.



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-24 22:37                     ` Jay Martin
@ 1994-10-25  5:47                       ` Matt Kennel
  1994-10-25 10:04                         ` David Emery
  1994-10-25 16:43                         ` John Volan
  1994-10-25 15:54                       ` John Volan
  1 sibling, 2 replies; 45+ messages in thread
From: Matt Kennel @ 1994-10-25  5:47 UTC (permalink / raw)


Jay Martin (jmartin@baleen.cs.ucla.edu) wrote:

: Ada9x is too obese and is being too effected by trying to be an
: "elegant" (rigid) extension of obese Ada83.  I really don't understand
: why can't some clown spend a few minutes to come up with a cleaner
: smaller (more minimalist) Ada style language.

That's what Meyer did, it's called Eiffel.  Really.  Ada83 was a big
influence.

Absent this, the problem here in 9x can be "solved" by a nearly transparent
change to the language:  say "cyclic dependencies in types, but not
initialization expressions, are now allowed."  like
it always should have been, in my opinion.

Now you can declare an X which has a component of type/package/class/whatever
Y, and have Y which has a component of class X.

It's not transparent to the compiler implementors, but no fix
here would be.

--
-Matt Kennel  		mbk@inls1.ucsd.edu
-Institute for Nonlinear Science, University of California, San Diego
-*** AD: Archive for nonlinear dynamics papers & programs: FTP to
-***     lyapunov.ucsd.edu, username "anonymous".



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-25  5:47                       ` Matt Kennel
@ 1994-10-25 10:04                         ` David Emery
  1994-10-25 16:43                         ` John Volan
  1 sibling, 0 replies; 45+ messages in thread
From: David Emery @ 1994-10-25 10:04 UTC (permalink / raw)


>: Ada9x is too obese and is being too effected by trying to be an
>: "elegant" (rigid) extension of obese Ada83.  I really don't understand
>: why can't some clown spend a few minutes to come up with a cleaner
>: smaller (more minimalist) Ada style language.
>That's what Meyer did, it's called Eiffel.  Really.  Ada83 was a big
>influence.

Eiffel and Ada(83|9X) have somewhat different design goals.  Ada tends
to be more general-purpose, while Eiffel tends to promote a specific
view of software design.

				dave
--
--The preceeding opinions do not necessarily reflect the opinions of
--The MITRE Corporation or its sponsors. 
-- "A good plan violently executed -NOW- is better than a perfect plan
--  next week"                                      George Patton
-- "Any damn fool can write a plan.  It's the execution that gets you
--  all screwed up"                              James Hollingsworth
-------------------------------------------------------------------------



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-24 22:37                     ` Jay Martin
  1994-10-25  5:47                       ` Matt Kennel
@ 1994-10-25 15:54                       ` John Volan
  1994-10-26  1:24                         ` Bob Duff
  1994-10-28  4:28                         ` Jay Martin
  1 sibling, 2 replies; 45+ messages in thread
From: John Volan @ 1994-10-25 15:54 UTC (permalink / raw)


jmartin@baleen.cs.ucla.edu (Jay Martin) writes:

>jgv@swl.msd.ray.com (John Volan) writes:

>>Don't underestimate the complexities involved here.  Your "package
>>forward" idea is essentially identical to the "package abstract"
>>concept I suggested a while back (although my proposal didn't require
>>any new Ada reserved-words :-).  When I presented the idea of "package
>>abstracts", I at least considered some of the issues they raise:

>>1. Is a package abstract an optional feature, or are you compelled to
>>   precede every package spec with a package abstract?  If optional,
>>   how do you distinguish a package spec that has a preceding abstract
>>   from one that does not?  Or are we creating a situation analogous to
>>   the Ada83 problem of an "optional body for a bodiless package spec"?

>>2. How do you distinguish a "with"-clause that only imports a package
>>   abstract from one that imports the whole package spec?

>>3. Can a package-with-abstract be generic?  If so, where does the generic
>>   clause go?  How do you instantiate such a beast?  What impact does this
>>   have on the whole generic contract scheme?

>>4. This is much too late for 9X, and has to be left for 0X, if it goes
>>   anywhere at all.  Even if all the difficulties can be ironed out, is
>>   this feature worth the added compiler complexity, when there are
>>   reusable workarounds that already effectively extend the language?

>1. Optional, No, No.
>2. No.

"NO"?  What's the point of having two outside views of a package (one
incomplete, the other fuller) if a potential client can't select how
much of a view they want?  (Do you even have a *clue* what I'm talking
about, Jay?)

>3. No.

Why not?  Why do we have to make a *special exception* in this case,
for a feature that ought to be *orthogonal* to this?  Is it just
because someone like you doesn't want to be bothered about thinking
things through?

>4. Who cares. If the standard can't be easily modified as was the
>   case for Ada83 then Ada9x is dead.  

"Easily modified"?  Do you think what the MRT has been doing these
past few years was *easy*?  Where have you *been*?  Do you have
*any* idea about what it takes to revise an *international standard*?

>  The Compiler complexity is trivial,
>  the language would be cleaner.

"Cleaner"?  With yet another language feature to complicate things?  I
don't think it would be the *language* that would be "cleaner".  The
*programs* written in that language would be (a tad) "cleaner", at the
expense of (possibly a lot) more complexity in the language.  Or
rather, a certain very particular *style* of programs would be
"cleaner", possibly at the expense of other styles of programming.

I'm not a language lawyer, and I've never written a compiler, so I
haven't presumed to make any claim as to how "trivial" this kind of
feature would be.  At most, I've tried to point out a few of the
conceptual difficulties I could see, but that's all speculation on my
part.  Maybe it *is* "trivial", and if so, I hope some experienced
language lawyers will pipe up and say so.  Even if it isn't trivial,
maybe it's worth it anyway -- and if so, I hope some language lawyers
will pipe up about that too.  But for now, I'm reserving my judgment.

Jay, are *you* a language lawyer?  Have *you* ever written an
industrial-strength compiler?  That's not a rhetorical dig.  If you've
got some real experience here, by all means say so. But somehow I
doubt it, since your organization seems to be a university computer
science department, and I suspect you are a student.

>Ada9x is too obese and is being too effected [sic] by trying to be an
>"elegant" (rigid) extension of obese Ada83.

One man's "elegant" is another man's "rigid."  Is C++ an "elegant"
extension of C, or is it "rigidly" preserving C's syntax, which many
(even in the C/C++ camp) have disavowed as obsolete and kludgy?  (For
goodness sake, even *Bjarne Stroustrup* seems to have chafed a bit
about C syntax -- but I won't presume to speak for him.)  Is C++ still
"lean and mean" today, or is the agglomeration of new features such as
templates, exceptions, first-class bool and string types, and
namespaces, (all of which were in Ada ten years ago) turning it into
an "obese" language?  Is Eiffel "elegant" because of its minimalist
design, or is it "rigid" because it offers only "One True Way" of
modularizing a program, and has to resort to auxiliary languages such
as LACE to deal with higher levels of organization?

>I really don't understand
>why can't some clown ...
                ^^^^^ 
Let's see, from now on we'll have all our programming languages
designed by Bozo and Ronald MacDonald, and maybe a few Congressmen,
too...

>... spend a few minutes ...
           ^^^^^^^^^^^^^ 
Is that how long K&R spent designing C? Might explain a lot ...  

> ... to come up with a cleaner
>smaller (more minimalist) Ada style language.  

... as long as your own "trivial" pet language construct gets into it?
Honestly, do you really think that language designs can just be
slapped together, or that you can just slap in yet another feature
without causing a ripple effect in the whole design of a language?  It
seems to me that *that* way leads to *larger*, *more complex*, *less
cohesive* languages, NOT "smaller, more minimalist" languages.

Of course, if you so vehemently believe that this *is* such a 
trivial feature to slap on top of Ada9X, then I suggest that you
get yourself a copy of GNAT, revise it to implement your new
language feature, experiment with it, and then write a learned
treatise on just how trivial and orthogonal it is (or isn't,
as you might just discover).  Put up or shut up.

>My theory of why CS is
    ^^^^^^
>not coming up with one is: (1) Most Computer Scientists are
>masturbating on useless theoretic, pseudo "huge breakthroughs" and
                         ^^^^^^^^^
>"scientific" things.  

Oh, I see.  It's okay for *you* to have your pet theories, but nobody
else's ideas are worth pursuing.  Whatever's "trivial" according to
*your* theories are nuggets of wisdom to be enshrined, but if anybody
*else* has an opposing view of what's important for software
engineering, that's "pseudoscience."

Maybe your jaundiced view about "Computer Science" has less to do with
the state of the software engineering *industry* and more to do with
the state of *academic* computer science -- or maybe it just says more
about the particular academic *institution* you're currently part of.
If the latter is the case, then I feel sorry for you, and suggest you
transfer immediately to another school.

>Language design requires them to sink into the
>abyss of unholy "social science" and the law of the lowest common
                                      ^^^^^^^^^^^^^^^^^^^^^^^^^^^^
>denominator.  
 ^^^^^^^^^^^^

I understand it all now.  Forget striving for excellence, folks! Don't
bother!  Let's just keep things at the level where any fool can slap
software together!  Sure, only a fool would buy or use such software,
but that's okay, because *everybody* would be equally foolish.  O
Brave New World ...

>(2) Even if one did, political jealousy and power games
>within the Computer Science community would not allow them to
>recognize, except [sic], support and then champion a really good and
>software engineering efficient language.

"Let him who is without sin ..."  In my experience, those who
whine most about "political jealousy" and "power games" are usually
those who *tried* to play political power games in the past and
*failed*.  

Another phenomenon I've seen is this: Somebody relatively naive about
a subject thinks that they've found some grand and glorious solution
to all problems, and presents it to the experts.  The experts might
agree about some of the good points in the neophyte's ideas, but,
being more experienced than the neophyte, they also notice some of the
flaws, and calmly point them out.  Instead of addressing the flaws and
possibly taking the idea further (and maybe *learning* something in
the process), the neophyte gets angry, starts accusing the experts of
political scheming and playing power games, and storms off in a huff.
The experts look at each other and shrug, and secretly pray that the
neophyte doesn't somehow grow up to be their manager some day...

>(Can't do anything other than rant now (got to fix bugs)) Jay.
                               ^^^^      ^^^^^^^^^^^^^^^ 
Maybe if you (and a few other people) spent less time "ranting" about
"rigid, obese" languages, and spent more time trying to "recognize,
accept, support, and then champion a really good and software
engineering efficient language", then you might now be spending less
of your time fixing bugs, and more of your time doing some real
software engineering in that language.  (Guess which language I mean?)

-- John Volan

P.S.  After an outburst like that, folks, I wouldn't blame any of you
if you stuck this whole thread in your kill file.  I'm even tempted to
do so now, and I started this thread!

--------------------------------------------------------------------------------
--  Me : Person := (Name                => "John Volan",
--                  Company             => "Raytheon Missile Systems Division",
--                  E_Mail_Address      => "jgv@swl.msd.ray.com",
--                  Affiliation         => "Enthusiastic member of Team Ada!",
--                  Humorous_Disclaimer => "These opinions are undefined " &
--                                         "by my employer and therefore " &
--                                         "any use of them would be "     &
--                                         "totally erroneous.");
--------------------------------------------------------------------------------







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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-25  5:47                       ` Matt Kennel
  1994-10-25 10:04                         ` David Emery
@ 1994-10-25 16:43                         ` John Volan
  1994-10-27  4:25                           ` Rob Heyes
  1 sibling, 1 reply; 45+ messages in thread
From: John Volan @ 1994-10-25 16:43 UTC (permalink / raw)


mbk@inls1.ucsd.edu (Matt Kennel) writes:

>Jay Martin (jmartin@baleen.cs.ucla.edu) wrote:

>: Ada9x is too obese and is being too effected by trying to be an
>: "elegant" (rigid) extension of obese Ada83.  I really don't understand
>: why can't some clown spend a few minutes to come up with a cleaner
>: smaller (more minimalist) Ada style language.

>That's what Meyer did, it's called Eiffel.  Really.  Ada83 was a big
>influence.

Eiffel is nice.  I like Eiffel.  But is Eiffel really enough?  Why does
Eiffel need LACE to prop it up, for instance?

>Absent this, the problem here in 9x can be "solved" by a nearly transparent
>change to the language:  say "cyclic dependencies in types, but not
>initialization expressions, are now allowed."  like
>it always should have been, in my opinion.

I dispute that this is a "nearly transparent" change to the language.
Other folks have already pointed out to you that Ada's
order-of-declaration dependencies reflect an underlying assumption
about declarations: They all get *elaborated* at run-time, in a
specific order.  That is, every declaration "takes effect" at a
specific point in time during execution, and this might (or might not,
as the case may be) cause something to occur at run time (such as
initialization).  This rule applies to *all* declarations in Ada,
including variable declarations, type declarations, subprogram
declarations, package declarations, what have you.

Your answer to this seems to be: "Well, let's single out one kind of
declaration -- type declarations -- as a *special case* that totally
violates that general rule, just to make one particular style of
programming easier, or to make Ada more closely resemble somebody
else's pet language.  Go ahead and refer to types that haven't been
declared yet -- even types from other packages that haven't been
*compiled* yet. We don't really care who gets elaborated first ..."

IMHO, that road leads to madness.  If you establish broad language
design principles, but then overrule them for special cases at every
turn, you wind up with a recipe for a bloated, complex, and incoherent
language.  No thank you.  A lot of the additional power in Ada9X over
Ada83 has arisen as a direct result of *broadening* the application of
Ada's original principles, *eliminating* special-case situations, NOT
adding new ones.

>Now you can declare an X which has a component of type/package/class/whatever
>Y, and have Y which has a component of class X.

"Type/package/class/whatever"????  Again, you're conflating all these
things to be the same thing, as if Ada were Eiffel.

>It's not transparent to the compiler implementors, but no fix
>here would be.

Of course.  But I would rather live with "package abstracts" than
"automagically forwarded types."

--------------------------------------------------------------------------------
--  Me : Person := (Name                => "John Volan",
--                  Company             => "Raytheon Missile Systems Division",
--                  E_Mail_Address      => "jgv@swl.msd.ray.com",
--                  Affiliation         => "Enthusiastic member of Team Ada!",
--                  Humorous_Disclaimer => "These opinions are undefined " &
--                                         "by my employer and therefore " &
--                                         "any use of them would be "     &
--                                         "totally erroneous.");
--------------------------------------------------------------------------------





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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-20 11:25               ` Robb Nebbe
  1994-10-20 19:19                 ` John Volan
@ 1994-10-26  0:07                 ` Mark S. Hathaway
  1994-10-26 18:48                 ` gamache
  2 siblings, 0 replies; 45+ messages in thread
From: Mark S. Hathaway @ 1994-10-26  0:07 UTC (permalink / raw)


> In article <1994Oct20.121408@di.epfl.ch>,
> Robb.Nebbe@di.epfl.ch (Robb Nebbe) writes:
 
>|> In article <38289r$79m@oahu.cs.ucla.edu>,
>|>jmartin@oahu.cs.ucla.edu (Jay Martin) writes:

>|> With all these ugly workarounds it looks like we must have a
>|> language extension to Ada to handle mutual dependencies.
>|> Otherwise Ada9x is a "joke".  Of course if there is no way that Ada
>|> will be extended quickly, it will be a "joke" anyway.  Hopefully C++
>|> has taught language designers/standardizers something.
  
> As an analogy consider a wall as representing a programming problem
> and a language as providing a way to get to the other side. What you
> have seen is a lot of "ugly workarounds" to go through the wall.
> I saw at least one suggestion to go over the wall and another to
> go around the wall but both were refused. Why? because the goal
> had ceased being "getting to the other side" but instead had become
> "going through the wall".
> 
> - Robb Nebbe
> 
> P.S. the fact that some langauges provide a tool that will cut a
> hole in the wall and install a door to the otherside may lead
> some to believe that it is a good idea to go through the wall.
> They must first answer the question "Why was the wall there in
> the first place?"

It didn't look to me like a well-defined problem.  For example...

  Was it a free-standing wall or part of a room?

  If one looks around the room, is there an existing door one could use
  to exit the room (reusability)?

  If you want to go through the wall, do you have the tools sufficient
  to get through that type of material(s)?

  Was the wall only a divider inside a room that could be picked-up and
  moved; or simply walked around?

To be so close to the wall and focused on it that you can't look around
to see the rest of the environment is a myopia that could be disastrous.


Mark S. Hathaway      <hathawa2@muvms6.mu.wvnet.edu>



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-25 15:54                       ` John Volan
@ 1994-10-26  1:24                         ` Bob Duff
  1994-10-28  4:28                         ` Jay Martin
  1 sibling, 0 replies; 45+ messages in thread
From: Bob Duff @ 1994-10-26  1:24 UTC (permalink / raw)


In article <1994Oct25.155420.27353@swlvx2.msd.ray.com>,
John Volan <jgv@swl.msd.ray.com> wrote:
>jmartin@baleen.cs.ucla.edu (Jay Martin) writes:
> ...Do you think what the MRT has been doing these
>past few years was *easy*?

Piece o' cake.  :-) :-)

[flames deleted]

Lighten up, folks.

- Bob
-- 
Bob Duff                                bobduff@inmet.com
Oak Tree Software, Inc.
Ada 9X Mapping/Revision Team (Intermetrics, Inc.)



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

* Generic association example (was Re: Mutual Recursion Challenge)
  1994-10-24 20:32                     ` John Volan
@ 1994-10-26 11:42                       ` Robert I. Eachus
  1994-10-26 23:21                         ` John Volan
  0 siblings, 1 reply; 45+ messages in thread
From: Robert I. Eachus @ 1994-10-26 11:42 UTC (permalink / raw)


In article <1994Oct24.203214.4967@swlvx2.msd.ray.com> jgv@swl.msd.ray.com (John Volan) writes:

 > Could you clarify this a bit, and elaborate on how using mixins would
 > work here?  I think I understand what you're driving at, but perhaps
 > other folks won't.  What, precisely, do you mean by the "baggage" that
 > would be there anyway?  Also, how well does the mixin technique really
 > scale up, when you imagine many classes, many associations, and each
 > class participating in many associations?

   >It may seem that creating a dozen abstract types which are only there
   >as placeholders is a problem, but in fact the only problem I have
   >found with it is coming up with names.  (The best strategy I have
   >found is to use the base class name joined with the generic package
   >name as the name of the package instance:

   >    package Persons_Office_Assignment is new Office_Assignment(Person);

   >    and elsewhere:

   >    package Office_Staff_Assignment is new Staff_Assignment(Office);
 > I take it that Persons_Office_Assignment would declare a derived type
 > inheriting from Person, with an extension supporting the association
 > with Office.  Likewise, Office_Staff_Assignment would declare a
 > derived type inheriting from Office, with an extension supporting the
 > association with Person.

Yes and yes.

 > One problem I see with this particular formulation is that a
 > Person-who-can-occupy-an-Office can point to any Office, not
 > necessarily only an Office-that-can-be-occupied; likewise, an
 > Office-that-can-be-occupied can point to any Person, not
 > necessarily only a Person-who-can-occupy-an-Office.

That is what abstract types are for.  In particular, the feature added
last August that abstract types need not have any abstract operations
makes it easy.  All the types that you can point to but shouldn't are
abstract, and since the type determination in a dispacthing operation
comes from the object, the issue doesn't arise.

 > Is there a way of putting this together that guarantees the
 > invariant that if a Person occupies an Office, then that Office is
 > occupied by that Person?

Yes.  It is best understood with the "double generic" version, but
doesn't depend on it.  However, make sure you reserve one-to-one
mappings for where they are appropriate.  Supporting many-to-many
mappings requires a lot more complexity in the Association
abstraction, so there should probably be several--one-to-one and onto,
one-to-many, and many-to-many.  They only need to be written once, so
let's try the simplest case:

(I spent a lot of time barking up the wrong tree on this.  Querying
the attributes is not a problem, but defining an operation to set them
resulted in all sorts of visible kludges or silly looking code.  There
are two facets to the solution.  The first is that in the one-to-one
case there are two necessary set operations: un-set and set, not set
for office and set for person.  The second is that, while the query
functions want to be class-wide in one parameter, these should be
symmetric, and thus class-wide in both.)

    generic
      type Father is abstract tagged private;
       -- probably all the abstract types should be limited too.
      type Target_Ancestor is abstract tagged private;
      -- ancester of the destination type, for example, Controlled.
    package Association is

      type Extended is abstract new Father with private;

      function Get(E: in Extended) return Target_Ancestor'CLASS;
      -- If you follow the above directions about abstraction, this
      -- must always return the "right" type.  But if you have several
      -- non-abstract types which are specializations of say Person,
      -- you want the attribute declared this way anyway.  Raises
      -- Constraint_Error if the attribute is not set. 

      function Is_Set(E: in Extended) return Boolean;
      -- Inquiry function to avoid Constraint_Error.

      generic
        type Mother is abstract tagged private;
      package Inner_Association is
         
        type Inner_Extended is new Mother with private;

        function Get(E: in Inner_Extended) return Extended'CLASS;
        -- Again we want the 'CLASS even in cases where it may not be
        -- necessary to complete the code...

        function Is_Set(E: in Extended) return Boolean;
        -- Inquiry function to avoid Constraint_Error as above.

        procedure Safe_Set (E:   in out Extended'CLASS;
                            IE:  in out Inner_Extended'CLASS);

        procedure Force_Set(E:   in out Extended'CLASS;
                            IE:  in out Inner_Extended'CLASS);

        -- There are two choices here, set in any case, but preserve
        -- the invariants, or raise an exception and change nothing if
        -- one or the other is already set.  Since it is simple to
        -- provide both, I do so.  (Safe_Set does the checks and may
        -- raise an exception, Force_Set unsets the partner of any
        -- object that is being reassigned.)

        procedure UnSet(E: in out Extended'CLASS);
        procedure UnSet(IE: in out Extended'CLASS);
        -- UnSet the attribute.  If already set, unset the partner as well.

      private

        type Outer_Ref is access all Extended;

        type Inner_Extended is new Mother with record
          Attribute: Outer_Ref;
        end record;

      end Inner_Association;

      pragma INLINE(Get, Is_Set, Safe_Set, Force_Set);

    private

      type Inner_Ref is access all Target_Ancestor;

      type Extended is new Father with record
        Attribute: Inner_Ref;
      end record;

      pragma INLINE(Get, Is_Set);

    end Association;

    -- generic
    -- type Father is abstract tagged private;
    -- type Target_Ancestor is abstract tagged private;
    package body Association is

    -- type Extended is new Father with record
    --       Attribute: Inner_Ref; end record;

      function Get(E: in Extended) return Target_Ancestor'CLASS is
      begin return E.Attribute.all; end Get;

      function Is_Set(E: in Extended) return Boolean is
      begin return E.Attribute = null; end Is_Set;

      -- generic
      -- type Mother is abstract tagged private;
      package Inner_Association is
         
        -- type Inner_Extended is new Mother with record
        -- Attribute: Outer_Ref; end record;

        function Get(E: in Inner_Extended) return Extended'CLASS is
        begin return E.Attribute.all; end Get;

        function Is_Set(E: in Extended) return Boolean is
        begin return E.Attribute = null; end Is_Set;

        procedure Safe_Set (E:   in out Extended'CLASS;
                            IE:  in out Inner_Extended'CLASS) is
        begin
          if Is_Set(E) or Is_Set(IE)
          then raise Constraint_Error;
          else
          end if;
        end Safe_Set;

        procedure Force_Set(E:   in out Extended'CLASS;
                            IE:  in out Inner_Extended'CLASS) is
        begin
          if Is_Set(E) then UnSet(E); end if;
          if Is_Set(IE) then UnSet(IE); end if;
          E.Attribute := IE'Access;
          IE.Attribute := E'Access;
        end Force_Set;

        procedure UnSet(E: in out Extended'CLASS) is
        begin
          if E.Attribute /= null
          then
             E.Attribute.Attribute := null;
             E.Attribute := null;
          end if;
        end UnSet;

        procedure UnSet(IE: in out Extended'CLASS) is
        begin
          if IE.Attribute /= null
          then
             IE.Attribute.Attribute := null;
             IE.Attribute := null;
          end if;
        end UnSet;

      end Inner_Association;

    end Association;

    (If anyone can compile this successfully, please let me know.
There is a bug in GNAT 1.83 that is supposed to be fixed in 1.84 that
the spec runs into.)

      Okay, now using this package goes like this...

      with Ada.Finalization; with Assignments;
      package People is

	type Base_Person is abstract 
             new Ada.Finalization.Controlled with private;

        package Office_Assignments is 
                   new Assignments(Base_Person,Ada.Finalization.Controlled);
      
        type Person is new Office_Assignments.Extended with null;

        function Office(P: in Person) return Controlled'CLASS renames Get;
        function Has_Office(P: in Person) return Boolean renames Is_Set;

      private
        ...
      end People;
                 
      with Ada.Finalization; with People;
      package Offices is
	type Office_Base is abstract new Ada.Finalization.Controlled
                 with private;
        package People_Assignments is new
          People.Office_Assignments.Inner_Association(Office_Base);
        
        type Office is new People_Assignments.Inner_Extended with null;
        function Occupant(O: in Office) return
              People.Office_Assignments.Extended'CLASS renames Get;
        function Is_Occupied(O: in Office) return Boolean renames Is_Set;
        procedure Reassign(P: in out People.Office_Assignments.Extended'CLASS;
                           O: in out People_Assignments.Inner_Extended'CLASS);
        ...

      private
        ...
      end Offices;

  > If I'm totally mixed-up about mixins :-), please help me out.  Thanks.

    I hope this helps.  The trick is to get as much of the "plumbing"
code into generics which are written once, and then use appropriate
renamings to make it understandable.  (In fact, in the code above I
probably would use subtype definitions to make those ugly 'CLASS
parameters go away.  The other possible approach is to replace the
renamings with operations on the parent types which do the ugly calls
in the body.  It's a matter of style and in this case, I'm trying to
show the workings...)
--

					Robert I. Eachus

with Standard_Disclaimer;
use  Standard_Disclaimer;
function Message (Text: in Clever_Ideas) return Better_Ideas is...



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-20 11:25               ` Robb Nebbe
  1994-10-20 19:19                 ` John Volan
  1994-10-26  0:07                 ` Mark S. Hathaway
@ 1994-10-26 18:48                 ` gamache
  1994-10-27  2:15                   ` John Volan
  2 siblings, 1 reply; 45+ messages in thread
From: gamache @ 1994-10-26 18:48 UTC (permalink / raw)


In article <1994Oct20.121408@di.epfl.ch>, Robb.Nebbe@di.epfl.ch (Robb Nebbe) writes:
> 
> As an analogy consider a wall as representing a programming problem
> and a language as providing a way to get to the other side. What you
> have seen is a lot of "ugly workarounds" to go through the wall.
> I saw at least one suggestion to go over the wall and another to
> go around the wall but both were refused. Why? because the goal
> had ceased being "getting to the other side" but instead had become
> "going through the wall".
> 
> - Robb Nebbe
> 

I've been reading this thread for awhile now and have finally organized my
thoughts enough to respond.  I chose to reply to the above to further amplify
and clarify the issues on "Decoupled Mutual Recursion".  It is not my intent to
put words in Mr. Nebbe's mouth (err, should I say Newsreader?) and if I have
mistaken his post, I apologize, most of the material here is reasonably
standalone.  However, looking at the various solutions posted I had an almost
intrinistic dislike to the generics approach, but found the solutions "to go
over the wall and another to go around the wall" acceptable.

What is "Decoupled Mutual Recursion"?
-------------------------------------

While I have experience with coupling, I had not previously heard of this term.
Thinking about it, I ask the net the above question.  Is this a real term in
general usage?  If so, I suggest abandoning it in favor of a more descriptive
term.  What type of coupling is being "decoupled" anyway?  To use diagrams
consistent with this thread, two classes my be seen to be coupled by
relationship R1 as shown below:

          +----+          R1           +----+
          | C1 |-----------------------| C2 |
          +----+                       +----+
These classes are coupled.  To me, decoupling would look like:
          +----+                       +----+
          | C1 |                       | C2 |
          +----+                       +----+
Yet, that is not what is being proposed, so I think the use of decoupled causes
more harm than good.  Further, to accomplish useful work, coupling is generally
acknowledged to be required.  One of the classical examples used is that of the
wires connecting the speakers to the receiver/amplifier of a stereo system.  If
they are "decoupled" (again, to me this is synonomous with the word I have seen
more often in the literature, uncoupled) then no sound will result and the
system will not accomplish useful work.  How can the speakers be coupled to rest
of the system?  They can be 'hardwired' (as in soldered to the speaker terminals
and the wire running out the back of the speaker) which would be a form of high
or tight coupling.  Or they can be made to be easily disconnected/reconnected as
with RCA-type jacks, or screw mounts.  This would be a lower form of coupling.
Thus, the notion of coupling as SCALE is born:

 low                             medium                                high
   +--------------------------------------------------------------------+
   |                         Coupling Scale                             |
   +--------------------------------------------------------------------+
   data          stamp            control          common            content

In software engineering, it has become widely accepted that low coupling (such
as data coupling) is good, whereas high coupling (such as content coupling) is
bad.  If "decoupled mutual recursion" is moving on this scale, from where to
where?  I couldn't make this out from the proposed solution.  In fact, this
reasoning solidifies my initial opposition to it.  To see why, let me review the
definition of one of the types of coupling listed above.  This definition is
from Page-Jones, but similar definitions are available from a variety of
authors, sometimes the name of the specific type of coupling is different, but
the end result is almost the same.

	Two modules exhibit content (or pathological) coupling if
	one refers to the inside of the other in any way; for
	instance,... if one module refers to (or changes) data
	within another.... Such coupling makes nonsense of the
	concept of black-box modules....

Now I'm not saying that the above was the *intent* of the proposed solution;
however, if I evaluate the type of coupling that the proposed solution
*implements* (on the basis of xyz_Identity.Value being System.Address *and* the
very existance of To_Pointer operation), I am forced to conclude that many
modules *MAY* modify the data of one another ==> content coupling.

A Solution
----------

Okay, if any is even still reading, I have some thoughts regarding what I
believe to be a low-coupled solution to this problem.  Using the following
approach, the entire issue of 'recursion' with 'one of its own subclasses' is a
non-issue.  The solution is the same whether or not the relations are between
Office--houses--employee or Manager--supervises--employee.  I'd like to lay
complete and total claim to the following solution, however, it has been widely
recognized and published by various authors (which is certainly how I learned
about it :).  As I read the problem statement, my determination is that the
primary issue is really one of entity analysis.  That is, which relationships
need to be traversable in a single direction and which need to be
bi-directional?  In this case, Manager_Supervises_Employee and
Employee_Is_Supervised_By_Manager can be assumed to have been determined to be
of need.  Shlear/Mellor describe this process as the creation of a "Reduced
Information Model", while Yourdon in "Modern Structured Analysis" (Chap 12 for
anyone reading along at home...) describes the process as follows:

        After the first-cut ERD has been developed, the next step
        that you should carry out is that of attributing the data
        element in the system to the various object types.... The
        attribution process may provide one of three reasons for
        creating new object types:
           1. You may discover data elements that can be attributed
              to some instances of an object, but not to others.
           2. You may discover some data elements that are applicable
              to all instances of two different objects.
           3. You may discover that some data elements describe
              relationships between other object types.

Using the above, if I had:

+--------+   Supervises +----------+
| Mgr    |--------------| Employee |
+--------+              +----------+

I would have by rule 2 above the need to create another object class.  These
objects are known as Associative Objects.  Shlear/Mellor define as "an
associative object arises when there is supplementary information associated
with instance of a relationship".  Yourdon states that associative objects
"represent something that functions both as an object and a relationship".
Given this the picture that *should* be offered for implementation is:

+--------+              +----------+
| Mgr    |--------------| Employee |
+--------+      |       +----------+
                |
                |
         +-------------+
         | Supervises  |
         +-------------+

This notation easily scales to problems of the dimension alluded to in earlier
posts.  I can attest to their success on large/complex projects involving Ada.
We have been using these techniques since the mid-80's.  By the way, I should
have stated this more clearly at the outset, the reason I didn't like the
proposed solution was that we had tried such approaches with Ada83 and found out
first-hand the inherent integration problems (i.e. been there, done that).
However, we are just starting any type of effort with 9X.  Which leads me to the
long awaited conclusion.  The above ERD is easily implementable (even in Ada83)
in a variety of acceptable ways, all of which house shared relationship data in
a standalone, no hashing tables required, low-coupled package.  (Interested
readers are referred to Shlear/Mellors first book for implementation strategies
concerning 1-1, 1-m, or m-m relationships of this type)

Summary
-------

(Maybe I should have put this at the beginning?) Anyway, I felt:

o the proposed approach is an attempt to package content-coupling as a
  feature rather than a liability.
o the problem statement is not new or rare, nor does it have much to do
  with subclasses, rather it is a problem concerning associative objects.
o existing techniques are available and in place for dealing with
  associative object implementations in a low-coupled fashion.

While its certainly possible I've been misreading this thread, to get 
realigned I would need identification of what type of coupling one is 
"decoupling" and what type one is ending up with.

-----------------------------------------------------------------------------
with the_usual_i_dont_speak_for_my_employer_disclaimer;



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

* Re: Generic association example (was Re: Mutual Recursion Challenge)
  1994-10-26 11:42                       ` Generic association example (was Re: Mutual Recursion Challenge) Robert I. Eachus
@ 1994-10-26 23:21                         ` John Volan
  1994-10-27 10:53                           ` Robert I. Eachus
  1994-10-27 14:37                           ` Mark A Biggar
  0 siblings, 2 replies; 45+ messages in thread
From: John Volan @ 1994-10-26 23:21 UTC (permalink / raw)


eachus@spectre.mitre.org (Robert I. Eachus) writes:

>In article <1994Oct24.203214.4967@swlvx2.msd.ray.com> jgv@swl.msd.ray.com (John Volan) writes:

> > One problem I see with this particular formulation is that a
> > Person-who-can-occupy-an-Office can point to any Office, not
> > necessarily only an Office-that-can-be-occupied; likewise, an
> > Office-that-can-be-occupied can point to any Person, not
> > necessarily only a Person-who-can-occupy-an-Office.

>That is what abstract types are for.  In particular, the feature added
>last August that abstract types need not have any abstract operations
>makes it easy.  All the types that you can point to but shouldn't are
>abstract, and since the type determination in a dispacthing operation
>comes from the object, the issue doesn't arise.

Hmmm... Yes, I can see that this guarantees that the only objects that
would exist at run-time would be "Persons-who-can-occupy-Offices" and
"Offices-that-can-be-occupied-by-Persons", and not just "Persons" and
"Offices".  Or, more to the point, they could only be "Total Persons"
and "Total Offices", supporting all the associations that pertain to
"Persons" and "Offices" within the given application.  And the
objects themselves would "know" what concrete type they were, by
virtue of their tags.

But I still see a problem: It looks like each class is giving up the
ability to use static strong typing to assert the exact type of the
*other* objects associated with it.  In other words, a "Person-who-
can-occupy-an-Office" can't assert that it's associated with an
"Office-that-can-be-occupied-by-a-Person" (or with a "Total Office",
for that matter).  All it can say is that it's associated with an
"Office".  So when a client asks a Person object for its Office, the
Person can answer with its associated "Office", but it can't provide
the client with a "Total" view of that Office.  The client would have
to do the view-conversion itself by "narrowing" (safely downcasting)
that Office into a "Total Office".

That narrowing operation would incur a run-time check on the Office's
tag.  But that check is actually redundant.  You know and I know that
the Office object will really be a "Total Office"; we can assert that
as a statically-determined fact, since we're the designers of the
software, and that was our original intent for the association.
However, when we go to write our Ada code for the Person class, we
discover that we can't explicitly assert, in the Ada code itself, that
a Person's associated Office will actually be one of those "Total
Offices".  So we can't tell the compiler that this is a
statically-determined assertion that it can check statically.
Instead, it becomes a dynamically-checked assertion.  In short, this
takes us a step away from a statically-checked style of programming,
and moves us closer to the dynamically-checked style of languages such
as Smalltalk.

I suppose we could apply a pragma Suppress at some point to eliminate
the extra dynamic check, once the program was fully tested.  But, more
to the point, we've lost a certain amount of expressibility.  Since
the Ada code doesn't directly express what we mean, its readability by
other Ada programmers (for example, maintainers) is reduced.  

Moreover, I must insist once again that all these extra layers of
abstract types don't really represent anything from the problem
domain.  As far as our object-oriented analysis is concerned, a Person
is just a Person, and an Office is just an Office.  Part of what it
means to be a Person is the ability to occupy an Office, and likewise,
part of being an Office is the ability to accomodate Person (at least
within the application in question).  All those abstract types layered
on top of this are really just artifacts of the way we've chosen to
construct the software that will implement our analysis.  Perhaps we
can exploit all these layered views to gain some reusability benefits,
but the costs that they incur are very clear: The job of reading and
understanding the program has been complicated by the proliferation of
multiple views for what, in the problem domain, are just single
classes.

You mentioned that you found it difficult to come up with *names* for
those multiple views.  I've had trouble with that too, as you can see
from the way I had to resort to awkward phrases such as
"Person-who-can-occupy-an-Office".  Far from being a minor
inconvenience, I really think this is a diagnostic symptom of a very
serious problem.  What cannot be easily named, cannot be easily
explained, and therefore cannot be easily understood.

> > Is there a way of putting this together that guarantees the
> > invariant that if a Person occupies an Office, then that Office is
> > occupied by that Person?

>Yes.  It is best understood with the "double generic" version, but
>doesn't depend on it.  However, make sure you reserve one-to-one
>mappings for where they are appropriate.  Supporting many-to-many
>mappings requires a lot more complexity in the Association
>abstraction, so there should probably be several--one-to-one and onto,
>one-to-many, and many-to-many.  They only need to be written once, so
>let's try the simplest case:

>(I spent a lot of time barking up the wrong tree on this.  Querying
>the attributes is not a problem, but defining an operation to set them
>resulted in all sorts of visible kludges or silly looking code.  There
>are two facets to the solution.  The first is that in the one-to-one
>case there are two necessary set operations: un-set and set, not set
>for office and set for person.  

Yes, I encountered the same issue: I had to have a "Dissociate"
operation as well as an "Associate" operation, and the latter wound up
calling the former when the cardinality of the association was "one"
(but not when it was "many").

>The second is that, while the query
>functions want to be class-wide in one parameter, [the Set procedures] 
>should be
>symmetric, and thus class-wide in both.)

That's if you're interpreting "Set" and "Unset" (or "Associate" and
"Dissociate") as "friend" operations.  In other words, you're not
considering them as "belonging" to either class specifically, but
rather they're sort of straddling the association between the classes.

But that's not the only way you could arrange things.  If you noticed,
in my previous posts, I actually conceived of *distributing* this
"Setting" responsibility to *both* of the classes.  In other words, I
imagined having *two* "Associate" operations: one that was primitive
for an Employee and one that was primitive for an Office.  The
Associate for Employee would only directly modify the Employee's
pointer to its Office; likewise the Associate for Office would only
directly modify the Office's pointer to its Employee.  That follows
the "Law of Demeter": an object's operations should only directly
manipulate its own attributes, but not the attributes of any other
object.

However, both of these Associate operations would also be responsible
for satisfying the invariant of the association: i.e, if an Employee
points to an Office, then that Office must point back to that Employee
as well.  The most convenient way for the two Associate operations to
do that would be ...  to call each other!  In other words, they would
be *mutually recursive* subprograms, reflecting the *mutually
recursive* relationship between the two classes.

Consequently, we could use either one of those Associate subprograms
to establish a link between a given Employee and a given Office.
Which one we would pick at any given point would be arbitrary, and
would probably depend on which of the two classes we were focusing on
in the course of some larger algorithm.

The upside to this scheme is that we didn't have to resort to breaking
object-oriented encapsulation in order to implement this capability.
In other words, we didn't have to make this a "friend" operation that
can "see" the structure of both types at once.  The downside, though,
is that now we have to look at two subprograms, distributed in two
packages, to fully understand how the "functionality" of "setting up
an association" will get done.  But I don't think that's really so
bad.  As I've said before, it's going to be a very common thing for
"functionality" to be smeared across multiple object classes, whenever
you make the objects, rather than the functions, the central criterion
of your software design.

>    generic
>      type Father is abstract tagged private;
>       -- probably all the abstract types should be limited too.
>      type Target_Ancestor is abstract tagged private;
>      -- ancester of the destination type, for example, Controlled.
>    package Association is

>      type Extended is abstract new Father with private;

>      function Get(E: in Extended) return Target_Ancestor'CLASS;
                                           ^^^^^^^^^^^^^^^
You see, that's what I mean -- you've lost the ability to express the
exact type of the other object in a static fashion, even though you,
as the designer, do know what that exact class should be, a priori.

>      -- If you follow the above directions about abstraction, this
>      -- must always return the "right" type.  But if you have several
>      -- non-abstract types which are specializations of say Person,
>      -- you want the attribute declared this way anyway.  

Yes, I have no trouble with this returning a class-wide type, I just
have trouble with the root-type of the class being so indistinct.  I'd
rather be able to say something like "Internal_Extended'Class" here.
But that's the chicken-and-egg problem again.

>      -- Raises
>      -- Constraint_Error if the attribute is not set. 

Interesting interpretation.  I didn't think there was any trouble with
returning "null".  Clients could just interpret a "null" value as
meaning that E isn't associated with any Target.  But that's okay --
you just have a slightly different abstraction in mind than I have.

>      function Is_Set(E: in Extended) return Boolean;
>      -- Inquiry function to avoid Constraint_Error.

This might be supplied anyway as a convenience, even if you go with
my interpretation of allowing Get to return null.

>      generic
>        type Mother is abstract tagged private;
>      package Inner_Association is
>         
>        type Inner_Extended is new Mother with private;

>        function Get(E: in Inner_Extended) return Extended'CLASS;
>        -- Again we want the 'CLASS even in cases where it may not be
>        -- necessary to complete the code...

>        function Is_Set(E: in Extended) return Boolean;
>        -- Inquiry function to avoid Constraint_Error as above.

>        procedure Safe_Set (E:   in out Extended'CLASS;
>                            IE:  in out Inner_Extended'CLASS);

>        procedure Force_Set(E:   in out Extended'CLASS;
>                            IE:  in out Inner_Extended'CLASS);

>        -- There are two choices here, set in any case, but preserve
>        -- the invariants, or raise an exception and change nothing if
>        -- one or the other is already set.  Since it is simple to
>        -- provide both, I do so.  (Safe_Set does the checks and may
>        -- raise an exception, Force_Set unsets the partner of any
>        -- object that is being reassigned.)

Interesting.  I hadn't thought of providing these alternatives.  My
Associate subprograms correspond to your Force_Set.

>        procedure UnSet(E: in out Extended'CLASS);
>        procedure UnSet(IE: in out Extended'CLASS);
>        -- UnSet the attribute.  If already set, unset the partner as well.

By the way, in the case of "many"-cardinality, I think UnSet would
actually wind up being a single operation with two parameters.

>      private

>        type Outer_Ref is access all Extended;

>        type Inner_Extended is new Mother with record
>          Attribute: Outer_Ref;
>        end record;

>      end Inner_Association;

>      pragma INLINE(Get, Is_Set, Safe_Set, Force_Set);

>    private

>      type Inner_Ref is access all Target_Ancestor;

>      type Extended is new Father with record
>        Attribute: Inner_Ref;
>      end record;

>      pragma INLINE(Get, Is_Set);

>    end Association;


[snip implementation of generic package body]


>      Okay, now using this package goes like this...

>      with Ada.Finalization; with Assignments;
>      package People is

>	type Base_Person is abstract 
>             new Ada.Finalization.Controlled with private;

>        package Office_Assignments is 
>                   new Assignments(Base_Person,Ada.Finalization.Controlled);
                                                ^^^^^^^^^^^^^^^^^^^^^^^^^^^ 

Once again, it looks like we've lost some expressibility here: At this
point, we can't say anything more about what kind of objects People
are going to be associated with, other than that they're going to be
something derived from Ada.Finalization.Controlled.  But you and I
know that these are Offices.

>      
>        type Person is new Office_Assignments.Extended with null;

>        function Office(P: in Person) return Controlled'CLASS renames Get;
>        function Has_Office(P: in Person) return Boolean renames Is_Set;

>      private
>        ...
>      end People;
>                 
>      with Ada.Finalization; with People;
>      package Offices is
>	type Office_Base is abstract new Ada.Finalization.Controlled
>                 with private;
>        package People_Assignments is new
>          People.Office_Assignments.Inner_Association(Office_Base);
>        
>        type Office is new People_Assignments.Inner_Extended with null;
>        function Occupant(O: in Office) return
>              People.Office_Assignments.Extended'CLASS renames Get;
>        function Is_Occupied(O: in Office) return Boolean renames Is_Set;
>        procedure Reassign(P: in out People.Office_Assignments.Extended'CLASS;
>                           O: in out People_Assignments.Inner_Extended'CLASS);
>        ...

>      private
>        ...
>      end Offices;

>  > If I'm totally mixed-up about mixins :-), please help me out.  Thanks.

>    I hope this helps.  The trick is to get as much of the "plumbing"
>code into generics which are written once, and then use appropriate
>renamings to make it understandable.  

I fully agree with this sentiment in principle, but not necessarily
with the way you've put it into practice here.  For example, those
mutually-recursive Associate procedures I described above do follow a
common pattern that can apply to any association.  That makes them an
excellent candidate for a generic solution, and I think I've come up
with one.  However, it only takes care of *implementing* the Associate
operations.  You still have to write the spec for an Associate
procedure in each of your class packages.  But when you get to the
package bodies, you don't have to worry about doing the "plumbing."
You can instantiate the template in terms of those procedure specs,
and then, via renaming declarations, you can use the resulting
instance procedures as the *bodies* for those specs!  Granted, it
doesn't take care of all the "boilerplating" that you need to support
an association; I think perhaps some code-generating tool might be
better suited to doing that, and this generic could could work along
with that tool. But using renaming declarations as subprogram bodies
is a neat trick that Ada9X now makes possible.

>(In fact, in the code above I
>probably would use subtype definitions to make those ugly 'CLASS
>parameters go away.  The other possible approach is to replace the
>renamings with operations on the parent types which do the ugly calls
>in the body.  It's a matter of style and in this case, I'm trying to
>show the workings...)
>--

>					Robert I. Eachus

>with Standard_Disclaimer;
>use  Standard_Disclaimer;
>function Message (Text: in Clever_Ideas) return Better_Ideas is...


-- John Volan

--------------------------------------------------------------------------------
--  Me : Person := (Name                => "John Volan",
--                  Company             => "Raytheon Missile Systems Division",
--                  E_Mail_Address      => "jgv@swl.msd.ray.com",
--                  Affiliation         => "Enthusiastic member of Team Ada!",
--                  Humorous_Disclaimer => "These opinions are undefined " &
--                                         "by my employer and therefore " &
--                                         "any use of them would be "     &
--                                         "totally erroneous.");
--------------------------------------------------------------------------------



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-26 18:48                 ` gamache
@ 1994-10-27  2:15                   ` John Volan
  0 siblings, 0 replies; 45+ messages in thread
From: John Volan @ 1994-10-27  2:15 UTC (permalink / raw)


gamache@rapnet.sanders.lockheed.com writes:

[Objections to the use of the term "Decoupled" in this thread.]

I fully agree, my use of the term "decoupled" was unfortunate.  In a binary
association, the two classes are indeed coupled, one way or another, and
I really wasn't trying suggest that we can eliminate that coupling.

On better reflection, I think I should have used a term more like
"Separately-Encapsulated Mutual Recursion".  The challenge I was 
proposing was how one could achieve the coupling necessary for
a mutually-recursive association while still being able to encapsulate
each class in its own separate package.  

Some folks have insisted that the "cleanest" way to achieve the
necessary coupling is to give up on separate encapsulation; both types
"must" be encapsulated in the same package.  The problem I saw with
this was that the effect would be transitive: Every time some other
class had to be associated, it would wind up being dumped into the
same package.  In the extreme case, *all* the classes in a large
semantic network would wind up inside of one, huge, monolithic
package.  This, I think, would defeat the whole purpose of packages
as a way of modularizing software designs.

"Gamache" (I'm sorry, you didn't sign your post, so I don't know your
full name) points out that there are various degrees of coupling, and
that, in particular, "content" coupling is the worst:

>In software engineering, it has become widely accepted that low coupling (such
>as data coupling) is good, whereas high coupling (such as content coupling) is
>bad.  If "decoupled mutual recursion" is moving on this scale, from where to
>where?  I couldn't make this out from the proposed solution.  In fact, this
>reasoning solidifies my initial opposition to it.  To see why, let me review the
>definition of one of the types of coupling listed above.  This definition is
>from Page-Jones, but similar definitions are available from a variety of
>authors, sometimes the name of the specific type of coupling is different, but
>the end result is almost the same.

>	Two modules exhibit content (or pathological) coupling if
>	one refers to the inside of the other in any way; for
>	instance,... if one module refers to (or changes) data
>	within another.... Such coupling makes nonsense of the
>	concept of black-box modules....

>Now I'm not saying that the above was the *intent* of the proposed solution;

Ironically enough, I think my original intent was to find a way to
*avoid* "content coupling."  If we're forced to declare two types
within the same package simply because they're associated to each
other, then the operations for either of the types would be able to
directly access the internal structure of the other type.  With
respect to each other, the two types would cease to be "black boxes".
No, I would rather see the two types encapsulated as private types in
separate packages, with no *direct* access to each other's structures.

>however, if I evaluate the type of coupling that the proposed solution
>*implements* (on the basis of xyz_Identity.Value being System.Address *and* the
>very existance of To_Pointer operation), I am forced to conclude that many
>modules *MAY* modify the data of one another ==> content coupling.

No, no! You're misinterpreting what my generic solution is doing! Each
"Xyz_Identity.Value" type is only going to be allowed *one* Pointer type
that it can be translated into.  I agree, if "Xyz_Identity.Translation"
could be instantiated more than once, then we'd break type safety and
general insanity would ensue.  But note that each Xyz_Identity package
has a guard that causes Program_Error to be raised if its Translation
sub-package is instantiated more than once.  Properly speaking, only
the package that actually implements the "Xyz" class should do an
instantiation of "Xyz_Identity.Translation", and only for its "Xyz.Pointer"
type.

Don't be confused by the use of System.Address as one of the possible
*implementations* of Identity.Value.  There are many reasons why
System.Address is a poor choice, but they have more to do with
portability, not type safety.  In fact, it's precisely because
Identity.Value *is* a "black box" that System.Address could be even a
half-way reasonable implementation for it.  There are better ways to
implement Identity.Value, but regardless of how it's done, it is still
going to be a "black box."  Remember, only valid Xyz.Pointers can go into
an Xyz_Identity.Value, and only valid Xyz.Pointers can come out.

I think the best way to understand what my Identity package does is to
focus on the term I used when I first introduced this solution:
"Deferred Coupling".  The Identity package makes it possible for the
inevitable coupling between two mutually-recursive classes to be
*deferred*, so that we can get on with establishing their interfaces
(package specs).  This is achieved by allowing an Xyz_Identity.Value
type to act as an "opaque forward declaration" for some Xyz.Pointer
type -- if you will, a "surrogate" that can stand in the place of that
Xyz.Pointer type, even at a point in time before it's possible to
declare the Xyz.Pointer type.  Eventually, we will establish the
coupling between Xyz_Identity.Value and Xyz.Pointer (by instantiating
Xyz_Identity.Translation), but, at least for a while, that coupling
can be *deferred.*

Also, don't be confused by the fact that two classes like Employee and
Office would contain pointers to each other (whether those pointers
are hidden in opaque identity values or not).  Yes, these pointers
mean that the two classes are coupled -- that's inevitable, and it's
the whole point to mutual recursion.  But it does *not* necessarily
mean that they are *content* coupled. If the pointer's designated type
(e.g.  Xyz.Object) is private, then there is no way that you can use
that pointer to *directly* manipulate the structure of the designated
object.  As you would expect, you have to go through the public
subprograms from the package spec where that designated private type
was originally declared.


>A Solution
>----------

["Gamache" goes on to suggest off-loading responsibility for the
association to another class of object that would represent the
association itself.]

Yes, several people have already suggested this solution.  I have
absolutely no trouble with this kind of scheme, and I fully accept the
fact that it is quite appropriate for some applications.  However,
that scheme is based on the premise that the associated classes do not
need to "know" about the association -- i.e., they do not need to 
bear any direct responsibility for the association.  Well, as long
as that premise holds, then it's okay.

Having said that, I still insist that there may be some applications,
or perhaps some styles of design, where it is not appropriate to make
that assumption.  Throughout this thread, I have taken it as a premise
that the two classes in an association would know about their
association and would share responsibility for it.  Essentially, I've
been asking the participants in this newsgroup to simply accept that
as an assumption for the sake of argument, and to see where that
assumption would lead.  Some people have vehemently refuse to do so,
even for the sake of argument.  Well, I can't force people to explore
ideas that they don't want to explore.  Nevertheless, I will be the
first to thank those folks for opening up my own mind to other
possibilities, even if those alternatives are based on different
assumptions.

["Gamache" also points out that Entity/Relationship analysis (such
as that of Shlaer/Mellor) may discover data attributes that pertain
not to either of the classes in an association, but actually to the
association itself.  This even more strongly suggests that the
association should be a class of objects itself.]

I wholeheartedly agree with this, but I don't think it changes the
nature of the problem.  Indeed, I think any such situation simply
brings up the same issues.  If, during analysis, a proposed
"association" becomes a class of object instead, then it is
conceivable that this new object class could end up in
mutually-recursive relationships with the two other classes.

Let me illustrate with an example:  Suppose you were considering
this association:

  +-------+                                            +-------+
  |       |     Is_Now_Or_Has_Ever_Beem_Married_To     |       |
  |  MAN  |(0..many)--------------------------(0..many)| WOMAN |
  |       |                                            |       |
  +-------+                                            +-------+

If we were to implement a mutually-recursive design to meet this
analysis, all we would have to do would be to endow the Man class
with a set of pointers to Woman objects, and vice versa.  However,
on further consideration, we might revise our analysis to allow
the association itself to have attributes, by making it a class
of its own:

  +-------+               +------------+               +-------+
  |       |               |            |               |       |
  |  MAN  |------(0..many)|  MARRIAGE  |(0..many)------| WOMAN |
  |       |               +------------+               |       |
  +-------+               | Start:Date |               +-------+
                          | End:Date   |
                          | ... etc... |
                          +------------+

Each Marriage object represents the particular association of one Man
and one Woman for some given period of time.  But now we effectively
have two associations between three classes of object.  My mutual
recursion question can still apply to this, as long as you accept my
basic premise.  We could distribute the responsibility for the
associations Man--has partaken of--Marriage and Woman--has partaken
of--Marriage to the classes involved.  Each Marriage object could hold
a pointer to a Man object and a Woman object, but each Man object and
each Woman object also could hold a set of pointers to Marriages.


>Summary
>-------

>(Maybe I should have put this at the beginning?) Anyway, I felt:

>o the proposed approach is an attempt to package content-coupling as a
>  feature rather than a liability.

Not true.  Indeed, the exact opposite is true, as I have argued.

>o the problem statement is not new or rare, nor does it have much to do
>  with subclasses, rather it is a problem concerning associative objects.

I fully agree, as long as you allow the possibility of substituting the
phrase "associations between objects" for the phrase "associative objects."
I concur that there should not be any need to resort to abstract classes
and inheritance just to achieve "separate encapsulation".

>o existing techniques are available and in place for dealing with
>  associative object implementations in a low-coupled fashion.

Fully agree -- but this is only one possible style of design.  Your
experience may have encouraged you that this is the best style for the
kind of applications you have tackled, but please do not assume that
it's perfect for all applications.  As evidence, please consider the
fact that "Separately Encapsulated Mutual Recursion" is effectively
supported by other languages, including C++ and Eiffel.  I think it
would be a good idea if Ada9X could support it as well, in some
reasonable way.

>While its certainly possible I've been misreading this thread, to get 
>realigned I would need identification of what type of coupling one is 
>"decoupling" and what type one is ending up with.

If anything, I think my challenge (and my solution to it) attempted to
promote the best possible form of coupling ("data" coupling?) and to
discourage the worst form, by preserving the separate encapsulation
of classes.

--------------------------------------------------------------------------------
--  Me : Person := (Name                => "John Volan",
--                  Company             => "Raytheon Missile Systems Division",
--                  E_Mail_Address      => "jgv@swl.msd.ray.com",
--                  Affiliation         => "Enthusiastic member of Team Ada!",
--                  Humorous_Disclaimer => "These opinions are undefined " &
--                                         "by my employer and therefore " &
--                                         "any use of them would be "     &
--                                         "totally erroneous.");
--------------------------------------------------------------------------------




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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-25 16:43                         ` John Volan
@ 1994-10-27  4:25                           ` Rob Heyes
  1994-10-28  9:03                             ` Mutual Recursion (was Re: SOLVED! Decoupled Mutual Recursion Challenger) Robert I. Eachus
  1994-10-28 15:04                             ` SOLVED! Decoupled Mutual Recursion Challenger Robb Nebbe
  0 siblings, 2 replies; 45+ messages in thread
From: Rob Heyes @ 1994-10-27  4:25 UTC (permalink / raw)


In article <1994Oct25.164314.28453@swlvx2.msd.ray.com> jgv@swl.msd.ray.com (John Volan) writes:
> Eiffel is nice.  I like Eiffel.  But is Eiffel really enough?  Why does
> Eiffel need LACE to prop it up, for instance?

LACE is used to build systems out of classes and to resolve naming conflicts.
This is not a language level feature.  IMHO it is a rather elegant solution
to the problem.  Are you telling me that you build systems in Ada *entirely*
in Ada - how do you go about setting up special versions of a system that
contain debugging code?  If you tell me that it's a compiler switch or that
it's in the makefile (I hope Ada doesn't use makefiles), or you tell the
environment to do it then it's clearly done outside of Ada itself.

> I dispute that this is a "nearly transparent" change to the language.
> Other folks have already pointed out to you that Ada's
> order-of-declaration dependencies reflect an underlying assumption
> about declarations: They all get *elaborated* at run-time, in a
> specific order.  That is, every declaration "takes effect" at a
> specific point in time during execution, and this might (or might not,
> as the case may be) cause something to occur at run time (such as
> initialization).  This rule applies to *all* declarations in Ada,
> including variable declarations, type declarations, subprogram
> declarations, package declarations, what have you.

What happens with mutually recursive procedures in Ada then?  The above
statement would seem to preclude the possibility if Ada is so consistent.
If I've got hold of the wrong end of the stick then please tell me.

Rob
-- 
Q: What happens when the human body is completely submerged in water?
A: The telephone rings

Rob Heyes                                    rob@brewster.demon.co.uk



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

* Re: Generic association example (was Re: Mutual Recursion Challenge)
  1994-10-26 23:21                         ` John Volan
@ 1994-10-27 10:53                           ` Robert I. Eachus
  1994-10-31 17:34                             ` John Volan
  1994-10-27 14:37                           ` Mark A Biggar
  1 sibling, 1 reply; 45+ messages in thread
From: Robert I. Eachus @ 1994-10-27 10:53 UTC (permalink / raw)



    (I'll post one last time on this subject here, then take any
follow-up to mail.)

In article <1994Oct26.232154.29094@swlvx2.msd.ray.com> jgv@swl.msd.ray.com (John Volan) writes:

  > I suppose we could apply a pragma Suppress at some point to
  > eliminate the extra dynamic check, once the program was fully
  > tested.  But, more to the point, we've lost a certain amount of
  > expressibility.  Since the Ada code doesn't directly express what
  > we mean, its readability by other Ada programmers (for example,
  > maintainers) is reduced.

   Let the compiler do the work.  If there is only one concrete type
in an abstract class, the check might result in a call at run-time to
a check, but the check should be implemented as a return instruction.
If there are types derived from Office or Person, there may be an
actual check in some other cases that you want made.  But any compiler
that does run time checks for abstract types, or builds dispatch
tables for abstract types has a bug.  (There are cases where you may
have a view of an object as an abstract type, but that must always be
a static view--at least, that is the intent.)

  > What cannot be easily named, cannot be easily explained, and
  > therefore cannot be easily understood.

    The style of Ada 9X programming I am focusing on addresses this by
making that disappear from sight.  The only objects visible in the
"main" program should be complete objects of complete types.  The rest
should be treated like making sausage or scrapple and hidden in
private parts whereever possible.

  > But that's not the only way you could arrange things.  If you
  > noticed, in my previous posts, I actually conceived of
  > *distributing* this "Setting" responsibility to *both* of the
  > classes.  In other words, I imagined having *two* "Associate"
  > operations: one that was primitive for an Employee and one that
  > was primitive for an Office.  The Associate for Employee would
  > only directly modify the Employee's pointer to its Office;
  > likewise the Associate for Office would only directly modify the
  > Office's pointer to its Employee.  That follows the "Law of
  > Demeter": an object's operations should only directly manipulate
  > its own attributes, but not the attributes of any other object.

  > However, both of these Associate operations would also be
  > responsible for satisfying the invariant of the association: i.e,
  > if an Employee points to an Office, then that Office must point
  > back to that Employee as well.  The most convenient way for the
  > two Associate operations to do that would be ...  to call each
  > other!  In other words, they would be *mutually recursive*
  > subprograms, reflecting the *mutually recursive* relationship
  > between the two classes.

      Excellent reasoning, but I wouldn't code the blasted bodies that
way.  Infinite recursion is frowned upon, so if set for office calls
set for person and vice-versa, something has to break the loop.  The
"best" way I found was to set the local attribute, then check the
remote attribute and if it was "wrong" call the matching set.  It
works, but it is pretty kludgy.  I'm willing to pay a bit for
elegance, but that's a little expensive.  Above you talk about
eliminating redundant checks, here you not only prohibit simple
operations from being effectively inlined, but require a check that
the thing you just set has the right value.

      According to ME ;-) the association package "owns" the Attribute
fields and is the only one to monkey with them, and this is the right
and proper approach in Ada 9X.  It is different, but it seems better
from an encapsulation point of view.  With the Smalltalk or C++ model
large and complex object implementations soon get buried in
interactions between different components of an object.  In this
model, each abstraction takes care of its own.

      I left some stuff out here for simplicity, but in a "real"
implementation of this idea, I would insist that both object be
derived from Controlled, or Limited Controlled, and I would insure
that there were no dangling pointers when an object was destroyed, and
that copying an object did not copy the assignments. (In a many-to-one
or many-to-many implementation the policy would be different of
course.)  In other words, fix all those bugs before they occur, and
transparent to the user of the abstraction.

  > You see, that's what I mean -- you've lost the ability to express
  > the exact type of the other object in a static fashion, even
  > though you, as the designer, do know what that exact class should
  > be, a priori.

   In the instance you can use subtypes and renames to express things
right, and in a real world application, as I said I would put as much
of this as possible in the private part.  (Due to the form of the
generic, the outer instance must be public, but that's about it--other
than the operations and types you want to show.)

  > Interesting interpretation.  I didn't think there was any trouble
  > with returning "null".  Clients could just interpret a "null"
  > value as meaning that E isn't associated with any Target.  But
  > that's okay -- you just have a slightly different abstraction in
  > mind than I have.

   Major difference, but subtle in its way.  I hid the "pointer"
types, so all external interfaces deal with objects, not pointers to
objects.  Yes, we know that what gets passed around is a reference,
so there is no extra calling overhead, but doing it this way
eliminates--if done correctly--dangling pointer worries for users of
the abstractions.  I didn't show all of that, but for example, the
finalization operation on a Person would unset his office.  So there
is no null value to return.

  > >       procedure UnSet(E: in out Extended'CLASS);
  > >        procedure UnSet(IE: in out Extended'CLASS);
  > >       -- UnSet the attribute.  If already set, unset the partner as well.

  > By the way, in the case of "many"-cardinality, I think UnSet would
  > actually wind up being a single operation with two parameters.

   (Read a little closer.  UnSet can always get the partner when
needed, and the code does it that way.  But, yes, you also need the
two parameter form in the many-to-many mapping to remove exactly one
pairing.)
--

					Robert I. Eachus

with Standard_Disclaimer;
use  Standard_Disclaimer;
function Message (Text: in Clever_Ideas) return Better_Ideas is...



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

* Re: Generic association example (was Re: Mutual Recursion Challenge)
  1994-10-26 23:21                         ` John Volan
  1994-10-27 10:53                           ` Robert I. Eachus
@ 1994-10-27 14:37                           ` Mark A Biggar
  1 sibling, 0 replies; 45+ messages in thread
From: Mark A Biggar @ 1994-10-27 14:37 UTC (permalink / raw)


In article <1994Oct26.232154.29094@swlvx2.msd.ray.com> jgv@swl.msd.ray.com (John Volan) writes:
>But I still see a problem: It looks like each class is giving up the
>ability to use static strong typing to assert the exact type of the
>*other* objects associated with it.  In other words, a "Person-who-
>can-occupy-an-Office" can't assert that it's associated with an
>"Office-that-can-be-occupied-by-a-Person" (or with a "Total Office",
>for that matter).  All it can say is that it's associated with an
>"Office".  So when a client asks a Person object for its Office, the
>Person can answer with its associated "Office", but it can't provide
>the client with a "Total" view of that Office.  The client would have
>to do the view-conversion itself by "narrowing" (safely downcasting)
>that Office into a "Total Office".
>
>That narrowing operation would incur a run-time check on the Office's
>tag.  But that check is actually redundant.  You know and I know that
>the Office object will really be a "Total Office"; we can assert that
>as a statically-determined fact, since we're the designers of the
>software, and that was our original intent for the association.
>However, when we go to write our Ada code for the Person class, we
>discover that we can't explicitly assert, in the Ada code itself, that
>a Person's associated Office will actually be one of those "Total
>Offices".  So we can't tell the compiler that this is a
>statically-determined assertion that it can check statically.
>Instead, it becomes a dynamically-checked assertion.  In short, this
>takes us a step away from a statically-checked style of programming,
>and moves us closer to the dynamically-checked style of languages such
>as Smalltalk.
>
>I suppose we could apply a pragma Suppress at some point to eliminate
>the extra dynamic check, once the program was fully tested.  But, more
>to the point, we've lost a certain amount of expressibility.  Since
>the Ada code doesn't directly express what we mean, its readability by
>other Ada programmers (for example, maintainers) is reduced.  

Actually this case is not a real problem, as a smart compiler can optimize
the run time check away.  Any "Narrowing" downcasting from an abstract
type to its first non-abstract decendent will always pass the check, and
so the check need not be done, even without the pragma Suppress.

--
Mark Biggar
mab@wdl.loral.com




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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-25 15:54                       ` John Volan
  1994-10-26  1:24                         ` Bob Duff
@ 1994-10-28  4:28                         ` Jay Martin
  1994-10-28 10:52                           ` Robert I. Eachus
                                             ` (2 more replies)
  1 sibling, 3 replies; 45+ messages in thread
From: Jay Martin @ 1994-10-28  4:28 UTC (permalink / raw)


jgv@swl.msd.ray.com (John Volan) writes:

>jmartin@baleen.cs.ucla.edu (Jay Martin) writes:

>>(Can't do anything other than rant now (got to fix bugs)) Jay.
>                               ^^^^      ^^^^^^^^^^^^^^^ 

Oops, I was trying to say that, I was under time pressure to get something
done and couldn't fully analyze your post but was going to respond later. 
Instead I took a nasty swipe at CS (I am a CS PHD student).

You think my last post was bad....

>>>Don't underestimate the complexities involved here.  Your "package
>>>forward" idea is essentially identical to the "package abstract"
>>>concept I suggested a while back (although my proposal didn't require
>>>any new Ada reserved-words :-).  When I presented the idea of "package
>>>abstracts", I at least considered some of the issues they raise:

>>>1. Is a package abstract an optional feature, or are you compelled to
>>>   precede every package spec with a package abstract?  If optional,
>>>   how do you distinguish a package spec that has a preceding abstract
>>>   from one that does not?  Or are we creating a situation analogous to
>>>   the Ada83 problem of an "optional body for a bodiless package spec"?

>>>2. How do you distinguish a "with"-clause that only imports a package
>>>   abstract from one that imports the whole package spec?

>>>3. Can a package-with-abstract be generic?  If so, where does the generic
>>>   clause go?  How do you instantiate such a beast?  What impact does this
>>>   have on the whole generic contract scheme?

>>>4. This is much too late for 9X, and has to be left for 0X, if it goes
>>>   anywhere at all.  Even if all the difficulties can be ironed out, is
>>>   this feature worth the added compiler complexity, when there are
>>>   reusable workarounds that already effectively extend the language?

>>1. Optional, No, No.
>>2. No.

>"NO"?  What's the point of having two outside views of a package (one
>incomplete, the other fuller) if a potential client can't select how
>much of a view they want?  (Do you even have a *clue* what I'm talking
>about, Jay?)

Since, I specified that only thing a package "forward" could contain
is an incomplete type or a pointer type to one of these incomplete
types.  Such alternate views would be pretty much useless for
forwards.   Only thing the package forward does is stop the compiler
from giving errors for types that are going to be declared.  The same
sort of thing could probably also be done by "type forward
OtherPackage.AType;" shoved into the spec of dependent mutually
recursive type.  Its saying "hey" I am going to declare this type
later in the other package don't kill my compile.  Of course we could
depend on a complex compilation system to solve all these mutually
recursion problem, but forward is more in accordance with the simple
Ada model of compiling in dependency order.  I thought I heard
cross-package incomplete types in the early days of Ada9X? (Probably 
dropped)  

>>3. No.

>Why not?  Why do we have to make a *special exception* in this case,
>for a feature that ought to be *orthogonal* to this?  Is it just
>because someone like you doesn't want to be bothered about thinking
>things through?

Orthogonality is crap.  It used as a excuse, "well we have this
feature so we must have this feature.  This feature has to be
seemlessly integrated with that feature and we need this other
feature to do it!  Hey we can throw in this capability for almost
free!".  A programming language is like the budget for the US
government.  You can only throw in so much complexity until the
implementation gets huge and learning curve start to overwhelm the
programmer, thus going over budget.  You can borrow money and go over
the budget but you'll have to pay for it eventually when your obese
language has to evolve.  You got to cut sometimes even if the
features are important and useful.  Language design is also like the
Vietnam war, each small step was rational and reasonable in a micro
perspective but the overall result ends up irrational.  Anyway, if
your language is getting so complex and obscure that you need
hundreds of people to work out the details, then I believe that the
language has crossed the boundry of reasonableness.  How is a
programmer ever going to understand such things.  I believe
simplicity is possible.  Simplicity of course has costs.  Don't
confuse non-orthogonality with PL1 (the typical example), if IBM had
made PL1 completely orthogonal it still would have been crap!
Exceptions rule! Cut the budget!

In my opinion, the first reaction to whether an arbitrary feature A
"package forward" works with feature B "generic packages" should be
no.  The compiler can just say "package forwards cannot be generic
(RM5.2.23.3)".  We can not just make the argument, due to
orthogonanlity....  We must weigh whether it is worth the extra
complexity/danger given typical usage.  Likewise, we shouldn't say
that "We can't add that feature because due to orthogonality, it
implies this, this and this must be inserted which makes the original
proposal too obese".

Okay, okay some substance.  It seems more reasonable for generic
mutual recursive objects to be in the same generic unit this is
because I assuming the we want to instantiate the generics with 
the same generic parameters.   For example:

generic
  ...
package Holder is
  
  package forward X ...;
  
  package Y ...;
  package X ...;
end Holder;


Of course we may want to have each of the mutually recursive generic
packages be separately compiled.   The problem is that we can't
reference a generic package because it may have multiple instances.
(Unlike C++'s  TemplateType<<GenParTypes>> which can only have one
template instance per template parameter combination).   This implies
that the mutual recursive package types must be passed in the generic
parameters themselves.   Thus we can use the "forward" idea in the
following way.  We define generic versions of the package and achieve
mutual recursion in the following way.

package forward X is new XGen;   -- Incomplete generic instatiation.
package Y is new YGen(X.XType,...);
package X is new XGen(Y.YType,...);
  

So, I think the answer to, Can there be forward packages that are generic?
is still NO. I know this is probably got tons of flaws and so I will have
analyze this more fully after I read the Ada9x manuals this weekend. (Time
pressure again) 

    
>>4. Who cares. If the standard can't be easily modified as was the
>>   case for Ada83 then Ada9x is dead.  

>"Easily modified"?  Do you think what the MRT has been doing these
>past few years was *easy*?  Where have you *been*?  Do you have
>*any* idea about what it takes to revise an *international standard*?

The standards community is basically full of shit with respect to
computer languages and should be destroyed. Look at the FORTRAN
standardization process it was essentually politically gridlocked
producing nothing for 20 years.  The only thing that is holding C++
together is the brilliance and leadership of Stroustrup.  Imagine if
some committee designed C++ from scratch, it would have been
worthless joke.  Ada83 was just handed over to the international
standardization organization and said, "Check the spelling and ratify
it". This, in my opinion, is the only way that languages should be
standardarized.  Ada83 has been ruined because it has been set in
cement with even minor changes impossible. Why? Standards! Don't you
love em!  What the DOD should have done is kept Ichbiah and CO. in a
cage (with lots of money) and had him modify Ada as was necessary
over the last 12 years.  Language design is maintanance!  So it is
trivially obvious that the only way to do language design and
maintanance is to have one reasonable,dedicated and responsible 
individual have total power and control (The IQ of a committee...).
(Wirth the only Computer Scientist to make a widely used language
fails the dedicated and responsible criteria).

>>  The Compiler complexity is trivial,
>>  the language would be cleaner.

>"Cleaner"?  With yet another language feature to complicate things?  I
>don't think it would be the *language* that would be "cleaner".  The
>*programs* written in that language would be (a tad) "cleaner", at the
>expense of (possibly a lot) more complexity in the language.  Or
>rather, a certain very particular *style* of programs would be
>"cleaner", possibly at the expense of other styles of programming.

Cleaner is is what cleaner does.

>I'm not a language lawyer, and I've never written a compiler, so I
>haven't presumed to make any claim as to how "trivial" this kind of
>feature would be.  At most, I've tried to point out a few of the
>conceptual difficulties I could see, but that's all speculation on my
>part.  Maybe it *is* "trivial", and if so, I hope some experienced
>language lawyers will pipe up and say so.  Even if it isn't trivial,
>maybe it's worth it anyway -- and if so, I hope some language lawyers
>will pipe up about that too.  But for now, I'm reserving my judgment.

>Jay, are *you* a language lawyer?  Have *you* ever written an
>industrial-strength compiler?  That's not a rhetorical dig.  If you've
>got some real experience here, by all means say so. But somehow I
>doubt it, since your organization seems to be a university computer
>science department, and I suspect you are a student.


Like all lawyers, language lawyers should be shot. :-)

Sorry, real language design and implementation are not worthy of
study in Computer Science (I heard a rumor that this is what Stanford
said to Wirth when they gave him the boot), so I have not worked on or
likely to work on languages of the size, generality and seriousness
of Ada9x or C++.  Actually the bugs I am working on are in a compiler
for an concurrent language.

If the forward idea is not "orthogonalized" to include everything and
the kitchen sink.  Then it would be simple to play with the parser to
except them.  A new object type would have to be added to ada
libraries (besides spec and body).  On withing a package spec if the
real spec had not yet been compiled the incomplete type symbols would
be read into the symbol table.  A simple check at link time for
missing specs and ta da!
  
>>Ada9x is too obese and is being too effected [sic] by trying to be an
>>"elegant" (rigid) extension of obese Ada83.

>One man's "elegant" is another man's "rigid."  Is C++ an "elegant"
>extension of C, or is it "rigidly" preserving C's syntax, which many
>(even in the C/C++ camp) have disavowed as obsolete and kludgy?  (For
>goodness sake, even *Bjarne Stroustrup* seems to have chafed a bit
>about C syntax -- but I won't presume to speak for him.)  Is C++ still
>"lean and mean" today, or is the agglomeration of new features such as
>templates, exceptions, first-class bool and string types, and
>namespaces, (all of which were in Ada ten years ago) turning it into
>an "obese" language?  Is Eiffel "elegant" because of its minimalist
>design, or is it "rigid" because it offers only "One True Way" of
>modularizing a program, and has to resort to auxiliary languages such
>as LACE to deal with higher levels of organization?

The only way to elegantly extend C is with a nuclear weapon. 
C++ is obese. Eiffel is less obese but still pretty fat. I was not that
impressed by the original Eiffel. I am sure "Eiffel 3000" has probably 
fixed alot of these problems, but I haven't looked at the new version.
Ada9x design is rigid because it tried too hard to extend Ada existing
features.  Maybe it should have just thrown in the towel on derived
types,  depreciated private types, kept packages as containers and
added a "class" construct.

>>I really don't understand
>>why can't some clown ...
>                ^^^^^ 
>Let's see, from now on we'll have all our programming languages
>designed by Bozo and Ronald MacDonald, and maybe a few Congressmen,
>too...

One clown is all that is needed and would get better results than 
any committee.  (I am writing this on bozo.cs... so I vote for Bozo!)

>>... spend a few minutes ...
>           ^^^^^^^^^^^^^ 
>Is that how long K&R spent designing C? Might explain a lot ...  

Come on, it took them at least an hour not counting the hour they beat
each other in the head with baseball bats to obtain the necessary
idiocy to produce C!  C is brilliant work of CS! Designing a language?
Don't know which way to do something?  Doing the opposite from C
pretty much guarantees you got it right.
 
>> ... to come up with a cleaner
>>smaller (more minimalist) Ada style language.  

>... as long as your own "trivial" pet language construct gets into it?
>Honestly, do you really think that language designs can just be
>slapped together, or that you can just slap in yet another feature
>without causing a ripple effect in the whole design of a language?  It
>seems to me that *that* way leads to *larger*, *more complex*, *less
>cohesive* languages, NOT "smaller, more minimalist" languages.

See anti-orthogonality arguments above.

>Of course, if you so vehemently believe that this *is* such a 
>trivial feature to slap on top of Ada9X, then I suggest that you
>get yourself a copy of GNAT, revise it to implement your new
>language feature, experiment with it, and then write a learned
>treatise on just how trivial and orthogonal it is (or isn't,
>as you might just discover).  Put up or shut up.

Huh? Oops, by "Ada style language" I meant a completely different language
without upward compatibility problems.  Remove tasking, exceptions, nesting,
floating point types, discriminated records, derived types, real models,
fixed point types, blocks,  goto, named parameters, aggregates, slices, 
rep clauses, simplify generics,etc, you can gain alot of simplicity.  

>>My theory of why CS is
>    ^^^^^^
>>not coming up with one is: (1) Most Computer Scientists are
>>masturbating on useless theoretic, pseudo "huge breakthroughs" and
>                         ^^^^^^^^^
>>"scientific" things.  

>Oh, I see.  It's okay for *you* to have your pet theories, but nobody
>else's ideas are worth pursuing.  Whatever's "trivial" according to
>*your* theories are nuggets of wisdom to be enshrined, but if anybody
>*else* has an opposing view of what's important for software
>engineering, that's "pseudoscience."

>Maybe your jaundiced view about "Computer Science" has less to do with
>the state of the software engineering *industry* and more to do with
>the state of *academic* computer science -- or maybe it just says more
>about the particular academic *institution* you're currently part of.
>If the latter is the case, then I feel sorry for you, and suggest you
>transfer immediately to another school.

I am talking about academic computer science (what else is there). And you
are right, no one here really gives a rats ass about programming, software
engineering or SE language design.  There currently not even one class
being taught about Software Engineering at my university (not this year or
last) Ada isn't even on our CS dept computer, C++ probably wouldn't be if
it didn't automatically come with GCC.  In my opinion, the priests of
Computer Science don't care much about Software Engineering, its pretty
much an orphan field in academia.  Look at some CS journals or thesis/tech
reports from CS departments to see some really useless theoretical
nonsence.  I have a vision of Computer Science acting as the "powerful
tugboat" pulling the ocean liner "Software Industry" through the stormy
waters.  The truth is more like ocean liner "Software Industry" is pulling
a tiny dingy with passenger Computer Science performing unspeakable
masturbitorial acts.  Lucky the rope used to tow the dingy is miles long
so that the passengers on the ocean liner don't have to view this
disgusting behavior!
 
Why is this important to Ada?  Because I don't think industry is ever
going to start using Ada or any elegant SE language.   Maybe if the
colleges (which theoretically are more purist) supported Ada then it would
take off.   But sadly I don't see much hope there either.

>>Language design requires them to sink into the
>>abyss of unholy "social science" and the law of the lowest common
>                                      ^^^^^^^^^^^^^^^^^^^^^^^^^^^^
>>denominator.  
> ^^^^^^^^^^^^

>I understand it all now.  Forget striving for excellence, folks! Don't
>bother!  Let's just keep things at the level where any fool can slap
>software together!  Sure, only a fool would buy or use such software,
>but that's okay, because *everybody* would be equally foolish.  O
>Brave New World ...

My theory of computer language design is this: Programmers are idiots,
assholes and pinheads. Since I am a programmer, I am a pinhead
too.  Look what I wrote in a boolean expression in C today:  
BoolVar = (IntVar =! 2);.  I wanted  "!=" not "=!".  So what did
C do for me instead of giving a compiler error:

(1) It conceptually converted 2 into a boolean True and (!) not-ed it
to False.  Implicit type conversion rules! 

(2) Converted the Boolean False to an integer 0 and assigned it to
IntVar. IntVar is trashed. I never imbedded assignments especially not
in boolean expressions, I did today!

(3) The assignment convieniently returned a copy of the new value
of IntVar, which was converted to a boolean and assigned to my 
boolean variable.    

Yahoo.  C gave me the power and flexiblity to make an embarassing 
mistake. 
-----------

If you design a language that requires 200 IQ brainos who never make
errors to understand/use, then trying to use that language on a
project of a hundred average programmers is not going to be
successful.  Thus language design must be down to earth,
understandable and safe for the average programmer.   Spaced out
grandious languages is not what software developers need. I am not
saying this languages shouldn't be researched but practical designs
must also be studied.

>>(2) Even if one did, political jealousy and power games
>>within the Computer Science community would not allow them to
>>recognize, except [sic], support and then champion a really good and
>>software engineering efficient language.

>"Let him who is without sin ..."  In my experience, those who
>whine most about "political jealousy" and "power games" are usually
>those who *tried* to play political power games in the past and
>*failed*.  

Never tried. Never will. Politics both facinates and repulses me
at the same time.  Can they really be that stupid/self centered?

Yup, the CS community is rolling out the ol red carpet for Ada since 1983.
And they are screaming and yelling how great Eiffel is.  My opinion is
that no endorsements are allowed as they are "too political" and
non-scientific.  Of course, social science programming experiments could
be performed to prove that certain language styles are more SE efficient
than others but this might step on some toes and besides its obvious
and boring. 

I want CS to be out in front AND practical in the field of language
design.  They should be defining language design, not ignoring it.
Computer Science has been pretty much failures at producing practical
computer languages.  My theory is that this political climate exists, thus
causing no academic work to be carried out.  I get the feeling that if I
proposed to do a language for my thesis, they would laugh, "Where is the
science?".

Jay.




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

* Mutual Recursion (was Re: SOLVED! Decoupled Mutual Recursion Challenger)
  1994-10-27  4:25                           ` Rob Heyes
@ 1994-10-28  9:03                             ` Robert I. Eachus
  1994-10-28 15:04                             ` SOLVED! Decoupled Mutual Recursion Challenger Robb Nebbe
  1 sibling, 0 replies; 45+ messages in thread
From: Robert I. Eachus @ 1994-10-28  9:03 UTC (permalink / raw)



In article <783257151snx@brewster.demon.co.uk> rob@brewster.demon.co.uk (Rob Heyes) writes:

  > What happens with mutually recursive procedures in Ada then?  The
  > above statement would seem to preclude the possibility if Ada is
  > so consistent.  If I've got hold of the wrong end of the stick
  > then please tell me.

  Mutually recursive procedures are usually not a problem, because, in
general all elaboration occurs before procedures get called.  But:

    Elaboration is a property of declarations, and in any language I
hope it is impossible to call a procedure before it is declared.  Ada,
however, also requires that the body of a subprogram be declared
before the procedure can be called.  This allows time for eveything
visible to the body of the subprogram to be elaborated before it is
referenced.

    The case most people run into is when they try to use a function
defined in a declarative part to initialize a variable declared in the
same declarative part.  It doesn't work (unless the function is a
generic instantiation) due to the circular visibility problem:

    function F return Integer;
    X: Integer := F;
    ...
    function F return Integer is begin return X; end F;

    It is legal to write this, but there is no possible valid
elaboration order, so you will get PROGRAM_ERROR at run-time.

--

					Robert I. Eachus

with Standard_Disclaimer;
use  Standard_Disclaimer;
function Message (Text: in Clever_Ideas) return Better_Ideas is...



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-28  4:28                         ` Jay Martin
@ 1994-10-28 10:52                           ` Robert I. Eachus
  1994-10-28 18:46                             ` Jay Martin
  1994-10-29  0:38                           ` Bob Duff
  1994-10-31 18:44                           ` SOLVED! Decoupled Mutual Recursion Challenger John Volan
  2 siblings, 1 reply; 45+ messages in thread
From: Robert I. Eachus @ 1994-10-28 10:52 UTC (permalink / raw)



In article <38pulp$ovg@oahu.cs.ucla.edu> jmartin@oahu.cs.ucla.edu (Jay Martin) writes:

   First that bug in your C program is a classic, worse than some of
my old PL/I implicit conversion horror stories!

   Second, let's put the package forward proposal in the trashcan it
deserves.  I'm not trying to be critical, but as one of those language
lawyers you want to shoot, the only feature it would add to the
language is to allow you to shoot yourself in the foot instead of
stopping you.  Ada, even Ada 83, has a perfectly good mechanism for
generating mutually recursive types, with operations which derive and
(in 9X) dispatch.  All you have to do is stick in a "extra"
derivation. (Or if you want apparent symmetry, two.)  Treat the extra
work exactly as it should be treated--as a warning that there is
complexity here which needs thinking about.

   All the hullaballo is about that required (and in some sense
arbitrary) symmetry breaking.  But as has been pointed out the
ordering is a feature of the language which no one should want to
throw away.  It is really a guarantee that no object's value is
referenced before it is created and (if it has an initial value)
initialized.  All the "clever" solutions ignore this.  When you look
at the way the bodies have to be written, all you have done is either
postphone the problem, or ask the programmer to solve it for the
compiler.

  > Ada83 was just handed over to the international standardization
  > organization and said, "Check the spelling and ratify it".

   This is a misunderstanding.  It took a lot of effort to insure that
there was a single Ada standard, and part of that effort involved a
translation of ANSI Ada into French. (ISO 8652 1987 is a one-page
endorsement of the ANSI and AFNOR standards.  With 9X the ANSI and ISO
standards will be the same document.)  But the effort that went into
converting Ada 80 (MIL-STD 1815) into a useable standard took more
than two years, and a lot of work worldwide by thousands of people.
Having a single small design team kept this from creating a camel, and
the same approach was taken for 9X.

  > This, in my opinion, is the only way that languages should be
  > standardarized.  Ada83 has been ruined because it has been set in
  > cement with even minor changes impossible.

  This is a total misunderstanding.  If you get a copy of the
Annotated Ada Reference Manual, you will find that almost every page
has an AI on it.  The terminology of "Ada Interpretation" and "Binding
Interpretation," was chosen due to the fact that standard maintenance
was not really supported by standards organizations a decade ago, but
the Ada maintenance procedures were used as a model in setting up the
current ISO procedures.

  > Language design is maintanance!  So it is trivially obvious that
  > the only way to do language design and maintanance is to have one
  > reasonable,dedicated and responsible individual have total power
  > and control (The IQ of a committee...).

    Consensus and a number of people with a vision of what the
language IS help a lot.  But no single individual can get it right
every time.  If you look at the AI's closely you will find that not
even a dedicated group of language lawyers can accomplish that.  But
there are relatively few AI's that correct other AI's, so we did
pretty well (at least in the final product).

  > Huh? Oops, by "Ada style language" I meant a completely different
  > language without upward compatibility problems.  Remove tasking,
  > exceptions, nesting, floating point types, discriminated records,
  > derived types, real models, fixed point types, blocks, goto, named
  > parameters, aggregates, slices, rep clauses, simplify
  > generics,etc, you can gain alot of simplicity.

    So remove all the features you don't need this week, and you have
a much smaller language.  Fine, no one is stopping you from using that
subset.  But the whole purpose of the Ada standardization effort was
to make it possible to take your code, and Joe's code, and Ralph's
code, and use them in the same program without migraines.  This
requires that subsets work with programs that use the pieces they
ingnore.  THAT is what orthogonality is about.

    A one page or even ten page program that used "all" of Ada would
be an abomination.  But Ada needs to be able to express any
programming construct so that the programmer can think about what is
the most appropriate technique to use in this application.  Removing
that would be a major disservice to serious programmers.

  > If you design a language that requires 200 IQ brainos who never
  > make errors to understand/use, then trying to use that language on
  > a project of a hundred average programmers is not going to be
  > successful.  Thus language design must be down to earth,
  > understandable and safe for the average programmer.  Spaced out
  > grandious languages is not what software developers need. I am not
  > saying this languages shouldn't be researched but practical
  > designs must also be studied.

   What we have in Ada is a language which is very easy for software
engineers to use without being punished for mistakes and oversights,
but without those bugs getting into the delivered product.

  Most software engineers regard the fact that there are many
programmers out there who don't understand software engineering and
therefore can't use Ada as an advantage.  But it would be even nicee
if someone could teach them software engineering!

--

					Robert I. Eachus

with Standard_Disclaimer;
use  Standard_Disclaimer;
function Message (Text: in Clever_Ideas) return Better_Ideas is...



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-27  4:25                           ` Rob Heyes
  1994-10-28  9:03                             ` Mutual Recursion (was Re: SOLVED! Decoupled Mutual Recursion Challenger) Robert I. Eachus
@ 1994-10-28 15:04                             ` Robb Nebbe
  1 sibling, 0 replies; 45+ messages in thread
From: Robb Nebbe @ 1994-10-28 15:04 UTC (permalink / raw)


|> What happens with mutually recursive procedures in Ada then?  The above
|> statement would seem to preclude the possibility if Ada is so consistent.
|> If I've got hold of the wrong end of the stick then please tell me.
|> 

There is a problem if you try to inline two mutually recursive procedures;
it is impossible and one of the procedure will not be inlined. Normally
procedures have a level of indirection, the procedure call, which avoids
any problems with mutual recursion.

Types on the other hand do not have an implicit level of indirection in
Ada (they normally do in Eiffel which is how Eiffel sidesteps the whole
issue). If you want mutually recursive types you must use an explicit level
of indirection. The trick was separating this over multiple packages which
is difficult because of Ada's tight control over visibility.

There are better solutions that avoid the whole issue in both Eiffel
and Ada.

- Robb Nebbe



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-28 10:52                           ` Robert I. Eachus
@ 1994-10-28 18:46                             ` Jay Martin
  1994-11-02 14:56                               ` Robert I. Eachus
  0 siblings, 1 reply; 45+ messages in thread
From: Jay Martin @ 1994-10-28 18:46 UTC (permalink / raw)


Could you give an example of how you could shoot yourself in the foot
using the package forward idea.  How do you implement mutual recursion
using straight Ada83 derived types?  The abstract type solution and
downcasting are not deemed very exceptable by many of the lang.ada
participants.  Jay



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-28  4:28                         ` Jay Martin
  1994-10-28 10:52                           ` Robert I. Eachus
@ 1994-10-29  0:38                           ` Bob Duff
  1994-10-29  7:26                             ` Jay Martin
  1994-10-29 11:59                             ` Richard Kenner
  1994-10-31 18:44                           ` SOLVED! Decoupled Mutual Recursion Challenger John Volan
  2 siblings, 2 replies; 45+ messages in thread
From: Bob Duff @ 1994-10-29  0:38 UTC (permalink / raw)


In article <38pulp$ovg@oahu.cs.ucla.edu>,
Jay Martin <jmartin@oahu.cs.ucla.edu> wrote:
> ...There currently not even one class
>being taught about Software Engineering at my university (not this year or
>last) Ada isn't even on our CS dept computer, C++ probably wouldn't be if
>it didn't automatically come with GCC.

I've heard that the GNAT Ada compiler will also be distributed with gcc.

> ...Look what I wrote in a boolean expression in C today:  
>BoolVar = (IntVar =! 2);.  I wanted  "!=" not "=!".

Interesting bug.

>If you design a language that requires 200 IQ brainos who never make
>errors to understand/use, then trying to use that language on a
>project of a hundred average programmers is not going to be
>successful.  Thus language design must be down to earth,

All programmers make mistakes.  Even those with 200 IQ.
I agree -- language design must be down to earth in the sense that
languages ought to prevent and/or detect down-to-earth mistakes.

> ...Of course, social science programming experiments could
>be performed to prove that certain language styles are more SE efficient
>than others but this might step on some toes and besides its obvious
>and boring. 

I think the reason such experiments are not done is that they would be
very expensive.  We can't experiment on rats, after all.

Sure, theoretically, you could compare Ada-with-discriminants to
Ada-without-discriminants, using two groups of 100 teams of programmers,
one for each language, all doing the same project.  But that experiment
would cost hundreds of millions of dollars.  And that's just to
investigate whether discriminants are a good idea.  What about all the
other features of various languages?

You could compare Ada with C++ using a similarly costly experiment, but
what would that tell you?  Having found out which of the two is "better"
a language designer would still want to know why.  Surely neither one is
perfect; we should strive to improve on both.

And, of course, nobody in "real" science trusts experimental results
until they've been duplicated by several different researchers.

That's why I think we're going to be stuck with seat-of-the-pants
language design and anecdotal-evidence on their merits for at least some
decades.

They say that in computer science, one takes a single data point, and
extrapolates from there.  It makes curve fitting easy.  ;-) ;-)

- Bob
-- 
Bob Duff                                bobduff@inmet.com
Oak Tree Software, Inc.
Ada 9X Mapping/Revision Team (Intermetrics, Inc.)



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-29  0:38                           ` Bob Duff
@ 1994-10-29  7:26                             ` Jay Martin
  1994-10-29 11:59                             ` Richard Kenner
  1 sibling, 0 replies; 45+ messages in thread
From: Jay Martin @ 1994-10-29  7:26 UTC (permalink / raw)


>> ...Of course, social science programming experiments could
>>be performed to prove that certain language styles are more SE efficient
>>than others but this might step on some toes and besides its obvious
>>and boring. 

>I think the reason such experiments are not done is that they would be
>very expensive.  We can't experiment on rats, after all.

The rats are undergrad computer science majors.  It seems me
reasonable that every CS major to take part in say 2-3 quarters of
software engineering experiments on large scale programs.  I
believe they would learn alot about programming in the large. 
These experiments should get large chunks of computer science budgets
as they are really the heart of computer science (though currently
the computer scientists don't think so).  

>Sure, theoretically, you could compare Ada-with-discriminants to
>Ada-without-discriminants, using two groups of 100 teams of programmers,
>one for each language, all doing the same project.  But that experiment
>would cost hundreds of millions of dollars.  And that's just to
>investigate whether discriminants are a good idea.  What about all the
>other features of various languages?

Surely we wouldn't want to spend time trying to quantify micro
changes in languages, but big differences like dynamic versus/static
typing, etc.  Restrictive versus permissive, etc.   Big and
orthogonal, versus small/simple non-orthogonal.  Isn't getting some data
on these differences important?  These experiments could be run by a
few CS professors and grad students at each university for less than
hundreds of millions of dollars.  

>You could compare Ada with C++ using a similarly costly experiment, but
>what would that tell you?  Having found out which of the two is "better"
>a language designer would still want to know why.  Surely neither one is
>perfect; we should strive to improve on both.

I think this study would be beneficial.  And I believe Ada9x would
come out on top.  We would know why by reading the qualitative
analysis of each of the studies.  Unfortunately, I don't believe you
can improve languages indefinitely by adding features.  To really
improve C++ and Ada9x style languages alot of features would have to
be removed and the languages remade from the ground up.

>And, of course, nobody in "real" science trusts experimental results
>until they've been duplicated by several different researchers.
>That's why I think we're going to be stuck with seat-of-the-pants
>language design and anecdotal-evidence on their merits for at least some
>decades.
>They say that in computer science, one takes a single data point, and
>extrapolates from there.  It makes curve fitting easy.  ;-) ;-)

Heh, everyone knows that fields with "science" in their name are
always non-scientific jokes. :-)

If enough CS departments were doing such studies instead of zero, 
then we would have the data points to get answers to these big 
questions.  At least we would stop people from wasting their time on
endless arguments about these topics.

Jay. 




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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-29  0:38                           ` Bob Duff
  1994-10-29  7:26                             ` Jay Martin
@ 1994-10-29 11:59                             ` Richard Kenner
  1994-10-31 13:17                               ` Robert Dewar
  1994-10-31 14:13                               ` gcc distribution (was: SOLVED! Decoupled Mutual Recursion Challenger) Norman H. Cohen
  1 sibling, 2 replies; 45+ messages in thread
From: Richard Kenner @ 1994-10-29 11:59 UTC (permalink / raw)


In article <CyEsGL.KGE@inmet.camb.inmet.com> bobduff@dsd.camb.inmet.com (Bob Duff) writes:
>In article <38pulp$ovg@oahu.cs.ucla.edu>,
>Jay Martin <jmartin@oahu.cs.ucla.edu> wrote:
>> ...There currently not even one class
>>being taught about Software Engineering at my university (not this year or
>>last) Ada isn't even on our CS dept computer, C++ probably wouldn't be if
>>it didn't automatically come with GCC.
>
>I've heard that the GNAT Ada compiler will also be distributed with gcc.

No, that's unlikely due to its size.  Similarly for GNU Fortran 77.

In fact, it's likely that GNU C++ (g++) won't be distributed with GCC
anymore starting with GCC 2.7.0.  GNU Objective-C will probably always
remain distributed with GCC because it's too small to be worth
splitting off.



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-29 11:59                             ` Richard Kenner
@ 1994-10-31 13:17                               ` Robert Dewar
  1994-10-31 14:13                               ` gcc distribution (was: SOLVED! Decoupled Mutual Recursion Challenger) Norman H. Cohen
  1 sibling, 0 replies; 45+ messages in thread
From: Robert Dewar @ 1994-10-31 13:17 UTC (permalink / raw)


To clarify RIchard's remarks. Now that the entire GCC system, with all its
front ends, is getting larger and larger, the distribution setup is being
changed so that you are not forced to download the entire set of front ends.
This doesn't mean that GNAT and the other front ends will not be distributed
"with GCC", it just means that you decide which pieces of the system to
pick up when you get GCC, but it will still be the case that GNAT will
eventually be available by the normal GCC distribution paths.




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

* gcc distribution (was: SOLVED! Decoupled Mutual Recursion Challenger)
  1994-10-29 11:59                             ` Richard Kenner
  1994-10-31 13:17                               ` Robert Dewar
@ 1994-10-31 14:13                               ` Norman H. Cohen
  1994-11-02 14:14                                 ` Richard Kenner
  1 sibling, 1 reply; 45+ messages in thread
From: Norman H. Cohen @ 1994-10-31 14:13 UTC (permalink / raw)


In article <38tdeo$bta@cmcl2.NYU.EDU>, kenner@lab.ultra.nyu.edu (Richard
Kenner) writes: 

|> In article <CyEsGL.KGE@inmet.camb.inmet.com> bobduff@dsd.camb.inmet.com (Bob Duff) writes: 
...
|> >I've heard that the GNAT Ada compiler will also be distributed with gcc.
|>
|> No, that's unlikely due to its size.

This is distressing.  One of the things that most excited me about the
GNAT project when I first heard about it was the prospect that an Ada
compiler would be hidden in each standard gcc distribution, and thus
serve as a Trojan horse to sneak Ada into the camps of the C programmers.

Upon accidently discovering Ada compilers on their machines, gcc users,
epsecially in academia might be tempted to try it out one day.
Also, users would be more likely to download Ada source code if they were
told, "You probably already have an Ada compiler on your machine that you
never knew about," than if they were told, "You can obtain an Ada
compiler by anonymous ftp as follows...." A tool readily at hand is much
more likely to be tried out on a whim than one that must be retrieved
over the net first.

--
Norman H. Cohen    ncohen@watson.ibm.com



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

* Re: Generic association example (was Re: Mutual Recursion Challenge)
  1994-10-27 10:53                           ` Robert I. Eachus
@ 1994-10-31 17:34                             ` John Volan
  0 siblings, 0 replies; 45+ messages in thread
From: John Volan @ 1994-10-31 17:34 UTC (permalink / raw)


eachus@spectre.mitre.org (Robert I. Eachus) writes:

> In article <1994Oct26.232154.29094@swlvx2.msd.ray.com> jgv@swl.msd.ray.com (John Volan) writes:
> 

[snip my objection about the need for the client to do narrowing to get
a fuller view of an associated object after a query]

>   Let the compiler do the work.  If there is only one concrete type
>in an abstract class, the check might result in a call at run-time to
>a check, but the check should be implemented as a return instruction.
>If there are types derived from Office or Person, there may be an
>actual check in some other cases that you want made.  But any compiler
>that does run time checks for abstract types, or builds dispatch
>tables for abstract types has a bug.  (There are cases where you may
>have a view of an object as an abstract type, but that must always be
>a static view--at least, that is the intent.)

It still bothers me that when you query an object like an Employee for
another object associated with it, let's say its Office, the result
you get back will only provide a highly abstract view of that
associated object.  If the client wants to invoke operations on
the second object that are only available from a more complete view
(for instance, we want to find out the Building the Office is in) the
client has to do a narrowing type-cast on it.  I just think it would
have been nice if the original query operation provided the more
complete view of the associated object in the first place.  But to
do that, you somehow have to solve the chicken-and-egg problem.

To be fair, even under my generic scheme, an associative query is only
going to provide a "highly abstract view", and the client still has to
do a conversion to a more complete view.  But that "highly abstract
view" is one of those Identity.Value types, so the effect is a bit
different.  An Identity.Value type is just a "black box" with a
one-to-one relationship with a particular access-to-classwide-type,
and that access type presumably is exactly the "complete" view we're
looking for.  In theory, the translation shouldn't need to involve any
run-time checks -- but, of course, that depends on how you actually
implement the "black box."

>  > What cannot be easily named, cannot be easily explained, and
>  > therefore cannot be easily understood.

>    The style of Ada 9X programming I am focusing on addresses this by
>making that disappear from sight.  The only objects visible in the
>"main" program should be complete objects of complete types.  The rest
>should be treated like making sausage or scrapple and hidden in
>private parts whereever possible.

Okay, okay, I believe you.  I guess it would help me to see a
completely worked-out example (or to sit down and work one out
myself).  Believe me, I'm very enthusiastic about any scheme that can
let you snap together a class from reusable parts.  But I don't see
how the association-supporting code for a class can actually be hidden
away in private parts, regardless of how it gets constructed.
Remember, I'm working under the basic assumption that
association-related operations are going to be public features of a
class, in whatever complete view you have for it.

I can see that the final step in constructing a class with
associations would be to just derive a final concrete type (with null
extension) from the last abstract type coming out of a chain of these
association-instantiations.  But this means that a reader must examine
this whole chain of instantiations to fully understand the class.
Yes, I see how that might be mitigated by using renamings and subtypes
to restate the total class interface accumulated from all the abstract
ancestors....

Hmmm ... those renamings you allude to, do you mean them to be
renamings-as-declarations, or renamings-as-bodies?  I thought you
meant the former, but if you meant the latter, then that opens up a
whole new realm of possibilities.  One upshot of this is that it would
at least be conceivable that we could merge our two techniques: Your
mixin scheme could be used to easily snap together the implementation
backbone for the associations, while my scheme of
deferred-coupling-via-generics could be used in packaging up the final
"total" abstraction for the classes, solving the chicken-and-egg
problem of how to establish mutually-dependent package specs (that is,
if you really *need* the mutual dependency to be publicly visible in
the package specs).

[snip my sketch of mutually-recursive Associate procedures]

>      Excellent reasoning, but I wouldn't code the blasted bodies that
>way.  

Then perhaps a scheme such as yours could provide the actual hidden
implementation.

>Infinite recursion is frowned upon, so if set for office calls
>set for person and vice-versa, something has to break the loop.  

Of course.

>The
>"best" way I found was to set the local attribute, then check the
>remote attribute and if it was "wrong" call the matching set.  It
>works, but it is pretty kludgy.  

Actually, the way I worked it was to always keep things as "local" as
possible: I'd check the local attribute first to see if it was already
"right", and then break the infinite recursion there (on the
assumption that the mutual-pointing invariant condition had always
been satisfied in the past).  Otherwise, I'd set the local attribute
(disassociating the old partner first if necessary), and then make the
mutually-recursive call to the cross-side Associate procedure.  The
same thing would happen on the other side, and then the first
Associate would get called again.  At that point, the recursion would
stop, because the local attribute would turn out to be "right"
already.  Is this better or worse than the way you describe?  I can't
really say, but I'd welcome any comments.

>I'm willing to pay a bit for
>elegance, but that's a little expensive.  Above you talk about
>eliminating redundant checks, here you not only prohibit simple
>operations from being effectively inlined, but require a check that
>the thing you just set has the right value.

Well, I can't deny the expense of the mutual recursion.  And I'm not
sure how I could get rid of the extra check without breaking my own
encapsulation scheme: To do that, each class would have to publish a
non-recursive "Set" operation that merely set the local pointer
without guaranteeing the invariant condition.  This operation could be
called by the "Associate" operation on the other side in order to
fulfill the invariant in an efficient manner.  But this opens up the
possibility of other clients also calling these weaker "Set"
operations, rather than the stronger "Associate" operations, thereby
possibly violating the invariant.  Obviously not a good idea.  (There
might be a tricky way to use generics and access-to-subprogram types
to make these "Set" operations accessible from the cross-side
"Associate" operations without otherwise making them public globally,
but this still won't solve the inlining issue you raise.)

As for mutual recursion preventing a "simple" operation from being
inlined ... hmmm ... that observation is actually triggering some
interesting questions in my mind.  Let me respond to this first by
saying that, yes, you're right, mutual recursion is a liability --
if the operation of setting up an association is really a "simple"
one.

But what if it isn't "simple"? 

This question is actually forcing me to rethink some of my own
intuitions about this whole issue.  You see, in previous posts I
myself agreed to the idea that the attributes and operations
supporting a given association would probably be class-wide, and
orthogonal to those of any other association.  In other words, there
was probably no need to make these into dispatching operations.  And
you probably wouldn't want subclasses to alter the way these
operations behaved by introducing overriding implementations for them.

In fact, I also conceded the possibility that, for some applications,
association operations didn't even need to be primitive or
inheritable.  That's why it was a viable alternative to off-load
these operations to child units, where the "withing" problem
disappears.  Or even to off-load the whole association itself into
an association package.

But now I'm beginning to think that there may be applications where
those assumptions are actually invalid.  In fact, there might be
occasions where you *do* want to make association operations into
primitive, inherited-but-overridable, dispatching operations.  I think
I've been subconsciously groping toward that intuition all this time,
without realizing it.

Oh, don't get me wrong: *Structurally*, I don't think a subclass
should do anything different about setting up the pointers for an
association.  One way or another, association operations in a
subclass should satisfy the mutual-pointing invariant condition, most
likely by just invoking inherited forms of these operations.  (For
that matter, a hidden implementation for these inherited operations
could take advantage of your mixin technique.)

BUT, beyond purely structural considerations, a subclass might
introduce other *behavioral* variations on what happens when an
association is set up (or taken apart).  In fact, these differences
may involve interactions between the association in question and
_other_ _associations_ _the_ _class_ _is_ _involved_ _in_.  In other
words, associations might not always be so orthogonal after all.

As an example, consider these possible application requirements:

   "Whenever any Employee is assigned a new Office, the Manager who
    immediately supervises that Employee shall be notified of the move 
    (via an appropriate Memo generated by the system)."

   "Whenever a Manager is assigned a new Office, all the Employees
    who are immediate subordinates of that Manager shall be notified of
    the move (via an appropriate Memo generated by the system)."

Here we have a situation where an event affecting one association
(Employee gets assigned a new Office) can involve traversing another
association (find and notify the Employee's supervising Manager),
and can involve additional behavior at a subclass level (if an Employee
happens to be a Manager, also find and notify that Manager's subordinate
Employees).

But if this kind of situation is the case, then the whole issue of
inlining becomes a moot point.  You can't do a statically-determined
optimization like inlining if you're in a dynamically-determined
situation like dispatching.

Moreover, consider this possibility:

   "Offices shall be distinguished into Doorless_Offices (i.e., 
    industrial "cattlepens" formed out of modular partitions) versus
    Doored_Offices (actual rooms with solid walls and doors).  Since the
    latter are highly desirable these shall be preferentially assigned
    to Managers.  There shall be a prioritized list of Managers waiting
    for Doored_Offices.  Whenever a Doored_Office becomes available,
    either because of new construction/remodeling, or because a
    previous occupant Employee moves out, the next Manager on the waiting
    list shall be notified (via an appropriate Memo generated by the system)."

Now, when we disassociate an Employee from an Office, we not only need
to dispatch on the type of Employee, but we also need to dispatch on
the type of Office.  The fact that there are *two* classes to dispatch
on makes mutual recursion even more necessary -- such an operation
would be a "multimethod".  It's illegal in Ada9X to have a single
operation dispatch against more than one class.  But it is perfectly
okay to have two operations working in concert, each operation
dispatching against only one of the classes.

>      According to ME ;-) the association package "owns" the Attribute
>fields and is the only one to monkey with them, and this is the right
>and proper approach in Ada 9X.  It is different, but it seems better
>from an encapsulation point of view.

I agree ... as long as the association truly is a separate abstraction
within the problem domain, one that is indeed orthogonal to any other.
But I think that there might be some applications where this is not
the case.  Or rather, only the *structural* aspects of an association
might be truly orthogonal and separable, but the overall *behavior*
connected with an association might not be.

In other words, I'd say your technique is *a* "right and proper Ada9X
approach", but not necessarily *the* "right and proper Ada9X approach"
for all applications.  Be careful: We've been criticizing other
languages for forcing us to accept only "One True Way".  Let's not
simply replace "THEIR One True Way" with "OUR One True Way."  Ada is a
general purpose language with a lot of expressive power.  Its features
ought to be able to support many different styles of design, and even
allow the fruitful merging of different styles.

>With the Smalltalk or C++ model
>large and complex object implementations soon get buried in
>interactions between different components of an object.  In this
>model, each abstraction takes care of its own.

And I think this is a very good thing, a true benefit of your
technique ... as long as these associations are truly separable
abstractions.  But there may be situations where they would not be
separable, and only the classes themselves would be truly separable as
abstractions.  In such cases, the reason we couldn't address the
association operations totally in isolation wouldn't be because of any
artefact of our chosen style of software design, but because of the
irreducible complexity of the problem domain itself.  As Brooks said,
there's "No Silver Bullet" that can eliminate that sort of complexity,
it just has to be dealt with.

We've been staring for so long at this wall of "how to get two types
in two different packages to point to each other", that we've
forgotten that there may be other walls we need to cut through -- and
even some floors and ceilings, too, if we want to install stairwells
and elevators.  My deferred-coupling-via-generics technique really
addresses a broader set of problems than just mutually-pointing types.
It provides a solution for any situation where two or more
abstractions need to be mutually dependent on each other, and the
dependency needs to be a public feature of their respective interfaces
(and perhaps even a primitive feature), yet the different abstractions
still need to be encapsulated in separate packages.

>      I left some stuff out here for simplicity, but in a "real"
>implementation of this idea, I would insist that both object be
>derived from Controlled, or Limited Controlled, 

Total agreement here.

>and I would insure
>that there were no dangling pointers when an object was destroyed, and
>that copying an object did not copy the assignments. (In a many-to-one
>or many-to-many implementation the policy would be different of
>course.)  In other words, fix all those bugs before they occur, and
>transparent to the user of the abstraction.

Couldn't agree with you more.

[snip]

>  > Interesting interpretation.  I didn't think there was any trouble
>  > with returning "null".  Clients could just interpret a "null"
>  > value as meaning that E isn't associated with any Target.  But
>  > that's okay -- you just have a slightly different abstraction in
>  > mind than I have.

>   Major difference, but subtle in its way.  I hid the "pointer"
>types, so all external interfaces deal with objects, not pointers to
>objects.  Yes, we know that what gets passed around is a reference,
>so there is no extra calling overhead, 

In that case, it is quite a major difference.  My assumption was that
a "Get" operation would return a value that gave complete access to
the associated object as a *variable*, so that a client doing a
traversal would then be able to invoke operations that could modify
the state of that object, if need be.  In other words, the return
value would be a "name" that designated an object, rather than the
"value" (state) of object itself.  Since it is possible that there
might not yet be any object assigned along a given association (e.g.,
a particular Employee might not have an Office yet), it is possible
that the "name" retrieved by a Get would be "null" (or the moral
equivalent of that), designating "no object at all."

Now, I may be confused, but I always thought that a function call
could only act as the name of a *constant*, not the name of a
variable.  The only way the return result of a function call could
designate a variable would be if the return type were actually an
access type (or something readily translatable into one, such as one
of my Identity.Value types).  Has this changed in Ada9X?  From what
I can find in the RM9X;5.0, it seems not.

Unless your "object" types themselves act as the moral equivalent of
access types, magically designating your objects rather than being the
objects themselves, I think that the usefulness of your Get functions
will be very restricted.  In other words, your tagged types would have
to implement "reference semantics", in a way similar what Bill
Beckwith does in his IDL-to-Ada9X translation.  But if we're dealing
with reference semantics anyway, then the special value "reference to
no object at all" ought to be part of that semantics.

Taking a closer look at your code, I notice that your object types are
non-limited tagged types, rather than limited tagged types.  I thought
Ada9X could only guarantee pass-by-reference for a limited type, whereas
a non-limited type may be either pass-by-copy or pass-by-reference.

>but doing it this way
>eliminates--if done correctly--dangling pointer worries for users of
>the abstractions.  I didn't show all of that, but for example, the
>finalization operation on a Person would unset his office.  So there
>is no null value to return.

I'm not sure what the issue of "dangling pointers" has to do with the
choice of whether to hide the use of pointer types or expose the
possibility of null pointers.  I always thought that "dangling
pointers" referred to a situation where one object has already been
destroyed (e.g., via Unchecked_Deallocation), yet some other object
still has an access value designating it.  Certainly, the process of
finalizing any object should include disconnecting it from every
association it takes part in, so that the associated objects will no
longer retain pointers to it.  But doesn't that mean that those other
objects will then contain null pointers (assuming the cardinality is
"one")?

>					Robert I. Eachus

					John G. Volan

--------------------------------------------------------------------------------
--  Me : Person := (Name                => "John Volan",
--                  Company             => "Raytheon Missile Systems Division",
--                  E_Mail_Address      => "jgv@swl.msd.ray.com",
--                  Affiliation         => "Enthusiastic member of Team Ada!",
--                  Humorous_Disclaimer => "These opinions are undefined " &
--                                         "by my employer and therefore " &
--                                         "any use of them would be "     &
--                                         "totally erroneous.");
--------------------------------------------------------------------------------



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-28  4:28                         ` Jay Martin
  1994-10-28 10:52                           ` Robert I. Eachus
  1994-10-29  0:38                           ` Bob Duff
@ 1994-10-31 18:44                           ` John Volan
  2 siblings, 0 replies; 45+ messages in thread
From: John Volan @ 1994-10-31 18:44 UTC (permalink / raw)


jmartin@oahu.cs.ucla.edu (Jay Martin) writes:

>jgv@swl.msd.ray.com (John Volan) writes:

>>jmartin@baleen.cs.ucla.edu (Jay Martin) writes:

>>>(Can't do anything other than rant now (got to fix bugs)) Jay.
>>                               ^^^^      ^^^^^^^^^^^^^^^ 

>Oops, I was trying to say that, I was under time pressure to get something
>done and couldn't fully analyze your post but was going to respond later. 
>Instead I took a nasty swipe at CS (I am a CS PHD student).

>You think my last post was bad....

Re-reading your post a little more closely, I realize now that we may be
more in agreement than I initially thought.  Therefore, I humbly apologize
for the flame.  (However, the tone of your posts is pretty inflammatory ...
might I suggest cooling it off a bit?)

[snip]

>Since, I specified that only thing a package "forward" could contain
>is an incomplete type or a pointer type to one of these incomplete
>types.  Such alternate views would be pretty much useless for
>forwards.

The intent of my package "abstracts" was to allow exactly that kind
of thing (temporary tolerance for "incomplete" declarations), and in
fact, that's the "alternate view" that I was talking about.

>Only thing the package forward does is stop the compiler
>from giving errors for types that are going to be declared.  The same
>sort of thing could probably also be done by "type forward
>OtherPackage.AType;" shoved into the spec of dependent mutually
>recursive type.  Its saying "hey" I am going to declare this type
>later in the other package don't kill my compile.  

But this buries an inter-module dependency within a special kind of
type declaration that could then appear anywhere within a package.  How
about just leaving the issue of inter-module dependencies to context
clauses, where they've always been?  In other words, why couldn't we
have something like:

    with abstract of Employee;
    -- Only imports the abstract of package Employee, providing only
    -- incomplete views of some object types, plus some access types
    -- (i.e., whatever we actually put in the abstract).

versus:

    with Employee;
    -- Imports the full package spec of Employee as well as the abstract
    -- (if there is one), and so provides complete views of all types 
    -- declared publicly (and anything else declared there).

I think that your "package forwards" are pretty close to my "package
abstracts", but some of the details that you propose seem more ad-hoc,
given the design of Ada.

>Of course we could
>depend on a complex compilation system to solve all these mutually
>recursion problem, but forward is more in accordance with the simple
>Ada model of compiling in dependency order.  I thought I heard
>cross-package incomplete types in the early days of Ada9X? (Probably 
>dropped)  

If so, it was probably for good reasons.  Unfortunately, it doesn't
look like anyone fought to find an alternative that could avoid those
problems (whatever they were).  Maybe the package abstracts concept
is a step closer to that ideal alternative.  I don't know.

>>>3. No.

>>Why not?  Why do we have to make a *special exception* in this case,
>>for a feature that ought to be *orthogonal* to this?  Is it just
>>because someone like you doesn't want to be bothered about thinking
>>things through?

>Orthogonality is crap.  It used as a excuse, "well we have this
>feature so we must have this feature.  This feature has to be
>seemlessly integrated with that feature and we need this other
>feature to do it!  Hey we can throw in this capability for almost
>free!".  

Orthogonality is not an excuse to add ad-hoc features.  Done right, it
can simplify the design of a language, and *reduce* the need for
ad-hoc features.  But to do it right, the features have to be cast in
such a way as to be truly orthogonal to each other, and thus truly
*composable*.  If you do find that you have to add ad-hoc special
cases and restrictions when you try to compose features that were
supposed to be orthogonal, it may be a sign that the way you split up
the language is flawed.

>In my opinion, the first reaction to whether an arbitrary feature A
>"package forward" works with feature B "generic packages" should be
>no.  The compiler can just say "package forwards cannot be generic
>(RM5.2.23.3)".  We can not just make the argument, due to
>orthogonanlity....  We must weigh whether it is worth the extra
>complexity/danger given typical usage.  Likewise, we shouldn't say
>that "We can't add that feature because due to orthogonality, it
>implies this, this and this must be inserted which makes the original
>proposal too obese".

Or perhaps there is third alternative: Perhaps we can formulate the
new feature in such a way that does not disturb the old features and
does not require a special-case restriction.  And perhaps, formulated
that way, the new feature can turn out to be extremely powerful for
many uses beyond those it was initially conceived for.  Perhaps the
"new" feature could even turn out to be just the thing that was needed
to *simplify* the whole design of the language, as well as the
compilers that support the language.  However, achieving something
like that requires a lot of deep thought and perhaps some research. It
cannot be slapped in on the spur of the moment.

[snip]

>Yahoo.  C gave me the power and flexiblity to make an embarassing 
>mistake. 

Interesting C bug.  But I would argue that this just shows that C's
"orthogonality" is "orthogonality done *wrong*".

[snip]

					John G. Volan

--------------------------------------------------------------------------------
--  Me : Person := (Name                => "John Volan",
--                  Company             => "Raytheon Missile Systems Division",
--                  E_Mail_Address      => "jgv@swl.msd.ray.com",
--                  Affiliation         => "Enthusiastic member of Team Ada!",
--                  Humorous_Disclaimer => "These opinions are undefined " &
--                                         "by my employer and therefore " &
--                                         "any use of them would be "     &
--                                         "totally erroneous.");
--------------------------------------------------------------------------------



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

* Re: gcc distribution (was: SOLVED! Decoupled Mutual Recursion Challenger)
  1994-10-31 14:13                               ` gcc distribution (was: SOLVED! Decoupled Mutual Recursion Challenger) Norman H. Cohen
@ 1994-11-02 14:14                                 ` Richard Kenner
  1994-11-04 23:56                                   ` Michael Feldman
  0 siblings, 1 reply; 45+ messages in thread
From: Richard Kenner @ 1994-11-02 14:14 UTC (permalink / raw)


In article <392u2l$jt4@watnews1.watson.ibm.com> ncohen@watson.ibm.com writes:
>This is distressing.  One of the things that most excited me about the
>GNAT project when I first heard about it was the prospect that an Ada
>compiler would be hidden in each standard gcc distribution, and thus
>serve as a Trojan horse to sneak Ada into the camps of the C programmers.

That's an interesting concept.

However, an increasing number of people are getting various CD-ROMS of
all the GNU tools together, so this is less of an issue.  Also, many
of the binary distributions may have all the compilers.

But for the official source distribution, one large file is a problem.
The GCC 2.6.1 distribution will be 7.1 MB.  0.7 MB of that is g++.  So
once that's split off, there'll be a 6.4 MB base compiler.

Then 0.7 MB for C++, 1.7 MB for Ada, and some unknown sizes for
Fortran, Chill, Pascal, and others.

All this stuff is getting up to something like 12 MB of compressed
tar.  That's getting to the point where you may not actually be able
to copy the full file before the network connection dies.

Also, there's the very serious problem of coordinating releases of all
of these language, which are being independently developed.

For GCC 2.6.0, we decided to set up a mechanism to enable other
languages, specifically such as Ada, to be able to be "dropped in" on
top of the base GCC distribution.

>Upon accidently discovering Ada compilers on their machines, gcc users,
>epsecially in academia might be tempted to try it out one day.
>Also, users would be more likely to download Ada source code if they were
>told, "You probably already have an Ada compiler on your machine that you
>never knew about," than if they were told, "You can obtain an Ada
>compiler by anonymous ftp as follows...." A tool readily at hand is much
>more likely to be tried out on a whim than one that must be retrieved
>over the net first.

Well, yes, but I'd guess that people who would be trying Ada "on whim"
are not likely to be those that will get excited by what they find.

Also, note that Ada and C++ will be on equal footing soon; neither will
come with the base GCC source distribution and both will have to be
copied over and dropped in.



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

* Re: SOLVED! Decoupled Mutual Recursion Challenger
  1994-10-28 18:46                             ` Jay Martin
@ 1994-11-02 14:56                               ` Robert I. Eachus
  0 siblings, 0 replies; 45+ messages in thread
From: Robert I. Eachus @ 1994-11-02 14:56 UTC (permalink / raw)


In article <38rguj$9cd@oahu.cs.ucla.edu> jmartin@oahu.cs.ucla.edu (Jay Martin) writes:

  > Could you give an example of how you could shoot yourself in the foot
  > using the package forward idea.  How do you implement mutual recursion
  > using straight Ada83 derived types?  The abstract type solution and
  > downcasting are not deemed very exceptable by many of the lang.ada
  > participants.  Jay

    The representations CAN'T be mutually recursive without some
variant records and other tricks.  The package forward idea would
allow such declarations. (There is no easy place to decide that you
have such a loop.)  On the other hand, even in Ada 83 it is possible
to defer the actual declaration of the record object corresponding to
the type to the body of the package.  If you do this, you get pointer
semantics for objects of the type, which may have to be adjusted in
the interface, but--especially if you make the type limited--that is
not a major issue.

    Yes, yes.  If you want to have a primitive operation on Office
which returns a Person and vice-versa, you can do it in one package
spec, or three, or four, but not two.  I still fail to understand the
degree of mouth frothing directed at this "weakness" of Ada.  As we
have seen in the past several weeks, Ada provides lots of different
ways of modeling this system.  That there are some models in other
languages which can be duplicated more easily than others should not
come as a surprise.  Let's focus on the "right" way to do it in Ada
instead.


--

					Robert I. Eachus

with Standard_Disclaimer;
use  Standard_Disclaimer;
function Message (Text: in Clever_Ideas) return Better_Ideas is...



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

* Re: gcc distribution (was: SOLVED! Decoupled Mutual Recursion Challenger)
  1994-11-02 14:14                                 ` Richard Kenner
@ 1994-11-04 23:56                                   ` Michael Feldman
  0 siblings, 0 replies; 45+ messages in thread
From: Michael Feldman @ 1994-11-04 23:56 UTC (permalink / raw)


In article <3986rv$fr9@cmcl2.NYU.EDU>,
Richard Kenner <kenner@lab.ultra.nyu.edu> wrote:
>In article <392u2l$jt4@watnews1.watson.ibm.com> ncohen@watson.ibm.com writes:
>>This is distressing.  One of the things that most excited me about the
>>GNAT project when I first heard about it was the prospect that an Ada
>>compiler would be hidden in each standard gcc distribution, and thus
>>serve as a Trojan horse to sneak Ada into the camps of the C programmers.
>
Indeed, Robert Dewar used to say,

"When GNAT becomes part of the gcc distribution, nobody will ever have
to ask how to get Ada. They will have to ask how to NOT get Ada."

(This is a pretty direct quote from Robert.)

Oh, well, the best-laid plans etc...

Mike Feldman



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

end of thread, other threads:[~1994-11-04 23:56 UTC | newest]

Thread overview: 45+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
1994-10-12 22:49 SOLVED! Decoupled Mutual Recursion Challenger John Volan
1994-10-17 15:48 ` John Volan
1994-10-17 17:55   ` Bob Duff
1994-10-17 20:52     ` John Volan
1994-10-17 22:10       ` Bob Duff
1994-10-18 22:17         ` John Volan
1994-10-19  1:01           ` Bob Duff
1994-10-19  4:45             ` Jay Martin
1994-10-19 14:38               ` Mark A Biggar
     [not found]                 ` <38fi4r$l81@oahu.cs.ucla.edu>
1994-10-24 11:49                   ` Mutual Recursion Challenge Robert I. Eachus
1994-10-24 20:32                     ` John Volan
1994-10-26 11:42                       ` Generic association example (was Re: Mutual Recursion Challenge) Robert I. Eachus
1994-10-26 23:21                         ` John Volan
1994-10-27 10:53                           ` Robert I. Eachus
1994-10-31 17:34                             ` John Volan
1994-10-27 14:37                           ` Mark A Biggar
1994-10-24 17:42                   ` SOLVED! Decoupled Mutual Recursion Challenger John Volan
1994-10-24 22:37                     ` Jay Martin
1994-10-25  5:47                       ` Matt Kennel
1994-10-25 10:04                         ` David Emery
1994-10-25 16:43                         ` John Volan
1994-10-27  4:25                           ` Rob Heyes
1994-10-28  9:03                             ` Mutual Recursion (was Re: SOLVED! Decoupled Mutual Recursion Challenger) Robert I. Eachus
1994-10-28 15:04                             ` SOLVED! Decoupled Mutual Recursion Challenger Robb Nebbe
1994-10-25 15:54                       ` John Volan
1994-10-26  1:24                         ` Bob Duff
1994-10-28  4:28                         ` Jay Martin
1994-10-28 10:52                           ` Robert I. Eachus
1994-10-28 18:46                             ` Jay Martin
1994-11-02 14:56                               ` Robert I. Eachus
1994-10-29  0:38                           ` Bob Duff
1994-10-29  7:26                             ` Jay Martin
1994-10-29 11:59                             ` Richard Kenner
1994-10-31 13:17                               ` Robert Dewar
1994-10-31 14:13                               ` gcc distribution (was: SOLVED! Decoupled Mutual Recursion Challenger) Norman H. Cohen
1994-11-02 14:14                                 ` Richard Kenner
1994-11-04 23:56                                   ` Michael Feldman
1994-10-31 18:44                           ` SOLVED! Decoupled Mutual Recursion Challenger John Volan
1994-10-20 11:25               ` Robb Nebbe
1994-10-20 19:19                 ` John Volan
1994-10-26  0:07                 ` Mark S. Hathaway
1994-10-26 18:48                 ` gamache
1994-10-27  2:15                   ` John Volan
     [not found]           ` <CxwGJF.FwB@ois.com>
1994-10-19 16:35             ` John Volan
1994-10-17 22:54   ` Cyrille Comar

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