Skip to content

Commit

Permalink
+Make h_neglect argument mandatory in 28 routines
Browse files Browse the repository at this point in the history
  Made the h_neglect argument non-optional to 28 routines, because there is no
way to provide a consistent hard-coded default for a dimensional parameter.  The
routines where this change was made include remapping_core_h, remapping_core_w,
build_reconstructions_1d, P1M_interpolation, P3M_interpolation,
P3M_boundary_extrapolation, PLM_reconstruction, PLM_boundary_extrapolation,
PPM_reconstruction, PPM_limiter_standard, PPM_boundary_extrapolation,
PQM_reconstruction, PQM_limiter, PQM_boundary_extrapolation_v1,
build_hycom1_column, build_rho_column, bound_edge_values,
edge_values_explicit_h4, edge_values_explicit_h4cw, edge_values_implicit_h4,
edge_slopes_implicit_h3, edge_slopes_implicit_h5, edge_values_implicit_h6,
regridding_set_ppolys, build_and_interpolate_grid, remapByProjection,
remapByDeltaZ, and integrateReconOnInterval.

  In those cases that also have an optional h_neglect_edge argument the default
is now set to h_neglect.  Improperly hard-coded dimensional default values for
h_neglect or h_neglect_edge were eliminated in 15 places as a result of this
change, but they were added back in 2 unit testing routines (one of these is
archaic and unused) that do not use exercise dimensional rescaling tests.

  Because these previously optional arguments were already present in all calls
from the dev/gfdl or main branches of the MOM6 code, all answers are bitwise
identical in the regression tests, but this change in interfaces could impact
other code that is not in the main branch of MOM6.
  • Loading branch information
Hallberg-NOAA committed Jul 31, 2024
1 parent 90749f3 commit fbd77ce
Show file tree
Hide file tree
Showing 12 changed files with 160 additions and 232 deletions.
6 changes: 4 additions & 2 deletions config_src/drivers/timing_tests/time_MOM_remapping.F90
Original file line number Diff line number Diff line change
Expand Up @@ -17,8 +17,9 @@ program time_MOM_remapping
real, dimension(nschemes) :: tmin ! Shortest time for a call [s]
real, dimension(nschemes) :: tmax ! Longest time for a call [s]
real, dimension(:,:), allocatable :: u0, u1 ! Source/target values [arbitrary but same units as each other]
real, dimension(:,:), allocatable :: h0, h1 ! Source target thicknesses [0..1]
real, dimension(:,:), allocatable :: h0, h1 ! Source target thicknesses [0..1] [nondim]
real :: start, finish ! Times [s]
real :: h_neglect ! A negligible thickness [nondim]
real :: h0sum, h1sum ! Totals of h0 and h1 [nondim]
integer :: ij, k, isamp, iter, ischeme ! Indices and counters
integer :: seed_size ! Number of integers used by seed
Expand Down Expand Up @@ -50,6 +51,7 @@ program time_MOM_remapping
h0(:,ij) = h0(:,ij) / h0sum
h1(:,ij) = h1(:,ij) / h1sum
enddo
h_neglect = 1.0-30

! Loop over many samples of timing loop to collect statistics
tmean(:) = 0.
Expand All @@ -63,7 +65,7 @@ program time_MOM_remapping
call cpu_time(start)
do iter = 1, nits ! Make many passes to reduce sampling error
do ij = 1, nij ! Calling nij times to make similar to cost in MOM_ALE()
call remapping_core_h(CS, nk, h0(:,ij), u0(:,ij), nk, h1(:,ij), u1(:,ij))
call remapping_core_h(CS, nk, h0(:,ij), u0(:,ij), nk, h1(:,ij), u1(:,ij), h_neglect)
enddo
enddo
call cpu_time(finish)
Expand Down
62 changes: 30 additions & 32 deletions src/ALE/MOM_remapping.F90
Original file line number Diff line number Diff line change
Expand Up @@ -190,12 +190,12 @@ subroutine remapping_core_h(CS, n0, h0, u0, n1, h1, u1, h_neglect, h_neglect_edg
integer, intent(in) :: n1 !< Number of cells on target grid
real, dimension(n1), intent(in) :: h1 !< Cell widths on target grid [H]
real, dimension(n1), intent(out) :: u1 !< Cell averages on target grid [A]
real, optional, intent(in) :: h_neglect !< A negligibly small width for the
real, intent(in) :: h_neglect !< A negligibly small width for the
!! purpose of cell reconstructions
!! in the same units as h0 [H]
real, optional, intent(in) :: h_neglect_edge !< A negligibly small width
!! for the purpose of edge value
!! calculations in the same units as h0 [H]
real, optional, intent(in) :: h_neglect_edge !< A negligibly small width for the purpose
!! of edge value calculations in the same units as h0 [H].
!! The default is h_neglect.
logical, dimension(n0), optional, intent(in) :: PCM_cell !< If present, use PCM remapping for
!! cells in the source grid where this is true.

Expand All @@ -204,14 +204,13 @@ subroutine remapping_core_h(CS, n0, h0, u0, n1, h1, u1, h_neglect, h_neglect_edg
real, dimension(n0,2) :: ppoly_r_S ! Edge slope of polynomial [A H-1]
real, dimension(n0,CS%degree+1) :: ppoly_r_coefs ! Coefficients of polynomial reconstructions [A]
real :: uh_err ! A bound on the error in the sum of u*h, as estimated by the remapping code [A H]
real :: hNeglect, hNeglect_edge ! Negligibly small cell widths in the same units as h0 [H]
real :: hNeglect_edge ! Negligibly small cell widths in the same units as h0 [H]
integer :: iMethod ! An integer indicating the integration method used

hNeglect = 1.0e-30 ; if (present(h_neglect)) hNeglect = h_neglect
hNeglect_edge = 1.0e-10 ; if (present(h_neglect_edge)) hNeglect_edge = h_neglect_edge
hNeglect_edge = h_neglect ; if (present(h_neglect_edge)) hNeglect_edge = h_neglect_edge

call build_reconstructions_1d( CS, n0, h0, u0, ppoly_r_coefs, ppoly_r_E, ppoly_r_S, iMethod, &
hNeglect, hNeglect_edge, PCM_cell )
h_neglect, hNeglect_edge, PCM_cell )

if (CS%om4_remap_via_sub_cells) then

Expand Down Expand Up @@ -244,27 +243,26 @@ subroutine remapping_core_w( CS, n0, h0, u0, n1, dx, u1, h_neglect, h_neglect_ed
integer, intent(in) :: n1 !< Number of cells on target grid
real, dimension(n1+1), intent(in) :: dx !< Cell widths on target grid [H]
real, dimension(n1), intent(out) :: u1 !< Cell averages on target grid [A]
real, optional, intent(in) :: h_neglect !< A negligibly small width for the
real, intent(in) :: h_neglect !< A negligibly small width for the
!! purpose of cell reconstructions
!! in the same units as h0 [H].
real, optional, intent(in) :: h_neglect_edge !< A negligibly small width
!! for the purpose of edge value
!! calculations in the same units as h0 [H].
real, optional, intent(in) :: h_neglect_edge !< A negligibly small width for the purpose
!! of edge value calculations in the same units as h0 [H].
!! The default is h_neglect.
! Local variables
real, dimension(n0,2) :: ppoly_r_E ! Edge value of polynomial [A]
real, dimension(n0,2) :: ppoly_r_S ! Edge slope of polynomial [A H-1]
real, dimension(n0,CS%degree+1) :: ppoly_r_coefs ! Coefficients of polynomial reconstructions [A]
real, dimension(n1) :: h1 !< Cell widths on target grid [H]
real :: uh_err ! A bound on the error in the sum of u*h, as estimated by the remapping code [A H]
real :: hNeglect, hNeglect_edge ! Negligibly small thicknesses [H]
real :: hNeglect_edge ! Negligibly small thicknesses [H]
integer :: iMethod ! An integer indicating the integration method used
integer :: k

hNeglect = 1.0e-30 ; if (present(h_neglect)) hNeglect = h_neglect
hNeglect_edge = 1.0e-10 ; if (present(h_neglect_edge)) hNeglect_edge = h_neglect_edge
hNeglect_edge = h_neglect ; if (present(h_neglect_edge)) hNeglect_edge = h_neglect_edge

call build_reconstructions_1d( CS, n0, h0, u0, ppoly_r_coefs, ppoly_r_E, ppoly_r_S, iMethod,&
hNeglect, hNeglect_edge )
h_neglect, hNeglect_edge )

if (CS%check_reconstruction) call check_reconstructions_1d(n0, h0, u0, CS%degree, &
CS%boundary_extrapolation, ppoly_r_coefs, ppoly_r_E)
Expand Down Expand Up @@ -300,19 +298,23 @@ subroutine build_reconstructions_1d( CS, n0, h0, u0, ppoly_r_coefs, &
real, dimension(n0,2), intent(out) :: ppoly_r_E !< Edge value of polynomial [A]
real, dimension(n0,2), intent(out) :: ppoly_r_S !< Edge slope of polynomial [A H-1]
integer, intent(out) :: iMethod !< Integration method
real, optional, intent(in) :: h_neglect !< A negligibly small width for the
real, intent(in) :: h_neglect !< A negligibly small width for the
!! purpose of cell reconstructions
!! in the same units as h0 [H]
real, optional, intent(in) :: h_neglect_edge !< A negligibly small width
!! for the purpose of edge value
!! calculations in the same units as h0 [H]
real, optional, intent(in) :: h_neglect_edge !< A negligibly small width for the purpose
!! of edge value calculations in the same units as h0 [H].
!! The default is h_neglect.
logical, optional, intent(in) :: PCM_cell(n0) !< If present, use PCM remapping for
!! cells from the source grid where this is true.

! Local variables
real :: h_neg_edge ! A negligibly small width for the purpose of edge value
! calculations in the same units as h0 [H]
integer :: local_remapping_scheme
integer :: k, n

h_neg_edge = h_neglect ; if (present(h_neglect_edge)) h_neg_edge = h_neglect_edge

! Reset polynomial
ppoly_r_E(:,:) = 0.0
ppoly_r_S(:,:) = 0.0
Expand Down Expand Up @@ -349,22 +351,22 @@ subroutine build_reconstructions_1d( CS, n0, h0, u0, ppoly_r_coefs, &
iMethod = INTEGRATION_PLM
case ( REMAPPING_PPM_CW )
! identical to REMAPPING_PPM_HYBGEN
call edge_values_explicit_h4cw( n0, h0, u0, ppoly_r_E, h_neglect_edge )
call edge_values_explicit_h4cw( n0, h0, u0, ppoly_r_E, h_neg_edge )
call PPM_monotonicity( n0, u0, ppoly_r_E )
call PPM_reconstruction( n0, h0, u0, ppoly_r_E, ppoly_r_coefs, h_neglect, answer_date=CS%answer_date )
if ( CS%boundary_extrapolation ) then
call PPM_boundary_extrapolation( n0, h0, u0, ppoly_r_E, ppoly_r_coefs, h_neglect )
endif
iMethod = INTEGRATION_PPM
case ( REMAPPING_PPM_H4 )
call edge_values_explicit_h4( n0, h0, u0, ppoly_r_E, h_neglect_edge, answer_date=CS%answer_date )
call edge_values_explicit_h4( n0, h0, u0, ppoly_r_E, h_neg_edge, answer_date=CS%answer_date )
call PPM_reconstruction( n0, h0, u0, ppoly_r_E, ppoly_r_coefs, h_neglect, answer_date=CS%answer_date )
if ( CS%boundary_extrapolation ) then
call PPM_boundary_extrapolation( n0, h0, u0, ppoly_r_E, ppoly_r_coefs, h_neglect )
endif
iMethod = INTEGRATION_PPM
case ( REMAPPING_PPM_IH4 )
call edge_values_implicit_h4( n0, h0, u0, ppoly_r_E, h_neglect_edge, answer_date=CS%answer_date )
call edge_values_implicit_h4( n0, h0, u0, ppoly_r_E, h_neg_edge, answer_date=CS%answer_date )
call PPM_reconstruction( n0, h0, u0, ppoly_r_E, ppoly_r_coefs, h_neglect, answer_date=CS%answer_date )
if ( CS%boundary_extrapolation ) then
call PPM_boundary_extrapolation( n0, h0, u0, ppoly_r_E, ppoly_r_coefs, h_neglect )
Expand All @@ -383,7 +385,7 @@ subroutine build_reconstructions_1d( CS, n0, h0, u0, ppoly_r_coefs, &
call PPM_boundary_extrapolation( n0, h0, u0, ppoly_r_E, ppoly_r_coefs, h_neglect )
iMethod = INTEGRATION_PPM
case ( REMAPPING_PQM_IH4IH3 )
call edge_values_implicit_h4( n0, h0, u0, ppoly_r_E, h_neglect_edge, answer_date=CS%answer_date )
call edge_values_implicit_h4( n0, h0, u0, ppoly_r_E, h_neg_edge, answer_date=CS%answer_date )
call edge_slopes_implicit_h3( n0, h0, u0, ppoly_r_S, h_neglect, answer_date=CS%answer_date )
call PQM_reconstruction( n0, h0, u0, ppoly_r_E, ppoly_r_S, ppoly_r_coefs, h_neglect, &
answer_date=CS%answer_date )
Expand All @@ -393,7 +395,7 @@ subroutine build_reconstructions_1d( CS, n0, h0, u0, ppoly_r_coefs, &
endif
iMethod = INTEGRATION_PQM
case ( REMAPPING_PQM_IH6IH5 )
call edge_values_implicit_h6( n0, h0, u0, ppoly_r_E, h_neglect_edge, answer_date=CS%answer_date )
call edge_values_implicit_h6( n0, h0, u0, ppoly_r_E, h_neg_edge, answer_date=CS%answer_date )
call edge_slopes_implicit_h5( n0, h0, u0, ppoly_r_S, h_neglect, answer_date=CS%answer_date )
call PQM_reconstruction( n0, h0, u0, ppoly_r_E, ppoly_r_S, ppoly_r_coefs, h_neglect, &
answer_date=CS%answer_date )
Expand Down Expand Up @@ -1615,21 +1617,17 @@ logical function remapping_unit_tests(verbose)
real :: u02_err ! Error in remaping [A]
integer, allocatable, dimension(:) :: isrc_start, isrc_end, isrc_max, itgt_start, itgt_end, isub_src ! Indices
integer :: answer_date ! The vintage of the expressions to test
real, parameter :: hNeglect_dflt = 1.0e-30 ! A thickness [H ~> m or kg m-2] that can be
! added to thicknesses in a denominator without
! changing the numerical result, except where
! a division by zero would otherwise occur.
real :: err ! Errors in the remapped thicknesses [H] or values [A]
real :: h_neglect, h_neglect_edge ! Tiny thicknesses used in remapping [H]
type(testing) :: test ! Unit testing convenience functions
integer :: om4
integer :: i, om4
character(len=4) :: om4_tag

call test%set( verbose=verbose ) ! Sets the verbosity flag in test

answer_date = 20190101 ! 20181231
h_neglect = hNeglect_dflt
h_neglect_edge = hNeglect_dflt ; if (answer_date < 20190101) h_neglect_edge = 1.0e-10
h_neglect = 1.0e-30
h_neglect_edge = h_neglect ; if (answer_date < 20190101) h_neglect_edge = 1.0e-10

if (verbose) write(test%stdout,*) ' ===== MOM_remapping: remapping_unit_tests ================='

Expand Down
2 changes: 1 addition & 1 deletion src/ALE/P1M_functions.F90
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ subroutine P1M_interpolation( N, h, u, edge_values, ppoly_coef, h_neglect, answe
real, dimension(:,:), intent(inout) :: edge_values !< Potentially modified edge values [A]
real, dimension(:,:), intent(inout) :: ppoly_coef !< Potentially modified
!! piecewise polynomial coefficients, mainly [A]
real, optional, intent(in) :: h_neglect !< A negligibly small width [H]
real, intent(in) :: h_neglect !< A negligibly small width [H]
integer, optional, intent(in) :: answer_date !< The vintage of the expressions to use

! Local variables
Expand Down
Loading

0 comments on commit fbd77ce

Please sign in to comment.