38                     delta_ts, glac_index, z_sl, dzsl_dtau, z_mar)
 
   46 real(dp), 
intent(in) :: time, dtime, dxi, deta
 
   48 real(dp), 
intent(out)   :: delta_ts, glac_index, dzsl_dtau, z_mar
 
   49 real(dp), 
intent(inout) :: z_sl
 
   56 integer(i4b) :: i, j, n
 
   57 integer(i4b) :: i_gr, i_kl
 
   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           snowfall, rainfall, melt, melt_star
 
   65 real(dp), 
dimension(0:JMAX,0:IMAX,12) :: temp_mm
 
   66 real(dp), 
dimension(0:JMAX,0:IMAX) :: temp_ma
 
   67 real(dp), 
dimension(12) :: temp_mm_help
 
   68 real(dp) :: temp_jja_help
 
   69 real(dp), 
dimension(0:JMAX,0:IMAX) :: et
 
   70 real(dp) :: gamma_t, temp_diff
 
   71 real(dp) :: gamma_p, zs_thresh, &
 
   72             temp_rain, temp_snow, &
 
   73             inv_delta_temp_rain_snow, coeff(0:5), inv_sqrt2_s_stat, &
 
   74             precip_fact, frac_solid
 
   75 real(dp) :: s_stat, beta1, beta2, pmax, mu, lambda_lti, temp_lti
 
   76 logical, 
dimension(0:JMAX,0:IMAX) :: check_point
 
   78 real(dp), 
parameter :: &
 
   79           inv_twelve = 1.0_dp/12.0_dp, one_third = 1.0_dp/3.0_dp
 
   98 delta_ts = sine_amplit &
 
   99            *cos(2.0_dp*pi*time/(sine_period*year_sec)) &
 
  106 if (time/year_sec.lt.
real(grip_time_min,dp)) then
 
  107    delta_ts = griptemp(0)
 
  108 else if (time/year_sec.lt.
real(grip_time_max,dp)) then
 
  110    i_kl = floor(((time/year_sec) &
 
  111           -
real(grip_time_min,dp))/
real(grip_time_stp,dp))
 
  114    i_gr = ceiling(((time/year_sec) &
 
  115           -
real(grip_time_min,dp))/
real(grip_time_stp,dp))
 
  116    i_gr = min(i_gr, ndata_grip)
 
  118    if (i_kl.eq.i_gr) 
then 
  120       delta_ts = griptemp(i_kl)
 
  124       time_kl = (grip_time_min + i_kl*grip_time_stp) *year_sec
 
  125       time_gr = (grip_time_min + i_gr*grip_time_stp) *year_sec
 
  127       delta_ts = griptemp(i_kl) &
 
  128                 +(griptemp(i_gr)-griptemp(i_kl)) &
 
  129                 *(time-time_kl)/(time_gr-time_kl)
 
  135    delta_ts  = griptemp(ndata_grip)
 
  138 delta_ts = delta_ts * grip_temp_fact
 
  145 if (time/year_sec < 
real(gi_time_min,dp)) then
 
  146    glac_index = glacial_index(0)
 
  147 else if (time/year_sec < 
real(gi_time_max,dp)) then
 
  149    i_kl = floor(((time/year_sec) &
 
  150           -
real(gi_time_min,dp))/
real(gi_time_stp,dp))
 
  153    i_gr = ceiling(((time/year_sec) &
 
  154           -
real(gi_time_min,dp))/
real(gi_time_stp,dp))
 
  155    i_gr = min(i_gr, ndata_gi)
 
  157    if (i_kl == i_gr) 
then 
  159       glac_index = glacial_index(i_kl)
 
  163       time_kl = (gi_time_min + i_kl*gi_time_stp) *year_sec
 
  164       time_gr = (gi_time_min + i_gr*gi_time_stp) *year_sec
 
  166       glac_index = glacial_index(i_kl) &
 
  167                 +(glacial_index(i_gr)-glacial_index(i_kl)) &
 
  168                 *(time-time_kl)/(time_gr-time_kl)
 
  174    glac_index  = glacial_index(ndata_gi)
 
  190 t1 = -250000.0_dp *year_sec
 
  191 t2 = -140000.0_dp *year_sec
 
  192 t3 = -125000.0_dp *year_sec
 
  193 t4 =  -21000.0_dp *year_sec
 
  194 t5 =   -8000.0_dp *year_sec
 
  195 t6 =       0.0_dp *year_sec
 
  199 else if (time.lt.t2) 
then 
  200    z_sl = z_sl_min*(time-t1)/(t2-t1)
 
  201 else if (time.lt.t3) 
then 
  202    z_sl = -z_sl_min*(time-t3)/(t3-t2)
 
  203 else if (time.lt.t4) 
then 
  204    z_sl = z_sl_min*(time-t3)/(t4-t3)
 
  205 else if (time.lt.t5) 
then 
  206    z_sl = -z_sl_min*(time-t5)/(t5-t4)
 
  207 else if (time.lt.t6) 
then 
  217 if (time/year_sec.lt.
real(specmap_time_min,dp)) then
 
  218    z_sl = specmap_zsl(0)
 
  219 else if (time/year_sec.lt.
real(specmap_time_max,dp)) then
 
  221    i_kl = floor(((time/year_sec) &
 
  222           -
real(specmap_time_min,dp))/
real(specmap_time_stp,dp))
 
  225    i_gr = ceiling(((time/year_sec) &
 
  226           -
real(specmap_time_min,dp))/
real(specmap_time_stp,dp))
 
  227    i_gr = min(i_gr, ndata_specmap)
 
  229    if (i_kl.eq.i_gr) 
then 
  231       z_sl = specmap_zsl(i_kl)
 
  235       time_kl = (specmap_time_min + i_kl*specmap_time_stp) *year_sec
 
  236       time_gr = (specmap_time_min + i_gr*specmap_time_stp) *year_sec
 
  238       z_sl = specmap_zsl(i_kl) &
 
  239                 +(specmap_zsl(i_gr)-specmap_zsl(i_kl)) &
 
  240                 *(time-time_kl)/(time_gr-time_kl)
 
  246    z_sl  = specmap_zsl(ndata_specmap)
 
  253 if ( z_sl_old > -999999.9_dp ) 
then 
  254    dzsl_dtau = (z_sl-z_sl_old)/dtime
 
  263 #if ( MARINE_ICE_CALVING==2 || MARINE_ICE_CALVING==3 ) 
  265 #elif ( MARINE_ICE_CALVING==4 || MARINE_ICE_CALVING==5 ) 
  266 z_mar = fact_z_mar*z_sl
 
  267 #elif ( MARINE_ICE_CALVING==6 || MARINE_ICE_CALVING==7 ) 
  268 if (z_sl >= -80.0_dp) 
then 
  271    z_mar = 10.25_dp*(z_sl+80.0_dp)-200.0_dp
 
  273 z_mar = fact_z_mar*z_mar
 
  285    check_point(j,i) = .false.
 
  291    if (maske(j,i).ge.2) 
then 
  292       check_point(j  ,i  ) = .true.
 
  293       check_point(j  ,i+1) = .true.
 
  294       check_point(j  ,i-1) = .true.
 
  295       check_point(j+1,i  ) = .true.
 
  296       check_point(j-1,i  ) = .true.
 
  303    if (check_point(j,i)) 
then 
  313    if (check_point(j,i)) 
then 
  314       maske(j,i) = maske_neu(j,i)
 
  321 gamma_t = -6.5e-03_dp   
 
  331    temp_diff = gamma_t*(zs(j,i)-zs_ref(j,i)) + delta_ts
 
  334       temp_mm(j,i,n) = temp_mm_present(j,i,n) + temp_diff
 
  337 #elif (TSURFACE == 5) 
  342    temp_diff = gamma_t*(zs(j,i)-zs_ref(j,i))
 
  345       temp_mm(j,i,n) = temp_mm_present(j,i,n) &
 
  346                        + glac_index*temp_mm_lgm_anom(j,i,n) &
 
  354    temp_ma(j,i) = 0.0_dp   
 
  357       temp_ma(j,i) = temp_ma(j,i) + temp_mm(j,i,n)*inv_twelve
 
  365 #if (ELEV_DESERT == 1) 
  367 gamma_p   = gamma_p*1.0e-03_dp   
 
  369 zs_thresh = zs_thresh            
 
  373 #if (SOLID_PRECIP == 1)     /* Marsiat (1994) */ 
  380 inv_delta_temp_rain_snow = 1.0_dp/(temp_rain-temp_snow)
 
  382 #elif (SOLID_PRECIP == 2)   /* Bales et al. (2009) */ 
  389 coeff(0) =  5.4714e-01_dp   
 
  390 coeff(1) = -9.1603e-02_dp   
 
  391 coeff(2) = -3.314e-03_dp    
 
  392 coeff(3) =  4.66e-04_dp     
 
  393 coeff(4) =  3.8e-05_dp      
 
  394 coeff(5) =  6.0e-07_dp      
 
  396 #elif (SOLID_PRECIP == 3)   /* Huybrechts and de Wolde (1999) */ 
  400 temp_snow = temp_rain   
 
  406 inv_sqrt2_s_stat = 1.0_dp/(sqrt(2.0_dp)*s_stat)
 
  410 #if (ABLSURFACE==1 || ABLSURFACE==2) 
  413 beta1  = beta1_0  *(0.001_dp/86400.0_dp)*(rho_w/rho)
 
  415 beta2  = beta2_0  *(0.001_dp/86400.0_dp)*(rho_w/rho)
 
  418 mu     = mu_0     *(1000.0_dp*86400.0_dp)*(rho/rho_w)
 
  421 #elif (ABLSURFACE==3) 
  423 lambda_lti = lambda_lti  *(0.001_dp/year_sec)*(rho_w/rho)
 
  435 #if (ACCSURFACE <= 3) 
  439 #if (ELEV_DESERT == 0) 
  443 #elif (ELEV_DESERT == 1) 
  445    if (zs_ref(j,i) < zs_thresh) 
then 
  447          = exp(gamma_p*(max(zs(j,i),zs_thresh)-zs_thresh))
 
  450          = exp(gamma_p*(max(zs(j,i),zs_thresh)-zs_ref(j,i)))
 
  454    stop 
' boundary: Parameter ELEV_DESERT must be either 0 or 1!' 
  458       precip(j,i,n) = precip_present(j,i,n)*precip_fact
 
  466    precip_fact = accfact
 
  468    precip_fact = 1.0_dp + gamma_s*delta_ts
 
  470    precip_fact = exp(gamma_s*delta_ts)
 
  473 #if (ACCSURFACE <= 3) 
  475    precip(j,i,0) = 0.0_dp   
 
  478       precip(j,i,n) = precip(j,i,n)*precip_fact   
 
  479       precip(j,i,0) = precip(j,i,0) + precip(j,i,n)*inv_twelve
 
  483 #elif (ACCSURFACE == 5) 
  485    precip(j,i,0) = 0.0_dp   
 
  489 #if (PRECIP_ANOM_INTERPOL==1) 
  490       precip_fact = 1.0_dp-glac_index+glac_index*precip_lgm_anom(j,i,n)
 
  492 #elif (PRECIP_ANOM_INTERPOL==2) 
  493       precip_fact = exp(-glac_index*gamma_precip_lgm_anom(j,i,n))
 
  497       precip(j,i,n) = precip_present(j,i,n)*precip_fact   
 
  498       precip(j,i,0) = precip(j,i,0) + precip(j,i,n)*inv_twelve
 
  506    accum(j,i) = precip(j,i,0)
 
  508    snowfall(j,i) = 0.0_dp   
 
  512 #if (SOLID_PRECIP == 1)     /* Marsiat (1994) */ 
  514       if (temp_mm(j,i,n) >= temp_rain) 
then 
  516       else if (temp_mm(j,i,n) <= temp_snow) 
then 
  519          frac_solid = (temp_rain-temp_mm(j,i,n))*inv_delta_temp_rain_snow
 
  522 #elif (SOLID_PRECIP == 2)   /* Bales et al. (2009) */ 
  524       if (temp_mm(j,i,n) >= temp_rain) 
then 
  526       else if (temp_mm(j,i,n) <= temp_snow) 
then 
  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) ) ) ) )
 
  537 #elif (SOLID_PRECIP == 3)   /* Huybrechts and de Wolde (1999) */ 
  539       frac_solid = 1.0_dp &
 
  540                    - 0.5_dp*
erfcc((temp_rain-temp_mm(j,i,n))*inv_sqrt2_s_stat)
 
  544       snowfall(j,i) = snowfall(j,i) + precip(j,i,n)*frac_solid*inv_twelve
 
  548    rainfall(j,i) = precip(j,i,0) - snowfall(j,i)
 
  550    if (snowfall(j,i) < 0.0_dp) snowfall(j,i) = 0.0_dp   
 
  551    if (rainfall(j,i) < 0.0_dp) rainfall(j,i) = 0.0_dp   
 
  557 #if (ABLSURFACE==1 || ABLSURFACE==2) 
  562       temp_mm_help(n) = temp_mm(j,i,n)
 
  565    call 
pdd(temp_mm_help, s_stat, et(j,i))
 
  572    if ((beta1*et(j,i)) <= (pmax*snowfall(j,i))) 
then 
  573       melt_star(j,i) = beta1*et(j,i)
 
  575       runoff(j,i)    = melt(j,i)+rainfall(j,i)
 
  577       melt_star(j,i) = pmax*snowfall(j,i)
 
  578       melt(j,i)      = beta2*(et(j,i)-melt_star(j,i)/beta1)
 
  579       runoff(j,i)    = melt(j,i)+rainfall(j,i)
 
  582 #elif (ABLSURFACE==2) 
  584    if ( rainfall(j,i) <= (pmax*snowfall(j,i)) ) 
then 
  586       if ( (rainfall(j,i)+beta1*et(j,i)) <= (pmax*snowfall(j,i)) ) 
then 
  587          melt_star(j,i) = rainfall(j,i)+beta1*et(j,i)
 
  589          runoff(j,i)    = melt(j,i)
 
  591          melt_star(j,i) = pmax*snowfall(j,i)
 
  593                           *(et(j,i)-(melt_star(j,i)-rainfall(j,i))/beta1)
 
  594          runoff(j,i)    = melt(j,i)
 
  599       melt_star(j,i) = pmax*snowfall(j,i)
 
  600       melt(j,i)      = beta2*et(j,i)
 
  601       runoff(j,i)    = melt(j,i) + rainfall(j,i)-pmax*snowfall(j,i)
 
  607 #elif (ABLSURFACE==3) 
  609    temp_jja_help  = one_third*(temp_mm(j,i,6)+temp_mm(j,i,7)+temp_mm(j,i,8))
 
  611    melt_star(j,i) = 0.0_dp   
 
  612    melt(j,i)      = lambda_lti*max((temp_jja_help-temp_lti), 0.0_dp)
 
  613    runoff(j,i)    = melt(j,i) + rainfall(j,i)
 
  623    as_perp(j,i) = accum(j,i) - evap(j,i) - runoff(j,i)
 
  629    if (melt_star(j,i).ge.melt(j,i)) 
then 
  630       temp_s(j,i) = temp_ma(j,i) &
 
  631                     +mu*(melt_star(j,i)-melt(j,i))
 
  633       temp_s(j,i) = temp_ma(j,i)
 
  636    if (temp_s(j,i) > -0.001_dp) temp_s(j,i) = -0.001_dp
 
integer(i2b) function mask_update(z_sl, i, j)
Update of the topography mask due to changes of the sea level. 
 
Declarations of kind types for SICOPOLIS. 
 
subroutine pdd(temp_mm, s_stat, ET)
Computation of the positive degree days (PDD) with statistical temperature fluctuations; based on sem...
 
real(dp) function erfcc(x)
Computation of the complementary error function erfc(x) = 1-erf(x) with a fractional error everywhere...
 
Declarations of global variables for SICOPOLIS (for the ANT domain). 
 
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 ...
 
Declarations of global variables for SICOPOLIS.