Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

CRC in Ada?

271 views
Skip to first unread message

Dr. John B. Matthews

unread,
Mar 2, 1997, 3:00:00 AM3/2/97
to

Hi! Can anyone point me to 16-bit CRC code in Ada? I've checked the
PAL and several other archives without luck. Any help appreciated.

Thanks,

John
----------------------------------------------------------------
John B. Matthews, M.D.
jmat...@nova.wright.edu; john_m...@ccmail.dayton.saic.com
"Whom the gods would destroy, they first invite to program in C"


David Brown

unread,
Mar 3, 1997, 3:00:00 AM3/3/97
to

jmat...@nova.wright.edu (Dr. John B. Matthews) writes:

> Hi! Can anyone point me to 16-bit CRC code in Ada? I've checked the
> PAL and several other archives without luck. Any help appreciated.

I threw this together the other day. I declare this code to be public
domain. Please give it a try, but I offer no guarantees that this
works.

David Brown
dbr...@vigra.com

----------------------------------------------------------------------
package Data is

type Byte is mod 2 ** 8;
for Byte'Size use 8;

type Byte_Array is array (Positive range <>) of Byte;

end Data;
----------------------------------------------------------------------
with Data;
use Data;

package Crc16 is

type U16 is mod 2 ** 16;

procedure Update (Crc : in out U16;
Data : in Byte_Array);

end Crc16;
----------------------------------------------------------------------
package body Crc16 is

type U16_Array is array (Byte) of U16;

-- The generated lookup table.
Table : U16_Array;

procedure Update (Crc : in out U16;
Data : in Byte_Array) is
begin
for I in Data'Range loop
Crc := (Crc / 16#100#) xor Table (Byte (Crc) xor Data (I));
end loop;
end Update;

-- Generate the lookup table.
procedure Generate is
P : constant := 16#8408#;
V : U16;
begin
for B in Byte loop
V := U16 (B);
for I in 1 .. 8 loop
if (V and 1) = 0 then
V := V / 2;
else
V := (V / 2) xor P;
end if;
end loop;

Table (B) := V;
end loop;
end Generate;

begin
Generate;
end Crc16;
----------------------------------------------------------------------

Tom Moran

unread,
Mar 3, 1997, 3:00:00 AM3/3/97
to

The recent SIGADA publication had a 16 bit CRC article. But it ran
around a loop, a bit at a time, which is perhaps OK if your CPU power
greatly exceeds your comm bandwidth. There are table lookup CRCs that
run fast.

Stephen Garriga

unread,
Mar 4, 1997, 3:00:00 AM3/4/97
to

On 2 Mar 97 22:06:52 EST, jmat...@nova.wright.edu (Dr. John B.
Matthews) wrote:

>Hi! Can anyone point me to 16-bit CRC code in Ada? I've checked the
>PAL and several other archives without luck. Any help appreciated.

{sig snip}

Not the program you wanted, just a comment:

I had to do an 8 bit CRC a couple of years ago on a DEC Alpha running
OSF 3.2c & DEC Ada.

_IF_ you are doing the CRC on a file (as I was), I would advise you
to consider performance. I found (exactly the same algorithm)
implemented in C took an order of magnitude seconds less to execute
than the Ada equivalent.

Steve Garriga gar...@logica.com
type OPINION is access PERSONAL_THOUGHTS_AND_BIAS;
OPINION_STATED : new OPINION := not LOGICA.OPINION;
Logica UK Ltd. +44 171 637 9111 http://www.logica.com

Tom Moran

unread,
Mar 4, 1997, 3:00:00 AM3/4/97
to

> I found (exactly the same algorithm)
> implemented in C took an order of magnitude seconds less to execute
> than the Ada equivalent.
Was this a byte (or word) lookup or a bit shifting bit-at-a-time
algorithm? Ada 83 wasn't real handy with bit shifting.

Stephen Garriga

unread,
Mar 4, 1997, 3:00:00 AM3/4/97
to

I am not 100% sure but I think it was a straight forward XOR
algorithm. The problem was not with the actual calculation, but
with the I/O the implementation on the DEC at the time was terrible.
Even reading blocks of data into memory was slower than reading a byte
at a time using C stdio! (There is a LOT of code between a
sequential_io.read and the actual O/S call and significanly less using
the C libs) Also the io routines did not always correctly detect end
of file and I was having to spot it by trapping exceptions.
We took a pragmatic approach, wrote a few interfaces to the C libs, a
few simple C functions and lived it.

David L Brown

unread,
Mar 4, 1997, 3:00:00 AM3/4/97
to

gar...@logica.com (Stephen Garriga) writes:

> _IF_ you are doing the CRC on a file (as I was), I would advise you

> to consider performance. I found (exactly the same algorithm)


> implemented in C took an order of magnitude seconds less to execute
> than the Ada equivalent.

Well, I tried this. I wrote a small program to read files and compute
CRC16's on them. What I found was disheartening. The CRC code didn't
take very long. However, the Stream_IO read of the data was very
slow. I traced it down to doing a call to the C read function for
each byte.

I'm using GNAT 3.09 on Linux (pentium). Is there anything about the
specification for Stream_IO (or Text_IO for that matter) that is
causing the GNAT runtime to turn off buffering. This is a real
performance hit, and I have had to revert to calling the C routines
directly when streams would be adequate, if they just weren't so
inefficient.

Dave

Robert Dewar

unread,
Mar 4, 1997, 3:00:00 AM3/4/97
to

<< _IF_ you are doing the CRC on a file (as I was), I would advise you
to consider performance. I found (exactly the same algorithm)
implemented in C took an order of magnitude seconds less to execute
than the Ada equivalent.>>


Well of course no one can see what the two pieces of code you compared
are, since you did not post them, so we cannot tell whether the problem
came from inappropriate coding choices on your part, or bad code generation
in the Ada compiler you were using -- it certainly was nothing to do with
C vs Ada per se as languages.

In any case, using any decent Ada 95 compiler, this should not be an issue,
if you code using the same approach and general abstraction level in the
C code and in the Ada code. Indeed, the availability of packed arrays in
Ada (but not in C) may allow you to raise the semantic level of the Ada
code without penalty (but this is not necessarily the case,, just a
possibility).


Matthew Heaney

unread,
Mar 4, 1997, 3:00:00 AM3/4/97
to

In article <331bf6ce...@news.logica.co.uk>, gar...@logica.com
(Stephen Garriga) wrote:

> _IF_ you are doing the CRC on a file (as I was), I would advise you
>to consider performance. I found (exactly the same algorithm)
>implemented in C took an order of magnitude seconds less to execute
>than the Ada equivalent.

Once again it is necessary to clarify things with respect to languages and
efficiency.

First, performance is a characteristic of _implementations_, not of
_languages_. So let's not be making bold intimations that Ada the language
is somehow slower than C.

Second, one of the things many Ada programmers don't realize is that strong
typing can _increase_ the efficiency because it gives the compiler more
semantic information on which to base optimizations. (For example, using a
subtype for an array index value can turn off checks that would otherwise
be necessary to detect index constraint errors when dereferencing an
array.)

So show me this algorithm that "is exactly the same" and I'll tell you why
it runs more slowly.

matt

--------------------------------------------------------------------
Matthew Heaney
Software Development Consultant
<mailto:matthew...@acm.org>
(818) 985-1271

Robert Dewar

unread,
Mar 4, 1997, 3:00:00 AM3/4/97
to

David Brown:

<<Well, I tried this. I wrote a small program to read files and compute
CRC16's on them. What I found was disheartening. The CRC code didn't
take very long. However, the Stream_IO read of the data was very
slow. I traced it down to doing a call to the C read function for
each byte>>

Are you using stream attributes to read into a string. This is a mistake
that I have seen a number of people make. Why a mistake (if you are
worrying about efficiency?) Because Ada semantics require element by
element processing of arrays (and for a string, the element is a
character).

Instead use Read and Write directly to read and/or write buffers
of stream elements.

<<I'm using GNAT 3.09 on Linux (pentium). Is there anything about the
specification for Stream_IO (or Text_IO for that matter) that is
causing the GNAT runtime to turn off buffering. This is a real
performance hit, and I have had to revert to calling the C routines
directly when streams would be adequate, if they just weren't so
inefficient.>>

As for buffering, I am not sure what the default is, but you can use
setvbuf to control buffering (read the section in the GNAT manual about
getting at the underlying streams).


Jon S Anthony

unread,
Mar 4, 1997, 3:00:00 AM3/4/97
to

In article <331bf6ce...@news.logica.co.uk> gar...@logica.com (Stephen Garriga) writes:

> I had to do an 8 bit CRC a couple of years ago on a DEC Alpha running
> OSF 3.2c & DEC Ada.
>

> _IF_ you are doing the CRC on a file (as I was), I would advise you
> to consider performance. I found (exactly the same algorithm)
> implemented in C took an order of magnitude seconds less to execute
> than the Ada equivalent.

That sounds very odd. Did you use very different implementation
styles? For example, maybe use unconstrained types in the Ada or some
such? In general I would think a similar implementation style here
would yield basically the same "efficiency" result.

/Jon

--
Jon Anthony
Organon Motives, Inc.
Belmont, MA 02178
617.484.3383
j...@organon.com


Stephen Garriga

unread,
Mar 5, 1997, 3:00:00 AM3/5/97
to

On 4 Mar 1997 16:01:48 -0500, de...@merv.cs.nyu.edu (Robert Dewar)
wrote:
{quote snip}

>
>Well of course no one can see what the two pieces of code you compared
>are, since you did not post them, so we cannot tell whether the problem
>came from inappropriate coding choices on your part, or bad code generation
>in the Ada compiler you were using -- it certainly was nothing to do with
>C vs Ada per se as languages.
My comment was just a warning!
I was not saying C was a better language, merely that in certain
situations one has to be pragmatic. On certain platforms, certain
operations are fast in C and dogs in Ada.

>
>In any case, using any decent Ada 95 compiler, this should not be an issue,
This assumes you can use Ada95 or have compiler choice. In the UK at
least, our customers are still insisting on Ada(83) or specific vendor
implementations.

>if you code using the same approach and general abstraction level in the
>C code and in the Ada code. Indeed, the availability of packed arrays in
>Ada (but not in C) may allow you to raise the semantic level of the Ada
>code without penalty (but this is not necessarily the case,, just a
>possibility).
>
FYI the specific problem I encountered was generating a CRC for a
file. The performance problem was entirely due to poor performance by
the Ada I/O routines. (There were other problems like failure to
identify end of file situations too). DEC Ada & OS/F 3.2c

Stephen Garriga

unread,
Mar 5, 1997, 3:00:00 AM3/5/97
to

On 04 Mar 1997 14:56:58 -0800, David L Brown <dbr...@ted.vigra.com>
wrote:

>gar...@logica.com (Stephen Garriga) writes:
>
>> _IF_ you are doing the CRC on a file (as I was), I would advise you
>> to consider performance. I found (exactly the same algorithm)
>> implemented in C took an order of magnitude seconds less to execute
>> than the Ada equivalent.
>

>Well, I tried this. I wrote a small program to read files and compute
>CRC16's on them. What I found was disheartening. The CRC code didn't
>take very long. However, the Stream_IO read of the data was very
>slow. I traced it down to doing a call to the C read function for

>each byte.


>
>I'm using GNAT 3.09 on Linux (pentium). Is there anything about the
>specification for Stream_IO (or Text_IO for that matter) that is
>causing the GNAT runtime to turn off buffering. This is a real
>performance hit, and I have had to revert to calling the C routines
>directly when streams would be adequate, if they just weren't so
>inefficient.
>

>Dave
I was using a DEC Alpha, DEC Ada (83) and OS/F 3.2c!
I didn't the time to investigate too closely, but it looked to me
that, in my case, the I/O was actually implemented as many layers of
generics on top of the low level OS call then specific instantiations.
This remained in place at run time so instead of generating a single
stack frame/procedure call, dozens were done per read!
Efficiency was weighted over design purity and several such problems
were addressed with small C procedures interfaced to our Ada.

Laurent Pautet

unread,
Mar 5, 1997, 3:00:00 AM3/5/97
to

>>>>> "John" == John B Matthews <jmat...@nova.wright.edu> writes:

John> Hi! Can anyone point me to 16-bit CRC code in Ada? I've checked
John> the PAL and several other archives without luck. Any help
John> appreciated.

I looked at this a while ago. I remember that there is such a piece of
code in the PAL, it is called occ (compression algorithm).

Is Ada absolutly needed here ? You can interface with existing
software. Recently, we added compression filtering to GLADE and we
reused the Z library. I am almost sure that there is a CRC code in
this library.

--
-- Laurent

David C. Hoos, Sr.

unread,
Mar 5, 1997, 3:00:00 AM3/5/97
to

This is a multi-part message in MIME format.

------=_NextPart_000_01BC292F.C954A260
Content-Type: text/plain; charset=ISO-8859-1
Content-Transfer-Encoding: 7bit

Here is an implementation of a 16-bit CRC in both C and Ada. The C code is
perhaps ten years old, and is from an implementation of Xmodem. The Ada
code was translated from that.

The test driver tests both the C code (as an imported set of functions),
and the Ada code.

The form of the test driver is not suitable for performance testing, as the
CRC generation is swamped by the file reads. I'd like to modify this in
the next couple of days so as to be able to compare the speeds of the two
implementations. The test driver does serve to demonstrate the equivalence
of the two implementations, though.

The generating polynomial is one frequently used (x1021), but the value can
be changed as one likes.

--
David C. Hoos, Sr.,
http://www.dbhwww.com
http://www.ada95.com

Dr. John B. Matthews <jmat...@nova.wright.edu> wrote in article
<1997Mar...@nova.wright.edu>...

------=_NextPart_000_01BC292F.C954A260
Content-Type: application/octet-stream; name="crc.c"
Content-Transfer-Encoding: 7bit
Content-Description: crc.c (C source code file)
Content-Disposition: attachment; filename="crc.c"

/* crc.c */

#include "crc.h"

#define POLY 0x1021

static unsigned short CRCtable[256];

/* calculate CRC table entry */

unsigned short CalcTable(data,genpoly,accum)
unsigned short data;
unsigned short genpoly;
unsigned short accum;
{static int i;
data <<= 8;
for(i=8;i>0;i--)
{
if((data^accum) & 0x8000) accum = (accum << 1) ^ genpoly;
else accum <<= 1;
data <<= 1;
}
return(accum);
}

/* initialize CRC table */

void InitCRC(void)
{int i;
for(i=0;i<256;i++) CRCtable[i] = CalcTable(i,POLY,0);
}

/* compute updated CRC */

unsigned short UpdateCRC(crc,byte)
unsigned short crc;
unsigned char byte;
{
return( (crc << 8) ^ CRCtable[ (crc >> 8) ^ byte ] );
}

------=_NextPart_000_01BC292F.C954A260
Content-Type: application/octet-stream; name="crc.h"
Content-Transfer-Encoding: 7bit
Content-Description: crc.h (C Header File)
Content-Disposition: attachment; filename="crc.h"

void InitCRC(void);
unsigned short UpdateCRC(unsigned short,unsigned char);

------=_NextPart_000_01BC292F.C954A260
Content-Type: application/octet-stream; name="crc_pkg.adb"
Content-Transfer-Encoding: 7bit
Content-Description: crc_pkg.adb (ObjectAda File)
Content-Disposition: attachment; filename="crc_pkg.adb"

package body CRC_pkg is
type Lookup_Table_Type is
array (Interfaces.Unsigned_8) of Interfaces.Unsigned_16;
Lookup_Table : Lookup_Table_Type;
procedure Update
(The_CRC_Value : in out Interfaces.Unsigned_16;
With_The_Byte : in Interfaces.Unsigned_8) is
use Interfaces;
begin
The_CRC_Value := Shift_Left
(Value => The_CRC_Value,
Amount => 8) xor Lookup_Table
(Interfaces.Unsigned_8 (Shift_Right
(Value => The_CRC_Value,
Amount => 8)) xor With_The_Byte);
end Update;

begin -- CRC package initialization
declare
function Lookup_Table_Entry
(For_The_Index : in Interfaces.Unsigned_8;
And_The_Polynomial : in Interfaces.Unsigned_16)
return Interfaces.Unsigned_16 is
use Interfaces;
Temporary_Data : Interfaces.Unsigned_16 := Shift_Left
(Value => Interfaces.Unsigned_16 (For_The_Index),
Amount => 8);
Temporary_Accumulator : Interfaces.Unsigned_16 := 0;
begin
for I in reverse 1 .. 8 loop
if ((Temporary_Data xor Temporary_Accumulator) and
16#8000#) > 0 then
Temporary_Accumulator := Shift_Left
(Value => Temporary_Accumulator,
Amount => 1) xor And_The_Polynomial;
else
Temporary_Accumulator := Shift_Left
(Value => Temporary_Accumulator,
Amount => 1);
end if;
Temporary_Data := Shift_Left
(Value => Temporary_Data,
Amount => 1);
end loop;
return Temporary_Accumulator;
end Lookup_Table_Entry;
begin
for I in Lookup_Table'Range loop
Lookup_Table (I) := Lookup_Table_Entry
(For_The_Index => I,
And_The_Polynomial => Polynomial);
end loop;
end;
end CRC_pkg;


------=_NextPart_000_01BC292F.C954A260
Content-Type: application/octet-stream; name="crc_pkg.ads"
Content-Transfer-Encoding: 7bit
Content-Description: crc_pkg.ads (ObjectAda File)
Content-Disposition: attachment; filename="crc_pkg.ads"

with Interfaces;

package CRC_pkg is

use type Interfaces.Unsigned_8;
use type Interfaces.Unsigned_16;
Polynomial : constant Interfaces.Unsigned_16 := 16#1021#;

procedure Update
(The_CRC_Value : in out Interfaces.Unsigned_16;
With_The_Byte : in Interfaces.Unsigned_8);

end CRC_pkg;

------=_NextPart_000_01BC292F.C954A260
Content-Type: application/octet-stream; name="test_crc.adb"
Content-Transfer-Encoding: quoted-printable
Content-Description: test_crc.adb (ObjectAda File)
Content-Disposition: attachment; filename="test_crc.adb"

with Ada.Command_Line;
with Ada.Sequential_IO;
with Ada.Text_IO;
with CRC_pkg;
with Interfaces.C;
procedure Test_CRC is
package C renames Interfaces.C;
package Command_Line renames Ada.Command_Line;
package Text_IO renames Ada.Text_IO;
use type C.Unsigned_Char;
use type C.Unsigned_Short;
procedure Init_CRC;
function Updated_CRC=20
(Previous_CRC_Accumulation : C.Unsigned_Short;
Current_Byte : C.Unsigned_char)
return C.Unsigned_Short;
pragma Import (C, Init_CRC, "InitCRC");
pragma Import (C, Updated_CRC, "UpdateCRC");
pragma Linker_Options ("crc.o");
Current_CRC_Accumulation : C.Unsigned_Short;
package Unsigned_Short_IO is new Ada.Text_IO.Modular_IO =
(C.Unsigned_Short);
package Unsigned_Char_IO is new Ada.Sequential_IO (C.Unsigned_Char);
The_File : Unsigned_Char_IO.File_Type;
The_Unsigned_Char : C.Unsigned_Char;
begin
Text_Io.Put_Line (Integer'Image (C.Unsigned_Char'Size));
Text_Io.Put_Line ("16-bit CRCs (x1021) by file:");
Text_Io.Put_Line ("(Using imported C subprograms)");
Init_CRC;
for F in 1 .. Command_Line.Argument_Count loop
Text_IO.Put=20
("File """ &
Command_Line.Argument (F));
begin
Unsigned_Char_IO.Open
(File =3D> The_File,
Name =3D> Command_Line.Argument (F),
Mode =3D> Unsigned_Char_IO.In_File);
exception
when Text_Io.Name_Error =3D>
Text_IO.Put_Line (""": -- NOT FOUND!");
end;
if Unsigned_Char_IO.Is_Open (The_File) then
Current_CRC_Accumulation :=3D 0;
while not Unsigned_Char_IO.End_Of_File (The_File) loop
Unsigned_Char_IO.Read=20
(Item =3D> The_Unsigned_Char,
File =3D> The_File);
Current_CRC_Accumulation :=3D Updated_CRC
(Previous_CRC_Accumulation =3D> Current_CRC_Accumulation,
Current_Byte =3D> The_Unsigned_Char);
end loop;
Unsigned_Char_IO.Close (The_File);
Text_IO.Put (""":");
Unsigned_Short_IO.Put
(Item =3D> Current_CRC_Accumulation,
Width =3D> 10,
Base =3D> 16);
Text_IO.New_Line;
end if;
end loop;
=20
Text_Io.Put_Line ("(Using Ada subprogram)");
for F in 1 .. Command_Line.Argument_Count loop
Text_IO.Put=20
("File """ &
Command_Line.Argument (F));
begin
Unsigned_Char_IO.Open
(File =3D> The_File,
Name =3D> Command_Line.Argument (F),
Mode =3D> Unsigned_Char_IO.In_File);
exception
when Text_Io.Name_Error =3D>
Text_IO.Put_Line (""": -- NOT FOUND!");
end;
if Unsigned_Char_IO.Is_Open (The_File) then
Current_CRC_Accumulation :=3D 0;
while not Unsigned_Char_IO.End_Of_File (The_File) loop
Unsigned_Char_IO.Read=20
(Item =3D> The_Unsigned_Char,
File =3D> The_File);
CRC_Pkg.Update
(The_Crc_Value =3D> Interfaces.Unsigned_16 =
(Current_CRC_Accumulation),
With_The_Byte =3D> Interfaces.Unsigned_8 (The_Unsigned_Char));
end loop;
Unsigned_Char_IO.Close (The_File);
Text_IO.Put (""":");
Unsigned_Short_IO.Put
(Item =3D> Current_CRC_Accumulation,
Width =3D> 10,
Base =3D> 16);
Text_IO.New_Line;
end if;
end loop;
=20
end Test_CRC;

------=_NextPart_000_01BC292F.C954A260--


Larry Kilgallen

unread,
Mar 5, 1997, 3:00:00 AM3/5/97
to

In article <331d3cf9...@news.logica.co.uk>, gar...@logica.com (Stephen Garriga) writes:

> I was using a DEC Alpha, DEC Ada (83) and OS/F 3.2c!
> I didn't the time to investigate too closely, but it looked to me
> that, in my case, the I/O was actually implemented as many layers of
> generics on top of the low level OS call then specific instantiations.
> This remained in place at run time so instead of generating a single
> stack frame/procedure call, dozens were done per read!
> Efficiency was weighted over design purity and several such problems
> were addressed with small C procedures interfaced to our Ada.

If I were looking for maximum speed in Assembly Language, I would
minimize the total number of reads done, to a single read if possible.
This should be true for any language.

On VMS, the fact that C programs imported from Unix tend to do a
lot of single character I/O has forced the DEC C team to build in
many little tricks to support an inherently inefficient programming
technique.

For Ada, I would guess that implementors have not counted on
people using C-like programming constructs (vs. doing large
buffer reads as suggested earlier in this thread).

It is certainly possible to build an Ada environment optimized for
single-character reads, but that would not seem to be a priority
for most Ada compiler customers.

Larry Kilgallen

Robert A Duff

unread,
Mar 5, 1997, 3:00:00 AM3/5/97
to

In article <1997Mar5.083233.1@eisner>,

Larry Kilgallen <kilg...@eisner.decus.org> wrote:
>For Ada, I would guess that implementors have not counted on
>people using C-like programming constructs (vs. doing large
>buffer reads as suggested earlier in this thread).
>
>It is certainly possible to build an Ada environment optimized for
>single-character reads, but that would not seem to be a priority
>for most Ada compiler customers.

I think I disagree. Buffering should be the job of the OS and/or
standard libraries. Not every program.

I'm not sure why reading a file character-by-character is "C-like".
It seems like the natural way to write lots of programs, in any
language. The underlying language and OS should ensure that it can be
done efficiently (by making the "give-me-a-char" routine read from a
buffer whenever appropriate).

- Bob

Larry Kilgallen

unread,
Mar 5, 1997, 3:00:00 AM3/5/97
to

In article <E6Kxu...@world.std.com>, bob...@world.std.com (Robert A Duff) writes:
> In article <1997Mar5.083233.1@eisner>,
> Larry Kilgallen <kilg...@eisner.decus.org> wrote:
>>For Ada, I would guess that implementors have not counted on
>>people using C-like programming constructs (vs. doing large
>>buffer reads as suggested earlier in this thread).
>>
>>It is certainly possible to build an Ada environment optimized for
>>single-character reads, but that would not seem to be a priority
>>for most Ada compiler customers.
>
> I think I disagree. Buffering should be the job of the OS and/or
> standard libraries. Not every program.

While theoretical computing and Alan Turing may be centered on
the equivalence and correctness of programs, in the real world
performance is also a consideration. Just as those using intense
computation will be concerned about the efficiency of their
algorithms, those accessing large databases will take care
regarding order-of-access so as not to go skipping over the
whole thing when some locality-of-reference would yield better
performance. Those reading sequentially from disk should
likewise concern themselves with performance, and 512 calls
to even the lightest-weight library is too much if a single
call would do. For the stated problem (CRC) reading large
blocks is a clear win.

> I'm not sure why reading a file character-by-character is "C-like".
> It seems like the natural way to write lots of programs, in any
> language. The underlying language and OS should ensure that it can be
> done efficiently (by making the "give-me-a-char" routine read from a
> buffer whenever appropriate).

In my experience it is generally C programmers who make this mistake.
Perhaps it because many of them come from a Unix background where there
is no strong sense of a "record". On the other hand, it may just be
that there are so many C programmers that statistically speaking most
of the mistakes made will be made by a C programmer.

Larry Kilgallen

Robert Dewar

unread,
Mar 5, 1997, 3:00:00 AM3/5/97
to

Jon Anthony asks

<<That sounds very odd. Did you use very different implementation
styles? For example, maybe use unconstrained types in the Ada or some
such? In general I would think a similar implementation style here
would yield basically the same "efficiency" result.>>

One possibility is that the implementation was relying on doing rotates,
and there certainly is no easy portable efficient way of doing that
in Ada 83 (although for my taste I prefer to use table lookup for
computing CRC's and avoid the bit rotation stuff.


Robert A Duff

unread,
Mar 6, 1997, 3:00:00 AM3/6/97
to

In article <1997Mar5.131846.1@eisner>,

Larry Kilgallen <kilg...@eisner.decus.org> wrote:
>While theoretical computing and Alan Turing may be centered on
>the equivalence and correctness of programs, in the real world
>performance is also a consideration. Just as those using intense
>computation will be concerned about the efficiency of their
>algorithms, those accessing large databases will take care
>regarding order-of-access so as not to go skipping over the
>whole thing when some locality-of-reference would yield better
>performance. Those reading sequentially from disk should
>likewise concern themselves with performance, and 512 calls
>to even the lightest-weight library is too much if a single
>call would do. For the stated problem (CRC) reading large
>blocks is a clear win.

Agreed, but that's what inlining is for. All I was saying is that there
should be a standard package that does efficient I/O, with buffering,
and of course you want to inline a call that just bumps a pointer and
grabs a character out of a buffer (except in the rare case where the
buffer is exhausted). Unfortunately, Text_IO has an awful lot of
nearly-useless cruft in it. But why can't Stream_IO fit the bill here?

>> I'm not sure why reading a file character-by-character is "C-like".
>> It seems like the natural way to write lots of programs, in any
>> language. The underlying language and OS should ensure that it can be
>> done efficiently (by making the "give-me-a-char" routine read from a
>> buffer whenever appropriate).

And I should have added, "and by making that thing inline-able".
Actually, I suppose the OS has little to do with it -- obviously you
can't afford to do a system call (i.e. enter supervisor mode) on every
character.

>In my experience it is generally C programmers who make this mistake.
>Perhaps it because many of them come from a Unix background where there
>is no strong sense of a "record". On the other hand, it may just be
>that there are so many C programmers that statistically speaking most
>of the mistakes made will be made by a C programmer.

I still don't think it's a "mistake" to expect buffering to be done by
standard packages, rather than by every user's program. I mean, you
have to tell the thing that you're planning to read sequentially through
the file, but beyond that, the application program shouldn't have to
worry about it.

(When I programmed on VAX/VMS, I was appalled at the complexity of the
Record Management Services. I still don't know why all that complexity
is necessary, as compared to the Unix notion that a file is a sequence
of bytes. But I could be wrong -- I write compilers, mostly, which
don't need "fancy" I/O facilities.)

Note that Ada compilers don't typically use Text_IO to read the source
code! ;-)

- Bob

Ole-Hjalmar Kristensen FOU.TD/DELAB

unread,
Mar 6, 1997, 3:00:00 AM3/6/97
to

In article <1997Mar5.131846.1@eisner> kilg...@eisner.decus.org (Larry Kilgallen) writes:

In article <E6Kxu...@world.std.com>, bob...@world.std.com (Robert A Duff) writes:

> In article <1997Mar5.083233.1@eisner>,


> Larry Kilgallen <kilg...@eisner.decus.org> wrote:
>>For Ada, I would guess that implementors have not counted on
>>people using C-like programming constructs (vs. doing large
>>buffer reads as suggested earlier in this thread).
>>
>>It is certainly possible to build an Ada environment optimized for
>>single-character reads, but that would not seem to be a priority
>>for most Ada compiler customers.
>
> I think I disagree. Buffering should be the job of the OS and/or
> standard libraries. Not every program.

While theoretical computing and Alan Turing may be centered on


the equivalence and correctness of programs, in the real world
performance is also a consideration. Just as those using intense
computation will be concerned about the efficiency of their
algorithms, those accessing large databases will take care
regarding order-of-access so as not to go skipping over the
whole thing when some locality-of-reference would yield better
performance. Those reading sequentially from disk should
likewise concern themselves with performance, and 512 calls
to even the lightest-weight library is too much if a single
call would do. For the stated problem (CRC) reading large
blocks is a clear win.

I think you are missing something here. Altough in Unix it IS possible
to do reads of arbitrary length, the standard IO library of C
definitely does IO in blocks. The getc/putc functions are
usually implemented as macros, which just manipulate the buffer. Of
course it is possible to do it faster yourself, but the interface is
both efficient and simple to use. If you want to, you can even set the
buffer size.

You may judge for yourself:

#define getc(p) (--(p)->_cnt < 0 ? __filbuf(p) : (int)*(p)->_ptr++)
#define putc(x, p) (--(p)->_cnt < 0 ? __flsbuf((unsigned char) (x), (p)) \

: (int)(*(p)->_ptr++ = (x)))


> I'm not sure why reading a file character-by-character is "C-like".
> It seems like the natural way to write lots of programs, in any
> language. The underlying language and OS should ensure that it can be
> done efficiently (by making the "give-me-a-char" routine read from a
> buffer whenever appropriate).

In my experience it is generally C programmers who make this mistake.


Perhaps it because many of them come from a Unix background where there
is no strong sense of a "record". On the other hand, it may just be
that there are so many C programmers that statistically speaking most
of the mistakes made will be made by a C programmer.

Larry Kilgallen

It should be no harder to implement the putc/getc funtions on any
other OS which allows you to do character IO in blocks, than it is in Unix.

It may be a mistake in some cases, but talking about "this mistake" is
a vast oversimplification. Surely, there is nothing conceptually wrong
with having a set of single character IO operations like putc, getc,
and ungetc?


Ole-Hj. Kristensen

Ole-Hjalmar Kristensen FOU.TD/DELAB

unread,
Mar 6, 1997, 3:00:00 AM3/6/97
to

In article <E6Lpv...@world.std.com> bob...@world.std.com (Robert A Duff) writes:

<stuff deleted>

I still don't think it's a "mistake" to expect buffering to be done by
standard packages, rather than by every user's program. I mean, you
have to tell the thing that you're planning to read sequentially through
the file, but beyond that, the application program shouldn't have to
worry about it.

(When I programmed on VAX/VMS, I was appalled at the complexity of the
Record Management Services. I still don't know why all that complexity
is necessary, as compared to the Unix notion that a file is a sequence
of bytes. But I could be wrong -- I write compilers, mostly, which
don't need "fancy" I/O facilities.)

Nor do data base management systems. If you use something like the
RMS, your DBMS is probably not going to be very portable, and it is
not very likeley that the RMS idea of what properties and physical
layout a record should have matches the DBMS's ideas. I could make
similar complaints about the crazy idea of building so-called
"reliable" network protocols without regard to the rest of the system
(like TCP/IP), but I'll stop here.

The basic problem is that designers of services like file systems and
network protocols must assume soemthing about their clients. Often
that assumption is wrong, in which case the value of the service is
rather dubious. It is NOT easy to build complex mechanisms which must
be useable in a variety of contexts.

Graham Hughes

unread,
Mar 6, 1997, 3:00:00 AM3/6/97
to

-----BEGIN PGP SIGNED MESSAGE-----

o...@edeber.tfdt-o.nta.no (Ole-Hjalmar Kristensen FOU.TD/DELAB) writes:
>It may be a mistake in some cases, but talking about "this mistake" is
>a vast oversimplification. Surely, there is nothing conceptually wrong
>with having a set of single character IO operations like putc, getc,
>and ungetc?

One important point here, in agreement with what you say: for a lot of
stuff (e.g., about 80% of the stuff I program routinely), text I/O is a
major portion of the code. Things like scanners, editors, filters, and
others all require a good I/O interface, but also are most convenient
when read a character at a time.

When the standard libraries do buffering automatically, we win.
Low-level escapes like read() and write() could be retained, but having
fread() and cousins as a part of the library means that I don't have to
go implementing a buffering routine every time I want to do something
trivial. If somebody wants buffering off, then let them, but most
programs will want buffering.

Personally, if I'm going to have to work around GNAT not having I/O
buffering, I'm probably going to write it in Icon, Perl, C, C++,
Python, or any of a hundred other languages that do this for me. My
time is better spent coding, not writing buffers, and I'm going to have
to write buffers just for the sake of program speed.
- --
Graham Hughes (graham...@resnet.ucsb.edu)
http://A-abe.resnet.ucsb.edu/~graham/ -- MIME & PGP mail OK.
"Never attribute to malice that which can be adequately explained by
stupidity." -- Hanlon's Razor

-----BEGIN PGP SIGNATURE-----
Version: 2.6.3
Charset: noconv

iQCVAwUBMx6guiqNPSINiVE5AQEzyAP8DAbVaLEW7JFj6awX57mJQkvv7GAXruzY
0tiZRiEClTQaDCiyileSlxpXLXW07fR5XZiGiblwOy5WHK3QX+f6RJ+KbEEYL1pS
2UzEiUxwMX8L3i1nzVi/02Re40bFFWA0AlrI6fp/EK1JP8qg07V7b/bBOUYfj1gp
mA1DiGSqs8E=
=gKP9
-----END PGP SIGNATURE-----

Robert Dewar

unread,
Mar 6, 1997, 3:00:00 AM3/6/97
to

Bob Duff said

<<Agreed, but that's what inlining is for. All I was saying is that there
should be a standard package that does efficient I/O, with buffering,
and of course you want to inline a call that just bumps a pointer and
grabs a character out of a buffer (except in the rare case where the
buffer is exhausted). Unfortunately, Text_IO has an awful lot of
nearly-useless cruft in it. But why can't Stream_IO fit the bill here?>>

It can, but be careful. If you write String'Input, then not only do you
get the overhead of going character by character, unless a lot of
special optimization is at work, but you also get the general inefficiency
of dealing with unconstrained variable length objects, which usually
involves at least one extra copy. The character by character reads come
from the fact that this is the semantics of String'Input. yes, it could
indeed be optimized (in the normal case, where a user level attribute is
not supplied for type character), but you cannot count on that.

More likely to be efficient is using Read and Write directly on
buffers of stream elements.

Indeed it is perfectly easy, and probably safest to do your own
buffering in many cases (the same advice applies to C, it may be
efficient to do indidvidual getchar's, but it may also be a disaster
from an efficiency point of view.

Robert Dewar

unread,
Mar 6, 1997, 3:00:00 AM3/6/97
to

Larry Kilgallen <kilg...@eisner.decus.org> wrote:

<<While theoretical computing and Alan Turing may be centered on
the equivalence and correctness of programs, in the real world
performance is also a consideration.>>

This shows a big misunderstanding of the theory of correctness. If
performance is part of the requirement, it must be part of the
specification, and thus part of the criterion for correctness. This
is not to say it is easy to prove correctness for such specifications,
it is indeed hard. But there is a lot of work of value here, which
I recommend Larry investigate before dismissing it in such a
cavalier manner :-)

Robert Dewar

unread,
Mar 6, 1997, 3:00:00 AM3/6/97
to

Bob Duff said

<<(When I programmed on VAX/VMS, I was appalled at the complexity of the
Record Management Services. I still don't know why all that complexity
is necessary, as compared to the Unix notion that a file is a sequence
of bytes. But I could be wrong -- I write compilers, mostly, which
don't need "fancy" I/O facilities.)>>

Well this is an old discussion, the trouble in Unix is that there are
no standardized file formats for simple things like indexed sequential
files, and indeed, until recently, Unices have paid little attention
to I/O efficiency. If you spend 90% of your time running Syncsort on
mainframes, it is quite important to be able to describe the layout
of your file data precisely, including its positioning on external
devices (just to take one example of appalling complexity).

Yes, compiler writers don't need much in the way of I/O support, that's
true, but I don't think you can extend this experience very far. In
practice VMS is very successful in a segment of the market where Unix
has been quite unsuccessful, and the RMS facilities are one important
component in this success.


Fergus Henderson

unread,
Mar 6, 1997, 3:00:00 AM3/6/97
to

kilg...@eisner.decus.org (Larry Kilgallen) writes:

>bob...@world.std.com (Robert A Duff) writes:
>>

>> I think I disagree. Buffering should be the job of the OS and/or
>> standard libraries. Not every program.
>

>While theoretical computing and Alan Turing may be centered on
>the equivalence and correctness of programs, in the real world
>performance is also a consideration.

Sure. That's why buffering is needed. But buffering should be the


job of the OS and/or standard libraries.

>Just as those using intense


>computation will be concerned about the efficiency of their
>algorithms, those accessing large databases will take care
>regarding order-of-access so as not to go skipping over the
>whole thing when some locality-of-reference would yield better
>performance.

Sure. No disagreement here.

>Those reading sequentially from disk should
>likewise concern themselves with performance, and 512 calls
>to even the lightest-weight library is too much if a single
>call would do.

Nonsense, if the calls are inlined, and the compiler does a good
job of optimization, there is no reason why the cost need be too much.

>For the stated problem (CRC) reading large
>blocks is a clear win.

Yes, but that is true for just about all performance-intensive stream
I/O tasks. That's why it makes sense for this to be done by the
standard library and/or OS.

>> I'm not sure why reading a file character-by-character is "C-like".
>> It seems like the natural way to write lots of programs, in any
>> language. The underlying language and OS should ensure that it can be
>> done efficiently (by making the "give-me-a-char" routine read from a
>> buffer whenever appropriate).
>
>In my experience it is generally C programmers who make this mistake.

Why is it a mistake?

If the implementation implements it efficiently, as it should,
I don't see any reason to regard using such a mechanism as a mistake.

--
Fergus Henderson <f...@cs.mu.oz.au> | "I have always known that the pursuit
WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit"
PGP: finger f...@128.250.37.3 | -- the last words of T. S. Garp.

Larry Kilgallen

unread,
Mar 6, 1997, 3:00:00 AM3/6/97
to

In article <E6Lpv...@world.std.com>, bob...@world.std.com (Robert A Duff) writes:
> In article <1997Mar5.131846.1@eisner>,
> Larry Kilgallen <kilg...@eisner.decus.org> wrote:

>>In my experience it is generally C programmers who make this mistake.

>>Perhaps it because many of them come from a Unix background where there
>>is no strong sense of a "record". On the other hand, it may just be
>>that there are so many C programmers that statistically speaking most
>>of the mistakes made will be made by a C programmer.
>

> I still don't think it's a "mistake" to expect buffering to be done by
> standard packages, rather than by every user's program. I mean, you
> have to tell the thing that you're planning to read sequentially through
> the file, but beyond that, the application program shouldn't have to
> worry about it.

If one were to espouse the Unix paridigm of "stream of bytes",
it seems to me the logical representation of that is an array
(at least for files less than 1 GB if you do not have 64-bit
addressing). For large (compared to resources made available
by the operating system) file IO mechanisms such as provided
with Ada are needed.

> (When I programmed on VAX/VMS, I was appalled at the complexity of the
> Record Management Services. I still don't know why all that complexity
> is necessary, as compared to the Unix notion that a file is a sequence
> of bytes. But I could be wrong -- I write compilers, mostly, which
> don't need "fancy" I/O facilities.)

But there are more people writing financial software (in general)
than writing compilers. I write some programs were that record
stuff is crucial and some where it is skipped.

> Note that Ada compilers don't typically use Text_IO to read the source
> code! ;-)

And typical VMS compilers (meaning those from DEC) don't use RMS to
read those characters either. They map the files into their virtual
address space and compile directly out of memory. (Of course they
have alternate strategies for rare special cases such as compiling
from a magnetic tape or compiling from the keyboard). This is
perilously close to the "stream of bytes is an array" approach.

But compiler writers do this with a full understanding of the
performance characteristics of their environment. It is impossible
to write a program which performs well on all operating systems without
taking into account the varying characteristics of the operating systems.
The variable block-size disks used on MVS provide a swift example
where generality does not cut the mustard.

Larry Kilgallen

Larry Kilgallen

unread,
Mar 6, 1997, 3:00:00 AM3/6/97
to

In article <OHK.97Ma...@edeber.tfdt-o.nta.no>, o...@edeber.tfdt-o.nta.no (Ole-Hjalmar Kristensen FOU.TD/DELAB) writes:

> In article <1997Mar5.131846.1@eisner> kilg...@eisner.decus.org (Larry Kilgallen) writes:

> performance. Those reading sequentially from disk should


> likewise concern themselves with performance, and 512 calls
> to even the lightest-weight library is too much if a single

> call would do. For the stated problem (CRC) reading large


> blocks is a clear win.
>

> I think you are missing something here. Altough in Unix it IS possible
> to do reads of arbitrary length, the standard IO library of C
> definitely does IO in blocks. The getc/putc functions are
> usually implemented as macros, which just manipulate the buffer. Of

And relying on performance characteristics of a particular implementation
which are not mandated from implementation to implementation brings
problems. (Perhaps this implementation technique _is_ mandated,
but it is not something I would know.)

> > I'm not sure why reading a file character-by-character is "C-like".
> > It seems like the natural way to write lots of programs, in any
> > language. The underlying language and OS should ensure that it can be
> > done efficiently (by making the "give-me-a-char" routine read from a
> > buffer whenever appropriate).
>

> In my experience it is generally C programmers who make this mistake.
> Perhaps it because many of them come from a Unix background where there
> is no strong sense of a "record". On the other hand, it may just be
> that there are so many C programmers that statistically speaking most
> of the mistakes made will be made by a C programmer.

> It should be no harder to implement the putc/getc funtions on any


> other OS which allows you to do character IO in blocks, than it is in Unix.

And any vendor in the non-Unix space can choose to emulate as many
Unix characteristics as they choose, including performance-related
ones or not.

> It may be a mistake in some cases, but talking about "this mistake" is
> a vast oversimplification. Surely, there is nothing conceptually wrong
> with having a set of single character IO operations like putc, getc,
> and ungetc?

It is a mistake to assume performance semantics (if that is the term)
which are not present in the target environment.

Don't get me wrong, I think there are many instances for non-portable
code in the world. However just because something written in Ada (or
C) will compile and get the right answer in another environment, that
does not mean it is portable from the standpoint of the end user who
must wait for the results.

Larry Kilgallen

Larry Kilgallen

unread,
Mar 6, 1997, 3:00:00 AM3/6/97
to

In article <5fmo1k$a...@mulga.cs.mu.OZ.AU>, f...@mundook.cs.mu.OZ.AU (Fergus Henderson) writes:

> kilg...@eisner.decus.org (Larry Kilgallen) writes:
>
>>bob...@world.std.com (Robert A Duff) writes:

>>> I'm not sure why reading a file character-by-character is "C-like".
>>> It seems like the natural way to write lots of programs, in any
>>> language. The underlying language and OS should ensure that it can be
>>> done efficiently (by making the "give-me-a-char" routine read from a
>>> buffer whenever appropriate).
>>
>>In my experience it is generally C programmers who make this mistake.
>

> Why is it a mistake?
>
> If the implementation implements it efficiently, as it should,
> I don't see any reason to regard using such a mechanism as a mistake.

If a programmer _assumes_ that such a construct will be efficient,
when in fact it is _not_ efficient within a particular environment,
it is a mistake from a performance perspective.

I have run into programmers making this mistake over and over again.
In recent years their immediate response has been "Gee, it runs fast
on Unix", but in prior years their response was "Gee, it runs fast
on MVS". Obviously it is only the recent history where the C language
is involved, but the current generation seems much more surprised than
their MVS-centric predecessors.

An analogy would be developers who find their MS-DOS game cannot
write directly to the screen under Windows NT. That is a bit
rougher, as one has to start from scratch explaining the difference
between an operating system and a run-time library :-)

Larry Kilgallen

Jon S Anthony

unread,
Mar 6, 1997, 3:00:00 AM3/6/97
to

Right. That's a good example of the sort of thing I was fishing for,
but I guess it really had to do with the IO involved...

Robert A Duff

unread,
Mar 6, 1997, 3:00:00 AM3/6/97
to

In article <1997Mar6.114441.1@eisner>,

Larry Kilgallen <kilg...@eisner.decus.org> wrote:
>If a programmer _assumes_ that such a construct will be efficient,
>when in fact it is _not_ efficient within a particular environment,
>it is a mistake from a performance perspective.

OK, but where do you draw the line? Suppose I'm trying to write
portable software. I measure the performance on my current
OS/compiler/libraries, and it's fine. Can I assume that it will still
perform as expected on any other platform?

There don't seem to be any performance requirements in most standards.
E.g. an Ada compiler that implements assignment of integers by first
copying each bit one-by-one, and then doing 10,000 no-op instructions is
perfectly valid, according to the RM. But when I write code, I assume
that (32-bit) integer assignment, on a 100MHz machine, takes something
like 1/(10**8) seconds, give or take. Assuming I don't get a cache miss
or page fault. I assume it's not quadratic in the size of the variable
name, or some such oddity.

Why should I not assume that a get-character-from-file operation takes
more than a few instructions, on average? I know how to implement such
an operation, and it's not hard. If it turns out that some OS does it
slowly, then I feel righteous in blaming the OS. (Of course, from a
practical point of view, if that OS is popular, then I'll have to live
with its limitations.)

Remember this [sub]thread started with the claim that VMS folks had to
go to a lot of trouble to support those "evil" C programmers who wanted
to do char-by-char input. My response is: Good, somebody forced them to
do what they should do -- namely, implement char-by-char input
efficiently.

>I have run into programmers making this mistake over and over again.
>In recent years their immediate response has been "Gee, it runs fast
>on Unix", but in prior years their response was "Gee, it runs fast
>on MVS". Obviously it is only the recent history where the C language
>is involved, but the current generation seems much more surprised than
>their MVS-centric predecessors.

Seems pretty reasonable to me: if Unix or MVS can do it fast, why can't
whatever-OS-we're talking about do it fast? If not, it seems like the
fault of the OS, or the standard libraries implementation.

>An analogy would be developers who find their MS-DOS game cannot
>write directly to the screen under Windows NT. That is a bit
>rougher, as one has to start from scratch explaining the difference
>between an operating system and a run-time library :-)

I don't buy the analogy. If OS X can do some operation fast, and OS Y
does it much slower, then that's the fault of OS Y. (Assuming both OS's
are real operating systems -- that is, provide protection of address
spaces and so forth.) The write-directly-to-screen thing is different
-- as you say, one needs to explain the difference between MS-DOS and an
operating system.

- Bob

Robert Dewar

unread,
Mar 6, 1997, 3:00:00 AM3/6/97
to

Graham says

<<Personally, if I'm going to have to work around GNAT not having I/O
buffering, I'm probably going to write it in Icon, Perl, C, C++>>

Uh? GNAT uses exactly C stream semantics to read, it will be buffered
or unbuffered depending on whether the C streams are buffered or unbuffered
by default. As with C, setvbuf (I think I remember the name right) can e
used to control buffering.

More significant is that the Text_IO semantics has a lot of junk, like
column, line and page counting, which can introduce fundamental unwelcome
overhead.

If this is a problem, then of course it is perfectly easy to use the
C routines directly from Ada, or even GNAT.IO if you are using GNAT.

I recommend that people read the section on implementation of Text_IO
in the GNAT manual, which gives the EXACT correspondence between Ada
Text_IO and C stream IO.


Robert Dewar

unread,
Mar 6, 1997, 3:00:00 AM3/6/97
to

Fergus asks

<<>In my experience it is generally C programmers who make this mistake.

Why is it a mistake?>>

Tell you what Fergus, do a whole lot of timing tests comparing reading
character by character and reading large blocks, and come back and tell
us if it did not tell you the answer to that questin :-)


Ole-Hjalmar Kristensen FOU.TD/DELAB

unread,
Mar 7, 1997, 3:00:00 AM3/7/97
to

Bob Duff said

It may certainly be less effective, but I cannot think of any
implementation where it would be a disaster. The C single char IO
operations are not complicated, and have very little overhead. What
makes you think otherwise?


Ole-Hjalmar Kristensen FOU.TD/DELAB

unread,
Mar 7, 1997, 3:00:00 AM3/7/97
to

Fergus asks

OK, I'll bite:

The following two simple programs have been tested on a 24443068 byte
file, both compiled wit -O7 on the Centerline C compiler:

#include <stdio.h>

main() {
setvbuf(stdin,0,_IOFBF,4096);
int c,total=0;
while ((c = getc(stdin)) != EOF) total++;
printf("total %d\n",total);
}

Average results obtained with time:
2.28u 0.28s 0:02.66 96.2%

char buf[4096];

main() {
int c,n,total=0;
while ((n = read(0,buf,sizeof(buf))) > 0) {
int i;
for (i = 0; i < n; i++) {
c = buf[i];
total++;
}
}
printf("total %d\n",total);
}

Average results obtained with time:
0.12u 0.29s 0:00.41 100.0%


As you can see, the time used by the OS is pretty much the same in
both cases.

It is somewhat surprising that the difference between the user CPU
times is so large, but I'm more surprised by the speed of the second
version than by the slowness of the first.

Depending on what your program is really going to do with the 24443068
bytes, the 2.5 seconds spent in the C standard IO library may or may
not be significant....


Ole-Hjalmar Kristensen FOU.TD/DELAB

unread,
Mar 7, 1997, 3:00:00 AM3/7/97
to

In article <1997Mar6.091150.1@eisner> kilg...@eisner.decus.org (Larry Kilgallen) writes:

In article <OHK.97Ma...@edeber.tfdt-o.nta.no>, o...@edeber.tfdt-o.nta.no (Ole-Hjalmar Kristensen FOU.TD/DELAB) writes:

> In article <1997Mar5.131846.1@eisner> kilg...@eisner.decus.org (Larry Kilgallen) writes:

> performance. Those reading sequentially from disk should
> likewise concern themselves with performance, and 512 calls
> to even the lightest-weight library is too much if a single
> call would do. For the stated problem (CRC) reading large
> blocks is a clear win.
>
> I think you are missing something here. Altough in Unix it IS possible
> to do reads of arbitrary length, the standard IO library of C
> definitely does IO in blocks. The getc/putc functions are
> usually implemented as macros, which just manipulate the buffer. Of

And relying on performance characteristics of a particular implementation
which are not mandated from implementation to implementation brings
problems. (Perhaps this implementation technique _is_ mandated,
but it is not something I would know.)

No, it is not mandated, but every implementation I have ever seen,
has done it that way. NB, this has NOTHING to do with Unix, but with
the C standard IO library. And of course, you are right, language and
libraray specifications do not in general say anything about
performance. You cannot count on block IO being efficient either, but
I'll agree it's a good bet :-)

> > I'm not sure why reading a file character-by-character is "C-like".
> > It seems like the natural way to write lots of programs, in any
> > language. The underlying language and OS should ensure that it can be
> > done efficiently (by making the "give-me-a-char" routine read from a
> > buffer whenever appropriate).
>

> In my experience it is generally C programmers who make this mistake.

> Perhaps it because many of them come from a Unix background where there
> is no strong sense of a "record". On the other hand, it may just be
> that there are so many C programmers that statistically speaking most
> of the mistakes made will be made by a C programmer.

> It should be no harder to implement the putc/getc funtions on any
> other OS which allows you to do character IO in blocks, than it is in Unix.

And any vendor in the non-Unix space can choose to emulate as many
Unix characteristics as they choose, including performance-related
ones or not.

Again, the C standard IO library has nothing to do with Unix. The
question is whether the vendor has implemnted this library efficiently
or not, based on the mechanisms available in the OS.

> It may be a mistake in some cases, but talking about "this mistake" is
> a vast oversimplification. Surely, there is nothing conceptually wrong
> with having a set of single character IO operations like putc, getc,
> and ungetc?

It is a mistake to assume performance semantics (if that is the term)
which are not present in the target environment.

I agree 100%. Which means that you have to run your program and
profile it anyway.

Don't get me wrong, I think there are many instances for non-portable
code in the world. However just because something written in Ada (or
C) will compile and get the right answer in another environment, that
does not mean it is portable from the standpoint of the end user who
must wait for the results.

Larry Kilgallen

There is no such thing as portable, high-performance, code which does
IO :-)

Ole-Hj. Kristensen

Larry Kilgallen

unread,
Mar 7, 1997, 3:00:00 AM3/7/97
to

In article <E6n85...@world.std.com>, bob...@world.std.com (Robert A Duff) writes:
> In article <1997Mar6.114441.1@eisner>,
> Larry Kilgallen <kilg...@eisner.decus.org> wrote:
>>If a programmer _assumes_ that such a construct will be efficient,
>>when in fact it is _not_ efficient within a particular environment,
>>it is a mistake from a performance perspective.
>
> OK, but where do you draw the line? Suppose I'm trying to write
> portable software. I measure the performance on my current
> OS/compiler/libraries, and it's fine. Can I assume that it will still
> perform as expected on any other platform?

Starting with something which performs well in at least one environment
is certainly a bare minimum. I happen to think there is a need to plan
for revisiting performance when switching environments.

> Why should I not assume that a get-character-from-file operation takes
> more than a few instructions, on average? I know how to implement such
> an operation, and it's not hard. If it turns out that some OS does it
> slowly, then I feel righteous in blaming the OS. (Of course, from a
> practical point of view, if that OS is popular, then I'll have to live
> with its limitations.)

Why should finding a record with particular contents in the middle of
a file take a long time? There are books about how to write indexed
file systems, but some operating systems skipped that part of what I
am accustomed to relying upon. I don't include that to start a
feature war, but to introduce the next question: How hard is it to
get-character-from-file when the file has all that baggage used to
find records with with particular contents ? DEC compilers run
more slowly when fed such a file, because it is beyond the ability
programmed into their map-it-into-memory trick.

What you (or I) see as limitations in a particular selection of
compiler/os/library may be exactly what someone else needs to do
their job.

> Remember this [sub]thread started with the claim that VMS folks had to
> go to a lot of trouble to support those "evil" C programmers who wanted
> to do char-by-char input. My response is: Good, somebody forced them to
> do what they should do -- namely, implement char-by-char input
> efficiently.

While I understand that is your view on what they should do, not all
will share it. The last time I needed to do character-at-a-time IO was
to emulate an editor which required a termination character on input
_unless_ the first character was one particular alphabetic character
(which had no special meaning in other than the first position). I
have been faced with a different set of projects than you, but I have
my own list of things that "any environment ought to do properly" such
as file versioning :-).

>>I have run into programmers making this mistake over and over again.
>>In recent years their immediate response has been "Gee, it runs fast
>>on Unix", but in prior years their response was "Gee, it runs fast
>>on MVS". Obviously it is only the recent history where the C language
>>is involved, but the current generation seems much more surprised than
>>their MVS-centric predecessors.
>
> Seems pretty reasonable to me: if Unix or MVS can do it fast, why can't
> whatever-OS-we're talking about do it fast? If not, it seems like the
> fault of the OS, or the standard libraries implementation.

Sorry if I was unclear, but Unix and MVS could not do the _same_thing_
fast. The only commonality was that people coming from Unix and
people coming from MVS both assumed that the new operating system
would have the same performance characteristics as the one they are
coming from. Now obviously it is impossible for the target operating
system to fully mimic the behaviour of both Unix and MVS at the same
time to make both camps happy.

Larry Kilgallen

David Brown

unread,
Mar 7, 1997, 3:00:00 AM3/7/97
to

o...@edeber.tfdt-o.nta.no (Ole-Hjalmar Kristensen FOU.TD/DELAB) writes:

> char buf[4096];
>
> main() {
> int c,n,total=0;
> while ((n = read(0,buf,sizeof(buf))) > 0) {
> int i;
> for (i = 0; i < n; i++) {
> c = buf[i];
> total++;
> }
> }
> printf("total %d\n",total);
> }
>
> Average results obtained with time:
> 0.12u 0.29s 0:00.41 100.0%
>

> It is somewhat surprising that the difference between the user CPU
> times is so large, but I'm more surprised by the speed of the second
> version than by the slowness of the first.

I suspect that most of the inner loop is being optimized out. Since
you don't actually do anything with 'c', it probably is never actually
used. The buffer is probably never accessed. A slightly better test
would be to compute a simple checksum or something.

Dave Brown
dbr...@vigra.com

Robert A Duff

unread,
Mar 7, 1997, 3:00:00 AM3/7/97
to

In article <1997Mar7.090814.1@eisner>,

Larry Kilgallen <kilg...@eisner.decus.org> wrote:
>Why should finding a record with particular contents in the middle of
>a file take a long time? There are books about how to write indexed
>file systems, but some operating systems skipped that part of what I
>am accustomed to relying upon. ...

Good point, I admit.

>have been faced with a different set of projects than you, but I have
>my own list of things that "any environment ought to do properly" such
>as file versioning :-).

That one's on my list, too. :-)

- Bob

Robert Dewar

unread,
Mar 7, 1997, 3:00:00 AM3/7/97
to

Fergus said

<<It is somewhat surprising that the difference between the user CPU
times is so large, but I'm more surprised by the speed of the second
version than by the slowness of the first.>>

Well it does not surprise me, and I don't really understand why it
surprises you. I would expect a large difference here, and indeed
it is what we see!

Just shows that measurements can be a useful substitute for guesswork,
though measurements have the weakness of being system specific, so
nothing really substitutes for a lot of experience on a lot of difrerent
machiens!


Robert Dewar

unread,
Mar 7, 1997, 3:00:00 AM3/7/97
to

iRobert Duff says

<<OK, but where do you draw the line? Suppose I'm trying to write
portable software. I measure the performance on my current
OS/compiler/libraries, and it's fine. Can I assume that it will still
perform as expected on any other platform?
>>

No, you can't, but you are expected to have a good feel for what is
efficient and what is not efficient over a wide range of platforms if
you are trying to write portable code that is efficient. This is one
of the skills that is required for writing such code. Yes, it is VERY
hard to acquire this skill and the knowledge base required to support it!!


Tom Moran

unread,
Mar 7, 1997, 3:00:00 AM3/7/97
to

The original message in this thread did not say "reading a file a
character at a time is slow", but rather that doing it in Ada was an
order of magnitude slower than doing it in C, on the same OS and
hardware. Since there is no other way strictly in Ada to read a file
which is too large for memory and whose size is a prime number, this is
unfortunate. And saying Ada 95 can do it by calling a C function, is
less than a strong endorsement of Ada.

Robert Dewar

unread,
Mar 7, 1997, 3:00:00 AM3/7/97
to

TD/DELAB (?) said

<<It may certainly be less effective, but I cannot think of any
implementation where it would be a disaster. The C single char IO
operations are not complicated, and have very little overhead. What
makes you think otherwise?
>>

I'll tell you what. Go measure the relative speed of reading a 1 meg
file a character at a time, vs using read to read the entire 1 meg at
a time. Do this measurement on at least six different systems. Come
back here with the results and we will discuss them!


John Apa

unread,
Mar 7, 1997, 3:00:00 AM3/7/97
to

Stephen Garriga wrote:
>

snip

> _IF_ you are doing the CRC on a file (as I was), I would advise you
> to consider performance. I found (exactly the same algorithm)
> implemented in C took an order of magnitude seconds less to execute
> than the Ada equivalent.

Perhaps, but it so happens that I also implemented a crc algorithm in
both c and ada. I found that the ada was slightly faster (sun & i960,
using gnat for both) when running on disk files, and about even when
running against memory sections. Hmm.

IMVHO: Any broad statement (C faster than Ada, or the converse) will be
found to have counter examples. Results may vary, as has been shown in
this group time and again. Choosing c or ada without looking at the
results from your particular implementations is simply bad engineering.
If you have a good compiler and knowledge of the language, you can write
very good/fast/safe/_understandable_ code. Ada95 has added many features
which will assist in this for a variety of situations and systems.

To those who don't think ada95 is the best thing out there right now,
read the Rationale for this ANSI/ISO/IEC standard. It should change your
mind. You could read the one for c++, but only if you're a physic. ;-)

John

>
> Steve Garriga gar...@logica.com
> type OPINION is access PERSONAL_THOUGHTS_AND_BIAS;
> OPINION_STATED : new OPINION := not LOGICA.OPINION;
> Logica UK Ltd. +44 171 637 9111 http://www.logica.com

--
***********************************
That's my opinion, not Honeywell's.
John Thomas Apa
Honeywell Defense Avionics Systems
Albuquerque, New Mexico.
***********************************

Robert Dewar

unread,
Mar 8, 1997, 3:00:00 AM3/8/97
to

Larry says

<<As for a C implementation being better than an Ada implementation
at single character reads, I imagine there must be another language
characteristics where Ada has some advantage or other.>>

The comparison between C and Ada here is apples-oranges. Text_IO.Get
has far more elaborate semantics than getchar, so you cannot compare
the two. This is a common effect (see another example below). If you
want the simple minded semantics of getchar, then this is trivially
programmed in Ada (the GNAT package GNAT.IO is a much closer approximation
to the C level semantics).

Another interesting case of this is a timing comparison that Bob Klungle
sent me comparing the use of the official log and the log in the
"secret" package Aux. The log in Aux is a direct call to C, the log
in Ada has rather different semantics, as you can see from its coding:

function Log (X : Float_Type'Base) return Float_Type'Base is
begin
if X < 0.0 then
raise Argument_Error;

elsif X = 0.0 then
raise Constraint_Error;

elsif X = 1.0 then
return 0.0;
end if;

return Float_Type'Base (Aux.Log (Double (X)));
end Log;

Those extra tests, required by Ada semantics, end up making the use of
the Ada log function very much slower (almost a factor of two in Bob's tests)
which is a bit worrisome -- safety and accuracy are not free :-)


Robert A Duff

unread,
Mar 8, 1997, 3:00:00 AM3/8/97
to

In article <dewar.857749952@merv>, Robert Dewar <de...@merv.cs.nyu.edu> wrote:
>I'll tell you what. Go measure the relative speed of reading a 1 meg
>file a character at a time, vs using read to read the entire 1 meg at
>a time. Do this measurement on at least six different systems. Come
>back here with the results and we will discuss them!

I think the presumption is that the program needs to look at each
character, one at a time. So to make it a fair test, you need to loop
through all the characters and do something with them. Preferably
something that will prevent optimizing away the whole loop (like add
them up and print out the result at the end). The first program should
read a character at a time, and do something. The second should read
into a giant buffer, and *then* loop through it doing (the same)
something.

- Bob

Fergus Henderson

unread,
Mar 8, 1997, 3:00:00 AM3/8/97
to

de...@merv.cs.nyu.edu (Robert Dewar) writes:

>Fergus said
>
><<It is somewhat surprising that the difference between the user CPU
>times is so large, but I'm more surprised by the speed of the second
>version than by the slowness of the first.>>

Those weren't my words. You are quoting o...@edeber.tfdt-o.nta.no
("Ole-Hjalmar Kristensen FOU.TD/DELAB"), not me.

Dr. John B. Matthews

unread,
Mar 9, 1997, 3:00:00 AM3/9/97
to

In article <dewar.857652688@merv>, de...@merv.cs.nyu.edu (Robert Dewar) writes:
> More likely to be efficient is using Read and Write directly on
> buffers of stream elements.

Yes. In the code below I tried to compare Sequential_IO to Stream_IO
for the two extremes of one-at-a-time vs all-at-once (imagining
a buffered approach to fall between). In the one-at-a-time
procedures, I assumed knowledge of the file's length instead of
calling the relevant End_Of_File predicate; in the all-at-once
procedures, I looped through the resulting buffer.

For Sequential_IO, all-at-once is clearly faster than
one-at-a-time. Stream_IO is more interesting: In Stream_All1,
String'Read is actually slower than looping with Character'Read, as
the former calls Character'Read in a loop, checking for EOF as it
goes. The fastest approach seems to be to read the stream elements
directly, as in Stream_All2.

John
----------------------------------------------------------------
John B. Matthews, M.D.
jmat...@nova.wright.edu; john_m...@ccmail.dayton.saic.com
"Whom the gods would destroy, they first invite to program in C"
------------------------------------------------------------------
--|
--| iotest: time IO
--|
--| Author: John B. Matthews, Wright State University
--| Last Modified: March 8, 1997
--|
------------------------------------------------------------------
-- results of 6 runs on a 451239 byte file:
-- ave. std.dev.
-- 1.00278 0.03391 sequential, one character at a time.
-- 0.72499 0.02679 sequential, entire file.
-- 1.26389 0.01146 stream, one character at a time.
-- 1.41389 0.09738 stream, entire file 1.
-- 0.65113 0.08572 stream, entire file 2.
------------------------------------------------------------------
-- build: gnatmake iotest -largs -Xlstack=500000 (or so)

with Ada.Command_Line;
with Ada.Sequential_IO;
with Ada.Streams.Stream_IO;
with Ada.Text_IO;
with Calendar; use type Calendar.Time;

procedure IOTest is

package CLI renames Ada.Command_Line;
package Text_IO renames Ada.Text_IO;
package Fixed_IO is new Ada.Text_IO.Fixed_IO (Duration);

Length : Natural;
Start, Stop : Calendar.Time;

-- Determine the size (in bytes) of the file, Name.
function File_Size (Name : in String) return Natural is
package SIO renames Ada.Streams.Stream_IO;
F : SIO.File_Type;
Size : Natural;
begin
SIO.Open (F, SIO.In_File, Name);
Size := Integer (SIO.Size(F));
SIO.Close (F);
return Size;
end File_Size;

procedure Sequential_One (Name : String; Length : Natural) is
package SIO is new Ada.Sequential_IO (Character);
F : SIO.File_Type;
C : Character;
begin
SIO.Open (F, SIO.In_File, Name);
for i in 1 .. Length loop
SIO.Read (F, C);
end loop;
SIO.Close (F);
end Sequential_One;

procedure Sequential_All (Name : String; Length : Natural) is
subtype Data is String (1 .. Length);
package SIO is new Ada.Sequential_IO (Data);
F : SIO.File_Type;
S : Data;
C : Character;
begin
SIO.Open (F, SIO.In_File, Name);
SIO.Read (F, S);
for i in 1 .. Length loop
C := S (i);
end loop;
SIO.Close (F);
end Sequential_All;

procedure Stream_One (Name : String; Length : Natural) is
package SIO renames Ada.Streams.Stream_IO;
F : SIO.File_Type;
S : SIO.Stream_Access;
C : Character;
begin
SIO.Open (F, SIO.In_File, Name);
S := SIO.Stream (F);
for i in 1 .. Length loop
Character'Read (S, C);
end loop;
SIO.Close (F);
end Stream_One;

procedure Stream_All1 (Name : String; Length : Natural) is
subtype Data is String (1 .. Length);
package SIO renames Ada.Streams.Stream_IO;
F : SIO.File_Type;
S : Data;
C : Character;
begin
SIO.Open (F, SIO.In_File, Name);
Data'Read (SIO.Stream (F), S);
for i in 1 .. Length loop
C := S (i);
end loop;
SIO.Close (F);
end Stream_All1;

procedure Stream_All2 (Name : String; Length : Natural) is
subtype Data is String (1 .. Length);
package SIO renames Ada.Streams.Stream_IO;
F : SIO.File_Type;
S : Ada.Streams.Stream_Element_Array
(1 .. Ada.Streams.Stream_Element_Offset(Length));
L : Ada.Streams.Stream_Element_Offset;
C : Ada.Streams.Stream_Element;
begin
SIO.Open (F, SIO.In_File, Name);
SIO.Read (F, S, L);
for i in 1 .. L loop
C := S (i);
end loop;
SIO.Close (F);
end Stream_All2;

begin

if CLI.Argument_Count = 1 then

Length := File_Size (CLI.Argument (1));

Start := Calendar.Clock;
Sequential_One (CLI.Argument (1), Length);
Stop := Calendar.Clock;
Fixed_IO.Put (Stop - Start, 0, 5);
Text_IO.Put_Line (" sequential, one character at a time.");

Start := Calendar.Clock;
Sequential_All (CLI.Argument (1), Length);
Stop := Calendar.Clock;
Fixed_IO.Put (Stop - Start, 0, 5);
Text_IO.Put_Line (" sequential, entire file." );

Start := Calendar.Clock;
Stream_One (CLI.Argument (1), Length);
Stop := Calendar.Clock;
Fixed_IO.Put (Stop - Start, 0, 5);
Text_IO.Put_Line (" stream, one character at a time.");

Start := Calendar.Clock;
Stream_All1 (CLI.Argument (1), Length);
Stop := Calendar.Clock;
Fixed_IO.Put (Stop - Start, 0, 5);
Text_IO.Put_Line (" stream, entire file 1.");

Start := Calendar.Clock;
Stream_All2 (CLI.Argument (1), Length);
Stop := Calendar.Clock;
Fixed_IO.Put (Stop - Start, 0, 5);
Text_IO.Put_Line (" stream, entire file 2.");

else
Text_IO.Put_Line ("Usage: iotest <filename>");
end if;

end IOTest;


Robert Dewar

unread,
Mar 9, 1997, 3:00:00 AM3/9/97
to

OUe-Hjalmar says

> I think you are missing something here. Altough in Unix it IS possible
> to do reads of arbitrary length, the standard IO library of C
> definitely does IO in blocks. The getc/putc functions are
> usually implemented as macros, which just manipulate the buffer. Of


You cannot make such statements (the standard IO lbrary of C definitely
does IO in blocks). The standard speaks only of interfaces, not of
implementation, there is nothing in the standardized interface that requires
IO to be done in blocks. This may be an implementation characterstic of some
or even most or even all current implementations, but it is NOT a fundamental
property of the standard IO library.


Geert Bosch

unread,
Mar 9, 1997, 3:00:00 AM3/9/97
to

Robert Dewar (de...@merv.cs.nyu.edu) wrote:
Another interesting case of this is a timing comparison that Bob Klungle
sent me comparing the use of the official log and the log in the
"secret" package Aux. The log in Aux is a direct call to C, the log
in Ada has rather different semantics, as you can see from its coding:

But what surprises me is that in cases where the argument is *known*
to be larger than 1.0 the checks are still being made. Normally I would
use a subtype Positive_Float for values which should be positive in a
calculation. This will give a good compiler the opportunity to omit the
extra comparisons in the Ada code.

Sadly enough GNAT is not (yet) such a good compiler in this respect.
In fact GNAT should be able to generate faster code for invocations of
the log function for such arguments, since it can inline the function
to *only* contain the log instruction.

There are many real-world examples where optimizations like these
can make a difference of a factor 3 and more, so I guess these
optimizations satisfy Robert Dewars criterea.

Also the requirement to return 0.0 when the argument is 1.0 doesn't need
to generate extra code, since the check could be changed in Accurate_Log_1
and then X = 1.0, and the boolean value Accurate_Log_1 can be determined
at compile time.
(To be honest, this might not be possible for platforms where
the program may run on different numeric processors. In this case
the check must be done at elaboration time which leaves in the
boolean check.)

Regards,
Geert

Robert Dewar

unread,
Mar 10, 1997, 3:00:00 AM3/10/97
to

Tom Moran says

This makes no sense at all. My best guess is that the business about
prime numbers is talking about trying to misuse direct_io to read the
file.

The proper way to read this file in Ada 95 is to use Stream_IO into
a stream element buffer. The imagined "prime number" restriction
does not exist, and in practice this should be highly efficient.

I am afraid this is just misinformation that comes from misunderstanding.


Ole-Hjalmar Kristensen FOU.TD/DELAB

unread,
Mar 10, 1997, 3:00:00 AM3/10/97
to

OUe-Hjalmar says

Yes, of course you are right. I plead guilty of using imprecise language.

But I still would say that this is the only reasonable implementation,
especially as functions to explicitly control the buffering and flush
the buffer is part of the specification. You could just as well argue
that if you use the write system call, you have no guarantee that the
OS does not actually write a single byte at a time to the disk...
Maybe the standards should say something about the precise semantics
at this level as well.

Anyway, you seem to have missed my point, which is that as all the
Unix standard IO libraries I am aware og does block IO anyway, it
would not be any harder to implement such a library on any other OS
which have block IO but not single char IO as part of the system
calls.
The flexibility of the Unix read and write calls is not needed by the
usual implementations of the C standard IO library.

Ole-Hj. Kristensen

Ole-Hjalmar Kristensen FOU.TD/DELAB

unread,
Mar 10, 1997, 3:00:00 AM3/10/97
to

In article <dewar.857750112@merv> de...@merv.cs.nyu.edu (Robert Dewar) writes:


Fergus said

<<It is somewhat surprising that the difference between the user CPU
times is so large, but I'm more surprised by the speed of the second
version than by the slowness of the first.>>

Well it does not surprise me, and I don't really understand why it


surprises you. I would expect a large difference here, and indeed
it is what we see!

Just shows that measurements can be a useful substitute for guesswork,
though measurements have the weakness of being system specific, so
nothing really substitutes for a lot of experience on a lot of difrerent
machiens!

He didn't say it, I did.

So tell me, why would you expect a large difference?
I would expect the optimizer to recognize that both (&_iob[0])->_cnt
and (&_iob[0])->_ptr are constant expressions, so that the two loops
differ mainly in using indirect or direct addressing.
Bu I suppose Im'm expecting too much from optimizers.

Here is a version of the first program after it has passed through
cpp:

main() {
setvbuf((&_iob[0]),0,0000,4096);
int c,total=0;
while ((c = (--((&_iob[0]))->_cnt < 0 ? __filbuf((&_iob[0])) : (int)*((&_iob[0]))->_ptr++)) != (-1)) total++;


printf("total %d\n",total);
}

And the second:

main() {
int c,n,total=0;
while ((n = read(0,buf,sizeof(buf))) > 0) {
int i;
for (i = 0; i < n; i++) {
c = buf[i];
total++;
}
}
printf("total %d\n",total);
}

Ole-Hj. Kristensen


Tarjei Jensen

unread,
Mar 10, 1997, 3:00:00 AM3/10/97
to

>In article <332063...@bix.com> Tom Moran <tmo...@bix.com> writes:
>
> The original message in this thread did not say "reading a file a
> character at a time is slow", but rather that doing it in Ada was an
> order of magnitude slower than doing it in C, on the same OS and
> hardware. Since there is no other way strictly in Ada to read a file
> which is too large for memory and whose size is a prime number, this is
> unfortunate. And saying Ada 95 can do it by calling a C function, is
> less than a strong endorsement of Ada.
>

The usual explanation is that the C standard library buffers I/O while many
other languages does not have that requirement. If Ada required that the
stream I/O libraries had to support buffering then Ada would probably be as
fast as C for single character I/O.

The slowness of Ada is probably because each read triggers an system call which
reads a single character.

Good example: use Turbo Pascal under MSDOS and experiment with the buffer size
for the same program. Differences are dramatic.


Greetings,
--
// Tarjei T. Jensen
// tar...@ulrik.uio.no || fax +47 51664292 || voice +47 51 85 87 39
// Support you local rescue centre: GET LOST!
// Working, but not speaking for the Norwegian Hydrographic Service.

David Brown

unread,
Mar 10, 1997, 3:00:00 AM3/10/97
to

de...@merv.cs.nyu.edu (Robert Dewar) writes:

> The proper way to read this file in Ada 95 is to use Stream_IO into
> a stream element buffer. The imagined "prime number" restriction
> does not exist, and in practice this should be highly efficient.

Ok, so I am reading the file data into a stream element buffer
(Stream_Element_Array). My file, however, really consists of some
small objects (16 bit signed integers). What is the "proper" way to
get these integers out of this buffer? I want there to be as little
copying of these numbers as possible. Here are some solutions I've
come up with:

1. Have code to extract and insert my objects out of a stream element
array. These routines could be inlined and the access would end
up fast. However, they would be cumbersome to call because the
item wouldn't quite be an array.

2. Use for Foo'Address clauses or address to access conversions to
alias an array of my data on top of the stream element buffer.
Aside from the general feeling of grossness about this, I have
heard mentioned on this group that this is not the proper way of
aliasing two data items. Is there a "proper" way of doing this?

3. Use Ada.Storage_IO to convert the buffer into a buffer of my
data. This will cause a copy.

4. Just do my I/O by calling my underlying operating system calls.
This would probably be most efficient. With the GNAT runtime, the
stream IO read and write just call fread which on my OS doesn't do
a copy if the buffer is large enough. In other words, if I could
somehow avoid the copy in Ada, the Stream IO code would be
efficient enough.

Dave Brown
dbr...@vigra.com

Robert Dewar

unread,
Mar 10, 1997, 3:00:00 AM3/10/97
to

Ole-HJ said

<<But I still would say that this is the only reasonable implementation,
especially as functions to explicitly control the buffering and flush
the buffer is part of the specification.>>

YOu have lost me here, what do you mean when you say that functions to
explicitly control the buffering are part of the speciication. Yes
there is flush, but that's it ...


Robert Dewar

unread,
Mar 10, 1997, 3:00:00 AM3/10/97
to

Tarjei said

<<The usual explanation is that the C standard library buffers I/O while many
other languages does not have that requirement. If Ada required that the
stream I/O libraries had to support buffering then Ada would probably be as
fast as C for single character I/O.

The slowness of Ada is probably because each read triggers an system call which
reads a single character.>>

"If Ada required that the stream I/O libraries had to support buffering"

That is not the issue at all. The issue is that if you use String'Read
instead of reading into a buffer, the semantics pretty much imply character
by character reads, since such stream attribtues are by default executed
element wise. Yes, a compiler could optimize this, but is unlikely to.
The proper way to do fast stream_io is to read and write buffers of
stream elemkents.


Robert Dewar

unread,
Mar 10, 1997, 3:00:00 AM3/10/97
to

iTarjei said

<<The usual explanation is that the C standard library buffers I/O while many
other languages does not have that requirement. If Ada required that the
stream I/O libraries had to support buffering then Ada would probably be as
fast as C for single character I/O.>>

One more comment here: in GNAT, the I/O sits on top of the C standard
library stream I/O, you get whatever that layer gives you, so from the
point of view of system level access, the situation in GNAT is identical
to that in C. See GNAT reference manual for further details.


Tom Moran

unread,
Mar 10, 1997, 3:00:00 AM3/10/97
to

Robert Dewar says

> This makes no sense at all. My best guess is that the business about
> prime numbers is talking about trying to misuse direct_io to read the
> file.
>
> The proper way to read this file in Ada 95 is to use Stream_IO into
> a stream element buffer. The imagined "prime number" restriction
> does not exist, and in practice this should be highly efficient.
>
> I am afraid this is just misinformation that comes from misunderstanding.
>
Yes, you did misunderstand. The original post implied that the
comparison had taken place several years ago, which implies it was done
in Ada 83, which did not implement Stream_IO. The only "strictly in
Ada" way to read a file then was via Text, Sequential, or Direct_IO.
Both Sequential and Direct_IO require fixed size records. (Not strictly
true, but essentially true in practice. E.g., ActivAda, GNAT, and Janus
will all accept a "(string)" as the parameter to Sequential_IO, but all
three die on trying to actually read a text file in chunks that way.) So
the fixed buffer size, if one did *not* use Text_IO, would have to be a
divisor of the total file size. If the file size is a prime number,
it's divisors are itself and one. One takes us back to the original
byte-at-a-time that was 10x slower in Ada than C. If the whole file is
small enough to fit in memory, then we could use a single fixed size
record holding the entire file. If this doesn't fit in memory then that
option is not available, and byte-at-a-time is the only way, strictly in
Ada, to do the job. Yes, it can be done by calling the OS or a C
function, and I'm sure everyone has done this. But it doesn't make Ada
look particularly good to say "Oh yes, you can do it in Ada; just don't
use the Ada IO packages".

Graham Hughes

unread,
Mar 10, 1997, 3:00:00 AM3/10/97
to

-----BEGIN PGP SIGNED MESSAGE-----

de...@merv.cs.nyu.edu (Robert Dewar) writes:
>That is not the issue at all. The issue is that if you use String'Read
>instead of reading into a buffer, the semantics pretty much imply character
>by character reads, since such stream attribtues are by default executed
>element wise. Yes, a compiler could optimize this, but is unlikely to.
>The proper way to do fast stream_io is to read and write buffers of
>stream elemkents.

Perhaps. But the beauty of the C and other approaches is that I don't
have to write the buffer explicitly, and thus have to debug it. I *can*
read character by character if I want to, and often I do; socket
programming is a perfect example. But the rest of the time, I don't
want to worry about it, and don't have to.

Perhaps you feel that Unbounded_String is an abomination, because `the
proper way' to do arbitrary length strings is to do it yourself?
- --
Graham Hughes http://A-abe.resnet.ucsb.edu/~graham/ -- MIME & PGP mail OK.
PGP Key fingerprint = E9 B7 5F A0 F8 88 9E 1E 7C 62 D9 88 E1 03 29 5B

-----BEGIN PGP SIGNATURE-----
Version: 2.6.3
Charset: noconv

iQCVAwUBMyRu6SqNPSINiVE5AQH1igP/Twwim+fN+z59CCTsa+tQXyff/mvyLkEc
d97WaqyWJqpRpgQjTL86VfJnrkKGMitwajheMKqCDbEBFoDcCS6QnA5H1bUNgjPY
tcWIxxNQczCJf85ZLPpq96zdhSUQ8f9oJJPvo2RuuigIiTLp+i0wkSgtLAl/JEsK
kKUa5eEWAfw=
=52Ex
-----END PGP SIGNATURE-----

Dr. John B. Matthews

unread,
Mar 10, 1997, 3:00:00 AM3/10/97
to

In article <332063...@bix.com>, Tom Moran <tmo...@bix.com> writes:
> The original message in this thread did not say "reading a file a
> character at a time is slow", but rather that doing it in Ada was an
> order of magnitude slower than doing it in C, on the same OS and
> hardware. Since there is no other way strictly in Ada to read a file
> which is too large for memory and whose size is a prime number, this is
> unfortunate.

This can't be right. For example, Streams.Stream_IO.Read lets me
read into a buffer of arbitrary size, and politely tells me if
there's any stray elements in the last chunk.

> And saying Ada 95 can do it by calling a C function, is
> less than a strong endorsement of Ada.

For efficiency, I frequently call OS routines. I rarely know what
language they're written in, although I typically access them
through a language-specific interface. For example, under MacOS, I
use Pascal interfaces and C calling conventions. The ease with which
this can be done seems like a strong endorsement of Ada.

Jim Balter

unread,
Mar 10, 1997, 3:00:00 AM3/10/97
to

No, there is no flush, but there is fflush, and setbuf, setvbuf, _IOFBF,
_IOLBF, _IONBF, and BUFSIZ are all part of the specification; it really
helps if one limits one's authoritative claims to what one actually
knows something about. While it is true that an ANSI C
stdio implementation can send bytes by bicycle courier, "quality of
implementation" mandates against it. Byte-at-a-time C (or in fact
POSIX, and thus ADA, given a binding) programs perform well portably, a
fact that no amount of sophistry can cancel.

--
<J Q B>

Jim Balter

unread,
Mar 10, 1997, 3:00:00 AM3/10/97
to

Larry Kilgallen wrote:

> If a programmer _assumes_ that such a construct will be efficient,
> when in fact it is _not_ efficient within a particular environment,
> it is a mistake from a performance perspective.

This same argument was used to justify assembly language programming
for decades.

A programmer should assume that her tools are not broken, and that
she is not dealing with an anomalous case with unusually poor
performance, until and unless project requirements and empirical
measurements indicate otherwise.

> I have run into programmers making this mistake over and over again.
> In recent years their immediate response has been "Gee, it runs fast
> on Unix", but in prior years their response was "Gee, it runs fast
> on MVS". Obviously it is only the recent history where the C language
> is involved, but the current generation seems much more surprised than
> their MVS-centric predecessors.
>
> An analogy would be developers who find their MS-DOS game cannot
> write directly to the screen under Windows NT. That is a bit
> rougher, as one has to start from scratch explaining the difference
> between an operating system and a run-time library :-)

You are arguing against yourself. Putting screen I/O optimizations
into the lower system or library layers instead of embedding them into
every application is precisely the path for avoiding this sort of
problem. It is your "optimized" application that will fail miserably in
many environments, whereas my application that assumes an efficient
underlying buffering mechanism (or an optimizing compiler instead
of "clever" assembly code, or an abstract BLT operation that may well
be implemented in hardware instead of hand coding, or threads that
may be run in parallel processors instead of hand coded scheduling)
will run well in any environment that provides one, which means in
today's practice all of them. And an API is an API is an API; the line
between the OS and the run-time library has been quite blurred with
developments such as microkernels and dynamically linked libraries.
Welcome to the modern age.

--
<J Q B>

Jim Balter

unread,
Mar 10, 1997, 3:00:00 AM3/10/97
to

Larry Kilgallen wrote:

> Why should finding a record with particular contents in the middle of
> a file take a long time? There are books about how to write indexed
> file systems, but some operating systems skipped that part of what I

> am accustomed to relying upon. I don't include that to start a
> feature war, but to introduce the next question: How hard is it to
> get-character-from-file when the file has all that baggage used to
> find records with with particular contents ? DEC compilers run
> more slowly when fed such a file, because it is beyond the ability
> programmed into their map-it-into-memory trick.

How does one write a series of 3 megabyte text lines to a
record-oriented filesystem that was only designed with 16-bit record
lengths?

Putting record indexing into the filesystem is putting it at the wrong
level of abstraction. Commercial databases are written on UNIX
systems by doing direct I/O to disk devices or partitions. The OS
vendor cannot write an indexed system general enough to provide the
extremes of performance needed by such databases, which comes back to
your own performance point, but from the right direction. Buffered
stream I/O is a simple and common function that any system can provide.
Programs that have more demanding requirements
can provide their own indexing mechanisms or utilize libraries built
on top of primitive streams. This really is straightforward modern
systems design.

> What you (or I) see as limitations in a particular selection of
> compiler/os/library may be exactly what someone else needs to do
> their job.

The question is, which is the primitive on top of which the other
can be built?

> > Remember this [sub]thread started with the claim that VMS folks had to
> > go to a lot of trouble to support those "evil" C programmers who wanted
> > to do char-by-char input. My response is: Good, somebody forced them to
> > do what they should do -- namely, implement char-by-char input
> > efficiently.
>
> While I understand that is your view on what they should do, not all
> will share it. The last time I needed to do character-at-a-time IO was
> to emulate an editor which required a termination character on input
> _unless_ the first character was one particular alphabetic character
> (which had no special meaning in other than the first position).

That you haven't had much need for efficient char-by-char input cannot
possibly be an argument that it shouldn't be provided.

> I


> have been faced with a different set of projects than you, but I have
> my own list of things that "any environment ought to do properly" such
> as file versioning :-).

File versioning can be built on top of an unstructured name system
such as unix's, and programs such as emacs do so. OTOH, VMS and
DOS/Windows [...]xxxxx.yyy;nnn type stuff is a straightjacket.



> >>I have run into programmers making this mistake over and over again.
> >>In recent years their immediate response has been "Gee, it runs fast
> >>on Unix", but in prior years their response was "Gee, it runs fast
> >>on MVS". Obviously it is only the recent history where the C language
> >>is involved, but the current generation seems much more surprised than
> >>their MVS-centric predecessors.
> >

> > Seems pretty reasonable to me: if Unix or MVS can do it fast, why can't
> > whatever-OS-we're talking about do it fast? If not, it seems like the
> > fault of the OS, or the standard libraries implementation.
>
> Sorry if I was unclear, but Unix and MVS could not do the _same_thing_
> fast. The only commonality was that people coming from Unix and
> people coming from MVS both assumed that the new operating system
> would have the same performance characteristics as the one they are
> coming from. Now obviously it is impossible for the target operating
> system to fully mimic the behaviour of both Unix and MVS at the same
> time to make both camps happy.

Certainly not if the OS "primitives" are not sufficiently primitive.

--
<J Q B>

Jim Balter

unread,
Mar 10, 1997, 3:00:00 AM3/10/97
to

Robert Dewar wrote:
>
> TD/DELAB (?) said
>
> <<It may certainly be less effective, but I cannot think of any
> implementation where it would be a disaster. The C single char IO
> operations are not complicated, and have very little overhead. What
> makes you think otherwise?
> >>
>
> I'll tell you what. Go measure the relative speed of reading a 1 meg
> file a character at a time, vs using read to read the entire 1 meg at
> a time. Do this measurement on at least six different systems. Come
> back here with the results and we will discuss them!

Instead of being stupid about it, how about just looking at the
getchar macro, which is virtually the same on every single system?
I've done this repeatedly over the last nearly 20 years on many many
systems. There is a small overhead per byte due to the getchar
macro, which is reduced with good optimizing compilers and good
caching hardware. For the inner loop of "cat", the getchar cost
predominates. For anything else, it doesn't. This is basic
algorithmic analysis, which you can find good references for in your
local library, if you ever bother to head in that direction.

--
<J Q B>

Jim Balter

unread,
Mar 10, 1997, 3:00:00 AM3/10/97
to

Robert Dewar wrote:
>
> Fergus said
>
> <<It is somewhat surprising that the difference between the user CPU
> times is so large, but I'm more surprised by the speed of the second
> version than by the slowness of the first.>>
>
> Well it does not surprise me, and I don't really understand why it
> surprises you. I would expect a large difference here, and indeed
> it is what we see!
>
> Just shows that measurements can be a useful substitute for guesswork,
> though measurements have the weakness of being system specific, so
> nothing really substitutes for a lot of experience on a lot of difrerent
> machiens!

These measurements are totally misleading, and their use and
interpretation show a total *lack* of experience. If the tests are
coded properly so that the buffer accesses aren't optimized out of
existence, you will see about a 3:1 difference in user cpu time between
the getchar version and the read version, solely as a consequence of the
getchar macro requiring more instructions. Exactly the same number of
system calls are made, as anyone who attempts to *understand* the
issue instead of indulging in silly sophistry will know. If you then
do, say, 20 instructions worth of processing per character, the ratio
is 23:21. *Big* difference, like you'd expect. Feh.

--
<J Q B>

Fergus Henderson

unread,
Mar 11, 1997, 3:00:00 AM3/11/97
to

de...@merv.cs.nyu.edu (Robert Dewar) writes:

>Ole-HJ said
>
><<But I still would say that this is the only reasonable implementation,
>especially as functions to explicitly control the buffering and flush
>the buffer is part of the specification.>>
>
>YOu have lost me here, what do you mean when you say that functions to
>explicitly control the buffering are part of the speciication. Yes
>there is flush, but that's it ...

What about setvbuf()?

Ole-Hjalmar Kristensen FOU.TD/DELAB

unread,
Mar 11, 1997, 3:00:00 AM3/11/97
to

In article <dewar.858014326@merv> de...@merv.cs.nyu.edu (Robert Dewar) writes:

Ole-HJ said

<<But I still would say that this is the only reasonable implementation,
especially as functions to explicitly control the buffering and flush
the buffer is part of the specification.>>

YOu have lost me here, what do you mean when you say that functions to
explicitly control the buffering are part of the speciication. Yes
there is flush, but that's it ...


There are the functions fflush,setbuf, setvbuf and the constants _IOFBF,
_IOLBF, _IONBF, and BUFSIZ. Look them up if you aren't familiar with
stdio.

Btw., I admire your urge to reduce the bandwidth by only quoting
selected parts of messages, but on the other hand, you constantly run
the risk of looking like a smartass who likes quoting people out of context.

Ole-Hj. Kristensen

Robert Dewar

unread,
Mar 11, 1997, 3:00:00 AM3/11/97
to

<<<<But what surprises me is that in cases where the argument is *known*
to be larger than 1.0 the checks are still being made. Normally I would
use a subtype Positive_Float for values which should be positive in a
calculation. This will give a good compiler the opportunity to omit the
extra comparisons in the Ada code.

Sadly enough GNAT is not (yet) such a good compiler in this respect.
In fact GNAT should be able to generate faster code for invocations of
the log function for such arguments, since it can inline the function
to *only* contain the log instruction.

There are many real-world examples where optimizations like these
can make a difference of a factor 3 and more, so I guess these
optimizations satisfy Robert Dewars criterea.>>


That's a pretty marginal optimization. Maybe Geert makes subtypes
Positive_Float, but of all the code we ever had submitted to us,
no one ever bothered to do this, they just used Float.

Still it can go on the list, it's way down there in priority though,
there are MANY more important optimizations ahead of it!

Note of course that Geert's optimization is only possible in any
case if the log function is inlined.

(i.e. if you compile with -gnatn or -gnatN)

So I don't think this is so sad! My experience, as I mentioned before
is that people are always worrying about individual optimizations, but
these individual worries often correspond to optimizations that end
up being disappointing. This particular one is likely to be disappointing
because most people will use plain float as the type anyway.

I do agree that it is surprising how much extra time these comparisons
add (that of course is HIGHLY target dependent, so the other thing to
think about in getting enthusiastic about this optimization is to
find out how much it will help on various targets).

Note that anyone really worried about this problem can trivially call
the C log function directly anyway (not unreasonable, since it is a way
of clearly documenting that you don't need the Ada semantics)

Incidentally, the reason that optimizations like this are not so easy
is that gcc does not know about subranges, since C doe not know enough
about subranges. So gcc does not know about optimziat9ions. The optimization
under discussion here is of course one that has no conceivable analog in
C or C++ (I guess the "sadly enough GNAT is not such a good compiler" gets
translated into "sadly C and C++ are not such good languages" :-)

It's always hard to get very worked up over optimizations for numerical
code that could not be done in Fortran or C compilers.

The first item of business is to get the Ada code to be fully comparable
to Fortran code, which is a tall order already! Then we can worry about
refinements like this which make carefully written Ada code faster
than Fortran!

Note in particular that right now, the most significant optimization issue
for GNAT numerical code has to do with handling of unconstrained arrays,
which, on certain targets, is still non-ooptimal.


Robert Dewar

unread,
Mar 11, 1997, 3:00:00 AM3/11/97
to

Graham says

<<Perhaps. But the beauty of the C and other approaches is that I don't
have to write the buffer explicitly, and thus have to debug it. I *can*
read character by character if I want to, and often I do; socket
programming is a perfect example. But the rest of the time, I don't
want to worry about it, and don't have to.>>

Sure you can read character by character, but you are paying a considerable
price, even in C, for doing so!


Robert Dewar

unread,
Mar 11, 1997, 3:00:00 AM3/11/97
to

Ole-HJ said

<<No, there is no flush, but there is fflush, and setbuf, setvbuf>>

Ah, I was confused by your original post, I did not think you were talking
about C there, but about Ada.

Byte at a time procesing will always be slower than reading blocks. This
is true in C as well as Ada.

Given comparable I/O packages, C and Ada are not significantly different
here.

It is true that Text_IO has a lot of extra baggage that makes doing
Get(char) slower than getchar in C, these swimply are not comparble
operations.

Because of this extra baggage, put there quite deliberately of course,
most big Ada programs concerned with efficiency do NOT use Text_IO.

It is perfectly possible to do character by character IO using
streams in Ada, by reading one character at a time. This certainly
does introduce an extra overhead of call levels, but it does not
result in a system call per character, as some have suggested.

If you want something equivalent to the macroized get_char, that is
trivially easily programmed in C on top of stream_IO, perhaps it is
a good idea for a standard package -- any student could write it
in a few minutes, so it is not exactly rocket science!


Robert Dewar

unread,
Mar 11, 1997, 3:00:00 AM3/11/97
to

Jim Balter quoted me and replied

<<These measurements are totally misleading, and their use and
interpretation show a total *lack* of experience. If the tests are
coded properly so that the buffer accesses aren't optimized out of
existence, you will see about a 3:1 difference in user cpu time between
the getchar version and the read version, solely as a consequence of the
getchar macro requiring more instructions. Exactly the same number of
system calls are made, as anyone who attempts to *understand* the
issue instead of indulging in silly sophistry will know. If you then
do, say, 20 instructions worth of processing per character, the ratio
is 23:21. *Big* difference, like you'd expect. Feh.>>

Well if there is one thing I am certainly not guilty of, it is lack of
experience :-)

But actually Jim, you have your quotes confused. I never said there
were a different number of systems calls, of course not! I said exactly
the opposite.

I am not quite sure what you mean by the measurements being misleading,
they are measuring exactly what they purport to be measuring. It is
possible to draw incorrect conclusions from these measurements, but
they only mislead those who wish to be mislead!


Robert Dewar

unread,
Mar 11, 1997, 3:00:00 AM3/11/97
to

Jim Balter said

<<Instead of being stupid about it, how about just looking at the
getchar macro, which is virtually the same on every single system?
I've done this repeatedly over the last nearly 20 years on many many
systems. There is a small overhead per byte due to the getchar
macro, which is reduced with good optimizing compilers and good
caching hardware. For the inner loop of "cat", the getchar cost
predominates. For anything else, it doesn't. This is basic
algorithmic analysis, which you can find good references for in your
local library, if you ever bother to head in that direction.>>

(replying to me)

Very curious, your post EXACTLY agrees with my point, which is that
there is extra overhead, even in C in going character by character,
and you even go so far as to say (further than I went) that there
can be programs in which this effect is dominant.

Well of course your claim that ONLY cat can see this effect is
over-headed hyperbole, but there is a real difference, and for
example, in many of the compilers I have written in C, I have
found that the overall compilation time is noticably affected by
the choice of reading character by character or reading blocks.
A character read is going to do at least one pipe-line breaking
test (or one should say potentially pipe-line breaking test),
and it is not going to be free.

That was my point, and you seem to completely agree, and I really
don't see what algorithmic analysis has to do with the situation,
since we are talking O(N) in any case, i.e. we are discussing
constants, not algorithmic complexities


Graham Hughes

unread,
Mar 11, 1997, 3:00:00 AM3/11/97
to

-----BEGIN PGP SIGNED MESSAGE-----

de...@merv.cs.nyu.edu (Robert Dewar) writes:

>Sure you can read character by character, but you are paying a considerable
>price, even in C, for doing so!

Actually: virtually none.

Now, any stdio library can do this any way it damn well pleases, but the
*usual* way to implement the buffers is this:

If you request a character to be read, it feeds you the next character
in the buffer. If there isn't a next character in the buffer, it reads
in BUFSIZ elements and tries again. If it can't read any elements in,
then it returns EOF.

This is simplified somewhat, as ungetc() has to work across buffers, and
standard input is usually line buffered if it comes in from a tty (which
is handled largely by reading in as much as possible, getting an EOF,
and trying again later; see glibc).

Now, since BUFSIZ is 1024 bytes on my computer, this is in fact quite
efficient. The actual BUFSIZ varies from compiler to compiler and
platform to platform, much as stdio itself does.

I don't see why this is so hard to do in Ada. It's the most used
library in C (even hello world programs call printf()).

Oh, and as has been said earlier; with setvbuf, I can make the stream
buffer any way I want.


- --
Graham Hughes http://A-abe.resnet.ucsb.edu/~graham/ -- MIME & PGP mail OK.
PGP Key fingerprint = E9 B7 5F A0 F8 88 9E 1E 7C 62 D9 88 E1 03 29 5B


-----BEGIN PGP SIGNATURE-----
Version: 2.6.3
Charset: noconv

iQCVAwUBMyXTnCqNPSINiVE5AQEIHgP8C/daYdavY71nD4+/OiMVyhff2Cspbd0Q
ip7yB+q7ATJEs9WyJU4id5oYxxDtEq3rD7pWQwkDYIuyIX22/cB4EgMkw40ubFFF
NRClDGq8MhMsmm4q1KHBr0goR8t73wta/0H/zJw1VulRG+OqgfQ7zipL2/9r8jrY
K+JV6wLBCQY=
=PZp9
-----END PGP SIGNATURE-----

Jim Balter

unread,
Mar 11, 1997, 3:00:00 AM3/11/97
to

Robert Dewar wrote:
>
> Jim Balter said
>
> <<Instead of being stupid about it, how about just looking at the
> getchar macro, which is virtually the same on every single system?
> I've done this repeatedly over the last nearly 20 years on many many
> systems. There is a small overhead per byte due to the getchar
> macro, which is reduced with good optimizing compilers and good
> caching hardware. For the inner loop of "cat", the getchar cost
> predominates. For anything else, it doesn't. This is basic
> algorithmic analysis, which you can find good references for in your
> local library, if you ever bother to head in that direction.>>
>
> (replying to me)
>
> Very curious, your post EXACTLY agrees with my point, which is that
> there is extra overhead, even in C in going character by character,
> and you even go so far as to say (further than I went) that there
> can be programs in which this effect is dominant.

It take an unusual degree of intellectual dishonesty to misrepresent
one's own point. No more talk here of extra system calls,
buffering not being mandated, or the need to go out and empirically
check 6 implementations.

> Well of course your claim that ONLY cat can see this effect is
> over-headed hyperbole,

It would be if I claimed that; the only claim was about predominance,
i.e., the major factor in the cost.

> but there is a real difference, and for
> example, in many of the compilers I have written in C, I have
> found that the overall compilation time is noticably affected by
> the choice of reading character by character or reading blocks.
> A character read is going to do at least one pipe-line breaking
> test (or one should say potentially pipe-line breaking test),
> and it is not going to be free.

The point is and has been a radical overstatement of the cost,
as though it is just the luck of the draw whether a getchar
call might do an extra system call, and you have to go out and
empirically check 6 different systems to find out. Of course

if (c = (--n < 0? fetch() : *p++)) == EOF break;

is potentially more costly than

if (i == n) break; c = buf[i++];

but it is not the sort of "mistake" to code this way that some have
made it out to be. The hyperbole is on the other side.

> That was my point, and you seem to completely agree, and I really
> don't see what algorithmic analysis has to do with the situation,
> since we are talking O(N) in any case, i.e. we are discussing
> constants, not algorithmic complexities

The magnitude of constants is part of algorithmic analysis.

--
<J Q B>

Jim Balter

unread,
Mar 11, 1997, 3:00:00 AM3/11/97
to

Robert Dewar wrote:

> If you want something equivalent to the macroized get_char, that is
> trivially easily programmed in C on top of stream_IO, perhaps it is
> a good idea for a standard package

Since that was the original point, this whole discussion has been
much ado about nothing.

--
<J Q B>

Jim Balter

unread,
Mar 11, 1997, 3:00:00 AM3/11/97
to

Robert Dewar wrote:
>
> Jim Balter quoted me and replied
>
> <<These measurements are totally misleading, and their use and
> interpretation show a total *lack* of experience. If the tests are
> coded properly so that the buffer accesses aren't optimized out of
> existence, you will see about a 3:1 difference in user cpu time between
> the getchar version and the read version, solely as a consequence of the
> getchar macro requiring more instructions. Exactly the same number of
> system calls are made, as anyone who attempts to *understand* the
> issue instead of indulging in silly sophistry will know. If you then
> do, say, 20 instructions worth of processing per character, the ratio
> is 23:21. *Big* difference, like you'd expect. Feh.>>
>
> Well if there is one thing I am certainly not guilty of, it is lack of
> experience :-)
>
> But actually Jim, you have your quotes confused. I never said there
> were a different number of systems calls, of course not! I said exactly
> the opposite.

"You cannot make such statements (the standard IO lbrary of C definitely


does IO in blocks). The standard speaks only of interfaces, not of
implementation, there is nothing in the standardized interface that
requires
IO to be done in blocks. This may be an implementation characterstic of
some
or even most or even all current implementations, but it is NOT a
fundamental
property of the standard IO library.
"

And there has been other material in which you have implied that
multiple system calls might be involved.

> I am not quite sure what you mean by the measurements being misleading,
> they are measuring exactly what they purport to be measuring. It is
> possible to draw incorrect conclusions from these measurements, but
> they only mislead those who wish to be mislead!

What a foolish thing to say. Take a course in philosophy of science.

--
<J Q B>

Mark & Zurima McKinney

unread,
Mar 11, 1997, 3:00:00 AM3/11/97
to

Use an address clause for and object of the compatible type with and the
address of the buffer.

Jim Balter

unread,
Mar 11, 1997, 3:00:00 AM3/11/97
to

Robert Dewar wrote:

> I am not quite sure what you mean by the measurements being misleading,
> they are measuring exactly what they purport to be measuring. It is
> possible to draw incorrect conclusions from these measurements, but
> they only mislead those who wish to be mislead!

Robert Dewar is apparently so afraid of seeing certain inputs
that he has blocked mail from me. This immediately after misreading
a note from me pointing out that he had taken Ole-Hjalmar Kristensen's
measurements as valid because they showed what he wanted them to show
(even though important code in an inner loop may have been optimized
out) as instead claiming that *he*, Dewar, had taken the measurements,
and thereupon interpreting me as being unable to follow a newsgroup
thread. Of course, I made no such mistake as thinking that Dewar
had taken the measurement.

--
<J Q B>

Robert Dewar

unread,
Mar 11, 1997, 3:00:00 AM3/11/97
to

Jim said

<<It take an unusual degree of intellectual dishonesty to misrepresent
one's own point. No more talk here of extra system calls,
buffering not being mandated, or the need to go out and empirically
check 6 implementations.>>

No, sorry, you are confused, go back and check the thread, I never said
that there were extra system calls, that was someone else with whom I
disagreed!

As for buffering being mandated, I am not quite sure what you are talking
about here. As I noted, GNAT I/O is constructed directly on top of
C Stream I/O, so it inherits the same default buffering behavior (and
the same ability to control buffering, see the GNAT RM for details).


Robert Dewar

unread,
Mar 11, 1997, 3:00:00 AM3/11/97
to

Jim Balter said

<<And there has been other material in which you have implied that
multiple system calls might be involved.>>

Just so this is crystal clear at this stage, at least to other readers
than Jim, I definitely did NOT imply that there are multiple system calls.
It maybe that Jim does not know Ada 95 very well, and that is how he got
confused.

What I did say was that if you use String'Output and String'Input, the
RM strongly implies character by character reads, since stream I/O is
defined as being component wise. But of course this does not result in
a system call per character, at least not in a reasonable implementation.
For example in GNAT, this translates eventually into a normal C stream
operation, which will typically be buffered.


Robert Dewar

unread,
Mar 11, 1997, 3:00:00 AM3/11/97
to

Jim said

Actually I mistyped here, what I meant to say was "easily programmed
in Ada on top of [Ada] Stream_IO", and that is what would be a good idea
for a standard package.

One problem in using C I/O routines directly is that they are often
not properly thread safe, whereas you can count on Stream_IO being
thread safe, which is why it is safer to build on top of the existing
Ada packages.

Ole-Hjalmar Kristensen FOU.TD/DELAB

unread,
Mar 12, 1997, 3:00:00 AM3/12/97
to

In article <dewar.858138084@merv> de...@merv.cs.nyu.edu (Robert Dewar) writes:

Jim Balter said

<<And there has been other material in which you have implied that
multiple system calls might be involved.>>

But Jim Balter also said the following:

<Start quote of Jim Balter>

<stuff deleted>
<end quote>

Just so this is crystal clear at this stage, at least to other readers
than Jim, I definitely did NOT imply that there are multiple system calls.
It maybe that Jim does not know Ada 95 very well, and that is how he got
confused.

And the above quote from Jim Balter makes it crystal clear that we
were talking about the C standard IO library, not Ada 95. It seems
that you are deliberately trying to confuse things here.

What I did say was that if you use String'Output and String'Input, the
RM strongly implies character by character reads, since stream I/O is
defined as being component wise. But of course this does not result in
a system call per character, at least not in a reasonable implementation.
For example in GNAT, this translates eventually into a normal C stream
operation, which will typically be buffered.

Yes, you did say that, but that has nothing to do with the post you
replied to.

Ole-Hjalmar Kristensen FOU.TD/DELAB

unread,
Mar 12, 1997, 3:00:00 AM3/12/97
to

Robert Dewar wrote:

--
<J Q B>

Actually, I don't think he claimed to have done the measurements
himself.

But just some comments about doing invalid measurements and being
unable to interpret the results :-)

I did the measurements mainly to show that the amount of work being
done by system calls was exactly the same in both cases, and that is
why the setvbuf call was made to ensure that the buffer size was the
same in both cases. I didn't particulary care about the code in the
inner loop being optimized away, because as you have said yourself,
as soon as you start doing something interesting with the char, the
difference is pretty unimportant. I only expressed a mild surprise
that not more of the getchar macro had been optimzed away as well.

Btw., I've re-run the program with a simple checksum computation in the
innner loop, and the ratio is now 4 to 1. Still a bit more difference
than I would have thought, but pipelining effects may have something
to do with it, as Dewar pointed out.


Ole-Hjalmar Kristensen FOU.TD/DELAB

unread,
Mar 12, 1997, 3:00:00 AM3/12/97
to

In article <dewar.858096166@merv> de...@merv.cs.nyu.edu (Robert Dewar) writes:

Graham says

<<Perhaps. But the beauty of the C and other approaches is that I don't
have to write the buffer explicitly, and thus have to debug it. I *can*
read character by character if I want to, and often I do; socket
programming is a perfect example. But the rest of the time, I don't
want to worry about it, and don't have to.>>

Sure you can read character by character, but you are paying a considerable


price, even in C, for doing so!

If you actually want to do something with your char instead of just
reading it, it is usually negligible.

Robert Dewar

unread,
Mar 12, 1997, 3:00:00 AM3/12/97
to

Graham says

<<>Sure you can read character by character, but you are paying a considerable
>price, even in C, for doing so!

Actually: virtually none.>>

Well words like considerable and virtually are not very quantitative.
There definitely is a price in going character by character (even Balter
thinks this extra price might be dominant in something like "cat").

Every system where I have measured the effect (e.g. the difference in
a compiler that reads large blocks, or does character by character reads,
I have seen enough difference to be worth the effort of doing IO in blocks.
This is especially true if you can put a sentinel at the end of the block
that will naturally be detected by your processing, e.g. an end-of-file
mark of some kind in the compiler case, so that you can then process
character by character with out a test for buffer exhaustion (once you
commit to using getchar, you do of course have a test on each character
read for buffer exhuastion, because at that level it is not under
your control).

GNAT actually works exactly this way, it reads the entire source with
a single read, and then puts an end of file sentinel at the end of the
source. This provides noticable speed up over character by character
processing.


Jim Balter

unread,
Mar 12, 1997, 3:00:00 AM3/12/97
to

Robert Dewar wrote:
>
> Jim said
>
> <<> If you want something equivalent to the macroized get_char, that is
> > trivially easily programmed in C on top of stream_IO, perhaps it is
> > a good idea for a standard package
>
> Since that was the original point, this whole discussion has been
> much ado about nothing.
> >>
>
> Actually I mistyped here, what I meant to say was "easily programmed
> in Ada on top of [Ada] Stream_IO", and that is what would be a good idea
> for a standard package.

That's what I took you to mean (i.e., I misread you and thereby
read you properly).

--
<J Q B>

Jim Balter

unread,
Mar 12, 1997, 3:00:00 AM3/12/97
to

Robert Dewar wrote:
>
> Jim Balter said
>
> <<And there has been other material in which you have implied that
> multiple system calls might be involved.>>
>
> Just so this is crystal clear at this stage, at least to other readers
> than Jim, I definitely did NOT imply that there are multiple system calls.
> It maybe that Jim does not know Ada 95 very well, and that is how he got
> confused.

I gave a quote, which you have deliberately deleted, that made it
clear that you had implied that the *C language* getchar macro
might cause extra system calls to be made. And it is the "mistake"
of using getchar in C that has been at issue, so it seems that you
are having considerable trouble following the thread.

--
<J Q B>

Jim Balter

unread,
Mar 12, 1997, 3:00:00 AM3/12/97
to

Ole-Hjalmar Kristensen FOU.TD/DELAB wrote:

> Actually, I don't think he claimed to have done the measurements
> himself.

No, he didn't, nor did I say that he did. I said that he had
misread something I said to him as a claim by me that he had done
these measurements. He then claimed that (which was his own misreading
of something I said) showed that I couldn't follow a newsgroup thread.

> But just some comments about doing invalid measurements and being
> unable to interpret the results :-)
>
> I did the measurements mainly to show that the amount of work being
> done by system calls was exactly the same in both cases, and that is
> why the setvbuf call was made to ensure that the buffer size was the
> same in both cases. I didn't particulary care about the code in the
> inner loop being optimized away, because as you have said yourself,
> as soon as you start doing something interesting with the char, the
> difference is pretty unimportant. I only expressed a mild surprise
> that not more of the getchar macro had been optimzed away as well.

With getchar, the stdin ptr and cnt must be updated to accurately
reflect the amount of data scanned, and many compilers will generate
code that does the compare to EOF whether the char came from filbuf
or from *ptr++, even though the latter isn't necessary. In the read()
loop, the buffer need not be touched at all if the data isn't actually
used.



> Btw., I've re-run the program with a simple checksum computation in the
> innner loop, and the ratio is now 4 to 1. Still a bit more difference
> than I would have thought, but pipelining effects may have something
> to do with it, as Dewar pointed out.

The compiled code may well not be moving stdin._ptr and
stdin._cnt into registers. You would have to carefully evaluate
the actual compiled code for both the getchar and read() cases to
determine the precise overhead for getchar. It may even get down to
zero (within the loop; there would still be constant overhead) with
certain compilers and processors. Of course, it won't get down below
zero, unless the read() loop is really badly coded.
But it is easy to write read() loops that mishandle some cases,
such as a search for a two-character sequence that straddles a buffer
boundary, so loose talk about "mistakes" should be avoided.

My own measurements gave a getchar cost of 100 nanoseconds
per byte on a Pentium 166, rather a small fraction of the total cost,
but I didn't run a lot of cases or examine the generated code to be
sure I wasn't seeing some artifact, so my experience leads me not
to jump to conclusions about such numbers. And of course all these
measurements are *CPU* time, not elapsed time, and totally
exclude physical I/O time.

--
<J Q B>

Jim Balter

unread,
Mar 12, 1997, 3:00:00 AM3/12/97
to

Robert Dewar wrote:
>
> Jim said
>
> <<It take an unusual degree of intellectual dishonesty to misrepresent
> one's own point. No more talk here of extra system calls,
> buffering not being mandated, or the need to go out and empirically
> check 6 implementations.>>
>
> No, sorry, you are confused, go back and check the thread, I never said
> that there were extra system calls, that was someone else with whom I
> disagreed!

I have already quoted you as saying that a single I/O call per block
by the *C library* (not a comment about ADA) is not guaranteed.

> As for buffering being mandated, I am not quite sure what you are talking
> about here.

Sorry to here that you are having so much trouble following the thread.

--
<J Q B>

Robert I. Eachus

unread,
Mar 12, 1997, 3:00:00 AM3/12/97
to

In article <dewar.858095506@merv> de...@merv.cs.nyu.edu (Robert Dewar) writes:

> That's a pretty marginal optimization. Maybe Geert makes subtypes
> Positive_Float, but of all the code we ever had submitted to us,
> no one ever bothered to do this, they just used Float.

> Still it can go on the list, it's way down there in priority though,
> there are MANY more important optimizations ahead of it!

Let me put an optimization way ahead of it on the list and see if
anyone is interested...

The easiest way of dealing with the A.5.1(37-42) requirements in a
portable manner is the one currently taken by GNAT--explicit code.
However, most of these requirements will be met by any IEEE conforming
implementation. So it should be possible to have two versions of the
elementary functions packages, one which assumes good underlying math
libraries, and one which does not.

Note that the hard work here can be done completely separately from
other compiler maintenance and enhancement activities. It involves
writing some test code and running it on a lot of different
platforms. (The way I envision this is a set of alternate bodies, and
a test program which validates the elisions. Of course, the ultimate
would be a test program that generated a tailored version of the
bodies which matched the particular hardware.)


--

Robert I. Eachus

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

Mats Weber

unread,
Mar 12, 1997, 3:00:00 AM3/12/97
to

> I do agree that it is surprising how much extra time these comparisons
> add (that of course is HIGHLY target dependent, so the other thing to
> think about in getting enthusiastic about this optimization is to
> find out how much it will help on various targets).

I think that if the C library functions are good enough for C and
FORTRAN people, they should be good enough for Ada people also, without
adding these comparisons. Who wants to write algorithms that depend on
the sine function with cycle => 90.0 (which is a model number) returning
exactly 1.0, and other such particular cases ? Floating point is
approximate by nature.

This is another instance (the other being simple text IO, see other
threads going on) where Ada is by nature less effective than C, and the
sad thing is that it is not in the language itself but in standard
libraries that are over-featurized: who needs column and line numbers,
and a log function that is guaranteed to return exactly 0.0 when called
with exactly 1.0. I think such special needs are better addressed by
explicit coding: use an explicit line counter for that seldom occasion
where you need line numbers, or put the test for = 1.0 before you call
Log when you really need it to be a special case.

It would be nice if there was a version of the numerics packages with
direct calls to the library and comparisons only for the cases where an
exception must be raised (such as Log of a negative value).

One way to achieve this would be to have two versions of the elementary
functions:

Ada.Numerics.Generic_Elementary_Functions and
Ada.Numerics.Pedantic.Generic_Elementary_Functions :-)

or an installation option for the compiler.

Robert Dewar

unread,
Mar 12, 1997, 3:00:00 AM3/12/97
to

Dave Brown says

<<Ok, so I am reading the file data into a stream element buffer
(Stream_Element_Array). My file, however, really consists of some
small objects (16 bit signed integers). What is the "proper" way to
get these integers out of this buffer? I want there to be as little
copying of these numbers as possible. Here are some solutions I've
come up with:>>

Well first, as you go on to mention, you may well find that it is
efficient enough to use the stream attributes directly in the first
place.

If not, I would still use Stream_Attributes as the mechanism, but
write your own to access the buffer efficiently.


Robert Dewar

unread,
Mar 12, 1997, 3:00:00 AM3/12/97
to

Tom Moran said

<< Yes, you did misunderstand. The original post implied that the
comparison had taken place several years ago, which implies it was done
in Ada 83, which did not implement Stream_IO. The only "strictly in
Ada" way to read a file then was via Text, Sequential, or Direct_IO.
Both Sequential and Direct_IO require fixed size records. (Not strictly
true, but essentially true in practice. E.g., ActivAda, GNAT, and Janus
will all accept a "(string)" as the parameter to Sequential_IO, but all
three die on trying to actually read a text file in chunks that way.) So
the fixed buffer size, if one did *not* use Text_IO, would have to be a
divisor of the total file size. If the file size is a prime number,>>

Actually this is wrong, you cannot even assume that Direct_IO will work
even if the file size is comfortably divisible by a convenient record
size. There is nothing to suggest that the mapping of Direct_IO files
is direct at the byte level, and for example, it would be perfectly
reasonable to have a control byte that showed whether a record was
present, or even a tag to verify the type of the data from run to run.

But in any case, from a language design point of view, this is of
archeological interest only, since one would not consider using
Direct_IO for this purpose in Ada 95 anyway. If you are trying to
solve this problem with an old Ada 83 compiler, certainly the best
thing is to interface to C.

Unlike Tom (and some others), it never worries me to interface to C where
that is appropriate (or to interface to any other language). The idea that
everything must be done in Ada, and it is a terrible thing to use any
other language seems peculiar to me, and is something that is better left
on the dust heap of Ada relics. I realize that there are Ada fanatics who
feel very differently (though from his posts I would not have thought of
Tom as one), but to me Ada is a tool to be used in the most effective
way possible, and if the most effective way in some particular instance
is to interface to C, that's no problem -- why else have we put such
effort into designing this interface to C portably and effectively (it
certainly *is* more of a problem if you are in C or C++ and have to
interface portably to, e.g. COBOL or Fortran, since it cannot be done
in a portable manner).


Robert Dewar

unread,
Mar 12, 1997, 3:00:00 AM3/12/97
to

Jim Balter said

<<Robert Dewar is apparently so afraid of seeing certain inputs
that he has blocked mail from me>>

A curious misinterpretation, but just for the record, Mr. Balter's
arguments descended into a string of obsecnities, and at that point
I concluded that I had better things to do with my time (I do have
a rather large number of email messages to deal with that are somewhat
more informative and useful :-)


Robert Dewar

unread,
Mar 12, 1997, 3:00:00 AM3/12/97
to

Mats says

<<This is another instance (the other being simple text IO, see other
threads going on) where Ada is by nature less effective than C, and the
sad thing is that it is not in the language itself but in standard
libraries that are over-featurized: who needs column and line numbers,
and a log function that is guaranteed to return exactly 0.0 when called
with exactly 1.0. I think such special needs are better addressed by
explicit coding: use an explicit line counter for that seldom occasion
where you need line numbers, or put the test for = 1.0 before you call
Log when you really need it to be a special case.

Robert replies:

It would be nice if there was a version of the numerics packages with
direct calls to the library and comparisons only for the cases where an
exception must be raised (such as Log of a negative value).>>

Actually this is catered for in the Ada 95 RM already. Accuracy requirements
must only be met if the numerics annex is supported, and it is perfectly
reasonable to have two versoins of the libraries, one for strict accuracy
and one where accuracy is not required.

It's something we might do for GNAT at some time. Right now, our customers
have much different concerns about performance, so worrying about elementary
function performance is not high on our lists (when it comes to optimizations
we are very much influenced by customer requirements [of the real kind, not
of the subjunctive "well maybe you would have more customers if xxx" kind :-)]

I would NOT be in favor of having a version that did not raise proper
exceptions as required in the RM, this is asking for portability problems.

Ada is unusual in specifying the accuracy semantics of floating-point in
general. This does cause some extra overhead which may be annoying to
those who want fast answers and don't care if they are accurate, so you
may lose some users there, but on the other hand, for those who DO want
to write reliable portable numeric code, Ada offers great advantages.

You can partly have your cake and eat it if the compioler supports the
strict and non-strict modes separately, but not completely!

As for the discussion of Text_IO, it is hard for me to believe that people
use Text_IO for anything other than very casual I/O. For example, it would
not have occurred to us to use Text_IO in the implementation of GNAT
itself (and we would not be using getchar if it was written in C). I really
have not seen the performance of Text_IO be a significant issue in real
large projects.

As I have said previously, I see no reason for not borrowing things from C
if it makes sense. I know that there are two possible reactions to this

a) UGGGH! borrowing from C, what a horrible idea, GASP, SPLUTTER!

b) well if you have to import getchar, you might as well write your
whole million line application in C

I am afraid I have zero sympathy for either reaction. Neither makes any
sense at all. The first is borne of some over-fanatic Ada orientation,
the second is just a thinly disguised translation of an excuse!

Jim Balter

unread,
Mar 12, 1997, 3:00:00 AM3/12/97
to

My comments were in response to Dewar calling me a child and pompously
referring to his teaching of courses as some sort of
argument from authority rather than answering my substantive points.

--
<J Q B>

Jon S Anthony

unread,
Mar 13, 1997, 3:00:00 AM3/13/97
to

In article <5g4k31$g54$1...@A-abe.resnet.ucsb.edu> Graham Hughes <graham...@resnet.ucsb.edu> writes:

> Now, any stdio library can do this any way it damn well pleases, but the
> *usual* way to implement the buffers is this:
>
> If you request a character to be read, it feeds you the next character
> in the buffer. If there isn't a next character in the buffer, it reads
> in BUFSIZ elements and tries again. If it can't read any elements in,
> then it returns EOF.

...


> Now, since BUFSIZ is 1024 bytes on my computer, this is in fact quite
> efficient. The actual BUFSIZ varies from compiler to compiler and
> platform to platform, much as stdio itself does.
>
> I don't see why this is so hard to do in Ada. It's the most used
> library in C (even hello world programs call printf()).

It's not. It's easy. But you might not get that from the way this
thread has progressed. As Robert pointed out back at the start (and a
couple of times since), use Read and Write directly on buffers of
stream elements _instead_ of the attributes String'Read and
String'Write. The latter require character by character processing
(per RM element by element processing of arrays in streams).

OK, so clearly the Read/Write for streams into buffers will be very
efficient and you can then chop this at your leisure. But there are a
still a few issues in all this.

First, for GNAT String'Read/Write should boil down to a getc/putc or
some such C read/write, so any extra overhead here (beyond what you
have in C) should not be due to any buffering aspects whatsover. They
will be due to call overhead on the C IO function. The claim that
started this twist in the thread here, was that this overhead made the
IO "very slow". I guess the problem is with "very". 3 times slower?
4 times? What? And are these examples of "very slow"? Perhaps.
Regular ol' getchar, of course, can avoid this call overhead - though
I suppose it may not: thread safety issues anyone?

Second, while 13.13.2(9) sez that for composites (including arrays)
the associated Read and Write attributes call the Read/Write
attributes for each _component_, I don't see why this can't be one of
those cases where "as if semantics" apply. For example, for one
dimensional arrays, just read the thing as if you called Read/Write
for each element.

Third, since you can specify stream oriented attributes ('Read 'Write)
for any type with an attribute definition clause, you can always just
change the "efficiency" behavior of String'Read/Write to be just like
getchar's by inlining a version which does what getchar does.


/Jon
--
Jon Anthony
Organon Motives, Inc.
Belmont, MA 02178
617.484.3383
j...@organon.com


tmo...@bix.com

unread,
Mar 13, 1997, 3:00:00 AM3/13/97
to

> it never worries me to interface to C where that is appropriate
Me neither. But it does worry me if interfacing to C is appropriate
too often.
Multi-language projects are more work to maintain. C (or special OS
calls) are less portable. It's hard to argue strongly for Ada while
also saying "except for the parts Ada can't do well" (even if that
really means except for the parts this particular Ada compiler doesn't
do well). And consider the start of this discussion: someone
translated a small program from C to Ada and found it ten times
slower. I don't know what happened in that particular case, but often
that sort of thing results not in investigation of how to get around
the weak points of the Ada compiler/library, but rather in non-use of
Ada because "Ada is ten times slower".
There should be *very* few cases where C is the more appropriate
language.

It is loading more messages.
0 new messages