Copyright | Copyright (C) 2015-2021 Swift Navigation Inc. |
---|---|
License | MIT |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
< 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 {
- _griddedCorrectionHeader_tile_set_id :: !Word16
- _griddedCorrectionHeader_tile_id :: !Word16
- _griddedCorrectionHeader_time :: !GpsTimeSec
- _griddedCorrectionHeader_num_msgs :: !Word16
- _griddedCorrectionHeader_seq_num :: !Word16
- _griddedCorrectionHeader_update_interval :: !Word8
- _griddedCorrectionHeader_iod_atmo :: !Word8
- _griddedCorrectionHeader_tropo_quality_indicator :: !Word8
- sTECHeader_iod_atmo :: Lens' STECHeader Word8
- sTECHeader_num_msgs :: Lens' STECHeader Word8
- sTECHeader_seq_num :: Lens' STECHeader Word8
- sTECHeader_tile_id :: Lens' STECHeader Word16
- sTECHeader_tile_set_id :: Lens' STECHeader Word16
- sTECHeader_time :: Lens' STECHeader GpsTimeSec
- sTECHeader_update_interval :: Lens' STECHeader Word8
- data STECSatElement = STECSatElement {}
- griddedCorrectionHeader_iod_atmo :: Lens' GriddedCorrectionHeader Word8
- griddedCorrectionHeader_num_msgs :: Lens' GriddedCorrectionHeader Word16
- griddedCorrectionHeader_seq_num :: Lens' GriddedCorrectionHeader Word16
- griddedCorrectionHeader_tile_id :: Lens' GriddedCorrectionHeader Word16
- griddedCorrectionHeader_tile_set_id :: Lens' GriddedCorrectionHeader Word16
- griddedCorrectionHeader_time :: Lens' GriddedCorrectionHeader GpsTimeSec
- griddedCorrectionHeader_tropo_quality_indicator :: Lens' GriddedCorrectionHeader Word8
- griddedCorrectionHeader_update_interval :: Lens' GriddedCorrectionHeader Word8
- data TroposphericDelayCorrectionNoStd = TroposphericDelayCorrectionNoStd {}
- sTECSatElement_stec_coeff :: Lens' STECSatElement [Int16]
- sTECSatElement_stec_quality_indicator :: Lens' STECSatElement Word8
- sTECSatElement_sv_id :: Lens' STECSatElement SvId
- data TroposphericDelayCorrection = TroposphericDelayCorrection {}
- troposphericDelayCorrectionNoStd_hydro :: Lens' TroposphericDelayCorrectionNoStd Int16
- troposphericDelayCorrectionNoStd_wet :: Lens' TroposphericDelayCorrectionNoStd Int8
- data STECResidualNoStd = STECResidualNoStd {}
- troposphericDelayCorrection_hydro :: Lens' TroposphericDelayCorrection Int16
- troposphericDelayCorrection_stddev :: Lens' TroposphericDelayCorrection Word8
- troposphericDelayCorrection_wet :: Lens' TroposphericDelayCorrection Int8
- data STECResidual = STECResidual {}
- sTECResidualNoStd_residual :: Lens' STECResidualNoStd Int16
- sTECResidualNoStd_sv_id :: Lens' STECResidualNoStd SvId
- 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
- sTECResidual_residual :: Lens' STECResidual Int16
- sTECResidual_stddev :: Lens' STECResidual Word8
- sTECResidual_sv_id :: Lens' STECResidual SvId
- msgSsrOrbitClock :: Word16
- data MsgSsrCodeBiases = MsgSsrCodeBiases {}
- 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
- 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 MsgSsrStecCorrectionDep = MsgSsrStecCorrectionDep {}
- 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
- msgSsrStecCorrectionDep :: Word16
- data BoundsHeader = BoundsHeader {}
- msgSsrStecCorrectionDep_header :: Lens' MsgSsrStecCorrectionDep STECHeader
- msgSsrStecCorrectionDep_stec_sat_list :: Lens' MsgSsrStecCorrectionDep [STECSatElement]
- data MsgSsrStecCorrection = MsgSsrStecCorrection {}
- boundsHeader_num_msgs :: Lens' BoundsHeader Word8
- boundsHeader_seq_num :: Lens' BoundsHeader Word8
- boundsHeader_sol_id :: Lens' BoundsHeader Word8
- boundsHeader_time :: Lens' BoundsHeader GpsTimeSec
- boundsHeader_update_interval :: Lens' BoundsHeader Word8
- msgSsrStecCorrection :: Word16
- data MsgSsrGriddedCorrection = MsgSsrGriddedCorrection {}
- msgSsrStecCorrection_header :: Lens' MsgSsrStecCorrection BoundsHeader
- msgSsrStecCorrection_n_sats :: Lens' MsgSsrStecCorrection Word8
- msgSsrStecCorrection_ssr_iod_atmo :: Lens' MsgSsrStecCorrection Word8
- msgSsrStecCorrection_stec_sat_list :: Lens' MsgSsrStecCorrection [STECSatElement]
- msgSsrStecCorrection_tile_id :: Lens' MsgSsrStecCorrection Word16
- msgSsrStecCorrection_tile_set_id :: Lens' MsgSsrStecCorrection Word16
- msgSsrGriddedCorrection :: Word16
- data STECSatElementIntegrity = STECSatElementIntegrity {}
- msgSsrGriddedCorrection_header :: Lens' MsgSsrGriddedCorrection GriddedCorrectionHeader
- msgSsrGriddedCorrection_index :: Lens' MsgSsrGriddedCorrection Word16
- msgSsrGriddedCorrection_stec_residuals :: Lens' MsgSsrGriddedCorrection [STECResidual]
- msgSsrGriddedCorrection_tropo_delay_correction :: Lens' MsgSsrGriddedCorrection TroposphericDelayCorrection
- data MsgSsrGriddedCorrectionBounds = MsgSsrGriddedCorrectionBounds {
- _msgSsrGriddedCorrectionBounds_header :: !BoundsHeader
- _msgSsrGriddedCorrectionBounds_ssr_iod_atmo :: !Word8
- _msgSsrGriddedCorrectionBounds_tile_set_id :: !Word16
- _msgSsrGriddedCorrectionBounds_tile_id :: !Word16
- _msgSsrGriddedCorrectionBounds_tropo_qi :: !Word8
- _msgSsrGriddedCorrectionBounds_grid_point_id :: !Word16
- _msgSsrGriddedCorrectionBounds_tropo_delay_correction :: !TroposphericDelayCorrection
- _msgSsrGriddedCorrectionBounds_tropo_v_hydro_bound_mu :: !Word8
- _msgSsrGriddedCorrectionBounds_tropo_v_hydro_bound_sig :: !Word8
- _msgSsrGriddedCorrectionBounds_tropo_v_wet_bound_mu :: !Word8
- _msgSsrGriddedCorrectionBounds_tropo_v_wet_bound_sig :: !Word8
- _msgSsrGriddedCorrectionBounds_n_sats :: !Word8
- _msgSsrGriddedCorrectionBounds_stec_sat_list :: ![STECSatElementIntegrity]
- sTECSatElementIntegrity_stec_bound_mu :: Lens' STECSatElementIntegrity Word8
- sTECSatElementIntegrity_stec_bound_mu_dot :: Lens' STECSatElementIntegrity Word8
- sTECSatElementIntegrity_stec_bound_sig :: Lens' STECSatElementIntegrity Word8
- sTECSatElementIntegrity_stec_bound_sig_dot :: Lens' STECSatElementIntegrity Word8
- sTECSatElementIntegrity_stec_residual :: Lens' STECSatElementIntegrity STECResidual
- msgSsrGriddedCorrectionBounds :: Word16
- data MsgSsrTileDefinitionDepA = MsgSsrTileDefinitionDepA {
- _msgSsrTileDefinitionDepA_tile_set_id :: !Word16
- _msgSsrTileDefinitionDepA_tile_id :: !Word16
- _msgSsrTileDefinitionDepA_corner_nw_lat :: !Int16
- _msgSsrTileDefinitionDepA_corner_nw_lon :: !Int16
- _msgSsrTileDefinitionDepA_spacing_lat :: !Word16
- _msgSsrTileDefinitionDepA_spacing_lon :: !Word16
- _msgSsrTileDefinitionDepA_rows :: !Word16
- _msgSsrTileDefinitionDepA_cols :: !Word16
- _msgSsrTileDefinitionDepA_bitmask :: !Word64
- msgSsrGriddedCorrectionBounds_grid_point_id :: Lens' MsgSsrGriddedCorrectionBounds Word16
- msgSsrGriddedCorrectionBounds_header :: Lens' MsgSsrGriddedCorrectionBounds BoundsHeader
- msgSsrGriddedCorrectionBounds_n_sats :: Lens' MsgSsrGriddedCorrectionBounds Word8
- msgSsrGriddedCorrectionBounds_ssr_iod_atmo :: Lens' MsgSsrGriddedCorrectionBounds Word8
- msgSsrGriddedCorrectionBounds_stec_sat_list :: Lens' MsgSsrGriddedCorrectionBounds [STECSatElementIntegrity]
- msgSsrGriddedCorrectionBounds_tile_id :: Lens' MsgSsrGriddedCorrectionBounds Word16
- msgSsrGriddedCorrectionBounds_tile_set_id :: Lens' MsgSsrGriddedCorrectionBounds Word16
- msgSsrGriddedCorrectionBounds_tropo_delay_correction :: Lens' MsgSsrGriddedCorrectionBounds TroposphericDelayCorrection
- msgSsrGriddedCorrectionBounds_tropo_qi :: Lens' MsgSsrGriddedCorrectionBounds Word8
- msgSsrGriddedCorrectionBounds_tropo_v_hydro_bound_mu :: Lens' MsgSsrGriddedCorrectionBounds Word8
- msgSsrGriddedCorrectionBounds_tropo_v_hydro_bound_sig :: Lens' MsgSsrGriddedCorrectionBounds Word8
- msgSsrGriddedCorrectionBounds_tropo_v_wet_bound_mu :: Lens' MsgSsrGriddedCorrectionBounds Word8
- msgSsrGriddedCorrectionBounds_tropo_v_wet_bound_sig :: Lens' MsgSsrGriddedCorrectionBounds Word8
- msgSsrTileDefinitionDepA :: Word16
- data MsgSsrTileDefinitionDepB = MsgSsrTileDefinitionDepB {
- _msgSsrTileDefinitionDepB_ssr_sol_id :: !Word8
- _msgSsrTileDefinitionDepB_tile_set_id :: !Word16
- _msgSsrTileDefinitionDepB_tile_id :: !Word16
- _msgSsrTileDefinitionDepB_corner_nw_lat :: !Int16
- _msgSsrTileDefinitionDepB_corner_nw_lon :: !Int16
- _msgSsrTileDefinitionDepB_spacing_lat :: !Word16
- _msgSsrTileDefinitionDepB_spacing_lon :: !Word16
- _msgSsrTileDefinitionDepB_rows :: !Word16
- _msgSsrTileDefinitionDepB_cols :: !Word16
- _msgSsrTileDefinitionDepB_bitmask :: !Word64
- msgSsrTileDefinitionDepA_bitmask :: Lens' MsgSsrTileDefinitionDepA Word64
- msgSsrTileDefinitionDepA_cols :: Lens' MsgSsrTileDefinitionDepA Word16
- msgSsrTileDefinitionDepA_corner_nw_lat :: Lens' MsgSsrTileDefinitionDepA Int16
- msgSsrTileDefinitionDepA_corner_nw_lon :: Lens' MsgSsrTileDefinitionDepA Int16
- msgSsrTileDefinitionDepA_rows :: Lens' MsgSsrTileDefinitionDepA Word16
- msgSsrTileDefinitionDepA_spacing_lat :: Lens' MsgSsrTileDefinitionDepA Word16
- msgSsrTileDefinitionDepA_spacing_lon :: Lens' MsgSsrTileDefinitionDepA Word16
- msgSsrTileDefinitionDepA_tile_id :: Lens' MsgSsrTileDefinitionDepA Word16
- msgSsrTileDefinitionDepA_tile_set_id :: Lens' MsgSsrTileDefinitionDepA Word16
- msgSsrTileDefinitionDepB :: Word16
- data MsgSsrTileDefinition = MsgSsrTileDefinition {
- _msgSsrTileDefinition_time :: !GpsTimeSec
- _msgSsrTileDefinition_update_interval :: !Word8
- _msgSsrTileDefinition_sol_id :: !Word8
- _msgSsrTileDefinition_iod_atmo :: !Word8
- _msgSsrTileDefinition_tile_set_id :: !Word16
- _msgSsrTileDefinition_tile_id :: !Word16
- _msgSsrTileDefinition_corner_nw_lat :: !Int16
- _msgSsrTileDefinition_corner_nw_lon :: !Int16
- _msgSsrTileDefinition_spacing_lat :: !Word16
- _msgSsrTileDefinition_spacing_lon :: !Word16
- _msgSsrTileDefinition_rows :: !Word16
- _msgSsrTileDefinition_cols :: !Word16
- _msgSsrTileDefinition_bitmask :: !Word64
- msgSsrTileDefinitionDepB_bitmask :: Lens' MsgSsrTileDefinitionDepB Word64
- msgSsrTileDefinitionDepB_cols :: Lens' MsgSsrTileDefinitionDepB Word16
- msgSsrTileDefinitionDepB_corner_nw_lat :: Lens' MsgSsrTileDefinitionDepB Int16
- msgSsrTileDefinitionDepB_corner_nw_lon :: Lens' MsgSsrTileDefinitionDepB Int16
- msgSsrTileDefinitionDepB_rows :: Lens' MsgSsrTileDefinitionDepB Word16
- msgSsrTileDefinitionDepB_spacing_lat :: Lens' MsgSsrTileDefinitionDepB Word16
- msgSsrTileDefinitionDepB_spacing_lon :: Lens' MsgSsrTileDefinitionDepB Word16
- msgSsrTileDefinitionDepB_ssr_sol_id :: Lens' MsgSsrTileDefinitionDepB Word8
- msgSsrTileDefinitionDepB_tile_id :: Lens' MsgSsrTileDefinitionDepB Word16
- msgSsrTileDefinitionDepB_tile_set_id :: Lens' MsgSsrTileDefinitionDepB Word16
- msgSsrTileDefinition :: Word16
- data SatelliteAPC = SatelliteAPC {}
- msgSsrTileDefinition_bitmask :: Lens' MsgSsrTileDefinition Word64
- msgSsrTileDefinition_cols :: Lens' MsgSsrTileDefinition Word16
- msgSsrTileDefinition_corner_nw_lat :: Lens' MsgSsrTileDefinition Int16
- msgSsrTileDefinition_corner_nw_lon :: Lens' MsgSsrTileDefinition Int16
- msgSsrTileDefinition_iod_atmo :: Lens' MsgSsrTileDefinition Word8
- msgSsrTileDefinition_rows :: Lens' MsgSsrTileDefinition Word16
- msgSsrTileDefinition_sol_id :: Lens' MsgSsrTileDefinition Word8
- msgSsrTileDefinition_spacing_lat :: Lens' MsgSsrTileDefinition Word16
- msgSsrTileDefinition_spacing_lon :: Lens' MsgSsrTileDefinition Word16
- msgSsrTileDefinition_tile_id :: Lens' MsgSsrTileDefinition Word16
- msgSsrTileDefinition_tile_set_id :: Lens' MsgSsrTileDefinition Word16
- msgSsrTileDefinition_time :: Lens' MsgSsrTileDefinition GpsTimeSec
- msgSsrTileDefinition_update_interval :: Lens' MsgSsrTileDefinition Word8
- data MsgSsrSatelliteApcDep = MsgSsrSatelliteApcDep {}
- satelliteAPC_pco :: Lens' SatelliteAPC [Int16]
- satelliteAPC_pcv :: Lens' SatelliteAPC [Int8]
- satelliteAPC_sat_info :: Lens' SatelliteAPC Word8
- satelliteAPC_sid :: Lens' SatelliteAPC GnssSignal
- satelliteAPC_svn :: Lens' SatelliteAPC Word16
- msgSsrSatelliteApcDep :: Word16
- data MsgSsrSatelliteApc = MsgSsrSatelliteApc {}
- msgSsrSatelliteApcDep_apc :: Iso' MsgSsrSatelliteApcDep [SatelliteAPC]
- msgSsrSatelliteApc :: 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
- msgSsrSatelliteApc_apc :: Lens' MsgSsrSatelliteApc [SatelliteAPC]
- msgSsrSatelliteApc_iod_ssr :: Lens' MsgSsrSatelliteApc Word8
- msgSsrSatelliteApc_sol_id :: Lens' MsgSsrSatelliteApc Word8
- msgSsrSatelliteApc_time :: Lens' MsgSsrSatelliteApc GpsTimeSec
- msgSsrSatelliteApc_update_interval :: Lens' MsgSsrSatelliteApc Word8
- msgSsrOrbitClockDepA :: Word16
- data STECHeaderDepA = STECHeaderDepA {}
- 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
- data GriddedCorrectionHeaderDepA = GriddedCorrectionHeaderDepA {
- _griddedCorrectionHeaderDepA_time :: !GpsTimeSec
- _griddedCorrectionHeaderDepA_num_msgs :: !Word16
- _griddedCorrectionHeaderDepA_seq_num :: !Word16
- _griddedCorrectionHeaderDepA_update_interval :: !Word8
- _griddedCorrectionHeaderDepA_iod_atmo :: !Word8
- _griddedCorrectionHeaderDepA_tropo_quality_indicator :: !Word8
- sTECHeaderDepA_iod_atmo :: Lens' STECHeaderDepA Word8
- sTECHeaderDepA_num_msgs :: Lens' STECHeaderDepA Word8
- sTECHeaderDepA_seq_num :: Lens' STECHeaderDepA Word8
- sTECHeaderDepA_time :: Lens' STECHeaderDepA GpsTimeSec
- sTECHeaderDepA_update_interval :: Lens' STECHeaderDepA Word8
- data GridDefinitionHeaderDepA = GridDefinitionHeaderDepA {}
- griddedCorrectionHeaderDepA_iod_atmo :: Lens' GriddedCorrectionHeaderDepA Word8
- griddedCorrectionHeaderDepA_num_msgs :: Lens' GriddedCorrectionHeaderDepA Word16
- griddedCorrectionHeaderDepA_seq_num :: Lens' GriddedCorrectionHeaderDepA Word16
- griddedCorrectionHeaderDepA_time :: Lens' GriddedCorrectionHeaderDepA GpsTimeSec
- griddedCorrectionHeaderDepA_tropo_quality_indicator :: Lens' GriddedCorrectionHeaderDepA Word8
- griddedCorrectionHeaderDepA_update_interval :: Lens' GriddedCorrectionHeaderDepA Word8
- data MsgSsrStecCorrectionDepA = MsgSsrStecCorrectionDepA {}
- gridDefinitionHeaderDepA_area_width :: Lens' GridDefinitionHeaderDepA Word16
- gridDefinitionHeaderDepA_lat_nw_corner_enc :: Lens' GridDefinitionHeaderDepA Word16
- gridDefinitionHeaderDepA_lon_nw_corner_enc :: Lens' GridDefinitionHeaderDepA Word16
- gridDefinitionHeaderDepA_num_msgs :: Lens' GridDefinitionHeaderDepA Word8
- gridDefinitionHeaderDepA_region_size_inverse :: Lens' GridDefinitionHeaderDepA Word8
- gridDefinitionHeaderDepA_seq_num :: Lens' GridDefinitionHeaderDepA Word8
- msgSsrStecCorrectionDepA :: Word16
- data MsgSsrGriddedCorrectionNoStdDepA = MsgSsrGriddedCorrectionNoStdDepA {}
- msgSsrStecCorrectionDepA_header :: Lens' MsgSsrStecCorrectionDepA STECHeaderDepA
- msgSsrStecCorrectionDepA_stec_sat_list :: Lens' MsgSsrStecCorrectionDepA [STECSatElement]
- msgSsrGriddedCorrectionNoStdDepA :: Word16
- data MsgSsrGriddedCorrectionDepA = MsgSsrGriddedCorrectionDepA {}
- msgSsrGriddedCorrectionNoStdDepA_header :: Lens' MsgSsrGriddedCorrectionNoStdDepA GriddedCorrectionHeaderDepA
- msgSsrGriddedCorrectionNoStdDepA_index :: Lens' MsgSsrGriddedCorrectionNoStdDepA Word16
- msgSsrGriddedCorrectionNoStdDepA_stec_residuals :: Lens' MsgSsrGriddedCorrectionNoStdDepA [STECResidualNoStd]
- msgSsrGriddedCorrectionNoStdDepA_tropo_delay_correction :: Lens' MsgSsrGriddedCorrectionNoStdDepA TroposphericDelayCorrectionNoStd
- msgSsrGriddedCorrectionDepA :: Word16
- data MsgSsrGridDefinitionDepA = MsgSsrGridDefinitionDepA {}
- msgSsrGriddedCorrectionDepA_header :: Lens' MsgSsrGriddedCorrectionDepA GriddedCorrectionHeaderDepA
- msgSsrGriddedCorrectionDepA_index :: Lens' MsgSsrGriddedCorrectionDepA Word16
- msgSsrGriddedCorrectionDepA_stec_residuals :: Lens' MsgSsrGriddedCorrectionDepA [STECResidual]
- msgSsrGriddedCorrectionDepA_tropo_delay_correction :: Lens' MsgSsrGriddedCorrectionDepA TroposphericDelayCorrection
- msgSsrGridDefinitionDepA :: Word16
- data OrbitClockBound = OrbitClockBound {
- _orbitClockBound_sat_id :: !Word8
- _orbitClockBound_orb_radial_bound_mu :: !Word8
- _orbitClockBound_orb_along_bound_mu :: !Word8
- _orbitClockBound_orb_cross_bound_mu :: !Word8
- _orbitClockBound_orb_radial_bound_sig :: !Word8
- _orbitClockBound_orb_along_bound_sig :: !Word8
- _orbitClockBound_orb_cross_bound_sig :: !Word8
- _orbitClockBound_clock_bound_mu :: !Word8
- _orbitClockBound_clock_bound_sig :: !Word8
- msgSsrGridDefinitionDepA_header :: Lens' MsgSsrGridDefinitionDepA GridDefinitionHeaderDepA
- msgSsrGridDefinitionDepA_rle_list :: Lens' MsgSsrGridDefinitionDepA [Word8]
- data MsgSsrOrbitClockBounds = MsgSsrOrbitClockBounds {}
- orbitClockBound_clock_bound_mu :: Lens' OrbitClockBound Word8
- orbitClockBound_clock_bound_sig :: Lens' OrbitClockBound Word8
- orbitClockBound_orb_along_bound_mu :: Lens' OrbitClockBound Word8
- orbitClockBound_orb_along_bound_sig :: Lens' OrbitClockBound Word8
- orbitClockBound_orb_cross_bound_mu :: Lens' OrbitClockBound Word8
- orbitClockBound_orb_cross_bound_sig :: Lens' OrbitClockBound Word8
- orbitClockBound_orb_radial_bound_mu :: Lens' OrbitClockBound Word8
- orbitClockBound_orb_radial_bound_sig :: Lens' OrbitClockBound Word8
- orbitClockBound_sat_id :: Lens' OrbitClockBound Word8
- msgSsrOrbitClockBounds :: Word16
- data CodePhaseBiasesSatSig = CodePhaseBiasesSatSig {}
- msgSsrOrbitClockBounds_const_id :: Lens' MsgSsrOrbitClockBounds Word8
- msgSsrOrbitClockBounds_header :: Lens' MsgSsrOrbitClockBounds BoundsHeader
- msgSsrOrbitClockBounds_n_sats :: Lens' MsgSsrOrbitClockBounds Word8
- msgSsrOrbitClockBounds_orbit_clock_bounds :: Lens' MsgSsrOrbitClockBounds [OrbitClockBound]
- msgSsrOrbitClockBounds_ssr_iod :: Lens' MsgSsrOrbitClockBounds Word8
- data MsgSsrCodePhaseBiasesBounds = MsgSsrCodePhaseBiasesBounds {}
- codePhaseBiasesSatSig_code_bias_bound_mu :: Lens' CodePhaseBiasesSatSig Word8
- codePhaseBiasesSatSig_code_bias_bound_sig :: Lens' CodePhaseBiasesSatSig Word8
- codePhaseBiasesSatSig_phase_bias_bound_mu :: Lens' CodePhaseBiasesSatSig Word8
- codePhaseBiasesSatSig_phase_bias_bound_sig :: Lens' CodePhaseBiasesSatSig Word8
- codePhaseBiasesSatSig_sat_id :: Lens' CodePhaseBiasesSatSig Word8
- codePhaseBiasesSatSig_signal_id :: Lens' CodePhaseBiasesSatSig Word8
- msgSsrCodePhaseBiasesBounds :: Word16
- data OrbitClockBoundDegradation = OrbitClockBoundDegradation {
- _orbitClockBoundDegradation_orb_radial_bound_mu_dot :: !Word8
- _orbitClockBoundDegradation_orb_along_bound_mu_dot :: !Word8
- _orbitClockBoundDegradation_orb_cross_bound_mu_dot :: !Word8
- _orbitClockBoundDegradation_orb_radial_bound_sig_dot :: !Word8
- _orbitClockBoundDegradation_orb_along_bound_sig_dot :: !Word8
- _orbitClockBoundDegradation_orb_cross_bound_sig_dot :: !Word8
- _orbitClockBoundDegradation_clock_bound_mu_dot :: !Word8
- _orbitClockBoundDegradation_clock_bound_sig_dot :: !Word8
- msgSsrCodePhaseBiasesBounds_const_id :: Lens' MsgSsrCodePhaseBiasesBounds Word8
- msgSsrCodePhaseBiasesBounds_header :: Lens' MsgSsrCodePhaseBiasesBounds BoundsHeader
- msgSsrCodePhaseBiasesBounds_n_sats_signals :: Lens' MsgSsrCodePhaseBiasesBounds Word8
- msgSsrCodePhaseBiasesBounds_satellites_signals :: Lens' MsgSsrCodePhaseBiasesBounds [CodePhaseBiasesSatSig]
- msgSsrCodePhaseBiasesBounds_ssr_iod :: Lens' MsgSsrCodePhaseBiasesBounds Word8
- data MsgSsrOrbitClockBoundsDegradation = MsgSsrOrbitClockBoundsDegradation {
- _msgSsrOrbitClockBoundsDegradation_header :: !BoundsHeader
- _msgSsrOrbitClockBoundsDegradation_ssr_iod :: !Word8
- _msgSsrOrbitClockBoundsDegradation_const_id :: !Word8
- _msgSsrOrbitClockBoundsDegradation_sat_bitmask :: !Word64
- _msgSsrOrbitClockBoundsDegradation_orbit_clock_bounds_degradation :: !OrbitClockBoundDegradation
- orbitClockBoundDegradation_clock_bound_mu_dot :: Lens' OrbitClockBoundDegradation Word8
- orbitClockBoundDegradation_clock_bound_sig_dot :: Lens' OrbitClockBoundDegradation Word8
- orbitClockBoundDegradation_orb_along_bound_mu_dot :: Lens' OrbitClockBoundDegradation Word8
- orbitClockBoundDegradation_orb_along_bound_sig_dot :: Lens' OrbitClockBoundDegradation Word8
- orbitClockBoundDegradation_orb_cross_bound_mu_dot :: Lens' OrbitClockBoundDegradation Word8
- orbitClockBoundDegradation_orb_cross_bound_sig_dot :: Lens' OrbitClockBoundDegradation Word8
- orbitClockBoundDegradation_orb_radial_bound_mu_dot :: Lens' OrbitClockBoundDegradation Word8
- orbitClockBoundDegradation_orb_radial_bound_sig_dot :: Lens' OrbitClockBoundDegradation Word8
- msgSsrOrbitClockBoundsDegradation :: Word16
- msgSsrOrbitClockBoundsDegradation_const_id :: Lens' MsgSsrOrbitClockBoundsDegradation Word8
- msgSsrOrbitClockBoundsDegradation_header :: Lens' MsgSsrOrbitClockBoundsDegradation BoundsHeader
- msgSsrOrbitClockBoundsDegradation_orbit_clock_bounds_degradation :: Lens' MsgSsrOrbitClockBoundsDegradation OrbitClockBoundDegradation
- msgSsrOrbitClockBoundsDegradation_sat_bitmask :: Lens' MsgSsrOrbitClockBoundsDegradation Word64
- msgSsrOrbitClockBoundsDegradation_ssr_iod :: Lens' MsgSsrOrbitClockBoundsDegradation Word8
Documentation
data CodeBiasesContent Source #
CodeBiasesContent.
Code biases are to be added to pseudorange. The corrections conform with RTCMv3 MT 1059 / 1065.
CodeBiasesContent | |
|
Instances
FromJSON CodeBiasesContent Source # | |
Defined in SwiftNav.SBP.Ssr parseJSON :: Value -> Parser CodeBiasesContent # parseJSONList :: Value -> Parser [CodeBiasesContent] # | |
ToJSON CodeBiasesContent Source # | |
Defined in SwiftNav.SBP.Ssr toJSON :: CodeBiasesContent -> Value # toEncoding :: CodeBiasesContent -> Encoding # toJSONList :: [CodeBiasesContent] -> Value # toEncodingList :: [CodeBiasesContent] -> Encoding # | |
Read CodeBiasesContent Source # | |
Defined in SwiftNav.SBP.Ssr | |
Show CodeBiasesContent Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> CodeBiasesContent -> ShowS # show :: CodeBiasesContent -> String # showList :: [CodeBiasesContent] -> ShowS # | |
Binary CodeBiasesContent Source # | |
Defined in SwiftNav.SBP.Ssr put :: CodeBiasesContent -> Put # get :: Get CodeBiasesContent # putList :: [CodeBiasesContent] -> Put # | |
Eq CodeBiasesContent Source # | |
Defined in SwiftNav.SBP.Ssr (==) :: CodeBiasesContent -> CodeBiasesContent -> Bool # (/=) :: CodeBiasesContent -> CodeBiasesContent -> Bool # |
data PhaseBiasesContent Source #
PhaseBiasesContent.
Phase biases are to be added to carrier phase measurements.
PhaseBiasesContent | |
|
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.
STECHeader | |
|
Instances
FromJSON STECHeader Source # | |
Defined in SwiftNav.SBP.Ssr parseJSON :: Value -> Parser STECHeader # parseJSONList :: Value -> Parser [STECHeader] # | |
ToJSON STECHeader Source # | |
Defined in SwiftNav.SBP.Ssr toJSON :: STECHeader -> Value # toEncoding :: STECHeader -> Encoding # toJSONList :: [STECHeader] -> Value # toEncodingList :: [STECHeader] -> Encoding # | |
Read STECHeader Source # | |
Defined in SwiftNav.SBP.Ssr readsPrec :: Int -> ReadS STECHeader # readList :: ReadS [STECHeader] # readPrec :: ReadPrec STECHeader # readListPrec :: ReadPrec [STECHeader] # | |
Show STECHeader Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> STECHeader -> ShowS # show :: STECHeader -> String # showList :: [STECHeader] -> ShowS # | |
Binary STECHeader Source # | |
Defined in SwiftNav.SBP.Ssr | |
Eq STECHeader Source # | |
Defined in SwiftNav.SBP.Ssr (==) :: STECHeader -> STECHeader -> Bool # (/=) :: STECHeader -> STECHeader -> Bool # |
data GriddedCorrectionHeader Source #
GriddedCorrectionHeader.
The LPP message contains nested variable length arrays which are not supported in SBP, so each grid point will be identified by the index.
GriddedCorrectionHeader | |
|
Instances
FromJSON GriddedCorrectionHeader Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToJSON GriddedCorrectionHeader Source # | |
Defined in SwiftNav.SBP.Ssr | |
Read GriddedCorrectionHeader Source # | |
Show GriddedCorrectionHeader Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> GriddedCorrectionHeader -> ShowS # show :: GriddedCorrectionHeader -> String # showList :: [GriddedCorrectionHeader] -> ShowS # | |
Binary GriddedCorrectionHeader Source # | |
Defined in SwiftNav.SBP.Ssr put :: GriddedCorrectionHeader -> Put # get :: Get GriddedCorrectionHeader # putList :: [GriddedCorrectionHeader] -> Put # | |
Eq GriddedCorrectionHeader Source # | |
Defined in SwiftNav.SBP.Ssr |
data STECSatElement Source #
STECSatElement.
STEC polynomial for the given satellite.
STECSatElement | |
|
Instances
FromJSON STECSatElement Source # | |
Defined in SwiftNav.SBP.Ssr parseJSON :: Value -> Parser STECSatElement # parseJSONList :: Value -> Parser [STECSatElement] # | |
ToJSON STECSatElement Source # | |
Defined in SwiftNav.SBP.Ssr toJSON :: STECSatElement -> Value # toEncoding :: STECSatElement -> Encoding # toJSONList :: [STECSatElement] -> Value # toEncodingList :: [STECSatElement] -> Encoding # | |
Read STECSatElement Source # | |
Defined in SwiftNav.SBP.Ssr readsPrec :: Int -> ReadS STECSatElement # readList :: ReadS [STECSatElement] # | |
Show STECSatElement Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> STECSatElement -> ShowS # show :: STECSatElement -> String # showList :: [STECSatElement] -> ShowS # | |
Binary STECSatElement Source # | |
Defined in SwiftNav.SBP.Ssr | |
Eq STECSatElement Source # | |
Defined in SwiftNav.SBP.Ssr (==) :: STECSatElement -> STECSatElement -> Bool # (/=) :: STECSatElement -> STECSatElement -> Bool # |
data TroposphericDelayCorrectionNoStd Source #
TroposphericDelayCorrectionNoStd.
Troposphere vertical delays at the grid point.
TroposphericDelayCorrectionNoStd | |
|
Instances
data TroposphericDelayCorrection Source #
TroposphericDelayCorrection.
Troposphere vertical delays (mean and standard deviation) at the grid point.
TroposphericDelayCorrection | |
|
Instances
FromJSON TroposphericDelayCorrection Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToJSON TroposphericDelayCorrection Source # | |
Defined in SwiftNav.SBP.Ssr | |
Read TroposphericDelayCorrection Source # | |
Show TroposphericDelayCorrection Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> TroposphericDelayCorrection -> ShowS # show :: TroposphericDelayCorrection -> String # showList :: [TroposphericDelayCorrection] -> ShowS # | |
Binary TroposphericDelayCorrection Source # | |
Defined in SwiftNav.SBP.Ssr | |
Eq TroposphericDelayCorrection Source # | |
Defined in SwiftNav.SBP.Ssr |
data STECResidualNoStd Source #
STECResidualNoStd.
STEC residual for the given satellite at the grid point.
STECResidualNoStd | |
|
Instances
FromJSON STECResidualNoStd Source # | |
Defined in SwiftNav.SBP.Ssr parseJSON :: Value -> Parser STECResidualNoStd # parseJSONList :: Value -> Parser [STECResidualNoStd] # | |
ToJSON STECResidualNoStd Source # | |
Defined in SwiftNav.SBP.Ssr toJSON :: STECResidualNoStd -> Value # toEncoding :: STECResidualNoStd -> Encoding # toJSONList :: [STECResidualNoStd] -> Value # toEncodingList :: [STECResidualNoStd] -> Encoding # | |
Read STECResidualNoStd Source # | |
Defined in SwiftNav.SBP.Ssr | |
Show STECResidualNoStd Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> STECResidualNoStd -> ShowS # show :: STECResidualNoStd -> String # showList :: [STECResidualNoStd] -> ShowS # | |
Binary STECResidualNoStd Source # | |
Defined in SwiftNav.SBP.Ssr put :: STECResidualNoStd -> Put # get :: Get STECResidualNoStd # putList :: [STECResidualNoStd] -> Put # | |
Eq STECResidualNoStd Source # | |
Defined in SwiftNav.SBP.Ssr (==) :: STECResidualNoStd -> STECResidualNoStd -> Bool # (/=) :: STECResidualNoStd -> STECResidualNoStd -> Bool # |
data STECResidual Source #
STECResidual.
STEC residual (mean and standard deviation) for the given satellite at the grid point.
STECResidual | |
|
Instances
FromJSON STECResidual Source # | |
Defined in SwiftNav.SBP.Ssr parseJSON :: Value -> Parser STECResidual # parseJSONList :: Value -> Parser [STECResidual] # | |
ToJSON STECResidual Source # | |
Defined in SwiftNav.SBP.Ssr toJSON :: STECResidual -> Value # toEncoding :: STECResidual -> Encoding # toJSONList :: [STECResidual] -> Value # toEncodingList :: [STECResidual] -> Encoding # | |
Read STECResidual Source # | |
Defined in SwiftNav.SBP.Ssr readsPrec :: Int -> ReadS STECResidual # readList :: ReadS [STECResidual] # | |
Show STECResidual Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> STECResidual -> ShowS # show :: STECResidual -> String # showList :: [STECResidual] -> ShowS # | |
Binary STECResidual Source # | |
Defined in SwiftNav.SBP.Ssr | |
Eq STECResidual Source # | |
Defined in SwiftNav.SBP.Ssr (==) :: STECResidual -> STECResidual -> Bool # (/=) :: STECResidual -> STECResidual -> Bool # |
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 an equivalent to the 1060 /1066 RTCM message types.
MsgSsrOrbitClock | |
|
Instances
FromJSON MsgSsrOrbitClock Source # | |
Defined in SwiftNav.SBP.Ssr parseJSON :: Value -> Parser MsgSsrOrbitClock # parseJSONList :: Value -> Parser [MsgSsrOrbitClock] # | |
ToJSON MsgSsrOrbitClock Source # | |
Defined in SwiftNav.SBP.Ssr toJSON :: MsgSsrOrbitClock -> Value # toEncoding :: MsgSsrOrbitClock -> Encoding # toJSONList :: [MsgSsrOrbitClock] -> Value # toEncodingList :: [MsgSsrOrbitClock] -> Encoding # | |
Read MsgSsrOrbitClock Source # | |
Defined in SwiftNav.SBP.Ssr | |
Show MsgSsrOrbitClock Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> MsgSsrOrbitClock -> ShowS # show :: MsgSsrOrbitClock -> String # showList :: [MsgSsrOrbitClock] -> ShowS # | |
Binary MsgSsrOrbitClock Source # | |
Defined in SwiftNav.SBP.Ssr | |
Eq MsgSsrOrbitClock Source # | |
Defined in SwiftNav.SBP.Ssr (==) :: MsgSsrOrbitClock -> MsgSsrOrbitClock -> Bool # (/=) :: MsgSsrOrbitClock -> MsgSsrOrbitClock -> Bool # | |
ToSBP MsgSsrOrbitClock Source # | |
Defined in SwiftNav.SBP.Ssr |
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 an equivalent to the 1059 / 1065 RTCM message types.
MsgSsrCodeBiases | |
|
Instances
FromJSON MsgSsrCodeBiases Source # | |
Defined in SwiftNav.SBP.Ssr parseJSON :: Value -> Parser MsgSsrCodeBiases # parseJSONList :: Value -> Parser [MsgSsrCodeBiases] # | |
ToJSON MsgSsrCodeBiases Source # | |
Defined in SwiftNav.SBP.Ssr toJSON :: MsgSsrCodeBiases -> Value # toEncoding :: MsgSsrCodeBiases -> Encoding # toJSONList :: [MsgSsrCodeBiases] -> Value # toEncodingList :: [MsgSsrCodeBiases] -> Encoding # | |
Read MsgSsrCodeBiases Source # | |
Defined in SwiftNav.SBP.Ssr | |
Show MsgSsrCodeBiases Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> MsgSsrCodeBiases -> ShowS # show :: MsgSsrCodeBiases -> String # showList :: [MsgSsrCodeBiases] -> ShowS # | |
Binary MsgSsrCodeBiases Source # | |
Defined in SwiftNav.SBP.Ssr | |
Eq MsgSsrCodeBiases Source # | |
Defined in SwiftNav.SBP.Ssr (==) :: MsgSsrCodeBiases -> MsgSsrCodeBiases -> Bool # (/=) :: MsgSsrCodeBiases -> MsgSsrCodeBiases -> Bool # | |
ToSBP MsgSsrCodeBiases Source # | |
Defined in SwiftNav.SBP.Ssr |
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.
MsgSsrPhaseBiases | |
|
Instances
data MsgSsrStecCorrectionDep Source #
SBP class for message MSG_SSR_STEC_CORRECTION_DEP (0x05FB).
Deprecated.
MsgSsrStecCorrectionDep | |
|
Instances
FromJSON MsgSsrStecCorrectionDep Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToJSON MsgSsrStecCorrectionDep Source # | |
Defined in SwiftNav.SBP.Ssr | |
Read MsgSsrStecCorrectionDep Source # | |
Show MsgSsrStecCorrectionDep Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> MsgSsrStecCorrectionDep -> ShowS # show :: MsgSsrStecCorrectionDep -> String # showList :: [MsgSsrStecCorrectionDep] -> ShowS # | |
Binary MsgSsrStecCorrectionDep Source # | |
Defined in SwiftNav.SBP.Ssr put :: MsgSsrStecCorrectionDep -> Put # get :: Get MsgSsrStecCorrectionDep # putList :: [MsgSsrStecCorrectionDep] -> Put # | |
Eq MsgSsrStecCorrectionDep Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToSBP MsgSsrStecCorrectionDep Source # | |
Defined in SwiftNav.SBP.Ssr |
data BoundsHeader Source #
BoundsHeader | |
|
Instances
FromJSON BoundsHeader Source # | |
Defined in SwiftNav.SBP.Ssr parseJSON :: Value -> Parser BoundsHeader # parseJSONList :: Value -> Parser [BoundsHeader] # | |
ToJSON BoundsHeader Source # | |
Defined in SwiftNav.SBP.Ssr toJSON :: BoundsHeader -> Value # toEncoding :: BoundsHeader -> Encoding # toJSONList :: [BoundsHeader] -> Value # toEncodingList :: [BoundsHeader] -> Encoding # | |
Read BoundsHeader Source # | |
Defined in SwiftNav.SBP.Ssr readsPrec :: Int -> ReadS BoundsHeader # readList :: ReadS [BoundsHeader] # | |
Show BoundsHeader Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> BoundsHeader -> ShowS # show :: BoundsHeader -> String # showList :: [BoundsHeader] -> ShowS # | |
Binary BoundsHeader Source # | |
Defined in SwiftNav.SBP.Ssr | |
Eq BoundsHeader Source # | |
Defined in SwiftNav.SBP.Ssr (==) :: BoundsHeader -> BoundsHeader -> Bool # (/=) :: BoundsHeader -> BoundsHeader -> Bool # |
data MsgSsrStecCorrection Source #
MsgSsrStecCorrection | |
|
Instances
data MsgSsrGriddedCorrection Source #
SBP class for message MSG_SSR_GRIDDED_CORRECTION (0x05FC).
STEC residuals are per space vehicle, troposphere is not.
It is typically equivalent to the QZSS CLAS Sub Type 9 messages.
MsgSsrGriddedCorrection | |
|
Instances
FromJSON MsgSsrGriddedCorrection Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToJSON MsgSsrGriddedCorrection Source # | |
Defined in SwiftNav.SBP.Ssr | |
Read MsgSsrGriddedCorrection Source # | |
Show MsgSsrGriddedCorrection Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> MsgSsrGriddedCorrection -> ShowS # show :: MsgSsrGriddedCorrection -> String # showList :: [MsgSsrGriddedCorrection] -> ShowS # | |
Binary MsgSsrGriddedCorrection Source # | |
Defined in SwiftNav.SBP.Ssr put :: MsgSsrGriddedCorrection -> Put # get :: Get MsgSsrGriddedCorrection # putList :: [MsgSsrGriddedCorrection] -> Put # | |
Eq MsgSsrGriddedCorrection Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToSBP MsgSsrGriddedCorrection Source # | |
Defined in SwiftNav.SBP.Ssr |
data STECSatElementIntegrity Source #
STECSatElementIntegrity.
STEC polynomial and bounds for the given satellite.
STECSatElementIntegrity | |
|
Instances
FromJSON STECSatElementIntegrity Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToJSON STECSatElementIntegrity Source # | |
Defined in SwiftNav.SBP.Ssr | |
Read STECSatElementIntegrity Source # | |
Show STECSatElementIntegrity Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> STECSatElementIntegrity -> ShowS # show :: STECSatElementIntegrity -> String # showList :: [STECSatElementIntegrity] -> ShowS # | |
Binary STECSatElementIntegrity Source # | |
Defined in SwiftNav.SBP.Ssr put :: STECSatElementIntegrity -> Put # get :: Get STECSatElementIntegrity # putList :: [STECSatElementIntegrity] -> Put # | |
Eq STECSatElementIntegrity Source # | |
Defined in SwiftNav.SBP.Ssr |
msgSsrGriddedCorrection_tropo_delay_correction :: Lens' MsgSsrGriddedCorrection TroposphericDelayCorrection Source #
data MsgSsrGriddedCorrectionBounds Source #
SBP class for message MSG_SSR_GRIDDED_CORRECTION_BOUNDS (0x05FE).
Note 1: Range: 0-17.5 m. i<= 200, mean = 0.01i; 200<i<=230, mean=2+0.1(i-200); i>230, mean=5+0.5(i-230).
Instances
FromJSON MsgSsrGriddedCorrectionBounds Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToJSON MsgSsrGriddedCorrectionBounds Source # | |
Defined in SwiftNav.SBP.Ssr | |
Read MsgSsrGriddedCorrectionBounds Source # | |
Show MsgSsrGriddedCorrectionBounds Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> MsgSsrGriddedCorrectionBounds -> ShowS # show :: MsgSsrGriddedCorrectionBounds -> String # showList :: [MsgSsrGriddedCorrectionBounds] -> ShowS # | |
Binary MsgSsrGriddedCorrectionBounds Source # | |
Defined in SwiftNav.SBP.Ssr | |
Eq MsgSsrGriddedCorrectionBounds Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToSBP MsgSsrGriddedCorrectionBounds Source # | |
Defined in SwiftNav.SBP.Ssr |
data MsgSsrTileDefinitionDepA Source #
SBP class for message MSG_SSR_TILE_DEFINITION_DEP_A (0x05F6).
Deprecated.
MsgSsrTileDefinitionDepA | |
|
Instances
FromJSON MsgSsrTileDefinitionDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToJSON MsgSsrTileDefinitionDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
Read MsgSsrTileDefinitionDepA Source # | |
Show MsgSsrTileDefinitionDepA Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> MsgSsrTileDefinitionDepA -> ShowS # show :: MsgSsrTileDefinitionDepA -> String # showList :: [MsgSsrTileDefinitionDepA] -> ShowS # | |
Binary MsgSsrTileDefinitionDepA Source # | |
Defined in SwiftNav.SBP.Ssr put :: MsgSsrTileDefinitionDepA -> Put # get :: Get MsgSsrTileDefinitionDepA # putList :: [MsgSsrTileDefinitionDepA] -> Put # | |
Eq MsgSsrTileDefinitionDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToSBP MsgSsrTileDefinitionDepA Source # | |
Defined in SwiftNav.SBP.Ssr |
msgSsrGriddedCorrectionBounds_stec_sat_list :: Lens' MsgSsrGriddedCorrectionBounds [STECSatElementIntegrity] Source #
msgSsrGriddedCorrectionBounds_tropo_delay_correction :: Lens' MsgSsrGriddedCorrectionBounds TroposphericDelayCorrection Source #
msgSsrGriddedCorrectionBounds_tropo_v_hydro_bound_mu :: Lens' MsgSsrGriddedCorrectionBounds Word8 Source #
msgSsrGriddedCorrectionBounds_tropo_v_hydro_bound_sig :: Lens' MsgSsrGriddedCorrectionBounds Word8 Source #
msgSsrGriddedCorrectionBounds_tropo_v_wet_bound_mu :: Lens' MsgSsrGriddedCorrectionBounds Word8 Source #
msgSsrGriddedCorrectionBounds_tropo_v_wet_bound_sig :: Lens' MsgSsrGriddedCorrectionBounds Word8 Source #
data MsgSsrTileDefinitionDepB Source #
SBP class for message MSG_SSR_TILE_DEFINITION_DEP_B (0x05F7).
Deprecated.
MsgSsrTileDefinitionDepB | |
|
Instances
FromJSON MsgSsrTileDefinitionDepB Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToJSON MsgSsrTileDefinitionDepB Source # | |
Defined in SwiftNav.SBP.Ssr | |
Read MsgSsrTileDefinitionDepB Source # | |
Show MsgSsrTileDefinitionDepB Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> MsgSsrTileDefinitionDepB -> ShowS # show :: MsgSsrTileDefinitionDepB -> String # showList :: [MsgSsrTileDefinitionDepB] -> ShowS # | |
Binary MsgSsrTileDefinitionDepB Source # | |
Defined in SwiftNav.SBP.Ssr put :: MsgSsrTileDefinitionDepB -> Put # get :: Get MsgSsrTileDefinitionDepB # putList :: [MsgSsrTileDefinitionDepB] -> Put # | |
Eq MsgSsrTileDefinitionDepB Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToSBP MsgSsrTileDefinitionDepB Source # | |
Defined in SwiftNav.SBP.Ssr |
data MsgSsrTileDefinition Source #
SBP class for message MSG_SSR_TILE_DEFINITION (0x05F8).
Provides the correction point coordinates for the atmospheric correction values in the MSG_SSR_STEC_CORRECTION and MSG_SSR_GRIDDED_CORRECTION messages.
Based on ETSI TS 137 355 V16.1.0 (LTE Positioning Protocol) information element GNSS-SSR-CorrectionPoints. SBP only supports gridded arrays of correction points, not lists of points.
MsgSsrTileDefinition | |
|
Instances
data SatelliteAPC Source #
SatelliteAPC.
Contains phase center offset and elevation variation corrections for one signal on a satellite.
SatelliteAPC | |
|
Instances
FromJSON SatelliteAPC Source # | |
Defined in SwiftNav.SBP.Ssr parseJSON :: Value -> Parser SatelliteAPC # parseJSONList :: Value -> Parser [SatelliteAPC] # | |
ToJSON SatelliteAPC Source # | |
Defined in SwiftNav.SBP.Ssr toJSON :: SatelliteAPC -> Value # toEncoding :: SatelliteAPC -> Encoding # toJSONList :: [SatelliteAPC] -> Value # toEncodingList :: [SatelliteAPC] -> Encoding # | |
Read SatelliteAPC Source # | |
Defined in SwiftNav.SBP.Ssr readsPrec :: Int -> ReadS SatelliteAPC # readList :: ReadS [SatelliteAPC] # | |
Show SatelliteAPC Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> SatelliteAPC -> ShowS # show :: SatelliteAPC -> String # showList :: [SatelliteAPC] -> ShowS # | |
Binary SatelliteAPC Source # | |
Defined in SwiftNav.SBP.Ssr | |
Eq SatelliteAPC Source # | |
Defined in SwiftNav.SBP.Ssr (==) :: SatelliteAPC -> SatelliteAPC -> Bool # (/=) :: SatelliteAPC -> SatelliteAPC -> Bool # |
data MsgSsrSatelliteApcDep Source #
SBP class for message MSG_SSR_SATELLITE_APC_DEP (0x0604).
Deprecated.
MsgSsrSatelliteApcDep | |
|
Instances
data MsgSsrSatelliteApc Source #
MsgSsrSatelliteApc | |
|
Instances
data MsgSsrOrbitClockDepA Source #
SBP class for message MSG_SSR_ORBIT_CLOCK_DEP_A (0x05DC).
Deprecated.
MsgSsrOrbitClockDepA | |
|
Instances
data STECHeaderDepA Source #
STECHeaderDepA.
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.
STECHeaderDepA | |
|
Instances
FromJSON STECHeaderDepA Source # | |
Defined in SwiftNav.SBP.Ssr parseJSON :: Value -> Parser STECHeaderDepA # parseJSONList :: Value -> Parser [STECHeaderDepA] # | |
ToJSON STECHeaderDepA Source # | |
Defined in SwiftNav.SBP.Ssr toJSON :: STECHeaderDepA -> Value # toEncoding :: STECHeaderDepA -> Encoding # toJSONList :: [STECHeaderDepA] -> Value # toEncodingList :: [STECHeaderDepA] -> Encoding # | |
Read STECHeaderDepA Source # | |
Defined in SwiftNav.SBP.Ssr readsPrec :: Int -> ReadS STECHeaderDepA # readList :: ReadS [STECHeaderDepA] # | |
Show STECHeaderDepA Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> STECHeaderDepA -> ShowS # show :: STECHeaderDepA -> String # showList :: [STECHeaderDepA] -> ShowS # | |
Binary STECHeaderDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
Eq STECHeaderDepA Source # | |
Defined in SwiftNav.SBP.Ssr (==) :: STECHeaderDepA -> STECHeaderDepA -> Bool # (/=) :: STECHeaderDepA -> STECHeaderDepA -> Bool # |
data GriddedCorrectionHeaderDepA Source #
GriddedCorrectionHeaderDepA.
The 3GPP message contains nested variable length arrays which are not supported in SBP, so each grid point will be identified by the index.
GriddedCorrectionHeaderDepA | |
|
Instances
FromJSON GriddedCorrectionHeaderDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToJSON GriddedCorrectionHeaderDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
Read GriddedCorrectionHeaderDepA Source # | |
Show GriddedCorrectionHeaderDepA Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> GriddedCorrectionHeaderDepA -> ShowS # show :: GriddedCorrectionHeaderDepA -> String # showList :: [GriddedCorrectionHeaderDepA] -> ShowS # | |
Binary GriddedCorrectionHeaderDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
Eq GriddedCorrectionHeaderDepA Source # | |
Defined in SwiftNav.SBP.Ssr |
data GridDefinitionHeaderDepA Source #
GridDefinitionHeaderDepA.
Defines the grid for MSG_SSR_GRIDDED_CORRECTION messages. Also includes an RLE encoded validity list.
GridDefinitionHeaderDepA | |
|
Instances
FromJSON GridDefinitionHeaderDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToJSON GridDefinitionHeaderDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
Read GridDefinitionHeaderDepA Source # | |
Show GridDefinitionHeaderDepA Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> GridDefinitionHeaderDepA -> ShowS # show :: GridDefinitionHeaderDepA -> String # showList :: [GridDefinitionHeaderDepA] -> ShowS # | |
Binary GridDefinitionHeaderDepA Source # | |
Defined in SwiftNav.SBP.Ssr put :: GridDefinitionHeaderDepA -> Put # get :: Get GridDefinitionHeaderDepA # putList :: [GridDefinitionHeaderDepA] -> Put # | |
Eq GridDefinitionHeaderDepA Source # | |
Defined in SwiftNav.SBP.Ssr |
griddedCorrectionHeaderDepA_tropo_quality_indicator :: Lens' GriddedCorrectionHeaderDepA Word8 Source #
data MsgSsrStecCorrectionDepA Source #
SBP class for message MSG_SSR_STEC_CORRECTION_DEP_A (0x05EB).
Deprecated.
MsgSsrStecCorrectionDepA | |
|
Instances
FromJSON MsgSsrStecCorrectionDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToJSON MsgSsrStecCorrectionDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
Read MsgSsrStecCorrectionDepA Source # | |
Show MsgSsrStecCorrectionDepA Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> MsgSsrStecCorrectionDepA -> ShowS # show :: MsgSsrStecCorrectionDepA -> String # showList :: [MsgSsrStecCorrectionDepA] -> ShowS # | |
Binary MsgSsrStecCorrectionDepA Source # | |
Defined in SwiftNav.SBP.Ssr put :: MsgSsrStecCorrectionDepA -> Put # get :: Get MsgSsrStecCorrectionDepA # putList :: [MsgSsrStecCorrectionDepA] -> Put # | |
Eq MsgSsrStecCorrectionDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToSBP MsgSsrStecCorrectionDepA Source # | |
Defined in SwiftNav.SBP.Ssr |
data MsgSsrGriddedCorrectionNoStdDepA Source #
SBP class for message MSG_SSR_GRIDDED_CORRECTION_NO_STD_DEP_A (0x05F0).
Deprecated.
MsgSsrGriddedCorrectionNoStdDepA | |
|
Instances
data MsgSsrGriddedCorrectionDepA Source #
SBP class for message MSG_SSR_GRIDDED_CORRECTION_DEP_A (0x05FA).
Deprecated.
MsgSsrGriddedCorrectionDepA | |
|
Instances
FromJSON MsgSsrGriddedCorrectionDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToJSON MsgSsrGriddedCorrectionDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
Read MsgSsrGriddedCorrectionDepA Source # | |
Show MsgSsrGriddedCorrectionDepA Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> MsgSsrGriddedCorrectionDepA -> ShowS # show :: MsgSsrGriddedCorrectionDepA -> String # showList :: [MsgSsrGriddedCorrectionDepA] -> ShowS # | |
Binary MsgSsrGriddedCorrectionDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
Eq MsgSsrGriddedCorrectionDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToSBP MsgSsrGriddedCorrectionDepA Source # | |
Defined in SwiftNav.SBP.Ssr |
msgSsrGriddedCorrectionNoStdDepA_header :: Lens' MsgSsrGriddedCorrectionNoStdDepA GriddedCorrectionHeaderDepA Source #
msgSsrGriddedCorrectionNoStdDepA_stec_residuals :: Lens' MsgSsrGriddedCorrectionNoStdDepA [STECResidualNoStd] Source #
msgSsrGriddedCorrectionNoStdDepA_tropo_delay_correction :: Lens' MsgSsrGriddedCorrectionNoStdDepA TroposphericDelayCorrectionNoStd Source #
data MsgSsrGridDefinitionDepA Source #
SBP class for message MSG_SSR_GRID_DEFINITION_DEP_A (0x05F5).
Deprecated.
MsgSsrGridDefinitionDepA | |
|
Instances
FromJSON MsgSsrGridDefinitionDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToJSON MsgSsrGridDefinitionDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
Read MsgSsrGridDefinitionDepA Source # | |
Show MsgSsrGridDefinitionDepA Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> MsgSsrGridDefinitionDepA -> ShowS # show :: MsgSsrGridDefinitionDepA -> String # showList :: [MsgSsrGridDefinitionDepA] -> ShowS # | |
Binary MsgSsrGridDefinitionDepA Source # | |
Defined in SwiftNav.SBP.Ssr put :: MsgSsrGridDefinitionDepA -> Put # get :: Get MsgSsrGridDefinitionDepA # putList :: [MsgSsrGridDefinitionDepA] -> Put # | |
Eq MsgSsrGridDefinitionDepA Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToSBP MsgSsrGridDefinitionDepA Source # | |
Defined in SwiftNav.SBP.Ssr |
msgSsrGriddedCorrectionDepA_header :: Lens' MsgSsrGriddedCorrectionDepA GriddedCorrectionHeaderDepA Source #
msgSsrGriddedCorrectionDepA_stec_residuals :: Lens' MsgSsrGriddedCorrectionDepA [STECResidual] Source #
msgSsrGriddedCorrectionDepA_tropo_delay_correction :: Lens' MsgSsrGriddedCorrectionDepA TroposphericDelayCorrection Source #
data OrbitClockBound Source #
OrbitClockBound.
Orbit and clock bound.
OrbitClockBound | |
|
Instances
FromJSON OrbitClockBound Source # | |
Defined in SwiftNav.SBP.Ssr parseJSON :: Value -> Parser OrbitClockBound # parseJSONList :: Value -> Parser [OrbitClockBound] # | |
ToJSON OrbitClockBound Source # | |
Defined in SwiftNav.SBP.Ssr toJSON :: OrbitClockBound -> Value # toEncoding :: OrbitClockBound -> Encoding # toJSONList :: [OrbitClockBound] -> Value # toEncodingList :: [OrbitClockBound] -> Encoding # | |
Read OrbitClockBound Source # | |
Defined in SwiftNav.SBP.Ssr | |
Show OrbitClockBound Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> OrbitClockBound -> ShowS # show :: OrbitClockBound -> String # showList :: [OrbitClockBound] -> ShowS # | |
Binary OrbitClockBound Source # | |
Defined in SwiftNav.SBP.Ssr | |
Eq OrbitClockBound Source # | |
Defined in SwiftNav.SBP.Ssr (==) :: OrbitClockBound -> OrbitClockBound -> Bool # (/=) :: OrbitClockBound -> OrbitClockBound -> Bool # |
data MsgSsrOrbitClockBounds Source #
SBP class for message MSG_SSR_ORBIT_CLOCK_BOUNDS (0x05DE).
Note 1: Range: 0-17.5 m. i<=200, mean=0.01i; 200<i<=230, mean=2+0.1(i-200); i>230, mean=5+0.5(i-230).
Note 2: Range: 0-17.5 m. i<=200, std=0.01i; 200<i<=230, std=2+0.1(i-200) i>230, std=5+0.5(i-230).
MsgSsrOrbitClockBounds | |
|
Instances
FromJSON MsgSsrOrbitClockBounds Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToJSON MsgSsrOrbitClockBounds Source # | |
Defined in SwiftNav.SBP.Ssr toJSON :: MsgSsrOrbitClockBounds -> Value # toEncoding :: MsgSsrOrbitClockBounds -> Encoding # toJSONList :: [MsgSsrOrbitClockBounds] -> Value # | |
Read MsgSsrOrbitClockBounds Source # | |
Defined in SwiftNav.SBP.Ssr | |
Show MsgSsrOrbitClockBounds Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> MsgSsrOrbitClockBounds -> ShowS # show :: MsgSsrOrbitClockBounds -> String # showList :: [MsgSsrOrbitClockBounds] -> ShowS # | |
Binary MsgSsrOrbitClockBounds Source # | |
Defined in SwiftNav.SBP.Ssr put :: MsgSsrOrbitClockBounds -> Put # get :: Get MsgSsrOrbitClockBounds # putList :: [MsgSsrOrbitClockBounds] -> Put # | |
Eq MsgSsrOrbitClockBounds Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToSBP MsgSsrOrbitClockBounds Source # | |
Defined in SwiftNav.SBP.Ssr |
data CodePhaseBiasesSatSig Source #
CodePhaseBiasesSatSig | |
|
Instances
msgSsrOrbitClockBounds_orbit_clock_bounds :: Lens' MsgSsrOrbitClockBounds [OrbitClockBound] Source #
data MsgSsrCodePhaseBiasesBounds Source #
MsgSsrCodePhaseBiasesBounds | |
|
Instances
FromJSON MsgSsrCodePhaseBiasesBounds Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToJSON MsgSsrCodePhaseBiasesBounds Source # | |
Defined in SwiftNav.SBP.Ssr | |
Read MsgSsrCodePhaseBiasesBounds Source # | |
Show MsgSsrCodePhaseBiasesBounds Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> MsgSsrCodePhaseBiasesBounds -> ShowS # show :: MsgSsrCodePhaseBiasesBounds -> String # showList :: [MsgSsrCodePhaseBiasesBounds] -> ShowS # | |
Binary MsgSsrCodePhaseBiasesBounds Source # | |
Defined in SwiftNav.SBP.Ssr | |
Eq MsgSsrCodePhaseBiasesBounds Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToSBP MsgSsrCodePhaseBiasesBounds Source # | |
Defined in SwiftNav.SBP.Ssr |
data OrbitClockBoundDegradation Source #
OrbitClockBoundDegradation.
Orbit and clock bound degradation.
OrbitClockBoundDegradation | |
|
Instances
FromJSON OrbitClockBoundDegradation Source # | |
Defined in SwiftNav.SBP.Ssr | |
ToJSON OrbitClockBoundDegradation Source # | |
Defined in SwiftNav.SBP.Ssr | |
Read OrbitClockBoundDegradation Source # | |
Show OrbitClockBoundDegradation Source # | |
Defined in SwiftNav.SBP.Ssr showsPrec :: Int -> OrbitClockBoundDegradation -> ShowS # show :: OrbitClockBoundDegradation -> String # showList :: [OrbitClockBoundDegradation] -> ShowS # | |
Binary OrbitClockBoundDegradation Source # | |
Defined in SwiftNav.SBP.Ssr put :: OrbitClockBoundDegradation -> Put # get :: Get OrbitClockBoundDegradation # putList :: [OrbitClockBoundDegradation] -> Put # | |
Eq OrbitClockBoundDegradation Source # | |
Defined in SwiftNav.SBP.Ssr |
msgSsrCodePhaseBiasesBounds_satellites_signals :: Lens' MsgSsrCodePhaseBiasesBounds [CodePhaseBiasesSatSig] Source #
data MsgSsrOrbitClockBoundsDegradation Source #
MsgSsrOrbitClockBoundsDegradation | |
|
Instances
orbitClockBoundDegradation_orb_along_bound_mu_dot :: Lens' OrbitClockBoundDegradation Word8 Source #
orbitClockBoundDegradation_orb_along_bound_sig_dot :: Lens' OrbitClockBoundDegradation Word8 Source #
orbitClockBoundDegradation_orb_cross_bound_mu_dot :: Lens' OrbitClockBoundDegradation Word8 Source #
orbitClockBoundDegradation_orb_cross_bound_sig_dot :: Lens' OrbitClockBoundDegradation Word8 Source #
orbitClockBoundDegradation_orb_radial_bound_mu_dot :: Lens' OrbitClockBoundDegradation Word8 Source #
orbitClockBoundDegradation_orb_radial_bound_sig_dot :: Lens' OrbitClockBoundDegradation Word8 Source #
msgSsrOrbitClockBoundsDegradation_const_id :: Lens' MsgSsrOrbitClockBoundsDegradation Word8 Source #
msgSsrOrbitClockBoundsDegradation_header :: Lens' MsgSsrOrbitClockBoundsDegradation BoundsHeader Source #
msgSsrOrbitClockBoundsDegradation_orbit_clock_bounds_degradation :: Lens' MsgSsrOrbitClockBoundsDegradation OrbitClockBoundDegradation Source #