source: LMDZ6/trunk/libf/misc/wxios.F90 @ 4553

Last change on this file since 4553 was 4477, checked in by lfalletti, 17 months ago

New axis (axis_lat_greordered) that fixes a bug with latitudes being reversed for outputs from CMIP6 workflow (for zonal mean files only)

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