]> git.sur5r.net Git - cc65/blob - libsrc/common/modload.s
New files for loading modules at runtime
[cc65] / libsrc / common / modload.s
1 ;*****************************************************************************/
2 ;*                                                                           */
3 ;*                                   modload.s                               */
4 ;*                                                                           */
5 ;*                    o65 module loader for the cc65 library                 */
6 ;*                                                                           */
7 ;*                                                                           */
8 ;*                                                                           */
9 ;* (C) 2002      Ullrich von Bassewitz                                       */
10 ;*               Wacholderweg 14                                             */
11 ;*               D-70597 Stuttgart                                           */
12 ;* EMail:        uz@musoftware.de                                            */
13 ;*                                                                           */
14 ;*                                                                           */
15 ;* This software is provided 'as-is', without any expressed or implied       */
16 ;* warranty.  In no event will the authors be held liable for any damages    */
17 ;* arising from the use of this software.                                    */
18 ;*                                                                           */
19 ;* Permission is granted to anyone to use this software for any purpose,     */
20 ;* including commercial applications, and to alter it and redistribute it    */
21 ;* freely, subject to the following restrictions:                            */
22 ;*                                                                           */
23 ;* 1. The origin of this software must not be misrepresented; you must not   */
24 ;*    claim that you wrote the original software. If you use this software   */
25 ;*    in a product, an acknowledgment in the product documentation would be  */
26 ;*    appreciated but is not required.                                       */
27 ;* 2. Altered source versions must be plainly marked as such, and must not   */
28 ;*    be misrepresented as being the original software.                      */
29 ;* 3. This notice may not be removed or altered from any source              */
30 ;*    distribution.                                                          */
31 ;*                                                                           */
32 ;*****************************************************************************/
33
34
35
36         .include        "o65.inc"
37         .include        "modload.inc"
38
39         .import         pushax, pusha0, push0, push1, decax1
40         .import         _malloc, _free, _memset
41         .importzp       sp, ptr1, tmp1, regbank
42
43         .macpack        generic
44
45 ;------------------------------------------------------------------------------
46 ; Variables stored in the register bank in the zero page. Placing the variables
47 ; here will protect them when calling other C functions.
48
49 Module          = regbank+0             ; Pointer to module memory
50 Ctrl            = regbank+2             ; Pointer to mod_ctrl structure
51 TPtr            = regbank+4             ; Pointer to module data for relocation
52
53 ;------------------------------------------------------------------------------
54 ; Static module data
55
56 .bss
57
58 ; Save areas and error recovery data
59 Stack:          .byte   0               ; Old stackpointer
60 RegBankSave:    .res    6               ; Save area for register bank
61
62 ; The header of the o65 file. Since we don't need the 8 bytes any longer,
63 ; once we've checked them, we will overlay them with other data to save a
64 ; few bytes.
65 Header:         .res    O65_HDR_SIZE    ; The o65 header
66
67 ; Input
68 InputByte       = Header                ; Byte read from input
69
70 ; Stuff needed for relocation
71 TextReloc       = Header + 1            ; Relocation value for code seg
72 DataReloc       = Header + 3            ; Relocation value for data seg
73 BssReloc        = Header + 5            ; Relocation value for bss seg
74
75 .data
76 Read:           jmp     $FFFF           ; Jump to read routine
77
78 .rodata
79 ExpectedHdr:    .byte   $01, $00        ; non C64 marker
80                 .byte   $6F, $36, $35   ; Magic ("o65")
81                 .byte   $00             ; Version
82                 .word   $0000           ; Mode word
83 ExpectedHdrSize = * - ExpectedHdr
84
85
86 ;------------------------------------------------------------------------------
87 ; PushCtrl: Push the address of the control structure onto the C stack.
88
89 .code
90 PushCtrl:
91         lda     Ctrl
92         ldx     Ctrl+1
93         jmp     pushax
94
95 ;------------------------------------------------------------------------------
96 ; LoadCtrl: Load a word from the control structure into a/x. The offset of the
97 ;           high byte is passed in Y.
98
99 .code
100 LoadCtrl:
101         lda     (Ctrl),y
102         tax
103         dey
104         lda     (Ctrl),y
105         rts
106
107 ;------------------------------------------------------------------------------
108 ; RestoreRegBank: Restore the register bank contents from the save area. Will
109 ;                 destroy A and X
110
111 .code
112 RestoreRegBank:
113         ldx     #6-1
114 @L1:    lda     RegBankSave,x
115         sta     regbank,x
116         dex
117         bpl     @L1
118         rts
119
120 ;------------------------------------------------------------------------------
121 ; GetReloc: Return a relocation value based on the segment in A
122
123 .code
124 GetReloc:
125         cmp     #O65_SEGID_TEXT
126         bne     @L1
127         lda     TextReloc
128         ldx     TextReloc+1
129         rts
130
131 @L1:    cmp     #O65_SEGID_DATA
132         bne     @L2
133         lda     DataReloc
134         ldx     DataReloc+1
135         rts
136
137 @L2:    cmp     #O65_SEGID_BSS
138         bne     @L3
139         lda     BssReloc
140         ldx     BssReloc+1
141         rts
142
143 @L3:    lda     #MLOAD_ERR_FMT
144 ;       bne     CleanupAndExit          ; Branch always
145
146 ;------------------------------------------------------------------------------
147 ; CleanupAndExit: Free any allocated resources, restore the stack and return
148 ;                 to the caller.
149
150 .code
151 CleanupAndExit:
152
153 ; Restore the stack so we may return to the caller from here
154
155         ldx     Stack
156         txs
157
158 ; Save the error return code
159
160         pha
161
162 ; Check if we have to free the allocated block
163
164         lda     Module
165         ora     Module+1
166         beq     @L1                     ; Jump if no memory allocated
167
168         lda     Module
169         ldx     Module+1
170         jsr     _free                   ; Free the allocated block
171
172 ; Restore the register bank
173
174 @L1:    jsr     RestoreRegBank
175
176 ; Restore the  error code and return to the caller
177
178         ldx     #$00                    ; Load the high byte
179         pla
180         rts
181
182 ;------------------------------------------------------------------------------
183 ; ReadByte: Read one byte with error checking into InputByte and A.
184
185 .code
186 ReadByte:
187
188 ; C->read (C, &B, 1)
189
190         jsr     PushCtrl
191         lda     #<InputByte
192         ldx     #>InputByte
193         jsr     pushax
194         jsr     push1
195         jsr     Read
196
197 ; Check the return code and bail out in case of problems
198
199         tax
200         beq     @L1                     ; Jump if ok
201         lda     #MLOAD_ERR_READ
202         bne     CleanupAndExit
203
204 ; Done
205
206 @L1:    lda     InputByte
207 Done:   rts
208
209 ;------------------------------------------------------------------------------
210 ; RelocSeg: Relocate the segment pointed to by a/x
211
212 .code
213 RelocSeg:
214         jsr     decax1                  ; Start value is segment-1
215         sta     TPtr
216         stx     TPtr+1
217
218 Loop:   jsr     ReadByte                ; Read byte from relocation table
219         beq     Done                    ; Bail out if end of table reached
220
221         cmp     #255                    ; Special offset?
222         bne     @L1
223
224 ; Increment offset by 254 and continue
225
226         lda     TPtr
227         add     #254
228         sta     TPtr
229         bcc     Loop
230         inc     TPtr+1
231         jmp     Loop
232
233 ; Increment offset by A
234
235 @L1:    add     TPtr
236         sta     TPtr
237         bcc     @L2
238         inc     TPtr+1
239
240 ; Read the relocation byte, extract the segment id, fetch the corresponding
241 ; relocation value and place it into ptr1
242
243 @L2:    jsr     ReadByte
244         and     #O65_SEGID_MASK
245         jsr     GetReloc
246         sta     ptr1
247         stx     ptr1+1
248
249 ; Get the relocation byte again, this time extract the relocation type.
250
251         lda     InputByte
252         and     #O65_RTYPE_MASK
253
254 ; Check for and handle the different relocation types.
255
256         cmp     #O65_RTYPE_WORD
257         bne     @L3
258         ldy     #0
259         clc
260         lda     (TPtr),y
261         adc     ptr1
262         sta     (TPtr),y
263         iny
264         bne     @L4                     ; Branch always (add high byte)
265
266 @L3:    cmp     #O65_RTYPE_HIGH
267         bne     @L5
268         jsr     ReadByte                ; Read low byte from relocation table
269         ldy     #0
270         clc
271         adc     ptr1                    ; We just need the carry
272 @L4:    lda     (TPtr),y
273         adc     ptr1+1
274         sta     (TPtr),y
275         jmp     Loop                    ; Done, next entry
276
277 @L5:    cmp     #O65_RTYPE_LOW
278         beq     @L6
279
280 ; Problem: Invalid relocation code
281
282         lda     #MLOAD_ERR_FMT
283         jmp     CleanupAndExit
284
285 @L6:    ldy     #0
286         clc
287         lda     (TPtr),y
288         adc     ptr1
289         sta     (TPtr),y
290
291 ; Finished with this relocation
292
293         jmp     Loop
294
295 ;------------------------------------------------------------------------------
296 ; mod_load: Load and relocate an o65 module
297
298 .code
299 _mod_load:
300
301 ; Save the register bank and clear the Module pointer
302
303         pha
304         ldy     #6
305 @L1:    lda     regbank-1,y
306         sta     RegBankSave-1,y
307         dey
308         bne     @L1
309         sty     Module
310         sty     Module+1
311         pla
312
313 ; Save the passed parameter
314
315         sta     Ctrl
316         stx     Ctrl+1
317
318 ; Save the stack pointer so we can bail out even from subroutines
319
320         tsx
321         stx     Stack
322
323 ; Get the read function pointer from the control structure and place it into
324 ; our call vector
325
326         ldy     #MODCTRL_READ+1
327         jsr     LoadCtrl
328         sta     Read+1
329         stx     Read+2
330
331 ; Read the o65 header: C->read (C, &H, sizeof (H))
332
333         jsr     PushCtrl
334         lda     #<Header
335         ldx     #>Header
336         jsr     pushax
337         lda     #O65_HDR_SIZE
338         jsr     pusha0                  ; Always less than 256
339         jsr     Read
340
341 ; Check the return code
342
343         tax
344         beq     @L2
345         lda     #MLOAD_ERR_READ
346         jmp     CleanupAndExit
347
348 ; We read the o65 header successfully. Validate it.
349
350 @L2:    ldy     #ExpectedHdrSize-1
351 @L3:    lda     Header,y
352         cmp     ExpectedHdr,y
353         beq     @L4
354         lda     #MLOAD_ERR_HDR
355         jmp     CleanupAndExit
356 @L4:    dey
357         bpl     @L3
358
359 ; Header is ok as far as we can say now. Read and skip all options. We may
360 ; add a check here for the OS option later.
361
362 Opt:    jsr     ReadByte
363         beq     OptDone                 ; Jump if done
364         sta     TPtr                    ; Use TPtr as a counter
365 OneOpt: dec     TPtr
366         beq     Opt                     ; Next option
367         jsr     ReadByte                ; Skip one byte
368         jmp     OneOpt
369 OptDone:
370
371 ; Skipped all options. Calculate the sizes of several areas needed later
372
373         lda     Header + O65_HDR_TLEN
374         add     Header + O65_HDR_DLEN
375         sta     TPtr
376         lda     Header + O65_HDR_TLEN + 1
377         adc     Header + O65_HDR_DLEN + 1
378         sta     TPtr+1
379         lda     TPtr
380         add     Header + O65_HDR_BLEN
381         sta     tmp1
382         lda     TPtr+1
383         adc     Header + O65_HDR_BLEN + 1
384
385 ; Load the total module size into a/x and store it into the control structure
386
387         ldy     #MODCTRL_MODULE_SIZE + 1
388         sta     (Ctrl),y
389         tax
390         dey
391         lda     tmp1
392         sta     (Ctrl),y
393
394 ; Allocate memory, check if we got it
395
396         jsr     _malloc
397         sta     Module
398         stx     Module+1
399         ora     Module+1
400         bne     GotMem
401
402 ; Could not allocate memory
403
404         lda     #MLOAD_ERR_MEM
405         jmp     CleanupAndExit
406
407 ; We got the memory block. Setup the pointers and sizes in the control
408 ; structure. We will use internal knowlege about the layout of the structure
409 ; here to save some code.
410
411 GotMem: lda     Module
412         ldy     #MODCTRL_MODULE
413         sta     (Ctrl),y
414         ldy     #MODCTRL_CODE
415         sta     (Ctrl),y
416         txa
417         iny
418         sta     (Ctrl),y                ; MODCTRL_CODE+1
419         ldy     #MODCTRL_MODULE+1
420         sta     (Ctrl),y
421
422 ; The following loop will also copy some information that is not needed just
423 ; to save some code.
424
425         ldx     #O65_HDR_TLEN
426         ldy     #MODCTRL_CODE_SIZE
427 CLoop:  lda     Header,x
428         sta     (Ctrl),y
429         inx
430         iny
431         cpy     #MODCTRL_SIZE
432         bne     CLoop
433
434 ; Missing in the control structure now: start of the data and bss segments
435
436         ldy     #MODCTRL_DATA
437         lda     Module
438         add     Header + O65_HDR_TLEN
439         sta     (Ctrl),y
440         iny
441         lda     Module + 1
442         adc     Header + O65_HDR_TLEN + 1
443         sta     (Ctrl),y
444
445         ldy     #MODCTRL_BSS
446         lda     Module
447         add     TPtr
448         sta     (Ctrl),y
449         iny
450         lda     Module+1
451         add     TPtr+1
452         sta     (Ctrl),y
453
454 ; Control structure is complete now. Load code and data segment into memory.
455 ; The sum of the sizes of code and data segment is still in TPtr.
456 ; C->read (C, C->module, H.tlen + H.dlen)
457
458         jsr     PushCtrl
459         lda     Module
460         ldx     Module+1
461         jsr     pushax
462         lda     TPtr
463         ldx     TPtr+1
464         jsr     pushax
465         jsr     Read
466
467 ; Check for errors
468
469         tax
470         beq     LoadOk
471         lda     #MLOAD_ERR_READ
472         jmp     CleanupAndExit
473
474 ; We've got the code and data segments in memory. Next section contains
475 ; undefined references which we don't support. So check if the count of
476 ; undefined references is actually zero.
477
478 LoadOk: jsr     ReadByte
479         bne     Undef
480         jsr     ReadByte
481         beq     Reloc
482 Undef:  lda     #MLOAD_ERR_FMT
483         jmp     CleanupAndExit
484
485 ; Number of undefined references was zero. Next sections are the relocation
486 ; tables for code and data segment. Before doing the actual relocation, we
487 ; have to setup the relocation values for the three segments.
488
489 Reloc:  lda     Module
490         sub     Header + O65_HDR_TBASE
491         sta     TextReloc
492         lda     Module + 1
493         sbc     Header + O65_HDR_TBASE + 1
494         sta     TextReloc + 1
495
496         ldy     #MODCTRL_DATA
497         lda     (Ctrl),y
498         sub     Header + O65_HDR_DBASE
499         sta     DataReloc
500         iny
501         lda     (Ctrl),y
502         sbc     Header + O65_HDR_DBASE + 1
503         sta     DataReloc + 1
504
505         ldy     #MODCTRL_BSS
506         lda     (Ctrl),y
507         sub     Header + O65_HDR_BBASE
508         sta     BssReloc
509         iny
510         lda     (Ctrl),y
511         sbc     Header + O65_HDR_BBASE + 1
512         sta     BssReloc + 1
513
514 ; Relocate the code segment
515
516         lda     Module
517         ldx     Module + 1                      ; Code segment address
518         jsr     RelocSeg
519
520 ; Relocate the data segment
521
522         ldy     #MODCTRL_DATA + 1
523         jsr     LoadCtrl                        ; Get data segment address
524         jsr     RelocSeg
525
526 ; Clear the bss segment
527
528         ldy     #MODCTRL_BSS + 1
529         jsr     LoadCtrl                        ; Load bss segment address
530         jsr     pushax
531         jsr     push0
532         ldy     #MODCTRL_BSS_SIZE + 1
533         jsr     LoadCtrl                        ; Load bss segment size
534         jsr     _memset                         ; memset (bss, 0, bss_size);
535
536 ; We're done. Restore the register bank and return a success code
537
538         jsr     RestoreRegBank
539         lda     #MLOAD_OK
540         rts
541