1
0
mirror of https://github.com/KarolS/millfork.git synced 2024-05-31 18:41:30 +00:00

Basic groundwork for optimization hint support

This commit is contained in:
Karol Stasiak 2020-11-18 10:08:58 +01:00
parent 385b2fd40b
commit 97c7d0ffed
25 changed files with 357 additions and 81 deletions

View File

@ -561,6 +561,7 @@ object CompilationFlag extends Enumeration {
DangerousOptimizations, InlineFunctions, InterproceduralOptimization,
FunctionFallthrough, RegisterVariables, FunctionDeduplication, SubroutineExtraction,
OptimizeStdlib,
UseOptimizationHints,
// memory allocation options
VariableOverlap, CompactReturnDispatchParams, LUnixRelocatableCode,
// runtime check options

View File

@ -1181,8 +1181,8 @@ object AlwaysGoodOptimizations {
}: _*
)
val PointlessRegisterTransfers = new RuleBasedAssemblyOptimization("Pointless register transfers",
needsFlowInfo = FlowInfoRequirement.NoRequirement,
lazy val PointlessRegisterTransfers = new RuleBasedAssemblyOptimization("Pointless register transfers",
needsFlowInfo = FlowInfoRequirement.BackwardFlow,
HasOpcode(TYA) ~ (Elidable & HasOpcodeIn(TYA, TAY)) ~~> (_.init),
HasOpcode(TXA) ~ (Elidable & HasOpcodeIn(TXA, TAX)) ~~> (_.init),
HasOpcode(TAY) ~ (Elidable & HasOpcodeIn(TYA, TAY)) ~~> (_.init),
@ -1197,6 +1197,10 @@ object AlwaysGoodOptimizations {
(Elidable & HasOpcodeIn(TYA, TAY)) ~~> (_.init),
HasOpcode(TSX) ~ (Not(ChangesX) & Not(ChangesS) & Linear).* ~ (Elidable & HasOpcodeIn(TXS, TSX)) ~~> (_.init),
HasOpcode(TXS) ~ (Not(ChangesX) & Not(ChangesS) & Linear).* ~ (Elidable & HasOpcodeIn(TXS, TSX)) ~~> (_.init),
HasOpcodeIn(TXA, TAX) ~ (Not(ChangesA) & Not(ChangesX) & Linear).* ~ (Elidable & HasOpcode(TXA) & DoesntMatterWhatItDoesWith(State.Z, State.N)) ~~> (_.init),
HasOpcodeIn(TXA, TAX) ~ (Not(ChangesA) & Not(ChangesX) & Linear).* ~ (Elidable & HasOpcode(TAX) & DoesntMatterWhatItDoesWith(State.Z, State.N)) ~~> (_.init),
HasOpcodeIn(TYA, TAY) ~ (Not(ChangesA) & Not(ChangesY) & Linear).* ~ (Elidable & HasOpcode(TYA) & DoesntMatterWhatItDoesWith(State.Z, State.N)) ~~> (_.init),
HasOpcodeIn(TYA, TAY) ~ (Not(ChangesA) & Not(ChangesY) & Linear).* ~ (Elidable & HasOpcode(TAY) & DoesntMatterWhatItDoesWith(State.Z, State.N)) ~~> (_.init),
)
lazy val PointlessRegisterTransfersBeforeStore = new RuleBasedAssemblyOptimization("Pointless register transfers from flow",

View File

@ -862,22 +862,32 @@ case object DebugMatching extends AssemblyPattern {
}
case object Linear extends AssemblyLinePattern {
override def matchLineTo(ctx: AssemblyMatchingContext, flowInfo: FlowInfo, line: AssemblyLine): Boolean =
OpcodeClasses.AllLinear(line.opcode)
override def matchLineTo(ctx: AssemblyMatchingContext, flowInfo: FlowInfo, line: AssemblyLine): Boolean = {
if (line.opcode == Opcode.JSR) line.parameter match {
case MemoryAddressConstant(f: FunctionInMemory) => f.hasOptimizationHints
case _ => false
} else OpcodeClasses.AllLinear(line.opcode)
}
override def hitRate: Double = 0.89
}
case object LinearOrBranch extends TrivialAssemblyLinePattern {
override def apply(line: AssemblyLine): Boolean =
OpcodeClasses.AllLinear(line.opcode) || OpcodeClasses.ShortBranching(line.opcode)
if (line.opcode == Opcode.JSR) line.parameter match {
case MemoryAddressConstant(f: FunctionInMemory) => f.hasOptimizationHints
case _ => false
} else OpcodeClasses.AllLinear(line.opcode) || OpcodeClasses.ShortBranching(line.opcode)
override def hitRate: Double = 0.887
}
case object LinearOrLabel extends TrivialAssemblyLinePattern {
override def apply(line: AssemblyLine): Boolean =
line.opcode == Opcode.LABEL || OpcodeClasses.AllLinear(line.opcode)
if (line.opcode == Opcode.JSR) line.parameter match {
case MemoryAddressConstant(f: FunctionInMemory) => f.hasOptimizationHints
case _ => false
} else line.opcode == Opcode.LABEL || OpcodeClasses.AllLinear(line.opcode)
override def hitRate: Double = 0.899
}

View File

@ -631,9 +631,9 @@ object AbstractExpressionCompiler {
log.error(s"Cannot find function `${f.functionName}` with given params `${paramsWithTypes.map(_._1).mkString("(", ",", ")")}`", f.position)
}
val signature = NormalParamSignature(paramsWithTypes.map { case (t, _) =>
UninitializedMemoryVariable("?", t, VariableAllocationMethod.Auto, None, NoAlignment, isVolatile = false)
UninitializedMemoryVariable("?", t, VariableAllocationMethod.Auto, None, Set.empty, NoAlignment, isVolatile = false)
})
ExternFunction(f.functionName, NullType, signature, Constant.Zero, env, None)
ExternFunction(f.functionName, NullType, signature, Constant.Zero, env, Set.empty, None)
}
}
}

View File

@ -155,7 +155,7 @@ abstract class AbstractReturnDispatch[T <: AbstractCode] {
val a = InitializedArray(label + "$" + ix + ".array", None, (paramMins(ix) to paramMaxes(ix)).map { key =>
map(key)._2.lift(ix).getOrElse(LiteralExpression(0, 1))
}.toList,
ctx.function.declaredBank, b, b, readOnly = true, NoAlignment)
ctx.function.declaredBank, b, b, readOnly = true, Set.empty, NoAlignment)
env.registerUnnamedArray(a)
a
}

View File

@ -44,8 +44,8 @@ object M6809ReturnDispatch extends AbstractReturnDispatch[MLine] {
}
val copyParams = pair.reverse.flatten
// TODO: would it be better to use one table of words and do TFR X,D / LEAX D,X / LDX array,X ?
val jumpTableLo = InitializedArray(label + "$jl.array", None, (actualMin to actualMax).map(i => lobyte0(map(i)._1)).toList, ctx.function.declaredBank, b, b, readOnly = true, NoAlignment)
val jumpTableHi = InitializedArray(label + "$jh.array", None, (actualMin to actualMax).map(i => hibyte0(map(i)._1)).toList, ctx.function.declaredBank, b, b, readOnly = true, NoAlignment)
val jumpTableLo = InitializedArray(label + "$jl.array", None, (actualMin to actualMax).map(i => lobyte0(map(i)._1)).toList, ctx.function.declaredBank, b, b, readOnly = true, Set.empty, NoAlignment)
val jumpTableHi = InitializedArray(label + "$jh.array", None, (actualMin to actualMax).map(i => hibyte0(map(i)._1)).toList, ctx.function.declaredBank, b, b, readOnly = true, Set.empty, NoAlignment)
env.registerUnnamedArray(jumpTableLo)
env.registerUnnamedArray(jumpTableHi)
val moveOffsetToLo = (jumpTableLo.toAddress - actualMin).quickSimplify

View File

@ -41,7 +41,7 @@ object MosReturnDispatch extends AbstractReturnDispatch[AssemblyLine] {
}
if (useJmpaix) {
val jumpTable = InitializedArray(label + "$jt.array", None, (actualMin to actualMax).flatMap(i => List(lobyte0(map(i)._1), hibyte0(map(i)._1))).toList, ctx.function.declaredBank, b, b, readOnly = true, NoAlignment)
val jumpTable = InitializedArray(label + "$jt.array", None, (actualMin to actualMax).flatMap(i => List(lobyte0(map(i)._1), hibyte0(map(i)._1))).toList, ctx.function.declaredBank, b, b, readOnly = true, Set.empty, NoAlignment)
env.registerUnnamedArray(jumpTable)
if (copyParams.isEmpty) {
val loadIndex = MosExpressionCompiler.compile(ctx, stmt.indexer, Some(b -> RegisterVariable(MosRegister.A, b)), BranchSpec.None)
@ -56,8 +56,8 @@ object MosReturnDispatch extends AbstractReturnDispatch[AssemblyLine] {
}
} else {
val loadIndex = MosExpressionCompiler.compile(ctx, stmt.indexer, Some(b -> RegisterVariable(MosRegister.X, b)), BranchSpec.None)
val jumpTableLo = InitializedArray(label + "$jl.array", None, (actualMin to actualMax).map(i => lobyte1(map(i)._1)).toList, ctx.function.declaredBank, b, b, readOnly = true, NoAlignment)
val jumpTableHi = InitializedArray(label + "$jh.array", None, (actualMin to actualMax).map(i => hibyte1(map(i)._1)).toList, ctx.function.declaredBank, b, b, readOnly = true, NoAlignment)
val jumpTableLo = InitializedArray(label + "$jl.array", None, (actualMin to actualMax).map(i => lobyte1(map(i)._1)).toList, ctx.function.declaredBank, b, b, readOnly = true, Set.empty, NoAlignment)
val jumpTableHi = InitializedArray(label + "$jh.array", None, (actualMin to actualMax).map(i => hibyte1(map(i)._1)).toList, ctx.function.declaredBank, b, b, readOnly = true, Set.empty, NoAlignment)
env.registerUnnamedArray(jumpTableLo)
env.registerUnnamedArray(jumpTableHi)
val actualJump = if (ctx.options.flag(CompilationFlag.LUnixRelocatableCode)) {

View File

@ -51,8 +51,8 @@ object Z80ReturnDispatch extends AbstractReturnDispatch[ZLine] {
}
val copyParams = pair._2.reverse.flatten
val offsetAfterParams = pair._1
val jumpTableLo = InitializedArray(label + "$jl.array", None, (actualMin to actualMax).map(i => lobyte0(map(i)._1)).toList, ctx.function.declaredBank, b, b, readOnly = true, NoAlignment)
val jumpTableHi = InitializedArray(label + "$jh.array", None, (actualMin to actualMax).map(i => hibyte0(map(i)._1)).toList, ctx.function.declaredBank, b, b, readOnly = true, NoAlignment)
val jumpTableLo = InitializedArray(label + "$jl.array", None, (actualMin to actualMax).map(i => lobyte0(map(i)._1)).toList, ctx.function.declaredBank, b, b, readOnly = true, Set.empty, NoAlignment)
val jumpTableHi = InitializedArray(label + "$jh.array", None, (actualMin to actualMax).map(i => hibyte0(map(i)._1)).toList, ctx.function.declaredBank, b, b, readOnly = true, Set.empty, NoAlignment)
env.registerUnnamedArray(jumpTableLo)
env.registerUnnamedArray(jumpTableHi)

View File

@ -76,6 +76,7 @@ class Z80StatementPreprocessor(ctx: CompilationContext, statements: List[Executa
register = false,
None,
None,
Set.empty,
None
), ctx.options, isPointy = true)
(a -> f.variable) -> (a + infix + f.variable)

View File

@ -392,8 +392,8 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
InitializedMemoryVariable
UninitializedMemoryVariable
getArrayOrPointer(name) match {
case th@InitializedArray(_, _, cs, _, i, e, ro, _) => ConstantPointy(th.toAddress, Some(name), Some(e.alignedSize * cs.length), Some(cs.length), i, e, th.alignment, readOnly = ro)
case th@UninitializedArray(_, elementCount, _, i, e, ro, _) => ConstantPointy(th.toAddress, Some(name), Some(elementCount * e.alignedSize), Some(elementCount / e.size), i, e, th.alignment, readOnly = ro)
case th@InitializedArray(_, _, cs, _, i, e, ro, _, _) => ConstantPointy(th.toAddress, Some(name), Some(e.alignedSize * cs.length), Some(cs.length), i, e, th.alignment, readOnly = ro)
case th@UninitializedArray(_, elementCount, _, i, e, ro, _, _) => ConstantPointy(th.toAddress, Some(name), Some(elementCount * e.alignedSize), Some(elementCount / e.size), i, e, th.alignment, readOnly = ro)
case th@RelativeArray(_, _, elementCount, _, i, e, ro) => ConstantPointy(th.toAddress, Some(name), Some(elementCount * e.alignedSize), Some(elementCount / e.size), i, e, NoAlignment, readOnly = ro)
case ConstantThing(_, value, typ) if typ.size <= 2 && typ.isPointy =>
val e = get[VariableType](typ.pointerTargetName)
@ -1252,7 +1252,7 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
var hasElidedReturnVariable = false
val hasReturnVariable = resultType.size > Cpu.getMaxSizeReturnableViaRegisters(options.platform.cpu, options)
if (hasReturnVariable) {
registerVariable(VariableDeclarationStatement(stmt.name + ".return", stmt.resultType, None, global = true, stack = false, constant = false, volatile = false, register = false, None, None, None), options, isPointy = false)
registerVariable(VariableDeclarationStatement(stmt.name + ".return", stmt.resultType, None, global = true, stack = false, constant = false, volatile = false, register = false, None, None, Set.empty, None), options, isPointy = false)
}
stmt.statements match {
case None =>
@ -1267,6 +1267,7 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
params,
addr,
env,
prepareFunctionOptimizationHints(options, stmt),
stmt.bank
)
addThing(mangled, stmt.position)
@ -1395,6 +1396,7 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
isConstPure = stmt.constPure,
position = stmt.position,
declaredBank = stmt.bank,
optimizationHints = prepareFunctionOptimizationHints(options, stmt),
alignment = stmt.alignment.getOrElse(if (name == "main") NoAlignment else defaultFunctionAlignment(options, hot = true)) // TODO: decide actual hotness in a smarter way
)
addThing(mangled, stmt.position)
@ -1421,7 +1423,7 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
case _ => ???
}
if (maybeGet[Thing](name).isEmpty) {
root.registerArray(ArrayDeclarationStatement(name, None, None, "byte", None, const = true, Some(LiteralContents(literal.characters)), None, options.isBigEndian).pos(literal.position), options)
root.registerArray(ArrayDeclarationStatement(name, None, None, "byte", None, const = true, Some(LiteralContents(literal.characters)), Set.empty, None, options.isBigEndian).pos(literal.position), options)
}
name
}
@ -1430,7 +1432,7 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
val b = get[Type]("byte")
if (!thing.zeropage && options.flag(CompilationFlag.LUnixRelocatableCode)) {
val w = get[Type]("word")
val relocatable = UninitializedMemoryVariable(thing.name + ".addr", w, VariableAllocationMethod.Static, None, defaultVariableAlignment(options, 2), isVolatile = false)
val relocatable = UninitializedMemoryVariable(thing.name + ".addr", w, VariableAllocationMethod.Static, None, Set.empty, defaultVariableAlignment(options, 2), isVolatile = false)
val addr = relocatable.toAddress
addThing(relocatable, position)
addThing(RelativeVariable(thing.name + ".addr.hi", addr + 1, b, zeropage = false, None, isVolatile = false), position)
@ -1510,7 +1512,7 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
function.returnType.name,
List(ParameterDeclaration(param.typ.name, ByMosRegister(MosRegister.AX))),
Some(function.bank(options)),
None, None,
None, Set.empty, None,
Some(List(
MosAssemblyStatement(STA, Absolute, VariableExpression(localNameForParam), Elidability.Volatile),
MosAssemblyStatement(STX, Absolute, VariableExpression(localNameForParam) #+# 1, Elidability.Volatile),
@ -1542,7 +1544,7 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
if (pointies(name)) VariableAllocationMethod.Zeropage
else if (typ.isPointy && options.platform.cpuFamily == CpuFamily.M6502) VariableAllocationMethod.Register
else VariableAllocationMethod.Auto
val v = UninitializedMemoryVariable(prefix + name, typ, allocationMethod, None, defaultVariableAlignment(options, 2), isVolatile = false)
val v = UninitializedMemoryVariable(prefix + name, typ, allocationMethod, None, Set.empty, defaultVariableAlignment(options, 2), isVolatile = false)
addThing(v, stmt.position)
registerAddressConstant(v, stmt.position, options, Some(typ))
val addr = v.toAddress
@ -1738,6 +1740,78 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
else NoAlignment
}
def prepareFunctionOptimizationHints(options: CompilationOptions, stmt: FunctionDeclarationStatement): Set[String] = {
if (!options.flag(CompilationFlag.UseOptimizationHints)) return Set.empty
val filteredFlags = stmt.optimizationHints.flatMap{
case f@("hot" | "cold" | "idempotent" | "preserves_memory" | "inline" | "odd" | "even") =>
Seq(f)
case f@("preserves_a" | "preserves_x" | "preserves_y" | "preserves_c")
if options.platform.cpuFamily == CpuFamily.M6502 =>
if (stmt.statements.isDefined && !stmt.assembly) {
log.warn(s"Cannot use the $f optimization flags on non-assembly functions", stmt.position)
Nil
} else {
Seq(f)
}
case f@("preserves_a" | "preserves_b" | "preserves_d" | "preserves_c" | "preserves_x" | "preserves_y" | "preserves_u")
if options.platform.cpuFamily == CpuFamily.M6809 =>
if (stmt.statements.isDefined && !stmt.assembly) {
log.warn(s"Cannot use the $f optimization flags on non-assembly functions", stmt.position)
Nil
} else {
Seq(f)
}
case f@("preserves_dp")
if options.platform.cpuFamily == CpuFamily.M6809 =>
Seq(f)
case f =>
log.warn(s"Unsupported function optimization flag: $f", stmt.position)
Nil
}
if (filteredFlags("hot") && filteredFlags("cold")) {
log.warn(s"Conflicting optimization flags used: `hot` and `cold`", stmt.position)
}
if (filteredFlags("even") && filteredFlags("odd")) {
log.warn(s"Conflicting optimization flags used: `even` and `odd`", stmt.position)
}
if (filteredFlags("even") || filteredFlags("odd")) {
maybeGet[Type](stmt.resultType) match {
case Some(t) if t.size < 1 =>
log.warn(s"Cannot use `even` or `odd` flags with an empty return type", stmt.position)
case Some(t: CompoundVariableType) =>
log.warn(s"Cannot use `even` or `odd` flags with a compound return type", stmt.position)
case _ =>
}
}
filteredFlags
}
def prepareVariableOptimizationHints(options: CompilationOptions, stmt: VariableDeclarationStatement): Set[String] = {
if (!options.flag(CompilationFlag.UseOptimizationHints)) return Set.empty
val filteredFlags = stmt.optimizationHints.flatMap{
case f@("odd" | "even") =>
Seq(f)
case f =>
log.warn(s"Unsupported variable optimization flag: $f", stmt.position)
Nil
}
if (filteredFlags("even") && filteredFlags("odd")) {
log.warn(s"Conflicting optimization flags used: `even` and `odd`", stmt.position)
}
filteredFlags
}
//noinspection UnnecessaryPartialFunction
def prepareArrayOptimizationHints(options: CompilationOptions, stmt: ArrayDeclarationStatement): Set[String] = {
if (!options.flag(CompilationFlag.UseOptimizationHints)) return Set.empty
val filteredFlags: Set[String] = stmt.optimizationHints.flatMap{
case f =>
log.warn(s"Unsupported array optimization flag: $f", stmt.position)
Nil
}
filteredFlags
}
def registerArray(stmt: ArrayDeclarationStatement, options: CompilationOptions): Unit = {
if (options.flag(CompilationFlag.LUnixRelocatableCode) && stmt.alignment.exists(_.isMultiplePages)) {
log.error("Invalid alignment for LUnix code", stmt.position)
@ -1785,12 +1859,12 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
val alignment = stmt.alignment.getOrElse(defaultArrayAlignment(options, length))
val array = address match {
case None => UninitializedArray(arrayName + ".array", length.toInt,
declaredBank = stmt.bank, indexType, e, stmt.const, alignment)
declaredBank = stmt.bank, indexType, e, stmt.const, prepareArrayOptimizationHints(options, stmt), alignment)
case Some(aa) => RelativeArray(arrayName + ".array", aa, length.toInt,
declaredBank = stmt.bank, indexType, e, stmt.const)
}
addThing(array, stmt.position)
registerAddressConstant(UninitializedMemoryVariable(arrayName, p, VariableAllocationMethod.None, stmt.bank, alignment, isVolatile = false), stmt.position, options, Some(e))
registerAddressConstant(UninitializedMemoryVariable(arrayName, p, VariableAllocationMethod.None, stmt.bank, Set.empty, alignment, isVolatile = false), stmt.position, options, Some(e))
val a = address match {
case None => array.toAddress
case Some(aa) => aa
@ -1800,7 +1874,7 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
if (options.flag(CompilationFlag.LUnixRelocatableCode)) {
val b = get[Type]("byte")
val w = get[Type]("word")
val relocatable = UninitializedMemoryVariable(arrayName, w, VariableAllocationMethod.Static, None, NoAlignment, isVolatile = false)
val relocatable = UninitializedMemoryVariable(arrayName, w, VariableAllocationMethod.Static, None, Set.empty, NoAlignment, isVolatile = false)
val addr = relocatable.toAddress
addThing(relocatable, stmt.position)
addThing(RelativeVariable(arrayName + ".addr.hi", addr + 1, b, zeropage = false, None, isVolatile = false), stmt.position)
@ -1868,13 +1942,13 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
for (element <- contents) {
AbstractExpressionCompiler.checkAssignmentTypeLoosely(this, element, e)
}
val array = InitializedArray(arrayName + ".array", address, contents, declaredBank = stmt.bank, indexType, e, readOnly = stmt.const, alignment)
val array = InitializedArray(arrayName + ".array", address, contents, declaredBank = stmt.bank, indexType, e, readOnly = stmt.const, prepareArrayOptimizationHints(options, stmt), alignment)
if (!stmt.const && options.platform.ramInitialValuesBank.isDefined && array.bank(options) != "default") {
log.error(s"Preinitialized writable array `${stmt.name}` has to be in the default segment.", stmt.position)
}
addThing(array, stmt.position)
registerAddressConstant(UninitializedMemoryVariable(arrayName, p, VariableAllocationMethod.None,
declaredBank = stmt.bank, alignment, isVolatile = false), stmt.position, options, Some(e))
declaredBank = stmt.bank, Set.empty, alignment, isVolatile = false), stmt.position, options, Some(e))
val a = address match {
case None => array.toAddress
case Some(aa) => aa
@ -1884,7 +1958,7 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
if (options.flag(CompilationFlag.LUnixRelocatableCode)) {
val b = get[Type]("byte")
val w = get[Type]("word")
val relocatable = UninitializedMemoryVariable(arrayName, w, VariableAllocationMethod.Static, None, NoAlignment, isVolatile = false)
val relocatable = UninitializedMemoryVariable(arrayName, w, VariableAllocationMethod.Static, None, Set.empty, NoAlignment, isVolatile = false)
val addr = relocatable.toAddress
addThing(relocatable, stmt.position)
addThing(RelativeVariable(arrayName + ".array.hi", addr + 1, b, zeropage = false, None, isVolatile = false), stmt.position)
@ -2002,9 +2076,10 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
if (alloc != VariableAllocationMethod.Static && stmt.initialValue.isDefined) {
log.error(s"`$name` cannot be preinitialized`", position)
}
val optimizationHints = prepareVariableOptimizationHints(options, stmt)
val v = stmt.initialValue.fold[MemoryVariable](UninitializedMemoryVariable(prefix + name, typ, alloc,
declaredBank = stmt.bank, alignment, isVolatile = stmt.volatile)){ive =>
InitializedMemoryVariable(name, None, typ, ive, declaredBank = stmt.bank, alignment, isVolatile = stmt.volatile)
declaredBank = stmt.bank, optimizationHints, alignment, isVolatile = stmt.volatile)){ive =>
InitializedMemoryVariable(name, None, typ, ive, declaredBank = stmt.bank, optimizationHints, alignment, isVolatile = stmt.volatile)
}
registerAddressConstant(v, stmt.position, options, Some(typ))
(v, v.toAddress)
@ -2217,8 +2292,8 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
}
} else {
if (function.params.length != actualParams.length && function.name != "call") {
log.error(s"Invalid number of parameters for function `$name`", actualParams.headOption.flatMap(_._2.position))
}
log.error(s"Invalid number of parameters for function `$name`", actualParams.headOption.flatMap(_._2.position))
}
}
if (name == "call") return Some(function)
function.params match {
@ -2366,7 +2441,7 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
val b = get[VariableType]("byte")
val v = get[Type]("void")
if (options.flag(CompilationFlag.OptimizeForSonicSpeed)) {
addThing(InitializedArray("identity$", None, IndexedSeq.tabulate(256)(n => LiteralExpression(n, 1)), declaredBank = None, b, b, readOnly = true, defaultArrayAlignment(options, 256)), None)
addThing(InitializedArray("identity$", None, IndexedSeq.tabulate(256)(n => LiteralExpression(n, 1)), declaredBank = None, b, b, readOnly = true, Set.empty, defaultArrayAlignment(options, 256)), None)
}
program.declarations.foreach {
case a: AliasDefinitionStatement => registerAlias(a)
@ -2414,16 +2489,17 @@ class Environment(val parent: Option[Environment], val prefix: String, val cpuFa
register = false,
initialValue = None,
address = None,
optimizationHints = Set.empty,
alignment = None), options, isPointy = true)
}
if (CpuFamily.forType(options.platform.cpu) == CpuFamily.M6502) {
if (!things.contains("__constant8")) {
things("__constant8") = InitializedArray("__constant8", None, List(LiteralExpression(8, 1)), declaredBank = None, b, b, readOnly = true, NoAlignment)
things("__constant8") = InitializedArray("__constant8", None, List(LiteralExpression(8, 1)), declaredBank = None, b, b, readOnly = true, Set.empty, NoAlignment)
}
if (options.flag(CompilationFlag.SoftwareStack)) {
if (!things.contains("__sp")) {
things("__sp") = UninitializedMemoryVariable("__sp", b, VariableAllocationMethod.Auto, None, NoAlignment, isVolatile = false)
things("__stack") = UninitializedArray("__stack", 256, None, b, b, readOnly = false, DivisibleAlignment(256))
things("__sp") = UninitializedMemoryVariable("__sp", b, VariableAllocationMethod.Auto, None, Set.empty, NoAlignment, isVolatile = false)
things("__stack") = UninitializedArray("__stack", 256, None, b, b, readOnly = false, Set.empty, DivisibleAlignment(256))
}
}
}

View File

@ -248,6 +248,8 @@ sealed trait ThingInMemory extends Thing {
def toAddress: Constant
def hasOptimizationHints: Boolean = false
var farFlag: Option[Boolean] = None
val declaredBank: Option[String]
@ -264,7 +266,11 @@ sealed trait PreallocableThing extends ThingInMemory {
def alignment: MemoryAlignment
def toAddress: Constant = address.getOrElse(MemoryAddressConstant(this))
def toAddress: Constant = if (hasOptimizationHints) {
MemoryAddressConstant(this)
} else {
address.getOrElse(MemoryAddressConstant(this))
}
}
case class Label(name: String) extends ThingInMemory {
@ -294,6 +300,10 @@ sealed trait VariableInMemory extends Variable with ThingInMemory with Indexable
override def bank(compilationOptions: CompilationOptions): String =
declaredBank.getOrElse("default")
def optimizationHints: Set[String]
override def hasOptimizationHints: Boolean = optimizationHints.nonEmpty
}
case class RegisterVariable(register: MosRegister.Value, typ: Type) extends Variable {
@ -347,6 +357,7 @@ case class UninitializedMemoryVariable(
alloc:
VariableAllocationMethod.Value,
declaredBank: Option[String],
override val optimizationHints: Set[String],
override val alignment: MemoryAlignment,
override val isVolatile: Boolean) extends MemoryVariable with UninitializedMemory {
override def sizeInBytes: Int = typ.alignedSize
@ -362,6 +373,7 @@ case class InitializedMemoryVariable(
typ: Type,
initialValue: Expression,
declaredBank: Option[String],
override val optimizationHints: Set[String],
override val alignment: MemoryAlignment,
override val isVolatile: Boolean) extends MemoryVariable with PreallocableThing {
override def zeropage: Boolean = false
@ -380,9 +392,18 @@ trait MfArray extends ThingInMemory with IndexableThing {
def sizeInBytes: Int
def elementCount: Int
def readOnly: Boolean
def optimizationHints: Set[String]
override def hasOptimizationHints: Boolean = optimizationHints.nonEmpty
}
case class UninitializedArray(name: String, elementCount: Int, declaredBank: Option[String], indexType: VariableType, elementType: VariableType, override val readOnly: Boolean, override val alignment: MemoryAlignment) extends MfArray with UninitializedMemory {
case class UninitializedArray(name: String,
elementCount: Int,
declaredBank: Option[String],
indexType: VariableType,
elementType: VariableType,
override val readOnly: Boolean,
override val optimizationHints: Set[String],
override val alignment: MemoryAlignment) extends MfArray with UninitializedMemory {
override def toAddress: MemoryAddressConstant = MemoryAddressConstant(this)
override def alloc: VariableAllocationMethod.Value = VariableAllocationMethod.Static
@ -396,7 +417,13 @@ case class UninitializedArray(name: String, elementCount: Int, declaredBank: Opt
override def sizeInBytes: Int = elementCount * elementType.alignedSize
}
case class RelativeArray(name: String, address: Constant, elementCount: Int, declaredBank: Option[String], indexType: VariableType, elementType: VariableType, override val readOnly: Boolean) extends MfArray {
case class RelativeArray(name: String,
address: Constant,
elementCount: Int,
declaredBank: Option[String],
indexType: VariableType,
elementType: VariableType,
override val readOnly: Boolean) extends MfArray {
override def toAddress: Constant = address
override def isFar(compilationOptions: CompilationOptions): Boolean = farFlag.getOrElse(false)
@ -408,9 +435,19 @@ case class RelativeArray(name: String, address: Constant, elementCount: Int, dec
override def sizeInBytes: Int = elementCount * elementType.alignedSize
override def rootName: String = address.rootThingName
override def optimizationHints: Set[String] = Set.empty
}
case class InitializedArray(name: String, address: Option[Constant], contents: Seq[Expression], declaredBank: Option[String], indexType: VariableType, elementType: VariableType, override val readOnly: Boolean, override val alignment: MemoryAlignment) extends MfArray with PreallocableThing {
case class InitializedArray(name: String,
address: Option[Constant],
contents: Seq[Expression],
declaredBank: Option[String],
indexType: VariableType,
elementType: VariableType,
override val readOnly: Boolean,
override val optimizationHints: Set[String],
override val alignment: MemoryAlignment) extends MfArray with PreallocableThing {
override def shouldGenerate = true
override def isFar(compilationOptions: CompilationOptions): Boolean = farFlag.getOrElse(false)
@ -425,10 +462,17 @@ case class InitializedArray(name: String, address: Option[Constant], contents: S
override def sizeInBytes: Int = contents.size * elementType.alignedSize
}
case class RelativeVariable(name: String, address: Constant, typ: Type, zeropage: Boolean, declaredBank: Option[String], override val isVolatile: Boolean) extends VariableInMemory {
case class RelativeVariable(name: String,
address: Constant,
typ: Type,
zeropage: Boolean,
declaredBank: Option[String],
override val isVolatile: Boolean) extends VariableInMemory {
override def toAddress: Constant = address
override def rootName: String = address.rootThingName
override def optimizationHints: Set[String] = Set.empty
}
sealed trait MangledFunction extends CallableThing {
@ -484,6 +528,10 @@ sealed trait FunctionInMemory extends MangledFunction with ThingInMemory {
override def canBePointedTo: Boolean = !interrupt && returnType.size <= 2 && params.canBePointedTo && name !="call"
override def requiresTrampoline(compilationOptions: CompilationOptions): Boolean = params.requireTrampoline(compilationOptions)
def optimizationHints: Set[String]
override def hasOptimizationHints: Boolean = optimizationHints.nonEmpty
}
case class ExternFunction(name: String,
@ -491,8 +539,9 @@ case class ExternFunction(name: String,
params: ParamSignature,
address: Constant,
environment: Environment,
override val optimizationHints: Set[String],
declaredBank: Option[String]) extends FunctionInMemory {
override def toAddress: Constant = address
override def toAddress: Constant = if (hasOptimizationHints) MemoryAddressConstant(this) else address
override def interrupt = false
@ -515,6 +564,7 @@ case class NormalFunction(name: String,
kernalInterrupt: Boolean,
inAssembly: Boolean,
isConstPure: Boolean,
override val optimizationHints: Set[String],
reentrant: Boolean,
position: Option[Position],
declaredBank: Option[String],

View File

@ -211,6 +211,7 @@ sealed class NiceFunctionProperty(override val toString: String)
object NiceFunctionProperty {
case object DoesntReadMemory extends NiceFunctionProperty("MR")
case object DoesntWriteMemory extends NiceFunctionProperty("MW")
case object Idempotent extends NiceFunctionProperty("Idem")
case object IsLeaf extends NiceFunctionProperty("LEAF")
}
@ -245,6 +246,7 @@ object M6809NiceFunctionProperty {
case object DoesntChangeX extends NiceFunctionProperty("X")
case object DoesntChangeY extends NiceFunctionProperty("Y")
case object DoesntChangeU extends NiceFunctionProperty("U")
case object DoesntChangeDP extends NiceFunctionProperty("DP")
case object DoesntChangeCF extends NiceFunctionProperty("C")
case class SetsBTo(value: Int) extends NiceFunctionProperty("B=" + value)
}
@ -448,6 +450,7 @@ sealed trait DeclarationStatement extends Statement {
sealed trait BankedDeclarationStatement extends DeclarationStatement {
def bank: Option[String]
def name: String
def optimizationHints: Set[String]
def withChangedBank(bank: String): BankedDeclarationStatement
}
@ -465,6 +468,7 @@ case class VariableDeclarationStatement(name: String,
register: Boolean,
initialValue: Option[Expression],
address: Option[Expression],
optimizationHints: Set[String],
alignment: Option[MemoryAlignment]) extends BankedDeclarationStatement {
override def getAllExpressions: List[Expression] = List(initialValue, address).flatten
@ -581,6 +585,7 @@ case class ArrayDeclarationStatement(name: String,
address: Option[Expression],
const: Boolean,
elements: Option[ArrayContents],
optimizationHints: Set[String],
alignment: Option[MemoryAlignment],
bigEndian: Boolean) extends BankedDeclarationStatement {
override def getAllExpressions: List[Expression] = List(length, address).flatten ++ elements.fold(List[Expression]())(_.getAllExpressions(bigEndian))
@ -602,6 +607,7 @@ case class FunctionDeclarationStatement(name: String,
params: List[ParameterDeclaration],
bank: Option[String],
address: Option[Expression],
optimizationHints: Set[String],
alignment: Option[MemoryAlignment],
statements: Option[List[Statement]],
isMacro: Boolean,

View File

@ -272,6 +272,12 @@ abstract class AbstractAssembler[T <: AbstractCode](private val program: Program
val compiledFunctions = mutable.Map[String, CompiledFunction[T]]()
val recommendedCompilationOrder = callGraph.recommendedCompilationOrder
val niceFunctionProperties = mutable.Set[(NiceFunctionProperty, String)]()
env.things.values.foreach {
case function: FunctionInMemory =>
gatherFunctionOptimizationHints(options, niceFunctionProperties, function)
case _ =>
}
println(niceFunctionProperties)
val aliases = env.getAliases
recommendedCompilationOrder.foreach { f =>
if (!env.isAlias(f)) env.maybeGet[NormalFunction](f).foreach { function =>
@ -301,7 +307,12 @@ abstract class AbstractAssembler[T <: AbstractCode](private val program: Program
val code = opt.optimize(function, c, OptimizationContext(options, labelMapImm, env.maybeGet[ThingInMemory]("__reg"), niceFunctionPropertiesImm))
if (code eq c) code else quickSimplify(code)
}
compiledFunctions(f) = NormalCompiledFunction(function.declaredBank.getOrElse(platform.defaultCodeBank), extraOptimizedCode, function.address.isDefined, function.alignment)
compiledFunctions(f) = NormalCompiledFunction(
function.declaredBank.getOrElse(platform.defaultCodeBank),
extraOptimizedCode,
function.address.isDefined,
function.optimizationHints,
function.alignment)
optimizedCodeSize += code.map(_.sizeInBytes).sum
if (options.flag(CompilationFlag.InterproceduralOptimization)) {
gatherNiceFunctionProperties(options, niceFunctionProperties, function, code)
@ -347,7 +358,7 @@ abstract class AbstractAssembler[T <: AbstractCode](private val program: Program
})
env.allPreallocatables.filterNot(o => unusedRuntimeObjects(o.name)).foreach {
case thing@InitializedArray(name, Some(NumericConstant(address, _)), items, _, _, elementType, readOnly, _) =>
case thing@InitializedArray(name, Some(NumericConstant(address, _)), items, _, _, elementType, readOnly, _, _) =>
val bank = thing.bank(options)
if (!readOnly && options.platform.ramInitialValuesBank.isDefined) {
log.error(s"Preinitialized writable array $name cannot be put at a fixed address")
@ -374,13 +385,13 @@ abstract class AbstractAssembler[T <: AbstractCode](private val program: Program
}
printArrayToAssemblyOutput(assembly, name, elementType, items)
initializedVariablesSize += thing.sizeInBytes
case thing@InitializedArray(name, Some(_), items, _, _, _, _, _) => ???
case thing@InitializedArray(name, Some(_), items, _, _, _, _, _, _) => ???
case f: NormalFunction if f.address.isDefined =>
val bank = f.bank(options)
val bank0 = mem.banks(bank)
val index = f.address.get.asInstanceOf[NumericConstant].value.toInt
compiledFunctions(f.name) match {
case NormalCompiledFunction(_, functionCode, _, _) =>
case NormalCompiledFunction(_, functionCode, _, _, _) =>
labelMap(f.name) = bank0.index -> index
val end = outputFunction(bank, functionCode, index, assembly, options)
for (i <- index until end) {
@ -424,9 +435,9 @@ abstract class AbstractAssembler[T <: AbstractCode](private val program: Program
val sortedCompilerFunctions = compiledFunctions.toList.sortBy { case (_, cf) => cf.orderKey }
for (layoutStage <- 0 until layoutStageCount) {
sortedCompilerFunctions.filterNot(o => unusedRuntimeObjects(o._1)).foreach {
case (_, NormalCompiledFunction(_, _, true, _)) =>
case (_, NormalCompiledFunction(_, _, true, _, _)) =>
// already done before
case (name, th@NormalCompiledFunction(bank, functionCode, false, alignment)) if layoutStage == getLayoutStageNcf(name, th) =>
case (name, th@NormalCompiledFunction(bank, functionCode, false, optimizationFlags, alignment)) if layoutStage == getLayoutStageNcf(name, th) =>
val size = functionCode.map(_.sizeInBytes).sum
val bank0 = mem.banks(bank)
val index = codeAllocators(bank).allocateBytes(bank0, options, size, initialized = true, writeable = false, location = AllocationLocation.High, alignment = alignment)
@ -443,9 +454,9 @@ abstract class AbstractAssembler[T <: AbstractCode](private val program: Program
if (layoutStage == 0) {
// force early allocation of text literals:
env.allPreallocatables.filterNot(o => unusedRuntimeObjects(o.name)).foreach {
case thing@InitializedArray(_, _, items, _, _, _, _, _) =>
case thing@InitializedArray(_, _, items, _, _, _, _, _, _) =>
items.foreach(env.eval(_))
case InitializedMemoryVariable(_, _, _, value, _, _, _) =>
case InitializedMemoryVariable(_, _, _, value, _, _, _, _) =>
env.eval(value)
case _ =>
}
@ -453,9 +464,9 @@ abstract class AbstractAssembler[T <: AbstractCode](private val program: Program
if (layoutStage == defaultStage && options.flag(CompilationFlag.LUnixRelocatableCode)) {
env.allThings.things.foreach {
case (_, m@UninitializedMemoryVariable(name, typ, _, _, _, _)) if name.endsWith(".addr") || env.maybeGet[Thing](name + ".array").isDefined =>
case (_, m@UninitializedMemoryVariable(name, typ, _, _, _, _, _)) if name.endsWith(".addr") || env.maybeGet[Thing](name + ".array").isDefined =>
val isUsed = compiledFunctions.values.exists {
case NormalCompiledFunction(_, functionCode, _, _) => functionCode.exists(_.parameter.isRelatedTo(m))
case NormalCompiledFunction(_, functionCode, _, _, _) => functionCode.exists(_.parameter.isRelatedTo(m))
case _ => false
}
// println(m.name -> isUsed)
@ -508,7 +519,7 @@ abstract class AbstractAssembler[T <: AbstractCode](private val program: Program
}
}
env.allPreallocatables.filterNot(o => unusedRuntimeObjects(o.name)).foreach {
case thing@InitializedArray(name, None, items, _, _, elementType, readOnly, alignment) if readOnly == readOnlyPass && layoutStage == getLayoutStageThing(thing) =>
case thing@InitializedArray(name, None, items, _, _, elementType, readOnly, _, alignment) if readOnly == readOnlyPass && layoutStage == getLayoutStageThing(thing) =>
val bank = thing.bank(options)
if (options.platform.ramInitialValuesBank.isDefined && !readOnly && bank != "default") {
log.error(s"Preinitialized writable array `$name` should be defined in the `default` bank")
@ -538,7 +549,7 @@ abstract class AbstractAssembler[T <: AbstractCode](private val program: Program
printArrayToAssemblyOutput(assembly, name, elementType, items)
initializedVariablesSize += items.length
justAfterCode += bank -> index
case m@InitializedMemoryVariable(name, None, typ, value, _, alignment, _) if !readOnlyPass && layoutStage == getLayoutStageThing(m) =>
case m@InitializedMemoryVariable(name, None, typ, value, _, _, alignment, _) if !readOnlyPass && layoutStage == getLayoutStageThing(m) =>
val bank = m.bank(options)
if (options.platform.ramInitialValuesBank.isDefined && bank != "default") {
log.error(s"Preinitialized variable `$name` should be defined in the `default` bank")
@ -744,6 +755,8 @@ abstract class AbstractAssembler[T <: AbstractCode](private val program: Program
def gatherNiceFunctionProperties(options: CompilationOptions, niceFunctionProperties: mutable.Set[(NiceFunctionProperty, String)], function: NormalFunction, code: List[T]): Unit
def gatherFunctionOptimizationHints(options: CompilationOptions, niceFunctionProperties: mutable.Set[(NiceFunctionProperty, String)], function: FunctionInMemory): Unit
def performFinalOptimizationPass(f: NormalFunction, actuallyOptimize: Boolean, options: CompilationOptions, code: List[T]): List[T]
private val FinalWhitespace = "\\s+$".r

View File

@ -30,7 +30,7 @@ abstract class AbstractInliningCalculator[T <: AbstractCode] {
aggressivenessForNormal: Double,
aggressivenessForRecommended: Double): InliningResult = {
val callCount = mutable.Map[String, Int]().withDefaultValue(0)
val allFunctions = mutable.Set[String]()
val allFunctions = mutable.Map[String, Double]()
val badFunctions = mutable.Set[String]()
val recommendedFunctions = mutable.Set[String]()
getAllCalledFunctions(program.declarations).foreach{
@ -39,10 +39,13 @@ abstract class AbstractInliningCalculator[T <: AbstractCode] {
}
program.declarations.foreach{
case f:FunctionDeclarationStatement =>
allFunctions += f.name
if (f.inlinable.contains(true)) {
recommendedFunctions += f.name
}
val aggressiveness =
if (f.inlinable.contains(true) || f.optimizationHints("inline")) aggressivenessForRecommended
else aggressivenessForNormal
allFunctions(f.name) = aggressiveness
if (f.isMacro
|| f.inlinable.contains(false)
|| f.address.isDefined
@ -55,9 +58,9 @@ abstract class AbstractInliningCalculator[T <: AbstractCode] {
}
allFunctions --= badFunctions
recommendedFunctions --= badFunctions
val map = (if (inlineByDefault) allFunctions else recommendedFunctions).map(f => f -> {
val map = (if (inlineByDefault) allFunctions.keySet else recommendedFunctions).map(f => f -> {
val size = sizes(callCount(f) min (sizes.size - 1))
val aggressiveness = if (recommendedFunctions(f)) aggressivenessForRecommended else aggressivenessForNormal
val aggressiveness = allFunctions.getOrElse(f, aggressivenessForNormal)
(size * aggressiveness).floor.toInt
}).toMap
InliningResult(map, badFunctions.toSet)

View File

@ -9,7 +9,7 @@ sealed trait CompiledFunction[T <: AbstractCode] {
def orderKey : (Int, String)
}
case class NormalCompiledFunction[T <: AbstractCode](segment: String, code: List[T], hasFixedAddress: Boolean, alignment: MemoryAlignment) extends CompiledFunction[T] {
case class NormalCompiledFunction[T <: AbstractCode](segment: String, code: List[T], hasFixedAddress: Boolean, optimizationFlags: Set[String], alignment: MemoryAlignment) extends CompiledFunction[T] {
override def orderKey: (Int, String) = (if (hasFixedAddress) 1 else 2) -> ""
}

View File

@ -61,8 +61,8 @@ abstract class Deduplicate[T <: AbstractCode](env: Environment, options: Compila
var result = ListBuffer[(String, CompiledFunction[T])]()
val snippets: Seq[(List[T], CodeChunk[T])] = segContents.toSeq.flatMap {
case (_, Left(_)) => Nil
case (functionName, Right(CodeAndAlignment(code, _))) =>
if (functionName.startsWith(".xc")) Nil
case (functionName, Right(CodeAndAlignment(code, optimizationFlags, _))) =>
if (optimizationFlags("hot") || functionName.startsWith(".xc")) Nil
else getExtractableSnippets(functionName, code).filter(_.codeSizeInBytes.>=(minSnippetSize)).map(code -> _)
}
val chunksWithThresholds: Seq[(CodeChunk[T], Int)] = snippets.flatMap { case (wholeCode, snippet) =>
@ -135,7 +135,7 @@ abstract class Deduplicate[T <: AbstractCode](env: Environment, options: Compila
for((code, instances) <- best._2) {
val newName = env.nextLabel("xc")
val newCode = createLabel(newName) :: tco(instances.head.renumerateLabels(this, temporary = false).value :+ createReturn)
result += newName -> NormalCompiledFunction(segmentName, newCode, hasFixedAddress = false, alignment = NoAlignment)
result += newName -> NormalCompiledFunction(segmentName, newCode, hasFixedAddress = false, optimizationFlags = Set.empty, alignment = NoAlignment)
for(instance <- instances) {
toReplace(instance.functionName)(instance.offset) = newName
for (i <- instance.offset + 1 until instance.endOffset) {
@ -154,7 +154,7 @@ abstract class Deduplicate[T <: AbstractCode](env: Environment, options: Compila
else if (linesToReplace.contains(i)) Some(createCall(linesToReplace(i)))
else Some(line)
}
NormalCompiledFunction(segmentName, tco(newCode), hasFixedAddress = false, alignment = value.alignment)
NormalCompiledFunction(segmentName, tco(newCode), hasFixedAddress = false, optimizationFlags = value.optimizationFlags, alignment = value.alignment)
}
}
@ -180,10 +180,11 @@ abstract class Deduplicate[T <: AbstractCode](env: Environment, options: Compila
result += function -> RedirectedFunction(segmentName, representative, 0)
} else {
segContents(function) match {
case Right(CodeAndAlignment(code, alignment)) =>
case Right(CodeAndAlignment(code, optimizationFlags, alignment)) =>
result += function -> NormalCompiledFunction(segmentName,
set.toList.map(name => createLabel(name)) ++ actualCode(function, code),
hasFixedAddress = false,
optimizationFlags = optimizationFlags,
alignment = alignment)
case Left(_) =>
}
@ -213,7 +214,7 @@ abstract class Deduplicate[T <: AbstractCode](env: Environment, options: Compila
def eliminateTailJumps(segmentName: String, segContents: Map[String, Either[String, CodeAndAlignment[T]]]): Seq[(String, CompiledFunction[T])] = {
var result = ListBuffer[(String, CompiledFunction[T])]()
val fallThroughList = segContents.flatMap {
case (name, Right(CodeAndAlignment(code, alignment))) =>
case (name, Right(CodeAndAlignment(code, optimizationFlags, alignment))) =>
if (code.isEmpty) None
else getJump(code.last)
.filter(segContents.contains)
@ -233,6 +234,7 @@ abstract class Deduplicate[T <: AbstractCode](env: Environment, options: Compila
result += from -> NormalCompiledFunction(segmentName,
init ++ segContents(to).right.get.code,
hasFixedAddress = false,
optimizationFlags = value.optimizationFlags,
alignment = value.alignment
)
val initSize = init.map(_.sizeInBytes).sum
@ -248,7 +250,7 @@ abstract class Deduplicate[T <: AbstractCode](env: Environment, options: Compila
def eliminateRemainingTrivialTailJumps(segmentName: String, segContents: Map[String, Either[String, CodeAndAlignment[T]]]): Seq[(String, CompiledFunction[T])] = {
var result = ListBuffer[(String, CompiledFunction[T])]()
val fallThroughList = segContents.flatMap {
case (name, Right(CodeAndAlignment(code, alignment))) =>
case (name, Right(CodeAndAlignment(code, optimizationFlags, alignment))) =>
if (code.length != 2) None
else getJump(code.last)
.filter(segContents.contains)
@ -268,11 +270,12 @@ abstract class Deduplicate[T <: AbstractCode](env: Environment, options: Compila
case Some(actualTo) =>
options.log.trace(s"which physically is $actualTo")
val value = result.find(_._1 == actualTo).fold(segContents(actualTo).right.get){
case (_, NormalCompiledFunction(_, code, _, alignment)) => CodeAndAlignment(code, alignment)
case (_, NormalCompiledFunction(_, code, _, optimizationFlags, alignment)) => CodeAndAlignment(code, optimizationFlags, alignment)
}
result += actualTo -> NormalCompiledFunction(segmentName,
createLabel(from) :: value.code,
hasFixedAddress = false,
optimizationFlags = value.optimizationFlags,
alignment = value.alignment
)
case _ =>
@ -326,7 +329,7 @@ abstract class Deduplicate[T <: AbstractCode](env: Environment, options: Compila
def bySegment(compiledFunctions: mutable.Map[String, CompiledFunction[T]]): Map[String, Map[String, Either[String, CodeAndAlignment[T]]]] = {
compiledFunctions.flatMap {
case (name, NormalCompiledFunction(segment, code, false, alignment)) => Some((segment, name, Right(CodeAndAlignment(code, alignment)))) // TODO
case (name, NormalCompiledFunction(segment, code, false, optimizationFlags, alignment)) => Some((segment, name, Right(CodeAndAlignment(code, optimizationFlags, alignment)))) // TODO
case (name, RedirectedFunction(segment, target, 0)) => Some((segment, name, Left(target))) // TODO
case _ => None
}.groupBy(_._1).mapValues(_.map { case (_, name, code) => name -> code }.toMap).view.force
@ -380,7 +383,7 @@ abstract class Deduplicate[T <: AbstractCode](env: Environment, options: Compila
}
}
case class CodeAndAlignment[T <: AbstractCode](code: List[T], alignment: MemoryAlignment)
case class CodeAndAlignment[T <: AbstractCode](code: List[T], optimizationFlags: Set[String], alignment: MemoryAlignment)
case class CodeChunk[T <: AbstractCode](functionName: String, offset: Int, endOffset: Int)(val code: List[T]) {

View File

@ -5,7 +5,7 @@ import millfork.assembly.m6809.opt.JumpFixing
import millfork.{CompilationOptions, Platform}
import millfork.assembly.m6809.{MOpcode, _}
import millfork.compiler.m6809.M6809Compiler
import millfork.env.{Environment, Label, MemoryAddressConstant, NormalFunction, NumericConstant}
import millfork.env.{Environment, FunctionInMemory, Label, MemoryAddressConstant, NormalFunction, NumericConstant}
import millfork.node.{M6809Register, NiceFunctionProperty, Position, Program}
import scala.collection.mutable
@ -26,6 +26,25 @@ class M6809Assembler(program: Program,
override def gatherNiceFunctionProperties(options: CompilationOptions, niceFunctionProperties: mutable.Set[(NiceFunctionProperty, String)], function: NormalFunction, code: List[MLine]): Unit = ()
override def gatherFunctionOptimizationHints(options: CompilationOptions, niceFunctionProperties: mutable.Set[(NiceFunctionProperty, String)], function: FunctionInMemory): Unit = {
import NiceFunctionProperty._
import millfork.node.M6809NiceFunctionProperty._
val functionName = function.name
if (function.optimizationHints("preserves_memory")) niceFunctionProperties += DoesntWriteMemory -> functionName
if (function.optimizationHints("idempotent")) niceFunctionProperties += Idempotent -> functionName
if (function.optimizationHints("preserves_a")) niceFunctionProperties += DoesntChangeA -> functionName
if (function.optimizationHints("preserves_b")) niceFunctionProperties += DoesntChangeB -> functionName
if (function.optimizationHints("preserves_d")) {
niceFunctionProperties += DoesntChangeA -> functionName
niceFunctionProperties += DoesntChangeB -> functionName
}
if (function.optimizationHints("preserves_x")) niceFunctionProperties += DoesntChangeX -> functionName
if (function.optimizationHints("preserves_y")) niceFunctionProperties += DoesntChangeY -> functionName
if (function.optimizationHints("preserves_u")) niceFunctionProperties += DoesntChangeU -> functionName
if (function.optimizationHints("preserves_dp")) niceFunctionProperties += DoesntChangeDP -> functionName
if (function.optimizationHints("preserves_c")) niceFunctionProperties += DoesntChangeCF -> functionName
}
override def performFinalOptimizationPass(f: NormalFunction, actuallyOptimize: Boolean, options: CompilationOptions, code: List[MLine]): List[MLine] = {
JumpFixing(f, code, options)
}

View File

@ -247,6 +247,22 @@ class MosAssembler(program: Program,
simpleRtsPropertyScan(_.y)(SetsYTo)
}
override def gatherFunctionOptimizationHints(options: CompilationOptions, niceFunctionProperties: mutable.Set[(NiceFunctionProperty, String)], function: FunctionInMemory): Unit = {
import MosNiceFunctionProperty._
import NiceFunctionProperty._
val functionName = function.name
println(functionName)
println(function.optimizationHints)
if (function.optimizationHints("even")) niceFunctionProperties += Bit0OfA(false) -> functionName
if (function.optimizationHints("odd")) niceFunctionProperties += Bit0OfA(true) -> functionName
if (function.optimizationHints("preserves_a")) niceFunctionProperties += DoesntChangeA -> functionName
if (function.optimizationHints("preserves_x")) niceFunctionProperties += DoesntChangeX -> functionName
if (function.optimizationHints("preserves_y")) niceFunctionProperties += DoesntChangeY -> functionName
if (function.optimizationHints("preserves_c")) niceFunctionProperties += DoesntChangeC -> functionName
if (function.optimizationHints("preserves_memory")) niceFunctionProperties += DoesntWriteMemory -> functionName
if (function.optimizationHints("idempotent")) niceFunctionProperties += Idempotent -> functionName
}
override def bytePseudoopcode: String = "!byte"
override def deduplicate(options: CompilationOptions, compiledFunctions: mutable.Map[String, CompiledFunction[AssemblyLine]]): Unit =

View File

@ -7,6 +7,7 @@ import millfork.assembly.z80.{ZOpcode, _}
import millfork.assembly.z80.opt.{CoarseFlowAnalyzer, ConditionalInstructions, CpuStatus, JumpFollowing, JumpShortening}
import millfork.compiler.z80.Z80Compiler
import millfork.env._
import millfork.node.NiceFunctionProperty.DoesntWriteMemory
import millfork.node.Z80NiceFunctionProperty.{DoesntChangeBC, DoesntChangeDE, DoesntChangeHL, DoesntChangeIY, SetsATo}
import millfork.node.{NiceFunctionProperty, Position, Program, ZRegister}
@ -785,6 +786,7 @@ class Z80Assembler(program: Program,
override def gatherNiceFunctionProperties(options: CompilationOptions, niceFunctionProperties: mutable.Set[(NiceFunctionProperty, String)], function: NormalFunction, code: List[ZLine]): Unit = {
import ZOpcode._
import NiceFunctionProperty._
val functionName = function.name
if (isNaughty(code)) return
val localLabels = code.flatMap {
@ -836,6 +838,13 @@ class Z80Assembler(program: Program,
simpleRetPropertyScan(_.a)(SetsATo)
}
override def gatherFunctionOptimizationHints(options: CompilationOptions, niceFunctionProperties: mutable.Set[(NiceFunctionProperty, String)], function: FunctionInMemory): Unit = {
import NiceFunctionProperty._
val functionName = function.name
if (function.optimizationHints("preserves_memory")) niceFunctionProperties += DoesntWriteMemory -> functionName
if (function.optimizationHints("idempotent")) niceFunctionProperties += Idempotent -> functionName
}
@tailrec
private def isNaughty(code: List[ZLine]): Boolean = {
import ZOpcode._

View File

@ -30,6 +30,13 @@ class Z80ToX86Crossassembler(program: Program,
// do nothing yet
}
override def gatherFunctionOptimizationHints(options: CompilationOptions, niceFunctionProperties: mutable.Set[(NiceFunctionProperty, String)], function: FunctionInMemory): Unit = {
import NiceFunctionProperty._
val functionName = function.name
if (function.optimizationHints("preserves_memory")) niceFunctionProperties += DoesntWriteMemory -> functionName
if (function.optimizationHints("idempotent")) niceFunctionProperties += Idempotent -> functionName
}
override def bytePseudoopcode: String = "DB"
override def deduplicate(options: CompilationOptions, compiledFunctions: mutable.Map[String, CompiledFunction[ZLine]]): Unit =

View File

@ -113,7 +113,7 @@ abstract class MfParser[T](fileId: String, input: String, currentDirectory: Stri
val variableFlags: P[Set[String]] = flags_("const", "static", "volatile", "stack", "register")
val functionFlags: P[Set[String]] = flags_("asm", "inline", "interrupt", "macro", "noinline", "reentrant", "kernal_interrupt", "const")
val functionFlags: P[Set[String]] = flags_("extern", "asm", "inline", "interrupt", "macro", "noinline", "reentrant", "kernal_interrupt", "const")
val codec: P[TextCodecWithFlags] = P(position("text codec identifier") ~ identifier.?.map(_.getOrElse(""))).map { case (position, encoding) =>
val lenient = options.flag(CompilationFlag.LenientTextEncoding)
@ -197,16 +197,30 @@ abstract class MfParser[T](fileId: String, input: String, currentDirectory: Stri
identifier.rep(min = 1, sep = "/") ~ HWS ~ ("<" ~/ HWS ~/ quotedAtom.rep(min = 1, sep = HWS ~ "," ~/ HWS) ~/ HWS ~/ ">" ~/ Pass).?).
map{case (name, params) => Seq(ImportStatement(name.mkString("/"), params.getOrElse(Nil).toList))}
val optimizationHintsDeclaration: P[Set[String]] =
if (options.flag(CompilationFlag.EnableInternalTestSyntax)) {
("¥" ~/ HWS ~ "(" ~/ HWS ~/ identifier.rep(min = 0, sep = AWS ~ "," ~/ AWS) ~ HWS ~ ")" ~/ "").?.map {
case None => Set()
case Some(list) => list.toSet
}
} else P("").map(_ => Set.empty)
val globalVariableDefinition: P[Seq[BankedDeclarationStatement]] = variableDefinition(true)
val localVariableDefinition: P[Seq[DeclarationStatement]] = variableDefinition(false)
def singleVariableDefinition: P[(Position, String, Option[Expression], Option[Expression], Option[MemoryAlignment])] = for {
def singleVariableDefinition: P[(Position, String, Option[Expression], Option[Expression], Set[String], Option[MemoryAlignment])] = for {
p <- position()
name <- identifier ~/ HWS ~/ Pass
alignment1 <- alignmentDeclaration(fastAlignmentForFunctions).? ~/ HWS
optimizationHints <- optimizationHintsDeclaration ~/ HWS
alignment2 <- alignmentDeclaration(fastAlignmentForFunctions).? ~/ HWS
addr <- ("@" ~/ HWS ~/ mfExpression(1, false)).?.opaque("<address>") ~ HWS
initialValue <- ("=" ~/ HWS ~/ mfExpression(1, false)).? ~/ HWS
alignment = None // TODO
} yield (p, name, addr, initialValue, alignment)
initialValue <- ("=" ~/ HWS ~/ mfExpression(1, false)).? ~/ HWS // TODO
} yield {
if (alignment1.isDefined && alignment2.isDefined) log.error(s"Cannot define the alignment multiple times", Some(p))
val alignment = alignment1.orElse(alignment2)
(p, name, addr, initialValue, optimizationHints, alignment)
}
def variableDefinition(implicitlyGlobal: Boolean): P[Seq[BankedDeclarationStatement]] = for {
p <- position()
@ -217,14 +231,14 @@ abstract class MfParser[T](fileId: String, input: String, currentDirectory: Stri
vars <- singleVariableDefinition.rep(min = 1, sep = "," ~/ HWS)
_ <- Before_EOL ~/ ""
} yield {
vars.map { case (p, name, addr, initialValue, alignment) => VariableDeclarationStatement(name, typ,
vars.map { case (p, name, addr, initialValue, optimizationHints, alignment) => VariableDeclarationStatement(name, typ,
bank,
global = implicitlyGlobal || flags("static"),
stack = flags("stack"),
constant = flags("const"),
volatile = flags("volatile"),
register = flags("register"),
initialValue, addr, alignment).pos(p)
initialValue, addr, optimizationHints, alignment).pos(p)
}
}
@ -409,10 +423,16 @@ abstract class MfParser[T](fileId: String, input: String, currentDirectory: Stri
elementType <- ("(" ~/ AWS ~/ identifier ~ AWS ~ ")").? ~/ HWS
name <- identifier ~/ HWS
length <- ("[" ~/ AWS ~/ mfExpression(nonStatementLevel, false) ~ AWS ~ "]").? ~ HWS
alignment <- alignmentDeclaration(fastAlignmentForFunctions).? ~/ HWS
alignment1 <- alignmentDeclaration(fastAlignmentForFunctions).? ~/ HWS
optimizationHints <- optimizationHintsDeclaration ~/ HWS
alignment2 <- alignmentDeclaration(fastAlignmentForFunctions).? ~/ HWS
addr <- ("@" ~/ HWS ~/ mfExpression(1, false)).? ~/ HWS
contents <- ("=" ~/ HWS ~/ arrayContents).? ~/ HWS
} yield Seq(ArrayDeclarationStatement(name, bank, length, elementType.getOrElse("byte"), addr, const.isDefined, contents, alignment, options.isBigEndian).pos(p))
} yield {
if (alignment1.isDefined && alignment2.isDefined) log.error(s"Cannot define the alignment multiple times", Some(p))
val alignment = alignment1.orElse(alignment2)
Seq(ArrayDeclarationStatement(name, bank, length, elementType.getOrElse("byte"), addr, const.isDefined, contents, optimizationHints, alignment, options.isBigEndian).pos(p))
}
def tightMfExpression(allowIntelHex: Boolean, allowTopLevelIndexing: Boolean): P[Expression] = {
val a = if (allowIntelHex) atomWithIntel else atom
@ -668,10 +688,15 @@ abstract class MfParser[T](fileId: String, input: String, currentDirectory: Stri
if !Environment.neverValidTypeIdentifiers(returnType)
name <- identifier ~ HWS
params <- "(" ~/ AWS ~/ (if (flags("asm")) asmParamDefinition else if (flags("macro")) macroParamDefinition else paramDefinition).rep(sep = AWS ~ "," ~/ AWS) ~ AWS ~ ")" ~/ AWS
alignment <- alignmentDeclaration(fastAlignmentForFunctions).? ~/ AWS
alignment1 <- alignmentDeclaration(fastAlignmentForFunctions).? ~/ AWS
optimizationHints <- optimizationHintsDeclaration ~/ HWS
alignment2 <- alignmentDeclaration(fastAlignmentForFunctions).? ~/ AWS
addr <- ("@" ~/ HWS ~/ mfExpression(1, false)).?.opaque("<address>") ~/ AWS
statements <- (externFunctionBody | (if (flags("asm")) asmStatements else mfFunctionBody).map(l => Some(l))) ~/ Pass
} yield {
if (alignment1.isDefined && alignment2.isDefined) log.error(s"Cannot define the alignment multiple times", Some(p))
val alignment = alignment1.orElse(alignment2)
if (flags("extern")) log.error("The extern keyword should go at the end of a function declaration", Some(p))
if (flags("interrupt") && flags("macro")) log.error(s"Interrupt function `$name` cannot be macros", Some(p))
if (flags("kernal_interrupt") && flags("macro")) log.error(s"Kernal interrupt function `$name` cannot be macros", Some(p))
if (flags("interrupt") && flags("reentrant")) log.error(s"Interrupt function `$name` cannot be reentrant", Some(p))
@ -694,6 +719,7 @@ abstract class MfParser[T](fileId: String, input: String, currentDirectory: Stri
Seq(FunctionDeclarationStatement(name, returnType, params.toList,
bank,
addr,
optimizationHints,
alignment,
statements,
flags("macro"),

View File

@ -0,0 +1,29 @@
package millfork.test
import millfork.Cpu
import millfork.test.emu.{EmuBenchmarkRun, EmuOptimizedAccordingToLevelRun, EmuUnoptimizedCrossPlatformRun, EmuUnoptimizedRun, ShouldNotCompile, ShouldNotParse}
import org.scalatest.{FunSuite, Matchers}
/**
* @author Karol Stasiak
*/
class OptimizationHintsSuite extends FunSuite with Matchers {
test("Optimization hints test 1") {
EmuBenchmarkRun("""
| asm void putchar(byte register(a) character) ¥( preserves_a, preserves_x, preserves_y ) @$ffd2 extern
| noinline bool should_print(byte a) = a == 5
| void main() {
| byte i
| if should_print(3) {
| for i,0,parallelto,255 {
| putchar(i)
| putchar(i)
| }
| }
| }
|""".stripMargin) { m =>
}
}
}

View File

@ -85,6 +85,7 @@ class EmuM6809Run(cpu: millfork.Cpu.Value, nodeOptimizations: List[NodeOptimizat
println(source)
val platform = EmuPlatform.get(cpu)
val options = CompilationOptions(platform, Map(
CompilationFlag.UseOptimizationHints -> true,
CompilationFlag.EnableInternalTestSyntax -> true,
CompilationFlag.DecimalMode -> true,
CompilationFlag.LenientTextEncoding -> true,

View File

@ -148,6 +148,7 @@ class EmuRun(cpu: millfork.Cpu.Value, nodeOptimizations: List[NodeOptimization],
CompilationFlag.OptimizeStdlib -> this.inline,
CompilationFlag.InterproceduralOptimization -> true,
CompilationFlag.CompactReturnDispatchParams -> true,
CompilationFlag.UseOptimizationHints -> true,
CompilationFlag.SoftwareStack -> softwareStack,
CompilationFlag.EmitCmosOpcodes -> millfork.Cpu.CmosCompatible.contains(platform.cpu),
CompilationFlag.EmitSC02Opcodes -> millfork.Cpu.CmosCompatible.contains(platform.cpu),

View File

@ -78,6 +78,7 @@ class EmuZ80Run(cpu: millfork.Cpu.Value, nodeOptimizations: List[NodeOptimizatio
println(source)
val platform = EmuPlatform.get(cpu)
var extraFlags = Map(
CompilationFlag.UseOptimizationHints -> true,
CompilationFlag.DangerousOptimizations -> true,
CompilationFlag.EnableInternalTestSyntax -> true,
CompilationFlag.InlineFunctions -> this.inline,