SICOPOLIS V3.2
 All Classes Files Functions Variables Macros
boundary.F90
Go to the documentation of this file.
1 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
2 !
3 ! Subroutine : b o u n d a r y
4 !
5 !> @file
6 !!
7 !! Computation of the surface temperature (must be less than 0 deg C!)
8 !! and of the accumulation-ablation function.
9 !!
10 !! @section Copyright
11 !!
12 !! Copyright 2009-2016 Ralf Greve
13 !!
14 !! @section License
15 !!
16 !! This file is part of SICOPOLIS.
17 !!
18 !! SICOPOLIS is free software: you can redistribute it and/or modify
19 !! it under the terms of the GNU General Public License as published by
20 !! the Free Software Foundation, either version 3 of the License, or
21 !! (at your option) any later version.
22 !!
23 !! SICOPOLIS is distributed in the hope that it will be useful,
24 !! but WITHOUT ANY WARRANTY; without even the implied warranty of
25 !! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
26 !! GNU General Public License for more details.
27 !!
28 !! You should have received a copy of the GNU General Public License
29 !! along with SICOPOLIS. If not, see <http://www.gnu.org/licenses/>.
30 !<
31 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
32 
33 !-------------------------------------------------------------------------------
34 !> Computation of the surface temperature (must be less than 0 deg C!)
35 !! and of the accumulation-ablation function.
36 !<------------------------------------------------------------------------------
37 subroutine boundary(time, dtime, dxi, deta, &
38  delta_ts, glac_index, z_sl, dzsl_dtau, z_mar)
39 
40 use sico_types
42 use sico_vars
43 
44 implicit none
45 
46 real(dp), intent(in) :: time, dtime, dxi, deta
47 
48 real(dp), intent(out) :: delta_ts, glac_index, dzsl_dtau, z_mar
49 real(dp), intent(inout) :: z_sl
50 
51 ! Further return variables
52 ! (defined as global variables in module sico_variables):
53 !
54 ! accum(j,i), evap(j,i), runoff(j,i), as_perp(j,i), temp_s(j,i)
55 
56 integer(i4b) :: i, j, n
57 integer(i4b) :: i_gr, i_kl
58 real(dp) :: z_sl_old
59 real(dp) :: z_sl_min, t1, t2, t3, t4, t5, t6
60 real(dp) :: time_gr, time_kl
61 real(dp) :: z_sle_present, z_sle_help
62 real(dp), dimension(0:JMAX,0:IMAX,0:12) :: precip
63 real(dp), dimension(0:JMAX,0:IMAX) :: &
64  melt, melt_star
65 !real(dp), dimension(0:JMAX,0:IMAX) :: &
66 ! snowfall, rainfall, melt, melt_star
67 !snowfall, rainfall declared in sico_variables because of output5.F90
68 real(dp), dimension(0:JMAX,0:IMAX,12) :: temp_mm
69 real(dp), dimension(0:JMAX,0:IMAX) :: temp_ma
70 real(dp), dimension(12) :: temp_mm_help
71 real(dp) :: temp_jja_help
72 real(dp), dimension(0:JMAX,0:IMAX) :: et
73 real(dp) :: gamma_t, temp_diff
74 real(dp) :: gamma_p, zs_thresh, &
75  temp_rain, temp_snow, &
76  inv_delta_temp_rain_snow, coeff(0:5), inv_sqrt2_s_stat, &
77  precip_fact, frac_solid
78 real(dp) :: s_stat, beta1, beta2, pmax, mu, lambda_lti, temp_lti
79 logical, dimension(0:JMAX,0:IMAX) :: check_point
80 
81 real(dp), parameter :: &
82  inv_twelve = 1.0_dp/12.0_dp, one_third = 1.0_dp/3.0_dp
83 
84 
85 !-------- Initialization of intent(out) variables --------
86 
87 z_sl_old = z_sl
88 
89 delta_ts = 0.0_dp
90 glac_index = 0.0_dp
91 z_sl = 0.0_dp
92 dzsl_dtau = 0.0_dp
93 z_mar = 0.0_dp
94 
95 !-------- Surface-temperature deviation from present values --------
96 
97 #if TSURFACE==1
98 delta_ts = delta_ts0
99 
100 ! ! Steady state with prescribed constant
101 ! ! air-temperature deviation
102 #elif TSURFACE==3
103 delta_ts = sine_amplit &
104  *cos(2.0_dp*pi*time/(sine_period*year_sec)) &
105  -sine_amplit
106 ! ! Sinusoidal air-temperature forcing
107 #elif TSURFACE==4
108 
109 ! ------ delta_ts from ice-core record
110 
111 if (time/year_sec.lt.real(grip_time_min,dp)) then
112  delta_ts = griptemp(0)
113 else if (time/year_sec.lt.real(grip_time_max,dp)) then
114 
115  i_kl = floor(((time/year_sec)-real(grip_time_min,dp))/real(grip_time_stp,dp))
116  i_kl = max(i_kl, 0)
117 
118  i_gr = ceiling(((time/year_sec)-real(grip_time_min,dp))/real(grip_time_stp,dp))
119  i_gr = min(i_gr, ndata_grip)
120 
121  if (i_kl.eq.i_gr) then
122 
123  delta_ts = griptemp(i_kl)
124 
125  else
126 
127  time_kl = (grip_time_min + i_kl*grip_time_stp) *year_sec
128  time_gr = (grip_time_min + i_gr*grip_time_stp) *year_sec
129 
130  delta_ts = griptemp(i_kl) &
131  +(griptemp(i_gr)-griptemp(i_kl)) &
132  *(time-time_kl)/(time_gr-time_kl)
133  ! linear interpolation of the ice-core data
134 
135  end if
136 
137 else
138  delta_ts = griptemp(ndata_grip)
139 end if
140 
141 delta_ts = delta_ts * grip_temp_fact
142 ! ! modification by constant factor
143 
144 !-------- Glacial index --------
145 
146 #elif TSURFACE==5
147 
148 if (time/year_sec < real(gi_time_min,dp)) then
149  glac_index = glacial_index(0)
150 else if (time/year_sec < real(gi_time_max,dp)) then
151 
152  i_kl = floor(((time/year_sec)-real(gi_time_min,dp))/real(gi_time_stp,dp))
153  i_kl = max(i_kl, 0)
154 
155  i_gr = ceiling(((time/year_sec)-real(gi_time_min,dp))/real(gi_time_stp,dp))
156  i_gr = min(i_gr, ndata_gi)
157 
158  if (i_kl == i_gr) then
159 
160  glac_index = glacial_index(i_kl)
161 
162  else
163 
164  time_kl = (gi_time_min + i_kl*gi_time_stp) *year_sec
165  time_gr = (gi_time_min + i_gr*gi_time_stp) *year_sec
166 
167  glac_index = glacial_index(i_kl) &
168  +(glacial_index(i_gr)-glacial_index(i_kl)) &
169  *(time-time_kl)/(time_gr-time_kl)
170  ! linear interpolation of the glacial-index data
171 
172  end if
173 
174 else
175  glac_index = glacial_index(ndata_gi)
176 end if
177 
178 #endif
179 
180 !-------- Sea level --------
181 
182 #if SEA_LEVEL==1
183 ! ------ constant sea level
184 z_sl = z_sl0
185 
186 #elif SEA_LEVEL==2
187 ! ------ saw-tooth-shaped palaeoclimatic sea-level forcing
188 
189 z_sl_min = -130.0_dp
190 
191 t1 = -250000.0_dp *year_sec
192 t2 = -140000.0_dp *year_sec
193 t3 = -125000.0_dp *year_sec
194 t4 = -21000.0_dp *year_sec
195 t5 = -8000.0_dp *year_sec
196 t6 = 0.0_dp *year_sec
197 
198 if (time.lt.t1) then
199  z_sl = 0.0_dp
200 else if (time.lt.t2) then
201  z_sl = z_sl_min*(time-t1)/(t2-t1)
202 else if (time.lt.t3) then
203  z_sl = -z_sl_min*(time-t3)/(t3-t2)
204 else if (time.lt.t4) then
205  z_sl = z_sl_min*(time-t3)/(t4-t3)
206 else if (time.lt.t5) then
207  z_sl = -z_sl_min*(time-t5)/(t5-t4)
208 else if (time.lt.t6) then
209  z_sl = 0.0_dp
210 else
211  z_sl = 0.0_dp
212 end if
213 
214 #elif SEA_LEVEL==3
215 
216 ! ------ z_sl from the SPECMAP record
217 
218 if (time/year_sec.lt.real(specmap_time_min,dp)) then
219  z_sl = specmap_zsl(0)
220 else if (time/year_sec.lt.real(specmap_time_max,dp)) then
221 
222  i_kl = floor(((time/year_sec)-real(specmap_time_min,dp))/real(specmap_time_stp,dp))
223  i_kl = max(i_kl, 0)
224 
225  i_gr = ceiling(((time/year_sec)-real(specmap_time_min,dp))/real(specmap_time_stp,dp))
226  i_gr = min(i_gr, ndata_specmap)
227 
228  if (i_kl.eq.i_gr) then
229 
230  z_sl = specmap_zsl(i_kl)
231 
232  else
233 
234  time_kl = (specmap_time_min + i_kl*specmap_time_stp) *year_sec
235  time_gr = (specmap_time_min + i_gr*specmap_time_stp) *year_sec
236 
237  z_sl = specmap_zsl(i_kl) &
238  +(specmap_zsl(i_gr)-specmap_zsl(i_kl)) &
239  *(time-time_kl)/(time_gr-time_kl)
240  ! linear interpolation of the sea-level data
241 
242  end if
243 
244 else
245  z_sl = specmap_zsl(ndata_specmap)
246 end if
247 
248 #endif
249 
250 ! ------ Time derivative of the sea level
251 
252 if ( z_sl_old > -999999.9_dp ) then
253  dzsl_dtau = (z_sl-z_sl_old)/dtime
254 else ! only dummy value for z_sl_old available
255  dzsl_dtau = 0.0_dp
256 end if
257 
258 ! ------ Minimum bedrock elevation for extent of marine ice
259 
260 #if MARGIN==2
261 
262 #if ( MARINE_ICE_CALVING==2 || MARINE_ICE_CALVING==3 )
263 z_mar = z_mar
264 #elif ( MARINE_ICE_CALVING==4 || MARINE_ICE_CALVING==5 )
265 z_mar = fact_z_mar*z_sl
266 #elif ( MARINE_ICE_CALVING==6 || MARINE_ICE_CALVING==7 )
267 if (z_sl >= -80.0_dp) then
268  z_mar = 2.5_dp*z_sl
269 else
270  z_mar = 10.25_dp*(z_sl+80.0_dp)-200.0_dp
271 end if
272 z_mar = fact_z_mar*z_mar
273 #endif
274 
275 #endif
276 
277 ! ------ Update of the mask according to the sea level
278 
279 ! ---- Check all sea and floating-ice points and their direct
280 ! neighbours
281 
282 do i=0, imax
283 do j=0, jmax
284  check_point(j,i) = .false.
285 end do
286 end do
287 
288 do i=1, imax-1
289 do j=1, jmax-1
290  if (maske(j,i).ge.2) then
291  check_point(j ,i ) = .true.
292  check_point(j ,i+1) = .true.
293  check_point(j ,i-1) = .true.
294  check_point(j+1,i ) = .true.
295  check_point(j-1,i ) = .true.
296  end if
297 end do
298 end do
299 
300 do i=1, imax-1
301 do j=1, jmax-1
302  if (check_point(j,i)) then
303  maske_neu(j,i) = mask_update(z_sl, i, j)
304  end if
305 end do
306 end do
307 
308 ! ---- Assign new values of the mask
309 
310 do i=1, imax-1
311 do j=1, jmax-1
312  if (check_point(j,i)) then
313  maske(j,i) = maske_neu(j,i)
314  end if
315 end do
316 end do
317 
318 !-------- Surface air temperatures --------
319 
320 gamma_t = -4.5e-03_dp ! atmospheric lapse rate
321 
322 do i=0, imax
323 do j=0, jmax
324 
325 #if (TSURFACE <= 4)
326 
327 ! ------ Correction of present monthly temperatures with elevation changes
328 ! and temperature deviation delta_ts
329 
330  temp_diff = gamma_t*(zs(j,i)-zs_ref(j,i)) + delta_ts
331 
332  do n=1, 12 ! month counter
333  temp_mm(j,i,n) = temp_mm_present(j,i,n) + temp_diff
334  end do
335 
336 #elif (TSURFACE == 5)
337 
338 ! ------ Correction of present monthly temperatures with LGM anomaly and
339 ! glacial index as well as elevation changes
340 
341  temp_diff = gamma_t*(zs(j,i)-zs_ref(j,i))
342 
343  do n=1, 12 ! month counter
344  temp_mm(j,i,n) = temp_mm_present(j,i,n) &
345  + glac_index*temp_mm_lgm_anom(j,i,n) &
346  + temp_diff
347  end do
348 
349 #endif
350 
351 ! ------ Mean annual air temperature
352 
353  temp_ma(j,i) = 0.0_dp ! initialisation value
354 
355  do n=1, 12 ! month counter
356  temp_ma(j,i) = temp_ma(j,i) + temp_mm(j,i,n)*inv_twelve
357  end do
358 
359 end do
360 end do
361 
362 !-------- Accumulation-ablation function as_perp --------
363 
364 #if (ELEV_DESERT == 1)
365 
366 gamma_p = gamma_p*1.0e-03_dp ! Precipitation lapse rate
367  ! for elevation desertification, in m^(-1)
368 zs_thresh = zs_thresh ! Elevation threshold, in m
369 
370 #endif
371 
372 #if (SOLID_PRECIP == 1) /* Marsiat (1994) */
373 
374 temp_rain = 7.0_dp ! Threshold monthly mean temperature for
375  ! precipitation = 100% rain, in deg C
376 temp_snow = -10.0_dp ! Threshold monthly mean temperature for &
377  ! precipitation = 100% snow, in deg C
378 
379 inv_delta_temp_rain_snow = 1.0_dp/(temp_rain-temp_snow)
380 
381 #elif (SOLID_PRECIP == 2) /* Bales et al. (2009) */
382 
383 temp_rain = 7.2_dp ! Threshold monthly mean temperature for &
384  ! precipitation = 100% rain, in deg C
385 temp_snow = -11.6_dp ! Threshold monthly mean temperature for &
386  ! precipitation = 100% snow, in deg C
387 
388 coeff(0) = 5.4714e-01_dp ! Coefficients
389 coeff(1) = -9.1603e-02_dp ! of
390 coeff(2) = -3.314e-03_dp ! the
391 coeff(3) = 4.66e-04_dp ! fifth-order
392 coeff(4) = 3.8e-05_dp ! polynomial
393 coeff(5) = 6.0e-07_dp ! fit
394 
395 #elif (SOLID_PRECIP == 3) /* Huybrechts and de Wolde (1999) */
396 
397 temp_rain = 2.0_dp ! Threshold instantaneous temperature for &
398  ! precipitation = 100% rain, in deg C
399 temp_snow = temp_rain ! Threshold instantaneous temperature for &
400  ! precipitation = 100% snow, in deg C
401 
402 s_stat = s_stat_0 ! Standard deviation of the air termperature
403  ! (same parameter as in the PDD model)
404 
405 inv_sqrt2_s_stat = 1.0_dp/(sqrt(2.0_dp)*s_stat)
406 
407 #endif
408 
409 #if (ABLSURFACE==1 || ABLSURFACE==2)
410 
411 s_stat = s_stat_0
412 beta1 = beta1_0 *(0.001_dp/86400.0_dp)*(rho_w/rho)
413  ! (mm WE)/(d*deg C) --> (m IE)/(s*deg C)
414 beta2 = beta2_0 *(0.001_dp/86400.0_dp)*(rho_w/rho)
415  ! (mm WE)/(d*deg C) --> (m IE)/(s*deg C)
416 
417 pmax = pmax_0
418 mu = mu_0 *(1000.0_dp*86400.0_dp)*(rho/rho_w)
419  ! (d*deg C)/(mm WE) --> (s*deg C)/(m IE)
420 
421 #elif (ABLSURFACE==3)
422 
423 lambda_lti = lambda_lti *(0.001_dp/year_sec)*(rho_w/rho)
424  ! (mm WE)/(a*deg C) --> (m IE)/(s*deg C)
425 temp_lti = temp_lti
426 mu = 0.0_dp ! no superimposed ice considered
427 
428 #endif
429 
430 do i=0, imax
431 do j=0, jmax
432 
433 ! ------ Accumulation
434 
435 #if (ACCSURFACE <= 3)
436 
437 ! ---- Elevation desertification of precipitation
438 
439 #if (ELEV_DESERT == 0)
440 
441  precip_fact = 1.0_dp ! no elevation desertification
442 
443 #elif (ELEV_DESERT == 1)
444 
445  if (zs_ref(j,i) < zs_thresh) then
446  precip_fact &
447  = exp(gamma_p*(max(zs(j,i),zs_thresh)-zs_thresh))
448  else
449  precip_fact &
450  = exp(gamma_p*(max(zs(j,i),zs_thresh)-zs_ref(j,i)))
451  end if
452 
453 #else
454  stop ' boundary: Parameter ELEV_DESERT must be either 0 or 1!'
455 #endif
456 
457  do n=1, 12 ! month counter
458  precip(j,i,n) = precip_present(j,i,n)*precip_fact
459  end do
460 
461 #endif
462 
463 ! ---- Precipitation change related to changing climate
464 
465 #if ACCSURFACE==1
466  precip_fact = accfact
467 #elif ACCSURFACE==2
468  precip_fact = 1.0_dp + gamma_s*delta_ts
469 #elif ACCSURFACE==3
470  precip_fact = exp(gamma_s*delta_ts)
471 #endif
472 
473 #if (ACCSURFACE <= 3)
474 
475  precip(j,i,0) = 0.0_dp ! initialisation value for mean annual precip
476 
477  do n=1, 12 ! month counter
478  precip(j,i,n) = precip(j,i,n)*precip_fact ! monthly precip
479  precip(j,i,0) = precip(j,i,0) + precip(j,i,n)*inv_twelve
480  ! mean annual precip
481  end do
482 
483 #elif (ACCSURFACE == 5)
484 
485  precip(j,i,0) = 0.0_dp ! initialisation value for mean annual precip
486 
487  do n=1, 12 ! month counter
488 
489 #if (PRECIP_ANOM_INTERPOL==1)
490  precip_fact = 1.0_dp-glac_index+glac_index*precip_lgm_anom(j,i,n)
491  ! interpolation with a linear function
492 #elif (PRECIP_ANOM_INTERPOL==2)
493  precip_fact = exp(-glac_index*gamma_precip_lgm_anom(j,i,n))
494  ! interpolation with an exponential function
495 #endif
496 
497  precip(j,i,n) = precip_present(j,i,n)*precip_fact ! monthly precip
498  precip(j,i,0) = precip(j,i,0) + precip(j,i,n)*inv_twelve
499  ! mean annual precip
500  end do
501 
502 #endif
503 
504 ! ---- Annual accumulation, snowfall and rainfall rates
505 
506  accum(j,i) = precip(j,i,0)
507 
508  snowfall(j,i) = 0.0_dp ! initialisation value
509 
510  do n=1, 12 ! month counter
511 
512 #if (SOLID_PRECIP == 1) /* Marsiat (1994) */
513 
514  if (temp_mm(j,i,n) >= temp_rain) then
515  frac_solid = 0.0_dp
516  else if (temp_mm(j,i,n) <= temp_snow) then
517  frac_solid = 1.0_dp
518  else
519  frac_solid = (temp_rain-temp_mm(j,i,n))*inv_delta_temp_rain_snow
520  end if
521 
522 #elif (SOLID_PRECIP == 2) /* Bales et al. (2009) */
523 
524  if (temp_mm(j,i,n) >= temp_rain) then
525  frac_solid = 0.0_dp
526  else if (temp_mm(j,i,n) <= temp_snow) then
527  frac_solid = 1.0_dp
528  else
529  frac_solid = coeff(0) + temp_mm(j,i,n) * ( coeff(1) &
530  + temp_mm(j,i,n) * ( coeff(2) &
531  + temp_mm(j,i,n) * ( coeff(3) &
532  + temp_mm(j,i,n) * ( coeff(4) &
533  + temp_mm(j,i,n) * coeff(5) ) ) ) )
534  ! evaluation of 5th-order polynomial by Horner scheme
535  end if
536 
537 #elif (SOLID_PRECIP == 3) /* Huybrechts and de Wolde (1999) */
538 
539  frac_solid = 1.0_dp &
540  - 0.5_dp*erfcc((temp_rain-temp_mm(j,i,n))*inv_sqrt2_s_stat)
541 
542 #endif
543 
544  snowfall(j,i) = snowfall(j,i) + precip(j,i,n)*frac_solid*inv_twelve
545 
546  end do
547 
548  rainfall(j,i) = precip(j,i,0) - snowfall(j,i)
549 
550  if (snowfall(j,i) < 0.0_dp) snowfall(j,i) = 0.0_dp ! correction of
551  if (rainfall(j,i) < 0.0_dp) rainfall(j,i) = 0.0_dp ! negative values
552 
553 ! ------ Ablation
554 
555 ! ---- Runoff
556 
557 #if (ABLSURFACE==1 || ABLSURFACE==2)
558 
559 ! ---- Temperature excess ET
560 
561  do n=1, 12 ! month counter
562  temp_mm_help(n) = temp_mm(j,i,n)
563  end do
564 
565  call pdd(temp_mm_help, s_stat, et(j,i))
566 
567 
568 ! ---- Formation rate of superimposed ice (melt_star), melt rate (melt)
569 ! and runoff rate (runoff)
570 
571 #if (ABLSURFACE==1)
572 
573  if ((beta1*et(j,i)) <= (pmax*snowfall(j,i))) then
574  melt_star(j,i) = beta1*et(j,i)
575  melt(j,i) = 0.0_dp
576  runoff(j,i) = melt(j,i)+rainfall(j,i)
577  else
578  melt_star(j,i) = pmax*snowfall(j,i)
579  melt(j,i) = beta2*(et(j,i)-melt_star(j,i)/beta1)
580  runoff(j,i) = melt(j,i)+rainfall(j,i)
581  end if
582 
583 #elif (ABLSURFACE==2)
584 
585  if ( rainfall(j,i) <= (pmax*snowfall(j,i)) ) then
586 
587  if ( (rainfall(j,i)+beta1*et(j,i)) <= (pmax*snowfall(j,i)) ) then
588  melt_star(j,i) = rainfall(j,i)+beta1*et(j,i)
589  melt(j,i) = 0.0_dp
590  runoff(j,i) = melt(j,i)
591  else
592  melt_star(j,i) = pmax*snowfall(j,i)
593  melt(j,i) = beta2 &
594  *(et(j,i)-(melt_star(j,i)-rainfall(j,i))/beta1)
595  runoff(j,i) = melt(j,i)
596  end if
597 
598  else
599 
600  melt_star(j,i) = pmax*snowfall(j,i)
601  melt(j,i) = beta2*et(j,i)
602  runoff(j,i) = melt(j,i) + rainfall(j,i)-pmax*snowfall(j,i)
603 
604  end if
605 
606 #endif
607 
608 #elif (ABLSURFACE==3)
609 
610  temp_jja_help = one_third*(temp_mm(j,i,6)+temp_mm(j,i,7)+temp_mm(j,i,8))
611 
612  melt_star(j,i) = 0.0_dp ! no superimposed ice considered
613  melt(j,i) = lambda_lti*max((temp_jja_help-temp_lti), 0.0_dp)
614  runoff(j,i) = melt(j,i) + rainfall(j,i)
615 
616 #endif
617 
618 ! ---- Evaporation
619 
620  evap(j,i) = 0.0_dp
621 
622 
623 ! ------ Accumulation minus runoff
624 
625  as_perp(j,i) = accum(j,i) - evap(j,i) - runoff(j,i)
626 
627  !hack for initial present-day conditions:
628  !set as_perp to zero, hold bedrock fixed and let zs evolve freely (initial zs smoothing)
629  !as_perp(j,i) = 0.0_dp
630 
631 ! ------ Ice-surface temperature (10-m firn temperature) temp_s,
632 ! including empirical firn-warming correction due to
633 ! refreezing meltwater when superimposed ice is formed
634 
635  if (melt_star(j,i).ge.melt(j,i)) then
636  temp_s(j,i) = temp_ma(j,i) &
637  +mu*(melt_star(j,i)-melt(j,i))
638  else
639  temp_s(j,i) = temp_ma(j,i)
640  end if
641 
642  if (temp_s(j,i) > -0.001_dp) temp_s(j,i) = -0.001_dp
643  ! Cut-off of positive air temperatures
644 
645 end do
646 end do
647 
648 end subroutine boundary
649 !
integer(i2b) function mask_update(z_sl, i, j)
Update of the topography mask due to changes of the sea level.
Definition: mask_update.F90:35
Declarations of kind types for SICOPOLIS.
Definition: sico_types.F90:35
subroutine pdd(temp_mm, s_stat, ET)
Computation of the positive degree days (PDD) with statistical temperature fluctuations; based on sem...
Definition: pdd.F90:41
real(dp) function erfcc(x)
Computation of the complementary error function erfc(x) = 1-erf(x) with a fractional error everywhere...
Definition: erfcc.F90:39
Declarations of global variables for SICOPOLIS (for the ANT domain).
Definition: sico_vars.F90:35
subroutine boundary(time, dtime, dxi, deta, delta_ts, glac_index, z_sl, dzsl_dtau, z_mar)
Computation of the surface temperature (must be less than 0 deg C!) and of the accumulation-ablation ...
Definition: boundary.F90:37
Declarations of global variables for SICOPOLIS.