source: tags/ORCHIDEE_4_1/ORCHIDEE/src_parallel/xios_orchidee.f90 @ 7852

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

Activate possibility to use forcing files on grid regular_xy such as Safran Lambert Conformal, as done in ORCHIDEE_2_2. See ticket #830

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