Copyright | Copyright (C) 2015-2021 Swift Navigation Inc. |
---|---|
License | MIT |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
< System health, configuration, and diagnostic messages specific to the Piksi L1 receiver, including a variety of legacy messages that may no longer be used. >
Synopsis
- data MsgAlmanac = MsgAlmanac
- data MsgSetTime = MsgSetTime
- data MsgReset = MsgReset {}
- data MsgResetDep = MsgResetDep
- data MsgCwResults = MsgCwResults
- data MsgCwStart = MsgCwStart
- data MsgResetFilters = MsgResetFilters {}
- data MsgInitBaseDep = MsgInitBaseDep
- data MsgThreadState = MsgThreadState {}
- data UARTChannel = UARTChannel {}
- data Period = Period {
- _period_avg :: !Int32
- _period_pmin :: !Int32
- _period_pmax :: !Int32
- _period_current :: !Int32
- data Latency = Latency {
- _latency_avg :: !Int32
- _latency_lmin :: !Int32
- _latency_lmax :: !Int32
- _latency_current :: !Int32
- data MsgUartState = MsgUartState {}
- data MsgUartStateDepa = MsgUartStateDepa {}
- data MsgIarState = MsgIarState {}
- data MsgMaskSatellite = MsgMaskSatellite {}
- data MsgMaskSatelliteDep = MsgMaskSatelliteDep {}
- data MsgDeviceMonitor = MsgDeviceMonitor {}
- data MsgCommandReq = MsgCommandReq {}
- data MsgCommandResp = MsgCommandResp {}
- data MsgCommandOutput = MsgCommandOutput {}
- data MsgNetworkStateReq = MsgNetworkStateReq
- data MsgNetworkStateResp = MsgNetworkStateResp {
- _msgNetworkStateResp_ipv4_address :: ![Word8]
- _msgNetworkStateResp_ipv4_mask_size :: !Word8
- _msgNetworkStateResp_ipv6_address :: ![Word8]
- _msgNetworkStateResp_ipv6_mask_size :: !Word8
- _msgNetworkStateResp_rx_bytes :: !Word32
- _msgNetworkStateResp_tx_bytes :: !Word32
- _msgNetworkStateResp_interface_name :: !Text
- _msgNetworkStateResp_flags :: !Word32
- data NetworkUsage = NetworkUsage {}
- data MsgNetworkBandwidthUsage = MsgNetworkBandwidthUsage {}
- data MsgCellModemStatus = MsgCellModemStatus {}
- data MsgSpecanDep = MsgSpecanDep {}
- data MsgSpecan = MsgSpecan {}
- data MsgFrontEndGain = MsgFrontEndGain {
- _msgFrontEndGain_rf_gain :: ![Int8]
- _msgFrontEndGain_if_gain :: ![Int8]
- msgAlmanac :: Word16
- msgSetTime :: Word16
- msgReset :: Word16
- msgResetDep :: Word16
- msgCwResults :: Word16
- msgCwStart :: Word16
- msgResetFilters :: Word16
- msgInitBaseDep :: Word16
- msgThreadState :: Word16
- msgUartState :: Word16
- msgUartStateDepa :: Word16
- msgIarState :: Word16
- msgMaskSatellite :: Word16
- msgMaskSatelliteDep :: Word16
- msgDeviceMonitor :: Word16
- msgCommandReq :: Word16
- msgCommandResp :: Word16
- msgCommandOutput :: Word16
- msgNetworkStateReq :: Word16
- msgNetworkStateResp :: Word16
- msgNetworkBandwidthUsage :: Word16
- msgCellModemStatus :: Word16
- msgSpecanDep :: Word16
- msgSpecan :: Word16
- msgFrontEndGain :: Word16
- msgReset_flags :: Iso' MsgReset Word32
- msgResetFilters_filter :: Iso' MsgResetFilters Word8
- msgThreadState_cpu :: Lens' MsgThreadState Word16
- msgThreadState_name :: Lens' MsgThreadState Text
- msgThreadState_stack_free :: Lens' MsgThreadState Word32
- uARTChannel_crc_error_count :: Lens' UARTChannel Word16
- uARTChannel_io_error_count :: Lens' UARTChannel Word16
- uARTChannel_rx_buffer_level :: Lens' UARTChannel Word8
- uARTChannel_rx_throughput :: Lens' UARTChannel Float
- uARTChannel_tx_buffer_level :: Lens' UARTChannel Word8
- uARTChannel_tx_throughput :: Lens' UARTChannel Float
- period_avg :: Lens' Period Int32
- period_current :: Lens' Period Int32
- period_pmax :: Lens' Period Int32
- period_pmin :: Lens' Period Int32
- latency_avg :: Lens' Latency Int32
- latency_current :: Lens' Latency Int32
- latency_lmax :: Lens' Latency Int32
- latency_lmin :: Lens' Latency Int32
- msgUartState_latency :: Lens' MsgUartState Latency
- msgUartState_obs_period :: Lens' MsgUartState Period
- msgUartState_uart_a :: Lens' MsgUartState UARTChannel
- msgUartState_uart_b :: Lens' MsgUartState UARTChannel
- msgUartState_uart_ftdi :: Lens' MsgUartState UARTChannel
- msgUartStateDepa_latency :: Lens' MsgUartStateDepa Latency
- msgUartStateDepa_uart_a :: Lens' MsgUartStateDepa UARTChannel
- msgUartStateDepa_uart_b :: Lens' MsgUartStateDepa UARTChannel
- msgUartStateDepa_uart_ftdi :: Lens' MsgUartStateDepa UARTChannel
- msgIarState_num_hyps :: Iso' MsgIarState Word32
- msgMaskSatellite_mask :: Lens' MsgMaskSatellite Word8
- msgMaskSatellite_sid :: Lens' MsgMaskSatellite GnssSignal
- msgMaskSatelliteDep_mask :: Lens' MsgMaskSatelliteDep Word8
- msgMaskSatelliteDep_sid :: Lens' MsgMaskSatelliteDep GnssSignalDep
- msgDeviceMonitor_cpu_temperature :: Lens' MsgDeviceMonitor Int16
- msgDeviceMonitor_cpu_vaux :: Lens' MsgDeviceMonitor Int16
- msgDeviceMonitor_cpu_vint :: Lens' MsgDeviceMonitor Int16
- msgDeviceMonitor_dev_vin :: Lens' MsgDeviceMonitor Int16
- msgDeviceMonitor_fe_temperature :: Lens' MsgDeviceMonitor Int16
- msgCommandReq_command :: Lens' MsgCommandReq Text
- msgCommandReq_sequence :: Lens' MsgCommandReq Word32
- msgCommandResp_code :: Lens' MsgCommandResp Int32
- msgCommandResp_sequence :: Lens' MsgCommandResp Word32
- msgCommandOutput_line :: Lens' MsgCommandOutput Text
- msgCommandOutput_sequence :: Lens' MsgCommandOutput Word32
- msgNetworkStateResp_flags :: Lens' MsgNetworkStateResp Word32
- msgNetworkStateResp_interface_name :: Lens' MsgNetworkStateResp Text
- msgNetworkStateResp_ipv4_address :: Lens' MsgNetworkStateResp [Word8]
- msgNetworkStateResp_ipv4_mask_size :: Lens' MsgNetworkStateResp Word8
- msgNetworkStateResp_ipv6_address :: Lens' MsgNetworkStateResp [Word8]
- msgNetworkStateResp_ipv6_mask_size :: Lens' MsgNetworkStateResp Word8
- msgNetworkStateResp_rx_bytes :: Lens' MsgNetworkStateResp Word32
- msgNetworkStateResp_tx_bytes :: Lens' MsgNetworkStateResp Word32
- networkUsage_duration :: Lens' NetworkUsage Word64
- networkUsage_interface_name :: Lens' NetworkUsage Text
- networkUsage_rx_bytes :: Lens' NetworkUsage Word32
- networkUsage_total_bytes :: Lens' NetworkUsage Word64
- networkUsage_tx_bytes :: Lens' NetworkUsage Word32
- msgNetworkBandwidthUsage_interfaces :: Iso' MsgNetworkBandwidthUsage [NetworkUsage]
- msgCellModemStatus_reserved :: Lens' MsgCellModemStatus [Word8]
- msgCellModemStatus_signal_error_rate :: Lens' MsgCellModemStatus Float
- msgCellModemStatus_signal_strength :: Lens' MsgCellModemStatus Int8
- msgSpecanDep_amplitude_ref :: Lens' MsgSpecanDep Float
- msgSpecanDep_amplitude_unit :: Lens' MsgSpecanDep Float
- msgSpecanDep_amplitude_value :: Lens' MsgSpecanDep [Word8]
- msgSpecanDep_channel_tag :: Lens' MsgSpecanDep Word16
- msgSpecanDep_freq_ref :: Lens' MsgSpecanDep Float
- msgSpecanDep_freq_step :: Lens' MsgSpecanDep Float
- msgSpecanDep_t :: Lens' MsgSpecanDep GpsTimeDep
- msgSpecan_amplitude_ref :: Lens' MsgSpecan Float
- msgSpecan_amplitude_unit :: Lens' MsgSpecan Float
- msgSpecan_amplitude_value :: Lens' MsgSpecan [Word8]
- msgSpecan_channel_tag :: Lens' MsgSpecan Word16
- msgSpecan_freq_ref :: Lens' MsgSpecan Float
- msgSpecan_freq_step :: Lens' MsgSpecan Float
- msgSpecan_t :: Lens' MsgSpecan GpsTime
- msgFrontEndGain_if_gain :: Lens' MsgFrontEndGain [Int8]
- msgFrontEndGain_rf_gain :: Lens' MsgFrontEndGain [Int8]
Documentation
data MsgAlmanac Source #
SBP class for message MSG_ALMANAC (0x0069).
This is a legacy message for sending and loading a satellite alamanac onto the Piksi's flash memory from the host.
Instances
FromJSON MsgAlmanac Source # | |
Defined in SwiftNav.SBP.Piksi parseJSON :: Value -> Parser MsgAlmanac # parseJSONList :: Value -> Parser [MsgAlmanac] # | |
ToJSON MsgAlmanac Source # | |
Defined in SwiftNav.SBP.Piksi toJSON :: MsgAlmanac -> Value # toEncoding :: MsgAlmanac -> Encoding # toJSONList :: [MsgAlmanac] -> Value # toEncodingList :: [MsgAlmanac] -> Encoding # omitField :: MsgAlmanac -> Bool # | |
Read MsgAlmanac Source # | |
Defined in SwiftNav.SBP.Piksi readsPrec :: Int -> ReadS MsgAlmanac # readList :: ReadS [MsgAlmanac] # readPrec :: ReadPrec MsgAlmanac # readListPrec :: ReadPrec [MsgAlmanac] # | |
Show MsgAlmanac Source # | |
Defined in SwiftNav.SBP.Piksi showsPrec :: Int -> MsgAlmanac -> ShowS # show :: MsgAlmanac -> String # showList :: [MsgAlmanac] -> ShowS # | |
Binary MsgAlmanac Source # | |
Defined in SwiftNav.SBP.Piksi | |
Eq MsgAlmanac Source # | |
Defined in SwiftNav.SBP.Piksi (==) :: MsgAlmanac -> MsgAlmanac -> Bool # (/=) :: MsgAlmanac -> MsgAlmanac -> Bool # | |
ToSBP MsgAlmanac Source # | |
Defined in SwiftNav.SBP.Piksi |
data MsgSetTime Source #
SBP class for message MSG_SET_TIME (0x0068).
This message sets up timing functionality using a coarse GPS time estimate sent by the host.
Instances
FromJSON MsgSetTime Source # | |
Defined in SwiftNav.SBP.Piksi parseJSON :: Value -> Parser MsgSetTime # parseJSONList :: Value -> Parser [MsgSetTime] # | |
ToJSON MsgSetTime Source # | |
Defined in SwiftNav.SBP.Piksi toJSON :: MsgSetTime -> Value # toEncoding :: MsgSetTime -> Encoding # toJSONList :: [MsgSetTime] -> Value # toEncodingList :: [MsgSetTime] -> Encoding # omitField :: MsgSetTime -> Bool # | |
Read MsgSetTime Source # | |
Defined in SwiftNav.SBP.Piksi readsPrec :: Int -> ReadS MsgSetTime # readList :: ReadS [MsgSetTime] # readPrec :: ReadPrec MsgSetTime # readListPrec :: ReadPrec [MsgSetTime] # | |
Show MsgSetTime Source # | |
Defined in SwiftNav.SBP.Piksi showsPrec :: Int -> MsgSetTime -> ShowS # show :: MsgSetTime -> String # showList :: [MsgSetTime] -> ShowS # | |
Binary MsgSetTime Source # | |
Defined in SwiftNav.SBP.Piksi | |
Eq MsgSetTime Source # | |
Defined in SwiftNav.SBP.Piksi (==) :: MsgSetTime -> MsgSetTime -> Bool # (/=) :: MsgSetTime -> MsgSetTime -> Bool # | |
ToSBP MsgSetTime Source # | |
Defined in SwiftNav.SBP.Piksi |
SBP class for message MSG_RESET (0x00B6).
This message from the host resets the Piksi back into the bootloader.
MsgReset | |
|
data MsgResetDep Source #
SBP class for message MSG_RESET_DEP (0x00B2).
Deprecated.
Instances
data MsgCwResults Source #
SBP class for message MSG_CW_RESULTS (0x00C0).
This is an unused legacy message for result reporting from the CW interference channel on the SwiftNAP. This message will be removed in a future release.
Instances
FromJSON MsgCwResults Source # | |
Defined in SwiftNav.SBP.Piksi parseJSON :: Value -> Parser MsgCwResults # parseJSONList :: Value -> Parser [MsgCwResults] # | |
ToJSON MsgCwResults Source # | |
Defined in SwiftNav.SBP.Piksi toJSON :: MsgCwResults -> Value # toEncoding :: MsgCwResults -> Encoding # toJSONList :: [MsgCwResults] -> Value # toEncodingList :: [MsgCwResults] -> Encoding # omitField :: MsgCwResults -> Bool # | |
Read MsgCwResults Source # | |
Defined in SwiftNav.SBP.Piksi readsPrec :: Int -> ReadS MsgCwResults # readList :: ReadS [MsgCwResults] # | |
Show MsgCwResults Source # | |
Defined in SwiftNav.SBP.Piksi showsPrec :: Int -> MsgCwResults -> ShowS # show :: MsgCwResults -> String # showList :: [MsgCwResults] -> ShowS # | |
Binary MsgCwResults Source # | |
Defined in SwiftNav.SBP.Piksi | |
Eq MsgCwResults Source # | |
Defined in SwiftNav.SBP.Piksi (==) :: MsgCwResults -> MsgCwResults -> Bool # (/=) :: MsgCwResults -> MsgCwResults -> Bool # | |
ToSBP MsgCwResults Source # | |
Defined in SwiftNav.SBP.Piksi |
data MsgCwStart Source #
SBP class for message MSG_CW_START (0x00C1).
This is an unused legacy message from the host for starting the CW interference channel on the SwiftNAP. This message will be removed in a future release.
Instances
FromJSON MsgCwStart Source # | |
Defined in SwiftNav.SBP.Piksi parseJSON :: Value -> Parser MsgCwStart # parseJSONList :: Value -> Parser [MsgCwStart] # | |
ToJSON MsgCwStart Source # | |
Defined in SwiftNav.SBP.Piksi toJSON :: MsgCwStart -> Value # toEncoding :: MsgCwStart -> Encoding # toJSONList :: [MsgCwStart] -> Value # toEncodingList :: [MsgCwStart] -> Encoding # omitField :: MsgCwStart -> Bool # | |
Read MsgCwStart Source # | |
Defined in SwiftNav.SBP.Piksi readsPrec :: Int -> ReadS MsgCwStart # readList :: ReadS [MsgCwStart] # readPrec :: ReadPrec MsgCwStart # readListPrec :: ReadPrec [MsgCwStart] # | |
Show MsgCwStart Source # | |
Defined in SwiftNav.SBP.Piksi showsPrec :: Int -> MsgCwStart -> ShowS # show :: MsgCwStart -> String # showList :: [MsgCwStart] -> ShowS # | |
Binary MsgCwStart Source # | |
Defined in SwiftNav.SBP.Piksi | |
Eq MsgCwStart Source # | |
Defined in SwiftNav.SBP.Piksi (==) :: MsgCwStart -> MsgCwStart -> Bool # (/=) :: MsgCwStart -> MsgCwStart -> Bool # | |
ToSBP MsgCwStart Source # | |
Defined in SwiftNav.SBP.Piksi |
data MsgResetFilters Source #
SBP class for message MSG_RESET_FILTERS (0x0022).
This message resets either the DGNSS Kalman filters or Integer Ambiguity Resolution (IAR) process.
MsgResetFilters | |
|
Instances
FromJSON MsgResetFilters Source # | |
Defined in SwiftNav.SBP.Piksi parseJSON :: Value -> Parser MsgResetFilters # parseJSONList :: Value -> Parser [MsgResetFilters] # | |
ToJSON MsgResetFilters Source # | |
Defined in SwiftNav.SBP.Piksi toJSON :: MsgResetFilters -> Value # toEncoding :: MsgResetFilters -> Encoding # toJSONList :: [MsgResetFilters] -> Value # toEncodingList :: [MsgResetFilters] -> Encoding # omitField :: MsgResetFilters -> Bool # | |
Read MsgResetFilters Source # | |
Defined in SwiftNav.SBP.Piksi | |
Show MsgResetFilters Source # | |
Defined in SwiftNav.SBP.Piksi showsPrec :: Int -> MsgResetFilters -> ShowS # show :: MsgResetFilters -> String # showList :: [MsgResetFilters] -> ShowS # | |
Binary MsgResetFilters Source # | |
Defined in SwiftNav.SBP.Piksi | |
Eq MsgResetFilters Source # | |
Defined in SwiftNav.SBP.Piksi (==) :: MsgResetFilters -> MsgResetFilters -> Bool # (/=) :: MsgResetFilters -> MsgResetFilters -> Bool # | |
ToSBP MsgResetFilters Source # | |
Defined in SwiftNav.SBP.Piksi |
data MsgInitBaseDep Source #
SBP class for message MSG_INIT_BASE_DEP (0x0023).
Deprecated.
Instances
data MsgThreadState Source #
SBP class for message MSG_THREAD_STATE (0x0017).
The thread usage message from the device reports real-time operating system (RTOS) thread usage statistics for the named thread. The reported percentage values must be normalized.
MsgThreadState | |
|
Instances
data UARTChannel Source #
UARTChannel.
Throughput, utilization, and error counts on the RX/TX buffers of this UART channel. The reported percentage values must be normalized.
UARTChannel | |
|
Instances
FromJSON UARTChannel Source # | |
Defined in SwiftNav.SBP.Piksi parseJSON :: Value -> Parser UARTChannel # parseJSONList :: Value -> Parser [UARTChannel] # | |
ToJSON UARTChannel Source # | |
Defined in SwiftNav.SBP.Piksi toJSON :: UARTChannel -> Value # toEncoding :: UARTChannel -> Encoding # toJSONList :: [UARTChannel] -> Value # toEncodingList :: [UARTChannel] -> Encoding # omitField :: UARTChannel -> Bool # | |
Read UARTChannel Source # | |
Defined in SwiftNav.SBP.Piksi readsPrec :: Int -> ReadS UARTChannel # readList :: ReadS [UARTChannel] # readPrec :: ReadPrec UARTChannel # readListPrec :: ReadPrec [UARTChannel] # | |
Show UARTChannel Source # | |
Defined in SwiftNav.SBP.Piksi showsPrec :: Int -> UARTChannel -> ShowS # show :: UARTChannel -> String # showList :: [UARTChannel] -> ShowS # | |
Binary UARTChannel Source # | |
Defined in SwiftNav.SBP.Piksi | |
Eq UARTChannel Source # | |
Defined in SwiftNav.SBP.Piksi (==) :: UARTChannel -> UARTChannel -> Bool # (/=) :: UARTChannel -> UARTChannel -> Bool # |
Period.
Statistics on the period of observations received from the base station. As complete observation sets are received, their time of reception is compared with the prior set''s time of reception. This measurement provides a proxy for link quality as incomplete or missing sets will increase the period. Long periods can cause momentary RTK solution outages.
Period | |
|
Latency.
Statistics on the latency of observations received from the base station. As observation packets are received their GPS time is compared to the current GPS time calculated locally by the receiver to give a precise measurement of the end-to-end communication latency in the system.
Latency | |
|
data MsgUartState Source #
SBP class for message MSG_UART_STATE (0x001D).
The UART message reports data latency and throughput of the UART channels providing SBP I/O. On the default Piksi configuration, UARTs A and B are used for telemetry radios, but can also be host access ports for embedded hosts, or other interfaces in future. The reported percentage values must be normalized. Observations latency and period can be used to assess the health of the differential corrections link. Latency provides the timeliness of received base observations while the period indicates their likelihood of transmission.
MsgUartState | |
|
Instances
FromJSON MsgUartState Source # | |
Defined in SwiftNav.SBP.Piksi parseJSON :: Value -> Parser MsgUartState # parseJSONList :: Value -> Parser [MsgUartState] # | |
ToJSON MsgUartState Source # | |
Defined in SwiftNav.SBP.Piksi toJSON :: MsgUartState -> Value # toEncoding :: MsgUartState -> Encoding # toJSONList :: [MsgUartState] -> Value # toEncodingList :: [MsgUartState] -> Encoding # omitField :: MsgUartState -> Bool # | |
Read MsgUartState Source # | |
Defined in SwiftNav.SBP.Piksi readsPrec :: Int -> ReadS MsgUartState # readList :: ReadS [MsgUartState] # | |
Show MsgUartState Source # | |
Defined in SwiftNav.SBP.Piksi showsPrec :: Int -> MsgUartState -> ShowS # show :: MsgUartState -> String # showList :: [MsgUartState] -> ShowS # | |
Binary MsgUartState Source # | |
Defined in SwiftNav.SBP.Piksi | |
Eq MsgUartState Source # | |
Defined in SwiftNav.SBP.Piksi (==) :: MsgUartState -> MsgUartState -> Bool # (/=) :: MsgUartState -> MsgUartState -> Bool # | |
ToSBP MsgUartState Source # | |
Defined in SwiftNav.SBP.Piksi |
data MsgUartStateDepa Source #
SBP class for message MSG_UART_STATE_DEPA (0x0018).
Deprecated.
MsgUartStateDepa | |
|
Instances
FromJSON MsgUartStateDepa Source # | |
Defined in SwiftNav.SBP.Piksi parseJSON :: Value -> Parser MsgUartStateDepa # parseJSONList :: Value -> Parser [MsgUartStateDepa] # | |
ToJSON MsgUartStateDepa Source # | |
Defined in SwiftNav.SBP.Piksi toJSON :: MsgUartStateDepa -> Value # toEncoding :: MsgUartStateDepa -> Encoding # toJSONList :: [MsgUartStateDepa] -> Value # toEncodingList :: [MsgUartStateDepa] -> Encoding # omitField :: MsgUartStateDepa -> Bool # | |
Read MsgUartStateDepa Source # | |
Defined in SwiftNav.SBP.Piksi | |
Show MsgUartStateDepa Source # | |
Defined in SwiftNav.SBP.Piksi showsPrec :: Int -> MsgUartStateDepa -> ShowS # show :: MsgUartStateDepa -> String # showList :: [MsgUartStateDepa] -> ShowS # | |
Binary MsgUartStateDepa Source # | |
Defined in SwiftNav.SBP.Piksi | |
Eq MsgUartStateDepa Source # | |
Defined in SwiftNav.SBP.Piksi (==) :: MsgUartStateDepa -> MsgUartStateDepa -> Bool # (/=) :: MsgUartStateDepa -> MsgUartStateDepa -> Bool # | |
ToSBP MsgUartStateDepa Source # | |
Defined in SwiftNav.SBP.Piksi |
data MsgIarState Source #
SBP class for message MSG_IAR_STATE (0x0019).
This message reports the state of the Integer Ambiguity Resolution (IAR) process, which resolves unknown integer ambiguities from double-differenced carrier-phase measurements from satellite observations.
MsgIarState | |
|
Instances
data MsgMaskSatellite Source #
SBP class for message MSG_MASK_SATELLITE (0x002B).
This message allows setting a mask to prevent a particular satellite from being used in various Piksi subsystems.
MsgMaskSatellite | |
|
Instances
FromJSON MsgMaskSatellite Source # | |
Defined in SwiftNav.SBP.Piksi parseJSON :: Value -> Parser MsgMaskSatellite # parseJSONList :: Value -> Parser [MsgMaskSatellite] # | |
ToJSON MsgMaskSatellite Source # | |
Defined in SwiftNav.SBP.Piksi toJSON :: MsgMaskSatellite -> Value # toEncoding :: MsgMaskSatellite -> Encoding # toJSONList :: [MsgMaskSatellite] -> Value # toEncodingList :: [MsgMaskSatellite] -> Encoding # omitField :: MsgMaskSatellite -> Bool # | |
Read MsgMaskSatellite Source # | |
Defined in SwiftNav.SBP.Piksi | |
Show MsgMaskSatellite Source # | |
Defined in SwiftNav.SBP.Piksi showsPrec :: Int -> MsgMaskSatellite -> ShowS # show :: MsgMaskSatellite -> String # showList :: [MsgMaskSatellite] -> ShowS # | |
Binary MsgMaskSatellite Source # | |
Defined in SwiftNav.SBP.Piksi | |
Eq MsgMaskSatellite Source # | |
Defined in SwiftNav.SBP.Piksi (==) :: MsgMaskSatellite -> MsgMaskSatellite -> Bool # (/=) :: MsgMaskSatellite -> MsgMaskSatellite -> Bool # | |
ToSBP MsgMaskSatellite Source # | |
Defined in SwiftNav.SBP.Piksi |
data MsgMaskSatelliteDep Source #
SBP class for message MSG_MASK_SATELLITE_DEP (0x001B).
Deprecated.
MsgMaskSatelliteDep | |
|
Instances
data MsgDeviceMonitor Source #
SBP class for message MSG_DEVICE_MONITOR (0x00B5).
This message contains temperature and voltage level measurements from the processor's monitoring system and the RF frontend die temperature if available.
MsgDeviceMonitor | |
|
Instances
FromJSON MsgDeviceMonitor Source # | |
Defined in SwiftNav.SBP.Piksi parseJSON :: Value -> Parser MsgDeviceMonitor # parseJSONList :: Value -> Parser [MsgDeviceMonitor] # | |
ToJSON MsgDeviceMonitor Source # | |
Defined in SwiftNav.SBP.Piksi toJSON :: MsgDeviceMonitor -> Value # toEncoding :: MsgDeviceMonitor -> Encoding # toJSONList :: [MsgDeviceMonitor] -> Value # toEncodingList :: [MsgDeviceMonitor] -> Encoding # omitField :: MsgDeviceMonitor -> Bool # | |
Read MsgDeviceMonitor Source # | |
Defined in SwiftNav.SBP.Piksi | |
Show MsgDeviceMonitor Source # | |
Defined in SwiftNav.SBP.Piksi showsPrec :: Int -> MsgDeviceMonitor -> ShowS # show :: MsgDeviceMonitor -> String # showList :: [MsgDeviceMonitor] -> ShowS # | |
Binary MsgDeviceMonitor Source # | |
Defined in SwiftNav.SBP.Piksi | |
Eq MsgDeviceMonitor Source # | |
Defined in SwiftNav.SBP.Piksi (==) :: MsgDeviceMonitor -> MsgDeviceMonitor -> Bool # (/=) :: MsgDeviceMonitor -> MsgDeviceMonitor -> Bool # | |
ToSBP MsgDeviceMonitor Source # | |
Defined in SwiftNav.SBP.Piksi |
data MsgCommandReq Source #
SBP class for message MSG_COMMAND_REQ (0x00B8).
Request the recipient to execute an command. Output will be sent in MSG_LOG messages, and the exit code will be returned with MSG_COMMAND_RESP.
MsgCommandReq | |
|
Instances
FromJSON MsgCommandReq Source # | |
Defined in SwiftNav.SBP.Piksi parseJSON :: Value -> Parser MsgCommandReq # parseJSONList :: Value -> Parser [MsgCommandReq] # | |
ToJSON MsgCommandReq Source # | |
Defined in SwiftNav.SBP.Piksi toJSON :: MsgCommandReq -> Value # toEncoding :: MsgCommandReq -> Encoding # toJSONList :: [MsgCommandReq] -> Value # toEncodingList :: [MsgCommandReq] -> Encoding # omitField :: MsgCommandReq -> Bool # | |
Read MsgCommandReq Source # | |
Defined in SwiftNav.SBP.Piksi readsPrec :: Int -> ReadS MsgCommandReq # readList :: ReadS [MsgCommandReq] # | |
Show MsgCommandReq Source # | |
Defined in SwiftNav.SBP.Piksi showsPrec :: Int -> MsgCommandReq -> ShowS # show :: MsgCommandReq -> String # showList :: [MsgCommandReq] -> ShowS # | |
Binary MsgCommandReq Source # | |
Defined in SwiftNav.SBP.Piksi | |
Eq MsgCommandReq Source # | |
Defined in SwiftNav.SBP.Piksi (==) :: MsgCommandReq -> MsgCommandReq -> Bool # (/=) :: MsgCommandReq -> MsgCommandReq -> Bool # | |
ToSBP MsgCommandReq Source # | |
Defined in SwiftNav.SBP.Piksi |
data MsgCommandResp Source #
SBP class for message MSG_COMMAND_RESP (0x00B9).
The response to MSG_COMMAND_REQ with the return code of the command. A return code of zero indicates success.
MsgCommandResp | |
|
Instances
data MsgCommandOutput Source #
SBP class for message MSG_COMMAND_OUTPUT (0x00BC).
Returns the standard output and standard error of the command requested by MSG_COMMAND_REQ. The sequence number can be used to filter for filtering the correct command.
MsgCommandOutput | |
|
Instances
FromJSON MsgCommandOutput Source # | |
Defined in SwiftNav.SBP.Piksi parseJSON :: Value -> Parser MsgCommandOutput # parseJSONList :: Value -> Parser [MsgCommandOutput] # | |
ToJSON MsgCommandOutput Source # | |
Defined in SwiftNav.SBP.Piksi toJSON :: MsgCommandOutput -> Value # toEncoding :: MsgCommandOutput -> Encoding # toJSONList :: [MsgCommandOutput] -> Value # toEncodingList :: [MsgCommandOutput] -> Encoding # omitField :: MsgCommandOutput -> Bool # | |
Read MsgCommandOutput Source # | |
Defined in SwiftNav.SBP.Piksi | |
Show MsgCommandOutput Source # | |
Defined in SwiftNav.SBP.Piksi showsPrec :: Int -> MsgCommandOutput -> ShowS # show :: MsgCommandOutput -> String # showList :: [MsgCommandOutput] -> ShowS # | |
Binary MsgCommandOutput Source # | |
Defined in SwiftNav.SBP.Piksi | |
Eq MsgCommandOutput Source # | |
Defined in SwiftNav.SBP.Piksi (==) :: MsgCommandOutput -> MsgCommandOutput -> Bool # (/=) :: MsgCommandOutput -> MsgCommandOutput -> Bool # | |
ToSBP MsgCommandOutput Source # | |
Defined in SwiftNav.SBP.Piksi |
data MsgNetworkStateReq Source #
SBP class for message MSG_NETWORK_STATE_REQ (0x00BA).
Request state of Piksi network interfaces. Output will be sent in MSG_NETWORK_STATE_RESP messages.
Instances
data MsgNetworkStateResp Source #
SBP class for message MSG_NETWORK_STATE_RESP (0x00BB).
The state of a network interface on the Piksi. Data is made to reflect output of ifaddrs struct returned by getifaddrs in c.
MsgNetworkStateResp | |
|
Instances
data NetworkUsage Source #
NetworkUsage.
The bandwidth usage for each interface can be reported within this struct and utilize multiple fields to fully specify the type of traffic that is being tracked. As either the interval of collection or the collection time may vary, both a timestamp and period field is provided, though may not necessarily be populated with a value.
NetworkUsage | |
|
Instances
FromJSON NetworkUsage Source # | |
Defined in SwiftNav.SBP.Piksi parseJSON :: Value -> Parser NetworkUsage # parseJSONList :: Value -> Parser [NetworkUsage] # | |
ToJSON NetworkUsage Source # | |
Defined in SwiftNav.SBP.Piksi toJSON :: NetworkUsage -> Value # toEncoding :: NetworkUsage -> Encoding # toJSONList :: [NetworkUsage] -> Value # toEncodingList :: [NetworkUsage] -> Encoding # omitField :: NetworkUsage -> Bool # | |
Read NetworkUsage Source # | |
Defined in SwiftNav.SBP.Piksi readsPrec :: Int -> ReadS NetworkUsage # readList :: ReadS [NetworkUsage] # | |
Show NetworkUsage Source # | |
Defined in SwiftNav.SBP.Piksi showsPrec :: Int -> NetworkUsage -> ShowS # show :: NetworkUsage -> String # showList :: [NetworkUsage] -> ShowS # | |
Binary NetworkUsage Source # | |
Defined in SwiftNav.SBP.Piksi | |
Eq NetworkUsage Source # | |
Defined in SwiftNav.SBP.Piksi (==) :: NetworkUsage -> NetworkUsage -> Bool # (/=) :: NetworkUsage -> NetworkUsage -> Bool # |
data MsgNetworkBandwidthUsage Source #
SBP class for message MSG_NETWORK_BANDWIDTH_USAGE (0x00BD).
The bandwidth usage, a list of usage by interface.
MsgNetworkBandwidthUsage | |
|
Instances
FromJSON MsgNetworkBandwidthUsage Source # | |
Defined in SwiftNav.SBP.Piksi | |
ToJSON MsgNetworkBandwidthUsage Source # | |
Defined in SwiftNav.SBP.Piksi | |
Read MsgNetworkBandwidthUsage Source # | |
Show MsgNetworkBandwidthUsage Source # | |
Defined in SwiftNav.SBP.Piksi showsPrec :: Int -> MsgNetworkBandwidthUsage -> ShowS # show :: MsgNetworkBandwidthUsage -> String # showList :: [MsgNetworkBandwidthUsage] -> ShowS # | |
Binary MsgNetworkBandwidthUsage Source # | |
Defined in SwiftNav.SBP.Piksi put :: MsgNetworkBandwidthUsage -> Put # get :: Get MsgNetworkBandwidthUsage # putList :: [MsgNetworkBandwidthUsage] -> Put # | |
Eq MsgNetworkBandwidthUsage Source # | |
Defined in SwiftNav.SBP.Piksi | |
ToSBP MsgNetworkBandwidthUsage Source # | |
Defined in SwiftNav.SBP.Piksi |
data MsgCellModemStatus Source #
SBP class for message MSG_CELL_MODEM_STATUS (0x00BE).
If a cell modem is present on a piksi device, this message will be send periodically to update the host on the status of the modem and its various parameters.
MsgCellModemStatus | |
|
Instances
data MsgSpecanDep Source #
SBP class for message MSG_SPECAN_DEP (0x0050).
Deprecated.
MsgSpecanDep | |
|
Instances
FromJSON MsgSpecanDep Source # | |
Defined in SwiftNav.SBP.Piksi parseJSON :: Value -> Parser MsgSpecanDep # parseJSONList :: Value -> Parser [MsgSpecanDep] # | |
ToJSON MsgSpecanDep Source # | |
Defined in SwiftNav.SBP.Piksi toJSON :: MsgSpecanDep -> Value # toEncoding :: MsgSpecanDep -> Encoding # toJSONList :: [MsgSpecanDep] -> Value # toEncodingList :: [MsgSpecanDep] -> Encoding # omitField :: MsgSpecanDep -> Bool # | |
Read MsgSpecanDep Source # | |
Defined in SwiftNav.SBP.Piksi readsPrec :: Int -> ReadS MsgSpecanDep # readList :: ReadS [MsgSpecanDep] # | |
Show MsgSpecanDep Source # | |
Defined in SwiftNav.SBP.Piksi showsPrec :: Int -> MsgSpecanDep -> ShowS # show :: MsgSpecanDep -> String # showList :: [MsgSpecanDep] -> ShowS # | |
Binary MsgSpecanDep Source # | |
Defined in SwiftNav.SBP.Piksi | |
Eq MsgSpecanDep Source # | |
Defined in SwiftNav.SBP.Piksi (==) :: MsgSpecanDep -> MsgSpecanDep -> Bool # (/=) :: MsgSpecanDep -> MsgSpecanDep -> Bool # | |
ToSBP MsgSpecanDep Source # | |
Defined in SwiftNav.SBP.Piksi |
SBP class for message MSG_SPECAN (0x0051).
Spectrum analyzer packet.
MsgSpecan | |
|
data MsgFrontEndGain Source #
SBP class for message MSG_FRONT_END_GAIN (0x00BF).
This message describes the gain of each channel in the receiver frontend. Each gain is encoded as a non-dimensional percentage relative to the maximum range possible for the gain stage of the frontend. By convention, each gain array has 8 entries and the index of the array corresponding to the index of the rf channel in the frontend. A gain of 127 percent encodes that rf channel is not present in the hardware. A negative value implies an error for the particular gain stage as reported by the frontend.
MsgFrontEndGain | |
|
Instances
FromJSON MsgFrontEndGain Source # | |
Defined in SwiftNav.SBP.Piksi parseJSON :: Value -> Parser MsgFrontEndGain # parseJSONList :: Value -> Parser [MsgFrontEndGain] # | |
ToJSON MsgFrontEndGain Source # | |
Defined in SwiftNav.SBP.Piksi toJSON :: MsgFrontEndGain -> Value # toEncoding :: MsgFrontEndGain -> Encoding # toJSONList :: [MsgFrontEndGain] -> Value # toEncodingList :: [MsgFrontEndGain] -> Encoding # omitField :: MsgFrontEndGain -> Bool # | |
Read MsgFrontEndGain Source # | |
Defined in SwiftNav.SBP.Piksi | |
Show MsgFrontEndGain Source # | |
Defined in SwiftNav.SBP.Piksi showsPrec :: Int -> MsgFrontEndGain -> ShowS # show :: MsgFrontEndGain -> String # showList :: [MsgFrontEndGain] -> ShowS # | |
Binary MsgFrontEndGain Source # | |
Defined in SwiftNav.SBP.Piksi | |
Eq MsgFrontEndGain Source # | |
Defined in SwiftNav.SBP.Piksi (==) :: MsgFrontEndGain -> MsgFrontEndGain -> Bool # (/=) :: MsgFrontEndGain -> MsgFrontEndGain -> Bool # | |
ToSBP MsgFrontEndGain Source # | |
Defined in SwiftNav.SBP.Piksi |
msgAlmanac :: Word16 Source #
msgSetTime :: Word16 Source #
msgResetDep :: Word16 Source #
msgCwStart :: Word16 Source #
msgIarState :: Word16 Source #