comp.lang.ada
 help / color / mirror / Atom feed
* Re: 16 bit integers in streams
  1997-09-25  0:00     ` Tucker Taft
@ 1997-09-25  0:00       ` Stephen Leake
  1997-09-26  0:00         ` Tucker Taft
  0 siblings, 1 reply; 7+ messages in thread
From: Stephen Leake @ 1997-09-25  0:00 UTC (permalink / raw)



Tucker Taft wrote:
> 
> Stephen Leake (Stephen.Leake@gsfc.nasa.gov) wrote:
> 
> : Ok, I understand the consistency issue. Apparently GNAT uses 16 bit > : base integers when I request them. I hearby request an option on 
> : ObjectAda (and therefore the AdaMagic front end?) to sacrifice 
> : efficient integer arithmetic, and give me 16 bit base integers (when 
> : appropriate), and therefore 16 bits in streams! Could pragma 
> : Optimize (Space) do this?
> 
> Gulp.  This would be a pretty big semantic effect for pragma Optimize.
> 
> The problem is that the representation used on streams is in one
> sense a very important "high-level" external effect, and in another
> sense something almost analagous to internal representation.

I assume size clauses control both the external and internal
representation; see below.

> I suspect the "right" solution is to consider the base range to be
> a 16 bit range for types like this, even though 32-bit arithmetic is
> used for them. We have already considered doing this, but haven't
> done it yet.  Of course, the longer we wait, the more people will 
> begin to rely on the current behavior...

Or complain about it :). Surely the intent of 'Read is to put the
_memory_ image of a type into the stream, not the _register_ image?
 
> Perhaps we could use an explicit size clause as a way to control
> the base range.  We have frequently debated the meaning of
> a "confirming" size clause.  Perhaps this could be one "real" effect
> of such a clause.  It's an intriguing thought...

This is definitely what I expect a size clause to mean; I'm telling the
compiler I want exactly 16 bits, anyplace it matters (including
streams). I assume that's what GNAT does now, although maybe GNAT is
also doing 16 bit arithmetic.

> --
> -Tucker Taft   stt@inmet.com   http://www.inmet.com/~stt/
> Intermetrics, Inc.  Burlington, MA  USA

-- 
- Stephe




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

* 16 bit integers in streams
@ 1997-09-25  0:00 Stephen Leake
  1997-09-25  0:00 ` Tucker Taft
  0 siblings, 1 reply; 7+ messages in thread
From: Stephen Leake @ 1997-09-25  0:00 UTC (permalink / raw)



I'm trying to use streams to read Microsoft Windows resources into Ada
types, so I can manipulate them. I've run into a problem reading 16 bit
integers. ObjectAda 7.1 under Windows 95 reads and writes four bytes (32
bits) to a stream for a 16 bit integer. GNAT 3.10 under Windows 95
writes two bytes to a stream for a 16 bit integer.

Here's code that demonstrates this:

with Ada.Streams; use Ada.Streams;
package Test_Streams is
   type Stream_Type is new Root_Stream_Type with null record;

   procedure Write
     (Stream : in out Stream_Type;
      Item   : in Stream_Element_Array);

   procedure Read
     (Stream : in out Stream_Type;
      Item   : out Stream_Element_Array;
      Last   : out Stream_Element_Offset);

end Test_Streams;

-----------------
with Ada.Text_IO; use Ada.Text_IO;
package body Test_Streams is

   procedure Put (Item : in Stream_Element_Array)
   is begin
      Put ("(");
      for I in Item'First .. Item'Last - 1 loop
         Put (Stream_Element'Image (Item (I)) & ", ");
      end loop;
      Put (Stream_Element'Image (Item (Item'last)) & ")");
   end Put;

   procedure Write
     (Stream : in out Stream_Type;
      Item   : in Stream_Element_Array)
   is begin
      Put (Item);
   end Write;

   -- dummy definition to override abstract Ada.Streams.Read
   procedure Read
     (Stream : in out Stream_Type;
      Item   : out Stream_Element_Array;
      Last   : out Stream_Element_Offset)
   is begin
      Item := (others => 1);
      Last := 0;
   end Read;

end Test_Streams;

-----------------
with Interfaces;
with Ada.Text_IO; use Ada.Text_IO;
with Test_Streams;
procedure Test
is
   Stream : aliased Test_Streams.Stream_Type;
begin
   Put_Line ("write 1 as 16 bit integer");
   Interfaces.Integer_16'Write (Stream'access,
Interfaces.Integer_16'(1));
end Test;

Compiled with GNAT 3.10 on Windows 95, then run, we get:

write 1 as 16 bit integer
( 1,  0)

This writes two bytes, as expected.

Compiled with ObjectAda 7.1 on Windows 95, then run, we get:

write 1 as 16 bit integer
( 1,  0,  0,  0)

This writes 4 bytes, or 32 bits.

This difference in behavior is allowed by RM 13.13.2 (9): "For
elementary types, the representation in terms of stream elements is
implementation defined." But it prevents using ObjectAda to read a
stream file written by GNAT. It also prevents reading Windows resources
directly. Here's an attempt to force ObjectAda to read a 16 bit integer:

with Ada.Streams;
package Interface_Streams is

   type Integer_16 is range -32768 .. 32767;
   for Integer_16'Size use 16;

   procedure Read_16
      (Stream : access Ada.Streams.Root_Stream_Type'Class;
       Item : out Integer_16);

   subtype Integer_16_Base is Integer_16'base;
   for Integer_16_Base'Read use Read_16;

   procedure Write_16
      (Stream : access Ada.Streams.Root_Stream_Type'Class;
       Item : in Integer_16);

   for Integer_16'Write use Write_16;

end Interface_Streams;

For both attribute definition clauses, ObjectAda 7.1 gives the error:

interface_streams.ads: Error: line 18 col 33 LRM:13.13.2(36), For an
attribute definition clause specifying a stream attribute for a scalar
type, the subtype  for the Item parameter must be the base subtype

Apparently ObjectAda uses a 32 bit base integer type, even when only 16
bits are requested. What is the rationale for this? Is it legal for
ObjectAda to reject these attribute definition clauses? What is the base
type of Integer_16?

I hope this issue can be addressed by the Uniformity Rapporteur Group;
it would be very nice if streams generated by one compiler/run-time
could be read by another. It would also be nice if a 16 bit integer
would read and write just 16 bits.

I just looked (on AdaHome) for the commentaries produced by the URG; I
found a bunch of AI's, but no UI's. Can someone point me to where the
URG output is?

-- 
- Stephe




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

* Re: 16 bit integers in streams
  1997-09-25  0:00 16 bit integers in streams Stephen Leake
@ 1997-09-25  0:00 ` Tucker Taft
  1997-09-25  0:00   ` Stephen Leake
  0 siblings, 1 reply; 7+ messages in thread
From: Tucker Taft @ 1997-09-25  0:00 UTC (permalink / raw)



Stephen Leake (Stephen.Leake@gsfc.nasa.gov) wrote:

: ... Here's an attempt to force ObjectAda to read a 16 bit integer:

: with Ada.Streams;
: package Interface_Streams is

:    type Integer_16 is range -32768 .. 32767;
:    for Integer_16'Size use 16;

:    procedure Read_16
:       (Stream : access Ada.Streams.Root_Stream_Type'Class;
:        Item : out Integer_16);

:    subtype Integer_16_Base is Integer_16'base;
:    for Integer_16_Base'Read use Read_16;

:    procedure Write_16
:       (Stream : access Ada.Streams.Root_Stream_Type'Class;
:        Item : in Integer_16);

:    for Integer_16'Write use Write_16;

: end Interface_Streams;

: For both attribute definition clauses, ObjectAda 7.1 gives the error:

: interface_streams.ads: Error: line 18 col 33 LRM:13.13.2(36), For an
: attribute definition clause specifying a stream attribute for a scalar
: type, the subtype  for the Item parameter must be the base subtype

: Apparently ObjectAda uses a 32 bit base integer type, even when only 16
: bits are requested. What is the rationale for this? 

The rationale is that the most efficient arithmetic is 32-bits.
Even though you ask for only 16 bits, and memory-resident variables
will only take up 16 bits, the base "value" size is 32 bits,
and the compiler will use 32-bit registers and 32-bit arithmetic 
for computations.  

Note that this is similar to declaring a 6 bit integer type.
You presumably would not be surprised if the compiler used
a base subtype of larger than 6 bits.  On most modern processors,
the efficient arithmetic size is 32 or 64 bits, so less and less
should you expect the base subtypes to be anything shorter than 32.

: ... Is it legal for
: ObjectAda to reject these attribute definition clauses? 

It is *required* to reject them, given that Integer_16'Base is not 
the same subtype as Integer_16.  In fact, even if Integer_16'Base'Size
were 16, it would still be required to reject the above, since
you didn't use Integer_16'Base.  

If you want to specify a stream attribute for a discrete subtype,
you have to use the 'Base attribute, since any other subtype
will be constrained (even if the constraints happen to match
the base range), and the stream attributes require the (unconstrained)
base subtype for scalars.

: ... What is the base type of Integer_16?
                       ^^^^ "subtype"

Integer_16'Base.

: I hope this issue can be addressed by the Uniformity Rapporteur Group;
: it would be very nice if streams generated by one compiler/run-time
: could be read by another. It would also be nice if a 16 bit integer
: would read and write just 16 bits.

The fact that 'Read and 'Write use the base subtype rather than
the first subtype for a scalar type is a bit problematic, but
there are good reasons for it (of course ;-).  Basically you get
only one 'Read attribute per *type*, and there is nothing prohibiting 
someone from declaring a variable using the 'Base subtype, so if the
stream attributes are going to work for all subtypes of the type,
they need to accommodate the 'Base subtype as well.

One possibility is to "pretend" the base subtype is only 16 bits,
even though 32-bit arithmetic and 32-bit registers are used
for all calculations.  This would bring the stream behavior
back to where it only wrote 16 bits per item, but the meaning
of 'Base would be somewhat muddied.

: I just looked (on AdaHome) for the commentaries produced by the URG; I
: found a bunch of AI's, but no UI's. Can someone point me to where the
: URG output is?

The URG is no longer an active group.  The ARG is taking up the slack,
and there will probably be AIs that address implementation advice,
as opposed to implementation requirements.

: -- 
: - Stephe

--
-Tucker Taft   stt@inmet.com   http://www.inmet.com/~stt/
Intermetrics, Inc.  Burlington, MA  USA




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

* Re: 16 bit integers in streams
  1997-09-25  0:00 ` Tucker Taft
@ 1997-09-25  0:00   ` Stephen Leake
  1997-09-25  0:00     ` Tucker Taft
  0 siblings, 1 reply; 7+ messages in thread
From: Stephen Leake @ 1997-09-25  0:00 UTC (permalink / raw)



Tucker Taft wrote:
> 
> Stephen Leake (Stephen.Leake@gsfc.nasa.gov) wrote:
> 
> : ... Here's an attempt to force ObjectAda to read a 16 bit integer:
> 
> : with Ada.Streams;
> : package Interface_Streams is
> 
> :    type Integer_16 is range -32768 .. 32767;
> :    for Integer_16'Size use 16;
> 
> :    procedure Read_16
> :       (Stream : access Ada.Streams.Root_Stream_Type'Class;
> :        Item : out Integer_16);
> 
> :    subtype Integer_16_Base is Integer_16'base;
> :    for Integer_16_Base'Read use Read_16;
> 
> :    procedure Write_16
> :       (Stream : access Ada.Streams.Root_Stream_Type'Class;
> :        Item : in Integer_16);
> 
> :    for Integer_16'Write use Write_16;
> 
> : end Interface_Streams;
> 
> : For both attribute definition clauses, ObjectAda 7.1 gives the >   error:
> 
> : interface_streams.ads: Error: line 18 col 33 LRM:13.13.2(36), For an
> : attribute definition clause specifying a stream attribute for a > : scalar
> : type, the subtype  for the Item parameter must be the base subtype
> 
> Note that this is similar to declaring a 6 bit integer type.
> You presumably would not be surprised if the compiler used
> a base subtype of larger than 6 bits.  On most modern processors,
> the efficient arithmetic size is 32 or 64 bits, so less and less
> should you expect the base subtypes to be anything shorter than 32.

Yep, that's why I suspected the 32 bit base type.
 
> : ... Is it legal for
> : ObjectAda to reject these attribute definition clauses?
> 
> It is *required* to reject them, given that Integer_16'Base is not
> the same subtype as Integer_16.  In fact, even if Integer_16'Base'Size
> were 16, it would still be required to reject the above, since
> you didn't use Integer_16'Base.

But I DID use Integer_16'Base for Read (not for Write), at least with an
intevening subtype definition. I also tried:

   for Integer_16'Base'Read use Read_16;

and that gave the error:

interface_streams.ads: Error: line 12 col 19 LRM:13.3(5), The BASE
attribute is not a specifiable attribute

Is this a bug in ObjectAda? My maintenance contract has run out, but
I'll report it anyway.

> : I hope this issue can be addressed by the Uniformity Rapporteur > : Group;
> : it would be very nice if streams generated by one compiler/run-time
> : could be read by another. It would also be nice if a 16 bit integer
> : would read and write just 16 bits.
> 
> The fact that 'Read and 'Write use the base subtype rather than
> the first subtype for a scalar type is a bit problematic, but
> there are good reasons for it (of course ;-).  Basically you get
> only one 'Read attribute per *type*, and there is nothing prohibiting
> someone from declaring a variable using the 'Base subtype, so if the
> stream attributes are going to work for all subtypes of the type,
> they need to accommodate the 'Base subtype as well.
> 
> One possibility is to "pretend" the base subtype is only 16 bits,
> even though 32-bit arithmetic and 32-bit registers are used
> for all calculations.  This would bring the stream behavior
> back to where it only wrote 16 bits per item, but the meaning
> of 'Base would be somewhat muddied.

Ok, I understand the consistency issue. Apparently GNAT uses 16 bit base
integers when I request them. I hearby request an option on ObjectAda
(and therefore the AdaMagic front end?) to sacrifice efficient integer
arithmetic, and give me 16 bit base integers (when appropriate), and
therefore 16 bits in streams! Could pragma Optimize (Space) do this?

> The URG is no longer an active group.  The ARG is taking up the slack,
> and there will probably be AIs that address implementation advice,
> as opposed to implementation requirements.

So does this qualify as an AI? I guess I should just submit it and see
what happens.

> 
> --
> -Tucker Taft   stt@inmet.com   http://www.inmet.com/~stt/
> Intermetrics, Inc.  Burlington, MA  USA

Thanks for your clear and detailed response; it is always a pleasure
when you post to comp.lang.ada.

-- 
- Stephe




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

* Re: 16 bit integers in streams
  1997-09-25  0:00   ` Stephen Leake
@ 1997-09-25  0:00     ` Tucker Taft
  1997-09-25  0:00       ` Stephen Leake
  0 siblings, 1 reply; 7+ messages in thread
From: Tucker Taft @ 1997-09-25  0:00 UTC (permalink / raw)



Stephen Leake (Stephen.Leake@gsfc.nasa.gov) wrote:

: ...
: But I DID use Integer_16'Base for Read (not for Write), at least with an
: intevening subtype definition. I also tried:

:    for Integer_16'Base'Read use Read_16;

: and that gave the error:

: interface_streams.ads: Error: line 12 col 19 LRM:13.3(5), The BASE
: attribute is not a specifiable attribute

: Is this a bug in ObjectAda? My maintenance contract has run out, but
: I'll report it anyway.

No, this is not a bug.  Per RM95 13.13.2(36), the subtype of the Item
parameter in the spec for your Read_16 and Write_16 procedures must
be the base subtype.  The subtype in the rep-clause must be the
first subtype (13.1(8)).  Hence, to make this work, do something like:

   procedure Read_16(
      Stream : access Ada.Streams.Root_Stream_Type'Class;
      Item : Integer_16'Base   -- *here* is where you need the 'Base
   );
   for Integer_16'Read use Read_16;

See RM95 13.13.2(40) for a very similar example of use.

: ...
: > One possibility is to "pretend" the base subtype is only 16 bits,
: > even though 32-bit arithmetic and 32-bit registers are used
: > for all calculations.  This would bring the stream behavior
: > back to where it only wrote 16 bits per item, but the meaning
: > of 'Base would be somewhat muddied.

: Ok, I understand the consistency issue. Apparently GNAT uses 16 bit base
: integers when I request them. I hearby request an option on ObjectAda
: (and therefore the AdaMagic front end?) to sacrifice efficient integer
: arithmetic, and give me 16 bit base integers (when appropriate), and
: therefore 16 bits in streams! Could pragma Optimize (Space) do this?

Gulp.  This would be a pretty big semantic effect for pragma Optimize.

The problem is that the representation used on streams is in one
sense a very important "high-level" external effect, and in another
sense something almost analagous to internal representation.

I suspect the "right" solution is to consider the base range to be
a 16 bit range for types like this, even though 32-bit arithmetic is 
used for them.  We have already considered doing this, but haven't 
done it yet.  Of course, the longer we wait, the more people will begin
to rely on the current behavior...

Perhaps we could use an explicit size clause as a way to control 
the base range.  We have frequently debated the meaning of
a "confirming" size clause.  Perhaps this could be one "real" effect
of such a clause.  It's an intriguing thought...

: > The URG is no longer an active group.  The ARG is taking up the slack,
: > and there will probably be AIs that address implementation advice,
: > as opposed to implementation requirements.

: So does this qualify as an AI? I guess I should just submit it and see
: what happens.

Yes, it qualifies as an AI.

: Thanks for your clear and detailed response; it is always a pleasure
: when you post to comp.lang.ada.

Your welcome.

: -- 
: - Stephe

--
-Tucker Taft   stt@inmet.com   http://www.inmet.com/~stt/
Intermetrics, Inc.  Burlington, MA  USA




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

* Re: 16 bit integers in streams
  1997-09-25  0:00       ` Stephen Leake
@ 1997-09-26  0:00         ` Tucker Taft
  1997-09-26  0:00           ` Stephen Leake
  0 siblings, 1 reply; 7+ messages in thread
From: Tucker Taft @ 1997-09-26  0:00 UTC (permalink / raw)



Stephen Leake (Stephen.Leake@gsfc.nasa.gov) wrote:

: I assume size clauses control both the external and internal
: representation; see below.

You would be wrong if you made that assumption.

: > I suspect the "right" solution is to consider the base range to be
: > a 16 bit range for types like this, even though 32-bit arithmetic is
: > used for them. We have already considered doing this, but haven't
: > done it yet.  Of course, the longer we wait, the more people will 
: > begin to rely on the current behavior...

: Or complain about it :). Surely the intent of 'Read is to put the
: _memory_ image of a type into the stream, not the _register_ image?

Because 'Write/'Read are designed to handle the *base* range of the 
type, rather than the range of the first subtype, the stream 
representation is in some sense more related to the "register" image 
than the memory image.

: > Perhaps we could use an explicit size clause as a way to control
: > the base range.  We have frequently debated the meaning of
: > a "confirming" size clause.  Perhaps this could be one "real" effect
: > of such a clause.  It's an intriguing thought...

: This is definitely what I expect a size clause to mean; I'm telling the
: compiler I want exactly 16 bits, anyplace it matters (including
: streams). I assume that's what GNAT does now, although maybe GNAT is
: also doing 16 bit arithmetic.

A size clause currently has *no* effect on the base range of the type.
I am thinking that perhaps it ought to have such an effect, though
that "thought" is pretty radical.  And there are some problems with
the idea.  For example, given:

   type I16 is range 0..2**16-1;
   for I16'size use 16;

Clearly the base range of this type is required by the RM to be
at least -2**16+1 .. 2**16-1, since it is a signed integer type 
(even though the first subtype's range includes no negative values).
So what should be the stream representation for this type?  
Presuming each stream element is 8 bits, probably at least
3 stream elements, and more likely 4 stream elements, would be the
expected stream representation.

In general, the existence of the base subtype is more of an interesting
frill than a core feature, but with streams, the characteristics of
the base subtype suddenly become more important.  It's not clear
how to resolve this dilemma...

: -- 
: - Stephe

--
-Tucker Taft   stt@inmet.com   http://www.inmet.com/~stt/
Intermetrics, Inc.  Burlington, MA  USA




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

* Re: 16 bit integers in streams
  1997-09-26  0:00         ` Tucker Taft
@ 1997-09-26  0:00           ` Stephen Leake
  0 siblings, 0 replies; 7+ messages in thread
From: Stephen Leake @ 1997-09-26  0:00 UTC (permalink / raw)



Tucker Taft wrote:
> ...
> In general, the existence of the base subtype is more of an > interesting
> frill than a core feature, but with streams, the characteristics of
> the base subtype suddenly become more important.  It's not clear
> how to resolve this dilemma...

If I can summarize:
	
Stream attributes 'Read and 'Write need to work for the base type,
because we can declare objects of type 'Base.

A size clause specifies the size of the first subtype, not the base
type. The base type can in general contain more bits than the first
subtype.

ObjectAda chooses 32 bit integers as the base type when I ask for 16 bit
integers, and therefore reads and writes 32 bits in streams.

This now makes sense (to me, anyway :). My original problem was that I
want to read a 16 bit integer from a stream (where the stream format is
dicated outside my Ada program). 

Clearly, if I was reading a 12 bit integer, I'd have to read two stream
elements and then do a shift and an unchecked conversion, and keep track
of the extra bits that are part of the next item in the stream.

I can take the same approach when reading a 16 bit integer, but I don't
have to if I use GNAT, which allows 16 bit base integers. The stream
format assumes I can read 16 bit chunks; it does not use smaller chunks.
Actually, I found another work around for ObjectAda; I can read
Wide_Characters, which are 16 bits, and then use 'Pos to get an integer.
But that's a bit of a kludge.

This gets back to the question of why ObjectAda uses 32 bit base
integers, when I give a range that fits in 16 bits and a size clause for
16 bits. Tucker said it was for "efficient arithmetic", but that's not
what I want in this case. It seems to me that specifying a size clause
should be enough of a hint to the compiler that I am willing to
sacrifice efficiency for the sake of control over size (in streams, in
this case). If you want more of a hint, I can add a pragma Optimize
(Space) (which I suggested earlier). Tuck said this would be a "large
semantic effect". I'm not clear what the problem is; the choice of base
integer size affects three things (that I know of):

1) The time efficiency of integer arithmetic.

2) Whether CONSTRAINT_ERROR is raised for intermediate results that are
outside the first subtype range. 

3) The number of bits read/written in streams. 

What else does it affect? 

If we let size clauses influence the choice of base integer type, we
have the following user control:

For 1), to let the compiler to choose a time efficient arithmetic type,
I just specify the range, and do NOT give a size clause. Similarly, for
2), I can specify a range that covers my intermediate results. 

For 3), I specify the number of bits I want, with the understanding that
it will be rounded up to the next hardware-supported integer size.


Perhaps a totally different solution would be to introduce yet another
stream attribute: 'Write_Sized, which respects the size clause, and thus
cannot be used on an object of a base type. 

> 
> : --
> : - Stephe
> 
> --
> -Tucker Taft   stt@inmet.com   http://www.inmet.com/~stt/
> Intermetrics, Inc.  Burlington, MA  USA

-- 
- Stephe




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

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

Thread overview: 7+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
1997-09-25  0:00 16 bit integers in streams Stephen Leake
1997-09-25  0:00 ` Tucker Taft
1997-09-25  0:00   ` Stephen Leake
1997-09-25  0:00     ` Tucker Taft
1997-09-25  0:00       ` Stephen Leake
1997-09-26  0:00         ` Tucker Taft
1997-09-26  0:00           ` Stephen Leake

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