SCALE-RM
scale_ocean_phy_ice_simple.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
10 !-------------------------------------------------------------------------------
11 #include "scalelib.h"
13  !-----------------------------------------------------------------------------
14  !
15  !++ used modules
16  !
17  use scale_precision
18  use scale_io
19  use scale_prof
20  !-----------------------------------------------------------------------------
21  implicit none
22  private
23  !-----------------------------------------------------------------------------
24  !
25  !++ Public procedure
26  !
27  public :: ocean_phy_ice_setup
28  public :: ocean_phy_ice_fraction
29  public :: ocean_phy_ice_adjustment
30  public :: ocean_phy_ice_simple
31 
32  !-----------------------------------------------------------------------------
33  !
34  !++ Public parameters & variables
35  !
36  !-----------------------------------------------------------------------------
37  !
38  !++ Private procedure
39  !
40  !-----------------------------------------------------------------------------
41  !
42  !++ Private parameters & variables
43  !
44  real(rp), public :: ocean_phy_ice_freezetemp = 271.35_rp ! freezing temperature of sea ice [K]
45  real(rp), public :: ocean_phy_ice_density = 1000.0_rp ! density of sea ice [kg/m3]
46 
47  real(rp), private :: ocean_phy_ice_mass_critical = 1600.0_rp ! ice amount for fraction = 1 [kg/m2]
48  real(rp), private :: ocean_phy_ice_mass_limit = 50000.0_rp ! maximum ice amount [kg/m2]
49  real(rp), private :: ocean_phy_ice_fraction_limit = 1.0_rp ! maximum ice fraction [1]
50  real(rp), private :: ocean_phy_ice_dt_max = 5.e-2_rp ! maximum delta ice temperature [K/s]
51 
52  logical, private :: ocean_phy_ice_nudging = .false.
53  real(dp), private :: ocean_phy_ice_nudging_tausec
54  logical, private :: ocean_phy_ice_offline_mode = .false.
55 
56  !-----------------------------------------------------------------------------
57 contains
58  !-----------------------------------------------------------------------------
59  subroutine ocean_phy_ice_setup
60  use scale_prc, only: &
61  prc_abort
62  use scale_const, only: &
63  undef => const_undef
64  use scale_calendar, only: &
66  use scale_file_external_input, only: &
68  implicit none
69 
70  real(dp) :: ocean_phy_ice_nudging_tau = 0.0_dp ! Relaxation time
71  character(len=H_SHORT) :: ocean_phy_ice_nudging_tau_unit = "SEC"
72  character(len=H_LONG) :: ocean_phy_ice_nudging_basename = ''
73  logical :: ocean_phy_ice_nudging_basename_add_num = .false.
74  integer :: ocean_phy_ice_nudging_number_of_files = 1
75  logical :: ocean_phy_ice_nudging_enable_periodic_year = .false.
76  logical :: ocean_phy_ice_nudging_enable_periodic_month = .false.
77  logical :: ocean_phy_ice_nudging_enable_periodic_day = .false.
78  integer :: ocean_phy_ice_nudging_step_fixed = 0
79  real(rp) :: ocean_phy_ice_nudging_offset = 0.0_rp
80  real(rp) :: ocean_phy_ice_nudging_defval != UNDEF
81  logical :: ocean_phy_ice_nudging_check_coordinates = .true.
82  integer :: ocean_phy_ice_nudging_step_limit = 0
83 
84  namelist / param_ocean_phy_ice / &
86  ocean_phy_ice_mass_critical, &
87  ocean_phy_ice_mass_limit, &
88  ocean_phy_ice_fraction_limit, &
89  ocean_phy_ice_dt_max!, &
90 ! OCEAN_PHY_ICE_nudging, &
91 ! OCEAN_PHY_ICE_nudging_tau, &
92 ! OCEAN_PHY_ICE_nudging_tau_unit, &
93 ! OCEAN_PHY_ICE_nudging_basename, &
94 ! OCEAN_PHY_ICE_nudging_basename_add_num, &
95 ! OCEAN_PHY_ICE_nudging_number_of_files, &
96 ! OCEAN_PHY_ICE_nudging_enable_periodic_year, &
97 ! OCEAN_PHY_ICE_nudging_enable_periodic_month, &
98 ! OCEAN_PHY_ICE_nudging_enable_periodic_day, &
99 ! OCEAN_PHY_ICE_nudging_step_fixed, &
100 ! OCEAN_PHY_ICE_nudging_offset, &
101 ! OCEAN_PHY_ICE_nudging_defval, &
102 ! OCEAN_PHY_ICE_nudging_check_coordinates, &
103 ! OCEAN_PHY_ICE_nudging_step_limit
104 
105  integer :: ierr
106  !---------------------------------------------------------------------------
107 
108  log_newline
109  log_info("OCEAN_PHY_ICE_setup",*) 'Setup'
110 
111  ocean_phy_ice_nudging_defval = undef
112 
113  !--- read namelist
114  rewind(io_fid_conf)
115  read(io_fid_conf,nml=param_ocean_phy_ice,iostat=ierr)
116  if( ierr < 0 ) then !--- missing
117  log_info("OCEAN_PHY_ICE_setup",*) 'Not found namelist. Default used.'
118  elseif( ierr > 0 ) then !--- fatal error
119  log_error("OCEAN_PHY_ICE_setup",*) 'Not appropriate names in namelist PARAM_OCEAN_PHY_ICE. Check!'
120  call prc_abort
121  endif
122  log_nml(param_ocean_phy_ice)
123 
124  log_newline
125  log_info("OCEAN_PHY_ICE_setup",*) 'Ice amount for frac. = 1 [kg/m2] : ', ocean_phy_ice_mass_critical
126  if ( ocean_phy_ice_nudging ) then
127  call calendar_unit2sec( ocean_phy_ice_nudging_tausec, ocean_phy_ice_nudging_tau, ocean_phy_ice_nudging_tau_unit )
128 
129  log_info("OCEAN_PHY_ICE_setup",*) 'Use nudging for sea ice fraction : ON'
130  log_info("OCEAN_PHY_ICE_setup",*) 'Relaxation time Tau [sec] : ', ocean_phy_ice_nudging_tausec
131 
132  if ( ocean_phy_ice_nudging_tausec == 0.0_rp ) then
133  ocean_phy_ice_offline_mode = .true.
134  log_info("OCEAN_PHY_ICE_setup",*) 'Tau=0 means that sea ice is completely replaced by the external data.'
135  endif
136 
137  if ( ocean_phy_ice_nudging_basename == '' ) then
138  log_error("OCEAN_PHY_ICE_setup",*) 'OCEAN_PHY_ICE_nudging_basename is necessary. STOP'
139  call prc_abort
140  endif
141  else
142  log_info("OCEAN_PHY_ICE_setup",*) 'Use nudging for sea ice fraction : OFF'
143  endif
144 
145  if ( ocean_phy_ice_nudging ) then
146  call file_external_input_regist( ocean_phy_ice_nudging_basename, & ! [IN]
147  ocean_phy_ice_nudging_basename_add_num, & ! [IN]
148  ocean_phy_ice_nudging_number_of_files, & ! [IN]
149  'OCEAN_ICE_FRAC', & ! [IN]
150  'XY', & ! [IN]
151  ocean_phy_ice_nudging_enable_periodic_year, & ! [IN]
152  ocean_phy_ice_nudging_enable_periodic_month, & ! [IN]
153  ocean_phy_ice_nudging_enable_periodic_day, & ! [IN]
154  ocean_phy_ice_nudging_step_fixed, & ! [IN]
155  ocean_phy_ice_nudging_offset, & ! [IN]
156  ocean_phy_ice_nudging_defval, & ! [IN]
157  check_coordinates = ocean_phy_ice_nudging_check_coordinates, & ! [IN]
158  step_limit = ocean_phy_ice_nudging_step_limit ) ! [IN]
159  endif
160 
161  return
162  end subroutine ocean_phy_ice_setup
163 
164  !-----------------------------------------------------------------------------
165  subroutine ocean_phy_ice_fraction( &
166  OIA, OIS, OIE, &
167  OJA, OJS, OJE, &
168  ICE_MASS, &
169  ICE_FRAC )
170  implicit none
171 
172  integer, intent(in) :: oia, ois, oie
173  integer, intent(in) :: oja, ojs, oje
174  real(rp), intent(in) :: ice_mass(oia,oja) ! sea ice amount [kg/m2]
175  real(rp), intent(out) :: ice_frac(oia,oja) ! sea ice area fraction [1]
176 
177  integer :: i, j
178  !---------------------------------------------------------------------------
179 
180  do j = ojs, oje
181  do i = ois, oie
182  ice_frac(i,j) = ice_mass(i,j) / ocean_phy_ice_mass_critical
183 
184  ice_frac(i,j) = min( sqrt( max( ice_frac(i,j), 0.0_rp ) ), ocean_phy_ice_fraction_limit )
185  enddo
186  enddo
187 
188  return
189  end subroutine ocean_phy_ice_fraction
190 
191  !-----------------------------------------------------------------------------
192  subroutine ocean_phy_ice_adjustment( &
193  OIA, OIS, OIE, &
194  OJA, OJS, OJE, &
195  calc_flag, &
196  OCEAN_DEPTH, &
197  OCEAN_TEMP, &
198  ICE_TEMP, &
199  ICE_MASS, &
200  MASS_FLUX, &
201  ENGI_FLUX, &
202  MASS_SUPL, &
203  ENGI_SUPL )
204  use scale_const, only: &
205  dwatr => const_dwatr
206  use scale_atmos_hydrometeor, only: &
207  cv_water, &
208  cv_ice, &
209  lhf
210  implicit none
211 
212  integer, intent(in) :: oia, ois, oie
213  integer, intent(in) :: oja, ojs, oje
214  logical, intent(in) :: calc_flag (oia,oja) ! to decide calculate or not
215  real(rp), intent(in) :: ocean_depth ! depth of the first layer of the ocean
216  real(rp), intent(inout) :: ocean_temp(oia,oja) ! ocean temperature [K]
217  real(rp), intent(inout) :: ice_temp (oia,oja) ! sea ice temperature [K]
218  real(rp), intent(inout) :: ice_mass (oia,oja) ! sea ice amount [kg/m2]
219  real(rp), intent(out) :: mass_flux(oia,oja)
220  real(rp), intent(out) :: engi_flux(oia,oja)
221  real(rp), intent(out) :: mass_supl (oia,oja)
222  real(rp), intent(out) :: engi_supl (oia,oja)
223 
224  real(rp) :: c_w
225  real(rp) :: ice_mass_frz
226  real(rp) :: ice_mass_prev
227 
228  integer :: i, j
229  !---------------------------------------------------------------------------
230 
231  c_w = cv_water * dwatr * ocean_depth
232 
233  !$omp parallel do &
234  !$omp private(ICE_MASS_frz,ICE_MASS_prev)
235  do j = ojs, oje
236  do i = ois, oie
237  if ( calc_flag(i,j) &
238  .and. ocean_temp(i,j) < ocean_phy_ice_freezetemp .and. ice_mass(i,j) < ocean_phy_ice_mass_limit ) then
239  ice_mass_frz = c_w * ( ocean_phy_ice_freezetemp - ocean_temp(i,j) ) &
241  ice_mass_frz = min( ice_mass_frz, dwatr * ocean_depth )
242 
243  ! update ice mass
244  ice_mass_prev = ice_mass(i,j)
245  ice_mass(i,j) = ice_mass(i,j) + ice_mass_frz
246  ice_mass(i,j) = min( ice_mass(i,j), ocean_phy_ice_mass_limit ) ! apply limiter
247  ice_mass_frz = ice_mass(i,j) - ice_mass_prev
248 
249  ! update ice temperature
250  ice_temp(i,j) = ice_temp(i,j) &
251  + ( ocean_phy_ice_freezetemp - ice_temp(i,j) ) * ice_mass_frz / ice_mass(i,j)
252 
253  ! update ocean temperature
254  ocean_temp(i,j) = ocean_temp(i,j) &
255  + ( cv_water * ocean_temp(i,j) - cv_ice * ocean_phy_ice_freezetemp + lhf ) * ice_mass_frz &
256  / ( c_w - cv_water * ice_mass_frz )
257 
258  mass_flux(i,j) = ice_mass_frz
259  engi_flux(i,j) = ( cv_ice * ocean_phy_ice_freezetemp - lhf ) * ice_mass_frz
260  mass_supl(i,j) = ice_mass_frz
261  engi_supl(i,j) = ice_mass_frz * cv_water * ocean_temp(i,j)
262  else
263  mass_flux(i,j) = 0.0_rp
264  engi_flux(i,j) = 0.0_rp
265  mass_supl(i,j) = 0.0_rp
266  engi_supl(i,j) = 0.0_rp
267  endif
268  enddo
269  enddo
270 
271  return
272  end subroutine ocean_phy_ice_adjustment
273 
274  !-----------------------------------------------------------------------------
276  subroutine ocean_phy_ice_simple( &
277  OIA, OIS, OIE, &
278  OJA, OJS, OJE, &
279  iflx_water, &
280  iflx_hbalance, &
281  subsfc_temp, &
282  TC_dz, &
283  ICE_TEMP, &
284  ICE_MASS, &
285  ICE_FRAC, &
286  calc_flag, &
287  dt, &
288  ICE_TEMP_t, &
289  ICE_MASS_t, &
290  sflx_G, &
291  sflx_water, &
292  sflx_RHOE )
293  use scale_prc, only: &
294  prc_abort
295  use scale_atmos_hydrometeor, only: &
296  cv_water, &
297  cv_ice, &
298  lhf
299  use scale_file_external_input, only: &
300  file_external_input_update
301  implicit none
302 
303  integer, intent(in) :: oia, ois, oie
304  integer, intent(in) :: oja, ojs, oje
305  real(rp), intent(in) :: iflx_water (oia,oja) ! input mass flux [kg/m2/s] (downward)
306  real(rp), intent(in) :: iflx_hbalance(oia,oja) ! input heat flux [J/m2/s] (downward)
307  real(rp), intent(in) :: subsfc_temp (oia,oja) ! subsurface temperature [K]
308  real(rp), intent(in) :: tc_dz (oia,oja) ! Thermal conductance [K/m]
309  real(rp), intent(in) :: ice_temp (oia,oja) ! sea ice temperature [K]
310  real(rp), intent(in) :: ice_mass (oia,oja) ! sea ice amount [kg/m2]
311  real(rp), intent(in) :: ice_frac (oia,oja) ! sea ice fraction [0-1]
312  logical, intent(in) :: calc_flag (oia,oja) ! to decide calculate or not
313  real(dp), intent(in) :: dt
314  real(rp), intent(out) :: ice_temp_t (oia,oja) ! tendency of sea ice temperature [K/s]
315  real(rp), intent(out) :: ice_mass_t (oia,oja) ! tendency of sea ice amount [kg/m2/s]
316  real(rp), intent(out) :: sflx_g (oia,oja) ! heat flux from sea ice to subsurface
317  real(rp), intent(out) :: sflx_water (oia,oja) ! mass flux from sea ice to subsurface
318  real(rp), intent(out) :: sflx_rhoe (oia,oja) ! internal energy flux from sea ice to subsurface
319 
320  real(rp) :: ice_mass_new ! [kg/m2]
321  real(rp) :: ice_temp_new ! [K]
322  real(rp) :: mass_budget ! [kg/m2/s]
323  real(rp) :: heat_budget ! [J/m2/s]
324  real(rp) :: g ! [J/m2/s]
325  real(rp) :: dm ! [kg/m2]
326  real(rp) :: de ! [J/m2]
327  real(rp) :: m_mlt ! [kg/m2]
328  real(rp) :: dt_rp
329 
330  integer :: i, j
331  !---------------------------------------------------------------------------
332 
333  log_progress(*) 'ocean / physics / seaice'
334 
335  dt_rp = real(dt,kind=rp)
336 
337  !$omp parallel do &
338  !$omp private(mass_budget,heat_budget,dM,dE,G,M_mlt, &
339  !$omp ICE_TEMP_new,ICE_MASS_new)
340  do j = ojs, oje
341  do i = ois, oie
342  if ( calc_flag(i,j) ) then
343 
344  ! mass change
345  dm = iflx_water(i,j) * ice_frac(i,j) * dt_rp
346  ice_mass_new = ice_mass(i,j) + dm
347 
348  if ( ice_mass_new > 0.0_rp ) then
349  ! internal energy change
350  g = ( subsfc_temp(i,j) - ice_temp(i,j) ) * tc_dz(i,j) ! heat flux from ocean
351  de = ( iflx_hbalance(i,j) + g ) * ice_frac(i,j) * dt_rp
352  ice_temp_new = ice_temp(i,j) &
353  + ( de - ( cv_ice * ice_temp(i,j) - lhf ) * dm ) / ( cv_ice * ice_mass_new )
354 
355  ! melting ice
356  m_mlt = cv_ice * ( ice_temp_new - ocean_phy_ice_freezetemp ) * ice_mass_new &
358  m_mlt = min( max( m_mlt, 0.0_rp ), ice_mass_new )
359 
360  ice_mass_new = ice_mass_new - m_mlt
361  ice_temp_new = ice_temp_new &
362  + ( cv_ice * ice_temp_new - lhf - cv_water * ocean_phy_ice_freezetemp ) * m_mlt &
363  / ( cv_ice * ice_mass_new )
364 
365  ! ice to ocean flux
366  mass_budget = m_mlt / dt_rp
367  sflx_rhoe(i,j) = cv_water * ocean_phy_ice_freezetemp * mass_budget
368  sflx_g(i,j) = - g * ice_frac(i,j)
369  sflx_water(i,j) = mass_budget
370 
371  else
372 
373  ice_mass_new = 0.0_rp
374  ice_temp_new = ocean_phy_ice_freezetemp ! dummy
375 
376  sflx_rhoe(i,j) = cv_water * subsfc_temp(i,j) * ice_mass_new / dt_rp
377  sflx_g(i,j) = ( cv_ice * ice_temp(i,j) - lhf ) * ice_mass(i,j) &
378  - sflx_rhoe(i,j) + iflx_hbalance(i,j) * ice_frac(i,j)
379  sflx_water(i,j) = ice_mass_new ! (negative)
380 
381  endif
382 
383  ice_mass_t(i,j) = ( ice_mass_new - ice_mass(i,j) ) / dt_rp
384  ice_temp_t(i,j) = ( ice_temp_new - ice_temp(i,j) ) / dt_rp
385 
386  else
387  sflx_g(i,j) = 0.0_rp
388  sflx_water(i,j) = 0.0_rp
389  sflx_rhoe(i,j) = 0.0_rp
390  ice_mass_t(i,j) = 0.0_rp
391  ice_temp_t(i,j) = 0.0_rp
392  endif
393  enddo
394  enddo
395 
396  return
397  end subroutine ocean_phy_ice_simple
398 
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:342
scale_ocean_phy_ice_simple::ocean_phy_ice_adjustment
subroutine, public ocean_phy_ice_adjustment(OIA, OIS, OIE, OJA, OJS, OJE, calc_flag, OCEAN_DEPTH, OCEAN_TEMP, ICE_TEMP, ICE_MASS, MASS_FLUX, ENGI_FLUX, MASS_SUPL, ENGI_SUPL)
Definition: scale_ocean_phy_ice_simple.F90:204
scale_ocean_phy_ice_simple
module ocean / physics / ice / simple
Definition: scale_ocean_phy_ice_simple.F90:12
scale_file_external_input::file_external_input_regist
subroutine, public file_external_input_regist(basename, basename_add_num, number_of_files, varname, axistype, enable_periodic_year, enable_periodic_month, enable_periodic_day, step_fixed, offset, defval, check_coordinates, aggregate, allow_missing, step_limit, exist)
Regist data.
Definition: scale_file_external_input.F90:324
scale_precision
module PRECISION
Definition: scale_precision.F90:14
scale_ocean_phy_ice_simple::ocean_phy_ice_density
real(rp), public ocean_phy_ice_density
Definition: scale_ocean_phy_ice_simple.F90:45
scale_atmos_hydrometeor
module atmosphere / hydrometeor
Definition: scale_atmos_hydrometeor.F90:12
scale_calendar
module CALENDAR
Definition: scale_calendar.F90:13
scale_prc
module PROCESS
Definition: scale_prc.F90:11
scale_precision::rp
integer, parameter, public rp
Definition: scale_precision.F90:41
scale_io
module STDIO
Definition: scale_io.F90:10
scale_const
module CONSTANT
Definition: scale_const.F90:11
scale_ocean_phy_ice_simple::ocean_phy_ice_freezetemp
real(rp), public ocean_phy_ice_freezetemp
Definition: scale_ocean_phy_ice_simple.F90:44
scale_prof
module profiler
Definition: scale_prof.F90:11
scale_precision::dp
integer, parameter, public dp
Definition: scale_precision.F90:32
scale_const::const_dwatr
real(rp), parameter, public const_dwatr
density of water [kg/m3]
Definition: scale_const.F90:82
scale_ocean_phy_ice_simple::ocean_phy_ice_simple
subroutine, public ocean_phy_ice_simple(OIA, OIS, OIE, OJA, OJS, OJE, iflx_water, iflx_hbalance, subsfc_temp, TC_dz, ICE_TEMP, ICE_MASS, ICE_FRAC, calc_flag, dt, ICE_TEMP_t, ICE_MASS_t, sflx_G, sflx_water, sflx_RHOE)
Slab ocean model.
Definition: scale_ocean_phy_ice_simple.F90:293
scale_ocean_phy_ice_simple::ocean_phy_ice_setup
subroutine, public ocean_phy_ice_setup
Definition: scale_ocean_phy_ice_simple.F90:60
scale_atmos_hydrometeor::lhf
real(rp), public lhf
latent heat of fusion for use [J/kg]
Definition: scale_atmos_hydrometeor.F90:128
scale_ocean_phy_ice_simple::ocean_phy_ice_fraction
subroutine, public ocean_phy_ice_fraction(OIA, OIS, OIE, OJA, OJS, OJE, ICE_MASS, ICE_FRAC)
Definition: scale_ocean_phy_ice_simple.F90:170
scale_file_external_input
module file / external_input
Definition: scale_file_external_input.F90:12
scale_const::const_undef
real(rp), public const_undef
Definition: scale_const.F90:41
scale_io::io_fid_conf
integer, public io_fid_conf
Config file ID.
Definition: scale_io.F90:56
scale_atmos_hydrometeor::cv_water
real(rp), public cv_water
CV for water [J/kg/K].
Definition: scale_atmos_hydrometeor.F90:132
scale_atmos_hydrometeor::cv_ice
real(rp), public cv_ice
CV for ice [J/kg/K].
Definition: scale_atmos_hydrometeor.F90:134
scale_calendar::calendar_unit2sec
subroutine, public calendar_unit2sec(second, value, unit)
Convert several units to second.
Definition: scale_calendar.F90:424