Google
 

Trailing-Edge - PDP-10 Archives - BB-FB51A-RM - sna-ai/sources/saidlf.b36
There are no other files named saidlf.b36 in the archive.
%title 'SNA GATEWAY ACCESS DECNET LINK FUNCTIONS'

module SAIDLF (ident = 'Version 1.0') =
begin

! Copyright (c) 1985 by
! DIGITAL EQUIPMENT CORPORATION, Maynard, Massachusetts
!
! This software is furnished under a license and may be used and  copied
! only  in  accordance  with  the  terms  of  such  license and with the
! inclusion of the above copyright notice.  This software or  any  other
! copies  thereof may not be provided or otherwise made available to any
! other person.  No title to and ownership of  the  software  is  hereby
! transferred.
!
! The information in this software is subject to change  without  notice
! and  should  not  be  construed  as  a commitment by Digital Equipment
! Corporation.
!
! Digital assumes no responsibility for the use or  reliability  of  its
! software on equipment which is not supplied by Digital.


!++
! FACILITY:
!
!	SNA Gateway Access Module
!
! ABSTRACT:
!
!       The module contains routines to handle various functions related to
!       DECnet logical link activities native to the TOPS-20 systems.
!
! ENVIRONMENT:
!
!	TOPS-20 Operating Systems, user interface.
!
! AUTHOR:	Vicki Gary, CREATION DATE: March 17, 1984
!
! MODIFIED BY:
!
! 	, : Version
! 01	-
!--
!
! TABLE OF CONTENTS
!

!
! INCLUDE FILES
!

library 'MONSYM';                       ! Monitor symbols
library 'SNACOM';                       ! SNA Gateway Access Common symbols
require 'JSYS';                         ! JSYS declarations

!
! MACROS
!

macro RETURN_ERROR (ERROR) =            ! Macro to set error code for 
    begin                               ! port status block
    PORT[PCB_STATE] = AS_ABD;
    PORT[PCB_ERROR] = ERROR;

    return;
    end %;

!
! FORWARD REFERANCES
!

forward routine
       GAL$TERMINATE;

!
! EXTERNAL REFERENCES
!

external routine                        ! Gateway Access DECnet functions
    GAD$ABORT_LINK,
    GAD$DISCONNECT_LINK,
    GAD$RECEIVE_DATA,
    GAD$RECEIVE_INTERRUPT,
    GAD$LINK_STATUS,
    GAD$PROTOCOL_TYPE;

external routine                        ! Gateway Access Protocol I/O
    GAP$I_BINDDATA,
    GAP$I_DATA,
    GAP$I_FLUSH_BUF,
    GAP$I_RECON_PEND,
    GAP$I_PROTOCOL_TYPE;
%routine ('GAL$CONFIRM_VERSION', JFN) =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Function reads version numbers supplied by the Gateway Module,
!       verifies the compatibility of the Gateway Access Module and the
!       Gateway Module. If the two are compatible, according to the
!       verification of the Gateway Access Module, then it sends its
!       own version numbers back to the Gateway Module, otherwise, it
!       sends a reject code.
!
! FORMAL PARAMETERS:
!
!	JFN             DECnet logical link JFN to the Gateway Module.
!
! IMPLICIT INPUTS:
!
!	none
!
! IMPLICIT OUTPUTS:
!
!	none
!
! COMPLETION CODES:
!
!	none
!
! SIDE EFFECTS:
!
!	If the Gateway Access Module reject the version numbers supplied
!       by the Gateway Module, the Gateway Module terminates the link
!       between the two.
!
!--

   begin

        local
        TMPBUF,
        POINTER;

        POINTER = ch$ptr (TMPBUF,,8);
         return jsys_mtopr (.JFN, $mocc, .POINTER, 3);

   end;
%routine ('GAL$RECEIVE_DATA', PORT: ref PORT_CONTROL_BLOCK) : novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Function reads data from the DECnet logical link, determines the type,
!       buffers them or takes actions defined by the state machine.
!
! FORMAL PARAMETERS:
!
!	PORT            The port data base.
!
! IMPLICIT INPUTS:
!
!	none
!
! IMPLICIT OUTPUTS:
!
!	none
!
! COMPLETION CODES:
!
!	none
!
! SIDE EFFECTS:
!
!	Actions are taken immediately, when the type of the received data
!       packets are determined.
!
!--

    begin

    local
        POINTER,
        TYPE,
        DATA_BASE: ref USER_DATA_BASE;

    POINTER = ch$ptr (.PORT[PCB_INPUT_BUFFER],,8);
    ch$fill (0, IO_BUFFER_SIZE, .POINTER);
    DATA_BASE = .PORT[PCB_DATA_BASE];

    ! If the next packet to be read from the DECnet link is a data packet
    ! then check to find out if user is ready to receive it, i.e. the
    ! buffer is empty in the port data base. If the port data base buffer
    ! is empty, then read it and proceed to the following packet; otherwise
    ! ignore everything else and return.

    if .PORT[PCB_DATA]
    then begin
         if not .DATA_BASE[UDB_DATA_AVAILABLE] ! Is user ready to receive ?
         then begin                     ! Yes, then read
              local COUNT;

              COUNT = IO_BUFFER_SIZE;
              if not GAD$RECEIVE_DATA (.PORT[PCB_JFN], COUNT, .POINTER)
              then RETURN_ERROR (AE_NCM); ! No communication error
              GAP$I_DATA (.PORT, .POINTER, .COUNT);
              PORT[PCB_DATA] = $FALSE;
              end;

         return;
         end;

    ! If user is ready to receive any type of data, then proceed normally

    if not .DATA_BASE[UDB_DATA_AVAILABLE]
    then begin
         local COUNT;

         COUNT = IO_BUFFER_SIZE;
         if not GAD$RECEIVE_DATA (.PORT[PCB_JFN], COUNT, .POINTER)
         then RETURN_ERROR (AE_NCM);
         GAP$I_PROTOCOL_TYPE (.PORT, .POINTER, .COUNT);

         return;
         end;

    ! If the user is not quite ready, then check for the type of data
    ! coming in. If the message does not require buffering then proceed,
    ! otherwise flag and wait for next time.

    if not GAD$PROTOCOL_TYPE (.PORT[PCB_JFN], TYPE)
    then return;

    if .TYPE eql AP_NORMAL_DATA         ! If data packet then set
    then PORT[PCB_DATA] = $TRUE         ! flag and wait for next time
    else begin                          ! Otherwise read entire packet
         local COUNT;

         COUNT = IO_BUFFER_SIZE;        ! Read in the rest of the message
         if not GAD$RECEIVE_DATA (.PORT[PCB_JFN], COUNT, .POINTER)
         then RETURN_ERROR (AE_NCM);

         selectone .TYPE of
             set

        [AP_BINDDATA]:
            (GAP$I_BINDDATA (.PORT, .POINTER, (.COUNT)));

       	[AP_FLUSH_BUF]:               ! 6
	    (GAP$I_FLUSH_BUF (.PORT));

	[AP_RECON_PEND]:              ! 7
	    (GAP$I_RECON_PEND (.PORT, .POINTER));

             tes;
         end;

    end;                                ! End of GAL$RECEIVE_DATA
%routine ('GAL$RECEIVE_INTERRUPT', PORT: ref PORT_CONTROL_BLOCK) : novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Function reads data from the DECnet logical link, determines the type,
!       buffers them or takes actions defined by the state machine.
!
! FORMAL PARAMETERS:
!
!	PORT            The port data base.
!
! IMPLICIT INPUTS:
!
!	none
!
! IMPLICIT OUTPUTS:
!
!	none
!
! COMPLETION CODES:
!
!	none
!
! SIDE EFFECTS:
!
!	Actions are taken immediately, when the type of the received data
!       packets are determined.
!
!--

    begin

    local
        POINTER,
        COUNT,
        HEAD: ref RING_ENTRY,
        DATA_BASE: ref USER_DATA_BASE;

    DATA_BASE = .PORT[PCB_DATA_BASE];
    HEAD = .PORT[PCB_INHEAD_BUFFER];

    COUNT = INT_BUFFER_SIZE;

    POINTER = ch$ptr (HEAD[DATA_BUFFER],,8);

    if .HEAD[IN_USE_FLAG] eql 1
    then RETURN_ERROR (AE_EDO);

    if not GAD$RECEIVE_INTERRUPT (.PORT[PCB_JFN], COUNT, .POINTER)
    then RETURN_ERROR (AE_NCM);                ! No communication error

    DATA_BASE[UDB_INTERRUPT_AVAILABLE] = $TRUE;
    HEAD[DATA_LENGTH] = .COUNT;
    HEAD[IN_USE_FLAG] = 1;
    PORT[PCB_INTCNT] = .PORT[PCB_INTCNT] + 1;
    PORT[PCB_INHEAD_BUFFER] = .HEAD[NEXT_RING_PTR];

    return;
         
    end;                                ! End of GAL$RECEIVE_INTERRUPT
%global_routine ('GAL$LINK_SERVICE', PORT: ref PORT_CONTROL_BLOCK) : novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Function service DECnet logical link for a particular port
!
! FORMAL PARAMETERS:
!
!	PORT            The port data base.
!
! IMPLICIT INPUTS:
!
!	none
!
! IMPLICIT OUTPUTS:
!
!	none
!
! COMPLETION CODES:
!
!	none
!
! SIDE EFFECTS:
!
!	none
!
!--

    begin

    local
        POINTER,
        COUNT,
        ERROR,
        SENSE,
        STATUS,
        DATA_BASE: ref USER_DATA_BASE;

    POINTER = ch$ptr (.PORT[PCB_INPUT_BUFFER],,8); ! Get pointer to link buffer
    ch$fill (0, IO_BUFFER_SIZE, .POINTER);
    ERROR = $FALSE;                     ! Assume no error

    DATA_BASE = .PORT[PCB_DATA_BASE];   ! Get user data base address

    ! Check the status of the logical link.

    GAD$LINK_STATUS (.PORT[PCB_JFN], STATUS);

    ! If the link has been aborted, save the optional data if any
    ! for the user to read later

    if (.STATUS<$(mo_abt)> or .STATUS<$(mo_syn)>) 
    then begin

         local
         TMP,
         LEN,
         JFN,
         PTR;

         PTR = ch$ptr (DATA_BASE[UDB_ABORT_DATA],,8);
         JFN = .PORT[PCB_JFN];
         jsys_mtopr (.JFN, $morls; ,, TMP);
         jsys_mtopr (.JFN, $morda, .PTR; ,,, LEN);
         DATA_BASE[UDB_ABORT_LENGTH] = .LEN;
         DATA_BASE[UDB_ABORT_STATUS] = .TMP;

         end;                                            

    ! If the port was ABORTED, or in ERROR state, then it is normal that
    ! the DECnet link does not exist any more, so return normally.
    ! Otherwise, check for error code in the right half of the status word.

    if begin
       selectone .PORT[PCB_STATE] of
           set
           [AS_ABD,                     ! ABORTED
            AS_ABG,                     ! ABORTING
            AS_ERR]:                    ! ERROR
               $TRUE;

           [otherwise]:
               $FALSE;
           tes
       end
    then begin
         if .STATUS<$(mo_abt)> and .STATUS<$(mo_lwc)>
         then return
         else ERROR = $TRUE;
         end;

    ! Return error if the logical link is aborted or closed without user's
    ! consent or knowledge

    if (.STATUS<$(mo_abt)> or .STATUS<$(mo_syn)>) and not .ERROR
    then RETURN_ERROR (AE_NCM);

    ! If interrupt available on the logical link then process interrupt.
    ! If the message type is not expected, then return error.

    if .STATUS<$(mo_int)>
    then GAL$RECEIVE_INTERRUPT (.PORT);

    ! If the data available on the logical link then process data

    if .STATUS<$(mo_eom)>
    then GAL$RECEIVE_DATA (.PORT);

    if (not jsys_sibe (.PORT[PCB_JFN]; , COUNT))
    and (.COUNT gtr 0)
    then GAL$RECEIVE_DATA (.PORT);

    ! If the port state and the link state is not consistent,
    ! (i.e., if the port state is changed to ERROR because of bad data of
    ! bad link status, or if the port state is already CLEARED or ERROR but
    ! the link is not shutdown) then close it.

    SENSE = 0;                                         

    if ((.PORT[PCB_STATE] eql AS_ABD) and not .ERROR) or .ERROR
    then if not GAL$TERMINATE (.PORT[PCB_JFN], .SENSE, AR_UND)
         then GAD$ABORT_LINK (.PORT[PCB_JFN]);

    return;
    end;                                ! End of GAL$LINK_SERVICE
%global_routine ('GAL$TERMINATE', JFN, SENSE, REASON)  =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Assemble outgoing clear protocol message
!
!	MSG: /REASON/SENSE/
!
! FORMAL PARAMETERS:
!
!      SENSE    A 4-byte IBM sense code.
!      REASON   Reason for aborting the port.
!      
!
! IMPLICIT INPUTS:
!
!	none
!
! IMPLICIT OUTPUTS:
!
!	none
!
! COMPLETION CODES:
!
!	none
!
! SIDE EFFECTS:
!
!	none
!
!--

    begin

    local
	LENGTH,
	BASE,
        BUF: block [2],
	POINTER;

    BASE = POINTER = ch$ptr (BUF,,8);

    if (..REASON) neq 0
    then
    ch$move (1, ch$ptr (.REASON,,8), .POINTER)
    else
    ch$wchar_a (0, POINTER);

    if (..SENSE) neq 0
    then
    ch$move (4, ch$ptr (.SENSE,,8), .POINTER)
    else
    ch$wchar_a (0, POINTER);

    ! Get the length of protocol message

    LENGTH = ch$diff (.POINTER, .BASE);

    return     jsys_mtopr (.JFN, $moclz, .POINTER, .LENGTH);

    end;                                ! End of GAL$TERMINATE
%global_routine ('GAL$REJECT', JFN, SENSE, REASON) : novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Assemble outgoing clear protocol message
!
!	MSG: /REASON/SENSE/
!
! FORMAL PARAMETERS:
!
!       JFN         Port number
!       SENSE       4-byte IBM sense code
!       REASON      Reason for the reject
!
! IMPLICIT INPUTS:
!
!	none
!
! IMPLICIT OUTPUTS:
!
!	none
!
! COMPLETION CODES:
!
!	none
!
! SIDE EFFECTS:
!
!	none
!
!--

    begin

    local
	LENGTH,
	BASE,
        BUFFER :block [2],
	POINTER;

    BASE = POINTER = ch$ptr (.BUFFER,,8);

    if (..REASON) neq 0
    then
    ch$move (1, ch$ptr (.REASON,,8), .POINTER)
    else
    ch$wchar_a (0, POINTER);

    if (..SENSE) neq 0
    then
    ch$move (4, ch$ptr (.SENSE,,8), .POINTER)
    else
    ch$wchar_a (0, POINTER);

    ! Get the length of protocol message

    LENGTH = ch$diff (.POINTER, .BASE);

    jsys_mtopr (.JFN, $moclz, .POINTER, .LENGTH);

    return;
    end;                                ! End of GAL$REJECT
%global_routine ('GAL$INTERRUPT', ARGBLK: ref ARGUMENT_BLOCK, BUFFER, BUFLEN) : novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Assemble outgoing interrupt message
!
!	MSG: /SEQNUM/RH/DATA/
!
! FORMAL PARAMETERS:
!
!	ARGBLK          Argument block contains fields to be assembled.
!       BUFFER          Address of buffer to store the protocol message.
!       BUFLEN          Length of the protocol message to be returned.
!
! IMPLICIT INPUTS:
!
!	none
!
! IMPLICIT OUTPUTS:
!
!	none
!
! COMPLETION CODES:
!
!	none
!
! SIDE EFFECTS:
!
!	none
!
!--

    begin

    local
        BASE,
        LENGTH,
        POINTER;

    POINTER = BASE = ch$ptr (.BUFFER,,8);
    
    ch$wchar_a (0, POINTER);
    
    ! Put in the Sequence (2-byte) number
    
    ch$move (2, ch$ptr (.ARGBLK[TRA_SEQ_NUMBER],,8), .POINTER);

    POINTER = ch$move (3, ch$ptr (.ARGBLK[TRA_RH],,8), .POINTER);

!    ch$move (.ARGBLK[TRA_DATA_LENGTH], .ARGBLK[TRA_DATA], .POINTER);

    ! Assemble data. This section is non-transportable BLISS code


    if (LENGTH = .ARGBLK[TRA_DATA_LENGTH]) gtr 0
    then jsys_sin (.ARGBLK[TRA_DATA_POINTER], .POINTER, -.LENGTH; ARGBLK[TRA_DATA_POINTER], POINTER);

    ! Get the length of protocol message

    LENGTH = ch$diff (.POINTER, .BASE);


    return;
    end;                                ! End of GAL$INTERRUPT
end                                   ! End of Module XGADLF
eludom
! Local Modes:
! Mode:BLISS
! Auto Save Mode:2
! Comment Column:40
! Comment Rounding:+1
! End: