MOM6
MESO_surface_forcing.F90
1 !> Sets forcing for the MESO configuration
3 
4 ! This file is part of MOM6. See LICENSE.md for the license.
5 
6 use mom_diag_mediator, only : post_data, query_averaging_enabled
7 use mom_diag_mediator, only : register_diag_field, diag_ctrl, safe_alloc_ptr
8 use mom_domains, only : pass_var, pass_vector, agrid
9 use mom_error_handler, only : mom_error, fatal, warning, is_root_pe
12 use mom_forcing_type, only : allocate_forcing_type, allocate_mech_forcing
13 use mom_grid, only : ocean_grid_type
14 use mom_io, only : file_exists, mom_read_data, slasher
15 use mom_time_manager, only : time_type, operator(+), operator(/)
16 use mom_tracer_flow_control, only : call_tracer_set_forcing
19 use mom_variables, only : surface
20 
21 implicit none ; private
22 
23 public meso_buoyancy_forcing, meso_surface_forcing_init
24 
25 !> This control structure is used to store parameters associated with the MESO forcing.
26 type, public :: meso_surface_forcing_cs ; private
27 
28  logical :: use_temperature !< If true, temperature and salinity are used as state variables.
29  logical :: restorebuoy !< If true, use restoring surface buoyancy forcing.
30  real :: rho0 !< The density used in the Boussinesq approximation [kg m-3].
31  real :: g_earth !< The gravitational acceleration [L2 Z-1 T-2 ~> m s-2].
32  real :: flux_const !< The restoring rate at the surface [m s-1].
33  real :: gust_const !< A constant unresolved background gustiness
34  !! that contributes to ustar [Pa].
35  real, dimension(:,:), pointer :: &
36  t_restore(:,:) => null(), & !< The temperature to restore the SST toward [degC].
37  s_restore(:,:) => null(), & !< The salinity to restore the sea surface salnity toward [ppt]
38  pme(:,:) => null(), & !< The prescribed precip minus evap [m s-1].
39  solar(:,:) => null() !< The shortwave forcing into the ocean [W m-2].
40  real, dimension(:,:), pointer :: heat(:,:) => null() !< The prescribed longwave, latent and sensible
41  !! heat flux into the ocean [W m-2].
42  character(len=200) :: inputdir !< The directory where NetCDF input files are.
43  character(len=200) :: salinityrestore_file !< The file with the target sea surface salinity
44  character(len=200) :: sstrestore_file !< The file with the target sea surface temperature
45  character(len=200) :: solar_file !< The file with the shortwave forcing
46  character(len=200) :: heating_file !< The file with the longwave, latent, and sensible heating
47  character(len=200) :: pme_file !< The file with precipitation minus evaporation
48  type(diag_ctrl), pointer :: diag !< A structure that is used to regulate the
49  !! timing of diagnostic output.
51 
52 logical :: first_call = .true. !< True until after the first call to the MESO forcing routines
53 
54 contains
55 
56 !> This subroutine sets up the MESO buoyancy forcing, which uses control-theory style
57 !! specification restorative buoyancy fluxes at large scales.
58 subroutine meso_buoyancy_forcing(sfc_state, fluxes, day, dt, G, US, CS)
59  type(surface), intent(inout) :: sfc_state !< A structure containing fields that
60  !! describe the surface state of the ocean.
61  type(forcing), intent(inout) :: fluxes !< A structure containing thermodynamic forcing fields
62  type(time_type), intent(in) :: day !< The time of the fluxes
63  real, intent(in) :: dt !< The amount of time over which
64  !! the fluxes apply [s]
65  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
66  type(unit_scale_type), intent(in) :: us !< A dimensional unit scaling type
67  type(meso_surface_forcing_cs), pointer :: cs !< A pointer to the control structure returned by
68  !! a previous call to MESO_surface_forcing_init
69 
70 ! When temperature is used, there are long list of fluxes that need to be
71 ! set - essentially the same as for a full coupled model, but most of these
72 ! can be simply set to zero. The net fresh water flux should probably be
73 ! set in fluxes%evap and fluxes%lprec, with any salinity restoring
74 ! appearing in fluxes%vprec, and the other water flux components
75 ! (fprec, lrunoff and frunoff) left as arrays full of zeros.
76 ! Evap is usually negative and precip is usually positive. All heat fluxes
77 ! are in W m-2 and positive for heat going into the ocean. All fresh water
78 ! fluxes are in kg m-2 s-1 and positive for water moving into the ocean.
79 
80  real :: temp_restore ! The temperature that is being restored toward [degC].
81  real :: salin_restore ! The salinity that is being restored toward [ppt]
82  real :: density_restore ! The potential density that is being restored
83  ! toward [kg m-3].
84  real :: rhoxcp ! The mean density times the heat capacity [J m-3 degC-1].
85  real :: buoy_rest_const ! A constant relating density anomalies to the
86  ! restoring buoyancy flux [L2 m3 T-3 kg-1 ~> m5 s-3 kg-1].
87 
88  integer :: i, j, is, ie, js, je
89  integer :: isd, ied, jsd, jed
90 
91  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
92  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
93 
94  ! When modifying the code, comment out this error message. It is here
95  ! so that the original (unmodified) version is not accidentally used.
96 
97  ! Allocate and zero out the forcing arrays, as necessary. This portion is
98  ! usually not changed.
99  if (cs%use_temperature) then
100  call safe_alloc_ptr(fluxes%evap, isd, ied, jsd, jed)
101  call safe_alloc_ptr(fluxes%lprec, isd, ied, jsd, jed)
102  call safe_alloc_ptr(fluxes%fprec, isd, ied, jsd, jed)
103  call safe_alloc_ptr(fluxes%lrunoff, isd, ied, jsd, jed)
104  call safe_alloc_ptr(fluxes%frunoff, isd, ied, jsd, jed)
105  call safe_alloc_ptr(fluxes%vprec, isd, ied, jsd, jed)
106 
107  call safe_alloc_ptr(fluxes%sw, isd, ied, jsd, jed)
108  call safe_alloc_ptr(fluxes%lw, isd, ied, jsd, jed)
109  call safe_alloc_ptr(fluxes%latent, isd, ied, jsd, jed)
110  call safe_alloc_ptr(fluxes%sens, isd, ied, jsd, jed)
111  call safe_alloc_ptr(fluxes%heat_content_lprec, isd, ied, jsd, jed)
112  else ! This is the buoyancy only mode.
113  call safe_alloc_ptr(fluxes%buoy, isd, ied, jsd, jed)
114  endif
115 
116 
117  ! MODIFY THE CODE IN THE FOLLOWING LOOPS TO SET THE BUOYANCY FORCING TERMS.
118  if (cs%restorebuoy .and. first_call) then !#CTRL# .or. associated(CS%ctrl_forcing_CSp)) then
119  call safe_alloc_ptr(cs%T_Restore, isd, ied, jsd, jed)
120  call safe_alloc_ptr(cs%S_Restore, isd, ied, jsd, jed)
121  call safe_alloc_ptr(cs%Heat, isd, ied, jsd, jed)
122  call safe_alloc_ptr(cs%PmE, isd, ied, jsd, jed)
123  call safe_alloc_ptr(cs%Solar, isd, ied, jsd, jed)
124 
125  call mom_read_data(trim(cs%inputdir)//trim(cs%SSTrestore_file), "SST", &
126  cs%T_Restore(:,:), g%Domain)
127  call mom_read_data(trim(cs%inputdir)//trim(cs%salinityrestore_file), "SAL", &
128  cs%S_Restore(:,:), g%Domain)
129  call mom_read_data(trim(cs%inputdir)//trim(cs%heating_file), "Heat", &
130  cs%Heat(:,:), g%Domain)
131  call mom_read_data(trim(cs%inputdir)//trim(cs%PmE_file), "PmE", &
132  cs%PmE(:,:), g%Domain)
133  call mom_read_data(trim(cs%inputdir)//trim(cs%Solar_file), "NET_SOL", &
134  cs%Solar(:,:), g%Domain)
135  first_call = .false.
136  endif
137 
138  if ( cs%use_temperature ) then
139  ! Set whichever fluxes are to be used here. Any fluxes that
140  ! are always zero do not need to be changed here.
141  do j=js,je ; do i=is,ie
142  ! Fluxes of fresh water through the surface are in units of [kg m-2 s-1]
143  ! and are positive downward - i.e. evaporation should be negative.
144  fluxes%evap(i,j) = -0.0 * g%mask2dT(i,j)
145  fluxes%lprec(i,j) = cs%PmE(i,j) * cs%Rho0 * g%mask2dT(i,j)
146 
147  ! vprec will be set later, if it is needed for salinity restoring.
148  fluxes%vprec(i,j) = 0.0
149 
150  ! Heat fluxes are in units of [W m-2] and are positive into the ocean.
151  fluxes%lw(i,j) = 0.0 * g%mask2dT(i,j)
152  fluxes%latent(i,j) = 0.0 * g%mask2dT(i,j)
153  fluxes%sens(i,j) = cs%Heat(i,j) * g%mask2dT(i,j)
154  fluxes%sw(i,j) = cs%Solar(i,j) * g%mask2dT(i,j)
155  enddo ; enddo
156  else ! This is the buoyancy only mode.
157  do j=js,je ; do i=is,ie
158  ! fluxes%buoy is the buoyancy flux into the ocean [L2 T-3 ~> m2 s-3]. A positive
159  ! buoyancy flux is of the same sign as heating the ocean.
160  fluxes%buoy(i,j) = 0.0 * g%mask2dT(i,j)
161  enddo ; enddo
162  endif
163 
164  if (cs%restorebuoy) then
165  if (cs%use_temperature) then
166  call safe_alloc_ptr(fluxes%heat_added, isd, ied, jsd, jed)
167  ! When modifying the code, comment out this error message. It is here
168  ! so that the original (unmodified) version is not accidentally used.
169 ! call MOM_error(FATAL, "MESO_buoyancy_surface_forcing: " // &
170 ! "Temperature and salinity restoring used without modification." )
171 
172  rhoxcp = cs%Rho0 * fluxes%C_p
173  do j=js,je ; do i=is,ie
174  ! Set Temp_restore and Salin_restore to the temperature (in degC) and
175  ! salinity (in ppt or PSU) that are being restored toward.
176  if (g%mask2dT(i,j) > 0) then
177  fluxes%heat_added(i,j) = g%mask2dT(i,j) * &
178  ((cs%T_Restore(i,j) - sfc_state%SST(i,j)) * rhoxcp * cs%Flux_const)
179  fluxes%vprec(i,j) = - (cs%Rho0*cs%Flux_const) * &
180  (cs%S_Restore(i,j) - sfc_state%SSS(i,j)) / &
181  (0.5*(sfc_state%SSS(i,j) + cs%S_Restore(i,j)))
182  else
183  fluxes%heat_added(i,j) = 0.0
184  fluxes%vprec(i,j) = 0.0
185  endif
186  enddo ; enddo
187  else
188  ! When modifying the code, comment out this error message. It is here
189  ! so that the original (unmodified) version is not accidentally used.
190  call mom_error(fatal, "MESO_buoyancy_surface_forcing: " // &
191  "Buoyancy restoring used without modification." )
192 
193  ! The -1 is because density has the opposite sign to buoyancy.
194  buoy_rest_const = -1.0 * (cs%G_Earth * us%m_to_Z*us%T_to_s*cs%Flux_const) / cs%Rho0
195  do j=js,je ; do i=is,ie
196  ! Set density_restore to an expression for the surface potential
197  ! density [kg m-3] that is being restored toward.
198  density_restore = 1030.0
199 
200  fluxes%buoy(i,j) = g%mask2dT(i,j) * buoy_rest_const * &
201  (density_restore - sfc_state%sfc_density(i,j))
202  enddo ; enddo
203  endif
204  endif ! end RESTOREBUOY
205 
206 end subroutine meso_buoyancy_forcing
207 
208 !> Initialize the MESO surface forcing module
209 subroutine meso_surface_forcing_init(Time, G, US, param_file, diag, CS)
210 
211  type(time_type), intent(in) :: time !< The current model time
212  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
213  type(unit_scale_type), intent(in) :: us !< A dimensional unit scaling type
214  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
215  type(diag_ctrl), target, intent(inout) :: diag !< structure used to regulate diagnostic output
216  type(meso_surface_forcing_cs), pointer :: cs !< A pointer that is set to point to the
217  !! control structure for this module
218 
219 ! This include declares and sets the variable "version".
220 #include "version_variable.h"
221  character(len=40) :: mdl = "MESO_surface_forcing" ! This module's name.
222 
223  if (associated(cs)) then
224  call mom_error(warning, "MESO_surface_forcing_init called with an associated "// &
225  "control structure.")
226  return
227  endif
228  allocate(cs)
229  cs%diag => diag
230 
231  ! Read all relevant parameters and write them to the model log.
232  call log_version(param_file, mdl, version, "")
233  call get_param(param_file, mdl, "ENABLE_THERMODYNAMICS", cs%use_temperature, &
234  "If true, Temperature and salinity are used as state "//&
235  "variables.", default=.true.)
236 
237  call get_param(param_file, mdl, "G_EARTH", cs%G_Earth, &
238  "The gravitational acceleration of the Earth.", &
239  units="m s-2", default = 9.80, scale=us%m_to_L**2*us%Z_to_m*us%T_to_s**2)
240  call get_param(param_file, mdl, "RHO_0", cs%Rho0, &
241  "The mean ocean density used with BOUSSINESQ true to "//&
242  "calculate accelerations and the mass for conservation "//&
243  "properties, or with BOUSSINSEQ false to convert some "//&
244  "parameters from vertical units of m to kg m-2.", &
245  units="kg m-3", default=1035.0)
246  call get_param(param_file, mdl, "GUST_CONST", cs%gust_const, &
247  "The background gustiness in the winds.", units="Pa", &
248  default=0.02)
249 
250  call get_param(param_file, mdl, "RESTOREBUOY", cs%restorebuoy, &
251  "If true, the buoyancy fluxes drive the model back "//&
252  "toward some specified surface state with a rate "//&
253  "given by FLUXCONST.", default= .false.)
254 
255  if (cs%restorebuoy) then
256  call get_param(param_file, mdl, "FLUXCONST", cs%Flux_const, &
257  "The constant that relates the restoring surface fluxes "//&
258  "to the relative surface anomalies (akin to a piston "//&
259  "velocity). Note the non-MKS units.", units="m day-1", &
260  fail_if_missing=.true.)
261  ! Convert CS%Flux_const from m day-1 to m s-1.
262  cs%Flux_const = cs%Flux_const / 86400.0
263 
264  call get_param(param_file, mdl, "SSTRESTORE_FILE", cs%SSTrestore_file, &
265  "The file with the SST toward which to restore in "//&
266  "variable TEMP.", fail_if_missing=.true.)
267  call get_param(param_file, mdl, "SALINITYRESTORE_FILE", cs%salinityrestore_file, &
268  "The file with the surface salinity toward which to "//&
269  "restore in variable SALT.", fail_if_missing=.true.)
270  call get_param(param_file, mdl, "SENSIBLEHEAT_FILE", cs%heating_file, &
271  "The file with the non-shortwave heat flux in "//&
272  "variable Heat.", fail_if_missing=.true.)
273  call get_param(param_file, mdl, "PRECIP_FILE", cs%PmE_file, &
274  "The file with the net precipiation minus evaporation "//&
275  "in variable PmE.", fail_if_missing=.true.)
276  call get_param(param_file, mdl, "SHORTWAVE_FILE", cs%Solar_file, &
277  "The file with the shortwave heat flux in "//&
278  "variable NET_SOL.", fail_if_missing=.true.)
279  call get_param(param_file, mdl, "INPUTDIR", cs%inputdir, default=".")
280  cs%inputdir = slasher(cs%inputdir)
281 
282  endif
283 
284 end subroutine meso_surface_forcing_init
285 
286 !> \namespace meso_surface_forcing
287 !!
288 !! Rewritten by Robert Hallberg, June 2009
289 !!
290 !! This file contains the subroutines that a user should modify to
291 !! to set the surface wind stresses and fluxes of buoyancy or
292 !! temperature and fresh water. They are called when the run-time
293 !! parameters WIND_CONFIG or BUOY_CONFIG are set to "USER". The
294 !! standard version has simple examples, along with run-time error
295 !! messages that will cause the model to abort if this code has not
296 !! been modified. This code is intended for use with relatively
297 !! simple specifications of the forcing. For more complicated forms,
298 !! it is probably a good idea to read the forcing from input files
299 !! using "file" for WIND_CONFIG and BUOY_CONFIG.
300 !!
301 !! MESO_buoyancy forcing is used to set the surface buoyancy
302 !! forcing, which may include a number of fresh water flux fields
303 !! (evap, liq_precip, froz_precip, liq_runoff, froz_runoff, and
304 !! vprec) and the surface heat fluxes (sw, lw, latent and sens)
305 !! if temperature and salinity are state variables, or it may simply
306 !! be the buoyancy flux if it is not. This routine also has coded a
307 !! restoring to surface values of temperature and salinity.
308 
309 end module meso_surface_forcing
mom_time_manager
Wraps the FMS time manager functions.
Definition: MOM_time_manager.F90:2
mom_forcing_type::mech_forcing
Structure that contains pointers to the mechanical forcing at the surface used to drive the liquid oc...
Definition: MOM_forcing_type.F90:185
mom_variables::surface
Pointers to various fields which may be used describe the surface state of MOM, and which will be ret...
Definition: MOM_variables.F90:38
mom_file_parser::log_version
An overloaded interface to log version information about modules.
Definition: MOM_file_parser.F90:109
mom_diag_mediator
The subroutines here provide convenient wrappers to the fms diag_manager interfaces with additional d...
Definition: MOM_diag_mediator.F90:3
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_io
This module contains I/O framework code.
Definition: MOM_io.F90:2
mom_unit_scaling::unit_scale_type
Describes various unit conversion factors.
Definition: MOM_unit_scaling.F90:14
mom_diag_mediator::post_data
Make a diagnostic available for averaging or output.
Definition: MOM_diag_mediator.F90:70
mom_domains::pass_vector
Do a halo update on a pair of arrays representing the two components of a vector.
Definition: MOM_domains.F90:54
meso_surface_forcing
Sets forcing for the MESO configuration.
Definition: MESO_surface_forcing.F90:2
mom_forcing_type
This module implements boundary forcing for MOM6.
Definition: MOM_forcing_type.F90:2
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_io::mom_read_data
Read a data field from a file.
Definition: MOM_io.F90:74
mom_file_parser
The MOM6 facility to parse input files for runtime parameters.
Definition: MOM_file_parser.F90:2
mom_tracer_flow_control
Orchestrates the registration and calling of tracer packages.
Definition: MOM_tracer_flow_control.F90:2
mom_grid
Provides the ocean grid type.
Definition: MOM_grid.F90:2
mom_unit_scaling
Provides a transparent unit rescaling type to facilitate dimensional consistency testing.
Definition: MOM_unit_scaling.F90:2
mom_tracer_flow_control::tracer_flow_control_cs
The control structure for orchestrating the calling of tracer packages.
Definition: MOM_tracer_flow_control.F90:75
mom_forcing_type::forcing
Structure that contains pointers to the boundary forcing used to drive the liquid ocean simulated by ...
Definition: MOM_forcing_type.F90:49
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
meso_surface_forcing::meso_surface_forcing_cs
This control structure is used to store parameters associated with the MESO forcing.
Definition: MESO_surface_forcing.F90:26
mom_grid::ocean_grid_type
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:25
mom_diag_mediator::diag_ctrl
The following data type a list of diagnostic fields an their variants, as well as variables that cont...
Definition: MOM_diag_mediator.F90:239