Skip to content

Commit

Permalink
Reduce the printouts for GEFS processing.
Browse files Browse the repository at this point in the history
  • Loading branch information
WenMeng-NOAA committed Oct 23, 2024
1 parent 30d4079 commit ee5b712
Show file tree
Hide file tree
Showing 3 changed files with 10 additions and 10 deletions.
8 changes: 4 additions & 4 deletions sorc/ncep_post.fd/CLDRAD.f
Original file line number Diff line number Diff line change
Expand Up @@ -4703,7 +4703,7 @@ SUBROUTINE CLDRAD
ENDDO

IF ( LAEROPT ) THEN
PRINT *, 'COMPUTE AEROSOL OPTICAL PROPERTIES'
if(me == 0)PRINT *, 'COMPUTE AEROSOL OPTICAL PROPERTIES'

!!! ALLOCATE AEROSOL OPTICAL PROPERTIES
ALLOCATE ( extrhd_DU(KRHLEV,nbin_du,NBDSW))
Expand Down Expand Up @@ -4740,9 +4740,9 @@ SUBROUTINE CLDRAD
else if (nasa_on) then
nAero=KCM2
endif
PRINT *, 'aft AEROSOL allocate, nbin_du=',nbin_du, &
'nbin_ss=',nbin_ss,'nbin_su=',nbin_su,'nbin_bc=', &
'nbin_oc=',nbin_oc,'nbin_ni=',nbin_no3,'nAero=',nAero
! PRINT *, 'aft AEROSOL allocate, nbin_du=',nbin_du, &
! 'nbin_ss=',nbin_ss,'nbin_su=',nbin_su,'nbin_bc=', &
! 'nbin_oc=',nbin_oc,'nbin_ni=',nbin_no3,'nAero=',nAero

!!! READ AEROSOL LUTS
DO i = 1, nAero
Expand Down
2 changes: 1 addition & 1 deletion sorc/ncep_post.fd/INITPOST_NETCDF.f
Original file line number Diff line number Diff line change
Expand Up @@ -4119,7 +4119,7 @@ subroutine read_netcdf_2d_para(ncid,ista,ista_2l,iend,iend_2u,jsta,jsta_2l,jend,
implicit none
INCLUDE "mpif.h"
character(len=20),intent(in) :: VarName
character(len=*),intent(in) :: VarName
real,intent(in) :: spval
integer,intent(in) :: ncid,jsta_2l,jend_2u,jsta,jend,ista_2l,iend_2u,ista,iend
real,intent(out) :: buf(ista_2l:iend_2u,jsta_2l:jend_2u)
Expand Down
10 changes: 5 additions & 5 deletions sorc/ncep_post.fd/grib2_module.f
Original file line number Diff line number Diff line change
Expand Up @@ -587,10 +587,10 @@ subroutine gengrb2msg(idisc,icatg, iparm,nprm,nlvl,fldlvl1,fldlvl2,ntrange,tinvs
if(gefs_status /= 0) print *, &
"GEFS Run: Could not read e3 envir. var, User needs to set in script"

print*,'GEFS env var ',e1_type,perturb_num,num_ens_fcst
! print*,'GEFS env var ',e1_type,perturb_num,num_ens_fcst

! Set pdstmpl to tmpl4_1 or tmpl4_11
print *, "Processing for GEFS and default setting is tmpl4_1 and tmpl4_11"
! print *, "Processing for GEFS and default setting is tmpl4_1 and tmpl4_11"
if (trim(pset%param(nprm)%pdstmpl)=='tmpl4_0') then
pset%param(nprm)%pdstmpl='tmpl4_1'
elseif (trim(pset%param(nprm)%pdstmpl)=='tmpl4_8') then
Expand Down Expand Up @@ -640,8 +640,8 @@ subroutine gengrb2msg(idisc,icatg, iparm,nprm,nlvl,fldlvl1,fldlvl2,ntrange,tinvs
elseif(e1_type==3.or.e1_type==4) then
listsec1(13)=4
endif
print *, "After g2sec1 call we need to set listsec1(2) = ",listsec1(2)
print *, "After g2sec1 call we need to set listsec1(13) = ",listsec1(13)
! print *, "After g2sec1 call we need to set listsec1(2) = ",listsec1(2)
! print *, "After g2sec1 call we need to set listsec1(13) = ",listsec1(13)
else
listsec1(2)=0
endif
Expand Down Expand Up @@ -1444,7 +1444,7 @@ subroutine read_grib2_sngle(filenameG2,ntot,height,var)
lon1 = gfld%igdtmpl(13)/scale_factor
dx = gfld%igdtmpl(17)/scale_factor
nlat = gfld%igdtmpl(18)
write(*,*) gfld%igdtnum, nx, ny, lat1, lon1, dx, nlat
! write(*,*) gfld%igdtnum, nx, ny, lat1, lon1, dx, nlat
else
write(*,*) 'unknown projection'
stop 1235
Expand Down

0 comments on commit ee5b712

Please sign in to comment.