comp.lang.ada
 help / color / mirror / Atom feed
* Problems with Serial Interupt routines in ADA on MSDOS
@ 1997-05-20  0:00 tmoran
  0 siblings, 0 replies; 2+ messages in thread
From: tmoran @ 1997-05-20  0:00 UTC (permalink / raw)



>locks up the CPU every now and then.
  So the problem is probably not in the initialization code (the
first 300 lines of your 700 line message).

>context switching by the dos extender
  Can it reliably do all of what's necessary, plus your substantial
processing, in 500 microseconds (19200 baud) on your hardware, in the
presence of other (timer, disk, etc) interrupts?

>  invoke RTKERNEL.RTK_SAVE_REGS_AND_RESTORE_CONTEXT
>  invoke RTKERNEL.RTK_SWITCH_STACK
>  invoke RTKERNEL.RTK_DISABLE_INTERRUPTS
>     process
>  invoke RTKERNEL.ENABLE_INTERRUPTS
>  invoke RTKERNEL.RTK_RESTORE_STACK
>  invoke RTKERNEL.RTK_RESTORE_REGS_AND_IRET

  Presumably if you are handling an interrupt, they are already disabled,
no?  And if interrupts are enabled while you are restoring stacks, is
that safe?  Interrupt enable/disable and context switching is also often
only approximately emulated in dos extenders.
  You might consider a loop inside your interrupt processing, since it's
quite possible a second byte might arrive, or you may be able to xmit
a second byte, before you've left the ISR.  If you test and process
you'll save interrupt handling overhead in those cases.  That design
will also upgrade more easily to a 16550 (buffering) chip.
  You don't say what else is going on.  If not much else during
transmission of a block, and the interrupt overhead is preventing
reliable 19200 operation, then you might consider polling instead
of interrupts.

> BAUD  : integer := 19200;
Shouldn't that be 'integer range 2 .. 115200', since any value outside
that range will not work and your code will silently do the wrong thing.

>   in_char := COM_PORT.MCR_set_DTR +
               COM_PORT.MCR_set_out2;   -- clear RTS = line
  Which do you want, DTR or RTS?  The comment disagrees with the code.
BTW, how long does a PORT.OUT_BYTE take on your system?  Do you really
need to keep setting DTR after every byte received?




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

* Problems with Serial Interupt routines in ADA on MSDOS
@ 1997-05-20  0:00 Lee Cookk
  0 siblings, 0 replies; 2+ messages in thread
From: Lee Cookk @ 1997-05-20  0:00 UTC (permalink / raw)



This is a multi-part message in MIME format.

------=_NextPart_000_01BC6545.338C1AE0
Content-Type: text/plain; charset=ISO-8859-1
Content-Transfer-Encoding: 7bit

I am having problems with an interupt routine for the serial ports which
locks up the
CPU every now and then.  I am using :
Meriadian ADA 4.1.4
DOS v6.2

The code is included.

Do  you know of any other serial port handler code I could use or can
anyone spot a problem with the code included.

I would be very grateful for any feedback on this problem.



------=_NextPart_000_01BC6545.338C1AE0
Content-Type: application/octet-stream; name="Serial.txt"
Content-Transfer-Encoding: quoted-printable
Content-Description: Serial.txt (Text Document)
Content-Disposition: attachment; filename="Serial.txt"

package com_port is

  ---------------------------------------------------------------
  --  Hardware definitions for the IBM PC communication ports  --
  ---------------------------------------------------------------

  -- Base I/O addresses for IBM PC communication ports

  COM1                : constant :=3D 16#3F8#;
  COM2                : constant :=3D 16#2F8#;

  -- 8250 Register offset from base address

  RDR_register        : constant :=3D 16#00#;  -- Receiver Buffer =
Register
					     --  (read only)
  THR_register        : constant :=3D 16#00#;  -- Transmitter Holding =
Register
					     --  (write only)
  IER_register        : constant :=3D 16#01#;  -- Interrupt Enable =
Register
  IIR_register        : constant :=3D 16#02#;  -- Interrupt Ident. =
Register
					     --  (read only)
  LCR_register        : constant :=3D 16#03#;  -- Line Control Register
  MCR_register        : constant :=3D 16#04#;  -- Modem Control Register
  LSR_register        : constant :=3D 16#05#;  -- Line Status Register
  MSR_register        : constant :=3D 16#06#;  -- Modem Status Register

  COM1_RDR            : constant :=3D COM1 + RDR_register;
  COM1_THR            : constant :=3D COM1 + THR_register;
  COM1_IER            : constant :=3D COM1 + IER_register;
  COM1_IIR            : constant :=3D COM1 + IIR_register;
  COM1_LCR            : constant :=3D COM1 + LCR_register;
  COM1_MCR            : constant :=3D COM1 + MCR_register;
  COM1_LSR            : constant :=3D COM1 + LSR_register;
  COM1_MSR            : constant :=3D COM1 + MSR_register;

  -- Interrupt Enable Register values

  IER_disable_all     : constant :=3D 16#00#;  -- Disable all =
interruptss
  IER_receive_data    : constant :=3D 16#01#;  -- Data available =
interrupt enabled
  IER_transmit_data   : constant :=3D 16#02#;  -- THR reg. empty =
interrupt enabled
  IER_line_status     : constant :=3D 16#04#;  -- Receive line status =
interrupt
					     --  enabled
  IER_modem_status    : constant :=3D 16#08#;  -- Modem status interrupt =
enabled

  -- Interrupt Identification Register values (read only)
  --  All other values mean no interrupt is pending

  IIR_modem_status    : constant :=3D 16#00#;  -- Modem status interrupt =
pending
  IIR_transmit_data   : constant :=3D 16#02#;  -- THR reg. empty =
interrupt pending
  IIR_receive_data    : constant :=3D 16#04#;  -- Recieved data =
available
					     --  interrupt pending
  IIR_line_status     : constant :=3D 16#06#;  -- Receiver line status =
interrupt
					     --  pending
  IIR_interrupt_mask  : constant :=3D 16#07#;  -- To extract interrupt =
id only

  -- Line Control Register values

  LCR_5_bits          : constant :=3D 16#00#;  -- Char. length is 5 bits
  LCR_6_bits          : constant :=3D 16#01#;  -- Char. length is 6 bits
  LCR_7_bits          : constant :=3D 16#02#;  -- Char. length is 7 bits
  LCR_8_bits          : constant :=3D 16#03#;  -- Char. length is 8 bits =
(mask)
  LCR_1_stop_bit      : constant :=3D 16#00#;  -- Number of stop bits is =
1
  LCR_2_stop_bits     : constant :=3D 16#04#;  -- Number of stop bits is =
2 (mask)
  LCR_no_parity       : constant :=3D 16#00#;  -- Parity =
generat./checking is off
  LCR_odd_parity      : constant :=3D 16#08#;  -- Parity is odd
  LCR_even_parity     : constant :=3D 16#18#;  -- Parity is even
  LCR_one_parity      : constant :=3D 16#28#;  -- Parity is always 1
  LCR_zero_parith     : constant :=3D 16#38#;  -- Parity is always 0 =
(mask)
  LCR_break           : constant :=3D 16#40#;  -- Generate break signal
  LCR_DLAB            : constant :=3D 16#80#;  -- Divisor latch access =
bit

  -- Modem Control Register values

  MCR_set_DTR         : constant :=3D 16#01#;  -- Set data terminal =
ready line
  MCR_set_RTS         : constant :=3D 16#02#;  -- Set request to send =
line
  MCR_set_out1        : constant :=3D 16#04#;  -- Set user-defined =
output 1 line
  MCR_set_out2        : constant :=3D 16#08#;  -- Set user-defined =
output 2 line
  MCR_set_loop        : constant :=3D 16#10#;  -- Set UART loopback =
feature

  -- Line Status Register values

  LSR_data_ready      : constant :=3D 16#01#;  -- Receiver data is ready =
in RDR
  LSR_overrun_error   : constant :=3D 16#02#;  -- Receiver buffer reg =
overflowed
  LSR_parity_error    : constant :=3D 16#04#;  -- Received char has bad =
parity
  LSR_framing_error   : constant :=3D 16#08#;  -- Received char has bad =
stop bit
  LSR_break_interrupt : constant :=3D 16#10#;  -- Receiver detected a =
break signal
  LSR_THR_empty       : constant :=3D 16#20#;  -- THR register is empty
  LSR_TSR_empty       : constant :=3D 16#40#;  -- Transmitter Shift =
Register is
					     --  empty
  LSR_time_out_error  : constant :=3D 16#80#;  -- Time out error =
occurred

  -- Modem Status Register values

  MSR_CTS_changed     : constant :=3D 16#01#;  -- Clear To Send bit =
changed state
  MSR_DSR_changed     : constant :=3D 16#02#;  -- Data Set Ready bit =
changed state
  MSR_RI_changed      : constant :=3D 16#04#;  -- Ring Indicator changed =
state
  MSR_DCD_changed     : constant :=3D 16#08#;  -- Data Carrier Detect =
changed state
  MSR_CTS             : constant :=3D 16#10#;  -- Clear To Send state
  MSR_DSR             : constant :=3D 16#20#;  -- Data Set Ready state
  MSR_RI              : constant :=3D 16#40#;  -- Ring Indicator state
  MSR_DCD             : constant :=3D 16#80#;  -- Data Carrier Detect =
state

end com_port;=0A=

-------------------------------------------------------------------------=
-
--
-- UNIT SPECIFICATION
--
   procedure MS_OPEN_FCP_COMMS is
--
-- PARAMETER DEFINITIONS
--
-- None
--
-- UNIT DESCRIPTION
--
-- This proc setups up and initialises the fcp<->fcc comms driver.
-- It should be called only once, at the beginning of process inits =
only.
--
-- TYPE DEFINITIONS
--
-- None
--
-- SOFTWARE VARIABLES
--
-- Used for temporary storage.
--
   I1    : integer;

-- baud rate
--
   BAUD  : integer :=3D 19200;

-- Determines the communication protocol to be initialised.
-- (ie. 8 bits, 1 stop bit, and no parity)
--
   FLAGS : integer :=3D ( COM_PORT.LCR_8_bits +
                        COM_PORT.LCR_1_stop_bit +
                        COM_PORT.LCR_no_parity) ;

-- Used for setting the Baud rate.
--
   BAUD_DIVISOR         : integer;

-- Used for defining communication interrupts.
--
   REG_FILE             : INTERRUPT.REGISTERS :=3D (others =3D> 0);

-- Used for defining communication interrupts on Comm1.
--
   INTMASK              : INTEGER;

-- Contains the communication protocol for process control.
--
   MODEM_CONTROL_VALUES : constant :=3D COM_PORT.MCR_set_DTR +
                                      COM_PORT.MCR_SET_OUT2;

-- Renaming function.
--
   function "and"(LEFT, RIGHT : in INTEGER) return INTEGER
                          renames BIT_OPS."and";
--
-- UNIT CODE
--
   begin
-->>  invoke RTKERNEL.RTK_GET_INTERRUPT_VECTOR
-->>  invoke RTKERNEL.RTK_SET_INTERRUPT_VECTOR
-->>  invoke RTKERNEL.RTK_DISABLE_INTERRUPTS
-->>  write data to the output port

      OLD_HANDLER :=3D RTKERNEL.RTK_GET_INTERRUPT_VECTOR
                                          (NUMBER =3D> =
HW_INT.INT_COM_PORT1);

      RTKERNEL.RTK_SET_INTERRUPT_VECTOR(NUMBER =3D> =
HW_INT.INT_COM_PORT1,
                                        HANDLER =3D> =
COM_PORT_HANDLER'ADDRESS);

      RTKERNEL.RTK_DISABLE_INTERRUPTS;
      PORT.OUT_BYTE(PORT_NUMBER =3D> HW_INT.INC1_OCR,
                    DATA =3D> HW_INT.OCR_EOI_COM_PORT1);

--
--  Initialize the port's baud rate and protocols.
--
    BAUD_DIVISOR :=3D integer(115200 / BAUD);
    BAUD_DIVISOR :=3D (BAUD_DIVISOR and 16#0000FFFF#);

    i1 :=3D (FLAGS + COM_PORT.LCR_DLAB);
--
-- enable baud rate load
--
    PORT.OUT_BYTE (PORT_NUMBER =3D> ( COM_PORT.COM1_LCR ),
                   DATA        =3D> integer'pos(I1));
--
-- lsb byte
--
    I1 :=3D (BAUD_DIVISOR and 16#000000FF#);
    PORT.OUT_BYTE (PORT_NUMBER =3D> (COM_PORT.COM1_RDR),
                   DATA        =3D> integer'pos(i1));
--
-- msb byte
--
    I1 :=3D BIT_OPS.SHR ((BAUD_DIVISOR and 16#0000FF00#),8);
    PORT.OUT_BYTE (PORT_NUMBER =3D> ( COM_PORT.COM1_IER ),
                   DATA        =3D> integer'pos(i1));
--
-- Reload protocols
--
    PORT.OUT_BYTE (PORT_NUMBER =3D> ( COM_PORT.COM1_LCR ),
                   DATA        =3D> integer'pos(flags));


--
-->>  Enable the Rec. data  interrupts
--
--      i1 :=3D COM_PORT.IER_receive_data + COM_PORT.IER_modem_status;

      i1 :=3D COM_PORT.IER_receive_data;

      PORT.OUT_BYTE(PORT_NUMBER =3D> COM_PORT.COM1_IER,
                    DATA =3D> integer'pos(i1));
--
-->>  Enable COM1 interrupts
--

      INTMASK :=3D PORT.IN_BYTE(PORT_NUMBER =3D> HW_INT.INC1_IMR);
      INTMASK :=3D INTMASK and HW_INT.IMR1_ENABLE_COM_PORT1;
      PORT.OUT_BYTE(PORT_NUMBER =3D> HW_INT.INC1_IMR,
                    DATA =3D> INTEGER'POS(INTMASK));

--
-->>  Set modem signals like Data Terminal Ready
--

      PORT.OUT_BYTE(PORT_NUMBER =3D> COM_PORT.COM1_MCR,
                    DATA =3D> MODEM_CONTROL_VALUES);

--
-- Toss any pending input or status
--
-->>  read any pending input or status
      INTMASK :=3D PORT.IN_BYTE(PORT_NUMBER =3D> COM_PORT.COM1_RDR);
      INTMASK :=3D PORT.IN_BYTE(PORT_NUMBER =3D> COM_PORT.COM1_IIR);
      INTMASK :=3D PORT.IN_BYTE(PORT_NUMBER =3D> COM_PORT.COM1_LSR);
      INTMASK :=3D PORT.IN_BYTE(PORT_NUMBER =3D> COM_PORT.COM1_MSR);

-->>  invoke RTKERNEL.RTK_ENABLE_INTERRUPTS
      RTKERNEL.RTK_ENABLE_INTERRUPTS;


-->>  initialise serial IP buffer pointers

   end MS_OPEN_FCP_COMMS;

-------------------------------------------------------------------------=
-
--
-- UNIT SPECIFICATION
--
   procedure COM_PORT_HANDLER is
--
-- PARAMETER DEFINITIONS
--
-- Refer to Appendix B for the parameter description.
--
-- UNIT DESCRIPTION
--
-- This proc is the low level serial comms interupt handler called
-- whenever a com port interrupt occurs.
--
-- TYPE DEFINITIONS
--
-- None
--
-- SOFTWARE VARIABLES
--
-- Renaming function for BIT_OPS operator 'and'
--
   function "and"(LEFT, RIGHT : in INTEGER) return INTEGER renames =
BIT_OPS.
     "and";

--
-- UNIT CODE
--
   begin
-->>  invoke RTKERNEL.RTK_SAVE_REGS_AND_RESTORE_CONTEXT
-->>  invoke RTKERNEL.RTK_SWITCH_STACK
-->>  invoke RTKERNEL.RTK_DISABLE_INTERRUPTS
-->>  read data from port
-->>  mask data with interrupt
-->>  determine whether to transmit or receive data
-->>
-->>  invoke RTKERNEL.ENABLE_INTERRUPTS
-->>  invoke RTKERNEL.RTK_RESTORE_STACK
-->>  invoke RTKERNEL.RTK_RESTORE_REGS_AND_IRET


      RTKERNEL.RTK_SAVE_REGS_AND_RESTORE_CONTEXT;

      RTKERNEL.RTK_SWITCH_STACK(STACK_BASE =3D> INT_STACK'ADDRESS,
                                STACK_SIZE =3D> INT_STACK'LENGTH,
                                SAVED_CONTEXT =3D> SAVED_CONTEXT);
      RTKERNEL.RTK_DISABLE_INTERRUPTS;

--
--  Get Interrupt type and the line status.
--

      IN_CHAR  :=3D PORT.IN_BYTE(COM_PORT.COM1_IIR);
      IIR_STAT :=3D in_char;                           -- save for debug =
display
      lsr_stat :=3D PORT.IN_BYTE(COM_PORT.COM1_LSR);   -- save for debug =
display

--
--   Route to relevant interrupt condition.
--
--   Note: 'dchar' is for debugging purposes only.
--


        case (in_char and com_port.IIR_interrupt_mask) is       --
          when com_port.IIR_transmit_data =3D>  dchar :=3D 'T';


--
--        Handle the receipt of a data byte
--

          when com_port.IIR_receive_data  =3D>  dchar :=3D 'R';

               if ((lsr_stat and COM_PORT.LSR_data_ready) /=3D 0 ) then

                    MS_RX_BYTE;    -- receive a byte

                    in_char :=3D COM_PORT.MCR_set_DTR +
                               COM_PORT.MCR_set_out2;   -- clear RTS =
line

                    PORT.OUT_BYTE(PORT_NUMBER =3D> COM_PORT.COM1_MCR,
                                  DATA =3D> integer'pos(in_char));
               end if;

          when com_port.IIR_modem_status  =3D>  dchar :=3D 'S';
          when com_port.IIR_line_status   =3D>  dchar :=3D 'L';
          when others                     =3D>  dchar :=3D 'E';
        end case;


--
--  Interrupt routine exit formalities.
--

      PORT.OUT_BYTE(PORT_NUMBER =3D> HW_INT.INC1_OCR,
                    DATA =3D> HW_INT.OCR_EOI_COM_PORT1);
      RTKERNEL.RTK_ENABLE_INTERRUPTS;
      RTKERNEL.RTK_RESTORE_STACK(SAVED_CONTEXT =3D> SAVED_CONTEXT);
      RTKERNEL.RTK_RESTORE_REGS_AND_IRET;
   end COM_PORT_HANDLER;

-------------------------------------------------------------------------=
---
--

--
--        'com_port_poll_handler'
--
--        This routine must run in the main loop of the fcp
--        and NOT be merged into the interrupt routine, to reduce
--        overall interrupt activity and avoid unnecessary
--        context switching by the dos extender.
--
--        This routine  manages the necessary handshake control
--        lines between the FCP and the FCC.
--
--        The Protocol is that  1) When the 'DSR' line is hi,
--                                 the FCC whants to send a byte. So
--                                 we (FCP) will check if it is okay to =
do
--                                 so and assert the RTS line.
--                              2) When the FCC sees 'CTS' hi, it is =
allowed to
--                                 send a byte across.
--                              3) Upon receiving a byte, we (FCP) will =
get AN
--                                 RX data interrupt and we read the =
byte. After
--                                 the byte is read, we bring 'RTS' low.
--                              4) When FCC is ready to send another =
byte, it
--                                 tests to see 'CTS' is low first, =
otherwise
--                                 it cannot begin a new transmit byte =
phase.
--

  procedure com_port_poll_handler is

  in_char2 : integer :=3D 0;

  begin

     in_char1  :=3D PORT.IN_BYTE(COM_PORT.COM1_MSR);      -- get MSR =
contents.
     in_char2  :=3D PORT.IN_BYTE(COM_PORT.COM1_MCR);      -- get MCR =
contents.

     if  ((( in_char1 and COM_PORT.MSR_DSR) =3D COM_PORT.MSR_DSR) and
          (( in_char2 and COM_PORT.MCR_set_RTS) /=3D =
COM_PORT.MCR_set_RTS)) then

          in_char :=3D COM_PORT.MCR_set_out2 +
                     COM_PORT.MCR_set_DTR  +
                     COM_PORT.MCR_set_RTS;    -- set 'RTS' hi (CTS on =
FCC side)

          PORT.OUT_BYTE(PORT_NUMBER =3D> COM_PORT.COM1_MCR,
                           DATA =3D> integer'pos(in_char));
     end if;

  end COM_PORT_POLL_HANDLER;




-------------------------------------------------------------------------=
----
--
-- UNIT SPECIFICATION
--
   procedure MS_TRANSMIT is
--

-- PARAMETER DEFINITIONS
--
-- Refer to Appendix B for a description of the parameter data.
--
-- UNIT DESCRIPTION
--
-- This proc enables both rx & tx ints for fcp/fcc comms & starts the tx
-- phase.
-- Applicable for COM1 port only! com1 - 3f9  com2 - 2f9
-- It initiates the transmit phase by issuing a txmit hold buffer =
interrupt.
-- Before the issuing of the interrupt, it tests for the correct =
hardware
-- and issues the appropriate command for either the multi port card or
-- the system com port.
--
-- TYPE DEFINITIONS
--
-- None
--
-- SOFTWARE VARIABLES
--
-- Represents the low byte of a word value.
--
   T_LO     : NATURAL :=3D NATURAL(SERIAL_OP(2));

-- Represents the high byte of a word value.
--
   T_HI     : NATURAL :=3D NATURAL(SERIAL_OP(3));

-- Stores the byte count for the message, the value is derived
-- from t_lo and t_hi
--
   OP_COUNT : NATURAL :=3D (T_HI * 256) + T_LO;

-- Temporarily stores the values from the output buffer.
--
   TMP_BUFF : MULTI_COMMS.BYTE_BUFF :=3D =
(RTKERNEL.BYTE(FCP_TYPES.MSG_TYPE'POS
                                             =
(FCP_TYPES.MT_DISPLAY_MSG)),
                                        5,
                                        0,
                                   =
RTKERNEL.BYTE(MESSAGE_LIST.MESSAGE_ID'POS
                                 =
(MESSAGE_LIST.FCC_SOFTWARE_EXCEPTION_XXXX)),
                                 0, OTHERS =3D> 0);

-- UNIT CODE
--
   begin
-->>  enable receive and transmit interrupts

      if  Comm_types.Comm_system'pos(COM_HARDWARE) =3D
              Comm_types.Comm_system'pos(Comm_types.Scom_port)
      then
--
-- Load up the fcp comms o/p buffer for transmit.
--

         for I in 1..OP_COUNT loop
            TRANSMIT_BUFFER(TX_WRITE_PTR) :=3D SERIAL_OP(I);
            TX_WRITE_PTR :=3D TX_WRITE_PTR + 1;
            if TX_WRITE_PTR > END_POS then
               TX_WRITE_PTR :=3D START_POS;
            end if;
         end loop;

--         PORT.OUT_BYTE(PORT_NUMBER =3D> 16#03f9#, DATA =3D> 3);

      else
--
-- Load up the multi comms o/p buffer for transmit.
--
         if OP_COUNT > 3 then
            for I in 1..op_count  loop
               tmp_buff(i) :=3D rtkernel.byte(serial_op(I));
            end loop;
            multi_comms.mc_tx_to_mcomm(channel     =3D> =
comm_types.COMMS6,
                                       data_buffer =3D> tmp_buff,
                                       data_length =3D> op_count);
         else
            multi_comms.mc_tx_to_mcomm(channel     =3D> =
comm_types.COMMS6,
                                       data_buffer =3D> tmp_buff,
                                       data_length =3D> 5);
         end if;

      end if;

   end MS_TRANSMIT;

-------------------------------------------------------------------------=
-----

-------------------------------------------------------------------------=
-
--
-- UNIT SPECIFICATION
--
   procedure MS_RX_BYTE is
--
-- PARAMETER DEFINITIONS
--
-- Refer to Appendix B for the parameter description.
--
-- UNIT DESCRIPTION
--
-- This proc is a component the low level serial comms driver which
-- is called when a receive interrupt occurs. It will handle the case
-- of an in comming message packet.
--
-- TYPE DEFINITIONS
--
-- None
--
-- SOFTWARE VARIABLES
--
-- Data item used for temporaray storage of the
-- Size value of the serial input port.
--
   IP_SIZE       : INTEGER :=3D 0;

-- Used for temporary storing buffer data.
--
   I          : INTEGER :=3D 0;

--
-- UNIT CODE
--
   begin
-->>  read data from port
-->>  store data in the serial input buffer
-->>  select upon the input index
-->>     when 1 =3D>
-->>        reset the input count
-->>     when 2 =3D>
-->>        reset the input count
-->>     when 3 =3D>
-->>        determine the message size
-->>     when others =3D>
-->>        set the new message flag at the end of message receive
-->>  end case
-->>  decrement input index


      I :=3D PORT.IN_BYTE(PORT_NUMBER =3D> COM_PORT.COM1_RDR);

--      FCP_GFX.FIELD2_SPUT
--      (22,1,INTEGER'IMAGE(I));

      SERIAL_IP(BUFFER_WRITE_PTR) :=3D FCP_TYPES.BYTE'VAL(I);

      case TEMP_INDEX is
         when 1 =3D>
--                        message_complete :=3D false;
            IP_COUNT :=3D 0;                      -- rx the msg type =
byte
            old_write_ptr :=3D BUFFER_WRITE_PTR;

         when 2 =3D>
            T_LO :=3D INTEGER(SERIAL_IP(buffer_write_ptr));

         when 3 =3D>
            T_HI :=3D INTEGER(SERIAL_IP(buffer_write_ptr)) * 256;

            IP_SIZE  :=3D T_LO + T_HI;
            IP_COUNT :=3D IP_SIZE - 3;

         when others =3D>
            IP_COUNT :=3D IP_COUNT - 1;

            if IP_COUNT =3D 0 then
               TEMP_INDEX :=3D 0;
                           message_pending :=3D message_pending +1;
            end if;

      end case;

--
--        Check if a newly read message (complete one) means that we
--        would queue three messages. If so, dump this new message and =
carry on.
--        Otherwise, we have a legitimate message to queue or are in the
--        process of reading one.
--        Always keeping the buffer pointers in modulo 8k for circular =
buffer
--        operation where 8k is the current buffer size.
--

      if ((message_pending > 2) and (TEMP_INDEX =3D 0)) then
        message_pending :=3D message_pending -1;
        BUFFER_WRITE_PTR :=3D old_write_ptr;
      else
      BUFFER_WRITE_PTR :=3D buffer_write_ptr + 1;
         if BUFFER_WRITE_PTR > END_POS then
                  BUFFER_WRITE_PTR :=3D BUFFER_WRITE_PTR - END_POS;
         end if;
      end if;

--
--        Prepare the entry point for next time.
--

      TEMP_INDEX :=3D TEMP_INDEX + 1;

   end MS_RX_BYTE;

------=_NextPart_000_01BC6545.338C1AE0--





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

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

Thread overview: 2+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
1997-05-20  0:00 Problems with Serial Interupt routines in ADA on MSDOS tmoran
  -- strict thread matches above, loose matches on Subject: below --
1997-05-20  0:00 Lee Cookk

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