comp.lang.ada
 help / color / mirror / Atom feed
* Generics with concrete and class-wide types
@ 2008-03-31 20:22 Maciej Sobczak
  2008-03-31 23:38 ` Adam Beneschan
                   ` (3 more replies)
  0 siblings, 4 replies; 11+ messages in thread
From: Maciej Sobczak @ 2008-03-31 20:22 UTC (permalink / raw)


Consider a generic subprogram that makes sense for arguments of both
class-wide type and a concrete type.

As a motivating example, there might be a hierarchy of iterator types
rooted in some imaginary Iterator type that is itself defined in the
generic package with the element type as its own formal parameter.
There are concrete iterator types that are derived from this root
Iterator type (exactly: from some instantiation thereof).

There might be also a generic subprogram that operates on the iterator
given as its parameter. This subprogram takes two formal generic
parameters: the element type and the iterator type.

Now - on one hand it makes sense to have a hierarchy of iterators and
benefit from loose coupling and other features of OO, but on the other
hand the iterators themselves can be lightweight objects that are used
in tight loops and we can expect them to be fast, therefore we could
benefit from *avoiding* the dynamic dispatch if there is enough
context to do so.

Both make sense, depending on the context at the call site.

To achieve both benefits the user might instantiate the subprogram for
the Iterator'Class type (to be exact: for the 'Class of some
instantiation of Iterator) in the context where only a class-wide type
is available, like within some other polymorphic subprogram; and for
the concrete type, like My_Concrete_Iterator, in the context where the
concrete type is available, with the hope that such an instantiation
can be more easily inlined.

The sketch of types involved is:

generic
  type T is private; -- element type
package Iterators is
  type Iterator is interface;
  function Get (I : Iterator) return T is abstract;
  -- and so on for other operations...
end Iterators;

and at the user side (let's suppose the user works with Integers
only):

package body My_Stuff is
  package Iterators_Integer is new Iterators (T => Integer);
  type My_Concrete_Iterator is new Iterators_Integer.Iterator with ...

  overriding function Get (I : My_Concrete_Iterator) return Integer;
  -- and so on for other operations...

end My_Stuff;

Now, the generic subprogram that operates on the given iterator,
*without* using dynamic dispatch, can have the following form:

generic
  type Element is private;
  type Iterator_Type (<>) is private;
  with function Get (I : Iterator_Type) return Element is <>;
  -- and so on for all other operations that are needed by this
subprogram
procedure Some_Procedure (I : in Iterator_Type);

This works fine for direct instantiation with My_Concrete_Iterator:

procedure SP is new Some_Procedure
  (T => Integer, Iterator_Type => My_Concrete_Iterator);

The problem is that I failed to instantiate Some_Procedure for
Iterator_Integer.Iterator'Class, which I could then reuse for
My_Concrete_Iterator as well as for My_Other_Concrete_Iterator and so
on:

-- does not compile:
procedure SP is new Some_Procedure
  (T => Integer, Iterator_Type => Iterator_Integer'Class); -- Bang!

Bang, because relevant iterator operations cannot be found - the ones
that are found have *wrong signatures*.

Separate version of Some_Procedure can be written for polymorphic
operations:

generic
  type Element is private;
  with package Its is new Iterators (T => Element);
  -- no need to enumerate any operations, the interface serves its
purpose
procedure Some_Procedure (I : in Its.Iterator'Class);

This works fine when some instantiation of base Iterator type is
given:

procedure SP is new Some_Procedure
  (T => Integer, Its => Iterators_Integer);

and then SP can be used with My_Concrete_Iterator, presumably
dispatching on all calls to iterator in its body.

My expectation is that there should be a way to implement only one
generic procedure that can be instantiated for both concrete types and
for 'Class type.
Otherwise, I would need to provide both versions of Some_Procedure,
which not only looks like unnecessary duplication of code (the
implementations would be even textually identical!), but also seems to
be impossible - for some reason these two versions cannot exist in the
same package. What the heck?

I did not expect two orthogonal language features (generics and OO) to
interact in such a way.
Is there a good solution to this problem?

--
Maciej Sobczak * www.msobczak.com * www.inspirel.com



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

* Re: Generics with concrete and class-wide types
  2008-03-31 20:22 Generics with concrete and class-wide types Maciej Sobczak
@ 2008-03-31 23:38 ` Adam Beneschan
  2008-04-01 20:10   ` Randy Brukardt
  2008-04-01  0:23 ` Randy Brukardt
                   ` (2 subsequent siblings)
  3 siblings, 1 reply; 11+ messages in thread
From: Adam Beneschan @ 2008-03-31 23:38 UTC (permalink / raw)


On Mar 31, 1:22 pm, Maciej Sobczak <see.my.homep...@gmail.com> wrote:

> Consider a generic subprogram that makes sense for arguments of both
> class-wide type and a concrete type.

[snip]

> Now, the generic subprogram that operates on the given iterator,
> *without* using dynamic dispatch, can have the following form:
>
> generic
>   type Element is private;
>   type Iterator_Type (<>) is private;
>   with function Get (I : Iterator_Type) return Element is <>;
>   -- and so on for all other operations that are needed by this
> subprogram
> procedure Some_Procedure (I : in Iterator_Type);
>
> This works fine for direct instantiation with My_Concrete_Iterator:
>
> procedure SP is new Some_Procedure
>   (T => Integer, Iterator_Type => My_Concrete_Iterator);
>
> The problem is that I failed to instantiate Some_Procedure for
> Iterator_Integer.Iterator'Class, which I could then reuse for
> My_Concrete_Iterator as well as for My_Other_Concrete_Iterator and so
> on:
>
> -- does not compile:
> procedure SP is new Some_Procedure
>   (T => Integer, Iterator_Type => Iterator_Integer'Class); -- Bang!
>
> Bang, because relevant iterator operations cannot be found - the ones
> that are found have *wrong signatures*.

[snip]

At first, I thought it might be possible to do this, without
duplicating code, by writing a second generic package specifically for
class-wide types that would instantiate Some_Procedure.  Something
like this:

    generic
        type Element is private;
        type Iterator_Root is tagged private;
        with function Get (I : in Iterator_Root) return Element is <>;
        ... other operations
    package SP_For_Class is
        procedure Some_Procedure_Class (I : in Iterator_Root'Class);
    end SP_For_Class;

    with Some_Procedure;
    package body SP_For_Class is
        function Dispatching_Get (I : in Iterator_Root'Class)
                    return Element is
        begin
            return Get (I);
        end Dispatching_Get;
        ... similarly for other operations
        procedure SP_Inst is new Some_Procedure
            (Element, Iterator_Root'Class,
             Dispatching_Get, ...other operations);
        procedure Some_Procedure_Class (I : in Iterator_Root'Class)
            renames SP_Inst;
    end SP_For_Class;

Then for a concrete type, the programmer would instantiate
Some_Procedure; for a class-wide type, the programmer would
instantiate SP_For_Class, and then if Inst is the instance,
Inst.Some_Procedure_Class would be the equivalent procedure.
SP_For_Class would be sort of a wrapper, but it wouldn't need to
duplicate any of the logic from Some_Procedure.

The problem I ran into was the line "return Get(I)" fails because Get
is not a primitive operation of Iterator_Root and thus is not seen as
a dispatching operation.

What's missing here is a way to specify a generic formal subprogram
that must be a primitive operation of some tagged type (possibly a
generic formal tagged type), so that in the body of the generic the
formal subprogram will be treated as a dispatching operation; in an
instantiation, of course, the actual subprogram would have to meet the
criterion.  It seems like this might be a useful feature in some
cases besides this one (although I can't think of one offhand), but
I can see how it would be difficult to work this into the syntax.
(Especially if the generic formal subprogram has two different
parameter or result tagged types; you'd need a way to tell it which
type the subprogram must be a primitive operation of.)

(P.S. It seems like we had a discussion on Ada-Comment some years ago
about the sort of issue Maciej mentions, at least with regard to the
"=" function.  Some programmers were writing code, which GNAT accepted
due a bug, where generics declared

  with function "=" (Left, Right : T) is <>;

and then the generic was instantiated with some class-wide type for
T.  It
seemed like there was some sympathy for allowing this or providing for
a capability that would make this work, but not enough sympathy for
anyone to actually do anything about it.  Bob Duff, does this ring a
bell at all?)

                                -- Adam



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

* Re: Generics with concrete and class-wide types
  2008-03-31 20:22 Generics with concrete and class-wide types Maciej Sobczak
  2008-03-31 23:38 ` Adam Beneschan
@ 2008-04-01  0:23 ` Randy Brukardt
  2008-04-01  3:57   ` Eric Hughes
  2008-04-01  7:22 ` Georg Bauhaus
  2008-04-01  9:42 ` Dmitry A. Kazakov
  3 siblings, 1 reply; 11+ messages in thread
From: Randy Brukardt @ 2008-04-01  0:23 UTC (permalink / raw)


"Maciej Sobczak" <see.my.homepage@gmail.com> wrote in message
news:279b6f4f-36cf-446f-8b54-fd72b957b22f@i7g2000prf.googlegroups.com...
> Consider a generic subprogram that makes sense for arguments of both
> class-wide type and a concrete type.
...
> The problem is that I failed to instantiate Some_Procedure for
> Iterator_Integer.Iterator'Class, which I could then reuse for
> My_Concrete_Iterator as well as for My_Other_Concrete_Iterator and so
> on:
>
> -- does not compile:
> procedure SP is new Some_Procedure
>   (T => Integer, Iterator_Type => Iterator_Integer'Class); -- Bang!
>
> Bang, because relevant iterator operations cannot be found - the ones
> that are found have *wrong signatures*.

Right. This seems related to the problem mentioned in AI05-0071-1. (That AI
is still under construction, but it also is about operations having the
wrong signatures.) Since I'm not sure how that AI is going to be fixed, it's
not clear to me if it will cover this case or not. But perhaps you should
submit a question to Ada Comment so that it gets considered as well.

                                      Randy.





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

* Re: Generics with concrete and class-wide types
  2008-04-01  0:23 ` Randy Brukardt
@ 2008-04-01  3:57   ` Eric Hughes
  2008-04-01  6:58     ` christoph.grein
  0 siblings, 1 reply; 11+ messages in thread
From: Eric Hughes @ 2008-04-01  3:57 UTC (permalink / raw)


"Maciej Sobczak" <see.my.homep...@gmail.com> wrote in message
> Bang, because relevant iterator operations cannot be found - the ones
> that are found have *wrong signatures*.

On Mar 31, 6:23 pm, "Randy Brukardt" <ra...@rrsoftware.com> wrote:
> Right. This seems related to the problem mentioned in AI05-0071-1.

To my eye, it's also related to the discussion I was in recently
involving generic parameters, where the issue was hypothetical, but
also involved symbol mappings.  I've thought a lot about this thread,
and rather than start with a long discussion, I think a small riddle
is in order, one which seems to cut to the center of the problem.

Is it possible to get both dispatching and non-dispatching calls on a
single type (expressed as a single formal parameter) within a generic?

Eric



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

* Re: Generics with concrete and class-wide types
  2008-04-01  3:57   ` Eric Hughes
@ 2008-04-01  6:58     ` christoph.grein
  0 siblings, 0 replies; 11+ messages in thread
From: christoph.grein @ 2008-04-01  6:58 UTC (permalink / raw)


This works:

package Classwide is

  function Get (Iterator: My_Stuff.My_Iterator'Class) return Integer;

  procedure Classwide_Procedure is new Some_Procedure
    (Element       => Integer,
     Iterator_Type => My_Stuff.My_Iterator'Class,
     Get           => Get);

end Classwide;
package body Classwide is

  function Get (Iterator: My_Stuff.My_Iterator'Class) return Integer
is
  begin
    return My_Stuff.Get (Iterator);
  end Get;

end Classwide;



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

* Re: Generics with concrete and class-wide types
  2008-03-31 20:22 Generics with concrete and class-wide types Maciej Sobczak
  2008-03-31 23:38 ` Adam Beneschan
  2008-04-01  0:23 ` Randy Brukardt
@ 2008-04-01  7:22 ` Georg Bauhaus
  2008-04-01  9:42 ` Dmitry A. Kazakov
  3 siblings, 0 replies; 11+ messages in thread
From: Georg Bauhaus @ 2008-04-01  7:22 UTC (permalink / raw)


Maciej Sobczak wrote:
> Consider a generic subprogram that makes sense for arguments of both
> class-wide type and a concrete type.

> -- does not compile:
> procedure SP is new Some_Procedure
>   (T => Integer, Iterator_Type => Iterator_Integer'Class); -- Bang!

FWIW, the following triggers everything from a running
program to an Ada 95 compiler internal assertion failure
(in case the iterator object is initialized in the main
procedure).


with Iterators, Some_Procedure;
procedure Test_Iterators is

   package II is new Iterators(Integer);

   procedure Context_Conc(it: II.Conc_Iter) is
      procedure SP is new Some_Procedure
        (Integer, II, Iterator_Type => II.Conc_Iter);
   begin
      SP(it);
   end Context_Conc;

   procedure Context_Disp(it: II.Iterator'Class) is
      procedure SP is new Some_Procedure
        (Integer, II, Iterator_Type => II.Iterator'Class);
   begin
      SP(it);
   end Context_Disp;

   c: II.Conc_Iter := II.Conc_Iter'(El => new Integer'(42));
begin
   Context_Conc(c);
   Context_Disp(c);
end Test_Iterators;

with Iterators;
generic
   type T is private;
   with package Integer_Iterators is new Iterators(T);
   type Iterator_Type(<>) is new Integer_Iterators.Iterator with private;
procedure Some_Procedure (it: Iterator_Type);


generic
   type T is private;
package Iterators is

   type Iterator is abstract tagged null record;
   function Get(It: Iterator) return T is abstract;

   type T_Ptr is access constant T;
   type Conc_Iter is new Iterator with
      record
         El: T_Ptr;
      end record;

   function Get(It: Conc_Iter) return T;

end Iterators;


procedure Some_Procedure (It: Iterator_Type) is
   use type Integer_Iterators.Iterator;
   Tmp: T;
begin
   Tmp := Get(It);
end Some_Procedure;


package body Iterators is

   function Get (It: Conc_Iter) return T is
   begin
      return It.El.all;
   end Get;

end Iterators;



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

* Re: Generics with concrete and class-wide types
  2008-03-31 20:22 Generics with concrete and class-wide types Maciej Sobczak
                   ` (2 preceding siblings ...)
  2008-04-01  7:22 ` Georg Bauhaus
@ 2008-04-01  9:42 ` Dmitry A. Kazakov
  2008-04-01  9:51   ` Maciej Sobczak
  3 siblings, 1 reply; 11+ messages in thread
From: Dmitry A. Kazakov @ 2008-04-01  9:42 UTC (permalink / raw)


On Mon, 31 Mar 2008 13:22:10 -0700 (PDT), Maciej Sobczak wrote:

> Consider a generic subprogram that makes sense for arguments of both
> class-wide type and a concrete type.
> 
> As a motivating example, there might be a hierarchy of iterator types
> rooted in some imaginary Iterator type that is itself defined in the
> generic package with the element type as its own formal parameter.
> There are concrete iterator types that are derived from this root
> Iterator type (exactly: from some instantiation thereof).
> 
> There might be also a generic subprogram that operates on the iterator
> given as its parameter. This subprogram takes two formal generic
> parameters: the element type and the iterator type.
> 
> Now - on one hand it makes sense to have a hierarchy of iterators and
> benefit from loose coupling and other features of OO, but on the other
> hand the iterators themselves can be lightweight objects that are used
> in tight loops and we can expect them to be fast, therefore we could
> benefit from *avoiding* the dynamic dispatch if there is enough
> context to do so.
>
> Both make sense, depending on the context at the call site.
> 
> To achieve both benefits the user might instantiate the subprogram for
> the Iterator'Class type (to be exact: for the 'Class of some
> instantiation of Iterator) in the context where only a class-wide type
> is available, like within some other polymorphic subprogram; and for
> the concrete type, like My_Concrete_Iterator, in the context where the
> concrete type is available, with the hope that such an instantiation
> can be more easily inlined.

Just a small side note. If you care about performance you should do exactly
the opposite you tried to, i.e. you should instantiate it with a specific
type rather than with a class of. Doing so, you will force the compiler to
resolve primitive operations statically without dispatching overhead. When
you use class-wide, then its will dispatch somewhere, maybe later in the
bodies, maybe more than once.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



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

* Re: Generics with concrete and class-wide types
  2008-04-01  9:42 ` Dmitry A. Kazakov
@ 2008-04-01  9:51   ` Maciej Sobczak
  2008-04-01 10:53     ` Dmitry A. Kazakov
  0 siblings, 1 reply; 11+ messages in thread
From: Maciej Sobczak @ 2008-04-01  9:51 UTC (permalink / raw)


On 1 Kwi, 11:42, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
wrote:

> Just a small side note. If you care about performance you should do exactly
> the opposite you tried to, i.e. you should instantiate it with a specific
> type rather than with a class of.

This is exactly what I want to do.
If I have the knowledge of the specific iterator type, I want to
instantiate the subprogram with this specific type to facilitate
direct dispatch and code inlining.
When the only this I have is 'Class, then I want to instantiate the
subprogram with what I have and agree for indirect dispatch to
iterator operations within the subprogram body.

The question is whether it is possible in Ada without walking on the
edge of compiler conformance - and in particular without accidentally
benefiting from any compiler bug that will bite me later on when it's
fixed.
Yes, some bugs can be harmful after they are fixed. :-)

I will try the scheme proposed by Georg.

--
Maciej Sobczak * www.msobczak.com * www.inspirel.com



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

* Re: Generics with concrete and class-wide types
  2008-04-01  9:51   ` Maciej Sobczak
@ 2008-04-01 10:53     ` Dmitry A. Kazakov
  0 siblings, 0 replies; 11+ messages in thread
From: Dmitry A. Kazakov @ 2008-04-01 10:53 UTC (permalink / raw)


On Tue, 1 Apr 2008 02:51:19 -0700 (PDT), Maciej Sobczak wrote:

> On 1 Kwi, 11:42, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
> wrote:
> 
>> Just a small side note. If you care about performance you should do exactly
>> the opposite you tried to, i.e. you should instantiate it with a specific
>> type rather than with a class of.
> 
> This is exactly what I want to do.
> If I have the knowledge of the specific iterator type, I want to
> instantiate the subprogram with this specific type to facilitate
> direct dispatch and code inlining.
> When the only this I have is 'Class, then I want to instantiate the
> subprogram with what I have and agree for indirect dispatch to
> iterator operations within the subprogram body.
> 
> The question is whether it is possible in Ada without walking on the
> edge of compiler conformance - and in particular without accidentally
> benefiting from any compiler bug that will bite me later on when it's
> fixed.
> Yes, some bugs can be harmful after they are fixed. :-)
> 
> I will try the scheme proposed by Georg.

You could also do:

generic
   type Element_Type is private; -- element type
package Iterators is
   type Iterator_Type is interface;
   function Get (I : Iterator_Type) return Element_Type is abstract;
   -- and so on for other operations...
end Iterators;

with Iterators;
generic
   with package Root_Iterators is new Iterators (<>);
   type Base_Iterator_Type is
      new Root_Iterators.Iterator_Type with private;
package Some_Procedure is
   type Iterator_Type is new Base_Iterator_Type with null record;
   procedure Foo (I : Iterator_Type); -- Primitive operation when tagged
end Some_Procedure;

You have to derive from Iterator_Type in order to declare another primitive
operation Foo. The element type comes with the instance of Iterators which
is the first formal parameter. The second formal parameter is a
non-abstract iterator type implementing the iterator interface. This schema
allows to cascade packages like Some_Procedure taking
Some_Procedure_1_Instance.Iterator_Type as the parameter for
Some_Procedure_2_Instance. Base_Iterator_Type could also be abstract, but
that would more difficult to trace instantiation problems.

Example:

with Ada.Finalization;
with Iterators, Some_Procedure;

procedure Test_Iterators is

   ------ Iterators to tagged elements -----------
   type My_Element is new Ada.Finalization.Controlled with null record;
   package My_Element_Iterators is new Iterators (My_Element);

   package Firewall_1 is
      type My_Iterator is
         new My_Element_Iterators.Iterator_Type with null record;
      function Get (I : My_Iterator) return My_Element;
   end Firewall_1;

   package My_Element_SP is
      new Some_Procedure (My_Element_Iterators, Firewall_1.My_Iterator);

   ------- Iterators to integer elements -------
   package Integer_Iterators is new Iterators (Integer);
   package Firewall_2 is
      type Integer_Iterator is
         new Integer_Iterators.Iterator_Type with null record;
      function Get (I : Integer_Iterator) return Integer;
   end Firewall_2;

   package Integer_SP is
      new Some_Procedure (Integer_Iterators, Firewall_2.Integer_Iterator);

   ---------------------------------------------------------
   package body Firewall_1 is
      function Get (I : My_Iterator) return My_Element is
      begin
         return (Ada.Finalization.Controlled with null record);
      end Get;
   end Firewall_1;

   package body Firewall_2 is
      function Get (I : Integer_Iterator) return Integer is
      begin
         return 5;
      end Get;
   end Firewall_2;
   
begin
   null;
end Test_Iterators;

The packages like Firewall are needed to freeze the element type.
Otherwise, the compiler would yell that

    function Get (I : My_Iterator) return My_Element;

is doubly dispatching.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



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

* Re: Generics with concrete and class-wide types
  2008-03-31 23:38 ` Adam Beneschan
@ 2008-04-01 20:10   ` Randy Brukardt
  2008-04-01 21:17     ` Adam Beneschan
  0 siblings, 1 reply; 11+ messages in thread
From: Randy Brukardt @ 2008-04-01 20:10 UTC (permalink / raw)


"Adam Beneschan" <adam@irvine.com> wrote in message
news:f0879dc0-7498-48f7-8d44-9856316d35ce@s19g2000prg.googlegroups.com...
...
> What's missing here is a way to specify a generic formal subprogram
> that must be a primitive operation of some tagged type (possibly a
> generic formal tagged type),

No, it's not missing. That's what abstract formal subprograms are for. See
specifically 12.6(8.4-8.5/2).

I'm not sure that helps in this case, but feel free to try. ;-).

                       Randy.

P.S. These were totally my idea, originally in the context of
Generic_Dispatching_Constructor (which I also dreamt up after a conversation
with Steve Baird and Tucker Taft on the factory problem). I off-handedly
suggested that the "magic" embodied in the original version of that generic
could be given language status, and I was stunned to find that everyone
thought that was a good idea. (Especially after the death of defaults for
generic formal parameters.) And voila! Abstract formal subprograms. I'm glad
that you like them. ;-)





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

* Re: Generics with concrete and class-wide types
  2008-04-01 20:10   ` Randy Brukardt
@ 2008-04-01 21:17     ` Adam Beneschan
  0 siblings, 0 replies; 11+ messages in thread
From: Adam Beneschan @ 2008-04-01 21:17 UTC (permalink / raw)


On Apr 1, 1:10 pm, "Randy Brukardt" <ra...@rrsoftware.com> wrote:
> "Adam Beneschan" <a...@irvine.com> wrote in message
>
> news:f0879dc0-7498-48f7-8d44-9856316d35ce@s19g2000prg.googlegroups.com...
> ...
>
> > What's missing here is a way to specify a generic formal subprogram
> > that must be a primitive operation of some tagged type (possibly a
> > generic formal tagged type),
>
> No, it's not missing. That's what abstract formal subprograms are for. See
> specifically 12.6(8.4-8.5/2).

Ah ha, thank you!  No, I didn't realize that's what they were for,
perhaps because "abstract" isn't a synonym for "dispatching", but it
makes sense now that you pointed me in the right direction.


> I'm not sure that helps in this case, but feel free to try. ;-).

I think it does help.  If my previous example were changed to this:

    generic
        type Element is private;
        type Iterator_Root is tagged private;
        with function Get (I : in Iterator_Root) return Element
           is abstract <>;  -- unspeakable syntax??
        ... other operations
    package SP_For_Class is
        procedure Some_Procedure_Class (I : in Iterator_Root'Class);
    end SP_For_Class;

    with Some_Procedure;
    package body SP_For_Class is
        function Dispatching_Get (I : in Iterator_Root'Class)
                    return Element is
        begin
            return Get (I);
        end Dispatching_Get;
        ... similarly for other operations
        procedure SP_Inst is new Some_Procedure
            (Element, Iterator_Root'Class,
             Dispatching_Get, ...other operations);
        procedure Some_Procedure_Class (I : in Iterator_Root'Class)
            renames SP_Inst;
    end SP_For_Class;

then the call to Get inside Dispatching_Get would be legal.  Then, in
Maciej's case, if he wants a Some_Procedure instance that would work
on a class-wide type and dispatch, he could instantiate SP_For_Class
with the specific type, and then Some_Procedure_Class declared in the
instance would be the procedure he's looking for.  At least I think
this would work---I haven't tried it.  It's a little klunky to declare
the SP_For_Class generic, but at least it wouldn't involve any
duplicated code.  And if it works, it will work without waiting for a
solution to AI05-71.

                               -- Adam



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

end of thread, other threads:[~2008-04-01 21:17 UTC | newest]

Thread overview: 11+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2008-03-31 20:22 Generics with concrete and class-wide types Maciej Sobczak
2008-03-31 23:38 ` Adam Beneschan
2008-04-01 20:10   ` Randy Brukardt
2008-04-01 21:17     ` Adam Beneschan
2008-04-01  0:23 ` Randy Brukardt
2008-04-01  3:57   ` Eric Hughes
2008-04-01  6:58     ` christoph.grein
2008-04-01  7:22 ` Georg Bauhaus
2008-04-01  9:42 ` Dmitry A. Kazakov
2008-04-01  9:51   ` Maciej Sobczak
2008-04-01 10:53     ` Dmitry A. Kazakov

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