HPi-0.7.0: GPIO, I2C and SPI functions for the Raspberry Pi.

Safe HaskellSafe
LanguageHaskell98

System.RaspberryPi.GPIO

Contents

Description

Library for controlling the GPIO pins on a Raspberry Pi (or any system using the Broadcom 2835 SOC). It is constructed as a FFI wrapper over the BCM2835 library by Mike McCauley.

Synopsis

Data types

data Pin Source #

This describes the pins on the Raspberry Pi boards. Since the BCM2835 SOC internally uses different numbers (and these numbers differ between versions, the library internally translates this pin number to the correct number.

Constructors

Pin03

Pins for the P1 connector of the V2 revision of the Raspberry Pi

Pin05 
Pin07 
Pin08 
Pin10 
Pin11 
Pin12 
Pin13 
Pin15 
Pin16 
Pin18 
Pin19 
Pin21 
Pin22 
Pin23 
Pin24 
Pin26 
Pin36 
PinP5_03

Pins for the P5 connector of the V2 revision of the Raspberry Pi

PinP5_04 
PinP5_05 
PinP5_06 
PinV1_03

Pins for the P1 connector of the V1 revision of the Raspberry Pi

PinV1_05 
PinV1_07 
PinV1_08 
PinV1_10 
PinV1_11 
PinV1_12 
PinV1_13 
PinV1_15 
PinV1_16 
PinV1_18 
PinV1_19 
PinV1_21 
PinV1_22 
PinV1_23 
PinV1_24 
PinV1_26 

Instances

Eq Pin Source # 

Methods

(==) :: Pin -> Pin -> Bool

(/=) :: Pin -> Pin -> Bool

Show Pin Source # 

Methods

showsPrec :: Int -> Pin -> ShowS

show :: Pin -> String

showList :: [Pin] -> ShowS

data PinMode Source #

A GPIO pin can be either set to input mode, output mode or an alternative mode.

Constructors

Input 
Output 
Alt0 
Alt1 
Alt2 
Alt3 
Alt4 
Alt5 

Instances

Enum PinMode Source # 
Eq PinMode Source # 

Methods

(==) :: PinMode -> PinMode -> Bool

(/=) :: PinMode -> PinMode -> Bool

Show PinMode Source # 

Methods

showsPrec :: Int -> PinMode -> ShowS

show :: PinMode -> String

showList :: [PinMode] -> ShowS

type LogicLevel = Bool Source #

Either high or low.

type Address = Word8 Source #

This describes the address of an I2C slave.

data SPIBitOrder Source #

Specifies the SPI data bit ordering.

Constructors

LSBFirst 
MSBFirst 

data SPIPin Source #

This describes which Chip Select pins are asserted (used in SPI communications).

Constructors

CS0 
CS1 
CS2 
CSNONE 

Instances

Enum SPIPin Source # 
Eq SPIPin Source # 

Methods

(==) :: SPIPin -> SPIPin -> Bool

(/=) :: SPIPin -> SPIPin -> Bool

Show SPIPin Source # 

Methods

showsPrec :: Int -> SPIPin -> ShowS

show :: SPIPin -> String

showList :: [SPIPin] -> ShowS

type CPOL = Bool Source #

Clock polarity (CPOL) for SPI transmissions.

type CPHA = Bool Source #

Clock phase (CPHA) for SPI transmissions.

General functions

withGPIO :: IO a -> IO a Source #

Any IO computation that accesses the GPIO pins using this library should be wrapped with this function; ie withGPIO $ do foo. It prepares the file descriptors to devmem and makes sure everything is safely deallocated if an exception occurs. The behavior when accessing the GPIO outside of this function is undefined.

GPIO specific functions

setPinFunction :: Pin -> PinMode -> IO () Source #

Sets the pin to either Input or Output mode.

readPin :: Pin -> IO LogicLevel Source #

Returns the current state of the specified pin.

writePin :: Pin -> LogicLevel -> IO () Source #

Sets the specified pin to either True or False.

I2C specific functions

withI2C :: IO a -> IO a Source #

Any IO computation that uses the I2C bus using this library should be wrapped with this function; ie withI2C $ do foo. It prepares the relevant pins for use with the I2C protocol and makes sure everything is safely returned to normal if an exception occurs. If you only use the GPIO pins for I2C, you can do withGPIO . withI2C $ do foo and it will work as expected. WARNING: after this function returns, the I2C pins will be set to Input, so use setPinFunction if you want to use them for output.

setI2cClockDivider :: Word16 -> IO () Source #

Sets the clock divider for (and hence the speed of) the I2C bus.

setI2cBaudRate :: Word32 -> IO () Source #

Sets the baud rate of the I2C bus.

writeI2C :: Address -> ByteString -> IO () Source #

Writes the data in the ByteString to the specified I2C Address. Throws an IOException if an error occurs.

readI2C :: Address -> Int -> IO ByteString Source #

Reads num bytes from the specified Address. Throws an IOException if an error occurs.

writeReadRSI2C :: Address -> ByteString -> Int -> IO ByteString Source #

Writes the data in the ByteString to the specified Address, then issues a "repeated start" (with no prior stop) and then reads num bytes from the same Address. Necessary for devices that require such behavior, such as the MLX90620.

SPI specific functions

withAUXSPI :: IO a -> IO a Source #

Any IO computation that uses the AUX SPI functionality using this library should be wrapped with this function; ie withAUXSPI $ do foo. It prepares the relevant pins for use with the SPI protocol and makes sure everything is safely returned to normal if an exception occurs. If you only use the GPIO pins for SPI, you can do withGPIO . withAUXSPI $ do foo and it will work as expected. WARNING: after this function returns, the SPI pins will be set to Input, so use setPinFunction if you want to use them for output.

withSPI :: IO a -> IO a Source #

Any IO computation that uses the SPI functionality using this library should be wrapped with this function; ie withSPI $ do foo. It prepares the relevant pins for use with the SPI protocol and makes sure everything is safely returned to normal if an exception occurs. If you only use the GPIO pins for SPI, you can do withGPIO . withSPI $ do foo and it will work as expected. WARNING: after this function returns, the SPI pins will be set to Input, so use setPinFunction if you want to use them for output.

chipSelectSPI :: SPIPin -> IO () Source #

Sets the chip select pin(s). When a transfer is made with transferSPI or transferManySPI, the selected pin(s) will be asserted during the transfer.

setBitOrderSPI :: SPIBitOrder -> IO () Source #

Set the bit order to be used for transmit and receive. The bcm2835 SPI0 only supports MSBFirst, so if you select LSBFirst, the bytes will be reversed in software. The library defaults to MSBFirst.

setChipSelectPolaritySPI :: SPIPin -> LogicLevel -> IO () Source #

Sets the chip select pin polarity for a given pin(s). When a transfer is made with transferSPI or transferManySPI, the currently selected chip select pin(s) will be asserted to the LogicLevel supplied. When transfers are not happening, the chip select pin(s) return to the complement (inactive) value.

setClockDividerAUXSPI :: Word16 -> IO () Source #

Sets the AUX SPI clock divider and therefore the SPI clock speed.

setClockDividerSPI :: Word16 -> IO () Source #

Sets the SPI clock divider and therefore the SPI clock speed.

setDataModeSPI :: (CPOL, CPHA) -> IO () Source #

Sets the SPI clock polarity and phase (ie, CPOL and CPHA)

transferAUXSPI :: Word8 -> IO Word8 Source #

Transfers one byte to and from the SPI slave. Asserts the CS2 pin during the transfer. Clocks the 8 bit value out on MOSI, and simultaneously clocks in data from MISO. Returns the read data byte from the slave.

transferSPI :: Word8 -> IO Word8 Source #

Transfers one byte to and from the currently selected SPI slave. Asserts the currently selected CS pins (as previously set by chipSelectSPI) during the transfer. Clocks the 8 bit value out on MOSI, and simultaneously clocks in data from MISO. Returns the read data byte from the slave.

transferManySPI :: [Word8] -> IO [Word8] Source #

Transfers any number of bytes to and from the currently selected SPI slave, one byte at a time. Asserts the currently selected CS pins (as previously set by chipSelectSPI) during the transfer. Clocks 8 bit bytes out on MOSI, and simultaneously clocks in data from MISO.