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

-- |
-- Module:      SwiftNav.SBP.Msg
-- Copyright:   Copyright (C) 2015-2021 Swift Navigation, Inc.
-- License:     MIT
-- Contact:     https://support.swiftnav.com
-- Stability:   experimental
-- Portability: portable
--
-- SBP message containers.

module SwiftNav.SBP.Msg
  ( module SwiftNav.SBP.Msg
  ) where

import BasicPrelude
import Control.Lens
import Data.Aeson               hiding (decode)
import Data.Aeson.Lens
import Data.Binary
import Data.ByteString.Lazy     hiding (ByteString)
import SwiftNav.SBP.Acquisition
import SwiftNav.SBP.Bootload
import SwiftNav.SBP.ExtEvents
import SwiftNav.SBP.FileIo
import SwiftNav.SBP.Flash
import SwiftNav.SBP.Gnss
import SwiftNav.SBP.Imu
import SwiftNav.SBP.Integrity
import SwiftNav.SBP.Linux
import SwiftNav.SBP.Logging
import SwiftNav.SBP.Mag
import SwiftNav.SBP.Navigation
import SwiftNav.SBP.Ndb
import SwiftNav.SBP.Observation
import SwiftNav.SBP.Orientation
import SwiftNav.SBP.Piksi
import SwiftNav.SBP.Sbas
import SwiftNav.SBP.Settings
import SwiftNav.SBP.Signing
import SwiftNav.SBP.SolutionMeta
import SwiftNav.SBP.Ssr
import SwiftNav.SBP.System
import SwiftNav.SBP.Tracking
import SwiftNav.SBP.User
import SwiftNav.SBP.Vehicle
import SwiftNav.SBP.Types


-- | An SBP message ADT composed of all defined SBP messages.
--
-- Includes SBPMsgUnknown for valid SBP messages with undefined message
-- types and SBPMsgBadCRC for SBP messages with invalid CRC checksums.
data SBPMsg =
     SBPMsgAcqResult MsgAcqResult Msg
   | SBPMsgAcqResultDepA MsgAcqResultDepA Msg
   | SBPMsgAcqResultDepB MsgAcqResultDepB Msg
   | SBPMsgAcqResultDepC MsgAcqResultDepC Msg
   | SBPMsgAcqSvProfile MsgAcqSvProfile Msg
   | SBPMsgAcqSvProfileDep MsgAcqSvProfileDep Msg
   | SBPMsgAgeCorrections MsgAgeCorrections Msg
   | SBPMsgAlmanac MsgAlmanac Msg
   | SBPMsgAlmanacGlo MsgAlmanacGlo Msg
   | SBPMsgAlmanacGloDep MsgAlmanacGloDep Msg
   | SBPMsgAlmanacGps MsgAlmanacGps Msg
   | SBPMsgAlmanacGpsDep MsgAlmanacGpsDep Msg
   | SBPMsgAngularRate MsgAngularRate Msg
   | SBPMsgBasePosEcef MsgBasePosEcef Msg
   | SBPMsgBasePosLlh MsgBasePosLlh Msg
   | SBPMsgBaselineEcef MsgBaselineEcef Msg
   | SBPMsgBaselineEcefDepA MsgBaselineEcefDepA Msg
   | SBPMsgBaselineHeading MsgBaselineHeading Msg
   | SBPMsgBaselineHeadingDepA MsgBaselineHeadingDepA Msg
   | SBPMsgBaselineNed MsgBaselineNed Msg
   | SBPMsgBaselineNedDepA MsgBaselineNedDepA Msg
   | SBPMsgBootloaderHandshakeDepA MsgBootloaderHandshakeDepA Msg
   | SBPMsgBootloaderHandshakeReq MsgBootloaderHandshakeReq Msg
   | SBPMsgBootloaderHandshakeResp MsgBootloaderHandshakeResp Msg
   | SBPMsgBootloaderJumpToApp MsgBootloaderJumpToApp Msg
   | SBPMsgCellModemStatus MsgCellModemStatus Msg
   | SBPMsgCommandOutput MsgCommandOutput Msg
   | SBPMsgCommandReq MsgCommandReq Msg
   | SBPMsgCommandResp MsgCommandResp Msg
   | SBPMsgCsacTelemetry MsgCsacTelemetry Msg
   | SBPMsgCsacTelemetryLabels MsgCsacTelemetryLabels Msg
   | SBPMsgCwResults MsgCwResults Msg
   | SBPMsgCwStart MsgCwStart Msg
   | SBPMsgDeviceMonitor MsgDeviceMonitor Msg
   | SBPMsgDgnssStatus MsgDgnssStatus Msg
   | SBPMsgDops MsgDops Msg
   | SBPMsgDopsDepA MsgDopsDepA Msg
   | SBPMsgEd25519Certificate MsgEd25519Certificate Msg
   | SBPMsgEd25519Signature MsgEd25519Signature Msg
   | SBPMsgEphemerisBds MsgEphemerisBds Msg
   | SBPMsgEphemerisDepA MsgEphemerisDepA Msg
   | SBPMsgEphemerisDepB MsgEphemerisDepB Msg
   | SBPMsgEphemerisDepC MsgEphemerisDepC Msg
   | SBPMsgEphemerisDepD MsgEphemerisDepD Msg
   | SBPMsgEphemerisGal MsgEphemerisGal Msg
   | SBPMsgEphemerisGalDepA MsgEphemerisGalDepA Msg
   | SBPMsgEphemerisGlo MsgEphemerisGlo Msg
   | SBPMsgEphemerisGloDepA MsgEphemerisGloDepA Msg
   | SBPMsgEphemerisGloDepB MsgEphemerisGloDepB Msg
   | SBPMsgEphemerisGloDepC MsgEphemerisGloDepC Msg
   | SBPMsgEphemerisGloDepD MsgEphemerisGloDepD Msg
   | SBPMsgEphemerisGps MsgEphemerisGps Msg
   | SBPMsgEphemerisGpsDepE MsgEphemerisGpsDepE Msg
   | SBPMsgEphemerisGpsDepF MsgEphemerisGpsDepF Msg
   | SBPMsgEphemerisQzss MsgEphemerisQzss Msg
   | SBPMsgEphemerisSbas MsgEphemerisSbas Msg
   | SBPMsgEphemerisSbasDepA MsgEphemerisSbasDepA Msg
   | SBPMsgEphemerisSbasDepB MsgEphemerisSbasDepB Msg
   | SBPMsgExtEvent MsgExtEvent Msg
   | SBPMsgFileioConfigReq MsgFileioConfigReq Msg
   | SBPMsgFileioConfigResp MsgFileioConfigResp Msg
   | SBPMsgFileioReadDirReq MsgFileioReadDirReq Msg
   | SBPMsgFileioReadDirResp MsgFileioReadDirResp Msg
   | SBPMsgFileioReadReq MsgFileioReadReq Msg
   | SBPMsgFileioReadResp MsgFileioReadResp Msg
   | SBPMsgFileioRemove MsgFileioRemove Msg
   | SBPMsgFileioWriteReq MsgFileioWriteReq Msg
   | SBPMsgFileioWriteResp MsgFileioWriteResp Msg
   | SBPMsgFlashDone MsgFlashDone Msg
   | SBPMsgFlashErase MsgFlashErase Msg
   | SBPMsgFlashProgram MsgFlashProgram Msg
   | SBPMsgFlashReadReq MsgFlashReadReq Msg
   | SBPMsgFlashReadResp MsgFlashReadResp Msg
   | SBPMsgFrontEndGain MsgFrontEndGain Msg
   | SBPMsgFwd MsgFwd Msg
   | SBPMsgGloBiases MsgGloBiases Msg
   | SBPMsgGnssCapb MsgGnssCapb Msg
   | SBPMsgGnssTimeOffset MsgGnssTimeOffset Msg
   | SBPMsgGpsTime MsgGpsTime Msg
   | SBPMsgGpsTimeDepA MsgGpsTimeDepA Msg
   | SBPMsgGpsTimeGnss MsgGpsTimeGnss Msg
   | SBPMsgGroupDelay MsgGroupDelay Msg
   | SBPMsgGroupDelayDepA MsgGroupDelayDepA Msg
   | SBPMsgGroupDelayDepB MsgGroupDelayDepB Msg
   | SBPMsgGroupMeta MsgGroupMeta Msg
   | SBPMsgHeartbeat MsgHeartbeat Msg
   | SBPMsgIarState MsgIarState Msg
   | SBPMsgImuAux MsgImuAux Msg
   | SBPMsgImuRaw MsgImuRaw Msg
   | SBPMsgInitBaseDep MsgInitBaseDep Msg
   | SBPMsgInsStatus MsgInsStatus Msg
   | SBPMsgInsUpdates MsgInsUpdates Msg
   | SBPMsgIono MsgIono Msg
   | SBPMsgLinuxCpuState MsgLinuxCpuState Msg
   | SBPMsgLinuxCpuStateDepA MsgLinuxCpuStateDepA Msg
   | SBPMsgLinuxMemState MsgLinuxMemState Msg
   | SBPMsgLinuxMemStateDepA MsgLinuxMemStateDepA Msg
   | SBPMsgLinuxProcessFdCount MsgLinuxProcessFdCount Msg
   | SBPMsgLinuxProcessFdSummary MsgLinuxProcessFdSummary Msg
   | SBPMsgLinuxProcessSocketCounts MsgLinuxProcessSocketCounts Msg
   | SBPMsgLinuxProcessSocketQueues MsgLinuxProcessSocketQueues Msg
   | SBPMsgLinuxSocketUsage MsgLinuxSocketUsage Msg
   | SBPMsgLinuxSysState MsgLinuxSysState Msg
   | SBPMsgLinuxSysStateDepA MsgLinuxSysStateDepA Msg
   | SBPMsgLog MsgLog Msg
   | SBPMsgM25FlashWriteStatus MsgM25FlashWriteStatus Msg
   | SBPMsgMagRaw MsgMagRaw Msg
   | SBPMsgMaskSatellite MsgMaskSatellite Msg
   | SBPMsgMaskSatelliteDep MsgMaskSatelliteDep Msg
   | SBPMsgMeasurementState MsgMeasurementState Msg
   | SBPMsgNapDeviceDnaReq MsgNapDeviceDnaReq Msg
   | SBPMsgNapDeviceDnaResp MsgNapDeviceDnaResp Msg
   | SBPMsgNdbEvent MsgNdbEvent Msg
   | SBPMsgNetworkBandwidthUsage MsgNetworkBandwidthUsage Msg
   | SBPMsgNetworkStateReq MsgNetworkStateReq Msg
   | SBPMsgNetworkStateResp MsgNetworkStateResp Msg
   | SBPMsgObs MsgObs Msg
   | SBPMsgObsDepA MsgObsDepA Msg
   | SBPMsgObsDepB MsgObsDepB Msg
   | SBPMsgObsDepC MsgObsDepC Msg
   | SBPMsgOdometry MsgOdometry Msg
   | SBPMsgOrientEuler MsgOrientEuler Msg
   | SBPMsgOrientQuat MsgOrientQuat Msg
   | SBPMsgOsr MsgOsr Msg
   | SBPMsgPosEcef MsgPosEcef Msg
   | SBPMsgPosEcefCov MsgPosEcefCov Msg
   | SBPMsgPosEcefCovGnss MsgPosEcefCovGnss Msg
   | SBPMsgPosEcefDepA MsgPosEcefDepA Msg
   | SBPMsgPosEcefGnss MsgPosEcefGnss Msg
   | SBPMsgPosLlh MsgPosLlh Msg
   | SBPMsgPosLlhAcc MsgPosLlhAcc Msg
   | SBPMsgPosLlhCov MsgPosLlhCov Msg
   | SBPMsgPosLlhCovGnss MsgPosLlhCovGnss Msg
   | SBPMsgPosLlhDepA MsgPosLlhDepA Msg
   | SBPMsgPosLlhGnss MsgPosLlhGnss Msg
   | SBPMsgPpsTime MsgPpsTime Msg
   | SBPMsgPrintDep MsgPrintDep Msg
   | SBPMsgProtectionLevel MsgProtectionLevel Msg
   | SBPMsgProtectionLevelDepA MsgProtectionLevelDepA Msg
   | SBPMsgReferenceFrameParam MsgReferenceFrameParam Msg
   | SBPMsgReset MsgReset Msg
   | SBPMsgResetDep MsgResetDep Msg
   | SBPMsgResetFilters MsgResetFilters Msg
   | SBPMsgSbasRaw MsgSbasRaw Msg
   | SBPMsgSensorAidEvent MsgSensorAidEvent Msg
   | SBPMsgSetTime MsgSetTime Msg
   | SBPMsgSettingsReadByIndexDone MsgSettingsReadByIndexDone Msg
   | SBPMsgSettingsReadByIndexReq MsgSettingsReadByIndexReq Msg
   | SBPMsgSettingsReadByIndexResp MsgSettingsReadByIndexResp Msg
   | SBPMsgSettingsReadReq MsgSettingsReadReq Msg
   | SBPMsgSettingsReadResp MsgSettingsReadResp Msg
   | SBPMsgSettingsRegister MsgSettingsRegister Msg
   | SBPMsgSettingsRegisterResp MsgSettingsRegisterResp Msg
   | SBPMsgSettingsSave MsgSettingsSave Msg
   | SBPMsgSettingsWrite MsgSettingsWrite Msg
   | SBPMsgSettingsWriteResp MsgSettingsWriteResp Msg
   | SBPMsgSolnMeta MsgSolnMeta Msg
   | SBPMsgSolnMetaDepA MsgSolnMetaDepA Msg
   | SBPMsgSpecan MsgSpecan Msg
   | SBPMsgSpecanDep MsgSpecanDep Msg
   | SBPMsgSsrCodeBiases MsgSsrCodeBiases Msg
   | SBPMsgSsrCodePhaseBiasesBounds MsgSsrCodePhaseBiasesBounds Msg
   | SBPMsgSsrFlagHighLevel MsgSsrFlagHighLevel Msg
   | SBPMsgSsrFlagIonoGridPointSatLos MsgSsrFlagIonoGridPointSatLos Msg
   | SBPMsgSsrFlagIonoGridPoints MsgSsrFlagIonoGridPoints Msg
   | SBPMsgSsrFlagIonoTileSatLos MsgSsrFlagIonoTileSatLos Msg
   | SBPMsgSsrFlagSatellites MsgSsrFlagSatellites Msg
   | SBPMsgSsrFlagTropoGridPoints MsgSsrFlagTropoGridPoints Msg
   | SBPMsgSsrGridDefinitionDepA MsgSsrGridDefinitionDepA Msg
   | SBPMsgSsrGriddedCorrection MsgSsrGriddedCorrection Msg
   | SBPMsgSsrGriddedCorrectionBounds MsgSsrGriddedCorrectionBounds Msg
   | SBPMsgSsrGriddedCorrectionDepA MsgSsrGriddedCorrectionDepA Msg
   | SBPMsgSsrGriddedCorrectionNoStdDepA MsgSsrGriddedCorrectionNoStdDepA Msg
   | SBPMsgSsrOrbitClock MsgSsrOrbitClock Msg
   | SBPMsgSsrOrbitClockBounds MsgSsrOrbitClockBounds Msg
   | SBPMsgSsrOrbitClockBoundsDegradation MsgSsrOrbitClockBoundsDegradation Msg
   | SBPMsgSsrOrbitClockDepA MsgSsrOrbitClockDepA Msg
   | SBPMsgSsrPhaseBiases MsgSsrPhaseBiases Msg
   | SBPMsgSsrSatelliteApc MsgSsrSatelliteApc Msg
   | SBPMsgSsrStecCorrection MsgSsrStecCorrection Msg
   | SBPMsgSsrStecCorrectionDep MsgSsrStecCorrectionDep Msg
   | SBPMsgSsrStecCorrectionDepA MsgSsrStecCorrectionDepA Msg
   | SBPMsgSsrTileDefinition MsgSsrTileDefinition Msg
   | SBPMsgSsrTileDefinitionDep MsgSsrTileDefinitionDep Msg
   | SBPMsgStartup MsgStartup Msg
   | SBPMsgStatusJournal MsgStatusJournal Msg
   | SBPMsgStatusReport MsgStatusReport Msg
   | SBPMsgStmFlashLockSector MsgStmFlashLockSector Msg
   | SBPMsgStmFlashUnlockSector MsgStmFlashUnlockSector Msg
   | SBPMsgStmUniqueIdReq MsgStmUniqueIdReq Msg
   | SBPMsgStmUniqueIdResp MsgStmUniqueIdResp Msg
   | SBPMsgSvAzEl MsgSvAzEl Msg
   | SBPMsgSvConfigurationGpsDep MsgSvConfigurationGpsDep Msg
   | SBPMsgThreadState MsgThreadState Msg
   | SBPMsgTrackingIq MsgTrackingIq Msg
   | SBPMsgTrackingIqDepA MsgTrackingIqDepA Msg
   | SBPMsgTrackingIqDepB MsgTrackingIqDepB Msg
   | SBPMsgTrackingState MsgTrackingState Msg
   | SBPMsgTrackingStateDepA MsgTrackingStateDepA Msg
   | SBPMsgTrackingStateDepB MsgTrackingStateDepB Msg
   | SBPMsgTrackingStateDetailedDep MsgTrackingStateDetailedDep Msg
   | SBPMsgTrackingStateDetailedDepA MsgTrackingStateDetailedDepA Msg
   | SBPMsgUartState MsgUartState Msg
   | SBPMsgUartStateDepa MsgUartStateDepa Msg
   | SBPMsgUserData MsgUserData Msg
   | SBPMsgUtcLeapSecond MsgUtcLeapSecond Msg
   | SBPMsgUtcTime MsgUtcTime Msg
   | SBPMsgUtcTimeGnss MsgUtcTimeGnss Msg
   | SBPMsgVelBody MsgVelBody Msg
   | SBPMsgVelCog MsgVelCog Msg
   | SBPMsgVelEcef MsgVelEcef Msg
   | SBPMsgVelEcefCov MsgVelEcefCov Msg
   | SBPMsgVelEcefCovGnss MsgVelEcefCovGnss Msg
   | SBPMsgVelEcefDepA MsgVelEcefDepA Msg
   | SBPMsgVelEcefGnss MsgVelEcefGnss Msg
   | SBPMsgVelNed MsgVelNed Msg
   | SBPMsgVelNedCov MsgVelNedCov Msg
   | SBPMsgVelNedCovGnss MsgVelNedCovGnss Msg
   | SBPMsgVelNedDepA MsgVelNedDepA Msg
   | SBPMsgVelNedGnss MsgVelNedGnss Msg
   | SBPMsgWheeltick MsgWheeltick Msg
   | SBPMsgBadCrc Msg
   | SBPMsgUnknown Msg
  deriving ( Int -> SBPMsg -> ShowS
[SBPMsg] -> ShowS
SBPMsg -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SBPMsg] -> ShowS
$cshowList :: [SBPMsg] -> ShowS
show :: SBPMsg -> String
$cshow :: SBPMsg -> String
showsPrec :: Int -> SBPMsg -> ShowS
$cshowsPrec :: Int -> SBPMsg -> ShowS
Show, ReadPrec [SBPMsg]
ReadPrec SBPMsg
Int -> ReadS SBPMsg
ReadS [SBPMsg]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SBPMsg]
$creadListPrec :: ReadPrec [SBPMsg]
readPrec :: ReadPrec SBPMsg
$creadPrec :: ReadPrec SBPMsg
readList :: ReadS [SBPMsg]
$creadList :: ReadS [SBPMsg]
readsPrec :: Int -> ReadS SBPMsg
$creadsPrec :: Int -> ReadS SBPMsg
Read, SBPMsg -> SBPMsg -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SBPMsg -> SBPMsg -> Bool
$c/= :: SBPMsg -> SBPMsg -> Bool
== :: SBPMsg -> SBPMsg -> Bool
$c== :: SBPMsg -> SBPMsg -> Bool
Eq )

$(makePrisms ''SBPMsg)

instance Binary SBPMsg where
  get :: Get SBPMsg
get = do
    Word8
preamble <- Get Word8
getWord8
    if Word8
preamble forall a. Eq a => a -> a -> Bool
/= Word8
msgSBPPreamble then forall t. Binary t => Get t
get else
      Msg -> SBPMsg
decoder forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get where
        decoder :: Msg -> SBPMsg
decoder m :: Msg
m@Msg {Word8
Word16
Bytes
_msgSBPCrc :: Msg -> Word16
_msgSBPPayload :: Msg -> Bytes
_msgSBPLen :: Msg -> Word8
_msgSBPSender :: Msg -> Word16
_msgSBPType :: Msg -> Word16
_msgSBPCrc :: Word16
_msgSBPPayload :: Bytes
_msgSBPLen :: Word8
_msgSBPSender :: Word16
_msgSBPType :: Word16
..}
          | Msg -> Word16
checkCrc Msg
m forall a. Eq a => a -> a -> Bool
/= Word16
_msgSBPCrc = Msg -> SBPMsg
SBPMsgBadCrc Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgAcqResult = MsgAcqResult -> Msg -> SBPMsg
SBPMsgAcqResult (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgAcqResultDepA = MsgAcqResultDepA -> Msg -> SBPMsg
SBPMsgAcqResultDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgAcqResultDepB = MsgAcqResultDepB -> Msg -> SBPMsg
SBPMsgAcqResultDepB (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgAcqResultDepC = MsgAcqResultDepC -> Msg -> SBPMsg
SBPMsgAcqResultDepC (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgAcqSvProfile = MsgAcqSvProfile -> Msg -> SBPMsg
SBPMsgAcqSvProfile (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgAcqSvProfileDep = MsgAcqSvProfileDep -> Msg -> SBPMsg
SBPMsgAcqSvProfileDep (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgAgeCorrections = MsgAgeCorrections -> Msg -> SBPMsg
SBPMsgAgeCorrections (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgAlmanac = MsgAlmanac -> Msg -> SBPMsg
SBPMsgAlmanac (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgAlmanacGlo = MsgAlmanacGlo -> Msg -> SBPMsg
SBPMsgAlmanacGlo (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgAlmanacGloDep = MsgAlmanacGloDep -> Msg -> SBPMsg
SBPMsgAlmanacGloDep (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgAlmanacGps = MsgAlmanacGps -> Msg -> SBPMsg
SBPMsgAlmanacGps (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgAlmanacGpsDep = MsgAlmanacGpsDep -> Msg -> SBPMsg
SBPMsgAlmanacGpsDep (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgAngularRate = MsgAngularRate -> Msg -> SBPMsg
SBPMsgAngularRate (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgBasePosEcef = MsgBasePosEcef -> Msg -> SBPMsg
SBPMsgBasePosEcef (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgBasePosLlh = MsgBasePosLlh -> Msg -> SBPMsg
SBPMsgBasePosLlh (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgBaselineEcef = MsgBaselineEcef -> Msg -> SBPMsg
SBPMsgBaselineEcef (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgBaselineEcefDepA = MsgBaselineEcefDepA -> Msg -> SBPMsg
SBPMsgBaselineEcefDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgBaselineHeading = MsgBaselineHeading -> Msg -> SBPMsg
SBPMsgBaselineHeading (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgBaselineHeadingDepA = MsgBaselineHeadingDepA -> Msg -> SBPMsg
SBPMsgBaselineHeadingDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgBaselineNed = MsgBaselineNed -> Msg -> SBPMsg
SBPMsgBaselineNed (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgBaselineNedDepA = MsgBaselineNedDepA -> Msg -> SBPMsg
SBPMsgBaselineNedDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgBootloaderHandshakeDepA = MsgBootloaderHandshakeDepA -> Msg -> SBPMsg
SBPMsgBootloaderHandshakeDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgBootloaderHandshakeReq = MsgBootloaderHandshakeReq -> Msg -> SBPMsg
SBPMsgBootloaderHandshakeReq (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgBootloaderHandshakeResp = MsgBootloaderHandshakeResp -> Msg -> SBPMsg
SBPMsgBootloaderHandshakeResp (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgBootloaderJumpToApp = MsgBootloaderJumpToApp -> Msg -> SBPMsg
SBPMsgBootloaderJumpToApp (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgCellModemStatus = MsgCellModemStatus -> Msg -> SBPMsg
SBPMsgCellModemStatus (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgCommandOutput = MsgCommandOutput -> Msg -> SBPMsg
SBPMsgCommandOutput (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgCommandReq = MsgCommandReq -> Msg -> SBPMsg
SBPMsgCommandReq (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgCommandResp = MsgCommandResp -> Msg -> SBPMsg
SBPMsgCommandResp (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgCsacTelemetry = MsgCsacTelemetry -> Msg -> SBPMsg
SBPMsgCsacTelemetry (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgCsacTelemetryLabels = MsgCsacTelemetryLabels -> Msg -> SBPMsg
SBPMsgCsacTelemetryLabels (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgCwResults = MsgCwResults -> Msg -> SBPMsg
SBPMsgCwResults (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgCwStart = MsgCwStart -> Msg -> SBPMsg
SBPMsgCwStart (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgDeviceMonitor = MsgDeviceMonitor -> Msg -> SBPMsg
SBPMsgDeviceMonitor (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgDgnssStatus = MsgDgnssStatus -> Msg -> SBPMsg
SBPMsgDgnssStatus (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgDops = MsgDops -> Msg -> SBPMsg
SBPMsgDops (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgDopsDepA = MsgDopsDepA -> Msg -> SBPMsg
SBPMsgDopsDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEd25519Certificate = MsgEd25519Certificate -> Msg -> SBPMsg
SBPMsgEd25519Certificate (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEd25519Signature = MsgEd25519Signature -> Msg -> SBPMsg
SBPMsgEd25519Signature (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisBds = MsgEphemerisBds -> Msg -> SBPMsg
SBPMsgEphemerisBds (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisDepA = MsgEphemerisDepA -> Msg -> SBPMsg
SBPMsgEphemerisDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisDepB = MsgEphemerisDepB -> Msg -> SBPMsg
SBPMsgEphemerisDepB (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisDepC = MsgEphemerisDepC -> Msg -> SBPMsg
SBPMsgEphemerisDepC (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisDepD = MsgEphemerisDepD -> Msg -> SBPMsg
SBPMsgEphemerisDepD (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGal = MsgEphemerisGal -> Msg -> SBPMsg
SBPMsgEphemerisGal (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGalDepA = MsgEphemerisGalDepA -> Msg -> SBPMsg
SBPMsgEphemerisGalDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGlo = MsgEphemerisGlo -> Msg -> SBPMsg
SBPMsgEphemerisGlo (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGloDepA = MsgEphemerisGloDepA -> Msg -> SBPMsg
SBPMsgEphemerisGloDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGloDepB = MsgEphemerisGloDepB -> Msg -> SBPMsg
SBPMsgEphemerisGloDepB (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGloDepC = MsgEphemerisGloDepC -> Msg -> SBPMsg
SBPMsgEphemerisGloDepC (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGloDepD = MsgEphemerisGloDepD -> Msg -> SBPMsg
SBPMsgEphemerisGloDepD (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGps = MsgEphemerisGps -> Msg -> SBPMsg
SBPMsgEphemerisGps (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGpsDepE = MsgEphemerisGpsDepE -> Msg -> SBPMsg
SBPMsgEphemerisGpsDepE (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGpsDepF = MsgEphemerisGpsDepF -> Msg -> SBPMsg
SBPMsgEphemerisGpsDepF (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisQzss = MsgEphemerisQzss -> Msg -> SBPMsg
SBPMsgEphemerisQzss (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisSbas = MsgEphemerisSbas -> Msg -> SBPMsg
SBPMsgEphemerisSbas (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisSbasDepA = MsgEphemerisSbasDepA -> Msg -> SBPMsg
SBPMsgEphemerisSbasDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisSbasDepB = MsgEphemerisSbasDepB -> Msg -> SBPMsg
SBPMsgEphemerisSbasDepB (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgExtEvent = MsgExtEvent -> Msg -> SBPMsg
SBPMsgExtEvent (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgFileioConfigReq = MsgFileioConfigReq -> Msg -> SBPMsg
SBPMsgFileioConfigReq (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgFileioConfigResp = MsgFileioConfigResp -> Msg -> SBPMsg
SBPMsgFileioConfigResp (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgFileioReadDirReq = MsgFileioReadDirReq -> Msg -> SBPMsg
SBPMsgFileioReadDirReq (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgFileioReadDirResp = MsgFileioReadDirResp -> Msg -> SBPMsg
SBPMsgFileioReadDirResp (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgFileioReadReq = MsgFileioReadReq -> Msg -> SBPMsg
SBPMsgFileioReadReq (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgFileioReadResp = MsgFileioReadResp -> Msg -> SBPMsg
SBPMsgFileioReadResp (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgFileioRemove = MsgFileioRemove -> Msg -> SBPMsg
SBPMsgFileioRemove (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgFileioWriteReq = MsgFileioWriteReq -> Msg -> SBPMsg
SBPMsgFileioWriteReq (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgFileioWriteResp = MsgFileioWriteResp -> Msg -> SBPMsg
SBPMsgFileioWriteResp (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgFlashDone = MsgFlashDone -> Msg -> SBPMsg
SBPMsgFlashDone (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgFlashErase = MsgFlashErase -> Msg -> SBPMsg
SBPMsgFlashErase (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgFlashProgram = MsgFlashProgram -> Msg -> SBPMsg
SBPMsgFlashProgram (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgFlashReadReq = MsgFlashReadReq -> Msg -> SBPMsg
SBPMsgFlashReadReq (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgFlashReadResp = MsgFlashReadResp -> Msg -> SBPMsg
SBPMsgFlashReadResp (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgFrontEndGain = MsgFrontEndGain -> Msg -> SBPMsg
SBPMsgFrontEndGain (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgFwd = MsgFwd -> Msg -> SBPMsg
SBPMsgFwd (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgGloBiases = MsgGloBiases -> Msg -> SBPMsg
SBPMsgGloBiases (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgGnssCapb = MsgGnssCapb -> Msg -> SBPMsg
SBPMsgGnssCapb (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgGnssTimeOffset = MsgGnssTimeOffset -> Msg -> SBPMsg
SBPMsgGnssTimeOffset (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgGpsTime = MsgGpsTime -> Msg -> SBPMsg
SBPMsgGpsTime (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgGpsTimeDepA = MsgGpsTimeDepA -> Msg -> SBPMsg
SBPMsgGpsTimeDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgGpsTimeGnss = MsgGpsTimeGnss -> Msg -> SBPMsg
SBPMsgGpsTimeGnss (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgGroupDelay = MsgGroupDelay -> Msg -> SBPMsg
SBPMsgGroupDelay (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgGroupDelayDepA = MsgGroupDelayDepA -> Msg -> SBPMsg
SBPMsgGroupDelayDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgGroupDelayDepB = MsgGroupDelayDepB -> Msg -> SBPMsg
SBPMsgGroupDelayDepB (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgGroupMeta = MsgGroupMeta -> Msg -> SBPMsg
SBPMsgGroupMeta (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgHeartbeat = MsgHeartbeat -> Msg -> SBPMsg
SBPMsgHeartbeat (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgIarState = MsgIarState -> Msg -> SBPMsg
SBPMsgIarState (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgImuAux = MsgImuAux -> Msg -> SBPMsg
SBPMsgImuAux (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgImuRaw = MsgImuRaw -> Msg -> SBPMsg
SBPMsgImuRaw (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgInitBaseDep = MsgInitBaseDep -> Msg -> SBPMsg
SBPMsgInitBaseDep (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgInsStatus = MsgInsStatus -> Msg -> SBPMsg
SBPMsgInsStatus (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgInsUpdates = MsgInsUpdates -> Msg -> SBPMsg
SBPMsgInsUpdates (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgIono = MsgIono -> Msg -> SBPMsg
SBPMsgIono (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxCpuState = MsgLinuxCpuState -> Msg -> SBPMsg
SBPMsgLinuxCpuState (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxCpuStateDepA = MsgLinuxCpuStateDepA -> Msg -> SBPMsg
SBPMsgLinuxCpuStateDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxMemState = MsgLinuxMemState -> Msg -> SBPMsg
SBPMsgLinuxMemState (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxMemStateDepA = MsgLinuxMemStateDepA -> Msg -> SBPMsg
SBPMsgLinuxMemStateDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxProcessFdCount = MsgLinuxProcessFdCount -> Msg -> SBPMsg
SBPMsgLinuxProcessFdCount (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxProcessFdSummary = MsgLinuxProcessFdSummary -> Msg -> SBPMsg
SBPMsgLinuxProcessFdSummary (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxProcessSocketCounts = MsgLinuxProcessSocketCounts -> Msg -> SBPMsg
SBPMsgLinuxProcessSocketCounts (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxProcessSocketQueues = MsgLinuxProcessSocketQueues -> Msg -> SBPMsg
SBPMsgLinuxProcessSocketQueues (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxSocketUsage = MsgLinuxSocketUsage -> Msg -> SBPMsg
SBPMsgLinuxSocketUsage (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxSysState = MsgLinuxSysState -> Msg -> SBPMsg
SBPMsgLinuxSysState (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxSysStateDepA = MsgLinuxSysStateDepA -> Msg -> SBPMsg
SBPMsgLinuxSysStateDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgLog = MsgLog -> Msg -> SBPMsg
SBPMsgLog (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgM25FlashWriteStatus = MsgM25FlashWriteStatus -> Msg -> SBPMsg
SBPMsgM25FlashWriteStatus (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgMagRaw = MsgMagRaw -> Msg -> SBPMsg
SBPMsgMagRaw (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgMaskSatellite = MsgMaskSatellite -> Msg -> SBPMsg
SBPMsgMaskSatellite (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgMaskSatelliteDep = MsgMaskSatelliteDep -> Msg -> SBPMsg
SBPMsgMaskSatelliteDep (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgMeasurementState = MsgMeasurementState -> Msg -> SBPMsg
SBPMsgMeasurementState (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgNapDeviceDnaReq = MsgNapDeviceDnaReq -> Msg -> SBPMsg
SBPMsgNapDeviceDnaReq (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgNapDeviceDnaResp = MsgNapDeviceDnaResp -> Msg -> SBPMsg
SBPMsgNapDeviceDnaResp (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgNdbEvent = MsgNdbEvent -> Msg -> SBPMsg
SBPMsgNdbEvent (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgNetworkBandwidthUsage = MsgNetworkBandwidthUsage -> Msg -> SBPMsg
SBPMsgNetworkBandwidthUsage (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgNetworkStateReq = MsgNetworkStateReq -> Msg -> SBPMsg
SBPMsgNetworkStateReq (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgNetworkStateResp = MsgNetworkStateResp -> Msg -> SBPMsg
SBPMsgNetworkStateResp (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgObs = MsgObs -> Msg -> SBPMsg
SBPMsgObs (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgObsDepA = MsgObsDepA -> Msg -> SBPMsg
SBPMsgObsDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgObsDepB = MsgObsDepB -> Msg -> SBPMsg
SBPMsgObsDepB (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgObsDepC = MsgObsDepC -> Msg -> SBPMsg
SBPMsgObsDepC (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgOdometry = MsgOdometry -> Msg -> SBPMsg
SBPMsgOdometry (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgOrientEuler = MsgOrientEuler -> Msg -> SBPMsg
SBPMsgOrientEuler (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgOrientQuat = MsgOrientQuat -> Msg -> SBPMsg
SBPMsgOrientQuat (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgOsr = MsgOsr -> Msg -> SBPMsg
SBPMsgOsr (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgPosEcef = MsgPosEcef -> Msg -> SBPMsg
SBPMsgPosEcef (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgPosEcefCov = MsgPosEcefCov -> Msg -> SBPMsg
SBPMsgPosEcefCov (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgPosEcefCovGnss = MsgPosEcefCovGnss -> Msg -> SBPMsg
SBPMsgPosEcefCovGnss (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgPosEcefDepA = MsgPosEcefDepA -> Msg -> SBPMsg
SBPMsgPosEcefDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgPosEcefGnss = MsgPosEcefGnss -> Msg -> SBPMsg
SBPMsgPosEcefGnss (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgPosLlh = MsgPosLlh -> Msg -> SBPMsg
SBPMsgPosLlh (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgPosLlhAcc = MsgPosLlhAcc -> Msg -> SBPMsg
SBPMsgPosLlhAcc (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgPosLlhCov = MsgPosLlhCov -> Msg -> SBPMsg
SBPMsgPosLlhCov (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgPosLlhCovGnss = MsgPosLlhCovGnss -> Msg -> SBPMsg
SBPMsgPosLlhCovGnss (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgPosLlhDepA = MsgPosLlhDepA -> Msg -> SBPMsg
SBPMsgPosLlhDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgPosLlhGnss = MsgPosLlhGnss -> Msg -> SBPMsg
SBPMsgPosLlhGnss (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgPpsTime = MsgPpsTime -> Msg -> SBPMsg
SBPMsgPpsTime (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgPrintDep = MsgPrintDep -> Msg -> SBPMsg
SBPMsgPrintDep (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgProtectionLevel = MsgProtectionLevel -> Msg -> SBPMsg
SBPMsgProtectionLevel (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgProtectionLevelDepA = MsgProtectionLevelDepA -> Msg -> SBPMsg
SBPMsgProtectionLevelDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgReferenceFrameParam = MsgReferenceFrameParam -> Msg -> SBPMsg
SBPMsgReferenceFrameParam (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgReset = MsgReset -> Msg -> SBPMsg
SBPMsgReset (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgResetDep = MsgResetDep -> Msg -> SBPMsg
SBPMsgResetDep (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgResetFilters = MsgResetFilters -> Msg -> SBPMsg
SBPMsgResetFilters (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSbasRaw = MsgSbasRaw -> Msg -> SBPMsg
SBPMsgSbasRaw (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSensorAidEvent = MsgSensorAidEvent -> Msg -> SBPMsg
SBPMsgSensorAidEvent (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSetTime = MsgSetTime -> Msg -> SBPMsg
SBPMsgSetTime (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsReadByIndexDone = MsgSettingsReadByIndexDone -> Msg -> SBPMsg
SBPMsgSettingsReadByIndexDone (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsReadByIndexReq = MsgSettingsReadByIndexReq -> Msg -> SBPMsg
SBPMsgSettingsReadByIndexReq (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsReadByIndexResp = MsgSettingsReadByIndexResp -> Msg -> SBPMsg
SBPMsgSettingsReadByIndexResp (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsReadReq = MsgSettingsReadReq -> Msg -> SBPMsg
SBPMsgSettingsReadReq (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsReadResp = MsgSettingsReadResp -> Msg -> SBPMsg
SBPMsgSettingsReadResp (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsRegister = MsgSettingsRegister -> Msg -> SBPMsg
SBPMsgSettingsRegister (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsRegisterResp = MsgSettingsRegisterResp -> Msg -> SBPMsg
SBPMsgSettingsRegisterResp (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsSave = MsgSettingsSave -> Msg -> SBPMsg
SBPMsgSettingsSave (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsWrite = MsgSettingsWrite -> Msg -> SBPMsg
SBPMsgSettingsWrite (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsWriteResp = MsgSettingsWriteResp -> Msg -> SBPMsg
SBPMsgSettingsWriteResp (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSolnMeta = MsgSolnMeta -> Msg -> SBPMsg
SBPMsgSolnMeta (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSolnMetaDepA = MsgSolnMetaDepA -> Msg -> SBPMsg
SBPMsgSolnMetaDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSpecan = MsgSpecan -> Msg -> SBPMsg
SBPMsgSpecan (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSpecanDep = MsgSpecanDep -> Msg -> SBPMsg
SBPMsgSpecanDep (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrCodeBiases = MsgSsrCodeBiases -> Msg -> SBPMsg
SBPMsgSsrCodeBiases (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrCodePhaseBiasesBounds = MsgSsrCodePhaseBiasesBounds -> Msg -> SBPMsg
SBPMsgSsrCodePhaseBiasesBounds (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrFlagHighLevel = MsgSsrFlagHighLevel -> Msg -> SBPMsg
SBPMsgSsrFlagHighLevel (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrFlagIonoGridPointSatLos = MsgSsrFlagIonoGridPointSatLos -> Msg -> SBPMsg
SBPMsgSsrFlagIonoGridPointSatLos (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrFlagIonoGridPoints = MsgSsrFlagIonoGridPoints -> Msg -> SBPMsg
SBPMsgSsrFlagIonoGridPoints (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrFlagIonoTileSatLos = MsgSsrFlagIonoTileSatLos -> Msg -> SBPMsg
SBPMsgSsrFlagIonoTileSatLos (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrFlagSatellites = MsgSsrFlagSatellites -> Msg -> SBPMsg
SBPMsgSsrFlagSatellites (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrFlagTropoGridPoints = MsgSsrFlagTropoGridPoints -> Msg -> SBPMsg
SBPMsgSsrFlagTropoGridPoints (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrGridDefinitionDepA = MsgSsrGridDefinitionDepA -> Msg -> SBPMsg
SBPMsgSsrGridDefinitionDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrGriddedCorrection = MsgSsrGriddedCorrection -> Msg -> SBPMsg
SBPMsgSsrGriddedCorrection (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrGriddedCorrectionBounds = MsgSsrGriddedCorrectionBounds -> Msg -> SBPMsg
SBPMsgSsrGriddedCorrectionBounds (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrGriddedCorrectionDepA = MsgSsrGriddedCorrectionDepA -> Msg -> SBPMsg
SBPMsgSsrGriddedCorrectionDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrGriddedCorrectionNoStdDepA = MsgSsrGriddedCorrectionNoStdDepA -> Msg -> SBPMsg
SBPMsgSsrGriddedCorrectionNoStdDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrOrbitClock = MsgSsrOrbitClock -> Msg -> SBPMsg
SBPMsgSsrOrbitClock (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrOrbitClockBounds = MsgSsrOrbitClockBounds -> Msg -> SBPMsg
SBPMsgSsrOrbitClockBounds (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrOrbitClockBoundsDegradation = MsgSsrOrbitClockBoundsDegradation -> Msg -> SBPMsg
SBPMsgSsrOrbitClockBoundsDegradation (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrOrbitClockDepA = MsgSsrOrbitClockDepA -> Msg -> SBPMsg
SBPMsgSsrOrbitClockDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrPhaseBiases = MsgSsrPhaseBiases -> Msg -> SBPMsg
SBPMsgSsrPhaseBiases (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrSatelliteApc = MsgSsrSatelliteApc -> Msg -> SBPMsg
SBPMsgSsrSatelliteApc (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrStecCorrection = MsgSsrStecCorrection -> Msg -> SBPMsg
SBPMsgSsrStecCorrection (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrStecCorrectionDep = MsgSsrStecCorrectionDep -> Msg -> SBPMsg
SBPMsgSsrStecCorrectionDep (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrStecCorrectionDepA = MsgSsrStecCorrectionDepA -> Msg -> SBPMsg
SBPMsgSsrStecCorrectionDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrTileDefinition = MsgSsrTileDefinition -> Msg -> SBPMsg
SBPMsgSsrTileDefinition (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrTileDefinitionDep = MsgSsrTileDefinitionDep -> Msg -> SBPMsg
SBPMsgSsrTileDefinitionDep (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgStartup = MsgStartup -> Msg -> SBPMsg
SBPMsgStartup (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgStatusJournal = MsgStatusJournal -> Msg -> SBPMsg
SBPMsgStatusJournal (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgStatusReport = MsgStatusReport -> Msg -> SBPMsg
SBPMsgStatusReport (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgStmFlashLockSector = MsgStmFlashLockSector -> Msg -> SBPMsg
SBPMsgStmFlashLockSector (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgStmFlashUnlockSector = MsgStmFlashUnlockSector -> Msg -> SBPMsg
SBPMsgStmFlashUnlockSector (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgStmUniqueIdReq = MsgStmUniqueIdReq -> Msg -> SBPMsg
SBPMsgStmUniqueIdReq (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgStmUniqueIdResp = MsgStmUniqueIdResp -> Msg -> SBPMsg
SBPMsgStmUniqueIdResp (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSvAzEl = MsgSvAzEl -> Msg -> SBPMsg
SBPMsgSvAzEl (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgSvConfigurationGpsDep = MsgSvConfigurationGpsDep -> Msg -> SBPMsg
SBPMsgSvConfigurationGpsDep (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgThreadState = MsgThreadState -> Msg -> SBPMsg
SBPMsgThreadState (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgTrackingIq = MsgTrackingIq -> Msg -> SBPMsg
SBPMsgTrackingIq (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgTrackingIqDepA = MsgTrackingIqDepA -> Msg -> SBPMsg
SBPMsgTrackingIqDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgTrackingIqDepB = MsgTrackingIqDepB -> Msg -> SBPMsg
SBPMsgTrackingIqDepB (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgTrackingState = MsgTrackingState -> Msg -> SBPMsg
SBPMsgTrackingState (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgTrackingStateDepA = MsgTrackingStateDepA -> Msg -> SBPMsg
SBPMsgTrackingStateDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgTrackingStateDepB = MsgTrackingStateDepB -> Msg -> SBPMsg
SBPMsgTrackingStateDepB (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgTrackingStateDetailedDep = MsgTrackingStateDetailedDep -> Msg -> SBPMsg
SBPMsgTrackingStateDetailedDep (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgTrackingStateDetailedDepA = MsgTrackingStateDetailedDepA -> Msg -> SBPMsg
SBPMsgTrackingStateDetailedDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgUartState = MsgUartState -> Msg -> SBPMsg
SBPMsgUartState (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgUartStateDepa = MsgUartStateDepa -> Msg -> SBPMsg
SBPMsgUartStateDepa (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgUserData = MsgUserData -> Msg -> SBPMsg
SBPMsgUserData (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgUtcLeapSecond = MsgUtcLeapSecond -> Msg -> SBPMsg
SBPMsgUtcLeapSecond (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgUtcTime = MsgUtcTime -> Msg -> SBPMsg
SBPMsgUtcTime (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgUtcTimeGnss = MsgUtcTimeGnss -> Msg -> SBPMsg
SBPMsgUtcTimeGnss (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgVelBody = MsgVelBody -> Msg -> SBPMsg
SBPMsgVelBody (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgVelCog = MsgVelCog -> Msg -> SBPMsg
SBPMsgVelCog (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgVelEcef = MsgVelEcef -> Msg -> SBPMsg
SBPMsgVelEcef (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgVelEcefCov = MsgVelEcefCov -> Msg -> SBPMsg
SBPMsgVelEcefCov (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgVelEcefCovGnss = MsgVelEcefCovGnss -> Msg -> SBPMsg
SBPMsgVelEcefCovGnss (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgVelEcefDepA = MsgVelEcefDepA -> Msg -> SBPMsg
SBPMsgVelEcefDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgVelEcefGnss = MsgVelEcefGnss -> Msg -> SBPMsg
SBPMsgVelEcefGnss (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgVelNed = MsgVelNed -> Msg -> SBPMsg
SBPMsgVelNed (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgVelNedCov = MsgVelNedCov -> Msg -> SBPMsg
SBPMsgVelNedCov (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgVelNedCovGnss = MsgVelNedCovGnss -> Msg -> SBPMsg
SBPMsgVelNedCovGnss (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgVelNedDepA = MsgVelNedDepA -> Msg -> SBPMsg
SBPMsgVelNedDepA (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgVelNedGnss = MsgVelNedGnss -> Msg -> SBPMsg
SBPMsgVelNedGnss (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Word16
_msgSBPType forall a. Eq a => a -> a -> Bool
== Word16
msgWheeltick = MsgWheeltick -> Msg -> SBPMsg
SBPMsgWheeltick (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
_msgSBPPayload))) Msg
m
          | Bool
otherwise = Msg -> SBPMsg
SBPMsgUnknown Msg
m

  put :: SBPMsg -> Put
put SBPMsg
sm = do
    Word8 -> Put
putWord8 Word8
msgSBPPreamble
    SBPMsg -> Put
encoder SBPMsg
sm where
      encoder :: SBPMsg -> Put
encoder (SBPMsgAcqResult MsgAcqResult
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgAcqResultDepA MsgAcqResultDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgAcqResultDepB MsgAcqResultDepB
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgAcqResultDepC MsgAcqResultDepC
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgAcqSvProfile MsgAcqSvProfile
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgAcqSvProfileDep MsgAcqSvProfileDep
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgAgeCorrections MsgAgeCorrections
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgAlmanac MsgAlmanac
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgAlmanacGlo MsgAlmanacGlo
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgAlmanacGloDep MsgAlmanacGloDep
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgAlmanacGps MsgAlmanacGps
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgAlmanacGpsDep MsgAlmanacGpsDep
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgAngularRate MsgAngularRate
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgBasePosEcef MsgBasePosEcef
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgBasePosLlh MsgBasePosLlh
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgBaselineEcef MsgBaselineEcef
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgBaselineEcefDepA MsgBaselineEcefDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgBaselineHeading MsgBaselineHeading
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgBaselineHeadingDepA MsgBaselineHeadingDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgBaselineNed MsgBaselineNed
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgBaselineNedDepA MsgBaselineNedDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgBootloaderHandshakeDepA MsgBootloaderHandshakeDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgBootloaderHandshakeReq MsgBootloaderHandshakeReq
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgBootloaderHandshakeResp MsgBootloaderHandshakeResp
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgBootloaderJumpToApp MsgBootloaderJumpToApp
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgCellModemStatus MsgCellModemStatus
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgCommandOutput MsgCommandOutput
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgCommandReq MsgCommandReq
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgCommandResp MsgCommandResp
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgCsacTelemetry MsgCsacTelemetry
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgCsacTelemetryLabels MsgCsacTelemetryLabels
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgCwResults MsgCwResults
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgCwStart MsgCwStart
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgDeviceMonitor MsgDeviceMonitor
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgDgnssStatus MsgDgnssStatus
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgDops MsgDops
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgDopsDepA MsgDopsDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEd25519Certificate MsgEd25519Certificate
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEd25519Signature MsgEd25519Signature
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisBds MsgEphemerisBds
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisDepA MsgEphemerisDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisDepB MsgEphemerisDepB
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisDepC MsgEphemerisDepC
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisDepD MsgEphemerisDepD
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisGal MsgEphemerisGal
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisGalDepA MsgEphemerisGalDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisGlo MsgEphemerisGlo
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisGloDepA MsgEphemerisGloDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisGloDepB MsgEphemerisGloDepB
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisGloDepC MsgEphemerisGloDepC
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisGloDepD MsgEphemerisGloDepD
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisGps MsgEphemerisGps
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisGpsDepE MsgEphemerisGpsDepE
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisGpsDepF MsgEphemerisGpsDepF
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisQzss MsgEphemerisQzss
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisSbas MsgEphemerisSbas
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisSbasDepA MsgEphemerisSbasDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgEphemerisSbasDepB MsgEphemerisSbasDepB
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgExtEvent MsgExtEvent
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgFileioConfigReq MsgFileioConfigReq
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgFileioConfigResp MsgFileioConfigResp
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgFileioReadDirReq MsgFileioReadDirReq
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgFileioReadDirResp MsgFileioReadDirResp
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgFileioReadReq MsgFileioReadReq
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgFileioReadResp MsgFileioReadResp
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgFileioRemove MsgFileioRemove
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgFileioWriteReq MsgFileioWriteReq
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgFileioWriteResp MsgFileioWriteResp
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgFlashDone MsgFlashDone
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgFlashErase MsgFlashErase
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgFlashProgram MsgFlashProgram
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgFlashReadReq MsgFlashReadReq
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgFlashReadResp MsgFlashReadResp
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgFrontEndGain MsgFrontEndGain
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgFwd MsgFwd
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgGloBiases MsgGloBiases
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgGnssCapb MsgGnssCapb
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgGnssTimeOffset MsgGnssTimeOffset
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgGpsTime MsgGpsTime
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgGpsTimeDepA MsgGpsTimeDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgGpsTimeGnss MsgGpsTimeGnss
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgGroupDelay MsgGroupDelay
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgGroupDelayDepA MsgGroupDelayDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgGroupDelayDepB MsgGroupDelayDepB
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgGroupMeta MsgGroupMeta
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgHeartbeat MsgHeartbeat
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgIarState MsgIarState
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgImuAux MsgImuAux
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgImuRaw MsgImuRaw
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgInitBaseDep MsgInitBaseDep
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgInsStatus MsgInsStatus
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgInsUpdates MsgInsUpdates
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgIono MsgIono
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgLinuxCpuState MsgLinuxCpuState
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgLinuxCpuStateDepA MsgLinuxCpuStateDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgLinuxMemState MsgLinuxMemState
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgLinuxMemStateDepA MsgLinuxMemStateDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgLinuxProcessFdCount MsgLinuxProcessFdCount
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgLinuxProcessFdSummary MsgLinuxProcessFdSummary
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgLinuxProcessSocketCounts MsgLinuxProcessSocketCounts
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgLinuxProcessSocketQueues MsgLinuxProcessSocketQueues
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgLinuxSocketUsage MsgLinuxSocketUsage
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgLinuxSysState MsgLinuxSysState
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgLinuxSysStateDepA MsgLinuxSysStateDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgLog MsgLog
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgM25FlashWriteStatus MsgM25FlashWriteStatus
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgMagRaw MsgMagRaw
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgMaskSatellite MsgMaskSatellite
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgMaskSatelliteDep MsgMaskSatelliteDep
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgMeasurementState MsgMeasurementState
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgNapDeviceDnaReq MsgNapDeviceDnaReq
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgNapDeviceDnaResp MsgNapDeviceDnaResp
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgNdbEvent MsgNdbEvent
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgNetworkBandwidthUsage MsgNetworkBandwidthUsage
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgNetworkStateReq MsgNetworkStateReq
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgNetworkStateResp MsgNetworkStateResp
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgObs MsgObs
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgObsDepA MsgObsDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgObsDepB MsgObsDepB
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgObsDepC MsgObsDepC
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgOdometry MsgOdometry
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgOrientEuler MsgOrientEuler
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgOrientQuat MsgOrientQuat
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgOsr MsgOsr
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgPosEcef MsgPosEcef
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgPosEcefCov MsgPosEcefCov
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgPosEcefCovGnss MsgPosEcefCovGnss
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgPosEcefDepA MsgPosEcefDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgPosEcefGnss MsgPosEcefGnss
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgPosLlh MsgPosLlh
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgPosLlhAcc MsgPosLlhAcc
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgPosLlhCov MsgPosLlhCov
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgPosLlhCovGnss MsgPosLlhCovGnss
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgPosLlhDepA MsgPosLlhDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgPosLlhGnss MsgPosLlhGnss
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgPpsTime MsgPpsTime
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgPrintDep MsgPrintDep
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgProtectionLevel MsgProtectionLevel
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgProtectionLevelDepA MsgProtectionLevelDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgReferenceFrameParam MsgReferenceFrameParam
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgReset MsgReset
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgResetDep MsgResetDep
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgResetFilters MsgResetFilters
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSbasRaw MsgSbasRaw
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSensorAidEvent MsgSensorAidEvent
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSetTime MsgSetTime
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSettingsReadByIndexDone MsgSettingsReadByIndexDone
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSettingsReadByIndexReq MsgSettingsReadByIndexReq
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSettingsReadByIndexResp MsgSettingsReadByIndexResp
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSettingsReadReq MsgSettingsReadReq
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSettingsReadResp MsgSettingsReadResp
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSettingsRegister MsgSettingsRegister
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSettingsRegisterResp MsgSettingsRegisterResp
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSettingsSave MsgSettingsSave
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSettingsWrite MsgSettingsWrite
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSettingsWriteResp MsgSettingsWriteResp
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSolnMeta MsgSolnMeta
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSolnMetaDepA MsgSolnMetaDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSpecan MsgSpecan
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSpecanDep MsgSpecanDep
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrCodeBiases MsgSsrCodeBiases
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrCodePhaseBiasesBounds MsgSsrCodePhaseBiasesBounds
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrFlagHighLevel MsgSsrFlagHighLevel
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrFlagIonoGridPointSatLos MsgSsrFlagIonoGridPointSatLos
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrFlagIonoGridPoints MsgSsrFlagIonoGridPoints
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrFlagIonoTileSatLos MsgSsrFlagIonoTileSatLos
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrFlagSatellites MsgSsrFlagSatellites
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrFlagTropoGridPoints MsgSsrFlagTropoGridPoints
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrGridDefinitionDepA MsgSsrGridDefinitionDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrGriddedCorrection MsgSsrGriddedCorrection
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrGriddedCorrectionBounds MsgSsrGriddedCorrectionBounds
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrGriddedCorrectionDepA MsgSsrGriddedCorrectionDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrGriddedCorrectionNoStdDepA MsgSsrGriddedCorrectionNoStdDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrOrbitClock MsgSsrOrbitClock
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrOrbitClockBounds MsgSsrOrbitClockBounds
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrOrbitClockBoundsDegradation MsgSsrOrbitClockBoundsDegradation
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrOrbitClockDepA MsgSsrOrbitClockDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrPhaseBiases MsgSsrPhaseBiases
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrSatelliteApc MsgSsrSatelliteApc
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrStecCorrection MsgSsrStecCorrection
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrStecCorrectionDep MsgSsrStecCorrectionDep
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrStecCorrectionDepA MsgSsrStecCorrectionDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrTileDefinition MsgSsrTileDefinition
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSsrTileDefinitionDep MsgSsrTileDefinitionDep
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgStartup MsgStartup
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgStatusJournal MsgStatusJournal
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgStatusReport MsgStatusReport
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgStmFlashLockSector MsgStmFlashLockSector
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgStmFlashUnlockSector MsgStmFlashUnlockSector
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgStmUniqueIdReq MsgStmUniqueIdReq
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgStmUniqueIdResp MsgStmUniqueIdResp
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSvAzEl MsgSvAzEl
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgSvConfigurationGpsDep MsgSvConfigurationGpsDep
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgThreadState MsgThreadState
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgTrackingIq MsgTrackingIq
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgTrackingIqDepA MsgTrackingIqDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgTrackingIqDepB MsgTrackingIqDepB
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgTrackingState MsgTrackingState
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgTrackingStateDepA MsgTrackingStateDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgTrackingStateDepB MsgTrackingStateDepB
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgTrackingStateDetailedDep MsgTrackingStateDetailedDep
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgTrackingStateDetailedDepA MsgTrackingStateDetailedDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgUartState MsgUartState
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgUartStateDepa MsgUartStateDepa
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgUserData MsgUserData
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgUtcLeapSecond MsgUtcLeapSecond
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgUtcTime MsgUtcTime
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgUtcTimeGnss MsgUtcTimeGnss
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgVelBody MsgVelBody
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgVelCog MsgVelCog
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgVelEcef MsgVelEcef
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgVelEcefCov MsgVelEcefCov
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgVelEcefCovGnss MsgVelEcefCovGnss
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgVelEcefDepA MsgVelEcefDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgVelEcefGnss MsgVelEcefGnss
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgVelNed MsgVelNed
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgVelNedCov MsgVelNedCov
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgVelNedCovGnss MsgVelNedCovGnss
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgVelNedDepA MsgVelNedDepA
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgVelNedGnss MsgVelNedGnss
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgWheeltick MsgWheeltick
_ Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgUnknown Msg
m) = forall t. Binary t => t -> Put
put Msg
m
      encoder (SBPMsgBadCrc Msg
m) = forall t. Binary t => t -> Put
put Msg
m

instance FromJSON SBPMsg where
  parseJSON :: Value -> Parser SBPMsg
parseJSON obj :: Value
obj@(Object KeyMap Value
o) = do
    Word16
msgType <- KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser a
.: Key
"msg_type"
    Bytes
payload <- KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser a
.: Key
"payload"
    Word16 -> Bytes -> Parser SBPMsg
decoder Word16
msgType Bytes
payload where
      decoder :: Word16 -> Bytes -> Parser SBPMsg
decoder Word16
msgType Bytes
payload
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgAcqResult = MsgAcqResult -> Msg -> SBPMsg
SBPMsgAcqResult forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgAcqResultDepA = MsgAcqResultDepA -> Msg -> SBPMsg
SBPMsgAcqResultDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgAcqResultDepB = MsgAcqResultDepB -> Msg -> SBPMsg
SBPMsgAcqResultDepB forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgAcqResultDepC = MsgAcqResultDepC -> Msg -> SBPMsg
SBPMsgAcqResultDepC forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgAcqSvProfile = MsgAcqSvProfile -> Msg -> SBPMsg
SBPMsgAcqSvProfile forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgAcqSvProfileDep = MsgAcqSvProfileDep -> Msg -> SBPMsg
SBPMsgAcqSvProfileDep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgAgeCorrections = MsgAgeCorrections -> Msg -> SBPMsg
SBPMsgAgeCorrections forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgAlmanac = MsgAlmanac -> Msg -> SBPMsg
SBPMsgAlmanac forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgAlmanacGlo = MsgAlmanacGlo -> Msg -> SBPMsg
SBPMsgAlmanacGlo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgAlmanacGloDep = MsgAlmanacGloDep -> Msg -> SBPMsg
SBPMsgAlmanacGloDep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgAlmanacGps = MsgAlmanacGps -> Msg -> SBPMsg
SBPMsgAlmanacGps forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgAlmanacGpsDep = MsgAlmanacGpsDep -> Msg -> SBPMsg
SBPMsgAlmanacGpsDep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgAngularRate = MsgAngularRate -> Msg -> SBPMsg
SBPMsgAngularRate forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgBasePosEcef = MsgBasePosEcef -> Msg -> SBPMsg
SBPMsgBasePosEcef forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgBasePosLlh = MsgBasePosLlh -> Msg -> SBPMsg
SBPMsgBasePosLlh forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgBaselineEcef = MsgBaselineEcef -> Msg -> SBPMsg
SBPMsgBaselineEcef forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgBaselineEcefDepA = MsgBaselineEcefDepA -> Msg -> SBPMsg
SBPMsgBaselineEcefDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgBaselineHeading = MsgBaselineHeading -> Msg -> SBPMsg
SBPMsgBaselineHeading forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgBaselineHeadingDepA = MsgBaselineHeadingDepA -> Msg -> SBPMsg
SBPMsgBaselineHeadingDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgBaselineNed = MsgBaselineNed -> Msg -> SBPMsg
SBPMsgBaselineNed forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgBaselineNedDepA = MsgBaselineNedDepA -> Msg -> SBPMsg
SBPMsgBaselineNedDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgBootloaderHandshakeDepA = MsgBootloaderHandshakeDepA -> Msg -> SBPMsg
SBPMsgBootloaderHandshakeDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgBootloaderHandshakeReq = MsgBootloaderHandshakeReq -> Msg -> SBPMsg
SBPMsgBootloaderHandshakeReq forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgBootloaderHandshakeResp = MsgBootloaderHandshakeResp -> Msg -> SBPMsg
SBPMsgBootloaderHandshakeResp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgBootloaderJumpToApp = MsgBootloaderJumpToApp -> Msg -> SBPMsg
SBPMsgBootloaderJumpToApp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgCellModemStatus = MsgCellModemStatus -> Msg -> SBPMsg
SBPMsgCellModemStatus forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgCommandOutput = MsgCommandOutput -> Msg -> SBPMsg
SBPMsgCommandOutput forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgCommandReq = MsgCommandReq -> Msg -> SBPMsg
SBPMsgCommandReq forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgCommandResp = MsgCommandResp -> Msg -> SBPMsg
SBPMsgCommandResp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgCsacTelemetry = MsgCsacTelemetry -> Msg -> SBPMsg
SBPMsgCsacTelemetry forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgCsacTelemetryLabels = MsgCsacTelemetryLabels -> Msg -> SBPMsg
SBPMsgCsacTelemetryLabels forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgCwResults = MsgCwResults -> Msg -> SBPMsg
SBPMsgCwResults forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgCwStart = MsgCwStart -> Msg -> SBPMsg
SBPMsgCwStart forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgDeviceMonitor = MsgDeviceMonitor -> Msg -> SBPMsg
SBPMsgDeviceMonitor forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgDgnssStatus = MsgDgnssStatus -> Msg -> SBPMsg
SBPMsgDgnssStatus forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgDops = MsgDops -> Msg -> SBPMsg
SBPMsgDops forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgDopsDepA = MsgDopsDepA -> Msg -> SBPMsg
SBPMsgDopsDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEd25519Certificate = MsgEd25519Certificate -> Msg -> SBPMsg
SBPMsgEd25519Certificate forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEd25519Signature = MsgEd25519Signature -> Msg -> SBPMsg
SBPMsgEd25519Signature forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisBds = MsgEphemerisBds -> Msg -> SBPMsg
SBPMsgEphemerisBds forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisDepA = MsgEphemerisDepA -> Msg -> SBPMsg
SBPMsgEphemerisDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisDepB = MsgEphemerisDepB -> Msg -> SBPMsg
SBPMsgEphemerisDepB forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisDepC = MsgEphemerisDepC -> Msg -> SBPMsg
SBPMsgEphemerisDepC forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisDepD = MsgEphemerisDepD -> Msg -> SBPMsg
SBPMsgEphemerisDepD forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGal = MsgEphemerisGal -> Msg -> SBPMsg
SBPMsgEphemerisGal forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGalDepA = MsgEphemerisGalDepA -> Msg -> SBPMsg
SBPMsgEphemerisGalDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGlo = MsgEphemerisGlo -> Msg -> SBPMsg
SBPMsgEphemerisGlo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGloDepA = MsgEphemerisGloDepA -> Msg -> SBPMsg
SBPMsgEphemerisGloDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGloDepB = MsgEphemerisGloDepB -> Msg -> SBPMsg
SBPMsgEphemerisGloDepB forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGloDepC = MsgEphemerisGloDepC -> Msg -> SBPMsg
SBPMsgEphemerisGloDepC forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGloDepD = MsgEphemerisGloDepD -> Msg -> SBPMsg
SBPMsgEphemerisGloDepD forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGps = MsgEphemerisGps -> Msg -> SBPMsg
SBPMsgEphemerisGps forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGpsDepE = MsgEphemerisGpsDepE -> Msg -> SBPMsg
SBPMsgEphemerisGpsDepE forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisGpsDepF = MsgEphemerisGpsDepF -> Msg -> SBPMsg
SBPMsgEphemerisGpsDepF forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisQzss = MsgEphemerisQzss -> Msg -> SBPMsg
SBPMsgEphemerisQzss forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisSbas = MsgEphemerisSbas -> Msg -> SBPMsg
SBPMsgEphemerisSbas forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisSbasDepA = MsgEphemerisSbasDepA -> Msg -> SBPMsg
SBPMsgEphemerisSbasDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgEphemerisSbasDepB = MsgEphemerisSbasDepB -> Msg -> SBPMsg
SBPMsgEphemerisSbasDepB forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgExtEvent = MsgExtEvent -> Msg -> SBPMsg
SBPMsgExtEvent forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgFileioConfigReq = MsgFileioConfigReq -> Msg -> SBPMsg
SBPMsgFileioConfigReq forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgFileioConfigResp = MsgFileioConfigResp -> Msg -> SBPMsg
SBPMsgFileioConfigResp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgFileioReadDirReq = MsgFileioReadDirReq -> Msg -> SBPMsg
SBPMsgFileioReadDirReq forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgFileioReadDirResp = MsgFileioReadDirResp -> Msg -> SBPMsg
SBPMsgFileioReadDirResp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgFileioReadReq = MsgFileioReadReq -> Msg -> SBPMsg
SBPMsgFileioReadReq forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgFileioReadResp = MsgFileioReadResp -> Msg -> SBPMsg
SBPMsgFileioReadResp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgFileioRemove = MsgFileioRemove -> Msg -> SBPMsg
SBPMsgFileioRemove forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgFileioWriteReq = MsgFileioWriteReq -> Msg -> SBPMsg
SBPMsgFileioWriteReq forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgFileioWriteResp = MsgFileioWriteResp -> Msg -> SBPMsg
SBPMsgFileioWriteResp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgFlashDone = MsgFlashDone -> Msg -> SBPMsg
SBPMsgFlashDone forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgFlashErase = MsgFlashErase -> Msg -> SBPMsg
SBPMsgFlashErase forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgFlashProgram = MsgFlashProgram -> Msg -> SBPMsg
SBPMsgFlashProgram forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgFlashReadReq = MsgFlashReadReq -> Msg -> SBPMsg
SBPMsgFlashReadReq forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgFlashReadResp = MsgFlashReadResp -> Msg -> SBPMsg
SBPMsgFlashReadResp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgFrontEndGain = MsgFrontEndGain -> Msg -> SBPMsg
SBPMsgFrontEndGain forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgFwd = MsgFwd -> Msg -> SBPMsg
SBPMsgFwd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgGloBiases = MsgGloBiases -> Msg -> SBPMsg
SBPMsgGloBiases forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgGnssCapb = MsgGnssCapb -> Msg -> SBPMsg
SBPMsgGnssCapb forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgGnssTimeOffset = MsgGnssTimeOffset -> Msg -> SBPMsg
SBPMsgGnssTimeOffset forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgGpsTime = MsgGpsTime -> Msg -> SBPMsg
SBPMsgGpsTime forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgGpsTimeDepA = MsgGpsTimeDepA -> Msg -> SBPMsg
SBPMsgGpsTimeDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgGpsTimeGnss = MsgGpsTimeGnss -> Msg -> SBPMsg
SBPMsgGpsTimeGnss forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgGroupDelay = MsgGroupDelay -> Msg -> SBPMsg
SBPMsgGroupDelay forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgGroupDelayDepA = MsgGroupDelayDepA -> Msg -> SBPMsg
SBPMsgGroupDelayDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgGroupDelayDepB = MsgGroupDelayDepB -> Msg -> SBPMsg
SBPMsgGroupDelayDepB forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgGroupMeta = MsgGroupMeta -> Msg -> SBPMsg
SBPMsgGroupMeta forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgHeartbeat = MsgHeartbeat -> Msg -> SBPMsg
SBPMsgHeartbeat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgIarState = MsgIarState -> Msg -> SBPMsg
SBPMsgIarState forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgImuAux = MsgImuAux -> Msg -> SBPMsg
SBPMsgImuAux forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgImuRaw = MsgImuRaw -> Msg -> SBPMsg
SBPMsgImuRaw forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgInitBaseDep = MsgInitBaseDep -> Msg -> SBPMsg
SBPMsgInitBaseDep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgInsStatus = MsgInsStatus -> Msg -> SBPMsg
SBPMsgInsStatus forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgInsUpdates = MsgInsUpdates -> Msg -> SBPMsg
SBPMsgInsUpdates forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgIono = MsgIono -> Msg -> SBPMsg
SBPMsgIono forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxCpuState = MsgLinuxCpuState -> Msg -> SBPMsg
SBPMsgLinuxCpuState forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxCpuStateDepA = MsgLinuxCpuStateDepA -> Msg -> SBPMsg
SBPMsgLinuxCpuStateDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxMemState = MsgLinuxMemState -> Msg -> SBPMsg
SBPMsgLinuxMemState forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxMemStateDepA = MsgLinuxMemStateDepA -> Msg -> SBPMsg
SBPMsgLinuxMemStateDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxProcessFdCount = MsgLinuxProcessFdCount -> Msg -> SBPMsg
SBPMsgLinuxProcessFdCount forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxProcessFdSummary = MsgLinuxProcessFdSummary -> Msg -> SBPMsg
SBPMsgLinuxProcessFdSummary forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxProcessSocketCounts = MsgLinuxProcessSocketCounts -> Msg -> SBPMsg
SBPMsgLinuxProcessSocketCounts forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxProcessSocketQueues = MsgLinuxProcessSocketQueues -> Msg -> SBPMsg
SBPMsgLinuxProcessSocketQueues forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxSocketUsage = MsgLinuxSocketUsage -> Msg -> SBPMsg
SBPMsgLinuxSocketUsage forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxSysState = MsgLinuxSysState -> Msg -> SBPMsg
SBPMsgLinuxSysState forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgLinuxSysStateDepA = MsgLinuxSysStateDepA -> Msg -> SBPMsg
SBPMsgLinuxSysStateDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgLog = MsgLog -> Msg -> SBPMsg
SBPMsgLog forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgM25FlashWriteStatus = MsgM25FlashWriteStatus -> Msg -> SBPMsg
SBPMsgM25FlashWriteStatus forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgMagRaw = MsgMagRaw -> Msg -> SBPMsg
SBPMsgMagRaw forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgMaskSatellite = MsgMaskSatellite -> Msg -> SBPMsg
SBPMsgMaskSatellite forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgMaskSatelliteDep = MsgMaskSatelliteDep -> Msg -> SBPMsg
SBPMsgMaskSatelliteDep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgMeasurementState = MsgMeasurementState -> Msg -> SBPMsg
SBPMsgMeasurementState forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgNapDeviceDnaReq = MsgNapDeviceDnaReq -> Msg -> SBPMsg
SBPMsgNapDeviceDnaReq forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgNapDeviceDnaResp = MsgNapDeviceDnaResp -> Msg -> SBPMsg
SBPMsgNapDeviceDnaResp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgNdbEvent = MsgNdbEvent -> Msg -> SBPMsg
SBPMsgNdbEvent forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgNetworkBandwidthUsage = MsgNetworkBandwidthUsage -> Msg -> SBPMsg
SBPMsgNetworkBandwidthUsage forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgNetworkStateReq = MsgNetworkStateReq -> Msg -> SBPMsg
SBPMsgNetworkStateReq forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgNetworkStateResp = MsgNetworkStateResp -> Msg -> SBPMsg
SBPMsgNetworkStateResp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgObs = MsgObs -> Msg -> SBPMsg
SBPMsgObs forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgObsDepA = MsgObsDepA -> Msg -> SBPMsg
SBPMsgObsDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgObsDepB = MsgObsDepB -> Msg -> SBPMsg
SBPMsgObsDepB forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgObsDepC = MsgObsDepC -> Msg -> SBPMsg
SBPMsgObsDepC forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgOdometry = MsgOdometry -> Msg -> SBPMsg
SBPMsgOdometry forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgOrientEuler = MsgOrientEuler -> Msg -> SBPMsg
SBPMsgOrientEuler forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgOrientQuat = MsgOrientQuat -> Msg -> SBPMsg
SBPMsgOrientQuat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgOsr = MsgOsr -> Msg -> SBPMsg
SBPMsgOsr forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgPosEcef = MsgPosEcef -> Msg -> SBPMsg
SBPMsgPosEcef forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgPosEcefCov = MsgPosEcefCov -> Msg -> SBPMsg
SBPMsgPosEcefCov forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgPosEcefCovGnss = MsgPosEcefCovGnss -> Msg -> SBPMsg
SBPMsgPosEcefCovGnss forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgPosEcefDepA = MsgPosEcefDepA -> Msg -> SBPMsg
SBPMsgPosEcefDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgPosEcefGnss = MsgPosEcefGnss -> Msg -> SBPMsg
SBPMsgPosEcefGnss forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgPosLlh = MsgPosLlh -> Msg -> SBPMsg
SBPMsgPosLlh forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgPosLlhAcc = MsgPosLlhAcc -> Msg -> SBPMsg
SBPMsgPosLlhAcc forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgPosLlhCov = MsgPosLlhCov -> Msg -> SBPMsg
SBPMsgPosLlhCov forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgPosLlhCovGnss = MsgPosLlhCovGnss -> Msg -> SBPMsg
SBPMsgPosLlhCovGnss forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgPosLlhDepA = MsgPosLlhDepA -> Msg -> SBPMsg
SBPMsgPosLlhDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgPosLlhGnss = MsgPosLlhGnss -> Msg -> SBPMsg
SBPMsgPosLlhGnss forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgPpsTime = MsgPpsTime -> Msg -> SBPMsg
SBPMsgPpsTime forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgPrintDep = MsgPrintDep -> Msg -> SBPMsg
SBPMsgPrintDep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgProtectionLevel = MsgProtectionLevel -> Msg -> SBPMsg
SBPMsgProtectionLevel forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgProtectionLevelDepA = MsgProtectionLevelDepA -> Msg -> SBPMsg
SBPMsgProtectionLevelDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgReferenceFrameParam = MsgReferenceFrameParam -> Msg -> SBPMsg
SBPMsgReferenceFrameParam forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgReset = MsgReset -> Msg -> SBPMsg
SBPMsgReset forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgResetDep = MsgResetDep -> Msg -> SBPMsg
SBPMsgResetDep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgResetFilters = MsgResetFilters -> Msg -> SBPMsg
SBPMsgResetFilters forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSbasRaw = MsgSbasRaw -> Msg -> SBPMsg
SBPMsgSbasRaw forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSensorAidEvent = MsgSensorAidEvent -> Msg -> SBPMsg
SBPMsgSensorAidEvent forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSetTime = MsgSetTime -> Msg -> SBPMsg
SBPMsgSetTime forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsReadByIndexDone = MsgSettingsReadByIndexDone -> Msg -> SBPMsg
SBPMsgSettingsReadByIndexDone forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsReadByIndexReq = MsgSettingsReadByIndexReq -> Msg -> SBPMsg
SBPMsgSettingsReadByIndexReq forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsReadByIndexResp = MsgSettingsReadByIndexResp -> Msg -> SBPMsg
SBPMsgSettingsReadByIndexResp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsReadReq = MsgSettingsReadReq -> Msg -> SBPMsg
SBPMsgSettingsReadReq forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsReadResp = MsgSettingsReadResp -> Msg -> SBPMsg
SBPMsgSettingsReadResp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsRegister = MsgSettingsRegister -> Msg -> SBPMsg
SBPMsgSettingsRegister forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsRegisterResp = MsgSettingsRegisterResp -> Msg -> SBPMsg
SBPMsgSettingsRegisterResp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsSave = MsgSettingsSave -> Msg -> SBPMsg
SBPMsgSettingsSave forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsWrite = MsgSettingsWrite -> Msg -> SBPMsg
SBPMsgSettingsWrite forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSettingsWriteResp = MsgSettingsWriteResp -> Msg -> SBPMsg
SBPMsgSettingsWriteResp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSolnMeta = MsgSolnMeta -> Msg -> SBPMsg
SBPMsgSolnMeta forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSolnMetaDepA = MsgSolnMetaDepA -> Msg -> SBPMsg
SBPMsgSolnMetaDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSpecan = MsgSpecan -> Msg -> SBPMsg
SBPMsgSpecan forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSpecanDep = MsgSpecanDep -> Msg -> SBPMsg
SBPMsgSpecanDep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrCodeBiases = MsgSsrCodeBiases -> Msg -> SBPMsg
SBPMsgSsrCodeBiases forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrCodePhaseBiasesBounds = MsgSsrCodePhaseBiasesBounds -> Msg -> SBPMsg
SBPMsgSsrCodePhaseBiasesBounds forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrFlagHighLevel = MsgSsrFlagHighLevel -> Msg -> SBPMsg
SBPMsgSsrFlagHighLevel forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrFlagIonoGridPointSatLos = MsgSsrFlagIonoGridPointSatLos -> Msg -> SBPMsg
SBPMsgSsrFlagIonoGridPointSatLos forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrFlagIonoGridPoints = MsgSsrFlagIonoGridPoints -> Msg -> SBPMsg
SBPMsgSsrFlagIonoGridPoints forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrFlagIonoTileSatLos = MsgSsrFlagIonoTileSatLos -> Msg -> SBPMsg
SBPMsgSsrFlagIonoTileSatLos forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrFlagSatellites = MsgSsrFlagSatellites -> Msg -> SBPMsg
SBPMsgSsrFlagSatellites forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrFlagTropoGridPoints = MsgSsrFlagTropoGridPoints -> Msg -> SBPMsg
SBPMsgSsrFlagTropoGridPoints forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrGridDefinitionDepA = MsgSsrGridDefinitionDepA -> Msg -> SBPMsg
SBPMsgSsrGridDefinitionDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrGriddedCorrection = MsgSsrGriddedCorrection -> Msg -> SBPMsg
SBPMsgSsrGriddedCorrection forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrGriddedCorrectionBounds = MsgSsrGriddedCorrectionBounds -> Msg -> SBPMsg
SBPMsgSsrGriddedCorrectionBounds forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrGriddedCorrectionDepA = MsgSsrGriddedCorrectionDepA -> Msg -> SBPMsg
SBPMsgSsrGriddedCorrectionDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrGriddedCorrectionNoStdDepA = MsgSsrGriddedCorrectionNoStdDepA -> Msg -> SBPMsg
SBPMsgSsrGriddedCorrectionNoStdDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrOrbitClock = MsgSsrOrbitClock -> Msg -> SBPMsg
SBPMsgSsrOrbitClock forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrOrbitClockBounds = MsgSsrOrbitClockBounds -> Msg -> SBPMsg
SBPMsgSsrOrbitClockBounds forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrOrbitClockBoundsDegradation = MsgSsrOrbitClockBoundsDegradation -> Msg -> SBPMsg
SBPMsgSsrOrbitClockBoundsDegradation forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrOrbitClockDepA = MsgSsrOrbitClockDepA -> Msg -> SBPMsg
SBPMsgSsrOrbitClockDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrPhaseBiases = MsgSsrPhaseBiases -> Msg -> SBPMsg
SBPMsgSsrPhaseBiases forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrSatelliteApc = MsgSsrSatelliteApc -> Msg -> SBPMsg
SBPMsgSsrSatelliteApc forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrStecCorrection = MsgSsrStecCorrection -> Msg -> SBPMsg
SBPMsgSsrStecCorrection forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrStecCorrectionDep = MsgSsrStecCorrectionDep -> Msg -> SBPMsg
SBPMsgSsrStecCorrectionDep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrStecCorrectionDepA = MsgSsrStecCorrectionDepA -> Msg -> SBPMsg
SBPMsgSsrStecCorrectionDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrTileDefinition = MsgSsrTileDefinition -> Msg -> SBPMsg
SBPMsgSsrTileDefinition forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSsrTileDefinitionDep = MsgSsrTileDefinitionDep -> Msg -> SBPMsg
SBPMsgSsrTileDefinitionDep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgStartup = MsgStartup -> Msg -> SBPMsg
SBPMsgStartup forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgStatusJournal = MsgStatusJournal -> Msg -> SBPMsg
SBPMsgStatusJournal forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgStatusReport = MsgStatusReport -> Msg -> SBPMsg
SBPMsgStatusReport forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgStmFlashLockSector = MsgStmFlashLockSector -> Msg -> SBPMsg
SBPMsgStmFlashLockSector forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgStmFlashUnlockSector = MsgStmFlashUnlockSector -> Msg -> SBPMsg
SBPMsgStmFlashUnlockSector forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgStmUniqueIdReq = MsgStmUniqueIdReq -> Msg -> SBPMsg
SBPMsgStmUniqueIdReq forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgStmUniqueIdResp = MsgStmUniqueIdResp -> Msg -> SBPMsg
SBPMsgStmUniqueIdResp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSvAzEl = MsgSvAzEl -> Msg -> SBPMsg
SBPMsgSvAzEl forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgSvConfigurationGpsDep = MsgSvConfigurationGpsDep -> Msg -> SBPMsg
SBPMsgSvConfigurationGpsDep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgThreadState = MsgThreadState -> Msg -> SBPMsg
SBPMsgThreadState forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgTrackingIq = MsgTrackingIq -> Msg -> SBPMsg
SBPMsgTrackingIq forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgTrackingIqDepA = MsgTrackingIqDepA -> Msg -> SBPMsg
SBPMsgTrackingIqDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgTrackingIqDepB = MsgTrackingIqDepB -> Msg -> SBPMsg
SBPMsgTrackingIqDepB forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgTrackingState = MsgTrackingState -> Msg -> SBPMsg
SBPMsgTrackingState forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgTrackingStateDepA = MsgTrackingStateDepA -> Msg -> SBPMsg
SBPMsgTrackingStateDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgTrackingStateDepB = MsgTrackingStateDepB -> Msg -> SBPMsg
SBPMsgTrackingStateDepB forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgTrackingStateDetailedDep = MsgTrackingStateDetailedDep -> Msg -> SBPMsg
SBPMsgTrackingStateDetailedDep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgTrackingStateDetailedDepA = MsgTrackingStateDetailedDepA -> Msg -> SBPMsg
SBPMsgTrackingStateDetailedDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgUartState = MsgUartState -> Msg -> SBPMsg
SBPMsgUartState forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgUartStateDepa = MsgUartStateDepa -> Msg -> SBPMsg
SBPMsgUartStateDepa forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgUserData = MsgUserData -> Msg -> SBPMsg
SBPMsgUserData forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgUtcLeapSecond = MsgUtcLeapSecond -> Msg -> SBPMsg
SBPMsgUtcLeapSecond forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgUtcTime = MsgUtcTime -> Msg -> SBPMsg
SBPMsgUtcTime forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgUtcTimeGnss = MsgUtcTimeGnss -> Msg -> SBPMsg
SBPMsgUtcTimeGnss forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgVelBody = MsgVelBody -> Msg -> SBPMsg
SBPMsgVelBody forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgVelCog = MsgVelCog -> Msg -> SBPMsg
SBPMsgVelCog forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgVelEcef = MsgVelEcef -> Msg -> SBPMsg
SBPMsgVelEcef forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgVelEcefCov = MsgVelEcefCov -> Msg -> SBPMsg
SBPMsgVelEcefCov forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgVelEcefCovGnss = MsgVelEcefCovGnss -> Msg -> SBPMsg
SBPMsgVelEcefCovGnss forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgVelEcefDepA = MsgVelEcefDepA -> Msg -> SBPMsg
SBPMsgVelEcefDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgVelEcefGnss = MsgVelEcefGnss -> Msg -> SBPMsg
SBPMsgVelEcefGnss forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgVelNed = MsgVelNed -> Msg -> SBPMsg
SBPMsgVelNed forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgVelNedCov = MsgVelNedCov -> Msg -> SBPMsg
SBPMsgVelNedCov forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgVelNedCovGnss = MsgVelNedCovGnss -> Msg -> SBPMsg
SBPMsgVelNedCovGnss forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgVelNedDepA = MsgVelNedDepA -> Msg -> SBPMsg
SBPMsgVelNedDepA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgVelNedGnss = MsgVelNedGnss -> Msg -> SBPMsg
SBPMsgVelNedGnss forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Word16
msgType forall a. Eq a => a -> a -> Bool
== Word16
msgWheeltick = MsgWheeltick -> Msg -> SBPMsg
SBPMsgWheeltick forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Binary a => ByteString -> a
decode (ByteString -> ByteString
fromStrict (Bytes -> ByteString
unBytes Bytes
payload))) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
        | Bool
otherwise = Msg -> SBPMsg
SBPMsgUnknown forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON Value
obj
  parseJSON Value
_ = forall (m :: * -> *) a. MonadPlus m => m a
mzero

(<<>>) :: Value -> Value -> Value
<<>> :: Value -> Value -> Value
(<<>>) Value
a Value
b = forall a. a -> Maybe a -> a
fromMaybe Value
Null forall a b. (a -> b) -> a -> b
$ do
  KeyMap Value
a' <- forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview forall t. AsValue t => Prism' t (KeyMap Value)
_Object Value
a
  KeyMap Value
b' <- forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview forall t. AsValue t => Prism' t (KeyMap Value)
_Object Value
b
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review forall t. AsValue t => Prism' t (KeyMap Value)
_Object forall a b. (a -> b) -> a -> b
$ KeyMap Value
a' forall a. Semigroup a => a -> a -> a
<> KeyMap Value
b'

instance ToJSON SBPMsg where
  toJSON :: SBPMsg -> Value
toJSON (SBPMsgAcqResult MsgAcqResult
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgAcqResult
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgAcqResultDepA MsgAcqResultDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgAcqResultDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgAcqResultDepB MsgAcqResultDepB
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgAcqResultDepB
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgAcqResultDepC MsgAcqResultDepC
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgAcqResultDepC
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgAcqSvProfile MsgAcqSvProfile
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgAcqSvProfile
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgAcqSvProfileDep MsgAcqSvProfileDep
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgAcqSvProfileDep
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgAgeCorrections MsgAgeCorrections
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgAgeCorrections
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgAlmanac MsgAlmanac
_ Msg
m) = forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgAlmanacGlo MsgAlmanacGlo
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgAlmanacGlo
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgAlmanacGloDep MsgAlmanacGloDep
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgAlmanacGloDep
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgAlmanacGps MsgAlmanacGps
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgAlmanacGps
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgAlmanacGpsDep MsgAlmanacGpsDep
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgAlmanacGpsDep
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgAngularRate MsgAngularRate
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgAngularRate
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgBasePosEcef MsgBasePosEcef
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgBasePosEcef
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgBasePosLlh MsgBasePosLlh
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgBasePosLlh
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgBaselineEcef MsgBaselineEcef
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgBaselineEcef
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgBaselineEcefDepA MsgBaselineEcefDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgBaselineEcefDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgBaselineHeading MsgBaselineHeading
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgBaselineHeading
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgBaselineHeadingDepA MsgBaselineHeadingDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgBaselineHeadingDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgBaselineNed MsgBaselineNed
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgBaselineNed
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgBaselineNedDepA MsgBaselineNedDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgBaselineNedDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgBootloaderHandshakeDepA MsgBootloaderHandshakeDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgBootloaderHandshakeDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgBootloaderHandshakeReq MsgBootloaderHandshakeReq
_ Msg
m) = forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgBootloaderHandshakeResp MsgBootloaderHandshakeResp
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgBootloaderHandshakeResp
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgBootloaderJumpToApp MsgBootloaderJumpToApp
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgBootloaderJumpToApp
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgCellModemStatus MsgCellModemStatus
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgCellModemStatus
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgCommandOutput MsgCommandOutput
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgCommandOutput
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgCommandReq MsgCommandReq
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgCommandReq
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgCommandResp MsgCommandResp
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgCommandResp
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgCsacTelemetry MsgCsacTelemetry
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgCsacTelemetry
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgCsacTelemetryLabels MsgCsacTelemetryLabels
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgCsacTelemetryLabels
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgCwResults MsgCwResults
_ Msg
m) = forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgCwStart MsgCwStart
_ Msg
m) = forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgDeviceMonitor MsgDeviceMonitor
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgDeviceMonitor
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgDgnssStatus MsgDgnssStatus
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgDgnssStatus
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgDops MsgDops
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgDops
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgDopsDepA MsgDopsDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgDopsDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEd25519Certificate MsgEd25519Certificate
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEd25519Certificate
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEd25519Signature MsgEd25519Signature
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEd25519Signature
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisBds MsgEphemerisBds
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisBds
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisDepA MsgEphemerisDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisDepB MsgEphemerisDepB
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisDepB
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisDepC MsgEphemerisDepC
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisDepC
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisDepD MsgEphemerisDepD
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisDepD
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisGal MsgEphemerisGal
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisGal
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisGalDepA MsgEphemerisGalDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisGalDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisGlo MsgEphemerisGlo
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisGlo
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisGloDepA MsgEphemerisGloDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisGloDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisGloDepB MsgEphemerisGloDepB
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisGloDepB
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisGloDepC MsgEphemerisGloDepC
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisGloDepC
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisGloDepD MsgEphemerisGloDepD
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisGloDepD
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisGps MsgEphemerisGps
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisGps
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisGpsDepE MsgEphemerisGpsDepE
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisGpsDepE
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisGpsDepF MsgEphemerisGpsDepF
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisGpsDepF
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisQzss MsgEphemerisQzss
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisQzss
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisSbas MsgEphemerisSbas
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisSbas
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisSbasDepA MsgEphemerisSbasDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisSbasDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgEphemerisSbasDepB MsgEphemerisSbasDepB
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgEphemerisSbasDepB
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgExtEvent MsgExtEvent
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgExtEvent
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgFileioConfigReq MsgFileioConfigReq
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgFileioConfigReq
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgFileioConfigResp MsgFileioConfigResp
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgFileioConfigResp
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgFileioReadDirReq MsgFileioReadDirReq
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgFileioReadDirReq
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgFileioReadDirResp MsgFileioReadDirResp
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgFileioReadDirResp
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgFileioReadReq MsgFileioReadReq
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgFileioReadReq
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgFileioReadResp MsgFileioReadResp
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgFileioReadResp
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgFileioRemove MsgFileioRemove
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgFileioRemove
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgFileioWriteReq MsgFileioWriteReq
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgFileioWriteReq
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgFileioWriteResp MsgFileioWriteResp
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgFileioWriteResp
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgFlashDone MsgFlashDone
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgFlashDone
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgFlashErase MsgFlashErase
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgFlashErase
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgFlashProgram MsgFlashProgram
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgFlashProgram
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgFlashReadReq MsgFlashReadReq
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgFlashReadReq
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgFlashReadResp MsgFlashReadResp
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgFlashReadResp
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgFrontEndGain MsgFrontEndGain
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgFrontEndGain
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgFwd MsgFwd
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgFwd
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgGloBiases MsgGloBiases
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgGloBiases
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgGnssCapb MsgGnssCapb
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgGnssCapb
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgGnssTimeOffset MsgGnssTimeOffset
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgGnssTimeOffset
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgGpsTime MsgGpsTime
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgGpsTime
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgGpsTimeDepA MsgGpsTimeDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgGpsTimeDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgGpsTimeGnss MsgGpsTimeGnss
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgGpsTimeGnss
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgGroupDelay MsgGroupDelay
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgGroupDelay
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgGroupDelayDepA MsgGroupDelayDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgGroupDelayDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgGroupDelayDepB MsgGroupDelayDepB
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgGroupDelayDepB
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgGroupMeta MsgGroupMeta
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgGroupMeta
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgHeartbeat MsgHeartbeat
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgHeartbeat
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgIarState MsgIarState
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgIarState
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgImuAux MsgImuAux
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgImuAux
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgImuRaw MsgImuRaw
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgImuRaw
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgInitBaseDep MsgInitBaseDep
_ Msg
m) = forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgInsStatus MsgInsStatus
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgInsStatus
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgInsUpdates MsgInsUpdates
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgInsUpdates
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgIono MsgIono
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgIono
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgLinuxCpuState MsgLinuxCpuState
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgLinuxCpuState
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgLinuxCpuStateDepA MsgLinuxCpuStateDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgLinuxCpuStateDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgLinuxMemState MsgLinuxMemState
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgLinuxMemState
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgLinuxMemStateDepA MsgLinuxMemStateDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgLinuxMemStateDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgLinuxProcessFdCount MsgLinuxProcessFdCount
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgLinuxProcessFdCount
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgLinuxProcessFdSummary MsgLinuxProcessFdSummary
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgLinuxProcessFdSummary
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgLinuxProcessSocketCounts MsgLinuxProcessSocketCounts
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgLinuxProcessSocketCounts
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgLinuxProcessSocketQueues MsgLinuxProcessSocketQueues
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgLinuxProcessSocketQueues
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgLinuxSocketUsage MsgLinuxSocketUsage
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgLinuxSocketUsage
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgLinuxSysState MsgLinuxSysState
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgLinuxSysState
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgLinuxSysStateDepA MsgLinuxSysStateDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgLinuxSysStateDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgLog MsgLog
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgLog
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgM25FlashWriteStatus MsgM25FlashWriteStatus
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgM25FlashWriteStatus
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgMagRaw MsgMagRaw
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgMagRaw
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgMaskSatellite MsgMaskSatellite
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgMaskSatellite
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgMaskSatelliteDep MsgMaskSatelliteDep
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgMaskSatelliteDep
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgMeasurementState MsgMeasurementState
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgMeasurementState
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgNapDeviceDnaReq MsgNapDeviceDnaReq
_ Msg
m) = forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgNapDeviceDnaResp MsgNapDeviceDnaResp
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgNapDeviceDnaResp
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgNdbEvent MsgNdbEvent
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgNdbEvent
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgNetworkBandwidthUsage MsgNetworkBandwidthUsage
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgNetworkBandwidthUsage
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgNetworkStateReq MsgNetworkStateReq
_ Msg
m) = forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgNetworkStateResp MsgNetworkStateResp
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgNetworkStateResp
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgObs MsgObs
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgObs
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgObsDepA MsgObsDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgObsDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgObsDepB MsgObsDepB
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgObsDepB
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgObsDepC MsgObsDepC
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgObsDepC
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgOdometry MsgOdometry
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgOdometry
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgOrientEuler MsgOrientEuler
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgOrientEuler
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgOrientQuat MsgOrientQuat
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgOrientQuat
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgOsr MsgOsr
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgOsr
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgPosEcef MsgPosEcef
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgPosEcef
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgPosEcefCov MsgPosEcefCov
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgPosEcefCov
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgPosEcefCovGnss MsgPosEcefCovGnss
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgPosEcefCovGnss
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgPosEcefDepA MsgPosEcefDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgPosEcefDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgPosEcefGnss MsgPosEcefGnss
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgPosEcefGnss
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgPosLlh MsgPosLlh
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgPosLlh
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgPosLlhAcc MsgPosLlhAcc
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgPosLlhAcc
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgPosLlhCov MsgPosLlhCov
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgPosLlhCov
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgPosLlhCovGnss MsgPosLlhCovGnss
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgPosLlhCovGnss
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgPosLlhDepA MsgPosLlhDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgPosLlhDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgPosLlhGnss MsgPosLlhGnss
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgPosLlhGnss
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgPpsTime MsgPpsTime
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgPpsTime
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgPrintDep MsgPrintDep
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgPrintDep
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgProtectionLevel MsgProtectionLevel
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgProtectionLevel
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgProtectionLevelDepA MsgProtectionLevelDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgProtectionLevelDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgReferenceFrameParam MsgReferenceFrameParam
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgReferenceFrameParam
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgReset MsgReset
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgReset
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgResetDep MsgResetDep
_ Msg
m) = forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgResetFilters MsgResetFilters
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgResetFilters
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSbasRaw MsgSbasRaw
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSbasRaw
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSensorAidEvent MsgSensorAidEvent
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSensorAidEvent
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSetTime MsgSetTime
_ Msg
m) = forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSettingsReadByIndexDone MsgSettingsReadByIndexDone
_ Msg
m) = forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSettingsReadByIndexReq MsgSettingsReadByIndexReq
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSettingsReadByIndexReq
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSettingsReadByIndexResp MsgSettingsReadByIndexResp
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSettingsReadByIndexResp
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSettingsReadReq MsgSettingsReadReq
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSettingsReadReq
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSettingsReadResp MsgSettingsReadResp
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSettingsReadResp
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSettingsRegister MsgSettingsRegister
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSettingsRegister
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSettingsRegisterResp MsgSettingsRegisterResp
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSettingsRegisterResp
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSettingsSave MsgSettingsSave
_ Msg
m) = forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSettingsWrite MsgSettingsWrite
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSettingsWrite
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSettingsWriteResp MsgSettingsWriteResp
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSettingsWriteResp
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSolnMeta MsgSolnMeta
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSolnMeta
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSolnMetaDepA MsgSolnMetaDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSolnMetaDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSpecan MsgSpecan
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSpecan
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSpecanDep MsgSpecanDep
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSpecanDep
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrCodeBiases MsgSsrCodeBiases
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrCodeBiases
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrCodePhaseBiasesBounds MsgSsrCodePhaseBiasesBounds
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrCodePhaseBiasesBounds
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrFlagHighLevel MsgSsrFlagHighLevel
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrFlagHighLevel
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrFlagIonoGridPointSatLos MsgSsrFlagIonoGridPointSatLos
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrFlagIonoGridPointSatLos
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrFlagIonoGridPoints MsgSsrFlagIonoGridPoints
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrFlagIonoGridPoints
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrFlagIonoTileSatLos MsgSsrFlagIonoTileSatLos
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrFlagIonoTileSatLos
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrFlagSatellites MsgSsrFlagSatellites
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrFlagSatellites
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrFlagTropoGridPoints MsgSsrFlagTropoGridPoints
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrFlagTropoGridPoints
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrGridDefinitionDepA MsgSsrGridDefinitionDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrGridDefinitionDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrGriddedCorrection MsgSsrGriddedCorrection
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrGriddedCorrection
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrGriddedCorrectionBounds MsgSsrGriddedCorrectionBounds
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrGriddedCorrectionBounds
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrGriddedCorrectionDepA MsgSsrGriddedCorrectionDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrGriddedCorrectionDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrGriddedCorrectionNoStdDepA MsgSsrGriddedCorrectionNoStdDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrGriddedCorrectionNoStdDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrOrbitClock MsgSsrOrbitClock
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrOrbitClock
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrOrbitClockBounds MsgSsrOrbitClockBounds
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrOrbitClockBounds
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrOrbitClockBoundsDegradation MsgSsrOrbitClockBoundsDegradation
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrOrbitClockBoundsDegradation
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrOrbitClockDepA MsgSsrOrbitClockDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrOrbitClockDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrPhaseBiases MsgSsrPhaseBiases
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrPhaseBiases
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrSatelliteApc MsgSsrSatelliteApc
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrSatelliteApc
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrStecCorrection MsgSsrStecCorrection
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrStecCorrection
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrStecCorrectionDep MsgSsrStecCorrectionDep
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrStecCorrectionDep
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrStecCorrectionDepA MsgSsrStecCorrectionDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrStecCorrectionDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrTileDefinition MsgSsrTileDefinition
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrTileDefinition
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSsrTileDefinitionDep MsgSsrTileDefinitionDep
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSsrTileDefinitionDep
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgStartup MsgStartup
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgStartup
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgStatusJournal MsgStatusJournal
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgStatusJournal
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgStatusReport MsgStatusReport
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgStatusReport
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgStmFlashLockSector MsgStmFlashLockSector
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgStmFlashLockSector
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgStmFlashUnlockSector MsgStmFlashUnlockSector
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgStmFlashUnlockSector
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgStmUniqueIdReq MsgStmUniqueIdReq
_ Msg
m) = forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgStmUniqueIdResp MsgStmUniqueIdResp
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgStmUniqueIdResp
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSvAzEl MsgSvAzEl
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSvAzEl
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgSvConfigurationGpsDep MsgSvConfigurationGpsDep
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgSvConfigurationGpsDep
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgThreadState MsgThreadState
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgThreadState
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgTrackingIq MsgTrackingIq
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgTrackingIq
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgTrackingIqDepA MsgTrackingIqDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgTrackingIqDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgTrackingIqDepB MsgTrackingIqDepB
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgTrackingIqDepB
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgTrackingState MsgTrackingState
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgTrackingState
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgTrackingStateDepA MsgTrackingStateDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgTrackingStateDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgTrackingStateDepB MsgTrackingStateDepB
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgTrackingStateDepB
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgTrackingStateDetailedDep MsgTrackingStateDetailedDep
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgTrackingStateDetailedDep
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgTrackingStateDetailedDepA MsgTrackingStateDetailedDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgTrackingStateDetailedDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgUartState MsgUartState
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgUartState
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgUartStateDepa MsgUartStateDepa
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgUartStateDepa
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgUserData MsgUserData
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgUserData
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgUtcLeapSecond MsgUtcLeapSecond
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgUtcLeapSecond
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgUtcTime MsgUtcTime
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgUtcTime
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgUtcTimeGnss MsgUtcTimeGnss
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgUtcTimeGnss
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgVelBody MsgVelBody
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgVelBody
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgVelCog MsgVelCog
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgVelCog
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgVelEcef MsgVelEcef
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgVelEcef
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgVelEcefCov MsgVelEcefCov
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgVelEcefCov
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgVelEcefCovGnss MsgVelEcefCovGnss
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgVelEcefCovGnss
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgVelEcefDepA MsgVelEcefDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgVelEcefDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgVelEcefGnss MsgVelEcefGnss
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgVelEcefGnss
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgVelNed MsgVelNed
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgVelNed
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgVelNedCov MsgVelNedCov
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgVelNedCov
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgVelNedCovGnss MsgVelNedCovGnss
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgVelNedCovGnss
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgVelNedDepA MsgVelNedDepA
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgVelNedDepA
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgVelNedGnss MsgVelNedGnss
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgVelNedGnss
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgWheeltick MsgWheeltick
n Msg
m) = forall a. ToJSON a => a -> Value
toJSON MsgWheeltick
n Value -> Value -> Value
<<>> forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgBadCrc Msg
m) = forall a. ToJSON a => a -> Value
toJSON Msg
m
  toJSON (SBPMsgUnknown Msg
m) = forall a. ToJSON a => a -> Value
toJSON Msg
m

instance HasMsg SBPMsg where
  msg :: Lens' SBPMsg Msg
msg Msg -> f Msg
f (SBPMsgAcqResult MsgAcqResult
n Msg
m) = MsgAcqResult -> Msg -> SBPMsg
SBPMsgAcqResult MsgAcqResult
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgAcqResultDepA MsgAcqResultDepA
n Msg
m) = MsgAcqResultDepA -> Msg -> SBPMsg
SBPMsgAcqResultDepA MsgAcqResultDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgAcqResultDepB MsgAcqResultDepB
n Msg
m) = MsgAcqResultDepB -> Msg -> SBPMsg
SBPMsgAcqResultDepB MsgAcqResultDepB
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgAcqResultDepC MsgAcqResultDepC
n Msg
m) = MsgAcqResultDepC -> Msg -> SBPMsg
SBPMsgAcqResultDepC MsgAcqResultDepC
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgAcqSvProfile MsgAcqSvProfile
n Msg
m) = MsgAcqSvProfile -> Msg -> SBPMsg
SBPMsgAcqSvProfile MsgAcqSvProfile
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgAcqSvProfileDep MsgAcqSvProfileDep
n Msg
m) = MsgAcqSvProfileDep -> Msg -> SBPMsg
SBPMsgAcqSvProfileDep MsgAcqSvProfileDep
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgAgeCorrections MsgAgeCorrections
n Msg
m) = MsgAgeCorrections -> Msg -> SBPMsg
SBPMsgAgeCorrections MsgAgeCorrections
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgAlmanac MsgAlmanac
n Msg
m) = MsgAlmanac -> Msg -> SBPMsg
SBPMsgAlmanac MsgAlmanac
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgAlmanacGlo MsgAlmanacGlo
n Msg
m) = MsgAlmanacGlo -> Msg -> SBPMsg
SBPMsgAlmanacGlo MsgAlmanacGlo
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgAlmanacGloDep MsgAlmanacGloDep
n Msg
m) = MsgAlmanacGloDep -> Msg -> SBPMsg
SBPMsgAlmanacGloDep MsgAlmanacGloDep
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgAlmanacGps MsgAlmanacGps
n Msg
m) = MsgAlmanacGps -> Msg -> SBPMsg
SBPMsgAlmanacGps MsgAlmanacGps
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgAlmanacGpsDep MsgAlmanacGpsDep
n Msg
m) = MsgAlmanacGpsDep -> Msg -> SBPMsg
SBPMsgAlmanacGpsDep MsgAlmanacGpsDep
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgAngularRate MsgAngularRate
n Msg
m) = MsgAngularRate -> Msg -> SBPMsg
SBPMsgAngularRate MsgAngularRate
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgBasePosEcef MsgBasePosEcef
n Msg
m) = MsgBasePosEcef -> Msg -> SBPMsg
SBPMsgBasePosEcef MsgBasePosEcef
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgBasePosLlh MsgBasePosLlh
n Msg
m) = MsgBasePosLlh -> Msg -> SBPMsg
SBPMsgBasePosLlh MsgBasePosLlh
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgBaselineEcef MsgBaselineEcef
n Msg
m) = MsgBaselineEcef -> Msg -> SBPMsg
SBPMsgBaselineEcef MsgBaselineEcef
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgBaselineEcefDepA MsgBaselineEcefDepA
n Msg
m) = MsgBaselineEcefDepA -> Msg -> SBPMsg
SBPMsgBaselineEcefDepA MsgBaselineEcefDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgBaselineHeading MsgBaselineHeading
n Msg
m) = MsgBaselineHeading -> Msg -> SBPMsg
SBPMsgBaselineHeading MsgBaselineHeading
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgBaselineHeadingDepA MsgBaselineHeadingDepA
n Msg
m) = MsgBaselineHeadingDepA -> Msg -> SBPMsg
SBPMsgBaselineHeadingDepA MsgBaselineHeadingDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgBaselineNed MsgBaselineNed
n Msg
m) = MsgBaselineNed -> Msg -> SBPMsg
SBPMsgBaselineNed MsgBaselineNed
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgBaselineNedDepA MsgBaselineNedDepA
n Msg
m) = MsgBaselineNedDepA -> Msg -> SBPMsg
SBPMsgBaselineNedDepA MsgBaselineNedDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgBootloaderHandshakeDepA MsgBootloaderHandshakeDepA
n Msg
m) = MsgBootloaderHandshakeDepA -> Msg -> SBPMsg
SBPMsgBootloaderHandshakeDepA MsgBootloaderHandshakeDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgBootloaderHandshakeReq MsgBootloaderHandshakeReq
n Msg
m) = MsgBootloaderHandshakeReq -> Msg -> SBPMsg
SBPMsgBootloaderHandshakeReq MsgBootloaderHandshakeReq
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgBootloaderHandshakeResp MsgBootloaderHandshakeResp
n Msg
m) = MsgBootloaderHandshakeResp -> Msg -> SBPMsg
SBPMsgBootloaderHandshakeResp MsgBootloaderHandshakeResp
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgBootloaderJumpToApp MsgBootloaderJumpToApp
n Msg
m) = MsgBootloaderJumpToApp -> Msg -> SBPMsg
SBPMsgBootloaderJumpToApp MsgBootloaderJumpToApp
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgCellModemStatus MsgCellModemStatus
n Msg
m) = MsgCellModemStatus -> Msg -> SBPMsg
SBPMsgCellModemStatus MsgCellModemStatus
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgCommandOutput MsgCommandOutput
n Msg
m) = MsgCommandOutput -> Msg -> SBPMsg
SBPMsgCommandOutput MsgCommandOutput
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgCommandReq MsgCommandReq
n Msg
m) = MsgCommandReq -> Msg -> SBPMsg
SBPMsgCommandReq MsgCommandReq
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgCommandResp MsgCommandResp
n Msg
m) = MsgCommandResp -> Msg -> SBPMsg
SBPMsgCommandResp MsgCommandResp
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgCsacTelemetry MsgCsacTelemetry
n Msg
m) = MsgCsacTelemetry -> Msg -> SBPMsg
SBPMsgCsacTelemetry MsgCsacTelemetry
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgCsacTelemetryLabels MsgCsacTelemetryLabels
n Msg
m) = MsgCsacTelemetryLabels -> Msg -> SBPMsg
SBPMsgCsacTelemetryLabels MsgCsacTelemetryLabels
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgCwResults MsgCwResults
n Msg
m) = MsgCwResults -> Msg -> SBPMsg
SBPMsgCwResults MsgCwResults
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgCwStart MsgCwStart
n Msg
m) = MsgCwStart -> Msg -> SBPMsg
SBPMsgCwStart MsgCwStart
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgDeviceMonitor MsgDeviceMonitor
n Msg
m) = MsgDeviceMonitor -> Msg -> SBPMsg
SBPMsgDeviceMonitor MsgDeviceMonitor
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgDgnssStatus MsgDgnssStatus
n Msg
m) = MsgDgnssStatus -> Msg -> SBPMsg
SBPMsgDgnssStatus MsgDgnssStatus
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgDops MsgDops
n Msg
m) = MsgDops -> Msg -> SBPMsg
SBPMsgDops MsgDops
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgDopsDepA MsgDopsDepA
n Msg
m) = MsgDopsDepA -> Msg -> SBPMsg
SBPMsgDopsDepA MsgDopsDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEd25519Certificate MsgEd25519Certificate
n Msg
m) = MsgEd25519Certificate -> Msg -> SBPMsg
SBPMsgEd25519Certificate MsgEd25519Certificate
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEd25519Signature MsgEd25519Signature
n Msg
m) = MsgEd25519Signature -> Msg -> SBPMsg
SBPMsgEd25519Signature MsgEd25519Signature
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisBds MsgEphemerisBds
n Msg
m) = MsgEphemerisBds -> Msg -> SBPMsg
SBPMsgEphemerisBds MsgEphemerisBds
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisDepA MsgEphemerisDepA
n Msg
m) = MsgEphemerisDepA -> Msg -> SBPMsg
SBPMsgEphemerisDepA MsgEphemerisDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisDepB MsgEphemerisDepB
n Msg
m) = MsgEphemerisDepB -> Msg -> SBPMsg
SBPMsgEphemerisDepB MsgEphemerisDepB
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisDepC MsgEphemerisDepC
n Msg
m) = MsgEphemerisDepC -> Msg -> SBPMsg
SBPMsgEphemerisDepC MsgEphemerisDepC
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisDepD MsgEphemerisDepD
n Msg
m) = MsgEphemerisDepD -> Msg -> SBPMsg
SBPMsgEphemerisDepD MsgEphemerisDepD
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisGal MsgEphemerisGal
n Msg
m) = MsgEphemerisGal -> Msg -> SBPMsg
SBPMsgEphemerisGal MsgEphemerisGal
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisGalDepA MsgEphemerisGalDepA
n Msg
m) = MsgEphemerisGalDepA -> Msg -> SBPMsg
SBPMsgEphemerisGalDepA MsgEphemerisGalDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisGlo MsgEphemerisGlo
n Msg
m) = MsgEphemerisGlo -> Msg -> SBPMsg
SBPMsgEphemerisGlo MsgEphemerisGlo
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisGloDepA MsgEphemerisGloDepA
n Msg
m) = MsgEphemerisGloDepA -> Msg -> SBPMsg
SBPMsgEphemerisGloDepA MsgEphemerisGloDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisGloDepB MsgEphemerisGloDepB
n Msg
m) = MsgEphemerisGloDepB -> Msg -> SBPMsg
SBPMsgEphemerisGloDepB MsgEphemerisGloDepB
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisGloDepC MsgEphemerisGloDepC
n Msg
m) = MsgEphemerisGloDepC -> Msg -> SBPMsg
SBPMsgEphemerisGloDepC MsgEphemerisGloDepC
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisGloDepD MsgEphemerisGloDepD
n Msg
m) = MsgEphemerisGloDepD -> Msg -> SBPMsg
SBPMsgEphemerisGloDepD MsgEphemerisGloDepD
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisGps MsgEphemerisGps
n Msg
m) = MsgEphemerisGps -> Msg -> SBPMsg
SBPMsgEphemerisGps MsgEphemerisGps
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisGpsDepE MsgEphemerisGpsDepE
n Msg
m) = MsgEphemerisGpsDepE -> Msg -> SBPMsg
SBPMsgEphemerisGpsDepE MsgEphemerisGpsDepE
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisGpsDepF MsgEphemerisGpsDepF
n Msg
m) = MsgEphemerisGpsDepF -> Msg -> SBPMsg
SBPMsgEphemerisGpsDepF MsgEphemerisGpsDepF
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisQzss MsgEphemerisQzss
n Msg
m) = MsgEphemerisQzss -> Msg -> SBPMsg
SBPMsgEphemerisQzss MsgEphemerisQzss
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisSbas MsgEphemerisSbas
n Msg
m) = MsgEphemerisSbas -> Msg -> SBPMsg
SBPMsgEphemerisSbas MsgEphemerisSbas
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisSbasDepA MsgEphemerisSbasDepA
n Msg
m) = MsgEphemerisSbasDepA -> Msg -> SBPMsg
SBPMsgEphemerisSbasDepA MsgEphemerisSbasDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgEphemerisSbasDepB MsgEphemerisSbasDepB
n Msg
m) = MsgEphemerisSbasDepB -> Msg -> SBPMsg
SBPMsgEphemerisSbasDepB MsgEphemerisSbasDepB
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgExtEvent MsgExtEvent
n Msg
m) = MsgExtEvent -> Msg -> SBPMsg
SBPMsgExtEvent MsgExtEvent
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgFileioConfigReq MsgFileioConfigReq
n Msg
m) = MsgFileioConfigReq -> Msg -> SBPMsg
SBPMsgFileioConfigReq MsgFileioConfigReq
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgFileioConfigResp MsgFileioConfigResp
n Msg
m) = MsgFileioConfigResp -> Msg -> SBPMsg
SBPMsgFileioConfigResp MsgFileioConfigResp
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgFileioReadDirReq MsgFileioReadDirReq
n Msg
m) = MsgFileioReadDirReq -> Msg -> SBPMsg
SBPMsgFileioReadDirReq MsgFileioReadDirReq
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgFileioReadDirResp MsgFileioReadDirResp
n Msg
m) = MsgFileioReadDirResp -> Msg -> SBPMsg
SBPMsgFileioReadDirResp MsgFileioReadDirResp
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgFileioReadReq MsgFileioReadReq
n Msg
m) = MsgFileioReadReq -> Msg -> SBPMsg
SBPMsgFileioReadReq MsgFileioReadReq
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgFileioReadResp MsgFileioReadResp
n Msg
m) = MsgFileioReadResp -> Msg -> SBPMsg
SBPMsgFileioReadResp MsgFileioReadResp
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgFileioRemove MsgFileioRemove
n Msg
m) = MsgFileioRemove -> Msg -> SBPMsg
SBPMsgFileioRemove MsgFileioRemove
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgFileioWriteReq MsgFileioWriteReq
n Msg
m) = MsgFileioWriteReq -> Msg -> SBPMsg
SBPMsgFileioWriteReq MsgFileioWriteReq
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgFileioWriteResp MsgFileioWriteResp
n Msg
m) = MsgFileioWriteResp -> Msg -> SBPMsg
SBPMsgFileioWriteResp MsgFileioWriteResp
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgFlashDone MsgFlashDone
n Msg
m) = MsgFlashDone -> Msg -> SBPMsg
SBPMsgFlashDone MsgFlashDone
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgFlashErase MsgFlashErase
n Msg
m) = MsgFlashErase -> Msg -> SBPMsg
SBPMsgFlashErase MsgFlashErase
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgFlashProgram MsgFlashProgram
n Msg
m) = MsgFlashProgram -> Msg -> SBPMsg
SBPMsgFlashProgram MsgFlashProgram
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgFlashReadReq MsgFlashReadReq
n Msg
m) = MsgFlashReadReq -> Msg -> SBPMsg
SBPMsgFlashReadReq MsgFlashReadReq
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgFlashReadResp MsgFlashReadResp
n Msg
m) = MsgFlashReadResp -> Msg -> SBPMsg
SBPMsgFlashReadResp MsgFlashReadResp
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgFrontEndGain MsgFrontEndGain
n Msg
m) = MsgFrontEndGain -> Msg -> SBPMsg
SBPMsgFrontEndGain MsgFrontEndGain
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgFwd MsgFwd
n Msg
m) = MsgFwd -> Msg -> SBPMsg
SBPMsgFwd MsgFwd
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgGloBiases MsgGloBiases
n Msg
m) = MsgGloBiases -> Msg -> SBPMsg
SBPMsgGloBiases MsgGloBiases
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgGnssCapb MsgGnssCapb
n Msg
m) = MsgGnssCapb -> Msg -> SBPMsg
SBPMsgGnssCapb MsgGnssCapb
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgGnssTimeOffset MsgGnssTimeOffset
n Msg
m) = MsgGnssTimeOffset -> Msg -> SBPMsg
SBPMsgGnssTimeOffset MsgGnssTimeOffset
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgGpsTime MsgGpsTime
n Msg
m) = MsgGpsTime -> Msg -> SBPMsg
SBPMsgGpsTime MsgGpsTime
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgGpsTimeDepA MsgGpsTimeDepA
n Msg
m) = MsgGpsTimeDepA -> Msg -> SBPMsg
SBPMsgGpsTimeDepA MsgGpsTimeDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgGpsTimeGnss MsgGpsTimeGnss
n Msg
m) = MsgGpsTimeGnss -> Msg -> SBPMsg
SBPMsgGpsTimeGnss MsgGpsTimeGnss
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgGroupDelay MsgGroupDelay
n Msg
m) = MsgGroupDelay -> Msg -> SBPMsg
SBPMsgGroupDelay MsgGroupDelay
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgGroupDelayDepA MsgGroupDelayDepA
n Msg
m) = MsgGroupDelayDepA -> Msg -> SBPMsg
SBPMsgGroupDelayDepA MsgGroupDelayDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgGroupDelayDepB MsgGroupDelayDepB
n Msg
m) = MsgGroupDelayDepB -> Msg -> SBPMsg
SBPMsgGroupDelayDepB MsgGroupDelayDepB
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgGroupMeta MsgGroupMeta
n Msg
m) = MsgGroupMeta -> Msg -> SBPMsg
SBPMsgGroupMeta MsgGroupMeta
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgHeartbeat MsgHeartbeat
n Msg
m) = MsgHeartbeat -> Msg -> SBPMsg
SBPMsgHeartbeat MsgHeartbeat
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgIarState MsgIarState
n Msg
m) = MsgIarState -> Msg -> SBPMsg
SBPMsgIarState MsgIarState
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgImuAux MsgImuAux
n Msg
m) = MsgImuAux -> Msg -> SBPMsg
SBPMsgImuAux MsgImuAux
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgImuRaw MsgImuRaw
n Msg
m) = MsgImuRaw -> Msg -> SBPMsg
SBPMsgImuRaw MsgImuRaw
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgInitBaseDep MsgInitBaseDep
n Msg
m) = MsgInitBaseDep -> Msg -> SBPMsg
SBPMsgInitBaseDep MsgInitBaseDep
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgInsStatus MsgInsStatus
n Msg
m) = MsgInsStatus -> Msg -> SBPMsg
SBPMsgInsStatus MsgInsStatus
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgInsUpdates MsgInsUpdates
n Msg
m) = MsgInsUpdates -> Msg -> SBPMsg
SBPMsgInsUpdates MsgInsUpdates
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgIono MsgIono
n Msg
m) = MsgIono -> Msg -> SBPMsg
SBPMsgIono MsgIono
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgLinuxCpuState MsgLinuxCpuState
n Msg
m) = MsgLinuxCpuState -> Msg -> SBPMsg
SBPMsgLinuxCpuState MsgLinuxCpuState
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgLinuxCpuStateDepA MsgLinuxCpuStateDepA
n Msg
m) = MsgLinuxCpuStateDepA -> Msg -> SBPMsg
SBPMsgLinuxCpuStateDepA MsgLinuxCpuStateDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgLinuxMemState MsgLinuxMemState
n Msg
m) = MsgLinuxMemState -> Msg -> SBPMsg
SBPMsgLinuxMemState MsgLinuxMemState
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgLinuxMemStateDepA MsgLinuxMemStateDepA
n Msg
m) = MsgLinuxMemStateDepA -> Msg -> SBPMsg
SBPMsgLinuxMemStateDepA MsgLinuxMemStateDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgLinuxProcessFdCount MsgLinuxProcessFdCount
n Msg
m) = MsgLinuxProcessFdCount -> Msg -> SBPMsg
SBPMsgLinuxProcessFdCount MsgLinuxProcessFdCount
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgLinuxProcessFdSummary MsgLinuxProcessFdSummary
n Msg
m) = MsgLinuxProcessFdSummary -> Msg -> SBPMsg
SBPMsgLinuxProcessFdSummary MsgLinuxProcessFdSummary
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgLinuxProcessSocketCounts MsgLinuxProcessSocketCounts
n Msg
m) = MsgLinuxProcessSocketCounts -> Msg -> SBPMsg
SBPMsgLinuxProcessSocketCounts MsgLinuxProcessSocketCounts
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgLinuxProcessSocketQueues MsgLinuxProcessSocketQueues
n Msg
m) = MsgLinuxProcessSocketQueues -> Msg -> SBPMsg
SBPMsgLinuxProcessSocketQueues MsgLinuxProcessSocketQueues
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgLinuxSocketUsage MsgLinuxSocketUsage
n Msg
m) = MsgLinuxSocketUsage -> Msg -> SBPMsg
SBPMsgLinuxSocketUsage MsgLinuxSocketUsage
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgLinuxSysState MsgLinuxSysState
n Msg
m) = MsgLinuxSysState -> Msg -> SBPMsg
SBPMsgLinuxSysState MsgLinuxSysState
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgLinuxSysStateDepA MsgLinuxSysStateDepA
n Msg
m) = MsgLinuxSysStateDepA -> Msg -> SBPMsg
SBPMsgLinuxSysStateDepA MsgLinuxSysStateDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgLog MsgLog
n Msg
m) = MsgLog -> Msg -> SBPMsg
SBPMsgLog MsgLog
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgM25FlashWriteStatus MsgM25FlashWriteStatus
n Msg
m) = MsgM25FlashWriteStatus -> Msg -> SBPMsg
SBPMsgM25FlashWriteStatus MsgM25FlashWriteStatus
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgMagRaw MsgMagRaw
n Msg
m) = MsgMagRaw -> Msg -> SBPMsg
SBPMsgMagRaw MsgMagRaw
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgMaskSatellite MsgMaskSatellite
n Msg
m) = MsgMaskSatellite -> Msg -> SBPMsg
SBPMsgMaskSatellite MsgMaskSatellite
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgMaskSatelliteDep MsgMaskSatelliteDep
n Msg
m) = MsgMaskSatelliteDep -> Msg -> SBPMsg
SBPMsgMaskSatelliteDep MsgMaskSatelliteDep
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgMeasurementState MsgMeasurementState
n Msg
m) = MsgMeasurementState -> Msg -> SBPMsg
SBPMsgMeasurementState MsgMeasurementState
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgNapDeviceDnaReq MsgNapDeviceDnaReq
n Msg
m) = MsgNapDeviceDnaReq -> Msg -> SBPMsg
SBPMsgNapDeviceDnaReq MsgNapDeviceDnaReq
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgNapDeviceDnaResp MsgNapDeviceDnaResp
n Msg
m) = MsgNapDeviceDnaResp -> Msg -> SBPMsg
SBPMsgNapDeviceDnaResp MsgNapDeviceDnaResp
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgNdbEvent MsgNdbEvent
n Msg
m) = MsgNdbEvent -> Msg -> SBPMsg
SBPMsgNdbEvent MsgNdbEvent
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgNetworkBandwidthUsage MsgNetworkBandwidthUsage
n Msg
m) = MsgNetworkBandwidthUsage -> Msg -> SBPMsg
SBPMsgNetworkBandwidthUsage MsgNetworkBandwidthUsage
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgNetworkStateReq MsgNetworkStateReq
n Msg
m) = MsgNetworkStateReq -> Msg -> SBPMsg
SBPMsgNetworkStateReq MsgNetworkStateReq
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgNetworkStateResp MsgNetworkStateResp
n Msg
m) = MsgNetworkStateResp -> Msg -> SBPMsg
SBPMsgNetworkStateResp MsgNetworkStateResp
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgObs MsgObs
n Msg
m) = MsgObs -> Msg -> SBPMsg
SBPMsgObs MsgObs
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgObsDepA MsgObsDepA
n Msg
m) = MsgObsDepA -> Msg -> SBPMsg
SBPMsgObsDepA MsgObsDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgObsDepB MsgObsDepB
n Msg
m) = MsgObsDepB -> Msg -> SBPMsg
SBPMsgObsDepB MsgObsDepB
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgObsDepC MsgObsDepC
n Msg
m) = MsgObsDepC -> Msg -> SBPMsg
SBPMsgObsDepC MsgObsDepC
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgOdometry MsgOdometry
n Msg
m) = MsgOdometry -> Msg -> SBPMsg
SBPMsgOdometry MsgOdometry
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgOrientEuler MsgOrientEuler
n Msg
m) = MsgOrientEuler -> Msg -> SBPMsg
SBPMsgOrientEuler MsgOrientEuler
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgOrientQuat MsgOrientQuat
n Msg
m) = MsgOrientQuat -> Msg -> SBPMsg
SBPMsgOrientQuat MsgOrientQuat
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgOsr MsgOsr
n Msg
m) = MsgOsr -> Msg -> SBPMsg
SBPMsgOsr MsgOsr
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgPosEcef MsgPosEcef
n Msg
m) = MsgPosEcef -> Msg -> SBPMsg
SBPMsgPosEcef MsgPosEcef
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgPosEcefCov MsgPosEcefCov
n Msg
m) = MsgPosEcefCov -> Msg -> SBPMsg
SBPMsgPosEcefCov MsgPosEcefCov
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgPosEcefCovGnss MsgPosEcefCovGnss
n Msg
m) = MsgPosEcefCovGnss -> Msg -> SBPMsg
SBPMsgPosEcefCovGnss MsgPosEcefCovGnss
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgPosEcefDepA MsgPosEcefDepA
n Msg
m) = MsgPosEcefDepA -> Msg -> SBPMsg
SBPMsgPosEcefDepA MsgPosEcefDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgPosEcefGnss MsgPosEcefGnss
n Msg
m) = MsgPosEcefGnss -> Msg -> SBPMsg
SBPMsgPosEcefGnss MsgPosEcefGnss
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgPosLlh MsgPosLlh
n Msg
m) = MsgPosLlh -> Msg -> SBPMsg
SBPMsgPosLlh MsgPosLlh
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgPosLlhAcc MsgPosLlhAcc
n Msg
m) = MsgPosLlhAcc -> Msg -> SBPMsg
SBPMsgPosLlhAcc MsgPosLlhAcc
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgPosLlhCov MsgPosLlhCov
n Msg
m) = MsgPosLlhCov -> Msg -> SBPMsg
SBPMsgPosLlhCov MsgPosLlhCov
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgPosLlhCovGnss MsgPosLlhCovGnss
n Msg
m) = MsgPosLlhCovGnss -> Msg -> SBPMsg
SBPMsgPosLlhCovGnss MsgPosLlhCovGnss
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgPosLlhDepA MsgPosLlhDepA
n Msg
m) = MsgPosLlhDepA -> Msg -> SBPMsg
SBPMsgPosLlhDepA MsgPosLlhDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgPosLlhGnss MsgPosLlhGnss
n Msg
m) = MsgPosLlhGnss -> Msg -> SBPMsg
SBPMsgPosLlhGnss MsgPosLlhGnss
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgPpsTime MsgPpsTime
n Msg
m) = MsgPpsTime -> Msg -> SBPMsg
SBPMsgPpsTime MsgPpsTime
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgPrintDep MsgPrintDep
n Msg
m) = MsgPrintDep -> Msg -> SBPMsg
SBPMsgPrintDep MsgPrintDep
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgProtectionLevel MsgProtectionLevel
n Msg
m) = MsgProtectionLevel -> Msg -> SBPMsg
SBPMsgProtectionLevel MsgProtectionLevel
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgProtectionLevelDepA MsgProtectionLevelDepA
n Msg
m) = MsgProtectionLevelDepA -> Msg -> SBPMsg
SBPMsgProtectionLevelDepA MsgProtectionLevelDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgReferenceFrameParam MsgReferenceFrameParam
n Msg
m) = MsgReferenceFrameParam -> Msg -> SBPMsg
SBPMsgReferenceFrameParam MsgReferenceFrameParam
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgReset MsgReset
n Msg
m) = MsgReset -> Msg -> SBPMsg
SBPMsgReset MsgReset
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgResetDep MsgResetDep
n Msg
m) = MsgResetDep -> Msg -> SBPMsg
SBPMsgResetDep MsgResetDep
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgResetFilters MsgResetFilters
n Msg
m) = MsgResetFilters -> Msg -> SBPMsg
SBPMsgResetFilters MsgResetFilters
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSbasRaw MsgSbasRaw
n Msg
m) = MsgSbasRaw -> Msg -> SBPMsg
SBPMsgSbasRaw MsgSbasRaw
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSensorAidEvent MsgSensorAidEvent
n Msg
m) = MsgSensorAidEvent -> Msg -> SBPMsg
SBPMsgSensorAidEvent MsgSensorAidEvent
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSetTime MsgSetTime
n Msg
m) = MsgSetTime -> Msg -> SBPMsg
SBPMsgSetTime MsgSetTime
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSettingsReadByIndexDone MsgSettingsReadByIndexDone
n Msg
m) = MsgSettingsReadByIndexDone -> Msg -> SBPMsg
SBPMsgSettingsReadByIndexDone MsgSettingsReadByIndexDone
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSettingsReadByIndexReq MsgSettingsReadByIndexReq
n Msg
m) = MsgSettingsReadByIndexReq -> Msg -> SBPMsg
SBPMsgSettingsReadByIndexReq MsgSettingsReadByIndexReq
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSettingsReadByIndexResp MsgSettingsReadByIndexResp
n Msg
m) = MsgSettingsReadByIndexResp -> Msg -> SBPMsg
SBPMsgSettingsReadByIndexResp MsgSettingsReadByIndexResp
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSettingsReadReq MsgSettingsReadReq
n Msg
m) = MsgSettingsReadReq -> Msg -> SBPMsg
SBPMsgSettingsReadReq MsgSettingsReadReq
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSettingsReadResp MsgSettingsReadResp
n Msg
m) = MsgSettingsReadResp -> Msg -> SBPMsg
SBPMsgSettingsReadResp MsgSettingsReadResp
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSettingsRegister MsgSettingsRegister
n Msg
m) = MsgSettingsRegister -> Msg -> SBPMsg
SBPMsgSettingsRegister MsgSettingsRegister
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSettingsRegisterResp MsgSettingsRegisterResp
n Msg
m) = MsgSettingsRegisterResp -> Msg -> SBPMsg
SBPMsgSettingsRegisterResp MsgSettingsRegisterResp
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSettingsSave MsgSettingsSave
n Msg
m) = MsgSettingsSave -> Msg -> SBPMsg
SBPMsgSettingsSave MsgSettingsSave
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSettingsWrite MsgSettingsWrite
n Msg
m) = MsgSettingsWrite -> Msg -> SBPMsg
SBPMsgSettingsWrite MsgSettingsWrite
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSettingsWriteResp MsgSettingsWriteResp
n Msg
m) = MsgSettingsWriteResp -> Msg -> SBPMsg
SBPMsgSettingsWriteResp MsgSettingsWriteResp
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSolnMeta MsgSolnMeta
n Msg
m) = MsgSolnMeta -> Msg -> SBPMsg
SBPMsgSolnMeta MsgSolnMeta
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSolnMetaDepA MsgSolnMetaDepA
n Msg
m) = MsgSolnMetaDepA -> Msg -> SBPMsg
SBPMsgSolnMetaDepA MsgSolnMetaDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSpecan MsgSpecan
n Msg
m) = MsgSpecan -> Msg -> SBPMsg
SBPMsgSpecan MsgSpecan
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSpecanDep MsgSpecanDep
n Msg
m) = MsgSpecanDep -> Msg -> SBPMsg
SBPMsgSpecanDep MsgSpecanDep
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrCodeBiases MsgSsrCodeBiases
n Msg
m) = MsgSsrCodeBiases -> Msg -> SBPMsg
SBPMsgSsrCodeBiases MsgSsrCodeBiases
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrCodePhaseBiasesBounds MsgSsrCodePhaseBiasesBounds
n Msg
m) = MsgSsrCodePhaseBiasesBounds -> Msg -> SBPMsg
SBPMsgSsrCodePhaseBiasesBounds MsgSsrCodePhaseBiasesBounds
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrFlagHighLevel MsgSsrFlagHighLevel
n Msg
m) = MsgSsrFlagHighLevel -> Msg -> SBPMsg
SBPMsgSsrFlagHighLevel MsgSsrFlagHighLevel
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrFlagIonoGridPointSatLos MsgSsrFlagIonoGridPointSatLos
n Msg
m) = MsgSsrFlagIonoGridPointSatLos -> Msg -> SBPMsg
SBPMsgSsrFlagIonoGridPointSatLos MsgSsrFlagIonoGridPointSatLos
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrFlagIonoGridPoints MsgSsrFlagIonoGridPoints
n Msg
m) = MsgSsrFlagIonoGridPoints -> Msg -> SBPMsg
SBPMsgSsrFlagIonoGridPoints MsgSsrFlagIonoGridPoints
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrFlagIonoTileSatLos MsgSsrFlagIonoTileSatLos
n Msg
m) = MsgSsrFlagIonoTileSatLos -> Msg -> SBPMsg
SBPMsgSsrFlagIonoTileSatLos MsgSsrFlagIonoTileSatLos
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrFlagSatellites MsgSsrFlagSatellites
n Msg
m) = MsgSsrFlagSatellites -> Msg -> SBPMsg
SBPMsgSsrFlagSatellites MsgSsrFlagSatellites
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrFlagTropoGridPoints MsgSsrFlagTropoGridPoints
n Msg
m) = MsgSsrFlagTropoGridPoints -> Msg -> SBPMsg
SBPMsgSsrFlagTropoGridPoints MsgSsrFlagTropoGridPoints
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrGridDefinitionDepA MsgSsrGridDefinitionDepA
n Msg
m) = MsgSsrGridDefinitionDepA -> Msg -> SBPMsg
SBPMsgSsrGridDefinitionDepA MsgSsrGridDefinitionDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrGriddedCorrection MsgSsrGriddedCorrection
n Msg
m) = MsgSsrGriddedCorrection -> Msg -> SBPMsg
SBPMsgSsrGriddedCorrection MsgSsrGriddedCorrection
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrGriddedCorrectionBounds MsgSsrGriddedCorrectionBounds
n Msg
m) = MsgSsrGriddedCorrectionBounds -> Msg -> SBPMsg
SBPMsgSsrGriddedCorrectionBounds MsgSsrGriddedCorrectionBounds
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrGriddedCorrectionDepA MsgSsrGriddedCorrectionDepA
n Msg
m) = MsgSsrGriddedCorrectionDepA -> Msg -> SBPMsg
SBPMsgSsrGriddedCorrectionDepA MsgSsrGriddedCorrectionDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrGriddedCorrectionNoStdDepA MsgSsrGriddedCorrectionNoStdDepA
n Msg
m) = MsgSsrGriddedCorrectionNoStdDepA -> Msg -> SBPMsg
SBPMsgSsrGriddedCorrectionNoStdDepA MsgSsrGriddedCorrectionNoStdDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrOrbitClock MsgSsrOrbitClock
n Msg
m) = MsgSsrOrbitClock -> Msg -> SBPMsg
SBPMsgSsrOrbitClock MsgSsrOrbitClock
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrOrbitClockBounds MsgSsrOrbitClockBounds
n Msg
m) = MsgSsrOrbitClockBounds -> Msg -> SBPMsg
SBPMsgSsrOrbitClockBounds MsgSsrOrbitClockBounds
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrOrbitClockBoundsDegradation MsgSsrOrbitClockBoundsDegradation
n Msg
m) = MsgSsrOrbitClockBoundsDegradation -> Msg -> SBPMsg
SBPMsgSsrOrbitClockBoundsDegradation MsgSsrOrbitClockBoundsDegradation
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrOrbitClockDepA MsgSsrOrbitClockDepA
n Msg
m) = MsgSsrOrbitClockDepA -> Msg -> SBPMsg
SBPMsgSsrOrbitClockDepA MsgSsrOrbitClockDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrPhaseBiases MsgSsrPhaseBiases
n Msg
m) = MsgSsrPhaseBiases -> Msg -> SBPMsg
SBPMsgSsrPhaseBiases MsgSsrPhaseBiases
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrSatelliteApc MsgSsrSatelliteApc
n Msg
m) = MsgSsrSatelliteApc -> Msg -> SBPMsg
SBPMsgSsrSatelliteApc MsgSsrSatelliteApc
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrStecCorrection MsgSsrStecCorrection
n Msg
m) = MsgSsrStecCorrection -> Msg -> SBPMsg
SBPMsgSsrStecCorrection MsgSsrStecCorrection
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrStecCorrectionDep MsgSsrStecCorrectionDep
n Msg
m) = MsgSsrStecCorrectionDep -> Msg -> SBPMsg
SBPMsgSsrStecCorrectionDep MsgSsrStecCorrectionDep
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrStecCorrectionDepA MsgSsrStecCorrectionDepA
n Msg
m) = MsgSsrStecCorrectionDepA -> Msg -> SBPMsg
SBPMsgSsrStecCorrectionDepA MsgSsrStecCorrectionDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrTileDefinition MsgSsrTileDefinition
n Msg
m) = MsgSsrTileDefinition -> Msg -> SBPMsg
SBPMsgSsrTileDefinition MsgSsrTileDefinition
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSsrTileDefinitionDep MsgSsrTileDefinitionDep
n Msg
m) = MsgSsrTileDefinitionDep -> Msg -> SBPMsg
SBPMsgSsrTileDefinitionDep MsgSsrTileDefinitionDep
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgStartup MsgStartup
n Msg
m) = MsgStartup -> Msg -> SBPMsg
SBPMsgStartup MsgStartup
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgStatusJournal MsgStatusJournal
n Msg
m) = MsgStatusJournal -> Msg -> SBPMsg
SBPMsgStatusJournal MsgStatusJournal
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgStatusReport MsgStatusReport
n Msg
m) = MsgStatusReport -> Msg -> SBPMsg
SBPMsgStatusReport MsgStatusReport
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgStmFlashLockSector MsgStmFlashLockSector
n Msg
m) = MsgStmFlashLockSector -> Msg -> SBPMsg
SBPMsgStmFlashLockSector MsgStmFlashLockSector
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgStmFlashUnlockSector MsgStmFlashUnlockSector
n Msg
m) = MsgStmFlashUnlockSector -> Msg -> SBPMsg
SBPMsgStmFlashUnlockSector MsgStmFlashUnlockSector
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgStmUniqueIdReq MsgStmUniqueIdReq
n Msg
m) = MsgStmUniqueIdReq -> Msg -> SBPMsg
SBPMsgStmUniqueIdReq MsgStmUniqueIdReq
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgStmUniqueIdResp MsgStmUniqueIdResp
n Msg
m) = MsgStmUniqueIdResp -> Msg -> SBPMsg
SBPMsgStmUniqueIdResp MsgStmUniqueIdResp
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSvAzEl MsgSvAzEl
n Msg
m) = MsgSvAzEl -> Msg -> SBPMsg
SBPMsgSvAzEl MsgSvAzEl
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgSvConfigurationGpsDep MsgSvConfigurationGpsDep
n Msg
m) = MsgSvConfigurationGpsDep -> Msg -> SBPMsg
SBPMsgSvConfigurationGpsDep MsgSvConfigurationGpsDep
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgThreadState MsgThreadState
n Msg
m) = MsgThreadState -> Msg -> SBPMsg
SBPMsgThreadState MsgThreadState
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgTrackingIq MsgTrackingIq
n Msg
m) = MsgTrackingIq -> Msg -> SBPMsg
SBPMsgTrackingIq MsgTrackingIq
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgTrackingIqDepA MsgTrackingIqDepA
n Msg
m) = MsgTrackingIqDepA -> Msg -> SBPMsg
SBPMsgTrackingIqDepA MsgTrackingIqDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgTrackingIqDepB MsgTrackingIqDepB
n Msg
m) = MsgTrackingIqDepB -> Msg -> SBPMsg
SBPMsgTrackingIqDepB MsgTrackingIqDepB
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgTrackingState MsgTrackingState
n Msg
m) = MsgTrackingState -> Msg -> SBPMsg
SBPMsgTrackingState MsgTrackingState
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgTrackingStateDepA MsgTrackingStateDepA
n Msg
m) = MsgTrackingStateDepA -> Msg -> SBPMsg
SBPMsgTrackingStateDepA MsgTrackingStateDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgTrackingStateDepB MsgTrackingStateDepB
n Msg
m) = MsgTrackingStateDepB -> Msg -> SBPMsg
SBPMsgTrackingStateDepB MsgTrackingStateDepB
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgTrackingStateDetailedDep MsgTrackingStateDetailedDep
n Msg
m) = MsgTrackingStateDetailedDep -> Msg -> SBPMsg
SBPMsgTrackingStateDetailedDep MsgTrackingStateDetailedDep
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgTrackingStateDetailedDepA MsgTrackingStateDetailedDepA
n Msg
m) = MsgTrackingStateDetailedDepA -> Msg -> SBPMsg
SBPMsgTrackingStateDetailedDepA MsgTrackingStateDetailedDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgUartState MsgUartState
n Msg
m) = MsgUartState -> Msg -> SBPMsg
SBPMsgUartState MsgUartState
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgUartStateDepa MsgUartStateDepa
n Msg
m) = MsgUartStateDepa -> Msg -> SBPMsg
SBPMsgUartStateDepa MsgUartStateDepa
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgUserData MsgUserData
n Msg
m) = MsgUserData -> Msg -> SBPMsg
SBPMsgUserData MsgUserData
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgUtcLeapSecond MsgUtcLeapSecond
n Msg
m) = MsgUtcLeapSecond -> Msg -> SBPMsg
SBPMsgUtcLeapSecond MsgUtcLeapSecond
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgUtcTime MsgUtcTime
n Msg
m) = MsgUtcTime -> Msg -> SBPMsg
SBPMsgUtcTime MsgUtcTime
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgUtcTimeGnss MsgUtcTimeGnss
n Msg
m) = MsgUtcTimeGnss -> Msg -> SBPMsg
SBPMsgUtcTimeGnss MsgUtcTimeGnss
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgVelBody MsgVelBody
n Msg
m) = MsgVelBody -> Msg -> SBPMsg
SBPMsgVelBody MsgVelBody
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgVelCog MsgVelCog
n Msg
m) = MsgVelCog -> Msg -> SBPMsg
SBPMsgVelCog MsgVelCog
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgVelEcef MsgVelEcef
n Msg
m) = MsgVelEcef -> Msg -> SBPMsg
SBPMsgVelEcef MsgVelEcef
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgVelEcefCov MsgVelEcefCov
n Msg
m) = MsgVelEcefCov -> Msg -> SBPMsg
SBPMsgVelEcefCov MsgVelEcefCov
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgVelEcefCovGnss MsgVelEcefCovGnss
n Msg
m) = MsgVelEcefCovGnss -> Msg -> SBPMsg
SBPMsgVelEcefCovGnss MsgVelEcefCovGnss
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgVelEcefDepA MsgVelEcefDepA
n Msg
m) = MsgVelEcefDepA -> Msg -> SBPMsg
SBPMsgVelEcefDepA MsgVelEcefDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgVelEcefGnss MsgVelEcefGnss
n Msg
m) = MsgVelEcefGnss -> Msg -> SBPMsg
SBPMsgVelEcefGnss MsgVelEcefGnss
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgVelNed MsgVelNed
n Msg
m) = MsgVelNed -> Msg -> SBPMsg
SBPMsgVelNed MsgVelNed
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgVelNedCov MsgVelNedCov
n Msg
m) = MsgVelNedCov -> Msg -> SBPMsg
SBPMsgVelNedCov MsgVelNedCov
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgVelNedCovGnss MsgVelNedCovGnss
n Msg
m) = MsgVelNedCovGnss -> Msg -> SBPMsg
SBPMsgVelNedCovGnss MsgVelNedCovGnss
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgVelNedDepA MsgVelNedDepA
n Msg
m) = MsgVelNedDepA -> Msg -> SBPMsg
SBPMsgVelNedDepA MsgVelNedDepA
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgVelNedGnss MsgVelNedGnss
n Msg
m) = MsgVelNedGnss -> Msg -> SBPMsg
SBPMsgVelNedGnss MsgVelNedGnss
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgWheeltick MsgWheeltick
n Msg
m) = MsgWheeltick -> Msg -> SBPMsg
SBPMsgWheeltick MsgWheeltick
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgUnknown Msg
m) = Msg -> SBPMsg
SBPMsgUnknown forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m
  msg Msg -> f Msg
f (SBPMsgBadCrc Msg
m) = Msg -> SBPMsg
SBPMsgBadCrc forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m