1
0
mirror of https://github.com/KarolS/millfork.git synced 2025-04-01 02:31:38 +00:00

Z80: Intel syntax for output.

This commit is contained in:
Karol Stasiak 2018-08-01 21:16:20 +02:00
parent d4beba11a1
commit e952d89849
19 changed files with 362 additions and 55 deletions

View File

@ -26,6 +26,10 @@ no extension for BBC micro program file,
* `-s` Generate also the assembly output. It is not compatible with any assembler, but it serves purely informational purpose. The file has the same nam as the output file and the extension is `.asm`.
* `-foutput_intel_syntax`, `-foutput_zilog_syntax`
Choose syntax for assembly output on 8080-like targets.
`.ini` equivalent: `output_intel_syntax`. Default: Intel (true) on Intel 8080, Zilog (false) otherwise.
* `-g` Generate also the label file. The label file contains labels with their addresses, with duplicates removed. It can be loaded into the monitor of the Vice emulator for debugging purposes. The file has the same name as the output file and the extension is `.lbl`.
* `-I <dir>;<dir>` The include directories. The current working directory is also an include directory. Those directories are searched for modules and platform definitions.

View File

@ -77,6 +77,8 @@ Default: the same as `encoding`.
* `ix_scratch` allow using the IY register for other purposes, default is `false`
* `iy_scratch` allow using the IY register for other purposes, default is `false`
* `output_intel_syntax` use Intel syntax instead of Zilog syntax, default is `true` for Intel 8080 and `false` otherwise
#### `[define]` section

View File

@ -48,6 +48,7 @@ You may be also interested in the following:
* `-fipo` enable interprocedural optimization
* `-s` additionally generate assembly output
(if targeting Intel 8080, use `-foutput_intel_syntax` or `-foutput_zilog_syntax` to choose the preferred output syntax)
* `-g` additionally generate a label file, in format compatible with VICE emulator

View File

@ -10,7 +10,11 @@ There are two ways to include raw assembly code in your Millfork programs:
## Assembly syntax
Millfork uses Zilog syntax for Intel 8080, Z80 and LR35902 assembly. Intel syntax is not supported.
Millfork uses Zilog syntax for Intel 8080, Z80 and LR35902 assembly.
**Work in progress**:
Intel syntax is not supported yet.
LR35902 instructions for faster access to the $FFxx addresses are not available yet.
Indexing via the IX/IY register uses the following syntax: `IX(1)`
@ -20,8 +24,6 @@ LR35902 instructions that load/store the accumulator indirectly via HL and then
Only instructions available on the current CPU architecture are available.
Undocumented instructions are not supported, except for `SLL`.
LR35902 instructions for faster access to the $FFxx addresses are not available yet.
Labels have to be followed by a colon and they can optionally be on a separate line.
Indentation is not important:

View File

@ -37,7 +37,7 @@ case class CompilationOptions(platform: Platform,
if (CpuFamily.forType(platform.cpu) != CpuFamily.I80) invalids ++= Set(
EmitExtended80Opcodes, EmitZ80Opcodes, EmitSharpOpcodes, EmitIntel8080Opcodes, EmitEZ80Opcodes,
UseIxForStack, UseIyForStack, UseShadowRegistersForInterrupts)
UseIxForStack, UseIyForStack, UseShadowRegistersForInterrupts, UseIntelSyntaxForInput, UseIntelSyntaxForOutput)
invalids = invalids.filter(flags)
@ -210,7 +210,7 @@ object Cpu extends Enumeration {
case Sixteen =>
mosAlwaysDefaultFlags ++ Set(DecimalMode, EmitCmosOpcodes, EmitEmulation65816Opcodes, EmitNative65816Opcodes, ReturnWordsViaAccumulator)
case Intel8080 =>
i80AlwaysDefaultFlags ++ Set(EmitIntel8080Opcodes)
i80AlwaysDefaultFlags ++ Set(EmitIntel8080Opcodes, UseIntelSyntaxForOutput)
case Z80 =>
i80AlwaysDefaultFlags ++ Set(EmitIntel8080Opcodes, EmitExtended80Opcodes, EmitZ80Opcodes, UseIxForStack, UseShadowRegistersForInterrupts)
case EZ80 =>
@ -279,6 +279,8 @@ object CompilationFlag extends Enumeration {
UseShadowRegistersForInterrupts,
UseIxForStack, UseIyForStack,
UseIxForScratch, UseIyForScratch,
UseIntelSyntaxForInput,
UseIntelSyntaxForOutput,
// optimization options:
DangerousOptimizations, InlineFunctions, InterproceduralOptimization, OptimizeForSize, OptimizeForSpeed, OptimizeForSonicSpeed,
// memory allocation options
@ -313,6 +315,7 @@ object CompilationFlag extends Enumeration {
"ix_scratch" -> UseIxForScratch,
"iy_scratch" -> UseIyForScratch,
"use_shadow_registers_for_irq" -> UseShadowRegistersForInterrupts,
"output_intel_syntax" -> UseIntelSyntaxForOutput,
"ipo" -> InterproceduralOptimization,
"inline" -> InlineFunctions,
"dangerous_optimizations" -> DangerousOptimizations,

View File

@ -451,6 +451,9 @@ object Main {
flag("--single-threaded").action(c =>
c.changeFlag(CompilationFlag.SingleThreaded, true)
).description("Run the compiler in a single thread.")
boolean("-foutput_intel_syntax", "-foutput_zilog_syntax").action((c,v) =>
c.changeFlag(CompilationFlag.UseIntelSyntaxForOutput, v)
).description("Select syntax for assembly output.")
flag("--help").action(c => {
println("millfork version " + BuildInfo.version)

View File

@ -238,6 +238,27 @@ case class ZLine(opcode: ZOpcode.Value, registers: ZRegisters, parameter: Consta
case ZRegister.MEM_DE => "(DE)"
}
private def asIntelAssemblyString(r: ZRegister.Value): String = r match {
case ZRegister.A => "A"
case ZRegister.B => "B"
case ZRegister.C => "C"
case ZRegister.D => "D"
case ZRegister.E => "E"
case ZRegister.H => "H"
case ZRegister.L => "L"
case ZRegister.AF => "PSW"
case ZRegister.BC => "B"
case ZRegister.DE => "D"
case ZRegister.HL => "H"
case ZRegister.SP => "SP"
case ZRegister.MEM_ABS_8 => s"$parameter"
case ZRegister.MEM_ABS_16 => s"$parameter"
case ZRegister.IMM_8 => s"$parameter"
case ZRegister.IMM_16 => s"$parameter"
case ZRegister.MEM_HL => "M"
case _ => "???"
}
override def toString: String = {
import ZOpcode._
opcode match {
@ -248,7 +269,7 @@ case class ZLine(opcode: ZOpcode.Value, registers: ZRegisters, parameter: Consta
case DISCARD_DE => " ; DISCARD_DE"
case DISCARD_IX => " ; DISCARD_IX"
case DISCARD_IY => " ; DISCARD_IY"
case BYTE => " !byte " + parameter.toString // TODO: format?
case BYTE => " DB " + parameter.toString // TODO: format?
case LABEL => parameter.toString + ":"
case RST => s" RST $parameter"
case IM => s" IM $parameter"
@ -320,6 +341,173 @@ case class ZLine(opcode: ZOpcode.Value, registers: ZRegisters, parameter: Consta
}
}
def toIntelString: String = {
import ZOpcode._
import ZRegister._
val result = opcode match {
case LABEL => parameter.toString + ":"
case DISCARD_A => " ; DISCARD_A"
case DISCARD_HL => " ; DISCARD_HL"
case DISCARD_F => " ; DISCARD_F"
case DISCARD_BC => " ; DISCARD_BC"
case DISCARD_DE => " ; DISCARD_DE"
case DISCARD_IX => " ; DISCARD_IX"
case DISCARD_IY => " ; DISCARD_IY"
case BYTE => " DB " + parameter.toString
case LD => registers match {
case TwoRegisters(target, IMM_8) => s" MVI ${asIntelAssemblyString(target)}, ${parameter.toIntelString}"
case TwoRegisters(A, MEM_ABS_8) => s" LDA ${parameter.toIntelString}"
case TwoRegisters(MEM_ABS_8, A) => s" STA ${parameter.toIntelString}"
case TwoRegisters(A, MEM_BC) => " LDAX B"
case TwoRegisters(MEM_BC, A) => " STAX B"
case TwoRegisters(A, MEM_DE) => " LDAX D"
case TwoRegisters(MEM_DE, A) => " STAX D"
case TwoRegisters(target, source) => s" MOV ${asIntelAssemblyString(target)}, ${asIntelAssemblyString(source)}"
case _ => "???"
}
case LD_16 => registers match {
case TwoRegisters(SP, HL) => " SPHL"
case TwoRegisters(target, IMM_16) => s" LXI ${asIntelAssemblyString(target)}, ${parameter.toIntelString}"
case TwoRegisters(HL, MEM_ABS_16) => s" LHLD ${parameter.toIntelString}"
case TwoRegisters(MEM_ABS_16, HL) => s" SHLD ${parameter.toIntelString}"
case _ => "???"
}
case ADD_16 => registers match {
case TwoRegisters(HL, source) => s" DAD ${asIntelAssemblyString(source)}"
case _ => "???"
}
case DEC_16 => registers match {
case OneRegister(register) => s" DCX ${asIntelAssemblyString(register)}"
case _ => "???"
}
case INC_16 => registers match {
case OneRegister(register) => s" INX ${asIntelAssemblyString(register)}"
case _ => "???"
}
case DEC => registers match {
case OneRegister(register) => s" DCR ${asIntelAssemblyString(register)}"
case _ => "???"
}
case INC => registers match {
case OneRegister(register) => s" INR ${asIntelAssemblyString(register)}"
case _ => "???"
}
case PUSH => registers match {
case OneRegister(register) => s" PUSH ${asIntelAssemblyString(register)}"
case _ => "???"
}
case POP => registers match {
case OneRegister(register) => s" POP ${asIntelAssemblyString(register)}"
case _ => "???"
}
case DAA => " DAA"
case RLA => " RAL"
case RLCA => " RLC"
case RRA => " RAR"
case RRCA => " RRC"
case HALT => " HLT"
case RET => registers match {
case NoRegisters => " RET"
case IfFlagClear(ZFlag.C) => " RNC"
case IfFlagClear(ZFlag.Z) => " RNZ"
case IfFlagClear(ZFlag.S) => " RP"
case IfFlagClear(ZFlag.P) => " RPO"
case IfFlagSet(ZFlag.C) => " RC"
case IfFlagSet(ZFlag.Z) => " RZ"
case IfFlagSet(ZFlag.S) => " RM"
case IfFlagSet(ZFlag.P) => " RPE"
case _ => "???"
}
case JP => registers match {
case OneRegister(HL) => " PCHL"
case NoRegisters => s" JMP ${parameter.toIntelString}"
case IfFlagClear(ZFlag.C) => s" JNC ${parameter.toIntelString}"
case IfFlagClear(ZFlag.Z) => s" JNZ ${parameter.toIntelString}"
case IfFlagClear(ZFlag.S) => s" JP ${parameter.toIntelString}"
case IfFlagClear(ZFlag.P) => s" JPO ${parameter.toIntelString}"
case IfFlagSet(ZFlag.C) => s" JC ${parameter.toIntelString}"
case IfFlagSet(ZFlag.Z) => s" JZ ${parameter.toIntelString}"
case IfFlagSet(ZFlag.S) => s" JM ${parameter.toIntelString}"
case IfFlagSet(ZFlag.P) => s" JPE ${parameter.toIntelString}"
case _ => "???"
}
case CALL => registers match {
case NoRegisters => s" CALL ${parameter.toIntelString}"
case IfFlagClear(ZFlag.C) => s" CNC ${parameter.toIntelString}"
case IfFlagClear(ZFlag.Z) => s" CNZ ${parameter.toIntelString}"
case IfFlagClear(ZFlag.S) => s" CP ${parameter.toIntelString}"
case IfFlagClear(ZFlag.P) => s" CPO ${parameter.toIntelString}"
case IfFlagSet(ZFlag.C) => s" CC ${parameter.toIntelString}"
case IfFlagSet(ZFlag.Z) => s" CZ ${parameter.toIntelString}"
case IfFlagSet(ZFlag.S) => s" CM ${parameter.toIntelString}"
case IfFlagSet(ZFlag.P) => s" CPE ${parameter.toIntelString}"
case _ => "???"
}
case ADD => registers match {
case OneRegister(IMM_8) => s" ADI ${parameter.toIntelString}"
case OneRegister(register) => s" ADD ${asIntelAssemblyString(register)}"
case _ => "???"
}
case ADC => registers match {
case OneRegister(IMM_8) => s" ACI ${parameter.toIntelString}"
case OneRegister(register) => s" ADC ${asIntelAssemblyString(register)}"
case _ => "???"
}
case SUB => registers match {
case OneRegister(IMM_8) => s" SUI ${parameter.toIntelString}"
case OneRegister(register) => s" SUB ${asIntelAssemblyString(register)}"
case _ => "???"
}
case SBC => registers match {
case OneRegister(IMM_8) => s" SBI ${parameter.toIntelString}"
case OneRegister(register) => s" SBB ${asIntelAssemblyString(register)}"
case _ => "???"
}
case AND => registers match {
case OneRegister(IMM_8) => s" ANI ${parameter.toIntelString}"
case OneRegister(register) => s" ANA ${asIntelAssemblyString(register)}"
case _ => "???"
}
case OR => registers match {
case OneRegister(IMM_8) => s" ORI ${parameter.toIntelString}"
case OneRegister(register) => s" ORA ${asIntelAssemblyString(register)}"
case _ => "???"
}
case XOR => registers match {
case OneRegister(IMM_8) => s" XRI ${parameter.toIntelString}"
case OneRegister(register) => s" XRA ${asIntelAssemblyString(register)}"
case _ => "???"
}
case CP => registers match {
case OneRegister(IMM_8) => s" CPI ${parameter.toIntelString}"
case OneRegister(register) => s" CMP ${asIntelAssemblyString(register)}"
case _ => "???"
}
case EX_SP => registers match {
case OneRegister(HL) => s" XTHL"
case _ => "???"
}
case RST => parameter match {
case NumericConstant(n, _) if n % 8 == 0 => s" RST ${n / 8}"
case _ => "???"
}
case IN_IMM => s" IN ${parameter.toIntelString}"
case OUT_IMM => s" OUT ${parameter.toIntelString}"
case EI => " EI"
case DI => " EI"
case EX_DE_HL => " XCHG"
case NOP => " NOP"
case CPL => " CMA"
case SCF => " STC"
case CCF => " CMC"
case EI => " EI"
case EI => " EI"
case EI => " EI"
case _ => "???"
}
if (result.contains("???")) s" ??? (${this.toString.stripPrefix(" ")})" else result
}
def readsRegister(r: ZRegister.Value): Boolean = {
import ZOpcode._
import ZRegister._

View File

@ -17,6 +17,9 @@ import millfork.error.ConsoleLogger
import millfork.node.Position
sealed trait Constant {
def toIntelString: String
def isProvablyZero: Boolean = false
def isProvably(value: Int): Boolean = false
def isProvablyNonnegative: Boolean = false
@ -101,12 +104,15 @@ case class AssertByte(c: Constant) extends Constant {
override def quickSimplify: Constant = AssertByte(c.quickSimplify)
override def fitsInto(typ: Type): Boolean = true
override def toIntelString: String = c.toIntelString
}
case class UnexpandedConstant(name: String, requiredSize: Int) extends Constant {
override def isRelatedTo(v: Thing): Boolean = false
override def toString: String = name
override def toIntelString: String = name
}
case class NumericConstant(value: Long, requiredSize: Int) extends Constant {
@ -135,6 +141,11 @@ case class NumericConstant(value: Long, requiredSize: Int) extends Constant {
override def toString: String = if (value > 9) value.formatted("$%X") else value.toString
override def toIntelString: String = if (value > 9) {
val tmp = value.formatted("%Xh")
if (tmp(0) > '9') "0" + tmp else tmp
} else value.toString
override def isRelatedTo(v: Thing): Boolean = false
override def fitsInto(typ: Type): Boolean = {
@ -166,6 +177,8 @@ case class MemoryAddressConstant(var thing: ThingInMemory) extends Constant {
override def toString: String = thing.name
override def toIntelString: String = thing.name
override def isRelatedTo(v: Thing): Boolean = thing.name == v.name
}
@ -186,12 +199,17 @@ case class SubbyteConstant(base: Constant, index: Int) extends Constant {
override def isProvablyNonnegative: Boolean = true
override def toString: String = base + (index match {
case 0 => ".lo"
case 1 => ".hi"
case 2 => ".b2"
case 3 => ".b3"
})
override def toString: String = index match {
case 0 => s"lo($base)"
case 1 => s"hi($base)"
case i => s"b$i($base)"
}
override def toIntelString: String = index match {
case 0 => s"lo(${base.toIntelString})"
case 1 => s"hi($base.toIntelString)"
case i => s"b$i($base.toIntelString)"
}
override def isRelatedTo(v: Thing): Boolean = base.isRelatedTo(v)
}
@ -373,36 +391,70 @@ case class CompoundConstant(operator: MathOperator.Value, lhs: Constant, rhs: Co
}
}
private def plhs = lhs match {
case _: NumericConstant | _: MemoryAddressConstant => lhs
private def plhs: String = lhs match {
case _: NumericConstant | _: MemoryAddressConstant => lhs.toString
case _ => "(" + lhs + ')'
}
private def prhs = lhs match {
case _: NumericConstant | _: MemoryAddressConstant => rhs
private def prhs: String = lhs match {
case _: NumericConstant | _: MemoryAddressConstant => rhs.toString
case _ => "(" + rhs + ')'
}
private def plhis: String = lhs match {
case _: NumericConstant | _: MemoryAddressConstant => lhs.toIntelString
case _ => "(" + lhs.toIntelString + ')'
}
private def prhis: String = lhs match {
case _: NumericConstant | _: MemoryAddressConstant => rhs.toIntelString
case _ => "(" + rhs.toIntelString + ')'
}
override def toString: String = {
operator match {
case Plus => f"$plhs + $prhs"
case Plus9 => f"nonet($plhs + $prhs)"
case Minus => f"$plhs - $prhs"
case Times => f"$plhs * $prhs"
case Shl => f"$plhs << $prhs"
case Shr => f"$plhs >> $prhs"
case Shl9 => f"nonet($plhs << $prhs)"
case Shr9 => f"$plhs >>>> $prhs"
case DecimalPlus => f"$plhs +' $prhs"
case DecimalPlus9 => f"nonet($plhs +' $prhs)"
case DecimalMinus => f"$plhs -' $prhs"
case DecimalTimes => f"$plhs *' $prhs"
case DecimalShl => f"$plhs <<' $prhs"
case DecimalShl9 => f"nonet($plhs <<' $prhs)"
case DecimalShr => f"$plhs >>' $prhs"
case And => f"$plhs & $prhs"
case Or => f"$plhs | $prhs"
case Exor => f"$plhs ^ $prhs"
case Plus => s"$plhs + $prhs"
case Plus9 => s"nonet($plhs + $prhs)"
case Minus => s"$plhs - $prhs"
case Times => s"$plhs * $prhs"
case Shl => s"$plhs << $prhs"
case Shr => s"$plhs >> $prhs"
case Shl9 => s"nonet($plhs << $prhs)"
case Shr9 => s"$plhs >>>> $prhs"
case DecimalPlus => s"$plhs +' $prhs"
case DecimalPlus9 => s"nonet($plhs +' $prhs)"
case DecimalMinus => s"$plhs -' $prhs"
case DecimalTimes => s"$plhs *' $prhs"
case DecimalShl => s"$plhs <<' $prhs"
case DecimalShl9 => s"nonet($plhs <<' $prhs)"
case DecimalShr => s"$plhs >>' $prhs"
case And => s"$plhs & $prhs"
case Or => s"$plhs | $prhs"
case Exor => s"$plhs ^ $prhs"
}
}
override def toIntelString: String = {
operator match {
case Plus => s"$plhis + $prhis"
case Plus9 => s"nonet($plhis + $prhis)"
case Minus => s"$plhis - $prhis"
case Times => s"$plhis * $prhis"
case Shl => s"$plhis << $prhis"
case Shr => s"$plhis >> $prhis"
case Shl9 => s"nonet($plhis << $prhis)"
case Shr9 => s"$plhis >>>> $prhis"
case DecimalPlus => s"$plhis +' $prhis"
case DecimalPlus9 => s"nonet($plhis +' $prhis)"
case DecimalMinus => s"$plhis -' $prhis"
case DecimalTimes => s"$plhis *' $prhis"
case DecimalShl => s"$plhis <<' $prhis"
case DecimalShl9 => s"nonet($plhis <<' $prhis)"
case DecimalShr => s"$plhis >>' $prhis"
case And => s"$plhis & $prhis"
case Or => s"$plhis | $prhis"
case Exor => s"$plhis ^ $prhis"
}
}

View File

@ -6,8 +6,10 @@ import millfork.env._
import millfork.error.{ConsoleLogger, Logger}
import millfork.node.{CallGraph, NiceFunctionProperty, Program}
import millfork._
import millfork.assembly.z80.ZLine
import scala.collection.mutable
import scala.math.Integral.Implicits.infixIntegralOps
/**
* @author Karol Stasiak
@ -177,6 +179,8 @@ abstract class AbstractAssembler[T <: AbstractCode](private val program: Program
private def asDecimal(a: Long, b: Long, f: (Long, Long) => Long): Long =
storeDecimalValueInNormalRespresentation(f(parseNormalToDecimalValue(a), parseNormalToDecimalValue(b)))
def bytePseudoopcode: String
def assemble(callGraph: CallGraph, optimizations: Seq[AssemblyOptimization[T]], options: CompilationOptions): AssemblerOutput = {
mem.programName = options.outputFileName.getOrElse("MILLFORK")
val platform = options.platform
@ -266,7 +270,7 @@ abstract class AbstractAssembler[T <: AbstractCode](private val program: Program
index += 1
}
items.grouped(16).foreach { group =>
assembly.append(" !byte " + group.map(expr => env.eval(expr) match {
assembly.append(" " + bytePseudoopcode + " " + group.map(expr => env.eval(expr) match {
case Some(c) => c.quickSimplify.toString
case None => "<? unknown constant ?>"
}).mkString(", "))
@ -490,7 +494,16 @@ abstract class AbstractAssembler[T <: AbstractCode](private val program: Program
assOut.append("* = $" + startFrom.toHexString)
for (instr <- code) {
if (instr.isPrintable) {
assOut.append(instr.toString)
if (options.flag(CompilationFlag.UseIntelSyntaxForOutput)) {
instr match {
case zline: ZLine =>
assOut.append(zline.toIntelString)
case _ =>
assOut.append(instr.toString)
}
} else {
assOut.append(instr.toString)
}
}
index = emitInstruction(bank, options, index, instr)
}

View File

@ -164,6 +164,8 @@ class MosAssembler(program: Program,
case _ => true
}
}
override def bytePseudoopcode: String = "!byte"
}

View File

@ -615,6 +615,8 @@ class Z80Assembler(program: Program,
override def gatherNiceFunctionProperties(niceFunctionProperties: mutable.Set[(NiceFunctionProperty, String)], functionName: String, code: List[ZLine]): Unit = {
// do nothing yet
}
override def bytePseudoopcode: String = "DB"
}
object Z80Assembler {

View File

@ -51,16 +51,23 @@ abstract class AbstractSourceLoadingQueue[T](val initialFilenames: List[String],
options.log.fatal(s"Module `$moduleName` not found", position)
}
def createParser(filename: String, src: String, parentDir: String, featureConstants: Map[String, Long]) : MfParser[T]
def supportedPragmas: Set[String]
def createParser(filename: String, src: String, parentDir: String, featureConstants: Map[String, Long], pragmas: Set[String]) : MfParser[T]
def parseModule(moduleName: String, includePath: List[String], why: Either[Option[Position], String]): Unit = {
val filename: String = why.fold(p => lookupModuleFile(includePath, moduleName, p), s => s)
options.log.debug(s"Parsing $filename")
val path = Paths.get(filename)
val parentDir = path.toFile.getAbsoluteFile.getParent
val (src, featureConstants) = Preprocessor(options, Files.readAllLines(path, StandardCharsets.UTF_8).toIndexedSeq)
val PreprocessingResult(src, featureConstants, pragmas) = Preprocessor(options, Files.readAllLines(path, StandardCharsets.UTF_8).toIndexedSeq)
for (pragma <- pragmas) {
if (!supportedPragmas(pragma._1)) {
options.log.warn(s"Unsupported pragma: #pragma $pragma", Some(Position(moduleName, pragma._2, 1, 0)))
}
}
val shortFileName = path.getFileName.toString
val parser = createParser(shortFileName, src, parentDir, featureConstants)
val parser = createParser(shortFileName, src, parentDir, featureConstants, pragmas.keySet)
options.log.addSource(shortFileName, src.lines.toIndexedSeq)
parser.toAst match {
case Success(prog, _) =>

View File

@ -10,7 +10,7 @@ class MosSourceLoadingQueue(initialFilenames: List[String],
includePath: List[String],
options: CompilationOptions) extends AbstractSourceLoadingQueue[AssemblyLine](initialFilenames, includePath, options) {
override def createParser(filename: String, src: String, parentDir: String, featureConstants: Map[String, Long]): MfParser[AssemblyLine] =
override def createParser(filename: String, src: String, parentDir: String, featureConstants: Map[String, Long], pragmas: Set[String]): MfParser[AssemblyLine] =
MosParser(filename, src, parentDir, options, featureConstants)
def enqueueStandardModules(): Unit = {
@ -19,4 +19,5 @@ class MosSourceLoadingQueue(initialFilenames: List[String],
}
}
override val supportedPragmas: Set[String] = Set()
}

View File

@ -10,17 +10,20 @@ import scala.collection.mutable
/**
* @author Karol Stasiak
*/
case class PreprocessingResult(source: String, featureConstants: Map[String, Long], pragmas: Map[String, Int])
object Preprocessor {
private val Regex = raw"\A\s*#\s*([a-z]+)\s*(.*?)\s*\z".r
def preprocessForTest(options: CompilationOptions, code: String): (String, Map[String, Long]) = {
def preprocessForTest(options: CompilationOptions, code: String): PreprocessingResult = {
apply(options, code.lines.toSeq)
}
case class IfContext(hadEnabled: Boolean, hadElse: Boolean, enabledBefore: Boolean)
def apply(options: CompilationOptions, lines: Seq[String]): (String, Map[String, Long]) = {
def apply(options: CompilationOptions, lines: Seq[String]): PreprocessingResult = {
val platform = options.platform
val log = options.log
// if (log.traceEnabled) {
@ -30,6 +33,7 @@ object Preprocessor {
// }
val result = mutable.ListBuffer[String]()
val featureConstants = mutable.Map[String, Long]()
val pragmas = mutable.Map[String, Int]()
var enabled = true
val ifStack = mutable.Stack[IfContext]()
var lineNo = 0
@ -105,6 +109,9 @@ object Preprocessor {
}
ifStack.push(ifStack.pop().copy(hadEnabled = true, hadElse = true))
}
case "pragma" =>
if (param == "") log.error("#pragma should", pos)
pragmas += param -> lineNo
case _ =>
log.error("Invalid preprocessor directive: #" + keyword, pos)
@ -121,7 +128,7 @@ object Preprocessor {
// case (line, i) => log.trace(f"${i + 1}%-4d $line%s")
// }
// }
(result.mkString("\n"), featureConstants.toMap)
PreprocessingResult(result.mkString("\n"), featureConstants.toMap, pragmas.toMap)
}

View File

@ -13,7 +13,16 @@ import millfork.node._
/**
* @author Karol Stasiak
*/
case class Z80Parser(filename: String, input: String, currentDirectory: String, options: CompilationOptions, featureConstants: Map[String, Long]) extends MfParser[ZLine](filename, input, currentDirectory, options, featureConstants) {
case class Z80Parser(filename: String,
input: String,
currentDirectory: String,
options: CompilationOptions,
featureConstants: Map[String, Long],
useIntelSyntax: Boolean) extends MfParser[ZLine](filename, input, currentDirectory, options, featureConstants) {
if (useIntelSyntax) {
options.log.error("Parsing assembly with Intel syntax not supported yet")
}
import MfParser._
@ -60,7 +69,7 @@ case class Z80Parser(filename: String, input: String, currentDirectory: String,
"IY" -> ZRegister.IY, "iy" -> ZRegister.IY,
"SP" -> ZRegister.SP, "sp" -> ZRegister.SP,
)
private def param(allowAbsolute: Boolean, allowRI: Boolean = false): P[(ZRegister.Value, Option[Expression])] = asmExpressionWithParens.map {
case (VariableExpression("R" | "r"), false) if allowRI => (ZRegister.R, None)
case (VariableExpression("I" | "i"), false) if allowRI => (ZRegister.I, None)
@ -156,7 +165,7 @@ case class Z80Parser(filename: String, input: String, currentDirectory: String,
private val jumpConditionWithComma: P[ZRegisters] = (jumpCondition ~ "," ~/ HWS).?.map (_.getOrElse(NoRegisters))
private val jumpConditionWithoutComma: P[ZRegisters] = (jumpCondition ~/ HWS).?.map (_.getOrElse(NoRegisters))
val asmInstruction: P[ExecutableStatement] = {
val zilogAsmInstruction: P[ExecutableStatement] = {
import ZOpcode._
for {
el <- elidable
@ -361,6 +370,10 @@ case class Z80Parser(filename: String, input: String, currentDirectory: String,
}
}
val intelAsmInstruction: P[ExecutableStatement] = null // TODO
val asmInstruction: P[ExecutableStatement] = if (useIntelSyntax) intelAsmInstruction else zilogAsmInstruction
private def imm(opcode: ZOpcode.Value): P[(ZOpcode.Value, ZRegisters, Option[Expression], Expression)] =
P("").map(_=>(opcode, NoRegisters, None, zero))

View File

@ -11,11 +11,17 @@ class ZSourceLoadingQueue(initialFilenames: List[String],
includePath: List[String],
options: CompilationOptions) extends AbstractSourceLoadingQueue[ZLine](initialFilenames, includePath, options) {
override def createParser(filename: String, src: String, parentDir: String, featureConstants: Map[String, Long]): MfParser[ZLine] =
Z80Parser(filename, src, parentDir, options, featureConstants)
override def createParser(filename: String, src: String, parentDir: String, featureConstants: Map[String, Long], pragmas: Set[String]): MfParser[ZLine] = {
var useIntelSyntax = options.flag(CompilationFlag.UseIntelSyntaxForInput)
if (pragmas("intel_syntax") && pragmas("zilog_syntax")) options.log.error("Conflicting pragmas: #pragma intel_syntax and #pragma zilog_syntax")
if (pragmas("zilog_syntax")) useIntelSyntax = false
if (pragmas("intel_syntax")) useIntelSyntax = true
Z80Parser(filename, src, parentDir, options, featureConstants, useIntelSyntax)
}
def enqueueStandardModules(): Unit = {
// TODO
}
override val supportedPragmas: Set[String] = Set("intel_syntax", "zilog_syntax")
}

View File

@ -16,7 +16,7 @@ import millfork.error.{ConsoleLogger, Logger}
import millfork.node.StandardCallGraph
import millfork.node.opt.NodeOptimization
import millfork.output.{MemoryBank, MosAssembler}
import millfork.parser.{MosParser, Preprocessor}
import millfork.parser.{MosParser, PreprocessingResult, Preprocessor}
import millfork.{CompilationFlag, CompilationOptions, CpuFamily, JobContext}
import org.scalatest.Matchers
@ -121,7 +121,7 @@ class EmuRun(cpu: millfork.Cpu.Value, nodeOptimizations: List[NodeOptimization],
if (source.contains("import zp_reg"))
effectiveSource += Files.readAllLines(Paths.get("include/zp_reg.mfk"), StandardCharsets.US_ASCII).asScala.mkString("\n", "\n", "")
log.setSource(Some(effectiveSource.lines.toIndexedSeq))
val (preprocessedSource, features) = Preprocessor.preprocessForTest(options, effectiveSource)
val PreprocessingResult(preprocessedSource, features, _) = Preprocessor.preprocessForTest(options, effectiveSource)
val parserF = MosParser("", preprocessedSource, "", options, features)
parserF.toAst match {
case Success(unoptimized, _) =>

View File

@ -13,7 +13,7 @@ import millfork.error.ConsoleLogger
import millfork.node.StandardCallGraph
import millfork.node.opt.NodeOptimization
import millfork.output.{MemoryBank, Z80Assembler}
import millfork.parser.{Preprocessor, Z80Parser}
import millfork.parser.{PreprocessingResult, Preprocessor, Z80Parser}
import millfork.{CompilationFlag, CompilationOptions, CpuFamily, JobContext}
import millfork.compiler.z80.Z80Compiler
import org.scalatest.Matchers
@ -46,8 +46,9 @@ class EmuZ80Run(cpu: millfork.Cpu.Value, nodeOptimizations: List[NodeOptimizatio
var effectiveSource = source
if (!source.contains("_panic")) effectiveSource += "\n void _panic(){while(true){}}"
log.setSource(Some(effectiveSource.lines.toIndexedSeq))
val (preprocessedSource, features) = Preprocessor.preprocessForTest(options, effectiveSource)
val parserF = Z80Parser("", preprocessedSource, "", options, features)
val PreprocessingResult(preprocessedSource, features, pragmas) = Preprocessor.preprocessForTest(options, effectiveSource)
val parserF = Z80Parser("", preprocessedSource, "", options, features, false)
//if (pragmas.contains("intel_syntax")) true else if (pragmas.contains("zilog_syntax")) false else options.flag(CompilationFlag.UseIntelSyntax))
parserF.toAst match {
case Success(unoptimized, _) =>
log.assertNoErrors("Parse failed")

View File

@ -8,7 +8,7 @@ import millfork.compiler.{CompilationContext, LabelGenerator}
import millfork.compiler.mos.MosCompiler
import millfork.env.{Environment, InitializedArray, InitializedMemoryVariable, NormalFunction}
import millfork.node.StandardCallGraph
import millfork.parser.{MosParser, Preprocessor}
import millfork.parser.{MosParser, PreprocessingResult, Preprocessor}
import millfork._
import org.scalatest.Matchers
@ -36,7 +36,7 @@ object ShouldNotCompile extends Matchers {
if (source.contains("import zp_reg"))
effectiveSource += Files.readAllLines(Paths.get("include/zp_reg.mfk"), StandardCharsets.US_ASCII).asScala.mkString("\n", "\n", "")
log.setSource(Some(effectiveSource.lines.toIndexedSeq))
val (preprocessedSource, features) = Preprocessor.preprocessForTest(options, effectiveSource)
val PreprocessingResult(preprocessedSource, features, _) = Preprocessor.preprocessForTest(options, effectiveSource)
val parserF = MosParser("", preprocessedSource, "", options, features)
parserF.toAst match {
case Success(program, _) =>