Skip to content

Commit

Permalink
add option to allow zero obs in the obsfile (#179)
Browse files Browse the repository at this point in the history
  • Loading branch information
gmao-cda authored Aug 15, 2023
1 parent efa8e9e commit bb8f59c
Show file tree
Hide file tree
Showing 2 changed files with 13 additions and 7 deletions.
14 changes: 10 additions & 4 deletions src/model_specific/mom6/common_obs_mom6.f90.kdtree
Original file line number Diff line number Diff line change
Expand Up @@ -621,19 +621,23 @@ END SUBROUTINE monit_dep
!-----------------------------------------------------------------------
! Basic modules for observation input
!-----------------------------------------------------------------------
SUBROUTINE get_nobs(cfile,nrec,nn)
SUBROUTINE get_nobs(cfile,nrec,nn,errIfNoObs)
CHARACTER(*),INTENT(IN) :: cfile
INTEGER,INTENT(IN) :: nrec
INTEGER,INTENT(OUT) :: nn
LOGICAL,INTENT(IN),OPTIONAL :: errIfNoObs
REAL(r_sngl),ALLOCATABLE :: wk(:)
INTEGER :: ios
INTEGER :: iu,iv,it,is,issh,ieta,isst,isss,ix,iy,iz !(OCEAN)
INTEGER :: nprof !(OCEAN)
REAL(r_sngl) :: lon_m1, lat_m1
INTEGER :: iunit
LOGICAL :: ex
LOGICAL :: ex, errIfNoObs_
LOGICAL, PARAMETER :: dodebug=.false.

errIfNoObs_ = .true.
if (PRESENT(errIfNoObs)) errIfNoObs_ = errIfNoObs

ALLOCATE(wk(nrec))
nn = 0
iu = 0
Expand Down Expand Up @@ -716,8 +720,10 @@ SUBROUTINE get_nobs(cfile,nrec,nn)
DEALLOCATE(wk)

if (nn .eq. 0) then
WRITE(6,*) "get_nobs:: No observations have been found. Exiting..."
STOP (60)
if (errIfNoObs_) then
WRITE(6,*) "get_nobs:: No observations have been found. Exiting..."
STOP (60)
endif
endif

END SUBROUTINE get_nobs
Expand Down
6 changes: 3 additions & 3 deletions src/obs/obsop_sst_viirs.f90
Original file line number Diff line number Diff line change
Expand Up @@ -108,10 +108,10 @@ PROGRAM obsop_sst_viirs

if (BINARY_INPUT) then ![processed binary input]
print *, "obsop_sst_viirs.f90:: reading binary file=",trim(obsinfile)
CALL get_nobs(trim(obsinfile),8,nobs)
CALL get_nobs(trim(obsinfile),8,nobs,errIfNoObs=.false.)

if (nobs<0) then
print*, "obsop_sst_viirs.f90: nobs<=0. Exit now..."
if (nobs<=0) then
print*, "obsop_sst_viirs.f90: nobs=",nobs,"<=0. Exit now..."
STOP (0)
endif

Expand Down

0 comments on commit bb8f59c

Please sign in to comment.