Skip to content

Commit 90e9ccb

Browse files
Adding suggestions
1 parent e27eec5 commit 90e9ccb

File tree

3 files changed

+71
-70
lines changed

3 files changed

+71
-70
lines changed

src/parameterizations/lateral/MOM_MEKE.F90

Lines changed: 12 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -236,7 +236,8 @@ subroutine step_forward_MEKE(MEKE, h, SN_u, SN_v, visc, dt, G, GV, US, CS, hu, h
236236
real :: ldamping ! The MEKE damping rate [T-1 ~> s-1].
237237
real :: sdt ! dt to use locally [T ~> s] (could be scaled to accelerate)
238238
real :: sdt_damp ! dt for damping [T ~> s] (sdt could be split).
239-
real :: sfac ! A factor needed to compute damping due to Strang splitting [nondim]c
239+
real :: sfac ! A factor needed to compute damping due to Strang splitting [nondim]
240+
real :: Isfac ! Inverse of sfac [nondim]
240241
logical :: use_drag_rate ! Flag to indicate drag_rate is finite
241242
integer :: i, j, k, is, ie, js, je, Isq, Ieq, Jsq, Jeq, nz
242243
real(kind=real32), dimension(size(MEKE%MEKE),NUM_FEATURES) :: features_array ! The array of features
@@ -412,7 +413,6 @@ subroutine step_forward_MEKE(MEKE, h, SN_u, SN_v, visc, dt, G, GV, US, CS, hu, h
412413
if (allocated(MEKE%mom_src)) then
413414
!$OMP parallel do default(shared)
414415
do j=js,je ; do i=is,ie
415-
!src(i,j) = src(i,j) - CS%MEKE_FrCoeff*I_mass(i,j)*MEKE%mom_src(i,j)
416416
src(i,j) = src(i,j) - CS%MEKE_FrCoeff*I_mass(i,j)*MEKE%mom_src(i,j) &
417417
- (CS%MEKE_bhFrCoeff-CS%MEKE_FrCoeff)*I_mass(i,j)*MEKE%mom_src_bh(i,j)
418418
src_mom_lp(i,j) = - CS%MEKE_FrCoeff*I_mass(i,j)*(MEKE%mom_src(i,j)-MEKE%mom_src_bh(i,j))
@@ -483,12 +483,13 @@ subroutine step_forward_MEKE(MEKE, h, SN_u, SN_v, visc, dt, G, GV, US, CS, hu, h
483483
if (MEKE%MEKE(i,j) < 0.) ldamping = 0.
484484
! notice that the above line ensures a damping only if MEKE is positive,
485485
! while leaving MEKE unchanged if it is negative
486+
Isfac = 1. / (1. + sdt_damp * ldamping)
486487
MEKE%MEKE(i,j) = MEKE%MEKE(i,j) / (1.0 + sdt_damp*ldamping)
487488
MEKE_decay(i,j) = ldamping*G%mask2dT(i,j)
488489
ldamping_Strang1(i,j) = ldamping
489-
src_GM(i,j) = src_GM(i,j) / (1.0 + sdt_damp*ldamping)
490-
src_mom_lp(i,j) = src_mom_lp(i,j) / (1.0 + sdt_damp*ldamping)
491-
src_mom_bh(i,j) = src_mom_bh(i,j) / (1.0 + sdt_damp*ldamping)
490+
src_GM(i,j) = src_GM(i,j) * Isfac
491+
src_mom_lp(i,j) = src_mom_lp(i,j) * Isfac
492+
src_mom_bh(i,j) = src_mom_bh(i,j) * Isfac
492493
sfac = ( 1.0 + sdt_damp*ldamping )
493494
src_btm_drag(i,j) = MEKE_current(i,j) * ( (1.0 - sfac) / ( sdt * sfac ) )
494495
enddo ; enddo
@@ -661,13 +662,14 @@ subroutine step_forward_MEKE(MEKE, h, SN_u, SN_v, visc, dt, G, GV, US, CS, hu, h
661662
if (MEKE%MEKE(i,j) < 0.) ldamping = 0.
662663
! notice that the above line ensures a damping only if MEKE is positive,
663664
! while leaving MEKE unchanged if it is negative
665+
Isfac = 1. / (1. + sdt_damp*ldamping)
664666
MEKE%MEKE(i,j) = MEKE%MEKE(i,j) / (1.0 + sdt_damp*ldamping)
665667
MEKE_decay(i,j) = ldamping*G%mask2dT(i,j)
666-
src_GM(i,j) = src_GM(i,j) / (1.0 + sdt_damp*ldamping)
667-
src_mom_lp(i,j) = src_mom_lp(i,j) / (1.0 + sdt_damp*ldamping)
668-
src_mom_bh(i,j) = src_mom_bh(i,j) / (1.0 + sdt_damp*ldamping)
669-
src_adv(i,j) = src_adv(i,j) / (1.0 + sdt_damp*ldamping)
670-
src_mom_K4(i,j) = src_mom_K4(i,j) / (1.0 + sdt_damp*ldamping)
668+
src_GM(i,j) = src_GM(i,j) * Isfac
669+
src_mom_lp(i,j) = src_mom_lp(i,j) * Isfac
670+
src_mom_bh(i,j) = src_mom_bh(i,j) * Isfac
671+
src_adv(i,j) = src_adv(i,j) * Isfac
672+
src_mom_K4(i,j) = src_mom_K4(i,j) * Isfac
671673
sfac = ( 1.0 + sdt_damp*ldamping_Strang1(i,j) ) * ( 1.0 + sdt_damp*ldamping )
672674
src_btm_drag(i,j) = MEKE_current(i,j) * ( (1.0 - sfac) / ( sdt * sfac ) )
673675
enddo ; enddo

src/parameterizations/lateral/MOM_MEKE_types.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ module MOM_MEKE_types
1212
real, allocatable :: mom_src(:,:) !< MEKE source from lateral friction in the
1313
!! momentum equations [R Z L2 T-3 ~> W m-2].
1414
real, allocatable :: mom_src_bh(:,:) !< MEKE source from the biharmonic part of the lateral friction in the
15-
!! momentum equations [R Z L2 T-3 ~> W m-2]. !cyc
15+
!! momentum equations [R Z L2 T-3 ~> W m-2].
1616
real, allocatable :: GME_snk(:,:) !< MEKE sink from GME backscatter in the momentum equations [R Z L2 T-3 ~> W m-2].
1717
real, allocatable :: Kh(:,:) !< The MEKE-derived lateral mixing coefficient [L2 T-1 ~> m2 s-1].
1818
real, allocatable :: Kh_diff(:,:) !< Uses the non-MEKE-derived thickness diffusion coefficient to diffuse

src/parameterizations/lateral/MOM_hor_visc.F90

Lines changed: 58 additions & 59 deletions
Original file line numberDiff line numberDiff line change
@@ -64,8 +64,8 @@ module MOM_hor_visc
6464
!! for stability without considering other terms [nondim].
6565
!! The default is 0.8.
6666
real :: KS_coef !< A nondimensional coefficient on the biharmonic viscosity that sets the
67-
!! kill switch for backscatter. Default is 1.0.
68-
real :: KS_timescale !< A timescale for computing CFL limit for turning off backscatter (~DT)
67+
!! kill switch for backscatter. Default is 1.0 [nondim].
68+
real :: KS_timescale !< A timescale for computing CFL limit for turning off backscatter [T ~> s].
6969
logical :: backscatter_underbound !< If true, the bounds on the biharmonic viscosity are allowed
7070
!! to increase where the Laplacian viscosity is negative (due to
7171
!! backscatter parameterizations) beyond the largest timestep-dependent
@@ -237,7 +237,7 @@ module MOM_hor_visc
237237
integer :: id_vort_xy_q = -1, id_div_xx_h = -1
238238
integer :: id_sh_xy_q = -1, id_sh_xx_h = -1
239239
integer :: id_FrictWork = -1, id_FrictWorkIntz = -1
240-
integer :: id_FrictWork_bh = -1, id_FrictWorkIntz_bh = -1 !cyc
240+
integer :: id_FrictWork_bh = -1, id_FrictWorkIntz_bh = -1
241241
integer :: id_FrictWork_GME = -1
242242
integer :: id_normstress = -1, id_shearstress = -1
243243
integer :: id_visc_limit_h = -1, id_visc_limit_q = -1
@@ -325,7 +325,7 @@ subroutine horizontal_viscosity(u, v, h, uh, vh, diffu, diffv, MEKE, VarMix, G,
325325
str_xx_GME,& ! smoothed diagonal term in the stress tensor from GME [L2 T-2 ~> m2 s-2]
326326
bhstr_xx, & ! A copy of str_xx that only contains the biharmonic contribution [H L2 T-2 ~> m3 s-2 or kg s-2]
327327
FrictWorkIntz, & ! depth integrated energy dissipated by lateral friction [R L2 T-3 ~> W m-2]
328-
FrictWorkIntz_bh, & ! depth integrated energy dissipated by biharmonic lateral friction [R L2 T-3 ~> W m-2] !cyc
328+
FrictWorkIntz_bh, & ! depth integrated energy dissipated by biharmonic lateral friction [R L2 T-3 ~> W m-2]
329329
grad_vort_mag_h, & ! Magnitude of vorticity gradient at h-points [L-1 T-1 ~> m-1 s-1]
330330
grad_vort_mag_h_2d, & ! Magnitude of 2d vorticity gradient at h-points [L-1 T-1 ~> m-1 s-1]
331331
grad_div_mag_h, & ! Magnitude of divergence gradient at h-points [L-1 T-1 ~> m-1 s-1]
@@ -371,9 +371,9 @@ subroutine horizontal_viscosity(u, v, h, uh, vh, diffu, diffv, MEKE, VarMix, G,
371371
vort_xy_q, & ! vertical vorticity at corner points [T-1 ~> s-1]
372372
sh_xy_q, & ! horizontal shearing strain at corner points [T-1 ~> s-1]
373373
GME_coeff_q, & !< GME coeff. at q-points [L2 T-1 ~> m2 s-1]
374-
visc_limit_q, & ! used to stabilize the EY24_EBT_BS backscatter
375-
visc_limit_q_flag, & ! determines whether backscatter is shut off
376-
visc_limit_q_frac, & ! determines how close backscatter is to shutting off
374+
visc_limit_q, & ! used to stabilize the EY24_EBT_BS backscatter [nondim]
375+
visc_limit_q_flag, & ! determines whether backscatter is shut off [nondim]
376+
visc_limit_q_frac, & ! determines how close backscatter is to shutting off [nondim]
377377
BS_coeff_q, & ! A diagnostic array of the backscatter coefficient [L2 T-1 ~> m2 s-1]
378378
ShSt ! A diagnostic array of shear stress [T-1 ~> s-1].
379379
real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)+1) :: &
@@ -387,7 +387,7 @@ subroutine horizontal_viscosity(u, v, h, uh, vh, diffu, diffv, MEKE, VarMix, G,
387387
Kh_h, & ! Laplacian viscosity at thickness points [L2 T-1 ~> m2 s-1]
388388
dz, & ! Height change across layers [Z ~> m]
389389
FrictWork, & ! work done by MKE dissipation mechanisms [R L2 T-3 ~> W m-2]
390-
FrictWork_bh, & ! work done by the biharmonic MKE dissipation mechanisms [R L2 T-3 ~> W m-2] !cyc
390+
FrictWork_bh, & ! work done by the biharmonic MKE dissipation mechanisms [R L2 T-3 ~> W m-2]
391391
FrictWork_GME, & ! work done by GME [R L2 T-3 ~> W m-2]
392392
div_xx_h, & ! horizontal divergence [T-1 ~> s-1]
393393
sh_xx_h, & ! horizontal tension (du/dx - dv/dy) including metric terms [T-1 ~> s-1]
@@ -397,9 +397,9 @@ subroutine horizontal_viscosity(u, v, h, uh, vh, diffu, diffv, MEKE, VarMix, G,
397397
grid_Re_Kh, & ! Grid Reynolds number for Laplacian horizontal viscosity at h points [nondim]
398398
grid_Re_Ah, & ! Grid Reynolds number for Biharmonic horizontal viscosity at h points [nondim]
399399
GME_coeff_h, & ! GME coefficient at h-points [L2 T-1 ~> m2 s-1]
400-
visc_limit_h, & ! Used to stabilize the EY24_EBT_BS backscatter
401-
visc_limit_h_flag, & ! determines whether backscatter is shut off
402-
visc_limit_h_frac ! determines how close backscatter is to shutting off
400+
visc_limit_h, & ! Used to stabilize the EY24_EBT_BS backscatter [nondim]
401+
visc_limit_h_flag, & ! determines whether backscatter is shut off [nondim]
402+
visc_limit_h_frac ! determines how close backscatter is to shutting off [nondim]
403403
real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)) :: &
404404
u_smooth ! Zonal velocity, smoothed with a spatial low-pass filter [L T-1 ~> m s-1]
405405
real, dimension(SZI_(G),SZJB_(G),SZK_(GV)) :: &
@@ -1414,7 +1414,7 @@ subroutine horizontal_viscosity(u, v, h, uh, vh, diffu, diffv, MEKE, VarMix, G,
14141414
enddo ; enddo
14151415
endif
14161416

1417-
if ((CS%id_grid_Re_Ah>0)) then
1417+
if (CS%id_grid_Re_Ah > 0) then
14181418
do j=js,je ; do i=is,ie
14191419
KE = 0.125 * ((u(I,j,k) + u(I-1,j,k))**2 + (v(i,J,k) + v(i,J-1,k))**2)
14201420
grid_Ah = max(Ah(i,j), CS%min_grid_Ah)
@@ -1437,24 +1437,24 @@ subroutine horizontal_viscosity(u, v, h, uh, vh, diffu, diffv, MEKE, VarMix, G,
14371437
endif ! Get biharmonic coefficient at h points and biharmonic part of str_xx
14381438

14391439
! Backscatter using MEKE
1440-
if (CS%EY24_EBT_BS) then
1441-
do j=Jsq,Jeq+1 ; do i=Isq,Ieq+1
1442-
if (visc_limit_h_flag(i,j,k) > 0) then
1443-
Kh_BS(i,j) = 0.
1444-
else
1445-
Kh_BS(i,j) = MEKE%Ku(i,j) * VarMix%BS_struct(i,j,k)
1446-
endif
1447-
enddo ; enddo
1440+
if (CS%EY24_EBT_BS) then
1441+
do j=Jsq,Jeq+1 ; do i=Isq,Ieq+1
1442+
if (visc_limit_h_flag(i,j,k) > 0) then
1443+
Kh_BS(i,j) = 0.
1444+
else
1445+
Kh_BS(i,j) = MEKE%Ku(i,j) * VarMix%BS_struct(i,j,k)
1446+
endif
1447+
enddo ; enddo
14481448

1449+
do j=Jsq,Jeq+1 ; do i=Isq,Ieq+1
1450+
str_xx_BS(i,j) = -Kh_BS(i,j) * sh_xx(i,j)
1451+
enddo ; enddo
1452+
1453+
if (CS%id_BS_coeff_h>0) then
14491454
do j=Jsq,Jeq+1 ; do i=Isq,Ieq+1
1450-
str_xx_BS(i,j) = -Kh_BS(i,j) * sh_xx(i,j)
1455+
BS_coeff_h(i,j,k) = Kh_BS(i,j)
14511456
enddo ; enddo
1452-
1453-
if (CS%id_BS_coeff_h>0) then
1454-
do j=Jsq,Jeq+1 ; do i=Isq,Ieq+1
1455-
BS_coeff_h(i,j,k) = Kh_BS(i,j)
1456-
enddo ; enddo
1457-
endif
1457+
endif
14581458

14591459
do j=Jsq,Jeq+1 ; do i=Isq,Ieq+1
14601460
str_xx(i,j) = str_xx(i,j) + str_xx_BS(i,j)
@@ -1782,29 +1782,28 @@ subroutine horizontal_viscosity(u, v, h, uh, vh, diffu, diffv, MEKE, VarMix, G,
17821782
enddo ; enddo
17831783
endif ! Get Ah at q points and biharmonic part of str_xy
17841784

1785-
! Backscatter using MEKE
1786-
if (CS%EY24_EBT_BS) then
1787-
!if (grid_Re_Ah(i,j,k) < 1.) then
1788-
do j=Jsq,Jeq+1 ; do i=Isq,Ieq+1
1789-
if (visc_limit_q_flag(I,J,k) > 0) then
1790-
Kh_BS(I,J) = 0.
1791-
else
1792-
Kh_BS(I,J) = 0.25*( ((MEKE%Ku(i,j)*VarMix%BS_struct(i,j,k)) + &
1793-
(MEKE%Ku(i+1,j+1)*VarMix%BS_struct(i+1,j+1,k))) + &
1794-
((MEKE%Ku(i+1,j)*VarMix%BS_struct(i+1,j,k)) + &
1795-
(MEKE%Ku(i,j+1)*VarMix%BS_struct(i,j+1,k))) )
1796-
endif
1797-
enddo ; enddo
1785+
! Backscatter using MEKE
1786+
if (CS%EY24_EBT_BS) then
1787+
do j=Jsq,Jeq+1 ; do i=Isq,Ieq+1
1788+
if (visc_limit_q_flag(I,J,k) > 0) then
1789+
Kh_BS(I,J) = 0.
1790+
else
1791+
Kh_BS(I,J) = 0.25*( ((MEKE%Ku(i,j)*VarMix%BS_struct(i,j,k)) + &
1792+
(MEKE%Ku(i+1,j+1)*VarMix%BS_struct(i+1,j+1,k))) + &
1793+
((MEKE%Ku(i+1,j)*VarMix%BS_struct(i+1,j,k)) + &
1794+
(MEKE%Ku(i,j+1)*VarMix%BS_struct(i,j+1,k))) )
1795+
endif
1796+
enddo ; enddo
17981797

1799-
do J=js-1,Jeq ; do I=is-1,Ieq
1800-
str_xy_BS(I,J) = -Kh_BS(I,J) * (sh_xy(I,J))
1801-
enddo ; enddo
1798+
do J=js-1,Jeq ; do I=is-1,Ieq
1799+
str_xy_BS(I,J) = -Kh_BS(I,J) * (sh_xy(I,J))
1800+
enddo ; enddo
18021801

1803-
if (CS%id_BS_coeff_q>0) then
1804-
do J=js-1,Jeq ; do I=is-1,Ieq
1805-
BS_coeff_q(I,J,k) = Kh_BS(I,J)
1806-
enddo ; enddo
1807-
endif
1802+
if (CS%id_BS_coeff_q>0) then
1803+
do J=js-1,Jeq ; do I=is-1,Ieq
1804+
BS_coeff_q(I,J,k) = Kh_BS(I,J)
1805+
enddo ; enddo
1806+
endif
18081807

18091808
do J=js-1,Jeq ; do I=is-1,Ieq
18101809
str_xy(I,J) = str_xy(I,J) + str_xy_BS(I,J)
@@ -1915,8 +1914,8 @@ subroutine horizontal_viscosity(u, v, h, uh, vh, diffu, diffv, MEKE, VarMix, G,
19151914
! Diagnose str_xx*d_x u - str_yy*d_y v + str_xy*(d_y u + d_x v)
19161915
! This is the old formulation that includes energy diffusion
19171916
if (visc_limit_h_flag(i,j,k) > 0) then
1918-
FrictWork(i,j,k) = 0
1919-
FrictWork_bh(i,j,k) = 0
1917+
FrictWork(i,j,k) = 0.
1918+
FrictWork_bh(i,j,k) = 0.
19201919
else
19211920
FrictWork(i,j,k) = GV%H_to_RZ * ( &
19221921
(str_xx(i,j)*(u(I,j,k)-u(I-1,j,k))*G%IdxT(i,j) &
@@ -1934,7 +1933,7 @@ subroutine horizontal_viscosity(u, v, h, uh, vh, diffu, diffv, MEKE, VarMix, G,
19341933
(u(I,j,k)-u(I,j-1,k))*G%IdyBu(I,J-1) &
19351934
+(v(i+1,J-1,k)-v(i,J-1,k))*G%IdxBu(I,J-1) )) ) )
19361935
! Diagnose bhstr_xx*d_x u - bhstr_yy*d_y v + bhstr_xy*(d_y u + d_x v)
1937-
! This is the old formulation that includes energy diffusion !cyc
1936+
! This is the old formulation that includes energy diffusion
19381937
FrictWork_bh(i,j,k) = GV%H_to_RZ * ( &
19391938
(bhstr_xx(i,j) * (u(I,j,k)-u(I-1,j,k))*G%IdxT(i,j) &
19401939
- bhstr_xx(i,j) * (v(i,J,k)-v(i,J-1,k))*G%IdyT(i,j)) &
@@ -2079,7 +2078,7 @@ subroutine horizontal_viscosity(u, v, h, uh, vh, diffu, diffv, MEKE, VarMix, G,
20792078
if (k==1) then
20802079
do j=js,je ; do i=is,ie
20812080
MEKE%mom_src(i,j) = 0.
2082-
MEKE%mom_src_bh(i,j) = 0. !cyc
2081+
MEKE%mom_src_bh(i,j) = 0.
20832082
enddo ; enddo
20842083
if (allocated(MEKE%GME_snk)) then
20852084
do j=js,je ; do i=is,ie
@@ -2127,7 +2126,7 @@ subroutine horizontal_viscosity(u, v, h, uh, vh, diffu, diffv, MEKE, VarMix, G,
21272126
+ (str_xy(I,J-1)-RoScl*bhstr_xy(I,J-1)) * &
21282127
((u(I,j,k)-u(I,j-1,k))*G%IdyBu(I,J-1) &
21292128
+ (v(i+1,J-1,k)-v(i,J-1,k))*G%IdxBu(I,J-1)) ) ) )
2130-
MEKE%mom_src_bh(i,j) = MEKE%mom_src_bh(i,j) + GV%H_to_RZ * ( & !cyc
2129+
MEKE%mom_src_bh(i,j) = MEKE%mom_src_bh(i,j) + GV%H_to_RZ * ( &
21312130
((bhstr_xx(i,j)-RoScl*bhstr_xx(i,j))*(u(I,j,k)-u(I-1,j,k))*G%IdxT(i,j) &
21322131
-(bhstr_xx(i,j)-RoScl*bhstr_xx(i,j))*(v(i,J,k)-v(i,J-1,k))*G%IdyT(i,j)) &
21332132
+ 0.25*(((bhstr_xy(I,J)-RoScl*bhstr_xy(I,J)) * &
@@ -2143,11 +2142,11 @@ subroutine horizontal_viscosity(u, v, h, uh, vh, diffu, diffv, MEKE, VarMix, G,
21432142
((u(I,j,k)-u(I,j-1,k))*G%IdyBu(I,J-1) &
21442143
+ (v(i+1,J-1,k)-v(i,J-1,k))*G%IdxBu(I,J-1)) ) ) )
21452144
enddo ; enddo
2146-
else !cyc
2145+
else
21472146

21482147
do j=js,je ; do i=is,ie
21492148
MEKE%mom_src(i,j) = MEKE%mom_src(i,j) + FrictWork(i,j,k)
2150-
MEKE%mom_src_bh(i,j) = MEKE%mom_src_bh(i,j) + FrictWork_bh(i,j,k) !cyc
2149+
MEKE%mom_src_bh(i,j) = MEKE%mom_src_bh(i,j) + FrictWork_bh(i,j,k)
21512150
enddo ; enddo
21522151
endif ! MEKE%backscatter_Ro_c
21532152

@@ -2167,7 +2166,7 @@ subroutine horizontal_viscosity(u, v, h, uh, vh, diffu, diffv, MEKE, VarMix, G,
21672166
if (CS%id_diffu>0) call post_data(CS%id_diffu, diffu, CS%diag)
21682167
if (CS%id_diffv>0) call post_data(CS%id_diffv, diffv, CS%diag)
21692168
if (CS%id_FrictWork>0) call post_data(CS%id_FrictWork, FrictWork, CS%diag)
2170-
if (CS%id_FrictWork_bh>0) call post_data(CS%id_FrictWork_bh, FrictWork_bh, CS%diag) !cyc
2169+
if (CS%id_FrictWork_bh>0) call post_data(CS%id_FrictWork_bh, FrictWork_bh, CS%diag)
21712170
if (CS%id_Ah_h>0) call post_data(CS%id_Ah_h, Ah_h, CS%diag)
21722171
if (CS%id_grid_Re_Ah>0) call post_data(CS%id_grid_Re_Ah, grid_Re_Ah, CS%diag)
21732172
if (CS%id_div_xx_h>0) call post_data(CS%id_div_xx_h, div_xx_h, CS%diag)
@@ -2218,7 +2217,7 @@ subroutine horizontal_viscosity(u, v, h, uh, vh, diffu, diffv, MEKE, VarMix, G,
22182217
call post_data(CS%id_FrictWorkIntz, FrictWorkIntz, CS%diag)
22192218
endif
22202219

2221-
if (CS%id_FrictWorkIntz_bh > 0) then !cyc
2220+
if (CS%id_FrictWorkIntz_bh > 0) then
22222221
do j=js,je
22232222
do i=is,ie ; FrictWorkIntz_bh(i,j) = FrictWork_bh(i,j,1) ; enddo
22242223
do k=2,nz ; do i=is,ie
@@ -3200,10 +3199,10 @@ subroutine hor_visc_init(Time, G, GV, US, param_file, diag, CS, ADp)
32003199
cmor_standard_name='ocean_kinetic_energy_dissipation_per_unit_area_due_to_xy_friction')
32013200
CS%id_FrictWork_bh = register_diag_field('ocean_model','FrictWork_bh',diag%axesTL,Time,&
32023201
'Integral work done by the biharmonic lateral friction terms.', &
3203-
'W m-2', conversion=US%RZ3_T3_to_W_m2*US%L_to_Z**2) !cyc
3202+
'W m-2', conversion=US%RZ3_T3_to_W_m2*US%L_to_Z**2)
32043203
CS%id_FrictWorkIntz_bh = register_diag_field('ocean_model','FrictWorkIntz_bh',diag%axesT1,Time,&
32053204
'Depth integrated work done by the biharmonic lateral friction', &
3206-
'W m-2', conversion=US%RZ3_T3_to_W_m2*US%L_to_Z**2) !cyc
3205+
'W m-2', conversion=US%RZ3_T3_to_W_m2*US%L_to_Z**2)
32073206

32083207
end subroutine hor_visc_init
32093208

0 commit comments

Comments
 (0)