`
`DEFINT A-Y
`DEFSNG Z
`PRINT : PRINT : PRINT
`PRINT "4600/Solo Support Code 4/10/95"
`zcon = 180 / 3.141592654#
`zk1 = .005: zk2 = .995' Energy averaging constants
`
`DIM s$(512), s(512), c$(512), bit(512)
`DIM r(256)
`DIM xkindex(11), xkcor(11), kaindex(11), kacor(11)
`DIM hotxkindex(11), hotxkmag(11)
`DIM xkmag(11), kamag(11)
`DIM index(16), mag(16), cor(16)
`DIM rr(256, 10)
`
`DATA 1,2,4,8,&h10,&h20,&h40,&h80
`DATA &h100,&h200,&h400,&h800,&h1000,&h2000,&h4000,&h8000
`DIM p(15)
`FOR I = 0 TO 15: READ p(I): NEXT I
`aa$ = "## \ \ \ \"
`
`id = 3 ' # of plots
`DIM v(500)
`peaks = 10
`DIM nc(id, peaks), nm(id, peaks)
`DIM lc(id, peaks)
`DIM lm(id, peaks)
`DIM y1(id), zx(id), zy(id)
`DIM lp1(id), lp2(id)
`DIM rlx(id), rly(id)
`DIM rc(peaks)
`
`DEF FNA (I, j$) = NOT (I - VAL(j$))
`DEF fnb (I, j) = VAL("&H" + CHR$(I) + CHR$(j))
` DEF FNC (I, j, k, l) = VAL("&H" + CHR$(I) + CHR$(j) + CHR$(k)
`+ CHR$(l))
`DEF FND (I) = CSNG(I) / d256
`DEF fnx$ (I) = RIGHT$("0000" + HEX$(I), 4)
`DEF fnx (X) = zx(id) * X + x1
`DEF fny (Y) = (Y) * zy(id) + y1(id)
`
`iv1 = VARPTR(iv): iv2 = iv1 + 1
`
`' Constants
`'The following 2 elements are doubled in order to compensate for
`the
`'2 bytes storaged for each index in memory.
`mhz16 = 0
`mpy = 1: IF mhz16 THEN mpy = 2
`
`1
`
`Escort Ex. 2086, pg. 1
`
`
`
`xkbase = &H1000
`KABASE = &H3000
`HOTXKBASE = &H5000
`
`stoler = 90
`fullstick = 31
`tclose = 20
`' left = (33.3 - 16.2) * xcpts / 100' find size of
`smart mute
` ' rite = (66.6 - 16.2) * xcpts / 100'
`regions.
` ' msize = 1 + (rite - left) / 16
`
`' Start next transfer
`
`OPEN "COM1:19200,n,8,1,RB1000,bin,RS,op0,cd0,ds0" FOR RANDOM
`
`AS #1
`
`' Read a record from interface and extract the software
`version #
`
`grec:
`
` GOSUB record
`
`IF check <> 0 THEN PRINT "Fiber checksum error "; fnx$(check):
`GOTO grec
`IF scheck <> 0 THEN PRINT "Serial Transfer error"; fnx$(scheck):
`GOTO grec
`
`IF timeout <> 0 THEN GOTO grec
`
`CLS
`PRINT : PRINT : PRINT : PRINT
`PRINT "Software in target is version "; HEX$(version)
`CLOSE #2
`
`''''''''''''''''''''''''''''''' Real time display
`''''''''''''''''''''''
`q:
`dis: CLS 0
`black = 0: blue = 1: green = 2: cyan = 3
`red = 4: magenta = 5: BROWN = 6: white = 7
`gray = 8: lblue = 9: lgreen = 10: lcyan = 11
`lred = 12: lmagenta = 13: yellow = 14: hiwhite = 15
`
`foreground = white
`background = black
`border = blue
`
`SCREEN 12
`
`2
`
`Escort Ex. 2086, pg. 2
`
`
`
`xchars = 80: ychars = 30
`ycsize = 16: xcsize = 8
`sizex = xchars * xcsize - 1
`sizey = ychars * ycsize - 1
`VIEW (1, 1)-(sizex - 1, sizey - 1)', background', border
`WINDOW (1, 1)-(sizex - 1, sizey - 1)
`
`xcenter = (sizex + 1) \ 2
`ycenter = (sizey + 1) \ 2
`xchar2 = xchars \ 2
`DEF fnr (r) = xcsize * (r - 1)' FNR Maps char position to
`screen coor
`DEF fns (s) = ycsize * (ychars - s)'FNS Maps char position
`COLOR foreground', background
`
`full = fnr(xchar2 - 1): zfull = full
`
`ipavg = -1
`bad = 0
`sbad = 0
`tbad = 0
`textdone = 0
`plotdone = 0
`textc = 8
`textd = 13' Horizontal character position
`lmeter = -1
`xled = -1
`kled = -1
`kaled = -1
`lasled = -1
`
`LINE (xcenter, ycenter + 200)-(xcenter, sizey), lmagenta
`
`'''''*********** setup = r(set10)
`display:
`GOSUB record ' Get next record of data
`
`IF p4600 THEN
`xcpts = 2 * 2688 ' # points in x/k sweep
`kacpts = xcpts ' # points in Ka sweep
`' zflt = 125 / xcpts' convert index to mS
`hotxkcpts = 2 * 1276 * ((29 + 62.5) / 62.5)
` ELSE
`xcpts = 2 * 2048
`kacpts = xcpts
` hotxkcpts = 1111
` END IF
`
`
`IF check <> 0 THEN bad = (bad + 1) AND 255: GOTO display
`IF scheck <> 0 THEN sbad = (sbad + 1) AND 255: GOTO display
`
`3
`
`Escort Ex. 2086, pg. 3
`
`
`
`a$ = INKEY$
`IF a$ = CHR$(27) THEN END
`IF a$ = "*" THEN dhistory = 1
`IF (a$ = " ") THEN page2 = -1 ELSE page2 = 0
`
` xdetect = flaga AND 1: IF xdetect THEN xdetect = -1
` kdetect = flaga AND 2: IF kdetect THEN kdetect = -1:
`xdetect = 0
` kadetect = flaga AND &HC: IF kadetect THEN kadetect =
`
`-1
`
` kaouter = flaga AND 8
` kainner = flaga AND 4
`
`train = lcount AND 32: IF train THEN train = -1
`emergency = lcount AND 64: IF emergency THEN emergency = -1
`roadhaz = lcount AND 128: IF roadhaz THEN roadhaz = -1
`
`
` anydetect = xdetect OR kdetect OR kadetect OR hotkdetect OR
`hotxdetect
`
`
`row = 3
`LOCATE row, 1
`IF solo THEN PRINT "Solo": row = row + 1
`IF e4600 THEN PRINT "P 4600": row = row + 1
`
` state$(1) = "Bad RAM"
` state$(0) = "RAM ok "
` state = flagb AND 1: lstate = ram
` GOSUB estate: ram = state: row = row + 1
` state$(1) = "City Mode "
` state$(0) = "Highway Mode"
`state = flagi1 AND 8: lstate = city
`GOSUB dstate: city = state: row = row + 1
` state$(1) = "Muted "
` state$(0) = "Not Muted "
`state = flagi1 AND 2: lstate = muted
`GOSUB dstate: muted = state: row = row + 1
` state$(1) = "Automute "
` state$(0) = "Not Automute "
`state = flagi1 AND 32: lstate = amuted
`GOSUB dstate: amuted = state: row = row + 1
` state$(0) = "Not Dark Mode"
` state$(1) = "Dark Mode "
`state = flagi1 AND 4: lstate = darken
`GOSUB dstate: darken = state: row = row + 1
` state$(0) = "Transient "
` state$(1) = "Not Transient"
`state = flagc AND 4: lstate = transientd
`GOSUB dstate: transientd = state: row = row + 1
` state$(0) = " "
` state$(1) = "Unpaired"
`
`4
`
`Escort Ex. 2086, pg. 4
`
`
`
`state = flagb AND 4: lstate = unp
`GOSUB dstate: unp = state: row = row + 1
` LOCATE row, 1
` IF xdetect THEN PRINT "X "; ELSE PRINT " ";
` IF kdetect THEN PRINT "K "; ELSE PRINT " ";
` IF kadetect THEN PRINT "Ka " ELSE PRINT " "
`row = row + 1: LOCATE row, 1
` IF train THEN PRINT "Train "
` IF emergency THEN PRINT "Emergency Vehicle"
` IF roadhaz THEN PRINT "Road Hazzard "
` IF NOT (train AND emergency AND roadhaz) THEN PRINT "
`
`"
`
`row = row + 1: LOCATE row, 1
` IF hotxdetect THEN PRINT "Hot X "; ELSE PRINT " ";
` IF hotkdetect THEN PRINT "Hot K " ELSE PRINT " "
`
`row = row + 1
` LOCATE row, 1
`PRINT USING "In/Ot/Hot \\ \\ \\"; HEX$(swcntinner); HEX
`$(swcntouter); HEX$(swcnthotxk)
`row = row + 1
`PRINT USING "Fb/Sr/Tm \\ \\ \\"; HEX$(bad); HEX$(sbad); HEX
`$(tbad)
`row = row + 1
`PRINT "Smart "; HEX$(smartspec); " ";
`row = row + 1
` row = 1
` s$ = "x/k & Ka Outer Band Stick": lastx = lxklevn: lastax
`= laxklevn
`
`max = 45: r = xklevn: GOSUB tabar: lxklevn = X:
`laxklevn = ax
`row = row + 1
` s$ = "Ka Inner Band Stick": lastx = lkalevn: lastax =
`lakalevn
` r = kalevn
` GOSUB tabar: lkalevn = X: lakalevn = ax
`
`''''''''''''''''''''''''''led's''''''''''''''''''''''''''''''''
`
` xoff = 200
` yoff = ycsize
` ys = yoff + 14
` xs = 12
` xspace = 30
` xdisp = 20
` IF textdone THEN GOTO notx
` LOCATE ychars - 1, 21: PRINT "Meter";
` LOCATE ychars - 1, 48: PRINT "X";
` LOCATE ychars - 1, 56: PRINT "K";
` LOCATE ychars - 1, 63: PRINT "Ka";
` LOCATE ychars - 1, 71: PRINT "Laser";
`
`5
`
`Escort Ex. 2086, pg. 5
`
`
`
`notx:
`
`j = display1
`ip = j AND &H1F
`
` IF lmeter = ip THEN GOTO notnew
` ii = 1
` FOR I = 0 TO 4
` iii = ii AND j
` GOSUB led
` ii = ii * 2
` NEXT I
` lmeter = ip
`
` iii = 0''''''''''''''''''<-------------patch
`
`notnew:
`iii = &H20 AND display1' x band indicator
`IF xled = iii THEN GOTO skipx
` I = 8
` GOSUB led
` xled = iii
`skipx:
` iii = &H40 AND display1 ' k band indicator
` IF kled = iii THEN GOTO skipk
` I = 11
` GOSUB led
` kled = iii
`skipk:
` iii = &H80 AND display1' Ka Band indicator
` IF kaled = iii THEN GOTO skipka
` I = 14
` GOSUB led
` kaled = iii
`skipka:
` iii = 1 AND display2' Laser indicator
` IF lasled = iii THEN GOTO skipkb
` I = 17
` GOSUB led
`''' lasled = iii
`skipkb:
`
`'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
`''''''
`' Determine sweep type
` xkdata = -1''''''''''''''''''''''''''''''''''
`'''''' xkdata = r(set4) AND 1: IF xkdata <> 0 THEN xkdata = -1
`
`bchars = 1' # chars left on bottom
`vsize = ycsize * (ychars - bchars - row - 4 - 2) \ 3
`v = vsize - 7' Vertical size
`x1 = 160' Horizontal offset
`h = sizex - x1 - 35' Horizontal size
`
`6
`
`Escort Ex. 2086, pg. 6
`
`
`
`iindex = 0' Initial index
`maxv = &H80' max value
`
`'*****************************Handle x/k & Ka Outer data display
`here
`
`findex = xcpts' Final index
`' Calculate indicies of xk band segment of sweep
` IF p4600 THEN
`axleft = CSNG(findex) * CSNG((100 - (33.3 + 16.2 - 5))
`
`/ 100)
`
`5)) / 100)
`ELSE
`
`axrite = CSNG(findex) * CSNG((100 - (66.66 + 16.2 +
`
`axleft = CSNG(findex) * CSNG((33.3 + 16.2 - 5) / 100)
`axrite = CSNG(findex) * CSNG((66.66 + 16.2 + 5) / 100)
`END IF
`
`p1 = 0: p2 = 0
`alert = xdetect OR kdetect
`IF alert <> 0 THEN p1 = peak1 - xkbase: p2 = peak2 - xkbase'
`horizontal detect positions
`pclose = tclose
`id = 1: y1(id) = (bchars + 2) * ycsize'
`Vertical offset
`label$ = "x/k"
`FOR I = 0 TO 11
`index(I) = xkindex(I)
`mag(I) = xkmag(I)
`cor(I) = xkcor(I)
`NEXT I
`floor = 0
`dthresh = xkthresh
`GOSUB tplot
`
`'****************************Handle 'Ka Inner' data display here
`' xx = kapeak
` findex = kacpts' Final index
`
`' Calculate indicies of Ka 'false region'
`
`IF p4600 THEN
`fl = findex * CSNG((3.8) / 100): fr = CSNG(findex) * CSNG
`((63.8) / 100)
`ELSE
`fr = findex * CSNG((100 - 3.8) / 100): fl = CSNG(findex) *
`CSNG((100 - 63.8) / 100)
`END IF
`fi = (fr - fl) \ 4
`
` p1 = 0: p2 = 0' horizontal detect positions
` pclose = tclose
` id = 2
`
`7
`
`Escort Ex. 2086, pg. 7
`
`
`
` y1(id) = (bchars + 4) * ycsize + v' Vertical
`offset
` label$ = "Ka"
`alert = kadetect
`IF kadetect <> 0 THEN p1 = peak1 - KABASE: p2 = peak2 -
`KABASE
`FOR I = 0 TO 11
`index(I) = kaindex(I)
`mag(I) = kamag(I)
`cor(I) = kacor(I)
`NEXT I
`''''''floor = 25
`dthresh = kathresh
`GOSUB tplot
`'****************************Handle 'Hot xk' data display here
`'''''IF (tstflag AND 64) = 0 THEN GOTO skiphot
` IF solo THEN GOTO skiphot
` findex = hotxkcpts' Final index
`' Calculate indicies of hotxk 'useful region'
`fl = findex * CSNG(29 / (29 + 62.5)): fr = findex
`fi = (fr - fl) \ 4
` p1 = 0: p2 = 0' horizontal detect positions
` pclose = tclose
` id = 3: y1(id) = (bchars + 6) * ycsize + 2 * v'
`Vertical offset
` label$ = "Hot"
` alert = kadetect
`IF hotxkdetect <> 0 THEN p1 = peak1 - HOTXKBASE: p2 = peak2 -
`HOTXKBASE
`FOR I = 0 TO 11
`index(I) = hotxkindex(I)
`mag(I) = hotxkmag(I): cor(I) = 0
`NEXT I
`''''''floor =25
`dthresh = hotxkthresh
`GOSUB tplot
`
`skiphot: plotdone = -1: textdone = -1
`GOTO display
`'****************************************************************
`*********
`END
`
`' Display LED's
`led: X = xoff + I * xdisp
`IF iii THEN
`LINE (X, yoff)-(X + xs, ys), red, BF
`
`ELSE
`
`LINE (X, yoff)-(X + xs, ys), background, BF
`LINE (X, yoff)-(X + xs, ys), red, B
`END IF
`RETURN
`
`8
`
`Escort Ex. 2086, pg. 8
`
`
`
`' Display Decimal value 'v' of string s$
`
`tline: IF textdone THEN GOTO pdat
`LOCATE row, 1
`PRINT s$;
`pdat: LOCATE row, textd + 1
`PRINT USING "#####"; v;
`RETURN
`
`' Same as tline but with wider string
`
`ttline: IF textdone THEN GOTO pzdat
`LOCATE row, 1
`PRINT s$;
`pzdat: LOCATE row, textd + 1
`IF v THEN
`PRINT USING "#####"; v;
`ELSE
`PRINT " -";
`END IF
`RETURN
`
`' Two condition text display
`
`dstate: IF textdone = 0 THEN GOTO odat
`IF state = lstate THEN RETURN
`odat: IF state <> 0 THEN state = 1
`rest: LOCATE row, 1
`PRINT state$(state)
`RETURN
`
`' Two condition text display
`
`estate: IF textdone = 0 THEN GOTO qdat
`IF state = lstate THEN RETURN
`qdat: IF state <> 0 THEN state = 1
`PRINT state$(state)
`RETURN
`
`' Two condition text display
`
`pstate: IF textdone = 0 THEN GOTO podat
`IF state = lstate THEN RETURN
`podat: IF state <> 0 THEN state = 1
`LOCATE row, 1
`PRINT state$(state);
`RETURN
`
`' Four condition text display
`
`9
`
`Escort Ex. 2086, pg. 9
`
`
`
`state4: IF textdone = 0 THEN GOTO rest
`IF state = lstate THEN RETURN
`GOTO rest
`
`' Display Hex value 'v' of string s$
`
`hline: IF textdone THEN GOTO pdat1
`LOCATE row, 1
`PRINT s$
`pdat1: LOCATE row, textc + 2
`PRINT HEX$(v); " "
`RETURN
`
`' Scale bar graphs
`
`scale:
`IF textdone THEN RETURN
`X = zfull * calibrate / max + xcenter
`Y = fns(row) + ycsize
`LINE (xcenter, Y)-(X, Y), lblue
`t1 = Y - 2: t2 = Y + hh
`LINE (X - toler, t1)-(X, t2), red, BF
`LINE (xcenter + 1, Y)-(xcenter + 1, Y - 4), lblue
`X = X / xcsize + 2
`LOCATE row, X
`PRINT legend$;
`RETURN
`
`' Real time bar graph display
`
`tbar:
`
` IF textdone THEN GOTO pbar
`X = xchar2 - LEN(s$) ' On first pass print
`
`associated
`
`LOCATE row, X ' string
`PRINT s$
`pbar: ' Print the bar here
`'PRINT fnx$(r): RETURN
`IF r < 1 THEN r = 1' This improves appearance of
`
`bar
`
`IF r > max THEN r = max
`X = zfull * r / max
`Y = fns(row) + 6: yy = Y + 3
`xx = xcenter + X + 1
`IF lastx < X THEN
`LINE (xcenter + 1, Y)-(xx, yy), bcolor, BF
`
`ELSE
`
`LINE (xx, Y)-(xcenter + full + 1, yy), background, BF
`END IF
`RETURN
`
`' Real time bar graph display with averaged bar
`
`10
`
`Escort Ex. 2086, pg. 10
`
`
`
`tabar:
` IF textdone THEN GOTO apbar
`X = xchar2 - LEN(s$) ' On first pass print
`
`associated
`
`LOCATE row, X ' string
`PRINT s$
`apbar: ' Print the bar here
`IF r < 1 THEN r = 1' This improves appearance of
`
`bar
`
`IF r > max THEN r = max
`X = zfull * r / max
`Y = fns(row) + 8: yy = Y + 2
`xx = xcenter + X + 1
`IF lastx < X THEN
`LINE (xcenter + 1, Y)-(xx, yy), lblue, BF
`
`ELSE
`
`LINE (xx, Y)-(xcenter + full + 1, yy), background, BF
`END IF
`
`' Display averaged bar
`ax = CSNG(X) * .1 + .9 * CSNG(lastax)
`Y = fns(row) + 4: yy = Y + 2
`xx = xcenter + ax + 1
`IF lastax < ax THEN
`LINE (xcenter + 1, Y)-(xx, yy), yellow, BF
`
`ELSE
`
`LINE (xx, Y)-(xcenter + full + 1, yy), background, BF
`END IF
`RETURN
`'****************************************************************
`************
`' Plot 16 element array with indicies index() and
`magnitudes mag()
`' Assumes index values are
`ordered
`' RANDOMLY!
`' id: vertical plot number
`' p1,p2: indicies of stick enable peaks
`' alert: true if active alert for this display
`' v: Vertical size
`' h: Horizontal size
`' y1(id): Vertical offset
`' x1: Horizontal offset
`' findex: Final index number
`' iindex: Inital index number
`' maxv: Max value of data in plot
`' floor: X axis assigned this value to reduce viewed
`noise
`' label$: Label
`' dthresh: dynamic threshold
`'
`
`11
`
`Escort Ex. 2086, pg. 11
`
`
`
`' pair:
`' pclose: Illuminate region within close of pair
`'****************************************************************
`***********
`tplot:
`
`x2 = x1 + h: y2 = y1(id) + v
`zx(id) = h / (findex - iindex): zy(id) = v / maxv'
`find mapping values
`
`rly(id) = y1(id) + v \ 2 ' Location of right
`rlx(id) = x1 + h ' label
`
`IF plotdone THEN GOTO tupdate
`LOCATE ychars - rly(id) \ ycsize, rlx(id) \ xcsize + 2
`PRINT label$;
`LINE (x1 - 1, y1(id) - 1)-(x2 + 1, y2 + 1), hiwhite,
`B' draw box in plot area
`
`
`yy1 = fny(0) + vsize - 16: yy2 = yy1 + 16
`IF (id = 2) OR (id = 3) THEN
`sx = fnx(fl): LINE (sx, yy1)-(sx, yy2), hiwhite
`sx = fnx(fr): LINE (sx, yy1)-(sx, yy2), hiwhite
`END IF
`IF (id = 1) THEN
`sx = fnx(axleft): LINE (sx, yy1)-(sx, yy2),
`
`sx = fnx(axrite): LINE (sx, yy1)-(sx, yy2),
`
`END IF
`
`hiwhite
`
`hiwhite
`
`nc0 = fnx(0)
`FOR I = 1 TO peaks
`lc(id, I) = nc0: lm(id, I) = y1(id)' init
`previous set to 0
`NEXT I
`
`thresh(id) = fny(0)' Init position for dynamic
`
`threshold
`tupdate:
`
`' Display dynamic threshold
`Y = dthresh - floor: IF Y < 0 THEN Y = 0
`Y = fny(Y)
`col = background
`IF Y > thresh(id) THEN col = red
`LINE (x1 - 10, thresh(id))-(x1 - 5, Y), col, BF' growth
`thresh(id) = Y
`
`' Bubble Sort the peak table
`FOR j = peaks - 2 TO 0 STEP -1
`
`12
`
`Escort Ex. 2086, pg. 12
`
`
`
`FOR I = 0 TO j
`IF index(I) < index(I + 1) THEN
`SWAP index(I), index(I + 1)
`SWAP mag(I), mag(I + 1)
`END IF
`NEXT I
`NEXT j
`
`FOR I = 0 TO peaks - 1' Map peaks into display array
`r = index(I)
`nc(id, I + 1) = fnx(r) - iindex
`rc(I) = r
`r = mag(I) - floor: IF r < 0 THEN r = 0
`IF r > maxv THEN r = maxv
`nm(id, I + 1) = fny(r)
`
`NEXT I
`
`' Check to see if any mapped peaks have matched x-screen
`coordinates
`' If so, remove one of them or display anomolies will occur
`
`FOR I = 1 TO peaks - 1
`IF nc(id, I) <> nc(id, I + 1) THEN GOTO rich
`IF nc(id, I) = nc0 THEN GOTO rich
`'GOTO see
`nc(id, I + 1) = nc0
`
`rich: NEXT I
`
`FOR I = 1 TO peaks' Draw new peaks
`IF nc(id, I) = nc0 THEN GOTO edone
`
`element?
`
`FOR j = 1 TO peaks' Does this element match old
`
`IF nc(id, I) <> lc(id, j) THEN GOTO nomatch
`
`' Modify bar by either increasing or decreasing
`
`IF (nm(id, I) > lm(id, j)) THEN
`LINE (nc(id, I), lm(id, j))-(nc(id, I), nm(id, I)), yellow'
`growth
`
`ELSE
`LINE (nc(id, I), lm(id, j))-(nc(id, I), nm(id, I)),
`background' decline
`END IF
`lc(id, j) = nc0' remove old index
`GOTO edone' this element completed
`
`nomatch: NEXT j
`' If no element matches, draw new
`element
` LINE (nc(id, I), y1(id))-(nc(id, I), nm(id, I)), yellow
`
`13
`
`Escort Ex. 2086, pg. 13
`
`
`
`edone: NEXT I
`
`FOR I = 1 TO peaks' Remove old peaks
`IF lc(id, I) <> nc0 THEN
`LINE (lc(id, I), y1(id))-(lc(id, I), lm(id, I)),
`
`background
`
`END IF
`lc(id, I) = nc(id, I)
`lm(id, I) = nm(id, I)' Update aged array
`NEXT I
`
`'********************plot completed, now add supporting
`information
`
`' Show Average, Transient, & Phase
`Information************************
`tpr = 3 ' Bar height
`yy1 = fny(0) + vsize + 1: yy2 = yy1 + tpr: jp = 1
`yy3 = yy2 + 2: yy4 = yy3 + tpr
`ys1 = fny(0) + vsize + 1: ys2 = ys1 + 8
`xx1 = x1: xx2 = x1 + h
`LINE (xx1, ys1)-(xx2, ys2), background, BF
` FOR I = 0 TO 3'peaks - 1' Map peaks into display
`array
`
`'''''''''''''' j = nc(id, i + 1)' x-coordinate
`j = fnx(cor(I))
`IF j < x1 + 10 THEN GOTO drt
`'''''''''IF xkcor(i) THEN
`c = lred
`'''''''''''''''''''''IF rc(i) AND &H8000 THEN c = hiwhite
`LINE (j - jp, yy1)-(j + jp, yy2), c, BF
`'''''''''''''''''''''END IF
`'''''''''''''''''''''IF rc(i) AND &H2000 THEN LINE (j - jp,
`yy3)-(j + jp, yy4), lgreen, BF
`drt:
` NEXT I
`GOTO skiparound
`
`' Show Automute Smartmute deactivated
`regions*************************
`' IF id <> 1 THEN GOTO nosmute
` ' yt1 = ys1 - 6: yt2 = ys1 - 4
` ' IF ((r(set3)) AND 2) = 0 THEN ' Only clear
`background if no data
` ' LINE (xx1, yt1)-(xx2, yt2), background, BF'
`erase old stuff
` ' END IF
` ' jmsize = fnx(msize) - fnx(0)
` ' FOR i = 0 TO 15
` ' vv = r(smutexk) AND p(i)' regional bit value
`' IF vv THEN
`
`14
`
`Escort Ex. 2086, pg. 14
`
`
`
` ' j = left + i * msize' Find index of
`disabled regions
` ' j = fnx(j) ' x-coordinate
` ' LINE (j, yt1)-(j + jmsize, yt2), lblue, BF
` ' END IF
`'NEXT i
`'nosmute:
`skiparound:
`IF id <> 2 THEN GOTO fomp
`yy5 = yy1 - 2: yy6 = yy5 - 3
`fspace = fnx(fi) - fnx(0)
`ccut = 12' When timer<ccut, switch to dark
`
`green
`
`icl = background: IF regtim(0) THEN icl = lgreen: IF regtim(0) <
`ccut THEN icl = green
`xx5 = fnx(fl): xx6 = xx5 + fspace
`LINE (xx5, yy5)-(xx6, yy6), icl, BF
`
`icl = background: IF regtim(1) THEN icl = lgreen: IF regtim(1) <
`ccut THEN icl = green
`xx5 = xx6: xx6 = xx6 + fspace
`LINE (xx5, yy5)-(xx6, yy6), icl, BF
`
`icl = background: IF regtim(2) THEN icl = lgreen: IF regtim(2) <
`ccut THEN icl = green
`xx5 = xx6: xx6 = xx6 + fspace
`LINE (xx5, yy5)-(xx6, yy6), icl, BF
`
`icl = background: IF regtim(3) THEN icl = lgreen: IF regtim(3) <
`ccut THEN icl = green
`xx5 = xx6: xx6 = xx6 + fspace
`LINE (xx5, yy5)-(xx6, yy6), icl, BF
`
`fomp:
`
`' Show stick enable regions
`stickx:
`IF ABS(lp1(id) - p1) < pclose THEN GOTO transit
`pp1 = 0: pp2 = 0
`SWAP p1, pp1: SWAP p2, pp2' If bars moved, shift off
`screen
`GOSUB transit' Draw the bar
`SWAP p1, pp1: SWAP p2, pp2' & redisplay so they don't
`interract
`
`' Show alert position indicators
`yy1 = y1(id) - 8
`IF alert AND NOT (newwalert) THEN
`PSET (fnx(p1), yy1), green: PSET (fnx(p2), yy1), green
`END IF
`newwalert = alert
`
`15
`
`Escort Ex. 2086, pg. 15
`
`
`
`transit:
`'' IF p1 <= 10 THEN GOTO ignore
`b1 = y1(id) - 6: b2 = y1(id) - 2' vertical
`bar dimensions
`u1 = p1 - pclose: u2 = p1 + pclose
`v1 = lp1(id) - pclose: v2 = lp1(id) + pclose
`GOSUB xbar
`ignore:
`'' IF p2 <= 10 THEN GOTO capture
`u1 = p2 - pclose: u2 = p2 + pclose
`v1 = lp2(id) - pclose: v2 = lp2(id) + pclose
`GOSUB xbar
`capture: lp1(id) = p1: lp2(id) = p2
`RETURN
`
` ' Subroutine for erasing bars
`eraseb:
` p1 = 0: p2 = 0: GOTO stickx
`
`
`'Subroutine for Drawing one of two stick region bars
`
`xbar:
`
`IF u2 <= v1 THEN ' no overlap
`noover:
`LINE (fnx(v1), b1)-(fnx(v2), b2), background, BF
`IF u1 < 0 THEN RETURN
`LINE (fnx(u1), b1)-(fnx(u2), b2), lred, BF
`RETURN
`END IF
`
`IF (u2 > v1) AND (u1 < v1) THEN
`LINE (fnx(u2), b1)-(fnx(v2), b2), background, BF
`LINE (fnx(u1), b1)-(fnx(v1), b2), lred, BF
`RETURN
`END IF
`
`IF (u1 = v1) THEN RETURN
`
`IF (u1 < v2) AND (u2 > v2) THEN
`LINE (fnx(v1), b1)-(fnx(u1), b2), background, BF
`LINE (fnx(v2), b1)-(fnx(u2), b2), lred, BF
`RETURN
`END IF
`
`IF u1 >= v2 THEN GOTO noover
`STOP
`RETURN
`
`END
`
`'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
`
`16
`
`Escort Ex. 2086, pg. 16
`
`
`
`''''''''''
`
`record:
`
`by
`
`throughput
`
`' Request data from interface
`
`timeout = 0' transfer request is generated
`
`GOTO findsync' setting parallel bit high,low.
` ' This is previously done to improve
`
`retry: tbad = 255 AND (tbad + 1)
`timeout = 0
`LPRINT CHR$(1)' Set parallel port bit high
`LPRINT CHR$(0)' Set parallel port bit low
`
`'''WHILE LOC(1) = 0
` ''' IF INKEY$ = CHR$(27) THEN STOP
`'''WEND
`''' FOR q = 1 TO 1000: NEXT q
`''' GOTO record
`
`' Locate the sync
`findsync: ' IF (xdetect = 0) THEN STOP
` ' IF plevel = 4 THEN STOP
`I = 0: WHILE I <> &HAA
`GOSUB reads
`IF timeout THEN GOTO retry
`
`WEND
`GOSUB reads
`IF timeout THEN GOTO retry
`IF I <> &HAA THEN GOTO findsync
`GOSUB readword: check = iv' Read checksum
`'''''''''''''''IF check <> 0 THEN PRINT "--"; HEX$(check)
`IF timeout THEN GOTO retry
`GOSUB readword: words = iv' Read # of words
`bytes = 2 * words' Which gives # bytes
`IF timeout THEN GOTO retry
`IF words > 256 THEN GOTO findsync
`
`scheck = 0: NN = 0
`'CLS
`IF dhistory = 0 THEN
`FOR n = 0 TO words - 1' Do checksum
`calculation
`
`GOSUB reads' & fill the 'r(' array
`scheck = scheck + I
`r(NN) = I: rr(NN, HISTORY) = I: NN = NN + 1
`IF timeout THEN GOTO retry
`GOSUB reads
`r(NN) = I: rr(NN, HISTORY) = I: NN = NN + 1
` '''' PRINT HEX$(r(nn)); " ";
`
`17
`
`Escort Ex. 2086, pg. 17
`
`
`
`IF timeout THEN GOTO retry
`NEXT n
`GOSUB readword
`scheck = (scheck AND 255) - (iv AND 255)
`
`ELSE
`
`' IF user hit "*", play back the last ten sweeps
`LOCATE 1, 1
`PRINT "history: "; HISTORY; : INPUT BLAT
`IF BLAT <> 0 THEN HISTORY = BLAT
`FOR n = 0 TO words - 1
`r(NN) = rr(NN, HISTORY): NN = NN + 1
`r(NN) = rr(NN, HISTORY): NN = NN + 1
`NEXT n
`END IF
`
`HISTORY = HISTORY + 1: IF HISTORY > 10 THEN HISTORY =
`
`0
`
`'''GOTO findsync
`'''''''''''''''''''''''''''''''''''''''''''''''''''''''''
`' Map the 'r(' array into program variables '
`'''''''''''''''''''''''''''''''''''''''''''''''''''''''''
`p = 0
`version = r(p): p = p + 2
`IF version = 81 THEN solo = 1
`IF version = 70 THEN p4600 = 1
`LOCATE 18, 1
`ie = 0
`FOR I = 0 TO 11
`xkmag(I) = r(p + 3 * I)
`POKE iv1, r(p + 3 * I + 2)
`POKE iv2, r(p + 3 * I + 1)
`IF iv < 0 THEN GOTO record
`xkindex(I) = iv - xkbase
`NEXT I
`
`p = p + 36
`FOR I = 0 TO 3
`POKE iv1, r(p + 2 * I + 1)
`POKE iv2, r(p + 2 * I)
`xkcor(I) = (iv AND &H7FFF) - xkbase
`IF xkcor(I) < 0 THEN xkcor(I) = 0
`NEXT I
` ' FOR i = 0 TO 1
` ' IF xdetect OR kdetect THEN
` ' PRINT USING aa$; i; HEX$(xkcor(i)); HEX
`$(xkcor(i))
` ' ELSE
` ' PRINT USING aa$; i; HEX$(kacor(i)); HEX
`$(kacor(i))
` ' END IF
` ' NEXT i
`p = p + 8
`FOR I = 0 TO 11
`
`18
`
`Escort Ex. 2086, pg. 18
`
`
`
`kamag(I) = r(p + 3 * I)
`POKE iv1, r(p + 3 * I + 2)
`POKE iv2, r(p + 3 * I + 1)
`kaindex(I) = (iv AND &H7FFF) - KABASE
`NEXT I
`p = p + 36
`FOR I = 0 TO 3
`POKE iv1, r(p + 2 * I + 1)
`POKE iv2, r(p + 2 * I)
`kacor(I) = (iv AND &H7FFF) - KABASE
`IF kacor(I) < 0 THEN kacor(I) = 0
`NEXT I
`p = p + 8
`FOR I = 0 TO 7
`hotxkmag(I) = r(p + 3 * I)
`POKE iv1, r(p + 3 * I + 2)
`POKE iv2, r(p + 3 * I + 1)
`hotxkindex(I) = (iv AND &H7FFF) - HOTXKBASE
` NEXT I
`p = p + 24
`
`smartspec = r(p): p = p + 2
`
`flaga = r(p): p = p + 1
`flagb = r(p): p = p + 1
`flagc = r(p): p = p + 1
`
`FOR I = 0 TO 3
`regtim(I) = r(p): p = p + 1
`NEXT I
`lcount = r(p):
`IF p4600 THEN PRINT "laser : "; lcount; " "
`p = p + 1
`
`POKE iv1, r(p): POKE iv2, r(p + 1)
`peak1 = iv: p = p + 2
`POKE iv1, r(p): POKE iv2, r(p + 1)
`peak2 = iv: p = p + 2
`IF peak1 < peak2 THEN SWAP peak1, peak2
`
`swcntouter = r(p): p = p + 1
`swcntinner = r(p): p = p + 1
`swcnthotxk = r(p): p = p + 3
`
`xkthresh = r(p): p = p + 1
`hotxkthresh = r(p): p = p + 1
`kathresh = r(p): p = p + 1
`
`xklevn = r(p): p = p + 1
`kalevn = r(p): p = p + 1
`maxage = r(p): p = p + 1
`display1 = r(p): p = p + 1
`
`19
`
`Escort Ex. 2086, pg. 19
`
`
`
`plevel = r(p): p = p + 1
`'----------------------------------------------------
`ie = 0
`FOR I = 0 TO 5
`IF ie <= 4 THEN
`IF NOT (hotdetect) AND NOT (kainner) THEN ind = xkindex(I):
`mag = xkmag(I)
`IF hotdetect THEN ind = hotxkindex(I): mag = hotxkmag(I)
`IF kainner THEN ind = kaindex(I): mag = kamag(I)
`IF ind > 16 THEN
`PRINT USING aa$; I; HEX$(ind); HEX$(mag)
`pp(ie) = ind
`ie = ie + 1
`END IF
`END IF
`NEXT I
`FOR I = 0 TO 3
`IF kadetect THEN
`hold(I) = kacor(I)
`END IF
`PRINT USING aa$; I; HEX$(kacor(I)); HEX$(hold(I))
`NEXT I
`' zt = ABS(CSNG(pp(1) - pp(0)) * zflt)
` ' PRINT USING "p-p Delta ###.## mS"; zt
`
`
` ' PRINT USING "k/plevel ## "; plevel
`display2 = r(p): p = p + 1
`FOR I = 0 TO 3
`POKE iv1, r(p): POKE iv2, r(p + 1)
`center(I) = (iv AND &H7FFF) - xkbase: p = p + 2
`NEXT I
`
`tstflag = r(p): p = p + 1
`flagi1 = r(p): p = p + 1
`flagi2 = r(p): p = p + 1
`
` IF flagi2 AND 8 THEN PRINT "Linearize " ELSE PRINT
`"No Linearize"
`flagi3 = r(p): p = p + 1
`
`LPRINT CHR$(1)' Set parallel port bit high
`LPRINT CHR$(0)' Set parallel port bit low
`RETURN
`
`' Read two bytes from serial interface & form word
`
`readword:
`GOSUB reads: POKE iv1, I
`IF timeout THEN RETURN
`GOSUB reads: POKE iv2, I
`RETURN
`
`20
`
`Escort Ex. 2086, pg. 20
`
`
`
`' Read byte via serial interface
`
`reads: time = 32000
`'ERR = 0: ON ERROR RESUME NEXT
`WHILE LOC(1) = 0
`time = time - 1:
`IF time = 0 THEN
`timeout = -1:
`''''LOCATE 15, 0: PRINT "timeout # "; tbad; WORDS; N
`RETURN
`END IF
`
`WEND
` I = ASC(INPUT$(1, #1))
` ON ERROR GOTO 0' Terminate the error support
`RETURN
`
`21
`
`Escort Ex. 2086, pg. 21