source: trunk/LMDZ.COMMON/libf/evolution/criterion_co2_ice_stop_mod.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: 1.9 KB
Line 
1!
2! $Id $
3!
4SUBROUTINE criterion_co2_ice_stop(cell_area,initial_co2_ice,co2ice,STOPPING,ngrid,latitude,n_band_lat)
5
6  USE temps_mod_evol, ONLY: alpha_criterion
7
8      IMPLICIT NONE
9
10!=======================================================================
11!
12!  Routine that checks if the criterion to stop the PEM is reached
13!
14!=======================================================================
15
16!   arguments:
17!   ----------
18
19!   INPUT
20  INTEGER, intent(in) :: ngrid                  ! # of grid physical grid points
21  REAL,    intent(in) :: cell_area(ngrid)       ! physical point field : Area of the cells
22  REAL,    intent(in) ::  co2ice(ngrid)          ! physical point field : Actual density of water ice
23  REAL,    intent(in) ::  latitude(ngrid)          ! physical point field : Latitude
24  REAL,    intent(in) ::  initial_co2_ice(n_band_lat)  ! Initial/Actual surface of water ice
25
26
27
28!   OUTPUT
29  LOGICAL, intent(out) :: STOPPING              ! Logical : is the criterion reached?
30
31!   local:
32!   -----
33  INTEGER :: i,j,n_band_lat                    ! Loop
34  REAL :: present_co2(n_band_lat)  ! Initial/Actual surface of water ice
35  REAL :: pi
36
37!=======================================================================
38
39      pi=4.D0*DATAN(1.D0)
40
41!   initialisation to false
42    STOPPING=.FALSE.
43
44     do j=1,n_band_lat
45        present_co2(j)=0.
46     enddo
47
48  do i=1,ngrid
49            j=floor((latitude(i)+(pi/2))/(pi)*n_band_lat)+1
50      if(j.GT.n_band_lat) then
51          j=n_band_lat
52      endif
53      present_co2(j)=present_co2(j)+co2ice(i)*cell_area(i)
54  enddo
55 
56!   check of the criterion
57  do j=1,n_band_lat
58    if(present_co2(j).LT.initial_co2_ice(j)*(1-alpha_criterion) .OR. &
59       present_co2(j).GT.initial_co2_ice(j)*(1+alpha_criterion)) then
60         STOPPING=.TRUE.
61         print *, "j", j
62         print *, "present_co2(j)", present_co2(j)
63         print *, "initial_co2_ice(j)", initial_co2_ice(j)
64    endif
65  enddo
66
67END SUBROUTINE criterion_co2_ice_stop
68
69
70
71
72
Note: See TracBrowser for help on using the repository browser.