Google
 

Trailing-Edge - PDP-10 Archives - BB-KL11L-BM_1990 - t20src/mxnt20.r36
There are 11 other files named mxnt20.r36 in the archive. Click here to see a list.
!	COPYRIGHT (c) DIGITAL EQUIPMENT CORPORATION 1985, 1989.
!	ALL RIGHTS RESERVED.
!
!	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 THAT IS NOT SUPPLIED BY DIGITAL.
!++
! Facility: LSG DECnet Network Management
!
! Abstract: This file contains definitions that are specific to TOPS-20.
!
! Environment: Bliss-36, TOPS20
!
! Author: Steven M. Jenness, Creation date: 21-Oct-80
!
!--
!
! Other requirements for TOPS20
!

switches list (norequire);		! Suppress monitor symbol listing
library 'MONSYM';			! Monitor symbols
switches list (require);
library 'MXJLNK';			! JSYS linkage definitions
%title 'NMUT20 - Network Management Utilities TOPS-20 Definitions'
%sbttl 'Definitions For 36 Bit Instructions'

literal
       HRRI = %O'541',			! Half right to right immediate
       HRLI = %O'505',			! Half right to left immediate
       EXCH = %O'250',			! Exch register and memory
       SETOM = %O'476',			! Set memory to all ones
       SETZM = %O'402',			! Set memory to all zeros
       AOSE = %O'352',			! Add one to memory, skip if eql 0
       SOSLE = %O'373',                 ! Subtract one from memory, skip leq 0
       PUSH = %O'261',			! Push value onto stack
       POP = %O'262',			! Pop value from stack
       PUSHJ = %O'260',			! Call routine, save return on stack
       ADJSP = %O'105',			! Adjust stack pointer
       MOVE = %O'200',                  ! Load value into register
       MOVEI = %O'201',			! Load effective address into register
       MOVEM = %O'202',                 ! Store register contents into memory
       BLT = %O'251';			! Transfer memory block

literal
       MEMSIZE = %O'121',               ! Location containing first free word
					!  in memory.
       CONTEXT_SIZE = %O'20';		! Number of fullwords in a task's
					!  context (all the registers).

field STACK_POINTER_FIELDS =
    set
    STACK_SIZE = [0, 18, 18, 1],	! Number of words left in stack
    STACK_ADDRESS = [0, 0, 18, 0]	! Address of current word in stack
    tes;
%sbttl 'Halt program Macro'

! macro: STOP_PROGRAM
!
! Function - This macro halts the program
!
! Parameters - None

macro
    STOP_PROGRAM =

    begin
    local
         TASK: ref TASK_BLOCK;

    external routine NMLDIE;

    TASK = CURRENT_TASK;
    NMLDIE ( .TASK [TB_ERROR_PC], ch$ptr( TASK [TB_ERROR_BUFFER]));

    end %;
%sbttl 'Semaphore LOCK/UNLOCK Macros'

! macro: LOCK
!
! Function - This macro attempts a semaphore lock.  If the lock
!            attempt is successful, a "true" value is returned.
!
! Parameters -
!
!    SEMA_ADR    Address of a SEMAPHORE_BLOCK


macro
     LOCK (SEMA_ADDR) =
         begin
         builtin MACHSKIP;
         bind SEMBLK = SEMA_ADDR : SEMAPHORE_BLOCK;

         MACHSKIP (AOSE, 0, SEMBLK [SEMAPHORE])
         end %;


! macro: UNLOCK
!
! Function - This macro unlocks a semaphore that has been locked
!            with a LOCK macro call.
!
! Parameters -
!
!    SEMA_ADDR    Address of a SEMAPHORE_BLOCK.


macro
     UNLOCK (SEMA_ADDR) =
         begin
         builtin MACHOP;
         bind SEMBLK = SEMA_ADDR : SEMAPHORE_BLOCK;

         MACHOP (SETOM, 0, SEMBLK [SEMAPHORE]);
         end %;
%sbttl 'Task Scheduling Macros'

! macro: CONTEXT_SWITCH
!
! Function - This macro swaps the current task with the
!            specified future task.
!
! Parameters -
!
!    NEW_TASK    Address of the new task's task block


macro
     CONTEXT_SWITCH (NEW_TASK) =
         begin
         external routine SS_SWITCH;	! System specific routine

         SS_SWITCH (NEW_TASK);
         end %;


! macro: CURRENT_TASK
!
! Function - This macro returns the address of the
!            current task's task block.
!
! Return value -
!
!    Address the current task's task block.


macro
     CURRENT_TASK =
         begin
         external CURTSK;		! Cell containing current task

         .CURTSK
         end %;


! macro: TASK_INITIALIZE
!
! Function - This macro initializes a task's task block.
!            Specifically it sets up the stack and the
!            starting address so that the task will swap
!            context properly the first time that it
!            is scheduled.
!
! Parameters -
!
!     TK_BLOCK    The task's task block address
!     STACK_SIZE  Number of fullwords for the task's stack


macro
     TASK_INITIALIZE (TK_BLOCK, STACK_SIZE) =
         begin
         external routine SS_TINIT;	! System specific routine

         SS_TINIT (TK_BLOCK, STACK_SIZE);
         end %;
%sbttl 'Interrupt Macros'

! Macro - INTERRUPT_DATA_BASE
!
! Function - This macro defines the interrupt vector tables
!            and any other miscellaneous variables that are
!            required by the interrupt system.


macro
     INTERRUPT_DATA_BASE =
         literal
             INTERRUPT_STACK_SIZE = 100; ! Number of words in a interrupt stack

         global
             VECTAB : vector [36],      ! Routine to call for each channel
             DATTAB : vector [36],      ! Data to pass to interrupt routine
             LEV1PC,                    ! PC storage for level 1 interrupts
             LEV2PC,                    ! PC storage for level 2 interrupts
             LEV3PC,                    ! PC storage for level 3 interrupts
             LEVTAB : vector [3]        ! Vector for PC storage for each level
                      preset ([0] = LEV1PC, [1] = LEV2PC, [2] = LEV3PC),
             LEV1CHN,                   ! Channel currently active on channel 1
             LEV2CHN,                   ! Channel currently active on channel 2
             LEV3CHN;                   ! Channel currently active on channel 3

         !
         ! Stack and pointer for interrupt level 1
         !

         own
            STACK1 : vector [INTERRUPT_STACK_SIZE],
            LEV1STK : block [1] field (STACK_POINTER_FIELDS)
                      preset ([STACK_SIZE] = -INTERRUPT_STACK_SIZE,
                              [STACK_ADDRESS] = STACK1);

         !
         ! Stack and pointer for interrupt level 2
         !

         own
            STACK2 : vector [INTERRUPT_STACK_SIZE],
            LEV2STK : block [1] field (STACK_POINTER_FIELDS)
                      preset ([STACK_SIZE] = -INTERRUPT_STACK_SIZE,
                              [STACK_ADDRESS] = STACK2);

         !
         ! Stack and pointer for interrupt level 3
         !

         own
            STACK3 : vector [INTERRUPT_STACK_SIZE],
            LEV3STK : block [1] field (STACK_POINTER_FIELDS)
                      preset ([STACK_SIZE] = -INTERRUPT_STACK_SIZE,
                              [STACK_ADDRESS] = STACK3);

         !
         ! Define channels on each interrupt level.
         !

         macro
              LEVEL1_INTERRUPT_SET =
                  $ICAOV, $ICFOV, $ICPOV, $ICILI,
                  $ICIRD, $ICIWR, $ICMSE
                  %quote %;

         macro
              LEVEL2_INTERRUPT_SET =
                  0, 1, 2, 3, 4, 5, 23, 24, 25, 26, 27,
                  28, 29, 30, 31, 32, 33, 34, 35
                  %quote %;

         !
         ! Vector routines for each interrupt channel.
         !

         macro
              $$INT_FORWARDS [CHNNO] =
                  %name ('CSRV', CHNNO) : novalue %quote %;

         macro
              LEVEL1_VECTOR_ROUTINES [] =
                  forward routine
                          $$INT_FORWARDS (%remaining);
                          $$LEV1_ROUTINE (%remaining);
                  %quote %;

         macro
              $$LEV1_ROUTINE [CHNNO] =
                  routine %name ('CSRV', CHNNO) : novalue =
                      begin
                      external CRSACS,CRSPC;
                      DECLARE_JSYS (DEBRK);
                      literal P = %O'17';
                      builtin MACHOP;

                      MACHOP (EXCH, 0, CRSACS);
                      MACHOP (BLT, 0, CRSACS+17);
                      MACHOP (MOVE, 0, CRSACS);
                      MACHOP (EXCH, P, LEV1STK);
                      MACHOP (PUSH, P, 1);
                      MACHOP (MOVE, 1, LEV1PC);
                      MACHOP (MOVEM, 1, CRSPC);
                      MACHOP (MOVEI, 1, CHNNO);
                      MACHOP (MOVEM, 1, LEV1CHN);
                      MACHOP (PUSHJ, P, VECTAB + CHNNO, 0, 1);
                      MACHOP (SETOM,, LEV1CHN);
                      MACHOP (POP, P, 1);
                      MACHOP (EXCH, P, LEV1STK);
                      $$DEBRK ();
                      end;
                  %quote %;

         macro
              LEV1INT [CHNNO] =
                  [CHNNO, CT_LEVEL] = 1,
                  [CHNNO, CT_VECTOR] = %name ('CSRV', CHNNO)
                  %quote %;

         macro
              LEVEL2_VECTOR_ROUTINES [] =
                  forward routine
                          $$INT_FORWARDS (%remaining);
                          $$LEV2_ROUTINE (%remaining);
                  %quote %;

         macro
              $$LEV2_ROUTINE [CHNNO] =
                  routine %name ('CSRV', CHNNO) : novalue =
                      begin
                      DECLARE_JSYS (DEBRK)
                      literal P = %O'17';
                      builtin MACHOP;

                      MACHOP (EXCH, P, LEV2STK);
                      MACHOP (PUSH, P, 1);
                      MACHOP (PUSH, P, DATTAB + CHNNO);
                      MACHOP (MOVEI, 1, CHNNO);
                      MACHOP (MOVEM, 1, LEV2CHN);
                      MACHOP (PUSHJ, P, VECTAB + CHNNO, 0, 1);
                      MACHOP (SETOM,, LEV2CHN);
                      MACHOP (POP, P, 1);
                      MACHOP (POP, P, 1);
                      MACHOP (EXCH, P, LEV2STK);
                      $$DEBRK ();
                      end
                  %quote %;

         macro
              LEV2INT [CHNNO] =
                  [CHNNO, CT_LEVEL] = 2,
                  [CHNNO, CT_VECTOR] = %name ('CSRV', CHNNO)
                  %quote %;

         field CHANNEL_BLOCK_FIELDS =
             set
             CT_LEVEL = [0, 18, 18, 0],	! Level of interrupt
             CT_VECTOR = [0, 0, 18, 0]	! Interrupt vector
             tes;

         LEVEL1_VECTOR_ROUTINES (LEVEL1_INTERRUPT_SET);
         LEVEL2_VECTOR_ROUTINES (LEVEL2_INTERRUPT_SET);

         !
         ! Interrupt channel table
         !

         global
               CHNTAB : blockvector [36, 1] field (CHANNEL_BLOCK_FIELDS)
                        preset (LEV1INT (LEVEL1_INTERRUPT_SET),
                                LEV2INT (LEVEL2_INTERRUPT_SET));
         %;
%sbttl 'Interrupt Routine Linkages'

macro
     INTERRUPT_LINKAGE =
         pushj : linkage_regs (15,13,1)
                 preserve (0,2,3,4,5,6,7,8,9,10,11,12,14)
         %;

macro
     TIMER_INTERRUPT_ROUTINE = 
         : TIMER_INTERRUPT_LINKAGE %,

     NETWORK_INTERRUPT_ROUTINE =
         (LINK_INFO : ref LINK_INFO_BLOCK) : NETWORK_INTERRUPT_LINKAGE %,

     NI_RECEIVER_INTERRUPT_ROUTINE =
         : NI_RECEIVER_INTERRUPT_LINKAGE %,

     IPCF_INTERRUPT_ROUTINE =
         : IPCF_INTERRUPT_LINKAGE %;

linkage
       VANILLA_INTERRUPT_LINKAGE = INTERRUPT_LINKAGE,
       TIMER_INTERRUPT_LINKAGE = INTERRUPT_LINKAGE,
       NETWORK_INTERRUPT_LINKAGE = INTERRUPT_LINKAGE,
       NI_RECEIVER_INTERRUPT_LINKAGE = INTERRUPT_LINKAGE,
       IPCF_INTERRUPT_LINKAGE = INTERRUPT_LINKAGE;

macro
     INTERRUPT_ROUTINE [] =
         (%remaining) : VANILLA_INTERRUPT_LINKAGE
         %warn('Best to Use ???_INTERRUPT_ROUTINE') %;
%sbttl 'Interrupt System Operation Macros'

! Macro - CLEAR_INTERRUPT_SYSTEM
!
! Function - This macro clears the interrupt system.  All
!            interrupts disabled.  Set all interrupt channels
!            to not active (-1);


macro
     CLEAR_INTERRUPT_SYSTEM =
         begin
         DECLARE_JSYS (CIS)

         $$CIS ();
         LEV1CHN = -1;
         LEV2CHN = -1;
         LEV3CHN = -1;
         end %;


! Macro - INITIALIZE_INTERRUPT_SYSTEM
!
! Function - This macro setups any initial values needed in
!            the interrupt data base and informs the operating
!            system about the interrupt vector tables.


macro
     INITIALIZE_INTERRUPT_SYSTEM =
         begin
         DECLARE_JSYS (SIR, EIR)
         local T2;
	 external INTNST;
                        
	 INTNST = 0;
         T2 <18, 18, 0> = LEVTAB;       ! Level table vector
         T2 <0, 18, 0> = CHNTAB;        ! Channgel table vector
         $$SIR ($FHSLF, .T2);		! Set vector tables in PSB
         $$EIR ($FHSLF);                ! Enable PISYS system
         end %;


! Macro - ACTIVATE_INTERRUPT
!
! Function - This macro enables a specific interrupt.
!
! Parameters -
!
!    CHANNEL    Channel number to activate


macro
     ACTIVATE_INTERRUPT (CHANNEL) =
         begin
         DECLARE_JSYS (AIC)
         local T2;

         T2 = (1 ^ (35 - CHANNEL));
         $$AIC ($FHSLF, .T2);
         end %;


! Macro - DEACTIVATE_INTERRUPT
!
! Function - This macro disables a specific interrupt.  
!
! Parameters -
!
!    CHANNEL    Channel number to deactivate


macro
     DEACTIVATE_INTERRUPT (CHANNEL) =
         begin
         DECLARE_JSYS (DIC)
         local T2;

         T2 = (1 ^ (35 - CHANNEL));
         $$DIC ($FHSLF, .T2);
         end %;


! Macro - INTERRUPT_ON
!
! Function - This macro enables the interrupt system.  If nested
!            INTERRUPT_OFF calls have been made, this call only
!            decrements the nesting count.


macro
     INTERRUPT_ON =
         begin
         DECLARE_JSYS (DIR, EIR)
         builtin MACHSKIP;
         external INTNST;		! Interrupt nesting count

         IF .intnst GTR 0
         THEN
             if MACHSKIP (SOSLE,, INTNST)
             then begin
                  INTNST = 0;
                  $$EIR ($FHSLF);           ! Enable interrupt system
                  end;
         end %;


! Macro - INTERRUPT_OFF
!
! Function - This macro turns the interrupt system off.  It
!            also increments the nesting count of times that
!            it has been turned off.


macro
     INTERRUPT_OFF =
         begin
         DECLARE_JSYS (DIR)
         external INTNST;

         IF .intnst LEQ 0
         THEN
             $$DIR ($FHSLF);		! Turn interrupt system off
         INTNST = .INTNST + 1;          ! Increment nesting count
         end %;


! Macro - ALLOCATE_INTERRUPT_CHANNEL
!
! Function - This macro searchs the interrupt channel table
!            for a free channel.
!
! Paramaters -
!
!    I_ROUTINE    Routine to call when interrupt occurs on channel
!    I_DATA       Data to pass to interrupt routine when called
!
! Return value -
!
!        -1    No channel available
!        >0    Channel number


macro
     ALLOCATE_INTERRUPT_CHANNEL (I_ROUTINE, I_DATA) =
         begin
         local RESULT;
         external VECTAB : vector [36],
                  DATTAB : vector [36];

         RESULT = -1;
         incr INDEX from 0 to 5
         do if .VECTAB [.INDEX] eql 0
            then begin
                 RESULT = .INDEX;
                 exitloop;
                 end;

         if .RESULT lss 0
         then incr INDEX from 23 to 35
              do if .VECTAB [.INDEX] eql 0
                 then begin
                      RESULT = .INDEX;
                      exitloop;
                      end;

         %if not %null (I_ROUTINE)
         %then if .RESULT neq -1
               then VECTAB [.RESULT] = I_ROUTINE; %fi

         %if not %null (I_DATA)
         %then if .RESULT neq -1
               then DATTAB [.RESULT] = I_DATA; %fi

         .RESULT
         end %;


! Macro - RELEASE_INTERRUPT_CHANNEL
!
! Function - This macro flags that an interrupt channel is
!            now available for use
!
! Parameters -
!
!    CHANNEL    Channel number to release


macro
     RELEASE_INTERRUPT_CHANNEL (CHANNEL) =
         begin
         external VECTAB : vector [36];

         VECTAB [CHANNEL] = 0;
         end %;


! Macro - ARITHMETIC_OVERFLOW
!
! Function - This macro enables interrupts on arithmetic errors.
!            The routine specified will be called when an error
!            occurs.
!
! Parameters -
!
!    E_ROUTINE    Address of interrupt service routine
!

macro
     ARITHMETIC_OVERFLOW (E_ROUTINE) =
         begin
         VECTAB [$ICAOV] = E_ROUTINE;
         VECTAB [$ICFOV] = E_ROUTINE;
         ACTIVATE_INTERRUPT ($ICAOV);
         ACTIVATE_INTERRUPT ($ICFOV);
         end %;


! Macro - STACK_OVERFLOW
!
! Function - This macro enables interrupts on push down list
!            overflows. The routine specified will be called
!            when an error occurs.
!
! Parameters -
!
!    E_ROUTINE    Address of interrupt service routine


macro
     STACK_OVERFLOW (E_ROUTINE) =
         begin
         VECTAB [$ICPOV] = E_ROUTINE;
         ACTIVATE_INTERRUPT ($ICPOV);
         end %;


! Macro - ILLEGAL_INSTRUCTION
!
! Function - This macro enables interrupts on illegal instruction
!            traps. The routine specified will be called when an
!           error occurs.
!
! Parameters -
!
!    E_ROUTINE    Address of interrupt service routine


macro
     ILLEGAL_INSTRUCTION (E_ROUTINE) =
         begin
         VECTAB [$ICILI] = E_ROUTINE;
         ACTIVATE_INTERRUPT ($ICILI);
         end %;


! Macro - ILLEGAL_MEMORY_REFERENCE
!
! Function - This macro enables interrupts on illegal memory reads
!            and writes.  The routine specified will be called when
!            an error occurs.
!
! Parameters -
!
!    E_ROUTINE    Address of interrupt service routine


macro
     ILLEGAL_MEMORY_REFERENCE (E_ROUTINE) =
         begin
         VECTAB [$ICIRD] = E_ROUTINE;
         VECTAB [$ICIWR] = E_ROUTINE;
         ACTIVATE_INTERRUPT ($ICIRD);
         ACTIVATE_INTERRUPT ($ICIWR);
         end %;


! Macro - SYSTEM_RESOURCE_FAILURE
!
! Function - This macro enables interrupts on system resource
!            allocation failures.  The routine specified will
!            be called when an error occurs.
!
! Parameters -
!
!    E_ROUTINE    Address of interrupt service routine


macro
     SYSTEM_RESOURCE_FAILURE (E_ROUTINE) =
         begin
         VECTAB [$ICMSE] = E_ROUTINE;
         ACTIVATE_INTERRUPT ($ICMSE);
         end %;
%sbttl 'System Specific Time Interface'

! This set of macros allows transparent manipulation of "time"
! in a particular system.  The macros are defined to read time
! from the operating system, read time with a offset, compare time,
! set and clear interrupts on time.
!
!
! Time block structure
!
!	This structure defines the format needed for a specific
!	system to store a internal time/date value.

literal
       TIME_BLOCK_SIZE = 1,
       TIME_BLOCK_ALLOCATION = 1;

macro
     TIME_BLOCK =
         vector [1] %;


! Macro - TIME_PLUS
!
! Function -	This macro adds the second argument (which is in units of
!		seconds) to the first argument which is a time block.


macro
     TIME_PLUS (TIME, SECONDS) =
         begin
         bind TBLK = TIME : TIME_BLOCK;

         TBLK [0] = .TBLK[0] + SECONDS ^ 18 / (24 * 60 * 60)
         end %;


! Macro - TIME_DIFFERENCE_SECONDS
!
! Function - Compute the difference (in seconds) of two TIME_BLOCKS


macro
     TIME_DIFFERENCE_SECONDS (TIME1, TIME2) =
         begin
         builtin ash;
         bind TBLK1 = TIME1 : TIME_BLOCK,
              TBLK2 = TIME2 : TIME_BLOCK;

         ash (((.TBLK1[0] - .TBLK2[0]) * 24 * 60 * 60 + 1 ^ 17), -18)
         end %;


! Macro - TIME_INTERRUPT_CLEAR
!
! Function - This macro clears all outstanding timer interrupts.


macro
     TIME_INTERRUPT_CLEAR =
         begin
         DECLARE_JSYS (TIMER)
         literal TIME_CHANNEL = 35;
         local T1;

         T1<18,18,0> = $FHSLF;
         T1<0,18,0> = $TIMAL;
         $$TIMER (.T1);
         DEACTIVATE_INTERRUPT (TIME_CHANNEL);
         end %;


! Macro - TIME_INTERRUPT_SET
!
! Function - This macro sets a time interrupt.  It also
!            defines the routine to be called when the
!            interrupt occurs.
!
!            Note that since the interrupt channel is
!            hard coded the time interrupt must be unique.
!
! Parameters -
!
!    TIM_BLK	Address of time block with time in the future for a interrupt
!    TROUTINE	Address of the interrupt service routine


macro
     TIME_INTERRUPT_SET (TIM_BLK, TROUTINE) =
         begin
         DECLARE_JSYS (TIMER, AIC)
         bind TBLK = TIM_BLK : TIME_BLOCK;
         literal TIME_CHANNEL = 35;
         external VECTAB : vector [36];
         local T1;

         T1<18,18,0> = $FHSLF;
         T1<0,18,0> = $TIMDT;
         VECTAB [TIME_CHANNEL] = TROUTINE;
         if $$TIMER (.T1, .TBLK [0], TIME_CHANNEL)
         then ACTIVATE_INTERRUPT (TIME_CHANNEL)
         else if .T1 eql TIMX6
              then TROUTINE ();
         end %;


! Macro - TIME_CURRENT
!
! Function - This macro returns the current time in
!            the host operating systems time format.
!            This is the format needed to set timer
!            interrupts.
!
! Parameters -
!
!    OFFSET    is the number of seconds to add to the actual current time.
!    TIM_BLK   is the address of the time block in which to store
!              the resulting time.


macro
     TIME_CURRENT (OFFSET, TIM_BLK) =
         begin
         DECLARE_JSYS (GTAD)
         bind TBLK = TIM_BLK : TIME_BLOCK;

         $$GTAD (;TBLK [0]);
         TBLK [0] = .TBLK [0] + OFFSET * 3;
         end %;


! Macro - TIME_SET_NULL
!
! Function - This macro sets a time block to a null value.
!            This value is used as a sentinel to check for
!            a valid time value (null/not null).
!
! Parameters -
!
!    TIM_BLK    Address of the time block


macro
     TIME_SET_NULL (TIM_BLK) =
         begin
         bind TBLK = TIM_BLK : TIME_BLOCK;

         TBLK [0] = -1;
         end %;


! Macro - TIME_NOT_NULL
!
! Function - This macro checks to the value in a time block
!            to see if it is not null (see TIME_SET_NULL).
!
! Parameters -
!
!    TIM_BLK    Address of the time block to test


macro
     TIME_NOT_NULL (TIM_BLK) =
         begin
         bind TBLK = TIM_BLK : TIME_BLOCK;

         .TBLK [0] neq -1
         end %;


! Macro - TIME_NULL
!
! Function - This macro checks to the value in a time block
!            to see if it is null (see TIME_SET_NULL).
!
! Parameters -
!
!    TIM_BLK    Address of the time block to test


macro
     TIME_NULL (TIM_BLK) =
         begin
         bind TBLK = TIM_BLK : TIME_BLOCK;

         .TBLK [0] eql -1
         end %;


! Macro - TIME_COPY
!
! Function - This macro copies the time from one time block
!            to another time block.
!
! Parameters -
!
!    TO_BLK     Time block to copy the time to
!    FRM_BLK    Time block to copy the time from


macro
     TIME_COPY (TO_BLK, FRM_BLK) =
         begin
         bind TOBLK = TO_BLK : TIME_BLOCK,
              FRMBLK = FRM_BLK : TIME_BLOCK;

         TOBLK [0] = .FRMBLK [0];
         end %;


! Macro - TIME_TEST
!
! Function - This macro tests the chronological relation of
!            the values in two time blocks.  The test operator
!            is specified as an argument to the macro.  The
!            value returned by this macro is a boolean (true/false)
!            from the test "TB1 TST_FNC TB2" (i.e. TB1 lss TB2).
!
! Parameters -
!
!    TBLK1    The first time block
!    TST_FNC  The test operator (LSS, GTR, EQL,..etc)
!    TBLK2    The second time block


macro
     TIME_TEST (TBLK1, TST_FNC, TBLK2) =
         begin
         bind TIMBLK1 = TBLK1 : TIME_BLOCK,
              TIMBLK2 = TBLK2 : TIME_BLOCK;

         .TIMBLK1 [0] TST_FNC .TIMBLK2 [0] 
         end %;
%sbttl 'Memory Allocation'

! Wait Block Structure
!
!	This defines the WAIT_BLOCK used in timing out waiting for events,
!	specifically those waits implemented by calling NMU$SCHED_WAIT.

$field WAIT_BLOCK_FIELDS =
    set
    WAITING_TASK = [$address],          ! Task block address, to ref semaphore
        $align (fullword)
    WAIT_EVENT = [$address],            ! Address of event block to wait on
        $align (fullword)
    WAIT_TIME = [$sub_block(TIME_BLOCK_SIZE)] ! Time at which to 'wake'
    tes;

literal
       WAIT_BLOCK_SIZE = $field_set_size;

macro
     WAIT_BLOCK = block [WAIT_BLOCK_SIZE] field (WAIT_BLOCK_FIELDS)%;


! Macro - CORE_GET
!
!
! Function - This macro gets a block of memory from the
!            operating system of the specified size.  The
!            address of the block is returned as the value
!            of the macro.
!            
! Parameters -
!
!    BLOCK_SIZE    The number of fullwords to be allocated
!
! Return value -
!
!      0    if no memory can be allocated
!    <>0    address of memory block allocated


macro
     CORE_GET (BLKSIZE) =
         begin
         local BLKADDR;

         BLKADDR = .%O'121';		! Get current .JBFF value
         %O'121' = .%O'121' + BLKSIZE;
         if .%O'121' lss %O'400000'
         then .BLKADDR
         else 0
         end %;
%sbttl 'Process Sleep And Wakeup'

! Macro - PROCESS_SLEEP
!
! Function - This macro puts the current process to
!            sleep for the specified amount of time.
!            The process is not guaranteed to sleep
!            the specified amount.
!
! Parameters -
!
!    TIME    The number of seconds to sleep


macro
     PROCESS_SLEEP (TIME) =
         begin
         DECLARE_JSYS (THIBR)

         $$THIBR (TIME);
         end %;


! Macro - PROCESS_WAKE
!
! Function - This macro wakes up the current process.
!            It may be called at interrupt level to
!            complement the PROCESS_SLEEP function.


macro
     PROCESS_WAKE =
         begin
         DECLARE_JSYS (GJINF, TWAKE)
         local JOB;

         $$GJINF (;,,JOB);
         $$TWAKE (.JOB);
         end %;
%sbttl 'Network Interface Macros'

!
! System specific fields for the LINK_INFO_BLOCK
!

macro
     LINK_SYSTEM_SPECIFIC_FIELDS =
         LINK_FILE = [$string (150)],	! File specification
         LINK_JFN = [$integer],		! JFN for link
         LINK_FORK = [$address]         ! FIB for this link
         %;


! Macro - LOCAL_NODE_NUMBER
!
! Function - This macro returns the local node number.  It
!            puts it into a byte string pointed to by the
!            supplied byte pointer.
!
! Parameters -
!
!    NODE_PTR    is the address of a byte pointer that is
!                updated when done.

%if not $TOPS20
%then
macro
     LOCAL_NODE_NUMBER (NODE_PTR) =
         begin
         DECLARE_JSYS (NODE)
         local NODE_NUMBER;

         $$NODE ($NDGNM, NODE_NUMBER);
         ch$wchar_a (.NODE_NUMBER<0,8,0>, NODE_PTR);
         ch$wchar_a (.NODE_NUMBER<8,8,0>, NODE_PTR);
         end %;
%fi

! Macro - LOCAL_NODE_NAME
!
! Function - This macro returns the local node name in a
!            counted ASCII string.  The node name is written
!            into the string pointed to by the supplied byte
!            pointer and the first byte is the number of characters
!            in the node name.
!
! Parameters -
!
!    NODE_PTR    Address of a byte pointer


%if not $TOPS20
%then
macro
     LOCAL_NODE_NAME (NODE_PTR) =
         begin
         DECLARE_JSYS (NODE)
         local NAME_PTR;

         NAME_PTR = ch$plus (.NODE_PTR, 1);
         $$NODE ($NDGLN, NAME_PTR);
         ch$wchar_a (ch$len (ch$plus (.NODE_PTR, 1)), NODE_PTR);
         end %;
%fi


! Macro - BUILD_LINK_INFO_BLOCK
!
! Function - This macro fills in the system specific
!            portions of the link info block. The source
!            of information that it uses is the connect block
!            passed to NMU$NETWORK_OPEN
!
! Parameters -
!
!    CONN_BLK    Address of connect block
!    LINK_INFO   Address of link info block


%if not $TOPS20
%then
macro
     BUILD_LINK_INFO_BLOCK (CONN_BLK, LINK_INFO) =
         begin
         external routine USER_NAME;
         local FILE_PTR;
         bind LI = LINK_INFO : LINK_INFO_BLOCK,
              CB = CONN_BLK : CONNECT_BLOCK;

         LI [LINK_JFN] = LI [LINK_FORK] = 0;
         FILE_PTR = ch$ptr (LI [LINK_FILE]);
         if .LI [LINK_TYPE] eql SOURCE_LINK
         then begin
!
! Create DCN:HOST-OBJECT
!
              begin
              local NAME_PTR, LENGTH, NODE_ADDRESS;

              NAME_PTR = .CB [CB_HOST];
              NODE_ADDRESS = GETW (NAME_PTR);
              LENGTH = GETB (NAME_PTR);

              if .LENGTH gtr 0
              then $NMU$TEXT (FILE_PTR,
                              14,
                              '%NDCN:%#A-',
                              .LENGTH,
                              .NAME_PTR)
              else $NMU$TEXT (FILE_PTR,
                              14,
                              '%NDCN:%D-',
                              .NODE_ADDRESS);
              end;
!
! Add optional "descriptor" if debugging, i.e., PRIVATE_HOST_LINK is set
!

              if PRIVATE_HOST_LINK
              then $NMU$TEXT (FILE_PTR,
                              18,
                              '%N0-%@',
                              USER_NAME);
!		    	
! Add in object type
!
	      $NMU$TEXT (FILE_PTR,
			 3,
  			 '%N%D',
			 .CB [CB_OBJECT]);

! Add optional task name 
!
              if .CB [CB_TASK_LENGTH] gtr 0
              then $NMU$TEXT (FILE_PTR,
                              17,
                              '%N.%#A',
                              .CB [CB_TASK_LENGTH],
                              .CB [CB_TASK]);

!
! Add optional userid attribute
!
              if .CB [CB_USERID_LENGTH] gtr 0
              then $NMU$TEXT (FILE_PTR,
                              24,
                              '%N;USERID:%#A',
                              .CB [CB_USERID_LENGTH],
                              .CB [CB_USERID]);
!
! Add optional password attribute
!
              if .CB [CB_PASSWORD_LENGTH] gtr 0
              then $NMU$TEXT (FILE_PTR,
                              18,
                              '%N;PASSWORD:%#A',
                              .CB [CB_PASSWORD_LENGTH],
                              .CB [CB_PASSWORD]);
!
! Add optional account attribute
!
              if .CB [CB_ACCOUNT_LENGTH] gtr 0
              then $NMU$TEXT (FILE_PTR,
                              24,
                              '%N;CHARGE:%#A',
                              .CB [CB_ACCOUNT_LENGTH],
                              .CB [CB_ACCOUNT]);
!
! Add optional data attribute
!
              if .CB [CB_DATA_LENGTH] gtr 0
              then begin
                   if ch$size (.CB [CB_DATA]) eql 7
                   then $NMU$TEXT (FILE_PTR,
                                   24,
                                   '%N;DATA:%#A',
                                   .CB [CB_DATA_LENGTH],
                                   .CB [CB_DATA])
                   else $NMU$TEXT (FILE_PTR,
                                   48,
                                   '%N;BDATA:%#B',
                                   -.CB [CB_DATA_LENGTH],
                                   0,
                                   .CB [CB_DATA]);
                   end;
              end
         else begin
!
! Create SRV:OBJECT or SRV:.USERNAMEOBJECT (if debugging)
!
              if  PRIVATE_SERVER_LINK
              then $NMU$TEXT (FILE_PTR,
                              150,
                              '%NSRV:.%@%D',
			      USER_NAME,
			      .CB [CB_OBJECT])
              else $NMU$TEXT (FILE_PTR,
                              150,
                              '%NSRV:%D',
                              .CB [CB_OBJECT]);

!
! Add optional task name (not possible if debugging)
!
              if (.CB [CB_TASK_LENGTH] gtr 0) and (not PRIVATE_SERVER_LINK)
              then $NMU$TEXT (FILE_PTR,
                              17,
                              '%N.%#A',
                              .CB [CB_TASK_LENGTH],
                              .CB [CB_TASK]);
              end;
!
! Make into an ASCIZ string.
!
         ch$wchar_a (0, FILE_PTR);
         end %;
%fi

! Macro - OPEN_FOR_CONNECTION
!
! Function - This macro opens a logical link.  If it is a source
!            link, the connect is sent.  If it is a target link
!            it opens for possible connection.
!
! Parameters -
!
!    LINK_INFO    Address of link info block
!
! Return value -
!
!    $true    Link is setup for connection properly
!    $false   Link setup failed


macro
     OPEN_FOR_CONNECTION (LINK_INFO) =
        begin
        literal
            OPEN_CHANNEL = %o'200000000000';

        DECLARE_JSYS(DIC);
        bind LI = LINK_INFO : LINK_INFO_BLOCK;
        bind FI = LI [LINK_FORK] : REF FORK_INFO_BLOCK;

        external DATTAB : vector [36], VECTAB : vector [36];
        external SUBDCN;
        external routine MX$FORK_CREATE, MX$FORK_RUN;
        local TMO;
        
!
! Create and initialize the subfork
!
        FI = MX$FORK_CREATE(SUBDCN,LI[LINK_EVENT]);

        begin
        bind PG = (.FI[FORK_PAGE] * 512): FORK_DATA_PAGE;
        bind func = pg [SF_FUNCTION];
        bind arg2 = pg [SF_ARGUMENT_2];
        bind arg3 = pg [SF_ARGUMENT_3]: VOLATILE;


        FUNC = SD$OPN;
        ARG2 = ch$ptr(LI[LINK_FILE]);
        ARG3 = 0;

        TMO = (if .LI[LINK_TYPE] EQL SOURCE_LINK
               then
                   .ntimo
               else
                   0);

        if not (TMO = MX$FORK_RUN(.FI,.TMO))
        then
            $$DIC(.FI[FORK_HANDLE],OPEN_CHANNEL);

        LI[LINK_JFN] = .ARG3;
        $trace('JFN = %O',.LI[LINK_JFN]);
        .TMO
        end
        end %;


! Macro - ACCEPT_NETWORK_CONNECT
!
! Function - This macro accepts a connect on a target link.  It
!            specifies optional data that is sent in response
!            to the connect.  It blocks the calling task until
!            the connection is confirmed or broken.
!
! Parameters -
!
!    LINK_INFO    Address of link info block
!    DATA_LEN     Length (in bytes) of optional data
!    DATA_PTR     Pointer to optional data


macro
     ACCEPT_NETWORK_CONNECT (LINK_INFO, DATA_LEN, DATA_PTR) =
         begin
         DECLARE_JSYS (MTOPR,DISMS)
         bind LI = LINK_INFO : LINK_INFO_BLOCK;
         local WAITING;

         $$MTOPR (.LI [LINK_JFN], $MOCC, DATA_PTR, DATA_LEN);
         WAITING = $TRUE;
         while .WAITING
         do begin
            READ_LINK_STATUS (LINK_INFO);
            if (WAITING = not ((LINK_CONNECTED (LINK_INFO)) or
                               (LINK_DISCONNECTED (LINK_INFO))))
            then $$DISMS (1);           ! Wait a millisecond
            end;
         end %;

! Macro - REJECT_NETWORK_CONNECT
!
! Function - This macro rejects a connect on a target logical
!            link.  It passes the reject reason and any optional
!            data back to the connecting task.
!
! Parameters -
!
!    LINK_INFO    Address of link info block
!    REASON       DECnet reject reason code
!    DATA_LEN     Number of bytes in optional data
!    DATA_PTR     Pointer to optional data


macro
     REJECT_NETWORK_CONNECT (LINK_INFO, REASON, DATA_LEN, DATA_PTR) =
         begin
         DECLARE_JSYS (MTOPR)
         bind LI = LINK_INFO : LINK_INFO_BLOCK;
         local RSN;

         RSN<18,18,0> = REASON;
         RSN<0,18,0> = $MOCLZ;
         $$MTOPR (.LI [LINK_JFN], .RSN, DATA_PTR, DATA_LEN);
         end %;

! Macro - LINK_OPEN
!
! Function - This routine checks to see if a logical link is
!            open for connection.
!
! Parameters -
!
!    LINK_INFO    Address of link info block
!
! Return values -
!
!    $true    Source link    If link is connected
!             Target link    If link is waiting for connect confirm
!    $false   otherwise


macro
     LINK_OPEN (LINK_INFO) =
         begin
         bind LI = LINK_INFO : LINK_INFO_BLOCK;

         if .LI [LINK_TYPE] eql SOURCE_LINK
         then (.LI [$sub_field (LINK_STATUS, LSB_CONNECTED)] neq 0)
         else (.LI [$sub_field (LINK_STATUS, LSB_CCWAIT)] neq 0)
         end %;


! Macro - LINK_CONNECT
!
! Function - This macro checks to see if a link is connected.  If
!            this macro returns true, the link is ready for data
!            transfer.
!
! Parameters -
!
!    LINK_INFO    Address of link info block
!
! Return values -
!
!    $true    If link is connected
!    $false   If link is not connected


macro
     LINK_CONNECTED (LINK_INFO) =
         begin
         bind LI = LINK_INFO : LINK_INFO_BLOCK;

         .LI [$sub_field (LINK_STATUS, LSB_CONNECTED)] neq 0
         end %;


! Macro - LINK_DISCONNECTED
!
! Function - This macro checks to see is a logical link is no longer
!            in a state that allows data transfer.
!
! Parameters -
!
!    LINK_INFO    Address of link info block
!
! Return values -
!
!    $true    If the link has been disconnected
!    $false   If the link is not in a disconnected state


macro
     LINK_DISCONNECTED (LINK_INFO) =
         begin
         bind LI = LINK_INFO : LINK_INFO_BLOCK;

         (.LI [$sub_field (LINK_STATUS, LSB_PREV_CONNECT)] neq 0) or
         (.LI [$sub_field (LINK_STATUS, LSB_CLOSED)] neq 0) or
         (.LI [$sub_field (LINK_STATUS, LSB_ABORTED)] neq 0)
         end %;


! Macro - CONNECT_WAIT
!
! Function - This macro checks a logical link to see if it is
!            waiting for a connect to complete.
!
! Parameters -
!
!    LINK_INFO    Address of link info block
!
! Return values -
!
!    $true    Source link    Waiting for a connect confirm
!             Target link    Waiting for incoming connect initiate
!    $false   otherwise


macro
     CONNECT_WAIT (LINK_INFO) =
         begin
         bind LI = LINK_INFO : LINK_INFO_BLOCK;

         ((if .LI [LINK_TYPE] eql SOURCE_LINK
           then (.LI [$sub_field (LINK_STATUS, LSB_CCWAIT)] neq 0)
           else (.LI [$sub_field (LINK_STATUS, LSB_CIWAIT)] neq 0)) and
          (.LI [$sub_field (LINK_STATUS, LSB_ABORTED)] eql 0) and
          (.LI [$sub_field (LINK_STATUS, LSB_CLOSED)] eql 0))
         end %;

! Macro - LINK_EOM
!
! Function - This macro tests to see if the MO_EOM bit is lit.  This can be
!            used to detect if someone sends a null record...
!
! Parameters -
!
!    LINK_INFO - address of the link info block
!
! Value -
!    $true if MO_EOM is set
!    $false otherwise

MACRO link_eom(link_info) =
      BEGIN
      BIND li = link_info : link_info_block;

      .LI [$sub_field (LINK_STATUS, LSB_EOM)] 
      END %;

! Macro - READ_MESSAGE
!
! Function - This macro reads a message from a logical link.  It
!            blocks until the total message is read.
!
! Parameters -
!
!    LINK_INFO    Address of link info block
!    BUFFER_LEN   Length of receive buffer in bytes
!    BUFFER_PTR   Pointer to receive buffer
!
! Return values -
!
!    Number of characters read
!    0 indicates a null record was sent (a record with NO characters)
!    -1 indicates time out occurred
!    -2 indicates link failed

macro
     READ_MESSAGE (LINK_INFO, BUFFER_LEN, BUFFER_PTR) =
         begin
         bind LI = LINK_INFO : LINK_INFO_BLOCK;
         bind FI = .LI[LINK_FORK] : FORK_INFO_BLOCK;
         bind PG = (.FI[FORK_PAGE] * 512): FORK_DATA_PAGE;
         external routine MX$FORK_RUN;

         PG [SF_FUNCTION] = SD$RD;
         PG [SF_ARGUMENT_2] = .LI[LINK_JFN];
         PG [SF_ARGUMENT_3] = BUFFER_PTR;
         PG [SF_ARGUMENT_4] = BUFFER_LEN;
         if MX$FORK_RUN(FI,2*.NTIMO)
         then
             begin
             if .PG [SF_ERR]
             then
                 -2
             else
                 .PG [SF_ARGUMENT_4]
             end
         else
             -1
         end %;


! Macro - WRITE_MESSAGE
!
! Function - This macro writes a message on a logical link
!
! Parameters -
!
!    LINK_INFO    Address of link info block
!    BUFFER_LEN   Number of bytes to write
!    BUFFER_PTR   Pointer to message to write
!
! Return values -
!
!    $true    Successful write
!    $false   Failure during write


macro
     WRITE_MESSAGE (LINK_INFO, BUFFER_LEN, BUFFER_PTR) =
         begin
         bind LI = LINK_INFO : LINK_INFO_BLOCK;
         bind FI = .LI[LINK_FORK] : FORK_INFO_BLOCK;
         bind PG = (.FI[FORK_PAGE] * 512): FORK_DATA_PAGE;
         external routine MX$FORK_RUN;

         PG [SF_FUNCTION] = SD$WRM;
         PG [SF_ARGUMENT_2] = .LI[LINK_JFN];
         PG [SF_ARGUMENT_3] = BUFFER_PTR;
         PG [SF_ARGUMENT_4] = BUFFER_LEN;

         MX$FORK_RUN(FI,2*.NTIMO)
         END %;


! Macro - WRITE_STRING
!
! Function - This macro writes a string to a logical link.  It
!            does not terminate the write with an End-of-Message
!            indicator.
!
! Parameters -
!
!    LINK_INFO    Address of link info block
!    BUFFER_LEN   Number of bytes to write
!    BUFFER_PTR   Pointer to string to write
!
! Return values -
!
!    $true    Successful write
!    $false   Failure during write


macro
     WRITE_STRING (LINK_INFO, BUFFER_LEN, BUFFER_PTR) =
         begin
         bind LI = LINK_INFO : LINK_INFO_BLOCK;
         bind FI = .LI [LINK_FORK] : FORK_INFO_BLOCK;
         bind PG = (.FI[FORK_PAGE] * 512): FORK_DATA_PAGE;
         external routine MX$FORK_RUN;

         PG [SF_FUNCTION] = SD$WRS;
         PG [SF_ARGUMENT_2] = .LI[LINK_JFN];
         PG [SF_ARGUMENT_3] = BUFFER_PTR;
         PG [SF_ARGUMENT_4] = BUFFER_LEN;

         MX$FORK_RUN(FI, 2*.NTIMO)

         end %;


! Macro - ABORT_LINK
!
! Function - This macro aborts a logical link connection.  It
!            sends the reason for abort and optional data back
!            to the task at the other end of the link.
!
! Parameters -
!
!    LINK_INFO    Address of link info block
!    REASON       DECnet disconnect reason code
!    DATA_LEN     Number of bytes in optional data
!    DATA_PTR     Pointer to optional data


macro
     ABORT_LINK (LINK_INFO, REASON, DATA_LEN, DATA_PTR) =
         begin
         DECLARE_JSYS (MTOPR, CLOSF)
         bind LI = LINK_INFO : LINK_INFO_BLOCK;
         local RSN;

         RSN<18,18,0> = REASON;
         RSN<0,18,0> = $MOCLZ;
         $$MTOPR (.LI [LINK_JFN], .RSN, DATA_PTR, DATA_LEN);
         $$CLOSF ((.LI [LINK_JFN] or CZ_ABT));
         end %;


! Macro - CLOSE_LINK
!
! Function - This macro closes a logical link.  After this macro
!            the link info block can no longer be used for
!            manipulations of the logical link.
!
! Parameters -
!
!    LINK_INFO    Address of link info block
!    DATA_LEN     Number of bytes in optional closure data
!    DATA_PTR     Pointer to optional closure data


macro
     CLOSE_LINK (LINK_INFO, DATA_LEN, DATA_PTR) =
         begin
         DECLARE_JSYS (MTOPR, CLOSF)
         bind LI = LINK_INFO : LINK_INFO_BLOCK;

         $$MTOPR (.LI [LINK_JFN], $MOCLZ, DATA_PTR, DATA_LEN);
         if not $$CLOSF (.LI [LINK_JFN])
         then $$CLOSF ((.LI [LINK_JFN] or CZ_ABT));
         end %;


! Macro - READ_LINK_STATUS
!
! Function - This macro reads the logical link status and
!            stores it in the link info block.  Use the
!            link testing macros to check the link status.
!
! Parameters -
!
!    LINK_INFO    Address of link info block


macro
     READ_LINK_STATUS (LINK_INFO) =
         begin
         DECLARE_JSYS (MTOPR)
         bind LI = LINK_INFO : LINK_INFO_BLOCK;
         local STATUS;        

         if not $$MTOPR (.LI [LINK_JFN], $MORLS; STATUS)
         then 
              begin
              $trace('Read Link Status failed');
              STATUS = 0;
              end;
  
         $trace('Read Link Status: %O',.status);
         LI[$sub_field (LINK_STATUS, LSB_FLAGS)] = .STATUS <27,9,0>;
         LI [$sub_field (LINK_STATUS, LSB_REASON)] = .STATUS <0,8,0>;
         end %;


! Macro - READ_USER_NAME
!
! Function - This macro reads the remote user's name that is connected
!            to a logical link.  The CB_USERID field in the connect
!            is filled in to point to the CB_USERID_BUFFER.  The
!            length field CB_USERID_LENGTH is also set.
!
! Parameters -
!
!    CONN_BLOCK    Address of connect data block
!    INFO_BLOCK    Address of info block


macro
     READ_USER_NAME (CONN_BLOCK, INFO_BLOCK) =
         begin
         DECLARE_JSYS (MTOPR)
         local END_PTR;
         bind CB = CONN_BLOCK : CONNECT_BLOCK,
              LI = INFO_BLOCK : LINK_INFO_BLOCK;

         CB [CB_USERID] = ch$ptr ((CB [CB_USERID_BUFFER]),, 8);
         $$MTOPR (.LI [LINK_JFN], $MORUS, .CB [CB_USERID]; END_PTR);
         CB [CB_USERID_LENGTH] = ch$diff (.END_PTR, .CB [CB_USERID]);
         end %;


! Macro - READ_ACCOUNT_STRING
!
! Function - This macro reads the remote task's account string.
!            CB_ACCOUNT field in the connect is filled in to point
!            to the CB_ACCOUNT_BUFFER.  The length field
!            CB_ACCOUNT_LENGTH is also set.
!
! Parameters -
!
!    CONN_BLOCK    Address of connect data block
!    INFO_BLOCK    Address of info block


macro
     READ_ACCOUNT_STRING (CONN_BLOCK, INFO_BLOCK) =
         begin
         DECLARE_JSYS (MTOPR)
         local END_PTR;
         bind CB = CONN_BLOCK : CONNECT_BLOCK,
              LI = INFO_BLOCK : LINK_INFO_BLOCK;

         CB [CB_ACCOUNT] = ch$ptr (CB [CB_ACCOUNT_BUFFER],, 8);
         $$MTOPR (.LI [LINK_JFN], $MORAC, .CB [CB_ACCOUNT]; END_PTR);
         CB [CB_ACCOUNT_LENGTH] = ch$diff (.END_PTR, .CB [CB_ACCOUNT]);
         end %;


! Macro - READ_PASSWORD_STRING
!
! Function - This macro reads the remote task's password string.
!            CB_PASSWORD field in the connect is filled in to point
!            to the CB_PASSWORD_BUFFER.  The length field
!            CB_PASWWORD_LENGTH is also set.
!
! Parameters -
!
!    CONN_BLOCK    Address of connect data block
!    INFO_BLOCK    Address of info block


macro
     READ_PASSWORD_STRING (CONN_BLOCK, INFO_BLOCK) =
         begin
         DECLARE_JSYS (MTOPR)
         bind CB = CONN_BLOCK : CONNECT_BLOCK,
              LI = INFO_BLOCK : LINK_INFO_BLOCK;

         CB [CB_PASSWORD] = ch$ptr (CB [CB_PASSWORD_BUFFER],, 8);
         $$MTOPR (.LI [LINK_JFN], $MORPW, .CB [CB_PASSWORD]; ,CB [CB_PASSWORD_LENGTH]);
         end %;


! Macro - READ_OPTIONAL_DATA
!
! Function - This macro reads the remote task's optional data string.
!            CB_DATA field in the connect is filled in to point
!            to the CB_DATA_BUFFER.  The length field
!            CB_DATA_LENGTH is also set.
!
! Parameters -
!
!    CONN_BLOCK    Address of connect data block
!    INFO_BLOCK    Address of info block


macro
     READ_OPTIONAL_DATA (CONN_BLOCK, INFO_BLOCK) =
         begin
         DECLARE_JSYS (MTOPR)
         bind CB = CONN_BLOCK : CONNECT_BLOCK,
              LI = INFO_BLOCK : LINK_INFO_BLOCK;

         CB [CB_DATA] = ch$ptr (CB [CB_DATA_BUFFER],, 8);
         $$MTOPR (.LI [LINK_JFN], $MORDA, .CB [CB_DATA]; ,CB [CB_DATA_LENGTH]);
         end %;


! Macro - READ_OBJECT_TYPE
!
! Function - This macro reads the object type used in completion
!            of the logical link connection.  The CB_OBJECT field
!            in the connect is filled in with the objec type code.
!
! Parameters -
!
!    CONN_BLOCK    Address of connect data block
!    INFO_BLOCK    Address of info block


macro
     READ_OBJECT_TYPE (CONN_BLOCK, INFO_BLOCK) =
         begin
         DECLARE_JSYS (MTOPR)
         bind CB = CONN_BLOCK : CONNECT_BLOCK,
              LI = INFO_BLOCK : LINK_INFO_BLOCK;

         $$MTOPR (.LI [LINK_JFN], $MORCN; CB [CB_OBJECT]);
         end %;


! Macro - READ_HOST_ID
!
! Function - This macro reads the remote task's host id.
!            CB_HOST field in the connect is filled in to point
!            to the CB_HOST_BUFFER.  The length field
!            CB_HOST_LENGTH is also set.  The format of the id
!            is 2 bytes of node number followed by a counted
!            ASCII field (maximum of 6 bytes).
!
! Parameters -
!
!    CONN_BLOCK    Address of connect data block
!    INFO_BLOCK    Address of info block


macro
     READ_HOST_ID (CONN_BLOCK, INFO_BLOCK) =
         begin
         DECLARE_JSYS (MTOPR)
         local PTR, END_PTR, ERR_;
         bind CB = CONN_BLOCK : CONNECT_BLOCK,
              LI = INFO_BLOCK : LINK_INFO_BLOCK;

         PTR = (CB [CB_HOST] = ch$ptr (CB [CB_HOST_BUFFER],, 8));
         ch$wchar_a (0, PTR);
         ch$wchar_a (0, PTR);
         IF $$MTOPR (.LI [LINK_JFN], $MORHN, ch$plus (.PTR, 1); END_PTR)
         THEN
             ch$wchar_a ((ch$diff (.END_PTR, .PTR) - 1), PTR)
         ELSE
             IF .(.PTR<0,18,0>)<18,18,0> EQL 0
             THEN
                 BEGIN
                 err_ = .ptr;
                 ptr = CH$PLUS(.ptr,1);
                 ch$wchar($NMU$TEXT(ptr,max_string_length,'%D.%D',
                                    .(.end_ptr)<10,6,0>,
                                    .(.end_ptr)<0,10,0>) - 1,
                          .err_);
                 END;
            
         end %;


! Macro - READ_DESCRIPTOR
!
! Function - This macro reads the remote task's link descriptor.
!            CB_DESCRIPTOR field in the connect is filled in to point
!            to the CB_DESCRIPTOR_BUFFER.  The length field
!            CB_DESCRIPTOR_LENGTH is also set.
!
! Parameters -
!
!    CONN_BLOCK    Address of connect data block
!    INFO_BLOCK    Address of info block


macro
     READ_DESCRIPTOR (CONN_BLOCK, INFO_BLOCK) =
         begin
         DECLARE_JSYS (MTOPR)
         local END_PTR;
         bind CB = CONN_BLOCK : CONNECT_BLOCK,
              LI = INFO_BLOCK : LINK_INFO_BLOCK;

         CB [CB_DESCRIPTOR] = ch$ptr (CB [CB_DESCRIPTOR_BUFFER],, 8);
         $$MTOPR (.LI [LINK_JFN], $MORHN, .CB [CB_DESCRIPTOR]; END_PTR);
         CB [CB_DESCRIPTOR_LENGTH] = ch$diff (.END_PTR, .CB [CB_DESCRIPTOR]);
         end %;


! Macro - READ_REJECT_CODE
!
! Function - This macro reads the remote task's connect reject reason code.
!            CB_REJECT_CODE field in the connect is filled in.  The
!            READ_LINK_STATUS call must have been made first.
!
! Parameters -
!
!    CONN_BLOCK    Address of connect data block
!    INFO_BLOCK    Address of info block


macro
     READ_REJECT_CODE (CONN_BLOCK, INFO_BLOCK) =
         begin
         bind CB = CONN_BLOCK : CONNECT_BLOCK,
              LI = INFO_BLOCK : LINK_INFO_BLOCK;

         CB [CB_REJECT_CODE] = .LI [$sub_field (LINK_STATUS, LSB_REASON)];
         end %;


! Macro - NETWORK_INTERRUPT_CLEAR
!
! Function - This macro clears any "interrupt waiting" flag in the operating
!            system for a logical link.  This is used to tighten code
!            and suppress races.
!
! Parameters -
!
!    LINK_INFO    Address of link info block


macro
     NETWORK_INTERRUPT_CLEAR (LINK_INFO) =
         begin
         bind LI = LINK_INFO : LINK_INFO_BLOCK;
         DECLARE_JSYS (SIBE)

         $$SIBE (.LI [LINK_JFN]);
         end %;
%title ''
%sbttl ''

!
! [End of NMUT20]
! Local Modes:
! Mode:BLISS
! Auto Save Mode:0
! Comment Column:40
! Comment Rounding:+1
! End: