Skip to content

Commit

Permalink
allocate diagstate
Browse files Browse the repository at this point in the history
  • Loading branch information
bbakernoaa committed Oct 2, 2024
1 parent 884e15b commit 77f2531
Show file tree
Hide file tree
Showing 3 changed files with 12 additions and 5 deletions.
6 changes: 3 additions & 3 deletions src/core/diagstate_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -112,9 +112,9 @@ subroutine Diag_Allocate(Config, DiagState, ChemState, RC)
IF ( RC /= CC_SUCCESS ) THEN
ErrMsg = 'Could not Allocate DiagState%drydep_frequency(ChemState%nSpeciesAeroDryDep)'
CALL CC_Error( ErrMsg, RC, thisLoc )
! else
! write (*,*) "ChemState%nSpeciesAeroDryDep=", ChemState%nSpeciesAeroDryDep
! write (*,*) "allocated DiagState%drydep_frequency(ChemState%nSpeciesAeroDryDep) "
! else
! write (*,*) "ChemState%nSpeciesAeroDryDep=", ChemState%nSpeciesAeroDryDep
! write (*,*) "allocated DiagState%drydep_frequency(ChemState%nSpeciesAeroDryDep) "
ENDIF
DiagState%drydep_frequency(ChemState%nSpeciesAeroDryDep)= ZERO

Expand Down
4 changes: 2 additions & 2 deletions src/process/drydep/CCPr_DryDep_Mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -242,8 +242,8 @@ SUBROUTINE CCPr_DryDep_Run( MetState, DiagState, DryDepState, ChemState, RC )
!print *, "drydepf(1,1) = ", drydepf(1,1)
DryDepState%drydep_frequency(ChemState%DryDepIndex(i)) = drydepf(1,1)
DryDepState%drydep_vel(ChemState%DryDepIndex(i)) = MetState%ZMID(1) * drydepf(1,1)
!DiagState%drydep_frequency= DryDepState%drydep_frequency(ChemState%DryDepIndex(i))
!DiagState%drydep_vel = DryDepState%drydep_vel(ChemState%DryDepIndex(i))
DiagState%drydep_frequency(i)= drydepf(1,1)
DiagState%drydep_vel(i) = MetState%ZMID(1) * drydepf(1,1)

! apply drydep velocities/freq to chem species
dqa = 0.
Expand Down
7 changes: 7 additions & 0 deletions tests/test_drydep.f90
Original file line number Diff line number Diff line change
Expand Up @@ -90,6 +90,13 @@ program test_drydep
! Turn off resuspension
DryDepState%Resuspension = .FALSE.

! Allocate DiagState
call cc_allocate_diagstate(Config, DiagState, ChemState, RC)
if (rc /= CC_SUCCESS) then
errMsg = 'Error in cc_allocate_diagstate'
stop 1
endif

title = "DryDep Test 2 | Test GOCART DryDep defaults"

call cc_drydep_init(Config, DryDepState, ChemState, rc)
Expand Down

0 comments on commit 77f2531

Please sign in to comment.