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

Last change on this file since 3082 was 3082, checked in by jbclement, 14 months ago

PEM:

  • Correction of a bug in the initialization of constants. The correct modules are now used: 'comcstfi_h' (and no longer 'comconst_mod'!) in the general case and 'comcstfi_mod' in the case of generic model;
  • Addition of the variable 'ecritpem' in "run_PEM.def" to set the frequency of outputs in the "diagfi.nc". By default, 'ecritpem = 1' which means there is one output at each PEM year.

JBC

File size: 6.1 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 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
12#ifndef CPP_STD
13    use comcstfi_h,   only: pi
14#else
15    use comcstfi_mod, only: pi
16#endif
17
18  IMPLICIT NONE
19
20!=======================================================================
21!
22!  Routine that compute the evolution of the water ice
23!
24!=======================================================================
25
26!   arguments:
27!   ----------
28
29!   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)
36
37!   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
41
42!   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 
49!=======================================================================
50
51  STOPPING=.false.
52
53  pos_tend=0.
54  neg_tend=0.
55if (ngrid.NE.1) then ! to make sure we are not in 1D
56  ! We compute the amount of water accumulating and sublimating
57  do i=1,ngrid
58     if(delta_h2o_adsorbded(i).GT.0) then
59        pos_tend=pos_tend+delta_h2o_adsorbded(i)*cell_area(i)
60     else
61        neg_tend=neg_tend+delta_h2o_adsorbded(i)*cell_area(i)
62     endif
63     if(delta_h2o_icetablesublim(i).GT.0) then
64        pos_tend=pos_tend+delta_h2o_icetablesublim(i)*cell_area(i)
65     else
66        neg_tend=neg_tend+delta_h2o_icetablesublim(i)*cell_area(i)
67     endif
68     do islope=1,nslope
69     if (qsurf(i,islope).GT.0) then
70         if (tendencies_h2o_ice_phys(i,islope).GT.0) then
71            pos_tend=pos_tend+tendencies_h2o_ice_phys(i,islope)*cell_area(i)*subslope_dist(i,islope)/cos(def_slope_mean(islope)*pi/180.)
72         else
73            neg_tend=neg_tend-tendencies_h2o_ice_phys(i,islope)*cell_area(i)*subslope_dist(i,islope)/cos(def_slope_mean(islope)*pi/180.)
74         endif
75     endif
76     enddo
77  enddo
78  ! 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
80     do i=1,ngrid
81       do islope=1,nslope
82       if(tendencies_h2o_ice_phys(i,islope).LT.0) then ! We lower the sublimating rate by a coefficient
83          new_tendencies(i,islope)=tendencies_h2o_ice_phys(i,islope)*(pos_tend/neg_tend)
84       else                                            ! We dont't change the accumulating rate
85          new_tendencies(i,islope)=tendencies_h2o_ice_phys(i,islope)
86       endif
87       enddo
88     enddo
89   elseif(neg_tend.LT.pos_tend .and. neg_tend.GT.0) then ! We are condensing more in the planet than sublimating
90     do i=1,ngrid
91       do islope=1,nslope
92       if(tendencies_h2o_ice_phys(i,islope).LT.0) then ! We dont't change the sublimating rate
93          new_tendencies(i,islope)=tendencies_h2o_ice_phys(i,islope)
94       else                                            ! We lower the condensing rate by a coefficient
95          new_tendencies(i,islope)=tendencies_h2o_ice_phys(i,islope)*(neg_tend/pos_tend)
96       endif
97       enddo
98     enddo
99   elseif(pos_tend.EQ.0 .OR. neg_tend.EQ.0) then
100    write(*,*) "Reason of stopping : There is either no water ice sublimating or no water ice increasing !!"
101    write(*,*) "Tendencies on ice sublimating=", neg_tend
102    write(*,*) "Tendencies on ice increasing=", pos_tend
103    write(*,*) "This can be due to the absence of water ice in the PCM run!!"
104    call criterion_waterice_stop(cell_area,1.,qsurf(:,:)*0.,STOPPING,ngrid,qsurf(:,:)*0.)
105    do i=1,ngrid
106       do islope=1,nslope
107         new_tendencies(i,islope)=0
108       enddo
109    enddo
110   endif
111  negative_part = 0.
112
113! Evolution of the water ice for each physical point
114  do i=1,ngrid
115    do islope=1, nslope
116      qsurf(i,islope)=qsurf(i,islope)+new_tendencies(i,islope)*dt_pem
117      ! We compute the amount of water that is sublimated in excess
118      if (qsurf(i,islope).lt.0) then
119        negative_part=negative_part-qsurf(i,islope)*cell_area(i)*subslope_dist(i,islope)/cos(def_slope_mean(islope)*pi/180.)
120        qsurf(i,islope)=0.
121        tendencies_h2o_ice_phys(i,islope)=0.
122      endif
123    enddo
124  enddo
125 
126 
127  if(pos_tend.eq.0) then
128   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
132                                             ! of ice at other places
133  endif
134  do i=1,ngrid
135    do islope=1, nslope
136     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
137         qsurf(i,islope)=qsurf(i,islope)-new_tendencies(i,islope)*real_coefficient*dt_pem*cos(def_slope_mean(islope)*pi/180.)
138     endif
139    enddo
140  enddo
141else ! ngrid==1;
142  do islope=1, nslope
143    qsurf(1,islope)=qsurf(1,islope)+tendencies_h2o_ice_phys(1,islope)*dt_pem
144  enddo
145endif
146
147END SUBROUTINE evol_h2o_ice_s
148
149END MODULE evol_h2o_ice_s_mod
Note: See TracBrowser for help on using the repository browser.