There have been occasional articles in the various personal computer magazines concerning the sorting of data files. Some of these have presented sort routines written in BASIC that can be used in existing programs. The complex string handling required by the sort logic is not really suitable for BASIC's rather slow execution speed. Clearly, any type of repetitive string manipulations as performed by sorting or searching functions would definitely benefit from machine language. If you continue reading you will find out how much faster machine language really is.
Before we get into the programs themselves, it would probably be beneficial to include some background information. The verb to sort is defined as: "to put in a certain place or rank according to kind, class or nature; to arrange according to characteristics:" This comes pretty close to what we sometimes want to do with the data we store in our computers and files: put it in some kind of order. Once we have arranged it we can search it quicker (imagine a disorganized phone book), list it in a more readable format, or even match it to other files that have been sorted the same way.
First we must decide where will we do the actual sorting. All of us have arranged things on a desk or table. Our sort area is, therefore, the desk or table that we use. In a computer system we have a choice of using the memory within the machine (internal) or our disk drive (external). There are problems with both of these. Computer memory is limited in size and this, in turn, limits the number of records that can be read in. The disk drive may be able to hold more data, but the speed of the device is snail-like when compared to memory. We can also use both. Divide the file up into smaller chunks which can be sorted in memory, store these on disk as temporary files, and then merge all of them together. This process is usually referred to as sub-listing or sort-merge.
The next question involves the type of sort logic (there are many ways of putting things in order). The algorithm used here is called a bubble sort. The file or list is examined two records at a time. If the second has a lower sort key than the first, the two will exchange places within the file. Why then, you ask, is it called a bubble sort: because records appear to bubble upward in memory (I didn't coin the phrase). Although this is not a very exotic methodology, it does offer several advantages such as requiring no other memory allocations for sorting and a rather quick speed if the file is not too disorganized. It will also not disturb the relative positioning of records that have equal sort keys.
There are numerous other types of sort algorithms. A selection sort would go through a list of (n) items (n-1) times, pulling out the next lowest record and adding it to the current end of a new list. This would need double the memory though. A selection and exchange sort would perform a similar function within the main sort area, selecting the lowest element during each pass, moving it upward in the list to be exchanged with the element occupying its new position. This method tends to upset the existing relative positioning. Other types involve binary tree searches and more complex algorithms.
The difference between fixed and variable length records is really just that. Fixed length records are all exactly the same size, while variable implies that all or many of the records in the file may vary in length. Record 1 may be 80 bytes long, record 2 may be 120, etc.
The choice of language is, as stated above, rather clear. Unless you have a lot of time to kill, it must be in machine language. When you're doing several hundred thousand (or million) character comparisons and swaps, you don't have time to pull out a BASIC/machine language dictionary for each line in the program (this, in essence, is what the BASIC interpreter does).
Here are some representative execution times, based on some testing we did a while back. The speeds are approximate and do not include disk input/output time. The test file consisted of 200 records, each 75 characters in length. The sort key occupied ten positions:
BASIC selection/exchange sort (in memory) - 8 minutes
BASIC bubble sort (in memory) - 12 minutes
BASIC selection sort (on disk) - 2 hours plus (hit BREAK key)
Machine language bubble (memory) - 3 seconds
The sort program was developed with flexibility in mind. It will sort fixed length or variable length records from 2 through 250 bytes in length. The sort key itself may be located anywhere in the record and can be any length (up to the size of the record). It will sort in either ascending or descending order. The records themselves must be comprised of AT ASCII characters. While in memory, they need not be terminated by end-of-line ($9B) characters.
The nominal limit of 250 characters is imposed by a possible bug in Atari's DOS II. The second half of page 5 (memory addresses 0580-05FF hex, 1408-1535 decimal) appears to be utilized as an internal I/O buffer. When more than 128 bytes are input, the excess winds up on page 6. The sort program also resides in the safe user area of page 6 (beginning at $0680 or 1664). There is a physical law that states two things cannot occupy the same place at the same time. This also holds true in computer memory. The program has been pushed as far into page 6 as it can go.
In order to use the sort, you must feed it certain parameters. The record length must be POKEd into location 205 ($00CD). The sort type (0-Ascending, 1-Descending) would be POKEd into 206 ($00CE). The starting and ending positions of the sort key will also have to be POKEd into locations 203 ($00CB) and 204 ($00CC). The program is expecting to see the offset of the sort key. The offset is the number of positions in front of that byte. For example, the first position of a record has a 0 offset, the second has an offset of 1, and the hundredth has an offset of 99. The USeR function that calls the sort will also pass the address of the string containing the file and the record count. For those who are a little unsure of what this is all about, there are a few examples coming up.
Now that you have a routine that will sort your data faster than you can say Rumpelstiltskin, how do you use it? Here are several suggestions. The easiest method is to link through our sort/file loader in Program 1 (fixed length only). Your existing program that is processing the data file is probably much, much longer than the short loader. The main advantage of using a small program is that you wind up with more free memory. And, since memory is our sort area, the more that is free, the larger the file. If you don't type the REMark statements, you'll have an even larger sort area. The disk file must be fixed length records terminated by end-of-line characters. Your existing processing program must contain the POKEs mentioned above. It may look something like this:
POKE 203,SKEYA-l:POKE 204,SKEYB-l:POKE 205,RECLEN:POKE 206,0 (for Ascending)
The call to the loader would be a RUN "D:SORTLOAD" (give the loader this filename when you save it). The sort/file loader must have your filename in the variable F$ and your program name in P$. If your processing program handles several files, you can also pass the filename by using the following statements. First, your program:
FOR I=0 TO 14:POKE 1640+I,32:NEXT I FOR I=0 TO LEN(F$):POKE 1640+I,ASC(F$(I,I)):NEXT I Note: F$ is your files name
The sort/file loader will require the following lines to be added:
70 FOR I=0 TO 14:F$(I,I)=CHR$(PEEK(1640+I)):NEXT I 80 IF F$(1,2)<>"D:" THEN ? "ERROR":END
If your processing program or file is small, you may do all of the above from within your program. Besides the same POKEs as above (you wouldn't need the filename of course), you will need the following line added to your program:
IF RC>1 THEN A=USR(1664,ADR(X$),RC)
where RC is the number of records stored in the string X$. Substitute your names where applicable.
Programs 2,3,4, and 5 comprise a sort/merge utility that uses the same sort routine. This will give you the ability to handle much larger files and variable length records. With a 40 or 48K machine you will be able to sort files that are 60,000 bytes long. (If the record length is 60 characters, that will translate to 1,000 records.) This particular version divides the file into two manageable sub-files, sorts each, and then merges them. Be careful with your disk space; the temporary file will need room also. If you have more than one drive, you can modify the program to split it three or more ways and sort even more records. For example, put the temporaries on drive 2 and the new file on drive 3. Who said micros can't handle larger files?
The sort/merge utility is a stand-alone. Program 2 will load the machine language and display a title screen. Program 3 is a menu that will allow you to select either fixed or variable length record types and other parameters. If you select fixed length, Program 4 will be called; variable length will select Program 5.
Because of the chaining between these programs, Program 3 must be saved with a filename of "D:SORTXX". Programs 4 and 5 must likewise be saved with filenames of "D:SORT.FIX" and "D:SORT.VAR", respectively. Program 2 may be saved with any filename, but "D:SORTMERG" is suggested to avoid confusion.
Now that you know how to feed the sort its required parameters and call it, you must still get it into memory. Once again, you have several options. If you have the Assembler/Editor cartridge (or a similar assembler), the source appears in Program 6. Please feel free to modify it. If you're limited to BASIC, Program 7 will load the machine language when it is run. After doing either of these, you should go directly to DOS (DOS II only) and do a binary save (option K) with the following parameters:
D1:AUTORUN.SYS,0680,06FD
Saving the machine language as AUTORUN.SYS will enable the program to auto-boot when you power up with the disk (you must power up with that disk). Do not append an INIT or RUN address to the file unless you want the machine to lockup every time you tum it on. The stand-alone sort/merge utility will automatically load the machine language when RUN "D:SORTMERG" is executed by the Atari.
10 REM CALLING PROGRAM MUST: 12 REM 14 REM * POKE RECORD LENGTH INTO LOCATION 205 15 REM * POKE BEGINNING OF SORT KEY INTO LOC 203 16 REM * POKE END OF SORT KEY INTO LOCATION 204 17 REM * POKE TYPE (ASCENDING - 0 OR DESCENDING - 1) INTO LOC 206 18 REM 19 REM THIS PROGRAM WILL LOAD FILE INTO MEMORY AND CALL MACHINE 20 REM LANGUAGE ROUTINE. WHEN COMPLETED, YOUR PROGRAM MAY BE 21 REM RE-CALLED BY EQUATING P$ TO YOUR PROGRAM NAME. 22 REM 50 DIM X$(FRE(0)-600),R$(130),F$(15),P$(15),I$(1) 59 REM REPLACE X'S WITH YOUR FILE & PROGRAM NAMES 60 P$="XXXXXX":F$="XXXXXX" 99 REM GET RECORD LENGTH 100 RET=100:R=PEEK(205) 109 REM OPEN FILE AND INPUT RECORDS 110 ? " LOADING ";F$:TRAP 600:OPEN #2,4,0,F$:L=1 120 TRAP 140:INPUT #2,R$:TRAP 40000 130 X$(L,L+R-1)=R$:L=L+R:GOTO 120 140 CLOSE #2:L=L-1:N=L/R:? " RECORDS LOADED= ";N 149 REM CALL MACHINE LANGUAGE SORT ROUTINE 150 IF N>1 THEN ? " BEGIN SORT":A=USR(1664,ADR(X$),N) 160 RET=170:? " COMPLETED SAVING ";F$ 169 REM ERASE OLD FILE AND SAVE NEW ONE 170 TRAP 600:XIO 36,#2,0,0,F$:OPEN #2,8,0,F$ 180 FOR I=1 TO L STEP R:R$=X$(I,I+R-1):? #2;R$:NEXT I 190 CLOSE #2:XIO 35,#2,0,0,F$ 199 REM RETURN TO YOUR PROGRAM ? 200 RET=200:TRAP 600:IF P$(3,4)<>"XX" THEN ? " LOADING ";P$:RUN P$ 210 END 600 ? " ERROR - ";PEEK(195):CLOSE #2 610 ? " PRESS RETURN TO CONTINUE";:INPUT I$:GOTO RET
Listing. Sort Program Load (Files).
Download (Saved BASIC) / Download (Listed BASIC)
0 DIM M$(20):FOR I=1 TO 13:READ A:M$(I)=CHR$(A):NEXT I:DATA 72,198,208,165,208,141,10,212,141,24,208,104,64 1 GRAPHICS 21:POKE 752,1:POKE 82,1 2 POKE 708,52:POKE 709,8:POKE 710,148:POKE 711,66:POKE 712,152:POKE 559,0 4 I=PEEK(560)+PEEK(561)*256:FOR J=1 TO 4:READ A,B:POKE I+A,B:NEXT J 5 A=INT(ADR(M$)/256):POKE 513,A:POKE 512,ADR(M$)-A*256 6 FOR J=14 TO 30:POKE I+J,138:NEXT J:POKE 54286,192:POKE 559,34 8 DATA 3,70,6,6,7,6,8,6 10 POKE 87,2:POSITION 2,0:? #6;"* SORT / MERGE *":? #6;"{6 SPACES}UTILITY" 12 POKE 87,5 20 FOR N=1 TO 6:READ C,X1,Y1,X2,Y2,X3,Y3,X4,Y4 24 COLOR C:PLOT X1,Y1:DRAWTO X2,Y2:DRAWTO X3,Y3:POSITION X4,Y4 26 POKE 765,C:XIO 18,#6,0,0,"S:":NEXT N 28 COLOR 2:FOR I=12 TO 27 STEP 3:PLOT 59,I:NEXT I 30 FOR Y=34 TO 38 STEP 2:COLOR 3:FOR X=15-Y+40 TO 62+Y-40 STEP 2:PLOT X,Y:NEXT X:COLOR 1:PLOT X+2,Y:NEXT Y 36 COLOR 4:PLOT 26,22:DRAWTO 26,14:DRAWTO 29,14:PLOT 30,15:PLOT 31,16:PLOT 30,17:PLOT 29,18 37 DRAWTO 27,18:DRAWTO 31,22:PLOT 34,14:DRAWTO 34,22:DRAWTO 39,22 38 PLOT 42,22:DRAWTO 42,14:DRAWTO 46,18:DRAWTO 50,14:DRAWTO 50,22 40 DATA 2,70,40,62,32,16,32,8,40,1,62,31,62,27,17,27,17,31,1,20,26,20,10,17,10,17,26 42 DATA 1,62,26,62,10,56,10,56,26,1,62,9,62,6,17,6,17,9,3,55,26,55,10,21,10,21,26 100 FOR I=0 TO 125:READ A:POKE 1664+I,A:NEXT I 102 POKE 54286,64:RUN "D:SORTXX" 105 DATA 104,104,133,217,104,133,216,104,133,209,104,133,208,169,0 110 DATA 133,218,133,207,162,1,165,216,133,214,165,217,133,215,24 120 DATA 165,214,133,212,101,205,133,214,165,215,133,213,105,0,133 130 DATA 215,164,203,165,206,240,10,177,214,209,212,144,44,240,12 140 DATA 176,19,177,214,209,212,144,13,240,2,176,30,200,196,204 150 DATA 240,227,176,23,144,223,169,1,133,218,164,205,136,177,214 160 DATA 72,177,212,145,214,104,145,212,192,0,208,241,232,224,0 170 DATA 208,2,230,207,228,208,208,172,165,209,197,207,208,166,165 180 DATA 218,201,0,208,144,96
Listing. Sort/Merge Loader.
Download (Saved BASIC) / Download (Listed BASIC)
Program 3. | Sort/Merge Menu |
(SAVE as "D:SORTXX") |
0 REM SORT/MERGE MENU 10 POKE 82,1:GRAPHICS 0:? ,"{DOWN}SORT/MERGE UTILITY":? "{DOWN}{TAB}" 20 DIM I$(1),T$(1):Q3=40000:? "{DOWN}FOR FILE TO BE SORTED, ENTER:" 30 ? "{DOWN}FIXED (F) or VARIABLE (V) LENGTH";:INPUT I$ 40 R=0:IF I$="V" THEN 70 50 IF I$<>"F" THEN 30 60 ? "RECORD LENGTH ";:TRAP 40:INPUT R:TRAP Q3:IF R<2 OR R>250 THEN 60 70 ? "SORT KEY (1st,2nd) ";:TRAP 70:INPUT SS,SE:TRAP Q3 75 IF SS>=SE OR SS<0 OR SE>250 THEN 70 80 ? "ASCENDING - 0 OR DESCENDING - 1 ";:TRAP 80:INPUT T:TRAP Q3 85 IF T<0 OR T>1 THEN 80 90 POKE 205,R:POKE 203,SS:POKE 204,SE:POKE 206,T 100 TRAP 120:IF I$="V" THEN RUN "D:SORT.VAR" 110 RUN "D:SORT.FIX" 120 ? "INSERT DISKETTE WITH SORT PROGRAM":? "PRESS RETURN ";:INPUT T$:GOTO 100
Listing. Sort/Merge Menu.
Download (Saved BASIC) / Download (Listed BASIC)
Program 4. | Fixed Length Records |
(SAVE as "D:SORT.FIX) |
0 REM SORT/MERGE - FIXED LENGTH RECORDS 20 R=PEEK(205):SS=PEEK(203)+1:SE=PEEK(204)+1:T=PEEK(206) 30 XL=FRE(0)-600:DIM X$(XL),F$(15),R$(R),T$(R),D$(7) 40 Q1=210:Q2=600:Q3=40000:D$="D1:TEMP" 50 ? "ENTER FILE NAME (Dn:name.ext)":INPUT F$ 60 TRAP 50:DO=VAL(F$(2,2)):IF DO<1 OR DO>4 THEN 50 80 ? "DRIVE NUMBER FOR SORTED FILE ";:TRAP 80:INPUT DN 90 IF DN<1 OR DN>4 THEN 80 95 D$(2,2)=STR$(DO):? "INSERT ";F$;" IN DRIVE ";DO:IF DN<>DO THEN ? "AND BLANK DISK IN DRIVE ";DN 96 ? "PRESS RETURN ";:INPUT R$ 100 ? "LOADING ";F$:TRAP Q2:OPEN #2,4,0,F$:M=0 120 L=1:? "PASS 1 - ";:GOSUB 500:IF M=0 THEN 160 140 ? "WRITING ";D$:OPEN #3,8,0,D$:GOSUB 560 150 ? "PASS 2 - ";:L=1:GOSUB 500 160 CLOSE #2:TRAP Q2:IF DO=DN THEN ? "DELETING ";F$:XIO 36,#3,0,0,F$ 170 F$(2,2)=STR$(DN):OPEN #3,8,0,F$ 180 ? "WRITING ";F$:IF M=0 THEN GOSUB 560:GOTO 400 200 TRAP Q2:OPEN #2,4,0,D$:J=1:A=1:B=1:AE=1:BE=1 210 IF A=1 THEN TRAP 330:INPUT #2,R$:TRAP Q3 220 IF B=1 THEN TRAP 340:T$=X$(J,J+R-1):J=J+R:TRAP Q3 230 IF AE=0 AND BE=0 THEN 390 240 IF AE=1 AND BE=0 THEN 300 245 IF AE=0 AND BE=1 THEN 310 250 IF T=1 THEN 280 260 IF R$(SS,SE)>T$(SS,SE) THEN 310 270 GOTO 300 280 IF R$(SS,SE)<T$(SS,SE) THEN 310 300 ? #3;R$:A=1:B=0:IF AE=0 THEN A=0:B=BE 302 GOTO Q1 310 ? #3;T$:A=0:B=1:IF BE=0 THEN B=0:A=AE 312 GOTO Q1 330 AE=0:GOTO 220 340 BE=0:GOTO 230 390 CLOSE #2:? "DELETING ";D$:XIO 33,#2,0,0,D$ 400 CLOSE #3:XIO 36,#3,0,0,F$ 410 END 500 TRAP 530:INPUT #2,R$:TRAP Q3 510 X$(L)=R$:L=L+R:IF (L+R)<XL THEN 500 520 M=1 530 L=L-1:N=L/R:? "RECORDS LOADED = ";N 540 IF N>1 THEN ? "BEGIN SORT ";:A=USR(1664,ADR(X$),N) 550 ? "END SORT":RETURN 560 FOR I=1 TO L STEP R:R$=X$(I,I+R-1):? #3;R$:NEXT I:CLOSE #3:RETURN 600 ? "ERROR - ";PEEK(195):END
Listing. Fixed Length Records.
Download (Saved BASIC) / Download (Listed BASIC)
Program 5. | Variable Length Records |
(SAVE as "D:SORT.VAR) |
0 REM SORT/MERGE - VARIABLE LENGTH RECORDS 10 SS=PEEK(203)+1:SE=PEEK(204)+1:T=PEEK(206):POKE 203,SS:POKE 204,SE 20 XL=FRE(0)-600:DIM X$(XL),F$(15),R$(251),T$(251),D$(7) 30 Q1=210:Q2=600:Q3=40000:D$="D1:TEMP":T$(1)=" ":T$(251)=" ":T$(2)=T$(1) 40 ? "ENTER FILE NAME (Dn:name.ext)":INPUT F$ 45 TRAP 40:DO=VAL(F$(2,2)):IF DO<1 OR DO>4 THEN 40 50 ? "DRIVE NUMBER FOR SORTED FILE ";:TRAP 50:INPUT DN 55 IF DN<1 OR DN>4 THEN 50 57 ? "INSERT ";F$;" IN DRIVE ";DO:IF DN<>DO THEN ? "AND BLANK DISK IN DRIVE ";DN 58 D$(2,2)=STR$(DO):? "PRESS RETURN ";:INPUT R$ 60 ? "FINDING LONGEST RECORD LENGTH":TRAP Q2:OPEN #2,4,0,F$:R=0 70 TRAP 80:INPUT #2,R$:L=LEN(R$):IF L>R THEN R=L 75 GOTO 70 80 CLOSE #2:? "LONGEST LENGTH IS ";R:IF R>250 THEN ? "TOO LONG":END 100 POKE 205,R+1:? "LOADING ";F$:TRAP Q2:OPEN #2,4,0,F$:M=0 120 L=1:? "PASS 1 - ";:GOSUB 500:IF M=0 THEN 160 140 ? "WRITING ";D$:OPEN #3,8,0,D$:GOSUB 560 150 ? "PASS 2 - ";:L=1:GOSUB 500 160 CLOSE #2:TRAP Q2:IF DO=DN THEN ? "DELETING ";F$:XIO 36,#3,0,0,F$ 170 F$(2,2)=STR$(DN):OPEN #3,8,0,F$ 180 ? "WRITING ";F$:IF M=0 THEN GOSUB 560:GOTO 400 200 TRAP Q2:OPEN #2,4,0,D$:J=1:A=1:B=1:AE=1:BE=1 210 IF A=1 THEN TRAP 330:INPUT #2,R$:TRAP Q3 220 IF B=1 THEN TRAP 340:RL=ASC(X$(J,J)):T$=X$(J+1,J+RL):J=J+R+1:TRAP Q3 230 IF AE=0 AND BE=0 THEN 390 240 IF AE=1 AND BE=0 THEN 300 245 IF AE=0 AND BE=1 THEN 310 250 IF T=1 THEN 280 260 IF R$(SS,SE)>T$(SS,SE) THEN 310 270 GOTO 300 280 IF R$(SS,SE)<T$(SS,SE) THEN 310 300 ? #3;R$:A=1:B=0:IF AE=0 THEN A=0:B=BE 302 GOTO Q1 310 ? #3;T$:A=0:B=1:IF BE=0 THEN B=0:A=AE 312 GOTO Q1 330 AE=0:GOTO 220 340 BE=0:GOTO 230 390 CLOSE #2:? "DELETING ";D$:XIO 33,#2,0,0,D$ 400 CLOSE #3:XIO 36,#3,0,0,F$ 410 END 500 TRAP 530:INPUT #2,R$:TRAP Q3:RL=LEN(R$):IF RL<R THEN R$(RL+1)=T$ 510 X$(L,L)=CHR$(RL):X$(L+1)=R$:L=L+R+1:IF (L+R+1)<XL THEN 500 520 M=1 530 L=L-1:N=L/(R+1):? "RECORDS LOADED = ";N 540 IF N>1 THEN ? "BEGIN SORT ";:A=USR(1664,ADR(X$),N) 550 ? "END SORT":RETURN 560 FOR I=1 TO L STEP R+1:RL=ASC(X$(I,I)):R$=X$(I+1,I+RL) 570 ? #3;R$:NEXT I:CLOSE #3:RETURN 600 ? "ERROR - ";PEEK(195):END
Listing. Fixed Length Records.
Download (Saved BASIC) / Download (Listed BASIC)
0100 .TITLE "MACHINE LANGUAGE BUBBLE SORT" 0110 ; 0120 ; RLM MICRO SYSTEMS 01/20/82 0130 ; 0140 ; CALLED FROM BASIC WITH: 0150 ; 0160 ; A=USR(1664,ADR(X$),RC) 0170 ; 0180 ; NOTE: X$ IS THE STRING THAT CONTAINS THE FILE 0190 ; RC IS THE NUMBER OF RECORDS 0200 ; 0210 ; THE FOLLOWING ARE POKED BY BASIC PROGRAM: 0220 ; 0230 ; SS - BEGINNING OF SORT KEY (DECIMAL- 203) 0240 ; SE - END OF SORT KEY (DECIMAL - 204) 0250 ; RL - RECORD LENGTH (DECIMAL - 205) 0260 ; TYPE - ASCENDING (0) OR DESCENDING (1) 0270 ; (DECIMAL - 206) 0280 ; 0290 ; THE ROUTINE WILL LOOP THROUGH "FILE" SWAPPING UNSORTED 0300 ; ADJOINING MEMBERS UNTIL THE "SWAP" FLAG HAS NOT BEEN SET 0310 ; IN A GIVEN PASS. THE ZERO PAGE ADDRESSES "FST" AND "SEC" 0320 ; POINT AT THE INDIVIDUAL MEMBERS BEING COMPARED. THE Y 0330 ; REGISTER IS USED AS AN INDEX POINTER FOR TESTING OR 0340 ; MOVING BYTES BETWEEN THE TWO RECORDS. 0350 ; 0360 *= $0680 START ON PAGE 6 0370 FST = $D4 MEMBER n ADDRESS (LSB,MSB) 0380 SEC = $D6 MEMBER (n+1) ADDRESS (LSB,MSB) 0390 BASE = $D8 BASE ADDRESS OF LIST (LSB,MSB) 0400 SS = $C8 FIRST POSITION OF SORT KEY 0410 SE = $CC LAST POSITION OF SORT KEY 0420 RL = $CD ELEMENT LENGTH 0430 SWAP = $DA SWAP SWITCH 0440 RC = $D0 NUMBER OF ELEMENTS (LSB,MSB) 0450 CNTH = $CF RECORD COUNTER (MSB, X REG IS LSB) 0460 TYPE = $CE SORT TYPE, 0-ASC 1-DES 0470 ; 0480 ; 0490 PLA POP # OF ARGUMENTS FROM STACK 0500 PLA 0510 STA BASE+1 SET BASE ADDRESS 0520 PLA 0530 STA BASE 0540 PLA 0550 STA RC+1 SET ELEMENT COUNT 0560 PLA 0570 STA RC 0580 ; 0590 ; 0600 BEGIN LDA #$00 START EACH PASS THROUGH FILE 0610 STA SWAP SET SWAP TO 0 0620 STA CNTH SET HIGH COUNT TO 0 0630 LDX #$01 SET X REGISTER TO 1 (LOW COUNT) 0640 LDA BASE SET POINTER (n) TO BASE 0650 STA SEC 0660 LDA BASE+1 0670 STA SEC+1 0680 ; 0690 CONT CLC 0700 LDA SEC RESET POINTERS- 0710 STA FST (n) to (n+1) 0720 ADC RL 0730 STA SEC (n+1) to (n+2) 0740 LDA SEC+1 0750 STA FST+l 0760 ADC #$00 0770 STA SEC+1 0780 LDY SS ASCII STRING COMPARISON 0790 ; 0800 COMP LDA TYPE ASCENDING OR DESCENDING? 0810 BEQ ASC SORT IS ASCENDING 0820 LDA (SEC),Y TYPE = DESCENDING 0830 CMP (FST),Y COMPARE ADJOINING MEMBERS 0840 BCC BACK (n)>(n+1) 0850 BEQ INCR (n)=(n+1) TRY AGAIN 0860 BCS FLIP (n)<(n+1) 0870 ; 0880 ASC LDA (SEC),Y TYPE = ASCENDING 0890 CMP (FST),Y COMPARE ADJOINING MEMBERS 0900 BCC FLIP (n)>(n+1) 0910 BEQ INCR (n)=(n+1) TRY AGAIN 0920 BCS BACK (n)<(n+1) 0930 ; 0940 INCR INY ADD 1 TO POINTER 0950 CPY SE END OF SORT KEY? 0960 BEQ COMP NO 0970 BCS BACK YES, NEXT ELEMENT 0980 BCC COMP NO 0990 ; 1000 FLIP LDA #$01 SWAP ELEMENTS (n),(n+1) 1010 STA SWAP SET SWAP SWITCH ON 1020 LDY RL LOAD LENGTH 1030 ; 1040 MOVE DEY SET DISPLACEMENT 1050 LDA (SEC),Y EXCHANGE BYTES 1060 PHA 1070 LDA (FST),Y 1080 STA (SEC),Y 1090 PLA 1100 STA (FST),Y 1110 CPY #$00 MORE BYTES TO SWAP? 1120 BNE MOVE YES 1130 ; 1140 BACK INX INCREMENT RECORD COUNTER 1150 CPX #$00 CHECK FOR >255 1160 BNE TEST 1170 INC CNTH ADD 1 TO HIGH COUNT 1180 ; 1190 TEST CPX RC END OF FILE? 1200 BNE CONT NO 1210 LDA RC+1 CHECK HIGH EOF 1220 CMP CNTH 1230 BNE CONT NOT END OF FILE 1240 LDA SWAP TEST FOR END OF SORT 1250 CMP #$00 ANY SWAPS? 1260 BNE BEGIN YES, START OVER 1270 RTS NO, RETURN TO CALLING PROGRAM 1280 .END
Listing. Fixed Length Records.
Download (Saved OBJect) / Download (Listed ASseMbly)
98 FOR I=0 TO 125:READ A:POKE 1664+I,A:NEXT I 100 DATA 104,104,133,217,104,133,216,104,133,209,104,133,208,169,0 110 DATA 133,218,133,207,162,1,165,216,133,214,165,217,133,215,24 120 DATA 165,214,133,212,101,205,133,214,165,215,133,213,105,0,133 130 DATA 215,164,203,165,206,240,10,177,214,209,212,144,44,240,12 140 DATA 176,19,177,214,209,212,144,13,240,2,176,30,200,196,204 150 DATA 240,227,176,23,144,223,169,1,133,218,164,205,136,177,214 160 DATA 72,177,212,145,214,104,145,212,192,0,208,241,232,224,0 170 DATA 208,2,230,207,228,208,208,172,165,209,197,207,208,166,165 180 DATA 218,201,0,208,144,96
Listing. Sort Load.
Download (Saved BASIC) / Download (Listed BASIC)
The files in this section don't follow the normal naming convention used. They follow the suggested names given by the author:
Normal Filename | BASIC/OBJ Filename used | LiST/ASseMbly Filename used | ||
P258P1: | P258P1.BAS | P258P1.LST | ||
P258P2: | SORTMERG | SORTMERG.LST | ||
P258P3: | SORTXX | SORTXX.LST | ||
P258P4: | SORT.FIX | SORTFIX.LST | ||
P258P5: | SORT.VAR | SORTVAR.LST | ||
P258P6: | SORTML.OBJ | SORTML.ASM | ||
P258P7: | SORTLOAD | SORTLOAD.LST |
Return to Table of Contents | Previous Section | Next Section