Ignore:
Timestamp:
Jun 25, 2014, 1:19:59 PM (11 years ago)
Author:
emillour
Message:

Common dynamics:
Some updates to keep up with LMDZ5 Earth model evolution (up to LMDZ5 rev 1955).
Main change is the introduction of a "dyn3d_common" directory
to store files common to dyn3d and dyn3dpar.
See file "DOC/chantiers/commit_importants.log" for detailed list
of changes. These changes do not change results on test cases.
EM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/bibio/wxios.F90

    r1019 r1300  
    1818    TYPE(xios_context), SAVE :: g_ctx
    1919!$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
    2024
    2125    CONTAINS
     
    2529    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    2630   
    27     SUBROUTINE concat(str, i, str_i) !MAX i = 99
    28         CHARACTER(len=*), INTENT(IN) :: str
    29         INTEGER, INTENT(IN) :: i
    30         CHARACTER(len=100), INTENT(OUT) :: str_i
    31        
    32        
    33         !INT -> CHAR:
    34         CHARACTER(len=10) :: num
    35         WRITE(num, "(I5)") i
    36         str_i = TRIM(ADJUSTL(str//"_"//TRIM(ADJUSTL(num))))
    37        
     31    SUBROUTINE concat(str, str2, str_str2)
     32        CHARACTER(len=*), INTENT(IN) :: str, str2
     33        CHARACTER(len=20), INTENT(OUT) :: str_str2
     34       
     35       
     36        str_str2 = TRIM(ADJUSTL(str//"_"//TRIM(ADJUSTL(str2))))
     37        !IF (prt_level >= 10) WRITE(lunout,*) "Xios. ",str,"+",str2,"=",str_str2
    3838    END SUBROUTINE concat
    3939   
     
    4747       
    4848        INTEGER :: i = 0
    49        
     49         !!!!!!!!!!!!!!!!!!
     50         ! Pour XIOS:
     51         !  year : y
     52         !  month : mo
     53         !  day : d
     54         !  hour : h
     55         !  minute : mi
     56         !  second : s
     57         !!!!!!!!!!!!!!!!!!
     58
    5059        i = INDEX(odate, "day")
    5160        IF (i > 0) THEN
    5261            ndate = odate(1:i-1)//"d"
    53         ELSE
    54             i = INDEX(odate, "hr")
    55             IF (i > 0) THEN
    56                 ndate = odate(1:i-1)//"h"
    57             ELSE
    58                 ndate = odate
    59             END IF
    60         END IF
    61        
    62         !WRITE(*,*) "Xios. ", odate, " => ", ndate
     62        END IF
     63
     64        i = INDEX(odate, "hr")
     65        IF (i > 0) THEN
     66            ndate = odate(1:i-1)//"h"
     67        END IF
     68
     69        i = INDEX(odate, "mth")
     70        IF (i > 0) THEN
     71            ndate = odate(1:i-1)//"mo"
     72        END IF
     73       
     74        !IF (prt_level >= 10) WRITE(lunout,*) "Xios. ", odate, " => ", ndate
    6375    END SUBROUTINE reformadate
    6476   
     
    89101        END IF
    90102       
    91         !WRITE(*,*) "Xios. ", op, " => ", reformaop
     103        !IF (prt_level >= 10) WRITE(lunout,*) "Xios. ", op, " => ", reformaop
    92104    END FUNCTION reformaop
    93105
     
    97109    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    98110
    99     SUBROUTINE wxios_init(xios_ctx_name)
     111    SUBROUTINE wxios_init(xios_ctx_name, locom, outcom)
     112        IMPLICIT NONE
     113        INCLUDE 'iniprint.h'
     114
    100115      CHARACTER(len=*), INTENT(IN) :: xios_ctx_name
    101        
    102       INTEGER :: xios_comm
     116      INTEGER, INTENT(IN), OPTIONAL :: locom
     117      INTEGER, INTENT(OUT), OPTIONAL :: outcom
     118
     119   
    103120        TYPE(xios_context) :: xios_ctx
    104      
    105         WRITE(*,*) "Xios. Initialization"
    106 
    107         !Lancement de xios:
    108         CALL xios_initialize(xios_ctx_name, return_comm = xios_comm )
    109        
    110         !Initialisation du contexte:
    111         CALL xios_context_initialize(xios_ctx_name, xios_comm)
    112         CALL xios_get_handle(xios_ctx_name, xios_ctx)    !Récupération
    113         CALL xios_set_current_context(xios_ctx)            !Activation
     121        INTEGER :: xios_comm
     122
     123        IF (prt_level >= 10) WRITE(lunout,*) "wxios_init: Initialization"
     124
     125
     126
     127        IF (PRESENT(locom)) THEN
     128          CALL xios_initialize(xios_ctx_name, local_comm = locom, return_comm = xios_comm )
     129          IF (prt_level >= 10) WRITE(lunout,*) "wxios_init: ctx=",xios_ctx_name," local_comm=",locom,", return_comm=",xios_comm
     130        ELSE
     131          CALL xios_initialize(xios_ctx_name, return_comm = xios_comm )
     132          IF (prt_level >= 10) WRITE(lunout,*) "wxios_init: ctx=",xios_ctx_name," return_comm=",xios_comm
     133        END IF
     134       
     135        IF (PRESENT(outcom)) THEN
     136          outcom = xios_comm
     137          IF (prt_level >= 10) WRITE(lunout,*) "wxios_init: ctx=",xios_ctx_name," outcom=",outcom
     138        END IF
    114139       
    115140        !Enregistrement des variables globales:
    116141        g_comm = xios_comm
    117142        g_ctx_name = xios_ctx_name
     143       
     144        CALL wxios_context_init()
     145       
     146    END SUBROUTINE wxios_init
     147
     148    SUBROUTINE wxios_context_init()
     149        IMPLICIT NONE
     150        INCLUDE 'iniprint.h'
     151
     152        TYPE(xios_context) :: xios_ctx
     153
     154        !Initialisation du contexte:
     155        CALL xios_context_initialize(g_ctx_name, g_comm)
     156        CALL xios_get_handle(g_ctx_name, xios_ctx)    !Récupération
     157        CALL xios_set_current_context(xios_ctx)            !Activation
    118158        g_ctx = xios_ctx
    119        
    120         WRITE(*,*) "Xios. Current context is ", xios_ctx_name
    121     END SUBROUTINE wxios_init
     159
     160        IF (prt_level >= 10) WRITE(lunout,*) "wxios_context_init: Current context is ",trim(g_ctx_name)
     161
     162        !Une première analyse des héritages:
     163        CALL xios_solve_inheritance()
     164    END SUBROUTINE wxios_context_init
    122165
    123166    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    126169
    127170    SUBROUTINE wxios_set_cal(pasdetemps, calendrier, annee, mois, jour, heure)
     171        IMPLICIT NONE
     172        INCLUDE 'iniprint.h'
     173
    128174     !Paramètres:
    129175     CHARACTER(len=*), INTENT(IN) :: calendrier
     
    146192            CASE('earth_360d')
    147193                CALL xios_set_context_attr_hdl(g_ctx, calendar_type= "D360")
    148                 WRITE(*,*) 'Xios. Calendrier terrestre a 360 jours/an'
     194                IF (prt_level >= 10) WRITE(lunout,*) 'wxios_set_cal: Calendrier terrestre a 360 jours/an'
    149195            CASE('earth_365d')
    150196                CALL xios_set_context_attr_hdl(g_ctx, calendar_type= "NoLeap")
    151                 WRITE(*,*) 'Xios. Calendrier terrestre a 365 jours/an'
     197                IF (prt_level >= 10) WRITE(lunout,*) 'wxios_set_cal: Calendrier terrestre a 365 jours/an'
    152198            CASE('earth_366d')
    153199                CALL xios_set_context_attr_hdl(g_ctx, calendar_type= "Gregorian")
    154                 WRITE(*,*) 'Xios. Calendrier gregorien'
     200                IF (prt_level >= 10) WRITE(lunout,*) 'wxios_set_cal: Calendrier gregorien'
    155201            CASE DEFAULT
    156                 abort_message = 'Xios. Mauvais choix de calendrier'
     202                abort_message = 'wxios_set_cal: Mauvais choix de calendrier'
    157203                CALL abort_gcm('Gcm:Xios',abort_message,1)
    158204        END SELECT
     
    161207        WRITE(date, "(i4.4,'-',i2.2,'-',i2.2,' 00:00:00')") annee, mois, jour
    162208       
    163         WRITE(*,*) "Xios. Initial time: ", date
     209        IF (prt_level >= 10) WRITE(lunout,*) "wxios_set_cal: Initial time: ", date
    164210       
    165211        CALL xios_set_context_attr_hdl(g_ctx, start_date= date)
     
    167213        !Et enfin,le pas de temps:
    168214        CALL xios_set_timestep(mdtime)
    169         WRITE(*,*) "Xios. ts=",mdtime
     215        IF (prt_level >= 10) WRITE(lunout,*) "wxios_set_cal: ts=",mdtime
    170216    END SUBROUTINE wxios_set_cal
     217
     218    SUBROUTINE wxios_set_timestep(ts)
     219        REAL, INTENT(IN) :: ts
     220        TYPE(xios_time) :: mdtime     
     221
     222        mdtime = xios_time(0, 0, 0, 0, 0, ts)
     223
     224        CALL xios_set_timestep(mdtime)
     225    END SUBROUTINE wxios_set_timestep
    171226
    172227    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    173228    ! Pour initialiser un domaine !!!!!!!!!!!!!!!!!!!!
    174229    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    175     SUBROUTINE wxios_domain_param(dom_id, is_sequential, iim, jjm, io_lat, io_lon)
     230    SUBROUTINE wxios_domain_param(dom_id, is_sequential, ni, nj, ni_glo, nj_glo,        &
     231                                    ibegin, iend, ii_begin, ii_end, jbegin, jend,       &
     232                                    data_ni, data_ibegin, data_iend,                    &
     233                                    io_lat, io_lon,is_south_pole,mpi_rank)
    176234         
    177         CHARACTER (len=*), INTENT(IN) :: dom_id
    178         LOGICAL, INTENT(IN) :: is_sequential
    179         INTEGER, INTENT(IN) :: iim, jjm
    180         REAL, DIMENSION(:) :: io_lat, io_lon
    181        
     235
     236        IMPLICIT NONE
     237        INCLUDE 'iniprint.h'
     238
     239        CHARACTER(len=*),INTENT(IN) :: dom_id ! domain identifier
     240        LOGICAL,INTENT(IN) :: is_sequential ! flag
     241        INTEGER,INTENT(IN) :: ni ! local MPI domain number of longitudes
     242        INTEGER,INTENT(IN) :: nj ! local MPI domain number of latitudes
     243        INTEGER,INTENT(IN) :: ni_glo ! global grid number of longitudes
     244        INTEGER,INTENT(IN) :: nj_glo ! global grid number of latitudes
     245        INTEGER,INTENT(IN) :: ibegin ! start index, on global grid, of local MPI domain
     246        INTEGER,INTENT(IN) :: iend ! end index, on global grid, of local MPI domain
     247        INTEGER,INTENT(IN) :: ii_begin ! i index at which local data starts (first row)
     248        INTEGER,INTENT(IN) :: ii_end ! i index at which local data ends (last row)
     249        INTEGER,INTENT(IN) :: jbegin ! start index, on global grid, of local MPI domain
     250        INTEGER,INTENT(IN) :: jend ! end index, on global grid, of local MPI domain
     251        INTEGER,INTENT(IN) :: data_ni
     252        INTEGER,INTENT(IN) :: data_ibegin
     253        INTEGER,INTENT(IN) :: data_iend
     254        REAL,INTENT(IN) :: io_lat(:) ! latitudes (of global grid)
     255        REAL,INTENT(IN) :: io_lon(:) ! longitudes (of global grid)
     256        logical,intent(in) :: is_south_pole ! does this process include the south pole?
     257        integer,intent(in) :: mpi_rank ! rank of process
    182258       
    183259        TYPE(xios_domain) :: dom
    184         INTEGER :: ni, nj, ni_glo, nj_glo, ibegin, iend, jbegin, jend
    185         LOGICAl :: boool
    186        
    187         ni_glo = iim
    188         nj_glo = jjm
    189         ni = iim
    190         nj = jjm
    191         ibegin = 1
    192         jbegin = 1
    193         iend = ibegin + ni - 1
    194         jend = jbegin + nj - 1
     260        LOGICAL :: boool
     261       
     262        !Masque pour les problèmes de recouvrement MPI:
     263        LOGICAL :: mask(ni,nj)
    195264       
    196265        !On récupère le handle:
    197266        CALL xios_get_domain_handle(dom_id, dom)
    198267       
    199         WRITE(*,*) "Xios. ni:",iim," ni_glo:", iim, " nj:", jjm, " nj_glo:", jjm
    200         WRITE(*,*) "Xios. Size lon:", SIZE(io_lon), " lat:", SIZE(io_lat)
     268        IF (prt_level >= 10) THEN
     269          WRITE(lunout,*) "wxios_domain_param: mpirank=",mpi_rank," ni:",ni," ni_glo:", ni_glo, " nj:", nj, " nj_glo:", nj_glo
     270          WRITE(lunout,*) "wxios_domain_param: mpirank=",mpi_rank," ibegin:",ibegin," iend:", iend, " jbegin:", jbegin, " jend:", jend
     271          WRITE(lunout,*) "wxios_domain_param: mpirank=",mpi_rank," ii_begin:",ii_begin," ii_end:", ii_end
     272          WRITE(lunout,*) "wxios_domain_param: mpirank=",mpi_rank," Size io_lon:", SIZE(io_lon(ibegin:iend)), " io_lat:", SIZE(io_lat(jbegin:jend))
     273        ENDIF
    201274       
    202275        !On parametrise le domaine:
    203         !IF (is_sequential) THEN
    204             CALL xios_set_domain_attr_hdl(dom, ni_glo=iim, ibegin=1, ni=iim,&
    205             & nj_glo=jjm, jbegin=1,nj=jjm,&
    206             & lonvalue=io_lon(ibegin:iend), latvalue=io_lat(jbegin:jend))
    207         !END IF
     276        CALL xios_set_domain_attr_hdl(dom, ni_glo=ni_glo, ibegin=ibegin, ni=ni)
     277        CALL xios_set_domain_attr_hdl(dom, nj_glo=nj_glo, jbegin=jbegin, nj=nj, data_dim=2)
     278        CALL xios_set_domain_attr_hdl(dom, lonvalue=io_lon(ibegin:iend), latvalue=io_lat(jbegin:jend))
     279
     280        IF (.NOT.is_sequential) THEN
     281            mask(:,:)=.TRUE.
     282            if (ii_begin>1) mask(1:ii_begin-1,1) = .FALSE.
     283            if (ii_end<ni) mask(ii_end+1:ni,nj) = .FALSE.
     284            ! special case for south pole
     285            if ((ii_end.eq.1).and.(is_south_pole)) mask(1:ni,nj)=.true.
     286            IF (prt_level >= 10) THEN
     287              WRITE(lunout,*) "wxios_domain_param: mpirank=",mpi_rank," mask(:,1)=",mask(:,1)
     288              WRITE(lunout,*) "wxios_domain_param: mpirank=",mpi_rank," mask(:,nj)=",mask(:,nj)
     289            ENDIF
     290            CALL xios_set_domain_attr_hdl(dom, mask=mask)
     291        END IF
     292
    208293         CALL xios_is_defined_domain_attr_hdl(dom,ni_glo=boool)
    209294        !Vérification:
    210295        IF (xios_is_valid_domain(dom_id)) THEN
    211             WRITE(*,*) "Xios. Domain initialized: ", dom_id, boool
    212         ELSE
    213             WRITE(*,*) "Xios. Invalid domain: ", dom_id
     296            IF (prt_level >= 10) WRITE(lunout,*) "wxios_domain_param: Domain initialized: ", trim(dom_id), boool
     297        ELSE
     298            IF (prt_level >= 10) WRITE(lunout,*) "wxios_domain_param: Invalid domain: ", trim(dom_id)
    214299        END IF
    215300    END SUBROUTINE wxios_domain_param
     
    218303    ! Pour déclarer un axe vertical !!!!!!!!!!!!!!!
    219304    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    220     SUBROUTINE wxios_add_vaxis(axisgroup_id, axis_file_id, axis_size, axis_value)
    221         CHARACTER (len=*), INTENT(IN) :: axisgroup_id
    222         INTEGER, INTENT(IN) :: axis_file_id, axis_size
     305    SUBROUTINE wxios_add_vaxis(axisgroup_id, axis_file, axis_size, axis_value)
     306        IMPLICIT NONE
     307        INCLUDE 'iniprint.h'
     308
     309        CHARACTER (len=*), INTENT(IN) :: axisgroup_id, axis_file
     310        INTEGER, INTENT(IN) :: axis_size
    223311        REAL, DIMENSION(axis_size), INTENT(IN) :: axis_value
    224312       
    225313        TYPE(xios_axisgroup) :: axgroup
    226314        TYPE(xios_axis) :: ax
    227         CHARACTER(len=100) :: axis_id
     315        CHARACTER(len=20) :: axis_id
    228316       
    229317       
    230318        !Préparation du nom de l'axe:
    231         CALL concat(axisgroup_id, axis_file_id, axis_id)
     319        CALL concat(axisgroup_id, axis_file, axis_id)
    232320       
    233321        !On récupère le groupe d'axes qui va bien:
     
    235323       
    236324        !On ajoute l'axe correspondant à ce fichier:
    237         CALL xios_add_axis(axgroup, ax, axis_id)
     325        CALL xios_add_axis(axgroup, ax, TRIM(ADJUSTL(axis_id)))
    238326       
    239327        !Et on le parametrise:
     
    241329       
    242330        !Vérification:
    243         IF (xios_is_valid_axis(axis_id)) THEN
    244             WRITE(*,*) "Xios. Axis created: ", axis_id
    245         ELSE
    246             WRITE(*,*) "Xios. Invalid axis: ", axis_id
     331        IF (xios_is_valid_axis(TRIM(ADJUSTL(axis_id)))) THEN
     332            IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_vaxis: Axis created: ", TRIM(ADJUSTL(axis_id))
     333        ELSE
     334            WRITE(*,*) "wxios_add_vaxis: Invalid axis: ", TRIM(ADJUSTL(axis_id))
    247335        END IF
    248336
     
    254342    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    255343    SUBROUTINE wxios_add_file(fname, ffreq, flvl)
     344        IMPLICIT NONE
     345        INCLUDE 'iniprint.h'
     346
    256347        CHARACTER(len=*), INTENT(IN) :: fname
    257348        CHARACTER(len=*), INTENT(IN) :: ffreq
     
    262353        CHARACTER(len=100) :: nffreq
    263354       
    264         !On créé le noeud:
    265         CALL xios_get_filegroup_handle("defile", x_fg)
    266         CALL xios_add_file(x_fg, x_file, "X"//fname)
    267        
    268         !On reformate la fréquence:
    269         CALL reformadate(ffreq, nffreq)
    270        
    271         !On configure:
    272         CALL xios_set_file_attr_hdl(x_file, name="X"//fname,&
     355        !On regarde si le fichier n'est pas défini par XML:
     356        IF (.NOT.xios_is_valid_file(fname)) THEN
     357            !On créé le noeud:
     358            CALL xios_get_filegroup_handle("defile", x_fg)
     359            CALL xios_add_file(x_fg, x_file, fname)
     360       
     361            !On reformate la fréquence:
     362            CALL reformadate(ffreq, nffreq)
     363       
     364            !On configure:
     365            CALL xios_set_file_attr_hdl(x_file, name="X"//fname,&
    273366                output_freq=TRIM(ADJUSTL(nffreq)), output_level=flvl, enabled=.TRUE.)
    274367       
    275         IF (xios_is_valid_file("X"//fname)) THEN
    276             WRITE(*,*) "Xios. New file: ", "X"//fname
    277             WRITE(*,*) "Xios. output_freq=",TRIM(ADJUSTL(nffreq)),"; output_lvl=",flvl
    278         ELSE
    279             WRITE(*,*) "Xios. Error, invalid file: ", "X"//fname
    280             WRITE(*,*) "Xios. output_freq=",TRIM(ADJUSTL(nffreq)),"; output_lvl=",flvl
     368            IF (xios_is_valid_file("X"//fname)) THEN
     369                IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_file: New file: ", "X"//fname
     370                IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_file: output_freq=",TRIM(ADJUSTL(nffreq)),"; output_lvl=",flvl
     371            ELSE
     372                WRITE(*,*) "wxios_add_file: Error, invalid file: ", "X"//trim(fname)
     373                WRITE(*,*) "wxios_add_file: output_freq=",TRIM(ADJUSTL(nffreq)),"; output_lvl=",flvl
     374            END IF
     375        ELSE
     376            IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_file: File ",trim(fname), " défined using XML."
     377                CALL xios_set_file_attr(fname, enabled=.TRUE.)
    281378        END IF
    282379    END SUBROUTINE wxios_add_file
     
    286383    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    287384    SUBROUTINE wxios_add_field(fieldname, fieldgroup, fieldlongname, fieldunit)
    288         USE netcdf
     385        USE netcdf, only: nf90_fill_real
     386
     387        IMPLICIT NONE
     388        INCLUDE 'iniprint.h'
    289389       
    290390        CHARACTER(len=*), INTENT(IN) :: fieldname
     
    308408        !On ajoute le champ:
    309409        CALL xios_add_field(fieldgroup, field, fieldname)
    310         !WRITE(*,*) "Xios. ",fieldname,fieldgroup, fieldlongname, fieldunit
     410        !IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_field: ",fieldname,fieldgroup, fieldlongname, fieldunit
    311411       
    312412        !On rentre ses paramètres:
    313413        CALL xios_set_field_attr_hdl(field, standard_name=fieldlongname, unit=newunit, default_value=def)
    314         WRITE(*,*) "Xios. Champ ", fieldname, "cree:"
    315         WRITE(*,*) "Xios. long_name=",fieldlongname,"; unit=",newunit,";  default_value=",nf90_fill_real
     414        IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_field: Field ",trim(fieldname), "cree:"
     415        IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_field: long_name=",trim(fieldlongname),"; unit=",trim(newunit),";  default_value=",nf90_fill_real
    316416
    317417    END SUBROUTINE wxios_add_field
     
    321421    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    322422    SUBROUTINE wxios_add_field_to_file(fieldname, fdim, fid, fname, fieldlongname, fieldunit, field_level, op)
     423        IMPLICIT NONE
     424        INCLUDE 'iniprint.h'
     425
    323426        CHARACTER(len=*), INTENT(IN) :: fieldname
    324427        INTEGER, INTENT(IN)          :: fdim, fid
     
    329432        CHARACTER(len=*), INTENT(IN) :: op
    330433       
    331         CHARACTER(len=100) :: axis_id
     434        CHARACTER(len=20) :: axis_id
    332435        CHARACTER(len=100) :: operation
    333436        TYPE(xios_file) :: f
    334437        TYPE(xios_field) :: field
    335438        TYPE(xios_fieldgroup) :: fieldgroup
     439        LOGICAL :: bool=.FALSE.
     440        INTEGER :: lvl =0
    336441       
    337442       
    338443        !Préparation du nom de l'axe:
    339         CALL concat("presnivs", fid, axis_id)
     444        CALL concat("presnivs", fname, axis_id)
    340445       
    341446        !on prépare le nom de l'opération:
     
    352457       
    353458        !On regarde si le champ à déjà été créé ou non:
    354         IF (xios_is_valid_field(fieldname)) THEN
    355             WRITE(*,*) "Xios. Champ ", fieldname, "existe"
    356         ELSE
    357             WRITE(*,*) "Xios. Champ ", fieldname, "nexiste pas"
     459        IF (xios_is_valid_field(fieldname) .AND. .NOT. g_field_name == fieldname) THEN
     460            !Si ce champ existe via XML (ie, dès le premier passage, ie g_field_name != fieldname) alors rien d'autre à faire
     461            IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_field_to_file: Field ", trim(fieldname), "exists via XML"
     462            g_flag_xml = .TRUE.
     463            g_field_name = fieldname
     464
     465        ELSE IF (.NOT. g_field_name == fieldname) THEN
     466            !Si premier pssage et champ indéfini, alors on le créé
     467
     468            IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_field_to_file: Field ", trim(fieldname), "does not exist"
    358469           
    359470            !On le créé:
    360471            CALL wxios_add_field(fieldname,  fieldgroup, fieldlongname, fieldunit)
    361472            IF (xios_is_valid_field(fieldname)) THEN
    362                 WRITE(*,*) "Xios. Champ ", fieldname, "cree"
     473                IF (prt_level >= 10) WRITE(lunout,*) "wxios_add_field_to_file: Field ", trim(fieldname), "created"
    363474            ENDIF
    364         ENDIF
    365        
    366         !On ajoute le champ:
    367         CALL xios_get_file_handle("X"//fname, f)
    368         CALL xios_add_fieldtofile(f, field)
    369        
    370        
    371         !L'operation, sa frequence:
    372         CALL xios_set_field_attr_hdl(field, field_ref=fieldname, operation=TRIM(ADJUSTL(operation)), freq_op="1ts", prec=4)
    373 
    374        
    375         !On rentre ses paramètres:
    376         CALL xios_set_field_attr_hdl(field, level=field_level, enabled=.TRUE.)
    377        
    378         IF (fdim.EQ.2) THEN
    379             !Si c'est un champ 2D:
    380             WRITE(*,*) "Xios. Champ 2D ", fieldname, " de ", "X"//fname ," configure:"
    381             WRITE (*,*) "Xios. op=", TRIM(ADJUSTL(operation))
    382             WRITE(*,*) "Xios. freq_op=1ts","; lvl=",field_level
    383         ELSE
    384             !Si 3D :
    385             !On ajoute l'axe vertical qui va bien:
    386             CALL xios_set_field_attr_hdl(field, axis_ref=axis_id)
     475
     476            g_flag_xml = .FALSE.
     477            g_field_name = fieldname
     478
     479        END IF
     480
     481        IF (.NOT. g_flag_xml) THEN
     482            !Champ existe déjà, mais pas XML, alors on l'ajoute
     483            !On ajoute le champ:
     484            CALL xios_get_file_handle(fname, f)
     485            CALL xios_add_fieldtofile(f, field)
    387486           
    388             WRITE(*,*) "Xios. Champ 3D ", fieldname, " de ", "X"//fname, "configure:"
    389             WRITE(*,*) "Xios. freq_op=1ts","; lvl=",field_level
    390             WRITE(*,*) "Xios. axe=",axis_id
    391         END IF
     487           
     488            !L'operation, sa frequence:
     489            CALL xios_set_field_attr_hdl(field, field_ref=fieldname, operation=TRIM(ADJUSTL(operation)), freq_op="1ts", prec=4)
     490
     491           
     492            !On rentre ses paramètres:
     493            CALL xios_set_field_attr_hdl(field, level=field_level, enabled=.TRUE.)
     494           
     495            IF (fdim.EQ.2) THEN
     496                !Si c'est un champ 2D:
     497                IF (prt_level >= 10) THEN
     498                  WRITE(lunout,*) "wxios_add_field_to_file: 2D Field ", trim(fieldname), " in ", "X"//trim(fname) ," configured with:"
     499                  WRITE(lunout,*) "wxios_add_field_to_file: op=", TRIM(ADJUSTL(operation))
     500                  WRITE(lunout,*) "wxios_add_field_to_file: freq_op=1ts","; lvl=",field_level
     501                ENDIF
     502            ELSE
     503                !Si 3D :
     504                !On ajoute l'axe vertical qui va bien:
     505                CALL xios_set_field_attr_hdl(field, axis_ref=TRIM(ADJUSTL(axis_id)))
     506               
     507                IF (prt_level >= 10) THEN
     508                  WRITE(lunout,*) "wxios_add_field_to_file: 3D Field",trim(fieldname), " in ", "X"//trim(fname), "configured with:"
     509                  WRITE(lunout,*) "wxios_add_field_to_file: freq_op=1ts","; lvl=",field_level
     510                  WRITE(lunout,*) "wxios_add_field_to_file: axis=",TRIM(ADJUSTL(axis_id))
     511                ENDIF
     512            END IF
     513       
     514        ELSE
     515            !Sinon on se contente de l'activer:
     516            CALL xios_set_field_attr(fieldname, enabled=.TRUE.)
     517        ENDIF       
    392518       
    393519    END SUBROUTINE wxios_add_field_to_file
Note: See TracChangeset for help on using the changeset viewer.