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

Last change on this file since 3383 was 3331, checked in by jbclement, 6 months ago

PEM:
Update of the layering algorithm + corrections of wrong lines commited in r3330.
JBC

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