Skip to content

Commit

Permalink
add meta files for FA scheme and HAFS_update_moist
Browse files Browse the repository at this point in the history
  • Loading branch information
mzhangw committed Oct 23, 2019
1 parent a5b5fa9 commit bfedaab
Show file tree
Hide file tree
Showing 8 changed files with 753 additions and 445 deletions.
6 changes: 3 additions & 3 deletions physics/GFS_suite_interstitial.F90
Original file line number Diff line number Diff line change
Expand Up @@ -672,7 +672,7 @@ subroutine GFS_suite_interstitial_4_run (im, levs, ltaerosol, cplchm, tracers_to

integer, intent(in) :: im, levs, tracers_total, ntrac, ntcw, ntiw, ntclamt, ntrw, &
ntsw, ntrnc, ntsnc, ntgl, ntgnc, ntlnc, ntinc, nn, imp_physics, imp_physics_gfdl, imp_physics_thompson, &
imp_physics_zhao_carr, imp_physics_zhao_carr_pdf,imp_physics_fer_hires
imp_physics_zhao_carr, imp_physics_zhao_carr_pdf

logical, intent(in) :: ltaerosol, cplchm

Expand All @@ -685,8 +685,8 @@ subroutine GFS_suite_interstitial_4_run (im, levs, ltaerosol, cplchm, tracers_to
real(kind=kind_phys), dimension(im,levs,nn), intent(inout) :: clw
! dqdti may not be allocated
real(kind=kind_phys), dimension(:,:), intent(inout) :: dqdti
integer, intent(in) :: mpirank
integer, intent(in) :: mpiroot
!integer, intent(in) :: mpirank
!integer, intent(in) :: mpiroot


character(len=*), intent(out) :: errmsg
Expand Down
69 changes: 0 additions & 69 deletions physics/GFS_suite_interstitial.meta
Original file line number Diff line number Diff line change
Expand Up @@ -1638,50 +1638,6 @@
type = integer
intent = in
optional = F
[imp_physics_fer_hires]
standard_name = flag_for_fer_hires_microphysics_scheme
long_name = choice of Ferrier-Aligo microphysics scheme
units = flag
dimensions = ()
type = integer
intent = in
optional = F
[cwm]
standard_name = total_cloud_condensate_mixing_ratio_updated_by_physics
long_name = total cloud condensate mixing ratio (except water vapor) updated by physics
units = kg kg-1
dimensions = (horizontal_dimension,vertical_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[f_ice]
standard_name = fraction_of_ice_water_cloud
long_name = fraction of ice water cloud
units = frac
dimensions = (horizontal_dimension,vertical_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[f_rain]
standard_name = fraction_of_rain_water_cloud
long_name = fraction of rain water cloud
units = frac
dimensions = (horizontal_dimension,vertical_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[f_rimef]
standard_name = rime_factor
long_name = rime factor
units = frac
dimensions = (horizontal_dimension,vertical_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[dtf]
standard_name = time_step_for_dynamics
long_name = dynamics timestep
Expand Down Expand Up @@ -1718,15 +1674,6 @@
kind = kind_phys
intent = in
optional = F
[epsq]
standard_name = minimum_value_of_specific_humidity
long_name = floor value for specific humidity
units = kg kg-1
dimensions = ()
type = real
kind = kind_phys
intent = in
optional = F
[gq0]
standard_name = tracer_concentration_updated_by_physics
long_name = tracer concentration updated by physics
Expand Down Expand Up @@ -1754,22 +1701,6 @@
kind = kind_phys
intent = inout
optional = F
[mpirank]
standard_name = mpi_rank
long_name = current MPI-rank
units = index
dimensions = ()
type = integer
intent = in
optional = F
[mpiroot]
standard_name = mpi_root
long_name = master MPI-rank
units = index
dimensions = ()
type = integer
intent = in
optional = F
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
Expand Down
138 changes: 138 additions & 0 deletions physics/HAFS_update_moist.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,138 @@
!>\file HAFS_update_moist.F90
!! This file contains CCPP-compliant UPDATE_MOIST() in HWRF.
!!
!! In HWRF , this subroutine should be called before:
!! - radiation()
!! - CUCNVC()
!! - TURBLE()

!> This module contains the CCPP-compliant UPDATE_MOIST for Ferrier-Aligo MP.
module HAFS_update_moist

implicit none

private

public :: HAFS_update_moist_init, HAFS_update_moist_run, &
HAFS_update_moist_finalize

contains

subroutine HAFS_update_moist_init ()
end subroutine HAFS_update_moist_init

subroutine HAFS_update_moist_finalize ()
end subroutine HAFS_update_moist_finalize

!> \defgroup hafs_update_moist HAFS Update Moist Module
!! This subroutine is to update water array with CWM, F_RAIN, and F_ICE
!! and convert moist mixing ratio to dry mixing ratio
!! \section arg_table_HAFS_update_moist_run Argument Table
!! \htmlinclude HAFS_update_moist_run.html
!!
subroutine HAFS_update_moist_run (CWM,QV, F_ICE,F_RAIN &
,qc,qi,qr &
,imp_physics &
,imp_physics_fer_hires &
,qv_r, qc_r,qr_r,qi_r & !-output: dry mixing ratioes for HWRF physics
,qs_r, qg_r &
,spec_adv &
,LM,IME,errmsg,errflg )

USE MACHINE , only : kind_phys
IMPLICIT NONE

!----------------------
!-- Argument Variables
!----------------------
!
INTEGER,INTENT(IN) :: LM,IME
!

LOGICAL,INTENT(IN) :: SPEC_ADV
REAL(kind=kind_phys),DIMENSION(1:IME,1:LM),INTENT(IN) :: CWM,QV, &
QC,QI, &
QR
REAL(kind=kind_phys),DIMENSION(1:IME,1:LM),INTENT(IN) :: &
F_ICE, &
F_RAIN
integer, intent(in) :: imp_physics
integer, intent(in) :: imp_physics_fer_hires

!dry mixing ratio used in HWRF RRTMG/TURBL/FER
REAL(kind=kind_phys),DIMENSION(1:IME,1:LM),INTENT(OUT) :: qv_r, &
qc_r, &
qi_r, &
qr_r, &
qs_r, &
qg_r

!
!--------------------
!-- Local Variables
!--------------------
!
INTEGER :: I,K
character(len=*), intent(out) :: errmsg
integer, intent(out) :: errflg
!
!-----------------------------------------------------------------------
!***********************************************************************
!-----------------------------------------------------------------------

! Initialize CCPP error handling variables
errmsg = ''
errflg = 0

!-- Update WATER arrays when advecting only total condensate (spec_adv=F)
!-- and F_* or at the initial time step
if (imp_physics == imp_physics_fer_hires) then
if (spec_adv) then
qv_r (i,k)=qv(i,k)/(1.-qv(i,k))
qc_r (i,k)=qc(i,k)/(1.-qv(i,k))
qi_r (i,k)=qi(i,k)/(1.-qv(i,k))
qr_r (i,k)=qr(i,k)/(1.-qv(i,k))
qs_r (i,k)= 0.
qg_r (i,k)= 0.

else ! .not.spec_adv
DO K=1,LM
DO I=1,IME
!!MZ: HWRF::UPDATE_MOIST() solution
!calculate dry mixing ratio of all q
qv_r (i,k)=qv(i,k)/(1.-qv(i,k))
qi_r(I,K) =0.
qr_r(I,K) =0.
qc_r(I,K) =0.
IF(F_ICE(I,K)>=1.) THEN
qi_r(I,K) = CWM(i,k)
ELSEIF(F_ICE(I,K)<=0.) THEN
qc_r(I,K) = CWM(I,K)
ELSE
qi_r(I,K) = F_ICE(I,K)*CWM(I,K)
qc_r(I,K) = CWM(I,K)-qi_r(I,K)
ENDIF

IF(qc_r(I,K)>0. .AND. F_RAIN(I,K)>0.) THEN
IF(F_RAIN(I,K)>=1.)THEN
qr_r(I,K)=qc_r(I,K)
qc_r(I,K)=0.
ELSE
qr_r(I,K)=F_RAIN(I,K)*qc_r(I,K)
qc_r(I,K)=qc_r(I,K)-qr_r(I,K)
ENDIF
ENDIF
qs_r (I,K) = 0.
qg_r (I,K) = 0.
ENDDO
ENDDO
end if
else !.not. fer_hires
write(errmsg,'(*(a))') "Logic error: HAFS_update_moist only works for HWRF physics"
errflg = 1
return
end if

end subroutine HAFS_update_moist_run

end module HAFS_update_moist
Loading

0 comments on commit bfedaab

Please sign in to comment.