From b898297e0ad5284f07c22f213120157787fc4a0a Mon Sep 17 00:00:00 2001 From: Robert Hallberg Date: Tue, 7 Nov 2023 08:48:04 -0500 Subject: [PATCH 01/22] +(*)Add continuity_fluxes & continuity_adjust_vel Added the new public interfaces continuity_fluxes and continuity_adjust_vel to make use of the continuity code without actually updating the layer thicknesses, and made the existing routines zonal_mass_flux and meridional_mass_flux in the continuity_PPM module public. Continuity_fluxes is overloaded to provide either the layer thickness fluxes or the vertically summed barotropic fluxes. As a part of this change, the LB arguments to meridional_mass_flux and zonal_mass_flux were made optional and moved toward the end of the list of arguments. The intent of the ocean_grid_type argument to 11 routines in the continuity_PPM module was changed from inout to in. Missing factors of por_face_area[UV] were also added to merid_face_thickness and zonal_face_thickness when the visc_rem arguments are not present or where OBCs are in use. This could change answers, but it seems very unlikely that any impacted cases are in use yet. Answers are bitwise identical all known cases, but there are 4 new public interfaces, and some bugs were fixed in cases that are not likely in use yet. --- src/core/MOM_continuity.F90 | 192 ++++++++++++++++++++++++++++++-- src/core/MOM_continuity_PPM.F90 | 89 +++++++++------ 2 files changed, 239 insertions(+), 42 deletions(-) diff --git a/src/core/MOM_continuity.F90 b/src/core/MOM_continuity.F90 index 76e1bbc623..7a833ccb5c 100644 --- a/src/core/MOM_continuity.F90 +++ b/src/core/MOM_continuity.F90 @@ -3,8 +3,8 @@ module MOM_continuity ! This file is part of MOM6. See LICENSE.md for the license. -use MOM_continuity_PPM, only : continuity_PPM, continuity_PPM_init -use MOM_continuity_PPM, only : continuity_PPM_stencil +use MOM_continuity_PPM, only : continuity_PPM, zonal_mass_flux, meridional_mass_flux +use MOM_continuity_PPM, only : continuity_PPM_stencil, continuity_PPM_init use MOM_continuity_PPM, only : continuity_PPM_CS use MOM_diag_mediator, only : time_type, diag_ctrl use MOM_error_handler, only : MOM_error, MOM_mesg, FATAL, WARNING, is_root_pe @@ -20,7 +20,7 @@ module MOM_continuity #include -public continuity, continuity_init, continuity_stencil +public continuity, continuity_fluxes, continuity_adjust_vel, continuity_init, continuity_stencil !> Control structure for mom_continuity type, public :: continuity_CS ; private @@ -35,10 +35,16 @@ module MOM_continuity integer, parameter :: PPM_SCHEME = 1 !< Enumerated constant to select PPM character(len=20), parameter :: PPM_STRING = "PPM" !< String to select PPM +!> Finds the thickness fluxes from the continuity solver or their vertical sum without +!! actually updating the layer thicknesses. +interface continuity_fluxes + module procedure continuity_3d_fluxes, continuity_2d_fluxes +end interface continuity_fluxes + contains -!> Time steps the layer thicknesses, using a monotonically limited, directionally split PPM scheme, -!! based on Lin (1994). +!> Time steps the layer thicknesses, using a monotonically or positive-definite limited, directionally +!! split PPM scheme, based on Lin (1994). subroutine continuity(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhbt, vhbt, & visc_rem_u, visc_rem_v, u_cor, v_cor, BT_cont) type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure. @@ -63,21 +69,23 @@ subroutine continuity(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhbt, v type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. type(porous_barrier_type), intent(in) :: pbv !< porous barrier fractional cell metrics real, dimension(SZIB_(G),SZJ_(G)), & - optional, intent(in) :: uhbt !< The vertically summed volume - !! flux through zonal faces [H L2 T-1 ~> m3 s-1 or kg s-1]. + optional, intent(in) :: uhbt !< The vertically summed volume flux through + !! zonal faces [H L2 T-1 ~> m3 s-1 or kg s-1]. real, dimension(SZI_(G),SZJB_(G)), & - optional, intent(in) :: vhbt !< The vertically summed volume - !! flux through meridional faces [H L2 T-1 ~> m3 s-1 or kg s-1]. + optional, intent(in) :: vhbt !< The vertically summed volume flux through + !! meridional faces [H L2 T-1 ~> m3 s-1 or kg s-1]. real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & optional, intent(in) :: visc_rem_u !< Both the fraction of !! zonal momentum that remains after a time-step of viscosity, and the fraction of a time-step's !! worth of a barotropic acceleration that a layer experiences after viscosity is applied [nondim]. - !! Non-dimensional between 0 (at the bottom) and 1 (far above the bottom). + !! Non-dimensional between 0 (at the bottom) and 1 (far above the bottom). When this column is + !! under an ice shelf, this can also go to 0 at the top due to the no-slip boundary condition there. real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & optional, intent(in) :: visc_rem_v !< Both the fraction of !! meridional momentum that remains after a time-step of viscosity, and the fraction of a time-step's !! worth of a barotropic acceleration that a layer experiences after viscosity is applied [nondim]. - !! Non-dimensional between 0 (at the bottom) and 1 (far above the bottom). + !! Non-dimensional between 0 (at the bottom) and 1 (far above the bottom). When this column is + !! under an ice shelf, this can also go to 0 at the top due to the no-slip boundary condition there. real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & optional, intent(out) :: u_cor !< The zonal velocities that !! give uhbt as the depth-integrated transport [L T-1 ~> m s-1]. @@ -104,6 +112,168 @@ subroutine continuity(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhbt, v end subroutine continuity +!> Finds the thickness fluxes from the continuity solver without actually updating the +!! layer thicknesses. Because the fluxes in the two directions are calculated based on the +!! input thicknesses, which are not updated between the direcitons, the fluxes returned here +!! are not the same as those that would be returned by a call to continuity. +subroutine continuity_3d_fluxes(u, v, h, uh, vh, dt, G, GV, US, CS, OBC, pbv) + type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure. + type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure. + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & + intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]. + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & + intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + intent(in) :: h !< Layer thickness [H ~> m or kg m-2]. + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & + intent(out) :: uh !< Thickness fluxes through zonal faces, + !! u*h*dy [H L2 T-1 ~> m3 s-1 or kg s-1]. + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & + intent(out) :: vh !< Thickness fluxes through meridional faces, + !! v*h*dx [H L2 T-1 ~> m3 s-1 or kg s-1]. + real, intent(in) :: dt !< Time increment [T ~> s]. + type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type + type(continuity_CS), intent(in) :: CS !< Control structure for mom_continuity. + type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. + type(porous_barrier_type), intent(in) :: pbv !< porous barrier fractional cell metrics + + if (CS%continuity_scheme == PPM_SCHEME) then + call zonal_mass_flux(u, h, uh, dt, G, GV, US, CS%PPM, OBC, pbv%por_face_areaU) + + call meridional_mass_flux(v, h, vh, dt, G, GV, US, CS%PPM, OBC, pbv%por_face_areaV) + else + call MOM_error(FATAL, "continuity: Unrecognized value of continuity_scheme") + endif + +end subroutine continuity_3d_fluxes + +!> Find the vertical sum of the thickness fluxes from the continuity solver without actually +!! updating the layer thicknesses. Because the fluxes in the two directions are calculated +!! based on the input thicknesses, which are not updated between the directions, the fluxes +!! returned here are not the same as those that would be returned by a call to continuity. +subroutine continuity_2d_fluxes(u, v, h, uhbt, vhbt, dt, G, GV, US, CS, OBC, pbv) + type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure. + type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure. + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & + intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]. + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & + intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + intent(in) :: h !< Layer thickness [H ~> m or kg m-2]. + real, dimension(SZIB_(G),SZJ_(G)), & + intent(out) :: uhbt !< Vertically summed thickness flux through + !! zonal faces [H L2 T-1 ~> m3 s-1 or kg s-1]. + real, dimension(SZI_(G),SZJB_(G)), & + intent(out) :: vhbt !< Vertically summed thickness flux through + !! meridional faces [H L2 T-1 ~> m3 s-1 or kg s-1]. + real, intent(in) :: dt !< Time increment [T ~> s]. + type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type + type(continuity_CS), intent(in) :: CS !< Control structure for mom_continuity. + type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. + type(porous_barrier_type), intent(in) :: pbv !< porous barrier fractional cell metrics + + ! Local variables + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: uh ! Thickness fluxes through zonal faces, + ! u*h*dy [H L2 T-1 ~> m3 s-1 or kg s-1]. + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: vh ! Thickness fluxes through meridional faces, + ! v*h*dx [H L2 T-1 ~> m3 s-1 or kg s-1]. + integer :: i, j, k + + uh(:,:,:) = 0.0 + vh(:,:,:) = 0.0 + + if (CS%continuity_scheme == PPM_SCHEME) then + call zonal_mass_flux(u, h, uh, dt, G, GV, US, CS%PPM, OBC, pbv%por_face_areaU) + + call meridional_mass_flux(v, h, vh, dt, G, GV, US, CS%PPM, OBC, pbv%por_face_areaV) + else + call MOM_error(FATAL, "continuity: Unrecognized value of continuity_scheme") + endif + + uhbt(:,:) = 0.0 + vhbt(:,:) = 0.0 + + do k=1,GV%ke ; do j=G%jsc,G%jec ; do I=G%isc-1,G%iec + uhbt(I,j) = uhbt(I,j) + uh(I,j,k) + enddo ; enddo ; enddo + + do k=1,GV%ke ; do J=G%jsc-1,G%jec ; do i=G%isc,G%iec + vhbt(I,j) = vhbt(I,j) + vh(I,j,k) + enddo ; enddo ; enddo + +end subroutine continuity_2d_fluxes + + +!> Correct the velocities to give the specified depth-integrated transports by applying a +!! barotropic acceleration (subject to viscous drag) to the velocities. +subroutine continuity_adjust_vel(u, v, h, dt, G, GV, US, CS, OBC, pbv, uhbt, vhbt, visc_rem_u, visc_rem_v) + type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure. + type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure. + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & + intent(inout) :: u !< Zonal velocity, which will be adjusted to + !! give uhbt as the depth-integrated + !! transport [L T-1 ~> m s-1]. + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & + intent(inout) :: v !< Meridional velocity, which will be adjusted + !! to give vhbt as the depth-integrated + !! transport [L T-1 ~> m s-1]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + intent(in) :: h !< Layer thickness [H ~> m or kg m-2]. + real, intent(in) :: dt !< Time increment [T ~> s]. + type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type + type(continuity_CS), intent(in) :: CS !< Control structure for mom_continuity. + type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. + type(porous_barrier_type), intent(in) :: pbv !< porous barrier fractional cell metrics + real, dimension(SZIB_(G),SZJ_(G)), & + intent(in) :: uhbt !< The vertically summed thickness flux through + !! zonal faces [H L2 T-1 ~> m3 s-1 or kg s-1]. + real, dimension(SZI_(G),SZJB_(G)), & + intent(in) :: vhbt !< The vertically summed thickness flux through + !! meridional faces [H L2 T-1 ~> m3 s-1 or kg s-1]. + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & + optional, intent(in) :: visc_rem_u !< Both the fraction of the zonal momentum + !! that remains after a time-step of viscosity, and + !! the fraction of a time-step's worth of a barotropic + !! acceleration that a layer experiences after viscosity + !! is applied [nondim]. This goes between 0 (at the + !! bottom) and 1 (far above the bottom). When this + !! column is under an ice shelf, this also goes to 0 + !! at the top due to the no-slip boundary condition there. + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & + optional, intent(in) :: visc_rem_v !< Both the fraction of the meridional momentum + !! that remains after a time-step of viscosity, and + !! the fraction of a time-step's worth of a barotropic + !! acceleration that a layer experiences after viscosity + !! is applied [nondim]. This goes between 0 (at the + !! bottom) and 1 (far above the bottom). When this + !! column is under an ice shelf, this also goes to 0 + !! at the top due to the no-slip boundary condition there. + + ! Local variables + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: u_in !< Input zonal velocity [L T-1 ~> m s-1] + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: v_in !< Input meridional velocity [L T-1 ~> m s-1] + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: uh !< Volume flux through zonal faces = + !! u*h*dy [H L2 T-1 ~> m3 s-1 or kg s-1]. + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: vh !< Volume flux through meridional faces = + !! v*h*dx [H L2 T-1 ~> m3 s-1 or kg s-1]. + + ! It might not be necessary to separate the input velocity array from the adjusted velocities, + ! but it seems safer to do so, even if it might be less efficient. + u_in(:,:,:) = u(:,:,:) + v_in(:,:,:) = v(:,:,:) + + if (CS%continuity_scheme == PPM_SCHEME) then + call zonal_mass_flux(u_in, h, uh, dt, G, GV, US, CS%PPM, OBC, pbv%por_face_areaU, & + uhbt=uhbt, visc_rem_u=visc_rem_u, u_cor=u) + + call meridional_mass_flux(v_in, h, vh, dt, G, GV, US, CS%PPM, OBC, pbv%por_face_areaV, & + vhbt=vhbt, visc_rem_v=visc_rem_v, v_cor=v) + else + call MOM_error(FATAL, "continuity: Unrecognized value of continuity_scheme") + endif + +end subroutine continuity_adjust_vel + !> Initializes continuity_cs subroutine continuity_init(Time, G, GV, US, param_file, diag, CS) type(time_type), target, intent(in) :: Time !< Current model time. diff --git a/src/core/MOM_continuity_PPM.F90 b/src/core/MOM_continuity_PPM.F90 index 73c6503242..7f96e675cd 100644 --- a/src/core/MOM_continuity_PPM.F90 +++ b/src/core/MOM_continuity_PPM.F90 @@ -19,6 +19,7 @@ module MOM_continuity_PPM #include public continuity_PPM, continuity_PPM_init, continuity_PPM_stencil +public zonal_mass_flux, meridional_mass_flux !>@{ CPU time clock IDs integer :: id_clock_update, id_clock_correct @@ -72,7 +73,7 @@ module MOM_continuity_PPM !! based on Lin (1994). subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhbt, vhbt, & visc_rem_u, visc_rem_v, u_cor, v_cor, BT_cont) - type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure. + type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure. type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure. real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]. @@ -147,8 +148,8 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhb ! First, advect zonally. LB%ish = G%isc ; LB%ieh = G%iec LB%jsh = G%jsc-stencil ; LB%jeh = G%jec+stencil - call zonal_mass_flux(u, hin, uh, dt, G, GV, US, CS, LB, OBC, & - pbv%por_face_areaU, uhbt, visc_rem_u, u_cor, BT_cont) + call zonal_mass_flux(u, hin, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU, & + LB, uhbt, visc_rem_u, u_cor, BT_cont) call cpu_clock_begin(id_clock_update) !$OMP parallel do default(shared) @@ -163,8 +164,8 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhb ! Now advect meridionally, using the updated thicknesses to determine ! the fluxes. - call meridional_mass_flux(v, h, vh, dt, G, GV, US, CS, LB, OBC, & - pbv%por_face_areaV, vhbt, visc_rem_v, v_cor, BT_cont) + call meridional_mass_flux(v, h, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV, & + LB, vhbt, visc_rem_v, v_cor, BT_cont) call cpu_clock_begin(id_clock_update) !$OMP parallel do default(shared) @@ -180,8 +181,8 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhb LB%ish = G%isc-stencil ; LB%ieh = G%iec+stencil LB%jsh = G%jsc ; LB%jeh = G%jec - call meridional_mass_flux(v, hin, vh, dt, G, GV, US, CS, LB, OBC, & - pbv%por_face_areaV, vhbt, visc_rem_v, v_cor, BT_cont) + call meridional_mass_flux(v, hin, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV, & + LB, vhbt, visc_rem_v, v_cor, BT_cont) call cpu_clock_begin(id_clock_update) !$OMP parallel do default(shared) @@ -193,8 +194,8 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhb ! Now advect zonally, using the updated thicknesses to determine ! the fluxes. LB%ish = G%isc ; LB%ieh = G%iec ; LB%jsh = G%jsc ; LB%jeh = G%jec - call zonal_mass_flux(u, h, uh, dt, G, GV, US, CS, LB, OBC, & - pbv%por_face_areaU, uhbt, visc_rem_u, u_cor, BT_cont) + call zonal_mass_flux(u, h, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU, & + LB, uhbt, visc_rem_u, u_cor, BT_cont) call cpu_clock_begin(id_clock_update) !$OMP parallel do default(shared) @@ -210,9 +211,9 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhb end subroutine continuity_PPM !> Calculates the mass or volume fluxes through the zonal faces, and other related quantities. -subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, LB, OBC, por_face_areaU, uhbt, & - visc_rem_u, u_cor, BT_cont) - type(ocean_grid_type), intent(inout) :: G !< Ocean's grid structure. +subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, & + LB_in, uhbt, visc_rem_u, u_cor, BT_cont) + type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]. @@ -224,10 +225,11 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, LB, OBC, por_face_are real, intent(in) :: dt !< Time increment [T ~> s]. type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type type(continuity_PPM_CS), intent(in) :: CS !< This module's control structure. - type(loop_bounds_type), intent(in) :: LB !< Loop bounds structure. type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. real, dimension(SZIB_(G), SZJ_(G), SZK_(G)), & intent(in) :: por_face_areaU !< fractional open area of U-faces [nondim] + type(loop_bounds_type), & + optional, intent(in) :: LB_in !< Loop bounds structure. real, dimension(SZIB_(G),SZJ_(G)), & optional, intent(in) :: uhbt !< The summed volume flux through zonal faces !! [H L2 T-1 ~> m3 s-1 or kg s-1]. @@ -265,6 +267,7 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, LB, OBC, por_face_are real :: I_dt ! 1.0 / dt [T-1 ~> s-1]. real :: du_lim ! The velocity change that give a relative CFL of 1 [L T-1 ~> m s-1]. real :: dx_E, dx_W ! Effective x-grid spacings to the east and west [L ~> m]. + type(loop_bounds_type) :: LB integer :: i, j, k, ish, ieh, jsh, jeh, n, nz integer :: l_seg logical :: local_specified_BC, use_visc_rem, set_BT_cont, any_simple_OBC @@ -279,6 +282,12 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, LB, OBC, por_face_are local_Flather_OBC = OBC%Flather_u_BCs_exist_globally local_open_BC = OBC%open_u_BCs_exist_globally endif ; endif + + if (present(LB_in)) then + LB = LB_in + else + LB%ish = G%isc ; LB%ieh = G%iec ; LB%jsh = G%jsc ; LB%jeh = G%jec + endif ish = LB%ish ; ieh = LB%ieh ; jsh = LB%jsh ; jeh = LB%jeh ; nz = GV%ke CFL_dt = CS%CFL_limit_adjust / dt @@ -523,7 +532,7 @@ end subroutine zonal_mass_flux !> Evaluates the zonal mass or volume fluxes in a layer. subroutine zonal_flux_layer(u, h, h_L, h_R, uh, duhdu, visc_rem, dt, G, US, j, & ish, ieh, do_I, vol_CFL, por_face_areaU, OBC) - type(ocean_grid_type), intent(inout) :: G !< Ocean's grid structure. + type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. real, dimension(SZIB_(G)), intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]. real, dimension(SZIB_(G)), intent(in) :: visc_rem !< Both the fraction of the !! momentum originally in a layer that remains after a time-step @@ -606,7 +615,7 @@ end subroutine zonal_flux_layer !! back these thicknesses to account for viscosity and fractional open areas. subroutine zonal_face_thickness(u, h, h_L, h_R, h_u, dt, G, GV, US, LB, vol_CFL, & marginal, OBC, por_face_areaU, visc_rem_u) - type(ocean_grid_type), intent(inout) :: G !< Ocean's grid structure. + type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]. real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h !< Layer thickness used to @@ -617,7 +626,7 @@ subroutine zonal_face_thickness(u, h, h_L, h_R, h_u, dt, G, GV, US, LB, vol_CFL, !! reconstruction [H ~> m or kg m-2]. real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), intent(inout) :: h_u !< Effective thickness at zonal faces, !! scaled down to account for the effects of - !! viscoity and the fractional open area + !! viscosity and the fractional open area !! [H ~> m or kg m-2]. real, intent(in) :: dt !< Time increment [T ~> s]. type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type @@ -680,6 +689,11 @@ subroutine zonal_face_thickness(u, h, h_L, h_R, h_u, dt, G, GV, US, LB, vol_CFL, do k=1,nz ; do j=jsh,jeh ; do I=ish-1,ieh h_u(I,j,k) = h_u(I,j,k) * (visc_rem_u(I,j,k) * por_face_areaU(I,j,k)) enddo ; enddo ; enddo + else + !$OMP parallel do default(shared) + do k=1,nz ; do j=jsh,jeh ; do I=ish-1,ieh + h_u(I,j,k) = h_u(I,j,k) * por_face_areaU(I,j,k) + enddo ; enddo ; enddo endif local_open_BC = .false. @@ -695,7 +709,7 @@ subroutine zonal_face_thickness(u, h, h_L, h_R, h_u, dt, G, GV, US, LB, vol_CFL, enddo enddo ; else ; do k=1,nz do j = OBC%segment(n)%HI%jsd, OBC%segment(n)%HI%jed - h_u(I,j,k) = h(i,j,k) + h_u(I,j,k) = h(i,j,k) * por_face_areaU(I,j,k) enddo enddo ; endif else @@ -705,7 +719,7 @@ subroutine zonal_face_thickness(u, h, h_L, h_R, h_u, dt, G, GV, US, LB, vol_CFL, enddo enddo ; else ; do k=1,nz do j = OBC%segment(n)%HI%jsd, OBC%segment(n)%HI%jed - h_u(I,j,k) = h(i+1,j,k) + h_u(I,j,k) = h(i+1,j,k) * por_face_areaU(I,j,k) enddo enddo ; endif endif @@ -721,7 +735,7 @@ subroutine zonal_flux_adjust(u, h_in, h_L, h_R, uhbt, uh_tot_0, duhdu_tot_0, & du, du_max_CFL, du_min_CFL, dt, G, GV, US, CS, visc_rem, & j, ish, ieh, do_I_in, por_face_areaU, uh_3d, OBC) - type(ocean_grid_type), intent(inout) :: G !< Ocean's grid structure. + type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]. real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_in !< Layer thickness used to @@ -873,7 +887,7 @@ end subroutine zonal_flux_adjust subroutine set_zonal_BT_cont(u, h_in, h_L, h_R, BT_cont, uh_tot_0, duhdu_tot_0, & du_max_CFL, du_min_CFL, dt, G, GV, US, CS, visc_rem, & visc_rem_max, j, ish, ieh, do_I, por_face_areaU) - type(ocean_grid_type), intent(inout) :: G !< Ocean's grid structure. + type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]. real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_in !< Layer thickness used to @@ -1036,9 +1050,9 @@ subroutine set_zonal_BT_cont(u, h_in, h_L, h_R, BT_cont, uh_tot_0, duhdu_tot_0, end subroutine set_zonal_BT_cont !> Calculates the mass or volume fluxes through the meridional faces, and other related quantities. -subroutine meridional_mass_flux(v, h_in, vh, dt, G, GV, US, CS, LB, OBC, por_face_areaV, vhbt, & - visc_rem_v, v_cor, BT_cont) - type(ocean_grid_type), intent(inout) :: G !< Ocean's grid structure. +subroutine meridional_mass_flux(v, h_in, vh, dt, G, GV, US, CS, OBC, por_face_areaV, & + LB_in, vhbt, visc_rem_v, v_cor, BT_cont) + type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1] real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_in !< Layer thickness used to @@ -1048,11 +1062,12 @@ subroutine meridional_mass_flux(v, h_in, vh, dt, G, GV, US, CS, LB, OBC, por_fac real, intent(in) :: dt !< Time increment [T ~> s]. type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type type(continuity_PPM_CS), intent(in) :: CS !< This module's control structure.G - type(loop_bounds_type), intent(in) :: LB !< Loop bounds structure. type(ocean_OBC_type), pointer :: OBC !< Open boundary condition type !! specifies whether, where, and what open boundary conditions are used. real, dimension(SZI_(G),SZJB_(G),SZK_(G)), & intent(in) :: por_face_areaV !< fractional open area of V-faces [nondim] + type(loop_bounds_type), & + optional, intent(in) :: LB_in !< Loop bounds structure. real, dimension(SZI_(G),SZJB_(G)), optional, intent(in) :: vhbt !< The summed volume flux through !< meridional faces [H L2 T-1 ~> m3 s-1 or kg s-1]. real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & @@ -1090,6 +1105,7 @@ subroutine meridional_mass_flux(v, h_in, vh, dt, G, GV, US, CS, LB, OBC, por_fac real :: I_dt ! 1.0 / dt [T-1 ~> s-1]. real :: dv_lim ! The velocity change that give a relative CFL of 1 [L T-1 ~> m s-1]. real :: dy_N, dy_S ! Effective y-grid spacings to the north and south [L ~> m]. + type(loop_bounds_type) :: LB integer :: i, j, k, ish, ieh, jsh, jeh, n, nz integer :: l_seg logical :: local_specified_BC, use_visc_rem, set_BT_cont, any_simple_OBC @@ -1104,6 +1120,12 @@ subroutine meridional_mass_flux(v, h_in, vh, dt, G, GV, US, CS, LB, OBC, por_fac local_Flather_OBC = OBC%Flather_v_BCs_exist_globally local_open_BC = OBC%open_v_BCs_exist_globally endif ; endif + + if (present(LB_in)) then + LB = LB_in + else + LB%ish = G%isc ; LB%ieh = G%iec ; LB%jsh = G%jsc ; LB%jeh = G%jec + endif ish = LB%ish ; ieh = LB%ieh ; jsh = LB%jsh ; jeh = LB%jeh ; nz = GV%ke CFL_dt = CS%CFL_limit_adjust / dt @@ -1343,7 +1365,7 @@ end subroutine meridional_mass_flux !> Evaluates the meridional mass or volume fluxes in a layer. subroutine merid_flux_layer(v, h, h_L, h_R, vh, dvhdv, visc_rem, dt, G, US, J, & ish, ieh, do_I, vol_CFL, por_face_areaV, OBC) - type(ocean_grid_type), intent(inout) :: G !< Ocean's grid structure. + type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. real, dimension(SZI_(G)), intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1]. real, dimension(SZI_(G)), intent(in) :: visc_rem !< Both the fraction of the !! momentum originally in a layer that remains after a time-step @@ -1432,7 +1454,7 @@ end subroutine merid_flux_layer !! back these thicknesses to account for viscosity and fractional open areas. subroutine merid_face_thickness(v, h, h_L, h_R, h_v, dt, G, GV, US, LB, vol_CFL, & marginal, OBC, por_face_areaV, visc_rem_v) - type(ocean_grid_type), intent(inout) :: G !< Ocean's grid structure. + type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1]. real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h !< Layer thickness used to calculate fluxes, @@ -1443,7 +1465,7 @@ subroutine merid_face_thickness(v, h, h_L, h_R, h_v, dt, G, GV, US, LB, vol_CFL, !! [H ~> m or kg m-2]. real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(inout) :: h_v !< Effective thickness at meridional faces, !! scaled down to account for the effects of - !! viscoity and the fractional open area + !! viscosity and the fractional open area !! [H ~> m or kg m-2]. real, intent(in) :: dt !< Time increment [T ~> s]. type(loop_bounds_type), intent(in) :: LB !< Loop bounds structure. @@ -1508,6 +1530,11 @@ subroutine merid_face_thickness(v, h, h_L, h_R, h_v, dt, G, GV, US, LB, vol_CFL, do k=1,nz ; do J=jsh-1,jeh ; do i=ish,ieh h_v(i,J,k) = h_v(i,J,k) * (visc_rem_v(i,J,k) * por_face_areaV(i,J,k)) enddo ; enddo ; enddo + else + !$OMP parallel do default(shared) + do k=1,nz ; do J=jsh-1,jeh ; do i=ish,ieh + h_v(i,J,k) = h_v(i,J,k) * por_face_areaV(i,J,k) + enddo ; enddo ; enddo endif local_open_BC = .false. @@ -1523,7 +1550,7 @@ subroutine merid_face_thickness(v, h, h_L, h_R, h_v, dt, G, GV, US, LB, vol_CFL, enddo enddo ; else ; do k=1,nz do i = OBC%segment(n)%HI%isd, OBC%segment(n)%HI%ied - h_v(i,J,k) = h(i,j,k) + h_v(i,J,k) = h(i,j,k) * por_face_areaV(i,J,k) enddo enddo ; endif else @@ -1533,7 +1560,7 @@ subroutine merid_face_thickness(v, h, h_L, h_R, h_v, dt, G, GV, US, LB, vol_CFL, enddo enddo ; else ; do k=1,nz do i = OBC%segment(n)%HI%isd, OBC%segment(n)%HI%ied - h_v(i,J,k) = h(i,j+1,k) + h_v(i,J,k) = h(i,j+1,k) * por_face_areaV(i,J,k) enddo enddo ; endif endif @@ -1547,7 +1574,7 @@ end subroutine merid_face_thickness subroutine meridional_flux_adjust(v, h_in, h_L, h_R, vhbt, vh_tot_0, dvhdv_tot_0, & dv, dv_max_CFL, dv_min_CFL, dt, G, GV, US, CS, visc_rem, & j, ish, ieh, do_I_in, por_face_areaV, vh_3d, OBC) - type(ocean_grid_type), intent(inout) :: G !< Ocean's grid structure. + type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1]. @@ -1699,7 +1726,7 @@ end subroutine meridional_flux_adjust subroutine set_merid_BT_cont(v, h_in, h_L, h_R, BT_cont, vh_tot_0, dvhdv_tot_0, & dv_max_CFL, dv_min_CFL, dt, G, GV, US, CS, visc_rem, & visc_rem_max, j, ish, ieh, do_I, por_face_areaV) - type(ocean_grid_type), intent(inout) :: G !< Ocean's grid structure. + type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1]. real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_in !< Layer thickness used to calculate fluxes, From fc0bef1c23efe5236fc46d6fa7b6b5ea6e156648 Mon Sep 17 00:00:00 2001 From: Robert Hallberg Date: Tue, 14 Nov 2023 14:28:03 -0500 Subject: [PATCH 02/22] +Pass-through from continuity_PPM via continuity In recognition of the fact that there is only a single continuity scheme that is accessed via the MOM_continuity module, this commit refactors MOM_continuity to use 3 simple pass-through interfaces (continuity, continuity_init and continuity_stencil) to the corresponding routines from MOM_continuity_PPM, while the MOM_continuity control structure is now alias for continuity_PPM_CS and is opaque in the MOM_continuity module. As a part of these changes, the runtime parameter CONTINUITY_SCHEME was obsoleted with a warning value of "PPM". All answers are bitwise identical, and all public interfaces look the same from the outside, but there is one fewer entry in the MOM_parameter_doc.all files. --- src/core/MOM_continuity.F90 | 181 +++--------------------- src/diagnostics/MOM_obsolete_params.F90 | 3 +- 2 files changed, 19 insertions(+), 165 deletions(-) diff --git a/src/core/MOM_continuity.F90 b/src/core/MOM_continuity.F90 index 7a833ccb5c..44422d5e47 100644 --- a/src/core/MOM_continuity.F90 +++ b/src/core/MOM_continuity.F90 @@ -3,13 +3,12 @@ module MOM_continuity ! This file is part of MOM6. See LICENSE.md for the license. -use MOM_continuity_PPM, only : continuity_PPM, zonal_mass_flux, meridional_mass_flux -use MOM_continuity_PPM, only : continuity_PPM_stencil, continuity_PPM_init -use MOM_continuity_PPM, only : continuity_PPM_CS -use MOM_diag_mediator, only : time_type, diag_ctrl -use MOM_error_handler, only : MOM_error, MOM_mesg, FATAL, WARNING, is_root_pe -use MOM_file_parser, only : get_param, log_version, param_file_type -use MOM_string_functions, only : uppercase +use MOM_continuity_PPM, only : continuity=>continuity_PPM +use MOM_continuity_PPM, only : continuity_stencil=>continuity_PPM_stencil +use MOM_continuity_PPM, only : continuity_init=>continuity_PPM_init +use MOM_continuity_PPM, only : continuity_CS=>continuity_PPM_CS +use MOM_continuity_PPM, only : zonal_mass_flux, meridional_mass_flux +use MOM_diag_mediator, only : time_type use MOM_grid, only : ocean_grid_type use MOM_open_boundary, only : ocean_OBC_type use MOM_unit_scaling, only : unit_scale_type @@ -20,20 +19,9 @@ module MOM_continuity #include -public continuity, continuity_fluxes, continuity_adjust_vel, continuity_init, continuity_stencil - -!> Control structure for mom_continuity -type, public :: continuity_CS ; private - integer :: continuity_scheme !< Selects the discretization for the continuity solver. - !! Valid values are: - !! - PPM - A directionally split piecewise parabolic reconstruction solver. - !! The default, PPM, seems most appropriate for use with our current - !! time-splitting strategies. - type(continuity_PPM_CS) :: PPM !< Control structure for mom_continuity_ppm -end type continuity_CS - -integer, parameter :: PPM_SCHEME = 1 !< Enumerated constant to select PPM -character(len=20), parameter :: PPM_STRING = "PPM" !< String to select PPM +! These are direct pass-throughs of routines in continuity_PPM +public continuity, continuity_init, continuity_stencil, continuity_CS +public continuity_fluxes, continuity_adjust_vel !> Finds the thickness fluxes from the continuity solver or their vertical sum without !! actually updating the layer thicknesses. @@ -43,75 +31,6 @@ module MOM_continuity contains -!> Time steps the layer thicknesses, using a monotonically or positive-definite limited, directionally -!! split PPM scheme, based on Lin (1994). -subroutine continuity(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhbt, vhbt, & - visc_rem_u, visc_rem_v, u_cor, v_cor, BT_cont) - type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure. - type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure. - real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & - intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]. - real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & - intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1]. - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & - intent(in) :: hin !< Initial layer thickness [H ~> m or kg m-2]. - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & - intent(inout) :: h !< Final layer thickness [H ~> m or kg m-2]. - real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & - intent(out) :: uh !< Volume flux through zonal faces = - !! u*h*dy [H L2 T-1 ~> m3 s-1 or kg s-1]. - real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & - intent(out) :: vh !< Volume flux through meridional faces = - !! v*h*dx [H L2 T-1 ~> m3 s-1 or kg s-1]. - real, intent(in) :: dt !< Time increment [T ~> s]. - type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type - type(continuity_CS), intent(in) :: CS !< Control structure for mom_continuity. - type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. - type(porous_barrier_type), intent(in) :: pbv !< porous barrier fractional cell metrics - real, dimension(SZIB_(G),SZJ_(G)), & - optional, intent(in) :: uhbt !< The vertically summed volume flux through - !! zonal faces [H L2 T-1 ~> m3 s-1 or kg s-1]. - real, dimension(SZI_(G),SZJB_(G)), & - optional, intent(in) :: vhbt !< The vertically summed volume flux through - !! meridional faces [H L2 T-1 ~> m3 s-1 or kg s-1]. - real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & - optional, intent(in) :: visc_rem_u !< Both the fraction of - !! zonal momentum that remains after a time-step of viscosity, and the fraction of a time-step's - !! worth of a barotropic acceleration that a layer experiences after viscosity is applied [nondim]. - !! Non-dimensional between 0 (at the bottom) and 1 (far above the bottom). When this column is - !! under an ice shelf, this can also go to 0 at the top due to the no-slip boundary condition there. - real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & - optional, intent(in) :: visc_rem_v !< Both the fraction of - !! meridional momentum that remains after a time-step of viscosity, and the fraction of a time-step's - !! worth of a barotropic acceleration that a layer experiences after viscosity is applied [nondim]. - !! Non-dimensional between 0 (at the bottom) and 1 (far above the bottom). When this column is - !! under an ice shelf, this can also go to 0 at the top due to the no-slip boundary condition there. - real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & - optional, intent(out) :: u_cor !< The zonal velocities that - !! give uhbt as the depth-integrated transport [L T-1 ~> m s-1]. - real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & - optional, intent(out) :: v_cor !< The meridional velocities that - !! give vhbt as the depth-integrated transport [L T-1 ~> m s-1]. - type(BT_cont_type), & - optional, pointer :: BT_cont !< A structure with elements - !! that describe the effective open face areas as a function of barotropic flow. - - if (present(visc_rem_u) .neqv. present(visc_rem_v)) call MOM_error(FATAL, & - "MOM_continuity: Either both visc_rem_u and visc_rem_v or neither"// & - " one must be present in call to continuity.") - if (present(u_cor) .neqv. present(v_cor)) call MOM_error(FATAL, & - "MOM_continuity: Either both u_cor and v_cor or neither"// & - " one must be present in call to continuity.") - - if (CS%continuity_scheme == PPM_SCHEME) then - call continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS%PPM, OBC, pbv, uhbt, vhbt, & - visc_rem_u, visc_rem_v, u_cor, v_cor, BT_cont=BT_cont) - else - call MOM_error(FATAL, "continuity: Unrecognized value of continuity_scheme") - endif - -end subroutine continuity - !> Finds the thickness fluxes from the continuity solver without actually updating the !! layer thicknesses. Because the fluxes in the two directions are calculated based on the !! input thicknesses, which are not updated between the direcitons, the fluxes returned here @@ -137,13 +56,9 @@ subroutine continuity_3d_fluxes(u, v, h, uh, vh, dt, G, GV, US, CS, OBC, pbv) type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. type(porous_barrier_type), intent(in) :: pbv !< porous barrier fractional cell metrics - if (CS%continuity_scheme == PPM_SCHEME) then - call zonal_mass_flux(u, h, uh, dt, G, GV, US, CS%PPM, OBC, pbv%por_face_areaU) + call zonal_mass_flux(u, h, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU) - call meridional_mass_flux(v, h, vh, dt, G, GV, US, CS%PPM, OBC, pbv%por_face_areaV) - else - call MOM_error(FATAL, "continuity: Unrecognized value of continuity_scheme") - endif + call meridional_mass_flux(v, h, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV) end subroutine continuity_3d_fluxes @@ -182,13 +97,9 @@ subroutine continuity_2d_fluxes(u, v, h, uhbt, vhbt, dt, G, GV, US, CS, OBC, pbv uh(:,:,:) = 0.0 vh(:,:,:) = 0.0 - if (CS%continuity_scheme == PPM_SCHEME) then - call zonal_mass_flux(u, h, uh, dt, G, GV, US, CS%PPM, OBC, pbv%por_face_areaU) + call zonal_mass_flux(u, h, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU) - call meridional_mass_flux(v, h, vh, dt, G, GV, US, CS%PPM, OBC, pbv%por_face_areaV) - else - call MOM_error(FATAL, "continuity: Unrecognized value of continuity_scheme") - endif + call meridional_mass_flux(v, h, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV) uhbt(:,:) = 0.0 vhbt(:,:) = 0.0 @@ -262,70 +173,12 @@ subroutine continuity_adjust_vel(u, v, h, dt, G, GV, US, CS, OBC, pbv, uhbt, vhb u_in(:,:,:) = u(:,:,:) v_in(:,:,:) = v(:,:,:) - if (CS%continuity_scheme == PPM_SCHEME) then - call zonal_mass_flux(u_in, h, uh, dt, G, GV, US, CS%PPM, OBC, pbv%por_face_areaU, & - uhbt=uhbt, visc_rem_u=visc_rem_u, u_cor=u) + call zonal_mass_flux(u_in, h, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU, & + uhbt=uhbt, visc_rem_u=visc_rem_u, u_cor=u) - call meridional_mass_flux(v_in, h, vh, dt, G, GV, US, CS%PPM, OBC, pbv%por_face_areaV, & - vhbt=vhbt, visc_rem_v=visc_rem_v, v_cor=v) - else - call MOM_error(FATAL, "continuity: Unrecognized value of continuity_scheme") - endif + call meridional_mass_flux(v_in, h, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV, & + vhbt=vhbt, visc_rem_v=visc_rem_v, v_cor=v) end subroutine continuity_adjust_vel -!> Initializes continuity_cs -subroutine continuity_init(Time, G, GV, US, param_file, diag, CS) - type(time_type), target, intent(in) :: Time !< Current model time. - type(ocean_grid_type), intent(in) :: G !< Ocean grid structure. - type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure. - type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type - type(param_file_type), intent(in) :: param_file !< Parameter file handles. - type(diag_ctrl), target, intent(inout) :: diag !< Diagnostics control structure. - type(continuity_CS), intent(inout) :: CS !< Control structure for mom_continuity. - - ! This include declares and sets the variable "version". -# include "version_variable.h" - character(len=40) :: mdl = "MOM_continuity" ! This module's name. - character(len=20) :: tmpstr - - ! Read all relevant parameters and write them to the model log. - call log_version(param_file, mdl, version, "") - call get_param(param_file, mdl, "CONTINUITY_SCHEME", tmpstr, & - "CONTINUITY_SCHEME selects the discretization for the "//& - "continuity solver. The only valid value currently is: \n"//& - "\t PPM - use a positive-definite (or monotonic) \n"//& - "\t piecewise parabolic reconstruction solver.", & - default=PPM_STRING) - - tmpstr = uppercase(tmpstr) ; CS%continuity_scheme = 0 - select case (trim(tmpstr)) - case (PPM_STRING) ; CS%continuity_scheme = PPM_SCHEME - case default - call MOM_mesg('continuity_init: CONTINUITY_SCHEME ="'//trim(tmpstr)//'"', 0) - call MOM_mesg("continuity_init: The only valid value is currently "// & - trim(PPM_STRING), 0) - call MOM_error(FATAL, "continuity_init: Unrecognized setting "// & - "#define CONTINUITY_SCHEME "//trim(tmpstr)//" found in input file.") - end select - - if (CS%continuity_scheme == PPM_SCHEME) then - call continuity_PPM_init(Time, G, GV, US, param_file, diag, CS%PPM) - endif - -end subroutine continuity_init - - -!> continuity_stencil returns the continuity solver stencil size -function continuity_stencil(CS) result(stencil) - type(continuity_CS), intent(in) :: CS !< Module's control structure. - integer :: stencil !< The continuity solver stencil size with the current settings. - - stencil = 1 - - if (CS%continuity_scheme == PPM_SCHEME) then - stencil = continuity_PPM_stencil(CS%PPM) - endif -end function continuity_stencil - end module MOM_continuity diff --git a/src/diagnostics/MOM_obsolete_params.F90 b/src/diagnostics/MOM_obsolete_params.F90 index 4a50abbb14..2567e7591b 100644 --- a/src/diagnostics/MOM_obsolete_params.F90 +++ b/src/diagnostics/MOM_obsolete_params.F90 @@ -89,7 +89,8 @@ subroutine find_obsolete_params(param_file) if (test_logic .and. .not.split) call MOM_ERROR(FATAL, & "find_obsolete_params: #define DYNAMIC_SURFACE_PRESSURE is not yet "//& "implemented without #define SPLIT.") - + call obsolete_char(param_file, "CONTINUITY_SCHEME", warning_val="PPM", & + hint="Only one continuity scheme is available so this need not be specified.") call obsolete_real(param_file, "ETA_TOLERANCE_AUX", only_warn=.true.) call obsolete_real(param_file, "BT_MASS_SOURCE_LIMIT", 0.0) call obsolete_real(param_file, "FIRST_GUESS_SURFACE_LAYER_DEPTH") From 6b86ab84dcf622abe9b8b69d35f317315e5d52b8 Mon Sep 17 00:00:00 2001 From: Robert Hallberg Date: Wed, 15 Nov 2023 06:11:49 -0500 Subject: [PATCH 03/22] +Create zonal_edge_thickness in MOM_continuity_PPM Refactored MOM_continuity_PPM to create the separate publicly visible routines zonal_edge_thickness and meridional_edge_thickness, and also renamed the internal routines zonal_face_thickness and merid_face_thickness to zonal_flux_thickness, meridional_flux_thickness and made them publicly visible as well. This commit also renames a number of internal edge thickness variables from h_L and h_R to h_S and h_N or h_W and h_E for greater clarity, since left and right are not so well defined on the grid as north, south, east and west. All answers are bitwise identical, but there are 4 new publicly visible interfaces. --- src/core/MOM_continuity_PPM.F90 | 431 ++++++++++++++++++-------------- 1 file changed, 250 insertions(+), 181 deletions(-) diff --git a/src/core/MOM_continuity_PPM.F90 b/src/core/MOM_continuity_PPM.F90 index 7f96e675cd..415d04dd36 100644 --- a/src/core/MOM_continuity_PPM.F90 +++ b/src/core/MOM_continuity_PPM.F90 @@ -20,6 +20,8 @@ module MOM_continuity_PPM public continuity_PPM, continuity_PPM_init, continuity_PPM_stencil public zonal_mass_flux, meridional_mass_flux +public zonal_flux_thickness, meridional_flux_thickness +public zonal_edge_thickness, meridional_edge_thickness !>@{ CPU time clock IDs integer :: id_clock_update, id_clock_correct @@ -142,7 +144,7 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhb "MOM_continuity_PPM: Either both visc_rem_u and visc_rem_v or neither"// & " one must be present in call to continuity_PPM.") - stencil = 3 ; if (CS%simple_2nd) stencil = 2 ; if (CS%upwind_1st) stencil = 1 + stencil = continuity_PPM_stencil(CS) if (x_first) then ! First, advect zonally. @@ -210,6 +212,92 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhb end subroutine continuity_PPM +!> Set the reconstructed thicknesses at the eastern and western edges of tracer cells. +subroutine zonal_edge_thickness(h_in, h_W, h_E, G, GV, US, CS, OBC, LB_in) + type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. + type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + intent(in) :: h_in !< Tracer cell layer thickness [H ~> m or kg m-2]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + intent(out) :: h_W !< Western edge layer thickness [H ~> m or kg m-2]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + intent(out) :: h_E !< Eastern edge layer thickness [H ~> m or kg m-2]. + type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type + type(continuity_PPM_CS), intent(in) :: CS !< This module's control structure. + type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. + type(loop_bounds_type), & + optional, intent(in) :: LB_in !< Loop bounds structure. + + ! Local variables + type(loop_bounds_type) :: LB + integer :: i, j, k, ish, ieh, jsh, jeh, nz + + if (present(LB_in)) then + LB = LB_in + else + LB%ish = G%isc ; LB%ieh = G%iec ; LB%jsh = G%jsc ; LB%jeh = G%jec + endif + ish = LB%ish ; ieh = LB%ieh ; jsh = LB%jsh ; jeh = LB%jeh ; nz = GV%ke + + if (CS%upwind_1st) then + !$OMP parallel do default(shared) + do k=1,nz ; do j=jsh,jeh ; do i=ish-1,ieh+1 + h_W(i,j,k) = h_in(i,j,k) ; h_E(i,j,k) = h_in(i,j,k) + enddo ; enddo ; enddo + else + !$OMP parallel do default(shared) + do k=1,nz + call PPM_reconstruction_x(h_in(:,:,k), h_W(:,:,k), h_E(:,:,k), G, LB, & + 2.0*GV%Angstrom_H, CS%monotonic, CS%simple_2nd, OBC) + enddo + endif + +end subroutine zonal_edge_thickness + + +!> Set the reconstructed thicknesses at the eastern and western edges of tracer cells. +subroutine meridional_edge_thickness(h_in, h_S, h_N, G, GV, US, CS, OBC, LB_in) + type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. + type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + intent(in) :: h_in !< Tracer cell layer thickness [H ~> m or kg m-2]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + intent(out) :: h_S !< Southern edge layer thickness [H ~> m or kg m-2]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + intent(out) :: h_N !< Northern edge layer thickness [H ~> m or kg m-2]. + type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type + type(continuity_PPM_CS), intent(in) :: CS !< This module's control structure. + type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. + type(loop_bounds_type), & + optional, intent(in) :: LB_in !< Loop bounds structure. + + ! Local variables + type(loop_bounds_type) :: LB + integer :: i, j, k, ish, ieh, jsh, jeh, nz + + if (present(LB_in)) then + LB = LB_in + else + LB%ish = G%isc ; LB%ieh = G%iec ; LB%jsh = G%jsc ; LB%jeh = G%jec + endif + ish = LB%ish ; ieh = LB%ieh ; jsh = LB%jsh ; jeh = LB%jeh ; nz = GV%ke + + if (CS%upwind_1st) then + !$OMP parallel do default(shared) + do k=1,nz ; do j=jsh-1,jeh+1 ; do i=ish,ieh + h_S(i,j,k) = h_in(i,j,k) ; h_N(i,j,k) = h_in(i,j,k) + enddo ; enddo ; enddo + else + !$OMP parallel do default(shared) + do k=1,nz + call PPM_reconstruction_y(h_in(:,:,k), h_S(:,:,k), h_N(:,:,k), G, LB, & + 2.0*GV%Angstrom_H, CS%monotonic, CS%simple_2nd, OBC) + enddo + endif + +end subroutine meridional_edge_thickness + + !> Calculates the mass or volume fluxes through the zonal faces, and other related quantities. subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, & LB_in, uhbt, visc_rem_u, u_cor, BT_cont) @@ -248,7 +336,7 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, ! Local variables real, dimension(SZIB_(G),SZK_(GV)) :: duhdu ! Partial derivative of uh with u [H L ~> m2 or kg m-1]. - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: h_L, h_R ! Left and right face thicknesses [H ~> m or kg m-2]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: h_W, h_E ! Left and right face thicknesses [H ~> m or kg m-2]. real, dimension(SZIB_(G)) :: & du, & ! Corrective barotropic change in the velocity [L T-1 ~> m s-1]. du_min_CFL, & ! Lower limit on du correction to avoid CFL violations [L T-1 ~> m s-1] @@ -295,23 +383,13 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, if (CS%aggress_adjust) CFL_dt = I_dt call cpu_clock_begin(id_clock_update) -!$OMP parallel do default(none) shared(ish,ieh,jsh,jeh,nz,CS,h_L,h_in,h_R,G,GV,LB,visc_rem,OBC) - do k=1,nz - ! This sets h_L and h_R. - if (CS%upwind_1st) then - do j=jsh,jeh ; do i=ish-1,ieh+1 - h_L(i,j,k) = h_in(i,j,k) ; h_R(i,j,k) = h_in(i,j,k) - enddo ; enddo - else - call PPM_reconstruction_x(h_in(:,:,k), h_L(:,:,k), h_R(:,:,k), G, LB, & - 2.0*GV%Angstrom_H, CS%monotonic, CS%simple_2nd, OBC) - endif - do I=ish-1,ieh ; visc_rem(I,k) = 1.0 ; enddo - enddo + ! This sets h_W and h_E. + call zonal_edge_thickness(h_in, h_W, h_E, G, GV, US, CS, OBC, LB) call cpu_clock_end(id_clock_update) call cpu_clock_begin(id_clock_correct) -!$OMP parallel do default(none) shared(ish,ieh,jsh,jeh,nz,u,h_in,h_L,h_R,use_visc_rem,visc_rem_u, & + if (.not.use_visc_rem) visc_rem(:,:) = 1.0 +!$OMP parallel do default(none) shared(ish,ieh,jsh,jeh,nz,u,h_in,h_W,h_E,use_visc_rem,visc_rem_u, & !$OMP uh,dt,US,G,GV,CS,local_specified_BC,OBC,uhbt,set_BT_cont, & !$OMP CFL_dt,I_dt,u_cor,BT_cont, local_Flather_OBC, & !$OMP por_face_areaU) & @@ -320,33 +398,33 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, !$OMP any_simple_OBC,l_seg) & !$OMP firstprivate(visc_rem) do j=jsh,jeh - do I=ish-1,ieh ; do_I(I) = .true. ; visc_rem_max(I) = 0.0 ; enddo + do I=ish-1,ieh ; do_I(I) = .true. ; enddo ! Set uh and duhdu. do k=1,nz if (use_visc_rem) then ; do I=ish-1,ieh visc_rem(I,k) = visc_rem_u(I,j,k) - visc_rem_max(I) = max(visc_rem_max(I), visc_rem(I,k)) enddo ; endif - call zonal_flux_layer(u(:,j,k), h_in(:,j,k), h_L(:,j,k), h_R(:,j,k), & + call zonal_flux_layer(u(:,j,k), h_in(:,j,k), h_W(:,j,k), h_E(:,j,k), & uh(:,j,k), duhdu(:,k), visc_rem(:,k), & dt, G, US, j, ish, ieh, do_I, CS%vol_CFL, por_face_areaU(:,j,k), OBC) if (local_specified_BC) then - do I=ish-1,ieh + do I=ish-1,ieh ; if (OBC%segnum_u(I,j) /= OBC_NONE) then l_seg = OBC%segnum_u(I,j) - - if (l_seg /= OBC_NONE) then - if (OBC%segment(l_seg)%specified) & - uh(I,j,k) = OBC%segment(l_seg)%normal_trans(I,j,k) - endif - enddo + if (OBC%segment(l_seg)%specified) & + uh(I,j,k) = OBC%segment(l_seg)%normal_trans(I,j,k) + endif ; enddo endif enddo - if ((.not.use_visc_rem).or.(.not.CS%use_visc_rem_max)) then ; do I=ish-1,ieh - visc_rem_max(I) = 1.0 - enddo ; endif - if (present(uhbt) .or. set_BT_cont) then + if (use_visc_rem .and. CS%use_visc_rem_max) then + visc_rem_max(:) = 0.0 + do k=1,nz ; do I=ish-1,ieh + visc_rem_max(I) = max(visc_rem_max(I), visc_rem(I,k)) + enddo ; enddo + else + visc_rem_max(:) = 1.0 + endif ! Set limits on du that will keep the CFL number between -1 and 1. ! This should be adequate to keep the root bracketed in all cases. do I=ish-1,ieh @@ -440,7 +518,7 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, endif if (present(uhbt)) then - call zonal_flux_adjust(u, h_in, h_L, h_R, uhbt(:,j), uh_tot_0, duhdu_tot_0, du, & + call zonal_flux_adjust(u, h_in, h_W, h_E, uhbt(:,j), uh_tot_0, duhdu_tot_0, du, & du_max_CFL, du_min_CFL, dt, G, GV, US, CS, visc_rem, & j, ish, ieh, do_I, por_face_areaU, uh, OBC=OBC) @@ -459,7 +537,7 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, endif if (set_BT_cont) then - call set_zonal_BT_cont(u, h_in, h_L, h_R, BT_cont, uh_tot_0, duhdu_tot_0,& + call set_zonal_BT_cont(u, h_in, h_W, h_E, BT_cont, uh_tot_0, duhdu_tot_0,& du_max_CFL, du_min_CFL, dt, G, GV, US, CS, visc_rem, & visc_rem_max, j, ish, ieh, do_I, por_face_areaU) if (any_simple_OBC) then @@ -519,10 +597,10 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, if (set_BT_cont) then ; if (allocated(BT_cont%h_u)) then if (present(u_cor)) then - call zonal_face_thickness(u_cor, h_in, h_L, h_R, BT_cont%h_u, dt, G, GV, US, LB, & + call zonal_flux_thickness(u_cor, h_in, h_W, h_E, BT_cont%h_u, dt, G, GV, US, LB, & CS%vol_CFL, CS%marginal_faces, OBC, por_face_areaU, visc_rem_u) else - call zonal_face_thickness(u, h_in, h_L, h_R, BT_cont%h_u, dt, G, GV, US, LB, & + call zonal_flux_thickness(u, h_in, h_W, h_E, BT_cont%h_u, dt, G, GV, US, LB, & CS%vol_CFL, CS%marginal_faces, OBC, por_face_areaU, visc_rem_u) endif endif ; endif @@ -530,7 +608,7 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, end subroutine zonal_mass_flux !> Evaluates the zonal mass or volume fluxes in a layer. -subroutine zonal_flux_layer(u, h, h_L, h_R, uh, duhdu, visc_rem, dt, G, US, j, & +subroutine zonal_flux_layer(u, h, h_W, h_E, uh, duhdu, visc_rem, dt, G, US, j, & ish, ieh, do_I, vol_CFL, por_face_areaU, OBC) type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. real, dimension(SZIB_(G)), intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]. @@ -540,8 +618,8 @@ subroutine zonal_flux_layer(u, h, h_L, h_R, uh, duhdu, visc_rem, dt, G, US, j, & !! acceleration that a layer experiences after viscosity is applied [nondim]. !! Visc_rem is between 0 (at the bottom) and 1 (far above the bottom). real, dimension(SZI_(G)), intent(in) :: h !< Layer thickness [H ~> m or kg m-2]. - real, dimension(SZI_(G)), intent(in) :: h_L !< Left thickness [H ~> m or kg m-2]. - real, dimension(SZI_(G)), intent(in) :: h_R !< Right thickness [H ~> m or kg m-2]. + real, dimension(SZI_(G)), intent(in) :: h_W !< West edge thickness [H ~> m or kg m-2]. + real, dimension(SZI_(G)), intent(in) :: h_E !< East edge thickness [H ~> m or kg m-2]. real, dimension(SZIB_(G)), intent(inout) :: uh !< Zonal mass or volume !! transport [H L2 T-1 ~> m3 s-1 or kg s-1]. real, dimension(SZIB_(G)), intent(inout) :: duhdu !< Partial derivative of uh @@ -574,20 +652,20 @@ subroutine zonal_flux_layer(u, h, h_L, h_R, uh, duhdu, visc_rem, dt, G, US, j, & if (u(I) > 0.0) then if (vol_CFL) then ; CFL = (u(I) * dt) * (G%dy_Cu(I,j) * G%IareaT(i,j)) else ; CFL = u(I) * dt * G%IdxT(i,j) ; endif - curv_3 = h_L(i) + h_R(i) - 2.0*h(i) + curv_3 = h_W(i) + h_E(i) - 2.0*h(i) uh(I) = (G%dy_Cu(I,j) * por_face_areaU(I)) * u(I) * & - (h_R(i) + CFL * (0.5*(h_L(i) - h_R(i)) + curv_3*(CFL - 1.5))) - h_marg = h_R(i) + CFL * ((h_L(i) - h_R(i)) + 3.0*curv_3*(CFL - 1.0)) + (h_E(i) + CFL * (0.5*(h_W(i) - h_E(i)) + curv_3*(CFL - 1.5))) + h_marg = h_E(i) + CFL * ((h_W(i) - h_E(i)) + 3.0*curv_3*(CFL - 1.0)) elseif (u(I) < 0.0) then if (vol_CFL) then ; CFL = (-u(I) * dt) * (G%dy_Cu(I,j) * G%IareaT(i+1,j)) else ; CFL = -u(I) * dt * G%IdxT(i+1,j) ; endif - curv_3 = h_L(i+1) + h_R(i+1) - 2.0*h(i+1) + curv_3 = h_W(i+1) + h_E(i+1) - 2.0*h(i+1) uh(I) = (G%dy_Cu(I,j) * por_face_areaU(I)) * u(I) * & - (h_L(i+1) + CFL * (0.5*(h_R(i+1)-h_L(i+1)) + curv_3*(CFL - 1.5))) - h_marg = h_L(i+1) + CFL * ((h_R(i+1)-h_L(i+1)) + 3.0*curv_3*(CFL - 1.0)) + (h_W(i+1) + CFL * (0.5*(h_E(i+1)-h_W(i+1)) + curv_3*(CFL - 1.5))) + h_marg = h_W(i+1) + CFL * ((h_E(i+1)-h_W(i+1)) + 3.0*curv_3*(CFL - 1.0)) else uh(I) = 0.0 - h_marg = 0.5 * (h_L(i+1) + h_R(i)) + h_marg = 0.5 * (h_W(i+1) + h_E(i)) endif duhdu(I) = (G%dy_Cu(I,j) * por_face_areaU(I)) * h_marg * visc_rem(I) endif ; enddo @@ -611,18 +689,18 @@ subroutine zonal_flux_layer(u, h, h_L, h_R, uh, duhdu, visc_rem, dt, G, US, j, & endif end subroutine zonal_flux_layer -!> Sets the effective interface thickness at each zonal velocity point, optionally scaling -!! back these thicknesses to account for viscosity and fractional open areas. -subroutine zonal_face_thickness(u, h, h_L, h_R, h_u, dt, G, GV, US, LB, vol_CFL, & +!> Sets the effective interface thickness associated with the fluxes at each zonal velocity point, +!! optionally scaling back these thicknesses to account for viscosity and fractional open areas. +subroutine zonal_flux_thickness(u, h, h_W, h_E, h_u, dt, G, GV, US, LB, vol_CFL, & marginal, OBC, por_face_areaU, visc_rem_u) type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]. real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h !< Layer thickness used to !! calculate fluxes [H ~> m or kg m-2]. - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_L !< Left thickness in the + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_W !< West edge thickness in the !! reconstruction [H ~> m or kg m-2]. - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_R !< Right thickness in the + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_E !< East edge thickness in the !! reconstruction [H ~> m or kg m-2]. real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), intent(inout) :: h_u !< Effective thickness at zonal faces, !! scaled down to account for the effects of @@ -659,23 +737,23 @@ subroutine zonal_face_thickness(u, h, h_L, h_R, h_u, dt, G, GV, US, LB, vol_CFL, if (u(I,j,k) > 0.0) then if (vol_CFL) then ; CFL = (u(I,j,k) * dt) * (G%dy_Cu(I,j) * G%IareaT(i,j)) else ; CFL = u(I,j,k) * dt * G%IdxT(i,j) ; endif - curv_3 = h_L(i,j,k) + h_R(i,j,k) - 2.0*h(i,j,k) - h_avg = h_R(i,j,k) + CFL * (0.5*(h_L(i,j,k) - h_R(i,j,k)) + curv_3*(CFL - 1.5)) - h_marg = h_R(i,j,k) + CFL * ((h_L(i,j,k) - h_R(i,j,k)) + 3.0*curv_3*(CFL - 1.0)) + curv_3 = h_W(i,j,k) + h_E(i,j,k) - 2.0*h(i,j,k) + h_avg = h_E(i,j,k) + CFL * (0.5*(h_W(i,j,k) - h_E(i,j,k)) + curv_3*(CFL - 1.5)) + h_marg = h_E(i,j,k) + CFL * ((h_W(i,j,k) - h_E(i,j,k)) + 3.0*curv_3*(CFL - 1.0)) elseif (u(I,j,k) < 0.0) then if (vol_CFL) then ; CFL = (-u(I,j,k)*dt) * (G%dy_Cu(I,j) * G%IareaT(i+1,j)) else ; CFL = -u(I,j,k) * dt * G%IdxT(i+1,j) ; endif - curv_3 = h_L(i+1,j,k) + h_R(i+1,j,k) - 2.0*h(i+1,j,k) - h_avg = h_L(i+1,j,k) + CFL * (0.5*(h_R(i+1,j,k)-h_L(i+1,j,k)) + curv_3*(CFL - 1.5)) - h_marg = h_L(i+1,j,k) + CFL * ((h_R(i+1,j,k)-h_L(i+1,j,k)) + & + curv_3 = h_W(i+1,j,k) + h_E(i+1,j,k) - 2.0*h(i+1,j,k) + h_avg = h_W(i+1,j,k) + CFL * (0.5*(h_E(i+1,j,k)-h_W(i+1,j,k)) + curv_3*(CFL - 1.5)) + h_marg = h_W(i+1,j,k) + CFL * ((h_E(i+1,j,k)-h_W(i+1,j,k)) + & 3.0*curv_3*(CFL - 1.0)) else - h_avg = 0.5 * (h_L(i+1,j,k) + h_R(i,j,k)) + h_avg = 0.5 * (h_W(i+1,j,k) + h_E(i,j,k)) ! The choice to use the arithmetic mean here is somewhat arbitrarily, but - ! it should be noted that h_L(i+1,j,k) and h_R(i,j,k) are usually the same. - h_marg = 0.5 * (h_L(i+1,j,k) + h_R(i,j,k)) - ! h_marg = (2.0 * h_L(i+1,j,k) * h_R(i,j,k)) / & - ! (h_L(i+1,j,k) + h_R(i,j,k) + GV%H_subroundoff) + ! it should be noted that h_W(i+1,j,k) and h_E(i,j,k) are usually the same. + h_marg = 0.5 * (h_W(i+1,j,k) + h_E(i,j,k)) + ! h_marg = (2.0 * h_W(i+1,j,k) * h_E(i,j,k)) / & + ! (h_W(i+1,j,k) + h_E(i,j,k) + GV%H_subroundoff) endif if (marginal) then ; h_u(I,j,k) = h_marg @@ -727,11 +805,11 @@ subroutine zonal_face_thickness(u, h, h_L, h_R, h_u, dt, G, GV, US, LB, vol_CFL, enddo endif -end subroutine zonal_face_thickness +end subroutine zonal_flux_thickness !> Returns the barotropic velocity adjustment that gives the !! desired barotropic (layer-summed) transport. -subroutine zonal_flux_adjust(u, h_in, h_L, h_R, uhbt, uh_tot_0, duhdu_tot_0, & +subroutine zonal_flux_adjust(u, h_in, h_W, h_E, uhbt, uh_tot_0, duhdu_tot_0, & du, du_max_CFL, du_min_CFL, dt, G, GV, US, CS, visc_rem, & j, ish, ieh, do_I_in, por_face_areaU, uh_3d, OBC) @@ -740,9 +818,9 @@ subroutine zonal_flux_adjust(u, h_in, h_L, h_R, uhbt, uh_tot_0, duhdu_tot_0, & real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]. real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_in !< Layer thickness used to !! calculate fluxes [H ~> m or kg m-2]. - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_L !< Left thickness in the + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_W !< West edge thickness in the !! reconstruction [H ~> m or kg m-2]. - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_R !< Right thickness in the + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_E !< East edge thickness in the !! reconstruction [H ~> m or kg m-2]. real, dimension(SZIB_(G),SZK_(GV)), intent(in) :: visc_rem !< Both the fraction of the !! momentum originally in a layer that remains after a time-step of viscosity, and @@ -854,7 +932,7 @@ subroutine zonal_flux_adjust(u, h_in, h_L, h_R, uhbt, uh_tot_0, duhdu_tot_0, & if ((itt < max_itts) .or. present(uh_3d)) then ; do k=1,nz do I=ish-1,ieh ; u_new(I) = u(I,j,k) + du(I) * visc_rem(I,k) ; enddo - call zonal_flux_layer(u_new, h_in(:,j,k), h_L(:,j,k), h_R(:,j,k), & + call zonal_flux_layer(u_new, h_in(:,j,k), h_W(:,j,k), h_E(:,j,k), & uh_aux(:,k), duhdu(:,k), visc_rem(:,k), & dt, G, US, j, ish, ieh, do_I, CS%vol_CFL, por_face_areaU(:,j,k), OBC) enddo ; endif @@ -884,7 +962,7 @@ end subroutine zonal_flux_adjust !> Sets a structure that describes the zonal barotropic volume or mass fluxes as a !! function of barotropic flow to agree closely with the sum of the layer's transports. -subroutine set_zonal_BT_cont(u, h_in, h_L, h_R, BT_cont, uh_tot_0, duhdu_tot_0, & +subroutine set_zonal_BT_cont(u, h_in, h_W, h_E, BT_cont, uh_tot_0, duhdu_tot_0, & du_max_CFL, du_min_CFL, dt, G, GV, US, CS, visc_rem, & visc_rem_max, j, ish, ieh, do_I, por_face_areaU) type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. @@ -892,9 +970,9 @@ subroutine set_zonal_BT_cont(u, h_in, h_L, h_R, BT_cont, uh_tot_0, duhdu_tot_0, real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]. real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_in !< Layer thickness used to !! calculate fluxes [H ~> m or kg m-2]. - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_L !< Left thickness in the + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_W !< West edge thickness in the !! reconstruction [H ~> m or kg m-2]. - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_R !< Right thickness in the + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_E !< East edge thickness in the !! reconstruction [H ~> m or kg m-2]. type(BT_cont_type), intent(inout) :: BT_cont !< A structure with elements !! that describe the effective open face areas as a function of barotropic flow. @@ -961,7 +1039,7 @@ subroutine set_zonal_BT_cont(u, h_in, h_L, h_R, BT_cont, uh_tot_0, duhdu_tot_0, ! Diagnose the zero-transport correction, du0. do I=ish-1,ieh ; zeros(I) = 0.0 ; enddo - call zonal_flux_adjust(u, h_in, h_L, h_R, zeros, uh_tot_0, duhdu_tot_0, du0, & + call zonal_flux_adjust(u, h_in, h_W, h_E, zeros, uh_tot_0, duhdu_tot_0, du0, & du_max_CFL, du_min_CFL, dt, G, GV, US, CS, visc_rem, & j, ish, ieh, do_I, por_face_areaU) @@ -1003,11 +1081,11 @@ subroutine set_zonal_BT_cont(u, h_in, h_L, h_R, BT_cont, uh_tot_0, duhdu_tot_0, u_R(I) = u(I,j,k) + duR(I) * visc_rem(I,k) u_0(I) = u(I,j,k) + du0(I) * visc_rem(I,k) endif ; enddo - call zonal_flux_layer(u_0, h_in(:,j,k), h_L(:,j,k), h_R(:,j,k), uh_0, duhdu_0, & + call zonal_flux_layer(u_0, h_in(:,j,k), h_W(:,j,k), h_E(:,j,k), uh_0, duhdu_0, & visc_rem(:,k), dt, G, US, j, ish, ieh, do_I, CS%vol_CFL, por_face_areaU(:,j,k)) - call zonal_flux_layer(u_L, h_in(:,j,k), h_L(:,j,k), h_R(:,j,k), uh_L, duhdu_L, & + call zonal_flux_layer(u_L, h_in(:,j,k), h_W(:,j,k), h_E(:,j,k), uh_L, duhdu_L, & visc_rem(:,k), dt, G, US, j, ish, ieh, do_I, CS%vol_CFL, por_face_areaU(:,j,k)) - call zonal_flux_layer(u_R, h_in(:,j,k), h_L(:,j,k), h_R(:,j,k), uh_R, duhdu_R, & + call zonal_flux_layer(u_R, h_in(:,j,k), h_W(:,j,k), h_E(:,j,k), uh_R, duhdu_R, & visc_rem(:,k), dt, G, US, j, ish, ieh, do_I, CS%vol_CFL, por_face_areaU(:,j,k)) do I=ish-1,ieh ; if (do_I(I)) then FAmt_0(I) = FAmt_0(I) + duhdu_0(I) @@ -1086,7 +1164,7 @@ subroutine meridional_mass_flux(v, h_in, vh, dt, G, GV, US, CS, OBC, por_face_ar real, dimension(SZI_(G),SZK_(GV)) :: & dvhdv ! Partial derivative of vh with v [H L ~> m2 or kg m-1]. real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: & - h_L, h_R ! Left and right face thicknesses [H ~> m or kg m-2]. + h_S, h_N ! Southern and northern face thicknesses [H ~> m or kg m-2]. real, dimension(SZI_(G)) :: & dv, & ! Corrective barotropic change in the velocity [L T-1 ~> m s-1]. dv_min_CFL, & ! Lower limit on dv correction to avoid CFL violations [L T-1 ~> m s-1] @@ -1133,23 +1211,13 @@ subroutine meridional_mass_flux(v, h_in, vh, dt, G, GV, US, CS, OBC, por_face_ar if (CS%aggress_adjust) CFL_dt = I_dt call cpu_clock_begin(id_clock_update) -!$OMP parallel do default(none) shared(nz,ish,ieh,jsh,jeh,h_in,h_L,h_R,G,GV,LB,CS,visc_rem,OBC) - do k=1,nz - ! This sets h_L and h_R. - if (CS%upwind_1st) then - do j=jsh-1,jeh+1 ; do i=ish,ieh - h_L(i,j,k) = h_in(i,j,k) ; h_R(i,j,k) = h_in(i,j,k) - enddo ; enddo - else - call PPM_reconstruction_y(h_in(:,:,k), h_L(:,:,k), h_R(:,:,k), G, LB, & - 2.0*GV%Angstrom_H, CS%monotonic, CS%simple_2nd, OBC) - endif - do i=ish,ieh ; visc_rem(i,k) = 1.0 ; enddo - enddo + ! This sets h_S and h_N. + call meridional_edge_thickness(h_in, h_S, h_N, G, GV, US, CS, OBC, LB) call cpu_clock_end(id_clock_update) call cpu_clock_begin(id_clock_correct) -!$OMP parallel do default(none) shared(ish,ieh,jsh,jeh,nz,v,h_in,h_L,h_R,vh,use_visc_rem, & + if (.not.use_visc_rem) visc_rem(:,:) = 1.0 +!$OMP parallel do default(none) shared(ish,ieh,jsh,jeh,nz,v,h_in,h_S,h_N,vh,use_visc_rem, & !$OMP visc_rem_v,dt,US,G,GV,CS,local_specified_BC,OBC,vhbt, & !$OMP set_BT_cont,CFL_dt,I_dt,v_cor,BT_cont, local_Flather_OBC, & !$OMP por_face_areaV) & @@ -1158,32 +1226,33 @@ subroutine meridional_mass_flux(v, h_in, vh, dt, G, GV, US, CS, OBC, por_face_ar !$OMP is_simple,FAvi,dy_S,any_simple_OBC,l_seg) & !$OMP firstprivate(visc_rem) do J=jsh-1,jeh - do i=ish,ieh ; do_I(i) = .true. ; visc_rem_max(I) = 0.0 ; enddo + do i=ish,ieh ; do_I(i) = .true. ; enddo ! This sets vh and dvhdv. do k=1,nz if (use_visc_rem) then ; do i=ish,ieh visc_rem(i,k) = visc_rem_v(i,J,k) - visc_rem_max(i) = max(visc_rem_max(i), visc_rem(i,k)) enddo ; endif - call merid_flux_layer(v(:,J,k), h_in(:,:,k), h_L(:,:,k), h_R(:,:,k), & + call merid_flux_layer(v(:,J,k), h_in(:,:,k), h_S(:,:,k), h_N(:,:,k), & vh(:,J,k), dvhdv(:,k), visc_rem(:,k), & dt, G, US, J, ish, ieh, do_I, CS%vol_CFL, por_face_areaV(:,:,k), OBC) if (local_specified_BC) then - do i=ish,ieh + do i=ish,ieh ; if (OBC%segnum_v(i,J) /= OBC_NONE) then l_seg = OBC%segnum_v(i,J) - - if (l_seg /= OBC_NONE) then - if (OBC%segment(l_seg)%specified) & - vh(i,J,k) = OBC%segment(l_seg)%normal_trans(i,J,k) - endif - enddo + if (OBC%segment(l_seg)%specified) & + vh(i,J,k) = OBC%segment(l_seg)%normal_trans(i,J,k) + endif ; enddo endif enddo ! k-loop - if ((.not.use_visc_rem) .or. (.not.CS%use_visc_rem_max)) then ; do i=ish,ieh - visc_rem_max(i) = 1.0 - enddo ; endif if (present(vhbt) .or. set_BT_cont) then + if (use_visc_rem .and. CS%use_visc_rem_max) then + visc_rem_max(:) = 0.0 + do k=1,nz ; do i=ish,ieh + visc_rem_max(i) = max(visc_rem_max(i), visc_rem(i,k)) + enddo ; enddo + else + visc_rem_max(:) = 1.0 + endif ! Set limits on dv that will keep the CFL number between -1 and 1. ! This should be adequate to keep the root bracketed in all cases. do i=ish,ieh @@ -1274,7 +1343,7 @@ subroutine meridional_mass_flux(v, h_in, vh, dt, G, GV, US, CS, OBC, por_face_ar endif if (present(vhbt)) then - call meridional_flux_adjust(v, h_in, h_L, h_R, vhbt(:,J), vh_tot_0, dvhdv_tot_0, dv, & + call meridional_flux_adjust(v, h_in, h_S, h_N, vhbt(:,J), vh_tot_0, dvhdv_tot_0, dv, & dv_max_CFL, dv_min_CFL, dt, G, GV, US, CS, visc_rem, & j, ish, ieh, do_I, por_face_areaV, vh, OBC=OBC) @@ -1292,7 +1361,7 @@ subroutine meridional_mass_flux(v, h_in, vh, dt, G, GV, US, CS, OBC, por_face_ar endif if (set_BT_cont) then - call set_merid_BT_cont(v, h_in, h_L, h_R, BT_cont, vh_tot_0, dvhdv_tot_0,& + call set_merid_BT_cont(v, h_in, h_S, h_N, BT_cont, vh_tot_0, dvhdv_tot_0,& dv_max_CFL, dv_min_CFL, dt, G, GV, US, CS, visc_rem, & visc_rem_max, J, ish, ieh, do_I, por_face_areaV) if (any_simple_OBC) then @@ -1352,18 +1421,18 @@ subroutine meridional_mass_flux(v, h_in, vh, dt, G, GV, US, CS, OBC, por_face_ar if (set_BT_cont) then ; if (allocated(BT_cont%h_v)) then if (present(v_cor)) then - call merid_face_thickness(v_cor, h_in, h_L, h_R, BT_cont%h_v, dt, G, GV, US, LB, & - CS%vol_CFL, CS%marginal_faces, OBC, por_face_areaV, visc_rem_v) + call meridional_flux_thickness(v_cor, h_in, h_S, h_N, BT_cont%h_v, dt, G, GV, US, LB, & + CS%vol_CFL, CS%marginal_faces, OBC, por_face_areaV, visc_rem_v) else - call merid_face_thickness(v, h_in, h_L, h_R, BT_cont%h_v, dt, G, GV, US, LB, & - CS%vol_CFL, CS%marginal_faces, OBC, por_face_areaV, visc_rem_v) + call meridional_flux_thickness(v, h_in, h_S, h_N, BT_cont%h_v, dt, G, GV, US, LB, & + CS%vol_CFL, CS%marginal_faces, OBC, por_face_areaV, visc_rem_v) endif endif ; endif end subroutine meridional_mass_flux !> Evaluates the meridional mass or volume fluxes in a layer. -subroutine merid_flux_layer(v, h, h_L, h_R, vh, dvhdv, visc_rem, dt, G, US, J, & +subroutine merid_flux_layer(v, h, h_S, h_N, vh, dvhdv, visc_rem, dt, G, US, J, & ish, ieh, do_I, vol_CFL, por_face_areaV, OBC) type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. real, dimension(SZI_(G)), intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1]. @@ -1374,9 +1443,9 @@ subroutine merid_flux_layer(v, h, h_L, h_R, vh, dvhdv, visc_rem, dt, G, US, J, & !! Visc_rem is between 0 (at the bottom) and 1 (far above the bottom). real, dimension(SZI_(G),SZJ_(G)), intent(in) :: h !< Layer thickness used to calculate fluxes, !! [H ~> m or kg m-2]. - real, dimension(SZI_(G),SZJ_(G)), intent(in) :: h_L !< Left thickness in the reconstruction + real, dimension(SZI_(G),SZJ_(G)), intent(in) :: h_S !< South edge thickness in the reconstruction !! [H ~> m or kg m-2]. - real, dimension(SZI_(G),SZJ_(G)), intent(in) :: h_R !< Right thickness in the reconstruction + real, dimension(SZI_(G),SZJ_(G)), intent(in) :: h_N !< North edge thickness in the reconstruction !! [H ~> m or kg m-2]. real, dimension(SZI_(G)), intent(inout) :: vh !< Meridional mass or volume transport !! [H L2 T-1 ~> m3 s-1 or kg s-1]. @@ -1411,22 +1480,22 @@ subroutine merid_flux_layer(v, h, h_L, h_R, vh, dvhdv, visc_rem, dt, G, US, J, & if (v(i) > 0.0) then if (vol_CFL) then ; CFL = (v(i) * dt) * (G%dx_Cv(i,J) * G%IareaT(i,j)) else ; CFL = v(i) * dt * G%IdyT(i,j) ; endif - curv_3 = h_L(i,j) + h_R(i,j) - 2.0*h(i,j) - vh(i) = (G%dx_Cv(i,J)*por_face_areaV(i,J)) * v(i) * ( h_R(i,j) + CFL * & - (0.5*(h_L(i,j) - h_R(i,j)) + curv_3*(CFL - 1.5)) ) - h_marg = h_R(i,j) + CFL * ((h_L(i,j) - h_R(i,j)) + & + curv_3 = h_S(i,j) + h_N(i,j) - 2.0*h(i,j) + vh(i) = (G%dx_Cv(i,J)*por_face_areaV(i,J)) * v(i) * ( h_N(i,j) + CFL * & + (0.5*(h_S(i,j) - h_N(i,j)) + curv_3*(CFL - 1.5)) ) + h_marg = h_N(i,j) + CFL * ((h_S(i,j) - h_N(i,j)) + & 3.0*curv_3*(CFL - 1.0)) elseif (v(i) < 0.0) then if (vol_CFL) then ; CFL = (-v(i) * dt) * (G%dx_Cv(i,J) * G%IareaT(i,j+1)) else ; CFL = -v(i) * dt * G%IdyT(i,j+1) ; endif - curv_3 = h_L(i,j+1) + h_R(i,j+1) - 2.0*h(i,j+1) - vh(i) = (G%dx_Cv(i,J)*por_face_areaV(i,J)) * v(i) * ( h_L(i,j+1) + CFL * & - (0.5*(h_R(i,j+1)-h_L(i,j+1)) + curv_3*(CFL - 1.5)) ) - h_marg = h_L(i,j+1) + CFL * ((h_R(i,j+1)-h_L(i,j+1)) + & + curv_3 = h_S(i,j+1) + h_N(i,j+1) - 2.0*h(i,j+1) + vh(i) = (G%dx_Cv(i,J)*por_face_areaV(i,J)) * v(i) * ( h_S(i,j+1) + CFL * & + (0.5*(h_N(i,j+1)-h_S(i,j+1)) + curv_3*(CFL - 1.5)) ) + h_marg = h_S(i,j+1) + CFL * ((h_N(i,j+1)-h_S(i,j+1)) + & 3.0*curv_3*(CFL - 1.0)) else vh(i) = 0.0 - h_marg = 0.5 * (h_L(i,j+1) + h_R(i,j)) + h_marg = 0.5 * (h_S(i,j+1) + h_N(i,j)) endif dvhdv(i) = (G%dx_Cv(i,J)*por_face_areaV(i,J)) * h_marg * visc_rem(i) endif ; enddo @@ -1450,18 +1519,18 @@ subroutine merid_flux_layer(v, h, h_L, h_R, vh, dvhdv, visc_rem, dt, G, US, J, & endif end subroutine merid_flux_layer -!> Sets the effective interface thickness at each meridional velocity point, optionally scaling -!! back these thicknesses to account for viscosity and fractional open areas. -subroutine merid_face_thickness(v, h, h_L, h_R, h_v, dt, G, GV, US, LB, vol_CFL, & - marginal, OBC, por_face_areaV, visc_rem_v) +!> Sets the effective interface thickness associated with the fluxes at each meridional velocity point, +!! optionally scaling back these thicknesses to account for viscosity and fractional open areas. +subroutine meridional_flux_thickness(v, h, h_S, h_N, h_v, dt, G, GV, US, LB, vol_CFL, & + marginal, OBC, por_face_areaV, visc_rem_v) type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1]. real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h !< Layer thickness used to calculate fluxes, !! [H ~> m or kg m-2]. - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_L !< Left thickness in the reconstruction, + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_S !< South edge thickness in the reconstruction, !! [H ~> m or kg m-2]. - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_R !< Right thickness in the reconstruction, + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_N !< North edge thickness in the reconstruction, !! [H ~> m or kg m-2]. real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(inout) :: h_v !< Effective thickness at meridional faces, !! scaled down to account for the effects of @@ -1498,24 +1567,24 @@ subroutine merid_face_thickness(v, h, h_L, h_R, h_v, dt, G, GV, US, LB, vol_CFL, if (v(i,J,k) > 0.0) then if (vol_CFL) then ; CFL = (v(i,J,k) * dt) * (G%dx_Cv(i,J) * G%IareaT(i,j)) else ; CFL = v(i,J,k) * dt * G%IdyT(i,j) ; endif - curv_3 = h_L(i,j,k) + h_R(i,j,k) - 2.0*h(i,j,k) - h_avg = h_R(i,j,k) + CFL * (0.5*(h_L(i,j,k) - h_R(i,j,k)) + curv_3*(CFL - 1.5)) - h_marg = h_R(i,j,k) + CFL * ((h_L(i,j,k) - h_R(i,j,k)) + & + curv_3 = h_S(i,j,k) + h_N(i,j,k) - 2.0*h(i,j,k) + h_avg = h_N(i,j,k) + CFL * (0.5*(h_S(i,j,k) - h_N(i,j,k)) + curv_3*(CFL - 1.5)) + h_marg = h_N(i,j,k) + CFL * ((h_S(i,j,k) - h_N(i,j,k)) + & 3.0*curv_3*(CFL - 1.0)) elseif (v(i,J,k) < 0.0) then if (vol_CFL) then ; CFL = (-v(i,J,k)*dt) * (G%dx_Cv(i,J) * G%IareaT(i,j+1)) else ; CFL = -v(i,J,k) * dt * G%IdyT(i,j+1) ; endif - curv_3 = h_L(i,j+1,k) + h_R(i,j+1,k) - 2.0*h(i,j+1,k) - h_avg = h_L(i,j+1,k) + CFL * (0.5*(h_R(i,j+1,k)-h_L(i,j+1,k)) + curv_3*(CFL - 1.5)) - h_marg = h_L(i,j+1,k) + CFL * ((h_R(i,j+1,k)-h_L(i,j+1,k)) + & + curv_3 = h_S(i,j+1,k) + h_N(i,j+1,k) - 2.0*h(i,j+1,k) + h_avg = h_S(i,j+1,k) + CFL * (0.5*(h_N(i,j+1,k)-h_S(i,j+1,k)) + curv_3*(CFL - 1.5)) + h_marg = h_S(i,j+1,k) + CFL * ((h_N(i,j+1,k)-h_S(i,j+1,k)) + & 3.0*curv_3*(CFL - 1.0)) else - h_avg = 0.5 * (h_L(i,j+1,k) + h_R(i,j,k)) + h_avg = 0.5 * (h_S(i,j+1,k) + h_N(i,j,k)) ! The choice to use the arithmetic mean here is somewhat arbitrarily, but - ! it should be noted that h_L(i+1,j,k) and h_R(i,j,k) are usually the same. - h_marg = 0.5 * (h_L(i,j+1,k) + h_R(i,j,k)) - ! h_marg = (2.0 * h_L(i,j+1,k) * h_R(i,j,k)) / & - ! (h_L(i,j+1,k) + h_R(i,j,k) + GV%H_subroundoff) + ! it should be noted that h_S(i+1,j,k) and h_N(i,j,k) are usually the same. + h_marg = 0.5 * (h_S(i,j+1,k) + h_N(i,j,k)) + ! h_marg = (2.0 * h_S(i,j+1,k) * h_N(i,j,k)) / & + ! (h_S(i,j+1,k) + h_N(i,j,k) + GV%H_subroundoff) endif if (marginal) then ; h_v(i,J,k) = h_marg @@ -1568,10 +1637,10 @@ subroutine merid_face_thickness(v, h, h_L, h_R, h_v, dt, G, GV, US, LB, vol_CFL, enddo endif -end subroutine merid_face_thickness +end subroutine meridional_flux_thickness !> Returns the barotropic velocity adjustment that gives the desired barotropic (layer-summed) transport. -subroutine meridional_flux_adjust(v, h_in, h_L, h_R, vhbt, vh_tot_0, dvhdv_tot_0, & +subroutine meridional_flux_adjust(v, h_in, h_S, h_N, vhbt, vh_tot_0, dvhdv_tot_0, & dv, dv_max_CFL, dv_min_CFL, dt, G, GV, US, CS, visc_rem, & j, ish, ieh, do_I_in, por_face_areaV, vh_3d, OBC) type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. @@ -1581,9 +1650,9 @@ subroutine meridional_flux_adjust(v, h_in, h_L, h_R, vhbt, vh_tot_0, dvhdv_tot_0 real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & intent(in) :: h_in !< Layer thickness used to calculate fluxes [H ~> m or kg m-2]. real, dimension(SZI_(G),SZJ_(G),SZK_(GV)),& - intent(in) :: h_L !< Left thickness in the reconstruction [H ~> m or kg m-2]. + intent(in) :: h_S !< South edge thickness in the reconstruction [H ~> m or kg m-2]. real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & - intent(in) :: h_R !< Right thickness in the reconstruction [H ~> m or kg m-2]. + intent(in) :: h_N !< North edge thickness in the reconstruction [H ~> m or kg m-2]. real, dimension(SZI_(G),SZK_(GV)), intent(in) :: visc_rem !< Both the fraction of the momentum originally !! in a layer that remains after a time-step of viscosity, and the @@ -1693,7 +1762,7 @@ subroutine meridional_flux_adjust(v, h_in, h_L, h_R, vhbt, vh_tot_0, dvhdv_tot_0 if ((itt < max_itts) .or. present(vh_3d)) then ; do k=1,nz do i=ish,ieh ; v_new(i) = v(i,J,k) + dv(i) * visc_rem(i,k) ; enddo - call merid_flux_layer(v_new, h_in(:,:,k), h_L(:,:,k), h_R(:,:,k), & + call merid_flux_layer(v_new, h_in(:,:,k), h_S(:,:,k), h_N(:,:,k), & vh_aux(:,k), dvhdv(:,k), visc_rem(:,k), & dt, G, US, J, ish, ieh, do_I, CS%vol_CFL, por_face_areaV(:,:,k), OBC) enddo ; endif @@ -1723,7 +1792,7 @@ end subroutine meridional_flux_adjust !> Sets of a structure that describes the meridional barotropic volume or mass fluxes as a !! function of barotropic flow to agree closely with the sum of the layer's transports. -subroutine set_merid_BT_cont(v, h_in, h_L, h_R, BT_cont, vh_tot_0, dvhdv_tot_0, & +subroutine set_merid_BT_cont(v, h_in, h_S, h_N, BT_cont, vh_tot_0, dvhdv_tot_0, & dv_max_CFL, dv_min_CFL, dt, G, GV, US, CS, visc_rem, & visc_rem_max, j, ish, ieh, do_I, por_face_areaV) type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. @@ -1731,9 +1800,9 @@ subroutine set_merid_BT_cont(v, h_in, h_L, h_R, BT_cont, vh_tot_0, dvhdv_tot_0, real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1]. real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_in !< Layer thickness used to calculate fluxes, !! [H ~> m or kg m-2]. - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_L !< Left thickness in the reconstruction, + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_S !< South edge thickness in the reconstruction, !! [H ~> m or kg m-2]. - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_R !< Right thickness in the reconstruction, + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_N !< North edge thickness in the reconstruction, !! [H ~> m or kg m-2]. type(BT_cont_type), intent(inout) :: BT_cont !< A structure with elements !! that describe the effective open face areas as a function of barotropic flow. @@ -1800,7 +1869,7 @@ subroutine set_merid_BT_cont(v, h_in, h_L, h_R, BT_cont, vh_tot_0, dvhdv_tot_0, ! Diagnose the zero-transport correction, dv0. do i=ish,ieh ; zeros(i) = 0.0 ; enddo - call meridional_flux_adjust(v, h_in, h_L, h_R, zeros, vh_tot_0, dvhdv_tot_0, dv0, & + call meridional_flux_adjust(v, h_in, h_S, h_N, zeros, vh_tot_0, dvhdv_tot_0, dv0, & dv_max_CFL, dv_min_CFL, dt, G, GV, US, CS, visc_rem, & j, ish, ieh, do_I, por_face_areaV) @@ -1842,11 +1911,11 @@ subroutine set_merid_BT_cont(v, h_in, h_L, h_R, BT_cont, vh_tot_0, dvhdv_tot_0, v_R(i) = v(I,j,k) + dvR(i) * visc_rem(i,k) v_0(i) = v(I,j,k) + dv0(i) * visc_rem(i,k) endif ; enddo - call merid_flux_layer(v_0, h_in(:,:,k), h_L(:,:,k), h_R(:,:,k), vh_0, dvhdv_0, & + call merid_flux_layer(v_0, h_in(:,:,k), h_S(:,:,k), h_N(:,:,k), vh_0, dvhdv_0, & visc_rem(:,k), dt, G, US, J, ish, ieh, do_I, CS%vol_CFL, por_face_areaV(:,:,k)) - call merid_flux_layer(v_L, h_in(:,:,k), h_L(:,:,k), h_R(:,:,k), vh_L, dvhdv_L, & + call merid_flux_layer(v_L, h_in(:,:,k), h_S(:,:,k), h_N(:,:,k), vh_L, dvhdv_L, & visc_rem(:,k), dt, G, US, J, ish, ieh, do_I, CS%vol_CFL, por_face_areaV(:,:,k)) - call merid_flux_layer(v_R, h_in(:,:,k), h_L(:,:,k), h_R(:,:,k), vh_R, dvhdv_R, & + call merid_flux_layer(v_R, h_in(:,:,k), h_S(:,:,k), h_N(:,:,k), vh_R, dvhdv_R, & visc_rem(:,k), dt, G, US, J, ish, ieh, do_I, CS%vol_CFL, por_face_areaV(:,:,k)) do i=ish,ieh ; if (do_I(i)) then FAmt_0(i) = FAmt_0(i) + dvhdv_0(i) @@ -1887,12 +1956,12 @@ subroutine set_merid_BT_cont(v, h_in, h_L, h_R, BT_cont, vh_tot_0, dvhdv_tot_0, end subroutine set_merid_BT_cont !> Calculates left/right edge values for PPM reconstruction. -subroutine PPM_reconstruction_x(h_in, h_L, h_R, G, LB, h_min, monotonic, simple_2nd, OBC) +subroutine PPM_reconstruction_x(h_in, h_W, h_E, G, LB, h_min, monotonic, simple_2nd, OBC) type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. real, dimension(SZI_(G),SZJ_(G)), intent(in) :: h_in !< Layer thickness [H ~> m or kg m-2]. - real, dimension(SZI_(G),SZJ_(G)), intent(out) :: h_L !< Left thickness in the reconstruction, + real, dimension(SZI_(G),SZJ_(G)), intent(out) :: h_W !< West edge thickness in the reconstruction, !! [H ~> m or kg m-2]. - real, dimension(SZI_(G),SZJ_(G)), intent(out) :: h_R !< Right thickness in the reconstruction, + real, dimension(SZI_(G),SZJ_(G)), intent(out) :: h_E !< East edge thickness in the reconstruction, !! [H ~> m or kg m-2]. type(loop_bounds_type), intent(in) :: LB !< Active loop bounds structure. real, intent(in) :: h_min !< The minimum thickness @@ -1943,8 +2012,8 @@ subroutine PPM_reconstruction_x(h_in, h_L, h_R, G, LB, h_min, monotonic, simple_ do j=jsl,jel ; do i=isl,iel h_im1 = G%mask2dT(i-1,j) * h_in(i-1,j) + (1.0-G%mask2dT(i-1,j)) * h_in(i,j) h_ip1 = G%mask2dT(i+1,j) * h_in(i+1,j) + (1.0-G%mask2dT(i+1,j)) * h_in(i,j) - h_L(i,j) = 0.5*( h_im1 + h_in(i,j) ) - h_R(i,j) = 0.5*( h_ip1 + h_in(i,j) ) + h_W(i,j) = 0.5*( h_im1 + h_in(i,j) ) + h_E(i,j) = 0.5*( h_ip1 + h_in(i,j) ) enddo ; enddo else do j=jsl,jel ; do i=isl-1,iel+1 @@ -1984,8 +2053,8 @@ subroutine PPM_reconstruction_x(h_in, h_L, h_R, G, LB, h_min, monotonic, simple_ h_im1 = G%mask2dT(i-1,j) * h_in(i-1,j) + (1.0-G%mask2dT(i-1,j)) * h_in(i,j) h_ip1 = G%mask2dT(i+1,j) * h_in(i+1,j) + (1.0-G%mask2dT(i+1,j)) * h_in(i,j) ! Left/right values following Eq. B2 in Lin 1994, MWR (132) - h_L(i,j) = 0.5*( h_im1 + h_in(i,j) ) + oneSixth*( slp(i-1,j) - slp(i,j) ) - h_R(i,j) = 0.5*( h_ip1 + h_in(i,j) ) + oneSixth*( slp(i,j) - slp(i+1,j) ) + h_W(i,j) = 0.5*( h_im1 + h_in(i,j) ) + oneSixth*( slp(i-1,j) - slp(i,j) ) + h_E(i,j) = 0.5*( h_ip1 + h_in(i,j) ) + oneSixth*( slp(i,j) - slp(i+1,j) ) enddo ; enddo endif @@ -1996,39 +2065,39 @@ subroutine PPM_reconstruction_x(h_in, h_L, h_R, G, LB, h_min, monotonic, simple_ if (segment%direction == OBC_DIRECTION_E) then I=segment%HI%IsdB do j=segment%HI%jsd,segment%HI%jed - h_L(i+1,j) = h_in(i,j) - h_R(i+1,j) = h_in(i,j) - h_L(i,j) = h_in(i,j) - h_R(i,j) = h_in(i,j) + h_W(i+1,j) = h_in(i,j) + h_E(i+1,j) = h_in(i,j) + h_W(i,j) = h_in(i,j) + h_E(i,j) = h_in(i,j) enddo elseif (segment%direction == OBC_DIRECTION_W) then I=segment%HI%IsdB do j=segment%HI%jsd,segment%HI%jed - h_L(i,j) = h_in(i+1,j) - h_R(i,j) = h_in(i+1,j) - h_L(i+1,j) = h_in(i+1,j) - h_R(i+1,j) = h_in(i+1,j) + h_W(i,j) = h_in(i+1,j) + h_E(i,j) = h_in(i+1,j) + h_W(i+1,j) = h_in(i+1,j) + h_E(i+1,j) = h_in(i+1,j) enddo endif enddo endif if (monotonic) then - call PPM_limit_CW84(h_in, h_L, h_R, G, isl, iel, jsl, jel) + call PPM_limit_CW84(h_in, h_W, h_E, G, isl, iel, jsl, jel) else - call PPM_limit_pos(h_in, h_L, h_R, h_min, G, isl, iel, jsl, jel) + call PPM_limit_pos(h_in, h_W, h_E, h_min, G, isl, iel, jsl, jel) endif return end subroutine PPM_reconstruction_x !> Calculates left/right edge values for PPM reconstruction. -subroutine PPM_reconstruction_y(h_in, h_L, h_R, G, LB, h_min, monotonic, simple_2nd, OBC) +subroutine PPM_reconstruction_y(h_in, h_S, h_N, G, LB, h_min, monotonic, simple_2nd, OBC) type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. real, dimension(SZI_(G),SZJ_(G)), intent(in) :: h_in !< Layer thickness [H ~> m or kg m-2]. - real, dimension(SZI_(G),SZJ_(G)), intent(out) :: h_L !< Left thickness in the reconstruction, + real, dimension(SZI_(G),SZJ_(G)), intent(out) :: h_S !< South edge thickness in the reconstruction, !! [H ~> m or kg m-2]. - real, dimension(SZI_(G),SZJ_(G)), intent(out) :: h_R !< Right thickness in the reconstruction, + real, dimension(SZI_(G),SZJ_(G)), intent(out) :: h_N !< North edge thickness in the reconstruction, !! [H ~> m or kg m-2]. type(loop_bounds_type), intent(in) :: LB !< Active loop bounds structure. real, intent(in) :: h_min !< The minimum thickness @@ -2079,8 +2148,8 @@ subroutine PPM_reconstruction_y(h_in, h_L, h_R, G, LB, h_min, monotonic, simple_ do j=jsl,jel ; do i=isl,iel h_jm1 = G%mask2dT(i,j-1) * h_in(i,j-1) + (1.0-G%mask2dT(i,j-1)) * h_in(i,j) h_jp1 = G%mask2dT(i,j+1) * h_in(i,j+1) + (1.0-G%mask2dT(i,j+1)) * h_in(i,j) - h_L(i,j) = 0.5*( h_jm1 + h_in(i,j) ) - h_R(i,j) = 0.5*( h_jp1 + h_in(i,j) ) + h_S(i,j) = 0.5*( h_jm1 + h_in(i,j) ) + h_N(i,j) = 0.5*( h_jp1 + h_in(i,j) ) enddo ; enddo else do j=jsl-1,jel+1 ; do i=isl,iel @@ -2118,8 +2187,8 @@ subroutine PPM_reconstruction_y(h_in, h_L, h_R, G, LB, h_min, monotonic, simple_ h_jm1 = G%mask2dT(i,j-1) * h_in(i,j-1) + (1.0-G%mask2dT(i,j-1)) * h_in(i,j) h_jp1 = G%mask2dT(i,j+1) * h_in(i,j+1) + (1.0-G%mask2dT(i,j+1)) * h_in(i,j) ! Left/right values following Eq. B2 in Lin 1994, MWR (132) - h_L(i,j) = 0.5*( h_jm1 + h_in(i,j) ) + oneSixth*( slp(i,j-1) - slp(i,j) ) - h_R(i,j) = 0.5*( h_jp1 + h_in(i,j) ) + oneSixth*( slp(i,j) - slp(i,j+1) ) + h_S(i,j) = 0.5*( h_jm1 + h_in(i,j) ) + oneSixth*( slp(i,j-1) - slp(i,j) ) + h_N(i,j) = 0.5*( h_jp1 + h_in(i,j) ) + oneSixth*( slp(i,j) - slp(i,j+1) ) enddo ; enddo endif @@ -2130,27 +2199,27 @@ subroutine PPM_reconstruction_y(h_in, h_L, h_R, G, LB, h_min, monotonic, simple_ if (segment%direction == OBC_DIRECTION_N) then J=segment%HI%JsdB do i=segment%HI%isd,segment%HI%ied - h_L(i,j+1) = h_in(i,j) - h_R(i,j+1) = h_in(i,j) - h_L(i,j) = h_in(i,j) - h_R(i,j) = h_in(i,j) + h_S(i,j+1) = h_in(i,j) + h_N(i,j+1) = h_in(i,j) + h_S(i,j) = h_in(i,j) + h_N(i,j) = h_in(i,j) enddo elseif (segment%direction == OBC_DIRECTION_S) then J=segment%HI%JsdB do i=segment%HI%isd,segment%HI%ied - h_L(i,j) = h_in(i,j+1) - h_R(i,j) = h_in(i,j+1) - h_L(i,j+1) = h_in(i,j+1) - h_R(i,j+1) = h_in(i,j+1) + h_S(i,j) = h_in(i,j+1) + h_N(i,j) = h_in(i,j+1) + h_S(i,j+1) = h_in(i,j+1) + h_N(i,j+1) = h_in(i,j+1) enddo endif enddo endif if (monotonic) then - call PPM_limit_CW84(h_in, h_L, h_R, G, isl, iel, jsl, jel) + call PPM_limit_CW84(h_in, h_S, h_N, G, isl, iel, jsl, jel) else - call PPM_limit_pos(h_in, h_L, h_R, h_min, G, isl, iel, jsl, jel) + call PPM_limit_pos(h_in, h_S, h_N, h_min, G, isl, iel, jsl, jel) endif return From d3496fee35eeb5b16cbe0e02afe6940a6ad94da0 Mon Sep 17 00:00:00 2001 From: Robert Hallberg Date: Thu, 16 Nov 2023 11:41:27 -0500 Subject: [PATCH 04/22] +Call zonal_edge_thickness outside of zonal_mass_flux Moved the calls to zonal_edge_thickness and meridional_edge_thickness out of zonal_mass_flux and meridional_mass_flux to facilitate the reuse at some later date of the PPM thickness reconstructions. As a part of this, there are new edge thickness arguments to zonal_mass_flux and meridional_mass_flux. The interfaces to zonal_edge_thickness and meridional_edge_thickness are new publicly visible and are used in MOM_continuity. This commits also changes the name of the loop_bounds_type to cont_loop_bounds_type and makes it public but opaque adds the publicly visible function set_continuity_loop_bounds to enable the continuity loop bounds to be set from outside of the continuity_PPM module. Reflecting these changes there are new calls to zonal_edge_thickness and meridional_edge_thickness in the 3 routines in MOM_continuity and in continuity_PPM, and new arrays for holding the edge thicknesses in these routines. All answers are bitwise identical, but there are new publicly visible interfaces and types and changes to other publicly visible interfaces. However, no changes are required outside of MOM_continuity and MOM_continuity_PPM. --- src/core/MOM_continuity.F90 | 39 ++++-- src/core/MOM_continuity_PPM.F90 | 231 ++++++++++++++++++-------------- 2 files changed, 156 insertions(+), 114 deletions(-) diff --git a/src/core/MOM_continuity.F90 b/src/core/MOM_continuity.F90 index 44422d5e47..116bf8f195 100644 --- a/src/core/MOM_continuity.F90 +++ b/src/core/MOM_continuity.F90 @@ -7,6 +7,7 @@ module MOM_continuity use MOM_continuity_PPM, only : continuity_stencil=>continuity_PPM_stencil use MOM_continuity_PPM, only : continuity_init=>continuity_PPM_init use MOM_continuity_PPM, only : continuity_CS=>continuity_PPM_CS +use MOM_continuity_PPM, only : zonal_edge_thickness, meridional_edge_thickness use MOM_continuity_PPM, only : zonal_mass_flux, meridional_mass_flux use MOM_diag_mediator, only : time_type use MOM_grid, only : ocean_grid_type @@ -56,9 +57,17 @@ subroutine continuity_3d_fluxes(u, v, h, uh, vh, dt, G, GV, US, CS, OBC, pbv) type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. type(porous_barrier_type), intent(in) :: pbv !< porous barrier fractional cell metrics - call zonal_mass_flux(u, h, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU) + ! Local variables + real :: h_W(SZI_(G),SZJ_(G),SZK_(GV)) ! West edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] + real :: h_E(SZI_(G),SZJ_(G),SZK_(GV)) ! East edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] + real :: h_S(SZI_(G),SZJ_(G),SZK_(GV)) ! South edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] + real :: h_N(SZI_(G),SZJ_(G),SZK_(GV)) ! North edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] + + call zonal_edge_thickness(h, h_W, h_E, G, GV, US, CS, OBC) + call zonal_mass_flux(u, h, h_W, h_E, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU) - call meridional_mass_flux(v, h, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV) + call meridional_edge_thickness(h, h_S, h_N, G, GV, US, CS, OBC) + call meridional_mass_flux(v, h, h_S, h_N, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV) end subroutine continuity_3d_fluxes @@ -88,18 +97,22 @@ subroutine continuity_2d_fluxes(u, v, h, uhbt, vhbt, dt, G, GV, US, CS, OBC, pbv type(porous_barrier_type), intent(in) :: pbv !< porous barrier fractional cell metrics ! Local variables - real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: uh ! Thickness fluxes through zonal faces, - ! u*h*dy [H L2 T-1 ~> m3 s-1 or kg s-1]. - real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: vh ! Thickness fluxes through meridional faces, - ! v*h*dx [H L2 T-1 ~> m3 s-1 or kg s-1]. + real :: h_W(SZI_(G),SZJ_(G),SZK_(GV)) ! West edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] + real :: h_E(SZI_(G),SZJ_(G),SZK_(GV)) ! East edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] + real :: h_S(SZI_(G),SZJ_(G),SZK_(GV)) ! South edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] + real :: h_N(SZI_(G),SZJ_(G),SZK_(GV)) ! North edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] + real :: uh(SZIB_(G),SZJ_(G),SZK_(GV)) ! Thickness fluxes through zonal faces, u*h*dy [H L2 T-1 ~> m3 s-1 or kg s-1] + real :: vh(SZI_(G),SZJB_(G),SZK_(GV)) ! Thickness fluxes through v-point faces, v*h*dx [H L2 T-1 ~> m3 s-1 or kg s-1] integer :: i, j, k uh(:,:,:) = 0.0 vh(:,:,:) = 0.0 - call zonal_mass_flux(u, h, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU) + call zonal_edge_thickness(h, h_W, h_E, G, GV, US, CS, OBC) + call zonal_mass_flux(u, h, h_W, h_E, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU) - call meridional_mass_flux(v, h, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV) + call meridional_edge_thickness(h, h_S, h_N, G, GV, US, CS, OBC) + call meridional_mass_flux(v, h, h_S, h_N, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV) uhbt(:,:) = 0.0 vhbt(:,:) = 0.0 @@ -167,16 +180,22 @@ subroutine continuity_adjust_vel(u, v, h, dt, G, GV, US, CS, OBC, pbv, uhbt, vhb !! u*h*dy [H L2 T-1 ~> m3 s-1 or kg s-1]. real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: vh !< Volume flux through meridional faces = !! v*h*dx [H L2 T-1 ~> m3 s-1 or kg s-1]. + real :: h_W(SZI_(G),SZJ_(G),SZK_(GV)) ! West edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] + real :: h_E(SZI_(G),SZJ_(G),SZK_(GV)) ! East edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] + real :: h_S(SZI_(G),SZJ_(G),SZK_(GV)) ! South edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] + real :: h_N(SZI_(G),SZJ_(G),SZK_(GV)) ! North edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] ! It might not be necessary to separate the input velocity array from the adjusted velocities, ! but it seems safer to do so, even if it might be less efficient. u_in(:,:,:) = u(:,:,:) v_in(:,:,:) = v(:,:,:) - call zonal_mass_flux(u_in, h, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU, & + call zonal_edge_thickness(h, h_W, h_E, G, GV, US, CS, OBC) + call zonal_mass_flux(u_in, h, h_W, h_E, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU, & uhbt=uhbt, visc_rem_u=visc_rem_u, u_cor=u) - call meridional_mass_flux(v_in, h, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV, & + call meridional_edge_thickness(h, h_S, h_N, G, GV, US, CS, OBC) + call meridional_mass_flux(v_in, h, h_S, h_N, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV, & vhbt=vhbt, visc_rem_v=visc_rem_v, v_cor=v) end subroutine continuity_adjust_vel diff --git a/src/core/MOM_continuity_PPM.F90 b/src/core/MOM_continuity_PPM.F90 index 415d04dd36..0abc0c5568 100644 --- a/src/core/MOM_continuity_PPM.F90 +++ b/src/core/MOM_continuity_PPM.F90 @@ -22,6 +22,7 @@ module MOM_continuity_PPM public zonal_mass_flux, meridional_mass_flux public zonal_flux_thickness, meridional_flux_thickness public zonal_edge_thickness, meridional_edge_thickness +public set_continuity_loop_bounds !>@{ CPU time clock IDs integer :: id_clock_update, id_clock_correct @@ -63,11 +64,11 @@ module MOM_continuity_PPM end type continuity_PPM_CS !> A container for loop bounds -type :: loop_bounds_type ; private +type, public :: cont_loop_bounds_type ; private !>@{ Loop bounds integer :: ish, ieh, jsh, jeh !>@} -end type loop_bounds_type +end type cont_loop_bounds_type contains @@ -125,8 +126,12 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhb !! the effective open face areas as a function of barotropic flow. ! Local variables + real :: h_W(SZI_(G),SZJ_(G),SZK_(GV)) ! West edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] + real :: h_E(SZI_(G),SZJ_(G),SZK_(GV)) ! East edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] + real :: h_S(SZI_(G),SZJ_(G),SZK_(GV)) ! South edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] + real :: h_N(SZI_(G),SZJ_(G),SZK_(GV)) ! North edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] real :: h_min ! The minimum layer thickness [H ~> m or kg m-2]. h_min could be 0. - type(loop_bounds_type) :: LB + type(cont_loop_bounds_type) :: LB integer :: is, ie, js, je, nz, stencil integer :: i, j, k @@ -147,10 +152,13 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhb stencil = continuity_PPM_stencil(CS) if (x_first) then - ! First, advect zonally. - LB%ish = G%isc ; LB%ieh = G%iec - LB%jsh = G%jsc-stencil ; LB%jeh = G%jec+stencil - call zonal_mass_flux(u, hin, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU, & + ! First advect zonally, with loop bounds that accomodate the subsequent meridional advection. + LB = set_continuity_loop_bounds(G, CS, .false., .true.) + + call cpu_clock_begin(id_clock_update) + call zonal_edge_thickness(hin, h_W, h_E, G, GV, US, CS, OBC, LB) + call cpu_clock_end(id_clock_update) + call zonal_mass_flux(u, hin, h_W, h_E, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU, & LB, uhbt, visc_rem_u, u_cor, BT_cont) call cpu_clock_begin(id_clock_update) @@ -160,13 +168,14 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhb ! Uncomment this line to prevent underflow. ! if (h(i,j,k) < h_min) h(i,j,k) = h_min enddo ; enddo ; enddo - call cpu_clock_end(id_clock_update) - LB%ish = G%isc ; LB%ieh = G%iec ; LB%jsh = G%jsc ; LB%jeh = G%jec + LB = set_continuity_loop_bounds(G, CS, .false., .false.) - ! Now advect meridionally, using the updated thicknesses to determine - ! the fluxes. - call meridional_mass_flux(v, h, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV, & + ! Now advect meridionally, using the updated thicknesses to determine the fluxes. + call meridional_edge_thickness(h, h_S, h_N, G, GV, US, CS, OBC, LB) + call cpu_clock_end(id_clock_update) + + call meridional_mass_flux(v, h, h_S, h_N, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV, & LB, vhbt, visc_rem_v, v_cor, BT_cont) call cpu_clock_begin(id_clock_update) @@ -179,11 +188,13 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhb call cpu_clock_end(id_clock_update) else ! .not. x_first - ! First, advect meridionally, so set the loop bounds accordingly. - LB%ish = G%isc-stencil ; LB%ieh = G%iec+stencil - LB%jsh = G%jsc ; LB%jeh = G%jec + ! First advect meridionally, with loop bounds that accomodate the subsequent zonal advection. + LB = set_continuity_loop_bounds(G, CS, .true., .false.) - call meridional_mass_flux(v, hin, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV, & + call cpu_clock_begin(id_clock_update) + call meridional_edge_thickness(hin, h_S, h_N, G, GV, US, CS, OBC, LB) + call cpu_clock_end(id_clock_update) + call meridional_mass_flux(v, hin, h_S, h_N, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV, & LB, vhbt, visc_rem_v, v_cor, BT_cont) call cpu_clock_begin(id_clock_update) @@ -191,12 +202,13 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhb do k=1,nz ; do j=LB%jsh,LB%jeh ; do i=LB%ish,LB%ieh h(i,j,k) = hin(i,j,k) - dt * G%IareaT(i,j) * (vh(i,J,k) - vh(i,J-1,k)) enddo ; enddo ; enddo - call cpu_clock_end(id_clock_update) - ! Now advect zonally, using the updated thicknesses to determine - ! the fluxes. - LB%ish = G%isc ; LB%ieh = G%iec ; LB%jsh = G%jsc ; LB%jeh = G%jec - call zonal_mass_flux(u, h, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU, & + LB = set_continuity_loop_bounds(G, CS, .false., .false.) + + ! Now advect zonally, using the updated thicknesses to determine the fluxes. + call zonal_edge_thickness(h, h_W, h_E, G, GV, US, CS, OBC, LB) + call cpu_clock_end(id_clock_update) + call zonal_mass_flux(u, h, h_W, h_E, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU, & LB, uhbt, visc_rem_u, u_cor, BT_cont) call cpu_clock_begin(id_clock_update) @@ -225,11 +237,11 @@ subroutine zonal_edge_thickness(h_in, h_W, h_E, G, GV, US, CS, OBC, LB_in) type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type type(continuity_PPM_CS), intent(in) :: CS !< This module's control structure. type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. - type(loop_bounds_type), & + type(cont_loop_bounds_type), & optional, intent(in) :: LB_in !< Loop bounds structure. ! Local variables - type(loop_bounds_type) :: LB + type(cont_loop_bounds_type) :: LB integer :: i, j, k, ish, ieh, jsh, jeh, nz if (present(LB_in)) then @@ -268,11 +280,11 @@ subroutine meridional_edge_thickness(h_in, h_S, h_N, G, GV, US, CS, OBC, LB_in) type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type type(continuity_PPM_CS), intent(in) :: CS !< This module's control structure. type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. - type(loop_bounds_type), & + type(cont_loop_bounds_type), & optional, intent(in) :: LB_in !< Loop bounds structure. ! Local variables - type(loop_bounds_type) :: LB + type(cont_loop_bounds_type) :: LB integer :: i, j, k, ish, ieh, jsh, jeh, nz if (present(LB_in)) then @@ -299,7 +311,7 @@ end subroutine meridional_edge_thickness !> Calculates the mass or volume fluxes through the zonal faces, and other related quantities. -subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, & +subroutine zonal_mass_flux(u, h_in, h_W, h_E, uh, dt, G, GV, US, CS, OBC, por_face_areaU, & LB_in, uhbt, visc_rem_u, u_cor, BT_cont) type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. @@ -307,6 +319,10 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]. real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & intent(in) :: h_in !< Layer thickness used to calculate fluxes [H ~> m or kg m-2]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + intent(in) :: h_W !< Western edge thicknesses [H ~> m or kg m-2]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + intent(in) :: h_E !< Eastern edge thicknesses [H ~> m or kg m-2]. real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & intent(out) :: uh !< Volume flux through zonal faces = u*h*dy !! [H L2 T-1 ~> m3 s-1 or kg s-1]. @@ -316,7 +332,7 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. real, dimension(SZIB_(G), SZJ_(G), SZK_(G)), & intent(in) :: por_face_areaU !< fractional open area of U-faces [nondim] - type(loop_bounds_type), & + type(cont_loop_bounds_type), & optional, intent(in) :: LB_in !< Loop bounds structure. real, dimension(SZIB_(G),SZJ_(G)), & optional, intent(in) :: uhbt !< The summed volume flux through zonal faces @@ -336,7 +352,6 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, ! Local variables real, dimension(SZIB_(G),SZK_(GV)) :: duhdu ! Partial derivative of uh with u [H L ~> m2 or kg m-1]. - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: h_W, h_E ! Left and right face thicknesses [H ~> m or kg m-2]. real, dimension(SZIB_(G)) :: & du, & ! Corrective barotropic change in the velocity [L T-1 ~> m s-1]. du_min_CFL, & ! Lower limit on du correction to avoid CFL violations [L T-1 ~> m s-1] @@ -355,7 +370,7 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, real :: I_dt ! 1.0 / dt [T-1 ~> s-1]. real :: du_lim ! The velocity change that give a relative CFL of 1 [L T-1 ~> m s-1]. real :: dx_E, dx_W ! Effective x-grid spacings to the east and west [L ~> m]. - type(loop_bounds_type) :: LB + type(cont_loop_bounds_type) :: LB integer :: i, j, k, ish, ieh, jsh, jeh, n, nz integer :: l_seg logical :: local_specified_BC, use_visc_rem, set_BT_cont, any_simple_OBC @@ -382,11 +397,6 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, I_dt = 1.0 / dt if (CS%aggress_adjust) CFL_dt = I_dt - call cpu_clock_begin(id_clock_update) - ! This sets h_W and h_E. - call zonal_edge_thickness(h_in, h_W, h_E, G, GV, US, CS, OBC, LB) - call cpu_clock_end(id_clock_update) - call cpu_clock_begin(id_clock_correct) if (.not.use_visc_rem) visc_rem(:,:) = 1.0 !$OMP parallel do default(none) shared(ish,ieh,jsh,jeh,nz,u,h_in,h_W,h_E,use_visc_rem,visc_rem_u, & @@ -410,8 +420,7 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, if (local_specified_BC) then do I=ish-1,ieh ; if (OBC%segnum_u(I,j) /= OBC_NONE) then l_seg = OBC%segnum_u(I,j) - if (OBC%segment(l_seg)%specified) & - uh(I,j,k) = OBC%segment(l_seg)%normal_trans(I,j,k) + if (OBC%segment(l_seg)%specified) uh(I,j,k) = OBC%segment(l_seg)%normal_trans(I,j,k) endif ; enddo endif enddo @@ -508,8 +517,7 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, ! Avoid reconciling barotropic/baroclinic transports if transport is specified is_simple = .false. - if (l_seg /= OBC_NONE) & - is_simple = OBC%segment(l_seg)%specified + if (l_seg /= OBC_NONE) is_simple = OBC%segment(l_seg)%specified do_I(I) = .not. (l_seg /= OBC_NONE .and. is_simple) any_simple_OBC = any_simple_OBC .or. is_simple enddo ; else ; do I=ish-1,ieh @@ -525,11 +533,9 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, if (present(u_cor)) then ; do k=1,nz do I=ish-1,ieh ; u_cor(I,j,k) = u(I,j,k) + du(I) * visc_rem(I,k) ; enddo if (local_specified_BC) then ; do I=ish-1,ieh - l_seg = OBC%segnum_u(I,j) - - if (l_seg /= OBC_NONE) then - if (OBC%segment(l_seg)%specified) & - u_cor(I,j,k) = OBC%segment(l_seg)%normal_vel(I,j,k) + if (OBC%segnum_u(I,j) /= OBC_NONE) then + l_seg = OBC%segnum_u(I,j) + if (OBC%segment(l_seg)%specified) u_cor(I,j,k) = OBC%segment(l_seg)%normal_vel(I,j,k) endif enddo ; endif enddo ; endif ! u-corrected @@ -542,11 +548,8 @@ subroutine zonal_mass_flux(u, h_in, uh, dt, G, GV, US, CS, OBC, por_face_areaU, visc_rem_max, j, ish, ieh, do_I, por_face_areaU) if (any_simple_OBC) then do I=ish-1,ieh - l_seg = OBC%segnum_u(I,j) - do_I(I) = .false. - if (l_seg /= OBC_NONE) & - do_I(I) = OBC%segment(l_seg)%specified + if (OBC%segnum_u(I,j) /= OBC_NONE) do_I(I) = OBC%segment(OBC%segnum_u(I,j))%specified if (do_I(I)) FAuI(I) = GV%H_subroundoff*G%dy_Cu(I,j) enddo @@ -671,21 +674,18 @@ subroutine zonal_flux_layer(u, h, h_W, h_E, uh, duhdu, visc_rem, dt, G, US, j, & endif ; enddo if (local_open_BC) then - do I=ish-1,ieh ; if (do_I(I)) then + do I=ish-1,ieh ; if (do_I(I)) then ; if (OBC%segnum_u(I,j) /= OBC_NONE) then l_seg = OBC%segnum_u(I,j) - - if (l_seg /= OBC_NONE) then - if (OBC%segment(l_seg)%open) then - if (OBC%segment(l_seg)%direction == OBC_DIRECTION_E) then - uh(I) = (G%dy_Cu(I,j) * por_face_areaU(I)) * u(I) * h(i) - duhdu(I) = (G%dy_Cu(I,j) * por_face_areaU(I)) * h(i) * visc_rem(I) - else - uh(I) = (G%dy_Cu(I,j) * por_face_areaU(I)) * u(I) * h(i+1) - duhdu(I) = (G%dy_Cu(I,j)* por_face_areaU(I)) * h(i+1) * visc_rem(I) - endif + if (OBC%segment(l_seg)%open) then + if (OBC%segment(l_seg)%direction == OBC_DIRECTION_E) then + uh(I) = (G%dy_Cu(I,j) * por_face_areaU(I)) * u(I) * h(i) + duhdu(I) = (G%dy_Cu(I,j) * por_face_areaU(I)) * h(i) * visc_rem(I) + else + uh(I) = (G%dy_Cu(I,j) * por_face_areaU(I)) * u(I) * h(i+1) + duhdu(I) = (G%dy_Cu(I,j)* por_face_areaU(I)) * h(i+1) * visc_rem(I) endif endif - endif ; enddo + endif ; endif ; enddo endif end subroutine zonal_flux_layer @@ -708,7 +708,7 @@ subroutine zonal_flux_thickness(u, h, h_W, h_E, h_u, dt, G, GV, US, LB, vol_CFL, !! [H ~> m or kg m-2]. real, intent(in) :: dt !< Time increment [T ~> s]. type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type - type(loop_bounds_type), intent(in) :: LB !< Loop bounds structure. + type(cont_loop_bounds_type), intent(in) :: LB !< Loop bounds structure. logical, intent(in) :: vol_CFL !< If true, rescale the ratio !! of face areas to the cell areas when estimating the CFL number. logical, intent(in) :: marginal !< If true, report the @@ -1128,43 +1128,44 @@ subroutine set_zonal_BT_cont(u, h_in, h_W, h_E, BT_cont, uh_tot_0, duhdu_tot_0, end subroutine set_zonal_BT_cont !> Calculates the mass or volume fluxes through the meridional faces, and other related quantities. -subroutine meridional_mass_flux(v, h_in, vh, dt, G, GV, US, CS, OBC, por_face_areaV, & +subroutine meridional_mass_flux(v, h_in, h_S, h_N, vh, dt, G, GV, US, CS, OBC, por_face_areaV, & LB_in, vhbt, visc_rem_v, v_cor, BT_cont) - type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. - type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. - real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1] - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_in !< Layer thickness used to - !! calculate fluxes [H ~> m or kg m-2] - real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(out) :: vh !< Volume flux through meridional - !! faces = v*h*dx [H L2 T-1 ~> m3 s-1 or kg s-1] - real, intent(in) :: dt !< Time increment [T ~> s]. - type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type - type(continuity_PPM_CS), intent(in) :: CS !< This module's control structure.G - type(ocean_OBC_type), pointer :: OBC !< Open boundary condition type - !! specifies whether, where, and what open boundary conditions are used. - real, dimension(SZI_(G),SZJB_(G),SZK_(G)), & - intent(in) :: por_face_areaV !< fractional open area of V-faces [nondim] - type(loop_bounds_type), & - optional, intent(in) :: LB_in !< Loop bounds structure. - real, dimension(SZI_(G),SZJB_(G)), optional, intent(in) :: vhbt !< The summed volume flux through - !< meridional faces [H L2 T-1 ~> m3 s-1 or kg s-1]. + type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. + type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1] + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_in !< Layer thickness used to + !! calculate fluxes [H ~> m or kg m-2] + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_S !< South edge thickness in the + !! reconstruction [H ~> m or kg m-2]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_N !< North edge thickness in the + !! reconstruction [H ~> m or kg m-2]. + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(out) :: vh !< Volume flux through meridional + !! faces = v*h*dx [H L2 T-1 ~> m3 s-1 or kg s-1] + real, intent(in) :: dt !< Time increment [T ~> s]. + type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type + type(continuity_PPM_CS), intent(in) :: CS !< This module's control structure.G + type(ocean_OBC_type), pointer :: OBC !< Open boundary condition type + !! specifies whether, where, and what + !! open boundary conditions are used. + real, dimension(SZI_(G),SZJB_(G),SZK_(G)), intent(in) :: por_face_areaV !< fractional open area of V-faces [nondim] + type(cont_loop_bounds_type), optional, intent(in) :: LB_in !< Loop bounds structure. + real, dimension(SZI_(G),SZJB_(G)), optional, intent(in) :: vhbt !< The summed volume flux through meridional + !! faces [H L2 T-1 ~> m3 s-1 or kg s-1]. real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & - optional, intent(in) :: visc_rem_v !< Both the fraction of the momentum + optional, intent(in) :: visc_rem_v !< Both the fraction of the momentum !! originally in a layer that remains after a time-step of viscosity, !! and the fraction of a time-step's worth of a barotropic acceleration !! that a layer experiences after viscosity is applied [nondim]. !! Visc_rem_v is between 0 (at the bottom) and 1 (far above the bottom). real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & - optional, intent(out) :: v_cor + optional, intent(out) :: v_cor !< The meridional velocities (v with a barotropic correction) !! that give vhbt as the depth-integrated transport [L T-1 ~> m s-1]. - type(BT_cont_type), optional, pointer :: BT_cont !< A structure with elements that describe + type(BT_cont_type), optional, pointer :: BT_cont !< A structure with elements that describe !! the effective open face areas as a function of barotropic flow. ! Local variables real, dimension(SZI_(G),SZK_(GV)) :: & dvhdv ! Partial derivative of vh with v [H L ~> m2 or kg m-1]. - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: & - h_S, h_N ! Southern and northern face thicknesses [H ~> m or kg m-2]. real, dimension(SZI_(G)) :: & dv, & ! Corrective barotropic change in the velocity [L T-1 ~> m s-1]. dv_min_CFL, & ! Lower limit on dv correction to avoid CFL violations [L T-1 ~> m s-1] @@ -1183,7 +1184,7 @@ subroutine meridional_mass_flux(v, h_in, vh, dt, G, GV, US, CS, OBC, por_face_ar real :: I_dt ! 1.0 / dt [T-1 ~> s-1]. real :: dv_lim ! The velocity change that give a relative CFL of 1 [L T-1 ~> m s-1]. real :: dy_N, dy_S ! Effective y-grid spacings to the north and south [L ~> m]. - type(loop_bounds_type) :: LB + type(cont_loop_bounds_type) :: LB integer :: i, j, k, ish, ieh, jsh, jeh, n, nz integer :: l_seg logical :: local_specified_BC, use_visc_rem, set_BT_cont, any_simple_OBC @@ -1210,11 +1211,6 @@ subroutine meridional_mass_flux(v, h_in, vh, dt, G, GV, US, CS, OBC, por_face_ar I_dt = 1.0 / dt if (CS%aggress_adjust) CFL_dt = I_dt - call cpu_clock_begin(id_clock_update) - ! This sets h_S and h_N. - call meridional_edge_thickness(h_in, h_S, h_N, G, GV, US, CS, OBC, LB) - call cpu_clock_end(id_clock_update) - call cpu_clock_begin(id_clock_correct) if (.not.use_visc_rem) visc_rem(:,:) = 1.0 !$OMP parallel do default(none) shared(ish,ieh,jsh,jeh,nz,v,h_in,h_S,h_N,vh,use_visc_rem, & @@ -1238,8 +1234,7 @@ subroutine meridional_mass_flux(v, h_in, vh, dt, G, GV, US, CS, OBC, por_face_ar if (local_specified_BC) then do i=ish,ieh ; if (OBC%segnum_v(i,J) /= OBC_NONE) then l_seg = OBC%segnum_v(i,J) - if (OBC%segment(l_seg)%specified) & - vh(i,J,k) = OBC%segment(l_seg)%normal_trans(i,J,k) + if (OBC%segment(l_seg)%specified) vh(i,J,k) = OBC%segment(l_seg)%normal_trans(i,J,k) endif ; enddo endif enddo ! k-loop @@ -1333,8 +1328,7 @@ subroutine meridional_mass_flux(v, h_in, vh, dt, G, GV, US, CS, OBC, por_face_ar ! Avoid reconciling barotropic/baroclinic transports if transport is specified is_simple = .false. - if (l_seg /= OBC_NONE) & - is_simple = OBC%segment(l_seg)%specified + if (l_seg /= OBC_NONE) is_simple = OBC%segment(l_seg)%specified do_I(i) = .not.(l_seg /= OBC_NONE .and. is_simple) any_simple_OBC = any_simple_OBC .or. is_simple enddo ; else ; do i=ish,ieh @@ -1366,11 +1360,8 @@ subroutine meridional_mass_flux(v, h_in, vh, dt, G, GV, US, CS, OBC, por_face_ar visc_rem_max, J, ish, ieh, do_I, por_face_areaV) if (any_simple_OBC) then do i=ish,ieh - l_seg = OBC%segnum_v(i,J) - do_I(I) = .false. - if (l_seg /= OBC_NONE) & - do_I(i) = (OBC%segment(l_seg)%specified) + if (OBC%segnum_v(i,J) /= OBC_NONE) do_I(i) = (OBC%segment(OBC%segnum_v(i,J))%specified) if (do_I(i)) FAvi(i) = GV%H_subroundoff*G%dx_Cv(i,J) enddo @@ -1459,7 +1450,7 @@ subroutine merid_flux_layer(v, h, h_S, h_N, vh, dvhdv, visc_rem, dt, G, US, J, & logical, dimension(SZI_(G)), intent(in) :: do_I !< Which i values to work on. logical, intent(in) :: vol_CFL !< If true, rescale the !! ratio of face areas to the cell areas when estimating the CFL number. - real, dimension(SZI_(G), SZJB_(G)), & + real, dimension(SZI_(G),SZJB_(G)), & intent(in) :: por_face_areaV !< fractional open area of V-faces [nondim] type(ocean_OBC_type), optional, pointer :: OBC !< Open boundaries control structure. ! Local variables @@ -1537,7 +1528,7 @@ subroutine meridional_flux_thickness(v, h, h_S, h_N, h_v, dt, G, GV, US, LB, vol !! viscosity and the fractional open area !! [H ~> m or kg m-2]. real, intent(in) :: dt !< Time increment [T ~> s]. - type(loop_bounds_type), intent(in) :: LB !< Loop bounds structure. + type(cont_loop_bounds_type), intent(in) :: LB !< Loop bounds structure. type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type logical, intent(in) :: vol_CFL !< If true, rescale the ratio !! of face areas to the cell areas when estimating the CFL number. @@ -1963,7 +1954,7 @@ subroutine PPM_reconstruction_x(h_in, h_W, h_E, G, LB, h_min, monotonic, simple_ !! [H ~> m or kg m-2]. real, dimension(SZI_(G),SZJ_(G)), intent(out) :: h_E !< East edge thickness in the reconstruction, !! [H ~> m or kg m-2]. - type(loop_bounds_type), intent(in) :: LB !< Active loop bounds structure. + type(cont_loop_bounds_type), intent(in) :: LB !< Active loop bounds structure. real, intent(in) :: h_min !< The minimum thickness !! that can be obtained by a concave parabolic fit [H ~> m or kg m-2] logical, intent(in) :: monotonic !< If true, use the @@ -2099,7 +2090,7 @@ subroutine PPM_reconstruction_y(h_in, h_S, h_N, G, LB, h_min, monotonic, simple_ !! [H ~> m or kg m-2]. real, dimension(SZI_(G),SZJ_(G)), intent(out) :: h_N !< North edge thickness in the reconstruction, !! [H ~> m or kg m-2]. - type(loop_bounds_type), intent(in) :: LB !< Active loop bounds structure. + type(cont_loop_bounds_type), intent(in) :: LB !< Active loop bounds structure. real, intent(in) :: h_min !< The minimum thickness !! that can be obtained by a concave parabolic fit [H ~> m or kg m-2] logical, intent(in) :: monotonic !< If true, use the @@ -2392,8 +2383,7 @@ subroutine continuity_PPM_init(Time, G, GV, US, param_file, diag, CS) "If true, stop corrective iterations using a velocity "//& "based criterion and only stop if the iteration is "//& "better than all predecessors.", default=.true.) - call get_param(param_file, mdl, "CONT_PPM_USE_VISC_REM_MAX", & - CS%use_visc_rem_max, & + call get_param(param_file, mdl, "CONT_PPM_USE_VISC_REM_MAX", CS%use_visc_rem_max, & "If true, use more appropriate limiting bounds for "//& "corrections in strongly viscous columns.", default=.true.) call get_param(param_file, mdl, "CONT_PPM_MARGINAL_FACE_AREAS", CS%marginal_faces, & @@ -2417,6 +2407,39 @@ function continuity_PPM_stencil(CS) result(stencil) end function continuity_PPM_stencil +!> Set up a structure that stores the sizes of the i- and j-loops to to work on in the continuity solver. +function set_continuity_loop_bounds(G, CS, i_stencil, j_stencil) result(LB) + type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure. + type(continuity_PPM_CS), intent(in) :: CS !< Module's control structure. + logical, optional, intent(in) :: i_stencil !< If present and true, extend the i-loop bounds + !! by the stencil width of the continuity scheme. + logical, optional, intent(in) :: j_stencil !< If present and true, extend the j-loop bounds + !! by the stencil width of the continuity scheme. + type(cont_loop_bounds_type) :: LB !< A type storing the array sizes to work on in the continuity routines. + + ! Local variables + logical :: add_i_stencil, add_j_stencil ! Local variables set based on i_stencil and j_stensil + integer :: stencil ! The continuity solver stencil size with the current continuity scheme. + + add_i_stencil = .false. ; if (present(i_stencil)) add_i_stencil = i_stencil + add_j_stencil = .false. ; if (present(j_stencil)) add_j_stencil = j_stencil + + stencil = continuity_PPM_stencil(CS) + + if (add_i_stencil) then + LB%ish = G%isc-stencil ; LB%ieh = G%iec+stencil + else + LB%ish = G%isc ; LB%ieh = G%iec + endif + + if (add_j_stencil) then + LB%jsh = G%jsc-stencil ; LB%jeh = G%jec+stencil + else + LB%jsh = G%jsc ; LB%jeh = G%jec + endif + +end function set_continuity_loop_bounds + !> \namespace mom_continuity_ppm !! !! This module contains the subroutines that advect layer From bbda30f1214adce87c367a37891602579235516a Mon Sep 17 00:00:00 2001 From: Robert Hallberg Date: Thu, 16 Nov 2023 17:27:36 -0500 Subject: [PATCH 05/22] +Add zonal_BT_mass_flux & meridional_BT_mass_flux Added the new publicly visible routines zonal_BT_mass_flux and meridional_BT_mass_flux to return the vertically summed transports that the continuity solver would generate. Also revised the routine continuity_2d_fluxes in MOM_continuity to make use of these new routines. Because these new routines are not yet being used, all answers are bitwise identical, but there are new public interfaces. --- src/core/MOM_continuity.F90 | 22 +---- src/core/MOM_continuity_PPM.F90 | 149 ++++++++++++++++++++++++++++++++ 2 files changed, 152 insertions(+), 19 deletions(-) diff --git a/src/core/MOM_continuity.F90 b/src/core/MOM_continuity.F90 index 116bf8f195..59d6a58f74 100644 --- a/src/core/MOM_continuity.F90 +++ b/src/core/MOM_continuity.F90 @@ -9,6 +9,7 @@ module MOM_continuity use MOM_continuity_PPM, only : continuity_CS=>continuity_PPM_CS use MOM_continuity_PPM, only : zonal_edge_thickness, meridional_edge_thickness use MOM_continuity_PPM, only : zonal_mass_flux, meridional_mass_flux +use MOM_continuity_PPM, only : zonal_BT_mass_flux, meridional_BT_mass_flux use MOM_diag_mediator, only : time_type use MOM_grid, only : ocean_grid_type use MOM_open_boundary, only : ocean_OBC_type @@ -101,29 +102,12 @@ subroutine continuity_2d_fluxes(u, v, h, uhbt, vhbt, dt, G, GV, US, CS, OBC, pbv real :: h_E(SZI_(G),SZJ_(G),SZK_(GV)) ! East edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] real :: h_S(SZI_(G),SZJ_(G),SZK_(GV)) ! South edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] real :: h_N(SZI_(G),SZJ_(G),SZK_(GV)) ! North edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] - real :: uh(SZIB_(G),SZJ_(G),SZK_(GV)) ! Thickness fluxes through zonal faces, u*h*dy [H L2 T-1 ~> m3 s-1 or kg s-1] - real :: vh(SZI_(G),SZJB_(G),SZK_(GV)) ! Thickness fluxes through v-point faces, v*h*dx [H L2 T-1 ~> m3 s-1 or kg s-1] - integer :: i, j, k - - uh(:,:,:) = 0.0 - vh(:,:,:) = 0.0 call zonal_edge_thickness(h, h_W, h_E, G, GV, US, CS, OBC) - call zonal_mass_flux(u, h, h_W, h_E, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU) + call zonal_BT_mass_flux(u, h, h_W, h_E, uhbt, dt, G, GV, US, CS, OBC, pbv%por_face_areaU) call meridional_edge_thickness(h, h_S, h_N, G, GV, US, CS, OBC) - call meridional_mass_flux(v, h, h_S, h_N, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV) - - uhbt(:,:) = 0.0 - vhbt(:,:) = 0.0 - - do k=1,GV%ke ; do j=G%jsc,G%jec ; do I=G%isc-1,G%iec - uhbt(I,j) = uhbt(I,j) + uh(I,j,k) - enddo ; enddo ; enddo - - do k=1,GV%ke ; do J=G%jsc-1,G%jec ; do i=G%isc,G%iec - vhbt(I,j) = vhbt(I,j) + vh(I,j,k) - enddo ; enddo ; enddo + call meridional_BT_mass_flux(v, h, h_S, h_N, vhbt, dt, G, GV, US, CS, OBC, pbv%por_face_areaV) end subroutine continuity_2d_fluxes diff --git a/src/core/MOM_continuity_PPM.F90 b/src/core/MOM_continuity_PPM.F90 index 0abc0c5568..57b0668ca9 100644 --- a/src/core/MOM_continuity_PPM.F90 +++ b/src/core/MOM_continuity_PPM.F90 @@ -22,6 +22,7 @@ module MOM_continuity_PPM public zonal_mass_flux, meridional_mass_flux public zonal_flux_thickness, meridional_flux_thickness public zonal_edge_thickness, meridional_edge_thickness +public zonal_BT_mass_flux, meridional_BT_mass_flux public set_continuity_loop_bounds !>@{ CPU time clock IDs @@ -610,6 +611,80 @@ subroutine zonal_mass_flux(u, h_in, h_W, h_E, uh, dt, G, GV, US, CS, OBC, por_fa end subroutine zonal_mass_flux + +!> Calculates the vertically integrated mass or volume fluxes through the zonal faces. +subroutine zonal_BT_mass_flux(u, h_in, h_W, h_E, uhbt, dt, G, GV, US, CS, OBC, por_face_areaU, LB_in) + type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. + type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1] + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_in !< Layer thickness used to + !! calculate fluxes [H ~> m or kg m-2] + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_W !< Western edge thickness in the PPM + !! reconstruction [H ~> m or kg m-2]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_E !< Eastern edge thickness in the PPM + !! reconstruction [H ~> m or kg m-2]. + real, dimension(SZIB_(G),SZJ_(G)), intent(out) :: uhbt !< The summed volume flux through zonal + !! faces [H L2 T-1 ~> m3 s-1 or kg s-1]. + real, intent(in) :: dt !< Time increment [T ~> s]. + type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type + type(continuity_PPM_CS), intent(in) :: CS !< This module's control structure.G + type(ocean_OBC_type), pointer :: OBC !< Open boundary condition type + !! specifies whether, where, and what + !! open boundary conditions are used. + real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), intent(in) :: por_face_areaU !< fractional open area of U-faces [nondim] + type(cont_loop_bounds_type), optional, intent(in) :: LB_in !< Loop bounds structure. + + ! Local variables + real :: uh(SZIB_(G)) ! Volume flux through zonal faces = u*h*dy [H L2 T-1 ~> m3 s-1 or kg s-1] + real :: duhdu(SZIB_(G)) ! Partial derivative of uh with u [H L ~> m2 or kg m-1]. + logical, dimension(SZIB_(G)) :: do_I + real :: ones(SZIB_(G)) ! An array of 1's [nondim] + type(cont_loop_bounds_type) :: LB + integer :: i, j, k, ish, ieh, jsh, jeh, nz + logical :: local_specified_BC, OBC_in_row + + local_specified_BC = .false. + if (associated(OBC)) then ; if (OBC%OBC_pe) then + local_specified_BC = OBC%specified_v_BCs_exist_globally + endif ; endif + + if (present(LB_in)) then + LB = LB_in + else + LB%ish = G%isc ; LB%ieh = G%iec ; LB%jsh = G%jsc ; LB%jeh = G%jec + endif + ish = LB%ish ; ieh = LB%ieh ; jsh = LB%jsh ; jeh = LB%jeh ; nz = GV%ke + + call cpu_clock_begin(id_clock_correct) + ones(:) = 1.0 ; do_I(:) = .true. + + uhbt(:,:) = 0.0 + !$OMP parallel do default(shared) private(uh,duhdu,OBC_in_row) + do j=jsh,jeh + ! Determining whether there are any OBC points outside of the k-loop should be more efficient. + OBC_in_row = .false. + if (local_specified_BC) then ; do I=ish-1,ieh ; if (OBC%segnum_u(I,j) /= OBC_NONE) then + if (OBC%segment(OBC%segnum_u(I,j))%specified) OBC_in_row = .true. + endif ; enddo ; endif + do k=1,nz + ! This sets uh and duhdu. + call zonal_flux_layer(u(:,j,k), h_in(:,j,k), h_W(:,j,k), h_E(:,j,k), uh, duhdu, ones, & + dt, G, US, j, ish, ieh, do_I, CS%vol_CFL, por_face_areaU(:,j,k), OBC) + if (OBC_in_row) then ; do I=ish-1,ieh ; if (OBC%segnum_u(I,j) /= OBC_NONE) then + if (OBC%segment(OBC%segnum_u(I,j))%specified) uh(I) = OBC%segment(OBC%segnum_u(I,j))%normal_trans(I,j,k) + endif ; enddo ; endif + + ! Accumulate the barotropic transport. + do I=ish-1,ieh + uhbt(I,j) = uhbt(I,j) + uh(I) + enddo + enddo ! k-loop + enddo ! j-loop + call cpu_clock_end(id_clock_correct) + +end subroutine zonal_BT_mass_flux + + !> Evaluates the zonal mass or volume fluxes in a layer. subroutine zonal_flux_layer(u, h, h_W, h_E, uh, duhdu, visc_rem, dt, G, US, j, & ish, ieh, do_I, vol_CFL, por_face_areaU, OBC) @@ -1422,6 +1497,80 @@ subroutine meridional_mass_flux(v, h_in, h_S, h_N, vh, dt, G, GV, US, CS, OBC, p end subroutine meridional_mass_flux + +!> Calculates the vertically integrated mass or volume fluxes through the meridional faces. +subroutine meridional_BT_mass_flux(v, h_in, h_S, h_N, vhbt, dt, G, GV, US, CS, OBC, por_face_areaV, LB_in) + type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. + type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1] + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_in !< Layer thickness used to + !! calculate fluxes [H ~> m or kg m-2] + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_S !< Southern edge thickness in the PPM + !! reconstruction [H ~> m or kg m-2]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_N !< Northern edge thickness in the PPM + !! reconstruction [H ~> m or kg m-2]. + real, dimension(SZI_(G),SZJB_(G)), intent(out) :: vhbt !< The summed volume flux through meridional + !! faces [H L2 T-1 ~> m3 s-1 or kg s-1]. + real, intent(in) :: dt !< Time increment [T ~> s]. + type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type + type(continuity_PPM_CS), intent(in) :: CS !< This module's control structure.G + type(ocean_OBC_type), pointer :: OBC !< Open boundary condition type + !! specifies whether, where, and what + !! open boundary conditions are used. + real, dimension(SZI_(G),SZJB_(G),SZK_(G)), intent(in) :: por_face_areaV !< fractional open area of V-faces [nondim] + type(cont_loop_bounds_type), optional, intent(in) :: LB_in !< Loop bounds structure. + + ! Local variables + real :: vh(SZI_(G)) ! Volume flux through meridional faces = v*h*dx [H L2 T-1 ~> m3 s-1 or kg s-1] + real :: dvhdv(SZI_(G)) ! Partial derivative of vh with v [H L ~> m2 or kg m-1]. + logical, dimension(SZI_(G)) :: do_I + real :: ones(SZI_(G)) ! An array of 1's [nondim] + type(cont_loop_bounds_type) :: LB + integer :: i, j, k, ish, ieh, jsh, jeh, nz + logical :: local_specified_BC, OBC_in_row + + local_specified_BC = .false. + if (associated(OBC)) then ; if (OBC%OBC_pe) then + local_specified_BC = OBC%specified_v_BCs_exist_globally + endif ; endif + + if (present(LB_in)) then + LB = LB_in + else + LB%ish = G%isc ; LB%ieh = G%iec ; LB%jsh = G%jsc ; LB%jeh = G%jec + endif + ish = LB%ish ; ieh = LB%ieh ; jsh = LB%jsh ; jeh = LB%jeh ; nz = GV%ke + + call cpu_clock_begin(id_clock_correct) + ones(:) = 1.0 ; do_I(:) = .true. + + vhbt(:,:) = 0.0 + !$OMP parallel do default(shared) private(vh,dvhdv,OBC_in_row) + do J=jsh-1,jeh + ! Determining whether there are any OBC points outside of the k-loop should be more efficient. + OBC_in_row = .false. + if (local_specified_BC) then ; do i=ish,ieh ; if (OBC%segnum_v(i,J) /= OBC_NONE) then + if (OBC%segment(OBC%segnum_v(i,J))%specified) OBC_in_row = .true. + endif ; enddo ; endif + do k=1,nz + ! This sets vh and dvhdv. + call merid_flux_layer(v(:,J,k), h_in(:,:,k), h_S(:,:,k), h_N(:,:,k), vh, dvhdv, ones, & + dt, G, US, J, ish, ieh, do_I, CS%vol_CFL, por_face_areaV(:,:,k), OBC) + if (OBC_in_row) then ; do i=ish,ieh ; if (OBC%segnum_v(i,J) /= OBC_NONE) then + if (OBC%segment(OBC%segnum_v(i,J))%specified) vh(i) = OBC%segment(OBC%segnum_v(i,J))%normal_trans(i,J,k) + endif ; enddo ; endif + + ! Accumulate the barotropic transport. + do i=ish,ieh + vhbt(i,J) = vhbt(i,J) + vh(i) + enddo + enddo ! k-loop + enddo ! j-loop + call cpu_clock_end(id_clock_correct) + +end subroutine meridional_BT_mass_flux + + !> Evaluates the meridional mass or volume fluxes in a layer. subroutine merid_flux_layer(v, h, h_S, h_N, vh, dvhdv, visc_rem, dt, G, US, J, & ish, ieh, do_I, vol_CFL, por_face_areaV, OBC) From a70482cfc45c6bf891dfaae7613bde73d7128d19 Mon Sep 17 00:00:00 2001 From: Robert Hallberg Date: Sat, 18 Nov 2023 07:15:39 -0500 Subject: [PATCH 06/22] +Add continuity_zonal_convergence Added the new publicly visible routines continuity_zonal_convergence and continuity_meridional_convergence to increment layer thicknesses using the continuity loop bounds type to specify extents. Also revised continuity_PPM to use these new routines. These changes will allow for the reuse of some of the reconstructions in calls that replace calls to continuity with the unwrapped contents. All answers are bitwise identical, but there are two new public interfaces. --- src/core/MOM_continuity_PPM.F90 | 181 ++++++++++++++++++++------------ 1 file changed, 113 insertions(+), 68 deletions(-) diff --git a/src/core/MOM_continuity_PPM.F90 b/src/core/MOM_continuity_PPM.F90 index 57b0668ca9..f34131e03e 100644 --- a/src/core/MOM_continuity_PPM.F90 +++ b/src/core/MOM_continuity_PPM.F90 @@ -20,13 +20,14 @@ module MOM_continuity_PPM public continuity_PPM, continuity_PPM_init, continuity_PPM_stencil public zonal_mass_flux, meridional_mass_flux -public zonal_flux_thickness, meridional_flux_thickness public zonal_edge_thickness, meridional_edge_thickness +public continuity_zonal_convergence, continuity_merdional_convergence +public zonal_flux_thickness, meridional_flux_thickness public zonal_BT_mass_flux, meridional_BT_mass_flux public set_continuity_loop_bounds !>@{ CPU time clock IDs -integer :: id_clock_update, id_clock_correct +integer :: id_clock_reconstruct, id_clock_update, id_clock_correct !>@} !> Control structure for mom_continuity_ppm @@ -132,12 +133,8 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhb real :: h_S(SZI_(G),SZJ_(G),SZK_(GV)) ! South edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] real :: h_N(SZI_(G),SZJ_(G),SZK_(GV)) ! North edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] real :: h_min ! The minimum layer thickness [H ~> m or kg m-2]. h_min could be 0. - type(cont_loop_bounds_type) :: LB - integer :: is, ie, js, je, nz, stencil - integer :: i, j, k - + type(cont_loop_bounds_type) :: LB ! A type indicating the loop range for a phase of the updates logical :: x_first - is = G%isc ; ie = G%iec ; js = G%jsc ; je = G%jec ; nz = GV%ke h_min = GV%Angstrom_H @@ -150,80 +147,116 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhb "MOM_continuity_PPM: Either both visc_rem_u and visc_rem_v or neither"// & " one must be present in call to continuity_PPM.") - stencil = continuity_PPM_stencil(CS) - if (x_first) then ! First advect zonally, with loop bounds that accomodate the subsequent meridional advection. - LB = set_continuity_loop_bounds(G, CS, .false., .true.) - - call cpu_clock_begin(id_clock_update) + LB = set_continuity_loop_bounds(G, CS, i_stencil=.false., j_stencil=.true.) call zonal_edge_thickness(hin, h_W, h_E, G, GV, US, CS, OBC, LB) - call cpu_clock_end(id_clock_update) call zonal_mass_flux(u, hin, h_W, h_E, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU, & LB, uhbt, visc_rem_u, u_cor, BT_cont) - - call cpu_clock_begin(id_clock_update) - !$OMP parallel do default(shared) - do k=1,nz ; do j=LB%jsh,LB%jeh ; do i=LB%ish,LB%ieh - h(i,j,k) = hin(i,j,k) - dt * G%IareaT(i,j) * (uh(I,j,k) - uh(I-1,j,k)) - ! Uncomment this line to prevent underflow. - ! if (h(i,j,k) < h_min) h(i,j,k) = h_min - enddo ; enddo ; enddo - - LB = set_continuity_loop_bounds(G, CS, .false., .false.) + call continuity_zonal_convergence(h, uh, dt, G, GV, LB, hin) ! Now advect meridionally, using the updated thicknesses to determine the fluxes. + LB = set_continuity_loop_bounds(G, CS, i_stencil=.false., j_stencil=.false.) call meridional_edge_thickness(h, h_S, h_N, G, GV, US, CS, OBC, LB) - call cpu_clock_end(id_clock_update) - call meridional_mass_flux(v, h, h_S, h_N, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV, & LB, vhbt, visc_rem_v, v_cor, BT_cont) - - call cpu_clock_begin(id_clock_update) - !$OMP parallel do default(shared) - do k=1,nz ; do j=LB%jsh,LB%jeh ; do i=LB%ish,LB%ieh - h(i,j,k) = h(i,j,k) - dt * G%IareaT(i,j) * (vh(i,J,k) - vh(i,J-1,k)) - ! This line prevents underflow. - if (h(i,j,k) < h_min) h(i,j,k) = h_min - enddo ; enddo ; enddo - call cpu_clock_end(id_clock_update) + call continuity_merdional_convergence(h, vh, dt, G, GV, LB, hmin=h_min) else ! .not. x_first ! First advect meridionally, with loop bounds that accomodate the subsequent zonal advection. - LB = set_continuity_loop_bounds(G, CS, .true., .false.) - - call cpu_clock_begin(id_clock_update) + LB = set_continuity_loop_bounds(G, CS, i_stencil=.true., j_stencil=.false.) call meridional_edge_thickness(hin, h_S, h_N, G, GV, US, CS, OBC, LB) - call cpu_clock_end(id_clock_update) call meridional_mass_flux(v, hin, h_S, h_N, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV, & LB, vhbt, visc_rem_v, v_cor, BT_cont) - - call cpu_clock_begin(id_clock_update) - !$OMP parallel do default(shared) - do k=1,nz ; do j=LB%jsh,LB%jeh ; do i=LB%ish,LB%ieh - h(i,j,k) = hin(i,j,k) - dt * G%IareaT(i,j) * (vh(i,J,k) - vh(i,J-1,k)) - enddo ; enddo ; enddo - - LB = set_continuity_loop_bounds(G, CS, .false., .false.) + call continuity_merdional_convergence(h, vh, dt, G, GV, LB, hin) ! Now advect zonally, using the updated thicknesses to determine the fluxes. + LB = set_continuity_loop_bounds(G, CS, i_stencil=.false., j_stencil=.false.) call zonal_edge_thickness(h, h_W, h_E, G, GV, US, CS, OBC, LB) - call cpu_clock_end(id_clock_update) call zonal_mass_flux(u, h, h_W, h_E, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU, & LB, uhbt, visc_rem_u, u_cor, BT_cont) + call continuity_zonal_convergence(h, uh, dt, G, GV, LB, hmin=h_min) + endif - call cpu_clock_begin(id_clock_update) +end subroutine continuity_PPM + + +!> Updates the thicknesses due to zonal thickness fluxes. +subroutine continuity_zonal_convergence(h, uh, dt, G, GV, LB, hin, hmin) + type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure + type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + intent(inout) :: h !< Final layer thickness [H ~> m or kg m-2] + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & + intent(in) :: uh !< Zonal thickness flux, u*h*dy [H L2 T-1 ~> m3 s-1 or kg s-1] + real, intent(in) :: dt !< Time increment [T ~> s] + type(cont_loop_bounds_type), intent(in) :: LB !< Loop bounds structure + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + optional, intent(in) :: hin !< Initial layer thickness [H ~> m or kg m-2]. + !! If hin is absent, h is also the initial thickness. + real, optional, intent(in) :: hmin !< The minimum layer thickness [H ~> m or kg m-2] + + real :: h_min ! The minimum layer thickness [H ~> m or kg m-2]. h_min could be 0. + integer :: i, j, k + + call cpu_clock_begin(id_clock_update) + + h_min = 0.0 ; if (present(hmin)) h_min = hmin + + if (present(hin)) then + !$OMP parallel do default(shared) + do k=1,GV%ke ; do j=LB%jsh,LB%jeh ; do i=LB%ish,LB%ieh + h(i,j,k) = max( hin(i,j,k) - dt * G%IareaT(i,j) * (uh(I,j,k) - uh(I-1,j,k)), h_min ) + enddo ; enddo ; enddo + else !$OMP parallel do default(shared) - do k=1,nz ; do j=LB%jsh,LB%jeh ; do i=LB%ish,LB%ieh - h(i,j,k) = h(i,j,k) - dt * G%IareaT(i,j) * (uh(I,j,k) - uh(I-1,j,k)) - ! This line prevents underflow. - if (h(i,j,k) < h_min) h(i,j,k) = h_min + do k=1,GV%ke ; do j=LB%jsh,LB%jeh ; do i=LB%ish,LB%ieh + h(i,j,k) = max( h(i,j,k) - dt * G%IareaT(i,j) * (uh(I,j,k) - uh(I-1,j,k)), h_min ) enddo ; enddo ; enddo - call cpu_clock_end(id_clock_update) + endif + + call cpu_clock_end(id_clock_update) + +end subroutine continuity_zonal_convergence + +!> Updates the thicknesses due to meridional thickness fluxes. +subroutine continuity_merdional_convergence(h, vh, dt, G, GV, LB, hin, hmin) + type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure + type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + intent(inout) :: h !< Final layer thickness [H ~> m or kg m-2] + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & + intent(in) :: vh !< Meridional thickness flux, v*h*dx [H L2 T-1 ~> m3 s-1 or kg s-1] + real, intent(in) :: dt !< Time increment [T ~> s] + type(cont_loop_bounds_type), intent(in) :: LB !< Loop bounds structure + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + optional, intent(in) :: hin !< Initial layer thickness [H ~> m or kg m-2]. + !! If hin is absent, h is also the initial thickness. + real, optional, intent(in) :: hmin !< The minimum layer thickness [H ~> m or kg m-2] + real :: h_min ! The minimum layer thickness [H ~> m or kg m-2]. h_min could be 0. + integer :: i, j, k + + call cpu_clock_begin(id_clock_update) + + h_min = 0.0 ; if (present(hmin)) h_min = hmin + + if (present(hin)) then + !$OMP parallel do default(shared) + do k=1,GV%ke ; do j=LB%jsh,LB%jeh ; do i=LB%ish,LB%ieh + h(i,j,k) = max( hin(i,j,k) - dt * G%IareaT(i,j) * (vh(i,J,k) - vh(i,J-1,k)), h_min ) + enddo ; enddo ; enddo + else + !$OMP parallel do default(shared) + do k=1,GV%ke ; do j=LB%jsh,LB%jeh ; do i=LB%ish,LB%ieh + h(i,j,k) = max( h(i,j,k) - dt * G%IareaT(i,j) * (vh(i,J,k) - vh(i,J-1,k)), h_min ) + enddo ; enddo ; enddo endif -end subroutine continuity_PPM + call cpu_clock_end(id_clock_update) + +end subroutine continuity_merdional_convergence + !> Set the reconstructed thicknesses at the eastern and western edges of tracer cells. subroutine zonal_edge_thickness(h_in, h_W, h_E, G, GV, US, CS, OBC, LB_in) @@ -245,6 +278,8 @@ subroutine zonal_edge_thickness(h_in, h_W, h_E, G, GV, US, CS, OBC, LB_in) type(cont_loop_bounds_type) :: LB integer :: i, j, k, ish, ieh, jsh, jeh, nz + call cpu_clock_begin(id_clock_reconstruct) + if (present(LB_in)) then LB = LB_in else @@ -265,6 +300,8 @@ subroutine zonal_edge_thickness(h_in, h_W, h_E, G, GV, US, CS, OBC, LB_in) enddo endif + call cpu_clock_end(id_clock_reconstruct) + end subroutine zonal_edge_thickness @@ -288,6 +325,8 @@ subroutine meridional_edge_thickness(h_in, h_S, h_N, G, GV, US, CS, OBC, LB_in) type(cont_loop_bounds_type) :: LB integer :: i, j, k, ish, ieh, jsh, jeh, nz + call cpu_clock_begin(id_clock_reconstruct) + if (present(LB_in)) then LB = LB_in else @@ -308,6 +347,8 @@ subroutine meridional_edge_thickness(h_in, h_S, h_N, G, GV, US, CS, OBC, LB_in) enddo endif + call cpu_clock_end(id_clock_reconstruct) + end subroutine meridional_edge_thickness @@ -377,6 +418,8 @@ subroutine zonal_mass_flux(u, h_in, h_W, h_E, uh, dt, G, GV, US, CS, OBC, por_fa logical :: local_specified_BC, use_visc_rem, set_BT_cont, any_simple_OBC logical :: local_Flather_OBC, local_open_BC, is_simple + call cpu_clock_begin(id_clock_correct) + use_visc_rem = present(visc_rem_u) local_specified_BC = .false. ; set_BT_cont = .false. ; local_Flather_OBC = .false. local_open_BC = .false. @@ -398,7 +441,6 @@ subroutine zonal_mass_flux(u, h_in, h_W, h_E, uh, dt, G, GV, US, CS, OBC, por_fa I_dt = 1.0 / dt if (CS%aggress_adjust) CFL_dt = I_dt - call cpu_clock_begin(id_clock_correct) if (.not.use_visc_rem) visc_rem(:,:) = 1.0 !$OMP parallel do default(none) shared(ish,ieh,jsh,jeh,nz,u,h_in,h_W,h_E,use_visc_rem,visc_rem_u, & !$OMP uh,dt,US,G,GV,CS,local_specified_BC,OBC,uhbt,set_BT_cont, & @@ -597,7 +639,6 @@ subroutine zonal_mass_flux(u, h_in, h_W, h_E, uh, dt, G, GV, US, CS, OBC, por_fa endif enddo endif - call cpu_clock_end(id_clock_correct) if (set_BT_cont) then ; if (allocated(BT_cont%h_u)) then if (present(u_cor)) then @@ -609,6 +650,8 @@ subroutine zonal_mass_flux(u, h_in, h_W, h_E, uh, dt, G, GV, US, CS, OBC, por_fa endif endif ; endif + call cpu_clock_end(id_clock_correct) + end subroutine zonal_mass_flux @@ -639,23 +682,22 @@ subroutine zonal_BT_mass_flux(u, h_in, h_W, h_E, uhbt, dt, G, GV, US, CS, OBC, p real :: duhdu(SZIB_(G)) ! Partial derivative of uh with u [H L ~> m2 or kg m-1]. logical, dimension(SZIB_(G)) :: do_I real :: ones(SZIB_(G)) ! An array of 1's [nondim] - type(cont_loop_bounds_type) :: LB integer :: i, j, k, ish, ieh, jsh, jeh, nz logical :: local_specified_BC, OBC_in_row + call cpu_clock_begin(id_clock_correct) + local_specified_BC = .false. if (associated(OBC)) then ; if (OBC%OBC_pe) then local_specified_BC = OBC%specified_v_BCs_exist_globally endif ; endif if (present(LB_in)) then - LB = LB_in + ish = LB_in%ish ; ieh = LB_in%ieh ; jsh = LB_in%jsh ; jeh = LB_in%jeh ; nz = GV%ke else - LB%ish = G%isc ; LB%ieh = G%iec ; LB%jsh = G%jsc ; LB%jeh = G%jec + ish = G%isc ; ieh = G%iec ; jsh = G%jsc ; jeh = G%jec ; nz = GV%ke endif - ish = LB%ish ; ieh = LB%ieh ; jsh = LB%jsh ; jeh = LB%jeh ; nz = GV%ke - call cpu_clock_begin(id_clock_correct) ones(:) = 1.0 ; do_I(:) = .true. uhbt(:,:) = 0.0 @@ -1265,6 +1307,8 @@ subroutine meridional_mass_flux(v, h_in, h_S, h_N, vh, dt, G, GV, US, CS, OBC, p logical :: local_specified_BC, use_visc_rem, set_BT_cont, any_simple_OBC logical :: local_Flather_OBC, is_simple, local_open_BC + call cpu_clock_begin(id_clock_correct) + use_visc_rem = present(visc_rem_v) local_specified_BC = .false. ; set_BT_cont = .false. ; local_Flather_OBC = .false. local_open_BC = .false. @@ -1286,7 +1330,6 @@ subroutine meridional_mass_flux(v, h_in, h_S, h_N, vh, dt, G, GV, US, CS, OBC, p I_dt = 1.0 / dt if (CS%aggress_adjust) CFL_dt = I_dt - call cpu_clock_begin(id_clock_correct) if (.not.use_visc_rem) visc_rem(:,:) = 1.0 !$OMP parallel do default(none) shared(ish,ieh,jsh,jeh,nz,v,h_in,h_S,h_N,vh,use_visc_rem, & !$OMP visc_rem_v,dt,US,G,GV,CS,local_specified_BC,OBC,vhbt, & @@ -1483,7 +1526,6 @@ subroutine meridional_mass_flux(v, h_in, h_S, h_N, vh, dt, G, GV, US, CS, OBC, p endif enddo endif - call cpu_clock_end(id_clock_correct) if (set_BT_cont) then ; if (allocated(BT_cont%h_v)) then if (present(v_cor)) then @@ -1495,6 +1537,8 @@ subroutine meridional_mass_flux(v, h_in, h_S, h_N, vh, dt, G, GV, US, CS, OBC, p endif endif ; endif + call cpu_clock_end(id_clock_correct) + end subroutine meridional_mass_flux @@ -1525,23 +1569,22 @@ subroutine meridional_BT_mass_flux(v, h_in, h_S, h_N, vhbt, dt, G, GV, US, CS, O real :: dvhdv(SZI_(G)) ! Partial derivative of vh with v [H L ~> m2 or kg m-1]. logical, dimension(SZI_(G)) :: do_I real :: ones(SZI_(G)) ! An array of 1's [nondim] - type(cont_loop_bounds_type) :: LB integer :: i, j, k, ish, ieh, jsh, jeh, nz logical :: local_specified_BC, OBC_in_row + call cpu_clock_begin(id_clock_correct) + local_specified_BC = .false. if (associated(OBC)) then ; if (OBC%OBC_pe) then local_specified_BC = OBC%specified_v_BCs_exist_globally endif ; endif if (present(LB_in)) then - LB = LB_in + ish = LB_in%ish ; ieh = LB_in%ieh ; jsh = LB_in%jsh ; jeh = LB_in%jeh ; nz = GV%ke else - LB%ish = G%isc ; LB%ieh = G%iec ; LB%jsh = G%jsc ; LB%jeh = G%jec + ish = G%isc ; ieh = G%iec ; jsh = G%jsc ; jeh = G%jec ; nz = GV%ke endif - ish = LB%ish ; ieh = LB%ieh ; jsh = LB%jsh ; jeh = LB%jeh ; nz = GV%ke - call cpu_clock_begin(id_clock_correct) ones(:) = 1.0 ; do_I(:) = .true. vhbt(:,:) = 0.0 @@ -1566,6 +1609,7 @@ subroutine meridional_BT_mass_flux(v, h_in, h_S, h_N, vhbt, dt, G, GV, US, CS, O enddo enddo ! k-loop enddo ! j-loop + call cpu_clock_end(id_clock_correct) end subroutine meridional_BT_mass_flux @@ -2542,6 +2586,7 @@ subroutine continuity_PPM_init(Time, G, GV, US, param_file, diag, CS) CS%diag => diag + id_clock_reconstruct = cpu_clock_id('(Ocean continuity reconstruction)', grain=CLOCK_ROUTINE) id_clock_update = cpu_clock_id('(Ocean continuity update)', grain=CLOCK_ROUTINE) id_clock_correct = cpu_clock_id('(Ocean continuity correction)', grain=CLOCK_ROUTINE) From 6b6f8dcde50c16feebd2f895a50b32e562d2db25 Mon Sep 17 00:00:00 2001 From: Robert Hallberg Date: Sun, 19 Nov 2023 09:15:42 -0500 Subject: [PATCH 07/22] Move continuity_fluxes to MOM_continuity_PPM.F90 Move continuity_fluxes and continuity_adjust_vel from MOM_continuity.F90 to MOM_continuity_PPM.F90, but with these interfaces also offered via the MOM_continuity module so that no changes are required outside of these two files. In addtion, 11 of the recently added public interfaces from MOM_continuity_PPM are also made available as pass-through interfaces from MOM_continuity. All answers are bitwise identical. --- src/core/MOM_continuity.F90 | 179 ++------------------------------ src/core/MOM_continuity_PPM.F90 | 157 ++++++++++++++++++++++++++++ 2 files changed, 168 insertions(+), 168 deletions(-) diff --git a/src/core/MOM_continuity.F90 b/src/core/MOM_continuity.F90 index 59d6a58f74..14582d1eb5 100644 --- a/src/core/MOM_continuity.F90 +++ b/src/core/MOM_continuity.F90 @@ -7,181 +7,24 @@ module MOM_continuity use MOM_continuity_PPM, only : continuity_stencil=>continuity_PPM_stencil use MOM_continuity_PPM, only : continuity_init=>continuity_PPM_init use MOM_continuity_PPM, only : continuity_CS=>continuity_PPM_CS -use MOM_continuity_PPM, only : zonal_edge_thickness, meridional_edge_thickness +use MOM_continuity_PPM, only : continuity_fluxes, continuity_adjust_vel use MOM_continuity_PPM, only : zonal_mass_flux, meridional_mass_flux +use MOM_continuity_PPM, only : zonal_edge_thickness, meridional_edge_thickness +use MOM_continuity_PPM, only : continuity_zonal_convergence, continuity_merdional_convergence +use MOM_continuity_PPM, only : zonal_flux_thickness, meridional_flux_thickness use MOM_continuity_PPM, only : zonal_BT_mass_flux, meridional_BT_mass_flux -use MOM_diag_mediator, only : time_type -use MOM_grid, only : ocean_grid_type -use MOM_open_boundary, only : ocean_OBC_type -use MOM_unit_scaling, only : unit_scale_type -use MOM_variables, only : BT_cont_type, porous_barrier_type -use MOM_verticalGrid, only : verticalGrid_type +use MOM_continuity_PPM, only : set_continuity_loop_bounds, cont_loop_bounds_type implicit none ; private -#include - ! These are direct pass-throughs of routines in continuity_PPM public continuity, continuity_init, continuity_stencil, continuity_CS public continuity_fluxes, continuity_adjust_vel - -!> Finds the thickness fluxes from the continuity solver or their vertical sum without -!! actually updating the layer thicknesses. -interface continuity_fluxes - module procedure continuity_3d_fluxes, continuity_2d_fluxes -end interface continuity_fluxes - -contains - -!> Finds the thickness fluxes from the continuity solver without actually updating the -!! layer thicknesses. Because the fluxes in the two directions are calculated based on the -!! input thicknesses, which are not updated between the direcitons, the fluxes returned here -!! are not the same as those that would be returned by a call to continuity. -subroutine continuity_3d_fluxes(u, v, h, uh, vh, dt, G, GV, US, CS, OBC, pbv) - type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure. - type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure. - real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & - intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]. - real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & - intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1]. - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & - intent(in) :: h !< Layer thickness [H ~> m or kg m-2]. - real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & - intent(out) :: uh !< Thickness fluxes through zonal faces, - !! u*h*dy [H L2 T-1 ~> m3 s-1 or kg s-1]. - real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & - intent(out) :: vh !< Thickness fluxes through meridional faces, - !! v*h*dx [H L2 T-1 ~> m3 s-1 or kg s-1]. - real, intent(in) :: dt !< Time increment [T ~> s]. - type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type - type(continuity_CS), intent(in) :: CS !< Control structure for mom_continuity. - type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. - type(porous_barrier_type), intent(in) :: pbv !< porous barrier fractional cell metrics - - ! Local variables - real :: h_W(SZI_(G),SZJ_(G),SZK_(GV)) ! West edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] - real :: h_E(SZI_(G),SZJ_(G),SZK_(GV)) ! East edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] - real :: h_S(SZI_(G),SZJ_(G),SZK_(GV)) ! South edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] - real :: h_N(SZI_(G),SZJ_(G),SZK_(GV)) ! North edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] - - call zonal_edge_thickness(h, h_W, h_E, G, GV, US, CS, OBC) - call zonal_mass_flux(u, h, h_W, h_E, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU) - - call meridional_edge_thickness(h, h_S, h_N, G, GV, US, CS, OBC) - call meridional_mass_flux(v, h, h_S, h_N, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV) - -end subroutine continuity_3d_fluxes - -!> Find the vertical sum of the thickness fluxes from the continuity solver without actually -!! updating the layer thicknesses. Because the fluxes in the two directions are calculated -!! based on the input thicknesses, which are not updated between the directions, the fluxes -!! returned here are not the same as those that would be returned by a call to continuity. -subroutine continuity_2d_fluxes(u, v, h, uhbt, vhbt, dt, G, GV, US, CS, OBC, pbv) - type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure. - type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure. - real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & - intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]. - real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & - intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1]. - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & - intent(in) :: h !< Layer thickness [H ~> m or kg m-2]. - real, dimension(SZIB_(G),SZJ_(G)), & - intent(out) :: uhbt !< Vertically summed thickness flux through - !! zonal faces [H L2 T-1 ~> m3 s-1 or kg s-1]. - real, dimension(SZI_(G),SZJB_(G)), & - intent(out) :: vhbt !< Vertically summed thickness flux through - !! meridional faces [H L2 T-1 ~> m3 s-1 or kg s-1]. - real, intent(in) :: dt !< Time increment [T ~> s]. - type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type - type(continuity_CS), intent(in) :: CS !< Control structure for mom_continuity. - type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. - type(porous_barrier_type), intent(in) :: pbv !< porous barrier fractional cell metrics - - ! Local variables - real :: h_W(SZI_(G),SZJ_(G),SZK_(GV)) ! West edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] - real :: h_E(SZI_(G),SZJ_(G),SZK_(GV)) ! East edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] - real :: h_S(SZI_(G),SZJ_(G),SZK_(GV)) ! South edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] - real :: h_N(SZI_(G),SZJ_(G),SZK_(GV)) ! North edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] - - call zonal_edge_thickness(h, h_W, h_E, G, GV, US, CS, OBC) - call zonal_BT_mass_flux(u, h, h_W, h_E, uhbt, dt, G, GV, US, CS, OBC, pbv%por_face_areaU) - - call meridional_edge_thickness(h, h_S, h_N, G, GV, US, CS, OBC) - call meridional_BT_mass_flux(v, h, h_S, h_N, vhbt, dt, G, GV, US, CS, OBC, pbv%por_face_areaV) - -end subroutine continuity_2d_fluxes - - -!> Correct the velocities to give the specified depth-integrated transports by applying a -!! barotropic acceleration (subject to viscous drag) to the velocities. -subroutine continuity_adjust_vel(u, v, h, dt, G, GV, US, CS, OBC, pbv, uhbt, vhbt, visc_rem_u, visc_rem_v) - type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure. - type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure. - real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & - intent(inout) :: u !< Zonal velocity, which will be adjusted to - !! give uhbt as the depth-integrated - !! transport [L T-1 ~> m s-1]. - real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & - intent(inout) :: v !< Meridional velocity, which will be adjusted - !! to give vhbt as the depth-integrated - !! transport [L T-1 ~> m s-1]. - real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & - intent(in) :: h !< Layer thickness [H ~> m or kg m-2]. - real, intent(in) :: dt !< Time increment [T ~> s]. - type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type - type(continuity_CS), intent(in) :: CS !< Control structure for mom_continuity. - type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. - type(porous_barrier_type), intent(in) :: pbv !< porous barrier fractional cell metrics - real, dimension(SZIB_(G),SZJ_(G)), & - intent(in) :: uhbt !< The vertically summed thickness flux through - !! zonal faces [H L2 T-1 ~> m3 s-1 or kg s-1]. - real, dimension(SZI_(G),SZJB_(G)), & - intent(in) :: vhbt !< The vertically summed thickness flux through - !! meridional faces [H L2 T-1 ~> m3 s-1 or kg s-1]. - real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & - optional, intent(in) :: visc_rem_u !< Both the fraction of the zonal momentum - !! that remains after a time-step of viscosity, and - !! the fraction of a time-step's worth of a barotropic - !! acceleration that a layer experiences after viscosity - !! is applied [nondim]. This goes between 0 (at the - !! bottom) and 1 (far above the bottom). When this - !! column is under an ice shelf, this also goes to 0 - !! at the top due to the no-slip boundary condition there. - real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & - optional, intent(in) :: visc_rem_v !< Both the fraction of the meridional momentum - !! that remains after a time-step of viscosity, and - !! the fraction of a time-step's worth of a barotropic - !! acceleration that a layer experiences after viscosity - !! is applied [nondim]. This goes between 0 (at the - !! bottom) and 1 (far above the bottom). When this - !! column is under an ice shelf, this also goes to 0 - !! at the top due to the no-slip boundary condition there. - - ! Local variables - real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: u_in !< Input zonal velocity [L T-1 ~> m s-1] - real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: v_in !< Input meridional velocity [L T-1 ~> m s-1] - real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: uh !< Volume flux through zonal faces = - !! u*h*dy [H L2 T-1 ~> m3 s-1 or kg s-1]. - real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: vh !< Volume flux through meridional faces = - !! v*h*dx [H L2 T-1 ~> m3 s-1 or kg s-1]. - real :: h_W(SZI_(G),SZJ_(G),SZK_(GV)) ! West edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] - real :: h_E(SZI_(G),SZJ_(G),SZK_(GV)) ! East edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] - real :: h_S(SZI_(G),SZJ_(G),SZK_(GV)) ! South edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] - real :: h_N(SZI_(G),SZJ_(G),SZK_(GV)) ! North edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] - - ! It might not be necessary to separate the input velocity array from the adjusted velocities, - ! but it seems safer to do so, even if it might be less efficient. - u_in(:,:,:) = u(:,:,:) - v_in(:,:,:) = v(:,:,:) - - call zonal_edge_thickness(h, h_W, h_E, G, GV, US, CS, OBC) - call zonal_mass_flux(u_in, h, h_W, h_E, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU, & - uhbt=uhbt, visc_rem_u=visc_rem_u, u_cor=u) - - call meridional_edge_thickness(h, h_S, h_N, G, GV, US, CS, OBC) - call meridional_mass_flux(v_in, h, h_S, h_N, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV, & - vhbt=vhbt, visc_rem_v=visc_rem_v, v_cor=v) - -end subroutine continuity_adjust_vel +public zonal_mass_flux, meridional_mass_flux +public zonal_edge_thickness, meridional_edge_thickness +public continuity_zonal_convergence, continuity_merdional_convergence +public zonal_flux_thickness, meridional_flux_thickness +public zonal_BT_mass_flux, meridional_BT_mass_flux +public set_continuity_loop_bounds, cont_loop_bounds_type end module MOM_continuity diff --git a/src/core/MOM_continuity_PPM.F90 b/src/core/MOM_continuity_PPM.F90 index f34131e03e..be2dabd9e6 100644 --- a/src/core/MOM_continuity_PPM.F90 +++ b/src/core/MOM_continuity_PPM.F90 @@ -19,6 +19,7 @@ module MOM_continuity_PPM #include public continuity_PPM, continuity_PPM_init, continuity_PPM_stencil +public continuity_fluxes, continuity_adjust_vel public zonal_mass_flux, meridional_mass_flux public zonal_edge_thickness, meridional_edge_thickness public continuity_zonal_convergence, continuity_merdional_convergence @@ -72,6 +73,12 @@ module MOM_continuity_PPM !>@} end type cont_loop_bounds_type +!> Finds the thickness fluxes from the continuity solver or their vertical sum without +!! actually updating the layer thicknesses. +interface continuity_fluxes + module procedure continuity_3d_fluxes, continuity_2d_fluxes +end interface continuity_fluxes + contains !> Time steps the layer thicknesses, using a monotonically limit, directionally split PPM scheme, @@ -180,6 +187,156 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhb end subroutine continuity_PPM +!> Finds the thickness fluxes from the continuity solver without actually updating the +!! layer thicknesses. Because the fluxes in the two directions are calculated based on the +!! input thicknesses, which are not updated between the direcitons, the fluxes returned here +!! are not the same as those that would be returned by a call to continuity. +subroutine continuity_3d_fluxes(u, v, h, uh, vh, dt, G, GV, US, CS, OBC, pbv) + type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure. + type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure. + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & + intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]. + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & + intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + intent(in) :: h !< Layer thickness [H ~> m or kg m-2]. + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & + intent(out) :: uh !< Thickness fluxes through zonal faces, + !! u*h*dy [H L2 T-1 ~> m3 s-1 or kg s-1]. + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & + intent(out) :: vh !< Thickness fluxes through meridional faces, + !! v*h*dx [H L2 T-1 ~> m3 s-1 or kg s-1]. + real, intent(in) :: dt !< Time increment [T ~> s]. + type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type + type(continuity_PPM_CS), intent(in) :: CS !< Control structure for mom_continuity. + type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. + type(porous_barrier_type), intent(in) :: pbv !< porous barrier fractional cell metrics + + ! Local variables + real :: h_W(SZI_(G),SZJ_(G),SZK_(GV)) ! West edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] + real :: h_E(SZI_(G),SZJ_(G),SZK_(GV)) ! East edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] + real :: h_S(SZI_(G),SZJ_(G),SZK_(GV)) ! South edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] + real :: h_N(SZI_(G),SZJ_(G),SZK_(GV)) ! North edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] + + call zonal_edge_thickness(h, h_W, h_E, G, GV, US, CS, OBC) + call zonal_mass_flux(u, h, h_W, h_E, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU) + + call meridional_edge_thickness(h, h_S, h_N, G, GV, US, CS, OBC) + call meridional_mass_flux(v, h, h_S, h_N, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV) + +end subroutine continuity_3d_fluxes + +!> Find the vertical sum of the thickness fluxes from the continuity solver without actually +!! updating the layer thicknesses. Because the fluxes in the two directions are calculated +!! based on the input thicknesses, which are not updated between the directions, the fluxes +!! returned here are not the same as those that would be returned by a call to continuity. +subroutine continuity_2d_fluxes(u, v, h, uhbt, vhbt, dt, G, GV, US, CS, OBC, pbv) + type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure. + type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure. + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & + intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]. + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & + intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + intent(in) :: h !< Layer thickness [H ~> m or kg m-2]. + real, dimension(SZIB_(G),SZJ_(G)), & + intent(out) :: uhbt !< Vertically summed thickness flux through + !! zonal faces [H L2 T-1 ~> m3 s-1 or kg s-1]. + real, dimension(SZI_(G),SZJB_(G)), & + intent(out) :: vhbt !< Vertically summed thickness flux through + !! meridional faces [H L2 T-1 ~> m3 s-1 or kg s-1]. + real, intent(in) :: dt !< Time increment [T ~> s]. + type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type + type(continuity_PPM_CS), intent(in) :: CS !< Control structure for mom_continuity. + type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. + type(porous_barrier_type), intent(in) :: pbv !< porous barrier fractional cell metrics + + ! Local variables + real :: h_W(SZI_(G),SZJ_(G),SZK_(GV)) ! West edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] + real :: h_E(SZI_(G),SZJ_(G),SZK_(GV)) ! East edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] + real :: h_S(SZI_(G),SZJ_(G),SZK_(GV)) ! South edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] + real :: h_N(SZI_(G),SZJ_(G),SZK_(GV)) ! North edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] + + call zonal_edge_thickness(h, h_W, h_E, G, GV, US, CS, OBC) + call zonal_BT_mass_flux(u, h, h_W, h_E, uhbt, dt, G, GV, US, CS, OBC, pbv%por_face_areaU) + + call meridional_edge_thickness(h, h_S, h_N, G, GV, US, CS, OBC) + call meridional_BT_mass_flux(v, h, h_S, h_N, vhbt, dt, G, GV, US, CS, OBC, pbv%por_face_areaV) + +end subroutine continuity_2d_fluxes + +!> Correct the velocities to give the specified depth-integrated transports by applying a +!! barotropic acceleration (subject to viscous drag) to the velocities. +subroutine continuity_adjust_vel(u, v, h, dt, G, GV, US, CS, OBC, pbv, uhbt, vhbt, visc_rem_u, visc_rem_v) + type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure. + type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure. + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & + intent(inout) :: u !< Zonal velocity, which will be adjusted to + !! give uhbt as the depth-integrated + !! transport [L T-1 ~> m s-1]. + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & + intent(inout) :: v !< Meridional velocity, which will be adjusted + !! to give vhbt as the depth-integrated + !! transport [L T-1 ~> m s-1]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + intent(in) :: h !< Layer thickness [H ~> m or kg m-2]. + real, intent(in) :: dt !< Time increment [T ~> s]. + type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type + type(continuity_PPM_CS), intent(in) :: CS !< Control structure for mom_continuity. + type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure. + type(porous_barrier_type), intent(in) :: pbv !< porous barrier fractional cell metrics + real, dimension(SZIB_(G),SZJ_(G)), & + intent(in) :: uhbt !< The vertically summed thickness flux through + !! zonal faces [H L2 T-1 ~> m3 s-1 or kg s-1]. + real, dimension(SZI_(G),SZJB_(G)), & + intent(in) :: vhbt !< The vertically summed thickness flux through + !! meridional faces [H L2 T-1 ~> m3 s-1 or kg s-1]. + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & + optional, intent(in) :: visc_rem_u !< Both the fraction of the zonal momentum + !! that remains after a time-step of viscosity, and + !! the fraction of a time-step's worth of a barotropic + !! acceleration that a layer experiences after viscosity + !! is applied [nondim]. This goes between 0 (at the + !! bottom) and 1 (far above the bottom). When this + !! column is under an ice shelf, this also goes to 0 + !! at the top due to the no-slip boundary condition there. + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & + optional, intent(in) :: visc_rem_v !< Both the fraction of the meridional momentum + !! that remains after a time-step of viscosity, and + !! the fraction of a time-step's worth of a barotropic + !! acceleration that a layer experiences after viscosity + !! is applied [nondim]. This goes between 0 (at the + !! bottom) and 1 (far above the bottom). When this + !! column is under an ice shelf, this also goes to 0 + !! at the top due to the no-slip boundary condition there. + + ! Local variables + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: u_in !< Input zonal velocity [L T-1 ~> m s-1] + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: v_in !< Input meridional velocity [L T-1 ~> m s-1] + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: uh !< Volume flux through zonal faces = + !! u*h*dy [H L2 T-1 ~> m3 s-1 or kg s-1]. + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: vh !< Volume flux through meridional faces = + !! v*h*dx [H L2 T-1 ~> m3 s-1 or kg s-1]. + real :: h_W(SZI_(G),SZJ_(G),SZK_(GV)) ! West edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] + real :: h_E(SZI_(G),SZJ_(G),SZK_(GV)) ! East edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] + real :: h_S(SZI_(G),SZJ_(G),SZK_(GV)) ! South edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] + real :: h_N(SZI_(G),SZJ_(G),SZK_(GV)) ! North edge thicknesses in the meridional PPM reconstruction [H ~> m or kg m-2] + + ! It might not be necessary to separate the input velocity array from the adjusted velocities, + ! but it seems safer to do so, even if it might be less efficient. + u_in(:,:,:) = u(:,:,:) + v_in(:,:,:) = v(:,:,:) + + call zonal_edge_thickness(h, h_W, h_E, G, GV, US, CS, OBC) + call zonal_mass_flux(u_in, h, h_W, h_E, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU, & + uhbt=uhbt, visc_rem_u=visc_rem_u, u_cor=u) + + call meridional_edge_thickness(h, h_S, h_N, G, GV, US, CS, OBC) + call meridional_mass_flux(v_in, h, h_S, h_N, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV, & + vhbt=vhbt, visc_rem_v=visc_rem_v, v_cor=v) + +end subroutine continuity_adjust_vel + !> Updates the thicknesses due to zonal thickness fluxes. subroutine continuity_zonal_convergence(h, uh, dt, G, GV, LB, hin, hmin) From 78772923df3c8014512cb143e4b3baaec4c3bfdf Mon Sep 17 00:00:00 2001 From: Robert Hallberg Date: Tue, 12 Dec 2023 18:35:30 -0500 Subject: [PATCH 08/22] +Add optional argument du_cor to continuity_PPM Added the new optional arguments du_cor and dv_cor to continuity_PPM and zonal_mass_flux or meridional_mass_flux to return the barotropic velocity increments that make the summed barotropic transports match uhbt or vhbt. Also cleaned up and simplified the logic of some of the flags used to apply specified open boundary conditions, adding a new 1-d logical array thereby avoiding working unnecessarily on some loops or repeatedly checking for specified open boundary condition points. Two openMP directives were also simplified. All answers are bitwise identical, but there are new optional arguments to three publicly visible routines. --- src/core/MOM_continuity_PPM.F90 | 172 +++++++++++++++++--------------- 1 file changed, 91 insertions(+), 81 deletions(-) diff --git a/src/core/MOM_continuity_PPM.F90 b/src/core/MOM_continuity_PPM.F90 index be2dabd9e6..ba8c234bc2 100644 --- a/src/core/MOM_continuity_PPM.F90 +++ b/src/core/MOM_continuity_PPM.F90 @@ -84,7 +84,7 @@ module MOM_continuity_PPM !> Time steps the layer thicknesses, using a monotonically limit, directionally split PPM scheme, !! based on Lin (1994). subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhbt, vhbt, & - visc_rem_u, visc_rem_v, u_cor, v_cor, BT_cont) + visc_rem_u, visc_rem_v, u_cor, v_cor, BT_cont, du_cor, dv_cor) type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure. type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure. real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & @@ -133,6 +133,12 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhb !! transport [L T-1 ~> m s-1]. type(BT_cont_type), optional, pointer :: BT_cont !< A structure with elements that describe !! the effective open face areas as a function of barotropic flow. + real, dimension(SZIB_(G),SZJ_(G)), & + optional, intent(out) :: du_cor !< The zonal velocity increments from u that give uhbt + !! as the depth-integrated transports [L T-1 ~> m s-1]. + real, dimension(SZI_(G),SZJB_(G)), & + optional, intent(out) :: dv_cor !< The meridional velocity increments from v that give vhbt + !! as the depth-integrated transports [L T-1 ~> m s-1]. ! Local variables real :: h_W(SZI_(G),SZJ_(G),SZK_(GV)) ! West edge thicknesses in the zonal PPM reconstruction [H ~> m or kg m-2] @@ -159,14 +165,14 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhb LB = set_continuity_loop_bounds(G, CS, i_stencil=.false., j_stencil=.true.) call zonal_edge_thickness(hin, h_W, h_E, G, GV, US, CS, OBC, LB) call zonal_mass_flux(u, hin, h_W, h_E, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU, & - LB, uhbt, visc_rem_u, u_cor, BT_cont) + LB, uhbt, visc_rem_u, u_cor, BT_cont, du_cor) call continuity_zonal_convergence(h, uh, dt, G, GV, LB, hin) ! Now advect meridionally, using the updated thicknesses to determine the fluxes. LB = set_continuity_loop_bounds(G, CS, i_stencil=.false., j_stencil=.false.) call meridional_edge_thickness(h, h_S, h_N, G, GV, US, CS, OBC, LB) call meridional_mass_flux(v, h, h_S, h_N, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV, & - LB, vhbt, visc_rem_v, v_cor, BT_cont) + LB, vhbt, visc_rem_v, v_cor, BT_cont, dv_cor) call continuity_merdional_convergence(h, vh, dt, G, GV, LB, hmin=h_min) else ! .not. x_first @@ -174,14 +180,14 @@ subroutine continuity_PPM(u, v, hin, h, uh, vh, dt, G, GV, US, CS, OBC, pbv, uhb LB = set_continuity_loop_bounds(G, CS, i_stencil=.true., j_stencil=.false.) call meridional_edge_thickness(hin, h_S, h_N, G, GV, US, CS, OBC, LB) call meridional_mass_flux(v, hin, h_S, h_N, vh, dt, G, GV, US, CS, OBC, pbv%por_face_areaV, & - LB, vhbt, visc_rem_v, v_cor, BT_cont) + LB, vhbt, visc_rem_v, v_cor, BT_cont, dv_cor) call continuity_merdional_convergence(h, vh, dt, G, GV, LB, hin) ! Now advect zonally, using the updated thicknesses to determine the fluxes. LB = set_continuity_loop_bounds(G, CS, i_stencil=.false., j_stencil=.false.) call zonal_edge_thickness(h, h_W, h_E, G, GV, US, CS, OBC, LB) call zonal_mass_flux(u, h, h_W, h_E, uh, dt, G, GV, US, CS, OBC, pbv%por_face_areaU, & - LB, uhbt, visc_rem_u, u_cor, BT_cont) + LB, uhbt, visc_rem_u, u_cor, BT_cont, du_cor) call continuity_zonal_convergence(h, uh, dt, G, GV, LB, hmin=h_min) endif @@ -511,7 +517,7 @@ end subroutine meridional_edge_thickness !> Calculates the mass or volume fluxes through the zonal faces, and other related quantities. subroutine zonal_mass_flux(u, h_in, h_W, h_E, uh, dt, G, GV, US, CS, OBC, por_face_areaU, & - LB_in, uhbt, visc_rem_u, u_cor, BT_cont) + LB_in, uhbt, visc_rem_u, u_cor, BT_cont, du_cor) type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & @@ -548,15 +554,18 @@ subroutine zonal_mass_flux(u, h_in, h_W, h_E, uh, dt, G, GV, US, CS, OBC, por_fa !! that give uhbt as the depth-integrated transport [L T-1 ~> m s-1] type(BT_cont_type), optional, pointer :: BT_cont !< A structure with elements that describe the !! effective open face areas as a function of barotropic flow. + real, dimension(SZIB_(G),SZJ_(G)), & + optional, intent(out) :: du_cor !< The zonal velocity increments from u that give uhbt + !! as the depth-integrated transports [L T-1 ~> m s-1]. ! Local variables real, dimension(SZIB_(G),SZK_(GV)) :: duhdu ! Partial derivative of uh with u [H L ~> m2 or kg m-1]. real, dimension(SZIB_(G)) :: & - du, & ! Corrective barotropic change in the velocity [L T-1 ~> m s-1]. + du, & ! Corrective barotropic change in the velocity to give uhbt [L T-1 ~> m s-1]. du_min_CFL, & ! Lower limit on du correction to avoid CFL violations [L T-1 ~> m s-1] du_max_CFL, & ! Upper limit on du correction to avoid CFL violations [L T-1 ~> m s-1] duhdu_tot_0, & ! Summed partial derivative of uh with u [H L ~> m2 or kg m-1]. - uh_tot_0, & ! Summed transport with no barotropic correction [H L2 T-1 ~> m3 s-1 or kg s-1]. + uh_tot_0, & ! Summed transport with no barotropic correction [H L2 T-1 ~> m3 s-1 or kg s-1]. visc_rem_max ! The column maximum of visc_rem [nondim]. logical, dimension(SZIB_(G)) :: do_I real, dimension(SZIB_(G),SZK_(GV)) :: & @@ -571,22 +580,26 @@ subroutine zonal_mass_flux(u, h_in, h_W, h_E, uh, dt, G, GV, US, CS, OBC, por_fa real :: dx_E, dx_W ! Effective x-grid spacings to the east and west [L ~> m]. type(cont_loop_bounds_type) :: LB integer :: i, j, k, ish, ieh, jsh, jeh, n, nz - integer :: l_seg - logical :: local_specified_BC, use_visc_rem, set_BT_cont, any_simple_OBC - logical :: local_Flather_OBC, local_open_BC, is_simple + integer :: l_seg ! The OBC segment number + logical :: use_visc_rem, set_BT_cont + logical :: local_specified_BC, local_Flather_OBC, local_open_BC, any_simple_OBC ! OBC-related logicals + logical :: simple_OBC_pt(SZIB_(G)) ! Indicates points in a row with specified transport OBCs call cpu_clock_begin(id_clock_correct) use_visc_rem = present(visc_rem_u) - local_specified_BC = .false. ; set_BT_cont = .false. ; local_Flather_OBC = .false. - local_open_BC = .false. - if (present(BT_cont)) set_BT_cont = (associated(BT_cont)) + + set_BT_cont = .false. ; if (present(BT_cont)) set_BT_cont = (associated(BT_cont)) + + local_specified_BC = .false. ; local_Flather_OBC = .false. ; local_open_BC = .false. if (associated(OBC)) then ; if (OBC%OBC_pe) then local_specified_BC = OBC%specified_u_BCs_exist_globally local_Flather_OBC = OBC%Flather_u_BCs_exist_globally local_open_BC = OBC%open_u_BCs_exist_globally endif ; endif + if (present(du_cor)) du_cor(:,:) = 0.0 + if (present(LB_in)) then LB = LB_in else @@ -599,14 +612,10 @@ subroutine zonal_mass_flux(u, h_in, h_W, h_E, uh, dt, G, GV, US, CS, OBC, por_fa if (CS%aggress_adjust) CFL_dt = I_dt if (.not.use_visc_rem) visc_rem(:,:) = 1.0 -!$OMP parallel do default(none) shared(ish,ieh,jsh,jeh,nz,u,h_in,h_W,h_E,use_visc_rem,visc_rem_u, & -!$OMP uh,dt,US,G,GV,CS,local_specified_BC,OBC,uhbt,set_BT_cont, & -!$OMP CFL_dt,I_dt,u_cor,BT_cont, local_Flather_OBC, & -!$OMP por_face_areaU) & -!$OMP private(do_I,duhdu,du,du_max_CFL,du_min_CFL,uh_tot_0,duhdu_tot_0, & -!$OMP is_simple,FAuI,visc_rem_max,I_vrm,du_lim,dx_E,dx_W, & -!$OMP any_simple_OBC,l_seg) & -!$OMP firstprivate(visc_rem) + !$OMP parallel do default(shared) private(do_I,duhdu,du,du_max_CFL,du_min_CFL,uh_tot_0, & + !$OMP duhdu_tot_0,FAuI,visc_rem_max,I_vrm,du_lim,dx_E,dx_W, & + !$OMP simple_OBC_pt,any_simple_OBC,l_seg) & + !$OMP firstprivate(visc_rem) do j=jsh,jeh do I=ish-1,ieh ; do_I(I) = .true. ; enddo ! Set uh and duhdu. @@ -716,30 +725,32 @@ subroutine zonal_mass_flux(u, h_in, h_W, h_E, uh, dt, G, GV, US, CS, OBC, por_fa l_seg = OBC%segnum_u(I,j) ! Avoid reconciling barotropic/baroclinic transports if transport is specified - is_simple = .false. - if (l_seg /= OBC_NONE) is_simple = OBC%segment(l_seg)%specified - do_I(I) = .not. (l_seg /= OBC_NONE .and. is_simple) - any_simple_OBC = any_simple_OBC .or. is_simple + simple_OBC_pt(I) = .false. + if (l_seg /= OBC_NONE) simple_OBC_pt(I) = OBC%segment(l_seg)%specified + do_I(I) = .not.simple_OBC_pt(I) + any_simple_OBC = any_simple_OBC .or. simple_OBC_pt(I) enddo ; else ; do I=ish-1,ieh do_I(I) = .true. enddo ; endif endif if (present(uhbt)) then + ! Find du and uh. call zonal_flux_adjust(u, h_in, h_W, h_E, uhbt(:,j), uh_tot_0, duhdu_tot_0, du, & du_max_CFL, du_min_CFL, dt, G, GV, US, CS, visc_rem, & j, ish, ieh, do_I, por_face_areaU, uh, OBC=OBC) if (present(u_cor)) then ; do k=1,nz do I=ish-1,ieh ; u_cor(I,j,k) = u(I,j,k) + du(I) * visc_rem(I,k) ; enddo - if (local_specified_BC) then ; do I=ish-1,ieh - if (OBC%segnum_u(I,j) /= OBC_NONE) then - l_seg = OBC%segnum_u(I,j) - if (OBC%segment(l_seg)%specified) u_cor(I,j,k) = OBC%segment(l_seg)%normal_vel(I,j,k) - endif - enddo ; endif + if (any_simple_OBC) then ; do I=ish-1,ieh ; if (simple_OBC_pt(I)) then + u_cor(I,j,k) = OBC%segment(OBC%segnum_u(I,j))%normal_vel(I,j,k) + endif ; enddo ; endif enddo ; endif ! u-corrected + if (present(du_cor)) then + do I=ish-1,ieh ; du_cor(I,j) = du(I) ; enddo + endif + endif if (set_BT_cont) then @@ -748,19 +759,16 @@ subroutine zonal_mass_flux(u, h_in, h_W, h_E, uh, dt, G, GV, US, CS, OBC, por_fa visc_rem_max, j, ish, ieh, do_I, por_face_areaU) if (any_simple_OBC) then do I=ish-1,ieh - do_I(I) = .false. - if (OBC%segnum_u(I,j) /= OBC_NONE) do_I(I) = OBC%segment(OBC%segnum_u(I,j))%specified - - if (do_I(I)) FAuI(I) = GV%H_subroundoff*G%dy_Cu(I,j) + if (simple_OBC_pt(I)) FAuI(I) = GV%H_subroundoff*G%dy_Cu(I,j) enddo - ! NOTE: do_I(I) should prevent access to segment OBC_NONE - do k=1,nz ; do I=ish-1,ieh ; if (do_I(I)) then + ! NOTE: simple_OBC_pt(I) should prevent access to segment OBC_NONE + do k=1,nz ; do I=ish-1,ieh ; if (simple_OBC_pt(I)) then if ((abs(OBC%segment(OBC%segnum_u(I,j))%normal_vel(I,j,k)) > 0.0) .and. & (OBC%segment(OBC%segnum_u(I,j))%specified)) & FAuI(I) = FAuI(I) + OBC%segment(OBC%segnum_u(I,j))%normal_trans(I,j,k) / & OBC%segment(OBC%segnum_u(I,j))%normal_vel(I,j,k) endif ; enddo ; enddo - do I=ish-1,ieh ; if (do_I(I)) then + do I=ish-1,ieh ; if (simple_OBC_pt(I)) then BT_cont%FA_u_W0(I,j) = FAuI(I) ; BT_cont%FA_u_E0(I,j) = FAuI(I) BT_cont%FA_u_WW(I,j) = FAuI(I) ; BT_cont%FA_u_EE(I,j) = FAuI(I) BT_cont%uBT_WW(I,j) = 0.0 ; BT_cont%uBT_EE(I,j) = 0.0 @@ -1101,7 +1109,7 @@ subroutine zonal_flux_adjust(u, h_in, h_W, h_E, uhbt, uh_tot_0, duhdu_tot_0, & !! the fraction of a time-step's worth of a barotropic acceleration that a layer !! experiences after viscosity is applied [nondim]. !! Visc_rem is between 0 (at the bottom) and 1 (far above the bottom). - real, dimension(SZIB_(G)), optional, intent(in) :: uhbt !< The summed volume flux + real, dimension(SZIB_(G)), intent(in) :: uhbt !< The summed volume flux !! through zonal faces [H L2 T-1 ~> m3 s-1 or kg s-1]. real, dimension(SZIB_(G)), intent(in) :: du_max_CFL !< Maximum acceptable @@ -1403,7 +1411,7 @@ end subroutine set_zonal_BT_cont !> Calculates the mass or volume fluxes through the meridional faces, and other related quantities. subroutine meridional_mass_flux(v, h_in, h_S, h_N, vh, dt, G, GV, US, CS, OBC, por_face_areaV, & - LB_in, vhbt, visc_rem_v, v_cor, BT_cont) + LB_in, vhbt, visc_rem_v, v_cor, BT_cont, dv_cor) type(ocean_grid_type), intent(in) :: G !< Ocean's grid structure. type(verticalGrid_type), intent(in) :: GV !< Ocean's vertical grid structure. real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1] @@ -1437,11 +1445,16 @@ subroutine meridional_mass_flux(v, h_in, h_S, h_N, vh, dt, G, GV, US, CS, OBC, p !! that give vhbt as the depth-integrated transport [L T-1 ~> m s-1]. type(BT_cont_type), optional, pointer :: BT_cont !< A structure with elements that describe !! the effective open face areas as a function of barotropic flow. + real, dimension(SZI_(G),SZJB_(G)), & + optional, intent(out) :: dv_cor !< The meridional velocity increments from v + !! that give vhbt as the depth-integrated + !! transports [L T-1 ~> m s-1]. + ! Local variables real, dimension(SZI_(G),SZK_(GV)) :: & - dvhdv ! Partial derivative of vh with v [H L ~> m2 or kg m-1]. + dvhdv ! Partial derivative of vh with v [H L ~> m2 or kg m-1]. real, dimension(SZI_(G)) :: & - dv, & ! Corrective barotropic change in the velocity [L T-1 ~> m s-1]. + dv, & ! Corrective barotropic change in the velocity to give vhbt [L T-1 ~> m s-1]. dv_min_CFL, & ! Lower limit on dv correction to avoid CFL violations [L T-1 ~> m s-1] dv_max_CFL, & ! Upper limit on dv correction to avoid CFL violations [L T-1 ~> m s-1] dvhdv_tot_0, & ! Summed partial derivative of vh with v [H L ~> m2 or kg m-1]. @@ -1460,22 +1473,26 @@ subroutine meridional_mass_flux(v, h_in, h_S, h_N, vh, dt, G, GV, US, CS, OBC, p real :: dy_N, dy_S ! Effective y-grid spacings to the north and south [L ~> m]. type(cont_loop_bounds_type) :: LB integer :: i, j, k, ish, ieh, jsh, jeh, n, nz - integer :: l_seg - logical :: local_specified_BC, use_visc_rem, set_BT_cont, any_simple_OBC - logical :: local_Flather_OBC, is_simple, local_open_BC + integer :: l_seg ! The OBC segment number + logical :: use_visc_rem, set_BT_cont + logical :: local_specified_BC, local_Flather_OBC, local_open_BC, any_simple_OBC ! OBC-related logicals + logical :: simple_OBC_pt(SZI_(G)) ! Indicates points in a row with specified transport OBCs call cpu_clock_begin(id_clock_correct) use_visc_rem = present(visc_rem_v) - local_specified_BC = .false. ; set_BT_cont = .false. ; local_Flather_OBC = .false. - local_open_BC = .false. - if (present(BT_cont)) set_BT_cont = (associated(BT_cont)) + + set_BT_cont = .false. ; if (present(BT_cont)) set_BT_cont = (associated(BT_cont)) + + local_specified_BC = .false. ; local_Flather_OBC = .false. ; local_open_BC = .false. if (associated(OBC)) then ; if (OBC%OBC_pe) then local_specified_BC = OBC%specified_v_BCs_exist_globally local_Flather_OBC = OBC%Flather_v_BCs_exist_globally local_open_BC = OBC%open_v_BCs_exist_globally endif ; endif + if (present(dv_cor)) dv_cor(:,:) = 0.0 + if (present(LB_in)) then LB = LB_in else @@ -1488,14 +1505,10 @@ subroutine meridional_mass_flux(v, h_in, h_S, h_N, vh, dt, G, GV, US, CS, OBC, p if (CS%aggress_adjust) CFL_dt = I_dt if (.not.use_visc_rem) visc_rem(:,:) = 1.0 -!$OMP parallel do default(none) shared(ish,ieh,jsh,jeh,nz,v,h_in,h_S,h_N,vh,use_visc_rem, & -!$OMP visc_rem_v,dt,US,G,GV,CS,local_specified_BC,OBC,vhbt, & -!$OMP set_BT_cont,CFL_dt,I_dt,v_cor,BT_cont, local_Flather_OBC, & -!$OMP por_face_areaV) & -!$OMP private(do_I,dvhdv,dv,dv_max_CFL,dv_min_CFL,vh_tot_0, & -!$OMP dvhdv_tot_0,visc_rem_max,I_vrm,dv_lim,dy_N, & -!$OMP is_simple,FAvi,dy_S,any_simple_OBC,l_seg) & -!$OMP firstprivate(visc_rem) + !$OMP parallel do default(shared) private(do_I,dvhdv,dv,dv_max_CFL,dv_min_CFL,vh_tot_0, & + !$OMP dvhdv_tot_0,FAvi,visc_rem_max,I_vrm,dv_lim,dy_N,dy_S, & + !$OMP simple_OBC_pt,any_simple_OBC,l_seg) & + !$OMP firstprivate(visc_rem) do J=jsh-1,jeh do i=ish,ieh ; do_I(i) = .true. ; enddo ! This sets vh and dvhdv. @@ -1602,31 +1615,32 @@ subroutine meridional_mass_flux(v, h_in, h_S, h_N, vh, dt, G, GV, US, CS, OBC, p l_seg = OBC%segnum_v(i,J) ! Avoid reconciling barotropic/baroclinic transports if transport is specified - is_simple = .false. - if (l_seg /= OBC_NONE) is_simple = OBC%segment(l_seg)%specified - do_I(i) = .not.(l_seg /= OBC_NONE .and. is_simple) - any_simple_OBC = any_simple_OBC .or. is_simple + simple_OBC_pt(i) = .false. + if (l_seg /= OBC_NONE) simple_OBC_pt(i) = OBC%segment(l_seg)%specified + do_I(i) = .not.simple_OBC_pt(i) + any_simple_OBC = any_simple_OBC .or. simple_OBC_pt(i) enddo ; else ; do i=ish,ieh do_I(i) = .true. enddo ; endif endif if (present(vhbt)) then + ! Find dv and vh. call meridional_flux_adjust(v, h_in, h_S, h_N, vhbt(:,J), vh_tot_0, dvhdv_tot_0, dv, & dv_max_CFL, dv_min_CFL, dt, G, GV, US, CS, visc_rem, & j, ish, ieh, do_I, por_face_areaV, vh, OBC=OBC) if (present(v_cor)) then ; do k=1,nz do i=ish,ieh ; v_cor(i,J,k) = v(i,J,k) + dv(i) * visc_rem(i,k) ; enddo - if (local_specified_BC) then ; do i=ish,ieh - l_seg = OBC%segnum_v(i,J) - - if (l_seg /= OBC_NONE) then - if (OBC%segment(OBC%segnum_v(i,J))%specified) & - v_cor(i,J,k) = OBC%segment(OBC%segnum_v(i,J))%normal_vel(i,J,k) - endif - enddo ; endif + if (any_simple_OBC) then ; do i=ish,ieh ; if (simple_OBC_pt(i)) then + v_cor(i,J,k) = OBC%segment(OBC%segnum_v(i,J))%normal_vel(i,J,k) + endif ; enddo ; endif enddo ; endif ! v-corrected + + if (present(dv_cor)) then + do i=ish,ieh ; dv_cor(i,J) = dv(i) ; enddo + endif + endif if (set_BT_cont) then @@ -1635,19 +1649,16 @@ subroutine meridional_mass_flux(v, h_in, h_S, h_N, vh, dt, G, GV, US, CS, OBC, p visc_rem_max, J, ish, ieh, do_I, por_face_areaV) if (any_simple_OBC) then do i=ish,ieh - do_I(I) = .false. - if (OBC%segnum_v(i,J) /= OBC_NONE) do_I(i) = (OBC%segment(OBC%segnum_v(i,J))%specified) - - if (do_I(i)) FAvi(i) = GV%H_subroundoff*G%dx_Cv(i,J) + if (simple_OBC_pt(i)) FAvi(i) = GV%H_subroundoff*G%dx_Cv(i,J) enddo - ! NOTE: do_I(I) should prevent access to segment OBC_NONE - do k=1,nz ; do i=ish,ieh ; if (do_I(i)) then + ! NOTE: simple_OBC_pt(i) should prevent access to segment OBC_NONE + do k=1,nz ; do i=ish,ieh ; if (simple_OBC_pt(i)) then if ((abs(OBC%segment(OBC%segnum_v(i,J))%normal_vel(i,J,k)) > 0.0) .and. & (OBC%segment(OBC%segnum_v(i,J))%specified)) & FAvi(i) = FAvi(i) + OBC%segment(OBC%segnum_v(i,J))%normal_trans(i,J,k) / & OBC%segment(OBC%segnum_v(i,J))%normal_vel(i,J,k) endif ; enddo ; enddo - do i=ish,ieh ; if (do_I(i)) then + do i=ish,ieh ; if (simple_OBC_pt(i)) then BT_cont%FA_v_S0(i,J) = FAvi(i) ; BT_cont%FA_v_N0(i,J) = FAvi(i) BT_cont%FA_v_SS(i,J) = FAvi(i) ; BT_cont%FA_v_NN(i,J) = FAvi(i) BT_cont%vBT_SS(i,J) = 0.0 ; BT_cont%vBT_NN(i,J) = 0.0 @@ -2000,15 +2011,14 @@ subroutine meridional_flux_adjust(v, h_in, h_S, h_N, vhbt, vh_tot_0, dvhdv_tot_0 !! fraction of a time-step's worth of a barotropic acceleration that !! a layer experiences after viscosity is applied [nondim]. !! Visc_rem is between 0 (at the bottom) and 1 (far above the bottom). - real, dimension(SZI_(G)), & - optional, intent(in) :: vhbt !< The summed volume flux through meridional faces + real, dimension(SZI_(G)), intent(in) :: vhbt !< The summed volume flux through meridional faces !! [H L2 T-1 ~> m3 s-1 or kg s-1]. real, dimension(SZI_(G)), intent(in) :: dv_max_CFL !< Maximum acceptable value of dv [L T-1 ~> m s-1]. real, dimension(SZI_(G)), intent(in) :: dv_min_CFL !< Minimum acceptable value of dv [L T-1 ~> m s-1]. real, dimension(SZI_(G)), intent(in) :: vh_tot_0 !< The summed transport with 0 adjustment - !! [H L2 T-1 ~> m3 s-1 or kg s-1]. + !! [H L2 T-1 ~> m3 s-1 or kg s-1]. real, dimension(SZI_(G)), intent(in) :: dvhdv_tot_0 !< The partial derivative of dv_err with - !! dv at 0 adjustment [H L ~> m2 or kg m-1]. + !! dv at 0 adjustment [H L ~> m2 or kg m-1]. real, dimension(SZI_(G)), intent(out) :: dv !< The barotropic velocity adjustment [L T-1 ~> m s-1]. real, intent(in) :: dt !< Time increment [T ~> s]. type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type @@ -2036,7 +2046,7 @@ subroutine meridional_flux_adjust(v, h_in, h_S, h_N, vhbt, vh_tot_0, dvhdv_tot_0 dv_min, & ! Lower limit on dv correction based on CFL limits and previous iterations [L T-1 ~> m s-1] dv_max ! Upper limit on dv correction based on CFL limits and previous iterations [L T-1 ~> m s-1] real :: dv_prev ! The previous value of dv [L T-1 ~> m s-1]. - real :: ddv ! The change in dv from the previous iteration [L T-1 ~> m s-1]. + real :: ddv ! The change in dv from the previous iteration [L T-1 ~> m s-1]. real :: tol_eta ! The tolerance for the current iteration [H ~> m or kg m-2]. real :: tol_vel ! The tolerance for velocity in the current iteration [L T-1 ~> m s-1]. integer :: i, k, nz, itt, max_itts = 20 From 7d334f8867675b2902716789807e46d7e7510f9c Mon Sep 17 00:00:00 2001 From: Marshall Ward Date: Wed, 13 Dec 2023 13:13:00 -0500 Subject: [PATCH 09/22] Makedep: Include support for CPP condition blocks This patch adds support to makedep for handling most #ifdef-like condition blocks. The following preprocessing commands are handled: * #define / #undef * #ifdef / #else / #endif A new flag is added to provide defined macros (-D), and is chosen to match the `cpp` flag, so that flags can be shared across programs. Macros are tracked in a new internal variable and are used for #ifdef testing. Nested condition blocks are supported by using an internal stack of the exclusion state. Certain cases are still not handled. * #if blocks containing logical expressions are not parsed. * CPP content inside of #include is ignored. No doubt many other cases are still unconsidered, such as exotic macro names. The autoconf builds use this feature by passing the generated $(DEFS) argument to makedep. This is suitable for now, but we may need to consider two cases in the future: * Macros defined in $CPPFLAGS are currently ignored, and perhaps they should be included here. The risk is that it may contain non-macro flags. * At some point, DEFS could be moved to a config.h file, and DEFS would no longer contain these macros. (Note that this is very unlikely at the moment, since this feature only works with C.) --- ac/Makefile.in | 3 +- ac/makedep | 93 +++++++++++++++++++++++++++++++++++++++++++++++--- 2 files changed, 89 insertions(+), 7 deletions(-) diff --git a/ac/Makefile.in b/ac/Makefile.in index 64a60e70d1..c4d23efdfb 100644 --- a/ac/Makefile.in +++ b/ac/Makefile.in @@ -19,7 +19,6 @@ SRC_DIRS = @SRC_DIRS@ -include Makefile.dep - # Generate Makefile from template Makefile: @srcdir@/ac/Makefile.in config.status ./config.status @@ -33,7 +32,7 @@ rwildcard=$(foreach d,$(wildcard $(1:=/*)),$(call rwildcard,$d,$2) $(filter $(su .PHONY: depend depend: Makefile.dep Makefile.dep: $(MAKEDEP) $(call rwildcard,$(SRC_DIRS),*.h *.c *.inc *.F90) - $(PYTHON) $(MAKEDEP) -o Makefile.dep -e $(SRC_DIRS) + $(PYTHON) $(MAKEDEP) $(DEFS) -o Makefile.dep -e $(SRC_DIRS) # Delete any files associated with configuration (including the Makefile). diff --git a/ac/makedep b/ac/makedep index 99c2ef6ce6..e37f35aca5 100755 --- a/ac/makedep +++ b/ac/makedep @@ -13,9 +13,16 @@ import sys # Pre-compile re searches re_module = re.compile(r"^ *module +([a-z_0-9]+)") re_use = re.compile(r"^ *use +([a-z_0-9]+)") +re_cpp_define = re.compile(r"^ *# *define +[_a-zA-Z][_a-zA-Z0-9]") +re_cpp_undef = re.compile(r"^ *# *undef +[_a-zA-Z][_a-zA-Z0-9]") +re_cpp_ifdef = re.compile(r"^ *# *ifdef +[_a-zA-Z][_a-zA-Z0-9]") +re_cpp_ifndef = re.compile(r"^ *# *ifndef +[_a-zA-Z][_a-zA-Z0-9]") +re_cpp_if = re.compile(r"^ *# *if +") +re_cpp_else = re.compile(r"^ *# *else") +re_cpp_endif = re.compile(r"^ *# *endif") re_cpp_include = re.compile(r"^ *# *include *[<\"']([a-zA-Z_0-9\.]+)[>\"']") re_f90_include = re.compile(r"^ *include +[\"']([a-zA-Z_0-9\.]+)[\"']") -re_program = re.compile(r"^ *[pP][rR][oO][gG][rR][aA][mM] +([a-zA-Z_0-9]+)") +re_program = re.compile(r"^ *program +([a-z_0-9]+)", re.IGNORECASE) re_end = re.compile(r"^ *end *(module|procedure) ", re.IGNORECASE) # NOTE: This excludes comments and tokens with substrings containing `function` # or `subroutine`, but will fail if the keywords appear in other contexts. @@ -26,7 +33,7 @@ re_procedure = re.compile( def create_deps(src_dirs, skip_dirs, makefile, debug, exec_target, fc_rule, - link_externals, script_path): + link_externals, defines): """Create "makefile" after scanning "src_dis".""" # Scan everything Fortran related @@ -66,7 +73,7 @@ def create_deps(src_dirs, skip_dirs, makefile, debug, exec_target, fc_rule, o2mods, o2uses, o2h, o2inc, o2prg, prg2o, mod2o = {}, {}, {}, {}, {}, {}, {} externals, all_modules = [], [] for f in F90_files: - mods, used, cpp, inc, prg, has_externals = scan_fortran_file(f) + mods, used, cpp, inc, prg, has_externals = scan_fortran_file(f, defines) # maps object file to modules produced o2mods[object_file(f)] = mods # maps module produced to object file @@ -272,10 +279,16 @@ def nested_inc(inc_files, f2F): return inc_files + sorted(set(hlst)), used_mods -def scan_fortran_file(src_file): +def scan_fortran_file(src_file, defines=None): """Scan the Fortran file "src_file" and return lists of module defined, module used, and files included.""" module_decl, used_modules, cpp_includes, f90_includes, programs = [], [], [], [], [] + + cpp_defines = defines if defines is not None else [] + + cpp_macros = [define.split('=')[0] for define in cpp_defines] + cpp_group_stack = [] + with io.open(src_file, 'r', errors='replace') as file: lines = file.readlines() @@ -285,7 +298,72 @@ def scan_fortran_file(src_file): file_has_externals = False # True if the file contains any external objects + cpp_exclude = False + # True if the parser excludes the subsequent lines + + cpp_group_stack = [] + # Stack of condition group exclusion states + for line in lines: + # Start of #ifdef condition group + match = re_cpp_ifdef.match(line) + if match: + cpp_group_stack.append(cpp_exclude) + + # If outer group is excluding or macro is missing, then exclude + macro = line.lstrip()[1:].split()[1] + cpp_exclude = cpp_exclude or macro not in cpp_macros + + # Start of #ifndef condition group + match = re_cpp_ifndef.match(line) + if match: + cpp_group_stack.append(cpp_exclude) + + # If outer group is excluding or macro is present, then exclude + macro = line.lstrip()[1:].split()[1] + cpp_exclude = cpp_exclude or macro in cpp_macros + + # Start of #if condition group + match = re_cpp_if.match(line) + if match: + cpp_group_stack.append(cpp_exclude) + + # XXX: Don't attempt to parse #if statements, but store the state. + # if/endif stack. For now, assume that these always fail. + cpp_exclude = False + + # Complement #else condition group + match = re_cpp_else.match(line) + if match: + # Reverse the exclude state, if there is no outer exclude state + outer_grp_exclude = cpp_group_stack and cpp_group_stack[-1] + cpp_exclude = not cpp_exclude or outer_grp_exclude + + # Restore exclude state when exiting conditional block + match = re_cpp_endif.match(line) + if match: + cpp_exclude = cpp_group_stack.pop() + + # Skip lines inside of false condition blocks + if cpp_exclude: + continue + + # Activate a new macro (ignoring the value) + match = re_cpp_define.match(line) + if match: + new_macro = line.lstrip()[1:].split()[1] + cpp_macros.append(new_macro) + + # Deactivate a macro + match = re_cpp_undef.match(line) + if match: + new_macro = line.lstrip()[1:].split()[1] + try: + cpp_macros.remove(new_macro) + except: + # Ignore missing macros (for now?) + continue + match = re_module.match(line.lower()) if match: if match.group(1) not in 'procedure': # avoid "module procedure" statements @@ -404,8 +482,13 @@ parser.add_argument( action='append', help="Skip directory in source code search." ) +parser.add_argument( + '-D', '--define', + action='append', + help="Apply preprocessor define macros (of the form -DMACRO[=value])", +) args = parser.parse_args() # Do the thing create_deps(args.path, args.skip, args.makefile, args.debug, args.exec_target, - args.fc_rule, args.link_externals, sys.argv[0]) + args.fc_rule, args.link_externals, args.define) From 4e8fbe15039a5006adeb8025667fce4d2f6b608e Mon Sep 17 00:00:00 2001 From: Robert Hallberg Date: Wed, 16 Aug 2023 18:07:52 -0400 Subject: [PATCH 10/22] +Standardize input salinity units as "ppt" Standardized the syntax for the units of salinities that are read via get_param calls to be uniformly 'units="ppt"' or similar units for derivatives with salinity. The only exceptions are places where practical salinity is used specifically, which occurs for several arguments in the MOM_EOS code. All answers are bitwise identical, but there are changes to a number of MOM_parameter_doc files. --- .../FMS_cap/MOM_surface_forcing_gfdl.F90 | 2 +- .../solo_driver/MOM_surface_forcing.F90 | 8 ++-- src/equation_of_state/MOM_EOS.F90 | 30 ++++++------- src/equation_of_state/MOM_EOS_linear.F90 | 44 +++++++++---------- .../MOM_coord_initialization.F90 | 8 ++-- .../MOM_state_initialization.F90 | 10 ++--- .../vertical/MOM_bulk_mixed_layer.F90 | 4 +- src/tracer/MOM_tracer_Z_init.F90 | 12 ++--- src/user/DOME2d_initialization.F90 | 10 ++--- src/user/ISOMIP_initialization.F90 | 4 +- src/user/Rossby_front_2d_initialization.F90 | 14 +++--- src/user/SCM_CVMix_tests.F90 | 10 ++--- src/user/adjustment_initialization.F90 | 18 ++++---- src/user/benchmark_initialization.F90 | 2 +- src/user/dense_water_initialization.F90 | 10 ++--- src/user/dumbbell_initialization.F90 | 18 ++++---- src/user/dumbbell_surface_forcing.F90 | 4 +- src/user/seamount_initialization.F90 | 14 +++--- src/user/sloshing_initialization.F90 | 6 +-- 19 files changed, 112 insertions(+), 116 deletions(-) diff --git a/config_src/drivers/FMS_cap/MOM_surface_forcing_gfdl.F90 b/config_src/drivers/FMS_cap/MOM_surface_forcing_gfdl.F90 index f9f7fe88a0..fc4d8e79f6 100644 --- a/config_src/drivers/FMS_cap/MOM_surface_forcing_gfdl.F90 +++ b/config_src/drivers/FMS_cap/MOM_surface_forcing_gfdl.F90 @@ -1522,7 +1522,7 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, wind_stagger) endif call get_param(param_file, mdl, "SPEAR_DTFREEZE_DS", CS%SPEAR_dTf_dS, & "The derivative of the freezing temperature with salinity.", & - units="deg C PSU-1", default=-0.054, scale=US%degC_to_C*US%S_to_ppt, & + units="degC ppt-1", default=-0.054, scale=US%degC_to_C*US%S_to_ppt, & do_not_log=.not.CS%trestore_SPEAR_ECDA) call get_param(param_file, mdl, "RESTORE_FLUX_RHO", CS%rho_restore, & "The density that is used to convert piston velocities into salt or heat "//& diff --git a/config_src/drivers/solo_driver/MOM_surface_forcing.F90 b/config_src/drivers/solo_driver/MOM_surface_forcing.F90 index d17db5a9a1..14f861e955 100644 --- a/config_src/drivers/solo_driver/MOM_surface_forcing.F90 +++ b/config_src/drivers/solo_driver/MOM_surface_forcing.F90 @@ -1907,19 +1907,19 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, tracer_flow_C call get_param(param_file, mdl, "SST_NORTH", CS%T_north, & "With buoy_config linear, the sea surface temperature "//& "at the northern end of the domain toward which to "//& - "to restore.", units="deg C", default=0.0, scale=US%degC_to_C) + "to restore.", units="degC", default=0.0, scale=US%degC_to_C) call get_param(param_file, mdl, "SST_SOUTH", CS%T_south, & "With buoy_config linear, the sea surface temperature "//& "at the southern end of the domain toward which to "//& - "to restore.", units="deg C", default=0.0, scale=US%degC_to_C) + "to restore.", units="degC", default=0.0, scale=US%degC_to_C) call get_param(param_file, mdl, "SSS_NORTH", CS%S_north, & "With buoy_config linear, the sea surface salinity "//& "at the northern end of the domain toward which to "//& - "to restore.", units="PSU", default=35.0, scale=US%ppt_to_S) + "to restore.", units="ppt", default=35.0, scale=US%ppt_to_S) call get_param(param_file, mdl, "SSS_SOUTH", CS%S_south, & "With buoy_config linear, the sea surface salinity "//& "at the southern end of the domain toward which to "//& - "to restore.", units="PSU", default=35.0, scale=US%ppt_to_S) + "to restore.", units="ppt", default=35.0, scale=US%ppt_to_S) endif call get_param(param_file, mdl, "RESTORE_FLUX_RHO", CS%rho_restore, & "The density that is used to convert piston velocities into salt or heat "//& diff --git a/src/equation_of_state/MOM_EOS.F90 b/src/equation_of_state/MOM_EOS.F90 index a68e3b2229..d5c7abc977 100644 --- a/src/equation_of_state/MOM_EOS.F90 +++ b/src/equation_of_state/MOM_EOS.F90 @@ -1517,8 +1517,8 @@ subroutine EOS_init(param_file, EOS, US) "temperature.", units="kg m-3 K-1", default=-0.2) call get_param(param_file, mdl, "DRHO_DS", EOS%dRho_dS, & "When EQN_OF_STATE="//trim(EOS_LINEAR_STRING)//", "//& - "this is the partial derivative of density with "//& - "salinity.", units="kg m-3 PSU-1", default=0.8) + "this is the partial derivative of density with salinity.", & + units="kg m-3 ppt-1", default=0.8) call EOS_manual_init(EOS, form_of_EOS=EOS_LINEAR, Rho_T0_S0=EOS%Rho_T0_S0, dRho_dT=EOS%dRho_dT, dRho_dS=EOS%dRho_dS) endif if (EOS%form_of_EOS == EOS_WRIGHT) then @@ -1563,17 +1563,17 @@ subroutine EOS_init(param_file, EOS, US) call get_param(param_file, mdl, "TFREEZE_S0_P0",EOS%TFr_S0_P0, & "When TFREEZE_FORM="//trim(TFREEZE_LINEAR_STRING)//", "//& "this is the freezing potential temperature at "//& - "S=0, P=0.", units="deg C", default=0.0) + "S=0, P=0.", units="degC", default=0.0) call get_param(param_file, mdl, "DTFREEZE_DS",EOS%dTFr_dS, & "When TFREEZE_FORM="//trim(TFREEZE_LINEAR_STRING)//", "//& "this is the derivative of the freezing potential "//& "temperature with salinity.", & - units="deg C PSU-1", default=-0.054) + units="degC ppt-1", default=-0.054) call get_param(param_file, mdl, "DTFREEZE_DP",EOS%dTFr_dP, & "When TFREEZE_FORM="//trim(TFREEZE_LINEAR_STRING)//", "//& "this is the derivative of the freezing potential "//& "temperature with pressure.", & - units="deg C Pa-1", default=0.0) + units="degC Pa-1", default=0.0) endif if ((EOS%form_of_EOS == EOS_TEOS10 .or. EOS%form_of_EOS == EOS_ROQUET_RHO .or. & @@ -1694,7 +1694,7 @@ subroutine convert_temp_salt_for_TEOS10(T, S, HI, kd, mask_z, EOS) type(EOS_type), intent(in) :: EOS !< Equation of state structure real, parameter :: Sref_Sprac = (35.16504/35.0) ! The TEOS 10 conversion factor to go from - ! practical salinity to reference salinity [nondim] + ! practical salinity to reference salinity [PSU ppt-1] integer :: i, j, k if ((EOS%form_of_EOS /= EOS_TEOS10) .and. (EOS%form_of_EOS /= EOS_ROQUET_RHO) .and. & @@ -1808,20 +1808,20 @@ end subroutine pot_temp_to_cons_temp !! temperature uses this same scaling, but this can be replaced by the factor given by scale. subroutine abs_saln_to_prac_saln(S, prSaln, EOS, dom, scale) real, dimension(:), intent(in) :: S !< Absolute salinity [S ~> ppt] - real, dimension(:), intent(inout) :: prSaln !< Practical salinity [S ~> ppt] + real, dimension(:), intent(inout) :: prSaln !< Practical salinity [S ~> PSU] type(EOS_type), intent(in) :: EOS !< Equation of state structure integer, dimension(2), optional, intent(in) :: dom !< The domain of indices to work on, taking !! into account that arrays start at 1. real, optional, intent(in) :: scale !< A multiplicative factor by which to scale the output - !! practical in place of with scaling stored + !! practical salinities in place of with scaling stored !! in EOS. A value of 1.0 returns salinities in [PSU], !! while the default is equivalent to EOS%ppt_to_S. ! Local variables real, dimension(size(S)) :: Sa ! Salinity converted to [ppt] - real :: S_scale ! A factor to convert practical salinity from ppt to the desired units [S ppt-1 ~> 1] + real :: S_scale ! A factor to convert practical salinity from ppt to the desired units [S PSU-1 ~> 1] real, parameter :: Sprac_Sref = (35.0/35.16504) ! The TEOS 10 conversion factor to go from - ! reference salinity to practical salinity [nondim] + ! reference salinity to practical salinity [PSU ppt-1] integer :: i, is, ie if (present(dom)) then @@ -1848,21 +1848,21 @@ end subroutine abs_saln_to_prac_saln !! use the dimensionally rescaling as specified within the EOS type. The output potential !! temperature uses this same scaling, but this can be replaced by the factor given by scale. subroutine prac_saln_to_abs_saln(S, absSaln, EOS, dom, scale) - real, dimension(:), intent(in) :: S !< Practical salinity [S ~> ppt] + real, dimension(:), intent(in) :: S !< Practical salinity [S ~> PSU] real, dimension(:), intent(inout) :: absSaln !< Absolute salinity [S ~> ppt] type(EOS_type), intent(in) :: EOS !< Equation of state structure integer, dimension(2), optional, intent(in) :: dom !< The domain of indices to work on, taking !! into account that arrays start at 1. real, optional, intent(in) :: scale !< A multiplicative factor by which to scale the output - !! practical in place of with scaling stored - !! in EOS. A value of 1.0 returns salinities in [PSU], + !! absolute salnities in place of with scaling stored + !! in EOS. A value of 1.0 returns salinities in [ppt], !! while the default is equivalent to EOS%ppt_to_S. ! Local variables real, dimension(size(S)) :: Sp ! Salinity converted to [ppt] - real :: S_scale ! A factor to convert practical salinity from ppt to the desired units [S ppt-1 ~> 1] + real :: S_scale ! A factor to convert absolute salinity from ppt to the desired units [S ppt-1 ~> 1] real, parameter :: Sref_Sprac = (35.16504/35.0) ! The TEOS 10 conversion factor to go from - ! practical salinity to reference salinity [nondim] + ! practical salinity to reference salinity [PSU ppt-1] integer :: i, is, ie if (present(dom)) then diff --git a/src/equation_of_state/MOM_EOS_linear.F90 b/src/equation_of_state/MOM_EOS_linear.F90 index e171aaa442..db67040304 100644 --- a/src/equation_of_state/MOM_EOS_linear.F90 +++ b/src/equation_of_state/MOM_EOS_linear.F90 @@ -59,7 +59,7 @@ module MOM_EOS_linear real elemental function density_elem_linear(this, T, S, pressure) class(linear_EOS), intent(in) :: this !< This EOS real, intent(in) :: T !< Potential temperature relative to the surface [degC] - real, intent(in) :: S !< Salinity [PSU] + real, intent(in) :: S !< Salinity [ppt] real, intent(in) :: pressure !< Pressure [Pa] density_elem_linear = this%Rho_T0_S0 + this%dRho_dT*T + this%dRho_dS*S @@ -73,7 +73,7 @@ end function density_elem_linear real elemental function density_anomaly_elem_linear(this, T, S, pressure, rho_ref) class(linear_EOS), intent(in) :: this !< This EOS real, intent(in) :: T !< Potential temperature relative to the surface [degC] - real, intent(in) :: S !< Salinity [PSU] + real, intent(in) :: S !< Salinity [ppt] real, intent(in) :: pressure !< Pressure [Pa] real, intent(in) :: rho_ref !< A reference density [kg m-3] @@ -87,9 +87,8 @@ end function density_anomaly_elem_linear !! scalar and array inputs. real elemental function spec_vol_elem_linear(this, T, S, pressure) class(linear_EOS), intent(in) :: this !< This EOS - real, intent(in) :: T !< potential temperature relative to the surface - !! [degC]. - real, intent(in) :: S !< Salinity [PSU]. + real, intent(in) :: T !< Potential temperature relative to the surface [degC]. + real, intent(in) :: S !< Salinity [ppt]. real, intent(in) :: pressure !< Pressure [Pa]. spec_vol_elem_linear = 1.0 / ( this%Rho_T0_S0 + (this%dRho_dT*T + this%dRho_dS*S)) @@ -102,9 +101,8 @@ end function spec_vol_elem_linear !! scalar and array inputs. real elemental function spec_vol_anomaly_elem_linear(this, T, S, pressure, spv_ref) class(linear_EOS), intent(in) :: this !< This EOS - real, intent(in) :: T !< potential temperature relative to the surface - !! [degC]. - real, intent(in) :: S !< Salinity [PSU]. + real, intent(in) :: T !< Potential temperature relative to the surface [degC]. + real, intent(in) :: S !< Salinity [ppt]. real, intent(in) :: pressure !< Pressure [Pa]. real, intent(in) :: spv_ref !< A reference specific volume [m3 kg-1]. @@ -118,9 +116,8 @@ end function spec_vol_anomaly_elem_linear !! with potential temperature and salinity. elemental subroutine calculate_density_derivs_elem_linear(this,T, S, pressure, dRho_dT, dRho_dS) class(linear_EOS), intent(in) :: this !< This EOS - real, intent(in) :: T !< Potential temperature relative to the surface - !! [degC]. - real, intent(in) :: S !< Salinity [PSU]. + real, intent(in) :: T !< Potential temperature relative to the surface [degC]. + real, intent(in) :: S !< Salinity [ppt]. real, intent(in) :: pressure !< Pressure [Pa]. real, intent(out) :: drho_dT !< The partial derivative of density with !! potential temperature [kg m-3 degC-1]. @@ -138,16 +135,16 @@ elemental subroutine calculate_density_second_derivs_elem_linear(this, T, S, pre drho_dS_dS, drho_dS_dT, drho_dT_dT, drho_dS_dP, drho_dT_dP) class(linear_EOS), intent(in) :: this !< This EOS real, intent(in) :: T !< Potential temperature relative to the surface [degC]. - real, intent(in) :: S !< Salinity [PSU]. + real, intent(in) :: S !< Salinity [ppt]. real, intent(in) :: pressure !< pressure [Pa]. real, intent(inout) :: drho_dS_dS !< The second derivative of density with - !! salinity [kg m-3 PSU-2]. + !! salinity [kg m-3 ppt-2]. real, intent(inout) :: drho_dS_dT !< The second derivative of density with !! temperature and salinity [kg m-3 ppt-1 degC-1]. real, intent(inout) :: drho_dT_dT !< The second derivative of density with !! temperature [kg m-3 degC-2]. real, intent(inout) :: drho_dS_dP !< The second derivative of density with - !! salinity and pressure [kg m-3 PSU-1 Pa-1]. + !! salinity and pressure [kg m-3 ppt-1 Pa-1]. real, intent(inout) :: drho_dT_dP !< The second derivative of density with !! temperature and pressure [kg m-3 degC-1 Pa-1]. @@ -163,10 +160,10 @@ end subroutine calculate_density_second_derivs_elem_linear elemental subroutine calculate_specvol_derivs_elem_linear(this, T, S, pressure, dSV_dT, dSV_dS) class(linear_EOS), intent(in) :: this !< This EOS real, intent(in) :: T !< Potential temperature [degC] - real, intent(in) :: S !< Salinity [PSU] + real, intent(in) :: S !< Salinity [ppt] real, intent(in) :: pressure !< pressure [Pa] real, intent(inout) :: dSV_dS !< The partial derivative of specific volume with - !! salinity [m3 kg-1 PSU-1] + !! salinity [m3 kg-1 ppt-1] real, intent(inout) :: dSV_dT !< The partial derivative of specific volume with !! potential temperature [m3 kg-1 degC-1] ! Local variables @@ -184,9 +181,8 @@ end subroutine calculate_specvol_derivs_elem_linear !! salinity, potential temperature, and pressure. elemental subroutine calculate_compress_elem_linear(this, T, S, pressure, rho, drho_dp) class(linear_EOS), intent(in) :: this !< This EOS - real, intent(in) :: T !< Potential temperature relative to the surface - !! [degC]. - real, intent(in) :: S !< Salinity [PSU]. + real, intent(in) :: T !< Potential temperature relative to the surface [degC]. + real, intent(in) :: S !< Salinity [ppt]. real, intent(in) :: pressure !< pressure [Pa]. real, intent(out) :: rho !< In situ density [kg m-3]. real, intent(out) :: drho_dp !< The partial derivative of density with pressure @@ -201,7 +197,7 @@ end subroutine calculate_compress_elem_linear !> Calculates the layer average specific volumes. subroutine avg_spec_vol_linear(T, S, p_t, dp, SpV_avg, start, npts, Rho_T0_S0, dRho_dT, dRho_dS) real, dimension(:), intent(in) :: T !< Potential temperature [degC] - real, dimension(:), intent(in) :: S !< Salinity [PSU] + real, dimension(:), intent(in) :: S !< Salinity [ppt] real, dimension(:), intent(in) :: p_t !< Pressure at the top of the layer [Pa] real, dimension(:), intent(in) :: dp !< Pressure change in the layer [Pa] real, dimension(:), intent(inout) :: SpV_avg !< The vertical average specific volume @@ -268,7 +264,7 @@ subroutine int_density_dz_linear(T, S, z_t, z_b, rho_ref, rho_0_pres, G_e, HI, & intent(in) :: T !< Potential temperature relative to the surface !! [C ~> degC]. real, dimension(HI%isd:HI%ied,HI%jsd:HI%jed), & - intent(in) :: S !< Salinity [S ~> PSU]. + intent(in) :: S !< Salinity [S ~> ppt]. real, dimension(HI%isd:HI%ied,HI%jsd:HI%jed), & intent(in) :: z_t !< Height at the top of the layer in depth units [Z ~> m]. real, dimension(HI%isd:HI%ied,HI%jsd:HI%jed), & @@ -439,7 +435,7 @@ subroutine int_spec_vol_dp_linear(T, S, p_t, p_b, alpha_ref, HI, Rho_T0_S0, & intent(in) :: T !< Potential temperature relative to the surface !! [C ~> degC]. real, dimension(HI%isd:HI%ied,HI%jsd:HI%jed), & - intent(in) :: S !< Salinity [S ~> PSU]. + intent(in) :: S !< Salinity [S ~> ppt]. real, dimension(HI%isd:HI%ied,HI%jsd:HI%jed), & intent(in) :: p_t !< Pressure at the top of the layer [R L2 T-2 ~> Pa] real, dimension(HI%isd:HI%ied,HI%jsd:HI%jed), & @@ -614,7 +610,7 @@ end subroutine int_spec_vol_dp_linear subroutine calculate_density_array_linear(this, T, S, pressure, rho, start, npts, rho_ref) class(linear_EOS), intent(in) :: this !< This EOS real, dimension(:), intent(in) :: T !< Potential temperature relative to the surface [degC] - real, dimension(:), intent(in) :: S !< Salinity [PSU] + real, dimension(:), intent(in) :: S !< Salinity [ppt] real, dimension(:), intent(in) :: pressure !< Pressure [Pa] real, dimension(:), intent(out) :: rho !< In situ density [kg m-3] integer, intent(in) :: start !< The starting index for calculations @@ -640,7 +636,7 @@ end subroutine calculate_density_array_linear subroutine calculate_spec_vol_array_linear(this, T, S, pressure, specvol, start, npts, spv_ref) class(linear_EOS), intent(in) :: this !< This EOS real, dimension(:), intent(in) :: T !< Potential temperature relative to the surface [degC] - real, dimension(:), intent(in) :: S !< Salinity [PSU] + real, dimension(:), intent(in) :: S !< Salinity [ppt] real, dimension(:), intent(in) :: pressure !< Pressure [Pa] real, dimension(:), intent(out) :: specvol !< In situ specific volume [m3 kg-1] integer, intent(in) :: start !< The starting index for calculations diff --git a/src/initialization/MOM_coord_initialization.F90 b/src/initialization/MOM_coord_initialization.F90 index 37c719209b..bb7832525f 100644 --- a/src/initialization/MOM_coord_initialization.F90 +++ b/src/initialization/MOM_coord_initialization.F90 @@ -235,7 +235,7 @@ subroutine set_coord_from_TS_ref(Rlay, g_prime, GV, US, param_file, eqn_of_state "The initial temperature of the lightest layer.", & units="degC", scale=US%degC_to_C, fail_if_missing=.true.) call get_param(param_file, mdl, "S_REF", S_ref, & - "The initial salinities.", units="PSU", default=35.0, scale=US%ppt_to_S) + "The initial salinities.", units="ppt", default=35.0, scale=US%ppt_to_S) call get_param(param_file, mdl, "GFS", g_fs, & "The reduced gravity at the free surface.", units="m s-2", & default=GV%g_Earth*US%L_T_to_m_s**2*US%m_to_Z, scale=US%m_s_to_L_T**2*US%Z_to_m) @@ -376,13 +376,13 @@ subroutine set_coord_from_TS_range(Rlay, g_prime, GV, US, param_file, eqn_of_sta call get_param(param_file, mdl, "S_REF", S_Ref, & "The default initial salinities.", & - units="PSU", default=35.0, scale=US%ppt_to_S) + units="ppt", default=35.0, scale=US%ppt_to_S) call get_param(param_file, mdl, "TS_RANGE_S_LIGHT", S_Light, & "The initial lightest salinities when COORD_CONFIG is set to ts_range.", & - units="PSU", default=US%S_to_ppt*S_Ref, scale=US%ppt_to_S) + units="ppt", default=US%S_to_ppt*S_Ref, scale=US%ppt_to_S) call get_param(param_file, mdl, "TS_RANGE_S_DENSE", S_Dense, & "The initial densest salinities when COORD_CONFIG is set to ts_range.", & - units="PSU", default=US%S_to_ppt*S_Ref, scale=US%ppt_to_S) + units="ppt", default=US%S_to_ppt*S_Ref, scale=US%ppt_to_S) call get_param(param_file, mdl, "TS_RANGE_RESOLN_RATIO", res_rat, & "The ratio of density space resolution in the densest "//& diff --git a/src/initialization/MOM_state_initialization.F90 b/src/initialization/MOM_state_initialization.F90 index 4bddc0965a..7dfced262b 100644 --- a/src/initialization/MOM_state_initialization.F90 +++ b/src/initialization/MOM_state_initialization.F90 @@ -1745,7 +1745,7 @@ subroutine initialize_temp_salt_fit(T, S, G, GV, US, param_file, eqn_of_state, P units="degC", scale=US%degC_to_C, fail_if_missing=.not.just_read, do_not_log=just_read) call get_param(param_file, mdl, "S_REF", S_Ref, & "A reference salinity used in initialization.", & - units="PSU", default=35.0, scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=35.0, scale=US%ppt_to_S, do_not_log=just_read) call get_param(param_file, mdl, "FIT_SALINITY", fit_salin, & "If true, accept the prescribed temperature and fit the "//& "salinity; otherwise take salinity and fit temperature.", & @@ -1829,10 +1829,10 @@ subroutine initialize_temp_salt_linear(T, S, G, GV, US, param_file, just_read) units="degC", scale=US%degC_to_C, fail_if_missing=.not.just_read, do_not_log=just_read) call get_param(param_file, mdl, "S_TOP", S_top, & "Initial salinity of the top surface.", & - units="PSU", scale=US%ppt_to_S, fail_if_missing=.not.just_read, do_not_log=just_read) + units="ppt", scale=US%ppt_to_S, fail_if_missing=.not.just_read, do_not_log=just_read) call get_param(param_file, mdl, "S_RANGE", S_range, & "Initial salinity difference (top-bottom).", & - units="PSU", scale=US%ppt_to_S, fail_if_missing=.not.just_read, do_not_log=just_read) + units="ppt", scale=US%ppt_to_S, fail_if_missing=.not.just_read, do_not_log=just_read) if (just_read) return ! All run-time parameters have been read, so return. @@ -2645,7 +2645,7 @@ subroutine MOM_temp_salt_initialize_from_Z(h, tv, depth_tot, G, GV, US, PF, just units="degC", default=0.0, scale=US%degC_to_C, do_not_log=just_read) call get_param(PF, mdl, "LAND_FILL_SALIN", salt_land_fill, & "A value to use to fill in ocean salinities on land points.", & - units="1e-3", default=35.0, scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=35.0, scale=US%ppt_to_S, do_not_log=just_read) call get_param(PF, mdl, "HORIZ_INTERP_TOL_TEMP", tol_temp, & "The tolerance in temperature changes between iterations when interpolating "//& "from an input dataset using horiz_interp_and_extrap_tracer. This routine "//& @@ -2655,7 +2655,7 @@ subroutine MOM_temp_salt_initialize_from_Z(h, tv, depth_tot, G, GV, US, PF, just "The tolerance in salinity changes between iterations when interpolating "//& "from an input dataset using horiz_interp_and_extrap_tracer. This routine "//& "converges slowly, so an overly small tolerance can get expensive.", & - units="1e-3", default=1.0e-3, scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=1.0e-3, scale=US%ppt_to_S, do_not_log=just_read) if (just_read) then if ((.not.useALEremapping) .and. adjust_temperature) & diff --git a/src/parameterizations/vertical/MOM_bulk_mixed_layer.F90 b/src/parameterizations/vertical/MOM_bulk_mixed_layer.F90 index c7e522eddc..f2b38c4a29 100644 --- a/src/parameterizations/vertical/MOM_bulk_mixed_layer.F90 +++ b/src/parameterizations/vertical/MOM_bulk_mixed_layer.F90 @@ -4026,14 +4026,14 @@ subroutine bulkmixedlayer_init(Time, G, GV, US, param_file, diag, CS) "during detrainment.", units="K", default=0.5, scale=US%degC_to_C) call get_param(param_file, mdl, "ALLOWED_DETRAIN_SALT_CHG", CS%Allowed_S_chg, & "The amount by which salinity is allowed to exceed previous values "//& - "during detrainment.", units="PSU", default=0.1, scale=US%ppt_to_S) + "during detrainment.", units="ppt", default=0.1, scale=US%ppt_to_S) call get_param(param_file, mdl, "ML_DT_DS_WEIGHT", CS%dT_dS_wt, & "When forced to extrapolate T & S to match the layer "//& "densities, this factor (in deg C / PSU) is combined "//& "with the derivatives of density with T & S to determine "//& "what direction is orthogonal to density contours. It "//& "should be a typical value of (dR/dS) / (dR/dT) in oceanic profiles.", & - units="degC PSU-1", default=6.0, scale=US%degC_to_C*US%S_to_ppt) + units="degC ppt-1", default=6.0, scale=US%degC_to_C*US%S_to_ppt) call get_param(param_file, mdl, "BUFFER_LAYER_EXTRAP_LIMIT", CS%BL_extrap_lim, & "A limit on the density range over which extrapolation "//& "can occur when detraining from the buffer layers, "//& diff --git a/src/tracer/MOM_tracer_Z_init.F90 b/src/tracer/MOM_tracer_Z_init.F90 index fab7da3917..c404c560f3 100644 --- a/src/tracer/MOM_tracer_Z_init.F90 +++ b/src/tracer/MOM_tracer_Z_init.F90 @@ -628,16 +628,16 @@ subroutine determine_temperature(temp, salt, R_tgt, EOS, p_ref, niter, k_start, units="degC", default=31.0, scale=US%degC_to_C, do_not_log=just_read) call get_param(PF, mdl, "DETERMINE_TEMP_S_MIN", S_min, & "The minimum salinity that can be found by determine_temperature.", & - units="1e-3", default=0.5, scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=0.5, scale=US%ppt_to_S, do_not_log=just_read) call get_param(PF, mdl, "DETERMINE_TEMP_S_MAX", S_max, & "The maximum salinity that can be found by determine_temperature.", & - units="1e-3", default=65.0, scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=65.0, scale=US%ppt_to_S, do_not_log=just_read) call get_param(PF, mdl, "DETERMINE_TEMP_T_TOLERANCE", tol_T, & "The convergence tolerance for temperature in determine_temperature.", & units="degC", default=1.0e-4, scale=US%degC_to_C, do_not_log=just_read) call get_param(PF, mdl, "DETERMINE_TEMP_S_TOLERANCE", tol_S, & "The convergence tolerance for temperature in determine_temperature.", & - units="1e-3", default=1.0e-4, scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=1.0e-4, scale=US%ppt_to_S, do_not_log=just_read) call get_param(PF, mdl, "DETERMINE_TEMP_RHO_TOLERANCE", tol_rho, & "The convergence tolerance for density in determine_temperature.", & units="kg m-3", default=1.0e-4, scale=US%kg_m3_to_R, do_not_log=just_read) @@ -645,10 +645,10 @@ subroutine determine_temperature(temp, salt, R_tgt, EOS, p_ref, niter, k_start, ! By default 10 degC is weighted equivalently to 1 ppt when minimizing changes. call get_param(PF, mdl, "DETERMINE_TEMP_DT_DS_WEIGHT", dT_dS_gauge, & "When extrapolating T & S to match the layer target densities, this "//& - "factor (in deg C / PSU) is combined with the derivatives of density "//& + "factor (in degC / ppt) is combined with the derivatives of density "//& "with T & S to determine what direction is orthogonal to density contours. "//& "It could be based on a typical value of (dR/dS) / (dR/dT) in oceanic profiles.", & - units="degC PSU-1", default=10.0, scale=US%degC_to_C*US%S_to_ppt) + units="degC ppt-1", default=10.0, scale=US%degC_to_C*US%S_to_ppt) else call get_param(PF, mdl, "DETERMINE_TEMP_T_ADJ_RANGE", max_t_adj, & "The maximum amount by which the initial layer temperatures can be "//& @@ -657,7 +657,7 @@ subroutine determine_temperature(temp, salt, R_tgt, EOS, p_ref, niter, k_start, call get_param(PF, mdl, "DETERMINE_TEMP_S_ADJ_RANGE", max_S_adj, & "The maximum amount by which the initial layer salinities can be "//& "modified in determine_temperature.", & - units="1e-3", default=0.5, scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=0.5, scale=US%ppt_to_S, do_not_log=just_read) endif if (just_read) return ! All run-time parameters have been read, so return. diff --git a/src/user/DOME2d_initialization.F90 b/src/user/DOME2d_initialization.F90 index dade17a9a0..c1ec83257d 100644 --- a/src/user/DOME2d_initialization.F90 +++ b/src/user/DOME2d_initialization.F90 @@ -261,15 +261,15 @@ subroutine DOME2d_initialize_temperature_salinity ( T, S, h, G, GV, US, param_fi call get_param(param_file, mdl, "DOME2D_SHELF_DEPTH", dome2d_depth_bay, & units="nondim", default=0.2, do_not_log=.true.) call get_param(param_file, mdl, "S_REF", S_ref, 'Reference salinity', & - units='1e-3', default=35.0, scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=35.0, scale=US%ppt_to_S, do_not_log=just_read) call get_param(param_file, mdl, "T_REF", T_ref, 'Reference temperature', & units='degC', scale=US%degC_to_C, fail_if_missing=.not.just_read, do_not_log=just_read) call get_param(param_file, mdl, "S_RANGE", S_range,' Initial salinity range', & - units='1e-3', default=2.0, scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=2.0, scale=US%ppt_to_S, do_not_log=just_read) call get_param(param_file, mdl, "T_RANGE", T_range, 'Initial temperature range', & units='degC', default=0.0, scale=US%degC_to_C, do_not_log=just_read) call get_param(param_file, mdl, "INITIAL_SSS", S_surf, "Initial surface salinity", & - units="1e-3", default=34.0, scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=34.0, scale=US%ppt_to_S, do_not_log=just_read) call get_param(param_file, mdl, "DOME2D_T_BAY", T_bay, & "Temperature in the inflow embayment in the DOME2d test case", & units="degC", default=1.0, scale=US%degC_to_C, do_not_log=just_read) @@ -440,10 +440,10 @@ subroutine DOME2d_initialize_sponges(G, GV, US, tv, depth_tot, param_file, use_A call get_param(param_file, mdl, "S_RANGE", S_range, units="ppt", default=2.0, scale=US%ppt_to_S) call get_param(param_file, mdl, "T_RANGE", T_range, units="degC", default=0.0, scale=US%degC_to_C) call get_param(param_file, mdl, "INITIAL_SSS", S_surf, "Initial surface salinity", & - units="1e-3", default=34.0, scale=US%ppt_to_S, do_not_log=.true.) + units="ppt", default=34.0, scale=US%ppt_to_S, do_not_log=.true.) call get_param(param_file, mdl, "DOME2D_EAST_SPONGE_S_RANGE", S_range_sponge, & "Range of salinities in the eastern sponge region in the DOME2D configuration", & - units="1e-3", default=1.0, scale=US%ppt_to_S) + units="ppt", default=1.0, scale=US%ppt_to_S) ! Set the sponge damping rate as a function of position Idamp(:,:) = 0.0 diff --git a/src/user/ISOMIP_initialization.F90 b/src/user/ISOMIP_initialization.F90 index 232ce6d4e7..3f28da4d5e 100644 --- a/src/user/ISOMIP_initialization.F90 +++ b/src/user/ISOMIP_initialization.F90 @@ -348,7 +348,7 @@ subroutine ISOMIP_initialize_temperature_salinity ( T, S, h, depth_tot, G, GV, U default=.false., do_not_log=just_read) call get_param(param_file, mdl, "DRHO_DS", drho_dS1, & "Partial derivative of density with salinity.", & - units="kg m-3 PSU-1", scale=US%kg_m3_to_R*US%S_to_ppt, & + units="kg m-3 ppt-1", scale=US%kg_m3_to_R*US%S_to_ppt, & fail_if_missing=.not.just_read, do_not_log=just_read) call get_param(param_file, mdl, "DRHO_DT", drho_dT1, & "Partial derivative of density with temperature.", & @@ -359,7 +359,7 @@ subroutine ISOMIP_initialize_temperature_salinity ( T, S, h, depth_tot, G, GV, U units="degC", scale=US%degC_to_C, fail_if_missing=.not.just_read, do_not_log=just_read) call get_param(param_file, mdl, "S_REF", S_Ref, & "A reference salinity used in initialization.", & - units="PSU", default=35.0, scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=35.0, scale=US%ppt_to_S, do_not_log=just_read) if (just_read) return ! All run-time parameters have been read, so return. ! write(mesg,*) 'read drho_dS, drho_dT', drho_dS1, drho_dT1 diff --git a/src/user/Rossby_front_2d_initialization.F90 b/src/user/Rossby_front_2d_initialization.F90 index b76e69bb44..33c7641a00 100644 --- a/src/user/Rossby_front_2d_initialization.F90 +++ b/src/user/Rossby_front_2d_initialization.F90 @@ -68,7 +68,7 @@ subroutine Rossby_front_initialize_thickness(h, G, GV, US, param_file, just_read call get_param(param_file, mdl, "REGRIDDING_COORDINATE_MODE", verticalCoordinate, & default=DEFAULT_COORDINATE_MODE, do_not_log=just_read) call get_param(param_file, mdl, "T_RANGE", T_range, 'Initial temperature range', & - units='C', default=0.0, scale=US%degC_to_C, do_not_log=just_read) + units="degC", default=0.0, scale=US%degC_to_C, do_not_log=just_read) call get_param(param_file, mdl, "DRHO_DT", dRho_dT, & units="kg m-3 degC-1", default=-0.2, scale=US%kg_m3_to_R*US%C_to_degC, do_not_log=.true.) call get_param(param_file, mdl, "MAXIMUM_DEPTH", max_depth, & @@ -155,11 +155,11 @@ subroutine Rossby_front_initialize_temperature_salinity(T, S, h, G, GV, US, & call get_param(param_file, mdl,"REGRIDDING_COORDINATE_MODE", verticalCoordinate, & default=DEFAULT_COORDINATE_MODE, do_not_log=just_read) call get_param(param_file, mdl, "S_REF", S_ref, 'Reference salinity', & - default=35.0, units='1e-3', scale=US%ppt_to_S, do_not_log=just_read) + default=35.0, units="ppt", scale=US%ppt_to_S, do_not_log=just_read) call get_param(param_file, mdl, "T_REF", T_ref, 'Reference temperature', & - units='C', scale=US%degC_to_C, fail_if_missing=.not.just_read, do_not_log=just_read) + units="degC", scale=US%degC_to_C, fail_if_missing=.not.just_read, do_not_log=just_read) call get_param(param_file, mdl, "T_RANGE", T_range, 'Initial temperature range', & - units='C', default=0.0, scale=US%degC_to_C, do_not_log=just_read) + units="degC", default=0.0, scale=US%degC_to_C, do_not_log=just_read) call get_param(param_file, mdl, "MAXIMUM_DEPTH", max_depth, & units="m", default=-1.e9, scale=GV%m_to_H, do_not_log=.true.) @@ -231,11 +231,11 @@ subroutine Rossby_front_initialize_velocity(u, v, h, G, GV, US, param_file, just call get_param(param_file, mdl, "REGRIDDING_COORDINATE_MODE", verticalCoordinate, & default=DEFAULT_COORDINATE_MODE, do_not_log=just_read) call get_param(param_file, mdl, "T_RANGE", T_range, 'Initial temperature range', & - units='C', default=0.0, scale=US%degC_to_C, do_not_log=just_read) + units="degC", default=0.0, scale=US%degC_to_C, do_not_log=just_read) call get_param(param_file, mdl, "S_REF", S_ref, 'Reference salinity', & - default=35.0, units='1e-3', scale=US%ppt_to_S, do_not_log=.true.) + default=35.0, units="ppt", scale=US%ppt_to_S, do_not_log=.true.) call get_param(param_file, mdl, "T_REF", T_ref, 'Reference temperature', & - units='C', scale=US%degC_to_C, fail_if_missing=.not.just_read, do_not_log=.true.) + units="degC", scale=US%degC_to_C, fail_if_missing=.not.just_read, do_not_log=.true.) call get_param(param_file, mdl, "RHO_T0_S0", Rho_T0_S0, & units="kg m-3", default=1000.0, scale=US%kg_m3_to_R, do_not_log=.true.) call get_param(param_file, mdl, "DRHO_DT", dRho_dT, & diff --git a/src/user/SCM_CVMix_tests.F90 b/src/user/SCM_CVMix_tests.F90 index 104a2b0312..be515f22ca 100644 --- a/src/user/SCM_CVMix_tests.F90 +++ b/src/user/SCM_CVMix_tests.F90 @@ -88,13 +88,13 @@ subroutine SCM_CVMix_tests_TS_init(T, S, h, G, GV, US, param_file, just_read) 'Initial salt mixed layer depth', & units='m', default=0.0, scale=US%m_to_Z, do_not_log=just_read) call get_param(param_file, mdl, "SCM_L1_SALT", UpperLayerSalt, & - 'Layer 2 surface salinity', units='1e-3', default=35.0, scale=US%ppt_to_S, do_not_log=just_read) + 'Layer 2 surface salinity', units="ppt", default=35.0, scale=US%ppt_to_S, do_not_log=just_read) call get_param(param_file, mdl, "SCM_L1_TEMP", UpperLayerTemp, & - 'Layer 1 surface temperature', units='C', default=20.0, scale=US%degC_to_C, do_not_log=just_read) + 'Layer 1 surface temperature', units="degC", default=20.0, scale=US%degC_to_C, do_not_log=just_read) call get_param(param_file, mdl, "SCM_L2_SALT", LowerLayerSalt, & - 'Layer 2 surface salinity', units='1e-3', default=35.0, scale=US%ppt_to_S, do_not_log=just_read) + 'Layer 2 surface salinity', units="ppt", default=35.0, scale=US%ppt_to_S, do_not_log=just_read) call get_param(param_file, mdl, "SCM_L2_TEMP", LowerLayerTemp, & - 'Layer 2 surface temperature', units='C', default=20.0, scale=US%degC_to_C, do_not_log=just_read) + 'Layer 2 surface temperature', units="degC", default=20.0, scale=US%degC_to_C, do_not_log=just_read) call get_param(param_file, mdl, "SCM_L2_DTDZ", LowerLayerdTdZ, & 'Initial temperature stratification in layer 2', & units='C/m', default=0.0, scale=US%degC_to_C*US%Z_to_m, do_not_log=just_read) @@ -102,7 +102,7 @@ subroutine SCM_CVMix_tests_TS_init(T, S, h, G, GV, US, param_file, just_read) 'Initial salinity stratification in layer 2', & units='PPT/m', default=0.0, scale=US%ppt_to_S*US%Z_to_m, do_not_log=just_read) call get_param(param_file, mdl, "SCM_L2_MINTEMP",LowerLayerMinTemp, & - 'Layer 2 minimum temperature', units='C', default=4.0, scale=US%degC_to_C, do_not_log=just_read) + 'Layer 2 minimum temperature', units="degC", default=4.0, scale=US%degC_to_C, do_not_log=just_read) if (just_read) return ! All run-time parameters have been read, so return. diff --git a/src/user/adjustment_initialization.F90 b/src/user/adjustment_initialization.F90 index 58389b7b5c..4a1d6c3d9f 100644 --- a/src/user/adjustment_initialization.F90 +++ b/src/user/adjustment_initialization.F90 @@ -76,12 +76,12 @@ subroutine adjustment_initialize_thickness ( h, G, GV, US, param_file, just_read ! Parameters used by main model initialization if (.not.just_read) call log_version(param_file, mdl, version, "") call get_param(param_file, mdl, "S_REF", S_ref, 'Reference salinity', & - default=35.0, units='1e-3', scale=US%ppt_to_S, do_not_log=just_read) + default=35.0, units='ppt', scale=US%ppt_to_S, do_not_log=just_read) call get_param(param_file, mdl, "MIN_THICKNESS", min_thickness, 'Minimum layer thickness', & default=1.0e-3, units='m', scale=US%m_to_Z, do_not_log=just_read) call get_param(param_file, mdl, "DRHO_DS", dRho_dS, & "The partial derivative of density with salinity with a linear equation of state.", & - units="kg m-3 PSU-1", default=0.8, scale=US%kg_m3_to_R*US%S_to_ppt) + units="kg m-3 ppt-1", default=0.8, scale=US%kg_m3_to_R*US%S_to_ppt) ! Parameters specific to this experiment configuration call get_param(param_file, mdl, "REGRIDDING_COORDINATE_MODE", verticalCoordinate, & @@ -91,10 +91,10 @@ subroutine adjustment_initialize_thickness ( h, G, GV, US, param_file, just_read units=G%x_ax_unit_short, fail_if_missing=.not.just_read, do_not_log=just_read) call get_param(param_file, mdl, "DELTA_S_STRAT", delta_S_strat, & "Top-to-bottom salinity difference of stratification", & - units="1e-3", scale=US%ppt_to_S, fail_if_missing=.not.just_read, do_not_log=just_read) + units="ppt", scale=US%ppt_to_S, fail_if_missing=.not.just_read, do_not_log=just_read) call get_param(param_file, mdl, "ADJUSTMENT_DELTAS", adjustment_deltaS, & "Salinity difference across front", & - units="1e-3", scale=US%ppt_to_S, fail_if_missing=.not.just_read, do_not_log=just_read) + units="ppt", scale=US%ppt_to_S, fail_if_missing=.not.just_read, do_not_log=just_read) call get_param(param_file, mdl, "FRONT_WAVE_AMP", front_wave_amp, & "Amplitude of trans-frontal wave perturbation", & units=G%x_ax_unit_short, default=0., do_not_log=just_read) @@ -239,11 +239,11 @@ subroutine adjustment_initialize_temperature_salinity(T, S, h, depth_tot, G, GV, ! Parameters used by main model initialization call get_param(param_file, mdl, "S_REF", S_ref, 'Reference salinity', & - default=35.0, units='1e-3', scale=US%ppt_to_S, do_not_log=just_read) + default=35.0, units="ppt", scale=US%ppt_to_S, do_not_log=just_read) call get_param(param_file, mdl, "T_REF", T_ref, 'Reference temperature', & - units='C', scale=US%degC_to_C, fail_if_missing=.not.just_read, do_not_log=just_read) + units="degC", scale=US%degC_to_C, fail_if_missing=.not.just_read, do_not_log=just_read) call get_param(param_file, mdl, "S_RANGE", S_range, 'Initial salinity range', & - default=2.0, units='1e-3', scale=US%ppt_to_S, do_not_log=just_read) + default=2.0, units="ppt", scale=US%ppt_to_S, do_not_log=just_read) call get_param(param_file, mdl, "T_RANGE", T_range, 'Initial temperature range', & default=1.0, units='degC', scale=US%degC_to_C, do_not_log=just_read) ! Parameters specific to this experiment configuration BUT logged in previous s/r @@ -252,9 +252,9 @@ subroutine adjustment_initialize_temperature_salinity(T, S, h, depth_tot, G, GV, call get_param(param_file, mdl, "ADJUSTMENT_WIDTH", adjustment_width, & units=G%x_ax_unit_short, fail_if_missing=.not.just_read, do_not_log=.true.) call get_param(param_file, mdl, "ADJUSTMENT_DELTAS", adjustment_deltaS, & - units='1e-3', scale=US%ppt_to_S, fail_if_missing=.not.just_read, do_not_log=.true.) + units="ppt", scale=US%ppt_to_S, fail_if_missing=.not.just_read, do_not_log=.true.) call get_param(param_file, mdl, "DELTA_S_STRAT", delta_S_strat, & - units='1e-3', scale=US%ppt_to_S, fail_if_missing=.not.just_read, do_not_log=.true.) + units="ppt", scale=US%ppt_to_S, fail_if_missing=.not.just_read, do_not_log=.true.) call get_param(param_file, mdl, "FRONT_WAVE_AMP", front_wave_amp, & units=G%x_ax_unit_short, default=0., do_not_log=.true.) call get_param(param_file, mdl, "FRONT_WAVE_LENGTH", front_wave_length, & diff --git a/src/user/benchmark_initialization.F90 b/src/user/benchmark_initialization.F90 index ad75d83efa..333f53895e 100644 --- a/src/user/benchmark_initialization.F90 +++ b/src/user/benchmark_initialization.F90 @@ -142,7 +142,7 @@ subroutine benchmark_initialize_thickness(h, depth_tot, G, GV, US, param_file, e units="degC", default=29.0, scale=US%degC_to_C, do_not_log=just_read) call get_param(param_file, mdl, "S_REF", S_ref, & "The uniform salinities used to initialize the benchmark test case.", & - units="PSU", default=35.0, scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=35.0, scale=US%ppt_to_S, do_not_log=just_read) if (just_read) return ! This subroutine has no run-time parameters. diff --git a/src/user/dense_water_initialization.F90 b/src/user/dense_water_initialization.F90 index 03cc983a9f..2daf03ccb1 100644 --- a/src/user/dense_water_initialization.F90 +++ b/src/user/dense_water_initialization.F90 @@ -122,11 +122,11 @@ subroutine dense_water_initialize_TS(G, GV, US, param_file, T, S, h, just_read) "Depth of unstratified mixed layer as a fraction of the water column.", & units="nondim", default=default_mld, do_not_log=just_read) call get_param(param_file, mdl, "S_REF", S_ref, 'Reference salinity', & - default=35.0, units='1e-3', scale=US%ppt_to_S, do_not_log=just_read) + default=35.0, units="ppt", scale=US%ppt_to_S, do_not_log=just_read) call get_param(param_file, mdl,"T_REF", T_ref, 'Reference temperature', & units='degC', scale=US%degC_to_C, fail_if_missing=.not.just_read, do_not_log=just_read) call get_param(param_file, mdl,"S_RANGE", S_range, 'Initial salinity range', & - units='1e-3', default=2.0, scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=2.0, scale=US%ppt_to_S, do_not_log=just_read) if (just_read) return ! All run-time parameters have been read, so return. @@ -204,7 +204,7 @@ subroutine dense_water_initialize_sponges(G, GV, US, tv, depth_tot, param_file, units="nondim", default=0.1) call get_param(param_file, mdl, "DENSE_WATER_EAST_SPONGE_SALT", S_dense, & "Salt anomaly of the dense water being formed in the overflow region.", & - units="1e-3", default=4.0, scale=US%ppt_to_S) + units="ppt", default=4.0, scale=US%ppt_to_S) call get_param(param_file, mdl, "DENSE_WATER_MLD", mld, & units="nondim", default=default_mld, do_not_log=.true.) @@ -212,9 +212,9 @@ subroutine dense_water_initialize_sponges(G, GV, US, tv, depth_tot, param_file, units="nondim", default=default_sill, do_not_log=.true.) call get_param(param_file, mdl, "S_REF", S_ref, & - units='1e-3', default=35.0, scale=US%ppt_to_S, do_not_log=.true.) + units="ppt", default=35.0, scale=US%ppt_to_S, do_not_log=.true.) call get_param(param_file, mdl, "S_RANGE", S_range, & - units='1e-3', default=2.0, scale=US%ppt_to_S, do_not_log=.true.) + units="ppt", default=2.0, scale=US%ppt_to_S, do_not_log=.true.) call get_param(param_file, mdl, "T_REF", T_ref, & units='degC', scale=US%degC_to_C, fail_if_missing=.true., do_not_log=.true.) diff --git a/src/user/dumbbell_initialization.F90 b/src/user/dumbbell_initialization.F90 index 492cb3ebe8..3d968d85d0 100644 --- a/src/user/dumbbell_initialization.F90 +++ b/src/user/dumbbell_initialization.F90 @@ -183,15 +183,15 @@ subroutine dumbbell_initialize_thickness ( h, depth_tot, G, GV, US, param_file, case ( REGRIDDING_RHO, REGRIDDING_HYCOM1) ! Initial thicknesses for isopycnal coordinates call get_param(param_file, mdl, "INITIAL_SSS", S_surf, & - units='1e-3', default=34., scale=US%ppt_to_S, do_not_log=.true.) + units="ppt", default=34., scale=US%ppt_to_S, do_not_log=.true.) call get_param(param_file, mdl, "INITIAL_S_RANGE", S_range, & - units='1e-3', default=2., scale=US%ppt_to_S, do_not_log=.true.) + units="ppt", default=2., scale=US%ppt_to_S, do_not_log=.true.) call get_param(param_file, mdl, "S_REF", S_ref, & - units='1e-3', default=35.0, scale=US%ppt_to_S, do_not_log=.true.) + units="ppt", default=35.0, scale=US%ppt_to_S, do_not_log=.true.) call get_param(param_file, mdl, "TS_RANGE_S_LIGHT", S_light, & - units='1e-3', default=US%S_to_ppt*S_Ref, scale=US%ppt_to_S, do_not_log=.true.) + units="ppt", default=US%S_to_ppt*S_Ref, scale=US%ppt_to_S, do_not_log=.true.) call get_param(param_file, mdl, "TS_RANGE_S_DENSE", S_dense, & - units='1e-3', default=US%S_to_ppt*S_Ref, scale=US%ppt_to_S, do_not_log=.true.) + units="ppt", default=US%S_to_ppt*S_Ref, scale=US%ppt_to_S, do_not_log=.true.) call get_param(param_file, mdl, "INTERFACE_IC_QUANTA", eta_IC_quanta, & "The granularity of initial interface height values "//& "per meter, to avoid sensivity to order-of-arithmetic changes.", & @@ -291,10 +291,10 @@ subroutine dumbbell_initialize_temperature_salinity ( T, S, h, G, GV, US, param_ units='degC', default=20., scale=US%degC_to_C, do_not_log=just_read) call get_param(param_file, mdl, "DUMBBELL_SREF", S_surf, & 'DUMBBELL REFERENCE SALINITY', & - units='1e-3', default=34., scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=34., scale=US%ppt_to_S, do_not_log=just_read) call get_param(param_file, mdl, "DUMBBELL_S_RANGE", S_range, & 'DUMBBELL salinity range (right-left)', & - units='1e-3', default=2., scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=2., scale=US%ppt_to_S, do_not_log=just_read) call get_param(param_file, mdl, "DUMBBELL_LEN", dblen, & 'Lateral Length scale for dumbbell ', & units=G%x_ax_unit_short, default=600., do_not_log=just_read) @@ -388,10 +388,10 @@ subroutine dumbbell_initialize_sponges(G, GV, US, tv, h_in, depth_tot, param_fil units='degC', default=20., scale=US%degC_to_C, do_not_log=.true.) call get_param(param_file, mdl, "DUMBBELL_SREF", S_ref, & 'DUMBBELL REFERENCE SALINITY', & - units='1e-3', default=34., scale=US%ppt_to_S, do_not_log=.true.) + units="ppt", default=34., scale=US%ppt_to_S, do_not_log=.true.) call get_param(param_file, mdl, "DUMBBELL_S_RANGE", S_range, & 'DUMBBELL salinity range (right-left)', & - units='1e-3', default=2., scale=US%ppt_to_S, do_not_log=.true.) + units="ppt", default=2., scale=US%ppt_to_S, do_not_log=.true.) call get_param(param_file, mdl,"MIN_THICKNESS", min_thickness, & 'Minimum thickness for layer', & units='m', default=1.0e-3, scale=US%m_to_Z, do_not_log=.true.) diff --git a/src/user/dumbbell_surface_forcing.F90 b/src/user/dumbbell_surface_forcing.F90 index 6f6e4da439..288ccd89fa 100644 --- a/src/user/dumbbell_surface_forcing.F90 +++ b/src/user/dumbbell_surface_forcing.F90 @@ -221,10 +221,10 @@ subroutine dumbbell_surface_forcing_init(Time, G, US, param_file, diag, CS) default=.false., do_not_log=.true.) call get_param(param_file, mdl,"INITIAL_SSS", S_surf, & "Initial surface salinity", & - units="1e-3", default=34.0, scale=US%ppt_to_S, do_not_log=.true.) + units="ppt", default=34.0, scale=US%ppt_to_S, do_not_log=.true.) call get_param(param_file, mdl,"INITIAL_S_RANGE", S_range, & "Initial salinity range (bottom - surface)", & - units="1e-3", default=2., scale=US%ppt_to_S, do_not_log=.true.) + units="ppt", default=2., scale=US%ppt_to_S, do_not_log=.true.) call get_param(param_file, mdl, "RESTOREBUOY", CS%restorebuoy, & "If true, the buoyancy fluxes drive the model back "//& diff --git a/src/user/seamount_initialization.F90 b/src/user/seamount_initialization.F90 index d1971f25f9..60aef08cb4 100644 --- a/src/user/seamount_initialization.F90 +++ b/src/user/seamount_initialization.F90 @@ -233,16 +233,16 @@ subroutine seamount_initialize_temperature_salinity(T, S, h, G, GV, US, param_fi 'and "exponential".', default='linear', do_not_log=just_read) call get_param(param_file, mdl,"INITIAL_SSS", S_surf, & 'Initial surface salinity', & - units='1e-3', default=34., scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=34., scale=US%ppt_to_S, do_not_log=just_read) call get_param(param_file, mdl,"INITIAL_SST", T_surf, & 'Initial surface temperature', & - units='C', default=0., scale=US%degC_to_C, do_not_log=just_read) + units="degC", default=0., scale=US%degC_to_C, do_not_log=just_read) call get_param(param_file, mdl,"INITIAL_S_RANGE", S_range, & 'Initial salinity range (bottom - surface)', & - units='1e-3', default=2., scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=2., scale=US%ppt_to_S, do_not_log=just_read) call get_param(param_file, mdl,"INITIAL_T_RANGE", T_range, & 'Initial temperature range (bottom - surface)', & - units='C', default=0., scale=US%degC_to_C, do_not_log=just_read) + units="degC", default=0., scale=US%degC_to_C, do_not_log=just_read) select case ( coordinateMode(verticalCoordinate) ) case ( REGRIDDING_LAYER ) ! Initial thicknesses for layer isopycnal coordinates @@ -254,11 +254,11 @@ subroutine seamount_initialize_temperature_salinity(T, S, h, G, GV, US, param_fi call get_param(param_file, mdl, "TS_RANGE_T_DENSE", T_dense, & units="degC", default=US%C_to_degC*T_Ref, scale=US%degC_to_C, do_not_log=.true.) call get_param(param_file, mdl, "S_REF", S_ref, & - units="1e-3", default=35.0, scale=US%ppt_to_S, do_not_log=.true.) + units="ppt", default=35.0, scale=US%ppt_to_S, do_not_log=.true.) call get_param(param_file, mdl, "TS_RANGE_S_LIGHT", S_light, & - units="1e-3", default=US%S_to_ppt*S_Ref, scale=US%ppt_to_S, do_not_log=.true.) + units="ppt", default=US%S_to_ppt*S_Ref, scale=US%ppt_to_S, do_not_log=.true.) call get_param(param_file, mdl, "TS_RANGE_S_DENSE", S_dense, & - units="1e-3", default=US%S_to_ppt*S_Ref, scale=US%ppt_to_S, do_not_log=.true.) + units="ppt", default=US%S_to_ppt*S_Ref, scale=US%ppt_to_S, do_not_log=.true.) call get_param(param_file, mdl, "TS_RANGE_RESOLN_RATIO", res_rat, & units="nondim", default=1.0, do_not_log=.true.) if (just_read) return ! All run-time parameters have been read, so return. diff --git a/src/user/sloshing_initialization.F90 b/src/user/sloshing_initialization.F90 index 75e5889092..4381d42038 100644 --- a/src/user/sloshing_initialization.F90 +++ b/src/user/sloshing_initialization.F90 @@ -201,17 +201,17 @@ subroutine sloshing_initialize_temperature_salinity ( T, S, h, G, GV, US, param_ is = G%isc ; ie = G%iec ; js = G%jsc ; je = G%jec ; nz = GV%ke call get_param(param_file, mdl, "S_REF", S_ref, 'Reference value for salinity', & - default=35.0, units='1e-3', scale=US%ppt_to_S, do_not_log=just_read) + default=35.0, units="ppt", scale=US%ppt_to_S, do_not_log=just_read) call get_param(param_file, mdl, "T_REF", T_ref, 'Reference value for temperature', & units='degC', scale=US%degC_to_C, fail_if_missing=.not.just_read, do_not_log=just_read) ! The default is to assume an increase by 2 ppt for the salinity and a uniform temperature. call get_param(param_file, mdl, "S_RANGE", S_range, 'Initial salinity range.', & - units='1e-3', default=2.0, scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=2.0, scale=US%ppt_to_S, do_not_log=just_read) call get_param(param_file, mdl, "T_RANGE", T_range, 'Initial temperature range', & units='degC', default=0.0, scale=US%degC_to_C, do_not_log=just_read) call get_param(param_file, mdl, "INITIAL_SSS", S_surf, "Initial surface salinity", & - units="1e-3", default=34.0, scale=US%ppt_to_S, do_not_log=just_read) + units="ppt", default=34.0, scale=US%ppt_to_S, do_not_log=just_read) call get_param(param_file, mdl, "SLOSHING_T_PERT", T_pert, & 'A mid-column temperature perturbation in the sloshing test case', & units='degC', default=1.0, scale=US%degC_to_C, do_not_log=just_read) From a28443ba138c693fd498a2b3fd40a7b6a91ce83a Mon Sep 17 00:00:00 2001 From: Kate Hedstrom Date: Wed, 6 Dec 2023 13:50:09 -0900 Subject: [PATCH 11/22] Fix for an OBC issue with mask_tables - Without this, if part of your OBC is filled with land mask and if that land mask contains a masked out tile, you will generate a NaN from the phase speed calculation where h is negative in the halo neighbor of that masked tile. --- src/core/MOM_open_boundary.F90 | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/core/MOM_open_boundary.F90 b/src/core/MOM_open_boundary.F90 index b54c93cefa..76ac477906 100644 --- a/src/core/MOM_open_boundary.F90 +++ b/src/core/MOM_open_boundary.F90 @@ -3919,7 +3919,7 @@ subroutine update_OBC_segment_data(G, GV, US, OBC, tv, h, Time) segment%Htot(I,j) = segment%Htot(I,j) + segment%h(I,j,k) segment%dZtot(I,j) = segment%dZtot(I,j) + dz(i+ishift,j,k) enddo - segment%Cg(I,j) = sqrt(GV%g_prime(1) * segment%dZtot(I,j)) + segment%Cg(I,j) = sqrt(GV%g_prime(1) * max(0.0, segment%dZtot(I,j))) enddo else! (segment%direction == OBC_DIRECTION_N .or. segment%direction == OBC_DIRECTION_S) allocate(normal_trans_bt(segment%HI%isd:segment%HI%ied,segment%HI%JsdB:segment%HI%JedB), source=0.0) @@ -3933,7 +3933,7 @@ subroutine update_OBC_segment_data(G, GV, US, OBC, tv, h, Time) segment%Htot(i,J) = segment%Htot(i,J) + segment%h(i,J,k) segment%dZtot(i,J) = segment%dZtot(i,J) + dz(i,j+jshift,k) enddo - segment%Cg(i,J) = sqrt(GV%g_prime(1) * segment%dZtot(i,J)) + segment%Cg(i,J) = sqrt(GV%g_prime(1) * max(0.0, segment%dZtot(i,J))) enddo endif From 5c146680ff820c86e756611ec5b6cf2e26ad4621 Mon Sep 17 00:00:00 2001 From: Robert Hallberg Date: Fri, 15 Dec 2023 16:28:48 -0500 Subject: [PATCH 12/22] +FIX_USTAR_GUSTLESS_BUG is now USTAR_GUSTLESS_BUG Renamed the runtime parameter FIX_USTAR_GUSTLESS_BUG to USTAR_GUSTLESS_BUG (with a switch between the meanings of true and false for the two parameters) for consistency with the syntax of other bug-fix flags in MOM6 and to partially address dev/gfdl MOM6 issue #237. Input parameter files need not be changed right away because MOM6 will still work if FIX_USTAR_GUSTLESS_BUG is specified instead of USTAR_GUSTLESS_BUG, but USTAR_GUSTLESS_BUG will be logged, so there are changes to the MOM_parameter_doc files. By default or with existing input parameter files, all answers are bitwise identical, and there is error handling if inconsistent settings of FIX_USTAR_GUSTLESS_BUG and USTAR_GUSTLESS_BUG are both specified. --- .../FMS_cap/MOM_surface_forcing_gfdl.F90 | 34 +++++++++++++-- .../STALE_mct_cap/mom_surface_forcing_mct.F90 | 41 +++++++++++++++---- .../nuopc_cap/mom_surface_forcing_nuopc.F90 | 41 +++++++++++++++---- .../solo_driver/MOM_surface_forcing.F90 | 39 +++++++++++++++--- 4 files changed, 129 insertions(+), 26 deletions(-) diff --git a/config_src/drivers/FMS_cap/MOM_surface_forcing_gfdl.F90 b/config_src/drivers/FMS_cap/MOM_surface_forcing_gfdl.F90 index fc4d8e79f6..1e56486329 100644 --- a/config_src/drivers/FMS_cap/MOM_surface_forcing_gfdl.F90 +++ b/config_src/drivers/FMS_cap/MOM_surface_forcing_gfdl.F90 @@ -137,7 +137,7 @@ module MOM_surface_forcing_gfdl !! gustiness calculations. Values below 20190101 recover the answers !! from the end of 2018, while higher values use a simpler expression !! to calculate gustiness. - logical :: fix_ustar_gustless_bug !< If true correct a bug in the time-averaging of the + logical :: ustar_gustless_bug !< If true, include a bug in the time-averaging of the !! gustless wind friction velocity. logical :: check_no_land_fluxes !< Return warning if IOB flux over land is non-zero @@ -284,7 +284,7 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G, ! flux type has been used. if (fluxes%dt_buoy_accum < 0) then call allocate_forcing_type(G, fluxes, water=.true., heat=.true., ustar=.not.CS%nonBous, press=.true., & - fix_accum_bug=CS%fix_ustar_gustless_bug, tau_mag=CS%nonBous) + fix_accum_bug=.not.CS%ustar_gustless_bug, tau_mag=CS%nonBous) call safe_alloc_ptr(fluxes%sw_vis_dir,isd,ied,jsd,jed) call safe_alloc_ptr(fluxes%sw_vis_dif,isd,ied,jsd,jed) @@ -1298,6 +1298,9 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, wind_stagger) logical :: new_sim ! False if this simulation was started from a restart file ! or other equivalent files. logical :: iceberg_flux_diags ! If true, diagnostics of fluxes from icebergs are available. + logical :: fix_ustar_gustless_bug ! If false, include a bug using an older run-time parameter. + logical :: test_value ! This is used to determine whether a logical parameter is being set explicitly. + logical :: explicit_bug, explicit_fix ! These indicate which parameters are set explicitly. integer :: default_answer_date ! The default setting for the various ANSWER_DATE flags. type(time_type) :: Time_frc type(directories) :: dirs ! A structure containing relevant directory paths and input filenames. @@ -1611,9 +1614,32 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, wind_stagger) "of 2018, while higher values use a simpler expression to calculate gustiness.", & default=default_answer_date) - call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", CS%fix_ustar_gustless_bug, & + call get_param(param_file, mdl, "USTAR_GUSTLESS_BUG", CS%ustar_gustless_bug, & + "If true include a bug in the time-averaging of the gustless wind friction velocity", & + default=.false., do_not_log=.true.) + ! This is used to test whether USTAR_GUSTLESS_BUG is being actively set. + call get_param(param_file, mdl, "USTAR_GUSTLESS_BUG", test_value, default=.true., do_not_log=.true.) + explicit_bug = CS%ustar_gustless_bug .eqv. test_value + call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", fix_ustar_gustless_bug, & "If true correct a bug in the time-averaging of the gustless wind friction velocity", & - default=.true.) + default=.true., do_not_log=.true.) + call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", test_value, default=.false., do_not_log=.true.) + explicit_fix = fix_ustar_gustless_bug .eqv. test_value + + if (explicit_bug .and. explicit_fix .and. (fix_ustar_gustless_bug .eqv. CS%ustar_gustless_bug)) then + ! USTAR_GUSTLESS_BUG is being explicitly set, and should not be changed. + call MOM_error(FATAL, "USTAR_GUSTLESS_BUG and FIX_USTAR_GUSTLESS_BUG are both being set "//& + "with inconsistent values. FIX_USTAR_GUSTLESS_BUG is an obsolete "//& + "parameter and should be removed.") + elseif (explicit_fix) then + call MOM_error(WARNING, "FIX_USTAR_GUSTLESS_BUG is an obsolete parameter. "//& + "Use USTAR_GUSTLESS_BUG instead (noting that it has the opposite sense).") + CS%ustar_gustless_bug = .not.fix_ustar_gustless_bug + endif + call log_param(param_file, mdl, "USTAR_GUSTLESS_BUG", CS%ustar_gustless_bug, & + "If true include a bug in the time-averaging of the gustless wind friction velocity", & + default=.false.) + ! See whether sufficiently thick sea ice should be treated as rigid. call get_param(param_file, mdl, "USE_RIGID_SEA_ICE", CS%rigid_sea_ice, & diff --git a/config_src/drivers/STALE_mct_cap/mom_surface_forcing_mct.F90 b/config_src/drivers/STALE_mct_cap/mom_surface_forcing_mct.F90 index a5c2db6974..bb57810f5b 100644 --- a/config_src/drivers/STALE_mct_cap/mom_surface_forcing_mct.F90 +++ b/config_src/drivers/STALE_mct_cap/mom_surface_forcing_mct.F90 @@ -16,7 +16,7 @@ module MOM_surface_forcing_mct use MOM_domains, only : AGRID, BGRID_NE, CGRID_NE, To_All use MOM_domains, only : To_North, To_East, Omit_Corners use MOM_error_handler, only : MOM_error, WARNING, FATAL, is_root_pe, MOM_mesg -use MOM_file_parser, only : get_param, log_version, param_file_type +use MOM_file_parser, only : get_param, log_param, log_version, param_file_type use MOM_forcing_type, only : forcing, mech_forcing use MOM_forcing_type, only : forcing_diags, mech_forcing_diags, register_forcing_type_diags use MOM_forcing_type, only : allocate_forcing_type, deallocate_forcing_type @@ -117,7 +117,7 @@ module MOM_surface_forcing_mct real :: max_delta_srestore !< maximum delta salinity used for restoring [S ~> ppt] real :: max_delta_trestore !< maximum delta sst used for restoring [C ~> degC] real, pointer, dimension(:,:) :: basin_mask => NULL() !< mask for SSS restoring by basin - logical :: fix_ustar_gustless_bug !< If true correct a bug in the time-averaging of the + logical :: ustar_gustless_bug !< If true, include a bug in the time-averaging of the !! gustless wind friction velocity. type(diag_ctrl), pointer :: diag !< structure to regulate diagnostic output timing character(len=200) :: inputdir !< directory where NetCDF input files are @@ -276,7 +276,7 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G, ! flux type has been used. if (fluxes%dt_buoy_accum < 0) then call allocate_forcing_type(G, fluxes, water=.true., heat=.true., ustar=.true., & - press=.true., fix_accum_bug=CS%fix_ustar_gustless_bug, tau_mag=.true.) + press=.true., fix_accum_bug=.not.CS%ustar_gustless_bug, tau_mag=.true.) call safe_alloc_ptr(fluxes%sw_vis_dir,isd,ied,jsd,jed) call safe_alloc_ptr(fluxes%sw_vis_dif,isd,ied,jsd,jed) @@ -1025,11 +1025,13 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, restore_salt, ! Local variables real :: utide ! The RMS tidal velocity [Z T-1 ~> m s-1]. type(directories) :: dirs - logical :: new_sim, iceberg_flux_diags + logical :: new_sim, iceberg_flux_diags, fix_ustar_gustless_bug + logical :: test_value ! This is used to determine whether a logical parameter is being set explicitly. + logical :: explicit_bug, explicit_fix ! These indicate which parameters are set explicitly. type(time_type) :: Time_frc character(len=200) :: TideAmp_file, gust_file, salt_file, temp_file ! Input file names. -! This include declares and sets the variable "version". -#include "version_variable.h" + ! This include declares and sets the variable "version". +# include "version_variable.h" character(len=40) :: mdl = "MOM_surface_forcing_mct" ! This module's name. character(len=48) :: stagger character(len=48) :: flnam @@ -1257,9 +1259,32 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, restore_salt, call MOM_read_data(gust_file, 'gustiness', CS%gust, G%domain, timelevel=1, & scale=US%kg_m3_to_R*US%m_s_to_L_T**2*US%L_to_Z) ! units in file should be Pa endif - call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", CS%fix_ustar_gustless_bug, & + + call get_param(param_file, mdl, "USTAR_GUSTLESS_BUG", CS%ustar_gustless_bug, & + "If true include a bug in the time-averaging of the gustless wind friction velocity", & + default=.false., do_not_log=.true.) + ! This is used to test whether USTAR_GUSTLESS_BUG is being actively set. + call get_param(param_file, mdl, "USTAR_GUSTLESS_BUG", test_value, default=.true., do_not_log=.true.) + explicit_bug = CS%ustar_gustless_bug .eqv. test_value + call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", fix_ustar_gustless_bug, & "If true correct a bug in the time-averaging of the gustless wind friction velocity", & - default=.true.) + default=.true., do_not_log=.true.) + call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", test_value, default=.false., do_not_log=.true.) + explicit_fix = fix_ustar_gustless_bug .eqv. test_value + + if (explicit_bug .and. explicit_fix .and. (fix_ustar_gustless_bug .eqv. CS%ustar_gustless_bug)) then + ! USTAR_GUSTLESS_BUG is being explicitly set, and should not be changed. + call MOM_error(FATAL, "USTAR_GUSTLESS_BUG and FIX_USTAR_GUSTLESS_BUG are both being set "//& + "with inconsistent values. FIX_USTAR_GUSTLESS_BUG is an obsolete "//& + "parameter and should be removed.") + elseif (explicit_fix) then + call MOM_error(WARNING, "FIX_USTAR_GUSTLESS_BUG is an obsolete parameter. "//& + "Use USTAR_GUSTLESS_BUG instead (noting that it has the opposite sense).") + CS%ustar_gustless_bug = .not.fix_ustar_gustless_bug + endif + call log_param(param_file, mdl, "USTAR_GUSTLESS_BUG", CS%ustar_gustless_bug, & + "If true include a bug in the time-averaging of the gustless wind friction velocity", & + default=.false.) ! See whether sufficiently thick sea ice should be treated as rigid. call get_param(param_file, mdl, "USE_RIGID_SEA_ICE", CS%rigid_sea_ice, & diff --git a/config_src/drivers/nuopc_cap/mom_surface_forcing_nuopc.F90 b/config_src/drivers/nuopc_cap/mom_surface_forcing_nuopc.F90 index d699697140..e7d6c9abc6 100644 --- a/config_src/drivers/nuopc_cap/mom_surface_forcing_nuopc.F90 +++ b/config_src/drivers/nuopc_cap/mom_surface_forcing_nuopc.F90 @@ -17,7 +17,7 @@ module MOM_surface_forcing_nuopc use MOM_domains, only : AGRID, BGRID_NE, CGRID_NE, To_All use MOM_domains, only : To_North, To_East, Omit_Corners use MOM_error_handler, only : MOM_error, WARNING, FATAL, is_root_pe, MOM_mesg -use MOM_file_parser, only : get_param, log_version, param_file_type +use MOM_file_parser, only : get_param, log_param, log_version, param_file_type use MOM_forcing_type, only : forcing, mech_forcing use MOM_forcing_type, only : forcing_diags, mech_forcing_diags, register_forcing_type_diags use MOM_forcing_type, only : allocate_forcing_type, deallocate_forcing_type @@ -124,7 +124,7 @@ module MOM_surface_forcing_nuopc real :: max_delta_srestore !< maximum delta salinity used for restoring [S ~> ppt] real :: max_delta_trestore !< maximum delta sst used for restoring [C ~> degC] real, pointer, dimension(:,:) :: basin_mask => NULL() !< mask for SSS restoring by basin - logical :: fix_ustar_gustless_bug !< If true correct a bug in the time-averaging of the + logical :: ustar_gustless_bug !< If true, include a bug in the time-averaging of the !! gustless wind friction velocity. type(diag_ctrl), pointer :: diag !< structure to regulate diagnostic output timing @@ -296,7 +296,7 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G, ! flux type has been used. if (fluxes%dt_buoy_accum < 0) then call allocate_forcing_type(G, fluxes, water=.true., heat=.true., ustar=.true., & - press=.true., fix_accum_bug=CS%fix_ustar_gustless_bug, & + press=.true., fix_accum_bug=.not.CS%ustar_gustless_bug, & cfc=CS%use_CFC, hevap=CS%enthalpy_cpl, tau_mag=.true.) !call safe_alloc_ptr(fluxes%omega_w2x,isd,ied,jsd,jed) @@ -1103,11 +1103,13 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, restore_salt, ! Local variables real :: utide ! The RMS tidal velocity [Z T-1 ~> m s-1]. type(directories) :: dirs - logical :: new_sim, iceberg_flux_diags + logical :: new_sim, iceberg_flux_diags, fix_ustar_gustless_bug + logical :: test_value ! This is used to determine whether a logical parameter is being set explicitly. + logical :: explicit_bug, explicit_fix ! These indicate which parameters are set explicitly. type(time_type) :: Time_frc character(len=200) :: TideAmp_file, gust_file, salt_file, temp_file ! Input file names. -! This include declares and sets the variable "version". -#include "version_variable.h" + ! This include declares and sets the variable "version". +# include "version_variable.h" character(len=40) :: mdl = "MOM_surface_forcing_nuopc" ! This module's name. character(len=48) :: stagger character(len=48) :: flnam @@ -1342,9 +1344,32 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, restore_salt, call MOM_read_data(gust_file, 'gustiness', CS%gust, G%domain, timelevel=1, & scale=US%kg_m3_to_R*US%m_s_to_L_T**2*US%L_to_Z) ! units in file should be Pa endif - call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", CS%fix_ustar_gustless_bug, & + + call get_param(param_file, mdl, "USTAR_GUSTLESS_BUG", CS%ustar_gustless_bug, & + "If true include a bug in the time-averaging of the gustless wind friction velocity", & + default=.false., do_not_log=.true.) + ! This is used to test whether USTAR_GUSTLESS_BUG is being actively set. + call get_param(param_file, mdl, "USTAR_GUSTLESS_BUG", test_value, default=.true., do_not_log=.true.) + explicit_bug = CS%ustar_gustless_bug .eqv. test_value + call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", fix_ustar_gustless_bug, & "If true correct a bug in the time-averaging of the gustless wind friction velocity", & - default=.true.) + default=.true., do_not_log=.true.) + call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", test_value, default=.false., do_not_log=.true.) + explicit_fix = fix_ustar_gustless_bug .eqv. test_value + + if (explicit_bug .and. explicit_fix .and. (fix_ustar_gustless_bug .eqv. CS%ustar_gustless_bug)) then + ! USTAR_GUSTLESS_BUG is being explicitly set, and should not be changed. + call MOM_error(FATAL, "USTAR_GUSTLESS_BUG and FIX_USTAR_GUSTLESS_BUG are both being set "//& + "with inconsistent values. FIX_USTAR_GUSTLESS_BUG is an obsolete "//& + "parameter and should be removed.") + elseif (explicit_fix) then + call MOM_error(WARNING, "FIX_USTAR_GUSTLESS_BUG is an obsolete parameter. "//& + "Use USTAR_GUSTLESS_BUG instead (noting that it has the opposite sense).") + CS%ustar_gustless_bug = .not.fix_ustar_gustless_bug + endif + call log_param(param_file, mdl, "USTAR_GUSTLESS_BUG", CS%ustar_gustless_bug, & + "If true include a bug in the time-averaging of the gustless wind friction velocity", & + default=.false.) ! See whether sufficiently thick sea ice should be treated as rigid. call get_param(param_file, mdl, "USE_RIGID_SEA_ICE", CS%rigid_sea_ice, & diff --git a/config_src/drivers/solo_driver/MOM_surface_forcing.F90 b/config_src/drivers/solo_driver/MOM_surface_forcing.F90 index 14f861e955..3de43eec85 100644 --- a/config_src/drivers/solo_driver/MOM_surface_forcing.F90 +++ b/config_src/drivers/solo_driver/MOM_surface_forcing.F90 @@ -19,7 +19,7 @@ module MOM_surface_forcing use MOM_domains, only : fill_symmetric_edges, CGRID_NE use MOM_error_handler, only : MOM_error, FATAL, WARNING, MOM_mesg, is_root_pe use MOM_error_handler, only : callTree_enter, callTree_leave -use MOM_file_parser, only : get_param, log_version, param_file_type +use MOM_file_parser, only : get_param, log_param, log_version, param_file_type use MOM_string_functions, only : uppercase use MOM_forcing_type, only : forcing, mech_forcing use MOM_forcing_type, only : set_net_mass_forcing, copy_common_forcing_fields @@ -116,8 +116,8 @@ module MOM_surface_forcing !! Dates before 20190101 use original answers. !! Dates after 20190101 use a form of the gyre wind stresses that are !! rotationally invariant and more likely to be the same between compilers. - logical :: fix_ustar_gustless_bug !< If true correct a bug in the time-averaging of the - !! gustless wind friction velocity. + logical :: ustar_gustless_bug !< If true, include a bug in the time-averaging of the + !! gustless wind friction velocity. ! if WIND_CONFIG=='scurves' then use the following to define a piecewise scurve profile real :: scurves_ydata(20) = 90. !< Latitudes of scurve nodes [degreesN] real :: scurves_taux(20) = 0. !< Zonal wind stress values at scurve nodes [R L Z T-2 ~> Pa] @@ -256,7 +256,7 @@ subroutine set_forcing(sfc_state, forces, fluxes, day_start, day_interval, G, US call allocate_mech_forcing(G, forces, stress=.true., ustar=.not.CS%nonBous, press=.true., tau_mag=CS%nonBous) call allocate_forcing_type(G, fluxes, ustar=.not.CS%nonBous, tau_mag=CS%nonBous, & - fix_accum_bug=CS%fix_ustar_gustless_bug) + fix_accum_bug=.not.CS%ustar_gustless_bug) if (trim(CS%buoy_config) /= "NONE") then if ( CS%use_temperature ) then call allocate_forcing_type(G, fluxes, water=.true., heat=.true., press=.true.) @@ -1582,6 +1582,9 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, tracer_flow_C real :: flux_const_default ! The unscaled value of FLUXCONST [m day-1] logical :: Boussinesq ! If true, this run is fully Boussinesq logical :: semi_Boussinesq ! If true, this run is partially non-Boussinesq + logical :: fix_ustar_gustless_bug ! If false, include a bug using an older run-time parameter. + logical :: test_value ! This is used to determine whether a logical parameter is being set explicitly. + logical :: explicit_bug, explicit_fix ! These indicate which parameters are set explicitly. integer :: default_answer_date ! The default setting for the various ANSWER_DATE flags. character(len=40) :: mdl = "MOM_surface_forcing" ! This module's name. character(len=200) :: filename, gust_file ! The name of the gustiness input file. @@ -1935,9 +1938,33 @@ subroutine surface_forcing_init(Time, G, US, param_file, diag, CS, tracer_flow_C call get_param(param_file, mdl, "GUST_CONST", CS%gust_const, & "The background gustiness in the winds.", & units="Pa", default=0.0, scale=US%Pa_to_RLZ_T2) - call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", CS%fix_ustar_gustless_bug, & + + call get_param(param_file, mdl, "USTAR_GUSTLESS_BUG", CS%ustar_gustless_bug, & + "If true include a bug in the time-averaging of the gustless wind friction velocity", & + default=.false., do_not_log=.true.) + ! This is used to test whether USTAR_GUSTLESS_BUG is being actively set. + call get_param(param_file, mdl, "USTAR_GUSTLESS_BUG", test_value, default=.true., do_not_log=.true.) + explicit_bug = CS%ustar_gustless_bug .eqv. test_value + call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", fix_ustar_gustless_bug, & "If true correct a bug in the time-averaging of the gustless wind friction velocity", & - default=.true.) + default=.true., do_not_log=.true.) + call get_param(param_file, mdl, "FIX_USTAR_GUSTLESS_BUG", test_value, default=.false., do_not_log=.true.) + explicit_fix = fix_ustar_gustless_bug .eqv. test_value + + if (explicit_bug .and. explicit_fix .and. (fix_ustar_gustless_bug .eqv. CS%ustar_gustless_bug)) then + ! USTAR_GUSTLESS_BUG is being explicitly set, and should not be changed. + call MOM_error(FATAL, "USTAR_GUSTLESS_BUG and FIX_USTAR_GUSTLESS_BUG are both being set "//& + "with inconsistent values. FIX_USTAR_GUSTLESS_BUG is an obsolete "//& + "parameter and should be removed.") + elseif (explicit_fix) then + call MOM_error(WARNING, "FIX_USTAR_GUSTLESS_BUG is an obsolete parameter. "//& + "Use USTAR_GUSTLESS_BUG instead (noting that it has the opposite sense).") + CS%ustar_gustless_bug = .not.fix_ustar_gustless_bug + endif + call log_param(param_file, mdl, "USTAR_GUSTLESS_BUG", CS%ustar_gustless_bug, & + "If true include a bug in the time-averaging of the gustless wind friction velocity", & + default=.false.) + call get_param(param_file, mdl, "READ_GUST_2D", CS%read_gust_2d, & "If true, use a 2-dimensional gustiness supplied from "//& "an input file", default=.false.) From 7ddc727a2460784ea048e511d66dfa207c0a408e Mon Sep 17 00:00:00 2001 From: alex-huth Date: Mon, 27 Nov 2023 18:15:46 -0500 Subject: [PATCH 13/22] This commit guarantees consistency of the ice sheet code under rotated/flipped input and grids, and under dimensional rescaling to the +/-140 power. Bitwise identical results were achieved under rotation/rescaling using standard 2D test cases such as MISMIP+. Major changes include the following: - Specified order of operations throughout, and modified the implementation of FEM integration, h-point-to-node operations, etc for consistency under rotation (see MOM_ice_shelf_dynamics.F90 subroutines calc_shelf_driving_stress, CG_action, CG_action_subgrid_basal, matrix_diagonal, shelf_advance_front, and interpolate_h_to_b). - Added an ice-shelf version of 'first_direction' and 'alterate_first_direction', allowing users to control the order in which the x- and y-direction ice-shelf advection calls are made. Required for consistency under rotation. - Dimensional rescaling fixes throughout MOM_ice_shelf_initialize.F90, and within MOM_ice_shelf_dynamics.F90 (see subroutines initialize_ice_shelf_dyn, ice_shelf_solve_outer, and calc_shelf_taub) - Rotation/rescaling testing revealed two additional bugs that were subsequently fixed: (1) An index error in the conjugate gradient algorithm (subroutine CG_action) (2) Discretization error for the east/north fluxes in subroutines ice_shelf_advect_thickness_x and ice_shelf_advect_thickness_y. The commit also includes several simple changes for code readability and computational efficiency: - Saved Phi, PhiC, and Phisub in the ice shelf dynamics control structure at the start of each run, rather than reallocating and recalculating these static fields each time they are used. Reshaped the Phisub array for computational efficiency over loops. - Modified the sub-cell grounding scheme so that it is only called for partially-grounded cells that contain the grounding line (i.e. where float_cond(i,j)==1). Added float_cond to the ice dynamics structure for output. - Simplified the option to calculate ice viscosity at 4 quadrature points per cell rather than at cell centers, by adding parameter NUMBER_OF_ICE_VISCOSITY_QUADRATURE_POINTS and reshaping CS%ice_visc accordingly. - Style changes and removal of unused code (e.g. removed subroutine apply_boundary_values and field thickness_bdry_val) --- src/ice_shelf/MOM_ice_shelf_dynamics.F90 | 1180 ++++++++++---------- src/ice_shelf/MOM_ice_shelf_initialize.F90 | 58 +- 2 files changed, 620 insertions(+), 618 deletions(-) diff --git a/src/ice_shelf/MOM_ice_shelf_dynamics.F90 b/src/ice_shelf/MOM_ice_shelf_dynamics.F90 index 312fa43fe9..4bfcc3605c 100644 --- a/src/ice_shelf/MOM_ice_shelf_dynamics.F90 +++ b/src/ice_shelf/MOM_ice_shelf_dynamics.F90 @@ -84,12 +84,11 @@ module MOM_ice_shelf_dynamics real, pointer, dimension(:,:) :: t_shelf => NULL() !< Vertically integrated temperature in the ice shelf/stream, !! on corner-points (B grid) [C ~> degC] real, pointer, dimension(:,:) :: tmask => NULL() !< A mask on tracer points that is 1 where there is ice. - real, pointer, dimension(:,:) :: ice_visc => NULL() !< Glen's law ice viscosity (Pa s), + real, pointer, dimension(:,:,:) :: ice_visc => NULL() !< Glen's law ice viscosity (Pa s), !! in [R L2 T-1 ~> kg m-1 s-1]. - real, pointer, dimension(:,:,:) :: Ee => NULL() !< Glen's effective strain-rate ** (1-n)/(n) + !! at either 1 (cell-centered) or 4 quadrature points per cell real, pointer, dimension(:,:) :: AGlen_visc => NULL() !< Ice-stiffness parameter in Glen's law ice viscosity, !! often in [Pa-3 s-1] if n_Glen is 3. - real, pointer, dimension(:,:) :: thickness_bdry_val => NULL() !< The ice thickness at an inflowing boundary [Z ~> m]. real, pointer, dimension(:,:) :: u_bdry_val => NULL() !< The zonal ice velocity at inflowing boundaries !! [L yr-1 ~> m yr-1] real, pointer, dimension(:,:) :: v_bdry_val => NULL() !< The meridional ice velocity at inflowing boundaries @@ -114,6 +113,14 @@ module MOM_ice_shelf_dynamics real, pointer, dimension(:,:) :: ground_frac => NULL() !< Fraction of the time a cell is "exposed", i.e. the column !! thickness is below a threshold and interacting with the rock [nondim]. When this !! is 1, the ice-shelf is grounded + real, pointer, dimension(:,:) :: float_cond => NULL() !< If GL_regularize=true, indicates cells containing + !! the grounding line (float_cond=1) or not (float_cond=0) + real, pointer, dimension(:,:,:,:) :: Phi => NULL() !< The gradients of bilinear basis elements at Gaussian + !! 4 quadrature points surrounding the cell vertices [L-1 ~> m-1]. + real, pointer, dimension(:,:,:) :: PhiC => NULL() !< The gradients of bilinear basis elements at 1 cell-centered + !! quadrature point per cell [L-1 ~> m-1]. + real, pointer, dimension(:,:,:,:,:,:) :: Phisub => NULL() !< Quadrature structure weights at subgridscale + !! locations for finite element calculations [nondim] integer :: OD_rt_counter = 0 !< A counter of the number of contributions to OD_rt. real :: velocity_update_time_step !< The time interval over which to update the ice shelf velocity @@ -128,6 +135,13 @@ module MOM_ice_shelf_dynamics real :: density_ice !< A typical density of ice [R ~> kg m-3]. logical :: advect_shelf !< If true (default), advect ice shelf and evolve thickness + logical :: alternate_first_direction_IS !< If true, alternate whether the x- or y-direction + !! updates occur first in directionally split parts of the calculation. + integer :: first_direction_IS !< An integer that indicates which direction is + !! to be updated first in directionally split + !! parts of the ice sheet calculation (e.g. advection). + real :: first_dir_restart_IS = -1.0 !< A real copy of CS%first_direction_IS for use in restart files + integer :: visc_qps !< The number of quadrature points per cell (1 or 4) on which to calculate ice viscosity. character(len=40) :: ice_viscosity_compute !< Specifies whether the ice viscosity is computed internally !! according to Glen's flow law; is constant (for debugging purposes) !! or using observed strain rates and read from a file @@ -150,7 +164,7 @@ module MOM_ice_shelf_dynamics real :: eps_glen_min !< Min. strain rate to avoid infinite Glen's law viscosity, [T-1 ~> s-1]. real :: n_basal_fric !< Exponent in sliding law tau_b = C u^(m_slide) [nondim] logical :: CoulombFriction !< Use Coulomb friction law (Schoof 2005, Gagliardini et al 2007) - real :: CF_MinN !< Minimum Coulomb friction effective pressure [R L2 T-2 ~> Pa] + real :: CF_MinN !< Minimum Coulomb friction effective pressure [Pa] real :: CF_PostPeak !< Coulomb friction post peak exponent [nondim] real :: CF_Max !< Coulomb friction maximum coefficient [nondim] real :: density_ocean_avg !< A typical ocean density [R ~> kg m-3]. This does not affect ocean @@ -202,7 +216,7 @@ module MOM_ice_shelf_dynamics !>@{ Diagnostic handles integer :: id_u_shelf = -1, id_v_shelf = -1, id_t_shelf = -1, & id_taudx_shelf = -1, id_taudy_shelf = -1, id_bed_elev = -1, & - id_ground_frac = -1, id_col_thick = -1, id_OD_av = -1, & + id_ground_frac = -1, id_col_thick = -1, id_OD_av = -1, id_float_cond = -1, & id_u_mask = -1, id_v_mask = -1, id_ufb_mask =-1, id_vfb_mask = -1, id_t_mask = -1 !>@} ! ids for outputting intermediate thickness in advection subroutine (debugging) @@ -301,11 +315,28 @@ subroutine register_ice_shelf_dyn_restarts(G, US, param_file, CS, restart_CS) call get_param(param_file, mdl, "MISSING_SHELF_TEMPERATURE", T_shelf_missing, & "An ice shelf temperature to use where there is no ice shelf.",& units="degC", default=-10.0, scale=US%degC_to_C, do_not_log=.true.) + + call get_param(param_file, mdl, "NUMBER_OF_ICE_VISCOSITY_QUADRATURE_POINTS", CS%visc_qps, & + "Number of ice viscosity quadrature points. Either 1 (cell-centered) for 4", & + units="none", default=1) + if (CS%visc_qps/=1 .and. CS%visc_qps/=4) call MOM_error (FATAL, & + "NUMBER OF ICE_VISCOSITY_QUADRATURE_POINTS must be 1 or 4") + + call get_param(param_file, mdl, "FIRST_DIRECTION_IS", CS%first_direction_IS, & + "An integer that indicates which direction goes first "//& + "in parts of the code that use directionally split "//& + "updates (e.g. advection), with even numbers (or 0) used for x- first "//& + "and odd numbers used for y-first.", default=0) + call get_param(param_file, mdl, "ALTERNATE_FIRST_DIRECTION_IS", CS%alternate_first_direction_IS, & + "If true, after every advection call, alternate whether the x- or y- "//& + "direction advection updates occur first. "//& + "If this is true, FIRST_DIRECTION applies at the start of a new run or if "//& + "the next first direction can not be found in the restart file.", default=.false.) + allocate(CS%u_shelf(IsdB:IedB,JsdB:JedB), source=0.0) allocate(CS%v_shelf(IsdB:IedB,JsdB:JedB), source=0.0) allocate(CS%t_shelf(isd:ied,jsd:jed), source=T_shelf_missing) ! [C ~> degC] - allocate(CS%ice_visc(isd:ied,jsd:jed), source=0.0) - allocate(CS%Ee(isd:ied,jsd:jed,4), source=0.0) + allocate(CS%ice_visc(isd:ied,jsd:jed,CS%visc_qps), source=0.0) allocate(CS%AGlen_visc(isd:ied,jsd:jed), source=2.261e-25) ! [Pa-3 s-1] allocate(CS%basal_traction(isd:ied,jsd:jed), source=0.0) ! [R L3 T-1 ~> kg s-1] allocate(CS%C_basal_friction(isd:ied,jsd:jed), source=5.0e10) ! [Pa (m-1 s)^n_sliding] @@ -319,6 +350,7 @@ subroutine register_ice_shelf_dyn_restarts(G, US, param_file, CS, restart_CS) allocate(CS%u_face_mask_bdry(IsdB:IedB,JsdB:JedB), source=-2.0) allocate(CS%v_face_mask_bdry(IsdB:iedB,JsdB:JedB), source=-2.0) allocate(CS%h_bdry_val(isd:ied,jsd:jed), source=0.0) + ! additional restarts for ice shelf state call register_restart_field(CS%u_shelf, "u_shelf", .false., restart_CS, & "ice sheet/shelf u-velocity", & @@ -349,6 +381,8 @@ subroutine register_ice_shelf_dyn_restarts(G, US, param_file, CS, restart_CS) "ice thickness at the boundary", "m", conversion=US%Z_to_m) call register_restart_field(CS%bed_elev, "bed elevation", .true., restart_CS, & "bed elevation", "m", conversion=US%Z_to_m) + call register_restart_field(CS%first_dir_restart_IS, "first_direction_IS", .false., restart_CS, & + "Indicator of the first direction in split ice shelf calculations.", "nondim") endif end subroutine register_ice_shelf_dyn_restarts @@ -466,7 +500,7 @@ subroutine initialize_ice_shelf_dyn(param_file, Time, ISS, CS, G, US, diag, new_ units="none", default=.false., fail_if_missing=.false.) call get_param(param_file, mdl, "CF_MinN", CS%CF_MinN, & "Minimum Coulomb friction effective pressure", & - units="Pa", default=1.0, scale=US%Pa_to_RL2_T2, fail_if_missing=.false.) + units="Pa", default=1.0, fail_if_missing=.false.) call get_param(param_file, mdl, "CF_PostPeak", CS%CF_PostPeak, & "Coulomb friction post peak exponent", & units="none", default=1.0, fail_if_missing=.false.) @@ -500,11 +534,14 @@ subroutine initialize_ice_shelf_dyn(param_file, Time, ISS, CS, G, US, diag, new_ "If true, advect ice shelf and evolve thickness", & default=.true.) call get_param(param_file, mdl, "ICE_VISCOSITY_COMPUTE", CS%ice_viscosity_compute, & - "If MODEL, compute ice viscosity internally at cell centers, if OBS read from a file,"//& - "If MODEL_QUADRATURE, compute at quadrature points (4 per element),"//& + "If MODEL, compute ice viscosity internally using 1 or 4 quadrature points,"//& + "if OBS read from a file,"//& "if CONSTANT a constant value (for debugging).", & default="MODEL") + if ((CS%visc_qps/=1) .and. (trim(CS%ice_viscosity_compute) /= "MODEL")) then + call MOM_error(FATAL, "NUMBER_OF_ICE_VISCOSITY_QUADRATURE_POINTS must be 1 unless ICE_VISCOSITY_COMPUTE==MODEL.") + endif call get_param(param_file, mdl, "INFLOW_SHELF_TEMPERATURE", T_shelf_bdry, & "A default ice shelf temperature to use for ice flowing in through "//& "open boundaries.", units="degC", default=-15.0, scale=US%degC_to_C) @@ -558,7 +595,6 @@ subroutine initialize_ice_shelf_dyn(param_file, Time, ISS, CS, G, US, diag, new_ if (active_shelf_dynamics) then allocate( CS%t_bdry_val(isd:ied,jsd:jed), source=T_shelf_bdry) ! [C ~> degC] - allocate( CS%thickness_bdry_val(isd:ied,jsd:jed), source=0.0) allocate( CS%u_face_mask(Isdq:Iedq,Jsdq:Jedq), source=0.0) allocate( CS%v_face_mask(Isdq:Iedq,Jsdq:Jedq), source=0.0) allocate( CS%u_flux_bdry_val(Isdq:Iedq,jsd:jed), source=0.0) @@ -566,6 +602,7 @@ subroutine initialize_ice_shelf_dyn(param_file, Time, ISS, CS, G, US, diag, new_ allocate( CS%umask(Isdq:Iedq,Jsdq:Jedq), source=-1.0) allocate( CS%vmask(Isdq:Iedq,Jsdq:Jedq), source=-1.0) allocate( CS%tmask(Isdq:Iedq,Jsdq:Jedq), source=-1.0) + allocate( CS%float_cond(isd:ied,jsd:jed)) CS%OD_rt_counter = 0 allocate( CS%OD_rt(isd:ied,jsd:jed), source=0.0) @@ -575,6 +612,24 @@ subroutine initialize_ice_shelf_dyn(param_file, Time, ISS, CS, G, US, diag, new_ allocate( CS%calve_mask(isd:ied,jsd:jed), source=0.0) endif + allocate(CS%Phi(1:8,1:4,isd:ied,jsd:jed), source=0.0) + do j=G%jsd,G%jed ; do i=G%isd,G%ied + call bilinear_shape_fn_grid(G, i, j, CS%Phi(:,:,i,j)) + enddo; enddo + + if (CS%GL_regularize) then + allocate(CS%Phisub(2,2,CS%n_sub_regularize,CS%n_sub_regularize,2,2), source=0.0) + call bilinear_shape_functions_subgrid(CS%Phisub, CS%n_sub_regularize) + endif + + if ((trim(CS%ice_viscosity_compute) == "MODEL") .and. CS%visc_qps==1) then + !for calculating viscosity and 1 cell-centered quadrature point per cell + allocate(CS%PhiC(1:8,G%isc:G%iec,G%jsc:G%jec), source=0.0) + do j=G%jsc,G%jec ; do i=G%isc,G%iec + call bilinear_shape_fn_grid_1qp(G, i, j, CS%PhiC(:,i,j)) + enddo; enddo + endif + CS%elapsed_velocity_time = 0.0 call update_velocity_masks(CS, G, ISS%hmask, CS%umask, CS%vmask, CS%u_face_mask, CS%v_face_mask) @@ -622,15 +677,13 @@ subroutine initialize_ice_shelf_dyn(param_file, Time, ISS, CS, G, US, diag, new_ endif call pass_var(CS%OD_av,G%domain, complete=.false.) - call pass_var(CS%ground_frac,G%domain, complete=.false.) - call pass_var(CS%ice_visc,G%domain, complete=.false.) + call pass_var(CS%ground_frac, G%domain, complete=.false.) call pass_var(CS%basal_traction, G%domain, complete=.false.) call pass_var(CS%AGlen_visc, G%domain, complete=.false.) call pass_var(CS%bed_elev, G%domain, complete=.false.) call pass_var(CS%C_basal_friction, G%domain, complete=.false.) - call pass_var(CS%h_bdry_val, G%domain, complete=.false.) - call pass_var(CS%thickness_bdry_val, G%domain, complete=.true.) - if (trim(CS%ice_viscosity_compute) == "MODEL_QUADRATURE") call pass_var(CS%Ee,G%domain) + call pass_var(CS%h_bdry_val, G%domain, complete=.true.) + call pass_var(CS%ice_visc, G%domain) call pass_vector(CS%u_shelf, CS%v_shelf, G%domain, TO_ALL, BGRID_NE, complete=.false.) call pass_vector(CS%u_bdry_val, CS%v_bdry_val, G%domain, TO_ALL, BGRID_NE, complete=.false.) @@ -639,6 +692,12 @@ subroutine initialize_ice_shelf_dyn(param_file, Time, ISS, CS, G, US, diag, new_ endif if (active_shelf_dynamics) then + if (CS%first_dir_restart_IS > -1.0) then + CS%first_direction_IS = modulo(NINT(CS%first_dir_restart_IS), 2) + else + CS%first_dir_restart_IS = real(modulo(CS%first_direction_IS, 2)) + endif + ! If we are calving to a mask, i.e. if a mask exists where a shelf cannot, read the mask from a file. if (CS%calve_to_mask) then call MOM_mesg(" MOM_ice_shelf.F90, initialize_ice_shelf: reading calving_mask") @@ -670,16 +729,15 @@ subroutine initialize_ice_shelf_dyn(param_file, Time, ISS, CS, G, US, diag, new_ call pass_var(CS%C_basal_friction, G%domain, complete=.false.) ! initialize ice-stiffness AGlen - call initialize_ice_AGlen(CS%AGlen_visc, G, US, param_file) + call initialize_ice_AGlen(CS%AGlen_visc, CS%ice_viscosity_compute, G, US, param_file) call pass_var(CS%AGlen_visc, G%domain, complete=.false.) !initialize boundary conditions call initialize_ice_shelf_boundary_from_file(CS%u_face_mask_bdry, CS%v_face_mask_bdry, & CS%u_bdry_val, CS%v_bdry_val, CS%umask, CS%vmask, CS%h_bdry_val, & - CS%thickness_bdry_val, ISS%hmask, ISS%h_shelf, G, US, param_file ) + ISS%hmask, ISS%h_shelf, G, US, param_file ) call pass_var(ISS%hmask, G%domain, complete=.false.) - call pass_var(CS%h_bdry_val, G%domain, complete=.false.) - call pass_var(CS%thickness_bdry_val, G%domain, complete=.true.) + call pass_var(CS%h_bdry_val, G%domain, complete=.true.) call pass_vector(CS%u_bdry_val, CS%v_bdry_val, G%domain, TO_ALL, BGRID_NE, complete=.false.) call pass_vector(CS%u_face_mask_bdry, CS%v_face_mask_bdry, G%domain, TO_ALL, BGRID_NE, complete=.false.) @@ -696,17 +754,18 @@ subroutine initialize_ice_shelf_dyn(param_file, Time, ISS, CS, G, US, diag, new_ 'x-velocity of ice', 'm yr-1', conversion=365.0*86400.0*US%L_T_to_m_s) CS%id_v_shelf = register_diag_field('ice_shelf_model','v_shelf',CS%diag%axesB1, Time, & 'y-velocity of ice', 'm yr-1', conversion=365.0*86400.0*US%L_T_to_m_s) - ! I think that the conversion factors for the next two diagnostics are wrong. - RWH CS%id_taudx_shelf = register_diag_field('ice_shelf_model','taudx_shelf',CS%diag%axesB1, Time, & - 'x-driving stress of ice', 'kPa', conversion=1.e-3*US%RL2_T2_to_Pa) + 'x-driving stress of ice', 'kPa', conversion=1.e-3*US%RLZ_T2_to_Pa) CS%id_taudy_shelf = register_diag_field('ice_shelf_model','taudy_shelf',CS%diag%axesB1, Time, & - 'y-driving stress of ice', 'kPa', conversion=1.e-3*US%RL2_T2_to_Pa) + 'y-driving stress of ice', 'kPa', conversion=1.e-3*US%RLZ_T2_to_Pa) CS%id_u_mask = register_diag_field('ice_shelf_model','u_mask',CS%diag%axesB1, Time, & 'mask for u-nodes', 'none') CS%id_v_mask = register_diag_field('ice_shelf_model','v_mask',CS%diag%axesB1, Time, & 'mask for v-nodes', 'none') CS%id_ground_frac = register_diag_field('ice_shelf_model','ice_ground_frac',CS%diag%axesT1, Time, & 'fraction of cell that is grounded', 'none') + CS%id_float_cond = register_diag_field('ice_shelf_model','float_cond',CS%diag%axesT1, Time, & + 'sub-cell grounding cells', 'none') CS%id_col_thick = register_diag_field('ice_shelf_model','col_thick',CS%diag%axesT1, Time, & 'ocean column thickness passed to ice model', 'm', conversion=US%Z_to_m) CS%id_visc_shelf = register_diag_field('ice_shelf_model','ice_visc',CS%diag%axesT1, Time, & @@ -716,7 +775,7 @@ subroutine initialize_ice_shelf_dyn(param_file, Time, ISS, CS, G, US, diag, new_ CS%id_OD_av = register_diag_field('ice_shelf_model','OD_av',CS%diag%axesT1, Time, & 'intermediate ocean column thickness passed to ice model', 'm', conversion=US%Z_to_m) endif - call MOM_mesg("MOM_ice_shelf.F90, initialize_ice_shelf: initialize ice velocity.") + if (new_sim) then call update_OD_ffrac_uncoupled(CS, G, ISS%h_shelf(:,:)) endif @@ -821,6 +880,10 @@ subroutine update_ice_shelf(CS, ISS, G, US, time_step, Time, ocean_mass, coupled ! if (CS%advect_shelf) then call ice_shelf_advect(CS, ISS, G, time_step, Time) + if (CS%alternate_first_direction_IS) then + CS%first_direction_IS = modulo(CS%first_direction_IS+1,2) + CS%first_dir_restart_IS = real(CS%first_direction_IS) + endif endif CS%elapsed_velocity_time = CS%elapsed_velocity_time + time_step if (CS%elapsed_velocity_time >= CS%velocity_update_time_step) update_ice_vel = .true. @@ -832,7 +895,6 @@ subroutine update_ice_shelf(CS, ISS, G, US, time_step, Time, ocean_mass, coupled CS%GL_couple=.false. endif - if (update_ice_vel) then call ice_shelf_solve_outer(CS, ISS, G, US, CS%u_shelf, CS%v_shelf,CS%taudx_shelf,CS%taudy_shelf, iters, Time) endif @@ -854,12 +916,14 @@ subroutine update_ice_shelf(CS, ISS, G, US, time_step, Time, ocean_mass, coupled call post_data(CS%id_taudy_shelf, taud_y, CS%diag) endif if (CS%id_ground_frac > 0) call post_data(CS%id_ground_frac, CS%ground_frac, CS%diag) + if (CS%id_float_cond > 0) call post_data(CS%id_float_cond, CS%float_cond, CS%diag) if (CS%id_OD_av >0) call post_data(CS%id_OD_av, CS%OD_av,CS%diag) if (CS%id_visc_shelf > 0) then - ice_visc(:,:) = CS%ice_visc(:,:)*G%IareaT(:,:) - if (trim(CS%ice_viscosity_compute) == "MODEL_QUADRATURE") then - ice_visc(:,:) = ice_visc(:,:) * & - 0.25 * (CS%Ee(:,:,1) + CS%Ee(:,:,2) + CS%Ee(:,:,3) + CS%Ee(:,:,4)) + if (CS%visc_qps==4) then + ice_visc(:,:) = (0.25 * G%IareaT(:,:)) * & + ((CS%ice_visc(:,:,1) + CS%ice_visc(:,:,4)) + (CS%ice_visc(:,:,2) + CS%ice_visc(:,:,3))) + else + ice_visc(:,:) = CS%ice_visc(:,:,1)*G%IareaT(:,:) endif call post_data(CS%id_visc_shelf, ice_visc, CS%diag) endif @@ -945,11 +1009,11 @@ subroutine write_ice_shelf_energy(CS, G, US, mass, day, time_step) !calculate KE using cell-centered ice shelf velocity tmp1(:,:)=0.0 - KE_scale_factor = US%L_to_m**2 * US%RZ_to_kg_m2 * US%L_T_to_m_s**2 + KE_scale_factor = US%L_to_m**2 * (US%RZ_to_kg_m2 * US%L_T_to_m_s**2) do j=js,je ; do i=is,ie - tmp1(i,j) = KE_scale_factor * 0.03125 * G%areaT(i,j) * mass(i,j) * & - ((CS%u_shelf(I-1,J-1)+CS%u_shelf(I,J-1)+CS%u_shelf(I,J)+CS%u_shelf(I,J-1))**2 + & - (CS%v_shelf(I-1,J-1)+CS%v_shelf(I,J-1)+CS%v_shelf(I,J)+CS%v_shelf(I,J-1))**2) + tmp1(i,j) = (KE_scale_factor * 0.03125) * (G%areaT(i,j) * mass(i,j)) * & + (((CS%u_shelf(I-1,J-1)+CS%u_shelf(I,J))+(CS%u_shelf(I,J-1)+CS%u_shelf(I-1,J)))**2 + & + ((CS%v_shelf(I-1,J-1)+CS%v_shelf(I,J))+(CS%v_shelf(I,J-1)+CS%v_shelf(I-1,J)))**2) enddo; enddo KE_tot = reproducing_sum(tmp1, isr, ier, jsr, jer) @@ -958,7 +1022,7 @@ subroutine write_ice_shelf_energy(CS, G, US, mass, day, time_step) tmp1(:,:)=0.0 mass_scale_factor = US%L_to_m**2 * US%RZ_to_kg_m2 do j=js,je ; do i=is,ie - tmp1(i,j) = mass_scale_factor * mass(i,j) * G%areaT(i,j) + tmp1(i,j) = mass_scale_factor * (mass(i,j) * G%areaT(i,j)) enddo; enddo mass_tot = reproducing_sum(tmp1, isr, ier, jsr, jer) @@ -1034,7 +1098,7 @@ subroutine ice_shelf_advect(CS, ISS, G, time_step, Time) ! The flux overflows are included here. That is because they will be used to advect 3D scalars ! into partial cells - real, dimension(SZDI_(G),SZDJ_(G)) :: h_after_uflux, h_after_vflux ! Ice thicknesses [Z ~> m]. + real, dimension(SZDI_(G),SZDJ_(G)) :: h_after_flux1, h_after_flux2 ! Ice thicknesses [Z ~> m]. real, dimension(SZDIB_(G),SZDJ_(G)) :: uh_ice ! The accumulated zonal ice volume flux [Z L2 ~> m3] real, dimension(SZDI_(G),SZDJB_(G)) :: vh_ice ! The accumulated meridional ice volume flux [Z L2 ~> m3] type(loop_bounds_type) :: LB @@ -1046,37 +1110,39 @@ subroutine ice_shelf_advect(CS, ISS, G, time_step, Time) uh_ice(:,:) = 0.0 vh_ice(:,:) = 0.0 - h_after_uflux(:,:) = 0.0 - h_after_vflux(:,:) = 0.0 + h_after_flux1(:,:) = 0.0 + h_after_flux2(:,:) = 0.0 ! call MOM_mesg("MOM_ice_shelf.F90: ice_shelf_advect called") - do j=jsd,jed ; do i=isd,ied ; if (CS%thickness_bdry_val(i,j) /= 0.0) then - ISS%h_shelf(i,j) = CS%thickness_bdry_val(i,j) + do j=jsd,jed ; do i=isd,ied ; if (CS%h_bdry_val(i,j) /= 0.0) then + ISS%h_shelf(i,j) = CS%h_bdry_val(i,j) endif ; enddo ; enddo stencil = 2 - LB%ish = G%isc ; LB%ieh = G%iec ; LB%jsh = G%jsc-stencil ; LB%jeh = G%jec+stencil - if (LB%jsh < jsd) call MOM_error(FATAL, & - "ice_shelf_advect: Halo is too small for the ice thickness advection stencil.") - - call ice_shelf_advect_thickness_x(CS, G, LB, time_step, ISS%hmask, ISS%h_shelf, h_after_uflux, uh_ice) - -! call enable_averages(time_step, Time, CS%diag) - call pass_var(h_after_uflux, G%domain) -! if (CS%id_h_after_uflux > 0) call post_data(CS%id_h_after_uflux, h_after_uflux, CS%diag) -! call disable_averaging(CS%diag) - - LB%ish = G%isc ; LB%ieh = G%iec ; LB%jsh = G%jsc ; LB%jeh = G%jec - call ice_shelf_advect_thickness_y(CS, G, LB, time_step, ISS%hmask, h_after_uflux, h_after_vflux, vh_ice) - -! call enable_averages(time_step, Time, CS%diag) - call pass_var(h_after_vflux, G%domain) -! if (CS%id_h_after_vflux > 0) call post_data(CS%id_h_after_vflux, h_after_vflux, CS%diag) -! call disable_averaging(CS%diag) + if (modulo(CS%first_direction_IS,2)==0) then + !x first + LB%ish = G%isc ; LB%ieh = G%iec ; LB%jsh = G%jsc-stencil ; LB%jeh = G%jec+stencil + if (LB%jsh < jsd) call MOM_error(FATAL, & + "ice_shelf_advect: Halo is too small for the ice thickness advection stencil.") + call ice_shelf_advect_thickness_x(CS, G, LB, time_step, ISS%hmask, ISS%h_shelf, h_after_flux1, uh_ice) + call pass_var(h_after_flux1, G%domain) + LB%ish = G%isc ; LB%ieh = G%iec ; LB%jsh = G%jsc ; LB%jeh = G%jec + call ice_shelf_advect_thickness_y(CS, G, LB, time_step, ISS%hmask, h_after_flux1, h_after_flux2, vh_ice) + else + ! y first + LB%ish = G%isc-stencil ; LB%ieh = G%iec+stencil ; LB%jsh = G%jsc ; LB%jeh = G%jec + if (LB%ish < isd) call MOM_error(FATAL, & + "ice_shelf_advect: Halo is too small for the ice thickness advection stencil.") + call ice_shelf_advect_thickness_y(CS, G, LB, time_step, ISS%hmask, ISS%h_shelf, h_after_flux1, vh_ice) + call pass_var(h_after_flux1, G%domain) + LB%ish = G%isc ; LB%ieh = G%iec ; LB%jsh = G%jsc ; LB%jeh = G%jec + call ice_shelf_advect_thickness_x(CS, G, LB, time_step, ISS%hmask, h_after_flux1, h_after_flux2, uh_ice) + endif + call pass_var(h_after_flux2, G%domain) do j=jsd,jed do i=isd,ied - if (ISS%hmask(i,j) == 1) ISS%h_shelf(i,j) = h_after_vflux(i,j) + if (ISS%hmask(i,j) == 1) ISS%h_shelf(i,j) = h_after_flux2(i,j) enddo enddo @@ -1092,7 +1158,7 @@ subroutine ice_shelf_advect(CS, ISS, G, time_step, Time) endif do j=jsc,jec; do i=isc,iec - ISS%mass_shelf(i,j) = ISS%h_shelf(i,j) * ISS%area_shelf_h(i,j) * G%IareaT(i,j) * CS%density_ice + ISS%mass_shelf(i,j) = (ISS%h_shelf(i,j) * CS%density_ice) * (ISS%area_shelf_h(i,j) * G%IareaT(i,j)) enddo; enddo call pass_var(ISS%mass_shelf, G%domain, complete=.false.) @@ -1100,12 +1166,6 @@ subroutine ice_shelf_advect(CS, ISS, G, time_step, Time) call pass_var(ISS%area_shelf_h, G%domain, complete=.false.) call pass_var(ISS%hmask, G%domain, complete=.true.) - !call enable_averages(time_step, Time, CS%diag) - !if (CS%id_h_after_adv > 0) call post_data(CS%id_h_after_adv, ISS%h_shelf, CS%diag) - !call disable_averaging(CS%diag) - - !call change_thickness_using_melt(ISS, G, time_step, fluxes, CS%density_ice) - call update_velocity_masks(CS, G, ISS%hmask, CS%umask, CS%vmask, CS%u_face_mask, CS%v_face_mask) end subroutine ice_shelf_advect @@ -1134,40 +1194,30 @@ subroutine ice_shelf_solve_outer(CS, ISS, G, US, u_shlf, v_shlf, taudx, taudy, i real, dimension(SZDIB_(G),SZDJB_(G)) :: Au, Av ! The retarding lateral stress contributions [R L3 Z T-2 ~> kg m s-2] real, dimension(SZDIB_(G),SZDJB_(G)) :: u_last, v_last ! Previous velocities [L T-1 ~> m s-1] real, dimension(SZDIB_(G),SZDJB_(G)) :: H_node ! Ice shelf thickness at corners [Z ~> m]. - real, dimension(SZDI_(G),SZDJ_(G)) :: float_cond ! If GL_regularize=true, an array indicating where the ice - ! shelf is floating: 0 if floating, 1 if not + real, dimension(SZDI_(G),SZDJ_(G)) :: float_cond ! If GL_regularize=true, indicates cells containing + ! the grounding line (float_cond=1) or not (float_cond=0) real, dimension(SZDIB_(G),SZDJB_(G)) :: Normvec ! Used for convergence character(len=160) :: mesg ! The text of an error message integer :: conv_flag, i, j, k,l, iter - integer :: isdq, iedq, jsdq, jedq, isd, ied, jsd, jed, nodefloat, nsub + integer :: isdq, iedq, jsdq, jedq, isd, ied, jsd, jed, nodefloat real :: err_max, err_tempu, err_tempv, err_init, max_vel, tempu, tempv, Norm, PrevNorm real :: rhoi_rhow ! The density of ice divided by a typical water density [nondim] - real, pointer, dimension(:,:,:,:) :: Phi => NULL() ! The gradients of bilinear basis elements at Gaussian - ! quadrature points surrounding the cell vertices [L-1 ~> m-1]. - real, pointer, dimension(:,:,:,:,:,:) :: Phisub => NULL() ! Quadrature structure weights at subgridscale - ! locations for finite element calculations [nondim] integer :: Is_sum, Js_sum, Ie_sum, Je_sum ! Loop bounds for global sums or arrays starting at 1. - ! for GL interpolation - nsub = CS%n_sub_regularize - isdq = G%isdB ; iedq = G%iedB ; jsdq = G%jsdB ; jedq = G%jedB isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed rhoi_rhow = CS%density_ice / CS%density_ocean_avg taudx(:,:) = 0.0 ; taudy(:,:) = 0.0 - !u_bdry_cont(:,:) = 0.0 ; v_bdry_cont(:,:) = 0.0 Au(:,:) = 0.0 ; Av(:,:) = 0.0 ! need to make these conditional on GL interpolation - float_cond(:,:) = 0.0 ; H_node(:,:) = 0.0 + CS%float_cond(:,:) = 0.0 ; H_node(:,:) = 0.0 !CS%ground_frac(:,:) = 0.0 - allocate(Phisub(nsub,nsub,2,2,2,2), source=0.0) if (.not. CS%GL_couple) then do j=G%jsc,G%jec ; do i=G%isc,G%iec if (rhoi_rhow * ISS%h_shelf(i,j) - CS%bed_elev(i,j) > 0) then - if (CS%GL_regularize) float_cond(i,j) = 1.0 CS%ground_frac(i,j) = 1.0 CS%OD_av(i,j) =0.0 endif @@ -1197,34 +1247,24 @@ subroutine ice_shelf_solve_outer(CS, ISS, G, US, u_shlf, v_shlf, taudx, taudy, i endif enddo ; enddo if ((nodefloat > 0) .and. (nodefloat < 4)) then - float_cond(i,j) = 1.0 + CS%float_cond(i,j) = 1.0 CS%ground_frac(i,j) = 1.0 endif enddo ; enddo - call pass_var(float_cond, G%Domain, complete=.false.) - - call bilinear_shape_functions_subgrid(Phisub, nsub) + call pass_var(CS%float_cond, G%Domain, complete=.false.) endif - ! must prepare Phi - allocate(Phi(1:8,1:4,isd:ied,jsd:jed), source=0.0) - - do j=jsd,jed ; do i=isd,ied - call bilinear_shape_fn_grid(G, i, j, Phi(:,:,i,j)) - enddo ; enddo - - call calc_shelf_visc(CS, ISS, G, US, u_shlf, v_shlf) - call pass_var(CS%ice_visc, G%domain, complete=.false.) call calc_shelf_taub(CS, ISS, G, US, u_shlf, v_shlf) call pass_var(CS%basal_traction, G%domain, complete=.true.) - if (trim(CS%ice_viscosity_compute) == "MODEL_QUADRATURE") call pass_var(CS%Ee,G%domain) + call calc_shelf_visc(CS, ISS, G, US, u_shlf, v_shlf) + call pass_var(CS%ice_visc, G%domain) ! This makes sure basal stress is only applied when it is supposed to be if (CS%GL_regularize) then do j=G%jsd,G%jed ; do i=G%isd,G%ied - CS%basal_traction(i,j) = CS%basal_traction(i,j) * float_cond(i,j) + if (CS%ground_frac(i,j)/=1.0) CS%basal_traction(i,j) = 0.0 enddo ; enddo else do j=G%jsd,G%jed ; do i=G%isd,G%ied @@ -1233,25 +1273,21 @@ subroutine ice_shelf_solve_outer(CS, ISS, G, US, u_shlf, v_shlf, taudx, taudy, i endif if (CS%nonlin_solve_err_mode == 1) then - ! call apply_boundary_values(CS, ISS, G, US, time, Phisub, H_node, CS%ice_visc, & - ! CS%basal_traction, float_cond, rhoi_rhow, u_bdry_cont, v_bdry_cont) Au(:,:) = 0.0 ; Av(:,:) = 0.0 - call CG_action(CS, Au, Av, u_shlf, v_shlf, Phi, Phisub, CS%umask, CS%vmask, ISS%hmask, H_node, & - CS%ice_visc, float_cond, CS%bed_elev, CS%basal_traction, & + call CG_action(CS, Au, Av, u_shlf, v_shlf, CS%Phi, CS%Phisub, CS%umask, CS%vmask, ISS%hmask, H_node, & + CS%ice_visc, CS%float_cond, CS%bed_elev, CS%basal_traction, & G, US, G%isc-1, G%iec+1, G%jsc-1, G%jec+1, rhoi_rhow) call pass_vector(Au, Av, G%domain, TO_ALL, BGRID_NE) err_init = 0 ; err_tempu = 0 ; err_tempv = 0 do J=G%IscB,G%JecB ; do I=G%IscB,G%IecB if (CS%umask(I,J) == 1) then - !err_tempu = ABS(Au(I,J) + u_bdry_cont(I,J) - taudx(I,J)) err_tempu = ABS(Au(I,J) - taudx(I,J)) if (err_tempu >= err_init) err_init = err_tempu endif if (CS%vmask(I,J) == 1) then - !err_tempv = ABS(Av(I,J) + v_bdry_cont(I,J) - taudy(I,J)) err_tempv = ABS(Av(I,J) - taudy(I,J)) if (err_tempv >= err_init) err_init = err_tempv endif @@ -1271,8 +1307,8 @@ subroutine ice_shelf_solve_outer(CS, ISS, G, US, u_shlf, v_shlf, taudx, taudy, i ! Include the edge if tile is at the southern bdry; Should add a test to avoid this if reentrant. if (G%jsc+G%jdg_offset==G%jsg) Js_sum = G%JscB + (1-G%JsdB) do J=G%jscB,G%jecB ; do I=G%iscB,G%iecB - if (CS%umask(I,J) == 1) Normvec(I,J) = Normvec(I,J) + u_shlf(I,J)*u_shlf(I,J) - if (CS%vmask(I,J) == 1) Normvec(I,J) = Normvec(I,J) + v_shlf(I,J)*v_shlf(I,J) + if (CS%umask(I,J) == 1) Normvec(I,J) = Normvec(I,J) + (u_shlf(I,J)**2 * US%L_T_to_m_s**2) + if (CS%vmask(I,J) == 1) Normvec(I,J) = Normvec(I,J) + (v_shlf(I,J)**2 * US%L_T_to_m_s**2) enddo; enddo Norm = reproducing_sum( Normvec, Is_sum, Ie_sum, Js_sum, Je_sum ) Norm = sqrt(Norm) @@ -1284,8 +1320,8 @@ subroutine ice_shelf_solve_outer(CS, ISS, G, US, u_shlf, v_shlf, taudx, taudy, i do iter=1,50 - call ice_shelf_solve_inner(CS, ISS, G, US, u_shlf, v_shlf, taudx, taudy, H_node, float_cond, & - ISS%hmask, conv_flag, iters, time, Phi, Phisub) + call ice_shelf_solve_inner(CS, ISS, G, US, u_shlf, v_shlf, taudx, taudy, H_node, CS%float_cond, & + ISS%hmask, conv_flag, iters, time, CS%Phi, CS%Phisub) if (CS%debug) then call qchksum(u_shlf, "u shelf", G%HI, haloshift=2, scale=US%L_T_to_m_s) @@ -1295,16 +1331,15 @@ subroutine ice_shelf_solve_outer(CS, ISS, G, US, u_shlf, v_shlf, taudx, taudy, i write(mesg,*) "ice_shelf_solve_outer: linear solve done in ",iters," iterations" call MOM_mesg(mesg, 5) - call calc_shelf_visc(CS, ISS, G, US, u_shlf, v_shlf) - call pass_var(CS%ice_visc, G%domain, complete=.false.) call calc_shelf_taub(CS, ISS, G, US, u_shlf, v_shlf) call pass_var(CS%basal_traction, G%domain, complete=.true.) - if (trim(CS%ice_viscosity_compute) == "MODEL_QUADRATURE") call pass_var(CS%Ee,G%domain) + call calc_shelf_visc(CS, ISS, G, US, u_shlf, v_shlf) + call pass_var(CS%ice_visc, G%domain) ! makes sure basal stress is only applied when it is supposed to be if (CS%GL_regularize) then do j=G%jsd,G%jed ; do i=G%isd,G%ied - CS%basal_traction(i,j) = CS%basal_traction(i,j) * float_cond(i,j) + if (CS%ground_frac(i,j)/=1.0) CS%basal_traction(i,j) = 0.0 enddo ; enddo else do j=G%jsd,G%jed ; do i=G%isd,G%ied @@ -1313,15 +1348,11 @@ subroutine ice_shelf_solve_outer(CS, ISS, G, US, u_shlf, v_shlf, taudx, taudy, i endif if (CS%nonlin_solve_err_mode == 1) then - !u_bdry_cont(:,:) = 0 ; v_bdry_cont(:,:) = 0 - - ! call apply_boundary_values(CS, ISS, G, US, time, Phisub, H_node, CS%ice_visc, & - ! CS%basal_traction, float_cond, rhoi_rhow, u_bdry_cont, v_bdry_cont) Au(:,:) = 0 ; Av(:,:) = 0 - call CG_action(CS, Au, Av, u_shlf, v_shlf, Phi, Phisub, CS%umask, CS%vmask, ISS%hmask, H_node, & - CS%ice_visc, float_cond, CS%bed_elev, CS%basal_traction, & + call CG_action(CS, Au, Av, u_shlf, v_shlf, CS%Phi, CS%Phisub, CS%umask, CS%vmask, ISS%hmask, H_node, & + CS%ice_visc, CS%float_cond, CS%bed_elev, CS%basal_traction, & G, US, G%isc-1, G%iec+1, G%jsc-1, G%jec+1, rhoi_rhow) call pass_vector(Au, Av, G%domain, TO_ALL, BGRID_NE) @@ -1330,12 +1361,10 @@ subroutine ice_shelf_solve_outer(CS, ISS, G, US, u_shlf, v_shlf, taudx, taudy, i do J=G%jscB,G%jecB ; do I=G%jscB,G%iecB if (CS%umask(I,J) == 1) then - !err_tempu = ABS(Au(I,J) + u_bdry_cont(I,J) - taudx(I,J)) err_tempu = ABS(Au(I,J) - taudx(I,J)) if (err_tempu >= err_max) err_max = err_tempu endif if (CS%vmask(I,J) == 1) then - !err_tempv = ABS(Av(I,J) + v_bdry_cont(I,J) - taudy(I,J)) err_tempv = ABS(Av(I,J) - taudy(I,J)) if (err_tempv >= err_max) err_max = err_tempv endif @@ -1372,8 +1401,8 @@ subroutine ice_shelf_solve_outer(CS, ISS, G, US, u_shlf, v_shlf, taudx, taudy, i elseif (CS%nonlin_solve_err_mode == 3) then PrevNorm=Norm; Norm=0.0; Normvec=0.0 do J=G%jscB,G%jecB ; do I=G%iscB,G%iecB - if (CS%umask(I,J) == 1) Normvec(I,J) = Normvec(I,J) + u_shlf(I,J)*u_shlf(I,J) - if (CS%vmask(I,J) == 1) Normvec(I,J) = Normvec(I,J) + v_shlf(I,J)*v_shlf(I,J) + if (CS%umask(I,J) == 1) Normvec(I,J) = Normvec(I,J) + (u_shlf(I,J)**2 * US%L_T_to_m_s**2) + if (CS%vmask(I,J) == 1) Normvec(I,J) = Normvec(I,J) + (v_shlf(I,J)**2 * US%L_T_to_m_s**2) enddo; enddo Norm = reproducing_sum( Normvec, Is_sum, Ie_sum, Js_sum, Je_sum ) Norm = sqrt(Norm) @@ -1393,8 +1422,6 @@ subroutine ice_shelf_solve_outer(CS, ISS, G, US, u_shlf, v_shlf, taudx, taudy, i call MOM_mesg(mesg) write(mesg,*) "ice_shelf_solve_outer: exiting nonlinear solve after ",iter," iterations" call MOM_mesg(mesg) - deallocate(Phi) - deallocate(Phisub) end subroutine ice_shelf_solve_outer @@ -1417,8 +1444,8 @@ subroutine ice_shelf_solve_inner(CS, ISS, G, US, u_shlf, v_shlf, taudx, taudy, H intent(in) :: H_node !< The ice shelf thickness at nodal (corner) !! points [Z ~> m]. real, dimension(SZDI_(G),SZDJ_(G)), & - intent(in) :: float_cond !< If GL_regularize=true, an array indicating where the ice - !! shelf is floating: 0 if floating, 1 if not + intent(in) :: float_cond !< If GL_regularize=true, indicates cells containing + !! the grounding line (float_cond=1) or not (float_cond=0) real, dimension(SZDI_(G),SZDJ_(G)), & intent(in) :: hmask !< A mask indicating which tracer points are !! partly or fully covered by an ice-shelf @@ -1473,7 +1500,7 @@ subroutine ice_shelf_solve_inner(CS, ISS, G, US, u_shlf, v_shlf, taudx, taudy, H Zu(:,:) = 0 ; Zv(:,:) = 0 ; DIAGu(:,:) = 0 ; DIAGv(:,:) = 0 Ru(:,:) = 0 ; Rv(:,:) = 0 ; Au(:,:) = 0 ; Av(:,:) = 0 ; RHSu(:,:) = 0 ; RHSv(:,:) = 0 - Du(:,:) = 0 ; Dv(:,:) = 0 !; ubd(:,:) = 0 ; vbd(:,:) = 0 + Du(:,:) = 0 ; Dv(:,:) = 0 dot_p1 = 0 ! Determine the loop limits for sums, bearing in mind that the arrays will be starting at 1. @@ -1487,16 +1514,13 @@ subroutine ice_shelf_solve_inner(CS, ISS, G, US, u_shlf, v_shlf, taudx, taudy, H ! Include the edge if tile is at the southern bdry; Should add a test to avoid this if reentrant. if (G%jsc+G%jdg_offset==G%jsg) Js_sum = G%JscB + (1-G%JsdB) - !call apply_boundary_values(CS, ISS, G, US, time, Phisub, H_node, CS%ice_visc, & - ! CS%basal_traction, float_cond, rhoi_rhow, ubd, vbd) - - RHSu(:,:) = taudx(:,:) !- ubd(:,:) - RHSv(:,:) = taudy(:,:) !- vbd(:,:) + RHSu(:,:) = taudx(:,:) + RHSv(:,:) = taudy(:,:) call pass_vector(RHSu, RHSv, G%domain, TO_ALL, BGRID_NE, complete=.false.) call matrix_diagonal(CS, G, US, float_cond, H_node, CS%ice_visc, CS%basal_traction, & - hmask, rhoi_rhow, Phisub, DIAGu, DIAGv) + hmask, rhoi_rhow, Phi, Phisub, DIAGu, DIAGv) call pass_vector(DIAGu, DIAGv, G%domain, TO_ALL, BGRID_NE, complete=.false.) @@ -1508,9 +1532,8 @@ subroutine ice_shelf_solve_inner(CS, ISS, G, US, u_shlf, v_shlf, taudx, taudy, H Ru(:,:) = (RHSu(:,:) - Au(:,:)) Rv(:,:) = (RHSv(:,:) - Av(:,:)) - - resid_scale = US%L_to_m**2*US%s_to_T*US%RZ_to_kg_m2*US%L_T_to_m_s**2 - resid2_scale = (US%RZ_to_kg_m2*US%L_to_m*US%L_T_to_m_s**2)**2 + resid_scale = (US%L_to_m**2*US%s_to_T)*(US%RZ_to_kg_m2*US%L_T_to_m_s**2) + resid2_scale = ((US%RZ_to_kg_m2*US%L_to_m)*US%L_T_to_m_s**2)**2 sum_vec(:,:) = 0.0 do j=jscq,jecq ; do i=iscq,iecq @@ -1518,7 +1541,7 @@ subroutine ice_shelf_solve_inner(CS, ISS, G, US, u_shlf, v_shlf, taudx, taudy, H if (CS%vmask(I,J) == 1) sum_vec(I,J) = sum_vec(I,J) + resid2_scale*Rv(I,J)**2 enddo ; enddo - dot_p1 = reproducing_sum( sum_vec, Js_sum, Ie_sum, Js_sum, Je_sum ) + dot_p1 = reproducing_sum( sum_vec, Is_sum, Ie_sum, Js_sum, Je_sum ) resid0 = sqrt(dot_p1) @@ -1654,7 +1677,8 @@ subroutine ice_shelf_solve_inner(CS, ISS, G, US, u_shlf, v_shlf, taudx, taudy, H dot_p1 = reproducing_sum( sum_vec, Is_sum, Ie_sum, Js_sum, Je_sum ) dot_p1 = sqrt(dot_p1) - if (dot_p1 <= CS%cg_tolerance * resid0) then + + if (dot_p1 <= (CS%cg_tolerance * resid0)) then iters = iter conv_flag = 1 exit @@ -1732,37 +1756,39 @@ subroutine ice_shelf_advect_thickness_x(CS, G, LB, time_step, hmask, h0, h_after do j=jsh,jeh ; do I=ish-1,ieh if (CS%u_face_mask(I,j) == 4.) then ! The flux itself is a specified boundary condition. - uh_ice(I,j) = time_step * G%dyCu(I,j) * CS%u_flux_bdry_val(I,j) + uh_ice(I,j) = (time_step * G%dyCu(I,j)) * CS%u_flux_bdry_val(I,j) elseif ((hmask(i,j) == 1 .or. hmask(i,j) == 3) .or. (hmask(i+1,j) == 1 .or. hmask(i+1,j) == 3)) then u_face = 0.5 * (CS%u_shelf(I,J-1) + CS%u_shelf(I,J)) h_face = 0.0 ! This will apply when the source cell is iceless or not fully ice covered. if (u_face > 0) then if (hmask(i,j) == 3) then ! This is a open boundary inflow from the west - h_face = CS%thickness_bdry_val(i,j) + h_face = CS%h_bdry_val(i,j) elseif (hmask(i,j) == 1) then ! There can be eastward flow through this face. - if ((hmask(i-1,j) == 1) .and. (hmask(i+1,j) == 1)) then + if ((hmask(i-1,j) == 1 .or. hmask(i-1,j) == 3) .and. & + (hmask(i+1,j) == 1 .or. hmask(i+1,j) == 3)) then slope_lim = slope_limiter(h0(i,j)-h0(i-1,j), h0(i+1,j)-h0(i,j)) ! This is a 2nd-order centered scheme with a slope limiter. We could try PPM here. - h_face = h0(i,j) - slope_lim * 0.5 * (h0(i,j)-h0(i+1,j)) + h_face = h0(i,j) - slope_lim * (0.5 * (h0(i,j)-h0(i+1,j))) else h_face = h0(i,j) endif endif else if (hmask(i+1,j) == 3) then ! This is a open boundary inflow from the east - h_face = CS%thickness_bdry_val(i+1,j) + h_face = CS%h_bdry_val(i+1,j) elseif (hmask(i+1,j) == 1) then - if ((hmask(i,j) == 1) .and. (hmask(i+2,j) == 1)) then + if ((hmask(i,j) == 1 .or. hmask(i,j) == 3) .and. & + (hmask(i+2,j) == 1 .or. hmask(i+2,j) == 3)) then slope_lim = slope_limiter(h0(i+1,j)-h0(i,j), h0(i+2,j)-h0(i+1,j)) - h_face = h0(i+1,j) - slope_lim * 0.5 * (h0(i+1,j)-h0(i,j)) + h_face = h0(i+1,j) - slope_lim * (0.5 * (h0(i+2,j)-h0(i+1,j))) else h_face = h0(i+1,j) endif endif endif - uh_ice(I,j) = time_step * G%dyCu(I,j) * u_face * h_face + uh_ice(I,j) = (time_step * G%dyCu(I,j)) * (u_face * h_face) else uh_ice(I,j) = 0.0 endif @@ -1811,37 +1837,39 @@ subroutine ice_shelf_advect_thickness_y(CS, G, LB, time_step, hmask, h0, h_after do J=jsh-1,jeh ; do i=ish,ieh if (CS%v_face_mask(i,J) == 4.) then ! The flux itself is a specified boundary condition. - vh_ice(i,J) = time_step * G%dxCv(i,J) * CS%v_flux_bdry_val(i,J) + vh_ice(i,J) = (time_step * G%dxCv(i,J)) * CS%v_flux_bdry_val(i,J) elseif ((hmask(i,j) == 1 .or. hmask(i,j) == 3) .or. (hmask(i,j+1) == 1 .or. hmask(i,j+1) == 3)) then v_face = 0.5 * (CS%v_shelf(I-1,J) + CS%v_shelf(I,J)) h_face = 0.0 ! This will apply when the source cell is iceless or not fully ice covered. if (v_face > 0) then if (hmask(i,j) == 3) then ! This is a open boundary inflow from the south - h_face = CS%thickness_bdry_val(i,j) - elseif (hmask(i,j) == 1) then ! There can be northtward flow through this face. - if ((hmask(i,j-1) == 1) .and. (hmask(i,j+1) == 1)) then + h_face = CS%h_bdry_val(i,j) + elseif (hmask(i,j) == 1) then ! There can be northward flow through this face. + if ((hmask(i,j-1) == 1 .or. hmask(i,j-1) == 3) .and. & + (hmask(i,j+1) == 1 .or. hmask(i,j+1) == 3)) then slope_lim = slope_limiter(h0(i,j)-h0(i,j-1), h0(i,j+1)-h0(i,j)) ! This is a 2nd-order centered scheme with a slope limiter. We could try PPM here. - h_face = h0(i,j) - slope_lim * 0.5 * (h0(i,j)-h0(i,j+1)) + h_face = h0(i,j) - slope_lim * (0.5 * (h0(i,j)-h0(i,j+1))) else h_face = h0(i,j) endif endif else if (hmask(i,j+1) == 3) then ! This is a open boundary inflow from the north - h_face = CS%thickness_bdry_val(i,j+1) + h_face = CS%h_bdry_val(i,j+1) elseif (hmask(i,j+1) == 1) then - if ((hmask(i,j) == 1) .and. (hmask(i,j+2) == 1)) then + if ((hmask(i,j) == 1 .or. hmask(i,j) == 3) .and. & + (hmask(i,j+2) == 1 .or. hmask(i,j+2) == 3)) then slope_lim = slope_limiter(h0(i,j+1)-h0(i,j), h0(i,j+2)-h0(i,j+1)) - h_face = h0(i,j+1) - slope_lim * 0.5 * (h0(i,j+1)-h0(i,j)) + h_face = h0(i,j+1) - slope_lim * (0.5 * (h0(i,j+2)-h0(i,j+1))) else h_face = h0(i,j+1) endif endif endif - vh_ice(i,J) = time_step * G%dxCv(i,J) * v_face * h_face + vh_ice(i,J) = (time_step * G%dxCv(i,J)) * (v_face * h_face) else vh_ice(i,J) = 0.0 endif @@ -1902,7 +1930,11 @@ subroutine shelf_advance_front(CS, ISS, G, hmask, uh_ice, vh_ice) integer :: iter_flag real :: h_reference ! A reference thicknesss based on neighboring cells [Z ~> m] + real :: h_reference_ew !contribution to reference thickness from east + west cells [Z ~> m] + real :: h_reference_ns !contribution to reference thickness from north + south cells [Z ~> m] real :: tot_flux ! The total ice mass flux [Z L2 ~> m3] + real :: tot_flux_ew ! The contribution to total ice mass flux from east + west cells [Z L2 ~> m3] + real :: tot_flux_ns ! The contribution to total ice mass flux from north + south cells [Z L2 ~> m3] real :: partial_vol ! The volume covered by ice shelf [Z L2 ~> m3] real :: dxdyh ! Cell area [L2 ~> m2] character(len=160) :: mesg ! The text of an error message @@ -1953,15 +1985,17 @@ subroutine shelf_advance_front(CS, ISS, G, hmask, uh_ice, vh_ice) ((i+i_off) >= 1)) then ! first get reference thickness by averaging over cells that are fluxing into this cell n_flux = 0 - h_reference = 0.0 - tot_flux = 0.0 + h_reference_ew = 0.0 + h_reference_ns = 0.0 + tot_flux_ew = 0.0 + tot_flux_ns = 0.0 do k=1,2 if (flux_enter(i,j,k) > 0) then n_flux = n_flux + 1 - h_reference = h_reference + flux_enter(i,j,k) * ISS%h_shelf(i+2*k-3,j) + h_reference_ew = h_reference_ew + flux_enter(i,j,k) * ISS%h_shelf(i+2*k-3,j) !h_reference = h_reference + ISS%h_shelf(i+2*k-3,j) - tot_flux = tot_flux + flux_enter(i,j,k) + tot_flux_ew = tot_flux_ew + flux_enter(i,j,k) flux_enter(i,j,k) = 0.0 endif enddo @@ -1969,13 +2003,16 @@ subroutine shelf_advance_front(CS, ISS, G, hmask, uh_ice, vh_ice) do k=1,2 if (flux_enter(i,j,k+2) > 0) then n_flux = n_flux + 1 - h_reference = h_reference + flux_enter(i,j,k+2) * ISS%h_shelf(i,j+2*k-3) + h_reference_ns = h_reference_ns + flux_enter(i,j,k+2) * ISS%h_shelf(i,j+2*k-3) !h_reference = h_reference + ISS%h_shelf(i,j+2*k-3) - tot_flux = tot_flux + flux_enter(i,j,k+2) + tot_flux_ns = tot_flux_ns + flux_enter(i,j,k+2) flux_enter(i,j,k+2) = 0.0 endif enddo + h_reference = h_reference_ew + h_reference_ns + tot_flux = tot_flux_ew + tot_flux_ns + if (n_flux > 0) then dxdyh = G%areaT(i,j) h_reference = h_reference / tot_flux @@ -1983,7 +2020,7 @@ subroutine shelf_advance_front(CS, ISS, G, hmask, uh_ice, vh_ice) partial_vol = ISS%h_shelf(i,j) * ISS%area_shelf_h(i,j) + tot_flux if ((partial_vol / G%areaT(i,j)) == h_reference) then ! cell is exactly covered, no overflow - if (ISS%hmask(i,j).ne.3) ISS%hmask(i,j) = 1 + if (ISS%hmask(i,j)/=3) ISS%hmask(i,j) = 1 ISS%h_shelf(i,j) = h_reference ISS%area_shelf_h(i,j) = G%areaT(i,j) elseif ((partial_vol / G%areaT(i,j)) < h_reference) then @@ -1993,7 +2030,7 @@ subroutine shelf_advance_front(CS, ISS, G, hmask, uh_ice, vh_ice) ISS%h_shelf(i,j) = h_reference else - if (ISS%hmask(i,j).ne.3) ISS%hmask(i,j) = 1 + if (ISS%hmask(i,j)/=3) ISS%hmask(i,j) = 1 ISS%area_shelf_h(i,j) = G%areaT(i,j) !h_temp(i,j) = h_reference partial_vol = partial_vol - h_reference * G%areaT(i,j) @@ -2131,7 +2168,7 @@ subroutine calc_shelf_driving_stress(CS, ISS, G, US, taudx, taudy, OD) ! (it is assumed that base_ice = bed + OD) real, dimension(SIZE(OD,1),SIZE(OD,2)) :: S ! surface elevation [Z ~> m]. - + real, dimension(SZDI_(G),SZDJ_(G)) :: sx_e, sy_e !element contributions to driving stress real :: rho, rhow, rhoi_rhow ! Ice and ocean densities [R ~> kg m-3] real :: sx, sy ! Ice shelf top slopes [Z L-1 ~> nondim] real :: neumann_val ! [R Z L2 T-2 ~> kg s-2] @@ -2143,15 +2180,14 @@ subroutine calc_shelf_driving_stress(CS, ISS, G, US, taudx, taudy, OD) integer :: i_off, j_off isc = G%isc ; jsc = G%jsc ; iec = G%iec ; jec = G%jec - iscq = G%iscB ; iecq = G%iecB ; jscq = G%jscB ; jecq = G%jecB - isd = G%isd ; jsd = G%jsd +! iscq = G%iscB ; iecq = G%iecB ; jscq = G%jscB ; jecq = G%jecB isd = G%isd ; jsd = G%jsd ; ied = G%ied ; jed = G%jed - iegq = G%iegB ; jegq = G%jegB +! iegq = G%iegB ; jegq = G%jegB ! gisc = G%domain%nihalo+1 ; gjsc = G%domain%njhalo+1 gisc = 1 ; gjsc = 1 ! giec = G%domain%niglobal+G%domain%nihalo ; gjec = G%domain%njglobal+G%domain%njhalo giec = G%domain%niglobal ; gjec = G%domain%njglobal - is = iscq - 1; js = jscq - 1 +! is = iscq - 1; js = jscq - 1 i_off = G%idg_offset ; j_off = G%jdg_offset @@ -2182,6 +2218,8 @@ subroutine calc_shelf_driving_stress(CS, ISS, G, US, taudx, taudy, OD) call pass_var(S, G%domain) + sx_e(:,:)=0.0; sy_e(:,:)=0.0 + do j=jsc-1,jec+1 do i=isc-1,iec+1 cnt = 0 @@ -2210,14 +2248,14 @@ subroutine calc_shelf_driving_stress(CS, ISS, G, US, taudx, taudy, OD) else ! interior if (ISS%hmask(i+1,j) == 1 .or. ISS%hmask(i+1,j) == 3) then cnt = cnt+1 - Dx =dxh+ G%dxT(i+1,j) + Dx = dxh + G%dxT(i+1,j) sx = S(i+1,j) else sx = S(i,j) endif if (ISS%hmask(i-1,j) == 1 .or. ISS%hmask(i-1,j) == 3) then cnt = cnt+1 - Dx =dxh+ G%dxT(i-1,j) + Dx = dxh + G%dxT(i-1,j) sx = sx - S(i-1,j) else sx = sx - S(i,j) @@ -2225,7 +2263,7 @@ subroutine calc_shelf_driving_stress(CS, ISS, G, US, taudx, taudy, OD) if (cnt == 0) then sx = 0 else - sx = sx / ( Dx) + sx = sx / Dx endif endif @@ -2247,54 +2285,36 @@ subroutine calc_shelf_driving_stress(CS, ISS, G, US, taudx, taudy, OD) else ! interior if (ISS%hmask(i,j+1) == 1 .or. ISS%hmask(i,j+1) == 3) then cnt = cnt+1 - Dy =dyh+ G%dyT(i,j+1) + Dy = dyh + G%dyT(i,j+1) sy = S(i,j+1) else sy = S(i,j) endif if (ISS%hmask(i,j-1) == 1 .or. ISS%hmask(i,j-1) == 3) then cnt = cnt+1 + Dy = dyh + G%dyT(i,j-1) sy = sy - S(i,j-1) - Dy =dyh+ G%dyT(i,j-1) else sy = sy - S(i,j) endif if (cnt == 0) then sy = 0 else - sy = sy / (Dy) + sy = sy / Dy endif endif - ! SW vertex - !if (ISS%hmask(I-1,J-1) == 1) then - taudx(I-1,J-1) = taudx(I-1,J-1) - .25 * rho * grav * ISS%h_shelf(i,j) * sx * G%areaT(i,j) - taudy(I-1,J-1) = taudy(I-1,J-1) - .25 * rho * grav * ISS%h_shelf(i,j) * sy * G%areaT(i,j) - !endif - ! SE vertex - !if (ISS%hmask(I,J-1) == 1) then - taudx(I,J-1) = taudx(I,J-1) - .25 * rho * grav * ISS%h_shelf(i,j) * sx * G%areaT(i,j) - taudy(I,J-1) = taudy(I,J-1) - .25 * rho * grav * ISS%h_shelf(i,j) * sy * G%areaT(i,j) - !endif - ! NW vertex - !if (ISS%hmask(I-1,J) == 1) then - taudx(I-1,J) = taudx(I-1,J) - .25 * rho * grav * ISS%h_shelf(i,j) * sx * G%areaT(i,j) - taudy(I-1,J) = taudy(I-1,J) - .25 * rho * grav * ISS%h_shelf(i,j) * sy * G%areaT(i,j) - !endif - ! NE vertex - !if (ISS%hmask(I,J) == 1) then - taudx(I,J) = taudx(I,J) - .25 * rho * grav * ISS%h_shelf(i,j) * sx * G%areaT(i,j) - taudy(I,J) = taudy(I,J) - .25 * rho * grav * ISS%h_shelf(i,j) * sy * G%areaT(i,j) - !endif + sx_e(i,j) = (-.25 * G%areaT(i,j)) * ((rho * grav) * (ISS%h_shelf(i,j) * sx)) + sy_e(i,j) = (-.25 * G%areaT(i,j)) * ((rho * grav) * (ISS%h_shelf(i,j) * sy)) !Stress (Neumann) boundary conditions if (CS%ground_frac(i,j) == 1) then - neumann_val = (.5 * grav * (rho * ISS%h_shelf(i,j)**2 - rhow * CS%bed_elev(i,j)**2)) + neumann_val = ((.5 * grav) * (rho * ISS%h_shelf(i,j)**2 - rhow * CS%bed_elev(i,j)**2)) else - neumann_val = (.5 * grav * (1-rho/rhow) * rho * ISS%h_shelf(i,j)**2) + neumann_val = (.5 * grav) * ((1-rho/rhow) * (rho * ISS%h_shelf(i,j)**2)) endif if ((CS%u_face_mask_bdry(I-1,j) == 2) .OR. & - ((ISS%hmask(i-1,j) == 0 .OR. ISS%hmask(i-1,j) == 2) .AND. (i+i_off .ne. gisc))) then + ((ISS%hmask(i-1,j) == 0 .OR. ISS%hmask(i-1,j) == 2) .AND. (i+i_off /= gisc))) then ! left face of the cell is at a stress boundary ! the depth-integrated longitudinal stress is equal to the difference of depth-integrated ! pressure on either side of the face @@ -2309,30 +2329,33 @@ subroutine calc_shelf_driving_stress(CS, ISS, G, US, taudx, taudy, OD) endif if ((CS%u_face_mask_bdry(I,j) == 2) .OR. & - ((ISS%hmask(i+1,j) == 0 .OR. ISS%hmask(i+1,j) == 2) .and. (i+i_off .ne. giec))) then + ((ISS%hmask(i+1,j) == 0 .OR. ISS%hmask(i+1,j) == 2) .and. (i+i_off /= giec))) then ! east face of the cell is at a stress boundary taudx(I,J-1) = taudx(I,J-1) + .5 * dyh * neumann_val taudx(I,J) = taudx(I,J) + .5 * dyh * neumann_val endif if ((CS%v_face_mask_bdry(i,J-1) == 2) .OR. & - ((ISS%hmask(i,j-1) == 0 .OR. ISS%hmask(i,j-1) == 2) .and. (j+j_off .ne. gjsc))) then + ((ISS%hmask(i,j-1) == 0 .OR. ISS%hmask(i,j-1) == 2) .and. (j+j_off /= gjsc))) then ! south face of the cell is at a stress boundary taudy(I-1,J-1) = taudy(I-1,J-1) - .5 * dxh * neumann_val taudy(I,J-1) = taudy(I,J-1) - .5 * dxh * neumann_val endif if ((CS%v_face_mask_bdry(i,J) == 2) .OR. & - ((ISS%hmask(i,j+1) == 0 .OR. ISS%hmask(i,j+1) == 2) .and. (j+j_off .ne. gjec))) then + ((ISS%hmask(i,j+1) == 0 .OR. ISS%hmask(i,j+1) == 2) .and. (j+j_off /= gjec))) then ! north face of the cell is at a stress boundary taudy(I-1,J) = taudy(I-1,J) + .5 * dxh * neumann_val taudy(I,J) = taudy(I,J) + .5 * dxh * neumann_val endif - endif enddo enddo + do J=jsc-2,jec+1; do I=isc-2,iec+1 + taudx(I,J) = taudx(I,J) + ((sx_e(i,j)+sx_e(i+1,j+1)) + (sx_e(i+1,j)+sx_e(i,j+1))) + taudy(I,J) = taudy(I,J) + ((sy_e(i,j)+sy_e(i+1,j+1)) + (sy_e(i+1,j)+sy_e(i,j+1))) + enddo; enddo end subroutine calc_shelf_driving_stress ! Not used? Seems to be only set up to work for a specific test case with u_face_mask==3 @@ -2369,7 +2392,7 @@ subroutine init_boundary_values(CS, G, time, hmask, input_flux, input_thick, new do i=isd,ied if (hmask(i,j) == 3) then - CS%thickness_bdry_val(i,j) = input_thick + CS%h_bdry_val(i,j) = input_thick endif if ((hmask(i,j) == 0) .or. (hmask(i,j) == 1) .or. (hmask(i,j) == 2)) then @@ -2436,7 +2459,7 @@ subroutine CG_action(CS, uret, vret, u_shlf, v_shlf, Phi, Phisub, umask, vmask, real, dimension(SZDI_(G),SZDJ_(G)), & intent(in) :: hmask !< A mask indicating which tracer points are !! partly or fully covered by an ice-shelf - real, dimension(SZDI_(G),SZDJ_(G)), & + real, dimension(SZDI_(G),SZDJ_(G),CS%visc_qps), & intent(in) :: ice_visc !< A field related to the ice viscosity from Glen's !! flow law [R L4 Z T-1 ~> kg m2 s-1]. The exact form !! and units depend on the basal law exponent. @@ -2479,88 +2502,124 @@ subroutine CG_action(CS, uret, vret, u_shlf, v_shlf, Phi, Phisub, umask, vmask, real :: ux, uy, vx, vy ! Components of velocity shears or divergence [T-1 ~> s-1] real :: uq, vq ! Interpolated velocities [L T-1 ~> m s-1] - integer :: iq, jq, iphi, jphi, i, j, ilq, jlq, Itgt, Jtgt + integer :: iq, jq, iphi, jphi, i, j, ilq, jlq, Itgt, Jtgt, qp, qpv + logical :: visc_qp4 real, dimension(2) :: xquad real, dimension(2,2) :: Ucell, Vcell, Hcell, Usub, Vsub - real :: Ee + real, dimension(2,2,4) :: uret_qp, vret_qp + real, dimension(SZDIB_(G),SZDJB_(G),4) :: uret_b, vret_b xquad(1) = .5 * (1-sqrt(1./3)) ; xquad(2) = .5 * (1+sqrt(1./3)) - Ee=1.0 + if (CS%visc_qps == 4) then + visc_qp4=.true. + else + visc_qp4=.false. + qpv = 1 + endif + + uret(:,:) = 0.0; vret(:,:)=0.0 + uret_b(:,:,:)=0.0 ; vret_b(:,:,:)=0.0 do j=js,je ; do i=is,ie ; if (hmask(i,j) == 1 .or. hmask(i,j)==3) then + uret_qp(:,:,:)=0.0; vret_qp(:,:,:)=0.0 + do iq=1,2 ; do jq=1,2 - uq = u_shlf(I-1,J-1) * (xquad(3-iq) * xquad(3-jq)) + & - u_shlf(I,J-1) * (xquad(iq) * xquad(3-jq)) + & - u_shlf(I-1,J) * (xquad(3-iq) * xquad(jq)) + & - u_shlf(I,J) * (xquad(iq) * xquad(jq)) - - vq = v_shlf(I-1,J-1) * (xquad(3-iq) * xquad(3-jq)) + & - v_shlf(I,J-1) * (xquad(iq) * xquad(3-jq)) + & - v_shlf(I-1,J) * (xquad(3-iq) * xquad(jq)) + & - v_shlf(I,J) * (xquad(iq) * xquad(jq)) - - ux = u_shlf(I-1,J-1) * Phi(1,2*(jq-1)+iq,i,j) + & - u_shlf(I,J-1) * Phi(3,2*(jq-1)+iq,i,j) + & - u_shlf(I-1,J) * Phi(5,2*(jq-1)+iq,i,j) + & - u_shlf(I,J) * Phi(7,2*(jq-1)+iq,i,j) - - vx = v_shlf(I-1,J-1) * Phi(1,2*(jq-1)+iq,i,j) + & - v_shlf(I,J-1) * Phi(3,2*(jq-1)+iq,i,j) + & - v_shlf(I-1,J) * Phi(5,2*(jq-1)+iq,i,j) + & - v_shlf(I,J) * Phi(7,2*(jq-1)+iq,i,j) - - uy = u_shlf(I-1,J-1) * Phi(2,2*(jq-1)+iq,i,j) + & - u_shlf(I,J-1) * Phi(4,2*(jq-1)+iq,i,j) + & - u_shlf(I-1,J) * Phi(6,2*(jq-1)+iq,i,j) + & - u_shlf(I,J) * Phi(8,2*(jq-1)+iq,i,j) - - vy = v_shlf(I-1,J-1) * Phi(2,2*(jq-1)+iq,i,j) + & - v_shlf(I,J-1) * Phi(4,2*(jq-1)+iq,i,j) + & - v_shlf(I-1,J) * Phi(6,2*(jq-1)+iq,i,j) + & - v_shlf(I,J) * Phi(8,2*(jq-1)+iq,i,j) - - if (trim(CS%ice_viscosity_compute) == "MODEL_QUADRATURE") Ee = CS%Ee(i,j,2*(jq-1)+iq) - - do iphi=1,2 ; do jphi=1,2 ; Itgt = I-2+iphi ; ;Jtgt = J-2+jphi - if (umask(Itgt,Jtgt) == 1) uret(Itgt,Jtgt) = uret(Itgt,Jtgt) + 0.25 * Ee * ice_visc(i,j) * & - ((4*ux+2*vy) * Phi(2*(2*(jphi-1)+iphi)-1,2*(jq-1)+iq,i,j) + & - (uy+vx) * Phi(2*(2*(jphi-1)+iphi),2*(jq-1)+iq,i,j)) - if (vmask(Itgt,Jtgt) == 1) vret(Itgt,Jtgt) = vret(Itgt,Jtgt) + 0.25 * Ee * ice_visc(i,j) * & - ((uy+vx) * Phi(2*(2*(jphi-1)+iphi)-1,2*(jq-1)+iq,i,j) + & - (4*vy+2*ux) * Phi(2*(2*(jphi-1)+iphi),2*(jq-1)+iq,i,j)) + qp = 2*(jq-1)+iq !current quad point + + uq = (u_shlf(I-1,J-1) * (xquad(3-iq) * xquad(3-jq)) + & + u_shlf(I,J) * (xquad(iq) * xquad(jq))) + & + (u_shlf(I,J-1) * (xquad(iq) * xquad(3-jq)) + & + u_shlf(I-1,J) * (xquad(3-iq) * xquad(jq))) + + vq = (v_shlf(I-1,J-1) * (xquad(3-iq) * xquad(3-jq)) + & + v_shlf(I,J) * (xquad(iq) * xquad(jq))) + & + (v_shlf(I,J-1) * (xquad(iq) * xquad(3-jq)) + & + v_shlf(I-1,J) * (xquad(3-iq) * xquad(jq))) + + ux = (u_shlf(I-1,J-1) * Phi(1,qp,i,j) + & + u_shlf(I,J) * Phi(7,qp,i,j)) + & + (u_shlf(I,J-1) * Phi(3,qp,i,j) + & + u_shlf(I-1,J) * Phi(5,qp,i,j)) + + vx = (v_shlf(I-1,J-1) * Phi(1,qp,i,j) + & + v_shlf(I,J) * Phi(7,qp,i,j)) + & + (v_shlf(I,J-1) * Phi(3,qp,i,j) + & + v_shlf(I-1,J) * Phi(5,qp,i,j)) + + uy = (u_shlf(I-1,J-1) * Phi(2,qp,i,j) + & + u_shlf(I,J) * Phi(8,qp,i,j)) + & + (u_shlf(I,J-1) * Phi(4,qp,i,j) + & + u_shlf(I-1,J) * Phi(6,qp,i,j)) + + vy = (v_shlf(I-1,J-1) * Phi(2,qp,i,j) + & + v_shlf(I,J) * Phi(8,qp,i,j)) + & + (v_shlf(I,J-1) * Phi(4,qp,i,j) + & + v_shlf(I-1,J) * Phi(6,qp,i,j)) + + if (visc_qp4) qpv = qp !current quad point for viscosity + + do jphi=1,2 ; Jtgt = J-2+jphi ; do iphi=1,2 ; Itgt = I-2+iphi + if (umask(Itgt,Jtgt) == 1) uret_qp(iphi,jphi,qp) = ice_visc(i,j,qpv) * & + ((4*ux+2*vy) * Phi(2*(2*(jphi-1)+iphi)-1,qp,i,j) + & + (uy+vx) * Phi(2*(2*(jphi-1)+iphi),qp,i,j)) + if (vmask(Itgt,Jtgt) == 1) vret_qp(iphi,jphi,qp) = ice_visc(i,j,qpv) * & + ((uy+vx) * Phi(2*(2*(jphi-1)+iphi)-1,qp,i,j) + & + (4*vy+2*ux) * Phi(2*(2*(jphi-1)+iphi),qp,i,j)) if (float_cond(i,j) == 0) then ilq = 1 ; if (iq == iphi) ilq = 2 jlq = 1 ; if (jq == jphi) jlq = 2 - if (umask(Itgt,Jtgt) == 1) uret(Itgt,Jtgt) = uret(Itgt,Jtgt) + & - 0.25 * basal_trac(i,j) * uq * (xquad(ilq) * xquad(jlq)) - if (vmask(Itgt,Jtgt) == 1) vret(Itgt,Jtgt) = vret(Itgt,Jtgt) + & - 0.25 * basal_trac(i,j) * vq * (xquad(ilq) * xquad(jlq)) + if (umask(Itgt,Jtgt) == 1) uret_qp(iphi,jphi,qp) = uret_qp(iphi,jphi,qp) + & + (basal_trac(i,j) * uq) * (xquad(ilq) * xquad(jlq)) + if (vmask(Itgt,Jtgt) == 1) vret_qp(iphi,jphi,qp) = vret_qp(iphi,jphi,qp) + & + (basal_trac(i,j) * vq) * (xquad(ilq) * xquad(jlq)) endif enddo ; enddo enddo ; enddo + !element contribution to SW node (node 1, which sees the current element as element 4) + uret_b(I-1,J-1,4) = 0.25*((uret_qp(1,1,1)+uret_qp(1,1,4))+(uret_qp(1,1,2)+uret_qp(1,1,3))) + vret_b(I-1,J-1,4) = 0.25*((vret_qp(1,1,1)+vret_qp(1,1,4))+(vret_qp(1,1,2)+vret_qp(1,1,3))) + + !element contribution to NW node (node 3, which sees the current element as element 2) + uret_b(I-1,J ,2) = 0.25*((uret_qp(1,2,1)+uret_qp(1,2,4))+(uret_qp(1,2,2)+uret_qp(1,2,3))) + vret_b(I-1,J ,2) = 0.25*((vret_qp(1,2,1)+vret_qp(1,2,4))+(vret_qp(1,2,2)+vret_qp(1,2,3))) + + !element contribution to SE node (node 2, which sees the current element as element 3) + uret_b(I ,J-1,3) = 0.25*((uret_qp(2,1,1)+uret_qp(2,1,4))+(uret_qp(2,1,2)+uret_qp(2,1,3))) + vret_b(I ,J-1,3) = 0.25*((vret_qp(2,1,1)+vret_qp(2,1,4))+(vret_qp(2,1,2)+vret_qp(2,1,3))) + + !element contribution to NE node (node 4, which sees the current element as element 1) + uret_b(I ,J ,1) = 0.25*((uret_qp(2,2,1)+uret_qp(2,2,4))+(uret_qp(2,2,2)+uret_qp(2,2,3))) + vret_b(I ,J ,1) = 0.25*((vret_qp(2,2,1)+vret_qp(2,2,4))+(vret_qp(2,2,2)+vret_qp(2,2,3))) + if (float_cond(i,j) == 1) then Ucell(:,:) = u_shlf(I-1:I,J-1:J) ; Vcell(:,:) = v_shlf(I-1:I,J-1:J) - Hcell(:,:) = H_node(i-1:i,j-1:j) - call CG_action_subgrid_basal(Phisub, Hcell, Ucell, Vcell, bathyT(i,j), dens_ratio, Usub, Vsub) - - if (umask(I-1,J-1) == 1) uret(I-1,J-1) = uret(I-1,J-1) + Usub(1,1) * basal_trac(i,j) - if (umask(I-1,J) == 1) uret(I-1,J) = uret(I-1,J) + Usub(1,2) * basal_trac(i,j) - if (umask(I,J-1) == 1) uret(I,J-1) = uret(I,J-1) + Usub(2,1) * basal_trac(i,j) - if (umask(I,J) == 1) uret(I,J) = uret(I,J) + Usub(2,2) * basal_trac(i,j) - - if (vmask(I-1,J-1) == 1) vret(I-1,J-1) = vret(I-1,J-1) + Vsub(1,1) * basal_trac(i,j) - if (vmask(I-1,J) == 1) vret(I-1,J) = vret(I-1,J) + Vsub(1,2) * basal_trac(i,j) - if (vmask(I,J-1) == 1) vret(I,J-1) = vret(I,J-1) + Vsub(2,1) * basal_trac(i,j) - if (vmask(I,J) == 1) vret(I,J) = vret(I,J) + Vsub(2,2) * basal_trac(i,j) - endif + Hcell(:,:) = H_node(I-1:I,J-1:J) + + call CG_action_subgrid_basal(Phisub, Hcell, Ucell, Vcell, & + bathyT(i,j), dens_ratio, Usub, Vsub) + if (umask(I-1,J-1) == 1) uret_b(I-1,J-1,4) = uret_b(I-1,J-1,4) + (Usub(1,1) * basal_trac(i,j)) + if (umask(I-1,J ) == 1) uret_b(I-1,J ,2) = uret_b(I-1,J ,2) + (Usub(1,2) * basal_trac(i,j)) + if (umask(I ,J-1) == 1) uret_b(I ,J-1,3) = uret_b(I ,J-1,3) + (Usub(2,1) * basal_trac(i,j)) + if (umask(I ,J ) == 1) uret_b(I ,J ,1) = uret_b(I ,J ,1) + (Usub(2,2) * basal_trac(i,j)) + + if (vmask(I-1,J-1) == 1) vret_b(I-1,J-1,4) = vret_b(I-1,J-1,4) + (Vsub(1,1) * basal_trac(i,j)) + if (vmask(I-1,J ) == 1) vret_b(I-1,J ,2) = vret_b(I-1,J ,2) + (Vsub(1,2) * basal_trac(i,j)) + if (vmask(I ,J-1) == 1) vret_b(I ,J-1,3) = vret_b(I ,J-1,3) + (Vsub(2,1) * basal_trac(i,j)) + if (vmask(I ,J ) == 1) vret_b(I ,J ,1) = vret_b(I ,J ,1) + (Vsub(2,2) * basal_trac(i,j)) + endif endif ; enddo ; enddo + do J=js-1,je ; do I=is-1,ie + uret(I,J) = (uret_b(I,J,1)+uret_b(I,J,4)) + (uret_b(I,J,2)+uret_b(I,J,3)) + vret(I,J) = (vret_b(I,J,1)+vret_b(I,J,4)) + (vret_b(I,J,2)+vret_b(I,J,3)) + enddo; enddo + end subroutine CG_action subroutine CG_action_subgrid_basal(Phisub, H, U, V, bathyT, dens_ratio, Ucontr, Vcontr) @@ -2579,45 +2638,101 @@ subroutine CG_action_subgrid_basal(Phisub, H, U, V, bathyT, dens_ratio, Ucontr, real, dimension(2,2), intent(out) :: Vcontr !< The areal average of v-velocities where the ice shelf !! is grounded, or 0 where it is floating [L T-1 ~> m s-1]. + real, dimension(SIZE(Phisub,3),SIZE(Phisub,3),2,2) :: Ucontr_sub, Vcontr_sub ! The contributions to Ucontr and Vcontr + !! at each sub-cell + real, dimension(2,2) :: Ucontr_q, Vcontr_q !Contributions to a node from each quadrature point in a sub-grid cell real :: subarea ! The fractional sub-cell area [nondim] real :: hloc ! The local sub-cell ice thickness [Z ~> m] integer :: nsub, i, j, qx, qy, m, n - nsub = size(Phisub,1) + nsub = size(Phisub,3) subarea = 1.0 / (nsub**2) - do n=1,2 ; do m=1,2 - Ucontr(m,n) = 0.0 ; Vcontr(m,n) = 0.0 - do qy=1,2 ; do qx=1,2 ; do j=1,nsub ; do i=1,nsub - hloc = (Phisub(i,j,1,1,qx,qy)*H(1,1) + Phisub(i,j,2,2,qx,qy)*H(2,2)) + & - (Phisub(i,j,1,2,qx,qy)*H(1,2) + Phisub(i,j,2,1,qx,qy)*H(2,1)) + do n=1,2 ; do m=1,2 ; do j=1,nsub ; do i=1,nsub + do qy=1,2 ; do qx=1,2 + !calculate quadrature point contributions for the sub-cell, to each node + hloc = (Phisub(qx,qy,i,j,1,1)*H(1,1) + Phisub(qx,qy,i,j,2,2)*H(2,2)) + & + (Phisub(qx,qy,i,j,1,2)*H(1,2) + Phisub(qx,qy,i,j,2,1)*H(2,1)) + if (dens_ratio * hloc - bathyT > 0) then - Ucontr(m,n) = Ucontr(m,n) + subarea * 0.25 * Phisub(i,j,m,n,qx,qy) * & - ((Phisub(i,j,1,1,qx,qy) * U(1,1) + Phisub(i,j,2,2,qx,qy) * U(2,2)) + & - (Phisub(i,j,1,2,qx,qy) * U(1,2) + Phisub(i,j,2,1,qx,qy) * U(2,1))) - Vcontr(m,n) = Vcontr(m,n) + subarea * 0.25 * Phisub(i,j,m,n,qx,qy) * & - ((Phisub(i,j,1,1,qx,qy) * V(1,1) + Phisub(i,j,2,2,qx,qy) * V(2,2)) + & - (Phisub(i,j,1,2,qx,qy) * V(1,2) + Phisub(i,j,2,1,qx,qy) * V(2,1))) + Ucontr_q(qx,qy) = Phisub(qx,qy,i,j,m,n) * & + ((Phisub(qx,qy,i,j,1,1) * U(1,1) + Phisub(qx,qy,i,j,2,2) * U(2,2)) + & + (Phisub(qx,qy,i,j,1,2) * U(1,2) + Phisub(qx,qy,i,j,2,1) * U(2,1))) + Vcontr_q(qx,qy) = Phisub(qx,qy,i,j,m,n) * & + ((Phisub(qx,qy,i,j,1,1) * V(1,1) + Phisub(qx,qy,i,j,2,2) * V(2,2)) + & + (Phisub(qx,qy,i,j,1,2) * V(1,2) + Phisub(qx,qy,i,j,2,1) * V(2,1))) + else + Ucontr_q(qx,qy) = 0.0; Vcontr_q(qx,qy) = 0.0 endif - enddo ; enddo ; enddo ; enddo + enddo; enddo + + !calculate sub-cell contribution to each node by summing up quadrature point contributions from the sub-cell + Ucontr_sub(i,j,m,n) = (subarea * 0.25) * ((Ucontr_q(1,1) + Ucontr_q(2,2)) + (Ucontr_q(1,2)+Ucontr_q(2,1))) + Vcontr_sub(i,j,m,n) = (subarea * 0.25) * ((Vcontr_q(1,1) + Vcontr_q(2,2)) + (Vcontr_q(1,2)+Vcontr_q(2,1))) + enddo; enddo ; enddo ; enddo + + !sum up the sub-cell contributions to each node + do n=1,2 ; do m=1,2 + call sum_square_matrix(Ucontr(m,n),Ucontr_sub(:,:,m,n),nsub) + call sum_square_matrix(Vcontr(m,n),Vcontr_sub(:,:,m,n),nsub) enddo ; enddo end subroutine CG_action_subgrid_basal + +!! Returns the sum of the elements in a square matrix. This sum is bitwise identical even if the matrices are rotated. +subroutine sum_square_matrix(sum_out, mat_in, n) + integer, intent(in) :: n !< The length and width of each matrix in mat_in + real, dimension(n,n), intent(in) :: mat_in !< The four n x n matrices to be summed individually + real, intent(out) :: sum_out !< The sums of each of the 4 matrices given in mat_in + integer :: s0,e0,s1,e1 + + sum_out=0.0 + + s0=1; e0=n + + !start by summing elements on outer edges of matrix + do while (s0 returns the diagonal entries of the matrix for a Jacobi preconditioning subroutine matrix_diagonal(CS, G, US, float_cond, H_node, ice_visc, basal_trac, hmask, dens_ratio, & - Phisub, u_diagonal, v_diagonal) + Phi, Phisub, u_diagonal, v_diagonal) type(ice_shelf_dyn_CS), intent(in) :: CS !< A pointer to the ice shelf control structure type(ocean_grid_type), intent(in) :: G !< The grid structure used by the ice shelf. type(unit_scale_type), intent(in) :: US !< A structure containing unit conversion factors real, dimension(SZDI_(G),SZDJ_(G)), & - intent(in) :: float_cond !< If GL_regularize=true, an array indicating where the ice - !! shelf is floating: 0 if floating, 1 if not + intent(in) :: float_cond !< If GL_regularize=true, indicates cells containing + !! the grounding line (float_cond=1) or not (float_cond=0) real, dimension(SZDIB_(G),SZDJB_(G)), & intent(in) :: H_node !< The ice shelf thickness at nodal !! (corner) points [Z ~> m]. - real, dimension(SZDI_(G),SZDJ_(G)), & + real, dimension(SZDI_(G),SZDJ_(G),CS%visc_qps), & intent(in) :: ice_visc !< A field related to the ice viscosity from Glen's !! flow law [R L4 Z T-1 ~> kg m2 s-1]. The exact form !! and units depend on the basal law exponent. @@ -2630,6 +2745,9 @@ subroutine matrix_diagonal(CS, G, US, float_cond, H_node, ice_visc, basal_trac, !! partly or fully covered by an ice-shelf real, intent(in) :: dens_ratio !< The density of ice divided by the density !! of seawater [nondim] + real, dimension(8,4,SZDI_(G),SZDJ_(G)), & + intent(in) :: Phi !< The gradients of bilinear basis elements at Gaussian + !! quadrature points surrounding the cell vertices [L-1 ~> m-1] real, dimension(:,:,:,:,:,:), intent(in) :: Phisub !< Quadrature structure weights at subgridscale !! locations for finite element calculations [nondim] real, dimension(SZDIB_(G),SZDJB_(G)), & @@ -2644,89 +2762,122 @@ subroutine matrix_diagonal(CS, G, US, float_cond, H_node, ice_visc, basal_trac, real :: ux, uy, vx, vy ! Interpolated weight gradients [L-1 ~> m-1] real :: uq, vq - real, dimension(8,4) :: Phi ! Weight gradients [L-1 ~> m-1] real, dimension(2) :: xquad real, dimension(2,2) :: Hcell, sub_ground - integer :: i, j, isc, jsc, iec, jec, iphi, jphi, iq, jq, ilq, jlq, Itgt, Jtgt - real :: Ee + real, dimension(2,2,4) :: u_diag_qp, v_diag_qp + real, dimension(SZDIB_(G),SZDJB_(G),4) :: u_diag_b, v_diag_b + logical :: visc_qp4 + integer :: i, j, isc, jsc, iec, jec, iphi, jphi, iq, jq, ilq, jlq, Itgt, Jtgt, qp, qpv isc = G%isc ; jsc = G%jsc ; iec = G%iec ; jec = G%jec xquad(1) = .5 * (1-sqrt(1./3)) ; xquad(2) = .5 * (1+sqrt(1./3)) - Ee=1.0 + if (CS%visc_qps == 4) then + visc_qp4=.true. + else + visc_qp4=.false. + qpv = 1 + endif + + u_diag_b(:,:,:)=0.0 + v_diag_b(:,:,:)=0.0 do j=jsc-1,jec+1 ; do i=isc-1,iec+1 ; if (hmask(i,j) == 1 .or. hmask(i,j)==3) then - call bilinear_shape_fn_grid(G, i, j, Phi) - ! Phi(2*i-1,j) gives d(Phi_i)/dx at quadrature point j ! Phi(2*i,j) gives d(Phi_i)/dy at quadrature point j + u_diag_qp(:,:,:)=0.0; v_diag_qp(:,:,:)=0.0 + do iq=1,2 ; do jq=1,2 - if (trim(CS%ice_viscosity_compute) == "MODEL_QUADRATURE") Ee = CS%Ee(i,j,2*(jq-1)+iq) - do iphi=1,2 ; do jphi=1,2 + qp = 2*(jq-1)+iq !current quad point + if (visc_qp4) qpv = qp !current quad point for viscosity + + do jphi=1,2 ; Jtgt = J-2+jphi ; do iphi=1,2 ; Itgt = I-2+iphi - Itgt = I-2+iphi ; Jtgt = J-2+jphi ilq = 1 ; if (iq == iphi) ilq = 2 jlq = 1 ; if (jq == jphi) jlq = 2 if (CS%umask(Itgt,Jtgt) == 1) then - ux = Phi(2*(2*(jphi-1)+iphi)-1, 2*(jq-1)+iq) - uy = Phi(2*(2*(jphi-1)+iphi), 2*(jq-1)+iq) + ux = Phi(2*(2*(jphi-1)+iphi)-1,qp,i,j) + uy = Phi(2*(2*(jphi-1)+iphi),qp,i,j) vx = 0. vy = 0. - u_diagonal(Itgt,Jtgt) = u_diagonal(Itgt,Jtgt) + & - 0.25 * Ee * ice_visc(i,j) * ((4*ux+2*vy) * Phi(2*(2*(jphi-1)+iphi)-1,2*(jq-1)+iq) + & - (uy+vx) * Phi(2*(2*(jphi-1)+iphi),2*(jq-1)+iq)) + u_diag_qp(iphi,jphi,qp) = & + ice_visc(i,j,qpv) * ((4*ux+2*vy) * Phi(2*(2*(jphi-1)+iphi)-1,qp,i,j) + & + (uy+vx) * Phi(2*(2*(jphi-1)+iphi),qp,i,j)) if (float_cond(i,j) == 0) then uq = xquad(ilq) * xquad(jlq) - u_diagonal(Itgt,Jtgt) = u_diagonal(Itgt,Jtgt) + & - 0.25 * basal_trac(i,j) * uq * (xquad(ilq) * xquad(jlq)) + u_diag_qp(iphi,jphi,qp) = u_diag_qp(iphi,jphi,qp) + & + (basal_trac(i,j) * uq) * (xquad(ilq) * xquad(jlq)) endif endif if (CS%vmask(Itgt,Jtgt) == 1) then - vx = Phi(2*(2*(jphi-1)+iphi)-1, 2*(jq-1)+iq) - vy = Phi(2*(2*(jphi-1)+iphi), 2*(jq-1)+iq) + vx = Phi(2*(2*(jphi-1)+iphi)-1,qp,i,j) + vy = Phi(2*(2*(jphi-1)+iphi),qp,i,j) ux = 0. uy = 0. - v_diagonal(Itgt,Jtgt) = v_diagonal(Itgt,Jtgt) + & - 0.25 * Ee * ice_visc(i,j) * ((uy+vx) * Phi(2*(2*(jphi-1)+iphi)-1,2*(jq-1)+iq) + & - (4*vy+2*ux) * Phi(2*(2*(jphi-1)+iphi),2*(jq-1)+iq)) + v_diag_qp(iphi,jphi,qp) = & + ice_visc(i,j,qpv) * ((uy+vx) * Phi(2*(2*(jphi-1)+iphi)-1,qp,i,j) + & + (4*vy+2*ux) * Phi(2*(2*(jphi-1)+iphi),qp,i,j)) if (float_cond(i,j) == 0) then vq = xquad(ilq) * xquad(jlq) - v_diagonal(Itgt,Jtgt) = v_diagonal(Itgt,Jtgt) + & - 0.25 * basal_trac(i,j) * vq * (xquad(ilq) * xquad(jlq)) + v_diag_qp(iphi,jphi,qp) = v_diag_qp(iphi,jphi,qp) + & + (basal_trac(i,j) * vq) * (xquad(ilq) * xquad(jlq)) endif endif enddo ; enddo enddo ; enddo + !element contribution to SW node (node 1, which sees the current element as element 4) + u_diag_b(I-1,J-1,4) = 0.25*((u_diag_qp(1,1,1)+u_diag_qp(1,1,4))+(u_diag_qp(1,1,2)+u_diag_qp(1,1,3))) + v_diag_b(I-1,J-1,4) = 0.25*((v_diag_qp(1,1,1)+v_diag_qp(1,1,4))+(v_diag_qp(1,1,2)+v_diag_qp(1,1,3))) + + !element contribution to NW node (node 3, which sees the current element as element 2) + u_diag_b(I-1,J ,2) = 0.25*((u_diag_qp(1,2,1)+u_diag_qp(1,2,4))+(u_diag_qp(1,2,2)+u_diag_qp(1,2,3))) + v_diag_b(I-1,J ,2) = 0.25*((v_diag_qp(1,2,1)+v_diag_qp(1,2,4))+(v_diag_qp(1,2,2)+v_diag_qp(1,2,3))) + + !element contribution to SE node (node 2, which sees the current element as element 3) + u_diag_b(I ,J-1,3) = 0.25*((u_diag_qp(2,1,1)+u_diag_qp(2,1,4))+(u_diag_qp(2,1,2)+u_diag_qp(2,1,3))) + v_diag_b(I ,J-1,3) = 0.25*((v_diag_qp(2,1,1)+v_diag_qp(2,1,4))+(v_diag_qp(2,1,2)+v_diag_qp(2,1,3))) + + !element contribution to NE node (node 4, which sees the current element as element 1) + u_diag_b(I ,J ,1) = 0.25*((u_diag_qp(2,2,1)+u_diag_qp(2,2,4))+(u_diag_qp(2,2,2)+u_diag_qp(2,2,3))) + v_diag_b(I ,J ,1) = 0.25*((v_diag_qp(2,2,1)+v_diag_qp(2,2,4))+(v_diag_qp(2,2,2)+v_diag_qp(2,2,3))) + if (float_cond(i,j) == 1) then Hcell(:,:) = H_node(i-1:i,j-1:j) call CG_diagonal_subgrid_basal(Phisub, Hcell, CS%bed_elev(i,j), dens_ratio, sub_ground) - do iphi=1,2 ; do jphi=1,2 ; Itgt = I-2+iphi ; Jtgt = J-2+jphi - if (CS%umask(Itgt,Jtgt) == 1) then - u_diagonal(Itgt,Jtgt) = u_diagonal(Itgt,Jtgt) + sub_ground(iphi,jphi) * basal_trac(i,j) - endif - if (CS%vmask(Itgt,Jtgt) == 1) then - v_diagonal(Itgt,Jtgt) = v_diagonal(Itgt,Jtgt) + sub_ground(iphi,jphi) * basal_trac(i,j) - endif - enddo ; enddo + + if (CS%umask(I-1,J-1) == 1) u_diag_b(I-1,J-1,4) = u_diag_b(I-1,J-1,4) + sub_ground(1,1) * basal_trac(i,j) + if (CS%umask(I-1,J ) == 1) u_diag_b(I-1,J ,2) = u_diag_b(I-1,J ,2) + sub_ground(1,2) * basal_trac(i,j) + if (CS%umask(I ,J-1) == 1) u_diag_b(I ,J-1,3) = u_diag_b(I ,J-1,3) + sub_ground(2,1) * basal_trac(i,j) + if (CS%umask(I ,J ) == 1) u_diag_b(I ,J ,1) = u_diag_b(I ,J ,1) + sub_ground(2,2) * basal_trac(i,j) + + if (CS%vmask(I-1,J-1) == 1) v_diag_b(I-1,J-1,4) = v_diag_b(I-1,J-1,4) + sub_ground(1,1) * basal_trac(i,j) + if (CS%vmask(I-1,J ) == 1) v_diag_b(I-1,J ,2) = v_diag_b(I-1,J ,2) + sub_ground(1,2) * basal_trac(i,j) + if (CS%vmask(I ,J-1) == 1) v_diag_b(I ,J-1,3) = v_diag_b(I ,J-1,3) + sub_ground(2,1) * basal_trac(i,j) + if (CS%vmask(I ,J ) == 1) v_diag_b(I ,J ,1) = v_diag_b(I ,J ,1) + sub_ground(2,2) * basal_trac(i,j) endif endif ; enddo ; enddo + do J=jsc-2,jec+1 ; do I=isc-2,iec+1 + u_diagonal(I,J) = (u_diag_b(I,J,1)+u_diag_b(I,J,4)) + (u_diag_b(I,J,2)+u_diag_b(I,J,3)) + v_diagonal(I,J) = (v_diag_b(I,J,1)+v_diag_b(I,J,4)) + (v_diag_b(I,J,2)+v_diag_b(I,J,3)) + enddo ; enddo + end subroutine matrix_diagonal -subroutine CG_diagonal_subgrid_basal (Phisub, H_node, bathyT, dens_ratio, sub_grnd) +subroutine CG_diagonal_subgrid_basal (Phisub, H_node, bathyT, dens_ratio, f_grnd) real, dimension(:,:,:,:,:,:), & intent(in) :: Phisub !< Quadrature structure weights at subgridscale !! locations for finite element calculations [nondim] @@ -2735,184 +2886,43 @@ subroutine CG_diagonal_subgrid_basal (Phisub, H_node, bathyT, dens_ratio, sub_gr real, intent(in) :: bathyT !< The depth of ocean bathymetry at tracer points [Z ~> m]. real, intent(in) :: dens_ratio !< The density of ice divided by the density !! of seawater [nondim] - real, dimension(2,2), intent(out) :: sub_grnd !< The weighted fraction of the sub-cell where the ice shelf - !! is grounded [nondim] - - ! bathyT = cellwise-constant bed elevation + real, dimension(2,2), intent(out) :: f_grnd !< The weighted fraction of the sub-cell where the ice shelf + !! is grounded [nondim] + real, dimension(SIZE(Phisub,3),SIZE(Phisub,3),2,2) :: f_grnd_sub ! The contributions to nodal f_grnd + !! from each sub-cell + real, dimension(2,2) :: f_grnd_q !Contributions to a node from each quadrature point in a sub-grid cell real :: subarea ! The fractional sub-cell area [nondim] real :: hloc ! The local sub-region thickness [Z ~> m] integer :: nsub, i, j, qx, qy, m, n - nsub = size(Phisub,1) + nsub = size(Phisub,3) subarea = 1.0 / (nsub**2) - sub_grnd(:,:) = 0.0 - do m=1,2 ; do n=1,2 ; do j=1,nsub ; do i=1,nsub ; do qx=1,2 ; do qy = 1,2 - - hloc = (Phisub(i,j,1,1,qx,qy)*H_node(1,1) + Phisub(i,j,2,2,qx,qy)*H_node(2,2)) + & - (Phisub(i,j,1,2,qx,qy)*H_node(1,2) + Phisub(i,j,2,1,qx,qy)*H_node(2,1)) + do n=1,2 ; do m=1,2 ; do j=1,nsub ; do i=1,nsub + do qy=1,2 ; do qx = 1,2 + !calculate quadrature point contributions for the sub-cell, to each node + hloc = (Phisub(qx,qy,i,j,1,1)*H_node(1,1) + Phisub(qx,qy,i,j,2,2)*H_node(2,2)) + & + (Phisub(qx,qy,i,j,1,2)*H_node(1,2) + Phisub(qx,qy,i,j,2,1)*H_node(2,1)) - if (dens_ratio * hloc - bathyT > 0) then - sub_grnd(m,n) = sub_grnd(m,n) + subarea * 0.25 * Phisub(i,j,m,n,qx,qy)**2 - endif + if (dens_ratio * hloc - bathyT > 0) then + f_grnd_q(qx,qy) = Phisub(qx,qy,i,j,m,n)**2 + else + f_grnd_q(qx,qy) = 0.0 + endif + enddo ; enddo + !calculate sub-cell contribution to each node by summing up quadrature point contributions from the sub-cell + f_grnd_sub(i,j,m,n) = (subarea * 0.25) * ((f_grnd_q(1,1) + f_grnd_q(2,2)) + (f_grnd_q(1,2)+f_grnd_q(2,1))) + enddo ; enddo ; enddo ; enddo - enddo ; enddo ; enddo ; enddo ; enddo ; enddo + !sum up the sub-cell contributions to each node + do n=1,2 ; do m=1,2 + call sum_square_matrix(f_grnd(m,n),f_grnd_sub(:,:,m,n),nsub) + enddo ; enddo end subroutine CG_diagonal_subgrid_basal -subroutine apply_boundary_values(CS, ISS, G, US, time, Phisub, H_node, ice_visc, basal_trac, float_cond, & - dens_ratio, u_bdry_contr, v_bdry_contr) - - type(ice_shelf_dyn_CS), intent(in) :: CS !< A pointer to the ice shelf control structure - type(ice_shelf_state), intent(in) :: ISS !< A structure with elements that describe - !! the ice-shelf state - type(ocean_grid_type), intent(in) :: G !< The grid structure used by the ice shelf. - type(unit_scale_type), intent(in) :: US !< A structure containing unit conversion factors - type(time_type), intent(in) :: Time !< The current model time - real, dimension(:,:,:,:,:,:), & - intent(in) :: Phisub !< Quadrature structure weights at subgridscale - !! locations for finite element calculations [nondim] - real, dimension(SZDIB_(G),SZDJB_(G)), & - intent(in) :: H_node !< The ice shelf thickness at nodal - !! (corner) points [Z ~> m]. - real, dimension(SZDI_(G),SZDJ_(G)), & - intent(in) :: ice_visc !< A field related to the ice viscosity from Glen's - !! flow law. The exact form and units depend on the - !! basal law exponent. [R L4 Z T-1 ~> kg m2 s-1]. - real, dimension(SZDI_(G),SZDJ_(G)), & - intent(in) :: basal_trac !< Area-integrated taub_beta field related to the nonlinear - !! part of the "linearized" basal stress [R L3 T-1 ~> kg s-1]. - - real, dimension(SZDI_(G),SZDJ_(G)), & - intent(in) :: float_cond !< An array indicating where the ice - !! shelf is floating: 0 if floating, 1 if not. - real, intent(in) :: dens_ratio !< The density of ice divided by the density - !! of seawater, nondimensional - real, dimension(SZDIB_(G),SZDJB_(G)), & - intent(inout) :: u_bdry_contr !< Zonal force contributions due to the - !! open boundaries [R L3 Z T-2 ~> kg m s-2] - real, dimension(SZDIB_(G),SZDJB_(G)), & - intent(inout) :: v_bdry_contr !< Meridional force contributions due to the - !! open boundaries [R L3 Z T-2 ~> kg m s-2] - -! this will be a per-setup function. the boundary values of thickness and velocity -! (and possibly other variables) will be updated in this function - - real, dimension(8,4) :: Phi - real, dimension(2) :: xquad - real :: ux, uy, vx, vy ! Components of velocity shears or divergence [T-1 ~> s-1] - real :: uq, vq ! Interpolated velocities [L T-1 ~> m s-1] - real, dimension(2,2) :: Ucell,Vcell,Hcell,Usubcontr,Vsubcontr - integer :: i, j, isc, jsc, iec, jec, iq, jq, iphi, jphi, ilq, jlq, Itgt, Jtgt - real :: Ee - - isc = G%isc ; jsc = G%jsc ; iec = G%iec ; jec = G%jec - - xquad(1) = .5 * (1-sqrt(1./3)) ; xquad(2) = .5 * (1+sqrt(1./3)) - - Ee=1.0 - - do j=jsc-1,jec+1 ; do i=isc-1,iec+1 ; if (ISS%hmask(i,j) == 1 .or. ISS%hmask(i,j) == 3) then - - ! process this cell if any corners have umask set to non-dirichlet bdry. - - if ((CS%umask(I-1,J-1) == 3) .OR. (CS%umask(I,J-1) == 3) .OR. & - (CS%umask(I-1,J) == 3) .OR. (CS%umask(I,J) == 3) .OR. & - (CS%vmask(I-1,J-1) == 3) .OR. (CS%vmask(I,J-1) == 3) .OR. & - (CS%vmask(I-1,J) == 3) .OR. (CS%vmask(I,J) == 3)) then - - call bilinear_shape_fn_grid(G, i, j, Phi) - - ! Phi(2*i-1,j) gives d(Phi_i)/dx at quadrature point j - ! Phi(2*i,j) gives d(Phi_i)/dy at quadrature point j - - do iq=1,2 ; do jq=1,2 - - uq = CS%u_bdry_val(I-1,J-1) * (xquad(3-iq) * xquad(3-jq)) + & - CS%u_bdry_val(I,J-1) * (xquad(iq) * xquad(3-jq)) + & - CS%u_bdry_val(I-1,J) * (xquad(3-iq) * xquad(jq)) + & - CS%u_bdry_val(I,J) * (xquad(iq) * xquad(jq)) - - vq = CS%v_bdry_val(I-1,J-1) * (xquad(3-iq) * xquad(3-jq)) + & - CS%v_bdry_val(I,J-1) * (xquad(iq) * xquad(3-jq)) + & - CS%v_bdry_val(I-1,J) * (xquad(3-iq) * xquad(jq)) + & - CS%v_bdry_val(I,J) * (xquad(iq) * xquad(jq)) - - ux = CS%u_bdry_val(I-1,J-1) * Phi(1,2*(jq-1)+iq) + & - CS%u_bdry_val(I,J-1) * Phi(3,2*(jq-1)+iq) + & - CS%u_bdry_val(I-1,J) * Phi(5,2*(jq-1)+iq) + & - CS%u_bdry_val(I,J) * Phi(7,2*(jq-1)+iq) - - vx = CS%v_bdry_val(I-1,J-1) * Phi(1,2*(jq-1)+iq) + & - CS%v_bdry_val(I,J-1) * Phi(3,2*(jq-1)+iq) + & - CS%v_bdry_val(I-1,J) * Phi(5,2*(jq-1)+iq) + & - CS%v_bdry_val(I,J) * Phi(7,2*(jq-1)+iq) - - uy = CS%u_bdry_val(I-1,J-1) * Phi(2,2*(jq-1)+iq) + & - CS%u_bdry_val(I,J-1) * Phi(4,2*(jq-1)+iq) + & - CS%u_bdry_val(I-1,J) * Phi(6,2*(jq-1)+iq) + & - CS%u_bdry_val(I,J) * Phi(8,2*(jq-1)+iq) - - vy = CS%v_bdry_val(I-1,J-1) * Phi(2,2*(jq-1)+iq) + & - CS%v_bdry_val(I,J-1) * Phi(4,2*(jq-1)+iq) + & - CS%v_bdry_val(I-1,J) * Phi(6,2*(jq-1)+iq) + & - CS%v_bdry_val(I,J) * Phi(8,2*(jq-1)+iq) - - if (trim(CS%ice_viscosity_compute) == "MODEL_QUADRATURE") Ee = CS%Ee(i,j,2*(jq-1)+iq) - - do iphi=1,2 ; do jphi=1,2 ; Itgt = I-2+iphi ; Jtgt = J-2+jphi - ilq = 1 ; if (iq == iphi) ilq = 2 - jlq = 1 ; if (jq == jphi) jlq = 2 - - if (CS%umask(Itgt,Jtgt) == 1) then - u_bdry_contr(Itgt,Jtgt) = u_bdry_contr(Itgt,Jtgt) + & - 0.25 * Ee * ice_visc(i,j) * ( (4*ux+2*vy) * Phi(2*(2*(jphi-1)+iphi)-1,2*(jq-1)+iq) + & - (uy+vx) * Phi(2*(2*(jphi-1)+iphi),2*(jq-1)+iq) ) - - if (float_cond(i,j) == 0) then - u_bdry_contr(Itgt,Jtgt) = u_bdry_contr(Itgt,Jtgt) + & - 0.25 * basal_trac(i,j) * uq * (xquad(ilq) * xquad(jlq)) - endif - endif - - if (CS%vmask(Itgt,Jtgt) == 1) then - v_bdry_contr(Itgt,Jtgt) = v_bdry_contr(Itgt,Jtgt) + & - 0.25 * Ee * ice_visc(i,j) * ( (uy+vx) * Phi(2*(2*(jphi-1)+iphi)-1,2*(jq-1)+iq) + & - (4*vy+2*ux) * Phi(2*(2*(jphi-1)+iphi),2*(jq-1)+iq) ) - - if (float_cond(i,j) == 0) then - v_bdry_contr(Itgt,Jtgt) = v_bdry_contr(Itgt,Jtgt) + & - 0.25 * basal_trac(i,j) * vq * (xquad(ilq) * xquad(jlq)) - endif - endif - enddo ; enddo - enddo ; enddo - - if (float_cond(i,j) == 1) then - Ucell(:,:) = CS%u_bdry_val(i-1:i,j-1:j) ; Vcell(:,:) = CS%v_bdry_val(i-1:i,j-1:j) - Hcell(:,:) = H_node(i-1:i,j-1:j) - call CG_action_subgrid_basal(Phisub, Hcell, Ucell, Vcell, CS%bed_elev(i,j), & - dens_ratio, Usubcontr, Vsubcontr) - - if (CS%umask(I-1,J-1) == 1) u_bdry_contr(I-1,J-1) = u_bdry_contr(I-1,J-1) + Usubcontr(1,1) * basal_trac(i,j) - if (CS%umask(I-1,J) == 1) u_bdry_contr(I-1,J) = u_bdry_contr(I-1,J) + Usubcontr(1,2) * basal_trac(i,j) - if (CS%umask(I,J-1) == 1) u_bdry_contr(I,J-1) = u_bdry_contr(I,J-1) + Usubcontr(2,1) * basal_trac(i,j) - if (CS%umask(I,J) == 1) u_bdry_contr(I,J) = u_bdry_contr(I,J) + Usubcontr(2,2) * basal_trac(i,j) - - if (CS%vmask(I-1,J-1) == 1) v_bdry_contr(I-1,J-1) = v_bdry_contr(I-1,J-1) + Vsubcontr(1,1) * basal_trac(i,j) - if (CS%vmask(I-1,J) == 1) v_bdry_contr(I-1,J) = v_bdry_contr(I-1,J) + Vsubcontr(1,2) * basal_trac(i,j) - if (CS%vmask(I,J-1) == 1) v_bdry_contr(I,J-1) = v_bdry_contr(I,J-1) + Vsubcontr(2,1) * basal_trac(i,j) - if (CS%vmask(I,J) == 1) v_bdry_contr(I,J) = v_bdry_contr(I,J) + Vsubcontr(2,2) * basal_trac(i,j) - endif - endif - endif ; enddo ; enddo - - call pass_vector(u_bdry_contr, v_bdry_contr, G%domain, TO_ALL, BGRID_NE) -end subroutine apply_boundary_values - - !> Update depth integrated viscosity, based on horizontal strain rates subroutine calc_shelf_visc(CS, ISS, G, US, u_shlf, v_shlf) type(ice_shelf_dyn_CS), intent(inout) :: CS !< A pointer to the ice shelf control structure @@ -2924,9 +2934,6 @@ subroutine calc_shelf_visc(CS, ISS, G, US, u_shlf, v_shlf) intent(inout) :: u_shlf !< The zonal ice shelf velocity [L T-1 ~> m s-1]. real, dimension(G%IsdB:G%IedB,G%JsdB:G%JedB), & intent(inout) :: v_shlf !< The meridional ice shelf velocity [L T-1 ~> m s-1]. - real, pointer, dimension(:,:,:,:) :: Phi => NULL() ! The gradients of bilinear basis elements at Gaussian - ! quadrature points surrounding the cell vertices [L-1 ~> m-1]. - real, pointer, dimension(:,:,:) :: PhiC => NULL() ! Same as Phi, but 1 quadrature point per cell (rather than 4) ! update DEPTH_INTEGRATED viscosity, based on horizontal strain rates - this is for bilinear FEM solve @@ -2938,8 +2945,7 @@ subroutine calc_shelf_visc(CS, ISS, G, US, u_shlf, v_shlf) real :: Visc_coef, n_g real :: ux, uy, vx, vy real :: eps_min ! Velocity shears [T-1 ~> s-1] -! real, dimension(8,4) :: Phi -! real :: umid, vmid, unorm ! Velocities [L T-1 ~> m s-1] + logical :: model_qp1, model_qp4 isc = G%isc ; jsc = G%jsc ; iec = G%iec ; jec = G%jec iscq = G%iscB ; iecq = G%iecB ; jscq = G%jscB ; jecq = G%jecB @@ -2948,99 +2954,94 @@ subroutine calc_shelf_visc(CS, ISS, G, US, u_shlf, v_shlf) gisc = G%domain%nihalo+1 ; gjsc = G%domain%njhalo+1 giec = G%domain%niglobal+gisc ; gjec = G%domain%njglobal+gjsc is = iscq - 1; js = jscq - 1 - i_off = G%idg_offset ; j_off = G%jdg_offset + i_off = G%idg_offset ; j_off = G%jdg_offset if (trim(CS%ice_viscosity_compute) == "MODEL") then - allocate(PhiC(1:8,isc:iec,jsc:jec), source=0.0) - do j=jsc,jec ; do i=isc,iec - call bilinear_shape_fn_grid_1qp(G, i, j, PhiC(:,i,j)) - enddo; enddo - elseif (trim(CS%ice_viscosity_compute) == "MODEL_QUADRATURE") then - allocate(Phi(1:8,1:4,isc:iec,jsc:jec), source=0.0) - do j=jsc,jec ; do i=isc,iec - call bilinear_shape_fn_grid(G, i, j, Phi(:,:,i,j)) - enddo; enddo + if (CS%visc_qps==1) then + model_qp1=.true. + model_qp4=.false. + else + model_qp1=.false. + model_qp4=.true. + endif endif n_g = CS%n_glen; eps_min = CS%eps_glen_min - CS%ice_visc(:,:) = 1.0e22 -! Visc_coef = US%kg_m2s_to_RZ_T*US%m_to_L*US%Z_to_L*(CS%A_glen_isothermal)**(-1./CS%n_glen) + do j=jsc,jec ; do i=isc,iec if ((ISS%hmask(i,j) == 1) .OR. (ISS%hmask(i,j) == 3)) then if (trim(CS%ice_viscosity_compute) == "CONSTANT") then - CS%ice_visc(i,j) = 1e15 * US%kg_m3_to_R*US%m_to_L*US%m_s_to_L_T * (G%areaT(i,j) * ISS%h_shelf(i,j)) + CS%ice_visc(i,j,1) = 1e15 * (US%kg_m3_to_R*US%m_to_L*US%m_s_to_L_T) * (G%areaT(i,j) * ISS%h_shelf(i,j)) ! constant viscocity for debugging elseif (trim(CS%ice_viscosity_compute) == "OBS") then - if (CS%AGlen_visc(i,j) >0) CS%ice_visc(i,j) = CS%AGlen_visc(i,j)*(G%areaT(i,j) * ISS%h_shelf(i,j)) - ! Here CS%Aglen_visc(i,j) is the ice viscocity [Pa s-1] computed from obs and read from a file - elseif (trim(CS%ice_viscosity_compute) == "MODEL") then - - Visc_coef = ( (US%RL2_T2_to_Pa)**(-CS%n_glen)*US%T_to_s )**(-1./CS%n_glen) * & - (CS%AGlen_visc(i,j))**(-1./CS%n_glen) - ! Units of Aglen_visc [Pa-3 s-1] - - ux = u_shlf(I-1,J-1) * PhiC(1,i,j) + & - u_shlf(I,J) * PhiC(7,i,j) + & - u_shlf(I-1,J) * PhiC(5,i,j) + & - u_shlf(I,J-1) * PhiC(3,i,j) - - vx = v_shlf(I-1,J-1) * PhiC(1,i,j) + & - v_shlf(I,J) * PhiC(7,i,j) + & - v_shlf(I-1,J) * PhiC(5,i,j) + & - v_shlf(I,J-1) * PhiC(3,i,j) - - uy = u_shlf(I-1,J-1) * PhiC(2,i,j) + & - u_shlf(I,J) * PhiC(8,i,j) + & - u_shlf(I-1,J) * PhiC(6,i,j) + & - u_shlf(I,J-1) * PhiC(4,i,j) - - vy = v_shlf(I-1,J-1) * PhiC(2,i,j) + & - v_shlf(I,J) * PhiC(8,i,j) + & - v_shlf(I-1,J) * PhiC(6,i,j) + & - v_shlf(I,J-1) * PhiC(4,i,j) - - CS%ice_visc(i,j) = 0.5 * Visc_coef * (G%areaT(i,j) * ISS%h_shelf(i,j)) * & - (US%s_to_T**2 * (ux**2 + vy**2 + ux*vy + 0.25*(uy+vx)**2 + eps_min**2))**((1.-n_g)/(2.*n_g)) - elseif (trim(CS%ice_viscosity_compute) == "MODEL_QUADRATURE") then - !in this case, we will compute viscosity at quadrature points within subroutines CG_action - !and apply_boundary_values. CS%ice_visc(i,j) will include everything except the effective strain rate term: - Visc_coef = ( (US%RL2_T2_to_Pa)**(-CS%n_glen)*US%T_to_s )**(-1./CS%n_glen) * & - (CS%AGlen_visc(i,j))**(-1./CS%n_glen) - CS%ice_visc(i,j) = 0.5 * Visc_coef * (G%areaT(i,j) * ISS%h_shelf(i,j)) + if (CS%AGlen_visc(i,j) >0) CS%ice_visc(i,j,1) = CS%AGlen_visc(i,j) * (G%areaT(i,j) * ISS%h_shelf(i,j)) + ! Here CS%Aglen_visc(i,j) is the ice viscosity [Pa s ~> R L2 T-1] computed from obs and read from a file + elseif (model_qp1) then + !calculate viscosity at 1 cell-centered quadrature point per cell + + Visc_coef = (CS%AGlen_visc(i,j))**(-1./n_g) + ! Units of Aglen_visc [Pa-(n_g) s-1] + + ux = (u_shlf(I-1,J-1) * CS%PhiC(1,i,j) + & + u_shlf(I,J) * CS%PhiC(7,i,j)) + & + (u_shlf(I-1,J) * CS%PhiC(5,i,j) + & + u_shlf(I,J-1) * CS%PhiC(3,i,j)) + + vx = (v_shlf(I-1,J-1) * CS%PhiC(1,i,j) + & + v_shlf(I,J) * CS%PhiC(7,i,j)) + & + (v_shlf(I-1,J) * CS%PhiC(5,i,j) + & + v_shlf(I,J-1) * CS%PhiC(3,i,j)) + + uy = (u_shlf(I-1,J-1) * CS%PhiC(2,i,j) + & + u_shlf(I,J) * CS%PhiC(8,i,j)) + & + (u_shlf(I-1,J) * CS%PhiC(6,i,j) + & + u_shlf(I,J-1) * CS%PhiC(4,i,j)) + + vy = (v_shlf(I-1,J-1) * CS%PhiC(2,i,j) + & + v_shlf(I,J) * CS%PhiC(8,i,j)) + & + (v_shlf(I-1,J) * CS%PhiC(6,i,j) + & + v_shlf(I,J-1) * CS%PhiC(4,i,j)) + + CS%ice_visc(i,j,1) = 0.5 * Visc_coef * (G%areaT(i,j) * ISS%h_shelf(i,j)) * & + (US%s_to_T**2 * ((ux**2 + vy**2) + (ux*vy + 0.25*(uy+vx)**2) + eps_min**2))**((1.-n_g)/(2.*n_g)) * & + (US%Pa_to_RL2_T2*US%s_to_T) + elseif (model_qp4) then + !calculate viscosity at 4 quadrature points per cell + + Visc_coef = (CS%AGlen_visc(i,j))**(-1./n_g) do iq=1,2 ; do jq=1,2 - ux = u_shlf(I-1,J-1) * Phi(1,2*(jq-1)+iq,i,j) + & - u_shlf(I,J-1) * Phi(3,2*(jq-1)+iq,i,j) + & - u_shlf(I-1,J) * Phi(5,2*(jq-1)+iq,i,j) + & - u_shlf(I,J) * Phi(7,2*(jq-1)+iq,i,j) - - vx = v_shlf(I-1,J-1) * Phi(1,2*(jq-1)+iq,i,j) + & - v_shlf(I,J-1) * Phi(3,2*(jq-1)+iq,i,j) + & - v_shlf(I-1,J) * Phi(5,2*(jq-1)+iq,i,j) + & - v_shlf(I,J) * Phi(7,2*(jq-1)+iq,i,j) - - uy = u_shlf(I-1,J-1) * Phi(2,2*(jq-1)+iq,i,j) + & - u_shlf(I,J-1) * Phi(4,2*(jq-1)+iq,i,j) + & - u_shlf(I-1,J) * Phi(6,2*(jq-1)+iq,i,j) + & - u_shlf(I,J) * Phi(8,2*(jq-1)+iq,i,j) - - vy = v_shlf(I-1,J-1) * Phi(2,2*(jq-1)+iq,i,j) + & - v_shlf(I,J-1) * Phi(4,2*(jq-1)+iq,i,j) + & - v_shlf(I-1,J) * Phi(6,2*(jq-1)+iq,i,j) + & - v_shlf(I,J) * Phi(8,2*(jq-1)+iq,i,j) - - CS%Ee(i,j,2*(jq-1)+iq) = & - (US%s_to_T**2 * (ux**2 + vy**2 + ux*vy + 0.25*(uy+vx)**2 + eps_min**2))**((1.-n_g)/(2.*n_g)) + ux = (u_shlf(I-1,J-1) * CS%Phi(1,2*(jq-1)+iq,i,j) + & + u_shlf(I,J) * CS%Phi(7,2*(jq-1)+iq,i,j)) + & + (u_shlf(I,J-1) * CS%Phi(3,2*(jq-1)+iq,i,j) + & + u_shlf(I-1,J) * CS%Phi(5,2*(jq-1)+iq,i,j)) + + vx = (v_shlf(I-1,J-1) * CS%Phi(1,2*(jq-1)+iq,i,j) + & + v_shlf(I,J) * CS%Phi(7,2*(jq-1)+iq,i,j)) + & + (v_shlf(I,J-1) * CS%Phi(3,2*(jq-1)+iq,i,j) + & + v_shlf(I-1,J) * CS%Phi(5,2*(jq-1)+iq,i,j)) + + uy = (u_shlf(I-1,J-1) * CS%Phi(2,2*(jq-1)+iq,i,j) + & + u_shlf(I,J) * CS%Phi(8,2*(jq-1)+iq,i,j)) + & + (u_shlf(I,J-1) * CS%Phi(4,2*(jq-1)+iq,i,j) + & + u_shlf(I-1,J) * CS%Phi(6,2*(jq-1)+iq,i,j)) + + vy = (v_shlf(I-1,J-1) * CS%Phi(2,2*(jq-1)+iq,i,j) + & + v_shlf(I,J) * CS%Phi(8,2*(jq-1)+iq,i,j)) + & + (v_shlf(I,J-1) * CS%Phi(4,2*(jq-1)+iq,i,j) + & + v_shlf(I-1,J) * CS%Phi(6,2*(jq-1)+iq,i,j)) + + CS%ice_visc(i,j,2*(jq-1)+iq) = 0.5 * Visc_coef * (G%areaT(i,j) * ISS%h_shelf(i,j)) * & + (US%s_to_T**2 * ((ux**2 + vy**2) + (ux*vy + 0.25*(uy+vx)**2) + eps_min**2))**((1.-n_g)/(2.*n_g)) * & + (US%Pa_to_RL2_T2*US%s_to_T) enddo; enddo endif endif enddo ; enddo - if (trim(CS%ice_viscosity_compute) == "MODEL") deallocate(PhiC) - if (trim(CS%ice_viscosity_compute) == "MODEL_QUADRATURE") deallocate(Phi) end subroutine calc_shelf_visc @@ -3066,7 +3067,8 @@ subroutine calc_shelf_taub(CS, ISS, G, US, u_shlf, v_shlf) real :: alpha !Coulomb coefficient [nondim] real :: Hf !"floatation thickness" for Coulomb friction [Z ~> m] real :: fN !Effective pressure (ice pressure - ocean pressure) for Coulomb friction [R L2 T-2 ~> Pa] - real :: fB !for Coulomb Friction [(L T-1)^CS%CF_PostPeak ~> (m s-1)^CS%CF_PostPeak] + real :: fB !for Coulomb Friction [(T L-1)^CS%CF_PostPeak ~> (s m-1)^CS%CF_PostPeak] + real :: fN_scale !To convert effective pressure to mks units during Coulomb friction isc = G%isc ; jsc = G%jsc ; iec = G%iec ; jec = G%jec iscq = G%iscB ; iecq = G%iecB ; jscq = G%jscB ; jecq = G%jecB @@ -3079,11 +3081,12 @@ subroutine calc_shelf_taub(CS, ISS, G, US, u_shlf, v_shlf) eps_min = CS%eps_glen_min if (CS%CoulombFriction) then - if (CS%CF_PostPeak.ne.1.0) THEN + if (CS%CF_PostPeak/=1.0) THEN alpha = (CS%CF_PostPeak-1.0)**(CS%CF_PostPeak-1.0) / CS%CF_PostPeak**CS%CF_PostPeak ![nondim] else alpha = 1.0 endif + fN_scale = US%R_to_kg_m3 * US%L_T_to_m_s**2 endif do j=jsd+1,jed @@ -3091,20 +3094,22 @@ subroutine calc_shelf_taub(CS, ISS, G, US, u_shlf, v_shlf) if ((ISS%hmask(i,j) == 1) .OR. (ISS%hmask(i,j) == 3)) then umid = ((u_shlf(I,J) + u_shlf(I-1,J-1)) + (u_shlf(I,J-1) + u_shlf(I-1,J))) * 0.25 vmid = ((v_shlf(I,J) + v_shlf(I-1,J-1)) + (v_shlf(I,J-1) + v_shlf(I-1,J))) * 0.25 - unorm = US%L_T_to_m_s*sqrt(umid**2 + vmid**2 + eps_min**2*(G%dxT(i,j)**2 + G%dyT(i,j)**2)) + unorm = US%L_T_to_m_s * sqrt( (umid**2 + vmid**2) + (eps_min**2 * (G%dxT(i,j)**2 + G%dyT(i,j)**2)) ) !Coulomb friction (Schoof 2005, Gagliardini et al 2007) if (CS%CoulombFriction) then !Effective pressure - Hf = max(CS%density_ocean_avg * CS%bed_elev(i,j)/CS%density_ice, 0.0) - fN = max(CS%density_ice * CS%g_Earth * (ISS%h_shelf(i,j) - Hf),CS%CF_MinN) - + Hf = max((CS%density_ocean_avg/CS%density_ice) * CS%bed_elev(i,j), 0.0) + fN = max(fN_scale*((CS%density_ice * CS%g_Earth) * (ISS%h_shelf(i,j) - Hf)),CS%CF_MinN) fB = alpha * (CS%C_basal_friction(i,j) / (CS%CF_Max * fN))**(CS%CF_PostPeak/CS%n_basal_fric) - CS%basal_traction(i,j) = G%areaT(i,j) * CS%C_basal_friction(i,j) * & - unorm**(CS%n_basal_fric-1.0) / (1.0 + fB * unorm**CS%CF_PostPeak)**(CS%n_basal_fric) + + CS%basal_traction(i,j) = ((G%areaT(i,j) * CS%C_basal_friction(i,j)) * & + (unorm**(CS%n_basal_fric-1.0) / (1.0 + fB * unorm**CS%CF_PostPeak)**(CS%n_basal_fric))) * & + (US%Pa_to_RLZ_T2*US%L_T_to_m_s) else - !linear (CS%n_basal_fric=1) or "Weertman"/power-law (CS%n_basal_fric .ne. 1) - CS%basal_traction(i,j) = G%areaT(i,j) * CS%C_basal_friction(i,j) * unorm**(CS%n_basal_fric-1) + !linear (CS%n_basal_fric=1) or "Weertman"/power-law (CS%n_basal_fric /= 1) + CS%basal_traction(i,j) = ((G%areaT(i,j) * CS%C_basal_friction(i,j)) * (unorm**(CS%n_basal_fric-1))) * & + (US%Pa_to_RLZ_T2*US%L_T_to_m_s) endif endif enddo @@ -3353,8 +3358,8 @@ subroutine bilinear_shape_fn_grid(G, i, j, Phi) xexp = xquad(qpoint) endif - Phi(2*node-1,qpoint) = ( d * (2 * xnode - 3) * yexp ) / (a*d) - Phi(2*node,qpoint) = ( a * (2 * ynode - 3) * xexp ) / (a*d) + Phi(2*node-1,qpoint) = ( (d * (2 * xnode - 3)) * yexp ) / (a*d) + Phi(2*node,qpoint) = ( (a * (2 * ynode - 3)) * xexp ) / (a*d) enddo enddo @@ -3400,15 +3405,15 @@ subroutine bilinear_shape_fn_grid_1qp(G, i, j, Phi) do node=1,4 xnode = 2-mod(node,2) ; ynode = ceiling(REAL(node)/2) - Phi(2*node-1) = ( d * (2 * xnode - 3) * yexp ) / (a*d) - Phi(2*node) = ( a * (2 * ynode - 3) * xexp ) / (a*d) + Phi(2*node-1) = ( (d * (2 * xnode - 3)) * yexp ) / (a*d) + Phi(2*node) = ( (a * (2 * ynode - 3)) * xexp ) / (a*d) enddo end subroutine bilinear_shape_fn_grid_1qp subroutine bilinear_shape_functions_subgrid(Phisub, nsub) integer, intent(in) :: nsub !< The number of subgridscale quadrature locations in each direction - real, dimension(nsub,nsub,2,2,2,2), & + real, dimension(2,2,nsub,nsub,2,2), & intent(inout) :: Phisub !< Quadrature structure weights at subgridscale !! locations for finite element calculations [nondim] @@ -3420,13 +3425,13 @@ subroutine bilinear_shape_functions_subgrid(Phisub, nsub) ! i think this general approach may not work for nonrectangular elements... ! - ! Phisub(i,j,k,l,q1,q2) + ! Phisub(q1,q2,i,j,k,l) + ! q1: quad point x-index + ! q2: quad point y-index ! i: subgrid index in x-direction ! j: subgrid index in y-direction ! k: basis function x-index ! l: basis function y-index - ! q1: quad point x-index - ! q2: quad point y-index ! e.g. k=1,l=1 => node 1 ! q1=2,q2=1 => quad point 2 @@ -3447,10 +3452,10 @@ subroutine bilinear_shape_functions_subgrid(Phisub, nsub) do qy=1,2 ; do qx=1,2 x = x0 + fracx*xquad(qx) y = y0 + fracx*xquad(qy) - Phisub(i,j,1,1,qx,qy) = (1.0-x) * (1.0-y) - Phisub(i,j,1,2,qx,qy) = (1.0-x) * y - Phisub(i,j,2,1,qx,qy) = x * (1.0-y) - Phisub(i,j,2,2,qx,qy) = x * y + Phisub(qx,qy,i,j,1,1) = (1.0-x) * (1.0-y) + Phisub(qx,qy,i,j,1,2) = (1.0-x) * y + Phisub(qx,qy,i,j,2,1) = x * (1.0-y) + Phisub(qx,qy,i,j,2,2) = x * y enddo ; enddo enddo ; enddo @@ -3623,8 +3628,8 @@ subroutine interpolate_H_to_B(G, h_shelf, hmask, H_node) intent(inout) :: H_node !< The ice shelf thickness at nodal (corner) !! points [Z ~> m]. - integer :: i, j, isc, iec, jsc, jec, num_h, k, l - real :: summ + integer :: i, j, isc, iec, jsc, jec, num_h, k, l, ic, jc + real :: h_arr(2,2) isc = G%isc ; jsc = G%jsc ; iec = G%iec ; jec = G%jec @@ -3635,19 +3640,18 @@ subroutine interpolate_H_to_B(G, h_shelf, hmask, H_node) do j=jsc-1,jec do i=isc-1,iec - summ = 0.0 num_h = 0 - do k=0,1 - do l=0,1 - if (hmask(i+k,j+l) == 1.0 .or. hmask(i+k,j+l) == 3.0) then - summ = summ + h_shelf(i+k,j+l) - num_h = num_h + 1 - endif - enddo - enddo - if (num_h > 0) then - H_node(i,j) = summ / num_h - endif + do l=1,2; jc=j-1+l; do k=1,2; ic=i-1+k + if (hmask(ic,jc) == 1.0 .or. hmask(ic,jc) == 3.0) then + h_arr(k,l)=h_shelf(ic,jc) + num_h = num_h + 1 + else + h_arr(k,l)=0.0 + endif + if (num_h > 0) then + H_node(i,j) = ((h_arr(1,1)+h_arr(2,2))+(h_arr(1,2)+h_arr(2,1))) / num_h + endif + enddo; enddo enddo enddo @@ -3667,9 +3671,11 @@ subroutine ice_shelf_dyn_end(CS) deallocate(CS%u_bdry_val, CS%v_bdry_val) deallocate(CS%u_face_mask, CS%v_face_mask) deallocate(CS%umask, CS%vmask) + deallocate(CS%u_face_mask_bdry, CS%v_face_mask_bdry) + deallocate(CS%h_bdry_val) + deallocate(CS%float_cond) deallocate(CS%ice_visc, CS%AGlen_visc) - deallocate(CS%Ee) deallocate(CS%basal_traction,CS%C_basal_friction) deallocate(CS%OD_rt, CS%OD_av) deallocate(CS%t_bdry_val, CS%bed_elev) diff --git a/src/ice_shelf/MOM_ice_shelf_initialize.F90 b/src/ice_shelf/MOM_ice_shelf_initialize.F90 index 1e2076f889..f976187c2b 100644 --- a/src/ice_shelf/MOM_ice_shelf_initialize.F90 +++ b/src/ice_shelf/MOM_ice_shelf_initialize.F90 @@ -274,8 +274,7 @@ end subroutine initialize_ice_thickness_channel !> Initialize ice shelf boundary conditions for a channel configuration subroutine initialize_ice_shelf_boundary_channel(u_face_mask_bdry, v_face_mask_bdry, & u_flux_bdry_val, v_flux_bdry_val, u_bdry_val, v_bdry_val, u_shelf, v_shelf, h_bdry_val, & - thickness_bdry_val, hmask, h_shelf, G,& - US, PF ) + hmask, h_shelf, G, US, PF ) type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure real, dimension(SZIB_(G),SZJB_(G)), & @@ -299,10 +298,6 @@ subroutine initialize_ice_shelf_boundary_channel(u_face_mask_bdry, v_face_mask_b intent(inout) :: u_shelf !< The zonal ice shelf velocity [L T-1 ~> m s-1]. real, dimension(SZIB_(G),SZJB_(G)), & intent(inout) :: v_shelf !< The meridional ice shelf velocity [L T-1 ~> m s-1]. - real, dimension(SZDI_(G),SZDJ_(G)), & - intent(inout) :: thickness_bdry_val !< The ice shelf thickness at open boundaries [Z ~> m] - !! boundary vertices [L T-1 ~> m s-1]. - real, dimension(SZDI_(G),SZDJ_(G)), & intent(inout) :: h_bdry_val !< The ice shelf thickness at open boundaries [Z ~> m] real, dimension(SZDI_(G),SZDJ_(G)), & @@ -350,8 +345,13 @@ subroutine initialize_ice_shelf_boundary_channel(u_face_mask_bdry, v_face_mask_b if (G%geoLonBu(i,j) == westlon) then hmask(i+1,j) = 3.0 - h_bdry_val(i+1,j) = h_shelf(i+1,j) - thickness_bdry_val(i+1,j) = h_bdry_val(i+0*1,j) + !--- + !OLD: thickness_bdry_val was used for ice dynamics, and h_bdry_val was not used anywhere except here: + !h_bdry_val(i+1,j) = h_shelf(i+1,j) ; thickness_bdry_val(i+1,j) = h_bdry_val(i+0*1,j) + !--- + !NEW: h_bdry_val is used for ice dynamics instead of thickness_bdry_val, which was removed + h_bdry_val(i+1,j) = h_shelf(i+0*1,j) !why 0*1 + !--- u_face_mask_bdry(i+1,j) = 5.0 u_bdry_val(i+1,j) = input_vel*(1-16.0*((G%geoLatBu(i-1,j)/lenlat-0.5))**4) !velocity distribution endif @@ -393,8 +393,6 @@ end subroutine initialize_ice_shelf_boundary_channel !> Initialize ice shelf flow from file subroutine initialize_ice_flow_from_file(bed_elev,u_shelf, v_shelf,float_cond,& G, US, PF) -!subroutine initialize_ice_flow_from_file(bed_elev,u_shelf, v_shelf,float_cond,ice_visc,& -! G, US, PF) type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure real, dimension(SZDI_(G),SZDJ_(G)), & intent(inout) :: bed_elev !< The bed elevation [Z ~> m]. @@ -412,9 +410,8 @@ subroutine initialize_ice_flow_from_file(bed_elev,u_shelf, v_shelf,float_cond,& ! h_shelf [Z ~> m] and area_shelf_h [L2 ~> m2] (and dimensionless) and updates hmask character(len=200) :: filename,vel_file,inputdir,bed_topo_file ! Strings for file/path character(len=200) :: ushelf_varname, vshelf_varname, & - ice_visc_varname, floatfr_varname, bed_varname ! Variable name in file + floatfr_varname, bed_varname ! Variable name in file character(len=40) :: mdl = "initialize_ice_velocity_from_file" ! This subroutine's name. - real :: len_sidestress call MOM_mesg(" MOM_ice_shelf_init_profile.F90, initialize_velocity_from_file: reading velocity") @@ -423,9 +420,6 @@ subroutine initialize_ice_flow_from_file(bed_elev,u_shelf, v_shelf,float_cond,& call get_param(PF, mdl, "ICE_VELOCITY_FILE", vel_file, & "The file from which the velocity is read.", & default="ice_shelf_vel.nc") - call get_param(PF, mdl, "LEN_SIDE_STRESS", len_sidestress, & - "position past which shelf sides are stress free.", & - default=0.0, units="axis_units") filename = trim(inputdir)//trim(vel_file) call log_param(PF, mdl, "INPUTDIR/THICKNESS_FILE", filename) @@ -435,9 +429,6 @@ subroutine initialize_ice_flow_from_file(bed_elev,u_shelf, v_shelf,float_cond,& call get_param(PF, mdl, "ICE_V_VEL_VARNAME", vshelf_varname, & "The name of the v velocity variable in ICE_VELOCITY_FILE.", & default="v_shelf") - call get_param(PF, mdl, "ICE_VISC_VARNAME", ice_visc_varname, & - "The name of the ice viscosity variable in ICE_VELOCITY_FILE.", & - default="viscosity") call get_param(PF, mdl, "ICE_FLOAT_FRAC_VARNAME", floatfr_varname, & "The name of the ice float fraction (grounding fraction) variable in ICE_VELOCITY_FILE.", & default="float_frac") @@ -462,7 +453,7 @@ end subroutine initialize_ice_flow_from_file !> Initialize ice shelf b.c.s from file subroutine initialize_ice_shelf_boundary_from_file(u_face_mask_bdry, v_face_mask_bdry, & - u_bdry_val, v_bdry_val, umask, vmask, h_bdry_val, thickness_bdry_val, & + u_bdry_val, v_bdry_val, umask, vmask, h_bdry_val, & hmask, h_shelf, G, US, PF ) type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure @@ -480,8 +471,6 @@ subroutine initialize_ice_shelf_boundary_from_file(u_face_mask_bdry, v_face_mask intent(inout) :: umask !< A mask for ice shelf velocity [nondim] real, dimension(SZDIB_(G),SZDJB_(G)), & intent(inout) :: vmask !< A mask for ice shelf velocity [nondim] - real, dimension(SZDI_(G),SZDJ_(G)), & - intent(inout) :: thickness_bdry_val !< The ice shelf thickness at open boundaries [Z ~> m] real, dimension(SZDI_(G),SZDJ_(G)), & intent(inout) :: h_bdry_val !< The ice shelf thickness at open boundaries [Z ~> m] real, dimension(SZDI_(G),SZDJ_(G)), & @@ -501,7 +490,6 @@ subroutine initialize_ice_shelf_boundary_from_file(u_face_mask_bdry, v_face_mask integer :: i, j, isc, jsc, iec, jec h_bdry_val(:,:) = 0. - thickness_bdry_val(:,:) = 0. call MOM_mesg(" MOM_ice_shelf_init_profile.F90, initialize_b_c_s_from_file: reading b.c.s") @@ -542,9 +530,9 @@ subroutine initialize_ice_shelf_boundary_from_file(u_face_mask_bdry, v_face_mask call MOM_read_data(filename, trim(ufcmskbdry_varname), u_face_mask_bdry, G%Domain, position=CORNER, & - scale=US%m_s_to_L_T) + scale=1.) call MOM_read_data(filename, trim(vfcmskbdry_varname), v_face_mask_bdry, G%Domain, position=CORNER, & - scale=US%m_s_to_L_T) + scale=1.) call MOM_read_data(filename, trim(ubdryv_varname), u_bdry_val, G%Domain, position=CORNER, scale=US%m_s_to_L_T) call MOM_read_data(filename, trim(vbdryv_varname), v_bdry_val, G%Domain, position=CORNER, scale=US%m_s_to_L_T) call MOM_read_data(filename, trim(umask_varname), umask, G%Domain, position=CORNER, scale=1.) @@ -557,7 +545,6 @@ subroutine initialize_ice_shelf_boundary_from_file(u_face_mask_bdry, v_face_mask do j=jsc,jec do i=isc,iec if (hmask(i,j) == 3.) then - thickness_bdry_val(i,j) = h_shelf(i,j) h_bdry_val(i,j) = h_shelf(i,j) endif enddo @@ -587,7 +574,7 @@ subroutine initialize_ice_C_basal_friction(C_basal_friction, G, US, PF) if (trim(config)=="CONSTANT") then call get_param(PF, mdl, "BASAL_FRICTION_COEFF", C_friction, & - "Coefficient in sliding law.", units="Pa (m s-1)^(n_basal_fric)", default=5.e10) + "Coefficient in sliding law.", units="Pa (s m-1)^(n_basal_fric)", default=5.e10) C_basal_friction(:,:) = C_friction elseif (trim(config)=="FILE") then @@ -615,10 +602,13 @@ subroutine initialize_ice_C_basal_friction(C_basal_friction, G, US, PF) !> Initialize ice-stiffness parameter -subroutine initialize_ice_AGlen(AGlen, G, US, PF) +subroutine initialize_ice_AGlen(AGlen, ice_viscosity_compute, G, US, PF) type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure real, dimension(SZDI_(G),SZDJ_(G)), & intent(inout) :: AGlen !< The ice-stiffness parameter A_Glen, often in [Pa-3 s-1] + character(len=40) :: ice_viscosity_compute !< Specifies whether the ice viscosity is computed internally + !! according to Glen's flow law; is constant (for debugging purposes) + !! or using observed strain rates and read from a file type(unit_scale_type), intent(in) :: US !< A structure containing unit conversion factors type(param_file_type), intent(in) :: PF !< A structure to parse for run-time parameters @@ -635,7 +625,7 @@ subroutine initialize_ice_AGlen(AGlen, G, US, PF) if (trim(config)=="CONSTANT") then call get_param(PF, mdl, "A_GLEN", A_Glen, & - "Ice-stiffness parameter.", units="Pa-3 s-1", default=2.261e-25) + "Ice-stiffness parameter.", units="Pa-n_g s-1", default=2.261e-25) AGlen(:,:) = A_Glen @@ -655,8 +645,14 @@ subroutine initialize_ice_AGlen(AGlen, G, US, PF) if (.not.file_exists(filename, G%Domain)) call MOM_error(FATAL, & " initialize_ice_stiffness_from_file: Unable to open "//trim(filename)) - call MOM_read_data(filename,trim(varname), AGlen, G%Domain) + if (trim(ice_viscosity_compute) == "OBS") then + !AGlen is the ice viscosity [Pa s ~> R L2 T-1] computed from obs and read from a file + call MOM_read_data(filename, trim(varname), AGlen, G%Domain, scale=US%Pa_to_RL2_T2*US%s_to_T) + else + !AGlen is the ice stiffness parameter [Pa-n_g s-1] + call MOM_read_data(filename, trim(varname), AGlen, G%Domain) + endif endif end subroutine initialize_ice_AGlen @@ -681,7 +677,7 @@ subroutine initialize_ice_SMB(SMB, G, US, PF) if (trim(config)=="CONSTANT") then call get_param(PF, mdl, "SMB", SMB_val, & - "Surface mass balance.", units="kg m-2 s-1", default=0.0) + "Surface mass balance.", units="kg m-2 s-1", default=0.0, scale=US%kg_m2s_to_RZ_T) SMB(:,:) = SMB_val @@ -701,7 +697,7 @@ subroutine initialize_ice_SMB(SMB, G, US, PF) if (.not.file_exists(filename, G%Domain)) call MOM_error(FATAL, & " initialize_ice_SMV_from_file: Unable to open "//trim(filename)) - call MOM_read_data(filename,trim(varname), SMB, G%Domain) + call MOM_read_data(filename,trim(varname), SMB, G%Domain, scale=US%kg_m2s_to_RZ_T) endif end subroutine initialize_ice_SMB From b0ff6bd18feb797e146fc574bb1fb29ecad8cc2c Mon Sep 17 00:00:00 2001 From: alex-huth Date: Mon, 27 Nov 2023 18:58:38 -0500 Subject: [PATCH 14/22] fixed documentation of inputs to subroutine sum_square_matrix --- src/ice_shelf/MOM_ice_shelf_dynamics.F90 | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/ice_shelf/MOM_ice_shelf_dynamics.F90 b/src/ice_shelf/MOM_ice_shelf_dynamics.F90 index 4bfcc3605c..7a92b679f8 100644 --- a/src/ice_shelf/MOM_ice_shelf_dynamics.F90 +++ b/src/ice_shelf/MOM_ice_shelf_dynamics.F90 @@ -2683,8 +2683,8 @@ end subroutine CG_action_subgrid_basal !! Returns the sum of the elements in a square matrix. This sum is bitwise identical even if the matrices are rotated. subroutine sum_square_matrix(sum_out, mat_in, n) integer, intent(in) :: n !< The length and width of each matrix in mat_in - real, dimension(n,n), intent(in) :: mat_in !< The four n x n matrices to be summed individually - real, intent(out) :: sum_out !< The sums of each of the 4 matrices given in mat_in + real, dimension(n,n), intent(in) :: mat_in !< The n x n matrix whose elements will be summed + real, intent(out) :: sum_out !< The sum of the elements of matrix mat_in integer :: s0,e0,s1,e1 sum_out=0.0 From f7233e058eea1ae775a01a99d6b0dbc466a5e6a9 Mon Sep 17 00:00:00 2001 From: alex-huth Date: Thu, 30 Nov 2023 14:34:09 -0500 Subject: [PATCH 15/22] Optimized sub-cell grounding subroutines, increasing computational efficiency --- src/ice_shelf/MOM_ice_shelf_dynamics.F90 | 49 +++++++++++++----------- 1 file changed, 27 insertions(+), 22 deletions(-) diff --git a/src/ice_shelf/MOM_ice_shelf_dynamics.F90 b/src/ice_shelf/MOM_ice_shelf_dynamics.F90 index 7a92b679f8..d1efc4599d 100644 --- a/src/ice_shelf/MOM_ice_shelf_dynamics.F90 +++ b/src/ice_shelf/MOM_ice_shelf_dynamics.F90 @@ -2640,6 +2640,8 @@ subroutine CG_action_subgrid_basal(Phisub, H, U, V, bathyT, dens_ratio, Ucontr, real, dimension(SIZE(Phisub,3),SIZE(Phisub,3),2,2) :: Ucontr_sub, Vcontr_sub ! The contributions to Ucontr and Vcontr !! at each sub-cell + real, dimension(2,2,SIZE(Phisub,3),SIZE(Phisub,3)) :: uloc_arr !The local sub-cell u-velocity [L T-1 ~> m s-1] + real, dimension(2,2,SIZE(Phisub,3),SIZE(Phisub,3)) :: vloc_arr !The local sub-cell v-velocity [L T-1 ~> m s-1] real, dimension(2,2) :: Ucontr_q, Vcontr_q !Contributions to a node from each quadrature point in a sub-grid cell real :: subarea ! The fractional sub-cell area [nondim] real :: hloc ! The local sub-cell ice thickness [Z ~> m] @@ -2648,22 +2650,24 @@ subroutine CG_action_subgrid_basal(Phisub, H, U, V, bathyT, dens_ratio, Ucontr, nsub = size(Phisub,3) subarea = 1.0 / (nsub**2) + uloc_arr(:,:,:,:) = 0.0; vloc_arr(:,:,:,:)=0.0 + + do j=1,nsub ; do i=1,nsub; do qy=1,2 ; do qx=1,2 + hloc = (Phisub(qx,qy,i,j,1,1)*H(1,1) + Phisub(qx,qy,i,j,2,2)*H(2,2)) + & + (Phisub(qx,qy,i,j,1,2)*H(1,2) + Phisub(qx,qy,i,j,2,1)*H(2,1)) + if (dens_ratio * hloc - bathyT > 0) then + uloc_arr(qx,qy,i,j) = ((Phisub(qx,qy,i,j,1,1) * U(1,1) + Phisub(qx,qy,i,j,2,2) * U(2,2)) + & + (Phisub(qx,qy,i,j,1,2) * U(1,2) + Phisub(qx,qy,i,j,2,1) * U(2,1))) + vloc_arr(qx,qy,i,j) = ((Phisub(qx,qy,i,j,1,1) * V(1,1) + Phisub(qx,qy,i,j,2,2) * V(2,2)) + & + (Phisub(qx,qy,i,j,1,2) * V(1,2) + Phisub(qx,qy,i,j,2,1) * V(2,1))) + endif + enddo; enddo ; enddo ; enddo + do n=1,2 ; do m=1,2 ; do j=1,nsub ; do i=1,nsub do qy=1,2 ; do qx=1,2 !calculate quadrature point contributions for the sub-cell, to each node - hloc = (Phisub(qx,qy,i,j,1,1)*H(1,1) + Phisub(qx,qy,i,j,2,2)*H(2,2)) + & - (Phisub(qx,qy,i,j,1,2)*H(1,2) + Phisub(qx,qy,i,j,2,1)*H(2,1)) - - if (dens_ratio * hloc - bathyT > 0) then - Ucontr_q(qx,qy) = Phisub(qx,qy,i,j,m,n) * & - ((Phisub(qx,qy,i,j,1,1) * U(1,1) + Phisub(qx,qy,i,j,2,2) * U(2,2)) + & - (Phisub(qx,qy,i,j,1,2) * U(1,2) + Phisub(qx,qy,i,j,2,1) * U(2,1))) - Vcontr_q(qx,qy) = Phisub(qx,qy,i,j,m,n) * & - ((Phisub(qx,qy,i,j,1,1) * V(1,1) + Phisub(qx,qy,i,j,2,2) * V(2,2)) + & - (Phisub(qx,qy,i,j,1,2) * V(1,2) + Phisub(qx,qy,i,j,2,1) * V(2,1))) - else - Ucontr_q(qx,qy) = 0.0; Vcontr_q(qx,qy) = 0.0 - endif + Ucontr_q(qx,qy) = Phisub(qx,qy,i,j,m,n) * uloc_arr(qx,qy,i,j) + Vcontr_q(qx,qy) = Phisub(qx,qy,i,j,m,n) * vloc_arr(qx,qy,i,j) enddo; enddo !calculate sub-cell contribution to each node by summing up quadrature point contributions from the sub-cell @@ -2891,6 +2895,7 @@ subroutine CG_diagonal_subgrid_basal (Phisub, H_node, bathyT, dens_ratio, f_grnd real, dimension(SIZE(Phisub,3),SIZE(Phisub,3),2,2) :: f_grnd_sub ! The contributions to nodal f_grnd !! from each sub-cell + integer, dimension(2,2,SIZE(Phisub,3),SIZE(Phisub,3)) :: grnd_stat !0 at floating quad points, 1 at grounded real, dimension(2,2) :: f_grnd_q !Contributions to a node from each quadrature point in a sub-grid cell real :: subarea ! The fractional sub-cell area [nondim] real :: hloc ! The local sub-region thickness [Z ~> m] @@ -2899,17 +2904,17 @@ subroutine CG_diagonal_subgrid_basal (Phisub, H_node, bathyT, dens_ratio, f_grnd nsub = size(Phisub,3) subarea = 1.0 / (nsub**2) + grnd_stat(:,:,:,:)=0 + + do j=1,nsub ; do i=1,nsub; do qy=1,2 ; do qx=1,2 + hloc = (Phisub(qx,qy,i,j,1,1)*H_node(1,1) + Phisub(qx,qy,i,j,2,2)*H_node(2,2)) + & + (Phisub(qx,qy,i,j,1,2)*H_node(1,2) + Phisub(qx,qy,i,j,2,1)*H_node(2,1)) + if (dens_ratio * hloc - bathyT > 0) grnd_stat(qx,qy,i,j) = 1 + enddo; enddo ; enddo ; enddo + do n=1,2 ; do m=1,2 ; do j=1,nsub ; do i=1,nsub do qy=1,2 ; do qx = 1,2 - !calculate quadrature point contributions for the sub-cell, to each node - hloc = (Phisub(qx,qy,i,j,1,1)*H_node(1,1) + Phisub(qx,qy,i,j,2,2)*H_node(2,2)) + & - (Phisub(qx,qy,i,j,1,2)*H_node(1,2) + Phisub(qx,qy,i,j,2,1)*H_node(2,1)) - - if (dens_ratio * hloc - bathyT > 0) then - f_grnd_q(qx,qy) = Phisub(qx,qy,i,j,m,n)**2 - else - f_grnd_q(qx,qy) = 0.0 - endif + f_grnd_q(qx,qy) = grnd_stat(qx,qy,i,j) * Phisub(qx,qy,i,j,m,n)**2 enddo ; enddo !calculate sub-cell contribution to each node by summing up quadrature point contributions from the sub-cell f_grnd_sub(i,j,m,n) = (subarea * 0.25) * ((f_grnd_q(1,1) + f_grnd_q(2,2)) + (f_grnd_q(1,2)+f_grnd_q(2,1))) From d7096bdd26b8998bcef069e001be6fa8a08f06af Mon Sep 17 00:00:00 2001 From: alex-huth Date: Tue, 19 Dec 2023 16:49:35 -0500 Subject: [PATCH 16/22] fixed documented units of fN and fN_scale for ice shelf coulomb friction law --- src/ice_shelf/MOM_ice_shelf_dynamics.F90 | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/ice_shelf/MOM_ice_shelf_dynamics.F90 b/src/ice_shelf/MOM_ice_shelf_dynamics.F90 index d1efc4599d..ec49081baf 100644 --- a/src/ice_shelf/MOM_ice_shelf_dynamics.F90 +++ b/src/ice_shelf/MOM_ice_shelf_dynamics.F90 @@ -3071,9 +3071,9 @@ subroutine calc_shelf_taub(CS, ISS, G, US, u_shlf, v_shlf) real :: umid, vmid, unorm, eps_min ! Velocities [L T-1 ~> m s-1] real :: alpha !Coulomb coefficient [nondim] real :: Hf !"floatation thickness" for Coulomb friction [Z ~> m] - real :: fN !Effective pressure (ice pressure - ocean pressure) for Coulomb friction [R L2 T-2 ~> Pa] + real :: fN !Effective pressure (ice pressure - ocean pressure) for Coulomb friction [Pa] real :: fB !for Coulomb Friction [(T L-1)^CS%CF_PostPeak ~> (s m-1)^CS%CF_PostPeak] - real :: fN_scale !To convert effective pressure to mks units during Coulomb friction + real :: fN_scale !To convert effective pressure to mks units during Coulomb friction [Pa T2 R-1 L-2 ~> 1] isc = G%isc ; jsc = G%jsc ; iec = G%iec ; jec = G%jec iscq = G%iscB ; iecq = G%iecB ; jscq = G%jscB ; jecq = G%jecB From 90de5de86820a4f4384e5e504769e7b6b53f9b57 Mon Sep 17 00:00:00 2001 From: Robert Hallberg Date: Fri, 15 Dec 2023 16:44:47 -0500 Subject: [PATCH 17/22] Rename u arg to step_MOM_dyn_split_RK2 as u_inst Renamed the arguments u and v to step_MOM_dyn_split_RK2 as u_inst and v_inst to more clearly differentiate between the instantaneous velocities (u_inst and v_inst) and the velocities with a time-averaged phase in the barotropic mode (u_av and v_av). A comment is also added at one point where the wrong velocities are being used to calculate and apply the Orlanski-style radiation open boundary conditions, with the intention of adding the option to correct this in a subsequent commit. This commit only changes the name of a pair of internal variables in one routine, and all answers are bitwise identical. --- src/core/MOM_dynamics_split_RK2.F90 | 89 ++++++++++++++--------------- 1 file changed, 43 insertions(+), 46 deletions(-) diff --git a/src/core/MOM_dynamics_split_RK2.F90 b/src/core/MOM_dynamics_split_RK2.F90 index debc63cb46..11b1eb5c16 100644 --- a/src/core/MOM_dynamics_split_RK2.F90 +++ b/src/core/MOM_dynamics_split_RK2.F90 @@ -70,7 +70,7 @@ module MOM_dynamics_split_RK2 use MOM_vert_friction, only : updateCFLtruncationValue, vertFPmix use MOM_verticalGrid, only : verticalGrid_type, get_thickness_units use MOM_verticalGrid, only : get_flux_units, get_tr_flux_units -use MOM_wave_interface, only: wave_parameters_CS, Stokes_PGF +use MOM_wave_interface, only : wave_parameters_CS, Stokes_PGF use MOM_CVMix_KPP, only : KPP_get_BLD, KPP_CS use MOM_energetic_PBL, only : energetic_PBL_get_MLD, energetic_PBL_CS use MOM_diabatic_driver, only : diabatic_CS, extract_diabatic_member @@ -284,16 +284,16 @@ module MOM_dynamics_split_RK2 contains !> RK2 splitting for time stepping MOM adiabatic dynamics -subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, Time_local, dt, forces, p_surf_begin, p_surf_end, & - uh, vh, uhtr, vhtr, eta_av, G, GV, US, CS, calc_dtbt, VarMix, & - MEKE, thickness_diffuse_CSp, pbv, Waves) +subroutine step_MOM_dyn_split_RK2(u_inst, v_inst, h, tv, visc, Time_local, dt, forces, & + p_surf_begin, p_surf_end, uh, vh, uhtr, vhtr, eta_av, G, GV, US, CS, & + calc_dtbt, VarMix, MEKE, thickness_diffuse_CSp, pbv, Waves) type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & - target, intent(inout) :: u !< Zonal velocity [L T-1 ~> m s-1] + target, intent(inout) :: u_inst !< Instantaneous zonal velocity [L T-1 ~> m s-1] real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & - target, intent(inout) :: v !< Meridional velocity [L T-1 ~> m s-1] + target, intent(inout) :: v_inst !< Instantaneous meridional velocity [L T-1 ~> m s-1] real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & intent(inout) :: h !< Layer thickness [H ~> m or kg m-2] type(thermo_var_ptrs), intent(in) :: tv !< Thermodynamic type @@ -355,9 +355,9 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, Time_local, dt, forces, p_s ! height or column mass [H T-1 ~> m s-1 or kg m-2 s-1] real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: u_old_rad_OBC ! The starting zonal velocities, which are - ! saved for use in the Flather open boundary condition code [L T-1 ~> m s-1] + ! saved for use in the radiation open boundary condition code [L T-1 ~> m s-1] real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: v_old_rad_OBC ! The starting meridional velocities, which are - ! saved for use in the Flather open boundary condition code [L T-1 ~> m s-1] + ! saved for use in the radiation open boundary condition code [L T-1 ~> m s-1] ! GMM, TODO: make these allocatable? real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: uold ! u-velocity before vert_visc is applied, for fpmix @@ -423,8 +423,8 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, Time_local, dt, forces, p_s call updateCFLtruncationValue(Time_local, CS%vertvisc_CSp, US) if (CS%debug) then - call MOM_state_chksum("Start predictor ", u, v, h, uh, vh, G, GV, US, symmetric=sym) - call check_redundant("Start predictor u ", u, v, G, unscale=US%L_T_to_m_s) + call MOM_state_chksum("Start predictor ", u_inst, v_inst, h, uh, vh, G, GV, US, symmetric=sym) + call check_redundant("Start predictor u ", u_inst, v_inst, G, unscale=US%L_T_to_m_s) call check_redundant("Start predictor uh ", uh, vh, G, unscale=GV%H_to_MKS*US%L_to_m**2*US%s_to_T) endif @@ -475,7 +475,7 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, Time_local, dt, forces, p_s call create_group_pass(CS%pass_hp_uv, u_av, v_av, G%Domain, halo=max(2,obc_stencil)) call create_group_pass(CS%pass_hp_uv, uh(:,:,:), vh(:,:,:), G%Domain, halo=max(2,obc_stencil)) - call create_group_pass(CS%pass_uv, u, v, G%Domain, halo=max(2,cont_stencil)) + call create_group_pass(CS%pass_uv, u_inst, v_inst, G%Domain, halo=max(2,cont_stencil)) call create_group_pass(CS%pass_h, h, G%Domain, halo=max(2,cont_stencil)) call create_group_pass(CS%pass_av_uvh, u_av, v_av, G%Domain, halo=max(2,obc_stencil)) call create_group_pass(CS%pass_av_uvh, uh(:,:,:), vh(:,:,:), G%Domain, halo=max(2,obc_stencil)) @@ -503,7 +503,7 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, Time_local, dt, forces, p_s if (Use_Stokes_PGF) Use_Stokes_PGF = Waves%Stokes_PGF if (Use_Stokes_PGF) then call thickness_to_dz(h, tv, dz, G, GV, US, halo_size=1) - call Stokes_PGF(G, GV, US, dz, u, v, CS%PFu_Stokes, CS%PFv_Stokes, Waves) + call Stokes_PGF(G, GV, US, dz, u_inst, v_inst, CS%PFu_Stokes, CS%PFv_Stokes, Waves) ! We are adding Stokes_PGF to hydrostatic PGF here. The diag PFu/PFv ! will therefore report the sum total PGF and we avoid other @@ -576,15 +576,15 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, Time_local, dt, forces, p_s !$OMP parallel do default(shared) do k=1,nz do j=js,je ; do I=Isq,Ieq - up(I,j,k) = G%mask2dCu(I,j) * (u(I,j,k) + dt * u_bc_accel(I,j,k)) + up(I,j,k) = G%mask2dCu(I,j) * (u_inst(I,j,k) + dt * u_bc_accel(I,j,k)) enddo ; enddo do J=Jsq,Jeq ; do i=is,ie - vp(i,J,k) = G%mask2dCv(i,J) * (v(i,J,k) + dt * v_bc_accel(i,J,k)) + vp(i,J,k) = G%mask2dCv(i,J) * (v_inst(i,J,k) + dt * v_bc_accel(i,J,k)) enddo ; enddo enddo call enable_averages(dt, Time_local, CS%diag) - call set_viscous_ML(u, v, h, tv, forces, visc, dt, G, GV, US, CS%set_visc_CSp) + call set_viscous_ML(u_inst, v_inst, h, tv, forces, visc, dt, G, GV, US, CS%set_visc_CSp) call disable_averaging(CS%diag) if (CS%debug) then @@ -628,7 +628,7 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, Time_local, dt, forces, p_s ! u_accel_bt = layer accelerations due to barotropic solver if (associated(CS%BT_cont) .or. CS%BT_use_layer_fluxes) then call cpu_clock_begin(id_clock_continuity) - call continuity(u, v, h, hp, uh_in, vh_in, dt, G, GV, US, CS%continuity_CSp, CS%OBC, pbv, & + call continuity(u_inst, v_inst, h, hp, uh_in, vh_in, dt, G, GV, US, CS%continuity_CSp, CS%OBC, pbv, & visc_rem_u=CS%visc_rem_u, visc_rem_v=CS%visc_rem_v, BT_cont=CS%BT_cont) call cpu_clock_end(id_clock_continuity) if (BT_cont_BT_thick) then @@ -639,7 +639,7 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, Time_local, dt, forces, p_s endif if (CS%BT_use_layer_fluxes) then - uh_ptr => uh_in ; vh_ptr => vh_in; u_ptr => u ; v_ptr => v + uh_ptr => uh_in ; vh_ptr => vh_in; u_ptr => u_inst ; v_ptr => v_inst endif call cpu_clock_begin(id_clock_btstep) @@ -647,7 +647,7 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, Time_local, dt, forces, p_s if (showCallTree) call callTree_enter("btstep(), MOM_barotropic.F90") ! This is the predictor step call to btstep. ! The CS%ADp argument here stores the weights for certain integrated diagnostics. - call btstep(u, v, eta, dt, u_bc_accel, v_bc_accel, forces, CS%pbce, CS%eta_PF, u_av, v_av, & + call btstep(u_inst, v_inst, eta, dt, u_bc_accel, v_bc_accel, forces, CS%pbce, CS%eta_PF, u_av, v_av, & CS%u_accel_bt, CS%v_accel_bt, eta_pred, CS%uhbt, CS%vhbt, G, GV, US, & CS%barotropic_CSp, CS%visc_rem_u, CS%visc_rem_v, SpV_avg, CS%ADp, CS%OBC, CS%BT_cont, & eta_PF_start, taux_bot, tauy_bot, uh_ptr, vh_ptr, u_ptr, v_ptr) @@ -661,11 +661,11 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, Time_local, dt, forces, p_s !$OMP parallel do default(shared) do k=1,nz do J=Jsq,Jeq ; do i=is,ie - vp(i,J,k) = G%mask2dCv(i,J) * (v(i,J,k) + dt_pred * & + vp(i,J,k) = G%mask2dCv(i,J) * (v_inst(i,J,k) + dt_pred * & (v_bc_accel(i,J,k) + CS%v_accel_bt(i,J,k))) enddo ; enddo do j=js,je ; do I=Isq,Ieq - up(I,j,k) = G%mask2dCu(I,j) * (u(I,j,k) + dt_pred * & + up(I,j,k) = G%mask2dCu(I,j) * (u_inst(I,j,k) + dt_pred * & (u_bc_accel(I,j,k) + CS%u_accel_bt(I,j,k))) enddo ; enddo enddo @@ -679,7 +679,7 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, Time_local, dt, forces, p_s ! call MOM_state_chksum("Predictor 1", up, vp, h, uh, vh, G, GV, US, haloshift=1) call MOM_accel_chksum("Predictor accel", CS%CAu_pred, CS%CAv_pred, CS%PFu, CS%PFv, & CS%diffu, CS%diffv, G, GV, US, CS%pbce, CS%u_accel_bt, CS%v_accel_bt, symmetric=sym) - call MOM_state_chksum("Predictor 1 init", u, v, h, uh, vh, G, GV, US, haloshift=1, & + call MOM_state_chksum("Predictor 1 init", u_inst, v_inst, h, uh, vh, G, GV, US, haloshift=1, & symmetric=sym) call check_redundant("Predictor 1 up", up, vp, G, unscale=US%L_T_to_m_s) call check_redundant("Predictor 1 uh", uh, vh, G, unscale=GV%H_to_MKS*US%L_to_m**2*US%s_to_T) @@ -809,7 +809,7 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, Time_local, dt, forces, p_s if (Use_Stokes_PGF) Use_Stokes_PGF = Waves%Stokes_PGF if (Use_Stokes_PGF) then call thickness_to_dz(h, tv, dz, G, GV, US, halo_size=1) - call Stokes_PGF(G, GV, US, dz, u, v, CS%PFu_Stokes, CS%PFv_Stokes, Waves) + call Stokes_PGF(G, GV, US, dz, u_inst, v_inst, CS%PFu_Stokes, CS%PFv_Stokes, Waves) if (.not.Waves%Passive_Stokes_PGF) then do k=1,nz do j=js,je ; do I=Isq,Ieq @@ -899,7 +899,7 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, Time_local, dt, forces, p_s if (showCallTree) call callTree_enter("btstep(), MOM_barotropic.F90") ! This is the corrector step call to btstep. - call btstep(u, v, eta, dt, u_bc_accel, v_bc_accel, forces, CS%pbce, CS%eta_PF, u_av, v_av, & + call btstep(u_inst, v_inst, eta, dt, u_bc_accel, v_bc_accel, forces, CS%pbce, CS%eta_PF, u_av, v_av, & CS%u_accel_bt, CS%v_accel_bt, eta_pred, CS%uhbt, CS%vhbt, G, GV, US, & CS%barotropic_CSp, CS%visc_rem_u, CS%visc_rem_v, SpV_avg, CS%ADp, CS%OBC, CS%BT_cont, & eta_PF_start, taux_bot, tauy_bot, uh_ptr, vh_ptr, u_ptr, v_ptr, etaav=eta_av) @@ -920,22 +920,22 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, Time_local, dt, forces, p_s !$OMP parallel do default(shared) do k=1,nz do j=js,je ; do I=Isq,Ieq - u(I,j,k) = G%mask2dCu(I,j) * (u(I,j,k) + dt * & + u_inst(I,j,k) = G%mask2dCu(I,j) * (u_inst(I,j,k) + dt * & (u_bc_accel(I,j,k) + CS%u_accel_bt(I,j,k))) enddo ; enddo do J=Jsq,Jeq ; do i=is,ie - v(i,J,k) = G%mask2dCv(i,J) * (v(i,J,k) + dt * & + v_inst(i,J,k) = G%mask2dCv(i,J) * (v_inst(i,J,k) + dt * & (v_bc_accel(i,J,k) + CS%v_accel_bt(i,J,k))) enddo ; enddo enddo call cpu_clock_end(id_clock_mom_update) if (CS%debug) then - call uvchksum("Corrector 1 [uv]", u, v, G%HI, haloshift=0, symmetric=sym, scale=US%L_T_to_m_s) + call uvchksum("Corrector 1 [uv]", u_inst, v_inst, G%HI, haloshift=0, symmetric=sym, scale=US%L_T_to_m_s) call hchksum(h, "Corrector 1 h", G%HI, haloshift=1, scale=GV%H_to_MKS) call uvchksum("Corrector 1 [uv]h", uh, vh, G%HI, haloshift=2, & symmetric=sym, scale=GV%H_to_MKS*US%L_to_m**2*US%s_to_T) - ! call MOM_state_chksum("Corrector 1", u, v, h, uh, vh, G, GV, US, haloshift=1) + ! call MOM_state_chksum("Corrector 1", u_inst, v_inst, h, uh, vh, G, GV, US, haloshift=1) call MOM_accel_chksum("Corrector accel", CS%CAu, CS%CAv, CS%PFu, CS%PFv, & CS%diffu, CS%diffv, G, GV, US, CS%pbce, CS%u_accel_bt, CS%v_accel_bt, & symmetric=sym) @@ -951,26 +951,26 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, Time_local, dt, forces, p_s do k = 1, nz do j = js , je do I = Isq, Ieq - uold(I,j,k) = u(I,j,k) + uold(I,j,k) = u_inst(I,j,k) enddo enddo do J = Jsq, Jeq do i = is, ie - vold(i,J,k) = v(i,J,k) + vold(i,J,k) = v_inst(i,J,k) enddo enddo enddo endif call thickness_to_dz(h, tv, dz, G, GV, US, halo_size=1) - call vertvisc_coef(u, v, h, dz, forces, visc, tv, dt, G, GV, US, CS%vertvisc_CSp, CS%OBC, VarMix) - call vertvisc(u, v, h, forces, visc, dt, CS%OBC, CS%ADp, CS%CDp, G, GV, US, & + call vertvisc_coef(u_inst, v_inst, h, dz, forces, visc, tv, dt, G, GV, US, CS%vertvisc_CSp, CS%OBC, VarMix) + call vertvisc(u_inst, v_inst, h, forces, visc, dt, CS%OBC, CS%ADp, CS%CDp, G, GV, US, & CS%vertvisc_CSp, CS%taux_bot, CS%tauy_bot,waves=waves) if (CS%fpmix) then - call vertFPmix(u, v, uold, vold, hbl, h, forces, dt, & + call vertFPmix(u_inst, v_inst, uold, vold, hbl, h, forces, dt, & G, GV, US, CS%vertvisc_CSp, CS%OBC) - call vertvisc(u, v, h, forces, visc, dt, CS%OBC, CS%ADp, CS%CDp, G, GV, US, & + call vertvisc(u_inst, v_inst, h, forces, visc, dt, CS%OBC, CS%ADp, CS%CDp, G, GV, US, & CS%vertvisc_CSp, CS%taux_bot, CS%tauy_bot, waves=waves) endif @@ -1000,7 +1000,7 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, Time_local, dt, forces, p_s ! h = h + dt * div . uh ! u_av and v_av adjusted so their mass transports match uhbt and vhbt. call cpu_clock_begin(id_clock_continuity) - call continuity(u, v, h, h, uh, vh, dt, G, GV, US, CS%continuity_CSp, CS%OBC, pbv, & + call continuity(u_inst, v_inst, h, h, uh, vh, dt, G, GV, US, CS%continuity_CSp, CS%OBC, pbv, & CS%uhbt, CS%vhbt, CS%visc_rem_u, CS%visc_rem_v, u_av, v_av) call cpu_clock_end(id_clock_continuity) call do_group_pass(CS%pass_h, G%Domain, clock=id_clock_pass) @@ -1016,7 +1016,9 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, Time_local, dt, forces, p_s endif if (associated(CS%OBC)) then - call radiation_open_bdry_conds(CS%OBC, u, u_old_rad_OBC, v, v_old_rad_OBC, G, GV, US, dt) + !### I suspect that there is a bug here when u_inst is compared with a previous value of u_av + ! to estimate the dominant outward group velocity, but a fix is not available yet. + call radiation_open_bdry_conds(CS%OBC, u_inst, u_old_rad_OBC, v_inst, v_old_rad_OBC, G, GV, US, dt) endif ! h_av = (h_in + h_out)/2 . Going in to this line, h_av = h_in. @@ -1156,7 +1158,7 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, Time_local, dt, forces, p_s if (CS%id_deta_dt > 0) call post_data(CS%id_deta_dt, deta_dt, CS%diag) if (CS%debug) then - call MOM_state_chksum("Corrector ", u, v, h, uh, vh, G, GV, US, symmetric=sym) + call MOM_state_chksum("Corrector ", u_inst, v_inst, h, uh, vh, G, GV, US, symmetric=sym) call uvchksum("Corrector avg [uv]", u_av, v_av, G%HI, haloshift=1, symmetric=sym, scale=US%L_T_to_m_s) call hchksum(h_av, "Corrector avg h", G%HI, haloshift=1, scale=GV%H_to_MKS) ! call MOM_state_chksum("Corrector avg ", u_av, v_av, h_av, uh, vh, G, GV, US) @@ -1471,8 +1473,7 @@ subroutine initialize_dyn_split_RK2(u, v, h, uh, vh, eta, Time, G, GV, US, param ! Accel_diag%u_accel_bt => CS%u_accel_bt ; Accel_diag%v_accel_bt => CS%v_accel_bt ! Accel_diag%u_av => CS%u_av ; Accel_diag%v_av => CS%v_av - id_clock_pass_init = cpu_clock_id('(Ocean init message passing)', & - grain=CLOCK_ROUTINE) + id_clock_pass_init = cpu_clock_id('(Ocean init message passing)', grain=CLOCK_ROUTINE) call continuity_init(Time, G, GV, US, param_file, diag, CS%continuity_CSp) cont_stencil = continuity_stencil(CS%continuity_CSp) @@ -1482,17 +1483,14 @@ subroutine initialize_dyn_split_RK2(u, v, h, uh, vh, eta, Time, G, GV, US, param call PressureForce_init(Time, G, GV, US, param_file, diag, CS%PressureForce_CSp, & CS%SAL_CSp, CS%tides_CSp) call hor_visc_init(Time, G, GV, US, param_file, diag, CS%hor_visc, ADp=CS%ADp) - call vertvisc_init(MIS, Time, G, GV, US, param_file, diag, CS%ADp, dirs, & - ntrunc, CS%vertvisc_CSp) + call vertvisc_init(MIS, Time, G, GV, US, param_file, diag, CS%ADp, dirs, ntrunc, CS%vertvisc_CSp) CS%set_visc_CSp => set_visc - call updateCFLtruncationValue(Time, CS%vertvisc_CSp, US, & - activate=is_new_run(restart_CS) ) + call updateCFLtruncationValue(Time, CS%vertvisc_CSp, US, activate=is_new_run(restart_CS) ) if (associated(ALE_CSp)) CS%ALE_CSp => ALE_CSp if (associated(OBC)) then CS%OBC => OBC - if (OBC%ramp) call update_OBC_ramp(Time, CS%OBC, US, & - activate=is_new_run(restart_CS) ) + if (OBC%ramp) call update_OBC_ramp(Time, CS%OBC, US, activate=is_new_run(restart_CS) ) endif if (associated(update_OBC_CSp)) CS%update_OBC_CSp => update_OBC_CSp @@ -1515,8 +1513,7 @@ subroutine initialize_dyn_split_RK2(u, v, h, uh, vh, eta, Time, G, GV, US, param do j=js,je ; do i=is,ie ; eta(i,j) = CS%eta(i,j) ; enddo ; enddo call barotropic_init(u, v, h, CS%eta, Time, G, GV, US, param_file, diag, & - CS%barotropic_CSp, restart_CS, calc_dtbt, CS%BT_cont, & - CS%SAL_CSp) + CS%barotropic_CSp, restart_CS, calc_dtbt, CS%BT_cont, CS%SAL_CSp) if (.not. query_initialized(CS%diffu, "diffu", restart_CS) .or. & .not. query_initialized(CS%diffv, "diffv", restart_CS)) then From eac3bb33c49a47e5d31a43fadede9e84eae50396 Mon Sep 17 00:00:00 2001 From: Robert Hallberg Date: Fri, 15 Dec 2023 16:34:56 -0500 Subject: [PATCH 18/22] +FIX_UNSPLIT_DT_VISC_BUG is now UNSPLIT_DT_VISC_BUG Renamed the runtime parameter FIX_UNSPLIT_DT_VISC_BUG to UNSPLIT_DT_VISC_BUG (with a switch between the meanings of true and false for the two parameters) for consistency with the syntax of other bug-fix flags in MOM6 and to partially address dev/gfdl MOM6 issue #237. Input parameter files need not be changed right away because MOM6 will still work if FIX_UNSPLIT_DT_VISC_BUG is specified instead of UNSPLIT_DT_VISC_BUG, but UNSPLIT_DT_VISC_BUG will be logged, so there are changes to the MOM_parameter_doc files. By default or with existing input parameter files, all answers are bitwise identical, and there is error handling if inconsistent settings of FIX_UNSPLIT_DT_VISC_BUG and UNSPLIT_DT_VISC_BUG are both specified. --- src/core/MOM_dynamics_unsplit.F90 | 57 ++++++++++++++++++----- src/core/MOM_dynamics_unsplit_RK2.F90 | 65 ++++++++++++++++++++------- 2 files changed, 94 insertions(+), 28 deletions(-) diff --git a/src/core/MOM_dynamics_unsplit.F90 b/src/core/MOM_dynamics_unsplit.F90 index c87e6e9958..f9e4aa0efe 100644 --- a/src/core/MOM_dynamics_unsplit.F90 +++ b/src/core/MOM_dynamics_unsplit.F90 @@ -65,7 +65,7 @@ module MOM_dynamics_unsplit use MOM_domains, only : pass_vector, pass_vector_start, pass_vector_complete use MOM_domains, only : To_South, To_West, To_All, CGRID_NE, SCALAR_PAIR use MOM_error_handler, only : MOM_error, MOM_mesg, FATAL, WARNING, is_root_pe -use MOM_file_parser, only : get_param, log_version, param_file_type +use MOM_file_parser, only : get_param, log_param, log_version, param_file_type use MOM_get_input, only : directories use MOM_time_manager, only : time_type, real_to_time, operator(+) use MOM_time_manager, only : operator(-), operator(>), operator(*), operator(/) @@ -116,13 +116,13 @@ module MOM_dynamics_unsplit real, pointer, dimension(:,:) :: tauy_bot => NULL() !< frictional y-bottom stress from the ocean !! to the seafloor [R L Z T-2 ~> Pa] - logical :: use_correct_dt_visc !< If true, use the correct timestep in the viscous terms applied - !! in the first predictor step with the unsplit time stepping scheme, - !! and in the calculation of the turbulent mixed layer properties - !! for viscosity. The default should be true, but it is false. - logical :: debug !< If true, write verbose checksums for debugging purposes. - logical :: calculate_SAL !< If true, calculate self-attraction and loading. - logical :: use_tides !< If true, tidal forcing is enabled. + logical :: dt_visc_bug !< If false, use the correct timestep in viscous terms applied in the + !! first predictor step and in the calculation of the turbulent mixed + !! layer properties for viscosity. If this is true, an older incorrect + !! setting is used. + logical :: debug !< If true, write verbose checksums for debugging purposes. + logical :: calculate_SAL !< If true, calculate self-attraction and loading. + logical :: use_tides !< If true, tidal forcing is enabled. logical :: module_is_initialized = .false. !< Record whether this module has been initialized. @@ -346,11 +346,11 @@ subroutine step_MOM_dyn_unsplit(u, v, h, tv, visc, Time_local, dt, forces, & ! up <- up + dt/2 d/dz visc d/dz up call cpu_clock_begin(id_clock_vertvisc) call enable_averages(dt, Time_local, CS%diag) - dt_visc = 0.5*dt ; if (CS%use_correct_dt_visc) dt_visc = dt + dt_visc = dt ; if (CS%dt_visc_bug) dt_visc = 0.5*dt call set_viscous_ML(u, v, h_av, tv, forces, visc, dt_visc, G, GV, US, CS%set_visc_CSp) call disable_averaging(CS%diag) - dt_visc = 0.5*dt ; if (CS%use_correct_dt_visc) dt_visc = dt_pred + dt_visc = dt_pred ; if (CS%dt_visc_bug) dt_visc = 0.5*dt call thickness_to_dz(h_av, tv, dz, G, GV, US, halo_size=1) call vertvisc_coef(up, vp, h_av, dz, forces, visc, tv, dt_visc, G, GV, US, CS%vertvisc_CSp, CS%OBC, VarMix) call vertvisc(up, vp, h_av, forces, visc, dt_visc, CS%OBC, CS%ADp, CS%CDp, & @@ -630,6 +630,9 @@ subroutine initialize_dyn_unsplit(u, v, h, Time, G, GV, US, param_file, diag, CS character(len=48) :: flux_units ! This include declares and sets the variable "version". # include "version_variable.h" + logical :: use_correct_dt_visc + logical :: test_value ! This is used to determine whether a logical parameter is being set explicitly. + logical :: explicit_bug, explicit_fix ! These indicate which parameters are set explicitly. integer :: isd, ied, jsd, jed, nz, IsdB, IedB, JsdB, JedB isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed ; nz = GV%ke IsdB = G%IsdB ; IedB = G%IedB ; JsdB = G%JsdB ; JedB = G%JedB @@ -646,11 +649,41 @@ subroutine initialize_dyn_unsplit(u, v, h, Time, G, GV, US, param_file, diag, CS CS%diag => diag call log_version(param_file, mdl, version, "") - call get_param(param_file, mdl, "FIX_UNSPLIT_DT_VISC_BUG", CS%use_correct_dt_visc, & + + call get_param(param_file, mdl, "UNSPLIT_DT_VISC_BUG", CS%dt_visc_bug, & + "If false, use the correct timestep in the viscous terms applied in the first "//& + "predictor step with the unsplit time stepping scheme, and in the calculation "//& + "of the turbulent mixed layer properties for viscosity with unsplit or "//& + "unsplit_RK2. If true, an older incorrect value is used.", & + default=.false., do_not_log=.true.) + ! This is used to test whether UNSPLIT_DT_VISC_BUG is being actively set. + call get_param(param_file, mdl, "UNSPLIT_DT_VISC_BUG", test_value, default=.true., do_not_log=.true.) + explicit_bug = CS%dt_visc_bug .eqv. test_value + call get_param(param_file, mdl, "FIX_UNSPLIT_DT_VISC_BUG", use_correct_dt_visc, & "If true, use the correct timestep in the viscous terms applied in the first "//& "predictor step with the unsplit time stepping scheme, and in the calculation "//& "of the turbulent mixed layer properties for viscosity with unsplit or "//& - "unsplit_RK2.", default=.true.) + "unsplit_RK2.", default=.true., do_not_log=.true.) + call get_param(param_file, mdl, "FIX_UNSPLIT_DT_VISC_BUG", test_value, default=.false., do_not_log=.true.) + explicit_fix = use_correct_dt_visc .eqv. test_value + + if (explicit_bug .and. explicit_fix .and. (use_correct_dt_visc .eqv. CS%dt_visc_bug)) then + ! UNSPLIT_DT_VISC_BUG is being explicitly set, and should not be changed. + call MOM_error(FATAL, "UNSPLIT_DT_VISC_BUG and FIX_UNSPLIT_DT_VISC_BUG are both being set "//& + "with inconsistent values. FIX_UNSPLIT_DT_VISC_BUG is an obsolete "//& + "parameter and should be removed.") + elseif (explicit_fix) then + call MOM_error(WARNING, "FIX_UNSPLIT_DT_VISC_BUG is an obsolete parameter. "//& + "Use UNSPLIT_DT_VISC_BUG instead (noting that it has the opposite sense).") + CS%dt_visc_bug = .not.use_correct_dt_visc + endif + call log_param(param_file, mdl, "UNSPLIT_DT_VISC_BUG", CS%dt_visc_bug, & + "If false, use the correct timestep in the viscous terms applied in the first "//& + "predictor step with the unsplit time stepping scheme, and in the calculation "//& + "of the turbulent mixed layer properties for viscosity with unsplit or "//& + "unsplit_RK2. If true, an older incorrect value is used.", & + default=.false.) + call get_param(param_file, mdl, "DEBUG", CS%debug, & "If true, write out verbose debugging data.", & default=.false., debuggingParam=.true.) diff --git a/src/core/MOM_dynamics_unsplit_RK2.F90 b/src/core/MOM_dynamics_unsplit_RK2.F90 index b515229566..1c589f509c 100644 --- a/src/core/MOM_dynamics_unsplit_RK2.F90 +++ b/src/core/MOM_dynamics_unsplit_RK2.F90 @@ -64,7 +64,7 @@ module MOM_dynamics_unsplit_RK2 use MOM_domains, only : To_South, To_West, To_All, CGRID_NE, SCALAR_PAIR use MOM_error_handler, only : MOM_error, MOM_mesg, FATAL, WARNING, is_root_pe use MOM_error_handler, only : MOM_set_verbosity -use MOM_file_parser, only : get_param, log_version, param_file_type +use MOM_file_parser, only : get_param, log_param, log_version, param_file_type use MOM_get_input, only : directories use MOM_time_manager, only : time_type, time_type_to_real, operator(+) use MOM_time_manager, only : operator(-), operator(>), operator(*), operator(/) @@ -114,18 +114,18 @@ module MOM_dynamics_unsplit_RK2 real, pointer, dimension(:,:) :: tauy_bot => NULL() !< frictional y-bottom stress from the ocean !! to the seafloor [R L Z T-2 ~> Pa] - real :: be !< A nondimensional number from 0.5 to 1 that controls - !! the backward weighting of the time stepping scheme [nondim]. - real :: begw !< A nondimensional number from 0 to 1 that controls - !! the extent to which the treatment of gravity waves - !! is forward-backward (0) or simulated backward - !! Euler (1) [nondim]. 0 is often used. - logical :: use_correct_dt_visc !< If true, use the correct timestep in the calculation of the - !! turbulent mixed layer properties for viscosity. - !! The default should be true, but it is false. - logical :: debug !< If true, write verbose checksums for debugging purposes. - logical :: calculate_SAL !< If true, calculate self-attraction and loading. - logical :: use_tides !< If true, tidal forcing is enabled. + real :: be !< A nondimensional number from 0.5 to 1 that controls + !! the backward weighting of the time stepping scheme [nondim]. + real :: begw !< A nondimensional number from 0 to 1 that controls + !! the extent to which the treatment of gravity waves + !! is forward-backward (0) or simulated backward + !! Euler (1) [nondim]. 0 is often used. + logical :: dt_visc_bug !< If false, use the correct timestep in the calculation of the + !! turbulent mixed layer properties for viscosity. Otherwise if + !! this is true, an older incorrect setting is used. + logical :: debug !< If true, write verbose checksums for debugging purposes. + logical :: calculate_SAL !< If true, calculate self-attraction and loading. + logical :: use_tides !< If true, tidal forcing is enabled. logical :: module_is_initialized = .false. !< Record whether this module has been initialized. @@ -344,7 +344,7 @@ subroutine step_MOM_dyn_unsplit_RK2(u_in, v_in, h_in, tv, visc, Time_local, dt, ! up[n-1/2] <- up*[n-1/2] + dt/2 d/dz visc d/dz up[n-1/2] call cpu_clock_begin(id_clock_vertvisc) call enable_averages(dt, Time_local, CS%diag) - dt_visc = dt_pred ; if (CS%use_correct_dt_visc) dt_visc = dt + dt_visc = dt ; if (CS%dt_visc_bug) dt_visc = dt_pred call set_viscous_ML(u_in, v_in, h_av, tv, forces, visc, dt_visc, G, GV, US, CS%set_visc_CSp) call disable_averaging(CS%diag) @@ -578,6 +578,9 @@ subroutine initialize_dyn_unsplit_RK2(u, v, h, Time, G, GV, US, param_file, diag character(len=48) :: flux_units ! This include declares and sets the variable "version". # include "version_variable.h" + logical :: use_correct_dt_visc + logical :: test_value ! This is used to determine whether a logical parameter is being set explicitly. + logical :: explicit_bug, explicit_fix ! These indicate which parameters are set explicitly. integer :: isd, ied, jsd, jed, nz, IsdB, IedB, JsdB, JedB isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed ; nz = GV%ke IsdB = G%IsdB ; IedB = G%IedB ; JsdB = G%JsdB ; JedB = G%JedB @@ -610,11 +613,41 @@ subroutine initialize_dyn_unsplit_RK2(u, v, h, Time, G, GV, US, param_file, diag "If SPLIT is false and USE_RK2 is true, BEGW can be "//& "between 0 and 0.5 to damp gravity waves.", & units="nondim", default=0.0) - call get_param(param_file, mdl, "FIX_UNSPLIT_DT_VISC_BUG", CS%use_correct_dt_visc, & + + call get_param(param_file, mdl, "UNSPLIT_DT_VISC_BUG", CS%dt_visc_bug, & + "If false, use the correct timestep in the viscous terms applied in the first "//& + "predictor step with the unsplit time stepping scheme, and in the calculation "//& + "of the turbulent mixed layer properties for viscosity with unsplit or "//& + "unsplit_RK2. If true, an older incorrect value is used.", & + default=.false., do_not_log=.true.) + ! This is used to test whether UNSPLIT_DT_VISC_BUG is being explicitly set. + call get_param(param_file, mdl, "UNSPLIT_DT_VISC_BUG", test_value, default=.true., do_not_log=.true.) + explicit_bug = CS%dt_visc_bug .eqv. test_value + call get_param(param_file, mdl, "FIX_UNSPLIT_DT_VISC_BUG", use_correct_dt_visc, & "If true, use the correct timestep in the viscous terms applied in the first "//& "predictor step with the unsplit time stepping scheme, and in the calculation "//& "of the turbulent mixed layer properties for viscosity with unsplit or "//& - "unsplit_RK2.", default=.true.) + "unsplit_RK2.", default=.true., do_not_log=.true.) + call get_param(param_file, mdl, "FIX_UNSPLIT_DT_VISC_BUG", test_value, default=.false., do_not_log=.true.) + explicit_fix = use_correct_dt_visc .eqv. test_value + + if (explicit_bug .and. explicit_fix .and. (use_correct_dt_visc .eqv. CS%dt_visc_bug)) then + ! UNSPLIT_DT_VISC_BUG is being explicitly set, and should not be changed. + call MOM_error(FATAL, "UNSPLIT_DT_VISC_BUG and FIX_UNSPLIT_DT_VISC_BUG are both being set "//& + "with inconsistent values. FIX_UNSPLIT_DT_VISC_BUG is an obsolete "//& + "parameter and should be removed.") + elseif (explicit_fix) then + call MOM_error(WARNING, "FIX_UNSPLIT_DT_VISC_BUG is an obsolete parameter. "//& + "Use UNSPLIT_DT_VISC_BUG instead (noting that it has the opposite sense).") + CS%dt_visc_bug = .not.use_correct_dt_visc + endif + call log_param(param_file, mdl, "UNSPLIT_DT_VISC_BUG", CS%dt_visc_bug, & + "If false, use the correct timestep in the viscous terms applied in the first "//& + "predictor step with the unsplit time stepping scheme, and in the calculation "//& + "of the turbulent mixed layer properties for viscosity with unsplit or "//& + "unsplit_RK2. If true, an older incorrect value is used.", & + default=.false.) + call get_param(param_file, mdl, "DEBUG", CS%debug, & "If true, write out verbose debugging data.", & default=.false., debuggingParam=.true.) From 2ea0ac32d18027bd213667846a0f6c7a3d099f63 Mon Sep 17 00:00:00 2001 From: Robert Hallberg Date: Sun, 12 Nov 2023 16:54:11 -0500 Subject: [PATCH 19/22] +Add MOM_dynamics_split_RK2b enabled by SPLIT_RK2B Add the new module MOM_dynamics_split_RK2b and calls to the routines in this module to MOM.F90. These calls are exercised when the run time parameter SPLIT_RK2B is true. For now, all answers are bitwise identical when this new code is being exercised, but there is a new module with multiple public interfaces and a new entry in many MOM_parameter_doc files. --- src/core/MOM.F90 | 55 +- src/core/MOM_dynamics_split_RK2b.F90 | 1842 ++++++++++++++++++++++++++ 2 files changed, 1887 insertions(+), 10 deletions(-) create mode 100644 src/core/MOM_dynamics_split_RK2b.F90 diff --git a/src/core/MOM.F90 b/src/core/MOM.F90 index bcba4d37c7..e1f31b7558 100644 --- a/src/core/MOM.F90 +++ b/src/core/MOM.F90 @@ -77,6 +77,9 @@ module MOM use MOM_dynamics_split_RK2, only : step_MOM_dyn_split_RK2, register_restarts_dyn_split_RK2 use MOM_dynamics_split_RK2, only : initialize_dyn_split_RK2, end_dyn_split_RK2 use MOM_dynamics_split_RK2, only : MOM_dyn_split_RK2_CS, remap_dyn_split_rk2_aux_vars +use MOM_dynamics_split_RK2b, only : step_MOM_dyn_split_RK2b, register_restarts_dyn_split_RK2b +use MOM_dynamics_split_RK2b, only : initialize_dyn_split_RK2b, end_dyn_split_RK2b +use MOM_dynamics_split_RK2b, only : MOM_dyn_split_RK2b_CS, remap_dyn_split_RK2b_aux_vars use MOM_dynamics_unsplit_RK2, only : step_MOM_dyn_unsplit_RK2, register_restarts_dyn_unsplit_RK2 use MOM_dynamics_unsplit_RK2, only : initialize_dyn_unsplit_RK2, end_dyn_unsplit_RK2 use MOM_dynamics_unsplit_RK2, only : MOM_dyn_unsplit_RK2_CS @@ -284,6 +287,9 @@ module MOM logical :: do_dynamics !< If false, does not call step_MOM_dyn_*. This is an !! undocumented run-time flag that is fragile. logical :: split !< If true, use the split time stepping scheme. + logical :: use_alt_split !< If true, use a version of the split explicit time stepping + !! with a heavier emphasis on consistent tranports between the + !! layered and barotroic variables. logical :: use_RK2 !< If true, use RK2 instead of RK3 in unsplit mode !! (i.e., no split between barotropic and baroclinic). logical :: interface_filter !< If true, apply an interface height filter immediately @@ -379,6 +385,8 @@ module MOM !< Pointer to the control structure used for the unsplit RK2 dynamics type(MOM_dyn_split_RK2_CS), pointer :: dyn_split_RK2_CSp => NULL() !< Pointer to the control structure used for the mode-split RK2 dynamics + type(MOM_dyn_split_RK2b_CS), pointer :: dyn_split_RK2b_CSp => NULL() + !< Pointer to the control structure used for an alternate version of the mode-split RK2 dynamics type(thickness_diffuse_CS) :: thickness_diffuse_CSp !< Pointer to the control structure used for the isopycnal height diffusive transport. !! This is also common referred to as Gent-McWilliams diffusion @@ -1220,10 +1228,17 @@ subroutine step_MOM_dynamics(forces, p_surf_begin, p_surf_end, dt, dt_thermo, & endif endif - call step_MOM_dyn_split_RK2(u, v, h, CS%tv, CS%visc, Time_local, dt, forces, & - p_surf_begin, p_surf_end, CS%uh, CS%vh, CS%uhtr, CS%vhtr, & - CS%eta_av_bc, G, GV, US, CS%dyn_split_RK2_CSp, calc_dtbt, CS%VarMix, & - CS%MEKE, CS%thickness_diffuse_CSp, CS%pbv, waves=waves) + if (CS%use_alt_split) then + call step_MOM_dyn_split_RK2b(u, v, h, CS%tv, CS%visc, Time_local, dt, forces, & + p_surf_begin, p_surf_end, CS%uh, CS%vh, CS%uhtr, CS%vhtr, & + CS%eta_av_bc, G, GV, US, CS%dyn_split_RK2b_CSp, calc_dtbt, CS%VarMix, & + CS%MEKE, CS%thickness_diffuse_CSp, CS%pbv, waves=waves) + else + call step_MOM_dyn_split_RK2(u, v, h, CS%tv, CS%visc, Time_local, dt, forces, & + p_surf_begin, p_surf_end, CS%uh, CS%vh, CS%uhtr, CS%vhtr, & + CS%eta_av_bc, G, GV, US, CS%dyn_split_RK2_CSp, calc_dtbt, CS%VarMix, & + CS%MEKE, CS%thickness_diffuse_CSp, CS%pbv, waves=waves) + endif if (showCallTree) call callTree_waypoint("finished step_MOM_dyn_split (step_MOM)") elseif (CS%do_dynamics) then ! ------------------------------------ not SPLIT @@ -1646,8 +1661,12 @@ subroutine step_MOM_thermo(CS, G, GV, US, u, v, h, tv, fluxes, dtdia, & if (allocated(tv%SpV_avg)) tv%valid_SpV_halo = -1 ! Record that SpV_avg is no longer valid. if (CS%remap_aux_vars) then - if (CS%split) & + if (CS%split .and. CS%use_alt_split) then + call remap_dyn_split_RK2b_aux_vars(G, GV, CS%dyn_split_RK2b_CSp, h_old_u, h_old_v, & + h_new_u, h_new_v, CS%ALE_CSp) + elseif (CS%split) then call remap_dyn_split_RK2_aux_vars(G, GV, CS%dyn_split_RK2_CSp, h_old_u, h_old_v, h_new_u, h_new_v, CS%ALE_CSp) + endif if (associated(CS%OBC)) then call pass_var(h, G%Domain, complete=.false.) @@ -2154,6 +2173,10 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, & call get_param(param_file, "MOM", "SPLIT", CS%split, & "Use the split time stepping if true.", default=.true.) + call get_param(param_file, "MOM", "SPLIT_RK2B", CS%use_alt_split, & + "If true, use a version of the split explicit time stepping with a heavier "//& + "emphasis on consistent tranports between the layered and barotroic variables.", & + default=.false., do_not_log=.not.CS%split) if (CS%split) then CS%use_RK2 = .false. else @@ -2771,7 +2794,10 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, & restart_CSp => CS%restart_CS call set_restart_fields(GV, US, param_file, CS, restart_CSp) - if (CS%split) then + if (CS%split .and. CS%use_alt_split) then + call register_restarts_dyn_split_RK2b(HI, GV, US, param_file, & + CS%dyn_split_RK2b_CSp, restart_CSp, CS%uh, CS%vh) + elseif (CS%split) then call register_restarts_dyn_split_RK2(HI, GV, US, param_file, & CS%dyn_split_RK2_CSp, restart_CSp, CS%uh, CS%vh) elseif (CS%use_RK2) then @@ -3157,12 +3183,19 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, & if (CS%split) then allocate(eta(SZI_(G),SZJ_(G)), source=0.0) - call initialize_dyn_split_RK2(CS%u, CS%v, CS%h, CS%uh, CS%vh, eta, Time, & + if (CS%use_alt_split) then + call initialize_dyn_split_RK2b(CS%u, CS%v, CS%h, CS%uh, CS%vh, eta, Time, & + G, GV, US, param_file, diag, CS%dyn_split_RK2b_CSp, restart_CSp, & + CS%dt, CS%ADp, CS%CDp, MOM_internal_state, CS%VarMix, CS%MEKE, & + CS%thickness_diffuse_CSp, CS%OBC, CS%update_OBC_CSp, CS%ALE_CSp, CS%set_visc_CSp, & + CS%visc, dirs, CS%ntrunc, CS%pbv, calc_dtbt=calc_dtbt, cont_stencil=CS%cont_stencil) + else + call initialize_dyn_split_RK2(CS%u, CS%v, CS%h, CS%uh, CS%vh, eta, Time, & G, GV, US, param_file, diag, CS%dyn_split_RK2_CSp, restart_CSp, & CS%dt, CS%ADp, CS%CDp, MOM_internal_state, CS%VarMix, CS%MEKE, & - CS%thickness_diffuse_CSp, & - CS%OBC, CS%update_OBC_CSp, CS%ALE_CSp, CS%set_visc_CSp, & + CS%thickness_diffuse_CSp, CS%OBC, CS%update_OBC_CSp, CS%ALE_CSp, CS%set_visc_CSp, & CS%visc, dirs, CS%ntrunc, CS%pbv, calc_dtbt=calc_dtbt, cont_stencil=CS%cont_stencil) + endif if (CS%dtbt_reset_period > 0.0) then CS%dtbt_reset_interval = real_to_time(US%T_to_s*CS%dtbt_reset_period) ! Set dtbt_reset_time to be the next even multiple of dtbt_reset_interval. @@ -4116,7 +4149,9 @@ subroutine MOM_end(CS) if (CS%offline_tracer_mode) call offline_transport_end(CS%offline_CSp) - if (CS%split) then + if (CS%split .and. CS%use_alt_split) then + call end_dyn_split_RK2b(CS%dyn_split_RK2b_CSp) + elseif (CS%split) then call end_dyn_split_RK2(CS%dyn_split_RK2_CSp) elseif (CS%use_RK2) then call end_dyn_unsplit_RK2(CS%dyn_unsplit_RK2_CSp) diff --git a/src/core/MOM_dynamics_split_RK2b.F90 b/src/core/MOM_dynamics_split_RK2b.F90 new file mode 100644 index 0000000000..a289014313 --- /dev/null +++ b/src/core/MOM_dynamics_split_RK2b.F90 @@ -0,0 +1,1842 @@ +!> Time step the adiabatic dynamic core of MOM using RK2 method with greater use of the +!! time-filtered velocities and less inheritance of tedencies from the previous step in the +!! predictor step than in the original MOM_dyanmics_split_RK2. +module MOM_dynamics_split_RK2b + +! This file is part of MOM6. See LICENSE.md for the license. + +use MOM_variables, only : vertvisc_type, thermo_var_ptrs, porous_barrier_type +use MOM_variables, only : BT_cont_type, alloc_bt_cont_type, dealloc_bt_cont_type +use MOM_variables, only : accel_diag_ptrs, ocean_internal_state, cont_diag_ptrs +use MOM_forcing_type, only : mech_forcing + +use MOM_checksum_packages, only : MOM_thermo_chksum, MOM_state_chksum, MOM_accel_chksum +use MOM_cpu_clock, only : cpu_clock_id, cpu_clock_begin, cpu_clock_end +use MOM_cpu_clock, only : CLOCK_COMPONENT, CLOCK_SUBCOMPONENT +use MOM_cpu_clock, only : CLOCK_MODULE_DRIVER, CLOCK_MODULE, CLOCK_ROUTINE +use MOM_diag_mediator, only : diag_mediator_init, enable_averages +use MOM_diag_mediator, only : disable_averaging, post_data, safe_alloc_ptr +use MOM_diag_mediator, only : post_product_u, post_product_sum_u +use MOM_diag_mediator, only : post_product_v, post_product_sum_v +use MOM_diag_mediator, only : register_diag_field, register_static_field +use MOM_diag_mediator, only : set_diag_mediator_grid, diag_ctrl, diag_update_remap_grids +use MOM_domains, only : To_South, To_West, To_All, CGRID_NE, SCALAR_PAIR +use MOM_domains, only : To_North, To_East, Omit_Corners +use MOM_domains, only : create_group_pass, do_group_pass, group_pass_type +use MOM_domains, only : start_group_pass, complete_group_pass, pass_var, pass_vector +use MOM_debugging, only : hchksum, uvchksum +use MOM_error_handler, only : MOM_error, MOM_mesg, FATAL, WARNING, is_root_pe +use MOM_error_handler, only : MOM_set_verbosity, callTree_showQuery +use MOM_error_handler, only : callTree_enter, callTree_leave, callTree_waypoint +use MOM_file_parser, only : get_param, log_version, param_file_type +use MOM_get_input, only : directories +use MOM_io, only : vardesc, var_desc, EAST_FACE, NORTH_FACE +use MOM_restart, only : register_restart_field, register_restart_pair +use MOM_restart, only : query_initialized, set_initialized, save_restart +use MOM_restart, only : only_read_from_restarts +use MOM_restart, only : restart_init, is_new_run, MOM_restart_CS +use MOM_time_manager, only : time_type, time_type_to_real, operator(+) +use MOM_time_manager, only : operator(-), operator(>), operator(*), operator(/) + +use MOM_ALE, only : ALE_CS, ALE_remap_velocities +use MOM_barotropic, only : barotropic_init, btstep, btcalc, bt_mass_source +use MOM_barotropic, only : register_barotropic_restarts, set_dtbt, barotropic_CS +use MOM_barotropic, only : barotropic_end +use MOM_boundary_update, only : update_OBC_data, update_OBC_CS +use MOM_continuity, only : continuity, continuity_CS +use MOM_continuity, only : continuity_init, continuity_stencil +use MOM_CoriolisAdv, only : CorAdCalc, CoriolisAdv_CS +use MOM_CoriolisAdv, only : CoriolisAdv_init, CoriolisAdv_end +use MOM_debugging, only : check_redundant +use MOM_grid, only : ocean_grid_type +use MOM_hor_index, only : hor_index_type +use MOM_hor_visc, only : horizontal_viscosity, hor_visc_CS +use MOM_hor_visc, only : hor_visc_init, hor_visc_end +use MOM_interface_heights, only : thickness_to_dz, find_col_avg_SpV +use MOM_lateral_mixing_coeffs, only : VarMix_CS +use MOM_MEKE_types, only : MEKE_type +use MOM_open_boundary, only : ocean_OBC_type, radiation_open_bdry_conds +use MOM_open_boundary, only : open_boundary_zero_normal_flow, open_boundary_query +use MOM_open_boundary, only : open_boundary_test_extern_h, update_OBC_ramp +use MOM_PressureForce, only : PressureForce, PressureForce_CS +use MOM_PressureForce, only : PressureForce_init +use MOM_set_visc, only : set_viscous_ML, set_visc_CS +use MOM_thickness_diffuse, only : thickness_diffuse_CS +use MOM_self_attr_load, only : SAL_CS +use MOM_self_attr_load, only : SAL_init, SAL_end +use MOM_tidal_forcing, only : tidal_forcing_CS +use MOM_tidal_forcing, only : tidal_forcing_init, tidal_forcing_end +use MOM_unit_scaling, only : unit_scale_type +use MOM_vert_friction, only : vertvisc, vertvisc_coef, vertvisc_remnant +use MOM_vert_friction, only : vertvisc_init, vertvisc_end, vertvisc_CS +use MOM_vert_friction, only : updateCFLtruncationValue, vertFPmix +use MOM_verticalGrid, only : verticalGrid_type, get_thickness_units +use MOM_verticalGrid, only : get_flux_units, get_tr_flux_units +use MOM_wave_interface, only: wave_parameters_CS, Stokes_PGF +use MOM_CVMix_KPP, only : KPP_get_BLD, KPP_CS +use MOM_energetic_PBL, only : energetic_PBL_get_MLD, energetic_PBL_CS +use MOM_diabatic_driver, only : diabatic_CS, extract_diabatic_member + +implicit none ; private + +#include + +!> MOM_dynamics_split_RK2b module control structure +type, public :: MOM_dyn_split_RK2b_CS ; private + real ALLOCABLE_, dimension(NIMEMB_PTR_,NJMEM_,NKMEM_) :: & + CAu, & !< CAu = f*v - u.grad(u) [L T-2 ~> m s-2] + CAu_pred, & !< The predictor step value of CAu = f*v - u.grad(u) [L T-2 ~> m s-2] + PFu, & !< PFu = -dM/dx [L T-2 ~> m s-2] + PFu_Stokes, & !< PFu_Stokes = -d/dx int_r (u_L*duS/dr) [L T-2 ~> m s-2] + diffu !< Zonal acceleration due to convergence of the along-isopycnal stress tensor [L T-2 ~> m s-2] + + real ALLOCABLE_, dimension(NIMEM_,NJMEMB_PTR_,NKMEM_) :: & + CAv, & !< CAv = -f*u - u.grad(v) [L T-2 ~> m s-2] + CAv_pred, & !< The predictor step value of CAv = -f*u - u.grad(v) [L T-2 ~> m s-2] + PFv, & !< PFv = -dM/dy [L T-2 ~> m s-2] + PFv_Stokes, & !< PFv_Stokes = -d/dy int_r (v_L*dvS/dr) [L T-2 ~> m s-2] + diffv !< Meridional acceleration due to convergence of the along-isopycnal stress tensor [L T-2 ~> m s-2] + + real ALLOCABLE_, dimension(NIMEMB_PTR_,NJMEM_,NKMEM_) :: visc_rem_u + !< Both the fraction of the zonal momentum originally in a + !! layer that remains after a time-step of viscosity, and the + !! fraction of a time-step worth of a barotropic acceleration + !! that a layer experiences after viscosity is applied [nondim]. + !! Nondimensional between 0 (at the bottom) and 1 (far above). + real ALLOCABLE_, dimension(NIMEMB_PTR_,NJMEM_,NKMEM_) :: u_accel_bt + !< The zonal layer accelerations due to the difference between + !! the barotropic accelerations and the baroclinic accelerations + !! that were fed into the barotopic calculation [L T-2 ~> m s-2] + real ALLOCABLE_, dimension(NIMEM_,NJMEMB_PTR_,NKMEM_) :: visc_rem_v + !< Both the fraction of the meridional momentum originally in + !! a layer that remains after a time-step of viscosity, and the + !! fraction of a time-step worth of a barotropic acceleration + !! that a layer experiences after viscosity is applied [nondim]. + !! Nondimensional between 0 (at the bottom) and 1 (far above). + real ALLOCABLE_, dimension(NIMEM_,NJMEMB_PTR_,NKMEM_) :: v_accel_bt + !< The meridional layer accelerations due to the difference between + !! the barotropic accelerations and the baroclinic accelerations + !! that were fed into the barotopic calculation [L T-2 ~> m s-2] + + ! The following variables are only used with the split time stepping scheme. + real ALLOCABLE_, dimension(NIMEM_,NJMEM_) :: eta !< Instantaneous free surface height (in Boussinesq + !! mode) or column mass anomaly (in non-Boussinesq + !! mode) [H ~> m or kg m-2] + real ALLOCABLE_, dimension(NIMEMB_PTR_,NJMEM_,NKMEM_) :: u_av !< layer x-velocity with vertical mean replaced by + !! time-mean barotropic velocity over a baroclinic + !! timestep [L T-1 ~> m s-1] + real ALLOCABLE_, dimension(NIMEM_,NJMEMB_PTR_,NKMEM_) :: v_av !< layer y-velocity with vertical mean replaced by + !! time-mean barotropic velocity over a baroclinic + !! timestep [L T-1 ~> m s-1] + real ALLOCABLE_, dimension(NIMEM_,NJMEM_,NKMEM_) :: h_av !< arithmetic mean of two successive layer + !! thicknesses [H ~> m or kg m-2] + real ALLOCABLE_, dimension(NIMEM_,NJMEM_) :: eta_PF !< instantaneous SSH used in calculating PFu and + !! PFv [H ~> m or kg m-2] + real ALLOCABLE_, dimension(NIMEMB_PTR_,NJMEM_) :: uhbt !< average x-volume or mass flux determined by the + !! barotropic solver [H L2 T-1 ~> m3 s-1 or kg s-1]. + !! uhbt is roughly equal to the vertical sum of uh. + real ALLOCABLE_, dimension(NIMEM_,NJMEMB_PTR_) :: vhbt !< average y-volume or mass flux determined by the + !! barotropic solver [H L2 T-1 ~> m3 s-1 or kg s-1]. + !! vhbt is roughly equal to vertical sum of vh. + real ALLOCABLE_, dimension(NIMEM_,NJMEM_,NKMEM_) :: pbce !< pbce times eta gives the baroclinic pressure + !! anomaly in each layer due to free surface height + !! anomalies [L2 H-1 T-2 ~> m s-2 or m4 kg-1 s-2]. + type(KPP_CS), pointer :: KPP_CSp => NULL() !< KPP control structure needed to ge + type(energetic_PBL_CS), pointer :: energetic_PBL_CSp => NULL() !< ePBL control structure + + real, pointer, dimension(:,:) :: taux_bot => NULL() !< frictional x-bottom stress from the ocean + !! to the seafloor [R L Z T-2 ~> Pa] + real, pointer, dimension(:,:) :: tauy_bot => NULL() !< frictional y-bottom stress from the ocean + !! to the seafloor [R L Z T-2 ~> Pa] + type(BT_cont_type), pointer :: BT_cont => NULL() !< A structure with elements that describe the + !! effective summed open face areas as a function + !! of barotropic flow. + + logical :: split_bottom_stress !< If true, provide the bottom stress + !! calculated by the vertical viscosity to the + !! barotropic solver. + logical :: calc_dtbt !< If true, calculate the barotropic time-step + !! dynamically. + logical :: store_CAu !< If true, store the Coriolis and advective accelerations at the + !! end of the timestep for use in the next predictor step. + logical :: CAu_pred_stored !< If true, the Coriolis and advective accelerations at the + !! end of the timestep have been stored for use in the next + !! predictor step. This is used to accomodate various generations + !! of restart files. + logical :: calculate_SAL !< If true, calculate self-attraction and loading. + logical :: use_tides !< If true, tidal forcing is enabled. + logical :: remap_aux !< If true, apply ALE remapping to all of the auxiliary 3-D + !! variables that are needed to reproduce across restarts, + !! similarly to what is done with the primary state variables. + + real :: be !< A nondimensional number from 0.5 to 1 that controls + !! the backward weighting of the time stepping scheme [nondim] + real :: begw !< A nondimensional number from 0 to 1 that controls + !! the extent to which the treatment of gravity waves + !! is forward-backward (0) or simulated backward + !! Euler (1) [nondim]. 0 is often used. + logical :: debug !< If true, write verbose checksums for debugging purposes. + logical :: debug_OBC !< If true, do debugging calls for open boundary conditions. + logical :: fpmix = .false. !< If true, applies profiles of momentum flux magnitude and direction. + logical :: module_is_initialized = .false. !< Record whether this module has been initialized. + + !>@{ Diagnostic IDs + integer :: id_uold = -1, id_vold = -1 + integer :: id_uh = -1, id_vh = -1 + integer :: id_umo = -1, id_vmo = -1 + integer :: id_umo_2d = -1, id_vmo_2d = -1 + integer :: id_PFu = -1, id_PFv = -1 + integer :: id_CAu = -1, id_CAv = -1 + integer :: id_ueffA = -1, id_veffA = -1 + ! integer :: id_hf_PFu = -1, id_hf_PFv = -1 + integer :: id_h_PFu = -1, id_h_PFv = -1 + integer :: id_hf_PFu_2d = -1, id_hf_PFv_2d = -1 + integer :: id_intz_PFu_2d = -1, id_intz_PFv_2d = -1 + integer :: id_PFu_visc_rem = -1, id_PFv_visc_rem = -1 + ! integer :: id_hf_CAu = -1, id_hf_CAv = -1 + integer :: id_h_CAu = -1, id_h_CAv = -1 + integer :: id_hf_CAu_2d = -1, id_hf_CAv_2d = -1 + integer :: id_intz_CAu_2d = -1, id_intz_CAv_2d = -1 + integer :: id_CAu_visc_rem = -1, id_CAv_visc_rem = -1 + integer :: id_deta_dt = -1 + + ! Split scheme only. + integer :: id_uav = -1, id_vav = -1 + integer :: id_u_BT_accel = -1, id_v_BT_accel = -1 + ! integer :: id_hf_u_BT_accel = -1, id_hf_v_BT_accel = -1 + integer :: id_h_u_BT_accel = -1, id_h_v_BT_accel = -1 + integer :: id_hf_u_BT_accel_2d = -1, id_hf_v_BT_accel_2d = -1 + integer :: id_intz_u_BT_accel_2d = -1, id_intz_v_BT_accel_2d = -1 + integer :: id_u_BT_accel_visc_rem = -1, id_v_BT_accel_visc_rem = -1 + !>@} + + type(diag_ctrl), pointer :: diag => NULL() !< A structure that is used to regulate the + !! timing of diagnostic output. + type(accel_diag_ptrs), pointer :: ADp => NULL() !< A structure pointing to the various + !! accelerations in the momentum equations, + !! which can later be used to calculate + !! derived diagnostics like energy budgets. + type(accel_diag_ptrs), pointer :: AD_pred => NULL() !< A structure pointing to the various + !! predictor step accelerations in the momentum equations, + !! which can be used to debug truncations. + type(cont_diag_ptrs), pointer :: CDp => NULL() !< A structure with pointers to various + !! terms in the continuity equations, + !! which can later be used to calculate + !! derived diagnostics like energy budgets. + + ! The remainder of the structure points to child subroutines' control structures. + !> A pointer to the horizontal viscosity control structure + type(hor_visc_CS) :: hor_visc + !> A pointer to the continuity control structure + type(continuity_CS) :: continuity_CSp + !> The CoriolisAdv control structure + type(CoriolisAdv_CS) :: CoriolisAdv + !> A pointer to the PressureForce control structure + type(PressureForce_CS) :: PressureForce_CSp + !> A pointer to a structure containing interface height diffusivities + type(vertvisc_CS), pointer :: vertvisc_CSp => NULL() + !> A pointer to the set_visc control structure + type(set_visc_CS), pointer :: set_visc_CSp => NULL() + !> A pointer to the barotropic stepping control structure + type(barotropic_CS) :: barotropic_CSp + !> A pointer to the SAL control structure + type(SAL_CS) :: SAL_CSp + !> A pointer to the tidal forcing control structure + type(tidal_forcing_CS) :: tides_CSp + !> A pointer to the ALE control structure. + type(ALE_CS), pointer :: ALE_CSp => NULL() + + type(ocean_OBC_type), pointer :: OBC => NULL() !< A pointer to an open boundary + !! condition type that specifies whether, where, and what open boundary + !! conditions are used. If no open BCs are used, this pointer stays + !! nullified. Flather OBCs use open boundary_CS as well. + !> A pointer to the update_OBC control structure + type(update_OBC_CS), pointer :: update_OBC_CSp => NULL() + + type(group_pass_type) :: pass_eta !< Structure for group halo pass + type(group_pass_type) :: pass_visc_rem !< Structure for group halo pass + type(group_pass_type) :: pass_uvp !< Structure for group halo pass + type(group_pass_type) :: pass_hp_uv !< Structure for group halo pass + type(group_pass_type) :: pass_uv !< Structure for group halo pass + type(group_pass_type) :: pass_h !< Structure for group halo pass + type(group_pass_type) :: pass_av_uvh !< Structure for group halo pass + +end type MOM_dyn_split_RK2b_CS + + +public step_MOM_dyn_split_RK2b +public register_restarts_dyn_split_RK2b +public initialize_dyn_split_RK2b +public remap_dyn_split_RK2b_aux_vars +public end_dyn_split_RK2b + +!>@{ CPU time clock IDs +integer :: id_clock_Cor, id_clock_pres, id_clock_vertvisc +integer :: id_clock_horvisc, id_clock_mom_update +integer :: id_clock_continuity, id_clock_thick_diff +integer :: id_clock_btstep, id_clock_btcalc, id_clock_btforce +integer :: id_clock_pass, id_clock_pass_init +!>@} + +contains + +!> RK2 splitting for time stepping MOM adiabatic dynamics +subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, forces, & + p_surf_begin, p_surf_end, uh, vh, uhtr, vhtr, eta_av, & + G, GV, US, CS, calc_dtbt, VarMix, MEKE, thickness_diffuse_CSp, pbv, Waves) + type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure + type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure + type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & + target, intent(inout) :: u_inst !< Zonal velocity [L T-1 ~> m s-1] + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & + target, intent(inout) :: v_inst !< Meridional velocity [L T-1 ~> m s-1] + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + intent(inout) :: h !< Layer thickness [H ~> m or kg m-2] + type(thermo_var_ptrs), intent(in) :: tv !< Thermodynamic type + type(vertvisc_type), intent(inout) :: visc !< Vertical visc, bottom drag, and related + type(time_type), intent(in) :: Time_local !< Model time at end of time step + real, intent(in) :: dt !< Baroclinic dynamics time step [T ~> s] + type(mech_forcing), intent(in) :: forces !< A structure with the driving mechanical forces + real, dimension(:,:), pointer :: p_surf_begin !< Surface pressure at the start of this dynamic + !! time step [R L2 T-2 ~> Pa] + real, dimension(:,:), pointer :: p_surf_end !< Surface pressure at the end of this dynamic + !! time step [R L2 T-2 ~> Pa] + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & + target, intent(inout) :: uh !< Zonal volume or mass transport + !! [H L2 T-1 ~> m3 s-1 or kg s-1] + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & + target, intent(inout) :: vh !< Meridional volume or mass transport + !! [H L2 T-1 ~> m3 s-1 or kg s-1] + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & + intent(inout) :: uhtr !< Accumulated zonal volume or mass transport + !! since last tracer advection [H L2 ~> m3 or kg] + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & + intent(inout) :: vhtr !< Accumulated meridional volume or mass transport + !! since last tracer advection [H L2 ~> m3 or kg] + real, dimension(SZI_(G),SZJ_(G)), intent(out) :: eta_av !< Free surface height or column mass + !! averaged over time step [H ~> m or kg m-2] + type(MOM_dyn_split_RK2b_CS), pointer :: CS !< Module control structure + logical, intent(in) :: calc_dtbt !< If true, recalculate the barotropic time step + type(VarMix_CS), intent(inout) :: VarMix !< Variable mixing control structure + type(MEKE_type), intent(inout) :: MEKE !< MEKE fields + type(thickness_diffuse_CS), intent(inout) :: thickness_diffuse_CSp !< Pointer to a structure containing + !! interface height diffusivities + type(porous_barrier_type), intent(in) :: pbv !< porous barrier fractional cell metrics + type(wave_parameters_CS), optional, pointer :: Waves !< A pointer to a structure containing + !! fields related to the surface wave conditions + + ! local variables + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: up ! Predicted zonal velocity [L T-1 ~> m s-1]. + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: vp ! Predicted meridional velocity [L T-1 ~> m s-1]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: hp ! Predicted thickness [H ~> m or kg m-2]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: dz ! Distance between the interfaces around a layer [Z ~> m] + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: ueffA ! Effective Area of U-Faces [H L ~> m2] + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: veffA ! Effective Area of V-Faces [H L ~> m2] + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: u_bc_accel ! The summed zonal baroclinic accelerations + ! of each layer calculated by the non-barotropic + ! part of the model [L T-2 ~> m s-2] + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: v_bc_accel ! The summed meridional baroclinic accelerations + ! of each layer calculated by the non-barotropic + ! part of the model [L T-2 ~> m s-2] + + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), target :: uh_in ! The zonal mass transports that would be + ! obtained using the initial velocities [H L2 T-1 ~> m3 s-1 or kg s-1] + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), target :: vh_in ! The meridional mass transports that would be + ! obtained using the initial velocities [H L2 T-1 ~> m3 s-1 or kg s-1] + + real, dimension(SZI_(G),SZJ_(G)) :: eta_pred ! The predictor value of the free surface height + ! or column mass [H ~> m or kg m-2] + real, dimension(SZI_(G),SZJ_(G)) :: SpV_avg ! The column averaged specific volume [R-1 ~> m3 kg-1] + real, dimension(SZI_(G),SZJ_(G)) :: deta_dt ! A diagnostic of the time derivative of the free surface + ! height or column mass [H T-1 ~> m s-1 or kg m-2 s-1] + + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: u_old_rad_OBC ! The starting zonal velocities, which are + ! saved for use in the Flather open boundary condition code [L T-1 ~> m s-1] + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: v_old_rad_OBC ! The starting meridional velocities, which are + ! saved for use in the Flather open boundary condition code [L T-1 ~> m s-1] + + ! GMM, TODO: make these allocatable? + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: uold ! u-velocity before vert_visc is applied, for fpmix + ! [L T-1 ~> m s-1] + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: vold ! v-velocity before vert_visc is applied, for fpmix + ! [L T-1 ~> m s-1] + real :: pres_to_eta ! A factor that converts pressures to the units of eta + ! [H T2 R-1 L-2 ~> m Pa-1 or kg m-2 Pa-1] + real, pointer, dimension(:,:) :: & + p_surf => NULL(), & ! A pointer to the surface pressure [R L2 T-2 ~> Pa] + eta_PF_start => NULL(), & ! The value of eta that corresponds to the starting pressure + ! for the barotropic solver [H ~> m or kg m-2] + taux_bot => NULL(), & ! A pointer to the zonal bottom stress in some cases [R L Z T-2 ~> Pa] + tauy_bot => NULL(), & ! A pointer to the meridional bottom stress in some cases [R L Z T-2 ~> Pa] + ! This pointer is just used as shorthand for CS%eta. + eta => NULL() ! A pointer to the instantaneous free surface height (in Boussinesq + ! mode) or column mass anomaly (in non-Boussinesq mode) [H ~> m or kg m-2] + + real, pointer, dimension(:,:,:) :: & + ! These pointers are used to alter which fields are passed to btstep with various options: + u_ptr => NULL(), & ! A pointer to a zonal velocity [L T-1 ~> m s-1] + v_ptr => NULL(), & ! A pointer to a meridional velocity [L T-1 ~> m s-1] + uh_ptr => NULL(), & ! A pointer to a zonal volume or mass transport [H L2 T-1 ~> m3 s-1 or kg s-1] + vh_ptr => NULL(), & ! A pointer to a meridional volume or mass transport [H L2 T-1 ~> m3 s-1 or kg s-1] + ! These pointers are just used as shorthand for CS%u_av, CS%v_av, and CS%h_av. + u_av, & ! The zonal velocity time-averaged over a time step [L T-1 ~> m s-1]. + v_av, & ! The meridional velocity time-averaged over a time step [L T-1 ~> m s-1]. + h_av ! The layer thickness time-averaged over a time step [H ~> m or kg m-2]. + + real, dimension(SZI_(G),SZJ_(G)) :: hbl ! Boundary layer depth from Cvmix [H ~> m or kg m-2] + real :: dt_pred ! The time step for the predictor part of the baroclinic time stepping [T ~> s]. + real :: Idt_bc ! Inverse of the baroclinic timestep [T-1 ~> s-1] + logical :: dyn_p_surf + logical :: BT_cont_BT_thick ! If true, use the BT_cont_type to estimate the + ! relative weightings of the layers in calculating + ! the barotropic accelerations. + logical :: Use_Stokes_PGF ! If true, add Stokes PGF to hydrostatic PGF + !---For group halo pass + logical :: showCallTree, sym + + integer :: i, j, k, is, ie, js, je, Isq, Ieq, Jsq, Jeq, nz + integer :: cont_stencil, obc_stencil + + is = G%isc ; ie = G%iec ; js = G%jsc ; je = G%jec ; nz = GV%ke + Isq = G%IscB ; Ieq = G%IecB ; Jsq = G%JscB ; Jeq = G%JecB + u_av => CS%u_av ; v_av => CS%v_av ; h_av => CS%h_av ; eta => CS%eta + + Idt_bc = 1.0 / dt + + sym = G%Domain%symmetric ! switch to include symmetric domain in checksums + + showCallTree = callTree_showQuery() + if (showCallTree) call callTree_enter("step_MOM_dyn_split_RK2b(), MOM_dynamics_split_RK2b.F90") + + !$OMP parallel do default(shared) + do k=1,nz + do j=G%jsd,G%jed ; do i=G%isdB,G%iedB ; up(i,j,k) = 0.0 ; enddo ; enddo + do j=G%jsdB,G%jedB ; do i=G%isd,G%ied ; vp(i,j,k) = 0.0 ; enddo ; enddo + do j=G%jsd,G%jed ; do i=G%isd,G%ied ; hp(i,j,k) = h(i,j,k) ; enddo ; enddo + enddo + + ! Update CFL truncation value as function of time + call updateCFLtruncationValue(Time_local, CS%vertvisc_CSp, US) + + if (CS%debug) then + call MOM_state_chksum("Start predictor ", u_inst, v_inst, h, uh, vh, G, GV, US, symmetric=sym) + call check_redundant("Start predictor u ", u_inst, v_inst, G, unscale=US%L_T_to_m_s) + call check_redundant("Start predictor uh ", uh, vh, G, unscale=GV%H_to_MKS*US%L_to_m**2*US%s_to_T) + endif + + dyn_p_surf = associated(p_surf_begin) .and. associated(p_surf_end) + if (dyn_p_surf) then + p_surf => p_surf_end + call safe_alloc_ptr(eta_PF_start,G%isd,G%ied,G%jsd,G%jed) + eta_PF_start(:,:) = 0.0 + else + p_surf => forces%p_surf + endif + + if (associated(CS%OBC)) then + if (CS%debug_OBC) call open_boundary_test_extern_h(G, GV, CS%OBC, h) + + ! Update OBC ramp value as function of time + call update_OBC_ramp(Time_local, CS%OBC, US) + + do k=1,nz ; do j=G%jsd,G%jed ; do I=G%IsdB,G%IedB + u_old_rad_OBC(I,j,k) = u_av(I,j,k) + enddo ; enddo ; enddo + do k=1,nz ; do J=G%JsdB,G%JedB ; do i=G%isd,G%ied + v_old_rad_OBC(i,J,k) = v_av(i,J,k) + enddo ; enddo ; enddo + endif + + BT_cont_BT_thick = .false. + if (associated(CS%BT_cont)) BT_cont_BT_thick = & + (allocated(CS%BT_cont%h_u) .and. allocated(CS%BT_cont%h_v)) + + if (CS%split_bottom_stress) then + taux_bot => CS%taux_bot ; tauy_bot => CS%tauy_bot + endif + + !--- begin set up for group halo pass + + cont_stencil = continuity_stencil(CS%continuity_CSp) + obc_stencil = 2 + if (associated(CS%OBC)) then + if (CS%OBC%oblique_BCs_exist_globally) obc_stencil = 3 + endif + call cpu_clock_begin(id_clock_pass) + call create_group_pass(CS%pass_eta, eta, G%Domain, halo=1) + call create_group_pass(CS%pass_visc_rem, CS%visc_rem_u, CS%visc_rem_v, G%Domain, & + To_All+SCALAR_PAIR, CGRID_NE, halo=max(1,cont_stencil)) + call create_group_pass(CS%pass_uvp, up, vp, G%Domain, halo=max(1,cont_stencil)) + call create_group_pass(CS%pass_hp_uv, hp, G%Domain, halo=2) + call create_group_pass(CS%pass_hp_uv, u_av, v_av, G%Domain, halo=max(2,obc_stencil)) + call create_group_pass(CS%pass_hp_uv, uh(:,:,:), vh(:,:,:), G%Domain, halo=max(2,obc_stencil)) + + call create_group_pass(CS%pass_uv, u_inst, v_inst, G%Domain, halo=max(2,cont_stencil)) + call create_group_pass(CS%pass_h, h, G%Domain, halo=max(2,cont_stencil)) + call create_group_pass(CS%pass_av_uvh, u_av, v_av, G%Domain, halo=max(2,obc_stencil)) + call create_group_pass(CS%pass_av_uvh, uh(:,:,:), vh(:,:,:), G%Domain, halo=max(2,obc_stencil)) + call cpu_clock_end(id_clock_pass) + !--- end set up for group halo pass + + +! PFu = d/dx M(h,T,S) +! pbce = dM/deta + if (CS%begw == 0.0) call enable_averages(dt, Time_local, CS%diag) + call cpu_clock_begin(id_clock_pres) + call PressureForce(h, tv, CS%PFu, CS%PFv, G, GV, US, CS%PressureForce_CSp, & + CS%ALE_CSp, p_surf, CS%pbce, CS%eta_PF) + if (dyn_p_surf) then + pres_to_eta = 1.0 / (GV%g_Earth * GV%H_to_RZ) + !$OMP parallel do default(shared) + do j=Jsq,Jeq+1 ; do i=Isq,Ieq+1 + eta_PF_start(i,j) = CS%eta_PF(i,j) - pres_to_eta * (p_surf_begin(i,j) - p_surf_end(i,j)) + enddo ; enddo + endif + ! Stokes shear force contribution to pressure gradient + Use_Stokes_PGF = present(Waves) + if (Use_Stokes_PGF) then + Use_Stokes_PGF = associated(Waves) + if (Use_Stokes_PGF) Use_Stokes_PGF = Waves%Stokes_PGF + if (Use_Stokes_PGF) then + call thickness_to_dz(h, tv, dz, G, GV, US, halo_size=1) + call Stokes_PGF(G, GV, US, dz, u_inst, v_inst, CS%PFu_Stokes, CS%PFv_Stokes, Waves) + + ! We are adding Stokes_PGF to hydrostatic PGF here. The diag PFu/PFv + ! will therefore report the sum total PGF and we avoid other + ! modifications in the code. The PFu_Stokes is output within the waves routines. + if (.not.Waves%Passive_Stokes_PGF) then + do k=1,nz + do j=js,je ; do I=Isq,Ieq + CS%PFu(I,j,k) = CS%PFu(I,j,k) + CS%PFu_Stokes(I,j,k) + enddo ; enddo + enddo + do k=1,nz + do J=Jsq,Jeq ; do i=is,ie + CS%PFv(i,J,k) = CS%PFv(i,J,k) + CS%PFv_Stokes(i,J,k) + enddo ; enddo + enddo + endif + endif + endif + call cpu_clock_end(id_clock_pres) + call disable_averaging(CS%diag) + if (showCallTree) call callTree_wayPoint("done with PressureForce (step_MOM_dyn_split_RK2b)") + + if (associated(CS%OBC)) then ; if (CS%OBC%update_OBC) then + call update_OBC_data(CS%OBC, G, GV, US, tv, h, CS%update_OBC_CSp, Time_local) + endif ; endif + if (associated(CS%OBC) .and. CS%debug_OBC) & + call open_boundary_zero_normal_flow(CS%OBC, G, GV, CS%PFu, CS%PFv) + + if (G%nonblocking_updates) & + call start_group_pass(CS%pass_eta, G%Domain, clock=id_clock_pass) + +! CAu = -(f+zeta_av)/h_av vh + d/dx KE_av + if (.not.CS%CAu_pred_stored) then + ! Calculate a predictor-step estimate of the Coriolis and momentum advection terms, + ! if it was not already stored from the end of the previous time step. + call cpu_clock_begin(id_clock_Cor) + call CorAdCalc(u_av, v_av, h_av, uh, vh, CS%CAu_pred, CS%CAv_pred, CS%OBC, CS%AD_pred, & + G, GV, US, CS%CoriolisAdv, pbv, Waves=Waves) + call cpu_clock_end(id_clock_Cor) + if (showCallTree) call callTree_wayPoint("done with CorAdCalc (step_MOM_dyn_split_RK2b)") + endif + +! u_bc_accel = CAu + PFu + diffu(u[n-1]) + call cpu_clock_begin(id_clock_btforce) + !$OMP parallel do default(shared) + do k=1,nz + do j=js,je ; do I=Isq,Ieq + u_bc_accel(I,j,k) = (CS%CAu_pred(I,j,k) + CS%PFu(I,j,k)) + CS%diffu(I,j,k) + enddo ; enddo + do J=Jsq,Jeq ; do i=is,ie + v_bc_accel(i,J,k) = (CS%CAv_pred(i,J,k) + CS%PFv(i,J,k)) + CS%diffv(i,J,k) + enddo ; enddo + enddo + if (associated(CS%OBC)) then + call open_boundary_zero_normal_flow(CS%OBC, G, GV, u_bc_accel, v_bc_accel) + endif + call cpu_clock_end(id_clock_btforce) + + if (CS%debug) then + call MOM_accel_chksum("pre-btstep accel", CS%CAu_pred, CS%CAv_pred, CS%PFu, CS%PFv, & + CS%diffu, CS%diffv, G, GV, US, CS%pbce, u_bc_accel, v_bc_accel, & + symmetric=sym) + call check_redundant("pre-btstep CS%CA ", CS%CAu_pred, CS%CAv_pred, G, unscale=US%L_T2_to_m_s2) + call check_redundant("pre-btstep CS%PF ", CS%PFu, CS%PFv, G, unscale=US%L_T2_to_m_s2) + call check_redundant("pre-btstep CS%diff ", CS%diffu, CS%diffv, G, unscale=US%L_T2_to_m_s2) + call check_redundant("pre-btstep u_bc_accel ", u_bc_accel, v_bc_accel, G, unscale=US%L_T2_to_m_s2) + endif + + call cpu_clock_begin(id_clock_vertvisc) + !$OMP parallel do default(shared) + do k=1,nz + do j=js,je ; do I=Isq,Ieq + up(I,j,k) = G%mask2dCu(I,j) * (u_inst(I,j,k) + dt * u_bc_accel(I,j,k)) + enddo ; enddo + do J=Jsq,Jeq ; do i=is,ie + vp(i,J,k) = G%mask2dCv(i,J) * (v_inst(i,J,k) + dt * v_bc_accel(i,J,k)) + enddo ; enddo + enddo + + call enable_averages(dt, Time_local, CS%diag) + call set_viscous_ML(u_inst, v_inst, h, tv, forces, visc, dt, G, GV, US, CS%set_visc_CSp) + call disable_averaging(CS%diag) + + if (CS%debug) then + call uvchksum("before vertvisc: up", up, vp, G%HI, haloshift=0, symmetric=sym, scale=US%L_T_to_m_s) + endif + call thickness_to_dz(h, tv, dz, G, GV, US, halo_size=1) + call vertvisc_coef(up, vp, h, dz, forces, visc, tv, dt, G, GV, US, CS%vertvisc_CSp, CS%OBC, VarMix) + call vertvisc_remnant(visc, CS%visc_rem_u, CS%visc_rem_v, dt, G, GV, US, CS%vertvisc_CSp) + call cpu_clock_end(id_clock_vertvisc) + if (showCallTree) call callTree_wayPoint("done with vertvisc_coef (step_MOM_dyn_split_RK2b)") + + + call cpu_clock_begin(id_clock_pass) + if (G%nonblocking_updates) then + call complete_group_pass(CS%pass_eta, G%Domain) + call start_group_pass(CS%pass_visc_rem, G%Domain) + else + call do_group_pass(CS%pass_eta, G%Domain) + call do_group_pass(CS%pass_visc_rem, G%Domain) + endif + call cpu_clock_end(id_clock_pass) + + call cpu_clock_begin(id_clock_btcalc) + ! Calculate the relative layer weights for determining barotropic quantities. + if (.not.BT_cont_BT_thick) & + call btcalc(h, G, GV, CS%barotropic_CSp, OBC=CS%OBC) + call bt_mass_source(h, eta, .true., G, GV, CS%barotropic_CSp) + + SpV_avg(:,:) = 0.0 + if ((.not.GV%Boussinesq) .and. associated(CS%OBC)) then + ! Determine the column average specific volume if it is needed due to the + ! use of Flather open boundary conditions in non-Boussinesq mode. + if (open_boundary_query(CS%OBC, apply_Flather_OBC=.true.)) & + call find_col_avg_SpV(h, SpV_avg, tv, G, GV, US) + endif + call cpu_clock_end(id_clock_btcalc) + + if (G%nonblocking_updates) & + call complete_group_pass(CS%pass_visc_rem, G%Domain, clock=id_clock_pass) + +! u_accel_bt = layer accelerations due to barotropic solver + call cpu_clock_begin(id_clock_continuity) + call continuity(u_inst, v_inst, h, hp, uh_in, vh_in, dt, G, GV, US, CS%continuity_CSp, CS%OBC, pbv, & + visc_rem_u=CS%visc_rem_u, visc_rem_v=CS%visc_rem_v, BT_cont=CS%BT_cont) + call cpu_clock_end(id_clock_continuity) + if (BT_cont_BT_thick) then + call btcalc(h, G, GV, CS%barotropic_CSp, CS%BT_cont%h_u, CS%BT_cont%h_v, & + OBC=CS%OBC) + endif + if (showCallTree) call callTree_wayPoint("done with continuity[BT_cont] (step_MOM_dyn_split_RK2b)") + + uh_ptr => uh_in ; vh_ptr => vh_in ; u_ptr => u_inst ; v_ptr => v_inst + + call cpu_clock_begin(id_clock_btstep) + if (calc_dtbt) call set_dtbt(G, GV, US, CS%barotropic_CSp, eta, CS%pbce) + if (showCallTree) call callTree_enter("btstep(), MOM_barotropic.F90") + ! This is the predictor step call to btstep. + ! The CS%ADp argument here stores the weights for certain integrated diagnostics. + call btstep(u_inst, v_inst, eta, dt, u_bc_accel, v_bc_accel, forces, CS%pbce, CS%eta_PF, u_av, v_av, & + CS%u_accel_bt, CS%v_accel_bt, eta_pred, CS%uhbt, CS%vhbt, G, GV, US, & + CS%barotropic_CSp, CS%visc_rem_u, CS%visc_rem_v, SpV_avg, CS%ADp, CS%OBC, CS%BT_cont, & + eta_PF_start, taux_bot, tauy_bot, uh_ptr, vh_ptr, u_ptr, v_ptr) + if (showCallTree) call callTree_leave("btstep()") + call cpu_clock_end(id_clock_btstep) + +! up = u + dt_pred*( u_bc_accel + u_accel_bt ) + dt_pred = dt * CS%be + call cpu_clock_begin(id_clock_mom_update) + + !$OMP parallel do default(shared) + do k=1,nz + do J=Jsq,Jeq ; do i=is,ie + vp(i,J,k) = G%mask2dCv(i,J) * (v_inst(i,J,k) + dt_pred * & + (v_bc_accel(i,J,k) + CS%v_accel_bt(i,J,k))) + enddo ; enddo + do j=js,je ; do I=Isq,Ieq + up(I,j,k) = G%mask2dCu(I,j) * (u_inst(I,j,k) + dt_pred * & + (u_bc_accel(I,j,k) + CS%u_accel_bt(I,j,k))) + enddo ; enddo + enddo + call cpu_clock_end(id_clock_mom_update) + + if (CS%debug) then + call uvchksum("Predictor 1 [uv]", up, vp, G%HI, haloshift=0, symmetric=sym, scale=US%L_T_to_m_s) + call hchksum(h, "Predictor 1 h", G%HI, haloshift=1, scale=GV%H_to_MKS) + call uvchksum("Predictor 1 [uv]h", uh, vh, G%HI,haloshift=2, & + symmetric=sym, scale=GV%H_to_MKS*US%L_to_m**2*US%s_to_T) +! call MOM_state_chksum("Predictor 1", up, vp, h, uh, vh, G, GV, US, haloshift=1) + call MOM_accel_chksum("Predictor accel", CS%CAu_pred, CS%CAv_pred, CS%PFu, CS%PFv, & + CS%diffu, CS%diffv, G, GV, US, CS%pbce, CS%u_accel_bt, CS%v_accel_bt, symmetric=sym) + call MOM_state_chksum("Predictor 1 init", u_inst, v_inst, h, uh, vh, G, GV, US, haloshift=1, & + symmetric=sym) + call check_redundant("Predictor 1 up", up, vp, G, unscale=US%L_T_to_m_s) + call check_redundant("Predictor 1 uh", uh, vh, G, unscale=GV%H_to_MKS*US%L_to_m**2*US%s_to_T) + endif + +! up <- up + dt_pred d/dz visc d/dz up +! u_av <- u_av + dt_pred d/dz visc d/dz u_av + call cpu_clock_begin(id_clock_vertvisc) + if (CS%debug) then + call uvchksum("0 before vertvisc: [uv]p", up, vp, G%HI,haloshift=0, symmetric=sym, scale=US%L_T_to_m_s) + endif + + if (CS%fpmix) then + uold(:,:,:) = 0.0 + vold(:,:,:) = 0.0 + do k=1,nz ; do j=js,je ; do I=Isq,Ieq + uold(I,j,k) = up(I,j,k) + enddo ; enddo ; enddo + do k=1,nz ; do J=Jsq,Jeq ; do i=is,ie + vold(i,J,k) = vp(i,J,k) + enddo ; enddo ; enddo + endif + + call thickness_to_dz(h, tv, dz, G, GV, US, halo_size=1) + call vertvisc_coef(up, vp, h, dz, forces, visc, tv, dt_pred, G, GV, US, CS%vertvisc_CSp, & + CS%OBC, VarMix) + call vertvisc(up, vp, h, forces, visc, dt_pred, CS%OBC, CS%AD_pred, CS%CDp, G, & + GV, US, CS%vertvisc_CSp, CS%taux_bot, CS%tauy_bot, waves=waves) + + if (CS%fpmix) then + hbl(:,:) = 0.0 + if (ASSOCIATED(CS%KPP_CSp)) call KPP_get_BLD(CS%KPP_CSp, hbl, G, US, m_to_BLD_units=GV%m_to_H) + if (ASSOCIATED(CS%energetic_PBL_CSp)) & + call energetic_PBL_get_MLD(CS%energetic_PBL_CSp, hbl, G, US, m_to_MLD_units=GV%m_to_H) + call vertFPmix(up, vp, uold, vold, hbl, h, forces, & + dt_pred, G, GV, US, CS%vertvisc_CSp, CS%OBC) + call vertvisc(up, vp, h, forces, visc, dt_pred, CS%OBC, CS%ADp, CS%CDp, G, & + GV, US, CS%vertvisc_CSp, CS%taux_bot, CS%tauy_bot, waves=waves) + endif + + if (showCallTree) call callTree_wayPoint("done with vertvisc (step_MOM_dyn_split_RK2b)") + if (G%nonblocking_updates) then + call cpu_clock_end(id_clock_vertvisc) + call start_group_pass(CS%pass_uvp, G%Domain, clock=id_clock_pass) + call cpu_clock_begin(id_clock_vertvisc) + endif + call vertvisc_remnant(visc, CS%visc_rem_u, CS%visc_rem_v, dt_pred, G, GV, US, CS%vertvisc_CSp) + call cpu_clock_end(id_clock_vertvisc) + + call do_group_pass(CS%pass_visc_rem, G%Domain, clock=id_clock_pass) + if (G%nonblocking_updates) then + call complete_group_pass(CS%pass_uvp, G%Domain, clock=id_clock_pass) + else + call do_group_pass(CS%pass_uvp, G%Domain, clock=id_clock_pass) + endif + + ! uh = u_av * h + ! hp = h + dt * div . uh + call cpu_clock_begin(id_clock_continuity) + call continuity(up, vp, h, hp, uh, vh, dt, G, GV, US, CS%continuity_CSp, CS%OBC, pbv, & + CS%uhbt, CS%vhbt, CS%visc_rem_u, CS%visc_rem_v, & + u_av, v_av, BT_cont=CS%BT_cont) + call cpu_clock_end(id_clock_continuity) + if (showCallTree) call callTree_wayPoint("done with continuity (step_MOM_dyn_split_RK2b)") + + call do_group_pass(CS%pass_hp_uv, G%Domain, clock=id_clock_pass) + + if (associated(CS%OBC)) then + + if (CS%debug) & + call uvchksum("Pre OBC avg [uv]", u_av, v_av, G%HI, haloshift=1, symmetric=sym, scale=US%L_T_to_m_s) + + call radiation_open_bdry_conds(CS%OBC, u_av, u_old_rad_OBC, v_av, v_old_rad_OBC, G, GV, US, dt_pred) + + if (CS%debug) & + call uvchksum("Post OBC avg [uv]", u_av, v_av, G%HI, haloshift=1, symmetric=sym, scale=US%L_T_to_m_s) + + ! These should be done with a pass that excludes uh & vh. +! call do_group_pass(CS%pass_hp_uv, G%Domain, clock=id_clock_pass) + endif + + if (G%nonblocking_updates) then + call start_group_pass(CS%pass_av_uvh, G%Domain, clock=id_clock_pass) + endif + + ! h_av = (h + hp)/2 + !$OMP parallel do default(shared) + do k=1,nz ; do j=js-2,je+2 ; do i=is-2,ie+2 + h_av(i,j,k) = 0.5*(h(i,j,k) + hp(i,j,k)) + enddo ; enddo ; enddo + + ! The correction phase of the time step starts here. + call enable_averages(dt, Time_local, CS%diag) + + ! Calculate a revised estimate of the free-surface height correction to be + ! used in the next call to btstep. This call is at this point so that + ! hp can be changed if CS%begw /= 0. + ! eta_cor = ... (hidden inside CS%barotropic_CSp) + call cpu_clock_begin(id_clock_btcalc) + call bt_mass_source(hp, eta_pred, .false., G, GV, CS%barotropic_CSp) + call cpu_clock_end(id_clock_btcalc) + + if (CS%begw /= 0.0) then + ! hp <- (1-begw)*h_in + begw*hp + ! Back up hp to the value it would have had after a time-step of + ! begw*dt. hp is not used again until recalculated by continuity. + !$OMP parallel do default(shared) + do k=1,nz ; do j=js-1,je+1 ; do i=is-1,ie+1 + hp(i,j,k) = (1.0-CS%begw)*h(i,j,k) + CS%begw*hp(i,j,k) + enddo ; enddo ; enddo + + ! PFu = d/dx M(hp,T,S) + ! pbce = dM/deta + call cpu_clock_begin(id_clock_pres) + call PressureForce(hp, tv, CS%PFu, CS%PFv, G, GV, US, CS%PressureForce_CSp, & + CS%ALE_CSp, p_surf, CS%pbce, CS%eta_PF) + ! Stokes shear force contribution to pressure gradient + Use_Stokes_PGF = present(Waves) + if (Use_Stokes_PGF) then + Use_Stokes_PGF = associated(Waves) + if (Use_Stokes_PGF) Use_Stokes_PGF = Waves%Stokes_PGF + if (Use_Stokes_PGF) then + call thickness_to_dz(h, tv, dz, G, GV, US, halo_size=1) + call Stokes_PGF(G, GV, US, dz, u_inst, v_inst, CS%PFu_Stokes, CS%PFv_Stokes, Waves) + if (.not.Waves%Passive_Stokes_PGF) then + do k=1,nz + do j=js,je ; do I=Isq,Ieq + CS%PFu(I,j,k) = CS%PFu(I,j,k) + CS%PFu_Stokes(I,j,k) + enddo ; enddo + enddo + do k=1,nz + do J=Jsq,Jeq ; do i=is,ie + CS%PFv(i,J,k) = CS%PFv(i,J,k) + CS%PFv_Stokes(i,J,k) + enddo ; enddo + enddo + endif + endif + endif + call cpu_clock_end(id_clock_pres) + if (showCallTree) call callTree_wayPoint("done with PressureForce[hp=(1-b).h+b.h] (step_MOM_dyn_split_RK2b)") + endif + + if (G%nonblocking_updates) & + call complete_group_pass(CS%pass_av_uvh, G%Domain, clock=id_clock_pass) + + if (BT_cont_BT_thick) then + call btcalc(h, G, GV, CS%barotropic_CSp, CS%BT_cont%h_u, CS%BT_cont%h_v, & + OBC=CS%OBC) + if (showCallTree) call callTree_wayPoint("done with btcalc[BT_cont_BT_thick] (step_MOM_dyn_split_RK2b)") + endif + + if (CS%debug) then + call MOM_state_chksum("Predictor ", up, vp, hp, uh, vh, G, GV, US, symmetric=sym) + call uvchksum("Predictor avg [uv]", u_av, v_av, G%HI, haloshift=1, symmetric=sym, scale=US%L_T_to_m_s) + call hchksum(h_av, "Predictor avg h", G%HI, haloshift=0, scale=GV%H_to_MKS) + ! call MOM_state_chksum("Predictor avg ", u_av, v_av, h_av, uh, vh, G, GV, US) + call check_redundant("Predictor up ", up, vp, G, unscale=US%L_T_to_m_s) + call check_redundant("Predictor uh ", uh, vh, G, unscale=GV%H_to_MKS*US%L_to_m**2*US%s_to_T) + endif + +! diffu = horizontal viscosity terms (u_av) + call cpu_clock_begin(id_clock_horvisc) + call horizontal_viscosity(u_av, v_av, h_av, CS%diffu, CS%diffv, & + MEKE, Varmix, G, GV, US, CS%hor_visc, & + OBC=CS%OBC, BT=CS%barotropic_CSp, TD=thickness_diffuse_CSp, & + ADp=CS%ADp) + call cpu_clock_end(id_clock_horvisc) + if (showCallTree) call callTree_wayPoint("done with horizontal_viscosity (step_MOM_dyn_split_RK2b)") + +! CAu = -(f+zeta_av)/h_av vh + d/dx KE_av + call cpu_clock_begin(id_clock_Cor) + call CorAdCalc(u_av, v_av, h_av, uh, vh, CS%CAu, CS%CAv, CS%OBC, CS%ADp, & + G, GV, US, CS%CoriolisAdv, pbv, Waves=Waves) + call cpu_clock_end(id_clock_Cor) + if (showCallTree) call callTree_wayPoint("done with CorAdCalc (step_MOM_dyn_split_RK2b)") + +! Calculate the momentum forcing terms for the barotropic equations. + +! u_bc_accel = CAu + PFu + diffu(u[n-1]) + call cpu_clock_begin(id_clock_btforce) + !$OMP parallel do default(shared) + do k=1,nz + do j=js,je ; do I=Isq,Ieq + u_bc_accel(I,j,k) = (CS%Cau(I,j,k) + CS%PFu(I,j,k)) + CS%diffu(I,j,k) + enddo ; enddo + do J=Jsq,Jeq ; do i=is,ie + v_bc_accel(i,J,k) = (CS%Cav(i,J,k) + CS%PFv(i,J,k)) + CS%diffv(i,J,k) + enddo ; enddo + enddo + if (associated(CS%OBC)) then + call open_boundary_zero_normal_flow(CS%OBC, G, GV, u_bc_accel, v_bc_accel) + endif + call cpu_clock_end(id_clock_btforce) + + if (CS%debug) then + call MOM_accel_chksum("corr pre-btstep accel", CS%CAu, CS%CAv, CS%PFu, CS%PFv, & + CS%diffu, CS%diffv, G, GV, US, CS%pbce, u_bc_accel, v_bc_accel, & + symmetric=sym) + call check_redundant("corr pre-btstep CS%CA ", CS%CAu, CS%CAv, G, unscale=US%L_T2_to_m_s2) + call check_redundant("corr pre-btstep CS%PF ", CS%PFu, CS%PFv, G, unscale=US%L_T2_to_m_s2) + call check_redundant("corr pre-btstep CS%diff ", CS%diffu, CS%diffv, G, unscale=US%L_T2_to_m_s2) + call check_redundant("corr pre-btstep u_bc_accel ", u_bc_accel, v_bc_accel, G, unscale=US%L_T2_to_m_s2) + endif + + ! u_accel_bt = layer accelerations due to barotropic solver + ! pbce = dM/deta + call cpu_clock_begin(id_clock_btstep) + + uh_ptr => uh ; vh_ptr => vh ; u_ptr => u_av ; v_ptr => v_av + + if (showCallTree) call callTree_enter("btstep(), MOM_barotropic.F90") + ! This is the corrector step call to btstep. + call btstep(u_inst, v_inst, eta, dt, u_bc_accel, v_bc_accel, forces, CS%pbce, CS%eta_PF, u_av, v_av, & + CS%u_accel_bt, CS%v_accel_bt, eta_pred, CS%uhbt, CS%vhbt, G, GV, US, & + CS%barotropic_CSp, CS%visc_rem_u, CS%visc_rem_v, SpV_avg, CS%ADp, CS%OBC, CS%BT_cont, & + eta_PF_start, taux_bot, tauy_bot, uh_ptr, vh_ptr, u_ptr, v_ptr, etaav=eta_av) + if (CS%id_deta_dt>0) then + do j=js,je ; do i=is,ie ; deta_dt(i,j) = (eta_pred(i,j) - eta(i,j))*Idt_bc ; enddo ; enddo + endif + do j=js,je ; do i=is,ie ; eta(i,j) = eta_pred(i,j) ; enddo ; enddo + + call cpu_clock_end(id_clock_btstep) + if (showCallTree) call callTree_leave("btstep()") + + if (CS%debug) then + call check_redundant("u_accel_bt ", CS%u_accel_bt, CS%v_accel_bt, G, unscale=US%L_T2_to_m_s2) + endif + + ! u = u + dt*( u_bc_accel + u_accel_bt ) + call cpu_clock_begin(id_clock_mom_update) + !$OMP parallel do default(shared) + do k=1,nz + do j=js,je ; do I=Isq,Ieq + u_inst(I,j,k) = G%mask2dCu(I,j) * (u_inst(I,j,k) + dt * & + (u_bc_accel(I,j,k) + CS%u_accel_bt(I,j,k))) + enddo ; enddo + do J=Jsq,Jeq ; do i=is,ie + v_inst(i,J,k) = G%mask2dCv(i,J) * (v_inst(i,J,k) + dt * & + (v_bc_accel(i,J,k) + CS%v_accel_bt(i,J,k))) + enddo ; enddo + enddo + call cpu_clock_end(id_clock_mom_update) + + if (CS%debug) then + call uvchksum("Corrector 1 [uv]", u_inst, v_inst, G%HI, haloshift=0, symmetric=sym, scale=US%L_T_to_m_s) + call hchksum(h, "Corrector 1 h", G%HI, haloshift=1, scale=GV%H_to_MKS) + call uvchksum("Corrector 1 [uv]h", uh, vh, G%HI, haloshift=2, & + symmetric=sym, scale=GV%H_to_MKS*US%L_to_m**2*US%s_to_T) + ! call MOM_state_chksum("Corrector 1", u_inst, v_inst, h, uh, vh, G, GV, US, haloshift=1) + call MOM_accel_chksum("Corrector accel", CS%CAu, CS%CAv, CS%PFu, CS%PFv, & + CS%diffu, CS%diffv, G, GV, US, CS%pbce, CS%u_accel_bt, CS%v_accel_bt, & + symmetric=sym) + endif + + ! u <- u + dt d/dz visc d/dz u + ! u_av <- u_av + dt d/dz visc d/dz u_av + call cpu_clock_begin(id_clock_vertvisc) + + if (CS%fpmix) then + uold(:,:,:) = 0.0 + vold(:,:,:) = 0.0 + do k=1,nz ; do j=js,je ; do I=Isq,Ieq + uold(I,j,k) = u_inst(I,j,k) + enddo ; enddo ; enddo + do k=1,nz ; do J=Jsq,Jeq ; do i=is,ie + vold(i,J,k) = v_inst(i,J,k) + enddo ; enddo ; enddo + endif + + call thickness_to_dz(h, tv, dz, G, GV, US, halo_size=1) + call vertvisc_coef(u_inst, v_inst, h, dz, forces, visc, tv, dt, G, GV, US, CS%vertvisc_CSp, CS%OBC, VarMix) + call vertvisc(u_inst, v_inst, h, forces, visc, dt, CS%OBC, CS%ADp, CS%CDp, G, GV, US, & + CS%vertvisc_CSp, CS%taux_bot, CS%tauy_bot,waves=waves) + + if (CS%fpmix) then + call vertFPmix(u_inst, v_inst, uold, vold, hbl, h, forces, dt, & + G, GV, US, CS%vertvisc_CSp, CS%OBC) + call vertvisc(u_inst, v_inst, h, forces, visc, dt, CS%OBC, CS%ADp, CS%CDp, G, GV, US, & + CS%vertvisc_CSp, CS%taux_bot, CS%tauy_bot, waves=waves) + endif + + if (G%nonblocking_updates) then + call cpu_clock_end(id_clock_vertvisc) + call start_group_pass(CS%pass_uv, G%Domain, clock=id_clock_pass) + call cpu_clock_begin(id_clock_vertvisc) + endif + call vertvisc_remnant(visc, CS%visc_rem_u, CS%visc_rem_v, dt, G, GV, US, CS%vertvisc_CSp) + call cpu_clock_end(id_clock_vertvisc) + if (showCallTree) call callTree_wayPoint("done with vertvisc (step_MOM_dyn_split_RK2b)") + +! Later, h_av = (h_in + h_out)/2, but for now use h_av to store h_in. + !$OMP parallel do default(shared) + do k=1,nz ; do j=js-2,je+2 ; do i=is-2,ie+2 + h_av(i,j,k) = h(i,j,k) + enddo ; enddo ; enddo + + call do_group_pass(CS%pass_visc_rem, G%Domain, clock=id_clock_pass) + if (G%nonblocking_updates) then + call complete_group_pass(CS%pass_uv, G%Domain, clock=id_clock_pass) + else + call do_group_pass(CS%pass_uv, G%Domain, clock=id_clock_pass) + endif + + ! uh = u_av * h + ! h = h + dt * div . uh + ! u_av and v_av adjusted so their mass transports match uhbt and vhbt. + call cpu_clock_begin(id_clock_continuity) + call continuity(u_inst, v_inst, h, h, uh, vh, dt, G, GV, US, CS%continuity_CSp, CS%OBC, pbv, & + CS%uhbt, CS%vhbt, CS%visc_rem_u, CS%visc_rem_v, u_av, v_av) + call cpu_clock_end(id_clock_continuity) + call do_group_pass(CS%pass_h, G%Domain, clock=id_clock_pass) + ! Whenever thickness changes let the diag manager know, target grids + ! for vertical remapping may need to be regenerated. + call diag_update_remap_grids(CS%diag) + if (showCallTree) call callTree_wayPoint("done with continuity (step_MOM_dyn_split_RK2b)") + + if (G%nonblocking_updates) then + call start_group_pass(CS%pass_av_uvh, G%Domain, clock=id_clock_pass) + else + call do_group_pass(CS%pass_av_uvh, G%domain, clock=id_clock_pass) + endif + + if (associated(CS%OBC)) then + call radiation_open_bdry_conds(CS%OBC, u_inst, u_old_rad_OBC, v_inst, v_old_rad_OBC, G, GV, US, dt) + endif + +! h_av = (h_in + h_out)/2 . Going in to this line, h_av = h_in. + !$OMP parallel do default(shared) + do k=1,nz ; do j=js-2,je+2 ; do i=is-2,ie+2 + h_av(i,j,k) = 0.5*(h_av(i,j,k) + h(i,j,k)) + enddo ; enddo ; enddo + + if (G%nonblocking_updates) & + call complete_group_pass(CS%pass_av_uvh, G%Domain, clock=id_clock_pass) + + !$OMP parallel do default(shared) + do k=1,nz + do j=js-2,je+2 ; do I=Isq-2,Ieq+2 + uhtr(I,j,k) = uhtr(I,j,k) + uh(I,j,k)*dt + enddo ; enddo + do J=Jsq-2,Jeq+2 ; do i=is-2,ie+2 + vhtr(i,J,k) = vhtr(i,J,k) + vh(i,J,k)*dt + enddo ; enddo + enddo + + if (CS%store_CAu) then + ! Calculate a predictor-step estimate of the Coriolis and momentum advection terms + ! for use in the next time step, possibly after it has been vertically remapped. + call cpu_clock_begin(id_clock_Cor) + call disable_averaging(CS%diag) ! These calculations should not be used for diagnostics. + ! CAu = -(f+zeta_av)/h_av vh + d/dx KE_av + call CorAdCalc(u_av, v_av, h_av, uh, vh, CS%CAu_pred, CS%CAv_pred, CS%OBC, CS%AD_pred, & + G, GV, US, CS%CoriolisAdv, pbv, Waves=Waves) + CS%CAu_pred_stored = .true. + call enable_averages(dt, Time_local, CS%diag) ! Reenable the averaging + call cpu_clock_end(id_clock_Cor) + if (showCallTree) call callTree_wayPoint("done with CorAdCalc (step_MOM_dyn_split_RK2b)") + else + CS%CAu_pred_stored = .false. + endif + + if (CS%fpmix) then + if (CS%id_uold > 0) call post_data(CS%id_uold, uold, CS%diag) + if (CS%id_vold > 0) call post_data(CS%id_vold, vold, CS%diag) + endif + + ! The time-averaged free surface height has already been set by the last call to btstep. + + ! Deallocate this memory to avoid a memory leak. ### We should revisit how this array is declared. -RWH + if (dyn_p_surf .and. associated(eta_PF_start)) deallocate(eta_PF_start) + + ! Here various terms used in to update the momentum equations are + ! offered for time averaging. + if (CS%id_PFu > 0) call post_data(CS%id_PFu, CS%PFu, CS%diag) + if (CS%id_PFv > 0) call post_data(CS%id_PFv, CS%PFv, CS%diag) + if (CS%id_CAu > 0) call post_data(CS%id_CAu, CS%CAu, CS%diag) + if (CS%id_CAv > 0) call post_data(CS%id_CAv, CS%CAv, CS%diag) + + ! Here the thickness fluxes are offered for time averaging. + if (CS%id_uh > 0) call post_data(CS%id_uh, uh, CS%diag) + if (CS%id_vh > 0) call post_data(CS%id_vh, vh, CS%diag) + if (CS%id_uav > 0) call post_data(CS%id_uav, u_av, CS%diag) + if (CS%id_vav > 0) call post_data(CS%id_vav, v_av, CS%diag) + if (CS%id_u_BT_accel > 0) call post_data(CS%id_u_BT_accel, CS%u_accel_bt, CS%diag) + if (CS%id_v_BT_accel > 0) call post_data(CS%id_v_BT_accel, CS%v_accel_bt, CS%diag) + + ! Calculate effective areas and post data + if (CS%id_ueffA > 0) then + ueffA(:,:,:) = 0 + do k=1,nz ; do j=js,je ; do I=Isq,Ieq + if (abs(up(I,j,k)) > 0.) ueffA(I,j,k) = uh(I,j,k) / up(I,j,k) + enddo ; enddo ; enddo + call post_data(CS%id_ueffA, ueffA, CS%diag) + endif + + if (CS%id_veffA > 0) then + veffA(:,:,:) = 0 + do k=1,nz ; do J=Jsq,Jeq ; do i=is,ie + if (abs(vp(i,J,k)) > 0.) veffA(i,J,k) = vh(i,J,k) / vp(i,J,k) + enddo ; enddo ; enddo + call post_data(CS%id_veffA, veffA, CS%diag) + endif + + ! Diagnostics of the fractional thicknesses times momentum budget terms + ! 3D diagnostics hf_PFu etc. are commented because there is no clarity on proper remapping grid option. + ! The code is retained for debugging purposes in the future. + !if (CS%id_hf_PFu > 0) call post_product_u(CS%id_hf_PFu, CS%PFu, CS%ADp%diag_hfrac_u, G, nz, CS%diag) + !if (CS%id_hf_PFv > 0) call post_product_v(CS%id_hf_PFv, CS%PFv, CS%ADp%diag_hfrac_v, G, nz, CS%diag) + !if (CS%id_hf_CAu > 0) call post_product_u(CS%id_hf_CAu, CS%CAu, CS%ADp%diag_hfrac_u, G, nz, CS%diag) + !if (CS%id_hf_CAv > 0) call post_product_v(CS%id_hf_CAv, CS%CAv, CS%ADp%diag_hfrac_v, G, nz, CS%diag) + !if (CS%id_hf_u_BT_accel > 0) & + ! call post_product_u(CS%id_hf_u_BT_accel, CS%u_accel_bt, CS%ADp%diag_hfrac_u, G, nz, CS%diag) + !if (CS%id_hf_v_BT_accel > 0) & + ! call post_product_v(CS%id_hf_v_BT_accel, CS%v_accel_bt, CS%ADp%diag_hfrac_v, G, nz, CS%diag) + + ! Diagnostics for the vertical sum of layer thickness x prssure force accelerations + if (CS%id_intz_PFu_2d > 0) call post_product_sum_u(CS%id_intz_PFu_2d, CS%PFu, CS%ADp%diag_hu, G, nz, CS%diag) + if (CS%id_intz_PFv_2d > 0) call post_product_sum_v(CS%id_intz_PFv_2d, CS%PFv, CS%ADp%diag_hv, G, nz, CS%diag) + + ! Diagnostics for thickness-weighted vertically averaged prssure force accelerations + if (CS%id_hf_PFu_2d > 0) call post_product_sum_u(CS%id_hf_PFu_2d, CS%PFu, CS%ADp%diag_hfrac_u, G, nz, CS%diag) + if (CS%id_hf_PFv_2d > 0) call post_product_sum_v(CS%id_hf_PFv_2d, CS%PFv, CS%ADp%diag_hfrac_v, G, nz, CS%diag) + + ! Diagnostics for thickness x prssure force accelerations + if (CS%id_h_PFu > 0) call post_product_u(CS%id_h_PFu, CS%PFu, CS%ADp%diag_hu, G, nz, CS%diag) + if (CS%id_h_PFv > 0) call post_product_v(CS%id_h_PFv, CS%PFv, CS%ADp%diag_hv, G, nz, CS%diag) + + ! Diagnostics of Coriolis acceleratations + if (CS%id_intz_CAu_2d > 0) call post_product_sum_u(CS%id_intz_CAu_2d, CS%CAu, CS%ADp%diag_hu, G, nz, CS%diag) + if (CS%id_intz_CAv_2d > 0) call post_product_sum_v(CS%id_intz_CAv_2d, CS%CAv, CS%ADp%diag_hv, G, nz, CS%diag) + if (CS%id_hf_CAu_2d > 0) call post_product_sum_u(CS%id_hf_CAu_2d, CS%CAu, CS%ADp%diag_hfrac_u, G, nz, CS%diag) + if (CS%id_hf_CAv_2d > 0) call post_product_sum_v(CS%id_hf_CAv_2d, CS%CAv, CS%ADp%diag_hfrac_v, G, nz, CS%diag) + if (CS%id_h_CAu > 0) call post_product_u(CS%id_h_CAu, CS%CAu, CS%ADp%diag_hu, G, nz, CS%diag) + if (CS%id_h_CAv > 0) call post_product_v(CS%id_h_CAv, CS%CAv, CS%ADp%diag_hv, G, nz, CS%diag) + + ! Diagnostics of barotropic solver acceleratations + if (CS%id_intz_u_BT_accel_2d > 0) & + call post_product_sum_u(CS%id_intz_u_BT_accel_2d, CS%u_accel_bt, CS%ADp%diag_hu, G, nz, CS%diag) + if (CS%id_intz_v_BT_accel_2d > 0) & + call post_product_sum_v(CS%id_intz_v_BT_accel_2d, CS%v_accel_bt, CS%ADp%diag_hv, G, nz, CS%diag) + if (CS%id_hf_u_BT_accel_2d > 0) & + call post_product_sum_u(CS%id_hf_u_BT_accel_2d, CS%u_accel_bt, CS%ADp%diag_hfrac_u, G, nz, CS%diag) + if (CS%id_hf_v_BT_accel_2d > 0) & + call post_product_sum_v(CS%id_hf_v_BT_accel_2d, CS%v_accel_bt, CS%ADp%diag_hfrac_v, G, nz, CS%diag) + if (CS%id_h_u_BT_accel > 0) & + call post_product_u(CS%id_h_u_BT_accel, CS%u_accel_bt, CS%ADp%diag_hu, G, nz, CS%diag) + if (CS%id_h_v_BT_accel > 0) & + call post_product_v(CS%id_h_v_BT_accel, CS%v_accel_bt, CS%ADp%diag_hv, G, nz, CS%diag) + + ! Diagnostics for momentum budget terms multiplied by visc_rem_[uv], + if (CS%id_PFu_visc_rem > 0) call post_product_u(CS%id_PFu_visc_rem, CS%PFu, CS%ADp%visc_rem_u, G, nz, CS%diag) + if (CS%id_PFv_visc_rem > 0) call post_product_v(CS%id_PFv_visc_rem, CS%PFv, CS%ADp%visc_rem_v, G, nz, CS%diag) + if (CS%id_CAu_visc_rem > 0) call post_product_u(CS%id_CAu_visc_rem, CS%CAu, CS%ADp%visc_rem_u, G, nz, CS%diag) + if (CS%id_CAv_visc_rem > 0) call post_product_v(CS%id_CAv_visc_rem, CS%CAv, CS%ADp%visc_rem_v, G, nz, CS%diag) + if (CS%id_u_BT_accel_visc_rem > 0) & + call post_product_u(CS%id_u_BT_accel_visc_rem, CS%u_accel_bt, CS%ADp%visc_rem_u, G, nz, CS%diag) + if (CS%id_v_BT_accel_visc_rem > 0) & + call post_product_v(CS%id_v_BT_accel_visc_rem, CS%v_accel_bt, CS%ADp%visc_rem_v, G, nz, CS%diag) + + ! Diagnostics related to changes in eta + if (CS%id_deta_dt > 0) call post_data(CS%id_deta_dt, deta_dt, CS%diag) + + if (CS%debug) then + call MOM_state_chksum("Corrector ", u_inst, v_inst, h, uh, vh, G, GV, US, symmetric=sym) + call uvchksum("Corrector avg [uv]", u_av, v_av, G%HI, haloshift=1, symmetric=sym, scale=US%L_T_to_m_s) + call hchksum(h_av, "Corrector avg h", G%HI, haloshift=1, scale=GV%H_to_MKS) + ! call MOM_state_chksum("Corrector avg ", u_av, v_av, h_av, uh, vh, G, GV, US) + endif + + if (showCallTree) call callTree_leave("step_MOM_dyn_split_RK2b()") + +end subroutine step_MOM_dyn_split_RK2b + +!> This subroutine sets up any auxiliary restart variables that are specific +!! to the split-explicit time stepping scheme. All variables registered here should +!! have the ability to be recreated if they are not present in a restart file. +subroutine register_restarts_dyn_split_RK2b(HI, GV, US, param_file, CS, restart_CS, uh, vh) + type(hor_index_type), intent(in) :: HI !< Horizontal index structure + type(verticalGrid_type), intent(in) :: GV !< ocean vertical grid structure + type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type + type(param_file_type), intent(in) :: param_file !< parameter file + type(MOM_dyn_split_RK2b_CS), pointer :: CS !< module control structure + type(MOM_restart_CS), intent(inout) :: restart_CS !< MOM restart control structure + real, dimension(SZIB_(HI),SZJ_(HI),SZK_(GV)), & + target, intent(inout) :: uh !< zonal volume or mass transport [H L2 T-1 ~> m3 s-1 or kg s-1] + real, dimension(SZI_(HI),SZJB_(HI),SZK_(GV)), & + target, intent(inout) :: vh !< merid volume or mass transport [H L2 T-1 ~> m3 s-1 or kg s-1] + + character(len=40) :: mdl = "MOM_dynamics_split_RK2b" ! This module's name. + type(vardesc) :: vd(2) + character(len=48) :: thickness_units, flux_units + + integer :: isd, ied, jsd, jed, nz, IsdB, IedB, JsdB, JedB + + isd = HI%isd ; ied = HI%ied ; jsd = HI%jsd ; jed = HI%jed ; nz = GV%ke + IsdB = HI%IsdB ; IedB = HI%IedB ; JsdB = HI%JsdB ; JedB = HI%JedB + + ! This is where a control structure specific to this module would be allocated. + if (associated(CS)) then + call MOM_error(WARNING, "register_restarts_dyn_split_RK2b called with an associated "// & + "control structure.") + return + endif + allocate(CS) + + ALLOC_(CS%diffu(IsdB:IedB,jsd:jed,nz)) ; CS%diffu(:,:,:) = 0.0 + ALLOC_(CS%diffv(isd:ied,JsdB:JedB,nz)) ; CS%diffv(:,:,:) = 0.0 + ALLOC_(CS%CAu(IsdB:IedB,jsd:jed,nz)) ; CS%CAu(:,:,:) = 0.0 + ALLOC_(CS%CAv(isd:ied,JsdB:JedB,nz)) ; CS%CAv(:,:,:) = 0.0 + ALLOC_(CS%CAu_pred(IsdB:IedB,jsd:jed,nz)) ; CS%CAu_pred(:,:,:) = 0.0 + ALLOC_(CS%CAv_pred(isd:ied,JsdB:JedB,nz)) ; CS%CAv_pred(:,:,:) = 0.0 + ALLOC_(CS%PFu(IsdB:IedB,jsd:jed,nz)) ; CS%PFu(:,:,:) = 0.0 + ALLOC_(CS%PFv(isd:ied,JsdB:JedB,nz)) ; CS%PFv(:,:,:) = 0.0 + + ALLOC_(CS%eta(isd:ied,jsd:jed)) ; CS%eta(:,:) = 0.0 + ALLOC_(CS%u_av(IsdB:IedB,jsd:jed,nz)) ; CS%u_av(:,:,:) = 0.0 + ALLOC_(CS%v_av(isd:ied,JsdB:JedB,nz)) ; CS%v_av(:,:,:) = 0.0 + ALLOC_(CS%h_av(isd:ied,jsd:jed,nz)) ; CS%h_av(:,:,:) = GV%Angstrom_H + + thickness_units = get_thickness_units(GV) + flux_units = get_flux_units(GV) + + call get_param(param_file, mdl, "STORE_CORIOLIS_ACCEL", CS%store_CAu, & + "If true, calculate the Coriolis accelerations at the end of each "//& + "timestep for use in the predictor step of the next split RK2 timestep.", & + default=.true., do_not_log=.true.) + + if (GV%Boussinesq) then + call register_restart_field(CS%eta, "sfc", .false., restart_CS, & + longname="Free surface Height", units=thickness_units, conversion=GV%H_to_mks) + else + call register_restart_field(CS%eta, "p_bot", .false., restart_CS, & + longname="Bottom Pressure", units=thickness_units, conversion=GV%H_to_mks) + endif + + ! These are needed, either to calculate CAu and CAv or to calculate the velocity anomalies in + ! the barotropic solver's Coriolis terms. + vd(1) = var_desc("u2", "m s-1", "Auxiliary Zonal velocity", 'u', 'L') + vd(2) = var_desc("v2", "m s-1", "Auxiliary Meridional velocity", 'v', 'L') + call register_restart_pair(CS%u_av, CS%v_av, vd(1), vd(2), .false., restart_CS, & + conversion=US%L_T_to_m_s) + + if (CS%store_CAu) then + vd(1) = var_desc("CAu", "m s-2", "Zonal Coriolis and advactive acceleration", 'u', 'L') + vd(2) = var_desc("CAv", "m s-2", "Meridional Coriolis and advactive acceleration", 'v', 'L') + call register_restart_pair(CS%CAu_pred, CS%CAv_pred, vd(1), vd(2), .false., restart_CS, & + conversion=US%L_T2_to_m_s2) + else + call register_restart_field(CS%h_av, "h2", .false., restart_CS, & + longname="Auxiliary Layer Thickness", units=thickness_units, conversion=GV%H_to_mks) + + vd(1) = var_desc("uh", flux_units, "Zonal thickness flux", 'u', 'L') + vd(2) = var_desc("vh", flux_units, "Meridional thickness flux", 'v', 'L') + call register_restart_pair(uh, vh, vd(1), vd(2), .false., restart_CS, & + conversion=GV%H_to_MKS*US%L_to_m**2*US%s_to_T) + endif + + vd(1) = var_desc("diffu", "m s-2", "Zonal horizontal viscous acceleration", 'u', 'L') + vd(2) = var_desc("diffv", "m s-2", "Meridional horizontal viscous acceleration", 'v', 'L') + call register_restart_pair(CS%diffu, CS%diffv, vd(1), vd(2), .false., restart_CS, & + conversion=US%L_T2_to_m_s2) + + call register_barotropic_restarts(HI, GV, US, param_file, CS%barotropic_CSp, restart_CS) + +end subroutine register_restarts_dyn_split_RK2b + +!> This subroutine does remapping for the auxiliary restart variables that are used +!! with the split RK2 time stepping scheme. +subroutine remap_dyn_split_RK2b_aux_vars(G, GV, CS, h_old_u, h_old_v, h_new_u, h_new_v, ALE_CSp) + type(ocean_grid_type), intent(inout) :: G !< ocean grid structure + type(verticalGrid_type), intent(in) :: GV !< ocean vertical grid structure + type(MOM_dyn_split_RK2b_CS), pointer :: CS !< module control structure + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & + intent(in) :: h_old_u !< Source grid thickness at zonal + !! velocity points [H ~> m or kg m-2] + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & + intent(in) :: h_old_v !< Source grid thickness at meridional + !! velocity points [H ~> m or kg m-2] + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & + intent(in) :: h_new_u !< Destination grid thickness at zonal + !! velocity points [H ~> m or kg m-2] + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & + intent(in) :: h_new_v !< Destination grid thickness at meridional + !! velocity points [H ~> m or kg m-2] + type(ALE_CS), pointer :: ALE_CSp !< ALE control structure to use when remapping + + if (.not.CS%remap_aux) return + + if (CS%store_CAu) then + call ALE_remap_velocities(ALE_CSp, G, GV, h_old_u, h_old_v, h_new_u, h_new_v, CS%u_av, CS%v_av) + call pass_vector(CS%u_av, CS%v_av, G%Domain, complete=.false.) + call ALE_remap_velocities(ALE_CSp, G, GV, h_old_u, h_old_v, h_new_u, h_new_v, CS%CAu_pred, CS%CAv_pred) + call pass_vector(CS%CAu_pred, CS%CAv_pred, G%Domain, complete=.true.) + endif + + call ALE_remap_velocities(ALE_CSp, G, GV, h_old_u, h_old_v, h_new_u, h_new_v, CS%diffu, CS%diffv) + +end subroutine remap_dyn_split_RK2b_aux_vars + +!> This subroutine initializes all of the variables that are used by this +!! dynamic core, including diagnostics and the cpu clocks. +subroutine initialize_dyn_split_RK2b(u, v, h, uh, vh, eta, Time, G, GV, US, param_file, & + diag, CS, restart_CS, dt, Accel_diag, Cont_diag, MIS, & + VarMix, MEKE, thickness_diffuse_CSp, & + OBC, update_OBC_CSp, ALE_CSp, set_visc, & + visc, dirs, ntrunc, pbv, calc_dtbt, cont_stencil) + type(ocean_grid_type), intent(inout) :: G !< ocean grid structure + type(verticalGrid_type), intent(in) :: GV !< ocean vertical grid structure + type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & + intent(inout) :: u !< zonal velocity [L T-1 ~> m s-1] + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & + intent(inout) :: v !< merid velocity [L T-1 ~> m s-1] + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & + intent(inout) :: h !< layer thickness [H ~> m or kg m-2] + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & + target, intent(inout) :: uh !< zonal volume/mass transport [H L2 T-1 ~> m3 s-1 or kg s-1] + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & + target, intent(inout) :: vh !< merid volume/mass transport [H L2 T-1 ~> m3 s-1 or kg s-1] + real, dimension(SZI_(G),SZJ_(G)), intent(inout) :: eta !< free surface height or column mass [H ~> m or kg m-2] + type(time_type), target, intent(in) :: Time !< current model time + type(param_file_type), intent(in) :: param_file !< parameter file for parsing + type(diag_ctrl), target, intent(inout) :: diag !< to control diagnostics + type(MOM_dyn_split_RK2b_CS), pointer :: CS !< module control structure + type(MOM_restart_CS), intent(inout) :: restart_CS !< MOM restart control structure + real, intent(in) :: dt !< time step [T ~> s] + type(accel_diag_ptrs), target, intent(inout) :: Accel_diag !< points to momentum equation terms for + !! budget analysis + type(cont_diag_ptrs), target, intent(inout) :: Cont_diag !< points to terms in continuity equation + type(ocean_internal_state), intent(inout) :: MIS !< "MOM6 internal state" used to pass + !! diagnostic pointers + type(VarMix_CS), intent(inout) :: VarMix !< points to spatially variable viscosities + type(MEKE_type), intent(inout) :: MEKE !< MEKE fields + type(thickness_diffuse_CS), intent(inout) :: thickness_diffuse_CSp !< Pointer to the control structure + !! used for the isopycnal height diffusive transport. + type(ocean_OBC_type), pointer :: OBC !< points to OBC related fields + type(update_OBC_CS), pointer :: update_OBC_CSp !< points to OBC update related fields + type(ALE_CS), pointer :: ALE_CSp !< points to ALE control structure + type(set_visc_CS), target, intent(in) :: set_visc !< set_visc control structure + type(vertvisc_type), intent(inout) :: visc !< vertical viscosities, bottom drag, and related + type(directories), intent(in) :: dirs !< contains directory paths + integer, target, intent(inout) :: ntrunc !< A target for the variable that records + !! the number of times the velocity is + !! truncated (this should be 0). + logical, intent(out) :: calc_dtbt !< If true, recalculate the barotropic time step + type(porous_barrier_type), intent(in) :: pbv !< porous barrier fractional cell metrics + integer, intent(out) :: cont_stencil !< The stencil for thickness + !! from the continuity solver. + + ! local variables + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: h_tmp ! A temporary copy of the layer thicknesses [H ~> m or kg m-2] + character(len=40) :: mdl = "MOM_dynamics_split_RK2b" ! This module's name. + ! This include declares and sets the variable "version". +# include "version_variable.h" + character(len=48) :: thickness_units, flux_units, eta_rest_name + type(group_pass_type) :: pass_av_h_uvh + logical :: debug_truncations + logical :: read_uv, read_h2 + + integer :: i, j, k, is, ie, js, je, isd, ied, jsd, jed, nz + integer :: IsdB, IedB, JsdB, JedB + is = G%isc ; ie = G%iec ; js = G%jsc ; je = G%jec ; nz = GV%ke + isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed + IsdB = G%IsdB ; IedB = G%IedB ; JsdB = G%JsdB ; JedB = G%JedB + + if (.not.associated(CS)) call MOM_error(FATAL, & + "initialize_dyn_split_RK2b called with an unassociated control structure.") + if (CS%module_is_initialized) then + call MOM_error(WARNING, "initialize_dyn_split_RK2b called with a control "// & + "structure that has already been initialized.") + return + endif + CS%module_is_initialized = .true. + + CS%diag => diag + + call log_version(param_file, mdl, version, "") + call get_param(param_file, mdl, "TIDES", CS%use_tides, & + "If true, apply tidal momentum forcing.", default=.false.) + call get_param(param_file, mdl, "CALCULATE_SAL", CS%calculate_SAL, & + "If true, calculate self-attraction and loading.", default=CS%use_tides) + call get_param(param_file, mdl, "BE", CS%be, & + "If SPLIT is true, BE determines the relative weighting "//& + "of a 2nd-order Runga-Kutta baroclinic time stepping "//& + "scheme (0.5) and a backward Euler scheme (1) that is "//& + "used for the Coriolis and inertial terms. BE may be "//& + "from 0.5 to 1, but instability may occur near 0.5. "//& + "BE is also applicable if SPLIT is false and USE_RK2 "//& + "is true.", units="nondim", default=0.6) + call get_param(param_file, mdl, "BEGW", CS%begw, & + "If SPLIT is true, BEGW is a number from 0 to 1 that "//& + "controls the extent to which the treatment of gravity "//& + "waves is forward-backward (0) or simulated backward "//& + "Euler (1). 0 is almost always used. "//& + "If SPLIT is false and USE_RK2 is true, BEGW can be "//& + "between 0 and 0.5 to damp gravity waves.", & + units="nondim", default=0.0) + + call get_param(param_file, mdl, "SPLIT_BOTTOM_STRESS", CS%split_bottom_stress, & + "If true, provide the bottom stress calculated by the "//& + "vertical viscosity to the barotropic solver.", default=.false.) + call get_param(param_file, mdl, "STORE_CORIOLIS_ACCEL", CS%store_CAu, & + "If true, calculate the Coriolis accelerations at the end of each "//& + "timestep for use in the predictor step of the next split RK2 timestep.", & + default=.true.) + call get_param(param_file, mdl, "FPMIX", CS%fpmix, & + "If true, apply profiles of momentum flux magnitude and direction.", & + default=.false.) + call get_param(param_file, mdl, "REMAP_AUXILIARY_VARS", CS%remap_aux, & + "If true, apply ALE remapping to all of the auxiliary 3-dimensional "//& + "variables that are needed to reproduce across restarts, similarly to "//& + "what is already being done with the primary state variables. "//& + "The default should be changed to true.", default=.false., do_not_log=.true.) + if (CS%remap_aux .and. .not.CS%store_CAu) call MOM_error(FATAL, & + "REMAP_AUXILIARY_VARS requires that STORE_CORIOLIS_ACCEL = True.") + call get_param(param_file, mdl, "DEBUG", CS%debug, & + "If true, write out verbose debugging data.", & + default=.false., debuggingParam=.true.) + call get_param(param_file, mdl, "DEBUG_OBC", CS%debug_OBC, default=.false.) + call get_param(param_file, mdl, "DEBUG_TRUNCATIONS", debug_truncations, & + default=.false.) + + allocate(CS%taux_bot(IsdB:IedB,jsd:jed), source=0.0) + allocate(CS%tauy_bot(isd:ied,JsdB:JedB), source=0.0) + + ALLOC_(CS%uhbt(IsdB:IedB,jsd:jed)) ; CS%uhbt(:,:) = 0.0 + ALLOC_(CS%vhbt(isd:ied,JsdB:JedB)) ; CS%vhbt(:,:) = 0.0 + ALLOC_(CS%visc_rem_u(IsdB:IedB,jsd:jed,nz)) ; CS%visc_rem_u(:,:,:) = 0.0 + ALLOC_(CS%visc_rem_v(isd:ied,JsdB:JedB,nz)) ; CS%visc_rem_v(:,:,:) = 0.0 + ALLOC_(CS%eta_PF(isd:ied,jsd:jed)) ; CS%eta_PF(:,:) = 0.0 + ALLOC_(CS%pbce(isd:ied,jsd:jed,nz)) ; CS%pbce(:,:,:) = 0.0 + + ALLOC_(CS%u_accel_bt(IsdB:IedB,jsd:jed,nz)) ; CS%u_accel_bt(:,:,:) = 0.0 + ALLOC_(CS%v_accel_bt(isd:ied,JsdB:JedB,nz)) ; CS%v_accel_bt(:,:,:) = 0.0 + ALLOC_(CS%PFu_Stokes(IsdB:IedB,jsd:jed,nz)) ; CS%PFu_Stokes(:,:,:) = 0.0 + ALLOC_(CS%PFv_Stokes(isd:ied,JsdB:JedB,nz)) ; CS%PFv_Stokes(:,:,:) = 0.0 + + MIS%diffu => CS%diffu + MIS%diffv => CS%diffv + MIS%PFu => CS%PFu + MIS%PFv => CS%PFv + MIS%CAu => CS%CAu + MIS%CAv => CS%CAv + MIS%pbce => CS%pbce + MIS%u_accel_bt => CS%u_accel_bt + MIS%v_accel_bt => CS%v_accel_bt + MIS%u_av => CS%u_av + MIS%v_av => CS%v_av + + CS%ADp => Accel_diag + CS%CDp => Cont_diag + Accel_diag%diffu => CS%diffu + Accel_diag%diffv => CS%diffv + Accel_diag%PFu => CS%PFu + Accel_diag%PFv => CS%PFv + Accel_diag%CAu => CS%CAu + Accel_diag%CAv => CS%CAv + Accel_diag%u_accel_bt => CS%u_accel_bt + Accel_diag%v_accel_bt => CS%v_accel_bt + + allocate(CS%AD_pred) + CS%AD_pred%diffu => CS%diffu + CS%AD_pred%diffv => CS%diffv + CS%AD_pred%PFu => CS%PFu + CS%AD_pred%PFv => CS%PFv + CS%AD_pred%CAu => CS%CAu_pred + CS%AD_pred%CAv => CS%CAv_pred + CS%AD_pred%u_accel_bt => CS%u_accel_bt + CS%AD_pred%v_accel_bt => CS%v_accel_bt + +! Accel_diag%pbce => CS%pbce +! Accel_diag%u_accel_bt => CS%u_accel_bt ; Accel_diag%v_accel_bt => CS%v_accel_bt +! Accel_diag%u_av => CS%u_av ; Accel_diag%v_av => CS%v_av + + id_clock_pass_init = cpu_clock_id('(Ocean init message passing)', & + grain=CLOCK_ROUTINE) + + call continuity_init(Time, G, GV, US, param_file, diag, CS%continuity_CSp) + cont_stencil = continuity_stencil(CS%continuity_CSp) + call CoriolisAdv_init(Time, G, GV, US, param_file, diag, CS%ADp, CS%CoriolisAdv) + if (CS%calculate_SAL) call SAL_init(G, US, param_file, CS%SAL_CSp) + if (CS%use_tides) call tidal_forcing_init(Time, G, US, param_file, CS%tides_CSp) + call PressureForce_init(Time, G, GV, US, param_file, diag, CS%PressureForce_CSp, & + CS%SAL_CSp, CS%tides_CSp) + call hor_visc_init(Time, G, GV, US, param_file, diag, CS%hor_visc, ADp=CS%ADp) + call vertvisc_init(MIS, Time, G, GV, US, param_file, diag, CS%ADp, dirs, & + ntrunc, CS%vertvisc_CSp) + CS%set_visc_CSp => set_visc + call updateCFLtruncationValue(Time, CS%vertvisc_CSp, US, & + activate=is_new_run(restart_CS) ) + + if (associated(ALE_CSp)) CS%ALE_CSp => ALE_CSp + if (associated(OBC)) then + CS%OBC => OBC + if (OBC%ramp) call update_OBC_ramp(Time, CS%OBC, US, & + activate=is_new_run(restart_CS) ) + endif + if (associated(update_OBC_CSp)) CS%update_OBC_CSp => update_OBC_CSp + + eta_rest_name = "sfc" ; if (.not.GV%Boussinesq) eta_rest_name = "p_bot" + if (.not. query_initialized(CS%eta, trim(eta_rest_name), restart_CS)) then + ! Estimate eta based on the layer thicknesses - h. With the Boussinesq + ! approximation, eta is the free surface height anomaly, while without it + ! eta is the mass of ocean per unit area. eta always has the same + ! dimensions as h, either m or kg m-3. + ! CS%eta(:,:) = 0.0 already from initialization. + if (GV%Boussinesq) then + do j=js,je ; do i=is,ie ; CS%eta(i,j) = -GV%Z_to_H * G%bathyT(i,j) ; enddo ; enddo + endif + do k=1,nz ; do j=js,je ; do i=is,ie + CS%eta(i,j) = CS%eta(i,j) + h(i,j,k) + enddo ; enddo ; enddo + call set_initialized(CS%eta, trim(eta_rest_name), restart_CS) + endif + ! Copy eta into an output array. + do j=js,je ; do i=is,ie ; eta(i,j) = CS%eta(i,j) ; enddo ; enddo + + call barotropic_init(u, v, h, CS%eta, Time, G, GV, US, param_file, diag, & + CS%barotropic_CSp, restart_CS, calc_dtbt, CS%BT_cont, & + CS%SAL_CSp) + + if (.not. query_initialized(CS%diffu, "diffu", restart_CS) .or. & + .not. query_initialized(CS%diffv, "diffv", restart_CS)) then + call horizontal_viscosity(u, v, h, CS%diffu, CS%diffv, MEKE, VarMix, G, GV, US, CS%hor_visc, & + OBC=CS%OBC, BT=CS%barotropic_CSp, TD=thickness_diffuse_CSp) + call set_initialized(CS%diffu, "diffu", restart_CS) + call set_initialized(CS%diffv, "diffv", restart_CS) + endif + + if (.not. query_initialized(CS%u_av, "u2", restart_CS) .or. & + .not. query_initialized(CS%v_av, "v2", restart_CS)) then + do k=1,nz ; do j=jsd,jed ; do I=IsdB,IedB ; CS%u_av(I,j,k) = u(I,j,k) ; enddo ; enddo ; enddo + do k=1,nz ; do J=JsdB,JedB ; do i=isd,ied ; CS%v_av(i,J,k) = v(i,J,k) ; enddo ; enddo ; enddo + call set_initialized(CS%u_av, "u2", restart_CS) + call set_initialized(CS%v_av, "v2", restart_CS) + endif + + if (CS%store_CAu) then + if (query_initialized(CS%CAu_pred, "CAu", restart_CS) .and. & + query_initialized(CS%CAv_pred, "CAv", restart_CS)) then + CS%CAu_pred_stored = .true. + else + call only_read_from_restarts(uh, vh, 'uh', 'vh', G, restart_CS, stagger=CGRID_NE, & + filename=dirs%input_filename, directory=dirs%restart_input_dir, & + success=read_uv, scale=US%m_to_L**2*US%T_to_s/GV%H_to_mks) + call only_read_from_restarts('h2', CS%h_av, G, restart_CS, & + filename=dirs%input_filename, directory=dirs%restart_input_dir, & + success=read_h2, scale=1.0/GV%H_to_mks) + if (read_uv .and. read_h2) then + call pass_var(CS%h_av, G%Domain, clock=id_clock_pass_init) + else + do k=1,nz ; do j=jsd,jed ; do i=isd,ied ; h_tmp(i,j,k) = h(i,j,k) ; enddo ; enddo ; enddo + call continuity(CS%u_av, CS%v_av, h, h_tmp, uh, vh, dt, G, GV, US, CS%continuity_CSp, CS%OBC, pbv) + call pass_var(h_tmp, G%Domain, clock=id_clock_pass_init) + do k=1,nz ; do j=jsd,jed ; do i=isd,ied + CS%h_av(i,j,k) = 0.5*(h(i,j,k) + h_tmp(i,j,k)) + enddo ; enddo ; enddo + endif + call pass_vector(CS%u_av, CS%v_av, G%Domain, halo=2, clock=id_clock_pass_init, complete=.false.) + call pass_vector(uh, vh, G%Domain, halo=2, clock=id_clock_pass_init, complete=.true.) + call CorAdCalc(CS%u_av, CS%v_av, CS%h_av, uh, vh, CS%CAu_pred, CS%CAv_pred, CS%OBC, CS%ADp, & + G, GV, US, CS%CoriolisAdv, pbv) !, Waves=Waves) + CS%CAu_pred_stored = .true. + endif + else + CS%CAu_pred_stored = .false. + ! This call is just here to initialize uh and vh. + if (.not. query_initialized(uh, "uh", restart_CS) .or. & + .not. query_initialized(vh, "vh", restart_CS)) then + do k=1,nz ; do j=jsd,jed ; do i=isd,ied ; h_tmp(i,j,k) = h(i,j,k) ; enddo ; enddo ; enddo + call continuity(u, v, h, h_tmp, uh, vh, dt, G, GV, US, CS%continuity_CSp, CS%OBC, pbv) + call pass_var(h_tmp, G%Domain, clock=id_clock_pass_init) + do k=1,nz ; do j=jsd,jed ; do i=isd,ied + CS%h_av(i,j,k) = 0.5*(h(i,j,k) + h_tmp(i,j,k)) + enddo ; enddo ; enddo + call set_initialized(uh, "uh", restart_CS) + call set_initialized(vh, "vh", restart_CS) + call set_initialized(CS%h_av, "h2", restart_CS) + ! Try reading the CAu and CAv fields from the restart file, in case this restart file is + ! using a newer format. + call only_read_from_restarts(CS%CAu_pred, CS%CAv_pred, "CAu", "CAv", G, restart_CS, & + stagger=CGRID_NE, filename=dirs%input_filename, directory=dirs%restart_input_dir, & + success=read_uv, scale=US%m_s_to_L_T*US%T_to_s) + CS%CAu_pred_stored = read_uv + else + if (.not. query_initialized(CS%h_av, "h2", restart_CS)) then + CS%h_av(:,:,:) = h(:,:,:) + call set_initialized(CS%h_av, "h2", restart_CS) + endif + endif + endif + call cpu_clock_begin(id_clock_pass_init) + call create_group_pass(pass_av_h_uvh, CS%u_av, CS%v_av, G%Domain, halo=2) + if (CS%CAu_pred_stored) then + call create_group_pass(pass_av_h_uvh, CS%CAu_pred, CS%CAv_pred, G%Domain, halo=2) + else + call create_group_pass(pass_av_h_uvh, CS%h_av, G%Domain, halo=2) + call create_group_pass(pass_av_h_uvh, uh, vh, G%Domain, halo=2) + endif + call do_group_pass(pass_av_h_uvh, G%Domain) + call cpu_clock_end(id_clock_pass_init) + + flux_units = get_flux_units(GV) + thickness_units = get_thickness_units(GV) + CS%id_uh = register_diag_field('ocean_model', 'uh', diag%axesCuL, Time, & + 'Zonal Thickness Flux', flux_units, conversion=GV%H_to_MKS*US%L_to_m**2*US%s_to_T, & + y_cell_method='sum', v_extensive=.true.) + CS%id_vh = register_diag_field('ocean_model', 'vh', diag%axesCvL, Time, & + 'Meridional Thickness Flux', flux_units, conversion=GV%H_to_MKS*US%L_to_m**2*US%s_to_T, & + x_cell_method='sum', v_extensive=.true.) + + CS%id_CAu = register_diag_field('ocean_model', 'CAu', diag%axesCuL, Time, & + 'Zonal Coriolis and Advective Acceleration', 'm s-2', conversion=US%L_T2_to_m_s2) + CS%id_CAv = register_diag_field('ocean_model', 'CAv', diag%axesCvL, Time, & + 'Meridional Coriolis and Advective Acceleration', 'm s-2', conversion=US%L_T2_to_m_s2) + CS%id_PFu = register_diag_field('ocean_model', 'PFu', diag%axesCuL, Time, & + 'Zonal Pressure Force Acceleration', 'm s-2', conversion=US%L_T2_to_m_s2) + CS%id_PFv = register_diag_field('ocean_model', 'PFv', diag%axesCvL, Time, & + 'Meridional Pressure Force Acceleration', 'm s-2', conversion=US%L_T2_to_m_s2) + CS%id_ueffA = register_diag_field('ocean_model', 'ueffA', diag%axesCuL, Time, & + 'Effective U-Face Area', 'm^2', conversion=GV%H_to_m*US%L_to_m, & + y_cell_method='sum', v_extensive=.true.) + CS%id_veffA = register_diag_field('ocean_model', 'veffA', diag%axesCvL, Time, & + 'Effective V-Face Area', 'm^2', conversion=GV%H_to_m*US%L_to_m, & + x_cell_method='sum', v_extensive=.true.) + if (GV%Boussinesq) then + CS%id_deta_dt = register_diag_field('ocean_model', 'deta_dt', diag%axesT1, Time, & + 'Barotropic SSH tendency due to dynamics', trim(thickness_units)//' s-1', conversion=GV%H_to_MKS*US%s_to_T) + else + CS%id_deta_dt = register_diag_field('ocean_model', 'deta_dt', diag%axesT1, Time, & + 'Barotropic column-mass tendency due to dynamics', trim(thickness_units)//' s-1', & + conversion=GV%H_to_mks*US%s_to_T) + endif + + !CS%id_hf_PFu = register_diag_field('ocean_model', 'hf_PFu', diag%axesCuL, Time, & + ! 'Fractional Thickness-weighted Zonal Pressure Force Acceleration', & + ! 'm s-2', v_extensive=.true., conversion=US%L_T2_to_m_s2) + !if (CS%id_hf_PFu > 0) call safe_alloc_ptr(CS%ADp%diag_hfrac_u,IsdB,IedB,jsd,jed,nz) + + !CS%id_hf_PFv = register_diag_field('ocean_model', 'hf_PFv', diag%axesCvL, Time, & + ! 'Fractional Thickness-weighted Meridional Pressure Force Acceleration', & + ! 'm s-2', v_extensive=.true., conversion=US%L_T2_to_m_s2) + !if (CS%id_hf_PFv > 0) call safe_alloc_ptr(CS%ADp%diag_hfrac_v,isd,ied,JsdB,JedB,nz) + + !CS%id_hf_CAu = register_diag_field('ocean_model', 'hf_CAu', diag%axesCuL, Time, & + ! 'Fractional Thickness-weighted Zonal Coriolis and Advective Acceleration', & + ! 'm s-2', v_extensive=.true., conversion=US%L_T2_to_m_s2) + !if (CS%id_hf_CAu > 0) call safe_alloc_ptr(CS%ADp%diag_hfrac_u,IsdB,IedB,jsd,jed,nz) + + !CS%id_hf_CAv = register_diag_field('ocean_model', 'hf_CAv', diag%axesCvL, Time, & + ! 'Fractional Thickness-weighted Meridional Coriolis and Advective Acceleration', & + ! 'm s-2', v_extensive=.true., conversion=US%L_T2_to_m_s2) + !if (CS%id_hf_CAv > 0) call safe_alloc_ptr(CS%ADp%diag_hfrac_v,isd,ied,JsdB,JedB,nz) + + CS%id_hf_PFu_2d = register_diag_field('ocean_model', 'hf_PFu_2d', diag%axesCu1, Time, & + 'Depth-sum Fractional Thickness-weighted Zonal Pressure Force Acceleration', & + 'm s-2', conversion=US%L_T2_to_m_s2) + if (CS%id_hf_PFu_2d > 0) call safe_alloc_ptr(CS%ADp%diag_hfrac_u,IsdB,IedB,jsd,jed,nz) + + CS%id_hf_PFv_2d = register_diag_field('ocean_model', 'hf_PFv_2d', diag%axesCv1, Time, & + 'Depth-sum Fractional Thickness-weighted Meridional Pressure Force Acceleration', & + 'm s-2', conversion=US%L_T2_to_m_s2) + if (CS%id_hf_PFv_2d > 0) call safe_alloc_ptr(CS%ADp%diag_hfrac_v,isd,ied,JsdB,JedB,nz) + + CS%id_h_PFu = register_diag_field('ocean_model', 'h_PFu', diag%axesCuL, Time, & + 'Thickness Multiplied Zonal Pressure Force Acceleration', & + 'm2 s-2', conversion=GV%H_to_m*US%L_T2_to_m_s2) + if (CS%id_h_PFu > 0) call safe_alloc_ptr(CS%ADp%diag_hu,IsdB,IedB,jsd,jed,nz) + + CS%id_h_PFv = register_diag_field('ocean_model', 'h_PFv', diag%axesCvL, Time, & + 'Thickness Multiplied Meridional Pressure Force Acceleration', & + 'm2 s-2', conversion=GV%H_to_m*US%L_T2_to_m_s2) + if (CS%id_h_PFv > 0) call safe_alloc_ptr(CS%ADp%diag_hv,isd,ied,JsdB,JedB,nz) + + CS%id_intz_PFu_2d = register_diag_field('ocean_model', 'intz_PFu_2d', diag%axesCu1, Time, & + 'Depth-integral of Zonal Pressure Force Acceleration', & + 'm2 s-2', conversion=GV%H_to_m*US%L_T2_to_m_s2) + if (CS%id_intz_PFu_2d > 0) call safe_alloc_ptr(CS%ADp%diag_hu,IsdB,IedB,jsd,jed,nz) + + CS%id_intz_PFv_2d = register_diag_field('ocean_model', 'intz_PFv_2d', diag%axesCv1, Time, & + 'Depth-integral of Meridional Pressure Force Acceleration', & + 'm2 s-2', conversion=GV%H_to_m*US%L_T2_to_m_s2) + if (CS%id_intz_PFv_2d > 0) call safe_alloc_ptr(CS%ADp%diag_hv,isd,ied,JsdB,JedB,nz) + + CS%id_hf_CAu_2d = register_diag_field('ocean_model', 'hf_CAu_2d', diag%axesCu1, Time, & + 'Depth-sum Fractional Thickness-weighted Zonal Coriolis and Advective Acceleration', & + 'm s-2', conversion=US%L_T2_to_m_s2) + if (CS%id_hf_CAu_2d > 0) call safe_alloc_ptr(CS%ADp%diag_hfrac_u,IsdB,IedB,jsd,jed,nz) + + CS%id_hf_CAv_2d = register_diag_field('ocean_model', 'hf_CAv_2d', diag%axesCv1, Time, & + 'Depth-sum Fractional Thickness-weighted Meridional Coriolis and Advective Acceleration', & + 'm s-2', conversion=US%L_T2_to_m_s2) + if (CS%id_hf_CAv_2d > 0) call safe_alloc_ptr(CS%ADp%diag_hfrac_v,isd,ied,JsdB,JedB,nz) + + CS%id_h_CAu = register_diag_field('ocean_model', 'h_CAu', diag%axesCuL, Time, & + 'Thickness Multiplied Zonal Coriolis and Advective Acceleration', & + 'm2 s-2', conversion=GV%H_to_m*US%L_T2_to_m_s2) + if (CS%id_h_CAu > 0) call safe_alloc_ptr(CS%ADp%diag_hu,IsdB,IedB,jsd,jed,nz) + + CS%id_h_CAv = register_diag_field('ocean_model', 'h_CAv', diag%axesCvL, Time, & + 'Thickness Multiplied Meridional Coriolis and Advective Acceleration', & + 'm2 s-2', conversion=GV%H_to_m*US%L_T2_to_m_s2) + if (CS%id_h_CAv > 0) call safe_alloc_ptr(CS%ADp%diag_hv,isd,ied,JsdB,JedB,nz) + + CS%id_intz_CAu_2d = register_diag_field('ocean_model', 'intz_CAu_2d', diag%axesCu1, Time, & + 'Depth-integral of Zonal Coriolis and Advective Acceleration', & + 'm2 s-2', conversion=GV%H_to_m*US%L_T2_to_m_s2) + if (CS%id_intz_CAu_2d > 0) call safe_alloc_ptr(CS%ADp%diag_hu,IsdB,IedB,jsd,jed,nz) + + CS%id_intz_CAv_2d = register_diag_field('ocean_model', 'intz_CAv_2d', diag%axesCv1, Time, & + 'Depth-integral of Meridional Coriolis and Advective Acceleration', & + 'm2 s-2', conversion=GV%H_to_m*US%L_T2_to_m_s2) + if (CS%id_intz_CAv_2d > 0) call safe_alloc_ptr(CS%ADp%diag_hv,isd,ied,JsdB,JedB,nz) + + CS%id_uav = register_diag_field('ocean_model', 'uav', diag%axesCuL, Time, & + 'Barotropic-step Averaged Zonal Velocity', 'm s-1', conversion=US%L_T_to_m_s) + CS%id_vav = register_diag_field('ocean_model', 'vav', diag%axesCvL, Time, & + 'Barotropic-step Averaged Meridional Velocity', 'm s-1', conversion=US%L_T_to_m_s) + + CS%id_u_BT_accel = register_diag_field('ocean_model', 'u_BT_accel', diag%axesCuL, Time, & + 'Barotropic Anomaly Zonal Acceleration', 'm s-2', conversion=US%L_T2_to_m_s2) + CS%id_v_BT_accel = register_diag_field('ocean_model', 'v_BT_accel', diag%axesCvL, Time, & + 'Barotropic Anomaly Meridional Acceleration', 'm s-2', conversion=US%L_T2_to_m_s2) + + !CS%id_hf_u_BT_accel = register_diag_field('ocean_model', 'hf_u_BT_accel', diag%axesCuL, Time, & + ! 'Fractional Thickness-weighted Barotropic Anomaly Zonal Acceleration', & + ! 'm s-2', v_extensive=.true., conversion=US%L_T2_to_m_s2) + !if (CS%id_hf_u_BT_accel > 0) call safe_alloc_ptr(CS%ADp%diag_hfrac_u,IsdB,IedB,jsd,jed,nz) + + !CS%id_hf_v_BT_accel = register_diag_field('ocean_model', 'hf_v_BT_accel', diag%axesCvL, Time, & + ! 'Fractional Thickness-weighted Barotropic Anomaly Meridional Acceleration', & + ! 'm s-2', v_extensive=.true., conversion=US%L_T2_to_m_s2) + !if (CS%id_hf_v_BT_accel > 0) call safe_alloc_ptr(CS%ADp%diag_hfrac_v,isd,ied,JsdB,JedB,nz) + + CS%id_hf_u_BT_accel_2d = register_diag_field('ocean_model', 'hf_u_BT_accel_2d', diag%axesCu1, Time, & + 'Depth-sum Fractional Thickness-weighted Barotropic Anomaly Zonal Acceleration', & + 'm s-2', conversion=US%L_T2_to_m_s2) + if (CS%id_hf_u_BT_accel_2d > 0) call safe_alloc_ptr(CS%ADp%diag_hfrac_u,IsdB,IedB,jsd,jed,nz) + + CS%id_hf_v_BT_accel_2d = register_diag_field('ocean_model', 'hf_v_BT_accel_2d', diag%axesCv1, Time, & + 'Depth-sum Fractional Thickness-weighted Barotropic Anomaly Meridional Acceleration', & + 'm s-2', conversion=US%L_T2_to_m_s2) + if (CS%id_hf_v_BT_accel_2d > 0) call safe_alloc_ptr(CS%ADp%diag_hfrac_v,isd,ied,JsdB,JedB,nz) + + CS%id_h_u_BT_accel = register_diag_field('ocean_model', 'h_u_BT_accel', diag%axesCuL, Time, & + 'Thickness Multiplied Barotropic Anomaly Zonal Acceleration', & + 'm2 s-2', conversion=GV%H_to_m*US%L_T2_to_m_s2) + if (CS%id_h_u_BT_accel > 0) call safe_alloc_ptr(CS%ADp%diag_hu,IsdB,IedB,jsd,jed,nz) + + CS%id_h_v_BT_accel = register_diag_field('ocean_model', 'h_v_BT_accel', diag%axesCvL, Time, & + 'Thickness Multiplied Barotropic Anomaly Meridional Acceleration', & + 'm2 s-2', conversion=GV%H_to_m*US%L_T2_to_m_s2) + if (CS%id_h_v_BT_accel > 0) call safe_alloc_ptr(CS%ADp%diag_hv,isd,ied,JsdB,JedB,nz) + + CS%id_intz_u_BT_accel_2d = register_diag_field('ocean_model', 'intz_u_BT_accel_2d', diag%axesCu1, Time, & + 'Depth-integral of Barotropic Anomaly Zonal Acceleration', & + 'm2 s-2', conversion=GV%H_to_m*US%L_T2_to_m_s2) + if (CS%id_intz_u_BT_accel_2d > 0) call safe_alloc_ptr(CS%ADp%diag_hu,IsdB,IedB,jsd,jed,nz) + + CS%id_intz_v_BT_accel_2d = register_diag_field('ocean_model', 'intz_v_BT_accel_2d', diag%axesCv1, Time, & + 'Depth-integral of Barotropic Anomaly Meridional Acceleration', & + 'm2 s-2', conversion=GV%H_to_m*US%L_T2_to_m_s2) + if (CS%id_intz_v_BT_accel_2d > 0) call safe_alloc_ptr(CS%ADp%diag_hv,isd,ied,JsdB,JedB,nz) + + CS%id_PFu_visc_rem = register_diag_field('ocean_model', 'PFu_visc_rem', diag%axesCuL, Time, & + 'Zonal Pressure Force Acceleration multiplied by the viscous remnant', & + 'm s-2', conversion=US%L_T2_to_m_s2) + if (CS%id_PFu_visc_rem > 0) call safe_alloc_ptr(CS%ADp%visc_rem_u,IsdB,IedB,jsd,jed,nz) + CS%id_PFv_visc_rem = register_diag_field('ocean_model', 'PFv_visc_rem', diag%axesCvL, Time, & + 'Meridional Pressure Force Acceleration multiplied by the viscous remnant', & + 'm s-2', conversion=US%L_T2_to_m_s2) + if (CS%id_PFv_visc_rem > 0) call safe_alloc_ptr(CS%ADp%visc_rem_v,isd,ied,JsdB,JedB,nz) + + CS%id_CAu_visc_rem = register_diag_field('ocean_model', 'CAu_visc_rem', diag%axesCuL, Time, & + 'Zonal Coriolis and Advective Acceleration multiplied by the viscous remnant', & + 'm s-2', conversion=US%L_T2_to_m_s2) + if (CS%id_CAu_visc_rem > 0) call safe_alloc_ptr(CS%ADp%visc_rem_u,IsdB,IedB,jsd,jed,nz) + CS%id_CAv_visc_rem = register_diag_field('ocean_model', 'CAv_visc_rem', diag%axesCvL, Time, & + 'Meridional Coriolis and Advective Acceleration multiplied by the viscous remnant', & + 'm s-2', conversion=US%L_T2_to_m_s2) + if (CS%id_CAv_visc_rem > 0) call safe_alloc_ptr(CS%ADp%visc_rem_v,isd,ied,JsdB,JedB,nz) + + CS%id_u_BT_accel_visc_rem = register_diag_field('ocean_model', 'u_BT_accel_visc_rem', diag%axesCuL, Time, & + 'Barotropic Anomaly Zonal Acceleration multiplied by the viscous remnant', & + 'm s-2', conversion=US%L_T2_to_m_s2) + if (CS%id_u_BT_accel_visc_rem > 0) call safe_alloc_ptr(CS%ADp%visc_rem_u,IsdB,IedB,jsd,jed,nz) + CS%id_v_BT_accel_visc_rem = register_diag_field('ocean_model', 'v_BT_accel_visc_rem', diag%axesCvL, Time, & + 'Barotropic Anomaly Meridional Acceleration multiplied by the viscous remnant', & + 'm s-2', conversion=US%L_T2_to_m_s2) + if (CS%id_v_BT_accel_visc_rem > 0) call safe_alloc_ptr(CS%ADp%visc_rem_v,isd,ied,JsdB,JedB,nz) + + id_clock_Cor = cpu_clock_id('(Ocean Coriolis & mom advection)', grain=CLOCK_MODULE) + id_clock_continuity = cpu_clock_id('(Ocean continuity equation)', grain=CLOCK_MODULE) + id_clock_pres = cpu_clock_id('(Ocean pressure force)', grain=CLOCK_MODULE) + id_clock_vertvisc = cpu_clock_id('(Ocean vertical viscosity)', grain=CLOCK_MODULE) + id_clock_horvisc = cpu_clock_id('(Ocean horizontal viscosity)', grain=CLOCK_MODULE) + id_clock_mom_update = cpu_clock_id('(Ocean momentum increments)', grain=CLOCK_MODULE) + id_clock_pass = cpu_clock_id('(Ocean message passing)', grain=CLOCK_MODULE) + id_clock_btcalc = cpu_clock_id('(Ocean barotropic mode calc)', grain=CLOCK_MODULE) + id_clock_btstep = cpu_clock_id('(Ocean barotropic mode stepping)', grain=CLOCK_MODULE) + id_clock_btforce = cpu_clock_id('(Ocean barotropic forcing calc)', grain=CLOCK_MODULE) + +end subroutine initialize_dyn_split_RK2b + + +!> Close the dyn_split_RK2b module +subroutine end_dyn_split_RK2b(CS) + type(MOM_dyn_split_RK2b_CS), pointer :: CS !< module control structure + + call barotropic_end(CS%barotropic_CSp) + + call vertvisc_end(CS%vertvisc_CSp) + deallocate(CS%vertvisc_CSp) + + call hor_visc_end(CS%hor_visc) + if (CS%calculate_SAL) call SAL_end(CS%SAL_CSp) + if (CS%use_tides) call tidal_forcing_end(CS%tides_CSp) + call CoriolisAdv_end(CS%CoriolisAdv) + + DEALLOC_(CS%diffu) ; DEALLOC_(CS%diffv) + DEALLOC_(CS%CAu) ; DEALLOC_(CS%CAv) + DEALLOC_(CS%CAu_pred) ; DEALLOC_(CS%CAv_pred) + DEALLOC_(CS%PFu) ; DEALLOC_(CS%PFv) + + if (associated(CS%taux_bot)) deallocate(CS%taux_bot) + if (associated(CS%tauy_bot)) deallocate(CS%tauy_bot) + DEALLOC_(CS%uhbt) ; DEALLOC_(CS%vhbt) + DEALLOC_(CS%u_accel_bt) ; DEALLOC_(CS%v_accel_bt) + DEALLOC_(CS%visc_rem_u) ; DEALLOC_(CS%visc_rem_v) + + DEALLOC_(CS%eta) ; DEALLOC_(CS%eta_PF) ; DEALLOC_(CS%pbce) + DEALLOC_(CS%h_av) ; DEALLOC_(CS%u_av) ; DEALLOC_(CS%v_av) + + call dealloc_BT_cont_type(CS%BT_cont) + deallocate(CS%AD_pred) + + deallocate(CS) +end subroutine end_dyn_split_RK2b + + +!> \namespace mom_dynamics_split_rk2b +!! +!! This file time steps the adiabatic dynamic core by splitting +!! between baroclinic and barotropic modes. It uses a pseudo-second order +!! Runge-Kutta time stepping scheme for the baroclinic momentum +!! equation and a forward-backward coupling between the baroclinic +!! momentum and continuity equations. This split time-stepping +!! scheme is described in detail in Hallberg (JCP, 1997). Additional +!! issues related to exact tracer conservation and how to +!! ensure consistency between the barotropic and layered estimates +!! of the free surface height are described in Hallberg and +!! Adcroft (Ocean Modelling, 2009). This was the time stepping code +!! that is used for most GOLD applications, including GFDL's ESM2G +!! Earth system model, and all of the examples provided with the +!! MOM code (although several of these solutions are routinely +!! verified by comparison with the slower unsplit schemes). +!! +!! The subroutine step_MOM_dyn_split_RK2b actually does the time +!! stepping, while register_restarts_dyn_split_RK2b sets the fields +!! that are found in a full restart file with this scheme, and +!! initialize_dyn_split_RK2b initializes the cpu clocks that are +!! used in this module. For largely historical reasons, this module +!! does not have its own control structure, but shares the same +!! control structure with MOM.F90 and the other MOM_dynamics_... +!! modules. + +end module MOM_dynamics_split_RK2b From 8b98bd04b41be50c86bee3b8b5aee47962056a10 Mon Sep 17 00:00:00 2001 From: Robert Hallberg Date: Tue, 12 Dec 2023 06:44:40 -0500 Subject: [PATCH 20/22] *+Revise algorithm in step_MOM_dyn_split_RK2b Revised step_MOM_dyn_split_RK2b to use the time-filtered velocities as arguments and reconstruct the instantaneous velocities with the proper phase from the barotropic solver from the saved increments du_av_inst and dv_av_inst. As a part of this change, the continuity solver is used to find the thickness fluxes used in the predictor step Coriolis terms, and the horizontal viscous accelerations are calculated for both the predictor and corrector steps, thereby avoiding the need to vertically remap any 3-d fields apart from a single pair of velocity components. The run-time option STORE_CORIOLIS_ACCEL is no longer used when SPLIT_RK2B = True. FPMIX was also disabled in this mode due to unresolved dimensional inconsistency errors in that code. Additionally, the time-filtered velocities are now used instead of the instantaneous velocities in the second call to radiation_open_bdry_conds(), which should improve the performance of several of the Orlanski-type open boundary conditions. The 2-d fields du_av_inst and dv_av_inst were added to the restart file, while the 3-d fields u2, v2, diffu and diffv and either CAu and CAv or uh, vh and h2 are all removed from the restart files. Remap_dyn_split_RK2b_aux_vars() now has nothing to do, and it should probably be eliminated altogether in a subsequent commit. All answers are changed when SPLIT_RK2B = True, and there are changes to the contents of the restart files. --- src/core/MOM_dynamics_split_RK2b.F90 | 417 +++++++++++---------------- 1 file changed, 162 insertions(+), 255 deletions(-) diff --git a/src/core/MOM_dynamics_split_RK2b.F90 b/src/core/MOM_dynamics_split_RK2b.F90 index a289014313..9cd8fbfc09 100644 --- a/src/core/MOM_dynamics_split_RK2b.F90 +++ b/src/core/MOM_dynamics_split_RK2b.F90 @@ -141,6 +141,12 @@ module MOM_dynamics_split_RK2b real ALLOCABLE_, dimension(NIMEM_,NJMEM_,NKMEM_) :: pbce !< pbce times eta gives the baroclinic pressure !! anomaly in each layer due to free surface height !! anomalies [L2 H-1 T-2 ~> m s-2 or m4 kg-1 s-2]. + real ALLOCABLE_, dimension(NIMEMB_PTR_,NJMEM_) :: du_av_inst !< The barotropic zonal velocity increment + !! between filtered and instantaneous velocities + !! [L T-1 ~> m s-1] + real ALLOCABLE_, dimension(NIMEM_,NJMEMB_PTR_) :: dv_av_inst !< The barotropic meridional velocity increment + !! between filtered and instantaneous velocities + !! [L T-1 ~> m s-1] type(KPP_CS), pointer :: KPP_CSp => NULL() !< KPP control structure needed to ge type(energetic_PBL_CS), pointer :: energetic_PBL_CSp => NULL() !< ePBL control structure @@ -157,12 +163,6 @@ module MOM_dynamics_split_RK2b !! barotropic solver. logical :: calc_dtbt !< If true, calculate the barotropic time-step !! dynamically. - logical :: store_CAu !< If true, store the Coriolis and advective accelerations at the - !! end of the timestep for use in the next predictor step. - logical :: CAu_pred_stored !< If true, the Coriolis and advective accelerations at the - !! end of the timestep have been stored for use in the next - !! predictor step. This is used to accomodate various generations - !! of restart files. logical :: calculate_SAL !< If true, calculate self-attraction and loading. logical :: use_tides !< If true, tidal forcing is enabled. logical :: remap_aux !< If true, apply ALE remapping to all of the auxiliary 3-D @@ -181,7 +181,7 @@ module MOM_dynamics_split_RK2b logical :: module_is_initialized = .false. !< Record whether this module has been initialized. !>@{ Diagnostic IDs - integer :: id_uold = -1, id_vold = -1 + ! integer :: id_uold = -1, id_vold = -1 integer :: id_uh = -1, id_vh = -1 integer :: id_umo = -1, id_vmo = -1 integer :: id_umo_2d = -1, id_vmo_2d = -1 @@ -253,13 +253,14 @@ module MOM_dynamics_split_RK2b !> A pointer to the update_OBC control structure type(update_OBC_CS), pointer :: update_OBC_CSp => NULL() - type(group_pass_type) :: pass_eta !< Structure for group halo pass + type(group_pass_type) :: pass_eta !< Structure for group halo pass type(group_pass_type) :: pass_visc_rem !< Structure for group halo pass - type(group_pass_type) :: pass_uvp !< Structure for group halo pass + type(group_pass_type) :: pass_uvp !< Structure for group halo pass type(group_pass_type) :: pass_hp_uv !< Structure for group halo pass - type(group_pass_type) :: pass_uv !< Structure for group halo pass - type(group_pass_type) :: pass_h !< Structure for group halo pass - type(group_pass_type) :: pass_av_uvh !< Structure for group halo pass + type(group_pass_type) :: pass_h_av !< Structure for group halo pass + type(group_pass_type) :: pass_uv !< Structure for group halo pass + type(group_pass_type) :: pass_h !< Structure for group halo pass + type(group_pass_type) :: pass_av_uvh !< Structure for group halo pass end type MOM_dyn_split_RK2b_CS @@ -275,22 +276,22 @@ module MOM_dynamics_split_RK2b integer :: id_clock_horvisc, id_clock_mom_update integer :: id_clock_continuity, id_clock_thick_diff integer :: id_clock_btstep, id_clock_btcalc, id_clock_btforce -integer :: id_clock_pass, id_clock_pass_init +integer :: id_clock_pass !>@} contains !> RK2 splitting for time stepping MOM adiabatic dynamics -subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, forces, & +subroutine step_MOM_dyn_split_RK2b(u_av, v_av, h, tv, visc, Time_local, dt, forces, & p_surf_begin, p_surf_end, uh, vh, uhtr, vhtr, eta_av, & G, GV, US, CS, calc_dtbt, VarMix, MEKE, thickness_diffuse_CSp, pbv, Waves) type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), & - target, intent(inout) :: u_inst !< Zonal velocity [L T-1 ~> m s-1] + target, intent(inout) :: u_av !< Zonal velocity [L T-1 ~> m s-1] real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), & - target, intent(inout) :: v_inst !< Meridional velocity [L T-1 ~> m s-1] + target, intent(inout) :: v_av !< Meridional velocity [L T-1 ~> m s-1] real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), & intent(inout) :: h !< Layer thickness [H ~> m or kg m-2] type(thermo_var_ptrs), intent(in) :: tv !< Thermodynamic type @@ -330,6 +331,7 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: up ! Predicted zonal velocity [L T-1 ~> m s-1]. real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: vp ! Predicted meridional velocity [L T-1 ~> m s-1]. real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: hp ! Predicted thickness [H ~> m or kg m-2]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: dz ! Distance between the interfaces around a layer [Z ~> m] real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: ueffA ! Effective Area of U-Faces [H L ~> m2] real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: veffA ! Effective Area of V-Faces [H L ~> m2] @@ -340,6 +342,11 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, ! of each layer calculated by the non-barotropic ! part of the model [L T-2 ~> m s-2] + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), target :: u_inst ! Instantaneous zonal velocity [L T-1 ~> m s-1]. + real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), target :: v_inst ! Instantaneous meridional velocity [L T-1 ~> m s-1]. + real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: h_av ! The average of the layer thicknesses at the beginning + ! and end of a time step [H ~> m or kg m-2] + real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), target :: uh_in ! The zonal mass transports that would be ! obtained using the initial velocities [H L2 T-1 ~> m3 s-1 or kg s-1] real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), target :: vh_in ! The meridional mass transports that would be @@ -378,11 +385,7 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, u_ptr => NULL(), & ! A pointer to a zonal velocity [L T-1 ~> m s-1] v_ptr => NULL(), & ! A pointer to a meridional velocity [L T-1 ~> m s-1] uh_ptr => NULL(), & ! A pointer to a zonal volume or mass transport [H L2 T-1 ~> m3 s-1 or kg s-1] - vh_ptr => NULL(), & ! A pointer to a meridional volume or mass transport [H L2 T-1 ~> m3 s-1 or kg s-1] - ! These pointers are just used as shorthand for CS%u_av, CS%v_av, and CS%h_av. - u_av, & ! The zonal velocity time-averaged over a time step [L T-1 ~> m s-1]. - v_av, & ! The meridional velocity time-averaged over a time step [L T-1 ~> m s-1]. - h_av ! The layer thickness time-averaged over a time step [H ~> m or kg m-2]. + vh_ptr => NULL() ! A pointer to a meridional volume or mass transport [H L2 T-1 ~> m3 s-1 or kg s-1] real, dimension(SZI_(G),SZJ_(G)) :: hbl ! Boundary layer depth from Cvmix [H ~> m or kg m-2] real :: dt_pred ! The time step for the predictor part of the baroclinic time stepping [T ~> s]. @@ -400,7 +403,8 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, is = G%isc ; ie = G%iec ; js = G%jsc ; je = G%jec ; nz = GV%ke Isq = G%IscB ; Ieq = G%IecB ; Jsq = G%JscB ; Jeq = G%JecB - u_av => CS%u_av ; v_av => CS%v_av ; h_av => CS%h_av ; eta => CS%eta + + eta => CS%eta Idt_bc = 1.0 / dt @@ -409,19 +413,16 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, showCallTree = callTree_showQuery() if (showCallTree) call callTree_enter("step_MOM_dyn_split_RK2b(), MOM_dynamics_split_RK2b.F90") - !$OMP parallel do default(shared) - do k=1,nz - do j=G%jsd,G%jed ; do i=G%isdB,G%iedB ; up(i,j,k) = 0.0 ; enddo ; enddo - do j=G%jsdB,G%jedB ; do i=G%isd,G%ied ; vp(i,j,k) = 0.0 ; enddo ; enddo - do j=G%jsd,G%jed ; do i=G%isd,G%ied ; hp(i,j,k) = h(i,j,k) ; enddo ; enddo - enddo + ! Fill in some halo points for arrays that will have halo updates. + hp(:,:,:) = h(:,:,:) + up(:,:,:) = 0.0 ; vp(:,:,:) = 0.0 ; u_inst(:,:,:) = 0.0 ; v_inst(:,:,:) = 0.0 ! Update CFL truncation value as function of time call updateCFLtruncationValue(Time_local, CS%vertvisc_CSp, US) if (CS%debug) then - call MOM_state_chksum("Start predictor ", u_inst, v_inst, h, uh, vh, G, GV, US, symmetric=sym) - call check_redundant("Start predictor u ", u_inst, v_inst, G, unscale=US%L_T_to_m_s) + call MOM_state_chksum("Start predictor ", u_av, v_av, h, uh, vh, G, GV, US, symmetric=sym) + call check_redundant("Start predictor u ", u_av, v_av, G, unscale=US%L_T_to_m_s) call check_redundant("Start predictor uh ", uh, vh, G, unscale=GV%H_to_MKS*US%L_to_m**2*US%s_to_T) endif @@ -476,9 +477,25 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, call create_group_pass(CS%pass_h, h, G%Domain, halo=max(2,cont_stencil)) call create_group_pass(CS%pass_av_uvh, u_av, v_av, G%Domain, halo=max(2,obc_stencil)) call create_group_pass(CS%pass_av_uvh, uh(:,:,:), vh(:,:,:), G%Domain, halo=max(2,obc_stencil)) + + call create_group_pass(CS%pass_h_av, hp, G%Domain, halo=2) + call create_group_pass(CS%pass_h_av, uh(:,:,:), vh(:,:,:), G%Domain, halo=max(2,obc_stencil)) + call cpu_clock_end(id_clock_pass) !--- end set up for group halo pass + if (associated(CS%OBC)) then ; if (CS%OBC%update_OBC) then + call update_OBC_data(CS%OBC, G, GV, US, tv, h, CS%update_OBC_CSp, Time_local) + endif ; endif + + ! This calculates the transports and averaged thicknesses that will be used for the + ! predictor version of the Coriolis scheme. + call cpu_clock_begin(id_clock_continuity) + call continuity(u_av, v_av, h, hp, uh, vh, dt, G, GV, US, CS%continuity_CSp, CS%OBC, pbv) + call cpu_clock_end(id_clock_continuity) + + if (G%nonblocking_updates) & + call start_group_pass(CS%pass_h_av, G%Domain, clock=id_clock_pass) ! PFu = d/dx M(h,T,S) ! pbce = dM/deta @@ -500,7 +517,7 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, if (Use_Stokes_PGF) Use_Stokes_PGF = Waves%Stokes_PGF if (Use_Stokes_PGF) then call thickness_to_dz(h, tv, dz, G, GV, US, halo_size=1) - call Stokes_PGF(G, GV, US, dz, u_inst, v_inst, CS%PFu_Stokes, CS%PFv_Stokes, Waves) + call Stokes_PGF(G, GV, US, dz, u_av, v_av, CS%PFu_Stokes, CS%PFv_Stokes, Waves) ! We are adding Stokes_PGF to hydrostatic PGF here. The diag PFu/PFv ! will therefore report the sum total PGF and we avoid other @@ -523,25 +540,37 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, call disable_averaging(CS%diag) if (showCallTree) call callTree_wayPoint("done with PressureForce (step_MOM_dyn_split_RK2b)") - if (associated(CS%OBC)) then ; if (CS%OBC%update_OBC) then - call update_OBC_data(CS%OBC, G, GV, US, tv, h, CS%update_OBC_CSp, Time_local) - endif ; endif if (associated(CS%OBC) .and. CS%debug_OBC) & call open_boundary_zero_normal_flow(CS%OBC, G, GV, CS%PFu, CS%PFv) - if (G%nonblocking_updates) & + if (G%nonblocking_updates) then + call complete_group_pass(CS%pass_h_av, G%Domain, clock=id_clock_pass) call start_group_pass(CS%pass_eta, G%Domain, clock=id_clock_pass) + else + call do_group_pass(CS%pass_h_av, G%Domain, clock=id_clock_pass) + endif + + !$OMP parallel do default(shared) + do k=1,nz ; do j=js-2,je+2 ; do i=is-2,ie+2 + h_av(i,j,k) = 0.5*(hp(i,j,k) + h(i,j,k)) + enddo ; enddo ; enddo + + ! Calculate a predictor-step estimate of the Coriolis and momentum advection terms + ! and horizontal viscous accelerations. ! CAu = -(f+zeta_av)/h_av vh + d/dx KE_av - if (.not.CS%CAu_pred_stored) then - ! Calculate a predictor-step estimate of the Coriolis and momentum advection terms, - ! if it was not already stored from the end of the previous time step. - call cpu_clock_begin(id_clock_Cor) - call CorAdCalc(u_av, v_av, h_av, uh, vh, CS%CAu_pred, CS%CAv_pred, CS%OBC, CS%AD_pred, & - G, GV, US, CS%CoriolisAdv, pbv, Waves=Waves) - call cpu_clock_end(id_clock_Cor) - if (showCallTree) call callTree_wayPoint("done with CorAdCalc (step_MOM_dyn_split_RK2b)") - endif + call cpu_clock_begin(id_clock_Cor) + call CorAdCalc(u_av, v_av, h_av, uh, vh, CS%CAu_pred, CS%CAv_pred, CS%OBC, CS%AD_pred, & + G, GV, US, CS%CoriolisAdv, pbv, Waves=Waves) + call cpu_clock_end(id_clock_Cor) + if (showCallTree) call callTree_wayPoint("done with predictor CorAdCalc (step_MOM_dyn_split_RK2b)") + +! diffu = horizontal viscosity terms (u_av) + call cpu_clock_begin(id_clock_horvisc) + call horizontal_viscosity(u_av, v_av, h_av, CS%diffu, CS%diffv, MEKE, Varmix, G, GV, US, CS%hor_visc, & + OBC=CS%OBC, BT=CS%barotropic_CSp, TD=thickness_diffuse_CSp, ADp=CS%AD_pred) + call cpu_clock_end(id_clock_horvisc) + if (showCallTree) call callTree_wayPoint("done with predictor horizontal_viscosity (step_MOM_dyn_split_RK2b)") ! u_bc_accel = CAu + PFu + diffu(u[n-1]) call cpu_clock_begin(id_clock_btforce) @@ -573,15 +602,15 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, !$OMP parallel do default(shared) do k=1,nz do j=js,je ; do I=Isq,Ieq - up(I,j,k) = G%mask2dCu(I,j) * (u_inst(I,j,k) + dt * u_bc_accel(I,j,k)) + up(I,j,k) = G%mask2dCu(I,j) * (u_av(I,j,k) + dt * u_bc_accel(I,j,k)) enddo ; enddo do J=Jsq,Jeq ; do i=is,ie - vp(i,J,k) = G%mask2dCv(i,J) * (v_inst(i,J,k) + dt * v_bc_accel(i,J,k)) + vp(i,J,k) = G%mask2dCv(i,J) * (v_av(i,J,k) + dt * v_bc_accel(i,J,k)) enddo ; enddo enddo call enable_averages(dt, Time_local, CS%diag) - call set_viscous_ML(u_inst, v_inst, h, tv, forces, visc, dt, G, GV, US, CS%set_visc_CSp) + call set_viscous_ML(u_av, v_av, h, tv, forces, visc, dt, G, GV, US, CS%set_visc_CSp) call disable_averaging(CS%diag) if (CS%debug) then @@ -622,6 +651,17 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, if (G%nonblocking_updates) & call complete_group_pass(CS%pass_visc_rem, G%Domain, clock=id_clock_pass) + ! Reconstruct u_inst and v_inst from u_av and v_av. + call cpu_clock_begin(id_clock_mom_update) + do k=1,nz ; do j=js,je ; do I=Isq,Ieq + u_inst(I,j,k) = u_av(I,j,k) - CS%du_av_inst(I,j) * CS%visc_rem_u(I,j,k) + enddo ; enddo ; enddo + do k=1,nz ; do J=Jsq,Jeq ; do i=is,ie + v_inst(i,J,k) = v_av(i,J,k) - CS%dv_av_inst(i,j) * CS%visc_rem_v(i,J,k) + enddo ; enddo ; enddo + call cpu_clock_end(id_clock_mom_update) + call do_group_pass(CS%pass_uv, G%Domain, clock=id_clock_pass) + ! u_accel_bt = layer accelerations due to barotropic solver call cpu_clock_begin(id_clock_continuity) call continuity(u_inst, v_inst, h, hp, uh_in, vh_in, dt, G, GV, US, CS%continuity_CSp, CS%OBC, pbv, & @@ -647,10 +687,10 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, if (showCallTree) call callTree_leave("btstep()") call cpu_clock_end(id_clock_btstep) -! up = u + dt_pred*( u_bc_accel + u_accel_bt ) dt_pred = dt * CS%be call cpu_clock_begin(id_clock_mom_update) +! up = u + dt_pred*( u_bc_accel + u_accel_bt ) !$OMP parallel do default(shared) do k=1,nz do J=Jsq,Jeq ; do i=is,ie @@ -685,16 +725,16 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, call uvchksum("0 before vertvisc: [uv]p", up, vp, G%HI,haloshift=0, symmetric=sym, scale=US%L_T_to_m_s) endif - if (CS%fpmix) then - uold(:,:,:) = 0.0 - vold(:,:,:) = 0.0 - do k=1,nz ; do j=js,je ; do I=Isq,Ieq - uold(I,j,k) = up(I,j,k) - enddo ; enddo ; enddo - do k=1,nz ; do J=Jsq,Jeq ; do i=is,ie - vold(i,J,k) = vp(i,J,k) - enddo ; enddo ; enddo - endif + ! if (CS%fpmix) then + ! uold(:,:,:) = 0.0 + ! vold(:,:,:) = 0.0 + ! do k=1,nz ; do j=js,je ; do I=Isq,Ieq + ! uold(I,j,k) = up(I,j,k) + ! enddo ; enddo ; enddo + ! do k=1,nz ; do J=Jsq,Jeq ; do i=is,ie + ! vold(i,J,k) = vp(i,J,k) + ! enddo ; enddo ; enddo + ! endif call thickness_to_dz(h, tv, dz, G, GV, US, halo_size=1) call vertvisc_coef(up, vp, h, dz, forces, visc, tv, dt_pred, G, GV, US, CS%vertvisc_CSp, & @@ -702,16 +742,16 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, call vertvisc(up, vp, h, forces, visc, dt_pred, CS%OBC, CS%AD_pred, CS%CDp, G, & GV, US, CS%vertvisc_CSp, CS%taux_bot, CS%tauy_bot, waves=waves) - if (CS%fpmix) then - hbl(:,:) = 0.0 - if (ASSOCIATED(CS%KPP_CSp)) call KPP_get_BLD(CS%KPP_CSp, hbl, G, US, m_to_BLD_units=GV%m_to_H) - if (ASSOCIATED(CS%energetic_PBL_CSp)) & - call energetic_PBL_get_MLD(CS%energetic_PBL_CSp, hbl, G, US, m_to_MLD_units=GV%m_to_H) - call vertFPmix(up, vp, uold, vold, hbl, h, forces, & - dt_pred, G, GV, US, CS%vertvisc_CSp, CS%OBC) - call vertvisc(up, vp, h, forces, visc, dt_pred, CS%OBC, CS%ADp, CS%CDp, G, & - GV, US, CS%vertvisc_CSp, CS%taux_bot, CS%tauy_bot, waves=waves) - endif + ! if (CS%fpmix) then + ! hbl(:,:) = 0.0 + ! if (ASSOCIATED(CS%KPP_CSp)) call KPP_get_BLD(CS%KPP_CSp, hbl, G, US, m_to_BLD_units=GV%m_to_H) + ! if (ASSOCIATED(CS%energetic_PBL_CSp)) & + ! call energetic_PBL_get_MLD(CS%energetic_PBL_CSp, hbl, G, US, m_to_MLD_units=GV%m_to_H) + ! call vertFPmix(up, vp, uold, vold, hbl, h, forces, & + ! dt_pred, G, GV, US, CS%vertvisc_CSp, CS%OBC) + ! call vertvisc(up, vp, h, forces, visc, dt_pred, CS%OBC, CS%ADp, CS%CDp, G, & + ! GV, US, CS%vertvisc_CSp, CS%taux_bot, CS%tauy_bot, waves=waves) + ! endif if (showCallTree) call callTree_wayPoint("done with vertvisc (step_MOM_dyn_split_RK2b)") if (G%nonblocking_updates) then @@ -796,7 +836,7 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, if (Use_Stokes_PGF) Use_Stokes_PGF = Waves%Stokes_PGF if (Use_Stokes_PGF) then call thickness_to_dz(h, tv, dz, G, GV, US, halo_size=1) - call Stokes_PGF(G, GV, US, dz, u_inst, v_inst, CS%PFu_Stokes, CS%PFv_Stokes, Waves) + call Stokes_PGF(G, GV, US, dz, u_av, v_av, CS%PFu_Stokes, CS%PFv_Stokes, Waves) if (.not.Waves%Passive_Stokes_PGF) then do k=1,nz do j=js,je ; do I=Isq,Ieq @@ -835,10 +875,8 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, ! diffu = horizontal viscosity terms (u_av) call cpu_clock_begin(id_clock_horvisc) - call horizontal_viscosity(u_av, v_av, h_av, CS%diffu, CS%diffv, & - MEKE, Varmix, G, GV, US, CS%hor_visc, & - OBC=CS%OBC, BT=CS%barotropic_CSp, TD=thickness_diffuse_CSp, & - ADp=CS%ADp) + call horizontal_viscosity(u_av, v_av, h_av, CS%diffu, CS%diffv, MEKE, Varmix, G, GV, US, CS%hor_visc, & + OBC=CS%OBC, BT=CS%barotropic_CSp, TD=thickness_diffuse_CSp, ADp=CS%ADp) call cpu_clock_end(id_clock_horvisc) if (showCallTree) call callTree_wayPoint("done with horizontal_viscosity (step_MOM_dyn_split_RK2b)") @@ -931,28 +969,28 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, ! u_av <- u_av + dt d/dz visc d/dz u_av call cpu_clock_begin(id_clock_vertvisc) - if (CS%fpmix) then - uold(:,:,:) = 0.0 - vold(:,:,:) = 0.0 - do k=1,nz ; do j=js,je ; do I=Isq,Ieq - uold(I,j,k) = u_inst(I,j,k) - enddo ; enddo ; enddo - do k=1,nz ; do J=Jsq,Jeq ; do i=is,ie - vold(i,J,k) = v_inst(i,J,k) - enddo ; enddo ; enddo - endif + ! if (CS%fpmix) then + ! uold(:,:,:) = 0.0 + ! vold(:,:,:) = 0.0 + ! do k=1,nz ; do j=js,je ; do I=Isq,Ieq + ! uold(I,j,k) = u_inst(I,j,k) + ! enddo ; enddo ; enddo + ! do k=1,nz ; do J=Jsq,Jeq ; do i=is,ie + ! vold(i,J,k) = v_inst(i,J,k) + ! enddo ; enddo ; enddo + ! endif call thickness_to_dz(h, tv, dz, G, GV, US, halo_size=1) call vertvisc_coef(u_inst, v_inst, h, dz, forces, visc, tv, dt, G, GV, US, CS%vertvisc_CSp, CS%OBC, VarMix) call vertvisc(u_inst, v_inst, h, forces, visc, dt, CS%OBC, CS%ADp, CS%CDp, G, GV, US, & - CS%vertvisc_CSp, CS%taux_bot, CS%tauy_bot,waves=waves) + CS%vertvisc_CSp, CS%taux_bot, CS%tauy_bot, waves=waves) - if (CS%fpmix) then - call vertFPmix(u_inst, v_inst, uold, vold, hbl, h, forces, dt, & - G, GV, US, CS%vertvisc_CSp, CS%OBC) - call vertvisc(u_inst, v_inst, h, forces, visc, dt, CS%OBC, CS%ADp, CS%CDp, G, GV, US, & - CS%vertvisc_CSp, CS%taux_bot, CS%tauy_bot, waves=waves) - endif + ! if (CS%fpmix) then + ! call vertFPmix(u_inst, v_inst, uold, vold, hbl, h, forces, dt, & + ! G, GV, US, CS%vertvisc_CSp, CS%OBC) + ! call vertvisc(u_inst, v_inst, h, forces, visc, dt, CS%OBC, CS%ADp, CS%CDp, G, GV, US, & + ! CS%vertvisc_CSp, CS%taux_bot, CS%tauy_bot, waves=waves) + ! endif if (G%nonblocking_updates) then call cpu_clock_end(id_clock_vertvisc) @@ -980,8 +1018,19 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, ! h = h + dt * div . uh ! u_av and v_av adjusted so their mass transports match uhbt and vhbt. call cpu_clock_begin(id_clock_continuity) + call continuity(u_inst, v_inst, h, h, uh, vh, dt, G, GV, US, CS%continuity_CSp, CS%OBC, pbv, & - CS%uhbt, CS%vhbt, CS%visc_rem_u, CS%visc_rem_v, u_av, v_av) + CS%uhbt, CS%vhbt, CS%visc_rem_u, CS%visc_rem_v, u_av, v_av, & + du_cor=CS%du_av_inst, dv_cor=CS%dv_av_inst) + + ! This tests the ability to readjust the instantaneous velocity, and here it changes answers only at roundoff. + ! do k=1,nz ; do j=js,je ; do I=Isq,Ieq + ! u_inst(I,j,k) = u_av(I,j,k) - CS%du_av_inst(I,j) * CS%visc_rem_u(I,j,k) + ! enddo ; enddo ; enddo + ! do k=1,nz ; do J=Jsq,Jeq ; do i=is,ie + ! v_inst(i,J,k) = v_av(i,J,k) - CS%dv_av_inst(i,J) * CS%visc_rem_v(i,J,k) + ! enddo ; enddo ; enddo + call cpu_clock_end(id_clock_continuity) call do_group_pass(CS%pass_h, G%Domain, clock=id_clock_pass) ! Whenever thickness changes let the diag manager know, target grids @@ -996,10 +1045,10 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, endif if (associated(CS%OBC)) then - call radiation_open_bdry_conds(CS%OBC, u_inst, u_old_rad_OBC, v_inst, v_old_rad_OBC, G, GV, US, dt) + call radiation_open_bdry_conds(CS%OBC, u_av, u_old_rad_OBC, v_av, v_old_rad_OBC, G, GV, US, dt) endif -! h_av = (h_in + h_out)/2 . Going in to this line, h_av = h_in. + ! h_av = (h_in + h_out)/2 . Going in to this line, h_av = h_in. !$OMP parallel do default(shared) do k=1,nz ; do j=js-2,je+2 ; do i=is-2,ie+2 h_av(i,j,k) = 0.5*(h_av(i,j,k) + h(i,j,k)) @@ -1018,26 +1067,10 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, enddo ; enddo enddo - if (CS%store_CAu) then - ! Calculate a predictor-step estimate of the Coriolis and momentum advection terms - ! for use in the next time step, possibly after it has been vertically remapped. - call cpu_clock_begin(id_clock_Cor) - call disable_averaging(CS%diag) ! These calculations should not be used for diagnostics. - ! CAu = -(f+zeta_av)/h_av vh + d/dx KE_av - call CorAdCalc(u_av, v_av, h_av, uh, vh, CS%CAu_pred, CS%CAv_pred, CS%OBC, CS%AD_pred, & - G, GV, US, CS%CoriolisAdv, pbv, Waves=Waves) - CS%CAu_pred_stored = .true. - call enable_averages(dt, Time_local, CS%diag) ! Reenable the averaging - call cpu_clock_end(id_clock_Cor) - if (showCallTree) call callTree_wayPoint("done with CorAdCalc (step_MOM_dyn_split_RK2b)") - else - CS%CAu_pred_stored = .false. - endif - - if (CS%fpmix) then - if (CS%id_uold > 0) call post_data(CS%id_uold, uold, CS%diag) - if (CS%id_vold > 0) call post_data(CS%id_vold, vold, CS%diag) - endif + ! if (CS%fpmix) then + ! if (CS%id_uold > 0) call post_data(CS%id_uold, uold, CS%diag) + ! if (CS%id_vold > 0) call post_data(CS%id_vold, vold, CS%diag) + ! endif ! The time-averaged free surface height has already been set by the last call to btstep. @@ -1063,7 +1096,7 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, if (CS%id_ueffA > 0) then ueffA(:,:,:) = 0 do k=1,nz ; do j=js,je ; do I=Isq,Ieq - if (abs(up(I,j,k)) > 0.) ueffA(I,j,k) = uh(I,j,k) / up(I,j,k) + if (abs(u_av(I,j,k)) > 0.) ueffA(I,j,k) = uh(I,j,k) / u_av(I,j,k) enddo ; enddo ; enddo call post_data(CS%id_ueffA, ueffA, CS%diag) endif @@ -1071,7 +1104,7 @@ subroutine step_MOM_dyn_split_RK2b(u_inst, v_inst, h, tv, visc, Time_local, dt, if (CS%id_veffA > 0) then veffA(:,:,:) = 0 do k=1,nz ; do J=Jsq,Jeq ; do i=is,ie - if (abs(vp(i,J,k)) > 0.) veffA(i,J,k) = vh(i,J,k) / vp(i,J,k) + if (abs(v_av(i,J,k)) > 0.) veffA(i,J,k) = vh(i,J,k) / v_av(i,J,k) enddo ; enddo ; enddo call post_data(CS%id_veffA, veffA, CS%diag) endif @@ -1186,20 +1219,14 @@ subroutine register_restarts_dyn_split_RK2b(HI, GV, US, param_file, CS, restart_ ALLOC_(CS%CAv_pred(isd:ied,JsdB:JedB,nz)) ; CS%CAv_pred(:,:,:) = 0.0 ALLOC_(CS%PFu(IsdB:IedB,jsd:jed,nz)) ; CS%PFu(:,:,:) = 0.0 ALLOC_(CS%PFv(isd:ied,JsdB:JedB,nz)) ; CS%PFv(:,:,:) = 0.0 + ALLOC_(CS%du_av_inst(IsdB:IedB,jsd:jed)) ; CS%du_av_inst(:,:) = 0.0 + ALLOC_(CS%dv_av_inst(isd:ied,JsdB:JedB)) ; CS%dv_av_inst(:,:) = 0.0 ALLOC_(CS%eta(isd:ied,jsd:jed)) ; CS%eta(:,:) = 0.0 - ALLOC_(CS%u_av(IsdB:IedB,jsd:jed,nz)) ; CS%u_av(:,:,:) = 0.0 - ALLOC_(CS%v_av(isd:ied,JsdB:JedB,nz)) ; CS%v_av(:,:,:) = 0.0 - ALLOC_(CS%h_av(isd:ied,jsd:jed,nz)) ; CS%h_av(:,:,:) = GV%Angstrom_H thickness_units = get_thickness_units(GV) flux_units = get_flux_units(GV) - call get_param(param_file, mdl, "STORE_CORIOLIS_ACCEL", CS%store_CAu, & - "If true, calculate the Coriolis accelerations at the end of each "//& - "timestep for use in the predictor step of the next split RK2 timestep.", & - default=.true., do_not_log=.true.) - if (GV%Boussinesq) then call register_restart_field(CS%eta, "sfc", .false., restart_CS, & longname="Free surface Height", units=thickness_units, conversion=GV%H_to_mks) @@ -1208,33 +1235,14 @@ subroutine register_restarts_dyn_split_RK2b(HI, GV, US, param_file, CS, restart_ longname="Bottom Pressure", units=thickness_units, conversion=GV%H_to_mks) endif - ! These are needed, either to calculate CAu and CAv or to calculate the velocity anomalies in - ! the barotropic solver's Coriolis terms. - vd(1) = var_desc("u2", "m s-1", "Auxiliary Zonal velocity", 'u', 'L') - vd(2) = var_desc("v2", "m s-1", "Auxiliary Meridional velocity", 'v', 'L') - call register_restart_pair(CS%u_av, CS%v_av, vd(1), vd(2), .false., restart_CS, & + ! These are needed to reconstruct the phase in the barotorpic solution. + vd(1) = var_desc("du_avg_inst", "m s-1", & + "Barotropic velocity increment between instantaneous and filtered zonal velocities", 'u', '1') + vd(2) = var_desc("dv_avg_inst", "m s-1", & + "Barotropic velocity increment between instantaneous and filtered meridional velocities", 'v', '1') + call register_restart_pair(CS%du_av_inst, CS%dv_av_inst, vd(1), vd(2), .false., restart_CS, & conversion=US%L_T_to_m_s) - if (CS%store_CAu) then - vd(1) = var_desc("CAu", "m s-2", "Zonal Coriolis and advactive acceleration", 'u', 'L') - vd(2) = var_desc("CAv", "m s-2", "Meridional Coriolis and advactive acceleration", 'v', 'L') - call register_restart_pair(CS%CAu_pred, CS%CAv_pred, vd(1), vd(2), .false., restart_CS, & - conversion=US%L_T2_to_m_s2) - else - call register_restart_field(CS%h_av, "h2", .false., restart_CS, & - longname="Auxiliary Layer Thickness", units=thickness_units, conversion=GV%H_to_mks) - - vd(1) = var_desc("uh", flux_units, "Zonal thickness flux", 'u', 'L') - vd(2) = var_desc("vh", flux_units, "Meridional thickness flux", 'v', 'L') - call register_restart_pair(uh, vh, vd(1), vd(2), .false., restart_CS, & - conversion=GV%H_to_MKS*US%L_to_m**2*US%s_to_T) - endif - - vd(1) = var_desc("diffu", "m s-2", "Zonal horizontal viscous acceleration", 'u', 'L') - vd(2) = var_desc("diffv", "m s-2", "Meridional horizontal viscous acceleration", 'v', 'L') - call register_restart_pair(CS%diffu, CS%diffv, vd(1), vd(2), .false., restart_CS, & - conversion=US%L_T2_to_m_s2) - call register_barotropic_restarts(HI, GV, US, param_file, CS%barotropic_CSp, restart_CS) end subroutine register_restarts_dyn_split_RK2b @@ -1259,16 +1267,7 @@ subroutine remap_dyn_split_RK2b_aux_vars(G, GV, CS, h_old_u, h_old_v, h_new_u, h !! velocity points [H ~> m or kg m-2] type(ALE_CS), pointer :: ALE_CSp !< ALE control structure to use when remapping - if (.not.CS%remap_aux) return - - if (CS%store_CAu) then - call ALE_remap_velocities(ALE_CSp, G, GV, h_old_u, h_old_v, h_new_u, h_new_v, CS%u_av, CS%v_av) - call pass_vector(CS%u_av, CS%v_av, G%Domain, complete=.false.) - call ALE_remap_velocities(ALE_CSp, G, GV, h_old_u, h_old_v, h_new_u, h_new_v, CS%CAu_pred, CS%CAv_pred) - call pass_vector(CS%CAu_pred, CS%CAv_pred, G%Domain, complete=.true.) - endif - - call ALE_remap_velocities(ALE_CSp, G, GV, h_old_u, h_old_v, h_new_u, h_new_v, CS%diffu, CS%diffv) + return end subroutine remap_dyn_split_RK2b_aux_vars @@ -1328,7 +1327,6 @@ subroutine initialize_dyn_split_RK2b(u, v, h, uh, vh, eta, Time, G, GV, US, para ! This include declares and sets the variable "version". # include "version_variable.h" character(len=48) :: thickness_units, flux_units, eta_rest_name - type(group_pass_type) :: pass_av_h_uvh logical :: debug_truncations logical :: read_uv, read_h2 @@ -1374,20 +1372,15 @@ subroutine initialize_dyn_split_RK2b(u, v, h, uh, vh, eta, Time, G, GV, US, para call get_param(param_file, mdl, "SPLIT_BOTTOM_STRESS", CS%split_bottom_stress, & "If true, provide the bottom stress calculated by the "//& "vertical viscosity to the barotropic solver.", default=.false.) - call get_param(param_file, mdl, "STORE_CORIOLIS_ACCEL", CS%store_CAu, & - "If true, calculate the Coriolis accelerations at the end of each "//& - "timestep for use in the predictor step of the next split RK2 timestep.", & - default=.true.) - call get_param(param_file, mdl, "FPMIX", CS%fpmix, & - "If true, apply profiles of momentum flux magnitude and direction.", & - default=.false.) + ! call get_param(param_file, mdl, "FPMIX", CS%fpmix, & + ! "If true, apply profiles of momentum flux magnitude and direction.", & + ! default=.false.) + CS%fpmix = .false. call get_param(param_file, mdl, "REMAP_AUXILIARY_VARS", CS%remap_aux, & "If true, apply ALE remapping to all of the auxiliary 3-dimensional "//& "variables that are needed to reproduce across restarts, similarly to "//& "what is already being done with the primary state variables. "//& "The default should be changed to true.", default=.false., do_not_log=.true.) - if (CS%remap_aux .and. .not.CS%store_CAu) call MOM_error(FATAL, & - "REMAP_AUXILIARY_VARS requires that STORE_CORIOLIS_ACCEL = True.") call get_param(param_file, mdl, "DEBUG", CS%debug, & "If true, write out verbose debugging data.", & default=.false., debuggingParam=.true.) @@ -1419,8 +1412,6 @@ subroutine initialize_dyn_split_RK2b(u, v, h, uh, vh, eta, Time, G, GV, US, para MIS%pbce => CS%pbce MIS%u_accel_bt => CS%u_accel_bt MIS%v_accel_bt => CS%v_accel_bt - MIS%u_av => CS%u_av - MIS%v_av => CS%v_av CS%ADp => Accel_diag CS%CDp => Cont_diag @@ -1447,9 +1438,6 @@ subroutine initialize_dyn_split_RK2b(u, v, h, uh, vh, eta, Time, G, GV, US, para ! Accel_diag%u_accel_bt => CS%u_accel_bt ; Accel_diag%v_accel_bt => CS%v_accel_bt ! Accel_diag%u_av => CS%u_av ; Accel_diag%v_av => CS%v_av - id_clock_pass_init = cpu_clock_id('(Ocean init message passing)', & - grain=CLOCK_ROUTINE) - call continuity_init(Time, G, GV, US, param_file, diag, CS%continuity_CSp) cont_stencil = continuity_stencil(CS%continuity_CSp) call CoriolisAdv_init(Time, G, GV, US, param_file, diag, CS%ADp, CS%CoriolisAdv) @@ -1494,87 +1482,6 @@ subroutine initialize_dyn_split_RK2b(u, v, h, uh, vh, eta, Time, G, GV, US, para CS%barotropic_CSp, restart_CS, calc_dtbt, CS%BT_cont, & CS%SAL_CSp) - if (.not. query_initialized(CS%diffu, "diffu", restart_CS) .or. & - .not. query_initialized(CS%diffv, "diffv", restart_CS)) then - call horizontal_viscosity(u, v, h, CS%diffu, CS%diffv, MEKE, VarMix, G, GV, US, CS%hor_visc, & - OBC=CS%OBC, BT=CS%barotropic_CSp, TD=thickness_diffuse_CSp) - call set_initialized(CS%diffu, "diffu", restart_CS) - call set_initialized(CS%diffv, "diffv", restart_CS) - endif - - if (.not. query_initialized(CS%u_av, "u2", restart_CS) .or. & - .not. query_initialized(CS%v_av, "v2", restart_CS)) then - do k=1,nz ; do j=jsd,jed ; do I=IsdB,IedB ; CS%u_av(I,j,k) = u(I,j,k) ; enddo ; enddo ; enddo - do k=1,nz ; do J=JsdB,JedB ; do i=isd,ied ; CS%v_av(i,J,k) = v(i,J,k) ; enddo ; enddo ; enddo - call set_initialized(CS%u_av, "u2", restart_CS) - call set_initialized(CS%v_av, "v2", restart_CS) - endif - - if (CS%store_CAu) then - if (query_initialized(CS%CAu_pred, "CAu", restart_CS) .and. & - query_initialized(CS%CAv_pred, "CAv", restart_CS)) then - CS%CAu_pred_stored = .true. - else - call only_read_from_restarts(uh, vh, 'uh', 'vh', G, restart_CS, stagger=CGRID_NE, & - filename=dirs%input_filename, directory=dirs%restart_input_dir, & - success=read_uv, scale=US%m_to_L**2*US%T_to_s/GV%H_to_mks) - call only_read_from_restarts('h2', CS%h_av, G, restart_CS, & - filename=dirs%input_filename, directory=dirs%restart_input_dir, & - success=read_h2, scale=1.0/GV%H_to_mks) - if (read_uv .and. read_h2) then - call pass_var(CS%h_av, G%Domain, clock=id_clock_pass_init) - else - do k=1,nz ; do j=jsd,jed ; do i=isd,ied ; h_tmp(i,j,k) = h(i,j,k) ; enddo ; enddo ; enddo - call continuity(CS%u_av, CS%v_av, h, h_tmp, uh, vh, dt, G, GV, US, CS%continuity_CSp, CS%OBC, pbv) - call pass_var(h_tmp, G%Domain, clock=id_clock_pass_init) - do k=1,nz ; do j=jsd,jed ; do i=isd,ied - CS%h_av(i,j,k) = 0.5*(h(i,j,k) + h_tmp(i,j,k)) - enddo ; enddo ; enddo - endif - call pass_vector(CS%u_av, CS%v_av, G%Domain, halo=2, clock=id_clock_pass_init, complete=.false.) - call pass_vector(uh, vh, G%Domain, halo=2, clock=id_clock_pass_init, complete=.true.) - call CorAdCalc(CS%u_av, CS%v_av, CS%h_av, uh, vh, CS%CAu_pred, CS%CAv_pred, CS%OBC, CS%ADp, & - G, GV, US, CS%CoriolisAdv, pbv) !, Waves=Waves) - CS%CAu_pred_stored = .true. - endif - else - CS%CAu_pred_stored = .false. - ! This call is just here to initialize uh and vh. - if (.not. query_initialized(uh, "uh", restart_CS) .or. & - .not. query_initialized(vh, "vh", restart_CS)) then - do k=1,nz ; do j=jsd,jed ; do i=isd,ied ; h_tmp(i,j,k) = h(i,j,k) ; enddo ; enddo ; enddo - call continuity(u, v, h, h_tmp, uh, vh, dt, G, GV, US, CS%continuity_CSp, CS%OBC, pbv) - call pass_var(h_tmp, G%Domain, clock=id_clock_pass_init) - do k=1,nz ; do j=jsd,jed ; do i=isd,ied - CS%h_av(i,j,k) = 0.5*(h(i,j,k) + h_tmp(i,j,k)) - enddo ; enddo ; enddo - call set_initialized(uh, "uh", restart_CS) - call set_initialized(vh, "vh", restart_CS) - call set_initialized(CS%h_av, "h2", restart_CS) - ! Try reading the CAu and CAv fields from the restart file, in case this restart file is - ! using a newer format. - call only_read_from_restarts(CS%CAu_pred, CS%CAv_pred, "CAu", "CAv", G, restart_CS, & - stagger=CGRID_NE, filename=dirs%input_filename, directory=dirs%restart_input_dir, & - success=read_uv, scale=US%m_s_to_L_T*US%T_to_s) - CS%CAu_pred_stored = read_uv - else - if (.not. query_initialized(CS%h_av, "h2", restart_CS)) then - CS%h_av(:,:,:) = h(:,:,:) - call set_initialized(CS%h_av, "h2", restart_CS) - endif - endif - endif - call cpu_clock_begin(id_clock_pass_init) - call create_group_pass(pass_av_h_uvh, CS%u_av, CS%v_av, G%Domain, halo=2) - if (CS%CAu_pred_stored) then - call create_group_pass(pass_av_h_uvh, CS%CAu_pred, CS%CAv_pred, G%Domain, halo=2) - else - call create_group_pass(pass_av_h_uvh, CS%h_av, G%Domain, halo=2) - call create_group_pass(pass_av_h_uvh, uh, vh, G%Domain, halo=2) - endif - call do_group_pass(pass_av_h_uvh, G%Domain) - call cpu_clock_end(id_clock_pass_init) - flux_units = get_flux_units(GV) thickness_units = get_thickness_units(GV) CS%id_uh = register_diag_field('ocean_model', 'uh', diag%axesCuL, Time, & @@ -1800,11 +1707,11 @@ subroutine end_dyn_split_RK2b(CS) if (associated(CS%taux_bot)) deallocate(CS%taux_bot) if (associated(CS%tauy_bot)) deallocate(CS%tauy_bot) DEALLOC_(CS%uhbt) ; DEALLOC_(CS%vhbt) + DEALLOC_(CS%du_av_inst) ; DEALLOC_(CS%dv_av_inst) DEALLOC_(CS%u_accel_bt) ; DEALLOC_(CS%v_accel_bt) DEALLOC_(CS%visc_rem_u) ; DEALLOC_(CS%visc_rem_v) DEALLOC_(CS%eta) ; DEALLOC_(CS%eta_PF) ; DEALLOC_(CS%pbce) - DEALLOC_(CS%h_av) ; DEALLOC_(CS%u_av) ; DEALLOC_(CS%v_av) call dealloc_BT_cont_type(CS%BT_cont) deallocate(CS%AD_pred) From 9d57c15f6cada3ac98e0e7dc5c6a1d78b6c69409 Mon Sep 17 00:00:00 2001 From: Robert Hallberg Date: Sun, 17 Dec 2023 10:39:30 -0500 Subject: [PATCH 21/22] Regroup MOM_dynamics_split_RK2b halo updates This commit includes further revisions to MOM_dynamics_split_RK2b that avoid some unnecessary calculations and group some of the halo updates into fewer group passes. All answers are bitwise identical. --- src/core/MOM_dynamics_split_RK2b.F90 | 157 +++++++++------------------ 1 file changed, 53 insertions(+), 104 deletions(-) diff --git a/src/core/MOM_dynamics_split_RK2b.F90 b/src/core/MOM_dynamics_split_RK2b.F90 index 9cd8fbfc09..44a0b0bf5c 100644 --- a/src/core/MOM_dynamics_split_RK2b.F90 +++ b/src/core/MOM_dynamics_split_RK2b.F90 @@ -253,14 +253,13 @@ module MOM_dynamics_split_RK2b !> A pointer to the update_OBC control structure type(update_OBC_CS), pointer :: update_OBC_CSp => NULL() - type(group_pass_type) :: pass_eta !< Structure for group halo pass - type(group_pass_type) :: pass_visc_rem !< Structure for group halo pass - type(group_pass_type) :: pass_uvp !< Structure for group halo pass - type(group_pass_type) :: pass_hp_uv !< Structure for group halo pass - type(group_pass_type) :: pass_h_av !< Structure for group halo pass - type(group_pass_type) :: pass_uv !< Structure for group halo pass - type(group_pass_type) :: pass_h !< Structure for group halo pass - type(group_pass_type) :: pass_av_uvh !< Structure for group halo pass + type(group_pass_type) :: pass_eta !< Structure for group halo pass + type(group_pass_type) :: pass_visc_rem !< Structure for group halo pass + type(group_pass_type) :: pass_uvp !< Structure for group halo pass + type(group_pass_type) :: pass_uv_inst !< Structure for group halo pass + type(group_pass_type) :: pass_hp_uv !< Structure for group halo pass + type(group_pass_type) :: pass_hp_uhvh !< Structure for group halo pass + type(group_pass_type) :: pass_h_uv !< Structure for group halo pass end type MOM_dyn_split_RK2b_CS @@ -394,7 +393,6 @@ subroutine step_MOM_dyn_split_RK2b(u_av, v_av, h, tv, visc, Time_local, dt, forc logical :: BT_cont_BT_thick ! If true, use the BT_cont_type to estimate the ! relative weightings of the layers in calculating ! the barotropic accelerations. - logical :: Use_Stokes_PGF ! If true, add Stokes PGF to hydrostatic PGF !---For group halo pass logical :: showCallTree, sym @@ -469,17 +467,18 @@ subroutine step_MOM_dyn_split_RK2b(u_av, v_av, h, tv, visc, Time_local, dt, forc call create_group_pass(CS%pass_visc_rem, CS%visc_rem_u, CS%visc_rem_v, G%Domain, & To_All+SCALAR_PAIR, CGRID_NE, halo=max(1,cont_stencil)) call create_group_pass(CS%pass_uvp, up, vp, G%Domain, halo=max(1,cont_stencil)) + call create_group_pass(CS%pass_uv_inst, u_inst, v_inst, G%Domain, halo=max(2,cont_stencil)) + call create_group_pass(CS%pass_hp_uv, hp, G%Domain, halo=2) call create_group_pass(CS%pass_hp_uv, u_av, v_av, G%Domain, halo=max(2,obc_stencil)) call create_group_pass(CS%pass_hp_uv, uh(:,:,:), vh(:,:,:), G%Domain, halo=max(2,obc_stencil)) - call create_group_pass(CS%pass_uv, u_inst, v_inst, G%Domain, halo=max(2,cont_stencil)) - call create_group_pass(CS%pass_h, h, G%Domain, halo=max(2,cont_stencil)) - call create_group_pass(CS%pass_av_uvh, u_av, v_av, G%Domain, halo=max(2,obc_stencil)) - call create_group_pass(CS%pass_av_uvh, uh(:,:,:), vh(:,:,:), G%Domain, halo=max(2,obc_stencil)) + call create_group_pass(CS%pass_hp_uhvh, hp, G%Domain, halo=2) + call create_group_pass(CS%pass_hp_uhvh, uh(:,:,:), vh(:,:,:), G%Domain, halo=max(2,obc_stencil)) - call create_group_pass(CS%pass_h_av, hp, G%Domain, halo=2) - call create_group_pass(CS%pass_h_av, uh(:,:,:), vh(:,:,:), G%Domain, halo=max(2,obc_stencil)) + call create_group_pass(CS%pass_h_uv, h, G%Domain, halo=max(2,cont_stencil)) + call create_group_pass(CS%pass_h_uv, u_av, v_av, G%Domain, halo=max(2,obc_stencil)) + call create_group_pass(CS%pass_h_uv, uh(:,:,:), vh(:,:,:), G%Domain, halo=max(2,obc_stencil)) call cpu_clock_end(id_clock_pass) !--- end set up for group halo pass @@ -495,7 +494,7 @@ subroutine step_MOM_dyn_split_RK2b(u_av, v_av, h, tv, visc, Time_local, dt, forc call cpu_clock_end(id_clock_continuity) if (G%nonblocking_updates) & - call start_group_pass(CS%pass_h_av, G%Domain, clock=id_clock_pass) + call start_group_pass(CS%pass_hp_uhvh, G%Domain, clock=id_clock_pass) ! PFu = d/dx M(h,T,S) ! pbce = dM/deta @@ -511,31 +510,22 @@ subroutine step_MOM_dyn_split_RK2b(u_av, v_av, h, tv, visc, Time_local, dt, forc enddo ; enddo endif ! Stokes shear force contribution to pressure gradient - Use_Stokes_PGF = present(Waves) - if (Use_Stokes_PGF) then - Use_Stokes_PGF = associated(Waves) - if (Use_Stokes_PGF) Use_Stokes_PGF = Waves%Stokes_PGF - if (Use_Stokes_PGF) then - call thickness_to_dz(h, tv, dz, G, GV, US, halo_size=1) - call Stokes_PGF(G, GV, US, dz, u_av, v_av, CS%PFu_Stokes, CS%PFv_Stokes, Waves) - - ! We are adding Stokes_PGF to hydrostatic PGF here. The diag PFu/PFv - ! will therefore report the sum total PGF and we avoid other - ! modifications in the code. The PFu_Stokes is output within the waves routines. - if (.not.Waves%Passive_Stokes_PGF) then - do k=1,nz - do j=js,je ; do I=Isq,Ieq - CS%PFu(I,j,k) = CS%PFu(I,j,k) + CS%PFu_Stokes(I,j,k) - enddo ; enddo - enddo - do k=1,nz - do J=Jsq,Jeq ; do i=is,ie - CS%PFv(i,J,k) = CS%PFv(i,J,k) + CS%PFv_Stokes(i,J,k) - enddo ; enddo - enddo - endif + if (present(Waves)) then ; if (associated(Waves)) then ; if (Waves%Stokes_PGF) then + call thickness_to_dz(h, tv, dz, G, GV, US, halo_size=1) + call Stokes_PGF(G, GV, US, dz, u_av, v_av, CS%PFu_Stokes, CS%PFv_Stokes, Waves) + + ! We are adding Stokes_PGF to hydrostatic PGF here. The diag PFu/PFv + ! will therefore report the sum total PGF and we avoid other + ! modifications in the code. The PFu_Stokes is output within the waves routines. + if (.not.Waves%Passive_Stokes_PGF) then + do k=1,nz ; do j=js,je ; do I=Isq,Ieq + CS%PFu(I,j,k) = CS%PFu(I,j,k) + CS%PFu_Stokes(I,j,k) + enddo ; enddo ; enddo + do k=1,nz ; do J=Jsq,Jeq ; do i=is,ie + CS%PFv(i,J,k) = CS%PFv(i,J,k) + CS%PFv_Stokes(i,J,k) + enddo ; enddo ; enddo endif - endif + endif ; endif ; endif call cpu_clock_end(id_clock_pres) call disable_averaging(CS%diag) if (showCallTree) call callTree_wayPoint("done with PressureForce (step_MOM_dyn_split_RK2b)") @@ -544,15 +534,15 @@ subroutine step_MOM_dyn_split_RK2b(u_av, v_av, h, tv, visc, Time_local, dt, forc call open_boundary_zero_normal_flow(CS%OBC, G, GV, CS%PFu, CS%PFv) if (G%nonblocking_updates) then - call complete_group_pass(CS%pass_h_av, G%Domain, clock=id_clock_pass) + call complete_group_pass(CS%pass_hp_uhvh, G%Domain, clock=id_clock_pass) call start_group_pass(CS%pass_eta, G%Domain, clock=id_clock_pass) else - call do_group_pass(CS%pass_h_av, G%Domain, clock=id_clock_pass) + call do_group_pass(CS%pass_hp_uhvh, G%Domain, clock=id_clock_pass) endif !$OMP parallel do default(shared) do k=1,nz ; do j=js-2,je+2 ; do i=is-2,ie+2 - h_av(i,j,k) = 0.5*(hp(i,j,k) + h(i,j,k)) + h_av(i,j,k) = 0.5*(h(i,j,k) + hp(i,j,k)) enddo ; enddo ; enddo ! Calculate a predictor-step estimate of the Coriolis and momentum advection terms @@ -660,7 +650,7 @@ subroutine step_MOM_dyn_split_RK2b(u_av, v_av, h, tv, visc, Time_local, dt, forc v_inst(i,J,k) = v_av(i,J,k) - CS%dv_av_inst(i,j) * CS%visc_rem_v(i,J,k) enddo ; enddo ; enddo call cpu_clock_end(id_clock_mom_update) - call do_group_pass(CS%pass_uv, G%Domain, clock=id_clock_pass) + call do_group_pass(CS%pass_uv_inst, G%Domain, clock=id_clock_pass) ! u_accel_bt = layer accelerations due to barotropic solver call cpu_clock_begin(id_clock_continuity) @@ -781,7 +771,6 @@ subroutine step_MOM_dyn_split_RK2b(u_av, v_av, h, tv, visc, Time_local, dt, forc call do_group_pass(CS%pass_hp_uv, G%Domain, clock=id_clock_pass) if (associated(CS%OBC)) then - if (CS%debug) & call uvchksum("Pre OBC avg [uv]", u_av, v_av, G%HI, haloshift=1, symmetric=sym, scale=US%L_T_to_m_s) @@ -789,13 +778,6 @@ subroutine step_MOM_dyn_split_RK2b(u_av, v_av, h, tv, visc, Time_local, dt, forc if (CS%debug) & call uvchksum("Post OBC avg [uv]", u_av, v_av, G%HI, haloshift=1, symmetric=sym, scale=US%L_T_to_m_s) - - ! These should be done with a pass that excludes uh & vh. -! call do_group_pass(CS%pass_hp_uv, G%Domain, clock=id_clock_pass) - endif - - if (G%nonblocking_updates) then - call start_group_pass(CS%pass_av_uvh, G%Domain, clock=id_clock_pass) endif ! h_av = (h + hp)/2 @@ -830,34 +812,22 @@ subroutine step_MOM_dyn_split_RK2b(u_av, v_av, h, tv, visc, Time_local, dt, forc call PressureForce(hp, tv, CS%PFu, CS%PFv, G, GV, US, CS%PressureForce_CSp, & CS%ALE_CSp, p_surf, CS%pbce, CS%eta_PF) ! Stokes shear force contribution to pressure gradient - Use_Stokes_PGF = present(Waves) - if (Use_Stokes_PGF) then - Use_Stokes_PGF = associated(Waves) - if (Use_Stokes_PGF) Use_Stokes_PGF = Waves%Stokes_PGF - if (Use_Stokes_PGF) then - call thickness_to_dz(h, tv, dz, G, GV, US, halo_size=1) - call Stokes_PGF(G, GV, US, dz, u_av, v_av, CS%PFu_Stokes, CS%PFv_Stokes, Waves) - if (.not.Waves%Passive_Stokes_PGF) then - do k=1,nz - do j=js,je ; do I=Isq,Ieq - CS%PFu(I,j,k) = CS%PFu(I,j,k) + CS%PFu_Stokes(I,j,k) - enddo ; enddo - enddo - do k=1,nz - do J=Jsq,Jeq ; do i=is,ie - CS%PFv(i,J,k) = CS%PFv(i,J,k) + CS%PFv_Stokes(i,J,k) - enddo ; enddo - enddo - endif + if (present(Waves)) then ; if (associated(Waves)) then ; if (Waves%Stokes_PGF) then + call thickness_to_dz(h, tv, dz, G, GV, US, halo_size=1) + call Stokes_PGF(G, GV, US, dz, u_av, v_av, CS%PFu_Stokes, CS%PFv_Stokes, Waves) + if (.not.Waves%Passive_Stokes_PGF) then + do k=1,nz ; do j=js,je ; do I=Isq,Ieq + CS%PFu(I,j,k) = CS%PFu(I,j,k) + CS%PFu_Stokes(I,j,k) + enddo ; enddo ; enddo + do k=1,nz ; do J=Jsq,Jeq ; do i=is,ie + CS%PFv(i,J,k) = CS%PFv(i,J,k) + CS%PFv_Stokes(i,J,k) + enddo ; enddo ; enddo endif - endif + endif ; endif ; endif call cpu_clock_end(id_clock_pres) if (showCallTree) call callTree_wayPoint("done with PressureForce[hp=(1-b).h+b.h] (step_MOM_dyn_split_RK2b)") endif - if (G%nonblocking_updates) & - call complete_group_pass(CS%pass_av_uvh, G%Domain, clock=id_clock_pass) - if (BT_cont_BT_thick) then call btcalc(h, G, GV, CS%barotropic_CSp, CS%BT_cont%h_u, CS%BT_cont%h_v, & OBC=CS%OBC) @@ -994,24 +964,18 @@ subroutine step_MOM_dyn_split_RK2b(u_av, v_av, h, tv, visc, Time_local, dt, forc if (G%nonblocking_updates) then call cpu_clock_end(id_clock_vertvisc) - call start_group_pass(CS%pass_uv, G%Domain, clock=id_clock_pass) + call start_group_pass(CS%pass_uv_inst, G%Domain, clock=id_clock_pass) call cpu_clock_begin(id_clock_vertvisc) endif call vertvisc_remnant(visc, CS%visc_rem_u, CS%visc_rem_v, dt, G, GV, US, CS%vertvisc_CSp) call cpu_clock_end(id_clock_vertvisc) if (showCallTree) call callTree_wayPoint("done with vertvisc (step_MOM_dyn_split_RK2b)") -! Later, h_av = (h_in + h_out)/2, but for now use h_av to store h_in. - !$OMP parallel do default(shared) - do k=1,nz ; do j=js-2,je+2 ; do i=is-2,ie+2 - h_av(i,j,k) = h(i,j,k) - enddo ; enddo ; enddo - call do_group_pass(CS%pass_visc_rem, G%Domain, clock=id_clock_pass) if (G%nonblocking_updates) then - call complete_group_pass(CS%pass_uv, G%Domain, clock=id_clock_pass) + call complete_group_pass(CS%pass_uv_inst, G%Domain, clock=id_clock_pass) else - call do_group_pass(CS%pass_uv, G%Domain, clock=id_clock_pass) + call do_group_pass(CS%pass_uv_inst, G%Domain, clock=id_clock_pass) endif ! uh = u_av * h @@ -1032,31 +996,18 @@ subroutine step_MOM_dyn_split_RK2b(u_av, v_av, h, tv, visc, Time_local, dt, forc ! enddo ; enddo ; enddo call cpu_clock_end(id_clock_continuity) - call do_group_pass(CS%pass_h, G%Domain, clock=id_clock_pass) + + call do_group_pass(CS%pass_h_uv, G%Domain, clock=id_clock_pass) + ! Whenever thickness changes let the diag manager know, target grids ! for vertical remapping may need to be regenerated. call diag_update_remap_grids(CS%diag) if (showCallTree) call callTree_wayPoint("done with continuity (step_MOM_dyn_split_RK2b)") - if (G%nonblocking_updates) then - call start_group_pass(CS%pass_av_uvh, G%Domain, clock=id_clock_pass) - else - call do_group_pass(CS%pass_av_uvh, G%domain, clock=id_clock_pass) - endif - if (associated(CS%OBC)) then call radiation_open_bdry_conds(CS%OBC, u_av, u_old_rad_OBC, v_av, v_old_rad_OBC, G, GV, US, dt) endif - ! h_av = (h_in + h_out)/2 . Going in to this line, h_av = h_in. - !$OMP parallel do default(shared) - do k=1,nz ; do j=js-2,je+2 ; do i=is-2,ie+2 - h_av(i,j,k) = 0.5*(h_av(i,j,k) + h(i,j,k)) - enddo ; enddo ; enddo - - if (G%nonblocking_updates) & - call complete_group_pass(CS%pass_av_uvh, G%Domain, clock=id_clock_pass) - !$OMP parallel do default(shared) do k=1,nz do j=js-2,je+2 ; do I=Isq-2,Ieq+2 @@ -1169,10 +1120,8 @@ subroutine step_MOM_dyn_split_RK2b(u_av, v_av, h, tv, visc, Time_local, dt, forc if (CS%id_deta_dt > 0) call post_data(CS%id_deta_dt, deta_dt, CS%diag) if (CS%debug) then - call MOM_state_chksum("Corrector ", u_inst, v_inst, h, uh, vh, G, GV, US, symmetric=sym) - call uvchksum("Corrector avg [uv]", u_av, v_av, G%HI, haloshift=1, symmetric=sym, scale=US%L_T_to_m_s) - call hchksum(h_av, "Corrector avg h", G%HI, haloshift=1, scale=GV%H_to_MKS) - ! call MOM_state_chksum("Corrector avg ", u_av, v_av, h_av, uh, vh, G, GV, US) + call MOM_state_chksum("Corrector ", u_av, v_av, h, uh, vh, G, GV, US, symmetric=sym) + ! call uvchksum("Corrector inst [uv]", u_inst, v_inst, G%HI, symmetric=sym, scale=US%L_T_to_m_s) endif if (showCallTree) call callTree_leave("step_MOM_dyn_split_RK2b()") From 5137442fc91aced5162e00f5b8d2a1b5906b8e32 Mon Sep 17 00:00:00 2001 From: Robert Hallberg Date: Wed, 20 Dec 2023 16:44:53 -0500 Subject: [PATCH 22/22] +Correct description of SPLIT_RK2B Corrected the description of the runtime parameter SPLIT_RK2B that will appear in the MOM_parameter_doc files and in the doxygen descriptions of the MOM module to better reflect what was ultimately being done with this new scheme. All answers are bitwise identical, but there are changes to the (newly added) contents of some MOM_parameter_doc files. --- src/core/MOM.F90 | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/src/core/MOM.F90 b/src/core/MOM.F90 index e1f31b7558..2800011ccf 100644 --- a/src/core/MOM.F90 +++ b/src/core/MOM.F90 @@ -288,8 +288,9 @@ module MOM !! undocumented run-time flag that is fragile. logical :: split !< If true, use the split time stepping scheme. logical :: use_alt_split !< If true, use a version of the split explicit time stepping - !! with a heavier emphasis on consistent tranports between the - !! layered and barotroic variables. + !! scheme that exchanges velocities with step_MOM that have the + !! average barotropic phase over a baroclinic timestep rather + !! than the instantaneous barotropic phase. logical :: use_RK2 !< If true, use RK2 instead of RK3 in unsplit mode !! (i.e., no split between barotropic and baroclinic). logical :: interface_filter !< If true, apply an interface height filter immediately @@ -2174,8 +2175,9 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, & call get_param(param_file, "MOM", "SPLIT", CS%split, & "Use the split time stepping if true.", default=.true.) call get_param(param_file, "MOM", "SPLIT_RK2B", CS%use_alt_split, & - "If true, use a version of the split explicit time stepping with a heavier "//& - "emphasis on consistent tranports between the layered and barotroic variables.", & + "If true, use a version of the split explicit time stepping scheme that "//& + "exchanges velocities with step_MOM that have the average barotropic phase over "//& + "a baroclinic timestep rather than the instantaneous barotropic phase.", & default=.false., do_not_log=.not.CS%split) if (CS%split) then CS%use_RK2 = .false.