Skip to content

Commit

Permalink
Merge pull request #549 from GEOS-ESM/develop
Browse files Browse the repository at this point in the history
Sync develop into main for GOCART2G
  • Loading branch information
sdrabenh authored Feb 18, 2022
2 parents 194bd0a + 7661a71 commit ae3cf7c
Show file tree
Hide file tree
Showing 5 changed files with 227 additions and 20 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -1318,7 +1318,9 @@ subroutine SetServices ( GC, RC )

!Aerosol
call MAPL_AddConnectivity ( GC, &
SHORT_NAME = (/'AERO_ACI'/), &
SHORT_NAME = (/'AERO'/), &
! SHORT_NAME = (/'AERO_ACI '/), &
! SHORT_NAME = (/'AERO_ACI ', 'AERO2G_ACI'/), &
DST_ID = MOIST, &
SRC_ID = CHEM, &
RC=STATUS )
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -9939,6 +9939,7 @@ SUBROUTINE get_incloud_sc_chem_up(cumulus,fscav,mtp,se,se_cup,sc_up,pw_up,tot_pw
if( TRIM(CHEM_name (ispc)) == 'sulfur' .or. &

TRIM(CHEM_name (ispc)(1:len_trim('ss') )) == 'ss' .or. & ! 'seasalt'
TRIM(CHEM_name (ispc)(1:len_trim('SS') )) == 'SS' .or. & ! 'seasalt 2G'

TRIM(CHEM_name (ispc)) == 'SO2' .or. &
TRIM(CHEM_name (ispc)) == 'SO4' .or. &
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -839,13 +839,13 @@ subroutine SetServices ( GC, RC )
RC=STATUS )
VERIFY_(STATUS)

call MAPL_AddImportSpec(GC, &
LONG_NAME = 'aerosol_cloud_interaction', &
UNITS = '1', &
SHORT_NAME = 'AERO_ACI', &
DIMS = MAPL_DimsHorzVert, &
VLOCATION = MAPL_VLocationCenter, &
DATATYPE = MAPL_StateItem, &
call MAPL_AddImportSpec(GC, &
LONG_NAME = 'aerosols', &
UNITS = '1', &
SHORT_NAME = 'AERO', &
DIMS = MAPL_DimsHorzVert, &
VLOCATION = MAPL_VLocationCenter, &
DATATYPE = MAPL_StateItem, &
RC=STATUS )
VERIFY_(STATUS)

Expand Down Expand Up @@ -3844,6 +3844,73 @@ subroutine SetServices ( GC, RC )
! CAR 12/5/08
! Aerosol Scavenging diagnostics/export states
! ------------------------------
call MAPL_AddExportSpec(GC, &
SHORT_NAME='DDU2gDT ', &
LONG_NAME ='dust_tendency_due_to_conv_scav', &
UNITS ='kg m-2 s-1', &
DIMS = MAPL_DimsHorzOnly, &
__RC__ )

call MAPL_AddExportSpec(GC, &
SHORT_NAME='DSS2gDT ', &
LONG_NAME ='sea_salt_tendency_due_to_conv_scav', &
UNITS ='kg m-2 s-1', &
DIMS = MAPL_DimsHorzOnly, &
__RC__ )

call MAPL_AddExportSpec(GC, &
SHORT_NAME='DOC2gDT ', &
LONG_NAME ='organic_carbon_tendency_due_to_conv_scav', &
UNITS ='kg m-2 s-1', &
DIMS = MAPL_DimsHorzOnly, &
__RC__ )

call MAPL_AddExportSpec(GC, &
SHORT_NAME='DBC2gDT ', &
LONG_NAME ='black_carbon_tendency_due_to_conv_scav', &
UNITS ='kg m-2 s-1', &
DIMS = MAPL_DimsHorzOnly, &
__RC__ )

call MAPL_AddExportSpec(GC, &
SHORT_NAME='DSU2gDT ', &
LONG_NAME ='sulfate_tendency_due_to_conv_scav', &
UNITS ='kg m-2 s-1', &
DIMS = MAPL_DimsHorzOnly, &
__RC__ )

call MAPL_AddExportSpec(GC, &
SHORT_NAME='DNI2gDT', &
LONG_NAME ='nitrate_tendency_due_to_conv_scav', &
UNITS ='kg m-2 s-1', &
DIMS = MAPL_DimsHorzOnly, &
__RC__ )

call MAPL_AddExportSpec(GC, &
SHORT_NAME='DNH4A2gDT', &
LONG_NAME ='ammonium_aerosol_tendency_due_to_conv_scav', &
UNITS ='kg m-2 s-1', &
DIMS = MAPL_DimsHorzOnly, &
__RC__ )

call MAPL_AddExportSpec(GC, &
SHORT_NAME='DNH32gDT', &
LONG_NAME ='ammonia_tendency_due_to_conv_scav', &
UNITS ='kg m-2 s-1', &
DIMS = MAPL_DimsHorzOnly, &
__RC__ )

call MAPL_AddExportSpec(GC, &
SHORT_NAME='DBRC2gDT', &
LONG_NAME ='brown_carbon_tendency_due_to_conv_scav', &
UNITS ='kg m-2 s-1', &
DIMS = MAPL_DimsHorzOnly, &
__RC__ )





call MAPL_AddExportSpec(GC, &
SHORT_NAME='DDUDT ', &
LONG_NAME ='dust_tendency_due_to_conv_scav', &
Expand Down Expand Up @@ -5567,6 +5634,8 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)
! CAR
real, pointer, dimension(:,: ) :: DDUDT, &
DSSDT, DOCDT, DBCDT, DSUDT, DNIDT, DNH4ADT, DNH3DT, DBRCDT, DDUDTcarma, DSSDTcarma
real, pointer, dimension(:,: ) :: DDU2gDT, &
DSS2gDT, DOC2gDT, DBC2gDT, DSU2gDT, DNI2gDT, DNH4A2gDT, DNH32gDT, DBRC2gDT
character(len=ESMF_MAXSTR) :: QNAME, CNAME, ENAME
character(len=ESMF_MAXSTR), pointer, dimension(:) :: QNAMES, CNAMES
integer :: ind
Expand Down Expand Up @@ -5827,6 +5896,7 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)
character(len=ESMF_MAXSTR), allocatable, dimension(:) :: aero_aci_modes
integer :: ACI_STATUS


type (AerProps), dimension (IM, JM, LM) :: AeroProps !Storages aerosol properties for activation
type (AerProps) :: AeroAux, AeroAux_b

Expand Down Expand Up @@ -6242,6 +6312,7 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)
real :: cNN, cNN_OCEAN, cNN_LAND, CONVERT

real , dimension(IM,JM) :: CMDU, CMSS, CMOC, CMBC, CMSU, CMNI, CMNH3, CMNH4A, CMBRC
real , dimension(IM,JM) :: CMDU2g, CMSS2g, CMOC2g, CMBC2g, CMSU2g, CMNI2g, CMNH32g, CMNH4A2g, CMBRC2g
real , dimension(IM,JM) :: CMDUcarma, CMSScarma

real :: sigmaqt, qcn, cfn, qsatn, dqlls, dqils, qt
Expand Down Expand Up @@ -6948,6 +7019,16 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)
call MAPL_GetPointer(EXPORT, ENTLAM, 'ENTLAM' , RC=STATUS); VERIFY_(STATUS)
! Aerosol Scavenging
! CAR 12/5/08
call MAPL_GetPointer(EXPORT, DDU2gDT, 'DDU2gDT' , RC=STATUS); VERIFY_(STATUS)
call MAPL_GetPointer(EXPORT, DSS2gDT, 'DSS2gDT' , RC=STATUS); VERIFY_(STATUS)
call MAPL_GetPointer(EXPORT, DBC2gDT, 'DBC2gDT' , RC=STATUS); VERIFY_(STATUS)
call MAPL_GetPointer(EXPORT, DOC2gDT, 'DOC2gDT' , RC=STATUS); VERIFY_(STATUS)
call MAPL_GetPointer(EXPORT, DSU2gDT, 'DSU2gDT' , RC=STATUS); VERIFY_(STATUS)
call MAPL_GetPointer(EXPORT, DNI2gDT, 'DNI2gDT' , RC=STATUS); VERIFY_(STATUS)
call MAPL_GetPointer(EXPORT, DNH4A2gDT, 'DNH4A2gDT' , RC=STATUS); VERIFY_(STATUS)
call MAPL_GetPointer(EXPORT, DNH32gDT, 'DNH32gDT' , RC=STATUS); VERIFY_(STATUS)
call MAPL_GetPointer(EXPORT, DBRC2gDT, 'DBRC2gDT' , RC=STATUS); VERIFY_(STATUS)

call MAPL_GetPointer(EXPORT, DDUDT, 'DDUDT' , RC=STATUS); VERIFY_(STATUS)
call MAPL_GetPointer(EXPORT, DSSDT, 'DSSDT' , RC=STATUS); VERIFY_(STATUS)
call MAPL_GetPointer(EXPORT, DBCDT, 'DBCDT' , RC=STATUS); VERIFY_(STATUS)
Expand Down Expand Up @@ -7926,21 +8007,21 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)
end do


call ESMF_StateGet(IMPORT, 'AERO_ACI', aero_aci, __RC__)
call ESMF_StateGet(IMPORT, 'AERO', aero_aci, __RC__)

call ESMF_AttributeGet(aero_aci, name='implements_aerosol_activation_properties_method', &
value=implements_aerosol_activation_properties, __RC__)
! call ESMF_AttributeGet(aero_aci, name='implements_aerosol_activation_properties_method', &
! value=implements_aerosol_activation_properties, __RC__)

if (implements_aerosol_activation_properties) then
! if (implements_aerosol_activation_properties) then

call ESMF_AttributeGet(aero_aci, name='number_of_aerosol_modes', value=n_modes, __RC__)

if (n_modes > 0) then

allocate(aero_aci_modes(n_modes), __STAT__)
call ESMF_AttributeGet(aero_aci, name='aerosol_modes', itemcount=n_modes, valuelist=aero_aci_modes, __RC__)
call ESMF_AttributeGet(aero_aci, name='air_pressure', value=aci_field_name, __RC__)

call ESMF_AttributeGet(aero_aci, name='air_pressure_for_aerosol_optics', value=aci_field_name, __RC__)
if (aci_field_name /= '') then
call MAPL_GetPointer(aero_aci, aci_ptr_3d, trim(aci_field_name), __RC__)
aci_ptr_3d = PLE
Expand Down Expand Up @@ -8000,7 +8081,7 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)
#if (0)
if (MAPL_AM_I_ROOT()) then
print *
print *, 'AERO_ACI::' // trim(aero_aci_modes(n))
print *, 'AERO::' // trim(aero_aci_modes(n))

print *, 'num : ', aci_num(1,1,LM)
print *, 'dgn : ', aci_dgn(1,1,LM)
Expand Down Expand Up @@ -8064,11 +8145,11 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)

call MAPL_TimerOff(STATE,"--USE_AEROSOL_NN1")

else
! else
! options:
! *) set aerosol concentrations to 0.0, i.e., no aerosol
! *) raise an exception if aerosol is required!
end if
! end if


call init_Aer(AeroAux)
Expand Down Expand Up @@ -8340,6 +8421,16 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)
! Compute initial mass loading for aerosols; CAR 12/19/08
! -------------------------------------------------------
!! First initialize everything to zero
if(associated(DDU2gDT)) DDU2gDT = 0.0
if(associated(DSS2gDT)) DSS2gDT = 0.0
if(associated(DBC2gDT)) DBC2gDT = 0.0
if(associated(DOC2gDT)) DOC2gDT = 0.0
if(associated(DSU2gDT)) DSU2gDT = 0.0
if(associated(DNI2gDT)) DNI2gDT = 0.0
if(associated(DNH4A2gDT)) DNH4A2gDT = 0.0
if(associated(DNH32gDT)) DNH32gDT = 0.0
if(associated(DBRC2gDT)) DBRC2gDT= 0.0

if(associated(DDUDT)) DDUDT = 0.0
if(associated(DSSDT)) DSSDT = 0.0
if(associated(DBCDT)) DBCDT = 0.0
Expand All @@ -8352,6 +8443,16 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)
if(associated(DDUDTcarma)) DDUDTcarma = 0.0
if(associated(DSSDTcarma)) DSSDTcarma = 0.0

CMDU2g = 0.0
CMSS2g = 0.0
CMOC2g = 0.0
CMBC2g = 0.0
CMSU2g = 0.0
CMNI2g = 0.0
CMNH4A2g = 0.0
CMNH32g = 0.0
CMBRC2g = 0.0

CMDU = 0.0
CMSS = 0.0
CMOC = 0.0
Expand All @@ -8366,13 +8467,59 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)

!! Now loop over tracers and accumulate initial column loading
!! tendency kg/m2/s CAR

!if(mapl_am_i_root()) print*,'MOIST CNAMES = ',CNAMES
KK=0
do K=1,KM
if(IS_FRIENDLY(K)) then
KK = KK + 1
QNAME = trim(QNAMES(K))
CNAME = trim(CNAMES(K))
if((CNAME == 'DU') .or. (CNAME == 'SS') .or. (CNAME == 'NI') .or. (CNAME == 'SU') .or. &
(CNAME == 'CA.oc') .or. (CNAME == 'CA.bc') .or. (CNAME == 'CA.br')) then ! Diagnostics for GOCART2G tracers
SELECT CASE (QNAME(1:3))
CASE ('DU0')
if(associated(DDU2gDT)) then
CMDU2g = CMDU2g + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
CASE ('SS0')
if(associated(DSS2gDT)) then
CMSS2g = CMSS2g + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
CASE ('SO4')
if(associated(DSU2gDT)) then
CMSU2g = CMSU2g + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
CASE ('NO3')
if(associated(DNI2gDT)) then
CMNI2g = CMNI2g + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
CASE ('NH3')
if(associated(DNH32gDT)) then
CMNH32g = CMNH32g + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
CASE ('NH4')
if(associated(DNH4A2gDT)) then
CMNH4A2g = CMNH4A2g + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
END SELECT

SELECT CASE (QNAME(1:13))
CASE ('CAphilicCA.bc')
if(associated(DBC2gDT)) then
CMBC2g = CMBC2g + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
! CASE ('OCp')
CASE ('CAphilicCA.oc')
if(associated(DOC2gDT)) then
CMOC2g = CMOC2g + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
CASE ('CAphilicCA.br')
if(associated(DBRC2gDT)) then
CMBRC2g = CMBRC2g + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
END SELECT
endif

if(CNAME == 'GOCART') then ! Diagnostics for GOCART tracers
SELECT CASE (QNAME(1:3))
CASE ('du0')
Expand Down Expand Up @@ -8413,6 +8560,7 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)
end if
END SELECT
endif

if(CNAME == 'CARMA') then ! Diagnostics for CARMA tracers
! Check name to see if it is a "pc" element
ENAME = ''
Expand Down Expand Up @@ -8873,6 +9021,52 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)
KK = KK + 1
QNAME = trim(QNAMES(K))
CNAME = trim(CNAMES(K))
if((CNAME == 'DU') .or. (CNAME == 'SS') .or. (CNAME == 'NI') .or. (CNAME == 'SU') .or. &
(CNAME == 'CA.oc') .or. (CNAME == 'CA.bc') .or. (CNAME == 'CA.br')) then ! Diagnostics for GOCART2G tracers
SELECT CASE (QNAME(1:3))
CASE ('DU0')
if(associated(DDU2gDT)) then
DDU2gDT = DDU2gDT + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
CASE ('SS0')
if(associated(DSS2gDT)) then
DSS2gDT = DSS2gDT + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
CASE ('SO4')
if(associated(DSU2gDT)) then
DSU2gDT = DSU2gDT + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
CASE ('NO3')
if(associated(DNI2gDT)) then
DNI2gDT = DNI2gDT + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
CASE ('NH3')
if(associated(DNH32gDT)) then
DNH32gDT = DNH32gDT + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
CASE ('NH4')
if(associated(DNH4A2gDT)) then
DNH4A2gDT = DNH4A2gDT + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
END SELECT

SELECT CASE (QNAME(1:13))
CASE ('CAphilicCA.bc')
if(associated(DBC2gDT)) then
DBC2gDT = DBC2gDT + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
! CASE ('OCp')
CASE ('CAphilicCA.oc')
if(associated(DOC2gDT)) then
DOC2gDT = DOC2gDT + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
CASE ('CAphilicCA.br')
if(associated(DBRC2gDT)) then
DBRC2gDT = DBRC2gDT + sum(XHO(:,:,:,KK)*DP(:,:,:),dim=3)
end if
END SELECT
endif

if(CNAME == 'GOCART') then ! Diagnostics for GOCART tracers
SELECT CASE (QNAME(1:3))
CASE ('du0')
Expand Down Expand Up @@ -8936,6 +9130,16 @@ subroutine MOIST_DRIVER(IM,JM,LM, RC)
endif
end do

if (associated(DDU2gDT)) DDU2gDT = (DDU2gDT - CMDU2g) / (MAPL_GRAV*DT_MOIST)
if (associated(DSS2gDT)) DSS2gDT = (DSS2gDT - CMSS2g) / (MAPL_GRAV*DT_MOIST)
if (associated(DBC2gDT)) DBC2gDT = (DBC2gDT - CMBC2g) / (MAPL_GRAV*DT_MOIST)
if (associated(DOC2gDT)) DOC2gDT = (DOC2gDT - CMOC2g) / (MAPL_GRAV*DT_MOIST)
if (associated(DSU2gDT)) DSU2gDT = (DSU2gDT - CMSU2g) / (MAPL_GRAV*DT_MOIST)
if (associated(DNI2gDT)) DNI2gDT = (DNI2gDT - CMNI2g) / (MAPL_GRAV*DT_MOIST)
if (associated(DNH32gDT)) DNH32gDT = (DNH32gDT - CMNH32g) / (MAPL_GRAV*DT_MOIST)
if (associated(DNH4A2gDT)) DNH4A2gDT = (DNH4A2gDT - CMNH4A2g) / (MAPL_GRAV*DT_MOIST)
if (associated(DBRC2gDT)) DBRC2gDT= (DBRC2gDT- CMBRC2g)/ (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)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -1820,7 +1820,7 @@ subroutine Lw_Driver(IM,JM,LM,LATS,LONS,CoresPerNode,RC)
VERIFY_(STATUS)

! execute the aero provider's optics method
call ESMF_MethodExecute(AERO, label="aerosol_optics", RC=STATUS)
call ESMF_MethodExecute(AERO, label="run_aerosol_optics", RC=STATUS)
VERIFY_(STATUS)

! EXT from AERO_PROVIDER
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -1895,7 +1895,7 @@ subroutine RUN ( GC, IMPORT, EXPORT, CLOCK, RC )
value=(BANDS_SOLAR_OFFSET+band), __RC__)

! execute the aero provider's optics method
call ESMF_MethodExecute(AERO, label="aerosol_optics", userRC=AS_STATUS, RC=STATUS)
call ESMF_MethodExecute(AERO, label="run_aerosol_optics", userRC=AS_STATUS, RC=STATUS)
VERIFY_(AS_STATUS)
VERIFY_(STATUS)

Expand Down

0 comments on commit ae3cf7c

Please sign in to comment.