Skip to content

Commit 8c97707

Browse files
kshedstromHallberg-NOAA
authored andcommitted
Response to comments on h_reservoirs PR.
1 parent 2918a9d commit 8c97707

File tree

8 files changed

+62
-77
lines changed

8 files changed

+62
-77
lines changed

src/core/MOM_continuity_PPM.F90

Lines changed: 49 additions & 54 deletions
Original file line numberDiff line numberDiff line change
@@ -2413,19 +2413,12 @@ subroutine PPM_reconstruction_x(h_in, h_W, h_E, G, LB, h_min, monotonic, simple_
24132413
if (segment%direction == OBC_DIRECTION_E) then
24142414
I=segment%HI%IsdB
24152415
if (associated(segment%h_Reg)) then
2416-
if (allocated(segment%h_Reg%h_res)) then
2417-
do j=segment%HI%jsd,segment%HI%jed
2418-
h_W(i+1,j) = segment%h_Reg%h_res(i,j,k)
2419-
h_E(i+1,j) = segment%h_Reg%h_res(i,j,k)
2420-
h_W(i,j) = segment%h_Reg%h_res(i,j,k)
2421-
h_E(i,j) = segment%h_Reg%h_res(i,j,k)
2422-
enddo
2423-
else
2424-
write(mesg,'("In MOM_continuity_PPM, PPM_reconstruction_y called with ", &
2425-
& "badly configured h_res.")') &
2426-
stencil + max(G%jsd-jsl,jel-G%jed)
2427-
call MOM_error(FATAL,mesg)
2428-
endif
2416+
do j=segment%HI%jsd,segment%HI%jed
2417+
h_W(i+1,j) = segment%h_Reg%h_res(i,j,k)
2418+
h_E(i+1,j) = segment%h_Reg%h_res(i,j,k)
2419+
h_W(i,j) = segment%h_Reg%h_res(i,j,k)
2420+
h_E(i,j) = segment%h_Reg%h_res(i,j,k)
2421+
enddo
24292422
else
24302423
do j=segment%HI%jsd,segment%HI%jed
24312424
h_W(i+1,j) = h_in(i,j)
@@ -2437,19 +2430,12 @@ subroutine PPM_reconstruction_x(h_in, h_W, h_E, G, LB, h_min, monotonic, simple_
24372430
elseif (segment%direction == OBC_DIRECTION_W) then
24382431
I=segment%HI%IsdB
24392432
if (associated(segment%h_Reg)) then
2440-
if (allocated(segment%h_Reg%h_res)) then
2441-
do j=segment%HI%jsd,segment%HI%jed
2442-
h_W(i,j) = segment%h_Reg%h_res(i,j,k)
2443-
h_E(i,j) = segment%h_Reg%h_res(i,j,k)
2444-
h_W(i+1,j) = segment%h_Reg%h_res(i,j,k)
2445-
h_E(i+1,j) = segment%h_Reg%h_res(i,j,k)
2446-
enddo
2447-
else
2448-
write(mesg,'("In MOM_continuity_PPM, PPM_reconstruction_y called with ", &
2449-
& "badly configured h_res.")') &
2450-
stencil + max(G%jsd-jsl,jel-G%jed)
2451-
call MOM_error(FATAL,mesg)
2452-
endif
2433+
do j=segment%HI%jsd,segment%HI%jed
2434+
h_W(i,j) = segment%h_Reg%h_res(i,j,k)
2435+
h_E(i,j) = segment%h_Reg%h_res(i,j,k)
2436+
h_W(i+1,j) = segment%h_Reg%h_res(i,j,k)
2437+
h_E(i+1,j) = segment%h_Reg%h_res(i,j,k)
2438+
enddo
24532439
else
24542440
do j=segment%HI%jsd,segment%HI%jed
24552441
h_W(i,j) = h_in(i+1,j)
@@ -2579,19 +2565,12 @@ subroutine PPM_reconstruction_y(h_in, h_S, h_N, G, LB, h_min, monotonic, simple_
25792565
if (segment%direction == OBC_DIRECTION_N) then
25802566
J=segment%HI%JsdB
25812567
if (associated(segment%h_Reg)) then
2582-
if (allocated(segment%h_Reg%h_res)) then
2583-
do i=segment%HI%isd,segment%HI%ied
2584-
h_S(i,j+1) = segment%h_Reg%h_res(i,j,k)
2585-
h_N(i,j+1) = segment%h_Reg%h_res(i,j,k)
2586-
h_S(i,j) = segment%h_Reg%h_res(i,j,k)
2587-
h_N(i,j) = segment%h_Reg%h_res(i,j,k)
2588-
enddo
2589-
else
2590-
write(mesg,'("In MOM_continuity_PPM, PPM_reconstruction_y called with ", &
2591-
& "badly configured h_res.")') &
2592-
stencil + max(G%jsd-jsl,jel-G%jed)
2593-
call MOM_error(FATAL,mesg)
2594-
endif
2568+
do i=segment%HI%isd,segment%HI%ied
2569+
h_S(i,j+1) = segment%h_Reg%h_res(i,j,k)
2570+
h_N(i,j+1) = segment%h_Reg%h_res(i,j,k)
2571+
h_S(i,j) = segment%h_Reg%h_res(i,j,k)
2572+
h_N(i,j) = segment%h_Reg%h_res(i,j,k)
2573+
enddo
25952574
else
25962575
do i=segment%HI%isd,segment%HI%ied
25972576
h_S(i,j+1) = h_in(i,j)
@@ -2603,19 +2582,12 @@ subroutine PPM_reconstruction_y(h_in, h_S, h_N, G, LB, h_min, monotonic, simple_
26032582
elseif (segment%direction == OBC_DIRECTION_S) then
26042583
J=segment%HI%JsdB
26052584
if (associated(segment%h_Reg)) then
2606-
if (allocated(segment%h_Reg%h_res)) then
2607-
do i=segment%HI%isd,segment%HI%ied
2608-
h_S(i,j) = segment%h_Reg%h_res(i,j,k)
2609-
h_N(i,j) = segment%h_Reg%h_res(i,j,k)
2610-
h_S(i,j+1) = segment%h_Reg%h_res(i,j,k)
2611-
h_N(i,j+1) = segment%h_Reg%h_res(i,j,k)
2612-
enddo
2613-
else
2614-
write(mesg,'("In MOM_continuity_PPM, PPM_reconstruction_y called with ", &
2615-
& "badly configured h_res.")') &
2616-
stencil + max(G%jsd-jsl,jel-G%jed)
2617-
call MOM_error(FATAL,mesg)
2618-
endif
2585+
do i=segment%HI%isd,segment%HI%ied
2586+
h_S(i,j) = segment%h_Reg%h_res(i,j,k)
2587+
h_N(i,j) = segment%h_Reg%h_res(i,j,k)
2588+
h_S(i,j+1) = segment%h_Reg%h_res(i,j,k)
2589+
h_N(i,j+1) = segment%h_Reg%h_res(i,j,k)
2590+
enddo
26192591
else
26202592
do i=segment%HI%isd,segment%HI%ied
26212593
h_S(i,j) = h_in(i,j+1)
@@ -2737,23 +2709,33 @@ function ratio_max(a, b, maxrat) result(ratio)
27372709
end function ratio_max
27382710

27392711
!> Initializes continuity_ppm_cs
2740-
subroutine continuity_PPM_init(Time, G, GV, US, param_file, diag, CS)
2712+
subroutine continuity_PPM_init(Time, G, GV, US, param_file, diag, CS, OBC)
27412713
type(time_type), target, intent(in) :: Time !< The current model time.
27422714
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
27432715
type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure.
2744-
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
2716+
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
27452717
type(param_file_type), intent(in) :: param_file !< A structure indicating
27462718
!! the open file to parse for model parameter values.
27472719
type(diag_ctrl), target, intent(inout) :: diag !< A structure that is used to
27482720
!! regulate diagnostic output.
27492721
type(continuity_PPM_CS), intent(inout) :: CS !< Module's control structure.
2722+
type(ocean_OBC_type), pointer :: OBC !< Open boundaries control structure.
2723+
logical :: local_open_BC
2724+
type(OBC_segment_type), pointer :: segment => NULL()
2725+
integer :: n
27502726

27512727
!> This include declares and sets the variable "version".
27522728
# include "version_variable.h"
27532729
character(len=40) :: mdl = "MOM_continuity_PPM" ! This module's name.
2730+
character(len=256) :: mesg
27542731

27552732
CS%initialized = .true.
27562733

2734+
local_open_BC = .false.
2735+
if (associated(OBC)) then
2736+
local_open_BC = OBC%open_u_BCs_exist_globally
2737+
endif
2738+
27572739
! Read all relevant parameters and write them to the model log.
27582740
call log_version(param_file, mdl, version, "")
27592741
call get_param(param_file, mdl, "MONOTONIC_CONTINUITY", CS%monotonic, &
@@ -2817,6 +2799,19 @@ subroutine continuity_PPM_init(Time, G, GV, US, param_file, diag, CS)
28172799
id_clock_update = cpu_clock_id('(Ocean continuity update)', grain=CLOCK_ROUTINE)
28182800
id_clock_correct = cpu_clock_id('(Ocean continuity correction)', grain=CLOCK_ROUTINE)
28192801

2802+
if (local_open_BC) then
2803+
do n=1, OBC%number_of_segments
2804+
segment => OBC%segment(n)
2805+
if (associated(segment%h_Reg)) then
2806+
if (.not. allocated(segment%h_Reg%h_res)) then
2807+
write(mesg,'("In MOM_continuity_PPM, continuity_PPM_init called with ", &
2808+
& "badly configured h_res.")')
2809+
call MOM_error(FATAL, mesg)
2810+
endif
2811+
endif
2812+
enddo
2813+
endif
2814+
28202815
end subroutine continuity_PPM_init
28212816

28222817
!> continuity_PPM_stencil returns the continuity solver stencil size

src/core/MOM_dynamics_split_RK2.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1569,7 +1569,7 @@ subroutine initialize_dyn_split_RK2(u, v, h, tv, uh, vh, eta, Time, G, GV, US, p
15691569

15701570
id_clock_pass_init = cpu_clock_id('(Ocean init message passing)', grain=CLOCK_ROUTINE)
15711571

1572-
call continuity_init(Time, G, GV, US, param_file, diag, CS%continuity_CSp)
1572+
call continuity_init(Time, G, GV, US, param_file, diag, CS%continuity_CSp, CS%OBC)
15731573
cont_stencil = continuity_stencil(CS%continuity_CSp)
15741574
call CoriolisAdv_init(Time, G, GV, US, param_file, diag, CS%ADp, CS%CoriolisAdv)
15751575
cor_stencil = CoriolisAdv_stencil(CS%CoriolisAdv)

src/core/MOM_dynamics_split_RK2b.F90

Lines changed: 1 addition & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -498,10 +498,6 @@ subroutine step_MOM_dyn_split_RK2b(u_av, v_av, h, tv, visc, Time_local, dt, forc
498498
call cpu_clock_end(id_clock_pass)
499499
!--- end set up for group halo pass
500500

501-
if (associated(CS%OBC)) then ; if (CS%OBC%update_OBC) then
502-
call update_OBC_data(CS%OBC, G, GV, US, tv, h, CS%update_OBC_CSp, Time_local)
503-
endif ; endif
504-
505501
! This calculates the transports and averaged thicknesses that will be used for the
506502
! predictor version of the Coriolis scheme.
507503
call cpu_clock_begin(id_clock_continuity)
@@ -1464,7 +1460,7 @@ subroutine initialize_dyn_split_RK2b(u, v, h, tv, uh, vh, eta, Time, G, GV, US,
14641460
! Accel_diag%u_accel_bt => CS%u_accel_bt ; Accel_diag%v_accel_bt => CS%v_accel_bt
14651461
! Accel_diag%u_av => CS%u_av ; Accel_diag%v_av => CS%v_av
14661462

1467-
call continuity_init(Time, G, GV, US, param_file, diag, CS%continuity_CSp)
1463+
call continuity_init(Time, G, GV, US, param_file, diag, CS%continuity_CSp, CS%OBC)
14681464
cont_stencil = continuity_stencil(CS%continuity_CSp)
14691465
call CoriolisAdv_init(Time, G, GV, US, param_file, diag, CS%ADp, CS%CoriolisAdv)
14701466
dyn_h_stencil = max(cont_stencil, CoriolisAdv_stencil(CS%CoriolisAdv))

src/core/MOM_dynamics_unsplit.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -683,7 +683,7 @@ subroutine initialize_dyn_unsplit(u, v, h, tv, Time, G, GV, US, param_file, diag
683683
Accel_diag%PFu => CS%PFu ; Accel_diag%PFv => CS%PFv
684684
Accel_diag%CAu => CS%CAu ; Accel_diag%CAv => CS%CAv
685685

686-
call continuity_init(Time, G, GV, US, param_file, diag, CS%continuity_CSp)
686+
call continuity_init(Time, G, GV, US, param_file, diag, CS%continuity_CSp, CS%OBC)
687687
cont_stencil = continuity_stencil(CS%continuity_CSp)
688688
call CoriolisAdv_init(Time, G, GV, US, param_file, diag, CS%ADp, CS%CoriolisAdv)
689689
dyn_h_stencil = max(cont_stencil, CoriolisAdv_stencil(CS%CoriolisAdv))

src/core/MOM_dynamics_unsplit_RK2.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -649,7 +649,7 @@ subroutine initialize_dyn_unsplit_RK2(u, v, h, tv, Time, G, GV, US, param_file,
649649
Accel_diag%PFu => CS%PFu ; Accel_diag%PFv => CS%PFv
650650
Accel_diag%CAu => CS%CAu ; Accel_diag%CAv => CS%CAv
651651

652-
call continuity_init(Time, G, GV, US, param_file, diag, CS%continuity_CSp)
652+
call continuity_init(Time, G, GV, US, param_file, diag, CS%continuity_CSp, CS%OBC)
653653
cont_stencil = continuity_stencil(CS%continuity_CSp)
654654
call CoriolisAdv_init(Time, G, GV, US, param_file, diag, CS%ADp, CS%CoriolisAdv)
655655
dyn_h_stencil = max(cont_stencil, CoriolisAdv_stencil(CS%CoriolisAdv))

src/core/MOM_open_boundary.F90

Lines changed: 5 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -2116,17 +2116,11 @@ subroutine open_boundary_halo_update(G, OBC)
21162116
enddo
21172117
endif
21182118
if (allocated(OBC%h_res_x) .and. allocated(OBC%h_res_y)) then
2119-
do m=1,OBC%ntr
2120-
call pass_vector(OBC%h_res_x(:,:,:), OBC%h_res_y(:,:,:), G%Domain, To_All+Scalar_Pair)
2121-
enddo
2119+
call pass_vector(OBC%h_res_x(:,:,:), OBC%h_res_y(:,:,:), G%Domain, To_All+Scalar_Pair)
21222120
elseif (allocated(OBC%h_res_x)) then
2123-
do m=1,OBC%ntr
2124-
call pass_var(OBC%h_res_x(:,:,:), G%Domain, position=EAST_FACE)
2125-
enddo
2121+
call pass_var(OBC%h_res_x(:,:,:), G%Domain, position=EAST_FACE)
21262122
elseif (allocated(OBC%h_res_y)) then
2127-
do m=1,OBC%ntr
2128-
call pass_var(OBC%h_res_y(:,:,:), G%Domain, position=NORTH_FACE)
2129-
enddo
2123+
call pass_var(OBC%h_res_y(:,:,:), G%Domain, position=NORTH_FACE)
21302124
endif
21312125

21322126
end subroutine open_boundary_halo_update
@@ -2442,8 +2436,8 @@ subroutine setup_OBC_thickness_reservoirs(G, GV, OBC, restart_CS)
24422436

24432437
! Local variables
24442438
type(OBC_segment_type), pointer :: segment => NULL()
2445-
real :: I_scale ! The inverse of the scaling factor for the tracers.
2446-
! For salinity the units would be [ppt S-1 ~> 1]
2439+
real :: I_scale ! The inverse of the scaling factor for the thicknesses.
2440+
! [m Z-1 ~> 1]
24472441
logical :: set_h_res_x, set_h_res_y
24482442
character(len=12) :: x_var_name, y_var_name
24492443
integer :: i, j, k, n

src/initialization/MOM_state_initialization.F90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -704,9 +704,6 @@ subroutine MOM_initialize_OBCs(h, tv, OBC, Time, G, GV, US, PF, restart_CS, trac
704704
endif
705705
endif
706706

707-
if (OBC%use_h_res) &
708-
call fill_thickness_segments(G, GV, US, OBC, h)
709-
710707
! This controls user code for setting open boundary data
711708
call get_param(PF, mdl, "OBC_USER_CONFIG", config, &
712709
"A string that sets how the user code is invoked to set open boundary data: \n"//&
@@ -746,6 +743,9 @@ subroutine MOM_initialize_OBCs(h, tv, OBC, Time, G, GV, US, PF, restart_CS, trac
746743
call qchksum(G%mask2dBu, 'MOM_initialize_OBCs: mask2dBu ', G%HI)
747744
endif
748745
if (debug_OBC) call open_boundary_test_extern_h(G, GV, OBC, h)
746+
747+
if (OBC%use_h_res) &
748+
call fill_thickness_segments(G, GV, US, OBC, h)
749749
endif
750750

751751
call callTree_leave('MOM_initialize_OBCs()')

src/parameterizations/vertical/MOM_diabatic_aux.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
!> Provides functions for some diabatic processes such as fraxil, brine rejection,
1+
!> Provides functions for some diabatic processes such as frazil, brine rejection,
22
!! tendency due to surface flux divergence.
33
module MOM_diabatic_aux
44

0 commit comments

Comments
 (0)