Skip to content

Commit

Permalink
Merge pull request #320 from jedwards4b/replace_esmf_logmsg_error_shr…
Browse files Browse the repository at this point in the history
…_abort

replace calls to esmf_logmsg_error with shr_abort
  • Loading branch information
jedwards4b authored Jan 24, 2025
2 parents 0750c91 + c492b6a commit baa3024
Show file tree
Hide file tree
Showing 5 changed files with 50 additions and 94 deletions.
7 changes: 2 additions & 5 deletions docn/docn_import_data_mod.F90
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
module docn_import_data_mod

use ESMF , only : ESMF_State, ESMF_LOGMSG_INFO, ESMF_LogWrite, ESMF_SUCCESS
use ESMF , only : ESMF_LOGMSG_ERROR, ESMF_FAILURE
use NUOPC , only : NUOPC_Advertise
use shr_kind_mod , only : r8=>shr_kind_r8, i8=>shr_kind_i8, cl=>shr_kind_cl, cs=>shr_kind_cs
use dshr_fldlist_mod , only : fldlist_type, dshr_fldlist_add
Expand Down Expand Up @@ -70,7 +69,7 @@ end subroutine docn_import_data_advertise

!===============================================================================
subroutine docn_get_import_fields(str, flds, rc)

use shr_sys_mod , only : shr_sys_abort
! input/output variables
character(len=*) , intent(in) :: str ! colon deliminted string to search
character(len=*) , allocatable , intent(out) :: flds(:) ! memory will be allocate for flds
Expand Down Expand Up @@ -99,9 +98,7 @@ subroutine docn_get_import_fields(str, flds, rc)
valid = .false.
end if
if (.not. valid) then
call ESMF_LogWrite("ERROR: invalid list = "//trim(str), ESMF_LOGMSG_ERROR)
rc = ESMF_FAILURE
return
call shr_sys_abort("ERROR: invalid list = "//trim(str))
end if
! get number of fields in a colon delimited string list
nflds = 0
Expand Down
4 changes: 2 additions & 2 deletions dshr/dshr_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -89,6 +89,7 @@ module dshr_mod

subroutine dshr_model_initphase(gcomp, importState, exportState, clock, rc)
use ESMF, only : ESMF_ClockIsCreated, ESMF_StateIsCreated
use shr_sys_mod, only : shr_sys_abort
! input/output variables
type(ESMF_GridComp) :: gcomp
type(ESMF_State) :: importState, exportState
Expand All @@ -100,8 +101,7 @@ subroutine dshr_model_initphase(gcomp, importState, exportState, clock, rc)
rc = ESMF_SUCCESS
! To prevent an unused variable warning
if(.not. (ESMF_StateIsCreated(importState) .or. ESMF_StateIsCreated(exportState) .or. ESMF_ClockIsCreated(clock))) then
call ESMF_LogWrite(trim(subname)//' state or clock not created', ESMF_LOGMSG_ERROR)

call shr_sys_abort(trim(subname)//' state or clock not created')
endif

! Switch to IPDv01 by filtering all other phaseMap entries
Expand Down
62 changes: 18 additions & 44 deletions share/nuopc_shr_methods.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ module nuopc_shr_methods
use ESMF , only : operator(<), operator(/=), operator(+)
use ESMF , only : operator(-), operator(*) , operator(>=)
use ESMF , only : operator(<=), operator(>), operator(==), MOD
use ESMF , only : ESMF_LOGERR_PASSTHRU, ESMF_LogFoundError, ESMF_LOGMSG_ERROR, ESMF_MAXSTR
use ESMF , only : ESMF_LOGERR_PASSTHRU, ESMF_LogFoundError, ESMF_MAXSTR
use ESMF , only : ESMF_SUCCESS, ESMF_LogWrite, ESMF_LOGMSG_INFO, ESMF_FAILURE
use ESMF , only : ESMF_State, ESMF_StateGet
use ESMF , only : ESMF_Field, ESMF_FieldGet
Expand Down Expand Up @@ -373,9 +373,7 @@ subroutine state_diagnose(State, string, rc)
call ESMF_LogWrite(trim(msgString), ESMF_LOGMSG_INFO)
endif
else
call ESMF_LogWrite(trim(subname)//": ERROR rank not supported ", ESMF_LOGMSG_ERROR)
rc = ESMF_FAILURE
return
call shr_sys_abort(trim(subname)//": ERROR rank not supported ")
endif
enddo

Expand Down Expand Up @@ -411,10 +409,8 @@ subroutine field_getfldptr(field, fldptr1, fldptr2, rank, abort, rc)
! ----------------------------------------------

if (.not.present(rc)) then
call ESMF_LogWrite(trim(subname)//": ERROR rc not present ", &
ESMF_LOGMSG_ERROR, line=__LINE__, file=u_FILE_u)
rc = ESMF_FAILURE
return
call shr_sys_abort(trim(subname)//": ERROR rc not present ", &
line=__LINE__, file=u_FILE_u)
endif

rc = ESMF_SUCCESS
Expand Down Expand Up @@ -465,27 +461,21 @@ subroutine field_getfldptr(field, fldptr1, fldptr2, rank, abort, rc)
ESMF_LOGMSG_INFO)
elseif (lrank == 1) then
if (.not.present(fldptr1)) then
call ESMF_LogWrite(trim(subname)//": ERROR missing rank=1 array ", &
ESMF_LOGMSG_ERROR, line=__LINE__, file=u_FILE_u)
rc = ESMF_FAILURE
return
call shr_sys_abort(trim(subname)//": ERROR missing rank=1 array ", &
line=__LINE__, file=u_FILE_u)
endif
call ESMF_FieldGet(field, farrayPtr=fldptr1, rc=rc)
if (chkerr(rc,__LINE__,u_FILE_u)) return
elseif (lrank == 2) then
if (.not.present(fldptr2)) then
call ESMF_LogWrite(trim(subname)//": ERROR missing rank=2 array ", &
ESMF_LOGMSG_ERROR, line=__LINE__, file=u_FILE_u)
rc = ESMF_FAILURE
return
call shr_sys_abort(trim(subname)//": ERROR missing rank=2 array ", &
line=__LINE__, file=u_FILE_u)
endif
call ESMF_FieldGet(field, farrayPtr=fldptr2, rc=rc)
if (chkerr(rc,__LINE__,u_FILE_u)) return
else
call ESMF_LogWrite(trim(subname)//": ERROR in rank ", &
ESMF_LOGMSG_ERROR, line=__LINE__, file=u_FILE_u)
rc = ESMF_FAILURE
return
call shr_sys_abort(trim(subname)//": ERROR in rank ", &
line=__LINE__, file=u_FILE_u)
endif

endif ! status
Expand Down Expand Up @@ -566,14 +556,10 @@ subroutine alarmInit( clock, alarm, option, &
! Error checks
if (trim(option) == optdate) then
if (.not. present(opt_ymd)) then
call ESMF_LogWrite(trim(subname)//trim(option)//' requires opt_ymd', ESMF_LOGMSG_ERROR)
rc = ESMF_FAILURE
return
call shr_sys_abort(trim(subname)//trim(option)//' requires opt_ymd')
end if
if (lymd < 0 .or. ltod < 0) then
call ESMF_LogWrite(subname//trim(option)//'opt_ymd, opt_tod invalid', ESMF_LOGMSG_ERROR)
rc = ESMF_FAILURE
return
call shr_sys_abort(subname//trim(option)//'opt_ymd, opt_tod invalid')
end if
else if (&
trim(option) == optNSteps .or. trim(option) == trim(optNSteps)//'s' .or. &
Expand All @@ -584,14 +570,10 @@ subroutine alarmInit( clock, alarm, option, &
trim(option) == optNMonths .or. trim(option) == trim(optNMonths)//'s' .or. &
trim(option) == optNYears .or. trim(option) == trim(optNYears)//'s' ) then
if (.not.present(opt_n)) then
call ESMF_LogWrite(subname//trim(option)//' requires opt_n', ESMF_LOGMSG_ERROR)
rc = ESMF_FAILURE
return
call shr_sys_abort(subname//trim(option)//' requires opt_n')
end if
if (opt_n <= 0) then
call ESMF_LogWrite(subname//trim(option)//' invalid opt_n', ESMF_LOGMSG_ERROR)
rc = ESMF_FAILURE
return
call shr_sys_abort(subname//trim(option)//' invalid opt_n')
end if
end if
call ESMF_TimeIntervalSet(AlarmInterval, yy=9999, rc=rc)
Expand Down Expand Up @@ -629,9 +611,7 @@ subroutine alarmInit( clock, alarm, option, &
AlarmInterval = AlarmInterval * opt_n
! timestepinterval*0 is 0 of kind ESMF_TimeStepInterval
if (mod(AlarmInterval, TimestepInterval) /= (TimestepInterval*0)) then
call ESMF_LogWrite(subname//'illegal Alarm setting for '//trim(alarmname), ESMF_LOGMSG_ERROR)
rc = ESMF_FAILURE
return
call shr_sys_abort(subname//'illegal Alarm setting for '//trim(alarmname))
endif
update_nextalarm = .true.

Expand Down Expand Up @@ -691,9 +671,7 @@ subroutine alarmInit( clock, alarm, option, &
if (ChkErr(rc,__LINE__,u_FILE_u)) return

case default
call ESMF_LogWrite(subname//'unknown option '//trim(option), ESMF_LOGMSG_ERROR)
rc = ESMF_FAILURE
return
call shr_sys_abort(subname//'unknown option '//trim(option))

end select

Expand Down Expand Up @@ -804,14 +782,10 @@ integer function get_minimum_timestep(gcomp, rc)
enddo

if(get_minimum_timestep == huge(1)) then
call ESMF_LogWrite('minimum_timestep_error: this option is not supported ', ESMF_LOGMSG_ERROR)
rc = ESMF_FAILURE
return
call shr_sys_abort('minimum_timestep_error: this option is not supported ')
endif
if(get_minimum_timestep <= 0) then
call ESMF_LogWrite('minimum_timestep_error ERROR ', ESMF_LOGMSG_ERROR)
rc = ESMF_FAILURE
return
call shr_sys_abort('minimum_timestep_error ERROR ')
endif
end function get_minimum_timestep

Expand Down
18 changes: 10 additions & 8 deletions share/shr_abort_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ module shr_abort_mod
! when these routines were defined in shr_sys_mod.)

use, intrinsic :: iso_fortran_env, only: output_unit, error_unit
use ESMF, only : ESMF_Finalize, ESMF_END_ABORT, ESMF_LOGMSG_ERROR, ESMF_LogWrite

use shr_kind_mod, only : shr_kind_in, shr_kind_cx
use shr_log_mod , only : s_logunit => shr_log_Unit

Expand All @@ -34,14 +34,15 @@ module shr_abort_mod
contains

!===============================================================================
subroutine shr_abort_abort(string,rc)
subroutine shr_abort_abort(string,rc, line, file)
use esmf, only : ESMF_LOGWRITE, ESMF_LOGMSG_ERROR, ESMF_FINALIZE, ESMF_END_ABORT
! Consistent stopping mechanism

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

!----- local -----
integer(shr_kind_in), intent(in), optional :: line
character(len=*), intent(in), optional :: file

! Local version of the string.
! (Gets a default value if string is not present.)
Expand All @@ -53,15 +54,16 @@ subroutine shr_abort_abort(string,rc)
else
local_string = "Unknown error submitted to shr_abort_abort."
end if
if(present(rc)) then
write(local_string, *) trim(local_string), ' rc=',rc
endif

call print_error_to_logs("ERROR", local_string)

call ESMF_LogWrite(local_string, ESMF_LOGMSG_ERROR, line=line, file=file)

call shr_abort_backtrace()

if(present(rc)) then
write(local_string, *) trim(local_string), ' rc=',rc
endif
call ESMF_LogWrite(local_string, ESMF_LOGMSG_ERROR)
call ESMF_Finalize(endflag=ESMF_END_ABORT)

! A compiler's abort method may print a backtrace or do other nice
Expand Down
53 changes: 18 additions & 35 deletions streams/dshr_methods_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -6,14 +6,15 @@ module dshr_methods_mod
use ESMF , only : ESMF_LogWrite, ESMF_SUCCESS, ESMF_FAILURE
use ESMF , only : ESMF_StateRemove, ESMF_StateGet, ESMF_RouteHandle
use ESMF , only : ESMF_Region_Flag, ESMF_FieldStatus_Flag, ESMF_LOGMSG_INFO
use ESMF , only : ESMF_MAXSTR, ESMF_LOGMSG_ERROR, ESMF_LOGERR_PASSTHRU
use ESMF , only : ESMF_MAXSTR, ESMF_LOGERR_PASSTHRU
use ESMF , only : ESMF_FieldBundleGet, ESMF_FieldBundleAdd, ESMF_FieldGet
use ESMF , only : ESMF_REGION_TOTAL, ESMF_END_ABORT, ESMF_ITEMORDER_ADDORDER
use ESMF , only : ESMF_LogFoundError, ESMF_FieldRegrid, ESMF_Finalize, ESMF_FIELDSTATUS_COMPLETE
use ESMF , only : ESMF_TERMORDER_SRCSEQ, operator(/=)
use ESMF , only : ESMF_TraceRegionEnter, ESMF_TraceRegionExit
use shr_kind_mod , only : r8=>shr_kind_r8, cs=>shr_kind_cs, cl=>shr_kind_cl

use shr_sys_mod , only : shr_sys_abort

implicit none
public

Expand Down Expand Up @@ -139,9 +140,7 @@ subroutine dshr_state_diagnose(State, flds_scalar_name, string, rc)
write(msgString,'(A,a)') trim(string)//': '//trim(lfieldnamelist(n))," no data"
endif
else
call ESMF_LogWrite(trim(subname)//": ERROR rank not supported ", ESMF_LOGMSG_ERROR)
rc = ESMF_FAILURE
return
call shr_sys_abort(trim(subname)//": ERROR rank not supported ")
endif
call ESMF_LogWrite(trim(msgString), ESMF_LOGMSG_INFO)
end if
Expand Down Expand Up @@ -177,30 +176,24 @@ subroutine dshr_fldbun_GetFldPtr(FB, fldname, fldptr1, fldptr2, rank, field, rc)
rc = ESMF_SUCCESS

if (.not. dshr_fldbun_FldChk(FB, trim(fldname), rc=rc)) then
call ESMF_LogWrite(trim(subname)//": ERROR field "//trim(fldname)//" not in FB ", ESMF_LOGMSG_ERROR)
rc = ESMF_FAILURE
return
call shr_sys_abort(trim(subname)//": ERROR field "//trim(fldname)//" not in FB ")
endif
call ESMF_FieldBundleGet(FB, fieldName=trim(fldname), field=lfield, rc=rc)
if (chkerr(rc,__LINE__,u_FILE_u)) return
call ESMF_FieldGet(lfield, ungriddedUBound=ungriddedUBound, rc=rc)
if (chkerr(rc,__LINE__,u_FILE_u)) return
if (ungriddedUBound(1) > 0) then
if (.not.present(fldptr2)) then
call ESMF_LogWrite(trim(subname)//": ERROR missing rank=2 array ", &
ESMF_LOGMSG_ERROR, line=__LINE__, file=u_FILE_u)
rc = ESMF_FAILURE
return
call shr_sys_abort(trim(subname)//": ERROR missing rank=2 array ", &
line=__LINE__, file=u_FILE_u)
endif
call ESMF_FieldGet(lfield, farrayptr=fldptr2, rc=rc)
if (chkerr(rc,__LINE__,u_FILE_u)) return
lrank = 2
else
if (.not.present(fldptr1)) then
call ESMF_LogWrite(trim(subname)//": ERROR missing rank=1 array ", &
ESMF_LOGMSG_ERROR, line=__LINE__, file=u_FILE_u)
rc = ESMF_FAILURE
return
call shr_sys_abort(trim(subname)//": ERROR missing rank=1 array ", &
line=__LINE__, file=u_FILE_u)
endif
call ESMF_FieldGet(lfield, farrayptr=fldptr1, rc=rc)
if (chkerr(rc,__LINE__,u_FILE_u)) return
Expand Down Expand Up @@ -339,9 +332,7 @@ subroutine dshr_fldbun_getNameN(FB, fieldnum, fieldname, rc)
call ESMF_FieldBundleGet(FB, fieldCount=fieldCount, rc=rc)
if (chkerr(rc,__LINE__,u_FILE_u)) return
if (fieldnum > fieldCount) then
call ESMF_LogWrite(trim(subname)//": ERROR fieldnum > fieldCount ", ESMF_LOGMSG_ERROR)
rc = ESMF_FAILURE
return
call shr_sys_abort(trim(subname)//": ERROR fieldnum > fieldCount ")
endif

allocate(lfieldnamelist(fieldCount))
Expand Down Expand Up @@ -377,9 +368,7 @@ logical function dshr_fldbun_FldChk(FB, fldname, rc)

call ESMF_FieldBundleGet(FB, fieldName=trim(fldname), isPresent=isPresent, rc=rc)
if (chkerr(rc,__LINE__,u_FILE_u)) then
call ESMF_LogWrite(trim(subname)//" Error checking field: "//trim(fldname), ESMF_LOGMSG_ERROR)
rc = ESMF_FAILURE
return
call shr_sys_abort(trim(subname)//" Error checking field: "//trim(fldname))
endif

if (isPresent) then
Expand Down Expand Up @@ -434,9 +423,7 @@ subroutine dshr_fldbun_Field_diagnose(FB, fieldname, string, rc)
write(msgString,'(A,a)') trim(subname)//' '//trim(lstring)//': '//trim(fieldname)," no data"
endif
else
call ESMF_LogWrite(trim(subname)//": ERROR rank not supported ", ESMF_LOGMSG_ERROR)
rc = ESMF_FAILURE
return
call shr_sys_abort(trim(subname)//": ERROR rank not supported ")
endif
call ESMF_LogWrite(trim(msgString), ESMF_LOGMSG_INFO)

Expand Down Expand Up @@ -505,9 +492,7 @@ subroutine dshr_fldbun_diagnose(FB, string, rc)
endif

else
call ESMF_LogWrite(trim(subname)//": ERROR rank not supported ", ESMF_LOGMSG_ERROR)
rc = ESMF_FAILURE
return
call shr_sys_abort(trim(subname)//": ERROR rank not supported ")
endif
call ESMF_LogWrite(trim(msgString), ESMF_LOGMSG_INFO)
enddo
Expand Down Expand Up @@ -557,9 +542,7 @@ subroutine dshr_field_getfldptr(field, fldptr1, fldptr2, rank, abort, rc)
if (labort) then
call ESMF_FieldGet(field, name=name, rc=rc)
if (chkerr(rc,__LINE__,u_FILE_u)) return
call ESMF_LogWrite(trim(subname)//": field "//trim(name)//" has no data not allocated ", ESMF_LOGMSG_ERROR, rc=rc)
rc = ESMF_FAILURE
return
call shr_sys_abort(trim(subname)//": field "//trim(name)//" has no data not allocated ", rc=rc)
else
call ESMF_LogWrite(trim(subname)//": WARNING data not allocated ", ESMF_LOGMSG_INFO, rc=rc)
endif
Expand All @@ -568,8 +551,8 @@ subroutine dshr_field_getfldptr(field, fldptr1, fldptr2, rank, abort, rc)
if (chkerr(rc,__LINE__,u_FILE_u)) return
if (ungriddedUBound(1) > 0) then
if (.not.present(fldptr2)) then
call ESMF_LogWrite(trim(subname)//": ERROR missing rank=2 array for "//trim(name), &
ESMF_LOGMSG_ERROR, line=__LINE__, file=u_FILE_u)
call shr_sys_abort(trim(subname)//": ERROR missing rank=2 array for "//trim(name), &
line=__LINE__, file=u_FILE_u)
rc = ESMF_FAILURE
return
endif
Expand All @@ -578,8 +561,8 @@ subroutine dshr_field_getfldptr(field, fldptr1, fldptr2, rank, abort, rc)
lrank = 2
else
if (.not.present(fldptr1)) then
call ESMF_LogWrite(trim(subname)//": ERROR missing rank=1 array for "//trim(name), &
ESMF_LOGMSG_ERROR, line=__LINE__, file=u_FILE_u)
call shr_sys_abort(trim(subname)//": ERROR missing rank=1 array for "//trim(name), &
line=__LINE__, file=u_FILE_u)
rc = ESMF_FAILURE
return
endif
Expand Down

0 comments on commit baa3024

Please sign in to comment.