Changeset 3130 for trunk/LMDZ.COMMON


Ignore:
Timestamp:
Nov 20, 2023, 1:25:31 PM (12 months ago)
Author:
jbclement
Message:

PEM:
The perennial co2 ice is now taken into account with co2 frost (qsurf) to compute the tendency and to make the update + Rework of how co2 frost is converted to perennial co2 ice at the end of the PEM run + Correction of the value of 'threshold_co2_frost2perennial' to correspond to 10 m + Perennial co2 ice is now handled outside 'paleoclimate' in "phyetat0_mod.F90" of the Mars PCM + Some cleanings.

/!\ Commit for the PEM management of co2 ice before a rework of ice management in the PEM!
JBC

Location:
trunk/LMDZ.COMMON/libf/evolution
Files:
11 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/evolution/adsorption_mod.F90

    r3082 r3130  
    156156#ifndef CPP_STD
    157157
    158 !0.1 Look at perenial ice
     158!0.1 Look at perennial ice
    159159  do ig = 1,ngrid
    160160    do islope = 1,nslope
     
    317317#ifndef CPP_STD
    318318
    319 !0.1 Look at perenial ice
     319!0.1 Look at perennial ice
    320320  do ig = 1,ngrid
    321321    do islope = 1,nslope
  • trunk/LMDZ.COMMON/libf/evolution/changelog.txt

    r3123 r3130  
    137137Adapting the PEM soil grid to the one of the PCM
    138138Minor corrections when reading/initializing soil temperature, subsurface water ice
     139
     140== 20/11/2023 == JBC
     141The perennial co2 ice is now taken into account with co2 frost (qsurf) to compute the tendency and to make the update + Rework of how co2 frost is converted to perennial co2 ice at the end of the PEM run + Correction of the value of 'threshold_co2_frost2perennial' to correspond to 10 m + Perennial co2 ice is now handled outside 'paleoclimate' in "phyetat0_mod.F90" of the Mars PCM + Some cleanings.
     142
     143/!\ Commit for the PEM management of co2 ice before a rework of ice management in the PEM!
  • trunk/LMDZ.COMMON/libf/evolution/compute_tendencies_slope_mod.F90

    r3076 r3130  
    2525
    2626!   OUTPUT
    27 real, dimension(ngrid,nslope), intent(out) :: tendencies_ice ! physical point field : difference between the minima = evolution of perenial ice
     27real, dimension(ngrid,nslope), intent(out) :: tendencies_ice ! physical point field : difference between the minima = evolution of perennial ice
    2828!=======================================================================
    2929
  • trunk/LMDZ.COMMON/libf/evolution/constants_marspem_mod.F90

    r3076 r3130  
    3737real, parameter :: Lco2 =  5.71e5 ! Pilorget and Forget 2016
    3838
    39 ! Conversion H2O/CO2 frost to perenial frost and vice versa
    40 real, parameter :: threshold_water_frost2perenial = 1000. !~ 1m
    41 real, parameter :: threshold_co2_frost2perenial = 3200.   !~ 2m
     39! Conversion H2O/CO2 frost to perennial frost and vice versa
     40real, parameter :: threshold_water_frost2perennial = 1000. !~ 1 m
     41real, parameter :: threshold_co2_frost2perennial = 16000.   !~ 10 m
    4242
    4343END MODULE constants_marspem_mod
  • trunk/LMDZ.COMMON/libf/evolution/criterion_pem_stop_mod.F90

    r3050 r3130  
    1   module criterion_pem_stop_mod
    2   implicit none
     1MODULE criterion_pem_stop_mod
    32
    4   contains
     3implicit none
    54
     5contains
    66
    77!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    88!!!
    9 !!! Purpose: Criterions to check if the PEM needs to call the GCM !!!
     9!!! Purpose: Criterions to check if the PEM needs to call the PCM
    1010!!! Author: RV & LL, 02/2023
    1111!!!
    1212!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    1313
    14 
    1514SUBROUTINE criterion_waterice_stop(cell_area,ini_surf,qsurf,STOPPING,ngrid,initial_h2o_ice)
    1615
    17   use time_evol_mod, only: water_ice_criterion
    18   use comslope_mod,  only: subslope_dist,nslope
     16use time_evol_mod, only: water_ice_criterion
     17use comslope_mod,  only: subslope_dist, nslope
    1918
    20       IMPLICIT NONE
     19implicit none
    2120
    2221!=======================================================================
     
    2827!   arguments:
    2928!   ----------
    30 
    3129!   INPUT
    32   INTEGER, intent(in) :: ngrid                         ! # of grid physical grid points
    33   REAL,    intent(in) :: cell_area(ngrid)              ! physical point field : Area of the cells
    34   REAL,    intent(in) :: qsurf(ngrid,nslope)           ! physical point field : Actual density of water ice
    35   REAL,    intent(in) :: ini_surf                      ! Initial surface of h2o ice that was sublimating
    36   REAL,    intent(in) :: initial_h2o_ice(ngrid,nslope) ! Grid point that initialy were covered by h2o_ice
    37 
     30integer,                       intent(in) :: ngrid           ! # of physical grid points
     31real, dimension(ngrid),        intent(in) :: cell_area       ! Area of the cells
     32real, dimension(ngrid,nslope), intent(in) :: qsurf           ! Actual density of water ice
     33real,                          intent(in) :: ini_surf        ! Initial surface of h2o ice that was sublimating
     34real, dimension(ngrid,nslope), intent(in) :: initial_h2o_ice ! Grid point that initialy were covered by h2o_ice
    3835!   OUTPUT
    39   LOGICAL, intent(out) :: STOPPING              ! Logical : is the criterion reached?
    40 
     36logical, intent(out) :: STOPPING ! Is the criterion reached?
    4137!   local:
    42 !   -----
    43   INTEGER :: i,islope   ! Loop
    44   REAL :: present_surf ! Initial/Actual surface of water ice
     38!   ------
     39integer :: i, islope    ! Loop
     40real    :: present_surf ! Initial/Actual surface of water ice
    4541
    4642!=======================================================================
     43! Initialisation to false
     44STOPPING = .false.
    4745
    48 !   initialisation to false
    49     STOPPING=.FALSE.
     46! Computation of the present surface of water ice sublimating
     47present_surf = 0.
     48do i = 1,ngrid
     49    do islope = 1,nslope
     50        !if (initial_h2o_ice(i,islope) > 0.5 .and. qsurf(i,islope) > 0.) present_surf = present_surf + cell_area(i)*subslope_dist(i,islope)
     51        if (initial_h2o_ice(i,islope) > 0.5) present_surf = present_surf + cell_area(i)*subslope_dist(i,islope)
     52    enddo
     53enddo
    5054
    51 !   computation of the present surface of water ice sublimating
    52   present_surf=0.
    53   do i=1,ngrid
    54     do islope=1, nslope
    55       if (initial_h2o_ice(i,islope).GT.0.5 .and. qsurf(i,islope).GT.0.) then
    56          present_surf=present_surf+cell_area(i)*subslope_dist(i,islope)
    57       endif
    58     enddo
    59   enddo
    60  
    61 !   check of the criterion
    62   if(present_surf.LT.ini_surf*(1-water_ice_criterion) .OR. &
    63      present_surf.GT.ini_surf*(1+water_ice_criterion)) then
    64     STOPPING=.TRUE.
    65     write(*,*) "Reason of stopping : The surface of water ice sublimating reach the threshold:"
    66     write(*,*) "Current surface of water ice sublimating=", present_surf
    67     write(*,*) "Initial surface of water ice sublimating=", ini_surf
    68     write(*,*) "Percentage of change accepted=", water_ice_criterion*100
    69     write(*,*) "present_surf<ini_surf*(1-water_ice_criterion)", (present_surf.LT.ini_surf*(1-water_ice_criterion))
    70   endif
     55! Check of the criterion
     56if (present_surf < ini_surf*(1. - water_ice_criterion) .or. present_surf > ini_surf*(1. + water_ice_criterion)) then
     57    STOPPING = .true.
     58    write(*,*) "Reason of stopping: the surface of water ice sublimating reach the threshold"
     59    write(*,*) "Current surface of water ice sublimating =", present_surf
     60    write(*,*) "Initial surface of water ice sublimating =", ini_surf
     61    write(*,*) "Percentage of change accepted =", water_ice_criterion*100
     62    write(*,*) "present_surf < ini_surf*(1. - water_ice_criterion)", (present_surf < ini_surf*(1. - water_ice_criterion))
     63endif
    7164
    72   if (ini_surf.LT. 1E-5 .and. ini_surf.GT. -1E-5) then
    73     STOPPING=.FALSE.
    74   endif
     65if (ini_surf < 1.e-5 .and. ini_surf > -1.e-5) STOPPING = .false.
     66
    7567END SUBROUTINE criterion_waterice_stop
    7668
    77 ! ------------------------------------------------------------------------------------------------
     69! ----------------------------------------------------------------------
    7870
    7971SUBROUTINE criterion_co2_stop(cell_area,ini_surf,qsurf,STOPPING_ice,STOPPING_ps,ngrid,initial_co2_ice,global_ave_press_GCM,global_ave_press_new,nslope)
    8072
    81   use time_evol_mod, only: co2_ice_criterion,ps_criterion
    82   use comslope_mod,  only: subslope_dist
     73use time_evol_mod, only: co2_ice_criterion, ps_criterion
     74use comslope_mod,  only: subslope_dist
    8375
    84       IMPLICIT NONE
     76implicit none
    8577
    8678!=======================================================================
    8779!
    88 !  Routine that checks if the criterion to stop the PEM is reached
     80!  Routine that checks if the co2 and pressure criteria to stop the PEM are reached
    8981!
    9082!=======================================================================
     
    9284!   arguments:
    9385!   ----------
    94 
    9586!   INPUT
    96   INTEGER, intent(in) :: ngrid,nslope                  ! # of grid physical grid points
    97   REAL,    intent(in) :: cell_area(ngrid)              ! physical point field : Area of the cells
    98   REAL,    intent(in) ::  qsurf(ngrid,nslope)          ! physical point field : Actual density of water ice
    99   REAL,    intent(in) :: ini_surf                      ! Initial surface of co2 ice that was sublimating
    100   REAL,    intent(in) :: initial_co2_ice(ngrid,nslope) ! Grid point that initialy were covered by co2_ice
    101   REAL,    intent(in) :: global_ave_press_GCM          ! Planet average pressure from the GCM start files
    102   REAL,    intent(in) :: global_ave_press_new          ! Planet average pressure from the PEM computations
    103 
     87integer,                       intent(in) :: ngrid, nslope        ! # of grid physical grid points
     88real, dimension(ngrid),        intent(in) :: cell_area            ! Area of the cells
     89real, dimension(ngrid,nslope), intent(in) :: qsurf                ! Actual density of water ice
     90real,                          intent(in) :: ini_surf             ! Initial surface of co2 ice that was sublimating
     91real, dimension(ngrid,nslope), intent(in) :: initial_co2_ice      ! Grid point that initialy were covered by co2_ice
     92real,                          intent(in) :: global_ave_press_GCM ! Planet average pressure from the PCM start files
     93real,                          intent(in) :: global_ave_press_new ! Planet average pressure from the PEM computations
    10494!   OUTPUT
    105   LOGICAL, intent(out) :: STOPPING_ice              ! Logical : is the criterion for ice reached?
    106   LOGICAL, intent(out) :: STOPPING_ps               ! Logical : is the criterion for pressure reached ?
     95logical, intent(out) :: STOPPING_ice ! Is the criterion for co2 ice reached?
     96logical, intent(out) :: STOPPING_ps  ! Is the criterion for pressure reached?
    10797!   local:
    108 !   -----
    109   INTEGER :: i,islope   ! Loop
    110   REAL :: present_surf ! Initial/Actual surface of water ice
     98!   ------
     99integer :: i, islope    ! Loop
     100real    :: present_surf ! Initial/Actual surface of water ice
    111101
    112102!=======================================================================
     103! Initialisation to false
     104STOPPING_ice = .false.
     105STOPPING_ps = .false.
    113106
    114 !   initialisation to false
    115     STOPPING_ice=.FALSE.
    116     STOPPING_ps =.FALSE.
    117 !   computation of the actual surface
    118   present_surf=0.
    119   do i=1,ngrid
    120    do islope=1,nslope
    121       if (initial_co2_ice(i,islope).GT.0.5 .and. qsurf(i,islope).GT.0.) then
    122          present_surf=present_surf+cell_area(i)*subslope_dist(i,islope)
    123       endif
    124    enddo
    125   enddo
    126  
    127 !   check of the criterion
    128   if(present_surf.LT.ini_surf*(1-co2_ice_criterion) .OR. &
    129      present_surf.GT.ini_surf*(1+co2_ice_criterion)) then
    130     STOPPING_ice=.TRUE.
    131     write(*,*) "Reason of stopping : The surface of co2 ice sublimating reach the threshold:"
    132     write(*,*) "Current surface of co2 ice sublimating=", present_surf
    133     write(*,*) "Initial surface of co2 ice sublimating=", ini_surf
    134     write(*,*) "Percentage of change accepted=", co2_ice_criterion*100
    135     write(*,*) "present_surf<ini_surf*(1-co2_ice_criterion)", (present_surf.LT.ini_surf*(1-co2_ice_criterion))
    136   endif
     107! Computation of the actual surface
     108present_surf = 0.
     109do i = 1,ngrid
     110    do islope = 1,nslope
     111        if (initial_co2_ice(i,islope) > 0.5 .and. qsurf(i,islope) > 0.) present_surf = present_surf + cell_area(i)*subslope_dist(i,islope)
     112    enddo
     113enddo
    137114
    138   if (ini_surf.LT. 1E-5 .and. ini_surf.GT. -1E-5) then
    139        STOPPING_ice=.FALSE.
    140   endif
     115! Check of the criterion
     116if (present_surf < ini_surf*(1. - co2_ice_criterion) .or. present_surf > ini_surf*(1. + co2_ice_criterion)) then
     117    STOPPING_ice = .true.
     118    write(*,*) "Reason of stopping: the surface of co2 ice sublimating reach the threshold"
     119    write(*,*) "Current surface of co2 ice sublimating =", present_surf
     120    write(*,*) "Initial surface of co2 ice sublimating =", ini_surf
     121    write(*,*) "Percentage of change accepted =", co2_ice_criterion*100.
     122    write(*,*) "present_surf < ini_surf*(1. - co2_ice_criterion)", (present_surf < ini_surf*(1. - co2_ice_criterion))
     123endif
    141124
    142   if(global_ave_press_new.LT.global_ave_press_GCM*(1-ps_criterion) .OR. &
    143      global_ave_press_new.GT.global_ave_press_GCM*(1+ps_criterion)) then
    144     STOPPING_ps=.TRUE.
    145     write(*,*) "Reason of stopping : The global pressure reach the threshold:"
    146     write(*,*) "Current global pressure=", global_ave_press_new
    147     write(*,*) "GCM global pressure=", global_ave_press_GCM
    148     write(*,*) "Percentage of change accepted=", ps_criterion*100
    149     write(*,*) "global_ave_press_new<global_ave_press_GCM*(ps_criterion)", (global_ave_press_new.LT.global_ave_press_GCM*(1-ps_criterion))
    150   endif
     125if (abs(ini_surf) < 1.e-5) STOPPING_ice = .false.
     126
     127if (global_ave_press_new < global_ave_press_GCM*(1. - ps_criterion) .or. global_ave_press_new > global_ave_press_GCM*(1. + ps_criterion)) then
     128    STOPPING_ps = .true.
     129    write(*,*) "Reason of stopping: the global pressure reach the threshold"
     130    write(*,*) "Current global pressure =", global_ave_press_new
     131    write(*,*) "PCM global pressure =", global_ave_press_GCM
     132    write(*,*) "Percentage of change accepted =", ps_criterion*100.
     133    write(*,*) "global_ave_press_new < global_ave_press_GCM*(1. - ps_criterion)", (global_ave_press_new < global_ave_press_GCM*(1. - ps_criterion))
     134endif
    151135
    152136END SUBROUTINE criterion_co2_stop
    153137
    154 
    155138END MODULE
  • trunk/LMDZ.COMMON/libf/evolution/evol_co2_ice_s_mod.F90

    r3039 r3130  
    11MODULE evol_co2_ice_s_mod
    22
    3 IMPLICIT NONE
     3implicit none
    44
    5 CONTAINS
     5!=======================================================================
     6contains
     7!=======================================================================
    68
    7 SUBROUTINE evol_co2_ice_s(qsurf,tendencies_co2_ice_phys,&
    8                              iim_input,jjm_input,ngrid,cell_area,nslope)
     9SUBROUTINE evol_co2_ice_s(qsurf,tendencies_co2_ice_phys,iim_input,jjm_input,ngrid,cell_area,nslope)
    910
    10   use time_evol_mod, only: dt_pem
     11use time_evol_mod, only: dt_pem
    1112
    12       IMPLICIT NONE
     13implicit none
    1314
    1415!=======================================================================
     
    1718!
    1819!=======================================================================
    19 
    2020!   arguments:
    2121!   ----------
    22 
    2322!   INPUT
    24 
    25   INTEGER, intent(in) :: iim_input,jjm_input, ngrid,nslope      ! # of grid points along longitude/latitude/ total
    26   REAL, intent(in) ::  cell_area(ngrid)
     23integer,                intent(in) :: iim_input, jjm_input, ngrid, nslope ! # of grid points along longitude/latitude/ total
     24REAL, dimension(ngrid), intent(in) :: cell_area
    2725
    2826!   OUTPUT
    29   REAL, INTENT(INOUT) ::  qsurf(ngrid,nslope)                   ! physical point field : Previous and actual density of water ice
    30   REAL, intent(inout) ::  tendencies_co2_ice_phys(ngrid,nslope) ! physical point field : Evolution of perenial ice over one year
     27real, dimension(ngrid,nslope), intent(inout) :: qsurf                   ! physical point field: Previous and actual density of water ice
     28real, dimension(ngrid,nslope), intent(inout) :: tendencies_co2_ice_phys ! physical point field: Evolution of perennial ice over one year
    3129
    3230!   local:
    3331!   ----
    34 
    35   INTEGER :: i,j,ig0,islope                                     ! loop variable
    36 
     32integer :: i, j, ig0, islope ! loop variable
     33!=======================================================================
    3734! Evolution of the CO2 ice for each physical point
    38   do i=1,ngrid
     35do i=1,ngrid
    3936    do islope=1,nslope
    40       qsurf(i,islope)=qsurf(i,islope)+tendencies_co2_ice_phys(i,islope)*dt_pem
    41       if (qsurf(i,islope).lt.0) then
    42         qsurf(i,islope)=0.
    43         tendencies_co2_ice_phys(i,islope)=0.
    44       endif
     37        qsurf(i,islope) = qsurf(i,islope) + tendencies_co2_ice_phys(i,islope)*dt_pem
     38        if (qsurf(i,islope) < 0) then
     39            qsurf(i,islope) = 0.
     40            tendencies_co2_ice_phys(i,islope) = 0.
     41        endif
    4542    enddo
    46   enddo
     43enddo
    4744
    4845END SUBROUTINE evol_co2_ice_s
  • trunk/LMDZ.COMMON/libf/evolution/evol_h2o_ice_s_mod.F90

    r3082 r3130  
    11MODULE evol_h2o_ice_s_mod
    22
    3 IMPLICIT NONE
     3implicit none
    44
    5 CONTAINS
     5!=======================================================================
     6contains
     7!=======================================================================
    68
    79SUBROUTINE evol_h2o_ice_s(ngrid,nslope,cell_area,delta_h2o_adsorbded,delta_h2o_icetablesublim,qsurf,tendencies_h2o_ice_phys,STOPPING)
    810
    9   use time_evol_mod,          only: dt_pem
    10   use comslope_mod,           only: subslope_dist, def_slope_mean
    11   use criterion_pem_stop_mod, only: criterion_waterice_stop
     11use time_evol_mod,          only: dt_pem
     12use comslope_mod,           only: subslope_dist, def_slope_mean
     13use criterion_pem_stop_mod, only: criterion_waterice_stop
     14
    1215#ifndef CPP_STD
    1316    use comcstfi_h,   only: pi
     
    1619#endif
    1720
    18   IMPLICIT NONE
     21implicit none
    1922
    2023!=======================================================================
     
    2326!
    2427!=======================================================================
    25 
    2628!   arguments:
    2729!   ----------
    28 
    2930!   INPUT
    30 
    31   INTEGER, intent(in) :: ngrid                                  ! # of grid points along longitude/latitude grid;
    32   INTEGER, intent(in) :: nslope                                 ! # of subslope
    33   REAL, intent(in) ::  cell_area(ngrid)                         ! Area of each mesh grid (m^2)
    34   REAL, intent(in) :: delta_h2o_adsorbded(ngrid)                ! Mass of H2O adsorbded/desorbded in the soil (kg/m^2)
    35   REAL, intent(in) :: delta_h2o_icetablesublim(ngrid)                ! Mass of H2O that have condensed/sublimated at the ice table (kg/m^2)
     31integer,                intent(in) :: ngrid                    ! # of grid points along longitude/latitude grid;
     32integer,                intent(in) :: nslope                   ! # of subslope
     33real, dimension(ngrid), intent(in) :: cell_area                ! Area of each mesh grid (m^2)
     34real, dimension(ngrid), intent(in) :: delta_h2o_adsorbded      ! Mass of H2O adsorbded/desorbded in the soil (kg/m^2)
     35real, dimension(ngrid), intent(in) :: delta_h2o_icetablesublim ! Mass of H2O that have condensed/sublimated at the ice table (kg/m^2)
    3636
    3737!   OUTPUT
    38   REAL, INTENT(INOUT) ::  qsurf(ngrid,nslope)                   ! physical point field : Previous and actual density of water ice (kg/m^2)
    39   REAL, intent(inout) ::  tendencies_h2o_ice_phys(ngrid,nslope) ! physical point field : Evolution of perenial ice over one year (kg/m^2/year)
    40   LOGICAL, INTENT(INOUT) :: STOPPING                            ! Stopping criterion
     38real, dimension(ngrid,nslope), intent(inout) :: qsurf                   ! physical point field: Previous and actual density of water ice (kg/m^2)
     39real, dimension(ngrid,nslope), intent(inout) :: tendencies_h2o_ice_phys ! physical point field: Evolution of perennial ice over one year (kg/m^2/year)
     40logical,                       intent(inout) :: STOPPING                ! Stopping criterion
    4141
    4242!   local:
    43 !   ----
    44 
    45   INTEGER :: i,j,islope                                         ! loop variable
    46   REAL :: pos_tend, neg_tend, real_coefficient,negative_part    ! Variable to conserve water
    47   REAL ::  new_tendencies(ngrid,nslope)                         ! Tendencies computed in order to conserve water ice on the surface, only exchange between surface are done
    48  
     43!   ------
     44integer :: i,j,islope                                          ! loop variable
     45real    :: pos_tend, neg_tend, real_coefficient, negative_part ! Variable to conserve water
     46real    ::  new_tendencies(ngrid,nslope)                       ! Tendencies computed in order to conserve water ice on the surface, only exchange between surface are done
    4947!=======================================================================
    5048
     
    5351  pos_tend=0.
    5452  neg_tend=0.
    55 if (ngrid.NE.1) then ! to make sure we are not in 1D 
     53if (ngrid.NE.1) then ! to make sure we are not in 1D
    5654  ! We compute the amount of water accumulating and sublimating
    5755  do i=1,ngrid
     
    7775  enddo
    7876  ! We adapt the tendencies to conserve water and do only exchange between grid points
    79    if(neg_tend.GT.pos_tend .and. pos_tend.GT.0) then ! We are sublimating more in the planet than condensing 
     77   if(neg_tend.GT.pos_tend .and. pos_tend.GT.0) then ! We are sublimating more in the planet than condensing
    8078     do i=1,ngrid
    8179       do islope=1,nslope
     
    9795       enddo
    9896     enddo
    99    elseif(pos_tend.EQ.0 .OR. neg_tend.EQ.0) then 
     97   elseif(pos_tend.EQ.0 .OR. neg_tend.EQ.0) then
    10098    write(*,*) "Reason of stopping : There is either no water ice sublimating or no water ice increasing !!"
    10199    write(*,*) "Tendencies on ice sublimating=", neg_tend
     
    123121    enddo
    124122  enddo
    125  
    126  
     123
     124
    127125  if(pos_tend.eq.0) then
    128126   real_coefficient = 0.
    129   else 
    130    real_coefficient = negative_part/pos_tend ! We compute a coefficient by which we should remove the ice that has been added 
    131                                              ! to places even if this ice was contributing to an unphysical negative amount 
     127  else
     128   real_coefficient = negative_part/pos_tend ! We compute a coefficient by which we should remove the ice that has been added
     129                                             ! to places even if this ice was contributing to an unphysical negative amount
    132130                                             ! of ice at other places
    133131  endif
  • trunk/LMDZ.COMMON/libf/evolution/pem.F90

    r3129 r3130  
    4242use criterion_pem_stop_mod,       only: criterion_waterice_stop, criterion_co2_stop
    4343use constants_marspem_mod,        only: alpha_clap_co2, beta_clap_co2, alpha_clap_h2o, beta_clap_h2o, m_co2, &
    44                                         m_noco2, threshold_water_frost2perenial, threshold_co2_frost2perenial
     44                                        m_noco2, threshold_water_frost2perennial, threshold_co2_frost2perennial
    4545use evol_co2_ice_s_mod,           only: evol_co2_ice_s
    4646use evol_h2o_ice_s_mod,           only: evol_h2o_ice_s
     
    7777                                  albedodat, zmea, zstd, zsig, zgam, zthe,     &
    7878                                  hmons, summit, base,albedo_h2o_frost,        &
    79                                   frost_albedo_threshold, emissiv, watercaptag, perenial_co2ice, &
     79                                  frost_albedo_threshold, emissiv, watercaptag, perennial_co2ice, &
    8080                                  emisice, albedice
    8181    use dimradmars_mod,     only: totcloudfrac, albedo
     
    8484    use mod_phys_lmdz_para, only: is_parallel, is_sequential, is_mpi_root, is_omp_root, is_master
    8585    use planete_h,          only: aphelie, periheli, year_day, peri_day, obliquit, iniorbit
    86     use paleoclimate_mod,   only: albedo_perenialco2
     86    use paleoclimate_mod,   only: albedo_perennialco2
    8787    use comcstfi_h,         only: pi, rad, g, cpp, mugaz, r
    8888#else
     
    161161! Variables for h2o_ice evolution
    162162real                                :: ini_surf_h2o         ! Initial surface of sublimating h2o ice
    163 real                                :: ini_surf_co2         ! Initial surface of sublimating co2 ice
    164163real                                :: global_ave_press_GCM ! constant: global average pressure retrieved in the GCM [Pa]
    165164real                                :: global_ave_press_old ! constant: Global average pressure of initial/previous time step
     
    171170logical                             :: STOPPING_water       ! Logical: is the criterion (% of change in the surface of sublimating water ice) reached?
    172171logical                             :: STOPPING_1_water     ! Logical: is there still water ice to sublimate?
    173 logical                             :: STOPPING_co2         ! Logical: is the criterion (% of change in the surface of sublimating water ice) reached?
    174172logical                             :: STOPPING_pressure    ! Logical: is the criterion (% of change in the surface pressure) reached?
    175173integer                             :: criterion_stop       ! which criterion is reached ? 1= h2o ice surf, 2 = co2 ice surf, 3 = ps, 4 = orb param
    176174real, save                          :: A, B, mmean          ! Molar mass: intermediate A, B for computations of the  mean molar mass of the layer [mol/kg]
    177 real, dimension(:,:),   allocatable :: vmr_co2_gcm          ! Physics x Times  co2 volume mixing ratio retrieve from the PCM [m^3/m^3]
    178 real, dimension(:,:),   allocatable :: vmr_co2_pem_phys     ! Physics x Times  co2 volume mixing ratio used in the PEM
    179 real, dimension(:,:),   allocatable :: q_co2_PEM_phys       ! Physics x Times co2 mass mixing ratio in the first layer computed in the PEM, first value comes from PCM [kg/kg]
    180175real, dimension(:,:),   allocatable :: q_h2o_PEM_phys       ! Physics x Times: h2o mass mixing ratio computed in the PEM, first value comes from PCM [kg/kg]
    181176integer                             :: timelen              ! # time samples
     
    183178real, dimension(:,:),   allocatable :: p                    ! Physics x Atmosphere: pressure to recompute and write in restart (ngrid,llmp1)
    184179real                                :: extra_mass           ! Intermediate variables Extra mass of a tracer if it is greater than 1
     180
     181! Variables for co2_ice evolution
     182real                              :: ini_surf_co2         ! Initial surface of sublimating co2 ice
     183logical                           :: STOPPING_co2         ! Logical: is the criterion (% of change in the surface of sublimating co2 ice) reached?
     184real, dimension(:,:), allocatable :: vmr_co2_gcm          ! Physics x Times  co2 volume mixing ratio retrieve from the PCM [m^3/m^3]
     185real, dimension(:,:), allocatable :: vmr_co2_pem_phys     ! Physics x Times  co2 volume mixing ratio used in the PEM
     186real, dimension(:,:), allocatable :: q_co2_PEM_phys       ! Physics x Times co2 mass mixing ratio in the first layer computed in the PEM, first value comes from PCM [kg/kg]
     187real, dimension(:,:), allocatable :: co2frost_ini         ! Initial amount of co2 frost (at the start of the PEM run)
     188real, dimension(:,:), allocatable :: perennial_co2ice_ini ! Initial amoun of perennial co2 ice (at the start of the PEM run)
     189
     190
    185191
    186192! Variables for slopes
     
    193199real, dimension(:,:),   allocatable :: initial_h2o_ice        ! physical point field: Logical array indicating if there is water ice at initial state
    194200real, dimension(:,:),   allocatable :: initial_co2_ice        ! physical point field: Logical array indicating if there is co2 ice at initial state
    195 real, dimension(:,:),   allocatable :: tendencies_co2_ice     ! physical point x slope field: Tendency of evolution of perenial co2 ice over a year
    196 real, dimension(:,:),   allocatable :: tendencies_co2_ice_ini ! physical point x slope field x nslope: Tendency of evolution of perenial co2 ice over a year in the PCM
    197 real, dimension(:,:),   allocatable :: tendencies_h2o_ice     ! physical point x slope  field: Tendency of evolution of perenial h2o ice
     201real, dimension(:,:),   allocatable :: tendencies_co2_ice     ! physical point x slope field: Tendency of evolution of perennial co2 ice over a year
     202real, dimension(:,:),   allocatable :: tendencies_co2_ice_ini ! physical point x slope field x nslope: Tendency of evolution of perennial co2 ice over a year in the PCM
     203real, dimension(:,:),   allocatable :: tendencies_h2o_ice     ! physical point x slope  field: Tendency of evolution of perennial h2o ice
    198204real, dimension(:,:),   allocatable :: flag_co2flow           ! (ngrid,nslope): Flag where there is a CO2 glacier flow
    199205real, dimension(:),     allocatable :: flag_co2flow_mesh      ! (ngrid)       : Flag where there is a CO2 glacier flow
     
    383389    call phyetat0(FILE_NAME,0,0,nsoilmx,ngrid,nlayer,nq,nqsoil,day_ini,time_phys,tsurf, &
    384390                  tsoil,albedo,emis,q2,qsurf,qsoil,tauscaling,totcloudfrac,wstar,       &
    385                   watercap,perenial_co2ice,def_slope,def_slope_mean,subslope_dist)
     391                  watercap,perennial_co2ice,def_slope,def_slope_mean,subslope_dist)
    386392
    387393    ! Remove unphysical values of surface tracer
     
    588594        if (tendencies_h2o_ice(i,islope) < 0) then
    589595            initial_h2o_ice(i,islope) = 1.
    590             ini_surf_h2o=ini_surf_h2o + cell_area(i)*subslope_dist(i,islope)
     596            ini_surf_h2o = ini_surf_h2o + cell_area(i)*subslope_dist(i,islope)
    591597        else
    592598            initial_h2o_ice(i,islope) = 0.
     
    595601enddo
    596602
    597 write(*,*) "Total initial surface of co2ice sublimating (slope)=", ini_surf_co2
    598 write(*,*) "Total initial surface of h2o ice sublimating (slope)=", ini_surf_h2o
     603write(*,*) "Total initial surface of co2 ice sublimating (slope) =", ini_surf_co2
     604write(*,*) "Total initial surface of h2o ice sublimating (slope) =", ini_surf_h2o
    599605write(*,*) "Total surface of the planet=", Total_surface
    600606allocate(zplev_gcm(ngrid,nlayer + 1))
     
    625631delta_h2o_icetablesublim(:) = 0.
    626632
     633! We save the initial values for the co2 frost and perennial ice
     634allocate(co2frost_ini(ngrid,nslope),perennial_co2ice_ini(ngrid,nslope))
     635co2frost_ini = qsurf(:,igcm_co2,:)
     636perennial_co2ice_ini = perennial_co2ice
     637
    627638do ig = 1,ngrid
    628639    do islope = 1,nslope
    629640        qsurf(ig,igcm_h2o_ice,islope) = qsurf(ig,igcm_h2o_ice,islope) + watercap(ig,islope) + water_reservoir(ig)*cos(pi*def_slope_mean(islope)/180.)
     641        qsurf(ig,igcm_co2,islope) = qsurf(ig,igcm_co2,islope) + perennial_co2ice(ig,islope)
    630642    enddo
    631643enddo
     
    10001012!               2nd case: we have sublimate ice: then let's put qsurf = 0. and add the difference in watercap
    10011013                watercap(ig,islope) = watercap(ig,islope) + qsurf(ig,igcm_h2o_ice,islope) - (watercap(ig,islope) + water_reservoir(ig)*cos(pi*def_slope_mean(islope)/180.))
    1002                 qsurf(ig,igcm_h2o_ice,islope)=0.
     1014                qsurf(ig,igcm_h2o_ice,islope) = 0.
    10031015            endif
    1004             watercap_sum = watercap_sum+watercap(ig,islope)*subslope_dist(ig,islope)/cos(pi*def_slope_mean(islope)/180.)
     1016            watercap_sum = watercap_sum + watercap(ig,islope)*subslope_dist(ig,islope)/cos(pi*def_slope_mean(islope)/180.)
    10051017            watercap(ig,islope) = 0.
    10061018        enddo
     
    10151027    enddo
    10161028    if (.not. watercaptag(ig)) then ! let's check if we have an 'infinite' source of water that has been forming.
    1017         if (water_sum > threshold_water_frost2perenial) then ! the overall mesh can be considered as an infite source of water. No need to change the albedo: done in II.d.1
     1029        if (water_sum > threshold_water_frost2perennial) then ! the overall mesh can be considered as an infite source of water. No need to change the albedo: done in II.d.1
    10181030            watercaptag(ig) = .true.
    1019             water_reservoir(ig) = water_reservoir(ig) + threshold_water_frost2perenial/2. ! half of the excess ices goes to the reservoir, we let the rest to be frost
     1031            water_reservoir(ig) = water_reservoir(ig) + threshold_water_frost2perennial/2. ! half of the excess ices goes to the reservoir, we let the rest to be frost
    10201032            do islope = 1,nslope
    1021                 qsurf(ig,igcm_h2o_ice,islope) = qsurf(ig,igcm_h2o_ice,islope) - threshold_water_frost2perenial/2.*cos(pi*def_slope_mean(islope)/180.)
     1033                qsurf(ig,igcm_h2o_ice,islope) = qsurf(ig,igcm_h2o_ice,islope) - threshold_water_frost2perennial/2.*cos(pi*def_slope_mean(islope)/180.)
    10221034            enddo
    10231035        endif
    10241036    else ! let's check that the infinite source of water disapear
    1025         if ((water_sum + water_reservoir(ig)) < threshold_water_frost2perenial) then
     1037        if ((water_sum + water_reservoir(ig)) < threshold_water_frost2perennial) then
    10261038            watercaptag(ig) = .false.
    10271039            do islope = 1,nslope
     
    10361048do ig = 1,ngrid
    10371049    do islope = 1,nslope
    1038         if (qsurf(ig,igcm_co2,islope) > threshold_co2_frost2perenial) then
    1039             perenial_co2ice(ig,islope) = 0.5*qsurf(ig,igcm_co2,islope)
    1040             qsurf(ig,igcm_co2,islope)  = 0.5*qsurf(ig,igcm_co2,islope)
    1041             albedo(ig,1,islope) = albedo_perenialco2
    1042             albedo(ig,2,islope) = albedo_perenialco2
     1050        if (qsurf(ig,igcm_co2,islope) == threshold_co2_frost2perennial) then
     1051        ! If co2 ice is equal to the threshold, then everything is transformed into perennial ice
     1052            perennial_co2ice(ig,islope) = threshold_co2_frost2perennial
     1053            qsurf(ig,igcm_co2,islope) = 0.
     1054        else if (qsurf(ig,igcm_co2,islope) > threshold_co2_frost2perennial) then
     1055        ! If co2 ice is superior to the threshold, then co2 frost is equal to the threshold (max possible value)
     1056        ! and the leftover is transformed into perennial ice
     1057            perennial_co2ice(ig,islope) = qsurf(ig,igcm_co2,islope) - threshold_co2_frost2perennial
     1058            qsurf(ig,igcm_co2,islope) = threshold_co2_frost2perennial
     1059        else
     1060        ! If co2 ice is inferior to the threshold, then we compare with the initial state
     1061            if (qsurf(ig,igcm_co2,islope) > perennial_co2ice_ini(ig,islope)) then
     1062            ! If co2 ice higher than the initial perennial ice, then the change is affected only to the frost
     1063                perennial_co2ice(ig,islope) = perennial_co2ice_ini(ig,islope)
     1064                qsurf(ig,igcm_co2,islope) = qsurf(ig,igcm_co2,islope) - perennial_co2ice_ini(ig,islope)
     1065            else
     1066            ! If co2 ice is lower than the initial perennial ice, then there is no frost anymore
     1067                perennial_co2ice(ig,islope) = qsurf(ig,igcm_co2,islope)
     1068                qsurf(ig,igcm_co2,islope) = 0.
     1069            endif
    10431070        endif
    10441071    enddo
     
    11241151                  nlayer,nq,ptimestep,pday,0.,cell_area,albedodat,      &
    11251152                  inertiedat,def_slope,subslope_dist)
    1126 
    11271153    call physdem1("restartfi_evol.nc",nsoilmx,ngrid,nlayer,nq,nqsoil, &
    11281154                  ptimestep,ztime_fin,tsurf,tsoil,inertiesoil,        &
    11291155                  albedo,emis,q2,qsurf,qsoil,tauscaling,totcloudfrac, &
    1130                   wstar,watercap,perenial_co2ice)
     1156                  wstar,watercap,perennial_co2ice)
    11311157#else
    11321158    call physdem0("restartfi_evol.nc",longitude,latitude,nsoilmx,ngrid, &
    11331159                  nlayer,nq,ptimestep,pday,time_phys,cell_area,         &
    11341160                  albedo_bareground,inertiedat,zmea,zstd,zsig,zgam,zthe)
    1135 
    11361161    call physdem1("restartfi_evol.nc",nsoilmx,ngrid,nlayer,nq,nqsoil,  &
    11371162                  ptimestep,ztime_fin,tsurf,tsoil,emis,q2,qsurf,qsoil, &
     
    11621187deallocate(tsoil_phys_PEM_timeseries,watersoil_density_PEM_timeseries,watersoil_density_PEM_ave)
    11631188deallocate(delta_co2_adsorbded,delta_h2o_adsorbded,vmr_co2_pem_phys,delta_h2o_icetablesublim,porefillingice_thickness_prev_iter)
     1189deallocate(co2frost_ini,perennial_co2ice_ini)
    11641190!----------------------------- END OUTPUT ------------------------------
    11651191
  • trunk/LMDZ.COMMON/libf/evolution/read_data_PCM_mod.F90

    r3123 r3130  
    6666real, dimension(iim_input + 1,jjm_input + 1,nslope,timelen)         :: h2o_ice_s_dyn             ! h2o ice per slope of the concatenated file [kg/m^2]
    6767real, dimension(iim_input + 1,jjm_input + 1,nslope,timelen)         :: watercap
     68real, dimension(iim_input + 1,jjm_input + 1,nslope,timelen)         :: perennial_co2ice
    6869real, dimension(iim_input + 1,jjm_input + 1,timelen)                :: vmr_co2_gcm               ! CO2 volume mixing ratio in the first layer [mol/m^3]
    6970real, dimension(iim_input + 1,jjm_input + 1,timelen)                :: ps_GCM                    ! Surface Pressure [Pa]
     
    106107    call get_var3("watercap",watercap(:,:,1,:))
    107108    write(*,*) "Data for watercap downloaded!"
     109
     110    call get_var3("perennial_co2ice",perennial_co2ice(:,:,1,:))
     111    write(*,*) "Data for perennial_co2ice downloaded!"
    108112#endif
    109113
     
    142146    enddo
    143147    write(*,*) "Data for watercap downloaded!"
     148
     149    do islope = 1,nslope
     150        write(num,'(i2.2)') islope
     151        call get_var3("perennial_co2ice_slope"//num,perennial_co2ice(:,:,islope,:))
     152    enddo
     153    write(*,*) "Data for perennial_co2ice downloaded!"
    144154#endif
    145155
     
    179189write(*,*) "Computing the min of co2_ice..."
    180190where (co2_ice_slope_dyn < 0.) co2_ice_slope_dyn = 0.
    181 min_co2_ice_dyn(:,:,:) = minval(co2_ice_slope_dyn,4)
     191min_co2_ice_dyn(:,:,:) = minval(co2_ice_slope_dyn + perennial_co2ice,4)
    182192
    183193! Compute averages over the year for each point
     
    204214            endif
    205215            if (q_h2o_dyn(i,j,t) < 0) then
    206                 q_h2o_dyn(i,j,t) = 1.e-30
     216                q_h2o_dyn(i,j,t) = 1.e-10
    207217            else if (q_h2o_dyn(i,j,t) > 1) then
    208218                q_h2o_dyn(i,j,t) = 1.
     
    282292!=======================================================================
    283293
    284 SUBROUTINE get_var1(filename,v)
    285 
    286 implicit none
    287 
    288 character(len = *), intent(in)  :: filename
     294SUBROUTINE get_var1(var,v)
     295
     296implicit none
     297
     298character(len = *), intent(in)  :: var
    289299real, dimension(:), intent(out) :: v
    290300
    291 call error_msg(NF90_INQ_VARID(fID,filename,vID),"inq",filename)
    292 call error_msg(NF90_GET_VAR(fID,vID,v),"get",filename)
     301call error_msg(NF90_INQ_VARID(fID,var,vID),"inq",var)
     302call error_msg(NF90_GET_VAR(fID,vID,v),"get",var)
    293303
    294304END SUBROUTINE get_var1
     
    296306!=======================================================================
    297307
    298 SUBROUTINE get_var3(filename,v) ! on U grid
    299 
    300 implicit none
    301 
    302 character(len = *),     intent(in)  :: filename
     308SUBROUTINE get_var3(var,v) ! on U grid
     309
     310implicit none
     311
     312character(len = *),     intent(in)  :: var
    303313real, dimension(:,:,:), intent(out) :: v
    304314
    305 call error_msg(NF90_INQ_VARID(fID,filename,vID),"inq",filename)
    306 call error_msg(NF90_GET_VAR(fID,vID,v),"get",filename)
     315call error_msg(NF90_INQ_VARID(fID,var,vID),"inq",var)
     316call error_msg(NF90_GET_VAR(fID,vID,v),"get",var)
    307317
    308318END SUBROUTINE get_var3
     
    310320!=======================================================================
    311321
    312 SUBROUTINE get_var4(filename,v)
    313 
    314 implicit none
    315 
    316 character(len = *),       intent(in)  :: filename
     322SUBROUTINE get_var4(var,v)
     323
     324implicit none
     325
     326character(len = *),       intent(in)  :: var
    317327real, dimension(:,:,:,:), intent(out) :: v
    318328
    319 call error_msg(NF90_INQ_VARID(fID,filename,vID),"inq",filename)
    320 call error_msg(NF90_GET_VAR(fID,vID,v),"get",filename)
     329call error_msg(NF90_INQ_VARID(fID,var,vID),"inq",var)
     330call error_msg(NF90_GET_VAR(fID,vID,v),"get",var)
    321331
    322332END SUBROUTINE get_var4
  • trunk/LMDZ.COMMON/libf/evolution/recomp_tend_co2_slope_mod.F90

    r3076 r3130  
    2929real,                           intent(in) :: global_ave_press_GCM        ! global averaged pressure at previous timestep
    3030real,                           intent(in) :: global_ave_press_new        ! global averaged pressure at current timestep
    31 real, dimension(ngrid,nslope),  intent(in) :: tendencies_co2_ice_phys_ini ! physical point field : Evolution of perenial ice over one year
     31real, dimension(ngrid,nslope),  intent(in) :: tendencies_co2_ice_phys_ini ! physical point field : Evolution of perennial ice over one year
    3232real, dimension(ngrid,nslope),  intent(in) :: co2ice_slope                ! CO2 ice per mesh and sub-grid slope(kg/m^2)
    3333real, dimension(ngrid,nslope),  intent(in) :: emissivity_slope            ! Emissivity per mesh and sub-grid slope(1)
    3434!   OUTPUT
    35 real, intent(inout) ::  tendencies_co2_ice_phys(ngrid,nslope) ! physical point field : Evolution of perenial ice over one year
     35real, intent(inout) ::  tendencies_co2_ice_phys(ngrid,nslope) ! physical point field : Evolution of perennial ice over one year
    3636
    3737!   local:
  • trunk/LMDZ.COMMON/libf/evolution/soil_thermalproperties_mod.F90

    r2985 r3130  
    147147    do islope=1,nslope
    148148     if (ice_depth(ig,islope).gt.-1e-6) then
    149 ! 3.0 Case where it is perenial ice
     149! 3.0 Case where it is perennial ice
    150150      if (ice_depth(ig,islope).lt. 1e-10) then
    151151       call ice_thermal_properties(.true.,1.,0.,ice_inertia)
Note: See TracChangeset for help on using the changeset viewer.