;KeyMacs.src by James Newton
;Structured programming and memory management macros and layout for the SXKey
;Copyright 2000,2001,2002 James Newton <james@sxlist.com>
; This program is free software; you can redistribute it and/or modify
; it under the terms of the GNU General Public License version 2 as published
; by the Free Software Foundation. Note that permission is not granted
; to redistribute this program under the terms of any other version of the
; General Public License.
;
; This program is distributed in the hope that it will be useful,
; but WITHOUT ANY WARRANTY; without even the implied warranty of
; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
; GNU General Public License for more details.
;
; You should have received a copy of the GNU General Public License
; along with this program; if not, write to the Free Software
; Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
;
;Change these as required to reflect your target device
device SX28L ;SX18L, SX28L, SX48L, SX52L
CpuMhz = 50
CpuPins = 28 ;=18,28,48, or 52
CpuLongDate = 1 ;=0 for old 4 digit date code, =1 for new "A" 8 digit date code
CpuMode = 0 ;=0 for debug, =1 for full speed
CpuCarry = 1 ;carryx is on.
IF CpuPins = 18
IF CpuLongDate = 1
device turbo, STACKX_OPTIONX
ELSE
device pins18, pages8, banks8, turbo, stackx, optionx
ENDIF
ENDIF
IF CpuPins = 28
IF CpuLongDate = 1
device turbo, STACKX_OPTIONX
ELSE
device pins28, pages8, banks8, turbo, stackx, optionx
ENDIF
ENDIF
IF CpuPins = 52 or CpuPins = 48
IF CpuLongDate = 1
error 'A longdate SX48/52 did not exist at the time this ap was written'
ELSE
device DRTOFF, TURBO, STACKX, OPTIONX
ENDIF
ENDIF
IF CpuCarry = 1
device carryx
ENDIF
IF CpuMode = 1
IF CpuLongDate = 1
device OSCXTMAX
ELSE
device oschs ;full speed operation
ENDIF
ELSE
device oscrc ;debug operation
ENDIF
IF CpuMhz = 50
freq 50_000_000
ENDIF
IF CpuMhz = 100
freq 100_000_000
ENDIF
IF CpuPins > 18
IF CpuPins > 28
GPRegOrg = $0A ;$0A to $0F - limited to 6 bytes - global
ELSE
GPRegOrg = 8 ;$08 to $0F - limited to 8 bytes - global
ENDIF
ELSE
GPRegOrg = 7 ;$07 to $0F - limited to 9 bytes - global
ENDIF
;change YOURID to up to 8 characters that identify the project.
id 'YOURID'
RESET reset_entry
;EQUATES *************************************************************************
OptRTCisW = %01111111 ;And with Opts to make register 1 show W
OptRTCEnable = %10111111 ;And with Opts to enable rtcc interrupt
OptRTCInternal = %11011111 ;And with Opts to make rtcc internal
OptRTCIntLead = %11101111 ;And with Opts to make rtcc inc on Leading edge
OptRTCPrescale = %11110111 ;And with Opts to enable rtcc prescaler
Opts = %11111000 ;base Options. Last 3 bits are the PreScale divider.
IF CpuMhz = 100
OptPreScale = 8
IntPeriod = 217 ;will be subtracted from 256 to inc RTCC
myOpts = Opts & OptRTCEnable & OptRTCInternal & OptRTCisW
ENDIF
IF CpuMhz = 75
OptPreScale = 8
IntPeriod = 244 ;will be subtracted from 256 to inc RTCC
myOpts = Opts & OptRTCEnable & OptRTCInternal & OptRTCisW
ENDIF
IF CpuMhz = 50
OptPreScale = 4
IntPeriod = 217 ;will be subtracted from 256 to inc RTCC
myOpts = Opts & OptRTCEnable & OptRTCInternal & OptRTCisW
ENDIF
;217 is a magic number that "just works" at 50 or 100Mhz for RS232 irrespective
;of the Pre Scale. See
;http://www.sxlist.com/techref/scenix/isrcalc.asp
;to calculate other options
;217*4=868 cycles per interrupt. PP at .5us strobe via delay loops
;57,604 Hz interrupt rate 0.000,017,36 seconds per interrupt
;PreScaleBits 000=1:2, 001=1:4, 010=1:8, 011=1:16, 100=1:32, 101=1:64, 110=1:128, 111=1:256
OptPreScaleBits = ((OptPreScale>3)&1) + ((OptPreScale>7)&1) + ((OptPreScale>15)&1) + ((OptPreScale>31)&1) + ((OptPreScale>63)&1) + ((OptPreScale>127)&1) + ((OptPreScale>255)&1)
IF OptPreScale > 1
IF OptPreScale <> 2<<OptPreScaleBits
;Just incase an invalid PreScale was selected
ERROR 'invalid Prescale value'
ELSE
myOpts = myOpts & OptRTCPrescale | OptPreScaleBits
ENDIF
ELSE
myOpts = myOpts | (255^OptRTCPreScale)
ENDIF
ISRRate = 0
IF myOpts & OptRTCEnable AND myOpts & OptRTCInternal
MaxISRCycles = OptPreScale * IntPeriod
ISRRate = cpuMHz*1000000 / MaxISRCycles
ENDIF
; The following three values determine the UART baud rate.
; Baud rate = cpuMHz/(RS232ISRDiv * MaxISRCycles)
; = cpuMHz/(RS232ISRDiv * OptPreScale * IntPeriod)
;
RS232BaudRate = 9600
RS232ISRDiv = ISRRate / RS232BaudRate
IF RS232ISRDiv < 1 or RS232ISRDiv > 255
ERROR 'RS232BaudRate incompatible with cpuMhz and OptPreScale'
ENDIF
; The start delay value must be set equal to RS232ISRDiv * 1.5 + 1
RS232StartDelay = RS232ISRDiv + (RS232ISRDiv>>1) + 1
WKPND_B = $09
WKED_B = $0A
WKEN_B = $0B
;TRIS = $1F
in EQU $F00
out EQU $FFF
pull EQU $E00
float EQU $EFF
cmos EQU $D00
ttl EQU $DFF
sch EQU $CFF
inten EQU $B00
intedge EQU $A00
intpend EQU $900
;MACROS --------------------------------------------------------------------------
; Port r[a | b | c | d | e] [in | out | pull | float | cmos | ttl] bits
; sets the port mode and configuration for standard pins
; CycleFor <count>
; if the count is less than the interrupt period, compiles a delay loop of the
; required cycles. For large delays, compiles code to set up to a 3 byte timer
; to an interrupt count equal to the delay and then waits for the counter to
; zero.
; Delay value, [usec,msec,sec,cycles]
; Calculates cycles from delay value and units (milli seconds, micro seconds,
; or seconds). Calls cyclefor to delay that number of cycles
; LookupW <12bitValue> [, <12bitValue>]
; uses IREAD (affecting M and W) to lookup values up to 12 bits indexed by W
; BinJump <reg>, <Address> [, <Address>]
; Call with the first parameter of the register to tbe tested and
; the following parameters a list of addresses to jump to based on
; the value of the register.
; More effecient than a long jump table for 4 or fewer addresses
; GotoW <Address> [, <Address>]
; Implements a jump table using space in the first low half page of memory.
; must be invoked after all <Address>'s are defined.
; Uses BinJump for less than 5 addresses
; Subroutine
; Defines SubEntryAddr from the current address or the address of a jump from
; space in the first low half page of memory as needed to ensure global
; CALL access to a subroutine.
; Push, Pop
; compile code to push and pop W from a stack setup in one register bank.
; Condition enum (IsZero,Eq,Lt,LE,IsNotZero,NE,Gt,GE,EqN,LtN,LEN,NEN,GtN,GEN)
; enum values ending in N indicate that the second operand will be a constant
; Condition := [<reg>, <enum> | <reg>, <enum>, <reg> | <reg>, <enum>, <constant> ]
; Skz <reg>, [IsZero | IsNotZero]
; Generates a skip if the reg is zero or not zero
; Skc <reg1>, [Eq | Lt | LE | NE | Gt | GE], <reg2>
; Generates a skip if reg1 compaires as specified to reg2
; Skc <reg>, [EqN | LtN | LEN | NEN | GtN | GEN], <constant>
; Generates a skip if reg compaires as specified to constant
; StackPUSH, StackPOP, StackTOS and stack1...
; Provide a compile time stack to record and retrieve the addresses of
; locations were jumps need to be compiled once the jump-to address is
; known. Used by the following macros:
; Repeat
; <statements>
; [forever | while <condition> | until <condition>]
;
; compiles Skz or Skc with jumps to implement a structured loop
; DoIf <condition>
; <statements>
; [
; DoElseIf <condition>
; <statements>
; ]...
; [
; DoElse
; <statements>
; ]
; DoEndIf
;
; Compiles Skz or Skc with jumps to implement a structured conditional
; As many DoElseIf statements as desired may be included because each DoElseIf
; links to the next one at run time so that if the first DoElseIf condition
; is true, after its statements a jump will be compiled that will jump to
; the simular jump after the next DoElseIf statements. To avoid this extra
; run time, use DoSelect.
; DoSelect
; [
; DoCase <condition>
; <statements>
; ]...
; [
; DoCaseElse
; <statements>
; ]
; DoEndSelect
;
; Compiles Skz or Skc with jumps to implement a structured conditional
; A limited number of DoCase statments can be compiled because each
; case compiles a jump to the end of the select after the statements
; following the case condition and recording the position were these
; jumps must be org'd takes up space on the "stack" provided by
; StackPUSH, StackPOP and stack1...15
;See lable "Main" for start of examples
porthelp MACRO
ERROR 'USAGE: port r[a,b,c,d,e] [in,out,pull,float,cmos,ttl] bits'
ENDM
_PortMode = $1F
PortMode MACRO 1
noexpand
; IF _PortMode <> \1
IF CpuPins > 28
_PortMode = \1 | $10
expand
mov w,#_PortMode
mov m,w
noexpand
ELSE
_PortMode = \1
expand
mov m,#_PortMode
noexpand
ENDIF
; ENDIF
ENDM
port MACRO 3
noexpand
IF \1=RA OR \1=RB OR (CpuPins>18 AND \1=RC) OR (CpuPins > 28 AND (\1=RD OR \1=RE))
ELSE
porthelp
ENDIF
IF \2=in OR \2=out OR \2=pull OR \2=float OR \2=cmos OR \2=ttl OR (\1=RB AND (\2=sch OR \2=inten OR \2=intedge OR \2=intpend))
ELSE
porthelp
ENDIF
PortMode (\2 / $100)
_PortMask = (\2//$100)^\3
expand
mov !\1, #_PortMask
noexpand
ENDM
mynop MACRO
noexpand
page $
ENDM
nsec EQU -9
usec EQU -6
msec EQU -3
sec EQU 1
cycles EQU 0
cyclefor MACRO 1
noexpand
_cycles = \1
_temp = 0
IF _cycles - 10 > IntPeriod OR _cycles < 0
_cycles = _cycles - 10
_ints3 = $FF - (_cycles/(IntPeriod*$10000))
_ints2 = $FF - (_cycles/(IntPeriod*$100)//$100)
_ints1 = $FF - (_cycles/IntPeriod//$100)
IF Timers > $0F
; ERROR 'Timers must be in bank 0'
bank Timers
ENDIF
expand
clr TimerAccL
mov TimerAccT, #_ints3
mov TimerAccH, #_ints2
mov TimerAccL, #_ints1
mov w,#$02
clrb TimerFlag
sb TimerFlag
sub 2,w
noexpand
_cycles = _cycles // IntPeriod
ELSE
_temp = $ // 4
IF _temp = 2
IF _cycles < 5
REPT _cycles
expand
mynop
noexpand
ENDR
_cycles = 0
ELSE
expand
mynop
noexpand
_cycles = _cycles -1
ENDIF
ENDIF
IF _temp = 1
IF _cycles < 7
REPT _cycles
expand
mynop
noexpand
ENDR
_cycles = 0
ELSE
_cycles = _cycles - 2
_loops = _cycles / 5
expand
mov w, #_loops
page $+1
decsz 1
jmp $-1
noexpand
_cycles = _cycles // 5 ;cycles left over
ENDIF
ENDIF
IF _cycles > 5
_cycles = _cycles - 1
_loops = _cycles / 5
expand
mov w, #_loops
decsz 1
clrb 2.1
noexpand
_cycles = _cycles // 5 ;cycles left over
ENDIF
IF _cycles > 0
REPT _cycles
expand
mynop
noexpand
ENDR
ENDIF
ENDIF
ENDM
delayhelp MACRO
ERROR 'USAGE: delay value, [usec,msec,sec,cycles]'
ENDM
delay MACRO 2
noexpand
;Calculates cycles from delay value and units (milli seconds, micro seconds, or seconds)
;calls cyclefor to delay that number of cycles
IF (\2=nsec OR \2=usec OR \2=msec OR \2=sec) AND (\1<1000 AND \1>0)
IF \2=sec
_cycles = (\1 * 100000000 / (100/CpuMhz))
ENDIF
IF \2=msec
_cycles = (\1 * 1000000 / (1000/CpuMhz))
ENDIF
IF \2=usec
_cycles = (\1 * 1000 / (1000/CpuMhz))
ENDIF
IF \2=nsec
_cycles = (\1 * 10 + 5 / (10000/CpuMhz))
ENDIF
IF \2=cycles
_cycles = \1
ENDIF
IF _cycles = 0
expand
;delay less than one cycle at this processor speed'
noexpand
ELSE
cyclefor _cycles
ENDIF
ELSE
delayhelp
ENDIF
ENDM
ConditionBase equ $0
IsZero equ ConditionBase + %0000
Eq equ ConditionBase + %0001
Lt equ ConditionBase + %0010 ;2
LE equ ConditionBase + %0011 ;3
IsNotZero equ ConditionBase + %0100 ;8
NE equ ConditionBase + %0101 ;9
GE equ ConditionBase + %0110 ;10
Gt equ ConditionBase + %0111 ;11
EqN equ ConditionBase + %1001
LtN equ ConditionBase + %1010 ;2
LEN equ ConditionBase + %1011 ;3
NEN equ ConditionBase + %1101 ;9
GEN equ ConditionBase + %1110 ;10
GtN equ ConditionBase + %1111 ;11
; dabc
SkMskConst equ %1000
;column "d" (mask 8) shows which compare registers with constants and which with registers.
SkMskSwap equ %0100
;column "a" (mask 4) shows which are exact opposites of one another.
; e.g. Eq is the opposite of NE, Lt of GE, LE of Gt
SkMskNeq equ %0010
;column "b" (mask 2) shows which are inequalities and which are equalitites
SkMskC equ %0001
;column "c" (mask 1) differentiates the inequalities
SkMskFlip equ %0101
;Xor with condition to flip the inequality around X op Y becomes Y op X
Skc MACRO 3
; noexpand
;Usage: Skc pX, Condition, pY
pX = \1
tst = \2
pY = \3
SkcBank = 0
IF tst & SkMskConst
IF pX = WReg AND ((tst & SkMskNeq) > 1)
expand
mov temp, w ;WARNING! temp modified in macro.
noexpand
pX = temp
ENDIF
IF tst = GtN OR tst = LEN
expand
mov w, #(pY + 1)
noexpand
;if tst was GtN its now GE if it was LEN its Lt
tst = (tst ^ SkMskC) & ~SkMskConst
ELSE ; tst = GEN, LtN, NEN, EqN
IF pX = WReg
pX = pY
ELSE
expand
mov w, #pY
noexpand
tst = tst & ~SkMskConst
ENDIF
ENDIF
pY = WReg
ENDIF
IF pX = WReg
IF (tst & SkMskNeq) > 1
;Flip the operation around.
tst = tst ^ SkMskFlip
ENDIF
pX = pY
pY = WReg
ENDIF
;At this point, pX is NOT w
IF pY <> WReg
IF pY>$0F ;are we about to access a non-global register?
expand
bank pY ;non-global
noexpand
SkcBank = pY / $10
ENDIF
IF tst = Gt OR tst = LE
expand
mov w, ++pY
noexpand
;if tst was Gt its now GE if it was LE its Lt
tst = tst ^ SkMskC
ELSE ; tst = GE, Lt, Eq, NE
expand
mov w, pY
noexpand
ENDIF
pY = WReg
ENDIF
;At this point, pY is in W. pX is a register or a constant
IF pX>$0F AND (pX / $10) <> SkcBank AND tst & SkMskConst = 0
;are we about to access a non-global register in a new bank?
expand
bank pX ;non-global
noexpand
ENDIF
IF tst = Eq OR tst = NE OR tst = EqN OR tst = NEN
IF tst = EqN OR tst = NEN
expand
xor w, #pX
noexpand
tst = tst & ~SkMskConst
ELSE
expand
xor w, pX
noexpand
ENDIF
IF tst = Eq
expand
sz
noexpand
ELSE
expand
snz
noexpand
ENDIF
ELSE
IF CpuCarry
IF tst = Gt OR tst = LE
expand
clc
noexpand
ELSE
expand
stc
noexpand
ENDIF
ENDIF
expand
mov w, pX - w
noexpand
IF tst = Lt OR (tst = LE AND CpuCarry)
expand
snc
noexpand
ELSE
expand
sc
noexpand
ENDIF
ENDIF
IF (tst = Gt OR tst = LE) AND NOT CpuCarry
expand
snz
noexpand
ENDIF
IF tst = Gt AND NOT CpuCarry
expand
skip
noexpand
ENDIF
ENDM
Skz MACRO 2
;Usage: Skz register, [IsZero | IsNotZero]
noexpand
IF \1>$0F
expand
bank \1 ;non-global
noexpand
ENDIF
expand
test \1
noexpand
IF \2 = IsZero
expand
sz
noexpand
ELSE
IF \2 = IsNotZero
expand
snz
noexpand
ELSE
error 'Usage: Skz register, [IsZero | IsNotZero]'
ENDIF
ENDIF
ENDM
RepeatLabel5 = 0
RepeatLabel4 = 0
RepeatLabel3 = 0
RepeatLabel2 = 0
RepeatLabel = 0
PushRepeat MACRO
noexpand
RepeatLabel5 = RepeatLabel4
RepeatLabel4 = RepeatLabel3
RepeatLabel3 = RepeatLabel2
RepeatLabel2 = RepeatLabel
ENDM
PopRepeat MACRO
noexpand
RepeatLabel = RepeatLabel2
RepeatLabel2 = RepeatLabel3
RepeatLabel3 = RepeatLabel4
RepeatLabel4 = RepeatLabel5
RepeatLabel5 = 0
ENDM
Repeat MACRO
noexpand ;incase expand was already on.
PushRepeat
expand
RepeatLabel = $
noexpand
ENDM
Until MACRO
noexpand
IF \0 = 2
Skz \1,\2
ELSE
Skc \1,\2,\3
ENDIF
expand
jmp @RepeatLabel
noexpand
PopRepeat
ENDM
While MACRO
noexpand
IF \0 = 2
Skz \1,\2^SkMskSwap
ELSE
Skc \1,\2^SkMskSwap,\3
ENDIF
expand
jmp @RepeatLabel
noexpand
PopRepeat
ENDM
Forever MACRO
noexpand ;incase expand was already on.
expand
jmp @RepeatLabel
noexpand
PopRepeat
ENDM
StackTOS = -1
Stack1 = 0
Stack2 = 0
Stack3 = 0
Stack4 = 0
Stack5 = 0
Stack6 = 0
Stack7 = 0
Stack8 = 0
Stack9 = 0
Stack10 = 0
Stack11 = 0
Stack12 = 0
Stack13 = 0
Stack14 = 0
Stack15 = 0
StackPush MACRO 1
IF Stack8 = 0
IF Stack4 = 0
IF Stack2 = 0
IF Stack1 = 0
Stack1 = StackTOS
ELSE
Stack2 = StackTOS
ENDIF
ELSE
IF Stack3 = 0
Stack3 = StackTOS
ELSE
Stack4 = StackTOS
ENDIF
ENDIF
ELSE
IF Stack6 = 0
IF Stack5 = 0
Stack5 = StackTOS
ELSE
Stack6 = StackTOS
ENDIF
ELSE
IF Stack7 = 0
Stack7 = StackTOS
ELSE
Stack8 = StackTOS
ENDIF
ENDIF
ENDIF
ELSE
IF Stack12 = 0
IF Stack10 = 0
IF Stack9 = 0
Stack9 = StackTOS
ELSE
Stack10 = StackTOS
ENDIF
ELSE
IF Stack11 = 0
Stack11 = StackTOS
ELSE
Stack12 = StackTOS
ENDIF
ENDIF
ELSE
IF Stack14 = 0
IF Stack13 = 0
Stack13 = StackTOS
ELSE
Stack14 = StackTOS
ENDIF
ELSE
IF Stack15 = 0
Stack15 = StackTOS
ELSE
expand
; ERROR Stack Overflow
noexpand
ENDIF
ENDIF
ENDIF
ENDIF
StackTOS = \1
ENDM
StackPop MACRO 0
IF Stack8 = 0
IF Stack4 = 0
IF Stack2 = 0
IF Stack1 = 0
expand
; ERROR Stack Underflow
noexpand
ELSE
StackTOS = Stack1
Stack1 = 0
ENDIF
ELSE
IF Stack3 = 0
StackTOS = Stack2
Stack2 = 0
ELSE
StackTOS = Stack3
Stack3 = 0
ENDIF
ENDIF
ELSE
IF Stack6 = 0
IF Stack5 = 0
StackTOS = Stack4
Stack4 = 0
ELSE
StackTOS = Stack5
Stack5 = 0
ENDIF
ELSE
IF Stack7 = 0
StackTOS = Stack6
Stack6 = 0
ELSE
StackTOS = Stack7
Stack7 = 0
ENDIF
ENDIF
ENDIF
ELSE
IF Stack12 = 0
IF Stack10 = 0
IF Stack9 = 0
StackTOS = Stack8
Stack8 = 0
ELSE
StackTOS = Stack9
Stack9 = 0
ENDIF
ELSE
IF Stack11 = 0
StackTOS = Stack10
Stack10 = 0
ELSE
StackTOS = Stack11
Stack11 = 0
ENDIF
ENDIF
ELSE
IF Stack14 = 0
IF Stack13 = 0
StackTOS = Stack12
Stack12 = 0
ELSE
StackTOS = Stack13
Stack13 = 0
ENDIF
ELSE
IF Stack15 = 0
StackTOS = Stack14
Stack14 = 0
ELSE
StackTOS = Stack15
Stack15 = 0
ENDIF
ENDIF
ENDIF
ENDIF
ENDM
noexpand
StackPUSH 1
StackPUSH 2
StackPUSH 3
StackPUSH 4
StackPUSH 5
StackPUSH 6
StackPUSH 7
StackPUSH 8
StackPUSH 9
StackPUSH 10
StackPUSH 11
StackPUSH 12
StackPUSH 13
StackPUSH 14
StackPUSH 15
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
StackPOP
expand
link MACRO 2
:temp = $
org \1 ; go back
jmp @(\2) ;<- jmp to here
org :temp ; come forward
ENDM
DoIf MACRO
IF \0 = 2
Skz \1,\2
ELSE
Skc \1,\2,\3
ENDIF
;***Save place to link failure of this test to the Else, ElseIf or EndIf code
StackPUSH $ ;save space here for a jmp
expand
;mp +:FAIL
noexpand
org $+2
ENDM
DoElseIf MACRO
;***If there is a previous succeed place, link it to this one
IF (StackTOS >> 24) > 0
link (StackTOS - (StackTOS >> 24)), $
ENDIF
;***Setup place to Link the prev DoIf or DoElseIf success code out to the DoEndIf
nDoElseIf:S = $
expand
;mp +:SUCCEED
noexpand
org $+2
;***Link the last DoIf or DoElseIf fail to the DoElseIf code
expand
;:FAIL
noexpand
link (StackTOS & $FFFFFF), $
IF \0 = 2
Skz \1,\2
ELSE
Skc \1,\2,\3
ENDIF
;***Save place to link failure of this test to the Else, ElseIf or EndIf code
StackTOS = ($ - nDoElseIf:S)<<24 + $
expand
;mp +:FAIL
noexpand
org $+2
ENDM
DoElse MACRO
;***If there is a previous succeed place, link it to this one
IF (StackTOS >> 24) > 0
link (StackTOS - (StackTOS >> 24)), $
ENDIF
;***Setup place to Link the prev DoIf or DoElseIf success code out to the DoEndIf
nDoElse:S = $
expand
;mp +:SUCCEED
noexpand
org $+2 ; and leave space for it
;***Link the last DoIf or DoElseIf fail to the DoElse code
expand
;:FAIL
noExpand
link StackTOS, $
StackTOS = nDoElse:S
ENDM
DoEndIf MACRO
;***If there is a previous succeed place, link it to this one
IF (StackTOS >> 24) > 0
link (StackTOS - (StackTOS >> 24)), $
ENDIF
expand
:SUCCEED ;DoEndIf
:FAIL ;DoEndIf
noexpand
link (StackTOS & $FFFFFF), $
StackPOP
ENDM
DoSelect:Level = 0
DoCase:Count = 0
DoCase:F = 0
DoSelect MACRO
StackPUSH DoCase:Count - 1 ;can't push a zero
DoCase:Count = 0
StackPUSH DoCase:F + 1 ;can't push a zero
DoCase:F = 0
DoSelect:Level = DoSelect:Level + 1
ENDM
DoCase MACRO
DoCase:Count = DoCase:Count - 1
IF DoCase:Count < -1
;***Setup place to Link the prev Case success code out to the end
StackPUSH $
expand
;mp +:SUCCEED
noexpand
org $+2
;***Link the last fail to this DoCase test code
link DoCase:F, $
expand
;:FAIL
noexpand
ENDIF
IF \0 = 2
Skz \1,\2
ELSE
Skc \1,\2,\3
ENDIF
;***Save place to link failure of this test to the Else, ElseIf or EndIf code
DoCase:F = $
expand
;mp +:FAIL
noexpand
org $+2
ENDM
DoCaseElse MACRO
;***Setup place to Link the prev DoCase success code out to the DoCaseEnd
StackPUSH $
expand
;mp +:SUCCEED
noexpand
org $+2
;***Link the last fail to the DoCaseElse code
link DoCase:F, $
DoCase:F = 0
expand
;:FAIL
noExpand
ENDM
DoCaseEnd MACRO
;***If there is a previous succeed place, link it to this one
IF DoCase:Count < 0
REPT 0 - DoCase:Count
link StackTOS, $
StackPOP
ENDR
ENDIF
expand
:SUCCEED ;DoCaseEnd
noexpand
IF DoCase:F > 0
link DoCase:F, $
expand
:FAIL ;DoCaseEnd
noexpand
ENDIF
DoSelect:Level = DoSelect:Level - 1
DoCase:F = StackTOS - 1
StackPOP
DoCase:Count = StackTOS + 1 ;correct for -1 when pushed.
StackPOP
ENDM
doifadr = 0
doendifadr = 0
doelsifadr = 0
doifl = 0
odoif MACRO
noexpand
doifl = doifl + 1
IF doifl > 2
error 'Only 2 levels of nested conditions supported by doif macro'
ENDIF
doelsifadr = doelsifadr * 2048
IF \0 = 2
Skz \1,\2
ELSE
Skc \1,\2,\3
ENDIF
;***Save place to link failure of this test to the Else, ElseIf or EndIf code
expand
doifadr = doifadr * 2048 + $ ;save space here for a jmp
noexpand ;figure out where the jmp will be from
org $+2 ; and leave space for it
ENDM
oDoElse MACRO
noexpand
IF doifl < 1
error 'DoElse outside of DoIf/DoEndIf block'
ENDIF
IF doelsifadr > 0
error 'DoElse can not follow DoElseIf'
ENDIF
;***Link the last DoIf or DoElseIf fail to the DoElse code
;remember where we were,
;go back to where the jmp needs to be
;jmp to where we were
;go back to where we were
expand
doendifadr = doendifadr * 2048 + $
org doifadr // 2048 ; go back
jmp @(doendifadr // 2048)+2; do the jmp
org doendifadr // 2048 ; come forward
doendifadr = doendifadr / 2048
;***Setup place to Link the DoIf or DoElseIf success code out to the DoEndIf
doifadr = (doifadr & ~1023) + $ ;save space here for a jmp
noexpand ;figure out where the jmp will be from
org $+2 ; and leave space for it
ENDM
oDoElseIf MACRO
noexpand
IF doifl < 1
error 'DoElseIf outside of DoIf/DoEndIf block'
ENDIF
;***Setup place to Link the prev DoIf or DoElseIf success code out to the DoEndIf
doelsifadr = (doelsifadr & ~1023) + $ ;save space here for a jmp
noexpand ;figure out where the jmp will be from
org $+2 ; and leave space for it
;***Link the last DoIf or DoElseIf fail to the DoElseIf code
expand
doendifadr = doendifadr * 2048 + $
org doifadr // 2048 ; go back
jmp @(doendifadr // 2048); do the jmp
org doendifadr // 2048; come forward
doendifadr = doendifadr / 2048
noexpand
IF \0 = 2
Skz \1,\2
ELSE
Skc \1,\2,\3
ENDIF
;***Link the prev DoIf or DoElseIf success code out to the DoEndIf
expand
dotemp = $
org doelsifadr // 2048; go back
jmp @(dotemp); do the jmp
org dotemp; come forward
noexpand
;Sadly, if we link here, we can't use doElse after doElseIf because there is no
; way to differentiate a prior success from a lack of prior success... the
; else code is always executed.
;If we stack up all the success end addresses and link them in doEndIf, there is
; a limit to the number of doElseIf's that can be supported.
;The new DoIf, DoElseIf, DoElse, DoEndIf macros solve this.
;***Save place to link failure of this test to the Else, ElseIf or EndIf code
expand
doifadr = (doifadr & ~1023) + $ ;save space here for a jmp
noexpand ;figure out where the jmp will be from
org $+2 ; and leave space for it
ENDM
oDoEndIf MACRO
noexpand
IF doifl < 1
error 'DoEndIf outside of DoIf/DoEndIf block'
ENDIF
doelsifadr = doelsifadr / 2048
doifl = doifl - 1
;remember where we were,
;go back to where the jmp needs to be
;jmp to where we were
;go back to where we were
expand
doendifadr = doendifadr * 2048 + $
org doifadr // 2048 ; go back
jmp @(doendifadr // 2048) ; do the jmp
org doendifadr // 2048 ; come forward
doendifadr = doendifadr / 2048
doifadr = doifadr / 2048
noexpand
ENDM
Push MACRO 1
noexpand
parm = \1
expand
DecBufPtr StackPtr ;could use incsz rather than inc to avoid modifying Z
noexpand
IF Parm = Wreg OR parm = fsr
IF parm <> fsr
expand
mov fsr, w ;fsr could be anything (due to bank etc..) so use for parm
noexpand
parm = WReg
ENDIF
expand
mov w, StackPtr ;get the StackPtr into w
xor fsr, w ;swap w with fsr
xor w, fsr
xor fsr, w
mov ind, w ;store w to Top Of Stack.
noexpand
ELSE
expand
mov fsr, StackPtr ;W used
noexpand
IF parm > $0F
expand
bank parm
mov w, parm
bank Stack
mov ind, w
noexpand
ELSE
expand
mov ind, parm
noexpand
ENDIF
ENDIF
ENDM
Pop MACRO 1
noexpand
expand
mov fsr, StackPtr ;W used
mov w, ind
noexpand
IF \1 > $0F
expand
bank \1
noexpand
ENDIF
expand
mov \1,w
;\1 is now the StackPtr
IncBufPtr StackPtr ;point to valid data at new Top Of Stack
noexpand
ENDM
LookupW MACRO
noexpand
;Defines an in-line DW/IREAD lookup table returns the 12 bit value indexed by W in M:W.
;Affects M and W.
expand
jmp @$+\0+2
; IF \0
_LookupWTableBegin = $
noexpand
REPT \0
expand
DW \%
noexpand
ENDR
_LookupWTableEnd = $
expand
IF _LookupWTableBegin & $FF <> 0
mov temp,w ;WARNING temp modified by macro
mov w, #_LookupWTableBegin & $FF
add w, temp ;offset from start of table
ENDIF
mov m,#_LookupWTableBegin>>8
IF (_LookupWTableBegin / $100) <> (_LookupWTableEnd / $100)
snc ;correct if carry
mov m,#_LookupWTableBegin>>8+1
ENDIF
iread ;Retrieve data
noexpand
;{use the data}
ENDM
Subroutine MACRO
noexpand
;Usage: Define a Global lable,
; Execute Subroutine macro,
; Assign :Entry to the value now set in SubEntryAddr.
; Continue the definition of the subroutine.
; Elsewhere, call @Sub:Entry where Sub is the global lable
; you defined for the subroutine.
;Example
;SUB1 Subroutine
;:Entry = SubEntryAddr
;....
; Call SUB1:Entry
_SubAddr = $
IF (_SubAddr & $100) <> 0
org LowHalfPage
SubEntryAddr = $
;if we got here, the pagesel bits must be set for here
IF ($ / $100) = (_SubAddr / $100)
expand
jmp _SubAddr
noexpand
ELSE
expand
jmp @_SubAddr
noexpand
ENDIF
LowHalfPage = $
IF $+1 > HighHalfPage
ERROR 'Out of LowHalfPage Space'
ENDIF
org _SubAddr
ELSE ;The subroutine was already starting in a LowHalfPage
SubEntryAddr = $
ENDIF
ENDM
binjump MACRO
;Call with the first parameter of the register to tbe tested and
;the following parameters a list of addresses to jump to based on
;the value of the register.
;More effecient than a long jump table for 4 or fewer addresses
noexpand
if \0 > 5
if \0 = 6
expand
jb \1.2, @\6 ;=4
noexpand
binjump \1,\2,\3,\4,\5
else
expand
jb \1.2, @:2Set ;>4 ;@$+16
noexpand
binjump \1,\2,\3,\4,\5
expand
:2Set
noexpand
if \0 > 7
if \0 > 8
binjump \1,\6,\7,\8,\9
else
binjump \1,\6,\7,\8
endif
else
binjump \1,\6,\7
endif
endif
else ;5 or less
if \0 > 3
if \0 = 4
expand
jb \1.1, @\4 ;=2 or 6
noexpand
binjump \1,\2,\3
else
expand
jb \1.1, @:1Set ;>2 or >6; $+8
noexpand
binjump \1,\2,\3
expand
:1Set
noexpand
binjump \1,\4,\5
endif
else
expand
jnb \1.0,@\2
jmp @\3
noexpand
endif
endif
endm
GotoW MACRO
noexpand
;must be invoked after all parameters are defined
;i.e. no forward references.
;if you manually expand the macro, forward refs may work?
_SaveAddr = $
_GotoWPage = _SaveAddr / $200
REPT \0
IF (\% / $200) <> (_SaveAddr / $200)
_GotoWPage = (\% / $200) ;
ENDIF
ENDR
IF _GotoWPage <> (_SaveAddr / $200) OR ((_SaveAddr // $200) > $FF) ;has to be a long jump table
IF \0 > 127
ERROR 'Long jumps must be used and no more than 127 entries can be supported'
ENDIF
IF \0 = 2
binjump WReg, \1, \2
EXITM
ENDIF
IF \0 = 3
binjump WReg, \1, \2, \3
EXITM
ENDIF
IF \0 = 4
binjump WReg, \1, \2, \3, \4
EXITM
ENDIF
IF LowHalfPage + (\0*2) + 1 > HighHalfPage
ERROR 'Out of LowHalfPage Space'
ENDIF
org LowHalfPage
_GotoWPage = 0
ELSE
IF \0 > 255
ERROR 'No more than 255 entries can be supported'
ENDIF
IF LowHalfPage + \0 + 1 > HighHalfPage
ERROR 'Out of LowHalfPage Space'
ENDIF
ENDIF
expand
_GotoWTableBegin = $
add PC,W ;jump to the jump
noexpand
REPT \0
IF _GotoWPage = 0
expand
jmp @\%
noexpand
ELSE
expand
jmp \%
noexpand
ENDIF
ENDR
IF _GotoWPage = 0 ;its a long jump table
LowHalfPage = $
org _SaveAddr
expand
clc
rl WReg ;need long jumps
;WARNING: Insure OPTION:RWT = 0
jmp @_GotoWTableBegin
noexpand
ENDIF
ENDM
DecBufPtr MACRO 1
noexpand
;decrements buffer pointers and keeps them within one bank
IF CPUPins > 28
expand
dec \1
setb \1.5
noexpand
ELSE
expand
dec \1
setb \1.4
noexpand
ENDIF
ENDM
IncBufPtr MACRO 1
noexpand
;increments buffer pointers and keeps them within one bank
IF CPUPins > 28
expand
inc \1
setb \1.5
noexpand
ELSE
expand
inc \1
setb \1.4
clrb \1.5
noexpand
ENDIF
ENDM
mmov Macro 3
noexpand
_bank = 0
rept \3
IF ((\2 + %) / $10) <> _bank
_bank = (\2 + %) / $10
expand
bank (\2 + %)
noexpand
ENDIF
expand
mov w, (\2 + %)
noexpand
IF ((\1 + %) / $10) <> _bank
_bank = (\1 + %) / $10
expand
bank (\1 + %)
noexpand
ENDIF
expand
mov (\1 + %), w
noexpand
ENDR
ENDM
;PORTS --------------------------------------------------------
IF CpuPins > 28 ;CPUPins = 48 or 52
IF CpuPins > 48
;CPUPins = 52
ELSE
;CPUPins = 48
ENDIF
ELSE ;CPUPins = 18 or 28
IF CpuPins > 18
;CPUPins = 28
ELSE
;CPUPins = 18
ENDIF
ENDIF
rbIntMask = 0
;VARIABLES ****************************************************
;ds allocates registers starting from the register number
; specifed by the org address which does not relate to a
; program memory address
;GLOBAL VARIABLES ---------------------------------------------
org GPRegOrg
Temp ds 1
flags ds 1 ;general flag register
RS232Rx_flag = flags.0
RS232RxFrameErr = flags.1
TimerFlag = flags.2 ;timer rollover flag
Timers = $ ;timer
TimerAccL ds 1 ;timer accumulator low
TimerAccH ds 1 ;timer accumulator high
TimerAccT ds 1 ;timer accumulator top
watch TimerFlag, 1, ubin
watch TimerAccL, 24, uhex
StackPtr ds 1 ;Stack
watch StackPtr,8,UHEX
IF $ > $10
ERROR 'out of gobal variable space'
ENDIF
;BANK 0 VARIABLES ---------------------------------------------
org $10 ;$10 to $1F - limit 16 bytes - bank 0
bank0 = $
;place variables and watches here
VPSSlice ds 1
VPSCount ds 1
IntI ds 1
watch IntI,8,UHEX
IntJ ds 1
watch IntJ,8,UHEX
errat ds 1
watch errat,8,UHEX
IF $ > $20
ERROR 'out of variable space'
ENDIF
;BANK 1 VARIABLES ---------------------------------------------
org $30 ;$30 to $3F - limit 16 bytes - bank 1
bank1 = $
;place variables here
IF $ > $40
ERROR 'out of variable space'
ENDIF
;BANK 2 VARIABLES ---------------------------------------------
org $50 ;$50 to $5F - limit 16 bytes - bank 2
bank2 = $
;place variables here
IF $ > $60
ERROR 'out of variable space'
ENDIF
;BANK 3 VARIABLES ---------------------------------------------
org $70 ;$70 to $7F - limit 16 bytes - bank 3
bank3 = $
;place variables here
IF $ > $80
ERROR 'out of variable space'
ENDIF
;BANK 4 VARIABLES ---------------------------------------------
org $90 ;$90 to $9F - limit 16 bytes - bank 4
bank4 = $
;place variables here
IF $ > $A0
ERROR 'out of variable space'
ENDIF
;BANK 5 VARIABLES ---------------------------------------------
org $B0 ;$B0 to $BF - limit 16 bytes - bank 5
bank5 = $
;place variables here
IF $ > $C0
ERROR 'out of variable space'
ENDIF
;BANK 6 VARIABLES ---------------------------------------------
org $D0 ;$D0 to $DF - limit 16 bytes - bank 6
bank6 = $
;place variables here
IF $ > $E0
ERROR 'out of variable space'
ENDIF
;BANK 7 VARIABLES ---------------------------------------------
org $E0 ;$E0 to $EF - limit 16 bytes - bank 7
bank7 = $
Stack ds 16 ;Stack
;place variables here
IF $ > $100
ERROR 'out of variable space'
ENDIF
ISR ;(Interrupt Service Routine) ******************************
;put your ISR (or just a jump to it) here.
;org is now being used to set the starting point in code memory
org 0
jmp @VPS
:Out ;---------------------------------------------------------
;The Virtual Peripherals are expected to jump back
; to @ISR:Out when done
IF CpuLongDate <> 1
; << added to correct bug in 9818 chips
mov m,#WKEN_B ;Enable Port B interrupts
mov !rb,#rbIntMask
mov m,#TRIS ;Point mode back to ports
; end bug fix >>
ENDIF
mov !option, #myOpts
mov w,#-IntPeriod ;1
retiw ;3
;retiw adds w to RTCC which avoids
;jitter due to variations in ISR path or latency.
TABLES ;*******************************************************
;Jump tables are assembled here by the SUBROUTINE,
; and GOTOW macros.
LowHalfPage = $
HighHalfPage = $100
org HighHalfPage ;Leave space in the first LowHalfpage
;STARTUP ******************************************************
reset_entry ;must be in the first page
jmp @SETUP
org $+2 ;leave room for the debugger
;Virtual Peripherals ******************************************
;The Virtual Peripherals are expected to jump back to @ISR:Out
; when done
UART ;Universal Asynchronous Receiver Transmitter
;(UART) Virtual Peripheral-------------------------------------
;etc
jmp @ISR:Out
PWM ;Pulse Width Modulation Virtual Peripheral ----------------
;etc
jmp @ISR:Out
VPS ;Virtual Peripheral Sequencer------------------------------
;Time slice kernal goes here
;Positioned after the Virtual Peripherals so the GotoW avoids
; forward references.
mov w, --VPSSlice
snz
mov w, #VPSCount
mov VPSSlice, w
GotoW UART, PWM ;,etc...
SETUP ;********************************************************
; IO PORTS ----------------------------------------------------
bank 0
;mode (m) defaults to $0F or $1F - !r{a,b,c} is the data
;direction register. Ports default to input, no pullup, ttl,
;on all pins
IF CPUPins > 28
; SX52 Port setup
;
PortMode TRIS
ELSE
; SX28 Port setup
;
PortMode TRIS
ENDIF
; RAM - reset all ram banks
; GLOBAL RAM --------------------------------------------------
mov fsr,#GPRegOrg
:gloop
clr ind ;clear register pointed to by fsr
inc fsr
sb fsr.4
jmp @:gloop ;until fsr rolls over from $0F
; RAM BANKS ---------------------------------------------------
:loop
IF CpuPins <= 28
setb fsr.4 ;avoid control registers on smaller chips
ENDIF
clr ind ;set register pointed to by fsr to zero
ijnz fsr,@:loop ;until fsr rolls over from $FF
;SUBROUTINES **************************************************
;with luck, the ISR and VPS will push this into a new
; LowHalfPage. Subroutines can be rearranged manually to help
; the macros save memory.
SUB1 Subroutine ;==============================================
:Entry = SubEntryAddr
nop
;do stuff
jc @:Out
:test
djnz $10,@:test
:Out
MAIN ;PROGRAM *************************************************
binjump 9,1,2,3,4,$500
binjump 9,1,2,3,4,5,6
GotoW MAIN, $800, ISR, SUB1:Entry, $801
; GotoW Main, $100, $200, $300, $400, $500, $600, $700, $800, $100, $200, $300, $400, $500, $600, $700, $800
; GotoW Main, $100, $200, $300, $400, $500, $600, $700, $800, $100, $200, $300, $400, $500, $600, $700, $800, $100, $200, $300, $400, $500, $600, $700, $800, $100, $200, $300, $400, $500, $600, $700, $800, $100, $200, $300, $400, $500, $600, $700, $800, $100, $200, $300, $400, $500, $600, $700, $800, $100, $200, $300, $400, $500, $600, $700, $800, $100, $200, $300, $400, $500, $600, $700, $800, $100, $200, $300, $400, $500, $600, $700, $800, $100, $200, $300, $400, $500, $600, $700, $800, $100, $200, $300, $400, $500, $600, $700, $800, $100, $200, $300, $400, $500, $600, $700, $800
LookupW Main,ISR,SUB1
call @SUB1:Entry ;global call to subroutine
; call SUB1 ;local call to subroutine
clr IntI
:zeroloop
test IntI
jnz :notzero
:zero
mov errat,#$
Skz IntI,IsZero
jmp :bogus
mov errat,#$
Skz IntI,IsNotZero
skip
jmp :bogus
djnz IntI, :zeroloop
jmp :done
:notzero
mov errat,#$
Skz IntI,IsZero
skip
jmp :bogus
mov errat,#$
Skz IntI,IsNotZero
jmp :bogus
djnz intI,:zeroloop
:done
clr IntI
:outsideloop
clr IntJ
:insideloop
mov w, IntI
mov w, IntJ-w
snc
jmp :ILTJOut
:ILTJ
;yess
mov errat,#$
Skc IntI,NE,IntJ
jmp :bogus
mov errat,#$
Skc IntI,Lt,IntJ
jmp :bogus
mov errat,#$
Skc IntI,LE,IntJ
jmp :bogus
;nos
mov errat,#$
Skc IntI,Eq,IntJ
skip
jmp :bogus
mov errat,#$
Skc IntI,Gt,IntJ
skip
jmp :bogus
mov errat,#$
Skc IntI,GE,IntJ
skip
jmp :bogus
:ILTJOut
mov w, IntJ
mov w, IntI-w
sz
jmp :IEQJOut
;IEQJ
;yess
mov errat,#$
Skc IntI,Eq,IntJ
jmp :bogus
mov errat,#$
Skc IntI,LE,IntJ
jmp :bogus
mov errat,#$
Skc IntI,GE,IntJ
jmp :bogus
;nos
mov errat,#$
Skc IntI,NE,IntJ
skip
jmp :bogus
mov errat,#$
Skc IntI,Lt,IntJ
skip
jmp :bogus
mov errat,#$
Skc IntI,Gt,IntJ
skip
jmp :bogus
:IEQJOut
mov w, IntI
mov w, IntJ-w
sc
jmp :IGTJOut
:IGTJ
;yess
mov errat,#$
Skc IntI,NE,IntJ
jmp :bogus
mov errat,#$
Skc IntI,Gt,IntJ
jmp :bogus
mov errat,#$
Skc IntI,GE,IntJ
jmp :bogus
;nos
mov errat,#$
Skc IntI,Eq,IntJ
skip
jmp :bogus
mov errat,#$
Skc IntI,Lt,IntJ
skip
jmp :bogus
mov errat,#$
Skc IntI,LE,IntJ
skip
jmp :bogus
:IGTJOut
djnz IntJ,:insideloop
djnz IntI,:outsideloop
DoIf 1,lt,0 ;1=WReg or RTCC. RTCC is only going to get used in ISRs so just assume its W
clr 1
doendif
clr 2
doif 2,eq,0 ;Bank 0 registers so no bank but do load W.
clr 3
doendif
clr 4
doif 5,IsZero
clr 6
doendif
clr 7
repeat
clr 8
repeat
xor 8, 8
until 9, LEN, 8
until 9,IsNotZero
repeat
clr 10
while 11,IsZero
repeat
clr 12
forever
doif 16,eq,17 ;two registers in same (non zero) bank. One bank needed.
clr 18
doendif
clr 19
doif 20,eq,$30 ;two registers in two different banks.
clr 21
doendif
clr 22
doif 23,eq,24
clr 25
doelseif 26,lt,27
clr 28
doelse
clr 28
doendif
clr 29
push WReg
push 30
pop 31
pop PC
doif 32,ltN,33
clr 34
doelseif 35,gtN,36
clr 37
doelseif 37,gtN,38
doendif
clr errat
doif 1, LtN, 0
doif 2, Lt, 33
doendif
doendif
;And now, lets KICK IT UP A BIT!!!
DoSelect
DoCase 23,eq,24
clr 25
DoCase 26,eq,27
clr 28
DoSelect
DoCase 29,eq,30
clr 31
DoIf 32,EqN,32
clr 33
DoElseIf 34,Lt,35
clr 36
DoElse
clr 37
DoEndIf
DoCase 27,eq,25
clr 25
DoCaseElse
clr 25
DoCaseEnd
DoCaseElse
clr 25
DoCaseEnd
:bogus
break
end
file: /Techref/scenix/keymacs.src, 40KB, , updated: 2023/5/11 11:06, local time: 2025/5/3 10:37,
|
| ©2025 These pages are served without commercial sponsorship. (No popup ads, etc...).Bandwidth abuse increases hosting cost forcing sponsorship or shutdown. This server aggressively defends against automated copying for any reason including offline viewing, duplication, etc... Please respect this requirement and DO NOT RIP THIS SITE. Questions? <A HREF="http://www.linistepper.com/Techref/scenix/keymacs.src"> scenix keymacs</A> |
Did you find what you needed?
|