15 implicit none ;
private 17 #include <MOM_memory.h> 23 logical :: use_ebt_mode = .false.
27 real :: mono_n2_column_fraction = 0.
31 real :: mono_n2_depth = -1.
43 subroutine wave_speed(h, tv, G, GV, cg1, CS, full_halos, use_ebt_mode, &
44 mono_N2_column_fraction, mono_N2_depth, modal_structure)
47 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)),
intent(in) :: h
49 real,
dimension(SZI_(G),SZJ_(G)),
intent(out) :: cg1
51 logical,
optional,
intent(in) :: full_halos
53 logical,
optional,
intent(in) :: use_ebt_mode
55 real,
optional,
intent(in) :: mono_N2_column_fraction
58 real,
optional,
intent(in) :: mono_N2_depth
60 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)), &
61 optional,
intent(out) :: modal_structure
64 real,
dimension(SZK_(G)+1) :: &
68 real,
dimension(SZK_(G)) :: &
72 real,
dimension(SZK_(G),SZI_(G)) :: &
74 real,
dimension(SZK_(G)) :: &
76 real det, ddet, detKm1, detKm2, ddetKm1, ddetKm2
77 real :: lam, dlam, lam0
81 real,
dimension(SZI_(G)) :: &
83 H_here, HxT_here, HxS_here, HxR_here
85 real :: I_Hnew, drxh_sum
86 real,
parameter :: tol1 = 0.0001, tol2 = 0.001
87 real,
pointer,
dimension(:,:,:) :: T, S
89 real :: rescale, I_rescale
90 integer :: kf(szi_(g))
91 integer,
parameter :: max_itt = 10
92 real :: lam_it(max_itt), det_it(max_itt), ddet_it(max_itt)
96 integer :: i, j, k, k2, itt, is, ie, js, je, nz
97 real :: hw, gp, sum_hc, N2min
98 logical :: l_use_ebt_mode, calc_modal_structure
99 real :: l_mono_N2_column_fraction, l_mono_N2_depth
100 real :: mode_struct(szk_(g)), ms_min, ms_max, ms_sq
102 is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
104 if (.not.
associated(cs))
call mom_error(fatal,
"MOM_wave_speed: "// &
105 "Module must be initialized before it is used.")
106 if (
present(full_halos))
then ;
if (full_halos)
then 107 is = g%isd ; ie = g%ied ; js = g%jsd ; je = g%jed
110 l_use_ebt_mode = cs%use_ebt_mode
111 if (
present(use_ebt_mode)) l_use_ebt_mode = use_ebt_mode
112 l_mono_n2_column_fraction = cs%mono_N2_column_fraction
113 if (
present(mono_n2_column_fraction)) l_mono_n2_column_fraction = mono_n2_column_fraction
114 l_mono_n2_depth = cs%mono_N2_depth
115 if (
present(mono_n2_depth)) l_mono_n2_depth = mono_n2_depth
116 calc_modal_structure = l_use_ebt_mode
117 if (
present(modal_structure)) calc_modal_structure = .true.
118 if (calc_modal_structure)
then 119 do k=1,nz;
do j=js,je;
do i=is,ie
120 modal_structure(i,j,k) = 0.0
124 s => tv%S ; t => tv%T
125 g_rho0 = gv%g_Earth/gv%Rho0
126 use_eos =
associated(tv%eqn_of_state)
128 h_to_pres = gv%g_Earth * gv%Rho0
130 rescale = 1024.0**4 ; i_rescale = 1.0/rescale
132 min_h_frac = tol1 /
real(nz)
148 do i=is,ie ; htot(i) = 0.0 ;
enddo 149 do k=1,nz ;
do i=is,ie ; htot(i) = htot(i) + h(i,j,k)*h_to_m ;
enddo ;
enddo 152 hmin(i) = htot(i)*min_h_frac ; kf(i) = 1 ; h_here(i) = 0.0
153 hxt_here(i) = 0.0 ; hxs_here(i) = 0.0 ; hxr_here(i) = 0.0
156 do k=1,nz ;
do i=is,ie
157 if ((h_here(i) > hmin(i)) .and. (h(i,j,k)*h_to_m > hmin(i)))
then 158 hf(kf(i),i) = h_here(i)
159 tf(kf(i),i) = hxt_here(i) / h_here(i)
160 sf(kf(i),i) = hxs_here(i) / h_here(i)
164 h_here(i) = h(i,j,k)*h_to_m
165 hxt_here(i) = (h(i,j,k)*h_to_m)*t(i,j,k)
166 hxs_here(i) = (h(i,j,k)*h_to_m)*s(i,j,k)
168 h_here(i) = h_here(i) + h(i,j,k)*h_to_m
169 hxt_here(i) = hxt_here(i) + (h(i,j,k)*h_to_m)*t(i,j,k)
170 hxs_here(i) = hxs_here(i) + (h(i,j,k)*h_to_m)*s(i,j,k)
173 do i=is,ie ;
if (h_here(i) > 0.0)
then 174 hf(kf(i),i) = h_here(i)
175 tf(kf(i),i) = hxt_here(i) / h_here(i)
176 sf(kf(i),i) = hxs_here(i) / h_here(i)
179 do k=1,nz ;
do i=is,ie
180 if ((h_here(i) > hmin(i)) .and. (h(i,j,k)*h_to_m > hmin(i)))
then 181 hf(kf(i),i) = h_here(i) ; rf(kf(i),i) = hxr_here(i) / h_here(i)
185 h_here(i) = h(i,j,k)*h_to_m
186 hxr_here(i) = (h(i,j,k)*h_to_m)*gv%Rlay(k)
188 h_here(i) = h_here(i) + h(i,j,k)*h_to_m
189 hxr_here(i) = hxr_here(i) + (h(i,j,k)*h_to_m)*gv%Rlay(k)
192 do i=is,ie ;
if (h_here(i) > 0.0)
then 193 hf(kf(i),i) = h_here(i) ; rf(kf(i),i) = hxr_here(i) / h_here(i)
199 do i=is,ie ;
if (g%mask2dT(i,j) > 0.5)
then 203 pres(k) = pres(k-1) + h_to_pres*hf(k-1,i)
204 t_int(k) = 0.5*(tf(k,i)+tf(k-1,i))
205 s_int(k) = 0.5*(sf(k,i)+sf(k-1,i))
208 kf(i)-1, tv%eqn_of_state)
214 drxh_sum = drxh_sum + 0.5*(hf(k-1,i)+hf(k,i)) * &
215 max(0.0,drho_dt(k)*(tf(k,i)-tf(k-1,i)) + &
216 drho_ds(k)*(sf(k,i)-sf(k-1,i)))
221 drxh_sum = drxh_sum + 0.5*(hf(k-1,i)+hf(k,i)) * &
222 max(0.0,rf(k,i)-rf(k-1,i))
226 if (calc_modal_structure)
then 232 if (drxh_sum <= 0.0)
then 239 hc(1) = hf(1,i) ; tc(1) = tf(1,i) ; sc(1) = sf(1,i)
241 if ((drho_dt(k)*(tf(k,i)-tc(kc)) + drho_ds(k)*(sf(k,i)-sc(kc))) * &
242 (hc(kc) + hf(k,i)) < 2.0 * tol2*drxh_sum)
then 244 i_hnew = 1.0 / (hc(kc) + hf(k,i))
245 tc(kc) = (hc(kc)*tc(kc) + hf(k,i)*tf(k,i)) * i_hnew
246 sc(kc) = (hc(kc)*sc(kc) + hf(k,i)*sf(k,i)) * i_hnew
247 hc(kc) = (hc(kc) + hf(k,i))
252 if ((drho_dt(k2)*(tc(k2)-tc(k2-1)) + drho_ds(k2)*(sc(k2)-sc(k2-1))) * &
253 (hc(k2) + hc(k2-1)) < tol2*drxh_sum)
then 255 i_hnew = 1.0 / (hc(kc) + hc(kc-1))
256 tc(kc-1) = (hc(kc)*tc(kc) + hc(kc-1)*tc(kc-1)) * i_hnew
257 sc(kc-1) = (hc(kc)*sc(kc) + hc(kc-1)*sc(kc-1)) * i_hnew
258 hc(kc-1) = (hc(kc) + hc(kc-1))
265 drho_ds(kc) = drho_ds(k) ; drho_dt(kc) = drho_dt(k)
266 tc(kc) = tf(k,i) ; sc(kc) = sf(k,i) ; hc(kc) = hf(k,i)
271 gprime(k) = g_rho0 * (drho_dt(k)*(tc(k)-tc(k-1)) + &
272 drho_ds(k)*(sc(k)-sc(k-1)))
277 hc(1) = hf(1,i) ; rc(1) = rf(1,i)
279 if ((rf(k,i) - rc(kc)) * (hc(kc) + hf(k,i)) < 2.0*tol2*drxh_sum)
then 281 rc(kc) = (hc(kc)*rc(kc) + hf(k,i)*rf(k,i)) / (hc(kc) + hf(k,i))
282 hc(kc) = (hc(kc) + hf(k,i))
287 if ((rc(k2)-rc(k2-1)) * (hc(k2)+hc(k2-1)) < tol2*drxh_sum)
then 289 rc(kc-1) = (hc(kc)*rc(kc) + hc(kc-1)*rc(kc-1)) / (hc(kc) + hc(kc-1))
290 hc(kc-1) = (hc(kc) + hc(kc-1))
297 rc(kc) = rf(k,i) ; hc(kc) = hf(k,i)
302 gprime(k) = g_rho0 * (rc(k)-rc(k-1))
311 if (l_use_ebt_mode)
then 313 sum_hc = hc(1)*gv%H_to_m
314 n2min = gprime(2)/hc(1)
316 hw = 0.5*(hc(k-1)+hc(k))
318 if (l_mono_n2_column_fraction>0. .or. l_mono_n2_depth>=0.)
then 319 if (g%bathyT(i,j)-sum_hc<l_mono_n2_column_fraction*g%bathyT(i,j) .and. gp>n2min*hw)
then 322 elseif (l_mono_n2_depth>=0. .and. sum_hc>l_mono_n2_depth .and. gp>n2min*hw)
then 329 igu(k) = 1.0/(gp*hc(k))
330 igl(k-1) = 1.0/(gp*hc(k-1))
331 speed2_tot = speed2_tot + gprime(k)*(hc(k-1)+hc(k))*0.707
332 sum_hc = sum_hc + hc(k)*gv%H_to_m
338 igl(k) = 1.0/(gprime(k)*hc(k)) ; igu(k) = 1.0/(gprime(k)*hc(k-1))
339 speed2_tot = speed2_tot + gprime(k)*(hc(k-1)+hc(k))
343 if (calc_modal_structure)
then 344 mode_struct(1:kc) = 1.
348 if (calc_modal_structure)
then 349 lam0 = 0.5 / speed2_tot ; lam = lam0
351 lam0 = 1.0 / speed2_tot ; lam = lam0
356 if (l_use_ebt_mode)
then 364 detkm1 = 1.0 ; ddetkm1 = 0.0
365 det = ( igl(1)-lam) ; ddet = -1.0
367 detkm2 = detkm1; ddetkm2 = ddetkm1
368 detkm1 = det; ddetkm1 = ddet
369 det = (igu(2)+igl(2)-lam)*detkm1 - (igu(2)*igl(1))*detkm2
370 ddet = (igu(2)+igl(2)-lam)*ddetkm1 - (igu(2)*igl(1))*ddetkm2 - detkm1
381 detkm1 = 1.0 ; ddetkm1 = 0.0
382 det = (igu(2)+igl(2)-lam) ; ddet = -1.0
389 detkm2 = detkm1; ddetkm2 = ddetkm1
390 detkm1 = det; ddetkm1 = ddet
392 det = (igu(k)+igl(k)-lam)*detkm1 - (igu(k)*igl(k-1))*detkm2
393 ddet = (igu(k)+igl(k)-lam)*ddetkm1 - (igu(k)*igl(k-1))*ddetkm2 - detkm1
396 if (abs(det) > rescale)
then 397 det = i_rescale*det ; detkm1 = i_rescale*detkm1
398 ddet = i_rescale*ddet ; ddetkm1 = i_rescale*ddetkm1
402 det_it(itt) = det ; ddet_it(itt) = ddet
404 if ((ddet >= 0.0) .or. (-det > -0.5*lam*ddet))
then 415 if (calc_modal_structure)
then 416 call tdma6(kc, -igu, igu+igl, -igl, lam, mode_struct)
417 ms_min = mode_struct(1)
418 ms_max = mode_struct(1)
419 ms_sq = mode_struct(1)**2
421 ms_min = min(ms_min, mode_struct(k))
422 ms_max = max(ms_max, mode_struct(k))
423 ms_sq = ms_sq + mode_struct(k)**2
425 if (ms_min<0. .and. ms_max>0.)
then 426 lam = 0.5 * ( lam - dlam )
428 mode_struct(1:kc) = abs(mode_struct(1:kc)) / sqrt( ms_sq )
430 mode_struct(1:kc) = mode_struct(1:kc) / sqrt( ms_sq )
434 if (abs(dlam) < tol2*lam)
exit 438 if (lam > 0.0) cg1(i,j) = 1.0 / sqrt(lam)
440 if (
present(modal_structure))
then 441 if (mode_struct(1)/=0.)
then 442 mode_struct(1:kc) = mode_struct(1:kc) / mode_struct(1)
446 call remapping_core_h(cs%remapping_CS, kc, hc, mode_struct, nz, h(i,j,:), modal_structure(i,j,:))
450 if (
present(modal_structure)) modal_structure(i,j,:) = 0.
455 if (
present(modal_structure)) modal_structure(i,j,:) = 0.
463 subroutine tdma6(n, a, b, c, lam, y)
464 integer,
intent(in) :: n
465 real,
dimension(n),
intent(in) :: a
466 real,
dimension(n),
intent(in) :: b
467 real,
dimension(n),
intent(in) :: c
468 real,
intent(in) :: lam
469 real,
dimension(n),
intent(inout) :: y
472 real :: beta(n), yy(n), lambda
474 beta(1) = b(1) - lambda
475 if (beta(1)==0.)
then 477 lambda = (1. + 1.e-5) * lambda
478 beta(1) = b(1) - lambda
480 beta(1) = 1. / beta(1)
483 beta(k) = ( b(k) - lambda ) - a(k) * c(k-1) * beta(k-1)
484 if (beta(k)==0.)
then 486 lambda = (1. + 1.e-5) * lambda
487 beta(1) = 1. / ( b(1) - lambda )
489 beta(l) = 1. / ( ( b(l) - lambda ) - a(l) * c(l-1) * beta(l-1) )
490 yy(l) = y(l) - a(l) * yy(l-1) * beta(l-1)
493 beta(k) = 1. / beta(k)
495 yy(k) = y(k) - a(k) * yy(k-1) * beta(k-1)
497 y(n) = yy(n) * beta(n)
499 y(k) = ( yy(k) - c(k) * y(k+1) ) * beta(k)
504 subroutine wave_speeds(h, tv, G, GV, nmodes, cn, CS, full_halos)
505 type(ocean_grid_type),
intent(in) :: G
506 type(verticalgrid_type),
intent(in) :: GV
507 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)),
intent(in) :: h
508 type(thermo_var_ptrs),
intent(in) :: tv
509 integer,
intent(in) :: nmodes
510 real,
dimension(G%isd:G%ied,G%jsd:G%jed,nmodes),
intent(out) :: cn
512 logical,
optional,
intent(in) :: full_halos
515 real,
dimension(SZK_(G)+1) :: &
517 pres, T_int, S_int, &
519 real,
dimension(SZK_(G)) :: &
523 real,
dimension(SZK_(G)-1) :: &
524 a_diag, b_diag, c_diag
527 real,
dimension(SZK_(G),SZI_(G)) :: &
529 real,
dimension(SZK_(G)) :: &
531 real,
parameter :: c1_thresh = 0.01
542 real :: ddet_l,ddet_r
543 real :: det_sub,ddet_sub
546 real,
dimension(nmodes) :: &
549 integer :: nrootsfound
553 real,
dimension(SZI_(G)) :: &
555 H_here, HxT_here, HxS_here, HxR_here
558 real,
parameter :: reduct_factor = 0.5
560 real :: I_Hnew, drxh_sum
561 real,
parameter :: tol1 = 0.0001, tol2 = 0.001
562 real,
pointer,
dimension(:,:,:) :: T, S
564 integer :: kf(szi_(g))
565 integer,
parameter :: max_itt = 10
568 real,
dimension(SZK_(G)+1) :: z_int, N2
570 integer,
parameter :: sub_it_max = 4
573 logical :: sub_rootfound
575 integer :: sub, sub_it
576 integer :: i, j, k, k2, itt, is, ie, js, je, nz, row, iint, m, ig, jg
577 integer :: ig_need_sub, jg_need_sub
579 is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
581 if (
present(cs))
then 582 if (.not.
associated(cs))
call mom_error(fatal,
"MOM_wave_speed: "// &
583 "Module must be initialized before it is used.")
586 if (
present(full_halos))
then ;
if (full_halos)
then 587 is = g%isd ; ie = g%ied ; js = g%jsd ; je = g%jed
590 s => tv%S ; t => tv%T
591 g_rho0 = gv%g_Earth/gv%Rho0
592 use_eos =
associated(tv%eqn_of_state)
594 h_to_pres = gv%g_Earth * gv%Rho0
597 min_h_frac = tol1 /
real(nz)
614 do i=is,ie ; htot(i) = 0.0 ;
enddo 615 do k=1,nz ;
do i=is,ie ; htot(i) = htot(i) + h(i,j,k)*h_to_m ;
enddo ;
enddo 618 hmin(i) = htot(i)*min_h_frac ; kf(i) = 1 ; h_here(i) = 0.0
619 hxt_here(i) = 0.0 ; hxs_here(i) = 0.0 ; hxr_here(i) = 0.0
622 do k=1,nz ;
do i=is,ie
623 if ((h_here(i) > hmin(i)) .and. (h(i,j,k)*h_to_m > hmin(i)))
then 624 hf(kf(i),i) = h_here(i)
625 tf(kf(i),i) = hxt_here(i) / h_here(i)
626 sf(kf(i),i) = hxs_here(i) / h_here(i)
630 h_here(i) = h(i,j,k)*h_to_m
631 hxt_here(i) = (h(i,j,k)*h_to_m)*t(i,j,k)
632 hxs_here(i) = (h(i,j,k)*h_to_m)*s(i,j,k)
634 h_here(i) = h_here(i) + h(i,j,k)*h_to_m
635 hxt_here(i) = hxt_here(i) + (h(i,j,k)*h_to_m)*t(i,j,k)
636 hxs_here(i) = hxs_here(i) + (h(i,j,k)*h_to_m)*s(i,j,k)
639 do i=is,ie ;
if (h_here(i) > 0.0)
then 640 hf(kf(i),i) = h_here(i)
641 tf(kf(i),i) = hxt_here(i) / h_here(i)
642 sf(kf(i),i) = hxs_here(i) / h_here(i)
645 do k=1,nz ;
do i=is,ie
646 if ((h_here(i) > hmin(i)) .and. (h(i,j,k)*h_to_m > hmin(i)))
then 647 hf(kf(i),i) = h_here(i) ; rf(kf(i),i) = hxr_here(i) / h_here(i)
651 h_here(i) = h(i,j,k)*h_to_m
652 hxr_here(i) = (h(i,j,k)*h_to_m)*gv%Rlay(k)
654 h_here(i) = h_here(i) + h(i,j,k)*h_to_m
655 hxr_here(i) = hxr_here(i) + (h(i,j,k)*h_to_m)*gv%Rlay(k)
658 do i=is,ie ;
if (h_here(i) > 0.0)
then 659 hf(kf(i),i) = h_here(i) ; rf(kf(i),i) = hxr_here(i) / h_here(i)
666 if (g%mask2dT(i,j) > 0.5)
then 670 pres(k) = pres(k-1) + h_to_pres*hf(k-1,i)
671 t_int(k) = 0.5*(tf(k,i)+tf(k-1,i))
672 s_int(k) = 0.5*(sf(k,i)+sf(k-1,i))
674 call calculate_density_derivs(t_int, s_int, pres, drho_dt, drho_ds, 2, &
675 kf(i)-1, tv%eqn_of_state)
681 drxh_sum = drxh_sum + 0.5*(hf(k-1,i)+hf(k,i)) * &
682 max(0.0,drho_dt(k)*(tf(k,i)-tf(k-1,i)) + &
683 drho_ds(k)*(sf(k,i)-sf(k-1,i)))
688 drxh_sum = drxh_sum + 0.5*(hf(k-1,i)+hf(k,i)) * &
689 max(0.0,rf(k,i)-rf(k-1,i))
694 if (drxh_sum <= 0.0)
then 701 hc(1) = hf(1,i) ; tc(1) = tf(1,i) ; sc(1) = sf(1,i)
703 if ((drho_dt(k)*(tf(k,i)-tc(kc)) + drho_ds(k)*(sf(k,i)-sc(kc))) * &
704 (hc(kc) + hf(k,i)) < 2.0 * tol2*drxh_sum)
then 706 i_hnew = 1.0 / (hc(kc) + hf(k,i))
707 tc(kc) = (hc(kc)*tc(kc) + hf(k,i)*tf(k,i)) * i_hnew
708 sc(kc) = (hc(kc)*sc(kc) + hf(k,i)*sf(k,i)) * i_hnew
709 hc(kc) = (hc(kc) + hf(k,i))
714 if ((drho_dt(k2)*(tc(k2)-tc(k2-1)) + drho_ds(k2)*(sc(k2)-sc(k2-1))) * &
715 (hc(k2) + hc(k2-1)) < tol2*drxh_sum)
then 717 i_hnew = 1.0 / (hc(kc) + hc(kc-1))
718 tc(kc-1) = (hc(kc)*tc(kc) + hc(kc-1)*tc(kc-1)) * i_hnew
719 sc(kc-1) = (hc(kc)*sc(kc) + hc(kc-1)*sc(kc-1)) * i_hnew
720 hc(kc-1) = (hc(kc) + hc(kc-1))
727 drho_ds(kc) = drho_ds(k) ; drho_dt(kc) = drho_dt(k)
728 tc(kc) = tf(k,i) ; sc(kc) = sf(k,i) ; hc(kc) = hf(k,i)
733 gprime(k) = g_rho0 * (drho_dt(k)*(tc(k)-tc(k-1)) + &
734 drho_ds(k)*(sc(k)-sc(k-1)))
739 hc(1) = hf(1,i) ; rc(1) = rf(1,i)
741 if ((rf(k,i) - rc(kc)) * (hc(kc) + hf(k,i)) < 2.0*tol2*drxh_sum)
then 743 rc(kc) = (hc(kc)*rc(kc) + hf(k,i)*rf(k,i)) / (hc(kc) + hf(k,i))
744 hc(kc) = (hc(kc) + hf(k,i))
749 if ((rc(k2)-rc(k2-1)) * (hc(k2)+hc(k2-1)) < tol2*drxh_sum)
then 751 rc(kc-1) = (hc(kc)*rc(kc) + hc(kc-1)*rc(kc-1)) / (hc(kc) + hc(kc-1))
752 hc(kc-1) = (hc(kc) + hc(kc-1))
759 rc(kc) = rf(k,i) ; hc(kc) = hf(k,i)
764 gprime(k) = g_rho0 * (rc(k)-rc(k-1))
769 ig = i + g%idg_offset ; jg = j + g%jdg_offset
780 igl(k) = 1.0/(gprime(k)*hc(k)) ; igu(k) = 1.0/(gprime(k)*hc(k-1))
781 z_int(k) = z_int(k-1) + hc(k-1)
782 n2(k) = gprime(k)/(0.5*(hc(k)+hc(k-1)))
783 speed2_tot = speed2_tot + gprime(k)*(hc(k-1)+hc(k))
786 n2(1) = n2(2) ; n2(kc+1) = n2(kc)
788 z_int(kc+1) = z_int(kc)+hc(kc)
790 if (abs(z_int(kc+1)-htot(i)) > 1.e-10)
then 791 call mom_error(warning,
"wave_structure: mismatch in total depths")
793 print *,
"z_int(kc+1)=", z_int(kc+1)
794 print *,
"htot(i)=", htot(i)
801 a_diag(row) = (-igu(k))
802 b_diag(row) = (igu(k)+igl(k))
803 c_diag(row) = (-igl(k))
808 b_diag(row) = (igu(k)+igl(k))
809 c_diag(row) = (-igl(k))
812 a_diag(row) = (-igu(k))
813 b_diag(row) = (igu(k)+igl(k))
819 lam_1 = 1.0 / speed2_tot
824 call tridiag_det(a_diag(1:nrows),b_diag(1:nrows),c_diag(1:nrows), &
825 nrows,lam_1,det,ddet)
828 if ((ddet >= 0.0) .or. (-det > -0.5*lam_1*ddet))
then 836 if (abs(dlam) < tol2*lam_1)
then 838 if (lam_1 > 0.0) cn(i,j,1) = 1.0 / sqrt(lam_1)
862 if (nmodes>1 .and. kc>=nmodes+1 .and. cn(i,j,1)>c1_thresh)
then 865 lammin = lam_1*(1.0 + tol2)
867 speed2_min = (reduct_factor*cn(i,j,1)/
real(nmodes))**2
868 lammax = 1.0 / speed2_min
872 numint = nint((lammax - lammin)/laminc)
887 call tridiag_det(a_diag(1:nrows),b_diag(1:nrows),c_diag(1:nrows), &
888 nrows,lammin,det_l,ddet_l)
891 xr = lammin + laminc * iint
893 call tridiag_det(a_diag(1:nrows),b_diag(1:nrows),c_diag(1:nrows), &
894 nrows,xr,det_r,ddet_r)
902 if (det_l*det_r < 0.0)
then 903 if (det_l*ddet_l < 0.0)
then 904 nrootsfound = nrootsfound + 1
905 xbl(nrootsfound) = xl
906 xbr(nrootsfound) = xr
918 ig_need_sub = i + g%idg_offset ; jg_need_sub = j + g%jdg_offset
921 sub_rootfound = .false.
922 do sub_it=1,sub_it_max
926 xl_sub = xl + laminc/(nsub)*sub
927 call tridiag_det(a_diag(1:nrows),b_diag(1:nrows),c_diag(1:nrows), &
928 nrows,xl_sub,det_sub,ddet_sub)
929 if (det_sub*det_r < 0.0)
then 930 if (det_sub*ddet_sub < 0.0)
then 931 sub_rootfound = .true.
932 nrootsfound = nrootsfound + 1
933 xbl(nrootsfound) = xl_sub
934 xbr(nrootsfound) = xr
943 if (sub_rootfound)
exit 946 if (sub_it == sub_it_max)
then 947 call mom_error(warning,
"wave_speed: root not found "// &
948 " after sub_it_max subdivisions of original"// &
968 if (nrootsfound >= nmodes-1)
then 971 elseif (iint == numint)
then 974 cn(i,j,nrootsfound+2:nmodes) = 0.0
1001 call tridiag_det(a_diag(1:nrows),b_diag(1:nrows),c_diag(1:nrows), &
1002 nrows,lam_n,det,ddet)
1005 lam_n = lam_n + dlam
1006 if (abs(dlam) < tol2*lam_1)
then 1008 if (lam_n > 0.0) cn(i,j,m+1) = 1.0 / sqrt(lam_n)
1014 cn(i,j,2:nmodes) = 0.0
1046 subroutine tridiag_det(a,b,c,nrows,lam,det_out,ddet_out)
1047 real,
dimension(:),
intent(in) :: a
1048 real,
dimension(:),
intent(in) :: b
1049 real,
dimension(:),
intent(in) :: c
1050 integer,
intent(in) :: nrows
1051 real,
intent(in) :: lam
1052 real,
intent(out):: det_out
1053 real,
intent(out):: ddet_out
1055 real,
dimension(nrows) :: det
1056 real,
dimension(nrows) :: ddet
1057 real,
parameter:: rescale = 1024.0**4
1061 if (
size(b) .ne. nrows)
call mom_error(warning,
"Diagonal b must be same length as nrows.")
1062 if (
size(a) .ne. nrows)
call mom_error(warning,
"Diagonal a must be same length as nrows.")
1063 if (
size(c) .ne. nrows)
call mom_error(warning,
"Diagonal c must be same length as nrows.")
1065 i_rescale = 1.0/rescale
1067 det(1) = 1.0 ; ddet(1) = 0.0
1068 det(2) = b(2)-lam ; ddet(2) = -1.0
1070 det(n) = (b(n)-lam)*det(n-1) - (a(n)*c(n-1))*det(n-2)
1071 ddet(n) = (b(n)-lam)*ddet(n-1) - (a(n)*c(n-1))*ddet(n-2) - det(n-1)
1073 if (abs(det(n)) > rescale)
then 1074 det(n) = i_rescale*det(n) ; det(n-1) = i_rescale*det(n-1)
1075 ddet(n) = i_rescale*ddet(n) ; ddet(n-1) = i_rescale*ddet(n-1)
1078 det_out = det(nrows)
1079 ddet_out = ddet(nrows)
1084 subroutine wave_speed_init(CS, use_ebt_mode, mono_N2_column_fraction, mono_N2_depth)
1086 logical,
optional,
intent(in) :: use_ebt_mode
1088 real,
optional,
intent(in) :: mono_N2_column_fraction
1090 real,
optional,
intent(in) :: mono_N2_depth
1093 #include "version_variable.h" 1094 character(len=40) :: mdl =
"MOM_wave_speed" 1096 if (
associated(cs))
then 1097 call mom_error(warning,
"wave_speed_init called with an "// &
1098 "associated control structure.")
1100 else ;
allocate(cs) ;
endif 1103 call log_version(mdl, version)
1105 call wave_speed_set_param(cs, use_ebt_mode=use_ebt_mode, mono_n2_column_fraction=mono_n2_column_fraction)
1107 call initialize_remapping(cs%remapping_CS,
'PLM', boundary_extrapolation=.false.)
1114 logical,
optional,
intent(in) :: use_ebt_mode
1116 real,
optional,
intent(in) :: mono_N2_column_fraction
1118 real,
optional,
intent(in) :: mono_N2_depth
1121 if (.not.
associated(cs))
call mom_error(fatal, &
1122 "wave_speed_set_param called with an associated control structure.")
1124 if (
present(use_ebt_mode)) cs%use_ebt_mode=use_ebt_mode
1125 if (
present(mono_n2_column_fraction)) cs%mono_N2_column_fraction=mono_n2_column_fraction
1126 if (
present(mono_n2_depth)) cs%mono_N2_depth=mono_n2_depth
Control structure for MOM_wave_speed.
subroutine, public wave_speed_init(CS, use_ebt_mode, mono_N2_column_fraction, mono_N2_depth)
Initialize control structure for MOM_wave_speed.
Ocean grid type. See mom_grid for details.
Calculates density of sea water from T, S and P.
Provides the ocean grid type.
Provides column-wise vertical remapping functions.
Routines for calculating baroclinic wave speeds.
subroutine tdma6(n, a, b, c, lam, y)
Solve a non-symmetric tridiagonal problem with a scalar contribution to the leading diagonal...
Container for remapping parameters.
subroutine tridiag_det(a, b, c, nrows, lam, det_out, ddet_out)
Calculate the determinant of a tridiagonal matrix with diagonals a,b-lam,c where lam is constant acro...
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 wave_speed_set_param(CS, use_ebt_mode, mono_N2_column_fraction, mono_N2_depth)
Sets internal parameters for MOM_wave_speed.
Provides subroutines for quantities specific to the equation of state.
subroutine, public wave_speeds(h, tv, G, GV, nmodes, cn, CS, full_halos)
Calculates the wave speeds for the first few barolinic modes.
subroutine, public remapping_core_h(CS, n0, h0, u0, n1, h1, u1)
Remaps column of values u0 on grid h0 to grid h1 assuming the top edge is aligned.
The thermo_var_ptrs structure contains pointers to an assortment of thermodynamic fields that may be ...
subroutine, public wave_speed(h, tv, G, GV, cg1, CS, full_halos, use_ebt_mode, mono_N2_column_fraction, mono_N2_depth, modal_structure)
Calculates the wave speed of the first baroclinic mode.
subroutine, public initialize_remapping(CS, remapping_scheme, boundary_extrapolation, check_reconstruction, check_remapping, force_bounds_in_subcell)
Constructor for remapping control structure.
subroutine, public mom_error(level, message, all_print)