SCALE-RM
Functions/Subroutines
scale_land_dyn_bucket Module Reference

module land / dynamics / bucket More...

Functions/Subroutines

subroutine, public land_dyn_bucket_setup
 Setup. More...
 
subroutine, public land_dyn_bucket (LKMAX, LKS, LKE, LIA, LIS, LIE, LJA, LJS, LJE, TEMP_t, WATER_t, ICE_t, WaterLimit, ThermalCond, HeatCapacity, WaterDiff, SFLX_GH, SFLX_water, SFLX_RHOE, exists_land, CDZ, dt, NOWDAYSEC, TEMP, WATER, ICE, RUNOFF, RUNOFF_ENGI)
 Physical processes for land submodel. More...
 

Detailed Description

module land / dynamics / bucket

Description
slab-type land model
Author
Team SCALE
NAMELIST
  • PARAM_LAND_DYN_BUCKET
    nametypedefault valuecomment
    LAND_DYN_BUCKET_T_FRZ real(RP)
    LAND_DYN_BUCKET_NUDGING logical .false. Is nudging for land physics used?
    LAND_DYN_BUCKET_NUDGING_TAU real(DP) 0.0_DP time constant for nudging [sec]
    LAND_DYN_BUCKET_NUDGING_TAU_UNIT character(len=H_SHORT) "SEC"
    LAND_DYN_BUCKET_NUDGING_BASENAME character(len=H_LONG) ''
    LAND_DYN_BUCKET_NUDGING_BASENAME_ADD_NUM logical .false.
    LAND_DYN_BUCKET_NUDGING_NUMBER_OF_FILES integer 1
    LAND_DYN_BUCKET_NUDGING_ENABLE_PERIODIC_YEAR logical .false.
    LAND_DYN_BUCKET_NUDGING_ENABLE_PERIODIC_MONTH logical .false.
    LAND_DYN_BUCKET_NUDGING_ENABLE_PERIODIC_DAY logical .false.
    LAND_DYN_BUCKET_NUDGING_STEP_FIXED integer 0
    LAND_DYN_BUCKET_NUDGING_OFFSET real(RP) 0.0_RP
    LAND_DYN_BUCKET_NUDGING_DEFVAL real(RP) = UNDEF
    LAND_DYN_BUCKET_NUDGING_CHECK_COORDINATES logical .true.
    LAND_DYN_BUCKET_NUDGING_STEP_LIMIT integer 0
    LAND_DYN_BUCKET_UPDATE_BOTTOM_TEMP logical .false. Is LAND_TEMP updated in the lowest level?
    LAND_DYN_BUCKET_UPDATE_BOTTOM_WATER logical .false. Is LAND_WATER updated in the lowest level?

History Output
No history output

Function/Subroutine Documentation

◆ land_dyn_bucket_setup()

subroutine, public scale_land_dyn_bucket::land_dyn_bucket_setup

Setup.

Definition at line 72 of file scale_land_dyn_bucket.F90.

72  use scale_prc, only: &
73  prc_abort
74  use scale_const, only: &
75  undef => const_undef, &
76  tem00 => const_tem00, &
77  dwatr => const_dwatr, &
78  dice => const_dice, &
79  cl => const_cl
80  use scale_calendar, only: &
82  use scale_file_external_input, only: &
84  use scale_atmos_hydrometeor, only: &
85  cv_water, &
86  cv_ice
87  implicit none
88 
89  namelist / param_land_dyn_bucket / &
90  land_dyn_bucket_t_frz, &
91  land_dyn_bucket_nudging, &
92  land_dyn_bucket_nudging_tau, &
93  land_dyn_bucket_nudging_tau_unit, &
94  land_dyn_bucket_nudging_basename, &
95  land_dyn_bucket_nudging_basename_add_num, &
96  land_dyn_bucket_nudging_number_of_files, &
97  land_dyn_bucket_nudging_enable_periodic_year, &
98  land_dyn_bucket_nudging_enable_periodic_month, &
99  land_dyn_bucket_nudging_enable_periodic_day, &
100  land_dyn_bucket_nudging_step_fixed, &
101  land_dyn_bucket_nudging_offset, &
102  land_dyn_bucket_nudging_defval, &
103  land_dyn_bucket_nudging_check_coordinates, &
104  land_dyn_bucket_nudging_step_limit, &
105  land_dyn_bucket_update_bottom_temp, &
106  land_dyn_bucket_update_bottom_water
107 
108  integer :: ierr
109  !---------------------------------------------------------------------------
110 
111  log_newline
112  log_info("LAND_DYN_BUCKET_setup",*) 'Setup'
113 
114  land_dyn_bucket_nudging_defval = undef
115  land_dyn_bucket_t_frz = tem00
116 
117  !--- read namelist
118  rewind(io_fid_conf)
119  read(io_fid_conf,nml=param_land_dyn_bucket,iostat=ierr)
120  if( ierr < 0 ) then !--- missing
121  log_info("LAND_DYN_BUCKET_setup",*) 'Not found namelist. Default used.'
122  elseif( ierr > 0 ) then !--- fatal error
123  log_error("LAND_DYN_BUCKET_setup",*) 'Not appropriate names in namelist PARAM_LAND_DYN_BUCKET. Check!'
124  call prc_abort
125  endif
126  log_nml(param_land_dyn_bucket)
127 
128  if ( land_dyn_bucket_nudging ) then
129  call calendar_unit2sec( land_dyn_bucket_nudging_tausec, land_dyn_bucket_nudging_tau, land_dyn_bucket_nudging_tau_unit )
130 
131  log_info("LAND_DYN_BUCKET_setup",*) 'Use nudging for LAND physics : ON'
132  log_info("LAND_DYN_BUCKET_setup",*) 'Relaxation time Tau [sec] : ', land_dyn_bucket_nudging_tausec
133 
134  if ( land_dyn_bucket_nudging_tausec <= 0.0_rp ) then
135  log_info("LAND_DYN_BUCKET_setup",*) 'Tau<=0 means that LST is completely replaced by the external data.'
136  replace = .true.
137  endif
138 
139  if ( land_dyn_bucket_nudging_basename == '' ) then
140  log_error("LAND_DYN_BUCKET_setup",*) 'LAND_DYN_BUCKET_nudging_basename is necessary !!'
141  call prc_abort
142  end if
143 
144  call file_external_input_regist( land_dyn_bucket_nudging_basename, & ! [IN]
145  land_dyn_bucket_nudging_basename_add_num, & ! [IN]
146  land_dyn_bucket_nudging_number_of_files, & ! [IN]
147  'LAND_TEMP', & ! [IN]
148  'LXY', & ! [IN]
149  land_dyn_bucket_nudging_enable_periodic_year, & ! [IN]
150  land_dyn_bucket_nudging_enable_periodic_month, & ! [IN]
151  land_dyn_bucket_nudging_enable_periodic_day, & ! [IN]
152  land_dyn_bucket_nudging_step_fixed, & ! [IN]
153  land_dyn_bucket_nudging_offset, & ! [IN]
154  land_dyn_bucket_nudging_defval, & ! [IN]
155  check_coordinates = land_dyn_bucket_nudging_check_coordinates, & ! [IN]
156  step_limit = land_dyn_bucket_nudging_step_limit, & ! [IN]
157  allow_missing = (.not. replace) ) ! [IN]
158 
159  call file_external_input_regist( land_dyn_bucket_nudging_basename, & ! [IN]
160  land_dyn_bucket_nudging_basename_add_num, & ! [IN]
161  land_dyn_bucket_nudging_number_of_files, & ! [IN]
162  'LAND_WATER', & ! [IN]
163  'LXY', & ! [IN]
164  land_dyn_bucket_nudging_enable_periodic_year, & ! [IN]
165  land_dyn_bucket_nudging_enable_periodic_month, & ! [IN]
166  land_dyn_bucket_nudging_enable_periodic_day, & ! [IN]
167  land_dyn_bucket_nudging_step_fixed, & ! [IN]
168  land_dyn_bucket_nudging_offset, & ! [IN]
169  land_dyn_bucket_nudging_defval, & ! [IN]
170  check_coordinates = land_dyn_bucket_nudging_check_coordinates, & ! [IN]
171  step_limit = land_dyn_bucket_nudging_step_limit, & ! [IN]
172  allow_missing = (.not. replace) ) ! [IN]
173 
174  log_info("LAND_DYN_BUCKET_setup",*) 'Use nudging for Land physics: ON'
175  else
176  log_info("LAND_DYN_BUCKET_setup",*) 'Use nudging for Land physics: OFF'
177  end if
178 
179  water_denscs = dwatr * cv_water
180  ice_denscs = dice * cv_ice
181 
182  log_newline
183  log_info("LAND_DYN_BUCKET_setup",*) 'Update soil temperature of bottom layer? : ', land_dyn_bucket_update_bottom_temp
184  log_info("LAND_DYN_BUCKET_setup",*) 'Update soil moisture of bottom layer? : ', land_dyn_bucket_update_bottom_water
185 
186  return

References scale_calendar::calendar_unit2sec(), scale_const::const_cl, scale_const::const_dice, scale_const::const_dwatr, scale_const::const_tem00, scale_const::const_undef, scale_atmos_hydrometeor::cv_ice, scale_atmos_hydrometeor::cv_water, scale_file_external_input::file_external_input_regist(), scale_io::io_fid_conf, and scale_prc::prc_abort().

Referenced by mod_land_driver::land_driver_setup().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ land_dyn_bucket()

subroutine, public scale_land_dyn_bucket::land_dyn_bucket ( integer, intent(in)  LKMAX,
integer, intent(in)  LKS,
integer, intent(in)  LKE,
integer, intent(in)  LIA,
integer, intent(in)  LIS,
integer, intent(in)  LIE,
integer, intent(in)  LJA,
integer, intent(in)  LJS,
integer, intent(in)  LJE,
real(rp), dimension (lkmax,lia,lja), intent(in)  TEMP_t,
real(rp), dimension (lkmax,lia,lja), intent(in)  WATER_t,
real(rp), dimension (lkmax,lia,lja), intent(in)  ICE_t,
real(rp), dimension (lia,lja), intent(in)  WaterLimit,
real(rp), dimension (lia,lja), intent(in)  ThermalCond,
real(rp), dimension(lia,lja), intent(in)  HeatCapacity,
real(rp), dimension (lia,lja), intent(in)  WaterDiff,
real(rp), dimension (lia,lja), intent(in)  SFLX_GH,
real(rp), dimension (lia,lja), intent(in)  SFLX_water,
real(rp), dimension (lia,lja), intent(in)  SFLX_RHOE,
logical, dimension (lia,lja), intent(in)  exists_land,
real(rp), dimension (lkmax), intent(in)  CDZ,
real(dp), intent(in)  dt,
real(dp), intent(in)  NOWDAYSEC,
real(rp), dimension (lkmax,lia,lja), intent(inout)  TEMP,
real(rp), dimension(lkmax,lia,lja), intent(inout)  WATER,
real(rp), dimension (lkmax,lia,lja), intent(inout)  ICE,
real(rp), dimension (lia,lja), intent(out)  RUNOFF,
real(rp), dimension(lia,lja), intent(out)  RUNOFF_ENGI 
)

Physical processes for land submodel.

Definition at line 204 of file scale_land_dyn_bucket.F90.

204  use scale_const, only: &
205  undef => const_undef, &
206  dwatr => const_dwatr, &
207  dice => const_dice, &
208  emelt => const_emelt
209  use scale_prc, only: &
210  prc_abort
211  use scale_file_external_input, only: &
212  file_external_input_update
213  use scale_matrix, only: &
214  matrix_solver_tridiagonal
215  use scale_atmos_hydrometeor, only: &
216  cv_water, &
217  cv_ice, &
218  lhf
219  implicit none
220  integer, intent(in) :: LKMAX, LKS, LKE
221  integer, intent(in) :: LIA, LIS, LIE
222  integer, intent(in) :: LJA, LJS, LJE
223 
224  real(RP), intent(in) :: TEMP_t (LKMAX,LIA,LJA)
225  real(RP), intent(in) :: WATER_t (LKMAX,LIA,LJA)
226  real(RP), intent(in) :: ICE_t (LKMAX,LIA,LJA)
227  real(RP), intent(in) :: WaterLimit (LIA,LJA)
228  real(RP), intent(in) :: ThermalCond (LIA,LJA)
229  real(RP), intent(in) :: HeatCapacity(LIA,LJA)
230  real(RP), intent(in) :: WaterDiff (LIA,LJA)
231  real(RP), intent(in) :: SFLX_GH (LIA,LJA) ! positive for downward
232  real(RP), intent(in) :: SFLX_water (LIA,LJA) ! positive for downward
233  real(RP), intent(in) :: SFLX_RHOE (LIA,LJA) ! positive for downward
234  logical, intent(in) :: exists_land (LIA,LJA)
235  real(RP), intent(in) :: CDZ (LKMAX)
236  real(DP), intent(in) :: dt
237  real(DP), intent(in) :: NOWDAYSEC
238 
239  real(RP), intent(inout) :: TEMP (LKMAX,LIA,LJA)
240  real(RP), intent(inout) :: WATER(LKMAX,LIA,LJA)
241  real(RP), intent(inout) :: ICE (LKMAX,LIA,LJA)
242 
243  real(RP), intent(out) :: RUNOFF (LIA,LJA)
244  real(RP), intent(out) :: RUNOFF_ENGI(LIA,LJA) ! internal energy of the runoff water
245 
246  logical :: error
247 
248  real(RP) :: TEMP1 (LKMAX,LIA,LJA)
249  real(RP) :: WATER1(LKMAX,LIA,LJA)
250  real(RP) :: ICE1 (LKMAX,LIA,LJA)
251 
252  real(RP) :: kappa (LKMAX)
253 
254  real(RP) :: U(LKMAX,LIA,LJA)
255  real(RP) :: M(LKMAX,LIA,LJA)
256  real(RP) :: L(LKMAX,LIA,LJA)
257  real(RP) :: V(LKMAX,LIA,LJA)
258 
259  real(RP) :: NDG_TEMP (LKMAX,LIA,LJA)
260  real(RP) :: NDG_WATER(LKMAX,LIA,LJA)
261 
262  real(RP) :: MASS_total(LKMAX)
263  real(RP) :: MASS_water(LKMAX)
264  real(RP) :: MASS_ice(LKMAX)
265 
266  real(RP) :: ENGI(LKMAX,LIA,LJA)
267  real(RP) :: CS
268  real(RP) :: CL
269 
270  real(RP) :: flux(LKS-1:LKE)
271 
272  real(RP) :: ro, rw, ri
273  real(RP) :: sw
274 
275  integer :: k, i, j
276  !---------------------------------------------------------------------------
277 
278  log_progress(*) 'land / dynamics / bucket'
279 
280  if ( land_dyn_bucket_nudging ) then
281 
282  call file_external_input_update( &
283  'LAND_TEMP', & ! (in)
284  nowdaysec, & ! (in)
285  temp1, & ! (out)
286  error ) ! (out)
287  if ( error ) then
288  log_error("LAND_DYN_BUCKET",*) 'Requested data is not found!'
289  call prc_abort
290  end if
291 
292  call file_external_input_update( &
293  'LAND_WATER', & ! (in)
294  nowdaysec, & ! (in)
295  water1, & ! (out)
296  error ) ! (out)
297  if ( error ) then
298  log_error("LAND_DYN_BUCKET",*) 'Requested data is not found!'
299  call prc_abort
300  end if
301 
302  if ( .not. replace ) then
303  ! nudging is used
304 
305  !$omp parallel do
306  do j = ljs,lje
307  do i = lis,lie
308  do k = lks,lke
309  if ( temp1(k,i,j) == undef ) then
310  ndg_temp(k,i,j) = 0.0_rp
311  else
312  ndg_temp(k,i,j) = ( temp1(k,i,j) - temp(k,i,j) ) / land_dyn_bucket_nudging_tausec * dt
313  end if
314  end do
315  end do
316  end do
317 
318  !$omp parallel do
319  do j = ljs,lje
320  do i = lis,lie
321  do k = lks,lke
322  if ( water1(k,i,j) == undef ) then
323  ndg_water(k,i,j) = 0.0_rp
324  else
325  ndg_water(k,i,j) = ( water1(k,i,j) - ( water(k,i,j) + ice(k,i,j) ) ) / land_dyn_bucket_nudging_tausec * dt
326  end if
327  end do
328  end do
329  end do
330 
331  end if
332 
333  if ( .not. land_dyn_bucket_update_bottom_water ) then
334  !$omp parallel do
335  do j = ljs, lje
336  do i = lis, lie
337  ndg_water(lke,i,j) = 0.0_rp
338  end do
339  end do
340  end if
341 
342  if ( .not. land_dyn_bucket_update_bottom_temp ) then
343  !$omp parallel do
344  do j = ljs, lje
345  do i = lis, lie
346  ndg_temp(lke,i,j) = 0.0_rp
347  end do
348  end do
349  end if
350 
351  else
352  ! nudging is NOT used
353 
354  !$omp parallel do
355  do j = ljs,lje
356  do i = lis,lie
357  do k = lks,lke
358  ndg_temp(k,i,j) = 0.0_rp
359  ndg_water(k,i,j) = 0.0_rp
360  end do
361  end do
362  end do
363 
364  end if
365 
366  if ( .not. replace ) then
367 
368  !$omp parallel do &
369  !$omp private(MASS_total, MASS_water, MASS_ice, CS)
370  do j = ljs, lje
371  do i = lis, lie
372  if ( exists_land(i,j) ) then
373  do k = lks, lke
374  mass_total(k) = dwatr * water(k,i,j) + dice * ice(k,i,j)
375  end do
376  mass_total(lks) = mass_total(lks) + dt * sflx_water(i,j) / cdz(lks)
377 
378  cs = ( 1.0_rp - waterlimit(i,j) ) * heatcapacity(i,j)
379  do k = lks, lke
380  engi(k,i,j) = ( cs + water_denscs * water(k,i,j) + ice_denscs * ice(k,i,j) ) * temp(k,i,j) - lhf * dice * ice(k,i,j)
381  end do
382  engi(lks,i,j) = engi(lks,i,j) + dt * ( sflx_gh(i,j) + sflx_rhoe(i,j) ) / cdz(lks)
383 
384  ! phase change
385  do k = lks, lke
386  mass_ice(k) = min( mass_total(k), max( 0.0_rp, &
387  ( engi(k,i,j) - ( cs + cv_water * mass_total(k) ) * land_dyn_bucket_t_frz ) &
388  / ( ( cv_ice - cv_water ) * land_dyn_bucket_t_frz - lhf ) &
389  ) )
390  mass_water(k) = mass_total(k) - mass_ice(k)
391  v(k,i,j) = mass_water(k) / dwatr
392  ice1(k,i,j) = mass_ice(k) / dice
393  temp1(k,i,j) = ( engi(k,i,j) + lhf * mass_ice(k) ) &
394  / ( cs + cv_water * mass_water(k) + cv_ice * mass_ice(k) )
395  end do
396  end if
397  end do
398  end do
399 
400 
401  !$omp parallel do
402  do j = ljs, lje
403  do i = lis, lie
404  if ( exists_land(i,j) ) then
405  l(lks,i,j) = 0.0_rp
406  u(lks,i,j) = -2.0_rp * waterdiff(i,j) / ( cdz(lks) * ( cdz(lks) + cdz(lks+1) ) ) * dt
407  m(lks,i,j) = 1.0_rp - l(lks,i,j) - u(lks,i,j)
408  end if
409  end do
410  end do
411 
412  if ( land_dyn_bucket_update_bottom_water ) then
413  !$omp parallel do
414  do j = ljs, lje
415  do i = lis, lie
416  if ( exists_land(i,j) ) then
417  l(lke,i,j) = -2.0_rp * waterdiff(i,j) / ( cdz(lke) * ( cdz(lke) + cdz(lke-1) ) ) * dt
418  end if
419  end do
420  end do
421  else
422  !$omp parallel do
423  do j = ljs, lje
424  do i = lis, lie
425  if ( exists_land(i,j) ) then
426  l(lke,i,j) = 0.0_rp
427  end if
428  end do
429  end do
430  end if
431  !$omp parallel do
432  do j = ljs, lje
433  do i = lis, lie
434  if ( exists_land(i,j) ) then
435  u(lke,i,j) = 0.0_rp
436  m(lke,i,j) = 1.0_rp - l(lke,i,j) - u(lke,i,j)
437  end if
438  end do
439  end do
440 
441  !$omp parallel do
442  do j = ljs, lje
443  do i = lis, lie
444  do k = lks+1, lke-1
445  if ( exists_land(i,j) ) then
446  l(k,i,j) = -2.0_rp * waterdiff(i,j) / ( cdz(k) * ( cdz(k) + cdz(k-1) ) ) * dt
447  u(k,i,j) = -2.0_rp * waterdiff(i,j) / ( cdz(k) * ( cdz(k) + cdz(k+1) ) ) * dt
448  m(k,i,j) = 1.0_rp - l(k,i,j) - u(k,i,j)
449  end if
450  end do
451  end do
452  end do
453 
454  call matrix_solver_tridiagonal( lkmax, 1, lkmax, &
455  lia, lis, lie, &
456  lja, ljs, lje, &
457  u(:,:,:), m(:,:,:), l(:,:,:), & ! [IN]
458  v(:,:,:), & ! [IN]
459  water1(:,:,:), & ! [OUT]
460  mask = exists_land(:,:) ) ! [IN]
461 
462  ! temperature
463 
464  flux(lks-1) = 0.0_rp
465  flux(lke) = 0.0_rp
466 
467  !$omp parallel do &
468  !$omp private(kappa,CS,CL,sw) &
469  !$omp firstprivate(flux)
470  do j = ljs, lje
471  do i = lis, lie
472  if ( exists_land(i,j) ) then
473 
474  cs = ( 1.0_rp - waterlimit(i,j) ) * heatcapacity(i,j)
475  do k = lks, lke
476  kappa(k) = thermalcond(i,j) + 0.5_rp * water1(k,i,j)**(1.0_rp/3.0_rp)
477  end do
478 
479  do k = lks, lke-1
480  flux(k) = - 2.0_rp * dwatr * waterdiff(i,j) * ( water1(k+1,i,j) - water1(k,i,j) ) / ( cdz(k+1) + cdz(k) )
481  sw = 0.5_rp - sign( 0.5_rp, flux(k) )
482  flux(k) = flux(k) * cv_water * ( temp1(k+1,i,j) * sw + temp1(k,i,j) * ( 1.0_rp - sw ) )
483  end do
484  if ( .not. land_dyn_bucket_update_bottom_temp ) then
485  flux(lke) = flux(lke-1)
486  end if
487 
488  do k = lks, lke
489  v(k,i,j) = engi(k,i,j) + lhf * dice * ice1(k,i,j) &
490  - dt * ( flux(k) - flux(k-1) ) / cdz(k)
491  end do
492 
493  cl = cs + water_denscs * water1(lks,i,j) + ice_denscs * ice1(lks,i,j)
494  l(lks,i,j) = 0.0_rp
495  u(lks,i,j) = - ( kappa(lks) + kappa(lks+1) ) / ( cdz(lks) * ( cdz(lks) + cdz(lks+1) ) ) * dt
496  m(lks,i,j) = cl - l(lks,i,j) - u(lks,i,j)
497 
498  cl = cs + water_denscs * water1(lke,i,j) + ice_denscs * ice1(lke,i,j)
499  if ( land_dyn_bucket_update_bottom_water ) then
500 
501  l(lke,i,j) = - ( kappa(lke) + kappa(lke-1) ) / ( cdz(lke) * ( cdz(lke) + cdz(lke-1) ) ) * dt
502  else
503  l(lke,i,j) = 0.0_rp
504  end if
505  u(lke,i,j) = 0.0_rp
506  m(lke,i,j) = cl - l(lke,i,j) - u(lke,i,j)
507 
508  do k = lks+1, lke-1
509  cl = cs + water_denscs * water1(k,i,j) + ice_denscs * ice1(k,i,j)
510  l(k,i,j) = - ( kappa(k) + kappa(k-1) ) / ( cdz(k) * ( cdz(k) + cdz(k-1) ) ) * dt
511  u(k,i,j) = - ( kappa(k) + kappa(k+1) ) / ( cdz(k) * ( cdz(k) + cdz(k+1) ) ) * dt
512  m(k,i,j) = cl - l(k,i,j) - u(k,i,j)
513  end do
514 
515  end if
516  end do
517  end do
518 
519  call matrix_solver_tridiagonal( lkmax, 1, lkmax, &
520  lia, lis, lie, &
521  lja, ljs, lje, &
522  u(:,:,:), m(:,:,:), l(:,:,:), & ! [IN]
523  v(:,:,:), & ! [IN]
524  temp1(:,:,:), & ! [OUT]
525  mask = exists_land(:,:) ) ! [IN]
526 
527 
528  !$omp parallel do
529  do j = ljs, lje
530  do i = lis, lie
531  if ( exists_land(i,j) ) then
532  do k = lks, lke
533  temp1(k,i,j) = temp1(k,i,j) + ndg_temp(k,i,j)
534  end do
535  end if
536  end do
537  end do
538 
539 
540  !$omp parallel do &
541  !$omp private(ro,rw,ri)
542  do j = ljs, lje
543  do i = lis, lie
544  if ( exists_land(i,j) ) then
545  do k = lks, lke
546  if ( temp1(k,i,j) >= land_dyn_bucket_t_frz ) then
547  water1(k,i,j) = water1(k,i,j) + ndg_water(k,i,j)
548  else
549  ice1(k,i,j) = ice1(k,i,j) + ndg_water(k,i,j)
550  end if
551  end do
552 
553  ! runoff of soil moisture (vertical sum)
554  runoff(i,j) = 0.0_rp
555  runoff_engi(i,j) = 0.0_rp
556  do k = lks, lke
557  ro = max( water1(k,i,j) + ice1(k,i,j) - waterlimit(i,j), 0.0_rp )
558  rw = min( ro, water1(k,i,j) )
559  ri = ro - rw
560  water1(k,i,j) = water1(k,i,j) - rw
561  ice1(k,i,j) = ice1(k,i,j) - ri
562  rw = rw * dwatr / dt
563  ri = ri * dice / dt
564  runoff(i,j) = runoff(i,j) + ( rw + ri ) * cdz(k)
565  runoff_engi(i,j) = runoff_engi(i,j) &
566  + ( ( rw * cv_water + ri * cv_ice ) * temp1(k,i,j) - ri * lhf ) * cdz(k)
567  end do
568  end if
569  end do
570  end do
571 
572 
573  if ( .not. land_dyn_bucket_update_bottom_water ) then
574  !$omp parallel do
575  do j = ljs, lje
576  do i = lis, lie
577  if ( exists_land(i,j) ) then
578  water1(lke,i,j) = water(lke,i,j)
579  ice1(lke,i,j) = ice(lke,i,j)
580  end if
581  end do
582  end do
583  endif
584 
585  if ( .not. land_dyn_bucket_update_bottom_temp ) then
586  !$omp parallel do
587  do j = ljs, lje
588  do i = lis, lie
589  if ( exists_land(i,j) ) then
590  temp1(lke,i,j) = temp(lke,i,j)
591  end if
592  end do
593  end do
594  endif
595 
596  end if
597 
598 
599  !$omp parallel do
600  do j = ljs, lje
601  do i = lis, lie
602  if( exists_land(i,j) ) then
603  do k = lks, lke
604  temp(k,i,j) = temp1(k,i,j)
605  water(k,i,j) = water1(k,i,j)
606  ice(k,i,j) = ice1(k,i,j)
607  end do
608  end if
609  end do
610  end do
611 
612  return

References scale_const::const_dice, scale_const::const_dwatr, scale_const::const_emelt, scale_const::const_undef, scale_atmos_hydrometeor::cv_ice, scale_atmos_hydrometeor::cv_water, scale_atmos_hydrometeor::lhf, and scale_prc::prc_abort().

Referenced by mod_land_driver::land_driver_update().

Here is the call graph for this function:
Here is the caller graph for this function:
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:342
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_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_const
module CONSTANT
Definition: scale_const.F90:11
scale_matrix
module MATRIX
Definition: scale_matrix.F90:11
scale_atmos_hydrometeor::lhf
real(rp), public lhf
latent heat of fusion for use [J/kg]
Definition: scale_atmos_hydrometeor.F90:128
scale_file_external_input
module file / external_input
Definition: scale_file_external_input.F90:12
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