source: trunk/LMDZ.COMMON/libf/evolution/read_data_GCM.F90 @ 2841

Last change on this file since 2841 was 2835, checked in by romain.vande, 3 years ago

Mars PEM:
Introduction of the possibility to follow an orbital forcing.
Introduction of new control parameters.
Cleaning of the PEM (removing unused files, add comments and new files)

A file named run_PEM.def can be added to the run.def. It contains the following variables:

_ evol_orbit_pem: Boolean. Do you want to follow an orbital forcing predefined (read in ob_ex_lsp.asc for example)? (default=false)
_ year_bp_ini: Integer. Number of year before present to start the pem run if evol_orbit_pem=.true. , default=0
_ Max_iter_pem: Integer. Maximal number of iteration if none of the stopping criterion is reached and if evol_orbit_pem=.false., default=99999999
_ dt_pem: Integer. Time step of the PEM in year, default=1
_ alpha_criterion: Real. Acceptance rate of sublimating ice surface change, default=0.2
_ soil_pem: Boolean. Do you want to run with subsurface physical processes in the PEM? default=.true.

RV

File size: 9.6 KB
Line 
1!
2! $Id $
3!
4SUBROUTINE read_data_GCM(fichnom,min_h2o_ice_s,min_co2_ice_s,iim_input,jjm_input,nlayer,vmr_co2_gcm,ps_GCM,timelen, &
5             min_co2_ice_slope,min_h2o_ice_slope,nslope,tsurf_ave,tsoil_ave,tsurf_gcm,tsoil_gcm,TI_ave,q_co2_GCM,q_h2o_GCM,co2_ice_slope)
6
7      use netcdf, only: nf90_open,NF90_NOWRITE,nf90_noerr,nf90_strerror, &
8                        nf90_get_var, nf90_inq_varid, nf90_inq_dimid, &
9                        nf90_inquire_dimension,nf90_close
10      use comsoil_h, only: nsoilmx
11      USE soil_evolution_mod, ONLY: soil_pem
12
13      IMPLICIT NONE
14
15!=======================================================================
16!
17! Read initial confitions file
18!
19!=======================================================================
20
21  include "dimensions.h"
22
23!===============================================================================
24! Arguments:
25  CHARACTER(LEN=*), INTENT(IN) :: fichnom          !--- FILE NAME
26  INTEGER, INTENT(IN) :: timelen                   ! number of times stored in the file
27
28  INTEGER :: iim_input,jjm_input,nlayer,nslope
29  REAL, ALLOCATABLE ::  h2o_ice_s(:,:,:)                       ! h2o_ice_s of the concatenated file
30  REAL, ALLOCATABLE ::  co2_ice_s(:,:,:)                       ! co2_ice_s of the concatenated file
31
32  REAL, ALLOCATABLE ::  h2o_ice_s_slope(:,:,:,:)                       ! co2_ice_s of the concatenated file
33
34  REAL, INTENT(OUT) ::  min_h2o_ice_s(iim_input+1,jjm_input+1) ! Minimum of h2o_ice_s of the year
35  REAL, INTENT(OUT) ::  min_co2_ice_s(iim_input+1,jjm_input+1) ! Minimum of co2_ice_s of the year
36  REAL, INTENT(OUT) ::  min_co2_ice_slope(iim_input+1,jjm_input+1,nslope) ! Minimum of co2_ice slope of the year
37  REAL, INTENT(OUT) ::  min_h2o_ice_slope(iim_input+1,jjm_input+1,nslope) ! Minimum of co2_ice slope of the year
38  REAL, INTENT(OUT) ::  vmr_co2_gcm(iim_input+1,jjm_input+1,timelen)      !!!!vmr_co2_phys_gcm(iim_input+1,jjm_input+1,timelen)
39  REAL, INTENT(OUT) ::  q_h2o_GCM(iim_input+1,jjm_input+1,timelen)
40  REAL, INTENT(OUT) ::  q_co2_GCM(iim_input+1,jjm_input+1,timelen)
41  REAL, ALLOCATABLE ::  q1_co2_GCM(:,:,:)
42  REAL,  INTENT(OUT) ::  ps_GCM(iim_input+1,jjm_input+1,timelen)
43
44!SOIL
45  REAL, INTENT(OUT) ::  tsurf_ave(iim_input+1,jjm_input+1,nslope) ! Average surface temperature of the concatenated file
46  REAL, INTENT(OUT) ::  tsoil_ave(iim_input+1,jjm_input+1,nsoilmx,nslope) ! Average soil temperature of the concatenated file
47
48  REAL ,INTENT(OUT) ::  tsurf_gcm(iim_input+1,jjm_input+1,nslope,timelen) ! Surface temperature of the concatenated file
49  REAL , INTENT(OUT) ::  tsoil_gcm(iim_input+1,jjm_input+1,nsoilmx,nslope,timelen) ! Soil temperature of the concatenated file
50
51  REAL ::  TI_gcm(iim_input+1,jjm_input+1,nsoilmx,nslope,timelen) ! Thermal Inertia  of the concatenated file
52  REAL, INTENT(OUT) ::  TI_ave(iim_input+1,jjm_input+1,nsoilmx,nslope) ! Average Thermal Inertia  of the concatenated file
53  REAL, INTENT(OUT) ::  co2_ice_slope(iim_input+1,jjm_input+1,nslope,timelen) ! Minimum of co2_ice slope of the year
54!===============================================================================
55!   Local Variables
56  CHARACTER(LEN=256) :: msg, var, modname
57  INTEGER,PARAMETER :: length=100
58  INTEGER :: iq, fID, vID, idecal
59  INTEGER :: ierr
60  CHARACTER(len=12) :: start_file_type="earth" ! default start file type
61
62  REAL,ALLOCATABLE :: time(:) ! times stored in start
63  INTEGER :: indextime ! index of selected time
64
65  INTEGER :: edges(4),corner(4)
66  INTEGER :: i,j,t
67  real,save :: m_co2, m_noco2, A , B, mmean
68
69  INTEGER :: islope
70  CHARACTER*2 :: num
71
72!-----------------------------------------------------------------------
73  modname="pemetat0"
74
75      m_co2 = 44.01E-3  ! CO2 molecular mass (kg/mol)   
76      m_noco2 = 33.37E-3  ! Non condensible mol mass (kg/mol)   
77      A =(1/m_co2 - 1/m_noco2)
78      B=1/m_noco2
79
80      allocate(co2_ice_s(iim+1,jjm+1,timelen))
81      allocate(q1_co2_GCM(iim+1,jjm+1,timelen))
82      allocate(h2o_ice_s_slope(iim+1,jjm+1,nslope,timelen))
83      allocate(h2o_ice_s(iim+1,jjm+1,timelen))
84
85  print *, "Opening ", fichnom, "..."
86
87!  Open initial state NetCDF file
88  var=fichnom
89  CALL err(NF90_OPEN(var,NF90_NOWRITE,fID),"open",var)
90
91     print *, "Downloading data for h2oice ..."
92
93! Get h2o_ice_s of the concatenated file
94  CALL get_var3("h2o_ice_s"   ,h2o_ice_s)
95
96     print *, "Downloading data for h2oice done"
97     print *, "Downloading data for co2ice ..."
98
99  CALL get_var3("co2ice"   ,co2_ice_s)
100
101     print *, "Downloading data for co2ice done"
102     print *, "Downloading data for vmr co2..."
103
104  CALL get_var3("co2_cropped"   ,q_co2_GCM)
105
106     print *, "Downloading data for vmr co2 done"
107     print *, "Downloading data for vmr h20..."
108
109  CALL get_var3("h2o_cropped"   ,q_h2o_GCM)
110
111     print *, "Downloading data for vmr h2o done"
112     print *, "Downloading data for surface pressure ..."
113
114  CALL get_var3("ps"   ,ps_GCM)
115
116     print *, "Downloading data for surface pressure done"
117     print *, "nslope=", nslope
118     print *, "Downloading data for co2ice_slope ..."
119
120DO islope=1,nslope
121  write(num,fmt='(i2.2)') islope
122  call get_var3("co2ice_slope"//num,co2_ice_slope(:,:,islope,:))
123ENDDO
124
125     print *, "Downloading data for co2ice_slope done"
126     print *, "Downloading data for h2o_ice_s_slope ..."
127
128DO islope=1,nslope
129  write(num,fmt='(i2.2)') islope
130  call get_var3("h2o_ice_s_slope"//num,h2o_ice_s_slope(:,:,islope,:))
131ENDDO
132
133     print *, "Downloading data for h2o_ice_s_slope done"
134     print *, "Downloading data for tsurf_slope ..."
135
136DO islope=1,nslope
137  write(num,fmt='(i2.2)') islope
138  call get_var3("tsurf_slope"//num,tsurf_gcm(:,:,islope,:))
139ENDDO
140
141     print *, "Downloading data for tsurf_slope done"
142
143     if(soil_pem) then
144
145     print *, "Downloading data for tsoil_slope ..."
146
147DO islope=1,nslope
148  write(num,fmt='(i2.2)') islope
149  call get_var4("tsoil_slope"//num,tsoil_gcm(:,:,:,islope,:))
150ENDDO
151
152     print *, "Downloading data for tsoil_slope done"
153     print *, "Downloading data for inertiesoil_slope ..."
154
155DO islope=1,nslope
156  write(num,fmt='(i2.2)') islope
157  call get_var4("inertiesoil_slope"//num,TI_gcm(:,:,:,islope,:))
158ENDDO
159
160     print *, "Downloading data for inertiesoil_slope done"
161
162  endif
163
164! Compute the minimum over the year for each point
165  print *, "Computing the min of h2o_ice"
166  min_h2o_ice_s(:,:)=minval(h2o_ice_s,3)
167  print *, "Computing the min of co2_ice"
168  min_co2_ice_s(:,:)=minval(co2_ice_s,3)
169
170  print *, "Computing the min of h2o_ice_slope"
171  min_h2o_ice_slope(:,:,:)=minval(h2o_ice_s_slope,4)
172  print *, "Computing the min of co2_ice_slope"
173  min_co2_ice_slope(:,:,:)=minval(co2_ice_slope,4)
174
175!Compute averages
176
177    print *, "Computing average of tsurf"
178    tsurf_ave(:,:,:)=SUM(tsurf_gcm(:,:,:,:),4)/timelen
179
180  if(soil_pem) then
181    print *, "Computing average of tsoil"
182    tsoil_ave(:,:,:,:)=SUM(tsoil_gcm(:,:,:,:,:),5)/timelen
183    print *, "Computing average of TI"
184    TI_ave(:,:,:,:)=SUM(TI_gcm(:,:,:,:,:),5)/timelen
185  endif
186
187! By definition, a density is positive, we get rid of the negative values
188  DO i=1,iim+1
189    DO j = 1, jjm+1
190       if (min_co2_ice_s(i,j).LT.0) then
191          min_h2o_ice_s(i,j)  = 0.
192          min_co2_ice_s(i,j)  = 0.
193       endif
194       DO islope=1,nslope
195          if (min_co2_ice_slope(i,j,islope).LT.0) then
196            min_co2_ice_slope(i,j,islope)  = 0.
197          endif
198          if (min_h2o_ice_slope(i,j,islope).LT.0) then
199            min_h2o_ice_slope(i,j,islope)  = 0.
200          endif
201       ENDDO
202    ENDDO
203  ENDDO
204
205  DO i=1,iim+1
206    DO j = 1, jjm+1
207      DO t = 1, timelen
208         if (q_co2_GCM(i,j,t).LT.0) then
209              q_co2_GCM(i,j,t)=1E-10
210         elseif (q_co2_GCM(i,j,t).GT.1) then
211              q_co2_GCM(i,j,t)=1.
212         endif
213         if (q_h2o_GCM(i,j,t).LT.0) then
214              q_h2o_GCM(i,j,t)=1E-30
215         elseif (q_h2o_GCM(i,j,t).GT.1) then
216              q_h2o_GCM(i,j,t)=1.
217         endif
218         mmean=1/(A*q_co2_GCM(i,j,t) +B)
219         vmr_co2_gcm(i,j,t) = q_co2_GCM(i,j,t)*mmean/m_co2
220      ENDDO
221    ENDDO
222  ENDDO
223
224  CONTAINS
225
226SUBROUTINE check_dim(n1,n2,str1,str2)
227  INTEGER,          INTENT(IN) :: n1, n2
228  CHARACTER(LEN=*), INTENT(IN) :: str1, str2
229  CHARACTER(LEN=256) :: s1, s2
230  IF(n1/=n2) THEN
231    s1='value of '//TRIM(str1)//' ='
232    s2=' read in starting file differs from parametrized '//TRIM(str2)//' ='
233    WRITE(msg,'(10x,a,i4,2x,a,i4)')TRIM(s1),n1,TRIM(s2),n2
234    CALL ABORT_gcm(TRIM(modname),TRIM(msg),1)
235  END IF
236END SUBROUTINE check_dim
237
238
239SUBROUTINE get_var1(var,v)
240  CHARACTER(LEN=*), INTENT(IN)  :: var
241  REAL,             INTENT(OUT) :: v(:)
242  CALL err(NF90_INQ_VARID(fID,var,vID),"inq",var)
243  CALL err(NF90_GET_VAR(fID,vID,v),"get",var)
244END SUBROUTINE get_var1
245
246
247SUBROUTINE get_var3(var,v) ! on U grid
248  CHARACTER(LEN=*), INTENT(IN)  :: var
249  REAL,             INTENT(OUT) :: v(:,:,:)
250  CALL err(NF90_INQ_VARID(fID,var,vID),"inq",var)
251  CALL err(NF90_GET_VAR(fID,vID,v),"get",var)
252
253END SUBROUTINE get_var3
254
255SUBROUTINE get_var4(var,v)
256  CHARACTER(LEN=*), INTENT(IN)  :: var
257  REAL,             INTENT(OUT) :: v(:,:,:,:)
258  CALL err(NF90_INQ_VARID(fID,var,vID),"inq",var)
259  CALL err(NF90_GET_VAR(fID,vID,v),"get",var)
260END SUBROUTINE get_var4
261
262SUBROUTINE err(ierr,typ,nam)
263  INTEGER,          INTENT(IN) :: ierr   !--- NetCDF ERROR CODE
264  CHARACTER(LEN=*), INTENT(IN) :: typ    !--- TYPE OF OPERATION
265  CHARACTER(LEN=*), INTENT(IN) :: nam    !--- FIELD/FILE NAME
266  IF(ierr==NF90_NoERR) RETURN
267  SELECT CASE(typ)
268    CASE('inq');   msg="Field <"//TRIM(nam)//"> is missing"
269    CASE('get');   msg="Reading failed for <"//TRIM(nam)//">"
270    CASE('open');  msg="File opening failed for <"//TRIM(nam)//">"
271    CASE('close'); msg="File closing failed for <"//TRIM(nam)//">"
272  END SELECT
273  CALL ABORT_gcm(TRIM(modname),TRIM(msg),ierr)
274END SUBROUTINE err
275
276END SUBROUTINE read_data_gcm
Note: See TracBrowser for help on using the repository browser.