Skip to content

Commit

Permalink
fix aero_state%wghtpct function for carma optics
Browse files Browse the repository at this point in the history
        modified:   src/chemistry/aerosol/aerosol_state_mod.F90
        modified:   src/chemistry/aerosol/carma_aerosol_state_mod.F90
        modified:   src/chemistry/aerosol/hygrowghtpct_aerosol_optics_mod.F90
        modified:   src/chemistry/aerosol/modal_aerosol_state_mod.F90
        modified:   src/physics/carma/cam/carma_intr.F90
  • Loading branch information
fvitt committed Oct 18, 2023
1 parent 7837e39 commit 326a6c3
Show file tree
Hide file tree
Showing 5 changed files with 39 additions and 31 deletions.
5 changes: 3 additions & 2 deletions src/chemistry/aerosol/aerosol_state_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -251,10 +251,11 @@ end subroutine aero_water_uptake
!------------------------------------------------------------------------------
! aerosol weight precent of H2SO4/H2O solution
!------------------------------------------------------------------------------
function aero_wgtpct(self) result(wtp)
function aero_wgtpct(self, icol,ilev) result(wtp)
import :: aerosol_state, r8
class(aerosol_state), intent(in) :: self
real(r8), pointer :: wtp(:,:)
integer, intent(in) :: icol,ilev
real(r8) :: wtp ! weight precent of H2SO4/H2O solution for given icol, ilev

end function aero_wgtpct

Expand Down
12 changes: 7 additions & 5 deletions src/chemistry/aerosol/carma_aerosol_state_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ module carma_aerosol_state_mod
use physconst, only: pi
use carma_intr, only: carma_get_total_mmr, carma_get_dry_radius, carma_get_number, carma_get_number_cld
use carma_intr, only: carma_get_group_by_name, carma_get_kappa, carma_get_dry_radius, carma_get_wet_radius
use carma_intr, only: carma_sulfate_wght_pct
use ppgrid, only: begchunk, endchunk, pcols, pver

implicit none
Expand Down Expand Up @@ -446,12 +447,13 @@ end subroutine water_uptake
!------------------------------------------------------------------------------
! aerosol weight precent of H2SO4/H2O solution
!------------------------------------------------------------------------------
function wgtpct(self) result(wtp)
function wgtpct(self, icol,ilev) result(wtp)
class(carma_aerosol_state), intent(in) :: self
real(r8), pointer :: wtp(:,:) ! weight precent of H2SO4/H2O solution
! ****** NEED TO IMPLEMENT ******
!!$ call pbuf_get_field(self%pbuf, pbuf_get_index('WTP'), wtp)
nullify(wtp)
integer, intent(in) :: icol,ilev
real(r8) :: wtp ! weight precent of H2SO4/H2O solution for given icol, ilev

wtp = carma_sulfate_wght_pct(icol,ilev, self%state%lchnk)

end function wgtpct

!------------------------------------------------------------------------------
Expand Down
13 changes: 7 additions & 6 deletions src/chemistry/aerosol/hygrowghtpct_aerosol_optics_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -58,9 +58,9 @@ function constructor(aero_props, aero_state, ilist, ibin, ncol, nlev) result(new

integer :: ierr, nspec
integer :: ispec
integer :: i,k

real(r8), pointer :: specmmr(:,:) ! species mass mixing ratio
real(r8), pointer :: wgtpct_in(:,:) ! weight precent of H2SO4/H2O solution

allocate(newobj, stat=ierr)
if (ierr/=0) then
Expand All @@ -79,14 +79,15 @@ function constructor(aero_props, aero_state, ilist, ibin, ncol, nlev) result(new
nullify(newobj)
return
end if
! copy weight precent of H2SO4/H2O solution from aerosol state object
do k = 1,nlev
do i = 1,ncol
newobj%wgtpct(i,k) = aero_state%wgtpct(i,k)
end do
end do

!!$ wgtpct_in => aero_state%wgtpct()
!! *** NEED TO FIX ***
call aero_props%optics_params(ilist, ibin, wgtpct=newobj%tbl_wgtpct, nwtp=newobj%nwtp)

!!$ newobj%wgtpct(:ncol,:) = wgtpct_in(:ncol,:)
newobj%wgtpct(:ncol,:) = 0._r8

nspec = aero_props%nspecies(ilist, ibin)

newobj%totalmmr(:,:) = 0._r8
Expand Down
7 changes: 4 additions & 3 deletions src/chemistry/aerosol/modal_aerosol_state_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -598,11 +598,12 @@ end function water_volume
!------------------------------------------------------------------------------
! aerosol weight precent of H2SO4/H2O solution
!------------------------------------------------------------------------------
function wgtpct(self) result(wtp)
function wgtpct(self, icol,ilev) result(wtp)
class(modal_aerosol_state), intent(in) :: self
real(r8), pointer :: wtp(:,:) ! weight precent of H2SO4/H2O solution
integer, intent(in) :: icol,ilev
real(r8) :: wtp ! weight precent of H2SO4/H2O solution for given icol, ilev

nullify(wtp)
wtp = -huge(1._r8)

end function wgtpct

Expand Down
33 changes: 18 additions & 15 deletions src/physics/carma/cam/carma_intr.F90
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ module carma_intr
use shr_kind_mod, only: r8 => shr_kind_r8
use spmd_utils, only: masterproc, mpicom
use shr_reprosum_mod, only : shr_reprosum_calc
use ppgrid, only: pcols, pver, pverp
use ppgrid, only: pcols, pver, pverp, begchunk,endchunk
use ref_pres, only: pref_mid, pref_edge, pref_mid_norm, psurf_ref
use physics_types, only: physics_state, physics_ptend, physics_ptend_init, &
set_dry_to_wet, physics_state_copy
Expand Down Expand Up @@ -90,7 +90,6 @@ module carma_intr
public carma_get_bin_rmass
public carma_set_bin


! NOTE: This is required by physpkg.F90, since the carma_intr.F90 stub in physics/cam
! does not have access to carma_constant.F90, but needs to also provide a defintion
! for MAXCLDAERDIAG. Thus the definition of this variable needs to come from
Expand Down Expand Up @@ -203,6 +202,8 @@ module carma_intr
! elements.
real (r8) :: carma_massscalefactor(NGROUP, NBIN)

! sulfate weight percent -- updated in carma_timestep_tend
real(r8), allocatable, public, protected :: carma_sulfate_wght_pct(:,:,:)

contains

Expand Down Expand Up @@ -579,6 +580,7 @@ subroutine carma_init(pbuf2d)

logical :: history_carma
logical :: history_carma_srf_flx
integer :: astat

aero_check_routine=>carma_checkstate_local

Expand Down Expand Up @@ -805,6 +807,14 @@ subroutine carma_init(pbuf2d)
call CARMAMODEL_InitializeModel(carma, lq_carma, pbuf2d, rc)
if (rc < 0) call endrun('carma_init::CARMA_InitializeModel failed.')

! allocate sulfate weight percent array
allocate(carma_sulfate_wght_pct(pcols,pver,begchunk:endchunk),stat=astat)
if( astat /= 0 ) then
write(iulog,*) 'carma_init: failed to allocate carma_sulfate_wght_pct, error = ',astat
call endrun
end if
carma_sulfate_wght_pct(:,:,:) = -huge(1._r8)

return
end subroutine carma_init

Expand Down Expand Up @@ -854,6 +864,8 @@ subroutine carma_final
call CARMA_Destroy(carma, rc)
if (rc < 0) call endrun('carma_final::CARMA_Destroy failed.')

deallocate(carma_sulfate_wght_pct)

return
end subroutine carma_final

Expand Down Expand Up @@ -1458,7 +1470,7 @@ subroutine carma_timestep_tend(state, cam_in, cam_out, ptend, dt, pbuf, dlf, rli
call pbuf_get_field(pbuf, ipbuf4satl(igas), satl_ptr)

call CARMASTATE_GetGas(cstate, igas, newstate(:), rc, satice=satice, satliq=satliq, &
eqice=eqice, eqliq=eqliq, wtpct=wtpct)
eqice=eqice, eqliq=eqliq, wtpct=wtpct)
if (rc < 0) call endrun('carma_timestep_tend::CARMASTATE_GetGas failed.')

icnst = icnst4gas(igas)
Expand Down Expand Up @@ -1521,10 +1533,12 @@ subroutine carma_timestep_tend(state, cam_in, cam_out, ptend, dt, pbuf, dlf, rli
call CARMASTATE_Destroy(cstate, rc)
if (rc < 0) call endrun('carma_timestep_tend::CARMASTATE_Destroy failed.')


! Output diagnostic fields.
call carma_output_diagnostics(state_loc, ptend, pbuf, cam_in, gpdiags, sbdiags, gsdiags, spdiags, bndiags)

! save sulfate weight percent
carma_sulfate_wght_pct(:state%ncol,:,state%lchnk) = gsdiags(:state%ncol,:,I_GAS_H2SO4,GSDIAGS_WT)

end subroutine carma_timestep_tend

!! Check the CARMA aerosol to make sure that for each aerosol the
Expand Down Expand Up @@ -4423,15 +4437,4 @@ subroutine carma_get_bin_rmass(igroup, ibin, mass, rc)

end subroutine carma_get_bin_rmass

!!$ subroutine carma_get_wtpct
!!$
!!$ real(r8) :: mmr_gas(pver) !! gas mass mixing ratio (kg/kg)
!!$
!!$ do igas = 1,NGAS
!!$ if(igas .eq. I_GAS_H2SO4)then ! only output the sulfate weight percent
!!$ call CARMASTATE_GetGas(cstate, igas, mmr_gas(:), rc, wtpct=wtpct)
!!$ end if
!!$ end do
!!$
!!$ end subroutine carma_get_wtpct
end module carma_intr

0 comments on commit 326a6c3

Please sign in to comment.