Skip to content

Commit

Permalink
better handling of date/time
Browse files Browse the repository at this point in the history
  • Loading branch information
rtodling committed Mar 8, 2024
1 parent b7faf16 commit c8ac58d
Show file tree
Hide file tree
Showing 10 changed files with 63 additions and 219 deletions.
2 changes: 1 addition & 1 deletion CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
################################################################################

cmake_minimum_required( VERSION 3.12 )
project( gsibec VERSION 1.1.3 LANGUAGES Fortran )
project( gsibec VERSION 1.2.1 LANGUAGES Fortran )

## Ecbuild integration
set( ECBUILD_DEFAULT_BUILD_TYPE Release )
Expand Down
8 changes: 4 additions & 4 deletions src/gsibec/gsi/abstract_ensmod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -65,7 +65,7 @@ end subroutine destroy_sub2grid_info
end interface

abstract interface
subroutine get_user_ens(this,grd,member,ntindex,tau,atm_bundle,iret)
subroutine get_user_ens(this,grd,member,nymd,nhms,tau,atm_bundle,iret)
use m_kinds, only: i_kind
use general_sub2grid_mod, only: sub2grid_info
use gsi_bundlemod, only: gsi_bundle
Expand All @@ -74,15 +74,15 @@ subroutine get_user_ens(this,grd,member,ntindex,tau,atm_bundle,iret)
class(abstractEnsemble), intent(inout) :: this
type(sub2grid_info), intent(in ) :: grd
integer(i_kind), intent(in ) :: member
integer(i_kind), intent(in ) :: ntindex
integer(i_kind), intent(in ) :: nymd,nhms
integer(i_kind), intent(in ) :: tau
type(gsi_bundle), intent(inout) :: atm_bundle
integer(i_kind), intent( out) :: iret
end subroutine get_user_ens
end interface

abstract interface
subroutine get_user_Nens(this,grd,members,ntindex,tau,atm_bundle,iret)
subroutine get_user_Nens(this,grd,members,nymd,nhms,tau,atm_bundle,iret)
use m_kinds, only: i_kind
use general_sub2grid_mod, only: sub2grid_info
use gsi_bundlemod, only: gsi_bundle
Expand All @@ -91,7 +91,7 @@ subroutine get_user_Nens(this,grd,members,ntindex,tau,atm_bundle,iret)
class(abstractEnsemble), intent(inout) :: this
type(sub2grid_info), intent(in ) :: grd
integer(i_kind), intent(in ) :: members
integer(i_kind), intent(in ) :: ntindex
integer(i_kind), intent(in ) :: nymd,nhms
integer(i_kind), intent(in ) :: tau
type(gsi_bundle), intent(inout) :: atm_bundle(:)
integer(i_kind), intent( out) :: iret
Expand Down
25 changes: 16 additions & 9 deletions src/gsibec/gsi/get_gefs_ensperts_dualres.F90
Original file line number Diff line number Diff line change
Expand Up @@ -51,6 +51,7 @@ subroutine get_gefs_ensperts_dualres (tau)
use mpeu_util, only: die
use gridmod, only: idsl5
use hybrid_ensemble_parameters, only: n_ens,write_ens_sprd,oz_univ_static,ntlevs_ens
use hybrid_ensemble_parameters, only: nymd,nhms
use hybrid_ensemble_parameters, only: sst_staticB
use hybrid_ensemble_parameters, only: bens_recenter
use hybrid_ensemble_parameters, only: en_perts,ps_bar,nelen
Expand Down Expand Up @@ -162,7 +163,7 @@ subroutine get_gefs_ensperts_dualres (tau)

en_bar(m)%values=zero

call gsi_enscoupler_get_user_Nens(grd_tmp,n_ens,m,tau,en_read,iret)
call gsi_enscoupler_get_user_Nens(grd_tmp,n_ens,nymd(m),nhms(m),tau,en_read,iret)

! Check read return code. Revert to static B if read error detected
if ( iret /= 0 ) then
Expand Down Expand Up @@ -366,7 +367,7 @@ subroutine get_gefs_ensperts_dualres (tau)
! Before converting to perturbations, get ensemble spread
!-- if (m == 1 .and. write_ens_sprd ) call ens_spread_dualres(en_bar(1),1)
!!! the follwing call is not thread/$omp safe -> omp deactivted above.
if (write_ens_sprd) call ens_spread_dualres(en_bar(m),m)
if (write_ens_sprd) call ens_spread_dualres(en_bar(m),m,nymd(m),nhms(m))


call gsi_bundlegetpointer(en_bar(m),'ps',x2,istatus)
Expand Down Expand Up @@ -475,7 +476,7 @@ subroutine get_gefs_ensperts_dualres (tau)
return
end subroutine get_gefs_ensperts_dualres

subroutine ens_spread_dualres(en_bar,ibin)
subroutine ens_spread_dualres(en_bar,ibin,nymd,nhms)
!$$$ subprogram documentation block
! . . . .
! subprogram: ens_spread_dualres output ensemble spread for diagnostics
Expand Down Expand Up @@ -527,7 +528,7 @@ subroutine ens_spread_dualres(en_bar,ibin)
implicit none

type(gsi_bundle),intent(in):: en_bar
integer(i_kind),intent(in):: ibin
integer(i_kind),intent(in):: ibin,nymd,nhms

type(gsi_bundle):: sube,suba
type(gsi_grid):: grid_ens,grid_anl
Expand Down Expand Up @@ -622,13 +623,13 @@ subroutine ens_spread_dualres(en_bar,ibin)
call general_sube2suba(se,sa,p_e2a,sube%values,suba%values,regional)
end if

call write_spread_dualres(ibin,suba)
call write_spread_dualres(nymd,nhms,suba)

return
end subroutine ens_spread_dualres


subroutine write_spread_dualres(ibin,bundle)
subroutine write_spread_dualres(nymd,nhms,bundle)
!$$$ subprogram documentation block
! . . . .
! subprogram: write_spread_dualres write ensemble spread for diagnostics
Expand Down Expand Up @@ -678,7 +679,7 @@ subroutine write_spread_dualres(ibin,bundle)
#endif /* HAVE_BACIO */
implicit none

integer(i_kind), intent(in) :: ibin
integer(i_kind), intent(in) :: nymd,nhms
type(gsi_bundle):: bundle

! local variables
Expand Down Expand Up @@ -711,7 +712,10 @@ subroutine write_spread_dualres(ibin,bundle)

lu=get_lun()
if (mype==0) then
write(grdfile,'(a,2(i3.3,a))') 'ens_spread_',ibin, '.iter' ,jiter, '.grd'
write(grdfile,'(a,(i8.8,a),(i6.6,a),(i3.3,a))') 'ens_spread_', &
nymd, '_', &
nhms, '.iter', &
jiter, '.grd'
#ifdef HAVE_BACIO
call baopenwt(lu,trim(grdfile),iret)
#else /* HAVE_BACIO */
Expand Down Expand Up @@ -811,7 +815,10 @@ subroutine write_spread_dualres(ibin,bundle)
! Write out a corresponding grads control file
if (mype==0) then
lu=get_lun()
write(grdctl,'(a,2(i3.3,a))') 'ens_spread_',ibin, '.iter' ,jiter, '.ctl'
write(grdctl,'(a,(i8.8,a),(i6.6,a),(i3.3,a))') 'ens_spread_', &
nymd, '_', &
nhms, '.iter', &
jiter, '.ctl'
open(newunit=lu,file=trim(grdctl),form='formatted')
write(lu,'(2a)') 'DSET ^', trim(grdfile)
write(lu,'(2a)') 'TITLE ', 'gsi ensemble spread'
Expand Down
12 changes: 6 additions & 6 deletions src/gsibec/gsi/gsi_enscouplermod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -94,36 +94,36 @@ function typename_() result(name)
! Note the use of typemold_, instead of this_ensemble_.
end function typename_

subroutine get_user_ens_(grd,member,ntindex,tau,atm_bundle,iret)
subroutine get_user_ens_(grd,member,nymd,nhms,tau,atm_bundle,iret)
use m_kinds, only: i_kind,r_kind
use gsi_bundlemod, only: gsi_bundle
use general_sub2grid_mod, only: sub2grid_info
implicit none
! Declare passed variables
type(sub2grid_info) ,intent(in ) :: grd
integer(i_kind) ,intent(in ) :: member
integer(i_kind) ,intent(in ) :: ntindex
integer(i_kind) ,intent(in ) :: nymd,nhms
integer(i_kind) ,intent(in ) :: tau
type(gsi_bundle) ,intent(inout) :: atm_bundle
integer(i_kind) ,intent( out) :: iret
call ifn_alloc_() ! to ensure an allocated(this_ensemble_)
call this_ensemble_%get_user_ens(grd,member,ntindex,tau,atm_bundle,iret)
call this_ensemble_%get_user_ens(grd,member,nymd,nhms,tau,atm_bundle,iret)
end subroutine get_user_ens_

subroutine get_user_Nens_(grd,members,ntindex,tau,atm_bundle,iret)
subroutine get_user_Nens_(grd,members,nymd,nhms,tau,atm_bundle,iret)
use m_kinds, only: i_kind,r_kind
use gsi_bundlemod, only: gsi_bundle
use general_sub2grid_mod, only: sub2grid_info
implicit none
! Declare passed variables
type(sub2grid_info) ,intent(in ) :: grd
integer(i_kind) ,intent(in ) :: members
integer(i_kind) ,intent(in ) :: ntindex
integer(i_kind) ,intent(in ) :: nymd,nhms
integer(i_kind) ,intent(in ) :: tau
type(gsi_bundle) ,intent(inout) :: atm_bundle(:)
integer(i_kind) ,intent( out) :: iret
call ifn_alloc_() ! to ensure an allocated(this_ensemble_)
call this_ensemble_%get_user_Nens(grd,members,ntindex,tau,atm_bundle,iret)
call this_ensemble_%get_user_Nens(grd,members,nymd,nhms,tau,atm_bundle,iret)
end subroutine get_user_Nens_

subroutine put_user_ens_(grd,member,ntindex,pert,iret)
Expand Down
3 changes: 2 additions & 1 deletion src/gsibec/gsi/hybrid_ensemble_isotropic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1185,6 +1185,7 @@ subroutine load_ensemble (tau)
i_en_perts_io
use hybrid_ensemble_parameters, only: nelen,en_perts,ps_bar
use hybrid_ensemble_parameters, only: write_ens_sprd
use hybrid_ensemble_parameters, only: nymd,nhms
use gsi_enscouplermod, only: gsi_enscoupler_put_gsi_ens
use m_mpimod, only: mype
use get_pseudo_ensperts_mod, only: get_pseudo_ensperts_class
Expand Down Expand Up @@ -1303,7 +1304,7 @@ subroutine load_ensemble (tau)
endif
enddo

if (write_ens_sprd) call ens_spread_dualres(en_bar(m),m)
if (write_ens_sprd) call ens_spread_dualres(en_bar(m),m,nymd(m),nhms(m))

call gsi_bundledestroy(en_bar(m),istatus)
if(istatus/=0) then
Expand Down
3 changes: 3 additions & 0 deletions src/gsibec/gsi/hybrid_ensemble_parameters.f90
Original file line number Diff line number Diff line change
Expand Up @@ -297,6 +297,7 @@ module hybrid_ensemble_parameters
public :: upd_ens_spread
public :: upd_ens_localization
public :: EnsSource
public :: nymd,nhms

logical l_hyb_ens,uv_hyb_ens,q_hyb_ens,oz_univ_static,sst_staticB
logical bens_recenter,upd_ens_spread,upd_ens_localization
Expand Down Expand Up @@ -338,6 +339,8 @@ module hybrid_ensemble_parameters
character(len=512),save :: ens_fname_tmpl
character(len=80) :: EnsSource

integer, allocatable :: nymd(:),nhms(:)

! following is for storage of ensemble perturbations:

! def en_perts - array of ensemble perturbations
Expand Down
36 changes: 21 additions & 15 deletions src/gsibec/gsi/m_gsibec.F90
Original file line number Diff line number Diff line change
Expand Up @@ -11,8 +11,8 @@ module m_gsibec

use gsi_4dvar, only: nsubwin
use gsi_4dvar, only: lsqrtb
use gsi_4dvar, only: ibdate
use hybrid_ensemble_parameters, only: ntlevs_ens
use hybrid_ensemble_parameters, only: nymd,nhms
use jfunc, only: nsclen,npclen,ntclen
use jfunc, only: mockbkg
use jfunc, only: jouter_def
Expand Down Expand Up @@ -130,8 +130,8 @@ module m_gsibec

character(len=*), parameter :: myname ="m_gsibec"
contains
subroutine init_(cv,vgrid,bkgmock,nmlfile,befile,layout,ntimes, &
jouter,idate,&
subroutine init_(cv,vgrid,bkgmock,nmlfile,befile,layout, &
jouter,inymd,inhms,&
comm)

logical, intent(out) :: cv
Expand All @@ -140,8 +140,7 @@ subroutine init_(cv,vgrid,bkgmock,nmlfile,befile,layout,ntimes, &
character(len=*),optional,intent(in) :: nmlfile
character(len=*),optional,intent(in) :: befile
integer,optional,intent(in) :: layout(2) ! 1=nx, 2=ny
integer,optional,intent(in) :: ntimes
integer,optional,intent(in) :: idate(:)
integer,optional,intent(in) :: inymd(:),inhms(:)
integer,optional,intent(out):: jouter
integer,optional,intent(in) :: comm

Expand All @@ -158,16 +157,6 @@ subroutine init_(cv,vgrid,bkgmock,nmlfile,befile,layout,ntimes, &
if (mype==0) call warn(myname_,': already initialized, skipping ...')
return
endif
if (present(ntimes) ) then
nfldsig=ntimes
ntguessig=(ntimes+1)/2
else
nfldsig=1
ntguessig=1
endif
if (present(idate) ) then
ibdate = idate
endif

ier=0
call mpi_initialized(already_init_mpi,ier)
Expand All @@ -188,6 +177,21 @@ subroutine init_(cv,vgrid,bkgmock,nmlfile,befile,layout,ntimes, &
call befname_(befile,0)
endif
call gsimain_initialize(nmlfile=nmlfile)

nfldsig=1
ntguessig=1
if (present(inymd) .and. present(inhms)) then
if (size(inymd)/=ntlevs_ens) then
print *, 'nymd,ntlevs ', size(inymd), ntlevs_ens
call die(myname,'inconsistent number of time slots ier =',99)
endif
allocate(nymd(ntlevs_ens),nhms(ntlevs_ens))
nymd = inymd
nhms = inhms
nfldsig=ntlevs_ens
ntguessig=(ntlevs_ens+1)/2
endif

call set_(vgrid=vgrid)
if(l_hyb_ens) then
call hybens_grid_setup()
Expand Down Expand Up @@ -958,6 +962,8 @@ subroutine gsi2model_units_ad_(bundle)
end subroutine gsi2model_units_ad_
!--------------------------------------------------------
subroutine final_guess_
if(allocated(nymd)) deallocate(nymd)
if(allocated(nhms)) deallocate(nhms)
call gsiguess_final()
end subroutine final_guess_
end module m_gsibec
Loading

0 comments on commit c8ac58d

Please sign in to comment.