source: trunk/LMDZ.COMMON/libf/misc/wxios.F90 @ 1658

Last change on this file since 1658 was 1650, checked in by emillour, 8 years ago

Dynamical core: Further adaptations to stick with LMDZ5 (up to rev r2750)

  • libf
  • makelmdz[_fcm] : added Earth-specific "dust" and "strataer" cases and

-arch_path option

  • bld.cfg : added dust and strataer cases
  • dyn3d[par]
  • conf_gcm.F90 : added read_orop parameter (Earth-related) for

loading subgrid orography parameters.

  • guide[_p]_mod.F90: added output of nudging coefficients for winds

and temperature

  • temps_mod.F90 : cosmetics/comments
  • logic_mod.F90 : cosmetics/comments
  • dyn3d_common
  • comconst_mod.F90 : cosmetics/comments + added year_day module variable
  • conf_planete.F90 : added year_day from comconst_mod as done in LMDZ5
  • comvert_mod.F90 : cosmetics/comments
  • infotrac.F90 : added "startAer" case to follow up with LMDZ5
  • misc
  • wxios.F90 : follow up on changes in LMDZ5

EM

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