Skip to content

Commit c23c244

Browse files
raphaeldussinRaphael Dussin
andauthored
(*) Add option for minmod limiter for RayTracing (#948)
* (*) Add option for minmod limiter for RayTracing This PR adds a minmod limiter option for the advection of the internal tides energy, which becomes the new default. The current positive definite scheme is kept as an option but has shown to create ripples at the grid scale. * change adv_limiter options from string to integer --------- Co-authored-by: Raphael Dussin <Raphael.Dussin@noaa.gov>
1 parent b18bca2 commit c23c244

File tree

1 file changed

+88
-7
lines changed

1 file changed

+88
-7
lines changed

src/parameterizations/lateral/MOM_internal_tides.F90

Lines changed: 88 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ module MOM_internal_tides
2424
use MOM_restart, only : register_restart_field, MOM_restart_CS, restart_init, save_restart
2525
use MOM_restart, only : lock_check, restart_registry_lock
2626
use MOM_spatial_means, only : global_area_integral
27-
use MOM_string_functions, only: extract_real
27+
use MOM_string_functions, only: extract_real, uppercase
2828
use MOM_time_manager, only : time_type, time_type_to_real, operator(+), operator(/), operator(-)
2929
use MOM_unit_scaling, only : unit_scale_type
3030
use MOM_variables, only : surface, thermo_var_ptrs, vertvisc_type
@@ -154,6 +154,7 @@ module MOM_internal_tides
154154
type(time_type), pointer :: Time => NULL() !< A pointer to the model's clock.
155155
type(group_pass_type) :: pass_En !< Pass 5d array Energy as a group of 3d arrays
156156
character(len=200) :: inputdir !< directory to look for coastline angle file
157+
integer :: itides_adv_limiter !< The type of limiter to use for the energy advection scheme
157158
real, allocatable, dimension(:,:,:,:) :: decay_rate_2d !< rate at which internal tide energy is
158159
!! lost to the interior ocean internal wave field
159160
!! as a function of longitude, latitude, frequency
@@ -260,6 +261,13 @@ module MOM_internal_tides
260261
!>@}
261262
end type loop_bounds_type
262263

264+
!>@{ Enumeration values for numerical schemes
265+
integer, parameter :: LIMITER_ADV_MINMOD = 1
266+
integer, parameter :: LIMITER_ADV_POSITIVE = 2
267+
character*(20), parameter :: LIMITER_ADV_MINMOD_STRING = "MINMOD"
268+
character*(20), parameter :: LIMITER_ADV_POSITIVE_STRING = "POSITIVE"
269+
!>@}
270+
263271
contains
264272

265273
!> Calls subroutines in this file that are needed to refract, propagate,
@@ -2267,7 +2275,8 @@ subroutine propagate_x(En, speed_x, Cgx_av, dCgx, dt, G, US, Nangle, CS, LB, res
22672275
EnL(i,j) = En(i,j,a) ; EnR(i,j) = En(i,j,a)
22682276
enddo ; enddo
22692277
else
2270-
call PPM_reconstruction_x(En(:,:,a), EnL, EnR, G, LB, simple_2nd=CS%simple_2nd)
2278+
call PPM_reconstruction_x(En(:,:,a), EnL, EnR, G, LB, &
2279+
simple_2nd=CS%simple_2nd, adv_limiter=CS%itides_adv_limiter)
22712280
endif
22722281

22732282
do j=jsh,jeh
@@ -2349,7 +2358,8 @@ subroutine propagate_y(En, speed_y, Cgy_av, dCgy, dt, G, US, Nangle, CS, LB, res
23492358
EnL(i,j) = En(i,j,a) ; EnR(i,j) = En(i,j,a)
23502359
enddo ; enddo
23512360
else
2352-
call PPM_reconstruction_y(En(:,:,a), EnL, EnR, G, LB, simple_2nd=CS%simple_2nd)
2361+
call PPM_reconstruction_y(En(:,:,a), EnL, EnR, G, LB, &
2362+
simple_2nd=CS%simple_2nd, adv_limiter=CS%itides_adv_limiter)
23532363
endif
23542364

23552365
do J=jsh-1,jeh
@@ -2740,7 +2750,7 @@ subroutine correct_halo_rotation(En, test, G, NAngle, halo)
27402750
end subroutine correct_halo_rotation
27412751

27422752
!> Calculates left/right edge values for PPM reconstruction in x-direction.
2743-
subroutine PPM_reconstruction_x(h_in, h_l, h_r, G, LB, simple_2nd)
2753+
subroutine PPM_reconstruction_x(h_in, h_l, h_r, G, LB, simple_2nd, adv_limiter)
27442754
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
27452755
real, dimension(SZI_(G),SZJ_(G)), intent(in) :: h_in !< Energy density in a sector (2D)
27462756
!! [H Z2 T-2 ~> m3 s-2 or J m-2]
@@ -2752,6 +2762,8 @@ subroutine PPM_reconstruction_x(h_in, h_l, h_r, G, LB, simple_2nd)
27522762
logical, intent(in) :: simple_2nd !< If true, use the arithmetic mean
27532763
!! energy densities as default edge values
27542764
!! for a simple 2nd order scheme.
2765+
integer, intent(in) :: adv_limiter !< The type of limiter used
2766+
27552767
! Local variables
27562768
real, dimension(SZI_(G),SZJ_(G)) :: slp ! The slope in energy density times the cell width
27572769
! [H Z2 T-2 ~> m3 s-2 or J m-2]
@@ -2815,11 +2827,17 @@ subroutine PPM_reconstruction_x(h_in, h_l, h_r, G, LB, simple_2nd)
28152827
enddo ; enddo
28162828
endif
28172829

2818-
call PPM_limit_pos(h_in, h_l, h_r, 0.0, G, isl, iel, jsl, jel)
2830+
select case(adv_limiter)
2831+
case (LIMITER_ADV_POSITIVE)
2832+
call PPM_limit_pos(h_in, h_l, h_r, 0.0, G, isl, iel, jsl, jel)
2833+
case (LIMITER_ADV_MINMOD)
2834+
call minmod_limiter(h_in, h_l, h_r, G, isl, iel, jsl, jel)
2835+
end select
2836+
28192837
end subroutine PPM_reconstruction_x
28202838

28212839
!> Calculates left/right edge valus for PPM reconstruction in y-direction.
2822-
subroutine PPM_reconstruction_y(h_in, h_l, h_r, G, LB, simple_2nd)
2840+
subroutine PPM_reconstruction_y(h_in, h_l, h_r, G, LB, simple_2nd, adv_limiter)
28232841
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
28242842
real, dimension(SZI_(G),SZJ_(G)), intent(in) :: h_in !< Energy density in a sector (2D)
28252843
!! [H Z2 T-2 ~> m3 s-2 or J m-2]
@@ -2831,6 +2849,8 @@ subroutine PPM_reconstruction_y(h_in, h_l, h_r, G, LB, simple_2nd)
28312849
logical, intent(in) :: simple_2nd !< If true, use the arithmetic mean
28322850
!! energy densities as default edge values
28332851
!! for a simple 2nd order scheme.
2852+
integer, intent(in) :: adv_limiter !< The type of limiter used
2853+
28342854
! Local variables
28352855
real, dimension(SZI_(G),SZJ_(G)) :: slp ! The slope in energy density times the cell width
28362856
! [H Z2 T-2 ~> m3 s-2 or J m-2]
@@ -2892,7 +2912,13 @@ subroutine PPM_reconstruction_y(h_in, h_l, h_r, G, LB, simple_2nd)
28922912
enddo ; enddo
28932913
endif
28942914

2895-
call PPM_limit_pos(h_in, h_l, h_r, 0.0, G, isl, iel, jsl, jel)
2915+
select case(adv_limiter)
2916+
case (LIMITER_ADV_POSITIVE)
2917+
call PPM_limit_pos(h_in, h_l, h_r, 0.0, G, isl, iel, jsl, jel)
2918+
case (LIMITER_ADV_MINMOD)
2919+
call minmod_limiter(h_in, h_l, h_r, G, isl, iel, jsl, jel)
2920+
end select
2921+
28962922
end subroutine PPM_reconstruction_y
28972923

28982924
!> Limits the left/right edge values of the PPM reconstruction
@@ -2941,6 +2967,42 @@ subroutine PPM_limit_pos(h_in, h_L, h_R, h_min, G, iis, iie, jis, jie)
29412967
enddo ; enddo
29422968
end subroutine PPM_limit_pos
29432969

2970+
!> Limits the left/right edge values using the simple minmod limiter
2971+
!! written in a way that avoids branching in favor of intrinsics
2972+
subroutine minmod_limiter(h_in, h_L, h_R, G, iis, iie, jis, jie)
2973+
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
2974+
real, dimension(SZI_(G),SZJ_(G)), intent(in) :: h_in !< Energy density in each sector (2D)
2975+
!! [H Z2 T-2 ~> m3 s-2 or J m-2]
2976+
real, dimension(SZI_(G),SZJ_(G)), intent(inout) :: h_L !< Left edge value of reconstruction
2977+
!! [H Z2 T-2 ~> m3 s-2 or J m-2]
2978+
real, dimension(SZI_(G),SZJ_(G)), intent(inout) :: h_R !< Right edge value of reconstruction
2979+
!! [H Z2 T-2 ~> m3 s-2 or J m-2]
2980+
integer, intent(in) :: iis !< Start i-index for computations
2981+
integer, intent(in) :: iie !< End i-index for computations
2982+
integer, intent(in) :: jis !< Start j-index for computations
2983+
integer, intent(in) :: jie !< End j-index for computations
2984+
! Local variables
2985+
real :: sign_h_L, sign_h_R, sign_h_in ! the signs of the edge and center values
2986+
real :: sign_h_L_in, sign_h_R_in ! products of signs, detect crossing the zero line
2987+
integer :: i, j
2988+
2989+
do j=jis,jie ; do i=iis,iie
2990+
2991+
sign_h_L = sign(1.0d0, h_L(i,j))
2992+
sign_h_R = sign(1.0d0, h_R(i,j))
2993+
sign_h_in = sign(1.0d0, h_in(i,j))
2994+
2995+
sign_h_L_in = sign_h_L * sign_h_in
2996+
sign_h_R_in = sign_h_R * sign_h_in
2997+
2998+
! if opposite signs, goes to zero else take the min of edge and centers values
2999+
h_L(i,j) = (0.5 * (sign_h_L_in + 1.0)) * (sign_h_L * min(abs(h_L(i,j)), abs(h_in(i,j))))
3000+
h_R(i,j) = (0.5 * (sign_h_R_in + 1.0)) * (sign_h_R * min(abs(h_R(i,j)), abs(h_in(i,j))))
3001+
3002+
enddo ; enddo
3003+
3004+
end subroutine minmod_limiter
3005+
29443006
subroutine register_int_tide_restarts(G, GV, US, param_file, CS, restart_CS)
29453007
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
29463008
type(verticalGrid_type),intent(in):: GV !< The ocean's vertical grid structure.
@@ -3131,6 +3193,7 @@ subroutine internal_tides_init(Time, G, GV, US, param_file, diag, CS)
31313193
character(len=200) :: refl_pref_file, refl_dbl_file, trans_file
31323194
character(len=200) :: h2_file, decay_file
31333195
character(len=80) :: rough_var ! Input file variable names
3196+
character(len=80) :: tmpstr
31343197

31353198
character(len=240), dimension(:), allocatable :: energy_fractions
31363199
character(len=240) :: periods
@@ -3291,6 +3354,24 @@ subroutine internal_tides_init(Time, G, GV, US, param_file, diag, CS)
32913354
"1st-order upwind advection. This scheme is highly "//&
32923355
"continuity solver. This scheme is highly "//&
32933356
"diffusive but may be useful for debugging.", default=.false.)
3357+
call get_param(param_file, mdl, "INTERNAL_TIDE_ADV_LIMITER", tmpstr, &
3358+
"Choose the limiter scheme used for the internal tide advection scheme, "//&
3359+
"available schemes are: \n"//&
3360+
"\t POSITIVE - a positive definite scheme similar to the continuity solver. \n"//&
3361+
"\t MINMOD - the simplest limiter.", default=LIMITER_ADV_MINMOD_STRING)
3362+
3363+
tmpstr = uppercase(tmpstr)
3364+
select case (tmpstr)
3365+
case (LIMITER_ADV_POSITIVE_STRING)
3366+
CS%itides_adv_limiter = LIMITER_ADV_POSITIVE
3367+
case (LIMITER_ADV_MINMOD_STRING)
3368+
CS%itides_adv_limiter = LIMITER_ADV_MINMOD
3369+
case default
3370+
call MOM_mesg('internal_tide_init: Advection limiter ="'//trim(tmpstr)//'"', 0)
3371+
call MOM_error(FATAL, "internal_tide_init: Unrecognized setting "// &
3372+
"#define INTERNAL_TIDE_ADV_LIMITER "//trim(tmpstr)//" found in input file.")
3373+
end select
3374+
32943375
call get_param(param_file, mdl, "INTERNAL_TIDE_BACKGROUND_DRAG", CS%apply_background_drag, &
32953376
"If true, the internal tide ray-tracing advection uses a background drag "//&
32963377
"term as a sink.", default=.false.)

0 commit comments

Comments
 (0)