{-# LINE 1 "src/Network/SocketCAN/Bindings.hsc" #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Network.SocketCAN.Bindings
(
SockAddrCAN(..)
, pattern CAN_RAW
, SocketCANArbitrationField(..)
, SocketCANFrame(..)
) where
import Data.Word (Word8, Word16, Word32)
import Foreign.Storable (Storable(..))
import Foreign.Marshal.Array (peekArray, pokeArray)
import Foreign.Ptr (plusPtr)
import Network.Socket.Address (SocketAddress(..))
import Network.Socket (ProtocolNumber)
newtype SockAddrCAN = SockAddrCAN Word32
deriving (SockAddrCAN -> SockAddrCAN -> Bool
(SockAddrCAN -> SockAddrCAN -> Bool)
-> (SockAddrCAN -> SockAddrCAN -> Bool) -> Eq SockAddrCAN
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SockAddrCAN -> SockAddrCAN -> Bool
== :: SockAddrCAN -> SockAddrCAN -> Bool
$c/= :: SockAddrCAN -> SockAddrCAN -> Bool
/= :: SockAddrCAN -> SockAddrCAN -> Bool
Eq, Eq SockAddrCAN
Eq SockAddrCAN =>
(SockAddrCAN -> SockAddrCAN -> Ordering)
-> (SockAddrCAN -> SockAddrCAN -> Bool)
-> (SockAddrCAN -> SockAddrCAN -> Bool)
-> (SockAddrCAN -> SockAddrCAN -> Bool)
-> (SockAddrCAN -> SockAddrCAN -> Bool)
-> (SockAddrCAN -> SockAddrCAN -> SockAddrCAN)
-> (SockAddrCAN -> SockAddrCAN -> SockAddrCAN)
-> Ord SockAddrCAN
SockAddrCAN -> SockAddrCAN -> Bool
SockAddrCAN -> SockAddrCAN -> Ordering
SockAddrCAN -> SockAddrCAN -> SockAddrCAN
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SockAddrCAN -> SockAddrCAN -> Ordering
compare :: SockAddrCAN -> SockAddrCAN -> Ordering
$c< :: SockAddrCAN -> SockAddrCAN -> Bool
< :: SockAddrCAN -> SockAddrCAN -> Bool
$c<= :: SockAddrCAN -> SockAddrCAN -> Bool
<= :: SockAddrCAN -> SockAddrCAN -> Bool
$c> :: SockAddrCAN -> SockAddrCAN -> Bool
> :: SockAddrCAN -> SockAddrCAN -> Bool
$c>= :: SockAddrCAN -> SockAddrCAN -> Bool
>= :: SockAddrCAN -> SockAddrCAN -> Bool
$cmax :: SockAddrCAN -> SockAddrCAN -> SockAddrCAN
max :: SockAddrCAN -> SockAddrCAN -> SockAddrCAN
$cmin :: SockAddrCAN -> SockAddrCAN -> SockAddrCAN
min :: SockAddrCAN -> SockAddrCAN -> SockAddrCAN
Ord)
type CSaFamily = (Word16)
{-# LINE 30 "src/Network/SocketCAN/Bindings.hsc" #-}
instance SocketAddress SockAddrCAN where
sizeOfSocketAddress :: SockAddrCAN -> Int
sizeOfSocketAddress (SockAddrCAN Word32
_) =
Int
24
{-# LINE 34 "src/Network/SocketCAN/Bindings.hsc" #-}
peekSocketAddress sap = do
ifidx <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) sap
{-# LINE 36 "src/Network/SocketCAN/Bindings.hsc" #-}
return (SockAddrCAN ifidx)
pokeSocketAddress :: forall a. Ptr a -> SockAddrCAN -> IO ()
pokeSocketAddress Ptr a
p (SockAddrCAN Word32
ifIndex) = do
((\Ptr a
hsc_ptr -> Ptr a -> Int -> CSaFamily -> IO ()
forall b. Ptr b -> Int -> CSaFamily -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr a
hsc_ptr Int
0)) Ptr a
p ((CSaFamily
29) :: CSaFamily)
{-# LINE 39 "src/Network/SocketCAN/Bindings.hsc" #-}
((\hsc_ptr -> pokeByteOff hsc_ptr 4)) p ifIndex
{-# LINE 40 "src/Network/SocketCAN/Bindings.hsc" #-}
pattern CAN_RAW :: ProtocolNumber
pattern $mCAN_RAW :: forall {r}. ProtocolNumber -> ((# #) -> r) -> ((# #) -> r) -> r
$bCAN_RAW :: ProtocolNumber
CAN_RAW = 1
{-# LINE 44 "src/Network/SocketCAN/Bindings.hsc" #-}
newtype SocketCANArbitrationField =
SocketCANArbitrationField { SocketCANArbitrationField -> Word32
unSocketCANArbitrationField :: Word32 }
deriving (SocketCANArbitrationField -> SocketCANArbitrationField -> Bool
(SocketCANArbitrationField -> SocketCANArbitrationField -> Bool)
-> (SocketCANArbitrationField -> SocketCANArbitrationField -> Bool)
-> Eq SocketCANArbitrationField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SocketCANArbitrationField -> SocketCANArbitrationField -> Bool
== :: SocketCANArbitrationField -> SocketCANArbitrationField -> Bool
$c/= :: SocketCANArbitrationField -> SocketCANArbitrationField -> Bool
/= :: SocketCANArbitrationField -> SocketCANArbitrationField -> Bool
Eq, Eq SocketCANArbitrationField
Eq SocketCANArbitrationField =>
(SocketCANArbitrationField
-> SocketCANArbitrationField -> Ordering)
-> (SocketCANArbitrationField -> SocketCANArbitrationField -> Bool)
-> (SocketCANArbitrationField -> SocketCANArbitrationField -> Bool)
-> (SocketCANArbitrationField -> SocketCANArbitrationField -> Bool)
-> (SocketCANArbitrationField -> SocketCANArbitrationField -> Bool)
-> (SocketCANArbitrationField
-> SocketCANArbitrationField -> SocketCANArbitrationField)
-> (SocketCANArbitrationField
-> SocketCANArbitrationField -> SocketCANArbitrationField)
-> Ord SocketCANArbitrationField
SocketCANArbitrationField -> SocketCANArbitrationField -> Bool
SocketCANArbitrationField -> SocketCANArbitrationField -> Ordering
SocketCANArbitrationField
-> SocketCANArbitrationField -> SocketCANArbitrationField
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SocketCANArbitrationField -> SocketCANArbitrationField -> Ordering
compare :: SocketCANArbitrationField -> SocketCANArbitrationField -> Ordering
$c< :: SocketCANArbitrationField -> SocketCANArbitrationField -> Bool
< :: SocketCANArbitrationField -> SocketCANArbitrationField -> Bool
$c<= :: SocketCANArbitrationField -> SocketCANArbitrationField -> Bool
<= :: SocketCANArbitrationField -> SocketCANArbitrationField -> Bool
$c> :: SocketCANArbitrationField -> SocketCANArbitrationField -> Bool
> :: SocketCANArbitrationField -> SocketCANArbitrationField -> Bool
$c>= :: SocketCANArbitrationField -> SocketCANArbitrationField -> Bool
>= :: SocketCANArbitrationField -> SocketCANArbitrationField -> Bool
$cmax :: SocketCANArbitrationField
-> SocketCANArbitrationField -> SocketCANArbitrationField
max :: SocketCANArbitrationField
-> SocketCANArbitrationField -> SocketCANArbitrationField
$cmin :: SocketCANArbitrationField
-> SocketCANArbitrationField -> SocketCANArbitrationField
min :: SocketCANArbitrationField
-> SocketCANArbitrationField -> SocketCANArbitrationField
Ord, Int -> SocketCANArbitrationField -> ShowS
[SocketCANArbitrationField] -> ShowS
SocketCANArbitrationField -> String
(Int -> SocketCANArbitrationField -> ShowS)
-> (SocketCANArbitrationField -> String)
-> ([SocketCANArbitrationField] -> ShowS)
-> Show SocketCANArbitrationField
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SocketCANArbitrationField -> ShowS
showsPrec :: Int -> SocketCANArbitrationField -> ShowS
$cshow :: SocketCANArbitrationField -> String
show :: SocketCANArbitrationField -> String
$cshowList :: [SocketCANArbitrationField] -> ShowS
showList :: [SocketCANArbitrationField] -> ShowS
Show, Ptr SocketCANArbitrationField -> IO SocketCANArbitrationField
Ptr SocketCANArbitrationField
-> Int -> IO SocketCANArbitrationField
Ptr SocketCANArbitrationField
-> Int -> SocketCANArbitrationField -> IO ()
Ptr SocketCANArbitrationField -> SocketCANArbitrationField -> IO ()
SocketCANArbitrationField -> Int
(SocketCANArbitrationField -> Int)
-> (SocketCANArbitrationField -> Int)
-> (Ptr SocketCANArbitrationField
-> Int -> IO SocketCANArbitrationField)
-> (Ptr SocketCANArbitrationField
-> Int -> SocketCANArbitrationField -> IO ())
-> (forall b. Ptr b -> Int -> IO SocketCANArbitrationField)
-> (forall b. Ptr b -> Int -> SocketCANArbitrationField -> IO ())
-> (Ptr SocketCANArbitrationField -> IO SocketCANArbitrationField)
-> (Ptr SocketCANArbitrationField
-> SocketCANArbitrationField -> IO ())
-> Storable SocketCANArbitrationField
forall b. Ptr b -> Int -> IO SocketCANArbitrationField
forall b. Ptr b -> Int -> SocketCANArbitrationField -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
$csizeOf :: SocketCANArbitrationField -> Int
sizeOf :: SocketCANArbitrationField -> Int
$calignment :: SocketCANArbitrationField -> Int
alignment :: SocketCANArbitrationField -> Int
$cpeekElemOff :: Ptr SocketCANArbitrationField
-> Int -> IO SocketCANArbitrationField
peekElemOff :: Ptr SocketCANArbitrationField
-> Int -> IO SocketCANArbitrationField
$cpokeElemOff :: Ptr SocketCANArbitrationField
-> Int -> SocketCANArbitrationField -> IO ()
pokeElemOff :: Ptr SocketCANArbitrationField
-> Int -> SocketCANArbitrationField -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO SocketCANArbitrationField
peekByteOff :: forall b. Ptr b -> Int -> IO SocketCANArbitrationField
$cpokeByteOff :: forall b. Ptr b -> Int -> SocketCANArbitrationField -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> SocketCANArbitrationField -> IO ()
$cpeek :: Ptr SocketCANArbitrationField -> IO SocketCANArbitrationField
peek :: Ptr SocketCANArbitrationField -> IO SocketCANArbitrationField
$cpoke :: Ptr SocketCANArbitrationField -> SocketCANArbitrationField -> IO ()
poke :: Ptr SocketCANArbitrationField -> SocketCANArbitrationField -> IO ()
Storable)
data SocketCANFrame = SocketCANFrame
{ SocketCANFrame -> SocketCANArbitrationField
socketCANFrameArbitrationField :: SocketCANArbitrationField
, SocketCANFrame -> Word8
socketCANFrameLength :: Word8
, SocketCANFrame -> [Word8]
socketCANFrameData :: [Word8]
} deriving Int -> SocketCANFrame -> ShowS
[SocketCANFrame] -> ShowS
SocketCANFrame -> String
(Int -> SocketCANFrame -> ShowS)
-> (SocketCANFrame -> String)
-> ([SocketCANFrame] -> ShowS)
-> Show SocketCANFrame
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SocketCANFrame -> ShowS
showsPrec :: Int -> SocketCANFrame -> ShowS
$cshow :: SocketCANFrame -> String
show :: SocketCANFrame -> String
$cshowList :: [SocketCANFrame] -> ShowS
showList :: [SocketCANFrame] -> ShowS
Show
instance Storable SocketCANFrame where
sizeOf :: SocketCANFrame -> Int
sizeOf ~SocketCANFrame
_ = Int
16
{-# LINE 58 "src/Network/SocketCAN/Bindings.hsc" #-}
alignment ~_ = 8
{-# LINE 59 "src/Network/SocketCAN/Bindings.hsc" #-}
peek ptr = do
socketCANFrameArbitrationField
<- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 62 "src/Network/SocketCAN/Bindings.hsc" #-}
socketCANFrameLength
<- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr
{-# LINE 64 "src/Network/SocketCAN/Bindings.hsc" #-}
socketCANFrameData <-
peekArray
(fromIntegral socketCANFrameLength)
((\hsc_ptr -> hsc_ptr `plusPtr` 8) ptr)
{-# LINE 68 "src/Network/SocketCAN/Bindings.hsc" #-}
pure
$ SocketCANFrame{..}
poke :: Ptr SocketCANFrame -> SocketCANFrame -> IO ()
poke Ptr SocketCANFrame
ptr SocketCANFrame{[Word8]
Word8
SocketCANArbitrationField
socketCANFrameArbitrationField :: SocketCANFrame -> SocketCANArbitrationField
socketCANFrameLength :: SocketCANFrame -> Word8
socketCANFrameData :: SocketCANFrame -> [Word8]
socketCANFrameArbitrationField :: SocketCANArbitrationField
socketCANFrameLength :: Word8
socketCANFrameData :: [Word8]
..} = do
(\Ptr SocketCANFrame
hsc_ptr -> Ptr SocketCANFrame -> Int -> SocketCANArbitrationField -> IO ()
forall b. Ptr b -> Int -> SocketCANArbitrationField -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SocketCANFrame
hsc_ptr Int
0)
{-# LINE 72 "src/Network/SocketCAN/Bindings.hsc" #-}
ptr
SocketCANArbitrationField
socketCANFrameArbitrationField
(\Ptr SocketCANFrame
hsc_ptr -> Ptr SocketCANFrame -> Int -> Word8 -> IO ()
forall b. Ptr b -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SocketCANFrame
hsc_ptr Int
4)
{-# LINE 75 "src/Network/SocketCAN/Bindings.hsc" #-}
ptr
Word8
socketCANFrameLength
Ptr Word8 -> [Word8] -> IO ()
forall a. Storable a => Ptr a -> [a] -> IO ()
pokeArray
((\Ptr SocketCANFrame
hsc_ptr -> Ptr SocketCANFrame
hsc_ptr Ptr SocketCANFrame -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) Ptr SocketCANFrame
ptr)
{-# LINE 79 "src/Network/SocketCAN/Bindings.hsc" #-}
socketCANFrameData