"not" operator removed from ast and codegen (it's been replaced with x==0 as equivalent)

This commit is contained in:
Irmen de Jong
2022-06-29 01:13:08 +02:00
parent dc82a0fc16
commit 4b358abbb7
22 changed files with 216 additions and 433 deletions

View File

@@ -153,6 +153,12 @@ class PtPrefix(val operator: String, type: DataType, position: Position): PtExpr
val value: PtExpression val value: PtExpression
get() = children.single() as PtExpression get() = children.single() as PtExpression
init {
// note: the "not" operator may no longer occur in the ast; not x should have been replaced with x==0
if(operator !in setOf("+", "-", "~"))
throw IllegalArgumentException("invalid prefix operator: $operator")
}
override fun printProperties() { override fun printProperties() {
print(operator) print(operator)
} }

View File

@@ -3,7 +3,7 @@ package prog8.code.core
val AssociativeOperators = setOf("+", "*", "&", "|", "^", "or", "and", "xor", "==", "!=") val AssociativeOperators = setOf("+", "*", "&", "|", "^", "or", "and", "xor", "==", "!=")
val ComparisonOperators = setOf("==", "!=", "<", ">", "<=", ">=") val ComparisonOperators = setOf("==", "!=", "<", ">", "<=", ">=")
val AugmentAssignmentOperators = setOf("+", "-", "/", "*", "&", "|", "^", "<<", ">>", "%", "and", "or", "xor") val AugmentAssignmentOperators = setOf("+", "-", "/", "*", "&", "|", "^", "<<", ">>", "%", "and", "or", "xor")
val LogicalOperators = setOf("and", "or", "xor", "not") val LogicalOperators = setOf("and", "or", "xor") // not x is replaced with x==0
val BitwiseOperators = setOf("&", "|", "^") val BitwiseOperators = setOf("&", "|", "^")
fun invertedComparisonOperator(operator: String) = fun invertedComparisonOperator(operator: String) =

View File

@@ -664,22 +664,6 @@ internal class ExpressionsAsmGen(private val program: Program,
else -> throw AssemblyError("weird type") else -> throw AssemblyError("weird type")
} }
} }
"not" -> {
when(type) {
// if reg==0 ->
/*
lda P8ESTACK_LO+1,x
beq +
lda #1
+ eor #1
sta P8ESTACK_LO+1,x
rts
*/
in ByteDatatypes -> asmgen.out(" jsr prog8_lib.not_byte")
in WordDatatypes -> asmgen.out(" jsr prog8_lib.not_word")
else -> throw AssemblyError("weird type")
}
}
else -> throw AssemblyError("invalid prefix operator ${expr.operator}") else -> throw AssemblyError("invalid prefix operator ${expr.operator}")
} }
} }

View File

@@ -283,7 +283,6 @@ internal class AssignmentAsmGen(private val program: Program,
"+" -> {} "+" -> {}
"-" -> augmentableAsmGen.inplaceNegate(target, target.datatype) "-" -> augmentableAsmGen.inplaceNegate(target, target.datatype)
"~" -> augmentableAsmGen.inplaceInvert(target, target.datatype) "~" -> augmentableAsmGen.inplaceInvert(target, target.datatype)
"not" -> augmentableAsmGen.inplaceBooleanNot(target, target.datatype)
else -> throw AssemblyError("invalid prefix operator") else -> throw AssemblyError("invalid prefix operator")
} }
} }

View File

@@ -28,7 +28,6 @@ internal class AugmentableAssignmentAsmGen(private val program: Program,
"+" -> {} "+" -> {}
"-" -> inplaceNegate(target, type) "-" -> inplaceNegate(target, type)
"~" -> inplaceInvert(target, type) "~" -> inplaceInvert(target, type)
"not" -> inplaceBooleanNot(target, type)
else -> throw AssemblyError("invalid prefix operator") else -> throw AssemblyError("invalid prefix operator")
} }
} }
@@ -1800,136 +1799,6 @@ internal class AugmentableAssignmentAsmGen(private val program: Program,
} }
} }
internal fun inplaceBooleanNot(target: AsmAssignTarget, dt: DataType) {
when (dt) {
DataType.UBYTE -> {
when (target.kind) {
TargetStorageKind.VARIABLE -> {
asmgen.out("""
lda ${target.asmVarname}
beq +
lda #1
+ eor #1
sta ${target.asmVarname}""")
}
TargetStorageKind.MEMORY -> {
val mem = target.memory!!
when (mem.addressExpression) {
is NumericLiteral -> {
val addr = (mem.addressExpression as NumericLiteral).number.toHex()
asmgen.out("""
lda $addr
beq +
lda #1
+ eor #1
sta $addr""")
}
is IdentifierReference -> {
val sourceName = asmgen.loadByteFromPointerIntoA(mem.addressExpression as IdentifierReference)
asmgen.out("""
beq +
lda #1
+ eor #1""")
asmgen.storeAIntoZpPointerVar(sourceName)
}
else -> {
asmgen.assignExpressionToVariable(mem.addressExpression, "P8ZP_SCRATCH_W2", DataType.UWORD, target.scope)
asmgen.loadAFromZpPointerVar("P8ZP_SCRATCH_W2")
asmgen.out("""
beq +
lda #1
+ eor #1""")
asmgen.storeAIntoZpPointerVar("P8ZP_SCRATCH_W2")
}
}
}
TargetStorageKind.REGISTER -> {
when(target.register!!) {
RegisterOrPair.A -> asmgen.out("""
cmp #0
beq +
lda #1
+ eor #1""")
RegisterOrPair.X -> asmgen.out("""
txa
beq +
lda #1
+ eor #1
tax""")
RegisterOrPair.Y -> asmgen.out("""
tya
beq +
lda #1
+ eor #1
tay""")
else -> throw AssemblyError("invalid reg dt for byte not")
}
}
TargetStorageKind.STACK -> TODO("no asm gen for byte stack not")
else -> throw AssemblyError("no asm gen for in-place not of ubyte ${target.kind}")
}
}
DataType.UWORD -> {
when (target.kind) {
TargetStorageKind.VARIABLE -> {
asmgen.out("""
lda ${target.asmVarname}
ora ${target.asmVarname}+1
beq +
lda #1
+ eor #1
sta ${target.asmVarname}
lsr a
sta ${target.asmVarname}+1""")
}
TargetStorageKind.REGISTER -> {
when(target.register!!) {
RegisterOrPair.AX -> {
asmgen.out("""
stx P8ZP_SCRATCH_REG
ora P8ZP_SCRATCH_REG
beq +
lda #0
tax
beq ++
+ lda #1
+""")
}
RegisterOrPair.AY -> {
asmgen.out("""
sty P8ZP_SCRATCH_REG
ora P8ZP_SCRATCH_REG
beq +
lda #0
tay
beq ++
+ lda #1
+""")
}
RegisterOrPair.XY -> {
asmgen.out("""
stx P8ZP_SCRATCH_REG
tya
ora P8ZP_SCRATCH_REG
beq +
ldy #0
ldx #0
beq ++
+ ldx #1
+""")
}
in Cx16VirtualRegisters -> throw AssemblyError("cx16 virtual regs should be variables, not real registers")
else -> throw AssemblyError("invalid reg dt for word not")
}
}
TargetStorageKind.STACK -> TODO("no asm gen for word stack not")
else -> throw AssemblyError("no asm gen for in-place not of uword for ${target.kind}")
}
}
else -> throw AssemblyError("boolean-not of invalid type")
}
}
internal fun inplaceInvert(target: AsmAssignTarget, dt: DataType) { internal fun inplaceInvert(target: AsmAssignTarget, dt: DataType) {
when (dt) { when (dt) {
DataType.UBYTE -> { DataType.UBYTE -> {

View File

@@ -110,9 +110,6 @@ internal class AssignmentGen(private val codeGen: CodeGen, private val expressio
code += VmCodeInstruction(Opcode.LOAD, vmDt, reg1=regMask, value = mask) code += VmCodeInstruction(Opcode.LOAD, vmDt, reg1=regMask, value = mask)
code += VmCodeInstruction(Opcode.XORM, vmDt, reg1=regMask, value = address) code += VmCodeInstruction(Opcode.XORM, vmDt, reg1=regMask, value = address)
} }
"not" -> {
code += VmCodeInstruction(Opcode.NOTM, vmDt, value = address)
}
else -> throw AssemblyError("weird prefix operator") else -> throw AssemblyError("weird prefix operator")
} }
return code return code

View File

@@ -154,9 +154,6 @@ internal class ExpressionGen(private val codeGen: CodeGen) {
code += VmCodeInstruction(Opcode.LOAD, vmDt, reg1=regMask, value=mask) code += VmCodeInstruction(Opcode.LOAD, vmDt, reg1=regMask, value=mask)
code += VmCodeInstruction(Opcode.XOR, vmDt, reg1=resultRegister, reg2=regMask) code += VmCodeInstruction(Opcode.XOR, vmDt, reg1=resultRegister, reg2=regMask)
} }
"not" -> {
code += VmCodeInstruction(Opcode.NOT, vmDt, reg1=resultRegister)
}
else -> throw AssemblyError("weird prefix operator") else -> throw AssemblyError("weird prefix operator")
} }
return code return code
@@ -391,13 +388,11 @@ internal class ExpressionGen(private val codeGen: CodeGen) {
comparisonCall.children.add(binExpr.left) comparisonCall.children.add(binExpr.left)
comparisonCall.children.add(binExpr.right) comparisonCall.children.add(binExpr.right)
code += translate(comparisonCall, resultRegister, -1) code += translate(comparisonCall, resultRegister, -1)
if(notEquals) { if(!notEquals)
val maskReg = codeGen.vmRegisters.nextFree() code += VmCodeInstruction(Opcode.INV, vmDt, reg1=resultRegister)
code += VmCodeInstruction(Opcode.LOAD, vmDt, reg1=maskReg, value=1) val maskReg = codeGen.vmRegisters.nextFree()
code += VmCodeInstruction(Opcode.AND, vmDt, reg1=resultRegister, reg2=maskReg) code += VmCodeInstruction(Opcode.LOAD, vmDt, reg1=maskReg, value=1)
} else { code += VmCodeInstruction(Opcode.AND, vmDt, reg1=resultRegister, reg2=maskReg)
code += VmCodeInstruction(Opcode.NOT, vmDt, reg1=resultRegister)
}
} else { } else {
val rightResultReg = codeGen.vmRegisters.nextFree() val rightResultReg = codeGen.vmRegisters.nextFree()
code += translateExpression(binExpr.left, resultRegister, -1) code += translateExpression(binExpr.left, resultRegister, -1)

View File

@@ -80,11 +80,6 @@ class ConstantFoldingOptimizer(private val program: Program) : AstWalker() {
} }
else -> throw ExpressionError("can only take bitwise inversion of int", subexpr.position) else -> throw ExpressionError("can only take bitwise inversion of int", subexpr.position)
} }
"not" -> {
listOf(IAstModification.ReplaceNode(expr,
NumericLiteral.fromBoolean(subexpr.number == 0.0, subexpr.position),
parent))
}
else -> throw ExpressionError(expr.operator, subexpr.position) else -> throw ExpressionError(expr.operator, subexpr.position)
} }
} }

View File

@@ -108,7 +108,7 @@ class StatementOptimizer(private val program: Program,
// empty true part? switch with the else part // empty true part? switch with the else part
if(ifElse.truepart.isEmpty() && ifElse.elsepart.isNotEmpty()) { if(ifElse.truepart.isEmpty() && ifElse.elsepart.isNotEmpty()) {
val invertedCondition = PrefixExpression("not", ifElse.condition, ifElse.condition.position) val invertedCondition = BinaryExpression(ifElse.condition, "==", NumericLiteral.fromBoolean(false, ifElse.condition.position), ifElse.condition.position)
val emptyscope = AnonymousScope(mutableListOf(), ifElse.elsepart.position) val emptyscope = AnonymousScope(mutableListOf(), ifElse.elsepart.position)
val truepart = AnonymousScope(ifElse.elsepart.statements, ifElse.truepart.position) val truepart = AnonymousScope(ifElse.elsepart.statements, ifElse.truepart.position)
return listOf( return listOf(

View File

@@ -58,27 +58,6 @@ inv_word .proc
rts rts
.pend .pend
not_byte .proc
lda P8ESTACK_LO+1,x
beq +
lda #1
+ eor #1
sta P8ESTACK_LO+1,x
rts
.pend
not_word .proc
lda P8ESTACK_LO + 1,x
ora P8ESTACK_HI + 1,x
beq +
lda #1
+ eor #1
sta P8ESTACK_LO + 1,x
lsr a
sta P8ESTACK_HI + 1,x
rts
.pend
bitand_b .proc bitand_b .proc
; -- bitwise and (of 2 bytes) ; -- bitwise and (of 2 bytes)
lda P8ESTACK_LO+2,x lda P8ESTACK_LO+2,x

View File

@@ -823,10 +823,6 @@ internal class AstChecker(private val program: Program,
errors.err("can only take negative of a signed number type", expr.position) errors.err("can only take negative of a signed number type", expr.position)
} }
} }
else if(expr.operator == "not") {
if(dt !in IntegerDatatypes)
errors.err("can only use boolean not on integer types", expr.position)
}
else if(expr.operator == "~") { else if(expr.operator == "~") {
if(dt !in IntegerDatatypes) if(dt !in IntegerDatatypes)
errors.err("can only use bitwise invert on integer types", expr.position) errors.err("can only use bitwise invert on integer types", expr.position)

View File

@@ -3,6 +3,7 @@ package prog8.compiler.astprocessing
import prog8.ast.IFunctionCall import prog8.ast.IFunctionCall
import prog8.ast.Node import prog8.ast.Node
import prog8.ast.Program import prog8.ast.Program
import prog8.ast.base.FatalAstException
import prog8.ast.base.SyntaxError import prog8.ast.base.SyntaxError
import prog8.ast.expressions.* import prog8.ast.expressions.*
import prog8.ast.statements.* import prog8.ast.statements.*
@@ -116,7 +117,8 @@ class AstPreprocessor(val program: Program, val errors: IErrorReporter, val comp
override fun before(expr: PrefixExpression, parent: Node): Iterable<IAstModification> { override fun before(expr: PrefixExpression, parent: Node): Iterable<IAstModification> {
if(expr.operator == "not") { if(expr.operator == "not") {
// not(x) --> x==0 // not(x) --> x==0
val dt = expr.expression.inferType(program).getOr(DataType.UNDEFINED) // this means that "not" will never occur anywhere again in the ast
val dt = expr.expression.inferType(program).getOr(DataType.UBYTE)
val replacement = BinaryExpression(expr.expression, "==", NumericLiteral(dt,0.0, expr.position), expr.position) val replacement = BinaryExpression(expr.expression, "==", NumericLiteral(dt,0.0, expr.position), expr.position)
return listOf(IAstModification.ReplaceNodeSafe(expr, replacement, parent)) return listOf(IAstModification.ReplaceNodeSafe(expr, replacement, parent))
} }

View File

@@ -169,18 +169,6 @@ internal class BeforeAsmAstChanger(val program: Program,
} }
override fun after(ifElse: IfElse, parent: Node): Iterable<IAstModification> { override fun after(ifElse: IfElse, parent: Node): Iterable<IAstModification> {
val prefixExpr = ifElse.condition as? PrefixExpression
if(prefixExpr!=null && prefixExpr.operator=="not") {
// if not x -> if x==0
val booleanExpr = BinaryExpression(
prefixExpr.expression,
"==",
NumericLiteral.optimalInteger(0, ifElse.condition.position),
ifElse.condition.position
)
return listOf(IAstModification.ReplaceNode(ifElse.condition, booleanExpr, ifElse))
}
val binExpr = ifElse.condition as? BinaryExpression val binExpr = ifElse.condition as? BinaryExpression
if(binExpr==null || binExpr.operator !in ComparisonOperators) { if(binExpr==null || binExpr.operator !in ComparisonOperators) {
// if x -> if x!=0, if x+5 -> if x+5 != 0 // if x -> if x!=0, if x+5 -> if x+5 != 0

View File

@@ -1,10 +1,7 @@
package prog8.compiler.astprocessing package prog8.compiler.astprocessing
import prog8.ast.* import prog8.ast.*
import prog8.ast.expressions.DirectMemoryRead import prog8.ast.expressions.*
import prog8.ast.expressions.FunctionCallExpression
import prog8.ast.expressions.IdentifierReference
import prog8.ast.expressions.PrefixExpression
import prog8.ast.statements.* import prog8.ast.statements.*
import prog8.ast.walk.AstWalker import prog8.ast.walk.AstWalker
import prog8.ast.walk.IAstModification import prog8.ast.walk.IAstModification
@@ -58,16 +55,16 @@ do { STUFF } until CONDITION
===> ===>
_loop: _loop:
STUFF STUFF
if not CONDITION if CONDITION==0
goto _loop goto _loop
*/ */
val pos = untilLoop.position val pos = untilLoop.position
val loopLabel = program.makeLabel("untilloop", pos) val loopLabel = program.makeLabel("untilloop", pos)
val notCondition = PrefixExpression("not", untilLoop.condition, pos) val equalsZero = BinaryExpression(untilLoop.condition, "==", NumericLiteral.fromBoolean(false, pos), pos)
val replacement = AnonymousScope(mutableListOf( val replacement = AnonymousScope(mutableListOf(
loopLabel, loopLabel,
untilLoop.body, untilLoop.body,
IfElse(notCondition, IfElse(equalsZero,
AnonymousScope(mutableListOf(program.jumpLabel(loopLabel)), pos), AnonymousScope(mutableListOf(program.jumpLabel(loopLabel)), pos),
AnonymousScope(mutableListOf(), pos), AnonymousScope(mutableListOf(), pos),
pos) pos)
@@ -80,7 +77,7 @@ if not CONDITION
while CONDITION { STUFF } while CONDITION { STUFF }
==> ==>
_whileloop: _whileloop:
if NOT CONDITION goto _after if CONDITION==0 goto _after
STUFF STUFF
goto _whileloop goto _whileloop
_after: _after:
@@ -88,10 +85,10 @@ _after:
val pos = whileLoop.position val pos = whileLoop.position
val loopLabel = program.makeLabel("whileloop", pos) val loopLabel = program.makeLabel("whileloop", pos)
val afterLabel = program.makeLabel("afterwhile", pos) val afterLabel = program.makeLabel("afterwhile", pos)
val notCondition = PrefixExpression("not", whileLoop.condition, pos) val equalsZero = BinaryExpression(whileLoop.condition, "==", NumericLiteral.fromBoolean(false, pos), pos)
val replacement = AnonymousScope(mutableListOf( val replacement = AnonymousScope(mutableListOf(
loopLabel, loopLabel,
IfElse(notCondition, IfElse(equalsZero,
AnonymousScope(mutableListOf(program.jumpLabel(afterLabel)), pos), AnonymousScope(mutableListOf(program.jumpLabel(afterLabel)), pos),
AnonymousScope(mutableListOf(), pos), AnonymousScope(mutableListOf(), pos),
pos), pos),

View File

@@ -102,19 +102,6 @@ class TypecastsAdder(val program: Program, val options: CompilationOptions, val
return noModifications return noModifications
} }
override fun after(expr: PrefixExpression, parent: Node): Iterable<IAstModification> {
if(expr.operator=="not") {
val logical = parent as? BinaryExpression
if(logical!=null && logical.operator in LogicalOperators) {
// not x as operand in a logical expression --> cast it to ubyte
// TODO is this cast really necessary or does boolean() wrapping take care of it?
val cast = TypecastExpression(expr, DataType.UBYTE, true, expr.position)
return listOf(IAstModification.ReplaceNode(expr, cast, parent))
}
}
return noModifications
}
override fun after(assignment: Assignment, parent: Node): Iterable<IAstModification> { override fun after(assignment: Assignment, parent: Node): Iterable<IAstModification> {
// see if a typecast is needed to convert the value's type into the proper target type // see if a typecast is needed to convert the value's type into the proper target type
val valueItype = assignment.value.inferType(program) val valueItype = assignment.value.inferType(program)

View File

@@ -71,22 +71,6 @@ internal class VariousCleanups(val program: Program, val errors: IErrorReporter,
// +X --> X // +X --> X
return listOf(IAstModification.ReplaceNode(expr, expr.expression, parent)) return listOf(IAstModification.ReplaceNode(expr, expr.expression, parent))
} }
if(expr.operator=="not") {
val nestedPrefix = expr.expression as? PrefixExpression
if(nestedPrefix!=null && nestedPrefix.operator=="not") {
// NOT NOT X --> X
return listOf(IAstModification.ReplaceNode(expr, nestedPrefix.expression, parent))
}
val comparison = expr.expression as? BinaryExpression
if (comparison != null) {
// NOT COMPARISON ==> inverted COMPARISON
val invertedOperator = invertedComparisonOperator(comparison.operator)
if (invertedOperator != null) {
comparison.operator = invertedOperator
return listOf(IAstModification.ReplaceNode(expr, comparison, parent))
}
}
}
return noModifications return noModifications
} }

View File

@@ -20,181 +20,187 @@ main {
ubyte ub4 = 0 ubyte ub4 = 0
ubyte bvalue ubyte bvalue
txt.print("const not 126: ") txt.print("const not 0: ")
txt.print_ub(not 129) txt.print_ub(not 129)
txt.nl() txt.nl()
txt.print("const not 255: ") txt.print("const not 1: ")
txt.print_ub(not 0) txt.print_ub(not 0)
txt.nl() txt.nl()
txt.print("const inv 126: ")
txt.print_ub(~ 129)
txt.nl()
txt.print("const inv 255: ")
txt.print_ub(~ 0)
txt.nl()
bvalue = 129 bvalue = 129
txt.print("bitwise not 126: ") txt.print("bitwise inv 126: ")
bvalue = not bvalue bvalue = ~ bvalue
txt.print_ub(bvalue) txt.print_ub(bvalue)
txt.nl() txt.nl()
bvalue = 0 bvalue = 0
txt.print("bitwise not 255: ") txt.print("bitwise inv 255: ")
bvalue = not bvalue bvalue = ~ bvalue
txt.print_ub(bvalue) txt.print_ub(bvalue)
txt.nl() txt.nl()
; txt.print("bitwise or 14: ") txt.print("bitwise or 14: ")
; txt.print_ub(ub1 | ub2 | ub3 | ub4) txt.print_ub(ub1 | ub2 | ub3 | ub4)
; txt.nl() txt.nl()
; txt.print("bitwise or 142: ") txt.print("bitwise or 142: ")
; txt.print_ub(ub1 | ub2 | ub3 | ub4 | 128) txt.print_ub(ub1 | ub2 | ub3 | ub4 | 128)
; txt.nl() txt.nl()
; txt.print("bitwise and 0: ") txt.print("bitwise and 0: ")
; txt.print_ub(ub1 & ub2 & ub3 & ub4) txt.print_ub(ub1 & ub2 & ub3 & ub4)
; txt.nl() txt.nl()
; txt.print("bitwise and 8: ") txt.print("bitwise and 8: ")
; txt.print_ub(ub3 & ub3 & 127) txt.print_ub(ub3 & ub3 & 127)
; txt.nl() txt.nl()
; txt.print("bitwise xor 14: ") txt.print("bitwise xor 14: ")
; txt.print_ub(ub1 ^ ub2 ^ ub3 ^ ub4) txt.print_ub(ub1 ^ ub2 ^ ub3 ^ ub4)
; txt.nl() txt.nl()
; txt.print("bitwise xor 6: ") txt.print("bitwise xor 6: ")
; txt.print_ub(ub1 ^ ub2 ^ ub3 ^ 8) txt.print_ub(ub1 ^ ub2 ^ ub3 ^ 8)
; txt.nl() txt.nl()
; txt.print("bitwise not 247: ") txt.print("bitwise not 247: ")
; txt.print_ub(~ub3) txt.print_ub(~ub3)
; txt.nl() txt.nl()
; txt.print("bitwise not 255: ") txt.print("bitwise not 255: ")
; txt.print_ub(~ub4) txt.print_ub(~ub4)
; txt.nl() txt.nl()
;
; txt.print("not 0: ") txt.print("not 0: ")
; bvalue = 3 * (ub4 | not (ub3 | ub3 | ub3)) bvalue = 3 * (ub4 | not (ub3 | ub3 | ub3))
; txt.print_ub(bvalue) txt.print_ub(bvalue)
; if 3*(ub4 | not (ub1 | ub1 | ub1)) if 3*(ub4 | not (ub1 | ub1 | ub1))
; txt.print(" / fail") txt.print(" / fail")
; else else
; txt.print(" / ok") txt.print(" / ok")
; txt.nl() txt.nl()
;
; txt.print("not 0: ") txt.print("not 0: ")
; bvalue = not ub3 bvalue = not ub3
; txt.print_ub(bvalue) txt.print_ub(bvalue)
; if not ub1 if not ub1
; txt.print(" / fail") txt.print(" / fail")
; else else
; txt.print(" / ok") txt.print(" / ok")
; txt.nl() txt.nl()
;
; txt.print("not 1: ") txt.print("not 1: ")
; bvalue = not ub4 bvalue = not ub4
; txt.print_ub(bvalue) txt.print_ub(bvalue)
; if not ub4 if not ub4
; txt.print(" / ok") txt.print(" / ok")
; else else
; txt.print(" / fail") txt.print(" / fail")
; txt.nl() txt.nl()
;
; bvalue = bvalue and 128 bvalue = bvalue and 128
; txt.print("bvl 1: ") txt.print("bvl 1: ")
; txt.print_ub(bvalue) txt.print_ub(bvalue)
; if bvalue and 128 if bvalue and 128
; txt.print(" / ok") txt.print(" / ok")
; else else
; txt.print(" / fail") txt.print(" / fail")
; txt.nl() txt.nl()
;
; txt.print("and 1: ") txt.print("and 1: ")
; bvalue = ub1 and ub2 and ub3 bvalue = ub1 and ub2 and ub3
; txt.print_ub(bvalue) txt.print_ub(bvalue)
; if ub1 and ub2 and ub3 if ub1 and ub2 and ub3
; txt.print(" / ok") txt.print(" / ok")
; else else
; txt.print(" / fail") txt.print(" / fail")
; txt.nl() txt.nl()
; txt.print("and 1: ") txt.print("and 1: ")
; bvalue = ub1 and ub2 and ub3 and 64 bvalue = ub1 and ub2 and ub3 and 64
; txt.print_ub(bvalue) txt.print_ub(bvalue)
; if ub1 and ub2 and ub3 and 64 if ub1 and ub2 and ub3 and 64
; txt.print(" / ok") txt.print(" / ok")
; else else
; txt.print(" / fail") txt.print(" / fail")
; txt.nl() txt.nl()
; txt.print("and 1: ") txt.print("and 1: ")
; bvalue = ub1 and ub2 and ub3 and ftrue(99) bvalue = ub1 and ub2 and ub3 and ftrue(99)
; txt.print_ub(bvalue) txt.print_ub(bvalue)
; if ub1 and ub2 and ub3 and ftrue(99) if ub1 and ub2 and ub3 and ftrue(99)
; txt.print(" / ok") txt.print(" / ok")
; else else
; txt.print(" / fail") txt.print(" / fail")
; txt.nl() txt.nl()
; txt.print("and 0: ") txt.print("and 0: ")
; bvalue = ub1 and ub2 and ub3 and ub4 bvalue = ub1 and ub2 and ub3 and ub4
; txt.print_ub(bvalue) txt.print_ub(bvalue)
; if ub1 and ub2 and ub3 and ub4 if ub1 and ub2 and ub3 and ub4
; txt.print(" / fail") txt.print(" / fail")
; else else
; txt.print(" / ok") txt.print(" / ok")
; txt.nl() txt.nl()
; txt.print("and 0: ") txt.print("and 0: ")
; bvalue = ub1 and ub2 and ub3 and ffalse(99) bvalue = ub1 and ub2 and ub3 and ffalse(99)
; txt.print_ub(bvalue) txt.print_ub(bvalue)
; if ub1 and ub2 and ub3 and ffalse(99) if ub1 and ub2 and ub3 and ffalse(99)
; txt.print(" / fail") txt.print(" / fail")
; else else
; txt.print(" / ok") txt.print(" / ok")
; txt.nl() txt.nl()
;
; txt.print(" or 1: ") txt.print(" or 1: ")
; bvalue = ub1 or ub2 or ub3 or ub4 bvalue = ub1 or ub2 or ub3 or ub4
; txt.print_ub(bvalue) txt.print_ub(bvalue)
; if ub1 or ub2 or ub3 or ub4 if ub1 or ub2 or ub3 or ub4
; txt.print(" / ok") txt.print(" / ok")
; else else
; txt.print(" / fail") txt.print(" / fail")
; txt.nl() txt.nl()
; txt.print(" or 1: ") txt.print(" or 1: ")
; bvalue = ub4 or ub4 or ub1 bvalue = ub4 or ub4 or ub1
; txt.print_ub(bvalue) txt.print_ub(bvalue)
; if ub4 or ub4 or ub1 if ub4 or ub4 or ub1
; txt.print(" / ok") txt.print(" / ok")
; else else
; txt.print(" / fail") txt.print(" / fail")
; txt.nl() txt.nl()
; txt.print(" or 1: ") txt.print(" or 1: ")
; bvalue = ub1 or ub2 or ub3 or ftrue(99) bvalue = ub1 or ub2 or ub3 or ftrue(99)
; txt.print_ub(bvalue) txt.print_ub(bvalue)
; if ub1 or ub2 or ub3 or ftrue(99) if ub1 or ub2 or ub3 or ftrue(99)
; txt.print(" / ok") txt.print(" / ok")
; else else
; txt.print(" / fail") txt.print(" / fail")
; txt.nl() txt.nl()
;
; txt.print("xor 1: ") txt.print("xor 1: ")
; bvalue = ub1 xor ub2 xor ub3 xor ub4 bvalue = ub1 xor ub2 xor ub3 xor ub4
; txt.print_ub(bvalue) txt.print_ub(bvalue)
; if ub1 xor ub2 xor ub3 xor ub4 if ub1 xor ub2 xor ub3 xor ub4
; txt.print(" / ok") txt.print(" / ok")
; else else
; txt.print(" / fail") txt.print(" / fail")
; txt.nl() txt.nl()
; txt.print("xor 1: ") txt.print("xor 1: ")
; bvalue = ub1 xor ub2 xor ub3 xor ffalse(99) bvalue = ub1 xor ub2 xor ub3 xor ffalse(99)
; txt.print_ub(bvalue) txt.print_ub(bvalue)
; if ub1 xor ub2 xor ub3 xor ffalse(99) if ub1 xor ub2 xor ub3 xor ffalse(99)
; txt.print(" / ok") txt.print(" / ok")
; else else
; txt.print(" / fail") txt.print(" / fail")
; txt.nl() txt.nl()
;
; txt.print("xor 0: ") txt.print("xor 0: ")
; bvalue = ub1 xor ub2 xor ub3 xor ub4 xor true bvalue = ub1 xor ub2 xor ub3 xor ub4 xor true
; txt.print_ub(bvalue) txt.print_ub(bvalue)
; if ub1 xor ub2 xor ub3 xor ub4 xor true if ub1 xor ub2 xor ub3 xor ub4 xor true
; txt.print(" / fail") txt.print(" / fail")
; else else
; txt.print(" / ok") txt.print(" / ok")
; txt.nl() txt.nl()
; txt.print("xor 0: ") txt.print("xor 0: ")
; bvalue = ub1 xor ub2 xor ub3 xor ftrue(99) bvalue = ub1 xor ub2 xor ub3 xor ftrue(99)
; txt.print_ub(bvalue) txt.print_ub(bvalue)
; if ub1 xor ub2 xor ub3 xor ftrue(99) if ub1 xor ub2 xor ub3 xor ftrue(99)
; txt.print(" / fail") txt.print(" / fail")
; else else
; txt.print(" / ok") txt.print(" / ok")
} }
} }

View File

@@ -745,7 +745,7 @@ class TestProg8Parser: FunSpec( {
main { main {
ubyte bb ubyte bb
uword ww uword ww
ubyte bb2 = not bb or not ww ; expression combining ubyte and uword ubyte bb2 = (3+bb) or (3333+ww) ; expression combining ubyte and uword
} }
""") """)
val module = parseModule(src) val module = parseModule(src)

View File

@@ -109,7 +109,6 @@ class PrefixExpression(val operator: String, var expression: Expression, overrid
DataType.UWORD -> NumericLiteral(DataType.UWORD, (constval.number.toInt().inv() and 65535).toDouble(), constval.position) DataType.UWORD -> NumericLiteral(DataType.UWORD, (constval.number.toInt().inv() and 65535).toDouble(), constval.position)
else -> throw ExpressionError("can only take bitwise inversion of int", constval.position) else -> throw ExpressionError("can only take bitwise inversion of int", constval.position)
} }
"not" -> NumericLiteral.fromBoolean(constval.number == 0.0, constval.position)
else -> throw FatalAstException("invalid operator") else -> throw FatalAstException("invalid operator")
} }
converted.linkParents(this.parent) converted.linkParents(this.parent)
@@ -124,10 +123,6 @@ class PrefixExpression(val operator: String, var expression: Expression, overrid
return when(operator) { return when(operator) {
"+" -> inferred "+" -> inferred
"~", "not" -> { "~", "not" -> {
// note: "not" should ideally result in UBYTE (boolean) but the way the type system
// currently works means the result of an operator is the same type as the operand(s).
// So not(byte)->byte, not(word)->word. This is taken care of via a cast to ubyte later.
// If we give not a BYTE type here, the asmassignment validation will sometimes crash.
when(inferred.getOr(DataType.UNDEFINED)) { when(inferred.getOr(DataType.UNDEFINED)) {
in ByteDatatypes -> InferredTypes.knownFor(DataType.UBYTE) in ByteDatatypes -> InferredTypes.knownFor(DataType.UBYTE)
in WordDatatypes -> InferredTypes.knownFor(DataType.UWORD) in WordDatatypes -> InferredTypes.knownFor(DataType.UWORD)

View File

@@ -3,18 +3,22 @@ TODO
For next release For next release
^^^^^^^^^^^^^^^^ ^^^^^^^^^^^^^^^^
- 6502: fix not codegen to be bitwise not instead of boolean not (maybe need to change boolean() wrapping / variouscleanups) - chess.prg became A LOT larger, why!? (perhaps due to new while/until condition handling?)
all these testable with compiler/test/arithmetic/logical.p8 - imageviewer.prg became A LOT larger, why!?
- 6502: also fix logical and/or/xor routines to just be bitwise routines. - petaxian.prg became A LOT larger, why!?
- some programs became a bit larger since "not" was removed (assembler)
- get rid of logical and/or/xor/not in the codegen (6502+vm) - 6502: fix logical and/or/xor routines to just be bitwise routines.
- get rid of logical and/or/xor in the codegen (6502+vm)
because bitwise versions + correct use of boolean() operand wrapping are equivalent? because bitwise versions + correct use of boolean() operand wrapping are equivalent?
can do this for instance by replacing and/or/xor/not with their bitwise versions &, |, ^, ~ can do this for instance by replacing and/or/xor with their bitwise versions &, |, ^, ~
- compiling logical.p8 to virtual with optimization generates a lot larger code as without optimizations. - compiling logical.p8 to virtual with optimization generates a lot larger code as without optimizations.
this is not the case for the 6502 codegen. this is not the case for the 6502 codegen.
- add optimizations: not a or not b -> not(a and b) , not a and not b -> not(a or b) - add optimizations: not a or not b -> not(a and b) , not a and not b -> not(a or b)
actually this now means: (a==0) or (b==0) -> (a or b)==0, (a==0) and (b==0) -> (a or b)==0
add unit tests for that. add unit tests for that.
- bin expr splitter: split logical expressions on ands/ors/xors ? - bin expr splitter: split logical expressions on ands/ors/xors ?

View File

@@ -124,7 +124,7 @@ All have type b or w.
and reg1, reg2 - reg1 = reg1 bitwise and reg2 and reg1, reg2 - reg1 = reg1 bitwise and reg2
or reg1, reg2 - reg1 = reg1 bitwise or reg2 or reg1, reg2 - reg1 = reg1 bitwise or reg2
xor reg1, reg2 - reg1 = reg1 bitwise xor reg2 xor reg1, reg2 - reg1 = reg1 bitwise xor reg2
not reg1 - reg1 = bitwise not of reg1 (all bits flipped) inv reg1 - reg1 = bitwise invert of reg1 (all bits flipped)
lsrn reg1, reg2 - reg1 = multi-shift reg1 right by reg2 bits + set Carry to shifted bit lsrn reg1, reg2 - reg1 = multi-shift reg1 right by reg2 bits + set Carry to shifted bit
asrn reg1, reg2 - reg1 = multi-shift reg1 right by reg2 bits (signed) + set Carry to shifted bit asrn reg1, reg2 - reg1 = multi-shift reg1 right by reg2 bits (signed) + set Carry to shifted bit
lsln reg1, reg2 - reg1 = multi-shift reg1 left by reg2 bits + set Carry to shifted bit lsln reg1, reg2 - reg1 = multi-shift reg1 left by reg2 bits + set Carry to shifted bit
@@ -138,7 +138,7 @@ roxl reg1 - rotate reg1 left by 1 bits, using
andm reg1 address - memory = memory bitwise and reg1 andm reg1 address - memory = memory bitwise and reg1
orm reg1, address - memory = memory bitwise or reg1 orm reg1, address - memory = memory bitwise or reg1
xorm reg1, address - memory = memory bitwise xor reg1 xorm reg1, address - memory = memory bitwise xor reg1
notm address - memory = bitwise not of that memory (all bits flipped) invm address - memory = bitwise invert of that memory (all bits flipped)
lsrnm reg1, address - multi-shift memoryright by reg1 bits + set Carry to shifted bit lsrnm reg1, address - multi-shift memoryright by reg1 bits + set Carry to shifted bit
asrnm reg1, address - multi-shift memory right by reg1 bits (signed) + set Carry to shifted bit asrnm reg1, address - multi-shift memory right by reg1 bits (signed) + set Carry to shifted bit
lslnm reg1, address - multi-shift memory left by reg1 bits + set Carry to shifted bit lslnm reg1, address - multi-shift memory left by reg1 bits + set Carry to shifted bit
@@ -260,8 +260,8 @@ enum class Opcode {
ORM, ORM,
XOR, XOR,
XORM, XORM,
NOT, INV,
NOTM, INVM,
ASRN, ASRN,
ASRNM, ASRNM,
LSRN, LSRN,
@@ -330,7 +330,7 @@ val OpcodesWithAddress = setOf(
Opcode.MULM, Opcode.MULM,
Opcode.DIVM, Opcode.DIVM,
Opcode.DIVSM, Opcode.DIVSM,
Opcode.NOTM, Opcode.INVM,
Opcode.ORM, Opcode.ORM,
Opcode.XORM, Opcode.XORM,
Opcode.ANDM, Opcode.ANDM,
@@ -556,8 +556,8 @@ val instructionFormats = mutableMapOf(
Opcode.ORM to InstructionFormat.from("BW,r1,v"), Opcode.ORM to InstructionFormat.from("BW,r1,v"),
Opcode.XOR to InstructionFormat.from("BW,r1,r2"), Opcode.XOR to InstructionFormat.from("BW,r1,r2"),
Opcode.XORM to InstructionFormat.from("BW,r1,v"), Opcode.XORM to InstructionFormat.from("BW,r1,v"),
Opcode.NOT to InstructionFormat.from("BW,r1"), Opcode.INV to InstructionFormat.from("BW,r1"),
Opcode.NOTM to InstructionFormat.from("BW,v"), Opcode.INVM to InstructionFormat.from("BW,v"),
Opcode.ASRN to InstructionFormat.from("BW,r1,r2"), Opcode.ASRN to InstructionFormat.from("BW,r1,r2"),
Opcode.ASRNM to InstructionFormat.from("BW,r1,v"), Opcode.ASRNM to InstructionFormat.from("BW,r1,v"),
Opcode.LSRN to InstructionFormat.from("BW,r1,r2"), Opcode.LSRN to InstructionFormat.from("BW,r1,r2"),

View File

@@ -162,8 +162,8 @@ class VirtualMachine(val memory: Memory, program: List<Instruction>) {
Opcode.ORM -> InsORM(ins) Opcode.ORM -> InsORM(ins)
Opcode.XOR -> InsXOR(ins) Opcode.XOR -> InsXOR(ins)
Opcode.XORM ->InsXORM(ins) Opcode.XORM ->InsXORM(ins)
Opcode.NOT -> InsNOT(ins) Opcode.INV -> InsINV(ins)
Opcode.NOTM -> InsNOTM(ins) Opcode.INVM -> InsINVM(ins)
Opcode.ASRN -> InsASRN(ins) Opcode.ASRN -> InsASRN(ins)
Opcode.LSRN -> InsLSRN(ins) Opcode.LSRN -> InsLSRN(ins)
Opcode.LSLN -> InsLSLN(ins) Opcode.LSLN -> InsLSLN(ins)
@@ -1216,7 +1216,7 @@ class VirtualMachine(val memory: Memory, program: List<Instruction>) {
pc++ pc++
} }
private fun InsNOT(i: Instruction) { private fun InsINV(i: Instruction) {
when(i.type!!) { when(i.type!!) {
VmDataType.BYTE -> registers.setUB(i.reg1!!, registers.getUB(i.reg1).inv()) VmDataType.BYTE -> registers.setUB(i.reg1!!, registers.getUB(i.reg1).inv())
VmDataType.WORD -> registers.setUW(i.reg1!!, registers.getUW(i.reg1).inv()) VmDataType.WORD -> registers.setUW(i.reg1!!, registers.getUW(i.reg1).inv())
@@ -1225,7 +1225,7 @@ class VirtualMachine(val memory: Memory, program: List<Instruction>) {
pc++ pc++
} }
private fun InsNOTM(i: Instruction) { private fun InsINVM(i: Instruction) {
val address = i.value!! val address = i.value!!
when(i.type!!) { when(i.type!!) {
VmDataType.BYTE -> memory.setUB(address, memory.getUB(address).inv()) VmDataType.BYTE -> memory.setUB(address, memory.getUB(address).inv())