added clamp() builtin function and floats.clampf()

This commit is contained in:
Irmen de Jong 2023-05-17 23:03:59 +02:00
parent e243531dab
commit b43223cb7a
21 changed files with 386 additions and 27 deletions

View File

@ -99,8 +99,10 @@ val BuiltinFunctions: Map<String, FSignature> = mapOf(
"lsb" to FSignature(true, listOf(FParam("value", arrayOf(DataType.UWORD, DataType.WORD))), DataType.UBYTE),
"msb" to FSignature(true, listOf(FParam("value", arrayOf(DataType.UWORD, DataType.WORD))), DataType.UBYTE),
"mkword" to FSignature(true, listOf(FParam("msb", arrayOf(DataType.UBYTE)), FParam("lsb", arrayOf(DataType.UBYTE))), DataType.UWORD),
"min" to FSignature(true, listOf(FParam("value", NumericDatatypesNoBool)), null),
"max" to FSignature(true, listOf(FParam("value", NumericDatatypesNoBool)), null),
"clamp__byte" to FSignature(true, listOf(FParam("value", arrayOf(DataType.BYTE)), FParam("minimum", arrayOf(DataType.BYTE)), FParam("maximum", arrayOf(DataType.BYTE))), DataType.BYTE),
"clamp__ubyte" to FSignature(true, listOf(FParam("value", arrayOf(DataType.UBYTE)), FParam("minimum", arrayOf(DataType.UBYTE)), FParam("maximum", arrayOf(DataType.UBYTE))), DataType.UBYTE),
"clamp__word" to FSignature(true, listOf(FParam("value", arrayOf(DataType.WORD)), FParam("minimum", arrayOf(DataType.WORD)), FParam("maximum", arrayOf(DataType.WORD))), DataType.WORD),
"clamp__uword" to FSignature(true, listOf(FParam("value", arrayOf(DataType.UWORD)), FParam("minimum", arrayOf(DataType.UWORD)), FParam("maximum", arrayOf(DataType.UWORD))), DataType.UWORD),
"min__byte" to FSignature(true, listOf(FParam("val1", arrayOf(DataType.BYTE)), FParam("val2", arrayOf(DataType.BYTE))), DataType.BYTE),
"min__ubyte" to FSignature(true, listOf(FParam("val1", arrayOf(DataType.UBYTE)), FParam("val2", arrayOf(DataType.UBYTE))), DataType.UBYTE),
"min__word" to FSignature(true, listOf(FParam("val1", arrayOf(DataType.WORD)), FParam("val2", arrayOf(DataType.WORD))), DataType.WORD),

View File

@ -31,6 +31,7 @@ internal class BuiltinFunctionsAsmGen(private val program: PtProgram,
"msb" -> funcMsb(fcall, resultToStack, resultRegister)
"lsb" -> funcLsb(fcall, resultToStack, resultRegister)
"mkword" -> funcMkword(fcall, resultToStack, resultRegister)
"clamp__byte", "clamp__ubyte", "clamp__word", "clamp__uword" -> funcClamp(fcall, resultToStack, resultRegister)
"min__byte", "min__ubyte", "min__word", "min__uword" -> funcMin(fcall, resultToStack, resultRegister)
"max__byte", "max__ubyte", "max__word", "max__uword" -> funcMax(fcall, resultToStack, resultRegister)
"abs__byte", "abs__word", "abs__float" -> funcAbs(fcall, resultToStack, resultRegister, sscope)
@ -860,6 +861,37 @@ internal class BuiltinFunctionsAsmGen(private val program: PtProgram,
}
}
private fun funcClamp(fcall: PtBuiltinFunctionCall, resultToStack: Boolean, resultRegister: RegisterOrPair?) {
val signed = fcall.type in SignedDatatypes
when(fcall.type) {
in ByteDatatypes -> {
assignAsmGen.assignExpressionToVariable(fcall.args[1], "P8ZP_SCRATCH_W1", fcall.args[1].type) // minimum
assignAsmGen.assignExpressionToVariable(fcall.args[2], "P8ZP_SCRATCH_W1+1", fcall.args[2].type) // maximum
assignAsmGen.assignExpressionToRegister(fcall.args[0], RegisterOrPair.A, signed) // value
asmgen.out(" jsr prog8_lib.func_clamp_${fcall.type.toString().lowercase()}")
if(resultToStack) {
asmgen.out(" sta P8ESTACK_LO,x | dex")
} else {
val targetReg = AsmAssignTarget.fromRegisters(resultRegister!!, signed, fcall.position, fcall.definingISub(), asmgen)
assignAsmGen.assignRegisterByte(targetReg, CpuRegister.A, signed)
}
}
in WordDatatypes -> {
assignAsmGen.assignExpressionToVariable(fcall.args[1], "P8ZP_SCRATCH_W1", fcall.args[1].type) // minimum
assignAsmGen.assignExpressionToVariable(fcall.args[2], "P8ZP_SCRATCH_W2", fcall.args[2].type) // maximum
assignAsmGen.assignExpressionToRegister(fcall.args[0], RegisterOrPair.AY, signed) // value
asmgen.out(" jsr prog8_lib.func_clamp_${fcall.type.toString().lowercase()}")
if(resultToStack) {
asmgen.out(" sta P8ESTACK_LO,x | sty P8ESTACK_HI,x | dex")
} else {
val targetReg = AsmAssignTarget.fromRegisters(resultRegister!!, signed, fcall.position, fcall.definingISub(), asmgen)
assignAsmGen.assignRegisterpairWord(targetReg, RegisterOrPair.AY)
}
}
else -> throw AssemblyError("invalid dt")
}
}
private fun funcMin(fcall: PtBuiltinFunctionCall, resultToStack: Boolean, resultRegister: RegisterOrPair?) {
val signed = fcall.type in SignedDatatypes
if(fcall.type in ByteDatatypes) {

View File

@ -38,6 +38,7 @@ internal class BuiltinFuncGen(private val codeGen: IRCodeGen, private val exprGe
"pokew" -> funcPokeW(call)
"pokemon" -> ExpressionCodeResult.EMPTY // easter egg function
"mkword" -> funcMkword(call)
"clamp__byte", "clamp__ubyte", "clamp__word", "clamp__uword" -> funcClamp(call)
"min__byte", "min__ubyte", "min__word", "min__uword" -> funcMin(call)
"max__byte", "max__ubyte", "max__word", "max__uword" -> funcMax(call)
"sort" -> funcSort(call)
@ -324,6 +325,42 @@ internal class BuiltinFuncGen(private val codeGen: IRCodeGen, private val exprGe
return ExpressionCodeResult(result, IRDataType.WORD, lsbTr.resultReg, -1)
}
private fun funcClamp(call: PtBuiltinFunctionCall): ExpressionCodeResult {
val result = mutableListOf<IRCodeChunkBase>()
val type = irType(call.type)
val valueTr = exprGen.translateExpression(call.args[0])
val minimumTr = exprGen.translateExpression(call.args[1])
val maximumTr = exprGen.translateExpression(call.args[2])
result += valueTr.chunks
result += minimumTr.chunks
result += maximumTr.chunks
if(type==IRDataType.FLOAT) {
result += codeGen.makeSyscall(
IMSyscall.CLAMP_FLOAT, listOf(
valueTr.dt to valueTr.resultFpReg,
minimumTr.dt to minimumTr.resultFpReg,
maximumTr.dt to maximumTr.resultFpReg,
), type to valueTr.resultFpReg
)
return ExpressionCodeResult(result, type, -1, valueTr.resultFpReg)
} else {
val syscall = when(call.type) {
DataType.UBYTE -> IMSyscall.CLAMP_UBYTE
DataType.BYTE -> IMSyscall.CLAMP_BYTE
DataType.UWORD -> IMSyscall.CLAMP_UWORD
DataType.WORD -> IMSyscall.CLAMP_WORD
else -> throw AssemblyError("invalid dt")
}
result += codeGen.makeSyscall(syscall, listOf(
valueTr.dt to valueTr.resultReg,
minimumTr.dt to minimumTr.resultReg,
maximumTr.dt to maximumTr.resultReg,
), type to valueTr.resultReg
)
return ExpressionCodeResult(result, type, valueTr.resultReg, -1)
}
}
private fun funcMin(call: PtBuiltinFunctionCall): ExpressionCodeResult {
val type = irType(call.type)
val result = mutableListOf<IRCodeChunkBase>()

View File

@ -1212,7 +1212,7 @@ class IRCodeGen(
val afterIfLabel = createLabelName()
addInstr(
result,
IRInstruction(elseBranch, IRDataType.BYTE, reg1 = compResultReg, labelSymbol = elseLabel),
IRInstruction(elseBranch, IRDataType.BYTE, reg1 = compResultReg, immediate = 0, labelSymbol = elseLabel),
null
)
result += translateNode(ifElse.ifScope)
@ -1224,7 +1224,7 @@ class IRCodeGen(
val afterIfLabel = createLabelName()
addInstr(
result,
IRInstruction(elseBranch, IRDataType.BYTE, reg1 = compResultReg, labelSymbol = afterIfLabel),
IRInstruction(elseBranch, IRDataType.BYTE, reg1 = compResultReg, immediate = 0, labelSymbol = afterIfLabel),
null
)
result += translateNode(ifElse.ifScope)

View File

@ -72,7 +72,24 @@ class VarConstantValueTypeAdjuster(private val program: Program, private val err
override fun after(functionCallExpr: FunctionCallExpression, parent: Node): Iterable<IAstModification> {
// choose specific builtin function for the given types
val func = functionCallExpr.target.nameInSource
if(func==listOf("min") || func==listOf("max")) {
if(func==listOf("clamp")) {
val t1 = functionCallExpr.args[0].inferType(program)
if(t1.isKnown) {
val replaceFunc: String
if(t1.isBytes) {
replaceFunc = if(t1.istype(DataType.BYTE)) "clamp__byte" else "clamp__ubyte"
} else if(t1.isInteger) {
replaceFunc = if(t1.istype(DataType.WORD)) "clamp__word" else "clamp__uword"
} else {
errors.err("clamp builtin not supported for floats, use floats.clamp", functionCallExpr.position)
return noModifications
}
return listOf(IAstModification.SetExpression({functionCallExpr.target = it as IdentifierReference},
IdentifierReference(listOf(replaceFunc), functionCallExpr.target.position),
functionCallExpr))
}
}
else if(func==listOf("min") || func==listOf("max")) {
val t1 = functionCallExpr.args[0].inferType(program)
val t2 = functionCallExpr.args[1].inferType(program)
if(t1.isKnown && t2.isKnown) {

View File

@ -227,4 +227,13 @@ sub maxf(float f1, float f2) -> float {
return f2
}
sub clampf(float value, float minimum, float maximum) -> float {
if value>maximum
value=maximum
if value>minimum
return value
return minimum
}
}

View File

@ -555,3 +555,111 @@ func_pokew .proc
sta (P8ZP_SCRATCH_W1),y
rts
.pend
func_clamp_byte .proc
; signed value in A, result in A
; minimum in P8ZP_SCRATCH_W1
; maximum in P8ZP_SCRATCH_W1+1
tay
sec
sbc P8ZP_SCRATCH_W1+1
bvc +
eor #$80
+ bmi +
lda P8ZP_SCRATCH_W1+1
tay
jmp ++
+ tya
+ sec
sbc P8ZP_SCRATCH_W1
bvc +
eor #$80
+ bmi +
tya
rts
+ lda P8ZP_SCRATCH_W1
rts
.pend
func_clamp_ubyte .proc
; value in A, result in A
; minimum in P8ZP_SCRATCH_W1
; maximum in P8ZP_SCRATCH_W1+1
cmp P8ZP_SCRATCH_W1+1
bcc +
lda P8ZP_SCRATCH_W1+1
+ cmp P8ZP_SCRATCH_W1
bcc +
rts
+ lda P8ZP_SCRATCH_W1
rts
.pend
func_clamp_word .proc
; signed value in AY, result in AY
; minimum in P8ZP_SCRATCH_W1
; maximum in P8ZP_SCRATCH_W2
sta P8ZP_SCRATCH_B1
sty P8ZP_SCRATCH_REG
ldy P8ZP_SCRATCH_W2+1
lda P8ZP_SCRATCH_W2
cmp P8ZP_SCRATCH_B1
tya
sbc P8ZP_SCRATCH_REG
bvc +
eor #$80
+ bpl +
lda P8ZP_SCRATCH_W2
ldy P8ZP_SCRATCH_W2+1
sta P8ZP_SCRATCH_B1
sty P8ZP_SCRATCH_REG
+ ldy P8ZP_SCRATCH_W1+1
lda P8ZP_SCRATCH_W1
cmp P8ZP_SCRATCH_B1
tya
sbc P8ZP_SCRATCH_REG
bvc +
eor #$80
+ bpl +
ldy P8ZP_SCRATCH_REG
lda P8ZP_SCRATCH_B1
rts
+ ldy P8ZP_SCRATCH_W1+1
lda P8ZP_SCRATCH_W1
rts
.pend
func_clamp_uword .proc
; value in AY, result in AY
; minimum in P8ZP_SCRATCH_W1
; maximum in P8ZP_SCRATCH_W2
sta P8ZP_SCRATCH_B1
sty P8ZP_SCRATCH_REG
cpy P8ZP_SCRATCH_W2+1
bcc ++
bne +
cmp P8ZP_SCRATCH_W2
bcc ++
+ beq +
lda P8ZP_SCRATCH_W2
ldy P8ZP_SCRATCH_W2+1
sta P8ZP_SCRATCH_B1
sty P8ZP_SCRATCH_REG
+ ldy P8ZP_SCRATCH_REG
lda P8ZP_SCRATCH_B1
cpy P8ZP_SCRATCH_W1+1
bcc ++
bne +
cmp P8ZP_SCRATCH_W1
bcc ++
+ beq +
ldy P8ZP_SCRATCH_REG
lda P8ZP_SCRATCH_B1
rts
+ ldy P8ZP_SCRATCH_W1+1
lda P8ZP_SCRATCH_W1
rts
.pend

View File

@ -123,4 +123,13 @@ sub rndseedf(float seed) {
}}
}
sub clampf(float value, float minimum, float maximum) -> float {
if value<minimum
value=minimum
if value<maximum
return value
return maximum
}
}

View File

@ -24,6 +24,10 @@ internal val constEvaluatorsForBuiltinFuncs: Map<String, ConstExpressionCaller>
"lsb" to { a, p, prg -> oneIntArgOutputInt(a, p, prg) { x: Int -> (x and 255).toDouble() } },
"msb" to { a, p, prg -> oneIntArgOutputInt(a, p, prg) { x: Int -> (x ushr 8 and 255).toDouble()} },
"mkword" to ::builtinMkword,
"clamp__ubyte" to ::builtinClampUByte,
"clamp__byte" to ::builtinClampByte,
"clamp__uword" to ::builtinClampUWord,
"clamp__word" to ::builtinClampWord,
"min__ubyte" to ::builtinMinUByte,
"min__byte" to ::builtinMinByte,
"min__uword" to ::builtinMinUWord,
@ -245,3 +249,44 @@ private fun builtinMaxUWord(args: List<Expression>, position: Position, program:
val result = max(val1.number.toInt(), val2.number.toInt())
return NumericLiteral(DataType.UWORD, result.toDouble(), position)
}
private fun builtinClampUByte(args: List<Expression>, position: Position, program: Program): NumericLiteral {
if(args.size!=3)
throw SyntaxError("clamp requires 3 arguments", position)
val value = args[0].constValue(program) ?: throw NotConstArgumentException()
val minimum = args[1].constValue(program) ?: throw NotConstArgumentException()
val maximum = args[2].constValue(program) ?: throw NotConstArgumentException()
val result = min(max(value.number, minimum.number), maximum.number)
return NumericLiteral(DataType.UBYTE, result, position)
}
private fun builtinClampByte(args: List<Expression>, position: Position, program: Program): NumericLiteral {
if(args.size!=3)
throw SyntaxError("clamp requires 3 arguments", position)
val value = args[0].constValue(program) ?: throw NotConstArgumentException()
val minimum = args[1].constValue(program) ?: throw NotConstArgumentException()
val maximum = args[2].constValue(program) ?: throw NotConstArgumentException()
val result = min(max(value.number, minimum.number), maximum.number)
return NumericLiteral(DataType.BYTE, result, position)
}
private fun builtinClampUWord(args: List<Expression>, position: Position, program: Program): NumericLiteral {
if(args.size!=3)
throw SyntaxError("clamp requires 3 arguments", position)
val value = args[0].constValue(program) ?: throw NotConstArgumentException()
val minimum = args[1].constValue(program) ?: throw NotConstArgumentException()
val maximum = args[2].constValue(program) ?: throw NotConstArgumentException()
val result = min(max(value.number, minimum.number), maximum.number)
return NumericLiteral(DataType.UWORD, result, position)
}
private fun builtinClampWord(args: List<Expression>, position: Position, program: Program): NumericLiteral {
if(args.size!=3)
throw SyntaxError("clamp requires 3 arguments", position)
val value = args[0].constValue(program) ?: throw NotConstArgumentException()
val minimum = args[1].constValue(program) ?: throw NotConstArgumentException()
val maximum = args[2].constValue(program) ?: throw NotConstArgumentException()
val result = min(max(value.number, minimum.number), maximum.number)
return NumericLiteral(DataType.WORD, result, position)
}

View File

@ -261,6 +261,9 @@ point variables. This includes ``print_f``, the routine used to print floating
``maxf (x, y)``
returns the largest of x and y.
``clampf (value, minimum, maximum)``
returns the value restricted to the given minimum and maximum.
``print_f (x)``
prints the floating point number x as a string.

View File

@ -759,7 +759,11 @@ min (x, y)
Returns the smallest of x and y. Supported for integer types only, for floats use ``floats.minf()`` instead.
max (x, y)
Returns the largest of x and y. Supported for integer types only, for floats use ``floats.maxf()`` instead.
Returns the largest of x and y. Supported for integer types only, for floats use ``floats.maxf()`` instead.
clamp (value, minimum, maximum)
Returns the value restricted to the given minimum and maximum.
Supported for integer types only, for floats use ``floats.clampf()`` instead.
sgn (x)
Get the sign of the value. Result is -1, 0 or 1 (negative, zero, positive).

View File

@ -4,7 +4,8 @@ TODO
For 9.0 major changes
^^^^^^^^^^^^^^^^^^^^^
- DONE: added 'cbm' block in the syslib module that now contains all CBM compatible kernal routines and variables
- DONE: added min() max() builtin functions
- DONE: added min(), max() builtin functions. For floats, use floats.minf() and floats.maxf().
- DONE: added clamp(value, minimum, maximum) to restrict a value x to a minimum and maximum value. For floats, use floats.clampf(f, minv, maxv).
- DONE: rename sqrt16() to just sqrt(), make it accept multiple numeric types including float. Removed floats.sqrt().
- DONE: abs() now supports multiple datatypes including float. Removed floats.fabs().
- DONE: divmod() now supports multiple datatypes. divmodw() has been removed.
@ -13,7 +14,9 @@ For 9.0 major changes
- DONE: for loops now skip the whole loop if from value already outside the loop range (this is what all other programming languages also do)
- DONE: asmsub params or return values passed in cpu flags (like carry) now must be declared as booleans (previously ubyte was still accepted).
- once 9.0 is stable, upgrade other programs (assem, shell, etc) to it. + add migration guide to the manual.
TODO: test min/max, floats.minf/maxf on all compiler targets
- [much work:] add special (u)word array type (or modifier such as @fast? ) that puts the array into memory as 2 separate byte-arrays 1 for LSB 1 for MSB -> allows for word arrays of length 256 and faster indexing
this is an enormous amout of work, if this type is to be treated equally as existing (u)word , because all expression / lookup / assignment routines need to know about the distinction....
So maybe only allow the bare essentials? (store, get, bitwise operations?)

View File

@ -4,8 +4,8 @@ Upgrading from version 8
How to upgrade older programs written for Prog8 version 8 or earlier to version 9.
cx16diskio -> diskio
^^^^^^^^^^^^^^^^^^^^
``cx16diskio`` is now just ``diskio``
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
The ``cx16diskio`` module is gone, just use ``diskio``. The drivenumber is no longer a parameter on all routines.
@ -16,8 +16,8 @@ The ``cx16diskio`` module is gone, just use ``diskio``. The drivenumber is no lo
and then call the load routine normally.
@Pc now ``bool``
^^^^^^^^^^^^^^^^
@Pc param and return value is now always ``bool``
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Parameters and return values passed via the carry status flag (@Pc) now need to be declared as ``bool``.
(Previously also ``ubyte`` was allowed but as the value is just a single bit, this wasn't really correct)
@ -52,10 +52,10 @@ divmod(), sqrt() and abs() builtin functions accept multiple data types
- ``floats.fabs()`` and ``floats.sqrt()`` don't exist anymore, just use ``abs()`` and ``sqrt()`` they now accept floating point as well.
min() and max() are new builtin functions
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
If you used symbols named ``min`` or ``max`` you have to choose a new name as these are now
reserved for the two new builtin functions.
min(), max() and clamp() are new builtin functions
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
If you used symbols named ``min`` or ``max`` or ``clamp``, you have to choose a new name as these are now
reserved for these new builtin functions.
Code that uses an if statement and a comparison to determine the greater or lesser of two values,
can now be optimized by just using one of these new builtin functions.
For floats, use ``floats.minf()``, ``floats.maxf()`` and ``floats.clampf()``.

View File

@ -6,16 +6,42 @@ main {
sub start() {
word ww = -1234
uword uww = 1234
float fl = 123.34
byte bb = -99
byte bb = -123
ubyte ub = 123
txt.print_w(abs(ww))
txt.print_w(clamp(ww, -2000, -500))
txt.spc()
txt.print_w(clamp(ww, -1000, -500))
txt.spc()
txt.print_w(clamp(ww, -2000, -1500))
txt.nl()
txt.print_b(abs(bb))
txt.print_uw(clamp(uww, 500, 2000))
txt.spc()
txt.print_uw(clamp(uww, 500, 1000))
txt.spc()
txt.print_uw(clamp(uww, 1500, 2000))
txt.nl()
floats.print_f(abs(fl))
txt.print_b(clamp(bb, -127, -50))
txt.spc()
txt.print_b(clamp(bb, -100, -50))
txt.spc()
txt.print_b(clamp(bb, -127, -125))
txt.nl()
floats.print_f(sqrt(fl))
txt.print_ub(clamp(ub, 50, 200))
txt.spc()
txt.print_ub(clamp(ub, 50, 100))
txt.spc()
txt.print_ub(clamp(ub, 150, 200))
txt.nl()
floats.print_f(floats.clampf(fl, 50.0, 200.0))
txt.spc()
floats.print_f(floats.clampf(fl, 50.0, 100.0))
txt.spc()
floats.print_f(floats.clampf(fl, 150.0, 200.0))
txt.nl()
}
}

View File

@ -21,5 +21,10 @@ enum class IMSyscall(val number: Int) {
COMPARE_STRINGS(0x100d),
STRING_CONTAINS(0x100e),
BYTEARRAY_CONTAINS(0x100f),
WORDARRAY_CONTAINS(0x1010)
WORDARRAY_CONTAINS(0x1010),
CLAMP_UBYTE(0x1011),
CLAMP_BYTE(0x1012),
CLAMP_UWORD(0x1013),
CLAMP_WORD(0x1014),
CLAMP_FLOAT(0x1015)
}

View File

@ -714,6 +714,13 @@ data class IRInstruction(
}
}
}
if(format.immediate) {
if(opcode==Opcode.LOAD)
require(immediate != null || immediateFp != null || labelSymbol!=null) { "missing immediate value or labelsymbol" }
else
require(immediate != null || immediateFp != null) { "missing immediate value" }
}
reg1direction = format.reg1
reg2direction = format.reg2
fpReg1direction = format.fpReg1

View File

@ -14,7 +14,7 @@
<keywords keywords="&amp;;-&gt;;@;and;as;asmsub;break;clobbers;do;downto;else;false;for;goto;if;if_cc;if_cs;if_eq;if_mi;if_ne;if_neg;if_nz;if_pl;if_pos;if_vc;if_vs;if_z;in;inline;not;or;repeat;return;romsub;step;sub;to;true;unroll;until;when;while;xor;~" ignore_case="false" />
<keywords2 keywords="%address;%asm;%asmbinary;%asminclude;%breakpoint;%import;%ir;%launcher;%option;%output;%zeropage;%zpreserved;iso:;petscii:;sc:" />
<keywords3 keywords="@requirezp;@shared;@zp;bool;byte;const;float;str;ubyte;uword;void;word" />
<keywords4 keywords="abs;all;any;callfar;callram;callrom;cmp;divmod;len;lsb;max;memory;min;mkword;msb;peek;peekw;poke;pokew;pop;popw;push;pushw;reverse;rol;rol2;ror;ror2;rrestore;rrestorex;rsave;rsavex;sgn;sizeof;sort;sqrt;sqrt16;swap;|&gt;" />
<keywords4 keywords="abs;all;any;callfar;callram;callrom;clamp;cmp;divmod;len;lsb;max;memory;min;mkword;msb;peek;peekw;poke;pokew;pop;popw;push;pushw;reverse;rol;rol2;ror;ror2;rrestore;rrestorex;rsave;rsavex;sgn;sizeof;sort;sqrt;sqrt16;swap;|&gt;" />
</highlighting>
<extensionMap>
<mapping ext="p8" />

View File

@ -27,7 +27,7 @@
<Keywords name="Keywords1">void const&#x000D;&#x000A;str&#x000D;&#x000A;byte ubyte bool&#x000D;&#x000A;word uword&#x000D;&#x000A;float&#x000D;&#x000A;zp shared requirezp</Keywords>
<Keywords name="Keywords2">%address&#x000D;&#x000A;%asm&#x000D;&#x000A;%ir&#x000D;&#x000A;%asmbinary&#x000D;&#x000A;%asminclude&#x000D;&#x000A;%breakpoint&#x000D;&#x000A;%import&#x000D;&#x000A;%launcher&#x000D;&#x000A;%option&#x000D;&#x000A;%output&#x000D;&#x000A;%zeropage&#x000D;&#x000A;%zpreserved</Keywords>
<Keywords name="Keywords3">inline sub asmsub romsub&#x000D;&#x000A;clobbers&#x000D;&#x000A;asm&#x000D;&#x000A;if&#x000D;&#x000A;when else&#x000D;&#x000A;if_cc if_cs if_eq if_mi if_neg if_nz if_pl if_pos if_vc if_vs if_z&#x000D;&#x000A;for in step do while repeat unroll&#x000D;&#x000A;break return goto</Keywords>
<Keywords name="Keywords4">abs all any callfar cmp divmod len lsb lsl lsr memory mkword min max msb peek peekw poke pokew push pushw pop popw rsave rsavex rrestore rrestorex reverse rnd rndw rol rol2 ror ror2 sgn sizeof sort sqrtw swap</Keywords>
<Keywords name="Keywords4">abs all any callfar clamp cmp divmod len lsb lsl lsr memory mkword min max msb peek peekw poke pokew push pushw pop popw rsave rsavex rrestore rrestorex reverse rnd rndw rol rol2 ror ror2 sgn sizeof sort sqrtw swap</Keywords>
<Keywords name="Keywords5">true false&#x000D;&#x000A;not and or xor&#x000D;&#x000A;as to downto |&gt;</Keywords>
<Keywords name="Keywords6"></Keywords>
<Keywords name="Keywords7"></Keywords>

View File

@ -15,7 +15,7 @@ syn keyword prog8BuiltInFunc any all len reverse sort
" Miscellaneous functions
syn keyword prog8BuiltInFunc cmp divmod lsb msb mkword min max peek peekw poke pokew push pushw pop popw rsave rsavex rrestore rrestorex
syn keyword prog8BuiltInFunc rol rol2 ror ror2 sizeof
syn keyword prog8BuiltInFunc swap memory callfar
syn keyword prog8BuiltInFunc swap memory callfar clamp
" c64/floats.p8

View File

@ -3,6 +3,7 @@ package prog8.vm
import prog8.code.core.AssemblyError
import prog8.intermediate.FunctionCallArgs
import prog8.intermediate.IRDataType
import kotlin.math.max
import kotlin.math.min
/*
@ -82,7 +83,13 @@ enum class Syscall {
RNDF,
STRING_CONTAINS,
BYTEARRAY_CONTAINS,
WORDARRAY_CONTAINS;
WORDARRAY_CONTAINS,
CLAMP_BYTE,
CLAMP_UBYTE,
CLAMP_WORD,
CLAMP_UWORD,
CLAMP_FLOAT
;
companion object {
private val VALUES = values()
@ -413,6 +420,46 @@ object SysCalls {
}
returnValue(callspec.returns!!, 0u, vm)
}
Syscall.CLAMP_BYTE -> {
val (valueU, minimumU, maximumU) = getArgValues(callspec.arguments, vm)
val value = (valueU as UByte).toByte().toInt()
val minimum = (minimumU as UByte).toByte().toInt()
val maximum = (maximumU as UByte).toByte().toInt()
val result = min(max(value, minimum), maximum)
returnValue(callspec.returns!!, result, vm)
}
Syscall.CLAMP_UBYTE -> {
val (valueU, minimumU, maximumU) = getArgValues(callspec.arguments, vm)
val value = (valueU as UByte).toInt()
val minimum = (minimumU as UByte).toInt()
val maximum = (maximumU as UByte).toInt()
val result = min(max(value, minimum), maximum)
returnValue(callspec.returns!!, result, vm)
}
Syscall.CLAMP_WORD -> {
val (valueU, minimumU, maximumU) = getArgValues(callspec.arguments, vm)
val value = (valueU as UShort).toShort().toInt()
val minimum = (minimumU as UShort).toShort().toInt()
val maximum = (maximumU as UShort).toShort().toInt()
val result = min(max(value, minimum), maximum)
returnValue(callspec.returns!!, result, vm)
}
Syscall.CLAMP_UWORD -> {
val (valueU, minimumU, maximumU) = getArgValues(callspec.arguments, vm)
val value = (valueU as UShort).toInt()
val minimum = (minimumU as UShort).toInt()
val maximum = (maximumU as UShort).toInt()
val result = min(max(value, minimum), maximum)
returnValue(callspec.returns!!, result, vm)
}
Syscall.CLAMP_FLOAT -> {
val (valueU, minimumU, maximumU) = getArgValues(callspec.arguments, vm)
val value = (valueU as Float)
val minimum = (minimumU as Float)
val maximum = (maximumU as Float)
val result = min(max(value, minimum), maximum)
returnValue(callspec.returns!!, result, vm)
}
else -> throw AssemblyError("missing syscall ${call.name}")
}
}

View File

@ -118,6 +118,11 @@ class VmProgramLoader {
IMSyscall.STRING_CONTAINS.number -> Syscall.STRING_CONTAINS
IMSyscall.BYTEARRAY_CONTAINS.number -> Syscall.BYTEARRAY_CONTAINS
IMSyscall.WORDARRAY_CONTAINS.number -> Syscall.WORDARRAY_CONTAINS
IMSyscall.CLAMP_BYTE.number -> Syscall.CLAMP_BYTE
IMSyscall.CLAMP_UBYTE.number -> Syscall.CLAMP_UBYTE
IMSyscall.CLAMP_WORD.number -> Syscall.CLAMP_WORD
IMSyscall.CLAMP_UWORD.number -> Syscall.CLAMP_UWORD
IMSyscall.CLAMP_FLOAT.number -> Syscall.CLAMP_FLOAT
else -> null
}