The REM-arkable Misadventures of LIST

A proper account of the deplorable life and times of the LIST routine in Commodore BASIC.

As witnessed by the author and here brought forward as a Cautionary Tale and Moral Entertainment to the Educated & Erudite Reader, in Due Gratefulness for the unflagging & sturdy & untiring Efforts as demonstrated by the Hosting Company committed to the proper & timely distribution of this humble Website and the variety of bits & bytes thereof.

A stylized title illustration.

In our last installment we had a closer look into the tokenizer routine (also known as CRUNCH) in Commodore BASIC. This time, we follow up on this by a closer look into the reverse operation, namely the “LIST” command, which — among other things — has to expand the various BASIC tokens into human readable keywords back again. What could possibly go wrong?

A Graphic Story of Failings

Content warning: the following section may contain disturbing images. ;-)

Previously, we observed that the tokenizer routine parses the payload of a REM statement like a string that extends to the very end of the line, copying any characters, there are, to the BASIC program text as-is. And we remarked that this was not how the LIST routines handles such remarks.

Let’s have fun with an example and see what happens, and what might go wrong:

Screenshot, containing a BASIC program with REM-statements amounting to a rendetion of the well-known “It Is Fine” meme in PETSCII graphics. The listing of this program contains none of these graphics characters, but a plethora of BASIC keywords, like FOR, NEXT, THEN, etc.
Listing remarks with shifted characters in Commodore BASIC (PET 2001, “New ROM”).

Well, this came unexpected!

It should be quite clear what has happened here:
Instead of just printing the characters in the REM statement as-is, reproducing them as the unquoted string, they had been parsed as, the LIST routine continues to expand any bytes with a set sign-bit — meaning, any shifted PETSCII characters — to BASIC keywords, in order to please its human masters by the presentation of readable text. The human masters are not pleased, though.

Even worse, the LIST routine may even fail entirely over this operation, aborting with an error:

Screenshot, containing a BASIC program with a REM-statement containing a shifted 'L' character. The LIST output stops after printing 'REM' and reports a syntax error.
Listing SHIFT-L in Commodore BASIC (PET 2001, “New ROM”).

Peculiarly, the listing fails over a shifted “L” character, just to report a “SYNTAX ERROR”, where there is no syntax to check, at all!
As the versed enthusiast may know already, SHIFT-L is PETSCII code 0xCC. Let‘s see, what may happen with adjacent characters (here in lower-case/upper-case mode):

Screenshot: the short program '10 rem JK MN' lists as '10 rem mid$go fornext'.
Listing shifted J,K,M,N.

That‘s interesting: LIST doesn‘t fail over anything beyond 0xCC.
There may be a system to this. Let’s compare our finding to what we know about BASIC tokens:

input graphics petscii keyword token
SHIFT-J 0xCA MID$ 0xCA (#74)
SHIFT-K 0xCB GO 0xCB (#75)
SHIFT-L 0xCC error %0 (EOList)
SHIFT-M 0xCD FOR 0x81 (#1)
SHIFT-N 0xCE NEXT 0x82 (#2)

It seems, input characters and tokens do correspond: 0xCC corresponds to the zero-byte, which terminates the keyword list, and beyond this, it wraps around! — Indeed, in our introductory experiment, there were plenty of SHIFT-Ms () and SHIFT-Ns (), and these were listed as FOR and NEXT, respectively.

To recapitulate, here’s the keyword-token table from our tokenizing episode (underlined characters indicate a set sign-bit):

Let’s verify:

Where,

SHIFT-C  CHR$(195)  0xC3 (-0x80: 67)           `LEN`
SHIFT-O  CHR$(207)  0xCF (-0x80: 79 - 76 = 3)  `DATA`
SHIFT-M  CHR$(205)  0xCD (-0x80: 77 - 76 = 1)  `FOR`
SHIFT-M  CHR$(205)  0xCD (-0x80: 77 - 76 = 1)  `FOR`
SHIFT-O  CHR$(207)  0xCF (-0x80: 79 - 76 = 3)  `DATA`
SHIFT-D  CHR$(196)  0xC4 (-0x80: 68)           `STR$`
SHIFT-O  CHR$(207)  0xCF (-0x80: 79 - 76 = 3)  `DATA`
SHIFT-R  CHR$(210)  0xD2 (-0x80: 82 - 76 = 6)  `DIM`
SHIFT-E  CHR$(197)  0xC5 (-0x80: 69)           `VAL`

— ✓ checks! —

So, let’s have a look into how LENDATAFORFORDATASTR$DATADIMVAL BASIC achieves this.

The LIST Routine

Once again, we use the “New ROM” version as common ground, since it represents a consolidated, bug-fixed version that also served as the basis for the BASIC V.2 of the VIC-20 and C64. Here, the LIST routine is found at $C5B5:

Let’s have a little walk-trough. We‘re not so much interested in the first two sections. The former reads any and parses any arguments to set up the range of the listing. The latter is mildly interesting in our context: this is were we start to list a line, by first reading and checking the high-byte of the linkt to the next line of BASIC, we check for the end of program, and then proceed to read and check the line number (if the current line number is greater than the end of the range, we really ought to finish).

With setup and checks done, we print the line number in a new line and are ready to process the payload. As we approach our first block of interest at $C608, the Y register holds a cursor (index) into the current line for the read position and the accumulator holds the code for a blank character, we’re going to print next.

C608  A4 46      iC608   LDY $46      ;restore cursor from backup
C60A  29 7F              AND #$7F     ;clear sign-bit in byte to print
C60C  20 45 CA   iC60C   JSR $CA45    ;print character
C60F  C9 22              CMP #$22     ;`"`? 
C611  D0 06              BNE iC619    ;no…
C613  A5 09              LDA $09      ;load mode flag
C615  49 FF              EOR #$FF     ;flip bits
C617  85 09              STA $09      ;store it
C619  C8         iC619   INY          ;advance cursor
C61A  F0 11              BEQ iC62D    ;branch on overflow
C61C  B1 5C              LDA ($5C),Y  ;read next char
C61E  D0 10              BNE iC630    ;branch to handle it, unless zero (EOL)

This is the major character processing loop, beginning with the output of the current character. First, we restore the cursor into the line of BASIC, then we clear the sign-bit of the byte to handle. This being now a plain and unshifted ASCII character, we jump to a subroutine to print this to the current output channel. (As we enter this on the beginning of a line, this prints the blank, we had loaded previously, separating the line number from the text to follow.)

As this subroutine (or rather, a series of subroutines and jumps) preserves the contents of the accumulator, we can check this caracter immediately for a quotation mark ("). If it is one, we flip a mode flag (in $09). At the next instruction (at $C619), the paths converge again: we advance the cursor (in Y, aborting the routine on the event of an overflow) and read the next byte. If it’s not a zero-byte, indicating the end of the line, we branch forwards to the UN-CRUNCH routineat $C630 to handle it.

C620  A8                 TAY          ;reset Y
C621  B1 5C              LDA ($5C),Y  ;read link to next line
C623  AA                 TAX          ;low-byte into X
C624  C8                 INY          ;advance cursor
C625  B1 5C              LDA ($5C),Y  ;read high-byte
C627  86 5C              STX $5C      ;store it as new base pointer (low-byte)
C629  85 5D              STA $5D      ; -"- (high-byte)
C62B  D0 B5              BNE iC5E2    ;redo, unless high-byte is zero
C62D  4C 89 C3   iC62D   JMP iC389    ;end of program, forward to BASIC warm start

If we did just reach the end of the line, we set up for the next one: by transferring the zero value in A into Y, we reset the read cursor to the very beginning of the line in memory. The first two bytes must be the link address to the next line, low-byte and high-byte, and we read them into X and A, respectively, incrementing Y as we go along. Then, we store this as the new base pointer for our read operations (in $5C and $5D).

If the high addresss byte is not zero, we loop back to the code for a new BASIC line, at $C5E2.

This is also anpther check for the end of program: if the high-byte of the link is zero and we fall through, this can’t be a legitimate line address in user memory, it must be the end-of-program marker. Thus, we have finished and jump to the exit of the routine (and from there to the BASIC warm start to reset for the next command).

UN-CRUNCH

Welcome to the main attraction: this is the reverse of the tokenizing routine, for this also known as UN-CRUNCH. This is, where we handle a character for output and expand any tokens to BASIC keywords.

C630  10 DA      iC630   BPL iC60C    ;not a token, print it…
C632  C9 FF              CMP #$FF     ;`π`?
C634  F0 D6              BEQ iC60C    ;yes, print it and redo next…
C636  24 09              BIT $09      ;check mode flag: in quoted string?
C638  30 D2              BMI iC60C    ;yes: print and redo next…
C63A  38                 SEC          ;it's a token
C63B  E9 7F              SBC #$7F     ;subtract 0x80 - 1 (clear sign-bit, add 1)
C63D  AA                 TAX          ;use as a keyword counter
C63E  84 46              STY $46      ;store cursor
C640  A0 FF              LDY #$FF     ;prepare for pre-increment loop
C642  CA         iC642   DEX          ;decrement counter
C643  F0 08              BEQ iC64D    ;count-down complete: print keyword…
C645  C8         iC645   INY          ;increment read cursor
C646  B9 92 C0           LDA $C092,Y  ;load next byte
C649  10 FA              BPL iC645    ;redo, if not last char…
C64B  30 F5              BMI iC642    ;redo for next keyword… (unconditional)

C64D  C8         iC64D   INY          ;advance cursor
C64E  B9 92 C0           LDA $C092,Y  ;load next character
C651  30 B5              BMI iC608    ;redo main character loop…
C653  20 45 CA           JSR $CA45    ;output the character
C656  D0 F5              BNE iC64D    ;redo for next keyword char (unconditional)

As we enter, the character in question is in the accumulator. If the sign-bit is not set, it’s easy: it’s a plain character and we skip forward to print it. Otherwise, there’s a check for the special case of pi (π) and another one for this being in the middle of a quoted string. In both cases, we may skip forward to output the character as-is.

Otherwise, if we arrived at $C63A, it must be a token and we’re going to expand it into a keyword.

First, we derive an index into the keword list from the token value by subtracting the sign-bit plus one (because it will be a pre-increment loop), amounting to 0x7F. The resulting value will be used for a count-down in X. (E.g., if the token was 0x82 for NEXT, it’s now 3 — and NEXT is actually the 3rd entry in the keyword list, at the zero-based index #2.) The basic idea is that we will skip over n keywords, where n is the keyword index.

But, for a start, we have to store our read cursor for later use and set up the index (in Y) for reading from the list. Because this is a pre-increment loop, we preset it to 0xFF (-1), so that it will be zero for the first iteration.

Next follows the main search-skip loop: we decrement our counter, and, if we reached zero, we’re done and our read index points to just before the proper keyword. Hence, we forward to the end of the search loop to output the given keyword. (As we enter this, this will only be true for END, where the subtraction and pre-increment result in zero, END’s very token.)
Else, if we hadn’t just read what was the last character of a word, as indicated by an unset sign-bit, we read the next character in a tight loop. If the sign-bit is set, on the other hand, it was the last character and we just skipped over an entire keyword, for which we branch to the decrement of the keyword counter for another iteration of the search-skip loop. Notably, this is an unconditional branch: if it is not a negative value, it must be a positive one.

The final part at 0xC64D is actually printing the keyword:
Our index in Y points to the last character of the keyword, just before the one, we’re meaning to print. Thus, we advance the index and read a character from the list. If it has the sign-bit set, it’s the last one and we jump to the entrance of the main character loop, where we will print it and handle any rest of the line. (Now we also know why this should have cleared the sign-bit first before printing.)
Otherwise, we print it to the current output channel by the subroutine at $CA45. This subroutine (we’ve seen it before) preserves the contents of the accumulator, as well as flags, which allows us an elegant and ROM efficient branch to the next iteration of the main character loop. — Notably, this is meant to be an unconditional branch: we just printed a character from our keyword list, and we do know our keyword list, it’s all unshifted and shifted characters. So, a BNE instruction should work fine!

LIST’s Fall & Demise

Alas, Dearest Reader, lament the state of this corruption: there is no provision to catch and handle REM, at all. For a proper inverse of the CRUNCH routine, this would have required *some* check for the respective token (0x8F). Say, just after the check for the quotation mark (`"`) at $C60F and maybe a branch to a tight read-output loop till the next zero-byte. — But, no, there’s no such thing and we’re left with no options, but shedding tears to profess our humanity (apparently a requirement for any self-respecting character in a classic Gothic novel.)

But, honestly, the rest doesn’t look too bad. Yes, tokens will be expanded in any case, but it may not be that obvious how this fails so utterly over graphics characters in remarks. For this, we have to have another look at the keyword list and how this works in conjunction with the count-down in X.

For BASIC 2.0, this starts at $C092 and spans to $C190 (underlined characters indicate a set sign-bit):

Meaning, including the terminating zero-byte, it’s exactly 255 bytes! In order to access this via a simple indexed read instruction, there was just enough space left to squeeze in the additional GO for version 2.0!

As the read index/cursor in Y wraps around on an overflow, this is perfectly in sync with the length of the list, which has exactly 76 entries. Thus, a character value of 77 lists as token 0x81, “FOR”, which is at index #1 in this list, and so on. Now we can perfectly understand how these “excess tokens” are expanded!

Demise

We still haven’t explained why SHIFT-L, PETSCII 0xCC, isn’t expanded to “END’, which is in zeroth position (0xCC-0x80=76, 76-76=0). Readers may turn their p.t. attention to what actually is in 77th position of our zero-base-indexed list: it’s the terminating zero-byte!
This may already give away that this might be about an uncaught edge-condition. Some guard isn’t what it ought to be. — And how does this manage to generate a “SYNTAX ERROR”?

The issue of the edge case is an easier one, let’s have a look at this, step by step:

Oops, this last assumption failed! Utterly! It’s not unconditional and we actually fall through!

This explains why it fails, but it doesn’t explain how it fails, namely with a syntax error!
For this, we need to take an even closer look, as in CPU trace, starting just after we skipped over the entire keyword list and load what is supposedly the first character of our keyword:

addr instr     disass       |AC XR YR SP|nvdizc|

C64D C8        INY          |CF 00 FE FA|010011| ;increment Y to first keyword char
C64E B9 92 C0  LDA $C092,Y  |CF 00 FF FA|110001| ;load it: 0x00 (terminating zero-byte)
C651 30 B5     BMI $C608    |00 00 FF FA|010011| ;end of keyword? (no)
C653 20 45 CA  JSR $CA45    |00 00 FF FA|010011| ;output...
...
...            RTS          |00 00 FF FA|000010| ;...returns with A restored (0x00)
C656 D0 F5     BNE $C64D    |00 00 FF FA|000010| ;loop for next program byte (unless zero)
C658 A9 80     LDA #$80     |00 00 FF FA|000010| ;outside of LIST routine
C65A 85 0A     STA $0A      |80 00 FF FA|100000| ;       -- " --
C65C 20 AD C8  JSR $C8AD    |80 00 FF FA|100000| ;       -- " --
...

So, what is this “outside of LIST routine”, starting at $C658, as we fall through? And why should this cause a syntax error?

                                      ;end of LIST/UN-CRUNCH
...
C653  20 45 CA           JSR $CA45    ;output the character
C656  D0 F5              BNE iC64D    ;loop (really?)

                                      ;BASIC command `FOR`
C658  A9 80              LDA #$80
C65A  85 0A              STA $0A
C65C  20 AD C8           JSR $C8AD
...

It’s the start of the FOR routine, which follows immediately after LIST in ROM!

This also proves that isn’t the output routine, which fails over the zero-byte, but the FOR routine, which is failing over another issue: as this starts its preparations, it eventually attempts to collect and parse its parameters, thus trying to access a context/state, which has been long consumed by the LIST routine. It’s thus the LIST routine, which throws the syntax error.

BASIC 4.0

Let’s repeat our earlier experiment with BASIC 4.0:

Screenshot, dimilar to a previous one, showing a BASIC program with REM-statements amounting to a rendetion of the well-known “It Is Fine” meme in PETSCII graphics. The listing of this program contains none of these graphics characters, but a plethora of BASIC keywords, like FOR, NEXT, THEN, etc.
Listing remarks with shifted characters in Commodore BASIC 4.0.

Well, this looks similar, but different: there are lots of disk commands, and what’s this, “RETURN WITHOUT GOSUB”, even twice? Clearly, this doesn’t wrap around like earlier versions. But, what does it do instead?

Let’s have a look at the keyword list of BASIC 4.0:

The keyword list has been amended for BASIC 4.0 to include various disk commands and is clearly longer than 256 bytes. Therefor, BASIC 4.0 has to use a more complex construct to access the list, involving a zero-page pointer, just as we have seen it in the tokenizer routine (of which this is — in principle — the reverse.) As a consequence it has much more tokens to play with, as seen in our “This is fine” example.

But, what happens, if we read beyond this list, if we won’t wrap around?
Well, the skip-search spills over into what follows immediately after this in ROM, which happens to be:

It’s the list of error messages, which — for menace or luck — is encoded just in the same way!
If we’re out of keywords, these will do, as well.

Because of this, BASIC 4.0 will spell shifted/upper-case “COMMODORE” in remarks slightly differently, as in “lenrecorddopendopenrecordstr$backupval“.

Now that we know this crucial fact, we may turn our attention wholeheartedly to:

Beyond the PET — Commodore BASIC V.2 (VIC-20, C64…)

The LIST routine of BASIC V.2 is very similar to the “New ROM” of the PET 2001:

As we may observe, the two versions are nearly indentical, but for a single addition: instead of directly proceeding with UN-CRUNCH-ing, the C64 version takes an indirect jump via a vector at $0306, which is set by default to the very next address, $A71A. This newly introduced indirection allows BASIC extensions to plug-in their own UN-CRUNCH routine, in order to expand any additional tokens.

C64 Kernal Rev. 3

And Kernal Rev. 3? Well, it’s exactly the same, but addresses differ a little, as the routine has moved in ROM:

Well, that’s that. Now we have seen about all, there is to see. — But we’re not finished, yet.

LIST’s Reform

The indirection introduced in Commodore BASIC V.2 allows us to sketch out a patch that would actually fix the issues with REM in LIST.

As every program byte is handled by UN-CRUNCH before output, we may introduce a quick check for the token value of REM. If it’s not REM, we jump to the stock UN-CRUNCH routine. If it is, we divert to a path of our own, where we output the keyword (no need to go over the list for this) and then output the rest the line in a tight loop.

E.g., by something along those lines:

;LIST REM-fix sketch, C64 Kernal Rev.2
;we get here from $A717 via the jump vector at $0306

          CMP #$8F      ;is it REM?
          BEQ skip      ;yes, skip next
          JMP $A71A     ;continue with normal UN-CRUNCH
skip      LDA #$52      ;print `R`
          JSR $AB47
          LDA #$45      ;print `E`
          JSR $AB47
          LDA #$4D      ;print `M`
          JSR $AB47

loop      INY           ;advance cursor
          BEQ finish    ;check overflow (line too long)
          LDA ($5F),Y   ;get next char
          BEQ iseol     ;check for EOL
          JSR $AB47     ;print it
          BNE loop      ;next char (unconditional)
 
iseol     JMP $A707     ;to LIST EOL-code…
finish    JMP $E386     ;BASIC warm start

DISCLAIMER: This is just a sketch and entirely untested!
Mind that Kernal addresses will differ with Kernal/ROM revisions.

For Kernal Rev. 3, with the system addresses adapted, it should be something like this:

;LIST REM-fix sketch, C64 Kernal Rev.3
;we get here from $A713 via the jump vector at $0306

          CMP #$8F      ;is it REM?
          BEQ skip
          JMP $A716     ;UN-CRUNCH
skip      LDA #$52
          JSR $AB47
          LDA #$45
          JSR $AB47
          LDA #$4D
          JSR $AB47

loop      INY
          BEQ finish
          LDA ($5F),Y
          BEQ iseol
          JSR $AB47
          BNE loop
 
iseol     JMP $A703     ;LIST EOL-code…
finish    JMP $E386

DISCLAIMER: This is just a sketch and entirely untested!
Mind that Kernal addresses will differ with Kernal/ROM revisions.

But it’s also here that we can discern a conceptual blemish in this plug-in concept: while other routines, like the routine for outputting a character (at $AB47), are at invariable addresses, the LIST routine is not, nor is UN-CRUNCH. But, since this is not a subroutine, we’ll have to hand over to the stock UN-CRUNCH eventually, or, if we were to replace UN-CRUNCH enterily, jump back to the entracnce of the character loop in the LIST routine — and these addresses vary with Kernal revisions by a few bytes. Meaning, any BASIC extensions making use of this or even a small patch, like this one, will have to come in multiple versions, even for a machine, which is as monolithic as the C64 is.

(A way around the problem of the moving jump targets for any LIST extensions may be to store whatever we initially found in $0306 somewhere and to calculate jump addresses from relative offsets from there and store this in another two bytes as avector for an indirect jump instruction and then return to the originally routine by this additional step of indirection. But this will require us to find at least 4 otherwise unused and safe bytes in the already crowded system RAM area. Or you could use the RAM at $C000 for this, as a proper extension will probably use this anyways. But the problem remains: If we want to read till the end of the line, and not just handle custom tokens, we need to jump back into the code before UN-CRUNCH, because this doesn’t handle a terminating zero-byte, rather assuming that this would have been caught already.)

LIST’s Defeat

Until now, we’ve always stressed that BASIC programs are forward-linked lists. And, as we’ve seen, this is perfectly true for the LIST command: it pulls itself along, from line link to line link. As it encounters an end-of-line marker, it reads the address of the next line from the very beginning of the current line from memory and sets this as the new base pointer for the next iteration.

This is not as much true for the BASIC runtime, though. Since the editor always reorders the program in memory on any edit, the program text should be always linear, without any gaps, and always in strict order of the line numbers. Therfore, in any linear context, the runtime, whenever it encounters an end-of-line (a zero-byte), assumes that what follows in memory must be the next line. It “knows” that the next two bytes are the line-link and the next two after this must be the line number and that the 5th byte into this is the start of the actual program text (there is no such thing as an entirely empy line).
Thus, it just inspects the high-byte of the link for a zero-byte, indicative of the end of the program text. But it ignores it otherwise and skips over this, since it already “knows” its current position in memory. Line links are still crucial for searching line targets, as for GOTO and GOSUB. But in linear context, even for FORNEXT loops or for finding DATA sections, not so much.

We can (ab)use this incongruency in how program sequence is handled by LIST and by the runtime to hide any number of lines from LIST, by this defeating it for the purpose of inspection and giving away our precious code to nosy users: by manipulating the line links. The runtime will still churn along happily, as long as this doesn’t involve any GOTOs, GOSUBs, or related targets inside this section. (But we may still jump around this.)

All we need to do is to manipulate the line link(s) to exclude whatever amount of lines, we want to hide.

E.g., the following short program

is stored in memory (here on a PET with programs starting in memory at $0401) as

or, disassembled:

addr  code                semantics

0401  09 04               link: $0409
0403  0A 00               line# 10
0405  41                  ascii «A»
0406  B2                  token =
0407  31                  ascii «1»
0408  00                  -EOL-
0409  13 04               link: $0413
040B  0F 00               line# 15
040D  41                  ascii «A»
040E  B2                  token =
040F  32 30 30            ascii «200»
0412  00                  -EOL-
0413  1D 04               link: $041D
0415  14 00               line# 20
0417  99                  token PRINT
0418  20 41               ascii « A»
041A  AC                  token *
041B  41                  ascii «A»
041C  00                  -EOL-
041D  00 00               -EOT-

If we want to hide line #15 from our users, all we have to do is replacing the line link for line #10 by a pointer to line #20, as found in the link to the next line for line #15:

or, in disassmbly:

addr  code                semantics

0401  09 04               link: $0413       memory address of line #20!
0403  0A 00               line# 10
0405  41                  ascii «A»
0406  B2                  token =
0407  31                  ascii «1»
0408  00                  -EOL-
0409  13 04               link: $0413       now hidden!
040B  0F 00               line# 15
040D  41                  ascii «A»
040E  B2                  token =
040F  32 30 30            ascii «200»
0412  00                  -EOL-
0413  1D 04               link: $041D       LIST continues here
0415  14 00               line# 20
0417  99                  token PRINT
0418  20 41               ascii « A»
041A  AC                  token *
041B  41                  ascii «A»
041C  00                  -EOL-
041D  00 00               -EOT-

If we list our pragram now, it looks — quite inconspicuously — like this:

But, if we run it, line #15 (“A=200”) will be still executed — and math will be apparently not what it used to be:

LIST will still work as expected, while ignoring line #15

And here’s a screenshot of our proof of concept:

Screenshot of our experiment.
Our little experiment in emulation (PET 2001, “New ROM”).

And, of course, this will not only work for just a single line, but for any amount of lines.

However, this defeat will not be a final one:
Whenever we load such a manipulated program as a BASIC program, the program is handled similar to input, enforcing a tight in-order sequence in memory, which also involves a relinking of the lines. — And so, fear not, dear reader, the once hidden lines will LIST again and no malicious code will be hidden from your eyes.

(Meaning, for a normal BASIC program, the effect can only be achieved, once the program has already been entered or loaded in its final form, by a POKE at run-time.)

And that’s it, for today.