mirror of
https://github.com/KarolS/millfork.git
synced 2025-04-04 06:29:48 +00:00
Improvements related to large types:
– returning types larger than 2 – fastcall for 1 parameter of size 3 or 4 on Z80 – more integer types (up to int128) – marked farword as a deprecated alias of int24
This commit is contained in:
parent
070ae395ee
commit
cb92b09942
@ -18,6 +18,8 @@
|
||||
|
||||
* two-byte return values are passed via the A (low byte) and X (high byte) register
|
||||
|
||||
* otherwise, the return value is passed via a static location
|
||||
|
||||
#### Register preservation:
|
||||
|
||||
* callee may clobber all three registers (A, X, Y) and most flags (Z, V, C, N, and also I if using inline assembly)
|
||||
@ -42,6 +44,14 @@
|
||||
|
||||
* if the function has one parameter of size two bytes, it is passed via the HL register pair
|
||||
|
||||
* if the function has one parameter of size three bytes,
|
||||
its least significant two bytes are passed via the HL register pair
|
||||
and the most significant byte is passed via the E register
|
||||
|
||||
* if the function has one parameter of size four bytes,
|
||||
its least significant word is passed via the HL register pair
|
||||
and the most significant word is passed via the DE register pair
|
||||
|
||||
* otherwise, all parameters are passed via static locations
|
||||
|
||||
#### Return values:
|
||||
@ -50,6 +60,16 @@
|
||||
|
||||
* two-byte return values are passed via the HL register pair
|
||||
|
||||
* in case of three-byte return values,
|
||||
its least significant two bytes are passed via the HL register pair
|
||||
and the most significant byte is passed via the E register
|
||||
|
||||
* in case of four-byte return values,
|
||||
its least significant word is passed via the HL register pair
|
||||
and the most significant word is passed via the DE register pair
|
||||
|
||||
* otherwise, the return value is passed via a static location
|
||||
|
||||
#### Register preservation:
|
||||
|
||||
* callee may clobber all flags
|
||||
|
@ -9,11 +9,15 @@ Millfork puts extra limitations on which types can be used in which contexts.
|
||||
* `byte` – 1-byte value of undefined signedness, defaulting to unsigned
|
||||
|
||||
* `word` – 2-byte value of undefined signedness, defaulting to unsigned
|
||||
(alias: `int16`)
|
||||
|
||||
* `farword` – 3-byte value of undefined signedness, defaulting to unsigned
|
||||
(the name is an analogy to a future 24-bit type called `farpointer`)
|
||||
* `int24` – 3-byte value of undefined signedness, defaulting to unsigned
|
||||
(alias: `farword`; this alias is deprecated and might be removed in the future)
|
||||
|
||||
* `long` – 4-byte value of undefined signedness, defaulting to unsigned
|
||||
(alias: `int32`)
|
||||
|
||||
* `int40`, `int48`,... `int128` – even larger types
|
||||
|
||||
* `sbyte` – signed 1-byte value
|
||||
|
||||
|
@ -219,6 +219,13 @@ object Cpu extends Enumeration {
|
||||
case "intel8080" => Intel8080
|
||||
case _ => ErrorReporting.fatal("Unknown CPU achitecture: " + name)
|
||||
}
|
||||
|
||||
def getMaxSizeReturnableViaRegisters(cpu: Cpu.Value, compilationOptions: CompilationOptions): Int =
|
||||
CpuFamily.forType(cpu) match {
|
||||
case CpuFamily.M6502 => 2
|
||||
case CpuFamily.I80 | CpuFamily.I86 => 4
|
||||
case _ => ???
|
||||
}
|
||||
}
|
||||
|
||||
object CompilationFlag extends Enumeration {
|
||||
|
@ -1,5 +1,6 @@
|
||||
package millfork.assembly.mos.opt
|
||||
|
||||
import millfork.Cpu
|
||||
import millfork.assembly.mos.AddrMode._
|
||||
import millfork.assembly.mos.AssemblyLine
|
||||
import millfork.assembly.mos.Opcode._
|
||||
@ -40,7 +41,11 @@ object EmptyParameterStoreRemoval extends AssemblyOptimization[AssemblyLine] {
|
||||
case th: MemoryVariable if th.alloc == VariableAllocationMethod.Zeropage => Some(th.name) // TODO: ???
|
||||
case _ => None
|
||||
}
|
||||
params ++ locals
|
||||
if (other.returnType.size > Cpu.getMaxSizeReturnableViaRegisters(optimizationContext.options.platform.cpu, optimizationContext.options)) {
|
||||
other.name + ".return" :: (params ++ locals)
|
||||
} else {
|
||||
params ++ locals
|
||||
}
|
||||
}
|
||||
case _ => Nil
|
||||
}.toSet
|
||||
|
@ -171,7 +171,7 @@ case class ZLine(opcode: ZOpcode.Value, registers: ZRegisters, parameter: Consta
|
||||
import ZRegister._
|
||||
val inherent = opcode match {
|
||||
case BYTE => 1
|
||||
case DISCARD_BCDEIX | DISCARD_A | DISCARD_F | DISCARD_HL => 0
|
||||
case d if ZOpcodeClasses.NoopDiscards(d) => 0
|
||||
case JP => registers match {
|
||||
case OneRegister(HL | IX | IY) => 0
|
||||
case _ => 2
|
||||
@ -235,7 +235,10 @@ case class ZLine(opcode: ZOpcode.Value, registers: ZRegisters, parameter: Consta
|
||||
case DISCARD_A => " ; DISCARD_A"
|
||||
case DISCARD_HL => " ; DISCARD_HL"
|
||||
case DISCARD_F => " ; DISCARD_F"
|
||||
case DISCARD_BCDEIX => " ; DISCARD_BCDEIX"
|
||||
case DISCARD_BC => " ; DISCARD_BC"
|
||||
case DISCARD_DE => " ; DISCARD_DE"
|
||||
case DISCARD_IX => " ; DISCARD_IX"
|
||||
case DISCARD_IY => " ; DISCARD_IY"
|
||||
case BYTE => " !byte " + parameter.toString // TODO: format?
|
||||
case LABEL => parameter.toString + ":"
|
||||
case RST => s" RST $parameter"
|
||||
@ -400,7 +403,7 @@ case class ZLine(opcode: ZOpcode.Value, registers: ZRegisters, parameter: Consta
|
||||
}
|
||||
case JP | JR | RET | RETI | RETN |
|
||||
POP |
|
||||
DISCARD_A | DISCARD_BCDEIX | DISCARD_HL | DISCARD_F => false
|
||||
DISCARD_A | DISCARD_BC | DISCARD_DE | DISCARD_IX | DISCARD_IY | DISCARD_HL | DISCARD_F => false
|
||||
case DJNZ => r == B
|
||||
case DAA | NEG | CPL => r == A
|
||||
case LABEL | DI | EI | NOP | HALT => false
|
||||
@ -533,7 +536,7 @@ case class ZLine(opcode: ZOpcode.Value, registers: ZRegisters, parameter: Consta
|
||||
}
|
||||
case JP | JR | RET | RETI | RETN |
|
||||
PUSH |
|
||||
DISCARD_A | DISCARD_BCDEIX | DISCARD_HL | DISCARD_F => false
|
||||
DISCARD_A | DISCARD_BC | DISCARD_DE | DISCARD_IX | DISCARD_IY | DISCARD_HL | DISCARD_F => false
|
||||
case ADD | ADC | AND | OR | XOR | SUB | SBC | DAA | NEG | CPL => r == A
|
||||
case CP => false
|
||||
case DJNZ => r == B
|
||||
@ -564,7 +567,7 @@ case class ZLine(opcode: ZOpcode.Value, registers: ZRegisters, parameter: Consta
|
||||
}
|
||||
case JP | JR | RET | RETI | RETN |
|
||||
PUSH | DJNZ | DAA |
|
||||
DISCARD_A | DISCARD_BCDEIX | DISCARD_HL | DISCARD_F => false
|
||||
DISCARD_A | DISCARD_BC | DISCARD_DE | DISCARD_IX | DISCARD_IY | DISCARD_HL | DISCARD_F => false
|
||||
case LABEL | DI | EI | NOP => false
|
||||
case _ => true // TODO
|
||||
}
|
||||
@ -585,7 +588,7 @@ case class ZLine(opcode: ZOpcode.Value, registers: ZRegisters, parameter: Consta
|
||||
}
|
||||
case JP | JR | RET | RETI | RETN |
|
||||
PUSH | DJNZ | DAA |
|
||||
DISCARD_A | DISCARD_BCDEIX | DISCARD_HL | DISCARD_F => false
|
||||
DISCARD_A | DISCARD_BC | DISCARD_DE | DISCARD_IX | DISCARD_IY | DISCARD_HL | DISCARD_F => false
|
||||
case LABEL | DI | EI | NOP | HALT => false
|
||||
case _ => true // TODO
|
||||
}
|
||||
|
@ -24,7 +24,7 @@ object ZOpcode extends Enumeration {
|
||||
DJNZ, JP, JR, CALL, RET, RETN, RETI, HALT,
|
||||
//sharp:
|
||||
LD_AHLI, LD_AHLD, LD_HLIA, LD_HLDA, SWAP, LD_H, LD_HLSP, ADD_SP, STOP,
|
||||
DISCARD_A, DISCARD_F, DISCARD_HL, DISCARD_BCDEIX,
|
||||
DISCARD_A, DISCARD_F, DISCARD_HL, DISCARD_BC, DISCARD_DE, DISCARD_IX, DISCARD_IY,
|
||||
LABEL, BYTE = Value
|
||||
}
|
||||
|
||||
@ -52,7 +52,7 @@ object ZOpcodeClasses {
|
||||
INI, INIR, OUTI, OUTIR, IND, INDR, OUTD, OUTDR,
|
||||
LDI, LDIR, LDD, LDDR, CPI, CPIR, CPD, CPDR) ++ BIT ++ RES ++ SET
|
||||
|
||||
val NoopDiscards = Set(DISCARD_F, DISCARD_A, DISCARD_HL, DISCARD_BCDEIX)
|
||||
val NoopDiscards = Set(DISCARD_F, DISCARD_A, DISCARD_HL, DISCARD_BC, DISCARD_DE, DISCARD_IX, DISCARD_IY)
|
||||
|
||||
val ChangesAFAlways = Set( // TODO: !
|
||||
DAA, ADD, ADC, SUB, SBC, XOR, OR, AND, INC, DEC,
|
||||
|
@ -1,5 +1,6 @@
|
||||
package millfork.assembly.z80.opt
|
||||
|
||||
import millfork.Cpu
|
||||
import millfork.assembly.z80.ZOpcode._
|
||||
import millfork.assembly.z80.{TwoRegisters, ZLine}
|
||||
import millfork.assembly.{AssemblyOptimization, OptimizationContext}
|
||||
@ -35,7 +36,11 @@ object EmptyParameterStoreRemoval extends AssemblyOptimization[ZLine] {
|
||||
case th: MemoryVariable if th.alloc == VariableAllocationMethod.Auto => Some(th.name)
|
||||
case _ => None
|
||||
}
|
||||
params ++ locals
|
||||
if (other.returnType.size > Cpu.getMaxSizeReturnableViaRegisters(optimizationContext.options.platform.cpu, optimizationContext.options)) {
|
||||
other.name + ".return" :: (params ++ locals)
|
||||
} else {
|
||||
params ++ locals
|
||||
}
|
||||
}
|
||||
case _ => Nil
|
||||
}.toSet
|
||||
|
@ -211,8 +211,14 @@ object ReverseFlowAnalyzer {
|
||||
currentImportance = if (labelIndex < 0) finalImportance else importanceArray(labelIndex)
|
||||
case ZLine(DISCARD_HL, _, _, _) =>
|
||||
currentImportance = currentImportance.copy(h = Unimportant, l = Unimportant)
|
||||
case ZLine(DISCARD_BCDEIX, _, _, _) =>
|
||||
currentImportance = currentImportance.copy(b = Unimportant, c = Unimportant, d = Unimportant, e = Unimportant, ixh = Unimportant, ixl = Unimportant)
|
||||
case ZLine(DISCARD_DE, _, _, _) =>
|
||||
currentImportance = currentImportance.copy(d = Unimportant, e = Unimportant)
|
||||
case ZLine(DISCARD_BC, _, _, _) =>
|
||||
currentImportance = currentImportance.copy(b = Unimportant, c = Unimportant)
|
||||
case ZLine(DISCARD_IX, _, _, _) =>
|
||||
currentImportance = currentImportance.copy(ixh = Unimportant, ixl = Unimportant)
|
||||
case ZLine(DISCARD_IY, _, _, _) =>
|
||||
currentImportance = currentImportance.copy(iyh = Unimportant, iyl = Unimportant)
|
||||
case ZLine(DISCARD_A, _, _, _) =>
|
||||
currentImportance = currentImportance.copy(a = Unimportant)
|
||||
case ZLine(DISCARD_F, _, _, _) =>
|
||||
@ -364,6 +370,42 @@ object ReverseFlowAnalyzer {
|
||||
sf = Unimportant,
|
||||
hf = Unimportant
|
||||
)
|
||||
case NormalParamSignature(List(v)) if v.typ.size == 3 =>
|
||||
currentImportance = currentImportance.copy(
|
||||
a = Unimportant,
|
||||
b = Unimportant,
|
||||
c = Unimportant,
|
||||
d = Unimportant,
|
||||
e = Important,
|
||||
h = Important,
|
||||
l = Important,
|
||||
hlNumeric = Unimportant,
|
||||
iyh = Unimportant,
|
||||
iyl = Unimportant,
|
||||
zf = Unimportant,
|
||||
cf = Unimportant,
|
||||
nf = Unimportant,
|
||||
sf = Unimportant,
|
||||
hf = Unimportant
|
||||
)
|
||||
case NormalParamSignature(List(v)) if v.typ.size == 4 =>
|
||||
currentImportance = currentImportance.copy(
|
||||
a = Unimportant,
|
||||
b = Unimportant,
|
||||
c = Unimportant,
|
||||
d = Important,
|
||||
e = Important,
|
||||
h = Important,
|
||||
l = Important,
|
||||
hlNumeric = Unimportant,
|
||||
iyh = Unimportant,
|
||||
iyl = Unimportant,
|
||||
zf = Unimportant,
|
||||
cf = Unimportant,
|
||||
nf = Unimportant,
|
||||
sf = Unimportant,
|
||||
hf = Unimportant
|
||||
)
|
||||
case NormalParamSignature(_) | AssemblyParamSignature(Nil) =>
|
||||
currentImportance = currentImportance.copy(
|
||||
a = Unimportant,
|
||||
|
@ -28,6 +28,10 @@ object VariableStatus {
|
||||
Set[String]()
|
||||
case NormalParamSignature(List(MemoryVariable(_, typ, _))) if typ.size == 2 =>
|
||||
Set[String]()
|
||||
case NormalParamSignature(List(MemoryVariable(_, typ, _))) if typ.size == 3 =>
|
||||
Set[String]()
|
||||
case NormalParamSignature(List(MemoryVariable(_, typ, _))) if typ.size == 4 =>
|
||||
Set[String]()
|
||||
case NormalParamSignature(ps) =>
|
||||
ps.map(_.name).toSet
|
||||
case _ =>
|
||||
|
@ -676,6 +676,7 @@ object MosExpressionCompiler extends AbstractExpressionCompiler[AssemblyLine] {
|
||||
|
||||
case f@FunctionCallExpression(name, params) =>
|
||||
var zeroExtend = false
|
||||
var resultVariable = ""
|
||||
val calculate: List[AssemblyLine] = name match {
|
||||
case "not" =>
|
||||
assertBool(ctx, "not", params, 1)
|
||||
@ -1054,6 +1055,9 @@ object MosExpressionCompiler extends AbstractExpressionCompiler[AssemblyLine] {
|
||||
case function: EmptyFunction =>
|
||||
??? // TODO: type conversion?
|
||||
case function: FunctionInMemory =>
|
||||
if (function.returnType.size > 2) {
|
||||
resultVariable = function.name + ".return"
|
||||
}
|
||||
function match {
|
||||
case nf: NormalFunction =>
|
||||
if (nf.interrupt) {
|
||||
@ -1089,11 +1093,15 @@ object MosExpressionCompiler extends AbstractExpressionCompiler[AssemblyLine] {
|
||||
result
|
||||
}
|
||||
}
|
||||
val store: List[AssemblyLine] = expressionStorageFromAX(ctx, exprTypeAndVariable, expr.position)
|
||||
if (zeroExtend && exprTypeAndVariable.exists(_._1.size >= 2)) {
|
||||
calculate ++ List(AssemblyLine.immediate(LDX, 0)) ++ store
|
||||
if (resultVariable == "") {
|
||||
val store: List[AssemblyLine] = expressionStorageFromAX(ctx, exprTypeAndVariable, expr.position)
|
||||
if (zeroExtend && exprTypeAndVariable.exists(_._1.size >= 2)) {
|
||||
calculate ++ List(AssemblyLine.immediate(LDX, 0)) ++ store
|
||||
} else {
|
||||
calculate ++ store
|
||||
}
|
||||
} else {
|
||||
calculate ++ store
|
||||
calculate ++ compile(ctx, VariableExpression(resultVariable), exprTypeAndVariable, branches)
|
||||
}
|
||||
}
|
||||
}
|
||||
|
@ -209,6 +209,12 @@ object MosStatementCompiler extends AbstractStatementCompiler[AssemblyLine] {
|
||||
}
|
||||
stackPointerFixBeforeReturn(ctx) ++
|
||||
List(AssemblyLine.discardYF()) ++ returnInstructions
|
||||
case _ =>
|
||||
if (statement.position.isDefined){
|
||||
ErrorReporting.warn("Returning without a value", ctx.options, statement.position)
|
||||
}
|
||||
stackPointerFixBeforeReturn(ctx) ++
|
||||
List(AssemblyLine.discardAF(), AssemblyLine.discardXF(), AssemblyLine.discardYF()) ++ returnInstructions
|
||||
}
|
||||
}
|
||||
case s : ReturnDispatchStatement =>
|
||||
@ -224,6 +230,9 @@ object MosStatementCompiler extends AbstractStatementCompiler[AssemblyLine] {
|
||||
MosExpressionCompiler.compile(ctx, e, someRegisterA, NoBranching) ++ stackPointerFixBeforeReturn(ctx) ++ returnInstructions
|
||||
case 2 =>
|
||||
MosExpressionCompiler.compile(ctx, e, someRegisterAX, NoBranching) ++ stackPointerFixBeforeReturn(ctx) ++ returnInstructions
|
||||
case _ =>
|
||||
MosExpressionCompiler.compileAssignment(ctx, e, VariableExpression(ctx.function.name + "`return")) ++
|
||||
stackPointerFixBeforeReturn(ctx) ++ returnInstructions
|
||||
}
|
||||
case _ =>
|
||||
AbstractExpressionCompiler.checkAssignmentType(ctx, e, m.returnType)
|
||||
@ -244,6 +253,9 @@ object MosStatementCompiler extends AbstractStatementCompiler[AssemblyLine] {
|
||||
List(AssemblyLine.implied(TAX), AssemblyLine.implied(TYA), AssemblyLine.discardYF()) ++
|
||||
returnInstructions
|
||||
}
|
||||
case _ =>
|
||||
MosExpressionCompiler.compileAssignment(ctx, e, VariableExpression(ctx.function.name + ".return")) ++
|
||||
stackPointerFixBeforeReturn(ctx) ++ List(AssemblyLine.discardAF(), AssemblyLine.discardXF(), AssemblyLine.discardYF()) ++ returnInstructions
|
||||
}
|
||||
}
|
||||
case s: IfStatement =>
|
||||
|
@ -35,6 +35,37 @@ object Z80Compiler extends AbstractCompiler[ZLine] {
|
||||
ZLine.ld8(ZRegister.A, ZRegister.H),
|
||||
ZLine.ldAbs8(param.toAddress + 1, ZRegister.A))
|
||||
}
|
||||
case NormalParamSignature(List(param)) if param.typ.size == 3 =>
|
||||
import ZRegister._
|
||||
val p = param.toAddress
|
||||
if (ctx.options.flag(CompilationFlag.EmitIntel8080Opcodes)) {
|
||||
List(ZLine.ldAbs16(p, HL), ZLine.ld8(A, E), ZLine.ldAbs8(p + 2, A))
|
||||
} else {
|
||||
List(
|
||||
ZLine.ld8(A, L),
|
||||
ZLine.ldAbs8(p, A),
|
||||
ZLine.ld8(A, H),
|
||||
ZLine.ldAbs8(p + 1, A),
|
||||
ZLine.ld8(A, E),
|
||||
ZLine.ldAbs8(p + 2, A))
|
||||
}
|
||||
case NormalParamSignature(List(param)) if param.typ.size == 4 =>
|
||||
import ZRegister._
|
||||
val p = param.toAddress
|
||||
if (ctx.options.flag(CompilationFlag.EmitIntel8080Opcodes)) {
|
||||
// TODO: is this optimal?
|
||||
List(ZLine.ldAbs16(p, HL), ZLine.ld8(A, E), ZLine.ldAbs8(p + 2, A), ZLine.ld8(A, D), ZLine.ldAbs8(p + 3, A))
|
||||
} else {
|
||||
List(
|
||||
ZLine.ld8(A, L),
|
||||
ZLine.ldAbs8(p, A),
|
||||
ZLine.ld8(A, H),
|
||||
ZLine.ldAbs8(p + 1, A),
|
||||
ZLine.ld8(A, E),
|
||||
ZLine.ldAbs8(p + 2, A),
|
||||
ZLine.ld8(A, D),
|
||||
ZLine.ldAbs8(p + 3, A))
|
||||
}
|
||||
case _ => Nil
|
||||
}
|
||||
label :: (stackPointerFixAtBeginning(ctx) ++ storeParamsFromRegisters ++ chunk)
|
||||
|
@ -12,7 +12,7 @@ import millfork.error.ErrorReporting
|
||||
* @author Karol Stasiak
|
||||
*/
|
||||
object ZExpressionTarget extends Enumeration {
|
||||
val A, HL, BC, DE, NOTHING = Value
|
||||
val A, HL, BC, DE, EHL, DEHL, NOTHING = Value
|
||||
}
|
||||
|
||||
object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
@ -21,6 +21,10 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
|
||||
def compileToHL(ctx: CompilationContext, expression: Expression): List[ZLine] = compile(ctx, expression, ZExpressionTarget.HL)
|
||||
|
||||
def compileToEHL(ctx: CompilationContext, expression: Expression): List[ZLine] = compile(ctx, expression, ZExpressionTarget.EHL)
|
||||
|
||||
def compileToDEHL(ctx: CompilationContext, expression: Expression): List[ZLine] = compile(ctx, expression, ZExpressionTarget.DEHL)
|
||||
|
||||
def compileToBC(ctx: CompilationContext, expression: Expression): List[ZLine] = compile(ctx, expression, ZExpressionTarget.BC)
|
||||
|
||||
def compileToDE(ctx: CompilationContext, expression: Expression): List[ZLine] = compile(ctx, expression, ZExpressionTarget.DE)
|
||||
@ -168,6 +172,8 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
case ZExpressionTarget.HL => toWord(ZRegister.H, ZRegister.L)
|
||||
case ZExpressionTarget.BC => toWord(ZRegister.B, ZRegister.C)
|
||||
case ZExpressionTarget.DE => toWord(ZRegister.D, ZRegister.E)
|
||||
case ZExpressionTarget.EHL => toWord(ZRegister.H, ZRegister.L) ++ List(ZLine.ldImm8(ZRegister.E, 0))
|
||||
case ZExpressionTarget.DEHL => toWord(ZRegister.H, ZRegister.L) ++ List(ZLine.ldImm16(ZRegister.DE, 0))
|
||||
}
|
||||
}
|
||||
|
||||
@ -176,6 +182,17 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
case ZExpressionTarget.A => lines :+ ZLine.ld8(ZRegister.A, ZRegister.L)
|
||||
case ZExpressionTarget.BC => lines ++ List(ZLine.ld8(ZRegister.C, ZRegister.L), ZLine.ld8(ZRegister.B, ZRegister.H))
|
||||
case ZExpressionTarget.DE => lines ++ List(ZLine.ld8(ZRegister.E, ZRegister.L), ZLine.ld8(ZRegister.D, ZRegister.H))
|
||||
case ZExpressionTarget.EHL => lines ++ List(ZLine.ldImm8(ZRegister.E, 0))
|
||||
case ZExpressionTarget.DEHL => lines ++ List(ZLine.ldImm16(ZRegister.DE, 0))
|
||||
}
|
||||
|
||||
def targetifyEHL(ctx: CompilationContext, target: ZExpressionTarget.Value, lines: List[ZLine]): List[ZLine] = target match {
|
||||
case ZExpressionTarget.NOTHING | ZExpressionTarget.EHL => lines
|
||||
case ZExpressionTarget.DEHL => lines ++ List(ZLine.ldImm8(ZRegister.D, 0))
|
||||
}
|
||||
|
||||
def targetifyDEHL(ctx: CompilationContext, target: ZExpressionTarget.Value, lines: List[ZLine]): List[ZLine] = target match {
|
||||
case ZExpressionTarget.NOTHING | ZExpressionTarget.DEHL => lines
|
||||
}
|
||||
|
||||
def compile(ctx: CompilationContext, expression: Expression, target: ZExpressionTarget.Value, branches: BranchSpec = BranchSpec.None): List[ZLine] = {
|
||||
@ -193,6 +210,10 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
List(ZLine.ldImm16(ZRegister.BC, const))
|
||||
case ZExpressionTarget.DE =>
|
||||
List(ZLine.ldImm16(ZRegister.DE, const))
|
||||
case ZExpressionTarget.EHL =>
|
||||
List(ZLine.ldImm16(ZRegister.HL, const.subword(0)), ZLine.ldImm8(ZRegister.E, const.subbyte(2)))
|
||||
case ZExpressionTarget.DEHL =>
|
||||
List(ZLine.ldImm16(ZRegister.HL, const.subword(0)), ZLine.ldImm16(ZRegister.DE, const.subword(2)))
|
||||
case ZExpressionTarget.NOTHING =>
|
||||
Nil // TODO
|
||||
}
|
||||
@ -216,6 +237,22 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
// TODO: is it optimal?
|
||||
List(ZLine.ldAbs8(A, v), ZLine.ld8(L, A), ZLine.ldAbs8(A, v.toAddress + 1), ZLine.ld8(H, A))
|
||||
}
|
||||
case ZExpressionTarget.EHL =>
|
||||
// TODO: signed words
|
||||
if (ctx.options.flag(CompilationFlag.EmitIntel8080Opcodes)) {
|
||||
List(ZLine.ldAbs16(HL, v), ZLine.ldImm8(E, 0))
|
||||
} else {
|
||||
// TODO: is it optimal?
|
||||
List(ZLine.ldAbs8(A, v), ZLine.ld8(L, A), ZLine.ldAbs8(A, v.toAddress + 1), ZLine.ld8(H, A), ZLine.ldImm8(E, 0))
|
||||
}
|
||||
case ZExpressionTarget.DEHL =>
|
||||
// TODO: signed words
|
||||
if (ctx.options.flag(CompilationFlag.EmitIntel8080Opcodes)) {
|
||||
List(ZLine.ldAbs16(HL, v), ZLine.ldImm16(DE, 0))
|
||||
} else {
|
||||
// TODO: is it optimal?
|
||||
List(ZLine.ldAbs8(A, v), ZLine.ld8(L, A), ZLine.ldAbs8(A, v.toAddress + 1), ZLine.ld8(H, A), ZLine.ldImm16(DE, 0))
|
||||
}
|
||||
case ZExpressionTarget.BC =>
|
||||
if (ctx.options.flag(CompilationFlag.EmitZ80Opcodes)) {
|
||||
List(ZLine.ldAbs16(BC, v))
|
||||
@ -235,14 +272,57 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
List(ZLine.ldAbs8(A, v), ZLine.ld8(E, A), ZLine.ldAbs8(A, v.toAddress + 1), ZLine.ld8(D, A))
|
||||
}
|
||||
}
|
||||
case _ => ???
|
||||
case 3 => target match {
|
||||
case ZExpressionTarget.NOTHING => Nil
|
||||
case ZExpressionTarget.EHL =>
|
||||
if (ctx.options.flag(CompilationFlag.EmitIntel8080Opcodes)) {
|
||||
List(ZLine.ldAbs16(HL, v), ZLine.ldAbs8(A, v.toAddress + 2), ZLine.ld8(E, A))
|
||||
} else {
|
||||
// TODO: is it optimal?
|
||||
List(
|
||||
ZLine.ldAbs8(A, v), ZLine.ld8(L, A),
|
||||
ZLine.ldAbs8(A, v.toAddress + 1), ZLine.ld8(H, A),
|
||||
ZLine.ldAbs8(A, v.toAddress + 2), ZLine.ld8(E, A))
|
||||
}
|
||||
case ZExpressionTarget.DEHL =>
|
||||
// TODO: signed farwords
|
||||
if (ctx.options.flag(CompilationFlag.EmitIntel8080Opcodes)) {
|
||||
List(ZLine.ldAbs16(HL, v), ZLine.ldAbs8(A, v.toAddress + 2), ZLine.ld8(E, A), ZLine.ldImm8(D, 0))
|
||||
} else {
|
||||
// TODO: is it optimal?
|
||||
List(
|
||||
ZLine.ldAbs8(A, v), ZLine.ld8(L, A),
|
||||
ZLine.ldAbs8(A, v.toAddress + 1), ZLine.ld8(H, A),
|
||||
ZLine.ldAbs8(A, v.toAddress + 2), ZLine.ld8(E, A), ZLine.ldImm8(D, 0))
|
||||
}
|
||||
}
|
||||
case 4 => target match {
|
||||
case ZExpressionTarget.NOTHING => Nil
|
||||
case ZExpressionTarget.DEHL =>
|
||||
// TODO: signed farwords
|
||||
if (ctx.options.flag(CompilationFlag.EmitZ80Opcodes)) {
|
||||
List(ZLine.ldAbs16(HL, v), ZLine.ldAbs16(DE, v.toAddress + 2))
|
||||
} else if (ctx.options.flag(CompilationFlag.EmitIntel8080Opcodes)) {
|
||||
// The optimizer might spit out an EX DE,HL
|
||||
List(ZLine.ldAbs16(HL, v.toAddress + 2), ZLine.ld8(D,H), ZLine.ld8(E,L),ZLine.ldAbs16(HL, v))
|
||||
} else {
|
||||
// TODO: is it optimal?
|
||||
List(
|
||||
ZLine.ldAbs8(A, v), ZLine.ld8(L, A),
|
||||
ZLine.ldAbs8(A, v.toAddress + 1), ZLine.ld8(H, A),
|
||||
ZLine.ldAbs8(A, v.toAddress + 2), ZLine.ld8(E, A),
|
||||
ZLine.ldAbs8(A, v.toAddress + 3), ZLine.ld8(D, A))
|
||||
}
|
||||
}
|
||||
}
|
||||
case v: StackVariable =>
|
||||
import ZRegister._
|
||||
if (ctx.options.flag(CompilationFlag.UseIxForStack)) {
|
||||
v.typ.size match {
|
||||
case 0 => ???
|
||||
case 1 => loadByteViaIX(v.baseOffset, target)
|
||||
case 2 => target match {
|
||||
// TODO: signed words
|
||||
case ZExpressionTarget.NOTHING => Nil
|
||||
case ZExpressionTarget.HL =>
|
||||
List(ZLine.ldViaIx(ZRegister.L, v.baseOffset), ZLine.ldViaIx(ZRegister.H, v.baseOffset + 1))
|
||||
@ -250,16 +330,38 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
List(ZLine.ldViaIx(ZRegister.C, v.baseOffset), ZLine.ldViaIx(ZRegister.B, v.baseOffset + 1))
|
||||
case ZExpressionTarget.DE =>
|
||||
List(ZLine.ldViaIx(ZRegister.E, v.baseOffset), ZLine.ldViaIx(ZRegister.D, v.baseOffset + 1))
|
||||
case ZExpressionTarget.EHL =>
|
||||
List(ZLine.ldViaIx(L, v.baseOffset), ZLine.ldViaIx(H, v.baseOffset + 1), ZLine.ldImm8(E, 0))
|
||||
case ZExpressionTarget.DEHL =>
|
||||
List(ZLine.ldViaIx(L, v.baseOffset), ZLine.ldViaIx(H, v.baseOffset + 1), ZLine.ldImm16(DE, 0))
|
||||
}
|
||||
case 3 => target match {
|
||||
// TODO: signed farwords
|
||||
case ZExpressionTarget.NOTHING => Nil
|
||||
case ZExpressionTarget.EHL =>
|
||||
List(ZLine.ldViaIx(L, v.baseOffset), ZLine.ldViaIx(H, v.baseOffset + 1), ZLine.ldViaIx(E, v.baseOffset + 2))
|
||||
case ZExpressionTarget.DEHL =>
|
||||
List(ZLine.ldViaIx(L, v.baseOffset), ZLine.ldViaIx(H, v.baseOffset + 1), ZLine.ldViaIx(E, v.baseOffset + 2), ZLine.ldImm8(D, 0))
|
||||
}
|
||||
case 4 => target match {
|
||||
case ZExpressionTarget.NOTHING => Nil
|
||||
case ZExpressionTarget.EHL =>
|
||||
List(ZLine.ldViaIx(L, v.baseOffset), ZLine.ldViaIx(H, v.baseOffset + 1), ZLine.ldViaIx(E, v.baseOffset + 2))
|
||||
case ZExpressionTarget.DEHL =>
|
||||
List(ZLine.ldViaIx(L, v.baseOffset), ZLine.ldViaIx(H, v.baseOffset + 1), ZLine.ldViaIx(E, v.baseOffset + 2), ZLine.ldViaIx(D, v.baseOffset + 3))
|
||||
}
|
||||
case _ => ???
|
||||
}
|
||||
} else {
|
||||
val loadHL = calculateStackAddressToHL(ctx, v)
|
||||
val loadHL = calculateStackAddressToHL(ctx, v.baseOffset)
|
||||
lazy val loadHL2 = calculateStackAddressToHL(ctx, v.baseOffset + 2)
|
||||
lazy val loadHL3 = calculateStackAddressToHL(ctx, v.baseOffset + 3)
|
||||
import ZRegister._
|
||||
v.typ.size match {
|
||||
case 0 => ???
|
||||
case 1 => loadHL ++ loadByteViaHL(target)
|
||||
case 2 => target match {
|
||||
// TODO: signed words
|
||||
case ZExpressionTarget.NOTHING => Nil
|
||||
case ZExpressionTarget.HL =>
|
||||
loadHL ++ List(ZLine.ld8(A,MEM_HL), ZLine.register(INC_16, HL), ZLine.ld8(H, MEM_HL), ZLine.ld8(L, A))
|
||||
@ -267,6 +369,44 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
loadHL ++ List(ZLine.ld8(C,MEM_HL), ZLine.register(INC_16, HL), ZLine.ld8(B, MEM_HL))
|
||||
case ZExpressionTarget.DE =>
|
||||
loadHL ++ List(ZLine.ld8(E,MEM_HL), ZLine.register(INC_16, HL), ZLine.ld8(D, MEM_HL))
|
||||
case ZExpressionTarget.EHL =>
|
||||
loadHL ++ List(ZLine.ld8(A,MEM_HL), ZLine.register(INC_16, HL), ZLine.ld8(H, MEM_HL), ZLine.ld8(L, A), ZLine.ldImm8(E, 0))
|
||||
case ZExpressionTarget.DEHL =>
|
||||
loadHL ++ List(ZLine.ld8(A,MEM_HL), ZLine.register(INC_16, HL), ZLine.ld8(H, MEM_HL), ZLine.ld8(L, A), ZLine.ldImm16(DE, 0))
|
||||
}
|
||||
case 3 => target match {
|
||||
// TODO: signed farwords
|
||||
case ZExpressionTarget.NOTHING => Nil
|
||||
case ZExpressionTarget.EHL =>
|
||||
loadHL2 ++ List(
|
||||
ZLine.ld8(E,MEM_HL),
|
||||
ZLine.register(DEC_16, HL),
|
||||
ZLine.ld8(A, MEM_HL),
|
||||
ZLine.register(DEC_16, HL),
|
||||
ZLine.ld8(L, MEM_HL),
|
||||
ZLine.ld8(H, A))
|
||||
case ZExpressionTarget.DEHL =>
|
||||
loadHL2 ++ List(
|
||||
ZLine.ld8(E,MEM_HL),
|
||||
ZLine.register(DEC_16, HL),
|
||||
ZLine.ld8(A, MEM_HL),
|
||||
ZLine.register(DEC_16, HL),
|
||||
ZLine.ld8(L, MEM_HL),
|
||||
ZLine.ld8(H, A),
|
||||
ZLine.ldImm8(D, 0))
|
||||
}
|
||||
case 4 => target match {
|
||||
case ZExpressionTarget.NOTHING => Nil
|
||||
case ZExpressionTarget.DEHL =>
|
||||
loadHL3 ++ List(
|
||||
ZLine.ld8(D,MEM_HL),
|
||||
ZLine.register(DEC_16, HL),
|
||||
ZLine.ld8(E,MEM_HL),
|
||||
ZLine.register(DEC_16, HL),
|
||||
ZLine.ld8(A, MEM_HL),
|
||||
ZLine.register(DEC_16, HL),
|
||||
ZLine.ld8(L, MEM_HL),
|
||||
ZLine.ld8(H, A))
|
||||
}
|
||||
case _ => ???
|
||||
}
|
||||
@ -318,6 +458,8 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
case ZExpressionTarget.HL=> List(ZLine.ld8(ZRegister.L, ZRegister.H), ZLine.ldImm8(ZRegister.H, 0))
|
||||
case ZExpressionTarget.BC=> List(ZLine.ld8(ZRegister.C, ZRegister.H), ZLine.ldImm8(ZRegister.B, 0))
|
||||
case ZExpressionTarget.DE=> List(ZLine.ld8(ZRegister.E, ZRegister.H), ZLine.ldImm8(ZRegister.D, 0))
|
||||
case ZExpressionTarget.EHL => List(ZLine.ld8(ZRegister.L, ZRegister.H), ZLine.ldImm8(ZRegister.H, 0), ZLine.ldImm8(ZRegister.E, 0))
|
||||
case ZExpressionTarget.DEHL => List(ZLine.ld8(ZRegister.L, ZRegister.H), ZLine.ldImm8(ZRegister.H, 0), ZLine.ldImm16(ZRegister.DE, 0))
|
||||
})
|
||||
}
|
||||
case "lo" =>
|
||||
@ -331,6 +473,8 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
case ZExpressionTarget.HL => List(ZLine.ldImm8(ZRegister.H, 0))
|
||||
case ZExpressionTarget.BC => List(ZLine.ld8(ZRegister.C, ZRegister.L), ZLine.ldImm8(ZRegister.B, 0))
|
||||
case ZExpressionTarget.DE => List(ZLine.ld8(ZRegister.E, ZRegister.L), ZLine.ldImm8(ZRegister.D, 0))
|
||||
case ZExpressionTarget.EHL => List(ZLine.ldImm8(ZRegister.H, 0), ZLine.ldImm8(ZRegister.E, 0))
|
||||
case ZExpressionTarget.DEHL => List(ZLine.ldImm8(ZRegister.H, 0), ZLine.ldImm16(ZRegister.DE, 0))
|
||||
})
|
||||
}
|
||||
case "nonet" =>
|
||||
@ -341,6 +485,8 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
compileToA(ctx, params.head) ++ (target match {
|
||||
case ZExpressionTarget.NOTHING => Nil
|
||||
case ZExpressionTarget.A => Nil
|
||||
case ZExpressionTarget.EHL => compile(ctx, expression, ZExpressionTarget.HL, branches) :+ ZLine.ldImm8(ZRegister.E, 0)
|
||||
case ZExpressionTarget.DEHL => compile(ctx, expression, ZExpressionTarget.HL, branches) :+ ZLine.ldImm16(ZRegister.DE, 0)
|
||||
case ZExpressionTarget.HL =>
|
||||
if (ctx.options.flag(CompilationFlag.EmitExtended80Opcodes)) {
|
||||
List(
|
||||
@ -652,6 +798,10 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
compileToA(ctx, params.head) :+ ZLine(CALL, NoRegisters, function.toAddress)
|
||||
case NormalParamSignature(List(param)) if param.typ.size == 2 =>
|
||||
compileToHL(ctx, params.head) :+ ZLine(CALL, NoRegisters, function.toAddress)
|
||||
case NormalParamSignature(List(param)) if param.typ.size == 3 =>
|
||||
compileToEHL(ctx, params.head) :+ ZLine(CALL, NoRegisters, function.toAddress)
|
||||
case NormalParamSignature(List(param)) if param.typ.size == 4 =>
|
||||
compileToDEHL(ctx, params.head) :+ ZLine(CALL, NoRegisters, function.toAddress)
|
||||
case NormalParamSignature(paramVars) =>
|
||||
params.zip(paramVars).flatMap {
|
||||
case (paramExpr, paramVar) =>
|
||||
@ -661,7 +811,8 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
compileToA(ctx, paramExpr) ++ storeA(callCtx, VariableExpression(paramVar.name), paramVar.typ.isSigned)
|
||||
case 2 =>
|
||||
compileToHL(ctx, paramExpr) ++ storeHL(callCtx, VariableExpression(paramVar.name), paramVar.typ.isSigned)
|
||||
case _ => ???
|
||||
case _ =>
|
||||
storeLarge(callCtx, VariableExpression(paramVar.name), paramExpr)
|
||||
}
|
||||
} ++ List(ZLine(CALL, NoRegisters, function.toAddress))
|
||||
}
|
||||
@ -670,6 +821,10 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
targetifyA(ctx, target, result, isSigned = function.returnType.isSigned)
|
||||
case 2 =>
|
||||
targetifyHL(ctx, target, result)
|
||||
case 3 =>
|
||||
targetifyEHL(ctx, target, result)
|
||||
case 4 =>
|
||||
targetifyDEHL(ctx, target, result)
|
||||
case _ =>
|
||||
result
|
||||
}
|
||||
@ -717,13 +872,16 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
}
|
||||
}
|
||||
|
||||
def calculateStackAddressToHL(ctx: CompilationContext, v: StackVariable): List[ZLine] = {
|
||||
@inline
|
||||
def calculateStackAddressToHL(ctx: CompilationContext, v: StackVariable): List[ZLine] = calculateStackAddressToHL(ctx, v.baseOffset)
|
||||
|
||||
def calculateStackAddressToHL(ctx: CompilationContext, baseOffset: Int): List[ZLine] = {
|
||||
if (ctx.options.flag(CompilationFlag.UseIxForStack)) {
|
||||
???
|
||||
} else if (ctx.options.flag(CompilationFlag.EmitSharpOpcodes)) {
|
||||
List(ZLine.imm8(ZOpcode.LD_HLSP, v.baseOffset + ctx.extraStackOffset))
|
||||
List(ZLine.imm8(ZOpcode.LD_HLSP, baseOffset + ctx.extraStackOffset))
|
||||
} else {
|
||||
List(ZLine.ldImm16(ZRegister.HL, v.baseOffset + ctx.extraStackOffset), ZLine.registers(ZOpcode.ADD_16, ZRegister.HL, ZRegister.SP))
|
||||
List(ZLine.ldImm16(ZRegister.HL, baseOffset + ctx.extraStackOffset), ZLine.registers(ZOpcode.ADD_16, ZRegister.HL, ZRegister.SP))
|
||||
}
|
||||
}
|
||||
|
||||
@ -780,6 +938,8 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
case ZExpressionTarget.HL => List(ZLine.ldAbs8(ZRegister.A, sourceAddr), ZLine.ld8(ZRegister.L, ZRegister.A), ZLine.ldImm8(ZRegister.H, 0))
|
||||
case ZExpressionTarget.BC => List(ZLine.ldAbs8(ZRegister.A, sourceAddr), ZLine.ld8(ZRegister.C, ZRegister.A), ZLine.ldImm8(ZRegister.B, 0))
|
||||
case ZExpressionTarget.DE => List(ZLine.ldAbs8(ZRegister.A, sourceAddr), ZLine.ld8(ZRegister.E, ZRegister.A), ZLine.ldImm8(ZRegister.D, 0))
|
||||
case ZExpressionTarget.EHL => List(ZLine.ldAbs8(ZRegister.A, sourceAddr), ZLine.ld8(ZRegister.L, ZRegister.A), ZLine.ldImm8(ZRegister.H, 0), ZLine.ldImm8(ZRegister.E, 0))
|
||||
case ZExpressionTarget.DEHL => List(ZLine.ldAbs8(ZRegister.A, sourceAddr), ZLine.ld8(ZRegister.L, ZRegister.A), ZLine.ldImm8(ZRegister.H, 0), ZLine.ldImm16(ZRegister.DE, 0))
|
||||
}
|
||||
}
|
||||
|
||||
@ -790,6 +950,8 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
case ZExpressionTarget.HL => List(ZLine.ldViaIx(ZRegister.L, offset), ZLine.ldImm8(ZRegister.H, 0))
|
||||
case ZExpressionTarget.BC => List(ZLine.ldViaIx(ZRegister.C, offset), ZLine.ldImm8(ZRegister.B, 0))
|
||||
case ZExpressionTarget.DE => List(ZLine.ldViaIx(ZRegister.E, offset), ZLine.ldImm8(ZRegister.D, 0))
|
||||
case ZExpressionTarget.EHL => List(ZLine.ldViaIx(ZRegister.L, offset), ZLine.ldImm8(ZRegister.H, 0), ZLine.ldImm8(ZRegister.E, 0))
|
||||
case ZExpressionTarget.DEHL => List(ZLine.ldViaIx(ZRegister.L, offset), ZLine.ldImm8(ZRegister.H, 0), ZLine.ldImm16(ZRegister.DE, 0))
|
||||
}
|
||||
}
|
||||
|
||||
@ -800,6 +962,8 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
case ZExpressionTarget.HL => List(ZLine.ld8(ZRegister.L, ZRegister.MEM_HL), ZLine.ldImm8(ZRegister.H, 0))
|
||||
case ZExpressionTarget.BC => List(ZLine.ld8(ZRegister.C, ZRegister.MEM_HL), ZLine.ldImm8(ZRegister.B, 0))
|
||||
case ZExpressionTarget.DE => List(ZLine.ld8(ZRegister.E, ZRegister.MEM_HL), ZLine.ldImm8(ZRegister.D, 0))
|
||||
case ZExpressionTarget.EHL => List(ZLine.ld8(ZRegister.L, ZRegister.MEM_HL), ZLine.ldImm8(ZRegister.H, 0), ZLine.ldImm8(ZRegister.E, 0))
|
||||
case ZExpressionTarget.DEHL => List(ZLine.ld8(ZRegister.L, ZRegister.MEM_HL), ZLine.ldImm8(ZRegister.H, 0), ZLine.ldImm16(ZRegister.DE, 0))
|
||||
}
|
||||
}
|
||||
|
||||
@ -1130,7 +1294,34 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
List(ZLine.ldImm8(ZRegister.A, 0))
|
||||
}
|
||||
}
|
||||
case _ => ???
|
||||
case 3 =>
|
||||
List.tabulate(size) {
|
||||
case 0 => compileToEHL(ctx, rhs) :+ ZLine.ld8(ZRegister.A, ZRegister.L)
|
||||
case 1 => List(ZLine.ld8(ZRegister.A, ZRegister.H))
|
||||
case 2 => List(ZLine.ld8(ZRegister.A, ZRegister.E))
|
||||
case _ => List(ZLine.ldImm8(ZRegister.A, 0)) // TODO: signed farwords?
|
||||
}
|
||||
case 4 =>
|
||||
List.tabulate(size) {
|
||||
case 0 => compileToDEHL(ctx, rhs) :+ ZLine.ld8(ZRegister.A, ZRegister.L)
|
||||
case 1 => List(ZLine.ld8(ZRegister.A, ZRegister.H))
|
||||
case 2 => List(ZLine.ld8(ZRegister.A, ZRegister.E))
|
||||
case 3 => List(ZLine.ld8(ZRegister.A, ZRegister.D))
|
||||
case _ => List(ZLine.ldImm8(ZRegister.A, 0)) // TODO: signed longs?
|
||||
}
|
||||
case _ =>
|
||||
rhs match {
|
||||
case FunctionCallExpression(fname, _) =>
|
||||
env.maybeGet[NormalFunction](fname) match {
|
||||
case Some(function) =>
|
||||
val result = env.get[VariableInMemory](function.name + ".return")
|
||||
List.tabulate(size) {
|
||||
case 0 => compile(ctx, rhs, ZExpressionTarget.NOTHING, BranchSpec.None) :+ ZLine.ldAbs8(ZRegister.A, result)
|
||||
case i if i < typ.size => List(ZLine.ldAbs8(ZRegister.A, result.toAddress + i))
|
||||
case _ => List(ZLine.ldImm8(ZRegister.A, 0)) // TODO: signed large types?
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
|
@ -25,16 +25,13 @@ object Z80StatementCompiler extends AbstractStatementCompiler[ZLine] {
|
||||
case ReturnStatement(None) =>
|
||||
fixStackOnReturn(ctx) ++ (ctx.function.returnType match {
|
||||
case _: BooleanType =>
|
||||
List(ZLine.implied(DISCARD_A), ZLine.implied(DISCARD_HL), ZLine.implied(DISCARD_BCDEIX), ZLine.implied(RET))
|
||||
List(ZLine.implied(DISCARD_A), ZLine.implied(DISCARD_HL), ZLine.implied(DISCARD_BC), ZLine.implied(DISCARD_DE), ZLine.implied(RET))
|
||||
case t => t.size match {
|
||||
case 0 =>
|
||||
List(ZLine.implied(DISCARD_F), ZLine.implied(DISCARD_A), ZLine.implied(DISCARD_HL), ZLine.implied(DISCARD_BCDEIX), ZLine.implied(RET))
|
||||
case 1 =>
|
||||
List(ZLine.implied(DISCARD_F), ZLine.implied(DISCARD_A), ZLine.implied(DISCARD_HL), ZLine.implied(DISCARD_BC), ZLine.implied(DISCARD_DE), ZLine.implied(RET))
|
||||
case _ =>
|
||||
ErrorReporting.warn("Returning without a value", options, statement.position)
|
||||
List(ZLine.implied(DISCARD_F), ZLine.implied(DISCARD_A), ZLine.implied(DISCARD_HL), ZLine.implied(DISCARD_BCDEIX), ZLine.implied(RET))
|
||||
case 2 =>
|
||||
ErrorReporting.warn("Returning without a value", options, statement.position)
|
||||
List(ZLine.implied(DISCARD_F), ZLine.implied(DISCARD_A), ZLine.implied(DISCARD_HL), ZLine.implied(DISCARD_BCDEIX), ZLine.implied(RET))
|
||||
List(ZLine.implied(DISCARD_F), ZLine.implied(DISCARD_A), ZLine.implied(DISCARD_HL), ZLine.implied(DISCARD_BC), ZLine.implied(DISCARD_DE), ZLine.implied(RET))
|
||||
}
|
||||
})
|
||||
case ReturnStatement(Some(e)) =>
|
||||
@ -43,13 +40,13 @@ object Z80StatementCompiler extends AbstractStatementCompiler[ZLine] {
|
||||
case 0 =>
|
||||
ErrorReporting.error("Cannot return anything from a void function", statement.position)
|
||||
fixStackOnReturn(ctx) ++
|
||||
List(ZLine.implied(DISCARD_A), ZLine.implied(DISCARD_HL), ZLine.implied(DISCARD_BCDEIX), ZLine.implied(RET))
|
||||
List(ZLine.implied(DISCARD_A), ZLine.implied(DISCARD_HL), ZLine.implied(DISCARD_BC), ZLine.implied(DISCARD_DE), ZLine.implied(RET))
|
||||
case 1 =>
|
||||
Z80ExpressionCompiler.compileToA(ctx, e) ++ fixStackOnReturn(ctx) ++
|
||||
List(ZLine.implied(DISCARD_HL), ZLine.implied(DISCARD_BCDEIX), ZLine.implied(RET))
|
||||
List(ZLine.implied(DISCARD_HL), ZLine.implied(DISCARD_BC), ZLine.implied(DISCARD_DE), ZLine.implied(RET))
|
||||
case 2 =>
|
||||
Z80ExpressionCompiler.compileToHL(ctx, e) ++ fixStackOnReturn(ctx) ++
|
||||
List(ZLine.implied(DISCARD_A), ZLine.implied(DISCARD_BCDEIX), ZLine.implied(RET))
|
||||
List(ZLine.implied(DISCARD_A), ZLine.implied(DISCARD_BC), ZLine.implied(DISCARD_DE), ZLine.implied(RET))
|
||||
}
|
||||
case t =>
|
||||
AbstractExpressionCompiler.checkAssignmentType(ctx, e, ctx.function.returnType)
|
||||
@ -57,13 +54,23 @@ object Z80StatementCompiler extends AbstractStatementCompiler[ZLine] {
|
||||
case 0 =>
|
||||
ErrorReporting.error("Cannot return anything from a void function", statement.position)
|
||||
fixStackOnReturn(ctx) ++
|
||||
List(ZLine.implied(DISCARD_F), ZLine.implied(DISCARD_A), ZLine.implied(DISCARD_HL), ZLine.implied(DISCARD_BCDEIX), ZLine.implied(RET))
|
||||
List(ZLine.implied(DISCARD_F), ZLine.implied(DISCARD_A), ZLine.implied(DISCARD_HL), ZLine.implied(DISCARD_BC), ZLine.implied(DISCARD_DE), ZLine.implied(RET))
|
||||
case 1 =>
|
||||
Z80ExpressionCompiler.compileToA(ctx, e) ++ fixStackOnReturn(ctx) ++
|
||||
List(ZLine.implied(DISCARD_F), ZLine.implied(DISCARD_HL), ZLine.implied(DISCARD_BCDEIX), ZLine.implied(RET))
|
||||
List(ZLine.implied(DISCARD_F), ZLine.implied(DISCARD_HL), ZLine.implied(DISCARD_BC), ZLine.implied(DISCARD_DE), ZLine.implied(RET))
|
||||
case 2 =>
|
||||
Z80ExpressionCompiler.compileToHL(ctx, e) ++ fixStackOnReturn(ctx) ++
|
||||
List(ZLine.implied(DISCARD_F), ZLine.implied(DISCARD_A), ZLine.implied(DISCARD_BCDEIX), ZLine.implied(RET))
|
||||
List(ZLine.implied(DISCARD_F), ZLine.implied(DISCARD_A), ZLine.implied(DISCARD_BC), ZLine.implied(DISCARD_DE), ZLine.implied(RET))
|
||||
case 3 =>
|
||||
Z80ExpressionCompiler.compileToEHL(ctx, e) ++ fixStackOnReturn(ctx) ++
|
||||
List(ZLine.implied(DISCARD_F), ZLine.implied(DISCARD_A), ZLine.implied(DISCARD_BC), ZLine.implied(RET))
|
||||
case 4 =>
|
||||
Z80ExpressionCompiler.compileToDEHL(ctx, e) ++ fixStackOnReturn(ctx) ++
|
||||
List(ZLine.implied(DISCARD_F), ZLine.implied(DISCARD_A), ZLine.implied(DISCARD_BC), ZLine.implied(RET))
|
||||
case _ =>
|
||||
Z80ExpressionCompiler.storeLarge(ctx, VariableExpression(ctx.function.name + ".return"), e) ++ fixStackOnReturn(ctx) ++
|
||||
List(ZLine.implied(DISCARD_F), ZLine.implied(DISCARD_A), ZLine.implied(DISCARD_HL), ZLine.implied(DISCARD_BC), ZLine.implied(DISCARD_DE), ZLine.implied(RET))
|
||||
|
||||
}
|
||||
}
|
||||
case Assignment(destination, source) =>
|
||||
|
17
src/main/scala/millfork/env/Constant.scala
vendored
17
src/main/scala/millfork/env/Constant.scala
vendored
@ -66,7 +66,22 @@ sealed trait Constant {
|
||||
if (requiredSize <= index) Constant.Zero
|
||||
else {
|
||||
// TODO: check if ok
|
||||
CompoundConstant(MathOperator.Or, CompoundConstant(MathOperator.Shl, subbyte(index+1), NumericConstant(8, 1)), subbyte(0)).quickSimplify
|
||||
CompoundConstant(MathOperator.Or, CompoundConstant(MathOperator.Shl, subbyte(index + 1), NumericConstant(8, 1)), subbyte(index)).quickSimplify
|
||||
}
|
||||
}
|
||||
|
||||
def subconstant(offset: Int, length: Int): Constant = {
|
||||
if (offset == 0 && length == requiredSize) {
|
||||
this
|
||||
} else if (length == 1) {
|
||||
subbyte(offset)
|
||||
} else if (offset >= requiredSize) {
|
||||
Constant.Zero
|
||||
} else {
|
||||
((length - 1) to 0 by (-1)).map { i =>
|
||||
val index = i + offset
|
||||
if (i == 0) subbyte(index) else CompoundConstant(MathOperator.Shl, subbyte(index), NumericConstant(8 * i, 1))
|
||||
}.reduceLeft((l, r) => CompoundConstant(MathOperator.Or, l, r).quickSimplify).quickSimplify
|
||||
}
|
||||
}
|
||||
|
||||
|
156
src/main/scala/millfork/env/Environment.scala
vendored
156
src/main/scala/millfork/env/Environment.scala
vendored
@ -3,7 +3,7 @@ package millfork.env
|
||||
import java.util.concurrent.atomic.AtomicLong
|
||||
|
||||
import millfork.assembly.BranchingOpcodeMapping
|
||||
import millfork.{CompilationFlag, CompilationOptions, CpuFamily}
|
||||
import millfork.{CompilationFlag, CompilationOptions, Cpu, CpuFamily}
|
||||
import millfork.assembly.mos.Opcode
|
||||
import millfork.assembly.z80.{IfFlagClear, IfFlagSet, ZFlag}
|
||||
import millfork.error.ErrorReporting
|
||||
@ -113,6 +113,10 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
|
||||
Nil
|
||||
case NormalParamSignature(List(MemoryVariable(_, typ, _))) if typ.size == 2 && options.platform.cpuFamily == CpuFamily.I80 =>
|
||||
Nil
|
||||
case NormalParamSignature(List(MemoryVariable(_, typ, _))) if typ.size == 3 && options.platform.cpuFamily == CpuFamily.I80 =>
|
||||
Nil
|
||||
case NormalParamSignature(List(MemoryVariable(_, typ, _))) if typ.size == 4 && options.platform.cpuFamily == CpuFamily.I80 =>
|
||||
Nil
|
||||
case NormalParamSignature(ps) =>
|
||||
ps.map(p => p.name)
|
||||
case _ =>
|
||||
@ -233,7 +237,11 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
|
||||
t.asInstanceOf[T]
|
||||
} else {
|
||||
t match {
|
||||
case Alias(_, target) => root.get[T](target)
|
||||
case Alias(_, target, deprectated) =>
|
||||
if (deprectated) {
|
||||
ErrorReporting.info(s"Alias `$name` is deprecated, use `$target` instead", position)
|
||||
}
|
||||
root.get[T](target)
|
||||
case _ => ErrorReporting.fatal(s"`$name` is not a ${clazz.getSimpleName}", position)
|
||||
}
|
||||
}
|
||||
@ -254,7 +262,11 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
|
||||
Some(t.asInstanceOf[T])
|
||||
} else {
|
||||
t match {
|
||||
case Alias(_, target) => root.maybeGet[T](target)
|
||||
case Alias(_, target, deprectated) =>
|
||||
if (deprectated) {
|
||||
ErrorReporting.info(s"Alias `$name` is deprecated, use `$target` instead")
|
||||
}
|
||||
root.maybeGet[T](target)
|
||||
case _ => None
|
||||
}
|
||||
}
|
||||
@ -302,12 +314,30 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
|
||||
val w = BasicPlainType("word", 2)
|
||||
addThing(b, None)
|
||||
addThing(w, None)
|
||||
addThing(BasicPlainType("farword", 3), None)
|
||||
addThing(BasicPlainType("long", 4), None)
|
||||
addThing(Alias("int8", "byte"), None)
|
||||
addThing(Alias("int16", "word"), None)
|
||||
addThing(BasicPlainType("int24", 3), None)
|
||||
addThing(Alias("farword", "int24", deprecated = true), None)
|
||||
addThing(BasicPlainType("int32", 4), None)
|
||||
addThing(Alias("long", "int32"), None)
|
||||
addThing(BasicPlainType("int40", 5), None)
|
||||
addThing(BasicPlainType("int48", 6), None)
|
||||
addThing(BasicPlainType("int56", 7), None)
|
||||
addThing(BasicPlainType("int64", 8), None)
|
||||
addThing(BasicPlainType("int72", 9), None)
|
||||
addThing(BasicPlainType("int80", 10), None)
|
||||
addThing(BasicPlainType("int88", 11), None)
|
||||
addThing(BasicPlainType("int96", 12), None)
|
||||
addThing(BasicPlainType("int104", 13), None)
|
||||
addThing(BasicPlainType("int112", 14), None)
|
||||
addThing(BasicPlainType("int120", 15), None)
|
||||
addThing(BasicPlainType("int128", 16), None)
|
||||
addThing(DerivedPlainType("pointer", w, isSigned = false), None)
|
||||
// addThing(DerivedPlainType("farpointer", get[PlainType]("farword"), isSigned = false), None)
|
||||
addThing(DerivedPlainType("ubyte", b, isSigned = false), None)
|
||||
addThing(DerivedPlainType("sbyte", b, isSigned = true), None)
|
||||
addThing(Alias("unsigned8", "ubyte"), None)
|
||||
addThing(Alias("signed8", "sbyte"), None)
|
||||
val trueType = ConstantBooleanType("true$", value = true)
|
||||
val falseType = ConstantBooleanType("false$", value = false)
|
||||
addThing(trueType, None)
|
||||
@ -315,6 +345,7 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
|
||||
addThing(ConstantThing("true", NumericConstant(0, 0), trueType), None)
|
||||
addThing(ConstantThing("false", NumericConstant(0, 0), falseType), None)
|
||||
addThing(ConstantThing("__zeropage_usage", UnexpandedConstant("__zeropage_usage", 1), b), None)
|
||||
addThing(ConstantThing("__heap_start", UnexpandedConstant("__heap_start", 1), b), None)
|
||||
addThing(FlagBooleanType("set_carry",
|
||||
BranchingOpcodeMapping(Opcode.BCS, IfFlagSet(ZFlag.C)),
|
||||
BranchingOpcodeMapping(Opcode.BCC, IfFlagClear(ZFlag.C))),
|
||||
@ -673,6 +704,9 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
|
||||
env.get[MemoryVariable](pd.assemblyParamPassingConvention.asInstanceOf[ByVariable].name)
|
||||
})
|
||||
}
|
||||
if (resultType.size > Cpu.getMaxSizeReturnableViaRegisters(options.platform.cpu, options)) {
|
||||
registerVariable(VariableDeclarationStatement(stmt.name + ".return", stmt.resultType, None, global = true, stack = false, constant = false, volatile = false, register = false, None, None), options)
|
||||
}
|
||||
stmt.statements match {
|
||||
case None =>
|
||||
stmt.address match {
|
||||
@ -712,7 +746,7 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
|
||||
resultType,
|
||||
params,
|
||||
env,
|
||||
executableStatements ++ (if (needsExtraRTS) List(MosAssemblyStatement.implied(Opcode.RTS, elidable = true)) else Nil)
|
||||
executableStatements
|
||||
)
|
||||
addThing(mangled, stmt.position)
|
||||
} else {
|
||||
@ -772,28 +806,12 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
|
||||
stmt.assemblyParamPassingConvention match {
|
||||
case ByVariable(name) =>
|
||||
val zp = typ.name == "pointer" // TODO
|
||||
val v = UninitializedMemoryVariable(prefix + name, typ, if (zp) VariableAllocationMethod.Zeropage else VariableAllocationMethod.Auto, None)
|
||||
val v = UninitializedMemoryVariable(prefix + name, typ, if (zp) VariableAllocationMethod.Zeropage else VariableAllocationMethod.Auto, None)
|
||||
addThing(v, stmt.position)
|
||||
registerAddressConstant(v, stmt.position, options)
|
||||
val addr = v.toAddress
|
||||
typ.size match {
|
||||
case 2 =>
|
||||
addThing(RelativeVariable(v.name + ".hi", addr + 1, b, zeropage = zp, None), stmt.position)
|
||||
addThing(RelativeVariable(v.name + ".lo", addr, b, zeropage = zp, None), stmt.position)
|
||||
case 3 =>
|
||||
addThing(RelativeVariable(v.name + ".hiword", addr + 1, w, zeropage = zp, None), stmt.position)
|
||||
addThing(RelativeVariable(v.name + ".loword", addr, w, zeropage = zp, None), stmt.position)
|
||||
addThing(RelativeVariable(v.name + ".b2", addr + 2, b, zeropage = zp, None), stmt.position)
|
||||
addThing(RelativeVariable(v.name + ".b1", addr + 1, b, zeropage = zp, None), stmt.position)
|
||||
addThing(RelativeVariable(v.name + ".b0", addr, b, zeropage = zp, None), stmt.position)
|
||||
case 4 =>
|
||||
addThing(RelativeVariable(v.name + ".hiword", addr + 2, w, zeropage = zp, None), stmt.position)
|
||||
addThing(RelativeVariable(v.name + ".loword", addr, w, zeropage = zp, None), stmt.position)
|
||||
addThing(RelativeVariable(v.name + ".b3", addr + 3, b, zeropage = zp, None), stmt.position)
|
||||
addThing(RelativeVariable(v.name + ".b2", addr + 2, b, zeropage = zp, None), stmt.position)
|
||||
addThing(RelativeVariable(v.name + ".b1", addr + 1, b, zeropage = zp, None), stmt.position)
|
||||
addThing(RelativeVariable(v.name + ".b0", addr, b, zeropage = zp, None), stmt.position)
|
||||
case _ =>
|
||||
for((suffix, offset, t) <- getSubvariables(typ)) {
|
||||
addThing(RelativeVariable(v.name + suffix, addr + offset, t, zeropage = zp, None), stmt.position)
|
||||
}
|
||||
case ByMosRegister(_) => ()
|
||||
case ByZRegister(_) => ()
|
||||
@ -1005,24 +1023,8 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
|
||||
val constantValue: Constant = stmt.initialValue.flatMap(eval).getOrElse(Constant.error(s"`$name` has a non-constant value", position))
|
||||
if (constantValue.requiredSize > typ.size) ErrorReporting.error(s"`$name` is has an invalid value: not in the range of `$typ`", position)
|
||||
addThing(ConstantThing(prefix + name, constantValue, typ), stmt.position)
|
||||
typ.size match {
|
||||
case 2 =>
|
||||
addThing(ConstantThing(prefix + name + ".hi", constantValue.hiByte, b), stmt.position)
|
||||
addThing(ConstantThing(prefix + name + ".lo", constantValue.loByte, b), stmt.position)
|
||||
case 3 =>
|
||||
addThing(ConstantThing(prefix + name + ".hiword", constantValue.subword(1), b), stmt.position)
|
||||
addThing(ConstantThing(prefix + name + ".loword", constantValue.subword(0), b), stmt.position)
|
||||
addThing(ConstantThing(prefix + name + ".b2", constantValue.subbyte(2), b), stmt.position)
|
||||
addThing(ConstantThing(prefix + name + ".b1", constantValue.hiByte, b), stmt.position)
|
||||
addThing(ConstantThing(prefix + name + ".b0", constantValue.loByte, b), stmt.position)
|
||||
case 4 =>
|
||||
addThing(ConstantThing(prefix + name + ".hiword", constantValue.subword(2), b), stmt.position)
|
||||
addThing(ConstantThing(prefix + name + ".loword", constantValue.subword(0), b), stmt.position)
|
||||
addThing(ConstantThing(prefix + name + ".b3", constantValue.subbyte(3), b), stmt.position)
|
||||
addThing(ConstantThing(prefix + name + ".b2", constantValue.subbyte(2), b), stmt.position)
|
||||
addThing(ConstantThing(prefix + name + ".b1", constantValue.hiByte, b), stmt.position)
|
||||
addThing(ConstantThing(prefix + name + ".b0", constantValue.loByte, b), stmt.position)
|
||||
case _ =>
|
||||
for((suffix, offset, t) <- getSubvariables(typ)) {
|
||||
addThing(ConstantThing(prefix + name + suffix, constantValue.subconstant(offset, t.size), t), stmt.position)
|
||||
}
|
||||
} else {
|
||||
if (stmt.stack && stmt.global) ErrorReporting.error(s"`$name` is static or global and cannot be on stack", position)
|
||||
@ -1036,24 +1038,8 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
|
||||
val v = StackVariable(prefix + name, typ, this.baseStackOffset)
|
||||
baseStackOffset += typ.size
|
||||
addThing(v, stmt.position)
|
||||
typ.size match {
|
||||
case 2 =>
|
||||
addThing(StackVariable(prefix + name + ".hi", b, baseStackOffset + 1), stmt.position)
|
||||
addThing(StackVariable(prefix + name + ".lo", b, baseStackOffset), stmt.position)
|
||||
case 3 =>
|
||||
addThing(StackVariable(prefix + name + ".hiword", w, baseStackOffset + 1), stmt.position)
|
||||
addThing(StackVariable(prefix + name + ".loword", w, baseStackOffset), stmt.position)
|
||||
addThing(StackVariable(prefix + name + ".b2", b, baseStackOffset + 2), stmt.position)
|
||||
addThing(StackVariable(prefix + name + ".b1", b, baseStackOffset + 1), stmt.position)
|
||||
addThing(StackVariable(prefix + name + ".b0", b, baseStackOffset), stmt.position)
|
||||
case 4 =>
|
||||
addThing(StackVariable(prefix + name + ".hiword", w, baseStackOffset + 2), stmt.position)
|
||||
addThing(StackVariable(prefix + name + ".loword", w, baseStackOffset), stmt.position)
|
||||
addThing(StackVariable(prefix + name + ".b3", b, baseStackOffset + 3), stmt.position)
|
||||
addThing(StackVariable(prefix + name + ".b2", b, baseStackOffset + 2), stmt.position)
|
||||
addThing(StackVariable(prefix + name + ".b1", b, baseStackOffset + 1), stmt.position)
|
||||
addThing(StackVariable(prefix + name + ".b0", b, baseStackOffset), stmt.position)
|
||||
case _ =>
|
||||
for((suffix, offset, t) <- getSubvariables(typ)) {
|
||||
addThing(StackVariable(prefix + name + suffix, t, baseStackOffset + offset), stmt.position)
|
||||
}
|
||||
} else {
|
||||
val (v, addr) = stmt.address.fold[(VariableInMemory, Constant)]({
|
||||
@ -1089,29 +1075,41 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
|
||||
if (!v.isInstanceOf[MemoryVariable]) {
|
||||
addThing(ConstantThing(v.name + "`", addr, b), stmt.position)
|
||||
}
|
||||
typ.size match {
|
||||
case 2 =>
|
||||
addThing(RelativeVariable(prefix + name + ".hi", addr + 1, b, zeropage = v.zeropage, declaredBank = stmt.bank), stmt.position)
|
||||
addThing(RelativeVariable(prefix + name + ".lo", addr, b, zeropage = v.zeropage, declaredBank = stmt.bank), stmt.position)
|
||||
case 3 =>
|
||||
addThing(RelativeVariable(prefix + name + ".hiword", addr + 1, w, zeropage = v.zeropage, declaredBank = stmt.bank), stmt.position)
|
||||
addThing(RelativeVariable(prefix + name + ".loword", addr, w, zeropage = v.zeropage, declaredBank = stmt.bank), stmt.position)
|
||||
addThing(RelativeVariable(prefix + name + ".b2", addr + 2, b, zeropage = v.zeropage, declaredBank = stmt.bank), stmt.position)
|
||||
addThing(RelativeVariable(prefix + name + ".b1", addr + 1, b, zeropage = v.zeropage, declaredBank = stmt.bank), stmt.position)
|
||||
addThing(RelativeVariable(prefix + name + ".b0", addr, b, zeropage = v.zeropage, declaredBank = stmt.bank), stmt.position)
|
||||
case 4 =>
|
||||
addThing(RelativeVariable(prefix + name + ".hiword", addr + 2, w, zeropage = v.zeropage, declaredBank = stmt.bank), stmt.position)
|
||||
addThing(RelativeVariable(prefix + name + ".loword", addr, w, zeropage = v.zeropage, declaredBank = stmt.bank), stmt.position)
|
||||
addThing(RelativeVariable(prefix + name + ".b3", addr + 3, b, zeropage = v.zeropage, declaredBank = stmt.bank), stmt.position)
|
||||
addThing(RelativeVariable(prefix + name + ".b2", addr + 2, b, zeropage = v.zeropage, declaredBank = stmt.bank), stmt.position)
|
||||
addThing(RelativeVariable(prefix + name + ".b1", addr + 1, b, zeropage = v.zeropage, declaredBank = stmt.bank), stmt.position)
|
||||
addThing(RelativeVariable(prefix + name + ".b0", addr, b, zeropage = v.zeropage, declaredBank = stmt.bank), stmt.position)
|
||||
case _ =>
|
||||
for((suffix, offset, t) <- getSubvariables(typ)) {
|
||||
addThing(RelativeVariable(prefix + name + suffix, addr + offset, t, zeropage = v.zeropage, declaredBank = stmt.bank), stmt.position)
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
|
||||
def getSubvariables(typ: Type): List[(String, Int, VariableType)] = {
|
||||
val b = get[VariableType]("byte")
|
||||
val w = get[VariableType]("word")
|
||||
typ match {
|
||||
case _: PlainType => typ.size match {
|
||||
case 2 => List(
|
||||
(".lo", 0, b),
|
||||
(".hi", 1, b))
|
||||
case 3 => List(
|
||||
(".loword", 0, w),
|
||||
(".hiword", 1, w),
|
||||
(".b0", 0, b),
|
||||
(".b1", 1, b),
|
||||
(".b2", 2, b))
|
||||
case 4 => List(
|
||||
(".loword", 0, w),
|
||||
(".hiword", 2, w),
|
||||
(".b0", 0, b),
|
||||
(".b1", 1, b),
|
||||
(".b2", 2, b),
|
||||
(".b3", 3, b))
|
||||
case sz if sz > 4 => List.tabulate(sz){ i => (".b" + i, i, b) }
|
||||
case _ => Nil
|
||||
}
|
||||
case _ => Nil
|
||||
}
|
||||
}
|
||||
|
||||
def lookup[T <: Thing : Manifest](name: String): Option[T] = {
|
||||
if (things.contains(name)) {
|
||||
maybeGet(name)
|
||||
|
2
src/main/scala/millfork/env/Thing.scala
vendored
2
src/main/scala/millfork/env/Thing.scala
vendored
@ -9,7 +9,7 @@ sealed trait Thing {
|
||||
def name: String
|
||||
}
|
||||
|
||||
case class Alias(name: String, target: String) extends Thing
|
||||
case class Alias(name: String, target: String, deprecated: Boolean = false) extends Thing
|
||||
|
||||
sealed trait CallableThing extends Thing
|
||||
|
||||
|
@ -70,9 +70,9 @@ class Z80Assembler(program: Program,
|
||||
case ZLine(BYTE, NoRegisters, param, _) =>
|
||||
writeByte(bank, index, param)
|
||||
index + 1
|
||||
case ZLine(DISCARD_F | DISCARD_HL | DISCARD_BCDEIX | DISCARD_A, NoRegisters, _, _) =>
|
||||
case ZLine(DISCARD_F | DISCARD_HL | DISCARD_BC | DISCARD_DE | DISCARD_IX | DISCARD_IY | DISCARD_A, NoRegisters, _, _) =>
|
||||
index
|
||||
case ZLine(LABEL | BYTE | DISCARD_F | DISCARD_HL | DISCARD_BCDEIX | DISCARD_A, _, _, _) =>
|
||||
case ZLine(LABEL | BYTE | DISCARD_F | DISCARD_HL | DISCARD_BC | DISCARD_DE | DISCARD_IX | DISCARD_IY | DISCARD_A, _, _, _) =>
|
||||
???
|
||||
case ZLine(RST, NoRegisters, param, _) =>
|
||||
val opcode = param.quickSimplify match {
|
||||
|
@ -198,4 +198,132 @@ class LongTest extends FunSuite with Matchers {
|
||||
m.readLong(0xc018) should equal(0xffffffff)
|
||||
}
|
||||
}
|
||||
|
||||
test("Returning long") {
|
||||
EmuCrossPlatformBenchmarkRun(Cpu.Mos, Cpu.Z80, Cpu.Intel8080, Cpu.Sharp)(
|
||||
"""
|
||||
| long output @$c000
|
||||
| void main () {
|
||||
| output = l($91929394)
|
||||
| }
|
||||
| long l(long param) {
|
||||
| return param
|
||||
| }
|
||||
""".stripMargin) { m =>
|
||||
m.readLong(0xc000) should equal(0x91929394)
|
||||
}
|
||||
}
|
||||
|
||||
test("Various combinations involving promotions") {
|
||||
EmuCrossPlatformBenchmarkRun(Cpu.Mos, Cpu.Z80, Cpu.Intel8080, Cpu.Sharp)(
|
||||
"""
|
||||
| long output0 @$c000
|
||||
| long output1 @$c004
|
||||
| long output2 @$c008
|
||||
| long output3 @$c00c
|
||||
| long output4 @$c010
|
||||
| long output5 @$c014
|
||||
| long output6 @$c018
|
||||
|
|
||||
| farword f0 @$c020
|
||||
| farword f1 @$c023
|
||||
| farword f2 @$c026
|
||||
| void main () {
|
||||
| output0 = ll($91929394)
|
||||
| output1 = lf($929394)
|
||||
| output2 = ff($929394)
|
||||
| output3 = lw($9394)
|
||||
| output4 = fw($9394)
|
||||
| output5 = lb($94)
|
||||
| output6 = fb($94)
|
||||
|
|
||||
| f0 = ff($929394)
|
||||
| f1 = fw($9394)
|
||||
| f2 = fb($94)
|
||||
| }
|
||||
| long ll(long param) {
|
||||
| return param
|
||||
| }
|
||||
| long lf(farword param) {
|
||||
| return param
|
||||
| }
|
||||
| long lw(word param) {
|
||||
| return param
|
||||
| }
|
||||
| long lb(byte param) {
|
||||
| return param
|
||||
| }
|
||||
| farword ff(farword param) {
|
||||
| return param
|
||||
| }
|
||||
| farword fw(word param) {
|
||||
| return param
|
||||
| }
|
||||
| farword fb(byte param) {
|
||||
| return param
|
||||
| }
|
||||
""".stripMargin) { m =>
|
||||
m.readLong(0xc000) should equal(0x91929394)
|
||||
m.readLong(0xc004) should equal(0x929394)
|
||||
m.readLong(0xc008) should equal(0x929394)
|
||||
m.readLong(0xc00c) should equal(0x9394)
|
||||
m.readLong(0xc010) should equal(0x9394)
|
||||
m.readLong(0xc014) should equal(0x94)
|
||||
m.readLong(0xc018) should equal(0x94)
|
||||
m.readMedium(0xc020) should equal(0x929394)
|
||||
m.readMedium(0xc023) should equal(0x9394)
|
||||
m.readMedium(0xc026) should equal(0x94)
|
||||
}
|
||||
}
|
||||
|
||||
test("Larger than long") {
|
||||
EmuCrossPlatformBenchmarkRun(Cpu.Mos, Cpu.Z80, Cpu.Intel8080, Cpu.Sharp)(
|
||||
"""
|
||||
| int64 output0 @$c000
|
||||
| int64 output1 @$c008
|
||||
| int64 output2 @$c010
|
||||
| int64 output3 @$c018
|
||||
| int64 output4 @$c020
|
||||
|
|
||||
| void main () {
|
||||
| output0 = xl($91929394)
|
||||
| output1 = xf($929394)
|
||||
| output2 = xw($9394)
|
||||
| output3 = xb($94)
|
||||
| output4 = xx($91929394)
|
||||
| }
|
||||
| int64 xl(long param) {
|
||||
| return param
|
||||
| }
|
||||
| int64 xf(farword param) {
|
||||
| return param
|
||||
| }
|
||||
| int64 xw(word param) {
|
||||
| return param
|
||||
| }
|
||||
| int64 xb(byte param) {
|
||||
| return param
|
||||
| }
|
||||
| int64 xx(int64 param) {
|
||||
| param.b4 += 1
|
||||
| param.b5 += 1
|
||||
| param.b6 += 1
|
||||
| param.b7 += 1
|
||||
| return param
|
||||
| }
|
||||
""".stripMargin) { m =>
|
||||
m.readLong(0xc000) should equal(0x91929394)
|
||||
m.readLong(0xc008) should equal(0x929394)
|
||||
m.readLong(0xc010) should equal(0x9394)
|
||||
m.readLong(0xc018) should equal(0x94)
|
||||
|
||||
m.readLong(0xc004) should equal(0)
|
||||
m.readLong(0xc00c) should equal(0)
|
||||
m.readLong(0xc014) should equal(0)
|
||||
m.readLong(0xc01c) should equal(0)
|
||||
|
||||
m.readLong(0xc020) should equal(0x91929394)
|
||||
m.readLong(0xc024) should equal(0x01010101)
|
||||
}
|
||||
}
|
||||
}
|
||||
|
Loading…
x
Reference in New Issue
Block a user