SnipPIC

Index Case statement
Converting a 3-bit number in a 8-bit mask
Divide 16-bit by 8-bit
Continious delay
Divide by 3
Compute parity
BCD to binary
BCD (packed) to binary
BCD (packed) addition
BCD (packed) subtraction
Binary to BCD (packed)
Multiple byte increment and decrement
Conversion of byte to percentage
Convert byte to HEX
Complement carry flag
Moving data block
Rotating register
CASE statement

From: Alexandr Redchuk

Wswitch  macro
wsw_last set 0                     ;setup variable only
         endm

case     macro   val, addr
         xorlw   val ^ wsw_last
         bz      addr
wsw_last set val
         endm

....

         Wswitch
         case    7,  W_CONTAINED_7
         case    51, W_CONTAINED_51
         case    12, W_CONTAINED_12
 

Converting a 3-bit number in a 8-bit mask

From: Mike Keitz

There is a trick method that works for 4 bits.  It replaces a 2-bit 
number in a variable with a 4-bit mask: 

        incf    BitP, W  ;W = 0001 0010 0011 0100
        btfsc   BitP, 1  ;If 0 or 1, result is almost correct now.
        iorwf   BitP, F  ;BitP = [0000] [0001] 0011 0111
        incf    BitP, F  ;BitP = 0001 0010 0100 1000

It could be the core of an 8-bit routine thus: 

; Convert 3-bit number (0-7) in INDEX to a 8-bit mask (00000001 ...
; 10000000) in BitP.
        movfw   INDEX
        andlw   b'00000011'     ;Start with half of the mask.
        movwf   BitP
        incf    BitP, W         ;The 4-bit converter
        btfsc   BitP, 1
        iorwf   BitP, F
        incf    BitP, F
        btfsc   INDEX, 2        ;Is it high 4 bits?
        swapf   BitP, F
 

Divide 16-bit by 8-bit

From: Bob Fehrenbach

;Divide 16 bits by 8 bits, 8 bit result.
;Conventional shift and subtract
;Result MUST fit in 8 bits, otherwise erroneous result.
;110 clock cycles.
;Source: BF
;   dvdHI : dvdLO / dvsrLO  -> dvdLO, rem in dvdHI
;Uses count

div8:
   movlw   8
   movwf   count
div_loop:
   rlf     dvdLO, F
   rlf     dvdHI, F
   rlf     tmpLO, F                ;save "borrow"
   movf    dvsrLO, W
   subwf   dvdHI, W
   btfss   tmpLO, 0                ;Save result if borrow = 1
   skpnc                           ;Else, save only if positive
   movwf   dvdHI
   btfsc   tmpLO, 0                ;Make sure carry is a 1 if
   rrf     tmpLO, F                ;borrow = 1
   decfsz  count, F
   goto    div_loop
   rlf     dvdLO, F                ;quotient in dvdLO
div_exit:                          ;remainder in dvdHI
   return
 

Continious delay

From: Andy Warren

; This routine delays X cycles.  Enter with X (in the range
; [20-271]) in the W register.
;
; Note that the delay is inclusive of the "MOVLW X", "CALL
; DELAY", and "RETURN" overhead, so a sequence like:
;
;     MOVLW   100
;     CALL    DELAY
;     MOVLW   200
;     CALL    DELAY
;
; will delay EXACTLY 300 cycles.

DELAY:
        MOVWF   COUNTER
        BTFSC   COUNTER, 0
        GOTO    $+1
        BTFSS   COUNTER, 1
        GOTO    SKIP
        NOP
        GOTO    $+1
SKIP:
        RRF     COUNTER
        RRF     COUNTER
        MOVLW   4
        SUBWF   COUNTER
        BCF     COUNTER,6
        BCF     COUNTER,7
LOOP:
        NOP
        DECFSZ  COUNTER
        GOTO    LOOP

        RETURN
 

Divide by 3

From: Scott Dattalo

; Divide by 3
; Input in W  , Output W/3
;
        ADDLW   1
        SKPNC
         RETLW  0x55

        MOVWF   quo_L
        CLRF    quo_H

        RLF     quo_L, F
        RLF     quo_H, F
        RLF     quo_L, F
        RLF     quo_H, F  ;quo_L:H = 4*dividend

        ADDWF   quo_L, F
        SKPNC
         INCF   quo_H, F  ;quo_L:H = 5*dividend

  ;At this point, we have dividend * 5. We actually need
  ;dividend * 0x55. So the next instructions will add
  ;add 0x10*quo_L:H to quo_L:H.

        SWAPF   quo_H, W  ;quo_H * 0x10
        ADDWF   quo_H, F  ;quo_H += quo_H*0x10

        SWAPF   quo_L, W  ;quo_L * 0x10
        ANDLW   0x0f      ;
        ADDWF   quo_L, F  ;quo_L += quo_L*0x10

        SKPNDC            ;Note the 'DC'
         ADDLW  1         ;

        ADDWF   quo_H, W  ;quo_H += quo_L*0x10 (plus stuff)
 

Compute parity

From: John Payson

;This routine will leave the parity of X in X.0
;while blenderizing most of the rest of X

        swapf   X, W
        xorwf   X, F
        rrf     X, W
        xorwf   X, F
        btfsc   X, 2
        incf    X, F
 

BCD to binary

From: Mike Keitz

;You have to have the 2 BCD digits in the low 4 bits of
;bcdh and bcdl, with the high 4 bits all zero.
;The result is place in bin.
;Note that it could be modified to just reuse one of the
;bcd locations to store the binary result.

        movfw   bcdh
        movwf   bin             ;bin = bcdh
        clrc
        rlf     bin, F          ;bin = bcdh * 2
        rlf     bin, F          ;bin = bcdh * 4
        addwf   bin, F          ;bin = bcdh * 4 + bcdh = bcdh * 5
        rlf     bin, F          ;Now bin = bcdh * 5 * 2 = bcdh * 10
        movfw   bcdl
        addwf   bin, F          ;Finally bin = bcdh*10 + bcdl
 

BCD (packed) to binary 

From: Scott Dattalo

        rrf   bcd, W
        andlw 01111000b  ;W = tens*8
        movwf temp
        clrc
        rrf   temp, F    ;temp = tens*4
        rrf   temp, F    ;temp = tens*2
        subwf bcd, W     ;W = tens*16 + ones - tens*8
                         ;W = tens*8 + ones
        addwf temp, W    ;W = tens*10 + ones
BCD (packed) addition

From: Scott Dattalo

;******************************************
;bcd_add
;
; Computes  z = x + y
; where x,y,z are all 8-bit packed BCD numbers
; Exits with C=1 if x+y > 0x99 and with z=1 if
; x+y = 0x100.
; Note that z can be aliased to x or y so that
;it's possible to calculate x = x+y or y = x+y
;This routine forms the BCD two's complement of
;y and then uses the bcd_subtract routine to
;find the sum. e.g. z = x - (-y) = x + y
;
; 10 cycles

bcd_add
        COMF    y, W    ;W = ~y
        ADDLW   0x9a+1  ;W = ~y + 0x9a +1
                        ;W = (~y + 1) + 0x9a
                        ;W = 0x9a - y
        SUBWF   x, W    ;W = x - (0x9a - y)
                        ;W = x + y - 0x9a
                        ;W = x + y + 0x66
        RLF     z, F    ;Get the carry
        SKPDC           ;if lsn of x + lsn of y < 10 (dec)
         ADDLW  -0x06   ; then remove the extra 6 added above
        BTFSS   z, 0    ;Similarly for the msn
         ADDLW  -0x60
        RRF     z, F    ;restore the carry
        MOVWF   z

        RETURN
 

BCD (packed) subtraction

From: Scott Dattalo

;******************************************
;bcd_subtract
;
; Computes  z = x - y
; where x,y,z are all 8-bit packed BCD numbers
; Exits with C=1 (and DC=1 too)  if x>=y
; and with z=1 if x==y.
; Note that z can be aliased to x or y so that
;it's possible to calculate x = x-y or y = x-y
; 9 cycles (+ return)

bcd_subtract

        MOVF    y, W    ;W = y
        SUBWF   x, W    ;W = x-y
        RLF     z, F    ;lsb of z has the carry
        SKPDC           ;if lsn of x < lsn of y
         ADDLW  -0x06   ; then convert lsn of the
                        ; result to BCD.
        BTFSS   z, 0    ;Similarly for the msn's
         ADDLW  -0x60
        RRF     z, F    ;Get the carry
        MOVWF   z       ;and save the result

        RETURN
 

Binary to BCD (packed)

From: Scott Dattalo

;********************************
;binary_to_bcd - 8-bits
;
;Input
;  bin  - 8-bit binary number
;Outputs
; hundreds - the hundreds digit of the BCD conversion
; tens_and_ones - the tens and ones digits of the BCD conversion

binary_to_bcd:

        CLRF    hundreds
        SWAPF   bin, W
        ADDWF   bin, W
        ANDLW   00001111b
        SKPNDC
         ADDLW  0x16
        SKPNDC
         ADDLW  0x06
        ADDLW   0x06
        SKPDC
         ADDLW  -0x06

        BTFSC   bin,4
         ADDLW   0x16 - 1 + 0x6
        SKPDC
         ADDLW  -0x06

        BTFSC   bin, 5
         ADDLW  0x30

        BTFSC   bin, 6
         ADDLW  0x60

        BTFSC   bin, 7
         ADDLW  0x20

        ADDLW   0x60
        RLF     hundreds, F
        BTFSS   hundreds, 0
         ADDLW  -0x60

        MOVWF   tens_and_ones
        BTFSC   bin,7
         INCF   hundreds, F
 

Multiple byte increment and decrement

From: Dmitry Kiryashov

; Multi byte increment (expandable)

        movlw   1
        addwf   L, F
        btfss   STATUS, C
        addwf   M, F
        btfss   STATUS, C
        addwf   H, F

; Multi byte decrement (expandable)

        movlw   1
        subwf   L, F
        btfss   STATUS, C
        subwf   M, F
        btfss   STATUS, C
        subwf   H, F
 

Conversion of byte to percentage

From: Scott Dattalo

;*******************************************************************
;scale_hex2dec
;  The purpose of this routine is to scale a hexadecimal byte to a
;decimal byte. In other words, if 'h' is a hexadecimal byte then
;the scaled decimal equivalent 'd' is:
;    d = h * 100/256.
;Note that this can be simplified:
;    d = h * 25 / 64 = h * 0x19 / 0x40
;Multiplication and division can be expressed in terms of shift lefts
;and shift rights:
;    d = [ (h<<4) + (h<<3) + h ] >> 6
;The program divides the shifting as follows so that carries are
automatically
;taken care of:
;    d =   (h + (h + (h>>3)) >> 1) >> 2
;
;Inputs:   W - should contain 'h', the hexadecimal value to be scaled
;Outputs:  W - The scaled hexadecimal value is returned in W
;Memory:   temp
;Calls:    none

scale_hex2dec

        MOVWF   temp            ;Hex value is in W.
        CLRC                    ;Clear the Carry bit so it doesn't
                                ;affect RRF
        RRF     temp, F
        CLRC
        RRF     temp, F
        CLRC
        RRF     temp, F         ;temp = h>>3
        ADDWF   temp, F         ;temp = h + (h>>3)
        RRF     temp, F         ;temp = (h + (h>>3)) >> 1
        ADDWF   temp, F         ;temp = h + ((h + (h>>3)) >> 1)
        RRF     temp, F
        CLRC
        RRF     temp, W         ;d = W = (h + (h + (h>>3)) >> 1) >> 2

        RETURN
 

Convert byte to HEX

From: Marco Di Leo

        swapf   value, W         ; Get the value nibble-swapped
        andlw   0x0f             ; Isolate the low nibble
        addlw   -0x0a            ; Check for digit value
        btfsc   STATUS, C        ; If 0-9 skip next
        addlw   0x07             ; Add offset between digits and
                                 ; letters (use 0x27 for lowercase)
        addlw   0x3a             ; Add back the value we subtracted
                                 ; for test and the offset between
                                 ; 0 and the char '0'

        (here W holds the high nibble char)

        movf    value, W         ; Get the value in W
        andlw   0x0f             ; Same as high digit
        addlw   -0x0a
        btfsc   STATUS, C
        addlw   0x07
        addlw   0x3a

        (here W holds the low nibble char)
 

Complement carry flag

From: Chip Weller

        bcf     STATUS, 1        ; Clear Digit Carry
        incfsz  STATUS, F        ; Carry complemented, DC has old carry
Moving data block

From: Dmitry Kiryashov

; for ( i = num_of_elements; i != 0; ) { i--; b[i] = a[i]; }

        movlw   num_of_elements
        movwf   i
loop:
        decf    i, W
        addlw   a
        movwf   FSR     ; (a+i)
        movfw   INDF
        movwf   temp

        movlw   (b-a)
        addwf   FSR, F  ; (b+i)
        movfw   temp
        movwf   INDF

        decfsz  i, F
        goto    loop
 

Rotating register

From: Dale Wescombe

        RLF REG, W      ; Where reg is the register who's contents
                        ; you want to rotate
        RLF REG, F      ; This does leave the W register scrambled
                        ; but you can enter with REG having "abcdefgh"
                        ; and leave with it having "bcdefgha"
 

Please note: I have not tested the routines in this page so use them at your own risk.



This page is (C)1998,1999 by Marco Di Leo <m.dileo@bigfoot.com>