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

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

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

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

instance HasMsg SBPMsg where
  msg :: (Msg -> f Msg) -> SBPMsg -> f SBPMsg
msg Msg -> f Msg
f (SBPMsgAcqResult MsgAcqResult
n Msg
m) = MsgAcqResult -> Msg -> SBPMsg
SBPMsgAcqResult MsgAcqResult
n (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
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 (Msg -> SBPMsg) -> f Msg -> f SBPMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Msg -> f Msg
f Msg
m