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

Last change on this file since 2962 was 2944, checked in by llange, 20 months ago

PEM
Introduce module 'constants_marspem': Constants that are used are now put in this module, and load in each subroutine.
LL

File size: 13.2 KB
Line 
1!
2! $Id $
3!
4SUBROUTINE read_data_GCM(fichnom,timelen, iim_input,jjm_input,ngrid,nslope,vmr_co2_gcm_phys,ps_timeseries, &
5             min_co2_ice,min_h2o_ice,tsurf_ave,tsoil_ave,tsurf_gcm,tsoil_gcm,q_co2,q_h2o,co2_ice_slope, &
6             watersurf_density_ave,watersoil_density)
7
8      use netcdf, only: nf90_open,NF90_NOWRITE,nf90_noerr,nf90_strerror, &
9                        nf90_get_var, nf90_inq_varid, nf90_inq_dimid, &
10                        nf90_inquire_dimension,nf90_close
11      use comsoil_h, only: nsoilmx
12      USE comsoil_h_PEM, ONLY: soil_pem
13      use constants_marspem_mod,only: m_co2,m_noco2
14      IMPLICIT NONE
15
16!=======================================================================
17!
18! Purpose: Read initial confitions file from the GCM
19!
20! Authors: RV & LL
21!=======================================================================
22
23  include "dimensions.h"
24
25!===============================================================================
26! Arguments:
27
28  CHARACTER(LEN=*), INTENT(IN) :: fichnom          !--- FILE NAME
29  INTEGER, INTENT(IN) :: timelen                   ! number of times stored in the file
30  INTEGER :: iim_input,jjm_input,ngrid,nslope            ! number of points in the lat x lon dynamical grid, number of subgrid slopes
31! Ouputs
32  REAL, INTENT(OUT) ::  min_co2_ice(ngrid,nslope) ! Minimum of co2 ice  per slope of the year [kg/m^2]
33  REAL, INTENT(OUT) ::  min_h2o_ice(ngrid,nslope) ! Minimum of h2o ice per slope of the year [kg/m^2]
34  REAL, INTENT(OUT)  :: vmr_co2_gcm_phys(ngrid,timelen) ! Physics x Times  co2 volume mixing ratio retrieve from the gcm [m^3/m^3]
35  REAL, INTENT(OUT) ::  ps_timeseries(ngrid,timelen)! Surface Pressure [Pa]
36  REAL, INTENT(OUT) ::  q_co2(ngrid,timelen)        ! CO2 mass mixing ratio in the first layer [kg/m^3]
37  REAL, INTENT(OUT) ::  q_h2o(ngrid,timelen)        ! H2O mass mixing ratio in the first layer [kg/m^3]
38  REAL, INTENT(OUT) ::  co2_ice_slope(ngrid,nslope,timelen) ! co2 ice amount per  slope of the year [kg/m^2]
39!SOIL
40  REAL, INTENT(OUT) ::  tsurf_ave(ngrid,nslope)         ! Average surface temperature of the concatenated file [K]
41  REAL, INTENT(OUT) ::  tsoil_ave(ngrid,nsoilmx,nslope) ! Average soil temperature of the concatenated file [K]
42  REAL ,INTENT(OUT) ::  tsurf_gcm(ngrid,nslope,timelen)                  ! Surface temperature of the concatenated file, time series [K]
43  REAL , INTENT(OUT) ::  tsoil_gcm(ngrid,nsoilmx,nslope,timelen)         ! Soil temperature of the concatenated file, time series [K]
44  REAL , INTENT(OUT) ::  watersurf_density_ave(ngrid,nslope)             ! Water density at the surface [kg/m^3]
45  REAL , INTENT(OUT) ::  watersoil_density(ngrid,nsoilmx,nslope,timelen) ! Water density in the soil layer, time series [kg/m^3]
46!===============================================================================
47!   Local Variables
48  CHARACTER(LEN=256) :: msg, var, modname               ! for reading
49  INTEGER :: iq, fID, vID, idecal                       ! for reading
50  INTEGER :: ierr                                       ! for reading
51  CHARACTER(len=12) :: start_file_type="earth" ! default start file type
52
53  REAL,ALLOCATABLE :: time(:) ! times stored in start
54  INTEGER :: indextime ! index of selected time
55
56  INTEGER :: edges(4),corner(4)
57  INTEGER :: i,j,l,t                                                   ! loop variables
58  real  ::  A , B, mmean                                           ! Molar Mass of co2 and no co2, A;B intermediate variables to compute the mean molar mass of the layer
59
60  INTEGER :: islope                                                    ! loop for variables
61  CHARACTER*2 :: num                                                   ! for reading sloped variables
62  REAL ::  h2o_ice_s_dyn(iim_input+1,jjm_input+1,nslope,timelen)       ! h2o ice per slope of the concatenated file [kg/m^2]
63  REAL ::  watercap_slope(iim_input+1,jjm_input+1,nslope,timelen)
64  REAL ::  vmr_co2_gcm(iim_input+1,jjm_input+1,timelen)                ! CO2 volume mixing ratio in the first layer  [mol/m^3]
65  REAL ::  ps_GCM(iim_input+1,jjm_input+1,timelen)                     ! Surface Pressure [Pa]
66  REAL ::  min_co2_ice_dyn(iim_input+1,jjm_input+1,nslope)
67  REAL ::  min_h2o_ice_dyn(iim_input+1,jjm_input+1,nslope)
68  REAL ::  tsurf_ave_dyn(iim_input+1,jjm_input+1,nslope)               ! Average surface temperature of the concatenated file [K]
69  REAL ::  tsoil_ave_dyn(iim_input+1,jjm_input+1,nsoilmx,nslope)       ! Average soil temperature of the concatenated file [K]
70  REAL ::  tsurf_gcm_dyn(iim_input+1,jjm_input+1,nslope,timelen)       ! Surface temperature of the concatenated file, time series [K]
71  REAL ::  tsoil_gcm_dyn(iim_input+1,jjm_input+1,nsoilmx,nslope,timelen)! Soil temperature of the concatenated file, time series [K]
72  REAL ::  q_co2_dyn(iim_input+1,jjm_input+1,timelen)                  ! CO2 mass mixing ratio in the first layer [kg/m^3]
73  REAL ::  q_h2o_dyn(iim_input+1,jjm_input+1,timelen)                  ! H2O mass mixing ratio in the first layer [kg/m^3]
74  REAL ::  co2_ice_slope_dyn(iim_input+1,jjm_input+1,nslope,timelen)  ! co2 ice amount per  slope of the year [kg/m^2]
75  REAL ::  watersurf_density_dyn(iim_input+1,jjm_input+1,nslope,timelen)! Water density at the surface, time series [kg/m^3]
76  REAL ::  watersurf_density(ngrid,nslope,timelen)                     ! Water density at the surface, time series [kg/m^3]
77  REAL ::  watersoil_density_dyn(iim_input+1,jjm_input+1,nsoilmx,nslope,timelen) ! Water density in the soil layer, time series [kg/m^3]
78
79!-----------------------------------------------------------------------
80  modname="read_data_gcm"
81
82      A =(1/m_co2 - 1/m_noco2)
83      B=1/m_noco2
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 vmr co2..."
92
93  CALL get_var3("co2_cropped"   ,q_co2_dyn)
94
95     print *, "Downloading data for vmr co2 done"
96     print *, "Downloading data for vmr h20..."
97
98  CALL get_var3("h2o_cropped"   ,q_h2o_dyn)
99
100     print *, "Downloading data for vmr h2o done"
101     print *, "Downloading data for surface pressure ..."
102
103  CALL get_var3("ps"   ,ps_GCM)
104
105     print *, "Downloading data for surface pressure done"
106     print *, "nslope=", nslope
107     print *, "Downloading data for co2ice_slope ..."
108
109if(nslope.gt.1) then
110
111DO islope=1,nslope
112  write(num,fmt='(i2.2)') islope
113  call get_var3("co2ice_slope"//num,co2_ice_slope_dyn(:,:,islope,:))
114ENDDO
115
116     print *, "Downloading data for co2ice_slope done"
117     print *, "Downloading data for h2o_ice_s_slope ..."
118
119DO islope=1,nslope
120  write(num,fmt='(i2.2)') islope
121  call get_var3("h2o_ice_s_slope"//num,h2o_ice_s_dyn(:,:,islope,:))
122ENDDO
123
124     print *, "Downloading data for h2o_ice_s_slope done"
125
126     print *, "Downloading data for watercap_slope ..."
127DO islope=1,nslope
128       write(num,fmt='(i2.2)') islope
129       call get_var3("watercap_slope"//num,watercap_slope(:,:,islope,:))
130!        watercap_slope(:,:,:,:)= 0.
131ENDDO           
132     print *, "Downloading data for watercap_slope done"
133   
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_dyn(:,:,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_dyn(:,:,:,islope,:))
150ENDDO
151
152     print *, "Downloading data for tsoil_slope done"
153
154     print *, "Downloading data for watersoil_density ..."
155
156DO islope=1,nslope
157  write(num,fmt='(i2.2)') islope
158  call get_var4("Waterdensity_soil_slope"//num,watersoil_density_dyn(:,:,:,islope,:))
159ENDDO
160
161     print *, "Downloading data for  watersoil_density  done"
162
163     print *, "Downloading data for  watersurf_density  ..."
164
165DO islope=1,nslope
166  write(num,fmt='(i2.2)') islope
167  call get_var3("Waterdensity_surface"//num,watersurf_density_dyn(:,:,islope,:))
168ENDDO
169
170     print *, "Downloading data for  watersurf_density  done"
171
172  endif !soil_pem
173
174  else !nslope=1 no slope, we copy all the values
175
176    CALL get_var3("h2o_ice_s", h2o_ice_s_dyn(:,:,1,:))
177    CALL get_var3("co2ice", co2_ice_slope_dyn(:,:,1,:))
178    call get_var3("tsurf", tsurf_gcm_dyn(:,:,1,:))
179#ifndef CPP_STD
180    call get_var3("watercap", watercap_slope(:,:,1,:))
181#endif
182
183    if(soil_pem) then
184      call get_var4("tsoil",tsoil_gcm_dyn(:,:,:,1,:))
185    endif !soil_pem
186  endif !nslope=1
187
188! Compute the minimum over the year for each point
189  print *, "Computing the min of h2o_ice_slope"
190  min_h2o_ice_dyn(:,:,:)=minval(h2o_ice_s_dyn+watercap_slope,4)
191!  min_h2o_ice_dyn(:,:,:)=minval(h2o_ice_s_dyn,4)
192  print *, "Computing the min of co2_ice_slope"
193  min_co2_ice_dyn(:,:,:)=minval(co2_ice_slope_dyn,4)
194
195!Compute averages
196
197    print *, "Computing average of tsurf"
198    tsurf_ave_dyn(:,:,:)=SUM(tsurf_gcm_dyn(:,:,:,:),4)/timelen
199
200  DO islope = 1,nslope
201    DO t=1,timelen
202      CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,watersurf_density_dyn(:,:,islope,t),watersurf_density(:,islope,t))
203    ENDDO
204  ENDDO
205
206  if(soil_pem) then
207    print *, "Computing average of tsoil"
208    tsoil_ave_dyn(:,:,:,:)=SUM(tsoil_gcm_dyn(:,:,:,:,:),5)/timelen
209    print *, "Computing average of watersurf_density"
210    watersurf_density_ave(:,:) = SUM(watersurf_density(:,:,:),3)/timelen
211  endif
212
213! By definition, a density is positive, we get rid of the negative values
214  DO i=1,iim+1
215    DO j = 1, jjm+1
216       DO islope=1,nslope
217          if (min_co2_ice_dyn(i,j,islope).LT.0) then
218            min_co2_ice_dyn(i,j,islope)  = 0.
219          endif
220          if (min_h2o_ice_dyn(i,j,islope).LT.0) then
221            min_h2o_ice_dyn(i,j,islope)  = 0.
222          endif
223       ENDDO
224    ENDDO
225  ENDDO
226
227  DO i=1,iim+1
228    DO j = 1, jjm+1
229      DO t = 1, timelen
230         if (q_co2_dyn(i,j,t).LT.0) then
231              q_co2_dyn(i,j,t)=1E-10
232         elseif (q_co2_dyn(i,j,t).GT.1) then
233              q_co2_dyn(i,j,t)=1.
234         endif
235         if (q_h2o_dyn(i,j,t).LT.0) then
236              q_h2o_dyn(i,j,t)=1E-30
237         elseif (q_h2o_dyn(i,j,t).GT.1) then
238              q_h2o_dyn(i,j,t)=1.
239         endif
240         mmean=1/(A*q_co2_dyn(i,j,t) +B)
241         vmr_co2_gcm(i,j,t) = q_co2_dyn(i,j,t)*mmean/m_co2
242      ENDDO
243    ENDDO
244  ENDDO
245
246     CALL gr_dyn_fi(timelen,iim_input+1,jjm_input+1,ngrid,vmr_co2_gcm,vmr_co2_gcm_phys)
247     call gr_dyn_fi(timelen,iim_input+1,jjm_input+1,ngrid,ps_GCM,ps_timeseries)
248     CALL gr_dyn_fi(timelen,iim_input+1,jjm_input+1,ngrid,q_co2_dyn,q_co2)
249     CALL gr_dyn_fi(timelen,iim_input+1,jjm_input+1,ngrid,q_h2o_dyn,q_h2o)
250
251     DO islope = 1,nslope
252       CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,min_co2_ice_dyn(:,:,islope),min_co2_ice(:,islope))
253       CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,min_h2o_ice_dyn(:,:,islope),min_h2o_ice(:,islope))
254       if(soil_pem) then
255       DO l=1,nsoilmx
256         CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,tsoil_ave_dyn(:,:,l,islope),tsoil_ave(:,l,islope))
257         DO t=1,timelen
258           CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,tsoil_gcm_dyn(:,:,l,islope,t),tsoil_gcm(:,l,islope,t))
259           CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,watersoil_density_dyn(:,:,l,islope,t),watersoil_density(:,l,islope,t))
260         ENDDO
261       ENDDO
262       endif !soil_pem
263       DO t=1,timelen
264         CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,tsurf_GCM_dyn(:,:,islope,t),tsurf_GCM(:,islope,t))
265         CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,co2_ice_slope_dyn(:,:,islope,t),co2_ice_slope(:,islope,t))
266       ENDDO
267     ENDDO
268
269     CALL gr_dyn_fi(nslope,iim_input+1,jjm_input+1,ngrid,tsurf_ave_dyn,tsurf_ave)
270
271  CONTAINS
272
273SUBROUTINE check_dim(n1,n2,str1,str2)
274  INTEGER,          INTENT(IN) :: n1, n2
275  CHARACTER(LEN=*), INTENT(IN) :: str1, str2
276  CHARACTER(LEN=256) :: s1, s2
277  IF(n1/=n2) THEN
278    s1='value of '//TRIM(str1)//' ='
279    s2=' read in starting file differs from parametrized '//TRIM(str2)//' ='
280    WRITE(msg,'(10x,a,i4,2x,a,i4)')TRIM(s1),n1,TRIM(s2),n2
281    CALL ABORT_gcm(TRIM(modname),TRIM(msg),1)
282  END IF
283END SUBROUTINE check_dim
284
285
286SUBROUTINE get_var1(var,v)
287  CHARACTER(LEN=*), INTENT(IN)  :: var
288  REAL,             INTENT(OUT) :: v(:)
289  CALL err(NF90_INQ_VARID(fID,var,vID),"inq",var)
290  CALL err(NF90_GET_VAR(fID,vID,v),"get",var)
291END SUBROUTINE get_var1
292
293
294SUBROUTINE get_var3(var,v) ! on U grid
295  CHARACTER(LEN=*), INTENT(IN)  :: var
296  REAL,             INTENT(OUT) :: v(:,:,:)
297  CALL err(NF90_INQ_VARID(fID,var,vID),"inq",var)
298  CALL err(NF90_GET_VAR(fID,vID,v),"get",var)
299
300END SUBROUTINE get_var3
301
302SUBROUTINE get_var4(var,v)
303  CHARACTER(LEN=*), INTENT(IN)  :: var
304  REAL,             INTENT(OUT) :: v(:,:,:,:)
305  CALL err(NF90_INQ_VARID(fID,var,vID),"inq",var)
306  CALL err(NF90_GET_VAR(fID,vID,v),"get",var)
307END SUBROUTINE get_var4
308
309SUBROUTINE err(ierr,typ,nam)
310  INTEGER,          INTENT(IN) :: ierr   !--- NetCDF ERROR CODE
311  CHARACTER(LEN=*), INTENT(IN) :: typ    !--- TYPE OF OPERATION
312  CHARACTER(LEN=*), INTENT(IN) :: nam    !--- FIELD/FILE NAME
313  IF(ierr==NF90_NoERR) RETURN
314  SELECT CASE(typ)
315    CASE('inq');   msg="Field <"//TRIM(nam)//"> is missing"
316    CASE('get');   msg="Reading failed for <"//TRIM(nam)//">"
317    CASE('open');  msg="File opening failed for <"//TRIM(nam)//">"
318    CASE('close'); msg="File closing failed for <"//TRIM(nam)//">"
319  END SELECT
320  CALL ABORT_gcm(TRIM(modname),TRIM(msg),ierr)
321END SUBROUTINE err
322
323END SUBROUTINE read_data_gcm
Note: See TracBrowser for help on using the repository browser.