perm filename SYMSRT.FAI[GEM,BGB] blob sn#040001 filedate 1973-06-17 generic text, type T, neo UTF8
COMMENT ⊗   VALID 00010 PAGES 
RECORD PAGE   DESCRIPTION
 00001 00001
 00002 00002	AC defs, SPLIT (Quicksort)
 00008 00003	Initialization
 00010 00004	Description of basic storage areas
 00014 00005	Copy the symbols
 00021 00006	Allocate areas, sort symbol table
 00025 00007	Move symbols back up, by ranges
 00028 00008	Create Block Name, pointer tables, set up base pointer table, write file
 00032 00009	Outsym, and Symbol Type Routines
 00036 00010	GET FILE SPEC FROM TTY LINE 
 00039 ENDMK
⊗;
;AC defs, SPLIT (Quicksort)
	TITLE	SORT
I←2
J←3
K←4
L←5
KEY←6
T←7
G←10
H←11
M←12
RUNBAS←14
↓P←17
UPR←←400000
SMT←←400116
COR←←400133
PTRSIZ←←4		;size of pointer area at base of new symbol table.
RNGSIZ←←5		;number of symbol ranges + 1 (for final boundary)
EXTERNAL JOBFF, JOBHRL
INTEGER BASE, BASEI, BASEK, BASEL, BASEK1, BASEL1, TABNO, SVSTK, PID, ID
INTEGER SYMBAS, NEWSIZ, OFLOW, SPRLOC, SPRSIZ, SPRFLO
ARRAY TAB [20], BLKVAL [=600], BLKNAM [=600], BLKSTK[=100], PDLSTK[=100]
;COMMENT SPLIT(I,J) -- Canonical Quicksort, with Insert sort for lists of
;	 length < 10.

; The sort is carried out through an intermediate table of pointers to
; actual elements to be sorted.  The @pointers BASEK1, etc., provide access
; to addresses within this indirect table, or to the values they represent.
; BASEK1 fetches a value.  BASEK indicates a pointer entry.  Rather than
; figure it all out, just copy sections of the current code to extend.

SPLIT:	MOVE	I,-2(P)
	MOVE	J,-1(P)
	CAIGE	J,=10(I)		;Insert Sort for groups (J-I) of
	JRST	INSERT			; length > 10.
	MOVE	K,I			;K and L compress toward each other
	MOVE	L,J			; during one pass of the sort.
	MOVE	KEY,@BASEK1		;Arbitrarily choosing as key the element
COMPIT:	CAMGE	KEY,@BASEL1		; at the low end of the range, reduce L
	 SOJA	 L,COMPIT		; until something is found whose value
	MOVE	T,@BASEL		; does not exceed the Key.
	EXCH	T,@BASEK		;Exchange table pointers, so that now the
	MOVEM	T,@BASEL		; key value has been "moved" to this spot
COMP1:	CAMLE	KEY,@BASEK1		; such that all values above it are larger.
	 AOJA	 K,COMP1		;Then increase K (using same key) until 
	MOVE	T,@BASEL		; something is found whose value is not
	EXCH	T,@BASEK		; exceeded by the key, and perform a similar
	MOVEM	T,@BASEL		; exchange.  Continue shoving things smaller
	CAME	K,L			; than the key to the left of it, and things
	 SOJA	 L,COMPIT		; larger than it to the right of it, until
DON1:	MOVE	KEY,J			; K (left) and L (right) meet.
	SUB	KEY,K			;Now from I to (K,L) and from (K,L) to J
	MOVE	T,K			; form two areas.  Sort the smaller first
	SUB	T,I			; (to get rid of it), saving the larger by
	CAMG	T,KEY			; calling split recursively.
	 JRST	 OTHER			;Then sort the larger (non-recursive
	SUBI	K,1			; this level).
	MOVEM	K,-1(P)			;This is done by putting larger new I,J
	ADDI	K,2			; (either old I to (K,L) or (K,L) to J)
	PUSH	P,K			; back into stack locs (-1(P), -2(P)), 
	PUSH	P,J			; pushing new ones onto stack for recursive
	PUSHJ	P,SPLIT			; call, then returning to code which
	JRST	SPLIT			; refetches I, J to ACs.
OTHER:	ADDI	K,1
	MOVEM	K,-2(P)			;Rather than get fancy, I just repeated the
	SUBI	K,2			; code, with approp. mods, for the two
	PUSH	P,I			; cases -- range 1 larger, or range 2 larger.
	PUSH	P,K
	PUSHJ	P,SPLIT
	JRST	SPLIT

INSERT:	POP	P,-2(P)			;The insertion sort copies all the values
	POP	P,K			; (pointers, really) into a max-sized 
	CAML	I,J			; (like 10 words, what's that?) region,
	 POPJ	 P,			;Then shoves them back in, starting at
	HRLI	K,@BASEI		; the last entry inserted each time, and
	HRRI	K,TAB			; moving down towards the base of the I,J
	MOVE	L,J			; region, moving old entries up until the
	SUBI	L,-1(I)			; correct place for each new entry is found.
	BLT	K,TAB-1(L)		;On completion, the I,J region is trivially
	SETZM	TABNO			; seen to be in correct order.
L2:	CAMLE	I,J
	 POPJ 	 P,	
	AOS	T,TABNO
	MOVE	H,TAB-1(T)
	MOVE	KEY,(H)
	MOVEI	G,@BASEI
	JRST	T1	
L1:	CAML	KEY,@-1(G)
	 JRST	 DN2
	MOVE	L,-1(G)
	MOVEM	L,(G)
	SUBI	G,1
T1:	SOJN	T,L1
DN2:	MOVEM	H,(G)
	AOJA	I,L2
;Initialization

START:	CALLI
	MOVE	P,[-=200,PDLSTK-1]
	MOVE	1,[-=200,BLKSTK-1]		;This stack's not used too
	PUSH	1,[0]				; often, so it lives in core.
	MOVEM	1,SVSTK
	INIT	1,17				;This program always reads
	SIXBIT	/DSK/				;TEST.DMP from the current  PPN
	0					; or alias.
	0	
	SETZM	LL+3
	SETZM	LL+2
start1:	outstr[asciz/File name:/]
	push p,[sixbit/dmp/]
	push p,[0]
	pushj p,getfil
	jrst start1
	lookup 1,filnam
	jrst [ outstr[asciz/File not found.
/]↔	       jrst start1 ]
;	LOOKUP	1,[LL: SIXBIT /TEST/
;		       SIXBIT /DMP/
;			0
;			0]
;	0
	MOVS	1,LL+3				;Reads the entire .DMP file into
	MOVNS	1				; the upper segment, offsetting
	ADDI	1,401074			; by the unsaved JOBJDA amount
	CALL	1,[SIXBIT /CORE2/]		; so that location x in the running
	0					; core image for TEST is found
	MOVE	1,LL+3				; in location upr+x (upr is 400000)
	HRRI	1,400073			; in the upper segment.
	MOVEI	2,
	INPUT	1,1
	HLRE	1,SMT				;SMT is UPR+JOBSYM, TEST's symtab
	HRRZS	SMT				; pointer.
	MOVEI	2,UPR				;SMT ← UPR+RH(SMT), to allow direct
	ORM	2,SMT				; reference to the symbols through
	MOVNS	1				; SMT, and avoid @ problems by 
	MOVE	2,1				; clearing lh.  Size will be

	MOVE	3,2				; different later, anyway.
	EXCH	1,JOBFF
;Description of basic storage areas
COMMENT ⊗
Storage is allocated for several areas, each identified by one or more
 @ pointers, tailored for special indexing operations.  The regions, their
 pointers, and their uses, are:

SYMBAS:	symbols copied from UPR symbol table, certain elements filtered.
	The copies are not strictly necessary until it is time to rewrite
	the symbols in modified order, but might as well move them now as
	later.

BASE:	base of pointer table.  To make sorting a bit easier, one of these
	pointers is created for each symbol entry in SYMBAS.  At first, then
	each pointer is two greater than the last.  During the sort phase, only
	these pointers move.  Then eventually the symbols will be moved back
	into the SMT region, one at a time, in the final pointer order.  This
	is not really a waste because additional bits are needed for each entry
	during the process anyway, and we can use the left half.
 BASEI: @BASEI gives the (I)th elt of the BASE table, I being the AC named I.
 BASEK: @BASEK gives the (K)th elt.
 BASEK1:@BASEK1 allows access to the symbol value indicated by the pointer in
	the Kth BASE table element.
 BASEL:	The Lth BASE element.
 BASEL1:The symbol value of same.

BLKVAL: A large (600 word) table for storing info about each block.
BLKNAM: A large table for storing the R50 name of each block.  These tables are
	statically allocated.  The index of a block name (or program name) in
	the BLKNAM table is its BID (PID), the number which will forever hereafter
	identify the block or program.

 The SMT area in the upper segment will later be expanded if necessary and 
 differentiated into segments later (the segments as described in RAID.FAI),
 but that comes later.

 At this point, it is time to allocate the above-described regions, to
 copy the symbols from the SMT, filter out the
 programs, blocks, and non-symbols, and to attach program and block identities
 to each normal symbol (since order will no longer identify them).

 To start with, R1 contains the pointer to current free storage,
		R2 contains the original symbol table size,
		R3 contains the original symbol table size, and
		JOBFF contains the original symbol table size.  All this
 was accomplished above.
⊗
;Copy the symbols

	MOVEM	1,SYMBAS		;Allocate areas and set pointers
	ADDM	1,JOBFF			; described in above opus.
	LSH	2,-1			;The pointer table is half as big
	EXCH	2,JOBFF			; as the original symbol table (at
	MOVEM	2,BASE			; most), containing only one word
	HRLI	2,I			; per entry
	MOVEM	2,BASEI
	HRLI	2,K
	MOVEM	2,BASEK
	HRLI	2,20+K			;Additional @ bit allows additional
	MOVEM	2,BASEK1		; level of reference.
	HRLI	2,L
	MOVEM	2,BASEL
	HRLI	2,20+L
	MOVEM	2,BASEL1
	HRRZS	2
	ADDB	2,JOBFF
	CALLI	2,11			;Get enough room.
	0

	SETOM	ID			;ID is updated for each new program or
	SETZM	PID			; block; PID is loaded from ID for programs
	HRLS	3			; only.  Set up all sorts of counts and
	ADD	3,SMT			; pointers, to new and old areas, and
	MOVE	5,BASE			; begin.
	AOS	4,SYMBAS
	SKIPA

LUP:	ADDI	4,2
NOINST:	SUB	3,[2,,2]		;Controls entire copy loop -- look at
	JUMPL	3,DON3			; every symbol in original SMT.
	MOVE	2,(3)			;0 for symbol name is an anomalous entry
	JUMPE	2,NOINST		; (I don't know its origin or purpose), and
	MOVE	1,1(3)			; I've chosen to omit them completely.
	LDB	6,[POINT 4,(3),3]	;0 in the symbol type bits (0:3) implies
	JUMPE	6,NEWPRG		; a program name, and 3 identifies a block
	CAIN	6,3			; name.  These will no longer be stored in
	JRST	NEWBLK			; with the symbols, so sort them out now.

Comment ⊗ We're looking at  the symbol table from top to bottom -- it was 
 set up by program, from top to bottom, a program name entry preceding (in
 the top to bottom sense) the symbols for that program, and each block entry
 preceding the symbols for that block.  Blocks appear in the order in which
 their codes end (inside→out), and each entry contains as value the block
 nesting depth, so that an increase of depth implies entry of another nest,
 while a decrease implies a passage to next level of current nest -- at any
 rate, the entire nesting tree for the program is determinable from all this.
As each program or block is encountered, ID is updated (PID too for programs).
 For the symbols below, ID and PID may be considered correct indications of
 the scope of their scope.
At NEWPRG and NEWBLK there is further discussion of the ID/PIDs, and the new
 block structure imposed.  Additional discussion is in RAID.
⊗
	MOVEM	1,(4)			;Store the copy
	MOVEM	2,-1(4)
	MOVE	6,ID			;Permanently attach the current BID
	LSH	6,5			; (same as program if no block struct.)
	HRL	4,6			; to the symbol by storing it in 0:12 of
	MOVEM	4,(5)			; the pointer word for th symbol.
	AOJA	5,LUP			; This avoids @-conflicts, and is big enuf.

Comment ⊗
 A sort of hairy stack algorithm, which I am loath to explain fully at
this time, must be used to determine the linkages between blocks and
the blocks or programs that contain them.  POPOFF controls this algorithm,
whose result is to link blocks as described in RAID.
 NEWPRG finishes up previous linkages, then stores the new program name
and associated values in BLKNAM/BLKVAL tables.   It bumps ID (and PID) to
create a new identifier to be used in symbols.
 NEWBLK performs similar activities for block names, updating ID.
⊗
NEWPRG:	MOVE	6,PID			;Block linkage is performed here only
	CAML	6,ID			; if the program had a nested block,
	JRST	NPR			; otherwise not.
	MOVEI	1,
	PUSHJ	P,POPOFF
NPR:	AOS	6,ID			;Store the new program name in
	MOVEM	2,BLKNAM(6)		; the BLKNAM table, and store
	MOVE	7,PID			; the PID of the previous program
	MOVEM	6,PID			; in the BLKVAL table -- accomplishes
	HRLM	6,BLKVAL(7)		; the linkage between programs 
	JRST	NOINST			; described in RAID.

NEWBLK:	AOS	6,ID			;Stack, link, unstack, or whatever to 
	PUSHJ	P,POPOFF		; achieve proper block likage
	MOVEM	2,BLKNAM(6)		; described in RAID -- store new
	JRST	NOINST			; block name.

POPOFF:	MOVE	7,SVSTK			;This algorithm uses the nesting
PPOF:	HRRZ	10,(7)			; levels contained in the block
	CAMG	10,1			; symbol values (0 invented for
	 JRST	 PUSHIT			; progs), and the SVSTK to keep
	POP	7,10			; track of the order of things, to
	HLRZS	10			; construct the linked lists 
	HRRM	6,BLKVAL(10)		; (using PIDs and BIDs as pointers,
	JRST	PPOF			; thus making references relative
PUSHIT:	HRL	1,6			; to the table bases) giving block
	PUSH	7,1			; relationships, described in RAID.
	MOVEM	7,SVSTK
	HRLZ	7,PID
	MOVEM	7,BLKVAL(6)
	POPJ	P,
;Allocate areas, sort symbol table

COMMENT ⊗
 Now the original symbol area indicated by SMT is enlarged if necessary
and allocated into the areas described in RAID.  Here are additional
variables and the values they represent:

NEWSIZ:	The size of the actual symbol area -- smaller than the original
	because of the removal of program and block names, and 0 symbols.
SPRSIZ:	The size allocated for expansion of the symbol table, no smaller
	than 30 nor greater than 200, but otherwise proportional to the
	number of symbols.
SPRLOC:	The beginning of the symbol expansion area, thus the end of the
	original symbols.
SPRFLO:	This expansion area is used both for main symbol definitions
	(building from the bottom), and overflow words (top down).  The
	original overflow words (see RAID again) are allocated above the
	expansion area.  SPRFLO will remain fixed, used later in building
	the basic pointer tables. 
OFLOW:	Starts out same as SPRFLO, increased as original OFLOW words are
	placed.  When finished, will indicate upper range of OFLOW area.
PTRSIZ:	The size of the pointer area at the base of the new symbol table --
	These (unrelocated) pointers will indicate to RAID the locations
	of the various areas within the new super-duper symbol table.
RNGSIZ:	The number of symbol ranges, +1 to contain the final limit (ranges
	have a lower and upper value, but middle ones serve double duty).
⊗

DON3:	MOVE	6,PID		;Here we must finish linkages for last
	CAML	6,ID		; program copied down -- sort of like
	 JRST	 NPRR		; "last card" special stuff.
	MOVEI	1,
	PUSHJ	P,POPOFF
NPRR:	HRRZS	4		;Store NEWSIZ, and calculate expansion
	SUB	4,SYMBAS	; area size, =30≤SPRSIZ≤=200
	MOVEM	4,NEWSIZ
	MOVE	1,4
	LSH	1,-5
	CAILE	1,=200
	MOVEI	1,=200
	CAIGE	1,=30
	MOVEI	1,=30
	MOVEM	1,SPRSIZ
	ADD	4,SMT		;Straightforward calc. of other params.
	ADDI	4,PTRSIZ
	HRRZM	4,SPRLOC
	ADD	4,1
	HRRZM	4,SPRFLO
	HRRZM	4,OFLOW
	SUBI	5,1		;Prepare for, and carry out, sort of
	SUB	5,BASE		; symbol table (pointers).
	PUSH	P,[0]
	PUSH	P,5
	MOVNI	5,1(5)
	HRLM	5,BASE
	PUSHJ	P,SPLIT
;Move symbols back up, by ranges

Comment ⊗
 As described in RAID, the final symbol table is not in strict order
by value -- in particular, those symbols whose low-order 27 bits are
0 (opcodes) are collected into a special range -- and all others with 
left-half values are placed in another range.  Additionally, since the 
opcode-type symbols will be stored as right-half values, the negative
ones must be stored following the positive ones within that range, in
order that symbols increase in value withing the range.
 This section of code copies the symbols back into the upper segment, 
by range, setting up range table pointers as it goes.
⊗
SETSYM:	SETOM	PID		;PID is used in here (and subroutines
	HRRZ	2,SMT		; below) as a range indicator.
	ADDI	2,PTRSIZ	;Each symbol range is composed of symbols
	MOVEI	11,TYPE1	; satisfying uniquely a set of criteria --
	PUSHJ	P,OUTSYM	; the symbol type.  OUTSYM calls the
	MOVEI	11,TYPE2	; routine with address in R11 for EACH
	PUSHJ	P,OUTSYM	; symbol, storing into the new symbol table
	MOVEI	11,TYPE3	; only those symbols satisfying the type
	PUSHJ	P,OUTSYM	; test this routine provides.  These tests
	MOVEI	11,TYPE5	; are arranged to be mutually exclusive and
	PUSHJ	P,OUTSY2	; complete, so that at the conclusion, each
	MOVEI	11,TYPE4	; symbol appears in one, and only one, range.
	PUSHJ	P,OUTSYM	;Before copying, OUTSYM updates the PID range
	MOVE	4,2		; index and records the base adr. for the range.
	SUB	4,SMT		; The final limit is inserted here by hand.
	AOS	3,PID		;OUTSY2 was called above to avoid this update,
	MOVEM	4,RANGE(3)	; combining the ranges (see TYPE3, TYPE5).
;Create Block Name, pointer tables, set up base pointer table, write file

BIGNUF:	HRRZ	2,OFLOW		;Now expand upper segment core as
	ADDI	2,RNGSIZ	; necessary to hold the remaining tables.
	ADD	2,ID
	ADD	2,ID
	CALL	2,[SIXBIT /CORE2/]
	0
SETRNG:	HRRO	2,OFLOW		;The final OFLOW indicates the first
	SUB	2,SMT		; location available for additional tables.
	HRRZ	7,SMT		;The first is the Range table, indicating
	MOVEM	2,(7)		; the beginnings and ends of each symbol
	ADDI	2,RNGSIZ	; range.
	MOVEM	2,1(7)		;All (internal, produced here) pointers
	ADD	2,SMT		; in the symbol table are relative to the
	HRRI	3,-5(2)		; base of the symbol table (except BID/PID
	HRLI	3,RANGE		; pointers in BLKVAL table and in symbol
	BLT	3,-1(2)		; entries, see below).  Much of the messing
SETBLK:	HRLI	3,BLKVAL	; around in this section involves converting
	HRR	3,2		; core locations (lower or upper) to relative
	ADD	2,ID		; pointers.
	BLT	3,(2)		;The BLKVAL table is placed just after the 
	MOVEI	3,1(2)		; range table.
	SUB	3,SMT
	HRLM	3,1(7)		;R7 locates the new symbol table base in the
	HRLI	3,BLKNAM	; upper segment -- is used to store the base
	HRRI	3,1(2)		; pointers to the different areas.
	ADD	2,ID
	BLT	3,1(2)		;BLKNAM table moved as is
	SUBI	2,UPR-2
	HRLM	2,400120	;Update JOBFF, JOBSA pointers to free
	HRRZM	2,400121	; storage in new program
	MOVE	3,SPRLOC
	SUB	3,SMT		;Insert final base table entries, and copy
	HRRZM	3,2(7)		; the OFLOW area (which was created by 
	SOS	3,SPRFLO	; the TYPE routine for full-word values.
	SUB	3,SMT
	HRRZM	3,3(7)
	MOVE	3,SPRLOC
	HRLI	3,1(3)
	SETZM	(3)
	MOVSS	3		;Clear expansion area.
	BLT	3,@SPRFLO
	SUBI	7,UPR(2)
	HRLM	7,SMT		;Update JOBSYM (size half) in new program
	MOVEI	7,UPR
	ANDCAM	7,SMT
	INIT	1,17		;Write TESU.DMP on current PPN.
	SIXBIT	/DSK/
	0
	0
	MOVEI	1,UPR		;New JOBREL, save in JOBCOR for GET.
	SUB	1,JOBHRL
	MOVNM	1,COR
	HRLZI	1,73(1)		;Size of new file
	SETZM	LL+3
	SETZM	LL+2
;	MOVEI	2,10000
;	ADDM	2,LL
;	ENTER	1,LL
	enter 1,filnam
	jrst [ outstr [asciz/Can write out file.
/]↔	       halt .-1]
	HRRI	1,400073
	MOVEI	2,
	OUTPUT	1,1
	RELEASE	1,
	CALLI	12		;Exit, that's it.
;Outsym, and Symbol Type Routines

OUTSYM:	AOS	3,PID		;First record the beginning
	MOVE	4,2		; of a new range (avoid this
	SUB	4,SMT		; by calling OUTSY2
	MOVEM	4,RANGE(3)
OUTSY2:	MOVE	3,BASE		;Now look at all the symbols,
LUP3:	MOVE	4,(3)		; picking symbol name word into
	MOVE	5,-1(4)		; R5, symbol value into R6,
	MOVE	6,(4)		; and pointer to symbol in R4,
	PUSHJ	P,(11)		; then call type routine to
	AOBJN	3,LUP3		; copy up if symbol satisfies test.
	POPJ	P,

TYPE1:	TLNN	6,-1		;Range 1 -- symbols with value
	TRNE	6,UPR		; 0≤value<400000
	 POPJ	 P,		; (lower segment)

TP1:	HLL	6,4		;When a symbol succeeds, its BID index
	MOVEM	5,(2)		; is copied from the base table word
	MOVEM	6,1(2)		; into the left half value word, both
	ADDI	2,2		; words are stored, and the output
	POPJ	P,		; pointer (R2) is updated.

TYPE2:	TLNN	6,-1		;Range 2 -- symbols with value
	TRNN	6,UPR		; 400000≤value<1000000
	 POPJ	 P,		; (upper segment)
	JRST	TP1


TYPE3:	TLNE	6,-1		;Range 3 -- symbols with non-zero bits
	TDNE	6,[400777,,-1]	; 0:8, 0 in bits 9:35 (opcodes).
	 POPJ	 P,		;Since the left half of symbol values
TP3:	MOVSS	6		; is new reserved for BID indices, the
	JRST	TP1		; actual opcode value is moved to the
				; left half.
TYPE5:	TLNE	6,-1		;And since, when this is done, the negative
	TDNE	6,[777,,-1]	; opcodes yield larger values than the
	 POPJ	 P,		; positive ones (good old two's compl),
	TLNN	6,400000	; These two subranges must be reversed -- thus
	 POPJ	 P,		; two types for the same range -- OUTSY2 is
	JRST	TP3		; called to do type 5 to avoid updating range
				; pointers -- thus combining the subranges.

TYPE4:	TLNE	6,-1		;Range 4 -- everything else -- non-zero bits
	TDNN	6,[777,,-1]	; in bits 9:17, perhaps elsewhere.
	 POPJ	 P,
	MOVEM	6,@OFLOW	;Here we move the value elsewhere, into the
	AOS	6,OFLOW		; OFLOW area, then replace the value by a
	SUB	6,SMT		; (symbol-table relative) pointer to the
	TLO	4,RUNBAS	; actual value -- allowing use of the left
	SOJA	6,TP1		; half as a BID index.  RAID decodes all this
				; correctly by observing range information.
	0
RANGE:	0↔0↔0↔0↔0
;GET FILE SPEC FROM TTY LINE 
	begin getfil
	opdef go [jrst]
	define pop0j <popj p,>
	define pop2j <jrst[sub p,[3,,3]↔jrst @3(p)]>
	define pop3j <jrst[sub p,[4,,4]↔jrst @4(p)]>
	define arg1 <-1(p)>
	define arg2 <-2(p)>
↑getfil:
	SETZM FILNAM↔SETZM EXTION
	SETZM EXTION+1↔SETZM PPPN
	MOVE 4,[POINT 6,FILNAM,-1]↔MOVEI 2,6
	INCHWL 1↔CAIN 1,15↔GO[INCHWL↔POP2J]↔AOS(P)
	JRST L+1
L:	INCHWL 1
	CAILE 1,"z"↔POP2J
	CAIL 1,"a"↔SUBI 1,40		;CONVERT LOWER CASE
	CAIN 1,"."↔GO[MOVE 4,[POINT 6,EXTION,-1]↔MOVEI 2,3↔GO L]
	CAIN 1,"["↔GO[MOVE 4,[POINT 6,PPPN,-1]  ↔MOVEI 2,3↔GO L]
	CAIN 1,","↔GO[HLRZ PPPN
		      PUSHJ P,[PPJUST:	JUMPE [OUTSTR[ASCIZ/BAD P,PN
/]↔						CLRBFI↔SOS -1(P)↔POP3J]	
		   	 		TRNE 77↔POP0J↔LSH -6↔GO PPJUST]
		      HRLM PPPN↔MOVE 4,[POINT 6,PPPN,17]↔MOVEI 2,3↔GO L]
	CAIN 1,"]"↔GO[HRRZ PPPN↔PUSHJ P,PPJUST
		   HRRM PPPN↔INCHWL 1↔GO FINQ]
FINQ:	CAIN 1,15↔GO EOL			;END OF THE LINE.
	CAIN 1,12↔POP2J
;	CAIN 1,"→"↔POP2J
	CAIG 1," "↔GO L	;IGNORE GARBAGE.
	SOJL 2,L↔SUBI 1,40↔IDPB 1,4↔GO L

EOL:	INCHWL 2
	SKIPN 2,EXTION↔MOVE 2,ARG2↔MOVEM 2,EXTION
;	SKIPN FLGBGB↔POP2J
;BGB'S DEFAULT PROJECT SPECIFICATION.
;	SKIPE 2,PPPN↔POP2J
;	MOVE 2,ARG1↔MOVEM 2,PPPN
;	SETZ 2,↔DSKPPN 2,
;	HRRM 2,PPPN
	POP2J
BEND;12/10/72------------------------------------------------------

LL:	
FILNAM:	0	;FILE NAME.
EXTION:	0	;EXTENSION.
	0
PPPN:	0	;PROJECT-PROGRAMMER.
	END	START