! File: LISTC.BLI ! Module LISTC= Begin ! LISTC MODULE ! ------------ ! Require 'Bliss'; Own CNT : Integer, ALDON : Boolean, DLABEL : Integer, curr_psect : Integer; ! THE FOLLOWING SECTION HANDLES LISTING OBJECT CODE External OPERTYPE : Vector[,Byte]; Forward Routine OUTCODE : Novalue, OUTLAB : Novalue, OUTNAME : Novalue, OUTNAMOFF : Novalue, OUTOPD : Novalue, OUTCSECT : Novalue, OUTPLIT : Novalue, OUTSTORAGE : Novalue, OUTGLBINDS : Novalue, OUTVARS : Novalue, OUTDLAB : Novalue, PLACENXTDLAB : Novalue, OUTDNUM : Novalue, ODADR : Novalue, DTYPE, OUTDEBSYMTAB : Novalue, OUTDEBNAMTAB : Novalue; Macro AAA[k] = [%count] = AZ(k) %; Own PDP11PRT : Vector[75,Long] Preset(AAA( '; UUO', 'MOV', 'MOVB','CMP', 'CMPB', 'BIT', 'BITB', 'BIC', 'BICB','BIS', 'BISB', 'ADD', 'SUB', 'CLR', 'CLRB','COM', 'COMB', 'INC', 'INCB', 'DEC', 'DECB','NEG', 'NEGB', 'ADC', 'ADCB', 'SBC', 'SBCB','TST', 'TSTB', 'ROR', 'RORB', 'ROL', 'ROLB','ASR', 'ASRB', 'ASL', 'ASLB', 'JMP', 'SWAB','JSR', 'RTS', 'HALT','WAIT', 'RTI', 'IOT', 'RESET','EMT', 'TRAP', 'BR', 'BR', 'BNE', 'BEQ', 'BGE', 'BLT','BLE','BGT', 'BPL', 'BMI', 'BHI', 'BLOS', 'BVC', 'BVS','BHIS','BLO', 'NOP', 'CLC', '00243','.WORD','.WORD', 'MFPI','MFPD','MTPI', 'MTPD')); Own REGNAMES : Vector[8,Long] Preset(AAA( 'R0', 'R1', 'R2', 'R3', 'R4', 'R5', 'SP', 'PC') ); Global Routine OUTINST(p : Ref CELL) : Novalue = Begin If .p[cel_code] Eql PINLINE Then Begin If .p[cel_inl_comment] Then Print(AZ('\n;')); Print(AZ('%q\n'),.p[cel_inl_arg]); If .p[cel_inl_comment] Then Print(AZ('\n')) Else Begin NINLINES = .NINLINES+1; ! Q: I don't know why this number was chosen other than maybe to guarantee ! that there are no short branches over in-line code. ! ! A: indeed it is. CODESIZE = .CODESIZE - 129; FINRTNSIZE = .FINRTNSIZE - 129 End; Return End; ! display the instruction name Print(AZ('\t%s\t'),.PDP11PRT[.p[cel_code]]); ! and now handle the operands Case .OPERTYPE[.p[cel_code]] From LO_OPTYPE To HI_OPTYPE Of Set [ OPTYPE_NOP ]: 0; [ OPTYPE_ONE ]: OUTOPD(p[cel_src]); [ OPTYPE_TWO ]: Begin OUTOPD(p[cel_src]); OUTPUT(','); OUTOPD(p[cel_dst]) End; [ OPTYPE_BR ]: OUTOPD(p[cel_src]); [ OPTYPE_JSR ]: Begin Print(AZ('%s,'),.REGNAMES[.p[cel_src_reg]]); OUTOPD(p[cel_dst]) End; [ OPTYPE_RTS ]: Print(AZ('%s'),.REGNAMES[.p[cel_src_reg]]); [ OPTYPE_TRAP ]: PRint(AZ('%d'),.p[cel_src_disp]); [ OPTYPE_WORD ]: OUTNAMOFF(p[cel_src]); [ OPTYPE_CASE ]: Begin OUTNAMOFF(p[cel_src]); OUTPUT('-'); OUTNAMOFF(p[cel_dst]) End Tes; Print(AZ('\n')) End; Routine OUTCODE : Novalue = Begin Local CASEFLAG : Boolean, L : Ref CELL, CODEPTR : Ref CELL; ! if this is the first time here, generate a .TITLE, .IDENT ! as needed, select the code psect, and perform register equates. If Not .ALDON Then Begin Print(AZ('\t.TITLE %s\n\n'),.MODNAME); If .IDENTLEX Neqa 0 Then Begin Print(AZ('\t.IDENT /%s/\n\n'),IDENTLEX[tx_data]); FreeNode(.IDENTLEX); IDENTLEX = 0 End; OUTCSECT(PS_CODE); Incr I From 0 To 7 Do Print(AZ('\t%s = %d\n'),.REGNAMES[.I],.I); ALDON = TRUE End; ! make sure we are in the code psect OUTCSECT(PS_CODE); ! generate any debug entry information as needed. the ! information is the end-of-routine unique id label or a zero. If .swit_debug And Not .MODDONE And .CODENAME[4] Neq 0 Then Begin Print(AZ('\t')); OUTDLAB(.CODENAME[3]); Print(AZ('\n')); CODESIZE = .CODESIZE+1; FINRTNSIZE = .FINRTNSIZE+1 End; ! if any code was generated for this routine... (the only time not ! is for an empty module body) If .BRAK1[cel_next] Neq .BRAK2 Then Begin ! if this is a routine with a unique name then set to make the routine ! name as just a comment If .CODENAME[2] Gtr 0 Then OUTPUT(';'); Print(AZ('%s:\n'),.CODENAME[0]); If .CODENAME[3] Neq 0 Then Print(AZ('$%D:\n'),.CODENAME[3]) End; ! if this is the module body, generate code to load the stack If .MODDONE And .MAINDECL And .SSTKLEN Gtr 0 Then Begin Print(AZ('\tMOV\t#S$TK-2,SP\n')); Print(AZ('\tMOV\t#S$TK,$BREG\n')); CODESIZE = .CODESIZE+5; FINRTNSIZE = .FINRTNSIZE+5 End; ! loop, generating each instruction CASEFLAG = FALSE; CODEPTR = .BRAK1[cel_next]; Until .CODEPTR Eql .BRAK2 Do Begin Case .CODEPTR[cel_type] From LO_CELL_TYPE To HI_CELL_TYPE Of Set [Inrange]: 0; [CELL_CODE]: OUTINST(.CODEPTR); [CELL_LABEL]: Begin L = .CODEPTR[cel_next]; If .swit_i_d And .L[cel_type] Eql CELL_CODE And .L[cel_code] Eql PCASE Then Begin CASEFLAG = TRUE; OUTCSECT(PS_GLOBAL) End; OUTLAB(.CODEPTR); OUTPUT(':') End Tes; CODEPTR = .CODEPTR[cel_next]; If .CASEFLAG And Not .CODEPTR[cel_type] Eql CELL_CODE Then Begin CASEFLAG = FALSE; OUTCSECT(PS_CODE) End End; Print(AZ('\n')); ! generate any statistics If .swit_statistics And Not .flg_tty And .FINRTNSIZE Gtr 0 Then Print(AZ('%b%1m%s %d\n%e'),.CODENAME[0],.FINRTNSIZE); ! generate the debug end label If .swit_debug Then If .CODENAME[3] Neq 0 Then Print(AZ('$$%d:\n'),.CODENAME[2]) Else Print(AZ('$%s:\n'),.CODENAME[0]); If .FINRTNSIZE Gtr 0 Then Print(AZ('; ROUTINE SIZE: %d\n'),.FINRTNSIZE) End; Routine OUTLAB(LAB : Ref CELL) : Novalue = Begin Local S : Ref ST; S = .LAB[cel_lab_name]; Case .LAB[cel_lab_type] From LO_LAB_TYPE To HI_LAB_TYPE Of Set [LAB_ROUTINE]: Print(AZ('$%s'),Block[.S[st_name],nt_data]); [LAB_USER]: Begin OUTNAME(.S); S[st_lab_used] = TRUE End; [LAB_COMP]: Print(AZ('L%d'),.S) Tes End; Routine OUTNAME(S : Ref ST) : Novalue = Begin If .S[st_v_unique] And ONEOF(.S[st_code],S_LABEL,S_OWN,S_ROUTINE,S_GBL_ROUTINE,S_FORWARD) Then Print(AZ('$%d'),.S[st_unique]) Else Print(AZ('%s'),Block[.S[st_name],nt_data]) End; Routine OUTNAMOFF(OPRND : Ref ADRVARSTR) : Novalue = Begin Local N : Integer, S : Ref ST; N = .OPRND[adr_disp]; S = .OPRND[adr_name]; If .OPRND[adr_name] Gtr 1 Then Begin If .OPRND[adr_name_type] Eql NAME_NORMAL Then OUTNAME(.S) Else If .OPRND[adr_name_type] Eql NAME_LABEL Then OUTLAB(.S[cel_ref_ef]) Else Print(AZ('$TN')); If .N Eql 0 Then Return Else If .N Gtr 0 Then OUTPUT('+') Else OUTPUT('-'); Print(AZ('%d'),Abs(.N)) End Else If .OPRND[adr_type] Eql ADDR_IMMED Then Print(AZ('%d'),.N) Else Begin If .N Lss 0 Then OUTPUT ('-'); Print(AZ('%d'),Abs(.N)) End End; Routine OUTOPD(OPRND : Ref ADRVARSTR) : Novalue = Begin Local XMODE : Integer, R : Integer; R = .OPRND[adr_reg]; XMODE = .OPRND[adr_mode]; If .XMODE Then OUTPUT('@'); XMODE<0,1> = 0; If .XMODE Eql GENREG Then Print(AZ('%s'),.REGNAMES[.R]) Else If .R Neq PC Then Selectone .XMODE Of Set [AUTODECR]: Print(AZ('-(%s)'),.REGNAMES[.R]); [INDEXED]: Begin OUTNAMOFF(.OPRND); Print(AZ('(%s)'),.REGNAMES[.R]) End; [AUTOINCR]: Print(AZ('(%s)+'),.REGNAMES[.R]); Tes Else Begin If .XMODE Eql IMMEDIATE Then OUTPUT('#'); OUTNAMOFF(.OPRND) End End; Routine OUTNAMEDISP(S : Ref ST) : Novalue = Begin Local B : Ref ST, N; If .S[st_v_namexp] Then Begin B = .S[st_var_base]; N = .S[gt_disp]-.B[gt_disp]; If .N Neq 0 Then Print(AZ('%c%d'),If .N Gtr 0 Then '+' Else '-',Abs(.N)) End End; Routine OUTCSECT(X) : Novalue = Begin If .X Neq .curr_psect Then Begin curr_psect = .X; Print(AZ('\t.PSECT\t%p\n'),.psc_name[.X]) End End; Routine OUTPLIT(NAM : Ref ST,PP : Ref ST) : Novalue = Begin Local NL : Ref ST, LEX : Ref GT, NPAD : Integer; Routine ENDSEP : Novalue = Begin If .CNT Gtr 0 Then Begin CNT = 0; Print(AZ('\n')) End End; Routine OUTSEP : Novalue = Begin If .CNT Eql 0 Then Print(AZ('\t.WORD\t')) Else If .CNT Lss 3 Then Print(AZ(',')) Else Begin Print(AZ('\n\t.WORD\t')); CNT = 0 End; CNT = .CNT + 1 End; If .NAM Neqa 0 Then Begin If .NAM[st_v_counted] Then Print(AZ('\t.WORD\t%d\n'),.PP[pl_size]); NPAD = .NAM[st_var_size] - .PP[pl_size] * 2; OUTNAME(.NAM); Print(AZ(':')); CNT = 0 End; If .PP[pl_type] Eql T_PLIT Then Begin Do Begin If .PP[pl_count] Neq 1 Then Begin ENDSEP(); Print(AZ('\t.IRP\t%d\n'),.NL[pl_count]); OUTPLIT(0,.PP[pl_data]); Print(AZ('\t.ENDR\n')) End Else OUTPLIT(0,.PP[pl_data]); PP = .PP[pl_next] End While .PP Neqa 0 End Else Begin Case .PP[gt_type] From T_LITERAL To T_STRING Of Set [Inrange,Outrange]: 0; ! DELIMITER [T_LITERAL]: Begin OUTSEP(); Print(AZ('%d'),.PP[gt_disp]) End; [T_VARIABLE]: Begin PP = .PP[gt_disp]; OUTSEP(); OUTNAME(.PP); OUTNAMEDISP(.PP) End; [T_STRING]: Begin Print(AZ('\t.ASCII\t''%q''\n'),.PP); Print(AZ('\t.EVEN\n')) End Tes End; If .NAM Neqa 0 Then Begin If .CNT Gtr 0 Then Print(AZ('\n')); If .NPAD Gtr 0 Then Print(AZ('\t. = . + %d\n'),.NPAD) End End; Routine OUTSTORAGE(TYPE : Integer,REGION : Integer,MUSTBEPLIT : Boolean) : Novalue = Begin Local BYT : Integer, DOLABEL : Boolean, L : Ref GT, P : Ref ST, R : Ref ST; Label bbb; DOLABEL = TRUE; BYT = 0; ! loop for each symbol on purged list R = .PURGED; While (P = .R) Neqa 0 Do bbb: Begin ! skip if not the desired type, already printed, or not the right ! plit state R = .P[st_next]; If .P[st_code] Neq .TYPE Then Leave bbb; If .P[st_v_printed] Then Leave bbb; If .P[st_v_plit] Neq .MUSTBEPLIT Then Leave bbb; If .DOLABEL Then Begin OUTCSECT(.REGION); DOLABEL = FALSE End; L = .P[gt_len]; If .BYT And .L[gt_disp] Mod WRDSZ Eql 0 Then Begin Print(AZ('\t.EVEN\n')); BYT = 0 End; If .P[st_v_init] Then OUTPLIT(.P,.P[st_var_init]) Else Begin OUTNAME(.P); Print(AZ(':\t. = . + %d\n'),.P[st_var_size]) End; BYT = .BYT + .P[st_var_size]; If .P[st_v_plit] And .P[st_v_counted] Then BYT = .BYT + 2; P[st_v_printed] = TRUE End; If .BYT Then Print(AZ('\t.EVEN\n')); If .MODDONE And .MAINDECL And .REGION Eql PS_GLOBAL Then Begin If .DOLABEL Then OUTCSECT(PS_GLOBAL); !!! Print(AZ('%n:\t. = . + 2\n'),.LEXBREG) End End; Routine OUTGLBINDS : Novalue = Begin Local LEX : Ref GT, PUR : Ref ST; PUR = .PURGED; While .PUR Neqa 0 Do Begin If .PUR[st_code] Eql S_BIND And .PUR[st_v_gbl_bind] Then Begin Print(AZ('%n\t=\t'),.PUR); LEX = .PUR[st_bind_data]; If .LEX[gt_type] Eql T_LITERAL Then Print(AZ('%d'),.LEX[gt_disp]) Else Begin OUTNAME(.LEX); OUTNAMEDISP(.LEX) End; Print(AZ('\n\t.GLOBL\t%s\n'),Block[.PUR[st_name],nt_data]) End; PUR = .PUR[st_next] End End; Routine OUTVARS : Novalue = Begin Local SAVPTR : Ref ST; Bind OUTL=PLIT( LEXMUL, LEXDIV, LEXMOD, LEXROT, LEXSHIFT, LXSAV2, LXSAV3, LXSAV4, LXSAV5, LXSIGL, LXSIG1, LXENAB, LXSIGV, LXSIGR, LXINT612, LXE612, LXX612, LXY612 ) : Vector; Print(AZ('\n')); ! output own storage OUTSTORAGE(S_OWN,PS_OWN,FALSE); If .NEXTOWN Then NEXTOWN = .NEXTOWN+1; ! output global storage OUTSTORAGE(S_GLOBAL,PS_GLOBAL,FALSE); If .NEXTGLOBAL Then NEXTGLOBAL = .NEXTGLOBAL+1; ! output plits OUTSTORAGE(S_OWN,PS_OWN,TRUE); OUTSTORAGE(S_GLOBAL,PS_PLIT,TRUE); ! output global binds OUTGLBINDS(); SAVPTR = .PURGED; While .SAVPTR Neqa 0 Do Begin If ONEOF(.SAVPTR[st_code],S_EXTERNAL,S_GLOBAL,S_GBL_ROUTINE) Then If Not (.SAVPTR[st_v_listed_external] Or .SAVPTR[st_v_plit] Or .SAVPTR[st_v_namexp]) Then Begin Print(AZ('\t.GLOBL\t%s\n'),Block[.SAVPTR[st_name],nt_data]); SAVPTR[st_v_listed_external] = TRUE End; SAVPTR = .SAVPTR[st_next] End; If .PURGED Neqa 0 Then Print(AZ('\n')); If .MODDONE Then Begin DATASIZE = .DATASIZE+(.NEXTOWN+.NEXTGLOBAL)/2; Decr I From .OUTL[-1]-1 To 0 Do Begin SAVPTR = ..OUTL[.I]; If .SAVPTR[st_v_listed_external] Then Begin Print(AZ('\t.GLOBL\t%s\n'),Block[.SAVPTR[st_name],nt_data]); SAVPTR[st_v_listed_external] = FALSE End End; !!! If .MAINDECL Then !!! Print(AZ('\t.GLOBL\t%s\n'),Block[.LEXBREG[st_name],nt_data]); End; If .MODDONE And .MAINDECL Then Begin If .SSTKLEN Gtr 0 Then Begin Print(AZ('\t.ASECT\n')); Print(AZ('\t. = 400\n')); Print(AZ('\t. = . + %d\n'),2 * .SSTKLEN); Print(AZ('S$TK\t= . - 2\n\n')); DATASIZE = .DATASIZE+.SSTKLEN End End End; Routine OUTDLAB(L : Integer) : Novalue = Begin If .L Eql 0 Then Print(AZ('+0')) Else Print(AZ('D$%d'),.L) End; Routine PLACENXTDLAB(L : Ref GT) : Novalue = Begin DLABEL = .L[st_unique]; OUTDLAB(.DLABEL); OUTPUT(':') End; Routine OUTDNUM(X : Integer) : Novalue = Begin Print(AZ(',%d'),.X<0,15>) End; Routine ODADR(X) : Novalue = Begin OUTPUT(','); OUTNAME(.X) End; ! calculate the debugger data type ! ! 0 unrecognized ! 1 module name ! 2 routine ! 3 own ! 4 global ! 5 local ! 6 local in a register ! 7 register ! 8 bind to name/literal ! 9 label ! 10 unused ! 11 linkage ! 12 structure ! 13 macro ! 14 bind to expression ! 15 bind to expression in a register ! 16 formal ! 17 formal in a register Routine DTYPE(L : Ref GT) = Begin Local X : Ref GT, N : Ref GT; Selectone .L[st_code] Of Set [S_ROUTINE]: Return 2; [S_GBL_ROUTINE]: Return 2; [S_OWN]: Return 3; [S_GLOBAL]: Return (If .L[st_v_plit] Then 0 Else 4); [S_LOCAL]: Return 5; [S_REGISTER]: Return 7; [S_BIND]: Begin X = .L[st_bind_data]; If .X[gt_type] Eql T_LITERAL Then Return 0; ! USED TO BE 8 If .X[gt_type] Eql T_NODE Then Return 14; If .X[st_v_namexp] Then Return (If .X[gt_reg] Eql SP Then DTYPE(.X)+(-1)^32 Else 8); Return 0 End; [S_LABEL]: Begin If Not .L[st_lab_used] Then Return 0; If .Block[.L[st_name],nt_data] Eql '$' Then Return 0; Return 9 End; [S_FORMAL]: Return 16; [Otherwise]: Return 0 Tes End; Routine OUTDEBSYMTAB : Novalue = Begin Local L : Ref ST, M : Ref ST, NAME : Ref GT, T : Ref GT, LT : Ref GT, PC; Label bbb; Routine BITCOUNT(N : Integer) = ! COUNT THE ONE BITS Begin Local COUNT : Integer; COUNT = 0; While .N Neq 0 Do Begin If .N Then COUNT = .COUNT+1; N = .N^(-1) End; Return .COUNT End; If Not .swit_debug Then Return; M = L = .PURGED; PC = -1; While .L Neqa 0 Do Begin T = DTYPE(.L); If .T Neq 0 Then bbb: Begin If .L[st_v_namexp] Or Not .L[st_v_debug] Then Leave bbb; If .T Lss 0 Then ! LEFT HALF SET BY DTYPE L = .L[st_bind_data]; If .PC Neq 0 Then Begin OUTCSECT(PS_DEBUG); PC = 0 End; Print(AZ('\n')); PLACENXTDLAB(.M); Print(AZ('\t')); Selectone .T Of Set [5]: If .L[st_var_reg_index] Neq SP Then T = 6; [14]: If .L[st_var_reg_index] Eql SP Then T = 15; [16]: If .L[gt_reg] Neq SP Then T = 17 Tes; NAME = .M[st_name]; OUTDLAB(.NAME[nt_debug]); NAME[nt_debug] = .DLABEL; OUTDNUM(.M[st_unique]); OUTDNUM(.T); Print(AZ('\n\t')); If .MODDONE Then OUTPUT('0') Else OUTDLAB(Abs(.CODENAME[3])); Case .T From 0 To 17 Of Set [Inrange]: 0; [2]: Begin ODADR(.L); Print(AZ('\n\t$')); OUTNAME(.L); OUTPUT('-'); OUTNAME(.L); OUTDNUM(.L[st_var_reg_save]); OUTDNUM(.Block[.L[st_var_linkage],st_lnk_type]) End; [3]: ! own Begin ODADR(.L); Print(AZ('\n\t%d'),.L[st_var_size]) End; [4]: ! global Begin Print(AZ(',%s'),Block[.L[st_name],nt_data]); Print(AZ('\n\t%d'),.L[st_var_size]) End; [5]: ! stack local Begin T = .CODENAME[4]; If .T Neq 0 Then T = BITCOUNT(.T[st_var_reg_save]); ! NOTE TO WHOEVER PUT IN THAT CODE FOR ! THE $SAV-N PC WORD: DEBSW *FORCES* ! INLINE REGISTER SAVING. -TL OUTDNUM(.L[gt_disp]-(.T+.VTN)*2); OUTDNUM(0); Print(AZ('\n\t%d'),.L[st_var_size]) End; [6]: ! register local OUTDNUM(.L[st_var_reg_index]); [7]: ! register OUTDNUM(.L[st_var_reg_index]); [8]: ! simple bind Begin LT = .L[st_bind_data]; If .LT[gt_type] Eql T_LITERAL Then OUTDNUM(.LT[gt_disp]) Else Begin OUTPUT(','); OUTNAME(.LT); OUTNAMEDISP(.LT) End End; [9]: ! label ODADR(.L); [14]: ! dynamic bind in a register OUTDNUM(.L[st_var_reg_index]); [15]: ! dynamic bind in a stack temporary Begin T = .CODENAME[4]; If .T Neq 0 Then T = BITCOUNT(.T[st_var_reg_save]); OUTDNUM(.L[gt_disp]-(.T+.VTN)*2); End; [16]: ! stack formal OUTDNUM(.L[gt_disp]); [17]: ! register formal OUTDNUM(.L[st_var_reg_index]) Tes End; M = L = .M[st_next] End End; Routine OUTDEBNAMTAB : Novalue = Begin Local L : Ref ST, PC : Boolean; If Not .MODDONE Then Return; If Not .swit_debug Then Return; PC = TRUE; Print(AZ('\n')); Incr I From 0 To HTSIZE-1 Do Begin L = .HT_NAME[.I]; While .L Neqa 0 Do Begin If .L[nt_debug] Neq 0 Then Begin If .PC Then Begin Print(AZ('\n')); If .swit_list And Not .flg_tty Then ! MUST NOT CROSS PAGE If .NLINES Gtr 44 Then PAGE(); OUTCSECT(PS_DEBUG); PC = FALSE; Print(AZ('\n.MACRO $NTE X,Y\n')); Print(AZ('\t.RAD50 /X/\n')); Print(AZ('\t.WORD Y\n')); Print(AZ('\t.ENDM\n\n')); Print(AZ('$NMTAB:')) End; Print(AZ('\n\t$NTE\t')); Print(AZ('^''%s'''),.l); OUTPUT(','); OUTDLAB(.L[nt_debug]); L[nt_debug] = 0 End; L = .L[nt_next] End End End; Global Routine FINALDRIV : Novalue = Begin Local SAVLST : Boolean; FINAL(); SAVLST = .swit_list; swit_list = TRUE; !ALWAYS LIST CODE OUTCODE(); ERASELIST(.NLHEAD); ERASEDET(.NLHEAD); ERASELIST(.BRAK1); ERASEDET(.BRAK1); OUTVARS(); OUTDEBSYMTAB(); OUTDEBNAMTAB(); swit_list = .SAVLST End; End Eludom