MOM6
MOM_forcing_type.F90
Go to the documentation of this file.
1 !> This module implements boundary forcing for MOM6.
3 
4 ! This file is part of MOM6. See LICENSE.md for the license.
5 
6 use mom_debugging, only : hchksum, uvchksum
7 use mom_cpu_clock, only : cpu_clock_id, cpu_clock_begin, cpu_clock_end, clock_routine
9 use mom_diag_mediator, only : time_type, diag_ctrl, safe_alloc_alloc, query_averaging_enabled
10 use mom_error_handler, only : mom_error, fatal, warning
13 use mom_grid, only : ocean_grid_type
18 
20 
21 implicit none ; private
22 
23 #include <MOM_memory.h>
24 
29 
30 !> Structure that contains pointers to the boundary forcing
31 !! used to drive the liquid ocean simulated by MOM.
32 !! Data in this type is allocated in the module
33 !! MOM_surface_forcing.F90, of which there are three:
34 !! solo, coupled, and ice-shelf. Alternatively, they are
35 !! allocated in MESO_surface_forcing.F90, which is a
36 !! special case of solo_driver/MOM_surface_forcing.F90.
37 type, public :: forcing
38 
39  ! Pointers in this module should be initialized to NULL.
40 
41  ! surface stress components and turbulent velocity scale
42  real, pointer, dimension(:,:) :: &
43  taux => null(), & !< zonal wind stress (Pa)
44  tauy => null(), & !< meridional wind stress (Pa)
45  ustar => null() !< surface friction velocity scale (m/s)
46 
47  ! surface buoyancy force
48  real, pointer, dimension(:,:) :: &
49  buoy => null() !< buoyancy flux (m^2/s^3)
50 
51  ! radiative heat fluxes into the ocean (W/m^2)
52  real, pointer, dimension(:,:) :: &
53  sw => null(), & !< shortwave (W/m^2)
54  sw_vis_dir => null(), & !< visible, direct shortwave (W/m^2)
55  sw_vis_dif => null(), & !< visible, diffuse shortwave (W/m^2)
56  sw_nir_dir => null(), & !< near-IR, direct shortwave (W/m^2)
57  sw_nir_dif => null(), & !< near-IR, diffuse shortwave (W/m^2)
58  lw => null() !< longwave (W/m^2) (typically negative)
59 
60  ! turbulent heat fluxes into the ocean (W/m^2)
61  real, pointer, dimension(:,:) :: &
62  latent => null(), & !< latent (W/m^2) (typically < 0)
63  sens => null(), & !< sensible (W/m^2) (typically negative)
64  heat_added => null() !< additional heat flux from SST restoring or flux adjustments (W/m^2)
65 
66  ! components of latent heat fluxes used for diagnostic purposes
67  real, pointer, dimension(:,:) :: &
68  latent_evap_diag => null(), & !< latent (W/m^2) from evaporating liquid water (typically < 0)
69  latent_fprec_diag => null(), & !< latent (W/m^2) from melting fprec (typically < 0)
70  latent_frunoff_diag => null() !< latent (W/m^2) from melting frunoff (calving) (typically < 0)
71 
72  ! water mass fluxes into the ocean ( kg/(m^2 s) ); these fluxes impact the ocean mass
73  real, pointer, dimension(:,:) :: &
74  evap => null(), & !< (-1)*fresh water flux evaporated out of the ocean ( kg/(m^2 s) )
75  lprec => null(), & !< precipitating liquid water into the ocean ( kg/(m^2 s) )
76  fprec => null(), & !< precipitating frozen water into the ocean ( kg/(m^2 s) )
77  vprec => null(), & !< virtual liquid precip associated w/ SSS restoring ( kg/(m^2 s) )
78  lrunoff => null(), & !< liquid river runoff entering ocean ( kg/(m^2 s) )
79  frunoff => null(), & !< frozen river runoff (calving) entering ocean ( kg/(m^2 s) )
80  seaice_melt => null(), & !< seaice melt (positive) or formation (negative) ( kg/(m^2 s) )
81  netmassin => null(), & !< Sum of water mass flux out of the ocean ( kg/(m^2 s) )
82  netmassout => null(), & !< Net water mass flux into of the ocean ( kg/(m^2 s) )
83  netsalt => null() !< Net salt entering the ocean
84 
85  ! heat associated with water crossing ocean surface
86  real, pointer, dimension(:,:) :: &
87  heat_content_cond => null(), & !< heat content associated with condensating water (W/m^2)
88  heat_content_lprec => null(), & !< heat content associated with liquid >0 precip (W/m^2) (diagnostic)
89  heat_content_fprec => null(), & !< heat content associated with frozen precip (W/m^2)
90  heat_content_vprec => null(), & !< heat content associated with virtual >0 precip (W/m^2)
91  heat_content_lrunoff => null(), & !< heat content associated with liquid runoff (W/m^2)
92  heat_content_frunoff => null(), & !< heat content associated with frozen runoff (W/m^2)
93  heat_content_icemelt => null(), & !< heat content associated with liquid sea ice (W/m^2)
94  heat_content_massout => null(), & !< heat content associated with mass leaving ocean (W/m^2)
95  heat_content_massin => null() !< heat content associated with mass entering ocean (W/m^2)
96 
97  ! salt mass flux (contributes to ocean mass only if non-Bouss )
98  real, pointer, dimension(:,:) :: &
99  salt_flux => null(), & !< net salt flux into the ocean ( kg salt/(m^2 s) )
100  salt_flux_in => null(), & !< salt flux provided to the ocean from coupler ( kg salt/(m^2 s) )
101  salt_flux_added => null() !< additional salt flux from restoring or flux adjustment before adjustment
102  !! to net zero ( kg salt/(m^2 s) )
103 
104  ! applied surface pressure from other component models (e.g., atmos, sea ice, land ice)
105  real, pointer, dimension(:,:) :: &
106  p_surf_full => null(), & !< Pressure at the top ocean interface (Pa).
107  !! if there is sea-ice, then p_surf_flux is at ice-ocean interface
108  p_surf => null(), & !< Pressure at the top ocean interface (Pa) as used
109  !! to drive the ocean model. If p_surf is limited,
110  !! p_surf may be smaller than p_surf_full,
111  !! otherwise they are the same.
112  p_surf_ssh => null() !< Pressure at the top ocean interface that is used
113  !! in corrections to the sea surface height field
114  !! that is passed back to the calling routines.
115  !! This may point to p_surf or to p_surf_full.
116 
117  ! tide related inputs
118  real, pointer, dimension(:,:) :: &
119  tke_tidal => null(), & !< tidal energy source driving mixing in bottom boundary layer (W/m^2)
120  ustar_tidal => null() !< tidal contribution to bottom ustar (m/s)
121 
122  ! iceberg related inputs
123  real, pointer, dimension(:,:) :: &
124  ustar_berg => null(),& !< iceberg contribution to top ustar (m/s)
125  area_berg => null(),& !< area of ocean surface covered by icebergs (m2/m2)
126  mass_berg => null() !< mass of icebergs (kg/m2)
127 
128  ! land ice-shelf related inputs
129  real, pointer, dimension(:,:) :: &
130  ustar_shelf => null(), & !< friction velocity under ice-shelves (m/s)
131  !! as computed by the ocean at the previous time step.
132  frac_shelf_h => null(), & !< Fractional ice shelf coverage of h-, u-, and v-
133  frac_shelf_u => null(), & !< cells, nondimensional from 0 to 1. These are only
134  frac_shelf_v => null(), & !< associated if ice shelves are enabled, and are
135  !! exactly 0 away from shelves or on land.
136  iceshelf_melt => null(), & !< ice shelf melt rate (positive) or freezing (negative) ( m/year )
137  rigidity_ice_u => null(),& !< Depth-integrated lateral viscosity of ice
138  rigidity_ice_v => null() !< shelves or sea ice at u- or v-points (m3/s)
139 
140  ! Scalars set by surface forcing modules
141  real :: vprecglobaladj !< adjustment to restoring vprec to zero out global net ( kg/(m^2 s) )
142  real :: saltfluxglobaladj !< adjustment to restoring salt flux to zero out global net ( kg salt/(m^2 s) )
143  real :: netfwglobaladj !< adjustment to net fresh water to zero out global net ( kg/(m^2 s) )
144  real :: vprecglobalscl !< scaling of restoring vprec to zero out global net ( -1..1 )
145  real :: saltfluxglobalscl !< scaling of restoring salt flux to zero out global net ( -1..1 )
146  real :: netfwglobalscl !< scaling of net fresh water to zero out global net ( -1..1 )
147 
148  logical :: fluxes_used = .true. !< If true, all of the heat, salt, and mass
149  !! fluxes have been applied to the ocean.
150  real :: dt_buoy_accum = -1.0 !< The amount of time over which the buoyancy fluxes
151  !! should be applied, in s. If negative, this forcing
152  !! type variable has not yet been inialized.
153 
154  ! heat capacity
155  real :: c_p !< heat capacity of seawater ( J/(K kg) ).
156  !! C_p is is the same value as in thermovar_ptrs_type.
157 
158  ! passive tracer surface fluxes
159  type(coupler_2d_bc_type), pointer :: tr_fluxes => null() !< This structure
160  !! may contain an array of named fields used for passive tracer fluxes.
161  !! All arrays in tr_fluxes use the coupler indexing, which has no halos.
162  !! This is not a convenient convention, but imposed on MOM6 by the coupler.
163 
164  ! For internal error tracking
165  integer :: num_msg = 0 !< Number of messages issues about excessive SW penetration
166  integer :: max_msg = 2 !< Maximum number of messages to issue about excessive SW penetration
167 
168 end type forcing
169 
170 !> Structure that defines the id handles for the forcing type
171 type, public :: forcing_diags
172 
173  ! mass flux diagnostic handles
174  integer :: id_prcme = -1, id_evap = -1
175  integer :: id_precip = -1, id_vprec = -1
176  integer :: id_lprec = -1, id_fprec = -1
177  integer :: id_lrunoff = -1, id_frunoff = -1
178  integer :: id_net_massout = -1, id_net_massin = -1
179  integer :: id_massout_flux = -1, id_massin_flux = -1
180  integer :: id_seaice_melt = -1
181 
182  ! global area integrated mass flux diagnostic handles
183  integer :: id_total_prcme = -1, id_total_evap = -1
184  integer :: id_total_precip = -1, id_total_vprec = -1
185  integer :: id_total_lprec = -1, id_total_fprec = -1
186  integer :: id_total_lrunoff = -1, id_total_frunoff = -1
187  integer :: id_total_net_massout = -1, id_total_net_massin = -1
188  integer :: id_total_seaice_melt = -1
189 
190  ! global area averaged mass flux diagnostic handles
191  integer :: id_prcme_ga = -1, id_evap_ga = -1
192  integer :: id_lprec_ga = -1, id_fprec_ga= -1
193  integer :: id_precip_ga = -1, id_vprec_ga= -1
194 
195  ! heat flux diagnostic handles
196  integer :: id_net_heat_coupler = -1, id_net_heat_surface = -1
197  integer :: id_sens = -1, id_lwlatsens = -1
198  integer :: id_sw = -1, id_lw = -1
199  integer :: id_sw_vis = -1, id_sw_nir = -1
200  integer :: id_lat_evap = -1, id_lat_frunoff = -1
201  integer :: id_lat = -1, id_lat_fprec = -1
202  integer :: id_heat_content_lrunoff= -1, id_heat_content_frunoff = -1
203  integer :: id_heat_content_lprec = -1, id_heat_content_fprec = -1
204  integer :: id_heat_content_cond = -1, id_heat_content_surfwater= -1
205  integer :: id_heat_content_vprec = -1, id_heat_content_massout = -1
206  integer :: id_heat_added = -1, id_heat_content_massin = -1
207  integer :: id_hfrainds = -1, id_hfrunoffds = -1
208 
209 
210  ! global area integrated heat flux diagnostic handles
211  integer :: id_total_net_heat_coupler = -1, id_total_net_heat_surface = -1
212  integer :: id_total_sens = -1, id_total_lwlatsens = -1
213  integer :: id_total_sw = -1, id_total_lw = -1
214  integer :: id_total_lat_evap = -1, id_total_lat_frunoff = -1
215  integer :: id_total_lat = -1, id_total_lat_fprec = -1
216  integer :: id_total_heat_content_lrunoff= -1, id_total_heat_content_frunoff = -1
217  integer :: id_total_heat_content_lprec = -1, id_total_heat_content_fprec = -1
218  integer :: id_total_heat_content_cond = -1, id_total_heat_content_surfwater= -1
219  integer :: id_total_heat_content_vprec = -1, id_total_heat_content_massout = -1
220  integer :: id_total_heat_added = -1, id_total_heat_content_massin = -1
221 
222  ! global area averaged heat flux diagnostic handles
223  integer :: id_net_heat_coupler_ga = -1, id_net_heat_surface_ga = -1
224  integer :: id_sens_ga = -1, id_lwlatsens_ga = -1
225  integer :: id_sw_ga = -1, id_lw_ga = -1
226  integer :: id_lat_ga = -1
227 
228  ! salt flux diagnostic handles
229  integer :: id_saltflux = -1
230  integer :: id_saltfluxin = -1
231  integer :: id_saltfluxadded = -1
232 
233  integer :: id_total_saltflux = -1
234  integer :: id_total_saltfluxin = -1
235  integer :: id_total_saltfluxadded = -1
236 
237  integer :: id_vprecglobaladj = -1
238  integer :: id_vprecglobalscl = -1
239  integer :: id_saltfluxglobaladj = -1
240  integer :: id_saltfluxglobalscl = -1
241  integer :: id_netfwglobaladj = -1
242  integer :: id_netfwglobalscl = -1
243 
244  ! momentum flux diagnostic handls
245  integer :: id_taux = -1
246  integer :: id_tauy = -1
247  integer :: id_ustar = -1
248 
249  integer :: id_psurf = -1
250  integer :: id_tke_tidal = -1
251  integer :: id_buoy = -1
252 
253  ! clock id handle
254  integer :: id_clock_forcing
255 
256  ! iceberg id handle
257  integer :: id_ustar_berg = -1
258  integer :: id_area_berg = -1
259  integer :: id_mass_berg = -1
260 
261  !Iceberg + Ice shelf
262  integer :: id_ustar_ice_cover = -1
263  integer :: id_frac_ice_cover = -1
264 
265 end type forcing_diags
266 
267 contains
268 
269 !> This subroutine extracts fluxes from the surface fluxes type. It works on a j-row
270 !! for optimization purposes. The 2d (i,j) wrapper is the next subroutine below.
271 !! This routine multiplies fluxes by dt, so that the result is an accumulation of fluxes
272 !! over a time step.
273 subroutine extractfluxes1d(G, GV, fluxes, optics, nsw, j, dt, &
274  DepthBeforeScalingFluxes, useRiverHeatContent, useCalvingHeatContent, &
275  h, T, netMassInOut, netMassOut, net_heat, net_salt, pen_SW_bnd, tv, &
276  aggregate_FW_forcing, nonpenSW, netmassInOut_rate,net_Heat_Rate, &
277  net_salt_rate, pen_sw_bnd_Rate, skip_diags)
279  type(ocean_grid_type), intent(in) :: G !< ocean grid structure
280  type(verticalgrid_type), intent(in) :: GV !< ocean vertical grid structure
281  type(forcing), intent(inout) :: fluxes !< structure containing pointers to possible
282  !! forcing fields. NULL unused fields.
283  type(optics_type), pointer :: optics !< pointer to optics
284  integer, intent(in) :: nsw !< number of bands of penetrating SW
285  integer, intent(in) :: j !< j-index to work on
286  real, intent(in) :: dt !< time step in seconds
287  real, intent(in) :: DepthBeforeScalingFluxes !< min ocean depth before scale away fluxes (H)
288  logical, intent(in) :: useRiverHeatContent !< logical for river heat content
289  logical, intent(in) :: useCalvingHeatContent !< logical for calving heat content
290  real, dimension(SZI_(G),SZK_(G)), intent(in) :: h !< layer thickness (in H units)
291  real, dimension(SZI_(G),SZK_(G)), intent(in) :: T !< layer temperatures (deg C)
292  real, dimension(SZI_(G)), intent(out) :: netMassInOut !< net mass flux (non-Bouss) or volume flux
293  !! (if Bouss) of water in/out of ocean over
294  !! a time step (H units)
295  real, dimension(SZI_(G)), intent(out) :: netMassOut !< net mass flux (non-Bouss) or volume flux
296  !! (if Bouss) of water leaving ocean surface
297  !! over a time step (H units).
298  !! netMassOut < 0 means mass leaves ocean.
299  real, dimension(SZI_(G)), intent(out) :: net_heat !< net heat at the surface accumulated over a
300  !! time step for coupler + restoring.
301  !! Exclude two terms from net_heat:
302  !! (1) downwelling (penetrative) SW,
303  !! (2) evaporation heat content,
304  !! (since do not yet know evap temperature).
305  !! Units of net_heat are (K * H).
306  real, dimension(SZI_(G)), intent(out) :: net_salt !< surface salt flux into the ocean accumulated
307  !! over a time step (ppt * H)
308  real, dimension(:,:), intent(out) :: pen_SW_bnd !< penetrating SW flux, split into bands.
309  !! Units are (deg K * H) and array size
310  !! nsw x SZI_(G), where nsw=number of SW bands
311  !! in pen_SW_bnd. This heat flux is not part
312  !! of net_heat.
313  type(thermo_var_ptrs), intent(inout) :: tv !< structure containing pointers to available
314  !! thermodynamic fields. Used to keep
315  !! track of the heat flux associated with net
316  !! mass fluxes into the ocean.
317  logical, intent(in) :: aggregate_FW_forcing !< For determining how to aggregate forcing.
318  real, dimension(SZI_(G)), optional, intent(out) :: nonpenSW !< non-downwelling SW; use in net_heat.
319  !! Sum over SW bands when diagnosing nonpenSW.
320  !! Units are (K * H).
321  real, dimension(SZI_(G)), optional, intent(out) :: net_Heat_rate !< Optional outputs of contributions to surface
322  real, dimension(SZI_(G)), optional, intent(out) :: net_salt_rate !< buoyancy flux which do not include dt
323  real, dimension(SZI_(G)), optional, intent(out) :: netmassInOut_rate !< and therefore are used to compute the rate.
324  real, dimension(:,:), optional, intent(out) :: pen_sw_bnd_rate !< Perhaps just a temporary fix.
325  logical, optional, intent(in) :: skip_diags !< If present and true, skip calculating
326  !! diagnostics
327 
328  ! local
329  real :: htot(szi_(g)) ! total ocean depth (m for Bouss or kg/m^2 for non-Bouss)
330  real :: Pen_sw_tot(szi_(g)) ! sum across all bands of Pen_SW (K * H)
331  real :: pen_sw_tot_rate(szi_(g)) ! Similar but sum but as a rate (no dt in calculation)
332  real :: Ih_limit ! inverse depth at which surface fluxes start to be limited (1/H)
333  real :: scale ! scale scales away fluxes if depth < DepthBeforeScalingFluxes
334  real :: J_m2_to_H ! converts J/m^2 to H units (m for Bouss and kg/m^2 for non-Bouss)
335  real :: Irho0 ! 1.0 / Rho0
336  real :: I_Cp ! 1.0 / C_p
337  logical :: calculate_diags ! Indicate to calculate/update diagnostic arrays
338  character(len=200) :: mesg
339  integer :: is, ie, nz, i, k, n
340 
341  logical :: do_NHR, do_NSR, do_NMIOR, do_PSWBR
342 
343  !BGR-Jul 5,2017{
344  ! Initializes/sets logicals if 'rates' are requested
345  ! These factors are required for legacy reasons
346  ! and therefore computed only when optional outputs are requested
347  do_nhr = .false.
348  do_nsr = .false.
349  do_nmior = .false.
350  do_pswbr = .false.
351  if (present(net_heat_rate)) do_nhr = .true.
352  if (present(net_salt_rate)) do_nsr = .true.
353  if (present(netmassinout_rate)) do_nmior = .true.
354  if (present(pen_sw_bnd_rate)) do_pswbr = .true.
355  !}BGR
356 
357  ih_limit = 1.0 / depthbeforescalingfluxes
358  irho0 = 1.0 / gv%Rho0
359  i_cp = 1.0 / fluxes%C_p
360  j_m2_to_h = 1.0 / (gv%H_to_kg_m2 * fluxes%C_p)
361 
362  is = g%isc ; ie = g%iec ; nz = g%ke
363 
364  calculate_diags = .true.
365  if (present(skip_diags)) calculate_diags = .not. skip_diags
366 
367  ! error checking
368 
369  if (nsw > 0) then ; if (nsw /= optics%nbands) call mom_error(warning, &
370  "mismatch in the number of bands of shortwave radiation in MOM_forcing_type extract_fluxes.")
371  endif
372 
373  if (.not.ASSOCIATED(fluxes%sw)) call mom_error(fatal, &
374  "MOM_forcing_type extractFluxes1d: fluxes%sw is not associated.")
375 
376  if (.not.ASSOCIATED(fluxes%lw)) call mom_error(fatal, &
377  "MOM_forcing_type extractFluxes1d: fluxes%lw is not associated.")
378 
379  if (.not.ASSOCIATED(fluxes%latent)) call mom_error(fatal, &
380  "MOM_forcing_type extractFluxes1d: fluxes%latent is not associated.")
381 
382  if (.not.ASSOCIATED(fluxes%sens)) call mom_error(fatal, &
383  "MOM_forcing_type extractFluxes1d: fluxes%sens is not associated.")
384 
385  if (.not.ASSOCIATED(fluxes%evap)) call mom_error(fatal, &
386  "MOM_forcing_type extractFluxes1d: No evaporation defined.")
387 
388  if (.not.ASSOCIATED(fluxes%vprec)) call mom_error(fatal, &
389  "MOM_forcing_type extractFluxes1d: fluxes%vprec not defined.")
390 
391  if ((.not.ASSOCIATED(fluxes%lprec)) .or. &
392  (.not.ASSOCIATED(fluxes%fprec))) call mom_error(fatal, &
393  "MOM_forcing_type extractFluxes1d: No precipitation defined.")
394 
395  do i=is,ie ; htot(i) = h(i,1) ; enddo
396  do k=2,nz ; do i=is,ie ; htot(i) = htot(i) + h(i,k) ; enddo ; enddo
397 
398 
399  do i=is,ie
400 
401  scale = 1.0
402  if (htot(i)*ih_limit < 1.0) scale = htot(i)*ih_limit
403 
404  ! Convert the penetrating shortwave forcing to (K * H)
405  ! (H=m for Bouss, H=kg/m2 for non-Bouss)
406  pen_sw_tot(i) = 0.0
407  if (nsw >= 1) then
408  do n=1,nsw
409  pen_sw_bnd(n,i) = j_m2_to_h*scale*dt * max(0.0, optics%sw_pen_band(n,i,j))
410  pen_sw_tot(i) = pen_sw_tot(i) + pen_sw_bnd(n,i)
411  enddo
412  else
413  pen_sw_bnd(1,i) = 0.0
414  endif
415 
416  !BGR-Jul 5, 2017{
417  !Repeats above code w/ dt=1. for legacy reason
418  if (do_pswbr) then
419  pen_sw_tot_rate(i) = 0.0
420  if (nsw >= 1) then
421  do n=1,nsw
422  pen_sw_bnd_rate(n,i) = j_m2_to_h*scale * max(0.0, optics%sw_pen_band(n,i,j))
423  pen_sw_tot_rate(i) = pen_sw_tot_rate(i) + pen_sw_bnd_rate(n,i)
424  enddo
425  else
426  pen_sw_bnd_rate(1,i) = 0.0
427  endif
428  endif
429  !}BGR
430 
431  ! net volume/mass of liquid and solid passing through surface boundary fluxes
432  netmassinout(i) = dt * (scale * ((((( fluxes%lprec(i,j) &
433  + fluxes%fprec(i,j) ) &
434  + fluxes%evap(i,j) ) &
435  + fluxes%lrunoff(i,j) ) &
436  + fluxes%vprec(i,j) ) &
437  + fluxes%frunoff(i,j) ) )
438 
439  !BGR-Jul 5, 2017{
440  !Repeats above code w/ dt=1. for legacy reason
441  if (do_nmior) then
442  netmassinout_rate(i) = (scale * ((((( fluxes%lprec(i,j) &
443  + fluxes%fprec(i,j) ) &
444  + fluxes%evap(i,j) ) &
445  + fluxes%lrunoff(i,j) ) &
446  + fluxes%vprec(i,j) ) &
447  + fluxes%frunoff(i,j) ) )
448  endif
449  !}BGR
450 
451  ! smg:
452  ! for non-Bouss, we add/remove salt mass to total ocean mass. to conserve
453  ! total salt mass ocean+ice, the sea ice model must lose mass when
454  ! salt mass is added to the ocean, which may still need to be coded.
455  if (.not.gv%Boussinesq .and. ASSOCIATED(fluxes%salt_flux)) then
456  netmassinout(i) = netmassinout(i) + (dt * gv%kg_m2_to_H) * (scale * fluxes%salt_flux(i,j))
457 
458  !BGR-Jul 5, 2017{
459  !Repeats above code w/ dt=1. for legacy reason
460  if (do_nmior) netmassinout_rate(i) = netmassinout_rate(i) + (gv%kg_m2_to_H) * (scale * fluxes%salt_flux(i,j))
461  !}BGR
462  endif
463 
464  ! net volume/mass of water leaving the ocean.
465  ! check that fluxes are < 0, which means mass is indeed leaving.
466  netmassout(i) = 0.0
467 
468  ! evap > 0 means condensating water is added into ocean.
469  ! evap < 0 means evaporation of water from the ocean, in
470  ! which case heat_content_evap is computed in MOM_diabatic_driver.F90
471  if(fluxes%evap(i,j) < 0.0) then
472  netmassout(i) = netmassout(i) + fluxes%evap(i,j)
473  ! if(ASSOCIATED(fluxes%heat_content_cond)) fluxes%heat_content_cond(i,j) = 0.0 !??? --AJA
474  endif
475 
476  ! lprec < 0 means sea ice formation taking water from the ocean.
477  ! smg: we should split the ice melt/formation from the lprec
478  if(fluxes%lprec(i,j) < 0.0) then
479  netmassout(i) = netmassout(i) + fluxes%lprec(i,j)
480  endif
481 
482  ! vprec < 0 means virtual evaporation arising from surface salinity restoring,
483  ! in which case heat_content_vprec is computed in MOM_diabatic_driver.F90.
484  if(fluxes%vprec(i,j) < 0.0) then
485  netmassout(i) = netmassout(i) + fluxes%vprec(i,j)
486  endif
487  netmassout(i) = dt * scale * netmassout(i)
488 
489  ! convert to H units (Bouss=meter or non-Bouss=kg/m^2)
490  netmassinout(i) = gv%kg_m2_to_H * netmassinout(i)
491  !BGR-Jul 5, 2017{
492  !Repeats above code w/ dt=1. for legacy reason
493  if (do_nmior) netmassinout_rate(i) = gv%kg_m2_to_H * netmassinout_rate(i)
494  !}BGR
495  netmassout(i) = gv%kg_m2_to_H * netmassout(i)
496 
497  ! surface heat fluxes from radiation and turbulent fluxes (K * H)
498  ! (H=m for Bouss, H=kg/m2 for non-Bouss)
499  net_heat(i) = scale * dt * j_m2_to_h * &
500  ( fluxes%sw(i,j) + ((fluxes%lw(i,j) + fluxes%latent(i,j)) + fluxes%sens(i,j)) )
501  !BGR-Jul 5, 2017{
502  !Repeats above code w/ dt=1. for legacy reason
503  if (do_nhr) net_heat_rate(i) = scale * j_m2_to_h * &
504  ( fluxes%sw(i,j) + ((fluxes%lw(i,j) + fluxes%latent(i,j)) + fluxes%sens(i,j)) )
505  !}BGR
506  ! Add heat flux from surface damping (restoring) (K * H) or flux adjustments.
507  if (ASSOCIATED(fluxes%heat_added)) then
508  net_heat(i) = net_heat(i) + (scale * (dt * j_m2_to_h)) * fluxes%heat_added(i,j)
509  if (do_nhr) net_heat_rate(i) = net_heat_rate(i) + (scale * (j_m2_to_h)) * fluxes%heat_added(i,j)
510  endif
511 
512  ! Add explicit heat flux for runoff (which is part of the ice-ocean boundary
513  ! flux type). Runoff is otherwise added with a temperature of SST.
514  if (useriverheatcontent) then
515  ! remove lrunoff*SST here, to counteract its addition elsewhere
516  net_heat(i) = (net_heat(i) + (scale*(dt*j_m2_to_h)) * fluxes%heat_content_lrunoff(i,j)) - &
517  (gv%kg_m2_to_H * (scale * dt)) * fluxes%lrunoff(i,j) * t(i,1)
518  !BGR-Jul 5, 2017{
519  !Intentionally neglect the following contribution to rate for legacy reasons.
520  !if (do_NHR) net_heat_rate(i) = (net_heat_rate(i) + (scale*(J_m2_to_H)) * fluxes%heat_content_lrunoff(i,j)) - &
521  ! (GV%kg_m2_to_H * (scale)) * fluxes%lrunoff(i,j) * T(i,1)
522  !}BGR
523  if (calculate_diags .and. ASSOCIATED(tv%TempxPmE)) then
524  tv%TempxPmE(i,j) = tv%TempxPmE(i,j) + (scale * dt) * &
525  (i_cp*fluxes%heat_content_lrunoff(i,j) - fluxes%lrunoff(i,j)*t(i,1))
526  endif
527  endif
528 
529  ! Add explicit heat flux for calving (which is part of the ice-ocean boundary
530  ! flux type). Calving is otherwise added with a temperature of SST.
531  if (usecalvingheatcontent) then
532  ! remove frunoff*SST here, to counteract its addition elsewhere
533  net_heat(i) = net_heat(i) + (scale*(dt*j_m2_to_h)) * fluxes%heat_content_frunoff(i,j) - &
534  (gv%kg_m2_to_H * (scale * dt)) * fluxes%frunoff(i,j) * t(i,1)
535  !BGR-Jul 5, 2017{
536  !Intentionally neglect the following contribution to rate for legacy reasons.
537 ! if (do_NHR) net_heat_rate(i) = net_heat_rate(i) + (scale*(J_m2_to_H)) * fluxes%heat_content_frunoff(i,j) - &
538 ! (GV%kg_m2_to_H * (scale)) * fluxes%frunoff(i,j) * T(i,1)
539  !}BGR
540  if (calculate_diags .and. ASSOCIATED(tv%TempxPmE)) then
541  tv%TempxPmE(i,j) = tv%TempxPmE(i,j) + (scale * dt) * &
542  (i_cp*fluxes%heat_content_frunoff(i,j) - fluxes%frunoff(i,j)*t(i,1))
543  endif
544  endif
545 
546 ! smg: new code
547  ! add heat from all terms that may add mass to the ocean (K * H).
548  ! if evap, lprec, or vprec < 0, then compute their heat content
549  ! inside MOM_diabatic_driver.F90 and fill in fluxes%heat_content_massout.
550  ! we do so since we do not here know the temperature
551  ! of water leaving the ocean, as it could be leaving from more than
552  ! one layer of the upper ocean in the case of very thin layers.
553  ! When evap, lprec, or vprec > 0, then we know their heat content here
554  ! via settings from inside of the appropriate config_src driver files.
555 ! if (ASSOCIATED(fluxes%heat_content_lprec)) then
556 ! net_heat(i) = net_heat(i) + scale * dt * J_m2_to_H * &
557 ! (fluxes%heat_content_lprec(i,j) + (fluxes%heat_content_fprec(i,j) + &
558 ! (fluxes%heat_content_lrunoff(i,j) + (fluxes%heat_content_frunoff(i,j) + &
559 ! (fluxes%heat_content_cond(i,j) + fluxes%heat_content_vprec(i,j))))))
560 ! endif
561 
562  if (fluxes%num_msg < fluxes%max_msg) then
563  if (pen_sw_tot(i) > 1.000001*j_m2_to_h*scale*dt*fluxes%sw(i,j)) then
564  fluxes%num_msg = fluxes%num_msg + 1
565  write(mesg,'("Penetrating shortwave of ",1pe17.10, &
566  &" exceeds total shortwave of ",1pe17.10,&
567  &" at ",1pg11.4,"E, "1pg11.4,"N.")') &
568  pen_sw_tot(i),j_m2_to_h*scale*dt*fluxes%sw(i,j),&
569  g%geoLonT(i,j),g%geoLatT(i,j)
570  call mom_error(warning,mesg)
571  endif
572  endif
573 
574  ! remove penetrative portion of the SW that is NOT absorbed within a
575  ! tiny layer at the top of the ocean.
576  net_heat(i) = net_heat(i) - pen_sw_tot(i)
577  !BGR-Jul 5, 2017{
578  !Repeat above code for 'rate' term
579  if (do_nhr) net_heat_rate(i) = net_heat_rate(i) - pen_sw_tot_rate(i)
580  !}BGR
581 
582  ! diagnose non-downwelling SW
583  if (present(nonpensw)) then
584  nonpensw(i) = scale * dt * j_m2_to_h * fluxes%sw(i,j) - pen_sw_tot(i)
585  endif
586 
587  ! Salt fluxes
588  net_salt(i) = 0.0
589  if (do_nsr) net_salt_rate(i) = 0.0
590  ! Convert salt_flux from kg (salt)/(m^2 * s) to
591  ! Boussinesq: (ppt * m)
592  ! non-Bouss: (g/m^2)
593  if (ASSOCIATED(fluxes%salt_flux)) then
594  net_salt(i) = (scale * dt * (1000.0 * fluxes%salt_flux(i,j))) * gv%kg_m2_to_H
595  !BGR-Jul 5, 2017{
596  !Repeat above code for 'rate' term
597  if (do_nsr) net_salt_rate(i) = (scale * 1. * (1000.0 * fluxes%salt_flux(i,j))) * gv%kg_m2_to_H
598  !}BGR
599  endif
600 
601  ! Diagnostics follow...
602  if (calculate_diags) then
603 
604  ! Store Net_salt for unknown reason?
605  if (ASSOCIATED(fluxes%salt_flux)) then
606  if (calculate_diags) fluxes%netSalt(i,j) = net_salt(i)
607  endif
608 
609  ! Initialize heat_content_massin that is diagnosed in mixedlayer_convection or
610  ! applyBoundaryFluxes such that the meaning is as the sum of all incoming components.
611  if (ASSOCIATED(fluxes%heat_content_massin)) then
612  if (aggregate_fw_forcing) then
613  if (netmassinout(i) > 0.0) then ! net is "in"
614  fluxes%heat_content_massin(i,j) = -fluxes%C_p * netmassout(i) * t(i,1) * gv%H_to_kg_m2 / dt
615  else ! net is "out"
616  fluxes%heat_content_massin(i,j) = fluxes%C_p * ( netmassinout(i) - netmassout(i) ) * t(i,1) * gv%H_to_kg_m2 / dt
617  endif
618  else
619  fluxes%heat_content_massin(i,j) = 0.
620  endif
621  endif
622 
623  ! Initialize heat_content_massout that is diagnosed in mixedlayer_convection or
624  ! applyBoundaryFluxes such that the meaning is as the sum of all outgoing components.
625  if (ASSOCIATED(fluxes%heat_content_massout)) then
626  if (aggregate_fw_forcing) then
627  if (netmassinout(i) > 0.0) then ! net is "in"
628  fluxes%heat_content_massout(i,j) = fluxes%C_p * netmassout(i) * t(i,1) * gv%H_to_kg_m2 / dt
629  else ! net is "out"
630  fluxes%heat_content_massout(i,j) = -fluxes%C_p * ( netmassinout(i) - netmassout(i) ) * t(i,1) * gv%H_to_kg_m2 / dt
631  endif
632  else
633  fluxes%heat_content_massout(i,j) = 0.0
634  endif
635  endif
636 
637  ! smg: we should remove sea ice melt from lprec!!!
638  ! fluxes%lprec > 0 means ocean gains mass via liquid precipitation and/or sea ice melt.
639  ! When atmosphere does not provide heat of this precipitation, the ocean assumes
640  ! it enters the ocean at the SST.
641  ! fluxes%lprec < 0 means ocean loses mass via sea ice formation. As we do not yet know
642  ! the layer at which this mass is removed, we cannot compute it heat content. We must
643  ! wait until MOM_diabatic_driver.F90.
644  if (ASSOCIATED(fluxes%heat_content_lprec)) then
645  if (fluxes%lprec(i,j) > 0.0) then
646  fluxes%heat_content_lprec(i,j) = fluxes%C_p*fluxes%lprec(i,j)*t(i,1)
647  else
648  fluxes%heat_content_lprec(i,j) = 0.0
649  endif
650  endif
651 
652  ! fprec SHOULD enter ocean at 0degC if atmos model does not provide fprec heat content.
653  ! However, we need to adjust netHeat above to reflect the difference between 0decC and SST
654  ! and until we do so fprec is treated like lprec and enters at SST. -AJA
655  if (ASSOCIATED(fluxes%heat_content_fprec)) then
656  if (fluxes%fprec(i,j) > 0.0) then
657  fluxes%heat_content_fprec(i,j) = fluxes%C_p*fluxes%fprec(i,j)*t(i,1)
658  else
659  fluxes%heat_content_fprec(i,j) = 0.0
660  endif
661  endif
662 
663  ! virtual precip associated with salinity restoring
664  ! vprec > 0 means add water to ocean, assumed to be at SST
665  ! vprec < 0 means remove water from ocean; set heat_content_vprec in MOM_diabatic_driver.F90
666  if (ASSOCIATED(fluxes%heat_content_vprec)) then
667  if (fluxes%vprec(i,j) > 0.0) then
668  fluxes%heat_content_vprec(i,j) = fluxes%C_p*fluxes%vprec(i,j)*t(i,1)
669  else
670  fluxes%heat_content_vprec(i,j) = 0.0
671  endif
672  endif
673 
674  ! fluxes%evap < 0 means ocean loses mass due to evaporation.
675  ! Evaporation leaves ocean surface at a temperature that has yet to be determined,
676  ! since we do not know the precise layer that the water evaporates. We therefore
677  ! compute fluxes%heat_content_massout at the relevant point inside MOM_diabatic_driver.F90.
678  ! fluxes%evap > 0 means ocean gains moisture via condensation.
679  ! Condensation is assumed to drop into the ocean at the SST, just like lprec.
680  if (ASSOCIATED(fluxes%heat_content_cond)) then
681  if (fluxes%evap(i,j) > 0.0) then
682  fluxes%heat_content_cond(i,j) = fluxes%C_p*fluxes%evap(i,j)*t(i,1)
683  else
684  fluxes%heat_content_cond(i,j) = 0.0
685  endif
686  endif
687 
688  ! Liquid runoff enters ocean at SST if land model does not provide runoff heat content.
689  if (.not. useriverheatcontent) then
690  if (ASSOCIATED(fluxes%lrunoff) .and. ASSOCIATED(fluxes%heat_content_lrunoff)) then
691  fluxes%heat_content_lrunoff(i,j) = fluxes%C_p*fluxes%lrunoff(i,j)*t(i,1)
692  endif
693  endif
694 
695  ! Icebergs enter ocean at SST if land model does not provide calving heat content.
696  if (.not. usecalvingheatcontent) then
697  if (ASSOCIATED(fluxes%frunoff) .and. ASSOCIATED(fluxes%heat_content_frunoff)) then
698  fluxes%heat_content_frunoff(i,j) = fluxes%C_p*fluxes%frunoff(i,j)*t(i,1)
699  endif
700  endif
701 
702  endif ! calculate_diags
703 
704  enddo ! i-loop
705 
706 end subroutine extractfluxes1d
707 
708 
709 !> 2d wrapper for 1d extract fluxes from surface fluxes type.
710 !! This subroutine extracts fluxes from the surface fluxes type. It multiplies the
711 !! fluxes by dt, so that the result is an accumulation of the fluxes over a time step.
712 subroutine extractfluxes2d(G, GV, fluxes, optics, nsw, dt, &
713  DepthBeforeScalingFluxes, useRiverHeatContent, useCalvingHeatContent, &
714  h, T, netMassInOut, netMassOut, net_heat, Net_salt, Pen_SW_bnd, tv, &
715  aggregate_FW_forcing)
717  type(ocean_grid_type), intent(in) :: G !< ocean grid structure
718  type(verticalgrid_type), intent(in) :: GV !< ocean vertical grid structure
719  type(forcing), intent(inout) :: fluxes !< structure containing pointers to forcing.
720  type(optics_type), pointer :: optics !< pointer to optics
721  integer, intent(in) :: nsw !< number of bands of penetrating SW
722  real, intent(in) :: dt !< time step in seconds
723  real, intent(in) :: DepthBeforeScalingFluxes !< min ocean depth before scale away fluxes (H)
724  logical, intent(in) :: useRiverHeatContent !< logical for river heat content
725  logical, intent(in) :: useCalvingHeatContent !< logical for calving heat content
726  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< layer thickness (in H units)
727  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: T !< layer temperatures (deg C)
728  real, dimension(SZI_(G),SZJ_(G)), intent(out) :: netMassInOut !< net mass flux (non-Bouss) or volume flux
729  !! (if Bouss) of water in/out of ocean over
730  !! a time step (H units)
731  real, dimension(SZI_(G),SZJ_(G)), intent(out) :: netMassOut !< net mass flux (non-Bouss) or volume flux
732  !! (if Bouss) of water leaving ocean surface
733  !! over a time step (H units).
734  real, dimension(SZI_(G),SZJ_(G)), intent(out) :: net_heat !< net heat at the surface accumulated over a
735  !! time step associated with coupler + restore.
736  !! Exclude two terms from net_heat:
737  !! (1) downwelling (penetrative) SW,
738  !! (2) evaporation heat content,
739  !! (since do not yet know temperature of evap).
740  !! Units of net_heat are (K * H).
741  real, dimension(SZI_(G),SZJ_(G)), intent(out) :: net_salt !< surface salt flux into the ocean accumulated
742  !! over a time step (ppt * H)
743  real, dimension(:,:,:), intent(out) :: pen_SW_bnd !< penetrating shortwave flux, split into bands.
744  !! Units (deg K * H) & array size nsw x SZI_(G),
745  !! where nsw=number of SW bands in pen_SW_bnd.
746  !! This heat flux is not in net_heat.
747  type(thermo_var_ptrs), intent(inout) :: tv !< structure containing pointers to available
748  !! thermodynamic fields. Here it is used to keep
749  !! track of the heat flux associated with net
750  !! mass fluxes into the ocean.
751  logical, intent(in) :: aggregate_FW_forcing !< For determining how to aggregate the forcing.
752 
753 
754  integer :: j
755 !$OMP parallel do default(none) shared(G, GV, fluxes, optics, nsw,dt,DepthBeforeScalingFluxes, &
756 !$OMP useRiverHeatContent, useCalvingHeatContent, &
757 !$OMP h,T,netMassInOut,netMassOut,Net_heat,Net_salt,Pen_SW_bnd,tv, &
758 !$OMP aggregate_FW_forcing)
759  do j=g%jsc, g%jec
760  call extractfluxes1d(g, gv, fluxes, optics, nsw, j, dt, &
761  depthbeforescalingfluxes, useriverheatcontent, usecalvingheatcontent,&
762  h(:,j,:), t(:,j,:), netmassinout(:,j), netmassout(:,j), &
763  net_heat(:,j), net_salt(:,j), pen_sw_bnd(:,:,j), tv, aggregate_fw_forcing)
764  enddo
765 
766 end subroutine extractfluxes2d
767 
768 
769 !> This routine calculates surface buoyancy flux by adding up the heat, FW & salt fluxes.
770 !! These are actual fluxes, with units of stuff per time. Setting dt=1 in the call to
771 !! extractFluxes routine allows us to get "stuf per time" rather than the time integrated
772 !! fluxes needed in other routines that call extractFluxes.
773 subroutine calculatebuoyancyflux1d(G, GV, fluxes, optics, h, Temp, Salt, tv, j, &
774  buoyancyFlux, netHeatMinusSW, netSalt, skip_diags)
775  type(ocean_grid_type), intent(in) :: G !< ocean grid
776  type(verticalgrid_type), intent(in) :: GV !< ocean vertical grid structure
777  type(forcing), intent(inout) :: fluxes !< surface fluxes
778  type(optics_type), pointer :: optics !< penetrating SW optics
779  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< layer thickness (H)
780  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: Temp !< prognostic temp(deg C)
781  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: Salt !< salinity (ppt)
782  type(thermo_var_ptrs), intent(inout) :: tv !< thermodynamics type
783  integer, intent(in) :: j !< j-row to work on
784  real, dimension(SZI_(G),SZK_(G)+1), intent(inout) :: buoyancyFlux !< buoyancy flux (m^2/s^3)
785  real, dimension(SZI_(G)), intent(inout) :: netHeatMinusSW !< surf Heat flux (K H/s)
786  real, dimension(SZI_(G)), intent(inout) :: netSalt !< surf salt flux (ppt H/s)
787  logical, optional, intent(in) :: skip_diags !< If present and true, skip calculating
788  !! diagnostics inside extractFluxes1d()
789  ! local variables
790  integer :: nsw, start, npts, k
791  real, parameter :: dt = 1. ! to return a rate from extractFluxes1d
792  real, dimension( SZI_(G) ) :: netH ! net FW flux (m/s for Bouss)
793  real, dimension( SZI_(G) ) :: netEvap ! net FW flux leaving ocean via evaporation (m/s for Bouss)
794  real, dimension( SZI_(G) ) :: netHeat ! net temp flux (K m/s)
795  real, dimension( optics%nbands, SZI_(G) ) :: penSWbnd ! SW penetration bands
796  real, dimension( SZI_(G) ) :: pressure ! pressurea the surface (Pa)
797  real, dimension( SZI_(G) ) :: dRhodT ! density partial derivative wrt temp
798  real, dimension( SZI_(G) ) :: dRhodS ! density partial derivative wrt saln
799  real, dimension(SZI_(G),SZK_(G)+1) :: netPen
800 
801  logical :: useRiverHeatContent
802  logical :: useCalvingHeatContent
803  real :: depthBeforeScalingFluxes, GoRho
804  real :: H_limit_fluxes
805 
806  nsw = optics%nbands
807 
808  ! smg: what do we do when have heat fluxes from calving and river?
809  useriverheatcontent = .false.
810  usecalvingheatcontent = .false.
811 
812  depthbeforescalingfluxes = max( gv%Angstrom, 1.e-30*gv%m_to_H )
813  pressure(:) = 0. ! Ignore atmospheric pressure
814  gorho = gv%g_Earth / gv%Rho0
815  start = 1 + g%isc - g%isd
816  npts = 1 + g%iec - g%isc
817 
818  h_limit_fluxes = depthbeforescalingfluxes
819 
820  ! The surface forcing is contained in the fluxes type.
821  ! We aggregate the thermodynamic forcing for a time step into the following:
822  ! netH = water (H units/s) added/removed via surface fluxes
823  ! netHeat = heat (degC * H/s) via surface fluxes
824  ! netSalt = salt ( g(salt)/m2 for non-Bouss and ppt*m for Bouss /s) via surface fluxes
825  ! Note that unlike other calls to extractFLuxes1d() that return the time-integrated flux
826  ! this call returns the rate because dt=1
827  call extractfluxes1d(g, gv, fluxes, optics, nsw, j, dt, &
828  depthbeforescalingfluxes, useriverheatcontent, usecalvingheatcontent, &
829  h(:,j,:), temp(:,j,:), neth, netevap, netheatminussw, &
830  netsalt, penswbnd, tv, .false., skip_diags=skip_diags)
831 
832  ! Sum over bands and attenuate as a function of depth
833  ! netPen is the netSW as a function of depth
834  call sumswoverbands(g, gv, h(:,j,:), optics%opacity_band(:,:,j,:), nsw, j, dt, &
835  h_limit_fluxes, .true., penswbnd, netpen)
836 
837  ! Density derivatives
838  call calculate_density_derivs(temp(:,j,1), salt(:,j,1), pressure, &
839  drhodt, drhods, start, npts, tv%eqn_of_state)
840 
841  ! Adjust netSalt to reflect dilution effect of FW flux
842  netsalt(g%isc:g%iec) = netsalt(g%isc:g%iec) - salt(g%isc:g%iec,j,1) * neth(g%isc:g%iec) * gv%H_to_m ! ppt H/s
843 
844  ! Add in the SW heating for purposes of calculating the net
845  ! surface buoyancy flux affecting the top layer.
846  !netHeat(:) = netHeatMinusSW(:) + sum( penSWbnd, dim=1 )
847  netheat(g%isc:g%iec) = netheatminussw(g%isc:g%iec) + netpen(g%isc:g%iec,1) ! K H/s
848 
849  ! Convert to a buoyancy flux, excluding penetrating SW heating
850  buoyancyflux(g%isc:g%iec,1) = - gorho * ( drhods(g%isc:g%iec) * netsalt(g%isc:g%iec) + &
851  drhodt(g%isc:g%iec) * netheat(g%isc:g%iec) ) * gv%H_to_m ! m^2/s^3
852  ! We also have a penetrative buoyancy flux associated with penetrative SW
853  do k=2, g%ke+1
854  buoyancyflux(g%isc:g%iec,k) = - gorho * ( drhodt(g%isc:g%iec) * netpen(g%isc:g%iec,k) ) * gv%H_to_m ! m^2/s^3
855  enddo
856 
857 end subroutine calculatebuoyancyflux1d
858 
859 
860 !> Calculates surface buoyancy flux by adding up the heat, FW and salt fluxes,
861 !! for 2d arrays. This is a wrapper for calculateBuoyancyFlux1d.
862 subroutine calculatebuoyancyflux2d(G, GV, fluxes, optics, h, Temp, Salt, tv, &
863  buoyancyFlux, netHeatMinusSW, netSalt, skip_diags)
864  type(ocean_grid_type), intent(in) :: G !< ocean grid
865  type(verticalgrid_type), intent(in) :: GV !< ocean vertical grid structure
866  type(forcing), intent(inout) :: fluxes !< surface fluxes
867  type(optics_type), pointer :: optics !< SW ocean optics
868  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< layer thickness (H)
869  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: Temp !< temperature (deg C)
870  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: Salt !< salinity (ppt)
871  type(thermo_var_ptrs), intent(inout) :: tv !< thermodynamics type
872  real, dimension(SZI_(G),SZJ_(G),SZK_(G)+1), intent(inout) :: buoyancyFlux !< buoy flux (m^2/s^3)
873  real, dimension(SZI_(G),SZJ_(G)), optional, intent(inout) :: netHeatMinusSW !< surf temp flux (K H)
874  real, dimension(SZI_(G),SZJ_(G)), optional, intent(inout) :: netSalt !< surf salt flux (ppt H)
875  logical, optional, intent(in) :: skip_diags !< If present and true, skip calculating
876  !! diagnostics inside extractFluxes1d()
877  ! local variables
878  real, dimension( SZI_(G) ) :: netT ! net temperature flux (K m/s)
879  real, dimension( SZI_(G) ) :: netS ! net saln flux (ppt m/s)
880  integer :: j
881 
882  nett(g%isc:g%iec) = 0. ; nets(g%isc:g%iec) = 0.
883 
884 !$OMP parallel do default(none) shared(G,GV,fluxes,optics,h,Temp,Salt,tv,buoyancyFlux,&
885 !$OMP netHeatMinusSW,netSalt,skip_diags) &
886 !$OMP firstprivate(netT,netS)
887  do j = g%jsc, g%jec
888  call calculatebuoyancyflux1d(g, gv, fluxes, optics, h, temp, salt, tv, j, buoyancyflux(:,j,:), &
889  nett, nets, skip_diags=skip_diags)
890  if (present(netheatminussw)) netheatminussw(g%isc:g%iec,j) = nett(g%isc:g%iec)
891  if (present(netsalt)) netsalt(g%isc:g%iec,j) = nets(g%isc:g%iec)
892  enddo ! j
893 
894 end subroutine calculatebuoyancyflux2d
895 
896 
897 !> Write out chksums for basic state variables.
898 subroutine mom_forcing_chksum(mesg, fluxes, G, haloshift)
899  character(len=*), intent(in) :: mesg !< message
900  type(forcing), intent(in) :: fluxes !< fluxes type
901  type(ocean_grid_type), intent(in) :: G !< grid type
902  integer, optional, intent(in) :: haloshift !< shift in halo
903 
904  integer :: is, ie, js, je, nz, hshift
905  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
906 
907  hshift=1; if (present(haloshift)) hshift=haloshift
908 
909  ! Note that for the chksum calls to be useful for reproducing across PE
910  ! counts, there must be no redundant points, so all variables use is..ie
911  ! and js...je as their extent.
912  if (associated(fluxes%taux) .and. associated(fluxes%tauy)) &
913  call uvchksum(mesg//" fluxes%tau[xy]", fluxes%taux, fluxes%tauy, g%HI, &
914  haloshift=hshift, symmetric=.true.)
915  if (associated(fluxes%ustar)) &
916  call hchksum(fluxes%ustar, mesg//" fluxes%ustar",g%HI,haloshift=hshift)
917  if (associated(fluxes%buoy)) &
918  call hchksum(fluxes%buoy, mesg//" fluxes%buoy ",g%HI,haloshift=hshift)
919  if (associated(fluxes%sw)) &
920  call hchksum(fluxes%sw, mesg//" fluxes%sw",g%HI,haloshift=hshift)
921  if (associated(fluxes%sw_vis_dir)) &
922  call hchksum(fluxes%sw_vis_dir, mesg//" fluxes%sw_vis_dir",g%HI,haloshift=hshift)
923  if (associated(fluxes%sw_vis_dif)) &
924  call hchksum(fluxes%sw_vis_dif, mesg//" fluxes%sw_vis_dif",g%HI,haloshift=hshift)
925  if (associated(fluxes%sw_nir_dir)) &
926  call hchksum(fluxes%sw_nir_dir, mesg//" fluxes%sw_nir_dir",g%HI,haloshift=hshift)
927  if (associated(fluxes%sw_nir_dif)) &
928  call hchksum(fluxes%sw_nir_dif, mesg//" fluxes%sw_nir_dif",g%HI,haloshift=hshift)
929  if (associated(fluxes%lw)) &
930  call hchksum(fluxes%lw, mesg//" fluxes%lw",g%HI,haloshift=hshift)
931  if (associated(fluxes%latent)) &
932  call hchksum(fluxes%latent, mesg//" fluxes%latent",g%HI,haloshift=hshift)
933  if (associated(fluxes%latent_evap_diag)) &
934  call hchksum(fluxes%latent_evap_diag, mesg//" fluxes%latent_evap_diag",g%HI,haloshift=hshift)
935  if (associated(fluxes%latent_fprec_diag)) &
936  call hchksum(fluxes%latent_fprec_diag, mesg//" fluxes%latent_fprec_diag",g%HI,haloshift=hshift)
937  if (associated(fluxes%latent_frunoff_diag)) &
938  call hchksum(fluxes%latent_frunoff_diag, mesg//" fluxes%latent_frunoff_diag",g%HI,haloshift=hshift)
939  if (associated(fluxes%sens)) &
940  call hchksum(fluxes%sens, mesg//" fluxes%sens",g%HI,haloshift=hshift)
941  if (associated(fluxes%evap)) &
942  call hchksum(fluxes%evap, mesg//" fluxes%evap",g%HI,haloshift=hshift)
943  if (associated(fluxes%lprec)) &
944  call hchksum(fluxes%lprec, mesg//" fluxes%lprec",g%HI,haloshift=hshift)
945  if (associated(fluxes%fprec)) &
946  call hchksum(fluxes%fprec, mesg//" fluxes%fprec",g%HI,haloshift=hshift)
947  if (associated(fluxes%vprec)) &
948  call hchksum(fluxes%vprec, mesg//" fluxes%vprec",g%HI,haloshift=hshift)
949  if (associated(fluxes%seaice_melt)) &
950  call hchksum(fluxes%seaice_melt, mesg//" fluxes%seaice_melt",g%HI,haloshift=hshift)
951  if (associated(fluxes%p_surf)) &
952  call hchksum(fluxes%p_surf, mesg//" fluxes%p_surf",g%HI,haloshift=hshift)
953  if (associated(fluxes%salt_flux)) &
954  call hchksum(fluxes%salt_flux, mesg//" fluxes%salt_flux",g%HI,haloshift=hshift)
955  if (associated(fluxes%TKE_tidal)) &
956  call hchksum(fluxes%TKE_tidal, mesg//" fluxes%TKE_tidal",g%HI,haloshift=hshift)
957  if (associated(fluxes%ustar_tidal)) &
958  call hchksum(fluxes%ustar_tidal, mesg//" fluxes%ustar_tidal",g%HI,haloshift=hshift)
959  if (associated(fluxes%lrunoff)) &
960  call hchksum(fluxes%lrunoff, mesg//" fluxes%lrunoff",g%HI,haloshift=hshift)
961  if (associated(fluxes%frunoff)) &
962  call hchksum(fluxes%frunoff, mesg//" fluxes%frunoff",g%HI,haloshift=hshift)
963  if (associated(fluxes%heat_content_lrunoff)) &
964  call hchksum(fluxes%heat_content_lrunoff, mesg//" fluxes%heat_content_lrunoff",g%HI,haloshift=hshift)
965  if (associated(fluxes%heat_content_frunoff)) &
966  call hchksum(fluxes%heat_content_frunoff, mesg//" fluxes%heat_content_frunoff",g%HI,haloshift=hshift)
967  if (associated(fluxes%heat_content_lprec)) &
968  call hchksum(fluxes%heat_content_lprec, mesg//" fluxes%heat_content_lprec",g%HI,haloshift=hshift)
969  if (associated(fluxes%heat_content_fprec)) &
970  call hchksum(fluxes%heat_content_fprec, mesg//" fluxes%heat_content_fprec",g%HI,haloshift=hshift)
971  if (associated(fluxes%heat_content_cond)) &
972  call hchksum(fluxes%heat_content_cond, mesg//" fluxes%heat_content_cond",g%HI,haloshift=hshift)
973  if (associated(fluxes%heat_content_massout)) &
974  call hchksum(fluxes%heat_content_massout, mesg//" fluxes%heat_content_massout",g%HI,haloshift=hshift)
975 end subroutine mom_forcing_chksum
976 
977 
978 !> Write out values of the fluxes arrays at the i,j location. This is a debugging tool.
979 subroutine forcing_singlepointprint(fluxes, G, i, j, mesg)
980  type(forcing), intent(in) :: fluxes !< Fluxes type
981  type(ocean_grid_type), intent(in) :: G !< Grid type
982  character(len=*), intent(in) :: mesg !< Message
983  integer, intent(in) :: i !< i-index
984  integer, intent(in) :: j !< j-index
985 
986  write(0,'(2a)') 'MOM_forcing_type, forcing_SinglePointPrint: Called from ',mesg
987  write(0,'(a,2es15.3)') 'MOM_forcing_type, forcing_SinglePointPrint: lon,lat = ',g%geoLonT(i,j),g%geoLatT(i,j)
988  call locmsg(fluxes%taux,'taux')
989  call locmsg(fluxes%tauy,'tauy')
990  call locmsg(fluxes%ustar,'ustar')
991  call locmsg(fluxes%buoy,'buoy')
992  call locmsg(fluxes%sw,'sw')
993  call locmsg(fluxes%sw_vis_dir,'sw_vis_dir')
994  call locmsg(fluxes%sw_vis_dif,'sw_vis_dif')
995  call locmsg(fluxes%sw_nir_dir,'sw_nir_dir')
996  call locmsg(fluxes%sw_nir_dif,'sw_nir_dif')
997  call locmsg(fluxes%lw,'lw')
998  call locmsg(fluxes%latent,'latent')
999  call locmsg(fluxes%latent_evap_diag,'latent_evap_diag')
1000  call locmsg(fluxes%latent_fprec_diag,'latent_fprec_diag')
1001  call locmsg(fluxes%latent_frunoff_diag,'latent_frunoff_diag')
1002  call locmsg(fluxes%sens,'sens')
1003  call locmsg(fluxes%evap,'evap')
1004  call locmsg(fluxes%lprec,'lprec')
1005  call locmsg(fluxes%fprec,'fprec')
1006  call locmsg(fluxes%vprec,'vprec')
1007  call locmsg(fluxes%seaice_melt,'seaice_melt')
1008  call locmsg(fluxes%p_surf,'p_surf')
1009  call locmsg(fluxes%salt_flux,'salt_flux')
1010  call locmsg(fluxes%TKE_tidal,'TKE_tidal')
1011  call locmsg(fluxes%ustar_tidal,'ustar_tidal')
1012  call locmsg(fluxes%lrunoff,'lrunoff')
1013  call locmsg(fluxes%frunoff,'frunoff')
1014  call locmsg(fluxes%heat_content_lrunoff,'heat_content_lrunoff')
1015  call locmsg(fluxes%heat_content_frunoff,'heat_content_frunoff')
1016  call locmsg(fluxes%heat_content_lprec,'heat_content_lprec')
1017  call locmsg(fluxes%heat_content_fprec,'heat_content_fprec')
1018  call locmsg(fluxes%heat_content_vprec,'heat_content_vprec')
1019  call locmsg(fluxes%heat_content_cond,'heat_content_cond')
1020  call locmsg(fluxes%heat_content_cond,'heat_content_massout')
1021  contains
1022 
1023  !> Format and write a message depending on associated state of array
1024  subroutine locmsg(array,aname)
1025  real, dimension(:,:), pointer :: array !< Array to write element from
1026  character(len=*) :: aname !< Name of array
1027 
1028  if (associated(array)) then
1029  write(0,'(3a,es15.3)') 'MOM_forcing_type, forcing_SinglePointPrint: ',trim(aname),' = ',array(i,j)
1030  else
1031  write(0,'(4a)') 'MOM_forcing_type, forcing_SinglePointPrint: ',trim(aname),' is not associated.'
1032  endif
1033 
1034  end subroutine locmsg
1035 
1036 end subroutine forcing_singlepointprint
1037 
1038 
1039 !> Register members of the forcing type for diagnostics
1040 subroutine register_forcing_type_diags(Time, diag, use_temperature, handles, use_berg_fluxes)
1041  type(time_type), intent(in) :: Time !< time type
1042  type(diag_ctrl), intent(inout) :: diag !< diagnostic control type
1043  logical, intent(in) :: use_temperature !< True if T/S are in use
1044  type(forcing_diags), intent(inout) :: handles !< handles for diagnostics
1045  logical, optional, intent(in) :: use_berg_fluxes !< If true, allow iceberg flux diagnostics
1046 
1047  ! Clock for forcing diagnostics
1048  handles%id_clock_forcing=cpu_clock_id('(Ocean forcing diagnostics)', grain=clock_routine)
1049 
1050 
1051  handles%id_taux = register_diag_field('ocean_model', 'taux', diag%axesCu1, time, &
1052  'Zonal surface stress from ocean interactions with atmos and ice', 'Pascal',&
1053  standard_name='surface_downward_x_stress', cmor_field_name='tauuo', &
1054  cmor_units='N m-2', cmor_long_name='Surface Downward X Stress', &
1055  cmor_standard_name='surface_downward_x_stress')
1056 
1057  handles%id_tauy = register_diag_field('ocean_model', 'tauy', diag%axesCv1, time, &
1058  'Meridional surface stress ocean interactions with atmos and ice', 'Pascal',&
1059  standard_name='surface_downward_y_stress', cmor_field_name='tauvo', &
1060  cmor_units='N m-2', cmor_long_name='Surface Downward Y Stress', &
1061  cmor_standard_name='surface_downward_y_stress')
1062 
1063  handles%id_ustar = register_diag_field('ocean_model', 'ustar', diag%axesT1, time, &
1064  'Surface friction velocity = [(gustiness + tau_magnitude)/rho0]^(1/2)', 'meter second-1')
1065 
1066  if (present(use_berg_fluxes)) then
1067  if (use_berg_fluxes) then
1068  handles%id_ustar_berg = register_diag_field('ocean_model', 'ustar_berg', diag%axesT1, time, &
1069  'Friction velocity below iceberg ', 'meter second-1')
1070 
1071  handles%id_area_berg = register_diag_field('ocean_model', 'area_berg', diag%axesT1, time, &
1072  'Area of grid cell covered by iceberg ', 'm2/m2')
1073 
1074  handles%id_mass_berg = register_diag_field('ocean_model', 'mass_berg', diag%axesT1, time, &
1075  'Mass of icebergs ', 'kg/m2')
1076 
1077  handles%id_ustar_ice_cover = register_diag_field('ocean_model', 'ustar_ice_cover', diag%axesT1, time, &
1078  'Friction velocity below iceberg and ice shelf together', 'meter second-1')
1079 
1080  handles%id_frac_ice_cover = register_diag_field('ocean_model', 'frac_ice_cover', diag%axesT1, time, &
1081  'Area of grid cell below iceberg and ice shelf together ', 'm2/m2')
1082  endif
1083  endif
1084 
1085  handles%id_psurf = register_diag_field('ocean_model', 'p_surf', diag%axesT1, time, &
1086  'Pressure at ice-ocean or atmosphere-ocean interface', 'Pascal', cmor_field_name='pso',&
1087  cmor_long_name='Sea Water Pressure at Sea Water Surface', cmor_units='Pa', &
1088  cmor_standard_name='sea_water_pressure_at_sea_water_surface')
1089 
1090  handles%id_TKE_tidal = register_diag_field('ocean_model', 'TKE_tidal', diag%axesT1, time, &
1091  'Tidal source of BBL mixing', 'Watt/m^2')
1092 
1093  if (.not. use_temperature) then
1094  handles%id_buoy = register_diag_field('ocean_model', 'buoy', diag%axesT1, time, &
1095  'Buoyancy forcing', 'meter^2/second^3')
1096  return
1097  endif
1098 
1099 
1100  !===============================================================
1101  ! surface mass flux maps
1102 
1103  handles%id_prcme = register_diag_field('ocean_model', 'PRCmE', diag%axesT1, time, &
1104  'Net surface water flux (precip+melt+lrunoff+ice calving-evap)', 'kilogram meter-2 second-1',&
1105  standard_name='water_flux_into_sea_water', cmor_field_name='wfo', cmor_units='kg m-2 s-1', &
1106  cmor_standard_name='water_flux_into_sea_water',cmor_long_name='Water Flux Into Sea Water')
1107 
1108  handles%id_evap = register_diag_field('ocean_model', 'evap', diag%axesT1, time, &
1109  'Evaporation/condensation at ocean surface (evaporation is negative)', 'kilogram meter-2 second-1',&
1110  standard_name='water_evaporation_flux', cmor_field_name='evs', cmor_units='kg m-2 s-1', &
1111  cmor_standard_name='water_evaporation_flux', &
1112  cmor_long_name='Water Evaporation Flux Where Ice Free Ocean over Sea')
1113 
1114  ! smg: seaice_melt field requires updates to the sea ice model
1115  !handles%id_seaice_melt = register_diag_field('ocean_model', 'seaice_melt', &
1116  ! diag%axesT1, Time, 'water flux to ocean from sea ice melt(> 0) or form(< 0)', &
1117  ! 'kilogram/(meter^2 * second)', &
1118  ! standard_name='water_flux_into_sea_water_due_to_sea_ice_thermodynamics', &
1119  ! cmor_field_name='fsitherm', cmor_units='kg m-2 s-1', &
1120  ! cmor_standard_name='water_flux_into_sea_water_due_to_sea_ice_thermodynamics',&
1121  ! cmor_long_name='water flux to ocean from sea ice melt(> 0) or form(< 0)')
1122 
1123  handles%id_precip = register_diag_field('ocean_model', 'precip', diag%axesT1, time, &
1124  'Liquid + frozen precipitation into ocean', 'kilogram/(meter^2 * second)')
1125 
1126  handles%id_fprec = register_diag_field('ocean_model', 'fprec', diag%axesT1, time, &
1127  'Frozen precipitation into ocean', 'kilogram meter-2 second-1', &
1128  standard_name='snowfall_flux', cmor_field_name='prsn', cmor_units='kg m-2 s-1', &
1129  cmor_standard_name='snowfall_flux', cmor_long_name='Snowfall Flux where Ice Free Ocean over Sea')
1130 
1131  handles%id_lprec = register_diag_field('ocean_model', 'lprec', diag%axesT1, time, &
1132  'Liquid precipitation into ocean', 'kilogram/(meter^2 * second)', &
1133  standard_name='rainfall_flux', &
1134  cmor_field_name='prlq', cmor_units='kg m-2 s-1', cmor_standard_name='rainfall_flux',&
1135  cmor_long_name='Rainfall Flux where Ice Free Ocean over Sea')
1136 
1137  handles%id_vprec = register_diag_field('ocean_model', 'vprec', diag%axesT1, time, &
1138  'Virtual liquid precip into ocean due to SSS restoring', 'kilogram/(meter^2 second)')
1139 
1140  handles%id_frunoff = register_diag_field('ocean_model', 'frunoff', diag%axesT1, time, &
1141  'Frozen runoff (calving) and iceberg melt into ocean', 'kilogram/(meter^2 second)',&
1142  standard_name='water_flux_into_sea_water_from_icebergs', &
1143  cmor_field_name='ficeberg', cmor_units='kg m-2 s-1', &
1144  cmor_standard_name='water_flux_into_sea_water_from_icebergs', &
1145  cmor_long_name='Water Flux into Seawater from Icebergs')
1146 
1147  handles%id_lrunoff = register_diag_field('ocean_model', 'lrunoff', diag%axesT1, time, &
1148  'Liquid runoff (rivers) into ocean', 'kilogram meter-2 second-1', &
1149  standard_name='water_flux_into_sea_water_from_rivers', cmor_field_name='friver', &
1150  cmor_units='kg m-2 s-1', cmor_standard_name='water_flux_into_sea_water_from_rivers', &
1151  cmor_long_name='Water Flux into Sea Water From Rivers')
1152 
1153  handles%id_net_massout = register_diag_field('ocean_model', 'net_massout', diag%axesT1, time, &
1154  'Net mass leaving the ocean due to evaporation, seaice formation', 'kilogram meter-2 second-1')
1155 
1156  handles%id_net_massin = register_diag_field('ocean_model', 'net_massin', diag%axesT1, time, &
1157  'Net mass entering ocean due to precip, runoff, ice melt', 'kilogram meter-2 second-1')
1158 
1159  handles%id_massout_flux = register_diag_field('ocean_model', 'massout_flux', diag%axesT1, time, &
1160  'Net mass flux of freshwater out of the ocean (used in the boundary flux calculation)', &
1161  'kilogram meter-2')
1162 
1163  handles%id_massin_flux = register_diag_field('ocean_model', 'massin_flux', diag%axesT1, time, &
1164  'Net mass flux of freshwater into the ocean (used in boundary flux calculation)', 'kilogram meter-2')
1165  !=========================================================================
1166  ! area integrated surface mass transport
1167 
1168  handles%id_total_prcme = register_scalar_field('ocean_model', 'total_PRCmE', time, diag, &
1169  long_name='Area integrated net surface water flux (precip+melt+liq runoff+ice calving-evap)',&
1170  units='kg/s', standard_name='water_flux_into_sea_water_area_integrated', &
1171  cmor_field_name='total_wfo', cmor_units='kg s-1', &
1172  cmor_standard_name='water_flux_into_sea_water_area_integrated', &
1173  cmor_long_name='Water Transport Into Sea Water Area Integrated')
1174 
1175  handles%id_total_evap = register_scalar_field('ocean_model', 'total_evap', time, diag,&
1176  long_name='Area integrated evap/condense at ocean surface', &
1177  units='kg/s', standard_name='water_evaporation_flux_area_integrated', &
1178  cmor_field_name='total_evs', cmor_units='kg s-1', &
1179  cmor_standard_name='water_evaporation_flux_area_integrated', &
1180  cmor_long_name='Evaporation Where Ice Free Ocean over Sea Area Integrated')
1181 
1182  ! seaice_melt field requires updates to the sea ice model
1183  !handles%id_total_seaice_melt = register_scalar_field('ocean_model', 'total_seaice_melt', Time, diag, &
1184  ! long_name='Area integrated sea ice melt (>0) or form (<0)', units='kg/s', &
1185  ! standard_name='water_flux_into_sea_water_due_to_sea_ice_thermodynamics_area_integrated', &
1186  ! cmor_field_name='total_fsitherm', cmor_units='kg s-1', &
1187  ! cmor_standard_name='water_flux_into_sea_water_due_to_sea_ice_thermodynamics_area_integrated', &
1188  ! cmor_long_name='Water Melt/Form from Sea Ice Area Integrated')
1189 
1190  handles%id_total_precip = register_scalar_field('ocean_model', 'total_precip', time, diag, &
1191  long_name='Area integrated liquid+frozen precip into ocean', units='kg/s')
1192 
1193  handles%id_total_fprec = register_scalar_field('ocean_model', 'total_fprec', time, diag,&
1194  long_name='Area integrated frozen precip into ocean', units='kg/s', &
1195  standard_name='snowfall_flux_area_integrated', &
1196  cmor_field_name='total_prsn', cmor_units='kg s-1', &
1197  cmor_standard_name='snowfall_flux_area_integrated', &
1198  cmor_long_name='Snowfall Flux where Ice Free Ocean over Sea Area Integrated')
1199 
1200  handles%id_total_lprec = register_scalar_field('ocean_model', 'total_lprec', time, diag,&
1201  long_name='Area integrated liquid precip into ocean', units='kg/s', &
1202  standard_name='rainfall_flux_area_integrated', &
1203  cmor_field_name='total_pr', cmor_units='kg s-1', &
1204  cmor_standard_name='rainfall_flux_area_integrated', &
1205  cmor_long_name='Rainfall Flux where Ice Free Ocean over Sea Area Integrated')
1206 
1207  handles%id_total_vprec = register_scalar_field('ocean_model', 'total_vprec', time, diag, &
1208  long_name='Area integrated virtual liquid precip due to SSS restoring', units='kg/s')
1209 
1210  handles%id_total_frunoff = register_scalar_field('ocean_model', 'total_frunoff', time, diag, &
1211  long_name='Area integrated frozen runoff (calving) & iceberg melt into ocean', units='kg/s',&
1212  cmor_field_name='total_ficeberg', cmor_units='kg s-1', &
1213  cmor_standard_name='water_flux_into_sea_water_from_icebergs_area_integrated', &
1214  cmor_long_name='Water Flux into Seawater from Icebergs Area Integrated')
1215 
1216  handles%id_total_lrunoff = register_scalar_field('ocean_model', 'total_lrunoff', time, diag,&
1217  long_name='Area integrated liquid runoff into ocean', units='kg/s', &
1218  cmor_field_name='total_friver', cmor_units='kg s-1', &
1219  cmor_standard_name='water_flux_into_sea_water_from_rivers_area_integrated', &
1220  cmor_long_name='Water Flux into Sea Water From Rivers Area Integrated')
1221 
1222  handles%id_total_net_massout = register_scalar_field('ocean_model', 'total_net_massout', time, diag, &
1223  long_name='Area integrated mass leaving ocean due to evap and seaice form', units='kg/s')
1224 
1225  handles%id_total_net_massin = register_scalar_field('ocean_model', 'total_net_massin', time, diag, &
1226  long_name='Area integrated mass entering ocean due to predip, runoff, ice melt', units='kg/s')
1227 
1228  !=========================================================================
1229  ! area averaged surface mass transport
1230 
1231  handles%id_prcme_ga = register_scalar_field('ocean_model', 'PRCmE_ga', time, diag, &
1232  long_name='Area averaged net surface water flux (precip+melt+liq runoff+ice calving-evap)',&
1233  units='kg m-2 s-1', standard_name='water_flux_into_sea_water_area_averaged', &
1234  cmor_field_name='ave_wfo', cmor_units='kg m-2 s-1', &
1235  cmor_standard_name='rainfall_flux_area_averaged', &
1236  cmor_long_name='Water Transport Into Sea Water Area Averaged')
1237 
1238  handles%id_evap_ga = register_scalar_field('ocean_model', 'evap_ga', time, diag,&
1239  long_name='Area averaged evap/condense at ocean surface', &
1240  units='kg m-2 s-1', standard_name='water_evaporation_flux_area_averaged', &
1241  cmor_field_name='ave_evs', cmor_units='kg m-2 s-1', &
1242  cmor_standard_name='water_evaporation_flux_area_averaged', &
1243  cmor_long_name='Evaporation Where Ice Free Ocean over Sea Area Averaged')
1244 
1245  handles%id_lprec_ga = register_scalar_field('ocean_model', 'lprec_ga', time, diag,&
1246  long_name='Area integrated liquid precip into ocean', units='kg m-2 s-1', &
1247  standard_name='rainfall_flux_area_averaged', &
1248  cmor_field_name='ave_pr', cmor_units='kg m-2 s-1', &
1249  cmor_standard_name='rainfall_flux_area_averaged', &
1250  cmor_long_name='Rainfall Flux where Ice Free Ocean over Sea Area Averaged')
1251 
1252  handles%id_fprec_ga = register_scalar_field('ocean_model', 'fprec_ga', time, diag,&
1253  long_name='Area integrated frozen precip into ocean', units='kg m-2 s-1', &
1254  standard_name='snowfall_flux_area_averaged', &
1255  cmor_field_name='ave_prsn', cmor_units='kg m-2 s-1', &
1256  cmor_standard_name='snowfall_flux_area_averaged', &
1257  cmor_long_name='Snowfall Flux where Ice Free Ocean over Sea Area Averaged')
1258 
1259  handles%id_precip_ga = register_scalar_field('ocean_model', 'precip_ga', time, diag, &
1260  long_name='Area averaged liquid+frozen precip into ocean', units='kg m-2 s-1')
1261 
1262  handles%id_vprec_ga = register_scalar_field('ocean_model', 'vrec_ga', time, diag, &
1263  long_name='Area averaged virtual liquid precip due to SSS restoring', units='kg m-2 s-1')
1264 
1265  !===============================================================
1266  ! surface heat flux maps
1267 
1268  handles%id_heat_content_frunoff = register_diag_field('ocean_model', 'heat_content_frunoff', &
1269  diag%axesT1, time, 'Heat content (relative to 0C) of solid runoff into ocean', 'Watt meter-2',&
1270  standard_name='temperature_flux_due_to_solid_runoff_expressed_as_heat_flux_into_sea_water')
1271 
1272  handles%id_heat_content_lrunoff = register_diag_field('ocean_model', 'heat_content_lrunoff', &
1273  diag%axesT1, time, 'Heat content (relative to 0C) of liquid runoff into ocean', 'Watt meter-2',&
1274  standard_name='temperature_flux_due_to_runoff_expressed_as_heat_flux_into_sea_water')
1275 
1276  handles%id_hfrunoffds = register_diag_field('ocean_model', 'hfrunoffds', &
1277  diag%axesT1, time, 'Heat content (relative to 0C) of liquid+solid runoff into ocean', 'W m-2',&
1278  standard_name='temperature_flux_due_to_runoff_expressed_as_heat_flux_into_sea_water')
1279 
1280  handles%id_heat_content_lprec = register_diag_field('ocean_model', 'heat_content_lprec', &
1281  diag%axesT1,time,'Heat content (relative to 0degC) of liquid precip entering ocean', &
1282  'W/m^2')
1283 
1284  handles%id_heat_content_fprec = register_diag_field('ocean_model', 'heat_content_fprec',&
1285  diag%axesT1,time,'Heat content (relative to 0degC) of frozen prec entering ocean',&
1286  'W/m^2')
1287 
1288  handles%id_heat_content_vprec = register_diag_field('ocean_model', 'heat_content_vprec', &
1289  diag%axesT1,time,'Heat content (relative to 0degC) of virtual precip entering ocean',&
1290  'Watt/m^2')
1291 
1292  handles%id_heat_content_cond = register_diag_field('ocean_model', 'heat_content_cond', &
1293  diag%axesT1,time,'Heat content (relative to 0degC) of water condensing into ocean',&
1294  'Watt/m^2')
1295 
1296  handles%id_hfrainds = register_diag_field('ocean_model', 'hfrainds', &
1297  diag%axesT1,time,'Heat content (relative to 0degC) of liquid+frozen precip entering ocean', &
1298  'W/m^2',standard_name='temperature_flux_due_to_rainfall_expressed_as_heat_flux_into_sea_water',&
1299  cmor_long_name='Heat Content (relative to 0degC) of Liquid + Frozen Precipitation')
1300 
1301  handles%id_heat_content_surfwater = register_diag_field('ocean_model', 'heat_content_surfwater',&
1302  diag%axesT1, time, &
1303  'Heat content (relative to 0degC) of net water crossing ocean surface (frozen+liquid)', &
1304  'Watt/m^2')
1305 
1306  handles%id_heat_content_massout = register_diag_field('ocean_model', 'heat_content_massout', &
1307  diag%axesT1, time,'Heat content (relative to 0degC) of net mass leaving ocean ocean via evap and ice form',&
1308  'Watt/m^2', &
1309  cmor_field_name='hfevapds', cmor_units='W m-2', &
1310  cmor_standard_name='temperature_flux_due_to_evaporation_expressed_as_heat_flux_out_of_sea_water', &
1311  cmor_long_name='Heat Content (relative to 0degC) of Water Leaving Ocean via Evaporation and Ice Formation')
1312 
1313  handles%id_heat_content_massin = register_diag_field('ocean_model', 'heat_content_massin', &
1314  diag%axesT1, time,'Heat content (relative to 0degC) of net mass entering ocean ocean',&
1315  'Watt/m^2')
1316 
1317  handles%id_net_heat_coupler = register_diag_field('ocean_model', 'net_heat_coupler', &
1318  diag%axesT1,time,'Surface ocean heat flux from SW+LW+latent+sensible (via the coupler)',&
1319  'Watt/m^2')
1320 
1321  handles%id_net_heat_surface = register_diag_field('ocean_model', 'net_heat_surface',diag%axesT1, &
1322  time,'Surface ocean heat flux from SW+LW+lat+sens+mass transfer+frazil+restore or flux adjustments', 'Watt/m^2',&
1323  standard_name='surface_downward_heat_flux_in_sea_water', cmor_field_name='hfds', &
1324  cmor_units='W m-2', cmor_standard_name='surface_downward_heat_flux_in_sea_water', &
1325  cmor_long_name='Surface ocean heat flux from SW+LW+latent+sensible+masstransfer+frazil')
1326 
1327  handles%id_sw = register_diag_field('ocean_model', 'SW', diag%axesT1, time, &
1328  'Shortwave radiation flux into ocean', 'Watt meter-2', &
1329  standard_name='net_downward_shortwave_flux_at_sea_water_surface', &
1330  cmor_field_name='rsntds', cmor_units='W m-2', &
1331  cmor_standard_name='net_downward_shortwave_flux_at_sea_water_surface', &
1332  cmor_long_name='Net Downward Shortwave Radiation at Sea Water Surface')
1333  handles%id_sw_vis = register_diag_field('ocean_model', 'sw_vis', diag%axesT1, time, &
1334  'Shortwave radiation direct and diffuse flux into the ocean in the visible band', &
1335  'Watt/m^2')
1336  handles%id_sw_nir = register_diag_field('ocean_model', 'sw_nir', diag%axesT1, time, &
1337  'Shortwave radiation direct and diffuse flux into the ocean in the near-infrared band', &
1338  'Watt/m^2')
1339 
1340  handles%id_LwLatSens = register_diag_field('ocean_model', 'LwLatSens', diag%axesT1, time, &
1341  'Combined longwave, latent, and sensible heating at ocean surface', 'Watt/m^2')
1342 
1343  handles%id_lw = register_diag_field('ocean_model', 'LW', diag%axesT1, time, &
1344  'Longwave radiation flux into ocean', 'Watt meter-2', &
1345  standard_name='surface_net_downward_longwave_flux', &
1346  cmor_field_name='rlntds', cmor_units='W m-2', &
1347  cmor_standard_name='surface_net_downward_longwave_flux', &
1348  cmor_long_name='Surface Net Downward Longwave Radiation')
1349 
1350  handles%id_lat = register_diag_field('ocean_model', 'latent', diag%axesT1, time, &
1351  'Latent heat flux into ocean due to fusion and evaporation (negative means ocean heat loss)', &
1352  'Watt meter-2', cmor_field_name='hflso', cmor_units='W m-2', &
1353  cmor_standard_name='surface_downward_latent_heat_flux', &
1354  cmor_long_name='Surface Downward Latent Heat Flux due to Evap + Melt Snow/Ice')
1355 
1356  handles%id_lat_evap = register_diag_field('ocean_model', 'latent_evap', diag%axesT1, time, &
1357  'Latent heat flux into ocean due to evaporation/condensation', 'Watt/m^2')
1358 
1359  handles%id_lat_fprec = register_diag_field('ocean_model', 'latent_fprec_diag', diag%axesT1, time,&
1360  'Latent heat flux into ocean due to melting of frozen precipitation', 'Watt meter-2', &
1361  cmor_field_name='hfsnthermds', cmor_units='W m-2', &
1362  cmor_standard_name='heat_flux_into_sea_water_due_to_snow_thermodynamics', &
1363  cmor_long_name='Latent Heat to Melt Frozen Precipitation')
1364 
1365  handles%id_lat_frunoff = register_diag_field('ocean_model', 'latent_frunoff', diag%axesT1, time, &
1366  'Latent heat flux into ocean due to melting of icebergs', 'Watt/m^2', &
1367  cmor_field_name='hfibthermds', cmor_units='W m-2', &
1368  cmor_standard_name='heat_flux_into_sea_water_due_to_iceberg_thermodynamics', &
1369  cmor_long_name='Latent Heat to Melt Frozen Runoff/Iceberg')
1370 
1371  handles%id_sens = register_diag_field('ocean_model', 'sensible', diag%axesT1, time,&
1372  'Sensible heat flux into ocean', 'Watt meter-2', &
1373  standard_name='surface_downward_sensible_heat_flux', &
1374  cmor_field_name='hfsso', cmor_units='W m-2', &
1375  cmor_standard_name='surface_downward_sensible_heat_flux', &
1376  cmor_long_name='Surface Downward Sensible Heat Flux')
1377 
1378  handles%id_heat_added = register_diag_field('ocean_model', 'heat_added', diag%axesT1, time, &
1379  'Flux Adjustment or restoring surface heat flux into ocean', 'Watt/m^2')
1380 
1381 
1382  !===============================================================
1383  ! area integrated surface heat fluxes
1384 
1385  handles%id_total_heat_content_frunoff = register_scalar_field('ocean_model', &
1386  'total_heat_content_frunoff', time, diag, &
1387  long_name='Area integrated heat content (relative to 0C) of solid runoff', &
1388  units='Watt', cmor_field_name='total_hfsolidrunoffds', cmor_units='W', &
1389  cmor_standard_name= &
1390  'temperature_flux_due_to_solid_runoff_expressed_as_heat_flux_into_sea_water_area_integrated',&
1391  cmor_long_name= &
1392  'Temperature Flux due to Solid Runoff Expressed as Heat Flux into Sea Water Area Integrated')
1393 
1394  handles%id_total_heat_content_lrunoff = register_scalar_field('ocean_model', &
1395  'total_heat_content_lrunoff', time, diag, &
1396  long_name='Area integrated heat content (relative to 0C) of liquid runoff', &
1397  units='Watt', cmor_field_name='total_hfrunoffds', cmor_units='W', &
1398  cmor_standard_name= &
1399  'temperature_flux_due_to_runoff_expressed_as_heat_flux_into_sea_water_area_integrated',&
1400  cmor_long_name= &
1401  'Temperature Flux due to Runoff Expressed as Heat Flux into Sea Water Area Integrated')
1402 
1403  handles%id_total_heat_content_lprec = register_scalar_field('ocean_model', &
1404  'total_heat_content_lprec', time, diag, &
1405  long_name='Area integrated heat content (relative to 0C) of liquid precip', &
1406  units='Watt', cmor_field_name='total_hfrainds', cmor_units='W', &
1407  cmor_standard_name= &
1408  'temperature_flux_due_to_rainfall_expressed_as_heat_flux_into_sea_water_area_integrated',&
1409  cmor_long_name= &
1410  'Temperature Flux due to Rainfall Expressed as Heat Flux into Sea Water Area Integrated')
1411 
1412  handles%id_total_heat_content_fprec = register_scalar_field('ocean_model', &
1413  'total_heat_content_fprec', time, diag, &
1414  long_name='Area integrated heat content (relative to 0C) of frozen precip',&
1415  units='Watt')
1416 
1417  handles%id_total_heat_content_vprec = register_scalar_field('ocean_model', &
1418  'total_heat_content_vprec', time, diag, &
1419  long_name='Area integrated heat content (relative to 0C) of virtual precip',&
1420  units='Watt')
1421 
1422  handles%id_total_heat_content_cond = register_scalar_field('ocean_model', &
1423  'total_heat_content_cond', time, diag, &
1424  long_name='Area integrated heat content (relative to 0C) of condensate',&
1425  units='Watt')
1426 
1427  handles%id_total_heat_content_surfwater = register_scalar_field('ocean_model', &
1428  'total_heat_content_surfwater', time, diag, &
1429  long_name='Area integrated heat content (relative to 0C) of water crossing surface',&
1430  units='Watt')
1431 
1432  handles%id_total_heat_content_massout = register_scalar_field('ocean_model', &
1433  'total_heat_content_massout', time, diag, &
1434  long_name='Area integrated heat content (relative to 0C) of water leaving ocean', &
1435  units='Watt', &
1436  cmor_field_name='total_hfevapds', cmor_units='W', &
1437  cmor_standard_name= &
1438  'temperature_flux_due_to_evaporation_expressed_as_heat_flux_out_of_sea_water_area_integrated',&
1439  cmor_long_name='Heat Flux Out of Sea Water due to Evaporating Water Area Integrated')
1440 
1441  handles%id_total_heat_content_massin = register_scalar_field('ocean_model', &
1442  'total_heat_content_massin', time, diag, &
1443  long_name='Area integrated heat content (relative to 0C) of water entering ocean',&
1444  units='Watt')
1445 
1446  handles%id_total_net_heat_coupler = register_scalar_field('ocean_model', &
1447  'total_net_heat_coupler', time, diag, &
1448  long_name='Area integrated surface heat flux from SW+LW+latent+sensible (via the coupler)',&
1449  units='Watt')
1450 
1451  handles%id_total_net_heat_surface = register_scalar_field('ocean_model', &
1452  'total_net_heat_surface', time, diag, &
1453  long_name='Area integrated surface heat flux from SW+LW+lat+sens+mass+frazil+restore or flux adjustments', &
1454  units='Watt', &
1455  cmor_field_name='total_hfds', cmor_units='W', &
1456  cmor_standard_name='surface_downward_heat_flux_in_sea_water_area_integrated', &
1457  cmor_long_name= &
1458  'Surface Ocean Heat Flux from SW+LW+latent+sensible+mass transfer+frazil Area Integrated')
1459 
1460  handles%id_total_sw = register_scalar_field('ocean_model', &
1461  'total_sw', time, diag, &
1462  long_name='Area integrated net downward shortwave at sea water surface', &
1463  units='Watt', &
1464  cmor_field_name='total_rsntds', cmor_units='W', &
1465  cmor_standard_name='net_downward_shortwave_flux_at_sea_water_surface_area_integrated',&
1466  cmor_long_name= &
1467  'Net Downward Shortwave Radiation at Sea Water Surface Area Integrated')
1468 
1469  handles%id_total_LwLatSens = register_scalar_field('ocean_model',&
1470  'total_LwLatSens', time, diag, &
1471  long_name='Area integrated longwave+latent+sensible heating',&
1472  units='Watt')
1473 
1474  handles%id_total_lw = register_scalar_field('ocean_model', &
1475  'total_lw', time, diag, &
1476  long_name='Area integrated net downward longwave at sea water surface', &
1477  units='Watt', &
1478  cmor_field_name='total_rlntds', cmor_units='W', &
1479  cmor_standard_name='surface_net_downward_longwave_flux_area_integrated',&
1480  cmor_long_name= &
1481  'Surface Net Downward Longwave Radiation Area Integrated')
1482 
1483  handles%id_total_lat = register_scalar_field('ocean_model', &
1484  'total_lat', time, diag, &
1485  long_name='Area integrated surface downward latent heat flux', &
1486  units='Watt', &
1487  cmor_field_name='total_hflso', cmor_units='W', &
1488  cmor_standard_name='surface_downward_latent_heat_flux_area_integrated',&
1489  cmor_long_name= &
1490  'Surface Downward Latent Heat Flux Area Integrated')
1491 
1492  handles%id_total_lat_evap = register_scalar_field('ocean_model', &
1493  'total_lat_evap', time, diag, &
1494  long_name='Area integrated latent heat flux due to evap/condense',&
1495  units='Watt')
1496 
1497  handles%id_total_lat_fprec = register_scalar_field('ocean_model', &
1498  'total_lat_fprec', time, diag, &
1499  long_name='Area integrated latent heat flux due to melting frozen precip', &
1500  units='Watt', &
1501  cmor_field_name='total_hfsnthermds', cmor_units='W', &
1502  cmor_standard_name='heat_flux_into_sea_water_due_to_snow_thermodynamics_area_integrated',&
1503  cmor_long_name= &
1504  'Latent Heat to Melt Frozen Precipitation Area Integrated')
1505 
1506  handles%id_total_lat_frunoff = register_scalar_field('ocean_model', &
1507  'total_lat_frunoff', time, diag, &
1508  long_name='Area integrated latent heat flux due to melting icebergs', &
1509  units='Watt', &
1510  cmor_field_name='total_hfibthermds', cmor_units='W', &
1511  cmor_standard_name='heat_flux_into_sea_water_due_to_iceberg_thermodynamics_area_integrated',&
1512  cmor_long_name= &
1513  'Heat Flux into Sea Water due to Iceberg Thermodynamics Area Integrated')
1514 
1515  handles%id_total_sens = register_scalar_field('ocean_model', &
1516  'total_sens', time, diag, &
1517  long_name='Area integrated downward sensible heat flux', &
1518  units='Watt', &
1519  cmor_field_name='total_hfsso', cmor_units='W', &
1520  cmor_standard_name='surface_downward_sensible_heat_flux_area_integrated',&
1521  cmor_long_name= &
1522  'Surface Downward Sensible Heat Flux Area Integrated')
1523 
1524  handles%id_total_heat_added = register_scalar_field('ocean_model',&
1525  'total_heat_adjustment', time, diag, &
1526  long_name='Area integrated surface heat flux from restoring and/or flux adjustment', &
1527  units='Watt')
1528 
1529 
1530  !===============================================================
1531  ! area averaged surface heat fluxes
1532 
1533  handles%id_net_heat_coupler_ga = register_scalar_field('ocean_model', &
1534  'net_heat_coupler_ga', time, diag, &
1535  long_name='Area averaged surface heat flux from SW+LW+latent+sensible (via the coupler)',&
1536  units='W m-2')
1537 
1538  handles%id_net_heat_surface_ga = register_scalar_field('ocean_model', &
1539  'net_heat_surface_ga', time, diag, &
1540  long_name='Area averaged surface heat flux from SW+LW+lat+sens+mass+frazil+restore or flux adjustments', &
1541  units='W m-2', &
1542  cmor_field_name='ave_hfds', cmor_units='W m-2', &
1543  cmor_standard_name='surface_downward_heat_flux_in_sea_water_area_averaged', &
1544  cmor_long_name= &
1545  'Surface Ocean Heat Flux from SW+LW+latent+sensible+mass transfer+frazil Area Averaged')
1546 
1547  handles%id_sw_ga = register_scalar_field('ocean_model', &
1548  'sw_ga', time, diag, &
1549  long_name='Area averaged net downward shortwave at sea water surface', &
1550  units='W m-2', &
1551  cmor_field_name='ave_rsntds', cmor_units='W m-2', &
1552  cmor_standard_name='net_downward_shortwave_flux_at_sea_water_surface_area_averaged',&
1553  cmor_long_name= &
1554  'Net Downward Shortwave Radiation at Sea Water Surface Area Averaged')
1555 
1556  handles%id_LwLatSens_ga = register_scalar_field('ocean_model',&
1557  'LwLatSens_ga', time, diag, &
1558  long_name='Area averaged longwave+latent+sensible heating',&
1559  units='W m-2')
1560 
1561  handles%id_lw_ga = register_scalar_field('ocean_model', &
1562  'lw_ga', time, diag, &
1563  long_name='Area averaged net downward longwave at sea water surface', &
1564  units='W m-2', &
1565  cmor_field_name='ave_rlntds', cmor_units='W m-2', &
1566  cmor_standard_name='surface_net_downward_longwave_flux_area_averaged',&
1567  cmor_long_name= &
1568  'Surface Net Downward Longwave Radiation Area Averaged')
1569 
1570  handles%id_lat_ga = register_scalar_field('ocean_model', &
1571  'lat_ga', time, diag, &
1572  long_name='Area averaged surface downward latent heat flux', &
1573  units='W m-2', &
1574  cmor_field_name='ave_hflso', cmor_units='W m-2', &
1575  cmor_standard_name='surface_downward_latent_heat_flux_area_averaged',&
1576  cmor_long_name= &
1577  'Surface Downward Latent Heat Flux Area Averaged')
1578 
1579  handles%id_sens_ga = register_scalar_field('ocean_model', &
1580  'sens_ga', time, diag, &
1581  long_name='Area averaged downward sensible heat flux', &
1582  units='W m-2', &
1583  cmor_field_name='ave_hfsso', cmor_units='W m-2', &
1584  cmor_standard_name='surface_downward_sensible_heat_flux_area_averaged',&
1585  cmor_long_name= &
1586  'Surface Downward Sensible Heat Flux Area Averaged')
1587 
1588 
1589  !===============================================================
1590  ! maps of surface salt fluxes, virtual precip fluxes, and adjustments
1591 
1592  handles%id_saltflux = register_diag_field('ocean_model', 'salt_flux', diag%axesT1, time,&
1593  'Net salt flux into ocean at surface (restoring + sea-ice)', &
1594  'kilogram meter-2 second-1',cmor_field_name='sfdsi', cmor_units='kg m-2 s-1', &
1595  cmor_standard_name='downward_sea_ice_basal_salt_flux', &
1596  cmor_long_name='Downward Sea Ice Basal Salt Flux')
1597 
1598  handles%id_saltFluxIn = register_diag_field('ocean_model', 'salt_flux_in', diag%axesT1, time, &
1599  'Salt flux into ocean at surface from coupler', 'kilogram/(meter^2 * second)')
1600 
1601  handles%id_saltFluxAdded = register_diag_field('ocean_model', 'salt_flux_added', &
1602  diag%axesT1,time,'Salt flux into ocean at surface due to restoring or flux adjustment', &
1603  'kilogram/(meter^2 * second)')
1604 
1605  handles%id_saltFluxGlobalAdj = register_scalar_field('ocean_model', &
1606  'salt_flux_global_restoring_adjustment', time, diag, &
1607  'Adjustment needed to balance net global salt flux into ocean at surface', &
1608  'kilogram/(meter^2 * second)')
1609 
1610  handles%id_vPrecGlobalAdj = register_scalar_field('ocean_model', &
1611  'vprec_global_adjustment', time, diag, &
1612  'Adjustment needed to adjust net vprec into ocean to zero', &
1613  'kilogram/(meter^2 * second)')
1614 
1615  handles%id_netFWGlobalAdj = register_scalar_field('ocean_model', &
1616  'net_fresh_water_global_adjustment', time, diag, &
1617  'Adjustment needed to adjust net fresh water into ocean to zero',&
1618  'kilogram/(meter^2 * second)')
1619 
1620  handles%id_saltFluxGlobalScl = register_scalar_field('ocean_model', &
1621  'salt_flux_global_restoring_scaling', time, diag, &
1622  'Scaling applied to balance net global salt flux into ocean at surface', &
1623  '(nondim)')
1624 
1625  handles%id_vPrecGlobalScl = register_scalar_field('ocean_model',&
1626  'vprec_global_scaling', time, diag, &
1627  'Scaling applied to adjust net vprec into ocean to zero', &
1628  '(nondim)')
1629 
1630  handles%id_netFWGlobalScl = register_scalar_field('ocean_model', &
1631  'net_fresh_water_global_scaling', time, diag, &
1632  'Scaling applied to adjust net fresh water into ocean to zero', &
1633  '(nondim)')
1634 
1635  !===============================================================
1636  ! area integrals of surface salt fluxes
1637 
1638  handles%id_total_saltflux = register_scalar_field('ocean_model', &
1639  'total_salt_flux', time, diag, &
1640  long_name='Area integrated surface salt flux', units='kg', &
1641  cmor_field_name='total_sfdsi', &
1642  cmor_units='kg s-1', &
1643  cmor_standard_name='downward_sea_ice_basal_salt_flux_area_integrated',&
1644  cmor_long_name='Downward Sea Ice Basal Salt Flux Area Integrated')
1645 
1646  handles%id_total_saltFluxIn = register_scalar_field('ocean_model', 'total_salt_Flux_In', &
1647  time, diag, long_name='Area integrated surface salt flux at surface from coupler', units='kg')
1648 
1649  handles%id_total_saltFluxAdded = register_scalar_field('ocean_model', 'total_salt_Flux_Added', &
1650  time, diag, long_name='Area integrated surface salt flux due to restoring or flux adjustment', units='kg')
1651 
1652 
1653 end subroutine register_forcing_type_diags
1654 
1655 !> Accumulate the forcing over time steps
1656 subroutine forcing_accumulate(flux_tmp, fluxes, dt, G, wt2)
1657  type(forcing), intent(in) :: flux_tmp
1658  type(forcing), intent(inout) :: fluxes
1659  real, intent(in) :: dt !< The elapsed time since the last call to this subroutine, in s
1660  type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure
1661  real, intent(out) :: wt2
1662 
1663  ! This subroutine copies mechancal forcing from flux_tmp to fluxes and
1664  ! stores the time-weighted averages of the various buoyancy fluxes in fluxes,
1665  ! and increments the amount of time over which the buoyancy forcing should be
1666  ! applied.
1667 
1668  real :: wt1
1669  integer :: i, j, is, ie, js, je, Isq, Ieq, Jsq, Jeq, i0, j0
1670  integer :: isd, ied, jsd, jed, IsdB, IedB, JsdB, JedB, isr, ier, jsr, jer
1671  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
1672  isq = g%IscB ; ieq = g%IecB ; jsq = g%JscB ; jeq = g%JecB
1673  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
1674  isdb = g%IsdB ; iedb = g%IedB ; jsdb = g%JsdB ; jedb = g%JedB
1675 
1676 
1677  if (fluxes%dt_buoy_accum < 0) call mom_error(fatal, "forcing_accumulate: "//&
1678  "fluxes must be initialzed before it can be augmented.")
1679 
1680  ! wt1 is the relative weight of the previous fluxes.
1681  wt1 = fluxes%dt_buoy_accum / (fluxes%dt_buoy_accum + dt)
1682  wt2 = 1.0 - wt1 ! = dt / (fluxes%dt_buoy_accum + dt)
1683  fluxes%dt_buoy_accum = fluxes%dt_buoy_accum + dt
1684 
1685  ! Copy over the pressure and momentum flux fields.
1686  do j=js,je ; do i=is,ie
1687  fluxes%p_surf(i,j) = flux_tmp%p_surf(i,j)
1688  fluxes%p_surf_full(i,j) = flux_tmp%p_surf_full(i,j)
1689  enddo ; enddo
1690  do j=js,je ; do i=isq,ieq
1691  fluxes%taux(i,j) = flux_tmp%taux(i,j)
1692  enddo ; enddo
1693  do j=jsq,jeq ; do i=is,ie
1694  fluxes%tauy(i,j) = flux_tmp%tauy(i,j)
1695  enddo ; enddo
1696 
1697  ! Average the water, heat, and salt fluxes, and ustar.
1698  do j=js,je ; do i=is,ie
1699  fluxes%ustar(i,j) = wt1*fluxes%ustar(i,j) + wt2*flux_tmp%ustar(i,j)
1700 
1701  fluxes%evap(i,j) = wt1*fluxes%evap(i,j) + wt2*flux_tmp%evap(i,j)
1702  fluxes%lprec(i,j) = wt1*fluxes%lprec(i,j) + wt2*flux_tmp%lprec(i,j)
1703  fluxes%fprec(i,j) = wt1*fluxes%fprec(i,j) + wt2*flux_tmp%fprec(i,j)
1704  fluxes%vprec(i,j) = wt1*fluxes%vprec(i,j) + wt2*flux_tmp%vprec(i,j)
1705  fluxes%lrunoff(i,j) = wt1*fluxes%lrunoff(i,j) + wt2*flux_tmp%lrunoff(i,j)
1706  fluxes%frunoff(i,j) = wt1*fluxes%frunoff(i,j) + wt2*flux_tmp%frunoff(i,j)
1707  ! ### ADD LATER fluxes%seaice_melt(i,j) = wt1*fluxes%seaice_melt(i,j) + wt2*flux_tmp%seaice_melt(i,j)
1708 
1709  fluxes%sw(i,j) = wt1*fluxes%sw(i,j) + wt2*flux_tmp%sw(i,j)
1710  fluxes%sw_vis_dir(i,j) = wt1*fluxes%sw_vis_dir(i,j) + wt2*flux_tmp%sw_vis_dir(i,j)
1711  fluxes%sw_vis_dif(i,j) = wt1*fluxes%sw_vis_dif(i,j) + wt2*flux_tmp%sw_vis_dif(i,j)
1712  fluxes%sw_nir_dir(i,j) = wt1*fluxes%sw_nir_dir(i,j) + wt2*flux_tmp%sw_nir_dir(i,j)
1713  fluxes%sw_nir_dif(i,j) = wt1*fluxes%sw_nir_dif(i,j) + wt2*flux_tmp%sw_nir_dif(i,j)
1714  fluxes%lw(i,j) = wt1*fluxes%lw(i,j) + wt2*flux_tmp%lw(i,j)
1715  fluxes%latent(i,j) = wt1*fluxes%latent(i,j) + wt2*flux_tmp%latent(i,j)
1716  fluxes%sens(i,j) = wt1*fluxes%sens(i,j) + wt2*flux_tmp%sens(i,j)
1717 
1718  fluxes%salt_flux(i,j) = wt1*fluxes%salt_flux(i,j) + wt2*flux_tmp%salt_flux(i,j)
1719  enddo ; enddo
1720  if (associated(fluxes%heat_added) .and. associated(flux_tmp%heat_added)) then
1721  do j=js,je ; do i=is,ie
1722  fluxes%heat_added(i,j) = wt1*fluxes%heat_added(i,j) + wt2*flux_tmp%heat_added(i,j)
1723  enddo ; enddo
1724  endif
1725  ! These might always be associated, in which case they can be combined?
1726  if (associated(fluxes%heat_content_cond) .and. associated(flux_tmp%heat_content_cond)) then
1727  do j=js,je ; do i=is,ie
1728  fluxes%heat_content_cond(i,j) = wt1*fluxes%heat_content_cond(i,j) + wt2*flux_tmp%heat_content_cond(i,j)
1729  enddo ; enddo
1730  endif
1731  if (associated(fluxes%heat_content_lprec) .and. associated(flux_tmp%heat_content_lprec)) then
1732  do j=js,je ; do i=is,ie
1733  fluxes%heat_content_lprec(i,j) = wt1*fluxes%heat_content_lprec(i,j) + wt2*flux_tmp%heat_content_lprec(i,j)
1734  enddo ; enddo
1735  endif
1736  if (associated(fluxes%heat_content_fprec) .and. associated(flux_tmp%heat_content_fprec)) then
1737  do j=js,je ; do i=is,ie
1738  fluxes%heat_content_fprec(i,j) = wt1*fluxes%heat_content_fprec(i,j) + wt2*flux_tmp%heat_content_fprec(i,j)
1739  enddo ; enddo
1740  endif
1741  if (associated(fluxes%heat_content_vprec) .and. associated(flux_tmp%heat_content_vprec)) then
1742  do j=js,je ; do i=is,ie
1743  fluxes%heat_content_vprec(i,j) = wt1*fluxes%heat_content_vprec(i,j) + wt2*flux_tmp%heat_content_vprec(i,j)
1744  enddo ; enddo
1745  endif
1746  if (associated(fluxes%heat_content_lrunoff) .and. associated(flux_tmp%heat_content_lrunoff)) then
1747  do j=js,je ; do i=is,ie
1748  fluxes%heat_content_lrunoff(i,j) = wt1*fluxes%heat_content_lrunoff(i,j) + wt2*flux_tmp%heat_content_lrunoff(i,j)
1749  enddo ; enddo
1750  endif
1751  if (associated(fluxes%heat_content_frunoff) .and. associated(flux_tmp%heat_content_frunoff)) then
1752  do j=js,je ; do i=is,ie
1753  fluxes%heat_content_frunoff(i,j) = wt1*fluxes%heat_content_frunoff(i,j) + wt2*flux_tmp%heat_content_frunoff(i,j)
1754  enddo ; enddo
1755  endif
1756  if (associated(fluxes%heat_content_icemelt) .and. associated(flux_tmp%heat_content_icemelt)) then
1757  do j=js,je ; do i=is,ie
1758  fluxes%heat_content_icemelt(i,j) = wt1*fluxes%heat_content_icemelt(i,j) + wt2*flux_tmp%heat_content_icemelt(i,j)
1759  enddo ; enddo
1760  endif
1761 
1762  if (associated(fluxes%ustar_shelf) .and. associated(flux_tmp%ustar_shelf)) then
1763  do i=isd,ied ; do j=jsd,jed
1764  fluxes%ustar_shelf(i,j) = flux_tmp%ustar_shelf(i,j)
1765  enddo ; enddo
1766  endif
1767 
1768  if (associated(fluxes%iceshelf_melt) .and. associated(flux_tmp%iceshelf_melt)) then
1769  do i=isd,ied ; do j=jsd,jed
1770  fluxes%iceshelf_melt(i,j) = flux_tmp%iceshelf_melt(i,j)
1771  enddo ; enddo
1772  endif
1773 
1774  if (associated(fluxes%frac_shelf_h) .and. associated(flux_tmp%frac_shelf_h)) then
1775  do i=isd,ied ; do j=jsd,jed
1776  fluxes%frac_shelf_h(i,j) = flux_tmp%frac_shelf_h(i,j)
1777  enddo ; enddo
1778  endif
1779  if (associated(fluxes%frac_shelf_u) .and. associated(flux_tmp%frac_shelf_u)) then
1780  do i=isdb,iedb ; do j=jsd,jed
1781  fluxes%frac_shelf_u(i,j) = flux_tmp%frac_shelf_u(i,j)
1782  enddo ; enddo
1783  endif
1784  if (associated(fluxes%frac_shelf_v) .and. associated(flux_tmp%frac_shelf_v)) then
1785  do i=isd,ied ; do j=jsdb,jedb
1786  fluxes%frac_shelf_v(i,j) = flux_tmp%frac_shelf_v(i,j)
1787  enddo ; enddo
1788  endif
1789  if (associated(fluxes%rigidity_ice_u) .and. associated(flux_tmp%rigidity_ice_u)) then
1790  do i=isd,ied-1 ; do j=jsd,jed
1791  fluxes%rigidity_ice_u(i,j) = flux_tmp%rigidity_ice_u(i,j)
1792  enddo ; enddo
1793  endif
1794  if (associated(fluxes%rigidity_ice_v) .and. associated(flux_tmp%rigidity_ice_v)) then
1795  do i=isd,ied ; do j=jsd,jed-1
1796  fluxes%rigidity_ice_v(i,j) = flux_tmp%rigidity_ice_v(i,j)
1797  enddo ; enddo
1798  endif
1799 
1800  !### This needs to be replaced with an appropriate copy and average.
1801  fluxes%tr_fluxes => flux_tmp%tr_fluxes
1802 
1803 end subroutine forcing_accumulate
1804 
1805 
1806 !> Offer mechanical forcing fields for diagnostics for those
1807 !! fields registered as part of register_forcing_type_diags.
1808 subroutine mech_forcing_diags(fluxes, dt, G, diag, handles)
1809  type(forcing), intent(in) :: fluxes !< fluxes type
1810  real, intent(in) :: dt !< time step
1811  type(ocean_grid_type), intent(in) :: G !< grid type
1812  type(diag_ctrl), intent(in) :: diag !< diagnostic type
1813  type(forcing_diags), intent(inout) :: handles !< diagnostic id for diag_manager
1814 
1815  integer :: i,j,is,ie,js,je
1816 
1817  call cpu_clock_begin(handles%id_clock_forcing)
1818 
1819  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
1820  if (query_averaging_enabled(diag)) then
1821 
1822  if ((handles%id_taux > 0) .and. ASSOCIATED(fluxes%taux)) &
1823  call post_data(handles%id_taux, fluxes%taux, diag)
1824  if ((handles%id_tauy > 0) .and. ASSOCIATED(fluxes%tauy)) &
1825  call post_data(handles%id_tauy, fluxes%tauy, diag)
1826  if ((handles%id_ustar > 0) .and. ASSOCIATED(fluxes%ustar)) &
1827  call post_data(handles%id_ustar, fluxes%ustar, diag)
1828  if (handles%id_ustar_berg > 0) &
1829  call post_data(handles%id_ustar_berg, fluxes%ustar_berg, diag)
1830  if (handles%id_area_berg > 0) &
1831  call post_data(handles%id_area_berg, fluxes%area_berg, diag)
1832  if (handles%id_mass_berg > 0) &
1833  call post_data(handles%id_mass_berg, fluxes%mass_berg, diag)
1834  if (handles%id_frac_ice_cover > 0) &
1835  call post_data(handles%id_frac_ice_cover, fluxes%frac_shelf_h, diag)
1836  if (handles%id_ustar_ice_cover > 0) &
1837  call post_data(handles%id_ustar_ice_cover, fluxes%ustar_shelf, diag)
1838 
1839  endif
1840 
1841  call cpu_clock_end(handles%id_clock_forcing)
1842 end subroutine mech_forcing_diags
1843 
1844 
1845 !> Offer buoyancy forcing fields for diagnostics for those
1846 !! fields registered as part of register_forcing_type_diags.
1847 subroutine forcing_diagnostics(fluxes, state, dt, G, diag, handles)
1848  type(forcing), intent(in) :: fluxes !< flux type
1849  type(surface), intent(in) :: state !< ocean state
1850  real, intent(in) :: dt !< time step
1851  type(ocean_grid_type), intent(in) :: G !< grid type
1852  type(diag_ctrl), intent(in) :: diag !< diagnostic regulator
1853  type(forcing_diags), intent(inout) :: handles !< diagnostic ids
1854 
1855  ! local
1856  real, dimension(SZI_(G),SZJ_(G)) :: res
1857  real :: total_transport ! for diagnosing integrated boundary transport
1858  real :: ave_flux ! for diagnosing averaged boundary flux
1859  real :: C_p ! seawater heat capacity (J/(deg K * kg))
1860  real :: I_dt ! inverse time step
1861  real :: ppt2mks ! conversion between ppt and mks
1862  integer :: i,j,is,ie,js,je
1863 
1864  call cpu_clock_begin(handles%id_clock_forcing)
1865 
1866  c_p = fluxes%C_p
1867  i_dt = 1.0/dt
1868  ppt2mks = 1e-3
1869  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
1870 
1871  if (query_averaging_enabled(diag)) then
1872 
1873  ! post the diagnostics for surface mass fluxes ==================================
1874 
1875  if (handles%id_prcme > 0 .or. handles%id_total_prcme > 0 .or. handles%id_prcme_ga > 0) then
1876  do j=js,je ; do i=is,ie
1877  res(i,j) = 0.0
1878  if (ASSOCIATED(fluxes%lprec)) res(i,j) = res(i,j)+fluxes%lprec(i,j)
1879  if (ASSOCIATED(fluxes%fprec)) res(i,j) = res(i,j)+fluxes%fprec(i,j)
1880  ! fluxes%cond is not needed because it is derived from %evap > 0
1881  if (ASSOCIATED(fluxes%evap)) res(i,j) = res(i,j)+fluxes%evap(i,j)
1882  if (ASSOCIATED(fluxes%lrunoff)) res(i,j) = res(i,j)+fluxes%lrunoff(i,j)
1883  if (ASSOCIATED(fluxes%frunoff)) res(i,j) = res(i,j)+fluxes%frunoff(i,j)
1884  if (ASSOCIATED(fluxes%vprec)) res(i,j) = res(i,j)+fluxes%vprec(i,j)
1885  enddo ; enddo
1886  call post_data(handles%id_prcme, res, diag)
1887  if(handles%id_total_prcme > 0) then
1888  total_transport = global_area_integral(res,g)
1889  call post_data(handles%id_total_prcme, total_transport, diag)
1890  endif
1891  if(handles%id_prcme_ga > 0) then
1892  ave_flux = global_area_mean(res,g)
1893  call post_data(handles%id_prcme_ga, ave_flux, diag)
1894  endif
1895  endif
1896 
1897  if(handles%id_net_massout > 0 .or. handles%id_total_net_massout > 0) then
1898  do j=js,je ; do i=is,ie
1899  res(i,j) = 0.0
1900  if(fluxes%lprec(i,j) < 0.0) res(i,j) = res(i,j) + fluxes%lprec(i,j)
1901  if(fluxes%vprec(i,j) < 0.0) res(i,j) = res(i,j) + fluxes%vprec(i,j)
1902  if(fluxes%evap(i,j) < 0.0) res(i,j) = res(i,j) + fluxes%evap(i,j)
1903  enddo ; enddo
1904  call post_data(handles%id_net_massout, res, diag)
1905  if(handles%id_total_net_massout > 0) then
1906  total_transport = global_area_integral(res,g)
1907  call post_data(handles%id_total_net_massout, total_transport, diag)
1908  endif
1909  endif
1910 
1911  if(handles%id_massout_flux > 0) call post_data(handles%id_massout_flux,fluxes%netMassOut,diag)
1912 
1913  if(handles%id_net_massin > 0 .or. handles%id_total_net_massin > 0) then
1914  do j=js,je ; do i=is,ie
1915  res(i,j) = fluxes%fprec(i,j) + fluxes%lrunoff(i,j) + fluxes%frunoff(i,j)
1916  if(fluxes%lprec(i,j) > 0.0) res(i,j) = res(i,j) + fluxes%lprec(i,j)
1917  if(fluxes%vprec(i,j) > 0.0) res(i,j) = res(i,j) + fluxes%vprec(i,j)
1918  ! fluxes%cond is not needed because it is derived from %evap > 0
1919  if(fluxes%evap(i,j) > 0.0) res(i,j) = res(i,j) + fluxes%evap(i,j)
1920  enddo ; enddo
1921  call post_data(handles%id_net_massin, res, diag)
1922  if(handles%id_total_net_massin > 0) then
1923  total_transport = global_area_integral(res,g)
1924  call post_data(handles%id_total_net_massin, total_transport, diag)
1925  endif
1926  endif
1927 
1928  if(handles%id_massin_flux > 0) call post_data(handles%id_massin_flux,fluxes%netMassIn,diag)
1929 
1930  if ((handles%id_evap > 0) .and. ASSOCIATED(fluxes%evap)) &
1931  call post_data(handles%id_evap, fluxes%evap, diag)
1932  if ((handles%id_total_evap > 0) .and. ASSOCIATED(fluxes%evap)) then
1933  total_transport = global_area_integral(fluxes%evap,g)
1934  call post_data(handles%id_total_evap, total_transport, diag)
1935  endif
1936  if ((handles%id_evap_ga > 0) .and. ASSOCIATED(fluxes%evap)) then
1937  ave_flux = global_area_mean(fluxes%evap,g)
1938  call post_data(handles%id_evap_ga, ave_flux, diag)
1939  endif
1940 
1941  if (ASSOCIATED(fluxes%lprec) .and. ASSOCIATED(fluxes%fprec)) then
1942  do j=js,je ; do i=is,ie
1943  res(i,j) = fluxes%lprec(i,j) + fluxes%fprec(i,j)
1944  enddo ; enddo
1945  if (handles%id_precip > 0) call post_data(handles%id_precip, res, diag)
1946  if (handles%id_total_precip > 0) then
1947  total_transport = global_area_integral(res,g)
1948  call post_data(handles%id_total_precip, total_transport, diag)
1949  endif
1950  if (handles%id_precip_ga > 0) then
1951  ave_flux = global_area_mean(res,g)
1952  call post_data(handles%id_precip_ga, ave_flux, diag)
1953  endif
1954  endif
1955 
1956  if (ASSOCIATED(fluxes%lprec)) then
1957  if (handles%id_lprec > 0) call post_data(handles%id_lprec, fluxes%lprec, diag)
1958  if (handles%id_total_lprec > 0) then
1959  total_transport = global_area_integral(fluxes%lprec,g)
1960  call post_data(handles%id_total_lprec, total_transport, diag)
1961  endif
1962  if (handles%id_lprec_ga > 0) then
1963  ave_flux = global_area_mean(fluxes%lprec,g)
1964  call post_data(handles%id_lprec_ga, ave_flux, diag)
1965  endif
1966  endif
1967 
1968  if (ASSOCIATED(fluxes%fprec)) then
1969  if (handles%id_fprec > 0) call post_data(handles%id_fprec, fluxes%fprec, diag)
1970  if (handles%id_total_fprec > 0) then
1971  total_transport = global_area_integral(fluxes%fprec,g)
1972  call post_data(handles%id_total_fprec, total_transport, diag)
1973  endif
1974  if (handles%id_fprec_ga > 0) then
1975  ave_flux = global_area_mean(fluxes%fprec,g)
1976  call post_data(handles%id_fprec_ga, ave_flux, diag)
1977  endif
1978  endif
1979 
1980  if (ASSOCIATED(fluxes%vprec)) then
1981  if (handles%id_vprec > 0) call post_data(handles%id_vprec, fluxes%vprec, diag)
1982  if (handles%id_total_vprec > 0) then
1983  total_transport = global_area_integral(fluxes%vprec,g)
1984  call post_data(handles%id_total_vprec, total_transport, diag)
1985  endif
1986  if (handles%id_vprec_ga > 0) then
1987  ave_flux = global_area_mean(fluxes%vprec,g)
1988  call post_data(handles%id_vprec_ga, ave_flux, diag)
1989  endif
1990  endif
1991 
1992  if (ASSOCIATED(fluxes%lrunoff)) then
1993  if (handles%id_lrunoff > 0) call post_data(handles%id_lrunoff, fluxes%lrunoff, diag)
1994  if (handles%id_total_lrunoff > 0) then
1995  total_transport = global_area_integral(fluxes%lrunoff,g)
1996  call post_data(handles%id_total_lrunoff, total_transport, diag)
1997  endif
1998  endif
1999 
2000  if (ASSOCIATED(fluxes%frunoff)) then
2001  if (handles%id_frunoff > 0) call post_data(handles%id_frunoff, fluxes%frunoff, diag)
2002  if (handles%id_total_frunoff > 0) then
2003  total_transport = global_area_integral(fluxes%frunoff,g)
2004  call post_data(handles%id_total_frunoff, total_transport, diag)
2005  endif
2006  endif
2007 
2008  ! post diagnostics for boundary heat fluxes ====================================
2009 
2010  if ((handles%id_heat_content_lrunoff > 0) .and. ASSOCIATED(fluxes%heat_content_lrunoff)) &
2011  call post_data(handles%id_heat_content_lrunoff, fluxes%heat_content_lrunoff, diag)
2012  if ((handles%id_total_heat_content_lrunoff > 0) .and. ASSOCIATED(fluxes%heat_content_lrunoff)) then
2013  total_transport = global_area_integral(fluxes%heat_content_lrunoff,g)
2014  call post_data(handles%id_total_heat_content_lrunoff, total_transport, diag)
2015  endif
2016 
2017  if ((handles%id_heat_content_frunoff > 0) .and. ASSOCIATED(fluxes%heat_content_frunoff)) &
2018  call post_data(handles%id_heat_content_frunoff, fluxes%heat_content_frunoff, diag)
2019  if ((handles%id_total_heat_content_frunoff > 0) .and. ASSOCIATED(fluxes%heat_content_frunoff)) then
2020  total_transport = global_area_integral(fluxes%heat_content_frunoff,g)
2021  call post_data(handles%id_total_heat_content_frunoff, total_transport, diag)
2022  endif
2023 
2024  if ((handles%id_heat_content_lprec > 0) .and. ASSOCIATED(fluxes%heat_content_lprec)) &
2025  call post_data(handles%id_heat_content_lprec, fluxes%heat_content_lprec, diag)
2026  if ((handles%id_total_heat_content_lprec > 0) .and. ASSOCIATED(fluxes%heat_content_lprec)) then
2027  total_transport = global_area_integral(fluxes%heat_content_lprec,g)
2028  call post_data(handles%id_total_heat_content_lprec, total_transport, diag)
2029  endif
2030 
2031  if ((handles%id_heat_content_fprec > 0) .and. ASSOCIATED(fluxes%heat_content_fprec)) &
2032  call post_data(handles%id_heat_content_fprec, fluxes%heat_content_fprec, diag)
2033  if ((handles%id_total_heat_content_fprec > 0) .and. ASSOCIATED(fluxes%heat_content_fprec)) then
2034  total_transport = global_area_integral(fluxes%heat_content_fprec,g)
2035  call post_data(handles%id_total_heat_content_fprec, total_transport, diag)
2036  endif
2037 
2038  if ((handles%id_heat_content_vprec > 0) .and. ASSOCIATED(fluxes%heat_content_vprec)) &
2039  call post_data(handles%id_heat_content_vprec, fluxes%heat_content_vprec, diag)
2040  if ((handles%id_total_heat_content_vprec > 0) .and. ASSOCIATED(fluxes%heat_content_vprec)) then
2041  total_transport = global_area_integral(fluxes%heat_content_vprec,g)
2042  call post_data(handles%id_total_heat_content_vprec, total_transport, diag)
2043  endif
2044 
2045  if ((handles%id_heat_content_cond > 0) .and. ASSOCIATED(fluxes%heat_content_cond)) &
2046  call post_data(handles%id_heat_content_cond, fluxes%heat_content_cond, diag)
2047  if ((handles%id_total_heat_content_cond > 0) .and. ASSOCIATED(fluxes%heat_content_cond)) then
2048  total_transport = global_area_integral(fluxes%heat_content_cond,g)
2049  call post_data(handles%id_total_heat_content_cond, total_transport, diag)
2050  endif
2051 
2052  if ((handles%id_heat_content_massout > 0) .and. ASSOCIATED(fluxes%heat_content_massout)) &
2053  call post_data(handles%id_heat_content_massout, fluxes%heat_content_massout, diag)
2054  if ((handles%id_total_heat_content_massout > 0) .and. ASSOCIATED(fluxes%heat_content_massout)) then
2055  total_transport = global_area_integral(fluxes%heat_content_massout,g)
2056  call post_data(handles%id_total_heat_content_massout, total_transport, diag)
2057  endif
2058 
2059  if ((handles%id_heat_content_massin > 0) .and. ASSOCIATED(fluxes%heat_content_massin)) &
2060  call post_data(handles%id_heat_content_massin, fluxes%heat_content_massin, diag)
2061  if ((handles%id_total_heat_content_massin > 0) .and. ASSOCIATED(fluxes%heat_content_massin)) then
2062  total_transport = global_area_integral(fluxes%heat_content_massin,g)
2063  call post_data(handles%id_total_heat_content_massin, total_transport, diag)
2064  endif
2065 
2066  if (handles%id_net_heat_coupler > 0 .or. handles%id_total_net_heat_coupler > 0 .or. handles%id_net_heat_coupler_ga > 0. ) then
2067  do j=js,je ; do i=is,ie
2068  res(i,j) = 0.0
2069  if (ASSOCIATED(fluxes%LW)) res(i,j) = res(i,j) + fluxes%LW(i,j)
2070  if (ASSOCIATED(fluxes%latent)) res(i,j) = res(i,j) + fluxes%latent(i,j)
2071  if (ASSOCIATED(fluxes%sens)) res(i,j) = res(i,j) + fluxes%sens(i,j)
2072  if (ASSOCIATED(fluxes%SW)) res(i,j) = res(i,j) + fluxes%SW(i,j)
2073  enddo ; enddo
2074  call post_data(handles%id_net_heat_coupler, res, diag)
2075  if(handles%id_total_net_heat_coupler > 0) then
2076  total_transport = global_area_integral(res,g)
2077  call post_data(handles%id_total_net_heat_coupler, total_transport, diag)
2078  endif
2079  if(handles%id_net_heat_coupler_ga > 0) then
2080  ave_flux = global_area_mean(res,g)
2081  call post_data(handles%id_net_heat_coupler_ga, ave_flux, diag)
2082  endif
2083  endif
2084 
2085  if (handles%id_net_heat_surface > 0 .or. handles%id_total_net_heat_surface > 0 .or. handles%id_net_heat_surface_ga > 0. ) then
2086  do j=js,je ; do i=is,ie
2087  res(i,j) = 0.0
2088  if (ASSOCIATED(fluxes%LW)) res(i,j) = res(i,j) + fluxes%LW(i,j)
2089  if (ASSOCIATED(fluxes%latent)) res(i,j) = res(i,j) + fluxes%latent(i,j)
2090  if (ASSOCIATED(fluxes%sens)) res(i,j) = res(i,j) + fluxes%sens(i,j)
2091  if (ASSOCIATED(fluxes%SW)) res(i,j) = res(i,j) + fluxes%SW(i,j)
2092  if (ASSOCIATED(state%frazil)) res(i,j) = res(i,j) + state%frazil(i,j) * i_dt
2093  ! if (ASSOCIATED(state%TempXpme)) then
2094  ! res(i,j) = res(i,j) + state%TempXpme(i,j) * fluxes%C_p * I_dt
2095  ! else
2096  if (ASSOCIATED(fluxes%heat_content_lrunoff)) res(i,j) = res(i,j) + fluxes%heat_content_lrunoff(i,j)
2097  if (ASSOCIATED(fluxes%heat_content_frunoff)) res(i,j) = res(i,j) + fluxes%heat_content_frunoff(i,j)
2098  if (ASSOCIATED(fluxes%heat_content_lprec)) res(i,j) = res(i,j) + fluxes%heat_content_lprec(i,j)
2099  if (ASSOCIATED(fluxes%heat_content_fprec)) res(i,j) = res(i,j) + fluxes%heat_content_fprec(i,j)
2100  if (ASSOCIATED(fluxes%heat_content_vprec)) res(i,j) = res(i,j) + fluxes%heat_content_vprec(i,j)
2101  if (ASSOCIATED(fluxes%heat_content_cond)) res(i,j) = res(i,j) + fluxes%heat_content_cond(i,j)
2102  if (ASSOCIATED(fluxes%heat_content_massout)) res(i,j) = res(i,j) + fluxes%heat_content_massout(i,j)
2103  ! endif
2104  if (ASSOCIATED(fluxes%heat_added)) res(i,j) = res(i,j) + fluxes%heat_added(i,j)
2105  enddo ; enddo
2106  call post_data(handles%id_net_heat_surface, res, diag)
2107 
2108  if(handles%id_total_net_heat_surface > 0) then
2109  total_transport = global_area_integral(res,g)
2110  call post_data(handles%id_total_net_heat_surface, total_transport, diag)
2111  endif
2112  if(handles%id_net_heat_surface_ga > 0) then
2113  ave_flux = global_area_mean(res,g)
2114  call post_data(handles%id_net_heat_surface_ga, ave_flux, diag)
2115  endif
2116  endif
2117 
2118  if (handles%id_heat_content_surfwater > 0 .or. handles%id_total_heat_content_surfwater > 0) then
2119  do j=js,je ; do i=is,ie
2120  res(i,j) = 0.0
2121  ! if (ASSOCIATED(state%TempXpme)) then
2122  ! res(i,j) = res(i,j) + state%TempXpme(i,j) * fluxes%C_p * I_dt
2123  ! else
2124  if (ASSOCIATED(fluxes%heat_content_lrunoff)) res(i,j) = res(i,j) + fluxes%heat_content_lrunoff(i,j)
2125  if (ASSOCIATED(fluxes%heat_content_frunoff)) res(i,j) = res(i,j) + fluxes%heat_content_frunoff(i,j)
2126  if (ASSOCIATED(fluxes%heat_content_lprec)) res(i,j) = res(i,j) + fluxes%heat_content_lprec(i,j)
2127  if (ASSOCIATED(fluxes%heat_content_fprec)) res(i,j) = res(i,j) + fluxes%heat_content_fprec(i,j)
2128  if (ASSOCIATED(fluxes%heat_content_vprec)) res(i,j) = res(i,j) + fluxes%heat_content_vprec(i,j)
2129  if (ASSOCIATED(fluxes%heat_content_cond)) res(i,j) = res(i,j) + fluxes%heat_content_cond(i,j)
2130  if (ASSOCIATED(fluxes%heat_content_massout)) res(i,j) = res(i,j) + fluxes%heat_content_massout(i,j)
2131  ! endif
2132  enddo ; enddo
2133  call post_data(handles%id_heat_content_surfwater, res, diag)
2134  if(handles%id_total_heat_content_surfwater > 0) then
2135  total_transport = global_area_integral(res,g)
2136  call post_data(handles%id_total_heat_content_surfwater, total_transport, diag)
2137  endif
2138  endif
2139 
2140  ! for OMIP, hfrunoffds = heat content of liquid plus frozen runoff
2141  if (handles%id_hfrunoffds > 0) then
2142  do j=js,je ; do i=is,ie
2143  res(i,j) = 0.0
2144  if(ASSOCIATED(fluxes%heat_content_lrunoff)) res(i,j) = res(i,j) + fluxes%heat_content_lrunoff(i,j)
2145  if(ASSOCIATED(fluxes%heat_content_frunoff)) res(i,j) = res(i,j) + fluxes%heat_content_frunoff(i,j)
2146  enddo ; enddo
2147  call post_data(handles%id_hfrunoffds, res, diag)
2148  endif
2149 
2150  ! for OMIP, hfrainds = heat content of lprec + fprec + cond
2151  if (handles%id_hfrainds > 0) then
2152  do j=js,je ; do i=is,ie
2153  res(i,j) = 0.0
2154  if(ASSOCIATED(fluxes%heat_content_lprec)) res(i,j) = res(i,j) + fluxes%heat_content_lprec(i,j)
2155  if(ASSOCIATED(fluxes%heat_content_fprec)) res(i,j) = res(i,j) + fluxes%heat_content_fprec(i,j)
2156  if(ASSOCIATED(fluxes%heat_content_cond)) res(i,j) = res(i,j) + fluxes%heat_content_cond(i,j)
2157  enddo ; enddo
2158  call post_data(handles%id_hfrainds, res, diag)
2159  endif
2160 
2161  if ((handles%id_LwLatSens > 0) .and. ASSOCIATED(fluxes%lw) .and. &
2162  ASSOCIATED(fluxes%latent) .and. ASSOCIATED(fluxes%sens)) then
2163  do j=js,je ; do i=is,ie
2164  res(i,j) = (fluxes%lw(i,j) + fluxes%latent(i,j)) + fluxes%sens(i,j)
2165  enddo ; enddo
2166  call post_data(handles%id_LwLatSens, res, diag)
2167  endif
2168 
2169  if ((handles%id_total_LwLatSens > 0) .and. ASSOCIATED(fluxes%lw) .and. &
2170  ASSOCIATED(fluxes%latent) .and. ASSOCIATED(fluxes%sens)) then
2171  do j=js,je ; do i=is,ie
2172  res(i,j) = (fluxes%lw(i,j) + fluxes%latent(i,j)) + fluxes%sens(i,j)
2173  enddo ; enddo
2174  total_transport = global_area_integral(res,g)
2175  call post_data(handles%id_total_LwLatSens, total_transport, diag)
2176  endif
2177 
2178  if ((handles%id_LwLatSens_ga > 0) .and. ASSOCIATED(fluxes%lw) .and. &
2179  ASSOCIATED(fluxes%latent) .and. ASSOCIATED(fluxes%sens)) then
2180  do j=js,je ; do i=is,ie
2181  res(i,j) = (fluxes%lw(i,j) + fluxes%latent(i,j)) + fluxes%sens(i,j)
2182  enddo ; enddo
2183  ave_flux = global_area_mean(res,g)
2184  call post_data(handles%id_LwLatSens_ga, ave_flux, diag)
2185  endif
2186 
2187  if ((handles%id_sw > 0) .and. ASSOCIATED(fluxes%sw)) then
2188  call post_data(handles%id_sw, fluxes%sw, diag)
2189  endif
2190  if ((handles%id_sw_vis > 0) .and. ASSOCIATED(fluxes%sw_vis_dir) .and. &
2191  ASSOCIATED(fluxes%sw_vis_dif)) then
2192  call post_data(handles%id_sw_vis, fluxes%sw_vis_dir+fluxes%sw_vis_dif, diag)
2193  endif
2194  if ((handles%id_sw_nir > 0) .and. ASSOCIATED(fluxes%sw_nir_dir) .and. &
2195  ASSOCIATED(fluxes%sw_nir_dif)) then
2196  call post_data(handles%id_sw_nir, fluxes%sw_nir_dir+fluxes%sw_nir_dif, diag)
2197  endif
2198  if ((handles%id_total_sw > 0) .and. ASSOCIATED(fluxes%sw)) then
2199  total_transport = global_area_integral(fluxes%sw,g)
2200  call post_data(handles%id_total_sw, total_transport, diag)
2201  endif
2202  if ((handles%id_sw_ga > 0) .and. ASSOCIATED(fluxes%sw)) then
2203  ave_flux = global_area_mean(fluxes%sw,g)
2204  call post_data(handles%id_sw_ga, ave_flux, diag)
2205  endif
2206 
2207  if ((handles%id_lw > 0) .and. ASSOCIATED(fluxes%lw)) then
2208  call post_data(handles%id_lw, fluxes%lw, diag)
2209  endif
2210  if ((handles%id_total_lw > 0) .and. ASSOCIATED(fluxes%lw)) then
2211  total_transport = global_area_integral(fluxes%lw,g)
2212  call post_data(handles%id_total_lw, total_transport, diag)
2213  endif
2214  if ((handles%id_lw_ga > 0) .and. ASSOCIATED(fluxes%lw)) then
2215  ave_flux = global_area_mean(fluxes%lw,g)
2216  call post_data(handles%id_lw_ga, ave_flux, diag)
2217  endif
2218 
2219  if ((handles%id_lat > 0) .and. ASSOCIATED(fluxes%latent)) then
2220  call post_data(handles%id_lat, fluxes%latent, diag)
2221  endif
2222  if ((handles%id_total_lat > 0) .and. ASSOCIATED(fluxes%latent)) then
2223  total_transport = global_area_integral(fluxes%latent,g)
2224  call post_data(handles%id_total_lat, total_transport, diag)
2225  endif
2226  if ((handles%id_lat_ga > 0) .and. ASSOCIATED(fluxes%latent)) then
2227  ave_flux = global_area_mean(fluxes%latent,g)
2228  call post_data(handles%id_lat_ga, ave_flux, diag)
2229  endif
2230 
2231  if ((handles%id_lat_evap > 0) .and. ASSOCIATED(fluxes%latent_evap_diag)) then
2232  call post_data(handles%id_lat_evap, fluxes%latent_evap_diag, diag)
2233  endif
2234  if ((handles%id_total_lat_evap > 0) .and. ASSOCIATED(fluxes%latent_evap_diag)) then
2235  total_transport = global_area_integral(fluxes%latent_evap_diag,g)
2236  call post_data(handles%id_total_lat_evap, total_transport, diag)
2237  endif
2238 
2239  if ((handles%id_lat_fprec > 0) .and. ASSOCIATED(fluxes%latent_fprec_diag)) then
2240  call post_data(handles%id_lat_fprec, fluxes%latent_fprec_diag, diag)
2241  endif
2242  if ((handles%id_total_lat_fprec > 0) .and. ASSOCIATED(fluxes%latent_fprec_diag)) then
2243  total_transport = global_area_integral(fluxes%latent_fprec_diag,g)
2244  call post_data(handles%id_total_lat_fprec, total_transport, diag)
2245  endif
2246 
2247  if ((handles%id_lat_frunoff > 0) .and. ASSOCIATED(fluxes%latent_frunoff_diag)) then
2248  call post_data(handles%id_lat_frunoff, fluxes%latent_frunoff_diag, diag)
2249  endif
2250  if(handles%id_total_lat_frunoff > 0 .and. ASSOCIATED(fluxes%latent_frunoff_diag)) then
2251  total_transport = global_area_integral(fluxes%latent_frunoff_diag,g)
2252  call post_data(handles%id_total_lat_frunoff, total_transport, diag)
2253  endif
2254 
2255  if ((handles%id_sens > 0) .and. ASSOCIATED(fluxes%sens)) then
2256  call post_data(handles%id_sens, fluxes%sens, diag)
2257  endif
2258  if ((handles%id_total_sens > 0) .and. ASSOCIATED(fluxes%sens)) then
2259  total_transport = global_area_integral(fluxes%sens,g)
2260  call post_data(handles%id_total_sens, total_transport, diag)
2261  endif
2262  if ((handles%id_sens_ga > 0) .and. ASSOCIATED(fluxes%sens)) then
2263  ave_flux = global_area_mean(fluxes%sens,g)
2264  call post_data(handles%id_sens_ga, ave_flux, diag)
2265  endif
2266 
2267  if ((handles%id_heat_added > 0) .and. ASSOCIATED(fluxes%heat_added)) then
2268  call post_data(handles%id_heat_added, fluxes%heat_added, diag)
2269  endif
2270 
2271  if ((handles%id_total_heat_added > 0) .and. ASSOCIATED(fluxes%heat_added)) then
2272  total_transport = global_area_integral(fluxes%heat_added,g)
2273  call post_data(handles%id_total_heat_added, total_transport, diag)
2274  endif
2275 
2276 
2277  ! post the diagnostics for boundary salt fluxes ==========================
2278 
2279  if ((handles%id_saltflux > 0) .and. ASSOCIATED(fluxes%salt_flux)) &
2280  call post_data(handles%id_saltflux, fluxes%salt_flux, diag)
2281  if ((handles%id_total_saltflux > 0) .and. ASSOCIATED(fluxes%salt_flux)) then
2282  total_transport = ppt2mks*global_area_integral(fluxes%salt_flux,g)
2283  call post_data(handles%id_total_saltflux, total_transport, diag)
2284  endif
2285 
2286  if ((handles%id_saltFluxAdded > 0) .and. ASSOCIATED(fluxes%salt_flux_added)) &
2287  call post_data(handles%id_saltFluxAdded, fluxes%salt_flux_added, diag)
2288  if ((handles%id_total_saltFluxAdded > 0) .and. ASSOCIATED(fluxes%salt_flux_added)) then
2289  total_transport = ppt2mks*global_area_integral(fluxes%salt_flux_added,g)
2290  call post_data(handles%id_total_saltFluxAdded, total_transport, diag)
2291  endif
2292 
2293  if (handles%id_saltFluxIn > 0 .and. ASSOCIATED(fluxes%salt_flux_in)) &
2294  call post_data(handles%id_saltFluxIn, fluxes%salt_flux_in, diag)
2295  if ((handles%id_total_saltFluxIn > 0) .and. ASSOCIATED(fluxes%salt_flux_in)) then
2296  total_transport = ppt2mks*global_area_integral(fluxes%salt_flux_in,g)
2297  call post_data(handles%id_total_saltFluxIn, total_transport, diag)
2298  endif
2299 
2300  if (handles%id_saltFluxGlobalAdj > 0) &
2301  call post_data(handles%id_saltFluxGlobalAdj, fluxes%saltFluxGlobalAdj, diag)
2302  if (handles%id_vPrecGlobalAdj > 0) &
2303  call post_data(handles%id_vPrecGlobalAdj, fluxes%vPrecGlobalAdj, diag)
2304  if (handles%id_netFWGlobalAdj > 0) &
2305  call post_data(handles%id_netFWGlobalAdj, fluxes%netFWGlobalAdj, diag)
2306  if (handles%id_saltFluxGlobalScl > 0) &
2307  call post_data(handles%id_saltFluxGlobalScl, fluxes%saltFluxGlobalScl, diag)
2308  if (handles%id_vPrecGlobalScl > 0) &
2309  call post_data(handles%id_vPrecGlobalScl, fluxes%vPrecGlobalScl, diag)
2310  if (handles%id_netFWGlobalScl > 0) &
2311  call post_data(handles%id_netFWGlobalScl, fluxes%netFWGlobalScl, diag)
2312 
2313 
2314  ! remaining boundary terms ==================================================
2315 
2316  if ((handles%id_psurf > 0) .and. ASSOCIATED(fluxes%p_surf)) &
2317  call post_data(handles%id_psurf, fluxes%p_surf, diag)
2318 
2319  if ((handles%id_TKE_tidal > 0) .and. ASSOCIATED(fluxes%TKE_tidal)) &
2320  call post_data(handles%id_TKE_tidal, fluxes%TKE_tidal, diag)
2321 
2322  if ((handles%id_buoy > 0) .and. ASSOCIATED(fluxes%buoy)) &
2323  call post_data(handles%id_buoy, fluxes%buoy, diag)
2324 
2325 
2326  endif
2327 
2328  call cpu_clock_end(handles%id_clock_forcing)
2329 end subroutine forcing_diagnostics
2330 
2331 
2332 !> Conditionally allocate fields within the forcing type
2333 subroutine allocate_forcing_type(G, fluxes, stress, ustar, water, heat, shelf, press, iceberg)
2334  type(ocean_grid_type), intent(in) :: G !< Ocean grid structure
2335  type(forcing), intent(inout) :: fluxes !< Forcing fields structure
2336  logical, optional, intent(in) :: stress !< If present and true, allocate taux, tauy
2337  logical, optional, intent(in) :: ustar !< If present and true, allocate ustar
2338  logical, optional, intent(in) :: water !< If present and true, allocate water fluxes
2339  logical, optional, intent(in) :: heat !< If present and true, allocate heat fluxes
2340  logical, optional, intent(in) :: shelf !< If present and true, allocate fluxes for ice-shelf
2341  logical, optional, intent(in) :: press !< If present and true, allocate p_surf
2342  logical, optional, intent(in) :: iceberg !< If present and true, allocate fluxes for icebergs
2343 
2344  ! Local variables
2345  integer :: isd, ied, jsd, jed, IsdB, IedB, JsdB, JedB
2346  logical :: heat_water
2347 
2348  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
2349  isdb = g%IsdB ; iedb = g%IedB ; jsdb = g%JsdB ; jedb = g%JedB
2350 
2351  call myalloc(fluxes%taux,isdb,iedb,jsd,jed, stress)
2352  call myalloc(fluxes%tauy,isd,ied,jsdb,jedb, stress)
2353  call myalloc(fluxes%ustar,isd,ied,jsd,jed, ustar)
2354 
2355  call myalloc(fluxes%evap,isd,ied,jsd,jed, water)
2356  call myalloc(fluxes%lprec,isd,ied,jsd,jed, water)
2357  call myalloc(fluxes%fprec,isd,ied,jsd,jed, water)
2358  call myalloc(fluxes%vprec,isd,ied,jsd,jed, water)
2359  call myalloc(fluxes%lrunoff,isd,ied,jsd,jed, water)
2360  call myalloc(fluxes%frunoff,isd,ied,jsd,jed, water)
2361  call myalloc(fluxes%seaice_melt,isd,ied,jsd,jed, water)
2362  call myalloc(fluxes%netMassOut,isd,ied,jsd,jed, water)
2363  call myalloc(fluxes%netMassIn,isd,ied,jsd,jed, water)
2364  call myalloc(fluxes%netSalt,isd,ied,jsd,jed, water)
2365 
2366  call myalloc(fluxes%sw,isd,ied,jsd,jed, heat)
2367  call myalloc(fluxes%lw,isd,ied,jsd,jed, heat)
2368  call myalloc(fluxes%latent,isd,ied,jsd,jed, heat)
2369  call myalloc(fluxes%sens,isd,ied,jsd,jed, heat)
2370  call myalloc(fluxes%latent_evap_diag,isd,ied,jsd,jed, heat)
2371  call myalloc(fluxes%latent_fprec_diag,isd,ied,jsd,jed, heat)
2372  call myalloc(fluxes%latent_frunoff_diag,isd,ied,jsd,jed, heat)
2373 
2374  if (present(heat) .and. present(water)) then ; if (heat .and. water) then
2375  call myalloc(fluxes%heat_content_cond,isd,ied,jsd,jed, .true.)
2376  call myalloc(fluxes%heat_content_lprec,isd,ied,jsd,jed, .true.)
2377  call myalloc(fluxes%heat_content_fprec,isd,ied,jsd,jed, .true.)
2378  call myalloc(fluxes%heat_content_vprec,isd,ied,jsd,jed, .true.)
2379  call myalloc(fluxes%heat_content_lrunoff,isd,ied,jsd,jed, .true.)
2380  call myalloc(fluxes%heat_content_frunoff,isd,ied,jsd,jed, .true.)
2381  call myalloc(fluxes%heat_content_massout,isd,ied,jsd,jed, .true.)
2382  call myalloc(fluxes%heat_content_massin,isd,ied,jsd,jed, .true.)
2383  endif ; endif
2384 
2385  call myalloc(fluxes%frac_shelf_h,isd,ied,jsd,jed, shelf)
2386  call myalloc(fluxes%frac_shelf_u,isdb,iedb,jsd,jed, shelf)
2387  call myalloc(fluxes%frac_shelf_v,isd,ied,jsdb,jedb, shelf)
2388  call myalloc(fluxes%ustar_shelf,isd,ied,jsd,jed, shelf)
2389  call myalloc(fluxes%iceshelf_melt,isd,ied,jsd,jed, shelf)
2390  call myalloc(fluxes%rigidity_ice_u,isdb,iedb,jsd,jed, shelf)
2391  call myalloc(fluxes%rigidity_ice_v,isd,ied,jsdb,jedb, shelf)
2392 
2393  call myalloc(fluxes%p_surf,isd,ied,jsd,jed, press)
2394 
2395  !These fields should only on allocated when iceberg area is being passed through the coupler.
2396  call myalloc(fluxes%ustar_berg,isd,ied,jsd,jed, iceberg)
2397  call myalloc(fluxes%area_berg,isd,ied,jsd,jed, iceberg)
2398  call myalloc(fluxes%mass_berg,isd,ied,jsd,jed, iceberg)
2399  contains
2400 
2401  !> Allocates and zeroes-out array.
2402  subroutine myalloc(array, is, ie, js, je, flag)
2403  real, dimension(:,:), pointer :: array !< Array to be allocated
2404  integer, intent(in) :: is !< Start i-index
2405  integer, intent(in) :: ie !< End i-index
2406  integer, intent(in) :: js !< Start j-index
2407  integer, intent(in) :: je !< End j-index
2408  logical, optional, intent(in) :: flag !< Flag to indicate to allocate
2409 
2410  if (present(flag)) then
2411  if (flag) then
2412  if (.not.associated(array)) then
2413  ALLOCATE(array(is:ie,js:je))
2414  array(is:ie,js:je) = 0.0
2415  endif
2416  endif
2417  endif
2418  end subroutine myalloc
2419 
2420 end subroutine allocate_forcing_type
2421 
2422 
2423 !> Deallocate the forcing type
2424 subroutine deallocate_forcing_type(fluxes)
2425  type(forcing), intent(inout) :: fluxes !< Forcing fields structure
2426 
2427  if (associated(fluxes%taux)) deallocate(fluxes%taux)
2428  if (associated(fluxes%tauy)) deallocate(fluxes%tauy)
2429  if (associated(fluxes%ustar)) deallocate(fluxes%ustar)
2430  if (associated(fluxes%buoy)) deallocate(fluxes%buoy)
2431  if (associated(fluxes%sw)) deallocate(fluxes%sw)
2432  if (associated(fluxes%sw_vis_dir)) deallocate(fluxes%sw_vis_dir)
2433  if (associated(fluxes%sw_vis_dif)) deallocate(fluxes%sw_vis_dif)
2434  if (associated(fluxes%sw_nir_dir)) deallocate(fluxes%sw_nir_dir)
2435  if (associated(fluxes%sw_nir_dif)) deallocate(fluxes%sw_nir_dif)
2436  if (associated(fluxes%lw)) deallocate(fluxes%lw)
2437  if (associated(fluxes%latent)) deallocate(fluxes%latent)
2438  if (associated(fluxes%latent_evap_diag)) deallocate(fluxes%latent_evap_diag)
2439  if (associated(fluxes%latent_fprec_diag)) deallocate(fluxes%latent_fprec_diag)
2440  if (associated(fluxes%latent_frunoff_diag)) deallocate(fluxes%latent_frunoff_diag)
2441  if (associated(fluxes%sens)) deallocate(fluxes%sens)
2442  if (associated(fluxes%heat_added)) deallocate(fluxes%heat_added)
2443  if (associated(fluxes%heat_content_lrunoff)) deallocate(fluxes%heat_content_lrunoff)
2444  if (associated(fluxes%heat_content_frunoff)) deallocate(fluxes%heat_content_frunoff)
2445  if (associated(fluxes%heat_content_lprec)) deallocate(fluxes%heat_content_lprec)
2446  if (associated(fluxes%heat_content_fprec)) deallocate(fluxes%heat_content_fprec)
2447  if (associated(fluxes%heat_content_cond)) deallocate(fluxes%heat_content_cond)
2448  if (associated(fluxes%heat_content_massout)) deallocate(fluxes%heat_content_massout)
2449  if (associated(fluxes%heat_content_massin)) deallocate(fluxes%heat_content_massin)
2450  if (associated(fluxes%evap)) deallocate(fluxes%evap)
2451  if (associated(fluxes%lprec)) deallocate(fluxes%lprec)
2452  if (associated(fluxes%fprec)) deallocate(fluxes%fprec)
2453  if (associated(fluxes%vprec)) deallocate(fluxes%vprec)
2454  if (associated(fluxes%lrunoff)) deallocate(fluxes%lrunoff)
2455  if (associated(fluxes%frunoff)) deallocate(fluxes%frunoff)
2456  if (associated(fluxes%seaice_melt)) deallocate(fluxes%seaice_melt)
2457  if (associated(fluxes%salt_flux)) deallocate(fluxes%salt_flux)
2458  if (associated(fluxes%p_surf_full)) deallocate(fluxes%p_surf_full)
2459  if (associated(fluxes%p_surf)) deallocate(fluxes%p_surf)
2460  if (associated(fluxes%TKE_tidal)) deallocate(fluxes%TKE_tidal)
2461  if (associated(fluxes%ustar_tidal)) deallocate(fluxes%ustar_tidal)
2462  if (associated(fluxes%ustar_shelf)) deallocate(fluxes%ustar_shelf)
2463  if (associated(fluxes%iceshelf_melt)) deallocate(fluxes%iceshelf_melt)
2464  if (associated(fluxes%frac_shelf_h)) deallocate(fluxes%frac_shelf_h)
2465  if (associated(fluxes%frac_shelf_u)) deallocate(fluxes%frac_shelf_u)
2466  if (associated(fluxes%frac_shelf_v)) deallocate(fluxes%frac_shelf_v)
2467  if (associated(fluxes%rigidity_ice_u)) deallocate(fluxes%rigidity_ice_u)
2468  if (associated(fluxes%rigidity_ice_v)) deallocate(fluxes%rigidity_ice_v)
2469  if (associated(fluxes%tr_fluxes)) deallocate(fluxes%tr_fluxes)
2470  if (associated(fluxes%ustar_berg)) deallocate(fluxes%ustar_berg)
2471  if (associated(fluxes%area_berg)) deallocate(fluxes%area_berg)
2472  if (associated(fluxes%mass_berg)) deallocate(fluxes%mass_berg)
2473 end subroutine deallocate_forcing_type
2474 
2475 
2476 !> \namespace mom_forcing_type
2477 !!
2478 !! \section section_fluxes Boundary fluxes
2479 !!
2480 !! The ocean is a forced-dissipative system. Forcing occurs at the
2481 !! boundaries, and this module mediates the various forcing terms
2482 !! from momentum, heat, salt, and mass. Boundary fluxes from other
2483 !! tracers are treated by coupling to biogeochemical models. We
2484 !! here present elements of how MOM6 assumes boundary fluxes are
2485 !! passed into the ocean.
2486 !!
2487 !! Note that all fluxes are positive into the ocean. For surface
2488 !! boundary fluxes, that means fluxes are positive downward.
2489 !! For example, a positive shortwave flux warms the ocean.
2490 !!
2491 !! \subsection subsection_momentum_fluxes Surface boundary momentum fluxes
2492 !!
2493 !! The ocean surface exchanges momentum with the overlying atmosphere,
2494 !! sea ice, and land ice. The momentum is exchanged as a horizontal
2495 !! stress (Newtons per squared meter: N/m2) imposed on the upper ocean
2496 !! grid cell.
2497 !!
2498 !! \subsection subsection_mass_fluxes Surface boundary mass fluxes
2499 !!
2500 !! The ocean gains or loses mass through evaporation, precipitation,
2501 !! sea ice melt/form, and and river runoff. Positive mass fluxes
2502 !! add mass to the liquid ocean. The boundary mass flux units are
2503 !! (kilogram per square meter per sec: kg/(m2/sec)).
2504 !!
2505 !! * Evaporation field can in fact represent a
2506 !! mass loss (evaporation) or mass gain (condensation in foggy areas).
2507 !! * sea ice formation leads to mass moving from the liquid ocean to the
2508 !! ice model, and melt adds liquid to the ocean.
2509 !! * Precipitation can be liquid or frozen (snow). Furthermore, in
2510 !! some versions of the GFDL coupler, precipitation can be negative.
2511 !! The reason is that the ice model combines precipitation with
2512 !! ice melt and ice formation. This limitation of the ice model
2513 !! diagnostics should be overcome future versions.
2514 !! * River runoff can be liquid or frozen. Frozen runoff is often
2515 !! associated with calving land-ice and/or ice bergs.
2516 !!
2517 !! \subsection subsection_salt_fluxes Surface boundary salt fluxes
2518 !!
2519 !! Over most of the ocean, there is no exchange of salt with the
2520 !! atmosphere. However, the liquid ocean exchanges salt with sea ice.
2521 !! When ice forms, it extracts salt from ice pockets and discharges the
2522 !! salt into the liquid ocean. The salt concentration of sea ice
2523 !! is therefore much lower (around 5ppt) than liquid seawater
2524 !! (around 30-35ppt in high latitudes).
2525 !!
2526 !! For ocean-ice models run with a prescribed atmosphere, such as
2527 !! in the CORE/OMMIP simulations, it is necessary to employ a surface
2528 !! restoring term to the k=1 salinity equation, thus imposing a salt
2529 !! flux onto the ocean even outside of sea ice regimes. This salt
2530 !! flux is non-physical, and represents a limitation of the ocean-ice
2531 !! models run without an interactive atmosphere. Sometimes this salt
2532 !! flux is converted to an implied fresh water flux. However, doing
2533 !! so generally leads to changes in the sea level, unless a global
2534 !! normalization is provided to zero-out the net water flux.
2535 !! As a complement, for models with a restoring salt flux, one may
2536 !! choose to zero-out the net salt entering the ocean. There are
2537 !! pros/cons of each approach.
2538 !!
2539 !!
2540 !! \subsection subsection_heat_fluxes Surface boundary heat fluxes
2541 !!
2542 !! There are many terms that contribute to boundary-related heating
2543 !! of the k=1 surface model grid cell. We here outline details of
2544 !! this heat, with each term having units W/m2.
2545 !!
2546 !! The net flux of heat crossing ocean surface is stored in the diagnostic
2547 !! array "hfds". This array is computed as
2548 !! \f[
2549 !! \mbox{hfds = shortwave + longwave + latent + sensible + mass transfer + frazil + restore + flux adjustments}
2550 !! \f]
2551 !!
2552 !! * shortwave (SW) = shortwave radiation (always warms ocean)
2553 !! * longwave (LW) = longwave radiation (generally cools ocean)
2554 !! * latent (LAT) = turbulent latent heat loss due to evaporation
2555 !! (liquid to vapor) or melt (snow to liquid); generally
2556 !! cools the ocean
2557 !! * sensible (SENS) = turbulent heat transfer due to differences in
2558 !! air-sea or ice-sea temperature
2559 !! * mass transfer (MASS) = heat transfer due to heat content of mass (e.g., E-P+R)
2560 !! transferred across ocean surface; computed relative
2561 !! to 0 Celsius
2562 !! * frazil (FRAZ) = heat transferred to form frazil sea ice
2563 !! (positive heating of liquid ocean)
2564 !! * restore (RES) = heat from surface damping sometimes imposed
2565 !! in non-coupled model simulations .
2566 !! * restore (flux adjustments) = heat from surface flux adjustment.
2567 !!
2568 !! \subsubsection subsubsection_SW Treatment of shortwave
2569 !!
2570 !! The shortwave field itself is split into two pieces:
2571 !!
2572 !! * shortwave = penetrative SW + non-penetrative SW
2573 !! * non-penetrative = non-downwelling shortwave; portion of SW
2574 !! totally absorbed in the k=1 cell.
2575 !! The non-penetrative SW is combined with
2576 !! LW+LAT+SENS in net_heat inside routine
2577 !! extractFluxes1d. Notably, for many cases,
2578 !! non-penetrative SW = 0.
2579 !! * penetrative = that portion of shortwave penetrating below
2580 !! a tiny surface layer. This is the downwelling
2581 !! shortwave. Penetrative SW participates in
2582 !! the penetrative SW heating of k=1,nz cells,
2583 !! with the amount of penetration dependent on
2584 !! optical properties.
2585 !!
2586 !! \subsubsection subsubsection_bdy_heating Convergence of heat into the k=1 cell
2587 !!
2588 !! The convergence of boundary-related heat into surface grid cell is
2589 !! given by the difference in the net heat entering the top of the k=1
2590 !! cell and the penetrative SW leaving the bottom of the cell.
2591 !! \f{eqnarray*}{
2592 !! Q(k=1) &=& \mbox{hfds} - \mbox{pen_SW(leaving bottom of k=1)}
2593 !! \\ &=& \mbox{nonpen_SW} + (\mbox{pen_SW(enter k=1)}-\mbox{pen_SW(leave k=1)})
2594 !! + \mbox{LW+LAT+SENS+MASS+FRAZ+RES}
2595 !! \\ &=& \mbox{nonpen_SW}+ \mbox{LW+LAT+SENS+MASS+FRAZ+RES}
2596 !! + [\mbox{pen_SW(enter k=1)} - \mbox{pen_SW(leave k=1)}]
2597 !! \f}
2598 !! The convergence of the penetrative shortwave flux is given by
2599 !! \f$ \mbox{pen_SW (enter k)}-\mbox{pen_SW (leave k)}\f$. This term
2600 !! appears for all cells k=1,nz. It is diagnosed as "rsdoabsorb" inside module
2601 !! MOM6/src/parameterizations/vertical/MOM_diabatic_aux.F90
2602 !!
2603 
2604 end module mom_forcing_type
The following structure contains pointers to various fields which may be used describe the surface st...
This module implements boundary forcing for MOM6.
integer function, public register_scalar_field(module_name, field_name, init_time, diag_cs, long_name, units, missing_value, range, standard_name, do_not_log, err_msg, interp_method, cmor_field_name, cmor_long_name, cmor_units, cmor_standard_name)
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
The following data type a list of diagnostic fields an their variants, as well as variables that cont...
Provides the ocean grid type.
Definition: MOM_grid.F90:2
subroutine myalloc(array, is, ie, js, je, flag)
Allocates and zeroes-out array.
subroutine, public mom_forcing_chksum(mesg, fluxes, G, haloshift)
Write out chksums for basic state variables.
subroutine, public allocate_forcing_type(G, fluxes, stress, ustar, water, heat, shelf, press, iceberg)
Conditionally allocate fields within the forcing type.
subroutine, public extractfluxes2d(G, GV, fluxes, optics, nsw, dt, DepthBeforeScalingFluxes, useRiverHeatContent, useCalvingHeatContent, h, T, netMassInOut, netMassOut, net_heat, Net_salt, Pen_SW_bnd, tv, aggregate_FW_forcing)
2d wrapper for 1d extract fluxes from surface fluxes type. This subroutine extracts fluxes from the s...
real function, public global_area_integral(var, G)
subroutine, public forcing_accumulate(flux_tmp, fluxes, dt, G, wt2)
Accumulate the forcing over time steps.
logical function, public query_averaging_enabled(diag_cs, time_int, time_end)
subroutine, public sumswoverbands(G, GV, h, opacity_band, nsw, j, dt, H_limit_fluxes, absorbAllSW, iPen_SW_bnd, netPen)
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
subroutine, public register_forcing_type_diags(Time, diag, use_temperature, handles, use_berg_fluxes)
Register members of the forcing type for diagnostics.
subroutine, public forcing_diagnostics(fluxes, state, dt, G, diag, handles)
Offer buoyancy forcing fields for diagnostics for those fields registered as part of register_forcing...
subroutine, public calculatebuoyancyflux2d(G, GV, fluxes, optics, h, Temp, Salt, tv, buoyancyFlux, netHeatMinusSW, netSalt, skip_diags)
Calculates surface buoyancy flux by adding up the heat, FW and salt fluxes, for 2d arrays...
Structure that contains pointers to the boundary forcing used to drive the liquid ocean simulated by ...
Provides subroutines for quantities specific to the equation of state.
Definition: MOM_EOS.F90:2
subroutine, public calculatebuoyancyflux1d(G, GV, fluxes, optics, h, Temp, Salt, tv, j, buoyancyFlux, netHeatMinusSW, netSalt, skip_diags)
This routine calculates surface buoyancy flux by adding up the heat, FW & salt fluxes. These are actual fluxes, with units of stuff per time. Setting dt=1 in the call to extractFluxes routine allows us to get "stuf per time" rather than the time integrated fluxes needed in other routines that call extractFluxes.
subroutine, public extractfluxes1d(G, GV, fluxes, optics, nsw, j, dt, DepthBeforeScalingFluxes, useRiverHeatContent, useCalvingHeatContent, h, T, netMassInOut, netMassOut, net_heat, net_salt, pen_SW_bnd, tv, aggregate_FW_forcing, nonpenSW, netmassInOut_rate, net_Heat_Rate, net_salt_rate, pen_sw_bnd_Rate, skip_diags)
This subroutine extracts fluxes from the surface fluxes type. It works on a j-row for optimization pu...
The thermo_var_ptrs structure contains pointers to an assortment of thermodynamic fields that may be ...
subroutine locmsg(array, aname)
Format and write a message depending on associated state of array.
subroutine, public deallocate_forcing_type(fluxes)
Deallocate the forcing type.
real function, public global_area_mean(var, G)
Structure that defines the id handles for the forcing type.
integer function, public register_diag_field(module_name, field_name, axes, init_time, long_name, units, missing_value, range, mask_variant, standard_name, verbose, do_not_log, err_msg, interp_method, tile_count, cmor_field_name, cmor_long_name, cmor_units, cmor_standard_name, cell_methods, x_cell_method, y_cell_method, v_cell_method, conversion, v_extensive)
Returns the "diag_mediator" handle for a group (native, CMOR, z-coord, ...) of diagnostics derived fr...
subroutine, public mom_error(level, message, all_print)
subroutine, public mech_forcing_diags(fluxes, dt, G, diag, handles)
Offer mechanical forcing fields for diagnostics for those fields registered as part of register_forci...
subroutine, public forcing_singlepointprint(fluxes, G, i, j, mesg)
Write out values of the fluxes arrays at the i,j location. This is a debugging tool.