Copyright | Copyright (C) 2015-2018 Swift Navigation Inc. |
---|---|
License | LGPL-3 |
Maintainer | Swift Navigation <dev@swiftnav.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
SwiftNav.SBP.Ssr
Description
Precise State Space Representation (SSR) corrections format
Synopsis
- data CodeBiasesContent = CodeBiasesContent {}
- data PhaseBiasesContent = PhaseBiasesContent {}
- codeBiasesContent_code :: Lens' CodeBiasesContent Word8
- codeBiasesContent_value :: Lens' CodeBiasesContent Int16
- data STECHeader = STECHeader {}
- phaseBiasesContent_bias :: Lens' PhaseBiasesContent Int32
- phaseBiasesContent_code :: Lens' PhaseBiasesContent Word8
- phaseBiasesContent_discontinuity_counter :: Lens' PhaseBiasesContent Word8
- phaseBiasesContent_integer_indicator :: Lens' PhaseBiasesContent Word8
- phaseBiasesContent_widelane_integer_indicator :: Lens' PhaseBiasesContent Word8
- data GriddedCorrectionHeader = GriddedCorrectionHeader {}
- sTECHeader_iod_ssr :: Lens' STECHeader Word8
- sTECHeader_num_msgs :: Lens' STECHeader Word8
- sTECHeader_seq_num :: Lens' STECHeader Word8
- sTECHeader_ssr_update_interval :: Lens' STECHeader Word16
- sTECHeader_time :: Lens' STECHeader GpsTime
- data STECSatElement = STECSatElement {}
- griddedCorrectionHeader_iod_ssr :: Lens' GriddedCorrectionHeader Word8
- griddedCorrectionHeader_num_msgs :: Lens' GriddedCorrectionHeader Word16
- griddedCorrectionHeader_seq_num :: Lens' GriddedCorrectionHeader Word16
- griddedCorrectionHeader_ssr_update_interval :: Lens' GriddedCorrectionHeader Word16
- griddedCorrectionHeader_time :: Lens' GriddedCorrectionHeader GpsTime
- griddedCorrectionHeader_tropo_quality :: Lens' GriddedCorrectionHeader Word8
- data TroposphericDelayCorrection = TroposphericDelayCorrection {}
- sTECSatElement_stec_coeff :: Lens' STECSatElement [Int16]
- sTECSatElement_stec_quality_indicator :: Lens' STECSatElement Word8
- sTECSatElement_sv_id :: Lens' STECSatElement SvId
- data STECResidual = STECResidual {}
- troposphericDelayCorrection_hydro :: Lens' TroposphericDelayCorrection Int16
- troposphericDelayCorrection_wet :: Lens' TroposphericDelayCorrection Int8
- data GridElement = GridElement {}
- sTECResidual_residual :: Lens' STECResidual Int16
- sTECResidual_sv_id :: Lens' STECResidual SvId
- data GridDefinitionHeader = GridDefinitionHeader {}
- gridElement_STEC_residuals :: Lens' GridElement [STECResidual]
- gridElement_index :: Lens' GridElement Word16
- gridElement_tropo_delay_correction :: Lens' GridElement TroposphericDelayCorrection
- data MsgSsrOrbitClock = MsgSsrOrbitClock {
- _msgSsrOrbitClock_time :: !GpsTimeSec
- _msgSsrOrbitClock_sid :: !GnssSignal
- _msgSsrOrbitClock_update_interval :: !Word8
- _msgSsrOrbitClock_iod_ssr :: !Word8
- _msgSsrOrbitClock_iod :: !Word32
- _msgSsrOrbitClock_radial :: !Int32
- _msgSsrOrbitClock_along :: !Int32
- _msgSsrOrbitClock_cross :: !Int32
- _msgSsrOrbitClock_dot_radial :: !Int32
- _msgSsrOrbitClock_dot_along :: !Int32
- _msgSsrOrbitClock_dot_cross :: !Int32
- _msgSsrOrbitClock_c0 :: !Int32
- _msgSsrOrbitClock_c1 :: !Int32
- _msgSsrOrbitClock_c2 :: !Int32
- gridDefinitionHeader_area_width :: Lens' GridDefinitionHeader Word16
- gridDefinitionHeader_lat_nw_corner_enc :: Lens' GridDefinitionHeader Word16
- gridDefinitionHeader_lon_nw_corner_enc :: Lens' GridDefinitionHeader Word16
- gridDefinitionHeader_num_msgs :: Lens' GridDefinitionHeader Word8
- gridDefinitionHeader_region_size_inverse :: Lens' GridDefinitionHeader Word8
- gridDefinitionHeader_seq_num :: Lens' GridDefinitionHeader Word8
- msgSsrOrbitClock :: Word16
- data MsgSsrOrbitClockDepA = MsgSsrOrbitClockDepA {
- _msgSsrOrbitClockDepA_time :: !GpsTimeSec
- _msgSsrOrbitClockDepA_sid :: !GnssSignal
- _msgSsrOrbitClockDepA_update_interval :: !Word8
- _msgSsrOrbitClockDepA_iod_ssr :: !Word8
- _msgSsrOrbitClockDepA_iod :: !Word8
- _msgSsrOrbitClockDepA_radial :: !Int32
- _msgSsrOrbitClockDepA_along :: !Int32
- _msgSsrOrbitClockDepA_cross :: !Int32
- _msgSsrOrbitClockDepA_dot_radial :: !Int32
- _msgSsrOrbitClockDepA_dot_along :: !Int32
- _msgSsrOrbitClockDepA_dot_cross :: !Int32
- _msgSsrOrbitClockDepA_c0 :: !Int32
- _msgSsrOrbitClockDepA_c1 :: !Int32
- _msgSsrOrbitClockDepA_c2 :: !Int32
- msgSsrOrbitClock_along :: Lens' MsgSsrOrbitClock Int32
- msgSsrOrbitClock_c0 :: Lens' MsgSsrOrbitClock Int32
- msgSsrOrbitClock_c1 :: Lens' MsgSsrOrbitClock Int32
- msgSsrOrbitClock_c2 :: Lens' MsgSsrOrbitClock Int32
- msgSsrOrbitClock_cross :: Lens' MsgSsrOrbitClock Int32
- msgSsrOrbitClock_dot_along :: Lens' MsgSsrOrbitClock Int32
- msgSsrOrbitClock_dot_cross :: Lens' MsgSsrOrbitClock Int32
- msgSsrOrbitClock_dot_radial :: Lens' MsgSsrOrbitClock Int32
- msgSsrOrbitClock_iod :: Lens' MsgSsrOrbitClock Word32
- msgSsrOrbitClock_iod_ssr :: Lens' MsgSsrOrbitClock Word8
- msgSsrOrbitClock_radial :: Lens' MsgSsrOrbitClock Int32
- msgSsrOrbitClock_sid :: Lens' MsgSsrOrbitClock GnssSignal
- msgSsrOrbitClock_time :: Lens' MsgSsrOrbitClock GpsTimeSec
- msgSsrOrbitClock_update_interval :: Lens' MsgSsrOrbitClock Word8
- msgSsrOrbitClockDepA :: Word16
- data MsgSsrCodeBiases = MsgSsrCodeBiases {}
- msgSsrOrbitClockDepA_along :: Lens' MsgSsrOrbitClockDepA Int32
- msgSsrOrbitClockDepA_c0 :: Lens' MsgSsrOrbitClockDepA Int32
- msgSsrOrbitClockDepA_c1 :: Lens' MsgSsrOrbitClockDepA Int32
- msgSsrOrbitClockDepA_c2 :: Lens' MsgSsrOrbitClockDepA Int32
- msgSsrOrbitClockDepA_cross :: Lens' MsgSsrOrbitClockDepA Int32
- msgSsrOrbitClockDepA_dot_along :: Lens' MsgSsrOrbitClockDepA Int32
- msgSsrOrbitClockDepA_dot_cross :: Lens' MsgSsrOrbitClockDepA Int32
- msgSsrOrbitClockDepA_dot_radial :: Lens' MsgSsrOrbitClockDepA Int32
- msgSsrOrbitClockDepA_iod :: Lens' MsgSsrOrbitClockDepA Word8
- msgSsrOrbitClockDepA_iod_ssr :: Lens' MsgSsrOrbitClockDepA Word8
- msgSsrOrbitClockDepA_radial :: Lens' MsgSsrOrbitClockDepA Int32
- msgSsrOrbitClockDepA_sid :: Lens' MsgSsrOrbitClockDepA GnssSignal
- msgSsrOrbitClockDepA_time :: Lens' MsgSsrOrbitClockDepA GpsTimeSec
- msgSsrOrbitClockDepA_update_interval :: Lens' MsgSsrOrbitClockDepA Word8
- msgSsrCodeBiases :: Word16
- data MsgSsrPhaseBiases = MsgSsrPhaseBiases {
- _msgSsrPhaseBiases_time :: !GpsTimeSec
- _msgSsrPhaseBiases_sid :: !GnssSignal
- _msgSsrPhaseBiases_update_interval :: !Word8
- _msgSsrPhaseBiases_iod_ssr :: !Word8
- _msgSsrPhaseBiases_dispersive_bias :: !Word8
- _msgSsrPhaseBiases_mw_consistency :: !Word8
- _msgSsrPhaseBiases_yaw :: !Word16
- _msgSsrPhaseBiases_yaw_rate :: !Int8
- _msgSsrPhaseBiases_biases :: ![PhaseBiasesContent]
- msgSsrCodeBiases_biases :: Lens' MsgSsrCodeBiases [CodeBiasesContent]
- msgSsrCodeBiases_iod_ssr :: Lens' MsgSsrCodeBiases Word8
- msgSsrCodeBiases_sid :: Lens' MsgSsrCodeBiases GnssSignal
- msgSsrCodeBiases_time :: Lens' MsgSsrCodeBiases GpsTimeSec
- msgSsrCodeBiases_update_interval :: Lens' MsgSsrCodeBiases Word8
- msgSsrPhaseBiases :: Word16
- data MsgSsrStecCorrection = MsgSsrStecCorrection {}
- msgSsrPhaseBiases_biases :: Lens' MsgSsrPhaseBiases [PhaseBiasesContent]
- msgSsrPhaseBiases_dispersive_bias :: Lens' MsgSsrPhaseBiases Word8
- msgSsrPhaseBiases_iod_ssr :: Lens' MsgSsrPhaseBiases Word8
- msgSsrPhaseBiases_mw_consistency :: Lens' MsgSsrPhaseBiases Word8
- msgSsrPhaseBiases_sid :: Lens' MsgSsrPhaseBiases GnssSignal
- msgSsrPhaseBiases_time :: Lens' MsgSsrPhaseBiases GpsTimeSec
- msgSsrPhaseBiases_update_interval :: Lens' MsgSsrPhaseBiases Word8
- msgSsrPhaseBiases_yaw :: Lens' MsgSsrPhaseBiases Word16
- msgSsrPhaseBiases_yaw_rate :: Lens' MsgSsrPhaseBiases Int8
- msgSsrStecCorrection :: Word16
- data MsgSsrGriddedCorrection = MsgSsrGriddedCorrection {}
- msgSsrStecCorrection_header :: Lens' MsgSsrStecCorrection STECHeader
- msgSsrStecCorrection_stec_sat_list :: Lens' MsgSsrStecCorrection [STECSatElement]
- msgSsrGriddedCorrection :: Word16
- data MsgSsrGridDefinition = MsgSsrGridDefinition {}
- msgSsrGriddedCorrection_element :: Lens' MsgSsrGriddedCorrection GridElement
- msgSsrGriddedCorrection_header :: Lens' MsgSsrGriddedCorrection GriddedCorrectionHeader
- msgSsrGridDefinition :: Word16
- msgSsrGridDefinition_header :: Lens' MsgSsrGridDefinition GridDefinitionHeader
- msgSsrGridDefinition_rle_list :: Lens' MsgSsrGridDefinition [Word8]
Documentation
data CodeBiasesContent Source #
CodeBiasesContent.
Code biases are to be added to pseudorange. The corrections are conform with typical RTCMv3 MT1059 and 1065.
Constructors
CodeBiasesContent | |
Fields
|
Instances
data PhaseBiasesContent Source #
PhaseBiasesContent.
Phase biases are to be added to carrier phase measurements. The corrections are conform with typical RTCMv3 MT1059 and 1065.
Constructors
PhaseBiasesContent | |
Fields
|
Instances
data STECHeader Source #
STECHeader.
A full set of STEC information will likely span multiple SBP messages, since SBP message a limited to 255 bytes. The header is used to tie multiple SBP messages into a sequence.
Constructors
STECHeader | |
Fields
|
Instances
Eq STECHeader Source # | |
Defined in SwiftNav.SBP.Ssr | |
Read STECHeader Source # | |
Defined in SwiftNav.SBP.Ssr Methods readsPrec :: Int -> ReadS STECHeader # readList :: ReadS [STECHeader] # readPrec :: ReadPrec STECHeader # readListPrec :: ReadPrec [STECHeader] # | |
Show STECHeader Source # | |
Defined in SwiftNav.SBP.Ssr Methods showsPrec :: Int -> STECHeader -> ShowS # show :: STECHeader -> String # showList :: [STECHeader] -> ShowS # | |
ToJSON STECHeader Source # | |
Defined in SwiftNav.SBP.Ssr Methods toJSON :: STECHeader -> Value # toEncoding :: STECHeader -> Encoding # toJSONList :: [STECHeader] -> Value # toEncodingList :: [STECHeader] -> Encoding # | |
FromJSON STECHeader Source # | |
Defined in SwiftNav.SBP.Ssr | |
Binary STECHeader Source # | |
Defined in SwiftNav.SBP.Ssr |
data GriddedCorrectionHeader Source #
GriddedCorrectionHeader.
The 3GPP message contains nested variable length arrays which are not suppported in SBP, so each grid point will be identified by the index.
Constructors
GriddedCorrectionHeader | |
Fields
|
Instances
data STECSatElement Source #
STECSatElement.
STEC for the given satellite.
Constructors
STECSatElement | |
Fields
|
Instances
data TroposphericDelayCorrection Source #
TroposphericDelayCorrection.
Contains wet vertical and hydrostatic vertical delay
Constructors
TroposphericDelayCorrection | |
Fields
|
Instances
data STECResidual Source #
STECResidual.
STEC residual
Constructors
STECResidual | |
Fields
|
Instances
Eq STECResidual Source # | |
Defined in SwiftNav.SBP.Ssr | |
Read STECResidual Source # | |
Defined in SwiftNav.SBP.Ssr Methods readsPrec :: Int -> ReadS STECResidual # readList :: ReadS [STECResidual] # | |
Show STECResidual Source # | |
Defined in SwiftNav.SBP.Ssr Methods showsPrec :: Int -> STECResidual -> ShowS # show :: STECResidual -> String # showList :: [STECResidual] -> ShowS # | |
ToJSON STECResidual Source # | |
Defined in SwiftNav.SBP.Ssr Methods toJSON :: STECResidual -> Value # toEncoding :: STECResidual -> Encoding # toJSONList :: [STECResidual] -> Value # toEncodingList :: [STECResidual] -> Encoding # | |
FromJSON STECResidual Source # | |
Defined in SwiftNav.SBP.Ssr | |
Binary STECResidual Source # | |
Defined in SwiftNav.SBP.Ssr |
data GridElement Source #
GridElement.
Contains one tropo datum, plus STEC residuals for each space vehicle
Constructors
GridElement | |
Fields
|
Instances
Eq GridElement Source # | |
Defined in SwiftNav.SBP.Ssr | |
Read GridElement Source # | |
Defined in SwiftNav.SBP.Ssr Methods readsPrec :: Int -> ReadS GridElement # readList :: ReadS [GridElement] # readPrec :: ReadPrec GridElement # readListPrec :: ReadPrec [GridElement] # | |
Show GridElement Source # | |
Defined in SwiftNav.SBP.Ssr Methods showsPrec :: Int -> GridElement -> ShowS # show :: GridElement -> String # showList :: [GridElement] -> ShowS # | |
ToJSON GridElement Source # | |
Defined in SwiftNav.SBP.Ssr Methods toJSON :: GridElement -> Value # toEncoding :: GridElement -> Encoding # toJSONList :: [GridElement] -> Value # toEncodingList :: [GridElement] -> Encoding # | |
FromJSON GridElement Source # | |
Defined in SwiftNav.SBP.Ssr | |
Binary GridElement Source # | |
Defined in SwiftNav.SBP.Ssr |
data GridDefinitionHeader Source #
GridDefinitionHeader.
Defines the grid for STEC and tropo grid messages. Also includes an RLE encoded validity list.
Constructors
GridDefinitionHeader | |
Fields
|
Instances
data MsgSsrOrbitClock Source #
SBP class for message MSG_SSR_ORBIT_CLOCK (0x05DD).
The precise orbit and clock correction message is to be applied as a delta correction to broadcast ephemeris and is typically an equivalent to the 1060 and 1066 RTCM message types
Constructors
MsgSsrOrbitClock | |
Fields
|
Instances
data MsgSsrOrbitClockDepA Source #
SBP class for message MSG_SSR_ORBIT_CLOCK_DEP_A (0x05DC).
The precise orbit and clock correction message is to be applied as a delta correction to broadcast ephemeris and is typically an equivalent to the 1060 and 1066 RTCM message types
Constructors
MsgSsrOrbitClockDepA | |
Fields
|
Instances
data MsgSsrCodeBiases Source #
SBP class for message MSG_SSR_CODE_BIASES (0x05E1).
The precise code biases message is to be added to the pseudorange of the corresponding signal to get corrected pseudorange. It is typically an equivalent to the 1059 and 1065 RTCM message types
Constructors
MsgSsrCodeBiases | |
Fields
|
Instances
data MsgSsrPhaseBiases Source #
SBP class for message MSG_SSR_PHASE_BIASES (0x05E6).
The precise phase biases message contains the biases to be added to the carrier phase of the corresponding signal to get corrected carrier phase measurement, as well as the satellite yaw angle to be applied to compute the phase wind-up correction. It is typically an equivalent to the 1265 RTCM message types
Constructors
MsgSsrPhaseBiases | |
Fields
|
Instances
data MsgSsrStecCorrection Source #
SBP class for message MSG_SSR_STEC_CORRECTION (0x05EB).
The STEC per space vehicle, given as polynomial approximation for a given grid. This should be combined with SSR-GriddedCorrection message to get the state space representation of the atmospheric delay.
Constructors
MsgSsrStecCorrection | |
Fields
|
Instances
data MsgSsrGriddedCorrection Source #
SBP class for message MSG_SSR_GRIDDED_CORRECTION (0x05F0).
STEC residuals are per space vehicle, tropo is not.
Constructors
MsgSsrGriddedCorrection | |
Fields
|
Instances
data MsgSsrGridDefinition Source #
SBP class for message MSG_SSR_GRID_DEFINITION (0x05F5).
Definition of the grid for STEC and tropo messages
Constructors
MsgSsrGridDefinition | |
Fields
|