Skip to main content

Notice

Please note that most of the software linked on this forum is likely to be safe to use. If you are unsure, feel free to ask in the relevant topics, or send a private message to an administrator or moderator. To help curb the problems of false positives, or in the event that you do find actual malware, you can contribute through the article linked here.
Topic: Audio CD ROT, Red Book CD-DA data recovery, Disc Rot (Read 15365 times) previous topic - next topic
0 Members and 1 Guest are viewing this topic.

Audio CD ROT, Red Book CD-DA data recovery, Disc Rot

Reply #25
BASIC PROGRAM UTILITY TOOL
TO INSPECT SUPERIMPOSED WAVEFORMS
IN MULTIPLE SETS OF ALMOST IDENTICAL .WAV FILES

My previous CDrot-DUMP3-27JAN12.bas program generated encouraging numerics for my audio CD data recovery experiment. But when I added some ability to see the corresponding superimposed waveforms, things did not look so good at first. It is not obvious which of the differing samples is the "right" value. And the differences seem so minor, that the whole project seems sort of pointless -- I'm not sure I'd hear the difference, in most cases. But it still seems worth trying to work out the best automated corrections for these "easy" cases -- because there are some occasional longer runs of errors in this one track that may be a challenge, and I expect some of the other tracks are in much worse shape.

I am now focusing attention on the fact that most of the disputed samples include votes for a value that is the exact linear interpolation of the adjacent values. These interpolated values seem to be the most likely to be "fake". I am guessing that almost all of the outlier non-linear values are "true" original data. I am hoping to test that approach.

The new DUMP4 BASIC program program below adds a kluge ability to plot the waveform. These added graphics interact unpredictably (because this code is so ad-hoc) with the numeric text output, but work well enough to give a very useful sample of waveform details. I've learned that pure linear sequences of 3 samples seem to occur so often in legitimate data that such data cannot be automatically discarded. But when one sample value is in dispute between the multiple copies, then discarding the apparently interpolated ones may be a good way to figure out which points are valid, by elimination. The next step is to write a program to test this, particularly by finding out how many points are still in dispute -- or end up with no candidate valid values left... Also, counting how many points are discarded by this approach in each data set copy may be a useful quality measure for each copy, leading to possibly elimating some copies from inclusion, or sections of some copies.

In order to use this interactive BASIC program, a few key lines can be adjusted to your needs:
Code: [Select]
       DELAY 30 ' MILLISECS
       CLS : X=50 '   ******* CLEAR SCREEN FOR PLOT *******
This DELAY adjusts how long the display of segments of no-error waveform remains on the screen before starting the plot of the next piece. Start with this number larger, say 5000 (for 5 seconds), and reduce it as you become familiar with what your "good" data looks like.

This is the most important line to adjust:
Code: [Select]
     IF BLKBAD>99 OR VALSMAX>2 OR TOTMINMAX>3 THEN INPUT "WAITING  ";JUNK$
It can pause the program after each error-block grid of numerics is displayed, or after particular kinds of error-blocks, depending on the logical combination of key block statistics specified.

This version of DUMP4 includes extra features to plot the linear portions of the waveform in a different color. Some PRINT statements can be un-commented to allow printout of the sample value numbers for each sequence of 3 samples that are linear.

Code: [Select]
' CDrot.bas (SmallBASIC FLTK 0.10.6 Windows XP)
' CD disc rot processing
' kd 28 jan 2012
' FIND DIFFERENCES IN .WAV FILE AND DUMP DATA BLOCK
' DUMP4 - BEFORE AND AFTER DATA BLOCK VERSION, WITH BLOCK STATISTICS AND OUTPUT FILE
' AND WITH WAVEFORM GRAPHICS

COLOR 7
PRINT DATE$;" ";TIME$;" START of CDrot-DUMP4-28JAN12.bas"
?
OUT=FREEFILE
NEWLINE$=CHR(13)+CHR(10)
NEWLINE$=CHR(13) ' TRY TO FIND A WAY IN WINDOWS FOR TEXT FILES TO WORK IN BOTH NOTEPAD AND WORDPAD
OPEN "DUMP4-OUT.TXT" FOR APPEND AS #OUT
PRINT #OUT,;NEWLINE$
PRINT #OUT, DATE$;" ";TIME$;" START of CDrot-DUMP4-28JAN12.bas";NEWLINE$

DIM PAST$(9) ' STORE PAST DATA LINES
SAMECNT=999 ' COUNT SUCCESSIVE LINES OF ALL-SAME DATA
BLOCK=0 ' COUNT DATA BLOCKS DUMPED OUT
BLKBAD=0 : MAXBLKBAD=0 ' COUNT BAD LINES IN A DATA BLOCK
VALSMAX=0 ' MAXIMUM NUMBER OF DIFFERENT VALUES IN ONE CHANNEL SET
TOTMINMAX=0 ' MAXIMUM NUMBER OF MINORITY VALUES IN ONE CHANNEL SET
DIM VMAX(1 TO 7),TMAX(1 TO 7) ' ARRAYS OF VALSMAX AND TOTMINMAX BLOCK RESULT TALLIES
BLKBADOVR=0 : BBOVR$="" : DIM BLKBADA(1 TO 9) ' TALLY BLKBAD RESULTS
N=0 ' COUNT THE INPUT/OUTPUT DATA SAMPLES
DIM XOLD(9),LLOLD(9),RROLD(9),LLOLD2(9),RROLD2(9) ' SAVE THIS POINT FOR PLOTTING LINE NEXT TIME
 
REM OPEN INPUT FILES
DIM INFILE$(9),F(9)
INFILE$(1)="E1.wav"
INFILE$(2)="E2.wav"
INFILE$(3)="E3.wav"
 INFILE$(4)="E4.wav"
 INFILE$(5)="E5.wav"
 INFILE$(6)="N1.wav"
 INFILE$(7)="N2.wav"
INFILES=0
 N=15000 : PRINT  "SKIPPING SAMPLES: ";N
FOR I = 1 TO 9
  IF INFILE$(I)<>""
    PRINT INFILE$(I);"  ";
    PRINT #OUT, INFILE$(I);"  ";
    F(I)=FREEFILE
    OPEN INFILE$(I) FOR INPUT AS #F(I)
    INFILES += 1
    REM SKIP OVER FILE HEADERS
    JJ=11 : IF LEFT(INFILE$(I),1)="N" THEN JJ=JJ+588 ' 588 SAMPLES ARE ONE SECTOR SHIFT
    JJ=JJ+N ' SPEED UP START
    FOR J = 1 TO 4*JJ
      DISCARD=BGETC(F(I))
      NEXT J   
    ENDIF
  NEXT I
PRINT : PRINT INFILES;" INPUT FILES" : PRINT
PRINT #OUT,;NEWLINE$ : PRINT #OUT, INFILES;" INPUT FILES";NEWLINE$
   
REM READ AND PROCESS ONE SET OF SAMPLES FROM EACH INPUT FILE

K215=2^15 : K216=2^16 : KBIG=K216+K215
DIM OUT$(9)
DIFF=0
 
100
L$="" : R$=""
LD=0 : RD=0
LOLD=KBIG ' INITIALIZE WITH INVALID SAMPLE VALUES
ROLD=KBIG
DIM LA(9),RA(9) ' ARRAYS OF LEFT AND RIGHT VALUES
FOR I = 0 TO 9
  LA(I)=KBIG : RA(I)=KBIG
  NEXT I
STPF=0 : STPL=0 : STPR=0 ' COUNT FILES, STOP-LEFT, STOP-RIGHT INSTANCES
FOR I = 1 TO 9
  IF INFILE$(I)<>""
      L1=BGETC(F(I))
      L2=BGETC(F(I))
      R1=BGETC(F(I))
      R2=BGETC(F(I))
      LL=L2*256+L1
      RR=R2*256+R1
      IF LL>=K215 THEN LL=LL-K216
      IF RR>=K215 THEN RR=RR-K216     
     
      IF X>820 THEN X=X-800
      IF XOLD(I)>X THEN XOLD(I)=20+I*2
      X += 2                                ' X-AXIS FOR PLOTTING WAVEFORM
  '  PSET X,600-(((LL/40)+40200) MOD 400) COLOR 9
  '  PSET X,650-(((RR/40)+40200) MOD 400) COLOR 12     
      LINE XOLD(I),600-(((LLOLD(I)/4)+40200) MOD 400),X,600-(((LL/4)+40200) MOD 400) COLOR 9
      LINE XOLD(I),650-(((RROLD(I)/4)+40200) MOD 400),X,650-(((RR/4)+40200) MOD 400) COLOR 12
     
      STPF += 1
      LLP=(LLOLD2(I)+LL)/2
      IF ABS(LLOLD(I)-LLP)<1.1      ' INTERPOLATED FAKE VALUE?
  '    PRINT LLOLD2(I),LLOLD(I),LL," LEFT CHANNEL FAKE? ";LLP
        STPL += 1
        LINE XOLD(I)+XOLD(I)-X,600-(((LLOLD2(I)/4)+40200) MOD 400),X,600-(((LL/4)+40200) MOD 400) COLOR 7
        ENDIF     
      RRP=(RROLD2(I)+RR)/2
      IF ABS(RROLD(I)-RRP)<1.1      ' INTERPOLATED FAKE VALUE?
    '    PRINT RROLD2(I),RROLD(I),RR," RIGHT CHANNEL FAKE? ";RRP
        STPR += 1
        LINE XOLD(I)+XOLD(I)-X,650-(((RROLD2(I)/4)+40200) MOD 400),X,650-(((RR/4)+40200) MOD 400) COLOR 7
        ENDIF             
     
      LLOLD2(I)=LLOLD(I) : RROLD2(I)=RROLD(I)
      XOLD(I)=X : LLOLD(I)=LL : RROLD(I)=RR ' SAVE THIS POINT FOR NEXT TIME
   
      LA(I)=LL : RA(I)=RR
      IF LL<>LOLD THEN LD=LD+1
      IF RR<>ROLD THEN RD=RD+1
      LLL$="  " : IF LL<>LOLD THEN LLL$=" *"
      RRR$="  " : IF RR<>ROLD THEN RRR$=" *"
      LOLD=LL : ROLD=RR
      L$=L$+LLL$+FORMAT("#####0",LL)
      R$=R$+RRR$+FORMAT("#####0",RR)
    ENDIF
  NEXT I
 
  IF (STPL>0 AND STPL<STPF) OR (STPR>0 AND STPR<STPF)
    JUNK$="" : '      INPUT "WAITING  ";JUNK$
    ENDIF 
  X += 10
 
N=N+1 : ' IF N>15 THEN 900
LLL$=LEFT(" *********",LD)
RRR$=LEFT(" *********",RD)

'IF (LD>1 OR RD>1) THEN PRINT N,L$,R$

INSERT PAST$,0,(FORMAT("##,###,000",N)+L$+" /"+R$)
DELETE PAST$,10
SAME = NOT (LD>1 OR RD>1)

IF NOT SAME

  SORT LA ' GROUP SAME VALUES IN ORDER
  V=LA(0) : LA(0)=1 : I=1 ' REPLACE THE VALUES WITH A COUNT OF SAME ONES
  WHILE I<=UBOUND(LA)
    IF LA(I)=V
      DELETE LA,I
      LA(I-1) = LA(I-1)+1
    ELSE
      V=LA(I) : LA(I)=1 : I += 1
    ENDIF
  WEND
  DELETE LA,UBOUND(LA) ' DELETE LAST VALUE WHICH IS COUNT OF INVALID KBIGS
  SORT LA ' SORT THE VALID COUNTS OF SAME VALUES
  VALS=UBOUND(LA)+1 : IF VALS>VALSMAX THEN VALSMAX=VALS
  TOTMIN=SUM(LA)-LA(UBOUND(LA)) : IF TOTMIN>TOTMINMAX THEN TOTMINMAX=TOTMIN

  SORT RA ' GROUP SAME VALUES IN ORDER
  V=RA(0) : RA(0)=1 : I=1 ' REPLACE THE VALUES WITH A COUNT OF SAME ONES
  WHILE I<=UBOUND(RA)
    IF RA(I)=V
      DELETE RA,I
      RA(I-1) = RA(I-1)+1
    ELSE
      V=RA(I) : RA(I)=1 : I += 1
    ENDIF
  WEND
  DELETE RA,UBOUND(RA) ' DELETE LAST VALUE WHICH IS COUNT OF INVALID KBIGS
  SORT RA ' SORT THE VALID COUNTS OF SAME VALUES
  VALS=UBOUND(RA)+1 : IF VALS>VALSMAX THEN VALSMAX=VALS
  TOTMIN=SUM(RA)-RA(UBOUND(RA)) : IF TOTMIN>TOTMINMAX THEN TOTMINMAX=TOTMIN

ENDIF

SAMEMAX=3
IF SAMECNT=SAMEMAX ' POSSIBLE END OF DATA DUMP BLOCK
  IF SAME
    SAMECNT += 1 ' YES- END OF BLOCK
    IF BLKBAD>9
      BLKBADOVR += 1
      BBOVR$=BBOVR$+","+STR(BLKBAD)
    ELSE
      BLKBADA(BLKBAD) = BLKBADA(BLKBAD)+1 ' TALLY RESULTS
    ENDIF   
    IF BLKBAD>MAXBLKBAD THEN MAXBLKBAD=BLKBAD 
    VMAX(VALSMAX)=VMAX(VALSMAX)+1 : TMAX(TOTMINMAX)=TMAX(TOTMINMAX)+1 ' TALLY RESULTS
    PRINT "BLOCK ";BLOCK;": BLKLINESBAD ";BLKBAD;BLKBADA;BLKBADOVR;" OVERS, MAX ";MAXBLKBAD;
    PRINT ", VALSMAX ";VALSMAX;VMAX;" // TOTMINMAX ";TOTMINMAX;TMAX
    PRINT "OVERS:";BBOVR$ 
   
    PRINT #OUT,N;" BLOCK ";BLOCK;": BLKLINESBAD ";BLKBAD;BLKBADA;BLKBADOVR;" OVERS, MAX ";MAXBLKBAD;;NEWLINE$
    PRINT #OUT, ", VALSMAX ";VALSMAX;VMAX;" // TOTMINMAX ";TOTMINMAX;TMAX;NEWLINE$
    PRINT #OUT, "OVERS:";BBOVR$;NEWLINE$ 
   
    JUNK$="" :                      IF BLKBAD>99 OR VALSMAX>2 OR TOTMINMAX>3 THEN INPUT "WAITING  ";JUNK$    ' ********
    IF JUNK$="STOP" THEN 900
    VALSMAX=0 : TOTMINMAX=0 ' RESET FOR NEXT BLOCK   
  ELSE
    SAMECNT = 0
    PRINT PAST$(0) ' NOT END OF BLOCK - KEEP DUMPING
    BLKBAD += 1
  ENDIF
ELSEIF SAMECNT>SAMEMAX ' NOT CURRENTLY OUTPUTTING
  IF SAME
    SAMECNT += 1 ' SAME BLANKNESS CONTINUES
    IF (SAMECNT MOD 25)=5
        DELAY 30 ' MILLISECS
        CLS : X=50 '                                    ******* CLEAR SCREEN FOR PLOT *******
        ENDIF   
  ELSE
    SAMECNT = 0 ' START DUMPING A BLOCK OUT   
    BLOCK += 1
    PRINT "BLOCK ";BLOCK
    PRINT PAST$(3)
    PRINT PAST$(2)
    PRINT PAST$(1) 
    PRINT PAST$(0)
    BLKBAD=1 ' START COUNTING BAD LINES IN THIS BLOCK
  ENDIF
ELSE 
  IF SAME
    SAMECNT += 1
  ELSE
    SAMECNT = 0
    BLKBAD += 1
  ENDIF 
  PRINT PAST$(0) ' CONTINUE OUTPUTTING
ENDIF
 
' IF LD>4 THEN 900
' IF NOT EOF(F(1)) THEN 100
FOR I = 1 TO 9
  IF INFILE$(I)<>""
    IF EOF(F(I)) THEN 800   
    ENDIF
  NEXT I
  GOTO 100 ' LOOP BACK UP TO ANOTHER SET OF SAMPLES IF NO EOF
800
PRINT "EOF"
900
    PRINT
    PRINT N;" BLOCK ";BLOCK;": BLKLINESBAD ";BLKBAD;BLKBADA;BLKBADOVR;" OVERS, MAX ";MAXBLKBAD
    PRINT ",                  VALSMAX ";VALSMAX;VMAX;" // TOTMINMAX ";TOTMINMAX;TMAX
    PRINT "OVERS:";BBOVR$     
    PRINT #OUT,N;" BLOCK ";BLOCK;": BLKLINESBAD ";BLKBAD;BLKBADA;BLKBADOVR;" OVERS, MAX ";MAXBLKBAD;;NEWLINE$
    PRINT #OUT, ", VALSMAX ";VALSMAX;VMAX;" // TOTMINMAX ";TOTMINMAX;TMAX;NEWLINE$
    PRINT #OUT, "OVERS:";BBOVR$;NEWLINE$   
FOR I = 1 TO 9
  IF INFILE$(I)<>""
CLOSE #F(I)
    ENDIF
  NEXT I
PRINT #OUT, DATE$;" ";TIME$;" END OF CD rot DUMP4 28JAN12";NEWLINE$
PRINT #OUT,;NEWLINE$ : PRINT #OUT,;NEWLINE$
CLOSE #OUT
PRINT DATE$;" ";TIME$;" END OF CD rot DUMP4 28JAN12"
STOP

Audio CD ROT, Red Book CD-DA data recovery, Disc Rot

Reply #26
Dude, seriously, you'll be better off just re-transferring the cassette tapes.


Audio CD ROT, Red Book CD-DA data recovery, Disc Rot

Reply #27
Dude, seriously, you'll be better off just re-transferring the cassette tapes.


Perhaps so. But many people trying to recover data from rotted audio CDs have no access to any other versions, so it might be useful generally to explore the best ways to do this.

Audio CD ROT, Red Book CD-DA data recovery, Disc Rot

Reply #28
BASIC PROGRAM WAV-FILT-LIN
TO RECONCILE MULTIPLE SETS OF ALMOST IDENTICAL .WAV FILES
AND PRODUCE ONE MERGED OUTPUT .WAV FILE
BY FILTERING OUT INTERPOLATED AND REPEATED VALUES

Success! Here is a working CDrot-WAV-FILT-LIN-2FEB12.bas program to reconcile and merge multiple nearly identical .wav files into one.

I re-wrote my previous program to test strategies for reconciling disputed samples in my recovered audio CD test data. Out of millions of samples, only on the order of 10,000 were in dispute. In most cases, tossing out the data points that appeared to be linear interpolations left just one apparently correct value. In most of the remaining cases, tossing out values that were repeats of the previous values resolved the dispute (why do missing samples sometimes get filled in this way?). In some cases, the remaining values were almost the same, differing only by one. In the last remaining cases, I've decided to just use the median of all the value-votes. (I had some other ideas about how to further resolve the disputes, but with this data there are only about ten cases that need to be resolved by taking the median of a range of over one, so this seems good enough for now.)

Here is the summary statistics output:
Code: [Select]
2014639 SAMPLES,   45.68342 SECONDS, 10990 LDISPUTES, 11 LRANGEOVR
10885 RDISPUTES, 13 RRANGEOVR
[0,0,0,0,0,0,0,0,0]    [0,3,2,6,0,5,5,0,0]
    [0,2258,2268,1999,0,6273,5798,0,0]    [0,2223,2245,1918,0,6143,5666,0,0]
[0,0,0,0,0,0,0,0,0]    [0,4,3,6,0,4,4,0,0]
    [0,2370,2325,2032,0,6099,5683,0,0]    [0,2330,2298,1960,0,5985,5570,0,0]
E2.wav    0    3    2258    2223   LSEQ,LSEQMAX,LSEQTOT,LSEQCNT
02/02/2012 16:50:33 END OF CD rot WAV-FILT-LIN 2FEB12

There were about 11,000 disputes in each of the left and right channels, but only 11 and 13 that had to be resolved by using the median. The max number of discarded values in any channel of any one copy was 6. The max total number of discarded values was 6273. The max number of sequential runs of discarded values in any channel of any one copy was 6143. (Using these statistics from previous runs, I decided to leave out two copies of one of the discs that had been read five times, that had a larger number of discards.)

The output sounds very good. But that doesn't mean much, since these test inputs also sound very good. Subtracting the waveforms in Audacity shows a low level of clicks that were removed throughout, which is gratifying.

It would be nice if the program would also produce an output file version of each individual input file, with the combined-reconciled output subtracted, and some summary statistics for each of those difference files, to make it more convenient to browse the differences. But although the concepts are simple, this implementation is already quite large and slow (about 30 minutes to process 6 copies of one minute of sound, interpreted BASIC on underpowered WinXP computer). There were many messy practical details needed for the program to actually work, and a large variety of exploratory features needed to learn what would work with this particular data. Faster would be great, but until you pin down exactly what works with your data, ease of modification is more important.

So far, I have tried the program on one other recovered track, that is even cleaner, with even better results, and two other tracks with more serious problems that will need further work.

It seems possible that these concepts might have enough general utility that some (better, faster) version would be a useful tool. Conceivably as Audacity plugins? But that may not be a good context for designating a sizable number of inputs...

Code: [Select]
' CDrot.bas (SmallBASIC FLTK 0.10.6 Windows XP)
' CD disc rot processing    WAV-FILT-LIN-2FEB12.bas
' kd 2 feb 2012
' FIND DIFFERENCES IN MULTIPLE .WAV FILES
' FILTER OUT INTERPOLATED (AND REPEATED) DATA POINTS
' OUTPUT ONE RECONCILED FILTERED WAV FILE
' ACCUMULATE STATISTICS
' SPEEDIER VERSION - USE SEEK AND AUTOSYNC
' USE FAST BYTE PASS-THRU FOR UNDISPUTED RUNS
' DETECT RUN OF ZEROES (PAST 30 SECS) AS END AND FILL WITH ZERO AT END
' LEFT AND RIGHT CHANNEL PROCESSING IMPLEMENTED

TDELAY=0
REM OPTION BASE 1    ' MIGHT BE NICE TO CHANGE DEFAULT ARRAY BASE FROM 0 TO 1 ?
PRINT TRUE,FALSE, NOT TRUE, NOT FALSE, TRUE, FALSE
PRINT DATE$;" ";TIME$;" START of CDrot-WAV-FILT-LIN-2FEB12.bas"
?
REPF=FREEFILE
NEWLINE$=CHR(13)+CHR(10)
NEWLINE$=CHR(13) ' TRY TO FIND A WAY IN WINDOWS FOR TEXT FILES TO WORK IN BOTH NOTEPAD AND WORDPAD
OPEN "WAV-FILT-LIN-OUT.TXT" FOR APPEND AS #REPF ' OPEN REPORTING FILE FOR APPEND
PRINT #REPF,;NEWLINE$
PRINT #REPF,"===";NEWLINE$
PRINT #REPF, DATE$;" ";TIME$;" START of CDrot-WAV-FILT-LIN-2FEB12.bas";NEWLINE$

DIM LSEQ(1 TO 9),LSEQMAX(1 TO 9),LSEQTOT(1 TO 9),LSEQCNT(1 TO 9)
                          'COUNT LEFT CHAN INVALID DATA: SEQ LENGTH, MAX SEQ, OVERALL TOTAL, COUNT OF SEQ RUNS
DIM RSEQ(1 TO 9),RSEQMAX(1 TO 9),RSEQTOT(1 TO 9),RSEQCNT(1 TO 9)
                          'COUNT RIGHT CHAN INVALID DATA: SEQ LENGTH, MAX SEQ, OVERALL TOTAL, COUNT OF SEQ RUNS
 
REM OPEN INPUT FILES
DIM INFILE$(9),F(9),GF$(9),GF(9),GFI(9),GPSAV(9)  'REM G ARRAYS ARE DENSER, ORDER VERSION OF INFILE$ & F(I)
 INFILE$(1)="E1.wav"
INFILE$(2)="E2.wav"
' INFILE$(2)="E1-MED2.wav"
INFILE$(3)="E3.wav"
' INFILE$(3)="E1-MED.wav"
 INFILE$(4)="E4.wav"
 INFILE$(5)="E5.wav"
 INFILE$(6)="N1.wav"
 INFILE$(7)="N2.wav"
A=2              'REM WHICH INFILE IS THE MAIN REF ONE FOR COPY TO OUTPUT
 
INFILES=0
'N=15700
'N=38300 ' FIRST REPEAT AT 38305
'N=70850 ' FIRST ALL-LINEAR AT 70913
' N=1900000
 : PRINT  "SKIPPING SAMPLES: ";N
FOR I = 1 TO 9
  IF INFILE$(I)<>""
    PRINT INFILE$(I);"  ";
    PRINT #REPF, INFILE$(I);"  ";
    F(I)=FREEFILE
    OPEN INFILE$(I) FOR INPUT AS #F(I)
    INFILES += 1
   
    REM SKIP OVER FILE HEADERS
    JJ=11                                'REM SKIP OVER FILE HEADERS - 44 bytes total
'    IF LEFT(INFILE$(I),1)="N" THEN JJ=JJ+588 ' 588 SAMPLES ARE ONE SECTOR SHIFT
    JJ=JJ+N ' SPEED UP START

    SEEK #F(I);(SEEK(F(I))+4*JJ) 'REM JUMP FILE POINTER
'    FOR J = 1 TO 4*JJ
'      DISCARD=BGETC(F(I))
'      NEXT J   

    ENDIF
  NEXT I
PRINT : PRINT INFILES;" INPUT FILES" : PRINT
PRINT #REPF,;NEWLINE$ : PRINT #REPF, INFILES;" INPUT FILES";NEWLINE$ : PRINT #REPF,;NEWLINE$

J=1
GFI(J)=A : GF(J)=F(A) : GF$(J)=INFILE$(A) 'REM PUT MAIN-REF INPUT FILE IN FIRST CELL OF DENSER G ARRAY
GFA=F(A) 'REM FOR QUICKER USE
FOR I = 1 TO 9
  IF INFILE$(I)<>""
    IF I<>A
      J += 1
      GFI(J)=I : GF(J)=F(I) : GF$(J)=INFILE$(I)
  ENDIF
 ENDIF
NEXT
 
' GOTO 50          'REM BYPASS AUTOSYNC?
PRINT "AUTOSYNC"
PRINT #REPF,"AUTOSYNC";NEWLINE$
NINCSAV=0 : BB=-1000 
FOR I = 1 TO 9
  IF INFILE$(I)<>""
      J=F(I)
      POLD=SEEK(F(I))
      WHILE BGETC(J)=0 :WEND   
      SEEK #F(I);(SEEK(F(I))-1)
      P=SEEK(F(I)) :  B=BGETC(F(I))
      NINC=INT((P-POLD)/4)  'REM 4 BYTES PER L-R 16-BIT SAMPLE PAIR
      SEEK #F(I);POLD+(NINC*4)  'REM POINT TO FIRST NON-ZERO SAMPLE PAIR
      IF NINCSAV=0 THEN NINCSAV=NINC
      NN=(NINC-NINCSAV)
      PRINT INFILE$(I);" ";POLD;"  POS-BYTE: ";P;" ";B; "    NINC ";NINC,NN,NN/588;" SECTOR"
      PRINT #REPF,INFILE$(I);" ";POLD;"  POS-BYTE: ";P;" ";B; "    NINC ";NINC,NN,NN/588;" SECTOR";NEWLINE$
      IF BB=-1000 THEN BB=B    'REM BB -1000 FOR NOTHING YET
      IF BB<>B THEN BB=-2000    'REM BB -2000 FOR MORE THAN ONE BYTE VALUE
  ENDIF
  NEXT
  IF BB=-2000 THEN PRINT "AUTOSYNC FAIL! STOP ***" : PRINT #REPF,"AUTOSYNC FAIL! STOP ***";NEWLINE$ : STOP
  N += NINC : PRINT N : PRINT
              PRINT #REPF,N;NEWLINE$ : PRINT #REPF,;NEWLINE$
50 
 
OUTF=FREEFILE
OPEN "OUTPUT.WAV" FOR OUTPUT AS #OUTF ' OPEN OUTPUT FILE FOR RECONCILED RESULTS
II = SEEK(F(A))
SEEK #F(A);0
J=F(A)
FOR I = 1 TO II : B=(BGETC(J)) : BPUTC #OUTF;B : NEXT 'COPY HEADER AND LEADER BYTES TO OUTPUT.WAV

     
REM READ AND PROCESS ONE SET OF SAMPLES FROM EACH INPUT FILE              ****************
K215=2^15 : K216=2^16 : KBIG=K216+K215 : KBIG=99999
EOFF=FALSE ' END OF SOME INPUT FILE
L1=KBIG 'REM FLAG OLD BYTE VALUES AS BAD TO BYPASS FIRST OUTPUT

90
REM RE-ZERO ARRAYS - DIM STATEMENTS ARE EXECUTABLE IN THIS VERSION OF BASIC
DIM LPREV(1 TO 9),LL(1 TO 9),LNEXT(1 TO 9) ' PREVIOUS, THIS, AND NEXT SAMPLES FOR EACH IN FILE
DIM RPREV(1 TO 9),RR(1 TO 9),RNEXT(1 TO 9) ' SAME FOR RIGHT CHANNEL
 
100  ' REM MAIN LOOP
IF EOFF THEN 800 ' END OF SOME INPUT FILE?
N=N+1 : ' IF N>120000 THEN 900          'REM COUNT SAMPLES PROCESSED
LDIFF=FALSE : LREF=KBIG : LNDIFF=FALSE : LNREF=KBIG
RDIFF=FALSE : RREF=KBIG : RNDIFF=FALSE : RNREF=KBIG
L11=L1:L22=L2:R11=R1:R22=R2 'REM SAVE PREVIOUS BYTES FOR OUTPUT IF NO DIFF FOUND
FOR I = 1 TO 9
  IF INFILE$(I)<>""
      L1=BGETC(F(I))
      L2=BGETC(F(I))
      R1=BGETC(F(I))
      R2=BGETC(F(I))
      L=L2*256+L1
      R=R2*256+R1
      IF L>=K215 THEN L=L-K216
      IF R>=K215 THEN R=R-K216
      IF LNREF=KBIG THEN LNREF=L
      IF LNREF<>L THEN LNDIFF=TRUE ' NEW LEFT CHAN VALUES ALL THE SAME?
      IF RNREF=KBIG THEN RNREF=R
      IF RNREF<>R THEN RNDIFF=TRUE ' NEW RIGHT CHAN VALUES ALL THE SAME?                 
      LPREV(I)=LL(I) : LL(I)=LNEXT(I) : LNEXT(I)=L ' LEFT CHAN 3-SAMPLE BUFFER
      RPREV(I)=RR(I) : RR(I)=RNEXT(I) : RNEXT(I)=R ' RIGHT CHAN 3-SAMPLE BUFFER
      IF LREF=KBIG THEN LREF=LL(I)
      IF LREF<>LL(I) THEN LDIFF=TRUE ' OLD LEFT CHAN VALUES ALL THE SAME?
      IF RREF=KBIG THEN RREF=RR(I)
      IF RREF<>RR(I) THEN RDIFF=TRUE ' OLD RIGHT CHAN VALUES ALL THE SAME?     
      IF EOF(F(I)) THEN EOFF=TRUE             
    ENDIF
  NEXT I
IF LREF=KBIG THEN PRINT "LREF=KBIG NO-DATA ERR *** STOP" : STOP
IF RREF=KBIG THEN PRINT "RREF=KBIG NO-DATA ERR *** STOP" : STOP 
'  PRINT : PRINT N
'  PRINT LPREV : PRINT LL : PRINT LNEXT : 'INPUT "  WAITING ";JUNK$

IF LDIFF OR RDIFF THEN 300  'REM NO DISPUTE -- POSSIBLE START OF NO-DISPUTE RUN?
  DIM LSEQ(1 TO 9) : DIM RSEQ(1 TO 9)    'REM ZERO LSEQ AND RSEQ COUNTERS
  IF L11=KBIG THEN 100 'REM BYPASS OUTPUT FIRST TIME, AS BUFFER FILLS
  BPUTC #OUTF;L11 :BPUTC #OUTF;L22 :BPUTC #OUTF;R11 :BPUTC #OUTF;R22 'COPY THE UNCHANGED INPUT BYTES TO OUTPUT WAV FILE
 
' J=LL(A) : IF J<0 THEN J += K216
' J2=INT(J/256) : J1=J-J2*256
' IF (J1<>L11) OR (J2<>L22) THEN PRINT "ERR *** J1 J2 BYTE MATH ***STOP ",L11,L22,J1,J2 : STOP
'  GOTO 100 
' ENDIF

IF LNDIFF OR RNDIFF THEN 100 'REM NEW-NEXT DATA HAS DISPUTES, SO GO BACK TO CONTINUED SLOW PROCESSING
REM POSSIBLE START OF RUN OF SAME BYTES FOR FAST PASS-THRU    !!!!!!!!!
BPUTC #OUTF;L1 :BPUTC #OUTF;L2 :BPUTC #OUTF;R1 :BPUTC #OUTF;R2 'COPY THE UNCHANGED INPUT BYTES TO OUTPUT WAV FILE
N += 1 : L1=KBIG : L2=KBIG : R1=KBIG : R2=KBIG 'REM EMPTY INPUT BUFFER

POLD=SEEK(GFA)
KK=LOF(GFA)-SEEK(GFA) 'REM HOW MANY BYTES LEFT IN THIS FILE?
FOR I=1 TO INFILES
  K=LOF(GF(I))-SEEK(GF(I)) : IF KK>K THEN KK=K 'REM FIND SMALLEST LEFT UNTIL EOF
  GPSAV(I)=SEEK(GF(I))  'REM SAVE INPUT FILE POSITIONS
'PRINT SEEK(GF(I)),I," OLD SEEK POSITION"
  NEXT
POUTSAV=SEEK(OUTF)

                        'REM PASS THRU BYTES FAST UNTIL DIFFERENCES FOUND
Z=0  'REM COUNT ZERO BYTES IN A ROW

IF N<44100*30    'REM FIRST 30 SECS? DON'T LOOK FOR RUN OF ZEROES....

FOR K = 1 TO KK
 B=BGETC(GFA) : BPUTC #OUTF;B
 FOR I=2 TO INFILES
  IF B<>BGETC(GF(I)) THEN 250
  NEXT
NEXT

ELSE          'REM PAST FIRST 30 SECS DO LOOK FOR RUN OF ZEROES

FOR K = 1 TO KK
 B=BGETC(GFA) : BPUTC #OUTF;B
 FOR I=2 TO INFILES
  IF B<>BGETC(GF(I)) THEN 250
  NEXT
 IF B=0
    Z +=1
    IF Z>999 THEN EXIT FOR   
  ELSE
    Z=0
  ENDIF
NEXT

ENDIF

IF K<=KK      'REM EXITED FOR LOOP? FOUND ZERO SEQ AT END? PRETEND END OF FILE...
PRINT Z," ZEROES - PRETEND END"
PRINT #REPF,Z," ZEROES - ASSUME END";NEWLINE$
ENDIF

REM REACHED END OF AT LEAST ONE INPUT FILE!
P=SEEK(GFA) 
NINC=INT((P-POLD-1)/4)
N += NINC
PRINT N;" SAMPLES AT";FORMAT("####0.00000",N/44100);" SECS @";P,,NINC;"  SAMPLES IN LAST RUN OF UNDISPUTED DATA"
PRINT #REPF,N;" SAMPLES AT";FORMAT("####0.00000",N/44100);" SECS @";P,,NINC;"  SAMPLES IN LAST RUN OF UNDISPUTED DATA";NEWLINE$
'N += INT((SEEK(GFA)-POLD-1 )/4)  'REM N=???? DEAL WITH END OF FILE
GOTO 910

250 
P=SEEK(GFA) 
NINC=INT((P-POLD-1)/4)-1 'REM BACK UP ONE EXTRA TO ENSURE BUFFER FILLS
FOR I=1 TO INFILES 
  SEEK #GF(I);(GPSAV(I)+(NINC*4))  'REM RE-POSITION FILE POINTERS
'PRINT SEEK(GF(I)),I," NEW SEEK POSITION"
  NEXT

SEEK #OUTF;(POUTSAV+(NINC*4))
N += NINC
IF NINC>99
PRINT N;" SAMPLES AT";FORMAT("####0.00000",N/44100);" SECS @";P,,NINC;"  SAMPLES IN RUN OF UNDISPUTED DATA"
PRINT #REPF,N;" SAMPLES AT";FORMAT("####0.00000",N/44100);" SECS @";P,,NINC;"  SAMPLES IN RUN OF UNDISPUTED DATA";NEWLINE$
ENDIF

GOTO 90
REM  ===========================================================

300            'REM PROCESS DISPUTED SAMPLES

IF LDIFF
  LDISPUTES += 1                                          'REM *** DEAL WITH LEFT CHAN DISPUTE ***
DIM LL$(1 TO 9)    ' TRACK BAD DATA TYPES, L=LINEAR, R=REPEATED VALUE
'FOR I = 1 TO 9 : LL$(I)=" " : NEXT
REM IN THIS BASIC ARRAYS ARE INITIALIZED TO NUMERIC ZEROES,
REM DATA TYPES CHANGE AUTOMATICALLY,
REM AND ZERO AND NULL STRING COMPARE EQUAL !!!
                                   
PRINT : PRINT N;" LEFT CHAN DISPUTE ";LDISPUTES;" AT";FORMAT("####0.00000",N/44100);" SECONDS"
PRINT LPREV : PRINT LL : PRINT LNEXT

REM WEED OUT LINEAR DATA POINTS   
  LVALS=0 : LREF=KBIG ' COUNT VALID L VALUES
  FOR I = 1 TO 9
    IF INFILE$(I)<>""
      II=((LPREV(I)+LNEXT(I))/2)    'INTERPOLATED LINEAR VALUE
'PRINT "LINEAR?  ";LL(I);"  ";II;"  ";(LL(I)-II);
      IF ABS(LL(I)-II) > .6  ' VALID DATA POINT?
'PRINT " not-lin"       
                                                      ' YES - DATA POINT IS VALID
        IF LREF=KBIG ' FIRST GOOD POINT?
          LREF=LL(I)
          LVALS=1
        ELSE ' NOT FIRST GOOD POINT
          IF LREF<>LL(I) THEN LVALS += 1 ' MORE THAN ONE DIFFERENT GOOD VALUE?
        ENDIF
       
      ELSE                                              ' NO - DATA POINT IS NOT VALID
'PRINT " *** LINEAR ***"
        LL$(I)="L"        ' MARK THE DATA TO BE IGNORED LATER
      ENDIF
    ENDIF
  NEXT I
IF LVALS=1 THEN 500 'REM FOUND ONE GOOD DATA VALUE = LREF
IF LVALS=0 THEN 550 'REM ALL DATA WAS DISCARDED

REM DISPUTE REMAINS, SO WEED OUT REPEAT VALUES
  LVALS=0 : LREF=KBIG ' COUNT VALID L VALUES
  FOR I = 1 TO 9
    IF INFILE$(I)<>"" AND LL$(I)<>"L"
      II=LPREV(I)    'PREVIOUS VALUE
PRINT "REPEAT?  ";LL(I);"  ";II;"  ";(LL(I)-II);
      IF LL(I)<>LPREV(I)  ' VALID DATA POINT?
PRINT " not-rep"       
                                                      ' YES - DATA POINT IS VALID
        IF LREF=KBIG ' FIRST GOOD POINT?
          LREF=LL(I)
          LVALS=1
        ELSE ' NOT FIRST GOOD POINT
          IF LREF<>LL(I) THEN LVALS += 1 ' MORE THAN ONE DIFFERENT GOOD VALUE?
        ENDIF
       
      ELSE                                              ' NO - DATA POINT IS NOT VALID
PRINT " *** REPEAT ***"
        LL$(I)="R"       
      ENDIF
    ENDIF
  NEXT I
 
IF LVALS<>1 THEN 550 'REM STILL HAVE TOO LITTLE OR TOO MUCH DISPUTE, SO GIVE UP AND PUNT

500      'REM FOUND THE ONE GOOD DATA VALUE LREF, SO TALLY THE STATISTICS

  FOR I = 1 TO 9
    IF INFILE$(I)<>""

      IF LL$(I)=""  ' VALID DATA POINT?
'PRINT "VALID DATA POINT"       
                                                      ' YES - DATA POINT IS VALID
       
      ELSE                                              ' NO - DATA POINT IS NOT VALID
PRINT " *** DISCARD DATA POINT *** ";LL$(I)
        IF LSEQ(I)=0 THEN LSEQCNT(I)=LSEQCNT(I)+1  ' START OF SEQ OF BAD DATA?
        LSEQ(I)=LSEQ(I)+1
        LSEQTOT(I)=LSEQTOT(I)+1
        IF LSEQMAX(I)<LSEQ(I) THEN LSEQMAX(I)=LSEQ(I)
       
      ENDIF
    ENDIF
  NEXT I

'  PRINT LL$ : PRINT LPREV : PRINT LL : PRINT LNEXT
  PRINT LSEQ,LSEQMAX,LSEQTOT,LSEQCNT   
  IF LVALS<1 THEN PRINT LL, LVALS, "LVALS=0 ERR *** STOP" : INPUT "WAITING ";TDELAY
  IF LVALS>1 THEN PRINT LL, LVALS, "LVALS>1 ERR *** STOP" : INPUT "WAITING ";TDELAY
  PRINT "LEFT DISPUTE RESOLVED: ";LREF : DELAY TDELAY : 'INPUT "WAITING ";TDELAY
                                           
REM THE FOLLOWING CODE IS NOT ALWAYS REACHED                 
ELSE        ' OTHERWISE, NO DISPUTE -- ALL GOOD DATA
  FOR I = 1 TO 9
    IF INFILE$(I)<>"" THEN LSEQ(I)=0    ' RESET ALL BAD-DATA SEQ COUNTERS TO ZERO
  NEXT I
ENDIF
GOTO 590

550 '? ALL DATA DISCARDED, SO TRY RESTORING DATA IF PREVIOUS DATA DISCARDED?

570 '? GIVE UP ON PICKING VALID DATA, JUST USE MEDIAN OF ALL ORIGINAL DATA POINTS
DIM S(1 TO 1)
FOR I = 1 TO 9   
  IF INFILE$(I)<>"" THEN APPEND S,LL(I)
  NEXT I
  DELETE S,1
SORT S
PRINT "SORTED VALUES: ";S
RANGE = S(UBOUND(S)) - S(1)
PRINT "RANGE ";S(1);" TO ";S(UBOUND(S))
I=(LBOUND(S)+UBOUND(S))/2
M1=I : M2=I : IF I<>INT(I) THEN M1=INT(I) : M2=FIX(I)  ' EVEN OR ODD NUMBER OF VALUES?
M12=((S(M1)+S(M2))/2)
PRINT "MEDIAN VALUE: ";M12

IF RANGE>1 'THEN PRINT "WAIT - RANGE TOO LARGE ";RANGE : INPUT "WAITING ";TDELAY
 LRANGEOVR += 1
 PRINT LRANGEOVR;" RANGE TOO LARGE ";RANGE
 PRINT LSEQ,LSEQMAX,LSEQTOT,LSEQCNT
 PRINT
PRINT #REPF,;NEWLINE$
PRINT #REPF,N;" LEFT CHAN DISPUTE ";LDISPUTES;" AT";FORMAT("####0.00000",N/44100);" SECONDS";NEWLINE$
PRINT #REPF,LPREV;NEWLINE$ : PRINT #REPF,LL;NEWLINE$ : PRINT #REPF,LNEXT;NEWLINE$
PRINT #REPF,"SORTED VALUES: ";S;NEWLINE$
PRINT #REPF,"RANGE ";S(1);" TO ";S(UBOUND(S));NEWLINE$
PRINT #REPF,"MEDIAN VALUE: ";M12;NEWLINE$
PRINT #REPF,LRANGEOVR;" LEFT RANGE TOO LARGE ";RANGE;NEWLINE$
PRINT #REPF,LSEQ,LSEQMAX,LSEQTOT,LSEQCNT;NEWLINE$
PRINT #REPF,;NEWLINE$
ENDIF
LREF=M12

590 '? FINISH WITH THIS CHANNEL
J=LREF : IF J<0 THEN J += K216
J2=INT(J/256) : J1=J-J2*256 : J0=0
BPUTC #OUTF;J1 :BPUTC #OUTF;J2 ':BPUTC #OUTF;J0 :BPUTC #OUTF;J0      'REM OUTPUT RECONCILED DATA
' DELAY TDELAY : ' INPUT "WAITING ";TDELAY

REM =============================================


IF RDIFF
  RDISPUTES += 1                                          'REM *** DEAL WITH RIGHT CHAN DISPUTE ***
DIM RR$(1 TO 9)    ' TRACK BAD DATA TYPES, L=LINEAR, R=REPEATED VALUE
'FOR I = 1 TO 9 : RR$(I)=" " : NEXT
REM IN THIS BASIC ARRAYS ARE INITIALIZED TO NUMERIC ZEROES,
REM DATA TYPES CHANGE AUTOMATICALLY,
REM AND ZERO AND NULL STRING COMPARE EQUAL !!!
                                   
PRINT : PRINT N;" RIGHT CHAN DISPUTE ";RDISPUTES;" AT";FORMAT("####0.00000",N/44100);" SECONDS"
PRINT RPREV : PRINT RR : PRINT RNEXT

REM WEED OUT LINEAR DATA POINTS   
  RVALS=0 : RREF=KBIG ' COUNT VALID R VALUES
  FOR I = 1 TO 9
    IF INFILE$(I)<>""
      II=((RPREV(I)+RNEXT(I))/2)    'INTERPOLATED LINEAR VALUE
'PRINT "LINEAR?  ";RR(I);"  ";II;"  ";(RR(I)-II);
      IF ABS(RR(I)-II) > .6  ' VALID DATA POINT?
'PRINT " not-lin"       
                                                      ' YES - DATA POINT IS VALID
        IF RREF=KBIG ' FIRST GOOD POINT?
          RREF=RR(I)
          RVALS=1
        ELSE ' NOT FIRST GOOD POINT
          IF RREF<>RR(I) THEN RVALS += 1 ' MORE THAN ONE DIFFERENT GOOD VALUE?
        ENDIF
       
      ELSE                                              ' NO - DATA POINT IS NOT VALID
'PRINT " *** LINEAR ***"
        RR$(I)="L"        ' MARK THE DATA TO BE IGNORED LATER
      ENDIF
    ENDIF
  NEXT I
IF RVALS=1 THEN 600 'REM FOUND ONE GOOD DATA VALUE = RREF
IF RVALS=0 THEN 650 'REM ALL DATA WAS DISCARDED

REM DISPUTE REMAINS, SO WEED OUT REPEAT VALUES
  RVALS=0 : RREF=KBIG ' COUNT VALID R VALUES
  FOR I = 1 TO 9
    IF INFILE$(I)<>"" AND RR$(I)<>"L"
      II=RPREV(I)    'PREVIOUS VALUE
PRINT "REPEAT?  ";RR(I);"  ";II;"  ";(RR(I)-II);
      IF RR(I)<>RPREV(I)  ' VALID DATA POINT?
PRINT " not-rep"       
                                                      ' YES - DATA POINT IS VALID
        IF RREF=KBIG ' FIRST GOOD POINT?
          RREF=RR(I)
          RVALS=1
        ELSE ' NOT FIRST GOOD POINT
          IF RREF<>RR(I) THEN RVALS += 1 ' MORE THAN ONE DIFFERENT GOOD VALUE?
        ENDIF
       
      ELSE                                              ' NO - DATA POINT IS NOT VALID
PRINT " *** REPEAT ***"
        RR$(I)="R"       
      ENDIF
    ENDIF
  NEXT I
 
IF RVALS<>1 THEN 650 'REM STILL HAVE TOO LITTLE OR TOO MUCH DISPUTE, SO GIVE UP AND PUNT

600      'REM FOUND THE ONE GOOD DATA VALUE LREF, SO TALLY THE STATISTICS

  FOR I = 1 TO 9
    IF INFILE$(I)<>""

      IF RR$(I)=""  ' VALID DATA POINT?
'PRINT "VALID DATA POINT"       
                                                      ' YES - DATA POINT IS VALID
       
      ELSE                                              ' NO - DATA POINT IS NOT VALID
PRINT " *** DISCARD DATA POINT *** ";RR$(I)
        IF RSEQ(I)=0 THEN RSEQCNT(I)=RSEQCNT(I)+1  ' START OF SEQ OF BAD DATA?
        RSEQ(I)=RSEQ(I)+1
        RSEQTOT(I)=RSEQTOT(I)+1
        IF RSEQMAX(I)<RSEQ(I) THEN RSEQMAX(I)=RSEQ(I)
       
      ENDIF
    ENDIF
  NEXT I

'  PRINT RR$ : PRINT RPREV : PRINT RR : PRINT RNEXT
  PRINT RSEQ,RSEQMAX,RSEQTOT,RSEQCNT   
  IF RVALS<1 THEN PRINT RR, RVALS, "RVALS=0 ERR *** STOP" : INPUT "WAITING ";TDELAY
  IF RVALS>1 THEN PRINT RR, RVALS, "RVALS>1 ERR *** STOP" : INPUT "WAITING ";TDELAY
  PRINT "RIGHT DISPUTE RESOLVED: ";RREF : DELAY TDELAY : 'INPUT "WAITING ";TDELAY
                                           
REM THE FOLLOWING CODE IS NOT ALWAYS REACHED                 
ELSE        ' OTHERWISE, NO DISPUTE -- ALL GOOD DATA
  FOR I = 1 TO 9
    IF INFILE$(I)<>"" THEN RSEQ(I)=0    ' RESET ALL BAD-DATA SEQ COUNTERS TO ZERO
  NEXT I
ENDIF
GOTO 690

650 '? ALL DATA DISCARDED, SO TRY RESTORING DATA IF PREVIOUS DATA DISCARDED?

670 '? GIVE UP ON PICKING VALID DATA, JUST USE MEDIAN OF ALL ORIGINAL DATA POINTS
DIM S(1 TO 1)
FOR I = 1 TO 9   
  IF INFILE$(I)<>"" THEN APPEND S,RR(I)
  NEXT I
  DELETE S,1
SORT S
PRINT "SORTED VALUES: ";S
RANGE = S(UBOUND(S)) - S(1)
PRINT "RANGE ";S(1);" TO ";S(UBOUND(S))
I=(LBOUND(S)+UBOUND(S))/2
M1=I : M2=I : IF I<>INT(I) THEN M1=INT(I) : M2=FIX(I)  ' EVEN OR ODD NUMBER OF VALUES?
M12=((S(M1)+S(M2))/2)
PRINT "MEDIAN VALUE: ";M12

IF RANGE>1 'THEN PRINT "WAIT - RANGE TOO LARGE ";RANGE : INPUT "WAITING ";TDELAY
 RRANGEOVR += 1
 PRINT RRANGEOVR;" RANGE TOO LARGE ";RANGE
 PRINT RSEQ,RSEQMAX,RSEQTOT,RSEQCNT
 PRINT
PRINT #REPF,;NEWLINE$
PRINT #REPF,N;" RIGHT CHAN DISPUTE ";RDISPUTES;" AT";FORMAT("####0.00000",N/44100);" SECONDS";NEWLINE$
PRINT #REPF,RPREV;NEWLINE$ : PRINT #REPF,RR;NEWLINE$ : PRINT #REPF,RNEXT;NEWLINE$
PRINT #REPF,"SORTED VALUES: ";S;NEWLINE$
PRINT #REPF,"RANGE ";S(1);" TO ";S(UBOUND(S));NEWLINE$
PRINT #REPF,"MEDIAN VALUE: ";M12;NEWLINE$
PRINT #REPF,RRANGEOVR;" RIGHT RANGE TOO LARGE ";RANGE;NEWLINE$
PRINT #REPF,RSEQ,RSEQMAX,RSEQTOT,RSEQCNT;NEWLINE$
PRINT #REPF,;NEWLINE$
ENDIF
RREF=M12

690 '? FINISH WITH THIS CHANNEL
J=RREF : IF J<0 THEN J += K216
J2=INT(J/256) : J1=J-J2*256 : J0=0
BPUTC #OUTF;J1 :BPUTC #OUTF;J2 ':BPUTC #OUTF;J0 :BPUTC #OUTF;J0      'REM OUTPUT RECONCILED DATA
' DELAY TDELAY : ' INPUT "WAITING ";TDELAY


GOTO 100 ' LOOP BACK UP TO ANOTHER SET OF SAMPLES


800
PRINT : PRINT "*** EOF ***"

900
BPUTC #OUTF;L1 :BPUTC #OUTF;L2 :BPUTC #OUTF;R1 :BPUTC #OUTF;R2 'COPY THE LAST UNCHANGED INPUT BYTES TO OUTPUT WAV FILE
REM N += 1 'REM NO -- N ALREADY PRE-INC BACK AT TOP OF MAIN LOOP

910    'REM FILE OUTPUT FILE END WITH ZEROS
J=LOF(GFA) : Z=0
JJ=(J-LOF(OUTF))
PRINT "FILLING END OF OUTPUT FILE WITH ";JJ;" ZERO BYTES"
PRINT #REPF,"FILLING END OF OUTPUT FILE WITH ";JJ;" ZERO BYTES";NEWLINE$
WHILE LOF(OUTF)<J
  BPUTC #OUTF;Z
  WEND
N += INT(JJ/4)
 
PRINT
PRINT N;" SAMPLES,";FORMAT("####0.00000",N/44100);" SECONDS, ";LDISPUTES;" LDISPUTES, ";LRANGEOVR;" LRANGEOVR"
PRINT N;" SAMPLES,";FORMAT("####0.00000",N/44100);" SECONDS, ";RDISPUTES;" RDISPUTES, ";RRANGEOVR;" RRANGEOVR"
PRINT #REPF,;NEWLINE$
PRINT #REPF,N;" SAMPLES,";FORMAT("####0.00000",N/44100);" SECONDS, ";
PRINT #REPF,LDISPUTES;" LDISPUTES, ";LRANGEOVR;" LRANGEOVR";NEWLINE$
PRINT #REPF,,,,RDISPUTES;" RDISPUTES, ";RRANGEOVR;" RRANGEOVR";NEWLINE$
PRINT LSEQ,LSEQMAX,LSEQTOT,LSEQCNT
PRINT RSEQ,RSEQMAX,RSEQTOT,RSEQCNT
PRINT #REPF,LSEQ,LSEQMAX,LSEQTOT,LSEQCNT;NEWLINE$
PRINT #REPF,RSEQ,RSEQMAX,RSEQTOT,RSEQCNT;NEWLINE$
FOR I = 1 TO 9
  IF INFILE$(I)<>""
    PRINT INFILE$(I),LSEQ(I),LSEQMAX(I),LSEQTOT(I),LSEQCNT(I);"  LSEQ,LSEQMAX,LSEQTOT,LSEQCNT"
    PRINT #REPF,INFILE$(I),LSEQ(I),LSEQMAX(I),LSEQTOT(I),LSEQCNT(I);"  LSEQ,LSEQMAX,LSEQTOT,LSEQCNT";NEWLINE$
    ENDIF
  NEXT I
FOR I = 1 TO 9
  IF INFILE$(I)<>""
    PRINT INFILE$(I),RSEQ(I),RSEQMAX(I),RSEQTOT(I),RSEQCNT(I);"  RSEQ,RSEQMAX,RSEQTOT,RSEQCNT"
    PRINT #REPF,INFILE$(I),RSEQ(I),RSEQMAX(I),RSEQTOT(I),RSEQCNT(I);"  RSEQ,RSEQMAX,RSEQTOT,RSEQCNT";NEWLINE$
    ENDIF
  NEXT I
     
CLOSE #OUTF
FOR I = 1 TO 9
  IF INFILE$(I)<>""
CLOSE #F(I)
    ENDIF
  NEXT I

PRINT #REPF, DATE$;" ";TIME$;" END OF CD rot WAV-FILT-LIN 2FEB12";NEWLINE$
PRINT #REPF,;NEWLINE$ : PRINT #REPF,;NEWLINE$
CLOSE #REPF
PRINT DATE$;" ";TIME$;" END OF CD rot WAV-FILT-LIN 2FEB12"
STOP

Audio CD ROT, Red Book CD-DA data recovery, Disc Rot

Reply #29
CD disc rot processing    WAV-FILES-COPYR.bas
COPY AND RENAME FILES - UTILITY TOOL
FROM ONE-SET-OF-TRACKS-PER-DIRECTORY STRUCTURE
TO N-COPIES IN SEPARATE BY-TRACK DIRECTORIES

When I began this data recovery project I had no data, since the audio CDs would not play. Then I was able to cajole-force the production of 7 imperfect copies of the disc. Ever since, the challenge is to deal with too much data.

Fre:ac put each set of one copy of the disc in by-copy directories. For the data combining task, my program needs each copy of a given track together, in separate by-track directories. This involves copy-redistributing-renaming 7x34 wav files. Below is a little utility program to do this, run once per copy...

So far, it looks like the current version of WAV-FILT-LIN will work fairly well on about half of my problem tracks; the others are in worse shape, and may need additional reconciliation.

I did encounter one case where about 0.1 second of one track was time-shifted in the middle of a track. Since this was just one of five copies of one disc, it was easier to just discard that copy than figure out a way to correct that glitch.

Code: [Select]
' CDrot.bas (SmallBASIC FLTK 0.10.6 Windows XP)
' CD disc rot processing    WAV-FILES-COPYR.bas
' kd 3 feb 2012
' COPY AND RENAME FILES - UTILITY TOOL
' FROM ONE-SET-OF-TRACKS-PER-DIRECTORY STRUCTURE
' TO N-COPIES IN SEPARATE BY-TRACK DIRECTORIES
PRINT DATE$;" ";TIME$;" START of CDrot WAV-FILES-COPYR-3FEB12.bas"

D$ = "E1-4X-JITTER"
D$ = "E2-8X-JITTER"
D$ = "E3-16X-JITTER"
D$ = "E4-1037PM"
D$ = "E5-EMILY-418PM"

D$ = "N1-4X-JITTER-1150AM"
D$ = "N2-4X-JITTER-1134AM"

D2$ = LEFT (D$,2)  'REM STANDARDIZED SHORT FORM FOR NAMING FILES
D2W$ = D2$+".wav" : ? D2W$

IF (NOT(ISDIR(D$))) THEN CHDIR ("..") 'RETURN TO BASE DIR IF NEEDED
CHDIR (D$)
? FILES("*")
FIL$=FILES("*")
? LEN(FIL$),FIL$

FOR I = 0 TO LEN(FIL$)-1
  N$=FIL$(I) 
  ? LEN(N$),N$
 
  J=INSTR(N$,"Track ")
  ? J
  IF J>0
    T$=MID(N$,J+6,2)
'    ? T$
    IF LEN(T$)<>2 THEN T$="99"
    TT$ = "TRACK"+T$
    TTT$ = "..\\COPY\\"+TT$  'REM DANGER -- BACKSLASHES IN STRINGS HAVE TO BE ESCAPED!
    TTTT$ = TTT$+"\\"+D2W$
    ? TTTT$;" MAKING DIR AND COPYING FILE"
    IF (NOT(ISDIR(TTT$))) THEN  MKDIR TTT$
    COPY FIL$(I),TTTT$   
  ENDIF   

  NEXT

?"GOOD JOB"
PRINT DATE$;" ";TIME$;" END OF CDrot WAV-FILES-COPYR-3FEB12.bas"
STOP

COPY FIL$(1),"..\TEST\TEST.JNK"
?"DONE"
END

Re: Audio CD ROT, Red Book CD-DA data recovery, Disc Rot

Reply #30
Hello listeners,

I am very aware that this is a VERY old topic, but I wondered if anyone had success with any of the ideas presented here?

Several years before this topic came up I had a very similar problem with about 10% of my CDRs that I had burnt back when CDRs were still quite new... the mid nineties.

When playing my discs many years later I noted that some of them were sounding rather scratchy so I decided to try and rip them to disk to firstly see what was going on, and secondly to make a backup. Back when they were burnt, disk space was very expensive, so I burnt my audio to CDR and erased the originals. Yeah I know, big mistake. At the very least I should have made two copies of each. Even at 100+ discs, this would have been cheaper in the long run. Hindsight is so clear!

When I started my recovery, the best I could do was EAC (exact audio copy). The forums were not much help - few others had experienced disc fade (or disc rot). And yes, I keep my discs cool and out of the light. Unlike the OP, my tracks were stereo, so I could not sample compare between channels. The most useful information I found was the "Plextor" drives were the best for reading damaged media (and I did manage to recover about 10% of the 10% bad discs).

I came across a guy that was interested in programming a GPU to do click detection on audio tracks taken from vinyl. His approach was not FFT based as everything else I'd seen. From my understanding he was analysing the waveform in the time domain to make sure that the samples 'made sense'. Sort of following the waveform along and making sure that the current sample was (within reason) where the previous X samples (using a curve fitting algorithm) expected it to be. If it was out too far, then it was flagged as possibly bad.

He was not getting much interest for LP click removal, but I contacted him about disc rot/fade problems. What I had noted in my rips of the bad CDRs, a bad sample would just be a single random value, and the samples around it good. This guy very generously rejigged his software to search for these single outlying samples and fill them with an interpolated sample (based on the surrounds).

In my search for solutions I came across some other interesting stuff.  A hardware hacker (who and where I don't recall, but I saved off as much stuff as I could find) had dug very deep into CD recorders and had actually got right into the point between when the data is read as a stream of raw information (NOT bits) from the CD, and where it passed into the decoder to get turned into genuine data bits. What he did was extremely interesting as he was getting the information from almost the very bottom level.

He had then written a program that took this raw information and, applying more smarts than the hardware in the drive, turned them into data bits. Unfortunately (for me), he was not doing audio, he was doing data. Even more unfortunately (perhaps) he was using a fairly old drive. The reasons for using an old drive were very specific... the old drives used separate chips for reading and for decoding, whereas more modern drives were integrated. Hence he was able to get at the data (raw information) that he was after.

Sorry, this has turned into a long post on a very old subject - but perhaps somebody will find something here useful, and I am always willing to discuss more if somebody wants to!

Cheers,
MM.

 

Re: Audio CD ROT, Red Book CD-DA data recovery, Disc Rot

Reply #31
Back again after several months, and I see that no-body has made any follow-up comments, so I will make some of my own in case anyone is interested (or is even listening!).

The suggestion of using DVDisaster (using multiple drives and the feature that allows filling of "blank" areas of a poor read with good samples from the same disc in another drive) sounded very promising. However, the software specifically does NOT support audio CDs. Whether this is a technical limitation or one that has been put in by the author (to prevent being sued, and I can understand his stance) is unknown.

I did try the suggested 'abandonware' product "PerfectRip" on my own CD-Rs, hoping it could spit out the C2 error flags (so they would help me pinpoint errors), but because of either a problem with my drive/s, or an incorrect interpretation by [mjb2006] on the software, or some setup/ini file settings that are not explained in any documentation (or webpage) that I have found - it did NOT output C2 error markers. Sigh, my hopes had been so high :(

Life has got in the way of recovering my CD-Rs, but I now have multiple copies of them as rips done by EAC with different drives, stored away on both on-site and off-site hard disks, and I have stored my bad CD-Rs in the cellar in a cool, dry and dark place.

I hope to get to them one day...

MM