source: trunk/LMDZ.COMMON/libf/evolution/evol_h2o_ice_s_mod.F90 @ 3031

Last change on this file since 3031 was 3031, checked in by llange, 18 months ago

MARS PEM
Add the water vapor exchanges between the subsurface ice and the atmosphere in the mass balance of H20 over the planet.
LL

File size: 6.0 KB
Line 
1MODULE evol_h2o_ice_s_mod
2
3IMPLICIT NONE
4
5CONTAINS
6
7SUBROUTINE evol_h2o_ice_s(ngrid,nslope,cell_area,delta_h2o_adsorbded,delta_h2o_icetablesublim,qsurf,tendencies_h2o_ice_phys,STOPPING)
8
9  use temps_mod_evol, only: dt_pem
10  use comslope_mod, only: subslope_dist,def_slope_mean
11  use criterion_pem_stop_mod, only: criterion_waterice_stop
12  use comconst_mod,only: pi
13
14  IMPLICIT NONE
15
16!=======================================================================
17!
18!  Routine that compute the evolution of the water ice
19!
20!=======================================================================
21
22!   arguments:
23!   ----------
24
25!   INPUT
26
27  INTEGER, intent(in) :: ngrid                                  ! # of grid points along longitude/latitude grid;
28  INTEGER, intent(in) :: nslope                                 ! # of subslope
29  REAL, intent(in) ::  cell_area(ngrid)                         ! Area of each mesh grid (m^2)
30  REAL, intent(in) :: delta_h2o_adsorbded(ngrid)                ! Mass of H2O adsorbded/desorbded in the soil (kg/m^2)
31  REAL, intent(in) :: delta_h2o_icetablesublim(ngrid)                ! Mass of H2O that have condensed/sublimated at the ice table (kg/m^2)
32
33!   OUTPUT
34  REAL, INTENT(INOUT) ::  qsurf(ngrid,nslope)                   ! physical point field : Previous and actual density of water ice (kg/m^2)
35  REAL, intent(inout) ::  tendencies_h2o_ice_phys(ngrid,nslope) ! physical point field : Evolution of perenial ice over one year (kg/m^2/year)
36  LOGICAL, INTENT(INOUT) :: STOPPING                            ! Stopping criterion
37
38!   local:
39!   ----
40
41  INTEGER :: i,j,islope                                         ! loop variable
42  REAL :: pos_tend, neg_tend, real_coefficient,negative_part    ! Variable to conserve water
43  REAL ::  new_tendencies(ngrid,nslope)                         ! Tendencies computed in order to conserve water ice on the surface, only exchange between surface are done
44 
45!=======================================================================
46
47  STOPPING=.false.
48
49  pos_tend=0.
50  neg_tend=0.
51if (ngrid.NE.1) then ! to make sure we are not in 1D
52  ! We compute the amount of water accumulating and sublimating
53  do i=1,ngrid
54     if(delta_h2o_adsorbded(i).GT.0) then
55        pos_tend=pos_tend+delta_h2o_adsorbded(i)*cell_area(i)
56     else
57        neg_tend=neg_tend+delta_h2o_adsorbded(i)*cell_area(i)
58     endif
59     if(delta_h2o_icetablesublim(i).GT.0) then
60        pos_tend=pos_tend+delta_h2o_icetablesublim(i)*cell_area(i)
61     else
62        neg_tend=neg_tend+delta_h2o_icetablesublim(i)*cell_area(i)
63     endif
64     do islope=1,nslope
65     if (qsurf(i,islope).GT.0) then
66         if (tendencies_h2o_ice_phys(i,islope).GT.0) then
67            pos_tend=pos_tend+tendencies_h2o_ice_phys(i,islope)*cell_area(i)*subslope_dist(i,islope)/cos(def_slope_mean(islope)*pi/180.)
68         else
69            neg_tend=neg_tend-tendencies_h2o_ice_phys(i,islope)*cell_area(i)*subslope_dist(i,islope)/cos(def_slope_mean(islope)*pi/180.)
70         endif
71     endif
72     enddo
73  enddo
74  ! We adapt the tendencies to conserve water and do only exchange between grid points
75   if(neg_tend.GT.pos_tend .and. pos_tend.GT.0) then ! We are sublimating more in the planet than condensing
76     do i=1,ngrid
77       do islope=1,nslope
78       if(tendencies_h2o_ice_phys(i,islope).LT.0) then ! We lower the sublimating rate by a coefficient
79          new_tendencies(i,islope)=tendencies_h2o_ice_phys(i,islope)*(pos_tend/neg_tend)
80       else                                            ! We dont't change the accumulating rate
81          new_tendencies(i,islope)=tendencies_h2o_ice_phys(i,islope)
82       endif
83       enddo
84     enddo
85   elseif(neg_tend.LT.pos_tend .and. neg_tend.GT.0) then ! We are condensing more in the planet than sublimating
86     do i=1,ngrid
87       do islope=1,nslope
88       if(tendencies_h2o_ice_phys(i,islope).LT.0) then ! We dont't change the sublimating rate
89          new_tendencies(i,islope)=tendencies_h2o_ice_phys(i,islope)
90       else                                            ! We lower the condensing rate by a coefficient
91          new_tendencies(i,islope)=tendencies_h2o_ice_phys(i,islope)*(neg_tend/pos_tend)
92       endif
93       enddo
94     enddo
95   elseif(pos_tend.EQ.0 .OR. neg_tend.EQ.0) then
96    print *, "Reason of stopping : There is either no water ice sublimating or no water ice increasing !!"
97    print *, "Tendencies on ice sublimating=", neg_tend
98    print *, "Tendencies on ice increasing=", pos_tend
99    print *, "This can be due to the absence of water ice in the PCM run!!"
100    call criterion_waterice_stop(cell_area,1.,qsurf(:,:)*0.,STOPPING,ngrid,qsurf(:,:)*0.)
101    do i=1,ngrid
102       do islope=1,nslope
103         new_tendencies(i,islope)=0
104       enddo
105    enddo
106   endif
107  negative_part = 0.
108
109! Evolution of the water ice for each physical point
110  do i=1,ngrid
111    do islope=1, nslope
112      qsurf(i,islope)=qsurf(i,islope)+new_tendencies(i,islope)*dt_pem
113      ! We compute the amount of water that is sublimated in excess
114      if (qsurf(i,islope).lt.0) then
115        negative_part=negative_part-qsurf(i,islope)*cell_area(i)*subslope_dist(i,islope)/cos(def_slope_mean(islope)*pi/180.)
116        qsurf(i,islope)=0.
117        tendencies_h2o_ice_phys(i,islope)=0.
118      endif
119    enddo
120  enddo
121 
122 
123  if(pos_tend.eq.0) then
124   real_coefficient = 0.
125  else
126   real_coefficient = negative_part/pos_tend ! We compute a coefficient by which we should remove the ice that has been added
127                                             ! to places even if this ice was contributing to an unphysical negative amount
128                                             ! of ice at other places
129  endif
130  do i=1,ngrid
131    do islope=1, nslope
132     if(new_tendencies(i,islope).GT.0) then  ! In the place of accumulation of ice, we remove a bit of ice in order to conserve water
133         qsurf(i,islope)=qsurf(i,islope)-new_tendencies(i,islope)*real_coefficient*dt_pem*cos(def_slope_mean(islope)*pi/180.)
134     endif
135    enddo
136  enddo
137else ! ngrid==1;
138  do islope=1, nslope
139    qsurf(1,islope)=qsurf(1,islope)+tendencies_h2o_ice_phys(1,islope)*dt_pem
140  enddo
141endif
142
143END SUBROUTINE evol_h2o_ice_s
144
145END MODULE evol_h2o_ice_s_mod
Note: See TracBrowser for help on using the repository browser.