Skip to content

Commit

Permalink
physics/module_mp_thompson.F90, physics/mp_thompson.F90: cleanup, ret…
Browse files Browse the repository at this point in the history
…urn with an error if CCN_ACTIVATE.BIN is not found, remove temporary stopping of model
  • Loading branch information
climbfuji committed Jul 9, 2019
1 parent 86ade1c commit 1d8cb0b
Show file tree
Hide file tree
Showing 2 changed files with 14 additions and 16 deletions.
26 changes: 12 additions & 14 deletions physics/module_mp_thompson.F90
Original file line number Diff line number Diff line change
Expand Up @@ -414,7 +414,8 @@ SUBROUTINE thompson_init(nwfa2d, nifa2d, nwfa, nifa, &
ids, ide, jds, jde, kds, kde, &
ims, ime, jms, jme, kms, kme, &
its, ite, jts, jte, kts, kte, &
mpicomm, mpirank, mpiroot, threads)
mpicomm, mpirank, mpiroot, &
threads, errmsg, errflg)

IMPLICIT NONE

Expand All @@ -428,6 +429,8 @@ SUBROUTINE thompson_init(nwfa2d, nifa2d, nwfa, nifa, &
REAL, DIMENSION(ims:ime,jms:jme), OPTIONAL, INTENT(IN) :: nwfa2d, nifa2d
INTEGER, INTENT(IN) :: mpicomm, mpirank, mpiroot
INTEGER, INTENT(IN) :: threads
CHARACTER(len=*), INTENT(INOUT) :: errmsg
INTEGER, INTENT(INOUT) :: errflg


INTEGER:: i, j, k, l, m, n
Expand Down Expand Up @@ -881,7 +884,8 @@ SUBROUTINE thompson_init(nwfa2d, nifa2d, nwfa, nifa, &
! doing it always ensures that the correct data is in the SIONlib
! file containing the precomputed tables *DH
WRITE (*,*) ' calling table_ccnAct routine'
call table_ccnAct
call table_ccnAct(errmsg,errflg)
if (.not. errflg==0) return

!> - Call table_efrw() and table_efsw() to creat collision efficiency table
!! between rain/snow and cloud water
Expand Down Expand Up @@ -4613,15 +4617,17 @@ end subroutine table_dropEvap
!! vertical velocity, temperature, lognormal mean aerosol radius, and
!! hygroscopicity, kappa. The data are read from external file and
!! contain activated fraction of CCN for given conditions.
subroutine table_ccnAct
subroutine table_ccnAct(errmess,errflag)

implicit none

!..Error handling variables
CHARACTER(len=*), INTENT(INOUT) :: errmess
INTEGER, INTENT(INOUT) :: errflag

!..Local variables
INTEGER:: iunit_mp_th1, i
LOGICAL:: opened
CHARACTER*64 errmess

iunit_mp_th1 = -1
DO i = 20,99
Expand Down Expand Up @@ -4649,19 +4655,11 @@ subroutine table_ccnAct
RETURN
9009 CONTINUE
WRITE( errmess , '(A,I2)' ) 'module_mp_thompson: error opening CCN_ACTIVATE.BIN on unit ',iunit_mp_th1
write(0,*) errmess
! DH* TEMPORARY FIX 20181203
call sleep(5)
stop
! *DH
errflag = 1
RETURN
9010 CONTINUE
WRITE( errmess , '(A,I2)' ) 'module_mp_thompson: error reading CCN_ACTIVATE.BIN on unit ',iunit_mp_th1
write(0,*) errmess
! DH* TEMPORARY FIX 20181203
call sleep(5)
stop
! *DH
errflag = 1
RETURN

end subroutine table_ccnAct
Expand Down
4 changes: 2 additions & 2 deletions physics/mp_thompson.F90
Original file line number Diff line number Diff line change
Expand Up @@ -124,7 +124,7 @@ subroutine mp_thompson_init(ncol, nlev, is_aerosol_aware, &
ims=ims, ime=ime, jms=jms, jme=jme, kms=kms, kme=kme, &
its=its, ite=ite, jts=jts, jte=jte, kts=kts, kte=kte, &
mpicomm=mpicomm, mpirank=mpirank, mpiroot=mpiroot, &
threads=threads)
threads=threads, errmsg=errmsg, errflg=errflg)
if (errflg /= 0) return
else if (is_aerosol_aware) then
write(errmsg,fmt='(*(a))') 'Logic error in mp_thompson_init:', &
Expand All @@ -137,7 +137,7 @@ subroutine mp_thompson_init(ncol, nlev, is_aerosol_aware, &
ims=ims, ime=ime, jms=jms, jme=jme, kms=kms, kme=kme, &
its=its, ite=ite, jts=jts, jte=jte, kts=kts, kte=kte, &
mpicomm=mpicomm, mpirank=mpirank, mpiroot=mpiroot, &
threads=threads)
threads=threads, errmsg=errmsg, errflg=errflg)
if (errflg /= 0) return
end if

Expand Down

0 comments on commit 1d8cb0b

Please sign in to comment.