mirror of
https://github.com/KarolS/millfork.git
synced 2024-12-23 23:30:22 +00:00
6809: Some optimizations
This commit is contained in:
parent
f08caa0b7a
commit
e19ac75350
@ -5,6 +5,7 @@ import java.nio.charset.StandardCharsets
|
||||
import java.nio.file.{Files, Paths}
|
||||
import java.util.Locale
|
||||
|
||||
import millfork.assembly.m6809.opt.M6809OptimizationPresets
|
||||
import millfork.assembly.mos.AssemblyLine
|
||||
import millfork.assembly.mos.opt._
|
||||
import millfork.assembly.z80.opt.Z80OptimizationPresets
|
||||
@ -317,10 +318,7 @@ object Main {
|
||||
val env = new Environment(None, "", platform.cpuFamily, options)
|
||||
env.collectDeclarations(program, options)
|
||||
|
||||
val assemblyOptimizations = optLevel match {
|
||||
case 0 => Nil
|
||||
case _ => Nil
|
||||
}
|
||||
val assemblyOptimizations = M6809OptimizationPresets.forLevel(optLevel)
|
||||
|
||||
// compile
|
||||
val assembler = new M6809Assembler(program, env, platform)
|
||||
|
@ -10,6 +10,10 @@ import millfork.node.{M6809Register, Position}
|
||||
* @author Karol Stasiak
|
||||
*/
|
||||
|
||||
object MState extends Enumeration {
|
||||
val A, B, X, Y, U, ZF, CF, HF, VF, NF = Value
|
||||
}
|
||||
|
||||
object MLine0 {
|
||||
|
||||
@inline
|
||||
@ -92,8 +96,15 @@ case class MLine(opcode: MOpcode.Value, addrMode: MAddrMode, parameter: Constant
|
||||
|
||||
def mergePos(s: Seq[Option[SourceLine]]): MLine = if (s.isEmpty) this else pos(SourceLine.merge(this.source, s))
|
||||
|
||||
@inline
|
||||
def refersTo(name: String): Boolean = parameter.refersTo(name)
|
||||
|
||||
@inline
|
||||
def elidable: Boolean = elidability == Elidability.Elidable
|
||||
|
||||
@inline
|
||||
def notFixed: Boolean = elidability != Elidability.Fixed
|
||||
|
||||
override def sizeInBytes: Int = 1 // TODO
|
||||
|
||||
override def isPrintable: Boolean = true // TODO
|
||||
@ -152,8 +163,8 @@ case class MLine(opcode: MOpcode.Value, addrMode: MAddrMode, parameter: Constant
|
||||
case (_, InherentB) => overlaps(B)
|
||||
case (PULU, set:RegisterSet) => reg == U || set.contains(reg)
|
||||
case (PULS, set:RegisterSet) => reg == S || set.contains(reg)
|
||||
case (PSHS, _) => reg == U
|
||||
case (PSHU, _) => reg == S
|
||||
case (PSHS, _) => reg == S
|
||||
case (PSHU, _) => reg == U
|
||||
case (TFR, TwoRegisters(_, dest)) => overlaps(dest)
|
||||
case (EXG, TwoRegisters(r1, r2)) => overlaps(r1) || overlaps(r2)
|
||||
case (op, _) if MOpcode.ChangesAAlways(op) => overlaps(A) || addrMode.changesRegister(reg)
|
||||
@ -170,5 +181,115 @@ case class MLine(opcode: MOpcode.Value, addrMode: MAddrMode, parameter: Constant
|
||||
case _ => true // TODO
|
||||
}
|
||||
}
|
||||
|
||||
def readsRegister(reg: M6809Register.Value): Boolean = {
|
||||
import M6809Register._
|
||||
def overlaps(other: M6809Register.Value): Boolean = {
|
||||
if (reg == D && (other == A || other == B)) true
|
||||
else if (other == D && (reg == A || reg == B)) true
|
||||
else reg == other
|
||||
}
|
||||
import MOpcode._
|
||||
val readByAddrMode = addrMode match {
|
||||
case InherentA => opcode != CLR && overlaps(A)
|
||||
case InherentB => opcode != CLR && overlaps(B)
|
||||
case Indexed(base, _) => overlaps(base)
|
||||
case Absolute(_) | DirectPage | Inherent | Immediate => false
|
||||
case DAccumulatorIndexed(base, _) => overlaps(D) || overlaps(base)
|
||||
case AAccumulatorIndexed(base, _) => overlaps(A) || overlaps(base)
|
||||
case BAccumulatorIndexed(base, _) => overlaps(B) || overlaps(base)
|
||||
case TwoRegisters(source, dest) => opcode match {
|
||||
case TFR => overlaps(source)
|
||||
case EXG => overlaps(source) || overlaps(dest)
|
||||
}
|
||||
case RegisterSet(set) => opcode match {
|
||||
case PSHS | PSHU => set.exists(overlaps)
|
||||
case PULS | PULU => false
|
||||
}
|
||||
case LongRelative | Relative => false
|
||||
case NonExistent => false
|
||||
case RawByte => true
|
||||
case _ => true
|
||||
}
|
||||
if (readByAddrMode) return true
|
||||
opcode match {
|
||||
case ADDA | SUBA | ADCA | SBCA | ORA | EORA | ANDA | CMPA | BITA | DAA => overlaps(A)
|
||||
case ADDB | SUBB | ADCB | SBCB | ORB | EORB | ANDB | CMPB | BITB | SEX => overlaps(B)
|
||||
case ADDD | SUBD | CMPD => overlaps(D)
|
||||
case ABX => reg == X || overlaps(B)
|
||||
case CMPX => reg == X
|
||||
case CMPY => reg == Y
|
||||
case CMPU => reg == U
|
||||
case CMPS => reg == S
|
||||
case STA => overlaps(A)
|
||||
case STB => overlaps(B)
|
||||
case STD => overlaps(D)
|
||||
case STU => reg == U
|
||||
case MUL => overlaps(D)
|
||||
case ABX => reg == X || overlaps(B)
|
||||
case NOP | SWI | SWI2 | SWI3 | SYNC => false
|
||||
case INC | DEC | ROL | ROR | ASL | ASR | LSR | CLR | COM | NEG | TST => false // variants for A and B handled before
|
||||
case op if Branching(op) => false
|
||||
case JMP => false
|
||||
case _ => true // TODO
|
||||
}
|
||||
}
|
||||
|
||||
def readsMemory(): Boolean = {
|
||||
import MOpcode._
|
||||
val opcodeIsForReading = opcode match {
|
||||
case LDA | LDB | LDD | LDX | LDY | LDU | LDS | PULU | PULS => true
|
||||
case ADDA | SUBA | ADCA | SBCA | ORA | EORA | ANDA | CMPA | BITA => true
|
||||
case ADDB | SUBB | ADCB | SBCB | ORB | EORB | ANDB | CMPB | BITB => true
|
||||
case INC | DEC | ROL | ROR | ASL | ASR | LSR | CLR | COM | NEG | TST => true
|
||||
case STA | STB | STD | STX | STY | STS | STU | PSHU | PSHS => false
|
||||
case TFR | EXG | DAA | SEX | ABX | MUL => false
|
||||
case _ => false // TODO: ???
|
||||
}
|
||||
addrMode match {
|
||||
case InherentA => false
|
||||
case InherentB => false
|
||||
case Indexed(_, indirect) => indirect
|
||||
case Absolute(indirect) => indirect || opcodeIsForReading
|
||||
case DAccumulatorIndexed(_, indirect) => indirect || opcodeIsForReading
|
||||
case AAccumulatorIndexed(_, indirect) => indirect || opcodeIsForReading
|
||||
case BAccumulatorIndexed(_, indirect) => indirect || opcodeIsForReading
|
||||
case RegisterSet(_) => opcodeIsForReading
|
||||
case TwoRegisters(_, _) => false
|
||||
case LongRelative | Relative => false
|
||||
case NonExistent => false
|
||||
case RawByte => true
|
||||
case _ => true
|
||||
}
|
||||
}
|
||||
|
||||
def changesMemory(): Boolean = {
|
||||
import MOpcode._
|
||||
val opcodeIsForWriting = opcode match {
|
||||
case LDA | LDB | LDD | LDX | LDY | LDU | LDS | PULU | PULS => false
|
||||
case ADDA | SUBA | ADCA | SBCA | ORA | EORA | ANDA | CMPA | BITA => false
|
||||
case ADDB | SUBB | ADCB | SBCB | ORB | EORB | ANDB | CMPB | BITB => false
|
||||
case INC | DEC | ROL | ROR | ASL | ASR | LSR | CLR | COM | NEG | TST => true
|
||||
case TST => false
|
||||
case STA | STB | STD | STX | STY | STS | STU | PSHU | PSHS => true
|
||||
case TFR | EXG | DAA | SEX | ABX | MUL => false
|
||||
case _ => false // TODO: ???
|
||||
}
|
||||
addrMode match {
|
||||
case InherentA => false
|
||||
case InherentB => false
|
||||
case Indexed(_, _) => opcodeIsForWriting
|
||||
case Absolute(_) => opcodeIsForWriting
|
||||
case DAccumulatorIndexed(_, _) => opcodeIsForWriting
|
||||
case AAccumulatorIndexed(_, _) => opcodeIsForWriting
|
||||
case BAccumulatorIndexed(_, _) => opcodeIsForWriting
|
||||
case RegisterSet(_) => opcodeIsForWriting
|
||||
case TwoRegisters(_, _) => false
|
||||
case LongRelative | Relative => false
|
||||
case NonExistent => false
|
||||
case RawByte => true
|
||||
case _ => true
|
||||
}
|
||||
}
|
||||
}
|
||||
|
||||
|
@ -42,9 +42,85 @@ object MOpcode extends Enumeration {
|
||||
val Prefixed: Set[MOpcode.Value] = PrefixedBy10 ++ PrefixedBy11
|
||||
val CanHaveInherentAccumulator: Set[MOpcode.Value] = Set(ASL, ASR, CLR, COM, DEC, INC, LSR, NEG, ROL, ROR, TST)
|
||||
val Branching: Set[MOpcode.Value] = Set(BRA, BRN, BHI, BLS, BCC, BCS, BNE, BEQ, BVC, BVS, BPL, BMI, BGE, BLT, BGT, BLE)
|
||||
val ConditionalBranching: Set[MOpcode.Value] = Set(BHI, BLS, BCC, BCS, BNE, BEQ, BVC, BVS, BPL, BMI, BGE, BLT, BGT, BLE)
|
||||
val ChangesAAlways: Set[MOpcode.Value] = Set(ADDA, ADCA, SUBA, SBCA, ANDA, ORA, EORA, SEX, DAA)
|
||||
val ChangesBAlways: Set[MOpcode.Value] = Set(ADDB, ADCB, SUBB, SBCB, ANDB, ORB, EORB)
|
||||
val ChangesDAlways: Set[MOpcode.Value] = Set(ADDD, SUBD, ANDB, ORB, EORB)
|
||||
val ChangesCFAlways: Set[MOpcode.Value] = Set(ADDD, SUBD, ANDB, ORB, EORB)
|
||||
val ReadsAAlways: Set[MOpcode.Value] = Set(ADDD, SUBD, ANDB, ORB, EORB)
|
||||
val AccessesWordInMemory: Set[MOpcode.Value] = Set(ADDD, SUBD, LDD, STD, LDX, LDY, LDU, LDS, STX, STY, STU, STS, CMPD, CMPX, CMPY, CMPU, CMPS)
|
||||
val AllLinear: Set[MOpcode.Value] = Set(
|
||||
ABX, ADCA, ADCB, ADDA, ADDB, ADDD, ANDA, ANDB, ANDCC, ASL, ASR,
|
||||
BITA, BITB,
|
||||
CLR, CMPA, CMPB, CMPD, CMPS, CMPU, CMPX, CMPY, COMA, COMB, COM, CWAI,
|
||||
DAA, DEC,
|
||||
EORA, EORB, EXG,
|
||||
INC,
|
||||
LDA, LDB, LDD, LDS, LDU, LDX, LDY, LEAS, LEAU, LEAX, LEAY, LSR,
|
||||
MUL,
|
||||
NEG, NOP,
|
||||
ORA, ORB, ORCC,
|
||||
PSHS, PSHU, PULS, PULU,
|
||||
ROL, ROR,
|
||||
SBCA, SBCB, SEX, STA, STB, STD, STS, STU, STX, STY, SUBA, SUBB, SUBD, SYNC,
|
||||
TFR, TST,
|
||||
)
|
||||
val ReadsH: Set[MOpcode.Value] = Set(CWAI, DAA)
|
||||
val ReadsV: Set[MOpcode.Value] = Set(CWAI, BVC, BVS, BGE, BLT, BGT, BLE)
|
||||
val ReadsN: Set[MOpcode.Value] = Set(CWAI, BPL, BMI, BGE, BLT, BGT, BLE)
|
||||
val ReadsZ: Set[MOpcode.Value] = Set(CWAI, BEQ, BNE, BHI, BLS, BLE, BGT)
|
||||
val ReadsC: Set[MOpcode.Value] = Set(CWAI, BCC, BCS, BHI, BLS, ADCA, ADCB, SBCA, SBCB, ROL, ROR)
|
||||
val ChangesC: Set[MOpcode.Value] = Set(
|
||||
CWAI, ORCC, ANDCC,
|
||||
ADDA, ADDB, ADDD, ADCA, ADCB, DAA,
|
||||
ASL, ASR,
|
||||
ASL, BITA, BITB, CLR, COM,
|
||||
CMPA, CMPB, CMPD, CMPX, CMPY, CMPU, CMPS,
|
||||
MUL,
|
||||
)
|
||||
// The following are incomplete:
|
||||
val ChangesN: Set[MOpcode.Value] = Set(
|
||||
CWAI, ORCC, ANDCC,
|
||||
ADDA, ADDB, ADDD, ADCA, ADCB, SEX,
|
||||
SUBA, SUBB, SUBD, SBCA, SBCB,
|
||||
ASL, ASR, LSR, ROL, ROR,
|
||||
INC, DEC, CLR, NEG, COM, TST,
|
||||
ORA, ORB, EORA, EORB, ANDA, ANDB,
|
||||
LDA, LDB, LDD, LDX, LDY, LDU, LDS,
|
||||
STA, STB, STD, STX, STY, STU, STS,
|
||||
CMPA, CMPB, CMPD, CMPX, CMPY, CMPU, CMPS,
|
||||
)
|
||||
val ChangesZ: Set[MOpcode.Value] = Set(
|
||||
CWAI, ORCC, ANDCC,
|
||||
ADDA, ADDB, ADDD, ADCA, ADCB, DAA, SEX,
|
||||
SUBA, SUBB, SUBD, SBCA, SBCB,
|
||||
ASL, ASR, LSR, ROL, ROR,
|
||||
INC, DEC, CLR, NEG, COM, TST,
|
||||
ORA, ORB, EORA, EORB, ANDA, ANDB,
|
||||
LDA, LDB, LDD, LDX, LDY, LDU, LDS,
|
||||
STA, STB, STD, STX, STY, STU, STS,
|
||||
CMPA, CMPB, CMPD, CMPX, CMPY, CMPU, CMPS,
|
||||
LEAX, LEAY,
|
||||
MUL,
|
||||
)
|
||||
val ChangesV: Set[MOpcode.Value] = Set(
|
||||
CWAI, ORCC, ANDCC,
|
||||
ADDA, ADDB, ADDD, ADCA, ADCB, DAA, SEX,
|
||||
SUBA, SUBB, SUBD, SBCA, SBCB,
|
||||
ASL, ASR, LSR, ROL, ROR,
|
||||
INC, DEC, CLR, NEG, COM, TST,
|
||||
ORA, ORB, EORA, EORB, ANDA, ANDB,
|
||||
LDA, LDB, LDD, LDX, LDY, LDU, LDS,
|
||||
STA, STB, STD, STX, STY, STU, STS,
|
||||
CMPA, CMPB, CMPD, CMPX, CMPY, CMPU, CMPS,
|
||||
)
|
||||
val ChangesH: Set[MOpcode.Value] = Set(
|
||||
CWAI, ORCC, ANDCC,
|
||||
ADDA, ADDB, ADCA, ADCB,
|
||||
SUBA, SUBB, SBCA, SBCB,
|
||||
ASL, ASR, LSR, ROL, ROR,
|
||||
NEG
|
||||
)
|
||||
|
||||
def lookup(opcode: String, position: Some[Position], log: Logger): (MOpcode.Value, Option[MAddrMode]) = {
|
||||
val o = opcode.toUpperCase(Locale.ROOT)
|
||||
|
@ -0,0 +1,42 @@
|
||||
package millfork.assembly.m6809.opt
|
||||
|
||||
|
||||
import millfork.assembly.AssemblyOptimization
|
||||
import millfork.assembly.m6809.MOpcode._
|
||||
import millfork.assembly.m6809.{MLine, MState}
|
||||
|
||||
/**
|
||||
* @author Karol Stasiak
|
||||
*/
|
||||
object AlwaysGoodMOptimizations {
|
||||
|
||||
val PointlessLoad = new RuleBasedAssemblyOptimization("Pointless load",
|
||||
needsFlowInfo = FlowInfoRequirement.BackwardFlow,
|
||||
(Elidable & HasOpcodeIn(LDA, ANDA, ORA, EORA) & DoesntMatterWhatItDoesWith(MState.A, MState.NF, MState.ZF, MState.VF)) ~~> (_ => Nil),
|
||||
(Elidable & HasOpcodeIn(LDB, ANDB, ORB, EORB) & DoesntMatterWhatItDoesWith(MState.B, MState.NF, MState.ZF, MState.VF)) ~~> (_ => Nil),
|
||||
(Elidable & HasOpcode(LDD) & DoesntMatterWhatItDoesWith(MState.A, MState.B, MState.NF, MState.ZF, MState.VF)) ~~> (_ => Nil),
|
||||
(Elidable & HasOpcodeIn(LDX, LEAX) & DoesntMatterWhatItDoesWith(MState.X, MState.NF, MState.ZF, MState.VF)) ~~> (_ => Nil),
|
||||
(Elidable & HasOpcodeIn(LDY, LEAY) & DoesntMatterWhatItDoesWith(MState.Y, MState.NF, MState.ZF, MState.VF)) ~~> (_ => Nil),
|
||||
)
|
||||
|
||||
val SimplifiableZeroStore = new RuleBasedAssemblyOptimization("Simplifiable zero store",
|
||||
needsFlowInfo = FlowInfoRequirement.BothFlows,
|
||||
(Elidable & HasOpcode(LDA) & HasImmediate(0) & DoesntMatterWhatItDoesWith(MState.CF)) ~~> {
|
||||
_ => List(MLine.inherentA(CLR))
|
||||
},
|
||||
(Elidable & HasOpcode(LDB) & HasImmediate(0) & DoesntMatterWhatItDoesWith(MState.CF)) ~~> {
|
||||
_ => List(MLine.inherentB(CLR))
|
||||
},
|
||||
(Elidable & HasOpcode(STA) & HasA(0) & DoesntMatterWhatItDoesWith(MState.CF)) ~~> {
|
||||
code => code.map(_.copy(opcode = CLR))
|
||||
},
|
||||
(Elidable & HasOpcode(STB) & HasB(0) & DoesntMatterWhatItDoesWith(MState.CF)) ~~> {
|
||||
code => code.map(_.copy(opcode = CLR))
|
||||
},
|
||||
)
|
||||
|
||||
val All: Seq[AssemblyOptimization[MLine]] = Seq(
|
||||
PointlessLoad,
|
||||
SimplifiableZeroStore
|
||||
)
|
||||
}
|
@ -1,8 +1,9 @@
|
||||
package millfork.assembly.m6809.opt
|
||||
|
||||
import millfork.assembly.m6809.MState
|
||||
import millfork.assembly.mos.State
|
||||
import millfork.assembly.opt._
|
||||
import millfork.env.Constant
|
||||
import millfork.env.{Constant, NumericConstant}
|
||||
|
||||
//noinspection RedundantNewCaseClass
|
||||
case class CpuStatus(a: Status[Int] = UnknownStatus,
|
||||
@ -31,9 +32,18 @@ case class CpuStatus(a: Status[Int] = UnknownStatus,
|
||||
def nz: CpuStatus =
|
||||
this.copy(n = AnyStatus, z = AnyStatus)
|
||||
|
||||
def nz(i: Long): CpuStatus =
|
||||
def nzB(i: Long): CpuStatus =
|
||||
this.copy(n = SingleStatus((i & 0x80) != 0), z = SingleStatus((i & 0xff) == 0))
|
||||
|
||||
def nzW(i: Long): CpuStatus =
|
||||
this.copy(n = SingleStatus((i & 0x8000) != 0), z = SingleStatus((i & 0xffff) == 0))
|
||||
|
||||
def nzW(c: Constant): CpuStatus = c match {
|
||||
case NumericConstant(i, _) =>
|
||||
this.copy(n = SingleStatus((i & 0x8000) != 0), z = SingleStatus((i & 0xffff) == 0))
|
||||
case _ => this.nz
|
||||
}
|
||||
|
||||
def ~(that: CpuStatus) = new CpuStatus(
|
||||
a = this.a ~ that.a,
|
||||
b = this.b ~ that.b,
|
||||
@ -49,6 +59,26 @@ case class CpuStatus(a: Status[Int] = UnknownStatus,
|
||||
v = this.v ~ that.v
|
||||
)
|
||||
|
||||
def hasClear(state: MState.Value): Boolean = state match {
|
||||
case MState.A => a.contains(0)
|
||||
case MState.B => b.contains(0)
|
||||
case MState.X => x.contains(0)
|
||||
case MState.Y => y.contains(0)
|
||||
case MState.U => u.contains(0)
|
||||
case MState.ZF => z.contains(false)
|
||||
case MState.NF => n.contains(false)
|
||||
case MState.CF => c.contains(false)
|
||||
case MState.VF => v.contains(false)
|
||||
case _ => false
|
||||
}
|
||||
|
||||
def hasSet(state: MState.Value): Boolean = state match {
|
||||
case MState.ZF => z.contains(true)
|
||||
case MState.NF => n.contains(true)
|
||||
case MState.CF => c.contains(true)
|
||||
case MState.VF => v.contains(true)
|
||||
case _ => false
|
||||
}
|
||||
}
|
||||
|
||||
object CpuStatus {
|
||||
|
@ -0,0 +1,63 @@
|
||||
package millfork.assembly.m6809.opt
|
||||
|
||||
import millfork.assembly.OptimizationContext
|
||||
import millfork.assembly.m6809.{MLine, MLine0, MOpcode, MState}
|
||||
import millfork.env.{Label, MemoryAddressConstant, NormalFunction}
|
||||
|
||||
/**
|
||||
* @author Karol Stasiak
|
||||
*/
|
||||
|
||||
class FlowHolder(_statusBefore: () => List[CpuStatus], _importanceAfter: () => List[CpuImportance]) {
|
||||
lazy val statusBefore: List[CpuStatus] = _statusBefore()
|
||||
lazy val importanceAfter: List[CpuImportance] = _importanceAfter()
|
||||
|
||||
def toString(index: Int): String = statusBefore(index).toString ++ " -> " ++ importanceAfter(index).toString
|
||||
}
|
||||
|
||||
case class FlowInfo(holder: FlowHolder, index: Int, _labelUseCountMap: () => Option[Map[String, Int]]) {
|
||||
|
||||
lazy val statusBefore: CpuStatus = holder.statusBefore(index)
|
||||
lazy val importanceAfter: CpuImportance = holder.importanceAfter(index)
|
||||
lazy val labelUseCountMap: Option[Map[String, Int]] = _labelUseCountMap()
|
||||
|
||||
def hasClear(state: MState.Value): Boolean = statusBefore.hasClear(state)
|
||||
|
||||
def hasSet(state: MState.Value): Boolean = statusBefore.hasSet(state)
|
||||
|
||||
def isUnimportant(state: MState.Value): Boolean = importanceAfter.isUnimportant(state)
|
||||
|
||||
def labelUseCount(label: String): Int = labelUseCountMap.map(_.getOrElse(label, 0)).getOrElse(-1)
|
||||
|
||||
override def toString: String = holder.toString(index)
|
||||
}
|
||||
|
||||
object FlowAnalyzer {
|
||||
|
||||
private val EmptyCpuStatus = CpuStatus()
|
||||
private val EmptyCpuImportance = CpuImportance()
|
||||
|
||||
def analyze(f: NormalFunction, code: List[MLine], optimizationContext: OptimizationContext, req: FlowInfoRequirement.Value): List[(FlowInfo, MLine)] = {
|
||||
val forwardFlow = req match {
|
||||
case FlowInfoRequirement.BothFlows | FlowInfoRequirement.ForwardFlow =>
|
||||
() => ForwardFlowAnalysis.analyze(f, code, optimizationContext)
|
||||
case FlowInfoRequirement.BackwardFlow | FlowInfoRequirement.JustLabels | FlowInfoRequirement.NoRequirement =>
|
||||
() => List.fill(code.size)(EmptyCpuStatus)
|
||||
}
|
||||
val reverseFlow = req match {
|
||||
case FlowInfoRequirement.BothFlows | FlowInfoRequirement.BackwardFlow =>
|
||||
() => ReverseFlowAnalyzer.analyze(f, code, optimizationContext)
|
||||
case FlowInfoRequirement.ForwardFlow | FlowInfoRequirement.JustLabels | FlowInfoRequirement.NoRequirement =>
|
||||
() => List.fill(code.size)(EmptyCpuImportance)
|
||||
}
|
||||
val labelMap: () => Option[Map[String, Int]] = () => req match {
|
||||
case FlowInfoRequirement.NoRequirement => None
|
||||
case _ => Some(code.flatMap {
|
||||
case MLine0(op, _, MemoryAddressConstant(Label(l))) if op != MOpcode.LABEL => Some(l)
|
||||
case _ => None
|
||||
}.groupBy(identity).mapValues(_.size).view.force)
|
||||
}
|
||||
val holder = new FlowHolder(forwardFlow, reverseFlow)
|
||||
code.zipWithIndex.map{ case (line, i) => FlowInfo(holder, i, labelMap) -> line}
|
||||
}
|
||||
}
|
@ -2,7 +2,8 @@ package millfork.assembly.m6809.opt
|
||||
|
||||
import millfork.CompilationFlag
|
||||
import millfork.assembly.OptimizationContext
|
||||
import millfork.assembly.m6809.{MLine, MLine0}
|
||||
import millfork.assembly.m6809.{Immediate, MLine, MLine0}
|
||||
import millfork.assembly.opt.Status.SingleFalse
|
||||
import millfork.assembly.opt.{AnyStatus, FlowCache, SingleStatus, Status}
|
||||
import millfork.env._
|
||||
import millfork.node.{M6809Register, NiceFunctionProperty}
|
||||
@ -74,6 +75,21 @@ object ForwardFlowAnalysis {
|
||||
case MLine0(NOP, _, _) =>
|
||||
()
|
||||
|
||||
case MLine0(LDA, Immediate, NumericConstant(n, _)) =>
|
||||
currentStatus = currentStatus.copy(a = SingleStatus(n.toInt & 0xff), v = SingleFalse).nzB(n)
|
||||
case MLine0(LDB, Immediate, NumericConstant(n, _)) =>
|
||||
currentStatus = currentStatus.copy(b = SingleStatus(n.toInt & 0xff), v = SingleFalse).nzB(n)
|
||||
case MLine0(LDD, Immediate, NumericConstant(n, _)) =>
|
||||
currentStatus = currentStatus.copy(
|
||||
a = SingleStatus(n.toInt.>>(8) & 0xff),
|
||||
b = SingleStatus(n.toInt & 0xff),
|
||||
v = SingleFalse
|
||||
).nzW(n)
|
||||
case MLine0(LDX, Immediate, c) =>
|
||||
currentStatus = currentStatus.copy(x = SingleStatus(c), v = SingleFalse).nzW(c)
|
||||
case MLine0(LDY, Immediate, c) =>
|
||||
currentStatus = currentStatus.copy(y = SingleStatus(c), v = SingleFalse).nzW(c)
|
||||
|
||||
case MLine0(opcode, addrMode, _) =>
|
||||
// TODO
|
||||
currentStatus = initialStatus
|
||||
|
@ -0,0 +1,14 @@
|
||||
package millfork.assembly.m6809.opt
|
||||
|
||||
import millfork.assembly.AssemblyOptimization
|
||||
import millfork.assembly.m6809.MLine
|
||||
|
||||
/**
|
||||
* @author Karol Stasiak
|
||||
*/
|
||||
object M6809OptimizationPresets {
|
||||
|
||||
val Default: List[AssemblyOptimization[MLine]] = forLevel(2)
|
||||
|
||||
def forLevel(level: Int): List[AssemblyOptimization[MLine]] = List.fill(level)(AlwaysGoodMOptimizations.All).flatten
|
||||
}
|
@ -0,0 +1,203 @@
|
||||
package millfork.assembly.m6809.opt
|
||||
|
||||
import millfork.assembly._
|
||||
import millfork.assembly.m6809.{Absolute, MLine, MLine0, MOpcode, MState}
|
||||
import millfork.assembly.opt.FlowCache
|
||||
import millfork.env._
|
||||
import millfork.node.M6809NiceFunctionProperty.DoesntChangeB
|
||||
import millfork.node.{M6809Register, MosRegister}
|
||||
|
||||
/**
|
||||
* @author Karol Stasiak
|
||||
*/
|
||||
|
||||
sealed trait Importance {
|
||||
def ~(that: Importance): Importance = (this, that) match {
|
||||
case (_, Important) | (Important, _) => Important
|
||||
case (_, Unimportant) | (Unimportant, _) => Unimportant
|
||||
case (UnknownImportance, UnknownImportance) => UnknownImportance
|
||||
}
|
||||
}
|
||||
|
||||
case object Important extends Importance {
|
||||
override def toString = "!"
|
||||
}
|
||||
|
||||
case object Unimportant extends Importance {
|
||||
override def toString = "*"
|
||||
}
|
||||
|
||||
case object UnknownImportance extends Importance {
|
||||
override def toString = "?"
|
||||
}
|
||||
|
||||
//noinspection RedundantNewCaseClass
|
||||
case class CpuImportance(a: Importance = UnknownImportance,
|
||||
b: Importance = UnknownImportance,
|
||||
x: Importance = UnknownImportance,
|
||||
y: Importance = UnknownImportance,
|
||||
u: Importance = UnknownImportance,
|
||||
nf: Importance = UnknownImportance,
|
||||
zf: Importance = UnknownImportance,
|
||||
vf: Importance = UnknownImportance,
|
||||
cf: Importance = UnknownImportance,
|
||||
hf: Importance = UnknownImportance,
|
||||
) {
|
||||
|
||||
|
||||
override def toString: String = s"A=$a,B=$b,X=$x,Y=$y; Z=$zf,N=$nf,C=$cf,V=$vf,H=$hf"
|
||||
|
||||
def ~(that: CpuImportance) = new CpuImportance(
|
||||
a = this.a ~ that.a,
|
||||
b = this.b ~ that.b,
|
||||
x = this.x ~ that.x,
|
||||
y = this.y ~ that.y,
|
||||
u = this.u ~ that.u,
|
||||
nf = this.nf ~ that.nf,
|
||||
cf = this.cf ~ that.cf,
|
||||
hf = this.hf ~ that.hf,
|
||||
vf = this.vf ~ that.vf,
|
||||
zf = this.zf ~ that.zf,
|
||||
)
|
||||
|
||||
def isUnimportant(state: MState.Value): Boolean = state match {
|
||||
// UnknownImportance is usually an effect of unreachable code
|
||||
case MState.A => a != Important
|
||||
case MState.B => b != Important
|
||||
case MState.X => x != Important
|
||||
case MState.Y => y != Important
|
||||
case MState.U => u != Important
|
||||
case MState.ZF => zf != Important
|
||||
case MState.NF => nf != Important
|
||||
case MState.CF => cf != Important
|
||||
case MState.VF => vf != Important
|
||||
case MState.HF => hf != Important
|
||||
}
|
||||
|
||||
}
|
||||
|
||||
object ReverseFlowAnalyzer {
|
||||
val readsA: Set[String] = Set("call")
|
||||
val readsB: Set[String] = Set("call")
|
||||
val readsX: Set[String] = Set("call")
|
||||
val readsY: Set[String] = Set("")
|
||||
|
||||
val cache = new FlowCache[MLine, CpuImportance]("m6809 reverse")
|
||||
private val importanceBeforeJsr: CpuImportance = CpuImportance(
|
||||
a = Unimportant,
|
||||
b = Unimportant,
|
||||
x = Unimportant,
|
||||
y = Unimportant,
|
||||
u = Important,
|
||||
zf = Unimportant,
|
||||
nf = Unimportant,
|
||||
cf = Unimportant,
|
||||
vf = Unimportant,
|
||||
hf = Unimportant)
|
||||
private val finalImportance: CpuImportance = CpuImportance(
|
||||
a = Important, b = Important,
|
||||
x = Important, y = Important, u = Important,
|
||||
cf = Important, vf = Important, hf = Important, zf = Important, nf = Important)
|
||||
|
||||
//noinspection RedundantNewCaseClass
|
||||
def analyze(f: NormalFunction, code: List[MLine], optimizationContext: OptimizationContext): List[CpuImportance] = {
|
||||
cache.get(code).foreach(return _)
|
||||
val niceFunctionProperties = optimizationContext.niceFunctionProperties
|
||||
val importanceArray = Array.fill[CpuImportance](code.length)(new CpuImportance())
|
||||
val codeArray = code.toArray
|
||||
|
||||
var changed = true
|
||||
changed = true
|
||||
while (changed) {
|
||||
changed = false
|
||||
var currentImportance = finalImportance
|
||||
for (i <- codeArray.indices.reverse) {
|
||||
import millfork.assembly.m6809.MOpcode._
|
||||
import millfork.node.M6809NiceFunctionProperty._
|
||||
if (importanceArray(i) != currentImportance) {
|
||||
changed = true
|
||||
importanceArray(i) = currentImportance
|
||||
}
|
||||
val currentLine = codeArray(i)
|
||||
currentLine match {
|
||||
case MLine0(opcode, _, MemoryAddressConstant(Label(l))) if MOpcode.ConditionalBranching(opcode) =>
|
||||
val L = l
|
||||
val labelIndex = codeArray.indexWhere {
|
||||
case MLine0(LABEL, _, MemoryAddressConstant(Label(L))) => true
|
||||
case _ => false
|
||||
}
|
||||
currentImportance = if (labelIndex < 0) finalImportance else importanceArray(labelIndex) ~ currentImportance
|
||||
case _ =>
|
||||
}
|
||||
currentLine match {
|
||||
|
||||
case MLine0(JSR | JMP, Absolute(false), MemoryAddressConstant(fun: FunctionInMemory)) =>
|
||||
// this case has to be handled first, because the generic JSR importance handler is too conservative
|
||||
var result = importanceBeforeJsr
|
||||
fun.params match {
|
||||
case AssemblyParamSignature(params) =>
|
||||
params.foreach(_.variable match {
|
||||
case M6809RegisterVariable(M6809Register.A, _) =>
|
||||
result = result.copy(a = Important)
|
||||
case M6809RegisterVariable(M6809Register.B, _) =>
|
||||
result = result.copy(b = Important)
|
||||
case M6809RegisterVariable(M6809Register.D, _) =>
|
||||
result = result.copy(a = Important, b = Important)
|
||||
case M6809RegisterVariable(M6809Register.U, _) =>
|
||||
result = result.copy(u = Important)
|
||||
case M6809RegisterVariable(M6809Register.X, _) =>
|
||||
result = result.copy(x = Important)
|
||||
case M6809RegisterVariable(M6809Register.Y, _) =>
|
||||
result = result.copy(y = Important)
|
||||
case _ =>
|
||||
})
|
||||
case NormalParamSignature(List(MemoryVariable(_, typ, _))) if typ.size == 1 =>
|
||||
result = result.copy(b = Important)
|
||||
case NormalParamSignature(List(MemoryVariable(_, typ, _))) if typ.size == 2 =>
|
||||
result = result.copy(a = Important, b = Important)
|
||||
case _ =>
|
||||
}
|
||||
if (readsA(fun.name)) result = result.copy(a = Important)
|
||||
if (readsB(fun.name)) result = result.copy(b = Important)
|
||||
if (readsX(fun.name)) result = result.copy(x = Important)
|
||||
if (readsY(fun.name)) result = result.copy(y = Important)
|
||||
currentImportance = result.copy(
|
||||
a = if (niceFunctionProperties(DoesntChangeA -> fun.name)) currentImportance.a ~ result.a else result.a,
|
||||
b = if (niceFunctionProperties(DoesntChangeB -> fun.name)) currentImportance.b ~ result.b else result.b,
|
||||
x = if (niceFunctionProperties(DoesntChangeX -> fun.name)) currentImportance.x ~ result.x else result.x,
|
||||
y = if (niceFunctionProperties(DoesntChangeY -> fun.name)) currentImportance.y ~ result.y else result.y,
|
||||
u = if (niceFunctionProperties(DoesntChangeU -> fun.name)) currentImportance.u ~ result.u else result.u,
|
||||
cf = if (niceFunctionProperties(DoesntChangeCF -> fun.name)) currentImportance.cf ~ result.cf else result.cf,
|
||||
)
|
||||
|
||||
case MLine0(opcode, addrMode, _) =>
|
||||
if (MOpcode.ChangesC(opcode)) currentImportance = currentImportance.copy(cf = Unimportant)
|
||||
if (MOpcode.ChangesN(opcode)) currentImportance = currentImportance.copy(nf = Unimportant)
|
||||
if (MOpcode.ChangesZ(opcode)) currentImportance = currentImportance.copy(zf = Unimportant)
|
||||
if (MOpcode.ChangesZ(opcode)) currentImportance = currentImportance.copy(zf = Unimportant)
|
||||
if (MOpcode.ReadsC(opcode)) currentImportance = currentImportance.copy(cf = Important)
|
||||
if (MOpcode.ReadsH(opcode)) currentImportance = currentImportance.copy(hf = Important)
|
||||
if (MOpcode.ReadsV(opcode)) currentImportance = currentImportance.copy(vf = Important)
|
||||
if (MOpcode.ReadsZ(opcode)) currentImportance = currentImportance.copy(zf = Important)
|
||||
if (MOpcode.ReadsN(opcode)) currentImportance = currentImportance.copy(nf = Important)
|
||||
if (currentLine.changesRegister(M6809Register.A)) currentImportance = currentImportance.copy(a = Unimportant)
|
||||
if (currentLine.changesRegister(M6809Register.B)) currentImportance = currentImportance.copy(b = Unimportant)
|
||||
if (currentLine.changesRegister(M6809Register.X)) currentImportance = currentImportance.copy(x = Unimportant)
|
||||
if (currentLine.changesRegister(M6809Register.Y)) currentImportance = currentImportance.copy(y = Unimportant)
|
||||
if (currentLine.changesRegister(M6809Register.U)) currentImportance = currentImportance.copy(u = Unimportant)
|
||||
if (currentLine.readsRegister(M6809Register.A)) currentImportance = currentImportance.copy(a = Important)
|
||||
if (currentLine.readsRegister(M6809Register.B)) currentImportance = currentImportance.copy(b = Important)
|
||||
if (currentLine.readsRegister(M6809Register.X)) currentImportance = currentImportance.copy(x = Important)
|
||||
if (currentLine.readsRegister(M6809Register.Y)) currentImportance = currentImportance.copy(y = Important)
|
||||
if (currentLine.readsRegister(M6809Register.U)) currentImportance = currentImportance.copy(u = Important)
|
||||
}
|
||||
}
|
||||
}
|
||||
// importanceArray.zip(codeArray).foreach{
|
||||
// case (i, y) => if (y.isPrintable) println(f"$y%-32s $i%-32s")
|
||||
// }
|
||||
// println("---------------------")
|
||||
|
||||
cache.put(code, importanceArray.toList)
|
||||
}
|
||||
}
|
File diff suppressed because it is too large
Load Diff
@ -203,6 +203,16 @@ object Z80NiceFunctionProperty {
|
||||
case class SetsATo(value: Int) extends NiceFunctionProperty("A=" + value)
|
||||
}
|
||||
|
||||
object M6809NiceFunctionProperty {
|
||||
case object DoesntChangeA extends NiceFunctionProperty("A")
|
||||
case object DoesntChangeB extends NiceFunctionProperty("B")
|
||||
case object DoesntChangeX extends NiceFunctionProperty("X")
|
||||
case object DoesntChangeY extends NiceFunctionProperty("Y")
|
||||
case object DoesntChangeU extends NiceFunctionProperty("U")
|
||||
case object DoesntChangeCF extends NiceFunctionProperty("C")
|
||||
case class SetsBTo(value: Int) extends NiceFunctionProperty("B=" + value)
|
||||
}
|
||||
|
||||
object MosRegister extends Enumeration {
|
||||
val A, X, Y, AX, AY, YA, XA, XY, YX, AW = Value
|
||||
}
|
||||
|
@ -128,19 +128,19 @@ object EmuIntel8086BenchmarkRun {
|
||||
object EmuMotorola6809BenchmarkRun {
|
||||
def apply(source: String)(verifier: MemoryBank => Unit): Unit = {
|
||||
val (Timings(t0, _), m0) = EmuUnoptimizedM6809Run.apply2(source)
|
||||
// val (Timings(t1, _), m1) = EmuOptimizedIntel8086Run.apply2(source)
|
||||
// val (Timings(t2, _), m2) = EmuOptimizedInlinedIntel8086Run.apply2(source)
|
||||
val (Timings(t1, _), m1) = EmuOptimizedM6809Run.apply2(source)
|
||||
val (Timings(t2, _), m2) = EmuOptimizedInlinedM6809Run.apply2(source)
|
||||
println(f"Before optimization: $t0%7d")
|
||||
// println(f"After optimization: $t1%7d")
|
||||
// println(f"After inlining: $t2%7d")
|
||||
// println(f"Gain: ${(100L * (t0 - t1) / t0.toDouble).round}%7d%%")
|
||||
// println(f"Gain with inlining: ${(100L * (t0 - t2) / t0.toDouble).round}%7d%%")
|
||||
println(f"After optimization: $t1%7d")
|
||||
println(f"After inlining: $t2%7d")
|
||||
println(f"Gain: ${(100L * (t0 - t1) / t0.toDouble).round}%7d%%")
|
||||
println(f"Gain with inlining: ${(100L * (t0 - t2) / t0.toDouble).round}%7d%%")
|
||||
println(f"Running 6809 unoptimized")
|
||||
verifier(m0)
|
||||
// println(f"Running 6809 optimized")
|
||||
// verifier(m1)
|
||||
// println(f"Running 6809 optimized inlined")
|
||||
// verifier(m2)
|
||||
println(f"Running 6809 optimized")
|
||||
verifier(m1)
|
||||
println(f"Running 6809 optimized inlined")
|
||||
verifier(m2)
|
||||
}
|
||||
}
|
||||
|
||||
@ -167,7 +167,7 @@ object EmuCrossPlatformBenchmarkRun {
|
||||
if (Settings.enableZ80Tests && platforms.contains(millfork.Cpu.Z80)) {
|
||||
EmuZ80BenchmarkRun.apply(source)(verifier)
|
||||
}
|
||||
if (Settings.enableGameboyTests && platforms.contains(millfork.Cpu.Intel8080)) {
|
||||
if (Settings.enableIntel8080Tests && platforms.contains(millfork.Cpu.Intel8080)) {
|
||||
EmuIntel8080BenchmarkRun.apply(source)(verifier)
|
||||
}
|
||||
if (Settings.enableUnemulatedTests && platforms.contains(millfork.Cpu.Intel8085)) {
|
||||
|
@ -1,5 +1,6 @@
|
||||
package millfork.test.emu
|
||||
|
||||
import millfork.assembly.m6809.opt.M6809OptimizationPresets
|
||||
import millfork.assembly.mos.opt.{LaterOptimizations, ZeropageRegisterOptimizations}
|
||||
import millfork.assembly.z80.opt.Z80OptimizationPresets
|
||||
import millfork.{Cpu, OptimizationPresets}
|
||||
@ -49,4 +50,7 @@ object EmuOptimizedInlinedSharpRun extends EmuZ80Run(Cpu.Sharp, OptimizationPres
|
||||
override def inline: Boolean = true
|
||||
}
|
||||
|
||||
object EmuOptimizedInlinedM6809Run extends EmuM6809Run(Cpu.Motorola6809, OptimizationPresets.NodeOpt, M6809OptimizationPresets.Default) {
|
||||
override def inline: Boolean = true
|
||||
}
|
||||
|
||||
|
@ -1,5 +1,6 @@
|
||||
package millfork.test.emu
|
||||
|
||||
import millfork.assembly.m6809.opt.M6809OptimizationPresets
|
||||
import millfork.assembly.mos.opt.{LaterOptimizations, ZeropageRegisterOptimizations}
|
||||
import millfork.assembly.z80.opt.{AlwaysGoodZ80Optimizations, Z80OptimizationPresets}
|
||||
import millfork.{Cpu, OptimizationPresets}
|
||||
@ -78,3 +79,5 @@ object EmuSizeOptimizedIntel8080Run extends EmuZ80Run(Cpu.Intel8080, Optimizatio
|
||||
}
|
||||
|
||||
object EmuOptimizedSharpRun extends EmuZ80Run(Cpu.Sharp, OptimizationPresets.NodeOpt, Z80OptimizationPresets.GoodForSharp)
|
||||
|
||||
object EmuOptimizedM6809Run extends EmuM6809Run(Cpu.Motorola6809, OptimizationPresets.NodeOpt, M6809OptimizationPresets.Default)
|
||||
|
@ -42,7 +42,7 @@ object ShouldNotCompile extends Matchers {
|
||||
case CpuFamily.M6502 =>
|
||||
effectiveSource += "\nnoinline asm word call(word ax) {\nJMP ((__reg.b2b3))\n}\n"
|
||||
case CpuFamily.M6809 =>
|
||||
effectiveSource += "\nnoinline asm word call(word d) {\nJMP ,x\n}\n"
|
||||
effectiveSource += "\nnoinline asm word call(word x) {\nJMP ,x\n}\n"
|
||||
case CpuFamily.I80 =>
|
||||
if (options.flag(CompilationFlag.UseIntelSyntaxForInput))
|
||||
effectiveSource += "\nnoinline asm word call(word de) {\npush d\nret\n}\n"
|
||||
|
Loading…
Reference in New Issue
Block a user