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

Last change on this file since 3316 was 3308, checked in by jbclement, 20 months ago

PEM:
Few small corrections to make the PEM work in 3D, in particular concerning the initialization of the planet type and the evolution of ice with slopes.
JBC

File size: 27.9 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
16integer         :: nb_str_max
17
18! Physical parameters
19real, parameter :: tend_dust = 5.78e-2          ! Tendency of dust [kg.m-2.y-1]
20real, parameter :: dry_lag_porosity = 0.5       ! Porosity of dust lag
21real, parameter :: dry_regolith_porosity = 0.45 ! Porosity of regolith
22real, parameter :: co2ice_porosity = 0.3        ! Porosity of CO2 ice
23real, parameter :: h2oice_porosity = 0.3        ! Porosity of H2O ice
24real, parameter :: rho_co2ice = 1650.           ! Density of CO2 ice [kg.m-3]
25real, parameter :: rho_h2oice = 920.            ! Density of H2O ice [kg.m-3]
26real, parameter :: rho_dust = 2500.             ! Density of dust [kg.m-3]
27real, parameter :: rho_rock = 3200.             ! Density of rock [kg.m-3]
28
29! Stratum = node of the linked list
30type :: stratum
31    real               :: thickness          ! Layer thickness [m]
32    real               :: top_elevation      ! Layer top_elevation (top height from the surface) [m]
33    real               :: co2ice_volfrac     ! CO2 ice volumic fraction
34    real               :: h2oice_volfrac     ! H2O ice volumic fraction
35    real               :: dust_volfrac       ! Dust volumic fraction
36    real               :: air_volfrac        ! Air volumic fraction inside pores
37    type(stratum), pointer :: up => null()   ! Upper stratum (next node)
38    type(stratum), pointer :: down => null() ! Lower stratum (previous node)
39end type stratum
40
41! Layering = linked list
42type layering
43    integer                :: nb_str = 0       ! Number of strata
44    type(stratum), pointer :: bottom => null() ! First stratum (head of the list)
45    type(stratum), pointer :: top => null()    ! Last stratum (tail of the list)
46end type layering
47
48! Array of pointers to "stratum"
49type ptrarray
50    type(stratum), pointer :: p
51end type ptrarray
52
53!=======================================================================
54contains
55! Procedures to manipulate the data structure:
56!     > print_stratum
57!     > add_stratum
58!     > insert_stratum
59!     > rm_stratum
60!     > get_stratum
61!     > ini_layering
62!     > del_layering
63!     > print_layering
64!     > get_nb_str_max
65!     > stratif2array
66!     > array2stratif
67!     > print_stratif
68! Procedures for the algorithm to evolve the layering:
69!     > make_layering
70!     > subl_co2ice_layering
71!     > subl_h2oice_layering
72!     > lift_dust_lags
73!=======================================================================
74! To display a stratum
75SUBROUTINE print_stratum(this)
76
77implicit none
78
79!---- Arguments
80type(stratum), intent(in) :: this
81
82!---- Code
83write(*,'(a20,es13.6)') 'Thickness      : ', this%thickness
84write(*,'(a20,es13.6)') 'Top elevation  : ', this%top_elevation
85write(*,'(a20,es13.6)') 'CO2 ice (m3/m3): ', this%co2ice_volfrac
86write(*,'(a20,es13.6)') 'H2O ice (m3/m3): ', this%h2oice_volfrac
87write(*,'(a20,es13.6)') 'Dust (m3/m3)   : ', this%dust_volfrac
88write(*,'(a20,es13.6)') 'Air (m3/m3)    : ', this%air_volfrac
89
90END SUBROUTINE print_stratum
91
92!=======================================================================
93! To add a stratum to the top of a layering
94SUBROUTINE add_stratum(this,thickness,top_elevation,co2ice,h2oice,dust,air)
95
96implicit none
97
98!---- Arguments
99type(layering), intent(inout)  :: this
100real, intent(in), optional :: thickness, top_elevation, co2ice, h2oice, dust, air
101
102!---- Local variables
103type(stratum), pointer :: str
104
105!---- Code
106! Creation of the stratum
107allocate(str)
108nullify(str%up,str%down)
109str%thickness = 1.
110str%top_elevation = 1.
111str%co2ice_volfrac = 0.
112str%h2oice_volfrac = 0.
113str%dust_volfrac = 0.
114str%air_volfrac = 1.
115if (present(thickness)) str%thickness = thickness
116if (present(top_elevation)) str%top_elevation = top_elevation
117if (present(co2ice)) str%co2ice_volfrac = co2ice
118if (present(h2oice)) str%h2oice_volfrac = h2oice
119if (present(dust)) str%dust_volfrac = dust
120if (present(air)) str%air_volfrac = air
121
122! Verification of volume fraction
123if (abs(1. - (str%co2ice_volfrac + str%h2oice_volfrac + str%dust_volfrac + str%air_volfrac)) > tol) &
124     error stop 'add_stratum: properties for the new stratum are not possible (sum of volumic fraction /= 1)!'
125
126! Increment the number of strata
127this%nb_str = this%nb_str + 1
128
129! Add the stratum to the layering
130if (.not. associated(this%bottom)) then ! If it is the very first one
131    this%bottom => str
132    this%top => str
133else
134    str%down => this%top
135    this%top%up => str
136    this%top => str
137endif
138
139END SUBROUTINE add_stratum
140
141!=======================================================================
142! To insert a stratum after another one in a layering
143SUBROUTINE insert_stratum(this,str_prev,thickness,top_elevation,co2ice,h2oice,dust,air)
144
145implicit none
146
147!---- Arguments
148type(layering),         intent(inout) :: this
149type(stratum), pointer, intent(inout) :: str_prev
150real, intent(in), optional :: thickness, top_elevation, co2ice, h2oice, dust, air
151
152!---- Local variables
153type(stratum), pointer :: str, current
154
155!---- Code
156if (.not. associated(str_prev%up)) then ! If str_prev is the top stratum of the layering
157    call add_stratum(this,thickness,top_elevation,co2ice,h2oice,dust,air)
158else
159    ! Creation of the stratum
160    allocate(str)
161    nullify(str%up,str%down)
162    str%thickness = 1.
163    str%top_elevation = 1.
164    str%co2ice_volfrac = 0.
165    str%h2oice_volfrac = 0.
166    str%dust_volfrac = 0.
167    str%air_volfrac = 1.
168    if (present(thickness)) str%thickness = thickness
169    if (present(top_elevation)) str%top_elevation = top_elevation
170    if (present(co2ice)) str%co2ice_volfrac = co2ice
171    if (present(h2oice)) str%h2oice_volfrac = h2oice
172    if (present(dust)) str%dust_volfrac = dust
173    if (present(air)) str%air_volfrac = air
174
175    ! Verification of volume fraction
176    if (abs(1. - (str%co2ice_volfrac + str%h2oice_volfrac + str%dust_volfrac + str%air_volfrac)) > tol) &
177         error stop 'insert_stratum: properties for the new stratum are not possible (sum of volumic fraction /= 1)!'
178
179    ! Increment the number of strata
180    this%nb_str = this%nb_str + 1
181
182    ! Insert the stratum into the layering at the right place
183    str%down => str_prev
184    str%up => str_prev%up
185    str_prev%up => str
186    str%up%down => str
187
188    ! Correct the value of top_elevation for the upper strata
189    current => str%up
190    do while (associated(current))
191        current%top_elevation = current%down%top_elevation + current%thickness
192        current => current%up
193    enddo
194endif
195
196END SUBROUTINE insert_stratum
197
198!=======================================================================
199! To remove a stratum in a layering
200SUBROUTINE rm_stratum(this,str)
201
202implicit none
203
204!---- Arguments
205type(layering),         intent(inout) :: this
206type(stratum), pointer, intent(inout) :: str
207
208!---- Local variables
209type(stratum), pointer :: new_str
210
211!---- Code
212! Protect the 3 sub-surface strata from removing
213if (str%top_elevation <= 0.) return
214
215! Decrement the number of strata
216this%nb_str = this%nb_str - 1
217
218! Remove the stratum from the layering
219str%down%up => str%up
220if (associated(str%up)) then ! If it is not the last one at the top of the layering
221    str%up%down => str%down
222else
223    this%top => str%down
224endif
225new_str => str%down
226nullify(str%up,str%down)
227deallocate(str)
228nullify(str)
229str => new_str
230
231END SUBROUTINE rm_stratum
232
233!=======================================================================
234! To get a specific stratum in a layering
235FUNCTION get_stratum(lay,i) RESULT(str)
236
237implicit none
238
239!---- Arguments
240type(layering), intent(in) :: lay
241integer,        intent(in) :: i
242type(stratum), pointer     :: str
243
244!---- Local variables
245integer :: k
246
247!---- Code
248if (i < 1 .or. i > lay%nb_str) error stop 'get_stratum: requested number is beyond the number of strata of the layering!'
249k = 1
250str => lay%bottom
251do while (k /= i)
252    str => str%up
253    k = k + 1
254enddo
255
256END FUNCTION get_stratum
257
258!=======================================================================
259! To initialize the layering
260SUBROUTINE ini_layering(this)
261
262implicit none
263
264!---- Arguments
265type(layering), intent(inout) :: this
266
267!---- Code
268! Creation of three strata at the bottom of the layering
269! 1) Dry porous deep regolith
270call add_stratum(this,18.,-12.,0.,0.,dry_regolith_porosity,1. - dry_regolith_porosity)
271! 2) Ice-cemented regolith (ice table)
272call add_stratum(this,10.,-2.,0.,1. - dry_regolith_porosity,dry_regolith_porosity,0.)
273! 3) Dry porous regolith
274call add_stratum(this,2.,0.,0.,0.,dry_regolith_porosity,1. - dry_regolith_porosity)
275
276END SUBROUTINE ini_layering
277
278!=======================================================================
279! To delete the entire layering
280SUBROUTINE del_layering(this)
281
282implicit none
283
284!---- Arguments
285type(layering), intent(inout) :: this
286
287!---- Local variables
288type(stratum), pointer :: current, next
289
290!---- Code
291current => this%bottom
292do while (associated(current))
293    next => current%up
294    deallocate(current)
295    nullify(current)
296    current => next
297enddo
298this%nb_str = 0
299
300END SUBROUTINE del_layering
301
302!=======================================================================
303! To display a layering
304SUBROUTINE print_layering(this)
305
306implicit none
307
308!---- Arguments
309type(layering), intent(in) :: this
310
311!---- Local variables
312type(stratum), pointer :: current
313integer                :: i
314
315!---- Code
316current => this%top
317
318i = this%nb_str
319do while (associated(current))
320    write(*,'(a8,i4)') 'Stratum ', i
321    call print_stratum(current)
322    write(*,*)
323    current => current%down
324    i = i - 1
325enddo
326
327END SUBROUTINE print_layering
328
329!=======================================================================
330! To get the maximum number of "stratum" in the stratification (layerings)
331FUNCTION get_nb_str_max(stratif,ngrid,nslope) RESULT(nb_str_max)
332
333implicit none
334
335!---- Arguments
336type(layering), dimension(ngrid,nslope), intent(in) :: stratif
337integer,                                 intent(in) :: ngrid, nslope
338integer :: nb_str_max
339
340!---- Local variables
341integer :: ig, islope
342
343!---- Code
344nb_str_max = 0
345do islope = 1,nslope
346    do ig = 1,ngrid
347        nb_str_max = max(stratif(ig,islope)%nb_str,nb_str_max)
348    enddo
349enddo
350
351END FUNCTION get_nb_str_max
352
353!=======================================================================
354! To convert the stratification data structure (layerings) into an array able to be outputted
355SUBROUTINE stratif2array(stratif,ngrid,nslope,stratif_array)
356
357implicit none
358
359!---- Arguments
360integer,                                 intent(in) :: ngrid, nslope
361type(layering), dimension(ngrid,nslope), intent(in) :: stratif
362real, dimension(:,:,:,:), allocatable, intent(inout) :: stratif_array
363
364!---- Local variables
365type(stratum), pointer :: current
366integer                :: ig, islope, k
367
368!---- Code
369stratif_array = 0.
370do islope = 1,nslope
371    do ig = 1,ngrid
372        current => stratif(ig,islope)%bottom
373        k = 1
374        do while (associated(current))
375            stratif_array(ig,islope,k,1) = current%thickness
376            stratif_array(ig,islope,k,2) = current%top_elevation
377            stratif_array(ig,islope,k,3) = current%co2ice_volfrac
378            stratif_array(ig,islope,k,4) = current%h2oice_volfrac
379            stratif_array(ig,islope,k,5) = current%dust_volfrac
380            stratif_array(ig,islope,k,6) = current%air_volfrac
381            current => current%up
382            k = k + 1
383        enddo
384    enddo
385enddo
386
387END SUBROUTINE stratif2array
388
389!=======================================================================
390! To convert the stratification array into the stratification data structure (layerings)
391SUBROUTINE array2stratif(stratif_array,ngrid,nslope,stratif)
392
393implicit none
394
395!---- Arguments
396integer,                               intent(in) :: ngrid, nslope
397real, dimension(:,:,:,:), allocatable, intent(in) :: stratif_array
398type(layering), dimension(ngrid,nslope), intent(inout) :: stratif
399
400!---- Local variables
401type(stratum), pointer :: current
402integer                :: ig, islope, k
403
404!---- Code
405do islope = 1,nslope
406    do ig = 1,ngrid
407        current => stratif(ig,islope)%bottom
408        do k = 1,3
409            current%thickness      = stratif_array(ig,islope,k,1)
410            current%top_elevation  = stratif_array(ig,islope,k,2)
411            current%co2ice_volfrac = stratif_array(ig,islope,k,3)
412            current%h2oice_volfrac = stratif_array(ig,islope,k,4)
413            current%dust_volfrac   = stratif_array(ig,islope,k,5)
414            current%air_volfrac    = stratif_array(ig,islope,k,6)
415            current => current%up
416        enddo
417        do k = 4,size(stratif_array,3)
418            if (all(abs(stratif_array(ig,islope,k,:)) < eps)) exit
419            call add_stratum(stratif(ig,islope),stratif_array(ig,islope,k,1),stratif_array(ig,islope,k,2),stratif_array(ig,islope,k,3),stratif_array(ig,islope,k,4),stratif_array(ig,islope,k,5),stratif_array(ig,islope,k,6))
420        enddo
421    enddo
422enddo
423
424END SUBROUTINE array2stratif
425
426!=======================================================================
427! To display a stratification (layerings)
428SUBROUTINE print_stratif(this,ngrid,nslope)
429
430implicit none
431
432!---- Arguments
433integer,                                 intent(in) :: ngrid, nslope
434type(layering), dimension(ngrid,nslope), intent(in) :: this
435
436!---- Local variables
437integer :: ig, islope
438
439!---- Code
440do ig = 1,ngrid
441    write(*,'(a10,i4)') 'Grid cell ', ig
442    do islope = 1,nslope
443        write(*,'(a13,i1)') 'Slope number ', islope
444        call print_layering(this(ig,islope))
445        write(*,*) '~~~~~~~~~~'
446    enddo
447    write(*,*) '--------------------'
448enddo
449
450END SUBROUTINE print_stratif
451
452!=======================================================================
453! Layering algorithm
454SUBROUTINE make_layering(this,tend_co2ice,tend_h2oice,tend_dust,new_str,new_lag1,new_lag2,stopPEM,current1,current2)
455
456implicit none
457
458!---- Arguments
459type(layering),         intent(inout) :: this
460type(stratum), pointer, intent(inout) :: current1, current2
461logical,                intent(inout) :: new_str, new_lag1, new_lag2
462integer,                intent(inout) :: stopPEM
463real,     intent(in) :: tend_co2ice, tend_h2oice, tend_dust
464
465!---- Local variables
466real :: htend_co2ice, htend_h2oice, htend_dust
467real :: h_co2ice_old, h_h2oice_old, h_dust_old
468real :: thickness, h2subl, h2subl_tot, h2lift, h2lift_tot
469
470!---- Code
471htend_co2ice = tend_co2ice/rho_co2ice
472htend_h2oice = tend_h2oice/rho_h2oice
473htend_dust = tend_dust/rho_dust
474
475if (htend_dust < 0.) then ! Dust lifting
476    if (abs(htend_co2ice) > eps .or. abs(htend_h2oice) > eps) error stop 'Situation not managed: dust lifting + CO2/H2O ice condensation/sublimation!'
477    write(*,'(a)') ' Stratification -> Dust lifting'
478    h2lift_tot = abs(htend_dust)
479    do while (h2lift_tot > 0. .and. associated(current1))
480        ! Is the considered stratum a dust lag?
481        if (abs(1. - (current1%dust_volfrac + current1%air_volfrac)) < tol) then ! Yes, we can lift dust
482            h_dust_old = current1%dust_volfrac*current1%thickness
483            ! How much dust can be lifted in the considered dust lag?
484            if (h2lift_tot - h_dust_old <= eps) then ! There is enough to lift
485                h2lift = h2lift_tot
486                h2lift_tot = 0.
487                call lift_dust_lags(this,current1,h2lift)
488            else ! Only a fraction can be lifted and so we move to the underlying stratum
489                h2lift = h_dust_old
490                h2lift_tot = h2lift_tot - h2lift
491                call lift_dust_lags(this,current1,h2lift)
492                current1 => current1%down
493            endif
494        else ! No, we stop
495            write(*,'(a)') ' Stratification -> Dust lifting: no dust lag!'
496            stopPEM = 7
497            exit
498        endif
499    enddo
500    if (h2lift_tot > 0.) then
501        write(*,'(a)') ' Stratification -> Not enough dust in the lag layers to complete the lifting!'
502        stopPEM = 7
503    endif
504
505else
506
507!------ Dust sedimentation
508    if (abs(htend_co2ice) < eps .and. abs(htend_h2oice) < eps) then
509        write(*,'(a)') ' Stratification -> Dust sedimentation'
510        ! New stratum at the layering top by sedimentation of dust
511        thickness = htend_dust/(1. - dry_regolith_porosity)
512        if (thickness > 0.) then ! Only if the stratum is builiding up
513             if (new_str) then
514                 call add_stratum(this,thickness,this%top%top_elevation + thickness,0.,0.,htend_dust/thickness,dry_regolith_porosity)
515                 new_str = .false.
516             else
517                 this%top%thickness = this%top%thickness + thickness
518                 this%top%top_elevation = this%top%top_elevation + thickness
519             endif
520        endif
521
522!------ Condensation of CO2 ice + H2O ice
523    else if ((htend_co2ice >= 0. .and. htend_h2oice > 0.) .or. (htend_co2ice > 0. .and. htend_h2oice >= 0.)) then
524        write(*,'(a)') ' Stratification -> CO2 and H2O ice condensation'
525        ! New stratum at the layering top by condensation of CO2 and H2O ice
526        thickness = htend_co2ice/(1. - co2ice_porosity) + htend_h2oice/(1. - h2oice_porosity) + htend_dust
527        if (thickness > 0.) then ! Only if the stratum is builiding up
528             if (new_str) then
529                 call add_stratum(this,thickness,this%top%top_elevation + thickness,htend_co2ice/thickness,htend_h2oice/thickness,htend_dust/thickness,1. - (htend_co2ice/thickness + htend_h2oice/thickness + htend_dust/thickness))
530                 new_str = .false.
531             else
532                 this%top%thickness = this%top%thickness + thickness
533                 this%top%top_elevation = this%top%top_elevation + thickness
534             endif
535        endif
536
537!------ Sublimation of CO2 ice + Condensation of H2O ice
538    else if (htend_co2ice < 0. .and. htend_h2oice > 0.) then
539        write(*,'(a)') ' Stratification -> Sublimation of CO2 ice + Condensation of H2O ice'
540        ! CO2 ice sublimation in the considered stratum + New stratum for dust lag
541        h2subl_tot = abs(htend_co2ice)
542        do while (h2subl_tot > 0. .and. associated(current1))
543            h_co2ice_old = current1%co2ice_volfrac*current1%thickness
544            h_h2oice_old = current1%h2oice_volfrac*current1%thickness
545            h_dust_old = current1%dust_volfrac*current1%thickness
546            ! How much CO2 ice can sublimate in the considered stratum?
547            if (h2subl_tot - h_co2ice_old <= eps) then ! There is enough to sublimate
548                h2subl = h2subl_tot
549                h2subl_tot = 0.
550                call subl_co2ice_layering(this,current1,h2subl,h_co2ice_old,h_h2oice_old,h_dust_old,new_lag1)
551            else if (h_co2ice_old < eps) then ! There is nothing to sublimate so we move to the underlying stratum
552                current1 => current1%down
553                new_lag1 = .true.
554            else ! Only a fraction can sublimate and so we move to the underlying stratum
555                h2subl = h_co2ice_old
556                h2subl_tot = h2subl_tot - h2subl
557                call subl_co2ice_layering(this,current1,h2subl,h_co2ice_old,h_h2oice_old,h_dust_old,new_lag1)
558                current1 => current1%down
559                new_lag1 = .true.
560            endif
561        enddo
562        if (h2subl_tot > 0.) then
563            write(*,'(a)') ' Stratification -> Not enough CO2 ice in the layering to complete the sublimation!'
564            stopPEM = 7
565        endif
566        ! New stratum at the layering top by condensation of H2O ice
567        thickness = htend_h2oice/(1. - h2oice_porosity) + htend_dust
568        if (thickness > 0.) then ! Only if the stratum is builiding up
569             if (new_str) then
570                 call add_stratum(this,thickness,this%top%top_elevation + thickness,0.,htend_h2oice/thickness,htend_dust/thickness,1. - (htend_h2oice/thickness + htend_dust/thickness))
571                 new_str = .false.
572             else
573                 this%top%thickness = this%top%thickness + thickness
574                 this%top%top_elevation = this%top%top_elevation + thickness
575             endif
576        endif
577
578!------ Sublimation of CO2 ice + H2O ice
579    else if ((htend_co2ice <= 0. .and. htend_h2oice < 0.) .or. (htend_co2ice < 0. .and. htend_h2oice <= 0.)) then
580        write(*,'(a)') ' Stratification -> Sublimation of CO2 and H2O ice'
581        ! CO2 ice sublimation in the considered stratum + New stratum for dust lag
582        h2subl_tot = abs(htend_co2ice)
583        do while (h2subl_tot > 0. .and. associated(current1))
584            h_co2ice_old = current1%co2ice_volfrac*current1%thickness
585            h_h2oice_old = current1%h2oice_volfrac*current1%thickness
586            h_dust_old = current1%dust_volfrac*current1%thickness
587            ! How much CO2 ice can sublimate in the considered stratum?
588            if (h2subl_tot - h_co2ice_old <= eps) then ! There is enough to sublimate
589                h2subl = h2subl_tot
590                h2subl_tot = 0.
591                call subl_co2ice_layering(this,current1,h2subl,h_co2ice_old,h_h2oice_old,h_dust_old,new_lag1)
592            else if (h_co2ice_old < eps) then ! There is nothing to sublimate so we move to the underlying stratum
593                current1 => current1%down
594                new_lag1 = .true.
595            else ! Only a fraction can sublimate and so we move to the underlying stratum
596                h2subl = h_co2ice_old
597                h2subl_tot = h2subl_tot - h2subl
598                call subl_co2ice_layering(this,current1,h2subl,h_co2ice_old,h_h2oice_old,h_dust_old,new_lag1)
599                current1 => current1%down
600                new_lag1 = .true.
601            endif
602        enddo
603        if (h2subl_tot > 0.) then
604            write(*,'(a)') ' Stratification -> Not enough CO2 ice in the layering to complete the sublimation!'
605            stopPEM = 7
606        endif
607        ! H2O ice sublimation in the considered stratum + New stratum for dust lag
608        h2subl_tot = abs(htend_h2oice)
609        do while (h2subl_tot > 0. .and. associated(current2))
610            h_co2ice_old = current2%co2ice_volfrac*current2%thickness
611            h_h2oice_old = current2%h2oice_volfrac*current2%thickness
612            h_dust_old = current2%dust_volfrac*current2%thickness
613            ! How much H2O ice can sublimate in the considered stratum?
614            if (h2subl_tot - h_h2oice_old <= eps) then ! There is enough to sublimate
615                h2subl = h2subl_tot
616                h2subl_tot = 0.
617                call subl_h2oice_layering(this,current2,h2subl,h_co2ice_old,h_h2oice_old,h_dust_old,new_lag2)
618            else if (h_h2oice_old < eps) then ! There is nothing to sublimate so we move to the underlying stratum
619                current2 => current2%down
620                new_lag2 = .true.
621            else ! Only a fraction can sublimate and so we move to the underlying stratum
622                h2subl = h_h2oice_old
623                h2subl_tot = h2subl_tot - h2subl
624                call subl_h2oice_layering(this,current2,h2subl,h_co2ice_old,h_h2oice_old,h_dust_old,new_lag2)
625                current2 => current2%down
626                new_lag2 = .true.
627            endif
628        enddo
629        if (h2subl_tot > 0.) then
630            write(*,'(a)') ' Stratification -> Not enough H2O ice in the layering to complete the sublimation!'
631            stopPEM = 7
632        endif
633
634!------ Condensation of CO2 ice + Sublimation of H2O ice
635    else if (htend_co2ice > 0. .and. htend_h2oice < 0.) then
636        error stop 'Impossible situation: CO2 ice condensation + H2O ice sublimation!'
637    endif
638endif
639
640END SUBROUTINE make_layering
641
642!=======================================================================
643! To sublimate CO2 ice in the layering
644SUBROUTINE subl_co2ice_layering(this,str,h2subl,h_co2ice_old,h_h2oice_old,h_dust_old,new_lag)
645
646implicit none
647
648!---- Arguments
649type(layering),         intent(inout) :: this
650type(stratum), pointer, intent(inout) :: str
651logical,                intent(inout) :: new_lag
652real, intent(in) :: h2subl, h_co2ice_old, h_h2oice_old, h_dust_old
653
654!---- Local variables
655real                   :: r_subl, hsubl_dust, h_lag
656type(stratum), pointer :: current
657
658!---- Code
659! How much dust does CO2 ice sublimation involve to create the lag?
660r_subl = h2subl/(1. - co2ice_porosity) &
661        /(str%thickness*(str%co2ice_volfrac/(1. - co2ice_porosity) + str%h2oice_volfrac/(1. - h2oice_porosity)))
662hsubl_dust = r_subl*str%dust_volfrac*str%thickness
663! Update of properties in the sublimating stratum
664str%thickness = str%thickness - h2subl/(1. - co2ice_porosity) - hsubl_dust
665str%top_elevation = str%top_elevation - h2subl/(1. - co2ice_porosity) - hsubl_dust
666str%co2ice_volfrac = (h_co2ice_old - h2subl)/str%thickness
667str%h2oice_volfrac = h_h2oice_old/str%thickness
668str%dust_volfrac = (h_dust_old - hsubl_dust)/str%thickness
669str%air_volfrac = 1. - (str%co2ice_volfrac + str%h2oice_volfrac + str%dust_volfrac)
670! Correct the value of top_elevation for the upper strata
671current => str%up
672do while (associated(current))
673    current%top_elevation = current%down%top_elevation + current%thickness
674    current => current%up
675enddo
676! Remove the sublimating stratum if there is no ice anymore
677if (str%thickness < tol) call rm_stratum(this,str)
678! New stratum = dust lag
679h_lag = hsubl_dust/(1. - dry_lag_porosity)
680if (h_lag > 0.) then ! Only if the dust lag is building up
681    if (new_lag) then
682        call insert_stratum(this,str,h_lag,str%top_elevation + h_lag,0.,0.,1. - dry_lag_porosity,dry_lag_porosity)
683        new_lag = .false.
684    else
685        str%up%thickness = str%up%thickness + h_lag
686        str%up%top_elevation = str%up%top_elevation + h_lag
687    endif
688endif
689
690END SUBROUTINE subl_co2ice_layering
691
692!=======================================================================
693! To sublimate H2O ice in the layering
694SUBROUTINE subl_h2oice_layering(this,str,h2subl,h_co2ice_old,h_h2oice_old,h_dust_old,new_lag)
695
696implicit none
697
698!---- Arguments
699type(layering),         intent(inout) :: this
700type(stratum), pointer, intent(inout) :: str
701logical,                intent(inout) :: new_lag
702real, intent(in) :: h2subl, h_co2ice_old, h_h2oice_old, h_dust_old
703
704!---- Local variables
705real                   :: r_subl, hsubl_dust, h_lag
706type(stratum), pointer :: current
707
708!---- Code
709! How much dust does CO2 ice sublimation involve to create the lag?
710r_subl = h2subl/(1. - h2oice_porosity) &
711        /(str%thickness*(str%co2ice_volfrac/(1. - co2ice_porosity) + str%h2oice_volfrac/(1. - h2oice_porosity)))
712hsubl_dust = r_subl*str%dust_volfrac*str%thickness
713! Update of properties in the sublimating stratum
714str%thickness = str%thickness - h2subl/(1. - h2oice_porosity) - hsubl_dust
715str%top_elevation = str%top_elevation - h2subl/(1. - h2oice_porosity) - hsubl_dust
716str%co2ice_volfrac = h_co2ice_old/str%thickness
717str%h2oice_volfrac = (h_h2oice_old - h2subl)/str%thickness
718str%dust_volfrac = (h_dust_old - hsubl_dust)/str%thickness
719str%air_volfrac = 1. - (str%co2ice_volfrac + str%h2oice_volfrac + str%dust_volfrac)
720! Correct the value of top_elevation for the upper strata
721current => str%up
722do while (associated(current))
723    current%top_elevation = current%down%top_elevation + current%thickness
724    current => current%up
725enddo
726! Remove the sublimating stratum if there is no ice anymore
727if (str%thickness < tol) call rm_stratum(this,str)
728! New stratum = dust lag
729h_lag = hsubl_dust/(1. - dry_lag_porosity)
730if (h_lag > 0.) then ! Only if the dust lag is building up
731    if (new_lag) then
732        call insert_stratum(this,str,h_lag,str%top_elevation + h_lag,0.,0.,1. - dry_lag_porosity,dry_lag_porosity)
733        new_lag = .false.
734    else
735        str%up%thickness = str%up%thickness + h_lag
736        str%up%top_elevation = str%up%top_elevation + h_lag
737    endif
738endif
739
740END SUBROUTINE subl_h2oice_layering
741
742!=======================================================================
743! To lift dust in the layering
744SUBROUTINE lift_dust_lags(this,str,h2lift)
745
746implicit none
747
748!---- Arguments
749type(layering),         intent(inout) :: this
750type(stratum), pointer, intent(inout) :: str
751real, intent(in) :: h2lift
752
753!---- Code
754! Update of properties in the eroding dust lag
755str%thickness = str%thickness - h2lift/(1. - str%air_volfrac)
756str%top_elevation = str%top_elevation - h2lift/(1. - str%air_volfrac)
757! Remove the eroding dust lag if there is no dust anymore
758if (str%thickness < tol) call rm_stratum(this,str)
759
760END SUBROUTINE lift_dust_lags
761
762END MODULE layering_mod
Note: See TracBrowser for help on using the repository browser.