source: LMDZ5/branches/IPSLCM5A2.1/libf/misc/wxios.F90 @ 3650

Last change on this file since 3650 was 3650, checked in by acozic, 4 years ago

make a modification in the way to calcul longitude for xios output. As it was done, in VLR, dimension lon as not the value "0" but "-2.544444e-14". It's create a problem in cmip grid reordered longitude.
This commit doesn't change the results of a simulation

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