source: trunk/LMDZ.COMMON/libf/evolution/computeice_table.F90 @ 2852

Last change on this file since 2852 was 2849, checked in by llange, 3 years ago

PEM
Update the codes for subsurface evolution to run with XIOS
1) Water density at the surface and in the soil is now read in the XIOS file
2) Reshape routine created as XIOS output have one element less in the longitude grid
3) The ice table is now computed using these water densities
4) Minor fixs in the main, adsorption module, and tendencies evolutions

LL

File size: 1.5 KB
Line 
1   SUBROUTINE computeice_table(ngrid,nslope,nsoil_PEM,rhowatersurf_ave,rhowatersoil_ave,ice_table)
2#ifndef CPP_STD
3    USE comsoil_h, only:  inertiedat, volcapa
4    USE vertical_layers_mod, ONLY: ap,bp
5    USE comsoil_h_PEM, only: layer_PEM
6    implicit none
7
8    integer,intent(in) :: ngrid,nslope,nsoil_PEM
9    real,intent(in) :: rhowatersurf_ave(ngrid,nslope)    ! surface temperature, timeseries [K]
10    real,intent(in) :: rhowatersoil_ave(ngrid,nsoil_PEM,nslope)    ! soil water density, yearly average [kg/m^3]
11    real,intent(inout) :: ice_table(ngrid,nslope)                 ! ice table [m]
12    real :: z1,z2
13    integer ig, islope,isoil
14    real :: diff_rho(nsoil_PEM)                    ! difference of vapor content
15
16
17     do ig = 1,ngrid
18      do islope = 1,nslope
19           ice_table(ig,islope) = -10.
20
21         do isoil = 1,nsoil_PEM
22           diff_rho(isoil) = rhowatersurf_ave(ig,islope) - rhowatersoil_ave(ig,isoil,islope)
23
24         enddo
25
26         if(diff_rho(1) > 0) then
27           ice_table(ig,islope) = 0.
28         else
29           do isoil = 1,nsoil_PEM -1
30             if((diff_rho(isoil).lt.0).and.(diff_rho(isoil+1).gt.0.)) then
31               z1 = (diff_rho(isoil) - diff_rho(isoil+1))/(layer_PEM(isoil) - layer_PEM(isoil+1))
32               z2 = -layer_PEM(isoil+1)*z1 +  diff_rho(isoil+1)
33               ice_table(ig,islope) = -z2/z1
34               exit
35             endif
36           enddo
37          endif
38        enddo
39      enddo
40
41   
42
43!=======================================================================
44      RETURN
45
46#endif
47      END
Note: See TracBrowser for help on using the repository browser.