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