MOM6
MOM_boundary_update.F90
Go to the documentation of this file.
1 ! This file is part of MOM6. See LICENSE.md for the license.
2 !> Controls where open boundary conditions are applied
4 
5 ! This file is part of MOM6. See LICENSE.md for the license.
6 
7 use mom_cpu_clock, only : cpu_clock_id, cpu_clock_begin, cpu_clock_end, clock_routine
8 use mom_diag_mediator, only : time_type
9 use mom_error_handler, only : mom_mesg, mom_error, fatal, warning
11 use mom_grid, only : ocean_grid_type
25 
26 implicit none ; private
27 
28 #include <MOM_memory.h>
29 
31 public update_obc_data
32 
33 type, public :: update_obc_cs ; private
34  logical :: use_files = .false.
35  logical :: use_kelvin = .false.
36  logical :: use_tidal_bay = .false.
37  logical :: use_shelfwave = .false.
38  type(file_obc_cs), pointer :: file_obc_csp => null()
39  type(kelvin_obc_cs), pointer :: kelvin_obc_csp => null()
40  type(tidal_bay_obc_cs), pointer :: tidal_bay_obc_csp => null()
41  type(shelfwave_obc_cs), pointer :: shelfwave_obc_csp => null()
42 end type update_obc_cs
43 
44 integer :: id_clock_pass
45 
46 character(len=40) :: mdl = "MOM_boundary_update" ! This module's name.
47 ! This include declares and sets the variable "version".
48 #include "version_variable.h"
49 
50 contains
51 
52 !> The following subroutines and associated definitions provide the
53 !! machinery to register and call the subroutines that initialize
54 !! open boundary conditions.
55 subroutine call_obc_register(param_file, CS, OBC)
56  type(param_file_type), intent(in) :: param_file !< Parameter file to parse
57  type(update_obc_cs), pointer :: CS !< Control structure for OBCs
58  type(ocean_obc_type), pointer :: OBC !< Open boundary structure
59  character(len=40) :: mdl = "MOM_boundary_update" ! This module's name.
60 
61  if (associated(cs)) then
62  call mom_error(warning, "call_OBC_register called with an associated "// &
63  "control structure.")
64  return
65  else ; allocate(cs) ; endif
66 
67  call log_version(param_file, mdl, version, "")
68 
69  call get_param(param_file, mdl, "USE_FILE_OBC", cs%use_files, &
70  "If true, use external files for the open boundary.", &
71  default=.false.)
72  call get_param(param_file, mdl, "USE_TIDAL_BAY_OBC", cs%use_tidal_bay, &
73  "If true, use the tidal_bay open boundary.", &
74  default=.false.)
75  call get_param(param_file, mdl, "USE_KELVIN_WAVE_OBC", cs%use_Kelvin, &
76  "If true, use the Kelvin wave open boundary.", &
77  default=.false.)
78  call get_param(param_file, mdl, "USE_SHELFWAVE_OBC", cs%use_shelfwave, &
79  "If true, use the shelfwave open boundary.", &
80  default=.false.)
81 
82  if (cs%use_files) cs%use_files = &
83  register_file_obc(param_file, cs%file_OBC_CSp, &
84  obc%OBC_Reg)
85  if (cs%use_tidal_bay) cs%use_tidal_bay = &
86  register_tidal_bay_obc(param_file, cs%tidal_bay_OBC_CSp, &
87  obc%OBC_Reg)
88  if (cs%use_Kelvin) cs%use_Kelvin = &
89  register_kelvin_obc(param_file, cs%Kelvin_OBC_CSp, &
90  obc%OBC_Reg)
91  if (cs%use_shelfwave) cs%use_shelfwave = &
92  register_shelfwave_obc(param_file, cs%shelfwave_OBC_CSp, &
93  obc%OBC_Reg)
94 
95 end subroutine call_obc_register
96 
97 !> Calls appropriate routine to update the open boundary conditions.
98 subroutine update_obc_data(OBC, G, GV, tv, h, CS, Time)
99  type(ocean_grid_type), intent(in) :: G !< Ocean grid structure
100  type(verticalgrid_type), intent(in) :: GV !< Ocean vertical grid structure
101  type(thermo_var_ptrs), intent(in) :: tv !< Thermodynamics structure
102  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(inout) :: h !< layer thickness
103  type(ocean_obc_type), pointer :: OBC !< Open boundary structure
104  type(update_obc_cs), pointer :: CS !< Control structure for OBCs
105  type(time_type), intent(in) :: Time !< Model time
106  ! Local variables
107  logical :: read_OBC_eta = .false.
108  logical :: read_OBC_uv = .false.
109  logical :: read_OBC_TS = .false.
110  integer :: i, j, k, itt, is, ie, js, je, isd, ied, jsd, jed, nz
111  integer :: isd_off, jsd_off
112  integer :: IsdB, IedB, JsdB, JedB
113  character(len=40) :: mdl = "update_OBC_data" ! This subroutine's name.
114  character(len=200) :: filename, OBC_file, inputdir ! Strings for file/path
115 
116  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
117  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
118  isdb = g%IsdB ; iedb = g%IedB ; jsdb = g%JsdB ; jedb = g%JedB
119 
120 ! Something here... with CS%file_OBC_CSp?
121 ! if (CS%use_files) &
122 ! call update_OBC_segment_data(G, GV, OBC, tv, h, Time)
123  if (cs%use_tidal_bay) &
124  call tidal_bay_set_obc_data(obc, cs%tidal_bay_OBC_CSp, g, h, time)
125  if (cs%use_Kelvin) &
126  call kelvin_set_obc_data(obc, cs%Kelvin_OBC_CSp, g, h, time)
127  if (cs%use_shelfwave) &
128  call shelfwave_set_obc_data(obc, cs%shelfwave_OBC_CSp, g, h, time)
129  if (obc%needs_IO_for_data) &
130  call update_obc_segment_data(g, gv, obc, tv, h, time)
131 
132 end subroutine update_obc_data
133 
134 !> Clean up the OBC registry.
135 subroutine obc_register_end(CS)
136  type(update_obc_cs), pointer :: CS !< Control structure for OBCs
137 
138  if (cs%use_files) call file_obc_end(cs%file_OBC_CSp)
139  if (cs%use_tidal_bay) call tidal_bay_obc_end(cs%tidal_bay_OBC_CSp)
140  if (cs%use_Kelvin) call kelvin_obc_end(cs%Kelvin_OBC_CSp)
141 
142  if (associated(cs)) deallocate(cs)
143 end subroutine obc_register_end
144 
145 !> \namespace mom_boundary_update
146 !! This module updates the open boundary arrays when time-varying.
147 !! It caused a circular dependency with the tidal_bay setup when
148 !! MOM_open_boundary.
149 !!
150 !! A small fragment of the grid is shown below:
151 !!
152 !! j+1 x ^ x ^ x At x: q, CoriolisBu
153 !! j+1 > o > o > At ^: v, tauy
154 !! j x ^ x ^ x At >: u, taux
155 !! j > o > o > At o: h, bathyT, buoy, tr, T, S, Rml, ustar
156 !! j-1 x ^ x ^ x
157 !! i-1 i i+1 At x & ^:
158 !! i i+1 At > & o:
159 !!
160 !! The boundaries always run through q grid points (x).
161 
162 end module mom_boundary_update
subroutine, public kelvin_set_obc_data(OBC, CS, G, h, Time)
This subroutine sets the properties of flow at open boundary conditions.
subroutine, public tidal_bay_set_obc_data(OBC, CS, G, h, Time)
This subroutine sets the properties of flow at open boundary conditions.
subroutine, public shelfwave_obc_end(CS)
Clean up the shelfwave OBC from registry.
subroutine, public file_obc_end(CS)
Clean up the file OBC from registry.
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
Controls where open boundary conditions are applied.
Provides the ocean grid type.
Definition: MOM_grid.F90:2
subroutine, public kelvin_obc_end(CS)
Clean up the Kelvin wave OBC from registry.
subroutine, public shelfwave_set_obc_data(OBC, CS, G, h, Time)
This subroutine sets the properties of flow at open boundary conditions.
The module configures the model for the "tidal_bay" experiment. tidal_bay = Tidally resonant bay from...
logical function, public register_file_obc(param_file, CS, OBC_Reg)
Add file to OBC registry.
subroutine, public update_obc_segment_data(G, GV, OBC, tv, h, Time)
Update the OBC values on the segments.
This module contains the tracer_registry_type and the subroutines that handle registration of tracers...
The module configures the model for the idealized shelfwave test case.
Type to carry basic OBC information needed for updating values.
Type to carry basic tracer information.
subroutine, public add_tracer_obc_values(name, Reg, OBC_inflow, OBC_in_u, OBC_in_v)
This subroutine adds open boundary condition concentrations for a tracer that has previously been reg...
logical function, public register_shelfwave_obc(param_file, CS, OBC_Reg)
Add shelfwave to OBC registry.
subroutine, public update_obc_data(OBC, G, GV, tv, h, CS, Time)
Calls appropriate routine to update the open boundary conditions.
subroutine, public mom_mesg(message, verb, all_print)
Control structure for tidal bay open boundaries.
logical function, public register_kelvin_obc(param_file, CS, OBC_Reg)
Add Kelvin wave to OBC registry.
Control structure for open boundaries that read from files. Probably lots to update here...
Control structure for shelfwave open boundaries.
Control structure for Kelvin wave open boundaries.
The thermo_var_ptrs structure contains pointers to an assortment of thermodynamic fields that may be ...
subroutine, public tidal_bay_obc_end(CS)
Clean up the tidal bay OBC from registry.
subroutine, public obc_register_end(CS)
Clean up the OBC registry.
Controls where open boundary conditions are applied.
subroutine, public call_obc_register(param_file, CS, OBC)
The following subroutines and associated definitions provide the machinery to register and call the s...
subroutine, public mom_error(level, message, all_print)
logical function, public register_tidal_bay_obc(param_file, CS, OBC_Reg)
Add tidal bay to OBC registry.