.MCALL .MODULE .MODULE STBSUB,00, ; Copyright (c) 1998 by Mentec, Inc., Nashua, NH. ; All rights reserved ; ; This software is furnished under a license for use only on a ; single computer system and may be copied only 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 except for use on such ; system and to one who agrees to these license terms. Title ; to and ownership of the software shall at all times remain ; in Mentec, Inc. ; ; The information in this document is subject to change without ; notice and should not be construed as a commitment by Digital ; Equipment Corporation, or Mentec, Inc. ; ; Digital and Mentec assume no responsibility for the use or ; reliability of its software on equipment which is not supplied ; by Digital or Mentec, and listed in the Software Product ; Description. ;++ ; Facility: DBGSYM - .STB file manipulation utility ; ; Author: Joe Worrall ; ; Created: 09-Feb-83 ; ; Abstract: STBSUB - .STB file manipulation subroutines ; ; Externals Description ; --------- ----------- ; Under RT-11: ; $STBBF = 200 Byte buffer for .STB records ; Under RSX-11M: ; $STBDF FDB open to .STB file ; $SAVAL Register save/restore routine ; .POINT FCS record point routine ; .GETSQ FCS get record routine ; ; Edit Who Date Description of modification ; ---- --- ---- --------------------------- ; 001 Jrw 17-Dec-85 Cleanup for release. ; 002 Jrw 28-Feb-86 Incorporate code review comments ;-- ; Mcalls .MCALL .READW .GLOBL $STBBF $STBSZ ==: 200 ; Maximum size of .STB record .PSECT PURE, RO, I ; Pure code starts here. .SBTTL SYMLOC - Locate a RAD50 symbol in a .STB file ;+ ; SYMLOC ; FUNCTIONAL DESCRIPTION ; ; This routine looks for a match on a RAD50 double word in ; the .STB file. ; ; Inputs: $SYMB,$SYMB+2 = RAD50 symbol to look for ; ; Outputs: CC R0 = Symbol value ; CS Symbol not found ; ; All other registers saved. ; ;- GS.NAM =: 0 ;Offset to symbol name in GSD record GS.VAL =: 6 ;Offset to symbol value in GSD record ;.ASSUME GS.NAM EQ 0 ;.ASSUME GS.VAL EQ 6 SYMLOC::MOV R1,-(SP) ;Save user R1 CALL REWIND ;Rewind .STB file to first record. 10$: CALL GETGSD ;Get a GSD entry from .STB file or memory BCS 20$ ;Branch if no more. CMP @R1,$SYMB ;First 3 chars match ? BNE 10$ ;Branch if not, try next CMP GS.NAM+2(R1),$SYMB+2 ;Second 3 chars match ? BNE 10$ ;Branch if not MOV GS.VAL(R1),R0 ;Return value in user R0 CLC ;Set status = success 20$: MOV (SP)+,R1 ;Restore user R1 RETURN ;Return to caller .PSECT DATA, RW, D $SYMB:: .BLKW 2 ;Two RAD50 words to look for .PSECT PURE, RO, I .SBTTL FNDSYM - Find a symbol+offset given a value ;+ ; FNDSYM ; FUNCTIONAL DESCRIPTION ; ; This routine attempts to match the value given in R3 with a ; SYMBOL + a OFFSET in the current .STB file. ; ; Inputs: R3 = Octal value to find. ; ; Outputs: CC - $SYMB,$SYMB+2 = RAD50 symbol value ; R4 = Positive offset from symbol ; ; CS - Can't translate. ; ; All other registers saved ; ; WARNING: If stack usage is changed in this routine, then re-calculate the ; offset to return the value in R3. ;- FNDSYM::CALL $SAVAL ;Save all user registers CALL REWIND ;Rewind .STB file to beginning MOV #-1,R4 ;Starting BEST DISPLACEMENT IS MAX. CLR R2 ;Symbol found flag CLR $SYMB ;Clear symbol RAD50 value save area 10$: CALL GETGSD ;Get a GSD entry BCS 20$ ;Branch if no more. MOV 6(R1),R0 ;Get value of this symbol CMP R0,R3 ;Higher than the one we are looking for? BHI 10$ ;Branch if so, next MOV R3,R5 ;Calculate in R5 new offset SUB R0,R5 ;... CMP R5,R4 ;Compare against last offset we found BHI 10$ ;If higher than last, try for another MOV @R1,$SYMB ;Else remember the new SYMBOL MOV 2(R1),$SYMB+2 ;... MOV R5,R4 ;Remember new best displacement BNE 10$ ;and try again unless MATCH ! 20$: TST $SYMB ;Did we find a symbol to use ? BEQ 30$ ;Branch if not, return w/c-bit set. MOV R4,12(SP) ;Return to user R4 displacement from symbol TST (PC)+ ;Clear carry 30$: SEC ; Set carry - symbol not matched. RETURN ;Return to caller .SBTTL GETREC - Get next GSD record from .STB file ;+ ; GETREC ; FUNCTIONAL DESCRIPTION ; ; This routine gets the next record from the .STB file, ; and verifys it as a GSD format record. ; ; Possible DATA BLOCK codes are: ; ; TYPE DESCRIPTION ; ---- ----------- ; 0 Undefined ; 1 GSD type record ; 2 End GSD record ; 3 TEXT record ; 4 RLD type record ; 5 ISD type record ; 6 End of module ; 7 RT-11 Librarian record start ; 10 RT-11 Librarian end ; ; Inputs: .STB file open ; ; Outputs: CC - R1 -> Record ; ENDREC -> End of record ; ; CS - Some error occured. ; ; All other registers saved. ;- GETREC: CALL NXTREC ;Get next record from .STB file BCS 10$ ;Branch if error. ;R1 -> Start of record ;ENDREC -> End of record BIT #177770,@R1 ;Check for bad record BNE 10$ ;Branch if bad record found. CMP #6,@R1 ;End of module record found ? BEQ 10$ ;Branch if so, no more to be found here. CMP #1,(R1)+ ;Declare GSD Record found ? (Bump rec pnt) BNE GETREC ;Branch if not, try getting next record MOV R1,GSDPTR ;Setup GSD pointer for user TST (PC)+ ;Clear carry - no error 10$: SEC ;Set carry - error getting next GSD record RETURN ;Return to caller .PSECT DATA, RW, D GSDPTR: .BLKW 1 ;-> to currect GSD record .PSECT PURE, RO, I .SBTTL GETGSD - Get next GSD record from .STB file ;+ ; GETGSD ; FUNCTIONAL DESCRIPTION ; ; This routine gets the next global symbol GSD record from ; the .STB file. It calls GETREC until EOF or a correct GSD ; entry is found. ; ; This routine is also set-up to get the next GSD record from ; a in-memory copy if $FSYM <> 0. ; ; Possible GSD types are : ; ; TYPE DESCRIPTION ; ---- ----------- ; 0 Module name ; 1 Control section name ; 2 Internal symbol name ; 3 Transfer address ; 4 Global symbol name ; 5 Program section name ; 6 Program version/ID (.IDENT) ; 7 Mapped arry declaration (VSECT) ; ; Inputs: .STB file open ; ; Outputs: CC - R1 -> New GSD entry ; CS - EOF or bad STB file ; ; All other registers saved ;- GETGSD::MOV R0,-(SP) ;Save user R0 TST $FSYM ;Using memory resident list of symbols ? BEQ 5$ ;Branch if not. MOV GSDPTR,R0 ;R1 -> Memory resident listhead TST @R0 ;At the end of memory resident list ? BEQ 20$ ;Branch if so, [EOF] MOV #TEMPS,R1 ;R1 -> Fake GSD entry MOV (R0)+,(R1)+ ;Fill it RAD50 name double word MOV (R0)+,(R1)+ ; ... MOV #400,(R1)+ ;Fake entry type/flags word MOV (R0)+,@R1 ;Address of this symbol MOV R0,GSDPTR ;Set address of next entry in in-core list MOV #TEMPS,R1 ;R1 -> Fake GSD entry for USER BR 15$ ;Give entry to user 5$: ADD #10,GSDPTR ;Point to next GSD record MOV GSDPTR,R1 ;R1 -> Next record CMP R1,ENDREC ;Is pointer outside record ? BLO 10$ ;Branch if not CALL GETREC ;Else - get next record from .STB file BCS 20$ ;Branch if error getting next record 10$: BITB #370,5(R1) ;Check validity of this GSD entry BNE 20$ ;Error - not in range 0-7 CMPB 5(R1),#4 ;We want type = 4 BNE 5$ ;Branch if not a GLOBAL DESCRIPTION. 15$: TST (PC)+ ;Clear carry 20$: SEC ;Set carry - Error MOV (SP)+,R0 ;Restore user R0 RETURN ;Return to caller with C-BIT, R1 -> GSD entry .SBTTL REWIND - Rewind .STB file to first record. ;+ ; REWIND ; FUNCTIONAL DESCRIPTION ; ; This routine rewinds the current open .STB file to the first ; block/record. ; ; Inputs: .STB file open ; .or. $FSYM -> Memory resident symbol table listhead ; ; Outputs: All registers saved. ;- REWIND::MOV $FSYM,GSDPTR ;Reset memory resident -> BNE 10$ ;Branch if we are using memory resident copy. CLR IBLK ;Reset block number to zero MOV #-1,IBFPTR ;Set -> into buffer past end CLR BINREC ;Flag not started on this file yet. MOV #-11,GSDPTR ;Force a read of the first record 10$: RETURN ;Return to caller .PSECT DATA, RW, D $FSYM:: .WORD 0 ;<> 0 means this -> memory resident symbol ;listhead. .PSECT PURE, RO, I .SBTTL NXTREC - Get next physical record from .STB file ;+ ; NXTREC ; FUNCTIONAL DESCRIPTION ; ; This routine returns the next formatted binary record in ; the .STB file already open. ; ; Inputs: .STB file open ; ; Outputs: CC R1 -> Start of record ; ENDREC -> end of record ; ; CS Some error getting next record ; ; All other registers saved. ;- NXTREC: CALL $SAVAL ;Save all registers .ENABL LSB MOV BINREC,-(SP) ;@SP = Library check flag 10$: MOV #THREAD,R4 ;R4 -> jump list for code thread 20$: CMP IBFPTR,#IBUFF+512. ;Past the end of the buffer? BLO 21$ ;Branch if not .READW #TEMPS,ICHAN,#IBUFF,#256.,IBLK ;Read a buffer load BCS 80$ ;Branch on error or eof INC IBLK ;Increment block number *C-BIT* MOV #IBUFF,IBFPTR ;Reset the buffer pointer *C-BIT* 21$: CLR R0 ;Set up for MOVB BISB @IBFPTR,R0 ;Get the character INC IBFPTR ;Bump the buffer pointer BIC #^C<377>,R0 ;Leave only low byte TST @SP ;Have we checked for .OBJ library yet? BNE 30$ ;Branch if so CMP IBUFF+4,#7 ;Is it a library file? BEQ 80$ ;Branch if so. Can't binary copy INC @SP ;Flag that we don't need to check again 30$: MOV @R4,PC ;*** JMP in disguise BYTE1: CMP R0,#1 ;Found first data byte? BNE 20$ ;Branch if not. Ignore CLR CKSUM ;Clear the checksum word CLR BYCNT ;Clear the byte count. BR MBYTEA ;Output data and advance code thread SIZE1: MOVB R0,BCNTMP ;Save the first byte of the byte count BR MBYTEA ;Output data and advance code thread SIZE2: MOVB R0,BCNTMP+1 ;Save the second byte of the byte count ADD BCNTMP,BYCNT ;Compute the byte count CMP BYCNT,#200 ;Can't be > 200 octal bytes (128.) BGT 80$ ;Branch if so, can't do it. INC BYCNT ;Adjust for checksum byte MOV #$STBBF,R3 ;R3 -> input record buffer MOV SP,BINREC ;Flag that processing has started MBYTEA: TST (R4)+ ;Advance the code thread BR 40$ ;Go add in byte for checksum calculation MBYTE: MOVB R0,(R3)+ ;Store the byte 40$: ADD R0,CKSUM ;Compute checksum DEC BYCNT ;Done with this block? BNE 20$ ;Branch if not. Get next byte. DEC R3 ;Back up away from checksum byte TSTB CKSUM ;Checksum 0? BNE 80$ ;Branch if not - checksum error ! MOV #$STBBF,6(SP) ;Set user R1 -> Begining of record MOV R3,ENDREC ;Setup -> end of record TST (PC)+ ;Clear carry - no error 80$: SEC ;Set carry - some error occured. BIT (SP)+,R0 ;POP LIBFLG from stack, save C-BIT RETURN ;Return to caller .DSABL LSB .PSECT DATA, RW, D ENDREC: .BLKW 1 ;-> End of current record TEMPS: .BLKW 5 ;Scratch area IBLK: .BLKW 1 ;*INI* ;= Next block to read ICHAN:: .BLKW 1 ;*INI* ;= I/O Channel to use for .READW's IBUFF: .BLKW 256. ;A one block buffer IBFPTR: .BLKW 1 ;*INI* ;-> into IBUFF BCNTMP: .BLKW 1 ;Byte count accumulator BYCNT: .BLKW 1 ;Byte count for binary block CKSUM: .BLKW 1 ;Checksum accumulator BINREC: .BLKW 1 ;*INI* ;Flag to indicate processing has started .PSECT PURED, RW, D THREAD: .WORD BYTE1 ;Find the 001 byte .WORD MBYTEA ;Output following null .WORD SIZE1 ;Get first byte of byte count .WORD SIZE2 ;Get second byte of byte count .WORD MBYTE ;Get rest of data w/out advancing thread .PSECT PURE, RO, I .SBTTL $SAVAL - Save/Restore all registers ;+ ; $SAVAL ; Famous register save/restore coroutine ; ; JSR PC,$SAVAL (CALL $SAVAL) ; ; All registers saved/restored ;- $SAVAL:: MOV R4,-(SP) ;Save R4 MOV R3,-(SP) ;Save R3 MOV R2,-(SP) ;Save R2 MOV R1,-(SP) ;Save R1 MOV R0,-(SP) ;Save R0 MOV 12(SP),-(SP) ;Get the return address MOV R5,14(SP) ;Save R5 JSR PC,@(SP)+ ;Call the caller MOV (SP)+,R0 ;Restore R0 MOV (SP)+,R1 ;and R1 MOV (SP)+,R2 ;and R2 MOV (SP)+,R3 ;and R3 MOV (SP)+,R4 ;and R4 MOV (SP)+,R5 ;and R5 RETURN .END