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

Last change on this file since 3666 was 3666, checked in by jbclement, 4 months ago

PEM:

  • Adjusments of few scripts to handle more situations.
  • Bug correction related to deallocation in case of "soil_pem = .false." or "layering_algo = .true.".

JBC

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