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