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