{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE RecordWildCards #-}
module SwiftNav.SBP.Imu
( module SwiftNav.SBP.Imu
) where
import BasicPrelude
import Control.Lens
import Control.Monad.Loops
import Data.Binary
import Data.Binary.Get
import Data.Binary.IEEE754
import Data.Binary.Put
import Data.ByteString.Lazy hiding (ByteString)
import Data.Int
import Data.Word
import SwiftNav.SBP.TH
import SwiftNav.SBP.Types
{-# ANN module ("HLint: ignore Use camelCase"::String) #-}
{-# ANN module ("HLint: ignore Redundant do"::String) #-}
{-# ANN module ("HLint: ignore Use newtype instead of data"::String) #-}
msgImuRaw :: Word16
msgImuRaw :: Word16
msgImuRaw = Word16
0x0900
data MsgImuRaw = MsgImuRaw
{ MsgImuRaw -> Word32
_msgImuRaw_tow :: !Word32
, MsgImuRaw -> Word8
_msgImuRaw_tow_f :: !Word8
, MsgImuRaw -> Int16
_msgImuRaw_acc_x :: !Int16
, MsgImuRaw -> Int16
_msgImuRaw_acc_y :: !Int16
, MsgImuRaw -> Int16
_msgImuRaw_acc_z :: !Int16
, MsgImuRaw -> Int16
_msgImuRaw_gyr_x :: !Int16
, MsgImuRaw -> Int16
_msgImuRaw_gyr_y :: !Int16
, MsgImuRaw -> Int16
_msgImuRaw_gyr_z :: !Int16
} deriving ( Int -> MsgImuRaw -> ShowS
[MsgImuRaw] -> ShowS
MsgImuRaw -> String
(Int -> MsgImuRaw -> ShowS)
-> (MsgImuRaw -> String)
-> ([MsgImuRaw] -> ShowS)
-> Show MsgImuRaw
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MsgImuRaw -> ShowS
showsPrec :: Int -> MsgImuRaw -> ShowS
$cshow :: MsgImuRaw -> String
show :: MsgImuRaw -> String
$cshowList :: [MsgImuRaw] -> ShowS
showList :: [MsgImuRaw] -> ShowS
Show, ReadPrec [MsgImuRaw]
ReadPrec MsgImuRaw
Int -> ReadS MsgImuRaw
ReadS [MsgImuRaw]
(Int -> ReadS MsgImuRaw)
-> ReadS [MsgImuRaw]
-> ReadPrec MsgImuRaw
-> ReadPrec [MsgImuRaw]
-> Read MsgImuRaw
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MsgImuRaw
readsPrec :: Int -> ReadS MsgImuRaw
$creadList :: ReadS [MsgImuRaw]
readList :: ReadS [MsgImuRaw]
$creadPrec :: ReadPrec MsgImuRaw
readPrec :: ReadPrec MsgImuRaw
$creadListPrec :: ReadPrec [MsgImuRaw]
readListPrec :: ReadPrec [MsgImuRaw]
Read, MsgImuRaw -> MsgImuRaw -> Bool
(MsgImuRaw -> MsgImuRaw -> Bool)
-> (MsgImuRaw -> MsgImuRaw -> Bool) -> Eq MsgImuRaw
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MsgImuRaw -> MsgImuRaw -> Bool
== :: MsgImuRaw -> MsgImuRaw -> Bool
$c/= :: MsgImuRaw -> MsgImuRaw -> Bool
/= :: MsgImuRaw -> MsgImuRaw -> Bool
Eq )
instance Binary MsgImuRaw where
get :: Get MsgImuRaw
get = do
Word32
_msgImuRaw_tow <- Get Word32
getWord32le
Word8
_msgImuRaw_tow_f <- Get Word8
getWord8
Int16
_msgImuRaw_acc_x <- (Word16 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Int16) -> Get Word16 -> Get Int16
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le)
Int16
_msgImuRaw_acc_y <- (Word16 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Int16) -> Get Word16 -> Get Int16
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le)
Int16
_msgImuRaw_acc_z <- (Word16 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Int16) -> Get Word16 -> Get Int16
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le)
Int16
_msgImuRaw_gyr_x <- (Word16 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Int16) -> Get Word16 -> Get Int16
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le)
Int16
_msgImuRaw_gyr_y <- (Word16 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Int16) -> Get Word16 -> Get Int16
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le)
Int16
_msgImuRaw_gyr_z <- (Word16 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Int16) -> Get Word16 -> Get Int16
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le)
MsgImuRaw -> Get MsgImuRaw
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure MsgImuRaw {Int16
Word8
Word32
_msgImuRaw_tow :: Word32
_msgImuRaw_tow_f :: Word8
_msgImuRaw_acc_x :: Int16
_msgImuRaw_acc_y :: Int16
_msgImuRaw_acc_z :: Int16
_msgImuRaw_gyr_x :: Int16
_msgImuRaw_gyr_y :: Int16
_msgImuRaw_gyr_z :: Int16
_msgImuRaw_tow :: Word32
_msgImuRaw_tow_f :: Word8
_msgImuRaw_acc_x :: Int16
_msgImuRaw_acc_y :: Int16
_msgImuRaw_acc_z :: Int16
_msgImuRaw_gyr_x :: Int16
_msgImuRaw_gyr_y :: Int16
_msgImuRaw_gyr_z :: Int16
..}
put :: MsgImuRaw -> Put
put MsgImuRaw {Int16
Word8
Word32
_msgImuRaw_tow :: MsgImuRaw -> Word32
_msgImuRaw_tow_f :: MsgImuRaw -> Word8
_msgImuRaw_acc_x :: MsgImuRaw -> Int16
_msgImuRaw_acc_y :: MsgImuRaw -> Int16
_msgImuRaw_acc_z :: MsgImuRaw -> Int16
_msgImuRaw_gyr_x :: MsgImuRaw -> Int16
_msgImuRaw_gyr_y :: MsgImuRaw -> Int16
_msgImuRaw_gyr_z :: MsgImuRaw -> Int16
_msgImuRaw_tow :: Word32
_msgImuRaw_tow_f :: Word8
_msgImuRaw_acc_x :: Int16
_msgImuRaw_acc_y :: Int16
_msgImuRaw_acc_z :: Int16
_msgImuRaw_gyr_x :: Int16
_msgImuRaw_gyr_y :: Int16
_msgImuRaw_gyr_z :: Int16
..} = do
Word32 -> Put
putWord32le Word32
_msgImuRaw_tow
Word8 -> Put
putWord8 Word8
_msgImuRaw_tow_f
(Word16 -> Put
putWord16le (Word16 -> Put) -> (Int16 -> Word16) -> Int16 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral) Int16
_msgImuRaw_acc_x
(Word16 -> Put
putWord16le (Word16 -> Put) -> (Int16 -> Word16) -> Int16 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral) Int16
_msgImuRaw_acc_y
(Word16 -> Put
putWord16le (Word16 -> Put) -> (Int16 -> Word16) -> Int16 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral) Int16
_msgImuRaw_acc_z
(Word16 -> Put
putWord16le (Word16 -> Put) -> (Int16 -> Word16) -> Int16 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral) Int16
_msgImuRaw_gyr_x
(Word16 -> Put
putWord16le (Word16 -> Put) -> (Int16 -> Word16) -> Int16 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral) Int16
_msgImuRaw_gyr_y
(Word16 -> Put
putWord16le (Word16 -> Put) -> (Int16 -> Word16) -> Int16 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral) Int16
_msgImuRaw_gyr_z
$(makeSBP 'msgImuRaw ''MsgImuRaw)
$(makeJSON "_msgImuRaw_" ''MsgImuRaw)
$(makeLenses ''MsgImuRaw)
msgImuAux :: Word16
msgImuAux :: Word16
msgImuAux = Word16
0x0901
data MsgImuAux = MsgImuAux
{ MsgImuAux -> Word8
_msgImuAux_imu_type :: !Word8
, MsgImuAux -> Int16
_msgImuAux_temp :: !Int16
, MsgImuAux -> Word8
_msgImuAux_imu_conf :: !Word8
} deriving ( Int -> MsgImuAux -> ShowS
[MsgImuAux] -> ShowS
MsgImuAux -> String
(Int -> MsgImuAux -> ShowS)
-> (MsgImuAux -> String)
-> ([MsgImuAux] -> ShowS)
-> Show MsgImuAux
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MsgImuAux -> ShowS
showsPrec :: Int -> MsgImuAux -> ShowS
$cshow :: MsgImuAux -> String
show :: MsgImuAux -> String
$cshowList :: [MsgImuAux] -> ShowS
showList :: [MsgImuAux] -> ShowS
Show, ReadPrec [MsgImuAux]
ReadPrec MsgImuAux
Int -> ReadS MsgImuAux
ReadS [MsgImuAux]
(Int -> ReadS MsgImuAux)
-> ReadS [MsgImuAux]
-> ReadPrec MsgImuAux
-> ReadPrec [MsgImuAux]
-> Read MsgImuAux
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MsgImuAux
readsPrec :: Int -> ReadS MsgImuAux
$creadList :: ReadS [MsgImuAux]
readList :: ReadS [MsgImuAux]
$creadPrec :: ReadPrec MsgImuAux
readPrec :: ReadPrec MsgImuAux
$creadListPrec :: ReadPrec [MsgImuAux]
readListPrec :: ReadPrec [MsgImuAux]
Read, MsgImuAux -> MsgImuAux -> Bool
(MsgImuAux -> MsgImuAux -> Bool)
-> (MsgImuAux -> MsgImuAux -> Bool) -> Eq MsgImuAux
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MsgImuAux -> MsgImuAux -> Bool
== :: MsgImuAux -> MsgImuAux -> Bool
$c/= :: MsgImuAux -> MsgImuAux -> Bool
/= :: MsgImuAux -> MsgImuAux -> Bool
Eq )
instance Binary MsgImuAux where
get :: Get MsgImuAux
get = do
Word8
_msgImuAux_imu_type <- Get Word8
getWord8
Int16
_msgImuAux_temp <- (Word16 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Int16) -> Get Word16 -> Get Int16
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le)
Word8
_msgImuAux_imu_conf <- Get Word8
getWord8
MsgImuAux -> Get MsgImuAux
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure MsgImuAux {Int16
Word8
_msgImuAux_imu_type :: Word8
_msgImuAux_temp :: Int16
_msgImuAux_imu_conf :: Word8
_msgImuAux_imu_type :: Word8
_msgImuAux_temp :: Int16
_msgImuAux_imu_conf :: Word8
..}
put :: MsgImuAux -> Put
put MsgImuAux {Int16
Word8
_msgImuAux_imu_type :: MsgImuAux -> Word8
_msgImuAux_temp :: MsgImuAux -> Int16
_msgImuAux_imu_conf :: MsgImuAux -> Word8
_msgImuAux_imu_type :: Word8
_msgImuAux_temp :: Int16
_msgImuAux_imu_conf :: Word8
..} = do
Word8 -> Put
putWord8 Word8
_msgImuAux_imu_type
(Word16 -> Put
putWord16le (Word16 -> Put) -> (Int16 -> Word16) -> Int16 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral) Int16
_msgImuAux_temp
Word8 -> Put
putWord8 Word8
_msgImuAux_imu_conf
$(makeSBP 'msgImuAux ''MsgImuAux)
$(makeJSON "_msgImuAux_" ''MsgImuAux)
$(makeLenses ''MsgImuAux)
msgImuComp :: Word16
msgImuComp :: Word16
msgImuComp = Word16
0x0905
data MsgImuComp = MsgImuComp
{ MsgImuComp -> Word64
_msgImuComp_time :: !Word64
, MsgImuComp -> Word16
_msgImuComp_flags :: !Word16
, MsgImuComp -> Int32
_msgImuComp_acc_comp_x :: !Int32
, MsgImuComp -> Int32
_msgImuComp_acc_comp_y :: !Int32
, MsgImuComp -> Int32
_msgImuComp_acc_comp_z :: !Int32
, MsgImuComp -> Int32
_msgImuComp_gyr_comp_x :: !Int32
, MsgImuComp -> Int32
_msgImuComp_gyr_comp_y :: !Int32
, MsgImuComp -> Int32
_msgImuComp_gyr_comp_z :: !Int32
} deriving ( Int -> MsgImuComp -> ShowS
[MsgImuComp] -> ShowS
MsgImuComp -> String
(Int -> MsgImuComp -> ShowS)
-> (MsgImuComp -> String)
-> ([MsgImuComp] -> ShowS)
-> Show MsgImuComp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MsgImuComp -> ShowS
showsPrec :: Int -> MsgImuComp -> ShowS
$cshow :: MsgImuComp -> String
show :: MsgImuComp -> String
$cshowList :: [MsgImuComp] -> ShowS
showList :: [MsgImuComp] -> ShowS
Show, ReadPrec [MsgImuComp]
ReadPrec MsgImuComp
Int -> ReadS MsgImuComp
ReadS [MsgImuComp]
(Int -> ReadS MsgImuComp)
-> ReadS [MsgImuComp]
-> ReadPrec MsgImuComp
-> ReadPrec [MsgImuComp]
-> Read MsgImuComp
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MsgImuComp
readsPrec :: Int -> ReadS MsgImuComp
$creadList :: ReadS [MsgImuComp]
readList :: ReadS [MsgImuComp]
$creadPrec :: ReadPrec MsgImuComp
readPrec :: ReadPrec MsgImuComp
$creadListPrec :: ReadPrec [MsgImuComp]
readListPrec :: ReadPrec [MsgImuComp]
Read, MsgImuComp -> MsgImuComp -> Bool
(MsgImuComp -> MsgImuComp -> Bool)
-> (MsgImuComp -> MsgImuComp -> Bool) -> Eq MsgImuComp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MsgImuComp -> MsgImuComp -> Bool
== :: MsgImuComp -> MsgImuComp -> Bool
$c/= :: MsgImuComp -> MsgImuComp -> Bool
/= :: MsgImuComp -> MsgImuComp -> Bool
Eq )
instance Binary MsgImuComp where
get :: Get MsgImuComp
get = do
Word64
_msgImuComp_time <- Get Word64
getWord64le
Word16
_msgImuComp_flags <- Get Word16
getWord16le
Int32
_msgImuComp_acc_comp_x <- (Word32 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int32) -> Get Word32 -> Get Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32le)
Int32
_msgImuComp_acc_comp_y <- (Word32 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int32) -> Get Word32 -> Get Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32le)
Int32
_msgImuComp_acc_comp_z <- (Word32 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int32) -> Get Word32 -> Get Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32le)
Int32
_msgImuComp_gyr_comp_x <- (Word32 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int32) -> Get Word32 -> Get Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32le)
Int32
_msgImuComp_gyr_comp_y <- (Word32 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int32) -> Get Word32 -> Get Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32le)
Int32
_msgImuComp_gyr_comp_z <- (Word32 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int32) -> Get Word32 -> Get Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32le)
MsgImuComp -> Get MsgImuComp
forall a. a -> Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure MsgImuComp {Int32
Word16
Word64
_msgImuComp_time :: Word64
_msgImuComp_flags :: Word16
_msgImuComp_acc_comp_x :: Int32
_msgImuComp_acc_comp_y :: Int32
_msgImuComp_acc_comp_z :: Int32
_msgImuComp_gyr_comp_x :: Int32
_msgImuComp_gyr_comp_y :: Int32
_msgImuComp_gyr_comp_z :: Int32
_msgImuComp_time :: Word64
_msgImuComp_flags :: Word16
_msgImuComp_acc_comp_x :: Int32
_msgImuComp_acc_comp_y :: Int32
_msgImuComp_acc_comp_z :: Int32
_msgImuComp_gyr_comp_x :: Int32
_msgImuComp_gyr_comp_y :: Int32
_msgImuComp_gyr_comp_z :: Int32
..}
put :: MsgImuComp -> Put
put MsgImuComp {Int32
Word16
Word64
_msgImuComp_time :: MsgImuComp -> Word64
_msgImuComp_flags :: MsgImuComp -> Word16
_msgImuComp_acc_comp_x :: MsgImuComp -> Int32
_msgImuComp_acc_comp_y :: MsgImuComp -> Int32
_msgImuComp_acc_comp_z :: MsgImuComp -> Int32
_msgImuComp_gyr_comp_x :: MsgImuComp -> Int32
_msgImuComp_gyr_comp_y :: MsgImuComp -> Int32
_msgImuComp_gyr_comp_z :: MsgImuComp -> Int32
_msgImuComp_time :: Word64
_msgImuComp_flags :: Word16
_msgImuComp_acc_comp_x :: Int32
_msgImuComp_acc_comp_y :: Int32
_msgImuComp_acc_comp_z :: Int32
_msgImuComp_gyr_comp_x :: Int32
_msgImuComp_gyr_comp_y :: Int32
_msgImuComp_gyr_comp_z :: Int32
..} = do
Word64 -> Put
putWord64le Word64
_msgImuComp_time
Word16 -> Put
putWord16le Word16
_msgImuComp_flags
(Word32 -> Put
putWord32le (Word32 -> Put) -> (Int32 -> Word32) -> Int32 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral) Int32
_msgImuComp_acc_comp_x
(Word32 -> Put
putWord32le (Word32 -> Put) -> (Int32 -> Word32) -> Int32 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral) Int32
_msgImuComp_acc_comp_y
(Word32 -> Put
putWord32le (Word32 -> Put) -> (Int32 -> Word32) -> Int32 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral) Int32
_msgImuComp_acc_comp_z
(Word32 -> Put
putWord32le (Word32 -> Put) -> (Int32 -> Word32) -> Int32 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral) Int32
_msgImuComp_gyr_comp_x
(Word32 -> Put
putWord32le (Word32 -> Put) -> (Int32 -> Word32) -> Int32 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral) Int32
_msgImuComp_gyr_comp_y
(Word32 -> Put
putWord32le (Word32 -> Put) -> (Int32 -> Word32) -> Int32 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral) Int32
_msgImuComp_gyr_comp_z
$(makeSBP 'msgImuComp ''MsgImuComp)
$(makeJSON "_msgImuComp_" ''MsgImuComp)
$(makeLenses ''MsgImuComp)