logo
background
 Home and Links
 Your PC and Security
 Server NAS
 Wargames
 Astronomy
 PhotoStory
 DVD making
 Raspberry Pi
 PIC projects
 Other projects
 Next >>

Using the PIC for everything

Links to all my PIC tips, tricks and 'mini-project' notes

Whilst the mid-range PIC's can tackle many complex and otherwise almost impossible applications with ease, the challenge is to minimise cost by using the cheapest baseline PIC 'whenever possible'. Baseline PIC's can be had for less than 50p each = I purchased many 16F5x chips for between 40 and 50p each (mainly from CPC as 'remaindered' stock in their 'Bargain bin' section).

The even cheaper to use 12F675 (it has an internal OSC) can be found for as little as 20p (in Qty 10pcs, eBay), as can many other PIC's for less than £1 each. These PIC's are so cheap that you will soon start using them 'for everything' (especially as the PIC can often be used in place of a higher cost 'single function' digital chip - such as divider, ADC, PWM generator etc.) !

Buying the PIC in a 'TSOP' package is (sometimes) cheaper than the DIL/DIP package version = and whilst this costs you 10-20p extra for a mini-PCB TSOP-DIP 'converter', if you use a 'bigger' PCB than the PIC TSOP really needs you can mount other devices (resistors, caps, even osc. crystals) on the same board - and make use of the extra 'pin holes' to wire this up to the rest of your circuit

Below is a mix of programming tips and tricks, common circuit tricks and all the 'mini-projects' I've used the PIC for

I hope these details proves as useful to you as it does to me !

Below, click on the '+' to expand 'in place' (includes diagrams/images) or click the title URL (to view/download the text only version).

(+) 0004 Multi byte ADD - (24bit)



(-) 0005 new PIC 33 instruction set - (macros)


;
 messg	"Steve B new PIC-33 (baseline) macro library, version 2017-08-17 (draft 2.1)"
;
; WARNING - this is the exact same file that will be INCLUDED in MPASM, so it must contain no 'uncommented' HTML  markup
;
; v2.1 Fixed problem with user specifying absolute numeric as the bit number, rather than using a redefinable variable (label)
; v2   Normalised Macro instruction names to 4 characters where possible (major exceptions ADD, SUB, AND, OR, XOR betc.)
;
; Note: to convert from 'bit number' (Bn = 0-7) to 'bit mask', MPASM accepts (1 << Bn) 1 shift left Bn places = 2^Bn
;  ~(exp)  (tild(exp)) means 1's complement (i.e. bit invert), whilst -()exp) means -1 * exp (-1 is 0xFF)
;
;
; 1) In your source code, FIRST you need to define :=
; processor (PIC chip ID, eg 16F54)
; errorlevel 0   ;sets the most detailed error reporting
; org (address)  ;sets origin of the code segment
;
; 2) You then add this macro 'set' to your code using the #include statement
;#include c:/new-PIC-33-instruction-set.inc
;
;
; Note, whilst aimed at baseline instruction set, Macros will take advantage of
; enhanced/miderange instructions (if available)
;
;start by discovering which CPU is being used
; 3 types are :-
;  baseline
;  midrange (default)
;  enhanced

test4cputype macro type,iftype
 IF processor=="iftype"
    cputype set "type"
 ENDIF
 ENDM

;start by assuming midrange (there are more than 58 midrange, but on 19 baseline and 44 enhanced)
 cputype set "midrange" ; assume midrange

;check for baseline :-
; 10F2xx (200/2/4/6, 220/2)
; 12F5xx (508/9)
; 16F5x/5xx (54,57,59,  505/6, 510/9, 526/7,  526/9(t39a) 570)
;
#ifdef processor
 test4cputype "baseline",10F200
 test4cputype "baseline",10F202
 test4cputype "baseline",10F204
 test4cputype "baseline",10F206
 test4cputype "baseline",10F220
 test4cputype "baseline",10F222
 test4cputype "baseline",12F508
 test4cputype "baseline",12F509
 test4cputype "baseline",16F54
 test4cputype "baseline",16F57
 test4cputype "baseline",16F59
 test4cputype "baseline",16F505
 test4cputype "baseline",16F506
 test4cputype "baseline",16F510
 test4cputype "baseline",16F519
 test4cputype "baseline",16F526
 test4cputype "baseline",16F527
 test4cputype "baseline",16F529
 test4cputype "baseline",16F570
#endif

; Baseline do no have readable TRIS registers - instad they have a TRIS command that writes a latch
;  (on mid-range devices, the TRIS and OPTION commands are 'do not use')
; Baseline also lack the weak-pull-ups (control reg) and Interrupts (no Interrupt on Change reg, no RTI instruction)
; The main difference between the baseline (33) and mod-rnage (35) Instruction set is the ADDLW (ADD 0xNN to Acc) and SUBLW (Subtract Acc from 0xNN, result to Acc)



; check for enhanced :-
;
#ifdef processor
 test4cputype "enhanced",12F1501
 test4cputype "enhanced",16F1503
 test4cputype "enhanced",16F1507
 test4cputype "enhanced",16F1822
 test4cputype "enhanced",16F1508
 test4cputype "enhanced",16F1840
 test4cputype "enhanced",16F1823
 test4cputype "enhanced",16F1509
 test4cputype "enhanced",16F1512
 test4cputype "enhanced",16F1824
 test4cputype "enhanced",16F1452
 test4cputype "enhanced",16F1513
 test4cputype "enhanced",16F1825
 test4cputype "enhanced",16F1516
 test4cputype "enhanced",16F1826
 test4cputype "enhanced",16F1455
 test4cputype "enhanced",16F1828
 test4cputype "enhanced",16F1518
 test4cputype "enhanced",16F1827
 test4cputype "enhanced",16F1829
 test4cputype "enhanced",16F1847
 test4cputype "enhanced",16F1859
 test4cputype "enhanced",16LF1902
 test4cputype "enhanced",16LF1903
 test4cputype "enhanced",16LF1904
 test4cputype "enhanced",16LF1906
 test4cputype "enhanced",16LF1907
 test4cputype "enhanced",16F1782
 test4cputype "enhanced",16F1933
 test4cputype "enhanced",16F1829L
 test4cputype "enhanced",16F1783
 test4cputype "enhanced",16F1936
 test4cputype "enhanced",16F1517
 test4cputype "enhanced",16F1519
 test4cputype "enhanced",16F1786
 test4cputype "enhanced",16F1938
 test4cputype "enhanced",16F1788
 test4cputype "enhanced",16F1934
 test4cputype "enhanced",16F1526
 test4cputype "enhanced",16F1937
 test4cputype "enhanced",16F1527
 test4cputype "enhanced",16F1784
 test4cputype "enhanced",16F1787
 test4cputype "enhanced",16F1939
 test4cputype "enhanced",16F1789
 test4cputype "enhanced",16F1946
 test4cputype "enhanced",16F1947
#endif

;
; The Macro temp register should never be referenced in normal code, so don'yt need +0x100 added 
;  macro temp reg is the 'top of the lower set', so same in every Bnak & we can ignore Bank bits

 rMacro = 0x0F ; this is the same as 2F, 4F 6F 8F i.e. maps to 0F from every Bank


;
; The  'missing parameter' (0) / Acc / rN (register) / 0xNN dilemma
; We need some way to distinguish between all 4 cases
;  Since we can't change 'constants' (0xNN), we will change rN by adding 0x100
;  Acc can then be set to 0x200
; This still leaves no differnce between 0x00 and 'missing parameter',
;  however that's only a problem if 0xNN could ever be in the 'last' (missing) parameter position

; First some special cases
 rSTATUS set 3  ;Status reg


;
; The bN bits dilemma
;  User is quite likley to specify a bit position as an absolute numeric value (0-7)
;  This prevents clever 'redefinition' of the variable names
;   Instead, to get a 'bit patturn' from 'n' (where n = absolute 0-7) we use '1 << n' (1 shifted left 1 positiopns'
;     so for n=0, 1<<0 (1 shifted 0 times) = 0000 0001 (and n=7, 1<<7, is 1000 0000)
;   To get the inverse, use the ~ (tild) as in ~(1<OK, now let's define the actual macros

; since we are always checking for IF saveAcc, lets define a macro
;
IFsaveAcc macro mode  ; mode = save or ignored
; Cases:-
; IFsaveAcc save - check the saveAcc flag, if true, save Acc to rMacro = 1 instr
; IFsaveAcc - check saveAcc flag, if true, restore Acc from rMacro = 1 instr
;
 IF (mode=="save")
  IF saveAcc
    MOVWF rMacro ;saving Acc
  ENDIF
 ELSE
  IF saveAcc
    MOVF rMacro,0 ;restoring Acc
  ENDIF
 ENDIF
 ENDM
;


; Alias the "option" command to a more obvious name
;
 preScaler macro ;
  OPTION
 endm
;


; Define the 'reg name values' macro (so macro IF can tell the difference between 0xNN and regNN)
;
setReg macro mode ;
local rn set 0x100 ;define the start outside mormal range (for mode == false)
 IF mode           ; if normal mode TRUE, reset rn
  rn SET 0
 ENDIF
; OK lets do it (all 'rX' == my own names for registers)
 Acc SET rn         ;Acc is normally 0 (so if b=Acc, (b+0) == 0)
 INDF set rn+0x20   ;this will 'map' INDF to address 0 in all device RAM banks (except 16F54)
 rIND set INDF      ; register, Indirect
 TMR set rn+1       ;first (8bit) counter/timer 
 PCL set rn+2       ;low order byte of Prog Counter
 rSTATUS set rn+3
 FSR set rn+4      ; 'pointer' used for INDF
 rIPA set FSR      ;register, Indirect Pointer Address
 rOSCcal set rn+5  ; some chips have OSCcal instead of the 4bit portA
; NOTE that reading the Port register gets the i/o PIN value, NOT THE register !
 portA set rn+5  ;16F5x portA
 portB set rn+6
 portC set rn+7	;16F57/9 only
 portD set rn+8	;16F57/9 only
 portE set rn+9	;16F59 only
; set TRIS 'registers' so we can detect them
; Note COPY Acc,TrisX macro uses "TRIS dest-0x1000"
 rTrisA set 0x1000+5 ;
 rTrisB set 0x1000+6 ;
 rTrisC set 0x1000+7 ;
 rTrisD set 0x1000+8 ;
 rTrisE set 0x1000+9 ;
; set Option reg so it can be detected
 rOption set 0x1000
;
; On basefline devices, the registers are arranged into 'banks' of 32, and each bank is addressed in two 'halves' of 16
;  The first 16 addresses (0x00-0x0F) in all banks 'map' to the same set of special registers
;  Only the 'hi' half of each bank (0x10-0x1F) map to unique data registers
    this means yoi have no more than 128 'top half' data registers (plus a handfull from the lower half), rather than 256
;   it also means (for example) INDR (or rIND), which is 'normally' address 0x00 can also be accessed as 0x20, 0x40, 0x60 etc.
;   == however we wnant to avoid confusion, so should only define names for actual registers 
; Set now the regNN set, from reg31 to reg1 (via reg7F, reg7E, reg7D .... reg1
;
local rname set 0x7F  ;note, hex address
 while rname
 reg#v(rname)=rn+rname ;should get us names 'reg00' to 'reg7F' (or maybe reg0 to reg7f) values 0-7F
 rname set rname-1
 endw
;
ENDM
;




; ***************************************
; ** Start of actual Macro definitions **
; ***************************************
;

;
; COPY and LOAD = replaces all the nonsense MOVF, MOVWF, MOVLW, TRIS, OPTION  ...
;  COPY does exactly that, LOAD is included to support LOADing fo constants (0xNN to dest)
; Note. A constant is 0x00-0xFF .. this means 'everything else (Acc, RegN) MUST be defined as something 'outside' the 00-FF range
; 
;
COPY macro s,d  ; COPY - is always copy the contents of source (Register/Acc) to dest (Acc/Register)
; Cases:-
; (COPY 0xNN,dest = is re-direted to LOAD)
; Copy Acc,reg = 1 inst (also TRIS and OPTION)
; Copy reg,Acc (or COPY reg) = 1 inst
; Copy regX,regY = 2/4 (saveAcc TRUE/FALSE)
;
 setReg FALSE ;set detect reg mode
 IF s < 0x100 ;check if first param is Acc/reg
  setReg TRUE ;first param is not a reg or Acc, assume 0xNN
  LOAD s,d     ;re-direct to LOAD command
 ELSE ;s is reg/Acc
   setReg TRUE ;set the reg back
    IF s == Acc ;source is Acc ?
	  IF d==rOption ;
        OPTION
      ELSE
        IF d>0x1000 ;tris ?
          TRIS d-0x1000 ;yes
        ELSE ;must be reg
          MOVWF d   ;yes, s is Acc, and dest must be reg
		ENDIF
	  ENDIF
    ELSE ;no, source is reg, what's d ?
	  IF d == Acc ;s is reg, dest is Acc ?
        MOVF s,0	;yes, Acc is dest
      ELSE ;s and d are both reg, bow it's more complicated
        IFsaveAcc "save" ;+1 insr to save Acc
		MOVF s,0          ;source to acc
		MOVWF d           ;acc to dest
        IFsaveAcc        ;+1 inst to restore Acc
      ENDIF
    ENDIF
 ENDIF
 ENDM
;
;

;
 LOAD macro s,d  ; loads immediate data source to Acc or to Reg dest, BUT LOAD can be used instead of COPY
; Cases :-
; LOAD 0xNN,Acc or LOAD 0xNN (1 inst)
; LOAD 0xNN, rOption (Acc lost, 2)
; LOAD 0xNN, rTrisX (Acc lost, 2)
; LOAD 0xNN,Reg (Reg not INDF) 2/3*/4 inst (saveAcc = false/true, *powers of 2 +/-1 or neg power of 2)
; 
; Note, if s is not an immediate value, redirect to COPY
;
 setReg FALSE
 IF s < 0x100 ; source is immediate (0x00-0xFF) ?
   setReg TRUE ;yes, set reg values back
   IF (d + 0) == 0 ;dest is Acc (or missing, still Acc)
	 MOVLW s			;move literal (s) to Acc
   ELSE ; OK it's immediate to reg
   ; start by sorting the 'special regs'
    IF d > 0x1000 ;Tris ?
	  MOVLW s			;move literal (s) to Acc
	  TRIS d-0x1000
	  EXITM
	ENDIF
	IF d = rOption
	  MOVLW s			;move literal (s) to Acc
	  OPTION
   	  EXITM
	ENDIF
   ; If value is 0, do it in 1
    IF s==0x00
	 CLR d
	 EXITM
	ENDIF
    ; we can do any 'power of 2' in 2 without worrying about saving Acc
local bname set 8
  while bname ;loop whilst bname is non-0
    bname set bname-1 ;start at 7, run to 0
    IF s==b#v(bname) ;value is power of 2 ?
      setBits2n
      CLR d
      Bset d,b#v(bname)
	  setReg true
      EXITM
    ENDIF
  endw
    ; also 0xFF in 2
	IF s==0xFF
	  CLR d
	  DEC d
	  EXITM
	ENDIF
    ; OK, if not saving Acc, do it in 2
	IF !saveAcc
      MOVLW s		;move literal (s) to Acc
      MOVWF d		;value to d reg
	  EXITM
	ENDIF
	; if here, then saving Acc. That would cost 4 .. but we can do some values in 3
	; we can:- clr, invert(comf), dec,inc, bitset,bitclr, nibble swap (also rotL,rotR but we can't depend on Cy)
	; have to start with Clr, then any 2 others (although can't see how nibble swap helps)
	;  can't be an exact power of 2, those done above, but +/-1 (inc or dec) or neg power ..
	bname set 8
  while bname ;loop whilst bname is non-0
    bname set bname-1 ;start at 7, run to 0
    IF s==b#v(bname)+1 ;value is power of 2 + 1?
      setBits2n
      CLR d
      Bset d,b#v(bname)
	  INC d
	  setReg true
      EXITM
    ENDIF
	IF s==b#v(bname)-1 ;value is power of 2 - 1?
	  setBits2n
      CLR d
      Bset d,b#v(bname)
	  DEC d
	  setReg true
      EXITM
    ENDIF
	IF s==nb#v(bname) ;value is negative power of 2 ?
	  setBits2n
      CLR d ;0x00
	  DEC d ;(or COMF d,1) = 0xFF (neither inst. effects Cy)
      Bclr d,b#v(bname) ;neg power of 2
	  setReg true
      EXITM
    ENDIF
  endw
	; OK, now do it in 4
    COPY Acc,rMacro  ;save Acc
    MOVLW s			;move literal (s) to Acc
    MOVWF d		    ;value to d reg
    COPY rMacro,Acc  ;restore Acc
	EXITM
  ENDIF
 ELSE ; source is not immediate, assume COPY
   setReg TRUE ; put reg's back
   COPY s,d    ;exit to COPY
 ENDIF
 ENDM
;

;
; Arithmetic - ADD, SUBreact, ADDCy (ASS with Cy), SUBBw (Subtract with borrow) and MULtiply (tbd) 
;
;
; 
ADD macro a,b ; ADD using the normal convention, ADD a,b means ADD source a, to destination b
; The PIC-33 instruction set supports a single ADD = "ADDWF reg,n", which adds reg to Acc, with result to reg(n=1) or Acc(n=0)
;  since a+b is the same as b+a, we can use the ADDWF (Reg+Acc) for both Acc and reg destinations
;
; Cases:-
;  ADD reg,Acc or Acc,reg (1 instruction)
;  ADD immediate,Acc (3 instructions)
;  ADD immediate,reg (4/3 instructions, saveAcc true/false)
;  ADD reg,reg (4/3 instructions, saveAcc true/false)
; Specials to watch out for:-
;  ADD 1,Acc (or Add 1) = increment Acc (2 inst)
;  ADD Acc,Acc (or ADD Acc)
;  ADD regX,regY
;
; Check 'a' = can be Acc, regN or an immediate value (0xNN) (as in ADD 0xNN to Acc/Reg)
 setReg FALSE    ;set all reg outside immediate range
 IF (a < 0x100)  ;if true, then a is an immediate value, ADD that to b (Acc or reg)
;OK, adding immediate to Acc or reg
  setReg TRUE    ;restore reg real values
   IF (b+0) == 0   ;true if b zero (Acc) or missing
;OK, add a immediate to Acc
   ; deal with specail case (ADD 1,Acc)
     IF a == 1    ;inc Acc, 2 instructions
      SUBWF PCL,0  ;acc-PCL
      ADDWF PCL,0  ;acc+PCL+1
     ELSE         ;not special, 
      COPY Acc,rMacro ;current Acc to temp
	  MOV a,Acc      ;immediate to Acc
	  ADDWF rMacro,0  ;add rMacro (contains original Acc) to Acc (contains immediate), result to Acc
     ENDIF
   ELSE
; it's add immediate a to reg b
     IFsaveAcc "save"     ;need to save Acc ?
     MOV a,Acc      ;immediate to Acc
     ADDWF b,1      ;add reg (b) to Acc (contains immediate), result to reg
     IFsaveAcc      ;restore Acc if saved
   ENDIF           ;end of b test
 ELSE
; only reach here if first test was zero, so a = reg or Acc, check b
 setReg TRUE     ; get the reg numbers back (Acc must be 0)
 IF (b+0) == 0   ;true if b missing or zero (so add to Acc)
   IF a==Acc ;could be add Acc to itself
     COPY Acc,rMacro  ; yes, copy Acc
	 ADD rMacro,0     ;add rMacro(Acc) to Acc 
   ELSE
     ADDWF a,0	     ;add reg to Acc, result to Acc
   ENDIF
 ELSE
  ; here if b non-zero (must be reg)
     IF a==Acc    ;could be add Acc to reg
      ADD b,1     ;add Acc to reg, result to reg 
     ELSE         ;it's reg + reg
     IFsaveAcc "save"
     COPY a,Acc     ;copy reg(a) to Acc
     ADDWF b,1       ;add Acc contents to dest (reg(b) )
     IFsaveAcc      ;restore Acc if saved
 ENDIF
 ENDM

;
; WARNING - 'immediates' are 'fixed' at compile time !
; (so no 'cheating' with 'add one to immediate on Carry' :-) )
;

;
 ADDC macro s,d ;Same as ADDCy
  ADDCy s,d
 ENDM
;

;
 ADDCy macro s,d ;ADD source + Cy to dest
; Cases:-
;  ADDCy Acc,reg (3 instruction)
;  ADDCy reg,Acc  (5 instructions)
;  ADDCy immediate,Acc (3 instructions)
;  ADDCy immediate,reg (4/3 instructions, saveAcc true/false)
;  ADDCy regX,regY (4/3 instructions, saveAcc true/false)
;
 IF d == Acc ; dest is Acc ?
   ; dest is Acc, source is reg or immediate
   setReg FALSE  ; set reg outside 0xFF range
   IF s < 0x100 ;immediate ?
     setReg TRUE    ;restore reg real values
	 CLRF rMacro ;rMacro to z
     BTFSC rStatus,Cy ;skip if carry clear
     INCR rMacro,1 ;carry was set, rMacro to 1
     MOVLW d     ;load Acc with immediate
	 ADDWF rMacro,0 ;add rMacro to Acc
   ELSE ; source is reg, dest is Acc
     setReg TRUE    ;restore reg real values
     CLRF rMacro ;rMacro to z
     BTFSC rStatus,Cy ;skip is carry clear
     INCR rMacro,1 ;carry was set, rMacro to 1
     ADDWF rMacro,0 ;add rMacro to Acc
     ADDWF s,0       ;now add source to Acc
   ENDIF
 ELSE ; dest is a reg, we can INC that on Cy & exit via normal ADD macro
   BTFSC rStatus,Cy ;skip if carry clear
   INCR d,1 ;carry was set, rMacro to 1
   ADD s,d ;do a normal ADD
 ENDIF
 ENDM
; 


; 
ADD16 macro a,d ; ADD 2 source registers s(lsb),s+1(msb) into 2 dest. registers d(lsb),d+1(msb)
; ADD16 s,d = ADD source into dest - 6/8 instr (Cy is set on dest msb overflow)
;
 IFsaveAcc "save" ;save Acc
 MOVF s,0   ;source lsb to Acc
 ADDWF d,1  ;add acc (s lsb) into dest lsb
 Skip nCy   ;skip no Carry
 INC d+1    ;carry, inc the msb dest. (note = if msb overflows here, too bad)
 MOVF s+1,0   ;source msb to Acc
 ADDWF d+1,1  ;add acc (s msb) into dest msb, Cy set on overflow
 IFsaveAcc  ;restore Acc? (will loose Z flag, but Cy is preserved)
 ENDM
;


;
;
SUB macro s,d ;
; SUBtract s,d = by convention, SUBtract source (from) destination, so d=d-s
; Unlike ADD, ORDER COUNTS, so the PIC-33 instruction SUBWF reg,1 (Reg=Reg-W) is OK (for SUB Acc,Reg)
;  BUT the PIC-33 SUBWF reg,0 (W=Reg-W) is NOT OK for SUB Reg,Acc (which must be Acc=Acc-Reg) !
;
; SUBWF uses 2's complement arithmatic (specifically, the operation is dest = reg + (-W)
;  As a result, the Cy (rStatus b0) is 'inverted' compared to what you might expect (0 = 'borrow', 1 = 'no borrow')
;
;  b is optional (in which case destination is Acc)
; cases :-
; SUB reg,Acc or SUB reg or SUB 0xNN,Acc or SUB 0xNN = all Acc=Acc-reg/immediate, 3 inst
; SUB Acc,reg is reg=reg-Acc
; SUB 0xNN,reg is reg=reg-0xNN
; SUB reg(a),reg(b) means b=b-a
; Specials :-
;  SUB 1,Acc (decrement Acc)
;
; start with the 'easy ones'
 IF (d + 0) == 0 ; destination missing or d=Acc ?
; Yes, it's Acc=Acc-Reg or Acc=Acc-immediate, we don't care which, as the code is the same
     COPY Acc,rMacro   ;save Acc to rMacro
	 LOAD s           ;load reg or immediate to Acc
	 SUBWF rMacro,0      ;(W=Reg(Acc)-W(immediate))
 ELSE
; OK dest not Acc, must be reg, what's the source ?
   Acc SET 0x100 ; source could be Acc, better test for it
   IF a == 0x100
    SUBWF d,1  ; yes, source is Acc, reg=reg-Acc
   ELSE        ; source is reg or immediate, don't care which, logic is same
	 IFsaveAcc "save" ; saving ?
	 LOAD s           ;load immediate or source reg to Acc
	 SUBWF d,1       ;dest Reg= dest Reg-W(immediate or source))
	 IFsaveAcc      ;restore Acc if saved
   Acc SET 0x00 ; reset Acc flag
 ENDIF
ENDM
;

;
;
SUBB macro s,d ; Same as SUBBw (subtract source and Borrow from destination (Bw = nCy))
 SUBBw s,d
 ENDM
;

;
;
SUBBw macro s,d ; Subtract source and Borrow from destination (Bw = nCy)
; cases :-
; SUBBw reg,Acc (Acc=Acc-reg-Bw)
; SUBBw Acc,reg (reg=reg-Acc-Bw)
; SUBBw 0xNN,reg (reg=reg-0xNN-Bw)
; SUBBw regS,regD (means regD=regD-regS-Bw)
;
; If dest is Acc, 

; If dest is a reg, we can do a normal SUB and then subtract one more
 ID d>0x00

 ENDM
;


;
; Multiply requires 2 named registers, which will used for the result, LSB,MSB (that order)
;  An 'immediate' or Acc can be specified as the 'first' value, followed by the two registers LSB,MSB (that order)
;  (result will be immediate/Acc * LSB, to LSB,MSB of course)
;
;
MUL s1,msb,lsb ;(unsigned) Multiply the source s1 (can be immediate, Acc) * lsb to destination msb, lsb
; If msb is omitted, s1 (which must be a reg) becomes the msb
; Cases:-
; MUL lsb,msb = recurse call MUL msb,lsb,msb
; MUL reg,lsb,msb   33/35 inst
; MUL 0xNN,lsb,msb  33/35 inst
; MUL Acc,lsb,msb  33 inst
;
; This macro implementation uses a 'max speed' approach
;  == that means an 8 step 'shift and add' unwound loop @4 instructions per bit = 32 + setup (saveAcc true cost +2 CPU CLKs) 
; For a a minimium code approach, use the MULT subroutine
;
; must have s1,lsb,msb, so check for msb
 setReg false ;do we have a msb ?
 IF (msb + 0) == 0 ;no, recursive call
   setReg true
   MUL msb,lsb,msb
   EXITM
 ENDIF
; Processing starts when s1 is in Acc (saveAcc is optional)
; note, setReg is still false
 IF lsb < 0x100 ;s1 is immediate ?
   IFsaveAcc "true"          ;save Acc if set
   LOAD lsb ;load Acc
 ELSE ;not immediate, could be Acc ?
   setReg false ;need to detect 0xNN
   IF s1 == Acc
     ;do nothing
   ELSE ; it's a reg
    IFsaveAcc "true"          ;save Acc if set
    COPY s1,Acc    
   ENDIF
 ENDIF
; OK, we have value in Acc, shift lsb, add on Cy to msb
 setReg true ;get reg values back (if not already)
; existing lsb value will all be shifted out, but msb must start 0x00
 CLR msb
 ; OK lets go for first step .. 1 setup + 4 inst per step, so 33 instr for all 8 bits
 RRF lsb,1      ;lsb b0 to Cy, initial Cy 'x' to b7 (don't care since it's going to be shifted out at end)
 Skip nCy       ;skip no carry
 ADDWF msb,1 ;if Cy, add (Acc) to msb, this will clear Cy (since we are adding to 0x00)
 RRF     msb,1         ; shift 16 bit result down one bit
 RRF     lsb,1         ; .. b7 is msb b0, x to b6 and lsb b1 to Cy
 ;
 Skip nCy      ;skip no carry
 ADDWF msb,1 ;if Cy, add s2 (Acc) to msb, 9 bit result now includes Cy
 RRF     msb,1         ; shift 16 bit result down one bit
 RRF     lsb,1         ; .. x to b5, and lsb b2 to Cy
;  
 Skip nCy      ;skip no carry
 ADDWF msb,1 ;if Cy, add s2 (Acc) to msb, 9 bit result now includes Cy
 RRF     msb,1         ; shift 16 bit result down one bit
 RRF     lsb,1         ; .. x to b4, and lsb b3 to Cy
 ;  
 Skip nCy      ;skip no carry
 ADDWF msb,1 ;if Cy, add s2 (Acc) to msb, 9 bit result now includes Cy
 RRF     msb,1         ; shift 16 bit result down one bit
 RRF     lsb,1         ;.. x to b3, and lsb b4 to Cy
;  
 Skip nCy      ;skip no carry
 ADDWF msb,1 ;if Cy, add s2 (Acc) to msb, 9 bit result now includes Cy
 RRF     msb,1         ; shift 16 bit result down one bit
 RRF     lsb,1         ; .. x to b2, and lsb b5 to Cy
;  
 Skip nCy      ;skip no carry
 ADDWF msb,1 ;if Cy, add s2 (Acc) to msb, 9 bit result now includes Cy
 RRF     msb,1         ; shift 16 bit result down one bit
 RRF     lsb,1         ;.. x to b1, and lsb b6 to Cy
;  
 Skip nCy      ;skip no carry
 ADDWF msb,1 ;if Cy, add s2 (Acc) to msb, 9 bit result now includes Cy
 RRF     msb,1         ; shift 16 bit result down one bit
 RRF     lsb,1         ;.. x to b0, and lsb b7 to Cy
;  
 Skip nCy      ;skip no carry
 ADDWF msb,1 ;if Cy, add s2 (Acc) to msb, 9 bit result now includes Cy
 RRF     msb,1         ; shift 16 bit result down one bit
 RRF     lsb,1         ;.. x to Cy, result is complete
;
 setReg false
 IF s1 == Acc ;did we change Acc ?
       ; no, Acc not changed, do nothing
 ELSE  ;yes, restore if saved
  IFsaveAcc   ;if saved, restore Acc (rMacro is not effected by setReg true/false)
 ENDIF
 setReg true ;restore the reg flags (address values)
 ENDM 
;

;
SMUL s1,lsb,msb ;signed Multiply the source s1 (can be immediate, Acc) * lsb to destination msb, lsb
; If msb is omitted, s1 (which must be a reg) becomes the msb
; Cases:-
; MUL lsb,msb = recurse call MUL msb,lsb,msb
; MUL reg,lsb,msb   33/35 inst
; MUL 0xNN,lsb,msb  33/35 inst
; MUL Acc,lsb,msb  33 inst
;
; check source for -ve, 2's comp any found and do a unsigned MUL
; on 'exit' if (only) one of the source was -ve, 2's comp the result 

 ENDM
;


;
;Logical = TEST reg,(bit), AND, OR, XOR (s,d)
; AND .. 1+1 = 1, all other 0
; OR .. 0+0 = 0, all other 1
; XOR .. 0+0 / 1+1 = 1, other 0

;
;
 TEST r,b  ;Test for bit condition (set, not set). The Z flag is set on the result
; NOTE rather than use this as part of a 'conditional branch' operation,
;  the more direct SKIP reg,n and conditional BRAnch (JMP,JUMP) r,b,d or CALL r,b,d should be used 
; cases:-
; TEST Acc (TestZ,Acc) = Test if Acc zero (1 inst)
; TEST reg (TestZ,reg)= Test if reg zero (1 inst)
; TEST Acc,b0-b7 = Test if Acc bit is set (Z flag is set if bit is '1') - 4 inst
; TEST Acc,nb0-nb7 = Test if Acc bit is NOT set (Z flag is set if bit is '0') - 3 inst
; TEST reg,b0-b7 = Test if regN bit is set (Z flag is set if bit is '1') - 3 inst
; TEST reg,nb0-nb7 = Test is regN bit is NOT set (Z flag is set if bit is '0') - 3 inst
;
 IF (b+0) == 0 ;bit (2nd parameter) ?
   IF r==Acc ;no 2nd, test Acc?
     ANDLF 0xFF ;TestZ Acc
   ELSE
     MOVF r,1   ;TestZ reg (move reg to itself)
   ENDIF
 ELSE ; we have 2 params, first is Acc/reg other bit or not bit
   setBits2n   ;n0-7 = 0-7, nb0-7=FF-FE (convert to 0-7 by subtracting from 0xFF)
   IF r==Acc   ;
     IF b<0xF0 ;bit or nbit ?
       	 ; Acc test for bit==1, 4 inst
         MOVWF rMacro   ;copy Acc to rMacro, if Acc0, Z flag is set
         BCS rMacro,b   ;sets the bit we want to test to '1' (has no effect on flags)
	     COMF rMacro,1  ;invert reg (so bit we want to test is now '0')
         XORWF rMacro,1 ;result is 0, except if tets bit is '1' in Acc
     ELSE
        ;Acc test for not bit (i.e Z flag on bit == 0), 3 inst
	    CLRF rMacro     ;set Z flag
	    BSF rMacro,0xFF-b  ;set bit (has no effect on flags)
	    ANDWF rMacro,1  ;AND Acc to rMacro, if bit was 0, then Z flag now set	 
	 ENDIF
   ELSE ;must be reg
     IF b<0xF0 ;bit or nbit ?
        ;test for reg bit==1
	    CLRF rMacro    ;set Z flag
        BTFSC r,b    ;skip if bit is 0
        COMF rMacro,1  ;invert rMacro (since rMacro was 0, this will clear Z bit)
	 ELSE
        ;test for reg bit==0
	    CLRF rMacro    ;set Z flag
        BTFSS r,0xFF-b ;skip if bit is 1
        COMF rMacro,1  ;invert rMacro (since rMacro was 0, this will clear Z bit)
	ENDIF
 ENDIF
 setReg TRUE ;put bits back (b0-b7 0x01-0x80, nb0-nb7 0xFE-0x7F)
 ENDM
;

;
TestZ macro r ;Set Z flag of reg/Acc is zero
;
 IF r==Acc    ;Acc ?
   ANDLF 0xFF ;TestZ Acc
 ELSE
   MOVF r,1   ;TestZ reg (move reg to itself)
 ENDIF
 ENDM
;

;
;
AND macro s,d  ;AND source to destination
; cases:-
; AND reg, Acc (AND reg) (1 inst)
; AND Acc, reg (1 inst)
; AND 0xNN,Acc (AND 0xNN) (1 inst)
; AND 0xNN,reg (2/4, saveAcc true/false)
; AND regX,regY (2/4, saveAcc true/false)
; Special case:-
; AND Acc,Acc (AND Acc) == testZ Acc (1 inst)
;
; source is immediate ?
 setReg FALSE
 IF s<0x100
  ;yes, it's an immediate value, what's the dest ?
  setReg TRUE
  IF (d + 0) == 0 ;dest = Acc ?
    ANDLW s ;source is immedate, dest Acc
  ELSE
    ;dest exists and must be reg, 
    IFsaveAcc "save"
	LOAD s ;immediate to Acc
	ANDWF d,1 ;AND acc to reg
	IFsaveAcc      ;restore Acc if saved
  ENDIF
 ELSE ;source is reg or Acc, dest is reg or Acc
 setReg TRUE
 IF s==Acc
   IF (d + 0) == 0 ;AND Acc,Acc is a test of Acc for Zero
     ANDLF 0xFF ; == TestZ Acc
   ELSE ;s is Acc, d must be reg
     ANDWF d,1
   ENDIF
 ELSE ;s is reg, d is acc or reg
   IF d==Acc ;
     ANDWF s,0 ;AND reg Acc to Acc
   ELSE
   ; OK, AND reg with reg, source has to go to Acc
     IFsaveAcc "save"
	 COPY s  ;copy source reg to acc
     ANDWF d,1 ;AND acc to dest reg
	 IFsaveAcc ;put acc back ?
   ENDIF
 ENDIF
 ENDM
;	  


;
OR macro s,d  ; OR source with (into) destination
; cases (same as AND):
; OR reg, Acc (OR reg) = 1 inst
; OR Acc, reg = 1 instr
; OR 0xNN,Acc (OR 0xNN) = 1 inst
; OR 0xNN,reg = 2/4 inst (saveAcc true/false)
; OR regX,regY =
;  
 setReg FALSE ; testing for immediate
 IF s<0x100 ;yes, it's immediate, but what's the dest ?
   setReg TRUE
  IF (d + 0) == 0 ;Acc?
   ;yes, dest is Acc, source is immediate
   IORLW s ;OR literal with A, result to Acc
  ELSE ;dest must be reg, source is immedaite
   IFsaveAcc "save"
   LOAD s ;overwrite Acc with immediate
   IORWF r,1 ;OR reg with A, result to reg  
   IFsaveAcc      ;restore Acc if saved
  ELSE ; s not immediate, either Acc or reg
   IF s==Acc ;source is Acc, if so dest == reg
     IORWF d,1  ;OR Acc with reg, result to reg
   ELSE ; s must be reg, dest is Acc or reg
    IF d==Acc
	 IORWF s,0 ;reg with A, result to A
	ENDIF
	
else
	if (a + 0) == Acc
		IORWF a,1 ;reg with A, result to reg
	else
		IORLW a ;literal with A, result to A 
	endif
endif
endm
;


;
XOR macro a,b  ;
; cases (same as AND):
; XOR reg, Acc (OR reg)
; XOR Acc, reg
; XOR 0xNN,Acc (OR 0xNN)
; XOR 0xNN,reg
; XOR regX,regY
; 

if (b + 0) == Acc
	XORWF a,0 ;reg with A, result to A
else
	if (a + 0) == Acc
		XORWF a,1 ;reg with A, result to reg
	else
		XORLW a ;literal with A, result to A 
	endif
endif
endm
;

;
;
INV macro s,d  ; INVert (1's complement), aka NEGate
; Note Z flag is set on ALL results
; cases :-
; INV Acc (1 inst)
; INV reg (1 inst)
; INV Acc, reg (2 inst)
; INV reg, Acc (1 inst)
; INV regX,regY (3/5, saveAcc true/false)
;
 setReg false    ;can't have Acc=0x00 when testing for 'no dest'
 IF (d + 0) == 0 ;check if dest exists
   setReg true   ;put reg values back 
  IF s==Acc    ;no dest, INV Acc ?
	XORLW 0xFF ;yes, invert Acc
  ELSE         ;no, INV reg
   	COMF s,1 ;INVert reg (to itself)
  ENDIF
 ELSE ;dest exists, it's acc (to reg), reg to acc or reg to reg
   IF d==Acc ; dest is Acc ?
	COMF s,0 ;yes, must be INVert of reg to Acc
   ELSE      ;no, dest is reg, could be Acc to reg, reg to reg
	IF s==Acc   ; source acc ?
	  COPY s,d  ;yes, INV Acc to reg = start with copy
	  COMF d,1  ;now INVert the dest reg (to itself)
	ELSE ;no, it's reg to reg will need to use Acc intermediate step
	  IFsaveAcc "save"  ;if save, cost +1 inst
	  COPY s,Acc        ;
	  COPY Acc,d        ;
	  IFsaveAcc         ;restore Acc if saved, cost +1 inst
      COMF d,1    ;INVert dest reg = done here so on exit Z flag is correct !!
   ENDIF
 ENDIF
 ENDM
;

;
 INVERT macro s,d  ; INVERT is the same as INV
 INV s,d
 ENDM
;

;
 NEG macro s,d  ; NEG is same as INV
 INV s,d
 ENDM
;

;
 NEGATE macro s,d  ; NEGATE is same as INV
 INV s,d
 ENDM
;


;
;
CMPR macro a,b  ; Compare b-a == sets Z flag on equal, Cy if a is larger (ie. it's b-a, source a FROM dest b))
; See also Skip Acc/reg,0xNN
; WARNING, Acc is always lost !! (restore destroys Z flag)
; cases:
; CMPR Acc (testZ Acc) (= 1 inst)
; CMPR reg (testZ reg) (= 1 inst)
; CMPR Acc,reg = set flags on reg-Acc (= 2)
; CMPR reg,Acc = flags on Acc-reg (= 3)
; CMPR 0xNN,Acc (CMPR 0xNN) = flags on Acc-0xNN (= 2)
; CMPR 0xNN,reg = flags on reg-0xNN (= 2)
; CMPR regS,regD = flags on RegD-regS (= 2)
;
; testZ case ?
 setReg FALSE ; can't have Acc=0 when looking for missing d
 IF (b+0)==0 ;dest specified ?
   IF a<0x100 ;no dest, but watch out for 'CMPR 0xNN' shorthand case
     COMPR a,Acc ;recurse call, setReg will be corrected next time around
   ELSE       ;no dest, just testing for zero
   setRegTrue ;get Acc=0 and actual reg addresses back  
     IF a==Acc ;test z Acc?
	   AND 0xFF,Acc ;all 0 = Z flag
	 ELSE ;must be test reg 0
	   MOVF a,1 ;
     ENDIF
   ENDIF ;OK, that's all z tests done
 ELSE ; setreg is still false so might as well check for 0xNN next
   IF (a < 0x100) ;0xNN immediate value ?
   setReg TRUE
     IF (b+0)==0 ;compare (Acc-immediate) ?
	   COPY Acc,rMacro    ;yes, SUBWF is reg-Acc (always), so we need Acc in reg, immediae in Acc
       SUBWF rMacro,0     ;reg-Acc (always), result to Acc
     ELSE  ;it's compare immediate to reg
	   LOAD a         ;load Acc with immediate
	   SUBWF b,0     ;reg-Acc (always), result to Acc
     ENDIF
   ELSE  ; a not immediate, so it's acc reg, reg acc, regA regB
   setReg TRUE
     IF a==Acc ;compare Acc to reg ? (reg-Acc)
       COPY Acc,rMacro ;COPY Acc
       SUBWF b,0     ;SUBWF is reg-Acc (always), result to Acc
     ELSE ;a is reg, b Acc or reg
       IF b==Acc ;reg to Acc (Acc-reg) case ?
         COPY Acc,rMacro ;copy Acc
	     COPY b         ;copy reg (b) to Acc
         SUBWF rMacro,0  ;SUBWF reg-Acc (always), result to Acc
	   ELSE ;regB-regA case = Acc will always be lost as restore (copy rMacro,Acc) will destroy the Z flasg
	     COPY a         ;reg a to Acc
         SUBWF b,0      ;regb-Acc(regA) (always), result to Acc
	   ENDIF
    ENDIF
 ENDIF
 ENDM
;

;
;
COMPARE macro a,b  ; Same as CMPR, compare b-a == sets Z flag on equal, Cy if a is larger (ie. it's b-a, source a FROM dest b))
 CMPR a,b
 ENDM
;


;
COMP macro s,d  ; COMPlement = 2's Complement (INV+1 aka NEG+1) source to dest. Z flag set on result.
; Cases:-
; COMP Acc (COMP Acc to itself) = 2,1 inst
; COMP Acc,reg = 2 instr
; COMP reg (COMP reg to itself) = 2 instr
; COMP reg,Acc
; 
; Easy way to do this is to subtract (source) from 0 (remember SUBWF is reg(0)-w, always)
; WARNING: the PIC-33 'COM' instruction performs a NEGATE !!! (i.e. it's a "1's complement")
; To get COMP, you NEG and add 1, however you can't add to or inc the accumulator
;  but you can Dec a reg to Acc and then negate
;
 IF a==Acc; COMP Acc?
   IF (b+0) == 0 ;Acc in place ?
     ;yes, Acc to /Acc + 1
	 ;SUBLW 0x00 ;midrange only
	  CLRF rMacro
	  SUBWF rMacro,0 ;0-Acc to Acc
	ELSE ;Acc to reg(b)
	  CLRF b
	  SUBWF b,1 ;0-Acc to reg(b)
	ENDIF
  ELSE ;a must be reg, but to itself or to Acc ?
    IF (b+0) == 0 ;COMP reg in place ?
      INCF a,1  ;reg(a)-1
      COMF a,1  ;neg(reg(a)-1) == neg(reg(a)) +1
    ELSE ; COMP reg to Acc
	  LOAD 0x01  ;
	  SUBWF a,0  ;reg(a)-Acc to Acc
	ENDIF
  ENDIF
 ENDM
;


;
SWAP macro a,b  ; Swap a and b
; Cases:-
; SWAP Acc,reg or SWAP reg,Acc (= 3 inst)
; SWAP reg,reg (= 5/7 inst)
; [SWAP with no parameters (or SWAP 0,0) = FLIP the INDF pointer FSR (reg 4) ??]
;
 IF a == Acc ; if Acc is first param, reg must be second
   XORWF b,1
   XORWF b,0
   XORWF b,1
   EXITM
 ENDIF
 IF b == Acc ;if b acc, a must be reg
  XORWF a,1
  XORWF a,0
  XORWF a,1
  EXITM
 ENDIF
; OK, just the swap two registers case left
 IFsaveAcc "save" ; +1 if saving Acc
 COPY a,Acc     ; get a reg to Acc 
 XORWF b,1      ;swap b with Acc (which is a)
 XORWF b,0
 XORWF b,1
 COPY Acc,a     ;Acc (now b) to a
 IFsaveAcc "save" ; +1 if saving Acc
ENDM
;

;
;
FLIP macro a ; FLIP the register pointed to by the INDF (indirect addressing) pointer FSR (register 4)
	COMF 4,1
endm
;


;
;
CLR macro a  ; Clear reg, Acc or WDT, all = 1 inst
 IF a == WDT	; Clear Watchdog Timer ?
	CLRWDT
	exitm
 ENDIF
 IF a = Acc	; Acc ?
	CLRW
 ELSE		; not Acc, must be reg
	CLRF a
 ENDIF
 ENDM
;


;
INC macro s,d  ; INCrement (see also DECrement) source to (optional) destination. Z flag on reult
; Normally you can't INC (or DEC) the Acc, however we can by using ADD/SUB PCL
; Cases:-
; INC Acc = 2 inst
; INC reg = 1 inst
; INC Acc,reg = 2 inst
; INC reg,Acc = 1 inst
;
 IF (d + 0) = 0 ;no dest parameter, it's INC Acc or INC reg
   IF s == Acc ; INC Acc
; WARNING = fails when this code straddles an 8bit (255-0) address boundary ...
     SUBWF PCL,0	;subtract the program counter (n) from Acc
     ADDWF PCL,0 ;add Program Cntr (n+1) to Acc, result = Acc+1
   ELSE ; INC reg
     INCF s,1 ; INC register
   ENDIF
 ELSE ; d exists (either Acc to reg or reg to Acc)
  IF s == Acc ; INC Acc to reg (b) = actually COPY Acc to reg, then INC reg
	MOVWF d		; Acc to reg
	INCF d,1	; INC the register in place
  ELSE
	INCF s,0	; INC register (a) to Acc (b)
  ENDIF
 ENDIF
 ENDM
;


;
DEC macro s,d  ; DECrement source to (optional) dest. Z flag on result
; Cases:-
; DEC Acc = 1/2 inst (midrange/baseline)
; DEC reg = 1 inst
; DEC Acc,reg = 2 inst
; DEC reg,Acc = 1 inst
 IF (d + 0) = 0 ;no b parameter, DEC Acc or DEC reg
	IF s == Acc ; DEC Acc
	 IF cputype="basline"
      ADDWF PCL,Acc  ;add PCL
	  SUBWF PCL,Acc  ;sub PCL, 1 higher than add so Acc = Acc-1
	 ELSE
	  ADDLW 0xFF ; Acc + '-1' (this instruction does not exist on baseline CPU)	 
	 ENDIF
	ELSE ;DEC reg
      DECF s,1 ; DEC register
	ENDIF
 ELSE
 ; d exists (either Acc to reg or reg to Acc)
   IF s == Acc ; DEC Acc to reg (b) = actually COPY Acc to reg, then DEC reg
     MOVWF d		; Acc to reg
     DECF d,1	; DEC the register in place#
   ELSE
	DECF s,0	; DEC register (a) to Acc (b)
   ENDIF
 ENDIF
 ENDM
;


;
; INC and DEC, Branch on result Z/nZ
; NOTE - BnZ is faster than BZ
;
;
IncBnZ macro r,d  ;; INCrement, Branch if non-Zero
; Cases :-
; IncBnZ reg,dest - 2 inst
;
 INCFSZ r,1	;Inc reg, skip if Z
 JMP d		; nZ, take the jump
 ENDM
;

;
DecBnZ macro r,d  ; DECrement, Branch if non-Zero
; Cases:-
; DecBnZ r,d = 2 inst
;
  DECFSZ r,1	;Dec reg, skip if Z
  JMP d		; nZ, take the jump
 ENDM
;

;
IncBZ macro r,d  ; INCrement, Branch if Zero
; Cases:-
; IncBZ r,d = 3 inst
;
 INCFSZ r,1	;Inc reg, skip if Z
 JMP $+2		; nZ, skip the jump
 JMP d		; Z, take the jump
 ENDM
;

;
DecBZ macro r,d  ; INCrement, Branch if Zero
; Cases :-
; DecBZ r,d = 3 inst
;
 DECFSZ r,1	;Dec reg, skip if Z
 JMP $+2		; nZ, skip the jump
 JMP d		; Z, take the jump
 ENDM
;


;
;BIT instructions
; bSET, bCLR, bFLP/bFLIP Source,bit{,destination}. Default destination=source
; 
; Bset reg/Acc, bitN = for Acc, OR sets '1', leaves 0's unchanged
;	BCLR n,Acc/reg = (for Acc, AND clears '0', leaves 1's unchanged)
;	BFLP n,Acc/reg = (for Acc, XOR flips on '1', leaves 0's unchanged, for reg have to test bit)
; For SET,CLR,FLP if reg/Acc is mising, then n = Status bit (Cy = b0, DC = b1, Z = b2)
;
; The problem is that the user may specify a number rather than a label (eg '1' rather than 'bit1')
;  To 'invert' (1's complement, invert bits) mpasm uses the tild '~' synbol ('-' is 2's complement, invert + 1)
;  To convert a bit number n, into a '000x00' type patturn, use 1 << n 

;
 BSET macro s,n,d  ; n = bit number (b0-b7)
; Cases:-
; Bset reg/acc,n = 1 inst
; Bset reg,n,Acc = 2 inst
; Bset Acc,n,reg = 2 inst
; Bset reg1,n,reg2 = 3/5 inst (Acc lost/saved)
;
 IF (d + 0) == 0 ;destination exists ?
  ;no, dest = source
   IF s==Acc ; need n as a bit patturn, 
    IORLW 1 << n ;'0' is 1 shifted left 0 times, '1' shifted once is 000 0010 and so on (see also BCLR)
   ELSE ; s must be reg,
    BSF s,n
   ENDIF
 ELSE ;dest exists, reg to acc, or acc to reg is 'easy'
  IF s==Acc ;source acc, dest must be reg
   COPY s,d
   BSET d,n
  ELSE ; source not acc, perhaps dest is ?
   IF d==Acc
    COPY s,d
    BSET d,n
   ELSE ; neither s not dest is acc, both must be reg
    IFsaveAcc save
    COPY s,Acc
    COPY Acc,d
    BSET d,n
	IFsaveAcc
   ENDIF
  ENDIF
 ENDIF
 ENDM
;
;
;
;
BCLR macro r,n  ; BCLR Acc/reg
; Cases:-
; Bclr reg / Acc, n (for n=0 to 7) = 1 inst
 IF r==Acc ;Acc case
   setNegBits ;switch to neg bit patturn (b0 = 1111 1110 etc)
   ANDLW, n
 ELSE
   setBits2n   ;redefine n bit as a number (0-7) not a patturn (0x01-0x80)
   BCF r,n     ;clear reg r, bit n
 ENDIF
   setReg TRUE ;bits back to patturn mode
 ENDM
; 

;
;
BFLP macro r,n  ; ; Bit Flip = easy for Acc (1 CLK), harder for reg (5 CLK
; Cases:-
; Bflp Acc,n = 1 inst
; Bflp reg,n = 2/4 inst (for saveAcc true/false)
;
 IF r == Acc ; set a bit n(0-7) of the Acc, XOR =1 flips that bit, 0=unchanged
   XORLW n ;for bitN is patturn (b0-0000 0001, b1=0000 0010 etc)0000 0001
 ELSE ; r must be a reg
   IFsaveAcc "save"
   LOAD n        ;load bit patturn to Acc
   XORWF r,1     ;XOR bit patturn with reg, result to reg
   IFsaveAcc      ;restore Acc if saved
 ENDIF
 ENDM
;

;
;  CALL  k   ;Subroutine Call
; no change reqd !
;

;
AccCALL macro d ; AccCALL (CALL using Acc, must be matched with AccRTN)
; ONLY works for (return) address in low 255 address locations of current code page
; WARNING - subroutine code MUST NOT MOD Acc
;
 LOAD $+2,Acc
 JMP d
 ENDM
;

;
 AccRTN macro ; Return via Acc (to address in Lo 256 locations of current code page)
  COPY Acc,PCL ; note loads Lo 8 byte (b0-7) of PCL, b8 is cleared 
 ENDM
;


;Skip, Branch and Jump macros
; Skip, SkipSet, SkipClr
; The 'generic' approach to Skip 0xNN is to copy 0xNN to Acc, SUB, Skip on Z = 3 instructions (Acc always lost, since restore effects Z flag))
; Skip reg,0x00 is (of course) 2 inst (Copy reg to self, skip Z)
; Then the INC skip on Z and DEC skip on Z instructions allow 2 (register) special cases (still loose the Acc value)
; Skip reg,0xFF and skip reg,0x01 are the first two (1 inst, Acc lost = used as dest to avoid changing reg)
;  (it is possible to preserve Acc on Skip reg,0xFF / 0xNN by pre (or post) INC/DEC reg to itself (total 2 inst) )
;


;
SKIP Macro r,b ;alias of SKIPset / SKIPclr on status Cy/nCy etc.
;Cases:-
; Skip Z/nZ DCy/nDCy Cy/nCy Bw/nBw = skip on status reg bit set/clr
; Skip Acc,Z/nZ / Z/nZ,Acc = skip if Acc is zero
; Skip Reg,Z/nZ / Z/nZ,Reg = skip if Reg is zero
;
 IF r > 0xFF ;first parameter is Acc (0x200) or reg (0x1nn) ?
  IF b==0 ;Z ?
    SKIPclr r
  ELSE ;must be nZ
    SKIPset r
  ENDIF
 ELSE ; first not Acc or reg, maybe second is ?
  IF b > 0xFF
    IF r=0      ;yep, Z or nZ ?
	  SKIPclr b ;Z
	ELSE
	  SKIPset b ;nZ
	ENDIF
  ELSE    ;doene all reg/Acc cases, must be status 
    IF b<8 ; bit 0-7 set
     SKIPset rStatus,b ;call with reg=status, bit=first param
    ELSE ;'not' bit 8-15 (clr)
     SKIPclr rStatus,b-8
    ENDIF
  ENDIF
 ENDIF
 ENDM
;


;
SKIPz Macro s ;skip if source is zero
; Cases:-
; SKIPz Acc - 2 inst
; SKIPz regN - 2 inst (but Z flag invalid)
;
 IF s==Acc ;Acc ?
  COPY Acc,rMacro ;copy sets z flag
  BTFSS rStatus,0 ;skip if z
 ELSE ;it's a reg test
  DECF (s-0x100)     ;dec the reg
  INCFSZ (s-0x100),1 ;inc it back up, and skip on Z
 ENDIF
 ENDM
;

;
SKIPnZ Macro s ;skip if source is non-zero
; Cases :-
; SKIPnZ Acc - 2 inst
; SKIPnZ regN - 3 inst
;
 IF s==Acc
  COPY Acc,rMacro ;copy sets z flag
  BTFSC rStatus,0 ;skip if nZ
 ELSE ; reg
  DECF (s-0x100)     ;dec the reg
  INCF (s-0x100)
  BTFSC rStatus,0    ;skip if Z flag clr (nZ)
 ENDM
; 

;
SKIPset macro r,b  ; Skip (on bit) set. In each case, if the bit is set, the 'next' instruction is skipped
; Cases:-
; SKIPset Acc, bn = skip Acc bit n set
; SKIPset reg, bn = skip Reg bit n set
;

 IF (b+0) == 0 ; check for second param
   ;no second, must be skip on status reg shorthand
   SKIP rStatus,r ;call again with reg=status, bit=first param
 ELSE ;we have 2 params, r & b
   IF r==Acc ;is source r = Acc?
     COPY Acc,rMacro ;yes, copy Acc to rMacro (so we can skip on reg)
	 SKIP rMacro,b
   ELSE ;we have reg and bit, but is it bit set (b0-b7) or bit clear (nb0-nb7) ?
     setBits2n  ;set bits 0-7 for set, inverse for 'nBit' (nb0=0xFF etc)
     IF b>8 ;'nb' case ?
       BTFSC r,b+1 ;yes, skip if reg bit clear (nb0 (0xFF) +1 = bit 0 etc)
     ELSE
       BTFSS r,b ;skip if reg bit set
     ENDIF
     setReg TRUE ;put the bit patturn values back
   ENDIF
 ENDIF
 ENDM
;


;
SKIPclr macro r,b  ; Skip (on bit) instructions. In each case, if the bit is set, the 'next' instruction is skipped
;
SKIPset macro r,b  ; Skip (on bit) set. In each case, if the bit is set, the 'next' instruction is skipped
; Cases:-
; Skip Acc, bX / nBx = skip Acc bit X set, bit X clear (not set)
; Skip reg, bX / nbX = skip Reg bit X set, bit X clear (not set)
; Skip Acc, Z / nZ = skip if Acc is Zero/non-Zero
; Skip reg, Z / nZ = skip if Register is zero/non-zero
;
 IF (b+0) == 0 ; check for second param
   ;no second, must be skip on status reg shorthand
   SKIP rStatus,r ;call again with reg=status, bit=first param
 ELSE ;we have 2 params, r & b
   IF r==Acc ;is source r = Acc?
     COPY Acc,rMacro ;yes, copy Acc to rMacro (so we can skip on reg)
	 SKIP rMacro,b
   ELSE ;we have reg and bit, but is it bit set (b0-b7) or bit clear (nb0-nb7) ?
     setBits2n  ;set bits 0-7 for set, inverse for 'nBit' (nb0=0xFF etc)
     IF b>8 ;'nb' case ?
       BTFSC r,b+1 ;yes, skip if reg bit clear (nb0 (0xFF) +1 = bit 0 etc)
     ELSE
       BTFSS r,b ;skip if reg bit set
     ENDIF
     setReg TRUE ;put the bit patturn values back
   ENDIF
 ENDIF
 ENDM
;



;
;
BRA macro r,b,d ;; BRAnch on condition, reg bit (set/clear) to dest (r omitted = status bit)
; Cases:-
; BRA b,d - Branch on Status bit (Z/nZ Cy/nBw nC/Bw DC/nDC) to dest = 2 inst
; BRA Acc,b,d - Branch on Acc b0-b7/nb0-nb7 to dest = 2 inst
; BRA r,b,d - Branch on reg b0-b7/nb0-nb7 to dest = 2 inst
;
 IF (d+0)==0 ; if no 3rd parameter, then it's a status bit branch
   BRA rStatus,r,b ;
 ESLE ;ok have 3 params
   IF r==Acc ; is first parameter Acc ?
     COPY Acc,rMacro ;yes, switch to reg
	 BRA rMacro,b,d
   ELSE ; nope, r must be reg, bit or nbit ?
     setBits2n  ;set bits 0-7 for set, inverse for 'nBit' (nb0=0xFF etc)
	 IF b>8 ;'nb' case ?
	 ; yes, branch if bit is clear
	   BTFSS r,b+1 ;skip if reg bit set
	   GOTO d      ;bracnh if clear
	 ELSE ;b set
       BTFSC r,b  ;yes, skip if reg bit clear (nb0 (0xFF) +1 = bit 0 etc)
	   GOTO d     ;bracnh if set
	 ENDIF
     setReg TRUE ;put the bit patturn values back
   ENDIF
 ENDIF
 ENDM
;


;
JUMP macro r,b,d  ; Same as JMP
 JMP r,b,d
 ENDM
;

;
 JMP macro r,b,d  ; Same as BRAnch, except direct jump case
; Cases:-
; JMP d
; JMP statusBit, d
; JMP reg/Acc,bit,d
;
 IF (b+0) == 0 ;is there a second parameter ?
   BRA r,b,d ;yes, let BRAnch sort it out
 ELSE ;no 2nd (or 3rd), must be direct jump
   GOTO r
 ENDIF
 ENDM
;


;
; NOP	—	No Operation
; no change reqd !


;
;
ROTL s,d  ; ROTate Left ('up') source to dest (dest optional)
; Cases:-
; ROTL Acc (= ROTL Acc,Acc) = 2 inst
; ROTL reg (= ROTL reg,reg) = 1 inst
; ROTL Acc,reg = 2 inst
; ROTL reg,Acc = 1 inst
; ROTL regX,regY
;
 IF (d+0) == 0 ;missing dest ?
   ;yes, s must be reg or Acc
   IF s==Acc ;acc?
    COPY Acc,rMacro
	RLF rMacro,0  ;
   ELSE ;reg rotate
    RLF d,1      ;
   ENDIF
  ELSE ; not simple case
   IF s==Acc ;acc source ? (in which case reg dest)
    COPY Acc,d ;get Acc to dest
    RLF d,1      ;
   ELSE ; s must be reg, whats the dest ?
    IF d==Acc ;dest is Acc?
	  RLF s,0 ;done
	ELSE ; regX to regY
      IFsaveAcc "save"

	  IFsaveAcc     ;restore Acc if saved
    ENDIF
   ENDIF
 ENDIF
 ENDM

 if (a + 0) == Acc ;rotate Acc on it's own
	MOVWF temp		;copy Acc to temp
	RLF temp,0		;rotate temp to Acc = result is rotate Acc
exitm
endif
if (b + 0) == Acc ;Reg to Acc
	RLF b,0
else
	RLF b,1	;Reg to itself
endif
endm
;

;
ROTR s,d  ; ROTate Right ('down') source to dest (dest optional)
;
if (a + 0) == Acc ;rotate Acc on it's own
	MOVWF temp		;copy Acc to temp
	RRF temp,0		;rotate temp back to Acc = result is rotate Acc
exitm
endif
if (b + 0) == Acc ;Acc is the dest
	RRF b,0
else
	RRL b,1
endif
endm

;
;
; Nibble swap (see SWAP for swapping contents of reg and Acc)
;
NIBS macro s,d  ;
; swap nibbles in reg or from reg to Acc
 IF (d + 0) == Acc
	SWAPF s,0   ;reg to Acc
 ELSE
	SWAPF s,1   ;reg back to reg
 ENDIF
 ENDM
;


;
;
nRR macro s,n  ; Rotate source(=dest) 'in place' (i.e. not via Cy) by n bits Right
; nRR reg,1 = 2 inst.
; nRR reg,2 = 4 inst. 
; nRR reg,3 = 3 inst. (nibble swap + nRL 1)
; nRR reg,4 = 1 inst. (nibble swap)
;
; n=4 is nibble swap ...
 IF (n + 0) == 4
	SWAPF s,1   ;4 bits = nibble swap
	EXITM
 ELSE ;OK, do something more clever
 ; 5,6,7 == nRL 3,2,1
   IF n = 5
     nRL s,3
	 EXITM
   ENDIF
   IF n = 6
     nRL s,2
	 EXITM
   ENDIF
   IF n = 7
     nRL s,1
	 EXITM
   ENDIF
 ; 3 bits right is nibble swap followed by 1 bit left
   IF n == 3
     SWAPF s,1   ;do 4 bits right = nibble swap
     nRL s,1     ;and 1 bit left
     EXITM
   ENDIF
 ; OK left with 1 or 2 bits right ...
 ; the 'problem' is that normal Rotate is via Cy .. the trick, then, is to preset Cy :-)
   IF n==1
     RRF s,0  ;b0 to Cy, result to Acc
     RRF s,1  ;now Cy (was b0) to b7, reg to self
   EXITM
   IF n==2   ;Rotate Right 2
     RRF s,0  ;b0 to Cy, result to Acc
     RRF s,1  ;now Cy (b0) to b7, reg to self
     RRF s,0  ;b0 to Cy, result to Acc
     RRF s,1  ;now Cy (b0) to b7, reg to self	 
   ELSE
	 NOP ;*** ERROR *** nRR s,n Macro only supports s=reg and n=1,7
   ENDIF
 ENDIF
 ENDM
;


;
;
nRL macro s,n  ; Rotate Left source(=dest) 'in place' (i.e. not via Cy) by n bits
; nRL reg,1 = 2 inst.
; nRL reg,2 = 4 inst. 
; nRL reg,3 = 3 inst. (nibble swap + nRR 1)
; nRL reg,4 = 1 inst. (nibble swap)
;
; n=4 is nibble swap ...
 IF (n + 0) == 4
	SWAPF s,1   ;4 bits = nibble swap
	EXITM
 ELSE ;OK, do something more clever
 ; 5,6,7 == nRR 3,2,1
   IF n = 5
     nRR s,3
	 EXITM
   ENDIF
   IF n = 6
     nRR s,2
	 EXITM
   ENDIF
   IF n = 7
     nRR s,1
	 EXITM
   ENDIF
 ; 3 bits right is nibble swap followed by 1 bit Right
   IF n == 3
     SWAPF s,1   ;do 4 bits right = nibble swap
     nRR s,1     ;and 1 bit Right
     EXITM
   ENDIF
 ; OK left with 1 or 2 bits right ...
 ; the 'problem' is that normal Rotate is via Cy .. the trick, then, is to preset Cy :-)
   IF n==1
     RLF s,0  ;b0 to Cy, result to Acc
     RLF s,1  ;now Cy (was b0) to b7, reg to self
   EXITM
   IF n==2   ;Rotate Right 2
     RLF s,0  ;b0 to Cy, result to Acc
     RLF s,1  ;now Cy (b0) to b7, reg to self
     RLF s,0  ;b0 to Cy, result to Acc
     RLF s,1  ;now Cy (b0) to b7, reg to self	 
   ELSE
	 NOP ;*** ERROR *** Macro nRL s,n Rotate Left only supports s=reg and n=1,7
   ENDIF
 ENDIF
 ENDM
;

;
; nBit Shift Right, Left (nSFR, nSFL)
;  Shift fills the 'incoming' bits with 0 .. so all we need is to Clr Cy first
;  however AND 0x0F with Nibble swap can be used to speed up count = 4
; nSFR s,1 shift right 1 bit = 2 inst
; nSFR s,2 shift right 2 bit = 4 inst
; nSFR s,3 shift right 3 bit = 5 inst
; nSFR s,4 shift right 4 bit = 3 inst
; nSFR s,5 shift right 5 bit = 4 inst
; nSFR s,6 shift right 6 bit = 5 inst
; nSFR s,7 shift right 7 bit = 3 inst
;
;
nSFR macro s,n  ; Shift Right source(=dest) 'in place' (i.e. not via Cy) by n bits
; Shift Right 1 bit
 IF n == 1
   CLR Cy   ;make sure Cy is 0
   RRF s,1  ;rotate reg right
   EXITM
 ENDIF
 IF n == 2 ;Shift Right 2 bits (b7 to 5, set7,6 0)
   CLR Cy
   RRF s,1  ;rotate reg right (b7 to 6, b7=Cy(0), b0 to Cy)
   CLR Cy
   RRF s,1  ;rotate reg right (orig b7 is now b5, 7&6 now 0)
   EXITM
 ENDIF
 IF n == 3 ;Right 3, b7 shift down to b4, b7,6,5 = 0
   RRF s,1  ;(b7) to 6
   RRF s,1  ;(b7) to 5
   RRF s,0  ;(b7) to 4, result to Acc
   AND 0x1F ;7,6,5 to 0
   COPY Acc,s ;back to reg
   EXITM
 ENDIF
 IF n == 4 ;Right 4, b7 shift down to b3, b7,6,5,4 = 0
   NIBS s,Acc ;swap Reg nibbles to Acc, b7 is now in b3
   AND 0x0F   ;remove top 4 bits
   COPY Acc,s ;put back to reg
   EXITM
 ENDIF
 IF n == 5 ;Right 5, b7 shift down to b2, b7,6,5,4,3 = 0
   RRF s,1  ;b7 to 6
   NIBS s,Acc ;swap Reg nibbles to Acc, b7 is now in b2
   AND 0x07   ;remove top 5 bits
   COPY Acc,s ;put back to reg  
   EXITM
 ENDIF
 IF n == 6 ;Right 6, (b7) shift down to b1, b7,6,5,4,3,2 = 0
   RLF s,1 ;(b7) to Cy, b0=x
   RLF s,1 ;(b6) into Cy, b0=(b7), b1=x
   RLF s,0 ;b1=(b7), b0=(b6) result to Acc
   AND 0x03   ;remove top 6 bits
   COPY Acc,s ;put back to reg
   EXITM
 ENDM	
 IF n == 7 ;Right 7, b7 shift down to b0, b7,6,5,4,3,2,1 = 0	
   RLF s,1 ;put b7 into Cy
   CLR s   ;zero reg
   RLF s,1 ;b7 (saved in Cy) to b0
   EXITM
 ENDM
;


;
;
nSFL macro s,n  ; Shift Left source(=dest) 'in place' (i.e. not via Cy) by n bits


 ENDM
;


;
; MODE is either :-
; 1) Set PORT (A=5, B=6) direction bits using the value in the Accumulator
; (bit=1 sets input, bit=0 sets as output)
; When set as an output, the pin state == the current register contents
; 2) sets the TMR and Pre-scaler register
;
;
MODE macro a  ; Set the PORT Tristate or Prescaler
 if (a + 0) == 0 ; no Port defined, so must be Timer
	OPTION ;loads TMR and Pre-scaler from Accumulator
 else
	TRIS a ;loads PORT A or B input/output from Accumulator
 endif
 endm
;

;
; SLEEP	= Go into Standby mode
; no change reqd !

;
;
; RETURN with a value (or none) = 1 inst
;
RETURN macro a  ; allow return with or without defining a value
 IF (a + 0) == 0 ; this works for both 'no value' and 0
	RETLW 0
 ELSE			; yes, return with the value
	RETLW a
 ENDIF
 ENDM
;

; and thats's all !

This note last modified: 10th Sep 2017 04:33.

[top]

(+) 0006 Binary multiply methods

(+) 0007 8x8 - (multiply)

(+) 0008 8x16 - (multiply)

(+) 0011 Bi color LED driving

(+) 0012 One pin dual LED and button detect

(+) 0013 Input only multi button detect

(+) 001a One pin controls motor Fwd off Reverse

(+) 001c One pin controls 3 relays

(+) 0020 I2C bit banging

(+) 0021 I2C code

(+) 0021 Serial link - (9600 baud)

(+) 0028 RS422 RS485 drive with one PIC pin

(+) 0030 D to A conversion - (R2R DAC)

(+) 0031 Ternary DAC - (R3R)

(+) 0032 Hybrid ternary bit conversion - (code)

(+) 0035 Pulse Width Modulation - (PWM)

(+) 0040 Gearing axis sensor

(+) 005a TYC50 AC motor details

(+) 0061 16F54 2char month map - (VTI)

(+) 0062 DDmmmYYYY character map - (VTI)

(+) 1000 PIC16F684 tips and tricks

(+) 2000 18Fx tips and tricks

(+) 6500 18Fxx data Table output - (max rate)

(+) 6501 18Fxx Return with value LUT - (max rate)

(+) 6502 18Fxx extended instruction data output - (max rate)

(+) 6530 simple data transmission

(+) 6540 Using RS485

Next subject :- index

[top]