source: branches/ORCHIDEE_2_2/ORCHIDEE/src_parallel/xios_orchidee.f90 @ 7255

Last change on this file since 7255 was 7255, checked in by agnes.ducharne, 3 years ago

As done in trunk r6372: clean temp_hydro cf ticket #397.

  • Property svn:keywords set to Date Revision HeadURL
File size: 51.0 KB
Line 
1! ================================================================================================================================
2!  MODULE       : xios_orchidee
3!
4!  CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6!  LICENCE      : IPSL (2006)
7!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF   This module contains the initialization and interface to the XIOS code.
10!!
11!!\n DESCRIPTION: This module contains the interface for the use of the XIOS code. All call to XIOS are done in this module.
12!!                Revision 965 of XIOS/trunk or later is needed. This version is also called XIOS2.
13!!                Older revisions and XIOS1 can not be used.
14!!               
15!!                Summury of subroutines
16!!                      xios_orchidee_comm_init       : First call to XIOS to get the MPI communicator
17!!                      xios_orchidee_init            : Initialize variables needed for use of XIOS
18!!                                                      Deactivation of fields not calculated due specific run options
19!!                      xios_orchidee_update_calendar : Update the calandar in XIOS
20!!                      xios_orchidee_finalize        : Last call to XIOS for finalization
21!!                      xios_orchidee_send_field      : Interface to send fields with 1, 2 or 3 dimensions to XIOS
22!!                      xios_orchidee_send_field_r1d  : Internal subroutine for 1D(array) fields
23!!                      xios_orchidee_send_field_r2d  : Internal subroutine for 2D fields
24!!                      xios_orchidee_send_field_r3d  : Internal subroutine for 3D fields
25!!
26!!                It is only possible to use XIOS2. Note that compilation must be done with the preprocessing key XIOS
27!!                and CPP_PARA. Compiling without these keys makes it impossible to activate XIOS.
28!!                To activate running using XIOS, the flag XIOS_ORCHIDEE_OK=y must be set in run.def and the file iodef.xml must exist. 
29!!
30!! RECENT CHANGE(S): Created by Arnaud Caubel(LSCE), Josefine Ghattas (IPSL) 2013
31!!                   Removed possibility to use XIOS1, 21/10/2016
32!!
33!! REFERENCE(S) : None
34!!
35!! SVN          :
36!! $HeadURL$
37!! $Date$
38!! $Revision$
39!! \n
40!_ ================================================================================================================================
41
42MODULE xios_orchidee
43
44#ifdef XIOS
45  USE xios
46#endif
47  USE defprec
48  USE pft_parameters_var, ONLY : nvm
49  USE constantes_var
50  USE constantes_soil_var, ONLY : nstm, nscm, diaglev, check_cwrr, ok_freeze_cwrr
51  USE time, ONLY : dt_sechiba
52  USE vertical_soil_var, ONLY : ngrnd, nslm
53  USE IOIPSL, ONLY : ioget_calendar, ju2ymds
54  USE mod_orchidee_para_var
55  USE mod_orchidee_transfert_para
56  USE ioipsl_para
57
58  IMPLICIT NONE
59  PRIVATE
60  PUBLIC :: xios_orchidee_init, xios_orchidee_change_context, &
61            xios_orchidee_update_calendar, xios_orchidee_context_finalize, xios_orchidee_finalize, &
62            xios_orchidee_close_definition, &
63            xios_orchidee_send_field, xios_orchidee_recv_field, &
64            xios_orchidee_set_file_attr, xios_orchidee_set_field_attr, xios_orchidee_set_fieldgroup_attr, xios_orchidee_setvar
65
66
67  !
68  !! Declaration of public variables
69  !
70  LOGICAL, PUBLIC, SAVE           :: xios_orchidee_ok=.TRUE.     !! Use XIOS for diagnostic files
71  !$OMP THREADPRIVATE(xios_orchidee_ok)
72  LOGICAL, PUBLIC, SAVE           :: xios_interpolation          !! Do reading and interpolations with XIOS. If false, reading will be done with IOIOSL and interpolation using aggregate_p
73  !$OMP THREADPRIVATE(xios_interpolation)
74
75  REAL(r_std), PUBLIC, SAVE       :: xios_default_val=0          !! Default value (missing value) used in XIOS. The value 0 will be overwritten with the value taken from XIOS.
76  !$OMP THREADPRIVATE(xios_default_val)
77
78  !
79  !! Declaration of internal variables
80  !
81#ifdef XIOS
82  TYPE(xios_context)              :: ctx_hdl_orchidee      !! Handel for ORCHIDEE
83  !$OMP THREADPRIVATE(ctx_hdl_orchidee)
84#endif
85
86
87
88  !! ==============================================================================================================================
89  !! INTERFACE   : xios_orchidee_send_field
90  !!
91  !>\BRIEF         Send a field to XIOS.
92  !!
93  !! DESCRIPTION  :\n Send a field to XIOS. The field can have 1, 2 or 3 dimensions.
94  !!                  This interface should be called at each time-step for each output varaiables.
95  !!
96  !! \n
97  !_ ================================================================================================================================
98  INTERFACE xios_orchidee_send_field
99     MODULE PROCEDURE xios_orchidee_send_field_r1d, xios_orchidee_send_field_r2d, xios_orchidee_send_field_r3d, &
100                      xios_orchidee_send_field_r4d, xios_orchidee_send_field_r5d
101  END INTERFACE
102
103  INTERFACE xios_orchidee_recv_field
104     MODULE PROCEDURE xios_orchidee_recv_field_r1d, xios_orchidee_recv_field_r2d, xios_orchidee_recv_field_r3d
105  END INTERFACE
106
107
108CONTAINS
109
110
111  !! ==============================================================================================================================
112  !! SUBROUTINE   : xios_orchidee_init
113  !!
114  !>\BRIEF         Initialize variables needed for use of XIOS.
115  !!
116  !! DESCRIPTION  :\n Initialization of specific varaiables needed to use XIOS such as model domain and time step.
117  !!
118  !!                  In this subroutine also a section containg deactivation of some fields is found. The variables are
119  !!                  deactivated of not according to the corresponding control flag. For exemple the variables cacluated by the
120  !!                  routing scheme will be deactivated if the routing is deactivated. This is done to be able to keep the same
121  !!                  iodef.xml input file for several options without geting empty fields in the output file. Note that a field that
122  !!                  is activated in the code can always be deactivated from the iodef.xml external file.
123  !!
124  !! \n
125  !_ ================================================================================================================================
126  SUBROUTINE xios_orchidee_init(MPI_COMM_ORCH,                   &
127       date0,    year,      month,             day, julian_diff, &
128       lon_mpi,  lat_mpi,   soilth_lev )
129
130    USE grid, ONLY : grid_type, unstructured, regular_lonlat, regular_xy, nvertex, &
131                     longitude, latitude, bounds_lon, bounds_lat, ind_cell_glo
132    IMPLICIT NONE
133    !
134    !! 0. Variable and parameter declaration
135    !
136    !! 0.1 Input variables
137    !
138    INTEGER(i_std), INTENT(in)                            :: MPI_COMM_ORCH    !! Orchidee MPI communicator (from module mod_orchidee_mpi_data)
139    REAL(r_std), INTENT(in)                               :: date0            !! Julian day at first time step
140    INTEGER(i_std), INTENT(in)                            :: year, month, day !! Current date information
141    REAL(r_std), INTENT(in)                               :: julian_diff      !! Current day in the year [1,365(366)]
142    REAL(r_std),DIMENSION (iim_g,jj_nb), INTENT(in)       :: lon_mpi, lat_mpi !! Longitudes and latitudes on MPI local domain 2D domain
143    REAL(r_std),DIMENSION (ngrnd), INTENT(in)             :: soilth_lev       !! Vertical soil levels for thermal scheme (m)
144    !
145    !! 0.2 Local variables
146    !
147#ifdef XIOS
148
149    TYPE(xios_duration)            :: dtime_xios
150    TYPE(xios_date)                :: start_date
151    TYPE(xios_date)                :: time_origin
152    TYPE(xios_fieldgroup)          :: fieldgroup_handle
153    TYPE(xios_field)               :: field_handle
154    TYPE(xios_file)                :: file_handle
155#endif
156    INTEGER(i_std)                 :: i
157    INTEGER(i_std)                 :: year0, month0, day0 !! Time origin date information
158    REAL(r_std)                    :: sec0                !! Time origin date information
159    CHARACTER(LEN=20)              :: calendar_str        !! Name of current calendar
160    CHARACTER(LEN=30)              :: start_str           !! Current date as character string
161    CHARACTER(LEN=30)              :: startorig_str       !! Time origin date as character string
162
163    REAL(r_std),ALLOCATABLE        :: longitude_mpi(:), latitude_mpi(:)
164    REAL(r_std),ALLOCATABLE        :: bounds_lon_mpi(:,:),bounds_lat_mpi(:,:) 
165    INTEGER(i_std),ALLOCATABLE     :: ind_cell_mpi(:) 
166    LOGICAL                        :: xios_remap_output
167    !_ ================================================================================================================================
168   
169   
170    IF (printlev>=3) WRITE(numout,*) 'Entering xios_orchidee_init'
171
172    !Config Key   = XIOS_ORCHIDEE_OK
173    !Config Desc  = Use XIOS for writing diagnostics file
174    !Config If    =
175    !Config Def   = y
176    !Config Help  = Compiling and linking with XIOS library is necessary.
177    !Config Units = [FLAG]
178    CALL getin_p('XIOS_ORCHIDEE_OK',xios_orchidee_ok)
179    IF (printlev>=1) WRITE(numout,*)'In xios_orchidee_init, xios_orchidee_ok=',xios_orchidee_ok
180
181   
182    ! Coherence test between flag and preprocessing key
183#ifndef XIOS
184    IF (xios_orchidee_ok) THEN
185       CALL ipslerr_p(3,'xios_orchidee_init', 'Preprocessing key XIOS is missing to run ORCHIDEE with XIOS',&
186            'Recompile with preprocessing flag XIOS or set XIOS_ORCHIDEE_OK=n in run.def', '')
187    END IF
188#endif
189
190
191
192    IF (xios_orchidee_ok) THEN
193      !Config Key   = XIOS_INTERPOLATION
194      !Config Desc  = Actiave reading and intrepolation using XIOS
195      !Config If    = XIOS_ORCHIDEE_OK
196      !Config Def   = n
197      !Config Help  = This flag allows the user to decide to use xios
198      !Config         interpolation or standard method for reading input files
199      !Config Units = [FLAG]
200      xios_interpolation = .FALSE.
201      CALL getin_p('XIOS_INTERPOLATION', xios_interpolation)
202
203
204      !Config Key   = XIOS_REMAP_OUTPUT
205      !Config Desc  = Actiave remaping of diagnostic output files to regular grid
206      !Config If    = XIOS_ORCHIDEE_OK .AND. grid_type=unstructured
207      !Config Def   = True
208      !Config Help  = Set this flag to false to output an unstructured grid on its natvie grid without interpolation
209      !Config Units = [FLAG]
210      xios_remap_output=.TRUE.
211      CALL getin_p("XIOS_REMAP_OUTPUT",xios_remap_output) 
212
213   ELSE
214      ! Deactivate interpolation with XIOS not possible wihtout having
215      ! xios_orchidee_ok=true
216      xios_interpolation = .FALSE.
217   END IF
218
219   ! Force xios_interpolation=.TRUE. if using unstructured grid
220   IF (grid_type==unstructured .AND. .NOT. xios_interpolation) THEN
221      WRITE(numout,*) 'xios_interpolation must be true for unstructured grid. It is now changed to true.'
222      xios_interpolation=.TRUE.
223   END IF
224   IF (printlev>=1) WRITE(numout,*)'In xios_orchidee_init, xios_interpolation=', xios_interpolation
225
226
227    !
228    !! 1. Set date and calendar information on the format needed by XIOS
229    !
230
231    ! Get the calendar from IOIPSL and modify the string to correspond to what XIOS expects
232    CALL ioget_calendar(calendar_str)
233
234    IF (calendar_str == 'gregorian') THEN
235       calendar_str='gregorian'
236    ELSE IF (calendar_str == 'noleap') THEN
237       calendar_str='noleap'
238    ELSE IF (calendar_str == '360d') THEN
239       calendar_str='d360'
240    END IF
241
242    ! Transform the time origin from julian days into year, month, day and seconds
243    CALL ju2ymds(date0, year0, month0, day0, sec0)
244
245    IF (grid_type==unstructured) THEN
246      IF (is_omp_root) THEN
247        ALLOCATE(longitude_mpi(ij_nb))
248        ALLOCATE(latitude_mpi(ij_nb))
249        ALLOCATE(bounds_lon_mpi(ij_nb,nvertex))
250        ALLOCATE(bounds_lat_mpi(ij_nb,nvertex))
251        ALLOCATE(ind_cell_mpi(ij_nb))
252      ELSE
253        ALLOCATE(longitude_mpi(0))
254        ALLOCATE(latitude_mpi(0))
255        ALLOCATE(bounds_lon_mpi(0,0))
256        ALLOCATE(bounds_lat_mpi(0,0))
257        ALLOCATE(ind_cell_mpi(0))
258      ENDIF
259     
260      CALL gather_unindexed_omp(longitude,longitude_mpi)
261      CALL gather_unindexed_omp(latitude,latitude_mpi)
262      CALL gather_unindexed_omp(bounds_lon,bounds_lon_mpi)
263      CALL gather_unindexed_omp(bounds_lat,bounds_lat_mpi)
264      CALL gather_unindexed_omp(ind_cell_glo,ind_cell_mpi)
265    ENDIF
266   
267   
268    IF (xios_orchidee_ok .AND. is_omp_root) THEN
269#ifdef XIOS
270       !
271       !! 2. Context initialization
272       !
273       CALL xios_context_initialize("orchidee",MPI_COMM_ORCH)
274       CALL xios_get_handle("orchidee",ctx_hdl_orchidee)
275       CALL xios_set_current_context(ctx_hdl_orchidee)
276
277       !
278       !! 2. Calendar, timstep and date definition
279       !
280       dtime_xios%second=dt_sechiba
281
282       CALL xios_define_calendar(type=calendar_str, start_date=xios_date(year,month,day,0,0,0), &
283            time_origin=xios_date(year0,month0,day0,0,0,0), timestep=dtime_xios)
284
285       !
286       !! 3. Domain definition
287       !
288       IF (grid_type==regular_lonlat) THEN
289          ! Global domain
290          CALL xios_set_domain_attr("domain_landpoints", ni_glo=iim_g, nj_glo=jjm_g)
291          ! Local MPI domain
292          CALL xios_set_domain_attr("domain_landpoints",type="rectilinear", ibegin=0, ni=iim_g, jbegin=jj_begin-1, nj=jj_nb)
293         
294          ! Define how data is stored on memory : 1D array for only continental points
295          CALL xios_set_domain_attr("domain_landpoints",data_dim=1, data_ibegin=0, data_ni=nbp_mpi)
296          CALL xios_set_domain_attr("domain_landpoints",data_ni=nbp_mpi, data_i_index=kindex_mpi-1)     
297         
298          ! Define longitudes and latitudes on local MPI domain
299          CALL xios_set_domain_attr("domain_landpoints",lonvalue_1d=lon_mpi(:,1),latvalue_1d=lat_mpi(1,:))
300         
301       ELSE IF (grid_type==regular_xy ) THEN
302          ! Case not yet fully implemented
303          CALL ipslerr_p(3,'xios_orchidee_init', 'Implemention for grid_type=regular_xy is not finalized',&
304               'Initialization of the domain must be looked over in the code', '')
305
306! Following was done in previous version for case grid_type=regular_xy
307!         ! Local MPI domain
308!          CALL xios_set_domain_attr("domain_landpoints",type="curvilinear", ibegin=0, ni=iim_g, jbegin=jj_begin-1, nj=jj_nb)
309!
310!          ! Define how data is stored on memory : 1D array for only continental points
311!          CALL xios_set_domain_attr("domain_landpoints",data_dim=1, data_ibegin=0, data_ni=nbp_mpi)
312!          CALL xios_set_domain_attr("domain_landpoints",data_ni=nbp_mpi, data_i_index=kindex_mpi-1)     
313!
314!          ! Define longitudes and latitudes on local MPI domain depending on grid_type
315!          CALL xios_set_domain_attr("domain_landpoints",lonvalue_2d=lon_mpi,latvalue_2d=lat_mpi)
316
317       ELSE IF (grid_type==unstructured) THEN
318         
319          ! Global domain
320          CALL xios_set_domain_attr("domain_landpoints", ni_glo=jjm_g, type="unstructured", nvertex=nvertex)
321          ! Local MPI domain
322          CALL xios_set_domain_attr("domain_landpoints", ibegin=ij_begin-1, ni=ij_nb)
323         
324          ! Define how data is stored on memory : 1D array for only continental points
325          CALL xios_set_domain_attr("domain_landpoints",data_dim=1, data_ni=nbp_mpi, data_i_index=kindex_mpi-1) 
326         
327          ! Define longitudes and latitudes on local MPI domain
328          CALL xios_set_domain_attr("domain_landpoints",lonvalue_1d=longitude_mpi,latvalue_1d=latitude_mpi)
329          CALL xios_set_domain_attr("domain_landpoints",bounds_lon_1d=RESHAPE(bounds_lon_mpi,(/nvertex,ij_nb/),order=(/2,1/)))
330          CALL xios_set_domain_attr("domain_landpoints",bounds_lat_1d=RESHAPE(bounds_lat_mpi,(/nvertex,ij_nb/),order=(/2,1/)))
331
332
333          IF (xios_remap_output) THEN
334             
335             ! Define output grid as domain_landpoints_regular (grid specified in xml files)
336             CALL xios_set_domain_attr("domain_landpoints_out",domain_ref="domain_landpoints_regular")
337             
338             CALL xios_set_fieldgroup_attr("remap_expr",expr="@this_ref")
339             CALL xios_set_fieldgroup_attr("remap_1ts",   freq_op=xios_duration_convert_from_string("1ts"))
340             CALL xios_set_fieldgroup_attr("remap_1800s", freq_op=xios_duration_convert_from_string("1800s"))
341             CALL xios_set_fieldgroup_attr("remap_1h",    freq_op=xios_duration_convert_from_string("1h"))
342             CALL xios_set_fieldgroup_attr("remap_3h",    freq_op=xios_duration_convert_from_string("3h"))
343             CALL xios_set_fieldgroup_attr("remap_6h",    freq_op=xios_duration_convert_from_string("6h"))
344             CALL xios_set_fieldgroup_attr("remap_1d",    freq_op=xios_duration_convert_from_string("1d"))
345             CALL xios_set_fieldgroup_attr("remap_1mo",   freq_op=xios_duration_convert_from_string("1mo"))
346             CALL xios_set_fieldgroup_attr("remap_1y",    freq_op=xios_duration_convert_from_string("1y"))
347          ENDIF
348
349       END IF
350
351       !
352       !! 4. Axis definition
353       !
354       CALL xios_set_axis_attr("nvm",n_glo=nvm ,VALUE=(/(REAL(i,r_std),i=1,nvm)/))
355       CALL xios_set_axis_attr("nlut",n_glo=nlut ,VALUE=(/(REAL(i,r_std),i=1,nlut)/))
356       CALL xios_set_axis_attr("ncarb",n_glo=ncarb ,VALUE=(/(REAL(i,r_std),i=1,ncarb)/))
357       CALL xios_set_axis_attr("nparts",n_glo=nparts,VALUE=(/(REAL(i,r_std),i=1,nparts)/))
358       CALL xios_set_axis_attr("nlaip1", n_glo=nlai+1,VALUE=(/(REAL(i,r_std),i=1,nlai+1)/))
359       CALL xios_set_axis_attr("ngrnd",n_glo=ngrnd ,VALUE=soilth_lev(:))
360       CALL xios_set_axis_attr("nstm", n_glo=nstm,VALUE=(/(REAL(i,r_std),i=1,nstm)/))
361       CALL xios_set_axis_attr("ncsm", n_glo=nscm,VALUE=(/(REAL(i,r_std),i=1,nscm)/))
362       CALL xios_set_axis_attr("nnobio", n_glo=nnobio,VALUE=(/(REAL(i,r_std),i=1,nnobio)/))
363       CALL xios_set_axis_attr("albtyp", n_glo=2,VALUE=(/(REAL(i,r_std),i=1,2)/))
364       CALL xios_set_axis_attr("nslm", n_glo=nslm,VALUE=(/(REAL(i,r_std),i=1,nslm)/))
365       CALL xios_set_axis_attr("P10", n_glo=10,VALUE=(/(REAL(i,r_std), i=1,10)/))
366       CALL xios_set_axis_attr("P100", n_glo=100,VALUE=(/(REAL(i,r_std), i=1,100)/))
367       CALL xios_set_axis_attr("P11", n_glo=11,VALUE=(/(REAL(i,r_std), i=1,11)/))
368       CALL xios_set_axis_attr("P101", n_glo=101,VALUE=(/(REAL(i,r_std), i=1,101)/))
369       CALL xios_set_axis_attr("nsnow", n_glo=nsnow,VALUE=(/(REAL(i,r_std),i=1,nsnow)/))
370             
371       !
372       !! 5. Get the default value (missing value) used by XIOS. This value is set in field_def_orchidee.xml
373       !
374       CALL xios_get_fieldgroup_attr("field_definition", default_value=xios_default_val)
375       IF (printlev>=2) WRITE(numout,*) 'Default value read from XIOS, xios_default_val=',xios_default_val
376
377       !
378       !! 5. Deactivation of some fields if they are not calculated
379       !
380       IF ( OFF_LINE_MODE ) THEN
381          CALL xios_set_field_attr("riverflow_cpl",enabled=.FALSE.)
382          CALL xios_set_field_attr("coastalflow_cpl",enabled=.FALSE.)
383       END IF
384
385       IF ( .NOT. river_routing ) THEN
386          CALL xios_set_field_attr("basinmap",enabled=.FALSE.)
387          CALL xios_set_field_attr("nbrivers",enabled=.FALSE.)
388          CALL xios_set_field_attr("riversret",enabled=.FALSE.)
389          CALL xios_set_field_attr("hydrographs",enabled=.FALSE.)
390          CALL xios_set_field_attr("fastr",enabled=.FALSE.)
391          CALL xios_set_field_attr("slowr",enabled=.FALSE.)
392          CALL xios_set_field_attr("streamr",enabled=.FALSE.)
393          CALL xios_set_field_attr("laker",enabled=.FALSE.)
394          CALL xios_set_field_attr("lake_overflow",enabled=.FALSE.)
395          CALL xios_set_field_attr("mask_coast",enabled=.FALSE.)
396          CALL xios_set_field_attr("pondr",enabled=.FALSE.)
397          CALL xios_set_field_attr("floodr",enabled=.FALSE.)
398          CALL xios_set_field_attr("slowflow",enabled=.FALSE.)
399          CALL xios_set_field_attr("delfastr",enabled=.FALSE.)
400          CALL xios_set_field_attr("delslowr",enabled=.FALSE.)
401          CALL xios_set_field_attr("delstreamr",enabled=.FALSE.)
402          CALL xios_set_field_attr("dellaker",enabled=.FALSE.)
403          CALL xios_set_field_attr("delpondr",enabled=.FALSE.)
404          CALL xios_set_field_attr("delfloodr",enabled=.FALSE.)
405          CALL xios_set_field_attr("irrigmap",enabled=.FALSE.)
406          CALL xios_set_field_attr("swampmap",enabled=.FALSE.)
407          CALL xios_set_field_attr("wbr_stream",enabled=.FALSE.)
408          CALL xios_set_field_attr("wbr_fast",enabled=.FALSE.)
409          CALL xios_set_field_attr("wbr_slow",enabled=.FALSE.)
410          CALL xios_set_field_attr("wbr_lake",enabled=.FALSE.)
411          CALL xios_set_field_attr("reinfiltration",enabled=.FALSE.)
412          CALL xios_set_field_attr("irrigation",enabled=.FALSE.)
413          CALL xios_set_field_attr("netirrig",enabled=.FALSE.)
414          CALL xios_set_field_attr("SurfStor",enabled=.FALSE.)
415       END IF
416
417
418       IF (.NOT. ok_freeze_cwrr) THEN
419          CALL xios_set_field_attr("profil_froz_hydro",enabled=.FALSE.)
420       END IF
421
422       
423       IF (.NOT. check_cwrr) THEN
424          CALL xios_set_field_attr("check_infilt",enabled=.FALSE.)
425          CALL xios_set_field_attr("check_tr",enabled=.FALSE.)
426          CALL xios_set_field_attr("check_over",enabled=.FALSE.)
427          CALL xios_set_field_attr("check_under",enabled=.FALSE.)
428          CALL xios_set_field_attr("check_top",enabled=.FALSE.)
429          CALL xios_set_field_attr("qflux",enabled=.FALSE.)
430       END IF
431
432       IF ( .NOT. do_floodplains ) THEN
433          CALL xios_set_field_attr("floodmap",enabled=.FALSE.)
434          CALL xios_set_field_attr("floodh",enabled=.FALSE.)       
435          CALL xios_set_field_attr("floodout",enabled=.FALSE.)       
436       END IF
437
438       ! Deactivate some stomate fields.
439       ! These fields were traditionally added in sechiba_history.nc output file.
440       IF ( .NOT. ok_stomate ) THEN
441          CALL xios_set_field_attr("nee",enabled=.FALSE.)
442          CALL xios_set_field_attr("maint_resp",enabled=.FALSE.)
443          CALL xios_set_field_attr("hetero_resp",enabled=.FALSE.)
444          CALL xios_set_field_attr("growth_resp",enabled=.FALSE.)
445          CALL xios_set_field_attr("npp",enabled=.FALSE.)
446       END IF
447
448       IF ( .NOT. do_irrigation ) THEN
449          CALL xios_set_field_attr("irrigation",enabled=.FALSE.)
450          CALL xios_set_field_attr("netirrig",enabled=.FALSE.)
451          CALL xios_set_field_attr("irrigmap",enabled=.FALSE.)
452       END IF
453
454       IF ( .NOT. ok_bvoc)THEN
455          CALL xios_set_field_attr("PAR",enabled=.FALSE.)
456          CALL xios_set_field_attr("flx_fertil_no",enabled=.FALSE.)
457          CALL xios_set_field_attr("flx_iso",enabled=.FALSE.)
458          CALL xios_set_field_attr("flx_mono",enabled=.FALSE.)
459          CALL xios_set_field_attr("flx_ORVOC",enabled=.FALSE.)
460          CALL xios_set_field_attr("flx_MBO",enabled=.FALSE.)
461          CALL xios_set_field_attr("flx_methanol",enabled=.FALSE.)
462          CALL xios_set_field_attr("flx_acetone",enabled=.FALSE.)
463          CALL xios_set_field_attr("flx_acetal",enabled=.FALSE.)
464          CALL xios_set_field_attr("flx_formal",enabled=.FALSE.)
465          CALL xios_set_field_attr("flx_acetic",enabled=.FALSE.)
466          CALL xios_set_field_attr("flx_formic",enabled=.FALSE.)
467          CALL xios_set_field_attr("flx_no_soil",enabled=.FALSE.)
468          CALL xios_set_field_attr("flx_no",enabled=.FALSE.)
469          CALL xios_set_field_attr('flx_apinen'   ,enabled=.FALSE.)
470          CALL xios_set_field_attr('flx_bpinen'   ,enabled=.FALSE.)
471          CALL xios_set_field_attr('flx_limonen'  ,enabled=.FALSE.)
472          CALL xios_set_field_attr('flx_myrcen'   ,enabled=.FALSE.)
473          CALL xios_set_field_attr('flx_sabinen'  ,enabled=.FALSE.)
474          CALL xios_set_field_attr('flx_camphen'  ,enabled=.FALSE.)
475          CALL xios_set_field_attr('flx_3caren'   ,enabled=.FALSE.)
476          CALL xios_set_field_attr('flx_tbocimen' ,enabled=.FALSE.)
477          CALL xios_set_field_attr('flx_othermono',enabled=.FALSE.)
478          CALL xios_set_field_attr('flx_sesquiter',enabled=.FALSE.)
479          CALL xios_set_field_attr("CRF",enabled=.FALSE.)
480          CALL xios_set_field_attr("fco2",enabled=.FALSE.)
481       END IF
482
483       IF ( .NOT. ok_bvoc .OR. .NOT. ok_radcanopy ) THEN
484          CALL xios_set_field_attr("PARdf",enabled=.FALSE.)
485          CALL xios_set_field_attr("PARdr",enabled=.FALSE.)
486       END IF
487
488       IF ( .NOT. ok_bvoc .OR. .NOT. ok_radcanopy .OR. .NOT. ok_multilayer ) THEN
489          CALL xios_set_field_attr( 'PARsuntab',enabled=.FALSE.)
490          CALL xios_set_field_attr( 'PARshtab' ,enabled=.FALSE.)
491       END IF
492
493       IF ( .NOT. ok_bvoc .OR. .NOT. ok_radcanopy .OR. ok_multilayer ) THEN
494          CALL xios_set_field_attr("PARsun",enabled=.FALSE.)
495          CALL xios_set_field_attr("PARsh",enabled=.FALSE.)
496          CALL xios_set_field_attr("laisun",enabled=.FALSE.)
497          CALL xios_set_field_attr("laish",enabled=.FALSE.)
498       END IF
499
500       IF ( .NOT. ok_bvoc .OR. .NOT. ok_bbgfertil_Nox) THEN
501          CALL xios_set_field_attr("flx_co2_bbg_year",enabled=.FALSE.)
502       END IF
503
504       IF ( .NOT. ok_bvoc .OR. .NOT. ok_cropsfertil_Nox) THEN
505          CALL xios_set_field_attr("N_qt_WRICE_year",enabled=.FALSE.)
506          CALL xios_set_field_attr("N_qt_OTHER_year",enabled=.FALSE.)
507       END IF
508
509       ! Set record_offset for enable start in the middle of the year.
510       ! julian_diff is the day of the year where the current run start
511       IF (printlev>=3) WRITE(numout,*) 'In xios_orchidee_init, julian_diff, INT(julian_diff) =', &
512            julian_diff, INT(julian_diff)
513
514       IF (ok_nudge_mc .AND. nudge_interpol_with_xios) THEN
515          ! Activate the input file with id="nudge_moistc" specified in file_def_orchidee.xml.
516          ! The nudging file should be called nudge_moistc.nc (see name in the xml file) and is
517          ! supposed to contain daily values for the full year for the variable moistc.
518          CALL xios_set_file_attr("nudge_moistc",enabled=.TRUE.)
519          ! Set record_offset to start read at correct day in the nudging file.
520          CALL xios_set_file_attr("nudge_moistc",record_offset=INT(julian_diff))
521       ELSE
522          ! Deactivate input file for nudging of soil moisture
523          CALL xios_set_file_attr("nudge_moistc",enabled=.FALSE.)
524          ! Deactivate variables related to soil moisture nudgnig
525          CALL xios_set_field_attr("mask_moistc_interp",enabled=.FALSE.)
526          CALL xios_set_field_attr("moistc_interp",enabled=.FALSE.)
527
528          ! Deactivate output variables related to soil moisture nudging
529          CALL xios_set_field_attr("mc_read_current",enabled=.FALSE.)
530          CALL xios_set_field_attr("mc_read_prev",enabled=.FALSE.)
531          CALL xios_set_field_attr("mc_read_next",enabled=.FALSE.)
532          CALL xios_set_field_attr("mask_mc_interp_out",enabled=.FALSE.)
533       END IF
534       IF (.NOT. ok_nudge_mc ) CALL xios_set_field_attr("nudgincsm",enabled=.FALSE.)
535
536       IF (ok_nudge_snow .AND. nudge_interpol_with_xios) THEN
537          ! Activate the input file with id="nudge_snow" specified in file_def_orchidee.xml.
538          ! The nudging file should be called nudge_snow.nc (see name in the xml file) and is
539          ! supposed to contain daily values for the full year for the variables snowdz, snowtemp and snowrho.
540          CALL xios_set_file_attr("nudge_snow",enabled=.TRUE.)
541          ! Set record_offset to start read at correct day in the nudging file.
542          CALL xios_set_file_attr("nudge_snow",record_offset=INT(julian_diff))
543       ELSE
544          ! Deactivate input file for nudging of snow variables
545          CALL xios_set_file_attr("nudge_snow",enabled=.FALSE.)
546
547          ! Deactivate input variables related to snow nudging
548          CALL xios_set_field_attr("mask_snow_interp",enabled=.FALSE.)
549          CALL xios_set_field_attr("snowdz_interp",enabled=.FALSE.)
550          CALL xios_set_field_attr("snowrho_interp",enabled=.FALSE.)
551          CALL xios_set_field_attr("snowtemp_interp",enabled=.FALSE.)
552
553          ! Deactivate output variables related to snow nudging
554          CALL xios_set_field_attr("snowdz_read_current",enabled=.FALSE.)
555          CALL xios_set_field_attr("snowdz_read_prev",enabled=.FALSE.)
556          CALL xios_set_field_attr("snowdz_read_next",enabled=.FALSE.)
557          CALL xios_set_field_attr("snowrho_read_current",enabled=.FALSE.)
558          CALL xios_set_field_attr("snowrho_read_prev",enabled=.FALSE.)
559          CALL xios_set_field_attr("snowrho_read_next",enabled=.FALSE.)
560          CALL xios_set_field_attr("snowtemp_read_current",enabled=.FALSE.)
561          CALL xios_set_field_attr("snowtemp_read_prev",enabled=.FALSE.)
562          CALL xios_set_field_attr("snowtemp_read_next",enabled=.FALSE.)
563          CALL xios_set_field_attr("mask_snow_interp_out",enabled=.FALSE.)
564       END IF
565       IF (.NOT. ok_nudge_snow) CALL xios_set_field_attr("nudgincswe",enabled=.FALSE.)
566
567       IF (impaze) THEN
568          CALL xios_set_field_attr("soilalb_vis",enabled=.FALSE.)
569          CALL xios_set_field_attr("soilalb_nir",enabled=.FALSE.)
570          CALL xios_set_field_attr("vegalb_vis",enabled=.FALSE.)
571          CALL xios_set_field_attr("vegalb_nir",enabled=.FALSE.)
572       END IF
573
574       IF (.NOT. do_wood_harvest) THEN
575          CALL xios_set_field_attr("PROD10_HARVEST",enabled=.FALSE.)
576          CALL xios_set_field_attr("FLUX10_HARVEST",enabled=.FALSE.)
577          CALL xios_set_field_attr("PROD100_HARVEST",enabled=.FALSE.)
578          CALL xios_set_field_attr("FLUX100_HARVEST",enabled=.FALSE.)
579          CALL xios_set_field_attr("CONVFLUX_HARVEST",enabled=.FALSE.)
580          CALL xios_set_field_attr("CFLUX_PROD10_HARVEST",enabled=.FALSE.)
581          CALL xios_set_field_attr("CFLUX_PROD100_HARVEST",enabled=.FALSE.)
582          CALL xios_set_field_attr("WOOD_HARVEST",enabled=.FALSE.)
583          CALL xios_set_field_attr("WOOD_HARVEST_PFT",enabled=.FALSE.)
584       END IF
585
586
587#endif
588    END IF
589
590    IF (xios_orchidee_ok) THEN
591       ! Send variables to all OMP thredds
592       CALL bcast(xios_default_val)
593       CALL bcast(almaoutput)
594    END IF
595
596    IF (printlev>=3) WRITE(numout,*) 'End xios_orchidee_init'
597  END SUBROUTINE xios_orchidee_init
598
599
600  SUBROUTINE xios_orchidee_close_definition
601
602    IF (printlev >=4) WRITE(numout,*) 'Start xios_orchidee_close_definition'
603    IF (xios_orchidee_ok .AND. is_omp_root) THEN
604#ifdef XIOS
605
606       !
607       !! 6. Close context
608       !
609       CALL xios_close_context_definition()     
610
611       !
612       !! 7. Activate almaoutput if needed
613       !! Some extra calculations have to be done for the variables 
614       !! delsoilmoist, delintercept, delswe and soilwet.
615       !! Set almaoutput=true if at least one of these variables are defined in an output file.
616       !! If not, keep the initial value of almaoutput.
617       IF ( xios_field_is_active("delsoilmoist") .OR. xios_field_is_active("delintercept") .OR. &
618            xios_field_is_active("delswe")       .OR. xios_field_is_active("soilwet")      .OR. &
619            xios_field_is_active("twbr")) THEN
620
621          almaoutput=.TRUE.
622          IF (printlev >=3) WRITE(numout,*) 'The flag almaoutput has been activated in xios_orchidee_init'
623       END IF
624#endif
625    END IF
626
627    IF (xios_orchidee_ok) THEN
628       ! Send variables to all OMP thredds
629       CALL bcast(xios_default_val)
630       CALL bcast(almaoutput)
631    END IF
632    IF (printlev >=4) WRITE(numout,*) 'End xios_orchidee_close_definition'
633  END SUBROUTINE xios_orchidee_close_definition
634 
635 
636 
637  !! ==============================================================================================================================
638  !! SUBROUTINE   : xios_orchidee_change_context
639  !!
640  !>\BRIEF         Use this subroutine to switch between different context.
641  !!               This subroutine must be called when running in coupled mode at each time ORCHIDEE is called, in the
642  !!               begining and end of intersurf_gathered. First call is done after xios_orchidee_init is done.
643  !!
644  !! DESCRIPTION  :\n
645  !!                 
646  !! \n
647  !_ ================================================================================================================================
648  SUBROUTINE xios_orchidee_change_context(new_context)
649    !
650    !! 0. Variable and parameter declaration
651    !
652    !!    Input variable
653    CHARACTER(LEN=*),INTENT(IN)              :: new_context
654
655    !! Local variables
656#ifdef XIOS
657    TYPE(xios_context) :: ctx_hdl
658#endif
659    !_ ================================================================================================================================
660
661    IF (xios_orchidee_ok .AND. is_omp_root) THEN
662#ifdef XIOS
663       CALL xios_get_handle(new_context,ctx_hdl)
664       CALL xios_set_current_context(ctx_hdl)
665#endif
666    END IF
667   
668  END SUBROUTINE xios_orchidee_change_context
669
670  !! ==============================================================================================================================
671  !! SUBROUTINE   : xios_orchidee_update_calendar
672  !!
673  !>\BRIEF          Update the calandar in XIOS.
674  !!
675  !! DESCRIPTION  :\n Update the calendar in XIOS : let XIOS know that ORCHIDEE avanced one time-step.
676  !!                  This subroutine should be called in the beginning of each time-step. The first
677  !!                  time-step in a new execution should always start at 1. Therefore, first calculate
678  !!                  an offset that is substracted to the current time step in sechiba.
679  !!
680  !! \n
681  !_ ================================================================================================================================
682  SUBROUTINE xios_orchidee_update_calendar(itau_sechiba)
683    !
684    !! 0. Variable and parameter declaration
685    !
686    !! 0.1 Input variables
687    !
688    INTEGER(i_std), INTENT(IN) :: itau_sechiba    !! Current time step of the model
689    !
690    !! 0.2 Local variables
691    !
692    LOGICAL, SAVE         :: first=.TRUE.         !! Flag for first entering in subroutine
693    INTEGER(i_std), SAVE  :: offset               !! Offset to substract from itau_sechiba
694    INTEGER(i_std)        :: itau_xios            !! Current time step for XIOS
695
696    !_ ================================================================================================================================
697
698    IF (xios_orchidee_ok .AND. is_omp_root) THEN
699#ifdef XIOS
700       ! Calculate the offset
701       IF (first) THEN
702          offset=itau_sechiba-1
703          first=.FALSE.
704       END IF
705
706       ! Substract the offset to the current time step in sechiba
707       itau_xios=itau_sechiba-offset
708
709       ! Send the new time step to XIOS
710       IF (printlev>=3) WRITE(numout,*) 'xios_orchidee_update_calendar: itau_sechiba, itau_xios=',itau_sechiba,itau_xios
711       CALL xios_update_calendar(itau_xios)
712#endif
713    END IF
714  END SUBROUTINE xios_orchidee_update_calendar
715  !! ==============================================================================================================================
716  !! SUBROUTINE   : xios_orchidee_context_finalize
717  !!
718  !>\BRIEF         Finalize orchidee context.
719  !!
720  !! DESCRIPTION  :\n This subroutine finalizes the orchidee context without finalizing XIOS. In coupled mode, the atmospheric
721  !!                  modele must finalize XIOS. This subroutine is called in the end of the execution of ORCHIDEE only in
722  !!                  coupeld mode.
723  !!                 
724  !! \n
725  !_ ================================================================================================================================
726  SUBROUTINE xios_orchidee_context_finalize
727
728    !_ ================================================================================================================================
729
730    IF (xios_orchidee_ok .AND. is_omp_root) THEN
731       IF (printlev>=3) WRITE(numout,*) 'Entering xios_orchidee_context_finalize'
732#ifdef XIOS
733       CALL xios_context_finalize()
734#endif
735    END IF
736  END SUBROUTINE xios_orchidee_context_finalize
737
738
739  !! ==============================================================================================================================
740  !! SUBROUTINE   : xios_orchidee_finalize
741  !!
742  !>\BRIEF         Last call to XIOS for finalization.
743  !!
744  !! DESCRIPTION  :\n Last call to XIOS for finalization of the orchidee context and XIOS.
745  !!                  This subroutine is called only when ORCHIDEE is run in offline mode. In coupled mode it is the atmospheric
746  !!                  model that finalizes XIOS. In that case, the context orchidee must be finalized using the
747  !!                  subroutine xios_orchidee_context_finalize
748  !!                 
749  !! \n
750  !_ ================================================================================================================================
751  SUBROUTINE xios_orchidee_finalize
752
753    !_ ================================================================================================================================
754
755    IF (xios_orchidee_ok .AND. is_omp_root) THEN
756       IF (printlev>=3) WRITE(numout,*) 'Entering xios_orchidee_finalize'
757#ifdef XIOS
758       CALL xios_context_finalize()
759       CALL xios_finalize()
760#endif
761    END IF
762  END SUBROUTINE xios_orchidee_finalize
763
764
765  !! ==============================================================================================================================
766  !! SUBROUTINE   : xios_orchidee_send_field_r1d
767  !!
768  !>\BRIEF          Subroutine for sending 1D (array) fields to XIOS.
769  !!
770  !! DESCRIPTION  :\n Send one field to XIOS. This is the interface for 1D fields (array).
771  !!                  NB! This subroutine should not be called directly. Use interface xios_orchidee_send_field.
772  !!
773  !! \n
774  !_ ================================================================================================================================
775  SUBROUTINE xios_orchidee_send_field_r1d(field_id,field)
776    !
777    !! 0. Variable and parameter declaration
778    !
779    !! 0.1 Input variables
780    !
781    CHARACTER(len=*), INTENT(IN)          :: field_id
782    REAL(r_std), DIMENSION(:), INTENT(IN) :: field
783
784    !! 0.2 Local variables
785    REAL(r_std), DIMENSION(nbp_mpi) :: field_mpi
786
787    !_ ================================================================================================================================
788    IF (xios_orchidee_ok) THEN
789       IF (printlev>=4) WRITE(numout,*) 'Entering xios_orchidee_send_field_r1d, field_id=',field_id
790
791       ! Gather all omp domains on the mpi domains
792       CALL gather_omp(field, field_mpi)
793
794       ! All master threads send the field to XIOS
795       IF (is_omp_root) THEN
796#ifdef XIOS
797          CALL xios_send_field(field_id,field_mpi)
798#endif
799       END IF
800    END IF
801  END SUBROUTINE xios_orchidee_send_field_r1d
802
803
804  !! ==============================================================================================================================
805  !! SUBROUTINE   : xios_orchidee_send_field_r2d
806  !!
807  !>\BRIEF          Subroutine for sending 2D fields to XIOS.
808  !!
809  !! DESCRIPTION  :\n Send one field to XIOS. This is the interface for 2D fields.
810  !!                  NB! This subroutine should not be called directly. Use interface xios_orchidee_send_field.
811  !!
812  !! \n
813  !_ ================================================================================================================================
814  SUBROUTINE xios_orchidee_send_field_r2d(field_id,field)
815    !
816    !! 0. Variable and parameter declaration
817    !
818    !! 0.1 Input variables
819    !
820    CHARACTER(len=*), INTENT(IN)            :: field_id
821    REAL(r_std), DIMENSION(:,:), INTENT(IN) :: field
822
823    !! 0.2 Local variables
824    REAL(r_std), DIMENSION(nbp_mpi,size(field,2)) :: field_mpi
825
826    !_ ================================================================================================================================
827    IF (xios_orchidee_ok) THEN
828       IF (printlev>=4) WRITE(numout,*) 'Entering xios_orchidee_send_field_r2d, field_id=',field_id
829
830       ! Gather all omp domains on the mpi domains
831       CALL gather_omp(field, field_mpi)
832
833       ! All master threads send the field to XIOS
834       IF (is_omp_root) THEN
835#ifdef XIOS
836          CALL xios_send_field(field_id,field_mpi)
837#endif
838       END IF
839    END IF
840  END SUBROUTINE xios_orchidee_send_field_r2d
841
842
843  !! ==============================================================================================================================
844  !! SUBROUTINE   : xios_orchidee_send_field_r3d
845  !!
846  !>\BRIEF          Subroutine for sending 3D fields to XIOS.
847  !!
848  !! DESCRIPTION  :\n Send one field to XIOS. This is the interface for 3D fields.
849  !!                  NB! This subroutine should not be called directly. Use interface xios_orchidee_send_field.
850  !!
851  !! \n
852  !_ ================================================================================================================================
853  SUBROUTINE xios_orchidee_send_field_r3d(field_id,field)
854    !
855    !! 0. Variable and parameter declaration
856    !
857    !! 0.1 Input variables
858    !
859    CHARACTER(len=*), INTENT(IN)              :: field_id
860    REAL(r_std), DIMENSION(:,:,:), INTENT(IN) :: field
861
862    !! 0.2 Local variables
863    REAL(r_std), DIMENSION(nbp_mpi,size(field,2),size(field,3)) :: field_mpi
864
865    !_ ================================================================================================================================
866    IF (xios_orchidee_ok) THEN
867       IF (printlev>=4) WRITE(numout,*) 'Entering xios_orchidee_send_field_r3d, field_id=',field_id
868
869       ! Gather all omp domains on the mpi domains
870       CALL gather_omp(field, field_mpi)
871
872       ! All master threads send the field to XIOS
873       IF (is_omp_root) THEN
874#ifdef XIOS
875          CALL xios_send_field(field_id,field_mpi)
876#endif
877       END IF
878    END IF
879  END SUBROUTINE xios_orchidee_send_field_r3d
880
881  !! ==============================================================================================================================
882  !! SUBROUTINE   : xios_orchidee_send_field_r4d
883  !!
884  !>\BRIEF          Subroutine for sending 4D fields to XIOS.
885  !!
886  !! DESCRIPTION  :\n Send one field to XIOS. This is the interface for 4D fields.
887  !!                  NB! This subroutine should not be called directly. Use interface xios_orchidee_send_field.
888  !!
889  !! \n
890  !_ ================================================================================================================================
891  SUBROUTINE xios_orchidee_send_field_r4d(field_id,field)
892    !
893    !! 0. Variable and parameter declaration
894    !
895    !! 0.1 Input variables
896    !
897    CHARACTER(len=*), INTENT(IN)              :: field_id
898    REAL(r_std), DIMENSION(:,:,:,:), INTENT(IN) :: field
899
900    !! 0.2 Local variables
901    INTEGER :: jv
902    REAL(r_std), DIMENSION(nbp_mpi,size(field,2),size(field,3),size(field,4)) :: field_mpi
903
904    !_ ================================================================================================================================
905    IF (xios_orchidee_ok) THEN
906       IF (printlev>=4) WRITE(numout,*) 'Entering xios_orchidee_send_field_r4d, field_id=',field_id
907
908       ! Gather all omp domains on the mpi domains
909       CALL gather_omp(field, field_mpi)
910
911       ! All master threads send the field to XIOS
912       IF (is_omp_root) THEN
913#ifdef XIOS
914          CALL xios_send_field(field_id,field_mpi)
915#endif
916       END IF
917    END IF
918  END SUBROUTINE xios_orchidee_send_field_r4d
919
920  !! ==============================================================================================================================
921  !! SUBROUTINE   : xios_orchidee_send_field_r5d
922  !!
923  !>\BRIEF          Subroutine for sending 5D fields to XIOS.
924  !!
925  !! DESCRIPTION  :\n Send one field to XIOS. This is the interface for 5D fields.
926  !!                  NB! This subroutine should not be called directly. Use interface xios_orchidee_send_field.
927  !!
928  !! \n
929  !_ ================================================================================================================================
930  SUBROUTINE xios_orchidee_send_field_r5d(field_id,field)
931    !
932    !! 0. Variable and parameter declaration
933    !
934    !! 0.1 Input variables
935    !
936    CHARACTER(len=*), INTENT(IN)              :: field_id
937    REAL(r_std), DIMENSION(:,:,:,:,:), INTENT(IN) :: field
938
939    !! 0.2 Local variables
940    INTEGER :: jv
941    REAL(r_std), DIMENSION(nbp_mpi,size(field,2),size(field,3),size(field,4),size(field,5)) :: field_mpi
942
943    !_ ================================================================================================================================
944    IF (xios_orchidee_ok) THEN
945       IF (printlev>=4) WRITE(numout,*) 'Entering xios_orchidee_send_field_r5d, field_id=',field_id
946
947       ! Gather all omp domains on the mpi domains
948       CALL gather_omp(field, field_mpi)
949
950       ! All master threads send the field to XIOS
951       IF (is_omp_root) THEN
952#ifdef XIOS
953          CALL xios_send_field(field_id,field_mpi)
954#endif
955       END IF
956    END IF
957  END SUBROUTINE xios_orchidee_send_field_r5d
958 
959  !! ==============================================================================================================================
960  !! SUBROUTINE   : xios_orchidee_recv_field_r2d
961  !!
962  !>\BRIEF          Subroutine for receiving 1D (kjpindex) fields to XIOS.
963  !!
964  !! DESCRIPTION  :\n
965  !!
966  !! \n
967  !_ ================================================================================================================================
968  SUBROUTINE xios_orchidee_recv_field_r1d(field_id,field)
969    !
970    !! 0. Variable and parameter declaration
971    !
972    !! 0.1 Input variables
973    !
974    CHARACTER(len=*), INTENT(IN)              :: field_id
975   
976    !! 0.2 Output variables
977    REAL(r_std), DIMENSION(:), INTENT(OUT)    :: field
978
979    !! 0.2 Local variables
980    REAL(r_std), DIMENSION(nbp_mpi)           :: field_mpi
981
982    !_ ================================================================================================================================
983    IF (xios_orchidee_ok) THEN
984       IF (printlev>=4) WRITE(numout,*) 'Entering xios_orchidee_recv_field_r1d, field_id=',field_id
985
986       ! All master threads receive the field from XIOS
987       IF (is_omp_root) THEN
988#ifdef XIOS
989          CALL xios_recv_field(field_id,field_mpi)
990          IF (printlev>=5) WRITE(numout,*) 'Recieve done with xios_orchidee_recv_field_r1d, field_id=',field_id
991#endif
992       END IF
993
994       ! Scatter the mpi domains on local omp domains
995       CALL scatter_omp(field_mpi, field)
996
997    END IF
998  END SUBROUTINE xios_orchidee_recv_field_r1d
999
1000  !! ==============================================================================================================================
1001  !! SUBROUTINE   : xios_orchidee_recv_field_r2d
1002  !!
1003  !>\BRIEF          Subroutine for receiving 2D(kjpindex and 1 vertical axe) fields to XIOS.
1004  !!
1005  !! DESCRIPTION  :\n
1006  !!
1007  !! \n
1008  !_ ================================================================================================================================
1009  SUBROUTINE xios_orchidee_recv_field_r2d(field_id,field)
1010    !
1011    !! 0. Variable and parameter declaration
1012    !
1013    !! 0.1 Input variables
1014    !
1015    CHARACTER(len=*), INTENT(IN)              :: field_id
1016   
1017    !! 0.2 Output variables
1018    REAL(r_std), DIMENSION(:,:), INTENT(OUT)  :: field
1019
1020    !! 0.2 Local variables
1021    REAL(r_std), DIMENSION(nbp_mpi,size(field,2)) :: field_mpi
1022
1023    !_ ================================================================================================================================
1024    IF (xios_orchidee_ok) THEN
1025       IF (printlev>=4) WRITE(numout,*) 'Entering xios_orchidee_recv_field_r2d, field_id=',field_id
1026
1027       ! All master threads recieve the field from XIOS
1028       IF (is_omp_root) THEN
1029#ifdef XIOS
1030          CALL xios_recv_field(field_id,field_mpi)
1031          IF (printlev>=5) WRITE(numout,*) 'Recieve done with xios_orchidee_recv_field_r2d, field_id=',field_id
1032#endif
1033       END IF
1034
1035       ! Scatter the mpi domains on local omp domains
1036       CALL scatter_omp(field_mpi, field)
1037
1038    END IF
1039  END SUBROUTINE xios_orchidee_recv_field_r2d
1040
1041  !! ==============================================================================================================================
1042  !! SUBROUTINE   : xios_orchidee_recv_field_r3d
1043  !!
1044  !>\BRIEF          Subroutine for receiving 3D(kjpindex and 2 vertical axes) fields to XIOS.
1045  !!
1046  !! DESCRIPTION  :\n
1047  !!
1048  !! \n
1049  !_ ================================================================================================================================
1050  SUBROUTINE xios_orchidee_recv_field_r3d(field_id,field)
1051    !
1052    !! 0. Variable and parameter declaration
1053    !
1054    !! 0.1 Input variables
1055    !
1056    CHARACTER(len=*), INTENT(IN)              :: field_id
1057   
1058    !! 0.2 Output variables
1059    REAL(r_std), DIMENSION(:,:,:), INTENT(OUT) :: field
1060
1061    !! 0.2 Local variables
1062    REAL(r_std), DIMENSION(nbp_mpi,size(field,2),size(field,3)) :: field_mpi
1063
1064    !_ ================================================================================================================================
1065    IF (xios_orchidee_ok) THEN
1066       IF (printlev>=4) WRITE(numout,*) 'Entering xios_orchidee_recv_field_r3d, field_id=',field_id
1067
1068       ! All master threads receive the field from XIOS
1069       IF (is_omp_root) THEN
1070#ifdef XIOS
1071          CALL xios_recv_field(field_id,field_mpi)
1072          IF (printlev>=5) WRITE(numout,*) 'Recieve done with xios_orchidee_recv_field_r3d, field_id=',field_id
1073#endif
1074       END IF
1075
1076       ! Scatter the mpi domains on local omp domains
1077       CALL scatter_omp(field_mpi, field)
1078
1079    END IF
1080  END SUBROUTINE xios_orchidee_recv_field_r3d
1081
1082
1083
1084  SUBROUTINE xios_orchidee_set_file_attr(attr, name, enabled)
1085    CHARACTER(LEN=*), INTENT(IN)            :: attr     ! Name of the attribut
1086    CHARACTER(LEN=*), INTENT(IN), OPTIONAL  :: name     ! New name
1087    LOGICAL, INTENT(IN), OPTIONAL             :: enabled ! Flag
1088
1089    IF (xios_orchidee_ok .AND. is_omp_root) THEN
1090
1091#ifdef XIOS
1092       IF (PRESENT(name) .AND. PRESENT(enabled)) THEN
1093         CALL xios_set_file_attr(attr, name=name, enabled=enabled)
1094       ELSE IF (PRESENT(name)) THEN
1095         CALL xios_set_file_attr(attr, name=name)
1096       ELSE IF (PRESENT(enabled)) THEN
1097         CALL xios_set_file_attr(attr, enabled=enabled)
1098       ELSE
1099         CALL xios_set_file_attr(attr)
1100       END IF
1101#endif
1102
1103    END IF
1104
1105  END SUBROUTINE xios_orchidee_set_file_attr
1106 
1107  SUBROUTINE xios_orchidee_set_field_attr(attr,name, enabled)
1108    CHARACTER(LEN=*), INTENT(IN)            :: attr     ! Name of the attribut
1109    CHARACTER(LEN=*), INTENT(IN), OPTIONAL  :: name     ! New name
1110    LOGICAL, INTENT(IN), OPTIONAL             :: enabled ! Flag
1111
1112    IF (xios_orchidee_ok .AND. is_omp_root) THEN
1113
1114#ifdef XIOS
1115       IF (PRESENT(name) .AND. PRESENT(enabled)) THEN
1116         CALL xios_set_field_attr(attr, name=name, enabled=enabled)
1117       ELSE IF (PRESENT(name)) THEN
1118         CALL xios_set_field_attr(attr, name=name)
1119       ELSE IF (PRESENT(enabled)) THEN
1120         CALL xios_set_field_attr(attr, enabled=enabled)
1121       ELSE
1122         CALL xios_set_field_attr(attr)
1123       END IF
1124#endif
1125
1126    END IF
1127
1128
1129  END SUBROUTINE xios_orchidee_set_field_attr
1130 
1131  SUBROUTINE xios_orchidee_set_fieldgroup_attr(attr,name, enabled)
1132    CHARACTER(LEN=*), INTENT(IN)            :: attr     ! Name of the attribut
1133    CHARACTER(LEN=*), INTENT(IN), OPTIONAL  :: name     ! New name
1134    LOGICAL, INTENT(IN), OPTIONAL             :: enabled ! Flag
1135
1136    IF (xios_orchidee_ok .AND. is_omp_root) THEN
1137
1138#ifdef XIOS
1139       IF (PRESENT(name) .AND. PRESENT(enabled)) THEN
1140         CALL xios_set_fieldgroup_attr(attr, name=name, enabled=enabled)
1141       ELSE IF (PRESENT(name)) THEN
1142         CALL xios_set_fieldgroup_attr(attr, name=name)
1143       ELSE IF (PRESENT(enabled)) THEN
1144         CALL xios_set_fieldgroup_attr(attr, enabled=enabled)
1145       ELSE
1146         CALL xios_set_fieldgroup_attr(attr)
1147       END IF
1148#endif
1149
1150    END IF
1151
1152
1153  END SUBROUTINE xios_orchidee_set_fieldgroup_attr
1154 
1155  FUNCTION xios_orchidee_setvar(varname,varvalue) RESULT (out)
1156    CHARACTER(LEN=*), INTENT(IN) :: varname  ! Name of the variable
1157    REAL, INTENT(IN)               :: varvalue ! Value of the variable
1158    LOGICAL :: out
1159
1160    IF (xios_orchidee_ok .AND. is_omp_root) THEN
1161#ifdef XIOS
1162      out=xios_setvar(varname, varvalue)
1163#endif
1164    END IF
1165
1166  END FUNCTION xios_orchidee_setvar
1167
1168END MODULE xios_orchidee
1169
Note: See TracBrowser for help on using the repository browser.