]> git.sur5r.net Git - cc65/blob - libsrc/common/modload.s
Issue 814
[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         .include        "zeropage.inc"
39
40         .import         pushax, pusha0, push0, push1, decax1
41         .import         _malloc, _free, _bzero
42         .import         __ZP_START__    ; Linker generated
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    regbanksize     ; 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:         .tag    O65_HDR         ; The o65 header
67
68 ; Input
69 InputByte       = Header                ; Byte read from input
70
71 ; Relocation
72 RelocVal        = Header + 1            ; Relocation value
73
74 .data
75 Read:   jmp     $FFFF                   ; Jump to read routine
76
77 .rodata
78 ExpectedHdr:
79         .byte   O65_MARKER_0, O65_MARKER_1              ; non C64 marker
80         .byte   O65_MAGIC_0, O65_MAGIC_1, O65_MAGIC_2   ; Magic ("o65")
81         .byte   O65_VERSION                             ; Version
82         .word   O65_MODE_CC65                           ; Mode word
83
84 ExpectedHdrSize = * - ExpectedHdr
85
86
87 ;------------------------------------------------------------------------------
88 ; PushCallerData: Push the callerdata member from control structure onto the
89 ; C stack.
90
91 .code
92 PushCallerData:
93         ldy     #MOD_CTRL::CALLERDATA+1
94         lda     (Ctrl),y
95         tax
96         dey
97         lda     (Ctrl),y
98         jmp     pushax
99
100 ;------------------------------------------------------------------------------
101 ; RestoreRegBank: Restore the register bank contents from the save area. Will
102 ;                 destroy A and X (the latter will be zero on return).
103
104 .code
105 RestoreRegBank:
106         ldx     #6
107 @L1:    lda     RegBankSave-1,x
108         sta     regbank-1,x
109         dex
110         bne     @L1
111         rts
112
113 ;------------------------------------------------------------------------------
114 ; GetReloc: Return a relocation value based on the segment in A.
115 ; The routine uses some knowledge about the values to make the code shorter.
116
117 .code
118 GetReloc:
119         cmp     #O65_SEGID_TEXT
120         bcc     FormatError
121         cmp     #O65_SEGID_ZP
122         beq     @L1
123         bcs     FormatError
124
125 ; Text, data and bss segment
126
127         lda     Module
128         ldx     Module+1                ; Return start address of buffer
129         rts
130
131 ; Zero page relocation
132
133 @L1:    lda     #<__ZP_START__
134         ldx     #>__ZP_START__
135         rts
136
137 ;------------------------------------------------------------------------------
138 ; ReadByte: Read one byte with error checking into InputByte and A.
139 ; ReadAndCheckError: Call read with the current C stack and check for errors.
140
141 .bss
142 ReadSize:       .res    2
143
144 .code
145 ReadByte:
146
147 ; C->read (C->callerdata, &B, 1)
148
149         jsr     PushCallerData
150         lda     #<InputByte
151         ldx     #>InputByte
152         jsr     pushax
153         ldx     #0
154         lda     #1
155
156 ; This is a second entry point used by the other calls to Read
157
158 ReadAndCheckError:
159         sta     ReadSize
160         stx     ReadSize+1
161         jsr     Read
162
163 ; Check the return code and bail out in case of problems
164
165         cmp     ReadSize
166         bne     @L1
167         cpx     ReadSize+1
168         beq     @L2                     ; Jump if ok
169 @L1:    lda     #MLOAD_ERR_READ
170         bne     CleanupAndExit
171
172 ; Done
173
174 @L2:    lda     InputByte               ; If called ReadByte, load the byte read
175 Done:   rts
176
177 ;------------------------------------------------------------------------------
178 ; FormatError: Bail out with an o65 format error
179
180 .code
181 FormatError:
182         lda     #MLOAD_ERR_FMT
183 ;       bne     CleanupAndExit          ; Branch always
184
185 ;------------------------------------------------------------------------------
186 ; CleanupAndExit: Free any allocated resources, restore the stack and return
187 ;                 to the caller.
188
189 .code
190 CleanupAndExit:
191
192 ; Restore the stack so we may return to the caller from here
193
194         ldx     Stack
195         txs
196
197 ; Save the error return code
198
199         pha
200
201 ; Check if we have to free the allocated block
202
203         lda     Module
204         ldx     Module+1
205         bne     @L1
206         tay                             ; Test high byte
207         beq     @L2
208 @L1:    jsr     _free                   ; Free the allocated block
209
210 ; Restore the register bank
211
212 @L2:    jsr     RestoreRegBank
213
214 ; Restore the  error code and return to the caller
215
216         ldx     #$00                    ; Load the high byte
217         pla
218         rts
219
220 ;------------------------------------------------------------------------------
221 ; RelocSeg: Relocate the segment pointed to by a/x
222
223 .code
224 RelocSeg:
225         jsr     decax1                  ; Start value is segment-1
226         sta     TPtr
227         stx     TPtr+1
228
229 Loop:   jsr     ReadByte                ; Read byte from relocation table
230         beq     Done                    ; Bail out if end of table reached
231
232         cmp     #255                    ; Special offset?
233         bne     @L1
234
235 ; Increment offset by 254 and continue
236
237         lda     TPtr
238         add     #254
239         sta     TPtr
240         bcc     Loop
241         inc     TPtr+1
242         jmp     Loop
243
244 ; Increment offset by A
245
246 @L1:    add     TPtr
247         sta     TPtr
248         bcc     @L2
249         inc     TPtr+1
250
251 ; Read the relocation byte, extract the segment id, fetch the corresponding
252 ; relocation value and place it into ptr1
253
254 @L2:    jsr     ReadByte
255         and     #O65_SEGID_MASK
256         jsr     GetReloc
257         sta     RelocVal
258         stx     RelocVal+1
259
260 ; Get the relocation byte again, this time extract the relocation type.
261
262         lda     InputByte
263         and     #O65_RTYPE_MASK
264
265 ; Check for and handle the different relocation types.
266
267         cmp     #O65_RTYPE_WORD
268         beq     RelocWord
269         cmp     #O65_RTYPE_HIGH
270         beq     RelocHigh
271         cmp     #O65_RTYPE_LOW
272         bne     FormatError
273
274 ; Relocate the low byte
275
276 RelocLow:
277         ldy     #0
278         clc
279         lda     RelocVal
280         bcc     AddCommon
281
282 ; Relocate a high byte
283
284 RelocHigh:
285         jsr     ReadByte                ; Read low byte from relocation table
286         ldy     #0
287         clc
288         adc     RelocVal                ; We just need the carry
289 AddHigh:
290         lda     RelocVal+1
291 AddCommon:
292         adc     (TPtr),y
293         sta     (TPtr),y
294         jmp     Loop                    ; Done, next entry
295
296 ; Relocate a word
297
298 RelocWord:
299         ldy     #0
300         clc
301         lda     RelocVal
302         adc     (TPtr),y
303         sta     (TPtr),y
304         iny
305         bne     AddHigh                 ; Branch always (add high byte)
306
307 ;------------------------------------------------------------------------------
308 ; mod_load: Load and relocate an o65 module
309
310 .code
311 _mod_load:
312
313 ; Save the register bank and clear the Module pointer
314
315         pha
316         ldy     #6
317 @L1:    lda     regbank-1,y
318         sta     RegBankSave-1,y
319         dey
320         bne     @L1
321         sty     Module
322         sty     Module+1
323         pla
324
325 ; Save the passed parameter
326
327         sta     Ctrl
328         stx     Ctrl+1
329
330 ; Save the stack pointer so we can bail out even from subroutines
331
332         tsx
333         stx     Stack
334
335 ; Get the read function pointer from the control structure and place it into
336 ; our call vector
337
338         ldy     #MOD_CTRL::READ
339         lda     (Ctrl),y
340         sta     Read+1
341         iny
342         lda     (Ctrl),y
343         sta     Read+2
344
345 ; Read the o65 header: C->read (C->callerdata, &H, sizeof (H))
346
347         jsr     PushCallerData
348         lda     #<Header
349         ldx     #>Header
350         jsr     pushax
351         lda     #.sizeof(O65_HDR)
352         ldx     #0                      ; Always less than 256
353         jsr     ReadAndCheckError       ; Bails out in case of errors
354
355 ; We read the o65 header successfully. Validate it.
356
357         ldy     #ExpectedHdrSize-1
358 ValidateHeader:
359         lda     Header,y
360         cmp     ExpectedHdr,y
361         bne     HeaderError
362         dey
363         bpl     ValidateHeader
364
365 ; Header is ok as far as we can say now. Read all options, check for the
366 ; OS option and ignore all others. The OS option contains a version number
367 ; and the module id as additional data.
368
369         iny                             ; Y = $00
370         sty     TPtr+1                  ; Flag for OS option read
371 Opt:    jsr     ReadByte                ; Read the length byte
372         beq     OptDone                 ; Jump if done
373         sta     TPtr                    ; Use TPtr as a counter
374
375 ; An option has a length of at least 2 bytes
376
377         cmp     #2
378         bcc     HeaderError             ; Must be 2 bytes total at least
379
380 ; Check for the OS option
381
382         dec     TPtr
383         jsr     ReadByte                ; Get the option type
384         cmp     #O65_OPT_OS             ; OS option?
385         bne     SkipOpt                 ; No: Skip
386
387         lda     TPtr                    ; Get remaining length+1
388         cmp     #5                      ; CC65 has 6 bytes total
389         bne     OSError
390
391         jsr     ReadByte                ; Get the operating system
392         cmp     #O65_OS_CC65
393         bne     OSError                 ; Wrong operating system
394
395         jsr     ReadByte                ; Get the version number, expect zero
396         bne     OSError                 ; Wrong version
397
398         jsr     ReadByte                ; Get low byte of id
399         ldy     #MOD_CTRL::MODULE_ID
400         sta     (Ctrl),y
401         jsr     ReadByte
402         ldy     #MOD_CTRL::MODULE_ID+1
403         sta     (Ctrl),y
404
405         inc     TPtr+1                  ; Remember that we got the OS
406
407         jmp     Opt
408
409 ; Skip one option
410
411 SkipOpt:
412         dec     TPtr
413         beq     Opt                     ; Next option
414         jsr     ReadByte                ; Skip one byte
415         jmp     SkipOpt
416
417 ; Operating system error
418
419 OSError:
420         lda     #MLOAD_ERR_OS
421         jmp     CleanupAndExit
422
423 ; Options done, check that we got the OS option
424
425 OptDone:
426         lda     TPtr+1
427         bne     CalcSizes
428
429 ; Entry point for header errors
430
431 HeaderError:
432         lda     #MLOAD_ERR_HDR
433         jmp     CleanupAndExit
434
435 ; Skipped all options. Calculate the size of text+data and of text+data+bss
436 ; (the latter is the size of the memory block we need). We will store the
437 ; total module size also into the control structure for evaluation by the
438 ; caller
439
440 CalcSizes:
441         lda     Header + O65_HDR::TLEN
442         add     Header + O65_HDR::DLEN
443         sta     TPtr
444         lda     Header + O65_HDR::TLEN + 1
445         adc     Header + O65_HDR::DLEN + 1
446         sta     TPtr+1
447         lda     TPtr
448         add     Header + O65_HDR::BLEN
449         pha                             ; Save low byte of total size
450         ldy     #MOD_CTRL::MODULE_SIZE
451         sta     (Ctrl),y
452         lda     TPtr+1
453         adc     Header + O65_HDR::BLEN + 1
454         iny
455         sta     (Ctrl),y
456         tax
457         pla                             ; Restore low byte of total size
458
459 ; Total memory size is now in a/x. Allocate memory and remember the result,
460 ; both, locally and in the control structure so it the caller can access
461 ; the memory block. After that, check if we got the requested memory.
462
463         jsr     _malloc
464         sta     Module
465         stx     Module+1
466
467         ldy     #MOD_CTRL::MODULE
468         sta     (Ctrl),y
469         txa
470         iny
471         sta     (Ctrl),y
472         ora     Module
473         bne     GotMem
474
475 ; Could not allocate memory
476
477         lda     #MLOAD_ERR_MEM
478         jmp     CleanupAndExit
479
480 ; Control structure is complete now. Clear the bss segment.
481 ; bzero (bss_addr, bss_size)
482
483 GotMem: lda     Module
484         add     TPtr
485         pha
486         lda     Module+1
487         adc     TPtr+1                  ; Module + tlen + dlen
488         tax
489         pla
490         jsr     pushax
491         lda     Header + O65_HDR::BLEN
492         ldx     Header + O65_HDR::BLEN+1
493         jsr     _bzero                  ; bzero (bss, bss_size);
494
495 ; Load code and data segment into memory. The sum of the sizes of
496 ; code+data segment is still in TPtr.
497 ; C->read (C->callerdata, C->module, H.tlen + H.dlen)
498
499         jsr     PushCallerData
500         lda     Module
501         ldx     Module+1
502         jsr     pushax
503         lda     TPtr
504         ldx     TPtr+1
505         jsr     ReadAndCheckError       ; Bails out in case of errors
506
507 ; We've got the code and data segments in memory. Next section contains
508 ; undefined references which we don't support. So check if the count of
509 ; undefined references is actually zero.
510
511         jsr     ReadByte
512         bne     Undef
513         jsr     ReadByte
514         beq     Reloc
515 Undef:  jmp     FormatError
516
517 ; Number of undefined references was zero. Next come the relocation tables
518 ; for code and data segment. Relocate the code segment
519
520 Reloc:  lda     Module
521         ldx     Module + 1              ; Code segment address
522         jsr     RelocSeg
523
524 ; Relocate the data segment
525
526         lda     Module
527         add     Header + O65_HDR::TLEN
528         pha
529         lda     Module + 1
530         adc     Header + O65_HDR::TLEN + 1
531         tax
532         pla                             ; Data segment address in a/x
533         jsr     RelocSeg
534
535 ; We're done. Restore the register bank and return a success code
536
537         jsr     RestoreRegBank          ; X will be zero on return
538         lda     #MLOAD_OK
539         rts
540