MOM6
BFB_initialization.F90
1 !> Initialization of the boundary-forced-basing configuration
3 
4 ! This file is part of MOM6. See LICENSE.md for the license.
5 
6 use mom_error_handler, only : mom_mesg, mom_error, fatal, is_root_pe
8 use mom_get_input, only : directories
9 use mom_grid, only : ocean_grid_type
10 use mom_sponge, only : set_up_sponge_field, initialize_sponge, sponge_cs
16 implicit none ; private
17 
18 #include <MOM_memory.h>
19 
20 public bfb_set_coord
21 public bfb_initialize_sponges_southonly
22 
23 ! A note on unit descriptions in comments: MOM6 uses units that can be rescaled for dimensional
24 ! consistency testing. These are noted in comments with units like Z, H, L, and T, along with
25 ! their mks counterparts with notation like "a velocity [Z T-1 ~> m s-1]". If the units
26 ! vary with the Boussinesq approximation, the Boussinesq variant is given first.
27 
28 !> Unsafe model variable
29 !! \todo Remove this module variable
30 logical :: first_call = .true.
31 
32 contains
33 
34 !> This subroutine specifies the vertical coordinate in terms of temperature at the surface and at the bottom.
35 !! This case is set up in such a way that the temperature of the topmost layer is equal to the SST at the
36 !! southern edge of the domain. The temperatures are then converted to densities of the top and bottom layers
37 !! and linearly interpolated for the intermediate layers.
38 subroutine bfb_set_coord(Rlay, g_prime, GV, param_file, eqn_of_state)
39  real, dimension(NKMEM_), intent(out) :: rlay !< Layer potential density.
40  real, dimension(NKMEM_), intent(out) :: g_prime !< The reduced gravity at
41  !! each interface [L2 Z-1 T-2 ~> m s-2].
42  type(verticalgrid_type), intent(in) :: gv !< The ocean's vertical grid structure
43  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
44  type(eos_type), pointer :: eqn_of_state !< Integer that selects the
45  !! equation of state.
46  ! Local variables
47  real :: drho_dt, sst_s, t_bot, rho_top, rho_bot
48  integer :: k, nz
49  character(len=40) :: mdl = "BFB_set_coord" ! This subroutine's name.
50 
51  call get_param(param_file, mdl, "DRHO_DT", drho_dt, &
52  "Rate of change of density with temperature.", &
53  units="kg m-3 K-1", default=-0.2)
54  call get_param(param_file, mdl, "SST_S", sst_s, &
55  "SST at the suothern edge of the domain.", units="C", default=20.0)
56  call get_param(param_file, mdl, "T_BOT", t_bot, &
57  "Bottom Temp", units="C", default=5.0)
58  rho_top = gv%rho0 + drho_dt*sst_s
59  rho_bot = gv%rho0 + drho_dt*t_bot
60  nz = gv%ke
61 
62  do k = 1,nz
63  rlay(k) = (rho_bot - rho_top)/(nz-1)*real(k-1) + rho_top
64  if (k >1) then
65  g_prime(k) = (rlay(k) - rlay(k-1)) * gv%g_Earth/gv%rho0
66  else
67  g_prime(k) = gv%g_Earth
68  endif
69  !Rlay(:) = 0.0
70  !g_prime(:) = 0.0
71  enddo
72 
73  if (first_call) call write_bfb_log(param_file)
74 
75 end subroutine bfb_set_coord
76 
77 !> This subroutine sets up the sponges for the southern bouundary of the domain. Maximum damping occurs
78 !! within 2 degrees lat of the boundary. The damping linearly decreases northward over the next 2 degrees.
79 subroutine bfb_initialize_sponges_southonly(G, GV, US, use_temperature, tv, param_file, CSp, h)
80  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
81  type(verticalgrid_type), intent(in) :: gv !< The ocean's vertical grid structure.
82  type(unit_scale_type), intent(in) :: us !< A dimensional unit scaling type
83  logical, intent(in) :: use_temperature !< If true, temperature and salinity are used as
84  !! state variables.
85  type(thermo_var_ptrs), intent(in) :: tv !< A structure pointing to various thermodynamic variables
86  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
87  type(sponge_cs), pointer :: csp !< A pointer to the sponge control structure
88  real, dimension(NIMEM_, NJMEM_, NKMEM_), &
89  intent(in) :: h !< Layer thicknesses [H ~> m or kg m-2]
90 
91  ! Local variables
92  real :: eta(szi_(g),szj_(g),szk_(g)+1) ! A temporary array for eta, in depth units [Z ~> m].
93  real :: idamp(szi_(g),szj_(g)) ! The inverse damping rate [s-1].
94  real :: h0(szk_(g)) ! Resting layer thicknesses in depth units [Z ~> m].
95  real :: min_depth ! The minimum ocean depth in depth units [Z ~> m].
96  real :: damp, e_dense, damp_new, slat, wlon, lenlat, lenlon, nlat
97  character(len=40) :: mdl = "BFB_initialize_sponges_southonly" ! This subroutine's name.
98  integer :: i, j, k, is, ie, js, je, isd, ied, jsd, jed, nz
99 
100  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
101  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
102 
103  eta(:,:,:) = 0.0 ; idamp(:,:) = 0.0
104 
105 ! Here the inverse damping time [s-1], is set. Set Idamp to 0 !
106 ! wherever there is no sponge, and the subroutines that are called !
107 ! will automatically set up the sponges only where Idamp is positive!
108 ! and mask2dT is 1. !
109 
110 ! Set up sponges for DOME configuration
111  call get_param(param_file, mdl, "MINIMUM_DEPTH", min_depth, &
112  "The minimum depth of the ocean.", units="m", default=0.0, scale=us%m_to_Z)
113 
114  call get_param(param_file, mdl, "SOUTHLAT", slat, &
115  "The southern latitude of the domain.", units="degrees")
116  call get_param(param_file, mdl, "LENLAT", lenlat, &
117  "The latitudinal length of the domain.", units="degrees")
118  call get_param(param_file, mdl, "WESTLON", wlon, &
119  "The western longitude of the domain.", units="degrees", default=0.0)
120  call get_param(param_file, mdl, "LENLON", lenlon, &
121  "The longitudinal length of the domain.", units="degrees")
122  nlat = slat + lenlat
123  do k=1,nz ; h0(k) = -g%max_depth * real(k-1) / real(nz) ; enddo
124 
125  ! Use for meridional thickness profile initialization
126 ! do k=1,nz ; H0(k) = -G%max_depth * real(k-1) / real(nz-1) ; enddo
127 
128  do i=is,ie; do j=js,je
129  if (g%geoLatT(i,j) < slat+2.0) then ; damp = 1.0
130  elseif (g%geoLatT(i,j) < slat+4.0) then
131  damp_new = 1.0*(slat+4.0-g%geoLatT(i,j))/2.0
132  else ; damp = 0.0
133  endif
134 
135  ! These will be streched inside of apply_sponge, so they can be in
136  ! depth space for Boussinesq or non-Boussinesq models.
137 
138  ! This section is used for uniform thickness initialization
139  do k = 1,nz; eta(i,j,k) = h0(k); enddo
140 
141  ! The below section is used for meridional temperature profile thickness initiation
142  ! do k = 1,nz; eta(i,j,k) = H0(k); enddo
143  ! if (G%geoLatT(i,j) > 40.0) then
144  ! do k = 1,nz
145  ! eta(i,j,k) = -G%Angstrom_Z*(k-1)
146  ! enddo
147  ! elseif (G%geoLatT(i,j) > 20.0) then
148  ! do k = 1,nz
149  ! eta(i,j,k) = min(H0(k) + (G%geoLatT(i,j) - 20.0)*(G%max_depth - nz*G%Angstrom_Z)/20.0, &
150  ! -(k-1)*G%Angstrom_Z)
151  ! enddo
152  ! endif
153  eta(i,j,nz+1) = -g%max_depth
154 
155  if (g%bathyT(i,j) > min_depth) then
156  idamp(i,j) = damp/86400.0
157  else ; idamp(i,j) = 0.0 ; endif
158  enddo ; enddo
159 
160 ! This call sets up the damping rates and interface heights.
161 ! This sets the inverse damping timescale fields in the sponges. !
162  call initialize_sponge(idamp, eta, g, param_file, csp, gv)
163 
164 ! Now register all of the fields which are damped in the sponge. !
165 ! By default, momentum is advected vertically within the sponge, but !
166 ! momentum is typically not damped within the sponge. !
167 
168  if (first_call) call write_bfb_log(param_file)
169 
170 end subroutine bfb_initialize_sponges_southonly
171 
172 !> Write output about the parameter values being used.
173 subroutine write_bfb_log(param_file)
174  type(param_file_type), intent(in) :: param_file !< A structure indicating the
175  !! open file to parse for model
176  !! parameter values.
177 
178 ! This include declares and sets the variable "version".
179 #include "version_variable.h"
180  character(len=40) :: mdl = "BFB_initialization" ! This module's name.
181 
182  call log_version(param_file, mdl, version)
183  first_call = .false.
184 
185 end subroutine write_bfb_log
186 
187 end module bfb_initialization
mom_verticalgrid
Provides a transparent vertical ocean grid type and supporting routines.
Definition: MOM_verticalGrid.F90:2
mom_file_parser::log_version
An overloaded interface to log version information about modules.
Definition: MOM_file_parser.F90:109
mom_variables::thermo_var_ptrs
Pointers to an assortment of thermodynamic fields that may be available, including potential temperat...
Definition: MOM_variables.F90:82
mom_get_input::directories
Container for paths and parameter file names.
Definition: MOM_get_input.F90:20
mom_eos
Provides subroutines for quantities specific to the equation of state.
Definition: MOM_EOS.F90:2
mom_tracer_registry
This module contains the tracer_registry_type and the subroutines that handle registration of tracers...
Definition: MOM_tracer_registry.F90:5
mom_file_parser::param_file_type
A structure that can be parsed to read and document run-time parameters.
Definition: MOM_file_parser.F90:54
mom_file_parser::get_param
An overloaded interface to read and log the values of various types of parameters.
Definition: MOM_file_parser.F90:102
mom_get_input
Reads the only Fortran name list needed to boot-strap the model.
Definition: MOM_get_input.F90:6
mom_unit_scaling::unit_scale_type
Describes various unit conversion factors.
Definition: MOM_unit_scaling.F90:14
mom_eos::eos_type
A control structure for the equation of state.
Definition: MOM_EOS.F90:86
mom_verticalgrid::verticalgrid_type
Describes the vertical ocean grid, including unit conversion factors.
Definition: MOM_verticalGrid.F90:24
mom_variables
Provides transparent structures with groups of MOM6 variables and supporting routines.
Definition: MOM_variables.F90:2
mom_file_parser
The MOM6 facility to parse input files for runtime parameters.
Definition: MOM_file_parser.F90:2
mom_sponge
Implements sponge regions in isopycnal mode.
Definition: MOM_sponge.F90:2
bfb_initialization
Initialization of the boundary-forced-basing configuration.
Definition: BFB_initialization.F90:2
mom_eos::calculate_density_derivs
Calculate the derivatives of density with temperature and salinity from T, S, and P.
Definition: MOM_EOS.F90:70
mom_tracer_registry::tracer_registry_type
Type to carry basic tracer information.
Definition: MOM_tracer_registry.F90:122
mom_grid
Provides the ocean grid type.
Definition: MOM_grid.F90:2
mom_sponge::sponge_cs
This control structure holds memory and parameters for the MOM_sponge module.
Definition: MOM_sponge.F90:40
mom_unit_scaling
Provides a transparent unit rescaling type to facilitate dimensional consistency testing.
Definition: MOM_unit_scaling.F90:2
mom_error_handler
Routines for error handling and I/O management.
Definition: MOM_error_handler.F90:2
mom_grid::ocean_grid_type
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:25
mom_eos::calculate_density
Calculates density of sea water from T, S and P.
Definition: MOM_EOS.F90:60