source: trunk/LMDZ.COMMON/libf/evolution/layering_mod.F90 @ 3296

Last change on this file since 3296 was 3286, checked in by jbclement, 8 months ago

PEM:
Introduction of the module aiming to manage the layered deposits through a linked list data structure. It contains:

  • the object 'stratum' which holds several properties for one layer as well as pointers to the lower/upper 'stratum';
  • the object 'layering' which brings the linked 'stratum' objects together as a comprehensive structure;
  • properties for CO2/H2O ice, regolith and dust;
  • several subroutines to manipulate the 'layering' and 'stratum' (initilize, finalize, display, modify, etc);
  • subroutines of the algorithm to make the layering evolve according to the input tendencies (new layer, change of content in a layer, creation of dust lag layer, etc).

JBC

File size: 23.0 KB
Line 
1MODULE layering_mod
2
3!=======================================================================
4! Purpose: Manage layered deposits in the PEM with a linked list data structure
5!
6! Author: JBC
7! Date: 08/03/2024
8!=======================================================================
9
10
11implicit none
12
13!---- Declarations
14! Numerical parameter
15real, parameter :: eps = epsilon(1.), tol = 1.e2*eps
16
17! Physical parameters
18real, parameter :: tend_dust = 5.78e-2          ! Tendency of dust [kg.m-2.y-1]
19real, parameter :: dry_lag_porosity = 0.5       ! Porosity of dust lag
20real, parameter :: dry_regolith_porosity = 0.45 ! Porosity of regolith
21real, parameter :: co2ice_porosity = 0.3        ! Porosity of CO2 ice
22real, parameter :: h2oice_porosity = 0.3        ! Porosity of H2O ice
23real, parameter :: rho_co2ice = 1650.           ! Density of CO2 ice [kg.m-3]
24real, parameter :: rho_h2oice = 920.            ! Density of H2O ice [kg.m-3]
25real, parameter :: rho_dust = 2500.             ! Density of dust [kg.m-3]
26real, parameter :: rho_rock = 3200.             ! Density of rock [kg.m-3]
27
28! Stratum = node of the linked list
29type :: stratum
30    real               :: thickness          ! Layer thickness [m]
31    real               :: elevation          ! Layer elevation (top height from the surface) [m]
32    real               :: co2ice_volfrac     ! CO2 ice volumic fraction
33    real               :: h2oice_volfrac     ! H2O ice volumic fraction
34    real               :: dust_volfrac       ! Dust volumic fraction
35    real               :: air_volfrac        ! Air volumic fraction inside pores
36    type(stratum), pointer :: up => null()   ! Upper stratum (next node)
37    type(stratum), pointer :: down => null() ! Lower stratum (previous node)
38end type stratum
39
40! Layering = linked list
41type layering
42    integer                :: nb_str = 0       ! Number of strata
43    type(stratum), pointer :: bottom => null() ! First stratum (head of the list)
44    type(stratum), pointer :: top => null()    ! Last stratum (tail of the list)
45end type layering
46
47!=======================================================================
48contains
49!=======================================================================
50! To display a stratum
51SUBROUTINE print_stratum(this)
52
53implicit none
54
55!---- Arguments
56type(stratum), intent(in) :: this
57
58!---- Code
59write(*,'(a20,es13.6)') 'Thickness      : ', this%thickness
60write(*,'(a20,es13.6)') 'Elevation      : ', this%elevation
61write(*,'(a20,es13.6)') 'CO2 ice content: ', this%co2ice_volfrac
62write(*,'(a20,es13.6)') 'H2O ice content: ', this%h2oice_volfrac
63write(*,'(a20,es13.6)') 'Dust content   : ', this%dust_volfrac
64write(*,'(a20,es13.6)') 'Air content    : ', this%air_volfrac
65
66END SUBROUTINE print_stratum
67
68!=======================================================================
69! To display a layering
70SUBROUTINE print_lay(this)
71
72implicit none
73
74!---- Arguments
75type(layering), intent(in) :: this
76
77!---- Local variables
78type(stratum), pointer :: current
79integer                :: i
80
81!---- Code
82current => this%top
83
84i = this%nb_str
85do while (associated(current))
86    write(*,'(a8,i4)') 'Stratum ', i
87    call print_stratum(current)
88    write(*,*)
89    current => current%down
90    i = i - 1
91enddo
92
93END SUBROUTINE print_lay
94
95!=======================================================================
96! To add a stratum to the top of a layering
97SUBROUTINE add_stratum(this,thickness,elevation,co2ice,h2oice,dust,air)
98
99implicit none
100
101!---- Arguments
102type(layering), intent(inout)  :: this
103real, intent(in), optional :: thickness, elevation, co2ice, h2oice, dust, air
104
105!---- Local variables
106type(stratum), pointer :: str
107
108!---- Code
109! Creation of the stratum
110allocate(str)
111nullify(str%up,str%down)
112str%thickness = 1.
113str%elevation = 1.
114str%co2ice_volfrac = 0.
115str%h2oice_volfrac = 0.
116str%dust_volfrac = 0.
117str%air_volfrac = 1.
118if (present(thickness)) str%thickness = thickness
119if (present(elevation)) str%elevation = elevation
120if (present(co2ice)) str%co2ice_volfrac = co2ice
121if (present(h2oice)) str%h2oice_volfrac = h2oice
122if (present(dust)) str%dust_volfrac = dust
123if (present(air)) str%air_volfrac = air
124
125! Verification of volume fraction
126if (abs(1. - (str%co2ice_volfrac + str%h2oice_volfrac + str%dust_volfrac + str%air_volfrac)) > tol) &
127     error stop 'add_stratum: properties for the new stratum are not possible (sum of volumic fraction /= 1)!'
128
129! Increment the number of strata
130this%nb_str = this%nb_str + 1
131
132! Add the stratum to the layering
133if (.not. associated(this%bottom)) then ! If it is the very first one
134    this%bottom => str
135    this%top => str
136else
137    str%down => this%top
138    this%top%up => str
139    this%top => str
140endif
141
142END SUBROUTINE add_stratum
143
144!=======================================================================
145! To insert a stratum after another one in a layering
146SUBROUTINE insert_stratum(this,str_prev,thickness,elevation,co2ice,h2oice,dust,air)
147
148implicit none
149
150!---- Arguments
151type(layering),         intent(inout) :: this
152type(stratum), pointer, intent(inout) :: str_prev
153real, intent(in), optional :: thickness, elevation, co2ice, h2oice, dust, air
154
155!---- Local variables
156type(stratum), pointer :: str, current
157
158!---- Code
159if (.not. associated(str_prev%up)) then ! If str_prev is the top stratum of the layering
160    call add_stratum(this,thickness,elevation,co2ice,h2oice,dust,air)
161else
162    ! Creation of the stratum
163    allocate(str)
164    nullify(str%up,str%down)
165    str%thickness = 1.
166    str%elevation = 1.
167    str%co2ice_volfrac = 0.
168    str%h2oice_volfrac = 0.
169    str%dust_volfrac = 0.
170    str%air_volfrac = 1.
171    if (present(thickness)) str%thickness = thickness
172    if (present(elevation)) str%elevation = elevation
173    if (present(co2ice)) str%co2ice_volfrac = co2ice
174    if (present(h2oice)) str%h2oice_volfrac = h2oice
175    if (present(dust)) str%dust_volfrac = dust
176    if (present(air)) str%air_volfrac = air
177
178    ! Verification of volume fraction
179    if (abs(1. - (str%co2ice_volfrac + str%h2oice_volfrac + str%dust_volfrac + str%air_volfrac)) > tol) &
180         error stop 'insert_stratum: properties for the new stratum are not possible (sum of volumic fraction /= 1)!'
181
182    ! Increment the number of strata
183    this%nb_str = this%nb_str + 1
184
185    ! Insert the stratum into the layering at the right place
186    str%down => str_prev
187    str%up => str_prev%up
188    str_prev%up => str
189    str%up%down => str
190
191    ! Correct the value of elevation for the upper strata
192    current => str%up
193    do while (associated(current))
194        current%elevation = current%down%elevation + current%thickness
195        current => current%up
196    enddo
197endif
198
199END SUBROUTINE insert_stratum
200
201!=======================================================================
202! To remove a stratum in a layering
203SUBROUTINE rm_stratum(this,str)
204
205implicit none
206
207!---- Arguments
208type(layering),         intent(inout) :: this
209type(stratum), pointer, intent(inout) :: str
210
211!---- Local variables
212type(stratum), pointer :: new_str
213
214!---- Code
215! Protect the 3 sub-surface strata from removing
216if (str%elevation <= 0.) return
217
218! Decrement the number of strata
219this%nb_str = this%nb_str - 1
220
221! Remove the stratum from the stratification
222str%down%up => str%up
223if (associated(str%up)) then ! If it is not the last one at the top of the layering
224    str%up%down => str%down
225else
226    this%top => str%down
227endif
228new_str => str%down
229nullify(str%up,str%down)
230deallocate(str)
231nullify(str)
232str => new_str
233
234END SUBROUTINE rm_stratum
235
236!=======================================================================
237! To initialize the layering
238SUBROUTINE ini_layering(this)
239
240implicit none
241
242!---- Arguments
243type(layering), intent(inout) :: this
244
245!---- Code
246! Creation of three strata at the bottom of the layering
247! 1) Dry porous deep regolith
248call add_stratum(this,18.,-12.,0.,0.,dry_regolith_porosity,1. - dry_regolith_porosity)
249! 2) Ice-cemented regolith (ice table)
250call add_stratum(this,10.,-2.,0.,1. - dry_regolith_porosity,dry_regolith_porosity,0.)
251! 3) Dry porous regolith
252call add_stratum(this,2.,0.,0.,0.,dry_regolith_porosity,1. - dry_regolith_porosity)
253
254END SUBROUTINE ini_layering
255
256!=======================================================================
257! To delete the entire layering
258SUBROUTINE del_layering(this)
259
260implicit none
261
262!---- Arguments
263type(layering), intent(inout) :: this
264
265!---- Local variables
266type(stratum), pointer :: current, next
267
268!---- Code
269current => this%bottom
270do while (associated(current))
271    next => current%up
272    deallocate(current)
273    nullify(current)
274    current => next
275enddo
276this%nb_str = 0
277
278END SUBROUTINE del_layering
279
280!=======================================================================
281! To get a specific stratum in a layering
282FUNCTION get_stratum(lay,i) RESULT(str)
283
284implicit none
285
286!---- Arguments
287type(layering), intent(in) :: lay
288integer,        intent(in) :: i
289type(stratum), pointer     :: str
290
291!---- Local variables
292integer :: k
293
294!---- Code
295if (i < 1 .or. i > lay%nb_str) error stop 'get_stratum: requested number is beyond the number of strata of the layering!'
296k = 1
297str => lay%bottom
298do while (k /= i)
299    str => str%up
300    k = k + 1
301enddo
302
303END FUNCTION get_stratum
304
305!=======================================================================
306! To sublimate CO2 ice in the layering
307SUBROUTINE subl_co2ice_layering(this,str,h2subl,h_co2ice_old,h_h2oice_old,h_dust_old,new_lag)
308
309implicit none
310
311!---- Arguments
312type(layering),         intent(inout) :: this
313type(stratum), pointer, intent(inout) :: str
314logical,                intent(inout) :: new_lag
315real, intent(in) :: h2subl, h_co2ice_old, h_h2oice_old, h_dust_old
316
317!---- Local variables
318real               :: r_subl, hsubl_dust, h_lag
319type(stratum), pointer :: current
320
321!---- Code
322! How much dust does CO2 ice sublimation involve to create the lag?
323r_subl = h2subl/(1. - co2ice_porosity) &
324        /(str%thickness*(str%co2ice_volfrac/(1. - co2ice_porosity) + str%h2oice_volfrac/(1. - h2oice_porosity)))
325hsubl_dust = r_subl*str%dust_volfrac*str%thickness
326! Update of properties in the sublimating stratum
327str%thickness = str%thickness - h2subl/(1. - co2ice_porosity) - hsubl_dust
328str%elevation = str%elevation - h2subl/(1. - co2ice_porosity) - hsubl_dust
329str%co2ice_volfrac = (h_co2ice_old - h2subl)/str%thickness
330str%h2oice_volfrac = h_h2oice_old/str%thickness
331str%dust_volfrac = (h_dust_old - hsubl_dust)/str%thickness
332str%air_volfrac = 1. - (str%co2ice_volfrac + str%h2oice_volfrac + str%dust_volfrac)
333! Correct the value of elevation for the upper strata
334current => str%up
335do while (associated(current))
336    current%elevation = current%down%elevation + current%thickness
337    current => current%up
338enddo
339! Remove the sublimating stratum if there is no ice anymore
340if (str%thickness < tol) call rm_stratum(this,str)
341! New stratum = dust lag
342h_lag = hsubl_dust/(1. - dry_lag_porosity)
343if (h_lag > 0.) then ! Only if the dust lag is building up
344    if (new_lag) then
345        call insert_stratum(this,str,h_lag,str%elevation + h_lag,0.,0.,1. - dry_lag_porosity,dry_lag_porosity)
346        new_lag = .false.
347    else
348        str%up%thickness = str%up%thickness + h_lag
349        str%up%elevation = str%up%elevation + h_lag
350    endif
351endif
352
353END SUBROUTINE subl_co2ice_layering
354
355!=======================================================================
356! To sublimate H2O ice in the layering
357SUBROUTINE subl_h2oice_layering(this,str,h2subl,h_co2ice_old,h_h2oice_old,h_dust_old,new_lag)
358
359implicit none
360
361!---- Arguments
362type(layering),         intent(inout) :: this
363type(stratum), pointer, intent(inout) :: str
364logical,                intent(inout) :: new_lag
365real, intent(in) :: h2subl, h_co2ice_old, h_h2oice_old, h_dust_old
366
367!---- Local variables
368real               :: r_subl, hsubl_dust, h_lag
369type(stratum), pointer :: current
370
371!---- Code
372! How much dust does CO2 ice sublimation involve to create the lag?
373r_subl = h2subl/(1. - h2oice_porosity) &
374        /(str%thickness*(str%co2ice_volfrac/(1. - co2ice_porosity) + str%h2oice_volfrac/(1. - h2oice_porosity)))
375hsubl_dust = r_subl*str%dust_volfrac*str%thickness
376! Update of properties in the sublimating stratum
377str%thickness = str%thickness - h2subl/(1. - h2oice_porosity) - hsubl_dust
378str%elevation = str%elevation - h2subl/(1. - h2oice_porosity) - hsubl_dust
379str%co2ice_volfrac = h_co2ice_old/str%thickness
380str%h2oice_volfrac = (h_h2oice_old - h2subl)/str%thickness
381str%dust_volfrac = (h_dust_old - hsubl_dust)/str%thickness
382str%air_volfrac = 1. - (str%co2ice_volfrac + str%h2oice_volfrac + str%dust_volfrac)
383! Correct the value of elevation for the upper strata
384current => str%up
385do while (associated(current))
386    current%elevation = current%down%elevation + current%thickness
387    current => current%up
388enddo
389! Remove the sublimating stratum if there is no ice anymore
390if (str%thickness < tol) call rm_stratum(this,str)
391! New stratum = dust lag
392h_lag = hsubl_dust/(1. - dry_lag_porosity)
393if (h_lag > 0.) then ! Only if the dust lag is building up
394    if (new_lag) then
395        call insert_stratum(this,str,h_lag,str%elevation + h_lag,0.,0.,1. - dry_lag_porosity,dry_lag_porosity)
396        new_lag = .false.
397    else
398        str%up%thickness = str%up%thickness + h_lag
399        str%up%elevation = str%up%elevation + h_lag
400    endif
401endif
402
403END SUBROUTINE subl_h2oice_layering
404
405!=======================================================================
406! To lift dust in the layering
407SUBROUTINE lift_dust_lags(this,str,h2lift)
408
409implicit none
410
411!---- Arguments
412type(layering),         intent(inout) :: this
413type(stratum), pointer, intent(inout) :: str
414real, intent(in) :: h2lift
415
416!---- Code
417! Update of properties in the eroding dust lag
418str%thickness = str%thickness - h2lift/(1. - str%air_volfrac)
419str%elevation = str%elevation - h2lift/(1. - str%air_volfrac)
420! Remove the eroding dust lag if there is no dust anymore
421if (str%thickness < tol) call rm_stratum(this,str)
422
423END SUBROUTINE lift_dust_lags
424
425!=======================================================================
426! Layering algorithm
427SUBROUTINE make_layering(this,k,htend_co2ice,htend_h2oice,htend_dust,new_str,new_lag1,new_lag2,stopPEM,current1,current2)
428
429implicit none
430
431!---- Arguments
432type(layering),         intent(inout) :: this
433type(stratum), pointer, intent(inout) :: current1, current2
434logical,                intent(inout) :: new_str, new_lag1, new_lag2, stopPEM
435real, intent(in) :: htend_co2ice, htend_h2oice, htend_dust
436integer,  intent(in) :: k
437
438!---- Local variables
439real :: h_co2ice_old, h_h2oice_old, h_dust_old, thickness, h2subl, h2subl_tot, h2lift, h2lift_tot
440
441!---- Code
442if (htend_dust < 0.) then ! Dust lifting
443    if (abs(htend_co2ice) > eps .or. abs(htend_h2oice) > eps) error stop 'Situation not managed: dust lifting + CO2/H2O ice condensation/sublimation!'
444    write(*,'(a5,i3,a)') 'Year ', k, ' -> Dust lifting'
445    h2lift_tot = abs(htend_dust)
446    do while (h2lift_tot > 0. .and. associated(current1))
447        ! Is the considered stratum a dust lag?
448        if (abs(1. - (current1%dust_volfrac + current1%air_volfrac)) < tol) then ! Yes, we can lift dust
449            h_dust_old = current1%dust_volfrac*current1%thickness
450            ! How much dust can be lifted in the considered dust lag?
451            if (h2lift_tot - h_dust_old <= eps) then ! There is enough to lift
452                h2lift = h2lift_tot
453                h2lift_tot = 0.
454                call lift_dust_lags(this,current1,h2lift)
455            else ! Only a fraction can be lifted and so we move to the underlying stratum
456                h2lift = h_dust_old
457                h2lift_tot = h2lift_tot - h2lift
458                call lift_dust_lags(this,current1,h2lift)
459                current1 => current1%down
460            endif
461        else ! No, we stop
462            write(*,'(a5,i3,a)') 'Year ', k, ' -> Dust lifting: no dust lag!'
463            stopPEM = .true.
464            exit
465        endif
466    enddo
467    if (h2lift_tot > 0.) then
468        write(*,'(a5,i3,a)') 'Year ', k, ' -> Not enough dust in the lag layers to complete the lifting!'
469        stopPEM = .true.
470    endif
471
472else
473
474!------ Dust sedimentation
475    if (abs(htend_co2ice) < eps .and. abs(htend_h2oice) < eps) then
476        write(*,'(a5,i3,a)') 'Year ', k, ' -> Dust sedimentation'
477        ! New stratum at the layering top by sedimentation of dust
478        thickness = htend_dust/(1. - dry_regolith_porosity)
479        if (thickness > 0.) then ! Only if the stratum is builiding up
480             if (new_str) then
481                 call add_stratum(this,thickness,this%top%elevation + thickness,0.,0.,htend_dust/thickness,dry_regolith_porosity)
482                 new_str = .false.
483             else
484                 this%top%thickness = this%top%thickness + thickness
485                 this%top%elevation = this%top%elevation + thickness
486             endif
487        endif
488
489!------ Condensation of CO2 ice + H2O ice
490    else if ((htend_co2ice >= 0. .and. htend_h2oice > 0.) .or. (htend_co2ice > 0. .and. htend_h2oice >= 0.)) then
491        write(*,'(a5,i3,a)') 'Year ', k, ' -> CO2 and H2O ice condensation'
492        ! New stratum at the layering top by condensation of CO2 and H2O ice
493        thickness = htend_co2ice/(1. - co2ice_porosity) + htend_h2oice/(1. - h2oice_porosity) + htend_dust
494        if (thickness > 0.) then ! Only if the stratum is builiding up
495             if (new_str) then
496                 call add_stratum(this,thickness,this%top%elevation + thickness,htend_co2ice/thickness,htend_h2oice/thickness,htend_dust/thickness,1. - (htend_co2ice/thickness + htend_h2oice/thickness + htend_dust/thickness))
497                 new_str = .false.
498             else
499                 this%top%thickness = this%top%thickness + thickness
500                 this%top%elevation = this%top%elevation + thickness
501             endif
502        endif
503
504!------ Sublimation of CO2 ice + Condensation of H2O ice
505    else if (htend_co2ice < 0. .and. htend_h2oice >= 0. ) then
506        write(*,'(a5,i3,a)') 'Year ', k, ' -> Sublimation of CO2 ice + Condensation of H2O ice'
507        ! CO2 ice sublimation in the considered stratum + New stratum for dust lag
508        h2subl_tot = abs(htend_co2ice)
509        do while (h2subl_tot > 0. .and. associated(current1))
510            h_co2ice_old = current1%co2ice_volfrac*current1%thickness
511            h_h2oice_old = current1%h2oice_volfrac*current1%thickness
512            h_dust_old = current1%dust_volfrac*current1%thickness
513            ! How much CO2 ice can sublimate in the considered stratum?
514            if (h2subl_tot - h_co2ice_old <= eps) then ! There is enough to sublimate
515                h2subl = h2subl_tot
516                h2subl_tot = 0.
517                call subl_co2ice_layering(this,current1,h2subl,h_co2ice_old,h_h2oice_old,h_dust_old,new_lag1)
518            else if (h_co2ice_old < eps) then ! There is nothing to sublimate so we move to the underlying stratum
519                current1 => current1%down
520                new_lag1 = .true.
521            else ! Only a fraction can sublimate and so we move to the underlying stratum
522                h2subl = h_co2ice_old
523                h2subl_tot = h2subl_tot - h2subl
524                call subl_co2ice_layering(this,current1,h2subl,h_co2ice_old,h_h2oice_old,h_dust_old,new_lag1)
525                current1 => current1%down
526                new_lag1 = .true.
527            endif
528        enddo
529        if (h2subl_tot > 0.) then
530            write(*,'(a5,i3,a)') 'Year ', k, ' -> Not enough CO2 ice in the layering to complete the sublimation!'
531            stopPEM = .true.
532        endif
533        ! New stratum at the layering top by condensation of H2O ice
534        thickness = htend_h2oice/(1. - h2oice_porosity) + htend_dust
535        if (thickness > 0.) then ! Only if the stratum is builiding up
536             if (new_str) then
537                 call add_stratum(this,thickness,this%top%elevation + thickness,0.,htend_h2oice/thickness,htend_dust/thickness,1. - (htend_h2oice/thickness + htend_dust/thickness))
538                 new_str = .false.
539             else
540                 this%top%thickness = this%top%thickness + thickness
541                 this%top%elevation = this%top%elevation + thickness
542             endif
543        endif
544
545!------ Sublimation of CO2 ice + H2O ice
546    else if (htend_co2ice < 0. .and. htend_h2oice < 0.) then
547        write(*,'(a5,i3,a)') 'Year ', k, ' -> Sublimation of CO2 and H2O ice'
548        ! CO2 ice sublimation in the considered stratum + New stratum for dust lag
549        h2subl_tot = abs(htend_co2ice)
550        do while (h2subl_tot > 0. .and. associated(current1))
551            h_co2ice_old = current1%co2ice_volfrac*current1%thickness
552            h_h2oice_old = current1%h2oice_volfrac*current1%thickness
553            h_dust_old = current1%dust_volfrac*current1%thickness
554            ! How much CO2 ice can sublimate in the considered stratum?
555            if (h2subl_tot - h_co2ice_old <= eps) then ! There is enough to sublimate
556                h2subl = h2subl_tot
557                h2subl_tot = 0.
558                call subl_co2ice_layering(this,current1,h2subl,h_co2ice_old,h_h2oice_old,h_dust_old,new_lag1)
559            else if (h_co2ice_old < eps) then ! There is nothing to sublimate so we move to the underlying stratum
560                current1 => current1%down
561                new_lag1 = .true.
562            else ! Only a fraction can sublimate and so we move to the underlying stratum
563                h2subl = h_co2ice_old
564                h2subl_tot = h2subl_tot - h2subl
565                call subl_co2ice_layering(this,current1,h2subl,h_co2ice_old,h_h2oice_old,h_dust_old,new_lag1)
566                current1 => current1%down
567                new_lag1 = .true.
568            endif
569        enddo
570        if (h2subl_tot > 0.) then
571            write(*,'(a5,i3,a)') 'Year ', k, ' -> Not enough CO2 ice in the layering to complete the sublimation!'
572            stopPEM = .true.
573        endif
574        ! H2O ice sublimation in the considered stratum + New stratum for dust lag
575        h2subl_tot = abs(htend_h2oice)
576        do while (h2subl_tot > 0. .and. associated(current2))
577            h_co2ice_old = current2%co2ice_volfrac*current2%thickness
578            h_h2oice_old = current2%h2oice_volfrac*current2%thickness
579            h_dust_old = current2%dust_volfrac*current2%thickness
580            ! How much H2O ice can sublimate in the considered stratum?
581            if (h2subl_tot - h_h2oice_old <= eps) then ! There is enough to sublimate
582                h2subl = h2subl_tot
583                h2subl_tot = 0.
584                call subl_h2oice_layering(this,current2,h2subl,h_co2ice_old,h_h2oice_old,h_dust_old,new_lag2)
585            else if (h_h2oice_old < eps) then ! There is nothing to sublimate so we move to the underlying stratum
586                current2 => current2%down
587                new_lag2 = .true.
588            else ! Only a fraction can sublimate and so we move to the underlying stratum
589                h2subl = h_h2oice_old
590                h2subl_tot = h2subl_tot - h2subl
591                call subl_h2oice_layering(this,current2,h2subl,h_co2ice_old,h_h2oice_old,h_dust_old,new_lag2)
592                current2 => current2%down
593                new_lag2 = .true.
594            endif
595        enddo
596        if (h2subl_tot > 0.) then
597            write(*,'(a5,i3,a)') 'Year ', k, ' -> Not enough H2O ice in the layering to complete the sublimation!'
598            stopPEM = .true.
599        endif
600
601!------ Condensation of CO2 ice + Sublimation of H2O ice
602    else if (htend_co2ice >= 0. .and. htend_h2oice < 0.) then
603        error stop 'Impossible situation: CO2 ice condensation + H2O ice sublimation!'
604    endif
605endif
606
607END SUBROUTINE make_layering
608
609END MODULE layering_mod
Note: See TracBrowser for help on using the repository browser.