MOM6
user_shelf_init.F90
1 !> This module specifies the initial values and evolving properties of the
2 !! MOM6 ice shelf, using user-provided code.
4 
5 ! This file is part of MOM6. See LICENSE.md for the license.
6 
7 ! use MOM_domains, only : sum_across_PEs
8 use mom_error_handler, only : mom_mesg, mom_error, fatal, is_root_pe
10 use mom_grid, only : ocean_grid_type
11 use mom_time_manager, only : time_type, set_time, time_type_to_real
13 ! use MOM_io, only : close_file, fieldtype, file_exists
14 ! use MOM_io, only : open_file, read_data, read_axis_data, SINGLE_FILE
15 ! use MOM_io, only : write_field, slasher
16 implicit none ; private
17 
18 #include <MOM_memory.h>
19 
20 public user_initialize_shelf_mass, user_update_shelf_mass
21 public user_init_ice_thickness
22 
23 ! A note on unit descriptions in comments: MOM6 uses units that can be rescaled for dimensional
24 ! consistency testing. These are noted in comments with units like Z, H, L, and T, along with
25 ! their mks counterparts with notation like "a velocity [Z T-1 ~> m s-1]". If the units
26 ! vary with the Boussinesq approximation, the Boussinesq variant is given first.
27 
28 !> The control structure for the user_ice_shelf module
29 type, public :: user_ice_shelf_cs ; private
30  real :: rho_ocean !< The ocean's typical density [kg m-2 Z-1].
31  real :: max_draft !< The maximum ocean draft of the ice shelf [Z ~> m].
32  real :: min_draft !< The minimum ocean draft of the ice shelf [Z ~> m].
33  real :: flat_shelf_width !< The range over which the shelf is min_draft thick [km].
34  real :: shelf_slope_scale !< The range over which the shelf slopes [km].
35  real :: pos_shelf_edge_0 !< The x-position of the shelf edge at time 0 [km].
36  real :: shelf_speed !< The ice shelf speed of translation [km day-1]
37  logical :: first_call = .true. !< If true, this module has not been called before.
38 end type user_ice_shelf_cs
39 
40 contains
41 
42 !> This subroutine sets up the initial mass and area covered by the ice shelf, based on user-provided code.
43 subroutine user_initialize_shelf_mass(mass_shelf, area_shelf_h, h_shelf, hmask, G, US, CS, param_file, new_sim)
44 
45  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
46  real, dimension(SZDI_(G),SZDJ_(G)), &
47  intent(out) :: mass_shelf !< The ice shelf mass per unit area averaged
48  !! over the full ocean cell [kg m-2].
49  real, dimension(SZDI_(G),SZDJ_(G)), &
50  intent(out) :: h_shelf !< The ice shelf thickness [Z ~> m].
51  real, dimension(SZDI_(G),SZDJ_(G)), &
52  intent(out) :: area_shelf_h !< The area per cell covered by the ice shelf [m2].
53  real, dimension(SZDI_(G),SZDJ_(G)), &
54  intent(out) :: hmask !< A mask indicating which tracer points are
55  !! partly or fully covered by an ice-shelf
56  type(unit_scale_type), intent(in) :: us !< A structure containing unit conversion factors
57  type(user_ice_shelf_cs), pointer :: cs !< A pointer to the user ice shelf control structure
58  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
59  logical, intent(in) :: new_sim !< If true, this is a new run; otherwise it is
60  !! being started from a restart file.
61 
62 ! This subroutine sets up the initial mass and area covered by the ice shelf.
63  real :: rho_ocean ! The ocean's typical density [kg m-3].
64  real :: max_draft ! The maximum ocean draft of the ice shelf [Z ~> m].
65  real :: min_draft ! The minimum ocean draft of the ice shelf [Z ~> m].
66  real :: flat_shelf_width ! The range over which the shelf is min_draft thick.
67  real :: c1 ! The maximum depths in m.
68  character(len=40) :: mdl = "USER_initialize_shelf_mass" ! This subroutine's name.
69  integer :: i, j
70 
71  ! call MOM_error(FATAL, "USER_shelf_init.F90, USER_set_shelf_mass: " // &
72  ! "Unmodified user routine called - you must edit the routine to use it")
73 
74  if (.not.associated(cs)) allocate(cs)
75 
76  ! Read all relevant parameters and write them to the model log.
77  if (cs%first_call) call write_user_log(param_file)
78  cs%first_call = .false.
79  call get_param(param_file, mdl, "RHO_0", cs%Rho_ocean, &
80  "The mean ocean density used with BOUSSINESQ true to "//&
81  "calculate accelerations and the mass for conservation "//&
82  "properties, or with BOUSSINSEQ false to convert some "//&
83  "parameters from vertical units of m to kg m-2.", &
84  units="kg m-3", default=1035.0, scale=us%Z_to_m)
85  call get_param(param_file, mdl, "SHELF_MAX_DRAFT", cs%max_draft, &
86  units="m", default=1.0, scale=us%m_to_Z)
87  call get_param(param_file, mdl, "SHELF_MIN_DRAFT", cs%min_draft, &
88  units="m", default=1.0, scale=us%m_to_Z)
89  call get_param(param_file, mdl, "FLAT_SHELF_WIDTH", cs%flat_shelf_width, &
90  units="axis_units", default=0.0)
91  call get_param(param_file, mdl, "SHELF_SLOPE_SCALE", cs%shelf_slope_scale, &
92  units="axis_units", default=0.0)
93  call get_param(param_file, mdl, "SHELF_EDGE_POS_0", cs%pos_shelf_edge_0, &
94  units="axis_units", default=0.0)
95  call get_param(param_file, mdl, "SHELF_SPEED", cs%shelf_speed, &
96  units="axis_units day-1", default=0.0)
97 
98  call user_update_shelf_mass(mass_shelf, area_shelf_h, h_shelf, hmask, g, cs, set_time(0,0), new_sim)
99 
100 end subroutine user_initialize_shelf_mass
101 
102 !> This subroutine updates the ice shelf thickness, as specified by user-provided code.
103 subroutine user_init_ice_thickness(h_shelf, area_shelf_h, hmask, G, US, param_file)
104  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
105  real, dimension(SZDI_(G),SZDJ_(G)), &
106  intent(out) :: h_shelf !< The ice shelf thickness [m].
107  real, dimension(SZDI_(G),SZDJ_(G)), &
108  intent(out) :: area_shelf_h !< The area per cell covered by the ice shelf [m2].
109  real, dimension(SZDI_(G),SZDJ_(G)), &
110  intent(out) :: hmask !< A mask indicating which tracer points are
111  !! partly or fully covered by an ice-shelf
112  type(unit_scale_type), intent(in) :: us !< A structure containing unit conversion factors
113  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
114 
115  ! This subroutine initializes the ice shelf thickness. Currently it does so
116  ! calling USER_initialize_shelf_mass, but this can be revised as needed.
117  real, dimension(SZI_(G),SZJ_(G)) :: mass_shelf
118  type(user_ice_shelf_cs), pointer :: cs => null()
119 
120  call user_initialize_shelf_mass(mass_shelf, area_shelf_h, h_shelf, hmask, g, us, cs, param_file, .true.)
121 
122 end subroutine user_init_ice_thickness
123 
124 !> This subroutine updates the ice shelf mass, as specified by user-provided code.
125 subroutine user_update_shelf_mass(mass_shelf, area_shelf_h, h_shelf, hmask, G, CS, Time, new_sim)
126  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
127  real, dimension(SZDI_(G),SZDJ_(G)), &
128  intent(inout) :: mass_shelf !< The ice shelf mass per unit area averaged
129  !! over the full ocean cell [kg m-2].
130  real, dimension(SZDI_(G),SZDJ_(G)), &
131  intent(inout) :: area_shelf_h !< The area per cell covered by the ice shelf [m2].
132  real, dimension(SZDI_(G),SZDJ_(G)), &
133  intent(inout) :: h_shelf !< The ice shelf thickness [Z ~> m].
134  real, dimension(SZDI_(G),SZDJ_(G)), &
135  intent(inout) :: hmask !< A mask indicating which tracer points are
136  !! partly or fully covered by an ice-shelf
137  type(user_ice_shelf_cs), pointer :: cs !< A pointer to the user ice shelf control structure
138  type(time_type), intent(in) :: time !< The current model time
139  logical, intent(in) :: new_sim !< If true, this the start of a new run.
140 
141 
142  real :: c1, edge_pos, slope_pos
143  integer :: i, j
144 
145  edge_pos = cs%pos_shelf_edge_0 + cs%shelf_speed*(time_type_to_real(time) / 86400.0)
146 
147  slope_pos = edge_pos - cs%flat_shelf_width
148  c1 = 0.0 ; if (cs%shelf_slope_scale > 0.0) c1 = 1.0 / cs%shelf_slope_scale
149 
150 
151  do j=g%jsd,g%jed
152 
153  if (((j+g%jdg_offset) <= g%domain%njglobal+g%domain%njhalo) .AND. &
154  ((j+g%jdg_offset) >= g%domain%njhalo+1)) then
155 
156  do i=g%isc,g%iec
157 
158 ! if (((i+G%idg_offset) <= G%domain%niglobal+G%domain%nihalo) .AND. &
159 ! ((i+G%idg_offset) >= G%domain%nihalo+1)) then
160 
161  if ((j >= g%jsc) .and. (j <= g%jec)) then
162 
163  if (new_sim) then ; if (g%geoLonCu(i-1,j) >= edge_pos) then
164  ! Everything past the edge is open ocean.
165  mass_shelf(i,j) = 0.0
166  area_shelf_h(i,j) = 0.0
167  hmask(i,j) = 0.0
168  h_shelf(i,j) = 0.0
169  else
170  if (g%geoLonCu(i,j) > edge_pos) then
171  area_shelf_h(i,j) = g%areaT(i,j) * (edge_pos - g%geoLonCu(i-1,j)) / &
172  (g%geoLonCu(i,j) - g%geoLonCu(i-1,j))
173  hmask(i,j) = 2.0
174  else
175  area_shelf_h(i,j) = g%areaT(i,j)
176  hmask(i,j) = 1.0
177  endif
178 
179  if (g%geoLonT(i,j) > slope_pos) then
180  h_shelf(i,j) = cs%min_draft
181  mass_shelf(i,j) = cs%Rho_ocean * cs%min_draft
182  else
183  mass_shelf(i,j) = cs%Rho_ocean * (cs%min_draft + &
184  (cs%max_draft - cs%min_draft) * &
185  min(1.0, (c1*(slope_pos - g%geoLonT(i,j)))**2) )
186  h_shelf(i,j) = (cs%min_draft + &
187  (cs%max_draft - cs%min_draft) * &
188  min(1.0, (c1*(slope_pos - g%geoLonT(i,j)))**2) )
189  endif
190 
191  endif ; endif ; endif
192 
193  if ((i+g%idg_offset) == g%domain%nihalo+1) then
194  hmask(i-1,j) = 3.0
195  endif
196 
197  enddo ; endif ; enddo
198 
199 end subroutine user_update_shelf_mass
200 
201 !> This subroutine writes out the user ice shelf code version number to the model log.
202 subroutine write_user_log(param_file)
203  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
204 
205  character(len=128) :: version = '$Id: user_shelf_init.F90,v 1.1.2.7 2012/06/19 22:15:52 Robert.Hallberg Exp $'
206  character(len=128) :: tagname = '$Name: MOM_ogrp $'
207  character(len=40) :: mdl = "user_shelf_init" ! This module's name.
208 
209  call log_version(param_file, mdl, version, tagname)
210 
211 end subroutine write_user_log
212 
213 end module user_shelf_init
mom_time_manager
Wraps the FMS time manager functions.
Definition: MOM_time_manager.F90:2
mom_file_parser::log_version
An overloaded interface to log version information about modules.
Definition: MOM_file_parser.F90:109
mom_file_parser::param_file_type
A structure that can be parsed to read and document run-time parameters.
Definition: MOM_file_parser.F90:54
mom_file_parser::get_param
An overloaded interface to read and log the values of various types of parameters.
Definition: MOM_file_parser.F90:102
mom_unit_scaling::unit_scale_type
Describes various unit conversion factors.
Definition: MOM_unit_scaling.F90:14
mom_file_parser
The MOM6 facility to parse input files for runtime parameters.
Definition: MOM_file_parser.F90:2
mom_grid
Provides the ocean grid type.
Definition: MOM_grid.F90:2
mom_unit_scaling
Provides a transparent unit rescaling type to facilitate dimensional consistency testing.
Definition: MOM_unit_scaling.F90:2
user_shelf_init
This module specifies the initial values and evolving properties of the MOM6 ice shelf,...
Definition: user_shelf_init.F90:3
mom_error_handler
Routines for error handling and I/O management.
Definition: MOM_error_handler.F90:2
user_shelf_init::user_ice_shelf_cs
The control structure for the user_ice_shelf module.
Definition: user_shelf_init.F90:29
mom_grid::ocean_grid_type
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:25