Ignore:
Timestamp:
Sep 9, 2022, 4:02:51 PM (2 years ago)
Author:
llange
Message:

MARS PEM:

  • Add a PEMETAT0 that read "startfi_pem.nc"
  • Add the soil in the model: soil temperature, thermal properties, ice table
  • Add a routine that compute CO2 + H2O adsorption
  • Minor corrections in PEM.F90

LL

File:
1 edited

Legend:

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

    r2779 r2794  
    66
    77  USE temps_mod_evol, ONLY: dt_pem
    8   use comslope_mod,  ONLY: subslope_dist
     8          use comslope_mod, ONLY: subslope_dist
    99
    1010      IMPLICIT NONE
    1111
    1212!=======================================================================
    13 
    14 !  Routine that compute the evolution of the water ice.
    15 
    16 !  We suppose that the water exchange uniquely form one point to another
    17 !  (water ice disappear from a sublimating point and increase at another
    18 !  accumulation point). Therfor the total positive and negative tendencies
    19 !  must be equal to conserve the total amount of water
    20 
     13!
     14!  Routine that compute the evolution of the water ice
     15!
    2116!=======================================================================
    2217
     
    2621!   INPUT
    2722
    28   INTEGER, intent(in) :: iim_input,jjm_input, ngrid,nslope      ! # of grid points along longitude/latitude/ total
    29   REAL, intent(in) ::  cell_area(ngrid)                         ! Area of each cell
     23  INTEGER, intent(in) :: iim_input,jjm_input, ngrid,nslope   ! # of grid points along longitude/latitude/ total
     24!  REAL, intent(in) ::  tendencies_h2o_ice_phys(ngrid) ! physical point field : Evolution of perenial ice over one year
     25  REAL, intent(in) ::  cell_area(ngrid)
    3026
    3127!   OUTPUT
    32   REAL, INTENT(INOUT) ::  qsurf(ngrid,nslope)                   ! physical point field : Previous and actual density of water ice
    33   LOGICAL :: STOPPING                                           ! Boolean to alert that there is no sublimating point anymore
     28  REAL, INTENT(INOUT) ::  qsurf(ngrid,nslope)                ! physical point field : Previous and actual density of water ice
     29  LOGICAL :: STOPPING
    3430  REAL, intent(inout) ::  tendencies_h2o_ice_phys(ngrid,nslope) ! physical point field : Evolution of perenial ice over one year
    3531
     
    3935
    4036  INTEGER :: i,j,ig0,islope                                  ! loop variable
    41   REAL :: pos_tend, neg_tend, real_coefficient               ! The integral of positive/negative tendencies overall the planet. Ratio
    42   REAL :: negative_part                                      ! After applying the tendencies, some point can be negative, we sum all of them in this variable
    43   REAL :: new_tendencies(ngrid,nslope)                       ! Tendencies after taking into account the non physical negative part above
     37!  REAL :: not_budget, budget
     38  REAL :: pos_tend, neg_tend, real_coefficient,negative_part
     39  REAL ::  new_tendencies(ngrid,nslope)
    4440
    4541
    4642!=======================================================================
    4743
    48 ! Integral of the positive and negative tendencies
     44!  budget=sum(qsurf(:))
     45
    4946  pos_tend=0.
    5047  neg_tend=0.
     
    6259  enddo
    6360
    64 ! These two quantities must be equal to conserve water, therfor we apply a ratio to them
     61!  print *, "pos_tend", pos_tend
     62!  print *, "neg_tend", neg_tend
    6563
    6664  if(neg_tend.GT.pos_tend .and. pos_tend.GT.0) then
     
    6866       do islope=1,nslope
    6967       if(tendencies_h2o_ice_phys(i,islope).LT.0) then
     68!          print *, "pos_tend/neg_tend", pos_tend/neg_tend
    7069          new_tendencies(i,islope)=tendencies_h2o_ice_phys(i,islope)*(pos_tend/neg_tend)
    7170       else
     
    7574     enddo
    7675  elseif(neg_tend.LT.pos_tend .and. neg_tend.GT.0) then
     76!          print *, "neg_tend/pos_tend", neg_tend/pos_tend
    7777     do i=1,ngrid
    7878       do islope=1,nslope
     
    8585     enddo
    8686  elseif(pos_tend.EQ.0 .OR. neg_tend.EQ.0) then
    87       call criterion_ice_stop_water_slope(cell_area,1,qsurf(:,:)*0,STOPPING,ngrid,cell_area)
     87
     88!      call criterion_ice_stop(cell_area,1,qsurf*0.,STOPPING,ngrid,cell_area)
     89      call criterion_ice_stop_water_slope(cell_area,1,qsurf(:,:)*0.,STOPPING,ngrid,cell_area)
    8890      do i=1,ngrid
    8991         do islope=1,nslope
     
    9395  endif
    9496
     97 
     98 
     99  negative_part = 0.
     100
    95101
    96102! Evolution of the water ice for each physical point
    97103  do i=1,ngrid
    98104    do islope=1, nslope
     105!      qsurf(i)=qsurf(i)+tendencies_h2o_ice_phys(i)*dt_pem
    99106      qsurf(i,islope)=qsurf(i,islope)+new_tendencies(i,islope)*dt_pem
    100       if (qsurf(i,islope).lt.0) then         ! If we have negative number, we put them to zero add sum them
     107!      budget=budget+tendencies_h2o_ice_phys(i)*dt_pem
     108      if (qsurf(i,islope).lt.0) then
     109!        not_budget=not_budget+qsurf(i)
     110!       print *, "NNqsurf(i,islope)", qsurf(i,islope)
     111!       print *, "NNnew_tendencies(i,islope)", new_tendencies(i,islope)
     112!       print *, "NNtendencies_h2o_ice_phys(i,islope)", tendencies_h2o_ice_phys(i,islope)
    101113        negative_part=negative_part-qsurf(i,islope)*cell_area(i)*subslope_dist(i,islope)
    102114        qsurf(i,islope)=0.
    103115        tendencies_h2o_ice_phys(i,islope)=0.
     116!        print *, "NNineg", i
     117      endif
     118      if(qsurf(i,islope).NE.qsurf(i,islope)) then
     119!          print *, "qsurf(i,islope)",qsurf(i,islope)
     120!          print *, "new_tendencies",new_tendencies(i,islope)
     121!          print *, "tendencies_h2o_ice_phys",tendencies_h2o_ice_phys(i,islope)
     122!          print *, "i", i
     123!          print *,"islope",islope
    104124      endif
    105125    enddo
    106126  enddo
    107127
    108 ! This negative part must be put somewhere else to conserve water, therfor we compute new tendencies
     128!  print *, "negative_part", negative_part
    109129  real_coefficient=negative_part/pos_tend
     130!  print *, "real_coefficient", real_coefficient
    110131
    111132  do i=1,ngrid
     
    118139
    119140
     141
     142! Conservation of water ice
     143!  qsurf(:)=qsurf(:)*budget/sum(qsurf(:))
     144
     145
    120146END SUBROUTINE evol_h2o_ice_s_slope
Note: See TracChangeset for help on using the changeset viewer.