source: trunk/LMDZ.COMMON/libf/evolution/criterion_ice_stop_mod_slope.F90 @ 2814

Last change on this file since 2814 was 2794, checked in by llange, 3 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.6 KB
Line 
1!
2! $Id $
3!
4SUBROUTINE criterion_ice_stop_slope(cell_area,ini_surf,qsurf,STOPPING,ngrid,initial_h2o_ice,global_ave_press_GCM,global_ave_press_new,nslope)
5
6  USE temps_mod_evol, ONLY: alpha_criterion
7  use comslope_mod, ONLY: subslope_dist
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,nslope                  ! # 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  REAL,    intent(in) :: global_ave_press_GCM
27  REAL,    intent(in) :: global_ave_press_new
28
29
30!   OUTPUT
31  LOGICAL, intent(out) :: STOPPING              ! Logical : is the criterion reached?
32
33!   local:
34!   -----
35  INTEGER :: i,islope                    ! Loop
36  REAL :: present_surf  ! Initial/Actual surface of water ice
37
38!=======================================================================
39
40!   initialisation to false
41    STOPPING=.FALSE.
42
43!   computation of the actual surface
44  present_surf=0.
45  do i=1,ngrid
46   do islope=1,nslope
47      if (initial_h2o_ice(i,islope).GT.0.5 .and. qsurf(i,islope).GT.0.) then
48         print *, "i", i
49         print *, "initial_h2o_ice(i,islope)", initial_h2o_ice(i,islope)
50         print *, "qsurf(i,:)", qsurf(i,:)
51         print *, "cell_area(i)", cell_area(i)
52         print *, "present_surf",present_surf
53         present_surf=present_surf+cell_area(i)*subslope_dist(i,islope)
54      endif
55   enddo
56  enddo
57
58!  print *, "initial_h2o_ice", initial_h2o_ice
59!  print *, "qsurf", qsurf
60
61  print *, "present_surf", present_surf
62  print *, "ini_surf", ini_surf
63  print *, "ini_surf*0.8", ini_surf*(1-alpha_criterion)
64 
65!   check of the criterion
66  if(present_surf.LT.ini_surf*(1-alpha_criterion) .OR. &
67     present_surf.GT.ini_surf*(1+alpha_criterion)) then
68  STOPPING=.TRUE.
69  endif
70
71  if (ini_surf.LT. 1E-5 .and. ini_surf.GT. -1E-5) then
72       STOPPING=.FALSE.
73  endif
74
75!  if(global_ave_press_GCM.LT.global_ave_press_new*(1-alpha_criterion) .OR. &
76!     global_ave_press_GCM.GT.global_ave_press_new*(1+alpha_criterion)) then
77!  STOPPING=.TRUE.
78!  endif
79
80  if(global_ave_press_new.LT.global_ave_press_GCM*(0.9) .OR. &
81     global_ave_press_new.GT.global_ave_press_GCM*(1.1)) then
82  STOPPING=.TRUE.
83  endif
84
85END SUBROUTINE criterion_ice_stop_slope
86
87
88
89
90
Note: See TracBrowser for help on using the repository browser.