Skip to content

Commit e56784c

Browse files
authored
Merge branch 'dev/gfdl' into UCTbug
2 parents 1652246 + a78aa57 commit e56784c

18 files changed

+1133
-825
lines changed

config_src/drivers/FMS_cap/MOM_surface_forcing_gfdl.F90

Lines changed: 21 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -635,16 +635,20 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,
635635
endif
636636

637637
! Set the wind stresses and ustar.
638-
if (associated(fluxes%ustar) .and. associated(fluxes%ustar_gustless) .and. associated(fluxes%tau_mag)) then
638+
if (associated(fluxes%ustar) .and. associated(fluxes%ustar_gustless) .and. associated(fluxes%tau_mag) &
639+
.and. associated(fluxes%tau_mag_gustless) ) then
639640
call extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, ustar=fluxes%ustar, &
640-
mag_tau=fluxes%tau_mag, gustless_ustar=fluxes%ustar_gustless)
641+
mag_tau=fluxes%tau_mag, gustless_ustar=fluxes%ustar_gustless, &
642+
gustless_mag_tau=fluxes%tau_mag_gustless)
641643
else
642644
if (associated(fluxes%ustar)) &
643645
call extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, ustar=fluxes%ustar)
644646
if (associated(fluxes%ustar_gustless)) &
645647
call extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, gustless_ustar=fluxes%ustar_gustless)
646648
if (associated(fluxes%tau_mag)) &
647649
call extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, mag_tau=fluxes%tau_mag)
650+
if (associated(fluxes%tau_mag_gustless)) &
651+
call extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, gustless_mag_tau=fluxes%tau_mag_gustless)
648652
endif
649653

650654
if (coupler_type_initialized(fluxes%tr_fluxes) .and. &
@@ -908,7 +912,7 @@ end subroutine convert_IOB_to_forces
908912
!! Ice_ocean_boundary_type into optional argument arrays, including changes of units, sign
909913
!! conventions, and putting the fields into arrays with MOM-standard sized halos.
910914
subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy, ustar, &
911-
gustless_ustar, mag_tau, tau_halo)
915+
gustless_ustar, mag_tau, gustless_mag_tau, tau_halo)
912916
type(ice_ocean_boundary_type), &
913917
target, intent(in) :: IOB !< An ice-ocean boundary type with fluxes to drive
914918
!! the ocean in a coupled model
@@ -931,6 +935,9 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
931935
real, dimension(SZI_(G),SZJ_(G)), &
932936
optional, intent(inout) :: mag_tau !< The magintude of the wind stress at tracer points
933937
!! including subgridscale variability and gustiness [R Z L T-2 ~> Pa]
938+
real, dimension(SZI_(G),SZJ_(G)), &
939+
optional, intent(out) :: gustless_mag_tau !< The magintude of the wind stress at tracer points
940+
!! without any contributions from gustiness [R Z L T-2 ~> Pa]
934941
integer, optional, intent(in) :: tau_halo !< The halo size of wind stresses to set, 0 by default.
935942

936943
! Local variables
@@ -947,7 +954,7 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
947954
real :: tau_mag ! magnitude of the wind stress [R Z L T-2 ~> Pa]
948955
real :: stress_conversion ! A unit conversion factor from Pa times any stress multiplier [R Z L T-2 Pa-1 ~> 1]
949956

950-
logical :: do_ustar, do_gustless, do_tau_mag
957+
logical :: do_ustar, do_gustless, do_tau_mag, do_gustless_tau_mag
951958
integer :: wind_stagger ! AGRID, BGRID_NE, or CGRID_NE (integers from MOM_domains)
952959
integer :: i, j, is, ie, js, je, ish, ieh, jsh, jeh, Isqh, Ieqh, Jsqh, Jeqh, i0, j0, halo
953960

@@ -960,7 +967,8 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
960967
IRho0 = US%L_to_Z / CS%Rho0
961968
stress_conversion = US%Pa_to_RLZ_T2 * CS%wind_stress_multiplier
962969

963-
do_ustar = present(ustar) ; do_gustless = present(gustless_ustar) ; do_tau_mag = present(mag_tau)
970+
do_ustar = present(ustar) ; do_gustless = present(gustless_ustar)
971+
do_tau_mag = present(mag_tau) ; do_gustless_tau_mag = present(gustless_mag_tau)
964972

965973
wind_stagger = CS%wind_stagger
966974
if ((IOB%wind_stagger == AGRID) .or. (IOB%wind_stagger == BGRID_NE) .or. &
@@ -973,7 +981,8 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
973981

974982
! Set surface momentum stress related fields as a function of staggering.
975983
if (present(taux) .or. present(tauy) .or. &
976-
((do_ustar .or. do_tau_mag .or. do_gustless) .and. .not.associated(IOB%stress_mag)) ) then
984+
((do_ustar .or. do_tau_mag .or. do_gustless .or. do_gustless_tau_mag) &
985+
.and. .not.associated(IOB%stress_mag)) ) then
977986

978987
if (wind_stagger == BGRID_NE) then
979988
taux_in_B(:,:) = 0.0 ; tauy_in_B(:,:) = 0.0
@@ -1053,7 +1062,7 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
10531062
endif ! endif for extracting wind stress fields with various staggerings
10541063
endif
10551064

1056-
if (do_ustar .or. do_tau_mag .or. do_gustless) then
1065+
if (do_ustar .or. do_tau_mag .or. do_gustless .or. do_gustless_tau_mag) then
10571066
! Set surface friction velocity directly or as a function of staggering.
10581067
! ustar is required for the bulk mixed layer formulation and other turbulent mixing
10591068
! parametizations. The background gustiness (for example with a relatively small value
@@ -1071,6 +1080,8 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
10711080
endif
10721081
if (do_tau_mag) &
10731082
mag_tau(i,j) = gustiness + US%Pa_to_RLZ_T2*IOB%stress_mag(i-i0,j-j0)
1083+
if (do_gustless_tau_mag) &
1084+
gustless_mag_tau(i,j) = US%Pa_to_RLZ_T2*IOB%stress_mag(i-i0,j-j0)
10741085
if (do_ustar) &
10751086
ustar(i,j) = sqrt(gustiness*IRho0 + IRho0*US%Pa_to_RLZ_T2*IOB%stress_mag(i-i0,j-j0))
10761087
enddo ; enddo ; endif
@@ -1097,6 +1108,7 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
10971108
endif
10981109
if (do_ustar) ustar(i,j) = sqrt(gustiness*IRho0 + IRho0 * tau_mag)
10991110
if (do_tau_mag) mag_tau(i,j) = gustiness + tau_mag
1111+
if (do_gustless_tau_mag) gustless_mag_tau(i,j) = tau_mag
11001112
if (CS%answer_date < 20190101) then
11011113
if (do_gustless) gustless_ustar(i,j) = sqrt(US%L_to_Z*tau_mag / CS%Rho0)
11021114
else
@@ -1110,6 +1122,7 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
11101122
if (CS%read_gust_2d .and. (G%mask2dT(i,j) > 0.0)) gustiness = CS%gust(i,j)
11111123
if (do_ustar) ustar(i,j) = sqrt(gustiness*IRho0 + IRho0 * tau_mag)
11121124
if (do_tau_mag) mag_tau(i,j) = gustiness + tau_mag
1125+
if (do_gustless_tau_mag) gustless_mag_tau(i,j) = tau_mag
11131126
if (CS%answer_date < 20190101) then
11141127
if (do_gustless) gustless_ustar(i,j) = sqrt(US%L_to_Z*tau_mag / CS%Rho0)
11151128
else
@@ -1132,6 +1145,7 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
11321145

11331146
if (do_ustar) ustar(i,j) = sqrt(gustiness*IRho0 + IRho0 * tau_mag)
11341147
if (do_tau_mag) mag_tau(i,j) = gustiness + tau_mag
1148+
if (do_gustless_tau_mag) gustless_mag_tau(i,j) = tau_mag
11351149
if (CS%answer_date < 20190101) then
11361150
if (do_gustless) gustless_ustar(i,j) = sqrt(US%L_to_Z*tau_mag / CS%Rho0)
11371151
else

src/ALE/MOM_regridding.F90

Lines changed: 87 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -226,12 +226,38 @@ subroutine initialize_regridding(CS, GV, US, max_depth, param_file, mdl, coord_m
226226
real, dimension(:), allocatable :: dz_max ! Thicknesses used to find maximum interface depths
227227
! [H ~> m or kg m-2] or other units
228228
real, dimension(:), allocatable :: rho_target ! Target density used in HYBRID mode [kg m-3]
229-
!> Thicknesses [m] that give level centers corresponding to table 2 of WOA09
230-
real, dimension(40) :: woa09_dz = (/ 5., 10., 10., 15., 22.5, 25., 25., 25., &
231-
37.5, 50., 50., 75., 100., 100., 100., 100., &
232-
100., 100., 100., 100., 100., 100., 100., 175., &
233-
250., 375., 500., 500., 500., 500., 500., 500., &
234-
500., 500., 500., 500., 500., 500., 500., 500. /)
229+
! Thicknesses [m] that give level centers approximately corresponding to table 2 of WOA09
230+
! These are approximate because the WOA09 depths are not smoothly spaced. Levels
231+
! 1, 4, 5, 9, 12, 24, and 36 are 2.5, 2.5, 1.25 12.5, 37.5 and 62.5 m deeper than WOA09
232+
! but all others are identical.
233+
real, dimension(40) :: woa09_dz_approx = (/ 5., 10., 10., 15., 22.5, 25., 25., 25., &
234+
37.5, 50., 50., 75., 100., 100., 100., 100., &
235+
100., 100., 100., 100., 100., 100., 100., 175., &
236+
250., 375., 500., 500., 500., 500., 500., 500., &
237+
500., 500., 500., 500., 500., 500., 500., 500. /)
238+
! These are the actual spacings [m] between WOA09 depths which, if used for layer thickness, places
239+
! the interfaces at the WOA09 depths.
240+
real, dimension(39) :: woa09_dzi = (/ 10., 10., 10., 20., 25., 25., 25., 25., &
241+
50., 50., 50., 100., 100., 100., 100., 100., &
242+
100., 100., 100., 100., 100., 100., 100., 250., &
243+
250., 500., 500., 500., 500., 500., 500., 500., &
244+
500., 500., 500., 500., 500., 500., 500. /)
245+
! These are the spacings [m] between WOA23 depths from table 3 of
246+
! https://www.ncei.noaa.gov/data/oceans/woa/WOA13/DOC/woa13documentation.pdf
247+
real, dimension(136) :: woa23_dzi = (/ 5., 5., 5., 5., 5., 5., 5., 5., 5., 5., &
248+
5., 5., 5., 5., 5., 5., 5., 5., 5., 5., &
249+
25., 25., 25., 25., 25., 25., 25., 25., 25., 25., &
250+
25., 25., 25., 25., 25., 25., 50., 50., 50., 50., &
251+
50., 50., 50., 50., 50., 50., 50., 50., 50., 50., &
252+
50., 50., 50., 50., 50., 50., 50., 50., 50., 50., &
253+
50., 50., 50., 50., 50., 50., 100., 100., 100., 100., &
254+
100., 100., 100., 100., 100., 100., 100., 100., 100., 100., &
255+
100., 100., 100., 100., 100., 100., 100., 100., 100., 100., &
256+
100., 100., 100., 100., 100., 100., 100., 100., 100., 100., &
257+
100., 100., 100., 100., 100., 100., 100., 100., 100., 100., &
258+
100., 100., 100., 100., 100., 100., 100., 100., 100., 100., &
259+
100., 100., 100., 100., 100., 100., 100., 100., 100., 100., &
260+
100., 100., 100., 100., 100., 100. /)
235261

236262
call get_param(param_file, mdl, "INPUTDIR", inputdir, default=".")
237263
inputdir = slasher(inputdir)
@@ -325,6 +351,8 @@ subroutine initialize_regridding(CS, GV, US, max_depth, param_file, mdl, coord_m
325351
" by a comma or space, e.g. FILE:lev.nc,dz\n"//&
326352
" or FILE:lev.nc,interfaces=zw\n"//&
327353
" WOA09[:N] - the WOA09 vertical grid (approximately)\n"//&
354+
" WOA09INT[:N] - layers spanned by the WOA09 depths\n"//&
355+
" WOA23INT[:N] - layers spanned by the WOA23 depths\n"//&
328356
" FNC1:string - FNC1:dz_min,H_total,power,precision\n"//&
329357
" HYBRID:string - read from a file. The string specifies\n"//&
330358
" the filename and two variable names, separated\n"//&
@@ -458,29 +486,75 @@ subroutine initialize_regridding(CS, GV, US, max_depth, param_file, mdl, coord_m
458486
call log_param(param_file, mdl, "!TARGET_DENSITIES", rho_target, &
459487
'HYBRID target densities for interfaces', units=coordinateUnits(coord_mode))
460488
endif
489+
elseif (index(trim(string),'WOA09INT')==1) then
490+
if (len_trim(string)==8) then ! string=='WOA09INT'
491+
tmpReal = 0. ; ke = 0 ; dz_extra = 0.
492+
do while (tmpReal<maximum_depth)
493+
ke = ke + 1
494+
if (ke > size(woa09_dzi)) then
495+
dz_extra = maximum_depth - tmpReal
496+
exit
497+
endif
498+
tmpReal = tmpReal + woa09_dzi(ke)
499+
enddo
500+
elseif (index(trim(string),'WOA09INT:')==1) then ! string starts with 'WOA09INT:'
501+
if (len_trim(string)==9) call MOM_error(FATAL,trim(mdl)//', initialize_regridding: '// &
502+
'Expected string of form "WOA09INT:N" but got "'//trim(string)//'".')
503+
ke = extract_integer(string(10:len_trim(string)),'',1)
504+
if (ke>39 .or. ke<1) call MOM_error(FATAL,trim(mdl)//', initialize_regridding: '// &
505+
'For "WOA05INT:N" N must 0<N<40 but got "'//trim(string)//'".')
506+
endif
507+
allocate(dz(ke))
508+
do k=1,min(ke, size(woa09_dzi))
509+
dz(k) = woa09_dzi(k)
510+
enddo
511+
if (ke > size(woa09_dzi)) dz(ke) = dz_extra
512+
elseif (index(trim(string),'WOA23INT')==1) then
513+
if (len_trim(string)==8) then ! string=='WOA23INT'
514+
tmpReal = 0. ; ke = 0 ; dz_extra = 0.
515+
do while (tmpReal<maximum_depth)
516+
ke = ke + 1
517+
if (ke > size(woa23_dzi)) then
518+
dz_extra = maximum_depth - tmpReal
519+
exit
520+
endif
521+
tmpReal = tmpReal + woa23_dzi(ke)
522+
enddo
523+
elseif (index(trim(string),'WOA23INT:')==1) then ! string starts with 'WOA23INT:'
524+
if (len_trim(string)==9) call MOM_error(FATAL,trim(mdl)//', initialize_regridding: '// &
525+
'Expected string of form "WOA23INT:N" but got "'//trim(string)//'".')
526+
ke = extract_integer(string(10:len_trim(string)),'',1)
527+
if (ke>39 .or. ke<1) call MOM_error(FATAL,trim(mdl)//', initialize_regridding: '// &
528+
'For "WOA05INT:N" N must 0<N<40 but got "'//trim(string)//'".')
529+
endif
530+
allocate(dz(ke))
531+
do k=1,min(ke, size(woa23_dzi))
532+
dz(k) = woa23_dzi(k)
533+
enddo
534+
if (ke > size(woa23_dzi)) dz(ke) = dz_extra
461535
elseif (index(trim(string),'WOA09')==1) then
462-
if (len_trim(string)==5) then
536+
if (len_trim(string)==5) then ! string=='WOA09'
463537
tmpReal = 0. ; ke = 0 ; dz_extra = 0.
464538
do while (tmpReal<maximum_depth)
465539
ke = ke + 1
466-
if (ke > size(woa09_dz)) then
540+
if (ke > size(woa09_dz_approx)) then
467541
dz_extra = maximum_depth - tmpReal
468542
exit
469543
endif
470-
tmpReal = tmpReal + woa09_dz(ke)
544+
tmpReal = tmpReal + woa09_dz_approx(ke)
471545
enddo
472-
elseif (index(trim(string),'WOA09:')==1) then
546+
elseif (index(trim(string),'WOA09:')==1) then ! string starts with 'WOA09:'
473547
if (len_trim(string)==6) call MOM_error(FATAL,trim(mdl)//', initialize_regridding: '// &
474548
'Expected string of form "WOA09:N" but got "'//trim(string)//'".')
475549
ke = extract_integer(string(7:len_trim(string)),'',1)
476550
if (ke>40 .or. ke<1) call MOM_error(FATAL,trim(mdl)//', initialize_regridding: '// &
477551
'For "WOA05:N" N must 0<N<41 but got "'//trim(string)//'".')
478552
endif
479553
allocate(dz(ke))
480-
do k=1,min(ke, size(woa09_dz))
481-
dz(k) = woa09_dz(k)
554+
do k=1,min(ke, size(woa09_dz_approx))
555+
dz(k) = woa09_dz_approx(k)
482556
enddo
483-
if (ke > size(woa09_dz)) dz(ke) = dz_extra
557+
if (ke > size(woa09_dz_approx)) dz(ke) = dz_extra
484558
else
485559
call MOM_error(FATAL,trim(mdl)//", initialize_regridding: "// &
486560
"Unrecognized coordinate configuration"//trim(string))

0 commit comments

Comments
 (0)