Google
 

Trailing-Edge - PDP-10 Archives - BB-P363B-SM_1985 - mcb/drivers/kdpdat.r16
There are no other files named kdpdat.r16 in the archive.
! [Beginning of KDPDAT]
!
!
!                    COPYRIGHT (c) 1980, 1981, 1982
!                    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: MCB KMC/DUP Driver
!
! ABSTRACT:
!
!	This contains the data structure definitions for the KMC/DUP DDM.
!
! ENVIRONMENT: MCB V3.0
!
! AUTHOR: Alan D. Peckham	CREATION DATE: 30-Oct-80
!
! MODIFIED BY:
!
!	Alan D. Peckham, 30-Oct-80: Version 1
! 01	- Rewrite from MACRO-11 to BLISS.
! 02	- Add new features to K_ and D_ tables.
! 03	- Add transmit/receive-to-KMC counters for proper shutdown.
!	  Add temporary counters for hardware errors.
! 04	- Add KF_LD and K_ACTIVE.
! 05	- Add CT_MNT field in SEL7 for control-in.
!--

%if not %declared (XPO$K_VERSION) %then library 'XPORT'; %fi

%if not %declared (MCB$K_VERSION) %then library 'MCBLIB'; %fi

library 'NMXLIB';

$SHOW (FIELDS) $SHOW (LITERALS)

!
! Status Codes:
!

DECLARE_SEVERITY (KDP, INFO, WARNING, SEVERE);

$KDP_INFO (KDP$_EVT, 'Network event')
$KDP_SEVERE (KDP$_QUE, 'Queue should not be empty')
$KDP_SEVERE (KDP$_CMP, 'Completion overrun')
$KDP_SEVERE (KDP$_NXM, 'KMC given address of non-existent memory')
$KDP_SEVERE (KDP$_SEG, 'Too many transmit segments')
$KDP_SEVERE (KDP$_PWF, 'Unable to handle power failure recovery')
$KDP_WARNING (KDP$_LOD, 'Cannot load the KMC microcode')
$KDP_WARNING (KDP$_RUN, 'Cannot start the KMC')
$KDP_SEVERE (KDP$_DSC, 'Unexpected descriptor address')
$KDP_SEVERE (KDP$_CODE, 'Invalid command type code from KMC')
$KDP_SEVERE (KDP$_BROKEN, 'Unrecoverable error encountered')

!
! Global Synonyms
!

macro
    PARAMETER_DEVICE_REGISTERS = PLL0 %,
    REGISTER_NXM = KMCNXM %;

!
! Linkages for global routines
!

linkage
    KDP_CSR_NUM = jsr (register = 0, register = 1),
    KDP_REG = jsr (register = 1) : nopreserve (1);

!
! Useful macros
!

macro
    !
    ! Get the bit number for a one-bit field
    !
    BIT_NUMBER [FLD] =
	%fieldexpand (FLD, 1) %,
    !
    ! Produce a mask for the given field
    !
    BIT_MASK [] =
	(0 + BIT_MSK (%remaining)) %,
    BIT_MSK [FLD] =
	(1^%fieldexpand (FLD, 2) - 1)^%fieldexpand (FLD, 1) %,
    !
    ! Add the specified value to an 18 bit address in the data base
    !
    PHYSICAL_ADD (DB, FLD, VALUE) =
	begin

	builtin
	    rot;

	if rot (DB [$SUB_FIELD (FLD, PHYSICAL_LOW)] =
	    .DB [$SUB_FIELD (FLD, PHYSICAL_LOW)] + VALUE, 1)
	then
	    DB [$SUB_FIELD (FLD, PHYSICAL_HIGH)] =
		.DB [$SUB_FIELD (FLD, PHYSICAL_HIGH)] + 1;

	end %;

!
! Data base creation items
!

macro
    $ALIGN_SIGN =
	%assign ($xpo$fill_index, $xpo$fill_index + 1)
	%assign ($xpo$fill_temp, 7 - ($xpo$bit_index mod 8))
	%name (XPOfill, %number ($xpo$fill_index)) = [$BITS ($xpo$fill_temp)], %,
    $SIGN_BIT =
	$XPO$FIELD (1, 1, 0) %;

compiletime
    $xpo$fill_index = 0,
    $xpo$fill_temp = 0;

$FIELD
    !
    ! List head definition
    !
    LIST_FIRST = [$ADDRESS],
    LIST_LAST = [$ADDRESS];

compiletime
    $KDP$length = $FIELD_SET_SIZE;

macro
    $LIST_HEAD =
	$SUB_BLOCK (%expand %number ($KDP$length)) %;

$FIELD
    !
    ! Physical 18 bit address
    !
    PHYSICAL_HIGH = [$BITS (16)],
    PHYSICAL_LOW = [$BITS (16)];

%assign ($KDP$length, $FIELD_SET_SIZE)

macro
    $BIAS =
	$SHORT_INTEGER %,
    $PHYSICAL_ADDRESS =
	$SUB_BLOCK (%expand %number ($KDP$length)) %,
    $SYNCH_BLOCK =
	$SUB_BLOCK (3) %;

undeclare
    $KDP$length;
!
! KDP11 hardware register definitions
!

field
    KDP_FIELDS =
	set
	SEL0 = [0, 0, 16, 1],
	BSEL0 = [0, 0, 8, 1],
	BSEL1 = [0, 8, 8, 1],
	    RUN = [0, 15, 1, 1],	! Run
	    MCL = [0, 14, 1, 0],	! Master clear
	    RQI = [0, 7, 1, 1],		! Request data ports
	    IEO = [0, 4, 1, 0],		! Enable output-request interrupts
	    IEI = [0, 0, 1, 0],		! Enable input-request interrupts
	SEL2 = [1, 0, 16, 1],
	BSEL2 = [1, 0, 8, 1],
	BSEL3 = [1, 8, 8, 1],
	    LNBR = [0, 8, 7, 0],	! DUP number
	    RDYO = [0, 7, 1, 1],	! Data ports ready for output
	    RDYI = [0, 4, 1, 0],	! Data ports ready for input
	    IN_I_O = [0, 2, 1, 0],	! Operation is a receive
	    COM = [0, 0, 3, 0],		! Command code
	SEL4 = [2, 0, 16, 1],
	SEL6 = [3, 0, 16, 1],

! Buffer address in/out

	    BA_LOW = [0, 0, 16, 0],
	    BA_KIL = [0, 12, 1, 0],
	    BA_EOM = [0, 12, 1, 0],
	    BA_HIGH = [0, 14, 2, 0],

! Control in

	    CT_ENB = [0, 8, 1, 0],
	    CT_MNT = [0, 10, 2, 0],
	    CT_DUP = [0, 13, 1, 0],
	    CT_DEC = [0, 15, 1, 1]
	tes;

literal
    TBA = 0,				! Transmit buffer/address in/out
    CTL = 1,				! Control function in/out
    BAS = 3,				! DUP-11 CSR base address in
    RBA = 4;				! Receive buffer/address in/out

!
! Buffer descriptors
!

field
    BD_FIELDS =
	set
	BD_LOW = [0, 0, 16, 0],		! Low order 16 bits
	BD_CC = [1, 0, 16, 0],		! Character count
	BD_SOM = [2, 8, 1, 0],		! Start of message
	BD_EOM = [2, 9, 1, 0],		! End of message
	BD_HIGH = [2, 10, 2, 0],	! High order 2 bits
	BD_SYN = [2, 12, 1, 0],		! Preceede with SYNs
	BD_LBD = [2, 15, 1, 1]		! Last buffer descriptor
	tes;

literal
    BD_LEN = 3;

!
! DUP hardware device registers
!

field
    DUP_FIELDS =
	set
	RXCSR = [0, 0, 16, 1],
	    DATA_SET_CHANGE_B = [0, 0, 1, 0],
	    DATA_TERMINAL_READY = [0, 1, 1, 0],
	    REQUEST_TO_SEND = [0, 2, 1, 0],
	    SECONDARY_TRANSMIT_DATA = [0, 3, 1, 0],
	    RECEIVER_ENABLE = [0, 4, 1, 0],
	    DATA_SET_INTERRUPT_ENABLE = [0, 5, 1, 0],
	    RECEIVER_INTERRUPT_ENABLE = [0, 6, 1, 0],
	    RECEIVER_DONE = [0, 7, 1, 1],
	    STRIP_SYNCH = [0, 8, 1, 0],
	    DATA_SET_READY = [0, 9, 1, 0],
	    SECONDARY_RECEIVED_DATA = [0, 10, 1, 0],
	    RECEIVER_ACTIVE = [0, 11, 1, 0],
	    CARRIER = [0, 12, 1, 0],
	    CLEAR_TO_SEND = [0, 13, 1, 0],
	    RING_INDICATOR = [0, 14, 1, 0],
	    DATA_SET_CHANGE_A = [0, 15, 1, 1],

	RXDBUF = [1, 0, 16, 1],
	    RECEIVER_DATA_BUFFER = [0, 0, 8, 0],
	    START_OF_RECEIVED_MESSAGE = [0, 8, 1, 0],
	    END_OF_RECEIVED_MESSAGE = [0, 9, 1, 0],
	    RECEIVED_ABORT = [0, 10, 1, 0],
	    RCRC_ERROR = [0, 12, 1, 0],
	    OVERRUN = [0, 14, 1, 0],
	    ERROR = [0, 15, 1, 1],

	PARCSR = [1, 0, 16, 1],
	    SECONDARY_ADDRESS = [0, 0, 8, 0],
	    RECEIVER_SYNCH = [0, 0, 8, 0],
	    CRC_INHIBIT = [0, 9, 1, 0],
	    SECONDARY_MODE_SELECT = [0, 12, 1, 0],
	    DEC_MODE = [0, 15, 1, 0],

	TXCSR = [2, 0, 16, 0],
	    HALF_DUPLEX = [0, 3, 1, 0],
	    SEND = [0, 4, 1, 0],
	    TRANSMITTER_INTERRUPT_ENABLE = [0, 6, 1, 0],
	    TRANSMITTER_DONE = [0, 7, 1, 1],
	    DEVICE_RESET = [0, 8, 1, 0],
	    TRANSMITTER_ACTIVE = [0, 9, 1, 0],
	    MAITENANCE_INPUT_DATA = [0, 10, 1, 0],
	    MAINTENANCE_MODE_SELECT = [0, 11, 2, 0],
	    MAINTENANCE_CLOCK = [0, 13, 1, 0],
	    MAINTENANCE_TRANSMIT_DATA_OUT = [0, 14, 1, 0],
	    TRANSMIT_DATA_LATE_ERROR = [0, 15, 1, 1],

	TXDBUF = [3, 0, 16, 1],
	    TRANSMIT_DATA_BUFFER = [0, 0, 8, 0],
	    TRANSMIT_START_OF_MESSAGE = [0, 8, 1, 0],
	    TRANSMIT_END_OF_MESSAGE = [0, 9, 1, 0],
	    TRANSMIT_ABORT = [0, 10, 1, 0],
	    MAINTENANCE_TIMER = [0, 11, 1, 0],
	    TCRCIN = [0, 12, 1, 0],
	    RCRIN = [0, 14, 1, 0]
	tes;
!
! KDP driver data bases
!

macro
    KDP_DATA_BASE = block field (DIR_FIELDS) %,
    KMC_DATA_BASE = block field (K_FIELDS) %,
    DUP_DATA_BASE = block field (D_FIELDS) %;

literal
    KD_DUP = 4;

$FIELD
    K_FIELDS =
	set
	K_TIM = [$BYTE],		! Data base timer
	KF_MICROCODE_LOADED = [$BIT],	! KMC microcode loaded
	KF_MICROCODE_RUNNING = [$BIT],	! KMC has been initialized
	    $ALIGN (FULLWORD)
	K_REGISTER = [$ADDRESS],	! KMC SEL0 register address
	K_VECTOR = [$ADDRESS],		! KMC interrupt vector address
	K_PRIORITY = [$TINY_INTEGER],	! KMC interrupt priority
	K_CONTROLLER = [$TINY_INTEGER],	! KMC controller number
	K_SYNCH_BLOCK = [$ADDRESS],	! SYNCH block address
	K_INPUT_QUEUE = [$LIST_HEAD],	! Input request queue
	K_INPUT_DATA = [$ADDRESS],	! Registers for next input transfer
	K_OUTPUT_DATA = [$ADDRESS],	! Output data port holding area
	K_DEVICE_ERRORS = [$COUNTER (8)],
	K_INVALID_UNIT = [$COUNTER (1)],
	K_INVALID_OUTPUT_CODE = [$COUNTER (1)],
	K_MICROCODE_WONT_LOAD = [$COUNTER (1)],
	K_MICROCODE_WONT_START = [$COUNTER (1)],
	    $ALIGN (FULLWORD)
	K_PERFORMANCE_ERRORS = [$COUNTER (8)],
	K_COMPLETION_QUEUE_OVERRUN = [$COUNTER (1)],
	K_LOST_INTERRUPT = [$COUNTER (1)],
	K_LATE_RDYI = [$COUNTER (1)],
	    $ALIGN (FULLWORD)
	K_ACTIVE = [$TINY_INTEGER],	! Number of active DUPs
	K_UNITS = [$BYTE],		! Maximum number of DUPs on this KMC
	K_DUP_PIX = [$BYTES (KD_DUP)]	! PIXs of DUP processes
	    $ALIGN (FULLWORD)
	tes;

literal
    K_LEN = $FIELD_SET_SIZE;

$FIELD
    D_FIELDS =
	set
	D_TIM = [$TINY_INTEGER],	! Long timer
	DF_KILLING_TRANSMITS = [$BIT],	! Transmit kill I/O in progress
	DF_KILLING_RECEIVES = [$BIT],	! Receive kill I/O in progress
	DF_DSR = [$BIT],		! Current DSR condition
	DF_TRANSMIT_UNDERRUN = [$BIT],	! Transmitter has had underrun
	    $ALIGN_SIGN
	DF_TRUNCATING_RECEIVE = [$SIGN_BIT], ! Current message is too long
	    $ALIGN (FULLWORD)
	DF_STOPPING_LINE = [$BIT],	! Stop in progress
	DF_STARTING_LINE = [$BIT],	! Start in progress
	DF_HALF_DUPLEX = [$BIT],	! Line is half duplex
	DF_CONTROLLER_LOOPBACK = [$BIT],
	DF_INTERNAL_CLOCK = [$BIT],
	DF_ENABLED = [$BIT],		! Line is enabled
	DF_DUP_CSR_SET = [$BIT],	! BASE-IN has been performed
	    $ALIGN_SIGN
	DF_LINE_ACTIVE = [$SIGN_BIT],	! Line has been started
	    $ALIGN (FULLWORD)
	D_ASSIGNABLE_TRANSMIT_CCBS = [$LIST_HEAD], ! Transmit buffers awaiting assignment
	D_PENDING_CONTROL_CCBS = [$LIST_HEAD], ! Pending control function queue
	D_KMC_HANDLE = [$INTEGER],
	    $OVERLAY (D_KMC_HANDLE)
	D_CONTROLLER = [$TINY_INTEGER],	! KMC number
	D_KMC_PIX = [$BYTE],		! KMC process PIX
	    $CONTINUE
	D_DUP_HANDLE = [$INTEGER],
	    $OVERLAY (D_DUP_HANDLE)
	D_UNIT = [$TINY_INTEGER],	! DUP number
	D_DUP_PIX = [$BYTE],		! DUP process PIX
	    $CONTINUE
	D_LIX = [$INTEGER],		! Line index
	D_ASSIGNED_TRANSMIT_COUNT = [$TINY_INTEGER],
	D_ASSIGNABLE_TRANSMIT_COUNT = [$TINY_INTEGER], ! Number of available transmit descriptors
	D_ASSIGNED_RECEIVE_COUNT = [$TINY_INTEGER],
	D_ASSIGNABLE_RECEIVE_COUNT = [$TINY_INTEGER], ! Number of available receive descriptors
	D_TRANSMIT_TIMEOUT = [$TINY_INTEGER], ! Transmit timeout interval
	D_POLLING_THRESHOLD = [$TINY_INTEGER], ! Polling change threshold count
	D_MAXIMUM_TRANSMIT_SEGMENTS = [$TINY_INTEGER], ! Maximum number of transmit segments
	    $ALIGN (FULLWORD)
	D_DEVICE_ERRORS = [$COUNTER (8)],
	D_RECEIVE_BA_ERROR = [$COUNTER (1)],
	D_TRANSMIT_BA_ERROR = [$COUNTER (1)],
	D_INVALID_ERROR_CODE = [$COUNTER (1)],
	D_NONEXISTENT_MEMORY = [$COUNTER (1)],
	    $ALIGN (FULLWORD)
	D_PERFORMANCE_ERRORS = [$COUNTER (8)],
	D_NO_BUFFER_ASSIGNED = [$COUNTER (1)],
	D_POLLING_ADJUSTMENT = [$COUNTER (1)],
	    $ALIGN (FULLWORD)
	D_EXT_BIAS = [$BIAS],		! Extension table
	D_EXT_ADDR = [$ADDRESS]
	tes;

literal
    D_LEN = $FIELD_SET_SIZE;

$FIELD
    E_FIELDS =
	set
	E_NEXT_TRANSMIT_DESCRIPTOR = [$ADDRESS], ! Next transmit descriptor to assign
	E_NEXT_RECEIVE_DESCRIPTOR = [$ADDRESS], ! Next receive descriptor to assign
	E_ASSIGNED_TRANSMIT_CCBS = [$LIST_HEAD], ! Assigned transmit buffer chains
	E_ASSIGNED_RECEIVE_CCBS = [$LIST_HEAD], ! Assigned receive buffer chains
	E_ENTITY = [$INTEGER],		! Network management entity identification
	E_REGISTER = [$ADDRESS],	! Address of DUP SEL0 register
	EF_HDX = [$BIT],		! Half duplex line operation
	ES_FILL1 = [$BITS (7)],
	ES_XMT = [$BITS (4)],		! Transmit speed
	ES_RCV = [$BITS (4)],		! Receive speed
	    $ALIGN (FULLWORD)
	ES_PRT = [$BITS (3)],		! Protocol type
	EF_MPT = [$BIT],		! Multipoint line
	EF_SEC = [$BIT],		! Multipoint secondary station
	EF_ADR = [$BIT],		! Secondary station in 16 bits
	    $ALIGN (FULLWORD)
	E_CTL = [$SHORT_INTEGER],	! CONTROL-IN flags
	E_POLLING_RATE = [$TINY_INTEGER], ! Polling rate
	E_PTH = [$TINY_INTEGER],	! (unused)
	E_DESCRIPTORS = [$SUB_BLOCK (0)] ! Beginning of descriptors
	tes;

literal
    E_LEN = $FIELD_SET_SIZE,
    EP_DEC = 1,				! DDCMP protocol
    EP_BSC = 2,				! BSC
    EP_SDL = 3,				! SDLC/ADDCP/HDLC
    EP_X25 = 4;				! X.25

$FIELD
    DIR_FIELDS =
	set
	DIR_CONTROLLERS = [$BYTE],	! Maximum number of KMCs.
	DIR_KMC_PIX = [$BYTES (1)]	! PIXs of KMC processes
					!  indexed by controller number.
	tes;

!
! [End of KDPDAT]