mirror of
https://github.com/KarolS/millfork.git
synced 2024-12-23 08:29:35 +00:00
Unsigned division of word by byte
This commit is contained in:
parent
2583f280a8
commit
e31737ad40
@ -46,6 +46,8 @@ In the descriptions below, arguments to the operators are explained as follows:
|
||||
|
||||
* `byte` means any numeric one-byte type
|
||||
|
||||
* `unsigned byte` means any numeric one-byte type that is not signed
|
||||
|
||||
* `word` means any numeric two-byte type, or a byte expanded to a word; `pointer` is considered to be numeric
|
||||
|
||||
* `long` means any numeric type longer than two bytes, or a shorter type expanded to such length to match the other argument
|
||||
@ -91,11 +93,11 @@ TODO
|
||||
`word * byte` (zpreg)
|
||||
`byte * word` (zpreg)
|
||||
|
||||
* `/`, `%%`: unsigned division and unsigned modulo
|
||||
|
||||
`byte / byte`
|
||||
* `/`, `%%`: unsigned division and unsigned modulo
|
||||
`unsigned byte / unsigned byte` (zpreg)
|
||||
`word / unsigned byte` (zpreg)
|
||||
`constant word / constant word`
|
||||
`constant long / constant long`
|
||||
`constant long / constant long`
|
||||
|
||||
## Bitwise operators
|
||||
|
||||
@ -197,12 +199,16 @@ An expression of form `a[f()] += b` may call `f` an undefined number of times.
|
||||
|
||||
* `*=`: multiplication in place
|
||||
`mutable byte *= constant byte`
|
||||
`mutable byte *= byte` (zpreg)
|
||||
`mutable byte *= byte` (zpreg)
|
||||
`mutable word *= unsigned byte` (zpreg)
|
||||
|
||||
* `*'=`: decimal multiplication in place
|
||||
`mutable byte *'= constant byte`
|
||||
|
||||
* `/=`, `%%=`: unsigned division and modulo in place
|
||||
`mutable unsigned byte /= unsigned byte` (zpreg)
|
||||
`mutable word /= unsigned byte` (zpreg)
|
||||
|
||||
## Indexing
|
||||
|
||||
While Millfork does not consider indexing an operator, this is a place as good as any to discuss it.
|
||||
|
@ -67,4 +67,32 @@ __mul_u16u8u16_start:
|
||||
? RTS
|
||||
}
|
||||
|
||||
// divide (__reg[1]:__reg[0])/__reg[2]
|
||||
|
||||
noinline asm byte __mod_u16u8u16u8() {
|
||||
? LDA #0
|
||||
? LDX #15
|
||||
? CLC
|
||||
__divmod_u16u8u16u8_start:
|
||||
? ROL __reg
|
||||
? ROL __reg+1
|
||||
? ROL
|
||||
? CMP __reg+2
|
||||
? BCC __divmod_u16u8u16u8_skip
|
||||
? SBC __reg+2
|
||||
__divmod_u16u8u16u8_skip:
|
||||
? DEX
|
||||
? BPL __divmod_u16u8u16u8_start
|
||||
? ROL __reg
|
||||
? ROL __reg+1
|
||||
? RTS
|
||||
}
|
||||
|
||||
asm word __div_u16u8u16u8() {
|
||||
? JSR __mod_u16u8u16u8
|
||||
? LDA __reg
|
||||
? LDX __reg+1
|
||||
? RTS
|
||||
}
|
||||
|
||||
#endif
|
||||
|
@ -15,6 +15,8 @@ object ZeropageRegisterOptimizations {
|
||||
"__mul_u8u8u8" -> Set(0, 1),
|
||||
"__mod_u8u8u8u8" -> Set(0, 1),
|
||||
"__div_u8u8u8u8" -> Set(0, 1),
|
||||
"__mod_u16u8u16u8" -> Set(0, 1, 2),
|
||||
"__div_u16u8u16u8" -> Set(0, 1, 2),
|
||||
"__mul_u16u8u16" -> Set(0, 1, 2),
|
||||
"__adc_decimal" -> Set(2, 3),
|
||||
"__sbc_decimal" -> Set(2, 3),
|
||||
|
@ -200,10 +200,14 @@ object ZLine {
|
||||
|
||||
def ldViaIx(targetOffset: Int, source: ZRegister.Value): ZLine = ZLine(LD, TwoRegistersOffset(ZRegister.MEM_IX_D, source, targetOffset), Constant.Zero)
|
||||
|
||||
def ld0ViaIx(targetOffset: Int): ZLine = ZLine(LD, TwoRegistersOffset(ZRegister.MEM_IX_D, ZRegister.IMM_8, targetOffset), Constant.Zero)
|
||||
|
||||
def ldViaIy(target: ZRegister.Value, sourceOffset: Int): ZLine = ZLine(LD, TwoRegistersOffset(target, ZRegister.MEM_IY_D, sourceOffset), Constant.Zero)
|
||||
|
||||
def ldViaIy(targetOffset: Int, source: ZRegister.Value): ZLine = ZLine(LD, TwoRegistersOffset(ZRegister.MEM_IY_D, source, targetOffset), Constant.Zero)
|
||||
|
||||
def ld0ViaIy(targetOffset: Int): ZLine = ZLine(LD, TwoRegistersOffset(ZRegister.MEM_IY_D, ZRegister.IMM_8, targetOffset), Constant.Zero)
|
||||
|
||||
def ldViaIxy(x: Boolean, target: ZRegister.Value, sourceOffset: Int): ZLine = if (x) ldViaIx(target, sourceOffset) else ldViaIy(target, sourceOffset)
|
||||
|
||||
def ldViaIxy(x: Boolean, targetOffset: Int, source: ZRegister.Value): ZLine = if (x) ldViaIx(targetOffset, source) else ldViaIy(targetOffset, source)
|
||||
|
@ -86,9 +86,12 @@ class AbstractExpressionCompiler[T <: AbstractCode] {
|
||||
val lSize = lType.size
|
||||
val rType = getExpressionType(ctx, params(1))
|
||||
val rSize = rType.size
|
||||
if (lSize > 1 || rSize > 1) {
|
||||
if (lSize > 2 || rSize > 2) {
|
||||
ctx.log.error("Long division not supported", params.head.position)
|
||||
}
|
||||
if (rSize > 1) {
|
||||
ctx.log.error("Division by words not supported", params.head.position)
|
||||
}
|
||||
if (lType.isSigned || rType.isSigned) {
|
||||
ctx.log.error("Signed division not supported", params.head.position)
|
||||
}
|
||||
@ -338,7 +341,12 @@ object AbstractExpressionCompiler {
|
||||
case 1 => b
|
||||
case 2 => w
|
||||
}
|
||||
case FunctionCallExpression("*" | "|" | "&" | "^" | "/" | "%%", params) => params.map { e => getExpressionType(env, log, e).size }.max match {
|
||||
case FunctionCallExpression("%%", params) => params.map { e => getExpressionType(env, log, e).size } match {
|
||||
case List(1, 1) | List(2, 1) => b
|
||||
case List(1, 2) | List(2, 2) => w
|
||||
case _ => log.error("Combining values bigger than words", expr.position); w
|
||||
}
|
||||
case FunctionCallExpression("*" | "|" | "&" | "^" | "/", params) => params.map { e => getExpressionType(env, log, e).size }.max match {
|
||||
case 1 => b
|
||||
case 2 => w
|
||||
case _ => log.error("Combining values bigger than words", expr.position); w
|
||||
|
@ -1009,8 +1009,16 @@ object BuiltIns {
|
||||
}
|
||||
}
|
||||
|
||||
def compileUnsignedWordByByteDivision(ctx: CompilationContext, p: Expression, q: Expression, modulo: Boolean): List[AssemblyLine] = {
|
||||
if (ctx.options.zpRegisterSize < 3) {
|
||||
ctx.log.error("Word by byte division requires the zeropage pseudoregister of size at least 3", p.position)
|
||||
return Nil
|
||||
}
|
||||
PseudoregisterBuiltIns.compileUnsignedWordByByteDivision(ctx, p, q, modulo)
|
||||
}
|
||||
|
||||
def compileUnsignedByteDivision(ctx: CompilationContext, p: Expression, q: Expression, modulo: Boolean): List[AssemblyLine] = {
|
||||
if (ctx.options.zpRegisterSize < 1) {
|
||||
if (ctx.options.zpRegisterSize < 2) {
|
||||
ctx.log.error("Byte division requires the zeropage pseudoregister", p.position)
|
||||
return Nil
|
||||
}
|
||||
|
@ -1314,6 +1314,12 @@ object MosExpressionCompiler extends AbstractExpressionCompiler[AssemblyLine] {
|
||||
size match {
|
||||
case 1 =>
|
||||
BuiltIns.compileUnsignedByteDivision(ctx, l, r, f.functionName == "%%=") ++ compileByteStorage(ctx, MosRegister.A, l)
|
||||
case 2 =>
|
||||
if (f.functionName == "%%=") {
|
||||
BuiltIns.compileUnsignedWordByByteDivision(ctx, l, r, true) ++ compileByteStorage(ctx, MosRegister.A, l)
|
||||
} else {
|
||||
compileAssignment(ctx, FunctionCallExpression("/", List(l, r)).pos(f.position), l)
|
||||
}
|
||||
}
|
||||
case "/" | "%%" =>
|
||||
assertSizesForDivision(ctx, params, inPlace = false)
|
||||
@ -1321,6 +1327,8 @@ object MosExpressionCompiler extends AbstractExpressionCompiler[AssemblyLine] {
|
||||
size match {
|
||||
case 1 =>
|
||||
BuiltIns.compileUnsignedByteDivision(ctx, l, r, f.functionName == "%%")
|
||||
case 2 =>
|
||||
BuiltIns.compileUnsignedWordByByteDivision(ctx, l, r, f.functionName == "%%")
|
||||
}
|
||||
case "*'=" =>
|
||||
assertAllArithmeticBytes("Long multiplication not supported", ctx, params)
|
||||
|
@ -462,6 +462,41 @@ object PseudoregisterBuiltIns {
|
||||
load ++ calculate
|
||||
}
|
||||
|
||||
def compileUnsignedWordByByteDivision(ctx: CompilationContext, param1: Expression, param2: Expression, modulo: Boolean): List[AssemblyLine] = {
|
||||
(AbstractExpressionCompiler.getExpressionType(ctx, param1).size,
|
||||
AbstractExpressionCompiler.getExpressionType(ctx, param2).size) match {
|
||||
case (2 | 1, 1) => // ok
|
||||
case _ => ctx.log.fatal("Invalid code path", param2.position)
|
||||
}
|
||||
(ctx.env.eval(param1), ctx.env.eval(param2)) match {
|
||||
case (Some(l), Some(r)) =>
|
||||
val operator = if (modulo) MathOperator.Modulo else MathOperator.Divide
|
||||
val product = CompoundConstant(operator, l, r).quickSimplify
|
||||
return List(AssemblyLine.immediate(LDA, product.loByte), AssemblyLine.immediate(LDX, product.hiByte))
|
||||
// TODO: powers of 2, like with *
|
||||
case _ =>
|
||||
}
|
||||
val b = ctx.env.get[Type]("byte")
|
||||
val w = ctx.env.get[Type]("word")
|
||||
val reg = ctx.env.get[VariableInMemory]("__reg")
|
||||
val code1 = MosExpressionCompiler.compile(ctx, param1, Some(w -> RegisterVariable(MosRegister.AX, w)), BranchSpec.None)
|
||||
val code2 = MosExpressionCompiler.compile(ctx, param2, Some(b -> RegisterVariable(MosRegister.A, b)), BranchSpec.None)
|
||||
val load = if (!usesRegLo(code2) && !usesRegHi(code2)) {
|
||||
code1 ++ List(AssemblyLine.zeropage(STA, reg), AssemblyLine.zeropage(STX, reg, 1)) ++ code2 ++ List(AssemblyLine.zeropage(STA, reg, 2))
|
||||
} else if (!usesReg2(code1)) {
|
||||
code2 ++ List(AssemblyLine.zeropage(STA, reg, 2)) ++ code1 ++ List(AssemblyLine.zeropage(STA, reg), AssemblyLine.zeropage(STX, reg, 1))
|
||||
} else {
|
||||
code2 ++ List(AssemblyLine.implied(PHA)) ++ code1 ++ List(
|
||||
AssemblyLine.zeropage(STA, reg),
|
||||
AssemblyLine.zeropage(STX, reg, 1),
|
||||
AssemblyLine.implied(PLA),
|
||||
AssemblyLine.zeropage(STA, reg, 2)
|
||||
)
|
||||
}
|
||||
val functionName = if(modulo) "__mod_u16u8u16u8" else "__div_u16u8u16u8"
|
||||
load ++ List(AssemblyLine.absoluteOrLongAbsolute(JSR, ctx.env.get[FunctionInMemory](functionName), ctx.options))
|
||||
}
|
||||
|
||||
private def simplicity(env: Environment, expr: Expression): Char = {
|
||||
val constPart = env.eval(expr) match {
|
||||
case Some(NumericConstant(_, _)) => 'Z'
|
||||
|
@ -888,12 +888,71 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
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((LocalVariableAddressViaHL, code)) =>
|
||||
code ++ (stashHLIfChanged(ctx, Z80Multiply.compileUnsignedByteDivision(ctx, Left(LocalVariableAddressViaHL), r, f.functionName == "%%=")) :+ ZLine.ld8(ZRegister.MEM_HL, ZRegister.A))
|
||||
case Some((lvo, code)) =>
|
||||
code ++ (stashHLIfChanged(ctx, Z80Multiply.compileUnsignedByteDivision(ctx, Left(lvo), r, f.functionName == "%%=")) :+ ZLine.ld8(lvo, ZRegister.A))
|
||||
code ++ (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
|
||||
}
|
||||
case 2 =>
|
||||
if (f.functionName == "%%=") {
|
||||
calculateAddressToAppropriatePointer(ctx, l, forWriting = true) match {
|
||||
case Some((LocalVariableAddressViaHL, List(ZLine0(LD_16, TwoRegisters(ZRegister.HL, ZRegister.IMM_16), addr)))) =>
|
||||
Z80Multiply.compileUnsignedWordByByteDivision(ctx, Right(l), r) ++ List(
|
||||
ZLine.ldAbs8(addr, ZRegister.A),
|
||||
ZLine.register(XOR, ZRegister.A),
|
||||
ZLine.ldAbs8(addr+1, ZRegister.A)
|
||||
)
|
||||
case Some((lvo@LocalVariableAddressViaHL, code)) =>
|
||||
code ++ stashHLIfChanged(ctx, Z80Multiply.compileUnsignedWordByByteDivision(ctx, Left(lvo), r)) ++ List(
|
||||
ZLine.ld8(ZRegister.MEM_HL, ZRegister.A),
|
||||
ZLine.register(INC_16, ZRegister.HL),
|
||||
ZLine.ldImm8(ZRegister.MEM_HL, 0)
|
||||
)
|
||||
case Some((lvo@LocalVariableAddressViaIX(offset), code)) =>
|
||||
code ++ Z80Multiply.compileUnsignedWordByByteDivision(ctx, Left(lvo), r) ++ List(
|
||||
ZLine.ldViaIx(offset, ZRegister.A),
|
||||
ZLine.ld0ViaIx(offset + 1)
|
||||
)
|
||||
case Some((lvo@LocalVariableAddressViaIY(offset), code)) =>
|
||||
code ++ Z80Multiply.compileUnsignedWordByByteDivision(ctx, Left(lvo), r) ++ List(
|
||||
ZLine.ldViaIy(offset, ZRegister.A),
|
||||
ZLine.ld0ViaIy(offset + 1)
|
||||
)
|
||||
case None =>
|
||||
ctx.log.error("Invalid left-hand side", l.position)
|
||||
Nil
|
||||
}
|
||||
} else {
|
||||
calculateAddressToAppropriatePointer(ctx, l, forWriting = true) match {
|
||||
case Some((lvo@LocalVariableAddressViaHL, code)) =>
|
||||
code ++
|
||||
stashHLIfChanged(ctx,
|
||||
Z80Multiply.compileUnsignedWordByByteDivision(ctx, Left(LocalVariableAddressViaHL), r) ++ (
|
||||
if (ctx.options.flags(CompilationFlag.EmitIntel8080Opcodes)) List(ZLine.implied(EX_DE_HL))
|
||||
else List(ZLine.ld8(ZRegister.E, ZRegister.L), ZLine.ld8(ZRegister.D, ZRegister.H))
|
||||
)
|
||||
) ++
|
||||
List(
|
||||
ZLine.ld8(ZRegister.MEM_HL, ZRegister.E),
|
||||
ZLine.register(INC_16, ZRegister.HL),
|
||||
ZLine.ld8(ZRegister.MEM_HL, ZRegister.D)
|
||||
)
|
||||
case Some((lvo@LocalVariableAddressViaIX(offset), code)) =>
|
||||
code ++
|
||||
Z80Multiply.compileUnsignedWordByByteDivision(ctx, Left(lvo), r) ++
|
||||
storeHLViaIX(ctx, offset, 2, false)
|
||||
case Some((lvo@LocalVariableAddressViaIY(offset), code)) =>
|
||||
code ++
|
||||
Z80Multiply.compileUnsignedWordByByteDivision(ctx, Left(lvo), r) ++
|
||||
storeHLViaIY(ctx, offset, 2, false)
|
||||
case _ =>
|
||||
ctx.log.error("Invalid left-hand side", l.position)
|
||||
Nil
|
||||
}
|
||||
}
|
||||
}
|
||||
case "/" | "%%" =>
|
||||
assertSizesForDivision(ctx, params, inPlace = false)
|
||||
@ -901,6 +960,12 @@ object Z80ExpressionCompiler extends AbstractExpressionCompiler[ZLine] {
|
||||
size match {
|
||||
case 1 =>
|
||||
targetifyA(ctx, target, Z80Multiply.compileUnsignedByteDivision(ctx, Right(l), r, f.functionName == "%%"), false)
|
||||
case 2 =>
|
||||
if (f.functionName == "%%") {
|
||||
targetifyA(ctx, target, Z80Multiply.compileUnsignedWordByByteDivision(ctx, Right(l), r), false)
|
||||
} else {
|
||||
targetifyHL(ctx, target, Z80Multiply.compileUnsignedWordByByteDivision(ctx, Right(l), r))
|
||||
}
|
||||
}
|
||||
case "*'=" =>
|
||||
assertAllArithmeticBytes("Long multiplication not supported", ctx, params)
|
||||
|
@ -103,6 +103,32 @@ object Z80Multiply {
|
||||
}
|
||||
}
|
||||
|
||||
/**
|
||||
* Calculate HL = p / q and A = p %% q
|
||||
*/
|
||||
def compileUnsignedWordByByteDivision(ctx: CompilationContext, p: Either[LocalVariableAddressOperand, LhsExpression], q: Expression): List[ZLine] = {
|
||||
val pb = p match {
|
||||
case Right(pp) => Z80ExpressionCompiler.compileToHL(ctx, pp)
|
||||
case Left(LocalVariableAddressViaHL) => List(
|
||||
ZLine.ld8(ZRegister.A, ZRegister.MEM_HL),
|
||||
ZLine.register(ZOpcode.INC_16, ZRegister.HL),
|
||||
ZLine.ld8(ZRegister.H, ZRegister.MEM_HL),
|
||||
ZLine.ld8(ZRegister.L, ZRegister.A)
|
||||
)
|
||||
case Left(LocalVariableAddressViaIX(offset)) => List(ZLine.ldViaIx(ZRegister.L, offset), ZLine.ldViaIx(ZRegister.H, offset+1))
|
||||
case Left(LocalVariableAddressViaIY(offset)) => List(ZLine.ldViaIy(ZRegister.L, offset), ZLine.ldViaIy(ZRegister.H, offset+1))
|
||||
}
|
||||
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))
|
||||
}
|
||||
load :+ ZLine(ZOpcode.CALL, NoRegisters, ctx.env.get[FunctionInMemory]("__divmod_u16u8u16u8").toAddress)
|
||||
}
|
||||
|
||||
/**
|
||||
* Calculate A = p / q or A = p %% q
|
||||
*/
|
||||
@ -128,25 +154,11 @@ object Z80Multiply {
|
||||
compileUnsignedByteDivisionImpl(ctx, p, qq.toInt, modulo)
|
||||
}
|
||||
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)
|
||||
val call = compileUnsignedWordByByteDivision(ctx, p, q)
|
||||
if (modulo) {
|
||||
load :+ call
|
||||
call
|
||||
} else {
|
||||
load ++ List(call, ZLine.ld8(ZRegister.A, ZRegister.L))
|
||||
call :+ ZLine.ld8(ZRegister.A, ZRegister.L)
|
||||
}
|
||||
}
|
||||
}
|
||||
|
@ -25,6 +25,12 @@ object UnusedFunctions extends NodeOptimization {
|
||||
("/", 2, "__mod_u8u8u8u8"),
|
||||
("/=", 2, "__div_u8u8u8u8"),
|
||||
("/", 2, "__div_u8u8u8u8"),
|
||||
("%%=", 2, "__mod_u16u8u16u8"),
|
||||
("%%", 2, "__mod_u16u8u16u8"),
|
||||
("/=", 2, "__mod_u16u8u16u8"),
|
||||
("/", 2, "__mod_u16u8u16u8"),
|
||||
("/=", 2, "__div_u16u8u16u8"),
|
||||
("/", 2, "__div_u16u8u16u8"),
|
||||
("+'", 4, "__adc_decimal"),
|
||||
("+'=", 4, "__adc_decimal"),
|
||||
("-'", 4, "__sub_decimal"),
|
||||
|
@ -447,4 +447,95 @@ class WordMathSuite extends FunSuite with Matchers with AppendedClues {
|
||||
m.readWord(0xc004) should equal(x * y) withClue s"$x * $y"
|
||||
}
|
||||
}
|
||||
|
||||
test("Word division 1") {
|
||||
divisionCase1(0, 1)
|
||||
divisionCase1(1, 1)
|
||||
divisionCase1(1, 5)
|
||||
divisionCase1(6, 5)
|
||||
divisionCase2(420, 11)
|
||||
divisionCase2(1210, 11)
|
||||
divisionCase2(35000, 45)
|
||||
divisionCase2(51462, 1)
|
||||
}
|
||||
|
||||
private def divisionCase1(x: Int, y: Int): Unit = {
|
||||
EmuCrossPlatformBenchmarkRun(Cpu.Mos /*,Cpu.Z80, Cpu.Intel8080, Cpu.Sharp, Cpu.Intel8086*/)(
|
||||
s"""
|
||||
| import zp_reg
|
||||
| word output_q1 @$$c000
|
||||
| word output_m1 @$$c002
|
||||
| word output_q2 @$$c004
|
||||
| word output_m2 @$$c006
|
||||
| void main () {
|
||||
| word a
|
||||
| a = f()
|
||||
| output_q1 = a / $y
|
||||
| output_m1 = a %% $y
|
||||
| output_q2 = a
|
||||
| output_m2 = a
|
||||
| output_q2 /= $y
|
||||
| output_m2 %%= $y
|
||||
| }
|
||||
| word f() = $x
|
||||
""".
|
||||
stripMargin) { m =>
|
||||
m.readWord(0xc000) should equal(x / y) withClue s"= $x / $y"
|
||||
m.readWord(0xc002) should equal(x % y) withClue s"= $x %% $y"
|
||||
m.readWord(0xc004) should equal(x / y) withClue s"= $x / $y"
|
||||
m.readWord(0xc006) should equal(x % y) withClue s"= $x %% $y"
|
||||
}
|
||||
}
|
||||
|
||||
test("Word 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(73, 8)
|
||||
divisionCase2(75, 5)
|
||||
divisionCase2(42, 11)
|
||||
divisionCase2(420, 11)
|
||||
divisionCase2(1210, 11)
|
||||
divisionCase2(35000, 45)
|
||||
divisionCase2(35000, 2)
|
||||
divisionCase2(51462, 3)
|
||||
divisionCase2(51462, 1)
|
||||
}
|
||||
|
||||
private def divisionCase2(x: Int, y: Int): Unit = {
|
||||
EmuCrossPlatformBenchmarkRun(Cpu.Mos, Cpu.Z80, Cpu.Intel8080, Cpu.Sharp, Cpu.Intel8086)(
|
||||
s"""
|
||||
| import zp_reg
|
||||
| word output_q1 @$$c000
|
||||
| word output_m1 @$$c002
|
||||
| word output_q2 @$$c004
|
||||
| word output_m2 @$$c006
|
||||
| void main () {
|
||||
| word 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
|
||||
| }
|
||||
| word f() = $x
|
||||
| noinline byte g() = $y
|
||||
""".
|
||||
stripMargin) { m =>
|
||||
m.readWord(0xc000) should equal(x / y) withClue s"= $x / $y"
|
||||
m.readWord(0xc002) should equal(x % y) withClue s"= $x %% $y"
|
||||
m.readWord(0xc004) should equal(x / y) withClue s"= $x / $y"
|
||||
m.readWord(0xc006) should equal(x % y) withClue s"= $x %% $y"
|
||||
}
|
||||
}
|
||||
}
|
||||
|
Loading…
Reference in New Issue
Block a user