28 use mom_io, only : write_field, slasher
36 implicit none ;
private 38 character(len=40) ::
mdl =
"adjustment_initialization" 40 #include <MOM_memory.h> 61 real,
dimension(SZI_(G),SZJ_(G),SZK_(GV)), &
65 logical,
optional,
intent(in) :: just_read_params
70 real :: eta1D(szk_(g)+1)
72 real :: x, y, yy, delta_S_strat, dSdz, delta_S, S_ref
73 real :: min_thickness, adjustment_width, adjustment_delta, adjustment_deltaS
74 real :: front_wave_amp, front_wave_length, front_wave_asym
75 real :: target_values(szk_(g)+1)
77 character(len=20) :: verticalCoordinate
79 #include "version_variable.h" 80 character(len=40) :: mdl =
"adjustment_initialization" 81 integer :: i, j, k, is, ie, js, je, nz
83 is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
85 just_read = .false. ;
if (
present(just_read_params)) just_read = just_read_params
88 call mom_mesg(
"initialize_thickness_uniform: setting thickness")
91 if (.not.just_read)
call log_version(param_file, mdl, version,
"")
92 call get_param(param_file, mdl,
"S_REF",s_ref,fail_if_missing=.true.,do_not_log=.true.)
93 call get_param(param_file, mdl,
"MIN_THICKNESS",min_thickness,
'Minimum layer thickness', &
94 units=
'm',default=1.0e-3, do_not_log=just_read)
97 call get_param(param_file, mdl,
"REGRIDDING_COORDINATE_MODE",verticalcoordinate, &
98 default=default_coordinate_mode, do_not_log=just_read)
99 call get_param(param_file, mdl,
"ADJUSTMENT_WIDTH",adjustment_width, &
100 "Width of frontal zone", &
101 units=
"same as x,y", fail_if_missing=.not.just_read, do_not_log=just_read)
102 call get_param(param_file, mdl,
"DELTA_S_STRAT",delta_s_strat, &
103 "Top-to-bottom salinity difference of stratification", &
104 units=
"1e-3", fail_if_missing=.not.just_read, do_not_log=just_read)
105 call get_param(param_file, mdl,
"ADJUSTMENT_DELTAS",adjustment_deltas, &
106 "Salinity difference across front", &
107 units=
"1e-3", fail_if_missing=.not.just_read, do_not_log=just_read)
108 call get_param(param_file, mdl,
"FRONT_WAVE_AMP",front_wave_amp, &
109 "Amplitude of trans-frontal wave perturbation", &
110 units=
"same as x,y",default=0., do_not_log=just_read)
111 call get_param(param_file, mdl,
"FRONT_WAVE_LENGTH",front_wave_length, &
112 "Wave-length of trans-frontal wave perturbation", &
113 units=
"same as x,y",default=0., do_not_log=just_read)
114 call get_param(param_file, mdl,
"FRONT_WAVE_ASYM",front_wave_asym, &
115 "Amplitude of frontal asymmetric perturbation", &
116 default=0., do_not_log=just_read)
118 if (just_read)
return 128 dsdz = -delta_s_strat/g%max_depth
130 select case ( coordinatemode(verticalcoordinate) )
133 if (delta_s_strat.ne.0.)
then 134 adjustment_delta = adjustment_deltas / delta_s_strat * g%max_depth
136 e0(k) = adjustment_delta-(g%max_depth+2*adjustment_delta) * (
real(k-1) /
real(nz))
139 adjustment_delta = 2.*g%max_depth
141 e0(k) = -(g%max_depth) * (
real(k-1) /
real(nz))
144 target_values(1) = gv%Rlay(1)+0.5*(gv%Rlay(1)-gv%Rlay(2))
145 target_values(nz+1) = gv%Rlay(nz)+0.5*(gv%Rlay(nz)-gv%Rlay(nz-1))
147 target_values(k) = target_values(k-1) + ( gv%Rlay(nz) - gv%Rlay(1) ) / (nz-1)
149 target_values = target_values - 1000.
150 do j=js,je ;
do i=is,ie
151 if (front_wave_length.ne.0.)
then 152 y = ( 0.125 + g%geoLatT(i,j) / front_wave_length ) * ( 4. * acos(0.) )
153 yy = 2. * ( g%geoLatT(i,j) - 0.5 * g%len_lat ) / adjustment_width
154 yy = min(1.0, yy); yy = max(-1.0, yy)
155 yy = yy * 2. * acos( 0. )
156 y = front_wave_amp*sin(y) + front_wave_asym*sin(yy)
160 x = ( ( g%geoLonT(i,j) - 0.5 * g%len_lon ) + y ) / adjustment_width
161 x = min(1.0, x); x = max(-1.0, x)
163 delta_s = adjustment_deltas * 0.5 * (1. - sin( x ) )
166 eta1d(k) = ( target_values(k) - ( s_ref + delta_s ) ) / dsdz
168 eta1d(k) = e0(k) - (0.5*adjustment_delta) * sin( x )
170 eta1d(k) = max( eta1d(k), -g%max_depth )
171 eta1d(k) = min( eta1d(k), 0. )
173 eta1d(1)=0.; eta1d(nz+1)=-g%max_depth
175 if (eta1d(k) > 0.)
then 176 eta1d(k) = max( eta1d(k+1) + min_thickness, 0. )
177 h(i,j,k) = max( eta1d(k) - eta1d(k+1), min_thickness )
178 elseif (eta1d(k) <= (eta1d(k+1) + min_thickness))
then 179 eta1d(k) = eta1d(k+1) + min_thickness
180 h(i,j,k) = min_thickness
182 h(i,j,k) = eta1d(k) - eta1d(k+1)
189 eta1d(k) = -(g%max_depth) * (
real(k-1) /
real(nz))
190 eta1d(k) = max(min(eta1d(k),0.),-g%max_depth)
192 do j=js,je ;
do i=is,ie
194 h(i,j,k) = eta1d(k) - eta1d(k+1)
199 call mom_error(fatal,
"adjustment_initialize_thickness: "// &
200 "Unrecognized i.c. setup - set ADJUSTMENT_IC")
211 eqn_of_state, just_read_params)
213 real,
dimension(SZI_(G),SZJ_(G), SZK_(G)),
intent(out) :: T
214 real,
dimension(SZI_(G),SZJ_(G), SZK_(G)),
intent(out) :: S
215 real,
dimension(SZI_(G),SZJ_(G), SZK_(G)),
intent(in) :: h
218 type(
eos_type),
pointer :: eqn_of_state
219 logical,
optional,
intent(in) :: just_read_params
222 integer :: i, j, k, is, ie, js, je, nz
224 integer :: index_bay_z
227 real :: S_range, T_range
229 real :: xi0, xi1, dSdz, delta_S, delta_S_strat
230 real :: adjustment_width, adjustment_deltaS
231 real :: front_wave_amp, front_wave_length, front_wave_asym
232 real :: eta1d(szk_(g)+1)
234 character(len=20) :: verticalCoordinate
236 is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
238 just_read = .false. ;
if (
present(just_read_params)) just_read = just_read_params
241 call get_param(param_file,
mdl,
"S_REF",s_ref,
'Reference salinity', units=
'1e-3', &
242 fail_if_missing=.not.just_read, do_not_log=just_read)
243 call get_param(param_file,
mdl,
"T_REF",t_ref,
'Reference temperature', units=
'C', &
244 fail_if_missing=.not.just_read, do_not_log=just_read)
245 call get_param(param_file,
mdl,
"S_RANGE",s_range,
'Initial salinity range', units=
'1e-3', &
246 default=2.0, do_not_log=just_read)
247 call get_param(param_file,
mdl,
"T_RANGE",t_range,
'Initial temperature range', units=
'C', &
248 default=0.0, do_not_log=just_read)
250 call get_param(param_file,
mdl,
"REGRIDDING_COORDINATE_MODE",verticalcoordinate, &
251 default=default_coordinate_mode, do_not_log=just_read)
252 call get_param(param_file,
mdl,
"ADJUSTMENT_WIDTH", adjustment_width, &
253 fail_if_missing=.not.just_read, do_not_log=.true.)
254 call get_param(param_file,
mdl,
"ADJUSTMENT_DELTAS", adjustment_deltas, &
255 fail_if_missing=.not.just_read, do_not_log=.true.)
256 call get_param(param_file,
mdl,
"DELTA_S_STRAT", delta_s_strat, &
257 fail_if_missing=.not.just_read, do_not_log=.true.)
258 call get_param(param_file,
mdl,
"FRONT_WAVE_AMP", front_wave_amp, default=0., &
260 call get_param(param_file,
mdl,
"FRONT_WAVE_LENGTH",front_wave_length, &
261 default=0.,do_not_log=.true.)
262 call get_param(param_file,
mdl,
"FRONT_WAVE_ASYM", front_wave_asym, default=0., &
265 if (just_read)
return 271 select case ( coordinatemode(verticalcoordinate) )
274 dsdz = -delta_s_strat/g%max_depth
275 do j=js,je ;
do i=is,ie
276 eta1d(nz+1)=-g%bathyT(i,j)
278 eta1d(k)=eta1d(k+1)+h(i,j,k)
280 if (front_wave_length.ne.0.)
then 281 y = ( 0.125 + g%geoLatT(i,j) / front_wave_length ) * ( 4. * acos(0.) )
282 yy = 2. * ( g%geoLatT(i,j) - 0.5 * g%len_lat ) / front_wave_length
283 yy = min(1.0, yy); yy = max(-1.0, yy)
284 yy = yy * 2. * acos( 0. )
285 y = front_wave_amp*sin(y) + front_wave_asym*sin(yy)
289 x = ( ( g%geoLonT(i,j) - 0.5 * g%len_lon ) + y ) / adjustment_width
290 x = min(1.0, x); x = max(-1.0, x)
292 delta_s = adjustment_deltas * 0.5 * (1. - sin( x ) )
294 s(i,j,k) = s_ref + delta_s + 0.5 * ( eta1d(k)+eta1d(k+1) ) * dsdz
295 x = abs(s(i,j,k) - 0.5*
real(nz-1)/
real(nz)*S_range)/s_range*
real(2*nz)
305 s(:,:,k) = s_ref + s_range * ( (
real(k)-0.5) /
real( nz ) )
312 call mom_error(fatal,
"adjustment_initialize_temperature_salinity: "// &
313 "Unrecognized i.c. setup - set ADJUSTMENT_IC")
integer, parameter regridding_layer
Layer mode.
subroutine, public read_axis_data(filename, axis_name, var)
integer function coordinatemode(string)
Parse a string parameter specifying the coordinate mode and return the appropriate enumerated integer...
integer, parameter regridding_sigma
Sigma coordinates.
Ocean grid type. See mom_grid for details.
Calculates density of sea water from T, S and P.
Provides the ocean grid type.
character(len= *), parameter default_coordinate_mode
Default coordinate mode.
The module configures the model for the geostrophic adjustment test case.
This module contains I/O framework code.
subroutine, public adjustment_initialize_temperature_salinity(T, S, h, G, param_file, eqn_of_state, just_read_params)
Initialization of temperature and salinity.
subroutine, public calculate_density_derivs(T, S, pressure, drho_dT, drho_dS, start, npts, EOS)
Calls the appropriate subroutine to calculate density derivatives for 1-D array inputs.
logical function, public is_root_pe()
subroutine, public mom_mesg(message, verb, all_print)
Provides subroutines for quantities specific to the equation of state.
integer, parameter regridding_zstar
z* coordinates
The thermo_var_ptrs structure contains pointers to an assortment of thermodynamic fields that may be ...
Contains constants for interpreting input parameters that control regridding.
subroutine, public adjustment_initialize_thickness(h, G, GV, param_file, just_read_params)
Initialization of thicknesses. This subroutine initializes the layer thicknesses to be uniform...
subroutine, public mom_error(level, message, all_print)
integer, parameter regridding_rho
Target interface densities.
A control structure for the equation of state.