Skip to content

Commit

Permalink
Merge pull request #423 from GEOS-ESM/develop
Browse files Browse the repository at this point in the history
Sync develop into main
  • Loading branch information
sdrabenh authored Apr 15, 2021
2 parents 7d9761d + 1d158c9 commit 3553b5f
Show file tree
Hide file tree
Showing 14 changed files with 647 additions and 441 deletions.
2 changes: 1 addition & 1 deletion .circleci/config.yml
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ version: 2.1
executors:
gcc-build-env:
docker:
- image: gmao/ubuntu20-geos-env-mkl:v6.0.27-openmpi_4.0.5-gcc_10.2.0
- image: gmao/ubuntu20-geos-env-mkl:v6.1.0-openmpi_4.0.5-gcc_10.2.0
auth:
username: $DOCKERHUB_USER
password: $DOCKERHUB_AUTH_TOKEN
Expand Down
2 changes: 1 addition & 1 deletion .github/workflows/workflow.yml
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ jobs:
if: "!contains(github.event.pull_request.labels.*.name, '0 diff trivial')"
runs-on: ubuntu-latest
container:
image: gmao/ubuntu20-geos-env-mkl:v6.0.27-openmpi_4.0.5-gcc_10.2.0
image: gmao/ubuntu20-geos-env-mkl:v6.1.0-openmpi_4.0.5-gcc_10.2.0
credentials:
username: ${{ secrets.DOCKERHUB_USERNAME }}
password: ${{ secrets.DOCKERHUB_TOKEN }}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -1219,7 +1219,7 @@ subroutine SetServices ( GC, RC )
'CN ', 'RHOS ', 'WET2 ', &
'SNOMAS ', 'SNOWDP ', 'ITY ', &
'LHFX ', 'Q2M ', 'Q10M ', &
'T10M ' /), &
'T10M ', 'WCSF ' /), &
DST_ID = CHEM, &
SRC_ID = SURF, &
RC=STATUS )
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -9930,6 +9930,7 @@ SUBROUTINE get_incloud_sc_chem_up(cumulus,fscav,mtp,se,se_cup,sc_up,pw_up,tot_pw
! - if tracer is type "carbon" then set coefficient to 0 for hydrophobic
if( TRIM(CHEM_name (ispc)(1:len_trim('OCphobic') )) == 'OCphobic') factor_temp(ispc,:,:) = 0.0


! - suppress scavenging most aerosols at cold T except BCn1 (hydrophobic), dust, and HNO3
if( TRIM(CHEM_name (ispc)(1:len_trim('BCphobic') )) == 'BCphobic') then
where(tempco < 258.) factor_temp(ispc,:,:) = 0.0
Expand All @@ -9942,7 +9943,7 @@ SUBROUTINE get_incloud_sc_chem_up(cumulus,fscav,mtp,se,se_cup,sc_up,pw_up,tot_pw
TRIM(CHEM_name (ispc)) == 'SO2' .or. &
TRIM(CHEM_name (ispc)) == 'SO4' .or. &

TRIM(CHEM_name (ispc)) == 'nitrate' .or. &
TRIM(CHEM_name (ispc)(1:len_trim('NO3an') )) == 'NO3an' .or. &
TRIM(CHEM_name (ispc)) == 'bromine' .or. &
TRIM(CHEM_name (ispc)) == 'NH3' .or. &
TRIM(CHEM_name (ispc)) == 'NH4a' ) then
Expand Down Expand Up @@ -10071,38 +10072,28 @@ FUNCTION henry(ispc,temp,rhoair) RESULT(henry_coef)
real , intent(in) :: temp,rhoair
real :: henry_coef
real :: fct ,tcorr, corrh

!--- define some constants!
real, parameter:: rgas = 8.32e-2 ! atm M^-1 K^-1 ! 8.314 gas constant [J/(mol*K)]
real, parameter:: avogad= 6.022e23! Avogadro constant [1/mol]
real, parameter:: rhoH2O= 999.9668! density of water [kg/m3]
real, parameter:: temp0 = 298.15! standard temperature [K]
real, parameter:: temp0i= 1./298.15! inverse of standard temperature [K]
real, parameter:: MWH2O = 18.02! molecular mass of water [kg/kmol]
real, parameter:: MWAIR = 28.97! effective molecular mass of air [kg/kmol]
real, parameter:: conv3 = avogad / 1.0e6! [mol(g)/m3(air)] to [molec(g)/cm3(air)]
real, parameter:: conv4 = 100. ! [m] to [cm]
real, parameter:: conv5 = 1000. ! [m^3] to [l]
real, parameter:: conv7 = 1/conv5 ! [l] to [m^3]
real, parameter:: conv6 = 1. / 101325. ! [Pa] to [atm]
real, parameter:: hplus = 1.175E-4 ! for cloud water. pH is asuumed to be 3.93: pH=3.93 =>hplus=10**(-pH)

real, parameter:: rgas = 8.205e-2 ! atm M^-1 K^-1 ! 8.314 gas constant [J/(mol*K)]
real, parameter:: temp0i= 1./298.15 ! inverse of standard temperature [K]
real, parameter:: hplus = 1.175E-4 ! for cloud water. pH is asuumed to be 3.93: pH=3.93 =>hplus=10**(-pH)

! aqueous-phase concentrations XXXa [mol/m3(air)]!
! gas-phase concentrations XXXg [mol/m3(air)]!
! Henry constants XXXh for scavenging [mol/(l*atm)]!
! converted to [(mol(aq)/m3(aq))/(mol(g)/m3(air))], i.e. dimensionless!
! in equilibrium XXXa = XXXh * LWC * XXXg!
tcorr = 1./temp - temp0i
fct = conv7 * rgas * temp

fct = rgas * temp
!-taking into account the acid dissociation constant
! ak=ak0*exp(dak*(1/t-1/298))
corrh=1.+Hcts(ispc)%ak0 * exp(Hcts(ispc)%dak * tcorr)/hplus

!-- for concentration in mol[specie]/mol[air] - Eq 5 in 'Compilation of Henry's law constants (version 4.0) for
!-- water as solvent, R. Sander, ACP 2015'.
henry_coef = Hcts(ispc)%hstar* exp(Hcts(ispc)%dhr*tcorr) * fct * corrh

henry_coef = Hcts(ispc)%hstar* exp(Hcts(ispc)%dhr*tcorr) * fct * corrh
END FUNCTION henry

!---------------------------------------------------------------------------------------------------
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3608,6 +3608,30 @@ subroutine SetServices ( GC, RC )
RC=STATUS )
VERIFY_(STATUS)

call MAPL_AddExportSpec(GC, &
SHORT_NAME='DNH4ADT', &
LONG_NAME ='ammonium_aerosol_tendency_due_to_conv_scav', &
UNITS ='kg m-2 s-1', &
DIMS = MAPL_DimsHorzOnly, &
RC=STATUS )
VERIFY_(STATUS)

call MAPL_AddExportSpec(GC, &
SHORT_NAME='DNH3DT', &
LONG_NAME ='ammonia_tendency_due_to_conv_scav', &
UNITS ='kg m-2 s-1', &
DIMS = MAPL_DimsHorzOnly, &
RC=STATUS )
VERIFY_(STATUS)

call MAPL_AddExportSpec(GC, &
SHORT_NAME='DBRCDT', &
LONG_NAME ='brown_carbon_tendency_due_to_conv_scav', &
UNITS ='kg m-2 s-1', &
DIMS = MAPL_DimsHorzOnly, &
RC=STATUS )
VERIFY_(STATUS)

call MAPL_AddExportSpec(GC, &
SHORT_NAME='DDUDTcarma ', &
LONG_NAME ='carma_dust_tendency_due_to_conv_scav', &
Expand Down Expand Up @@ -5276,7 +5300,7 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)
! Aerosol convective scavenging internal pointers (2D column-averages); must deallocate!!!
! CAR
real, pointer, dimension(:,: ) :: DDUDT, &
DSSDT, DOCDT, DBCDT, DSUDT, DNIDT, DDUDTcarma, DSSDTcarma
DSSDT, DOCDT, DBCDT, DSUDT, DNIDT, DNH4ADT, DNH3DT, DBRCDT, DDUDTcarma, DSSDTcarma
character(len=ESMF_MAXSTR) :: QNAME, CNAME, ENAME
character(len=ESMF_MAXSTR), pointer, dimension(:) :: QNAMES, CNAMES
integer :: ind
Expand Down Expand Up @@ -5952,7 +5976,7 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)
real :: icefall
real :: cNN, cNN_OCEAN, cNN_LAND, CONVERT

real , dimension(IM,JM) :: CMDU, CMSS, CMOC, CMBC, CMSU, CMNI
real , dimension(IM,JM) :: CMDU, CMSS, CMOC, CMBC, CMSU, CMNI, CMNH3, CMNH4A, CMBRC
real , dimension(IM,JM) :: CMDUcarma, CMSScarma

real :: sigmaqt, qcn, cfn, qsatn, dqlls, dqils, qt
Expand Down Expand Up @@ -6609,6 +6633,9 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)
call MAPL_GetPointer(EXPORT, DOCDT, 'DOCDT' , RC=STATUS); VERIFY_(STATUS)
call MAPL_GetPointer(EXPORT, DSUDT, 'DSUDT' , RC=STATUS); VERIFY_(STATUS)
call MAPL_GetPointer(EXPORT, DNIDT, 'DNIDT' , RC=STATUS); VERIFY_(STATUS)
call MAPL_GetPointer(EXPORT, DNH4ADT, 'DNH4ADT' , RC=STATUS); VERIFY_(STATUS)
call MAPL_GetPointer(EXPORT, DNH3DT, 'DNH3DT' , RC=STATUS); VERIFY_(STATUS)
call MAPL_GetPointer(EXPORT, DBRCDT, 'DBRCDT' , RC=STATUS); VERIFY_(STATUS)
call MAPL_GetPointer(EXPORT, DDUDTcarma, 'DDUDTcarma' , RC=STATUS); VERIFY_(STATUS)
call MAPL_GetPointer(EXPORT, DSSDTcarma, 'DSSDTcarma' , RC=STATUS); VERIFY_(STATUS)

Expand Down Expand Up @@ -7974,21 +8001,27 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)
! Compute initial mass loading for aerosols; CAR 12/19/08
! -------------------------------------------------------
!! First initialize everything to zero
if(associated(DDUDT)) DDUDT = 0.0
if(associated(DSSDT)) DSSDT = 0.0
if(associated(DBCDT)) DBCDT = 0.0
if(associated(DOCDT)) DOCDT = 0.0
if(associated(DSUDT)) DSUDT = 0.0
if(associated(DNIDT)) DNIDT = 0.0
if(associated(DDUDT)) DDUDT = 0.0
if(associated(DSSDT)) DSSDT = 0.0
if(associated(DBCDT)) DBCDT = 0.0
if(associated(DOCDT)) DOCDT = 0.0
if(associated(DSUDT)) DSUDT = 0.0
if(associated(DNIDT)) DNIDT = 0.0
if(associated(DNH4ADT)) DNH4ADT = 0.0
if(associated(DNH3DT)) DNH3DT = 0.0
if(associated(DBRCDT)) DBRCDT= 0.0
if(associated(DDUDTcarma)) DDUDTcarma = 0.0
if(associated(DSSDTcarma)) DSSDTcarma = 0.0

CMDU = 0.0
CMSS = 0.0
CMOC = 0.0
CMBC = 0.0
CMSU = 0.0
CMNI = 0.0
CMDU = 0.0
CMSS = 0.0
CMOC = 0.0
CMBC = 0.0
CMSU = 0.0
CMNI = 0.0
CMNH4A = 0.0
CMNH3 = 0.0
CMBRC = 0.0
CMDUcarma = 0.0
CMSScarma = 0.0

Expand Down Expand Up @@ -8027,6 +8060,18 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)
if(associated(DNIDT)) then
CMNI = CMNI + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
CASE ('NH3')
if(associated(DNH3DT)) then
CMNH3 = CMNH3 + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
CASE ('NH4')
if(associated(DNH4ADT)) then
CMNH4A = CMNH4A + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
CASE ('BRC')
if(associated(DBRCDT)) then
CMBRC = CMBRC + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
END SELECT
endif
if(CNAME == 'CARMA') then ! Diagnostics for CARMA tracers
Expand Down Expand Up @@ -8514,6 +8559,18 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)
if(associated(DNIDT)) then
DNIDT = DNIDT + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
CASE ('NH3')
if(associated(DNH3DT)) then
DNH3DT = DNH3DT + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
CASE ('NH4')
if(associated(DNH4ADT)) then
DNH4ADT = DNH4ADT + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
CASE ('BRC')
if(associated(DBRCDT)) then
DBRCDT = DBRCDT + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
END SELECT
endif
end if
Expand All @@ -8539,12 +8596,15 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)
endif
end do

if (associated(DDUDT)) DDUDT = (DDUDT - CMDU) / (MAPL_GRAV*DT_MOIST)
if (associated(DSSDT)) DSSDT = (DSSDT - CMSS) / (MAPL_GRAV*DT_MOIST)
if (associated(DBCDT)) DBCDT = (DBCDT - CMBC) / (MAPL_GRAV*DT_MOIST)
if (associated(DOCDT)) DOCDT = (DOCDT - CMOC) / (MAPL_GRAV*DT_MOIST)
if (associated(DSUDT)) DSUDT = (DSUDT - CMSU) / (MAPL_GRAV*DT_MOIST)
if (associated(DNIDT)) DNIDT = (DNIDT - CMNI) / (MAPL_GRAV*DT_MOIST)
if (associated(DDUDT)) DDUDT = (DDUDT - CMDU) / (MAPL_GRAV*DT_MOIST)
if (associated(DSSDT)) DSSDT = (DSSDT - CMSS) / (MAPL_GRAV*DT_MOIST)
if (associated(DBCDT)) DBCDT = (DBCDT - CMBC) / (MAPL_GRAV*DT_MOIST)
if (associated(DOCDT)) DOCDT = (DOCDT - CMOC) / (MAPL_GRAV*DT_MOIST)
if (associated(DSUDT)) DSUDT = (DSUDT - CMSU) / (MAPL_GRAV*DT_MOIST)
if (associated(DNIDT)) DNIDT = (DNIDT - CMNI) / (MAPL_GRAV*DT_MOIST)
if (associated(DNH3DT)) DNH3DT = (DNH3DT - CMNH3) / (MAPL_GRAV*DT_MOIST)
if (associated(DNH4ADT)) DNH4ADT = (DNH4ADT - CMNH4A) / (MAPL_GRAV*DT_MOIST)
if (associated(DBRCDT)) DBRCDT= (DBRCDT- CMBRC)/ (MAPL_GRAV*DT_MOIST)

if (associated(DDUDTcarma)) DDUDTcarma = (DDUDTcarma - CMDUcarma) / (MAPL_GRAV*DT_MOIST)
if (associated(DSSDTcarma)) DSSDTcarma = (DSSDTcarma - CMSScarma) / (MAPL_GRAV*DT_MOIST)
Expand Down
Loading

0 comments on commit 3553b5f

Please sign in to comment.