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

Last change on this file since 3707 was 3704, checked in by evos, 10 months ago

Changing the paramters of the PEM to be more realistic and to work with the layering

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