source: branches/ORCHIDEE_3_CMIP6/ORCHIDEE/src_stomate/stomate_io_soil_carbon_discretization.f90 @ 8367

Last change on this file since 8367 was 6731, checked in by bertrand.guenet, 4 years ago

bug correction: missing variables in stomate_Cforcing

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