Skip to content

Commit

Permalink
Merge pull request #456 from RussTreadon-NOAA/release/gfsda.v16.3.0
Browse files Browse the repository at this point in the history
Release/gfsda.v16.3.0
  • Loading branch information
emilyhcliu authored Aug 28, 2022
2 parents d6fc665 + 36481a2 commit 733629e
Show file tree
Hide file tree
Showing 32 changed files with 154 additions and 114 deletions.
6 changes: 0 additions & 6 deletions modulefiles/gsi_wcoss2.lua
Original file line number Diff line number Diff line change
Expand Up @@ -19,11 +19,5 @@ load(pathJoin("python", python_ver))
load(pathJoin("prod_util", prod_util_ver))

load("gsi_common")
unload("crtm")

pushenv("HPC_OPT", "/apps/ops/para/libs")
prepend_path("MODULEPATH", "/apps/ops/para/libs/modulefiles/compiler/intel/19.1.3.304")
prepend_path("MODULEPATH", "/apps/ops/para/libs/modulefiles/mpi/intel/19.1.3.304/cray-mpich/8.1.7/")
load("crtm/2.4.0")

whatis("Description: GSI environment on WCOSS2")
1 change: 0 additions & 1 deletion scripts/exgdas_enkf_ecen.sh
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,6 @@ ntiles=${ntiles:-6}
# Utilities
NCP=${NCP:-"/bin/cp -p"}
NLN=${NLN:-"/bin/ln -sf"}
NEMSIOGET=${NEMSIOGET:-${NWPROD}/exec/nemsio_get}
NCLEN=${NCLEN:-$HOMEgfs/ush/getncdimlen}

# Scripts
Expand Down
1 change: 0 additions & 1 deletion scripts/exgdas_enkf_sfc.sh
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,6 @@ ntiles=${ntiles:-6}
# Utilities
NCP=${NCP:-"/bin/cp -p"}
NLN=${NLN:-"/bin/ln -sf"}
NEMSIOGET=${NEMSIOGET:-${NWPROD}/exec/nemsio_get}
NCLEN=${NCLEN:-$HOMEgfs/ush/getncdimlen}

# Scripts
Expand Down
1 change: 0 additions & 1 deletion scripts/exgdas_enkf_update.sh
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,6 @@ pwd=$(pwd)
# Utilities
NCP=${NCP:-"/bin/cp -p"}
NLN=${NLN:-"/bin/ln -sf"}
NEMSIOGET=${NEMSIOGET:-$NWPROD/utils/exec/nemsio_get}
NCLEN=${NCLEN:-$HOMEgfs/ush/getncdimlen}
USE_CFP=${USE_CFP:-"NO"}
CFP_MP=${CFP_MP:-"NO"}
Expand Down
1 change: 0 additions & 1 deletion scripts/exglobal_atmos_analysis.sh
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,6 @@ export NCP=${NCP:-"/bin/cp"}
export NMV=${NMV:-"/bin/mv"}
export NLN=${NLN:-"/bin/ln -sf"}
export CHGRP_CMD=${CHGRP_CMD:-"chgrp ${group_name:-rstprod}"}
export NEMSIOGET=${NEMSIOGET:-${NWPROD}/exec/nemsio_get}
export NCLEN=${NCLEN:-$HOMEgfs/ush/getncdimlen}
COMPRESS=${COMPRESS:-gzip}
UNCOMPRESS=${UNCOMPRESS:-gunzip}
Expand Down
1 change: 0 additions & 1 deletion scripts/exglobal_atmos_analysis_calc.sh
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,6 @@ export NCP=${NCP:-"/bin/cp"}
export NMV=${NMV:-"/bin/mv"}
export NLN=${NLN:-"/bin/ln -sf"}
export CHGRP_CMD=${CHGRP_CMD:-"chgrp ${group_name:-rstprod}"}
export NEMSIOGET=${NEMSIOGET:-${NWPROD}/exec/nemsio_get}
export NCLEN=${NCLEN:-$HOMEgfs/ush/getncdimlen}
COMPRESS=${COMPRESS:-gzip}
UNCOMPRESS=${UNCOMPRESS:-gunzip}
Expand Down
1 change: 0 additions & 1 deletion scripts/exglobal_diag.sh
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,6 @@ export NCP=${NCP:-"/bin/cp"}
export NMV=${NMV:-"/bin/mv"}
export NLN=${NLN:-"/bin/ln -sf"}
export CHGRP_CMD=${CHGRP_CMD:-"chgrp ${group_name:-rstprod}"}
export NEMSIOGET=${NEMSIOGET:-${NWPROD}/exec/nemsio_get}
export NCLEN=${NCLEN:-$HOMEgfs/ush/getncdimlen}
export CATEXEC=${CATEXEC:-$HOMEgfs/exec/ncdiag_cat_serial.x}
COMPRESS=${COMPRESS:-gzip}
Expand Down
28 changes: 14 additions & 14 deletions src/gsi/cplr_gfs_ensmod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -385,7 +385,7 @@ subroutine move2bundle_(grd3d,en_loc3,atm_bundle,m_cvars2d,m_cvars3d,iret)
character(len=70) :: filename

integer(i_kind) :: ierr
integer(i_kind) :: km,m
integer(i_kind) :: km1,m
integer(i_kind) :: icw,iql,iqi,iqr,iqs,iqg
real(r_kind),pointer,dimension(:,:) :: ps
!real(r_kind),pointer,dimension(:,:) :: sst
Expand Down Expand Up @@ -440,31 +440,31 @@ subroutine move2bundle_(grd3d,en_loc3,atm_bundle,m_cvars2d,m_cvars3d,iret)
! if(trim(cvars2d(m))=='sst') sst=en_loc3(:,:,m_cvars2d(m)) !no sst for now
enddo

km = en_perts(1,1)%grid%km
km1 = en_perts(1,1)%grid%km - 1
!$omp parallel do schedule(dynamic,1) private(m)
do m=1,nc3d
if(trim(cvars3d(m))=='sf')then
u = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km)
u = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km1)
else if(trim(cvars3d(m))=='vp') then
v = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km)
v = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km1)
else if(trim(cvars3d(m))=='t') then
tv = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km)
tv = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km1)
else if(trim(cvars3d(m))=='q') then
q = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km)
q = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km1)
else if(trim(cvars3d(m))=='oz') then
oz = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km)
oz = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km1)
else if(trim(cvars3d(m))=='cw') then
cwmr = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km)
cwmr = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km1)
else if(trim(cvars3d(m))=='ql') then
qlmr = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km)
qlmr = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km1)
else if(trim(cvars3d(m))=='qi') then
qimr = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km)
qimr = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km1)
else if(trim(cvars3d(m))=='qr') then
qrmr = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km)
qrmr = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km1)
else if(trim(cvars3d(m))=='qs') then
qsmr = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km)
qsmr = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km1)
else if(trim(cvars3d(m))=='qg') then
qgmr = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km)
qgmr = en_loc3(:,:,m_cvars3d(m):m_cvars3d(m)+km1)
end if
enddo

Expand Down Expand Up @@ -930,7 +930,7 @@ subroutine parallel_read_gfsnc_state_(en_full,m_cvars2d,m_cvars3d,nlon,nlat,nsig

atmges = open_dataset(filename,errcode=ierror)
if (ierror /=0) then
write(6,*)' PARALLEL_READ_GFSNC_STATE: ***ERROR*** ',trim(filename),' NOT AVAILABLE: PROGRAM STOPS'
write(6,*)' PARALLEL_READ_GFSNC_STATE: ***FATAL ERROR*** ',trim(filename),' NOT AVAILABLE: PROGRAM STOPS'
call stop2(999)
endif
! get dimension sizes
Expand Down
1 change: 1 addition & 0 deletions src/gsi/general_read_gfsatm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -2825,6 +2825,7 @@ subroutine general_read_gfsatm_allhydro_nc(grd,sp_a,filename,uvflag,vordivflag,z
call gsi_bundlegetpointer(gfs_bundle,'q' ,g_q ,ier);istatus=istatus+ier
call gsi_bundlegetpointer(gfs_bundle,'oz',g_oz ,ier);istatus=istatus+ier
! call gsi_bundlegetpointer(gfs_bundle,'cw',g_cwmr,ier);istatus=istatus+ier
istatus1=0
call gsi_bundlegetpointer(gfs_bundle,'ql',g_ql ,ier);istatus1=istatus1+ier
call gsi_bundlegetpointer(gfs_bundle,'qi',g_qi ,ier);istatus1=istatus1+ier
call gsi_bundlegetpointer(gfs_bundle,'qr',g_qr ,ier);istatus1=istatus1+ier
Expand Down
10 changes: 5 additions & 5 deletions src/gsi/gesinfo.F90
Original file line number Diff line number Diff line change
Expand Up @@ -148,7 +148,7 @@ subroutine gesinfo
write(filename,'("sigf",i2.2)')nhr_assimilation
inquire(file=filename,exist=fexist)
if(.not.fexist) then
write(6,*)' GESINFO: ***ERROR*** ',trim(filename),' NOT AVAILABLE: PROGRAM STOPS'
write(6,*)' GESINFO: ***FATAL ERROR*** ',trim(filename),' NOT AVAILABLE: PROGRAM STOPS'
call stop2(99)
stop
end if
Expand Down Expand Up @@ -339,12 +339,12 @@ subroutine gesinfo
! open the netCDF file
atmges = open_dataset(filename,errcode=iret)
if (iret /=0) then
write(6,*)'GESINFO: ***ERROR*** ',trim(filename),' NOT AVAILABLE: PROGRAM STOPS'
write(6,*)'GESINFO: ***FATAL ERROR*** ',trim(filename),' NOT AVAILABLE: PROGRAM STOPS'
call stop2(99)
endif
sfcges = open_dataset(sfilename,errcode=iret)
if (iret /=0) then
write(6,*)'GESINFO: ***ERROR*** ',trim(sfilename),' NOT AVAILABLE: PROGRAM STOPS'
write(6,*)'GESINFO: ***FATAL ERROR*** ',trim(sfilename),' NOT AVAILABLE: PROGRAM STOPS'
call stop2(99)
endif
! get dimension sizes
Expand Down Expand Up @@ -451,7 +451,7 @@ subroutine gesinfo
! Check for consistency with namelist settings
if (gfshead%jcap/=jcap_b.and..not.regional .or. gfshead%levs/=nsig) then
if (gfshead%levs/=nsig) then
write(6,*)'GESINFO: ***ERROR*** guess levels inconsistent with namelist'
write(6,*)'GESINFO: ***FATAL ERROR*** guess levels inconsistent with namelist'
write(6,*)' guess nsig=',gfshead%levs
write(6,*)' namelist nsig=',nsig
fatal = .true.
Expand All @@ -466,7 +466,7 @@ subroutine gesinfo
fatal = .false.
else
if ( mype == mype_out ) &
write(6,*)'GESINFO: ***ERROR*** guess jcap inconsistent with namelist'
write(6,*)'GESINFO: ***FATAL ERROR*** guess jcap inconsistent with namelist'
fatal = .true.
endif
if ( mype == mype_out ) &
Expand Down
2 changes: 1 addition & 1 deletion src/gsi/netcdfgfs_io.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1300,7 +1300,7 @@ subroutine read_sfc_anl_(isli_anl)
! open the netCDF file
sfcges = open_dataset(filename,errcode=iret)
if (iret/=0) then
write(6,*) trim(my_name),': ***ERROR*** ',trim(filename),' NOT AVAILABLE: PROGRAM STOPS'
write(6,*) trim(my_name),': ***FATAL ERROR*** ',trim(filename),' NOT AVAILABLE: PROGRAM STOPS'
call stop2(999)
endif

Expand Down
4 changes: 3 additions & 1 deletion src/gsi/read_diag.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1165,7 +1165,9 @@ subroutine read_radiag_data_nc(diag_status,header_fix,data_fix,data_chan,data_ex

data_fix = diag_status%all_data_fix(diag_status%cur_ob_idx)
data_chan(:) = diag_status%all_data_chan(diag_status%cur_ob_idx,:)
data_extra(:,:) = diag_status%all_data_extra(diag_status%cur_ob_idx,:,:)
if (header_fix%iextra > 0) then
data_extra(:,:) = diag_status%all_data_extra(diag_status%cur_ob_idx,:,:)
endif

diag_status%cur_ob_idx = diag_status%cur_ob_idx + 1

Expand Down
8 changes: 4 additions & 4 deletions src/gsi/read_files.f90
Original file line number Diff line number Diff line change
Expand Up @@ -620,7 +620,7 @@ subroutine read_files(mype)
endif
if (l4densvar .and. nfldsig/=ntlevs_ens) then
if (mype==0) then
write(6,*)'READ_FILES: ***ERROR*** insufficient atm fcst for 4densvar: PROGRAM STOPS'
write(6,*)'READ_FILES: ***FATAL ERROR*** insufficient atm fcst for 4densvar: PROGRAM STOPS'
do i=1,ntlevs_ens
ihr=nhr_obsbin*(i-1)+nhr_half
present=.false.
Expand All @@ -629,7 +629,7 @@ subroutine read_files(mype)
end do
if (.not.present) then
write(filename,'(''sigf'',i2.2)')ihr
write(6,*)'READ_FILES: ***ERROR*** file ',trim(filename),' missing: PROGRAM STOPS'
write(6,*)'READ_FILES: ***FATAL ERROR*** file ',trim(filename),' missing: PROGRAM STOPS'
endif
end do
endif
Expand All @@ -652,7 +652,7 @@ subroutine read_files(mype)
endif
if (l4densvar .and. nfldsfc/=ntlevs_ens) then
if (mype==0) then
write(6,*)'READ_FILES: ***ERROR*** insufficient sfc fcst for 4densvar: PROGRAM STOPS'
write(6,*)'READ_FILES: ***FATAL ERROR*** insufficient sfc fcst for 4densvar: PROGRAM STOPS'
do i=1,ntlevs_ens
ihr=nhr_obsbin*(i-1)+nhr_half
present=.false.
Expand All @@ -661,7 +661,7 @@ subroutine read_files(mype)
end do
if (.not.present) then
write(filename,'(''sfcf'',i2.2)')ihr
write(6,*)'READ_FILES: ***ERROR*** file ',trim(filename),' missing: PROGRAM STOPS'
write(6,*)'READ_FILES: ***FATAL ERROR*** file ',trim(filename),' missing: PROGRAM STOPS'
endif
end do
endif
Expand Down
6 changes: 3 additions & 3 deletions src/gsi/read_prepbufr.f90
Original file line number Diff line number Diff line change
Expand Up @@ -475,7 +475,7 @@ subroutine read_prepbufr(nread,ndata,nodata,infile,obstype,lunout,twindin,sis,&
if(tob)then
nreal=25
else if(uvob) then
nreal=27
nreal=26
else if(spdob) then
nreal=24
else if(psob) then
Expand Down Expand Up @@ -2239,8 +2239,8 @@ subroutine read_prepbufr(nread,ndata,nodata,infile,obstype,lunout,twindin,sis,&
cdata_all(25,iout)=var_jb(5,k) ! non linear qc parameter
cdata_all(26,iout)=one ! hilbert curve weight, modified later
if(perturb_obs)then
cdata_all(28,iout)=ran01dom()*perturb_fact ! u perturbation
cdata_all(29,iout)=ran01dom()*perturb_fact ! v perturbation
cdata_all(27,iout)=ran01dom()*perturb_fact ! u perturbation
cdata_all(28,iout)=ran01dom()*perturb_fact ! v perturbation
endif

else if(spdob) then
Expand Down
19 changes: 8 additions & 11 deletions src/gsi/read_satwnd.f90
Original file line number Diff line number Diff line change
Expand Up @@ -74,8 +74,6 @@ subroutine read_satwnd(nread,ndata,nodata,infile,obstype,lunout,gstime,twind,sis
! or hilber curve downweighting
!
! 2020-05-04 wu - no rotate_wind for fv3_regional
! 2021-07-25 Genkova - read GOES-17 AMVQ flag:8-mitigated height
! 16-mit.target, 24-mit.target & height; write in diag
! 2021-07-25 Genkova - added code for Metop-B/C winds in new BUFR,NC005081 !
! 2022-01-20 Genkova - added missing station_id for polar winds
! 2022-01-20 Genkova - added code for Meteosat and Himawari AMVs in new BUFR
Expand Down Expand Up @@ -212,7 +210,7 @@ subroutine read_satwnd(nread,ndata,nodata,infile,obstype,lunout,gstime,twind,sis
real(r_kind),dimension(nsig):: presl

real(r_double),dimension(13):: hdrdat
real(r_double),dimension(5):: obsdat
real(r_double),dimension(4):: obsdat
real(r_double),dimension(2) :: hdrdat_test
real(r_double),dimension(3,5) :: heightdat
real(r_double),dimension(6,4) :: derdwdat
Expand Down Expand Up @@ -242,8 +240,8 @@ subroutine read_satwnd(nread,ndata,nodata,infile,obstype,lunout,gstime,twind,sis
data hdrtr_v2 /'SAID CLATH CLONH YEAR MNTH DAYS HOUR MINU SWCM SAZA OGCE SCCF SWQM'/ ! OGCE replaces GCLONG, OGCE exists in old and new BUFR
! SWQM doesn't exist in the new BUFR, so qm is initialized to '2' manually

data obstr_v1 /'HAMD PRLC WDIR WSPD AMVQ'/
data obstr_v2 /'EHAM PRLC WDIR WSPD AMVQ'/
data obstr_v1 /'HAMD PRLC WDIR WSPD'/
data obstr_v2 /'EHAM PRLC WDIR WSPD'/
! data heightr/'MDPT '/
! data derdwtr/'TWIND'/
data qcstr /' OGCE GNAP PCCF'/
Expand Down Expand Up @@ -271,7 +269,7 @@ subroutine read_satwnd(nread,ndata,nodata,infile,obstype,lunout,gstime,twind,sis
! Set lower limits for observation errors
werrmin=one
nsattype=0
nreal=27
nreal=26
if(perturb_obs ) nreal=nreal+2
ntread=1
ntmatch=0
Expand Down Expand Up @@ -644,10 +642,10 @@ subroutine read_satwnd(nread,ndata,nodata,infile,obstype,lunout,gstime,twind,sis
call ufbint(lunin,hdrdat_test,2,1,iret, 'CLAT CLON')
if ( hdrdat_test(1) > 100000000.0_r_kind .and. hdrdat_test(2) > 100000000.0_r_kind ) then
call ufbint(lunin,hdrdat,13,1,iret,hdrtr_v2)
call ufbint(lunin,obsdat,5,1,iret,obstr_v2)
call ufbint(lunin,obsdat,4,1,iret,obstr_v2)
else
call ufbint(lunin,hdrdat,13,1,iret,hdrtr_v1)
call ufbint(lunin,obsdat,5,1,iret,obstr_v1)
call ufbint(lunin,obsdat,4,1,iret,obstr_v1)
endif

ppb=obsdat(2)
Expand Down Expand Up @@ -1586,11 +1584,10 @@ subroutine read_satwnd(nread,ndata,nodata,infile,obstype,lunout,gstime,twind,sis
cdata_all(23,iout)=r_sprvstg(1,1) ! subprovider name
cdata_all(25,iout)=var_jb ! non linear qc parameter
cdata_all(26,iout)=one ! hilbert curve weight
cdata_all(27,iout)=obsdat(5) ! AMVQ for GOES-17 mitig.AMVs

if(perturb_obs)then
cdata_all(28,iout)=ran01dom()*perturb_fact ! u perturbation
cdata_all(29,iout)=ran01dom()*perturb_fact ! v perturbation
cdata_all(27,iout)=ran01dom()*perturb_fact ! u perturbation
cdata_all(28,iout)=ran01dom()*perturb_fact ! v perturbation
endif

enddo loop_readsb
Expand Down
13 changes: 4 additions & 9 deletions src/gsi/setupw.f90
Original file line number Diff line number Diff line change
Expand Up @@ -219,7 +219,6 @@ subroutine setupw(obsLL,odiagLL,lunin,mype,bwork,awork,nele,nobs,is,conv_diagsav
! level; they are now loaded by
! aircraftinfo.
! 2020-05-04 wu - no rotate_wind for fv3_regional
! 2021-07-25 Genkova - write AMVQ in diagnostic files
! 2021-10-xx pondeca/morris/zhao - added observation provider/subprovider
! information in diagonostic file, which is used
! in offline observation quality control program (AutoObsQC)
Expand Down Expand Up @@ -293,7 +292,7 @@ subroutine setupw(obsLL,odiagLL,lunin,mype,bwork,awork,nele,nobs,is,conv_diagsav
integer(i_kind) ihgt,ier2,iuse,ilate,ilone
integer(i_kind) izz,iprvd,isprvd
integer(i_kind) idomsfc,isfcr,iskint,iff10
integer(i_kind) ibb,ikk,ihil,idddd,iamvq
integer(i_kind) ibb,ikk,ihil,idddd

integer(i_kind) num_bad_ikx,iprev_station

Expand Down Expand Up @@ -384,9 +383,8 @@ subroutine setupw(obsLL,odiagLL,lunin,mype,bwork,awork,nele,nobs,is,conv_diagsav
icat=24 ! index of data level category
ijb=25 ! index of non linear qc parameter
ihil=26 ! index of hilbert curve weight
iamvq=27 ! index of AMVQ
iptrbu=28 ! index of u perturbation
iptrbv=29 ! index of v perturbation
iptrbu=27 ! index of u perturbation
iptrbv=28 ! index of v perturbation

mm1=mype+1
scale=one
Expand All @@ -402,7 +400,7 @@ subroutine setupw(obsLL,odiagLL,lunin,mype,bwork,awork,nele,nobs,is,conv_diagsav
if(conv_diagsave)then
ii=0
nchar=1
ioff0=26
ioff0=25
nreal=ioff0
if (lobsdiagsave) nreal=nreal+7*miter+2
if (twodvar_regional .or. l_obsprvdiag) then
Expand Down Expand Up @@ -1726,7 +1724,6 @@ subroutine contents_binary_diag_(udiag,vdiag)
rdiagbuf(23,ii) = factw ! 10m wind reduction factor
rdiagbuf(24,ii) = 1.e+10_r_single ! u spread (filled in by EnKF)
rdiagbuf(25,ii) = 1.e+10_r_single ! v spread (filled in by EnKF)
rdiagbuf(26,ii) = data(iamvq,i) ! AMVQ mitigation flag for AMVs;only for GOES17,LHP issue

ioff=ioff0
if (lobsdiagsave) then
Expand Down Expand Up @@ -1813,8 +1810,6 @@ subroutine contents_netcdf_diag_(udiag,vdiag)
call nc_diag_metadata("Errinv_Input", sngl(errinv_input) )
call nc_diag_metadata("Errinv_Adjust", sngl(errinv_adjst) )
call nc_diag_metadata("Errinv_Final", sngl(errinv_final) )
! AMVQ Mitigated winds
call nc_diag_metadata("Mitigation_flag_AMVQ", sngl(data(iamvq,i)) )
call nc_diag_metadata("Wind_Reduction_Factor_at_10m", sngl(factw) )

if (.not. regional .or. fv3_regional) then
Expand Down
3 changes: 1 addition & 2 deletions src/gsi/write_incr.f90
Original file line number Diff line number Diff line change
Expand Up @@ -366,10 +366,9 @@ subroutine write_fv3_inc_ (grd,sp_a,filename,mype_out,gfs_bundle,ibin)
ncstart = (/ jstart(mype+1), 1, 1 /)
nccount = (/ grd%lon1, grd%lat1-1, grd%nsig /)
j1 = 2
j2 = grd%lat1-1
else if (istart(mype+1)+grd%lat1 == grd%nlat+1) then
nccount = (/ grd%lon1, grd%lat1-1, grd%nsig /)
j2 = grd%lat1-2
j2 = grd%lat1-1
end if
call mpi_barrier(mpi_comm_world,ierror)
allocate(out3d(nccount(1),nccount(2),grd%nsig))
Expand Down
3 changes: 3 additions & 0 deletions ush/build_4nco_global.sh
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,9 @@ export ENKF_MODE="GFS"
export REGRESSION_TESTS="NO"
export UTIL_OPTS="-DBUILD_UTIL_ENKF_GFS=ON -DBUILD_UTIL_MON=ON -DBUILD_UTIL_NCIO=ON"

# Optionally set compiler flags
##export FFLAGS="-check all,noarg_temp_created"

# Prune the directory structure per NCO liking
if [[ "${PRUNE_4NCO:-}" =~ [yYtT] ]]; then
$DIR_ROOT/ush/prune_4nco_global.sh prune
Expand Down
Loading

0 comments on commit 733629e

Please sign in to comment.