Skip to content

Commit

Permalink
Merge pull request #181 from gmao-cda/bugfix/cda/obsop_sss
Browse files Browse the repository at this point in the history
update SSS processing & obsop
  • Loading branch information
cd10kfsu authored Oct 18, 2023
2 parents ab3e74f + 3e8c0dd commit 1d08cfc
Show file tree
Hide file tree
Showing 3 changed files with 24 additions and 1 deletion.
4 changes: 4 additions & 0 deletions src/obs/obsop_sss.f90
Original file line number Diff line number Diff line change
Expand Up @@ -488,6 +488,10 @@ SUBROUTINE process_command_line
CALL GET_COMMAND_ARGUMENT(i+1,arg2)
PRINT *, "Argument ", i+1, " = ",TRIM(arg2)
read (arg2,*) DO_SUPEROBS
case('-binary')
CALL GET_COMMAND_ARGUMENT(i+1,arg2)
PRINT *, "Argument ", i+1, " = ",TRIM(arg2)
read (arg2,*) BINARY_INPUT
case('-thin')
CALL GET_COMMAND_ARGUMENT(i+1,arg2)
PRINT *, "Argument ", i+1, " = ",TRIM(arg2)
Expand Down
7 changes: 6 additions & 1 deletion src/obs/read_smap.f90
Original file line number Diff line number Diff line change
Expand Up @@ -253,6 +253,8 @@ SUBROUTINE read_jpl_smap_l2_sss_h5(obsinfile, obs_data, nobs, Syyyymmddhh, delta
INTEGER,PARAMETER :: QUAL_FLAG_SSS_USABLE_BAD = 1
INTEGER,PARAMETER :: QUAL_FLAG_SSS_HAS_LAND = 1
INTEGER,PARAMETER :: QUAL_FLAG_SSS_HAS_ICE = 1
REAL(r_size),PARAMETER :: oerr_qc_user = 2.0 ! psu, obs with JPL > oerr_qc_user removed
REAL(r_size),PARAMETER :: oerr_min_user = 0.2 ! psu, obs with JPL oerr < oerr_min_user has err oerr_min_user

!-------------------------------------------------------------------------------
! Open the hdf5 file
Expand Down Expand Up @@ -393,6 +395,9 @@ SUBROUTINE read_jpl_smap_l2_sss_h5(obsinfile, obs_data, nobs, Syyyymmddhh, delta
where(stde < r4FillValue)
valid = .false.
end where
where(stde > oerr_qc_user) ! User QC based on read-in oerr
valid = .false.
end where
WRITE(6,*) "[msg] read_jpl_smap_l2_sss_h5::smap_sss_uncertainty: min, max=", &
minval(stde, mask=valid), maxval(stde, mask=valid)

Expand Down Expand Up @@ -481,7 +486,7 @@ SUBROUTINE read_jpl_smap_l2_sss_h5(obsinfile, obs_data, nobs, Syyyymmddhh, delta
obs_data(n)%x_grd(2) = alat2d(i,j)
obs_data(n)%hour = sss_time_in_seconds_since19780101(i)/3600.
obs_data(n)%value = sea_surface_salinity(i,j)
obs_data(n)%oerr = stde(i,j)
obs_data(n)%oerr = max(stde(i,j), oerr_min_user) ! set a limit bound for error
end if
end do
end do
Expand Down
14 changes: 14 additions & 0 deletions src/obs/superob.f90
Original file line number Diff line number Diff line change
Expand Up @@ -64,6 +64,8 @@ PROGRAM superob
INTEGER, DIMENSION(:,:), ALLOCATABLE :: supercnt
INTEGER :: idx
REAL(r_size) :: min_oerr = 0.2 !(K)
REAL(r_size) :: input_oerr = 0.75 ! (K)
LOGICAL :: HAS_INPUT_OERR = .false.

!-----------------------------------------------------------------------------
! Initialize the common_oceanmodel module, and process command line options
Expand Down Expand Up @@ -181,6 +183,10 @@ PROGRAM superob
nobs = idx
endif

if (HAS_INPUT_OERR) then
oerr(:) = input_oerr
endif

call write_obs3(trim(obsoutfile),nobs,elem(1:nobs), &
rlon(1:nobs), &
rlat(1:nobs), &
Expand Down Expand Up @@ -243,6 +249,14 @@ SUBROUTINE process_command_line
CALL GET_COMMAND_ARGUMENT(i+1,arg2)
PRINT *, "Argument ", i+1, " = ",TRIM(arg2)
read (arg2,*) min_quality_level
case('-inputoerr')
CALL GET_COMMAND_ARGUMENT(i+1,arg2)
PRINT *, "Argument ", i+1, " = ",TRIM(arg2)
read (arg2,*) HAS_INPUT_OERR
case('-useroerr')
CALL GET_COMMAND_ARGUMENT(i+1,arg2)
PRINT *, "Argument ", i+1, " = ",TRIM(arg2)
read (arg2,*) input_oerr
case('-debug')
CALL GET_COMMAND_ARGUMENT(i+1,arg2)
PRINT *, "Argument ", i+1, " = ",TRIM(arg2)
Expand Down

0 comments on commit 1d08cfc

Please sign in to comment.