source: trunk/LMDZ.COMMON/libf/evolution/evol_h2o_ice_s_mod_slope.F90 @ 2842

Last change on this file since 2842 was 2835, checked in by romain.vande, 3 years ago

Mars PEM:
Introduction of the possibility to follow an orbital forcing.
Introduction of new control parameters.
Cleaning of the PEM (removing unused files, add comments and new files)

A file named run_PEM.def can be added to the run.def. It contains the following variables:

_ evol_orbit_pem: Boolean. Do you want to follow an orbital forcing predefined (read in ob_ex_lsp.asc for example)? (default=false)
_ year_bp_ini: Integer. Number of year before present to start the pem run if evol_orbit_pem=.true. , default=0
_ Max_iter_pem: Integer. Maximal number of iteration if none of the stopping criterion is reached and if evol_orbit_pem=.false., default=99999999
_ dt_pem: Integer. Time step of the PEM in year, default=1
_ alpha_criterion: Real. Acceptance rate of sublimating ice surface change, default=0.2
_ soil_pem: Boolean. Do you want to run with subsurface physical processes in the PEM? default=.true.

RV

File size: 3.5 KB
Line 
1!
2! $Id $
3!
4SUBROUTINE evol_h2o_ice_s_slope(qsurf,tendencies_h2o_ice_phys,&
5                             iim_input,jjm_input,ngrid,cell_area,STOPPING,nslope)
6
7  USE temps_mod_evol, ONLY: dt_pem
8  use comslope_mod, ONLY: subslope_dist
9
10      IMPLICIT NONE
11
12!=======================================================================
13!
14!  Routine that compute the evolution of the water ice
15!
16!=======================================================================
17
18!   arguments:
19!   ----------
20
21!   INPUT
22
23  INTEGER, intent(in) :: iim_input,jjm_input, ngrid,nslope   ! # of grid points along longitude/latitude/ total
24  REAL, intent(in) ::  cell_area(ngrid)
25
26!   OUTPUT
27  REAL, INTENT(INOUT) ::  qsurf(ngrid,nslope)                ! physical point field : Previous and actual density of water ice
28  LOGICAL :: STOPPING
29  REAL, intent(inout) ::  tendencies_h2o_ice_phys(ngrid,nslope) ! physical point field : Evolution of perenial ice over one year
30
31!   local:
32!   ----
33
34  INTEGER :: i,j,ig0,islope                                  ! loop variable
35  REAL :: pos_tend, neg_tend, real_coefficient,negative_part
36  REAL ::  new_tendencies(ngrid,nslope)
37
38!=======================================================================
39
40  pos_tend=0.
41  neg_tend=0.
42
43  do i=1,ngrid
44     do islope=1,nslope
45     if (qsurf(i,islope).GT.0) then
46         if (tendencies_h2o_ice_phys(i,islope).GT.0) then
47            pos_tend=pos_tend+tendencies_h2o_ice_phys(i,islope)*cell_area(i)*subslope_dist(i,islope)
48         else
49            neg_tend=neg_tend-tendencies_h2o_ice_phys(i,islope)*cell_area(i)*subslope_dist(i,islope)
50         endif
51     endif
52     enddo
53  enddo
54
55  if(neg_tend.GT.pos_tend .and. pos_tend.GT.0) then
56     do i=1,ngrid
57       do islope=1,nslope
58       if(tendencies_h2o_ice_phys(i,islope).LT.0) then
59          new_tendencies(i,islope)=tendencies_h2o_ice_phys(i,islope)*(pos_tend/neg_tend)
60       else
61          new_tendencies(i,islope)=tendencies_h2o_ice_phys(i,islope)
62       endif
63       enddo
64     enddo
65  elseif(neg_tend.LT.pos_tend .and. neg_tend.GT.0) then
66     do i=1,ngrid
67       do islope=1,nslope
68       if(tendencies_h2o_ice_phys(i,islope).LT.0) then
69          new_tendencies(i,islope)=tendencies_h2o_ice_phys(i,islope)
70       else
71          new_tendencies(i,islope)=tendencies_h2o_ice_phys(i,islope)*(neg_tend/pos_tend)
72       endif
73       enddo
74     enddo
75  elseif(pos_tend.EQ.0 .OR. neg_tend.EQ.0) then
76    print *, "Reason of stopping : There is either no water ice sublimating or no water ice increasing !!"
77    print *, "Tendencies on ice sublimating=", neg_tend
78    print *, "Tendencies on ice increasing=", pos_tend
79    print *, "This can be due to the absence of water ice in the PCM run!!"
80      call criterion_ice_stop_water_slope(cell_area,1,qsurf(:,:)*0.,STOPPING,ngrid,cell_area)
81      do i=1,ngrid
82         do islope=1,nslope
83          new_tendencies(i,islope)=0
84         enddo
85      enddo
86  endif
87
88  negative_part = 0.
89
90! Evolution of the water ice for each physical point
91  do i=1,ngrid
92    do islope=1, nslope
93      qsurf(i,islope)=qsurf(i,islope)+new_tendencies(i,islope)*dt_pem
94      if (qsurf(i,islope).lt.0) then
95        negative_part=negative_part-qsurf(i,islope)*cell_area(i)*subslope_dist(i,islope)
96        qsurf(i,islope)=0.
97        tendencies_h2o_ice_phys(i,islope)=0.
98      endif
99    enddo
100  enddo
101
102  real_coefficient=negative_part/pos_tend
103
104  do i=1,ngrid
105    do islope=1, nslope
106     if(new_tendencies(i,islope).GT.0) then
107         qsurf(i,islope)=qsurf(i,islope)-new_tendencies(i,islope)*real_coefficient*dt_pem
108     endif
109    enddo
110  enddo
111
112
113
114END SUBROUTINE evol_h2o_ice_s_slope
Note: See TracBrowser for help on using the repository browser.