Changeset 1575


Ignore:
Timestamp:
Jul 13, 2016, 4:29:03 PM (8 years ago)
Author:
emillour
Message:

All GCMs:
Further adaptations to keep up with changes in LMDZ5 concerning
physics/dynamics separation (up to rev r2575 of LMDZ5)

  • dyn3d_common:
  • infotrac.F90 : propagate initialisations for INCA (Earth GCM)
  • misc:
  • wxios.F90: updates to use the XIOS2 library
  • dynphy_lonlat:
  • grid_atob_m.F90: fix for some zoomed grid interpolation cases

EM

Location:
trunk
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/DOC/chantiers/commit_importants.log

    r1573 r1575  
    18441844routine.
    18451845
     1846**********************
     1847**** commit_v1575 ****
     1848**********************
     1849Ehouarn: Further adaptations to keep up with changes in LMDZ5 concerning
     1850physics/dynamics separation (up to rev r2575 of LMDZ5)
     1851
     1852* dyn3d_common:
     1853- infotrac.F90 : propagate initialisations for INCA (Earth GCM)
     1854
     1855* misc:
     1856- wxios.F90: updates to use the XIOS2 library
     1857
     1858* dynphy_lonlat:
     1859- grid_atob_m.F90: fix for some zoomed grid interpolation cases
     1860
  • trunk/LMDZ.COMMON/libf/dyn3d_common/infotrac.F90

    r1549 r1575  
    8686    INTEGER, ALLOCATABLE, DIMENSION(:) :: hadv  ! index of horizontal trasport schema
    8787    INTEGER, ALLOCATABLE, DIMENSION(:) :: vadv  ! index of vertical trasport schema
     88
     89    INTEGER, ALLOCATABLE, DIMENSION(:) :: hadv_inca  ! index of horizontal trasport schema
     90    INTEGER, ALLOCATABLE, DIMENSION(:) :: vadv_inca  ! index of vertical trasport schema
    8891
    8992    CHARACTER(len=15), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
     
    196199#endif
    197200       nqtrue=nbtr+nqo
     201
     202       ALLOCATE(hadv_inca(nbtr), vadv_inca(nbtr))
     203
    198204     END IF   ! type_trac
    199205
     
    375381!>jyg
    376382! le module de chimie fournit les noms des traceurs
    377 ! et les schemas d'advection associes.
     383! et les schemas d'advection associes. excepte pour ceux lus
     384! dans traceur.def
     385       IF (ierr .eq. 0) then
     386          DO iq=1,nqo
     387
     388             write(*,*) 'infotrac 237: iq=',iq
     389             ! CRisi: ajout du nom du fluide transporteur
     390             ! mais rester retro compatible
     391             READ(90,'(I2,X,I2,X,A)',IOSTAT=IOstatus) hadv(iq),vadv(iq),tchaine
     392             write(lunout,*) 'iq,hadv(iq),vadv(iq)=',iq,hadv(iq),vadv(iq)
     393             write(lunout,*) 'tchaine=',trim(tchaine)
     394             write(*,*) 'infotrac 238: IOstatus=',IOstatus
     395             if (IOstatus.ne.0) then
     396                CALL abort_gcm('infotrac_init','Pb dans la lecture de traceur.def',1)
     397             endif
     398             ! Y-a-t-il 1 ou 2 noms de traceurs? -> On regarde s'il y a un
     399             ! espace ou pas au milieu de la chaine.
     400             continu=.true.
     401             nouveau_traceurdef=.false.
     402             iiq=1
     403             do while (continu)
     404                if (tchaine(iiq:iiq).eq.' ') then
     405                  nouveau_traceurdef=.true.
     406                  continu=.false.
     407                else if (iiq.lt.LEN_TRIM(tchaine)) then
     408                  iiq=iiq+1
     409                else
     410                  continu=.false.
     411                endif
     412             enddo
     413             write(*,*) 'iiq,nouveau_traceurdef=',iiq,nouveau_traceurdef
     414             if (nouveau_traceurdef) then
     415                write(lunout,*) 'C''est la nouvelle version de traceur.def'
     416                tnom_0(iq)=tchaine(1:iiq-1)
     417                tnom_transp(iq)=tchaine(iiq+1:15)
     418             else
     419                write(lunout,*) 'C''est l''ancienne version de traceur.def'
     420                write(lunout,*) 'On suppose que les traceurs sont tous d''air'
     421                tnom_0(iq)=tchaine
     422                tnom_transp(iq) = 'air'
     423             endif
     424             write(lunout,*) 'tnom_0(iq)=<',trim(tnom_0(iq)),'>'
     425             write(lunout,*) 'tnom_transp(iq)=<',trim(tnom_transp(iq)),'>'
     426
     427          END DO !DO iq=1,nqtrue
     428          CLOSE(90) 
     429       ELSE  !! if traceur.def doesn't exist
     430          tnom_0(1)='H2Ov'
     431          tnom_transp(1) = 'air'
     432          tnom_0(2)='H2Ol'
     433          tnom_transp(2) = 'air'
     434          hadv(1) = 10
     435          hadv(2) = 10
     436          vadv(1) = 10
     437          vadv(2) = 10
     438       ENDIF
    378439     
    379440#ifdef INCA
    380441       CALL init_transport( &
    381             hadv, &
    382             vadv, &
     442            hadv_inca, &
     443            vadv_inca, &
    383444            conv_flg, &
    384445            pbl_flg,  &
    385446            tracnam)
    386447#endif
    387        tnom_0(1)='H2Ov'
    388        tnom_transp(1) = 'air'
    389        tnom_0(2)='H2Ol'
    390        tnom_transp(2) = 'air'
    391        IF (nqo == 3) then
    392          tnom_0(3)='H2Oi'     !! jyg
    393          tnom_transp(3) = 'air'
    394        endif
    395448
    396449!jyg<
  • trunk/LMDZ.COMMON/libf/dynphy_lonlat/grid_atob_m.F90

    r1508 r1575  
    66
    77  USE assert_eq_m, ONLY: assert_eq
    8   REAL, SAVE :: pi, deg2rad
    98
    109  PRIVATE
     
    2221! Arguments:
    2322  REAL,              INTENT(IN)  :: x_i(:), y_i(:) !-- INPUT  X&Y COOR. (mi)(ni)
    24   REAL,              INTENT(IN)  :: x_o(:), y_o(:) !-- OUTPUT X&Y COOR. (mi)(ni)
     23  REAL,              INTENT(IN)  :: x_o(:), y_o(:) !-- OUTPUT X&Y COOR. (mo)(no)
    2524  REAL,              INTENT(OUT) :: d_o1(:,:)      !-- OUTPUT FIELD     (mo,no)
    2625  REAL,    OPTIONAL, INTENT(IN)  :: d_i (:,:)      !-- INPUT FIELD      (mi,ni)
    27   LOGICAL, OPTIONAL, INTENT(IN)  :: msk (:,:)      !-- MASK             (mi,ni)
     26  LOGICAL, OPTIONAL, INTENT(IN)  :: msk (:,:)      !-- MASK             (mo,no)
    2827  REAL,    OPTIONAL, INTENT(OUT) :: d_o2(:,:)      !-- OUTPUT FOR d_i^2 (mo,no)
    2928!-------------------------------------------------------------------------------
    3029! Local variables:
    3130  CHARACTER(LEN=256) :: modname="fine2coarse"
    32   INTEGER :: mi, ni, ii, ji, mo, no, io, jo, nr(2), m1, n1, m2, n2, nn
    33   INTEGER :: num_tot(SIZE(x_o),SIZE(y_o))
    34   LOGICAL :: found(SIZE(x_o),SIZE(y_o)), li
    35   LOGICAL :: mask (SIZE(x_i),SIZE(y_i)), lo
    36   REAL    :: dist (SIZE(x_o),SIZE(y_o))
    37   REAL    :: a(SIZE(x_o)), b(SIZE(x_o)), c(SIZE(y_o)), d(SIZE(y_o)), inc
    38   REAL, PARAMETER :: thresh=1.E-5
    39 !-------------------------------------------------------------------------------
    40   mask(:,:)=.TRUE.; IF(PRESENT(msk)) mask(:,:)=msk(:,:)
    41   mi=SIZE(x_i); m1=mi; ni=SIZE(y_i); n1=ni
    42   mo=SIZE(x_o); m2=mo; no=SIZE(y_o); n2=no
     31  INTEGER :: mi, ni, ii, ji, mo, no, io, jo, nr(2), m1,m2, n1,n2, mx,my, nn, i,j
     32  LOGICAL :: li, lo, first=.TRUE.
     33  REAL    :: inc, cpa, spa, crlo(SIZE(x_i))
     34  REAL, SAVE :: pi, hpi
     35  INTEGER, DIMENSION(SIZE(x_o),SIZE(y_o)) :: num_tot
     36  LOGICAL, DIMENSION(SIZE(x_o),SIZE(y_o)) :: found, mask
     37  REAL,    DIMENSION(SIZE(x_i),SIZE(y_i)) :: dist
     38  REAL,    DIMENSION(SIZE(x_o))           :: a, b
     39  REAL,    DIMENSION(SIZE(y_o))           :: c, d
     40  REAL,    PARAMETER :: thresh=1.E-5
     41!-------------------------------------------------------------------------------
     42  IF(first) THEN; pi=4.0*ATAN(1.0); hpi=pi/2.0; first=.FALSE.; END IF
     43  mi=SIZE(x_i); ni=SIZE(y_i); mo=SIZE(x_o); no=SIZE(y_o)
     44  m1=m1; m2=mo; mx=mo; IF(PRESENT(msk)) mx=SIZE(msk,1)
     45  n1=ni; n2=no; my=no; IF(PRESENT(msk)) my=SIZE(msk,2)
    4346  li=PRESENT(d_i ); IF(li) THEN; m1=SIZE(d_i ,1); n1=SIZE(d_i ,2); END IF
    4447  lo=PRESENT(d_o2); IF(lo) THEN; m2=SIZE(d_o2,1); n2=SIZE(d_o2,2); END IF
    45   mi=assert_eq(mi,m1,SIZE(mask,1),TRIM(modname)//" mi")
    46   ni=assert_eq(ni,n1,SIZE(mask,2),TRIM(modname)//" ni")
    47   mo=assert_eq(mo,m2,SIZE(d_o1,1),TRIM(modname)//" mo")
    48   no=assert_eq(no,n2,SIZE(d_o1,2),TRIM(modname)//" no")
     48  mi=assert_eq(mi,m1,TRIM(modname)//" mi")
     49  ni=assert_eq(ni,n1,TRIM(modname)//" ni")
     50  mo=assert_eq(mo,m2,mx,SIZE(d_o1,1),TRIM(modname)//" mo")
     51  no=assert_eq(no,n2,my,SIZE(d_o1,2),TRIM(modname)//" no")
     52  mask(:,:)=.TRUE.; IF(PRESENT(msk)) mask(:,:)=msk(:,:)
    4953
    5054!--- COMPUTE CELLS INTERFACES COORDINATES OF OUTPUT GRID
     
    6771             (x_i(ii)-a(io)>thresh.OR.x_i(ii)-b(io)<thresh)) CYCLE
    6872          num_tot(io,jo)=num_tot(io,jo)+1
    69           IF(mask(ii,ji)) d_o1(io,jo)=d_o1(io,jo)+inc
     73          IF(mask(io,jo)) d_o1(io,jo)=d_o1(io,jo)+inc
    7074          IF(.NOT.lo) CYCLE
    71           IF(mask(ii,ji)) d_o2(io,jo)=d_o2(io,jo)+inc*inc
     75          IF(mask(io,jo)) d_o2(io,jo)=d_o2(io,jo)+inc*inc
    7276        END DO
    7377      END DO
     
    8993      IF(found(io,jo)) CYCLE
    9094!      IF(prt_level>=1) PRINT*, "Problem: point out of domain (i,j)=", io,jo
    91       CALL dist_sphe(x_o(io),y_o(jo),x_i,y_i,dist(:,:))
     95      crlo(:)=COS(x_o(io)-x_i(:))     !--- COS of points 1 and 2 angle
     96      cpa=COS(y_o(jo)); spa=SIN(y_o(jo))
     97      DO j=1,ni; dist(:,j)=ACOS(spa*SIN(y_i(j))+cpa*COS(y_i(j))*crlo(:)); END DO
    9298      nr=MINLOC(dist(:,:))!; IF(prt_level>=1) PRINT*, "Solution: ", nr
    9399      inc=1.0; IF(li) inc=d_i(nr(1),nr(2))
    94       IF(mask(nr(1),nr(2))) d_o1(io,jo)=inc
     100      IF(mask(io,jo)) d_o1(io,jo)=inc
    95101    END DO
    96102  END DO
     
    250256!-------------------------------------------------------------------------------
    251257
    252 
    253 !-------------------------------------------------------------------------------
    254 !
    255 SUBROUTINE dist_sphe(rf_lon,rf_lat,rlon,rlat,distance)
    256 !
    257 !-------------------------------------------------------------------------------
    258 ! Author:  Laurent Li (december 30th 1996).
    259 ! Purpose: Compute min. distance (along big circle) between 2 points in degrees.
    260 !-------------------------------------------------------------------------------
    261   IMPLICIT NONE
    262 !-------------------------------------------------------------------------------
    263 ! Arguments:
    264   REAL, INTENT(IN) :: rf_lon, rf_lat  !--- Reference point coordinates (degrees)
    265   REAL, INTENT(IN) :: rlon(:), rlat(:)!--- Points longitudes/latitudes (degrees)
    266   REAL, INTENT(OUT):: distance(SIZE(rlon),SIZE(rlat)) !--- Distance    (degrees)
    267 !-------------------------------------------------------------------------------
    268 ! Local variables:
    269   LOGICAL, SAVE :: first=.TRUE.
    270   REAL    :: pa, pb, cpa, cpab, spa, spab, crlo(SIZE(rlon))
    271   INTEGER :: i, j
    272 !-------------------------------------------------------------------------------
    273   IF(first) THEN
    274     pi=4.0*ATAN(1.0); deg2rad=pi/180.0; first=.FALSE.
    275   END IF
    276   crlo(:)=COS((rf_lon-rlon(:))*deg2rad)     !--- COS of points 1 and 2 angle
    277   pa=(90.0-rf_lat)*deg2rad                  !--- North Pole - Point 1 distance
    278   cpa=COS(pa); spa=SIN(pa)
    279   DO j=1,SIZE(rlat)
    280     pb=(90.0-rlat(j))*deg2rad               !--- North Pole - Point 2 distance
    281     cpab=cpa*COS(pb); spab=spa*SIN(pb)
    282     distance(:,j)=ACOS(cpab+spab*crlo(:))/deg2rad
    283   END DO
    284 
    285 END SUBROUTINE dist_sphe
    286 !
    287 !-------------------------------------------------------------------------------
    288 
    289258END MODULE grid_atob_m
    290259!
  • trunk/LMDZ.COMMON/libf/misc/wxios.F90

    r1549 r1575  
    1 ! $Id: wxios.F90 $
     1! $Id$
    22#ifdef CPP_XIOS
    33MODULE wxios
     
    3333    SUBROUTINE reformadate(odate, ndate)
    3434        CHARACTER(len=*), INTENT(IN) :: odate
     35#ifdef XIOS1
    3536        CHARACTER(len=100), INTENT(OUT) :: ndate
     37#else
     38        TYPE(xios_duration) :: ndate
     39#endif
    3640       
    3741        INTEGER :: i = 0
     
    4852        i = INDEX(odate, "day")
    4953        IF (i > 0) THEN
     54#ifdef XIOS1
    5055            ndate = odate(1:i-1)//"d"
     56#else
     57            read(odate(1:i-1),*) ndate%day
     58#endif
    5159        END IF
    5260
    5361        i = INDEX(odate, "hr")
    5462        IF (i > 0) THEN
     63#ifdef XIOS1
    5564            ndate = odate(1:i-1)//"h"
     65#else
     66            read(odate(1:i-1),*) ndate%hour
     67#endif
    5668        END IF
    5769
    5870        i = INDEX(odate, "mth")
    5971        IF (i > 0) THEN
     72#ifdef XIOS1
    6073            ndate = odate(1:i-1)//"mo"
     74#else
     75            read(odate(1:i-1),*) ndate%month
     76#endif
    6177        END IF
    6278       
     
    99115
    100116    SUBROUTINE wxios_init(xios_ctx_name, locom, outcom, type_ocean)
    101         IMPLICIT NONE
    102         INCLUDE 'iniprint.h'
     117        USE print_control_mod, ONLY : prt_level, lunout
     118        IMPLICIT NONE
    103119
    104120      CHARACTER(len=*), INTENT(IN) :: xios_ctx_name
     
    140156
    141157    SUBROUTINE wxios_context_init()
    142         IMPLICIT NONE
    143         INCLUDE 'iniprint.h'
     158        USE print_control_mod, ONLY : prt_level, lunout
     159!        USE mod_phys_lmdz_mpi_data, ONLY : COMM_LMDZ_PHY
     160        IMPLICIT NONE
    144161
    145162        TYPE(xios_context) :: xios_ctx
    146163
     164!$OMP MASTER
    147165        !Initialisation du contexte:
    148166        CALL xios_context_initialize(g_ctx_name, g_comm)
     
    157175        !Une première analyse des héritages:
    158176        CALL xios_solve_inheritance()
     177!$OMP END MASTER
    159178    END SUBROUTINE wxios_context_init
    160179
     
    164183
    165184    SUBROUTINE wxios_set_cal(pasdetemps, calendrier, annee, mois, jour, heure, ini_an, ini_mois, ini_jour, ini_heure)
    166         IMPLICIT NONE
    167         INCLUDE 'iniprint.h'
     185        USE print_control_mod, ONLY : prt_level, lunout
     186        IMPLICIT NONE
    168187
    169188     !Paramètres:
     
    178197     
    179198     !Variables pour xios:
     199#ifdef XIOS1
    180200     TYPE(xios_time) :: mdtime
     201#else
     202     TYPE(xios_duration) :: mdtime
     203#endif
    181204     !REAL(kind = 8) :: year=0, month=0, day=0, hour=0, minute=0, second=0
    182205     
     206#ifdef XIOS1
    183207        mdtime = xios_time(0, 0, 0, 0, 0, pasdetemps)
     208#else
     209        mdtime%second=pasdetemps
     210#endif
    184211
    185212        !Réglage du calendrier:
     213#ifdef XIOS1
    186214        SELECT CASE (calendrier)
    187215            CASE('earth_360d')
     
    198226                CALL abort_gcm('Gcm:Xios',abort_message,1)
    199227        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
    200244       
    201245        !Formatage de la date d'origine:
    202         WRITE(date, "(i4.4,'-',i2.2,'-',i2.2,' ',i2.2,':00:00')") annee, mois, jour, int(heure)
     246        WRITE(date, "(i4.4,'-',i2.2,'-',i2.2,' ',i2.2,':00:00')") annee, mois, jour, int(heure) 
    203247       
    204248        IF (prt_level >= 10) WRITE(lunout,*) "wxios_set_cal: Time origin: ", date
    205        
     249#ifdef XIOS1
    206250        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
    207254
    208255        !Formatage de la date de debut:
     
    212259        IF (prt_level >= 10) WRITE(lunout,*) "wxios_set_cal: Start date: ", date
    213260       
     261#ifdef XIOS1
    214262        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
    215266       
    216267        !Et enfin,le pas de temps:
     
    221272    SUBROUTINE wxios_set_timestep(ts)
    222273        REAL, INTENT(IN) :: ts
     274#ifdef XIOS1
    223275        TYPE(xios_time) :: mdtime     
    224276
    225277        mdtime = xios_time(0, 0, 0, 0, 0, ts)
     278#else
     279        TYPE(xios_duration) :: mdtime     
     280
     281        mdtime%timestep = ts
     282#endif
    226283
    227284        CALL xios_set_timestep(mdtime)
     
    237294         
    238295
    239         IMPLICIT NONE
    240         INCLUDE 'iniprint.h'
     296        USE print_control_mod, ONLY : prt_level, lunout
     297        IMPLICIT NONE
    241298
    242299        CHARACTER(len=*),INTENT(IN) :: dom_id ! domain identifier
     
    277334       
    278335        !On parametrise le domaine:
     336#ifdef XIOS1
    279337        CALL xios_set_domain_attr_hdl(dom, ni_glo=ni_glo, ibegin=ibegin, ni=ni)
    280338        CALL xios_set_domain_attr_hdl(dom, nj_glo=nj_glo, jbegin=jbegin, nj=nj, data_dim=2)
    281339        CALL xios_set_domain_attr_hdl(dom, lonvalue=io_lon(ibegin:iend), latvalue=io_lat(jbegin:jend))
    282 
     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), latvalue_1d=io_lat(jbegin:jend))
     344#endif
    283345        IF (.NOT.is_sequential) THEN
    284346            mask(:,:)=.TRUE.
     
    291353              WRITE(lunout,*) "wxios_domain_param: mpirank=",mpi_rank," mask(:,nj)=",mask(:,nj)
    292354            ENDIF
     355#ifdef XIOS1
    293356            CALL xios_set_domain_attr_hdl(dom, mask=mask)
     357#else
     358            CALL xios_set_domain_attr_hdl(dom, mask_2d=mask)
     359#endif
    294360        END IF
    295361
     
    307373    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    308374    SUBROUTINE wxios_add_vaxis(axis_id, axis_size, axis_value)
    309         IMPLICIT NONE
    310         INCLUDE 'iniprint.h'
     375        USE print_control_mod, ONLY : prt_level, lunout
     376        IMPLICIT NONE
    311377
    312378        CHARACTER (len=*), INTENT(IN) :: axis_id
     
    335401       
    336402        ! Ehouarn: New way to declare axis, without axis_group:
     403#ifdef XIOS1
    337404        CALL xios_set_axis_attr(trim(axis_id),size=axis_size,value=axis_value)
    338        
     405#else
     406        CALL xios_set_axis_attr(trim(axis_id),n_glo=axis_size,value=axis_value)
     407#endif       
    339408        !Vérification:
    340409        IF (xios_is_valid_axis(TRIM(ADJUSTL(axis_id)))) THEN
     
    351420    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    352421    SUBROUTINE wxios_add_file(fname, ffreq, flvl)
    353         IMPLICIT NONE
    354         INCLUDE 'iniprint.h'
     422        USE print_control_mod, ONLY : prt_level, lunout
     423        IMPLICIT NONE
    355424
    356425        CHARACTER(len=*), INTENT(IN) :: fname
     
    360429        TYPE(xios_file) :: x_file
    361430        TYPE(xios_filegroup) :: x_fg
     431#ifdef XIOS1
    362432        CHARACTER(len=100) :: nffreq
     433#else
     434        TYPE(xios_duration) :: nffreq
     435#endif
    363436       
    364437        !On regarde si le fichier n'est pas défini par XML:
     
    372445       
    373446            !On configure:
     447#ifdef XIOS1
    374448            CALL xios_set_file_attr_hdl(x_file, name="X"//fname,&
    375449                output_freq=TRIM(ADJUSTL(nffreq)), output_level=flvl, enabled=.TRUE.)
    376        
     450#else
     451            CALL xios_set_file_attr_hdl(x_file, name="X"//fname,&
     452                output_freq=nffreq, output_level=flvl, enabled=.TRUE.)
     453#endif
     454       
    377455            IF (xios_is_valid_file("X"//fname)) THEN
    378456                IF (prt_level >= 10) THEN
    379457                  WRITE(lunout,*) "wxios_add_file: New file: ", "X"//fname
     458#ifdef XIOS1
    380459                  WRITE(lunout,*) "wxios_add_file: output_freq=",TRIM(ADJUSTL(nffreq)),"; output_lvl=",flvl
     460#else
     461                  WRITE(lunout,*) "wxios_add_file: output_freq=",nffreq,"; output_lvl=",flvl
     462#endif
    381463                ENDIF
    382464            ELSE
    383465                WRITE(lunout,*) "wxios_add_file: Error, invalid file: ", "X"//trim(fname)
     466#ifdef XIOS1
    384467                WRITE(lunout,*) "wxios_add_file: output_freq=",TRIM(ADJUSTL(nffreq)),"; output_lvl=",flvl
     468#else
     469                WRITE(lunout,*) "wxios_add_file: output_freq=",nffreq,"; output_lvl=",flvl
     470#endif
    385471            END IF
    386472        ELSE
     
    435521    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    436522    SUBROUTINE wxios_add_field_to_file(fieldname, fdim, fid, fname, fieldlongname, fieldunit, field_level, op, nam_axvert)
    437         IMPLICIT NONE
    438         INCLUDE 'iniprint.h'
     523        USE print_control_mod, ONLY : prt_level, lunout
     524        IMPLICIT NONE
    439525
    440526        CHARACTER(len=*), INTENT(IN) :: fieldname
     
    452538        TYPE(xios_field) :: field
    453539        TYPE(xios_fieldgroup) :: fieldgroup
     540#ifndef XIOS1
     541        TYPE(xios_duration) :: freq_op
     542#endif
    454543        LOGICAL :: bool=.FALSE.
    455544        INTEGER :: lvl =0
     
    510599           
    511600            !L'operation, sa frequence:
     601#ifdef XIOS1
    512602            CALL xios_set_field_attr_hdl(field, field_ref=fieldname, operation=TRIM(ADJUSTL(operation)), freq_op="1ts", prec=4)
     603#else
     604            freq_op%timestep=1
     605            CALL xios_set_field_attr_hdl(field, field_ref=fieldname, operation=TRIM(ADJUSTL(operation)), freq_op=freq_op, prec=4)
     606#endif
    513607
    514608           
Note: See TracChangeset for help on using the changeset viewer.