Skip to content

Commit

Permalink
Merge branch 'user/ksh/bad_segs' into dev/master
Browse files Browse the repository at this point in the history
  • Loading branch information
adcroft committed Jan 13, 2017
2 parents 5147edc + ec30811 commit 2a928ee
Show file tree
Hide file tree
Showing 8 changed files with 866 additions and 47 deletions.
4 changes: 2 additions & 2 deletions src/core/MOM_dynamics_legacy_split.F90
Original file line number Diff line number Diff line change
Expand Up @@ -742,7 +742,7 @@ subroutine step_MOM_dyn_legacy_split(u, v, h, tv, visc, &

if (associated(CS%OBC)) then
call radiation_open_bdry_conds(CS%OBC, u_av, u_old_rad_OBC, v_av, &
v_old_rad_OBC, hp, h_old_rad_OBC, G)
v_old_rad_OBC, hp, h_old_rad_OBC, G, dt)
endif

! h_av = (h + hp)/2
Expand Down Expand Up @@ -1005,7 +1005,7 @@ subroutine step_MOM_dyn_legacy_split(u, v, h, tv, visc, &

if (associated(CS%OBC)) then
call radiation_open_bdry_conds(CS%OBC, u, u_old_rad_OBC, v, &
v_old_rad_OBC, h, h_old_rad_OBC, G)
v_old_rad_OBC, h, h_old_rad_OBC, G, dt)
endif

! h_av = (h_in + h_out)/2 . Going in to this line, h_av = h_in.
Expand Down
4 changes: 2 additions & 2 deletions src/core/MOM_dynamics_split_RK2.F90
Original file line number Diff line number Diff line change
Expand Up @@ -639,7 +639,7 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, &

if (associated(CS%OBC)) then
call radiation_open_bdry_conds(CS%OBC, u_av, u_old_rad_OBC, v_av, &
v_old_rad_OBC, hp, h_old_rad_OBC, G)
v_old_rad_OBC, hp, h_old_rad_OBC, G, dt)
endif

! h_av = (h + hp)/2
Expand Down Expand Up @@ -855,7 +855,7 @@ subroutine step_MOM_dyn_split_RK2(u, v, h, tv, visc, &

if (associated(CS%OBC)) then
call radiation_open_bdry_conds(CS%OBC, u, u_old_rad_OBC, v, &
v_old_rad_OBC, h, h_old_rad_OBC, G)
v_old_rad_OBC, h, h_old_rad_OBC, G, dt)
endif

! h_av = (h_in + h_out)/2 . Going in to this line, h_av = h_in.
Expand Down
861 changes: 823 additions & 38 deletions src/core/MOM_open_boundary.F90

Large diffs are not rendered by default.

4 changes: 0 additions & 4 deletions src/initialization/MOM_fixed_initialization.F90
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,6 @@ module MOM_fixed_initialization
use sloshing_initialization, only : sloshing_initialize_topography
use seamount_initialization, only : seamount_initialize_topography
use Phillips_initialization, only : Phillips_initialize_topography
use supercritical_initialization, only : supercritical_initialize_topography

use netcdf

Expand Down Expand Up @@ -91,7 +90,6 @@ subroutine MOM_initialize_fixed(G, OBC, PF, write_geom, output_dir)
case ("none")
case ("DOME") ! Avoid FATAL when using segments
case ("tidal_bay") ; !Using segments now
case ("supercritical") ; !Using segments now
case ("USER") ! Avoid FATAL when using segments
case default ; call MOM_error(FATAL, "MOM_initialize_fixed: "// &
"The open boundary positions specified by OBC_CONFIG="//&
Expand Down Expand Up @@ -207,7 +205,6 @@ subroutine MOM_initialize_topography(D, max_depth, G, PF)
" \t DOME2D - use a shelf and slope configuration for the \n"//&
" \t\t DOME2D gravity current/overflow test case. \n"//&
" \t seamount - Gaussian bump for spontaneous motion test case.\n"//&
" \t supercritical - flat but with 8.95 degree land mask.\n"//&
" \t Phillips - ACC-like idealized topography used in the Phillips config.\n"//&
" \t USER - call a user modified routine.", &
fail_if_missing=.true.)
Expand All @@ -225,7 +222,6 @@ subroutine MOM_initialize_topography(D, max_depth, G, PF)
case ("sloshing"); call sloshing_initialize_topography(D, G, PF, max_depth)
case ("seamount"); call seamount_initialize_topography(D, G, PF, max_depth)
case ("Phillips"); call Phillips_initialize_topography(D, G, PF, max_depth)
case ("supercritical"); call supercritical_initialize_topography(D, G, PF, max_depth)
case ("USER"); call user_initialize_topography(D, G, PF, max_depth)
case default ; call MOM_error(FATAL,"MOM_initialize_topography: "// &
"Unrecognized topography setup '"//trim(config)//"'")
Expand Down
1 change: 1 addition & 0 deletions src/initialization/MOM_state_initialization.F90
Original file line number Diff line number Diff line change
Expand Up @@ -449,6 +449,7 @@ subroutine MOM_initialize_state(u, v, h, tv, Time, G, GV, PF, dirs, &
if (open_boundary_query(OBC, apply_specified_OBC=.true.)) then
if (trim(config) == "DOME") then
call DOME_set_OBC_data(OBC, tv, G, GV, PF, tracer_Reg)
OBC%update_OBC = .false.
elseif (trim(config) == "USER") then
call user_set_OBC_data(OBC, tv, G, PF, tracer_Reg)
elseif (.not. trim(config) == "none") then
Expand Down
20 changes: 20 additions & 0 deletions src/user/DOME_initialization.F90
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,7 @@ module DOME_initialization
use MOM_get_input, only : directories
use MOM_grid, only : ocean_grid_type
use MOM_open_boundary, only : ocean_OBC_type, OBC_NONE, OBC_SIMPLE
use MOM_open_boundary, only : OBC_segment_type
use MOM_tracer_registry, only : tracer_registry_type, add_tracer_OBC_values
use MOM_variables, only : thermo_var_ptrs
use MOM_verticalGrid, only : verticalGrid_type
Expand Down Expand Up @@ -269,6 +270,7 @@ subroutine DOME_set_OBC_data(OBC, tv, G, GV, param_file, tr_Reg)
character(len=40) :: mod = "DOME_set_OBC_data" ! This subroutine's name.
integer :: i, j, k, itt, is, ie, js, je, isd, ied, jsd, jed, nz
integer :: IsdB, IedB, JsdB, JedB
type(OBC_segment_type), pointer :: segment

is = G%isc ; ie = G%iec ; js = G%jsc ; je = G%jec ; nz = G%ke
isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed
Expand All @@ -288,6 +290,13 @@ subroutine DOME_set_OBC_data(OBC, tv, G, GV, param_file, tr_Reg)
Def_Rad = sqrt(D_edge*g_prime_tot) / (1.0e-4*1000.0)
tr_0 = (-D_edge*sqrt(D_edge*g_prime_tot)*0.5e3*Def_Rad) * GV%m_to_H

if (OBC%number_of_segments .ne. 1) then
print *, 'Error in DOME OBC segment setup'
return !!! Need a better error message here
endif
segment => OBC%OBC_segment_number(1)
if (.not. segment%on_pe) return

do k=1,nz
rst = -1.0
if (k>1) rst = -1.0 + (real(k-1)-0.5)/real(nz-1)
Expand All @@ -305,6 +314,7 @@ subroutine DOME_set_OBC_data(OBC, tv, G, GV, param_file, tr_Reg)
(2.0 - Ri_trans))
if (k == nz) tr_k = tr_k + tr_0 * (2.0/(Ri_trans*(2.0+Ri_trans))) * &
log((2.0+Ri_trans)/(2.0-Ri_trans))
! Old way
do J=JsdB,JedB ; do i=isd,ied
if (OBC%OBC_segment_v(i,J) /= OBC_NONE) then
! This needs to be unneccesarily complicated without symmetric memory.
Expand All @@ -317,6 +327,16 @@ subroutine DOME_set_OBC_data(OBC, tv, G, GV, param_file, tr_Reg)
OBC%vh(i,J,k) = 0.0 ; OBC%v(i,J,k) = 0.0
endif
enddo ; enddo
! New way
isd = segment%HI%isd ; ied = segment%HI%ied
JsdB = segment%HI%JsdB ; JedB = segment%HI%JedB
print *, 'DOME segment indices', isd, ied, JsdB, JedB
! do J=JsdB,JedB ; do i=isd,ied
! lon_im1 = 2.0*G%geoLonCv(i,J) - G%geoLonBu(I,J)
! segment%normal_trans(i,J,k) = tr_k * (exp(-2.0*(lon_im1 - 1000.0)/Def_Rad) -&
! exp(-2.0*(G%geoLonBu(I,J) - 1000.0)/Def_Rad))
! segment%normal_vel(i,J,k) = v_k * exp(-2.0*(G%geoLonCv(i,J) - 1000.0)/Def_Rad)
! enddo ; enddo
enddo

! The inflow values of temperature and salinity also need to be set here if
Expand Down
3 changes: 3 additions & 0 deletions src/user/supercritical_initialization.F90
Original file line number Diff line number Diff line change
Expand Up @@ -110,6 +110,9 @@ subroutine supercritical_set_OBC_data(OBC, G, param_file)

allocate(OBC%u(G%IsdB:G%IedB,G%jsd:G%jed,G%ke)) ; OBC%u(:,:,:) = 0.0
allocate(OBC%uh(G%IsdB:G%IedB,G%jsd:G%jed,G%ke)) ; OBC%uh(:,:,:) = 0.0
if (.not.associated(OBC%ubt_outer)) then
allocate(OBC%ubt_outer(G%IsdB:G%IedB,G%jsd:G%jed)) ; OBC%ubt_outer(:,:) = 0.0
endif

do j=G%jsd,G%jed ; do I=G%IsdB,G%IedB
if (OBC%OBC_segment_u(I,j)>0) then
Expand Down
16 changes: 15 additions & 1 deletion src/user/tidal_bay_initialization.F90
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,7 @@ module tidal_bay_initialization
use MOM_file_parser, only : get_param, log_version, param_file_type
use MOM_grid, only : ocean_grid_type
use MOM_open_boundary, only : ocean_OBC_type, OBC_NONE
use MOM_open_boundary, only : OBC_segment_type
use MOM_verticalGrid, only : verticalGrid_type
use MOM_time_manager, only : time_type, set_time, time_type_to_real

Expand All @@ -49,8 +50,9 @@ subroutine tidal_bay_set_OBC_data(OBC, G, h, Time)
real :: my_area, my_flux
real :: PI
character(len=40) :: mod = "tidal_bay_set_OBC_data" ! This subroutine's name.
integer :: i, j, k, itt, is, ie, js, je, isd, ied, jsd, jed, nz
integer :: i, j, k, itt, is, ie, js, je, isd, ied, jsd, jed, nz, n
integer :: IsdB, IedB, JsdB, JedB
type(OBC_segment_type), pointer :: segment

is = G%isc ; ie = G%iec ; js = G%jsc ; je = G%jec ; nz = G%ke
isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed
Expand All @@ -75,6 +77,7 @@ subroutine tidal_bay_set_OBC_data(OBC, G, h, Time)
enddo ; enddo
my_flux = -tide_flow*SIN(2.0*PI*time_sec/(12.0*3600.0))

! Old way
do j=jsd,jed ; do I=IsdB,IedB
if (OBC%OBC_segment_u(I,j) /= OBC_NONE) then
OBC%eta_outer_u(I,j) = cff
Expand All @@ -88,6 +91,17 @@ subroutine tidal_bay_set_OBC_data(OBC, G, h, Time)
endif
enddo ; enddo

! New way
! do n = 1, OBC%number_of_segments
! segment => OBC%OBC_segment_number(n)

! if (.not. segment%on_pe) cycle ! continue to next segment if not in computational domain

! segment%normal_vel_bt(:,:) = my_flux/my_area
! segment%eta(:,:) = cff

! enddo ! end segment loop

end subroutine tidal_bay_set_OBC_data

!> \class tidal_bay_Initialization
Expand Down

0 comments on commit 2a928ee

Please sign in to comment.