Skip to content

Commit

Permalink
1. Reorganize the section for parallelization_over_ensmembers
Browse files Browse the repository at this point in the history
2. Add namlelist consistency check for fed and dbz DA
	modified:   cplr_get_fv3_regional_ensperts.f90
	modified:   gsimod.F90
	modified:   read_fed.f90
	modified:   wrf_vars_mod.f90
  • Loading branch information
hongli-wang committed Oct 27, 2023
1 parent 2372b4d commit 95cd412
Show file tree
Hide file tree
Showing 4 changed files with 97 additions and 66 deletions.
125 changes: 76 additions & 49 deletions src/gsi/cplr_get_fv3_regional_ensperts.f90
Original file line number Diff line number Diff line change
Expand Up @@ -406,34 +406,52 @@ subroutine get_fv3_regional_ensperts_run(this,en_perts,nelen,ps_bar)
endif
!
! READ ENEMBLE MEMBERS DATA
if( .not. parallelization_over_ensmembers )then
if (mype == 0) write(6,'(a,a)') &
'CALL READ_FV3_REGIONAL_ENSPERTS FOR ENS DATA with the filename str : ',trim(ensfilenam_str)

! There are three options to control the list of variables that
! will be read in along with the basic variables, ps,u,v,tv,rh,oz.
! Here the 6 cases that are considered in
! the current applications are listed as of Oct 20 2023.
!
! There are three options to control the list of variables that
! will be read in along with the basic variables, ps,u,v,tv,rh,oz.

! parallelization_over_ensmembers=.True. only works for cases when l_use_dbz_directDA=.False.
! Noted that l_use_dbz_directDA and if_modle_dbz couldn't be true at the same time

!
! I_CASEFLAG defination
!

! default: all the three options ( l_use_dbz_directDA, if_model_dbz, if_model_fed) are turned off .i.e.,
! if(.not. (l_use_dbz_directDA .or. if_model_dbz .or. if_model_fed ))
! read in ps,u,v,tv,rh,oz
i_caseflag=0

! only l_use_dbz_directDA is true
if (l_use_dbz_directDA .and. .not.if_model_dbz .and. .not.if_model_fed) i_caseflag=1

! only if_model_dbz is true
if(.not.l_use_dbz_directDA .and. if_model_dbz .and. .not.if_model_fed) i_caseflag=2

! default: all the three options ( l_use_dbz_directDA, if_model_dbz, if_model_fed) are turned off .i.e.,
! if(.not. (l_use_dbz_directDA .or. if_model_dbz .or. if_model_fed ))
i_caseflag=0 ! read in ps,u,v,tv,rh,oz
! only if_model_fed is true
if(.not.l_use_dbz_directDA .and. .not.if_model_dbz .and. .not.if_model_fed) i_caseflag=3

! only l_use_dbz_directDA is true
if (l_use_dbz_directDA .and. .not.if_model_dbz .and. .not.if_model_fed) i_caseflag=1
! l_use_dbz_directDA=.true. and if_model_fed=.true.
if(l_use_dbz_directDA .and. .not.if_model_dbz .and. if_model_fed) i_caseflag=4

! only if_model_dbz is true
if(.not.l_use_dbz_directDA .and. if_model_dbz .and. .not.if_model_fed) i_caseflag=2
! if_model_dbz=.true. and if_model_fed=.true.
if(.not. l_use_dbz_directDA.and. if_model_dbz .and. if_model_fed) i_caseflag=5

! only if_model_fed is true
if(.not.l_use_dbz_directDA .and. .not.if_model_dbz .and. .not.if_model_fed) i_caseflag=3

!--------------------------------------------------
! When .not. parallelization_over_ensmembers=.True.
! All the above 6 cases (i_caseflag=0,1,2,3,4,5) are valid in
! the current applications as of Oct 20 2023.

! l_use_dbz_directDA=.true. and if_model_fed=.true.
if(l_use_dbz_directDA .and. .not.if_model_dbz .and. if_model_fed) i_caseflag=4
!--------------------------------------------
! When parallelization_over_ensmembers=.True.
! Only i_flagcase=0,2,3,5 are vaild choices.

! if_model_dbz=.true. and if_model_fed=.true.
if(.not. l_use_dbz_directDA.and. if_model_dbz .and. if_model_fed) i_caseflag=5

if( .not. parallelization_over_ensmembers )then
if (mype == 0) write(6,'(a,a)') &
'CALL READ_FV3_REGIONAL_ENSPERTS FOR ENS DATA with the filename str : ',trim(ensfilenam_str)

select case (i_caseflag)
case (0)
call this%general_read_fv3_regional(fv3_filename,ps,u,v,tv,rh,oz)
Expand All @@ -459,49 +477,58 @@ subroutine get_fv3_regional_ensperts_run(this,en_perts,nelen,ps_bar)
iope=(n_fv3sar-1)*npe/n_ens_fv3sar
if(mype==iope) then
write(0,'(I0,A,I0,A)') mype,': scatter member ',n_fv3sar,' to other ranks...'
if( if_model_dbz .and. if_model_fed)then
call this%parallel_read_fv3_step2(mype,iope,&
g_ps=ps,g_u=u,g_v=v,g_tv=tv,g_rh=rh,g_ql=ql,&
g_oz=oz,g_w=w,g_qr=qr,g_qs=qs,g_qi=qi,g_qg=qg,g_dbz=dbz,g_fed=fed,&
gg_ps=gg_ps,gg_tv=gg_tv,gg_u=gg_u,gg_v=gg_v,&
gg_rh=gg_rh,gg_w=gg_w,gg_dbz=gg_dbz,gg_fed=gg_fed,gg_qr=gg_qr,&
gg_qs=gg_qs,gg_qi=gg_qi,gg_qg=gg_qg,gg_ql=gg_cwmr)
elseif( if_model_dbz )then
call this%parallel_read_fv3_step2(mype,iope,&
select case (i_caseflag)
case (0)
call this%parallel_read_fv3_step2(mype,iope,&
g_ps=ps,g_u=u,g_v=v,g_tv=tv,g_rh=rh,g_ql=ql,g_oz=oz, &
gg_ps=gg_ps,gg_tv=gg_tv,gg_u=gg_u,gg_v=gg_v,gg_rh=gg_rh)
case (2)
call this%parallel_read_fv3_step2(mype,iope,&
g_ps=ps,g_u=u,g_v=v,g_tv=tv,g_rh=rh,g_ql=ql,&
g_oz=oz,g_w=w,g_qr=qr,g_qs=qs,g_qi=qi,g_qg=qg,g_dbz=dbz,&
gg_ps=gg_ps,gg_tv=gg_tv,gg_u=gg_u,gg_v=gg_v,&
gg_rh=gg_rh,gg_w=gg_w,gg_dbz=gg_dbz,gg_qr=gg_qr,&
gg_qs=gg_qs,gg_qi=gg_qi,gg_qg=gg_qg,gg_ql=gg_cwmr)
elseif( if_model_fed )then
call this%parallel_read_fv3_step2(mype,iope,&
case (3)
call this%parallel_read_fv3_step2(mype,iope,&
g_ps=ps,g_u=u,g_v=v,g_tv=tv,g_rh=rh,g_ql=ql,&
g_oz=oz,g_w=w,g_qr=qr,g_qs=qs,g_qi=qi,g_qg=qg,g_fed=fed,&
gg_ps=gg_ps,gg_tv=gg_tv,gg_u=gg_u,gg_v=gg_v,&
gg_rh=gg_rh,gg_w=gg_w,gg_fed=gg_fed,gg_qr=gg_qr,&
gg_qs=gg_qs,gg_qi=gg_qi,gg_qg=gg_qg,gg_ql=gg_cwmr)
else
call this%parallel_read_fv3_step2(mype,iope,&
g_ps=ps,g_u=u,g_v=v,g_tv=tv,g_rh=rh,g_ql=ql,g_oz=oz, &
gg_ps=gg_ps,gg_tv=gg_tv,gg_u=gg_u,gg_v=gg_v,gg_rh=gg_rh)
end if
else
if( if_model_dbz .and. if_model_fed)then
call this%parallel_read_fv3_step2(mype,iope,&
case (5)
call this%parallel_read_fv3_step2(mype,iope,&
g_ps=ps,g_u=u,g_v=v,g_tv=tv,g_rh=rh,g_ql=ql,&
g_oz=oz,g_w=w,g_qr=qr,g_qs=qs,g_qi=qi,g_qg=qg,g_dbz=dbz,g_fed=fed)
elseif( if_model_dbz )then
call this%parallel_read_fv3_step2(mype,iope,&
g_oz=oz,g_w=w,g_qr=qr,g_qs=qs,g_qi=qi,g_qg=qg,g_dbz=dbz,g_fed=fed,&
gg_ps=gg_ps,gg_tv=gg_tv,gg_u=gg_u,gg_v=gg_v,&
gg_rh=gg_rh,gg_w=gg_w,gg_dbz=gg_dbz,gg_fed=gg_fed,gg_qr=gg_qr,&
gg_qs=gg_qs,gg_qi=gg_qi,gg_qg=gg_qg,gg_ql=gg_cwmr)
case (1,4)
write(6,*)'i_case_flag=1 or 4 is not a valid choice for parallelization_over_ensmembers=.T. Stop(8880) '
call stop2(8880)
end select
else
select case (i_caseflag)
case (0)
call this%parallel_read_fv3_step2(mype,iope,&
g_ps=ps,g_u=u,g_v=v,g_tv=tv,g_rh=rh,g_ql=ql,g_oz=oz)
case (2)
call this%parallel_read_fv3_step2(mype,iope,&
g_ps=ps,g_u=u,g_v=v,g_tv=tv,g_rh=rh,g_ql=ql,&
g_oz=oz,g_w=w,g_qr=qr,g_qs=qs,g_qi=qi,g_qg=qg,g_dbz=dbz)
elseif( if_model_fed )then
call this%parallel_read_fv3_step2(mype,iope,&
case (3)
call this%parallel_read_fv3_step2(mype,iope,&
g_ps=ps,g_u=u,g_v=v,g_tv=tv,g_rh=rh,g_ql=ql,&
g_oz=oz,g_w=w,g_qr=qr,g_qs=qs,g_qi=qi,g_qg=qg,g_fed=fed)
else
call this%parallel_read_fv3_step2(mype,iope,&
g_ps=ps,g_u=u,g_v=v,g_tv=tv,g_rh=rh,g_ql=ql,g_oz=oz)
endif
case (5)
call this%parallel_read_fv3_step2(mype,iope,&
g_ps=ps,g_u=u,g_v=v,g_tv=tv,g_rh=rh,g_ql=ql,&
g_oz=oz,g_w=w,g_qr=qr,g_qs=qs,g_qi=qi,g_qg=qg,g_dbz=dbz,g_fed=fed)
case (1,4)
write(6,*)'i_case_flag=1 or 4 is not a valid choice for parallelization_over_ensmembers=.T. Stop(8880) '
call stop2(8880)
end select

endif

call MPI_Barrier(mpi_comm_world,ierror)
Expand Down
17 changes: 11 additions & 6 deletions src/gsi/gsimod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -203,7 +203,7 @@ module gsimod
use gsi_nstcouplermod, only: gsi_nstcoupler_init_nml
use gsi_nstcouplermod, only: nst_gsi,nstinfo,zsea1,zsea2,fac_dtl,fac_tsl
use ncepnems_io, only: init_nems,imp_physics,lupp
use wrf_vars_mod, only: init_wrf_vars,fed_exist
use wrf_vars_mod, only: init_wrf_vars,fed_exist,dbz_exist
use gsi_rfv3io_mod,only : fv3sar_bg_opt
use radarz_cst, only: mphyopt, MFflg
use radarz_iface, only: init_mphyopt
Expand Down Expand Up @@ -515,7 +515,7 @@ module gsimod
! 2023-09-14 H. Wang - add namelist option for FED EnVar DA.
! - if_model_fed=.true. : FED in background and ens. If
! perform FED DA, this has to be true along with fed in
! control/analysis variable list. If only run GSI observer,
! control/analysis and metguess vectors. If only run GSI observer,
! it can be false.
! - innov_use_model_fed=.true. : Use FED from BG to calculate innovation.
! this requires if_model_fed=.true.
Expand Down Expand Up @@ -1991,12 +1991,17 @@ subroutine gsimain_initialize

if (innov_use_model_fed .and. .not.if_model_fed) then
if(mype==0) write(6,*)' GSIMOD: invalid innov_use_model_fed=.true. but if_model_fed=.false.'
call die(myname_,'invalid innov_use_model_fed,if_model_fed, check namelist settings',332)
call die(myname_,'invalid innov_use_model_fed,if_model_fed, check namelist settings',330)
end if

if (miter > 0 .and. if_model_fed .and. .not. fed_exist) then
if(mype==0) write(6,*)' GSIMOD: invalid miter > 0 and if_model_fed=.true. but fed is not in anavinfo file'
call die(myname_,'Please add fed in anavinfo (contro/state_vector and met_guess) when miter > 0 and if_model_fed=.true.',334)
if (.not. (miter == 0 .or. lobserver) .and. if_model_fed .and. .not. fed_exist) then
if(mype==0) write(6,*)' GSIMOD: .not. (miter == 0 .or. lobserver) and if_model_fed=.true. but fed is not in anavinfo file'
call die(myname_,'Please check namelist parameters and/or add fed in anavinfo (contro/state_vector and met_guess) when miter > 0 and if_model_fed=.true.',332)
end if

if (.not. (miter == 0 .or. lobserver) .and. if_model_dbz .and. .not. dbz_exist) then
if(mype==0) write(6,*)' GSIMOD: .not. (miter == 0 .or. lobserver) and if_model_dbz=.true. but dbz is not in anavinfo file'
call die(myname_,'Please check namelist parameters and/or add dbz in anavinfo (contro/state_vector and met_guess) when miter > 0 and if_model_fed=.true.',334)
end if

! Ensure valid number of horizontal scales
Expand Down
15 changes: 7 additions & 8 deletions src/gsi/read_fed.f90
Original file line number Diff line number Diff line change
Expand Up @@ -35,9 +35,9 @@ subroutine read_fed(nread,ndata,nodata,infile,obstype,lunout,twind,sis,nobs)
!_____________________________________________________________________
!
use kinds, only: r_kind,r_double,i_kind
use constants, only: zero,one,deg2rad
use constants, only: zero,one,deg2rad,r60inv
use convinfo, only: nconvtype,ctwind,icuse,ioctype
use gsi_4dvar, only: l4dvar,l4densvar
use gsi_4dvar, only: iwinbgn
use gridmod, only: tll2xy
use mod_wrfmass_to_a, only: wrfmass_obs_to_a8
use mpimod, only: npe
Expand Down Expand Up @@ -115,11 +115,6 @@ subroutine read_fed(nread,ndata,nodata,infile,obstype,lunout,twind,sis,nobs)
real(r_kind) :: timeb,twindm,rmins_an,rmins_ob


if (l4dvar.or.l4densvar) then
write(6,*) 'FED obs type is not set up for l4dvar.or.l4densvar. STOP92'
call stop2(92)
end if

hgt_fed = r_hgt_fed

write(6,*) "r_kind=",r_kind
Expand Down Expand Up @@ -224,6 +219,10 @@ subroutine read_fed(nread,ndata,nodata,infile,obstype,lunout,twind,sis,nobs)
if(abs(timeb) > abs(twindm)) then
print*, 'WARNING: ALL FED OBSERVATIONS OUTSIDE ASSIMILATION TIME WINDOW: ', timeb, twindm
endif

!time relative to the beginning of the da time window
timeb=real(mins_an-iwinbgn,r_kind)

numfed = maxobs
do i=1,numfed
if (fed3d_column( 3, i ) >= fed_lowbnd2 .or. fed3d_column( 3, i ) == fed_lowbnd ) then
Expand Down Expand Up @@ -315,7 +314,7 @@ subroutine read_fed(nread,ndata,nodata,infile,obstype,lunout,twind,sis,nobs)
cdata_out( 6,ndata2) = rstation_id ! station id (charstring equivalent to real double)
! id=6 ! index of station id

cdata_out( 7,ndata2) = 0.0_r_kind ! observation time in data array
cdata_out( 7,ndata2) = timeb*r60inv ! observation time in data array
! itime=7 ! index of observation time in data array
cdata_out( 8,ndata2) = ikx ! ob type
! ikxx=8 ! index of ob type
Expand Down
6 changes: 3 additions & 3 deletions src/gsi/wrf_vars_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -90,9 +90,9 @@ subroutine init_wrf_vars
fed_exist=.false.
endif

!if(.not.dbz_exist .or. .not.fed_cloud_exist )then
! dbz_exist=.false.
!endif
if(.not.dbz_exist .or. .not.dbz_cloud_exist )then
dbz_exist=.false.
endif

if(ncloud>0) deallocate(cloud)

Expand Down

0 comments on commit 95cd412

Please sign in to comment.