]> git.sur5r.net Git - cc65/blob - libsrc/cbm510/crt0.s
Use external symbols for the CBM kernal jump table functions. This allows
[cc65] / libsrc / cbm510 / crt0.s
1 ;
2 ; Startup code for cc65 (CBM 500 version)
3 ;
4 ; This must be the *first* file on the linker command line
5 ;
6
7         .export         _exit
8         .exportzp       vic, sid, cia1, cia2, acia, tpi1, tpi2, ktab1
9         .exportzp       ktab2, ktab3, ktab4, time, RecvBuf, SendBuf
10
11         .import         _clrscr, initlib, donelib
12         .import         push0, _main
13         .import         __CHARRAM_START__, __CHARRAM_SIZE__, __VIDRAM_START__
14         .import         __BSS_RUN__, __BSS_SIZE__
15         .import         irq, nmi
16         .import         k_irq, k_nmi, PLOT, UDTIM, SCNKEY
17
18         .include        "zeropage.inc"
19         .include        "cbm510.inc"
20
21
22 ; ------------------------------------------------------------------------
23 ; BASIC header and a small BASIC program. Since it is not possible to start
24 ; programs in other banks using SYS, the BASIC program will write a small
25 ; machine code program into memory at $100 and start that machine code
26 ; program. The machine code program will then start the machine language
27 ; code in bank 0, which will initialize the system by copying stuff from
28 ; the system bank, and start the application.
29 ;
30 ; Here's the basic program that's in the following lines:
31 ;
32 ; 10 for i=0 to 4
33 ; 20 read j
34 ; 30 poke 256+i,j
35 ; 40 next i
36 ; 50 sys 256
37 ; 60 data 120,169,0,133,0
38 ;
39 ; The machine program in the data lines is:
40 ;
41 ; sei
42 ; lda     #$00
43 ; sta     $00           <-- Switch to bank 0 after this command
44 ;
45 ; Initialization is not only complex because of the jumping from one bank
46 ; into another. but also because we want to save memory, and because of
47 ; this, we will use the system memory ($00-$3FF) for initialization stuff
48 ; that is overwritten later.
49 ;
50
51 .code
52
53 ; To make things more simple, make the code of this module absolute.
54
55         .org    $0001
56 Head:   .byte   $03,$00,$11,$00,$0a,$00,$81,$20,$49,$b2,$30,$20,$a4,$20,$34,$00
57         .byte   $19,$00,$14,$00,$87,$20,$4a,$00,$27,$00,$1e,$00,$97,$20,$32,$35
58         .byte   $36,$aa,$49,$2c,$4a,$00,$2f,$00,$28,$00,$82,$20,$49,$00,$39,$00
59         .byte   $32,$00,$9e,$20,$32,$35,$36,$00,$4f,$00,$3c,$00,$83,$20,$31,$32
60         .byte   $30,$2c,$31,$36,$39,$2c,$30,$2c,$31,$33,$33,$2c,$30,$00,$00,$00
61
62 ; Since we need some vectors to access stuff in the system bank for our own,
63 ; we will include them here, starting from $60:
64
65         .res    $60-*
66
67 vic:            .word   $d800
68 sid:            .word   $da00
69 cia1:           .word   $db00
70 cia2:           .word   $dc00
71 acia:           .word   $dd00
72 tpi1:           .word   $de00
73 tpi2:           .word   $df00
74 ktab1:          .word   $eab1
75 ktab2:          .word   $eb11
76 ktab3:          .word   $eb71
77 ktab4:          .word   $ebd1
78 time:           .dword  $0000
79 RecvBuf:        .word   $0100           ; RS232 received buffer
80 SendBuf:        .word   $0200           ; RS232 send buffer
81
82
83 ; The code in the target bank when switching back will be put at the bottom
84 ; of the stack. We will jump here to switch segments. The range $F2..$FF is
85 ; not used by any kernal routine.
86
87         .res    $F8-*
88 Back:   ldx     spsave
89         txs
90         lda     IndReg
91         sta     ExecReg
92
93 ; The following code is a copy of the code that is poked in the system bank
94 ; memory by the basic header program, it's only for documentation and not
95 ; actually used here:
96
97         sei
98         lda     #$00
99         sta     ExecReg
100
101 ; This is the actual starting point of our code after switching banks for
102 ; startup. Beware: The following code will get overwritten as soon as we
103 ; use the stack (since it's in page 1)!
104
105         tsx
106         stx     spsave          ; Save the system stackpointer
107         ldx     #$FF
108         txs                     ; Set up our own stack
109
110 ; Set the interrupt, NMI and other vectors
111
112         ldy     #vectable_size
113 L0:     lda     vectable-1,y
114         sta     $FF80,y
115         dey
116         bne     L0
117
118 ; Switch the indirect segment to the system bank
119
120         lda     #$0F
121         sta     IndReg
122
123 ; Copy the kernal zero page ($90-$F2) from the system bank
124
125         lda     #$90
126         sta     ptr1
127         lda     #$00
128         sta     ptr1+1
129         ldy     #$62-1
130 L1:     lda     (ptr1),y
131         sta     $90,y
132         dey
133         bpl     L1
134
135 ; Copy the page 3 vectors in place
136
137         ldy     #$00
138 L2:     lda     p3vectable,y
139         sta     $300,y
140         iny
141         cpy     #p3vectable_size
142         bne     L2
143
144 ; Copy the rest of page 3 from the system bank
145
146         lda     #$00
147         sta     ptr1
148         lda     #$03
149         sta     ptr1+1
150 L3:     lda     (ptr1),y
151         sta     $300,y
152         iny
153         bne     L3
154
155 ; Set the indirect segment to bank we're executing in
156
157         lda     ExecReg
158         sta     IndReg
159
160 ; Zero the BSS segment. We will do that here instead calling the routine
161 ; in the common library, since we have the memory anyway, and this way,
162 ; it's reused later.
163
164         lda     #<__BSS_RUN__
165         sta     ptr1
166         lda     #>__BSS_RUN__
167         sta     ptr1+1
168         lda     #0
169         tay
170
171 ; Clear full pages
172
173         ldx     #>__BSS_SIZE__
174         beq     Z2
175 Z1:     sta     (ptr1),y
176         iny
177         bne     Z1
178         inc     ptr1+1                  ; Next page
179         dex
180         bne     Z1
181
182 ; Clear the remaining page
183
184 Z2:     ldx     #<__BSS_SIZE__
185         beq     Z4
186 Z3:     sta     (ptr1),y
187         iny
188         dex
189         bne     Z3
190 Z4:
191
192 ; Setup the C stack
193
194         lda     #<$FF81
195         sta     sp
196         lda     #>$FF81
197         sta     sp+1
198
199 ; We expect to be in page 2 now
200
201 .if     (* < $1FD)
202         jmp     $200
203         .res    $200-*
204 .endif
205 .if     (* < $200)
206         .res    $200-*,$EA
207 .endif
208 .if     (* >= $2F0)
209 .error  "Code range invalid"
210 .endif
211
212 ; This code is in page 2, so we may now start calling subroutines safely,
213 ; since the code we execute is no longer in the stack page.
214
215 ; Copy the character rom from the system bank into the execution bank
216
217         lda     #<$C000
218         sta     ptr1
219         lda     #>$C000
220         sta     ptr1+1
221         lda     #<__CHARRAM_START__
222         sta     ptr2
223         lda     #>__CHARRAM_START__
224         sta     ptr2+1
225         lda     #>__CHARRAM_SIZE__      ; 16 * 256 bytes to copy
226         sta     tmp1
227         ldy     #$00
228 ccopy:  lda     #$0F
229         sta     IndReg                  ; Access the system bank
230 ccopy1: lda     (ptr1),y
231         sta     __VIDRAM_START__,y
232         iny
233         bne     ccopy1
234         lda     ExecReg
235         sta     IndReg
236 ccopy2: lda     __VIDRAM_START__,y
237         sta     (ptr2),y
238         iny
239         bne     ccopy2
240         inc     ptr1+1
241         inc     ptr2+1                  ; Bump high pointer bytes
242         dec     tmp1
243         bne     ccopy
244
245 ; Clear the video memory. We will do this before switching the video to bank 0
246 ; to avoid garbage when doing so.
247
248         jsr     _clrscr
249
250 ; Reprogram the VIC so that the text screen and the character ROM is in the
251 ; execution bank. This is done in three steps:
252
253         lda     #$0F                    ; We need access to the system bank
254         sta     IndReg
255
256 ; Place the VIC video RAM into bank 0
257 ; CA (STATVID)   = 0
258 ; CB (VICDOTSEL) = 0
259
260         ldy     #tpiCtrlReg
261         lda     (tpi1),y
262         sta     vidsave+0
263         and     #%00001111
264         ora     #%10100000
265         sta     (tpi1),y
266
267 ; Set bit 14/15 of the VIC address range to the high bits of __VIDRAM_START__
268 ; PC6/PC7 (VICBANKSEL 0/1) = 11
269
270         ldy     #tpiPortC
271         lda     (tpi2),y
272         sta     vidsave+1
273         and     #$3F
274         ora     #<((>__VIDRAM_START__) & $C0)
275         sta     (tpi2),y
276
277 ; Set the VIC base address register to the addresses of the video and
278 ; character RAM.
279
280         ldy     #VIC_VIDEO_ADR
281         lda     (vic),y
282         sta     vidsave+2
283         and     #$01
284         ora     #<(((__VIDRAM_START__ >> 6) & $F0) | ((__CHARRAM_START__ >> 10) & $0E) | $02)
285 ;       and     #$0F
286 ;       ora     #<(((>__VIDRAM_START__) << 2) & $F0)
287         sta     (vic),y
288
289 ; Switch back to the execution bank
290
291         lda     ExecReg
292         sta     IndReg
293
294 ; Call module constructors
295
296         jsr     initlib
297
298 ; Create the (empty) command line for the program
299
300         jsr     push0           ; argc
301         jsr     push0           ; argv
302
303 ; Execute the program code
304
305         jmp     Start
306
307 ; ------------------------------------------------------------------------
308 ; Additional data that we need for initialization and that's overwritten
309 ; later
310
311 vectable:
312         jmp     $0000           ; CINT
313         jmp     $0000           ; IOINIT
314         jmp     $0000           ; RAMTAS
315         jmp     $0000           ; RESTOR
316         jmp     $0000           ; VECTOR
317         jmp     $0000           ; SETMSG
318         jmp     $0000           ; SECOND
319         jmp     $0000           ; TKSA
320         jmp     $0000           ; MEMTOP
321         jmp     $0000           ; MEMBOT
322         jmp     SCNKEY
323         jmp     $0000           ; SETTMO
324         jmp     $0000           ; ACPTR
325         jmp     $0000           ; CIOUT
326         jmp     $0000           ; UNTLK
327         jmp     $0000           ; UNLSN
328         jmp     $0000           ; LISTEN
329         jmp     $0000           ; TALK
330         jmp     $0000           ; READST
331         jmp     SETLFS
332         jmp     SETNAM
333         jmp     $0000           ; OPEN
334         jmp     $0000           ; CLOSE
335         jmp     $0000           ; CHKIN
336         jmp     $0000           ; CKOUT
337         jmp     $0000           ; CLRCH
338         jmp     $0000           ; BASIN
339         jmp     $0000           ; BSOUT
340         jmp     $0000           ; LOAD
341         jmp     $0000           ; SAVE
342         jmp     SETTIM
343         jmp     RDTIM
344         jmp     $0000           ; STOP
345         jmp     $0000           ; GETIN
346         jmp     $0000           ; CLALL
347         jmp     UDTIM
348         jmp     SCREEN
349         jmp     PLOT
350         jmp     IOBASE
351         sta     ExecReg
352         rts
353         .byte   $01             ; Filler
354         .word   nmi
355         .word   0               ; Reset - not used
356         .word   irq
357 vectable_size   = * - vectable
358
359 p3vectable:
360         .word   k_irq           ; IRQ user vector
361         .word   k_brk           ; BRK user vector
362         .word   k_nmi           ; NMI user vector
363 p3vectable_size = * - p3vectable
364
365
366 ; ------------------------------------------------------------------------
367 ; This is the program code after setup. It starts at $400
368
369         .res    $400-*
370
371 Start:
372
373 ; Enable interrupts
374
375         cli
376
377 ; Call the user code
378
379         ldy     #4              ; Argument size
380         jsr     _main           ; call the users code
381
382 ; Call module destructors. This is also the _exit entry.
383
384 _exit:  jsr     donelib         ; Run module destructors
385
386 ; We need access to the system bank now
387
388         lda     #$0F
389         sta     IndReg
390
391 ; Switch back the video to the system bank
392
393         ldy     #tpiCtrlReg
394         lda     vidsave+0
395         sta     (tpi1),y
396
397         ldy     #tpiPortC
398         lda     vidsave+1
399         sta     (tpi2),y
400
401         ldy     #VIC_VIDEO_ADR
402         lda     vidsave+2
403         sta     (vic),y
404
405 ; Clear the start of the zero page, since it will be interpreted as a
406 ; (garbage) BASIC program otherwise. This is also the default entry for
407 ; the break vector.
408
409 k_brk:  sei
410         lda     #$00
411         ldx     #$3E
412 Clear:  sta     $02,x
413         dex
414         bne     Clear
415
416 ; Setup the welcome code at the stack bottom in the system bank. Use
417 ; the F4/F5 vector to access the system bank
418
419         ldy     #$00
420         sty     $F4
421         iny
422         sty     $F5
423         ldy     #reset_size-1
424 @L1:    lda     reset,y
425         sta     ($F4),y
426         dey
427         bne     @L1
428         jmp     Back
429
430 ; ------------------------------------------------------------------------
431 ; Code that is copied into the system bank at $100 when switching back
432
433 reset:  cli
434         jmp     $8000                   ; BASIC cold start
435 reset_size = * - reset
436
437 ; ------------------------------------------------------------------------
438 ; Code for a few simpler kernal calls goes here
439
440 .export IOBASE
441 .proc   IOBASE
442          ldx    cia2
443         ldy     cia2+1
444         rts
445 .endproc
446
447 .export SCREEN
448 .proc   SCREEN
449         ldx     #40             ; Columns
450         ldy     #25             ; Lines
451         rts
452 .endproc
453
454 .export SETLFS
455 .proc   SETLFS
456         sta     LogicalAdr
457         stx     FirstAdr
458         sty     SecondAdr
459         rts
460 .endproc
461
462 .export SETNAM
463 .proc   SETNAM
464         sta     FileNameLen
465         lda     $00,x
466         sta     FileNameAdrLo
467         lda     $01,x
468         sta     FileNameAdrHi
469         lda     $02,x
470         sta     FileNameAdrSeg
471         rts
472 .endproc
473
474 .export RDTIM
475 .proc   RDTIM
476         sei
477         lda     time+0
478         ldx     time+1
479         ldy     time+2
480         cli
481         rts
482 .endproc
483
484 .export SETTIM
485 .proc   SETTIM
486         sei
487         sta     time+0
488         stx     time+1
489         sty     time+2
490         cli
491         rts
492 .endproc
493
494 ; -------------------------------------------------------------------------
495 ; Data area - switch back to relocatable mode
496
497         .reloc
498
499 .data
500 spsave: .res    1
501 vidsave:.res    3
502
503