source: trunk/LMDZ.COMMON/libf/evolution/criterion_ice_stop_mod_water_slope.F90 @ 2794

Last change on this file since 2794 was 2794, checked in by llange, 2 years ago

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 size: 2.2 KB
Line 
1!
2! $Id $
3!
4SUBROUTINE criterion_ice_stop_water_slope(cell_area,ini_surf,qsurf,STOPPING,ngrid,initial_h2o_ice)
5
6  USE temps_mod_evol, ONLY: alpha_criterion
7          use comslope_mod, ONLY: subslope_dist,nslope
8
9      IMPLICIT NONE
10
11!=======================================================================
12!
13!  Routine that checks if the criterion to stop the PEM is reached
14!
15!=======================================================================
16
17!   arguments:
18!   ----------
19
20!   INPUT
21  INTEGER, intent(in) :: ngrid                  ! # of grid physical grid points
22  REAL,    intent(in) :: cell_area(ngrid)       ! physical point field : Area of the cells
23  REAL,    intent(in) ::  qsurf(ngrid,nslope)          ! physical point field : Actual density of water ice
24  REAL,    intent(in) :: ini_surf
25  REAL,    intent(in) :: initial_h2o_ice(ngrid,nslope)
26
27
28!   OUTPUT
29  LOGICAL, intent(out) :: STOPPING              ! Logical : is the criterion reached?
30
31!   local:
32!   -----
33  INTEGER :: i,islope                    ! Loop
34  REAL :: present_surf  ! Initial/Actual surface of water ice
35
36!=======================================================================
37
38!   initialisation to false
39    STOPPING=.FALSE.
40
41!   computation of the actual surface
42  present_surf=0.
43  do i=1,ngrid
44    do islope=1, nslope
45      if (initial_h2o_ice(i,islope).GT.0.5 .and. qsurf(i,islope).GT.0.) then
46!         print *, "i", i
47!         print *, "initial_h2o_ice(i,islope)", initial_h2o_ice(i,islope)
48!         print *, "qsurf(i,islope)", qsurf(i,islope)
49!         print *, "cell_area(i)", cell_area(i)
50!         print *, "present_surf",present_surf
51         present_surf=present_surf+cell_area(i)*subslope_dist(i,islope)
52      endif
53    enddo
54  enddo
55
56!  print *, "initial_h2o_ice", initial_h2o_ice
57!  print *, "qsurf", qsurf
58
59!  print *, "present_surf", present_surf
60!  print *, "ini_surf", ini_surf
61!  print *, "ini_surf*0.8", ini_surf*(1-alpha_criterion)
62 
63!   check of the criterion
64  if(present_surf.LT.ini_surf*(1-alpha_criterion) .OR. &
65     present_surf.GT.ini_surf*(1+alpha_criterion)) then
66  STOPPING=.TRUE.
67  endif
68
69  if (ini_surf.LT. 1E-5 .and. ini_surf.GT. -1E-5) then
70       STOPPING=.FALSE.
71  endif
72
73END SUBROUTINE criterion_ice_stop_water_slope
74
75
76
77
78
Note: See TracBrowser for help on using the repository browser.