MOM6
user_surface_forcing.F90
1 !> Template for user to code up surface forcing.
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, read_data
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 user_wind_forcing, user_buoyancy_forcing, user_surface_forcing_init
24 
25 !> This control structure should be used to store any run-time variables
26 !! associated with the user-specified forcing.
27 !!
28 !! It can be readily modified for a specific case, and because it is private there
29 !! will be no changes needed in other code (although they will have to be recompiled).
30 type, public :: user_surface_forcing_cs ; private
31  ! The variables in the cannonical example are used for some common
32  ! cases, but do not need to be used.
33 
34  logical :: use_temperature !< If true, temperature and salinity are used as state variables.
35  logical :: restorebuoy !< If true, use restoring surface buoyancy forcing.
36  real :: rho0 !< The density used in the Boussinesq approximation [kg m-3].
37  real :: g_earth !< The gravitational acceleration [L2 Z-1 s-2 ~> m s-2].
38  real :: flux_const !< The restoring rate at the surface [m s-1].
39  real :: gust_const !< A constant unresolved background gustiness
40  !! that contributes to ustar [Pa].
41 
42  type(diag_ctrl), pointer :: diag !< A structure that is used to regulate the
43  !! timing of diagnostic output.
45 
46 contains
47 
48 !> This subroutine sets the surface wind stresses, forces%taux and forces%tauy, in [Pa].
49 !! These are the stresses in the direction of the model grid (i.e. the same
50 !! direction as the u- and v- velocities).
51 subroutine user_wind_forcing(sfc_state, forces, day, G, US, CS)
52  type(surface), intent(inout) :: sfc_state !< A structure containing fields that
53  !! describe the surface state of the ocean.
54  type(mech_forcing), intent(inout) :: forces !< A structure with the driving mechanical forces
55  type(time_type), intent(in) :: day !< The time of the fluxes
56  type(ocean_grid_type), intent(inout) :: g !< The ocean's grid structure
57  type(unit_scale_type), intent(in) :: us !< A dimensional unit scaling type
58  type(user_surface_forcing_cs), pointer :: cs !< A pointer to the control structure returned
59  !! by a previous call to user_surface_forcing_init
60 
61  ! Local variables
62  integer :: i, j, is, ie, js, je, isq, ieq, jsq, jeq
63 
64  ! When modifying the code, comment out this error message. It is here
65  ! so that the original (unmodified) version is not accidentally used.
66  call mom_error(fatal, "User_wind_surface_forcing: " // &
67  "User forcing routine called without modification." )
68 
69  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
70  isq = g%IscB ; ieq = g%IecB ; jsq = g%JscB ; jeq = g%JecB
71 
72  ! Allocate the forcing arrays, if necessary.
73  call allocate_mech_forcing(g, forces, stress=.true., ustar=.true.)
74 
75  ! Set the surface wind stresses, in units of Pa. A positive taux
76  ! accelerates the ocean to the (pseudo-)east.
77 
78  ! The i-loop extends to is-1 so that taux can be used later in the
79  ! calculation of ustar - otherwise the lower bound would be Isq.
80  do j=js,je ; do i=is-1,ieq
81  forces%taux(i,j) = g%mask2dCu(i,j) * 0.0 ! Change this to the desired expression.
82  enddo ; enddo
83  do j=js-1,jeq ; do i=is,ie
84  forces%tauy(i,j) = g%mask2dCv(i,j) * 0.0 ! Change this to the desired expression.
85  enddo ; enddo
86 
87  ! Set the surface friction velocity, in units of m s-1. ustar
88  ! is always positive.
89  if (associated(forces%ustar)) then ; do j=js,je ; do i=is,ie
90  ! This expression can be changed if desired, but need not be.
91  forces%ustar(i,j) = us%m_to_Z*us%T_to_s * g%mask2dT(i,j) * sqrt(cs%gust_const/cs%Rho0 + &
92  sqrt(0.5*(forces%taux(i-1,j)**2 + forces%taux(i,j)**2) + &
93  0.5*(forces%tauy(i,j-1)**2 + forces%tauy(i,j)**2))/cs%Rho0)
94  enddo ; enddo ; endif
95 
96 end subroutine user_wind_forcing
97 
98 !> This subroutine specifies the current surface fluxes of buoyancy or
99 !! temperature and fresh water. It may also be modified to add
100 !! surface fluxes of user provided tracers.
101 subroutine user_buoyancy_forcing(sfc_state, fluxes, day, dt, G, US, CS)
102  type(surface), intent(inout) :: sfc_state !< A structure containing fields that
103  !! describe the surface state of the ocean.
104  type(forcing), intent(inout) :: fluxes !< A structure containing thermodynamic forcing fields
105  type(time_type), intent(in) :: day !< The time of the fluxes
106  real, intent(in) :: dt !< The amount of time over which
107  !! the fluxes apply [s]
108  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
109  type(unit_scale_type), intent(in) :: us !< A dimensional unit scaling type
110  type(user_surface_forcing_cs), pointer :: cs !< A pointer to the control structure returned
111  !! by a previous call to user_surface_forcing_init
112 
113 ! This subroutine specifies the current surface fluxes of buoyancy or
114 ! temperature and fresh water. It may also be modified to add
115 ! surface fluxes of user provided tracers.
116 
117 ! When temperature is used, there are long list of fluxes that need to be
118 ! set - essentially the same as for a full coupled model, but most of these
119 ! can be simply set to zero. The net fresh water flux should probably be
120 ! set in fluxes%evap and fluxes%lprec, with any salinity restoring
121 ! appearing in fluxes%vprec, and the other water flux components
122 ! (fprec, lrunoff and frunoff) left as arrays full of zeros.
123 ! Evap is usually negative and precip is usually positive. All heat fluxes
124 ! are in W m-2 and positive for heat going into the ocean. All fresh water
125 ! fluxes are in kg m-2 s-1 and positive for water moving into the ocean.
126 
127  ! Local variables
128  real :: temp_restore ! The temperature that is being restored toward [degC].
129  real :: salin_restore ! The salinity that is being restored toward [ppt]
130  real :: density_restore ! The potential density that is being restored
131  ! toward [kg m-3].
132  real :: rhoxcp ! The mean density times the heat capacity [J m-3 degC-1].
133  real :: buoy_rest_const ! A constant relating density anomalies to the
134  ! restoring buoyancy flux [L2 m3 T-3 kg-1 ~> m5 s-3 kg-1].
135 
136  integer :: i, j, is, ie, js, je
137  integer :: isd, ied, jsd, jed
138 
139  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
140  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
141 
142  ! When modifying the code, comment out this error message. It is here
143  ! so that the original (unmodified) version is not accidentally used.
144  call mom_error(fatal, "User_buoyancy_surface_forcing: " // &
145  "User forcing routine called without modification." )
146 
147  ! Allocate and zero out the forcing arrays, as necessary. This portion is
148  ! usually not changed.
149  if (cs%use_temperature) then
150  call safe_alloc_ptr(fluxes%evap, isd, ied, jsd, jed)
151  call safe_alloc_ptr(fluxes%lprec, isd, ied, jsd, jed)
152  call safe_alloc_ptr(fluxes%fprec, isd, ied, jsd, jed)
153  call safe_alloc_ptr(fluxes%lrunoff, isd, ied, jsd, jed)
154  call safe_alloc_ptr(fluxes%frunoff, isd, ied, jsd, jed)
155  call safe_alloc_ptr(fluxes%vprec, isd, ied, jsd, jed)
156 
157  call safe_alloc_ptr(fluxes%sw, isd, ied, jsd, jed)
158  call safe_alloc_ptr(fluxes%lw, isd, ied, jsd, jed)
159  call safe_alloc_ptr(fluxes%latent, isd, ied, jsd, jed)
160  call safe_alloc_ptr(fluxes%sens, isd, ied, jsd, jed)
161  else ! This is the buoyancy only mode.
162  call safe_alloc_ptr(fluxes%buoy, isd, ied, jsd, jed)
163  endif
164 
165 
166  ! MODIFY THE CODE IN THE FOLLOWING LOOPS TO SET THE BUOYANCY FORCING TERMS.
167 
168  if ( cs%use_temperature ) then
169  ! Set whichever fluxes are to be used here. Any fluxes that
170  ! are always zero do not need to be changed here.
171  do j=js,je ; do i=is,ie
172  ! Fluxes of fresh water through the surface are in units of [kg m-2 s-1]
173  ! and are positive downward - i.e. evaporation should be negative.
174  fluxes%evap(i,j) = -0.0 * g%mask2dT(i,j)
175  fluxes%lprec(i,j) = 0.0 * g%mask2dT(i,j)
176 
177  ! vprec will be set later, if it is needed for salinity restoring.
178  fluxes%vprec(i,j) = 0.0
179 
180  ! Heat fluxes are in units of W m-2 and are positive into the ocean.
181  fluxes%lw(i,j) = 0.0 * g%mask2dT(i,j)
182  fluxes%latent(i,j) = 0.0 * g%mask2dT(i,j)
183  fluxes%sens(i,j) = 0.0 * g%mask2dT(i,j)
184  fluxes%sw(i,j) = 0.0 * g%mask2dT(i,j)
185  enddo ; enddo
186  else ! This is the buoyancy only mode.
187  do j=js,je ; do i=is,ie
188  ! fluxes%buoy is the buoyancy flux into the ocean [L2 T-3 ~> m2 s-3]. A positive
189  ! buoyancy flux is of the same sign as heating the ocean.
190  fluxes%buoy(i,j) = 0.0 * g%mask2dT(i,j)
191  enddo ; enddo
192  endif
193 
194  if (cs%restorebuoy) then
195  if (cs%use_temperature) then
196  call safe_alloc_ptr(fluxes%heat_added, isd, ied, jsd, jed)
197  ! When modifying the code, comment out this error message. It is here
198  ! so that the original (unmodified) version is not accidentally used.
199  call mom_error(fatal, "User_buoyancy_surface_forcing: " // &
200  "Temperature and salinity restoring used without modification." )
201 
202  rhoxcp = cs%Rho0 * fluxes%C_p
203  do j=js,je ; do i=is,ie
204  ! Set Temp_restore and Salin_restore to the temperature (in degC) and
205  ! salinity (in PSU or ppt) that are being restored toward.
206  temp_restore = 0.0
207  salin_restore = 0.0
208 
209  fluxes%heat_added(i,j) = (g%mask2dT(i,j) * (rhoxcp * cs%Flux_const)) * &
210  (temp_restore - sfc_state%SST(i,j))
211  fluxes%vprec(i,j) = - (g%mask2dT(i,j) * (cs%Rho0*cs%Flux_const)) * &
212  ((salin_restore - sfc_state%SSS(i,j)) / &
213  (0.5 * (salin_restore + sfc_state%SSS(i,j))))
214  enddo ; enddo
215  else
216  ! When modifying the code, comment out this error message. It is here
217  ! so that the original (unmodified) version is not accidentally used.
218  call mom_error(fatal, "User_buoyancy_surface_forcing: " // &
219  "Buoyancy restoring used without modification." )
220 
221  ! The -1 is because density has the opposite sign to buoyancy.
222  buoy_rest_const = -1.0 * (cs%G_Earth * us%m_to_Z*us%T_to_s*cs%Flux_const) / cs%Rho0
223  do j=js,je ; do i=is,ie
224  ! Set density_restore to an expression for the surface potential
225  ! density [kg m-3] that is being restored toward.
226  density_restore = 1030.0
227 
228  fluxes%buoy(i,j) = g%mask2dT(i,j) * buoy_rest_const * &
229  (density_restore - sfc_state%sfc_density(i,j))
230  enddo ; enddo
231  endif
232  endif ! end RESTOREBUOY
233 
234 end subroutine user_buoyancy_forcing
235 
236 !> This subroutine initializes the USER_surface_forcing module
237 subroutine user_surface_forcing_init(Time, G, US, param_file, diag, CS)
238  type(time_type), intent(in) :: time !< The current model time
239  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
240  type(unit_scale_type), intent(in) :: us !< A dimensional unit scaling type
241  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
242  type(diag_ctrl), target, intent(in) :: diag !< A structure that is used to regulate diagnostic output.
243  type(user_surface_forcing_cs), pointer :: cs !< A pointer that is set to point to
244  !! the control structure for this module
245 
246 ! This include declares and sets the variable "version".
247 #include "version_variable.h"
248  character(len=40) :: mdl = "user_surface_forcing" ! This module's name.
249 
250  if (associated(cs)) then
251  call mom_error(warning, "USER_surface_forcing_init called with an associated "// &
252  "control structure.")
253  return
254  endif
255  allocate(cs)
256  cs%diag => diag
257 
258  ! Read all relevant parameters and write them to the model log.
259  call log_version(param_file, mdl, version, "")
260  call get_param(param_file, mdl, "ENABLE_THERMODYNAMICS", cs%use_temperature, &
261  "If true, Temperature and salinity are used as state "//&
262  "variables.", default=.true.)
263 
264  call get_param(param_file, mdl, "G_EARTH", cs%G_Earth, &
265  "The gravitational acceleration of the Earth.", &
266  units="m s-2", default = 9.80, scale=us%m_to_L**2*us%Z_to_m*us%T_to_s**2)
267  call get_param(param_file, mdl, "RHO_0", cs%Rho0, &
268  "The mean ocean density used with BOUSSINESQ true to "//&
269  "calculate accelerations and the mass for conservation "//&
270  "properties, or with BOUSSINSEQ false to convert some "//&
271  "parameters from vertical units of m to kg m-2.", &
272  units="kg m-3", default=1035.0)
273  call get_param(param_file, mdl, "GUST_CONST", cs%gust_const, &
274  "The background gustiness in the winds.", units="Pa", &
275  default=0.02)
276 
277  call get_param(param_file, mdl, "RESTOREBUOY", cs%restorebuoy, &
278  "If true, the buoyancy fluxes drive the model back "//&
279  "toward some specified surface state with a rate "//&
280  "given by FLUXCONST.", default= .false.)
281  if (cs%restorebuoy) then
282  call get_param(param_file, mdl, "FLUXCONST", cs%Flux_const, &
283  "The constant that relates the restoring surface fluxes "//&
284  "to the relative surface anomalies (akin to a piston "//&
285  "velocity). Note the non-MKS units.", units="m day-1", &
286  fail_if_missing=.true.)
287  ! Convert CS%Flux_const from m day-1 to m s-1.
288  cs%Flux_const = cs%Flux_const / 86400.0
289  endif
290 
291 end subroutine user_surface_forcing_init
292 
293 !! \namespace user_surface_forcing
294 !!
295 !! This file contains the subroutines that a user should modify to
296 !! to set the surface wind stresses and fluxes of buoyancy or
297 !! temperature and fresh water. They are called when the run-time
298 !! parameters WIND_CONFIG or BUOY_CONFIG are set to "USER". The
299 !! standard version has simple examples, along with run-time error
300 !! messages that will cause the model to abort if this code has no
301 !! been modified. This code is intended for use with relatively
302 !! simple specifications of the forcing. For more complicated forms,
303 !! it is probably a good idea to read the forcing from input files
304 !! using "file" for WIND_CONFIG and BUOY_CONFIG.
305 !!
306 !! USER_wind_forcing() should set the surface wind stresses (taux and
307 !! tauy) perhaps along with the surface friction velocity (ustar).
308 !!
309 !! USER_buoyancy() forcing is used to set the surface buoyancy
310 !! forcing, which may include a number of fresh water flux fields
311 !! (evap, lprec, fprec, lrunoff, frunoff, and
312 !! vprec) and the surface heat fluxes (sw, lw, latent and sens)
313 !! if temperature and salinity are state variables, or it may simply
314 !! be the buoyancy flux if it is not. This routine also has coded a
315 !! restoring to surface values of temperature and salinity.
316 
317 end module user_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
user_surface_forcing::user_surface_forcing_cs
This control structure should be used to store any run-time variables associated with the user-specif...
Definition: user_surface_forcing.F90:30
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
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_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
user_surface_forcing
Template for user to code up surface forcing.
Definition: user_surface_forcing.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
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