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