comp.lang.ada
 help / color / mirror / Atom feed
* Interrupt Calls
@ 1997-11-08  0:00 Chad R. Meiners
  1997-11-10  0:00 ` Jerry van Dijk
  1997-11-10  0:00 ` Laura & Mike Palmer
  0 siblings, 2 replies; 10+ messages in thread
From: Chad R. Meiners @ 1997-11-08  0:00 UTC (permalink / raw)



Would anyone be able to give me an example on how to call an interrupt
in Ada.  I have tried to sort through the reference manual, and I have
looked in interrupt packages.  I am intending to call the dos interrupt
21h, and I am using Gnat 3.10p for NT if that makes a difference.
Thanks
-Chad R. Meiners





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

* Re: Interrupt Calls
  1997-11-08  0:00 Interrupt Calls Chad R. Meiners
@ 1997-11-10  0:00 ` Jerry van Dijk
  1997-11-11  0:00   ` Chad R. Meiners
  1997-11-10  0:00 ` Laura & Mike Palmer
  1 sibling, 1 reply; 10+ messages in thread
From: Jerry van Dijk @ 1997-11-10  0:00 UTC (permalink / raw)



In article <34651851.DAA7064E@academic.truman.edu> v025@academic.truman.edu writes:

>Would anyone be able to give me an example on how to call an interrupt
>in Ada.  I have tried to sort through the reference manual, and I have
>looked in interrupt packages.  I am intending to call the dos interrupt
>21h, and I am using Gnat 3.10p for NT if that makes a difference.

There would be little point in supporting Interrupts on Win95 or NT,
since there are no interrupts to support...

However, that does not mean your are lost, there are several options,
depending on which int21h calls you wanted to issue:

a) There is a Ada equivalent
b) There is a Win32 equivalent
c) There is a MS-C RTL equivalent
d) use dirty tricks using inline assembly

Otherwise, you can use the GNAT DOS compiler, which will naturally
support calling int21h functions.

Without knowing what functionality you are looking for I cannot give
more details.

--

-- Jerry van Dijk | Leiden, Holland
-- Consultant     | Team Ada
-- Ordina Finance | jdijk@acm.org




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

* Re: Interrupt Calls
  1997-11-08  0:00 Interrupt Calls Chad R. Meiners
  1997-11-10  0:00 ` Jerry van Dijk
@ 1997-11-10  0:00 ` Laura & Mike Palmer
  1997-11-11  0:00   ` Jerry van Dijk
  1997-11-12  0:00   ` Jerry van Dijk
  1 sibling, 2 replies; 10+ messages in thread
From: Laura & Mike Palmer @ 1997-11-10  0:00 UTC (permalink / raw)



Hi,
      here is an interesting example of how to use INT 21, as it make use
of  GNAT's ability to call C programs easily.
 
N.B. We use Windows 95.

First of all, you must create a package which contains a record that
defines  the registers and a procedure that will allow you to call the
interrupt.

For this purpose you can use 'package Disk', file disk.ads.

Then you need to write a C program which contains your own defined
procedure 
(void ada86) that uses the machine interrupt 'int86'. Why C ? Because so
you can use the C libraries --> Dos.h

You can call the C program DISKC.C

To test it write a procedure that calls My_Int86. You can use any
interrupts you like, in this example we use INT21, 36.

The package Interfaces is in the directory   ' GNAT305/ADAINC ' and allows
the eay usage of C types in Ada code.

***********************************************************************
*  DISK.ADS
*   This is the package spec; here we define a record that contains the
registers;
*   also we declare our custom design interrupt procedure (my_int86) which
has 
*   three parameters.
*   'pragma Import' import the procedure from the C program.
*
***********************************************************************

with Interfaces;   use Interfaces;
with Interfaces.C; use Interfaces.C;

package Disk is


   type Dpmi_Regs is
      record
         Di     : Unsigned_16;
         Di_Hi  : Unsigned_16;
         Si     : Unsigned_16;
         Si_Hi  : Unsigned_16;
         Bp     : Unsigned_16;
         Bp_Hi  : Unsigned_16;
         Res    : Unsigned_16;
         Res_Hi : Unsigned_16;
         Bx     : Unsigned_16;
         Bx_Hi  : Unsigned_16;
         Dx     : Unsigned_16;
         Dx_Hi  : Unsigned_16;
         Cx     : Unsigned_16;
         Cx_Hi  : Unsigned_16;
         Ax     : Unsigned_16;
         Ax_Hi  : Unsigned_16;
         Flags  : Unsigned_16;
         Es     : Unsigned_16;
         Ds     : Unsigned_16;
         Fs     : Unsigned_16;
         Gs     : Unsigned_16;
         Ip     : Unsigned_16;
         Cs     : Unsigned_16;
         Sp     : Unsigned_16;
         Ss     : Unsigned_16;
      end record;
   pragma Convention(C, Dpmi_Regs);

--------------------------------------------------------------

        procedure My_Int86(BIOS_number : Unsigned_16; -- from Interfaces.C
                            Registers_In : in out Dpmi_Regs;
                            Registers_Out : in out Dpmi_Regs);
	
        pragma Import(C, My_Int86, "ada86");
		--     Ada name /    C name/
--------------------------------------------------------------
end Disk;    (END OF DISK.ADS)

***********************************************************************
*  DISKC.C
*  This is your interface program.
*  You need this C program to be able to use the C libraries.
*  After you define your ada interrupt procedure (my_int86)(see disk.ads)
you have to
*  import it using (pragma Import). This allow you to create a C procedure 
* (void ada86) that can use the predefined machine interrupt 'int86'. 
*
***********************************************************************


#include <dos.h> 

/* This is a 'wrapper' to the C function that is provided in dos.h */

void ada86 (int num, union REGS *in_regs, union REGS *out_regs)
{
   int86 (num, in_regs, out_regs); 
}


(END OF DISKC.C)



***********************************************************************
*  TEST.ADB
*  This is your test procedure. In this example we use INT 21, 36 that
gives 
*  information about the free space on the disk. 
*  AX   =  36
*  DX   =  3    that is the C drive (A=1, B=2, C=3, etc.)
*
* the procedure My_Int86(16#21#, Reg_in, Reg_Out) has three parameters;
* you can pass the interrupt number; in this case 21, as the first
parameter
*   
*
***********************************************************************
with Interfaces.c;
use Interfaces.c;

with Ada.Text_IO;
use Ada.Text_IO;

with Disk;
use Disk;

procedure Test is

      Reg_in, Reg_out : Dpmi_Regs;
      The_Buffer : Buffer_Type := (others => 0);
     
 package Int_IO is new Ada.Text_IO.Integer_IO(Integer);
   use Int_IO;
begin
      Reg_in.Ax := 16#3600#;      -- INT 21, 36 Gets Disk Free Space
      -- Note Ax covers both AH and AL and so the above assigns 36 to AH
      Reg_in.Dx := 16#0003#;      -- drive number (1 - 25; A: - Z:)
      -- Note Dx covers DH and DL, as above

      My_Int86(16#21#, Reg_in, Reg_Out);
      
    Put ("Number Available Of Clusters : ");
    Put(Integer(Reg_Out.bx));
    new_line;
    Put ("Number Of Byte per Sector : ");
    Put(Integer(Reg_Out.cx));
    new_line;
    Put ("Number Of Cluster per Drive : ");
    Put(Integer(Reg_Out.dx));

end Test ;  (END OF TEST.ADB)

******************************************************************

SUMMARY

a)  Create a directory and dump all the files (disk.ads, diskc.c and
test.adb)
b)  From dos type the following :

C:\ gcc -c diskc.c -- this compiles the C program to produce an object code
file 
		    -- for subsequent linking

     C:\  gnat make test.adb

-- this will compile bind and link the test program

N.B. at this point you will see an error message saying that the link has
failed;
       just ignore it and type the following command.
     C:\  gnat link test.ali diskc.o -- this is a correct link command
You should now have an executable 'test.exe', just type
     C:\  test

and ENJOY !!!

Mike and Laura Palmer

Any problems / queries contact us at :

	thepalmers@lineone.net



Chad R. Meiners <v025@academic.truman.edu> wrote in article
<34651851.DAA7064E@academic.truman.edu>...
> Would anyone be able to give me an example on how to call an interrupt
> in Ada.  I have tried to sort through the reference manual, and I have
> looked in interrupt packages.  I am intending to call the dos interrupt
> 21h, and I am using Gnat 3.10p for NT if that makes a difference.
> Thanks
> -Chad R. Meiners
> 
> 




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

* Re: Interrupt Calls
  1997-11-10  0:00 ` Jerry van Dijk
@ 1997-11-11  0:00   ` Chad R. Meiners
  1997-11-12  0:00     ` Jerry van Dijk
  0 siblings, 1 reply; 10+ messages in thread
From: Chad R. Meiners @ 1997-11-11  0:00 UTC (permalink / raw)



In article <879126407.74snx@jvdsys.nextjk.stuyts.nl>, 
jerry@jvdsys.nextjk.stuyts.nl says...
>
>In article <34651851.DAA7064E@academic.truman.edu> v025@academic.truman.edu 
writes:
>
>>Would anyone be able to give me an example on how to call an interrupt
>>in Ada.  I have tried to sort through the reference manual, and I have
>>looked in interrupt packages.  I am intending to call the dos interrupt
>>21h, and I am using Gnat 3.10p for NT if that makes a difference.
>
>There would be little point in supporting Interrupts on Win95 or NT,
>since there are no interrupts to support...
>
>However, that does not mean your are lost, there are several options,
>depending on which int21h calls you wanted to issue:
>
>a) There is a Ada equivalent
>b) There is a Win32 equivalent
>c) There is a MS-C RTL equivalent
>d) use dirty tricks using inline assembly
>
>Otherwise, you can use the GNAT DOS compiler, which will naturally
>support calling int21h functions.
>
>Without knowing what functionality you are looking for I cannot give
>more details.
>
>--
>
>-- Jerry van Dijk | Leiden, Holland
>-- Consultant     | Team Ada
>-- Ordina Finance | jdijk@acm.org
I am trying to write a package similar to your conio package.  So there would 
be a text screen manipulation package for the NT complier.  I figured since NT 
supports text-base dos programs all I would need to do is call the dos 
interrupt, but all I really need is a move cursor cursor function for my text 
graphics routines.





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

* Re: Interrupt Calls
  1997-11-10  0:00 ` Laura & Mike Palmer
@ 1997-11-11  0:00   ` Jerry van Dijk
  1997-11-12  0:00   ` Jerry van Dijk
  1 sibling, 0 replies; 10+ messages in thread
From: Jerry van Dijk @ 1997-11-11  0:00 UTC (permalink / raw)



In article <01bcee03$8908d020$cd3663c3@default> thepalmers@lineone.net writes:

>      here is an interesting example of how to use INT 21, as it make use
>of  GNAT's ability to call C programs easily.
>
>N.B. We use Windows 95.

Sorry, you might be running your program in a Windows command shell,
but you cannot possibly be using the NT compiler.

In fact, you are using the GNAT DOS compiler as shown by:

>   type Dpmi_Regs is

where have I seen this before... :-)

>#include <dos.h>

There is no such header in the GNAT 3.10p1 for NT distribution.

-- Jerry van Dijk | Leiden, Holland
-- Consultant     | Team Ada
-- Ordina Finance | jdijk@acm.org




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

* Re: Interrupt Calls
  1997-11-10  0:00 ` Laura & Mike Palmer
  1997-11-11  0:00   ` Jerry van Dijk
@ 1997-11-12  0:00   ` Jerry van Dijk
       [not found]     ` <01bcf06a$ba1d1900$933e63c3@default>
  1 sibling, 1 reply; 10+ messages in thread
From: Jerry van Dijk @ 1997-11-12  0:00 UTC (permalink / raw)



In article <01bcee03$8908d020$cd3663c3@default> thepalmers@lineone.net writes:

>      here is an interesting example of how to use INT 21, as it make use
>of  GNAT's ability to call C programs easily.

As long as you are using GNAT/DOS, why not simplify things, and write
the whole program in Ada ?


-- ************************************************
-- * dos_int.ads - execute realmode DOS interrups *
-- ************************************************

with Interfaces;

package DOS_Int is

   ---------------------------------------------
   -- NAME:    Dpmi_Regs                      --
   --                                         --
   -- PURPOSE: Simplified processor registers --
   ---------------------------------------------
   type Dpmi_Regs is
      record
         Di     : Interfaces.Unsigned_16;
         Di_Hi  : Interfaces.Unsigned_16;
         Si     : Interfaces.Unsigned_16;
         Si_Hi  : Interfaces.Unsigned_16;
         Bp     : Interfaces.Unsigned_16;
         Bp_Hi  : Interfaces.Unsigned_16;
         Res    : Interfaces.Unsigned_16;
         Res_Hi : Interfaces.Unsigned_16;
         Bx     : Interfaces.Unsigned_16;
         Bx_Hi  : Interfaces.Unsigned_16;
         Dx     : Interfaces.Unsigned_16;
         Dx_Hi  : Interfaces.Unsigned_16;
         Cx     : Interfaces.Unsigned_16;
         Cx_Hi  : Interfaces.Unsigned_16;
         Ax     : Interfaces.Unsigned_16;
         Ax_Hi  : Interfaces.Unsigned_16;
         Flags  : Interfaces.Unsigned_16;
         Es     : Interfaces.Unsigned_16;
         Ds     : Interfaces.Unsigned_16;
         Fs     : Interfaces.Unsigned_16;
         Gs     : Interfaces.Unsigned_16;
         Ip     : Interfaces.Unsigned_16;
         Cs     : Interfaces.Unsigned_16;
         Sp     : Interfaces.Unsigned_16;
         Ss     : Interfaces.Unsigned_16;
      end record;

   --------------------------------------------------
   -- NAME:    Dpmi_Int                            --
   --                                              --
   -- PURPOSE: Call a real-mode interrupt          --
   --                                              --
   -- INPUTS:  Vector - Interrupt number           --
   --          Regs   - Processor registers        --
   --                                              --
   -- OUTPUTS: Regs - Modified processor registers --
   --------------------------------------------------
   procedure Dpmi_Int(Vector : in     Interfaces.Unsigned_16;
                      Regs   : in out Dpmi_Regs);

private

   pragma Convention(C, Dpmi_Regs);
   pragma Import(C, Dpmi_Int, "__dpmi_int");

end DOS_Int;


-- ***************************************************
-- * test.adb - shows calling realmode DOS interrups *
-- ***************************************************

with DOS_Int; use DOS_Int;

with Interfaces;  use Interfaces;
with Ada.Text_IO; use Ada.Text_IO;

procedure Test is

   DOS_Drive          : constant Unsigned_16 := 16#0003#;
   DOS_Get_Disk_Space : constant Unsigned_16 := 16#3600#;
   DOS_Interrupt      : constant Unsigned_16 := 16#0021#;

   Regs : Dpmi_Regs;

begin

   Regs.Dx := Dos_Drive;
   Regs.Ax := DOS_Get_Disk_Space;
   Dpmi_Int (DOS_Interrupt, Regs);

   Put_Line ("Number Available Of Clusters:" & Regs.Bx'Img);
   Put_Line ("Number Of Byte per Sector:   " & Regs.Cx'Img);
   Put_Line ("Number Of Cluster per Drive: " & Regs.Dx'Img);

end Test;

--

-- Jerry van Dijk | Leiden, Holland
-- Consultant     | Team Ada
-- Ordina Finance | jdijk@acm.org




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

* Re: Interrupt Calls
  1997-11-11  0:00   ` Chad R. Meiners
@ 1997-11-12  0:00     ` Jerry van Dijk
  0 siblings, 0 replies; 10+ messages in thread
From: Jerry van Dijk @ 1997-11-12  0:00 UTC (permalink / raw)



In article <3467a0ef.0@silver.truman.edu> v025@academic.truman.edu writes:

>I am trying to write a package similar to your conio package.  So there would
>be a text screen manipulation package for the NT complier.  I figured since NT
>supports text-base dos programs all I would need to do is call the dos
>interrupt, but all I really need is a move cursor cursor function for my text
>graphics routines.

Unfortunately, there is no such thing as a 'dos interrupt' in a Win95/NT
program. To do this you need to use the Win32 API.

I will release AdaConio (a console package simular to conio for DOS) for
Win95/NT after the next upgrade of AdaGraph.

In the meantime, if you just need cursor control, the following might be
of some help:


-- ****************************************
-- * cursor.ads - Win95/NT cursor control *
-- ****************************************

package Cursor is

   procedure Console_Size (X, Y: out Integer);

   function Where_X return Integer;
   function Where_Y return Integer;

   procedure Goto_XY (X, Y: Integer);

end Cursor;


-- ****************************************
-- * cursor.adb - Win95/NT cursor control *
-- ****************************************

pragma C_Pass_By_Copy (128);

package body Cursor is

   -----------------
   -- WIN32 stuff --
   -----------------

   type SHORT is mod 2 ** 16;
   for SHORT'Size use 16;

   subtype WORD   is SHORT;
   subtype BOOL   is Integer;
   subtype DWORD  is Integer;
   subtype HANDLE is Integer;

   type COORD is
      record
         X : SHORT;
         Y : SHORT;
      end record;
   pragma Convention (C, COORD);

   type SMALL_RECT is
      record
         Left   : SHORT;
         Top    : SHORT;
         Right  : SHORT;
         Bottom : SHORT;
      end record;
   pragma Convention (C, SMALL_RECT);

   type CONSOLE_SCREEN_BUFFER_INFO is
      record
         Size       : COORD;
         Cursor_Pos : COORD;
         Attrib     : WORD;
         Window     : SMALL_RECT;
         Max_Size   : COORD;
      end record;
   pragma Convention (C, CONSOLE_SCREEN_BUFFER_INFO);

   type PCONSOLE_SCREEN_BUFFER_INFO is access all CONSOLE_SCREEN_BUFFER_INFO;
   pragma Convention (C, PCONSOLE_SCREEN_BUFFER_INFO);

   function GetStdHandle (Value : DWORD) return HANDLE;
   pragma Import (StdCall, GetStdHandle, "GetStdHandle");

   function SetConsoleCursorPosition (Buffer : HANDLE;
                                      Pos    : COORD)
                                      return BOOL;
   pragma Import (StdCall, SetConsoleCursorPosition,
                          "SetConsoleCursorPosition");

   function GetConsoleScreenBufferInfo (Buffer : HANDLE;
                                        Info   : PCONSOLE_SCREEN_BUFFER_INFO)
                                        return BOOL;
   pragma Import (StdCall, GetConsoleScreenBufferInfo,
                          "GetConsoleScreenBufferInfo");

   FALSE                : constant BOOL   := 0;
   STD_OUTPUT_HANDLE    : constant DWORD  := -11;
   INVALID_HANDLE_VALUE : constant HANDLE := -1;

   Output_Buffer   : HANDLE;
   Buffer_Info_Rec : aliased CONSOLE_SCREEN_BUFFER_INFO;
   Buffer_Info     : PCONSOLE_SCREEN_BUFFER_INFO := Buffer_Info_Rec'Access;

   Cursor_Pos_Error     : Exception;
   Buffer_Info_Error    : Exception;
   Invalid_Handle_Error : Exception;

   ----------------------
   -- Supporting stuff --
   ----------------------

   procedure Get_Buffer_Info is
   begin
      if GetConsoleScreenBufferInfo (Output_Buffer, Buffer_Info) = FALSE then
         raise Buffer_Info_Error;
      end if;
   end Get_Buffer_Info;

   ---------------------
   -- Implementations --
   ---------------------

   procedure Console_Size (X, Y: out Integer) is
   begin
      Get_Buffer_Info;
      X := Integer (Buffer_Info_Rec.Size.X);
      Y := Integer (Buffer_Info_Rec.Size.Y);
   end Console_Size;

   function Where_X return Integer is
   begin
      Get_Buffer_Info;
      return Integer (Buffer_Info_Rec.Cursor_Pos.X);
   end Where_X;

   function Where_Y return Integer is
   begin
      Get_Buffer_Info;
      return Integer (Buffer_Info_Rec.Cursor_Pos.Y);
   end Where_Y;

   procedure Goto_XY (X, Y: in Integer) is
      New_Pos : COORD := (SHORT (X), SHORT (Y));
   begin
      Get_Buffer_Info;

      if New_Pos.X > Buffer_Info_Rec.Size.X then
         New_Pos.X := Buffer_Info_Rec.Size.X;
      end if;

      if New_Pos.Y > Buffer_Info_Rec.Size.Y then
         New_Pos.Y := Buffer_Info_Rec.Size.Y;
      end if;

      if SetConsoleCursorPosition (Output_Buffer, New_Pos) = FALSE then
         raise Cursor_Pos_Error;
      end if;

   end Goto_XY;

--------------------
-- Initialization --
--------------------
begin
   Output_Buffer := GetStdHandle (STD_OUTPUT_HANDLE);
   if Output_Buffer = INVALID_HANDLE_VALUE then
      raise Invalid_Handle_Error;
   end if;
end Cursor;

--

-- Jerry van Dijk | Leiden, Holland
-- Consultant     | Team Ada
-- Ordina Finance | jdijk@acm.org




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

* Re: Interrupt Calls
       [not found]     ` <01bcf06a$ba1d1900$933e63c3@default>
@ 1997-11-21  0:00       ` Chad R. Meiners
  1997-11-21  0:00         ` Larry Coon
  0 siblings, 1 reply; 10+ messages in thread
From: Chad R. Meiners @ 1997-11-21  0:00 UTC (permalink / raw)



Okay, I now understand how to interface win32 through NT thanks to Jerry.  The 
reason I wanted the package so I could change the cursor.  Jerry also showed me 
how to accomplish this in ada.  I am using this package it write a Nethack 
clone solely an Ada.  I haven't replied due partally due to class load and 
mainly due to my news server being down.  Thank you for all your help. 





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

* Re: Interrupt Calls
  1997-11-21  0:00       ` Chad R. Meiners
@ 1997-11-21  0:00         ` Larry Coon
  1997-11-22  0:00           ` Jerry van Dijk
  0 siblings, 1 reply; 10+ messages in thread
From: Larry Coon @ 1997-11-21  0:00 UTC (permalink / raw)



Chad R. Meiners wrote:

> Okay, I now understand how to interface win32 through NT thanks to Jerry.  The
> reason I wanted the package so I could change the cursor.

BTW, if you're doing it in a DOS window (as I think I
remember reading) and you have ansi.sys loaded, this works
for cursor positioning:

package screen is
	procedure clear_screen;
	procedure move_cursor (row, col: natural);
end screen;

with ada.text_io; use ada.text_io;
package body screen is
	procedure clear_screen is
	begin
		put (character'val (27));
		put ("[2J");		
	end clear_screen;

	procedure move_cursor (row, col: natural) is
		package nat_io is new integer_io (natural);
		use nat_io;
	begin
		put (character'val (27));
		put ("[");
		put (row, width => 1);
		put (';');
		put (col, width => 1);
		put ('f');
	end move_cursor;
end screen;

Larry Coon
University of California
larry@assist.org
and lmcoon@home.com




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

* Re: Interrupt Calls
  1997-11-21  0:00         ` Larry Coon
@ 1997-11-22  0:00           ` Jerry van Dijk
  0 siblings, 0 replies; 10+ messages in thread
From: Jerry van Dijk @ 1997-11-22  0:00 UTC (permalink / raw)



In article <3475CE2D.5424@assist.org> larry@assist.org writes:

>> Okay, I now understand how to interface win32 through NT thanks to Jerry. > The
>> reason I wanted the package so I could change the cursor.
>
>BTW, if you're doing it in a DOS window (as I think I
>remember reading) and you have ansi.sys loaded, this works
>for cursor positioning:

Only on Win95, not on NT.

--

-- Jerry van Dijk | Leiden, Holland
-- Consultant     | Team Ada
-- Ordina Finance | jdijk@acm.org




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

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

Thread overview: 10+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
1997-11-08  0:00 Interrupt Calls Chad R. Meiners
1997-11-10  0:00 ` Jerry van Dijk
1997-11-11  0:00   ` Chad R. Meiners
1997-11-12  0:00     ` Jerry van Dijk
1997-11-10  0:00 ` Laura & Mike Palmer
1997-11-11  0:00   ` Jerry van Dijk
1997-11-12  0:00   ` Jerry van Dijk
     [not found]     ` <01bcf06a$ba1d1900$933e63c3@default>
1997-11-21  0:00       ` Chad R. Meiners
1997-11-21  0:00         ` Larry Coon
1997-11-22  0:00           ` Jerry van Dijk

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