MOM6
adjustment_initialization.F90
Go to the documentation of this file.
2 !***********************************************************************
3 !* GNU General Public License *
4 !* This file is a part of MOM. *
5 !* *
6 !* MOM is free software; you can redistribute it and/or modify it and *
7 !* are expected to follow the terms of the GNU General Public License *
8 !* as published by the Free Software Foundation; either version 2 of *
9 !* the License, or (at your option) any later version. *
10 !* *
11 !* MOM is distributed in the hope that it will be useful, but WITHOUT *
12 !* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY *
13 !* or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public *
14 !* License for more details. *
15 !* *
16 !* For the full text of the GNU General Public License, *
17 !* write to: Free Software Foundation, Inc., *
18 !* 675 Mass Ave, Cambridge, MA 02139, USA. *
19 !* or see: http://www.gnu.org/licenses/gpl.html *
20 !***********************************************************************
21 
24 use mom_get_input, only : directories
25 use mom_grid, only : ocean_grid_type
26 use mom_io, only : close_file, fieldtype, file_exists
27 use mom_io, only : open_file, read_data, read_axis_data, single_file
28 use mom_io, only : write_field, slasher
35 
36 implicit none ; private
37 
38 character(len=40) :: mdl = "adjustment_initialization" ! This module's name.
39 
40 #include <MOM_memory.h>
41 
42 ! -----------------------------------------------------------------------------
43 ! The following routines are visible to the outside world
44 ! -----------------------------------------------------------------------------
47 
48 ! -----------------------------------------------------------------------------
49 ! This module contains the following routines
50 ! -----------------------------------------------------------------------------
51 contains
52 
53 !------------------------------------------------------------------------------
54 !> Initialization of thicknesses.
55 !! This subroutine initializes the layer thicknesses to be uniform.
56 !------------------------------------------------------------------------------
57 subroutine adjustment_initialize_thickness ( h, G, GV, param_file, just_read_params)
58 
59  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
60  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
61  real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), &
62  intent(out) :: h !< The thickness that is being initialized, in m.
63  type(param_file_type), intent(in) :: param_file !< A structure indicating the open file
64  !! to parse for model parameter values.
65  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
66  !! only read parameters without changing h.
67 
68  real :: e0(szk_(g)+1) ! The resting interface heights, in m, usually !
69  ! negative because it is positive upward. !
70  real :: eta1D(szk_(g)+1)! Interface height relative to the sea surface !
71  ! positive upward, in m. !
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)
76  logical :: just_read ! If true, just read parameters but set nothing.
77  character(len=20) :: verticalCoordinate
78 ! This include declares and sets the variable "version".
79 #include "version_variable.h"
80  character(len=40) :: mdl = "adjustment_initialization" ! This module's name.
81  integer :: i, j, k, is, ie, js, je, nz
82 
83  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
84 
85  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
86 
87  if (.not.just_read) &
88  call mom_mesg("initialize_thickness_uniform: setting thickness")
89 
90  ! Parameters used by main model initialization
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)
95 
96  ! Parameters specific to this experiment configuration
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)
117 
118  if (just_read) return ! All run-time parameters have been read, so return.
119 
120  ! WARNING: this routine specifies the interface heights so that the last layer
121  ! is vanished, even at maximum depth. In order to have a uniform
122  ! layer distribution, use this line of code within the loop:
123  ! e0(k) = -G%max_depth * real(k-1) / real(nz)
124  ! To obtain a thickness distribution where the last layer is
125  ! vanished and the other thicknesses uniformly distributed, use:
126  ! e0(k) = -G%max_depth * real(k-1) / real(nz-1)
127 
128  dsdz = -delta_s_strat/g%max_depth
129 
130  select case ( coordinatemode(verticalcoordinate) )
131 
132  case ( regridding_layer, regridding_rho )
133  if (delta_s_strat.ne.0.) then
134  adjustment_delta = adjustment_deltas / delta_s_strat * g%max_depth
135  do k=1,nz+1
136  e0(k) = adjustment_delta-(g%max_depth+2*adjustment_delta) * (real(k-1) / real(nz))
137  enddo
138  else
139  adjustment_delta = 2.*g%max_depth
140  do k=1,nz+1
141  e0(k) = -(g%max_depth) * (real(k-1) / real(nz))
142  enddo
143  endif
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))
146  do k = 2,nz
147  target_values(k) = target_values(k-1) + ( gv%Rlay(nz) - gv%Rlay(1) ) / (nz-1)
148  end do
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)
157  else
158  y = 0.
159  endif
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)
162  x = x * acos( 0. )
163  delta_s = adjustment_deltas * 0.5 * (1. - sin( x ) )
164  do k=2,nz
165  if (dsdz.ne.0.) then
166  eta1d(k) = ( target_values(k) - ( s_ref + delta_s ) ) / dsdz
167  else
168  eta1d(k) = e0(k) - (0.5*adjustment_delta) * sin( x )
169  endif
170  eta1d(k) = max( eta1d(k), -g%max_depth )
171  eta1d(k) = min( eta1d(k), 0. )
172  enddo
173  eta1d(1)=0.; eta1d(nz+1)=-g%max_depth
174  do k=nz,1,-1
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
181  else
182  h(i,j,k) = eta1d(k) - eta1d(k+1)
183  endif
184  enddo
185  enddo ; enddo
186 
187  case ( regridding_zstar, regridding_sigma )
188  do k=1,nz+1
189  eta1d(k) = -(g%max_depth) * (real(k-1) / real(nz))
190  eta1d(k) = max(min(eta1d(k),0.),-g%max_depth)
191  enddo
192  do j=js,je ; do i=is,ie
193  do k=nz,1,-1
194  h(i,j,k) = eta1d(k) - eta1d(k+1)
195  enddo
196  enddo ; enddo
197 
198  case default
199  call mom_error(fatal,"adjustment_initialize_thickness: "// &
200  "Unrecognized i.c. setup - set ADJUSTMENT_IC")
201 
202  end select
203 
204 end subroutine adjustment_initialize_thickness
205 
206 
207 !------------------------------------------------------------------------------
208 !> Initialization of temperature and salinity.
209 !------------------------------------------------------------------------------
210 subroutine adjustment_initialize_temperature_salinity ( T, S, h, G, param_file, &
211  eqn_of_state, just_read_params)
212  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
213  real, dimension(SZI_(G),SZJ_(G), SZK_(G)), intent(out) :: T !< The temperature that is being initialized.
214  real, dimension(SZI_(G),SZJ_(G), SZK_(G)), intent(out) :: S !< The salinity that is being initialized.
215  real, dimension(SZI_(G),SZJ_(G), SZK_(G)), intent(in) :: h !< The model thickness.
216  type(param_file_type), intent(in) :: param_file !< A structure indicating the
217  !! open file to parse for model parameter values.
218  type(eos_type), pointer :: eqn_of_state !< Equation of state.
219  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
220  !! only read parameters without changing h.
221 
222  integer :: i, j, k, is, ie, js, je, nz
223  real :: x, y, yy
224  integer :: index_bay_z
225  real :: S_ref, T_ref ! Reference salinity and temerature within
226  ! surface layer
227  real :: S_range, T_range ! Range of salinities and temperatures over the
228  ! vertical
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)
233  logical :: just_read ! If true, just read parameters but set nothing.
234  character(len=20) :: verticalCoordinate
235 
236  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
237 
238  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
239 
240  ! Parameters used by main model initialization
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)
249  ! Parameters specific to this experiment configuration BUT logged in previous s/r
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., &
259  do_not_log=.true.)
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., &
263  do_not_log=.true.)
264 
265  if (just_read) return ! All run-time parameters have been read, so return.
266 
267  t(:,:,:) = 0.0
268  s(:,:,:) = 0.0
269 
270  ! Linear salinity profile
271  select case ( coordinatemode(verticalcoordinate) )
272 
273  case ( regridding_zstar, regridding_sigma )
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)
277  do k=nz,1,-1
278  eta1d(k)=eta1d(k+1)+h(i,j,k)
279  enddo
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)
286  else
287  y = 0.
288  endif
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)
291  x = x * acos( 0. )
292  delta_s = adjustment_deltas * 0.5 * (1. - sin( x ) )
293  do k=1,nz
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)
296  x = 1.-min(1., x)
297  t(i,j,k) = x
298  enddo
299  ! x=sum(T(i,j,:)*h(i,j,:))
300  ! T(i,j,:)=T(i,j,:)/x*(G%max_depth*1.5/real(nz))
301  enddo ; enddo
302 
303  case ( regridding_layer, regridding_rho )
304  do k = 1,nz
305  s(:,:,k) = s_ref + s_range * ( (real(k)-0.5) / real( nz ) )
306  ! x = abs(S(1,1,k) - 0.5*real(nz-1)/real(nz)*S_range)/S_range*real(2*nz)
307  ! x = 1.-min(1., x)
308  ! T(:,:,k) = x
309  end do
310 
311  case default
312  call mom_error(fatal,"adjustment_initialize_temperature_salinity: "// &
313  "Unrecognized i.c. setup - set ADJUSTMENT_IC")
314 
315  end select
316 
318 
319 !> \namespace adjustment_initialization
320 !!
321 !! The module configures the model for the geostrophic adjustment
322 !! test case.
323 end module adjustment_initialization
integer, parameter regridding_layer
Layer mode.
subroutine, public read_axis_data(filename, axis_name, var)
Definition: MOM_io.F90:424
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.
Definition: MOM_grid.F90:19
Calculates density of sea water from T, S and P.
Definition: MOM_EOS.F90:45
Provides the ocean grid type.
Definition: MOM_grid.F90:2
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.
Definition: MOM_io.F90:2
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.
Definition: MOM_EOS.F90:214
logical function, public is_root_pe()
subroutine, public mom_mesg(message, verb, all_print)
Provides subroutines for quantities specific to the equation of state.
Definition: MOM_EOS.F90:2
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.
Definition: MOM_EOS.F90:55