Skip to content

Commit

Permalink
Slightly modify the Thompson scheme but it will not change the baseline
Browse files Browse the repository at this point in the history
  • Loading branch information
ChunxiZhang-NOAA committed Sep 28, 2022
1 parent fb66f0f commit d49e0d6
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 17 deletions.
25 changes: 8 additions & 17 deletions physics/module_mp_thompson.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1142,15 +1142,12 @@ SUBROUTINE mp_gt_driver(qv, qc, qr, qi, qs, qg, ni, nr, nc, &

if ( (present(tt) .and. (present(th) .or. present(pii))) .or. &
(.not.present(tt) .and. .not.(present(th) .and. present(pii))) ) then
if (present(errmsg)) then
if (present(errmsg) .and. present(errflg)) then
write(errmsg, '(a)') 'Logic error in mp_gt_driver: provide either tt or th+pii'
else
write(*,'(a)') 'Logic error in mp_gt_driver: provide either tt or th+pii'
end if
if (present(errflg)) then
errflg = 1
return
else
write(*,'(a)') 'Logic error in mp_gt_driver: provide either tt or th+pii'
stop
end if
end if
Expand All @@ -1160,33 +1157,27 @@ SUBROUTINE mp_gt_driver(qv, qc, qr, qi, qs, qg, ni, nr, nc, &
.not.present(nifa) .or. &
.not.present(nwfa2d) .or. &
.not.present(nifa2d) )) then
if (present(errmsg)) then
if (present(errmsg) .and. present(errflg)) then
write(errmsg, '(*(a))') 'Logic error in mp_gt_driver: provide nc, nwfa, nifa, nwfa2d', &
' and nifa2d for aerosol-aware version of Thompson microphysics'
else
write(*, '(*(a))') 'Logic error in mp_gt_driver: provide nc, nwfa, nifa, nwfa2d', &
' and nifa2d for aerosol-aware version of Thompson microphysics'
end if
if (present(errflg)) then
errflg = 1
return
else
write(*, '(*(a))') 'Logic error in mp_gt_driver: provide nc, nwfa, nifa, nwfa2d', &
' and nifa2d for aerosol-aware version of Thompson microphysics'
stop
end if
else if (merra2_aerosol_aware .and. (.not.present(nc) .or. &
.not.present(nwfa) .or. &
.not.present(nifa) )) then
if (present(errmsg)) then
if (present(errmsg) .and. present(errflg)) then
write(errmsg, '(*(a))') 'Logic error in mp_gt_driver: provide nc, nwfa, and nifa', &
' for merra2 aerosol-aware version of Thompson microphysics'
else
write(*, '(*(a))') 'Logic error in mp_gt_driver: provide nc, nwfa, and nifa', &
' for merra2 aerosol-aware version of Thompson microphysics'
end if
if (present(errflg)) then
errflg = 1
return
else
write(*, '(*(a))') 'Logic error in mp_gt_driver: provide nc, nwfa, and nifa', &
' for merra2 aerosol-aware version of Thompson microphysics'
stop
end if
else if (.not.is_aerosol_aware .and. .not.merra2_aerosol_aware .and. &
Expand Down
8 changes: 8 additions & 0 deletions physics/mp_thompson.F90
Original file line number Diff line number Diff line change
Expand Up @@ -879,6 +879,14 @@ subroutine mp_thompson_finalize(errmsg, errflg)
end subroutine mp_thompson_finalize

subroutine get_niwfa(aerfld, nifa, nwfa, ncol, nlev)
! To calculate nifa and nwfa from bins of aerosols.
! In GOCART and MERRA2, aerosols are given as mixing ratio (kg/kg). To
! convert from kg/kg to #/kg, the "unit mass" (mass of one particle)
! within the mass bins is calculated. A lognormal size distribution
! within aerosol bins is used to find the size based upon the median
! mass. NIFA is mainly summarized over five dust bins and NWFA over the
! other 10 bins. The parameters besides each bins are carefully tuned
! for a good performance of the scheme.
implicit none
integer, intent(in)::ncol, nlev
real (kind=kind_phys), dimension(:,:,:), intent(in) :: aerfld
Expand Down

0 comments on commit d49e0d6

Please sign in to comment.