Skip to content

Commit

Permalink
Merge pull request #36 from jedwards4b/shr_file_to_shr_log
Browse files Browse the repository at this point in the history
move shr_file_setlogunit to shr_log_setlogunit
  • Loading branch information
jedwards4b authored Dec 5, 2022
2 parents 7c0c445 + e0bf6bf commit 737b932
Show file tree
Hide file tree
Showing 2 changed files with 56 additions and 39 deletions.
7 changes: 4 additions & 3 deletions src/shr_file_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -884,11 +884,11 @@ END SUBROUTINE shr_file_setIO
!BOP ===========================================================================
!
! !IROUTINE: shr_file_setLogUnit -- Set the Log I/O Unit number
!
! Depricated - use shr_log_setLogUnit
! !INTERFACE: ------------------------------------------------------------------

SUBROUTINE shr_file_setLogUnit(unit)

use shr_log_mod, only: shr_log_setLogUnit
implicit none

! !INPUT/OUTPUT PARAMETERS:
Expand All @@ -909,8 +909,9 @@ SUBROUTINE shr_file_setLogUnit(unit)
write(s_logunit,*) subName,': reset log unit number from/to ',s_logunit, unit
write( unit,*) subName,': reset log unit number from/to ',s_logunit, unit
endif
print *,__FILE__,__LINE__,'This routine is depricated - use shr_log_setLogUnit instead'
#endif
s_logunit = unit
call shr_log_setLogUnit(unit)

END SUBROUTINE shr_file_setLogUnit

Expand Down
88 changes: 52 additions & 36 deletions src/shr_log_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ module shr_log_mod

! !USES:

use shr_kind_mod
use shr_kind_mod, only: shr_kind_in, shr_kind_cx
use shr_strconvert_mod, only: toString

use, intrinsic :: iso_fortran_env, only: output_unit
Expand All @@ -29,6 +29,8 @@ module shr_log_mod

public :: shr_log_errMsg
public :: shr_log_OOBMsg
public :: shr_log_setLogUnit
public :: shr_log_getLogUnit

! !PUBLIC DATA MEMBERS:

Expand Down Expand Up @@ -65,40 +67,54 @@ module shr_log_mod
!
! !INTERFACE: ------------------------------------------------------------------

pure function shr_log_errMsg(file, line)

! !INPUT/OUTPUT PARAMETERS:

character(len=SHR_KIND_CX) :: shr_log_errMsg
character(len=*), intent(in) :: file
integer , intent(in) :: line

!EOP

shr_log_errMsg = 'ERROR in '//trim(file)//' at line '//toString(line)

end function shr_log_errMsg

! Create a message for an out of bounds error.
pure function shr_log_OOBMsg(operation, bounds, idx) result(OOBMsg)

! A name for the operation being attempted when the bounds error
! occurred. A string containing the subroutine name is ideal, but more
! generic descriptions such as "read", "modify", or "insert" could be used.
character(len=*), intent(in) :: operation

! Upper and lower bounds allowed for the operation.
integer, intent(in) :: bounds(2)

! Index at which access was attempted.
integer, intent(in) :: idx

! Output message
character(len=:), allocatable :: OOBMsg

allocate(OOBMsg, source=(operation//": "//toString(idx)//" not in range ["//&
toString(bounds(1))//", "//toString(bounds(2))//"]."))

end function shr_log_OOBMsg
pure function shr_log_errMsg(file, line)

! !INPUT/OUTPUT PARAMETERS:

character(len=SHR_KIND_CX) :: shr_log_errMsg
character(len=*), intent(in) :: file
integer , intent(in) :: line

!EOP

shr_log_errMsg = 'ERROR in '//trim(file)//' at line '//toString(line)

end function shr_log_errMsg

! Create a message for an out of bounds error.
pure function shr_log_OOBMsg(operation, bounds, idx) result(OOBMsg)

! A name for the operation being attempted when the bounds error
! occurred. A string containing the subroutine name is ideal, but more
! generic descriptions such as "read", "modify", or "insert" could be used.
character(len=*), intent(in) :: operation

! Upper and lower bounds allowed for the operation.
integer, intent(in) :: bounds(2)

! Index at which access was attempted.
integer, intent(in) :: idx

! Output message
character(len=:), allocatable :: OOBMsg

allocate(OOBMsg, source=(operation//": "//toString(idx)//" not in range ["//&
toString(bounds(1))//", "//toString(bounds(2))//"]."))

end function shr_log_OOBMsg

subroutine shr_log_setLogUnit(unit)
integer, intent(in) :: unit

shr_log_unit = unit

end subroutine shr_log_setLogUnit

subroutine shr_log_getLogUnit(unit)
integer, intent(out) :: unit

unit = shr_log_unit

end subroutine shr_log_getLogUnit

end module shr_log_mod

0 comments on commit 737b932

Please sign in to comment.