comp.lang.ada
 help / color / mirror / Atom feed
* Persistence of limited tagged types
@ 2003-04-07 12:47 Jano
  2003-04-07 14:47 ` Nick Roberts
  2003-04-07 18:11 ` Stephen Leake
  0 siblings, 2 replies; 21+ messages in thread
From: Jano @ 2003-04-07 12:47 UTC (permalink / raw)


Hello,

I've read several past threads about this, but to reassure me I want to 
bring it back again, or at least to know the typical workaround.

I have a heterogeneous collection by means of class wide access types, 
where the accessed types itself are descendants of a 

type Object is abstract tagged limited private;

These objects are kind of state-dependent, and I have an abstract method 
which serializes an Object to disk. So far, so good.

The problem comes when I want to reconstruct the collection from disk. I 
can't think of a mean to obtain a valid allocated pointer initialized 
with some dispatching call.

A neat solution could be a function that returned an allocated pointer 
given a tag, but AFAIK there is not such a function.

I think that my only option is to make the type non-limited and couple 
it somehow with the limited components. It's not a so hard change at 
this stage, but I'd be glad to know other people takes on this problem.

Thanks,

-- 
-------------------------
Jano
402450.at.cepsz.unizar.es
-------------------------



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

* Re: Persistence of limited tagged types
  2003-04-07 12:47 Persistence of limited tagged types Jano
@ 2003-04-07 14:47 ` Nick Roberts
  2003-04-09 10:05   ` Nick Roberts
                     ` (2 more replies)
  2003-04-07 18:11 ` Stephen Leake
  1 sibling, 3 replies; 21+ messages in thread
From: Nick Roberts @ 2003-04-07 14:47 UTC (permalink / raw)


On Mon, 7 Apr 2003 14:47:36 +0200, Jano <nono@celes.unizar.es> wrote:

> I've read several past threads about this, but to reassure me I want to 
> bring it back again, or at least to know the typical workaround.
>
> I have a heterogeneous collection by means of class wide access types, 
> where the accessed types itself are descendants of a
>
> type Object is abstract tagged limited private;
>
> These objects are kind of state-dependent, and I have an abstract method 
> which serializes an Object to disk. So far, so good.
>
> The problem comes when I want to reconstruct the collection from disk. I 
> can't think of a mean to obtain a valid allocated pointer initialized 
> with some dispatching call.
>
> A neat solution could be a function that returned an allocated pointer 
> given a tag, but AFAIK there is not such a function.
>
> I think that my only option is to make the type non-limited and couple it 
> somehow with the limited components. It's not a so hard change at this 
> stage, but I'd be glad to know other people takes on this problem.

Speaking (all right writing) 'off the cuff' as it were, my attitude is that 
limited types are (supposed to be) inherently not the kind of types which 
are persistent (serialisable).

I would expect your type (hierarchy) to be non-limited if it is 
serialisable; possibly this is a slightly purist point of view.

For serialisation, I would normally expect T'Read and T'Write to be 
redefined for every type T in the hierarchy whenever the defaults did not 
suffice (or some guarantees of portability or longevity, of data or code or 
both, are required). A suitable T'Read and T'Write will also have to be 
available for every type T of all the discriminants used in all the types 
in the hierarchy.

Then you simply use T'Output to write out a value of a type in the 
hierarchy, and T'Input (a function) to read in a value (of any type) in the 
hierarchy.

If you really intend to be serialising limited types, I suspect that (both 
theoretically and practically) you need to have intermediate non-limited 
types to help you. Serialisation of a limited type will then involve: 
conversion to and from a suitable non-limited type; serialisation of the 
non-limited type.

To illustrate this idea, suppose you have a limited type Bank_Account. To 
save an object of type Bank_Account, you might first convert the object, 
perhaps as a result of an operation such as Suspend_Account, to a value of 
the non-limited type Suspended_Account (which might contain the balance of 
the account, a list of outstanding transactions, and so on), and then save 
the Suspended_Account. To load a Bank_Account, you would first load a 
Suspended_Account, and then construct an object of type Bank_Account from 
it, perhaps with an operation such as Reactivate_Account.

My point is that you cannot (generally) just naively save and load a 
limited type (such as Bank_Account), because more logic than that is almost 
certain to be required (for example, the actions of suspending and 
reactivating the account).

Hope this helps.

-- 
Nick Roberts
Jabber: debater@charente.de [ICQ: 159718630]



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

* Re: Persistence of limited tagged types
  2003-04-07 12:47 Persistence of limited tagged types Jano
  2003-04-07 14:47 ` Nick Roberts
@ 2003-04-07 18:11 ` Stephen Leake
  2003-04-07 19:07   ` Hyman Rosen
  2003-04-07 20:17   ` Robert Spooner
  1 sibling, 2 replies; 21+ messages in thread
From: Stephen Leake @ 2003-04-07 18:11 UTC (permalink / raw)


Jano <nono@celes.unizar.es> writes:

> Hello,
> 
> I've read several past threads about this, but to reassure me I want to 
> bring it back again, or at least to know the typical workaround.
> 
> I have a heterogeneous collection by means of class wide access types, 
> where the accessed types itself are descendants of a 
> 
> type Object is abstract tagged limited private;
> 
> These objects are kind of state-dependent, and I have an abstract method 
> which serializes an Object to disk. So far, so good.
> 
> The problem comes when I want to reconstruct the collection from disk. I 
> can't think of a mean to obtain a valid allocated pointer initialized 
> with some dispatching call.
> 
> A neat solution could be a function that returned an allocated pointer 
> given a tag, but AFAIK there is not such a function.

The external representation of the type needs to be significantly
different than the internal representation. In particular, the
external representation needs to have a "readable" representation of
the tag.

You will have to write a function that reads the external
representation of the tag, allocates an object of the appropriate
type, and returns the pointer. Yes, this function must be changed
every time you add a new tag.

-- 
-- Stephe



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

* Re: Persistence of limited tagged types
  2003-04-07 18:11 ` Stephen Leake
@ 2003-04-07 19:07   ` Hyman Rosen
  2003-04-07 22:09     ` Jano
  2003-04-07 20:17   ` Robert Spooner
  1 sibling, 1 reply; 21+ messages in thread
From: Hyman Rosen @ 2003-04-07 19:07 UTC (permalink / raw)


Stephen Leake wrote:
> You will have to write a function that reads the external
> representation of the tag, allocates an object of the appropriate
> type, and returns the pointer. Yes, this function must be changed
> every time you add a new tag.

This is known as the Factory pattern. Instead of changing the
function for each new tag, you can have the package that defines
the type enroll a read method into a table of methods. Then the
factory reads the external tag representation, looks it up in
the table, and calls the method if it's present.




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

* Re: Persistence of limited tagged types
  2003-04-07 18:11 ` Stephen Leake
  2003-04-07 19:07   ` Hyman Rosen
@ 2003-04-07 20:17   ` Robert Spooner
  2003-04-07 21:14     ` Stephen Leake
  1 sibling, 1 reply; 21+ messages in thread
From: Robert Spooner @ 2003-04-07 20:17 UTC (permalink / raw)
  To: Stephen Leake

Stephen Leake wrote:
> Jano <nono@celes.unizar.es> writes:
> 
> 
>>Hello,
>>
>>I've read several past threads about this, but to reassure me I want to 
>>bring it back again, or at least to know the typical workaround.
>>
>>I have a heterogeneous collection by means of class wide access types, 
>>where the accessed types itself are descendants of a 
>>
>>type Object is abstract tagged limited private;
>>
>>These objects are kind of state-dependent, and I have an abstract method 
>>which serializes an Object to disk. So far, so good.
>>
>>The problem comes when I want to reconstruct the collection from disk. I 
>>can't think of a mean to obtain a valid allocated pointer initialized 
>>with some dispatching call.
>>
>>A neat solution could be a function that returned an allocated pointer 
>>given a tag, but AFAIK there is not such a function.
> 
> 
> The external representation of the type needs to be significantly
> different than the internal representation. In particular, the
> external representation needs to have a "readable" representation of
> the tag.
> 
> You will have to write a function that reads the external
> representation of the tag, allocates an object of the appropriate
> type, and returns the pointer. Yes, this function must be changed
> every time you add a new tag.
> 

I think that if you use 'output to put the object onto the disk, it will 
put the external representation of the tag out with it. Then if you use 
'imput to read it back in as an object of type Object'class you will get 
what you're looking for.

Bob
-- 
                             Robert L. Spooner
                      Registered Professional Engineer
                        Associate Research Engineer
                   Intelligent Control Systems Department

          Applied Research Laboratory        Phone: (814) 863-4120
          The Pennsylvania State University  FAX:   (814) 863-7841
          P. O. Box 30
          State College, PA 16804-0030       rls19@psu.edu




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

* Re: Persistence of limited tagged types
  2003-04-07 20:17   ` Robert Spooner
@ 2003-04-07 21:14     ` Stephen Leake
  2003-04-08 12:56       ` Robert Spooner
  0 siblings, 1 reply; 21+ messages in thread
From: Stephen Leake @ 2003-04-07 21:14 UTC (permalink / raw)


Robert Spooner <rls19@psu.edu> writes:

> I think that if you use 'output to put the object onto the disk, it
> will put the external representation of the tag out with it. Then if
> you use 'imput to read it back in as an object of type Object'class
> you will get what you're looking for.

That is certainly true. The trick is to get an object of type
Object'class; it's an unconstrained type, so you can't just do:

An_Object : Object'class;

In practice, you need to know the concrete object type _before_ you
call 'input, so you can allocate (or declare) an object of that type.
That means some representation of the tag must be stored in the
external file separately from the object, so you can read it first.

-- 
-- Stephe



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

* Re: Persistence of limited tagged types
  2003-04-07 19:07   ` Hyman Rosen
@ 2003-04-07 22:09     ` Jano
  2003-04-08 13:58       ` Matthew Heaney
  0 siblings, 1 reply; 21+ messages in thread
From: Jano @ 2003-04-07 22:09 UTC (permalink / raw)


Hyman Rosen dice...
> Stephen Leake wrote:
> > You will have to write a function that reads the external
> > representation of the tag, allocates an object of the appropriate
> > type, and returns the pointer. Yes, this function must be changed
> > every time you add a new tag.
> 
> This is known as the Factory pattern. Instead of changing the
> function for each new tag, you can have the package that defines
> the type enroll a read method into a table of methods. Then the
> factory reads the external tag representation, looks it up in
> the table, and calls the method if it's present.

I like this solution. With very little overwork.

-- 
-------------------------
Jano
402450.at.cepsz.unizar.es
-------------------------



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

* Re: Persistence of limited tagged types
  2003-04-07 21:14     ` Stephen Leake
@ 2003-04-08 12:56       ` Robert Spooner
  2003-04-08 13:41         ` Jano
  0 siblings, 1 reply; 21+ messages in thread
From: Robert Spooner @ 2003-04-08 12:56 UTC (permalink / raw)
  To: Stephen Leake


Stephen Leake wrote:
> Robert Spooner <rls19@psu.edu> writes:
> 
> 
>>I think that if you use 'output to put the object onto the disk, it
>>will put the external representation of the tag out with it. Then if
>>you use 'imput to read it back in as an object of type Object'class
>>you will get what you're looking for.
> 
> 
> That is certainly true. The trick is to get an object of type
> Object'class; it's an unconstrained type, so you can't just do:
> 
> An_Object : Object'class;
> 
> In practice, you need to know the concrete object type _before_ you
> call 'input, so you can allocate (or declare) an object of that type.
> That means some representation of the tag must be stored in the
> external file separately from the object, so you can read it first.
> 

The input attribute is a function, so you can initialize an object of 
the class using it without a priori knowledge of the type.

Bob
-- 
                             Robert L. Spooner
                      Registered Professional Engineer
                        Associate Research Engineer
                   Intelligent Control Systems Department

          Applied Research Laboratory        Phone: (814) 863-4120
          The Pennsylvania State University  FAX:   (814) 863-7841
          P. O. Box 30
          State College, PA 16804-0030       rls19@psu.edu




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

* Re: Persistence of limited tagged types
  2003-04-08 12:56       ` Robert Spooner
@ 2003-04-08 13:41         ` Jano
  0 siblings, 0 replies; 21+ messages in thread
From: Jano @ 2003-04-08 13:41 UTC (permalink / raw)


Robert Spooner dice...
> 
> Stephen Leake wrote:
> > Robert Spooner <rls19@psu.edu> writes:
> > 
> > 
> >>I think that if you use 'output to put the object onto the disk, it
> >>will put the external representation of the tag out with it. Then if
> >>you use 'imput to read it back in as an object of type Object'class
> >>you will get what you're looking for.
> > 
> > 
> > That is certainly true. The trick is to get an object of type
> > Object'class; it's an unconstrained type, so you can't just do:
> > 
> > An_Object : Object'class;
> > 
> > In practice, you need to know the concrete object type _before_ you
> > call 'input, so you can allocate (or declare) an object of that type.
> > That means some representation of the tag must be stored in the
> > external file separately from the object, so you can read it first.
> > 
> 
> The input attribute is a function, so you can initialize an object of 
> the class using it without a priori knowledge of the type.

Yes, the whole matter arises because we are discussing limited types 
that can't be created that way.

-- 
-------------------------
Jano
402450.at.cepsz.unizar.es
-------------------------



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

* Re: Persistence of limited tagged types
  2003-04-07 22:09     ` Jano
@ 2003-04-08 13:58       ` Matthew Heaney
  2003-04-10 11:41         ` Julio Cano
  0 siblings, 1 reply; 21+ messages in thread
From: Matthew Heaney @ 2003-04-08 13:58 UTC (permalink / raw)


Jano <nono@celes.unizar.es> wrote in message news:<MPG.18fc158bd901913d9896db@News.CIS.DFN.DE>...
> Hyman Rosen dice...
> > 
> > This is known as the Factory pattern. Instead of changing the
> > function for each new tag, you can have the package that defines
> > the type enroll a read method into a table of methods. Then the
> > factory reads the external tag representation, looks it up in
> > the table, and calls the method if it's present.
> 
> I like this solution. With very little overwork.

This will be the subject of the Dear Ada column in next issue of Ada
Letters.

Basically, each type will register a factory function like this:

  function New_T return T'Class;

Implemented something like this (say, for NT, which derives from T):

  function New_T return T'Class is
  begin
     return NT'(T with I, J, K);
  end;

Actually, your type is limited, so it would be something like:

  function New_T return T_Class_Access is
     O : constant NT_Access := new NT;
  begin
     --init O
     return T_Class_Access (O);
  end;

You have a map whose keys are type string, and whose element is a
pointer to the factory function:

   type Factory_Type is access function return T_Class_Access;

   package Table_Types is
     new Charles.Maps.Sorted.Strings.Unbounded (Factory_Type);

   Table : Table_Types.Container_Type;

Now a type registers its factory function:

   procedure Register 
     (Key : Ada.Tags.Tag;
      Factory : Factory_Type) is
   begin
      Insert (Table, External_Tag (Key), Factory);
   end;

Now, given a tag, you can look up the factory function, and create a
new object, e.g.

   function New_T (Key : Ada.Tags.Tag) return T_Class_Access is
      I : constant Iterator_Type := Find (Table, External_Tag (Key));
   begin
      if I = Back (Table) then
        raise Tag_Error;
      end if;

      declare
         Factory : constant Factory_Type := Element (I);
      begin
         return Factory.all;  --invoke factory function
      end;
   end New_T;

If you're streaming off of disk, then the tag is probably stored in
the stream in its external form, so one possibility is:

   function New_T (Stream : access Root_Stream_Type'Class) 
      return T_Class_Access is

      Key : constant String := Read (Stream);  --or whatever
      I : constant Iterator_Type := Find (Table, Key);
   begin
      ...
      declare
         Factory : constant Factory_Type := Element (I);
      begin
         return Factory (Stream); --invoke factory function
      end;
   end New_T;

Here, we pass the stream to the factory function, and let it finish
reading the object out of the stream.

The map container in the example is from the Charles library.

http://home.earthlink.net/~matthewjheaney/charles/

You can use either the sorted or hashed version of the map, that has
type String as the key.



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

* Re: Persistence of limited tagged types
  2003-04-07 14:47 ` Nick Roberts
@ 2003-04-09 10:05   ` Nick Roberts
  2003-04-10  3:32     ` tmoran
  2003-04-09 23:09   ` Matthew Heaney
  2003-04-10  1:12   ` Matthew Heaney
  2 siblings, 1 reply; 21+ messages in thread
From: Nick Roberts @ 2003-04-09 10:05 UTC (permalink / raw)


I hope it won't be taken too amiss that a post a piece of code here.

This little test program is to illustrate the how the 'lifetime' concept (a 
fairly significant concept in computer science these days) applies to the 
persistence of 'live' objects.

A live object is an object which parallels (analogises, models) some 
conceptual or real-world entity, and therefore cannot validly be copied 
(unless it is to model the parallel entity also being duplicated). Live 
objects, therefore (to my mind) correspond, in Ada terms, to a limited type 
(hierarchy).

Live objects, because they cannot just be copied, cannot be directly 
archived or restored, but must first be properly deactivated and 
reactivated, by specific operations that have the correct specific logic 
for each live (limited) type.

In my example 'lifetime' package I have declared roots for the live objects 
(Root_Object) and for a co-hierarchy of their mothballed equivalents 
(Root_Parcel). To deactivate a live object you must call Mothball, and to 
reactivate one you must call Reinstate. (These names may not be the most 
appropriate, but they do at least suggest their function.)

There are many other aspects to the lifetime concept, but the conversion 
between different forms of an object is one of the basic aspects.


----------------------------------------------------------------------
-- Test out lifetime and persistence concepts in Ada.

with Ada.Streams.Stream_IO, Ada.Text_IO, Ada.Unchecked_Deallocation;
use Ada.Streams.Stream_IO, Ada.Text_IO;

procedure Persist1 is


   ------------------------------------------------------------
   package Lifetime is

      type Root_Object is abstract tagged limited private;
      type Object_Ref is access Root_Object'Class;

      type Root_Parcel is abstract tagged private;
      type Parcel_Ref is access Root_Parcel'Class;

      procedure Mothball (Object: in out Root_Object;
                          Parcel: out    Parcel_Ref) is abstract;

      procedure Reinstate (Object: out Object_Ref;
                           Parcel: in  Root_Parcel) is abstract;

   private

      type Root_Object is abstract tagged limited null record;
      type Root_Parcel is abstract tagged null record;

   end Lifetime;


   ------------------------------------------------------------
   package Banking is

      type Active_Account is new Lifetime.Root_Object with private;

      type Dead_Account is new Lifetime.Root_Parcel with private;

      function New_Account (Initial_Balance: in Integer) return 
Lifetime.Object_Ref;

      function Current_Balance (Account: in Active_Account) return Integer;

      procedure Mothball (Active: in out Active_Account;
                          Dead:   out    Lifetime.Parcel_Ref);

      procedure Reinstate (Active: out Lifetime.Object_Ref;
                           Dead:   in  Dead_Account);

   private

      type Active_Account is new Lifetime.Root_Object with
         record
            Balance: Integer;
         end record;

      type Dead_Account is new Lifetime.Root_Parcel with
         record
            Balance: Integer;
         end record;

   end Banking;


   ------------------------------------------------------------
   package body Banking is


      function New_Account (Initial_Balance: in Integer) return 
Lifetime.Object_Ref is

         Account: Lifetime.Object_Ref := new Active_Account;

      begin
         Active_Account(Account.all).Balance := Initial_Balance;
         return Account;
      end;


      function Current_Balance (Account: in Active_Account) return Integer 
is
      begin
         return Account.Balance;
      end;


      procedure Mothball (Active: in out Active_Account;
                          Dead:   out    Lifetime.Parcel_Ref) is
      begin
         -- here need to be actions to suspend the Active account
         Dead := new Dead_Account'( Lifetime.Root_Parcel with Balance => 
Active.Balance );
      end;


      procedure Reinstate (Active: out Lifetime.Object_Ref;
                           Dead:   in  Dead_Account) is
      begin
         Active := new Active_Account;
         Active_Account(Active.all).Balance := Dead.Balance;
         -- here need to be actions to reactivate Active account
      end;


   end banking;


   ------------------------------------------------------------
   type Object_Array is
      array (Positive range <>) of Lifetime.Object_Ref;


   procedure Free is
      new 
Ada.Unchecked_Deallocation(Lifetime.Root_Object'Class,Lifetime.Object_Ref);


   procedure Save (File: in out Ada.Streams.Stream_IO.File_Type;
                   Item: in out Object_Array) is

      Temp: Lifetime.Parcel_Ref;

   begin
      for i in Item'Range loop
         Lifetime.Mothball(Item(i).all,Temp);
         Free(Item(i)); -- make sure it is deallocated
         Lifetime.Root_Parcel'Class'Output(Stream(File),Temp.all);
      end loop;
   end Save;


   procedure Load (File: in out Ada.Streams.Stream_IO.File_Type;
                   Item: out    Object_Array;
                   Last: out    Natural) is

      i: Natural := Item'First-1;

   begin
      while not End_of_File(File) loop
         declare
            subtype LRPC is Lifetime.Root_Parcel'Class;
            Temp: Lifetime.Parcel_Ref := new LRPC'(LRPC'Input(Stream(File))) 
;
         begin
            i := i+1;
            Lifetime.Reinstate(Item(i),Temp.all);
         end;
      end loop;
      Last := i;
   end Load;


   Accounts: Object_Array(1..10);
   Datafile: Ada.Streams.Stream_IO.File_Type;
   Last: Natural;

begin

   Put("Creating test array ...");
   for i in Accounts'Range loop
      Accounts(i) := Banking.New_Account(i);
   end loop;
   Put(" Done.");
   New_Line;

   Put("Saving test array ...");
   Create(Datafile,Out_File,"TESTDAT1.BIN");
   Save(Datafile,Accounts);
   Close(Datafile);
   Put(" Done.");
   New_Line;

   Put("Reloading test array ...");
   Open(Datafile,In_File,"TESTDAT1.BIN");
   Load(Datafile,Accounts,Last);
   Close(Datafile);
   Put(" Done.");
   New_Line;

   Put("Checking test array ...");
   if Last /= Accounts'Last then
      Put(" *** FAILED!");
      goto Final_Stuff;
   end if;      for i in Accounts'Range loop
      if Banking.Current_Balance(Banking.Active_Account(Accounts(i).all)) 
/= i then
         Put(" *** FAILED!");
         goto Final_Stuff;
      end if;
   end loop;
   Put(" Done. Success!");

<<Final_Stuff>>
   New_Line;

end;
----------------------------------------------------------------------


Based on this idea, persistence of a live (limited) type will be done in 
two steps: the deactivation (mothballing) of the live type (derived from 
Root_Object) to get its storable equivalent (derived from Root_Parcel), and 
reactivation (reinstatement) of the stored equivalent to get back to the 
live object; the actual storage and retrieval of the storable (mothballed) 
types.

I think it is important not to confuse the two concepts of 
deactivation/reactivation of live (limited) objects and of persistence 
(which is really just the automatic, or transparent, storage and 
restoration of data).

Of course this little program is only a trivial test of the concept, but I 
think you will find it scales up nicely in practice.

Look particularly at the implementation of the Load and Save procedures, 
and how they use polymorphic (dispatching) calls both to obtain the 
appropriate input and output routines for objects of types derived from 
Root_Parcel and also to obtain the appropriate mothballing and 
reinstatement routines.

Hope this is of interest!


-- 
Nick Roberts
Jabber: debater@charente.de [ICQ: 159718630]



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

* Re: Persistence of limited tagged types
  2003-04-07 14:47 ` Nick Roberts
  2003-04-09 10:05   ` Nick Roberts
@ 2003-04-09 23:09   ` Matthew Heaney
  2003-04-10 14:40     ` Nick Roberts
  2003-04-10 18:49     ` Randy Brukardt
  2003-04-10  1:12   ` Matthew Heaney
  2 siblings, 2 replies; 21+ messages in thread
From: Matthew Heaney @ 2003-04-09 23:09 UTC (permalink / raw)


Nick Roberts <nickroberts@blueyonder.co.uk> wrote in message news:<oprm9kpdkkbqmqul@news.cis.dfn.de>...
> 
> Speaking (all right writing) 'off the cuff' as it were, my attitude is that 
> limited types are (supposed to be) inherently not the kind of types which 
> are persistent (serialisable).
> 
> I would expect your type (hierarchy) to be non-limited if it is 
> serialisable; possibly this is a slightly purist point of view.
 
Is T'Output available if type T is limited?

GNAT lets me declare an output operation:

  type T is limited null record;

  procedure Output 
    (Stream : access Root_Stream_Type'Class;
     Item   : in     T);

  for T'Output use Output;

but then it refuses to let me call it:

   O : T;
begin
   T'Output (Stream, O);
end;

I get an error message that "limited type T has no stream attributes."

However, if I define T'Write, then GNAT compiles

  T'Write (Stream, O);

without complaint.

What's up with that?  Is the expectation that T'Output can't be used
for a limited type?  Why does GNAT allow me to define the T'Output
stream attribute?



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

* Re: Persistence of limited tagged types
  2003-04-07 14:47 ` Nick Roberts
  2003-04-09 10:05   ` Nick Roberts
  2003-04-09 23:09   ` Matthew Heaney
@ 2003-04-10  1:12   ` Matthew Heaney
  2 siblings, 0 replies; 21+ messages in thread
From: Matthew Heaney @ 2003-04-10  1:12 UTC (permalink / raw)


Nick Roberts <nickroberts@blueyonder.co.uk> wrote in message news:<oprm9kpdkkbqmqul@news.cis.dfn.de>...
> 
> If you really intend to be serialising limited types, I suspect that (both 
> theoretically and practically) you need to have intermediate non-limited 
> types to help you. Serialisation of a limited type will then involve: 
> conversion to and from a suitable non-limited type; serialisation of the 
> non-limited type.

All types ultimately comprise primitive scalar types (as integer,
float, etc) and simple composite types (string, etc), so yes there
will be non-limited types involved.

What you'll probably have to do is "default construct" an instance,
and then call read as a post-initialization step, e.g.

function Input (Stream : access Root_Stream_Type'Class)
  return T_Class_Access is

  Key : constant String := String'Input (Stream);

  I : constant Iterator := Find (Map, Key);

  Factory : constant Factory_Type := Element (I);
begin
  return Factory (Stream);
end;

The factory for T would look something like:

function New_T (Stream : access Root_Stream_Type'Class)
  return T_Class_Access is

  O : constant T_Access := new T; --default value
begin
  Read (Stream, O.all);  --post-initialization
  return T_Class_Access (O);
end;



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

* Re: Persistence of limited tagged types
  2003-04-09 10:05   ` Nick Roberts
@ 2003-04-10  3:32     ` tmoran
  0 siblings, 0 replies; 21+ messages in thread
From: tmoran @ 2003-04-10  3:32 UTC (permalink / raw)


> Live objects, because they cannot just be copied, cannot be directly
> archived or restored, but must first be properly deactivated and
> reactivated, by specific operations that have the correct specific logic
> for each live (limited) type.
  That sounds like a Limited Controlled object.  Initialize creates
de novo or reads from disk to "activate" and Finalize deactivates,
storing appropriate reconstruction info on disk.



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

* Re: Persistence of limited tagged types
  2003-04-08 13:58       ` Matthew Heaney
@ 2003-04-10 11:41         ` Julio Cano
  2003-04-10 19:14           ` Jano
  0 siblings, 1 reply; 21+ messages in thread
From: Julio Cano @ 2003-04-10 11:41 UTC (permalink / raw)


Actualy I already posted a creational pattern like that when Jano (I
think it was him) asked for the first time how to instantiate the
types from tags.


mheaney@on2.com (Matthew Heaney) wrote in message news:<1ec946d1.0304080558.2df9c8c8@posting.google.com>...
> Jano <nono@celes.unizar.es> wrote in message news:<MPG.18fc158bd901913d9896db@News.CIS.DFN.DE>...
> > Hyman Rosen dice...
> > > 
> > > This is known as the Factory pattern. Instead of changing the
> > > function for each new tag, you can have the package that defines
> > > the type enroll a read method into a table of methods. Then the
> > > factory reads the external tag representation, looks it up in
> > > the table, and calls the method if it's present.
> > 
> > I like this solution. With very little overwork.
> 
> This will be the subject of the Dear Ada column in next issue of Ada
> Letters.
> 
> Basically, each type will register a factory function like this:
> 
>   function New_T return T'Class;
> 
> Implemented something like this (say, for NT, which derives from T):
> 
>   function New_T return T'Class is
>   begin
>      return NT'(T with I, J, K);
>   end;
> 
> Actually, your type is limited, so it would be something like:
> 
>   function New_T return T_Class_Access is
>      O : constant NT_Access := new NT;
>   begin
>      --init O
>      return T_Class_Access (O);
>   end;
> 
> You have a map whose keys are type string, and whose element is a
> pointer to the factory function:
> 
>    type Factory_Type is access function return T_Class_Access;
> 
>    package Table_Types is
>      new Charles.Maps.Sorted.Strings.Unbounded (Factory_Type);
> 
>    Table : Table_Types.Container_Type;
> 
> Now a type registers its factory function:
> 
>    procedure Register 
>      (Key : Ada.Tags.Tag;
>       Factory : Factory_Type) is
>    begin
>       Insert (Table, External_Tag (Key), Factory);
>    end;
> 
> Now, given a tag, you can look up the factory function, and create a
> new object, e.g.
> 
>    function New_T (Key : Ada.Tags.Tag) return T_Class_Access is
>       I : constant Iterator_Type := Find (Table, External_Tag (Key));
>    begin
>       if I = Back (Table) then
>         raise Tag_Error;
>       end if;
> 
>       declare
>          Factory : constant Factory_Type := Element (I);
>       begin
>          return Factory.all;  --invoke factory function
>       end;
>    end New_T;
> 
> If you're streaming off of disk, then the tag is probably stored in
> the stream in its external form, so one possibility is:
> 
>    function New_T (Stream : access Root_Stream_Type'Class) 
>       return T_Class_Access is
> 
>       Key : constant String := Read (Stream);  --or whatever
>       I : constant Iterator_Type := Find (Table, Key);
>    begin
>       ...
>       declare
>          Factory : constant Factory_Type := Element (I);
>       begin
>          return Factory (Stream); --invoke factory function
>       end;
>    end New_T;
> 
> Here, we pass the stream to the factory function, and let it finish
> reading the object out of the stream.
> 
> The map container in the example is from the Charles library.
> 
> http://home.earthlink.net/~matthewjheaney/charles/
> 
> You can use either the sorted or hashed version of the map, that has
> type String as the key.



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

* Re: Persistence of limited tagged types
  2003-04-09 23:09   ` Matthew Heaney
@ 2003-04-10 14:40     ` Nick Roberts
  2003-04-10 23:37       ` Robert A Duff
  2003-04-10 18:49     ` Randy Brukardt
  1 sibling, 1 reply; 21+ messages in thread
From: Nick Roberts @ 2003-04-10 14:40 UTC (permalink / raw)


On 9 Apr 2003 16:09:09 -0700, Matthew Heaney <mheaney@on2.com> wrote:

> Is T'Output available if type T is limited?

According to the RM95 (13.13 (36)) (which I'm certain you must have already 
consulted, Matt) the stream-oriented attributes (Read, Write, Input, 
Output) are defined for all types, but defaults are not provided for 
limited types.

> GNAT lets me declare an output operation:
>
> type T is limited null record;
>
> procedure Output (Stream : access Root_Stream_Type'Class;
> Item   : in     T);
>
> for T'Output use Output;
>
> but then it refuses to let me call it:
>
> O : T;
> begin
> T'Output (Stream, O);
> end;
>
> I get an error message that "limited type T has no stream attributes."
>
> However, if I define T'Write, then GNAT compiles
>
> T'Write (Stream, O);
>
> without complaint.
>
> What's up with that?  Is the expectation that T'Output can't be used
> for a limited type?  Why does GNAT allow me to define the T'Output
> stream attribute [but not call it]?

I don't immediately see how this (GNAT's) behaviour obeys the standard.

It could be argued that since T in this example is a definite type, it is 
not actually necessary to define or call T'Output, since T'Write could be 
defined and called instead with the same effect. But I don't see how this 
could permit GNAT to produce the error it does.

Perhaps I should ask which version of GNAT this was, and do some tests 
myself?

-- 
Nick Roberts
Jabber: debater@charente.de [ICQ: 159718630]



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

* Re: Persistence of limited tagged types
  2003-04-09 23:09   ` Matthew Heaney
  2003-04-10 14:40     ` Nick Roberts
@ 2003-04-10 18:49     ` Randy Brukardt
  1 sibling, 0 replies; 21+ messages in thread
From: Randy Brukardt @ 2003-04-10 18:49 UTC (permalink / raw)


Matthew Heaney wrote in message
<1ec946d1.0304091509.150cc6d7@posting.google.com>...
>Is T'Output available if type T is limited?
>
>GNAT lets me declare an output operation:
>
>  type T is limited null record;
>
>  procedure Output
>    (Stream : access Root_Stream_Type'Class;
>     Item   : in     T);
>
>  for T'Output use Output;
>
>but then it refuses to let me call it:
>
>   O : T;
>begin
>   T'Output (Stream, O);
>end;
>
>I get an error message that "limited type T has no stream attributes."
>
>What's up with that?  Is the expectation that T'Output can't be used
>for a limited type?  Why does GNAT allow me to define the T'Output
>stream attribute?

GNAT apparently has a bug here. Ada 95 always allowed calling of
redefined limited attributes; it's illegal to call ones that aren't
redefined.

The Corrigendum changed this some, so that there are now some cases
where you're allowed to call limited stream attributes even when they
weren't defined. However, that was pretty buggy (there are cases where
you're allowed to call something that doesn't exist), and we had to
change it all again for the amendment. But those cases don't apply here.
The current 13.13.2(36/1) allows this call, and the original 13.13.2(36)
did as well. So, I'd send a bug report to ACT.

(Note that the trouble with the various standards is with the class-wide
calls. I could imagine a compiler disallowing that; while the ARG has
approved rules that allow such calls, they won't be officially part of
the standard until the Amendment is finished. So a compiler wouldn't be
wrong to disallow them now.)

            Randy.







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

* Re: Persistence of limited tagged types
  2003-04-10 11:41         ` Julio Cano
@ 2003-04-10 19:14           ` Jano
  2003-04-11 12:54             ` Julio Cano
  0 siblings, 1 reply; 21+ messages in thread
From: Jano @ 2003-04-10 19:14 UTC (permalink / raw)


Julio Cano dice...
> Actualy I already posted a creational pattern like that when Jano (I
> think it was him) asked for the first time how to instantiate the
> types from tags.

I think that post get lost. I don't remember it and I think I would.

-- 
-------------------------
Jano
402450.at.cepsz.unizar.es
-------------------------



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

* Re: Persistence of limited tagged types
  2003-04-10 14:40     ` Nick Roberts
@ 2003-04-10 23:37       ` Robert A Duff
  2003-04-11 16:39         ` Nick Roberts
  0 siblings, 1 reply; 21+ messages in thread
From: Robert A Duff @ 2003-04-10 23:37 UTC (permalink / raw)


Nick Roberts <nickroberts@blueyonder.co.uk> writes:

> According to the RM95 (13.13 (36)) (which I'm certain you must have
> already consulted, Matt) the stream-oriented attributes (Read, Write,
> Input, Output) are defined for all types, but defaults are not provided
> for limited types.

Be careful in "consulting the RM".  The Ada 95 RM is somewhat buggy in
this area, and there are some AI's published by the ARG on the subject.
If your compiler does not obey the AI's, you might want to complain to
your compiler vendor.

- Bob



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

* Re: Persistence of limited tagged types
  2003-04-10 19:14           ` Jano
@ 2003-04-11 12:54             ` Julio Cano
  0 siblings, 0 replies; 21+ messages in thread
From: Julio Cano @ 2003-04-11 12:54 UTC (permalink / raw)


Jano <nono@celes.unizar.es> wrote in message news:<MPG.18ffe0e4178127ab9896e0@News.CIS.DFN.DE>...
> Julio Cano dice...
> > Actualy I already posted a creational pattern like that when Jano (I
> > think it was him) asked for the first time how to instantiate the
> > types from tags.
> 
> I think that post get lost. I don't remember it and I think I would.

If i didn't make a mistake, here it is:

http://groups.google.com/groups?q=author:julius_bip%40yahoo.com&hl=en&lr=&ie=UTF-8&selm=8fe0b883.0302200738.35e427f9%40posting.google.com&rnum=2

Obviously this solution doesn't make use of streams, while the
solution of Matthew uses streams for persistence and tags.



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

* Re: Persistence of limited tagged types
  2003-04-10 23:37       ` Robert A Duff
@ 2003-04-11 16:39         ` Nick Roberts
  0 siblings, 0 replies; 21+ messages in thread
From: Nick Roberts @ 2003-04-11 16:39 UTC (permalink / raw)


On 10 Apr 2003 19:37:38 -0400, Robert A Duff <bobduff@shell01.TheWorld.com> 
wrote:

> Nick Roberts <nickroberts@blueyonder.co.uk> writes:
>
>> According to the RM95 (13.13 (36)) (which I'm certain you must have
>> already consulted, Matt) the stream-oriented attributes (Read, Write,
>> Input, Output) are defined for all types, but defaults are not provided
>> for limited types.
>
> Be careful in "consulting the RM".  The Ada 95 RM is somewhat buggy in
> this area, and there are some AI's published by the ARG on the subject.
> If your compiler does not obey the AI's, you might want to complain to
> your compiler vendor.

Well warned, Bob. I've had a peruse, and the relevant AIs seem to be as 
follows.


AI95-00108/08 says :-

For a type extension, the predefined Read attribute is defined to call
the Read of the parent type, followed by the Read of the non-inherited
components, if any, in canonical order.  The analogous rule applies to
the Write attribute.

The Input and Output attributes are not inherited by a type extension.
Default stream attributes are never inherited; rather, the default
implementation for the derived type is used.

The stream attributes must work properly for every language-defined
nonlimited type.  For language-defined private types, the output
generated by the Write attribute is not specified, but it must be
readable by the Read attribute.


AI95-00137/08 says :-

13.1(10) says:

  For an untagged derived type, no type-related representation items are
  allowed if the parent type is a by-reference type, or has any user- 
defined
  primitive subprograms.

This rule does not apply to an attribute_definition_clause for one of
the stream-oriented attributes Read, Write, Input, and Output.


AI95-00195/14 says :-

1 - When the predefined Input attribute creates an object, this object
undergoes default initialization and finalization.

2 - For the purposes of checking legality rules, it is necessary to 
determine
whether a stream-oriented attribute has been specified for a limited type
(13.13.2(9/1) and 13.13.2(36/1)). This is done by applying the normal
visibility rules to the attribute_definition_clause.

3 - For a limited tagged type T, if Read is available then T'Input is
available, even if it is not specified. Similarly, if Write is available 
then
T'Output is available. T'Class'Read, T'Class'Write, T'Class'Input and
T'Class'Output are available only if they are specified or the 
corresponding
specific attribute is available somewhere within the same list of 
declarations
as T.

4 - In the profiles of the stream-oriented attributes, the notation
"italicized T" refers to the base subtype for a scalar type, and to the 
first
subtype otherwise.

5 - In an attribute_definition_clause for a stream-oriented attribute, the
name shall not denote an abstract subprogram.

6 - The predefined Read attribute for composite types with defaulted
discriminants must ensure that, if exceptions are raised by the Read
attribute for some discriminant, the discriminants of the actual object
passed to Read are not modified. This may require the creation of an
anonymous object, which undergoes initialization and finalization.

7 - The predefined Read attribute for composite types with defaulted
discriminants must raise Constraint_Error if the discriminants found in the
stream differ from those of the actual parameter to Read, and this 
parameter
is constrained.

8 - If S is a subtype of an abstract type, an attribute_reference for 
S'Input
is illegal unless this attribute has been specified by an
attribute_definition_clause.

9 - The number of calls performed by the predefined implementation of the
stream-oriented attributes on the Read and Write operations of the stream 
type
is unspecified. An implementation may take advantage of this permission to
perform internal buffering. However, all the calls on the Read and Write
operations of the stream type needed to implement an explicit invocation of 
a
stream-oriented attribute must take place before this invocation returns.


AI95-00240/04 says :-

E.2.2(14) and E.2.3(14) should allow any type with available Read
and Write stream attributes.


None of these strike me as permitting GNAT's behaviour.

-- 
Nick Roberts
Jabber: debater@charente.de [ICQ: 159718630]



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

end of thread, other threads:[~2003-04-11 16:39 UTC | newest]

Thread overview: 21+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2003-04-07 12:47 Persistence of limited tagged types Jano
2003-04-07 14:47 ` Nick Roberts
2003-04-09 10:05   ` Nick Roberts
2003-04-10  3:32     ` tmoran
2003-04-09 23:09   ` Matthew Heaney
2003-04-10 14:40     ` Nick Roberts
2003-04-10 23:37       ` Robert A Duff
2003-04-11 16:39         ` Nick Roberts
2003-04-10 18:49     ` Randy Brukardt
2003-04-10  1:12   ` Matthew Heaney
2003-04-07 18:11 ` Stephen Leake
2003-04-07 19:07   ` Hyman Rosen
2003-04-07 22:09     ` Jano
2003-04-08 13:58       ` Matthew Heaney
2003-04-10 11:41         ` Julio Cano
2003-04-10 19:14           ` Jano
2003-04-11 12:54             ` Julio Cano
2003-04-07 20:17   ` Robert Spooner
2003-04-07 21:14     ` Stephen Leake
2003-04-08 12:56       ` Robert Spooner
2003-04-08 13:41         ` Jano

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