PIC Xmit and Receive code for Nordic rF24L01

In the spirit of sharing I wanted to post some code for anyone that wants to play around with SF’s various breakout boards for the rF24L01. I started by buying two of the “Transceiver nRF24L01 Module with RP-SMA” modules (and matching antennas), but then got spooked by having to get both the transmitter and receiver code working at the same time (gee, is the bug on the transmitter side, or the receiver…) So, the modules just sat in my parts box for several months.

However, when the Nordic FOB came out, I got one of those figuring it would cut down my learning curve quite a bit to start with a working transmitter. Since I don’t have an Atmel programmer, I took the sample receiver code SF provided and reworked it a bit for the PIC16F610 (using the CCS “PCM” C compiler and MPLAB), which I’ll share here:

#device PIC16F610
#fuses  PUT, IOSC8, INTRC_IO, NOWDT, NOPROTECT, BROWNOUT, NOMCLR
#use    delay(clock=8000000)

#byte  PORTA    = 0x05
#byte  TRISA    = 0x85
#byte  PORTC    = 0x07
#byte  TRISC    = 0x87
#byte  ANSEL    = 0x91

#bit   RX_CE    =  PORTA.0  // out Pin 13
#bit   RX_CSN   =  PORTA.1  // out Pin 12
#bit   RX_SCK   =  PORTA.2  // out Pin 11
#bit   RX_MISO  =  PORTA.3  // in  Pin 4
#bit   RX_MOSI  =  PORTA.4  // out Pin 3

char data[4];

char spiIO (char out) {
  char ii, in;
  in = 0;
  for(ii = 0 ; ii < 8 ; ii++)  {
    if ((out & 0x80) != 0) {
      RX_MOSI = 1;
    } else {
      RX_MOSI = 0;
    }
    RX_SCK = 1;
    delay_us(5);
    in <<= 1;
    if (RX_MISO != 0) {
      in |= 0x01;
    }
    RX_SCK = 0;
    delay_us(5);
    out <<= 1;
  }
  return in;
}

char sendCmd (char cmd, char data) {
  char status;
  RX_CE = 0;                   // Stand by mode
  RX_CSN = 0;                  // Select chip
  spiIO(cmd);
  status = spiIO(data);
  RX_CSN = 1;                  // Deselect chip
  return status ;
}

void initRcvr (void) {
  char ii;
  RX_CE = 0;                  // Go into standby mode
  sendCmd(0x20, 0x39);        // Enable RX IRQ, CRC Enabled, be a receiver
  sendCmd(0x21, 0x00);        // Disable auto-acknowledge
  sendCmd(0x23, 0x03);        // Set address width to 5bytes (default, not really needed)
  sendCmd(0x26, 0x07);        // Air data rate 1Mbit, 0dBm, Setup LNA
  sendCmd(0x31, 0x04);        // 4 byte receive payload
  sendCmd(0x25, 0x02);        // RF Channel 2 (default, not really needed)
  RX_CSN = 0;                 // Select chip
  spiIO(0x2A);
  for (ii = 0 ; ii < 4 ; ii++) {
    spiIO(0xE7);
  }
  RX_CSN = 1;                 // Deselect chip
  sendCmd(0x20, 0x3B);        // RX interrupt, power up, be a receiver
  RX_CE = 1;                  // Start receiving
}    

char sendByte (char cmd) {
  char status;
  RX_CSN = 0;                  // Select chip
  status = spiIO(cmd);
  RX_CSN = 1;                  // Deselect chip
  return status;
}

void receive (void) {
  char ii;
  RX_CSN = 0;                  // Stand by mode
  spiIO(0x61);                 // Read RX Payload
  for (ii = 0; ii < 4; ii++) {
    data[ii] = spiIO(0xFF);
  }
  RX_CSN = 1;
  sendByte(0xE2);              // Flush RX FIFO
  sendCmd(0x27, 0x40);         // Clear RF FIFO interrupt
  RX_CE = 1;                   // Go back to receiving!
}

int main (void) {
  char leds;
  TRISA = 0x08;                // PORTA.0-3,5 are outputs, PORTA.4 is input
  TRISC = 0x00;                // PORTC.0-5 are outputs
  ANSEL = 0x00;                // All inputs digital
  PORTC = 0x18;
  RX_CE = 0;                  // Stand by mode
  initRcvr();
  leds = 0x18;
  while(1) {
    char in;
    in = sendByte(0xFF);       //Get status register
    if ((in & 0x40) != 0) {
      receive();
      switch (data[0]) {
      case 0x17:              // Left button
        leds ^= 0x01;
        break;
      case 0x1D:              // Top button
        leds ^= 0x02;
        break;
      case 0x1B:              // Right button
        leds ^= 0x04;
        break;
      case 0x1E:              // Bottom button
        leds ^= 0x08;
        break;
      case 0x0F:              // Center button
        leds ^= 0x10;
        break;
      }
      PORTC = leds;
    }
  }
}

The code toggles LEDs attached to port C on the 610 in response to button presses on the FOB. See the #bit definitions at the top of the source to see how the various signals from the rF24L01 are wired to the 16F610.

Once I had the receiver working, I coded up a simple, one button transmitter using a PIC12F683 that mimics what the FOB does. That code is here:

#device PIC12F683
#fuses  PUT, INTRC_IO, NOWDT, NOPROTECT, BROWNOUT, NOMCLR
#use    delay(clock=8000000)

#byte  GPIO    = 0x05
#byte  OPTION   = 0x81
#byte  TRISIO   = 0x85
#byte  OSCCON   = 0x8F
#byte  WPU      = 0x95

#bit  GPPU     = OPTION.7

#bit  TX_CE    =  GPIO.0  // out Pin 7
#bit  TX_CSN   =  GPIO.1  // out Pin 6
#bit  TX_SCK   =  GPIO.2  // out Pin 5
#bit  TX_MISO  =  GPIO.3  // in  Pin 4
#bit  TX_MOSI  =  GPIO.4  // out Pin 3
#bit  BUTTON   =  GPIO.5  // in Pin 2

char data[4];

char spiIO (char out) {
  char ii, in;
  in = 0;
  for(ii = 0 ; ii < 8 ; ii++)  {
    if ((out & 0x80) != 0) {
      TX_MOSI = 1;
    } else {
      TX_MOSI = 0;
    }
    TX_SCK = 1;
    in <<= 1;
    if (TX_MISO != 0) {
      in |= 0x01;
    }
    TX_SCK = 0; 
    out <<= 1;
  }
  return in;
}

char sendCmd (char cmd, char data) {
  char status;
  TX_CE = 0;                   // Stand by mode
  TX_CSN = 0;                  // Select chip
  spiIO(cmd);
  status = spiIO(data);
  TX_CSN = 1;                  // Deselect chip
  return status ;
}

char sendByte (char cmd) {
  char status;
  TX_CSN = 0;                  // Select chip
  status = spiIO(cmd);
  TX_CSN = 1;                  // Deselect chip
  return status;
}

void initXmtr (void) {
  char ii;
  TX_CE = 0;                  // Go into standby mode
  sendCmd(0x20, 0x78);        // CRC Enabled, be a transmitter
  sendCmd(0x21, 0x00);        // Disable auto-acknowledge
  sendCmd(0x24, 0x00);        // Disable auto-retransmit
  sendCmd(0x23, 0x03);        // Set address width to 5bytes (default, not really needed)
  sendCmd(0x26, 0x07);        // Air data rate 1Mbit, 0dBm, Setup LNA
  sendCmd(0x25, 0x02);        // RF Channel 2 (default, not really needed)
  TX_CSN = 0;                 // Select chip
  spiIO(0x30);                // Set TX Address
  for (ii = 0 ; ii < 4 ; ii++) {
    spiIO(0xE7);
  }
  TX_CSN = 1;                 // Deselect chip
  sendCmd(0x20, 0x7A);        // Power up transmitter
  sendByte(0xFF);
}    

void xmit (void) {
  char ii;
  sendCmd(0x27, 0x7E);        // Clear any interrupts
  sendCmd(0x20, 0x7A);        // Power up transmitter
  sendByte(0xE1);             // Clear TX FIFO
  TX_CSN = 0;                 // Select chip
  spiIO(0xA0);                // Clock in 4 byte data payload
  for (ii = 0 ; ii < 4 ; ii++) {
    spiIO(data[ii]);
  }
  TX_CSN = 1;                 // Deselect chip
  TX_CE = 1;                  // Pulse CE to start transmission
  delay_us(3);
  TX_CE = 0;
}

int main (void) {
  char  bc, bo;
  OSCCON = 0x70;              // 8 Mhz
  while ((OSCCON & 0x04) == 0)
    ;
  TRISIO = 0x28;              // GPIO.0-2,4 are outputs, GPIO.3,5 are inputs
  WPU    = 0x20;              // Weak pullup on GPIO.5
  GPPU    = 0;                // Enable global pullup enable
  TX_CE = 0;                  // Standby mode
  bo = 0xFF;
  initXmtr();
  while(1) {
    bc = GPIO;
    if (((bc ^ bo) & 0x20) != 0  && (bc & 0x20) == 0) {
      // get here on button transition from unpressed to pressed
      data[0] = 0x0F;         // Send "Center" button code to receiver
      data[1] = 0;
      data[2] = 0;
      data[3] = 0;
      xmit();
    }
    bo = bc;
    delay_us(100);
  }
}

My goal in coding these was to create simple examples that someone could use as a starting point to get something working with a minimum of components before branching out into more complex propjects. So, let me know if this is useful. Thanks.

Wayne

Thank you VERY MUCH for sharing!! This is very helpful for me :wink:

I’d be very grateful if from your experience or gained documentation, you could help me understand if what i want to do is possible. At http://www.rentron.com/rf_remote_control.htm, the reynolds electronics website sells very simple lower freq. 433mhz transmitters and receivers, and their on the site they provide examples for 8 bit transmitters and receiver circuits. Clicking on them I was amazed. There are apparently two very simple chips made by Holtek, a HT640 and an HT648. The 640 is used to collect up to 18 bits of data (arbitrarily designated as 10 address and 8 data bits), which it then serializes, prepending some sync and timing bits, which it then just sends it into the transmitter with one wire. A single resistor sets internal the bit rate oscillator. On the receiving end, an HT648 chip is is used to do the opposite, recovering and synchronizing the serialized data and making it available on 18 individual pins, again arbitrarily designated 10 for address and 8 for data. The examples on that site are only using 8 of the available bits.

This is exactly what I need! To be able to replicate some bits on a wireless link without having to deal with any MCU at all would spare me a lot of R & D time. But I have one problem… the 433Mhz frequency requires an antenna, and the application I have in mind has no room for such a clumsy addition. So I had hoped for something similar in the 2.4Ghz band. Well e-bay is full of these nRFL24LO boards! But of course these are all China based suppliers and documentation is pretty limited. Even if I did buy some canned Arduino board to get started, I fear it would bog me down in months of additional research. Having seen how simple these Holtek chips could make my life on a 433Mhz board, I just sense the a same could be done with these RF24LO boards with just a little help. So anything you can share would be most appreciated!