Skip to content
Draft
Show file tree
Hide file tree
Changes from 2 commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,9 @@ module CNBalanceCheckMod
! Module for carbon/nitrogen mass balance checking.
!
! !USES:

use ESMF

use shr_kind_mod , only : r8 => shr_kind_r8
use nanMod , only : nan
use shr_log_mod , only : errMsg => shr_log_errMsg
Expand Down Expand Up @@ -220,6 +223,7 @@ subroutine CBalanceCheck(this, bounds, num_soilc, filter_soilc, &
real(r8) :: som_c_leached_grc(bounds%begg:bounds%endg)
real(r8) :: hrv_xsmrpool_amount_left_to_dribble(bounds%begg:bounds%endg)
real(r8) :: dwt_conv_cflux_amount_left_to_dribble(bounds%begg:bounds%endg)
integer :: rc
!-----------------------------------------------------------------------

associate( &
Expand Down Expand Up @@ -307,7 +311,7 @@ subroutine CBalanceCheck(this, bounds, num_soilc, filter_soilc, &
write(iulog,*)'wood_harvestc = ',wood_harvestc(c)*dt
write(iulog,*)'grainc_to_cropprodc = ',grainc_to_cropprodc(c)*dt
write(iulog,*)'-1*som_c_leached = ',som_c_leached(c)*dt
call endrun(msg=errMsg(sourcefile, __LINE__))
call endrun(msg=errMsg(sourcefile, __LINE__),rc)
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Come to think of it, why not just use _ASSERT(.false.) here (and below)?? In any case, we probably need to take a look at error handling throughout the code in ./CLM51

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

My initial commit doesn't build because I didn't specify "Iam" in the CTSM abort routines. It doesn't make much sense to do that. I'll fix it in a bit along the lines of doing _ASSERT instead of endrun() in the science code

end if

! Repeat error check at the gridcell level
Expand Down Expand Up @@ -379,11 +383,13 @@ subroutine CBalanceCheck(this, bounds, num_soilc, filter_soilc, &
write(iulog,*)'dwt_seedc_to_deadstem_grc =', dwt_seedc_to_deadstem_grc(g) * dt
write(iulog,*)'--- Outputs ---'
write(iulog,*)'-1*som_c_leached_grc = ', som_c_leached_grc(g) * dt
call endrun(msg=errMsg(sourcefile, __LINE__))
call endrun(msg=errMsg(sourcefile, __LINE__),rc)
end if

end associate

RETURN_(ESMF_SUCCESS)

end subroutine CBalanceCheck

!-----------------------------------------------------------------------
Expand Down Expand Up @@ -426,6 +432,7 @@ subroutine NBalanceCheck(this, bounds, num_soilc, filter_soilc, &
real(r8):: grc_ninputs(bounds%begg:bounds%endg)
real(r8):: grc_noutputs(bounds%begg:bounds%endg)
real(r8):: grc_errnb(bounds%begg:bounds%endg)
integer :: rc
!-----------------------------------------------------------------------

associate( &
Expand Down Expand Up @@ -545,7 +552,7 @@ subroutine NBalanceCheck(this, bounds, num_soilc, filter_soilc, &



call endrun(msg=errMsg(sourcefile, __LINE__))
call endrun(msg=errMsg(sourcefile, __LINE__),rc)
end if

! Repeat error check at the gridcell level
Expand Down Expand Up @@ -619,11 +626,13 @@ subroutine NBalanceCheck(this, bounds, num_soilc, filter_soilc, &
write(iulog,*) 'grc_noutputs_partial =', grc_noutputs_partial(g) * dt
write(iulog,*) 'dwt_conv_nflux_grc =', dwt_conv_nflux_grc(g) * dt
write(iulog,*) 'product_loss_grc =', product_loss_grc(g) * dt
call endrun(msg=errMsg(sourcefile, __LINE__))
call endrun(msg=errMsg(sourcefile, __LINE__),rc)
end if

end associate

RETURN_(ESMF_SUCCESS)

end subroutine NBalanceCheck

end module CNBalanceCheckMod
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,8 @@ module abortutils
! Abort the model for abnormal termination
!-----------------------------------------------------------------------

use ESMF

private
save

Expand All @@ -20,7 +22,7 @@ module abortutils
CONTAINS

!-----------------------------------------------------------------------
subroutine endrun_vanilla(msg, additional_msg)
subroutine endrun_vanilla(msg, additional_msg, rc)

!-----------------------------------------------------------------------
! !DESCRIPTION:
Expand All @@ -39,6 +41,7 @@ subroutine endrun_vanilla(msg, additional_msg)
! and then just assert against msg.
character(len=*), intent(in), optional :: msg ! string to be passed to shr_sys_abort
character(len=*), intent(in), optional :: additional_msg ! string to be printed, but not passed to shr_sys_abort
integer, intent(out),optional :: rc ! return code
!-----------------------------------------------------------------------

if (present (additional_msg)) then
Expand All @@ -47,12 +50,14 @@ subroutine endrun_vanilla(msg, additional_msg)
write(iulog,*)'ENDRUN:'
end if

call shr_sys_abort(msg)
call shr_sys_abort(msg,rc)

RETURN_(ESMF_SUCCESS)

end subroutine endrun_vanilla

!-----------------------------------------------------------------------
subroutine endrun_globalindex(decomp_index, clmlevel, msg, additional_msg)
subroutine endrun_globalindex(decomp_index, clmlevel, msg, additional_msg, rc)

!-----------------------------------------------------------------------
! Description:
Expand All @@ -74,6 +79,7 @@ subroutine endrun_globalindex(decomp_index, clmlevel, msg, additional_msg)
! and then just assert against msg.
character(len=*), intent(in), optional :: msg ! string to be passed to shr_sys_abort
character(len=*), intent(in), optional :: additional_msg ! string to be printed, but not passed to shr_sys_abort
integer, intent(out),optional :: rc ! return code
!
! Local Variables:
integer :: igrc, ilun, icol
Expand All @@ -88,8 +94,10 @@ subroutine endrun_globalindex(decomp_index, clmlevel, msg, additional_msg)
write(iulog,*)'ENDRUN:'
end if

call shr_sys_abort(msg)
call shr_sys_abort(msg, rc)

RETURN_(ESMF_SUCCESS)

end subroutine endrun_globalindex

end module abortutils
Original file line number Diff line number Diff line change
Expand Up @@ -11,9 +11,10 @@ module shr_abort_mod

use, intrinsic :: iso_fortran_env, only: output_unit, error_unit

use ESMF
use MAPL_ExceptionHandling
use shr_kind_mod, only : shr_kind_in, shr_kind_cx
! use shr_mpi_mod , only : shr_mpi_initialized, shr_mpi_abort
!use shr_mpi_mod , only : shr_mpi_initialized, shr_mpi_abort
use shr_log_mod , only : s_logunit => shr_log_Unit

!#ifdef CPRNAG
Expand All @@ -33,18 +34,17 @@ module shr_abort_mod
! (shr_sys_abort, shr_sys_backtrace). (This is for consistency with older code, from
! when these routines were defined in shr_sys_mod.)
public :: shr_abort_abort ! abort a program
! public :: shr_abort_backtrace ! print a backtrace, if possible
!public :: shr_abort_backtrace ! print a backtrace, if possible

contains

!===============================================================================
subroutine shr_abort_abort(string,ec,rc)
subroutine shr_abort_abort(string,rc)
! Consistent stopping mechanism

!----- arguments -----
character(len=*) , intent(in) , optional :: string ! error message string
integer(shr_kind_in), intent(in) , optional :: ec ! error code
integer(shr_kind_in), intent(out), optional :: rc ! error code
integer(shr_kind_in), intent(out), optional :: rc ! return code

!----- local -----
!logical :: flag
Expand All @@ -62,21 +62,19 @@ subroutine shr_abort_abort(string,ec,rc)

call print_error_to_logs("ERROR", local_string)

! call shr_abort_backtrace()
!call shr_abort_backtrace()

! call shr_mpi_initialized(flag)
!call shr_mpi_initialized(flag)

if (present(ec)) then
_ASSERT(.FALSE.,trim(local_string))
else
_ASSERT(.FALSE.,trim(local_string))
endif
_ASSERT(.FALSE.,trim(local_string))

! A compiler's abort method may print a backtrace or do other nice
! things, but in fact we can rarely leverage this, because MPI_Abort
! usually sends SIGTERM to the process, and we don't catch that signal.
!call abort()


RETURN_(ESMF_SUCCESS)

end subroutine shr_abort_abort
!===============================================================================

Expand Down
Loading