Initial commit

This commit is contained in:
kenr 2021-02-15 21:10:40 -08:00
commit 528f2430ca
215 changed files with 27458 additions and 0 deletions

BIN
.DS_Store vendored Normal file

Binary file not shown.

BIN
850640/.DS_Store vendored Normal file

Binary file not shown.

1
850640/850640-44 Normal file

File diff suppressed because one or more lines are too long

225
850640/850640-44.si Normal file
View File

@ -0,0 +1,225 @@
_FIN
_JOB
* SEMI-AUTOMATIC TYPEWRITER TEST - W BUFFER/CHANNEL A
*
* J.M. FLETCHER
*
* CATALOG NUMBER
*
TYPE EQU 900
RORG 0200
DX EQU 1*(TYPE=9300)
IX EQU 2*(TYPE=900)+1*(TYPE=9300)
PROC 1
A9300 NAME
$INST FORM 24
P PROC 1
$BRTW NAME 02014000
$CLR NAME 04037711
INST P(0)
END
P PROC 1
$BPT NAME 022400
$SWTC FORM 18,6
SWTC P(0),1*/(6-P(1))
END
P PROC 1
$LSH NAME 060
$SHFT FORM 9,15
SHFT P(0),P(1)++04000
END
P PROC 1
$MIN NAME 071
$MIW NAME 030
$WIM NAME 032
$IOIN FORM 3,6,15
IOIN P(2),P(0),P(1)
END
END
P PROC 1
DIS NAME 0200000
TOP NAME 0214000
TYP1 NAME 0202041
TYP2 NAME 0202241
TYP3 NAME 0202441
TYP4 NAME 0202641
RKB1 NAME 0202001
RKB4 NAME 0202601
READ FORM 24
READ P(0)
END
DO TYPE=9300
A9300
INIT DIR DISABLE INTERRUPT
LDA RCVR SET-UP RECOVERY
STA 1
CLR
HLT ALLOW TYPEWRITER ID INSERT TO B-REG
STB DVCE STORE ID
BRM MODE CHECK ON/OFF-LINE MODE
BRU $+4
TEST TOP TERMINATE OUTPUT
BRTW BUFFER READY
BRU $-1 NO
BPT 1
BRU EKOL INITIATE LINE ECHO TEST
BPT 2
BRU EKO4 INITIATE 4 CHARACTER ECHO TEST
BPT 3
BRU CHAR INITIATE ALL CHARACTER PRINT-OUT
BRU TEST+3 LOOP
MODE HLT MODE TEST SUBROUTINE
SKN DVCE IS TTY TEH TEST SPECIMEN?
BRR MODE NO-CONTINUE PROGRAM
CORR SKS 010001 YES- IS IT ON-LINE?
BRU $+2 NO-PROCEED TO HALT
BRR MODE YES-CONTINUE PROGRAM
HLT
NOP DISPLAY IN C-REG
BRU CORR TEST AGAIN
EKOL RKB1 SELECT KEYBOARD - 1 CHAR/WORD
BRM MODE CHECK MODE
WIM TERM STORE TERMINATING CHARACTER
DIS YES - DISCONNECT
BRTW BUFFER READY
BRU $-1 NO
TYP1 SELECT PRINTER - 1 CHAR/WORD
MIW CRET EXECUTE CARRIAGE RETURN
TOP TERMINATE OUTPUT
CLR
STB WCOUNT CLEAR WORD COUNT
LDA =0177653 USE TO SET INDEX REG FOR OUTPUT TABLE
STA FILL MAXIMUM OF 86 ENTRIES
BRTW
BRU $-1 NO
RKB1 SELECT KEYBOARD - 1 CHAR/WORD
NEXT LDX =0177774,DX
BRM MODE CHECK MODE
WIM HOLD STORE SINGLE CHARACTER
LDB HOLD
LSH 18 LEFT JUSTIFY
LDA TEMP
LSH 6 ASSEMBLE MOST RECENT CHARACTER
STA TEMP RE-STORE PARTIAL WORD
LDB =077 LOAD MASK
LDA TERM LOAD TERMINATING CHARACTER
SKM HOLD IS LAST INPUT TERMINATING CHARACTER?
BRU CHEK NO
FULL BRX COMP,DX YES-HAS A 4 CHAR WORD BEEN ASSEMBLED?
STX TYPIX,DX
LDA =040000000 YES
STA FLAG SET END FLAG
STOR MIN WCOUNT INCREMENT WORD COUNT
LDX FILL,DX SET INDEX FOR OUTPUT TABLE ENTRY
LDA TEMP LOAD MOST RECENTLY ASSEMBLED WORD
STA POUT+85,IX STORE IN OUTPUT TABLE
MIN FILL INCREMENT INDEX
SKN FLAG END FLAG SET?
BRU NEXT NO-ASSEMBLE NEXT WORD
CLR YES
STA FLAG CLEAR END FLAG
DIS YES - DISCONNECT
BRTW BUF
BRU $-1 NO
LINRPT LDA =0
SUB WCOUNT INDEX SETTING DETERMINED BY NUMBER
ADD =0200000 SET INCREMENT FOR 9300
STA TEMP OF ENTRIES IN OUTPUT TABLE
LDX TEMP,DX
LDA WCOUNT SET UP MIW FOR INDEXING THRU OUTPUT
ADD FIXMIW TABLE OF KNOWN LENGTH
STA $+8
LDA =1 SET PRINT COUNT
LDB =0177 LOAD MASK
SKM WCOUNT TOTAL OF 4 OR LESS CHARACTERS ?
BRU $+2 NO - SET-UP NORMAL PRINT
BRU LAST+1 YES - SET-UP SPECIAL PRINT
PRNT EXU TPFORM+3 SELECT PRINTER - 4 CHAR/WORD
BRM MODE CHECK MODE
DATA 0 RESERVED FOR MIW
BPT 4 BREAKPOINT 4 SET?
HLT YES
BPT 1 NO-BREAKPOINT 1 SET?
BRU $+4 YES
BPT 3 NO-BREAKPOINT 3 SET?
BRU $+10 YES
BRU TEST NO-RETURN TO TEST SELECT LOOP
ADD =1 INCREMENT PRINT COUNT
LDB =0177 LOAD MASK
SKM WCOUNT ONLY 1 WORD REMAINING ?
BRU $+2 NO
BRU LAST YES
BRX PRNT+1,DX ALL ENTRIES NOT TYPED-TYPE NEXT WORD
BRM TOUT
BRU LINRPT ALL ENTRIES TYPED-REPEAT
BRX PRNT+1,DX TYPE NEXT WORD
BRM TOUT
BRU SCHIX REPEAT
LAST BRM TOUT PROCESS LAST ENTRY
LDX TYPIX,DX
EXU TPFORM+3,IX SELECT PRINTER - 1,2,3, CHAR/WORD
LDX =0177777,DX
BRU PRNT+1
CHEK BRX NEXT+1,DX WORD INCOMPLETE - FETCH NEXT CHAR
BRU STOR STORE IN OUTPUT TABLE
COMP STX TYPIX,DX
LDA TEMP LEFT JUSTIFY FINAL WORD
LSH 6
BRX $-1,DX
STA TEMP
BRU FULL+2
EKO4 RKB4 SELECT KEYBOARD - 4 CHAR/WORD
BRM MODE CHECK MODE
WIM POUT STORE 4 CHAR INPUT
DIS YES - DISCONNECT
BRTW
BRU $-1
LDX =0,DX CLEAR INDEX REG
LDA FIXMIW SET UP MIW
BRU LINRPT+7
CHAR LDX =0177760,DX
LDA CARTAB+16,IX TRANSFER CHARACTER TABLE TO
STA POUT+16,IX OUTPUT TABLE
BRX CHAR+1,DX
SCHIX LDX =0177760,DX SET INDEX FOR ALL CHAR TYPE-POUT
LDA =16 SET-UP MIW
BRU LINRPT+6
TOUT HLT
TOP
BRTW
BRU $-1
BRR TOUT
TPFORM TYP1 PRINTER EOM TABLE
TYP2
TYP3
TYP4
TYPIX DATA 0
RCVR BRU INIT
DVCE DATA 0 PERIPHERAL ID
TERM DATA 0 TERMINATING CHARACTER
CRET DATA 052000000 CARRIAGE RETURN
WCOUNT DATA 0 WORD COUNT
FILL DATA 0
HOLD DATA 0
TEMP DATA 0
FLAG DATA 0
POUT RES 86 OUTPUT TABLE
FIXMIW MIW POUT,IX PRINTOUT COMMAND TO BE ALTERED
CARTAB DATA 052535455 ALL CHARACTERS TABLE
DATA 056576061
DATA 062636465
DATA 066677071
DATA 072737475
DATA 076770001
DATA 002030405
DATA 006071011
DATA 012131415
DATA 016172021
DATA 022232425
DATA 026273031
DATA 032333435
DATA 036374041
DATA 042434445
DATA 046475051
END INIT
*EOF*

1
850640/850640-84 Normal file
View File

@ -0,0 +1 @@
Ă@CC@@@F@@C@g@p@C@Ch@Fp@RF8@Cp@F@@ @@ @C@F@^F@R@@@XF@C @@@@@@@@@@@@@@@X@@O@Ch@@X @WEh@@@@O@^F@@EF@ Ĺh@@pCh@Ch@Ep@Fp@Eh@RE @Ch@Cp@@CCT@|@F@@sC@8@@QFEX@C@@ 8@FCh@@Fp@L8@@h@@@@Ch@Cp@4@EEh@EX@@ C,@EF@EF8@E@@XĂ]kT@@R@pCh@s@C@@@@CpQXR@ @Q @@@I@@[@@Cv@@C@ @@@@EXQER@@XERQ2k[@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@d@d@ @@@@Ă]^X@@@@@@@@@XRCR@@@@@@a@Q @s@CCpTpF@Ch@@h@FXRChF8@R J]^@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@d@d@ @@@@Ă]2QppWF8@FChWhFpR@@CnCpC8OpFCChXFTpWhEnFEXX@ks@CChX@@@@@CEpF/@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@d@d@ @@@@Ă]ubCE TEhFEChWWpTEhE/ChCpFFhF@T@CT@C*XXR@@@@@ @@@@@@C^@@C&@EhFFhFp/@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@d@d@ @@@@ Ă]zvC @T@C#@C)CXF@CCXF@CXFORXF@C,@;C8OpWF8@FC2ChW@y@XR]@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@d@d@ @@@@Ă]*C8C@@@@@CzFpE/@CFIWpF@h)@FIpFJ@C @@@@@Q @@@EF@a@Ra@Ta@a@@@@g1 @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@d@d@ @@@@<08>%pJ@@@@@@@@@@*@@@@@@@@@@@@@@@@@@@@@@@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@d@d@ @@@@Ă]/uE/Q*k,mn/p12s4uv78yz;|=>@CEFIJ L OQRTWX[]^ ab#d%&gh)@O>k@O|@@@ @@@@@@@@@@@@@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@d@d@ @@@@Ŕu8%@F@@@O@Op@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@d@d@ @@@@Ř%QF @@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@d@d@ @@@@

6
850640/READ.ME Normal file
View File

@ -0,0 +1,6 @@
85064OAA B3 9-SERIES SEMI-AUTOMATIC TYPEWRITER TEST (SATT)
set break point 1 to echo a single character input in infinte loop
set break point 2 to echo 4 character input in infinite loop
set break point 3 to type all 64 characters in infinite loop

BIN
850640/test/.DS_Store vendored Normal file

Binary file not shown.

1
850640/test/850640-44 Normal file

File diff suppressed because one or more lines are too long

17
850640/ttytst Normal file
View File

@ -0,0 +1,17 @@
; command file to run tty test (850640-84)
;
;
; usage: do ttytst
; set bp and type c to continue after halt 207
; set break point 1 to echo a single character input in infinte loop
; set break point 2 to echo 4 character input in infinite loop
; set break point 3 to type all 64 characters in infinite loop
;
set log /users/admin/sds/simlog
set debug /users/admin/sds/simdebug
att cr 850640-84
set cpu history=2000
boot cr

1
850644/850644-44 Normal file
View File

@ -0,0 +1 @@
<EFBFBD>2IE, 7EOh4FO&)WF@yFEkO)2[Xb24dOyQvE FWyvTsOvd@E;Q[y%vTsOR)7J@TOysO#T7@OysE[y)##WO2b2@@@@OyvJ@EOR)4O%@RWyRQ2OX#sW<73>I4)2s)sO[y)2s)sOQTTRQ2Os)@y%@C@CC@O2sQWy#&QT#&QTO&d@@@@@CF@@C@TQsQ&@@@@@@@@&@@C vO#TQO#2XFCO)2XJvTsW QvO2bQW&)<13>yzbR)47 s sEJIX#sO24RW%vTsO2b%Oy%vW%T%s[y#&QTO&)Od%W#&QTW)##W@@@@WyX#s [y%T%sJ[y&)bO#TRWgO2bd[yg@IO2bWWyR)477s[y)#&&gÊ/O2sRO)#gy)#gW)#&&gWy7s %v2OR)dWgs8& gR&)dFIJE@ gsOgy@CFO%T@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Å*@pk)yL)8hs*48hs*8Qs*J4nF*E E JO WFFg%  EJ W^&^%FJ;8 X kmp ;@Q hs*vnF]F71 a^#|p8%1)EpQIFab7EpQd1*JQ*%1*ÅWm8Q2[k[   v |  RRa&pL4]m]amp >bQk d;^1mOF1*@[/a/pa @@%XF @Xbn2g g %&# gdIaEX@JE @&Ta L)@ XQRJ@ IhÅpQ F@ X8L@2@4&T2sp&u)#&vpp%Tp)&)T2p42Jv&)Tp&4%snp4z^]%WQsup&pv&)Tp&4%sp#22p& u@@I#a*@@QCT @%hF JLI@T|h&|F,E4JTy*mE g |%|E]v|E)*ELJTy* , T@ WX*@1pu@@I%a*288by W C 2maRkLgam R)7  2ma &I*zd8by Wam R)%#R*g R)a h#&#am R)dI,)p@R;C@&Fh@JL @ Å[,[22@nQLs8LkXy8Q*hy8@8Jyh8[T*2bp @XT*TTvLF,EL &vLI,Lz%*EJ[)4Fu@@&|Fu@@&>F*@I| @ [2@kT*h*XT*1sI8[T*XLkX2|[p[@)pvdW2bÅy[gpp%&pR4)p))&)1&@XQd@,vsvXXXXXXXI J48J44sTyR 8L TFdy)T||JTEQ h @  b@7 4X@I]ab@@ C F#^C@@gF4 h )@ 2 @ ,v ;L,y);LLLLLÅ*LLvET8,mILE*QJL @ X8 @; u ^^2bgpp#&QTp)#&[pvTpg)2%s8F [#O@hRsXRJLkL*48[T*]@[2@h^nXE8T*1sI8[T*bOL T@ X8X@  *@v u@In @R;Å>EC@zhC*y/a*h@CE @d>F;@y%XF^spI42J&*n>^ J L@C@ gLXJ#@Ed2CbhpTCp2*L@ pL%J#@F2CIbhpFCp2h*L@ T@pLJ#@C2C 2hp@1LapsL*L@ R L8Å J#@@L@=apsp*L@ 7 #J#@ LC2hp Lapu4*L@ T# gJ#@Fd2C2hpap7@*L@ ]# 2J#@hC]Rhp1ap7*L@ WC %J#@@L@C@ ^Q/h ;@ @74)>p@g8 @Cd@ /]JI @ IXCO@ ChE C8CLL@@Ra#nJbX@gp  @@s2@ @E @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ØW%n@@F@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

15
850644/READ.ME Normal file
View File

@ -0,0 +1,15 @@
850644 9-SERIES BINARY INPUT-BASIC PAPER TAPE LOADER
AUTHOR: XEROX
ABSTRACT:
TO LOAD RELOCATABLE OR A8S0LUTE OBJECT PROGRAMS PRODUCED BY SYMBOL OR HETA-SYMBOL ON PAPER TAPE. AND TO LOAD THE "STANDARD CONSTANTS. ' ,
COMMENTS:
SIZE 79 DECIMAL. CONFIGURATION: ANY XDS 900 SERIES COMPUTER WITH A PAPER TAPE READER.
850644-44 is a compressed source file for the loader.
You can uncompress it to obtain Hollerith coded card images using the recon program, 850647-84.
You can then assemble the Hollerith coded images with Symbol using the symbol/sym command file.
This file is included in the kit as an example to experiment with the SDS simulator.

1
850645/850645-44 Normal file

File diff suppressed because one or more lines are too long

1
850645/850645-84 Normal file
View File

@ -0,0 +1 @@
C@CC@@@F@@C@g@I@ py))FFk@I@ C2py))EvIFXEy@I@@I@IF Ezy @C8@@@C@@^F@@QF@@O@@X @Eh@WWp@@kb@@EX@@8@@W; @@IĂ@CC@@@F@@C@g@p@C@Ch@Fp@RF8@Cp@F@@ @@ @C@F@^F@R@@@XF@C @@@@@@@@@@@@@@@X@@O@Ch@@X @WEh@@@@O@^F@@EF@ Ĺh@@pCh@Ch@Ep@Fp@Eh@RE @Ch@Cp@@CCT@|@F@@sC@8@@QFEX@C@@ 8@FCh@@Fp@L8@@h@@@@Ch@Cp@4@EEh@EX@@ C,@EF@EF8@E@@XĂ]nn;h4R#T)pp @>@@@^@I@Cp>h]4^Jp^sEh^Cp^n@@IIII ^QCh^&s@CCh^hXWCXXgp^% 1/@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă][8h^E@]7@h^8Cp^&p^)p^kX]4@yEX^/@1X^@hR^X@@d@&X^@@W;=C8^p^ ^QCh^7O@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]y=kp^nX^@a@@@@@@yp^@@@I@@I^@7@^Ch^/@Wp^*p^,^E@@@@@@]Lp^&@@@@@@@@@yg>X@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]|WC@@@@@@W@ @WJ@@W F@WJ@^F^ @W@@^|EX^/@W>pWh^E@^z@W@Xp^;JkW@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]8^W[@]4@W*p^)p^kX]4@y^Wp^/h^8Wbp^ECh^yCh^pCh^1Ch^;EX^p@X pWFp@ ]8X]4@WsX]v@W>@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]/WsEX^1@W>Ch^1EX^y@W>^Wp^8h^/WyCh^p@Ws@ChWF8@CCh^%p]4F8@FX]y@XI@@@C@@C@WE ]vX^E>mg@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă];;X @XFCh^Ch^#p^WCh^XpW ^8^|^XF@^F^XEX^@XCh^XFp@L8^Xh^@W@@@@@EWCpWh^@^7O@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]11X#@Wp]4Ch^;@W@@@@p^WCh^X^%L],p^#h]4Cp^;]y@X|pXEh^& ^QEX^/@X7@Xy@@RRRRCh^&=1@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă] X;@pXEh^& ^QCh^8pX ^Op^ChXp^bCh^[pX^FC8^h]4F8@X^E@@Q^#F@^#WhXC4^[F^[;@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]av^pX^LEh^& ^RCh^dF@^#p^Ch^]4^]EX^^@8h^&EX^a@d@gh^gEX^ @Cp^ ]|Eh^Ch^@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă] ykX]|@4 ]|Ch^F@^d4^d8];C,^dF^d4^] ^@p^@h^&EX^a@=X@]Th^gEX^ @X@]TC,^d@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]=[CF^dF^]^FWh^bF8@p^bFF@^#@@@EX^#@]p^hX^dp^dCh^hEXg@@@@Cp^ ^QEh^ ^QCh^4^] ^=7=@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă] J[p^Ep]7Eh^XCh^Xp^#E ]7Ch^#X]4EXg^Xh^%F8@WCp^^Wp@ ]=^LEh^& ^QCh^dWh@Cp^ F8@ ]7Wu@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă],TsCh^p]4F8@FCh^8Wp@@Wh@^EX^^L]aL]%XEEX^^@[nX@@[p^dEX^ @[F^*@]EX^ @[F@^)F^y4/@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]|y[ p^dp^Wh@h@p@L ^QCh^4^Ch^ ^Ch^[Wp@ ^Qp^[C,^p^ ^QX]4@]@[Qp^dCh^4^ ^Q1>@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă][#^E@[ p^dp^CWh@h@p@L ^Q4^C,^@]Wp@X@@[vEX^ @]@F^,h@@]@EX^ @]@8^CF^yp^|^^@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]gp[;p^dh@Ch^Fp@ ]>Fp@OCh^^F@^k@;@@@@^Cp^[Ch^h^Ep^W@@@@Wp^[W@@@Wp]4EX^^p^L*==/@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă] yQ8@^L@WEEW;=C8^p^nX^@Jp^X^h@@@F@@FCh^n^np^h^[h@@p@h^F8@np^dh@EX^^]>^@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă];Xk@/X@F^)@]h^mF8@hQp@p^Lh@X@F^kp^m^mF8@Ch^F^mWp@ ]>p^dh@p^Fp@ ]>^8nmk@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]by]CX]E@]@@@@Ch^Wp@ ]p^h@E]Ep^mX]4@F@^m^mp^TX]E@]LEX^@ ]Ch^4^] ]>Fp@Ou/>@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]& ][Ch^^Wp@ ]>p^@@@v@@=@@=@@XF@@])@@=@@=@@XFp^dCh^g@]@@@@%@@%@@X,@@XF@@XF@@XF7@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă] ]s@@XF@@@@@@@@@@@@@C@@@@@@@@@@@@ @C@O8@@8|@@8@@XE@@@@@ @@@@O|@O;@Oz@8@O4 @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]%n^ @X@@@@@@@@>@@@@@@C C|@@@@@@@; @W@@X@@X@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@^^@C8@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]z|^#@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@;@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@OO@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]^;@@@@@@@@@@W@@@F^4^Ch^[Fp@O ]z@@E@aT^[F^[E ]u^E@R@Q @@@OE^JJJ*Eu&@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ŕu2@d22%WJT2*JJJ@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ř%sX @@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

6
850645/READ.ME Normal file
View File

@ -0,0 +1,6 @@
850645 9-SERIES UNIVERSAL LOADER
AUTHOR: XEROX
ABSTRACT:
TO LOAD ONE OR MORE PROGRAMS PRODUCED BY SYMBOL OR META-SYMBOL AND PRESENTED TO THE LOADER ON EITHER PUNCHED CARDS OR PAPER TAPE. THIS LOADER HAS ESSENTIALLY THE SAME CAPABILITIES AS THE XDS MONARCH LOADER BUT IT FUNCTIONS INDEPENDENTLY OF MONARCH.
COMMENTS:
SIZE 664 DECIMAL. ASSEMBLY LANGUAGE USED: SYMBOL. CONFIGUFIATION: ANY XDS 900 SERIES COMPUTER WITH A CARD READER AND/OR PHOTO READER AND A TYPEWRITER. LOADER EXISTS ON CARDS AND PAPER TAPE AND LOADS PROGRAMS WHICH EXIST EITHER ON CARDS OR PAPER TAPE.

1
850647/850647-84 Normal file

File diff suppressed because one or more lines are too long

29
850647/READ.ME Normal file
View File

@ -0,0 +1,29 @@
850647 900-SERIES ENCODED TO SYMBOLIC RECONSTRUCTOR(RECON)
AUTHOR: XEROX
ABSTRACT:
TO RECONSTRUCT FROM AN ENCODED REPRESENTATION OF A PROGRAM ON PAPER TAPE, CARDS OR MAGNETIC TAPE A SYMBOLIC REPRESENTATION OF THE PROGRAM ON CARDS. PAPER TAPE OR MAGNETIC TAPE.
COMMENTS:
SOURCE LANGUAGE: META-SYMBOL. SIZE: 1019 DECIMAL. CONFlGURATION: ANY XDS 900 SERIES COMPUTER WITH AT LEAST 4K WORDS OF MEMORY AND A CARD READER, OR PAPER TAPE READER, OR MAGNETIC TAPE UNIT AND CARD PUNCH OR PAPER TAPE PUNCH OR MAGNETIC TAPE UNIT. BINARY ALSO AVAILABLE ON MONARCH SYSTEM TAPES.
; usage: do recon file
; The program will hang waiting for typewriter input command specifying
; devices.
;
; Type ^ followed by two characters to specify input and
; output devices. Characters may be C, P or M, to specify
; card, paper tape or magnetic tape. Type / to restart entire
; command to correct an error.
;
; Magnetic tape output is on mt2. To list output on mag tape 2; use
; sds_listtape mt2.
;
; Program returns to 1113 for another ^command.
;
; For example, tyoe ^CMc/r - input from card reader, output on mt2
;
; Test with:
; do recon 850644-44
; type: ^CM
;

36
850647/recon Normal file
View File

@ -0,0 +1,36 @@
; recon - command file to translate encoded to symbolic
; using 850647-84
;
;
; usage: do recon file
; The program will hang waiting for typewriter input specifying
; devices.
; Type ^(057) followed by two characters to specify first input and
; second, output device. Characters may be C, P or M, to specify
; card, paper tape or magnetic tape. Restart entire command by
; typing / to correct error.
;
; Magnetic tape output is on mt2
;
; For example, tyoe ^CMc/r - input from card reader, output on mt2
;
; Test with:
; do recon 850644-44
; type: ^CM
;
; Program returns to 1113 for another ^command
; To list output on mag tape 2; listtape mt2
set log /users/admin/sds/simlog
set debug /users/admin/sds/simdebug
! cat 850647/850647-84 %1 > bootdeck
att cr bootdeck
att cp card-punch
att mt2 mt2
set cpu history=20000
boot cr

BIN
850648/.DS_Store vendored Normal file

Binary file not shown.

86
850648/850648-34.lo Normal file
View File

@ -0,0 +1,86 @@
06000000 1 MMO OPD 06000000
00000000 2 X0 EQU 0
00000002 3 X2 EQU 2
00000003 4 CW EQU 3
00000000 5 COUNT EQU 0
00000002 6 LOC EQU 2
00000003 7 LAST EQU 3
00000001 8 U EQU 1
00000000 9 CH EQU 0
07600 10 AORG 07600
07600 11 ORG RES 0
00000001 12 BIAS EQU 1
00007601 13 B EQU ORG+BIAS
07600 0 32 0 00003 14 WIM 3
07601 0 32 0 00004 15 WIM 4
07602 0 01 0 00002 16 BRU 2 04
07603 0 60 0 00002 17 SKR 2
07604 0 32 0 00047 18 WIM 047
19 *BACKWARDS BOOTSTRAP
20 *BOOTSTRAP LOOP READS NEXT WORD IN TO LOCATION 046 AND FOLLOWING
21 *WORDS INTO SUCCESSIVELY LOWER MEMORY LOCATIONS UNTIL LAST WORD (CRT)
22 *REPLACES BRU IN LOCATION 4
07605 23 READ RES 0
07605 0 01 0 00004 24 BRU READ-B 46 NO
07606 0 01 0 00003 25 BRU LAST 45 YES
07607 0 53 0 00000 26 SKN COUNT
07610 00007777 27 DATA 07777 43 NO HALT *CLEAR HALT TO ACCEPT
07611 0 70 0 00043 28 SKM MASK-B 42 DOES RECORD CHECKSUM
07612 0 75 0 00043 29 LDB MASK-B 41
07613 0 17 0 00002 30 EOR LOC 40
07614 31 NEXT RES 0
07614 0 66 0 00014 32 RSH 12 37
07615 0 35 0 00002 33 STA LOC 36 FOLD CHECKSUM
07616 0 20 12006 34 SRC CH,U 35
07617 0 17 0 00003 35 EOR LAST 34 TRANSFER ADDRESS FOR END RECORD
07620 0 32 0 00003 36 WIM LAST 33 0 FOR DATA RECORD OR
07621 37 THREE RES 0
07621 0 01 0 00025 38 BRU LOOP-B 32 NO
07622 0 53 0 00000 39 SKN COUNT 31 FINISHED
07623 0 61 0 00002 40 MIN LOC 30
07624 0 60 0 00000 41 MMO COUNT 27
07625 0 17 1 00002 42 EOR *LOC 26 ACCUMULATE CHECKSUM
07626 43 LOOP RES 0
07626 0 32 1 00002 44 WIM *LOC 25 READ NEXT WORD
07627 0 01 0 00033 45 BRU READLW-B 24 FOR END RECORD BYPASS LOOP
07630 0 40 0 20001 46 OVT 23
07631 0 17 0 00002 47 EOR LOC 22
07632 0 76 0 00003 48 LDA CW 21 BEGIN CHECKSUM
07633 0 35 0 00000 49 STA COUNT 20
07634 50 READLW RES 0
07634 0 66 0 00022 51 RSH 18 17
07635 0 54 0 00020 52 SUB THREE-B
07636 0 67 0 00003 53 LSH 3 16 END RECORD TURNS ON OVERFLOW
07637 0 76 0 00003 54 LDA CW 14 COMPUTE RECORD SIZE
07640 0 32 0 00002 55 WIM LOC 13 RECORD ORIGIN
07641 0 01 0 00003 56 BRU CW 12 YES *CLEAR HALT TO CONTINUE
07642 0 01 0 00013 57 BRU NEXT-B 11 NO
07643 0 40 0 21000 58 BRTW 10 CHECK FOR FEED ERRO
07644 59 MASK RES 0
07644 0 32 0 00003 60 WIM CW 07 READ FIRST CONTROL WORD
07645 0 20 03606 61 RCB CH,U,4 06
07646 0 01 0 00004 62 BRU READ-B 05
07647 0 40 12006 63 CRT CH,U 04 DELAY UNTIL CARD READER READY
07650 64 ENDQ RES 0
07650 0 76 0 07672 65 START LDA =11
07651 0 35 0 07671 66 STA TEMP
07652 0 40 0 14046 67 SKS 014046
07653 0 01 0 07652 68 BRU $-1
07654 0 02 0 03646 69 PUNCH EOM 03646
07655 0 71 0 07673 70 LDX =00177730
07656 2 12 0 07650 71 MIW ORG+40,2
07657 0 41 0 07656 72 BRX $-1
07660 0 02 0 14000 73 EOM 014000
07661 0 40 0 21000 74 SKS 021000
07662 0 01 0 07661 75 BRU $-1
07663 0 60 0 07671 76 SKR TEMP
07664 0 20 0 00000 77 NOP
07665 0 53 0 07671 78 SKN TEMP
07666 0 01 0 07654 79 BRU PUNCH
07667 0 00 0 00000 80 HLT
07670 0 01 0 07650 81 BRU START
07671 82 TEMP RES 1
00007650 83 END START
07672 00000013
07673 00177730

84
850648/850648-34.si Normal file
View File

@ -0,0 +1,84 @@
MMO OPD 06000000
X0 EQU 0
X2 EQU 2
CW EQU 3
COUNT EQU 0
LOC EQU 2
LAST EQU 3
U EQU 1
CH EQU 0
AORG 07600
ORG RES 0
BIAS EQU 1
B EQU ORG+BIAS
WIM 3
WIM 4
BRU 2 04
SKR 2
WIM 047
*BACKWARDS BOOTSTRAP
*BOOTSTRAP LOOP READS NEXT WORD IN TO LOCATION 046 AND FOLLOWING
*WORDS INTO SUCCESSIVELY LOWER MEMORY LOCATIONS UNTIL LAST WORD (CRT)
*REPLACES BRU IN LOCATION 4
READ RES 0
BRU READ-B 46 NO
BRU LAST 45 YES
SKN COUNT
DATA 07777 43 NO HALT *CLEAR HALT TO ACCEPT
SKM MASK-B 42 DOES RECORD CHECKSUM
LDB MASK-B 41
EOR LOC 40
NEXT RES 0
RSH 12 37
STA LOC 36 FOLD CHECKSUM
SRC CH,U 35
EOR LAST 34 TRANSFER ADDRESS FOR END RECORD
WIM LAST 33 0 FOR DATA RECORD OR
THREE RES 0
BRU LOOP-B 32 NO
SKN COUNT 31 FINISHED
MIN LOC 30
MMO COUNT 27
EOR *LOC 26 ACCUMULATE CHECKSUM
LOOP RES 0
WIM *LOC 25 READ NEXT WORD
BRU READLW-B 24 FOR END RECORD BYPASS LOOP
OVT 23
EOR LOC 22
LDA CW 21 BEGIN CHECKSUM
STA COUNT 20
READLW RES 0
RSH 18 17
SUB THREE-B
LSH 3 15 END RECORD TURNS ON OVERFLOW
LDA CW 14 COMPUTE RECORD SIZE
WIM LOC 13 RECORD ORIGIN
BRU CW 12 YES *CLEAR HALT TO CONTINUE
BRU NEXT-B 11 NO
BRTW 10 CHECK FOR FEED ERRO
MASK RES 0
WIM CW 07 READ FIRST CONTROL WORD
RCB CH,U,4 06
BRU READ-B 05
CRT CH,U 04 DELAY UNTIL CARD READER READY
ENDq RES 0
START LDA =11
STA TEMP
SKS 014046
BRU $-1
PUNCH EOM 03646
LDX =00177730
MIW ORG+40,2
BRX $-1
EOM 014000
SKS 021000
BRU $-1
SKR TEMP
NOP
SKN TEMP
BRU PUNCH
HLT
BRU START
TEMP RES 1
END START

1
850648/850648-44 Normal file

File diff suppressed because one or more lines are too long

1
850648/850648-84 Normal file
View File

@ -0,0 +1 @@
C@CC@@@F@@C@g@@@@CEX@@@@@@#h@#8@Fp@LCh@@QF8@CC@C@@EX@@F@F@@@|@CT@@@[@8@p@CCh@@Fp@RE @F8@Cp@CC@@@C@@ @C@C@^F@@F

11
850648/READ.ME Normal file
View File

@ -0,0 +1,11 @@
850648 9-SERIES BINARY INPUT ONE CARD LOADER
AUTHOR: XEROX
ABSTRACT:
TO SIMPLIFY THE LOADING OF OBJECT PROGRAMS WHICH HAVE BEEN OUTPUT BY SYMBOL
OR META-SYMBOL ON CARDS IN STANDARD BINARY FORMAT.
COMMENTS:
SIZE 39 DECIMAL. CONFIGURATION: ANY XDS 900 SERIES COMPUTER WITH CARD READER.
This is a one card loader that will load a single absolute binary deck in
standard binary format.

BIN
850649/.DS_Store vendored Normal file

Binary file not shown.

1
850649/850649-34 Normal file
View File

@ -0,0 +1 @@
<EFBFBD>dE, 7EOh4FO&)WF@yFEkO)2[Xb24dOyQvE FO%dgOggbF@C7W7O7%FC[y%vTsFOysOR)4OysEOyv@WyRQ2O2bQW&)b[y)##WO#TQ QvO2sQvTÀ@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@À@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@À@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@À@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@<40>dE, 7EOh4FO&)WF@yFEkO)2[Xb24dOyQvE FOdd&O&gTb@F@@@@@@ 7@WyvTsOvdFC[y%vTsFOysOR)4OysEOyv@WyRQ2O2bQW&)b[y)##WO#TQ QvO2sQvT<76>sWyvdCO)2XJO#2X v[y)2s)sO%@&%sy%@R)sv[y#&QTO&d@CF@F@@@@#&QTWyX#sO)sE;TQsQ@CQ&@&@@@@@@@@Wy#&QTW#&QTRQ2OX#s@C<>CC@Os)@OQTTWy&%sEOR)7J@O)RO#T7O2b27s s sEJIRX#sO24RW%vTs[y#&QTO&)Od%W#&QTW)##WO2)O2b%W)2s)sJ[y&)bO#TRWgO2bd[yg@I/p2[y)#&&gO2sRO)#gy)#gW)#&&gWy7s8uW2sQ)sE JsdgOgs[g4%XOgRb@@C@OdvOs&gO%&g[g4%XJ@OgyO%T@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Åd,pp;XIh4*XQs*J48XJX @XJ4,*yF*E E JO WFFg%  EJ W^&^%FJ;8 X kmp ;@Q hs*vnEL&4C#&&CgF>@ p4RdX1@b#@1Åk@*#p4p;)81X @uERI81X Xu  pu  huu8 ,**z[*n2vF4uJ&vdn^n@FI81Xv^ I4uJ&vdnhs>p Rn^v*mJ4vvCJv,*&EJ*uJa Xv8I81XLX7LXÅ77^I81XO  pv8*I81XOp78Opp@7g) aL,ma *kRm m sJh2&#g RIQah]aaX@CC8aX@Ib%4Ib%I@LIb%IJIb%4hIb%h #pp,@Ib%@Å>u@R#C@%FF&@ p@Ia)h@C@y8@CT@&dF& J4^FE JLLy*E @&*FOQCX@R^CI*%E@ 8XW Q@R#CI@@&FFE1p@XCXa,@C@ @v4@d2bgppTQsQp)Åk8&)T*pu*v%2sp7sp&)p%Tp)&)Tpv1s)%2)pQTT)kup@Iakh@RkC @@%dF/Wp b &^@CJvEJ,2^F4uJg^@FCJv,vX&dFpp b &^F4uJ& J*uJ&FbF4uJ&gFW@J4Å 4 b@ XX@v@v#g p8@y@p8@yup@I*a,p@R^Cp@gFs  L bE @gRF1@JL *@  n@k1@@ImXCXQ2b@@mC[ @g^F7@FF8| ]&4=&FFFFFF[*Å1bd&m Lu&pF1@4 g@ 2O @ XX]@ @zup@IQanh@RmC@;hC,12akh@RuCE @&*F; OuFF kpI42J&*n>^ J L@C@ ^QhLL*ppLC2hp@nXap1p*L@ X#hL J#Å8@EpLCbhp]Cp2*L@ ppL%J#@ubCI2hpgap2h*L@ & J>8hCL/d*aps ky@ R L;J>EbCR2/dLaps4ky@ XF J>FXzCX2/d@)apvpky@ [#h pJ>ÅIzC2/duJp7Xky@ & 8J>@L@C@ ^ahL @ ^1hL@ C*, =@J4 @ @L=#v@ IFCp* @pL=#vb@k@L>p @@pT*J2 @R* pJb2 @ s4@ I8@ Åd,IFCp* @@RL@s>@ LL@  RCO8@dX @ @R sz@@R s>@ L@COR= @RQ pJbpCbLCOR=ha@ JpCO,FbCX@p LEJdb@h@*hLh,bCX@phL=@@R^@@RQ pJbp@#@L<4C> @C@@R4 s>@ IFC8@)p@dXL>@C>X1LE @E@s8@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ØW%#@@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@<40>F  @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
850649/850649-84 Normal file
View File

@ -0,0 +1 @@
Ã@CC@@@F@@C@g@p@C@Ch@Fp@RF8@Cp@F@@ @@ @C@F@^F@R@@@XF@C @@@@@@@@@@@@@@@X@@O@Ch@@X @WEh@@@@O@^F@@EF@ Åh@@pCh@Ch@Ep@Fp@Eh@RE @Ch@Cp@@CCT@|@F@@sC@8@@QFEX@C@@ 8@FCh@@Fp@L8@@h@@@@Ch@Cp@4@EEh@EX@@ C,@EF@EF8@E@@X

BIN
850649/850649.si Normal file

Binary file not shown.

1
850649/READ.ME Normal file
View File

@ -0,0 +1 @@
850649AA B3 9-SERIES BINARY INPUT-TWO CARD LOADER

1
850657/850657-34 Normal file

File diff suppressed because one or more lines are too long

1
850657/850657.bo Normal file
View File

@ -0,0 +1 @@
Ă]d@@pCCh@@@@@@ @@@@@@@s@Ch,@J@@WphhEhF@O=ph,EhF@T@uW>@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]Cy@X@p@Ch@@@&@@] &@@@F&Q,@@@F@#@Q @@@@h@@@n&@@,FEXzmW@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]yX@p@@2@@aX@yFEX@@7@@@@@@@@@@@@@p=ChTWp,EhFz@FFTEXT@@@>p,@;@R@E@yk;=@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]nF@I@FhCWpWW@,@ X@yFEX@W@@aQO@@7Wh,@a>QTk;;@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]W @@7h,#@C8&@g &@)@F&Q,m@Q @@@p&@2FEX@8@kk@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]@s8@@;@%@@@@@b|;z4p,@@@@@C****u)8JJ&dg#s********@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@<40>]s[@u)8J))&)****@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ř%4@@7 @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

172
850657/850657.lo Normal file
View File

@ -0,0 +1,172 @@
1 *
2 * BP1 SET- SINGLE CHARACTER MODE.
3 * BP2 SET- ENTIRE CHARACTER SET.
4 * BP3 SET- VERIFY MODE
5 *
00000 0 76 00203 6 START LDA DM64
00001 0 35 00226 7 STA DONE
00002 0 40 20400 8 BPT 1
00003 0 01 00010 9 BRU TEST1
00004 0 40 20200 10 BPT 2
00005 0 01 00015 11 BRU TEST2
00006 0 00 00000 12 HLT
00007 0 01 00000 13 BRU START
14 *
00010 0 46 30003 15 TEST1 CLR INITIALIZE SINGLE
00011 0 71 00202 16 LDX DM20 CHARACTER TEST
00012 2 35 00254 17 STA IMAGE+20,2
00013 0 41 00012 18 BRX *-1
00014 0 01 00027 19 BRU COM1
20 *
00015 0 71 00201 21 TEST2 LDX DM16 INITIALIZE CHARACTER
00016 0 76 00207 22 LDA CSTAR SET TEST
00017 2 35 00250 23 STA IMAGE+16,2
00020 0 55 00206 24 ADD CADD4
00021 0 41 00017 25 BRX *-2
00022 0 71 00175 26 LDX DM4
00023 0 76 00207 27 LDA CSTAR
00024 2 35 00254 28 STA IMAGE+20,2
00025 0 55 00206 29 ADD CADD4
00026 0 41 00024 30 BRX *-2
31 *
00027 0 40 20100 32 COM1 BPT 3
00030 0 01 00110 33 BRU VERIFY
00031 0 76 00200 34 LDA DM12
00032 0 35 00225 35 STA CARD
00033 0 40 20200 36 BPT 2 OMIT BIT 13-TEST 2
00034 0 01 00037 37 BRU *+3
00035 0 40 12046 38 SKS 12046 BIT 13-PUNCH BUF RDY
00036 0 01 00035 39 BRU *-1
00037 0 40 14046 40 SKS 14046 BIT 12-PUNCH RDY
00040 0 01 00037 41 BRU *-1
00041 0 71 00202 42 COM2 LDX DM20
00042 0 02 00646 43 EOM 646 SELECT PUNCH
00043 2 12 00254 44 MIW IMAGE+20,2
00044 0 40 20010 45 BETW
00045 0 01 00006 46 BRU START+6
00046 0 41 00043 47 BRX *-3
00047 0 02 14000 48 TOPW COMPLETE ROW
00050 0 40 21000 49 BRTW
00051 0 01 00050 50 BRU *-1
00052 0 40 20200 51 BPT 2 OMIT BIT 13-TEST 2
00053 0 01 00056 52 BRU *+3
00054 0 40 12046 53 SKS 12046 BIT 13-PUNCH BUF RDY
00055 0 01 00054 54 BRU *-1
00056 0 61 00225 55 MIN CARD
00057 0 53 00225 56 SKN CARD
00060 0 01 00062 57 BRU *+2
00061 0 01 00041 58 BRU COM2 PUNCH NEXT ROW
00062 0 43 00071 59 BRM ROTATE
00063 0 61 00226 60 MIN DONE
00064 0 53 00226 61 SKN DONE TEST FOR DONE
00065 0 01 00067 62 BRU *+2
00066 0 01 00031 63 BRU COM1+2
00067 0 00 00000 64 COM5 HLT
00070 0 01 00000 65 BRU START
66 *
00071 0 00 00000 67 ROTATE PZE CHANGE CARD IMAGE
00072 0 71 00202 68 LDX DM20
00073 0 76 00175 69 LDA DM4
00074 0 35 00224 70 STA X2
00075 2 76 00254 71 LDA IMAGE+20,2
00076 0 55 00204 72 ADD 1B5
00077 0 67 20006 73 LCY 6
00100 0 61 00224 74 MIN X2
00101 0 53 00224 75 SKN X2
00102 0 01 00104 76 BRU *+2
00103 0 01 00076 77 BRU *-5
00104 2 36 00254 78 STB IMAGE+20,2
00105 0 41 00073 79 BRX ROTATE+2
00106 0 02 20001 80 ROV
00107 0 51 00071 81 BRR ROTATE
00110 0 71 00202 82 VERIFY LDX DM20
00111 0 40 12006 83 SKS 12006 CARD READER READY
00112 0 01 00111 84 BRU *-1
00113 0 02 02606 85 RCDW 1,4
00114 0 75 00210 86 LDB ONES
00115 0 32 00227 87 WIM TEMP
00116 0 76 00227 88 LDA TEMP
00117 2 70 00254 89 SKM IMAGE+20,2 COMPARE WORD
00120 0 01 00134 90 BRU ERROR
00121 0 41 00115 91 BRX *-4
00122 0 43 00071 92 BRM ROTATE
00123 0 61 00226 93 MIN DONE
00124 0 53 00226 94 SKN DONE TEST FOR DONE
00125 0 01 00127 95 BRU *+2
00126 0 01 00110 96 BRU VERIFY READ NEXT CARD
00127 0 02 02641 97 TYPW 1,4 DONE MESSAGE
00130 0 71 00177 98 LDX DM6
00131 2 12 00217 99 MIW MSG1+6,2
00132 0 41 00131 100 BRX *-1
00133 0 01 00067 101 BRU COM5
00134 2 75 00254 102 ERROR LDB IMAGE+20,2 PRINT ERROR MSG
00135 0 02 02641 103 TYPW 1,4
00136 0 71 00176 104 LDX DM5
00137 2 12 00224 105 MIW MSG2+5,2
00140 0 41 00137 106 BRX *-1
00141 0 01 00067 107 BRU COM5
108 *
109 * CARD PUNCH SERVICE ROUTINE.
110 * ENTER BY BRU 342
111 * EXIT BY BRU 200
112 * SET IMAGE IN A REGISTER BEFORE STARTING
113 * SET BP1 TO STOP TEST
114 *
00142 0 71 00202 115 SERV LDX DM20
00143 2 35 00254 116 STA IMAGE+20,2
00144 0 41 00143 117 BRX *-1
00145 0 71 00200 118 SERV1 LDX DM12
00146 0 37 00225 119 STX CARD
00147 0 40 12046 120 SKS 12046 BIT 13-PUNCH BUF RDY
00150 0 01 00147 121 BRU *-1
00151 0 40 14046 122 SKS 14046 BIT 12-PUNCH RDY
00152 0 01 00151 123 BRU *-1
00153 0 71 00202 124 SERV2 LDX DM20
00154 0 02 00646 125 EOM 646 SELECT PUNCH
00155 2 12 00254 126 MIW IMAGE+20,2
00156 0 41 00155 127 BRX *-1
00157 0 02 14000 128 TOPW
00160 0 40 21000 129 BRTW
00161 0 01 00160 130 BRU *-1
00162 0 40 12046 131 SKS 12046 BIT 13-PUNCH BUF RDY
00163 0 01 00162 132 BRU *-1
00164 0 61 00225 133 MIN CARD
00165 0 53 00225 134 SKN CARD
00166 0 01 00170 135 BRU *+2
00167 0 01 00153 136 BRU SERV2
00170 0 40 20400 137 BPT 1
00171 0 01 00173 138 BRU *+2
00172 0 01 00145 139 BRU SERV1
00173 0 00 00000 140 HLT
00174 0 01 00142 141 BRU SERV
142 *
00175 77777774 143 DM4 DEC -4
00176 77777773 144 DM5 DEC -5
00177 77777772 145 DM6 DEC -6
00200 77777764 146 DM12 DEC -12
00201 77777760 147 DM16 DEC -16
00202 77777754 148 DM20 DEC -20
00203 77777700 149 DM64 DEC -64
00204 01000000 150 1B5 DEC 1B5
00205 01010101 151 CADD OCT 01010101
00206 04040404 152 CADD4 OCT 04040404
00207 00010203 153 CSTAR OCT 00010203
00210 77777777 154 ONES OCT 77777777
00211 52525252 155 MSG1 OCT 52525252
00212 65255131 156 BCI 4,VERIFY COMPLETE
00213 26701212
00214 23464447
00215 43256325
00216 52525252 157 OCT 52525252
00217 52525252 158 MSG2 OCT 52525252
00220 65255131 159 BCI 3,VERIFY ERROR
00221 26701225
00222 51514651
00223 52525252 160 OCT 52525252
00224 0 00 00000 161 X2 PZE
00225 0 00 00000 162 CARD PZE
00226 0 00 00000 163 DONE PZE
00227 0 00 00000 164 TEMP PZE
00230 0 00 00000 165 IMAGE PZE
00000067 166 END COM5

13
850657/READ.ME Normal file
View File

@ -0,0 +1,13 @@
850657 9-SERIES CARD PUNCH TEST PROGRAM PACKAGE -9156
ABSTRACT:
TO PROVIDE AN ACCFPTANCE TEST FOR THE XDS MODEL 9156 CARD PUNCH SYSTEM.
COMMENTS:
SIZE 172 DECIMAL. SOURCE LANGUAGE: META-SYMBOL. CONFIGURATION: ANY XDS 920/930 OR 910/925 WITH A TYPEWRITER, AND XDS MODEL 9151 OR 9152 CARD READER ON CHANNEL A (W). INTERLACE IS NOT USED.
Use the command file symbol/sym to assemble the bcd deck at 850657-34 and create 850657.bo and 850657.lo.
run the test using command file cptst.
BP1 SET- SINGLE CHARACTER MODE.
BP2 SET- ENTIRE CHARACTER SET.
BP3 SET- VERIFY MODE

27
850657/cptst Normal file
View File

@ -0,0 +1,27 @@
; command file to run punch test
;
set log /users/admin/sds/simlog
set debug /users/admin/sds/simdebug
; set bpt 1 to boot from cards
; this will load 850657.bo at 30000 and halt at 30070
;
; set bpt 1 for single char test
; this will write 64 cards to cp
; set bpt 2 for character set test after punching,
;
; to verify after running the test, detach cp
; and attach card-punch to cr
; set bpt 3 and continue;
! cat 850648/850648-84 symbol/section-2a.bo 850657/850657.bo card-punch >bootdeck
set cpu history=700
! rm card-punch
att cr bootdeck
att cp card-punch
; set bpt1 to boot from card re
dep bpt1 1
boot cr

BIN
850816/.DS_Store vendored Normal file

Binary file not shown.

1
850816/850816-44 Normal file

File diff suppressed because one or more lines are too long

10
850816/READ.ME Normal file
View File

@ -0,0 +1,10 @@
850816 9-SERIES 910/925 ALGOL 60 BASIC 4K SYSTEM
AUTHOR: XEROX
ABSTRACT:
TO COMPILE, LOAD AND EXECUTE ALGOL PROGRAMS FROM A FREE STANDING SYSTEM.
COMMENTS:
SOURCE LANGUAGE: META-SYMBOL. CONFIGURATION: 910/925 COMPUTER WITH AT LEAST 4K MEMORY,
TYPEWRITER AND PAPER TAPE I/0. SEE MANUAL NO. 900699.
This file 850816-44 has 4 ^ type control cards preceeding the encoded deck.

1
850816/alg Normal file

File diff suppressed because one or more lines are too long

3887
850816/algol.si Normal file

File diff suppressed because it is too large Load Diff

1
890548/890548-24 Normal file

File diff suppressed because one or more lines are too long

1
890548/890548-44 Normal file

File diff suppressed because one or more lines are too long

17
890548/READ.ME Normal file
View File

@ -0,0 +1,17 @@
890548 930 REGEN-A BINARY TO SYMBOLIC TRANSLATOR
AUTHOR:.J.W. LAYLAND, ,JET PROPULSION LABORATORY
ABSTRACT:
REGEN IS A PROGRAM FOR TRANSLATING BETWEEN THE XDS 900 SERIES UNIVERSAL BINARY LANGUAGE AND A SYMBOLIC EQUIVALANT. THE PROGRAM OPERATES UNDER A BASIC MONARCH SYSTEM WITH ONE SCRATCH TAPE AND USES THE SYSTEM INPUT/OUTPUT ASSIGNMENTS. BREAKPOINTS 3 AND 4. SELECT THE PF!ODUCTION or EITHER A LIST OUTPUT OR AN ASSEMBLABLE SYMBOLIC: DECK OUTPUT. EXTERNAL REFERENCE AND DEFINITION ITEMS IN THE BINARY TEXT PROVIDE NAMES AND MAKE THE REGENERATED TEXT AS CLOSE AS POSSIBLE TO THE ORIGINAL SOURCE.
COMMENTS:
ADDITIONAL INFORMATlON:NEEDS I SCRATCH TAPE.
* regen - disassembler 930 binary to symbol
* catalog number 890548
* regen.si came from 890548-34
* commented out the proc directives in hope of
* assembling with symbol, not metasymbol
* 890548-24 is relocatable binary deck
* intended for Monarch
* has undefined refs from Monarch

1
890548/regen.bo Normal file

File diff suppressed because one or more lines are too long

2411
890548/regen.lo Normal file

File diff suppressed because it is too large Load Diff

2242
890548/regen.si Normal file

File diff suppressed because it is too large Load Diff

61
READ.ME Normal file
View File

@ -0,0 +1,61 @@
This is a collection of software for use with the SDS simulator
provided with the simh simulator system. It is provided in hopes of
exciting the interested of someone curious about computing during
the 1960-1976 period.
It includes a cross assembler used on a Mac to produce the included
Symbol assembler. It also includes a tool set to help manage and
manipulate this stuff; things like a binary object dump, a namelist
program and a program to retieve files from a PAL library file.
The SDS 900 Series computers were initially paper tape and card unit
systems and the software in this kit predominatly uses these devices.
The SDS programs in the kit were obtained from files copied from a
9-track tape that was created by the SDS PAL library back in 1982.
This file is from the bitsaver.org archives, M300-19820128.tap.
The SDS basic paper tape loader program, 850644, is included in the kit as
an example to experiment with the SDS recon and Symbol assembler
programs.
850640 SEMI-AUTOMATIC TYPEWRITER TEST
850644 BINARY INPUT-BASIC PAPER TAPE LOADER
850645 UNIVERSAL LOADER
850647 ENCODED TO SYMBOLIC RECONSTRUCTOR(RECON)
850648 BINARY INPUT ONE CARD LOADER
850649 BINARY INPUT-TWO CARD LOADER
850657 CARD PUNCH TEST PROGRAM PACKAGE
850816 910/925 ALGOL 60 BASIC 4K SYSTEM
890548 BINARY TO SYMBOLIC TRANSLATOR
cross assembler Assemble SYMBOL programs on a MAC
fortransa 920/930 FORTRAN II SYSTEM (STAND ALONE)
symbol Symbol assembler and command files
tests A magtape test, so far
tools Possibly useful tools
The work to put this kit together was done on a Mac. I don't know what
will happen using this stuff on other platforms

BIN
cross_assembler/.DS_Store vendored Normal file

Binary file not shown.

9
cross_assembler/READ.ME Normal file
View File

@ -0,0 +1,9 @@
This is a cross assmbler to mimic the SDS Symbol Assembler on a mac.
It was developed to assemble the SDS Symbol assembler from source
code listings found in the Symbol Tech Manual dated March 1965,
catalog number 900688A. It serves its purpose but is missing some
features that weren't needed at the time. I hope it may be useful.
The bld_xsym.sh is the simple gcc command to compile and link the
files.

2
cross_assembler/bld_xsym.sh Executable file
View File

@ -0,0 +1,2 @@
gcc -g sym.c sym2.c -o sym

BIN
cross_assembler/sym Executable file

Binary file not shown.

1148
cross_assembler/sym.c Normal file

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,20 @@
<?xml version="1.0" encoding="UTF-8"?>
<!DOCTYPE plist PUBLIC "-//Apple Computer//DTD PLIST 1.0//EN" "http://www.apple.com/DTDs/PropertyList-1.0.dtd">
<plist version="1.0">
<dict>
<key>CFBundleDevelopmentRegion</key>
<string>English</string>
<key>CFBundleIdentifier</key>
<string>com.apple.xcode.dsym.sym</string>
<key>CFBundleInfoDictionaryVersion</key>
<string>6.0</string>
<key>CFBundlePackageType</key>
<string>dSYM</string>
<key>CFBundleSignature</key>
<string>????</string>
<key>CFBundleShortVersionString</key>
<string>1.0</string>
<key>CFBundleVersion</key>
<string>1</string>
</dict>
</plist>

Binary file not shown.

112
cross_assembler/sym.h Normal file
View File

@ -0,0 +1,112 @@
//
// sym.h
//
// Created by Ken Rector on 3/15/20
#define INS1 020
#define INS9 04010
#define INS2 010
#define DIR1 04
#define DIR2 02
#define RELM 02
#define EXTM 01
#define REFT 01 // ref/def/pop subtype
#define DEFT 02
#define INTT 00
#define RECDAT 00 // record type
#define RECDEF 01
#define RECPOP 02
#define RECEND 03
#define AORG 0103
#define BCD 0104
#define BCI 0105
#define BORG 0106
#define BSS 0107
#define DEC 0110
#define DED 0111
#define END 0112
#define EQU 0113
#define FORM 0114
#define NOPO 0115
#define OCT 0116
#define OPD 0117
#define POPD 0120
#define PZE 0121
#define TEXT 0122
#define BOOL 0123
#define COPY 0124
#define DATA 0125
#define ORG 0126
#define PAGE 0127
#define BPT 0130
#define FORCEO 1
#define XMASK 07
#define EOM 00200000
typedef struct def {
int cw;
char lbl[8];
int data;
} def;
typedef struct tbl {
char lbl[8];
int mode;
int word;
} tbl;
#define CTT(c) ctt[ascii_to_sds930[c]]
#define IC 04000000
#define CC 02000000
#define LC 01000000
#define SC 00400000
#define DC 00200000
#define OC 00100000
#define XYZ 06000000
#define ITM 04000000 // ITEM
#define CON 02000000 // CONNECTOR
#define STM 05400000 // SYMBOL,LABEL,ITEM
#define DTM 04600000 // DECIMAL, SYMBOL, ITEM
#define OTM 04700000 // OCTAL,DECIMAL,SYMBOL,ITEM
#define SCO 0 // ZERO
#define SCD 0 // DIGIT
#define SCS 0 // LETTER
#define SCA 1 // APOSTROPHY (single quote)
#define SCL 5 // DOLLAR, ASTERISK
#define SCX 9 // LEFT PAREN
#define BCON 00000 // BLANK connector code
#define CCON 00100 // , connector code
#define RCON 00200 // ) connector code
#define SCON 03310 // + ++ connector codes
#define DCON 03411 // - -- connector codes
#define PCON 04522 // * ** connector codes
#define QCON 04647 // / // connector codes
#define CLS 0
#define CLD 1
#define CLP 2
#define CAS 3
#define CAD 4
#define CAP 5
#define CEQ 6
#define CXQ 7
#define CDS 8
#define CBS 9

736
cross_assembler/sym2.c Normal file
View File

@ -0,0 +1,736 @@
//
// sym2.c
//
//
// Created by Ken Rector on 3/21/20.
//
#include <stdio.h>
#include <stdlib.h>
#include <math.h>
#include <string.h>
#include <ctype.h>
#include "sym.h"
extern tbl *srch(tbl *t, char *key);
extern void _move(tbl *item, char *key, int loc, int mode);
extern char *var; // operand string
extern char refr[];
extern int *lop;
extern int *litm;
extern int ladd;
extern int *scnx;
extern int derr;
extern int eerr;
extern int iflg;
extern int loc;
extern int lsot;
extern int lsxt;
extern int mode;
extern int octf;
extern int pass2;
extern int perr;
extern int relm;
extern int rerr;
extern int scno;
extern int term;
extern int terr;
extern int _verr;
extern int valu;
extern int xerr;
void scan(void);
tbl mt[1000] = {
{"LCY", 00, 06720000},
{"LDA", 00, 07600000},
{"LDB", 00, 07500000},
{"LDE", 00, 04600140},
{"LDX", 00, 07100000},
{"LIL", DIR2, NOPO},
{"LIST", DIR2, NOPO},
{"LRSH", 00, 06624000},
{"LSH", 00, 06700000},
{"MIN", 00, 06100000},
{"MIW", 00, 01200000},
{"MIY", 00, 01000000},
{"MPT", INS9, 010210},
{"MRG", 00, 01600000},
{"MUL", 00, 06400000},
{"NOD", 00, 06710000},
{"NOP", 00, 02000000},
{"OCT", DIR2, OCT},
{"OPD", DIR1, OPD},
{"ORG", DIR1, ORG},
{"OVT", 00, 04020001},
{"PAGE", DIR2, PAGE},
{"PBF", INS9, 017457+EOM},
{"PBT", INS9, 04012045},
{"PCB", INS9, 03045+EOM},
{"PCD", INS9, 02045+EOM},
{"PFT", INS9, 011057},
{"PLP", INS9, 02057+EOM},
{"POL", INS9, 012057+EOM},
{"POPD", DIR1, POPD},
{"POT", 00, 01300000},
{"PPT", INS9, 02043+EOM},
{"PPTW", INS2, 0202043},
{"PPTY", INS2, 0202143},
{"PRT", INS9, 012057},
{"PS1F", INS9, 010457+EOM},
{"PS2F", INS9, 012457+EOM},
{"PSP1", INS9, 011657+EOM},
{"PSP2", INS9, 012657+EOM},
{"PSP3", INS9, 013657+EOM},
{"PSP4", INS9, 014657+EOM},
{"PSP5", INS9, 015657+EOM},
{"PSP6", INS9, 016657+EOM},
{"PSP7", INS9, 017657+EOM},
{"PTF", INS9, 011457+EOM},
{"PTL", INS9, 043+EOM},
{"PTLW", INS2, 0200043},
{"PTLY", INS2, 0200143},
{"PZE", DIR2, PZE},
{"RCB", INS9, 03005+EOM},
{"RCBW", INS2, 0203005},
{"RCBY", INS2, 0203105},
{"RCD", INS9, 02005+EOM},
{"RCDW", INS2, 0202005},
{"RCDY", INS2, 0202105},
{"RCH", INS1, 04600000},
{"RCY", 00, 06620000},
{"REL", DIR2, NOPO},
{"REO", 00, 020010+EOM},
{"RES", DIR2, BSS},
{"REW", INS9, 014010+EOM},
{"REWW", INS2, 014010+EOM},
{"RKB", INS9, 02000+EOM},
{"RKBW", INS2, 0202000},
{"RKBY", INS2, 0202100},
{"RORG", DIR2, ORG},
{"ROV", 00, 020001+EOM},
{"RPT", INS9, 02003+EOM},
{"RPTW", INS2, 0202003},
{"RPTY", INS2, 0202103},
{"RSH", 00, 06600000},
{"RTB", INS9, 03010+EOM},
{"RTBW", INS2, 0203010},
{"RTBY", INS2, 0203110},
{"RTD", INS9, 02010+EOM},
{"RTDW", INS2, 0202010},
{"RTDY", INS2, 0202110},
{"RTS", INS9, 014000+EOM},
{"SFB", INS9, 03030+EOM},
{"SFB", INS2, 0203030},
{"SFD", INS9, 02030+EOM},
{"SKA", 00, 07200000},
{"SKB", 00, 05200000},
{"SKD", 00, 07400000},
{"SKE", 00, 05000000},
{"SKG", 00, 07300000},
{"SKM", 00, 07000000},
{"SKN", 00, 05300000},
{"SKR", 00, 06000000},
{"SKS", INS1, 04000000},
{"SRB", INS9, 07030+EOM},
{"SRBW", INS2, 0207030},
{"SRC", INS9, 012005+EOM},
{"SRD", INS9, 06030+EOM},
{"SRR", INS9, 013610+EOM},
{"STA", 00, 03500000},
{"STB", 00, 03600000},
{"STE", 00, 04600122},
{"STX", 00, 03700000},
{"SUB", 00, 05400000},
{"SUC", 00, 05600000},
{"TCD", DIR2, NOPO},
{"TEXT", DIR2, TEXT},
{"TFT", INS9, 013610},
{"TGT", INS9, 012610},
{"TOP", INS9, 014000+EOM},
{"TOPW", 00, 014000+EOM},
{"TOPY", 00, 014100+EOM},
{"TRT", INS9, 04010410},
{"TYP", INS9, 02040+EOM},
{"TYPW", INS2, 0202040},
{"TYPY", INS2, 0202140},
{"UNLI", 0, 0},
{"WIM", 00, 03200000},
{"WTB", INS9, 03050+EOM},
{"WTBW", INS2, 0203050},
{"WTBY", INS2, 0203150},
{"WTD", INS9, 02050+EOM},
{"WTDW", INS2, 0202050},
{"WTDY", INS2, 0202150},
{"XAB", 00, 04600014},
{"XEE", 00, 04600160},
{"XMA", 00, 06200000},
{"XXA", 00, 04600600},
{"XXB", 00, 04600060},
{"YIM", 00, 03000000},
{"ABC", 00, 04620005},
{"ADC", 00, 05700000},
{"ADD", 00, 05500000},
{"ADM", 00, 06300000},
{"AIR", 00, 020020+EOM},
{"ALC", INS9, 0250000},
{"AORG", DIR1, AORG},
{"ASC", INS9, 012000+EOM},
{"BAC", 00, 04610012},
{"BCD", DIR2, BCD},
{"BCI", DIR2, BCI},
{"BETW", 00, 04020010},
{"BETY", 00, 04020020},
{"BLK", DIR2, NOPO},
{"BOOL", DIR1, BOOL},
{"BORG", DIR1, BORG},
{"BPT", DIR2, BPT},
{"BRM", 00, 04300000},
{"BRR", 00, 05100000},
{"BRTW", 00, 04021000},
{"BRTY", 00, 04022000},
{"BRU", 00, 00100000,},
{"BRX", 00, 04100000},
{"BSS", DIR2, BSS},
{"BTT", INS9, 04012010},
{"CAB", 00, 04600004},
{"CAT", INS9, 04014000},
{"CAX", 00, 04600400},
{"CBA", 00, 04600010},
{"CBX", 00, 04600020},
{"CET", INS9, 04011000},
{"CFT", INS9, 04011005},
{"CIT", INS9, 04010400},
{"CLA", 00, 04600001},
{"CLB", 00, 04600002},
{"CLR", 00, 04630003},
{"CLX", 00, 024600000},
{"CNA", 00, 04601000},
{"COPY", DIR2, COPY},
{"COPY", 0, 0},
{"CPT", INS9, 04014045},
{"CRT", INS9, 04012005},
{"CXA", 00, 04600200},
{"CXB", 00, 04600040},
{"CZT", INS9, 04012000},
{"DATA", DIR2, DATA},
{"DEC", DIR2, DEC},
{"DED", DIR2, DED},
{"DIR", 00, 00220004},
{"DISW", 00, 00+EOM},
{"DISY", 00, 0100+EOM},
{"DIV", 00, 06500000},
{"DSC", INS9, 00+EOM},
{"DT2", INS9, 016210},
{"DT5", INS9, 016610},
{"DT8", INS9, 017210},
{"EAX", 00, 07700000},
{"EFT", INS9, 03070+EOM},
{"EIR", 00, 00220002},
{"END", DIR2, END},
{"EOD", INS1, 0600000},
{"EOM", INS1, 0200000},
{"EOR", 00, 01700000},
{"EPT", INS9, 014057},
{"EQU", DIR1, EQU},
{"ERT", INS9, 07070+EOM},
{"ETR", 00, 01400000},
{"ETT", INS9, 04011010},
{"ETW", INS2, 0203070},
{"EXU", 00, 02300000},
{"F101", 0, 0},
{"FCT", INS9, 04014005},
{"FORM", DIR1, FORM},
{"FORT", DIR2, NOPO},
{"HLT", 0, 0},
{"FPT", INS9, 04014010},
{"IDT", 00, 04020002},
{"IET", 00, 04020004},
{"QQQ",00, 0000},
{" ", 00,00000}
};
tbl sym[1000] = {{"\0\0\0", 00,00000} // symbol table
};
tbl lt[1000] = {{"\0\0\0", 00,00000} // literal table
};
tbl rt[1000] = {{"\0\0\0", 00,00000} // ref table
};
const uint8_t ascii_to_sds930[128] = {
060, -1, -1, -1, -1, -1, -1, -1, /* 00 - 37 */
032, 072, -1, -1, -1, 052, -1, -1,
-1, -1, -1, -1, -1, -1, -1, -1,
-1, -1, -1, -1, -1, -1, -1, -1,
060, 052, -1, 077, 053, 017, -1, 014, /* 40 - 77 */
074, 034, 054, 020, 073, 040, 033, 061,
000, 001, 002, 003, 004, 005, 006, 007,
010, 011, 015, 056, 036, 013, 016, 072,
037, 021, 022, 023, 024, 025, 026, 027, /* 100 - 137 */
030, 031, 041, 042, 043, 044, 045, 046,
047, 050, 051, 062, 063, 064, 065, 066,
067, 070, 071, 035, 076, 055, 057, 060,
-1, 021, 022, 023, 024, 025, 026, 027, /* 140 - 177 */
030, 031, 041, 042, 043, 044, 045, 046, /* fold lower case to upper */
047, 050, 051, 062, 063, 064, 065, 066,
067, 070, 071, -1, -1, -1, -1, -1
};
int ctt[] = {
OTM |SCO, // O OO
OTM |SCD, // 1 01
OTM |SCD, // 2 02
OTM |SCD, // 3 03
OTM |SCD, // 4 04
OTM |SCD, // 5 05
OTM |SCD, // 6 06
OTM |SCD, // 7 07
DTM |SCD, // 8 10
DTM |SCD, // 9 11
0, // Z HLT 0
077, // C3 HLT 077 =
ITM |SCA, // ' 14
040000000, // 80 DATA 040000000
2, // 822 HLT 2
030, // P24 HLT 24
CON |SCON, // + 20
STM |SCS, // A 21
STM |SCS, // B 22
STM |SCS, // C 23
STM |SCS, // D 24
STM |SCS, // E 25
STM |SCS, // F 26
STM |SCS, // G 27
STM |SCS, // H 30
STM |SCS, // I 31
013, // ECHR |HLT '='
040, // MCHR |HLT '-'
CON |RCON, // ) 34
07, // A7 HLT 7
03, // P3 HLT 3
0100, // B17 HLT 0100
CON |DCON, // - 40
STM |SCS, // J 41
STM |SCS, // K 42
STM |SCS, // L 43
STM |SCS, // M 44
STM| SCS, // N 45
STM |SCS, // O 46
STM |SCS, // P 47
STM |SCS, // Q 50
STM| SCS, // R 51
020, // PLUS HLT '+' // +
ITM |SCL, // $ 53
XYZ |SCL, // * 54
033, // PCHR HLT '.'
014, // QCHR HLT 014
034, // RCHR HLT ')'
CON |BCON, // 60 ' ' = 02000000
CON |QCON, // / 61
STM |SCS, // S 62
STM |SCS, // T 63
STM |SCS, // U 64
STM |SCS, // V 65
STM |SCS, // W 66
STM |SCS, // X 67
STM |SCS, // Y 70
STM |SCS, // Z 71
0, // HLT 0
CON |CCON, // , 73
ITM |SCX, // ( 74
022, // HB HLT 'B'
025, // HE HLT 'E'
020000000 // X2W HLT 0,X2
};
int chr1;
// evaluate a connector partII 660
char * scc(char *s, int *m) {
//int flg;
int cnct;
if (!(CTT(*s) & CC)) {
term = *s; // not a connector
eerr++; // set E flag - skip char
*m = mode;
return ++s; // skip char
}
if (*s == '*') { // scc1 conecter is AP if *
chr1 = *s; // save it
s++;
if (*s == '+') {
cnct = 05000; // *+ decimal scale connector
// X *+ Y -> (X).(10^Y) //
}
else if (*s == '/') { // */ binary scale connector
cnct = 05100; // X */ Y -> (X).(2^Y)
// scc4 position at next char
}
else {
cnct = PCON; // PCON = 04522
if (*s == '*') {
cnct = cnct << 6; // ** == 2200 code for pair
}
}
}
else {
cnct = CTT(*s); // scc7 - save conecter
if (!(cnct & 07000)) { // if ), ,, or ' '
term = *s; // save terminater
}
else {
chr1 = *s; // scc2 not a terminator - save char
if (s[1] == chr1) { // if paired
cnct = cnct << 6; // use alternate connector
s++;
}
}
}
*m = mode | (cnct & 07700); // scc3 extract connecter
return ++s;
}
// evaluates an item part II - 431
char *sci(char *s, tbl *item) {
int i;
int n;
char itm[12];
tbl *t;
while (1) {
if (!(CTT(*s) & IC)) { // & 04000000 - OTM or DTM or STM symbol worthy
eerr++;
s++;
return s;
}
switch(CTT(*s) & 07777) {
case SCO: // digits and alpha
//chr2 = *s; // save lead char
if (!(CTT(*s) & SC)) { // if 1st char not item character
strncpy(item->lbl," ",6); // return error
return s;
}
n = (int)strlen(s);
for (i = 0; i < n; i++) {
if (!(CTT(*s) & SC)) // if not item character
break;
itm[i] = *s;
s++;
}
itm[i] = '\0';
n = 0;
for (i = 0; i < strlen(itm);i++) {
if (!isdigit(itm[i]))
break;
if ((itm[i] == '8') || (itm[i] == '9'))
n++;
}
if (i == strlen(itm)) {
if ((itm[0] == '0') || octf) {
if (!n)
n = sscanf(itm,"%o",&item->word);
else
n = 0; // found decimal digits
}
else
n = sscanf(itm,"%d",&item->word);
if (!n)
eerr++;
item->mode = 0;
}
else {
t = srch(sym,itm); // scit4 search a= valu b= mode
strncpy(item->lbl,itm,6);
if (*(int *)t == (int)t) {
_verr++; // 543 undefined referenced
}
if ((t->mode & 0100))
derr++; // refers to duplicate
item->mode = t->mode & 03;
if (t->word & 0100000)
item->mode |= RELM;
item->word = t->word;
if (item->mode & RELM)
item->word &= 037777; // clean up address
}
return (s);
case SCA: // 602 apostrophe (single quote)
valu = 0; // sca2
s++; // skip the quote
while (*s != '\'') { // scan for closing quote
if (valu & 077000000) { // sca1 alf char
terr++; // more than four characters
}
else {
valu = (valu << 6) | ascii_to_sds930[*s]; // insert new char
}
s++;
}
s++; // sca3 skip second quote
item->word = valu;
item->mode = 0;
return s;
case SCL: // 555 * or $
if (*s == '*') { // test for *
s++;
if (!(CTT(*s) & CC)) {
iflg++; // next character is a connector
continue;
}
}
else
s++; // scl1 skip $
if (loc & 00100000) // scl2 if relocatable
item->mode = RELM;
else
item->mode = 0;
item->word = loc & 037777;
return s;
case SCX: // 621 (
/*
if ((int)scnx <= scno) {
perr++; // scx1 too many levels - set p flag
s++;
while (*s != ')')
s++; // skip sub-expression
s++; // skip )
item->word = 0;
item->mode = 0;
return s;
}
*/
scnx++;
lop++;
litm++;
var++; // skip (
scan(); // get sub expression
lop--;
litm--;
scnx--;
item->word = valu;
item->mode = 0;
return var;
}
}
return s;
}
// evaluate symbolic expression part II 315:
// returns with valu and mode for address field
// and term == last terminator character
void scan() {
int i;
int n;
int B;
tbl t;
*lop = 0; // 0 to base conecter
valu = 0; // 0 to value
mode = 0; // 0 to mode
chr1 = 0; // reset
if (CTT(*var) & IC) { // & IC 04000000 connector flag?
var = sci(var,&t); // scn1: not a connecter - get next item
strncpy(refr,t.lbl,6); // save ref label
valu = t.word;
mode = t.mode; // mode indicates RELM or zero
}
while (1) {
// evaluate next connector
// returns the connector code from CTT[*var] or
// a generated code for two character connectors
// masked with 07700
var = scc(var,&mode); // scn8 get next connecter
scn6:
if ((mode <= *lop) ||
((mode & 07000) == *lop)) { // scn7 hierarchy mask
if ((*lop & 07000) == 0) { // scn2 last connector - test for terminator
B = mode & 077; // mask mode - gives connector code
if ((int)scnx == lsxt) { // test p level
if (term != ')') { // p level zero
while (1) { // scn12 - gnf() skip to next field
if ((term == ',') ||
(term == ' ') ||
(term =='\0'))
return;
var++;
term = *var;
}
}
else {
perr++; // level 0 and terminator == )
}
}
else { // not level 0
if (term != ')') // scn11
perr++;
}
return;
}
else {
i = *lop; // scn4 do operation
if ((*lop & 07000) != 05000)
i &= 0700;
i &= 01700;
i = i >> 6; // op number
switch (i) { // scn4 - do operation
case CLS: // logical sum V=L++V
valu = *litm | valu;
break;
case CLD: // logical diff V=L--V
valu = *litm ^ valu;
break;
case CLP: // logical product V=L**V
valu = *litm & valu;
break;
case CAS: // arithmetic sum V=L+V
valu = *litm + valu;
break;
case CAD: // arithmetic diff V=L-V
valu = *litm - valu;
break;
case CAP: // arithmetic product V=L*V
valu = *litm * valu;
break;
case CEQ: // inclusive quotent V=L+V-1
valu = (*litm + valu - 1) / valu;
break;
case CXQ: // exclusive quotent V=L/V
valu = *litm / valu;
break;
case CDS: // decimal shift
if ((n = valu) < 0)
n = abs(valu);
if (n > 9)
terr++;
valu = *litm * pow(10,n);
case CBS: // binary shift
n = valu;
valu = *litm * pow(2,n);
break; // goto CAP1
}
switch (i) {
case CEQ: // inclusive quotent
case CXQ: // exclusive quotent
case CLS: // logical sum
case CLD: // logical difference{
case CLP: // logical product
case CAP: // arithmetic product
case CDS:
case CBS:
if ((mode | *lop) & RELM) // cls1 error if either are relative
rerr++;
break;
case CAS: // arithmetic sum
if ((mode & *lop) & RELM) // cls2 error if both are relative
rerr++;
break;
case CAD: // arithmetic difference
if ((mode & (*lop ^ -1)) & RELM)
rerr++;
break;
}
// if previous mode was absolute, invert mode
if ((*lop & RELM))
mode = mode ^ RELM;
lop--; // scn6
litm--;
goto scn6; // avoided another loop
}
}
else {
*(++lop) = mode; // scn3 store op
*(++litm) = valu; // store item
var = sci(var,&t); // get next item
valu = t.word;
mode = t.mode;
}
}
return;
}
// insert literal
int scnm(char *s) {
tbl *t;
if (!pass2)
return 0;
t = srch(lt,s); // search for literal
if (*(int *)t == (int)t) {
_move(t,s,ladd,mode); // not found, insert literal in table
mode = ladd & 0100000 ? RELM : 0;
valu =ladd;
ladd++; // increment literal location
}
else {
mode = t->word & 0100000 ? RELM : 0; // sck3 found it
valu = t->word & 037777;
}
return valu;
}
// scan reference
// if just one symbol - its external ref
int scnr(int conn) {
tbl *t;
//char *s;
//int tmp;
scan(); // get expression
if (_verr <= 0) // undefined flag
return valu; // all symbol defined - no ref or literal
if (chr1 != 0) // test for no connectors
return valu; // undefined item
if (pass2) {
_verr = 0; // reset undefined flag
xerr++; // set external flag
t = srch(rt,refr); // search for reference
if (*(int *)t == (int)t) {
_move(t,refr,loc,0); // scr4 insert reference
valu = 0; // no previous ref
mode = 0;
}
else {
valu = t->word; // scr4 found it
t->word = loc; // link to next in chain
t->mode = (loc & 0100000) ? 0202 : 0200;
mode = t->mode;
}
return valu;
}
else
return 0;
}
// scan address field
int scnl() {
//tbl v;
int i = 0;
//char *s;
if (*var != '=') // test for =
i = scnr(i); // not literal - get expression
else {
var++; // skip =
scan();
i = scnm((char *)&valu);
}
return i;
}

BIN
fortransa/.DS_Store vendored Normal file

Binary file not shown.

1
fortransa/850957-84 Normal file

File diff suppressed because one or more lines are too long

43
fortransa/READ.ME Normal file
View File

@ -0,0 +1,43 @@
850957 9-SERIES 920/930 FORTRAN II SYSTEM (STAND ALONE)
AUTHOR: XEROX
ABSTRACT:
THIS IS THE STAND-ALONE 920/930 FORTRAN-II PACKAGE CONSISTING OF COMPILER, LOADER
AND RUN-TIME/LIBRARY
COMMENTS:
SOURCE LANGUAGE:SYMBOL. SIZE 4096 DECIMAL. THIS PROGRAM COVERS 850938,850959,850960.
SEE MANUALS 900587, 900 SERIES FORTRAN II OPERATIONS, 900003. 900 SERIES FORTRAN II REFERENCE MANUAL AND 901048, 900 SERIES FORTRAN II TECHNICAL MANUAL.
CONFIGURATION: ANY 920/930 COMPUTER.
This directory contains material having to do with the Stand Alone Fortran II system from the M300_19820128.tap file, catalog number 850957-84.
You may obtain the four parts of the Fortran II (Stand Alone) System, the Compiler (fort), Loader (fldr), Library (flib) and Runtime (frun), by splitting the
850957-84 file using head and tail and identifying the length of each section using tools/sds_bindmp. These files have been included here for your convience.
The 850957-84 file is composed of four sections delimited by Standard Binary Object End records and library catalog cards.
1. The Compiler, preceeded by a two card loader and terminated by an end record.
2. The Loader, preceeded by a two card loader and terminated by an end record.
3. The Library with 55 object decks, each preceeded by a catalog record and terminated by an end record (exept the last). The catalog record is a Hollerith BCD image beginning with the characters ^2 folowed by spaces and a file name. The last object deck has a catalog record with the file name SYS777 and has no end card.
4. The Runtime program, preceeded by a two card loader and (supposedly) terminated by an end record. (See problem 2. below)
Consult the Fortran II Operations Manual, 900587, for operating instructions for compiling and loading programs.
There are two problems with the 850957-84 file extracted from both the M300_19820128.tap and M400_19820305.tap files.
1, Three of the library files have out of order records. I used xxd and vi to edit the files to straighten things out and the fld file in this repository is correct and loads ok. It appears that these problems occured when copying the original card decks to tape, perhaps cards were dropped and then put back into the deck incorrectly as some were in reverse order. A corrected version of the library was saved as flib_corrected and the original, uncorrected version of the library is found in flib_original.
2, The runtime program is missing the last several data records and the end record. The missing end record was corrected but I could not find the missing data records. This file was saved as runtime_ldr. A version of a runtime program based on the source code in the Fortran II Technical Reference Manual, (900065) is included as frun.si, frun.bo and frun.lo for experimenting. This is notably different than the corrupted runtime program on the PAL trap but it will load and begin execution of the simple.si example.
There are three command files for use with the Fortran II SA System. Use the fort or fort_ascii command files to run the compiler with either Hollerith or ASCII format input, and save the binary object deck output from the attached cp device.
Use the fortran_run command file to load and run a binary object deck loaded with files from the flib and the frun.bo runtime. Since frun.bo is not preceeded by a loader the command file includes ldr_2crd preceeding frun.bo in the input deck.
A simple HELLO WORLD example is included as hello.f with output from its execution in hello_sample. Note that there is a halt at location 5 after the load map is printed. Clear this halt by branching to location 1 to continue, then type c to continue after loading is completed to execute the program. The program currently doesn't print the HELLO WORLD message. Maybe you can figure out why?
The program fiiexample.f is also included.
The Fortran II system depended on the operator to manage cards in the reader and punch. The simulator does not close and flush input and output on those devices just because the program has halted so its up to you to reset devices or quit the simulator as necessary.

22
fortransa/fiiexample.f Normal file
View File

@ -0,0 +1,22 @@
C PROGRAM TO SOLVE THE QUADRATIC EQUATION ABCDEFGH
READ 10,A,B,C
DISC = B*B-4*A*C
IF (DISC) 15,25,35
15 R = 0.0 - 0.5 * B/A
AI = 0.5 * SQRTF(0.0-DISC)/A
PRINT 11,R,AI
GO TO 99
25 R = 0.0 - 0.5 * B/A
PRINT 21,R
GO TO 99
35 SD = SQRTF(DISC)
R1 = 0.5*(SD-B)/A
R2 = 0.5*(0.0-(B+SD))/A
PRINT 31,R2,R1
99 STOP
10 FORMAT( 3F12.5 )
11 FORMAT( 19H TWO COMPLEX ROOTS:, F12.5,14H PLUS OR MINUS,
CF12.5, 2H I )
21 FORMAT( 15H ONE REAL ROOT:, F12.5 )
31 FORMAT( 16H TWO REAL ROOTS:, F12.5, 5H AND , F12.5 )
END

1
fortransa/fldr Normal file

File diff suppressed because one or more lines are too long

1
fortransa/flib_corrected Normal file

File diff suppressed because one or more lines are too long

1
fortransa/flib_original Normal file

File diff suppressed because one or more lines are too long

1
fortransa/fort Normal file

File diff suppressed because one or more lines are too long

18
fortransa/fortran Normal file
View File

@ -0,0 +1,18 @@
; Run Fortran II system standalone
; listing typewriter output
; binary object output on card-punch
;
set log /users/admin/sds/simlog
set debug /users/admin/sds/simdebug
!cat fff/fort %1 >bootdeck
att cr bootdeck
att cp card-punch
set cpu history=7000
dep bpt1 1
dep bpt2 0
boot cr

30
fortransa/fortran_ascii Normal file
View File

@ -0,0 +1,30 @@
; Run Fortran II system standalone ascii input
;
set log /users/admin/sds/simlog
set debug /users/admin/sds/simdebug
!rm %2
! cat fortransa/fort >bootdeck
! tools/mkdeck -a %1 >>bootdeck
att cr bootdeck
att cp %2
att lpt /users/admin/sds/line-printer
att mt0 /users/admin/sds/mt0
att mt1 /users/admin/sds/mt1
att mt2 /users/admin/sds/mt2
att mt3 /users/admin/sds/mt3
set cpu history=7000
; reset bp1; punch object program
dep bpt1 0
; reset bpt2; type source statements
dep bpt2 0
;dep bpt3 0
;dep bpt4 0
boot cr

16
fortransa/fortran_run Normal file
View File

@ -0,0 +1,16 @@
set cpu history=7000
reset cr
! cat fortransa/fldr %1 fortransa/flib_corrected fortransa/ldr_2crd fortransa/frun.bo >rundeck
; reset bpt1; output on typwewriter
dep bpt1 0
; set bpt2; produce map
dep bpt2 1
; set bpt3; type lbel map
dep bpt3 1
; reset bpt4; no label trace
dep bpt4 0
att cr rundeck
boot cr

1
fortransa/frun.bo Normal file

File diff suppressed because one or more lines are too long

1741
fortransa/frun.lo Normal file

File diff suppressed because it is too large Load Diff

1739
fortransa/frun.si Normal file

File diff suppressed because it is too large Load Diff

1
fortransa/frun_original Normal file

File diff suppressed because one or more lines are too long

1
fortransa/hello.bo Normal file
View File

@ -0,0 +1 @@
ÀE@@@@@@@@@kkkkkkkk@p@@@hI @88@h X88@@ 8y@E]X@X##&Jv&)#TmJJJ X8y@hC@@@p@@@p@@@p@@@p@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@CQ>@@@@@@@@

3
fortransa/hello.f Normal file
View File

@ -0,0 +1,3 @@
PRINT 13
13 FORMAT(12H0HELLO WORLD)
END

39
fortransa/hello_sample Normal file
View File

@ -0,0 +1,39 @@
SDS 940 simulator V4.0-0 Current git commit id: 9c60c904
sim> do fortransa/fortran_run fortransa/hello.bo
/Users/admin/sds/sds-kit/fortransa/fortran_run-15> att cr rundeck
CR: 455 card Deck Loaded from rundeck
/Users/admin/sds/sds-kit/fortransa/fortran_run-16> boot cr
SIGINT will be delivered to your debugger when the ^F character is entered
LOAD MAIN PROGRAM.
HALT instruction, P: 02754 (NOP 1003,2)
sim> c
NAME ENTRY ORIGIN LAST SIZE/10 COMMON BASE
= 13 03221
$$$$$$$$ 03216 03206 03227 18 03230
203SYS 03231 03230 03242 11
211SYS 03244 03243 03316 44
223SYS 03320 03317 03333 13
235SYS 03335 03334 03452 79
*PROGRAM 03216 03206 03452 165
HALT instruction, P: 00005 (EOM 12006)
sim> dep p 1
sim> c
LOADING COMPLETE
HALT instruction, P: 00377 (NOP 10000,2)
sim> c
*STOP*
HALT instruction, P: 03241 (BRU 1)
sim>

1
fortransa/ldr_2crd Normal file
View File

@ -0,0 +1 @@
@CC@@@F@@C@Ch@@E @ Fp@RF8@C@C @@@@@@@@@@@@Xp@C@C@@FR@@@@@C@@@C@@C@^F@@FFb@@@EC@@C@EC@F@@@C@@@@@QF@C@y@@F㎝@8@C@@@&CT@C|@CF@@@F@CEX@@@@ C@8@@QF@@@ Ch@CFp@L8@Ch@p@@p@@R@@p@X@@@FX@7@@@@R@@C@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

BIN
fortransa/lib/.DS_Store vendored Normal file

Binary file not shown.

1
fortransa/lib/ABS Normal file
View File

@ -0,0 +1 @@
ˆ=7dQR2ppppp @@QR2pppp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ Eu@@@@@@,@|4@y, @p@L7 @JFL@y4@|X@L8@@%@@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Øg/@@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/ALOG Normal file
View File

@ -0,0 +1 @@
ÉmvRQ#&Wpppp @@Q#&Wppp @@#&Wpppp @@#&Wppp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]g@@@@@@#8E|@|Wp@Wh@@X@ pR#h#pFp8@Fy@#hC#8s@C#hI#pgpgX@ @gp@Fz@E,[4@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]Q^@Xp@7Lgp @#hgpIp@C#hIgpghF]h@@Fz@#h#pF @8@#hghFmhp@L%h]p@L%8^mhF[;k@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]^T@pFp@p@L%hp@L%8 mhFFp@p@L% p@L%p mhFp@L%hp@L%8Igp@@%hC@ LFy@pdmh k@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ Ă]Fy@p gE%@@Fp@8@dE EX#&WJs@C J@@a@@%@@)@@m@@1@@u@@y@@=%X ^1pguL1p@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ămb@ hzkbLsL2sLs4R=2 dT^nEz8Th&F& ,)8T^nWaQz;=yI=&&&&WzCF;[=JOuphs2*=2&&R&m]=@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@%hX@8C^QT^nEQQz8>J&1,#yv2 g;II[@%zv>>#) d @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ř%h@J@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/AMIN Normal file
View File

@ -0,0 +1 @@
QdQ7pppp @@QdQ7@ppp @@QdQ7ppp @@dQ7ppppp @EdQ7@pppp @EdQ7pppp @EQd%pppp @IQd%@ppp @I@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ém|Qd%ppp @Id%ppppp @d%@pppp @d%pppp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]au@@@@@@p@gh@udX@R%@@@@@@dX@@v%@E@@@@pC,gh@vdX@R%@I@@@@dX@Iv%@@@@@#h@|#p@m#8@=gp@7#h@;)u@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]p@Xp@ Eh@#h@>%h@8#h@p@yE @ #h@g@g4@>, @gg4@7 @*g,@&L@>g4@h8@ykh@;#h@@@@@ @1*h@y]/;@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@%C@ph8@;d@a*h@;g@=%@RX@%X@;@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@> @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@&#@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/AMOD Normal file
View File

@ -0,0 +1 @@
ˆ=QQd&Tpppp @@Qd&Tppp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@EXF@@@@@@p@|#h@L&@LJ,@|,,@Lv7,L@L ,@|L8@@%@@@@@@ I@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Øg/@@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/ATAN Normal file
View File

@ -0,0 +1 @@
ÉI@QsQ%pppp @@QsQ%ppp @@QshQpppp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ã]Lv@@@@@@#8C=L@yWp@Wh@@#hC@L8@@#hCX#hC|#pC;p@ E @TE@@y @Qg8C @p@W@@gpCXE@@ @[X@ zQ@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ã]%;@XgpCughC4 7Wp@Wh@@#hC>a8C#hCXWp@@L8@@E@@ @*gpCughC4L8@@8@ yg C; >@#8C,hC;pRypyv@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ã]2F@p#hC8#pC7#8CTpF@X@ @8pF@ @zpF@dXu#hCz#pCygC% C@ % C @ Edd@gpCz#8C#pC7yWv@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ã]Lv C &C7#pC8F2@v C Fz@%hC82@E%8C7%hCQ8@Fy@p &Czp@L&CygCp@Lu C @TFy@hp ,hCypRz,b@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ Ã]h pF@dXLdXugCp@LuhCp@Lu8C]%XC pp@L%hC4p@p@L%8Cu8@Fp@%XC> 7p@L%hC4p@L%8Cu8@]]I*@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ã]@8Fy@Lp gC=%XCX%@@L8@@%@@gpCTghC7gC8dXL%XC dXu *%XC> ydXuFp@ s@@@@gXCR spF@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ã]#Fp@dR#8CT#hC8#pC7p@%hCTp@p@gpC8mhC7#hCz#pCymhC2p@@p@L%hCpp@L%8C1mhCyp@@p@L%hCnp@L^g22@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ã]4mh%8C/mhCyp@@p@L%hC,p@L%8CmmhC7gCTFy@C%LpF@%L@@@@pF@p@gXCv ;Tp@CpF@p@%upF@gCL2z#E@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ã]%C@ CIpF@gXC| @,&C|p@L&C;Tp@L @mpF@ C@@@@@C@@@@@@F@@@@@@@@@,J@@@@@@@L@@@@@@@@@@n*@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ÃCz@CX@@@@@@@@@@@@@)*,nIICzvz^|E/X1g;8|@WQd4hJR|b/d EO* 8LdOv=pFu@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@nI@Cp&&F&[[[p;[[[kn=E&7 R@@@>@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@#b@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/COS Normal file
View File

@ -0,0 +1 @@
ノmvR&2ppppp @@&2pppp @@2%ppppp @2%pppp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@テ]@@@@@@#8C|@|Wp@Wh@@,hz @ @ dX@Qp@@ @ dX@Q8@@%h7@p @#@@@@pF@a ygX8 @WTp@CpF@Q[R@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@テ],u@Xp%@Q@@@@#8C|@|gp@#h@@Wp@Wh@@,hzp#8C @ @s&C%hv&C#hCX#pCWdX@Qp@@#hCp@RFz@C%4@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@テ];@@pp@pgpC2X@zdX@Q8@@#hCX#pCWgu#8C @m  Q Q   I I p@L8@Eh@Tp@La8>E8@]@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@テ]>) X%h7dXTp@Lp@p@LE@Eh@Tp@@TFy@ p gC%@@gpCXghCWgCFy@XpF@X@ agp=gh|gC8@>O@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ テ]p %@@pF@#hCX#pCW#8Cp@%hCp@gX8 ,p@C  p@gpCXmhCWX@E@ 48@h@#hC#pCmhCQp@@nm@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@テ] p8p@L%hC p@L%8CmhCp@@p@L%hCIp@L%8CJmhCp@@p@L%hCEp@L%8CFmhCp@@p@L%hCp@L%8CmhCWgCW@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@テ]sJ R% 7dXT Q@@@@F8@#hCX#pCWmhCW#hC#pCmhCp@L%hCOp@L%8CmhCp@L%hC p@L%8CLmhCp@L%hC|m@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@テ]g/hp@L%8CmhCp@L%hCCp@L%8CmhCp@L%hp@L%8C@%T@@@@@@C@@@@@@p@@TQ@Cm&8@hIy>8u @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@> @C@OT mvm^,,L#[)X=ha4dCp;Q>d@EFQ@|*h, 7kb; OX @@|O%*I @@@1n/F>W@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@タm|@CX@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @リdy@C[@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @

1
fortransa/lib/DIM Normal file
View File

@ -0,0 +1 @@
ˆ=7dTdppppp @@Tdpppp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@<40>m4v@@@@@@p@|#h@I&@IJ,@|k,@I@s@C%@@@@@@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ Øgh@@J@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/EXIT Normal file
View File

@ -0,0 +1 @@
<EFBFBD>%[7spppp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@<40>u|@@@@@@pQh@JCpQXs,*ChQX@@@@*,7@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@g)@@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/EXP Normal file
View File

@ -0,0 +1 @@
ˆ=7d7gppppp @@7gpppp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ã]m@@@@@@#8Q|@|Wp@Wh@@pR#8mh*&%h#gX@ TgXd @gpdpF@#h#pRF @T8@@#hOgpghR>=g@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ã]/g@X8@@@R@a %#pR#hgp p@#h#pTgpd#hgagpghR7Xk @yp@Lu |p@Lupk#h#pRgpghTO=@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ã];,@pp@@p@L%hTp@L%8#h#pTgpghR&@d@&mh&%h mhT&O%h#p@gpOFy@pF@gXhgX)  pF@ =@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ã]Cp gQ%@@@ Rgp%gh)X7gJ Is@C IXbpbp@pF@p@@#pRp@@h@#pOa % @[%1@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ Ã1@ @@@@@Q@@@@@@%h E2E@@C;2% b*Rn@ JpE@s;z4@ms2@%@ a@Ep>@8d@@@nJ@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ã @8@@WE@@ b@@E1@@8@@O7h%yh2/QRE774 av;gvsOCp[2&y8ub=hQvEQ,Qh2]#TpT@*];T@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@<08>E|b@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ø%4@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/FLOAT Normal file
View File

@ -0,0 +1 @@
ˆ=7d#&Qsppp @@#&Qspp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@À=]a@@@@@@4@|7%@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@g&@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/IABS Normal file
View File

@ -0,0 +1 @@
ˆ=QQR2pppp @@QR2ppp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@E7 @@@@@@4@|,@yE, @X@p@%@@FL@y,@|p@Lv @E @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Øg/@@ @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/IDIM Normal file
View File

@ -0,0 +1 @@
ˆ=QTdpppp @@Tdppp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@<04>m /@@@@@@#8@I@yW4@@d@@s@Cg@I%@@@@@@X@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Øgh@@J@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/IF Normal file
View File

@ -0,0 +1 @@
<EFBFBD>%>4pppppp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ă]R@@@@@@#8@Wp@ Eh@W#h@XE@@| @RJ,@|@#8@Xpp%h@gX@Xh@p@Lg@W%@@J,@|pk,@X @I@@@#@@@@RdsL@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ŕ]2@@X@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Řg;@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/IFIX Normal file
View File

@ -0,0 +1 @@
Ê]u7pppp @@7ppp @@%sppppp @@%spppp @@Q%spppp @Q%sppp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@<08>]W7@@@@@@J,@|v%@@@@@@dX@@7%@E@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Øg*@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/ISIGN Normal file
View File

@ -0,0 +1 @@
<EFBFBD>=7d2W%ppp @@2W%pp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ =n@@@@@@#8@@yp,W@@W@@ @W4@@@p@@ @p@g@%@@J,@|v @I@@@@, @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Řgv@@T@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/LOCF Normal file
View File

@ -0,0 +1 @@
ˆ%gb#&pppp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@À=8@@@@@@4@y @W%@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@g&@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/MOD Normal file
View File

@ -0,0 +1 @@
ˆ%gd&Tppppp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@<40>%EF@@@@@@#8@@yW4@@d@p@Lg@%@@@@@@p@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@gk@@I@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/SIGN Normal file
View File

@ -0,0 +1 @@
<EFBFBD>=Q2W%pppp @@2W%ppp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ĂEuF@@@@@@#8@T@yWp@,@Wp@@, @LW4@@7 @ J,@|@L8@@@ @RL8@@g@T%@@@@@@Ip@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@g7@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/SQRT Normal file
View File

@ -0,0 +1 @@
ˆ=Q2h)spppp @@2h)sppp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @Ã]b@@@@@@#8R|@|Wp@Wh@@E@@ @ @h@ @*#h#pOpLFz@a @npF@v @;uh@7& uh@s& uh@/&OpE@7 >@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @ Ã][E@Xd@pF@Fp@ghphE@TFp@Fp@&hO#hQ1@J&hOF @T%hQ%hOp gR%@@X2h)sL8@@ @J@@@C/ gd [@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @Ãm@@pn;u]TCmnRC*gO |4C 7 =RyI [z^d 8dT,, ]R);LFC &LC4# nRL4Qp 2 J=4F7#s#@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @<08>m,O@y1JW;I|C|FEbC@4L[LX@u4@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @Ø&1@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @

1
fortransa/lib/SYS160 Normal file
View File

@ -0,0 +1 @@
ˆ%^dF@282pp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ %@@@@C8@JWp@@ @WCh@ X@@@@@LJ@@ X@@E@J@@@@@@@@@@L]EmR4 @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ˆ=uL282pp@EC282pp@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Øg,@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/SYS201 Normal file
View File

@ -0,0 +1 @@
<EFBFBD>%b@282pp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Ŕ=Xm@@@@@@p@yCh@%@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@g&@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/SYS202 Normal file
View File

@ -0,0 +1 @@
ˆ%b@282pp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@<40>]^Q@@@@@@p@E@@ @E%@@XQ)W%%@@F@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ Øg*@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/SYS203 Normal file
View File

@ -0,0 +1 @@
ˆ%^b@C282pp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@<04>mb@@@@@@@pQh@ICpQX&g,*ChQ@@@@@@*,2s@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@Øgh@@J@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@

1
fortransa/lib/SYS204 Normal file
View File

@ -0,0 +1 @@
ˆ%b@282pp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @ÃE2#@@@@@@C8@XC#X@@@Op@p@p@@p@TCh@ @@@@E@@F@@E@@X22@@@ @@@@@,8 @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ g7@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @

1
fortransa/lib/SYS205 Normal file
View File

@ -0,0 +1 @@
ˆ%Xb@E282pp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @=@@@@@@@C8@XX%X@@@p@p@h@z@@@@@=F@@8@ @=Ch@=E@@X2#F@@E@@p@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @Øgv@@T@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @

1
fortransa/lib/SYS205- Normal file
View File

@ -0,0 +1 @@
ˆ%Xb@E282pp @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @=@@@@@@@C8@XX%X@@@p@p@h@z@@@@@=F@@8@ @=Ch@=E@@X2#F@@E@@p@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @Øgv@@T@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ @

Some files were not shown because too many files have changed in this diff Show More