source: CONFIG_DEVT/IPSLCM6.5_work_ENSEMBLES/modeles/LMDZ/libf/misc/wxios.F90 @ 6165

Last change on this file since 6165 was 6165, checked in by ymipsl, 2 years ago

add value and axis_type to ensemble axis.
YM

File size: 25.9 KB
Line 
1! $Id$
2#ifdef CPP_XIOS
3MODULE wxios
4    USE xios
5    USE iaxis
6    USE iaxis_attr
7    USE icontext_attr
8    USE idate
9    USE idomain_attr
10    USE ifield_attr
11    USE ifile_attr
12    USE ixml_tree
13
14    !Variables disponibles pendant toute l'execution du programme:
15   
16    INTEGER, SAVE :: g_comm
17    CHARACTER(len=100), SAVE :: g_ctx_name ="LMDZ"
18    TYPE(xios_context), SAVE :: g_ctx
19!$OMP THREADPRIVATE(g_comm,g_cts_name,g_ctx)
20    LOGICAL, SAVE :: g_flag_xml = .FALSE.
21    CHARACTER(len=100) :: g_field_name = "nofield"
22!$OMP THREADPRIVATE(g_flag_xml,g_field_name)
23    REAL :: missing_val_omp
24    REAL :: missing_val
25!$OMP THREADPRIVATE(missing_val)
26
27#ifdef XIOS1
28#error "XIOS v1 no longer supported, use XIOS v2."
29#endif
30
31    CONTAINS
32   
33    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
34    !   36day => 36d etc     !!!!!!!!!!!!!!!!!!!!
35    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
36   
37    SUBROUTINE reformadate(odate, ndate)
38        CHARACTER(len=*), INTENT(IN) :: odate
39        TYPE(xios_duration) :: ndate
40       
41        INTEGER :: i = 0
42         !!!!!!!!!!!!!!!!!!
43         ! Pour XIOS:
44         !  year : y
45         !  month : mo
46         !  day : d
47         !  hour : h
48         !  minute : mi
49         !  second : s
50         !!!!!!!!!!!!!!!!!!
51
52        i = INDEX(odate, "day")
53        IF (i > 0) THEN
54            read(odate(1:i-1),*) ndate%day
55        END IF
56
57        i = INDEX(odate, "hr")
58        IF (i > 0) THEN
59            read(odate(1:i-1),*) ndate%hour
60        END IF
61
62        i = INDEX(odate, "mth")
63        IF (i > 0) THEN
64            read(odate(1:i-1),*) ndate%month
65        END IF
66       
67        !IF (prt_level >= 10) WRITE(lunout,*) "Xios. ", odate, " => ", ndate
68    END SUBROUTINE reformadate
69   
70    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
71    !   ave(X) => average etc     !!!!!!!!!!!!!!!
72    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
73   
74    CHARACTER(len=7) FUNCTION reformaop(op)
75        CHARACTER(len=*), INTENT(IN) :: op
76       
77        INTEGER :: i = 0
78        reformaop = "average"
79       
80        IF (op.EQ."inst(X)") THEN
81            reformaop = "instant"
82        END IF
83       
84        IF (op.EQ."once") THEN
85            reformaop = "once"
86        END IF
87       
88        IF (op.EQ."t_max(X)") THEN
89            reformaop = "maximum"
90        END IF
91       
92        IF (op.EQ."t_min(X)") THEN
93            reformaop = "minimum"
94        END IF
95       
96        !IF (prt_level >= 10) WRITE(lunout,*) "Xios. ", op, " => ", reformaop
97    END FUNCTION reformaop
98
99    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
100    ! Routine d'initialisation      !!!!!!!!!!!!!
101    !     A lancer juste aprÚs mpi_init !!!!!!!!!!!!!
102    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
103
104    SUBROUTINE wxios_init(xios_ctx_name, locom, outcom, type_ocean)
105        USE print_control_mod, ONLY : prt_level, lunout
106        IMPLICIT NONE
107
108      CHARACTER(len=*), INTENT(IN) :: xios_ctx_name
109      INTEGER, INTENT(IN), OPTIONAL :: locom
110      INTEGER, INTENT(OUT), OPTIONAL :: outcom
111      CHARACTER(len=6), INTENT(IN), OPTIONAL :: type_ocean
112
113   
114        TYPE(xios_context) :: xios_ctx
115        INTEGER :: xios_comm
116
117        IF (prt_level >= 10) WRITE(lunout,*) "wxios_init: Initialization"
118
119
120
121        IF (PRESENT(locom)) THEN
122          CALL xios_initialize(xios_ctx_name, local_comm = locom, return_comm = xios_comm )
123          IF (prt_level >= 10) WRITE(lunout,*) "wxios_init: ctx=",xios_ctx_name," local_comm=",locom,", return_comm=",xios_comm
124        ELSE
125          CALL xios_initialize(xios_ctx_name, return_comm = xios_comm )
126          IF (prt_level >= 10) WRITE(lunout,*) "wxios_init: ctx=",xios_ctx_name," return_comm=",xios_comm
127        END IF
128       
129        IF (PRESENT(outcom)) THEN
130          outcom = xios_comm
131          IF (prt_level >= 10) WRITE(lunout,*) "wxios_init: ctx=",xios_ctx_name," outcom=",outcom
132        END IF
133       
134        !Enregistrement des variables globales:
135        g_comm = xios_comm
136!        g_ctx_name = xios_ctx_name
137       
138!        ! Si couple alors init fait dans cpl_init
139!        IF (.not. PRESENT(type_ocean)) THEN
140!            CALL wxios_context_init()
141!        ENDIF
142
143    END SUBROUTINE wxios_init
144
145    SUBROUTINE wxios_context_init()
146        USE print_control_mod, ONLY : prt_level, lunout
147        USE mod_phys_lmdz_ensemble, ONLY : COMM_LMDZ_PHY_ENSEMBLE
148        IMPLICIT NONE
149
150        TYPE(xios_context) :: xios_ctx
151
152!$OMP MASTER
153        !Initialisation du contexte:
154        !!CALL xios_context_initialize(g_ctx_name, g_comm)
155        CALL xios_context_initialize(g_ctx_name, COMM_LMDZ_PHY_ENSEMBLE)
156        CALL xios_get_handle(g_ctx_name, xios_ctx)    !Récupération
157        CALL xios_set_current_context(xios_ctx)            !Activation
158        g_ctx = xios_ctx
159
160        IF (prt_level >= 10) THEN
161          WRITE(lunout,*) "wxios_context_init: Current context is ",trim(g_ctx_name)
162          WRITE(lunout,*) "     now call xios_solve_inheritance()"
163        ENDIF
164        !Une premiÚre analyse des héritages:
165        CALL xios_solve_inheritance()
166!$OMP END MASTER
167    END SUBROUTINE wxios_context_init
168
169
170    SUBROUTINE wxios_set_context()
171        IMPLICIT NONE
172        TYPE(xios_context) :: xios_ctx
173
174       !$OMP MASTER
175        CALL xios_get_handle(g_ctx_name, xios_ctx)    !Récupération
176        CALL xios_set_current_context(xios_ctx)            !Activation
177       !$OMP END MASTER
178
179    END SUBROUTINE wxios_set_context
180
181    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
182    ! Routine de paramétrisation !!!!!!!!!!!!!!!!!!
183    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
184
185    SUBROUTINE wxios_set_cal(pasdetemps, calendrier, annee, mois, jour, heure, ini_an, ini_mois, ini_jour, ini_heure)
186        USE print_control_mod, ONLY : prt_level, lunout
187        IMPLICIT NONE
188
189     !ParamÚtres:
190     CHARACTER(len=*), INTENT(IN) :: calendrier
191     INTEGER, INTENT(IN) :: annee, mois, jour, ini_an, ini_mois, ini_jour
192     REAL, INTENT(IN) :: pasdetemps, heure, ini_heure
193     
194     !Variables:
195     CHARACTER(len=80) :: abort_message
196     CHARACTER(len=19) :: date
197     INTEGER :: njour = 1
198     
199     !Variables pour xios:
200     TYPE(xios_duration) :: mdtime
201     !REAL(kind = 8) :: year=0, month=0, day=0, hour=0, minute=0, second=0
202     
203        mdtime%second=pasdetemps
204
205        !Réglage du calendrier:
206        SELECT CASE (calendrier)
207            CASE('earth_360d')
208                CALL xios_define_calendar("D360")
209                IF (prt_level >= 10) WRITE(lunout,*) 'wxios_set_cal: Calendrier terrestre a 360 jours/an'
210            CASE('earth_365d')
211                CALL xios_define_calendar("NoLeap")
212                IF (prt_level >= 10) WRITE(lunout,*) 'wxios_set_cal: Calendrier terrestre a 365 jours/an'
213            CASE('gregorian')
214                CALL xios_define_calendar("Gregorian")
215                IF (prt_level >= 10) WRITE(lunout,*) 'wxios_set_cal: Calendrier gregorien'
216            CASE DEFAULT
217                abort_message = 'wxios_set_cal: Mauvais choix de calendrier'
218                CALL abort_physic('Gcm:Xios',abort_message,1)
219        END SELECT
220       
221        !Formatage de la date d'origine:
222        WRITE(date, "(i4.4,'-',i2.2,'-',i2.2,' ',i2.2,':00:00')") annee, mois, jour, int(heure) 
223       
224        IF (prt_level >= 10) WRITE(lunout,*) "wxios_set_cal: Time origin: ", date
225        CALL xios_set_time_origin(xios_date(annee,mois,jour,int(heure),0,0))
226
227        !Formatage de la date de debut:
228
229        WRITE(date, "(i4.4,'-',i2.2,'-',i2.2,' ',i2.2,':00:00')") ini_an, ini_mois, ini_jour, int(ini_heure)
230       
231        IF (prt_level >= 10) WRITE(lunout,*) "wxios_set_cal: Start date: ", date
232       
233        CALL xios_set_start_date(xios_date(ini_an,ini_mois,ini_jour,int(ini_heure),0,0))
234       
235        !Et enfin,le pas de temps:
236        CALL xios_set_timestep(mdtime)
237        IF (prt_level >= 10) WRITE(lunout,*) "wxios_set_cal: ts=",mdtime
238    END SUBROUTINE wxios_set_cal
239
240    SUBROUTINE wxios_set_timestep(ts)
241        REAL, INTENT(IN) :: ts
242        TYPE(xios_duration) :: mdtime     
243
244        mdtime%timestep = ts
245
246        CALL xios_set_timestep(mdtime)
247    END SUBROUTINE wxios_set_timestep
248
249
250    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
251    ! Pour initialiser la dimension d'ensemble !!!!!!!
252    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
253    SUBROUTINE wxios_ensemble_param
254      USE mod_phys_lmdz_ensemble
255      IMPLICIT NONE
256     
257     !$OMP MASTER 
258        IF (ensemble_management)  THEN
259          CALL xios_set_axis_attr("ensemble",n_glo=whole_ensemble_size,begin=whole_ensemble_rank, axis_type="E", n=1, &
260                                   value=(/REAL(whole_ensemble_rank)/))
261        ENDIF
262     !$OMP END MASTER
263     
264    END SUBROUTINE wxios_ensemble_param
265
266    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
267    ! Pour initialiser un domaine !!!!!!!!!!!!!!!!!!!!
268    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
269    SUBROUTINE wxios_domain_param(dom_id)
270       USE dimphy, only: klon
271       USE mod_phys_lmdz_transfert_para, ONLY: gather, bcast
272       USE mod_phys_lmdz_para, only: jj_nb, jj_begin, jj_end, ii_begin, ii_end, &
273                                     mpi_size, mpi_rank, klon_mpi, &
274                                     is_sequential, is_south_pole_dyn
275       USE mod_grid_phy_lmdz, only: nbp_lon, nbp_lat, klon_glo         
276       USE print_control_mod, ONLY : prt_level, lunout
277       USE geometry_mod
278
279       IMPLICIT NONE
280        CHARACTER(len=*),INTENT(IN) :: dom_id ! domain identifier
281
282        REAL   :: rlat_glo(klon_glo)
283        REAL   :: rlon_glo(klon_glo)
284        REAL   :: io_lat(nbp_lat)
285        REAL   :: io_lon(nbp_lon)
286        LOGICAL :: mask(nbp_lon,jj_nb) !Masque pour les problÚmes de recouvrement MPI
287        TYPE(xios_domain) :: dom
288        INTEGER :: i
289        LOGICAL :: boool
290       
291
292
293        CALL gather(latitude_deg,rlat_glo) 
294        CALL bcast(rlat_glo)
295        CALL gather(longitude_deg,rlon_glo)
296        CALL bcast(rlon_glo)
297   
298  !$OMP MASTER 
299        io_lat(1)=rlat_glo(1)
300        io_lat(nbp_lat)=rlat_glo(klon_glo)
301        IF ((nbp_lon*nbp_lat) > 1) then
302          DO i=2,nbp_lat-1
303            io_lat(i)=rlat_glo(2+(i-2)*nbp_lon)
304          ENDDO
305        ENDIF
306
307        IF (klon_glo == 1) THEN
308          io_lon(1)=rlon_glo(1)
309        ELSE
310          io_lon(1:nbp_lon)=rlon_glo(2:nbp_lon+1)
311        ENDIF
312
313       
314        !On récupÚre le handle:
315        CALL xios_get_domain_handle(dom_id, dom)
316       
317        !On parametrise le domaine:
318        CALL xios_set_domain_attr_hdl(dom, ni_glo=nbp_lon, ibegin=0, ni=nbp_lon, type="rectilinear")
319        CALL xios_set_domain_attr_hdl(dom, nj_glo=nbp_lat, jbegin=jj_begin-1, nj=jj_nb, data_dim=2)
320        CALL xios_set_domain_attr_hdl(dom, lonvalue_1d=io_lon(1:nbp_lon), latvalue_1d=io_lat(jj_begin:jj_end))
321        CALL xios_set_domain_attr("dom_out", domain_ref=dom_id)
322
323        !On definit un axe de latitudes pour les moyennes zonales
324        IF (xios_is_valid_axis("axis_lat")) THEN
325           CALL xios_set_axis_attr( "axis_lat", n_glo=nbp_lat, n=jj_nb, begin=jj_begin-1, value=io_lat(jj_begin:jj_end))
326        ENDIF
327
328        IF (.NOT.is_sequential) THEN
329            mask(:,:)=.TRUE.
330            if (ii_begin>1) mask(1:ii_begin-1,1) = .FALSE.
331            if (ii_end<nbp_lon) mask(ii_end+1:nbp_lon,jj_nb) = .FALSE.
332            ! special case for south pole
333            if ((ii_end==1).and.(is_south_pole_dyn)) mask(1:nbp_lon,jj_nb)=.true.
334            IF (prt_level >= 10) THEN
335              WRITE(lunout,*) "wxios_domain_param: mpirank=",mpi_rank," mask(:,1)=",mask(:,1)
336              WRITE(lunout,*) "wxios_domain_param: mpirank=",mpi_rank," mask(:,jj_nb)=",mask(:,jj_nb)
337            ENDIF
338            CALL xios_set_domain_attr_hdl(dom, mask_2d=mask)
339        END IF
340
341         CALL xios_is_defined_domain_attr_hdl(dom,ni_glo=boool)
342        !Vérification:
343        IF (xios_is_valid_domain(dom_id)) THEN
344            IF (prt_level >= 10) WRITE(lunout,*) "wxios_domain_param: Domain initialized: ", trim(dom_id), boool
345        ELSE
346            IF (prt_level >= 10) WRITE(lunout,*) "wxios_domain_param: Invalid domain: ", trim(dom_id)
347        END IF
348!$OMP END MASTER
349       
350    END SUBROUTINE wxios_domain_param
351   
352
353    SUBROUTINE wxios_domain_param_unstructured(dom_id)
354        USE geometry_mod, ONLY : longitude, latitude, boundslon, boundslat,ind_cell_glo
355        USE mod_grid_phy_lmdz, ONLY : nvertex, klon_glo
356        USE mod_phys_lmdz_para 
357        USE nrtype, ONLY : PI
358        USE ioipsl_getin_p_mod, ONLY : getin_p
359        IMPLICIT NONE
360        CHARACTER(len=*),INTENT(IN) :: dom_id ! domain identifier
361        REAL :: lon_mpi(klon_mpi)
362        REAL :: lat_mpi(klon_mpi)
363        REAL :: boundslon_mpi(klon_mpi,nvertex)
364        REAL :: boundslat_mpi(klon_mpi,nvertex)
365        INTEGER :: ind_cell_glo_mpi(klon_mpi)
366        TYPE(xios_domain) :: dom
367       
368        LOGICAL :: remap_output
369
370        CALL gather_omp(longitude*180/PI,lon_mpi)
371        CALL gather_omp(latitude*180/PI,lat_mpi)
372        CALL gather_omp(boundslon*180/PI,boundslon_mpi)
373        CALL gather_omp(boundslat*180/PI,boundslat_mpi)
374        CALL gather_omp(ind_cell_glo,ind_cell_glo_mpi)
375       
376        remap_output=.TRUE.
377        CALL getin_p("remap_output",remap_output)
378
379!$OMP MASTER
380        CALL xios_get_domain_handle(dom_id, dom)
381       
382        !On parametrise le domaine:
383        CALL xios_set_attr(dom, ni_glo=klon_glo, ibegin=ij_begin-1, ni=ij_nb, type="unstructured")
384        CALL xios_set_attr(dom, nvertex=nvertex, lonvalue_1d=lon_mpi, latvalue_1d=lat_mpi, &
385                           bounds_lon_1d=TRANSPOSE(boundslon_mpi), bounds_lat_1d=TRANSPOSE(boundslat_mpi) )
386        CALL xios_set_attr(dom, i_index=ind_cell_glo_mpi(:)-1)
387        IF (remap_output) THEN
388          CALL xios_set_domain_attr("dom_out", domain_ref="dom_regular")
389          CALL xios_set_fieldgroup_attr("remap_expr", expr="@this_ref")
390          CALL xios_set_fieldgroup_attr("remap_1800s", freq_op=xios_duration_convert_from_string("1800s"))
391          CALL xios_set_fieldgroup_attr("remap_1h",    freq_op=xios_duration_convert_from_string("1h"))
392          CALL xios_set_fieldgroup_attr("remap_3h",    freq_op=xios_duration_convert_from_string("3h"))
393          CALL xios_set_fieldgroup_attr("remap_6h",    freq_op=xios_duration_convert_from_string("6h"))
394          CALL xios_set_fieldgroup_attr("remap_1d",    freq_op=xios_duration_convert_from_string("1d"))
395          CALL xios_set_fieldgroup_attr("remap_1mo",   freq_op=xios_duration_convert_from_string("1mo"))
396        ENDIF
397!$OMP END MASTER
398
399    END SUBROUTINE wxios_domain_param_unstructured
400
401
402
403
404    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
405    ! Pour déclarer un axe vertical !!!!!!!!!!!!!!!
406    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
407    SUBROUTINE wxios_add_vaxis(axis_id, axis_size, axis_value,     &
408                               positif, bnds)
409        USE print_control_mod, ONLY : prt_level, lunout
410        IMPLICIT NONE
411
412        CHARACTER (len=*), INTENT(IN) :: axis_id
413        INTEGER, INTENT(IN) :: axis_size
414        REAL, DIMENSION(axis_size), INTENT(IN) :: axis_value
415        CHARACTER (len=*), INTENT(IN), OPTIONAL :: positif
416        REAL, DIMENSION(axis_size, 2), INTENT(IN), OPTIONAL :: bnds
417       
418!        TYPE(xios_axisgroup) :: axgroup
419!        TYPE(xios_axis) :: ax
420!        CHARACTER(len=50) :: axis_id
421       
422!        IF (len_trim(axisgroup_id).gt.len(axis_id)) THEN
423!          WRITE(lunout,*) "wxios_add_vaxis: error, size of axis_id too small!!"
424!          WRITE(lunout,*) "     increase it to at least ",len_trim(axisgroup_id)
425!          CALL abort_gcm("wxios_add_vaxis","len(axis_id) too small",1)
426!        ENDIF
427!        axis_id=trim(axisgroup_id)
428       
429        !On récupÚre le groupe d'axes qui va bien:
430        !CALL xios_get_axisgroup_handle(axisgroup_id, axgroup)
431       
432        !On ajoute l'axe correspondant à ce fichier:
433        !CALL xios_add_axis(axgroup, ax, TRIM(ADJUSTL(axis_id)))
434       
435        !Et on le parametrise:
436        !CALL xios_set_axis_attr_hdl(ax, size=axis_size, value=axis_value)
437       
438        ! Ehouarn: New way to declare axis, without axis_group:
439        if (PRESENT(positif) .AND. PRESENT(bnds)) then
440          CALL xios_set_axis_attr(trim(axis_id),n_glo=axis_size,value=axis_value, &
441                                  positive=positif, bounds=bnds)
442        else if (PRESENT(positif)) then
443          CALL xios_set_axis_attr(trim(axis_id),n_glo=axis_size,value=axis_value, &
444                                  positive=positif)
445        else if (PRESENT(bnds)) then
446          CALL xios_set_axis_attr(trim(axis_id),n_glo=axis_size,value=axis_value, &
447                                  bounds=bnds)
448        else
449          CALL xios_set_axis_attr(trim(axis_id),n_glo=axis_size,value=axis_value)
450        endif
451
452        !Vérification:
453        IF (xios_is_valid_axis(TRIM(ADJUSTL(axis_id)))) THEN
454            IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_vaxis: Axis created: ", TRIM(ADJUSTL(axis_id))
455        ELSE
456            WRITE(lunout,*) "wxios_add_vaxis: Invalid axis: ", TRIM(ADJUSTL(axis_id))
457        END IF
458
459    END SUBROUTINE wxios_add_vaxis
460   
461   
462    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
463    ! Pour déclarer un fichier  !!!!!!!!!!!!!!!!!!!
464    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
465    SUBROUTINE wxios_add_file(fname, ffreq, flvl)
466        USE print_control_mod, ONLY : prt_level, lunout
467        IMPLICIT NONE
468
469        CHARACTER(len=*), INTENT(IN) :: fname
470        CHARACTER(len=*), INTENT(IN) :: ffreq
471        INTEGER, INTENT(IN) :: flvl
472       
473        TYPE(xios_file) :: x_file
474        TYPE(xios_filegroup) :: x_fg
475        TYPE(xios_duration) :: nffreq
476       
477        !On regarde si le fichier n'est pas défini par XML:
478        IF (.NOT.xios_is_valid_file(fname)) THEN
479            !On créé le noeud:
480            CALL xios_get_filegroup_handle("defile", x_fg)
481            CALL xios_add_file(x_fg, x_file, fname)
482       
483            !On reformate la fréquence:
484            CALL reformadate(ffreq, nffreq)
485       
486            !On configure:
487            CALL xios_set_file_attr_hdl(x_file, name="X"//fname,&
488                output_freq=nffreq, output_level=flvl, enabled=.TRUE.)
489       
490            IF (xios_is_valid_file("X"//fname)) THEN
491                IF (prt_level >= 10) THEN
492                  WRITE(lunout,*) "wxios_add_file: New file: ", "X"//fname
493                  WRITE(lunout,*) "wxios_add_file: output_freq=",nffreq,"; output_lvl=",flvl
494                ENDIF
495            ELSE
496                WRITE(lunout,*) "wxios_add_file: Error, invalid file: ", "X"//trim(fname)
497                WRITE(lunout,*) "wxios_add_file: output_freq=",nffreq,"; output_lvl=",flvl
498            END IF
499        ELSE
500            IF (prt_level >= 10) THEN
501              WRITE(lunout,*) "wxios_add_file: File ",trim(fname), " défined using XML."
502            ENDIF
503            ! Ehouarn: add an enable=.true. on top of xml definitions... why???
504            CALL xios_set_file_attr(fname, enabled=.TRUE.)
505        END IF
506    END SUBROUTINE wxios_add_file
507   
508    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
509    ! Pour créer un champ      !!!!!!!!!!!!!!!!!!!!
510    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
511    SUBROUTINE wxios_add_field(fieldname, fieldgroup, fieldlongname, fieldunit)
512        USE netcdf, only: nf90_fill_real
513
514        IMPLICIT NONE
515        INCLUDE 'iniprint.h'
516       
517        CHARACTER(len=*), INTENT(IN) :: fieldname
518        TYPE(xios_fieldgroup), INTENT(IN) :: fieldgroup
519        CHARACTER(len=*), INTENT(IN) :: fieldlongname
520        CHARACTER(len=*), INTENT(IN) :: fieldunit
521       
522        TYPE(xios_field) :: field
523        CHARACTER(len=10) :: newunit
524        REAL(KIND=8) :: def
525       
526        !La valeur par défaut des champs non définis:
527        def = nf90_fill_real
528       
529        IF (fieldunit .EQ. " ") THEN
530            newunit = "-"
531        ELSE
532            newunit = fieldunit
533        ENDIF
534       
535        !On ajoute le champ:
536        CALL xios_add_field(fieldgroup, field, fieldname)
537        !IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_field: ",fieldname,fieldgroup, fieldlongname, fieldunit
538       
539        !On rentre ses paramÚtres:
540        CALL xios_set_field_attr_hdl(field, standard_name=fieldlongname, unit=newunit, default_value=def)
541        IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_field: Field ",trim(fieldname), "cree:"
542        IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_field: long_name=",trim(fieldlongname),"; unit=",trim(newunit),";  default_value=",nf90_fill_real
543
544    END SUBROUTINE wxios_add_field
545   
546    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
547    ! Pour déclarer un champ      !!!!!!!!!!!!!!!!!
548    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
549    SUBROUTINE wxios_add_field_to_file(fieldname, fdim, fid, fname, fieldlongname, fieldunit, field_level, op, nam_axvert)
550        USE print_control_mod, ONLY : prt_level, lunout
551        IMPLICIT NONE
552
553        CHARACTER(len=*), INTENT(IN) :: fieldname
554        INTEGER, INTENT(IN)          :: fdim, fid
555        CHARACTER(len=*), INTENT(IN) :: fname
556        CHARACTER(len=*), INTENT(IN) :: fieldlongname
557        CHARACTER(len=*), INTENT(IN) :: fieldunit
558        INTEGER, INTENT(IN)          :: field_level
559        CHARACTER(len=*), INTENT(IN) :: op
560       
561        CHARACTER(len=20) :: axis_id ! Ehouarn: dangerous...
562        CHARACTER(len=20), INTENT(IN), OPTIONAL :: nam_axvert
563        CHARACTER(len=100) :: operation
564        TYPE(xios_file) :: f
565        TYPE(xios_field) :: field
566        TYPE(xios_fieldgroup) :: fieldgroup
567        TYPE(xios_duration) :: freq_op
568
569        LOGICAL :: bool=.FALSE.
570        INTEGER :: lvl =0
571       
572       
573        ! Ajout Abd pour NMC:
574        IF (fid.LE.6) THEN
575          axis_id="presnivs"
576        ELSE
577          axis_id="plev"
578        ENDIF
579 
580        IF (PRESENT(nam_axvert)) THEN
581           axis_id=nam_axvert
582           print*,'nam_axvert=',axis_id
583        ENDIF
584       
585        !on prépare le nom de l'opération:
586        operation = reformaop(op)
587       
588       
589        !On selectionne le bon groupe de champs:
590        IF (fdim.EQ.2) THEN
591          CALL xios_get_fieldgroup_handle("fields_2D", fieldgroup)
592        ELSE
593          CALL xios_get_fieldgroup_handle("fields_3D", fieldgroup)
594        ENDIF
595       
596        !On regarde si le champ à déjà été créé ou non:
597        IF (xios_is_valid_field(fieldname) .AND. .NOT. g_field_name == fieldname) THEN
598            !Si ce champ existe via XML (ie, dÚs le premier passage, ie g_field_name != fieldname) alors rien d'autre à faire
599            IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_field_to_file: Field ", trim(fieldname), "exists via XML"
600            g_flag_xml = .TRUE.
601            g_field_name = fieldname
602
603        ELSE IF (.NOT. g_field_name == fieldname) THEN
604            !Si premier pssage et champ indéfini, alors on le créé
605
606            IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_field_to_file: Field ", trim(fieldname), "does not exist"
607           
608            !On le créé:
609            CALL wxios_add_field(fieldname,  fieldgroup, fieldlongname, fieldunit)
610            IF (xios_is_valid_field(fieldname)) THEN
611                IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_field_to_file: Field ", trim(fieldname), "created"
612            ENDIF
613
614            g_flag_xml = .FALSE.
615            g_field_name = fieldname
616
617        END IF
618
619        IF (.NOT. g_flag_xml) THEN
620            !Champ existe déjà, mais pas XML, alors on l'ajoute
621            !On ajoute le champ:
622            CALL xios_get_file_handle(fname, f)
623            CALL xios_add_fieldtofile(f, field)
624           
625           
626            !L'operation, sa frequence:
627            freq_op%timestep=1
628            CALL xios_set_field_attr_hdl(field, field_ref=fieldname, operation=TRIM(ADJUSTL(operation)), freq_op=freq_op, prec=4)
629
630           
631            !On rentre ses paramÚtres:
632            CALL xios_set_field_attr_hdl(field, level=field_level, enabled=.TRUE.)
633           
634            IF (fdim.EQ.2) THEN
635                !Si c'est un champ 2D:
636                IF (prt_level >= 10) THEN
637                  WRITE(lunout,*) "wxios_add_field_to_file: 2D Field ", trim(fieldname), " in ", "X"//trim(fname) ," configured with:"
638                  WRITE(lunout,*) "wxios_add_field_to_file: op=", TRIM(ADJUSTL(operation))
639                  WRITE(lunout,*) "wxios_add_field_to_file: freq_op=1ts","; lvl=",field_level
640                ENDIF
641            ELSE
642                !Si 3D :
643                !On ajoute l'axe vertical qui va bien:
644                CALL xios_set_field_attr_hdl(field, axis_ref=TRIM(ADJUSTL(axis_id)))
645               
646                IF (prt_level >= 10) THEN
647                  WRITE(lunout,*) "wxios_add_field_to_file: 3D Field",trim(fieldname), " in ", "X"//trim(fname), "configured with:"
648                  WRITE(lunout,*) "wxios_add_field_to_file: freq_op=1ts","; lvl=",field_level
649                  WRITE(lunout,*) "wxios_add_field_to_file: axis=",TRIM(ADJUSTL(axis_id))
650                ENDIF
651            END IF
652       
653        ELSE
654            !Sinon on se contente de l'activer:
655            CALL xios_set_field_attr(fieldname, enabled=.TRUE.)
656            !NB: This will override an enable=.false. set by a user in the xml file;
657            !   then the only way to not output the field is by changing its
658            !   output level
659        ENDIF       
660       
661    END SUBROUTINE wxios_add_field_to_file
662   
663!    SUBROUTINE wxios_update_calendar(ito)
664!        INTEGER, INTENT(IN) :: ito
665!        CALL xios_update_calendar(ito)
666!    END SUBROUTINE wxios_update_calendar
667!   
668!    SUBROUTINE wxios_write_2D(fieldname, fdata)
669!        CHARACTER(len=*), INTENT(IN) :: fieldname
670!        REAL, DIMENSION(:,:), INTENT(IN) :: fdata
671!
672!        CALL xios_send_field(fieldname, fdata)
673!    END SUBROUTINE wxios_write_2D
674   
675!    SUBROUTINE wxios_write_3D(fieldname, fdata)
676!        CHARACTER(len=*), INTENT(IN) :: fieldname
677!        REAL, DIMENSION(:,:,:), INTENT(IN) :: fdata
678!       
679!        CALL xios_send_field(fieldname, fdata)
680!    END SUBROUTINE wxios_write_3D
681   
682    SUBROUTINE wxios_closedef()
683        CALL xios_close_context_definition()
684!        CALL xios_update_calendar(0)
685    END SUBROUTINE wxios_closedef
686   
687    SUBROUTINE wxios_close()
688        CALL xios_context_finalize()
689         CALL xios_finalize()
690     END SUBROUTINE wxios_close
691END MODULE wxios
692#endif
Note: See TracBrowser for help on using the repository browser.