{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# LANGUAGE NoImplicitPrelude           #-}
{-# LANGUAGE TemplateHaskell             #-}
{-# LANGUAGE RecordWildCards             #-}

-- |
-- Module:      SwiftNav.SBP.Imu
-- Copyright:   Copyright (C) 2015-2021 Swift Navigation, Inc.
-- License:     MIT
-- Contact:     https://support.swiftnav.com
-- Stability:   experimental
-- Portability: portable
--
-- \< Inertial Measurement Unit (IMU) messages. \>

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

-- | SBP class for message MSG_IMU_RAW (0x0900).
--
-- Raw data from the Inertial Measurement Unit, containing accelerometer and
-- gyroscope readings. The sense of the measurements are to be aligned with
-- the indications on the device itself. Measurement units, which are specific
-- to the device hardware and settings, are communicated via the MSG_IMU_AUX
-- message. If using "time since startup" time tags, the receiving end will
-- expect a `MSG_GNSS_TIME_OFFSET` when a PVT fix becomes available to
-- synchronise IMU measurements with GNSS. The timestamp must wrap around to
-- zero when reaching one week (604800 seconds).
--
-- The time-tagging mode should not change throughout a run.
data MsgImuRaw = MsgImuRaw
  { MsgImuRaw -> Word32
_msgImuRaw_tow :: !Word32
    -- ^ Milliseconds since reference epoch and time status.
  , MsgImuRaw -> Word8
_msgImuRaw_tow_f :: !Word8
    -- ^ Milliseconds since reference epoch, fractional part
  , MsgImuRaw -> Int16
_msgImuRaw_acc_x :: !Int16
    -- ^ Acceleration in the IMU frame X axis
  , MsgImuRaw -> Int16
_msgImuRaw_acc_y :: !Int16
    -- ^ Acceleration in the IMU frame Y axis
  , MsgImuRaw -> Int16
_msgImuRaw_acc_z :: !Int16
    -- ^ Acceleration in the IMU frame Z axis
  , MsgImuRaw -> Int16
_msgImuRaw_gyr_x :: !Int16
    -- ^ Angular rate around IMU frame X axis
  , MsgImuRaw -> Int16
_msgImuRaw_gyr_y :: !Int16
    -- ^ Angular rate around IMU frame Y axis
  , MsgImuRaw -> Int16
_msgImuRaw_gyr_z :: !Int16
    -- ^ Angular rate around IMU frame Z axis
  } deriving ( Int -> MsgImuRaw -> ShowS
[MsgImuRaw] -> ShowS
MsgImuRaw -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MsgImuRaw] -> ShowS
$cshowList :: [MsgImuRaw] -> ShowS
show :: MsgImuRaw -> String
$cshow :: MsgImuRaw -> String
showsPrec :: Int -> MsgImuRaw -> ShowS
$cshowsPrec :: Int -> MsgImuRaw -> ShowS
Show, ReadPrec [MsgImuRaw]
ReadPrec MsgImuRaw
Int -> ReadS MsgImuRaw
ReadS [MsgImuRaw]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MsgImuRaw]
$creadListPrec :: ReadPrec [MsgImuRaw]
readPrec :: ReadPrec MsgImuRaw
$creadPrec :: ReadPrec MsgImuRaw
readList :: ReadS [MsgImuRaw]
$creadList :: ReadS [MsgImuRaw]
readsPrec :: Int -> ReadS MsgImuRaw
$creadsPrec :: Int -> ReadS MsgImuRaw
Read, MsgImuRaw -> MsgImuRaw -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MsgImuRaw -> MsgImuRaw -> Bool
$c/= :: MsgImuRaw -> MsgImuRaw -> Bool
== :: MsgImuRaw -> MsgImuRaw -> Bool
$c== :: 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 <- (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le)
    Int16
_msgImuRaw_acc_y <- (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le)
    Int16
_msgImuRaw_acc_z <- (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le)
    Int16
_msgImuRaw_gyr_x <- (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le)
    Int16
_msgImuRaw_gyr_y <- (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le)
    Int16
_msgImuRaw_gyr_z <- (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le)
    forall (f :: * -> *) a. Applicative f => a -> f a
pure MsgImuRaw {Int16
Word8
Word32
_msgImuRaw_gyr_z :: Int16
_msgImuRaw_gyr_y :: Int16
_msgImuRaw_gyr_x :: Int16
_msgImuRaw_acc_z :: Int16
_msgImuRaw_acc_y :: Int16
_msgImuRaw_acc_x :: Int16
_msgImuRaw_tow_f :: Word8
_msgImuRaw_tow :: Word32
_msgImuRaw_gyr_z :: Int16
_msgImuRaw_gyr_y :: Int16
_msgImuRaw_gyr_x :: Int16
_msgImuRaw_acc_z :: Int16
_msgImuRaw_acc_y :: Int16
_msgImuRaw_acc_x :: Int16
_msgImuRaw_tow_f :: Word8
_msgImuRaw_tow :: Word32
..}

  put :: MsgImuRaw -> Put
put MsgImuRaw {Int16
Word8
Word32
_msgImuRaw_gyr_z :: Int16
_msgImuRaw_gyr_y :: Int16
_msgImuRaw_gyr_x :: Int16
_msgImuRaw_acc_z :: Int16
_msgImuRaw_acc_y :: Int16
_msgImuRaw_acc_x :: Int16
_msgImuRaw_tow_f :: Word8
_msgImuRaw_tow :: Word32
_msgImuRaw_gyr_z :: MsgImuRaw -> Int16
_msgImuRaw_gyr_y :: MsgImuRaw -> Int16
_msgImuRaw_gyr_x :: MsgImuRaw -> Int16
_msgImuRaw_acc_z :: MsgImuRaw -> Int16
_msgImuRaw_acc_y :: MsgImuRaw -> Int16
_msgImuRaw_acc_x :: MsgImuRaw -> Int16
_msgImuRaw_tow_f :: MsgImuRaw -> Word8
_msgImuRaw_tow :: MsgImuRaw -> Word32
..} = do
    Word32 -> Put
putWord32le Word32
_msgImuRaw_tow
    Word8 -> Put
putWord8 Word8
_msgImuRaw_tow_f
    (Word16 -> Put
putWord16le forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral) Int16
_msgImuRaw_acc_x
    (Word16 -> Put
putWord16le forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral) Int16
_msgImuRaw_acc_y
    (Word16 -> Put
putWord16le forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral) Int16
_msgImuRaw_acc_z
    (Word16 -> Put
putWord16le forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral) Int16
_msgImuRaw_gyr_x
    (Word16 -> Put
putWord16le forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral) Int16
_msgImuRaw_gyr_y
    (Word16 -> Put
putWord16le forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. 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

-- | SBP class for message MSG_IMU_AUX (0x0901).
--
-- Auxiliary data specific to a particular IMU. The `imu_type` field will
-- always be consistent but the rest of the payload is device specific and
-- depends on the value of `imu_type`.
data MsgImuAux = MsgImuAux
  { MsgImuAux -> Word8
_msgImuAux_imu_type :: !Word8
    -- ^ IMU type
  , MsgImuAux -> Int16
_msgImuAux_temp   :: !Int16
    -- ^ Raw IMU temperature
  , MsgImuAux -> Word8
_msgImuAux_imu_conf :: !Word8
    -- ^ IMU configuration
  } deriving ( Int -> MsgImuAux -> ShowS
[MsgImuAux] -> ShowS
MsgImuAux -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MsgImuAux] -> ShowS
$cshowList :: [MsgImuAux] -> ShowS
show :: MsgImuAux -> String
$cshow :: MsgImuAux -> String
showsPrec :: Int -> MsgImuAux -> ShowS
$cshowsPrec :: Int -> MsgImuAux -> ShowS
Show, ReadPrec [MsgImuAux]
ReadPrec MsgImuAux
Int -> ReadS MsgImuAux
ReadS [MsgImuAux]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MsgImuAux]
$creadListPrec :: ReadPrec [MsgImuAux]
readPrec :: ReadPrec MsgImuAux
$creadPrec :: ReadPrec MsgImuAux
readList :: ReadS [MsgImuAux]
$creadList :: ReadS [MsgImuAux]
readsPrec :: Int -> ReadS MsgImuAux
$creadsPrec :: Int -> ReadS MsgImuAux
Read, MsgImuAux -> MsgImuAux -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MsgImuAux -> MsgImuAux -> Bool
$c/= :: MsgImuAux -> MsgImuAux -> Bool
== :: MsgImuAux -> MsgImuAux -> Bool
$c== :: MsgImuAux -> MsgImuAux -> Bool
Eq )

instance Binary MsgImuAux where
  get :: Get MsgImuAux
get = do
    Word8
_msgImuAux_imu_type <- Get Word8
getWord8
    Int16
_msgImuAux_temp <- (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le)
    Word8
_msgImuAux_imu_conf <- Get Word8
getWord8
    forall (f :: * -> *) a. Applicative f => a -> f a
pure MsgImuAux {Int16
Word8
_msgImuAux_imu_conf :: Word8
_msgImuAux_temp :: Int16
_msgImuAux_imu_type :: Word8
_msgImuAux_imu_conf :: Word8
_msgImuAux_temp :: Int16
_msgImuAux_imu_type :: Word8
..}

  put :: MsgImuAux -> Put
put MsgImuAux {Int16
Word8
_msgImuAux_imu_conf :: Word8
_msgImuAux_temp :: Int16
_msgImuAux_imu_type :: Word8
_msgImuAux_imu_conf :: MsgImuAux -> Word8
_msgImuAux_temp :: MsgImuAux -> Int16
_msgImuAux_imu_type :: MsgImuAux -> Word8
..} = do
    Word8 -> Put
putWord8 Word8
_msgImuAux_imu_type
    (Word16 -> Put
putWord16le forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. 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)