of course, it'd be helpful to actually apply the patch in my tree...
[debian/as31] / examples / paulmon1.asm
1 ;  PAULMON 8051 Debugger by Paul Stoffregen
2
3 ;        .command +h58   ;set page height to 58 in listing file...
4
5         .equ    start,0000h    ;address for start of EPROM (0000h)
6         .equ    program,2000h  ;address for program loading location
7
8         .ORG    start        
9 rst:    lJMP    poweron
10
11         .org    start+3       ;ext int #0
12         LJMP    program+3
13         .org    start+11      ;timer #0
14         LJMP    program+11
15         .org    start+13h     ;external interrupt routine #1
16         jnb     tcon.2,intr0
17         ljmp    program+13h     ;don't do ssrun if edge trigger'd
18 intr0:  ajmp    step            ;but do ssrun if level trigger'd
19         .org    start+1bh     ;timer #1
20         ljmp    program+1bh   
21         .org    start+23h     ;serial port
22         ljmp    program+23h   
23         .org    start+2bh     ;timer #2 (8052 only)
24         ljmp    program+2bh
25
26
27         .org    start+30h     ;the jump table
28         ajmp    cout
29         ajmp    cin
30         ajmp    phex
31         ajmp    phex16
32         ajmp    pstr
33         ajmp    ghex
34         ajmp    ghex16
35         ajmp    esc
36         ajmp    upper
37         ljmp    init
38
39 step:    ;this is the single step interrupt processor code...
40         push    psw     ;better save these while we still can
41         push    acc
42         clr     psw.3   ;gotta be set to bank zero...
43         clr     psw.4
44 step1:  acall   cin
45         acall   upper
46 step2:  cjne    a,#13,step7
47         ajmp    status
48 step7:  cjne    a,#32,step8    ;check space
49         ajmp    done
50 step8:  cjne    a,#'?',step10  ;check '?'
51         acall   sshelp
52         ajmp    step1
53 step10: cjne    a,#'Q',step11  ;check 'Q'=quit and run normal
54         push    dpl
55         push    dph
56         mov     dptr,#squit
57         acall   pstr
58         pop     dph
59         pop     dpl
60         clr     ie.2
61         ajmp    done
62 step11: cjne    a,#'H',step12  ;check 'H'=hex dump internal ram
63         acall   ssdmp
64         ajmp    step1
65 step12: cjne    a,#'R',step13  ;check 'R'=print out registers
66         ajmp    ssreg
67 step13: cjne    a,#'S',step14  ;check 'S'=skip this inst
68         ajmp    skip0
69 step14: cjne    a,#'A',step20  ;check 'A'=change acc value
70         ajmp    chacc
71         
72 step20: ajmp    step1
73    
74 pequal:        ; prints '='
75         mov     a,#'='
76         acall   cout
77         ret
78
79 status:         ;prints two-line status during single step run
80         mov     a,r0
81         push    acc
82         acall   space
83         mov     a,#'S'
84         acall   cout
85         mov     a,#'P'
86         acall   cout
87         acall   pequal
88         mov     r0,sp
89         push    b
90         acall   phex
91         dec     r0
92         acall   space
93         lcall   pa
94         acall   pequal
95         mov     a,@r0
96         acall   phex
97         dec     r0
98         acall   space
99         lcall   prc
100         acall   pequal
101         mov     a,@r0
102         mov     c,acc.7
103         clr     a
104         rlc     a
105         acall   phex1
106         acall   space
107         lcall   pdptr
108         acall   pequal
109         mov     a,dph
110         acall   phex
111         mov     a,dpl
112         acall   phex
113         clr     a
114         acall   pregsn
115         mov     r0,sp
116         dec     r0
117         mov     a,@r0
118         acall   phex
119         mov     a,#1
120         acall   pregsn
121         mov     a,r1
122         acall   phex
123         mov     a,#2
124         acall   pregsn
125         mov     a,r2
126         acall   phex
127         mov     a,#3
128         acall   pregsn
129         mov     a,r3
130         acall   phex
131         mov     a,#4
132         acall   pregsn
133         mov     a,r4
134         acall   phex
135         mov     a,#5
136         acall   pregsn
137         mov     a,r5
138         acall   phex
139         mov     a,#6
140         acall   pregsn
141         mov     a,r6
142         acall   phex
143         mov     a,#7
144         acall   pregsn
145         mov     a,r7
146         acall   phex
147         acall   newline
148         acall   space           ;now begin printing the 2nd line
149         mov     a,#'P'
150         acall   cout
151         lcall   prc
152         acall   pequal
153         clr     c              
154         mov     a,sp
155         subb    a,#4
156         mov     r0,a
157         push    dpl
158         push    dph
159         lcall   inst
160         pop     dph
161         pop     dpl
162         pop     b
163         pop     acc
164         mov     r0,a
165 done:   pop     acc
166         pop     psw
167         reti
168
169
170 sshelp: push    dpl
171         push    dph
172         acall   newline
173         mov     dptr,#help5txt
174         acall   pstr
175         pop     dph
176         pop     dpl
177         ret
178
179 pregsn: push    acc
180         acall   space
181         mov     a,#'R'
182         acall   cout
183         pop     acc
184         acall   phex1
185         acall   pequal
186         ret
187
188 ssdmp:                    ;.
189         push    0
190         push    1
191         push    b
192         push    dpl
193         push    dph
194         mov     dptr,#ssdmps1
195         acall   pstr
196         pop     dph
197         pop     dpl
198         clr     a
199         acall   phex
200         mov     a,#':'
201         acall   cout
202         acall   space
203         mov     a,r0
204         acall   phex
205         acall   space
206         mov     a,r1
207         acall   phex
208         mov     r0,#2
209         mov     r1,#14
210         ajmp    ssdmp2
211 ssdmp1: mov     a,r0
212         acall   phex
213         mov     a,#':'
214         acall   cout
215         mov     r1,#16
216 ssdmp2: acall   space
217         mov     a,@r0
218         acall   phex
219         inc     r0
220         djnz    r1,ssdmp2
221         acall   newline
222         cjne    r0,#80h,ssdmp1
223         acall   newline
224         pop     b
225         pop     1
226         pop     0
227         ret
228
229 ssreg:           
230         push    b             ;.
231         acall   space
232         mov     a,#'B'
233         acall   cout
234         acall   pequal
235         mov     a,b
236         acall   phex
237         acall   space
238         mov     a,#'P'
239         acall   cout
240         mov     a,#'S'
241         acall   cout
242         mov     a,#'W'
243         acall   cout
244         acall   pequal
245         mov     a,r0
246         push    acc
247         mov     r0,sp
248         dec     r0
249         dec     r0
250         dec     r0
251         mov     a,@r0
252         acall   phex
253         acall   space
254         push    dpl
255         push    dph
256         mov     dptr,#sfr3+1
257         mov     r0,0xA8
258         acall   psfr
259         mov     dptr,#sfr4+1
260         mov     r0,0xB8
261         acall   psfr
262         mov     dptr,#sfr5+1
263         mov     r0,0x89
264         acall   psfr
265         mov     dptr,#sfr6+1
266         mov     r0,0x88
267         acall   psfr
268         mov     dptr,#sfr7+1
269         mov     r0,0x98
270         acall   psfr
271         mov     dptr,#sfr8+1
272         mov     r0,0x87
273         acall   psfr
274         mov     a,#'T'
275         acall   cout
276         mov     a,#'0'
277         acall   cout
278         acall   pequal
279         mov     a,8Ch
280         acall   phex
281         mov     a,8Ah
282         acall   phex
283         acall   space
284         mov     a,#'T'
285         acall   cout
286         mov     a,#'1'
287         acall   cout
288         acall   pequal
289         mov     a,8Dh
290         acall   phex
291         mov     a,8Bh
292         acall   phex
293         acall   newline
294         pop     dph
295         pop     dpl
296         pop     acc
297         mov     r0,a
298         pop     b
299         ajmp    step1
300
301 psfr:   acall   pstr
302         acall   pequal
303         mov     a,r0
304         acall   phex
305         acall   space
306         ret
307
308 skip0:                       ;.
309         push    b
310         mov     a,r0
311         push    acc
312         mov     a,sp
313         clr     c
314         subb    a,#4
315         mov     r0,a
316         push    dpl
317         push    dph
318         mov     dptr,#sskip1
319         acall   pstr
320         lcall   inst          ;print skipped instruction r0 points to pc
321         mov     a,sp
322         clr     c
323         subb    a,#6
324         mov     r0,a
325         mov     @r0,dph         ;actually change the pc!
326         dec     r0
327         mov     @r0,dpl
328         mov     dptr,#sskip2
329         acall   pstr
330         inc     r0
331         lcall   inst            ;print new instruction
332         pop     dph
333         pop     dpl
334         pop     acc
335         mov     r0,a
336         pop     b
337         ajmp    step1
338
339 chacc:
340         mov     a,r0
341         push    acc
342         push    b
343         mov     r0,sp
344         dec     r0
345         dec     r0
346         push    dpl
347         push    dph
348         mov     dptr,#chaccs1
349         acall   pstr
350         acall   ghex
351         jc      chacc2
352         mov     @r0,a
353         acall   newline
354         pop     dph
355         pop     dpl
356         pop     b
357         pop     acc
358         mov     r0,a
359         ajmp    step1
360 chacc2: mov     dptr,#abort
361         acall   pstr
362         pop     dph
363         pop     dpl
364         pop     b
365         pop     acc
366         mov     r0,a
367         ajmp    step1
368
369 DownLoad:       ;Note, this is a modified version of the
370                 ;auto baud rate detection routine from
371                 ;MDP/51.  Thank You, Kei-Yong Khoo (3-31-87)
372         push    dpl
373         push    dph
374         mov     dptr,#dwlds1            
375         acall   pstr            ;"begin sending file <ESC> to abort"
376 dwld0a: aCALL   cin 
377         CJNE    A, #27, DWLD0   ; Test for escape
378 dwldesc:mov     dptr,#dwlds2    
379         acall   pstr            ;"download aborted."
380         pop     dph
381         pop     dpl
382         ret
383 DWLD0:                         
384         CJNE    a, #0x3A, DWLD0a     ; wait for ':'
385         ACALL   ghex
386         jc      dwldesc
387         MOV     R0, A             ; R0 = # of data bytes
388         ACALL   ghex
389         jc      dwldesc
390         MOV     DPH, A            ; High byte of load address
391         ACALL   ghex
392         jc      dwldesc
393         MOV     DPL, A            ; Low byte of load address
394         ACALL   ghex              ; Record type
395         jc      dwldesc
396         CJNE    A, #1, DWLD1      ; End record?
397         mov     dptr,#dwlds3
398         acall   pstr              ;"download went ok..."
399         pop     dph
400         pop     dpl
401         ret
402 DWLD1:  INC     R0                ; adjust for repeat loop
403         AJMP    DWLD3
404 DWLD2:  ACALL   ghex              ; Get data byte
405         jc      dwldesc
406         MOVX    @DPTR, A
407         INC     DPTR
408 DWLD3:  DJNZ    R0, DWLD2
409         ACALL   ghex              ; Discard checksum
410         jc      dwldesc
411         aJMP    DWLD0a
412
413 INIT:           ;Note, this is a modified version of the
414                 ;auto baud rate detection routine from
415                 ;MDP/51.  Thank You, Kei-Yong Khoo (3-31-87)
416         orl     PCON,#10000000b   ; set double baud rate
417         MOV     TMOD,#00010001b
418         MOV     SCON,#01010000b  ; Set Serial for mode 1 &
419                                  ; Enable reception
420         ORL     TCON,#01010010b  ; Start timer 1 both timer
421         mov     a,7Bh
422         mov     r1,7Ah
423         mov     r2,79h
424         mov     r3,78h
425         xrl     1,#01010101b
426         xrl     2,#11001100b
427         xrl     3,#00011101b
428         cjne    a,1,auto
429         cjne    a,2,auto
430         cjne    a,3,auto
431         sjmp    autoend          ;baud rate is known from last time...
432 AUTO:   CLR     TR1              ; Stop timer 1
433         MOV     TH1, #0          ; Clear timer 1
434         MOV     TL1, #0
435         JB      RXD, *           ; Wait for start bit
436         JB      RXD,AUTO         ; make sure it's not just noise
437         JB      RXD,AUTO
438         JB      RXD,AUTO
439         JB      RXD,AUTO
440         JNB     RXD, *           ; skip start bit
441         SETB    TR1
442         JB      RXD, * 
443         JNB     RXD, *
444         JB      RXD, *
445         JNB     RXD, *         ; Count 3 more bits
446         CLR     TR1
447          ;  Compute baud rate
448         MOV     A, TL1           ; divide TH1-TL1 by 128
449         RLC     A                
450         MOV     A, TH1
451         RLC     A
452         CPL     A
453         INC     A                ; 2's complement
454         mov     b,a              ; store the reload value four times
455         mov     7Bh,a            ;so that it might be there later
456         xrl     a,#01010101b     ;we'll store the reload value
457         mov     7Ah,a            ;four times, just to be safe
458         mov     a,b
459         xrl     a,#11001100b
460         mov     79h,a
461         mov     a,b
462         xrl     a,#00011101b
463         mov     78h,a
464         mov     a,b
465 autoend:MOV     TH1,A
466         mov     tmod,#00100001b  ;now it's 8 bit auto-reload
467         SETB    TR1
468         RET
469
470 HELP:
471         push    dpl
472         push    dph
473         MOV     DPTR,#HELP1txt
474         ACALL   PSTR
475         mov     dptr,#cmd_tbl
476         clr     a
477 help0:  movc    a,@a+dptr
478         jz      help_2
479         inc     dptr
480         acall   space
481         acall   cout
482         mov     r0,#4
483 help1:  acall   space
484         djnz    r0,help1
485         clr     a
486         movc    a,@a+dptr   ;(high)
487         mov     b,a
488         inc     dptr
489         clr     a
490         movc    a,@a+dptr   ;(low)
491         inc     dptr
492         inc     dptr
493         inc     dptr
494         push    dpl
495         push    dph
496         mov     dpl,a
497         mov     dph,b
498         clr     a
499         acall   pstr
500         acall   newline
501         pop     dph
502         pop     dpl
503         sjmp    help0
504 help_2: mov     dptr,#help2txt
505         acall   pstr
506         pop     dph
507         pop     dpl
508         RET
509
510 run:
511         push    dpl
512         push    dph
513         mov     dptr,#prompt6
514         acall   pstr
515         acall   cin
516         acall   upper
517         cjne    a,#27,run1
518         mov     dptr,#abort             ;if they press <ESC>
519         acall   pstr
520         pop     dph
521         pop     dpl
522         ret
523 run1:   cjne    a,#'?',run3
524         mov     dptr,#help3txt          ;if they pressed ?
525         acall   pstr
526         mov     dptr,#prompt7
527         acall   pstr
528         acall   cin
529         cjne    a,#27,run2
530         pop     dph
531         pop     dpl
532         ret
533 run2:   mov     dptr,#help4txt
534         acall   pstr
535         mov     dptr,#help5txt
536         acall   pstr
537         pop     dph
538         pop     dpl
539         ret
540 run3:   cjne    a,#'S',run4
541         mov     dptr,#runss
542         acall   pstr
543         ajmp    ssrun
544 run4:   mov     dptr,#runstd
545         acall   pstr
546         mov     dptr,#prompt8              ;run the user's program
547         acall   pstr
548         pop     dph
549         pop     dpl
550         acall   phex16
551         push    dpl
552         push    dph
553         mov     dptr,#prompt4
554         acall   pstr
555         pop     dph
556         pop     dpl
557         acall   ghex16
558         jnc     run5
559         mov     dptr,#abort
560         acall   pstr
561         ret
562 run5:   mov     a,#'\r'
563         acall   cout
564         push    dpl
565         push    dph
566         mov     dptr,#runs1
567         acall   pstr
568         pop     dph
569         pop     dpl
570         mov     a,#rst & 0xFF           
571         push    acc
572         mov     a,#rst
573         push    acc
574         push    dpl
575         push    dph
576         ret                     ;<-- actually jumps to user's program
577
578         
579 ssrun:  mov     dptr,#prompt8              ;run single step
580         acall   pstr
581         pop     dph
582         pop     dpl
583         push    dpl
584         push    dph
585         acall   phex16
586         mov     dptr,#prompt4
587         acall   pstr
588         pop     dph
589         pop     dpl
590         acall   ghex16
591         push    dpl
592         push    dph
593         jnc     ssrun1
594         mov     dptr,#abort
595         acall   pstr
596         acall   newline
597         pop     dph
598         pop     dpl
599         ret
600 ssrun1: clr     tcon.2
601         jnb     p3.3,ssrun2
602         mov     dptr,#sserr1      ;give error msg if int1 not grounded
603         acall   pstr
604         pop     dph
605         pop     dpl
606         ret
607 ssrun2: mov     dptr,#prompt9           ;ask for priority
608         acall   pstr
609         acall   cin
610         acall   upper
611         cjne    a,#27,ssrun3
612         mov     dptr,#abort
613         acall   pstr
614         pop     dph
615         pop     dpl
616         ret
617 ssrun3: cjne    a,#'L',ssrun4
618         mov     ip,#00000000b
619         sjmp    ssrun5
620 ssrun4: mov     ip,#00000100b
621 ssrun5: mov     dptr,#ssmsg     ;tell 'em it now time, remind to
622         acall   pstr            ;to hit <RET> for next inst
623         pop     dph
624         pop     dpl
625         mov     sp,#38h
626         mov     a,#rst & 0xFF           
627         push    acc
628         mov     a,#0
629         push    acc
630         clr     a
631         clr     c
632         mov     r0,#0
633         mov     r1,#1
634         mov     r2,#0
635         mov     r3,#0
636         mov     r4,#0
637         mov     r5,#0
638         mov     r6,#0
639         mov     r7,#0
640         clr     tcon.2
641         setb    p3.3
642         mov     ie,#10000100b
643         jmp     @a+dptr
644
645
646
647
648 dump:   
649         mov     r2,#16          ;number of lines to print
650         acall   newline
651 dump1:  mov     r0,#20h         ;pointer to memory to store bytes
652         acall   phex16
653         mov     a,#':'
654         acall   cout
655         mov     a,#' '
656         acall   cout
657 dump2:  clr     A                  ;<--acquire 16 bytes
658         movc    a,@a+dptr          ;and store from 20 to 2F
659         mov     @r0,a
660         acall   phex
661         mov     a,#' '
662         acall   cout
663         inc     dptr
664         inc     r0
665         cjne    r0,#30h,dump2
666         acall   cout
667         mov     r0,#20h           ;now we'll print it in ascii
668 dump3:  mov     a,@r0
669         anl     a,#01111111b      ;avoid unprintable characters
670         mov     b,a
671         clr     c
672         subb    a,#20h
673         jnc     dump4
674         mov     b,#' '
675 dump4:  mov     a,b
676         acall   cout
677         inc     r0
678         cjne    r0,#30h,dump3
679         acall   newline
680         acall   esc
681         jc      dump5
682         djnz    r2,dump1        ;loop back up to print next line
683 dump5:  acall   newline
684         ret
685
686
687 new_loc:push    dph
688         push    dpl
689         acall   newline
690         mov     dptr,#prompt5
691         acall   pstr
692         pop     dpl
693         pop     dph
694         push    dph
695         push    dpl
696         acall   ghex16
697         acall   newline
698         jc      newloc1
699         acall   newline
700         pop     acc
701         pop     acc
702         ret
703 newloc1:mov     dptr,#abort
704         acall   pstr
705         pop     dpl
706         pop     dph
707         acall   newline
708         ret
709
710 edit:      ;edit external ram...
711         push    dpl
712         push    dph
713         mov     dptr,#edits1
714         acall   pstr
715         pop     dph
716         pop     dpl
717 edit1:  acall   phex16
718         mov     a,#':'
719         acall   cout
720         acall   space
721         mov     a,#'('
722         acall   cout
723         movx    a,@dptr
724         acall   phex
725         push    dpl
726         push    dph
727         mov     dptr,#prompt10
728         acall   pstr
729         acall   ghex
730         jb      psw.5,edit2
731         jc      edit2
732         pop     dph
733         pop     dpl
734         movx    @dptr,a
735         acall   newline
736         inc     dptr
737         ajmp    edit1
738 edit2:  mov     dptr,#edits2
739         acall   pstr
740         pop     dph
741         pop     dpl
742         ret
743
744 list:       ;prints out dis-assembly list of memory
745         mov     r2,#18  ;# of lines to list
746         acall   newline
747 list1:  mov     a,r2
748         push    acc
749         acall   disasm          ;this obviously does all the work
750         pop     acc
751         mov     r2,a
752         acall   esc
753         jc      list2
754         djnz    r2,list1
755 list2:  acall   newline
756         ret
757
758
759
760 CIN:
761         JNB     RI,cin  ; wait for character
762         CLR     RI
763         MOV     A,SBUF
764         RET
765
766 COUT:    ;note, improved... much faster transmission
767         jnb     ti,*       ;wait if a character is still sending
768         MOV     SBUF,A
769         CLR     TI         ;note: hardware will set ti when the
770         RET                ;      character finishes sending...
771  
772 esc:  ;checks to see if <ESC> is waiting on serial port.
773       ;C=clear if no <ESC>, C=set if <ESC> pressed, buffer flushed
774         push    acc
775         clr     c
776         jnb     ri,esc1
777         mov     a,sbuf
778         cjne    a,#27,esc1
779         setb    c
780         clr     ri
781 esc1:   pop     acc
782         ret
783
784 NEWLINE:
785         PUSH    ACC
786         MOV     A,#'\r'
787         ACALL   COUT
788         POP     ACC
789         RET
790
791 g1hex:     ;gets one character.  Converts to hex and places in Acc
792            ;C=1 if <ESC> pressed, 0 otherwise
793            ;PSW.5=1 if <RET> pressed, 0 otherwise
794            ;PSW.2=1 if backspace or delete, 0 otherwise  (not yet)
795         acall   cin
796         acall   upper
797         clr     c
798         clr     psw.5
799         clr     psw.2
800         cjne    a,#13,g1hex2
801         setb    psw.5
802         ret
803 g1hex2: cjne    a,#27,g1hex2a
804         cpl     c
805         ret
806 g1hex2a:cjne    a,#8,g1hex2c
807 g1hex2b:setb    psw.2
808         ret
809 g1hex2c:cjne    a,#127,g1hex3
810         sjmp    g1hex2b
811 g1hex3: push    b
812         mov     b,a
813         acall   asc2hex        
814         jc      g1hex4           ;they typed a bad char, so go back
815         xch     a,b
816         acall   cout
817         xch     a,b
818         pop     b
819         ret
820 g1hex4: pop     b
821         sjmp    g1hex
822
823 ghex:      ; gets an 8-bit hex value from keyboard, returned in A.
824            ; C=1 if <ESC> pressed, 0 otherwise
825            ; PSW.5 if <RET> pressed w/ no input, 0 otherwise
826         acall   g1hex
827         jnb     psw.5,ghex1
828         ret
829 ghex1:  jnc     ghex2
830         ret
831 ghex2:  swap    a
832         mov     b,a
833 ghex3:  acall   g1hex
834         jb      psw.2,ghex6
835         jnb     psw.5,ghex4
836         clr     psw.5
837         mov     a,b
838         swap    a
839         ret
840 ghex4:  jnc     ghex5
841         ret
842 ghex5:  orl     a,b
843         ret
844 ghex6:  mov     a,#8
845         acall   cout
846         sjmp    ghex
847
848
849
850         
851 ghex16:    ; gets a 16-bit hex value from keyboard, returned in DPTR.
852            ; C=0 if normal <RET>, C=1 if <ESC> pressed
853
854         push    acc
855         mov     a,r0
856         push    acc
857         mov     a,r1
858         push    acc
859         mov     a,r2
860         push    acc
861         mov     a,r3
862         push    acc
863 ghex16a:acall   g1hex           ;get first character
864         mov     r0,a
865         jc      ghex16z
866         jb      psw.5,ghex16z
867         jb      psw.2,ghex16a
868 ghex16e:acall   g1hex           ;get second character
869         mov     r1,a
870         jc      ghex16z
871         jb      psw.5,ghex16s
872         jnb     psw.2,ghex16i
873         mov     a,#8
874         acall   cout
875         sjmp    ghex16a
876 ghex16i:acall   g1hex           ;get third character
877         mov     r2,a
878         jc      ghex16z
879         jb      psw.5,ghex16t
880         jnb     psw.2,ghex16m
881         mov     a,#8
882         acall   cout
883         sjmp    ghex16e
884 ghex16m:acall   g1hex           ;get fourth character
885         mov     r3,a
886         jc      ghex16z
887         jb      psw.5,ghex16u
888         jnb     psw.2,ghex16v
889         mov     a,#8
890         acall   cout
891         sjmp    ghex16i        
892 ghex16s:mov     dph,#0          ;one digit entered
893         mov     dpl,r0
894         sjmp    ghex16z
895 ghex16t:mov     dph,#0          ;two digit entered
896         mov     a,r0
897         swap    a
898         orl     a,r1
899         mov     dpl,a
900         sjmp    ghex16z
901 ghex16u:mov     dph,r0          ;three digit entered
902         mov     a,r1
903         swap    a
904         orl     a,r2
905         mov     dpl,a
906         sjmp    ghex16z
907 ghex16v:mov     a,r0            ;all four digit entered
908         swap    a
909         orl     a,r1
910         mov     dph,a
911         mov     a,r2
912         swap    a
913         orl     a,r3
914         mov     dpl,a 
915 ghex16z:pop     acc             ;exit, at last...
916         mov     r3,a
917         pop     acc
918         mov     r2,a
919         pop     acc
920         mov     r1,a
921         pop     acc
922         mov     r0,a
923         pop     acc
924         ret
925         
926
927
928 PHEX:
929         PUSH    ACC
930         SWAP    A
931         ACALL   PHEX1
932         POP     ACC
933         ACALL   PHEX1
934         RET
935 PHEX1:  ANL     A,#0FH
936         ADD     A,#3
937         MOVC    A,@A+PC
938         ACALL   COUT
939         RET
940         .DB     "0123456789ABCDEF"
941
942 asc2hex:             ;carry set if invalid input
943         clr     c
944         push    b
945         subb    a,#'0'
946         mov     b,a
947         subb    a,#10
948         jc      a2h1
949         mov     a,b
950         subb    a,#7
951         mov     b,a
952 a2h1:   mov     a,b
953         clr     c
954         anl     a,#11110000b     ;just in case...
955         jz      a2h2
956         setb    c
957 a2h2:   mov     a,b
958         pop     b
959         ret
960
961 upper:  ;converts the ascii code in Acc to uppercase, if it is lowercase
962         push    b
963         mov     b,a
964         clr     c
965         subb    a,#61h
966         jc      upper1;   not a lowercase character
967         subb    a,#26
968         jnc     upper1
969         clr     c
970         mov     a,b
971         subb    a,#20h
972         mov     b,a
973 upper1: mov     a,b
974         pop     b
975         ret
976
977 space:  push    acc
978         mov     a,#' '
979         acall   cout
980         pop     acc
981         ret
982
983
984 PHEX16:
985         PUSH    ACC
986         MOV     A,DPH
987         ACALL   PHEX
988         MOV     A,DPL
989         ACALL   PHEX
990         POP     ACC
991         RET
992
993 PSTR:                  ;print string
994         PUSH    ACC
995 PSTR1:  CLR     A
996         MOVC    A,@A+DPTR
997         jb      ri,pstr3
998         JZ      PSTR2
999         mov     c,acc.7
1000         anl     a,#01111111b
1001         jnb     ti,*            ;wait for last character to finish sending
1002         mov     sbuf,a
1003         clr     ti
1004         Jc      pstr2
1005         inc     dptr
1006         SJMP    PSTR1                                          
1007 PSTR2:  POP     ACC
1008         RET    
1009 pstr3:  clr     ri
1010         mov     a,sbuf
1011         cjne    a,#27,pstr1
1012         mov     a,#13
1013         acall   cout
1014         sjmp    pstr2
1015
1016 disasm:    ;prints out instruction @dptr, and advances dptr
1017         acall   phex16        ;they'd like to know the address...
1018         clr     a
1019         movc    a,@a+dptr
1020         inc     dptr
1021         mov     r3,a
1022         push    dph
1023         push    dpl
1024         mov     dptr,#mnot    ;mnot=mnunonic offset table
1025         movc    a,@a+dptr
1026         mov     r2,a
1027         mov     a,r3
1028         mov     dptr,#opot    ;opot=operand offset table
1029         movc    a,@a+dptr
1030         mov     r6,a              ;these 2 tables are a bitch to enter!!!
1031         anl     a,#11111100b
1032         rr      a
1033         rr      a
1034         mov     r7,a
1035         mov     a,r6
1036         anl     a,#00000011b
1037         pop     dpl
1038         pop     dph
1039         mov     r6,a
1040         dec     a
1041         jz      disasm1
1042         push    acc
1043         clr     a
1044         movc    a,@a+dptr       ;fetch 2nd byte (if nec)
1045         inc     dptr
1046         mov     r4,a
1047         pop     acc
1048         dec     a
1049         jz      disasm1
1050         clr     a
1051         movc    a,@a+dptr       ;fetch 3rd byte (if nec)
1052         inc     dptr  
1053         mov     r5,a
1054 disasm1:acall   disasm4         ;prints the bytes+spaces
1055         push    dpl
1056         push    dph
1057         mov     dptr,#mnu_tbl   ;mnu_tlb: table with actual text...
1058         acall   disasm5         ;prints the mnenonic+spaces
1059         mov     a,r7
1060         mov     r0,a
1061         pop     acc
1062         pop     b
1063         push    b
1064         push    acc
1065         mov     r6,a      ;(high) in case of ajmp or acall or rel
1066         mov     a,b
1067         mov     r7,a      ;(low)
1068         mov     a,r0
1069         dec     a
1070         clr     c
1071         rlc     a
1072         mov     b,#dasm2 & 0xff  ;(low)
1073         push    b
1074         mov     b,#dasm2 / 256    ;(high)
1075         push    b
1076         mov     dptr,#oprt      ;oprt=operand routine table
1077         jmp     @a+dptr
1078 dasm2:  pop     dph
1079         pop     dpl
1080         acall   newline
1081         ret
1082
1083 disasm4:mov     a,#':'       ;print bytes and some punctuation
1084         acall   cout
1085         acall   space
1086         mov     a,r3
1087         acall   phex
1088         acall   space
1089         cjne    r6,#1,dis4a
1090         mov     r1,#11
1091         sjmp    dis4c
1092 dis4a:  mov     a,r4
1093         acall   phex
1094         acall   space
1095         cjne    r6,#2,dis4b
1096         mov     r1,#8
1097         sjmp    dis4c
1098 dis4b:  mov     a,r5
1099         acall   phex
1100         mov     r1,#6
1101 dis4c:  acall   space
1102         djnz    r1,dis4c
1103         ret
1104
1105 disasm5:mov     r0,#7+1         ;prints the mnunonic+spaces
1106 dis5a:  mov     a,r2
1107         MOVC    A,@A+DPTR
1108         INC     r2
1109         dec     r0
1110         mov     c,acc.7
1111         anl     a,#01111111b
1112         acall   cout
1113         Jc      dis5b
1114         SJMP    dis5a
1115 dis5b:  acall   space
1116         djnz    r0,dis5b
1117         RET
1118
1119
1120 ;-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-;
1121 ;       2k page boundry must exist between these dividers             ;
1122 ;-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-;
1123
1124            
1125 prompt1:.db     ">Loc=",0
1126 prompt2:.db     ": (Version 1.0) Command>",0
1127 prompt3:.db     "Location (",0
1128 prompt4:.db     "=Default): ",0
1129 prompt5:.db     "New memory pointer location: ",0
1130 prompt6:.db     "\rS=Single Step, N=Normal (default), ?=Help >",0
1131 prompt7:.db     "Press any key: ",0
1132 prompt8:.db     "\r\rRun from memory loaction (",0
1133 prompt9:.db     "\r\rInterrupt priority> "
1134         .db     "L=Low, H=High (default): ",0 
1135 prompt10:.db    ")  New Value: ",0
1136 abort:  .db     "  Command Aborted!\r",0
1137
1138
1139 ;-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-;
1140 ;       2k page boundry must exist between these dividers             ;
1141 ;-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-;
1142
1143
1144 oprt:   ajmp   opcd1           ;addr11
1145         ajmp   opcd2           ;A,Rn
1146         ajmp   opcd3           ;A,direct
1147         ajmp   opcd4           ;A,@Ri
1148         ajmp   opcd5           ;A,#data
1149         ajmp   opcd6           ;direct,A
1150         ajmp   opcd7           ;direct,#data
1151         ajmp   opcd8           ;C,bit
1152         ajmp   opcd9           ;C,/bit
1153         ajmp   opcd10          ;A,direct,rel
1154         ajmp   opcd11          ;A,#data,rel
1155         ajmp   opcd12          ;Rn,#data,rel
1156         ajmp   opcd13          ;@Ri,#data,rel
1157         ajmp   opcd14          ;A
1158         ajmp   opcd15          ;C
1159         ajmp   opcd16          ;bit
1160         ajmp   opcd17          ;direct
1161         ajmp   opcd18          ;@Ri
1162         ajmp   opcd19          ;AB
1163         ajmp   opcd20          ;Rn,rel
1164         ajmp   opcd21          ;direct,rel
1165         ajmp   opcd22          ;Rn
1166         ajmp   opcd23          ;DPTR
1167         ajmp   opcd24          ;bit,rel
1168         ajmp   opcd25          ;rel
1169         ajmp   opcd26          ;@A+DPTR
1170         ajmp   opcd27          ;addr16
1171         ajmp   opcd28          ;Rn,A
1172         ajmp   opcd29          ;Rn,direct
1173         ajmp   opcd30          ;Rn,#data
1174         ajmp   opcd31          ;direct,Rn
1175         ajmp   opcd32          ;direct,direct
1176         ajmp   opcd33          ;direct,@Ri
1177         ajmp   opcd34          ;@Ri,A
1178         ajmp   opcd35          ;@Ri,direct
1179         ajmp   opcd36          ;@Ri,#data
1180         ajmp   opcd37          ;bit,C
1181         ajmp   opcd38          ;DPTR,#data16
1182         ajmp   opcd39          ;A,@A+DPTR
1183         ajmp   opcd40          ;A,@A+PC
1184         ajmp   opcd41          ;A,@DPTR
1185         ajmp   opcd42          ;@DPTR,A
1186         ajmp   opcd43          ; <nothing>
1187
1188 p_reg_n:mov     a,#'R'
1189         lcall   cout
1190         mov     a,r3
1191         anl     a,#00000111b
1192         lcall   phex1
1193         ret
1194
1195 p_reg_i:mov     a,#'@'
1196         lcall   cout
1197         mov     a,#'R'
1198         lcall   cout
1199         mov     a,r3
1200         anl     a,#00000001b
1201         lcall   phex1
1202         ret
1203
1204 pdirect:
1205         mov     a,r4
1206         jb      acc.7,pdir1
1207 pdir0:  mov     a,r4
1208         lcall   phex
1209         ret
1210 pdir1:  mov     dptr,#sfrmnu
1211 pdir2:  clr     a
1212         movc    a,@a+dptr
1213         inc     dptr
1214         jz      pdir0
1215         mov     r0,a
1216         clr     c
1217         subb    a,r4
1218         jnz     pdir3
1219         lcall   pstr
1220         ret
1221 pdir3:  clr     a
1222         movc    a,@a+dptr
1223         inc     dptr
1224         jnb     acc.7,pdir3
1225         sjmp    pdir2
1226                 
1227 pbit: 
1228         mov     a,r4
1229         anl     a,#01111000b
1230         rl      a
1231         swap    a
1232         mov     r0,a
1233         mov     a,r4
1234         anl     a,#10000000b
1235         jz      pbit1
1236         mov     dptr,#bitptr        ;it's a Special Function Reg.
1237         mov     a,r0
1238         movc    a,@a+dptr
1239         mov     dptr,#bitmnu
1240         addc    a,dpl
1241         mov     dpl,a
1242         jnc     pbit0
1243         inc     dph
1244 pbit0:  lcall   pstr
1245         sjmp    pbit2
1246 pbit1:  mov     a,r0            ;it's between 20h and 2Fh
1247         add     a,#20h
1248         lcall   phex
1249 pbit2:  mov     a,#'.'
1250         lcall   cout
1251         mov     a,r4
1252         anl     a,#00000111b
1253         lcall   phex1
1254         ret
1255 prel:
1256         mov     a,r4
1257         jb      acc.7,prel4
1258         clr     c
1259         addc    a,r7
1260         mov     r7,a
1261         jnc     prel8
1262         inc     r6
1263         sjmp    prel8
1264 prel4:  cpl     a
1265         inc     a
1266         mov     r4,a
1267         mov     a,r7
1268         clr     c
1269         subb    a,r4
1270         mov     r7,a
1271         jnc     prel8
1272         dec     r6
1273 prel8:  mov     a,r6
1274         lcall   phex
1275         mov     a,r7
1276         lcall   phex    
1277         ret
1278
1279
1280 opcd1:  mov     a,r6        ;addr11             done
1281         anl     a,#11111000b
1282         mov     r0,a
1283         mov     a,r3
1284         swap    a
1285         rr      a
1286         anl     a,#00000111b
1287         orl     a,r0
1288         lcall   phex
1289         mov     a,r4
1290         lcall   phex
1291         ret       
1292 opcd2:                      ;A,Rn               done
1293         acall   pac
1294         acall   p_reg_n
1295         ret
1296 opcd3:                      ;A,direct           done
1297         acall   pac
1298         acall   pdirect
1299         ret
1300 opcd4:                      ;A,@Ri              done
1301         acall   pac
1302         acall   p_reg_i
1303         ret
1304 opcd5:                      ;A,#data            done
1305         acall   pa
1306 pdata:  acall   pcomma
1307         acall   plb
1308         mov     a,r4
1309         lcall   phex
1310         ret
1311 opcd6:                      ;direct,A           done
1312         acall   pdirect
1313         acall   pcomma
1314         acall   pa
1315         ret
1316 opcd7:                      ;direct,#data       done
1317         acall   pdirect
1318         mov     a,r5
1319         mov     r4,a
1320         ajmp    pdata
1321 opcd8:                      ;C,bit              done
1322         acall   prc
1323         acall   pcomma
1324         acall   pbit
1325         ret
1326 opcd9:                      ;C,/bit             done
1327         acall   prc
1328         acall   pcomma
1329         mov     a,#'/'
1330         lcall   cout
1331         acall   pbit
1332         ret
1333 opcd10:                     ;A,direct,rel       done
1334         acall   pac
1335         acall   pdirect
1336 opcd10a:acall   pcomma
1337         mov     a,r5
1338         mov     r4,a
1339         acall   prel
1340         ret
1341 opcd11:                     ;A,#data,rel        done
1342         acall   pa
1343 opcd11a:acall   pcomma
1344         acall   plb
1345         mov     a,r4
1346         lcall   phex
1347         ajmp    opcd10a
1348 opcd12:                     ;Rn,#data,rel       done
1349         acall   p_reg_n
1350         ajmp    opcd11a
1351 opcd13:                     ;@Ri,#data,rel      done
1352         acall   p_reg_i
1353         ajmp    opcd11a
1354 opcd14:                     ;A                  done
1355         acall   pa
1356         ret
1357 opcd15:                     ;C                  done
1358         acall   prc
1359         ret
1360 opcd16:                     ;bit                done
1361         acall   pbit
1362         ret
1363 opcd17:                     ;direct             done
1364         acall   pdirect
1365         ret
1366 opcd18:                     ;@Ri                done
1367         acall   p_reg_i
1368         ret
1369 opcd19:                     ;AB                 done
1370         acall    pa
1371         mov     a,#'B'
1372         lcall   cout
1373         ret
1374 opcd20:                     ;Rn,rel             done
1375         acall   p_reg_n
1376         acall   pcomma
1377         acall   prel
1378         ret
1379 opcd21:                     ;direct,rel         done
1380         acall   pdirect
1381         ajmp    opcd10a
1382 opcd22:                     ;Rn                 done
1383         acall   p_reg_n
1384         ret
1385 opcd23:                     ;DPTR               done
1386         acall   pdptr
1387         ret
1388 opcd24:                     ;bit,rel            done
1389         acall   pbit
1390         ajmp    opcd10a
1391 opcd25:                     ;rel                done
1392         acall   prel
1393         ret
1394 opcd26:                     ;@A+DPTR            done
1395         acall   pat
1396         acall   pa
1397         mov     a,#'+'
1398         lcall   cout
1399         acall   pdptr
1400         ret
1401 opcd28:                     ;Rn,A               done
1402         acall   p_reg_n
1403         acall   pcomma
1404         acall   pa
1405         ret    
1406 opcd29:                     ;Rn,direct          done
1407         acall   p_reg_n
1408         acall   pcomma          
1409         acall   pdirect
1410         ret
1411 opcd30:                     ;Rn,#data           done
1412         acall   p_reg_n
1413         ajmp    pdata
1414 opcd31:                     ;direct,Rn          done
1415         acall   pdirect
1416         acall   pcomma
1417         acall   p_reg_n
1418         ret
1419 opcd32:                     ;direct,direct      done
1420         mov     a,r4
1421         push    acc
1422         mov     a,r5
1423         mov     r4,a
1424         acall   pdirect
1425         acall   pcomma
1426         pop     acc
1427         mov     r4,a
1428         acall   pdirect
1429         ret
1430 opcd33:                     ;direct,@Ri         done
1431         acall   pdirect
1432         acall   pcomma
1433         acall   p_reg_i
1434         ret
1435 opcd34:                     ;@Ri,A              done
1436         acall   p_reg_i
1437         acall   pcomma
1438         acall   pa
1439         ret
1440 opcd35:                     ;@Ri,direct         done
1441         acall   p_reg_i
1442         acall   pcomma
1443         acall   pdirect
1444         ret
1445 opcd36:                     ;@Ri,#data          done
1446         acall   p_reg_i
1447         ajmp    pdata
1448 opcd37:                     ;bit,C              done
1449         acall   pbit
1450         acall   pcomma
1451         acall   prc
1452         ret
1453 opcd38:                     ;DPTR,#data16       done
1454         acall   pdptr
1455         acall   pcomma
1456         acall   plb
1457 opcd27: mov     a,r4           ;addr16          done
1458         lcall   phex
1459         mov     a,r5
1460         lcall   phex
1461         ret
1462 opcd39:                     ;A,@A+DPTR          done
1463         acall   pac
1464         acall   pat
1465         acall   pa
1466         mov     a,#'+'
1467         lcall   cout
1468         acall   pdptr
1469         ret
1470 opcd40:                     ;A,@A+PC            done
1471         acall   pac
1472         acall   pat
1473         acall   pa
1474         mov     a,#'+'
1475         lcall   cout
1476         mov     a,#'P'
1477         lcall   cout
1478         acall   prc
1479         ret
1480 opcd41:                     ;A,@DPTR            done
1481         acall   pac
1482         acall   pat
1483         acall   pdptr
1484         ret
1485 opcd42:                     ;@DPTR,A            done
1486         acall   pat
1487         acall   pdptr
1488         acall   pcomma
1489         acall   pa
1490 opcd43: ret                 ;<nothing>          done
1491
1492 pat:            ;prints the '@' symbol
1493         mov     a,#'@'
1494         lcall   cout
1495         ret
1496 pcomma:         ;prints a comma
1497         mov     a,#','
1498         lcall   cout
1499         lcall   space
1500         ret
1501 plb:            ;prints the '#' symbol
1502         mov     a,#'#'
1503         lcall   cout
1504         ret
1505 pa:             ;prints 'A'
1506         mov     a,#'A'
1507         lcall   cout
1508         ret
1509 prc:             ;prints 'C'
1510         mov     a,#'C'
1511         lcall   cout
1512         ret
1513 pac:            ;print "A,"
1514         acall   pa
1515         acall   pcomma
1516         ret
1517 pdptr:          ;prints DPTR
1518         push    dph
1519         push    dpl
1520         mov     dptr,#sdptr
1521         lcall   pstr
1522         pop     dpl
1523         pop     dph
1524         ret
1525
1526 poweron:
1527         MOV     SP,#30H
1528         clr     psw.3           ;set for register bank 0 (init needs it)
1529         clr     psw.4
1530         LCALL   INIT
1531         setb    ti              ;ti is normally set in this program
1532         clr     ri              ;ri is normallt cleared
1533         mov     r0,#8
1534         lcall   newline
1535         djnz    r0,*
1536         MOV     DPTR,#logon
1537         lCALL   PSTR
1538         mov     dptr,#program
1539         
1540 MENU:
1541         PUSH    DPL
1542         PUSH    DPH
1543         MOV     DPTR,#PROMPT1
1544         lCALL   PSTR
1545         POP     DPH
1546         POP     DPL
1547         lCALL   PHEX16
1548         PUSH    DPL
1549         PUSH    DPH
1550         MOV     DPTR,#PROMPT2
1551         lCALL   PSTR
1552         lCALL   CIN             ;GET THE INPUT CHARACTER
1553         lcall   upper
1554         .equ    char, 0x20
1555         MOV     CHAR,A
1556         MOV     DPTR,#CMD_TBL   ;BEGIN SEARCH THRU THE TABLE
1557 MENU1:  CLR     A 
1558         MOVC    A,@A+DPTR
1559         JZ      MENU3           ;JUMP IF END OF TABLE REACHED
1560         CJNE    A,CHAR,MENU2    ;JUMP IF THIS IS NOT THE COMMAND TYPED
1561         INC     DPTR            ;OK, SO THIS IS THE RIGHT ONE...
1562         CLR     A
1563         MOVC    A,@A+DPTR
1564         PUSH    Acc
1565         INC     DPTR
1566         CLR     A
1567         MOVC    A,@A+DPTR
1568         pop     b
1569         push    dpl
1570         push    dph
1571         MOV     DPL,A
1572         mov     DPH,b
1573         lCALL   PSTR            ;PRINT THE COMMAND NAME
1574         lCALL   NEWLINE
1575         pop     dph
1576         pop     dpl
1577         INC     DPTR
1578         CLR     A
1579         MOVC    A,@A+DPTR
1580         MOV     22h,A
1581         CLR     A
1582         INC     DPTR
1583         MOVC    A,@A+DPTR
1584         mov     21h,a
1585         POP     23h
1586         POP     24h
1587         mov     dptr,#menu
1588         push    dpl
1589         push    dph
1590         mov     dpl,24h
1591         mov     dph,23h
1592         PUSH    21h
1593         PUSH    22h
1594         RET                     ;SIMULATED CALL TO THE ROUTINE
1595         lJMP    MENU
1596 MENU2:  INC     DPTR            ;SKIP THIS TABLE ENTRY  
1597         INC     DPTR
1598         INC     DPTR
1599         INC     DPTR
1600         INC     DPTR
1601         lJMP    MENU1
1602 MENU3:  POP     DPH             ;NOW WE TELL 'EM THEY TYPED 
1603         POP     DPL             ;AN ILLEGAL CHARACTER
1604         lCALL   NEWLINE
1605         lJMP    MENU
1606
1607
1608   ;this prints the instructions for status and skip in single-step
1609 inst:   mov     a,r1            ;r0 must point to pc
1610         push    acc
1611         mov     a,r2
1612         push    acc
1613         mov     a,r3
1614         push    acc
1615         mov     a,r4
1616         push    acc
1617         mov     a,r5
1618         push    acc
1619         mov     a,r6
1620         push    acc
1621         mov     a,r7
1622         push    acc
1623         mov     dph,@r0         ;put pc into dptr for disasm
1624         dec     r0
1625         mov     dpl,@r0
1626         lcall   disasm
1627         pop     acc
1628         mov     r7,a
1629         pop     acc
1630         mov     r6,a
1631         pop     acc
1632         mov     r5,a
1633         pop     acc
1634         mov     r4,a
1635         pop     acc
1636         mov     r3,a
1637         pop     acc
1638         mov     r2,a
1639         pop     acc
1640         mov     r1,a
1641         ret
1642         
1643
1644
1645
1646 ;---------------------------------------------------------;
1647 ;                                                         ;
1648 ;      Here begins the data tables and strings:           ;
1649 ;                                                         ;
1650 ;---------------------------------------------------------;
1651                                                          
1652 logon:  .db     "\r   \r        "
1653         .db  12,"Welcome to the new and possibly even "
1654         .db     "improved 8031 monitor/debugger\r"
1655         .db     "by Paul Stoffregen on 14-OCT-91 "
1656         .db     "for no good reason whatsoever...\r\r"
1657     ;columbs     1234567890123456789012345678901234567890
1658         .db     "These are some of the features offered "
1659         .db     "by this particular debugger:\r\r"
1660         .db     "     Download programs from PC          "
1661         .db     "User-Friendliness!!!!!\r"
1662         .db     "     Run Program                        "
1663         .db     "Uses no external RAM\r"
1664         .db     "       (Normal, or single-step)         "
1665         .db     "<ESC> key is supported\r"
1666         .db     "     List assemble code from memory     "
1667         .db     "automatic baud rate detection\r"
1668         .db     "     Hex Dump and Edit external RAM     "
1669         .db     "On-line help (type '?')\r"
1670         .db     "\rHowever, you don't get somethin' for "
1671         .db     "nothin'...  The code for this debugger\r"
1672         .db     "requires quite a bit more room than is "
1673         .db     "typical for a debugger, but it will all\r"
1674         .db     "fit into a 2764 (8K x 8) EPROM.\r"
1675         .db     "\rNO Copyright!!  Please distribute freely.  "
1676         .db     "Make as many copies as you want.\r\r\r",0
1677                 
1678 mnu_tbl:.db     "ACAL",'L'+128         ;comma is ok
1679         .db     "AD",'D'+128,' '
1680         .db     "ADD",'C'+128
1681         .db     "AJM",'P'+128
1682         .db     "AN",'L'+128
1683         .DB     "CJN",'E'+128
1684         .DB     "CL",'R'+128
1685         .DB     "CP",'L'+128
1686         .DB     "D",'A'+128 
1687         .DB     "DE",'C'+128
1688         .DB     "DI",'V'+128
1689         .DB     "DJN",'Z'+128
1690         .DB     "IN",'C'+128
1691         .DB     "J",'B'+128
1692         .DB     "JB",'C'+128
1693         .DB     "J",'C'+128
1694         .DB     "JM",'P'+128
1695         .DB     "JN",'B'+128
1696         .DB     "JN",'C'+128
1697         .DB     "JN",'Z'+128
1698         .DB     "J",'Z'+128
1699         .DB     "LCAL",'L'+128
1700         .DB     "LJM",'P'+128
1701         .DB     "MO",'V'+128
1702         .DB     "MOV",'C'+128
1703         .DB     "MOV",'X'+128
1704         .DB     "MU",'L'+128
1705         .DB     "NO",'P'+128
1706         .DB     "OR",'L'+128
1707         .DB     "PO",'P'+128
1708         .DB     "PUS",'H'+128
1709         .DB     "RE",'T'+128
1710         .DB     "RET",'I'+128
1711         .DB     "R",'L'+128
1712         .DB     "RL",'C'+128
1713         .DB     "R",'R'+128
1714         .DB     "RR",'C'+128
1715         .DB     "SET",'B'+128
1716         .DB     "SJM",'P'+128
1717         .DB     "SUB",'B'+128
1718         .DB     "SWA",'P'+128
1719         .DB     "XC",'H'+128
1720         .DB     "XCH",'D'+128
1721         .DB     "XR",'L'+128
1722         .DB     "??",'?'+128,0
1723
1724 bitmnu: .db     'P','0'+128
1725         .db     "TCO",'N'+128
1726         .db     'P','1'+128
1727         .db     "SCO",'N'+128
1728         .DB     'P','2'+128
1729         .DB     'I','E'+128
1730         .DB     'P','3'+128
1731         .DB     'I','P'+128
1732         .DB     'C','0'+128
1733         .DB     "T2CO",'N'+128
1734         .DB     "PS",'W'+128
1735         .DB     'D','8'+128
1736         .DB     "AC",'C'+128
1737         .DB     'E'+'8'+128
1738         .DB     'B'+128
1739         .DB     'F'+'8'+128
1740         .DB     0
1741
1742 sfrmnu: .db     0xE0,"AC",'C'+128
1743         .db     0x81,'S','P'+128
1744         .DB     0x82,"DP",'L'+128
1745         .DB     0x83,"DP",'H'+128
1746         .DB     0x80,'P','0'+128
1747         .DB     0x90,'P','1'+128
1748         .DB     0xA0,'P','2'+128
1749         .DB     0xB0,'P','3'+128
1750         .DB     0x99,"SBU",'F'+128
1751         .DB     0xCD,"TH",'2'+128
1752         .DB     0xC8,"T2CO",'N'+128
1753         .DB     0xCC,"TL",'2'+128
1754         .DB     0xCB,"RCAP2",'H'+128
1755         .DB     0xCA,"RCAP2",'L'+128
1756         .DB     0x8C,"TH",'0'+128
1757         .DB     0x8A,"TL",'0'+128
1758         .DB     0x8D,"TH",'1'+128
1759         .DB     0x8B,"TL",'1'+128
1760 sfr1:   .db     0xF0,'B'+128               ;5
1761 sfr2:   .db     0xD0,"PS",'W'+128          ;7
1762 sfr3:   .DB     0xA8,'I','E'+128
1763 sfr4:   .DB     0xB8,'I','P'+128
1764 sfr5:   .DB     0x89,"TMO",'D'+128         ;8
1765 sfr6:   .DB     0x88,"TCO",'N'+128         ;8
1766 sfr7:   .DB     0x98,"SCO",'N'+128         ;8
1767 sfr8:   .DB     0x87,"PCO",'N'+128         ;8
1768         .DB     0
1769
1770
1771 mnot:        ;mnunonic offset table (gives offset into above table)
1772
1773         .db     5Ah,0Eh,48h,73h,2Bh,2Bh,2Bh,2Bh
1774         .DB     2Bh,2Bh,2Bh,2Bh,2Bh,2Bh,2Bh,2Bh ;INC
1775         .DB     30h,00h,43h,75h,21h,21h,21h,21h
1776         .DB     21h,21h,21h,21h,21h,21h,21h,21h ;DEC
1777         .DB     2Eh,0Eh,67h,6Eh,06h,06h,06h,06h
1778         .DB     06h,06h,06h,06h,06h,06h,06h,06h ;ADD
1779         .DB     38h,00h,6Ah,70h,0Ah,0Ah,0Ah,0Ah
1780         .DB     0Ah,0Ah,0Ah,0Ah,0Ah,0Ah,0Ah,0Ah ;ADDC
1781         .DB     33h,0Eh,5Dh,5Dh,5Dh,5Dh,5Dh,5Dh
1782         .DB     5Dh,5Dh,5Dh,5Dh,5Dh,5Dh,5Dh,5Dh ;ORL
1783         .DB     3Bh,00h,12h,12h,12h,12h,12h,12h
1784         .DB     12h,12h,12h,12h,12h,12h,12h,12h ;ANL
1785         .DB     41h,0Eh,8Fh,8Fh,8Fh,8Fh,8Fh,8Fh
1786         .DB     8Fh,8Fh,8Fh,8Fh,8Fh,8Fh,8Fh,8Fh ;XLR
1787         .DB     3Eh,00h,5Dh,35h,4Ch,4Ch,4Ch,4Ch
1788         .DB     4Ch,4Ch,4Ch,4Ch,4Ch,4Ch,4Ch,4Ch ;MOV
1789         .DB     7Ch,0Eh,12h,4Fh,24h,4Ch,4Ch,4Ch
1790         .DB     4Ch,4Ch,4Ch,4Ch,4Ch,4Ch,4Ch,4Ch ;MOV
1791         .DB     4Ch,00h,4Ch,4Fh,80h,80h,80h,80h
1792         .DB     80h,80h,80h,80h,80h,80h,80h,80h ;SUBB
1793         .DB     5Dh,0Eh,4Ch,2Bh,57h,92h,4Ch,4Ch
1794         .DB     4Ch,4Ch,4Ch,4Ch,4Ch,4Ch,4Ch,4Ch ;MOV
1795         .DB     12h,00h,1Ch,1Ch,15h,15h,15h,15h
1796         .DB     15h,15h,15h,15h,15h,15h,15h,15h ;CJNE
1797         .DB     63h,0Eh,19h,19h,84h,88h,88h,88h
1798         .DB     88h,88h,88h,88h,88h,88h,88h,88h ;XCH
1799         .DB     60h,00h,78h,78h,1Fh,27h,8Bh,8Bh
1800         .DB     27h,27h,27h,27h,27h,27h,27h,27h ;DJNZ
1801         .DB     53h,0Eh,53h,53h,19h,4Ch,4Ch,4Ch
1802         .DB     4Ch,4Ch,4Ch,4Ch,4Ch,4Ch,4Ch,4Ch ;MOV
1803         .DB     53h,00h,53h,53h,1Ch,4Ch,4Ch,4Ch
1804         .DB     4Ch,4Ch,4Ch,4Ch,4Ch,4Ch,4Ch,4Ch ;MOV
1805
1806 bitptr: .db     00h,02h,06h,08h,0Ch,0Eh,10h,12h
1807         .db     14h,16h,1Bh,1Eh,20h,23h,24h,25h
1808                                               
1809 opot:        ;opcode offset table (gives #bytes for the instruction
1810              ;and the number of the routine to print the operands)
1811
1812         .db     43*4+1,1*4+2,27*4+3,14*4+1        ;00
1813         .db     14*4+1,17*4+2,18*4+1,18*4+1
1814         .db     89,89,89,89,89,89,89,89         ;inc
1815         .db     24*4+3,1*4+2,27*4+3,14*4+1        ;10
1816         .db     14*4+1,17*4+2,18*4+1,18*4+1
1817         .db     89,89,89,89,89,89,89,89         ;dec
1818         .db     24*4+3,1*4+2,43*4+1,14*4+1        ;20
1819         .db     5*4+2,3*4+2,4*4+1,4*4+1
1820         .db     9,9,9,9,9,9,9,9                 ;add
1821         .db     24*4+3,1*4+2,43*4+1,14*4+1        ;30
1822         .db     5*4+2,3*4+2,4*4+1,4*4+1
1823         .db     9,9,9,9,9,9,9,9                 ;addc
1824         .db     25*4+2,1*4+2,6*4+2,7*4+3        ;40
1825         .db     5*4+2,3*4+2,4*4+1,4*4+1
1826         .db     9,9,9,9,9,9,9,9                 ;orl
1827         .db     25*4+2,1*4+2,6*4+2,7*4+3        ;50
1828         .db     5*4+2,3*4+2,4*4+1,4*4+1
1829         .db     9,9,9,9,9,9,9,9                 ;anl
1830         .db     25*4+2,1*4+2,6*4+2,7*4+3        ;60
1831         .db     5*4+2,3*4+2,4*4+1,4*4+1
1832         .db     9,9,9,9,9,9,9,9                 ;xrl
1833         .db     25*4+2,1*4+2,8*4+2,26*4+1        ;70
1834         .db     5*4+2,7*4+3,36*4+2,33*4+2
1835         .db     122,122,122,122,122,122,122,122 ;mov
1836         .db     25*4+2,1*4+2,34,40*4+1        ;80
1837         .db     19*4+1,32*4+3,33*4+2,33*4+2
1838         .db     126,126,126,126,126,126,126,126 ;mov
1839         .db     38*4+3,1*4+2,37*4+2,39*4+1        ;90
1840         .db     5*4+2,3*4+2,4*4+1,4*4+1
1841         .db     9,9,9,9,9,9,9,9                 ;subb
1842         .db     9*4+2,1*4+2,8*4+2,23*4+1        ;A0
1843         .db     19*4+1,43*4+1,35*4+2,35*4+2
1844         .db     118,118,118,118,118,118,118,118 ;mov
1845         .db     9*4+2,1*4+2,16*4+2,15*4+1        ;B0
1846         .db     11*4+3,10*4+3,13*4+3,13*4+3
1847         .db     51,51,51,51,51,51,51,51      ;cjne
1848         .db     17*4+2,1*4+2,16*4+2,15*4+1        ;C0
1849         .db     14*4+1,3*4+2,4*4+1,4*4+1
1850         .db     9,9,9,9,9,9,9,9                 ;xch
1851         .db     17*4+2,1*4+2,16*4+2,15*4+1        ;D0
1852         .db     14*4+1,21*4+3,4*4+1,4*4+1
1853         .db     82,82,82,82,82,82,82,82         ;djnz
1854         .db     41*4+1,1*4+2,4*4+1,4*4+1        ;E0
1855         .db     14*4+1,3*4+2,4*4+1,4*4+1
1856         .db     9,9,9,9,9,9,9,9                 ;mov
1857         .db     42*4+1,1*4+2,34*4+1,34*4+1        ;F0
1858         .db     14*4+1,6*4+2,34*4+1,34*4+1
1859         .db     113,113,113,113,113,113,113,113 ;mov
1860
1861 edits1: .db     "\rEditing External RAM...<ESC> to quit\r",0
1862 edits2: .db     "  Editing finished, this location unchanged\r\r",0
1863 dwlds1: .db     "\r\rBegin ascii transmission of "
1864         .db     "Intel HEX format file, "
1865         .db     "or <ESC> to abort\r\r",0
1866 dwlds2: .db     "Download aborted by user\r\r",0
1867 dwlds3: .db     "\r\r\r\rDownload completed\r\r",0
1868 runstd: .db     "Run normally",0
1869 runs1:  .db     "\rNow running the program...\r\r",0
1870 runss:  .db     "Run in single step mode",0
1871 sserr1: .db     "\r\rThe single step run feature will not function"
1872         .db     " unless INT1 (pin #13) is\r"
1873         .db     "connected to ground or otherwise held low.\r\r",0
1874 ssmsg:  .db     "\rNow running in single step mode:  "
1875         .db     "<RET>=default, ?=Help\r\r",0
1876 sskip1: .db     "Skipping ------>",0
1877 sskip2: .db     "Next will be -->",0
1878 ssdmps1:.db     "\rLoc:  Internal Ram Memory Contents\r",0
1879 chaccs1:.db     "New Acc Value: ",0
1880 squit:  .db     "\rQuit single step mode, now running normally.\r\r",0
1881 sdptr:  .db     "DPTR",0
1882 CMD_TBL:.DB     '?'
1883         .DW     CMD_hlp
1884         .DW     HELP
1885         .db     'R'
1886         .dw     CMD_run
1887         .dw     run
1888         .db     'D'                                      
1889         .dw     CMD_dwl
1890         .dw     download
1891         .db     'N'
1892         .dw     CMD_new
1893         .dw     new_loc
1894         .db     'H'
1895         .dw     CMD_dmp
1896         .dw     dump
1897         .db     'L'
1898         .dw     CMD_lst
1899         .dw     list
1900         .db     'E'
1901         .dw     CMD_edt
1902         .dw     edit
1903         .DB     00h
1904 CMD_run:.db     " Run program",0
1905 CMD_new:.db     " New memory location",0
1906 CMD_dmp:.db     " HEX Dump Memory to the Screen",0
1907 CMD_lst:.db     " List assembly code",0
1908 CMD_hlp:.DB     " Help???",0
1909 CMD_dwl:.Db     " Download program from PC",0
1910 CMD_edt:.db     " Edit external ram",0
1911 Help1txt:
1912         .db     12,"These commands are currently "
1913         .db     "supported:\r\r",0
1914 help2txt:
1915         ;        1234567890123456789012345678901234567890
1916         .db     "\rAll numerical values are shown in hex.  "
1917            
1918         .db     "Pressing <ESC> key will exit the\r"
1919         .db     "current command, even while listing/dumping.  "
1920         .db     "Most prompts require a\r"
1921         .db     "single character, typically the first letter "
1922         .db     "of the desired option.\r\rFor information "
1923         .db     "regarding the single-step run feature,\r"
1924         .db     "type '?' when asked 'Single-step/Normal' "
1925         .db     "before running the program.\r\r",0
1926 Help3txt:
1927         ;        1234567890123456789012345678901234567890
1928         .db  12,"The single step run feature allows you "
1929         .db     "to execute your program from memory\r"          ;1
1930         .db     "one instruction at a time, while monitoring "
1931         .db     "the registers and instructions.\r"              ;2
1932         .db     "It it NOT a simulation, the program is "
1933         .db     "executed by the 8031/51 processor.\r"           ;3
1934         .db     "External Interrupt #1 must be held low "
1935         .db     "to make the single step function.\r"            ;4
1936         .db     "\r"                                             ;5
1937         .db     "Despite attempts to make the single "
1938         .db     "step run compatible with all programs,\r"       ;6
1939         .db     "there will always be some basic limitations "
1940         .db     "due to its nature:\r\r"                         ;7 8
1941         .db     " 1- External Interrupt #1 must not be"
1942         .db     " disabled, e.g. MOV IE,#81h\r"                  ;9
1943         .db     " 2- Timer #1 must be correctly generating "
1944         .db     " the baud rate for the serial port\r"           ;10
1945         .db     " 3- TI and RI will not work normally, "
1946         .db     "e.g. 2003: JNB RI,2003, use skip...\r"          ;11
1947         .db     " 4- Interrupts will not get service " 
1948         .db     "or will interrupt the single step\r"            ;12
1949         .db     " 5- About 30 bytes of space must be "
1950         .db     "left available on the stack!\r"                 ;13
1951         .db     " 6- ???  Other problems may also "
1952         .db     "exist, (this program is FREE, you know)\r"      ;14
1953         ;        1234567890123456789012345678901234567890
1954         .db     "\r"                                             ;15
1955         .db     "Perhaps the worst limitation of the "
1956         .db     "single step run is that it takes a\r"           ;16
1957         .db     "very long time to execute even short "
1958         .db     "pieces of code.  It is recommended that\r"      ;17
1959         .db     "a normal run be attempted first to "
1960         .db     "estimate where the program goes astray,\r"      ;18
1961         .db     "the attempt a single step at the beginning "
1962         .db     "of the questionable code, with a\r"             ;19
1963         .db     "hardcopy of the assembly listing file "
1964         .db     "on-hand for memory location reference.\r\r",0   ;20 21
1965
1966
1967         ;        1234567890123456789012345678901234567890 
1968 Help4txt:
1969         .db  12,"Between steps, the monitor uses absolutely "
1970         .db     "NO internal or external memory.\r"
1971         .db     "However, about 30 bytes of stack space "
1972         .db     "must be left available...\r\r"
1973         .db     "During a single step run, pressing RETURN "
1974         .db     "repeatedly will be the usual course\r"
1975         .db     "of action.  However, other options are "
1976         .db     "available.\r\r"
1977         .db     "            "
1978         .db     "Typing '?' will display this help screen\r\r",0
1979
1980 Help5txt:
1981         .db     "Single Step Commands:\r\r"
1982         .db     " <RET>    Print Status and execute "
1983         .db                   "the next instruction\r"
1984         .db     " <SPACE>  Execute next instruction w/out status lines\r"
1985         .db     "  '?'     Display this on-line help\r"
1986         .db     "  'R'     Print out Special Function Registers\r"
1987         .db     "  'H'     Hex dump internal ram\r"
1988         .db     "  'S'     Skip this instruction\r"
1989         .db     "  'A'     Change the Accumulator's value\r"
1990         .db     "  'Q'     Quit Single Step, continue executing normally\r"
1991         .db     "\r",0
1992