Commented source code for BTPINS

    C.BTPINS
001 SUBROUTINE BTPINS(ROOT,SIZE,BFILE,DFILE,ID,ITEM)
002 * Insert a key into B-tree with nodes in following format:
003 *   AMC 0:  Arbitrary node number.
004 *   AMC 1:  Count of keys in node.
005 *   AMC 2:  Keys, stored as a subvalue list.
006 *   AMC 3:  (number of keys)+1 pointers to next nodes.
007 *   AMC 4:  Pointer to parent node if any.
008 INS.ID = ID ;* So we can clobber id while backing up without hurting CALLer
009 CALL BTPKEY(ROOT,INS.ID,ITEM,FINDKEY) ;* Get sort string for comparing to rest of tree
010 READ NODE.ID FROM BFILE,ROOT ELSE ;* No ptr to root, file must be empty, create empty root
011   READ NODE.ID FROM BFILE,"NEXT.ID" ELSE NODE.ID=0
012   WRITE (NODE.ID+1) ON BFILE,"NEXT.ID"
013   WRITE NODE.ID ON BFILE,ROOT
014   WRITE "" ON BFILE,NODE.ID
015   END
016 BACKINGUP = 0 ;* Flopped true when backtracking for promotions
017 NEW.PTR = "" ;* Pointer to sibling when promoting key into parent during backup
018 100 READ NODE FROM BFILE,NODE.ID ELSE STOP "Can't find node"
019 LEFT = 0 ; RIGHT = NODE<1>+1 ;* Boundaries for binary search of keys in node
020 IF RIGHT = 1 THEN POS = 1 ELSE ;* Not an empty root
021   LOOP
022     POS = INT((LEFT+RIGHT)/2) ;* Find position midway between boundaries
023     COMPARE.ID = NODE<2,POS> ;* Get that key
024     IF COMPARE.ID = INS.ID THEN ;* Key is already in node
025       CRT "Already in node"
026       IF BACKINGUP THEN STOP ELSE RETURN
027       END
028     READ COMPARE.ITEM FROM DFILE, COMPARE.ID ELSE STOP "Can't read"
029     CALL BTPKEY(ROOT,COMPARE.ID,COMPARE.ITEM,KEY) ;* Convert COMPARE.ITEM to KEY for comparison
030     IS.GREATER = (FINDKEY > KEY) ;* Is our key greater than node key?
031     IF IS.GREATER THEN LEFT = POS ELSE RIGHT = POS ;* Adjust search boundaries
032   UNTIL (RIGHT-LEFT) <= 1 DO REPEAT
033   IF IS.GREATER THEN POS = RIGHT ;* Else POS already OK
034   END
035 * POS points to where next key should be inserted if this is a leaf
036 NEXT.NODE.ID = NODE<3,POS> ;* Key not in this node, get pointer to next node
037 IF (NEXT.NODE.ID # "") AND NOT(BACKINGUP) THEN ;* Pointer exists for our downward trip, follow it
038   NODE.ID = NEXT.NODE.ID
039   GO TO 100
040   END
041 NODE = INSERT(NODE, 2, POS; INS.ID) ;* Hit a leaf or we've backed up, insert the key
042 IF BACKINGUP THEN NODE = INSERT(NODE, 3, POS+1; NEW.PTR) ;* Include ptr to new node
043 NODE<1> = NODE<1>+1 ;* Increment count of keys in this node
044 IF NODE<1> <= 2*SIZE THEN WRITE NODE ON BFILE,NODE.ID ELSE ;* Node full, split it
045   LOOP ;* Create new id for new node
046     READ NEW.PTR FROM BFILE,"NEXT.ID" ELSE NEW.PTR=0
047     WRITE (NEW.PTR+1) ON BFILE,"NEXT.ID"
048     READ NEW.NODE FROM BFILE,NEW.PTR ELSE NEW.NODE=""
049   UNTIL NEW.NODE = "" DO REPEAT
050   J = 1 ;* Copy right half of overflowed node to new node
051   FOR I = SIZE+2 TO (2*SIZE)+2 ;* Range includes last pointer in node
052     IF NODE<2,I> # "" THEN NEW.NODE<2,J> = NODE<2,I> ;* I goes past last key, so don't copy nulls
053     CHILD.ID = NODE<3,I>
054     IF CHILD.ID # "" THEN ;* Not a leaf, copy ptr too
055       NEW.NODE<3,J> = CHILD.ID
056       READ CHILD FROM BFILE,CHILD.ID ELSE STOP "Can't find"
057       CHILD<4> = NEW.PTR ;* Tell child about new parent
058       WRITE CHILD ON BFILE, CHILD.ID
059       END
060     J = J+1
061   NEXT I
062   NEW.NODE<1> = SIZE ;* Set count in new half-full node
063   NEW.NODE<4> = NODE<4> ;* Copy parent id since it's the same
064   WRITE NEW.NODE ON BFILE,NEW.PTR ;* Save new node
065   INS.ID = NODE<2, SIZE+1> ;* Get median key to promote to parent node
066   NEW.NODE = SIZE ;* Drop right half of full node by copying only left half
067   FOR I = 1 TO SIZE+1 ;* Range includes last pointer before median
068     IF I <= SIZE THEN NEW.NODE<2,I> = NODE<2,I> ;* Keep leftmost half
069     IF NODE<3,I> # "" THEN NEW.NODE<3,I> = NODE<3,I> ;* Avoids nulls in leafs
070   NEXT I
071   NEW.NODE<4> = NODE<4> ;* Remember parent too
072   WRITE NEW.NODE ON BFILE,NODE.ID ;* Save only left half of old node
073   IF NEW.NODE<4> # "" THEN ;* There's a parent, insert promotee and ptr to new node
074     BACKINGUP = 1 ;* Set flag so above code immediately inserts
075     NODE.ID = NEW.NODE<4> ;* Get parent id
076     GO TO 100
077     END
078   LOOP ;* We're already in the root, create new one to let tree grow
079     READ ROOT.ID FROM BFILE,"NEXT.ID" ELSE ROOT.ID=0
080     WRITE (ROOT.ID+1) ON BFILE,"NEXT.ID"
081     READ NEW.NODE FROM BFILE,ROOT.ID ELSE NEW.NODE=""
082   UNTIL NEW.NODE = "" DO REPEAT
083   NEW.NODE<1> = 1
084   NEW.NODE<2> = INS.ID
085   NEW.NODE<3,1> = NODE.ID
086   NEW.NODE<3,2> = NEW.PTR
087   WRITE NEW.NODE ON BFILE,ROOT.ID
088   WRITE ROOT.ID ON BFILE,ROOT
089   READ NEW.NODE FROM BFILE, NODE.ID ELSE STOP "Can't reread"
090   NEW.NODE<4> = ROOT.ID ;* Let child know its new parent, the root
091   WRITE NEW.NODE ON BFILE, NODE.ID
092   READ NEW.NODE FROM BFILE, NEW.PTR ELSE STOP "Can't reread"
093   NEW.NODE<4> = ROOT.ID ;* Do same for other child, the newly created node
094   WRITE NEW.NODE ON BFILE, NEW.PTR
095   END
096 RETURN
097 END