Module spi

This module provides an interface into the Serial Peripheral Interface (SPI) supported on many devices.

Description

This module currently support the SPI “leader” (historically known as the “master”) interface, allowing the leader to connect to one or more “follower” (historically known as “slave”) devices.

Users interact with this interface by creating an instance of the driver via the open/1 function, with returns an opaque reference to the driver instance. The open/1 function takes a complex map structure, which configures the driver to connect to follower devices. See the open/1 documentation for details about the structure of this configuration map.

Subsequent read and write operations use the SPI instance returned from the open/1 function. Users may read from a specific follower device at a specific address, write to the device at an address, or simultaneously read from and write to the device in a single transaction.

Data Types

address()


address() = non_neg_integer()

bus_config()


bus_config() = [{poci, non_neg_integer()} | {pico, non_neg_integer()} | {miso, non_neg_integer()} | {mosi, non_neg_integer()} | {sclk, non_neg_integer()} | {peripheral, peripheral()}]

device_config()


device_config() = [{clock_speed_hz, non_neg_integer()} | {mode, 0..3} | {cs, non_neg_integer()} | {address_len_bits, 0..64} | {command_len_bits, 0..16}]

device_name()


device_name() = atom()

params()


params() = [{bus_config, bus_config()} | {device_config, [{device_name(), device_config()}]}]

peripheral()


peripheral() = hspi | vspi | string() | binary()

spi()


spi() = pid()

transaction()


transaction() = #{command => integer(), address => non_neg_integer(), write_data => binary(), write_bits => non_neg_integer(), read_bits => non_neg_integer()}

Function Index

close/1 Close the SPI driver.
open/1Open a connection to the SPI driver.
read_at/4 Read a value from and address on the device.
write/3 Write data to the SPI device, using the instructions encoded in the supplied transaction.
write_at/5 Write a value to and address on the device.
write_read/3 Write data to the SPI device, using the instructions encoded in the supplied transaction.

Function Details

close/1


close(SPI::spi()) -> ok

SPI: SPI instance created via open/1

Close the SPI driver.

Close the SPI driver and free any resources in use by the driver.

The SPI instance will no longer be valid and usable after this function has been called.

open/1


open(Params::params()) -> spi()

Params: Initialization parameters

returns: process id of the driver.

throws badarg

Open a connection to the SPI driver

This function will open a connection to the SPI driver.

Supply a set of parameters to initialize the driver.

The parameters list must contain an SPI Bus configuration, together with a properties list containing one or more device configurations. This list must contain atom keys as names, which are used to identify the device in the subsequent read and write operations. You may use any atom value of your choosing.

The SPI Bus configuration is a properties list containing the following entries:

Key Type Default Description
miso non_neg_integer() - MISO pin number
mosi non_neg_integer() - MOSI pin number
sclk non_neg_integer() - SCLK pin number
peripheral hspi | vspi hspi SPI Peripheral (ESP32 only)

Each device configuration is a properties list containing the following entries:

Key Type Default Description
clock_speed_hz non_neg_integer() 1000000 Clock speed for the SPI device (in hz)
mode 0..3 0 SPI device mode
cs non_neg_integer() - SPI Chip Select pin number
address_len_bits non_neg_integer() 8 Number of bits in the device address

Example:


  Params = [
     {bus_config, [
         {miso, 16},
         {mosi, 17},
         {sclk, 5}
     },
     {device_config, [
         {device1, [
             {cs, 18}
         ]},
         {device2, [
             {cs, 19}
         ]}
     ]}
  ]

Note that device1 and device2 are atom names used to identify the device for read and write operations.

This function raises an Erlang exception with a badarg reason, if initialization of the SPI Bus or any device fails.

The write/3 and write_read/3 functions in this module are designed to provide the maximum mount of flexibility when interfacing with the SPI device. The both make use of a map structure to encapsulate an SPI transaction.

An SPI transaction may contain a command, and address, and/or a blob of data, each of which is optional and each of which depends on how users interact with the device. Consult the data sheet for your SPI device to understand which fields should be used with your device.

The fields of a transaction map are as follows:

KeyValue TypeDescription
commandinteger() (16-bit)SPI command. The low-order command_len_bits are written to the device.
addressinteger() (64-bit)Device address. The low-order address_len_bits are written to the device.
write_databinary()Data to write
write_bitsnon_neg_integer()Number of bits to write from write_data. If not included, then all bits will be written.
read_bitsnon_neg_integer()Number of bits to read from the SPI device. If not included, then the same number of bits will be read as were written.

read_at/4


read_at(SPI::spi(), DeviceName::device_name(), Address::address(), Len::non_neg_integer()) -> {ok, integer()} | {error, Reason::term()}

SPI: SPI instance created via open/1
DeviceName: device name from configuration
Address: SPI Address from which to read
Len: in bytes to read

returns: {ok, Value} or error

Read a value from and address on the device.

write/3


write(SPI::spi(), DeviceName::device_name(), Transaction::transaction()) -> ok | {error, Reason::term()}

SPI: SPI instance created via open/1
DeviceName: SPI device name (use key in device_config)
Transaction: transaction map.

returns: ok or {error, Reason}, if an error occurred.

Write data to the SPI device, using the instructions encoded in the supplied transaction.

The supplied Transaction encodes information about how data is to be written to the selected SPI device. See the description above for the fields that may be specified in this map.

When a binary is supplied in the write_data field, the data is written to the SPI device in the natural order of the binary. For example, if the input binary is <<16#57, 16#BA>>, then the first byte is 0x57 and the second byte is 0xBA.

The value of the write_bits field, if specified, must be less than or equal to 8 * byte_size(write_data). If write_bits is less than 8 * byte_size(write_data), only the first write_bits bits from write_data will be written.

This function will return a tuple containing the error atom if an error occurred writing to the SPI device at the specified address. The returned reason term is implementation-defined.

write_at/5


write_at(SPI::spi(), DeviceName::device_name(), Address::address(), Len::non_neg_integer(), Data::integer()) -> {ok, integer()} | {error, Reason::term()}

SPI: SPI instance created via open/1
DeviceName: device name from configuration
Address: SPI Address to which to write
Len: in bytes to read
Data: byte(s) to write

returns: {ok, Value} or error

Write a value to and address on the device.

The value returned from this function is dependent on the device and address. Consult the documentation for the device to understand expected return values from this function.

write_read/3


write_read(SPI::spi(), DeviceName::device_name(), Transaction::transaction()) -> {ok, ReadData::binary()} | {error, Reason::term()}

SPI: SPI instance created via open/1
DeviceName: SPI device name (use key in device_config)
Transaction: transaction.

returns: {ok, binary()} or {error, Reason}, if an error occurred.

Write data to the SPI device, using the instructions encoded in the supplied transaction. device, and simultaneously read data back from the device, returning the read data in a binary.

The supplied Transaction encodes information about how data is to be written to the selected SPI device. See the description above for the fields that may be specified in this map.

When a binary is supplied in the write_data field, the data is written to the SPI device in the natural order of the binary. For example, if the input binary is <<16#57, 16#BA>>, then the first byte is 0x57 and the second byte is 0xBA.

The value of the write_bits field, if specified, must be less than or equal to 8 * byte_size(write_data). If write_bits is less than 8 * byte_size(write_data), only the first write_bits bits from write_data will be written.

The return value contains a sequence of bytes that have been read from the SPI device. The number of bytes returned will be ceil(read_bits / 8). Only the first read_bits will be populated.

This function will return a tuple containing the error atom if an error occurred writing to the SPI device at the specified address. The returned reason term is implementation-defined.