mirror of
https://github.com/KarolS/millfork.git
synced 2025-01-10 20:29:35 +00:00
Unsigned byte division by non-constant
This commit is contained in:
parent
010b44f23e
commit
2583f280a8
@ -20,7 +20,7 @@
|
||||
|
||||
* Added structs and unions.
|
||||
|
||||
* Added unsigned byte division and modulo by a constant.
|
||||
* Added unsigned byte division and modulo.
|
||||
|
||||
* Pointers can now be allocated anywhere.
|
||||
|
||||
|
@ -52,9 +52,6 @@ In the descriptions below, arguments to the operators are explained as follows:
|
||||
|
||||
* `constant` means a compile-time constant
|
||||
|
||||
* `simpleconstant` means a compile-time constant evaluable at the first compilation pass
|
||||
(eg. a literal or a combination of literals, not an undefined address)
|
||||
|
||||
* `simple` means either: a constant, a non-stack variable,
|
||||
a pointer indexed with a constant, a pointer indexed with a non-stack variable,
|
||||
an array indexed with a constant, an array indexed with a non-stack variable,
|
||||
@ -96,7 +93,7 @@ TODO
|
||||
|
||||
* `/`, `%%`: unsigned division and unsigned modulo
|
||||
|
||||
`byte / simpleconstant byte`
|
||||
`byte / byte`
|
||||
`constant word / constant word`
|
||||
`constant long / constant long`
|
||||
|
||||
|
@ -50,6 +50,39 @@ noinline asm byte __mul_u8u8u8() {
|
||||
|
||||
#endif
|
||||
|
||||
noinline asm void __divmod_u16u8u16u8() {
|
||||
? XOR A
|
||||
? LD B, 16
|
||||
__divmod_u16u8u16u8_loop:
|
||||
? ADD HL,HL
|
||||
? RLA
|
||||
#if CPUFEATURE_Z80 || CPUFEATURE_GAMEBOY
|
||||
? JR C, __divmod_u16u8u16u8_overflow
|
||||
#else
|
||||
? JP C, __divmod_u16u8u16u8_overflow
|
||||
#endif
|
||||
? CP D
|
||||
#if CPUFEATURE_Z80 || CPUFEATURE_GAMEBOY
|
||||
? JR C, __divmod_u16u8u16u8_skip
|
||||
#else
|
||||
? JP C, __divmod_u16u8u16u8_skip
|
||||
#endif
|
||||
__divmod_u16u8u16u8_overflow:
|
||||
? SUB D
|
||||
? INC L
|
||||
__divmod_u16u8u16u8_skip:
|
||||
#if CPUFEATURE_Z80
|
||||
? DJNZ __divmod_u16u8u16u8_loop
|
||||
#elseif CPUFEATURE_GAMEBOY
|
||||
? DEC B
|
||||
? JR NZ, __divmod_u16u8u16u8_loop
|
||||
#else
|
||||
? DEC B
|
||||
? JP NZ, __divmod_u16u8u16u8_loop
|
||||
#endif
|
||||
? RET
|
||||
}
|
||||
|
||||
inline asm word __mul_u16u8u16() {
|
||||
? LD HL,0
|
||||
? LD B,8
|
||||
|
@ -18,6 +18,31 @@ __mul_u8u8u8_start:
|
||||
? RTS
|
||||
}
|
||||
|
||||
// divide __reg[0]/__reg[1]
|
||||
|
||||
noinline asm byte __mod_u8u8u8u8() {
|
||||
? LDA #0
|
||||
? LDX #7
|
||||
? CLC
|
||||
__divmod_u8u8u8u8_start:
|
||||
? ROL __reg
|
||||
? ROL
|
||||
? CMP __reg+1
|
||||
? BCC __divmod_u8u8u8u8_skip
|
||||
? SBC __reg+1
|
||||
__divmod_u8u8u8u8_skip:
|
||||
? DEX
|
||||
? BPL __divmod_u8u8u8u8_start
|
||||
? ROL __reg
|
||||
? RTS
|
||||
}
|
||||
|
||||
asm byte __div_u8u8u8u8() {
|
||||
? JSR __mod_u8u8u8u8
|
||||
? LDA __reg
|
||||
? RTS
|
||||
}
|
||||
|
||||
#if ZPREG_SIZE >= 3
|
||||
|
||||
noinline asm word __mul_u16u8u16() {
|
||||
|
@ -13,6 +13,8 @@ object ZeropageRegisterOptimizations {
|
||||
|
||||
val functionsThatUsePseudoregisterAsInput: Map[String, Set[Int]] = Map(
|
||||
"__mul_u8u8u8" -> Set(0, 1),
|
||||
"__mod_u8u8u8u8" -> Set(0, 1),
|
||||
"__div_u8u8u8u8" -> Set(0, 1),
|
||||
"__mul_u16u8u16" -> Set(0, 1, 2),
|
||||
"__adc_decimal" -> Set(2, 3),
|
||||
"__sbc_decimal" -> Set(2, 3),
|
||||
|
@ -25,7 +25,7 @@ object CoarseFlowAnalyzer {
|
||||
val preservesB: Set[String] = Set("__mul_u8u8u8")
|
||||
val preservesC: Set[String] = if (z80) Set("__mul_u8u8u8") else Set()
|
||||
val preservesD: Set[String] = Set()
|
||||
val preservesE: Set[String] = Set()
|
||||
val preservesE: Set[String] = Set("__divmod_u16u8u16u8")
|
||||
val preservesH: Set[String] = Set("__mul_u8u8u8")
|
||||
val preservesL: Set[String] = Set("__mul_u8u8u8")
|
||||
|
||||
|
@ -186,10 +186,10 @@ object ReverseFlowAnalyzer {
|
||||
val readsA = Set("__mul_u8u8u8", "__mul_u16u8u16")
|
||||
val readsB = Set("")
|
||||
val readsC = Set("")
|
||||
val readsD = Set("__mul_u8u8u8","__mul_u16u8u16")
|
||||
val readsD = Set("__mul_u8u8u8","__mul_u16u8u16", "__divmod_u16u8u16u8")
|
||||
val readsE = Set("__mul_u16u8u16")
|
||||
val readsH = Set("")
|
||||
val readsL = Set("")
|
||||
val readsH = Set("__divmod_u16u8u16u8")
|
||||
val readsL = Set("__divmod_u16u8u16u8")
|
||||
|
||||
//noinspection RedundantNewCaseClass
|
||||
def analyze(f: NormalFunction, code: List[ZLine]): List[CpuImportance] = {
|
||||
|
@ -1028,12 +1028,12 @@ object BuiltIns {
|
||||
} else {
|
||||
compileUnsignedByteDivision(ctx, p, qq.toInt, modulo)
|
||||
}
|
||||
case Some(_) =>
|
||||
ctx.log.error("Unsigned division by unknown constant", q.position)
|
||||
Nil
|
||||
case None =>
|
||||
ctx.log.error("Unsigned division by a variable expression", q.position)
|
||||
Nil
|
||||
case _ =>
|
||||
if (modulo) {
|
||||
PseudoregisterBuiltIns.compileUnsignedByteModulo(ctx, Some(p), q, storeInRegLo = false)
|
||||
} else {
|
||||
PseudoregisterBuiltIns.compileUnsignedByteDivision(ctx, Some(p), q, storeInRegLo = false)
|
||||
}
|
||||
}
|
||||
}
|
||||
def compileUnsignedByteDivision(ctx: CompilationContext, p: Expression, q: Int, modulo: Boolean): List[AssemblyLine] = {
|
||||
|
@ -338,7 +338,14 @@ object PseudoregisterBuiltIns {
|
||||
}
|
||||
}
|
||||
|
||||
def compileByteMultiplication(ctx: CompilationContext, param1OrRegister: Option[Expression], param2: Expression, storeInRegLo: Boolean): List[AssemblyLine] = {
|
||||
def compileByteMultiplication(ctx: CompilationContext, param1OrRegister: Option[Expression], param2: Expression, storeInRegLo: Boolean): List[AssemblyLine] =
|
||||
compileByteMultiplicationOrDivision(ctx, param1OrRegister, param2, storeInRegLo, "__mul_u8u8u8", commutative = true)
|
||||
def compileUnsignedByteDivision(ctx: CompilationContext, param1OrRegister: Option[Expression], param2: Expression, storeInRegLo: Boolean): List[AssemblyLine] =
|
||||
compileByteMultiplicationOrDivision(ctx, param1OrRegister, param2, storeInRegLo, "__div_u8u8u8u8", commutative = false)
|
||||
def compileUnsignedByteModulo(ctx: CompilationContext, param1OrRegister: Option[Expression], param2: Expression, storeInRegLo: Boolean): List[AssemblyLine] =
|
||||
compileByteMultiplicationOrDivision(ctx, param1OrRegister, param2, storeInRegLo, "__mod_u8u8u8u8", commutative = false)
|
||||
|
||||
def compileByteMultiplicationOrDivision(ctx: CompilationContext, param1OrRegister: Option[Expression], param2: Expression, storeInRegLo: Boolean, functionName: String, commutative: Boolean): List[AssemblyLine] = {
|
||||
if (ctx.options.zpRegisterSize < 2) {
|
||||
ctx.log.error("Variable byte multiplication requires the zeropage pseudoregister", param1OrRegister.flatMap(_.position))
|
||||
return Nil
|
||||
@ -352,10 +359,16 @@ object PseudoregisterBuiltIns {
|
||||
val code2 = MosExpressionCompiler.compile(ctx, param2, Some(b -> RegisterVariable(MosRegister.A, b)), BranchSpec.None)
|
||||
if (!usesRegLo(code2)) {
|
||||
code1 ++ List(AssemblyLine.zeropage(STA, reg)) ++ code2 ++ List(AssemblyLine.zeropage(STA, reg, 1))
|
||||
} else if (!commutative) {
|
||||
code2 ++ List(AssemblyLine.implied(PHA)) ++ MosExpressionCompiler.fixTsx(code1) ++ List(
|
||||
AssemblyLine.zeropage(STA, reg),
|
||||
AssemblyLine.implied(PLA),
|
||||
AssemblyLine.zeropage(STA, reg, 1)
|
||||
)
|
||||
} else if (!usesRegLo(code1)) {
|
||||
code2 ++ List(AssemblyLine.zeropage(STA, reg)) ++ code1 ++ List(AssemblyLine.zeropage(STA, reg, 1))
|
||||
} else {
|
||||
code1 ++ List(AssemblyLine.implied(PHA)) ++ code2 ++ List(
|
||||
code1 ++ List(AssemblyLine.implied(PHA)) ++ MosExpressionCompiler.fixTsx(code2) ++ List(
|
||||
AssemblyLine.zeropage(STA, reg),
|
||||
AssemblyLine.implied(PLA),
|
||||
AssemblyLine.zeropage(STA, reg, 1)
|
||||
@ -365,6 +378,12 @@ object PseudoregisterBuiltIns {
|
||||
val code2 = MosExpressionCompiler.compile(ctx, param2, Some(b -> RegisterVariable(MosRegister.A, b)), BranchSpec.None)
|
||||
if (!usesRegLo(code2)) {
|
||||
List(AssemblyLine.zeropage(STA, reg)) ++ code2 ++ List(AssemblyLine.zeropage(STA, reg, 1))
|
||||
} else if (!commutative) {
|
||||
List(AssemblyLine.implied(PHA)) ++ MosExpressionCompiler.fixTsx(code2) ++ List(
|
||||
AssemblyLine.zeropage(STA, reg, 1),
|
||||
AssemblyLine.implied(PLA),
|
||||
AssemblyLine.zeropage(STA, reg)
|
||||
)
|
||||
} else if (!usesRegHi(code2)) {
|
||||
List(AssemblyLine.zeropage(STA, reg, 1)) ++ code2 ++ List(AssemblyLine.zeropage(STA, reg))
|
||||
} else {
|
||||
@ -375,7 +394,7 @@ object PseudoregisterBuiltIns {
|
||||
)
|
||||
}
|
||||
}
|
||||
val calculate = AssemblyLine.absoluteOrLongAbsolute(JSR, ctx.env.get[FunctionInMemory]("__mul_u8u8u8"), ctx.options) ::
|
||||
val calculate = AssemblyLine.absoluteOrLongAbsolute(JSR, ctx.env.get[FunctionInMemory](functionName), ctx.options) ::
|
||||
(if (storeInRegLo) List(AssemblyLine.zeropage(STA, reg)) else Nil)
|
||||
load ++ calculate
|
||||
}
|
||||
|
@ -886,8 +886,10 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
size match {
|
||||
case 1 =>
|
||||
calculateAddressToAppropriatePointer(ctx, l, forWriting = true) match {
|
||||
case Some((LocalVariableAddressViaHL, List(ZLine0(LD_16, TwoRegisters(ZRegister.HL, ZRegister.IMM_16), addr)))) =>
|
||||
Z80Multiply.compileUnsignedByteDivision(ctx, Right(l), r, f.functionName == "%%=") :+ ZLine.ldAbs8(addr, ZRegister.A)
|
||||
case Some((lvo, code)) =>
|
||||
code ++ (Z80Multiply.compileUnsignedByteDivision(ctx, l, r, f.functionName == "%%=") :+ ZLine.ld8(lvo, ZRegister.A))
|
||||
code ++ (stashHLIfChanged(ctx, Z80Multiply.compileUnsignedByteDivision(ctx, Left(lvo), r, f.functionName == "%%=")) :+ ZLine.ld8(lvo, ZRegister.A))
|
||||
case None =>
|
||||
ctx.log.error("Invalid left-hand side", l.position)
|
||||
Nil
|
||||
@ -898,7 +900,7 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
val (l, r, size) = assertArithmeticAssignmentLike(ctx, params)
|
||||
size match {
|
||||
case 1 =>
|
||||
targetifyA(ctx, target, Z80Multiply.compileUnsignedByteDivision(ctx, l, r, f.functionName == "%%"), false)
|
||||
targetifyA(ctx, target, Z80Multiply.compileUnsignedByteDivision(ctx, Right(l), r, f.functionName == "%%"), false)
|
||||
}
|
||||
case "*'=" =>
|
||||
assertAllArithmeticBytes("Long multiplication not supported", ctx, params)
|
||||
|
@ -106,7 +106,7 @@ object Z80Multiply {
|
||||
/**
|
||||
* Calculate A = p / q or A = p %% q
|
||||
*/
|
||||
def compileUnsignedByteDivision(ctx: CompilationContext, p: LhsExpression, q: Expression, modulo: Boolean): List[ZLine] = {
|
||||
def compileUnsignedByteDivision(ctx: CompilationContext, p: Either[LocalVariableAddressOperand, LhsExpression], q: Expression, modulo: Boolean): List[ZLine] = {
|
||||
ctx.env.eval(q) match {
|
||||
case Some(NumericConstant(qq, _)) =>
|
||||
if (qq < 0) {
|
||||
@ -116,27 +116,53 @@ object Z80Multiply {
|
||||
ctx.log.error("Unsigned division by zero", q.position)
|
||||
Nil
|
||||
} else if (qq > 255) {
|
||||
if (modulo) Z80ExpressionCompiler.compileToA(ctx, p)
|
||||
else List(ZLine.ldImm8(ZRegister.A, 0))
|
||||
if (modulo) {
|
||||
p match {
|
||||
case Right(pp) => Z80ExpressionCompiler.compileToA(ctx, pp)
|
||||
case Left(LocalVariableAddressViaHL) => List(ZLine.ld8(ZRegister.A, ZRegister.MEM_HL))
|
||||
case Left(LocalVariableAddressViaIX(offset)) => List(ZLine.ldViaIx(ZRegister.A, offset))
|
||||
case Left(LocalVariableAddressViaIY(offset)) => List(ZLine.ldViaIy(ZRegister.A, offset))
|
||||
}
|
||||
} else List(ZLine.ldImm8(ZRegister.A, 0))
|
||||
} else {
|
||||
compileUnsignedByteDivisionImpl(ctx, p, qq.toInt, modulo)
|
||||
}
|
||||
case Some(_) =>
|
||||
ctx.log.error("Unsigned division by unknown constant", q.position)
|
||||
Nil
|
||||
case None =>
|
||||
ctx.log.error("Unsigned division by a variable expression", q.position)
|
||||
Nil
|
||||
case _ =>
|
||||
val pb = p match {
|
||||
case Right(pp) => Z80ExpressionCompiler.compileToHL(ctx, pp)
|
||||
case Left(LocalVariableAddressViaHL) => List(ZLine.ld8(ZRegister.L, ZRegister.MEM_HL), ZLine.ldImm8(ZRegister.H, 0))
|
||||
case Left(LocalVariableAddressViaIX(offset)) => List(ZLine.ldViaIx(ZRegister.L, offset), ZLine.ldImm8(ZRegister.H, 0))
|
||||
case Left(LocalVariableAddressViaIY(offset)) => List(ZLine.ldViaIy(ZRegister.L, offset), ZLine.ldImm8(ZRegister.H, 0))
|
||||
}
|
||||
val qb = Z80ExpressionCompiler.compileToA(ctx, q)
|
||||
val load = if (qb.exists(Z80ExpressionCompiler.changesHL)) {
|
||||
pb ++ Z80ExpressionCompiler.stashHLIfChanged(ctx, qb)
|
||||
} else if (pb.exists(Z80ExpressionCompiler.changesDE)) {
|
||||
qb ++ List(ZLine.ld8(ZRegister.D, ZRegister.A)) ++ Z80ExpressionCompiler.stashDEIfChanged(ctx, qb)
|
||||
} else {
|
||||
pb ++ qb ++ List(ZLine.ld8(ZRegister.D, ZRegister.A))
|
||||
}
|
||||
val call = ZLine(ZOpcode.CALL, NoRegisters, ctx.env.get[FunctionInMemory]("__divmod_u16u8u16u8").toAddress)
|
||||
if (modulo) {
|
||||
load :+ call
|
||||
} else {
|
||||
load ++ List(call, ZLine.ld8(ZRegister.A, ZRegister.L))
|
||||
}
|
||||
}
|
||||
}
|
||||
/**
|
||||
* Calculate A = p / q or A = p %% q
|
||||
*/
|
||||
def compileUnsignedByteDivisionImpl(ctx: CompilationContext, p: LhsExpression, q: Int, modulo: Boolean): List[ZLine] = {
|
||||
def compileUnsignedByteDivisionImpl(ctx: CompilationContext, p: Either[LocalVariableAddressOperand, LhsExpression], q: Int, modulo: Boolean): List[ZLine] = {
|
||||
import ZRegister._
|
||||
import ZOpcode._
|
||||
val result = ListBuffer[ZLine]()
|
||||
result ++= Z80ExpressionCompiler.compileToA(ctx, p)
|
||||
result ++= (p match {
|
||||
case Right(pp) => Z80ExpressionCompiler.compileToA(ctx, pp)
|
||||
case Left(LocalVariableAddressViaHL) => List(ZLine.ld8(ZRegister.A, ZRegister.MEM_HL))
|
||||
case Left(LocalVariableAddressViaIX(offset)) => List(ZLine.ldViaIx(ZRegister.A, offset))
|
||||
case Left(LocalVariableAddressViaIY(offset)) => List(ZLine.ldViaIy(ZRegister.A, offset))
|
||||
})
|
||||
result += ZLine.ldImm8(E, 0)
|
||||
|
||||
for (i <- 7.to(0, -1)) {
|
||||
|
@ -15,6 +15,16 @@ object UnusedFunctions extends NodeOptimization {
|
||||
("*", 3, "__mul_u16u8u16"),
|
||||
("*=", 2, "__mul_u8u8u8"),
|
||||
("*=", 2, "__mul_u16u8u16"),
|
||||
("/=", 0, "__divmod_u16u8u16u8"),
|
||||
("/", 0, "__divmod_u16u8u16u8"),
|
||||
("%%=", 0, "__divmod_u16u8u16u8"),
|
||||
("%%", 0, "__divmod_u16u8u16u8"),
|
||||
("%%=", 2, "__mod_u8u8u8u8"),
|
||||
("%%", 2, "__mod_u8u8u8u8"),
|
||||
("/=", 2, "__mod_u8u8u8u8"),
|
||||
("/", 2, "__mod_u8u8u8u8"),
|
||||
("/=", 2, "__div_u8u8u8u8"),
|
||||
("/", 2, "__div_u8u8u8u8"),
|
||||
("+'", 4, "__adc_decimal"),
|
||||
("+'=", 4, "__adc_decimal"),
|
||||
("-'", 4, "__sub_decimal"),
|
||||
|
@ -245,7 +245,7 @@ abstract class AbstractAssembler[T <: AbstractCode](private val program: Program
|
||||
}
|
||||
}
|
||||
|
||||
val unusedRuntimeObjects = Set("__mul_u8u8u8", "__constant8", "identity$", "__mul_u16u8u16").filterNot(name =>{
|
||||
val unusedRuntimeObjects = Set("__mul_u8u8u8", "__constant8", "identity$", "__mul_u16u8u16", "__divmod_u16u8u16u8", "__mod_u8u8u8u8", "__div_u8u8u8u8").filterNot(name =>{
|
||||
compiledFunctions.exists{
|
||||
case (fname, compiled) => fname != name && (compiled match {
|
||||
case f:NormalCompiledFunction[_] => f.code.exists(_.refersTo(name))
|
||||
|
@ -314,8 +314,8 @@ class ByteMathSuite extends FunSuite with Matchers with AppendedClues {
|
||||
| void main () {
|
||||
| byte a
|
||||
| a = f()
|
||||
| //output_q1 = a / $y
|
||||
| //output_m1 = a %% $y
|
||||
| output_q1 = a / $y
|
||||
| output_m1 = a %% $y
|
||||
| output_q2 = a
|
||||
| output_m2 = a
|
||||
| output_q2 /= $y
|
||||
@ -324,8 +324,53 @@ class ByteMathSuite extends FunSuite with Matchers with AppendedClues {
|
||||
| byte f() {return $x}
|
||||
""".
|
||||
stripMargin) { m =>
|
||||
// m.readByte(0xc000) should equal(x / y) withClue s"$x / $y"
|
||||
// m.readByte(0xc001) should equal(x % y) withClue s"$x %% $y"
|
||||
m.readByte(0xc000) should equal(x / y) withClue s"$x / $y"
|
||||
m.readByte(0xc001) should equal(x % y) withClue s"$x %% $y"
|
||||
m.readByte(0xc002) should equal(x / y) withClue s"$x / $y"
|
||||
m.readByte(0xc003) should equal(x % y) withClue s"$x %% $y"
|
||||
}
|
||||
}
|
||||
|
||||
test("Byte division 2") {
|
||||
divisionCase2(0, 1)
|
||||
divisionCase2(1, 1)
|
||||
divisionCase2(2, 1)
|
||||
divisionCase2(250, 1)
|
||||
divisionCase2(0, 3)
|
||||
divisionCase2(0, 5)
|
||||
divisionCase2(1, 5)
|
||||
divisionCase2(6, 5)
|
||||
divisionCase2(73, 5)
|
||||
divisionCase2(75, 5)
|
||||
divisionCase2(42, 11)
|
||||
}
|
||||
|
||||
private def divisionCase2(x: Int, y: Int): Unit = {
|
||||
EmuCrossPlatformBenchmarkRun(Cpu.Mos, Cpu.Z80, Cpu.Intel8080, Cpu.Sharp, Cpu.Intel8086)(
|
||||
s"""
|
||||
| import zp_reg
|
||||
| byte output_q1 @$$c000
|
||||
| byte output_m1 @$$c001
|
||||
| byte output_q2 @$$c002
|
||||
| byte output_m2 @$$c003
|
||||
| void main () {
|
||||
| byte a
|
||||
| byte b
|
||||
| a = f()
|
||||
| b = g()
|
||||
| output_q1 = a / b
|
||||
| output_m1 = a %% b
|
||||
| output_q2 = a
|
||||
| output_m2 = a
|
||||
| output_q2 /= b
|
||||
| output_m2 %%= b
|
||||
| }
|
||||
| byte f() = $x
|
||||
| noinline byte g() = $y
|
||||
""".
|
||||
stripMargin) { m =>
|
||||
m.readByte(0xc000) should equal(x / y) withClue s"$x / $y"
|
||||
m.readByte(0xc001) should equal(x % y) withClue s"$x %% $y"
|
||||
m.readByte(0xc002) should equal(x / y) withClue s"$x / $y"
|
||||
m.readByte(0xc003) should equal(x % y) withClue s"$x %% $y"
|
||||
}
|
||||
|
Loading…
x
Reference in New Issue
Block a user