Skip to content

Commit a563fa1

Browse files
committed
Barotropic OBC memory and halo update cleanup
Cleaned up the OBC-related memory allocation and moved it into initialize_BT_OBC. Also combined OBC-related halo passes to reduce latency during the set-up phase of btstep. Also simplified the code setting the various gtot values around OBC points. The OBC argument to btstep_timeloop was replaced with a new logical variable in the barotropic control structure that is set during initialization. All answers are bitwise identical and no public interfaces are changed.
1 parent eeb5f9d commit a563fa1

File tree

1 file changed

+93
-102
lines changed

1 file changed

+93
-102
lines changed

src/core/MOM_barotropic.F90

Lines changed: 93 additions & 102 deletions
Original file line numberDiff line numberDiff line change
@@ -98,13 +98,9 @@ module MOM_barotropic
9898
integer :: is_v_S_obc, ie_v_S_obc, Js_v_S_obc, Je_v_S_obc
9999
integer :: is_v_N_obc, ie_v_N_obc, Js_v_N_obc, Je_v_N_obc
100100
!>@}
101-
logical :: is_alloced = .false. !< True if BT_OBC is in use and has been allocated
102101

103-
type(group_pass_type) :: pass_uv !< Structure for group halo pass
104-
type(group_pass_type) :: pass_uhvh !< Structure for group halo pass
105-
type(group_pass_type) :: pass_h !< Structure for group halo pass
106-
type(group_pass_type) :: pass_cg !< Structure for group halo pass
107-
type(group_pass_type) :: pass_eta_outer !< Structure for group halo pass
102+
type(group_pass_type) :: pass_uv !< Structure for group halo pass of vectors
103+
type(group_pass_type) :: scalar_pass !< Structure for group halo pass of scalars
108104
end type BT_OBC_type
109105

110106
integer, parameter :: SPECIFIED_OBC = 1 !< An integer used to encode a specified OBC point
@@ -212,6 +208,8 @@ module MOM_barotropic
212208
!! equation. Otherwise the transports are the sum of the transports
213209
!! based on a series of instantaneous velocities and the BT_CONT_TYPE
214210
!! for transports. This is only valid if a BT_CONT_TYPE is used.
211+
logical :: integral_OBCs !< This is true if integral_bt_cont is true and there are open boundary
212+
!! conditions being applied somewhere in the global domain.
215213
logical :: Nonlinear_continuity !< If true, the barotropic continuity equation
216214
!! uses the full ocean thickness for transport.
217215
integer :: Nonlin_cont_update_period !< The number of barotropic time steps
@@ -1081,28 +1079,21 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
10811079
enddo ; enddo
10821080
enddo
10831081

1084-
if (apply_OBCs) then
1085-
do n=1,OBC%number_of_segments
1086-
if (.not. OBC%segment(n)%on_pe) cycle
1087-
I = OBC%segment(n)%HI%IsdB ; J = OBC%segment(n)%HI%JsdB
1088-
if (OBC%segment(n)%is_N_or_S .and. (J >= Jsq-1) .and. (J <= Jeq+1)) then
1089-
do i = max(Isq-1,OBC%segment(n)%HI%isd), min(Ieq+2,OBC%segment(n)%HI%ied)
1090-
if (OBC%segment(n)%direction == OBC_DIRECTION_N) then
1091-
gtot_S(i,j+1) = gtot_S(i,j) !### Should this be gtot_N(i,j) to use wt_v at the same point?
1092-
else ! (OBC%segment(n)%direction == OBC_DIRECTION_S)
1093-
gtot_N(i,j) = gtot_N(i,j+1) ! Perhaps this should be gtot_S(i,j+1)?
1094-
endif
1095-
enddo
1096-
elseif (OBC%segment(n)%is_E_or_W .and. (I >= Isq-1) .and. (I <= Ieq+1)) then
1097-
do j = max(Jsq-1,OBC%segment(n)%HI%jsd), min(Jeq+2,OBC%segment(n)%HI%jed)
1098-
if (OBC%segment(n)%direction == OBC_DIRECTION_E) then
1099-
gtot_W(i+1,j) = gtot_W(i,j) ! Perhaps this should be gtot_E(i,j)?
1100-
else ! (OBC%segment(n)%direction == OBC_DIRECTION_W)
1101-
gtot_E(i,j) = gtot_E(i+1,j) ! Perhaps this should be gtot_W(i+1,j)?
1102-
endif
1103-
enddo
1104-
endif
1105-
enddo
1082+
if (CS%BT_OBC%u_OBCs_on_PE) then
1083+
do j=js,je ; do I=is-1,ie
1084+
if (CS%BT_OBC%u_OBC_type(I,j) > 0) & ! Eastern boundary condition
1085+
gtot_W(i+1,j) = gtot_W(i,j) ! Perhaps this should be gtot_E(i,j)?
1086+
if (CS%BT_OBC%u_OBC_type(I,j) < 0) & ! Western boundary condition
1087+
gtot_E(i,j) = gtot_E(i+1,j) ! Perhaps this should be gtot_W(i+1,j)?
1088+
enddo ; enddo
1089+
endif
1090+
if (CS%BT_OBC%v_OBCs_on_PE) then
1091+
do J=js-1,je ; do i=is,ie
1092+
if (CS%BT_OBC%v_OBC_type(i,J) > 0) & ! Northern boundary condition
1093+
gtot_S(i,j+1) = gtot_S(i,j) !### Should this be gtot_N(i,j) to use wt_v at the same point?
1094+
if (CS%BT_OBC%v_OBC_type(i,J) < 0) & ! Southern boundary condition
1095+
gtot_N(i,j) = gtot_N(i,j+1) ! Perhaps this should be gtot_S(i,j+1)?
1096+
enddo ; enddo
11061097
endif
11071098

11081099
if (CS%calculate_SAL) then
@@ -1780,7 +1771,6 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
17801771
I_sum_wt_vel = 1.0 ; I_sum_wt_eta = 1.0 ; I_sum_wt_accel = 1.0 ; I_sum_wt_trans = 1.0
17811772
endif
17821773

1783-
17841774
! March the barotropic solver through all of its time steps.
17851775
call btstep_timeloop(eta, ubt, vbt, uhbt0, Datu, BTCL_u, vhbt0, Datv, BTCL_v, eta_IC, &
17861776
eta_PF_1, d_eta_PF, eta_src, dyn_coef_eta, uhbtav, vhbtav, u_accel_bt, v_accel_bt, &
@@ -1789,7 +1779,7 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
17891779
eta_PF, gtot_E, gtot_W, gtot_N, gtot_S, SpV_col_avg, dgeo_de, &
17901780
eta_sum, eta_wtd, ubt_wtd, vbt_wtd, Coru_avg, PFu_avg, Corv_avg, PFv_avg, &
17911781
use_BT_cont, interp_eta_PF, find_etaav, dt, dtbt, nstep, nfilter, &
1792-
wt_vel, wt_eta, wt_accel, wt_trans, wt_accel2, OBC, CS%BT_OBC, CS, G, MS, GV, US)
1782+
wt_vel, wt_eta, wt_accel, wt_trans, wt_accel2, CS%BT_OBC, CS, G, MS, GV, US)
17931783

17941784

17951785
if (id_clock_calc > 0) call cpu_clock_end(id_clock_calc)
@@ -2118,7 +2108,7 @@ subroutine btstep_timeloop(eta, ubt, vbt, uhbt0, Datu, BTCL_u, vhbt0, Datv, BTCL
21182108
eta_PF, gtot_E, gtot_W, gtot_N, gtot_S, SpV_col_avg, dgeo_de, &
21192109
eta_sum, eta_wtd, ubt_wtd, vbt_wtd, Coru_avg, PFu_avg, Corv_avg, PFv_avg, &
21202110
use_BT_cont, interp_eta_PF, find_etaav, dt, dtbt, nstep, nfilter, &
2121-
wt_vel, wt_eta, wt_accel, wt_trans, wt_accel2, OBC, BT_OBC, CS, G, MS, GV, US)
2111+
wt_vel, wt_eta, wt_accel, wt_trans, wt_accel2, BT_OBC, CS, G, MS, GV, US)
21222112

21232113
type(barotropic_CS), intent(inout) :: CS !< Barotropic control structure
21242114
type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure (inout to allow for halo updates)
@@ -2278,10 +2268,9 @@ subroutine btstep_timeloop(eta, ubt, vbt, uhbt0, Datu, BTCL_u, vhbt0, Datv, BTCL
22782268
real, dimension(nstep+nfilter+1), intent(in) :: &
22792269
wt_accel2 !< Potentially un-normalized relative weights of each of the
22802270
!! barotropic timesteps in determining the average accelerations [nondim]
2281-
type(ocean_OBC_type), pointer :: OBC !< An associated pointer to an OBC type
22822271
type(BT_OBC_type), intent(in) :: BT_OBC !< A structure with the private barotropic arrays
22832272
!! related to the open boundary conditions,
2284-
!! set by set_up_BT_OBC
2273+
!! with time evolving data stored via set_up_BT_OBC
22852274
type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure
22862275
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
22872276

@@ -2427,9 +2416,8 @@ subroutine btstep_timeloop(eta, ubt, vbt, uhbt0, Datu, BTCL_u, vhbt0, Datv, BTCL
24272416
if (integral_BT_cont) then
24282417
call create_group_pass(CS%pass_eta_ubt, ubt_int, vbt_int, CS%BT_Domain)
24292418
! This is only needed with integral_BT_cont, OBCs and multiple barotropic steps between halo updates.
2430-
if (associated(OBC)) then ; if (open_boundary_query(OBC, apply_open_OBC=.true.)) &
2419+
if (CS%integral_OBCs) &
24312420
call create_group_pass(CS%pass_eta_ubt, uhbt_int, vhbt_int, CS%BT_Domain)
2432-
endif
24332421
endif
24342422

24352423
! The following loop contains all of the time steps.
@@ -2601,15 +2589,15 @@ subroutine btstep_timeloop(eta, ubt, vbt, uhbt0, Datu, BTCL_u, vhbt0, Datv, BTCL
26012589
! Apply open boundary condition considerations to revise the updated velocities and transports.
26022590
if (CS%BT_OBC%u_OBCs_on_PE) then
26032591
!$OMP single
2604-
call apply_u_velocity_OBCs(ubt, uhbt, ubt_trans, eta, SpV_col_avg, ubt_prev, CS%BT_OBC, &
2592+
call apply_u_velocity_OBCs(ubt, uhbt, ubt_trans, eta, SpV_col_avg, ubt_prev, BT_OBC, &
26052593
G, MS, GV, US, CS, iev-ie, dtbt, CS%bebt, use_BT_cont, integral_BT_cont, n*dtbt, &
26062594
Datu, BTCL_u, uhbt0, ubt_int, ubt_int_prev, uhbt_int, uhbt_int_prev)
26072595
!$OMP end single
26082596
endif
26092597

26102598
if (CS%BT_OBC%v_OBCs_on_PE) then
26112599
!$OMP single
2612-
call apply_v_velocity_OBCs(vbt, vhbt, vbt_trans, eta, SpV_col_avg, vbt_prev, CS%BT_OBC, &
2600+
call apply_v_velocity_OBCs(vbt, vhbt, vbt_trans, eta, SpV_col_avg, vbt_prev, BT_OBC, &
26132601
G, MS, GV, US, CS, iev-ie, dtbt, CS%bebt, use_BT_cont, integral_BT_cont, n*dtbt, &
26142602
Datv, BTCL_v, vhbt0, vbt_int, vbt_int_prev, vhbt_int, vhbt_int_prev)
26152603
!$OMP end single
@@ -3972,6 +3960,33 @@ subroutine initialize_BT_OBC(OBC, BT_OBC, G, CS)
39723960
BT_OBC%u_OBCs_on_PE = ((BT_OBC%Is_u_E_obc <= iedw) .or. (BT_OBC%Is_u_W_obc <= iedw))
39733961
BT_OBC%v_OBCs_on_PE = ((BT_OBC%is_v_N_obc <= iedw) .or. (BT_OBC%is_v_S_obc <= iedw))
39743962

3963+
! Allocate time-varying arrays that will be used for open boundary conditions.
3964+
3965+
! This pair is used with either Flather or specified OBCs.
3966+
allocate(BT_OBC%ubt_outer(isdw-1:iedw,jsdw:jedw), source=0.0)
3967+
allocate(BT_OBC%vbt_outer(isdw:iedw,jsdw-1:jedw), source=0.0)
3968+
call create_group_pass(BT_OBC%pass_uv, BT_OBC%ubt_outer, BT_OBC%vbt_outer, CS%BT_Domain)
3969+
3970+
! This pair is only used with specified OBCs.
3971+
allocate(BT_OBC%uhbt(isdw-1:iedw,jsdw:jedw), source=0.0)
3972+
allocate(BT_OBC%vhbt(isdw:iedw,jsdw-1:jedw), source=0.0)
3973+
call create_group_pass(BT_OBC%pass_uv, BT_OBC%uhbt, BT_OBC%vhbt, CS%BT_Domain)
3974+
3975+
if (OBC%Flather_u_BCs_exist_globally .or. OBC%Flather_v_BCs_exist_globally) then
3976+
! These 3 pairs are only used with Flather OBCs.
3977+
allocate(BT_OBC%Cg_u(isdw-1:iedw,jsdw:jedw), source=0.0)
3978+
allocate(BT_OBC%dZ_u(isdw-1:iedw,jsdw:jedw), source=0.0)
3979+
allocate(BT_OBC%SSH_outer_u(isdw-1:iedw,jsdw:jedw), source=0.0)
3980+
3981+
allocate(BT_OBC%Cg_v(isdw:iedw,jsdw-1:jedw), source=0.0)
3982+
allocate(BT_OBC%dZ_v(isdw:iedw,jsdw-1:jedw), source=0.0)
3983+
allocate(BT_OBC%SSH_outer_v(isdw:iedw,jsdw-1:jedw), source=0.0)
3984+
3985+
call create_group_pass(BT_OBC%scalar_pass, BT_OBC%SSH_outer_u, BT_OBC%SSH_outer_v, CS%BT_Domain, To_All+Scalar_Pair)
3986+
call create_group_pass(BT_OBC%scalar_pass, BT_OBC%dZ_u, BT_OBC%dZ_v, CS%BT_Domain, To_All+Scalar_Pair)
3987+
call create_group_pass(BT_OBC%scalar_pass, BT_OBC%Cg_u, BT_OBC%Cg_v, CS%BT_Domain, To_All+Scalar_Pair)
3988+
endif
3989+
39753990
end subroutine initialize_BT_OBC
39763991

39773992
!> This subroutine sets up the time-varying fields in the private structure used to apply the open
@@ -4026,32 +4041,6 @@ subroutine set_up_BT_OBC(OBC, eta, SpV_avg, BT_OBC, BT_Domain, G, GV, US, CS, MS
40264041

40274042
I_dt = 1.0 / dt_baroclinic
40284043

4029-
if ((isdw < isd) .or. (jsdw < jsd)) then
4030-
call MOM_error(FATAL, "set_up_BT_OBC: Open boundary conditions are not "//&
4031-
"yet fully implemented with wide barotropic halos.")
4032-
endif
4033-
4034-
if (.not. BT_OBC%is_alloced) then
4035-
allocate(BT_OBC%Cg_u(isdw-1:iedw,jsdw:jedw), source=0.0)
4036-
allocate(BT_OBC%dZ_u(isdw-1:iedw,jsdw:jedw), source=0.0)
4037-
allocate(BT_OBC%uhbt(isdw-1:iedw,jsdw:jedw), source=0.0)
4038-
allocate(BT_OBC%ubt_outer(isdw-1:iedw,jsdw:jedw), source=0.0)
4039-
allocate(BT_OBC%SSH_outer_u(isdw-1:iedw,jsdw:jedw), source=0.0)
4040-
4041-
allocate(BT_OBC%Cg_v(isdw:iedw,jsdw-1:jedw), source=0.0)
4042-
allocate(BT_OBC%dZ_v(isdw:iedw,jsdw-1:jedw), source=0.0)
4043-
allocate(BT_OBC%vhbt(isdw:iedw,jsdw-1:jedw), source=0.0)
4044-
allocate(BT_OBC%vbt_outer(isdw:iedw,jsdw-1:jedw), source=0.0)
4045-
allocate(BT_OBC%SSH_outer_v(isdw:iedw,jsdw-1:jedw), source=0.0)
4046-
4047-
BT_OBC%is_alloced = .true.
4048-
call create_group_pass(BT_OBC%pass_uv, BT_OBC%ubt_outer, BT_OBC%vbt_outer, BT_Domain)
4049-
call create_group_pass(BT_OBC%pass_uhvh, BT_OBC%uhbt, BT_OBC%vhbt, BT_Domain)
4050-
call create_group_pass(BT_OBC%pass_eta_outer, BT_OBC%SSH_outer_u, BT_OBC%SSH_outer_v, BT_Domain,To_All+Scalar_Pair)
4051-
call create_group_pass(BT_OBC%pass_h, BT_OBC%dZ_u, BT_OBC%dZ_v, BT_Domain,To_All+Scalar_Pair)
4052-
call create_group_pass(BT_OBC%pass_cg, BT_OBC%Cg_u, BT_OBC%Cg_v, BT_Domain,To_All+Scalar_Pair)
4053-
endif
4054-
40554044
if (BT_OBC%u_OBCs_on_PE) then
40564045
if (OBC%specified_u_BCs_exist_globally) then
40574046
do n = 1, OBC%number_of_segments
@@ -4158,10 +4147,8 @@ subroutine set_up_BT_OBC(OBC, eta, SpV_avg, BT_OBC, BT_Domain, G, GV, US, CS, MS
41584147
endif
41594148

41604149
call do_group_pass(BT_OBC%pass_uv, BT_Domain)
4161-
call do_group_pass(BT_OBC%pass_uhvh, BT_Domain)
4162-
call do_group_pass(BT_OBC%pass_eta_outer, BT_Domain)
4163-
call do_group_pass(BT_OBC%pass_h, BT_Domain)
4164-
call do_group_pass(BT_OBC%pass_cg, BT_Domain)
4150+
if (OBC%Flather_u_BCs_exist_globally .or. OBC%Flather_v_BCs_exist_globally) &
4151+
call do_group_pass(BT_OBC%scalar_pass, BT_Domain)
41654152

41664153
end subroutine set_up_BT_OBC
41674154

@@ -4174,21 +4161,18 @@ subroutine destroy_BT_OBC(BT_OBC)
41744161
if (allocated(BT_OBC%u_OBC_type)) deallocate(BT_OBC%u_OBC_type)
41754162
if (allocated(BT_OBC%v_OBC_type)) deallocate(BT_OBC%v_OBC_type)
41764163

4177-
if (BT_OBC%is_alloced) then
4178-
deallocate(BT_OBC%Cg_u)
4179-
deallocate(BT_OBC%dZ_u)
4180-
deallocate(BT_OBC%uhbt)
4181-
deallocate(BT_OBC%ubt_outer)
4182-
deallocate(BT_OBC%SSH_outer_u)
4164+
if (allocated(BT_OBC%Cg_u)) deallocate(BT_OBC%Cg_u)
4165+
if (allocated(BT_OBC%dZ_u)) deallocate(BT_OBC%dZ_u)
4166+
if (allocated(BT_OBC%uhbt)) deallocate(BT_OBC%uhbt)
4167+
if (allocated(BT_OBC%ubt_outer)) deallocate(BT_OBC%ubt_outer)
4168+
if (allocated(BT_OBC%SSH_outer_u)) deallocate(BT_OBC%SSH_outer_u)
41834169

4184-
deallocate(BT_OBC%Cg_v)
4185-
deallocate(BT_OBC%dZ_v)
4186-
deallocate(BT_OBC%vhbt)
4187-
deallocate(BT_OBC%vbt_outer)
4188-
deallocate(BT_OBC%SSH_outer_v)
4170+
if (allocated(BT_OBC%Cg_v)) deallocate(BT_OBC%Cg_v)
4171+
if (allocated(BT_OBC%dZ_v)) deallocate(BT_OBC%dZ_v)
4172+
if (allocated(BT_OBC%vhbt)) deallocate(BT_OBC%vhbt)
4173+
if (allocated(BT_OBC%vbt_outer)) deallocate(BT_OBC%vbt_outer)
4174+
if (allocated(BT_OBC%SSH_outer_v)) deallocate(BT_OBC%SSH_outer_v)
41894175

4190-
BT_OBC%is_alloced = .false.
4191-
endif
41924176
end subroutine destroy_BT_OBC
41934177

41944178
!> btcalc calculates the barotropic velocities from the full velocity and
@@ -4465,7 +4449,7 @@ subroutine btcalc(h, G, GV, CS, h_u, h_v, may_use_default, OBC)
44654449
enddo
44664450
endif
44674451
else
4468-
call MOM_error(fatal, "btcalc encountered and OBC segment of indeterminate direction.")
4452+
call MOM_error(fatal, "btcalc encountered an OBC segment of indeterminate direction.")
44694453
endif
44704454
enddo ; endif
44714455

@@ -5652,26 +5636,6 @@ subroutine barotropic_init(u, v, h, Time, G, GV, US, param_file, diag, CS, &
56525636
CS%IareaT_OBCmask(i,j) = CS%IareaT(i,j)
56535637
enddo ; enddo
56545638

5655-
if (associated(OBC)) then
5656-
call initialize_BT_OBC(OBC, CS%BT_OBC, G, CS)
5657-
endif
5658-
5659-
! Update IareaT_OBCmask so that nothing changes outside of the OBC (problem for interior OBCs only)
5660-
if (associated(OBC) .and. (.not.CS%exterior_OBC_bug)) then
5661-
if (CS%BT_OBC%u_OBCs_on_PE) then
5662-
do j=jsd,jed ; do i=isd,ied
5663-
if (CS%BT_OBC%u_OBC_type(I-1,j) > 0) CS%IareaT_OBCmask(i,j) = 0.0 ! OBC_DIRECTION_E
5664-
if (CS%BT_OBC%u_OBC_type(I,j) < 0) CS%IareaT_OBCmask(i,j) = 0.0 ! OBC_DIRECTION_W
5665-
enddo ; enddo
5666-
endif
5667-
if (CS%BT_OBC%v_OBCs_on_PE) then
5668-
do j=jsd,jed ; do i=isd,ied
5669-
if (CS%BT_OBC%v_OBC_type(i,J-1) > 0) CS%IareaT_OBCmask(i,j) = 0.0 ! OBC_DIRECTION_N
5670-
if (CS%BT_OBC%v_OBC_type(i,J) < 0) CS%IareaT_OBCmask(i,j) = 0.0 ! OBC_DIRECTION_S
5671-
enddo ; enddo
5672-
endif
5673-
endif
5674-
56755639
! Note: G%IdxCu & G%IdyCv may be valid for a smaller extent than CS%IdxCu & CS%IdyCv, even without
56765640
! wide halos.
56775641
do j=G%jsd,G%jed ; do I=G%IsdB,G%IedB
@@ -5680,8 +5644,28 @@ subroutine barotropic_init(u, v, h, Time, G, GV, US, param_file, diag, CS, &
56805644
do J=G%JsdB,G%JedB ; do i=G%isd,G%ied
56815645
CS%IdyCv(i,J) = G%IdyCv(i,J) ; CS%dx_Cv(i,J) = G%dx_Cv(i,J)
56825646
enddo ; enddo
5683-
! Set masks to avoid changing velocities at OBC points.
5647+
56845648
if (associated(OBC)) then
5649+
! Set up information about the location and nature of the open boundary condition points.
5650+
call initialize_BT_OBC(OBC, CS%BT_OBC, G, CS)
5651+
5652+
! Update IareaT_OBCmask so that nothing changes outside of the OBC (problem for interior OBCs only)
5653+
if (.not.CS%exterior_OBC_bug) then
5654+
if (CS%BT_OBC%u_OBCs_on_PE) then
5655+
do j=jsd,jed ; do i=isd,ied
5656+
if (CS%BT_OBC%u_OBC_type(I-1,j) > 0) CS%IareaT_OBCmask(i,j) = 0.0 ! OBC_DIRECTION_E
5657+
if (CS%BT_OBC%u_OBC_type(I,j) < 0) CS%IareaT_OBCmask(i,j) = 0.0 ! OBC_DIRECTION_W
5658+
enddo ; enddo
5659+
endif
5660+
if (CS%BT_OBC%v_OBCs_on_PE) then
5661+
do j=jsd,jed ; do i=isd,ied
5662+
if (CS%BT_OBC%v_OBC_type(i,J-1) > 0) CS%IareaT_OBCmask(i,j) = 0.0 ! OBC_DIRECTION_N
5663+
if (CS%BT_OBC%v_OBC_type(i,J) < 0) CS%IareaT_OBCmask(i,j) = 0.0 ! OBC_DIRECTION_S
5664+
enddo ; enddo
5665+
endif
5666+
endif
5667+
5668+
! Set masks to avoid changing velocities at OBC points.
56855669
if (CS%BT_OBC%u_OBCs_on_PE) then
56865670
do j=G%jsd,G%jed ; do I=G%IsdB,G%IedB ; if (CS%BT_OBC%u_OBC_type(I,j) /= 0) then
56875671
CS%OBCmask_u(I,j) = 0.0 ; CS%IdxCu(I,j) = 0.0
@@ -5692,7 +5676,14 @@ subroutine barotropic_init(u, v, h, Time, G, GV, US, param_file, diag, CS, &
56925676
CS%OBCmask_v(i,J) = 0.0 ; CS%IdyCv(i,J) = 0.0
56935677
endif ; enddo ; enddo
56945678
endif
5679+
5680+
CS%integral_OBCs = CS%integral_BT_cont .and. open_boundary_query(OBC, apply_open_OBC=.true.)
5681+
else ! There are no OBC points anywhere.
5682+
CS%BT_OBC%u_OBCs_on_PE = .false.
5683+
CS%BT_OBC%v_OBCs_on_PE = .false.
5684+
CS%integral_OBCs = .false.
56955685
endif
5686+
56965687
call create_group_pass(pass_static_data, CS%IareaT, CS%BT_domain, To_All)
56975688
call create_group_pass(pass_static_data, CS%bathyT, CS%BT_domain, To_All)
56985689
call create_group_pass(pass_static_data, CS%IareaT_OBCmask, CS%BT_domain, To_All)

0 commit comments

Comments
 (0)