7 use mom_cpu_clock, only : cpu_clock_id, cpu_clock_begin, cpu_clock_end, clock_routine
21 implicit none ;
private 23 #include <MOM_memory.h> 42 real,
pointer,
dimension(:,:) :: &
48 real,
pointer,
dimension(:,:) :: &
52 real,
pointer,
dimension(:,:) :: &
54 sw_vis_dir => null(), &
55 sw_vis_dif => null(), &
56 sw_nir_dir => null(), &
57 sw_nir_dif => null(), &
61 real,
pointer,
dimension(:,:) :: &
67 real,
pointer,
dimension(:,:) :: &
68 latent_evap_diag => null(), &
69 latent_fprec_diag => null(), &
70 latent_frunoff_diag => null()
73 real,
pointer,
dimension(:,:) :: &
80 seaice_melt => null(), &
81 netmassin => null(), &
82 netmassout => null(), &
86 real,
pointer,
dimension(:,:) :: &
87 heat_content_cond => null(), &
88 heat_content_lprec => null(), &
89 heat_content_fprec => null(), &
90 heat_content_vprec => null(), &
91 heat_content_lrunoff => null(), &
92 heat_content_frunoff => null(), &
93 heat_content_icemelt => null(), &
94 heat_content_massout => null(), &
95 heat_content_massin => null()
98 real,
pointer,
dimension(:,:) :: &
99 salt_flux => null(), &
100 salt_flux_in => null(), &
101 salt_flux_added => null()
105 real,
pointer,
dimension(:,:) :: &
106 p_surf_full => null(), &
118 real,
pointer,
dimension(:,:) :: &
119 tke_tidal => null(), &
120 ustar_tidal => null()
123 real,
pointer,
dimension(:,:) :: &
124 ustar_berg => null(),&
125 area_berg => null(),&
129 real,
pointer,
dimension(:,:) :: &
130 ustar_shelf => null(), &
132 frac_shelf_h => null(), &
133 frac_shelf_u => null(), &
134 frac_shelf_v => null(), &
136 iceshelf_melt => null(), &
137 rigidity_ice_u => null(),&
138 rigidity_ice_v => null()
141 real :: vprecglobaladj
142 real :: saltfluxglobaladj
143 real :: netfwglobaladj
144 real :: vprecglobalscl
145 real :: saltfluxglobalscl
146 real :: netfwglobalscl
148 logical :: fluxes_used = .true.
150 real :: dt_buoy_accum = -1.0
165 integer :: num_msg = 0
166 integer :: max_msg = 2
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
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
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
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
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
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
229 integer :: id_saltflux = -1
230 integer :: id_saltfluxin = -1
231 integer :: id_saltfluxadded = -1
233 integer :: id_total_saltflux = -1
234 integer :: id_total_saltfluxin = -1
235 integer :: id_total_saltfluxadded = -1
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
245 integer :: id_taux = -1
246 integer :: id_tauy = -1
247 integer :: id_ustar = -1
249 integer :: id_psurf = -1
250 integer :: id_tke_tidal = -1
251 integer :: id_buoy = -1
254 integer :: id_clock_forcing
257 integer :: id_ustar_berg = -1
258 integer :: id_area_berg = -1
259 integer :: id_mass_berg = -1
262 integer :: id_ustar_ice_cover = -1
263 integer :: id_frac_ice_cover = -1
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)
281 type(
forcing),
intent(inout) :: fluxes
284 integer,
intent(in) :: nsw
285 integer,
intent(in) :: j
286 real,
intent(in) :: dt
287 real,
intent(in) :: DepthBeforeScalingFluxes
288 logical,
intent(in) :: useRiverHeatContent
289 logical,
intent(in) :: useCalvingHeatContent
290 real,
dimension(SZI_(G),SZK_(G)),
intent(in) :: h
291 real,
dimension(SZI_(G),SZK_(G)),
intent(in) :: T
292 real,
dimension(SZI_(G)),
intent(out) :: netMassInOut
295 real,
dimension(SZI_(G)),
intent(out) :: netMassOut
299 real,
dimension(SZI_(G)),
intent(out) :: net_heat
306 real,
dimension(SZI_(G)),
intent(out) :: net_salt
308 real,
dimension(:,:),
intent(out) :: pen_SW_bnd
317 logical,
intent(in) :: aggregate_FW_forcing
318 real,
dimension(SZI_(G)),
optional,
intent(out) :: nonpenSW
321 real,
dimension(SZI_(G)),
optional,
intent(out) :: net_Heat_rate
322 real,
dimension(SZI_(G)),
optional,
intent(out) :: net_salt_rate
323 real,
dimension(SZI_(G)),
optional,
intent(out) :: netmassInOut_rate
324 real,
dimension(:,:),
optional,
intent(out) :: pen_sw_bnd_rate
325 logical,
optional,
intent(in) :: skip_diags
329 real :: htot(szi_(g))
330 real :: Pen_sw_tot(szi_(g))
331 real :: pen_sw_tot_rate(szi_(g))
337 logical :: calculate_diags
338 character(len=200) :: mesg
339 integer :: is, ie, nz, i, k, n
341 logical :: do_NHR, do_NSR, do_NMIOR, do_PSWBR
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.
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)
362 is = g%isc ; ie = g%iec ; nz = g%ke
364 calculate_diags = .true.
365 if (
present(skip_diags)) calculate_diags = .not. skip_diags
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.")
373 if (.not.
ASSOCIATED(fluxes%sw))
call mom_error(fatal, &
374 "MOM_forcing_type extractFluxes1d: fluxes%sw is not associated.")
376 if (.not.
ASSOCIATED(fluxes%lw))
call mom_error(fatal, &
377 "MOM_forcing_type extractFluxes1d: fluxes%lw is not associated.")
379 if (.not.
ASSOCIATED(fluxes%latent))
call mom_error(fatal, &
380 "MOM_forcing_type extractFluxes1d: fluxes%latent is not associated.")
382 if (.not.
ASSOCIATED(fluxes%sens))
call mom_error(fatal, &
383 "MOM_forcing_type extractFluxes1d: fluxes%sens is not associated.")
385 if (.not.
ASSOCIATED(fluxes%evap))
call mom_error(fatal, &
386 "MOM_forcing_type extractFluxes1d: No evaporation defined.")
388 if (.not.
ASSOCIATED(fluxes%vprec))
call mom_error(fatal, &
389 "MOM_forcing_type extractFluxes1d: fluxes%vprec not defined.")
391 if ((.not.
ASSOCIATED(fluxes%lprec)) .or. &
392 (.not.
ASSOCIATED(fluxes%fprec)))
call mom_error(fatal, &
393 "MOM_forcing_type extractFluxes1d: No precipitation defined.")
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 402 if (htot(i)*ih_limit < 1.0) scale = htot(i)*ih_limit
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)
413 pen_sw_bnd(1,i) = 0.0
419 pen_sw_tot_rate(i) = 0.0
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)
426 pen_sw_bnd_rate(1,i) = 0.0
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) ) )
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) ) )
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))
460 if (do_nmior) netmassinout_rate(i) = netmassinout_rate(i) + (gv%kg_m2_to_H) * (scale * fluxes%salt_flux(i,j))
471 if(fluxes%evap(i,j) < 0.0)
then 472 netmassout(i) = netmassout(i) + fluxes%evap(i,j)
478 if(fluxes%lprec(i,j) < 0.0)
then 479 netmassout(i) = netmassout(i) + fluxes%lprec(i,j)
484 if(fluxes%vprec(i,j) < 0.0)
then 485 netmassout(i) = netmassout(i) + fluxes%vprec(i,j)
487 netmassout(i) = dt * scale * netmassout(i)
490 netmassinout(i) = gv%kg_m2_to_H * netmassinout(i)
493 if (do_nmior) netmassinout_rate(i) = gv%kg_m2_to_H * netmassinout_rate(i)
495 netmassout(i) = gv%kg_m2_to_H * netmassout(i)
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)) )
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)) )
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)
514 if (useriverheatcontent)
then 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)
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))
531 if (usecalvingheatcontent)
then 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)
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))
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)
576 net_heat(i) = net_heat(i) - pen_sw_tot(i)
579 if (do_nhr) net_heat_rate(i) = net_heat_rate(i) - pen_sw_tot_rate(i)
583 if (
present(nonpensw))
then 584 nonpensw(i) = scale * dt * j_m2_to_h * fluxes%sw(i,j) - pen_sw_tot(i)
589 if (do_nsr) net_salt_rate(i) = 0.0
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
597 if (do_nsr) net_salt_rate(i) = (scale * 1. * (1000.0 * fluxes%salt_flux(i,j))) * gv%kg_m2_to_H
602 if (calculate_diags)
then 605 if (
ASSOCIATED(fluxes%salt_flux))
then 606 if (calculate_diags) fluxes%netSalt(i,j) = net_salt(i)
611 if (
ASSOCIATED(fluxes%heat_content_massin))
then 612 if (aggregate_fw_forcing)
then 613 if (netmassinout(i) > 0.0)
then 614 fluxes%heat_content_massin(i,j) = -fluxes%C_p * netmassout(i) * t(i,1) * gv%H_to_kg_m2 / dt
616 fluxes%heat_content_massin(i,j) = fluxes%C_p * ( netmassinout(i) - netmassout(i) ) * t(i,1) * gv%H_to_kg_m2 / dt
619 fluxes%heat_content_massin(i,j) = 0.
625 if (
ASSOCIATED(fluxes%heat_content_massout))
then 626 if (aggregate_fw_forcing)
then 627 if (netmassinout(i) > 0.0)
then 628 fluxes%heat_content_massout(i,j) = fluxes%C_p * netmassout(i) * t(i,1) * gv%H_to_kg_m2 / dt
630 fluxes%heat_content_massout(i,j) = -fluxes%C_p * ( netmassinout(i) - netmassout(i) ) * t(i,1) * gv%H_to_kg_m2 / dt
633 fluxes%heat_content_massout(i,j) = 0.0
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)
648 fluxes%heat_content_lprec(i,j) = 0.0
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)
659 fluxes%heat_content_fprec(i,j) = 0.0
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)
670 fluxes%heat_content_vprec(i,j) = 0.0
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)
684 fluxes%heat_content_cond(i,j) = 0.0
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)
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)
713 DepthBeforeScalingFluxes, useRiverHeatContent, useCalvingHeatContent, &
714 h, T, netMassInOut, netMassOut, net_heat, Net_salt, Pen_SW_bnd, tv, &
715 aggregate_FW_forcing)
719 type(
forcing),
intent(inout) :: fluxes
721 integer,
intent(in) :: nsw
722 real,
intent(in) :: dt
723 real,
intent(in) :: DepthBeforeScalingFluxes
724 logical,
intent(in) :: useRiverHeatContent
725 logical,
intent(in) :: useCalvingHeatContent
726 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)),
intent(in) :: h
727 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)),
intent(in) :: T
728 real,
dimension(SZI_(G),SZJ_(G)),
intent(out) :: netMassInOut
731 real,
dimension(SZI_(G),SZJ_(G)),
intent(out) :: netMassOut
734 real,
dimension(SZI_(G),SZJ_(G)),
intent(out) :: net_heat
741 real,
dimension(SZI_(G),SZJ_(G)),
intent(out) :: net_salt
743 real,
dimension(:,:,:),
intent(out) :: pen_SW_bnd
751 logical,
intent(in) :: aggregate_FW_forcing
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)
774 buoyancyFlux, netHeatMinusSW, netSalt, skip_diags)
777 type(
forcing),
intent(inout) :: fluxes
779 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)),
intent(in) :: h
780 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)),
intent(in) :: Temp
781 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)),
intent(in) :: Salt
783 integer,
intent(in) :: j
784 real,
dimension(SZI_(G),SZK_(G)+1),
intent(inout) :: buoyancyFlux
785 real,
dimension(SZI_(G)),
intent(inout) :: netHeatMinusSW
786 real,
dimension(SZI_(G)),
intent(inout) :: netSalt
787 logical,
optional,
intent(in) :: skip_diags
790 integer :: nsw, start, npts, k
791 real,
parameter :: dt = 1.
792 real,
dimension( SZI_(G) ) :: netH
793 real,
dimension( SZI_(G) ) :: netEvap
794 real,
dimension( SZI_(G) ) :: netHeat
795 real,
dimension( optics%nbands, SZI_(G) ) :: penSWbnd
796 real,
dimension( SZI_(G) ) :: pressure
797 real,
dimension( SZI_(G) ) :: dRhodT
798 real,
dimension( SZI_(G) ) :: dRhodS
799 real,
dimension(SZI_(G),SZK_(G)+1) :: netPen
801 logical :: useRiverHeatContent
802 logical :: useCalvingHeatContent
803 real :: depthBeforeScalingFluxes, GoRho
804 real :: H_limit_fluxes
809 useriverheatcontent = .false.
810 usecalvingheatcontent = .false.
812 depthbeforescalingfluxes = max( gv%Angstrom, 1.e-30*gv%m_to_H )
814 gorho = gv%g_Earth / gv%Rho0
815 start = 1 + g%isc - g%isd
816 npts = 1 + g%iec - g%isc
818 h_limit_fluxes = depthbeforescalingfluxes
828 depthbeforescalingfluxes, useriverheatcontent, usecalvingheatcontent, &
829 h(:,j,:), temp(:,j,:), neth, netevap, netheatminussw, &
830 netsalt, penswbnd, tv, .false., skip_diags=skip_diags)
834 call sumswoverbands(g, gv, h(:,j,:), optics%opacity_band(:,:,j,:), nsw, j, dt, &
835 h_limit_fluxes, .true., penswbnd, netpen)
839 drhodt, drhods, start, npts, tv%eqn_of_state)
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
847 netheat(g%isc:g%iec) = netheatminussw(g%isc:g%iec) + netpen(g%isc:g%iec,1)
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
854 buoyancyflux(g%isc:g%iec,k) = - gorho * ( drhodt(g%isc:g%iec) * netpen(g%isc:g%iec,k) ) * gv%H_to_m
863 buoyancyFlux, netHeatMinusSW, netSalt, skip_diags)
866 type(
forcing),
intent(inout) :: fluxes
868 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)),
intent(in) :: h
869 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)),
intent(in) :: Temp
870 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)),
intent(in) :: Salt
872 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)+1),
intent(inout) :: buoyancyFlux
873 real,
dimension(SZI_(G),SZJ_(G)),
optional,
intent(inout) :: netHeatMinusSW
874 real,
dimension(SZI_(G),SZJ_(G)),
optional,
intent(inout) :: netSalt
875 logical,
optional,
intent(in) :: skip_diags
878 real,
dimension( SZI_(G) ) :: netT
879 real,
dimension( SZI_(G) ) :: netS
882 nett(g%isc:g%iec) = 0. ; nets(g%isc:g%iec) = 0.
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)
899 character(len=*),
intent(in) :: mesg
900 type(
forcing),
intent(in) :: fluxes
902 integer,
optional,
intent(in) :: haloshift
904 integer :: is, ie, js, je, nz, hshift
905 is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
907 hshift=1;
if (
present(haloshift)) hshift=haloshift
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)
982 character(len=*),
intent(in) :: mesg
983 integer,
intent(in) :: i
984 integer,
intent(in) :: j
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')
1024 subroutine locmsg(array,aname)
1025 real,
dimension(:,:),
pointer :: array
1026 character(len=*) :: aname
1028 if (
associated(array))
then 1029 write(0,
'(3a,es15.3)')
'MOM_forcing_type, forcing_SinglePointPrint: ',trim(aname),
' = ',array(i,j)
1031 write(0,
'(4a)')
'MOM_forcing_type, forcing_SinglePointPrint: ',trim(aname),
' is not associated.' 1041 type(time_type),
intent(in) :: Time
1043 logical,
intent(in) :: use_temperature
1045 logical,
optional,
intent(in) :: use_berg_fluxes
1048 handles%id_clock_forcing=cpu_clock_id(
'(Ocean forcing diagnostics)', grain=clock_routine)
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')
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')
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')
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')
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')
1074 handles%id_mass_berg = register_diag_field(
'ocean_model',
'mass_berg', diag%axesT1, time, &
1075 'Mass of icebergs ',
'kg/m2')
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')
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')
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')
1090 handles%id_TKE_tidal = register_diag_field(
'ocean_model',
'TKE_tidal', diag%axesT1, time, &
1091 'Tidal source of BBL mixing',
'Watt/m^2')
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')
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')
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')
1123 handles%id_precip = register_diag_field(
'ocean_model',
'precip', diag%axesT1, time, &
1124 'Liquid + frozen precipitation into ocean',
'kilogram/(meter^2 * second)')
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')
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')
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)')
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')
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')
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')
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')
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)', &
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')
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')
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')
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')
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')
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')
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')
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')
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')
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')
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')
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')
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')
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')
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')
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')
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')
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')
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')
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')
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', &
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',&
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',&
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',&
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')
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)', &
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',&
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')
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',&
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)',&
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')
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', &
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', &
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')
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')
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')
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')
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')
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')
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')
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')
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',&
1392 'Temperature Flux due to Solid Runoff Expressed as Heat Flux into Sea Water Area Integrated')
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',&
1401 'Temperature Flux due to Runoff Expressed as Heat Flux into Sea Water Area Integrated')
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',&
1410 'Temperature Flux due to Rainfall Expressed as Heat Flux into Sea Water Area Integrated')
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',&
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',&
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',&
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',&
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', &
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')
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',&
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)',&
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', &
1455 cmor_field_name=
'total_hfds', cmor_units=
'W', &
1456 cmor_standard_name=
'surface_downward_heat_flux_in_sea_water_area_integrated', &
1458 'Surface Ocean Heat Flux from SW+LW+latent+sensible+mass transfer+frazil Area Integrated')
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', &
1464 cmor_field_name=
'total_rsntds', cmor_units=
'W', &
1465 cmor_standard_name=
'net_downward_shortwave_flux_at_sea_water_surface_area_integrated',&
1467 'Net Downward Shortwave Radiation at Sea Water Surface Area Integrated')
1469 handles%id_total_LwLatSens = register_scalar_field(
'ocean_model',&
1470 'total_LwLatSens', time, diag, &
1471 long_name=
'Area integrated longwave+latent+sensible heating',&
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', &
1478 cmor_field_name=
'total_rlntds', cmor_units=
'W', &
1479 cmor_standard_name=
'surface_net_downward_longwave_flux_area_integrated',&
1481 'Surface Net Downward Longwave Radiation Area Integrated')
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', &
1487 cmor_field_name=
'total_hflso', cmor_units=
'W', &
1488 cmor_standard_name=
'surface_downward_latent_heat_flux_area_integrated',&
1490 'Surface Downward Latent Heat Flux Area Integrated')
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',&
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', &
1501 cmor_field_name=
'total_hfsnthermds', cmor_units=
'W', &
1502 cmor_standard_name=
'heat_flux_into_sea_water_due_to_snow_thermodynamics_area_integrated',&
1504 'Latent Heat to Melt Frozen Precipitation Area Integrated')
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', &
1510 cmor_field_name=
'total_hfibthermds', cmor_units=
'W', &
1511 cmor_standard_name=
'heat_flux_into_sea_water_due_to_iceberg_thermodynamics_area_integrated',&
1513 'Heat Flux into Sea Water due to Iceberg Thermodynamics Area Integrated')
1515 handles%id_total_sens = register_scalar_field(
'ocean_model', &
1516 'total_sens', time, diag, &
1517 long_name=
'Area integrated downward sensible heat flux', &
1519 cmor_field_name=
'total_hfsso', cmor_units=
'W', &
1520 cmor_standard_name=
'surface_downward_sensible_heat_flux_area_integrated',&
1522 'Surface Downward Sensible Heat Flux Area Integrated')
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', &
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)',&
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', &
1542 cmor_field_name=
'ave_hfds', cmor_units=
'W m-2', &
1543 cmor_standard_name=
'surface_downward_heat_flux_in_sea_water_area_averaged', &
1545 'Surface Ocean Heat Flux from SW+LW+latent+sensible+mass transfer+frazil Area Averaged')
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', &
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',&
1554 'Net Downward Shortwave Radiation at Sea Water Surface Area Averaged')
1556 handles%id_LwLatSens_ga = register_scalar_field(
'ocean_model',&
1557 'LwLatSens_ga', time, diag, &
1558 long_name=
'Area averaged longwave+latent+sensible heating',&
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', &
1565 cmor_field_name=
'ave_rlntds', cmor_units=
'W m-2', &
1566 cmor_standard_name=
'surface_net_downward_longwave_flux_area_averaged',&
1568 'Surface Net Downward Longwave Radiation Area Averaged')
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', &
1574 cmor_field_name=
'ave_hflso', cmor_units=
'W m-2', &
1575 cmor_standard_name=
'surface_downward_latent_heat_flux_area_averaged',&
1577 'Surface Downward Latent Heat Flux Area Averaged')
1579 handles%id_sens_ga = register_scalar_field(
'ocean_model', &
1580 'sens_ga', time, diag, &
1581 long_name=
'Area averaged downward sensible heat flux', &
1583 cmor_field_name=
'ave_hfsso', cmor_units=
'W m-2', &
1584 cmor_standard_name=
'surface_downward_sensible_heat_flux_area_averaged',&
1586 'Surface Downward Sensible Heat Flux Area Averaged')
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')
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)')
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)')
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)')
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)')
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)')
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', &
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', &
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', &
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')
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')
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')
1658 type(
forcing),
intent(inout) :: fluxes
1659 real,
intent(in) :: dt
1661 real,
intent(out) :: wt2
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
1677 if (fluxes%dt_buoy_accum < 0)
call mom_error(fatal,
"forcing_accumulate: "//&
1678 "fluxes must be initialzed before it can be augmented.")
1681 wt1 = fluxes%dt_buoy_accum / (fluxes%dt_buoy_accum + dt)
1683 fluxes%dt_buoy_accum = fluxes%dt_buoy_accum + dt
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)
1690 do j=js,je ;
do i=isq,ieq
1691 fluxes%taux(i,j) = flux_tmp%taux(i,j)
1693 do j=jsq,jeq ;
do i=is,ie
1694 fluxes%tauy(i,j) = flux_tmp%tauy(i,j)
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)
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)
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)
1718 fluxes%salt_flux(i,j) = wt1*fluxes%salt_flux(i,j) + wt2*flux_tmp%salt_flux(i,j)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
1801 fluxes%tr_fluxes => flux_tmp%tr_fluxes
1810 real,
intent(in) :: dt
1815 integer :: i,j,is,ie,js,je
1817 call cpu_clock_begin(handles%id_clock_forcing)
1819 is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
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)
1841 call cpu_clock_end(handles%id_clock_forcing)
1849 type(
surface),
intent(in) :: state
1850 real,
intent(in) :: dt
1856 real,
dimension(SZI_(G),SZJ_(G)) :: res
1857 real :: total_transport
1862 integer :: i,j,is,ie,js,je
1864 call cpu_clock_begin(handles%id_clock_forcing)
1869 is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
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
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)
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)
1886 call post_data(handles%id_prcme, res, diag)
1887 if(handles%id_total_prcme > 0)
then 1889 call post_data(handles%id_total_prcme, total_transport, diag)
1891 if(handles%id_prcme_ga > 0)
then 1893 call post_data(handles%id_prcme_ga, ave_flux, diag)
1897 if(handles%id_net_massout > 0 .or. handles%id_total_net_massout > 0)
then 1898 do j=js,je ;
do i=is,ie
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)
1904 call post_data(handles%id_net_massout, res, diag)
1905 if(handles%id_total_net_massout > 0)
then 1907 call post_data(handles%id_total_net_massout, total_transport, diag)
1911 if(handles%id_massout_flux > 0)
call post_data(handles%id_massout_flux,fluxes%netMassOut,diag)
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)
1919 if(fluxes%evap(i,j) > 0.0) res(i,j) = res(i,j) + fluxes%evap(i,j)
1921 call post_data(handles%id_net_massin, res, diag)
1922 if(handles%id_total_net_massin > 0)
then 1924 call post_data(handles%id_total_net_massin, total_transport, diag)
1928 if(handles%id_massin_flux > 0)
call post_data(handles%id_massin_flux,fluxes%netMassIn,diag)
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 1934 call post_data(handles%id_total_evap, total_transport, diag)
1936 if ((handles%id_evap_ga > 0) .and.
ASSOCIATED(fluxes%evap))
then 1938 call post_data(handles%id_evap_ga, ave_flux, diag)
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)
1945 if (handles%id_precip > 0)
call post_data(handles%id_precip, res, diag)
1946 if (handles%id_total_precip > 0)
then 1948 call post_data(handles%id_total_precip, total_transport, diag)
1950 if (handles%id_precip_ga > 0)
then 1952 call post_data(handles%id_precip_ga, ave_flux, diag)
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 1960 call post_data(handles%id_total_lprec, total_transport, diag)
1962 if (handles%id_lprec_ga > 0)
then 1964 call post_data(handles%id_lprec_ga, ave_flux, diag)
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 1972 call post_data(handles%id_total_fprec, total_transport, diag)
1974 if (handles%id_fprec_ga > 0)
then 1976 call post_data(handles%id_fprec_ga, ave_flux, diag)
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 1984 call post_data(handles%id_total_vprec, total_transport, diag)
1986 if (handles%id_vprec_ga > 0)
then 1988 call post_data(handles%id_vprec_ga, ave_flux, diag)
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 1996 call post_data(handles%id_total_lrunoff, total_transport, diag)
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 2004 call post_data(handles%id_total_frunoff, total_transport, diag)
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 2014 call post_data(handles%id_total_heat_content_lrunoff, total_transport, diag)
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 2021 call post_data(handles%id_total_heat_content_frunoff, total_transport, diag)
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 2028 call post_data(handles%id_total_heat_content_lprec, total_transport, diag)
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 2035 call post_data(handles%id_total_heat_content_fprec, total_transport, diag)
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 2042 call post_data(handles%id_total_heat_content_vprec, total_transport, diag)
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 2049 call post_data(handles%id_total_heat_content_cond, total_transport, diag)
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 2056 call post_data(handles%id_total_heat_content_massout, total_transport, diag)
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 2063 call post_data(handles%id_total_heat_content_massin, total_transport, diag)
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
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)
2074 call post_data(handles%id_net_heat_coupler, res, diag)
2075 if(handles%id_total_net_heat_coupler > 0)
then 2077 call post_data(handles%id_total_net_heat_coupler, total_transport, diag)
2079 if(handles%id_net_heat_coupler_ga > 0)
then 2081 call post_data(handles%id_net_heat_coupler_ga, ave_flux, diag)
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
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
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)
2104 if (
ASSOCIATED(fluxes%heat_added)) res(i,j) = res(i,j) + fluxes%heat_added(i,j)
2106 call post_data(handles%id_net_heat_surface, res, diag)
2108 if(handles%id_total_net_heat_surface > 0)
then 2110 call post_data(handles%id_total_net_heat_surface, total_transport, diag)
2112 if(handles%id_net_heat_surface_ga > 0)
then 2114 call post_data(handles%id_net_heat_surface_ga, ave_flux, diag)
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
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)
2133 call post_data(handles%id_heat_content_surfwater, res, diag)
2134 if(handles%id_total_heat_content_surfwater > 0)
then 2136 call post_data(handles%id_total_heat_content_surfwater, total_transport, diag)
2141 if (handles%id_hfrunoffds > 0)
then 2142 do j=js,je ;
do i=is,ie
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)
2147 call post_data(handles%id_hfrunoffds, res, diag)
2151 if (handles%id_hfrainds > 0)
then 2152 do j=js,je ;
do i=is,ie
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)
2158 call post_data(handles%id_hfrainds, res, diag)
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)
2166 call post_data(handles%id_LwLatSens, res, diag)
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)
2175 call post_data(handles%id_total_LwLatSens, total_transport, diag)
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)
2184 call post_data(handles%id_LwLatSens_ga, ave_flux, diag)
2187 if ((handles%id_sw > 0) .and.
ASSOCIATED(fluxes%sw))
then 2188 call post_data(handles%id_sw, fluxes%sw, diag)
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)
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)
2198 if ((handles%id_total_sw > 0) .and.
ASSOCIATED(fluxes%sw))
then 2200 call post_data(handles%id_total_sw, total_transport, diag)
2202 if ((handles%id_sw_ga > 0) .and.
ASSOCIATED(fluxes%sw))
then 2204 call post_data(handles%id_sw_ga, ave_flux, diag)
2207 if ((handles%id_lw > 0) .and.
ASSOCIATED(fluxes%lw))
then 2208 call post_data(handles%id_lw, fluxes%lw, diag)
2210 if ((handles%id_total_lw > 0) .and.
ASSOCIATED(fluxes%lw))
then 2212 call post_data(handles%id_total_lw, total_transport, diag)
2214 if ((handles%id_lw_ga > 0) .and.
ASSOCIATED(fluxes%lw))
then 2216 call post_data(handles%id_lw_ga, ave_flux, diag)
2219 if ((handles%id_lat > 0) .and.
ASSOCIATED(fluxes%latent))
then 2220 call post_data(handles%id_lat, fluxes%latent, diag)
2222 if ((handles%id_total_lat > 0) .and.
ASSOCIATED(fluxes%latent))
then 2224 call post_data(handles%id_total_lat, total_transport, diag)
2226 if ((handles%id_lat_ga > 0) .and.
ASSOCIATED(fluxes%latent))
then 2228 call post_data(handles%id_lat_ga, ave_flux, diag)
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)
2234 if ((handles%id_total_lat_evap > 0) .and.
ASSOCIATED(fluxes%latent_evap_diag))
then 2236 call post_data(handles%id_total_lat_evap, total_transport, diag)
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)
2242 if ((handles%id_total_lat_fprec > 0) .and.
ASSOCIATED(fluxes%latent_fprec_diag))
then 2244 call post_data(handles%id_total_lat_fprec, total_transport, diag)
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)
2250 if(handles%id_total_lat_frunoff > 0 .and.
ASSOCIATED(fluxes%latent_frunoff_diag))
then 2252 call post_data(handles%id_total_lat_frunoff, total_transport, diag)
2255 if ((handles%id_sens > 0) .and.
ASSOCIATED(fluxes%sens))
then 2256 call post_data(handles%id_sens, fluxes%sens, diag)
2258 if ((handles%id_total_sens > 0) .and.
ASSOCIATED(fluxes%sens))
then 2260 call post_data(handles%id_total_sens, total_transport, diag)
2262 if ((handles%id_sens_ga > 0) .and.
ASSOCIATED(fluxes%sens))
then 2264 call post_data(handles%id_sens_ga, ave_flux, diag)
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)
2271 if ((handles%id_total_heat_added > 0) .and.
ASSOCIATED(fluxes%heat_added))
then 2273 call post_data(handles%id_total_heat_added, total_transport, diag)
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 2283 call post_data(handles%id_total_saltflux, total_transport, diag)
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 2290 call post_data(handles%id_total_saltFluxAdded, total_transport, diag)
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 2297 call post_data(handles%id_total_saltFluxIn, total_transport, diag)
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)
2316 if ((handles%id_psurf > 0) .and.
ASSOCIATED(fluxes%p_surf)) &
2317 call post_data(handles%id_psurf, fluxes%p_surf, diag)
2319 if ((handles%id_TKE_tidal > 0) .and.
ASSOCIATED(fluxes%TKE_tidal)) &
2320 call post_data(handles%id_TKE_tidal, fluxes%TKE_tidal, diag)
2322 if ((handles%id_buoy > 0) .and.
ASSOCIATED(fluxes%buoy)) &
2323 call post_data(handles%id_buoy, fluxes%buoy, diag)
2328 call cpu_clock_end(handles%id_clock_forcing)
2335 type(
forcing),
intent(inout) :: fluxes
2336 logical,
optional,
intent(in) :: stress
2337 logical,
optional,
intent(in) :: ustar
2338 logical,
optional,
intent(in) :: water
2339 logical,
optional,
intent(in) :: heat
2340 logical,
optional,
intent(in) :: shelf
2341 logical,
optional,
intent(in) :: press
2342 logical,
optional,
intent(in) :: iceberg
2345 integer :: isd, ied, jsd, jed, IsdB, IedB, JsdB, JedB
2346 logical :: heat_water
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
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)
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)
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)
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.)
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)
2393 call myalloc(fluxes%p_surf,isd,ied,jsd,jed, press)
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)
2402 subroutine myalloc(array, is, ie, js, je, flag)
2403 real,
dimension(:,:),
pointer :: array
2404 integer,
intent(in) :: is
2405 integer,
intent(in) :: ie
2406 integer,
intent(in) :: js
2407 integer,
intent(in) :: je
2408 logical,
optional,
intent(in) :: flag
2410 if (
present(flag))
then 2412 if (.not.
associated(array))
then 2413 ALLOCATE(array(is:ie,js:je))
2414 array(is:ie,js:je) = 0.0
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)
The following structure contains pointers to various fields which may be used describe the surface st...
This module implements boundary forcing for MOM6.
Ocean grid type. See mom_grid for details.
Provides the ocean grid type.
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.
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.
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.
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.
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.