58 use mom_time_manager, only : time_type,
operator(+),
operator(/),
operator(-)
63 use fms_mod
, only : read_data
73 implicit none ;
private 75 #include <MOM_memory.h> 82 logical :: do_int_tides
85 integer :: nangle = 24
86 integer :: energized_angle = -1
99 real,
allocatable,
dimension(:,:) :: refl_angle
102 real :: nullangle = -999.9
103 real,
allocatable,
dimension(:,:) :: refl_pref
106 logical,
allocatable,
dimension(:,:) :: refl_pref_logical
109 logical,
allocatable,
dimension(:,:) :: refl_dbl
113 real,
allocatable,
dimension(:,:,:,:) :: cp
115 real,
allocatable,
dimension(:,:,:,:,:) :: tke_leak_loss
117 real,
allocatable,
dimension(:,:,:,:,:) :: tke_quad_loss
119 real,
allocatable,
dimension(:,:,:,:,:) :: tke_froude_loss
121 real,
allocatable,
dimension(:,:) :: tke_itidal_loss_fixed
125 real,
allocatable,
dimension(:,:,:,:,:) :: tke_itidal_loss
127 real,
allocatable,
dimension(:,:) :: tot_leak_loss, tot_quad_loss, &
128 tot_itidal_loss, tot_froude_loss, tot_allprocesses_loss
132 type(time_type),
pointer :: time
134 character(len=200) :: inputdir
139 logical :: apply_background_drag
141 logical :: apply_bottom_drag
143 logical :: apply_wave_drag
146 logical :: apply_froude_drag
148 real,
dimension(:,:,:,:,:),
pointer :: &
151 real,
dimension(:,:,:),
pointer :: &
154 real,
allocatable,
dimension(:) :: &
157 real :: int_tide_source_x
160 real :: int_tide_source_y
169 integer :: id_itide_drag = -1
170 integer :: id_refl_pref = -1, id_refl_ang = -1, id_land_mask = -1
171 integer :: id_dx_cv = -1, id_dy_cu = -1
172 integer :: id_tke_itidal_input = -1
174 integer :: id_tot_en = -1, &
175 id_tot_leak_loss = -1, &
176 id_tot_quad_loss = -1, &
177 id_tot_itidal_loss = -1, &
178 id_tot_froude_loss = -1, &
179 id_tot_allprocesses_loss = -1
181 integer,
allocatable,
dimension(:,:) :: &
183 id_itidal_loss_mode, &
184 id_allprocesses_loss_mode, &
188 integer,
allocatable,
dimension(:,:) :: &
190 id_itidal_loss_ang_mode
195 integer :: ish, ieh, jsh, jeh
206 real,
dimension(SZI_(G),SZJ_(G),SZK_(G)), &
211 real,
dimension(SZI_(G),SZJ_(G)),
intent(in) :: TKE_itidal_input
213 real,
dimension(SZI_(G),SZJ_(G)),
intent(in) :: vel_btTide
215 real,
dimension(SZI_(G),SZJ_(G)),
intent(in) :: Nb
216 real,
intent(in) :: dt
221 real,
dimension(SZI_(G),SZJ_(G),CS%nMode), &
239 real,
dimension(SZI_(G),SZJ_(G),2) :: &
241 real,
dimension(SZI_(G),SZJ_(G),CS%nFreq,CS%nMode) :: &
244 real,
dimension(SZI_(G),SZJB_(G)) :: &
247 real,
dimension(SZI_(G),SZJ_(G)) :: &
249 tot_leak_loss, tot_quad_loss, tot_itidal_loss, tot_Froude_loss, tot_allprocesses_loss, &
252 itidal_loss_mode, allprocesses_loss_mode
254 real :: frac_per_sector, f2, I_rho0, I_D_here, freq2, Kmag2
255 real :: c_phase, loss_rate, Fr2_max
256 real,
parameter :: cn_subRO = 1e-100
257 real :: En_new, En_check
258 real :: En_initial, Delta_E_check
259 real :: TKE_Froude_loss_check, TKE_Froude_loss_tot
260 integer :: a, m, fr, i, j, is, ie, js, je, isd, ied, jsd, jed, nAngle, nzm
261 integer :: id_g, jd_g
262 type(group_pass_type),
save :: pass_test, pass_En
264 if (.not.
associated(cs))
return 265 is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
266 isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed ; nangle = cs%NAngle
267 i_rho0 = 1.0 / gv%Rho0
277 if (cs%energized_angle <= 0)
then 278 frac_per_sector = 1.0 /
real(cs%nangle * cs%nmode * cs%nfreq)
279 do m=1,cs%nMode ;
do fr=1,cs%nFreq ;
do a=1,cs%nAngle ;
do j=js,je ;
do i=is,ie
280 f2 = 0.25*((g%CoriolisBu(i,j)**2 + g%CoriolisBu(i-1,j-1)**2) + &
281 (g%CoriolisBu(i,j-1)**2 + g%CoriolisBu(i-1,j)**2))
282 if (cs%frequency(fr)**2 > f2) &
283 cs%En(i,j,a,fr,m) = cs%En(i,j,a,fr,m) + &
284 dt*frac_per_sector*(1-cs%q_itides)*tke_itidal_input(i,j)
285 enddo ;
enddo ;
enddo ;
enddo ;
enddo 286 elseif (cs%energized_angle <= cs%nAngle)
then 287 frac_per_sector = 1.0 /
real(cs%nmode * cs%nfreq)
288 a = cs%energized_angle
289 do m=1,cs%nMode ;
do fr=1,cs%nFreq ;
do j=js,je ;
do i=is,ie
290 f2 = 0.25*((g%CoriolisBu(i,j)**2 + g%CoriolisBu(i-1,j-1)**2) + &
291 (g%CoriolisBu(i,j-1)**2 + g%CoriolisBu(i-1,j)**2))
292 if (cs%frequency(fr)**2 > f2) &
293 cs%En(i,j,a,fr,m) = cs%En(i,j,a,fr,m) + &
294 dt*frac_per_sector**(1-cs%q_itides)*tke_itidal_input(i,j)
295 enddo ;
enddo ;
enddo ;
enddo 297 call mom_error(warning,
"Internal tide energy is being put into a angular "//&
298 "band that does not exist.")
302 do j=jsd,jed ;
do i=isd,ied ; test(i,j,1) = 1.0 ; test(i,j,2) = 0.0 ;
enddo ;
enddo 303 do m=1,cs%nMode ;
do fr=1,cs%nFreq
306 call create_group_pass(pass_test, test(:,:,1), test(:,:,2), g%domain, stagger=agrid)
310 do m=1,cs%nMode ;
do fr=1,cs%nFreq
311 call refract(cs%En(:,:,:,fr,m), cn(:,:,m), cs%frequency(fr), 0.5*dt, g, cs%nAngle, cs%use_PPMang)
315 do m=1,cs%NMode ;
do fr=1,cs%Nfreq ;
do a=1,cs%nAngle
316 do j=js,je ;
do i=is,ie
317 if (cs%En(i,j,a,fr,m)<0.0)
then 318 id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset
319 print *,
'After first refraction: En<0.0 at ig=', id_g,
', jg=', jd_g
320 print *,
'En=',cs%En(i,j,a,fr,m)
321 print *,
'Setting En to zero'; cs%En(i,j,a,fr,m) = 0.0
325 enddo ;
enddo ;
enddo 327 call do_group_pass(pass_en, g%domain)
335 do m=1,cs%NMode ;
do fr=1,cs%Nfreq
336 call propagate(cs%En(:,:,:,fr,m), cn(:,:,m), cs%frequency(fr), dt, g, cs, cs%NAngle)
340 do m=1,cs%NMode ;
do fr=1,cs%Nfreq ;
do a=1,cs%nAngle
341 do j=js,je ;
do i=is,ie
342 if (cs%En(i,j,a,fr,m)<0.0)
then 343 id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset
344 cs%En(i,j,a,fr,m) = 0.0
345 if(abs(cs%En(i,j,a,fr,m))>1.0)then
346 print *,
'After propagation: En<0.0 at ig=', id_g,
', jg=', jd_g
347 print *,
'En=',cs%En(i,j,a,fr,m)
348 print *,
'Setting En to zero' 353 enddo ;
enddo ;
enddo 372 do m=1,cs%NMode ;
do fr=1,cs%Nfreq
373 call refract(cs%En(:,:,:,fr,m), cn(:,:,m), cs%frequency(fr), 0.5*dt, g, cs%NAngle, cs%use_PPMang)
377 do m=1,cs%NMode ;
do fr=1,cs%Nfreq ;
do a=1,cs%nAngle
378 do j=js,je ;
do i=is,ie
379 if (cs%En(i,j,a,fr,m)<0.0)
then 380 id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset
381 print *,
'After second refraction: En<0.0 at ig=', id_g,
', jg=', jd_g
385 enddo ;
enddo ;
enddo 388 if (cs%apply_background_drag .or. cs%apply_bottom_drag &
389 .or. cs%apply_wave_drag .or. cs%apply_Froude_drag &
390 .or. (cs%id_tot_En > 0))
then 392 tot_en_mode(:,:,:,:) = 0.0
393 do m=1,cs%NMode ;
do fr=1,cs%Nfreq
394 do j=jsd,jed ;
do i=isd,ied ;
do a=1,cs%nAngle
395 tot_en(i,j) = tot_en(i,j) + cs%En(i,j,a,fr,m)
396 tot_en_mode(i,j,fr,m) = tot_en_mode(i,j,fr,m) + cs%En(i,j,a,fr,m)
397 enddo ;
enddo ;
enddo 402 if (cs%apply_background_drag)
then 403 do m=1,cs%nMode ;
do fr=1,cs%nFreq ;
do a=1,cs%nAngle ;
do j=jsd,jed ;
do i=isd,ied
406 cs%TKE_leak_loss(i,j,a,fr,m) = cs%En(i,j,a,fr,m) * cs%decay_rate
407 cs%En(i,j,a,fr,m) = cs%En(i,j,a,fr,m) / (1.0 + dt *cs%decay_rate)
408 enddo ;
enddo ;
enddo ;
enddo ;
enddo 411 do m=1,cs%NMode ;
do fr=1,cs%Nfreq ;
do a=1,cs%nAngle
412 do j=js,je ;
do i=is,ie
413 if (cs%En(i,j,a,fr,m)<0.0)
then 414 id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset
415 print *,
'After leak loss: En<0.0 at ig=', id_g,
', jg=', jd_g
419 enddo ;
enddo ;
enddo 422 if (cs%apply_bottom_drag)
then 423 do j=jsd,jed ;
do i=isd,ied
424 i_d_here = 1.0 / max(g%bathyT(i,j), 1.0)
425 drag_scale(i,j) = cs%cdrag * sqrt(max(0.0, vel_bttide(i,j)**2 + &
426 tot_en(i,j) * i_rho0 * i_d_here)) * i_d_here
428 do m=1,cs%nMode ;
do fr=1,cs%nFreq ;
do a=1,cs%nAngle ;
do j=jsd,jed ;
do i=isd,ied
431 cs%TKE_quad_loss(i,j,a,fr,m) = cs%En(i,j,a,fr,m) * drag_scale(i,j)
432 cs%En(i,j,a,fr,m) = cs%En(i,j,a,fr,m) / (1.0 + dt *drag_scale(i,j))
433 enddo ;
enddo ;
enddo ;
enddo ;
enddo 436 do m=1,cs%NMode ;
do fr=1,cs%Nfreq ;
do a=1,cs%nAngle
437 do j=js,je ;
do i=is,ie
438 if (cs%En(i,j,a,fr,m)<0.0)
then 439 id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset
440 print *,
'After bottom loss: En<0.0 at ig=', id_g,
', jg=', jd_g
444 enddo ;
enddo ;
enddo 449 if (cs%apply_wave_drag .or. cs%apply_Froude_drag)
then 450 do m=1,cs%NMode ;
do fr=1,cs%Nfreq
452 call wave_structure(h, tv, g, gv, cn(:,:,m), m, cs%frequency(fr), &
453 cs%wave_structure_CSp, tot_en_mode(:,:,fr,m), full_halos=.true.)
455 do j=jsd,jed ;
do i=isd,ied
456 id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset
457 nzm = cs%wave_structure_CSp%num_intfaces(i,j)
458 ub(i,j,fr,m) = cs%wave_structure_CSp%Uavg_profile(i,j,nzm)
459 umax(i,j,fr,m) = maxval(cs%wave_structure_CSp%Uavg_profile(i,j,1:nzm))
481 if (cs%apply_wave_drag)
then 484 cs%TKE_itidal_loss, dt, full_halos=.false.)
487 do m=1,cs%NMode ;
do fr=1,cs%Nfreq ;
do a=1,cs%nAngle
488 do j=js,je ;
do i=is,ie
489 if (cs%En(i,j,a,fr,m)<0.0)
then 490 id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset
491 print *,
'After wave drag loss: En<0.0 at ig=', id_g,
', jg=', jd_g
495 enddo ;
enddo ;
enddo 498 if (cs%apply_Froude_drag)
then 500 do m=1,cs%NMode ;
do fr=1,cs%Nfreq
501 freq2 = cs%frequency(fr)**2
502 do j=jsd,jed ;
do i=isd,ied
503 id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset
505 f2 = 0.25*(g%CoriolisBu(i,j)**2 + g%CoriolisBu(i-1,j)**2 + &
506 g%CoriolisBu(i,j-1)**2 + g%CoriolisBu(i-1,j-1)**2 )
507 kmag2 = (freq2 - f2) / (cn(i,j,m)**2 + cn_subro**2)
509 if (kmag2 > 0.0)
then 510 c_phase = sqrt(freq2/kmag2)
511 nzm = cs%wave_structure_CSp%num_intfaces(i,j)
512 fr2_max = (umax(i,j,fr,m)/c_phase)**2
514 if (fr2_max > 1.0)
then 515 en_initial = sum(cs%En(i,j,:,fr,m))
517 loss_rate = (1/fr2_max - 1.0)/dt
520 cs%TKE_Froude_loss(i,j,a,fr,m) = cs%En(i,j,a,fr,m) * abs(loss_rate)
522 en_new = cs%En(i,j,a,fr,m)/fr2_max
523 en_check = cs%En(i,j,a,fr,m) - cs%TKE_Froude_loss(i,j,a,fr,m)*dt
525 cs%En(i,j,a,fr,m) = cs%En(i,j,a,fr,m)/fr2_max
527 if (abs(en_new - en_check) > 1e-10)
then 528 call mom_error(warning,
"MOM_internal_tides: something's wrong with Fr-breaking.")
529 print *,
"En_new=", en_new
530 print *,
"En_check=", en_check
534 delta_e_check = en_initial - sum(cs%En(i,j,:,fr,m))
535 tke_froude_loss_check = abs(delta_e_check)/dt
536 tke_froude_loss_tot = sum(cs%TKE_Froude_loss(i,j,:,fr,m))
537 if (abs(tke_froude_loss_check - tke_froude_loss_tot) > 1e-10)
then 538 call mom_error(warning,
"MOM_internal_tides: something's wrong with Fr energy update.")
539 print *,
"TKE_Froude_loss_check=", tke_froude_loss_check
540 print *,
"TKE_Froude_loss_tot=", tke_froude_loss_tot
544 cs%cp(i,j,fr,m) = c_phase
549 do m=1,cs%NMode ;
do fr=1,cs%Nfreq ;
do a=1,cs%nAngle
550 do j=js,je ;
do i=is,ie
551 if (cs%En(i,j,a,fr,m)<0.0)
then 552 id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset
553 print *,
'After Froude loss: En<0.0 at ig=', id_g,
', jg=', jd_g
557 enddo ;
enddo ;
enddo 560 do m=1,cs%NMode ;
do fr=1,cs%Nfreq
562 call sum_en(g,cs,cs%En(:,:,:,fr,m),
'prop_int_tide')
566 if (query_averaging_enabled(cs%diag))
then 568 if (cs%id_tot_En > 0)
call post_data(cs%id_tot_En, tot_en, cs%diag)
569 if (cs%id_itide_drag > 0)
call post_data(cs%id_itide_drag, drag_scale, cs%diag)
570 if (cs%id_TKE_itidal_input > 0)
call post_data(cs%id_TKE_itidal_input, &
571 tke_itidal_input, cs%diag)
574 do m=1,cs%NMode ;
do fr=1,cs%Nfreq ;
if (cs%id_En_mode(fr,m) > 0)
then 576 do a=1,cs%nAngle ;
do j=js,je ;
do i=is,ie
577 tot_en(i,j) = tot_en(i,j) + cs%En(i,j,a,fr,m)
578 enddo ;
enddo ;
enddo 579 call post_data(cs%id_En_mode(fr,m), tot_en, cs%diag)
580 endif ;
enddo ;
enddo 583 do m=1,cs%NMode ;
do fr=1,cs%Nfreq ;
if (cs%id_En_ang_mode(fr,m) > 0)
then 584 call post_data(cs%id_En_ang_mode(fr,m), cs%En(:,:,:,fr,m) , cs%diag)
585 endif ;
enddo ;
enddo 588 tot_leak_loss(:,:) = 0.0
589 tot_quad_loss(:,:) = 0.0
590 tot_itidal_loss(:,:) = 0.0
591 tot_froude_loss(:,:) = 0.0
592 tot_allprocesses_loss(:,:) = 0.0
593 do m=1,cs%NMode ;
do fr=1,cs%Nfreq ;
do a=1,cs%nAngle ;
do j=js,je ;
do i=is,ie
594 tot_leak_loss(i,j) = tot_leak_loss(i,j) + cs%TKE_leak_loss(i,j,a,fr,m)
595 tot_quad_loss(i,j) = tot_quad_loss(i,j) + cs%TKE_quad_loss(i,j,a,fr,m)
596 tot_itidal_loss(i,j) = tot_itidal_loss(i,j) + cs%TKE_itidal_loss(i,j,a,fr,m)
597 tot_froude_loss(i,j) = tot_froude_loss(i,j) + cs%TKE_Froude_loss(i,j,a,fr,m)
598 enddo ;
enddo ;
enddo ;
enddo ;
enddo 599 do j=js,je ;
do i=is,ie
600 tot_allprocesses_loss(i,j) = tot_leak_loss(i,j) + tot_quad_loss(i,j) + &
601 tot_itidal_loss(i,j) + tot_froude_loss(i,j)
603 cs%tot_leak_loss = tot_leak_loss
604 cs%tot_quad_loss = tot_quad_loss
605 cs%tot_itidal_loss = tot_itidal_loss
606 cs%tot_Froude_loss = tot_froude_loss
607 cs%tot_allprocesses_loss = tot_allprocesses_loss
608 if (cs%id_tot_leak_loss > 0)
then 609 call post_data(cs%id_tot_leak_loss, tot_leak_loss, cs%diag)
611 if (cs%id_tot_quad_loss > 0)
then 612 call post_data(cs%id_tot_quad_loss, tot_quad_loss, cs%diag)
614 if (cs%id_tot_itidal_loss > 0)
then 615 call post_data(cs%id_tot_itidal_loss, tot_itidal_loss, cs%diag)
617 if (cs%id_tot_Froude_loss > 0)
then 618 call post_data(cs%id_tot_Froude_loss, tot_froude_loss, cs%diag)
620 if (cs%id_tot_allprocesses_loss > 0)
then 621 call post_data(cs%id_tot_allprocesses_loss, tot_allprocesses_loss, cs%diag)
625 do m=1,cs%NMode ;
do fr=1,cs%Nfreq
626 if (cs%id_itidal_loss_mode(fr,m) > 0 .or. cs%id_allprocesses_loss_mode(fr,m) > 0)
then 627 itidal_loss_mode(:,:) = 0.0
628 allprocesses_loss_mode(:,:) = 0.0
629 do a=1,cs%nAngle ;
do j=js,je ;
do i=is,ie
630 itidal_loss_mode(i,j) = itidal_loss_mode(i,j) + cs%TKE_itidal_loss(i,j,a,fr,m)
631 allprocesses_loss_mode(i,j) = allprocesses_loss_mode(i,j) + &
632 cs%TKE_leak_loss(i,j,a,fr,m) + cs%TKE_quad_loss(i,j,a,fr,m) + &
633 cs%TKE_itidal_loss(i,j,a,fr,m) + cs%TKE_Froude_loss(i,j,a,fr,m)
634 enddo ;
enddo ;
enddo 635 call post_data(cs%id_itidal_loss_mode(fr,m), itidal_loss_mode, cs%diag)
636 call post_data(cs%id_allprocesses_loss_mode(fr,m), allprocesses_loss_mode, cs%diag)
637 endif ;
enddo ;
enddo 640 do m=1,cs%NMode ;
do fr=1,cs%Nfreq ;
if (cs%id_itidal_loss_ang_mode(fr,m) > 0)
then 641 call post_data(cs%id_itidal_loss_ang_mode(fr,m), cs%TKE_itidal_loss(:,:,:,fr,m) , cs%diag)
642 endif ;
enddo ;
enddo 645 do m=1,cs%NMode ;
do fr=1,cs%Nfreq ;
if (cs%id_Ub_mode(fr,m) > 0)
then 646 call post_data(cs%id_Ub_mode(fr,m), ub(:,:,fr,m), cs%diag)
647 endif ;
enddo ;
enddo 650 do m=1,cs%NMode ;
do fr=1,cs%Nfreq ;
if (cs%id_cp_mode(fr,m) > 0)
then 651 call post_data(cs%id_cp_mode(fr,m), cs%cp(:,:,fr,m), cs%diag)
652 endif ;
enddo ;
enddo 659 subroutine sum_en(G, CS, En, label)
662 real,
dimension(G%isd:G%ied,G%jsd:G%jed,CS%NAngle),
intent(in) :: En
663 character(len=*),
intent(in) :: label
667 real :: En_sum, tmpForSumming, En_sum_diff, En_sum_pdiff
669 real :: Isecs_per_day = 1.0 / 86400.0
672 call get_time(cs%Time, seconds)
673 days =
real(seconds) * Isecs_per_day
678 tmpforsumming = global_area_mean(en(:,:,a),g)*g%areaT_global
679 en_sum = en_sum + tmpforsumming
681 en_sum_diff = en_sum - cs%En_sum
682 if (cs%En_sum .ne. 0.0)
then 683 en_sum_pdiff= (en_sum_diff/cs%En_sum)*100.0
701 subroutine itidal_lowmode_loss(G, CS, Nb, Ub, En, TKE_loss_fixed, TKE_loss, dt, full_halos)
704 real,
dimension(G%isd:G%ied,G%jsd:G%jed), &
706 real,
dimension(G%isd:G%ied,G%jsd:G%jed,CS%nFreq,CS%nMode), &
709 real,
dimension(G%isd:G%ied,G%jsd:G%jed), &
710 intent(in) :: TKE_loss_fixed
712 real,
dimension(G%isd:G%ied,G%jsd:G%jed,CS%NAngle,CS%nFreq,CS%nMode), &
714 real,
dimension(G%isd:G%ied,G%jsd:G%jed,CS%NAngle,CS%nFreq,CS%nMode), &
715 intent(out) :: TKE_loss
717 real,
intent(in) :: dt
718 logical,
optional,
intent(in) :: full_halos
734 integer :: j,i,m,fr,a, is, ie, js, je
737 real :: TKE_sum_check
738 real :: frac_per_sector
742 real,
parameter :: En_negl = 1e-30
744 is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
746 q_itides = cs%q_itides
748 if (
present(full_halos))
then ;
if (full_halos)
then 749 is = g%isd ; ie = g%ied ; js = g%jsd ; je = g%jed
752 do j=js,je ;
do i=is,ie ;
do m=1,cs%nMode ;
do fr=1,cs%nFreq
757 en_tot = en_tot + en(i,j,a,fr,m)
761 tke_loss_tot = q_itides * tke_loss_fixed(i,j) * nb(i,j) * ub(i,j,fr,m)**2
765 if (en_tot > 0.0)
then 767 frac_per_sector = en(i,j,a,fr,m)/en_tot
768 tke_loss(i,j,a,fr,m) = frac_per_sector*tke_loss_tot
769 loss_rate = tke_loss(i,j,a,fr,m) / (en(i,j,a,fr,m) + en_negl)
770 en(i,j,a,fr,m) = en(i,j,a,fr,m) / (1.0 + dt*loss_rate)
774 tke_loss(i,j,:,fr,m) = 0.0
795 enddo ;
enddo ;
enddo ;
enddo 803 integer,
intent(in) :: i,j
806 character(len=*),
intent(in) :: mechanism
807 real,
intent(out) :: TKE_loss_sum
817 if(mechanism ==
'LeakDrag') tke_loss_sum = cs%tot_leak_loss(i,j)
818 if(mechanism ==
'QuadDrag') tke_loss_sum = cs%tot_quad_loss(i,j)
819 if(mechanism ==
'WaveDrag') tke_loss_sum = cs%tot_itidal_loss(i,j)
820 if(mechanism ==
'Froude') tke_loss_sum = cs%tot_Froude_loss(i,j)
825 subroutine refract(En, cn, freq, dt, G, NAngle, use_PPMang)
827 integer,
intent(in) :: NAngle
828 real,
dimension(G%isd:G%ied,G%jsd:G%jed,NAngle), &
832 real,
dimension(G%isd:G%ied,G%jsd:G%jed), &
834 real,
intent(in) :: freq
835 real,
intent(in) :: dt
836 logical,
intent(in) :: use_PPMang
848 integer,
parameter :: stencil = 2
849 real,
dimension(SZI_(G),1-stencil:NAngle+stencil) :: &
851 real,
dimension(1-stencil:NAngle+stencil) :: &
853 real,
dimension(SZI_(G)) :: &
854 Dk_Dt_Kmag, Dl_Dt_Kmag
855 real,
dimension(SZI_(G),0:nAngle) :: &
857 real,
dimension(SZI_(G),SZJ_(G),1-stencil:NAngle+stencil) :: &
861 real :: df2_dy, df2_dx
865 real :: Angle_size, dt_Angle_size, angle
866 real :: Ifreq, Kmag2, I_Kmag
867 real,
parameter :: cn_subRO = 1e-100
868 integer :: is, ie, js, je, asd, aed, na
871 is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; na =
size(en,3)
872 asd = 1-stencil ; aed = nangle+stencil
876 angle_size = (8.0*atan(1.0)) / (
real(nangle))
877 dt_angle_size = dt / angle_size
880 angle = (
real(A) - 0.5) * angle_size
881 cos_angle(a) = cos(angle) ; sin_angle(a) = sin(angle)
885 cfl_ang(:,:,:) = 0.0;
888 do a=1,na ;
do i=is,ie
889 en2d(i,a) = en(i,j,a)
891 do a=asd,0 ;
do i=is,ie
892 en2d(i,a) = en2d(i,a+nangle)
893 en2d(i,nangle+stencil+a) = en2d(i,stencil+a)
898 f2 = 0.25*((g%CoriolisBu(i,j)**2 + g%CoriolisBu(i-1,j-1)**2) + &
899 (g%CoriolisBu(i,j-1)**2 + g%CoriolisBu(i-1,j)**2))
900 favg = 0.25*((g%CoriolisBu(i,j) + g%CoriolisBu(i-1,j-1)) + &
901 (g%CoriolisBu(i,j-1) + g%CoriolisBu(i-1,j)))
902 df2_dx = 0.5*((g%CoriolisBu(i,j)**2 + g%CoriolisBu(i,j-1)**2) - &
903 (g%CoriolisBu(i-1,j)**2 + g%CoriolisBu(i-1,j-1)**2)) * &
905 df_dx = 0.5*((g%CoriolisBu(i,j) + g%CoriolisBu(i,j-1)) - &
906 (g%CoriolisBu(i-1,j) + g%CoriolisBu(i-1,j-1))) * &
908 dlncn_dx = 0.5*( g%IdxCu(i,j) * (cn(i+1,j) - cn(i,j)) / &
909 (0.5*(cn(i+1,j) + cn(i,j)) + cn_subro) + &
910 g%IdxCu(i-1,j) * (cn(i,j) - cn(i-1,j)) / &
911 (0.5*(cn(i,j) + cn(i-1,j)) + cn_subro) )
912 df2_dy = 0.5*((g%CoriolisBu(i,j)**2 + g%CoriolisBu(i-1,j)**2) - &
913 (g%CoriolisBu(i,j-1)**2 + g%CoriolisBu(i-1,j-1)**2)) * &
915 df_dy = 0.5*((g%CoriolisBu(i,j) + g%CoriolisBu(i-1,j)) - &
916 (g%CoriolisBu(i,j-1) + g%CoriolisBu(i-1,j-1))) * &
918 dlncn_dy = 0.5*( g%IdyCv(i,j) * (cn(i,j+1) - cn(i,j)) / &
919 (0.5*(cn(i,j+1) + cn(i,j)) + cn_subro) + &
920 g%IdyCv(i,j-1) * (cn(i,j) - cn(i,j-1)) / &
921 (0.5*(cn(i,j) + cn(i,j-1)) + cn_subro) )
922 kmag2 = (freq**2 - f2) / (cn(i,j)**2 + cn_subro**2)
923 if (kmag2 > 0.0)
then 924 i_kmag = 1.0 / sqrt(kmag2)
925 dk_dt_kmag(i) = -ifreq * (favg*df_dx + (freq**2 - f2) * dlncn_dx) * i_kmag
926 dl_dt_kmag(i) = -ifreq * (favg*df_dy + (freq**2 - f2) * dlncn_dy) * i_kmag
934 do a=asd,aed ;
do i=is,ie
935 cfl_ang(i,j,a) = (cos_angle(a) * dl_dt_kmag(i) - sin_angle(a) * dk_dt_kmag(i)) * &
937 if (abs(cfl_ang(i,j,a)) > 1.0)
then 938 call mom_error(warning,
"refract: CFL exceeds 1.", .true.)
939 if (cfl_ang(i,j,a) > 0.0)
then ; cfl_ang(i,j,a) = 1.0 ;
else ; cfl_ang(i,j,a) = -1.0 ;
endif 944 if(.not.use_ppmang)
then 946 do a=0,na ;
do i=is,ie
947 if (cfl_ang(i,j,a) > 0.0)
then 948 flux_e(i,a) = cfl_ang(i,j,a) * en2d(i,a)
950 flux_e(i,a) = cfl_ang(i,j,a) * en2d(i,a+1)
961 do a=1,na ;
do i=is,ie
965 en(i,j,a) = en2d(i,a) + (flux_e(i,a-1) - flux_e(i,a))
974 integer,
intent(in) :: NAngle
975 real,
intent(in) :: dt
976 integer,
intent(in) :: halo_ang
977 real,
dimension(1-halo_ang:NAngle+halo_ang), &
979 real,
dimension(1-halo_ang:NAngle+halo_ang), &
980 intent(in) :: CFL_ang
981 real,
dimension(0:NAngle),
intent(out) :: Flux_En
992 real :: aR, aL, dMx, dMn, Ep, Ec, Em, dA, mA, a6
995 angle_size = (8.0*atan(1.0)) / (
real(nangle))
996 i_angle_size = 1 / angle_size
1000 u_ang = cfl_ang(a)*angle_size*i_dt
1001 if (u_ang >= 0.0)
then 1003 ep = en2d(a+1)*i_angle_size
1004 ec = en2d(a) *i_angle_size
1005 em = en2d(a-1)*i_angle_size
1006 al = ( 5.*ec + ( 2.*em - ep ) )/6.
1007 al = max( min(ec,em), al) ; al = min( max(ec,em), al)
1008 ar = ( 5.*ec + ( 2.*ep - em ) )/6.
1009 ar = max( min(ec,ep), ar) ; ar = min( max(ec,ep), ar)
1010 da = ar - al ; ma = 0.5*( ar + al )
1011 if ((ep-ec)*(ec-em) <= 0.)
then 1013 elseif ( da*(ec-ma) > (da*da)/6. )
then 1015 elseif ( da*(ec-ma) < - (da*da)/6. )
then 1018 a6 = 6.*ec - 3. * (ar + al)
1020 flux = u_ang*( ar + 0.5 * cfl_ang(a) * ( ( al - ar ) + a6 * ( 1. - 2./3. * cfl_ang(a) ) ) )
1023 flux_en(a) = dt * flux
1027 ep = en2d(a+2)*i_angle_size
1028 ec = en2d(a+1)*i_angle_size
1029 em = en2d(a) *i_angle_size
1030 al = ( 5.*ec + ( 2.*em - ep ) )/6.
1031 al = max( min(ec,em), al) ; al = min( max(ec,em), al)
1032 ar = ( 5.*ec + ( 2.*ep - em ) )/6.
1033 ar = max( min(ec,ep), ar) ; ar = min( max(ec,ep), ar)
1034 da = ar - al ; ma = 0.5*( ar + al )
1035 if ((ep-ec)*(ec-em) <= 0.)
then 1037 elseif ( da*(ec-ma) > (da*da)/6. )
then 1039 elseif ( da*(ec-ma) < - (da*da)/6. )
then 1042 a6 = 6.*ec - 3. * (ar + al)
1044 flux = u_ang*( ar + 0.5 * cfl_ang(a) * ( ( al - ar ) + a6 * ( 1. - 2./3. * cfl_ang(a) ) ) )
1047 flux_en(a) = dt * flux
1054 subroutine propagate(En, cn, freq, dt, G, CS, NAngle)
1055 type(ocean_grid_type),
intent(inout) :: G
1056 integer,
intent(in) :: NAngle
1057 real,
dimension(G%isd:G%ied,G%jsd:G%jed,NAngle), &
1061 real,
dimension(G%isd:G%ied,G%jsd:G%jed), &
1063 real,
intent(in) :: freq
1064 real,
intent(in) :: dt
1075 real,
dimension(G%IsdB:G%IedB,G%JsdB:G%JedB) :: &
1077 integer,
parameter :: stencil = 2
1078 real,
dimension(SZIB_(G),SZJ_(G)) :: &
1080 real,
dimension(SZI_(G),SZJB_(G)) :: &
1082 real,
dimension(0:NAngle) :: &
1083 cos_angle, sin_angle
1084 real,
dimension(NAngle) :: &
1085 Cgx_av, Cgy_av, dCgx, dCgy
1087 real :: Angle_size, I_Angle_size, angle
1088 real :: Ifreq, freq2
1089 real,
parameter :: cn_subRO = 1e-100
1091 integer :: is, ie, js, je, asd, aed, na
1092 integer :: ish, ieh, jsh, jeh
1095 is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; na =
size(en,3)
1096 asd = 1-stencil ; aed = nangle+stencil
1110 jsh = js-1 ; jeh = je+1 ; ish = is-1 ; ieh = ie+1
1112 angle_size = (8.0*atan(1.0)) /
real(nangle)
1113 i_angle_size = 1.0 / angle_size
1115 if (cs%corner_adv)
then 1121 do j=jsh-1,jeh ;
do i=ish-1,ieh
1122 f2 = g%CoriolisBu(i,j)**2
1123 speed(i,j) = 0.25*(cn(i,j) + cn(i+1,j) + cn(i+1,j+1) + cn(i,j+1)) * &
1124 sqrt(max(freq2 - f2, 0.0)) * ifreq
1128 lb%jsh = js ; lb%jeh = je ; lb%ish = is ; lb%ieh = ie
1136 angle = (
real(A) - 0.5) * angle_size
1137 cos_angle(a) = cos(angle) ; sin_angle(a) = sin(angle)
1141 cgx_av(a) = (sin_angle(a) - sin_angle(a-1)) * i_angle_size
1142 cgy_av(a) = -(cos_angle(a) - cos_angle(a-1)) * i_angle_size
1143 dcgx(a) = sqrt(0.5 + 0.5*(sin_angle(a)*cos_angle(a) - &
1144 sin_angle(a-1)*cos_angle(a-1)) * i_angle_size - &
1146 dcgy(a) = sqrt(0.5 - 0.5*(sin_angle(a)*cos_angle(a) - &
1147 sin_angle(a-1)*cos_angle(a-1)) * i_angle_size - &
1151 do j=jsh,jeh ;
do i=ish-1,ieh
1152 f2 = 0.5*(g%CoriolisBu(i,j)**2 + g%CoriolisBu(i,j-1)**2)
1153 speed_x(i,j) = 0.5*(cn(i,j) + cn(i+1,j)) * g%mask2dCu(i,j) * &
1154 sqrt(max(freq2 - f2, 0.0)) * ifreq
1156 do j=jsh-1,jeh ;
do i=ish,ieh
1157 f2 = 0.5*(g%CoriolisBu(i,j)**2 + g%CoriolisBu(i-1,j)**2)
1158 speed_y(i,j) = 0.5*(cn(i,j) + cn(i,j+1)) * g%mask2dCv(i,j) * &
1159 sqrt(max(freq2 - f2, 0.0)) * ifreq
1163 lb%jsh = jsh ; lb%jeh = jeh ; lb%ish = ish ; lb%ieh = ieh
1164 call propagate_x(en(:,:,:), speed_x, cgx_av(:), dcgx(:), dt, g, cs%nAngle, cs, lb)
1170 call pass_var(en(:,:,:),g%domain)
1174 lb%jsh = jsh ; lb%jeh = jeh ; lb%ish = ish ; lb%ieh = ieh
1175 call propagate_y(en(:,:,:), speed_y, cgy_av(:), dcgy(:), dt, g, cs%nAngle, cs, lb)
1187 type(ocean_grid_type),
intent(in) :: G
1188 real,
dimension(G%isd:G%ied,G%jsd:G%jed), &
1191 real,
dimension(G%IsdB:G%IedB,G%Jsd:G%Jed), &
1194 integer,
intent(in) :: energized_wedge
1195 integer,
intent(in) :: NAngle
1196 real,
intent(in) :: dt
1216 integer :: i, j, k, ish, ieh, jsh, jeh, m
1217 real :: TwoPi, Angle_size
1218 real :: energized_angle
1223 real :: I_Nsubwedges
1224 real :: cos_thetaDT, sin_thetaDT
1225 real :: xNE,xNW,xSW,xSE,yNE,yNW,ySW,ySE
1226 real :: CFL_xNE,CFL_xNW,CFL_xSW,CFL_xSE,CFL_yNE,CFL_yNW,CFL_ySW,CFL_ySE,CFL_max
1227 real :: xN,xS,xE,xW,yN,yS,yE,yW
1230 real :: slopeN,slopeW,slopeS,slopeE, bN,bW,bS,bE
1231 real :: aNE,aN,aNW,aW,aSW,aS,aSE,aE,aC
1234 real,
dimension(G%IsdB:G%IedB,G%Jsd:G%Jed) :: x,y
1235 real,
dimension(G%IsdB:G%IedB,G%Jsd:G%Jed) :: Idx,Idy
1236 real,
dimension(G%IsdB:G%IedB,G%Jsd:G%Jed) :: dx,dy
1237 real,
dimension(2) :: E_new
1240 ish = lb%ish ; ieh = lb%ieh ; jsh = lb%jsh ; jeh = lb%jeh
1241 twopi = (8.0*atan(1.0))
1242 nsubrays =
real(size(e_new))
1243 i_nsubwedges = 1./(nsubrays - 1)
1245 angle_size = twopi /
real(nangle)
1246 energized_angle = angle_size *
real(energized_wedge - 1) 1251 idx = g%IdxBu; dx = g%dxBu
1252 idy = g%IdyBu; dy = g%dyBu
1254 do j=jsh,jeh;
do i=ish,ieh
1255 do m=1,int(nsubrays)
1256 theta = energized_angle - 0.5*angle_size +
real(m - 1)*Angle_size*I_Nsubwedges
1257 if (theta < 0.0)
then 1258 theta = theta + twopi
1259 elseif (theta > twopi)
then 1260 theta = theta - twopi
1262 cos_thetadt = cos(theta)*dt
1263 sin_thetadt = sin(theta)*dt
1266 xg = x(i,j); yg = y(i,j)
1267 xne = xg - speed(i,j)*cos_thetadt
1268 yne = yg - speed(i,j)*sin_thetadt
1269 cfl_xne = (xg-xne)*idx(i,j)
1270 cfl_yne = (yg-yne)*idy(i,j)
1272 xg = x(i-1,j); yg = y(i-1,j)
1273 xnw = xg - speed(i-1,j)*cos_thetadt
1274 ynw = yg - speed(i-1,j)*sin_thetadt
1275 cfl_xnw = (xg-xnw)*idx(i-1,j)
1276 cfl_ynw = (yg-ynw)*idy(i-1,j)
1278 xg = x(i-1,j-1); yg = y(i-1,j-1)
1279 xsw = xg - speed(i-1,j-1)*cos_thetadt
1280 ysw = yg - speed(i-1,j-1)*sin_thetadt
1281 cfl_xsw = (xg-xsw)*idx(i-1,j-1)
1282 cfl_ysw = (yg-ysw)*idy(i-1,j-1)
1284 xg = x(i,j-1); yg = y(i,j-1)
1285 xse = xg - speed(i,j-1)*cos_thetadt
1286 yse = yg - speed(i,j-1)*sin_thetadt
1287 cfl_xse = (xg-xse)*idx(i,j-1)
1288 cfl_yse = (yg-yse)*idy(i,j-1)
1290 cfl_max = max(abs(cfl_xne),abs(cfl_xnw),abs(cfl_xsw), &
1291 abs(cfl_xse),abs(cfl_yne),abs(cfl_ynw), &
1292 abs(cfl_ysw),abs(cfl_yse))
1293 if (cfl_max > 1.0)
then 1294 call mom_error(warning,
"propagate_corner_spread: CFL exceeds 1.", .true.)
1298 if (0.0 <= theta .and. theta < 0.25*twopi)
then 1301 elseif (0.25*twopi <= theta .and. theta < 0.5*twopi)
then 1304 elseif (0.5*twopi <= theta .and. theta < 0.75*twopi)
then 1307 elseif (0.75*twopi <= theta .and. theta <= 1.00*twopi)
then 1315 slopen = (yne - ynw)/(xne - xnw)
1316 bn = -slopen*xne + yne
1319 if (xnw == xsw)
then 1322 slopew = (ynw - ysw)/(xnw - xsw)
1323 bw = -slopew*xnw + ynw
1324 xw = (yw - bw)/slopew
1327 slopes = (ysw - yse)/(xsw - xse)
1328 bs = -slopes*xsw + ysw
1331 if (xne == xse)
then 1334 slopee = (yse - yne)/(xse - xne)
1335 be = -slopee*xse + yse
1336 xe = (ye - be)/slopee
1340 ane = 0.0; an = 0.0; anw = 0.0;
1341 aw = 0.0; asw = 0.0; as = 0.0;
1342 ase = 0.0; ae = 0.0; ac = 0.0;
1343 if (0.0 <= theta .and. theta < 0.25*twopi)
then 1344 xcrn = x(i-1,j-1); ycrn = y(i-1,j-1);
1346 a1 = (yn - ycrn)*(0.5*(xn + xcrn))
1347 a2 = (ycrn - yw)*(0.5*(xcrn + xw))
1348 a3 = (yw - ynw)*(0.5*(xw + xnw))
1349 a4 = (ynw - yn)*(0.5*(xnw + xn))
1350 aw = a1 + a2 + a3 + a4
1352 a1 = (ycrn - ys)*(0.5*(xcrn + xs))
1353 a2 = (ys - ysw)*(0.5*(xs + xsw))
1354 a3 = (ysw - yw)*(0.5*(xsw + xw))
1355 a4 = (yw - ycrn)*(0.5*(xw + xcrn))
1356 asw = a1 + a2 + a3 + a4
1358 a1 = (ye - yse)*(0.5*(xe + xse))
1359 a2 = (yse - ys)*(0.5*(xse + xs))
1360 a3 = (ys - ycrn)*(0.5*(xs + xcrn))
1361 a4 = (ycrn - ye)*(0.5*(xcrn + xe))
1362 as = a1 + a2 + a3 + a4
1364 a1 = (yne - ye)*(0.5*(xne + xe))
1365 a2 = (ye - ycrn)*(0.5*(xe + xcrn))
1366 a3 = (ycrn - yn)*(0.5*(xcrn + xn))
1367 a4 = (yn - yne)*(0.5*(xn + xne))
1368 ac = a1 + a2 + a3 + a4
1369 elseif (0.25*twopi <= theta .and. theta < 0.5*twopi)
then 1370 xcrn = x(i,j-1); ycrn = y(i,j-1);
1372 a1 = (ycrn - ys)*(0.5*(xcrn + xs))
1373 a2 = (ys - ysw)*(0.5*(xs + xsw))
1374 a3 = (ysw - yw)*(0.5*(xsw + xw))
1375 a4 = (yw - ycrn)*(0.5*(xw + xcrn))
1376 as = a1 + a2 + a3 + a4
1378 a1 = (ye - yse)*(0.5*(xe + xse))
1379 a2 = (yse - ys)*(0.5*(xse + xs))
1380 a3 = (ys - ycrn)*(0.5*(xs + xcrn))
1381 a4 = (ycrn - ye)*(0.5*(xcrn + xe))
1382 ase = a1 + a2 + a3 + a4
1384 a1 = (yne - ye)*(0.5*(xne + xe))
1385 a2 = (ye - ycrn)*(0.5*(xe + xcrn))
1386 a3 = (ycrn - yn)*(0.5*(xcrn + xn))
1387 a4 = (yn - yne)*(0.5*(xn + xne))
1388 ae = a1 + a2 + a3 + a4
1390 a1 = (yn - ycrn)*(0.5*(xn + xcrn))
1391 a2 = (ycrn - yw)*(0.5*(xcrn + xw))
1392 a3 = (yw - ynw)*(0.5*(xw + xnw))
1393 a4 = (ynw - yn)*(0.5*(xnw + xn))
1394 ac = a1 + a2 + a3 + a4
1395 elseif (0.5*twopi <= theta .and. theta < 0.75*twopi)
then 1396 xcrn = x(i,j); ycrn = y(i,j);
1398 a1 = (ye - yse)*(0.5*(xe + xse))
1399 a2 = (yse - ys)*(0.5*(xse + xs))
1400 a3 = (ys - ycrn)*(0.5*(xs + xcrn))
1401 a4 = (ycrn - ye)*(0.5*(xcrn + xe))
1402 ae = a1 + a2 + a3 + a4
1404 a1 = (yne - ye)*(0.5*(xne + xe))
1405 a2 = (ye - ycrn)*(0.5*(xe + xcrn))
1406 a3 = (ycrn - yn)*(0.5*(xcrn + xn))
1407 a4 = (yn - yne)*(0.5*(xn + xne))
1408 ane = a1 + a2 + a3 + a4
1410 a1 = (yn - ycrn)*(0.5*(xn + xcrn))
1411 a2 = (ycrn - yw)*(0.5*(xcrn + xw))
1412 a3 = (yw - ynw)*(0.5*(xw + xnw))
1413 a4 = (ynw - yn)*(0.5*(xnw + xn))
1414 an = a1 + a2 + a3 + a4
1416 a1 = (ycrn - ys)*(0.5*(xcrn + xs))
1417 a2 = (ys - ysw)*(0.5*(xs + xsw))
1418 a3 = (ysw - yw)*(0.5*(xsw + xw))
1419 a4 = (yw - ycrn)*(0.5*(xw + xcrn))
1420 ac = a1 + a2 + a3 + a4
1421 elseif (0.75*twopi <= theta .and. theta <= 1.00*twopi)
then 1422 xcrn = x(i-1,j); ycrn = y(i-1,j);
1424 a1 = (yne - ye)*(0.5*(xne + xe))
1425 a2 = (ye - ycrn)*(0.5*(xe + xcrn))
1426 a3 = (ycrn - yn)*(0.5*(xcrn + xn))
1427 a4 = (yn - yne)*(0.5*(xn + xne))
1428 an = a1 + a2 + a3 + a4
1430 a1 = (yn - ycrn)*(0.5*(xn + xcrn))
1431 a2 = (ycrn - yw)*(0.5*(xcrn + xw))
1432 a3 = (yw - ynw)*(0.5*(xw + xnw))
1433 a4 = (ynw - yn)*(0.5*(xnw + xn))
1434 anw = a1 + a2 + a3 + a4;
1436 a1 = (ycrn - ys)*(0.5*(xcrn + xs))
1437 a2 = (ys - ysw)*(0.5*(xs + xsw))
1438 a3 = (ysw - yw)*(0.5*(xsw + xw))
1439 a4 = (yw - ycrn)*(0.5*(xw + xcrn))
1440 aw = a1 + a2 + a3 + a4
1442 a1 = (ye - yse)*(0.5*(xe + xse))
1443 a2 = (yse - ys)*(0.5*(xse + xs))
1444 a3 = (ys - ycrn)*(0.5*(xs + xcrn))
1445 a4 = (ycrn - ye)*(0.5*(xcrn + xe))
1446 ac = a1 + a2 + a3 + a4
1450 a_total = ane + an + anw + aw + asw + as + ase + ae + ac
1451 e_new(m) = (ane*en(i+1,j+1) + an*en(i,j+1) + anw*en(i-1,j+1) + &
1452 aw*en(i-1,j) + asw*en(i-1,j-1) + as*en(i,j-1) + &
1453 ase*en(i+1,j-1) + ae*en(i+1,j) + ac*en(i,j)) / (dx(i,j)*dy(i,j))
1456 en(i,j) = sum(e_new)/nsubrays
1461 subroutine propagate_x(En, speed_x, Cgx_av, dCgx, dt, G, Nangle, CS, LB)
1462 type(ocean_grid_type),
intent(in) :: G
1463 integer,
intent(in) :: NAngle
1464 real,
dimension(G%isd:G%ied,G%jsd:G%jed,Nangle), &
1467 real,
dimension(G%IsdB:G%IedB,G%jsd:G%jed), &
1468 intent(in) :: speed_x
1470 real,
dimension(Nangle),
intent(in) :: Cgx_av, dCgx
1471 real,
intent(in) :: dt
1485 real,
dimension(SZI_(G),SZJ_(G)) :: &
1487 real,
dimension(SZIB_(G),SZJ_(G)) :: &
1489 real,
dimension(SZIB_(G)) :: &
1490 cg_p, cg_m, flux1, flux2
1492 real,
dimension(SZI_(G),SZJB_(G),Nangle) :: &
1494 integer :: i, j, k, ish, ieh, jsh, jeh, a
1496 ish = lb%ish ; ieh = lb%ieh ; jsh = lb%jsh ; jeh = lb%jeh
1499 if (cs%upwind_1st)
then 1500 do j=jsh,jeh ;
do i=ish-1,ieh+1
1501 enl(i,j) = en(i,j,a) ; enr(i,j) = en(i,j,a)
1510 cg_p(i) = speed_x(i,j) * (cgx_av(a))
1512 call zonal_flux_en(cg_p, en(:,j,a), enl(:,j), enr(:,j), flux1, &
1513 dt, g, j, ish, ieh, cs%vol_CFL)
1514 do i=ish-1,ieh ; flux_x(i,j) = flux1(i);
enddo 1517 do j=jsh,jeh ;
do i=ish,ieh
1518 fdt_m(i,j,a) = dt*flux_x(i-1,j)
1519 fdt_p(i,j,a) = -dt*flux_x(i,j)
1532 call reflect(fdt_m(:,:,:), nangle, cs, g, lb)
1533 call teleport(fdt_m(:,:,:), nangle, cs, g, lb)
1534 call reflect(fdt_p(:,:,:), nangle, cs, g, lb)
1535 call teleport(fdt_p(:,:,:), nangle, cs, g, lb)
1538 do j=jsh,jeh ;
do i=ish,ieh
1544 en(i,j,:) = en(i,j,:) + g%IareaT(i,j)*(fdt_m(i,j,:) + fdt_p(i,j,:))
1550 subroutine propagate_y(En, speed_y, Cgy_av, dCgy, dt, G, Nangle, CS, LB)
1551 type(ocean_grid_type),
intent(in) :: G
1552 integer,
intent(in) :: NAngle
1553 real,
dimension(G%isd:G%ied,G%jsd:G%jed,Nangle), &
1556 real,
dimension(G%isd:G%ied,G%JsdB:G%JedB), &
1557 intent(in) :: speed_y
1559 real,
dimension(Nangle),
intent(in) :: Cgy_av, dCgy
1560 real,
intent(in) :: dt
1574 real,
dimension(SZI_(G),SZJ_(G)) :: &
1576 real,
dimension(SZI_(G),SZJB_(G)) :: &
1578 real,
dimension(SZI_(G)) :: &
1579 cg_p, cg_m, flux1, flux2
1581 real,
dimension(SZI_(G),SZJB_(G),Nangle) :: &
1583 integer :: i, j, k, ish, ieh, jsh, jeh, a
1585 ish = lb%ish ; ieh = lb%ieh ; jsh = lb%jsh ; jeh = lb%jeh
1588 if (cs%upwind_1st)
then 1589 do j=jsh-1,jeh+1 ;
do i=ish,ieh
1590 enl(i,j) = en(i,j,a) ; enr(i,j) = en(i,j,a)
1599 cg_p(i) = speed_y(i,j) * (cgy_av(a))
1601 call merid_flux_en(cg_p, en(:,:,a), enl(:,:), enr(:,:), flux1, &
1602 dt, g, j, ish, ieh, cs%vol_CFL)
1603 do i=ish,ieh ; flux_y(i,j) = flux1(i);
enddo 1606 do j=jsh,jeh ;
do i=ish,ieh
1607 fdt_m(i,j,a) = dt*flux_y(i,j-1)
1608 fdt_p(i,j,a) = -dt*flux_y(i,j)
1629 call reflect(fdt_m(:,:,:), nangle, cs, g, lb)
1630 call teleport(fdt_m(:,:,:), nangle, cs, g, lb)
1631 call reflect(fdt_p(:,:,:), nangle, cs, g, lb)
1632 call teleport(fdt_p(:,:,:), nangle, cs, g, lb)
1635 do j=jsh,jeh ;
do i=ish,ieh
1641 en(i,j,:) = en(i,j,:) + g%IareaT(i,j)*(fdt_m(i,j,:) + fdt_p(i,j,:))
1647 subroutine zonal_flux_en(u, h, hL, hR, uh, dt, G, j, ish, ieh, vol_CFL)
1648 type(ocean_grid_type),
intent(in) :: G
1649 real,
dimension(SZIB_(G)),
intent(in) :: u
1650 real,
dimension(SZI_(G)),
intent(in) :: h
1652 real,
dimension(SZI_(G)),
intent(in) :: hL
1654 real,
dimension(SZI_(G)),
intent(in) :: hR
1656 real,
dimension(SZIB_(G)),
intent(inout) :: uh
1658 real,
intent(in) :: dt
1659 integer,
intent(in) :: j, ish, ieh
1660 logical,
intent(in) :: vol_CFL
1681 if (u(i) > 0.0)
then 1682 if (vol_cfl)
then ; cfl = (u(i) * dt) * (g%dy_Cu(i,j) * g%IareaT(i,j))
1683 else ; cfl = u(i) * dt * g%IdxT(i,j) ;
endif 1684 curv_3 = (hl(i) + hr(i)) - 2.0*h(i)
1685 uh(i) = g%dy_Cu(i,j) * u(i) * &
1686 (hr(i) + cfl * (0.5*(hl(i) - hr(i)) + curv_3*(cfl - 1.5)))
1687 elseif (u(i) < 0.0)
then 1688 if (vol_cfl)
then ; cfl = (-u(i) * dt) * (g%dy_Cu(i,j) * g%IareaT(i+1,j))
1689 else ; cfl = -u(i) * dt * g%IdxT(i+1,j) ;
endif 1690 curv_3 = (hl(i+1) + hr(i+1)) - 2.0*h(i+1)
1691 uh(i) = g%dy_Cu(i,j) * u(i) * &
1692 (hl(i+1) + cfl * (0.5*(hr(i+1)-hl(i+1)) + curv_3*(cfl - 1.5)))
1700 subroutine merid_flux_en(v, h, hL, hR, vh, dt, G, J, ish, ieh, vol_CFL)
1701 type(ocean_grid_type),
intent(in) :: G
1702 real,
dimension(SZI_(G)),
intent(in) :: v
1703 real,
dimension(SZI_(G),SZJ_(G)),
intent(in) :: h
1705 real,
dimension(SZI_(G),SZJ_(G)),
intent(in) :: hL
1707 real,
dimension(SZI_(G),SZJ_(G)),
intent(in) :: hR
1709 real,
dimension(SZI_(G)),
intent(inout) :: vh
1711 real,
intent(in) :: dt
1712 integer,
intent(in) :: J, ish, ieh
1713 logical,
intent(in) :: vol_CFL
1733 if (v(i) > 0.0)
then 1734 if (vol_cfl)
then ; cfl = (v(i) * dt) * (g%dx_Cv(i,j) * g%IareaT(i,j))
1735 else ; cfl = v(i) * dt * g%IdyT(i,j) ;
endif 1736 curv_3 = hl(i,j) + hr(i,j) - 2.0*h(i,j)
1737 vh(i) = g%dx_Cv(i,j) * v(i) * ( hr(i,j) + cfl * &
1738 (0.5*(hl(i,j) - hr(i,j)) + curv_3*(cfl - 1.5)) )
1739 elseif (v(i) < 0.0)
then 1740 if (vol_cfl)
then ; cfl = (-v(i) * dt) * (g%dx_Cv(i,j) * g%IareaT(i,j+1))
1741 else ; cfl = -v(i) * dt * g%IdyT(i,j+1) ;
endif 1742 curv_3 = hl(i,j+1) + hr(i,j+1) - 2.0*h(i,j+1)
1743 vh(i) = g%dx_Cv(i,j) * v(i) * ( hl(i,j+1) + cfl * &
1744 (0.5*(hr(i,j+1)-hl(i,j+1)) + curv_3*(cfl - 1.5)) )
1752 subroutine reflect(En, NAngle, CS, G, LB)
1753 type(ocean_grid_type),
intent(in) :: G
1754 integer,
intent(in) :: NAngle
1755 real,
dimension(G%isd:G%ied,G%jsd:G%jed,NAngle), &
1762 real,
dimension(G%isd:G%ied,G%jsd:G%jed) :: angle_c
1764 real,
dimension(G%isd:G%ied,G%jsd:G%jed) :: part_refl
1767 logical,
dimension(G%isd:G%ied,G%jsd:G%jed) :: ridge
1773 real,
dimension(1:NAngle) :: angle_i
1775 real,
dimension(1:Nangle) :: En_reflected
1776 integer :: i, j, a, a_r, na
1779 integer :: isc, iec, jsc, jec
1781 integer :: ish, ieh, jsh, jeh
1783 integer :: id_g, jd_g
1786 isc = g%isc ; iec = g%iec ; jsc = g%jsc ; jec = g%jec
1787 ish = lb%ish ; ieh = lb%ieh ; jsh = lb%jsh ; jeh = lb%jeh
1789 twopi = 8.0*atan(1.0);
1790 angle_size = twopi / (
real(nangle))
1795 angle_i(a) = angle_size *
real(a - 1) 1798 angle_c = cs%refl_angle
1799 part_refl = cs%refl_pref
1801 en_reflected(:) = 0.0
1805 jd_g = j + g%jdg_offset
1808 id_g = i + g%idg_offset
1811 if (angle_c(i,j) .ne. cs%nullangle)
then 1813 if (en(i,j,a) > 0.0)
then 1815 if (sin(angle_i(a) - angle_c(i,j)) >= 0.0)
then 1816 angle_wall = angle_c(i,j)
1818 elseif (ridge(i,j))
then 1819 angle_wall = angle_c(i,j) + 0.5*twopi
1820 if (angle_wall > twopi)
then 1821 angle_wall = angle_wall - twopi*floor(abs(angle_wall)/twopi)
1822 elseif (angle_wall < 0.0)
then 1823 angle_wall = angle_wall + twopi*ceiling(abs(angle_wall)/twopi)
1827 angle_wall = angle_c(i,j)
1830 if (sin(angle_i(a) - angle_wall) >= 0.0)
then 1831 angle_r = 2.0*angle_wall - angle_i(a)
1832 if (angle_r > twopi)
then 1833 angle_r = angle_r - twopi*floor(abs(angle_r)/twopi)
1834 elseif (angle_r < 0.0)
then 1835 angle_r = angle_r + twopi*ceiling(abs(angle_r)/twopi)
1837 a_r = nint(angle_r/angle_size) + 1
1838 do while (a_r > nangle) ; a_r = a_r - nangle ;
enddo 1839 if (a .ne. a_r)
then 1840 en_reflected(a_r) = part_refl(i,j)*en(i,j,a)
1841 en(i,j,a) = (1.0-part_refl(i,j))*en(i,j,a)
1846 en(i,j,:) = en(i,j,:) + en_reflected(:)
1847 en_reflected(:) = 0.0
1870 subroutine teleport(En, NAngle, CS, G, LB)
1871 type(ocean_grid_type),
intent(in) :: G
1872 integer,
intent(in) :: NAngle
1873 real,
dimension(G%isd:G%ied,G%jsd:G%jed,NAngle), &
1881 real,
dimension(G%isd:G%ied,G%jsd:G%jed) :: angle_c
1883 real,
dimension(G%isd:G%ied,G%jsd:G%jed) :: part_refl
1886 logical,
dimension(G%isd:G%ied,G%jsd:G%jed) :: pref_cell
1888 logical,
dimension(G%isd:G%ied,G%jsd:G%jed) :: ridge
1892 real,
dimension(1:NAngle) :: angle_i
1893 real,
dimension(1:NAngle) :: cos_angle, sin_angle
1900 integer :: ish, ieh, jsh, jeh
1902 integer :: id_g, jd_g
1904 real :: cos_normal, sin_normal, angle_wall
1909 ish = lb%ish ; ieh = lb%ieh ; jsh = lb%jsh ; jeh = lb%jeh
1911 twopi = 8.0*atan(1.0)
1912 angle_size = twopi / (
real(nangle))
1917 angle_i(a) = angle_size *
real(a - 1) 1918 cos_angle(a) = cos(angle_i(a)) ; sin_angle(a) = sin(angle_i(a))
1921 angle_c = cs%refl_angle
1922 part_refl = cs%refl_pref
1923 pref_cell = cs%refl_pref_logical
1928 id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset
1929 if (pref_cell(i,j))
then 1931 if (en(i,j,a) > 0)
then 1933 if (sin(angle_i(a) - angle_c(i,j)) >= 0.0)
then 1934 angle_wall = angle_c(i,j)
1936 elseif (ridge(i,j))
then 1937 angle_wall = angle_c(i,j) + 0.5*twopi
1940 angle_wall = angle_c(i,j)
1943 if (sin(angle_i(a) - angle_wall) >= 0.0)
then 1945 cos_normal = cos(angle_wall + 0.25*twopi)
1946 sin_normal = sin(angle_wall + 0.25*twopi)
1948 ios = int(sign(1.,cos_normal))
1950 jos = int(sign(1.,sin_normal))
1952 if (.not. pref_cell(i+ios,j+jos))
then 1953 en(i,j,a) = en(i,j,a) - en_tele
1954 en(i+ios,j+jos,a) = en(i+ios,j+jos,a) + en_tele
1956 call mom_error(warning,
"teleport: no receptive ocean cell", .true.)
1957 print *,
'idg=',id_g,
'jd_g=',jd_g,
'a=',a
1972 type(ocean_grid_type),
intent(in) :: G
1973 real,
dimension(:,:,:,:,:),
intent(inout) :: En
1974 real,
dimension(SZI_(G),SZJ_(G),2),
intent(in) :: test
1975 integer,
intent(in) :: NAngle
1979 real,
dimension(G%isd:G%ied,NAngle) :: En2d
1980 integer,
dimension(G%isd:G%ied) :: a_shift
1981 integer :: i_first, i_last, a_new
1982 integer :: a, i, j, isd, ied, jsd, jed, m, fr
1983 character(len=80) :: mesg
1984 isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
1987 i_first = ied+1 ; i_last = isd-1
1990 if (test(i,j,1) /= 1.0)
then 1991 if (i<i_first) i_first = i
1992 if (i>i_last) i_last = i
1994 if (test(i,j,1) == -1.0)
then ; a_shift(i) = nangle/2
1995 elseif (test(i,j,2) == 1.0)
then ; a_shift(i) = -nangle/4
1996 elseif (test(i,j,2) == -1.0)
then ; a_shift(i) = nangle/4
1998 write(mesg,
'("Unrecognized rotation test vector ",2ES9.2," at ",F7.2," E, ",& 1999 &F7.2," N; i,j=",2i4)') &
2000 test(i,j,1), test(i,j,2), g%GeoLonT(i,j), g%GeoLatT(i,j), i, j
2001 call mom_error(fatal, mesg)
2006 if (i_first <= i_last)
then 2008 do m=1,
size(en,5) ;
do fr=1,
size(en,4)
2009 do a=1,nangle ;
do i=i_first,i_last ;
if (a_shift(i) /= 0)
then 2010 a_new = a + a_shift(i)
2011 if (a_new < 1) a_new = a_new + nangle
2012 if (a_new > nangle) a_new = a_new - nangle
2013 en2d(i,a_new) = en(i,j,a,fr,m)
2014 endif ;
enddo ;
enddo 2015 do a=1,nangle ;
do i=i_first,i_last ;
if (a_shift(i) /= 0)
then 2016 en(i,j,a,fr,m) = en2d(i,a)
2017 endif ;
enddo ;
enddo 2025 type(ocean_grid_type),
intent(in) :: G
2026 real,
dimension(SZI_(G),SZJ_(G)),
intent(in) :: h_in
2027 real,
dimension(SZI_(G),SZJ_(G)),
intent(out) :: h_l
2028 real,
dimension(SZI_(G),SZJ_(G)),
intent(out) :: h_r
2030 logical,
optional,
intent(in) :: simple_2nd
2043 real,
dimension(SZI_(G),SZJ_(G)) :: slp
2044 real,
parameter :: oneSixth = 1./6.
2045 real :: h_ip1, h_im1
2047 logical :: use_CW84, use_2nd
2048 character(len=256) :: mesg
2049 integer :: i, j, isl, iel, jsl, jel, stencil
2051 use_2nd = .false. ;
if (
present(simple_2nd)) use_2nd = simple_2nd
2052 isl = lb%ish-1 ; iel = lb%ieh+1 ; jsl = lb%jsh ; jel = lb%jeh
2055 stencil = 2 ;
if (use_2nd) stencil = 1
2057 if ((isl-stencil < g%isd) .or. (iel+stencil > g%ied))
then 2058 write(mesg,
'("In MOM_internal_tides, PPM_reconstruction_x called with a ", & 2059 & "x-halo that needs to be increased by ",i2,".")') &
2060 stencil + max(g%isd-isl,iel-g%ied)
2061 call mom_error(fatal,mesg)
2063 if ((jsl < g%jsd) .or. (jel > g%jed))
then 2064 write(mesg,
'("In MOM_internal_tides, PPM_reconstruction_x called with a ", & 2065 & "y-halo that needs to be increased by ",i2,".")') &
2066 max(g%jsd-jsl,jel-g%jed)
2067 call mom_error(fatal,mesg)
2071 do j=jsl,jel ;
do i=isl,iel
2072 h_im1 = g%mask2dT(i-1,j) * h_in(i-1,j) + (1.0-g%mask2dT(i-1,j)) * h_in(i,j)
2073 h_ip1 = g%mask2dT(i+1,j) * h_in(i+1,j) + (1.0-g%mask2dT(i+1,j)) * h_in(i,j)
2074 h_l(i,j) = 0.5*( h_im1 + h_in(i,j) )
2075 h_r(i,j) = 0.5*( h_ip1 + h_in(i,j) )
2078 do j=jsl,jel ;
do i=isl-1,iel+1
2079 if ((g%mask2dT(i-1,j) * g%mask2dT(i,j) * g%mask2dT(i+1,j)) == 0.0)
then 2083 slp(i,j) = 0.5 * (h_in(i+1,j) - h_in(i-1,j))
2085 dmx = max(h_in(i+1,j), h_in(i-1,j), h_in(i,j)) - h_in(i,j)
2086 dmn = h_in(i,j) - min(h_in(i+1,j), h_in(i-1,j), h_in(i,j))
2087 slp(i,j) = sign(1.,slp(i,j)) * min(abs(slp(i,j)), 2. * min(dmx, dmn))
2092 do j=jsl,jel ;
do i=isl,iel
2097 h_im1 = g%mask2dT(i-1,j) * h_in(i-1,j) + (1.0-g%mask2dT(i-1,j)) * h_in(i,j)
2098 h_ip1 = g%mask2dT(i+1,j) * h_in(i+1,j) + (1.0-g%mask2dT(i+1,j)) * h_in(i,j)
2100 h_l(i,j) = 0.5*( h_im1 + h_in(i,j) ) + onesixth*( slp(i-1,j) - slp(i,j) )
2101 h_r(i,j) = 0.5*( h_ip1 + h_in(i,j) ) + onesixth*( slp(i,j) - slp(i+1,j) )
2105 call ppm_limit_pos(h_in, h_l, h_r, 0.0, g, isl, iel, jsl, jel)
2110 type(ocean_grid_type),
intent(in) :: G
2111 real,
dimension(SZI_(G),SZJ_(G)),
intent(in) :: h_in
2112 real,
dimension(SZI_(G),SZJ_(G)),
intent(out) :: h_l
2113 real,
dimension(SZI_(G),SZJ_(G)),
intent(out) :: h_r
2115 logical,
optional,
intent(in) :: simple_2nd
2128 real,
dimension(SZI_(G),SZJ_(G)) :: slp
2129 real,
parameter :: oneSixth = 1./6.
2130 real :: h_jp1, h_jm1
2133 character(len=256) :: mesg
2134 integer :: i, j, isl, iel, jsl, jel, stencil
2136 use_2nd = .false. ;
if (
present(simple_2nd)) use_2nd = simple_2nd
2137 isl = lb%ish ; iel = lb%ieh ; jsl = lb%jsh-1 ; jel = lb%jeh+1
2140 stencil = 2 ;
if (use_2nd) stencil = 1
2142 if ((isl < g%isd) .or. (iel > g%ied))
then 2143 write(mesg,
'("In MOM_internal_tides, PPM_reconstruction_y called with a ", & 2144 & "x-halo that needs to be increased by ",i2,".")') &
2145 max(g%isd-isl,iel-g%ied)
2146 call mom_error(fatal,mesg)
2148 if ((jsl-stencil < g%jsd) .or. (jel+stencil > g%jed))
then 2149 write(mesg,
'("In MOM_internal_tides, PPM_reconstruction_y called with a ", & 2150 & "y-halo that needs to be increased by ",i2,".")') &
2151 stencil + max(g%jsd-jsl,jel-g%jed)
2152 call mom_error(fatal,mesg)
2156 do j=jsl,jel ;
do i=isl,iel
2157 h_jm1 = g%mask2dT(i,j-1) * h_in(i,j-1) + (1.0-g%mask2dT(i,j-1)) * h_in(i,j)
2158 h_jp1 = g%mask2dT(i,j+1) * h_in(i,j+1) + (1.0-g%mask2dT(i,j+1)) * h_in(i,j)
2159 h_l(i,j) = 0.5*( h_jm1 + h_in(i,j) )
2160 h_r(i,j) = 0.5*( h_jp1 + h_in(i,j) )
2163 do j=jsl-1,jel+1 ;
do i=isl,iel
2164 if ((g%mask2dT(i,j-1) * g%mask2dT(i,j) * g%mask2dT(i,j+1)) == 0.0)
then 2168 slp(i,j) = 0.5 * (h_in(i,j+1) - h_in(i,j-1))
2170 dmx = max(h_in(i,j+1), h_in(i,j-1), h_in(i,j)) - h_in(i,j)
2171 dmn = h_in(i,j) - min(h_in(i,j+1), h_in(i,j-1), h_in(i,j))
2172 slp(i,j) = sign(1.,slp(i,j)) * min(abs(slp(i,j)), 2. * min(dmx, dmn))
2177 do j=jsl,jel ;
do i=isl,iel
2180 h_jm1 = g%mask2dT(i,j-1) * h_in(i,j-1) + (1.0-g%mask2dT(i,j-1)) * h_in(i,j)
2181 h_jp1 = g%mask2dT(i,j+1) * h_in(i,j+1) + (1.0-g%mask2dT(i,j+1)) * h_in(i,j)
2183 h_l(i,j) = 0.5*( h_jm1 + h_in(i,j) ) + onesixth*( slp(i,j-1) - slp(i,j) )
2184 h_r(i,j) = 0.5*( h_jp1 + h_in(i,j) ) + onesixth*( slp(i,j) - slp(i,j+1) )
2188 call ppm_limit_pos(h_in, h_l, h_r, 0.0, g, isl, iel, jsl, jel)
2195 subroutine ppm_limit_pos(h_in, h_L, h_R, h_min, G, iis, iie, jis, jie)
2196 type(ocean_grid_type),
intent(in) :: G
2197 real,
dimension(SZI_(G),SZJ_(G)),
intent(in) :: h_in
2198 real,
dimension(SZI_(G),SZJ_(G)),
intent(inout) :: h_L
2199 real,
dimension(SZI_(G),SZJ_(G)),
intent(inout) :: h_R
2200 real,
intent(in) :: h_min
2202 integer,
intent(in) :: iis, iie, jis, jie
2218 real :: curv, dh, scale
2219 character(len=256) :: mesg
2222 do j=jis,jie ;
do i=iis,iie
2225 curv = 3.0*(h_l(i,j) + h_r(i,j) - 2.0*h_in(i,j))
2226 if (curv > 0.0)
then 2227 dh = h_r(i,j) - h_l(i,j)
2228 if (abs(dh) < curv)
then 2229 if (h_in(i,j) <= h_min)
then 2230 h_l(i,j) = h_in(i,j) ; h_r(i,j) = h_in(i,j)
2231 elseif (12.0*curv*(h_in(i,j) - h_min) < (curv**2 + 3.0*dh**2))
then 2234 scale = 12.0*curv*(h_in(i,j) - h_min) / (curv**2 + 3.0*dh**2)
2235 h_l(i,j) = h_in(i,j) + scale*(h_l(i,j) - h_in(i,j))
2236 h_r(i,j) = h_in(i,j) + scale*(h_r(i,j) - h_in(i,j))
2300 type(time_type),
target,
intent(in) :: Time
2301 type(ocean_grid_type),
intent(inout) :: G
2302 type(verticalgrid_type),
intent(in) :: GV
2303 type(param_file_type),
intent(in) :: param_file
2305 type(diag_ctrl),
target,
intent(in) :: diag
2319 real,
allocatable :: angles(:)
2320 real,
allocatable,
dimension(:,:) :: h2
2321 real :: kappa_itides, kappa_h2_factor
2324 real,
allocatable :: ridge_temp(:,:)
2327 logical :: use_int_tides, use_temperature
2328 integer :: num_angle, num_freq, num_mode, m, fr, period_1
2329 integer :: isd, ied, jsd, jed, a, id_ang, i, j
2330 type(axes_grp) :: axes_ang
2332 #include "version_variable.h" 2333 character(len=40) :: mdl =
"MOM_internal_tides" 2334 character(len=16),
dimension(8) :: freq_name
2335 character(len=40) :: var_name
2336 character(len=160) :: var_descript
2337 character(len=200) :: filename
2338 character(len=200) :: refl_angle_file, land_mask_file
2339 character(len=200) :: refl_pref_file, refl_dbl_file
2340 character(len=200) :: dy_Cu_file, dx_Cv_file
2341 character(len=200) :: h2_file
2343 isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
2345 if (
associated(cs))
then 2346 call mom_error(warning,
"internal_tides_init called "//&
2347 "with an associated control structure.")
2353 use_int_tides = .false.
2354 call read_param(param_file,
"INTERNAL_TIDES", use_int_tides)
2355 cs%do_int_tides = use_int_tides
2356 if (.not.use_int_tides)
return 2358 use_temperature = .true.
2359 call read_param(param_file,
"ENABLE_THERMODYNAMICS", use_temperature)
2360 if (.not.use_temperature)
call mom_error(fatal, &
2361 "register_int_tide_restarts: internal_tides only works with "//&
2362 "ENABLE_THERMODYNAMICS defined.")
2365 num_freq = 1 ; num_angle = 24 ; num_mode = 1
2366 call read_param(param_file,
"INTERNAL_TIDE_FREQS", num_freq)
2367 call read_param(param_file,
"INTERNAL_TIDE_ANGLES", num_angle)
2368 call read_param(param_file,
"INTERNAL_TIDE_MODES", num_mode)
2369 if (.not.((num_freq > 0) .and. (num_angle > 0) .and. (num_mode > 0)))
return 2370 cs%nFreq = num_freq ; cs%nAngle = num_angle ; cs%nMode = num_mode
2373 allocate(cs%En(isd:ied, jsd:jed, num_angle, num_freq, num_mode))
2374 cs%En(:,:,:,:,:) = 0.0
2377 allocate(cs%cp(isd:ied, jsd:jed, num_freq, num_mode))
2378 cs%cp(:,:,:,:) = 0.0
2381 allocate(cs%frequency(num_freq))
2382 call read_param(param_file,
"FIRST_MODE_PERIOD", period_1);
2384 cs%frequency(fr) = (8.0*atan(1.0) * (
real(fr)) / period_1)
2391 call get_param(param_file, mdl,
"INPUTDIR", cs%inputdir, default=
".")
2392 cs%inputdir = slasher(cs%inputdir)
2394 call log_version(param_file, mdl, version,
"")
2396 call get_param(param_file, mdl,
"INTERNAL_TIDE_FREQS", num_freq, &
2397 "The number of distinct internal tide frequency bands \n"//&
2398 "that will be calculated.", default=1)
2399 call get_param(param_file, mdl,
"INTERNAL_TIDE_MODES", num_mode, &
2400 "The number of distinct internal tide modes \n"//&
2401 "that will be calculated.", default=1)
2402 call get_param(param_file, mdl,
"INTERNAL_TIDE_ANGLES", num_angle, &
2403 "The number of angular resolution bands for the internal \n"//&
2404 "tide calculations.", default=24)
2406 if (use_int_tides)
then 2407 if ((num_freq <= 0) .and. (num_mode <= 0) .and. (num_angle <= 0))
then 2408 call mom_error(warning,
"Internal tides were enabled, but the number "//&
2409 "of requested frequencies, modes and angles were not all positive.")
2413 if ((num_freq > 0) .and. (num_mode > 0) .and. (num_angle > 0))
then 2414 call mom_error(warning,
"Internal tides were not enabled, even though "//&
2415 "the number of requested frequencies, modes and angles were all "//&
2421 if (cs%NFreq /= num_freq)
call mom_error(fatal,
"Internal_tides_init: "//&
2422 "Inconsistent number of frequencies.")
2423 if (cs%NAngle /= num_angle)
call mom_error(fatal,
"Internal_tides_init: "//&
2424 "Inconsistent number of angles.")
2425 if (cs%NMode /= num_mode)
call mom_error(fatal,
"Internal_tides_init: "//&
2426 "Inconsistent number of modes.")
2427 if (4*(num_angle/4) /= num_angle)
call mom_error(fatal, &
2428 "Internal_tides_init: INTERNAL_TIDE_ANGLES must be a multiple of 4.")
2432 call get_param(param_file, mdl,
"INTERNAL_TIDE_DECAY_RATE", cs%decay_rate, &
2433 "The rate at which internal tide energy is lost to the \n"//&
2434 "interior ocean internal wave field.", units=
"s-1", default=0.0)
2435 call get_param(param_file, mdl,
"INTERNAL_TIDE_VOLUME_BASED_CFL", cs%vol_CFL, &
2436 "If true, use the ratio of the open face lengths to the \n"//&
2437 "tracer cell areas when estimating CFL numbers in the \n"//&
2438 "internal tide code.", default=.false.)
2439 call get_param(param_file, mdl,
"INTERNAL_TIDE_CORNER_ADVECT", cs%corner_adv, &
2440 "If true, internal tide ray-tracing advection uses a \n"//&
2441 " corner-advection scheme rather than PPM.\n", default=.false.)
2442 call get_param(param_file, mdl,
"INTERNAL_TIDE_SIMPLE_2ND_PPM", cs%simple_2nd, &
2443 "If true, CONTINUITY_PPM uses a simple 2nd order \n"//&
2444 "(arithmetic mean) interpolation of the edge values. \n"//&
2445 "This may give better PV conservation propterties. While \n"//&
2446 "it formally reduces the accuracy of the continuity \n"//&
2447 "solver itself in the strongly advective limit, it does \n"//&
2448 "not reduce the overall order of accuracy of the dynamic \n"//&
2449 "core.", default=.false.)
2450 call get_param(param_file, mdl,
"INTERNAL_TIDE_UPWIND_1ST", cs%upwind_1st, &
2451 "If true, the internal tide ray-tracing advection uses \n"//&
2452 "1st-order upwind advection. This scheme is highly \n"//&
2453 "continuity solver. This scheme is highly \n"//&
2454 "diffusive but may be useful for debugging.", default=.false.)
2455 call get_param(param_file, mdl,
"INTERNAL_TIDE_BACKGROUND_DRAG", &
2456 cs%apply_background_drag,
"If true, the internal tide \n"//&
2457 "ray-tracing advection uses a background drag term as a sink.",&
2459 call get_param(param_file, mdl,
"INTERNAL_TIDE_QUAD_DRAG", cs%apply_bottom_drag, &
2460 "If true, the internal tide ray-tracing advection uses \n"//&
2461 "a quadratic bottom drag term as a sink.", default=.false.)
2462 call get_param(param_file, mdl,
"INTERNAL_TIDE_WAVE_DRAG", cs%apply_wave_drag, &
2463 "If true, apply scattering due to small-scale roughness as a sink.", &
2465 call get_param(param_file, mdl,
"INTERNAL_TIDE_FROUDE_DRAG", cs%apply_Froude_drag, &
2466 "If true, apply wave breaking as a sink.", &
2468 call get_param(param_file, mdl,
"CDRAG", cs%cdrag, &
2469 "CDRAG is the drag coefficient relating the magnitude of \n"//&
2470 "the velocity field to the bottom stress.", units=
"nondim", &
2472 call get_param(param_file, mdl,
"INTERNAL_TIDE_ENERGIZED_ANGLE", cs%energized_angle, &
2473 "If positive, only one angular band of the internal tides \n"//&
2474 "gets all of the energy. (This is for debugging.)", default=-1)
2475 call get_param(param_file, mdl,
"USE_PPM_ANGULAR", cs%use_PPMang, &
2476 "If true, use PPM for advection of energy in angular \n"//&
2477 "space.", default=.false.)
2478 call get_param(param_file, mdl,
"GAMMA_ITIDES", cs%q_itides, &
2479 "The fraction of the internal tidal energy that is \n"//&
2480 "dissipated locally with INT_TIDE_DISSIPATION. \n"//&
2481 "THIS NAME COULD BE BETTER.", &
2482 units=
"nondim", default=0.3333)
2483 call get_param(param_file, mdl,
"KAPPA_ITIDES", kappa_itides, &
2484 "A topographic wavenumber used with INT_TIDE_DISSIPATION. \n"//&
2485 "The default is 2pi/10 km, as in St.Laurent et al. 2002.", &
2486 units=
"m-1", default=8.e-4*atan(1.0))
2487 call get_param(param_file, mdl,
"KAPPA_H2_FACTOR", kappa_h2_factor, &
2488 "A scaling factor for the roughness amplitude with n"//&
2489 "INT_TIDE_DISSIPATION.", units=
"nondim", default=1.0)
2492 allocate(h2(isd:ied,jsd:jed)) ; h2(:,:) = 0.0
2493 allocate(cs%TKE_itidal_loss_fixed(isd:ied,jsd:jed))
2494 cs%TKE_itidal_loss_fixed = 0.0
2495 allocate(cs%TKE_leak_loss(isd:ied,jsd:jed,num_angle,num_freq,num_mode))
2496 cs%TKE_leak_loss(:,:,:,:,:) = 0.0
2497 allocate(cs%TKE_quad_loss(isd:ied,jsd:jed,num_angle,num_freq,num_mode))
2498 cs%TKE_quad_loss(:,:,:,:,:) = 0.0
2499 allocate(cs%TKE_itidal_loss(isd:ied,jsd:jed,num_angle,num_freq,num_mode))
2500 cs%TKE_itidal_loss(:,:,:,:,:) = 0.0
2501 allocate(cs%TKE_Froude_loss(isd:ied,jsd:jed,num_angle,num_freq,num_mode))
2502 cs%TKE_Froude_loss(:,:,:,:,:) = 0.0
2503 allocate(cs%tot_leak_loss(isd:ied,jsd:jed)) ; cs%tot_leak_loss(:,:) = 0.0
2504 allocate(cs%tot_quad_loss(isd:ied,jsd:jed) ) ; cs%tot_quad_loss(:,:) = 0.0
2505 allocate(cs%tot_itidal_loss(isd:ied,jsd:jed)) ; cs%tot_itidal_loss(:,:) = 0.0
2506 allocate(cs%tot_Froude_loss(isd:ied,jsd:jed)) ; cs%tot_Froude_loss(:,:) = 0.0
2509 call get_param(param_file, mdl,
"H2_FILE", h2_file, &
2510 "The path to the file containing the sub-grid-scale \n"//&
2511 "topographic roughness amplitude with INT_TIDE_DISSIPATION.", &
2512 fail_if_missing=.true.)
2513 filename = trim(cs%inputdir) // trim(h2_file)
2514 call log_param(param_file, mdl,
"INPUTDIR/H2_FILE", filename)
2515 call read_data(filename,
'h2', h2, domain=g%domain%mpp_domain, timelevel=1)
2516 do j=g%jsc,g%jec ;
do i=g%isc,g%iec
2518 h2(i,j) = min(0.01*g%bathyT(i,j)**2, h2(i,j))
2521 cs%TKE_itidal_loss_fixed(i,j) = 0.5*kappa_h2_factor*gv%Rho0*&
2522 kappa_itides * h2(i,j)
2526 call get_param(param_file, mdl,
"REFL_ANGLE_FILE", refl_angle_file, &
2527 "The path to the file containing the local angle of \n"//&
2528 "the coastline/ridge/shelf with respect to the equator.", &
2529 fail_if_missing=.false.)
2530 filename = trim(cs%inputdir) // trim(refl_angle_file)
2531 call log_param(param_file, mdl,
"INPUTDIR/REFL_ANGLE_FILE", filename)
2532 allocate(cs%refl_angle(isd:ied,jsd:jed)) ; cs%refl_angle(:,:) = cs%nullangle
2533 call read_data(filename,
'refl_angle', cs%refl_angle, &
2534 domain=g%domain%mpp_domain, timelevel=1)
2536 do j=g%jsc,g%jec ;
do i=g%isc,g%iec
2537 if(is_nan(cs%refl_angle(i,j))) cs%refl_angle(i,j) = cs%nullangle
2539 call pass_var(cs%refl_angle,g%domain)
2542 call get_param(param_file, mdl,
"REFL_PREF_FILE", refl_pref_file, &
2543 "The path to the file containing the reflection coefficients.", &
2544 fail_if_missing=.false.)
2545 filename = trim(cs%inputdir) // trim(refl_pref_file)
2546 call log_param(param_file, mdl,
"INPUTDIR/REFL_PREF_FILE", filename)
2547 allocate(cs%refl_pref(isd:ied,jsd:jed)) ; cs%refl_pref(:,:) = 1.0
2548 call read_data(filename,
'refl_pref', cs%refl_pref, &
2549 domain=g%domain%mpp_domain, timelevel=1)
2551 call pass_var(cs%refl_pref,g%domain)
2554 allocate(cs%refl_pref_logical(isd:ied,jsd:jed)) ; cs%refl_pref_logical(:,:) = .false.
2558 if (cs%refl_angle(i,j) .ne. cs%nullangle .and. &
2559 cs%refl_pref(i,j) < 1.0 .and. cs%refl_pref(i,j) > 0.0)
then 2560 cs%refl_pref_logical(i,j) = .true.
2566 call get_param(param_file, mdl,
"REFL_DBL_FILE", refl_dbl_file, &
2567 "The path to the file containing the double-reflective ridge tags.", &
2568 fail_if_missing=.false.)
2569 filename = trim(cs%inputdir) // trim(refl_dbl_file)
2570 call log_param(param_file, mdl,
"INPUTDIR/REFL_DBL_FILE", filename)
2571 allocate(ridge_temp(isd:ied,jsd:jed)) ; ridge_temp(:,:) = 0.0
2572 call read_data(filename,
'refl_dbl', ridge_temp, &
2573 domain=g%domain%mpp_domain, timelevel=1)
2574 call pass_var(ridge_temp,g%domain)
2575 allocate(cs%refl_dbl(isd:ied,jsd:jed)) ; cs%refl_dbl(:,:) = .false.
2576 do i=isd,ied;
do j=jsd,jed
2577 if (ridge_temp(i,j) == 1) then; cs%refl_dbl(i,j) = .true.
2578 else ; cs%refl_dbl(i,j) = .false. ;
endif 2623 call get_param(param_file, mdl,
"INTERNAL_TIDE_SOURCE_X", cs%int_tide_source_x, &
2624 "X Location of generation site for internal tide", default=1.)
2625 call get_param(param_file, mdl,
"INTERNAL_TIDE_SOURCE_Y", cs%int_tide_source_y, &
2626 "Y Location of generation site for internal tide", default=1.)
2629 cs%id_refl_ang = register_diag_field(
'ocean_model',
'refl_angle', diag%axesT1, &
2630 time,
'Local angle of coastline/ridge/shelf with respect to equator',
'rad')
2631 cs%id_refl_pref = register_diag_field(
'ocean_model',
'refl_pref', diag%axesT1, &
2632 time,
'Partial reflection coefficients',
'')
2633 cs%id_dx_Cv = register_diag_field(
'ocean_model',
'dx_Cv', diag%axesT1, &
2634 time,
'North face unblocked width',
'm')
2635 cs%id_dy_Cu = register_diag_field(
'ocean_model',
'dy_Cu', diag%axesT1, &
2636 time,
'East face unblocked width',
'm')
2637 cs%id_land_mask = register_diag_field(
'ocean_model',
'land_mask', diag%axesT1, &
2638 time,
'Land mask',
'logical')
2640 if (cs%id_refl_ang > 0)
call post_data(cs%id_refl_ang, cs%refl_angle, cs%diag)
2641 if (cs%id_refl_pref > 0)
call post_data(cs%id_refl_pref, cs%refl_pref, cs%diag)
2642 if (cs%id_dx_Cv > 0)
call post_data(cs%id_dx_Cv, g%dx_Cv, cs%diag)
2643 if (cs%id_dy_Cu > 0)
call post_data(cs%id_dy_Cu, g%dy_Cu, cs%diag)
2644 if (cs%id_land_mask > 0)
call post_data(cs%id_land_mask, g%mask2dT, cs%diag)
2647 cs%id_tot_En = register_diag_field(
'ocean_model',
'ITide_tot_En', diag%axesT1, &
2648 time,
'Internal tide total energy density',
'J m-2')
2650 cs%id_itide_drag = register_diag_field(
'ocean_model',
'ITide_drag', diag%axesT1, &
2651 time,
'Interior and bottom drag internal tide decay timescale',
's-1')
2653 cs%id_TKE_itidal_input = register_diag_field(
'ocean_model',
'TKE_itidal_input', diag%axesT1, &
2654 time,
'Conversion from barotropic to baroclinic tide, \n'//&
2655 'a fraction of which goes into rays',
'W m-2')
2657 cs%id_tot_leak_loss = register_diag_field(
'ocean_model',
'ITide_tot_leak_loss', diag%axesT1, &
2658 time,
'Internal tide energy loss to background drag',
'W m-2')
2659 cs%id_tot_quad_loss = register_diag_field(
'ocean_model',
'ITide_tot_quad_loss', diag%axesT1, &
2660 time,
'Internal tide energy loss to bottom drag',
'W m-2')
2661 cs%id_tot_itidal_loss = register_diag_field(
'ocean_model',
'ITide_tot_itidal_loss', diag%axesT1, &
2662 time,
'Internal tide energy loss to wave drag',
'W m-2')
2663 cs%id_tot_Froude_loss = register_diag_field(
'ocean_model',
'ITide_tot_Froude_loss', diag%axesT1, &
2664 time,
'Internal tide energy loss to wave breaking',
'W m-2')
2665 cs%id_tot_allprocesses_loss = register_diag_field(
'ocean_model',
'ITide_tot_allprocesses_loss', diag%axesT1, &
2666 time,
'Internal tide energy loss summed over all processes',
'W m-2')
2668 allocate(cs%id_En_mode(cs%nFreq,cs%nMode)) ; cs%id_En_mode(:,:) = -1
2669 allocate(cs%id_En_ang_mode(cs%nFreq,cs%nMode)) ; cs%id_En_ang_mode(:,:) = -1
2670 allocate(cs%id_itidal_loss_mode(cs%nFreq,cs%nMode)) ; cs%id_itidal_loss_mode(:,:) = -1
2671 allocate(cs%id_allprocesses_loss_mode(cs%nFreq,cs%nMode)) ; cs%id_allprocesses_loss_mode(:,:) = -1
2672 allocate(cs%id_itidal_loss_ang_mode(cs%nFreq,cs%nMode)) ; cs%id_itidal_loss_ang_mode(:,:) = -1
2673 allocate(cs%id_Ub_mode(cs%nFreq,cs%nMode)) ; cs%id_Ub_mode(:,:) = -1
2674 allocate(cs%id_cp_mode(cs%nFreq,cs%nMode)) ; cs%id_cp_mode(:,:) = -1
2676 allocate(angles(cs%NAngle)) ; angles(:) = 0.0
2677 angle_size = (8.0*atan(1.0)) / (
real(num_angle))
2678 do a=1,num_angle ; angles(a) = (
real(a) - 1) * angle_size ; enddo
2680 id_ang = diag_axis_init(
"angle", angles,
"Radians",
"N",
"Angular Orienation of Fluxes")
2681 call define_axes_group(diag, (/ diag%axesT1%handles(1), diag%axesT1%handles(2), id_ang /), axes_ang)
2683 do fr=1,cs%nFreq ;
write(freq_name(fr),
'("freq",i1)') fr ;
enddo 2684 do m=1,cs%nMode ;
do fr=1,cs%nFreq
2686 write(var_name,
'("Itide_En_freq",i1,"_mode",i1)') fr, m
2687 write(var_descript,
'("Internal tide energy density in frequency ",i1," mode ",i1)') fr, m
2688 cs%id_En_mode(fr,m) = register_diag_field(
'ocean_model', var_name, &
2689 diag%axesT1, time, var_descript,
'J m-2')
2690 call mom_mesg(
"Registering "//trim(var_name)//
", Described as: "//var_descript, 5)
2693 write(var_name,
'("Itide_En_ang_freq",i1,"_mode",i1)') fr, m
2694 write(var_descript,
'("Internal tide angular energy density in frequency ",i1," mode ",i1)') fr, m
2695 cs%id_En_ang_mode(fr,m) = register_diag_field(
'ocean_model', var_name, &
2696 axes_ang, time, var_descript,
'J m-2 band-1')
2697 call mom_mesg(
"Registering "//trim(var_name)//
", Described as: "//var_descript, 5)
2701 write(var_name,
'("Itide_wavedrag_loss_freq",i1,"_mode",i1)') fr, m
2702 write(var_descript,
'("Internal tide energy loss due to wave-drag from frequency ",i1," mode ",i1)') fr, m
2703 cs%id_itidal_loss_mode(fr,m) = register_diag_field(
'ocean_model', var_name, &
2704 diag%axesT1, time, var_descript,
'W m-2')
2705 call mom_mesg(
"Registering "//trim(var_name)//
", Described as: "//var_descript, 5)
2707 write(var_name,
'("Itide_allprocesses_loss_freq",i1,"_mode",i1)') fr, m
2708 write(var_descript,
'("Internal tide energy loss due to all processes from frequency ",i1," mode ",i1)') fr, m
2709 cs%id_allprocesses_loss_mode(fr,m) = register_diag_field(
'ocean_model', var_name, &
2710 diag%axesT1, time, var_descript,
'W m-2')
2711 call mom_mesg(
"Registering "//trim(var_name)//
", Described as: "//var_descript, 5)
2715 write(var_name,
'("Itide_wavedrag_loss_ang_freq",i1,"_mode",i1)') fr, m
2716 write(var_descript,
'("Internal tide energy loss due to wave-drag from frequency ",i1," mode ",i1)') fr, m
2717 cs%id_itidal_loss_ang_mode(fr,m) = register_diag_field(
'ocean_model', var_name, &
2718 axes_ang, time, var_descript,
'W m-2 band-1')
2719 call mom_mesg(
"Registering "//trim(var_name)//
", Described as: "//var_descript, 5)
2722 write(var_name,
'("Itide_Ub_freq",i1,"_mode",i1)') fr, m
2723 write(var_descript,
'("Near-bottom horizonal velocity for frequency ",i1," mode ",i1)') fr, m
2724 cs%id_Ub_mode(fr,m) = register_diag_field(
'ocean_model', var_name, &
2725 diag%axesT1, time, var_descript,
'm s-1')
2726 call mom_mesg(
"Registering "//trim(var_name)//
", Described as: "//var_descript, 5)
2729 write(var_name,
'("Itide_cp_freq",i1,"_mode",i1)') fr, m
2730 write(var_descript,
'("Horizonal phase velocity for frequency ",i1," mode ",i1)') fr, m
2731 cs%id_cp_mode(fr,m) = register_diag_field(
'ocean_model', var_name, &
2732 diag%axesT1, time, var_descript,
'm s-1')
2733 call mom_mesg(
"Registering "//trim(var_name)//
", Described as: "//var_descript, 5)
2738 call wave_structure_init(time, g, param_file, diag, cs%wave_structure_CSp)
2748 if (
associated(cs))
then 2749 if (
associated(cs%En))
deallocate(cs%En)
2750 if (
allocated(cs%frequency))
deallocate(cs%frequency)
2751 if (
allocated(cs%id_En_mode))
deallocate(cs%id_En_mode)
2752 if (
allocated(cs%id_Ub_mode))
deallocate(cs%id_Ub_mode)
2753 if (
allocated(cs%id_cp_mode))
deallocate(cs%id_cp_mode)
The following structure contains pointers to various fields which may be used describe the surface st...
subroutine propagate(En, cn, freq, dt, G, CS, NAngle)
This subroutine does refraction on the internal waves at a single frequency.
subroutine, public wave_structure(h, tv, G, GV, cn, ModeNum, freq, CS, En, full_halos)
This subroutine determines the internal wave velocity structure for any mode.
subroutine propagate_x(En, speed_x, Cgx_av, dCgx, dt, G, Nangle, CS, LB)
subroutine zonal_flux_en(u, h, hL, hR, uh, dt, G, j, ish, ieh, vol_CFL)
This subroutines evaluates the zonal mass or volume fluxes in a layer.
subroutine, public internal_tides_init(Time, G, GV, param_file, diag, CS)
integer, parameter, public to_all
Ocean grid type. See mom_grid for details.
subroutine propagate_corner_spread(En, energized_wedge, NAngle, speed, dt, G, CS, LB)
This subroutine does first-order corner advection. It was written with the hopes of smoothing out the...
Provides the ocean grid type.
subroutine, public do_group_pass(group, MOM_dom)
subroutine refract(En, cn, freq, dt, G, NAngle, use_PPMang)
This subroutine does refraction on the internal waves at a single frequency.
subroutine, public get_lowmode_loss(i, j, G, CS, mechanism, TKE_loss_sum)
This subroutine extracts the energy lost from the propagating internal which has been summed across a...
subroutine, public internal_tides_end(CS)
subroutine, public wave_structure_init(Time, G, param_file, diag, CS)
This module contains I/O framework code.
subroutine propagate_y(En, speed_y, Cgy_av, dCgy, dt, G, Nangle, CS, LB)
subroutine correct_halo_rotation(En, test, G, NAngle)
This subroutine rotates points in the halos where required to accomodate changes in grid orientation...
subroutine ppm_reconstruction_x(h_in, h_l, h_r, G, LB, simple_2nd)
This subroutine calculates left/right edge values for PPM reconstruction.
subroutine, public propagate_int_tide(h, tv, cn, TKE_itidal_input, vel_btTide, Nb, dt, G, GV, CS)
This subroutine calls other subroutines in this file that are needed to refract, propagate, and dissipate energy density of the internal tide.
subroutine, public start_group_pass(group, MOM_dom)
subroutine itidal_lowmode_loss(G, CS, Nb, Ub, En, TKE_loss_fixed, TKE_loss, dt, full_halos)
This subroutine calculates the energy lost from the propagating internal tide due to scattering over ...
subroutine sum_en(G, CS, En, label)
This subroutine checks for energy conservation on computational domain.
logical function, public is_root_pe()
subroutine, public complete_group_pass(group, MOM_dom)
subroutine merid_flux_en(v, h, hL, hR, vh, dt, G, J, ish, ieh, vol_CFL)
This subroutines evaluates the meridional mass or volume fluxes in a layer.
subroutine, public mom_mesg(message, verb, all_print)
Type for describing a variable, typically a tracer.
subroutine teleport(En, NAngle, CS, G, LB)
This subroutine moves energy across lines of partial reflection to prevent reflection of energy that ...
subroutine ppm_reconstruction_y(h_in, h_l, h_r, G, LB, simple_2nd)
This subroutine calculates left/right edge valus for PPM reconstruction.
subroutine, public save_restart(directory, time, G, CS, time_stamped, filename, GV)
The thermo_var_ptrs structure contains pointers to an assortment of thermodynamic fields that may be ...
subroutine ppm_limit_pos(h_in, h_L, h_R, h_min, G, iis, iie, jis, jie)
This subroutine limits the left/right edge values of the PPM reconstruction to give a reconstruction ...
subroutine, public restart_init(param_file, CS, restart_root)
subroutine ppm_angular_advect(En2d, CFL_ang, Flux_En, NAngle, dt, halo_ang)
This subroutine calculates the 1-d flux for advection in angular space using a monotonic piecewise pa...
real function, public global_area_mean(var, G)
subroutine, public mom_error(level, message, all_print)
subroutine reflect(En, NAngle, CS, G, LB)
This subroutine does reflection of the internal waves at a single frequency.