Ignore:
Timestamp:
Jan 5, 2017, 3:21:54 PM (7 years ago)
Author:
Ehouarn Millour
Message:

Cleanup in wxios.F90: get rid of obsolete "XIOS1" case.
EM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/misc/wxios.F90

    r2509 r2741  
    2525!$OMP THREADPRIVATE(missing_val)
    2626
     27#ifdef XIOS1
     28#error "XIOS v1 no longer supported, use XIOS v2."
     29#endif
     30
    2731    CONTAINS
    2832   
     
    3337    SUBROUTINE reformadate(odate, ndate)
    3438        CHARACTER(len=*), INTENT(IN) :: odate
    35 #ifdef XIOS1
    36         CHARACTER(len=100), INTENT(OUT) :: ndate
    37 #else
    3839        TYPE(xios_duration) :: ndate
    39 #endif
    4040       
    4141        INTEGER :: i = 0
     
    5252        i = INDEX(odate, "day")
    5353        IF (i > 0) THEN
    54 #ifdef XIOS1
    55             ndate = odate(1:i-1)//"d"
    56 #else
    5754            read(odate(1:i-1),*) ndate%day
    58 #endif
    5955        END IF
    6056
    6157        i = INDEX(odate, "hr")
    6258        IF (i > 0) THEN
    63 #ifdef XIOS1
    64             ndate = odate(1:i-1)//"h"
    65 #else
    6659            read(odate(1:i-1),*) ndate%hour
    67 #endif
    6860        END IF
    6961
    7062        i = INDEX(odate, "mth")
    7163        IF (i > 0) THEN
    72 #ifdef XIOS1
    73             ndate = odate(1:i-1)//"mo"
    74 #else
    7564            read(odate(1:i-1),*) ndate%month
    76 #endif
    7765        END IF
    7866       
     
    197185     
    198186     !Variables pour xios:
    199 #ifdef XIOS1
    200      TYPE(xios_time) :: mdtime
    201 #else
    202187     TYPE(xios_duration) :: mdtime
    203 #endif
    204188     !REAL(kind = 8) :: year=0, month=0, day=0, hour=0, minute=0, second=0
    205189     
    206 #ifdef XIOS1
    207         mdtime = xios_time(0, 0, 0, 0, 0, pasdetemps)
    208 #else
    209190        mdtime%second=pasdetemps
    210 #endif
    211191
    212192        !Réglage du calendrier:
    213 #ifdef XIOS1
    214         SELECT CASE (calendrier)
    215             CASE('earth_360d')
    216                 CALL xios_set_context_attr_hdl(g_ctx, calendar_type= "D360")
    217                 IF (prt_level >= 10) WRITE(lunout,*) 'wxios_set_cal: Calendrier terrestre a 360 jours/an'
    218             CASE('earth_365d')
    219                 CALL xios_set_context_attr_hdl(g_ctx, calendar_type= "NoLeap")
    220                 IF (prt_level >= 10) WRITE(lunout,*) 'wxios_set_cal: Calendrier terrestre a 365 jours/an'
    221             CASE('gregorian')
    222                 CALL xios_set_context_attr_hdl(g_ctx, calendar_type= "Gregorian")
    223                 IF (prt_level >= 10) WRITE(lunout,*) 'wxios_set_cal: Calendrier gregorien'
    224             CASE DEFAULT
    225                 abort_message = 'wxios_set_cal: Mauvais choix de calendrier'
    226                 CALL abort_gcm('Gcm:Xios',abort_message,1)
    227         END SELECT
    228 #else
    229193        SELECT CASE (calendrier)
    230194            CASE('earth_360d')
     
    241205                CALL abort_gcm('Gcm:Xios',abort_message,1)
    242206        END SELECT
    243 #endif
    244207       
    245208        !Formatage de la date d'origine:
     
    247210       
    248211        IF (prt_level >= 10) WRITE(lunout,*) "wxios_set_cal: Time origin: ", date
    249 #ifdef XIOS1
    250         CALL xios_set_context_attr_hdl(g_ctx, time_origin = date)
    251 #else
    252212        CALL xios_set_time_origin(xios_date(annee,mois,jour,int(heure),0,0))
    253 #endif
    254213
    255214        !Formatage de la date de debut:
     
    259218        IF (prt_level >= 10) WRITE(lunout,*) "wxios_set_cal: Start date: ", date
    260219       
    261 #ifdef XIOS1
    262         CALL xios_set_context_attr_hdl(g_ctx, start_date = date)
    263 #else
    264220        CALL xios_set_start_date(xios_date(ini_an,ini_mois,ini_jour,int(ini_heure),0,0))
    265 #endif
    266221       
    267222        !Et enfin,le pas de temps:
     
    272227    SUBROUTINE wxios_set_timestep(ts)
    273228        REAL, INTENT(IN) :: ts
    274 #ifdef XIOS1
    275         TYPE(xios_time) :: mdtime     
    276 
    277         mdtime = xios_time(0, 0, 0, 0, 0, ts)
    278 #else
    279229        TYPE(xios_duration) :: mdtime     
    280230
    281231        mdtime%timestep = ts
    282 #endif
    283232
    284233        CALL xios_set_timestep(mdtime)
     
    334283       
    335284        !On parametrise le domaine:
    336 #ifdef XIOS1
    337         CALL xios_set_domain_attr_hdl(dom, ni_glo=ni_glo, ibegin=ibegin, ni=ni)
    338         CALL xios_set_domain_attr_hdl(dom, nj_glo=nj_glo, jbegin=jbegin, nj=nj, data_dim=2)
    339         CALL xios_set_domain_attr_hdl(dom, lonvalue=io_lon(ibegin:iend), latvalue=io_lat(jbegin:jend))
    340 #else
    341285        CALL xios_set_domain_attr_hdl(dom, ni_glo=ni_glo, ibegin=ibegin-1, ni=ni, type="rectilinear")
    342286        CALL xios_set_domain_attr_hdl(dom, nj_glo=nj_glo, jbegin=jbegin-1, nj=nj, data_dim=2)
    343287        CALL xios_set_domain_attr_hdl(dom, lonvalue_1d=io_lon(ibegin:iend), latvalue_1d=io_lat(jbegin:jend))
    344 #endif
    345288        IF (.NOT.is_sequential) THEN
    346289            mask(:,:)=.TRUE.
     
    353296              WRITE(lunout,*) "wxios_domain_param: mpirank=",mpi_rank," mask(:,nj)=",mask(:,nj)
    354297            ENDIF
    355 #ifdef XIOS1
    356             CALL xios_set_domain_attr_hdl(dom, mask=mask)
    357 #else
    358298            CALL xios_set_domain_attr_hdl(dom, mask_2d=mask)
    359 #endif
    360299        END IF
    361300
     
    401340       
    402341        ! Ehouarn: New way to declare axis, without axis_group:
    403 #ifdef XIOS1
    404         CALL xios_set_axis_attr(trim(axis_id),size=axis_size,value=axis_value)
    405 #else
    406342        CALL xios_set_axis_attr(trim(axis_id),n_glo=axis_size,value=axis_value)
    407 #endif       
     343
    408344        !Vérification:
    409345        IF (xios_is_valid_axis(TRIM(ADJUSTL(axis_id)))) THEN
     
    429365        TYPE(xios_file) :: x_file
    430366        TYPE(xios_filegroup) :: x_fg
    431 #ifdef XIOS1
    432         CHARACTER(len=100) :: nffreq
    433 #else
    434367        TYPE(xios_duration) :: nffreq
    435 #endif
    436368       
    437369        !On regarde si le fichier n'est pas défini par XML:
     
    445377       
    446378            !On configure:
    447 #ifdef XIOS1
    448             CALL xios_set_file_attr_hdl(x_file, name="X"//fname,&
    449                 output_freq=TRIM(ADJUSTL(nffreq)), output_level=flvl, enabled=.TRUE.)
    450 #else
    451379            CALL xios_set_file_attr_hdl(x_file, name="X"//fname,&
    452380                output_freq=nffreq, output_level=flvl, enabled=.TRUE.)
    453 #endif
    454381       
    455382            IF (xios_is_valid_file("X"//fname)) THEN
    456383                IF (prt_level >= 10) THEN
    457384                  WRITE(lunout,*) "wxios_add_file: New file: ", "X"//fname
    458 #ifdef XIOS1
    459                   WRITE(lunout,*) "wxios_add_file: output_freq=",TRIM(ADJUSTL(nffreq)),"; output_lvl=",flvl
    460 #else
    461385                  WRITE(lunout,*) "wxios_add_file: output_freq=",nffreq,"; output_lvl=",flvl
    462 #endif
    463386                ENDIF
    464387            ELSE
    465388                WRITE(lunout,*) "wxios_add_file: Error, invalid file: ", "X"//trim(fname)
    466 #ifdef XIOS1
    467                 WRITE(lunout,*) "wxios_add_file: output_freq=",TRIM(ADJUSTL(nffreq)),"; output_lvl=",flvl
    468 #else
    469389                WRITE(lunout,*) "wxios_add_file: output_freq=",nffreq,"; output_lvl=",flvl
    470 #endif
    471390            END IF
    472391        ELSE
     
    538457        TYPE(xios_field) :: field
    539458        TYPE(xios_fieldgroup) :: fieldgroup
    540 #ifndef XIOS1
    541459        TYPE(xios_duration) :: freq_op
    542 #endif
     460
    543461        LOGICAL :: bool=.FALSE.
    544462        INTEGER :: lvl =0
     
    599517           
    600518            !L'operation, sa frequence:
    601 #ifdef XIOS1
    602             CALL xios_set_field_attr_hdl(field, field_ref=fieldname, operation=TRIM(ADJUSTL(operation)), freq_op="1ts", prec=4)
    603 #else
    604519            freq_op%timestep=1
    605520            CALL xios_set_field_attr_hdl(field, field_ref=fieldname, operation=TRIM(ADJUSTL(operation)), freq_op=freq_op, prec=4)
    606 #endif
    607521
    608522           
Note: See TracChangeset for help on using the changeset viewer.