source: trunk/LMDZ.COMMON/libf/evolution/layered_deposits.F90 @ 3995

Last change on this file since 3995 was 3991, checked in by jbclement, 5 weeks ago

PEM:
Apply documentation template everywhere: standardized headers format with short description, separators between functions/subroutines, normalized code sections, aligned dependencies/arguments/variables declaration.
JBC

File size: 43.6 KB
Line 
1MODULE layered_deposits
2!-----------------------------------------------------------------------
3! NAME
4!     layered_deposits
5!
6! DESCRIPTION
7!     Manage layered deposits in the PEM with a linked list data structure.
8!     Provides data types and subroutines to manipulate layers of ice and dust.
9!
10! AUTHORS & DATE
11!     JB Clement, 2024
12!
13! NOTES
14!
15!-----------------------------------------------------------------------
16
17! DEPENDENCIES
18! ------------
19use surf_ice, only: rho_co2ice, rho_h2oice
20
21! DECLARATION
22! -----------
23implicit none
24
25! MODULE VARIABLES
26! ----------------
27! Numerical parameter
28real, parameter :: eps = epsilon(1.), tol = 1.e2*eps
29integer         :: nb_str_max
30logical         :: layering_algo
31
32! Physical parameters
33logical         :: impose_dust_ratio = .false. ! Impose dust-to-ice ratio instead of dust tendency (see 'dust2ice_ratio')
34real            :: dust2ice_ratio    = 0.1     ! Dust-to-ice ratio when ice condenses (10% by default)
35real            :: d_dust            = 5.78e-2 ! Tendency of dust [kg.m-2.y-1] (1.e-9 kg.m-2.s-1 by default)
36real, parameter :: dry_lag_porosity  = 0.2     ! Porosity of dust lag
37real, parameter :: wet_lag_porosity  = 0.15    ! Porosity of water ice lag
38real, parameter :: regolith_porosity = 0.4     ! Porosity of regolith
39real, parameter :: breccia_porosity  = 0.1     ! Porosity of breccia
40real, parameter :: co2ice_porosity   = 0.05    ! Porosity of CO2 ice
41real, parameter :: h2oice_porosity   = 0.1     ! Porosity of H2O ice
42real, parameter :: rho_dust          = 2500.   ! Density of dust [kg.m-3]
43real, parameter :: rho_rock          = 3200.   ! Density of rock [kg.m-3]
44real, parameter :: h_patchy_dust     = 5.e-4   ! Height under which a dust lag is considered patchy [m]
45real, parameter :: h_patchy_ice      = 5.e-4   ! Height under which a H2O ice lag is considered patchy [m]
46
47! Parameters for CO2 flux correction (inspired by Levrard et al. 2007)
48real, parameter :: hmin_lag_co2 = 0.5 ! Minimal height of the lag deposit to reduce the sublimation rate [m]
49real, parameter :: fred_sublco2 = 0.1 ! Reduction factor of sublimation rate
50
51! DATA STRUCTURES
52! ---------------
53! Stratum = node of the linked list
54type :: stratum
55    real                   :: top_elevation   ! Layer top_elevation (top height from the surface) [m]
56    real                   :: h_co2ice        ! Height of CO2 ice [m]
57    real                   :: h_h2oice        ! Height of H2O ice [m]
58    real                   :: h_dust          ! Height of dust [m]
59    real                   :: h_pore          ! Height of pores [m]
60    real                   :: poreice_volfrac ! Pore-filled ice volumetric fraction
61    type(stratum), pointer :: up => null()    ! Upper stratum (next node)
62    type(stratum), pointer :: down => null()  ! Lower stratum (previous node)
63end type stratum
64
65! Layering = linked list
66type layering
67    integer                :: nb_str = 0       ! Number of strata
68    type(stratum), pointer :: bottom => null() ! First stratum (head of the list)
69    type(stratum), pointer :: top => null()    ! Last stratum (tail of the list)
70    !real                   :: h_toplag         ! Height of dust layer at the top [m]
71    !type(stratum), pointer :: subice => null() ! Shallower stratum containing ice
72    !type(stratum), pointer :: surf => null()   ! Surface stratum
73end type layering
74
75! Array of pointers to "stratum"
76type ptrarray
77    type(stratum), pointer :: p
78end type ptrarray
79
80contains
81!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
82
83!=======================================================================
84SUBROUTINE print_stratum(this)
85!-----------------------------------------------------------------------
86! NAME
87!     print_stratum
88!
89! DESCRIPTION
90!     Print a stratum.
91!
92! AUTHORS & DATE
93!     JB Clement, 2024
94!
95! NOTES
96!
97!-----------------------------------------------------------------------
98
99! DECLARATION
100! -----------
101implicit none
102
103! ARGUMENTS
104! ---------
105type(stratum), intent(in) :: this
106
107! CODE
108! ----
109write(*,'(a,es13.6)') 'Top elevation       [m]: ', this%top_elevation
110write(*,'(a,es13.6)') 'Height of CO2 ice   [m]: ', this%h_co2ice
111write(*,'(a,es13.6)') 'Height of H2O ice   [m]: ', this%h_h2oice
112write(*,'(a,es13.6)') 'Height of dust      [m]: ', this%h_dust
113write(*,'(a,es13.6)') 'Height of pores     [m]: ', this%h_pore
114write(*,'(a,es13.6)') 'Pore-filled ice [m3/m3]: ', this%poreice_volfrac
115
116END SUBROUTINE print_stratum
117!=======================================================================
118
119!=======================================================================
120SUBROUTINE add_stratum(this,top_elevation,co2ice,h2oice,dust,pore,poreice)
121!-----------------------------------------------------------------------
122! NAME
123!     add_stratum
124!
125! DESCRIPTION
126!     Add a stratum to the top of a layering.
127!
128! AUTHORS & DATE
129!     JB Clement, 2024
130!
131! NOTES
132!
133!-----------------------------------------------------------------------
134
135! DECLARATION
136! -----------
137implicit none
138
139! ARGUMENTS
140! ---------
141type(layering), intent(inout)        :: this
142real,           intent(in), optional :: top_elevation, co2ice, h2oice, dust, pore, poreice
143
144! LOCAL VARIABLES
145! ---------------
146type(stratum), pointer :: str
147
148! CODE
149! ----
150! Creation of the stratum
151allocate(str)
152nullify(str%up,str%down)
153str%top_elevation   = 1.
154str%h_co2ice        = 0.
155str%h_h2oice        = 0.
156str%h_dust          = 1.
157str%h_pore          = 0.
158str%poreice_volfrac = 0.
159if (present(top_elevation)) str%top_elevation   = top_elevation
160if (present(co2ice))        str%h_co2ice        = co2ice
161if (present(h2oice))        str%h_h2oice        = h2oice
162if (present(dust))          str%h_dust          = dust
163if (present(pore))          str%h_pore          = pore
164if (present(poreice))       str%poreice_volfrac = poreice
165
166! Increment the number of strata
167this%nb_str = this%nb_str + 1
168
169! Add the stratum to the layering
170if (.not. associated(this%bottom)) then ! If it is the very first one
171    this%bottom => str
172    this%top => str
173else
174    str%down => this%top
175    this%top%up => str
176    this%top => str
177endif
178
179END SUBROUTINE add_stratum
180!=======================================================================
181
182!=======================================================================
183SUBROUTINE insert_stratum(this,str_prev,top_elevation,co2ice,h2oice,dust,pore,poreice)
184!-----------------------------------------------------------------------
185! NAME
186!     insert_stratum
187!
188! DESCRIPTION
189!     Insert a stratum after a given previous stratum in the layering.
190!
191! AUTHORS & DATE
192!     JB Clement, 2024
193!
194! NOTES
195!
196!-----------------------------------------------------------------------
197
198! DECLARATION
199! -----------
200implicit none
201
202! ARGUMENTS
203! ---------
204type(layering),         intent(inout)        ::  this
205type(stratum), pointer, intent(inout)        ::  str_prev
206real,                   intent(in), optional :: top_elevation, co2ice, h2oice, dust, pore, poreice
207
208! LOCAL VARIABLES
209! ---------------
210type(stratum), pointer :: str, current
211
212! CODE
213! ----
214if (.not. associated(str_prev%up)) then ! If str_prev is the top stratum of the layering
215    call add_stratum(this,top_elevation,co2ice,h2oice,dust,pore,poreice)
216else
217    ! Creation of the stratum
218    allocate(str)
219    nullify(str%up,str%down)
220    str%top_elevation   = 1.
221    str%h_co2ice        = 0.
222    str%h_h2oice        = 0.
223    str%h_dust          = 1.
224    str%h_pore          = 0.
225    str%poreice_volfrac = 0.
226    if (present(top_elevation)) str%top_elevation   = top_elevation
227    if (present(co2ice))        str%h_co2ice        = co2ice
228    if (present(h2oice))        str%h_h2oice        = h2oice
229    if (present(dust))          str%h_dust          = dust
230    if (present(pore))          str%h_pore          = pore
231    if (present(poreice))       str%poreice_volfrac = poreice
232
233    ! Increment the number of strata
234    this%nb_str = this%nb_str + 1
235
236    ! Insert the stratum into the layering at the right place
237    str%down => str_prev
238    str%up => str_prev%up
239    str_prev%up => str
240    str%up%down => str
241
242    ! Correct the value of top_elevation for the upper strata
243    current => str%up
244    do while (associated(current))
245        current%top_elevation = current%down%top_elevation + thickness(current)
246        current => current%up
247    enddo
248endif
249
250END SUBROUTINE insert_stratum
251!=======================================================================
252
253!=======================================================================
254SUBROUTINE del_stratum(this,str)
255!-----------------------------------------------------------------------
256! NAME
257!     del_stratum
258!
259! DESCRIPTION
260!     Delete a stratum from the layering and fix links.
261!
262! AUTHORS & DATE
263!     JB Clement, 2024
264!
265! NOTES
266!
267!-----------------------------------------------------------------------
268
269! DECLARATION
270! -----------
271implicit none
272
273! ARGUMENTS
274! ---------
275type(layering),         intent(inout) :: this
276type(stratum), pointer, intent(inout) :: str
277
278! LOCAL VARIABLES
279! ---------------
280type(stratum), pointer :: new_str
281
282! CODE
283! ----
284! Protect the sub-surface strata from deletion
285if (str%top_elevation <= 0.) return
286
287! Decrement the number of strata
288this%nb_str = this%nb_str - 1
289
290! Making the new links
291if (associated(str%down)) then ! If there is a lower stratum
292    str%down%up => str%up
293else ! If it was the first stratum (bottom of layering)
294    this%bottom => str%up
295endif
296if (associated(str%up)) then ! If there is an upper stratum
297    str%up%down => str%down
298else ! If it was the last stratum (top of layering)
299    this%top => str%down
300endif
301
302! Remove the stratum from the layering
303new_str => str%down
304nullify(str%up,str%down)
305deallocate(str)
306nullify(str)
307str => new_str
308
309END SUBROUTINE del_stratum
310!=======================================================================
311
312!=======================================================================
313! To get a specific stratum in a layering
314FUNCTION get_stratum(lay,i) RESULT(str)
315!-----------------------------------------------------------------------
316! NAME
317!     get_stratum
318!
319! DESCRIPTION
320!     Return the i-th stratum in the layering.
321!
322! AUTHORS & DATE
323!     JB Clement, 2024
324!
325! NOTES
326!
327!-----------------------------------------------------------------------
328
329! DECLARATION
330! -----------
331implicit none
332
333! ARGUMENTS
334! ---------
335type(layering), intent(in) :: lay
336integer,        intent(in) :: i
337type(stratum), pointer     :: str
338
339! LOCAL VARIABLES
340! ---------------
341integer :: k
342
343! CODE
344! ----
345if (i < 1 .or. i > lay%nb_str) error stop 'get_stratum: requested number is beyond the number of strata of the layering!'
346k = 1
347str => lay%bottom
348do while (k /= i)
349    str => str%up
350    k = k + 1
351enddo
352
353END FUNCTION get_stratum
354!=======================================================================
355
356!=======================================================================
357! To initialize the layering
358SUBROUTINE ini_layering(this)
359!-----------------------------------------------------------------------
360! NAME
361!     del_layering
362!
363! DESCRIPTION
364!     Delete all strata in a layering and reset counters.
365!
366! AUTHORS & DATE
367!     JB Clement, 2024
368!
369! NOTES
370!
371!-----------------------------------------------------------------------
372
373! DEPENDENCIES
374! ------------
375use soil, only: do_soil, nsoilmx_PEM, layer_PEM, index_breccia, index_bedrock
376
377! DECLARATION
378! -----------
379implicit none
380
381! ARGUMENTS
382! ---------
383type(layering), intent(inout) :: this
384
385! LOCAL VARIABLES
386! ---------------
387integer :: i
388real    :: h_soil, h_pore, h_tot
389
390! CODE
391! ----
392! Creation of strata at the bottom of the layering to describe the sub-surface
393if (do_soil) then
394    do i = nsoilmx_PEM,index_bedrock,-1
395        h_soil = layer_PEM(i) - layer_PEM(i - 1) ! No porosity
396        call add_stratum(this,-layer_PEM(i - 1),0.,0.,h_soil,0.,0.)
397    enddo
398    do i = index_bedrock - 1,index_breccia,-1
399        h_tot = layer_PEM(i) - layer_PEM(i - 1)
400        h_pore = h_tot*breccia_porosity
401        h_soil = h_tot - h_pore
402        call add_stratum(this,-layer_PEM(i - 1),0.,0.,h_soil,h_pore,0.)
403    enddo
404    do i = index_breccia - 1,2,-1
405        h_tot = layer_PEM(i) - layer_PEM(i - 1)
406        h_pore = h_tot*regolith_porosity
407        h_soil = h_tot - h_pore
408        call add_stratum(this,-layer_PEM(i - 1),0.,0.,h_soil,h_pore,0.)
409    enddo
410    h_pore = layer_PEM(1)*regolith_porosity
411    h_soil = layer_PEM(1) - h_pore
412    call add_stratum(this,0.,0.,0.,h_soil,h_pore,0.)
413endif
414
415END SUBROUTINE ini_layering
416!=======================================================================
417
418!=======================================================================
419SUBROUTINE del_layering(this)
420!-----------------------------------------------------------------------
421! NAME
422!     del_layering
423!
424! DESCRIPTION
425!     Delete all strata in a layering and reset counters.
426!
427! AUTHORS & DATE
428!     JB Clement, 2024
429!
430! NOTES
431!
432!-----------------------------------------------------------------------
433
434! DECLARATION
435! -----------
436implicit none
437
438! ARGUMENTS
439! ---------
440type(layering), intent(inout) :: this
441
442! LOCAL VARIABLES
443! ---------------
444type(stratum), pointer :: current, next
445
446! CODE
447! ----
448current => this%bottom
449do while (associated(current))
450    next => current%up
451    deallocate(current)
452    nullify(current)
453    current => next
454enddo
455this%nb_str = 0
456
457END SUBROUTINE del_layering
458!=======================================================================
459
460!=======================================================================
461SUBROUTINE print_layering(this)
462!-----------------------------------------------------------------------
463! NAME
464!     print_layering
465!
466! DESCRIPTION
467!     Display all strata from top to bottom for a layering.
468!
469! AUTHORS & DATE
470!     JB Clement, 2024
471!
472! NOTES
473!
474!-----------------------------------------------------------------------
475
476! DECLARATION
477! -----------
478implicit none
479
480! ARGUMENTS
481! ---------
482type(layering), intent(in) :: this
483
484! LOCAL VARIABLES
485! ---------------
486type(stratum), pointer :: current
487integer                :: i
488
489! CODE
490! ----
491current => this%top
492
493i = this%nb_str
494do while (associated(current))
495    write(*,'(a,i4)') 'Stratum ', i
496    call print_stratum(current)
497    write(*,*)
498    current => current%down
499    i = i - 1
500enddo
501
502END SUBROUTINE print_layering
503!=======================================================================
504
505!=======================================================================
506FUNCTION get_nb_str_max(layerings_map,ngrid,nslope) RESULT(nb_str_max)
507!-----------------------------------------------------------------------
508! NAME
509!     get_nb_str_max
510!
511! DESCRIPTION
512!     Return the maximum number of strata across all grid/slope layerings.
513!
514! AUTHORS & DATE
515!     JB Clement, 2024
516!
517! NOTES
518!
519!-----------------------------------------------------------------------
520
521! DECLARATION
522! -----------
523implicit none
524
525! ARGUMENTS
526! ---------
527type(layering), dimension(ngrid,nslope), intent(in) :: layerings_map
528integer,                                 intent(in) :: ngrid, nslope
529integer                                             :: nb_str_max
530
531! LOCAL VARIABLES
532! ---------------
533integer :: ig, islope
534
535! CODE
536! ----
537nb_str_max = 0
538do islope = 1,nslope
539    do ig = 1,ngrid
540        nb_str_max = max(layerings_map(ig,islope)%nb_str,nb_str_max)
541    enddo
542enddo
543
544END FUNCTION get_nb_str_max
545!=======================================================================
546
547!=======================================================================
548SUBROUTINE map2array(layerings_map,ngrid,nslope,layerings_array)
549!-----------------------------------------------------------------------
550! NAME
551!     map2array
552!
553! DESCRIPTION
554!     Convert the layerings map into an allocatable array for output.
555!
556! AUTHORS & DATE
557!     JB Clement, 2024
558!
559! NOTES
560!
561!-----------------------------------------------------------------------
562
563! DECLARATION
564! -----------
565implicit none
566
567! ARGUMENTS
568! ---------
569integer,                                 intent(in)    :: ngrid, nslope
570type(layering), dimension(ngrid,nslope), intent(in)    :: layerings_map
571real, dimension(:,:,:,:), allocatable,   intent(inout) :: layerings_array
572
573! LOCAL VARIABLES
574! ---------------
575type(stratum), pointer :: current
576integer                :: ig, islope, k
577
578! CODE
579! ----
580layerings_array = 0.
581do islope = 1,nslope
582    do ig = 1,ngrid
583        current => layerings_map(ig,islope)%bottom
584        k = 1
585        do while (associated(current))
586            layerings_array(ig,islope,k,1) = current%top_elevation
587            layerings_array(ig,islope,k,2) = current%h_co2ice
588            layerings_array(ig,islope,k,3) = current%h_h2oice
589            layerings_array(ig,islope,k,4) = current%h_dust
590            layerings_array(ig,islope,k,5) = current%h_pore
591            layerings_array(ig,islope,k,6) = current%poreice_volfrac
592            current => current%up
593            k = k + 1
594        enddo
595    enddo
596enddo
597
598END SUBROUTINE map2array
599!=======================================================================
600
601!=======================================================================
602SUBROUTINE array2map(layerings_array,ngrid,nslope,layerings_map)
603!-----------------------------------------------------------------------
604! NAME
605!     array2map
606!
607! DESCRIPTION
608!     Convert the stratification array back into the layerings map.
609!
610! AUTHORS & DATE
611!     JB Clement, 2024
612!
613! NOTES
614!
615!-----------------------------------------------------------------------
616
617! DECLARATION
618! -----------
619implicit none
620
621! ARGUMENTS
622! ---------
623integer,                                 intent(in)    :: ngrid, nslope
624real, dimension(:,:,:,:), allocatable,   intent(in)    :: layerings_array
625type(layering), dimension(ngrid,nslope), intent(inout) :: layerings_map
626
627! LOCAL VARIABLES
628! ---------------
629integer :: ig, islope, k
630
631! CODE
632! ----
633do islope = 1,nslope
634    do ig = 1,ngrid
635        do k = 1,size(layerings_array,3)
636            call add_stratum(layerings_map(ig,islope),layerings_array(ig,islope,k,1),layerings_array(ig,islope,k,2),layerings_array(ig,islope,k,3),layerings_array(ig,islope,k,4),layerings_array(ig,islope,k,5),layerings_array(ig,islope,k,6))
637        enddo
638    enddo
639enddo
640
641END SUBROUTINE array2map
642!=======================================================================
643
644!=======================================================================
645SUBROUTINE print_layerings_map(this,ngrid,nslope)
646!-----------------------------------------------------------------------
647! NAME
648!     print_layerings_map
649!
650! DESCRIPTION
651!     Display the entire layerings map for all grids and slopes.
652!
653! AUTHORS & DATE
654!     JB Clement, 2024
655!
656! NOTES
657!
658!-----------------------------------------------------------------------
659
660! DECLARATION
661! -----------
662implicit none
663
664! ARGUMENTS
665! ---------
666integer,                                 intent(in) :: ngrid, nslope
667type(layering), dimension(ngrid,nslope), intent(in) :: this
668
669! LOCAL VARIABLES
670! ---------------
671integer :: ig, islope
672
673! CODE
674! ----
675do ig = 1,ngrid
676    write(*,'(a10,i4)') 'Grid cell ', ig
677    do islope = 1,nslope
678        write(*,'(a13,i1)') 'Slope number ', islope
679        call print_layering(this(ig,islope))
680        write(*,*) '~~~~~~~~~~'
681    enddo
682    write(*,*) '--------------------'
683enddo
684
685END SUBROUTINE print_layerings_map
686!=======================================================================
687
688!=======================================================================
689FUNCTION thickness(this) RESULT(h_str)
690!-----------------------------------------------------------------------
691! NAME
692!     thickness
693!
694! DESCRIPTION
695!     Compute the total thickness of a stratum.
696!
697! AUTHORS & DATE
698!     JB Clement, 2024
699!
700! NOTES
701!
702!-----------------------------------------------------------------------
703
704! DECLARATION
705! -----------
706implicit none
707
708! ARGUMENTS
709! ---------
710type(stratum), intent(in) :: this
711
712! LOCAL VARIABLES
713! ---------------
714real :: h_str
715
716! CODE
717! ----
718h_str = this%h_co2ice + this%h_h2oice + this%h_dust + this%h_pore
719
720END FUNCTION thickness
721!=======================================================================
722
723!=======================================================================
724FUNCTION is_co2ice_str(str) RESULT(co2ice_str)
725!-----------------------------------------------------------------------
726! NAME
727!     is_co2ice_str
728!
729! DESCRIPTION
730!     Check if a stratum can be considered as a CO2 ice layer.
731!
732! AUTHORS & DATE
733!     JB Clement, 2024
734!
735! NOTES
736!
737!-----------------------------------------------------------------------
738
739! DECLARATION
740! -----------
741implicit none
742
743! ARGUMENTS
744! ---------
745type(stratum), intent(in) :: str
746
747! LOCAL VARIABLES
748! ---------------
749logical :: co2ice_str
750
751! CODE
752! ----
753co2ice_str = .false.
754if (str%h_co2ice > str%h_h2oice .and. str%h_co2ice > str%h_dust) co2ice_str = .true.
755
756END FUNCTION is_co2ice_str
757!=======================================================================
758
759!=======================================================================
760FUNCTION is_h2oice_str(str) RESULT(h2oice_str)
761!-----------------------------------------------------------------------
762! NAME
763!     is_h2oice_str
764!
765! DESCRIPTION
766!     Check if a stratum can be considered as a H2O ice layer.
767!
768! AUTHORS & DATE
769!     JB Clement, 2024
770!
771! NOTES
772!
773!-----------------------------------------------------------------------
774
775! DECLARATION
776! -----------
777implicit none
778
779! ARGUMENTS
780! ---------
781type(stratum), intent(in) :: str
782
783! LOCAL VARIABLES
784! ---------------
785logical :: h2oice_str
786
787! CODE
788! ----
789h2oice_str = .false.
790if (str%h_h2oice > str%h_co2ice .and. str%h_h2oice > str%h_dust) h2oice_str = .true.
791
792END FUNCTION is_h2oice_str
793!=======================================================================
794
795!=======================================================================
796FUNCTION is_dust_str(str) RESULT(dust_str)
797!-----------------------------------------------------------------------
798! NAME
799!     is_dust_str
800!
801! DESCRIPTION
802!     Check if a stratum can be considered as a dust layer.
803!
804! AUTHORS & DATE
805!     JB Clement, 2024
806!
807! NOTES
808!
809!-----------------------------------------------------------------------
810
811! DECLARATION
812! -----------
813implicit none
814
815! ARGUMENTS
816! ---------
817type(stratum), intent(in) :: str
818
819! LOCAL VARIABLES
820! ---------------
821logical :: dust_str
822
823! CODE
824! ----
825dust_str = .false.
826if (str%h_dust > str%h_co2ice .and. str%h_dust > str%h_h2oice) dust_str = .true.
827
828END FUNCTION is_dust_str
829!=======================================================================
830
831!=======================================================================
832FUNCTION is_dust_lag(str) RESULT(dust_lag)
833!-----------------------------------------------------------------------
834! NAME
835!     is_dust_lag
836!
837! DESCRIPTION
838!     Check if a stratum is a dust lag (no ice content).
839!
840! AUTHORS & DATE
841!     JB Clement, 2024
842!
843! NOTES
844!
845!-----------------------------------------------------------------------
846
847! DECLARATION
848! -----------
849implicit none
850
851! ARGUMENTS
852! ---------
853type(stratum), intent(in) :: str
854
855! LOCAL VARIABLES
856! ---------------
857logical :: dust_lag
858
859! CODE
860! ----
861dust_lag = .false.
862if (str%h_co2ice < tol .and. str%h_h2oice < tol .and. str%poreice_volfrac < tol) dust_lag = .true.
863
864END FUNCTION is_dust_lag
865!=======================================================================
866
867!=======================================================================
868SUBROUTINE subsurface_ice_layering(this,h_toplag,h2o_ice,co2_ice)
869!-----------------------------------------------------------------------
870! NAME
871!     subsurface_ice_layering
872!
873! DESCRIPTION
874!     Get data about possible subsurface ice in a layering.
875!
876! AUTHORS & DATE
877!     JB Clement, 2024
878!
879! NOTES
880!
881!-----------------------------------------------------------------------
882
883! DECLARATION
884! -----------
885implicit none
886
887! ARGUMENTS
888! ---------
889type(layering), intent(in)  :: this
890real,           intent(out) :: h2o_ice, co2_ice, h_toplag
891
892! LOCAL VARIABLES
893! ---------------
894type(stratum), pointer :: current
895
896! CODE
897! ----
898h_toplag = 0.
899h2o_ice = 0.
900co2_ice = 0.
901current => this%top
902! Is the considered stratum a dust lag?
903if (.not. is_dust_lag(current)) return
904do while (is_dust_lag(current))
905    h_toplag = h_toplag + thickness(current)
906    if (associated(current%down)) then
907        current => current%down
908    else
909        exit
910    endif
911enddo
912
913if (.not. associated(current%down)) then ! Bottom of the layering -> no ice below
914    h_toplag = 0.
915    return
916endif
917
918! Is the stratum below the dust lag made of ice?
919if (current%h_h2oice > 0. .and. current%h_h2oice > current%h_co2ice) then ! Yes, there is more H2O ice than CO2 ice
920    if (h_toplag < h_patchy_dust) then ! But the dust lag is too thin to considered ice as subsurface ice
921        h_toplag = 0.
922        h2o_ice = current%h_h2oice*rho_h2oice
923    endif
924else if (current%h_co2ice > 0. .and. current%h_co2ice > current%h_h2oice) then ! No, there is more CO2 ice than H2O ice
925    h_toplag = 0. ! Because it matters only for H2O ice
926    if (h_toplag < h_patchy_ice) co2_ice = current%h_co2ice*rho_co2ice ! But the dust lag is too thin to considered ice as subsurface ice
927endif
928
929END SUBROUTINE subsurface_ice_layering
930!=======================================================================
931
932!=======================================================================
933SUBROUTINE lift_dust(this,str,h2lift)
934!-----------------------------------------------------------------------
935! NAME
936!     lift_dust
937!
938! DESCRIPTION
939!     Lift dust in a stratum by wind erosion or other processes.
940!
941! AUTHORS & DATE
942!     JB Clement, 2024
943!
944! NOTES
945!
946!-----------------------------------------------------------------------
947
948! DECLARATION
949! -----------
950implicit none
951
952! ARGUMENTS
953! ---------
954type(layering),         intent(inout) :: this
955type(stratum), pointer, intent(inout) :: str
956real,                   intent(in)    :: h2lift
957
958! CODE
959! ----
960! Update of properties in the eroding dust lag
961str%top_elevation = str%top_elevation - h2lift*(1. + str%h_pore/str%h_dust)
962str%h_pore        = str%h_pore        - h2lift*str%h_pore/str%h_dust
963str%h_dust        = str%h_dust        - h2lift
964
965! Remove the eroding dust lag if there is no dust anymore
966if (str%h_dust < tol) call del_stratum(this,str)
967
968END SUBROUTINE lift_dust
969!=======================================================================
970
971!=======================================================================
972SUBROUTINE sublimate_ice(this,str,h2subl_co2ice,h2subl_h2oice,new_lag,zlag)
973!-----------------------------------------------------------------------
974! NAME
975!     sublimate_ice
976!
977! DESCRIPTION
978!     Handle ice sublimation in a stratum and create lag layer.
979!
980! AUTHORS & DATE
981!     JB Clement, 2024
982!
983! NOTES
984!
985!-----------------------------------------------------------------------
986
987! DECLARATION
988! -----------
989implicit none
990
991! ARGUMENTS
992! ---------
993type(layering),         intent(inout) :: this
994type(stratum), pointer, intent(inout) :: str
995logical,                intent(inout) :: new_lag
996real,                   intent(inout) :: zlag
997real,                   intent(in)    :: h2subl_co2ice, h2subl_h2oice
998
999! LOCAL VARIABLES
1000! ---------------
1001real                   :: h2subl, h_ice, h_pore, h_pore_new, h_tot
1002real                   :: hlag_dust, hlag_h2oice
1003type(stratum), pointer :: current
1004
1005! CODE
1006! ----
1007h_ice = str%h_co2ice + str%h_h2oice
1008h_pore = str%h_pore
1009h2subl = h2subl_co2ice + h2subl_h2oice
1010
1011! How much dust and H2O ice does ice sublimation involve to create the lag?
1012hlag_dust = str%h_dust*h2subl/h_ice
1013hlag_h2oice = 0.
1014if (h2subl_co2ice > 0. .and. h2subl_h2oice < tol) hlag_h2oice = str%h_h2oice*h2subl/h_ice
1015
1016! Update of properties in the sublimating stratum
1017str%top_elevation = str%top_elevation - h2subl*(1. + h_pore/h_ice) - hlag_dust - hlag_h2oice
1018str%h_co2ice      = str%h_co2ice      - h2subl_co2ice
1019str%h_h2oice      = str%h_h2oice      - h2subl_h2oice - hlag_h2oice
1020str%h_dust        = str%h_dust        - hlag_dust
1021str%h_pore        = str%h_pore        - h2subl*h_pore/h_ice
1022
1023! Correct the value of top_elevation for the upper strata
1024current => str%up
1025do while (associated(current))
1026    current%top_elevation = current%down%top_elevation + thickness(current)
1027    current => current%up
1028enddo
1029
1030! Remove the sublimating stratum if there is no ice anymore
1031if (str%h_co2ice < tol .and. str%h_h2oice < tol) call del_stratum(this,str)
1032
1033! Which porosity is considered?
1034if (hlag_dust >= hlag_h2oice) then
1035    h_pore_new = hlag_dust*dry_lag_porosity/(1. - dry_lag_porosity)
1036else
1037    h_pore_new = hlag_h2oice*wet_lag_porosity/(1. - wet_lag_porosity)
1038endif
1039h_tot = hlag_dust + hlag_h2oice + h_pore_new
1040
1041! New stratum above the current stratum as a lag layer
1042if (new_lag) then
1043    call insert_stratum(this,str,str%top_elevation + h_tot,0.,hlag_h2oice,hlag_dust,h_pore_new,0.)
1044    new_lag = .false.
1045else
1046    str%up%top_elevation = str%up%top_elevation + h_tot
1047    str%up%h_h2oice      = str%up%h_h2oice      + hlag_h2oice
1048    str%up%h_dust        = str%up%h_dust        + hlag_dust
1049    str%up%h_pore        = str%up%h_pore        + h_pore_new
1050endif
1051
1052zlag = zlag + h_tot
1053
1054END SUBROUTINE sublimate_ice
1055!=======================================================================
1056
1057!=======================================================================
1058SUBROUTINE make_layering(this,d_co2ice,d_h2oice,new_str,zshift_surf,new_lag,zlag,current)
1059!-----------------------------------------------------------------------
1060! NAME
1061!     make_layering
1062!
1063! DESCRIPTION
1064!     Main algorithm for layering evolution. Manages ice condensation/sublimation
1065!     and dust sedimentation/lifting. Handles multiple scenarios: building new
1066!     strata from ice/dust, retreating strata from sublimation/lifting, and mixed
1067!     scenarios with CO2 ice sublimation combined with H2O ice condensation.
1068!
1069! AUTHORS & DATE
1070!     JB Clement, 2024
1071!
1072! NOTES
1073!     Creates dust lag layers when ice sublimation occurs.
1074!-----------------------------------------------------------------------
1075
1076! DECLARATION
1077! -----------
1078implicit none
1079
1080! ARGUMENTS
1081! ---------
1082type(layering),         intent(inout) ::  this
1083type(stratum), pointer, intent(inout) ::  current
1084real,                   intent(inout) ::  d_co2ice, d_h2oice
1085logical,                intent(inout) ::  new_str, new_lag
1086real,                   intent(out)   ::  zshift_surf, zlag
1087
1088! LOCAL VARIABLES
1089! ---------------
1090real                   :: dh_co2ice, dh_h2oice, dh_dust, dh_dust_co2, dh_dust_h2o
1091real                   :: h_co2ice_old, h_h2oice_old, h_dust_old
1092real                   :: h2subl_co2ice, h2subl_h2oice, h2subl_co2ice_tot, h2subl_h2oice_tot
1093real                   :: h2lift, h2lift_tot, h_pore, h_tot, h_toplag, R_subl
1094logical                :: unexpected
1095type(stratum), pointer :: currentloc
1096
1097! CODE
1098! ----
1099dh_co2ice = d_co2ice/rho_co2ice
1100dh_h2oice = d_h2oice/rho_h2oice
1101dh_dust = 0.
1102if (dh_h2oice > 0.) then ! To put a dust sedimentation tendency only when ice is condensing
1103    if (impose_dust_ratio) then
1104        if (dh_co2ice > 0.) then
1105            dh_dust = dust2ice_ratio*(dh_h2oice + dh_co2ice)
1106        else
1107            dh_dust = dust2ice_ratio*dh_h2oice
1108        endif
1109    else
1110        dh_dust = d_dust/rho_dust
1111    endif
1112endif
1113zshift_surf = this%top%top_elevation
1114zlag = 0.
1115unexpected = .false.
1116
1117!~~~~~~~~~~
1118! NOTHING HAPPENS
1119if (abs(dh_co2ice) < tol .and. abs(dh_h2oice) < tol .and. abs(dh_dust) < tol) then
1120    ! So we do nothing
1121!~~~~~~~~~~
1122! BUILDING A STRATUM (ice condensation and/or dust desimentation)
1123else if (dh_co2ice >= 0. .and. dh_h2oice >= 0. .and. dh_dust >= 0.) then
1124    ! Which porosity is considered?
1125    if (dh_co2ice > dh_h2oice .and. dh_co2ice > dh_dust) then ! CO2 ice is dominant
1126        h_pore = dh_co2ice*co2ice_porosity/(1. - co2ice_porosity)
1127    else if (dh_h2oice > dh_co2ice .and. dh_h2oice > dh_dust) then ! H2O ice is dominant
1128        h_pore = dh_h2oice*h2oice_porosity/(1. - h2oice_porosity)
1129    else if (dh_dust > dh_co2ice .and. dh_dust > dh_h2oice) then ! Dust is dominant
1130        h_pore = dh_dust*regolith_porosity/(1. - regolith_porosity)
1131    else
1132        unexpected = .true.
1133    endif
1134    h_tot = dh_co2ice + dh_h2oice + dh_dust + h_pore
1135    ! New stratum at the top of the layering
1136    if (new_str) then
1137        call add_stratum(this,this%top%top_elevation + h_tot,dh_co2ice,dh_h2oice,dh_dust,h_pore,0.)
1138        new_str = .false.
1139    else
1140        this%top%top_elevation = this%top%top_elevation + h_tot
1141        this%top%h_co2ice      = this%top%h_co2ice      + dh_co2ice
1142        this%top%h_h2oice      = this%top%h_h2oice      + dh_h2oice
1143        this%top%h_dust        = this%top%h_dust        + dh_dust
1144        this%top%h_pore        = this%top%h_pore        + h_pore
1145    endif
1146!~~~~~~~~~~
1147 ! RETREATING A STRATUM (ice sublimation and/or dust lifting)
1148else if (dh_co2ice <= 0. .and. dh_h2oice <= 0. .and. dh_dust <= 0.) then
1149        h2subl_co2ice_tot = abs(dh_co2ice)
1150        h2subl_h2oice_tot = abs(dh_h2oice)
1151        h2lift_tot = abs(dh_dust)
1152        do while ((h2subl_co2ice_tot > 0. .or. h2subl_h2oice_tot > 0. .or. h2lift_tot > 0.) .and. associated(current))
1153            h_co2ice_old = current%h_co2ice
1154            h_h2oice_old = current%h_h2oice
1155
1156            ! How much is CO2 ice sublimation inhibited by the top dust lag?
1157            R_subl = 1.
1158            if (associated(current%up)) then ! If there is an upper stratum
1159                h_toplag = 0.
1160                currentloc => current%up
1161                do while (is_dust_lag(currentloc) .and. associated(currentloc%up))
1162                    h_toplag = h_toplag + thickness(currentloc)
1163                    currentloc => currentloc%up
1164                enddo
1165                if (currentloc%h_h2oice >= h_patchy_ice) then
1166                    R_subl = 0.
1167                else if (0. < currentloc%h_h2oice .and. currentloc%h_h2oice < h_patchy_ice) then
1168                    h_toplag = h_toplag + thickness(currentloc)
1169                    R_subl = fred_sublco2**(h_toplag/hmin_lag_co2)
1170                else
1171                    R_subl = fred_sublco2**(h_toplag/hmin_lag_co2)
1172                endif
1173            endif
1174           h2subl_co2ice_tot = h2subl_co2ice_tot*R_subl
1175
1176            ! Is there CO2 ice to sublimate?
1177            h2subl_co2ice = 0.
1178            if (h_co2ice_old > 0. .and. h2subl_co2ice_tot > 0.) then
1179                h2subl_co2ice = min(h2subl_co2ice_tot,h_co2ice_old)
1180                h2subl_co2ice_tot = h2subl_co2ice_tot - h2subl_co2ice
1181            endif
1182            ! Is there H2O ice to sublimate?
1183            h2subl_h2oice = 0.
1184            if (h_h2oice_old > 0. .and. h2subl_h2oice_tot > 0.) then
1185                h2subl_h2oice = min(h2subl_h2oice_tot,h_h2oice_old)
1186                h2subl_h2oice_tot = h2subl_h2oice_tot - h2subl_h2oice
1187            endif
1188            ! Ice sublimation
1189            if (h2subl_co2ice > 0. .or. h2subl_h2oice > 0.) call sublimate_ice(this,current,h2subl_co2ice,h2subl_h2oice,new_lag,zlag)
1190
1191            ! Is there dust to lift?
1192            h2lift = 0.
1193            if (is_dust_lag(current) .and. h2lift_tot > 0.) then
1194                h2lift = min(h2lift_tot,current%h_dust)
1195                h2lift_tot = h2lift_tot - h2lift
1196                ! Dust lifting
1197                if (h2lift > 0.) call lift_dust(this,current,h2lift)
1198            else if (associated(current%up)) then
1199                if (is_dust_lag(current%up) .and. h2lift_tot > 0.) then
1200                    h2lift = min(h2lift_tot,current%up%h_dust)
1201                    h2lift_tot = h2lift_tot - h2lift
1202                    ! Dust lifting
1203                    if (h2lift > 0.) call lift_dust(this,current%up,h2lift)
1204                endif
1205            endif
1206
1207            ! Still ice to be sublimated or dust to be lifted and no more ice in the current stratum so we move to the underlying stratum
1208            if ((h2subl_co2ice_tot > 0. .or. h2subl_h2oice_tot > 0. .or. h2lift_tot > 0.) .and. current%h_co2ice < tol .and. current%h_h2oice < tol .and. current%poreice_volfrac < tol) then
1209                current => current%down
1210                new_lag = .true.
1211            else
1212                exit
1213            endif
1214        enddo
1215        if (h2subl_co2ice_tot > 0.) dh_co2ice = 0. ! No CO2 ice available anymore so the tendency is set to 0
1216        if (h2subl_h2oice_tot > 0.) dh_h2oice = 0. ! No H2O ice available anymore so the tendency is set to 0
1217        if (h2lift_tot > 0.) dh_dust = 0. ! No dust available anymore so the tendency is set to 0
1218!~~~~~~~~~~
1219! CO2 ICE SUBLIMATION + H2O ICE CONDENSATION
1220else if (dh_co2ice <= 0. .and. dh_h2oice >= 0.) then
1221    if (dh_dust >= 0.) then
1222        dh_dust_co2 = 0.
1223        dh_dust_h2o = dh_dust
1224    else
1225        dh_dust_co2 = dh_dust
1226        dh_dust_h2o = 0.
1227    endif
1228    if (abs(dh_co2ice) > dh_h2oice) then ! CO2 ice sublimation is dominant
1229        ! CO2 ICE SUBLIMATION: retreating a stratum
1230        h2subl_co2ice_tot = abs(dh_co2ice)
1231        h2lift_tot = abs(dh_dust_co2)
1232        do while ((h2subl_co2ice_tot > 0. .or. h2lift_tot > 0.) .and. associated(current))
1233            h_co2ice_old = current%h_co2ice
1234
1235            ! How much is CO2 ice sublimation inhibited by the top dust lag?
1236            R_subl = 1.
1237            if (associated(current%up)) then ! If there is an upper stratum
1238                h_toplag = 0.
1239                currentloc => current%up
1240                do while (is_dust_lag(currentloc) .and. associated(currentloc%up))
1241                    h_toplag = h_toplag + thickness(currentloc)
1242                    currentloc => currentloc%up
1243                enddo
1244                if (currentloc%h_h2oice >= h_patchy_ice) then
1245                    R_subl = 0.
1246                else if (0. < currentloc%h_h2oice .and. currentloc%h_h2oice < h_patchy_ice) then
1247                    h_toplag = h_toplag + thickness(currentloc)
1248                    R_subl = fred_sublco2**(h_toplag/hmin_lag_co2)
1249                else
1250                    R_subl = fred_sublco2**(h_toplag/hmin_lag_co2)
1251                endif
1252            endif
1253           h2subl_co2ice_tot = h2subl_co2ice_tot*R_subl
1254
1255            ! Is there CO2 ice to sublimate?
1256            h2subl_co2ice = 0.
1257            if (h_co2ice_old > 0. .and. h2subl_co2ice_tot > 0.) then
1258                h2subl_co2ice = min(h2subl_co2ice_tot,h_co2ice_old)
1259                h2subl_co2ice_tot = h2subl_co2ice_tot - h2subl_co2ice
1260            endif
1261            ! Ice sublimation
1262            if (h2subl_co2ice > 0.) call sublimate_ice(this,current,h2subl_co2ice,0.,new_lag,zlag)
1263
1264            ! Is there dust to lift?
1265            h2lift = 0.
1266            if (is_dust_lag(current) .and. h2lift_tot > 0.) then
1267                h2lift = min(h2lift_tot,current%h_dust)
1268                h2lift_tot = h2lift_tot - h2lift
1269                ! Dust lifting
1270                if (h2lift > 0.) call lift_dust(this,current,h2lift)
1271            else if (associated(current%up)) then
1272                if (is_dust_lag(current%up) .and. h2lift_tot > 0.) then
1273                    h2lift = min(h2lift_tot,current%up%h_dust)
1274                    h2lift_tot = h2lift_tot - h2lift
1275                    ! Dust lifting
1276                    if (h2lift > 0.) call lift_dust(this,current%up,h2lift)
1277                endif
1278            endif
1279
1280            ! Still ice to be sublimated or dust to be lifted and no more ice in the current stratum so we move to the underlying stratum
1281            if ((h2subl_co2ice_tot > 0. .or. h2lift_tot > 0.) .and. current%h_co2ice < tol) then
1282                current => current%down
1283                new_lag = .true.
1284            else
1285                exit
1286            endif
1287        enddo
1288        if (h2subl_co2ice_tot > 0.) dh_co2ice = 0. ! No CO2 ice available anymore so the tendency is set to 0
1289        if (h2lift_tot > 0.) dh_dust = 0. ! No dust available anymore so the tendency is set to 0
1290
1291        ! H2O ICE CONDENSATION: building a stratum
1292        h_pore = dh_h2oice*h2oice_porosity/(1. - h2oice_porosity)
1293        h_tot = dh_h2oice + dh_dust_h2o + h_pore
1294        ! New stratum at the top of the layering
1295        if (new_str) then
1296            call add_stratum(this,this%top%top_elevation + h_tot,0.,dh_h2oice,dh_dust_h2o,h_pore,0.)
1297            new_str = .false.
1298        else
1299            this%top%top_elevation = this%top%top_elevation + h_tot
1300            this%top%h_h2oice      = this%top%h_h2oice      + dh_h2oice
1301            this%top%h_dust        = this%top%h_dust        + dh_dust_h2o
1302            this%top%h_pore        = this%top%h_pore        + h_pore
1303        endif
1304    else ! H2O ice condensation is dominant
1305        ! H2O ICE CONDENSATION: building a stratum
1306        h_pore = dh_h2oice*h2oice_porosity/(1. - h2oice_porosity)
1307        h_tot = dh_h2oice + dh_dust_h2o + h_pore
1308        ! New stratum at the top of the layering
1309        if (new_str) then
1310            call add_stratum(this,this%top%top_elevation + h_tot,0.,dh_h2oice,dh_dust_h2o,h_pore,0.)
1311            new_str = .false.
1312        else
1313            this%top%top_elevation = this%top%top_elevation + h_tot
1314            this%top%h_h2oice      = this%top%h_h2oice      + dh_h2oice
1315            this%top%h_dust        = this%top%h_dust        + dh_dust_h2o
1316            this%top%h_pore        = this%top%h_pore        + h_pore
1317        endif
1318
1319        ! CO2 ICE SUBLIMATION: retreating a stratum
1320        h2subl_co2ice_tot = abs(dh_co2ice)
1321        h2lift_tot = abs(dh_dust_co2)
1322        do while ((h2subl_co2ice_tot > 0. .or. h2lift_tot > 0.) .and. associated(current))
1323            h_co2ice_old = current%h_co2ice
1324
1325            ! How much is CO2 ice sublimation inhibited by the top dust lag?
1326            R_subl = 1.
1327            if (associated(current%up)) then ! If there is an upper stratum
1328                h_toplag = 0.
1329                currentloc => current%up
1330                do while (is_dust_lag(currentloc) .and. associated(currentloc%up))
1331                    h_toplag = h_toplag + thickness(currentloc)
1332                    currentloc => currentloc%up
1333                enddo
1334                if (currentloc%h_h2oice >= h_patchy_ice) then
1335                    R_subl = 0.
1336                else if (0. < currentloc%h_h2oice .and. currentloc%h_h2oice < h_patchy_ice) then
1337                    h_toplag = h_toplag + thickness(currentloc)
1338                    R_subl = fred_sublco2**(h_toplag/hmin_lag_co2)
1339                else
1340                    R_subl = fred_sublco2**(h_toplag/hmin_lag_co2)
1341                endif
1342            endif
1343           h2subl_co2ice_tot = h2subl_co2ice_tot*R_subl
1344
1345            ! Is there CO2 ice to sublimate?
1346            h2subl_co2ice = 0.
1347            if (h_co2ice_old > 0. .and. h2subl_co2ice_tot > 0.) then
1348                h2subl_co2ice = min(h2subl_co2ice_tot,h_co2ice_old)
1349                h2subl_co2ice_tot = h2subl_co2ice_tot - h2subl_co2ice
1350            endif
1351            ! Ice sublimation
1352            if (h2subl_co2ice > 0.) call sublimate_ice(this,current,h2subl_co2ice,0.,new_lag,zlag)
1353
1354            ! Is there dust to lift?
1355            h2lift = 0.
1356            if (is_dust_lag(current) .and. h2lift_tot > 0.) then
1357                h2lift = min(h2lift_tot,current%h_dust)
1358                h2lift_tot = h2lift_tot - h2lift
1359                ! Dust lifting
1360                if (h2lift > 0.) call lift_dust(this,current,h2lift)
1361            else if (associated(current%up)) then
1362                if (is_dust_lag(current%up) .and. h2lift_tot > 0.) then
1363                    h2lift = min(h2lift_tot,current%up%h_dust)
1364                    h2lift_tot = h2lift_tot - h2lift
1365                    ! Dust lifting
1366                    if (h2lift > 0.) call lift_dust(this,current%up,h2lift)
1367                endif
1368            endif
1369
1370            ! Still ice to be sublimated or dust to be lifted and no more ice in the current stratum so we move to the underlying stratum
1371            if ((h2subl_co2ice_tot > 0. .or. h2lift_tot > 0.) .and. current%h_co2ice < tol) then
1372                current => current%down
1373                new_lag = .true.
1374            else
1375                exit
1376            endif
1377        enddo
1378        if (h2subl_co2ice_tot > 0.) dh_co2ice = 0. ! No CO2 ice available anymore so the tendency is set to 0
1379        if (h2lift_tot > 0.) dh_dust = 0. ! No dust available anymore so the tendency is set to 0
1380    endif
1381!~~~~~~~~~~
1382! NOT EXPECTED SITUATION
1383else
1384    unexpected = .true.
1385endif
1386
1387if (unexpected) then
1388    write(*,'(a)') 'Error: situation for the layering construction not managed!'
1389    write(*,'(a,es12.3)') '    > dh_co2ice [m/y] = ', dh_co2ice
1390    write(*,'(a,es12.3)') '    > dh_h2oice [m/y] = ', dh_h2oice
1391    write(*,'(a,es12.3)') '    > dh_dust   [m/y] = ', dh_dust
1392    error stop
1393endif
1394
1395zshift_surf = this%top%top_elevation - zshift_surf
1396
1397END SUBROUTINE make_layering
1398!=======================================================================
1399
1400END MODULE layered_deposits
Note: See TracBrowser for help on using the repository browser.