]> git.sur5r.net Git - cc65/blob - libsrc/common/modload.s
4385b1a08260bdfd7da05ef5e623c685d73d7273
[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 ; PushCallerData: Push the callerdata member from control structure onto the
89 ; C stack.
90
91 .code
92 PushCallerData:
93         ldy     #MODCTRL_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     pushax
162         jsr     Read
163
164 ; Check the return code and bail out in case of problems
165
166         cmp     ReadSize
167         bne     @L1
168         cpx     ReadSize+1
169         beq     @L2                     ; Jump if ok
170 @L1:    lda     #MLOAD_ERR_READ
171         bne     CleanupAndExit
172
173 ; Done
174
175 @L2:    lda     InputByte               ; If called ReadByte, load the byte read
176 Done:   rts
177
178 ;------------------------------------------------------------------------------
179 ; FormatError: Bail out with an o65 format error
180
181 .code
182 FormatError:
183         lda     #MLOAD_ERR_FMT
184 ;       bne     CleanupAndExit          ; Branch always
185
186 ;------------------------------------------------------------------------------
187 ; CleanupAndExit: Free any allocated resources, restore the stack and return
188 ;                 to the caller.
189
190 .code
191 CleanupAndExit:
192
193 ; Restore the stack so we may return to the caller from here
194
195         ldx     Stack
196         txs
197
198 ; Save the error return code
199
200         pha
201
202 ; Check if we have to free the allocated block
203
204         lda     Module
205         ora     Module+1
206         beq     @L1                     ; Jump if no memory allocated
207
208         lda     Module
209         ldx     Module+1
210         jsr     _free                   ; Free the allocated block
211
212 ; Restore the register bank
213
214 @L1:    jsr     RestoreRegBank
215
216 ; Restore the  error code and return to the caller
217
218         ldx     #$00                    ; Load the high byte
219         pla
220         rts
221
222 ;------------------------------------------------------------------------------
223 ; RelocSeg: Relocate the segment pointed to by a/x
224
225 .code
226 RelocSeg:
227         jsr     decax1                  ; Start value is segment-1
228         sta     TPtr
229         stx     TPtr+1
230
231 Loop:   jsr     ReadByte                ; Read byte from relocation table
232         beq     Done                    ; Bail out if end of table reached
233
234         cmp     #255                    ; Special offset?
235         bne     @L1
236
237 ; Increment offset by 254 and continue
238
239         lda     TPtr
240         add     #254
241         sta     TPtr
242         bcc     Loop
243         inc     TPtr+1
244         jmp     Loop
245
246 ; Increment offset by A
247
248 @L1:    add     TPtr
249         sta     TPtr
250         bcc     @L2
251         inc     TPtr+1
252
253 ; Read the relocation byte, extract the segment id, fetch the corresponding
254 ; relocation value and place it into ptr1
255
256 @L2:    jsr     ReadByte
257         and     #O65_SEGID_MASK
258         jsr     GetReloc
259         sta     RelocVal
260         stx     RelocVal+1
261
262 ; Get the relocation byte again, this time extract the relocation type.
263
264         lda     InputByte
265         and     #O65_RTYPE_MASK
266
267 ; Check for and handle the different relocation types.
268
269         cmp     #O65_RTYPE_WORD
270         beq     RelocWord
271         cmp     #O65_RTYPE_HIGH
272         beq     RelocHigh
273         cmp     #O65_RTYPE_LOW
274         bne     FormatError
275
276 ; Relocate the low byte
277
278 RelocLow:
279         ldy     #0
280         clc
281         lda     RelocVal
282         bcc     AddCommon
283
284 ; Relocate a high byte
285
286 RelocHigh:
287         jsr     ReadByte                ; Read low byte from relocation table
288         ldy     #0
289         clc
290         adc     RelocVal                ; We just need the carry
291 AddHigh:
292         lda     RelocVal+1
293 AddCommon:
294         adc     (TPtr),y
295         sta     (TPtr),y
296         jmp     Loop                    ; Done, next entry
297
298 ; Relocate a word
299
300 RelocWord:
301         ldy     #0
302         clc
303         lda     RelocVal
304         adc     (TPtr),y
305         sta     (TPtr),y
306         iny
307         bne     AddHigh                 ; Branch always (add high byte)
308
309 ;------------------------------------------------------------------------------
310 ; mod_load: Load and relocate an o65 module
311
312 .code
313 _mod_load:
314
315 ; Save the register bank and clear the Module pointer
316
317         pha
318         ldy     #6
319 @L1:    lda     regbank-1,y
320         sta     RegBankSave-1,y
321         dey
322         bne     @L1
323         sty     Module
324         sty     Module+1
325         pla
326
327 ; Save the passed parameter
328
329         sta     Ctrl
330         stx     Ctrl+1
331
332 ; Save the stack pointer so we can bail out even from subroutines
333
334         tsx
335         stx     Stack
336
337 ; Get the read function pointer from the control structure and place it into
338 ; our call vector
339
340         ldy     #MODCTRL_READ
341         lda     (Ctrl),y
342         sta     Read+1
343         iny
344         lda     (Ctrl),y
345         sta     Read+2
346
347 ; Read the o65 header: C->read (C->callerdata, &H, sizeof (H))
348
349         jsr     PushCallerData
350         lda     #<Header
351         ldx     #>Header
352         jsr     pushax
353         lda     #O65_HDR_SIZE
354         ldx     #0                      ; Always less than 256
355         jsr     ReadAndCheckError       ; Bails out in case of errors
356
357 ; We read the o65 header successfully. Validate it.
358
359         ldy     #ExpectedHdrSize-1
360 ValidateHeader:
361         lda     Header,y
362         cmp     ExpectedHdr,y
363         bne     HeaderError
364         dey
365         bpl     ValidateHeader
366
367 ; Header is ok as far as we can say now. Read all options, check for the
368 ; OS option and ignore all others. The OS option contains a version number
369 ; and the module id as additional data.
370
371         iny                             ; Y = $00
372         sty     TPtr+1                  ; Flag for OS option read
373 Opt:    jsr     ReadByte                ; Read the length byte
374         beq     OptDone                 ; Jump if done
375         sta     TPtr                    ; Use TPtr as a counter
376
377 ; An option has a length of at least 2 bytes
378
379         cmp     #2
380         bcc     HeaderError             ; Must be 2 bytes total at least
381
382 ; Check for the OS option
383
384         dec     TPtr
385         jsr     ReadByte                ; Get the option type
386         cmp     #O65_OPT_OS             ; OS option?
387         bne     SkipOpt                 ; No: Skip
388
389         lda     TPtr                    ; Get remaining length+1
390         cmp     #5                      ; CC65 has 6 bytes total
391         bne     OSError
392
393         jsr     ReadByte                ; Get the operating system
394         cmp     #O65_OS_CC65_MODULE
395         bne     OSError                 ; Wrong operating system
396
397         jsr     ReadByte                ; Get the version number, expect zero
398         bne     OSError                 ; Wrong version
399
400         jsr     ReadByte                ; Get low byte of id
401         ldy     #MODCTRL_MODULE_ID
402         sta     (Ctrl),y
403         jsr     ReadByte
404         ldy     #MODCTRL_MODULE_ID+1
405         sta     (Ctrl),y
406
407         inc     TPtr+1                  ; Remember that we got the OS
408
409         jmp     Opt
410
411 ; Skip one option
412
413 SkipOpt:
414         dec     TPtr
415         beq     Opt                     ; Next option
416         jsr     ReadByte                ; Skip one byte
417         jmp     SkipOpt
418
419 ; Operating system error
420
421 OSError:
422         lda     #MLOAD_ERR_OS
423         jmp     CleanupAndExit
424
425 ; Options done, check that we got the OS option
426
427 OptDone:
428         lda     TPtr+1
429         bne     CalcSizes
430
431 ; Entry point for header errors
432
433 HeaderError:
434         lda     #MLOAD_ERR_HDR
435         jmp     CleanupAndExit
436
437 ; Skipped all options. Calculate the size of text+data and of text+data+bss
438 ; (the latter is the size of the memory block we need). We will store the
439 ; total module size also into the control structure for evaluation by the
440 ; caller
441
442 CalcSizes:
443         lda     Header + O65_HDR_TLEN
444         add     Header + O65_HDR_DLEN
445         sta     TPtr
446         lda     Header + O65_HDR_TLEN + 1
447         adc     Header + O65_HDR_DLEN + 1
448         sta     TPtr+1
449         lda     TPtr
450         add     Header + O65_HDR_BLEN
451         pha                             ; Save low byte of total size
452         ldy     #MODCTRL_MODULE_SIZE
453         sta     (Ctrl),y
454         lda     TPtr+1
455         adc     Header + O65_HDR_BLEN + 1
456         iny
457         sta     (Ctrl),y
458         tax
459         pla                             ; Restore low byte of total size
460
461 ; Total memory size is now in a/x. Allocate memory and remember the result,
462 ; both, locally and in the control structure so it the caller can access
463 ; the memory block. After that, check if we got the requested memory.
464
465         jsr     _malloc
466         sta     Module
467         stx     Module+1
468
469         ldy     #MODCTRL_MODULE
470         sta     (Ctrl),y
471         txa
472         iny
473         sta     (Ctrl),y
474         ora     Module
475         bne     GotMem
476
477 ; Could not allocate memory
478
479         lda     #MLOAD_ERR_MEM
480         jmp     CleanupAndExit
481
482 ; Control structure is complete now. Clear the bss segment.
483 ; bzero (bss_addr, bss_size)
484
485 GotMem: lda     Module
486         add     TPtr
487         pha
488         lda     Module+1
489         adc     TPtr+1                  ; Module + tlen + dlen
490         tax
491         pla
492         jsr     pushax
493         lda     Header + O65_HDR_BLEN
494         ldx     Header + O65_HDR_BLEN+1
495         jsr     _bzero                  ; bzero (bss, bss_size);
496
497 ; Load code and data segment into memory. The sum of the sizes of
498 ; code+data segment is still in TPtr.
499 ; C->read (C->callerdata, C->module, H.tlen + H.dlen)
500
501         jsr     PushCallerData
502         lda     Module
503         ldx     Module+1
504         jsr     pushax
505         lda     TPtr
506         ldx     TPtr+1
507         jsr     ReadAndCheckError       ; Bails out in case of errors
508
509 ; We've got the code and data segments in memory. Next section contains
510 ; undefined references which we don't support. So check if the count of
511 ; undefined references is actually zero.
512
513         jsr     ReadByte
514         bne     Undef
515         jsr     ReadByte
516         beq     Reloc
517 Undef:  jmp     FormatError
518
519 ; Number of undefined references was zero. Next come the relocation tables
520 ; for code and data segment. Relocate the code segment
521
522 Reloc:  lda     Module
523         ldx     Module + 1              ; Code segment address
524         jsr     RelocSeg
525
526 ; Relocate the data segment
527
528         lda     Module
529         add     Header + O65_HDR_TLEN
530         pha
531         lda     Module + 1
532         adc     Header + O65_HDR_TLEN + 1
533         tax
534         pla                             ; Data segment address in a/x
535         jsr     RelocSeg
536
537 ; We're done. Restore the register bank and return a success code
538
539         jsr     RestoreRegBank          ; X will be zero on return
540         lda     #MLOAD_OK
541         rts
542