{-# LANGUAGE OverloadedStrings, ForeignFunctionInterface #-}
module System.RaspberryPi.GPIO (
Pin(..),
PinMode(..),
LogicLevel,
Address,
SPIBitOrder(..),
SPIPin(..),
CPOL,
CPHA,
withGPIO,
setPinFunction,
readPin,
writePin,
withI2C,
setI2cClockDivider,
setI2cBaudRate,
writeI2C,
readI2C,
writeReadRSI2C,
withAUXSPI,
withSPI,
chipSelectSPI,
setBitOrderSPI,
setChipSelectPolaritySPI,
setClockDividerAUXSPI,
setClockDividerSPI,
setDataModeSPI,
transferAUXSPI,
transferSPI,
transferManySPI,
setClockPWM,
setModePWM,
setRangePWM,
setDataPWM
) where
import Control.Applicative ((<$>))
import Control.Exception
import Foreign
import Foreign.C
import Foreign.C.String
import qualified Data.ByteString as BS
import Data.Maybe
import Data.Tuple
import GHC.IO.Exception
data Pin =
Pin03|Pin05|Pin07|Pin08|Pin10|Pin11|Pin12|Pin13|Pin15|Pin16|Pin18|Pin19|Pin21|Pin22|Pin23|Pin24|Pin26|Pin32|Pin33|Pin35|Pin36|
PinP5_03|PinP5_04|PinP5_05|PinP5_06|
PinV1_03|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
deriving (Pin -> Pin -> LogicLevel
(Pin -> Pin -> LogicLevel) -> (Pin -> Pin -> LogicLevel) -> Eq Pin
forall a. (a -> a -> LogicLevel) -> (a -> a -> LogicLevel) -> Eq a
$c== :: Pin -> Pin -> LogicLevel
== :: Pin -> Pin -> LogicLevel
$c/= :: Pin -> Pin -> LogicLevel
/= :: Pin -> Pin -> LogicLevel
Eq,Int -> Pin -> ShowS
[Pin] -> ShowS
Pin -> String
(Int -> Pin -> ShowS)
-> (Pin -> String) -> ([Pin] -> ShowS) -> Show Pin
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Pin -> ShowS
showsPrec :: Int -> Pin -> ShowS
$cshow :: Pin -> String
show :: Pin -> String
$cshowList :: [Pin] -> ShowS
showList :: [Pin] -> ShowS
Show)
data PinMode = Input | Output | Alt0 | Alt1 | Alt2 | Alt3 | Alt4 | Alt5 deriving (PinMode -> PinMode -> LogicLevel
(PinMode -> PinMode -> LogicLevel)
-> (PinMode -> PinMode -> LogicLevel) -> Eq PinMode
forall a. (a -> a -> LogicLevel) -> (a -> a -> LogicLevel) -> Eq a
$c== :: PinMode -> PinMode -> LogicLevel
== :: PinMode -> PinMode -> LogicLevel
$c/= :: PinMode -> PinMode -> LogicLevel
/= :: PinMode -> PinMode -> LogicLevel
Eq,Int -> PinMode -> ShowS
[PinMode] -> ShowS
PinMode -> String
(Int -> PinMode -> ShowS)
-> (PinMode -> String) -> ([PinMode] -> ShowS) -> Show PinMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PinMode -> ShowS
showsPrec :: Int -> PinMode -> ShowS
$cshow :: PinMode -> String
show :: PinMode -> String
$cshowList :: [PinMode] -> ShowS
showList :: [PinMode] -> ShowS
Show)
instance Enum PinMode where
fromEnum :: PinMode -> Int
fromEnum = Maybe Int -> Int
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe Int -> Int) -> (PinMode -> Maybe Int) -> PinMode -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PinMode -> [(PinMode, Int)] -> Maybe Int)
-> [(PinMode, Int)] -> PinMode -> Maybe Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip PinMode -> [(PinMode, Int)] -> Maybe Int
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup [(PinMode, Int)]
table
toEnum :: Int -> PinMode
toEnum = Maybe PinMode -> PinMode
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe PinMode -> PinMode)
-> (Int -> Maybe PinMode) -> Int -> PinMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> [(Int, PinMode)] -> Maybe PinMode)
-> [(Int, PinMode)] -> Int -> Maybe PinMode
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> [(Int, PinMode)] -> Maybe PinMode
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup (((PinMode, Int) -> (Int, PinMode))
-> [(PinMode, Int)] -> [(Int, PinMode)]
forall a b. (a -> b) -> [a] -> [b]
map (PinMode, Int) -> (Int, PinMode)
forall a b. (a, b) -> (b, a)
swap [(PinMode, Int)]
table)
table :: [(PinMode, Int)]
table = [(PinMode
Input, Int
0), (PinMode
Output, Int
1), (PinMode
Alt0, Int
4), (PinMode
Alt1, Int
5), (PinMode
Alt2, Int
6), (PinMode
Alt3, Int
7), (PinMode
Alt4, Int
3), (PinMode
Alt5, Int
2)]
type Address = Word8
type LogicLevel = Bool
data SPIBitOrder = LSBFirst | MSBFirst
data SPIPin = CS0 | CS1 | CS2 | CSNONE deriving (SPIPin -> SPIPin -> LogicLevel
(SPIPin -> SPIPin -> LogicLevel)
-> (SPIPin -> SPIPin -> LogicLevel) -> Eq SPIPin
forall a. (a -> a -> LogicLevel) -> (a -> a -> LogicLevel) -> Eq a
$c== :: SPIPin -> SPIPin -> LogicLevel
== :: SPIPin -> SPIPin -> LogicLevel
$c/= :: SPIPin -> SPIPin -> LogicLevel
/= :: SPIPin -> SPIPin -> LogicLevel
Eq, Int -> SPIPin -> ShowS
[SPIPin] -> ShowS
SPIPin -> String
(Int -> SPIPin -> ShowS)
-> (SPIPin -> String) -> ([SPIPin] -> ShowS) -> Show SPIPin
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SPIPin -> ShowS
showsPrec :: Int -> SPIPin -> ShowS
$cshow :: SPIPin -> String
show :: SPIPin -> String
$cshowList :: [SPIPin] -> ShowS
showList :: [SPIPin] -> ShowS
Show, Int -> SPIPin
SPIPin -> Int
SPIPin -> [SPIPin]
SPIPin -> SPIPin
SPIPin -> SPIPin -> [SPIPin]
SPIPin -> SPIPin -> SPIPin -> [SPIPin]
(SPIPin -> SPIPin)
-> (SPIPin -> SPIPin)
-> (Int -> SPIPin)
-> (SPIPin -> Int)
-> (SPIPin -> [SPIPin])
-> (SPIPin -> SPIPin -> [SPIPin])
-> (SPIPin -> SPIPin -> [SPIPin])
-> (SPIPin -> SPIPin -> SPIPin -> [SPIPin])
-> Enum SPIPin
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: SPIPin -> SPIPin
succ :: SPIPin -> SPIPin
$cpred :: SPIPin -> SPIPin
pred :: SPIPin -> SPIPin
$ctoEnum :: Int -> SPIPin
toEnum :: Int -> SPIPin
$cfromEnum :: SPIPin -> Int
fromEnum :: SPIPin -> Int
$cenumFrom :: SPIPin -> [SPIPin]
enumFrom :: SPIPin -> [SPIPin]
$cenumFromThen :: SPIPin -> SPIPin -> [SPIPin]
enumFromThen :: SPIPin -> SPIPin -> [SPIPin]
$cenumFromTo :: SPIPin -> SPIPin -> [SPIPin]
enumFromTo :: SPIPin -> SPIPin -> [SPIPin]
$cenumFromThenTo :: SPIPin -> SPIPin -> SPIPin -> [SPIPin]
enumFromThenTo :: SPIPin -> SPIPin -> SPIPin -> [SPIPin]
Enum)
type CPOL = Bool
type CPHA = Bool
foreign import ccall unsafe "bcm2835.h bcm2835_init" initBCM2835 :: IO Int
foreign import ccall unsafe "bcm2835.h bcm2835_close" stopBCM2835 :: IO Int
foreign import ccall unsafe "bcm2835.h bcm2835_set_debug" setDebugBCM2835 :: CUChar -> IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_gpio_fsel" c_setPinFunction :: CUChar -> CUChar -> IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_gpio_write" c_writePin :: CUChar -> CUChar -> IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_gpio_lev" c_readPin :: CUChar -> IO CUChar
foreign import ccall unsafe "bcm2835.h bcm2835_i2c_begin" initI2C :: IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_i2c_end" stopI2C :: IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_i2c_setSlaveAddress" c_setSlaveAddressI2C :: CUChar -> IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_i2c_setClockDivider" c_setClockDividerI2C :: CUShort -> IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_i2c_set_baudrate" c_setBaudRateI2C :: CUInt -> IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_i2c_write" c_writeI2C :: CString -> CUInt -> IO CUChar
foreign import ccall unsafe "bcm2835.h bcm2835_i2c_read" c_readI2C :: CString -> CUShort -> IO CUChar
foreign import ccall unsafe "bcm2835.h bcm2835_i2c_write_read_rs" c_writeReadRSI2C :: CString -> CUInt -> CString -> CUInt -> IO CUChar
foreign import ccall unsafe "bcm2835.h bcm2835_spi_begin" initSPI :: IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_spi_end" stopSPI :: IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_spi_transfer" c_transferSPI :: CUChar -> IO CUChar
foreign import ccall unsafe "bcm2835.h bcm2835_spi_transfern" c_transferManySPI :: CString -> CUInt -> IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_spi_chipSelect" c_chipSelectSPI :: CUChar -> IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_spi_setBitOrder" c_setBitOrder :: CUChar -> IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_spi_setChipSelectPolarity" c_setChipSelectPolarity :: CUChar -> CUChar -> IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_spi_setClockDivider" c_setClockDividerSPI :: CUShort -> IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_spi_setDataMode" c_setDataModeSPI :: CUChar -> IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_aux_spi_begin" initAUXSPI :: IO Int
foreign import ccall unsafe "bcm2835.h bcm2835_aux_spi_end" stopAUXSPI :: IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_aux_spi_transfer" c_transferAUXSPI :: CUChar -> IO CUChar
foreign import ccall unsafe "bcm2835.h bcm2835_aux_spi_setClockDivider" c_setClockDividerAUXSPI :: CUShort -> IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_pwm_set_clock" c_setClockPWM :: CUInt -> IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_pwm_set_data" c_setDataPWM :: CUChar -> CUInt -> IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_pwm_set_mode" c_setModePWM :: CUChar -> CUChar -> CUChar -> IO ()
foreign import ccall unsafe "bcm2835.h bcm2835_pwm_set_range" c_setRangePWM :: CUChar -> CUInt -> IO ()
withGPIO :: IO a -> IO a
withGPIO :: forall a. IO a -> IO a
withGPIO IO a
f = IO Int -> (Int -> IO Int) -> (Int -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket IO Int
initBCM2835
(IO Int -> Int -> IO Int
forall a b. a -> b -> a
const IO Int
stopBCM2835)
(\Int
a -> if Int
aInt -> Int -> LogicLevel
forall a. Eq a => a -> a -> LogicLevel
==Int
0 then IOException -> IO a
forall e a. Exception e => e -> IO a
throwIO IOException
ioe else IO a
f)
where ioe :: IOException
ioe = Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
IllegalOperation String
"GPIO: " String
"Unable to start GPIO." Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
withI2C :: IO a -> IO a
withI2C :: forall a. IO a -> IO a
withI2C IO a
f = IO () -> IO () -> IO a -> IO a
forall a b c. IO a -> IO b -> IO c -> IO c
bracket_ IO ()
initI2C
IO ()
stopI2C
IO a
f
withSPI :: IO a -> IO a
withSPI :: forall a. IO a -> IO a
withSPI IO a
f = IO () -> IO () -> IO a -> IO a
forall a b c. IO a -> IO b -> IO c -> IO c
bracket_ IO ()
initSPI
IO ()
stopSPI
IO a
f
actOnResult :: CUChar -> CStringLen -> IO BS.ByteString
actOnResult :: CUChar -> CStringLen -> IO ByteString
actOnResult CUChar
rr CStringLen
buf = case CUChar
rr of
CUChar
0x01 -> IOException -> IO ByteString
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ByteString) -> IOException -> IO ByteString
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
IllegalOperation String
"I2C: " String
"Received an unexpected NACK." Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
CUChar
0x02 -> IOException -> IO ByteString
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ByteString) -> IOException -> IO ByteString
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
IllegalOperation String
"I2C: " String
"Received Clock Stretch Timeout." Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
CUChar
0x04 -> IOException -> IO ByteString
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ByteString) -> IOException -> IO ByteString
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
IllegalOperation String
"I2C: " String
"Not all data was read." Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
CUChar
0x00 -> CStringLen -> IO ByteString
BS.packCStringLen CStringLen
buf
getHwPin :: Pin -> CUChar
getHwPin :: Pin -> CUChar
getHwPin Pin
PinV1_03 = CUChar
0
getHwPin Pin
PinV1_05 = CUChar
1
getHwPin Pin
PinV1_07 = CUChar
4
getHwPin Pin
PinV1_08 = CUChar
14
getHwPin Pin
PinV1_10 = CUChar
15
getHwPin Pin
PinV1_11 = CUChar
17
getHwPin Pin
PinV1_12 = CUChar
18
getHwPin Pin
PinV1_13 = CUChar
21
getHwPin Pin
PinV1_15 = CUChar
22
getHwPin Pin
PinV1_16 = CUChar
23
getHwPin Pin
PinV1_18 = CUChar
24
getHwPin Pin
PinV1_19 = CUChar
10
getHwPin Pin
PinV1_21 = CUChar
9
getHwPin Pin
PinV1_22 = CUChar
25
getHwPin Pin
PinV1_23 = CUChar
11
getHwPin Pin
PinV1_24 = CUChar
8
getHwPin Pin
PinV1_26 = CUChar
7
getHwPin Pin
Pin03 = CUChar
2
getHwPin Pin
Pin05 = CUChar
3
getHwPin Pin
Pin07 = CUChar
4
getHwPin Pin
Pin08 = CUChar
14
getHwPin Pin
Pin10 = CUChar
15
getHwPin Pin
Pin11 = CUChar
17
getHwPin Pin
Pin12 = CUChar
18
getHwPin Pin
Pin13 = CUChar
27
getHwPin Pin
Pin15 = CUChar
22
getHwPin Pin
Pin16 = CUChar
23
getHwPin Pin
Pin18 = CUChar
24
getHwPin Pin
Pin19 = CUChar
10
getHwPin Pin
Pin21 = CUChar
9
getHwPin Pin
Pin22 = CUChar
25
getHwPin Pin
Pin23 = CUChar
11
getHwPin Pin
Pin24 = CUChar
8
getHwPin Pin
Pin26 = CUChar
7
getHwPin Pin
Pin32 = CUChar
12
getHwPin Pin
Pin33 = CUChar
13
getHwPin Pin
Pin35 = CUChar
19
getHwPin Pin
Pin36 = CUChar
16
getHwPin Pin
PinP5_03 = CUChar
28
getHwPin Pin
PinP5_04 = CUChar
29
getHwPin Pin
PinP5_05 = CUChar
30
getHwPin Pin
PinP5_06 = CUChar
31
setPinFunction :: Pin -> PinMode -> IO ()
setPinFunction :: Pin -> PinMode -> IO ()
setPinFunction Pin
pin PinMode
mode = CUChar -> CUChar -> IO ()
c_setPinFunction (Pin -> CUChar
getHwPin Pin
pin) (Int -> CUChar
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUChar) -> Int -> CUChar
forall a b. (a -> b) -> a -> b
$ PinMode -> Int
forall a. Enum a => a -> Int
fromEnum PinMode
mode)
writePin :: Pin -> LogicLevel -> IO ()
writePin :: Pin -> LogicLevel -> IO ()
writePin Pin
pin LogicLevel
level = CUChar -> CUChar -> IO ()
c_writePin (Pin -> CUChar
getHwPin Pin
pin) (Int -> CUChar
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUChar) -> Int -> CUChar
forall a b. (a -> b) -> a -> b
$ LogicLevel -> Int
forall a. Enum a => a -> Int
fromEnum LogicLevel
level)
readPin :: Pin -> IO LogicLevel
readPin :: Pin -> IO LogicLevel
readPin Pin
pin = (Int -> LogicLevel
forall a. Enum a => Int -> a
toEnum (Int -> LogicLevel) -> (CUChar -> Int) -> CUChar -> LogicLevel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUChar -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) (CUChar -> LogicLevel) -> IO CUChar -> IO LogicLevel
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CUChar -> IO CUChar
c_readPin (Pin -> CUChar
getHwPin Pin
pin)
setI2cAddress :: Address -> IO ()
setI2cAddress :: Word8 -> IO ()
setI2cAddress Word8
a = CUChar -> IO ()
c_setSlaveAddressI2C (CUChar -> IO ()) -> CUChar -> IO ()
forall a b. (a -> b) -> a -> b
$ Word8 -> CUChar
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
a
setI2cClockDivider :: Word16 -> IO ()
setI2cClockDivider :: Word16 -> IO ()
setI2cClockDivider Word16
a = CUShort -> IO ()
c_setClockDividerI2C (CUShort -> IO ()) -> CUShort -> IO ()
forall a b. (a -> b) -> a -> b
$ Word16 -> CUShort
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
a
setI2cBaudRate :: Word32 -> IO ()
setI2cBaudRate :: Word32 -> IO ()
setI2cBaudRate Word32
a = CUInt -> IO ()
c_setBaudRateI2C (CUInt -> IO ()) -> CUInt -> IO ()
forall a b. (a -> b) -> a -> b
$ Word32 -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
a
writeI2C :: Address -> BS.ByteString -> IO ()
writeI2C :: Word8 -> ByteString -> IO ()
writeI2C Word8
address ByteString
by = ByteString -> (CStringLen -> IO ()) -> IO ()
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
by ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
bs,Int
len) -> do
Word8 -> IO ()
setI2cAddress Word8
address
CUChar
readresult <- Ptr CChar -> CUInt -> IO CUChar
c_writeI2C Ptr CChar
bs (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
case CUChar
readresult of
CUChar
0x01 -> IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
IllegalOperation String
"I2C: " String
"Received an unexpected NACK." Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
CUChar
0x02 -> IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
IllegalOperation String
"I2C: " String
"Received Clock Stretch Timeout." Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
CUChar
0x04 -> IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
IllegalOperation String
"I2C: " String
"Not all data was read." Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
CUChar
0x00 -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
readI2C :: Address -> Int -> IO BS.ByteString
readI2C :: Word8 -> Int -> IO ByteString
readI2C Word8
address Int
num = Int -> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes (Int
numInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) ((Ptr CChar -> IO ByteString) -> IO ByteString)
-> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
buf -> do
Word8 -> IO ()
setI2cAddress Word8
address
CUChar
readresult <- Ptr CChar -> CUShort -> IO CUChar
c_readI2C Ptr CChar
buf (Int -> CUShort
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
num)
CUChar -> CStringLen -> IO ByteString
actOnResult CUChar
readresult (Ptr CChar
buf, Int
num)
writeReadRSI2C :: Address -> BS.ByteString -> Int -> IO BS.ByteString
writeReadRSI2C :: Word8 -> ByteString -> Int -> IO ByteString
writeReadRSI2C Word8
address ByteString
by Int
num = ByteString -> (CStringLen -> IO ByteString) -> IO ByteString
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
by ((CStringLen -> IO ByteString) -> IO ByteString)
-> (CStringLen -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
bs,Int
len) -> do
Int -> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
num ((Ptr CChar -> IO ByteString) -> IO ByteString)
-> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
buf -> do
Word8 -> IO ()
setI2cAddress Word8
address
CUChar
readresult <- Ptr CChar -> CUInt -> Ptr CChar -> CUInt -> IO CUChar
c_writeReadRSI2C Ptr CChar
bs (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len) Ptr CChar
buf (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
num)
CUChar -> CStringLen -> IO ByteString
actOnResult CUChar
readresult (Ptr CChar
buf, Int
num)
chipSelectSPI :: SPIPin -> IO ()
chipSelectSPI :: SPIPin -> IO ()
chipSelectSPI SPIPin
pin = CUChar -> IO ()
c_chipSelectSPI (Int -> CUChar
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUChar) -> (SPIPin -> Int) -> SPIPin -> CUChar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SPIPin -> Int
forall a. Enum a => a -> Int
fromEnum (SPIPin -> CUChar) -> SPIPin -> CUChar
forall a b. (a -> b) -> a -> b
$ SPIPin
pin)
setClockDividerSPI :: Word16 -> IO ()
setClockDividerSPI :: Word16 -> IO ()
setClockDividerSPI Word16
a = CUShort -> IO ()
c_setClockDividerSPI (CUShort -> IO ()) -> CUShort -> IO ()
forall a b. (a -> b) -> a -> b
$ Word16 -> CUShort
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
a
setBitOrderSPI :: SPIBitOrder -> IO ()
setBitOrderSPI :: SPIBitOrder -> IO ()
setBitOrderSPI SPIBitOrder
LSBFirst = CUChar -> IO ()
c_setBitOrder CUChar
0
setBitOrderSPI SPIBitOrder
MSBFirst = CUChar -> IO ()
c_setBitOrder CUChar
1
setChipSelectPolaritySPI :: SPIPin -> LogicLevel -> IO ()
setChipSelectPolaritySPI :: SPIPin -> LogicLevel -> IO ()
setChipSelectPolaritySPI SPIPin
pin LogicLevel
level = CUChar -> CUChar -> IO ()
c_setChipSelectPolarity (Int -> CUChar
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUChar) -> (SPIPin -> Int) -> SPIPin -> CUChar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SPIPin -> Int
forall a. Enum a => a -> Int
fromEnum (SPIPin -> CUChar) -> SPIPin -> CUChar
forall a b. (a -> b) -> a -> b
$ SPIPin
pin) (Int -> CUChar
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUChar) -> (LogicLevel -> Int) -> LogicLevel -> CUChar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LogicLevel -> Int
forall a. Enum a => a -> Int
fromEnum (LogicLevel -> CUChar) -> LogicLevel -> CUChar
forall a b. (a -> b) -> a -> b
$ LogicLevel
level)
setDataModeSPI :: (CPOL,CPHA) -> IO ()
setDataModeSPI :: (LogicLevel, LogicLevel) -> IO ()
setDataModeSPI (LogicLevel
False,LogicLevel
False) = CUChar -> IO ()
c_setDataModeSPI CUChar
0
setDataModeSPI (LogicLevel
False,LogicLevel
True) = CUChar -> IO ()
c_setDataModeSPI CUChar
1
setDataModeSPI (LogicLevel
True,LogicLevel
False) = CUChar -> IO ()
c_setDataModeSPI CUChar
2
setDataModeSPI (LogicLevel
True,LogicLevel
True) = CUChar -> IO ()
c_setDataModeSPI CUChar
3
transferSPI :: Word8 -> IO Word8
transferSPI :: Word8 -> IO Word8
transferSPI Word8
input = CUChar -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUChar -> Word8) -> IO CUChar -> IO Word8
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CUChar -> IO CUChar
c_transferSPI (Word8 -> CUChar
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
input)
transferManySPI :: [Word8] -> IO [Word8]
transferManySPI :: [Word8] -> IO [Word8]
transferManySPI [Word8]
input = ByteString -> (CStringLen -> IO [Word8]) -> IO [Word8]
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ([Word8] -> ByteString
BS.pack [Word8]
input) ((CStringLen -> IO [Word8]) -> IO [Word8])
-> (CStringLen -> IO [Word8]) -> IO [Word8]
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
buf,Int
len) -> do
Ptr CChar -> CUInt -> IO ()
c_transferManySPI Ptr CChar
buf (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
(CStringLen -> IO ByteString
BS.packCStringLen (Ptr CChar
buf,Int
len)) IO ByteString -> (ByteString -> IO [Word8]) -> IO [Word8]
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Word8] -> IO [Word8]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Word8] -> IO [Word8])
-> (ByteString -> [Word8]) -> ByteString -> IO [Word8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Word8]
BS.unpack
withAUXSPI :: IO a -> IO a
withAUXSPI :: forall a. IO a -> IO a
withAUXSPI IO a
f = IO Int -> (Int -> IO ()) -> (Int -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket IO Int
initAUXSPI
(IO () -> Int -> IO ()
forall a b. a -> b -> a
const IO ()
stopAUXSPI)
(\Int
r -> if Int
rInt -> Int -> LogicLevel
forall a. Eq a => a -> a -> LogicLevel
==Int
0 then IOException -> IO a
forall e a. Exception e => e -> IO a
throwIO IOException
ioe else IO a
f)
where ioe :: IOException
ioe = Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
IllegalOperation String
"AUXAPI: " String
"Unable to start AUXAPI." Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
setClockDividerAUXSPI :: Word16 -> IO ()
setClockDividerAUXSPI :: Word16 -> IO ()
setClockDividerAUXSPI Word16
a = CUShort -> IO ()
c_setClockDividerAUXSPI (CUShort -> IO ()) -> CUShort -> IO ()
forall a b. (a -> b) -> a -> b
$ Word16 -> CUShort
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
a
transferAUXSPI :: Word8 -> IO Word8
transferAUXSPI :: Word8 -> IO Word8
transferAUXSPI Word8
input = CUChar -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUChar -> Word8) -> IO CUChar -> IO Word8
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CUChar -> IO CUChar
c_transferAUXSPI (Word8 -> CUChar
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
input)
setClockPWM :: Word32 -> IO ()
setClockPWM :: Word32 -> IO ()
setClockPWM Word32
a = CUInt -> IO ()
c_setClockPWM (CUInt -> IO ()) -> CUInt -> IO ()
forall a b. (a -> b) -> a -> b
$ Word32 -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
a
setModePWM :: Word8 -> Word8 -> Word8 -> IO ()
setModePWM :: Word8 -> Word8 -> Word8 -> IO ()
setModePWM Word8
a Word8
b Word8
c = CUChar -> CUChar -> CUChar -> IO ()
c_setModePWM (Word8 -> CUChar
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
a) (Word8 -> CUChar
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
b) (Word8 -> CUChar
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
c)
setRangePWM :: Word8 -> Word32 -> IO ()
setRangePWM :: Word8 -> Word32 -> IO ()
setRangePWM Word8
a Word32
b = CUChar -> CUInt -> IO ()
c_setRangePWM (Word8 -> CUChar
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
a) (Word32 -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
b)
setDataPWM :: Word8 -> Word32 -> IO ()
setDataPWM :: Word8 -> Word32 -> IO ()
setDataPWM Word8
a Word32
b = CUChar -> CUInt -> IO ()
c_setDataPWM (Word8 -> CUChar
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
a) (Word32 -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
b)