MOM6
RGC_initialization.F90
1 module rgc_initialization
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 !* By Elizabeth Yankovsky, May 2018 *
21 !***********************************************************************
22 
25 use mom_sponge, only : sponge_cs, set_up_sponge_field, initialize_sponge
26 use mom_sponge, only : set_up_sponge_ml_density
28 use mom_error_handler, only : mom_mesg, mom_error, fatal, is_root_pe, warning
30 use mom_get_input, only : directories
31 use mom_grid, only : ocean_grid_type
32 use mom_io, only : file_exists, read_data
33 use mom_io, only : slasher
37 use mom_domains, only: pass_var
38 implicit none ; private
39 
40 #include <MOM_memory.h>
41 
42 character(len=40) :: mod = "RGC_initialization" ! This module's name.
43 public rgc_initialize_sponges
44 
45 contains
46 
47 !> Sets up the the inverse restoration time (Idamp), and
48 ! the values towards which the interface heights and an arbitrary
49 ! number of tracers should be restored within each sponge.
50 subroutine rgc_initialize_sponges(G, GV, tv, u, v, PF, use_ALE, CSp, ACSp)
51  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
52  type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
53  type(thermo_var_ptrs), intent(in) :: tv !< A structure containing pointers
54  !! to any available thermodynamic
55  !! fields, potential temperature and
56  !! salinity or mixed layer density.
57  !! Absent fields have NULL ptrs.
58  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), intent(in) :: u !< u velocity.
59  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), intent(in) :: v !< v velocity.
60  type(param_file_type), intent(in) :: PF !< A structure indicating the
61  !! open file to parse for model
62  !! parameter values.
63  logical, intent(in) :: use_ALE !< If true, indicates model is in ALE mode
64  type(sponge_CS), pointer :: CSp !< Layer-mode sponge structure
65  type(ALE_sponge_CS), pointer :: ACSp !< ALE-mode sponge structure
66 
67 ! Local variables
68  real :: T(SZI_(G),SZJ_(G),SZK_(G)) ! A temporary array for temp
69  real :: S(SZI_(G),SZJ_(G),SZK_(G)) ! A temporary array for salt
70  real :: U1(SZIB_(G), SZJ_(G), SZK_(G)) ! A temporary array for u
71  real :: V1(SZI_(G), SZJB_(G), SZK_(G)) ! A temporary array for v
72  real :: RHO(SZI_(G),SZJ_(G),SZK_(G)) ! A temporary array for RHO
73  real :: tmp(SZI_(G),SZJ_(G)) ! A temporary array for tracers.
74  real :: h(SZI_(G),SZJ_(G),SZK_(G)) ! A temporary array for thickness at h points
75  real :: Idamp(SZI_(G),SZJ_(G)) ! The inverse damping rate at h points, in s-1.
76  real :: TNUDG ! Nudging time scale, days
77  real :: pres(SZI_(G)) ! An array of the reference pressure, in Pa
78  real :: e0(SZK_(G)+1) ! The resting interface heights, in m, usually !
79  ! negative because it is positive upward. !
80  real :: eta(SZI_(G),SZJ_(G),SZK_(G)+1) ! A temporary array for eta.
81  ! positive upward, in m.
82  logical :: sponge_uv ! Nudge velocities (u and v) towards zero
83  real :: min_depth, dummy1, z, delta_h
84  real :: damp, rho_dummy, min_thickness, rho_tmp, xi0
85  real :: lenlat, lenlon, lensponge
86  character(len=40) :: filename, state_file
87  character(len=40) :: temp_var, salt_var, eta_var, inputdir, h_var
88 
89  character(len=40) :: mod = "RGC_initialize_sponges" ! This subroutine's name.
90  integer :: i, j, k, is, ie, js, je, isd, ied, jsd, jed, nz, iscB, iecB, jscB, jecB
91 
92  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
93  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
94  iscb = g%iscB ; iecb = g%iecB; jscb = g%jscB ; jecb = g%jecB
95 
96  call get_param(pf,mod,"MIN_THICKNESS",min_thickness,'Minimum layer thickness',units='m',default=1.e-3)
97 
98  call get_param(pf, mod, "RGC_TNUDG", tnudg, 'Nudging time scale for sponge layers (days)', default=0.0)
99 
100  call get_param(pf, mod, "LENLAT", lenlat, &
101  "The latitudinal or y-direction length of the domain", &
102  fail_if_missing=.true., do_not_log=.true.)
103 
104  call get_param(pf, mod, "LENLON", lenlon, &
105  "The longitudinal or x-direction length of the domain", &
106  fail_if_missing=.true., do_not_log=.true.)
107 
108  call get_param(pf, mod, "LENSPONGE", lensponge, &
109  "The length of the sponge layer (km).", &
110  default=10.0)
111 
112  call get_param(pf, mod, "SPONGE_UV", sponge_uv, &
113  "Nudge velocities (u and v) towards zero in the sponge layer.", &
114  default=.false., do_not_log=.true.)
115 
116  t(:,:,:) = 0.0 ; s(:,:,:) = 0.0 ; idamp(:,:) = 0.0; rho(:,:,:) = 0.0
117 
118  call get_param(pf, mod, "MINIMUM_DEPTH", min_depth, &
119  "The minimum depth of the ocean.", units="m", default=0.0)
120 
121  if (associated(csp)) call mom_error(fatal, &
122  "RGC_initialize_sponges called with an associated control structure.")
123  if (associated(acsp)) call mom_error(fatal, &
124  "RGC_initialize_sponges called with an associated ALE-sponge control structure.")
125 
126  ! Here the inverse damping time, in s-1, is set. Set Idamp to 0 !
127  ! wherever there is no sponge, and the subroutines that are called !
128  ! will automatically set up the sponges only where Idamp is positive!
129  ! and mask2dT is 1.
130 
131  do i=is,ie; do j=js,je
132  if (g%geoLonT(i,j) <= lensponge) then
133  dummy1 = -(g%geoLonT(i,j))/lensponge + 1.0
134  !damp = 1.0/TNUDG * max(0.0,dummy1)
135  damp = 0.0
136  !write(*,*)'1st, G%geoLonT(i,j), damp',G%geoLonT(i,j), damp
137 
138  elseif (g%geoLonT(i,j) >= (lenlon - lensponge) .AND. g%geoLonT(i,j) <= lenlon) then
139 
140  ! 1 / day
141  dummy1=(g%geoLonT(i,j)-(lenlon - lensponge))/(lensponge)
142  damp = (1.0/tnudg) * max(0.0,dummy1)
143 
144  else ; damp=0.0
145  endif
146 
147  ! convert to 1 / seconds
148  if (g%bathyT(i,j) > min_depth) then
149  idamp(i,j) = damp/86400.0
150  else ; idamp(i,j) = 0.0 ; endif
151  enddo ; enddo
152 
153 
154  ! 1) Read eta, salt and temp from IC file
155  call get_param(pf, mod, "INPUTDIR", inputdir, default=".")
156  inputdir = slasher(inputdir)
157  ! GM: get two different files, one with temp and one with salt values
158  ! this is work around to avoid having wrong values near the surface
159  ! because of the FIT_SALINITY option. To get salt values right in the
160  ! sponge, FIT_SALINITY=False. The oposite is true for temp. One can
161  ! combined the *correct* temp and salt values in one file instead.
162  call get_param(pf, mod, "RGC_SPONGE_FILE", state_file, &
163  "The name of the file with temps., salts. and interfaces to \n"// &
164  " damp toward.", fail_if_missing=.true.)
165  call get_param(pf, mod, "SPONGE_PTEMP_VAR", temp_var, &
166  "The name of the potential temperature variable in \n"//&
167  "SPONGE_STATE_FILE.", default="Temp")
168  call get_param(pf, mod, "SPONGE_SALT_VAR", salt_var, &
169  "The name of the salinity variable in \n"//&
170  "SPONGE_STATE_FILE.", default="Salt")
171  call get_param(pf, mod, "SPONGE_ETA_VAR", eta_var, &
172  "The name of the interface height variable in \n"//&
173  "SPONGE_STATE_FILE.", default="eta")
174  call get_param(pf, mod, "SPONGE_H_VAR", h_var, &
175  "The name of the layer thickness variable in \n"//&
176  "SPONGE_STATE_FILE.", default="h")
177 
178  !read temp and eta
179  filename = trim(inputdir)//trim(state_file)
180  if (.not.file_exists(filename, g%Domain)) &
181  call mom_error(fatal, " RGC_initialize_sponges: Unable to open "//trim(filename))
182  call read_data(filename,temp_var,t(:,:,:), domain=g%Domain%mpp_domain)
183  call read_data(filename,salt_var,s(:,:,:), domain=g%Domain%mpp_domain)
184 
185  if (use_ale) then
186 
187  call read_data(filename,h_var,h(:,:,:), domain=g%Domain%mpp_domain)
188  call pass_var(h, g%domain)
189 
190  !call initialize_ALE_sponge(Idamp, h, nz, G, PF, ACSp)
191  call initialize_ale_sponge(idamp, g, pf, acsp, h, nz)
192 
193  ! The remaining calls to set_up_sponge_field can be in any order. !
194  if ( associated(tv%T) ) then
195  call set_up_ale_sponge_field(t,g,tv%T,acsp)
196  endif
197  if ( associated(tv%S) ) then
198  call set_up_ale_sponge_field(s,g,tv%S,acsp)
199  endif
200 
201  if (sponge_uv) then
202  u1(:,:,:) = 0.0; v1(:,:,:) = 0.0
203  call set_up_ale_sponge_vel_field(u1,v1,g,u,v,acsp)
204  endif
205 
206 
207  else ! layer mode
208 
209  !read eta
210  call read_data(filename,eta_var,eta(:,:,:), domain=g%Domain%mpp_domain)
211 
212  ! Set the inverse damping rates so that the model will know where to
213  ! apply the sponges, along with the interface heights.
214  call initialize_sponge(idamp, eta, g, pf, csp, gv)
215 
216  if ( gv%nkml>0 ) then
217  ! This call to set_up_sponge_ML_density registers the target values of the
218  ! mixed layer density, which is used in determining which layers can be
219  ! inflated without causing static instabilities.
220  do i=is-1,ie ; pres(i) = tv%P_Ref ; enddo
221 
222  do j=js,je
223  call calculate_density(t(:,j,1), s(:,j,1), pres, tmp(:,j), &
224  is, ie-is+1, tv%eqn_of_state)
225  enddo
226 
227  call set_up_sponge_ml_density(tmp, g, csp)
228  endif
229 
230  ! Apply sponge in tracer fields
231  call set_up_sponge_field(t, tv%T, g, nz, csp)
232  call set_up_sponge_field(s, tv%S, g, nz, csp)
233 
234  endif
235 
236 end subroutine rgc_initialize_sponges
237 
238 end module rgc_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_ale_sponge::initialize_ale_sponge
Ddetermine the number of points which are within sponges in this computational domain.
Definition: MOM_ALE_sponge.F90:49
mom_dyn_horgrid
Contains a shareable dynamic type for describing horizontal grids and metric data and utilty routines...
Definition: MOM_dyn_horgrid.F90:3
mom_ale_sponge::ale_sponge_cs
ALE sponge control structure.
Definition: MOM_ALE_sponge.F90:85
mom_eos
Provides subroutines for quantities specific to the equation of state.
Definition: MOM_EOS.F90:2
mom_domains::pass_var
Do a halo update on an array.
Definition: MOM_domains.F90:49
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_ale_sponge
This module contains the routines used to apply sponge layers when using the ALE mode.
Definition: MOM_ALE_sponge.F90:11
mom_io
This module contains I/O framework code.
Definition: MOM_io.F90:2
mom_get_input
Reads the only Fortran name list needed to boot-strap the model.
Definition: MOM_get_input.F90:6
mom_eos::eos_type
A control structure for the equation of state.
Definition: MOM_EOS.F90:86
mom_ale_sponge::set_up_ale_sponge_field
Store the reference profile at h points for a variable.
Definition: MOM_ALE_sponge.F90:34
mom_verticalgrid::verticalgrid_type
Describes the vertical ocean grid, including unit conversion factors.
Definition: MOM_verticalGrid.F90:24
mom_domains
Describes the decomposed MOM domain and has routines for communications across PEs.
Definition: MOM_domains.F90:2
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
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_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_io::file_exists
Indicate whether a file exists, perhaps with domain decomposition.
Definition: MOM_io.F90:68
mom_error_handler
Routines for error handling and I/O management.
Definition: MOM_error_handler.F90:2
mom_dyn_horgrid::dyn_horgrid_type
Describes the horizontal ocean grid with only dynamic memory arrays.
Definition: MOM_dyn_horgrid.F90:22
mom_grid::ocean_grid_type
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:25
mom_ale_sponge::set_up_ale_sponge_vel_field
This subroutine stores the reference profile at u and v points for a vector.
Definition: MOM_ALE_sponge.F90:40
mom_eos::calculate_density
Calculates density of sea water from T, S and P.
Definition: MOM_EOS.F90:60