Skip to content

Commit

Permalink
update
Browse files Browse the repository at this point in the history
  • Loading branch information
mzhangw committed Aug 19, 2019
1 parent 7c481b5 commit dbabee7
Show file tree
Hide file tree
Showing 2 changed files with 3 additions and 60 deletions.
22 changes: 3 additions & 19 deletions physics/module_mp_fer_hires_pre.F90
Original file line number Diff line number Diff line change
Expand Up @@ -8,10 +8,10 @@ module mp_fer_hires_pre

implicit none

! private
private

! public :: mp_fer_hires_pre_init, mp_fer_hires_pre_run, &
! mp_fer_hires_pre_finalize
public :: mp_fer_hires_pre_init, mp_fer_hires_pre_run, &
mp_fer_hires_pre_finalize

contains

Expand Down Expand Up @@ -49,21 +49,6 @@ subroutine mp_fer_hires_pre_run (CWM,F_ICE,F_RAIN &
,T,QC,QR,QS,QI,QG &
,SPEC_ADV,kdt &
,LM,IME,errmsg,errflg )
!***********************************************************************
!$$$ SUBPROGRAM DOCUMENTATION BLOCK
! . . .
! SUBPROGRAM: UPDATE_WATER UPDATE WATER ARRAY
! PRGRMMR: FERRIER ORG: NP22 DATE: 3 AUG 2009
!
! ABSTRACT:
! UPDATE WATER ARRAY FOR FERRIER MICROPHYSICS
!
! PROGRAM HISTORY LOG (with changes to called routines) :
! 2009-08 FERRIER - Synchronize WATER array with CWM, F_rain, F_ice arrays
!
! ATTRIBUTES:
! LANGUAGE: FORTRAN 90
!-----------------------------------------------------------------------

USE MACHINE , only : kind_phys
IMPLICIT NONE
Expand All @@ -74,7 +59,6 @@ subroutine mp_fer_hires_pre_run (CWM,F_ICE,F_RAIN &
!-- Argument Variables
!----------------------
!
! INTEGER,INTENT(IN) :: NTIMESTEP,LM,IME
INTEGER,INTENT(IN) :: KDT,LM,IME
!
LOGICAL,INTENT(IN) :: SPEC_ADV
Expand Down
41 changes: 0 additions & 41 deletions physics/mp_fer_hires.F90
Original file line number Diff line number Diff line change
Expand Up @@ -126,40 +126,10 @@ SUBROUTINE mp_fer_hires_run(NCOL, NLEV, DT, &
,TRAIN,SR &
,F_ICE,F_RAIN,F_RIMEF &
,QC,QR,QI,QS,QG & ,NI,NR
!ZM ,F_QC,F_QR,F_QI,F_QS,F_QG,F_NI,F_NR &
! ,has_reqc, has_reqi, has_reqs &
,PREC,ACPREC &
,refl_10cm &
,RHGRD &
,errmsg,errflg)
! ,IMS,IME,LM,errmsg,errflg)

! CALL GSMDRIVE(Model%dtp,Model%NPRECIP &
! ,Sfcprop%sm(:),Sfcprop%oro(:) &
! ,Statein%prsi(:,:),Statein%prsl(:,:) &
! ,Stateout%gt0(:,:) &
! ,Stateout%gq0(:,:,1),Stateout%gq0(:,:,2) & !rv CW vs. QC
! ,Diag%TRAIN(:,:),Diag%sr(:) &
! ,Statein%f_ice(:,:),Statein%f_rain(:,:) &
! ,Statein%f_rimef(:,:) &
! ,Stateout%gq0(:,:,Model%ntcw) &
! ,Stateout%gq0(:,:,Model%ntrw) &
! ,Stateout%gq0(:,:,Model%ntiw) &
! ,Stateout%gq0(:,:,Model%ntsw) &
! ,Stateout%gq0(:,:,Model%ntgl) &
! ,Stateout%gq0(:,:,Model%ntinc) &
! ,Stateout%gq0(:,:,Model%ntrnc) &
! ,Model%F_QC,Model%F_QR,Model%F_QI,Model%F_QS &
! ,Model%F_QG,Model%F_NI,Model%F_NR &
! ,Model%has_reqc,Model%has_reqi,Model%has_reqs &
! ,Sfcprop%tprcp(:),Diag%totprcp(:) &
! ,Diag%AVRAIN,Statein%refl_10cm(:,:) &
! ,Statein%re_cloud(:,:) &
! ,Statein%re_ice(:,:),Statein%re_snow(:,:) &
! ,Model%MICROPHYSICS,Model%RHGRD,Diag%TP1(:,:) &
! ,Diag%QP1(:,:),Diag%PSP1(:) &
! ,ims,ime,LM)


!-----------------------------------------------------------------------
USE MACHINE, ONLY: kind_phys
Expand Down Expand Up @@ -193,21 +163,10 @@ SUBROUTINE mp_fer_hires_run(NCOL, NLEV, DT, &
real(kind_phys), intent(inout) :: qi(1:ncol,1:nlev)
real(kind_phys), intent(inout) :: qs(1:ncol,1:nlev)
real(kind_phys), intent(inout) :: qg(1:ncol,1:nlev)
! real(kind_phys), intent(inout) :: ni(1:ncol,1:nlev)
! real(kind_phys), intent(inout) :: nr(1:ncol,1:nlev)
! logical, intent(in ) :: f_qc
! logical, intent(in ) :: f_qr
! logical, intent(in ) :: f_qi
! logical, intent(in ) :: f_qs
! logical, intent(in ) :: f_qg
! logical, intent(in ) :: f_ni
! logical, intent(in ) :: f_nr
! integer, intent(in ) :: has_reqc, has_reqi,has_reqs
real(kind_phys), intent(inout) :: prec(1:ncol)
real(kind_phys), intent(inout) :: acprec(1:ncol)
real(kind_phys), intent(inout) :: refl_10cm(1:ncol,1:nlev)
real(kind_phys), intent(in ) :: rhgrd
! integer, intent(in ) :: IMS,IME,LM
character(len=*), intent(out) :: errmsg
integer, intent(out) :: errflg
!
Expand Down

0 comments on commit dbabee7

Please sign in to comment.