Skip to content

Commit

Permalink
Renames lateral_boundary_mixing to lateral_boundary_diffusion
Browse files Browse the repository at this point in the history
We think this is a more appropriate name.
  • Loading branch information
gustavo-marques committed Sep 27, 2019
1 parent 69ec18c commit 5583f84
Show file tree
Hide file tree
Showing 4 changed files with 29 additions and 29 deletions.
2 changes: 1 addition & 1 deletion src/core/MOM_unit_tests.F90
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ module MOM_unit_tests
use MOM_remapping, only : remapping_unit_tests
use MOM_neutral_diffusion, only : neutral_diffusion_unit_tests
use MOM_diag_vkernels, only : diag_vkernels_unit_tests
use MOM_lateral_boundary_mixing, only : near_boundary_unit_tests
use MOM_lateral_boundary_diffusion, only : near_boundary_unit_tests

implicit none ; private

Expand Down
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
!> Calculate and apply diffusive fluxes as a parameterization of lateral mixing (non-neutral) by
!! mesoscale eddies near the top and bottom boundary layers of the ocean.
module MOM_lateral_boundary_mixing
module MOM_lateral_boundary_diffusion

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

Expand All @@ -25,15 +25,15 @@ module MOM_lateral_boundary_mixing

implicit none ; private

public near_boundary_unit_tests, lateral_boundary_mixing, lateral_boundary_mixing_init
public near_boundary_unit_tests, lateral_boundary_diffusion, lateral_boundary_diffusion_init
public boundary_k_range
! Private parameters to avoid doing string comparisons for bottom or top boundary layer
integer, public, parameter :: SURFACE = -1 !< Set a value that corresponds to the surface bopundary
integer, public, parameter :: BOTTOM = 1 !< Set a value that corresponds to the bottom boundary
#include <MOM_memory.h>

!> Sets parameters for lateral boundary mixing module.
type, public :: lateral_boundary_mixing_CS ; private
type, public :: lateral_boundary_diffusion_CS ; private
integer :: method !< Determine which of the three methods calculate
!! and apply near boundary layer fluxes
!! 1. bulk-layer approach
Expand All @@ -47,40 +47,40 @@ module MOM_lateral_boundary_mixing
type(energetic_PBL_CS), pointer :: energetic_PBL_CSp => NULL() !< ePBL control structure needed to get MLD
type(diag_ctrl), pointer :: diag => NULL() !< A structure that is used to
!! regulate the timing of diagnostic output.
end type lateral_boundary_mixing_CS
end type lateral_boundary_diffusion_CS

! This include declares and sets the variable "version".
#include "version_variable.h"
character(len=40) :: mdl = "MOM_lateral_boundary_mixing" !< Name of this module
character(len=40) :: mdl = "MOM_lateral_boundary_diffusion" !< Name of this module

contains

!> Initialization routine that reads runtime parameters and sets up pointers to other control structures that might be
!! needed for lateral boundary mixing
logical function lateral_boundary_mixing_init(Time, G, param_file, diag, diabatic_CSp, CS)
logical function lateral_boundary_diffusion_init(Time, G, param_file, diag, diabatic_CSp, CS)
type(time_type), target, intent(in) :: Time !< Time structure
type(ocean_grid_type), intent(in) :: G !< Grid structure
type(param_file_type), intent(in) :: param_file !< Parameter file structure
type(diag_ctrl), target, intent(inout) :: diag !< Diagnostics control structure
type(diabatic_CS), pointer :: diabatic_CSp !< KPP control structure needed to get BLD
type(lateral_boundary_mixing_CS), pointer :: CS !< Lateral boundary mixing control structure
type(lateral_boundary_diffusion_CS), pointer :: CS !< Lateral boundary mixing control structure

character(len=80) :: string ! Temporary strings
logical :: boundary_extrap

if (ASSOCIATED(CS)) then
call MOM_error(FATAL, "lateral_boundary_mixing_init called with associated control structure.")
call MOM_error(FATAL, "lateral_boundary_diffusion_init called with associated control structure.")
return
endif

! Log this module and master switch for turning it on/off
call log_version(param_file, mdl, version, &
"This module implements lateral boundary mixing of tracers")
call get_param(param_file, mdl, "USE_LATERAL_BOUNDARY_MIXING", lateral_boundary_mixing_init, &
call get_param(param_file, mdl, "USE_LATERAL_BOUNDARY_DIFFUSION", lateral_boundary_diffusion_init, &
"If true, enables the lateral boundary mixing module.", &
default=.false.)

if (.not. lateral_boundary_mixing_init) then
if (.not. lateral_boundary_diffusion_init) then
return
endif

Expand All @@ -100,22 +100,22 @@ logical function lateral_boundary_mixing_init(Time, G, param_file, diag, diabati
"1. Bulk layer approach"//&
"2. Along layer approach"//&
"3. Decomposition on to pressure levels", default=1)
call get_param(param_file, mdl, "LBM_BOUNDARY_EXTRAP", boundary_extrap, &
"Use boundary extrapolation in LBM code", &
call get_param(param_file, mdl, "LBD_BOUNDARY_EXTRAP", boundary_extrap, &
"Use boundary extrapolation in LBD code", &
default=.false.)
call get_param(param_file, mdl, "LBM_REMAPPING_SCHEME", string, &
call get_param(param_file, mdl, "LBD_REMAPPING_SCHEME", string, &
"This sets the reconstruction scheme used "//&
"for vertical remapping for all variables. "//&
"It can be one of the following schemes: "//&
trim(remappingSchemesDoc), default=remappingDefaultScheme)
call initialize_remapping( CS%remap_CS, string, boundary_extrapolation = boundary_extrap )
call extract_member_remapping_CS(CS%remap_CS, degree=CS%deg)

end function lateral_boundary_mixing_init
end function lateral_boundary_diffusion_init

!> Driver routine for calculating lateral diffusive fluxes near the top and bottom boundaries. Two different methods
!! Method 1: Calculate fluxes from bulk layer integrated quantities
subroutine lateral_boundary_mixing(G, GV, US, h, Coef_x, Coef_y, dt, Reg, CS)
subroutine lateral_boundary_diffusion(G, GV, US, h, Coef_x, Coef_y, dt, Reg, CS)
type(ocean_grid_type), intent(inout) :: G !< Grid type
type(verticalGrid_type), intent(in) :: GV !< ocean vertical grid structure
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
Expand All @@ -126,7 +126,7 @@ subroutine lateral_boundary_mixing(G, GV, US, h, Coef_x, Coef_y, dt, Reg, CS)
real, intent(in) :: dt !< Tracer time step * I_numitts
!! (I_numitts in tracer_hordiff)
type(tracer_registry_type), pointer :: Reg !< Tracer registry
type(lateral_boundary_mixing_CS), intent(in) :: CS !< Control structure for this module
type(lateral_boundary_diffusion_CS), intent(in) :: CS !< Control structure for this module
! Local variables
real, dimension(SZI_(G),SZJ_(G)) :: hbl !< bnd. layer depth [m]
real, dimension(SZI_(G),SZJ_(G),SZK_(G),CS%deg+1) :: ppoly0_coefs !< Coefficients of polynomial
Expand Down Expand Up @@ -238,7 +238,7 @@ subroutine lateral_boundary_mixing(G, GV, US, h, Coef_x, Coef_y, dt, Reg, CS)
endif
enddo

end subroutine lateral_boundary_mixing
end subroutine lateral_boundary_diffusion

!< Calculate bulk layer value of a scalar quantity as the thickness weighted average
real function bulk_average(boundary, nk, deg, h, hBLT, phi, ppoly0_E, ppoly0_coefs, method, k_top, zeta_top, k_bot, &
Expand Down Expand Up @@ -970,4 +970,4 @@ logical function test_boundary_k_range(k_top, zeta_top, k_bot, zeta_bot, k_top_a


end function test_boundary_k_range
end module MOM_lateral_boundary_mixing
end module MOM_lateral_boundary_diffusion
2 changes: 1 addition & 1 deletion src/tracer/MOM_neutral_diffusion.F90
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ module MOM_neutral_diffusion
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
use MOM_lateral_boundary_mixing, only : boundary_k_range, SURFACE, BOTTOM
use MOM_lateral_boundary_diffusion, only : boundary_k_range, SURFACE, BOTTOM
implicit none ; private

#include <MOM_memory.h>
Expand Down
18 changes: 9 additions & 9 deletions src/tracer/MOM_tracer_hor_diff.F90
Original file line number Diff line number Diff line change
Expand Up @@ -23,8 +23,8 @@ module MOM_tracer_hor_diff
use MOM_neutral_diffusion, only : neutral_diffusion_init, neutral_diffusion_end
use MOM_neutral_diffusion, only : neutral_diffusion_CS
use MOM_neutral_diffusion, only : neutral_diffusion_calc_coeffs, neutral_diffusion
use MOM_lateral_boundary_mixing, only : lateral_boundary_mixing_CS, lateral_boundary_mixing_init
use MOM_lateral_boundary_mixing, only : lateral_boundary_mixing
use MOM_lateral_boundary_diffusion, only : lateral_boundary_diffusion_CS, lateral_boundary_diffusion_init
use MOM_lateral_boundary_diffusion, only : lateral_boundary_diffusion
use MOM_tracer_registry, only : tracer_registry_type, tracer_type, MOM_tracer_chksum
use MOM_unit_scaling, only : unit_scale_type
use MOM_variables, only : thermo_var_ptrs
Expand Down Expand Up @@ -60,12 +60,12 @@ module MOM_tracer_hor_diff
!! the CFL limit is not violated.
logical :: use_neutral_diffusion !< If true, use the neutral_diffusion module from within
!! tracer_hor_diff.
logical :: use_lateral_boundary_mixing !< If true, use the lateral_boundary_mixing module from within
logical :: use_lateral_boundary_diffusion !< If true, use the lateral_boundary_diffusion module from within
!! tracer_hor_diff.
logical :: recalc_neutral_surf !< If true, recalculate the neutral surfaces if CFL has been
!! exceeded
type(neutral_diffusion_CS), pointer :: neutral_diffusion_CSp => NULL() !< Control structure for neutral diffusion.
type(lateral_boundary_mixing_CS), pointer :: lateral_boundary_mixing_CSp => NULL() !< Control structure for lateral
type(lateral_boundary_diffusion_CS), pointer :: lateral_boundary_diffusion_CSp => NULL() !< Control structure for lateral
!! boundary mixing.
type(diag_ctrl), pointer :: diag => NULL() !< A structure that is used to
!! regulate the timing of diagnostic output.
Expand Down Expand Up @@ -390,7 +390,7 @@ subroutine tracer_hordiff(h, dt, MEKE, VarMix, G, GV, US, CS, Reg, tv, do_online
endif
enddo

if (CS%use_lateral_boundary_mixing) then
if (CS%use_lateral_boundary_diffusion) then

if (CS%show_call_tree) call callTree_waypoint("Calling lateral boundary mixing (tracer_hordiff)")

Expand All @@ -410,7 +410,7 @@ subroutine tracer_hordiff(h, dt, MEKE, VarMix, G, GV, US, CS, Reg, tv, do_online
if (itt>1) then ! Update halos for subsequent iterations
call do_group_pass(CS%pass_t, G%Domain, clock=id_clock_pass)
endif
call lateral_boundary_mixing(G, GV, US, h, Coef_x, Coef_y, I_numitts*dt, Reg, CS%lateral_boundary_mixing_CSp)
call lateral_boundary_diffusion(G, GV, US, h, Coef_x, Coef_y, I_numitts*dt, Reg, CS%lateral_boundary_diffusion_CSp)
enddo ! itt
endif

Expand Down Expand Up @@ -1500,10 +1500,10 @@ subroutine tracer_hor_diff_init(Time, G, US, param_file, diag, EOS, diabatic_CSp
CS%neutral_diffusion_CSp )
if (CS%use_neutral_diffusion .and. CS%Diffuse_ML_interior) call MOM_error(FATAL, "MOM_tracer_hor_diff: "// &
"USE_NEUTRAL_DIFFUSION and DIFFUSE_ML_TO_INTERIOR are mutually exclusive!")
CS%use_lateral_boundary_mixing = lateral_boundary_mixing_init(Time, G, param_file, diag, diabatic_CSp, &
CS%lateral_boundary_mixing_CSp)
CS%use_lateral_boundary_diffusion = lateral_boundary_diffusion_init(Time, G, param_file, diag, diabatic_CSp, &
CS%lateral_boundary_diffusion_CSp)
if (CS%use_neutral_diffusion .and. CS%Diffuse_ML_interior) call MOM_error(FATAL, "MOM_tracer_hor_diff: "// &
"USE_LATERAL_BOUNDARY_MIXING and DIFFUSE_ML_TO_INTERIOR are mutually exclusive!")
"USE_LATERAL_BOUNDARY_DIFFUSION and DIFFUSE_ML_TO_INTERIOR are mutually exclusive!")

call get_param(param_file, mdl, "DEBUG", CS%debug, default=.false.)

Expand Down

0 comments on commit 5583f84

Please sign in to comment.