first steps to add C128 compiler target

This commit is contained in:
Irmen de Jong 2021-12-21 19:08:33 +01:00
parent 7bccfc0006
commit 6da83e2bd7
17 changed files with 1607 additions and 76 deletions

View File

@ -0,0 +1,42 @@
package prog8.compiler.target
import com.github.michaelbull.result.fold
import prog8.ast.base.*
import prog8.ast.expressions.Expression
import prog8.ast.statements.RegisterOrStatusflag
import prog8.ast.statements.Subroutine
import prog8.compiler.target.c128.C128MachineDefinition
import prog8.compiler.target.cbm.Petscii
import prog8.compiler.target.cpu6502.codegen.asmsub6502ArgsEvalOrder
import prog8.compiler.target.cpu6502.codegen.asmsub6502ArgsHaveRegisterClobberRisk
import prog8.compilerinterface.ICompilationTarget
object C128Target: ICompilationTarget {
override val name = "c128"
override val machine = C128MachineDefinition()
override fun encodeString(str: String, altEncoding: Boolean): List<UByte> {
val coded = if (altEncoding) Petscii.encodeScreencode(str, true) else Petscii.encodePetscii(str, true)
return coded.fold(
failure = { throw it },
success = { it }
)
}
override fun decodeString(bytes: List<UByte>, altEncoding: Boolean) =
if (altEncoding) Petscii.decodeScreencode(bytes, true) else Petscii.decodePetscii(bytes, true)
override fun asmsubArgsEvalOrder(sub: Subroutine): List<Int> =
asmsub6502ArgsEvalOrder(sub)
override fun asmsubArgsHaveRegisterClobberRisk(args: List<Expression>, paramRegisters: List<RegisterOrStatusflag>) =
asmsub6502ArgsHaveRegisterClobberRisk(args, paramRegisters)
override fun memorySize(dt: DataType): Int {
return when(dt) {
in ByteDatatypes -> 1
in WordDatatypes -> 2
DataType.FLOAT -> machine.FLOAT_MEM_SIZE
in PassByReferenceDatatypes -> machine.POINTER_MEM_SIZE
else -> Int.MIN_VALUE
}
}
}

View File

@ -0,0 +1,68 @@
package prog8.compiler.target.c128
import prog8.ast.base.DataType
import prog8.compiler.target.c64.normal6502instructions
import prog8.compiler.target.cbm.Mflpt5
import prog8.compiler.target.cbm.viceMonListPostfix
import prog8.compilerinterface.*
import java.io.IOException
import java.nio.file.Path
class C128MachineDefinition: IMachineDefinition {
override val cpu = CpuType.CPU6502
override val FLOAT_MAX_POSITIVE = Mflpt5.FLOAT_MAX_POSITIVE
override val FLOAT_MAX_NEGATIVE = Mflpt5.FLOAT_MAX_NEGATIVE
override val FLOAT_MEM_SIZE = Mflpt5.FLOAT_MEM_SIZE
override val POINTER_MEM_SIZE = 2
override val BASIC_LOAD_ADDRESS = 0x1c01u // TODO c128 address
override val RAW_LOAD_ADDRESS = 0xc000u // TODO c128 address
// the 2*256 byte evaluation stack (on which bytes, words, and even floats are stored during calculations)
override val ESTACK_LO = 0xce00u // $ce00-$ceff inclusive // TODO c128 address
override val ESTACK_HI = 0xcf00u // $ce00-$ceff inclusive // TODO c128 address
override lateinit var zeropage: Zeropage
override fun getFloat(num: Number) = Mflpt5.fromNumber(num)
override fun importLibs(compilerOptions: CompilationOptions, compilationTargetName: String): List<String> {
return if (compilerOptions.launcher == LauncherType.BASIC || compilerOptions.output == OutputType.PRG)
listOf("syslib")
else
emptyList()
}
override fun launchEmulator(selectedEmulator: Int, programNameWithPath: Path) {
if(selectedEmulator!=1) {
System.err.println("The c128 target only supports the main emulator (Vice).")
return
}
for(emulator in listOf("x128")) {
println("\nStarting C-128 emulator $emulator...")
val cmdline = listOf(emulator, "-silent", "-moncommands", "${programNameWithPath}.$viceMonListPostfix",
"-autostartprgmode", "1", "-autostart-warp", "-autostart", "${programNameWithPath}.prg")
val processb = ProcessBuilder(cmdline).inheritIO()
val process: Process
try {
process=processb.start()
} catch(x: IOException) {
continue // try the next emulator executable
}
process.waitFor()
break
}
}
override fun isIOAddress(address: UInt): Boolean = address==0u || address==1u || address in 0xd000u..0xdfffu // TODO c128 address
override fun getPreallocatedZeropageVars(): Map<String, Pair<UInt, DataType>> = emptyMap()
override fun initializeZeropage(compilerOptions: CompilationOptions) {
zeropage = C128Zeropage(compilerOptions)
}
override val opcodeNames = normal6502instructions
}

View File

@ -0,0 +1,74 @@
package prog8.compiler.target.c128
import prog8.compilerinterface.CompilationOptions
import prog8.compilerinterface.InternalCompilerException
import prog8.compilerinterface.Zeropage
import prog8.compilerinterface.ZeropageType
class C128Zeropage(options: CompilationOptions) : Zeropage(options) {
override val SCRATCH_B1 = 0x80u // temp storage for a single byte // TODO c128 address
override val SCRATCH_REG = 0x81u // temp storage for a register, must be B1+1 // TODO c128 address
override val SCRATCH_W1 = 0xfbu // temp storage 1 for a word $fb+$fc
override val SCRATCH_W2 = 0xfdu // temp storage 2 for a word $fd+$fe
init {
if (options.floats && options.zeropage !in arrayOf(
ZeropageType.FLOATSAFE,
ZeropageType.BASICSAFE,
ZeropageType.DONTUSE
))
throw InternalCompilerException("when floats are enabled, zero page type should be 'floatsafe' or 'basicsafe' or 'dontuse'")
// TODO c128 address : build the lists of free ZP locations for the various configurations
if (options.zeropage == ZeropageType.FULL) {
free.addAll(0x09u..0xffu)
free.removeAll(setOf(SCRATCH_B1, SCRATCH_REG, SCRATCH_W1, SCRATCH_W1+1u, SCRATCH_W2, SCRATCH_W2+1u))
free.removeAll(setOf(0xa0u, 0xa1u, 0xa2u, 0x91u, 0xc0u, 0xc5u, 0xcbu, 0xf5u, 0xf6u)) // these are updated by IRQ
} else {
if (options.zeropage == ZeropageType.KERNALSAFE || options.zeropage == ZeropageType.FLOATSAFE) {
free.addAll(listOf(
0x09, 0x0a, 0x0b, 0x0c, 0x0d, 0x0e, 0x0f, 0x10, 0x11,
0x16, 0x17, 0x18, 0x19, 0x1a,
0x1b, 0x1c, 0x1d, 0x1e, 0x1f, 0x20, 0x21,
0x22, 0x23, 0x24, 0x25,
0x39, 0x3a, 0x3b, 0x3c, 0x3d, 0x3e, 0x3f, 0x40, 0x41, 0x42, 0x43, 0x44, 0x45, 0x46,
0x47, 0x48, 0x4b, 0x4c, 0x4d, 0x4e, 0x4f, 0x51, 0x52, 0x53,
0x57, 0x58, 0x59, 0x5a, 0x5b, 0x5c, 0x5d, 0x5e, 0x5f, 0x60,
0x61, 0x62, 0x63, 0x64, 0x65, 0x66, 0x67, 0x68,
0x69, 0x6a, 0x6b, 0x6c, 0x6d, 0x6e, 0x6f, 0x70, 0x71, 0x72,
0x73, 0x74, 0x75, 0x76, 0x77, 0x78, 0x79, 0x7a, 0x7b, 0x7c,
0x7d, 0x7e, 0x7f, 0x80, 0x81, 0x82, 0x83, 0x84, 0x85, 0x86, 0x87, 0x88, 0x89, 0x8a,
0x8b, 0x8c, 0x8d, 0x8e, 0x8f, 0xff
// 0x90-0xfa is 'kernal work storage area'
).map{it.toUInt()})
}
if (options.zeropage == ZeropageType.FLOATSAFE) {
// remove the zeropage locations used for floating point operations from the free list
free.removeAll(listOf(
0x22, 0x23, 0x24, 0x25,
0x10, 0x11, 0x12, 0x26, 0x27, 0x28, 0x29, 0x2a,
0x57, 0x58, 0x59, 0x5a, 0x5b, 0x5c, 0x5d, 0x5e, 0x5f, 0x60,
0x61, 0x62, 0x63, 0x64, 0x65, 0x66, 0x67, 0x68,
0x69, 0x6a, 0x6b, 0x6c, 0x6d, 0x6e, 0x6f, 0x70, 0x71, 0x72,
0x8b, 0x8c, 0x8d, 0x8e, 0x8f, 0xff
).map{it.toUInt()})
}
if(options.zeropage!= ZeropageType.DONTUSE) {
// add the free Zp addresses
// these are valid for the C-64 but allow BASIC to keep running fully *as long as you don't use tape I/O*
free.addAll(listOf(0x04, 0x05, 0x06, 0x0a, 0x0e,
0x92, 0x96, 0x9b, 0x9c, 0x9e, 0x9f, 0xa5, 0xa6,
0xb0, 0xb1, 0xbe, 0xbf, 0xf9).map{it.toUInt()})
} else {
// don't use the zeropage at all
free.clear()
}
}
removeReservedFromFreePool()
}
}

View File

@ -63,16 +63,18 @@ class C64MachineDefinition: IMachineDefinition {
zeropage = C64Zeropage(compilerOptions)
}
// 6502 opcodes (including aliases and illegal opcodes), these cannot be used as variable or label names
override val opcodeNames = setOf("adc", "ahx", "alr", "anc", "and", "ane", "arr", "asl", "asr", "axs", "bcc", "bcs",
"beq", "bge", "bit", "blt", "bmi", "bne", "bpl", "brk", "bvc", "bvs", "clc",
"cld", "cli", "clv", "cmp", "cpx", "cpy", "dcm", "dcp", "dec", "dex", "dey",
"eor", "gcc", "gcs", "geq", "gge", "glt", "gmi", "gne", "gpl", "gvc", "gvs",
"inc", "ins", "inx", "iny", "isb", "isc", "jam", "jmp", "jsr", "lae", "las",
"lax", "lda", "lds", "ldx", "ldy", "lsr", "lxa", "nop", "ora", "pha", "php",
"pla", "plp", "rla", "rol", "ror", "rra", "rti", "rts", "sax", "sbc", "sbx",
"sec", "sed", "sei", "sha", "shl", "shr", "shs", "shx", "shy", "slo", "sre",
"sta", "stx", "sty", "tas", "tax", "tay", "tsx", "txa", "txs", "tya", "xaa")
override val opcodeNames = normal6502instructions
}
// 6502 opcodes (including aliases and illegal opcodes), these cannot be used as variable or label names
internal val normal6502instructions = setOf(
"adc", "ahx", "alr", "anc", "and", "ane", "arr", "asl", "asr", "axs", "bcc", "bcs",
"beq", "bge", "bit", "blt", "bmi", "bne", "bpl", "brk", "bvc", "bvs", "clc",
"cld", "cli", "clv", "cmp", "cpx", "cpy", "dcm", "dcp", "dec", "dex", "dey",
"eor", "gcc", "gcs", "geq", "gge", "glt", "gmi", "gne", "gpl", "gvc", "gvs",
"inc", "ins", "inx", "iny", "isb", "isc", "jam", "jmp", "jsr", "lae", "las",
"lax", "lda", "lds", "ldx", "ldy", "lsr", "lxa", "nop", "ora", "pha", "php",
"pla", "plp", "rla", "rol", "ror", "rra", "rti", "rts", "sax", "sbc", "sbx",
"sec", "sed", "sei", "sha", "shl", "shr", "shs", "shx", "shy", "slo", "sre",
"sta", "stx", "sty", "tas", "tax", "tay", "tsx", "txa", "txs", "tya", "xaa")

View File

@ -10,7 +10,7 @@ class C64Zeropage(options: CompilationOptions) : Zeropage(options) {
override val SCRATCH_B1 = 0x02u // temp storage for a single byte
override val SCRATCH_REG = 0x03u // temp storage for a register, must be B1+1
override val SCRATCH_W1 = 0xfbu // temp storage 1 for a word $fb+$fc
override val SCRATCH_W2 = 0xfdu // temp storage 2 for a word $fb+$fc
override val SCRATCH_W2 = 0xfdu // temp storage 2 for a word $fd+$fe
init {
@ -22,8 +22,8 @@ class C64Zeropage(options: CompilationOptions) : Zeropage(options) {
throw InternalCompilerException("when floats are enabled, zero page type should be 'floatsafe' or 'basicsafe' or 'dontuse'")
if (options.zeropage == ZeropageType.FULL) {
free.addAll(0x04u..0xf9u)
free.add(0xffu)
free.addAll(0x02u..0xffu)
free.removeAll(setOf(SCRATCH_B1, SCRATCH_REG, SCRATCH_W1, SCRATCH_W1+1u, SCRATCH_W2, SCRATCH_W2+1u))
free.removeAll(setOf(0xa0u, 0xa1u, 0xa2u, 0x91u, 0xc0u, 0xc5u, 0xcbu, 0xf5u, 0xf6u)) // these are updated by IRQ
} else {
if (options.zeropage == ZeropageType.KERNALSAFE || options.zeropage == ZeropageType.FLOATSAFE) {

View File

@ -137,8 +137,8 @@ class AsmGen(private val program: Program,
when {
options.launcher == LauncherType.BASIC -> {
if (program.actualLoadAddress != 0x0801u)
throw AssemblyError("BASIC output must have load address $0801")
if (program.actualLoadAddress != options.compTarget.machine.BASIC_LOAD_ADDRESS)
throw AssemblyError("BASIC output must have correct load address")
out("; ---- basic program with sys call ----")
out("* = ${program.actualLoadAddress.toHex()}")
val year = LocalDate.now().year

View File

@ -0,0 +1,767 @@
; Prog8 definitions for the Commodore-128
; Including memory registers, I/O registers, Basic and Kernal subroutines.
;
; Written by Irmen de Jong (irmen@razorvine.net) - license: GNU GPL 3.0
;
; indent format: TABS, size=8
;
c64 {
; ---- kernal routines, these are the same as on the Commodore-64 (hence the same block name) ----
; // TODO c128 address : are these really the same?
romsub $AB1E = STROUT(uword strptr @ AY) clobbers(A, X, Y) ; print null-terminated string (use txt.print instead)
romsub $E544 = CLEARSCR() clobbers(A,X,Y) ; clear the screen
romsub $E566 = HOMECRSR() clobbers(A,X,Y) ; cursor to top left of screen
romsub $EA31 = IRQDFRT() clobbers(A,X,Y) ; default IRQ routine
romsub $EA81 = IRQDFEND() clobbers(A,X,Y) ; default IRQ end/cleanup
romsub $FF81 = CINT() clobbers(A,X,Y) ; (alias: SCINIT) initialize screen editor and video chip
romsub $FF84 = IOINIT() clobbers(A, X) ; initialize I/O devices (CIA, SID, IRQ)
romsub $FF87 = RAMTAS() clobbers(A,X,Y) ; initialize RAM, tape buffer, screen
romsub $FF8A = RESTOR() clobbers(A,X,Y) ; restore default I/O vectors
romsub $FF8D = VECTOR(uword userptr @ XY, ubyte dir @ Pc) clobbers(A,Y) ; read/set I/O vector table
romsub $FF90 = SETMSG(ubyte value @ A) ; set Kernal message control flag
romsub $FF93 = SECOND(ubyte address @ A) clobbers(A) ; (alias: LSTNSA) send secondary address after LISTEN
romsub $FF96 = TKSA(ubyte address @ A) clobbers(A) ; (alias: TALKSA) send secondary address after TALK
romsub $FF99 = MEMTOP(uword address @ XY, ubyte dir @ Pc) -> uword @ XY ; read/set top of memory pointer
romsub $FF9C = MEMBOT(uword address @ XY, ubyte dir @ Pc) -> uword @ XY ; read/set bottom of memory pointer
romsub $FF9F = SCNKEY() clobbers(A,X,Y) ; scan the keyboard
romsub $FFA2 = SETTMO(ubyte timeout @ A) ; set time-out flag for IEEE bus
romsub $FFA5 = ACPTR() -> ubyte @ A ; (alias: IECIN) input byte from serial bus
romsub $FFA8 = CIOUT(ubyte databyte @ A) ; (alias: IECOUT) output byte to serial bus
romsub $FFAB = UNTLK() clobbers(A) ; command serial bus device to UNTALK
romsub $FFAE = UNLSN() clobbers(A) ; command serial bus device to UNLISTEN
romsub $FFB1 = LISTEN(ubyte device @ A) clobbers(A) ; command serial bus device to LISTEN
romsub $FFB4 = TALK(ubyte device @ A) clobbers(A) ; command serial bus device to TALK
romsub $FFB7 = READST() -> ubyte @ A ; read I/O status word
romsub $FFBA = SETLFS(ubyte logical @ A, ubyte device @ X, ubyte secondary @ Y) ; set logical file parameters
romsub $FFBD = SETNAM(ubyte namelen @ A, str filename @ XY) ; set filename parameters
romsub $FFC0 = OPEN() clobbers(X,Y) -> ubyte @Pc, ubyte @A ; (via 794 ($31A)) open a logical file
romsub $FFC3 = CLOSE(ubyte logical @ A) clobbers(A,X,Y) ; (via 796 ($31C)) close a logical file
romsub $FFC6 = CHKIN(ubyte logical @ X) clobbers(A,X) -> ubyte @Pc ; (via 798 ($31E)) define an input channel
romsub $FFC9 = CHKOUT(ubyte logical @ X) clobbers(A,X) ; (via 800 ($320)) define an output channel
romsub $FFCC = CLRCHN() clobbers(A,X) ; (via 802 ($322)) restore default devices
romsub $FFCF = CHRIN() clobbers(X, Y) -> ubyte @ A ; (via 804 ($324)) input a character (for keyboard, read a whole line from the screen) A=byte read.
romsub $FFD2 = CHROUT(ubyte char @ A) ; (via 806 ($326)) output a character
romsub $FFD5 = LOAD(ubyte verify @ A, uword address @ XY) -> ubyte @Pc, ubyte @ A, uword @ XY ; (via 816 ($330)) load from device
romsub $FFD8 = SAVE(ubyte zp_startaddr @ A, uword endaddr @ XY) -> ubyte @ Pc, ubyte @ A ; (via 818 ($332)) save to a device
romsub $FFDB = SETTIM(ubyte low @ A, ubyte middle @ X, ubyte high @ Y) ; set the software clock
romsub $FFDE = RDTIM() -> ubyte @ A, ubyte @ X, ubyte @ Y ; read the software clock (A=lo,X=mid,Y=high)
romsub $FFE1 = STOP() clobbers(X) -> ubyte @ Pz, ubyte @ A ; (via 808 ($328)) check the STOP key (and some others in A)
romsub $FFE4 = GETIN() clobbers(X,Y) -> ubyte @Pc, ubyte @ A ; (via 810 ($32A)) get a character
romsub $FFE7 = CLALL() clobbers(A,X) ; (via 812 ($32C)) close all files
romsub $FFEA = UDTIM() clobbers(A,X) ; update the software clock
romsub $FFED = SCREEN() -> ubyte @ X, ubyte @ Y ; read number of screen rows and columns
romsub $FFF0 = PLOT(ubyte col @ Y, ubyte row @ X, ubyte dir @ Pc) -> ubyte @ X, ubyte @ Y ; read/set position of cursor on screen. Use txt.plot for a 'safe' wrapper that preserves X.
romsub $FFF3 = IOBASE() -> uword @ XY ; read base address of I/O devices
; ---- end of C64 ROM kernal routines ----
; ---- utilities -----
asmsub STOP2() -> ubyte @A {
; -- check if STOP key was pressed, returns true if so. More convenient to use than STOP() because that only sets the carry status flag.
%asm {{
txa
pha
jsr c64.STOP
beq +
pla
tax
lda #0
rts
+ pla
tax
lda #1
rts
}}
}
asmsub RDTIM16() -> uword @AY {
; -- like RDTIM() but only returning the lower 16 bits in AY for convenience
%asm {{
stx P8ZP_SCRATCH_REG
jsr c64.RDTIM
pha
txa
tay
pla
ldx P8ZP_SCRATCH_REG
rts
}}
}
}
c128 {
; TODO c128 address : if these are the same as on the c64, just use block name 'c64' instead of 'c128'
&ubyte TIME_HI = $a0 ; software jiffy clock, hi byte
&ubyte TIME_MID = $a1 ; .. mid byte
&ubyte TIME_LO = $a2 ; .. lo byte. Updated by IRQ every 1/60 sec
&ubyte STATUS = $90 ; kernal status variable for I/O
&ubyte STKEY = $91 ; various keyboard statuses (updated by IRQ)
&ubyte SFDX = $cb ; current key pressed (matrix value) (updated by IRQ)
&ubyte COLOR = $0286 ; cursor color
&ubyte HIBASE = $0288 ; screen base address / 256 (hi-byte of screen memory address)
&uword CINV = $0314 ; IRQ vector (in ram)
&uword CBINV = $0316 ; BRK vector (in ram)
&uword NMINV = $0318 ; NMI vector (in ram)
&uword NMI_VEC = $FFFA ; 6502 nmi vector, determined by the kernal if banked in
&uword RESET_VEC = $FFFC ; 6502 reset vector, determined by the kernal if banked in
&uword IRQ_VEC = $FFFE ; 6502 interrupt vector, determined by the kernal if banked in
; the default addresses for the character screen chars and colors
const uword Screen = $0400 ; to have this as an array[40*25] the compiler would have to support array size > 255
const uword Colors = $d800 ; to have this as an array[40*25] the compiler would have to support array size > 255
; the default locations of the 8 sprite pointers (store address of sprite / 64)
&ubyte SPRPTR0 = 2040
&ubyte SPRPTR1 = 2041
&ubyte SPRPTR2 = 2042
&ubyte SPRPTR3 = 2043
&ubyte SPRPTR4 = 2044
&ubyte SPRPTR5 = 2045
&ubyte SPRPTR6 = 2046
&ubyte SPRPTR7 = 2047
&ubyte[8] SPRPTR = 2040 ; the 8 sprite pointers as an array.
; ---- VIC-II 6567/6569/856x registers ----
&ubyte SP0X = $d000
&ubyte SP0Y = $d001
&ubyte SP1X = $d002
&ubyte SP1Y = $d003
&ubyte SP2X = $d004
&ubyte SP2Y = $d005
&ubyte SP3X = $d006
&ubyte SP3Y = $d007
&ubyte SP4X = $d008
&ubyte SP4Y = $d009
&ubyte SP5X = $d00a
&ubyte SP5Y = $d00b
&ubyte SP6X = $d00c
&ubyte SP6Y = $d00d
&ubyte SP7X = $d00e
&ubyte SP7Y = $d00f
&ubyte[16] SPXY = $d000 ; the 8 sprite X and Y registers as an array.
&uword[8] SPXYW = $d000 ; the 8 sprite X and Y registers as a combined xy word array.
&ubyte MSIGX = $d010
&ubyte SCROLY = $d011
&ubyte RASTER = $d012
&ubyte LPENX = $d013
&ubyte LPENY = $d014
&ubyte SPENA = $d015
&ubyte SCROLX = $d016
&ubyte YXPAND = $d017
&ubyte VMCSB = $d018
&ubyte VICIRQ = $d019
&ubyte IREQMASK = $d01a
&ubyte SPBGPR = $d01b
&ubyte SPMC = $d01c
&ubyte XXPAND = $d01d
&ubyte SPSPCL = $d01e
&ubyte SPBGCL = $d01f
&ubyte EXTCOL = $d020 ; border color
&ubyte BGCOL0 = $d021 ; screen color
&ubyte BGCOL1 = $d022
&ubyte BGCOL2 = $d023
&ubyte BGCOL4 = $d024
&ubyte SPMC0 = $d025
&ubyte SPMC1 = $d026
&ubyte SP0COL = $d027
&ubyte SP1COL = $d028
&ubyte SP2COL = $d029
&ubyte SP3COL = $d02a
&ubyte SP4COL = $d02b
&ubyte SP5COL = $d02c
&ubyte SP6COL = $d02d
&ubyte SP7COL = $d02e
&ubyte[8] SPCOL = $d027
; ---- end of VIC-II registers ----
; ---- CIA 6526 1 & 2 registers ----
&ubyte CIA1PRA = $DC00 ; CIA 1 DRA, keyboard column drive (and joystick control port #2)
&ubyte CIA1PRB = $DC01 ; CIA 1 DRB, keyboard row port (and joystick control port #1)
&ubyte CIA1DDRA = $DC02 ; CIA 1 DDRA, keyboard column
&ubyte CIA1DDRB = $DC03 ; CIA 1 DDRB, keyboard row
&ubyte CIA1TAL = $DC04 ; CIA 1 timer A low byte
&ubyte CIA1TAH = $DC05 ; CIA 1 timer A high byte
&ubyte CIA1TBL = $DC06 ; CIA 1 timer B low byte
&ubyte CIA1TBH = $DC07 ; CIA 1 timer B high byte
&ubyte CIA1TOD10 = $DC08 ; time of day, 1/10 sec.
&ubyte CIA1TODSEC = $DC09 ; time of day, seconds
&ubyte CIA1TODMMIN = $DC0A ; time of day, minutes
&ubyte CIA1TODHR = $DC0B ; time of day, hours
&ubyte CIA1SDR = $DC0C ; Serial Data Register
&ubyte CIA1ICR = $DC0D
&ubyte CIA1CRA = $DC0E
&ubyte CIA1CRB = $DC0F
&ubyte CIA2PRA = $DD00 ; CIA 2 DRA, serial port and video address
&ubyte CIA2PRB = $DD01 ; CIA 2 DRB, RS232 port / USERPORT
&ubyte CIA2DDRA = $DD02 ; CIA 2 DDRA, serial port and video address
&ubyte CIA2DDRB = $DD03 ; CIA 2 DDRB, RS232 port / USERPORT
&ubyte CIA2TAL = $DD04 ; CIA 2 timer A low byte
&ubyte CIA2TAH = $DD05 ; CIA 2 timer A high byte
&ubyte CIA2TBL = $DD06 ; CIA 2 timer B low byte
&ubyte CIA2TBH = $DD07 ; CIA 2 timer B high byte
&ubyte CIA2TOD10 = $DD08 ; time of day, 1/10 sec.
&ubyte CIA2TODSEC = $DD09 ; time of day, seconds
&ubyte CIA2TODMIN = $DD0A ; time of day, minutes
&ubyte CIA2TODHR = $DD0B ; time of day, hours
&ubyte CIA2SDR = $DD0C ; Serial Data Register
&ubyte CIA2ICR = $DD0D
&ubyte CIA2CRA = $DD0E
&ubyte CIA2CRB = $DD0F
; ---- end of CIA registers ----
; ---- SID 6581/8580 registers ----
&ubyte FREQLO1 = $D400 ; channel 1 freq lo
&ubyte FREQHI1 = $D401 ; channel 1 freq hi
&uword FREQ1 = $D400 ; channel 1 freq (word)
&ubyte PWLO1 = $D402 ; channel 1 pulse width lo (7-0)
&ubyte PWHI1 = $D403 ; channel 1 pulse width hi (11-8)
&uword PW1 = $D402 ; channel 1 pulse width (word)
&ubyte CR1 = $D404 ; channel 1 voice control register
&ubyte AD1 = $D405 ; channel 1 attack & decay
&ubyte SR1 = $D406 ; channel 1 sustain & release
&ubyte FREQLO2 = $D407 ; channel 2 freq lo
&ubyte FREQHI2 = $D408 ; channel 2 freq hi
&uword FREQ2 = $D407 ; channel 2 freq (word)
&ubyte PWLO2 = $D409 ; channel 2 pulse width lo (7-0)
&ubyte PWHI2 = $D40A ; channel 2 pulse width hi (11-8)
&uword PW2 = $D409 ; channel 2 pulse width (word)
&ubyte CR2 = $D40B ; channel 2 voice control register
&ubyte AD2 = $D40C ; channel 2 attack & decay
&ubyte SR2 = $D40D ; channel 2 sustain & release
&ubyte FREQLO3 = $D40E ; channel 3 freq lo
&ubyte FREQHI3 = $D40F ; channel 3 freq hi
&uword FREQ3 = $D40E ; channel 3 freq (word)
&ubyte PWLO3 = $D410 ; channel 3 pulse width lo (7-0)
&ubyte PWHI3 = $D411 ; channel 3 pulse width hi (11-8)
&uword PW3 = $D410 ; channel 3 pulse width (word)
&ubyte CR3 = $D412 ; channel 3 voice control register
&ubyte AD3 = $D413 ; channel 3 attack & decay
&ubyte SR3 = $D414 ; channel 3 sustain & release
&ubyte FCLO = $D415 ; filter cutoff lo (2-0)
&ubyte FCHI = $D416 ; filter cutoff hi (10-3)
&uword FC = $D415 ; filter cutoff (word)
&ubyte RESFILT = $D417 ; filter resonance and routing
&ubyte MVOL = $D418 ; filter mode and main volume control
&ubyte POTX = $D419 ; potentiometer X
&ubyte POTY = $D41A ; potentiometer Y
&ubyte OSC3 = $D41B ; channel 3 oscillator value read
&ubyte ENV3 = $D41C ; channel 3 envelope value read
; ---- end of SID registers ----
; ---- C128 specific system utility routines: ----
asmsub init_system() {
; Initializes the machine to a sane starting state.
; Called automatically by the loader program logic.
; This means that the BASIC, KERNAL and CHARGEN ROMs are banked in,
; the VIC, SID and CIA chips are reset, screen is cleared, and the default IRQ is set.
; Also a different color scheme is chosen to identify ourselves a little.
; Uppercase charset is activated, and all three registers set to 0, status flags cleared.
%asm {{
sei
cld
lda #%00101111
sta $00
lda #%00100111
sta $01
jsr c64.IOINIT
jsr c64.RESTOR
jsr c64.CINT
lda #6
sta c128.EXTCOL
lda #7
sta c128.COLOR
lda #0
sta c128.BGCOL0
jsr disable_runstop_and_charsetswitch
clc
clv
cli
rts
}}
}
asmsub init_system_phase2() {
%asm {{
rts ; no phase 2 steps on the C64
}}
}
asmsub disable_runstop_and_charsetswitch() clobbers(A) {
%asm {{
lda #$80
sta 657 ; disable charset switching
lda #239
sta 808 ; disable run/stop key
rts
}}
}
asmsub set_irq(uword handler @AY, ubyte useKernal @Pc) clobbers(A) {
%asm {{
sta _modified+1
sty _modified+2
lda #0
adc #0
sta _use_kernal
sei
lda #<_irq_handler
sta c64.CINV
lda #>_irq_handler
sta c64.CINV+1
cli
rts
_irq_handler jsr _irq_handler_init
_modified jsr $ffff ; modified
jsr _irq_handler_end
lda _use_kernal
bne +
lda #$ff
sta c64.VICIRQ ; acknowledge raster irq
lda c64.CIA1ICR ; acknowledge CIA1 interrupt
; end irq processing - don't use kernal's irq handling
pla
tay
pla
tax
pla
rti
+ jmp c64.IRQDFRT ; continue with normal kernal irq routine
_use_kernal .byte 0
_irq_handler_init
; save all zp scratch registers and the X register as these might be clobbered by the irq routine
stx IRQ_X_REG
lda P8ZP_SCRATCH_B1
sta IRQ_SCRATCH_ZPB1
lda P8ZP_SCRATCH_REG
sta IRQ_SCRATCH_ZPREG
lda P8ZP_SCRATCH_W1
sta IRQ_SCRATCH_ZPWORD1
lda P8ZP_SCRATCH_W1+1
sta IRQ_SCRATCH_ZPWORD1+1
lda P8ZP_SCRATCH_W2
sta IRQ_SCRATCH_ZPWORD2
lda P8ZP_SCRATCH_W2+1
sta IRQ_SCRATCH_ZPWORD2+1
; stack protector; make sure we don't clobber the top of the evaluation stack
dex
dex
dex
dex
dex
dex
cld
rts
_irq_handler_end
; restore all zp scratch registers and the X register
lda IRQ_SCRATCH_ZPB1
sta P8ZP_SCRATCH_B1
lda IRQ_SCRATCH_ZPREG
sta P8ZP_SCRATCH_REG
lda IRQ_SCRATCH_ZPWORD1
sta P8ZP_SCRATCH_W1
lda IRQ_SCRATCH_ZPWORD1+1
sta P8ZP_SCRATCH_W1+1
lda IRQ_SCRATCH_ZPWORD2
sta P8ZP_SCRATCH_W2
lda IRQ_SCRATCH_ZPWORD2+1
sta P8ZP_SCRATCH_W2+1
ldx IRQ_X_REG
rts
IRQ_X_REG .byte 0
IRQ_SCRATCH_ZPB1 .byte 0
IRQ_SCRATCH_ZPREG .byte 0
IRQ_SCRATCH_ZPWORD1 .word 0
IRQ_SCRATCH_ZPWORD2 .word 0
}}
}
asmsub restore_irq() clobbers(A) {
%asm {{
sei
lda #<c64.IRQDFRT
sta c64.CINV
lda #>c64.IRQDFRT
sta c64.CINV+1
lda #0
sta c64.IREQMASK ; disable raster irq
lda #%10000001
sta c64.CIA1ICR ; restore CIA1 irq
cli
rts
}}
}
asmsub set_rasterirq(uword handler @AY, uword rasterpos @R0, ubyte useKernal @Pc) clobbers(A) {
%asm {{
sta _modified+1
sty _modified+2
lda #0
adc #0
sta set_irq._use_kernal
lda cx16.r0
ldy cx16.r0+1
sei
jsr _setup_raster_irq
lda #<_raster_irq_handler
sta c64.CINV
lda #>_raster_irq_handler
sta c64.CINV+1
cli
rts
_raster_irq_handler
jsr set_irq._irq_handler_init
_modified jsr $ffff ; modified
jsr set_irq._irq_handler_end
lda #$ff
sta c64.VICIRQ ; acknowledge raster irq
lda set_irq._use_kernal
bne +
; end irq processing - don't use kernal's irq handling
pla
tay
pla
tax
pla
rti
+ jmp c64.IRQDFRT ; continue with kernal irq routine
_setup_raster_irq
pha
lda #%01111111
sta c64.CIA1ICR ; "switch off" interrupts signals from cia-1
sta c64.CIA2ICR ; "switch off" interrupts signals from cia-2
and c64.SCROLY
sta c64.SCROLY ; clear most significant bit of raster position
lda c64.CIA1ICR ; ack previous irq
lda c64.CIA2ICR ; ack previous irq
pla
sta c64.RASTER ; set the raster line number where interrupt should occur
cpy #0
beq +
lda c64.SCROLY
ora #%10000000
sta c64.SCROLY ; set most significant bit of raster position
+ lda #%00000001
sta c64.IREQMASK ;enable raster interrupt signals from vic
rts
}}
}
; ---- end of C128 specific system utility routines ----
}
sys {
; ------- lowlevel system routines --------
const ubyte target = 128 ; compilation target specifier. 64 = C64, 128 = C128, 16 = CommanderX16.
asmsub reset_system() {
; Soft-reset the system back to initial power-on Basic prompt.
%asm {{
sei
lda #14
sta $01 ; bank the kernal in
jmp (c128.RESET_VEC)
}}
}
sub wait(uword jiffies) {
; --- wait approximately the given number of jiffies (1/60th seconds)
; note: the system irq handler has to be active for this to work as it depends on the system jiffy clock
repeat jiffies {
ubyte jiff = lsb(c64.RDTIM16())
while jiff==lsb(c64.RDTIM16()) {
; wait until 1 jiffy has passed
}
}
}
asmsub waitvsync() clobbers(A) {
; --- busy wait till the next vsync has occurred (approximately), without depending on custom irq handling.
; note: a more accurate way to wait for vsync is to set up a vsync irq handler instead.
%asm {{
- bit c64.SCROLY
bpl -
- bit c64.SCROLY
bmi -
rts
}}
}
inline asmsub waitrastborder() {
; --- busy wait till the raster position has reached the bottom screen border (approximately)
; note: a more accurate way to do this is by using a raster irq handler instead.
%asm {{
- bit c64.SCROLY
bpl -
}}
}
asmsub memcopy(uword source @R0, uword target @R1, uword count @AY) clobbers(A,X,Y) {
%asm {{
ldx cx16.r0
stx P8ZP_SCRATCH_W1 ; source in ZP
ldx cx16.r0+1
stx P8ZP_SCRATCH_W1+1
ldx cx16.r1
stx P8ZP_SCRATCH_W2 ; target in ZP
ldx cx16.r1+1
stx P8ZP_SCRATCH_W2+1
cpy #0
bne _longcopy
; copy <= 255 bytes
tay
bne _copyshort
rts ; nothing to copy
_copyshort
; decrease source and target pointers so we can simply index by Y
lda P8ZP_SCRATCH_W1
bne +
dec P8ZP_SCRATCH_W1+1
+ dec P8ZP_SCRATCH_W1
lda P8ZP_SCRATCH_W2
bne +
dec P8ZP_SCRATCH_W2+1
+ dec P8ZP_SCRATCH_W2
- lda (P8ZP_SCRATCH_W1),y
sta (P8ZP_SCRATCH_W2),y
dey
bne -
rts
_longcopy
sta P8ZP_SCRATCH_B1 ; lsb(count) = remainder in last page
tya
tax ; x = num pages (1+)
ldy #0
- lda (P8ZP_SCRATCH_W1),y
sta (P8ZP_SCRATCH_W2),y
iny
bne -
inc P8ZP_SCRATCH_W1+1
inc P8ZP_SCRATCH_W2+1
dex
bne -
ldy P8ZP_SCRATCH_B1
bne _copyshort
rts
}}
}
asmsub memset(uword mem @R0, uword numbytes @R1, ubyte value @A) clobbers(A,X,Y) {
%asm {{
ldy cx16.r0
sty P8ZP_SCRATCH_W1
ldy cx16.r0+1
sty P8ZP_SCRATCH_W1+1
ldx cx16.r1
ldy cx16.r1+1
jmp prog8_lib.memset
}}
}
asmsub memsetw(uword mem @R0, uword numwords @R1, uword value @AY) clobbers(A,X,Y) {
%asm {{
ldx cx16.r0
stx P8ZP_SCRATCH_W1
ldx cx16.r0+1
stx P8ZP_SCRATCH_W1+1
ldx cx16.r1
stx P8ZP_SCRATCH_W2
ldx cx16.r1+1
stx P8ZP_SCRATCH_W2+1
jmp prog8_lib.memsetw
}}
}
inline asmsub read_flags() -> ubyte @A {
%asm {{
php
pla
}}
}
inline asmsub clear_carry() {
%asm {{
clc
}}
}
inline asmsub set_carry() {
%asm {{
sec
}}
}
inline asmsub clear_irqd() {
%asm {{
cli
}}
}
inline asmsub set_irqd() {
%asm {{
sei
}}
}
inline asmsub exit(ubyte returnvalue @A) {
; -- immediately exit the program with a return code in the A register
%asm {{
jsr c64.CLRCHN ; reset i/o channels
ldx prog8_lib.orig_stackpointer
txs
rts ; return to original caller
}}
}
inline asmsub progend() -> uword @AY {
%asm {{
lda #<prog8_program_end
ldy #>prog8_program_end
}}
}
}
cx16 {
; the sixteen virtual 16-bit registers that the CX16 has defined in the zeropage
; they are simulated on the C64 as well but their location in memory is different
; (because there's no room for them in the zeropage)
; they are allocated at the bottom of the eval-stack (should be ample space unless
; you're doing insane nesting of expressions...)
&uword r0 = $cf00
&uword r1 = $cf02
&uword r2 = $cf04
&uword r3 = $cf06
&uword r4 = $cf08
&uword r5 = $cf0a
&uword r6 = $cf0c
&uword r7 = $cf0e
&uword r8 = $cf10
&uword r9 = $cf12
&uword r10 = $cf14
&uword r11 = $cf16
&uword r12 = $cf18
&uword r13 = $cf1a
&uword r14 = $cf1c
&uword r15 = $cf1e
&word r0s = $cf00
&word r1s = $cf02
&word r2s = $cf04
&word r3s = $cf06
&word r4s = $cf08
&word r5s = $cf0a
&word r6s = $cf0c
&word r7s = $cf0e
&word r8s = $cf10
&word r9s = $cf12
&word r10s = $cf14
&word r11s = $cf16
&word r12s = $cf18
&word r13s = $cf1a
&word r14s = $cf1c
&word r15s = $cf1e
&ubyte r0L = $cf00
&ubyte r1L = $cf02
&ubyte r2L = $cf04
&ubyte r3L = $cf06
&ubyte r4L = $cf08
&ubyte r5L = $cf0a
&ubyte r6L = $cf0c
&ubyte r7L = $cf0e
&ubyte r8L = $cf10
&ubyte r9L = $cf12
&ubyte r10L = $cf14
&ubyte r11L = $cf16
&ubyte r12L = $cf18
&ubyte r13L = $cf1a
&ubyte r14L = $cf1c
&ubyte r15L = $cf1e
&ubyte r0H = $cf01
&ubyte r1H = $cf03
&ubyte r2H = $cf05
&ubyte r3H = $cf07
&ubyte r4H = $cf09
&ubyte r5H = $cf0b
&ubyte r6H = $cf0d
&ubyte r7H = $cf0f
&ubyte r8H = $cf11
&ubyte r9H = $cf13
&ubyte r10H = $cf15
&ubyte r11H = $cf17
&ubyte r12H = $cf19
&ubyte r13H = $cf1b
&ubyte r14H = $cf1d
&ubyte r15H = $cf1f
&byte r0sL = $cf00
&byte r1sL = $cf02
&byte r2sL = $cf04
&byte r3sL = $cf06
&byte r4sL = $cf08
&byte r5sL = $cf0a
&byte r6sL = $cf0c
&byte r7sL = $cf0e
&byte r8sL = $cf10
&byte r9sL = $cf12
&byte r10sL = $cf14
&byte r11sL = $cf16
&byte r12sL = $cf18
&byte r13sL = $cf1a
&byte r14sL = $cf1c
&byte r15sL = $cf1e
&byte r0sH = $cf01
&byte r1sH = $cf03
&byte r2sH = $cf05
&byte r3sH = $cf07
&byte r4sH = $cf09
&byte r5sH = $cf0b
&byte r6sH = $cf0d
&byte r7sH = $cf0f
&byte r8sH = $cf11
&byte r9sH = $cf13
&byte r10sH = $cf15
&byte r11sH = $cf17
&byte r12sH = $cf19
&byte r13sH = $cf1b
&byte r14sH = $cf1d
&byte r15sH = $cf1f
}

View File

@ -0,0 +1,617 @@
; Prog8 definitions for the Text I/O and Screen routines for the Commodore-64
;
; Written by Irmen de Jong (irmen@razorvine.net) - license: GNU GPL 3.0
;
; indent format: TABS, size=8
%import syslib
%import conv
txt {
const ubyte DEFAULT_WIDTH = 40
const ubyte DEFAULT_HEIGHT = 25
sub clear_screen() {
txt.chrout(147)
}
sub home() {
txt.chrout(19)
}
sub nl() {
txt.chrout('\n')
}
sub spc() {
txt.chrout(' ')
}
asmsub column(ubyte col @A) clobbers(A, X, Y) {
; ---- set the cursor on the given column (starting with 0) on the current line
%asm {{
sec
jsr c64.PLOT
tay
clc
jmp c64.PLOT
}}
}
asmsub fill_screen (ubyte char @ A, ubyte color @ Y) clobbers(A) {
; ---- fill the character screen with the given fill character and character color.
; (assumes screen and color matrix are at their default addresses)
%asm {{
pha
tya
jsr clear_screencolors
pla
jsr clear_screenchars
rts
}}
}
asmsub clear_screenchars (ubyte char @ A) clobbers(Y) {
; ---- clear the character screen with the given fill character (leaves colors)
; (assumes screen matrix is at the default address)
%asm {{
ldy #250
- sta c64.Screen+250*0-1,y
sta c64.Screen+250*1-1,y
sta c64.Screen+250*2-1,y
sta c64.Screen+250*3-1,y
dey
bne -
rts
}}
}
asmsub clear_screencolors (ubyte color @ A) clobbers(Y) {
; ---- clear the character screen colors with the given color (leaves characters).
; (assumes color matrix is at the default address)
%asm {{
ldy #250
- sta c64.Colors+250*0-1,y
sta c64.Colors+250*1-1,y
sta c64.Colors+250*2-1,y
sta c64.Colors+250*3-1,y
dey
bne -
rts
}}
}
sub color (ubyte txtcol) {
c128.COLOR = txtcol
}
sub lowercase() {
c128.VMCSB |= 2
}
sub uppercase() {
c128.VMCSB &= ~2
}
asmsub scroll_left (ubyte alsocolors @ Pc) clobbers(A, Y) {
; ---- scroll the whole screen 1 character to the left
; contents of the rightmost column are unchanged, you should clear/refill this yourself
; Carry flag determines if screen color data must be scrolled too
%asm {{
stx P8ZP_SCRATCH_REG
bcc _scroll_screen
+ ; scroll the screen and the color memory
ldx #0
ldy #38
-
.for row=0, row<=24, row+=1
lda c64.Screen + 40*row + 1,x
sta c64.Screen + 40*row + 0,x
lda c64.Colors + 40*row + 1,x
sta c64.Colors + 40*row + 0,x
.next
inx
dey
bpl -
rts
_scroll_screen ; scroll only the screen memory
ldx #0
ldy #38
-
.for row=0, row<=24, row+=1
lda c64.Screen + 40*row + 1,x
sta c64.Screen + 40*row + 0,x
.next
inx
dey
bpl -
ldx P8ZP_SCRATCH_REG
rts
}}
}
asmsub scroll_right (ubyte alsocolors @ Pc) clobbers(A) {
; ---- scroll the whole screen 1 character to the right
; contents of the leftmost column are unchanged, you should clear/refill this yourself
; Carry flag determines if screen color data must be scrolled too
%asm {{
stx P8ZP_SCRATCH_REG
bcc _scroll_screen
+ ; scroll the screen and the color memory
ldx #38
-
.for row=0, row<=24, row+=1
lda c64.Screen + 40*row + 0,x
sta c64.Screen + 40*row + 1,x
lda c64.Colors + 40*row + 0,x
sta c64.Colors + 40*row + 1,x
.next
dex
bpl -
rts
_scroll_screen ; scroll only the screen memory
ldx #38
-
.for row=0, row<=24, row+=1
lda c64.Screen + 40*row + 0,x
sta c64.Screen + 40*row + 1,x
.next
dex
bpl -
ldx P8ZP_SCRATCH_REG
rts
}}
}
asmsub scroll_up (ubyte alsocolors @ Pc) clobbers(A) {
; ---- scroll the whole screen 1 character up
; contents of the bottom row are unchanged, you should refill/clear this yourself
; Carry flag determines if screen color data must be scrolled too
%asm {{
stx P8ZP_SCRATCH_REG
bcc _scroll_screen
+ ; scroll the screen and the color memory
ldx #39
-
.for row=1, row<=24, row+=1
lda c64.Screen + 40*row,x
sta c64.Screen + 40*(row-1),x
lda c64.Colors + 40*row,x
sta c64.Colors + 40*(row-1),x
.next
dex
bpl -
rts
_scroll_screen ; scroll only the screen memory
ldx #39
-
.for row=1, row<=24, row+=1
lda c64.Screen + 40*row,x
sta c64.Screen + 40*(row-1),x
.next
dex
bpl -
ldx P8ZP_SCRATCH_REG
rts
}}
}
asmsub scroll_down (ubyte alsocolors @ Pc) clobbers(A) {
; ---- scroll the whole screen 1 character down
; contents of the top row are unchanged, you should refill/clear this yourself
; Carry flag determines if screen color data must be scrolled too
%asm {{
stx P8ZP_SCRATCH_REG
bcc _scroll_screen
+ ; scroll the screen and the color memory
ldx #39
-
.for row=23, row>=0, row-=1
lda c64.Colors + 40*row,x
sta c64.Colors + 40*(row+1),x
lda c64.Screen + 40*row,x
sta c64.Screen + 40*(row+1),x
.next
dex
bpl -
rts
_scroll_screen ; scroll only the screen memory
ldx #39
-
.for row=23, row>=0, row-=1
lda c64.Screen + 40*row,x
sta c64.Screen + 40*(row+1),x
.next
dex
bpl -
ldx P8ZP_SCRATCH_REG
rts
}}
}
romsub $FFD2 = chrout(ubyte char @ A) ; for consistency. You can also use c64.CHROUT directly ofcourse.
asmsub print (str text @ AY) clobbers(A,Y) {
; ---- print null terminated string from A/Y
; note: the compiler contains an optimization that will replace
; a call to this subroutine with a string argument of just one char,
; by just one call to c64.CHROUT of that single char.
%asm {{
sta P8ZP_SCRATCH_B1
sty P8ZP_SCRATCH_REG
ldy #0
- lda (P8ZP_SCRATCH_B1),y
beq +
jsr c64.CHROUT
iny
bne -
+ rts
}}
}
asmsub print_ub0 (ubyte value @ A) clobbers(A,Y) {
; ---- print the ubyte in A in decimal form, with left padding 0s (3 positions total)
%asm {{
stx P8ZP_SCRATCH_REG
jsr conv.ubyte2decimal
pha
tya
jsr c64.CHROUT
pla
jsr c64.CHROUT
txa
jsr c64.CHROUT
ldx P8ZP_SCRATCH_REG
rts
}}
}
asmsub print_ub (ubyte value @ A) clobbers(A,Y) {
; ---- print the ubyte in A in decimal form, without left padding 0s
%asm {{
stx P8ZP_SCRATCH_REG
jsr conv.ubyte2decimal
_print_byte_digits
pha
cpy #'0'
beq +
tya
jsr c64.CHROUT
pla
jsr c64.CHROUT
jmp _ones
+ pla
cmp #'0'
beq _ones
jsr c64.CHROUT
_ones txa
jsr c64.CHROUT
ldx P8ZP_SCRATCH_REG
rts
}}
}
asmsub print_b (byte value @ A) clobbers(A,Y) {
; ---- print the byte in A in decimal form, without left padding 0s
%asm {{
stx P8ZP_SCRATCH_REG
pha
cmp #0
bpl +
lda #'-'
jsr c64.CHROUT
+ pla
jsr conv.byte2decimal
jmp print_ub._print_byte_digits
}}
}
asmsub print_ubhex (ubyte value @ A, ubyte prefix @ Pc) clobbers(A,Y) {
; ---- print the ubyte in A in hex form (if Carry is set, a radix prefix '$' is printed as well)
%asm {{
stx P8ZP_SCRATCH_REG
bcc +
pha
lda #'$'
jsr c64.CHROUT
pla
+ jsr conv.ubyte2hex
jsr c64.CHROUT
tya
jsr c64.CHROUT
ldx P8ZP_SCRATCH_REG
rts
}}
}
asmsub print_ubbin (ubyte value @ A, ubyte prefix @ Pc) clobbers(A,Y) {
; ---- print the ubyte in A in binary form (if Carry is set, a radix prefix '%' is printed as well)
%asm {{
stx P8ZP_SCRATCH_REG
sta P8ZP_SCRATCH_B1
bcc +
lda #'%'
jsr c64.CHROUT
+ ldy #8
- lda #'0'
asl P8ZP_SCRATCH_B1
bcc +
lda #'1'
+ jsr c64.CHROUT
dey
bne -
ldx P8ZP_SCRATCH_REG
rts
}}
}
asmsub print_uwbin (uword value @ AY, ubyte prefix @ Pc) clobbers(A,Y) {
; ---- print the uword in A/Y in binary form (if Carry is set, a radix prefix '%' is printed as well)
%asm {{
pha
tya
jsr print_ubbin
pla
clc
jmp print_ubbin
}}
}
asmsub print_uwhex (uword value @ AY, ubyte prefix @ Pc) clobbers(A,Y) {
; ---- print the uword in A/Y in hexadecimal form (4 digits)
; (if Carry is set, a radix prefix '$' is printed as well)
%asm {{
pha
tya
jsr print_ubhex
pla
clc
jmp print_ubhex
}}
}
asmsub print_uw0 (uword value @ AY) clobbers(A,Y) {
; ---- print the uword in A/Y in decimal form, with left padding 0s (5 positions total)
%asm {{
stx P8ZP_SCRATCH_REG
jsr conv.uword2decimal
ldy #0
- lda conv.uword2decimal.decTenThousands,y
beq +
jsr c64.CHROUT
iny
bne -
+ ldx P8ZP_SCRATCH_REG
rts
}}
}
asmsub print_uw (uword value @ AY) clobbers(A,Y) {
; ---- print the uword in A/Y in decimal form, without left padding 0s
%asm {{
stx P8ZP_SCRATCH_REG
jsr conv.uword2decimal
ldx P8ZP_SCRATCH_REG
ldy #0
- lda conv.uword2decimal.decTenThousands,y
beq _allzero
cmp #'0'
bne _gotdigit
iny
bne -
_gotdigit
jsr c64.CHROUT
iny
lda conv.uword2decimal.decTenThousands,y
bne _gotdigit
rts
_allzero
lda #'0'
jmp c64.CHROUT
}}
}
asmsub print_w (word value @ AY) clobbers(A,Y) {
; ---- print the (signed) word in A/Y in decimal form, without left padding 0's
%asm {{
cpy #0
bpl +
pha
lda #'-'
jsr c64.CHROUT
tya
eor #255
tay
pla
eor #255
clc
adc #1
bcc +
iny
+ jmp print_uw
}}
}
asmsub input_chars (uword buffer @ AY) clobbers(A) -> ubyte @ Y {
; ---- Input a string (max. 80 chars) from the keyboard. Returns length in Y. (string is terminated with a 0 byte as well)
; It assumes the keyboard is selected as I/O channel!
%asm {{
sta P8ZP_SCRATCH_W1
sty P8ZP_SCRATCH_W1+1
ldy #0 ; char counter = 0
- jsr c64.CHRIN
cmp #$0d ; return (ascii 13) pressed?
beq + ; yes, end.
sta (P8ZP_SCRATCH_W1),y ; else store char in buffer
iny
bne -
+ lda #0
sta (P8ZP_SCRATCH_W1),y ; finish string with 0 byte
rts
}}
}
asmsub setchr (ubyte col @X, ubyte row @Y, ubyte character @A) clobbers(A, Y) {
; ---- sets the character in the screen matrix at the given position
%asm {{
pha
tya
asl a
tay
lda _screenrows+1,y
sta _mod+2
txa
clc
adc _screenrows,y
sta _mod+1
bcc +
inc _mod+2
+ pla
_mod sta $ffff ; modified
rts
_screenrows .word $0400 + range(0, 1000, 40)
}}
}
asmsub getchr (ubyte col @A, ubyte row @Y) clobbers(Y) -> ubyte @ A {
; ---- get the character in the screen matrix at the given location
%asm {{
pha
tya
asl a
tay
lda setchr._screenrows+1,y
sta _mod+2
pla
clc
adc setchr._screenrows,y
sta _mod+1
bcc _mod
inc _mod+2
_mod lda $ffff ; modified
rts
}}
}
asmsub setclr (ubyte col @X, ubyte row @Y, ubyte color @A) clobbers(A, Y) {
; ---- set the color in A on the screen matrix at the given position
%asm {{
pha
tya
asl a
tay
lda _colorrows+1,y
sta _mod+2
txa
clc
adc _colorrows,y
sta _mod+1
bcc +
inc _mod+2
+ pla
_mod sta $ffff ; modified
rts
_colorrows .word $d800 + range(0, 1000, 40)
}}
}
asmsub getclr (ubyte col @A, ubyte row @Y) clobbers(Y) -> ubyte @ A {
; ---- get the color in the screen color matrix at the given location
%asm {{
pha
tya
asl a
tay
lda setclr._colorrows+1,y
sta _mod+2
pla
clc
adc setclr._colorrows,y
sta _mod+1
bcc _mod
inc _mod+2
_mod lda $ffff ; modified
rts
}}
}
sub setcc (ubyte column, ubyte row, ubyte char, ubyte charcolor) {
; ---- set char+color at the given position on the screen
%asm {{
lda row
asl a
tay
lda setchr._screenrows+1,y
sta _charmod+2
adc #$d4
sta _colormod+2
lda setchr._screenrows,y
clc
adc column
sta _charmod+1
sta _colormod+1
bcc +
inc _charmod+2
inc _colormod+2
+ lda char
_charmod sta $ffff ; modified
lda charcolor
_colormod sta $ffff ; modified
rts
}}
}
asmsub plot (ubyte col @ Y, ubyte row @ A) clobbers(A) {
; ---- safe wrapper around PLOT kernal routine, to save the X register.
%asm {{
stx P8ZP_SCRATCH_REG
tax
clc
jsr c64.PLOT
ldx P8ZP_SCRATCH_REG
rts
}}
}
asmsub width() clobbers(X,Y) -> ubyte @A {
; -- returns the text screen width (number of columns)
%asm {{
jsr c64.SCREEN
txa
rts
}}
}
asmsub height() clobbers(X, Y) -> ubyte @A {
; -- returns the text screen height (number of rows)
%asm {{
jsr c64.SCREEN
tya
rts
}}
}
}

View File

@ -474,7 +474,7 @@ _setup_raster_irq
sys {
; ------- lowlevel system routines --------
const ubyte target = 64 ; compilation target specifier. 64 = C64, 16 = CommanderX16.
const ubyte target = 64 ; compilation target specifier. 64 = C64, 128 = C128, 16 = CommanderX16.
asmsub reset_system() {

View File

@ -811,7 +811,7 @@ asmsub set_rasterline(uword line @AY) {
sys {
; ------- lowlevel system routines --------
const ubyte target = 16 ; compilation target specifier. 64 = C64, 16 = CommanderX16.
const ubyte target = 16 ; compilation target specifier. 64 = C64, 128 = C128, 16 = CommanderX16.
asmsub reset_system() {

View File

@ -5,6 +5,7 @@ import prog8.ast.base.AstException
import prog8.compiler.CompilationResult
import prog8.compiler.CompilerArguments
import prog8.compiler.compileProgram
import prog8.compiler.target.C128Target
import prog8.compiler.target.C64Target
import prog8.compiler.target.Cx16Target
import java.io.File
@ -40,7 +41,7 @@ private fun compileMain(args: Array<String>): Boolean {
val watchMode by cli.option(ArgType.Boolean, fullName = "watch", description = "continuous compilation mode (watches for file changes), greatly increases compilation speed")
val slowCodegenWarnings by cli.option(ArgType.Boolean, fullName = "slowwarn", description="show debug warnings about slow/problematic assembly code generation")
val quietAssembler by cli.option(ArgType.Boolean, fullName = "quietasm", description = "don't print assembler output results")
val compilationTarget by cli.option(ArgType.String, fullName = "target", description = "target output of the compiler, currently '${C64Target.name}' and '${Cx16Target.name}' available").default(C64Target.name)
val compilationTarget by cli.option(ArgType.String, fullName = "target", description = "target output of the compiler (one of '${C64Target.name}', '${C128Target.name}', '${Cx16Target.name}')").default(C64Target.name)
val sourceDirs by cli.option(ArgType.String, fullName="srcdirs", description = "list of extra paths, separated with ${File.pathSeparator}, to search in for imported modules").multiple().delimiter(File.pathSeparator)
val moduleFiles by cli.argument(ArgType.String, fullName = "modules", description = "main module file(s) to compile").multiple(999)
@ -67,7 +68,7 @@ private fun compileMain(args: Array<String>): Boolean {
if(srcdirs.firstOrNull()!=".")
srcdirs.add(0, ".")
if (compilationTarget != C64Target.name && compilationTarget != Cx16Target.name) {
if (compilationTarget !in setOf(C64Target.name, C128Target.name, Cx16Target.name)) {
System.err.println("Invalid compilation target: $compilationTarget")
return false
}

View File

@ -10,6 +10,7 @@ import prog8.ast.expressions.Expression
import prog8.ast.expressions.NumericLiteralValue
import prog8.ast.statements.Directive
import prog8.compiler.astprocessing.*
import prog8.compiler.target.C128Target
import prog8.compiler.target.C64Target
import prog8.compiler.target.Cx16Target
import prog8.compiler.target.cpu6502.codegen.AsmGen
@ -50,6 +51,7 @@ fun compileProgram(args: CompilerArguments): CompilationResult {
val compTarget =
when(args.compilationTarget) {
C64Target.name -> C64Target
C128Target.name -> C128Target
Cx16Target.name -> Cx16Target
else -> throw IllegalArgumentException("invalid compilation target")
}

View File

@ -143,31 +143,16 @@ class TestC64Zeropage: FunSpec({
val zp3 = C64Zeropage(CompilationOptions(OutputType.RAW, LauncherType.NONE, ZeropageType.KERNALSAFE, emptyList(), false, false, C64Target))
zp3.availableBytes() shouldBe 125
val zp4 = C64Zeropage(CompilationOptions(OutputType.RAW, LauncherType.NONE, ZeropageType.FULL, emptyList(), false, false, C64Target))
zp4.availableBytes() shouldBe 238
zp4.availableBytes() shouldBe 239
zp4.allocate("test", DataType.UBYTE, null, errors)
zp4.availableBytes() shouldBe 237
zp4.availableBytes() shouldBe 238
zp4.allocate("test2", DataType.UBYTE, null, errors)
zp4.availableBytes() shouldBe 236
}
test("testFreeSpacesWords") {
val zp1 = C64Zeropage(CompilationOptions(OutputType.RAW, LauncherType.NONE, ZeropageType.BASICSAFE, emptyList(), true, false, C64Target))
zp1.availableWords() shouldBe 6
val zp2 = C64Zeropage(CompilationOptions(OutputType.RAW, LauncherType.NONE, ZeropageType.FLOATSAFE, emptyList(), false, false, C64Target))
zp2.availableWords() shouldBe 38
val zp3 = C64Zeropage(CompilationOptions(OutputType.RAW, LauncherType.NONE, ZeropageType.KERNALSAFE, emptyList(), false, false, C64Target))
zp3.availableWords() shouldBe 57
val zp4 = C64Zeropage(CompilationOptions(OutputType.RAW, LauncherType.NONE, ZeropageType.FULL, emptyList(), false, false, C64Target))
zp4.availableWords() shouldBe 116
zp4.allocate("test", DataType.UWORD, null, errors)
zp4.availableWords() shouldBe 115
zp4.allocate("test2", DataType.UWORD, null, errors)
zp4.availableWords() shouldBe 114
zp4.availableBytes() shouldBe 237
}
test("testReservedSpace") {
val zp1 = C64Zeropage(CompilationOptions(OutputType.RAW, LauncherType.NONE, ZeropageType.FULL, emptyList(), false, false, C64Target))
zp1.availableBytes() shouldBe 238
zp1.availableBytes() shouldBe 239
50u shouldBeIn zp1.free
100u shouldBeIn zp1.free
49u shouldBeIn zp1.free
@ -214,7 +199,7 @@ class TestC64Zeropage: FunSpec({
test("testFullAllocation") {
val zp = C64Zeropage(CompilationOptions(OutputType.RAW, LauncherType.NONE, ZeropageType.FULL, emptyList(), false, false, C64Target))
zp.availableBytes() shouldBe 238
zp.availableBytes() shouldBe 239
zp.hasByteAvailable() shouldBe true
zp.hasWordAvailable() shouldBe true
val loc = zp.allocate("", DataType.UWORD, null, errors)
@ -222,17 +207,17 @@ class TestC64Zeropage: FunSpec({
loc shouldNotBeIn zp.free
val num = zp.availableBytes() / 2
for(i in 0..num-4) {
for(i in 0..num-3) {
zp.allocate("", DataType.UWORD, null, errors)
}
zp.availableBytes() shouldBe 6
zp.availableBytes() shouldBe 5
shouldThrow<ZeropageDepletedError> {
// can't allocate because no more sequential bytes, only fragmented
zp.allocate("", DataType.UWORD, null, errors)
}
for(i in 0..5) {
for(i in 0..4) {
zp.allocate("", DataType.UBYTE, null, errors)
}
@ -295,19 +280,6 @@ class TestCx16Zeropage: FunSpec({
zp3.availableBytes() shouldBe 214
}
test("testFreeSpacesWords") {
val zp1 = CX16Zeropage(CompilationOptions(OutputType.RAW, LauncherType.NONE, ZeropageType.FULL, emptyList(), false, false, Cx16Target))
zp1.availableWords() shouldBe 108
val zp2 = CX16Zeropage(CompilationOptions(OutputType.RAW, LauncherType.NONE, ZeropageType.KERNALSAFE, emptyList(), false, false, Cx16Target))
zp2.availableWords() shouldBe 87
val zp3 = CX16Zeropage(CompilationOptions(OutputType.RAW, LauncherType.NONE, ZeropageType.BASICSAFE, emptyList(), true, false, Cx16Target))
zp3.availableWords() shouldBe 44
zp3.allocate("test", DataType.UWORD, null, errors)
zp3.availableWords() shouldBe 43
zp3.allocate("test2", DataType.UWORD, null, errors)
zp3.availableWords() shouldBe 42
}
test("testReservedSpace") {
val zp1 = CX16Zeropage(CompilationOptions(OutputType.RAW, LauncherType.NONE, ZeropageType.FULL, emptyList(), false, false, Cx16Target))
zp1.availableBytes() shouldBe 216

View File

@ -28,21 +28,6 @@ abstract class Zeropage(protected val options: CompilationOptions) {
fun availableBytes() = if(options.zeropage== ZeropageType.DONTUSE) 0 else free.size
fun hasByteAvailable() = if(options.zeropage== ZeropageType.DONTUSE) false else free.isNotEmpty()
fun availableWords(): Int {
if(options.zeropage== ZeropageType.DONTUSE)
return 0
val words = free.windowed(2).filter { it[0] == it[1]-1u }
var nonOverlappingWordsCount = 0
var prevMsbLoc = UInt.MAX_VALUE
for(w in words) {
if(w[0]!=prevMsbLoc) {
nonOverlappingWordsCount++
prevMsbLoc = w[1]
}
}
return nonOverlappingWordsCount
}
fun hasWordAvailable(): Boolean {
if(options.zeropage== ZeropageType.DONTUSE)
return false

View File

@ -99,7 +99,7 @@ One or more .p8 module files
``-target <compilation target>``
Sets the target output of the compiler, currently 'c64' and 'cx16' are valid targets.
c64 = Commodore-64, cx16 = Commander X16.
c64 = Commodore 64, c128 = Commodore 128, cx16 = Commander X16.
Default = c64
``-srcdirs <pathlist>``

View File

@ -11,8 +11,9 @@ Prog8 targets the following hardware:
Currently there are two machines that are supported as compiler target (selectable via the ``-target`` compiler argument):
- 'c64': the well-known Commodore-64
- 'cx16': the `CommanderX16 <https://www.commanderx16.com/>`_ conceived by the 8-Bit Guy.
- 'c64': the Commodore 64
- 'c128': the Commodore 128
- 'cx16': the `Commander X16 <https://www.commanderx16.com/>`_
This chapter explains the relevant system details of these machines.

View File

@ -1,4 +1,4 @@
%import textio
main {
ubyte @shared joy_info