comp.lang.ada
 help / color / mirror / Atom feed
* bitstreams
@ 2001-01-14 14:47 Daniel Nilsson
  2001-01-14 15:10 ` bitstreams Larry Kilgallen
                   ` (3 more replies)
  0 siblings, 4 replies; 16+ messages in thread
From: Daniel Nilsson @ 2001-01-14 14:47 UTC (permalink / raw)


Hi.
In my mp3 decoder I will have to search for bit-patterns in a buffer of
bytes, how is this best done, and How can I "shift" in a sequence of bits
into a byte, or word efficiently? (I want ex. take 5 bits from a buffer and
put them rightadjusted in a unsigned_32)

/Daniel Nilsson





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

* Re: bitstreams
  2001-01-14 14:47 bitstreams Daniel Nilsson
@ 2001-01-14 15:10 ` Larry Kilgallen
  2001-01-14 16:15 ` bitstreams tmoran
                   ` (2 subsequent siblings)
  3 siblings, 0 replies; 16+ messages in thread
From: Larry Kilgallen @ 2001-01-14 15:10 UTC (permalink / raw)


In article <93se2v$nen$1@eol.dd.chalmers.se>, "Daniel Nilsson" <danielnilsson@REMOVE_THIShem3.passagen.se> writes:

> In my mp3 decoder I will have to search for bit-patterns in a buffer of
> bytes, how is this best done, and How can I "shift" in a sequence of bits
> into a byte, or word efficiently? (I want ex. take 5 bits from a buffer and
> put them rightadjusted in a unsigned_32)

Step 1.	Use a sequence of statements that correctly describes what you want.
Step 2.	Use a computer that can accomplish your goal efficiently.
Step 3.	Use a compiler that will optimize your statements into efficient
	machine instructions.

If your choice of computer or compiler is limited by some other
constraint that you failed to mention, play with it to get the
best performance.  If a compiler is really great you will not
be able to affect performance by changing between reasonable
source code representations (other than those specifically
documented to affect performance, such as certain pragmas).
In theory the compiler _should_ choose the most efficient
representation that correctly implements your source statement.



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

* Re: bitstreams
  2001-01-14 14:47 bitstreams Daniel Nilsson
  2001-01-14 15:10 ` bitstreams Larry Kilgallen
@ 2001-01-14 16:15 ` tmoran
  2001-01-14 19:46 ` bitstreams srini
  2001-01-15 19:21 ` bitstreams mark_lundquist
  3 siblings, 0 replies; 16+ messages in thread
From: tmoran @ 2001-01-14 16:15 UTC (permalink / raw)


>In my mp3 decoder I will have to search for bit-patterns in a buffer of
>bytes, how is this best done, and How can I "shift" in a sequence of bits
   I'm guessing that perhaps mp3 uses a Huffman code like a fax.  For
a fax, the longest code is 13 bits so it's much faster to create an
array of 2**13 entries such that the next 13 bits in the data can be used
as an index, and the value at that position in the array is the desired
code.  For instance, if the third code is "01", then
lookup(16#0100000000000# .. 16#0111111111111#) = 3.



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

* Re: bitstreams
  2001-01-14 14:47 bitstreams Daniel Nilsson
  2001-01-14 15:10 ` bitstreams Larry Kilgallen
  2001-01-14 16:15 ` bitstreams tmoran
@ 2001-01-14 19:46 ` srini
  2001-01-15 19:56   ` bitstreams mark_lundquist
  2001-01-15 19:21 ` bitstreams mark_lundquist
  3 siblings, 1 reply; 16+ messages in thread
From: srini @ 2001-01-14 19:46 UTC (permalink / raw)


[-- Attachment #1: Type: text/plain, Size: 605 bytes --]

I do not know much about mp3 etc but I have developed a bit stream
package which allows you to perform reads in terms of bits. I use these
in my own compression/decompression test software. The spec is attached.
I would be happy to send you the body as well if you are interested.


Daniel Nilsson wrote:
> 
> Hi.
> In my mp3 decoder I will have to search for bit-patterns in a buffer of
> bytes, how is this best done, and How can I "shift" in a sequence of bits
> into a byte, or word efficiently? (I want ex. take 5 bits from a buffer and
> put them rightadjusted in a unsigned_32)
> 
> /Daniel Nilsson

[-- Attachment #2: bits_io.ads --]
[-- Type: text/plain, Size: 3363 bytes --]


with Interfaces ;
with ada.streams ;
with ada.streams.stream_io ;
----------------------------------------------------------------------
-- Abstract : Bits_Io
--      This package converts a normal I/O stream into a bit level I/O
----------------------------------------------------------------------
package Bits_Io is

   type File_Type is limited private;
   type File_Mode is (In_File, Out_File, Append_File);

   type Vector_type is array (natural range <>) of boolean ;
   pragma pack( Vector_Type ) ;

   -- Abstract : Open
   --    A file is opened using normal File Management facilities first and then
   -- a Bit Stream File is created using the following procedure. It is the same
   -- procedure whether performing input or output. It is assumed that the file
   -- is used only for one of these purposes at any time.
   procedure Open
     (File : in out File_Type;
      Mode : in File_Mode ;
      Stream : access Ada.Streams.Root_Stream_Type'Class ) ;

   -- Abstract : Read/Write
   --    The following two procedures allow an Unsigned_8 variable to read or
   -- write. Similar procedures for Unsigned_16 and Unsigned_32 are also provided
   procedure Read
     (File : in out File_Type ;
      Item : out Interfaces.Unsigned_8 ;
      Last : out Ada.Streams.Stream_Element_Offset) ;
                                       -- Returns the number of bits actually read

   procedure Write
     (File : in out File_Type ;
      Item : in Interfaces.Unsigned_8 ;
      Last : in integer );             -- How many bits should really be written?

   procedure Read
     (File : in out File_Type ;
      Item : out Interfaces.Unsigned_16 ;
      Last : out Ada.Streams.Stream_Element_Offset) ;

   procedure Write
     (File : in out File_Type ;
      Item : in Interfaces.Unsigned_16 ;
      Last : in integer );

   procedure Read
     (File : in out File_Type ;
      Item : out Interfaces.Unsigned_32 ;
      Last : out Ada.Streams.Stream_Element_Offset) ;

   procedure Write
     (File : in out File_Type ;
      Item : in Interfaces.Unsigned_32 ;
      Last : in integer );

   -- Abstract : Read/Write
   --    These are the real I/O procedures where all the work is done. The above
   -- routines simply call these internally.
   procedure Read
     (File : in out File_Type ;
      Item : out Vector_Type ;
      Last : out Ada.Streams.Stream_Element_Offset) ;

   procedure Write
     (File : in out File_Type ;
      Item : in Vector_Type );

   -- Abstract : Flush
   --    Used for writing operations, sends any residual bits to the output stream
   -- packed in a byte.
   procedure Flush (File : in out File_Type ) ;

private

    type Root_Stream_Access_Type is access all Ada.Streams.Root_Stream_Type'Class ;

    type File_Type is
       record
          Opened : Boolean := False ;
          Ac : Root_Stream_Access_Type ;
          Mode : File_Mode ;
          Residue : Interfaces.Unsigned_8 ;
          Bits_Used : Integer ;
       end record ;

end Bits_Io ;

-- $Author: Administrator $
-- $Revision: 1.1.1.1 $
-- $Log: bits_io.ads,v $
-- Revision 1.1.1.1  2000/08/04 06:07:07  Administrator
-- Initial Checkin
--
-- Revision 1.1  1998/09/12 04:43:32  srinivr
-- Bit level Stream Input/Output routines. Initial Check in with
-- some known problems.
--
-- Revision 1.1  1998/01/27 03:39:33  srinivr
-- Added annotations
--



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

* Re: bitstreams
  2001-01-14 14:47 bitstreams Daniel Nilsson
                   ` (2 preceding siblings ...)
  2001-01-14 19:46 ` bitstreams srini
@ 2001-01-15 19:21 ` mark_lundquist
  2001-01-15 20:43   ` bitstreams Pat Rogers
  2001-01-16  0:59   ` bitstreams Robert Dewar
  3 siblings, 2 replies; 16+ messages in thread
From: mark_lundquist @ 2001-01-15 19:21 UTC (permalink / raw)


In article <93se2v$nen$1@eol.dd.chalmers.se>,
  "Daniel Nilsson" <danielnilsson@REMOVE_THIShem3.passagen.se> wrote:
> Hi.
> In my mp3 decoder I will have to search for bit-patterns in a buffer
of
> bytes, how is this best done, and How can I "shift" in a sequence of
bits
> into a byte, or word efficiently? (I want ex. take 5 bits from a
buffer and
> put them rightadjusted in a unsigned_32)

Note that shift and rotate functions are primitive operations of the
Signed_<n> and Unsigned_<n> families of types (RM [B.2])

>
> /Daniel Nilsson
>
>


Sent via Deja.com
http://www.deja.com/



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

* Re: bitstreams
  2001-01-14 19:46 ` bitstreams srini
@ 2001-01-15 19:56   ` mark_lundquist
  2001-01-15 21:54     ` bitstreams Tucker Taft
  2001-01-16  0:39     ` bitstreams Robert Dewar
  0 siblings, 2 replies; 16+ messages in thread
From: mark_lundquist @ 2001-01-15 19:56 UTC (permalink / raw)


In article <3A622CE5.89C9378E@worldnet.att.net>,
  srini <r.srinivasan@worldnet.att.net> wrote:
>
> I do not know much about mp3 etc but I have developed a bit stream
> package which allows you to perform reads in terms of bits. I use
these
> in my own compression/decompression test software. The spec is
attached.

> ----------------------------------------------------------------------
> package Bits_Io is
>
>    type File_Type is limited private;
>    type File_Mode is (In_File, Out_File, Append_File);
>
>    type Vector_type is array (natural range <>) of boolean ;
>    pragma pack( Vector_Type ) ;
.
.
.

Beware, though... this is implementation-dependent. If the compiler
doesn't represent a packed array of boolean as a bit vector, it doesn't
work.

The package is called Bits_Io, why not define a proper type Bit and
then define Bit_Vector in terms of that?  Is Boolean used so that you
can be able to have the logical operations on arrays of Boolean?  Note
that the rationale for including that feature in Ada was in order to
implement sets efficiently (I think that goes back to Steelman).  So
the idea of "and" on Boolean arrays in Ada is not the idea of a
bitmask, it's the idea of a set intersection.

To me, it's confusing whenever Boolean is used for something other than
truth value.

A couple of thoughts for the original poster...

Bitstream is probably the wrong abstraction for all but a small handful
of applications... specifically, compression and encryption, where you
are going to do math on the bits but you have no awareness of the bits
_representing_ something.  MP3 is an application where you most
certainly *do* care what the bits represent!  So while it may lay on
the disk as a sequence of bits (as does everything else), that seems
irrelevant because you must immediately cease dealing with it as
snippets of bits as soon as you get your hands on the snippets.  You
want the interpretation to be immediate, you don't want to have to be
involved in dealing with the bits.

You can desperately say, "if only I can just get my hands on the bits,
then I can shift/mask/unchecked-convert my way to the answer", but you
probably won't end up with a very good program.

What you probably want to do is declare types for all the fields in the
MP3 format, then define the Stream attributes for those types.

Mark Lundquist



Sent via Deja.com
http://www.deja.com/



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

* Re: bitstreams
  2001-01-15 19:21 ` bitstreams mark_lundquist
@ 2001-01-15 20:43   ` Pat Rogers
  2001-01-15 21:15     ` bitstreams mark_lundquist
  2001-01-16  0:59   ` bitstreams Robert Dewar
  1 sibling, 1 reply; 16+ messages in thread
From: Pat Rogers @ 2001-01-15 20:43 UTC (permalink / raw)


Only for the modular (i.e., unsigned) types, not the signed types.  See
B.2{9}


<mark_lundquist@my-deja.com> wrote in message
news:93vik8$u08$1@nnrp1.deja.com...
> In article <93se2v$nen$1@eol.dd.chalmers.se>,
>   "Daniel Nilsson" <danielnilsson@REMOVE_THIShem3.passagen.se> wrote:
> > Hi.
> > In my mp3 decoder I will have to search for bit-patterns in a buffer of
> > bytes, how is this best done, and How can I "shift" in a sequence of
bits
> > into a byte, or word efficiently? (I want ex. take 5 bits from a buffer
and
> > put them rightadjusted in a unsigned_32)
>
> Note that shift and rotate functions are primitive operations of the
> Signed_<n> and Unsigned_<n> families of types (RM [B.2])






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

* Re: bitstreams
  2001-01-15 20:43   ` bitstreams Pat Rogers
@ 2001-01-15 21:15     ` mark_lundquist
  0 siblings, 0 replies; 16+ messages in thread
From: mark_lundquist @ 2001-01-15 21:15 UTC (permalink / raw)




Bah, of course, my bad...
I guess I blew a brain-fuse there while I was writing that...

Thx for the correction,
-- mark

In article <ThJ86.1718$hD5.38173@nnrp1.sbc.net>,
  "Pat Rogers" <progers@NOclasswideSPAM.com> wrote:
> Only for the modular (i.e., unsigned) types, not the signed types.
See
> B.2{9}
>
> <mark_lundquist@my-deja.com> wrote in message
> news:93vik8$u08$1@nnrp1.deja.com...
> > In article <93se2v$nen$1@eol.dd.chalmers.se>,
> >   "Daniel Nilsson" <danielnilsson@REMOVE_THIShem3.passagen.se>
wrote:
> > > Hi.
> > > In my mp3 decoder I will have to search for bit-patterns in a
buffer of
> > > bytes, how is this best done, and How can I "shift" in a sequence
of
> bits
> > > into a byte, or word efficiently? (I want ex. take 5 bits from a
buffer
> and
> > > put them rightadjusted in a unsigned_32)
> >
> > Note that shift and rotate functions are primitive operations of the
> > Signed_<n> and Unsigned_<n> families of types (RM [B.2])
>
>


Sent via Deja.com
http://www.deja.com/



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

* Re: bitstreams
  2001-01-15 19:56   ` bitstreams mark_lundquist
@ 2001-01-15 21:54     ` Tucker Taft
  2001-01-16  0:41       ` bitstreams Robert Dewar
  2001-01-16  0:39     ` bitstreams Robert Dewar
  1 sibling, 1 reply; 16+ messages in thread
From: Tucker Taft @ 2001-01-15 21:54 UTC (permalink / raw)


mark_lundquist@my-deja.com wrote:
> 
> In article <3A622CE5.89C9378E@worldnet.att.net>,
>   srini <r.srinivasan@worldnet.att.net> wrote:
> >
> > I do not know much about mp3 etc but I have developed a bit stream
> > package which allows you to perform reads in terms of bits. I use
> these
> > in my own compression/decompression test software. The spec is
> attached.
> 
> > ----------------------------------------------------------------------
> > package Bits_Io is
> >
> >    type File_Type is limited private;
> >    type File_Mode is (In_File, Out_File, Append_File);
> >
> >    type Vector_type is array (natural range <>) of boolean ;
> >    pragma pack( Vector_Type ) ;
> .
> .
> .
> 
> Beware, though... this is implementation-dependent. If the compiler
> doesn't represent a packed array of boolean as a bit vector, it doesn't
> work.

Any Ada 95 compiler that has passed the chapter 13 ACATS (aka ACVCs) 
supports packed bit vectors, so not-to-worry (cf. generic Length_Check
used by many chapter 13 "cd*.*" tests).
 
Ada 95 requires support for packed bit vectors as part of
conforming to the Systems Programming Annex, and about the
only compilers that don't support the Systems Programming Annex
these days are those that generate Java byte codes (and even those
can support packed bit vectors without too much pain, though 
supporting arbitrary unchecked conversion is generally not possible).

> ...
> Mark Lundquist

-- 
-Tucker Taft   stt@avercom.net   http://www.averstar.com/~stt/
Chief Technology Officer, AverCom, Inc. (A Titan Company) Burlington, MA  USA
(AverCom was formed 1/1/01 from the Commercial Division of AverStar)
(http://www.averstar.com/services/ebusiness_applications.html)



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

* Re: bitstreams
  2001-01-15 19:56   ` bitstreams mark_lundquist
  2001-01-15 21:54     ` bitstreams Tucker Taft
@ 2001-01-16  0:39     ` Robert Dewar
  2001-01-16 23:26       ` bitstreams Rajagopalan Srinivasan
  1 sibling, 1 reply; 16+ messages in thread
From: Robert Dewar @ 2001-01-16  0:39 UTC (permalink / raw)


In article <93vkl3$1j$1@nnrp1.deja.com>,
  mark_lundquist@my-deja.com wrote:
> Beware, though... this is implementation-dependent. If the
> compiler doesn't represent a packed array of boolean as a bit
> vector, it doesn't work.

That's misleading, any compiler that conforms to Annex C must
properly pack array of Boolean, and surely no one would use
a non-annex C compiler in a context like this (virtually all
Ada 95 compilers in current use implement Annex C).


Sent via Deja.com
http://www.deja.com/



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

* Re: bitstreams
  2001-01-15 21:54     ` bitstreams Tucker Taft
@ 2001-01-16  0:41       ` Robert Dewar
  0 siblings, 0 replies; 16+ messages in thread
From: Robert Dewar @ 2001-01-16  0:41 UTC (permalink / raw)


In article <3A63718A.12F72E9E@averstar.com>,
  Tucker Taft <stt@averstar.com> wrote:
> and even those
> can support packed bit vectors without too much pain, though
> supporting arbitrary unchecked conversion is generally not
> possible).

Indeed JGNAT supports packing of array-of-boolean


Sent via Deja.com
http://www.deja.com/



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

* Re: bitstreams
  2001-01-15 19:21 ` bitstreams mark_lundquist
  2001-01-15 20:43   ` bitstreams Pat Rogers
@ 2001-01-16  0:59   ` Robert Dewar
  2001-01-16 17:36     ` bitstreams mark_lundquist
  1 sibling, 1 reply; 16+ messages in thread
From: Robert Dewar @ 2001-01-16  0:59 UTC (permalink / raw)


In article <93vik8$u08$1@nnrp1.deja.com>,
  mark_lundquist@my-deja.com wrote:
> Note that shift and rotate functions are primitive operations
> of the Signed_<n> and Unsigned_<n> families of types (RM B.2)
         ^^^^^^^^^^

A surprising mistake :-) It is of course the case that these
functions do NOT apply to signed numbers (where there meaning
would be obscure or at least implementation defined, because
of the sign bit issue).

One interesting bit of non-portability comes from whether it
is possible to define these operators for *USER* defined
unsigned types. The RM does not require this capability, but
in GNAT you can define your own intrinsic shift functions for
your own modular types, and GNAT will permit this. I do not
know if other Ada 95 compilers provide this capability.



Sent via Deja.com
http://www.deja.com/



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

* Re: bitstreams
  2001-01-16  0:59   ` bitstreams Robert Dewar
@ 2001-01-16 17:36     ` mark_lundquist
  2001-01-16 20:08       ` bitstreams Pat Rogers
  0 siblings, 1 reply; 16+ messages in thread
From: mark_lundquist @ 2001-01-16 17:36 UTC (permalink / raw)


In article <9406cs$g4i$1@nnrp1.deja.com>,
  Robert Dewar <robert_dewar@my-deja.com> wrote:
> In article <93vik8$u08$1@nnrp1.deja.com>,
>   mark_lundquist@my-deja.com wrote:
> > Note that shift and rotate functions are primitive operations
> > of the Signed_<n> and Unsigned_<n> families of types (RM B.2)
>          ^^^^^^^^^^
>
> A surprising mistake :-)

You got that right... it sure suprised me!

Sloppy, sloppy.  Yesterday was NOT a good news-posting day for me...

:-) :-)

> It is of course the case that these
> functions do NOT apply to signed numbers (where there meaning
> would be obscure or at least implementation defined, because
> of the sign bit issue).
>
> One interesting bit of non-portability comes from whether it
> is possible to define these operators for *USER* defined
> unsigned types. The RM does not require this capability, but
> in GNAT you can define your own intrinsic shift functions for
> your own modular types, and GNAT will permit this. I do not
> know if other Ada 95 compilers provide this capability.

That is interesting...

-- mark


Sent via Deja.com
http://www.deja.com/



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

* Re: bitstreams
  2001-01-16 17:36     ` bitstreams mark_lundquist
@ 2001-01-16 20:08       ` Pat Rogers
  2001-01-17  2:15         ` bitstreams Robert Dewar
  0 siblings, 1 reply; 16+ messages in thread
From: Pat Rogers @ 2001-01-16 20:08 UTC (permalink / raw)


<mark_lundquist@my-deja.com> wrote in message
news:9420qv$2d$1@nnrp1.deja.com...
> In article <9406cs$g4i$1@nnrp1.deja.com>,
>   Robert Dewar <robert_dewar@my-deja.com> wrote:
> > In article <93vik8$u08$1@nnrp1.deja.com>,
> >   mark_lundquist@my-deja.com wrote:
> > > Note that shift and rotate functions are primitive operations
> > > of the Signed_<n> and Unsigned_<n> families of types (RM B.2)
> >          ^^^^^^^^^^
> >
> > A surprising mistake :-)
>
> You got that right... it sure suprised me!
>
> Sloppy, sloppy.  Yesterday was NOT a good news-posting day for me...
>
> :-) :-)
>
> > It is of course the case that these
> > functions do NOT apply to signed numbers (where there meaning
> > would be obscure or at least implementation defined, because
> > of the sign bit issue).
> >
> > One interesting bit of non-portability comes from whether it
> > is possible to define these operators for *USER* defined
> > unsigned types. The RM does not require this capability, but
> > in GNAT you can define your own intrinsic shift functions for
> > your own modular types, and GNAT will permit this. I do not
> > know if other Ada 95 compilers provide this capability.
>
> That is interesting...

When I want one of my own, I always derive from those in Interfaces to
inherit the primitives.





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

* Re: bitstreams
  2001-01-16  0:39     ` bitstreams Robert Dewar
@ 2001-01-16 23:26       ` Rajagopalan Srinivasan
  0 siblings, 0 replies; 16+ messages in thread
From: Rajagopalan Srinivasan @ 2001-01-16 23:26 UTC (permalink / raw)


in fact the basic technique used here was designed many many years ago using
a VAX (VMS and ELN) Ada compiler.


"Robert Dewar" <robert_dewar@my-deja.com> wrote in message
news:94058v$f3m$1@nnrp1.deja.com...
> In article <93vkl3$1j$1@nnrp1.deja.com>,
>   mark_lundquist@my-deja.com wrote:
> > Beware, though... this is implementation-dependent. If the
> > compiler doesn't represent a packed array of boolean as a bit
> > vector, it doesn't work.
>
> That's misleading, any compiler that conforms to Annex C must
> properly pack array of Boolean, and surely no one would use
> a non-annex C compiler in a context like this (virtually all
> Ada 95 compilers in current use implement Annex C).
>
>
> Sent via Deja.com
> http://www.deja.com/





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

* Re: bitstreams
  2001-01-16 20:08       ` bitstreams Pat Rogers
@ 2001-01-17  2:15         ` Robert Dewar
  0 siblings, 0 replies; 16+ messages in thread
From: Robert Dewar @ 2001-01-17  2:15 UTC (permalink / raw)


In article <jT196.318$6Q2.44214@nnrp3.sbc.net>,
  "Pat Rogers" <progers@NOclasswideSPAM.com> wrote:
> When I want one of my own, I always derive from those in
> Interfaces to inherit the primitives.

That can be annoying. Suppose what you really want to do is

   type Unsigned is mod 2 ** Integer'Size;

and then you want to define shift operators on this. It is
uncomfortable to have to use the types in Interfaces for this
purpose.


Sent via Deja.com
http://www.deja.com/



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

end of thread, other threads:[~2001-01-17  2:15 UTC | newest]

Thread overview: 16+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2001-01-14 14:47 bitstreams Daniel Nilsson
2001-01-14 15:10 ` bitstreams Larry Kilgallen
2001-01-14 16:15 ` bitstreams tmoran
2001-01-14 19:46 ` bitstreams srini
2001-01-15 19:56   ` bitstreams mark_lundquist
2001-01-15 21:54     ` bitstreams Tucker Taft
2001-01-16  0:41       ` bitstreams Robert Dewar
2001-01-16  0:39     ` bitstreams Robert Dewar
2001-01-16 23:26       ` bitstreams Rajagopalan Srinivasan
2001-01-15 19:21 ` bitstreams mark_lundquist
2001-01-15 20:43   ` bitstreams Pat Rogers
2001-01-15 21:15     ` bitstreams mark_lundquist
2001-01-16  0:59   ` bitstreams Robert Dewar
2001-01-16 17:36     ` bitstreams mark_lundquist
2001-01-16 20:08       ` bitstreams Pat Rogers
2001-01-17  2:15         ` bitstreams Robert Dewar

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