MOM6
|
Solve the layer continuity equation using the PPM method for layer fluxes.
This module contains the subroutines that advect layer thickness. The scheme here uses a Piecewise-Parabolic method with a positive definite limiter.
Data Types | |
type | continuity_ppm_cs |
Control structure for mom_continuity_ppm. More... | |
type | loop_bounds_type |
A container for loop bounds. More... | |
Functions/Subroutines | |
subroutine, public | continuity_ppm (u, v, hin, h, uh, vh, dt, G, GV, CS, uhbt, vhbt, OBC, visc_rem_u, visc_rem_v, u_cor, v_cor, uhbt_aux, vhbt_aux, u_cor_aux, v_cor_aux, BT_cont) |
Time steps the layer thicknesses, using a monotonically limit, directionally split PPM scheme, based on Lin (1994). More... | |
subroutine | zonal_mass_flux (u, h_in, uh, dt, G, GV, CS, LB, uhbt, OBC, visc_rem_u, u_cor, uhbt_aux, u_cor_aux, BT_cont) |
Calculates the mass or volume fluxes through the zonal faces, and other related quantities. More... | |
subroutine | zonal_flux_layer (u, h, h_L, h_R, uh, duhdu, visc_rem, dt, G, j, ish, ieh, do_I, vol_CFL) |
Evaluates the zonal mass or volume fluxes in a layer. More... | |
subroutine | zonal_face_thickness (u, h, h_L, h_R, h_u, dt, G, LB, vol_CFL, marginal, visc_rem_u) |
Sets the effective interface thickness at each zonal velocity point. More... | |
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, CS, visc_rem, j, ish, ieh, do_I_in, full_precision, uh_3d) |
Returns the barotropic velocity adjustment that gives the desired barotropic (layer-summed) transport. More... | |
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, CS, visc_rem, visc_rem_max, j, ish, ieh, do_I) |
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. More... | |
subroutine | meridional_mass_flux (v, h_in, vh, dt, G, GV, CS, LB, vhbt, OBC, visc_rem_v, v_cor, vhbt_aux, v_cor_aux, BT_cont) |
Calculates the mass or volume fluxes through the meridional faces, and other related quantities. More... | |
subroutine | merid_flux_layer (v, h, h_L, h_R, vh, dvhdv, visc_rem, dt, G, J, ish, ieh, do_I, vol_CFL) |
Evaluates the meridional mass or volume fluxes in a layer. More... | |
subroutine | merid_face_thickness (v, h, h_L, h_R, h_v, dt, G, LB, vol_CFL, marginal, visc_rem_v) |
Sets the effective interface thickness at each meridional velocity point. More... | |
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, CS, visc_rem, j, ish, ieh, do_I_in, full_precision, vh_3d) |
Returns the barotropic velocity adjustment that gives the desired barotropic (layer-summed) transport. More... | |
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, CS, visc_rem, visc_rem_max, j, ish, ieh, do_I) |
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. More... | |
subroutine | ppm_reconstruction_x (h_in, h_L, h_R, G, LB, h_min, monotonic, simple_2nd) |
Calculates left/right edge values for PPM reconstruction. More... | |
subroutine | ppm_reconstruction_y (h_in, h_L, h_R, G, LB, h_min, monotonic, simple_2nd) |
Calculates left/right edge values for PPM reconstruction. More... | |
subroutine | ppm_limit_pos (h_in, h_L, h_R, h_min, G, iis, iie, jis, jie) |
This subroutine limits the left/right edge values of the PPM reconstruction to give a reconstruction that is positive-definite. Here this is reinterpreted as giving a constant thickness if the mean thickness is less than h_min, with a minimum of h_min otherwise. More... | |
subroutine | ppm_limit_cw84 (h_in, h_L, h_R, G, iis, iie, jis, jie) |
This subroutine limits the left/right edge values of the PPM reconstruction according to the monotonic prescription of Colella and Woodward, 1984. More... | |
real function | ratio_max (a, b, maxrat) |
Return the maximum ratio of a/b or maxrat. More... | |
subroutine, public | continuity_ppm_init (Time, G, GV, param_file, diag, CS) |
Initializes continuity_ppm_cs. More... | |
integer function, public | continuity_ppm_stencil (CS) |
continuity_PPM_stencil returns the continuity solver stencil size More... | |
subroutine, public | continuity_ppm_end (CS) |
Destructor for continuity_ppm_cs. More... | |
Variables | |
integer | id_clock_update |
integer | id_clock_correct |
subroutine, public mom_continuity_ppm::continuity_ppm | ( | real, dimension( g %isdb: g %iedb, g %jsd: g %jed, g %ke), intent(in) | u, |
real, dimension( g %isd: g %ied, g %jsdb: g %jedb, g %ke), intent(in) | v, | ||
real, dimension( g %isd: g %ied, g %jsd: g %jed, g %ke), intent(inout) | hin, | ||
real, dimension( g %isd: g %ied, g %jsd: g %jed, g %ke), intent(inout) | h, | ||
real, dimension( g %isdb: g %iedb, g %jsd: g %jed, g %ke), intent(out) | uh, | ||
real, dimension( g %isd: g %ied, g %jsdb: g %jedb, g %ke), intent(out) | vh, | ||
real, intent(in) | dt, | ||
type(ocean_grid_type), intent(inout) | G, | ||
type(verticalgrid_type), intent(in) | GV, | ||
type(continuity_ppm_cs), pointer | CS, | ||
real, dimension( g %isdb: g %iedb, g %jsd: g %jed), intent(in), optional | uhbt, | ||
real, dimension( g %isd: g %ied, g %jsdb: g %jedb), intent(in), optional | vhbt, | ||
type(ocean_obc_type), optional, pointer | OBC, | ||
real, dimension( g %isdb: g %iedb, g %jsd: g %jed, g %ke), intent(in), optional | visc_rem_u, | ||
real, dimension(szi_(g),szjb_(g),szk_(g)), intent(in), optional | visc_rem_v, | ||
real, dimension( g %isdb: g %iedb, g %jsd: g %jed, g %ke), intent(out), optional | u_cor, | ||
real, dimension( g %isd: g %ied, g %jsdb: g %jedb, g %ke), intent(out), optional | v_cor, | ||
real, dimension( g %isdb: g %iedb, g %jsd: g %jed), intent(in), optional | uhbt_aux, | ||
real, dimension( g %isd: g %ied, g %jsdb: g %jedb), intent(in), optional | vhbt_aux, | ||
real, dimension( g %isdb: g %iedb, g %jsd: g %jed, g %ke), intent(out), optional | u_cor_aux, | ||
real, dimension( g %isd: g %ied, g %jsdb: g %jedb, g %ke), intent(out), optional | v_cor_aux, | ||
type(bt_cont_type), optional, pointer | BT_cont | ||
) |
Time steps the layer thicknesses, using a monotonically limit, directionally split PPM scheme, based on Lin (1994).
[in,out] | g | The ocean's grid structure. |
cs | Module's control structure. | |
[in] | u | Zonal velocity, in m s-1. |
[in] | v | Meridional velocity, in m s-1. |
[in,out] | hin | Initial layer thickness, in H. |
[in,out] | h | Final layer thickness, in H. |
[out] | uh | Zonal volume flux, u*h*dy, H m2 s-1. |
[out] | vh | Meridional volume flux, v*h*dx, H m2 s-1. |
[in] | dt | Time increment in s. |
[in] | gv | Vertical grid structure. |
[in] | uhbt | The summed volume flux through zonal faces, H m2 s-1. |
[in] | vhbt | The summed volume flux through meridional faces, H m2 s-1. |
obc | Open boundaries control structure. | |
[in] | visc_rem_u | The fraction of zonal 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. Non-dimensional between 0 (at the bottom) and 1 (far above the bottom). |
[in] | visc_rem_v | The fraction of meridional 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. Non-dimensional between 0 (at the bottom) and 1 (far above the bottom). |
[out] | u_cor | The zonal velocities that give uhbt as the depth-integrated transport, in m s-1. |
[out] | v_cor | The meridional velocities that give vhbt as the depth-integrated transport, in m s-1. |
[in] | uhbt_aux | A second set of summed volume fluxes through zonal faces, in H m2 s-1. |
[in] | vhbt_aux | A second set of summed volume fluxes through meridional faces, in H m2 s-1. |
[out] | u_cor_aux | The zonal velocities that give uhbt_aux as the depth-integrated transports, in m s-1. |
[out] | v_cor_aux | The meridional velocities that give vhbt_aux as the depth-integrated transports, in m s-1. |
bt_cont | A structure with elements that describe the effective open face areas as a function of barotropic flow. |
Definition at line 77 of file MOM_continuity_PPM.F90.
References id_clock_update, meridional_mass_flux(), mom_error_handler::mom_error(), mom_open_boundary::obc_direction_e, mom_open_boundary::obc_direction_n, mom_open_boundary::obc_direction_s, mom_open_boundary::obc_direction_w, and zonal_mass_flux().
subroutine, public mom_continuity_ppm::continuity_ppm_end | ( | type(continuity_ppm_cs), pointer | CS | ) |
Destructor for continuity_ppm_cs.
cs | Module's control structure. |
Definition at line 2209 of file MOM_continuity_PPM.F90.
Referenced by mom_continuity::continuity_end().
subroutine, public mom_continuity_ppm::continuity_ppm_init | ( | type(time_type), intent(in), target | Time, |
type(ocean_grid_type), intent(in) | G, | ||
type(verticalgrid_type), intent(in) | GV, | ||
type(param_file_type), intent(in) | param_file, | ||
type(diag_ctrl), intent(inout), target | diag, | ||
type(continuity_ppm_cs), pointer | CS | ||
) |
Initializes continuity_ppm_cs.
[in] | time | Time increment in s. |
[in] | g | The ocean's grid structure. |
[in] | gv | Vertical grid structure. |
[in] | param_file | A structure indicating the open file to parse for model parameter values. |
[in,out] | diag | A structure that is used to regulate diagnostic output. |
cs | Module's control structure. |
This include declares and sets the variable "version".
Definition at line 2105 of file MOM_continuity_PPM.F90.
References id_clock_correct, and id_clock_update.
integer function, public mom_continuity_ppm::continuity_ppm_stencil | ( | type(continuity_ppm_cs), pointer | CS | ) |
continuity_PPM_stencil returns the continuity solver stencil size
cs | Module's control structure. |
Definition at line 2200 of file MOM_continuity_PPM.F90.
|
private |
Sets the effective interface thickness at each meridional velocity point.
[in,out] | g | Ocean's grid structure. |
[in] | v | Meridional velocity, in m s-1. |
[in] | h | Layer thickness used to calculate fluxes, in H. |
[in] | h_l | Left thickness in the reconstruction, in H. |
[in] | h_r | Right thickness in the reconstruction, in H. |
[in,out] | h_v | Thickness at meridional faces, in H. |
[in] | dt | Time increment in s. |
[in] | lb | Loop bounds structure. |
[in] | vol_cfl | If true, rescale the ratio of face areas to the cell areas when estimating the CFL number. |
[in] | marginal | If true, report the marginal face thicknesses; otherwise report transport-averaged thicknesses. |
[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. Non-dimensional between 0 (at the bottom) and 1 (far above the bottom). |
Definition at line 1420 of file MOM_continuity_PPM.F90.
Referenced by meridional_mass_flux().
|
private |
Evaluates the meridional mass or volume fluxes in a layer.
[in,out] | g | Ocean's grid structure. |
[in] | v | Meridional velocity, in m s-1. |
[in] | visc_rem | 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. Non-dimensional between 0 (at the bottom) and 1 (far above the bottom). |
[in] | h | Layer thickness used to calculate fluxes, in H. |
[in] | h_l | Left thickness in the reconstruction, in H. |
[in] | h_r | Right thickness in the reconstruction, in H. |
[in,out] | vh | Meridional mass or volume transport, in H m2 s-1. |
[in,out] | dvhdv | Partial derivative of vh with v, in H m. |
[in] | dt | Time increment in s. |
[in] | j | Spatial index. |
[in] | ish | Start of index range. |
[in] | ieh | End of index range. |
[in] | do_i | Which i values to work on. |
[in] | vol_cfl | If true, rescale the ratio of face areas to the cell areas when estimating the CFL number. |
Definition at line 1360 of file MOM_continuity_PPM.F90.
Referenced by meridional_flux_adjust(), meridional_mass_flux(), and set_merid_bt_cont().
|
private |
Returns the barotropic velocity adjustment that gives the desired barotropic (layer-summed) transport.
[in,out] | g | Ocean's grid structure. |
[in] | v | Meridional velocity, in m s-1. |
[in] | h_in | Layer thickness used to calculate fluxes, in H. |
[in] | h_l | Left thickness in the reconstruction, in H. |
[in] | h_r | Right thickness in the reconstruction, in H. |
[in] | visc_rem | 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. Non-dimensional between 0 (at the bottom) and 1 (far above the bottom). |
[in] | vhbt | The summed volume flux through meridional faces, H m2 s-1. |
[in] | dv_max_cfl | Maximum acceptable value of dv, in m s-1. |
[in] | dv_min_cfl | Minimum acceptable value of dv, in m s-1. |
[in] | vh_tot_0 | The summed transport with 0 adjustment, in H m2 s-1. |
[in] | dvhdv_tot_0 | The partial derivative of dv_err with dv at 0 adjustment, in H m. |
[out] | dv | The barotropic velocity adjustment, in m s-1. |
[in] | dt | Time increment in s. |
cs | This module's control structure. | |
[in] | j | Spatial index. |
[in] | ish | Start of index range. |
[in] | ieh | End of index range. |
[in] | do_i_in | A logical flag indicating which I values to work on. |
[in] | full_precision | full_precision - A flag indicating how carefully to iterate. The default is .true. (more accurate). |
[in,out] | vh_3d | Volume flux through meridional faces = v*h*dx, H m2 s-1. |
Definition at line 1500 of file MOM_continuity_PPM.F90.
References merid_flux_layer().
Referenced by meridional_mass_flux(), and set_merid_bt_cont().
|
private |
Calculates the mass or volume fluxes through the meridional faces, and other related quantities.
[in,out] | g | Ocean's grid structure. |
[in] | gv | Ocean's vertical grid structure. |
[in] | v | Meridional velocity, in m s-1. |
[in,out] | h_in | Layer thickness used to calculate fluxes, in H. |
[out] | vh | Volume flux through meridional faces = v*h*dx, H m2 s-1. |
[in] | dt | Time increment in s. |
cs | This module's control structure. | |
[in] | lb | Loop bounds structure. |
obc | This open boundary condition type specifies whether, where, and what open boundary conditions are used. | |
[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. Nondimensional between 0 (at the bottom) and 1 (far above the bottom). |
[in] | vhbt | The summed volume flux through meridional faces, H m2 s-1. |
[in] | vhbt_aux | A second set of summed volume fluxes through meridional faces, in H m2 s-1. |
[out] | v_cor | The meridional velocitiess (v with a barotropic correction) that give vhbt as the depth-integrated transport, m s-1. |
[out] | v_cor_aux | The meridional velocities (v with a barotropic correction) that give vhbt_aux as the depth-integrated transports, in m s-1. |
bt_cont | A structure with elements that describe the effective |
Definition at line 1055 of file MOM_continuity_PPM.F90.
References id_clock_correct, id_clock_update, merid_face_thickness(), merid_flux_layer(), meridional_flux_adjust(), ppm_reconstruction_y(), ratio_max(), and set_merid_bt_cont().
Referenced by continuity_ppm().
|
private |
This subroutine limits the left/right edge values of the PPM reconstruction according to the monotonic prescription of Colella and Woodward, 1984.
[in] | g | Ocean's grid structure. |
[in] | h_in | Layer thickness, in H. |
[in,out] | h_l | Left thickness in the reconstruction, in H. |
[in,out] | h_r | Right thickness in the reconstruction, in H. |
[in] | iis | Start of i index range. |
[in] | iie | End of i index range. |
[in] | jis | Start of j index range. |
[in] | jie | End of j index range. |
Definition at line 2054 of file MOM_continuity_PPM.F90.
Referenced by ppm_reconstruction_x(), and ppm_reconstruction_y().
|
private |
This subroutine limits the left/right edge values of the PPM reconstruction to give a reconstruction that is positive-definite. Here this is reinterpreted as giving a constant thickness if the mean thickness is less than h_min, with a minimum of h_min otherwise.
[in] | g | Ocean's grid structure. |
[in] | h_in | Layer thickness, in H. |
[in,out] | h_l | Left thickness in the reconstruction, in H. |
[in,out] | h_r | Right thickness in the reconstruction, in H. |
[in] | h_min | The minimum thickness that can be obtained by a concave parabolic fit. |
[in] | iis | Start of i index range. |
[in] | iie | End of i index range. |
[in] | jis | Start of j index range. |
[in] | jie | End of j index range. |
Definition at line 2011 of file MOM_continuity_PPM.F90.
Referenced by ppm_reconstruction_x(), and ppm_reconstruction_y().
|
private |
Calculates left/right edge values for PPM reconstruction.
[in] | g | Ocean's grid structure. |
[in] | h_in | Layer thickness, in H. |
[out] | h_l | Left thickness in the reconstruction, in H. |
[out] | h_r | Right thickness in the reconstruction, in H. |
[in] | lb | Active loop bounds structure. |
[in] | h_min | The minimum thickness that can be obtained by a concave parabolic fit. |
[in] | monotonic | If true, use the Colella & Woodward monotonic limiter. Otherwise use a simple positive-definite limiter. |
[in] | simple_2nd | If true, use the arithmetic mean thicknesses as the default edge values for a simple 2nd order scheme. |
Definition at line 1828 of file MOM_continuity_PPM.F90.
References ppm_limit_cw84(), and ppm_limit_pos().
Referenced by zonal_mass_flux().
|
private |
Calculates left/right edge values for PPM reconstruction.
[in] | g | Ocean's grid structure. |
[in] | h_in | Layer thickness, in H. |
[out] | h_l | Left thickness in the reconstruction, in H. |
[out] | h_r | Right thickness in the reconstruction, in H. |
[in] | lb | Active loop bounds structure. |
[in] | h_min | The minimum thickness that can be obtained by a concave parabolic fit. |
[in] | monotonic | If true, use the Colella & Woodward monotonic limiter. Otherwise use a simple positive-definite limiter. |
[in] | simple_2nd | If true, use the arithmetic mean thicknesses as the default edge values for a simple 2nd order scheme. |
Definition at line 1919 of file MOM_continuity_PPM.F90.
References ppm_limit_cw84(), and ppm_limit_pos().
Referenced by meridional_mass_flux().
|
private |
Return the maximum ratio of a/b or maxrat.
[in] | a | Numerator |
[in] | b | Denominator |
[in] | maxrat | Maximum value of ratio. |
Definition at line 2091 of file MOM_continuity_PPM.F90.
Referenced by meridional_mass_flux(), and zonal_mass_flux().
|
private |
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.
[in,out] | g | Ocean's grid structure. |
[in] | v | Meridional velocity, in m s-1. |
[in] | h_in | Layer thickness used to calculate fluxes, in H. |
[in] | h_l | Left thickness in the reconstruction, in H. |
[in] | h_r | Right thickness in the reconstruction, in H. |
[in,out] | bt_cont | A structure with elements that describe the effective open face areas as a function of barotropic flow. |
[in] | vh_tot_0 | The summed transport with 0 adjustment, in H m2 s-1. |
[in] | dvhdv_tot_0 | The partial derivative of du_err with dv at 0 adjustment, in H m. |
[in] | dv_max_cfl | Maximum acceptable value of dv, in m s-1. |
[in] | dv_min_cfl | Minimum acceptable value of dv, in m s-1. |
[in] | dt | Time increment in s. |
cs | This module's control structure. | |
[in] | visc_rem | 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. Non-dimensional between 0 (at the bottom) and 1 (far above the bottom). |
[in] | visc_rem_max | Maximum allowable visc_rem. |
[in] | j | Spatial index. |
[in] | ish | Start of index range. |
[in] | ieh | End of index range. |
[in] | do_i | A logical flag indicating which I values to work on. |
Definition at line 1663 of file MOM_continuity_PPM.F90.
References merid_flux_layer(), and meridional_flux_adjust().
Referenced by meridional_mass_flux().
|
private |
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.
[in,out] | g | Ocean's grid structure. |
[in] | u | Zonal velocity, in m s-1. |
[in] | h_in | Layer thickness used to calculate fluxes, in H. |
[in] | h_l | Left thickness in the reconstruction, in H. |
[in] | h_r | Right thickness in the reconstruction, in H. |
[in,out] | bt_cont | A structure with elements that describe the effective open face areas as a function of barotropic flow. |
[in] | uh_tot_0 | The summed transport with 0 adjustment, in H m2 s-1. |
[in] | duhdu_tot_0 | The partial derivative of du_err with du at 0 adjustment, in H m. |
[in] | du_max_cfl | Maximum acceptable value of du, in m s-1. |
[in] | du_min_cfl | Minimum acceptable value of du, in m s-1. |
[in] | dt | Time increment in s. |
cs | This module's control structure. | |
[in] | visc_rem | 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. Non-dimensional between 0 (at the bottom) and 1 (far above the bottom). |
[in] | visc_rem_max | Maximum allowable visc_rem. |
[in] | j | Spatial index. |
[in] | ish | Start of index range. |
[in] | ieh | End of index range. |
[in] | do_i | A logical flag indicating which I values to work on. |
Definition at line 886 of file MOM_continuity_PPM.F90.
References zonal_flux_adjust(), and zonal_flux_layer().
Referenced by zonal_mass_flux().
|
private |
Sets the effective interface thickness at each zonal velocity point.
[in,out] | g | Ocean's grid structure. |
[in] | u | Zonal velocity, in m s-1. |
[in] | h | Layer thickness used to calculate fluxes, in H. |
[in] | h_l | Left thickness in the reconstruction, in H. |
[in] | h_r | Right thickness in the reconstruction, in H. |
[in,out] | h_u | Thickness at zonal faces, in H. |
[in] | dt | Time increment in s. |
[in] | lb | Loop bounds structure. |
[in] | vol_cfl | If true, rescale the ratio of face areas to the cell areas when estimating the CFL number. |
[in] | marginal | If true, report the marginal face thicknesses; otherwise report transport-averaged thicknesses. |
[in] | visc_rem_u | 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. Non-dimensional between 0 (at the bottom) and 1 (far above the bottom). |
Definition at line 644 of file MOM_continuity_PPM.F90.
Referenced by zonal_mass_flux().
|
private |
Returns the barotropic velocity adjustment that gives the desired barotropic (layer-summed) transport.
[in,out] | g | Ocean's grid structure. |
[in] | u | Zonal velocity, in m s-1. |
[in] | h_in | Layer thickness used to calculate fluxes, in H. |
[in] | h_l | Left thickness in the reconstruction, in H. |
[in] | h_r | Right thickness in the reconstruction, in H. |
[in] | visc_rem | 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. Non-dimensional between 0 (at the bottom) and 1 (far above the bottom). |
[in] | uhbt | The summed volume flux through zonal faces, H m2 s-1. |
[in] | du_max_cfl | Maximum acceptable value of du, in m s-1. |
[in] | du_min_cfl | Minimum acceptable value of du, in m s-1. |
[in] | uh_tot_0 | The summed transport with 0 adjustment, in H m2 s-1. |
[in] | duhdu_tot_0 | The partial derivative of du_err with du at 0 adjustment, in H m. |
[out] | du | The barotropic velocity adjustment, in m s-1. |
[in] | dt | Time increment in s. |
cs | This module's control structure. | |
[in] | j | Spatial index. |
[in] | ish | Start of index range. |
[in] | ieh | End of index range. |
[in] | do_i_in | A logical flag indicating which I values to work on. |
[in] | full_precision | A flag indicating how carefully to iterate. The default is .true. (more accurate). |
[in,out] | uh_3d | Volume flux through zonal faces = u*h*dy, H m2 s-1. |
Definition at line 723 of file MOM_continuity_PPM.F90.
References zonal_flux_layer().
Referenced by set_zonal_bt_cont(), and zonal_mass_flux().
|
private |
Evaluates the zonal mass or volume fluxes in a layer.
[in,out] | g | Ocean's grid structure. |
[in] | u | Zonal velocity, in m s-1. |
[in] | visc_rem | 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. Non-dimensional between 0 (at the bottom) and 1 (far above the bottom). |
[in] | h | Layer thickness, in H. |
[in] | h_l | Left thickness, in H. |
[in] | h_r | Right thickness, in H. |
[in,out] | uh | Zonal mass or volume transport, in H m2 s-1. |
[in,out] | duhdu | Partial derivative of uh with u, in H m. |
[in] | dt | Time increment in s. |
[in] | j | Spatial index. |
[in] | ish | Start of index range. |
[in] | ieh | End of index range. |
[in] | do_i | Which i values to work on. |
[in] | vol_cfl | If true, rescale the ratio of face areas to the cell areas when estimating the CFL number. |
Definition at line 588 of file MOM_continuity_PPM.F90.
Referenced by set_zonal_bt_cont(), zonal_flux_adjust(), and zonal_mass_flux().
|
private |
Calculates the mass or volume fluxes through the zonal faces, and other related quantities.
[in,out] | g | Ocean's grid structure. |
[in] | gv | Ocean's vertical grid structure. |
[in] | u | Zonal velocity, in m s-1. |
[in,out] | h_in | Layer thickness used to calculate fluxes, in H. |
[out] | uh | Volume flux through zonal faces = u*h*dy, H m2 s-1. |
[in] | dt | Time increment in s. |
cs | This module's control structure. | |
[in] | lb | Loop bounds structure. |
obc | Open boundaries control structure. | |
[in] | visc_rem_u | The fraction of zonal 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. Non-dimensional between 0 (at the bottom) and 1 (far above the bottom). |
[in] | uhbt | The summed volume flux through zonal faces, H m2 s-1. |
[in] | uhbt_aux | A second set of summed volume fluxes through zonal faces, in H m2 s-1. |
[out] | u_cor | The zonal velocitiess (u with a barotropic correction) that give uhbt as the depth-integrated transport, m s-1. |
[out] | u_cor_aux | The zonal velocities (u with a barotropic correction) that give uhbt_aux as the depth-integrated transports, in m s-1. |
bt_cont | A structure with elements that describe the effective open face areas as a function of barotropic flow. |
Definition at line 286 of file MOM_continuity_PPM.F90.
References id_clock_correct, id_clock_update, mom_open_boundary::obc_direction_e, mom_open_boundary::obc_direction_w, ppm_reconstruction_x(), ratio_max(), set_zonal_bt_cont(), zonal_face_thickness(), zonal_flux_adjust(), and zonal_flux_layer().
Referenced by continuity_ppm().
|
private |
Definition at line 22 of file MOM_continuity_PPM.F90.
Referenced by continuity_ppm_init(), meridional_mass_flux(), and zonal_mass_flux().
|
private |
Definition at line 22 of file MOM_continuity_PPM.F90.
Referenced by continuity_ppm(), continuity_ppm_init(), meridional_mass_flux(), and zonal_mass_flux().