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

Last change on this file since 7503 was 7503, checked in by josefine.ghattas, 2 years ago

Activate possibility to use forcing files on grid regular_xy such as Safran Lambert Conformal. Done by Jan Polcher and tested by Lucia Rinchiuso. See ticket #830

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