MOM6
coord_rho Module Reference

Detailed Description

Regrid columns for the continuous isopycnal (rho) coordinate.

Data Types

type  rho_cs
 Control structure containing required parameters for the rho coordinate. More...
 

Functions/Subroutines

subroutine, public init_coord_rho (CS, nk, ref_pressure, target_density, interp_CS)
 Initialise a rho_CS with pointers to parameters. More...
 
subroutine, public end_coord_rho (CS)
 
subroutine, public set_rho_params (CS, min_thickness, integrate_downward_for_e, interp_CS)
 
subroutine, public build_rho_column (CS, remapCS, nz, depth, h, T, S, eqn_of_state, zInterface)
 
subroutine, public old_inflate_layers_1d (minThickness, N, h)
 

Variables

integer, parameter nb_regridding_iterations = 1
 Maximum number of regridding iterations. More...
 
real, parameter deviation_tolerance = 1e-10
 Deviation tolerance between succesive grids in regridding iterations. More...
 

Function/Subroutine Documentation

◆ build_rho_column()

subroutine, public coord_rho::build_rho_column ( type(rho_cs), intent(in)  CS,
type(remapping_cs), intent(in)  remapCS,
integer, intent(in)  nz,
real, intent(in)  depth,
real, dimension(nz), intent(in)  h,
real, dimension(nz), intent(in)  T,
real, dimension(nz), intent(in)  S,
type(eos_type), pointer  eqn_of_state,
real, dimension(nz+1), intent(inout)  zInterface 
)
Parameters
[in]csRegridding control structure
[in]remapcsRemapping parameters and options
[in]nzNumber of levels
[in]depthDepth of ocean bottom (positive in m)
[in]hLayer thicknesses, in m
[in]sT and S for column
eqn_of_stateEquation of state structure
[in,out]zinterfaceAbsolute positions of interfaces

Definition at line 86 of file coord_rho.F90.

References regrid_interp::build_and_interpolate_grid(), deviation_tolerance, nb_regridding_iterations, old_inflate_layers_1d(), and mom_remapping::remapping_core_h().

Referenced by mom_diag_remap::diag_remap_update().

86  !< Build a rho coordinate column
87  !!
88  !! The algorithn operates as follows within each column:
89  !!
90  !! 1. Given T & S within each layer, the layer densities are computed.
91  !! 2. Based on these layer densities, a global density profile is reconstructed
92  !! (this profile is monotonically increasing and may be discontinuous)
93  !! 3. The new grid interfaces are determined based on the target interface
94  !! densities.
95  !! 4. T & S are remapped onto the new grid.
96  !! 5. Return to step 1 until convergence or until the maximum number of
97  !! iterations is reached, whichever comes first.
98 
99  type(rho_cs), intent(in) :: cs !< Regridding control structure
100  type(remapping_cs), intent(in) :: remapcs !< Remapping parameters and options
101  integer, intent(in) :: nz !< Number of levels
102  real, intent(in) :: depth !< Depth of ocean bottom (positive in m)
103  real, dimension(nz), intent(in) :: h !< Layer thicknesses, in m
104  real, dimension(nz), intent(in) :: t, s !< T and S for column
105  type(eos_type), pointer :: eqn_of_state !< Equation of state structure
106  real, dimension(nz+1), intent(inout) :: zinterface !< Absolute positions of interfaces
107 
108  ! Local variables
109  integer :: k, m
110  integer :: map_index
111  integer :: k_found
112  integer :: count_nonzero_layers
113  real :: deviation ! When iterating to determine the final
114  ! grid, this is the deviation between two
115  ! successive grids.
116  real :: threshold
117  real :: max_thickness
118  real :: correction
119  real, dimension(nz) :: p, densities, t_tmp, s_tmp, tmp
120  integer, dimension(nz) :: mapping
121  real :: dh
122  real, dimension(nz) :: h0, h1, htmp
123  real, dimension(nz+1) :: x0, x1, xtmp
124 
125  threshold = cs%min_thickness
126  p(:) = cs%ref_pressure
127  t_tmp(:) = t(:)
128  s_tmp(:) = s(:)
129  h0(:) = h(:)
130 
131  ! Start iterations to build grid
132  m = 1
133  deviation = 1e10
134  do while ( ( m <= nb_regridding_iterations ) .and. &
135  ( deviation > deviation_tolerance ) )
136 
137  ! Count number of nonzero layers within current water column
138  count_nonzero_layers = 0
139  do k = 1,nz
140  if ( h0(k) > threshold ) then
141  count_nonzero_layers = count_nonzero_layers + 1
142  end if
143  end do
144 
145  ! If there is at most one nonzero layer, stop here (no regridding)
146  if ( count_nonzero_layers <= 1 ) then
147  h1(:) = h0(:)
148  exit ! stop iterations here
149  end if
150 
151  ! Build new grid containing only nonzero layers
152  map_index = 1
153  correction = 0.0
154  do k = 1,nz
155  if ( h0(k) > threshold ) then
156  mapping(map_index) = k
157  htmp(map_index) = h0(k)
158  map_index = map_index + 1
159  else
160  correction = correction + h0(k)
161  end if
162  end do
163 
164  max_thickness = htmp(1)
165  k_found = 1
166  do k = 1,count_nonzero_layers
167  if ( htmp(k) > max_thickness ) then
168  max_thickness = htmp(k)
169  k_found = k
170  end if
171  end do
172 
173  htmp(k_found) = htmp(k_found) + correction
174 
175  xtmp(1) = 0.0
176  do k = 1,count_nonzero_layers
177  xtmp(k+1) = xtmp(k) + htmp(k)
178  end do
179 
180  ! Compute densities within current water column
181  call calculate_density( t_tmp, s_tmp, p, densities,&
182  1, nz, eqn_of_state )
183 
184  do k = 1,count_nonzero_layers
185  densities(k) = densities(mapping(k))
186  end do
187 
188  ! One regridding iteration
189  ! Based on global density profile, interpolate to generate a new grid
190  call build_and_interpolate_grid(cs%interp_CS, densities, count_nonzero_layers, &
191  htmp, xtmp, cs%target_density, nz, h1, x1)
192 
193  call old_inflate_layers_1d( cs%min_thickness, nz, h1 )
194  x1(1) = 0.0 ; do k = 1,nz ; x1(k+1) = x1(k) + h1(k) ; end do
195 
196  ! Remap T and S from previous grid to new grid
197  do k = 1,nz
198  h1(k) = x1(k+1) - x1(k)
199  end do
200 
201  call remapping_core_h(remapcs, nz, h0, s, nz, h1, tmp)
202  s_tmp(:) = tmp(:)
203 
204  call remapping_core_h(remapcs, nz, h0, t, nz, h1, tmp)
205  t_tmp(:) = tmp(:)
206 
207  ! Compute the deviation between two successive grids
208  deviation = 0.0
209  x0(1) = 0.0
210  x1(1) = 0.0
211  do k = 2,nz
212  x0(k) = x0(k-1) + h0(k-1)
213  x1(k) = x1(k-1) + h1(k-1)
214  deviation = deviation + (x0(k)-x1(k))**2
215  end do
216  deviation = sqrt( deviation / (nz-1) )
217 
218  m = m + 1
219 
220  ! Copy final grid onto start grid for next iteration
221  h0(:) = h1(:)
222 
223  end do ! end regridding iterations
224 
225  if (cs%integrate_downward_for_e) then
226  zinterface(1) = 0.
227  do k = 1,nz
228  zinterface(k+1) = zinterface(k) - h1(k)
229  ! Adjust interface position to accomodate inflating layers
230  ! without disturbing the interface above
231  enddo
232  else
233  ! The rest of the model defines grids integrating up from the bottom
234  zinterface(nz+1) = -depth
235  do k = nz,1,-1
236  zinterface(k) = zinterface(k+1) + h1(k)
237  ! Adjust interface position to accomodate inflating layers
238  ! without disturbing the interface above
239  enddo
240  endif
241 
Here is the call graph for this function:
Here is the caller graph for this function:

◆ end_coord_rho()

subroutine, public coord_rho::end_coord_rho ( type(rho_cs), pointer  CS)

Definition at line 64 of file coord_rho.F90.

64  type(rho_cs), pointer :: cs
65 
66  ! nothing to do
67  if (.not. associated(cs)) return
68  deallocate(cs%target_density)
69  deallocate(cs)

◆ init_coord_rho()

subroutine, public coord_rho::init_coord_rho ( type(rho_cs), pointer  CS,
integer, intent(in)  nk,
real, intent(in)  ref_pressure,
real, dimension(:), intent(in)  target_density,
type(interp_cs_type), intent(in)  interp_CS 
)

Initialise a rho_CS with pointers to parameters.

Parameters
csUnassociated pointer to hold the control structure

Definition at line 47 of file coord_rho.F90.

References mom_error_handler::mom_error().

47  type(rho_cs), pointer :: cs !< Unassociated pointer to hold the control structure
48  integer, intent(in) :: nk
49  real, intent(in) :: ref_pressure
50  real, dimension(:), intent(in) :: target_density
51  type(interp_cs_type), intent(in) :: interp_cs
52 
53  if (associated(cs)) call mom_error(fatal, "init_coord_rho: CS already associated!")
54  allocate(cs)
55  allocate(cs%target_density(nk+1))
56 
57  cs%nk = nk
58  cs%ref_pressure = ref_pressure
59  cs%target_density(:) = target_density(:)
60  cs%interp_CS = interp_cs
Here is the call graph for this function:

◆ old_inflate_layers_1d()

subroutine, public coord_rho::old_inflate_layers_1d ( real, intent(in)  minThickness,
integer, intent(in)  N,
real, dimension(:), intent(inout)  h 
)

Definition at line 248 of file coord_rho.F90.

Referenced by build_rho_column().

248 
249  ! Argument
250  real, intent(in) :: minthickness
251  integer, intent(in) :: n
252  real, intent(inout) :: h(:)
253 
254  ! Local variable
255  integer :: k
256  integer :: k_found
257  integer :: count_nonzero_layers
258  real :: delta
259  real :: correction
260  real :: maxthickness
261 
262  ! Count number of nonzero layers
263  count_nonzero_layers = 0
264  do k = 1,n
265  if ( h(k) > minthickness ) then
266  count_nonzero_layers = count_nonzero_layers + 1
267  end if
268  end do
269 
270  ! If all layer thicknesses are greater than the threshold, exit routine
271  if ( count_nonzero_layers == n ) return
272 
273  ! If all thicknesses are zero, inflate them all and exit
274  if ( count_nonzero_layers == 0 ) then
275  do k = 1,n
276  h(k) = minthickness
277  end do
278  return
279  end if
280 
281  ! Inflate zero layers
282  correction = 0.0
283  do k = 1,n
284  if ( h(k) <= minthickness ) then
285  delta = minthickness - h(k)
286  correction = correction + delta
287  h(k) = h(k) + delta
288  end if
289  end do
290 
291  ! Modify thicknesses of nonzero layers to ensure volume conservation
292  maxthickness = h(1)
293  k_found = 1
294  do k = 1,n
295  if ( h(k) > maxthickness ) then
296  maxthickness = h(k)
297  k_found = k
298  end if
299  end do
300 
301  h(k_found) = h(k_found) - correction
302 
Here is the caller graph for this function:

◆ set_rho_params()

subroutine, public coord_rho::set_rho_params ( type(rho_cs), pointer  CS,
real, intent(in), optional  min_thickness,
logical, intent(in), optional  integrate_downward_for_e,
type(interp_cs_type), intent(in), optional  interp_CS 
)

Definition at line 73 of file coord_rho.F90.

References mom_error_handler::mom_error().

73  type(rho_cs), pointer :: cs
74  real, optional, intent(in) :: min_thickness
75  logical, optional, intent(in) :: integrate_downward_for_e
76  type(interp_cs_type), optional, intent(in) :: interp_cs
77 
78  if (.not. associated(cs)) call mom_error(fatal, "set_rho_params: CS not associated")
79 
80  if (present(min_thickness)) cs%min_thickness = min_thickness
81  if (present(integrate_downward_for_e)) cs%integrate_downward_for_e = integrate_downward_for_e
82  if (present(interp_cs)) cs%interp_CS = interp_cs
Here is the call graph for this function:

Variable Documentation

◆ deviation_tolerance

real, parameter coord_rho::deviation_tolerance = 1e-10
private

Deviation tolerance between succesive grids in regridding iterations.

Definition at line 38 of file coord_rho.F90.

Referenced by build_rho_column().

38 real, parameter :: deviation_tolerance = 1e-10

◆ nb_regridding_iterations

integer, parameter coord_rho::nb_regridding_iterations = 1

Maximum number of regridding iterations.

Definition at line 36 of file coord_rho.F90.

Referenced by build_rho_column().

36 integer, parameter :: nb_regridding_iterations = 1