MOM6
MOM_ice_shelf_initialize.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 use mom_grid, only : ocean_grid_type
24 use mom_io, only: read_data, file_exists, slasher
25 use mom_error_handler, only : mom_error, mom_mesg, fatal, warning, is_root_pe
27 
28 implicit none ; private
29 
30 #include <MOM_memory.h>
31 #ifdef SYMMETRIC_LAND_ICE
32 # define GRID_SYM_ .true.
33 # define NIMEMQ_IS_ NIMEMQS_
34 # define NJMEMQ_IS_ NJMEMQS_
35 # define ISUMSTART_INT_ CS%grid%iscq+1
36 # define JSUMSTART_INT_ CS%grid%jscq+1
37 #else
38 # define GRID_SYM_ .false.
39 # define NIMEMQ_IS_ NIMEMQ_
40 # define NJMEMQ_IS_ NJMEMQ_
41 # define ISUMSTART_INT_ CS%grid%iscq
42 # define JSUMSTART_INT_ CS%grid%jscq
43 #endif
44 
45 
46 !MJHpublic initialize_ice_shelf_boundary, initialize_ice_thickness
48 
49 contains
50 
51 subroutine initialize_ice_thickness (h_shelf, area_shelf_h, hmask, G, PF)
52 
53  real, intent(inout), dimension(:,:) :: h_shelf, area_shelf_h, hmask
54  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
55  type(param_file_type), intent(in) :: PF
56 
57  character(len=40) :: mdl = "initialize_ice_thickness" ! This subroutine's name.
58  character(len=200) :: config
59 
60  call get_param(pf, mdl, "ICE_PROFILE_CONFIG", config, &
61  "This specifies how the initial ice profile is specified. \n"//&
62  "Valid values are: CHANNEL, FILE, and USER.", &
63  fail_if_missing=.true.)
64 
65  select case ( trim(config) )
66  case ("CHANNEL"); call initialize_ice_thickness_channel (h_shelf, area_shelf_h, hmask, g, pf)
67  case ("FILE"); call initialize_ice_thickness_from_file (h_shelf, area_shelf_h, hmask, g, pf)
68  case ("USER"); call user_init_ice_thickness (h_shelf, area_shelf_h, hmask, g, pf)
69  case default ; call mom_error(fatal,"MOM_initialize: "// &
70  "Unrecognized ice profile setup "//trim(config))
71  end select
72 
73 end subroutine initialize_ice_thickness
74 
75 
76 subroutine initialize_ice_thickness_from_file (h_shelf, area_shelf_h, hmask, G, PF)
77 
78  real, intent(inout), dimension(:,:) :: h_shelf, area_shelf_h, hmask
79  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
80  type(param_file_type), intent(in) :: PF
81 
82  ! This subroutine reads ice thickness and area from a file and puts it into
83  ! h_shelf and area_shelf_h in m (and dimensionless) and updates hmask
84  character(len=200) :: filename,thickness_file,inputdir ! Strings for file/path
85  character(len=200) :: thickness_varname, area_varname! Variable name in file
86  character(len=40) :: mdl = "initialize_ice_thickness_from_file" ! This subroutine's name.
87  integer :: i, j, isc, jsc, iec, jec
88  real :: len_sidestress, mask, udh
89 
90  call mom_mesg(" MOM_ice_shelf_init_profile.F90, initialize_thickness_from_file: reading thickness")
91 
92  call get_param(pf, mdl, "INPUTDIR", inputdir, default=".")
93  inputdir = slasher(inputdir)
94  call get_param(pf, mdl, "ICE_THICKNESS_FILE", thickness_file, &
95  "The file from which the bathymetry is read.", &
96  default="ice_shelf_h.nc")
97  call get_param(pf, mdl, "LEN_SIDE_STRESS", len_sidestress, &
98  "position past which shelf sides are stress free.", &
99  default=0.0, units="axis_units")
100 
101  filename = trim(inputdir)//trim(thickness_file)
102  call log_param(pf, mdl, "INPUTDIR/THICKNESS_FILE", filename)
103  call get_param(pf, mdl, "ICE_THICKNESS_VARNAME", thickness_varname, &
104  "The name of the thickness variable in ICE_THICKNESS_FILE.", &
105  default="h_shelf")
106  call get_param(pf, mdl, "ICE_AREA_VARNAME", area_varname, &
107  "The name of the area variable in ICE_THICKNESS_FILE.", &
108  default="area_shelf_h")
109 
110  if (.not.file_exists(filename, g%Domain)) call mom_error(fatal, &
111  " initialize_topography_from_file: Unable to open "//trim(filename))
112 
113  call read_data(filename,trim(thickness_varname),h_shelf,domain=g%Domain%mpp_domain)
114  call read_data(filename,trim(area_varname),area_shelf_h,domain=g%Domain%mpp_domain)
115 
116 ! call get_param(PF, mdl, "ICE_BOUNDARY_CONFIG", config, &
117 ! "This specifies how the ice domain boundary is specified", &
118 ! fail_if_missing=.true.)
119 
120  isc = g%isc ; jsc = g%jsc ; iec = g%iec ; jec = g%jec
121 
122  do j=jsc,jec
123  do i=isc,iec
124 
125  ! taper ice shelf in area where there is no sidestress -
126  ! but do not interfere with hmask
127 
128  if ((g%geoLonCv(i,j) .gt. len_sidestress).and. &
129  (len_sidestress .gt. 0.)) then
130  udh = exp(-(g%geoLonCv(i,j)-len_sidestress)/5.0) * h_shelf(i,j)
131  if (udh .le. 25.0) then
132  h_shelf(i,j) = 0.0
133  area_shelf_h(i,j) = 0.0
134  else
135  h_shelf(i,j) = udh
136  endif
137  endif
138 
139  ! update thickness mask
140 
141  if (area_shelf_h(i,j) .ge. g%areaT(i,j)) then
142  hmask(i,j) = 1.
143  elseif (area_shelf_h(i,j) .eq. 0.0) then
144  hmask(i,j) = 0.
145  elseif ((area_shelf_h(i,j) .gt. 0) .and. (area_shelf_h(i,j) .le. g%areaT(i,j))) then
146  hmask(i,j) = 2.
147  else
148  call mom_error(fatal,mdl// " AREA IN CELL OUT OF RANGE")
149  endif
150  enddo
151  enddo
152 
153 
155 
156 
157 subroutine initialize_ice_thickness_channel (h_shelf, area_shelf_h, hmask, G, PF)
159  real, intent(inout), dimension(:,:) :: h_shelf, area_shelf_h, hmask
160  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
161  type(param_file_type), intent(in) :: PF
162 
163  character(len=40) :: mdl = "initialize_ice_shelf_thickness_channel" ! This subroutine's name.
164  real :: max_draft, min_draft, flat_shelf_width, c1, slope_pos
165  real :: edge_pos, shelf_slope_scale, Rho_ocean
166  integer :: i, j, jsc, jec, jsd, jed, jedg, nyh, isc, iec, isd, ied
167  integer :: j_off
168 
169  jsc = g%jsc ; jec = g%jec ; isc = g%isc ; iec = g%iec
170  jsd = g%jsd ; jed = g%jed ; isd = g%isd ; ied = g%ied
171  nyh = g%domain%njhalo ; jedg = g%domain%njglobal+nyh
172  j_off = g%jdg_offset
173 
174  call mom_mesg(mdl//": setting thickness")
175 
176  call get_param(pf, mdl, "SHELF_MAX_DRAFT", max_draft, &
177  units="m", default=1.0)
178  call get_param(pf, mdl, "SHELF_MIN_DRAFT", min_draft, &
179  units="m", default=1.0)
180  call get_param(pf, mdl, "FLAT_SHELF_WIDTH", flat_shelf_width, &
181  units="axis_units", default=0.0)
182  call get_param(pf, mdl, "SHELF_SLOPE_SCALE", shelf_slope_scale, &
183  units="axis_units", default=0.0)
184  call get_param(pf, mdl, "SHELF_EDGE_POS_0", edge_pos, &
185  units="axis_units", default=0.0)
186 
187  slope_pos = edge_pos - flat_shelf_width
188  c1 = 0.0 ; if (shelf_slope_scale > 0.0) c1 = 1.0 / shelf_slope_scale
189 
190  do j=g%jsd,g%jed
191 
192  if (((j+j_off) <= jedg) .AND. ((j+j_off) >= nyh+1)) then
193 
194  do i=g%isc,g%iec
195 
196  if ((j.ge.jsc) .and. (j.le.jec)) then
197 
198  if (g%geoLonCu(i-1,j) >= edge_pos) then
199  ! Everything past the edge is open ocean.
200 ! mass_shelf(i,j) = 0.0
201  area_shelf_h(i,j) = 0.0
202  hmask(i,j) = 0.0
203  h_shelf(i,j) = 0.0
204  else
205  if (g%geoLonCu(i,j) > edge_pos) then
206  area_shelf_h(i,j) = g%areaT(i,j) * (edge_pos - g%geoLonCu(i-1,j)) / &
207  (g%geoLonCu(i,j) - g%geoLonCu(i-1,j))
208  hmask(i,j) = 2.0
209  else
210  area_shelf_h(i,j) = g%areaT(i,j)
211  hmask(i,j) = 1.0
212  endif
213 
214  if (g%geoLonT(i,j) > slope_pos) then
215  h_shelf(i,j) = min_draft
216 ! mass_shelf(i,j) = Rho_ocean * min_draft
217  else
218 ! mass_shelf(i,j) = Rho_ocean * (min_draft + &
219 ! (CS%max_draft - CS%min_draft) * &
220 ! min(1.0, (c1*(slope_pos - G%geoLonT(i,j)))**2) )
221  h_shelf(i,j) = (min_draft + &
222  (max_draft - min_draft) * &
223  min(1.0, (c1*(slope_pos - g%geoLonT(i,j)))**2) )
224  endif
225 
226  endif
227  endif
228 
229  if ((i+g%idg_offset) .eq. g%domain%nihalo+1) then
230  hmask(i-1,j) = 3.0
231  endif
232 
233  enddo
234  endif ; enddo
235 
237 
238 !BEGIN MJH subroutine initialize_ice_shelf_boundary ( &
239 ! u_face_mask_boundary, &
240 ! v_face_mask_boundary, &
241 ! u_flux_boundary_values, &
242 ! v_flux_boundary_values, &
243 ! u_boundary_values, &
244 ! v_boundary_values, &
245 ! h_boundary_values, &
246 ! hmask, G, PF)
247 
248 ! type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
249 ! real, intent(inout), dimension(SZIB_(G),SZJ_(G)) :: u_face_mask_boundary, u_flux_boundary_values
250 ! real, intent(inout), dimension(SZI_(G),SZJB_(G)) :: v_face_mask_boundary, v_flux_boundary_values
251 ! real, intent(inout), dimension(SZIB_(G),SZJB_(G)) :: u_boundary_values, v_boundary_values
252 ! real, intent(inout), dimension(:,:) :: hmask, h_boundary_values
253 ! type(param_file_type), intent(in) :: PF
254 
255 ! character(len=40) :: mdl = "initialize_ice_shelf_boundary" ! This subroutine's name.
256 ! character(len=200) :: config
257 ! logical flux_bdry
258 
259 ! call get_param(PF, mdl, "ICE_BOUNDARY_CONFIG", config, &
260 ! "This specifies how the ice domain boundary is specified. \n"//&
261 ! "valid values include CHANNEL, FILE and USER.", &
262 ! fail_if_missing=.true.)
263 ! call get_param(PF, mdl, "ICE_BOUNDARY_FLUX_CONDITION", flux_bdry, &
264 ! "This specifies whether mass input is a dirichlet or \n"//&
265 ! "flux condition", default=.true.)
266 
267 ! select case ( trim(config) )
268 ! case ("CHANNEL");
269 ! call initialize_ice_shelf_boundary_channel(u_face_mask_boundary, &
270 ! v_face_mask_boundary, u_flux_boundary_values, v_flux_boundary_values, &
271 ! u_boundary_values, v_boundary_values, h_boundary_values, hmask, G, &
272 ! flux_bdry, PF)
273 ! case ("FILE"); call MOM_error(FATAL,"MOM_initialize: "// &
274 ! "Unrecognized topography setup "//trim(config))
275 ! case ("USER"); call MOM_error(FATAL,"MOM_initialize: "// &
276 ! "Unrecognized topography setup "//trim(config))
277 ! case default ; call MOM_error(FATAL,"MOM_initialize: "// &
278 ! "Unrecognized topography setup "//trim(config))
279 ! end select
280 
281 ! end subroutine initialize_ice_shelf_boundary
282 
283 ! subroutine initialize_ice_shelf_boundary_channel ( &
284 ! u_face_mask_boundary, &
285 ! v_face_mask_boundary, &
286 ! u_flux_boundary_values, &
287 ! v_flux_boundary_values, &
288 ! u_boundary_values, &
289 ! v_boundary_values, &
290 ! h_boundary_values, &
291 ! hmask, &
292 ! G, flux_bdry, PF )
293 
294 ! type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
295 ! real, dimension(SZIB_(G),SZJ_(G)), intent(inout) :: u_face_mask_boundary, u_flux_boundary_values
296 ! real, dimension(SZI_(G),SZJB_(G)), intent(inout) :: v_face_mask_boundary, v_flux_boundary_values
297 ! real, dimension(SZIB_(G),SZJB_(G)), intent(inout) :: u_boundary_values, v_boundary_values
298 ! real, dimension(:,:), intent(inout) :: h_boundary_values, hmask
299 ! logical, intent(in) :: flux_bdry
300 ! type (param_file_type), intent(in) :: PF
301 
302 ! character(len=40) :: mdl = "initialize_ice_shelf_boundary_channel" ! This subroutine's name.
303 ! integer :: i, j, isd, jsd, is, js, iegq, jegq, giec, gjec, gisc, gjsc, isc, jsc, iec, jec, ied, jed
304 ! real :: lenlat, input_thick, input_flux, len_stress
305 
306 ! call get_param(PF, mdl, "LENLAT", lenlat, fail_if_missing=.true.)
307 
308 ! call get_param(PF, mdl, "INPUT_FLUX_ICE_SHELF", input_flux, &
309 ! "volume flux at upstream boundary", &
310 ! units="m2 s-1", default=0.)
311 ! call get_param(PF, mdl, "INPUT_THICK_ICE_SHELF", input_thick, &
312 ! "flux thickness at upstream boundary", &
313 ! units="m", default=1000.)
314 ! call get_param(PF, mdl, "LEN_SIDE_STRESS", len_stress, &
315 ! "maximum position of no-flow condition in along-flow direction", &
316 ! units="km", default=0.)
317 
318 ! call MOM_mesg(mdl//": setting boundary")
319 
320 ! isd = G%isd ; ied = G%ied
321 ! jsd = G%jsd ; jed = G%jed
322 ! isc = G%isc ; jsc = G%jsc ; iec = G%iec ; jec = G%jec
323 ! gisc = G%Domain%nihalo ; gjsc = G%Domain%njhalo
324 ! giec = G%Domain%niglobal+gisc ; gjec = G%Domain%njglobal+gjsc
325 
326 ! do j=jsd,jed
327 ! do i=isd,ied
328 
329 ! ! upstream boundary - set either dirichlet or flux condition
330 
331 ! if ((i+G%idg_offset) .eq. G%domain%nihalo+1) then
332 ! if (flux_bdry) then
333 ! u_face_mask_boundary (i-1,j) = 4.0
334 ! u_flux_boundary_values (i-1,j) = input_flux
335 ! else
336 ! hmask(i-1,j) = 3.0
337 ! h_boundary_values (i-1,j) = input_thick
338 ! u_face_mask_boundary (i-1,j) = 3.0
339 ! u_boundary_values (i-1,j-1) = (1 - ((G%geoLatBu(i-1,j-1) - 0.5*lenlat)*2./lenlat)**2) * &
340 ! 1.5 * input_flux / input_thick
341 ! u_boundary_values (i-1,j) = (1 - ((G%geoLatBu(i-1,j) - 0.5*lenlat)*2./lenlat)**2) * &
342 ! 1.5 * input_flux / input_thick
343 ! endif
344 ! endif
345 
346 ! ! side boundaries: no flow
347 
348 ! if (G%jdg_offset+j .eq. gjsc+1) then !bot boundary
349 ! if (len_stress .eq. 0. .OR. G%geoLonCv(i,j-1) .le. len_stress) then
350 ! v_face_mask_boundary (i,j-1) = 0.
351 ! else
352 ! v_face_mask_boundary (i,j-1) = 1.
353 ! endif
354 ! elseif (G%jdg_offset+j .eq. gjec) then !top boundary
355 ! if (len_stress .eq. 0. .OR. G%geoLonCv(i,j-1) .le. len_stress) then
356 ! v_face_mask_boundary (i,j) = 0.
357 ! else
358 ! v_face_mask_boundary (i,j) = 1.
359 ! endif
360 ! endif
361 
362 ! ! downstream boundary - CFBC
363 
364 ! if (i+G%idg_offset .eq. giec) then
365 ! u_face_mask_boundary(i,j) = 2.0
366 ! endif
367 
368 ! enddo
369 ! enddo
370 
371 !END MJH end subroutine initialize_ice_shelf_boundary_channel
372 
373 end module mom_ice_shelf_initialize
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
Provides the ocean grid type.
Definition: MOM_grid.F90:2
This module contains I/O framework code.
Definition: MOM_io.F90:2
subroutine, public user_init_ice_thickness(h_shelf, area_shelf_h, hmask, G, param_file)
subroutine, public initialize_ice_thickness(h_shelf, area_shelf_h, hmask, G, PF)
logical function, public is_root_pe()
subroutine initialize_ice_thickness_from_file(h_shelf, area_shelf_h, hmask, G, PF)
subroutine, public mom_mesg(message, verb, all_print)
subroutine initialize_ice_thickness_channel(h_shelf, area_shelf_h, hmask, G, PF)
subroutine, public mom_error(level, message, all_print)