Skip to content

Commit

Permalink
Replace cld_amt, the 3D cloud fraction from the GFDL mp with the same…
Browse files Browse the repository at this point in the history
… field for all (#170)

microphysics schemes, cldfra.
  • Loading branch information
ericaligo-NOAA authored Aug 26, 2020
1 parent 2a5aab0 commit 8261eec
Showing 1 changed file with 12 additions and 5 deletions.
17 changes: 12 additions & 5 deletions sorc/ncep_post.fd/INITPOST_NETCDF.f
Original file line number Diff line number Diff line change
Expand Up @@ -472,12 +472,12 @@ SUBROUTINE INITPOST_NETCDF(ncid3d)
end if
if(me==0)print*,'nhcas= ',nhcas
if (nhcas == 0 ) then !non-hydrostatic case
nrec=15
nrec=14
allocate (recname(nrec))
recname=[character(len=20) :: 'ugrd','vgrd','spfh','tmp','o3mr', &
'presnh','dzdt', 'clwmr','dpres', &
'delz','icmr','rwmr', &
'snmr','grle','cld_amt']
'snmr','grle']
else
nrec=8
allocate (recname(nrec))
Expand Down Expand Up @@ -848,9 +848,6 @@ SUBROUTINE INITPOST_NETCDF(ncid3d)
call read_netcdf_3d_scatter(me,ncid3d,1,im,jm,jsta,jsta_2l &
,jend_2u,MPI_COMM_COMP,icnt,idsp,spval,recname(14) &
,lm,qqg(1,jsta_2l,1))
call read_netcdf_3d_scatter(me,ncid3d,1,im,jm,jsta,jsta_2l &
,jend_2u,MPI_COMM_COMP,icnt,idsp,spval,recname(15) &
,lm,cfr(1,jsta_2l,1))
! calculate CWM from FV3 output
do l=1,lm
do j=jsta,jend
Expand Down Expand Up @@ -1255,6 +1252,16 @@ SUBROUTINE INITPOST_NETCDF(ncid3d)
! end do
! end do

! instantaneous 3D cloud fraction
VarName='cldfra'
! do l=1,lm
call read_netcdf_3d_scatter(me,ncid2d,1,im,jm,jsta,jsta_2l &
,jend_2u,MPI_COMM_COMP,icnt,idsp,spval,VarName &
,lm,cfr(1,jsta_2l,1))
! if(debugprint)print*,'sample ',VarName,'isa,jsa,l =' &
! ,cfr(isa,jsa,l),isa,jsa,l
! enddo

VarName='refl_10cm'
! do l=1,lm
call read_netcdf_3d_scatter(me,ncid2d,1,im,jm,jsta,jsta_2l &
Expand Down

0 comments on commit 8261eec

Please sign in to comment.