source: branches/publications/ORCHIDEE_GLUC_r6545/src_stomate/stomate_io_carbon_permafrost.f90 @ 6737

Last change on this file since 6737 was 4651, checked in by albert.jornet, 7 years ago

Clean: delete debug message from CH4
Clean: all Orchidee MPI references must point to MPI_COMM_ORCH instead of MPI_COMM_WORLD

File size: 21.4 KB
Line 
1!< $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/branches/ORCHIDEE-MICT/ORCHIDEE/src_stomate/stomate_io.f90 $
2!< $Date: 2016-06-17 13:26:43 +0200 (Fri, 17 Jun 2016) $
3!< $Author: albert.jornet $
4!< $Revision: 3564 $
5! IPSL (2006)
6!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
7!
8MODULE stomate_io_carbon_permafrost
9  !---------------------------------------------------------------------
10  !-
11  !-
12  !-
13  !---------------------------------------------------------------------
14  USE netcdf
15  USE defprec
16  USE stomate_data
17  USE constantes
18  USE constantes_soil
19  USE mod_orchidee_para
20  USE ioipsl_para 
21  USE utils      ! nccheck
22#ifdef CPP_PARA
23  USE mpi
24#endif
25  !-
26  IMPLICIT NONE
27  !-
28  PRIVATE
29  PUBLIC stomate_io_carbon_permafrost_write, stomate_io_carbon_permafrost_read
30  !-
31  ! TO CHECK, stomate_finalize also uses this type of var
32  INTEGER,PARAMETER                              :: r_typ = NF90_REAL8   !! Specify data format (server dependent)
33  !-
34CONTAINS
35  !-
36  !===
37  !-
38  !! ================================================================================================================================
39  !! SUBROUTINE         : stomate_io_carbon_permafrost_write
40  !!
41  !>\BRIEF        Writes stomate permafrost carbon data into a netcdf file
42  !!
43  !! DESCRIPTION  : It writes into a netcdf files in parallel mode all necessary
44  !!                 variables required for spinup (forecesoil)
45  !!               
46  !!               
47  !! \n
48  !_ ================================================================================================================================
49  SUBROUTINE stomate_io_carbon_permafrost_write (Cforcing_permafrost_name, & 
50                        nbp_glo,            start_px,           length_px,      nparan,     nbyear, &
51                        index_g,            zz_deep,            zz_coef_deep, &
52                        clay,               depth_organic_soil, lalo, &
53                        snowdz_2pfcforcing, snowrho_2pfcforcing, soilcarbon_input_2pfcforcing, &
54                        tsurf_2pfcforcing,  pb_2pfcforcing,     snow_2pfcforcing, &
55                        tprof_2pfcforcing,  fbact_2pfcforcing,  veget_max_2pfcforcing, &
56                        rprof_2pfcforcing,  hslong_2pfcforcing )
57   
58   
59
60
61    CHARACTER(LEN=100), INTENT(in)              :: Cforcing_permafrost_name !! Name of permafrost forcing file
62    INTEGER(i_std), INTENT(in)                  :: nbp_glo !nbp_glo is the number of global continental points
63    INTEGER(i_std), INTENT(in)                  :: start_px ! Start land point/pixex respect to nbp_glo
64    INTEGER(i_std), INTENT(in)                  :: length_px ! Length of lands point/pixel to write
65    INTEGER(i_std), INTENT(in)                  :: nparan ! Number of forcesoil timesteps 
66    INTEGER(i_std), INTENT(in)                  :: nbyear ! Number of years saved for carbon spinup
67    INTEGER(i_std),DIMENSION(:),INTENT(in)      :: index_g             !! Indices of the terrestrial pixels only (unitless)
68    REAL(r_std), DIMENSION(:),   INTENT (in)    :: zz_deep           !! deep vertical profile
69    REAL(r_std), DIMENSION(:),   INTENT (in)    :: zz_coef_deep      !! deep vertical profile
70    REAL(r_std), DIMENSION(:), INTENT(in)       :: clay                   !! Clay fraction of soil (0-1, unitless), parallel
71    REAL(r_std), DIMENSION(:),   INTENT (in)    :: depth_organic_soil !! how deep is the organic soil?
72    REAL(r_std), DIMENSION(:,:),INTENT(in)      :: lalo              !! Geographical coordinates (latitude,longitude)
73    REAL(r_std),DIMENSION(:,:,:), INTENT(in)    :: snowdz_2pfcforcing
74    REAL(r_std),DIMENSION(:,:,:), INTENT(in)    :: snowrho_2pfcforcing
75    REAL(r_std),DIMENSION(:,:,:,:), INTENT(in)  :: soilcarbon_input_2pfcforcing
76    REAL(r_std),DIMENSION(:,:), INTENT(in )     :: tsurf_2pfcforcing
77    REAL(r_std),DIMENSION(:,:), INTENT(in)      :: pb_2pfcforcing
78    REAL(r_std),DIMENSION(:,:), INTENT(in)      :: snow_2pfcforcing
79    REAL(r_std),DIMENSION(:,:,:,:), INTENT(in)  :: tprof_2pfcforcing
80    REAL(r_std),DIMENSION(:,:,:,:), INTENT(in)  :: fbact_2pfcforcing
81    REAL(r_std),DIMENSION(:,:,:,:), INTENT(in)  :: hslong_2pfcforcing
82    REAL(r_std),DIMENSION(:,:,:), INTENT(in)    :: veget_max_2pfcforcing
83    REAL(r_std),DIMENSION(:,:,:), INTENT(in)    :: rprof_2pfcforcing
84   
85    ! Local Variables
86    INTEGER(i_std)                              :: ier, n_directions, i
87    INTEGER(i_std)                              :: start(1), ncount(1), start_2d(2), ncount_2d(2), inival, endval 
88    INTEGER(i_std)                              :: start_4d(4), ncount_4d(4), start_3d(3), ncount_3d(3)
89    INTEGER(i_std),DIMENSION(10)                :: d_id                     !! List each netcdf dimension
90    INTEGER(i_std)                              :: vid                      !! Variable identifer of netCDF (unitless)
91    INTEGER(i_std)                              :: Cforcing_permafrost_id   !! Permafrost file identifer
92   
93    ! Create file
94#ifdef CPP_PARA
95    ier = NF90_CREATE (TRIM(Cforcing_permafrost_name),IOR(NF90_NETCDF4,NF90_MPIIO), &
96            Cforcing_permafrost_id, comm=MPI_COMM_ORCH, info=MPI_INFO_NULL)
97#else
98    ier = NF90_CREATE (TRIM(Cforcing_permafrost_name),NF90_NETCDF4, &
99            Cforcing_permafrost_id)
100#endif
101    IF (ier /= NF90_NOERR) THEN
102        CALL ipslerr_p (3,'stomate_finalize', &
103             &        'PROBLEM creating Cforcing_permafrost file', &
104             &        NF90_STRERROR(ier),'')
105     END IF
106
107
108     ! Add variable attribute
109     ! Note ::nbp_glo is the number of global continental points
110     CALL nccheck( NF90_PUT_ATT (Cforcing_permafrost_id,NF90_GLOBAL, &
111          &                           'kjpindex',REAL(nbp_glo,r_std)))
112     CALL nccheck( NF90_PUT_ATT (Cforcing_permafrost_id,NF90_GLOBAL, &
113          &                           'nparan',REAL(nparan,r_std)))
114     CALL nccheck( NF90_PUT_ATT (Cforcing_permafrost_id,NF90_GLOBAL, &
115          &                           'nbyear',REAL(nbyear,r_std)))
116
117     ! Add new dimension, variables values from USE
118     CALL nccheck( NF90_DEF_DIM (Cforcing_permafrost_id,'points',nbp_glo,d_id(1)))
119     CALL nccheck( NF90_DEF_DIM (Cforcing_permafrost_id,'carbtype',ncarb,d_id(2)))
120     CALL nccheck( NF90_DEF_DIM (Cforcing_permafrost_id,'vegtype',nvm,d_id(3)))
121     CALL nccheck( NF90_DEF_DIM (Cforcing_permafrost_id,'level',ndeep,d_id(4)))
122     CALL nccheck( NF90_DEF_DIM (Cforcing_permafrost_id,'time_step',NF90_UNLIMITED,d_id(5)))
123     n_directions=2
124     CALL nccheck( NF90_DEF_DIM (Cforcing_permafrost_id,'direction',n_directions,d_id(6)))
125
126
127     ! Add new variable
128     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'points', r_typ,d_id(1),vid))
129     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'carbtype', r_typ,d_id(2),vid))
130     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'vegtype', r_typ,d_id(3),vid))
131     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'level', r_typ,d_id(4),vid))
132     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'time_step',r_typ,d_id(5),vid))
133     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'direction',r_typ,d_id(6),vid))
134     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'index',r_typ,d_id(1),vid))
135     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'clay',r_typ,d_id(1),vid))
136     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'lalo',      r_typ, &
137          (/ d_id(1), d_id(6) /),vid))
138     !--time-invariant
139     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'zz_deep',r_typ,d_id(4),vid))
140     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'zz_coef_deep',r_typ,d_id(4),vid))
141     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'z_organic',r_typ,d_id(1),vid))
142     !--3layers snow
143     CALL nccheck( NF90_DEF_VAR(Cforcing_permafrost_id,'snowdz',r_typ,(/ d_id(1),d_id(2),d_id(5) /),vid))
144     CALL nccheck( NF90_DEF_VAR(Cforcing_permafrost_id,'snowrho',r_typ,(/ d_id(1),d_id(2),d_id(5) /),vid))
145     !--time-varying
146     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'soilcarbon_input',r_typ, &
147          &                        (/ d_id(1),d_id(2),d_id(3),d_id(5) /),vid))
148     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'pb',r_typ, & 
149          &                        (/ d_id(1),d_id(5) /),vid))
150     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'snow',r_typ, &
151          &                        (/ d_id(1),d_id(5) /),vid))
152     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'tprof',r_typ, &
153          &                        (/ d_id(1),d_id(4),d_id(3),d_id(5) /),vid))
154     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'fbact',r_typ, &
155          &                        (/ d_id(1),d_id(4),d_id(3),d_id(5) /),vid))
156     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'hslong',r_typ, &
157          &                        (/ d_id(1),d_id(4),d_id(3),d_id(5) /),vid))
158     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'veget_max',r_typ, &
159          &                        (/ d_id(1),d_id(3),d_id(5) /),vid))
160     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'rprof',r_typ, &
161          &                        (/ d_id(1),d_id(3),d_id(5) /),vid))
162     CALL nccheck( NF90_DEF_VAR (Cforcing_permafrost_id,'tsurf',r_typ, &
163          &                        (/ d_id(1),d_id(5) /),vid))
164     CALL nccheck( NF90_ENDDEF (Cforcing_permafrost_id))
165
166     ! Write data
167     start=(/ start_px /)
168     ncount=(/ length_px /)
169     inival=start_px
170     endval=start_px + length_px !length_px_end(mpi_rank)
171     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'points',vid) )
172     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
173     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, &
174          &  (/(REAL(i,r_std),i=inival,endval)/), &
175          &  start=start, count=ncount) )
176
177     ! no point to make parallel calls
178     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'carbtype',vid))
179     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
180     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, &
181          &                        (/(REAL(i,r_std),i=1,ncarb)/)))
182     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'vegtype',vid))
183     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
184     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, &
185          &                            (/(REAL(i,r_std),i=1,nvm)/)))
186     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'level',vid))
187     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
188     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, &
189          &                        (/(REAL(i,r_std),i=1,ndeep)/)))
190     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'time_step',vid))
191     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
192     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, &
193          &                       (/(REAL(i,r_std),i=1,nparan*nbyear)/)))
194     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'index',vid))
195     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
196     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, REAL(index_g,r_std) ))
197
198     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'zz_deep',vid))
199     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
200     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, zz_deep ))
201
202     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'zz_coef_deep',vid))
203     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
204     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, zz_coef_deep ))
205
206     ! Parallel writes
207     start=(/ start_px /)
208     ncount=(/ length_px /)
209     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'clay',vid))
210     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
211     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, clay, start=start, count=ncount  ))
212
213     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'z_organic',vid))
214     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
215     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid,depth_organic_soil, start=start, count=ncount))
216
217     start_2d=(/ start_px,1 /)
218     ncount_2d=(/ length_px,2 /)
219     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'lalo',vid))
220     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
221     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, lalo, start=start_2d, count=ncount_2d ))
222
223     ! putting 3 snow layers
224     start_3d=(/ start_px,1,1 /)
225     ncount_3d=(/ length_px,nsnow,nparan*nbyear /)
226     CALL nccheck( NF90_INQ_VARID(Cforcing_permafrost_id,'snowdz',vid))
227     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
228     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, snowdz_2pfcforcing, start=start_3d ,count=ncount_3d ))
229
230     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'snowrho',vid))
231     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
232     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, snowrho_2pfcforcing, &
233                    start=start_3d ,count=ncount_3d ))
234
235     start_4d=(/ start_px,1,1,1 /)
236     ncount_4d=(/ length_px,ncarb,nvm,nparan*nbyear /)
237     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'soilcarbon_input',vid))
238     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
239     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid,soilcarbon_input_2pfcforcing, &
240                    start=start_4d ,count=ncount_4d ))
241
242     start_2d=(/ start_px,1 /)
243     ncount_2d=(/ length_px,nparan*nbyear /)
244     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'tsurf',vid))
245     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
246     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, tsurf_2pfcforcing, start=start_2d, count=ncount_2d ))
247
248     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'pb',vid))
249     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
250     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, pb_2pfcforcing, start=start_2d, count=ncount_2d ))
251
252     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'snow',vid))
253     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
254     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, snow_2pfcforcing, start=start_2d, count=ncount_2d ))
255
256     start_4d=(/ start_px,1,1,1 /)
257     ncount_4d=(/ length_px,ndeep,nvm,nparan*nbyear /)
258     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'tprof',vid))
259     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
260     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, tprof_2pfcforcing ,start=start_4d, count=ncount_4d))
261
262     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'fbact',vid))
263     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
264     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, fbact_2pfcforcing,start=start_4d, count=ncount_4d ))
265
266     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'hslong',vid))
267     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
268     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, hslong_2pfcforcing,start=start_4d, count=ncount_4d ))
269
270     start_3d=(/ start_px,1,1 /)
271     ncount_3d=(/ length_px,nvm,nparan*nbyear /)
272     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'veget_max',vid))
273     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
274     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid,veget_max_2pfcforcing, start=start_3d, count=ncount_3d ))
275
276     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'rprof',vid))
277     CALL nccheck( NF90_VAR_PAR_ACCESS(Cforcing_permafrost_id, vid, NF90_COLLECTIVE))
278     CALL nccheck( NF90_PUT_VAR (Cforcing_permafrost_id,vid, rprof_2pfcforcing, start=start_3d, count=ncount_3d ))
279
280     ! Finish netcdf file management
281     CALL nccheck( NF90_CLOSE (Cforcing_permafrost_id) )
282
283  END SUBROUTINE stomate_io_carbon_permafrost_write
284  !-
285  !===
286  !-
287  SUBROUTINE stomate_io_carbon_permafrost_read (Cforcing_permafrost_name,   &
288                nparan,             nbyear,     start_px,   length_px,      &
289                soilcarbon_input,   pb,         snow,       tsurf,          & 
290                tprof,              fbact,      hslong,     rprof,          &
291                lalo,               snowdz,     snowrho,    veget_max )
292
293     ! Input Variables
294     CHARACTER(LEN=100), INTENT(in)               :: Cforcing_permafrost_name !! Name of permafrost forcing file
295     INTEGER(i_std), INTENT(in)                   :: start_px ! Start land point/pixex respect to nbp_glo
296     INTEGER(i_std), INTENT(in)                   :: length_px ! Length of lands point/pixel to write
297     INTEGER(i_std), INTENT(in)                   :: nparan, nbyear 
298
299     ! Output variables
300     REAL(r_std), DIMENSION(:,:,:,:), INTENT(out) :: soilcarbon_input
301     REAL(r_std), DIMENSION(:,:), INTENT(out)     :: pb 
302     REAL(r_std), DIMENSION(:,:), INTENT(out)     :: snow
303     REAL(r_std), DIMENSION(:,:), INTENT(out)     :: tsurf
304     REAL(r_std), DIMENSION(:,:,:,:), INTENT(out) :: tprof
305     REAL(r_std), DIMENSION(:,:,:,:), INTENT(out) :: fbact 
306     REAL(r_std), DIMENSION(:,:,:,:), INTENT(out) :: hslong
307     REAL(r_std), DIMENSION(:,:,:), INTENT(out)   :: rprof
308     REAL(r_std), DIMENSION(:,:), INTENT(out)     :: lalo
309     REAL(r_std), DIMENSION(:,:,:), INTENT(out)   :: snowdz
310     REAL(r_std), DIMENSION(:,:,:), INTENT(out)   :: snowrho 
311     REAL(r_std), DIMENSION(:,:,:), INTENT(out)   :: veget_max 
312
313     ! Local Variables
314     INTEGER(i_std)                               :: start_2d(2), count_2d(2) 
315     INTEGER(i_std)                               :: start_4d(4), count_4d(4), start_3d(3), count_3d(3)
316     INTEGER(i_std)                               :: v_id                      !! Variable identifer of netCDF (unitless)
317     INTEGER(i_std)                               :: Cforcing_permafrost_id   !! Permafrost file identifer
318     !-
319     ! Open FORCESOIL's forcing file to read some basic info (dimensions, variable ID's)
320     ! and allocate variables.
321     !-
322#ifdef CPP_PARA
323     CALL nccheck( NF90_OPEN (TRIM(Cforcing_permafrost_name),IOR(NF90_NOWRITE, NF90_MPIIO),Cforcing_permafrost_id, &
324                 & comm = MPI_COMM_ORCH, info = MPI_INFO_NULL ))
325#else
326     CALL nccheck( NF90_OPEN (TRIM(Cforcing_permafrost_name),NF90_NOWRITE,Cforcing_permafrost_id))
327#endif
328   
329     start_4d = (/ start_px, 1, 1, 1 /)
330     count_4d = (/ length_px, ncarb, nvm, nparan*nbyear /)
331     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'soilcarbon_input',v_id))
332     CALL nccheck( NF90_GET_VAR   (Cforcing_permafrost_id,v_id,soilcarbon_input,  &
333                    &  start = start_4d, count = count_4d ))
334
335     start_2d=(/ start_px, 1 /)
336     count_2d=(/ length_px, nparan*nbyear /)
337     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'pb',v_id ))
338     CALL nccheck( NF90_GET_VAR (Cforcing_permafrost_id,v_id,pb, &
339                & start=start_2d, count=count_2d))
340
341     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'snow',v_id))
342     CALL nccheck( NF90_GET_VAR (Cforcing_permafrost_id,v_id,snow, &
343                & start=start_2d, count=count_2d))
344
345     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'tsurf',v_id))
346     CALL nccheck( NF90_GET_VAR (Cforcing_permafrost_id,v_id,tsurf, &
347                & start=start_2d, count=count_2d))
348
349     start_4d=(/ start_px,1,1,1 /)
350     count_4d=(/ length_px,ndeep,nvm,nparan*nbyear /)
351     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'tprof',v_id))
352     CALL nccheck( NF90_GET_VAR (Cforcing_permafrost_id,v_id,tprof, &
353                & start=start_4d, count=count_4d))
354
355     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'fbact',v_id))
356     CALL nccheck( NF90_GET_VAR (Cforcing_permafrost_id,v_id,fbact, &
357                & start=start_4d, count=count_4d))
358
359     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'hslong',v_id))
360     CALL nccheck( NF90_GET_VAR (Cforcing_permafrost_id,v_id,hslong, &
361                & start=start_4d, count=count_4d))
362
363     start_3d=(/ start_px,1,1 /)
364     count_3d=(/ length_px,nvm,nparan*nbyear /)
365     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'veget_max',v_id))
366     CALL nccheck( NF90_GET_VAR (Cforcing_permafrost_id,v_id,veget_max, &
367                & start=start_3d, count=count_3d))
368
369     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'rprof',v_id))
370     CALL nccheck( NF90_GET_VAR (Cforcing_permafrost_id,v_id,rprof, &
371                & start=start_3d, count=count_3d))
372
373     start_2d=(/ start_px, 1 /)
374     count_2d=(/ length_px, 2 /)
375     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'lalo',v_id))
376     CALL nccheck( NF90_GET_VAR (Cforcing_permafrost_id,v_id,lalo, &
377                & start=start_2d, count=count_2d))
378
379     start_3d=(/ start_px,1,1 /)
380     count_3d=(/ length_px,nsnow,nparan*nbyear /)
381     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'snowdz',v_id))
382     CALL nccheck( NF90_GET_VAR (Cforcing_permafrost_id,v_id,snowdz, &
383                & start=start_3d, count=count_3d))
384
385     CALL nccheck( NF90_INQ_VARID (Cforcing_permafrost_id,'snowrho',v_id))
386     CALL nccheck( NF90_GET_VAR (Cforcing_permafrost_id,v_id,snowrho, &
387                & start=start_3d, count=count_3d))
388     !- Close Netcdf carbon permafrost file reference
389     CALL nccheck( NF90_CLOSE (Cforcing_permafrost_id))
390
391  END SUBROUTINE stomate_io_carbon_permafrost_read
392
393END MODULE stomate_io_carbon_permafrost
Note: See TracBrowser for help on using the repository browser.