new attempt

This commit is contained in:
Irmen de Jong 2023-03-26 04:49:23 +02:00
parent 0c81b32cac
commit f28206d989
17 changed files with 686 additions and 82 deletions

View File

@ -180,7 +180,13 @@ class PtFunctionCall(val name: String,
}
class PtIdentifier(val name: String, type: DataType, position: Position) : PtExpression(type, position)
class PtIdentifier(val name: String, type: DataType, position: Position) : PtExpression(type, position) {
override fun toString(): String {
return "[PtIdentifier:$name $type $position]"
}
fun copy() = PtIdentifier(name, type, position)
}
class PtMemoryByte(position: Position) : PtExpression(DataType.UBYTE, position) {

View File

@ -38,20 +38,17 @@ class PtSub(
class PtSubroutineParameter(name: String, val type: DataType, position: Position): PtNamedNode(name, position)
class PtAssignment(position: Position) : PtNode(position) {
sealed interface IPtAssignment {
val children: MutableList<PtNode>
val target: PtAssignTarget
get() = children[0] as PtAssignTarget
val value: PtExpression
get() = children[1] as PtExpression
}
class PtAssignment(position: Position) : PtNode(position), IPtAssignment
class PtAugmentedAssign(val operator: String, position: Position) : PtNode(position) {
val target: PtAssignTarget
get() = children[0] as PtAssignTarget
val value: PtExpression
get() = children[1] as PtExpression
}
class PtAugmentedAssign(val operator: String, position: Position) : PtNode(position), IPtAssignment
class PtAssignTarget(position: Position) : PtNode(position) {
@ -95,7 +92,7 @@ class PtForLoop(position: Position) : PtNode(position) {
class PtIfElse(position: Position) : PtNode(position) {
val condition: PtExpression // either PtRpn or PtBinaryExpression
val condition: PtExpression
get() = children[0] as PtExpression
val ifScope: PtNodeGroup
get() = children[1] as PtNodeGroup

View File

@ -21,13 +21,6 @@ class AsmGen6502: ICodeGeneratorBackend {
options: CompilationOptions,
errors: IErrorReporter
): IAssemblyProgram? {
if(options.useNewExprCode) {
// TODO("transform BinExprs?")
// errors.warn("EXPERIMENTAL NEW EXPRESSION CODEGEN IS USED. CODE SIZE+SPEED POSSIBLY SUFFERS.", Position.DUMMY)
}
// printAst(program, true) { println(it) }
val asmgen = AsmGen6502Internal(program, symbolTable, options, errors)
return asmgen.compileToAssembly()
}
@ -551,28 +544,74 @@ class AsmGen6502Internal (
}
private fun translate(stmt: PtIfElse) {
val condition = stmt.condition as PtBinaryExpression
requireComparisonExpression(condition) // IfStatement: condition must be of form 'x <comparison> <value>'
if (stmt.elseScope.children.isEmpty()) {
val jump = stmt.ifScope.children.singleOrNull()
if (jump is PtJump) {
translateCompareAndJumpIfTrue(condition, jump)
val condition = stmt.condition as? PtBinaryExpression
if(condition!=null) {
require(!options.useNewExprCode)
requireComparisonExpression(condition) // IfStatement: condition must be of form 'x <comparison> <value>'
if (stmt.elseScope.children.isEmpty()) {
val jump = stmt.ifScope.children.singleOrNull()
if (jump is PtJump) {
translateCompareAndJumpIfTrue(condition, jump)
} else {
val endLabel = makeLabel("if_end")
translateCompareAndJumpIfFalse(condition, endLabel)
translate(stmt.ifScope)
out(endLabel)
}
} else {
// both true and else parts
val elseLabel = makeLabel("if_else")
val endLabel = makeLabel("if_end")
translateCompareAndJumpIfFalse(condition, endLabel)
translateCompareAndJumpIfFalse(condition, elseLabel)
translate(stmt.ifScope)
jmp(endLabel)
out(elseLabel)
translate(stmt.elseScope)
out(endLabel)
}
} else {
// both true and else parts
val elseLabel = makeLabel("if_else")
val endLabel = makeLabel("if_end")
translateCompareAndJumpIfFalse(condition, elseLabel)
translate(stmt.ifScope)
jmp(endLabel)
out(elseLabel)
translate(stmt.elseScope)
out(endLabel)
// condition is a simple expression "if X" --> "if X!=0"
val zero = PtNumber(DataType.UBYTE,0.0, stmt.position)
val leftConst = stmt.condition as? PtNumber
if (stmt.elseScope.children.isEmpty()) {
val jump = stmt.ifScope.children.singleOrNull()
if (jump is PtJump) {
val label = when {
jump.generatedLabel!=null -> jump.generatedLabel!!
jump.identifier!=null -> asmSymbolName(jump.identifier!!)
jump.address!=null -> jump.address!!.toHex()
else -> throw AssemblyError("weird jump")
}
when(stmt.condition.type) {
in WordDatatypes -> translateWordEqualsJump(stmt.condition, zero, leftConst, zero, label)
in ByteDatatypes -> translateByteEqualsJump(stmt.condition, zero, leftConst, zero, label)
else -> throw AssemblyError("weird condition dt")
}
} else {
val endLabel = makeLabel("if_end")
when(stmt.condition.type) {
in WordDatatypes -> translateWordEqualsJump(stmt.condition, zero, leftConst, zero, endLabel)
in ByteDatatypes -> translateByteEqualsJump(stmt.condition, zero, leftConst, zero, endLabel)
else -> throw AssemblyError("weird condition dt")
}
translate(stmt.ifScope)
out(endLabel)
}
} else {
// both true and else parts
val elseLabel = makeLabel("if_else")
val endLabel = makeLabel("if_end")
when(stmt.condition.type) {
in WordDatatypes -> translateWordEqualsJump(stmt.condition, zero, leftConst, zero, elseLabel)
in ByteDatatypes -> translateByteEqualsJump(stmt.condition, zero, leftConst, zero, elseLabel)
else -> throw AssemblyError("weird condition dt")
}
translate(stmt.ifScope)
jmp(endLabel)
out(elseLabel)
translate(stmt.elseScope)
out(endLabel)
}
}
}
@ -740,7 +779,7 @@ $repeatLabel lda $counterVar
}
val isNested = parent is PtRepeatLoop
if(!isNested && !options.useNewExprCode) {
if(!isNested) {
// we can re-use a counter var from the subroutine if it already has one for that datatype
val existingVar = asmInfo.extraVars.firstOrNull { it.first==dt && it.second.endsWith("counter") }
if(existingVar!=null) {
@ -987,6 +1026,7 @@ $repeatLabel lda $counterVar
val operator: String
if (pointerOffsetExpr is PtBinaryExpression) {
require(!options.useNewExprCode)
operator = pointerOffsetExpr.operator
left = pointerOffsetExpr.left
right = pointerOffsetExpr.right
@ -2853,6 +2893,7 @@ $repeatLabel lda $counterVar
out(" sta P8ESTACK_LO,x | dex")
}
is PtBinaryExpression -> {
require(!options.useNewExprCode)
val addrExpr = expr.address as PtBinaryExpression
if(tryOptimizedPointerAccessWithA(addrExpr, addrExpr.operator, false)) {
if(pushResultOnEstack)

View File

@ -662,6 +662,7 @@ internal class BuiltinFunctionsAsmGen(private val program: PtProgram,
}
}
is PtBinaryExpression -> {
require(!asmgen.options.useNewExprCode)
val result = asmgen.pointerViaIndexRegisterPossible(addrExpr)
val pointer = result?.first as? PtIdentifier
if(result!=null && pointer!=null && asmgen.isZpVar(pointer)) {
@ -724,6 +725,7 @@ internal class BuiltinFunctionsAsmGen(private val program: PtProgram,
} else fallback()
}
is PtBinaryExpression -> {
require(!asmgen.options.useNewExprCode)
val result = asmgen.pointerViaIndexRegisterPossible(addrExpr)
val pointer = result?.first as? PtIdentifier
if(result!=null && pointer!=null && asmgen.isZpVar(pointer)) {

View File

@ -245,6 +245,8 @@ internal class ExpressionsAsmGen(private val program: PtProgram,
}
private fun translateExpression(expr: PtBinaryExpression) {
require(!asmgen.options.useNewExprCode)
// Uses evalstack to evaluate the given expression. THIS IS SLOW AND SHOULD BE AVOIDED!
if(translateSomewhatOptimized(expr.left, expr.operator, expr.right))
return

View File

@ -147,6 +147,7 @@ internal class AssignmentAsmGen(private val program: PtProgram,
assignMemoryByte(assign.target, null, value.address as PtIdentifier)
}
is PtBinaryExpression -> {
require(!asmgen.options.useNewExprCode)
val addrExpr = value.address as PtBinaryExpression
if(asmgen.tryOptimizedPointerAccessWithA(addrExpr, addrExpr.operator, false)) {
assignRegisterByte(assign.target, CpuRegister.A)
@ -301,6 +302,7 @@ internal class AssignmentAsmGen(private val program: PtProgram,
assignRegisterByte(assign.target, CpuRegister.A)
}
is PtBinaryExpression -> {
require(!asmgen.options.useNewExprCode)
if(!attemptAssignOptimizedBinexpr(value, assign)) {
// All remaining binary expressions just evaluate via the stack for now.
// (we can't use the assignment helper functions (assignExpressionTo...) to do it via registers here,
@ -346,6 +348,7 @@ internal class AssignmentAsmGen(private val program: PtProgram,
}
private fun attemptAssignOptimizedBinexpr(expr: PtBinaryExpression, assign: AsmAssignment): Boolean {
require(!asmgen.options.useNewExprCode)
if(expr.operator in ComparisonOperators) {
if(expr.right.asConstInteger() == 0) {
if(expr.operator == "==" || expr.operator=="!=") {
@ -728,6 +731,7 @@ internal class AssignmentAsmGen(private val program: PtProgram,
}
private fun attemptAssignToByteCompareZero(expr: PtBinaryExpression, assign: AsmAssignment): Boolean {
require(!asmgen.options.useNewExprCode)
when (expr.operator) {
"==" -> {
when(val dt = expr.left.type) {
@ -907,6 +911,7 @@ internal class AssignmentAsmGen(private val program: PtProgram,
assignMemoryByteIntoWord(target, null, value.address as PtIdentifier)
}
is PtBinaryExpression -> {
require(!asmgen.options.useNewExprCode)
val addrExpr = value.address as PtBinaryExpression
if(asmgen.tryOptimizedPointerAccessWithA(addrExpr, addrExpr.operator, false)) {
asmgen.out(" ldy #0")
@ -2519,7 +2524,7 @@ internal class AssignmentAsmGen(private val program: PtProgram,
}
}
private fun assignConstantFloat(target: AsmAssignTarget, float: Double) {
internal fun assignConstantFloat(target: AsmAssignTarget, float: Double) {
if (float == 0.0) {
// optimized case for float zero
when(target.kind) {
@ -2829,6 +2834,7 @@ internal class AssignmentAsmGen(private val program: PtProgram,
asmgen.storeAIntoPointerVar(addressExpr)
}
addressExpr is PtBinaryExpression -> {
require(!asmgen.options.useNewExprCode)
if(!asmgen.tryOptimizedPointerAccessWithA(addressExpr, addressExpr.operator, true))
storeViaExprEval()
}

View File

@ -1319,8 +1319,174 @@ internal class AugmentableAssignmentAsmGen(private val program: PtProgram,
lda #0
sta $name+1""")
}
// pretty uncommon, who's going to assign a comparison boolean expresion to a word var?:
"<", "<=", ">", ">=" -> TODO("word-litval-to-var comparisons")
"<" -> {
if(dt==DataType.UWORD) {
asmgen.out("""
lda $name+1
cmp #>$value
bcc ++
bne +
lda $name
cmp #<$value
bcc ++
+ lda #0 ; false
sta $name
sta $name+1
beq ++
+ lda #1 ; true
sta $name
lda #0
sta $name+1
+""")
}
else {
// signed
asmgen.out("""
lda $name
cmp #<$value
lda $name+1
sbc #>$value
bvc +
eor #$80
+ bmi +
lda #0
sta $name
sta $name+1
beq ++
+ lda #1 ; true
sta $name
lda #0
sta $name+1
+""")
}
}
"<=" -> {
if(dt==DataType.UWORD) {
asmgen.out("""
lda $name+1
cmp #>$value
beq +
bcc ++
- lda #0 ; false
sta $name
sta $name+1
beq +++
+ lda $name ; next
cmp #<$value
bcc +
bne -
+ lda #1 ; true
sta $name
lda #0
sta $name+1
+""")
}
else {
// signed
asmgen.out("""
lda #<$value
cmp $name
lda #>$value
sbc $name+1
bvc +
eor #$80
+ bpl +
lda #0
sta $name
sta $name+1
beq ++
+ lda #1
sta $name
lda #0
sta $name+1
+""")
}
}
">" -> {
// word > value --> value < word
if(dt==DataType.UWORD) {
asmgen.out("""
lda #>$value
cmp $name+1
bcc ++
bne +
lda #<$value
cmp $name
bcc ++
+ lda #0 ; false
sta $name
sta $name+1
beq ++
+ lda #1 ; true
sta $name
lda #0
sta $name+1
+""")
}
else {
// signed
asmgen.out("""
lda #<$value
cmp $name
lda #>$value
sbc $name+1
bvc +
eor #$80
+ bmi +
lda #0
sta $name
sta $name+1
beq ++
+ lda #1 ; true
sta $name
lda #0
sta $name+1
+""")
}
}
">=" -> {
// word >= value --> value <= word
if(dt==DataType.UWORD) {
asmgen.out("""
lda #>$value
cmp $name+1
beq +
bcc ++
- lda #0 ; false
sta $name
sta $name+1
beq +++
+ lda #<$value ; next
cmp $name
bcc +
bne -
+ lda #1 ; true
sta $name
lda #0
sta $name+1
+""")
}
else {
// signed
asmgen.out("""
lda $name
cmp #<$value
lda $name+1
sbc #>$value
bvc +
eor #$80
+ bpl +
lda #0
sta $name
sta $name+1
beq ++
+ lda #1
sta $name
lda #0
sta $name+1
+""")
}
}
else -> throw AssemblyError("invalid operator for in-place modification $operator")
}
}
@ -2129,8 +2295,126 @@ internal class AugmentableAssignmentAsmGen(private val program: PtProgram,
jsr floats.FDIV
""")
}
// pretty uncommon, who's going to assign a comparison boolean expresion to a float var:
"==", "!=", "<", "<=", ">", ">=" -> TODO("float-litval-to-var comparisons")
"==" -> {
asmgen.out("""
lda #<$name
ldy #>$name
sta P8ZP_SCRATCH_W1
sty P8ZP_SCRATCH_W1+1
lda #<$constValueName
ldy #>$constValueName
jsr floats.vars_equal_f
bne +""")
val nameTarget = AsmAssignTarget(TargetStorageKind.VARIABLE, asmgen, DataType.FLOAT, scope, Position.DUMMY, variableAsmName = name)
assignmentAsmGen.assignConstantFloat(nameTarget, 0.0)
asmgen.out("""
jmp ++
+""")
assignmentAsmGen.assignConstantFloat(nameTarget, 1.0)
asmgen.out("+")
asmgen.restoreRegisterLocal(CpuRegister.X)
return
}
"!=" -> {
asmgen.out("""
lda #<$name
ldy #>$name
sta P8ZP_SCRATCH_W1
sty P8ZP_SCRATCH_W1+1
lda #<$constValueName
ldy #>$constValueName
jsr floats.vars_equal_f
beq +""")
val nameTarget = AsmAssignTarget(TargetStorageKind.VARIABLE, asmgen, DataType.FLOAT, scope, Position.DUMMY, variableAsmName = name)
assignmentAsmGen.assignConstantFloat(nameTarget, 0.0)
asmgen.out("""
jmp ++
+""")
assignmentAsmGen.assignConstantFloat(nameTarget, 1.0)
asmgen.out("+")
asmgen.restoreRegisterLocal(CpuRegister.X)
return
}
"<" -> {
asmgen.out("""
lda #<$name
ldy #>$name
jsr floats.MOVFM
lda #<$constValueName
ldy #>$constValueName
jsr floats.FCOMP ; A = compare fac1 to mflpt in A/Y, 0=equal 1=fac1 is greater, 255=fac1 is less than
cmp #0
bmi +""")
val nameTarget = AsmAssignTarget(TargetStorageKind.VARIABLE, asmgen, DataType.FLOAT, scope, Position.DUMMY, variableAsmName = name)
assignmentAsmGen.assignConstantFloat(nameTarget, 0.0)
asmgen.out("""
jmp ++
+""")
assignmentAsmGen.assignConstantFloat(nameTarget, 1.0)
asmgen.out("+")
asmgen.restoreRegisterLocal(CpuRegister.X)
return
}
"<=" -> {
asmgen.out("""
lda #<$constValueName
ldy #>$constValueName
jsr floats.MOVFM
lda #<$name
ldy #>$name
jsr floats.FCOMP ; A = compare fac1 to mflpt in A/Y, 0=equal 1=fac1 is greater, 255=fac1 is less than
cmp #0
bpl +""")
val nameTarget = AsmAssignTarget(TargetStorageKind.VARIABLE, asmgen, DataType.FLOAT, scope, Position.DUMMY, variableAsmName = name)
assignmentAsmGen.assignConstantFloat(nameTarget, 0.0)
asmgen.out("""
jmp ++
+""")
assignmentAsmGen.assignConstantFloat(nameTarget, 1.0)
asmgen.out("+")
asmgen.restoreRegisterLocal(CpuRegister.X)
return
}
">" -> {
asmgen.out("""
lda #<$constValueName
ldy #>$constValueName
jsr floats.MOVFM
lda #<$name
ldy #>$name
jsr floats.FCOMP ; A = compare fac1 to mflpt in A/Y, 0=equal 1=fac1 is greater, 255=fac1 is less than
cmp #0
bmi +""")
val nameTarget = AsmAssignTarget(TargetStorageKind.VARIABLE, asmgen, DataType.FLOAT, scope, Position.DUMMY, variableAsmName = name)
assignmentAsmGen.assignConstantFloat(nameTarget, 0.0)
asmgen.out("""
jmp ++
+""")
assignmentAsmGen.assignConstantFloat(nameTarget, 1.0)
asmgen.out("+")
asmgen.restoreRegisterLocal(CpuRegister.X)
return
}
">=" -> {
asmgen.out("""
lda #<$name
ldy #>$name
jsr floats.MOVFM
lda #<$constValueName
ldy #>$constValueName
jsr floats.FCOMP ; A = compare fac1 to mflpt in A/Y, 0=equal 1=fac1 is greater, 255=fac1 is less than
cmp #0
bpl +""")
val nameTarget = AsmAssignTarget(TargetStorageKind.VARIABLE, asmgen, DataType.FLOAT, scope, Position.DUMMY, variableAsmName = name)
assignmentAsmGen.assignConstantFloat(nameTarget, 0.0)
asmgen.out("""
jmp ++
+""")
assignmentAsmGen.assignConstantFloat(nameTarget, 1.0)
asmgen.out("+")
asmgen.restoreRegisterLocal(CpuRegister.X)
return
}
else -> throw AssemblyError("invalid operator for in-place float modification $operator")
}
// store Fac1 back into memory

View File

@ -14,11 +14,6 @@ class ExperiCodeGen: ICodeGeneratorBackend {
errors: IErrorReporter
): IAssemblyProgram? {
if(options.useNewExprCode) {
// TODO("transform BinExprs?")
// errors.warn("EXPERIMENTAL NEW EXPRESSION CODEGEN IS USED. CODE SIZE+SPEED POSSIBLY SUFFERS.", Position.DUMMY)
}
// you could write a code generator directly on the PtProgram AST,
// but you can also use the Intermediate Representation to build a codegen on:
val irCodeGen = IRCodeGen(program, symbolTable, options, errors)

View File

@ -93,7 +93,7 @@ internal class AssignmentGen(private val codeGen: IRCodeGen, private val express
} else {
require(origAssign.operator.endsWith('='))
if(codeGen.options.useNewExprCode) {
TODO("use something else than a BinExpr?")
TODO("use something else than a BinExpr")
} else {
value = PtBinaryExpression(origAssign.operator.dropLast(1), origAssign.value.type, origAssign.value.position)
val left: PtExpression = origAssign.target.children.single() as PtExpression
@ -268,7 +268,7 @@ internal class AssignmentGen(private val codeGen: IRCodeGen, private val express
} else {
val mult : PtExpression
if(codeGen.options.useNewExprCode) {
TODO("use something else than a BinExpr?")
TODO("use something else than a BinExpr")
} else {
mult = PtBinaryExpression("*", DataType.UBYTE, array.position)
mult.children += array.index

View File

@ -320,6 +320,7 @@ internal class ExpressionGen(private val codeGen: IRCodeGen) {
}
private fun translate(binExpr: PtBinaryExpression): ExpressionCodeResult {
require(!codeGen.options.useNewExprCode)
val vmDt = codeGen.irType(binExpr.left.type)
val signed = binExpr.left.type in SignedDatatypes
return when(binExpr.operator) {

View File

@ -899,6 +899,7 @@ class IRCodeGen(
val goto = ifElse.ifScope.children.firstOrNull() as? PtJump
when (condition) {
is PtBinaryExpression -> {
require(!options.useNewExprCode)
if(condition.operator !in ComparisonOperators)
throw AssemblyError("if condition should only be a binary comparison expression")

View File

@ -14,13 +14,6 @@ class VmCodeGen: ICodeGeneratorBackend {
options: CompilationOptions,
errors: IErrorReporter
): IAssemblyProgram? {
if(options.useNewExprCode) {
// TODO("transform BinExprs?")
// errors.warn("EXPERIMENTAL NEW EXPRESSION CODEGEN IS USED. CODE SIZE+SPEED POSSIBLY SUFFERS.", Position.DUMMY)
}
val irCodeGen = IRCodeGen(program, symbolTable, options, errors)
val irProgram = irCodeGen.generate()
return VmAssemblyProgram(irProgram.name, irProgram)

View File

@ -251,7 +251,7 @@ pop_float_fac1 .proc
.pend
copy_float .proc
; -- copies the 5 bytes of the mflt value pointed to by SCRATCH_ZPWORD1,
; -- copies the 5 bytes of the mflt value pointed to by SCRATCH_W1,
; into the 5 bytes pointed to by A/Y. Clobbers A,Y.
sta _target+1
sty _target+2

View File

@ -8,7 +8,7 @@ import prog8.ast.expressions.Expression
import prog8.ast.expressions.NumericLiteral
import prog8.ast.statements.Directive
import prog8.code.SymbolTableMaker
import prog8.code.ast.PtProgram
import prog8.code.ast.*
import prog8.code.core.*
import prog8.code.target.*
import prog8.codegen.vm.VmCodeGen
@ -409,6 +409,11 @@ private fun createAssemblyAndAssemble(program: PtProgram,
else
throw NotImplementedError("no code generator for cpu ${compilerOptions.compTarget.machine.cpu}")
if(compilerOptions.useNewExprCode)
transformNewExpressions(program)
printAst(program, true) { println(it) }
val stMaker = SymbolTableMaker(program, compilerOptions)
val symbolTable = stMaker.make()
val assembly = asmgen.generate(program, symbolTable, compilerOptions, errors)
@ -420,3 +425,165 @@ private fun createAssemblyAndAssemble(program: PtProgram,
false
}
}
private fun transformNewExpressions(program: PtProgram) {
val newVariables = mutableMapOf<PtSub, MutableList<PtVariable>>()
fun getExprVar(what: String, type: DataType, count: Int, pos: Position, scope: PtSub): PtIdentifier {
val name = "p8p_exprvar_${what}_${count}_${type.toString().lowercase()}"
var subVars = newVariables[scope]
if(subVars==null) {
subVars = mutableListOf()
newVariables[scope] = subVars
}
if(subVars.all { it.name!=name }) {
subVars.add(PtVariable(name, type, ZeropageWish.DONTCARE, null, null, pos))
}
return PtIdentifier("${scope.scopedName}.$name", type, pos)
}
fun transformExpr(expr: PtBinaryExpression, postfix: String, depth: Int): Pair<PtExpression, List<IPtAssignment>> {
// depth first process the expression tree
val scope = expr.definingSub()!!
val assignments = mutableListOf<IPtAssignment>()
fun transformOperand(node: PtExpression, kind: String): PtNode {
return when(node) {
is PtNumber, is PtIdentifier, is PtArray, is PtString, is PtMachineRegister -> node
is PtBinaryExpression -> {
val (replacement, subAssigns) = transformExpr(node, kind, depth+1)
assignments.addAll(subAssigns)
replacement
}
else -> {
val variable = getExprVar(kind, node.type, depth, node.position, scope)
val assign = PtAssignment(node.position)
val target = PtAssignTarget(variable.position)
target.add(variable)
assign.add(target)
assign.add(node)
assignments.add(assign)
variable
}
}
}
val newLeft = transformOperand(expr.left,"l")
val newRight = transformOperand(expr.right, "r")
// process the binexpr
val resultVar =
if(expr.type == expr.left.type) {
getExprVar(postfix, expr.type, depth, expr.position, scope)
} else {
if(expr.operator in ComparisonOperators && expr.type == DataType.UBYTE) {
// this is very common and should be dealth with correctly; byte==0, word>42
getExprVar(postfix, expr.left.type, depth, expr.position, scope)
}
else if(expr.left.type in PassByReferenceDatatypes && expr.type==DataType.UBYTE) {
// this is common and should be dealth with correctly; for instance "name"=="irmen"
getExprVar(postfix, expr.left.type, depth, expr.position, scope)
} else {
TODO("expression type differs from left operand type! got ${expr.left.type} expected ${expr.type} ${expr.position}")
}
}
if(resultVar.name!=(newLeft as? PtIdentifier)?.name) {
// resultvar = left
val assign1 = PtAssignment(newLeft.position)
val target1 = PtAssignTarget(resultVar.position)
target1.add(resultVar)
assign1.add(target1)
assign1.add(newLeft)
assignments.add(assign1)
}
// resultvar {oper}= right
val operator = if(expr.operator in ComparisonOperators) expr.operator else expr.operator+'='
val assign2 = PtAugmentedAssign(operator, newRight.position)
val target2 = PtAssignTarget(resultVar.position)
target2.add(resultVar.copy())
assign2.add(target2)
assign2.add(newRight)
assignments.add(assign2)
return Pair(resultVar, assignments)
}
fun isProperStatement(node: PtNode): Boolean {
return when(node) {
is PtAssignment -> true
is PtAugmentedAssign -> true
is PtBreakpoint -> true
is PtConditionalBranch -> true
is PtForLoop -> true
is PtIfElse -> true
is PtIncludeBinary -> true
is PtInlineAssembly -> true
is PtJump -> true
is PtAsmSub -> true
is PtLabel -> true
is PtSub -> true
is PtVariable -> true
is PtNop -> true
is PtPostIncrDecr -> true
is PtRepeatLoop -> true
is PtReturn -> true
is PtWhen -> true
is PtBuiltinFunctionCall -> node.void
is PtFunctionCall -> node.void
else -> false
}
}
fun transform(node: PtNode, parent: PtNode, depth: Int) {
if(node is PtBinaryExpression) {
node.children.toTypedArray().forEach {
transform(it, node, depth+1)
}
val (rep, assignments) = transformExpr(node, "l", depth)
var replacement = rep
if(!(rep.type equalsSize node.type)) {
if(rep.type in NumericDatatypes && node.type in ByteDatatypes) {
replacement = PtTypeCast(node.type, node.position)
replacement.add(rep)
} else
TODO("cast replacement type ${rep.type} -> ${node.type}")
}
var idx = parent.children.indexOf(node)
parent.children[idx] = replacement
replacement.parent = parent
// find the statement above which we should insert the assignments
var stmt = node
while(!isProperStatement(stmt))
stmt = stmt.parent
idx = stmt.parent.children.indexOf(stmt)
assignments.reversed().forEach {
stmt.parent.add(idx, it as PtNode)
}
} else {
node.children.toTypedArray().forEach { child -> transform(child, node, depth+1) }
}
}
program.allBlocks().forEach { block ->
block.children.toTypedArray().forEach {
transform(it, block, 0)
}
}
// add the new variables
newVariables.forEach { (sub, vars) ->
vars.forEach {
sub.add(0, it)
}
}
// extra check to see that all PtBinaryExpressions have been transformed
fun binExprCheck(node: PtNode) {
if(node is PtBinaryExpression)
throw IllegalArgumentException("still got binexpr $node ${node.position}")
node.children.forEach { binExprCheck(it) }
}
binExprCheck(program)
}

View File

@ -957,7 +957,11 @@ internal class AstChecker(private val program: Program,
}
}
if(expr.operator !in ComparisonOperators) {
if(expr.operator in ComparisonOperators) {
if(leftDt!=rightDt && !(leftDt in ByteDatatypes && rightDt in ByteDatatypes)) {
throw FatalAstException("got comparison with different operand types: $leftDt ${expr.operator} $rightDt ${expr.position}")
}
} else {
if (leftDt == DataType.STR && rightDt == DataType.STR || leftDt in ArrayDatatypes && rightDt in ArrayDatatypes) {
// str+str and str*number have already been const evaluated before we get here.
errors.err("no computational or logical expressions with strings or arrays are possible", expr.position)

View File

@ -109,6 +109,8 @@ internal class NotExpressionAndIfComparisonExprChanger(val program: Program, val
if(binExpr==null || binExpr.operator !in ComparisonOperators)
return noModifications
return noModifications // TODO tijdelijk geen simplify
// Simplify the conditional expression, introduce simple assignments if required.
// This is REQUIRED for correct code generation on 6502 because evaluating certain expressions
// clobber the handful of temporary variables in the zeropage and leaving everything in one

View File

@ -1,38 +1,141 @@
%zeropage basicsafe
%import textio
%import floats
%zeropage basicsafe
; Draw a mandelbrot in graphics mode (the image will be 256 x 200 pixels).
; NOTE: this will take an eternity to draw on a real c64. A CommanderX16 is a bit faster.
; even in Vice in warp mode (700% speed on my machine) it's slow, but you can see progress
; Note: this program is compatible with C64 and CX16.
main {
sub start() {
float xsquared = 2.0
float ysquared = 1.9
uword w = 1
ubyte h = 0
sub start() {
byte b = -100
ubyte ub = 20
word w = -20000
uword uw = 2000
float f = -100
str name = ".tx2"
txt.print("all 1: ")
txt.print_ub(b == -100)
txt.print_ub(b != -99)
txt.print_ub(b < -99)
txt.print_ub(b <= -100)
txt.print_ub(b > -101)
txt.print_ub(b >= -100)
txt.print_ub(ub ==20)
txt.print_ub(ub !=19)
txt.print_ub(ub <21)
txt.print_ub(ub <=20)
txt.print_ub(ub>19)
txt.print_ub(ub>=20)
txt.spc()
txt.print_ub(w == -20000)
txt.print_ub(w != -19999)
txt.print_ub(w < -19999)
txt.print_ub(w <= -20000)
txt.print_ub(w > -20001)
txt.print_ub(w >= -20000)
txt.print_ub(uw == 2000)
txt.print_ub(uw != 2001)
txt.print_ub(uw < 2001)
txt.print_ub(uw <= 2000)
txt.print_ub(uw > 1999)
txt.print_ub(uw >= 2000)
txt.spc()
txt.print_ub(f == -100.0)
txt.print_ub(f != -99.0)
txt.print_ub(f < -99.0)
txt.print_ub(f <= -100.0)
txt.print_ub(f > -101.0)
txt.print_ub(f >= -100.0)
txt.nl()
if name==".jpg" or name==".txt" or name==".gif" {
txt.print("yes")
txt.print("all 0: ")
txt.print_ub(b == -99)
txt.print_ub(b != -100)
txt.print_ub(b < -100)
txt.print_ub(b <= -101)
txt.print_ub(b > -100)
txt.print_ub(b >= -99)
txt.print_ub(ub ==21)
txt.print_ub(ub !=20)
txt.print_ub(ub <20)
txt.print_ub(ub <=19)
txt.print_ub(ub>20)
txt.print_ub(ub>=21)
txt.spc()
txt.print_ub(w == -20001)
txt.print_ub(w != -20000)
txt.print_ub(w < -20000)
txt.print_ub(w <= -20001)
txt.print_ub(w > -20000)
txt.print_ub(w >= -19999)
txt.print_ub(uw == 1999)
txt.print_ub(uw != 2000)
txt.print_ub(uw < 2000)
txt.print_ub(uw <= 1999)
txt.print_ub(uw > 2000)
txt.print_ub(uw >= 2001)
txt.spc()
txt.print_ub(f == -99.0)
txt.print_ub(f != -100.0)
txt.print_ub(f < -100.0)
txt.print_ub(f <= -101.0)
txt.print_ub(f > -100.0)
txt.print_ub(f >= -99.0)
txt.nl()
; TODO ALL OF THE ABOVE BUT WITH A VARIABLE INSTEAD OF A CONST VALUE
b = -100
while b <= -20
b++
txt.print_b(b)
txt.print(" -19\n")
b = -100
while b < -20
b++
txt.print_b(b)
txt.print(" -20\n")
ub = 20
while ub <= 200
ub++
txt.print_ub(ub)
txt.print(" 201\n")
ub = 20
while ub < 200
ub++
txt.print_ub(ub)
txt.print(" 200\n")
w = -20000
while w <= -8000 {
w++
}
txt.print_w(w)
txt.print(" -7999\n")
w = -20000
while w < -8000 {
w++
}
txt.print_w(w)
txt.print(" -8000\n")
; if w==0 or xsquared+ysquared<4.0 {
; txt.print("yes")
; }
uw = 2000
while uw <= 8000 {
uw++
}
txt.print_uw(uw)
txt.print(" 8001\n")
uw = 2000
while uw < 8000 {
uw++
}
txt.print_uw(uw)
txt.print(" 8000\n")
; if w==0 {
; txt.print("w=0 ")
; }
; if h==0 {
; txt.print("h=0 ")
; }
; if w==0 or h==0 {
; txt.print(" w or h=0")
; }
f = 0.0
while f<2.2 {
f+=0.1
}
floats.print_f(f)
txt.print(" 2.2\n")
}
}