]> git.sur5r.net Git - cc65/blobdiff - libsrc/common/modload.s
atari5200: fix COLOR defines' names
[cc65] / libsrc / common / modload.s
index f90eac4cfa9f46bb0b6548d06e61ffc04ac2a575..2a4371215e03aadb464f2c07e91f0acb71bd6cc2 100644 (file)
 
         .include        "o65.inc"
         .include        "modload.inc"
+        .include        "zeropage.inc"
 
         .import         pushax, pusha0, push0, push1, decax1
-        .import         _malloc, _free, _memset
+        .import         _malloc, _free, _bzero
         .import         __ZP_START__    ; Linker generated
-        .importzp       sp, ptr1, tmp1, regbank
 
         .macpack        generic
 
@@ -58,56 +58,44 @@ TPtr            = regbank+4             ; Pointer to module data for relocation
 
 ; Save areas and error recovery data
 Stack:          .byte   0               ; Old stackpointer
-RegBankSave:    .res    6               ; Save area for register bank
+RegBankSave:    .res    regbanksize     ; Save area for register bank
 
 ; The header of the o65 file. Since we don't need the first 8 bytes any
 ; longer, once we've checked them, we will overlay them with other data to
 ; save a few bytes.
-Header:         .res    O65_HDR_SIZE    ; The o65 header
+Header:         .tag    O65_HDR         ; The o65 header
 
 ; Input
 InputByte       = Header                ; Byte read from input
 
-; Stuff needed for relocation. Since the ld65 linker uses a relocation base
-; address of zero for all segments, the relocation values needed are actually
-; the start addresses of the segments. Among other things this means that the
-; relocation value for the text segment is the same as the start address as
-; the whole module block.
-TextReloc       = Module                ; Relocation value for code seg
-DataReloc       = Header + 1            ; Relocation value for data seg
-BssReloc        = Header + 3            ; Relocation value for bss seg
+; Relocation
+RelocVal        = Header + 1            ; Relocation value
 
 .data
-Read:           jmp     $FFFF           ; Jump to read routine
+Read:   jmp     $FFFF                   ; Jump to read routine
 
 .rodata
-ExpectedHdr:    .byte   $01, $00        ; non C64 marker
-                .byte   $6F, $36, $35   ; Magic ("o65")
-                .byte   $00             ; Version
-                .word   $0000           ; Mode word
+ExpectedHdr:
+        .byte   O65_MARKER_0, O65_MARKER_1              ; non C64 marker
+        .byte   O65_MAGIC_0, O65_MAGIC_1, O65_MAGIC_2   ; Magic ("o65")
+        .byte   O65_VERSION                             ; Version
+        .word   O65_MODE_CC65                           ; Mode word
+
 ExpectedHdrSize = * - ExpectedHdr
 
 
 ;------------------------------------------------------------------------------
-; PushCtrl: Push the address of the control structure onto the C stack.
+; PushCallerData: Push the callerdata member from control structure onto the
+; C stack.
 
 .code
-PushCtrl:
-        lda     Ctrl
-        ldx     Ctrl+1
-        jmp     pushax
-
-;------------------------------------------------------------------------------
-; LoadCtrl: Load a word from the control structure into a/x. The offset of the
-;           high byte is passed in Y.
-
-.code
-LoadCtrl:
+PushCallerData:
+        ldy     #MOD_CTRL::CALLERDATA+1
         lda     (Ctrl),y
         tax
         dey
         lda     (Ctrl),y
-        rts
+        jmp     pushax
 
 ;------------------------------------------------------------------------------
 ; RestoreRegBank: Restore the register bank contents from the save area. Will
@@ -123,37 +111,73 @@ RestoreRegBank:
         rts
 
 ;------------------------------------------------------------------------------
-; GetReloc: Return a relocation value based on the segment in A
+; GetReloc: Return a relocation value based on the segment in A.
+; The routine uses some knowledge about the values to make the code shorter.
 
 .code
 GetReloc:
         cmp     #O65_SEGID_TEXT
-        bne     @L1
-        lda     TextReloc
-        ldx     TextReloc+1
-        rts
+        bcc     FormatError
+        cmp     #O65_SEGID_ZP
+        beq     @L1
+        bcs     FormatError
 
-@L1:    cmp     #O65_SEGID_DATA
-        bne     @L2
-        lda     DataReloc
-        ldx     DataReloc+1
-        rts
+; Text, data and bss segment
 
-@L2:    cmp     #O65_SEGID_BSS
-        bne     @L3
-        lda     BssReloc
-        ldx     BssReloc+1
+        lda     Module
+        ldx     Module+1                ; Return start address of buffer
         rts
 
-@L3:    cmp     #O65_SEGID_ZP
-        bne     FormatError
-        lda     #<__ZP_START__
+; Zero page relocation
+
+@L1:    lda     #<__ZP_START__
         ldx     #>__ZP_START__
         rts
 
+;------------------------------------------------------------------------------
+; ReadByte: Read one byte with error checking into InputByte and A.
+; ReadAndCheckError: Call read with the current C stack and check for errors.
+
+.bss
+ReadSize:       .res    2
+
+.code
+ReadByte:
+
+; C->read (C->callerdata, &B, 1)
+
+        jsr     PushCallerData
+        lda     #<InputByte
+        ldx     #>InputByte
+        jsr     pushax
+        ldx     #0
+        lda     #1
+
+; This is a second entry point used by the other calls to Read
+
+ReadAndCheckError:
+        sta     ReadSize
+        stx     ReadSize+1
+        jsr     Read
+
+; Check the return code and bail out in case of problems
+
+        cmp     ReadSize
+        bne     @L1
+        cpx     ReadSize+1
+        beq     @L2                     ; Jump if ok
+@L1:    lda     #MLOAD_ERR_READ
+        bne     CleanupAndExit
+
+; Done
+
+@L2:    lda     InputByte               ; If called ReadByte, load the byte read
+Done:   rts
+
 ;------------------------------------------------------------------------------
 ; FormatError: Bail out with an o65 format error
 
+.code
 FormatError:
         lda     #MLOAD_ERR_FMT
 ;       bne     CleanupAndExit          ; Branch always
@@ -176,17 +200,16 @@ CleanupAndExit:
 
 ; Check if we have to free the allocated block
 
-        lda     Module
-        ora     Module+1
-        beq     @L1                     ; Jump if no memory allocated
-
         lda     Module
         ldx     Module+1
-        jsr     _free                   ; Free the allocated block
+        bne     @L1
+        tay                             ; Test high byte
+        beq     @L2
+@L1:    jsr     _free                   ; Free the allocated block
 
 ; Restore the register bank
 
-@L1:    jsr     RestoreRegBank
+@L2:    jsr     RestoreRegBank
 
 ; Restore the  error code and return to the caller
 
@@ -194,38 +217,6 @@ CleanupAndExit:
         pla
         rts
 
-;------------------------------------------------------------------------------
-; ReadByte: Read one byte with error checking into InputByte and A.
-; ReadAndCheckError: Call read with the current C stack and check for errors.
-
-.code
-ReadByte:
-
-; C->read (C, &B, 1)
-
-        jsr     PushCtrl
-        lda     #<InputByte
-        ldx     #>InputByte
-        jsr     pushax
-        jsr     push1
-
-; This is a second entry point used by the other calls to Read
-
-ReadAndCheckError:
-        jsr     Read
-
-; Check the return code and bail out in case of problems
-
-        tax
-        beq     @L1                     ; Jump if ok
-        lda     #MLOAD_ERR_READ
-        bne     CleanupAndExit
-
-; Done
-
-@L1:    lda     InputByte               ; If called ReadByte, load the byte read
-Done:   rts
-
 ;------------------------------------------------------------------------------
 ; RelocSeg: Relocate the segment pointed to by a/x
 
@@ -263,8 +254,8 @@ Loop:   jsr     ReadByte                ; Read byte from relocation table
 @L2:    jsr     ReadByte
         and     #O65_SEGID_MASK
         jsr     GetReloc
-        sta     ptr1
-        stx     ptr1+1
+        sta     RelocVal
+        stx     RelocVal+1
 
 ; Get the relocation byte again, this time extract the relocation type.
 
@@ -285,10 +276,8 @@ Loop:   jsr     ReadByte                ; Read byte from relocation table
 RelocLow:
         ldy     #0
         clc
-        lda     (TPtr),y
-        adc     ptr1
-        sta     (TPtr),y
-        jmp     Loop
+        lda     RelocVal
+        bcc     AddCommon
 
 ; Relocate a high byte
 
@@ -296,9 +285,11 @@ RelocHigh:
         jsr     ReadByte                ; Read low byte from relocation table
         ldy     #0
         clc
-        adc     ptr1                    ; We just need the carry
-AddHigh:lda     (TPtr),y
-        adc     ptr1+1
+        adc     RelocVal                ; We just need the carry
+AddHigh:
+        lda     RelocVal+1
+AddCommon:
+        adc     (TPtr),y
         sta     (TPtr),y
         jmp     Loop                    ; Done, next entry
 
@@ -307,8 +298,8 @@ AddHigh:lda     (TPtr),y
 RelocWord:
         ldy     #0
         clc
-        lda     (TPtr),y
-        adc     ptr1
+        lda     RelocVal
+        adc     (TPtr),y
         sta     (TPtr),y
         iny
         bne     AddHigh                 ; Branch always (add high byte)
@@ -344,144 +335,173 @@ _mod_load:
 ; Get the read function pointer from the control structure and place it into
 ; our call vector
 
-        ldy     #MODCTRL_READ+1
-        jsr     LoadCtrl
+        ldy     #MOD_CTRL::READ
+        lda     (Ctrl),y
         sta     Read+1
-        stx     Read+2
+        iny
+        lda     (Ctrl),y
+        sta     Read+2
 
-; Read the o65 header: C->read (C, &H, sizeof (H))
+; Read the o65 header: C->read (C->callerdata, &H, sizeof (H))
 
-        jsr     PushCtrl
+        jsr     PushCallerData
         lda     #<Header
         ldx     #>Header
         jsr     pushax
-        lda     #O65_HDR_SIZE
-        jsr     pusha0                  ; Always less than 256
+        lda     #.sizeof(O65_HDR)
+        ldx     #0                      ; Always less than 256
         jsr     ReadAndCheckError       ; Bails out in case of errors
 
 ; We read the o65 header successfully. Validate it.
 
         ldy     #ExpectedHdrSize-1
-@L3:    lda     Header,y
+ValidateHeader:
+        lda     Header,y
         cmp     ExpectedHdr,y
-        beq     @L4
-        lda     #MLOAD_ERR_HDR
-        jmp     CleanupAndExit
-@L4:    dey
-        bpl     @L3
+        bne     HeaderError
+        dey
+        bpl     ValidateHeader
 
-; Header is ok as far as we can say now. Read and skip all options. We may
-; add a check here for the OS option later.
+; Header is ok as far as we can say now. Read all options, check for the
+; OS option and ignore all others. The OS option contains a version number
+; and the module id as additional data.
 
-Opt:    jsr     ReadByte
+        iny                             ; Y = $00
+        sty     TPtr+1                  ; Flag for OS option read
+Opt:    jsr     ReadByte                ; Read the length byte
         beq     OptDone                 ; Jump if done
         sta     TPtr                    ; Use TPtr as a counter
-OneOpt: dec     TPtr
+
+; An option has a length of at least 2 bytes
+
+        cmp     #2
+        bcc     HeaderError             ; Must be 2 bytes total at least
+
+; Check for the OS option
+
+        dec     TPtr
+        jsr     ReadByte                ; Get the option type
+        cmp     #O65_OPT_OS             ; OS option?
+        bne     SkipOpt                 ; No: Skip
+
+        lda     TPtr                    ; Get remaining length+1
+        cmp     #5                      ; CC65 has 6 bytes total
+        bne     OSError
+
+        jsr     ReadByte                ; Get the operating system
+        cmp     #O65_OS_CC65
+        bne     OSError                 ; Wrong operating system
+
+        jsr     ReadByte                ; Get the version number, expect zero
+        bne     OSError                 ; Wrong version
+
+        jsr     ReadByte                ; Get low byte of id
+        ldy     #MOD_CTRL::MODULE_ID
+        sta     (Ctrl),y
+        jsr     ReadByte
+        ldy     #MOD_CTRL::MODULE_ID+1
+        sta     (Ctrl),y
+
+        inc     TPtr+1                  ; Remember that we got the OS
+
+        jmp     Opt
+
+; Skip one option
+
+SkipOpt:
+        dec     TPtr
         beq     Opt                     ; Next option
         jsr     ReadByte                ; Skip one byte
-        jmp     OneOpt
+        jmp     SkipOpt
+
+; Operating system error
+
+OSError:
+        lda     #MLOAD_ERR_OS
+        jmp     CleanupAndExit
+
+; Options done, check that we got the OS option
+
 OptDone:
+        lda     TPtr+1
+        bne     CalcSizes
+
+; Entry point for header errors
+
+HeaderError:
+        lda     #MLOAD_ERR_HDR
+        jmp     CleanupAndExit
 
 ; Skipped all options. Calculate the size of text+data and of text+data+bss
 ; (the latter is the size of the memory block we need). We will store the
 ; total module size also into the control structure for evaluation by the
 ; caller
 
-        lda     Header + O65_HDR_TLEN
-        add     Header + O65_HDR_DLEN
+CalcSizes:
+        lda     Header + O65_HDR::TLEN
+        add     Header + O65_HDR::DLEN
         sta     TPtr
-        lda     Header + O65_HDR_TLEN + 1
-        adc     Header + O65_HDR_DLEN + 1
+        lda     Header + O65_HDR::TLEN + 1
+        adc     Header + O65_HDR::DLEN + 1
         sta     TPtr+1
         lda     TPtr
-        add     Header + O65_HDR_BLEN
+        add     Header + O65_HDR::BLEN
         pha                             ; Save low byte of total size
-        ldy     #MODCTRL_MODULE_SIZE
+        ldy     #MOD_CTRL::MODULE_SIZE
         sta     (Ctrl),y
         lda     TPtr+1
-        adc     Header + O65_HDR_BLEN + 1
+        adc     Header + O65_HDR::BLEN + 1
         iny
         sta     (Ctrl),y
         tax
         pla                             ; Restore low byte of total size
 
-; Total memory size is now in a/x. Allocate memory, check if we got it.
+; Total memory size is now in a/x. Allocate memory and remember the result,
+; both, locally and in the control structure so it the caller can access
+; the memory block. After that, check if we got the requested memory.
 
         jsr     _malloc
         sta     Module
         stx     Module+1
-        ora     Module+1
-        bne     GotMem
 
-; Could not allocate memory
-
-        lda     #MLOAD_ERR_MEM
-        jmp     CleanupAndExit
-
-; We got the memory block. Setup the pointers and sizes in the control
-; structure. We will use internal knowlege about the layout of the structure
-; here to save some code.
-
-GotMem: lda     Module                  ; Ctrl->module = Module;
-        ldy     #MODCTRL_MODULE
-        sta     (Ctrl),y
-        ldy     #MODCTRL_CODE           ; Ctrl->code = Module;
+        ldy     #MOD_CTRL::MODULE
         sta     (Ctrl),y
         txa
         iny
-        sta     (Ctrl),y                ; MODCTRL_CODE+1
-        ldy     #MODCTRL_MODULE+1
         sta     (Ctrl),y
+        ora     Module
+        bne     GotMem
 
-; The following loop will also copy some information that is not needed just
-; to save some code.
+; Could not allocate memory
 
-        ldx     #O65_HDR_TLEN
-        ldy     #MODCTRL_CODE_SIZE
-CLoop:  lda     Header,x
-        sta     (Ctrl),y
-        inx
-        iny
-        cpy     #MODCTRL_SIZE
-        bne     CLoop
+        lda     #MLOAD_ERR_MEM
+        jmp     CleanupAndExit
 
-; Missing in the control structure now: start of the data and bss segments.
-; Since the linker relocates all segments to zero, these addresses are also
-; the relocation values for the segments.
+; Control structure is complete now. Clear the bss segment.
+; bzero (bss_addr, bss_size)
 
-        ldy     #MODCTRL_DATA
-        lda     Module
-        add     Header + O65_HDR_TLEN
-        sta     (Ctrl),y
-        sta     DataReloc
-        iny
-        lda     Module + 1
-        adc     Header + O65_HDR_TLEN + 1
-        sta     (Ctrl),y
-        sta     DataReloc + 1
-
-        ldy     #MODCTRL_BSS
-        lda     Module
+GotMem: lda     Module
         add     TPtr
-        sta     (Ctrl),y
-        sta     BssReloc
-        iny
+        pha
         lda     Module+1
-        add     TPtr+1
-        sta     (Ctrl),y
-        sta     BssReloc + 1
+        adc     TPtr+1                  ; Module + tlen + dlen
+        tax
+        pla
+        jsr     pushax
+        lda     Header + O65_HDR::BLEN
+        ldx     Header + O65_HDR::BLEN+1
+        jsr     _bzero                  ; bzero (bss, bss_size);
 
-; Control structure is complete now. Load code and data segment into memory.
-; The sum of the sizes of code+data segment is still in TPtr.
-; C->read (C, C->module, H.tlen + H.dlen)
+; Load code and data segment into memory. The sum of the sizes of
+; code+data segment is still in TPtr.
+; C->read (C->callerdata, C->module, H.tlen + H.dlen)
 
-        jsr     PushCtrl
+        jsr     PushCallerData
         lda     Module
         ldx     Module+1
         jsr     pushax
         lda     TPtr
         ldx     TPtr+1
-        jsr     pushax
         jsr     ReadAndCheckError       ; Bails out in case of errors
 
 ; We've got the code and data segments in memory. Next section contains
@@ -494,8 +514,8 @@ CLoop:  lda     Header,x
         beq     Reloc
 Undef:  jmp     FormatError
 
-; Number of undefined references was zero. Next sections are the relocation
-; tables for code and data segment. Relocate the code segment
+; Number of undefined references was zero. Next come the relocation tables
+; for code and data segment. Relocate the code segment
 
 Reloc:  lda     Module
         ldx     Module + 1              ; Code segment address
@@ -503,20 +523,15 @@ Reloc:  lda     Module
 
 ; Relocate the data segment
 
-        ldy     #MODCTRL_DATA + 1
-        jsr     LoadCtrl                ; Get data segment address
+        lda     Module
+        add     Header + O65_HDR::TLEN
+        pha
+        lda     Module + 1
+        adc     Header + O65_HDR::TLEN + 1
+        tax
+        pla                             ; Data segment address in a/x
         jsr     RelocSeg
 
-; Clear the bss segment
-
-        ldy     #MODCTRL_BSS + 1
-        jsr     LoadCtrl                ; Load bss segment address
-        jsr     pushax
-        jsr     push0
-        lda     Header + O65_HDR_BLEN
-        ldx     Header + O65_HDR_BLEN+1
-        jsr     _memset                 ; memset (bss, 0, bss_size);
-
 ; We're done. Restore the register bank and return a success code
 
         jsr     RestoreRegBank          ; X will be zero on return