Skip to content

Commit

Permalink
Merge branch 'dev/gfdl' into brankart
Browse files Browse the repository at this point in the history
  • Loading branch information
adcroft authored Sep 1, 2020
2 parents 54cf60d + fc59c04 commit 63a2e2a
Show file tree
Hide file tree
Showing 5 changed files with 88 additions and 41 deletions.
4 changes: 2 additions & 2 deletions .testing/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -293,9 +293,9 @@ $(eval $(call CMP_RULE,regression,symmetric target))
|| !( \
mkdir -p results/$*; \
(diff $$^ | tee results/$*/chksum_diag.restart.diff | head) ; \
echo -e "${FAIL}: Diagnostics $*.restart.diag have changed." \
echo -e "${FAIL}: Solutions $*.restart have changed." \
)
@echo -e "${PASS}: Diagnostics $*.restart.diag agree."
@echo -e "${PASS}: Solutions $*.restart agree."

# TODO: chksum_diag parsing of restart files

Expand Down
5 changes: 3 additions & 2 deletions config_src/ice_solo_driver/ice_shelf_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -353,7 +353,7 @@ program Shelf_main
call close_file(unit)
endif

if (cpu_steps > 0) call write_cputime(Time, 0, nmax, write_CPU_CSp)
if (cpu_steps > 0) call write_cputime(Time, 0, write_CPU_CSp)

if (((.not.BTEST(Restart_control,1)) .and. (.not.BTEST(Restart_control,0))) &
.or. (Restart_control < 0)) permit_incr_restart = .false.
Expand Down Expand Up @@ -403,7 +403,7 @@ program Shelf_main
Time = Master_Time

if (cpu_steps > 0) then ; if (MOD(ns, cpu_steps) == 0) then
call write_cputime(Time, ns, nmax, write_CPU_CSp)
call write_cputime(Time, ns, write_CPU_CSp, nmax)
endif ; endif

! See if it is time to write out a restart file - timestamped or not.
Expand Down Expand Up @@ -459,6 +459,7 @@ program Shelf_main

call callTree_waypoint("End Shelf_main")
call diag_mediator_end(Time, diag, end_diag_manager=.true.)
if (cpu_steps > 0) call write_cputime(Time, ns-1, write_CPU_CSp, call_end=.true.)
call cpu_clock_end(termClock)

call io_infra_end ; call MOM_infra_end
Expand Down
5 changes: 3 additions & 2 deletions config_src/solo_driver/MOM_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -447,7 +447,7 @@ program MOM_main
call close_file(unit)
endif

if (cpu_steps > 0) call write_cputime(Time, 0, nmax, write_CPU_CSp)
if (cpu_steps > 0) call write_cputime(Time, 0, write_CPU_CSp)

if (((.not.BTEST(Restart_control,1)) .and. (.not.BTEST(Restart_control,0))) &
.or. (Restart_control < 0)) permit_incr_restart = .false.
Expand Down Expand Up @@ -564,7 +564,7 @@ program MOM_main
Time = Master_Time

if (cpu_steps > 0) then ; if (MOD(ns, cpu_steps) == 0) then
call write_cputime(Time, ns+ntstep-1, nmax, write_CPU_CSp)
call write_cputime(Time, ns+ntstep-1, write_CPU_CSp, nmax)
endif ; endif

call mech_forcing_diags(forces, dt_forcing, grid, Time, diag, surface_forcing_CSp%handles)
Expand Down Expand Up @@ -652,6 +652,7 @@ program MOM_main

call callTree_waypoint("End MOM_main")
call diag_mediator_end(Time, diag, end_diag_manager=.true.)
if (cpu_steps > 0) call write_cputime(Time, ns-1, write_CPU_CSp, call_end=.true.)
call cpu_clock_end(termClock)

call io_infra_end ; call MOM_infra_end
Expand Down
64 changes: 42 additions & 22 deletions src/framework/MOM_domains.F90
Original file line number Diff line number Diff line change
Expand Up @@ -26,11 +26,12 @@ module MOM_domains
use mpp_domains_mod, only : mpp_group_update_initialized
use mpp_domains_mod, only : mpp_start_group_update, mpp_complete_group_update
use mpp_domains_mod, only : compute_block_extent => mpp_compute_block_extent
use mpp_parameter_mod, only : AGRID, BGRID_NE, CGRID_NE, SCALAR_PAIR, BITWISE_EXACT_SUM, CORNER
use mpp_parameter_mod, only : To_East => WUPDATE, To_West => EUPDATE, Omit_Corners => EDGEUPDATE
use mpp_parameter_mod, only : To_North => SUPDATE, To_South => NUPDATE, CENTER
use fms_io_mod, only : file_exist, parse_mask_table
use fms_affinity_mod, only : fms_affinity_init, fms_affinity_set,fms_affinity_get
use mpp_domains_mod, only : AGRID, BGRID_NE, CGRID_NE, SCALAR_PAIR, BITWISE_EXACT_SUM
use mpp_domains_mod, only : To_East => WUPDATE, To_West => EUPDATE, Omit_Corners => EDGEUPDATE
use mpp_domains_mod, only : To_North => SUPDATE, To_South => NUPDATE
use mpp_domains_mod, only : CENTER, CORNER, NORTH_FACE => NORTH, EAST_FACE => EAST
use fms_io_mod, only : file_exist, parse_mask_table
use fms_affinity_mod, only : fms_affinity_init, fms_affinity_set, fms_affinity_get

implicit none ; private

Expand All @@ -40,7 +41,8 @@ module MOM_domains
public :: pass_var_start, pass_var_complete, fill_symmetric_edges, broadcast
public :: pass_vector_start, pass_vector_complete
public :: global_field_sum, sum_across_PEs, min_across_PEs, max_across_PEs
public :: AGRID, BGRID_NE, CGRID_NE, SCALAR_PAIR, BITWISE_EXACT_SUM, CORNER, CENTER
public :: AGRID, BGRID_NE, CGRID_NE, SCALAR_PAIR, BITWISE_EXACT_SUM
public :: CORNER, CENTER, NORTH_FACE, EAST_FACE
public :: To_East, To_West, To_North, To_South, To_All, Omit_Corners
public :: create_group_pass, do_group_pass, group_pass_type
public :: start_group_pass, complete_group_pass
Expand Down Expand Up @@ -153,8 +155,8 @@ subroutine pass_var_3d(array, MOM_dom, sideflag, complete, position, halo, &
!! progress resumes. Omitting complete is the
!! same as setting complete to .true.
integer, optional, intent(in) :: position !< An optional argument indicating the position.
!! This is usally CORNER, but is CENTER by
!! default.
!! This is CENTER by default and is often CORNER,
!! but could also be EAST_FACE or NORTH_FACE.
integer, optional, intent(in) :: halo !< The size of the halo to update - the full
!! halo by default.
integer, optional, intent(in) :: clock !< The handle for a cpu time clock that should be
Expand Down Expand Up @@ -198,8 +200,8 @@ subroutine pass_var_2d(array, MOM_dom, sideflag, complete, position, halo, inner
!! progress resumes. Omitting complete is the
!! same as setting complete to .true.
integer, optional, intent(in) :: position !< An optional argument indicating the position.
!! This is usally CORNER, but is CENTER
!! by default.
!! This is CENTER by default and is often CORNER,
!! but could also be EAST_FACE or NORTH_FACE.
integer, optional, intent(in) :: halo !< The size of the halo to update - the full halo
!! by default.
integer, optional, intent(in) :: inner_halo !< The size of an inner halo to avoid updating,
Expand Down Expand Up @@ -267,6 +269,24 @@ subroutine pass_var_2d(array, MOM_dom, sideflag, complete, position, halo, inner
elseif (size(array,2) == jed+1) then
jsfs = jsc - j_halo ; jefs = jsc+1 ; jsfn = jec+1 ; jefn = min(jec + 1 + j_halo, jed+1)
else ; call MOM_error(FATAL, "pass_var_2d: wrong j-size for CORNER array.") ; endif
elseif (pos == NORTH_FACE) then
if (size(array,1) == ied) then
isfw = isc - i_halo ; iefw = isc ; isfe = iec ; iefe = iec + i_halo
else ; call MOM_error(FATAL, "pass_var_2d: wrong i-size for NORTH_FACE array.") ; endif
if (size(array,2) == jed) then
jsfs = max(jsc - (j_halo+1), 1) ; jefs = jsc ; jsfn = jec ; jefn = jec + j_halo
elseif (size(array,2) == jed+1) then
jsfs = jsc - j_halo ; jefs = jsc+1 ; jsfn = jec+1 ; jefn = min(jec + 1 + j_halo, jed+1)
else ; call MOM_error(FATAL, "pass_var_2d: wrong j-size for NORTH_FACE array.") ; endif
elseif (pos == EAST_FACE) then
if (size(array,1) == ied) then
isfw = max(isc - (i_halo+1), 1) ; iefw = isc ; isfe = iec ; iefe = iec + i_halo
elseif (size(array,1) == ied+1) then
isfw = isc - i_halo ; iefw = isc+1 ; isfe = iec+1 ; iefe = min(iec + 1 + i_halo, ied+1)
else ; call MOM_error(FATAL, "pass_var_2d: wrong i-size for EAST_FACE array.") ; endif
if (size(array,2) == jed) then
isfw = isc - i_halo ; iefw = isc ; isfe = iec ; iefe = iec + i_halo
else ; call MOM_error(FATAL, "pass_var_2d: wrong j-size for EAST_FACE array.") ; endif
else
call MOM_error(FATAL, "pass_var_2d: Unrecognized position")
endif
Expand Down Expand Up @@ -297,8 +317,8 @@ function pass_var_start_2d(array, MOM_dom, sideflag, position, complete, halo, &
!! TO_NORTH, and TO_SOUTH. For example, TO_EAST sends the data to the processor to the east,
!! so the halos on the western side are filled. TO_ALL is the default if sideflag is omitted.
integer, optional, intent(in) :: position !< An optional argument indicating the position.
!! This is usally CORNER, but is CENTER
!! by default.
!! This is CENTER by default and is often CORNER,
!! but could also be EAST_FACE or NORTH_FACE.
logical, optional, intent(in) :: complete !< An optional argument indicating whether the
!! halo updates should be completed before
!! progress resumes. Omitting complete is the
Expand Down Expand Up @@ -342,8 +362,8 @@ function pass_var_start_3d(array, MOM_dom, sideflag, position, complete, halo, &
!! TO_NORTH, and TO_SOUTH. For example, TO_EAST sends the data to the processor to the east,
!! so the halos on the western side are filled. TO_ALL is the default if sideflag is omitted.
integer, optional, intent(in) :: position !< An optional argument indicating the position.
!! This is usally CORNER, but is CENTER
!! by default.
!! This is CENTER by default and is often CORNER,
!! but could also be EAST_FACE or NORTH_FACE.
logical, optional, intent(in) :: complete !< An optional argument indicating whether the
!! halo updates should be completed before
!! progress resumes. Omitting complete is the
Expand Down Expand Up @@ -390,8 +410,8 @@ subroutine pass_var_complete_2d(id_update, array, MOM_dom, sideflag, position, h
!! TO_NORTH, and TO_SOUTH. For example, TO_EAST sends the data to the processor to the east,
!! so the halos on the western side are filled. TO_ALL is the default if sideflag is omitted.
integer, optional, intent(in) :: position !< An optional argument indicating the position.
!! This is usally CORNER, but is CENTER
!! by default.
!! This is CENTER by default and is often CORNER,
!! but could also be EAST_FACE or NORTH_FACE.
integer, optional, intent(in) :: halo !< The size of the halo to update - the full
!! halo by default.
integer, optional, intent(in) :: clock !< The handle for a cpu time clock that should be
Expand Down Expand Up @@ -433,8 +453,8 @@ subroutine pass_var_complete_3d(id_update, array, MOM_dom, sideflag, position, h
!! TO_NORTH, and TO_SOUTH. For example, TO_EAST sends the data to the processor to the east,
!! so the halos on the western side are filled. TO_ALL is the default if sideflag is omitted.
integer, optional, intent(in) :: position !< An optional argument indicating the position.
!! This is usally CORNER, but is CENTER
!! by default.
!! This is CENTER by default and is often CORNER,
!! but could also be EAST_FACE or NORTH_FACE.
integer, optional, intent(in) :: halo !< The size of the halo to update - the full
!! halo by default.
integer, optional, intent(in) :: clock !< The handle for a cpu time clock that should be
Expand Down Expand Up @@ -901,8 +921,8 @@ subroutine create_var_group_pass_2d(group, array, MOM_dom, sideflag, position, &
!! TO_NORTH, and TO_SOUTH. For example, TO_EAST sends the data to the processor to the east,
!! so the halos on the western side are filled. TO_ALL is the default if sideflag is omitted.
integer, optional, intent(in) :: position !< An optional argument indicating the position.
!! This is usally CORNER, but is CENTER
!! by default.
!! This is CENTER by default and is often CORNER,
!! but could also be EAST_FACE or NORTH_FACE.
integer, optional, intent(in) :: halo !< The size of the halo to update - the full
!! halo by default.
integer, optional, intent(in) :: clock !< The handle for a cpu time clock that should be
Expand Down Expand Up @@ -946,8 +966,8 @@ subroutine create_var_group_pass_3d(group, array, MOM_dom, sideflag, position, h
!! TO_NORTH, and TO_SOUTH. For example, TO_EAST sends the data to the processor to the east,
!! so the halos on the western side are filled. TO_ALL is the default if sideflag is omitted.
integer, optional, intent(in) :: position !< An optional argument indicating the position.
!! This is usally CORNER, but is CENTER
!! by default.
!! This is CENTER by default and is often CORNER,
!! but could also be EAST_FACE or NORTH_FACE.
integer, optional, intent(in) :: halo !< The size of the halo to update - the full
!! halo by default.
integer, optional, intent(in) :: clock !< The handle for a cpu time clock that should be
Expand Down
51 changes: 38 additions & 13 deletions src/framework/MOM_write_cputime.F90
Original file line number Diff line number Diff line change
Expand Up @@ -3,15 +3,15 @@ module MOM_write_cputime

! This file is part of MOM6. See LICENSE.md for the license.

use MOM_coms, only : sum_across_PEs, pe_here, num_pes
use MOM_coms, only : sum_across_PEs, num_pes
use MOM_error_handler, only : MOM_error, MOM_mesg, FATAL, is_root_pe
use MOM_io, only : open_file, APPEND_FILE, ASCII_FILE, WRITEONLY_FILE
use MOM_io, only : open_file, close_file, APPEND_FILE, ASCII_FILE, WRITEONLY_FILE
use MOM_file_parser, only : get_param, log_param, log_version, param_file_type
use MOM_time_manager, only : time_type, get_time, operator(>)

implicit none ; private

public write_cputime, MOM_write_cputime_init, write_cputime_start_clock
public write_cputime, MOM_write_cputime_init, MOM_write_cputime_end, write_cputime_start_clock

!-----------------------------------------------------------------------

Expand All @@ -33,7 +33,7 @@ module MOM_write_cputime
real :: cputime2 = 0.0 !< The accumulated cpu time.
integer :: previous_calls = 0 !< The number of times write_CPUtime has been called.
integer :: prev_n = 0 !< The value of n from the last call.
integer :: fileCPU_ascii !< The unit number of the CPU time file.
integer :: fileCPU_ascii= -1 !< The unit number of the CPU time file.
character(len=200) :: CPUfile !< The name of the CPU time file.
end type write_cputime_CS

Expand Down Expand Up @@ -101,16 +101,35 @@ subroutine MOM_write_cputime_init(param_file, directory, Input_start_time, CS)

end subroutine MOM_write_cputime_init

!> This subroutine assesses how much CPU time the model has taken and determines how long the model
!! should be run before it saves a restart file and stops itself.
subroutine write_cputime(day, n, nmax, CS)
type(time_type), intent(inout) :: day !< The current model time.
integer, intent(in) :: n !< The time step number of the current execution.
integer, intent(inout) :: nmax !< The number of iterations after which to stop so
!! that the simulation will not run out of CPU time.
type(write_cputime_CS), pointer :: CS !< The control structure set up by a previous
!> Close the MOM_write_cputime module.
subroutine MOM_write_cputime_end(CS)
type(write_cputime_CS), pointer :: CS !< The control structure set up by a previous
!! call to MOM_write_cputime_init.

if (.not.associated(CS)) return

! Flush and close the output files.
if (is_root_pe() .and. CS%fileCPU_ascii > 0) then
call flush(CS%fileCPU_ascii)
call close_file(CS%fileCPU_ascii)
endif

deallocate(CS)

end subroutine MOM_write_cputime_end

!> This subroutine assesses how much CPU time the model has taken and determines how long the model
!! should be run before it saves a restart file and stops itself. Optionally this may also be used
!! to trigger this module's end routine.
subroutine write_cputime(day, n, CS, nmax, call_end)
type(time_type), intent(inout) :: day !< The current model time.
integer, intent(in) :: n !< The time step number of the current execution.
type(write_cputime_CS), pointer :: CS !< The control structure set up by a previous
!! call to MOM_write_cputime_init.
integer, optional, intent(inout) :: nmax !< The number of iterations after which to stop so
!! that the simulation will not run out of CPU time.
logical, optional, intent(in) :: call_end !< If true, also call MOM_write_cputime_end.

! Local variables
real :: d_cputime ! The change in CPU time since the last call
! this subroutine.
Expand Down Expand Up @@ -145,7 +164,7 @@ subroutine write_cputime(day, n, nmax, CS)
((CS%dn_dcpu_min*d_cputime < (n - CS%prev_n)) .or. &
(CS%dn_dcpu_min < 0.0))) &
CS%dn_dcpu_min = (n - CS%prev_n) / d_cputime
if (CS%dn_dcpu_min >= 0.0) then
if (present(nmax) .and. (CS%dn_dcpu_min >= 0.0)) then
! Have the model stop itself after 95% of the CPU time has been used.
nmax = n + INT( CS%dn_dcpu_min * &
(0.95*CS%maxcpu * REAL(num_pes())*CLOCKS_PER_SEC - &
Expand Down Expand Up @@ -180,9 +199,15 @@ subroutine write_cputime(day, n, nmax, CS)
write(CS%fileCPU_ascii,'(F12.3,", "I11,", ", F12.3,", ", F12.3)') &
reday, n, (CS%cputime2 / real(CLOCKS_PER_SEC)), &
d_cputime / real(CLOCKS_PER_SEC)

call flush(CS%fileCPU_ascii)
endif
CS%previous_calls = CS%previous_calls + 1

if (present(call_end)) then
if (call_end) call MOM_write_cputime_end(CS)
endif

end subroutine write_cputime

!> \namespace mom_write_cputime
Expand Down

0 comments on commit 63a2e2a

Please sign in to comment.