MOM6
user_shelf_init.F90
Go to the documentation of this file.
2 !***********************************************************************
3 !* GNU General Public License *
4 !* This file is a part of MOM. *
5 !* *
6 !* MOM is free software; you can redistribute it and/or modify it and *
7 !* are expected to follow the terms of the GNU General Public License *
8 !* as published by the Free Software Foundation; either version 2 of *
9 !* the License, or (at your option) any later version. *
10 !* *
11 !* MOM is distributed in the hope that it will be useful, but WITHOUT *
12 !* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY *
13 !* or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public *
14 !* License for more details. *
15 !* *
16 !* For the full text of the GNU General Public License, *
17 !* write to: Free Software Foundation, Inc., *
18 !* 675 Mass Ave, Cambridge, MA 02139, USA. *
19 !* or see: http://www.gnu.org/licenses/gpl.html *
20 !***********************************************************************
21 
22 !********+*********+*********+*********+*********+*********+*********+**
23 !* *
24 !* By Robert Hallberg, April 1994 - June 2002 *
25 !* *
26 !* This subroutine initializes the fields for the simulations. *
27 !* The one argument passed to initialize, Time, is set to the *
28 !* current time of the simulation. The fields which are initialized *
29 !* here are: *
30 !* u - Zonal velocity in m s-1. *
31 !* v - Meridional velocity in m s-1. *
32 !* h - Layer thickness in m. (Must be positive.) *
33 !* D - Basin depth in m. (Must be positive.) *
34 !* f - The Coriolis parameter, in s-1. *
35 !* g - The reduced gravity at each interface, in m s-2. *
36 !* Rlay - Layer potential density (coordinate variable) in kg m-3. *
37 !* If TEMPERATURE is defined: *
38 !* T - Temperature in C. *
39 !* S - Salinity in psu. *
40 !* If BULKMIXEDLAYER is defined: *
41 !* Rml - Mixed layer and buffer layer potential densities in *
42 !* units of kg m-3. *
43 !* If SPONGE is defined: *
44 !* A series of subroutine calls are made to set up the damping *
45 !* rates and reference profiles for all variables that are damped *
46 !* in the sponge. *
47 !* Any user provided tracer code is also first linked through this *
48 !* subroutine. *
49 !* *
50 !* Forcing-related fields (taux, tauy, buoy, ustar, etc.) are set *
51 !* in MOM_surface_forcing.F90. *
52 !* *
53 !* These variables are all set in the set of subroutines (in this *
54 !* file) USER_initialize_bottom_depth, USER_initialize_thickness, *
55 !* USER_initialize_velocity, USER_initialize_temperature_salinity, *
56 !* USER_initialize_mixed_layer_density, USER_initialize_sponges, *
57 !* USER_set_coord, and USER_set_ref_profile. *
58 !* *
59 !* The names of these subroutines should be self-explanatory. They *
60 !* start with "USER_" to indicate that they will likely have to be *
61 !* modified for each simulation to set the initial conditions and *
62 !* boundary conditions. Most of these take two arguments: an integer *
63 !* argument specifying whether the fields are to be calculated *
64 !* internally or read from a NetCDF file; and a string giving the *
65 !* path to that file. If the field is initialized internally, the *
66 !* path is ignored. *
67 !* *
68 !* Macros written all in capital letters are defined in MOM_memory.h.*
69 !* *
70 !* A small fragment of the grid is shown below: *
71 !* *
72 !* j+1 x ^ x ^ x At x: q, f *
73 !* j+1 > o > o > At ^: v, tauy *
74 !* j x ^ x ^ x At >: u, taux *
75 !* j > o > o > At o: h, D, buoy, tr, T, S, Rml, ustar *
76 !* j-1 x ^ x ^ x *
77 !* i-1 i i+1 At x & ^: *
78 !* i i+1 At > & o: *
79 !* *
80 !* The boundaries always run through q grid points (x). *
81 !* *
82 !********+*********+*********+*********+*********+*********+*********+**
83 
84 ! use MOM_domains, only : sum_across_PEs
87 use mom_grid, only : ocean_grid_type
88 use mom_time_manager, only : time_type, set_time, time_type_to_real
89 
90 use mpp_mod, only : mpp_pe, mpp_sync
91 ! use MOM_io, only : close_file, fieldtype, file_exists
92 ! use MOM_io, only : open_file, read_data, read_axis_data, SINGLE_FILE
93 ! use MOM_io, only : write_field, slasher, vardesc
94 implicit none ; private
95 
96 #include <MOM_memory.h>
97 
100 logical :: first_call = .true.
101 
102 type, public :: user_ice_shelf_cs ; private
103  real :: rho_ocean ! The ocean's typical density, in kg m-3.
104  real :: max_draft ! The maximum ocean draft of the ice shelf, in m.
105  real :: min_draft ! The minimum ocean draft of the ice shelf, in m.
106  real :: flat_shelf_width ! The range over which the shelf is min_draft thick.
107  real :: shelf_slope_scale ! The range over which the shelf slopes.
108  real :: pos_shelf_edge_0
109  real :: shelf_speed
110 end type user_ice_shelf_cs
111 
112 contains
113 
114 subroutine user_initialize_shelf_mass(mass_shelf, area_shelf_h, h_shelf, hmask, G, CS, param_file, new_sim)
116  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
117  real, dimension(SZI_(G),SZJ_(G)), intent(out) :: mass_shelf, area_shelf_h, hmask, h_shelf
118  type(user_ice_shelf_cs), pointer :: CS
119  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
120  logical :: new_sim
121 
122 ! Arguments: mass_shelf - The mass per unit area averaged over the full ocean
123 ! cell, in kg m-2. (Intent out)
124 ! (out) area_shelf_h - The area of the ocean cell that is covered by the
125 ! rigid ice shelf, in m2.
126 ! (in) G - The ocean's grid structure.
127 ! (in) param_file - A structure indicating the open file to parse for
128 ! model parameter values.
129 
130 
131 ! just check for cvs
132 ! This subroutine sets up the initial mass and area covered by the ice shelf.
133  real :: Rho_ocean ! The ocean's typical density, in kg m-3.
134  real :: max_draft ! The maximum ocean draft of the ice shelf, in m.
135  real :: min_draft ! The minimum ocean draft of the ice shelf, in m.
136  real :: flat_shelf_width ! The range over which the shelf is min_draft thick.
137  real :: c1 ! The maximum depths in m.
138  character(len=40) :: mdl = "USER_initialize_shelf_mass" ! This subroutine's name.
139  integer :: i, j
140 
141  ! call MOM_error(FATAL, "USER_shelf_init.F90, USER_set_shelf_mass: " // &
142  ! "Unmodified user routine called - you must edit the routine to use it")
143 
144  if (.not.associated(cs)) allocate(cs)
145 
146  ! Read all relevant parameters and write them to the model log.
147  if (first_call) call write_user_log(param_file)
148  call get_param(param_file, mdl, "RHO_0", cs%Rho_ocean, &
149  "The mean ocean density used with BOUSSINESQ true to \n"//&
150  "calculate accelerations and the mass for conservation \n"//&
151  "properties, or with BOUSSINSEQ false to convert some \n"//&
152  "parameters from vertical units of m to kg m-2.", &
153  units="kg m-3", default=1035.0)
154  call get_param(param_file, mdl, "SHELF_MAX_DRAFT", cs%max_draft, &
155  units="m", default=1.0)
156  call get_param(param_file, mdl, "SHELF_MIN_DRAFT", cs%min_draft, &
157  units="m", default=1.0)
158  call get_param(param_file, mdl, "FLAT_SHELF_WIDTH", cs%flat_shelf_width, &
159  units="axis_units", default=0.0)
160  call get_param(param_file, mdl, "SHELF_SLOPE_SCALE", cs%shelf_slope_scale, &
161  units="axis_units", default=0.0)
162  call get_param(param_file, mdl, "SHELF_EDGE_POS_0", cs%pos_shelf_edge_0, &
163  units="axis_units", default=0.0)
164  call get_param(param_file, mdl, "SHELF_SPEED", cs%shelf_speed, &
165  units="axis_units day-1", default=0.0)
166 
167  call user_update_shelf_mass(mass_shelf, area_shelf_h, h_shelf, hmask, g, cs, set_time(0,0), new_sim)
168 
169 
170 end subroutine user_initialize_shelf_mass
171 
172 subroutine user_init_ice_thickness(h_shelf, area_shelf_h, hmask, G, param_file)
173  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
174  real, dimension(SZI_(G),SZJ_(G)), intent(out) :: area_shelf_h, hmask, h_shelf
175  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
176 
177  ! This subroutine initializes the ice shelf thickness. Currently it does so
178  ! calling USER_initialize_shelf_mass, but this can be revised as needed.
179  real, dimension(SZI_(G),SZJ_(G)) :: mass_shelf
180  type(user_ice_shelf_cs), pointer :: CS => null()
181 
182  call user_initialize_shelf_mass(mass_shelf, area_shelf_h, h_shelf, hmask, g, cs, param_file, .true.)
183 
184 end subroutine user_init_ice_thickness
185 
186 subroutine user_update_shelf_mass(mass_shelf, area_shelf_h, h_shelf, hmask, G, CS, Time, new_sim)
187  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
188  real, dimension(SZI_(G),SZJ_(G)), intent(inout) :: mass_shelf, area_shelf_h, hmask, h_shelf
189  type(user_ice_shelf_cs), pointer :: CS
190  type(time_type), intent(in) :: Time
191  logical, intent(in) :: new_sim
192 
193 ! Arguments: mass_shelf - The mass per unit area averaged over the full ocean
194 ! cell, in kg m-2. (Intent out)
195 ! (out) area_shelf_h - The area of the ocean cell that is covered by the
196 ! rigid ice shelf, in m2.
197 ! (in) G - The ocean's grid structure.
198 ! (in) param_file - A structure indicating the open file to parse for
199 ! model parameter values.
200 
201  real :: c1, edge_pos, slope_pos
202  integer :: i, j
203 
204  edge_pos = cs%pos_shelf_edge_0 + cs%shelf_speed*(time_type_to_real(time) / 86400.0)
205 
206  slope_pos = edge_pos - cs%flat_shelf_width
207  c1 = 0.0 ; if (cs%shelf_slope_scale > 0.0) c1 = 1.0 / cs%shelf_slope_scale
208 
209 
210  do j=g%jsd,g%jed ;
211 
212  if (((j+g%jdg_offset) .le. g%domain%njglobal+g%domain%njhalo) .AND. &
213  ((j+g%jdg_offset) .ge. g%domain%njhalo+1)) then
214 
215  do i=g%isc,g%iec
216 
217 ! if (((i+G%idg_offset) <= G%domain%niglobal+G%domain%nihalo) .AND. &
218 ! ((i+G%idg_offset) >= G%domain%nihalo+1)) then
219 
220  if ((j.ge.g%jsc) .and. (j.le.g%jec)) then
221 
222  if (new_sim) then ; if (g%geoLonCu(i-1,j) >= edge_pos) then
223  ! Everything past the edge is open ocean.
224  mass_shelf(i,j) = 0.0
225  area_shelf_h(i,j) = 0.0
226  hmask(i,j) = 0.0
227  h_shelf(i,j) = 0.0
228  else
229  if (g%geoLonCu(i,j) > edge_pos) then
230  area_shelf_h(i,j) = g%areaT(i,j) * (edge_pos - g%geoLonCu(i-1,j)) / &
231  (g%geoLonCu(i,j) - g%geoLonCu(i-1,j))
232  hmask(i,j) = 2.0
233  else
234  area_shelf_h(i,j) = g%areaT(i,j)
235  hmask(i,j) = 1.0
236  endif
237 
238  if (g%geoLonT(i,j) > slope_pos) then
239  h_shelf(i,j) = cs%min_draft
240  mass_shelf(i,j) = cs%Rho_ocean * cs%min_draft
241  else
242  mass_shelf(i,j) = cs%Rho_ocean * (cs%min_draft + &
243  (cs%max_draft - cs%min_draft) * &
244  min(1.0, (c1*(slope_pos - g%geoLonT(i,j)))**2) )
245  h_shelf(i,j) = (cs%min_draft + &
246  (cs%max_draft - cs%min_draft) * &
247  min(1.0, (c1*(slope_pos - g%geoLonT(i,j)))**2) )
248  endif
249 
250  endif ; endif ; endif
251 
252  if ((i+g%idg_offset) .eq. g%domain%nihalo+1) then
253  hmask(i-1,j) = 3.0
254  endif
255 
256  enddo ; endif ; enddo
257 
258 end subroutine user_update_shelf_mass
259 
260 subroutine write_user_log(param_file)
261  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
262 
263  character(len=128) :: version = '$Id: user_shelf_init.F90,v 1.1.2.7 2012/06/19 22:15:52 Robert.Hallberg Exp $'
264  character(len=128) :: tagname = '$Name: MOM_ogrp $'
265  character(len=40) :: mdl = "user_shelf_init" ! This module's name.
266 
267  call log_version(param_file, mdl, version, tagname)
268  first_call = .false.
269 
270 end subroutine write_user_log
271 
272 end module user_shelf_init
subroutine, public user_initialize_shelf_mass(mass_shelf, area_shelf_h, h_shelf, hmask, G, CS, param_file, new_sim)
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
Provides the ocean grid type.
Definition: MOM_grid.F90:2
subroutine, public user_update_shelf_mass(mass_shelf, area_shelf_h, h_shelf, hmask, G, CS, Time, new_sim)
subroutine write_user_log(param_file)
subroutine, public user_init_ice_thickness(h_shelf, area_shelf_h, hmask, G, param_file)
logical function, public is_root_pe()
subroutine, public mom_mesg(message, verb, all_print)
subroutine, public mom_error(level, message, all_print)