Skip to content

Commit

Permalink
CADS for CrIS instruments requires band 1 ( channels 1 -713 ) to exis…
Browse files Browse the repository at this point in the history
…t. CrIS band 1 on NPP has failed. The band 1 failure creates a lot of I/O statements from the CADS cloud test quality control. These changes reject CrIS profiles when cris_cads = .true. and band 1 is missing. If cris_cads = .false., nothing changes. The verbose flag was also added to the CADS output.
  • Loading branch information
wx20jjung committed Nov 13, 2023
1 parent 3858863 commit ac16db4
Show file tree
Hide file tree
Showing 3 changed files with 18 additions and 9 deletions.
21 changes: 15 additions & 6 deletions src/gsi/cads.f90
Original file line number Diff line number Diff line change
Expand Up @@ -342,6 +342,7 @@ SUBROUTINE CADS_Setup_Cloud
! 16/04/20 R.Eresmaa 3.0 Rename, tidy up.

use kinds, only: i_kind, r_kind
use gsi_io, only: verbose
IMPLICIT NONE

! Local variables
Expand Down Expand Up @@ -895,15 +896,22 @@ SUBROUTINE CADS_Setup_Cloud
FILE=TRIM(CL__Cloud_Detection_File), IOSTAT=IOS)
IF (IOS == 0) THEN
READ(INIU1,nml=Cloud_Detect_Coeffs,IOSTAT=IOS)
IF (IOS /= 0) &
IF (IOS == 0) THEN
if ( verbose ) WRITE(*,'(3X,A)') TRIM(CL__InstrumentName) // &
' CLOUD DETECTION FILE READ OK'
ELSE
CALL CADS_Abort('PROBLEM READING '//TRIM(CL__InstrumentName)//&
'CLOUD DETECTION FILE')
ENDIF
CLOSE(INIU1)
ELSE
if ( verbose ) WRITE(*,'(3X,A)') 'NO '//TRIM(CL__InstrumentName) // &
' CLOUD DETECTION FILE : Using Default Values'
ENDIF
CLOSE(INIU1)

IF (MAXVAL(N__Band_Size(:)) > JP__Max_Channels) &
CALL CADS_Abort('Too many channels specified in cloud '//&
'detection - increase JP__Max_Channels')
IF (MAXVAL(N__Band_Size(:)) > JP__Max_Channels) &
CALL CADS_Abort('Too many channels specified in cloud '//&
'detection - increase JP__Max_Channels')


M__Sensor = J__SENSOR
Expand Down Expand Up @@ -1084,6 +1092,7 @@ SUBROUTINE CADS_Detect_Cloud( K__Sensor, K__NChans, K__ChanID, K__Minlev, K__
! R.Eresmaa 3.0 16/04/20 Move the call to imager-based detection here.

use kinds, only: i_kind, r_kind
use gsi_io, only: verbose
IMPLICIT NONE

!* 0.1 Global arrays
Expand Down Expand Up @@ -1221,7 +1230,7 @@ SUBROUTINE CADS_Detect_Cloud( K__Sensor, K__NChans, K__ChanID, K__Minlev, K__
ENDDO
ENDDO
IF ( I__NumFoundChans == 0 ) THEN
WRITE(*,*) &
if (verbose) WRITE(*,*) &
'**CADS_Detect_Cloud - WARNING: ' // &
'CHANNELS NOT FOUND CYCLING BAND: **', JBAND
IF (ALLOCATED(Z__DBT)) DEALLOCATE (Z__DBT)
Expand Down
4 changes: 2 additions & 2 deletions src/gsi/read_cris.f90
Original file line number Diff line number Diff line change
Expand Up @@ -820,12 +820,12 @@ subroutine read_cris(mype,val_cris,ithin,isfcalc,rmesh,jsatid,gstime,&
bufr_chan = bufr_index(i)
if(temperature(bufr_chan) <= tbmin .or. temperature(bufr_chan) >= tbmax ) then
temperature(bufr_chan) = tbmin
if(iuse_rad(ioff+i) >= 0) iskip = iskip + 1
if(iuse_rad(ioff+i) >= 0 .or. (cris_cads .and. sc_index(i) < 714)) iskip = iskip + 1
endif
end do skip_loop

if(iskip > 0 .and. print_verbose)write(6,*) ' READ_CRIS : iskip > 0 ',iskip
! if( iskip >= 10 )cycle read_loop
if( iskip >= 10 .and. cris_cads ) cycle read_loop

crit1=crit1 + ten*real(iskip,r_kind)

Expand Down
2 changes: 1 addition & 1 deletion src/gsi/setuprad.f90
Original file line number Diff line number Diff line change
Expand Up @@ -246,7 +246,7 @@ subroutine setuprad(obsLL,odiagLL,lunin,mype,aivals,stats,nchanl,nreal,nobs,&
npred,jpch_rad,varch,varch_cld,iuse_rad,icld_det,nusis,fbias,retrieval,b_rad,pg_rad,&
air_rad,ang_rad,adp_anglebc,angord,ssmis_precond,emiss_bc,upd_pred, &
passive_bc,ostats,rstats,newpc4pred,radjacnames,radjacindxs,nsigradjac,nvarjac, &
varch_sea,varch_land,varch_ice,varch_snow,varch_mixed,crtm_coeffs_path
varch_sea,varch_land,varch_ice,varch_snow,varch_mixed
use gsi_nstcouplermod, only: nstinfo
use read_diag, only: get_radiag,ireal_radiag,ipchan_radiag
use guess_grids, only: sfcmod_gfs,sfcmod_mm5,comp_fact10
Expand Down

0 comments on commit ac16db4

Please sign in to comment.