New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 7425 for branches/2016/dev_merge_2016/NEMOGCM/NEMO/OPA_SRC – NEMO

Ignore:
Timestamp:
2016-12-01T18:44:09+01:00 (8 years ago)
Author:
cetlod
Message:

Add Xios2

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_merge_2016/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r7421 r7425  
    9494      CHARACTER(len=*), INTENT(in)  :: cdname 
    9595#if defined key_iomput 
    96       TYPE(xios_time)   :: dtime    = xios_time(0, 0, 0, 0, 0, 0) 
    97       CHARACTER(len=19) :: cldate  
     96 
     97#if defined key_xios2 
     98      TYPE(xios_duration) :: dtime    = xios_duration(0, 0, 0, 0, 0, 0) 
     99      TYPE(xios_date)     :: start_date 
     100#else 
     101      TYPE(xios_time)     :: dtime    = xios_time(0, 0, 0, 0, 0, 0) 
     102      CHARACTER(len=19)   :: cldate  
     103#endif 
    98104      CHARACTER(len=10) :: clname 
    99105      INTEGER           :: ji, jkmin 
    100106      ! 
    101       REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_bnds 
    102       !!---------------------------------------------------------------------- 
    103  
    104       ALLOCATE( z_bnds(jpk,2) ) 
     107      REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zt_bnds, zw_bnds 
     108      !!---------------------------------------------------------------------- 
     109 
     110#if  defined key_xios2 
     111      ALLOCATE( zt_bnds(2,jpk), zw_bnds(2,jpk) ) 
     112#else 
     113      ALLOCATE( zt_bnds(jpk,2), zw_bnds(jpk,2) ) 
     114#endif 
    105115 
    106116      clname = cdname 
     
    109119      CALL iom_swap( cdname ) 
    110120 
     121 
     122#if  defined key_xios2 
     123      ! Calendar type is now defined in xml file  
     124      SELECT CASE ( nleapy )        ! Choose calendar for IOIPSL 
     125      CASE ( 1)   ; CALL xios_define_calendar( TYPE = "Gregorian", time_origin = xios_date(1900,01,01,00,00,00), & 
     126          &                                    start_date = xios_date(nyear,nmonth,nday,0,0,0) ) 
     127      CASE ( 0)   ; CALL xios_define_calendar( TYPE = "NoLeap"   , time_origin = xios_date(1900,01,01,00,00,00), & 
     128          &                                    start_date = xios_date(nyear,nmonth,nday,0,0,0) ) 
     129      CASE (30)   ; CALL xios_define_calendar( TYPE = "D360"     , time_origin = xios_date(1900,01,01,00,00,00), & 
     130          &                                    start_date = xios_date(nyear,nmonth,nday,0,0,0) ) 
     131      END SELECT 
     132#else 
    111133      ! calendar parameters 
    112134      SELECT CASE ( nleapy )        ! Choose calendar for IOIPSL 
     
    118140      CALL xios_set_context_attr(TRIM(clname), start_date=cldate ) 
    119141 
     142#endif 
    120143      ! horizontal grid definition 
    121144      CALL set_scalar 
     
    171194      ! Add vertical grid bounds 
    172195      jkmin = MIN(2,jpk)  ! in case jpk=1 (i.e. sas2D) 
    173       z_bnds(:      ,1) = gdepw_1d(:) 
    174       z_bnds(1:jpkm1,2) = gdepw_1d(jkmin:jpk) 
    175       z_bnds(jpk:   ,2) = gdepw_1d(jpk) + e3t_1d(jpk) 
    176       CALL iom_set_axis_attr( "deptht", bounds=z_bnds ) 
    177       CALL iom_set_axis_attr( "depthu", bounds=z_bnds ) 
    178       CALL iom_set_axis_attr( "depthv", bounds=z_bnds ) 
    179       z_bnds(:        ,2) = gdept_1d(:) 
    180       z_bnds(jkmin:jpk,1) = gdept_1d(1:jpkm1) 
    181       z_bnds(1        ,1) = gdept_1d(1) - e3w_1d(1) 
    182       CALL iom_set_axis_attr( "depthw", bounds=z_bnds ) 
     196#if defined key_xios2 
     197      zt_bnds(2,:        ) = gdept_1d(:) 
     198      zt_bnds(1,jkmin:jpk) = gdept_1d(1:jpkm1) 
     199      zt_bnds(1,1        ) = gdept_1d(1) - e3w_1d(1) 
     200      zw_bnds(1,:        ) = gdepw_1d(:) 
     201      zw_bnds(2,1:jpkm1  ) = gdepw_1d(jkmin:jpk) 
     202      zw_bnds(2,jpk:     ) = gdepw_1d(jpk) + e3t_1d(jpk) 
     203#else 
     204      zt_bnds(:        ,2) = gdept_1d(:) 
     205      zt_bnds(jkmin:jpk,1) = gdept_1d(1:jpkm1) 
     206      zt_bnds(1        ,1) = gdept_1d(1) - e3w_1d(1) 
     207      zw_bnds(:        ,1) = gdepw_1d(:) 
     208      zw_bnds(1:jpkm1  ,2) = gdepw_1d(jkmin:jpk) 
     209      zw_bnds(jpk:     ,2) = gdepw_1d(jpk) + e3t_1d(jpk) 
     210#endif 
     211      CALL iom_set_axis_attr( "deptht", bounds=zt_bnds ) 
     212      CALL iom_set_axis_attr( "depthu", bounds=zt_bnds ) 
     213      CALL iom_set_axis_attr( "depthv", bounds=zt_bnds ) 
     214      CALL iom_set_axis_attr( "depthw", bounds=zw_bnds ) 
     215 
    183216 
    184217# if defined key_floats 
     
    202235      CALL xios_update_calendar(0) 
    203236 
    204       DEALLOCATE( z_bnds ) 
     237      DEALLOCATE( zt_bnds, zw_bnds ) 
    205238 
    206239#endif 
     
    11521185      REAL(wp), DIMENSION(:)   , OPTIONAL, INTENT(in) ::   lonvalue, latvalue 
    11531186      REAL(wp), DIMENSION(:,:) , OPTIONAL, INTENT(in) ::   bounds_lon, bounds_lat, area 
    1154       LOGICAL,  DIMENSION(:,:) , OPTIONAL, INTENT(in) ::   mask 
    1155  
     1187#if defined key_xios2 
     1188      LOGICAL, DIMENSION(:)   , OPTIONAL, INTENT(in) ::   mask 
     1189#else 
     1190      LOGICAL, DIMENSION(:,:) , OPTIONAL, INTENT(in) ::   mask 
     1191#endif 
     1192 
     1193 
     1194#if defined key_xios2 
     1195      IF ( xios_is_valid_domain     (cdid) ) THEN 
     1196         CALL xios_set_domain_attr     ( cdid, ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, jbegin=jbegin, ni=ni, nj=nj,   & 
     1197            &    data_dim=data_dim, data_ibegin=data_ibegin, data_ni=data_ni, data_jbegin=data_jbegin, data_nj=data_nj ,   & 
     1198            &    lonvalue_1D=lonvalue, latvalue_1D=latvalue, mask_1D=mask, nvertex=nvertex, bounds_lon_1D=bounds_lon,      & 
     1199            &    bounds_lat_1D=bounds_lat, area=area, type='curvilinear') 
     1200     ENDIF 
     1201      IF ( xios_is_valid_domaingroup(cdid) ) THEN 
     1202         CALL xios_set_domaingroup_attr( cdid, ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, jbegin=jbegin, ni=ni, nj=nj,   & 
     1203            &    data_dim=data_dim, data_ibegin=data_ibegin, data_ni=data_ni, data_jbegin=data_jbegin, data_nj=data_nj ,   & 
     1204            &    lonvalue_1D=lonvalue, latvalue_1D=latvalue, mask_1D=mask, nvertex=nvertex, bounds_lon_1D=bounds_lon,      & 
     1205            &    bounds_lat_1D=bounds_lat, area=area, type='curvilinear' ) 
     1206      ENDIF 
     1207#else 
    11561208      IF ( xios_is_valid_domain     (cdid) ) THEN 
    11571209         CALL xios_set_domain_attr     ( cdid, ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, jbegin=jbegin, ni=ni, nj=nj,   & 
     
    11691221            &    bounds_lat=bounds_lat, area=area ) 
    11701222      ENDIF 
     1223#endif 
    11711224      CALL xios_solve_inheritance() 
    11721225 
    11731226   END SUBROUTINE iom_set_domain_attr 
     1227 
     1228#if defined key_xios2 
     1229  SUBROUTINE iom_set_zoom_domain_attr( cdid, ibegin, jbegin, ni, nj) 
     1230     CHARACTER(LEN=*)                   , INTENT(in) ::   cdid 
     1231     INTEGER                  , OPTIONAL, INTENT(in) ::   ibegin, jbegin, ni, nj 
     1232 
     1233     IF ( xios_is_valid_zoom_domain     (cdid) ) THEN 
     1234         CALL xios_set_zoom_domain_attr     ( cdid, ibegin=ibegin, jbegin=jbegin, ni=ni,    & 
     1235           &   nj=nj) 
     1236    ENDIF 
     1237  END SUBROUTINE iom_set_zoom_domain_attr 
     1238#endif 
    11741239 
    11751240 
     
    11781243      REAL(wp), DIMENSION(:)  , OPTIONAL, INTENT(in) ::   paxis 
    11791244      REAL(wp), DIMENSION(:,:), OPTIONAL, INTENT(in) ::   bounds 
     1245 
     1246#if defined key_xios2 
     1247      IF ( PRESENT(paxis) ) THEN 
     1248         IF ( xios_is_valid_axis     (cdid) )   CALL xios_set_axis_attr     ( cdid, n_glo=SIZE(paxis), value=paxis ) 
     1249         IF ( xios_is_valid_axisgroup(cdid) )   CALL xios_set_axisgroup_attr( cdid, n_glo=SIZE(paxis), value=paxis ) 
     1250      ENDIF 
     1251#else 
    11801252      IF ( PRESENT(paxis) ) THEN 
    11811253         IF ( xios_is_valid_axis     (cdid) )   CALL xios_set_axis_attr     ( cdid, size=SIZE(paxis), value=paxis ) 
    11821254         IF ( xios_is_valid_axisgroup(cdid) )   CALL xios_set_axisgroup_attr( cdid, size=SIZE(paxis), value=paxis ) 
    11831255      ENDIF 
     1256#endif 
    11841257      IF ( xios_is_valid_axis     (cdid) )   CALL xios_set_axis_attr     ( cdid, bounds=bounds ) 
    11851258      IF ( xios_is_valid_axisgroup(cdid) )   CALL xios_set_axisgroup_attr( cdid, bounds=bounds ) 
     
    11901263   SUBROUTINE iom_set_field_attr( cdid, freq_op, freq_offset ) 
    11911264      CHARACTER(LEN=*)          , INTENT(in) ::   cdid 
     1265#if defined key_xios2 
     1266      TYPE(xios_duration),OPTIONAL , INTENT(in) ::   freq_op 
     1267      TYPE(xios_duration),OPTIONAL , INTENT(in) ::   freq_offset 
     1268#else 
    11921269      CHARACTER(LEN=*),OPTIONAL , INTENT(in) ::   freq_op 
    11931270      CHARACTER(LEN=*),OPTIONAL , INTENT(in) ::   freq_offset 
     1271#endif 
    11941272      IF ( xios_is_valid_field     (cdid) )   CALL xios_set_field_attr       & 
    11951273    &     ( cdid, freq_op=freq_op, freq_offset=freq_offset ) 
     
    12111289   SUBROUTINE iom_get_file_attr( cdid, name, name_suffix, output_freq ) 
    12121290      CHARACTER(LEN=*)          , INTENT(in ) ::   cdid 
    1213       CHARACTER(LEN=*),OPTIONAL , INTENT(out) ::   name, name_suffix, output_freq 
     1291      CHARACTER(LEN=*),OPTIONAL , INTENT(out) ::   name, name_suffix 
     1292#if defined key_xios2 
     1293      TYPE(xios_duration), OPTIONAL , INTENT(out) :: output_freq 
     1294#else 
     1295      CHARACTER(LEN=*)   , OPTIONAL , INTENT(out) :: output_freq 
     1296#endif   
    12141297      LOGICAL                                 ::   llexist1,llexist2,llexist3 
    12151298      !--------------------------------------------------------------------- 
    12161299      IF( PRESENT( name        ) )   name = ''          ! default values 
    12171300      IF( PRESENT( name_suffix ) )   name_suffix = '' 
     1301#if defined key_xios2 
     1302      IF( PRESENT( output_freq ) )   output_freq = xios_duration(0,0,0,0,0,0) 
     1303#else 
    12181304      IF( PRESENT( output_freq ) )   output_freq = '' 
     1305#endif 
    12191306      IF ( xios_is_valid_file     (cdid) ) THEN 
    12201307         CALL xios_solve_inheritance() 
     
    12371324      CHARACTER(LEN=*)                   , INTENT(in) ::   cdid 
    12381325      LOGICAL, DIMENSION(:,:,:), OPTIONAL, INTENT(in) ::   mask 
     1326#if defined key_xios2 
     1327      IF ( xios_is_valid_grid     (cdid) )   CALL xios_set_grid_attr     ( cdid, mask_3D=mask ) 
     1328      IF ( xios_is_valid_gridgroup(cdid) )   CALL xios_set_gridgroup_attr( cdid, mask_3D=mask ) 
     1329#else 
    12391330      IF ( xios_is_valid_grid     (cdid) )   CALL xios_set_grid_attr     ( cdid, mask=mask ) 
    12401331      IF ( xios_is_valid_gridgroup(cdid) )   CALL xios_set_gridgroup_attr( cdid, mask=mask ) 
     1332#endif 
    12411333      CALL xios_solve_inheritance() 
    12421334   END SUBROUTINE iom_set_grid_attr 
     
    12801372      ni=nlei-nldi+1 ; nj=nlej-nldj+1 
    12811373 
     1374#if defined key_xios2 
     1375      CALL iom_set_domain_attr("grid_"//cdgrd, ni_glo=jpiglo, nj_glo=jpjglo, ibegin=nimpp+nldi-2, jbegin=njmpp+nldj-2, ni=ni, nj=nj) 
     1376#else 
    12821377      CALL iom_set_domain_attr("grid_"//cdgrd, ni_glo=jpiglo, nj_glo=jpjglo, ibegin=nimpp+nldi-1, jbegin=njmpp+nldj-1, ni=ni, nj=nj) 
     1378#endif      
    12831379      CALL iom_set_domain_attr("grid_"//cdgrd, data_dim=2, data_ibegin = 1-nldi, data_ni = jpi, data_jbegin = 1-nldj, data_nj = jpj) 
    12841380      CALL iom_set_domain_attr("grid_"//cdgrd, lonvalue = RESHAPE(plon(nldi:nlei, nldj:nlej),(/ ni*nj /)),   & 
     
    12941390         END SELECT 
    12951391         ! 
     1392#if defined key_xios2 
     1393         CALL iom_set_domain_attr( "grid_"//cdgrd       , mask = RESHAPE(zmask(nldi:nlei,nldj:nlej,1),(/ni*nj    /)) /= 0. ) 
     1394#else 
    12961395         CALL iom_set_domain_attr( "grid_"//cdgrd       , mask = RESHAPE(zmask(nldi:nlei,nldj:nlej,1),(/ni,nj    /)) /= 0. ) 
     1396#endif  
    12971397         CALL iom_set_grid_attr  ( "grid_"//cdgrd//"_3D", mask = RESHAPE(zmask(nldi:nlei,nldj:nlej,:),(/ni,nj,jpk/)) /= 0. ) 
    12981398      ENDIF 
     
    14281528      ALLOCATE( zlon(ni*nj) )       ;       zlon(:) = 0. 
    14291529 
     1530      CALL dom_ngb( 180., 90., ix, iy, 'T' ) !  i-line that passes near the North Pole : Reference latitude (used in plots) 
     1531#if  defined key_xios2 
     1532      CALL iom_set_domain_attr("gznl", ni_glo=jpiglo, nj_glo=jpjglo, ibegin=nimpp+nldi-2, jbegin=njmpp+nldj-2, ni=ni, nj=nj) 
     1533      CALL iom_set_domain_attr("gznl", data_dim=2, data_ibegin = 1-nldi, data_ni = jpi, data_jbegin = 1-nldj, data_nj = jpj) 
     1534      CALL iom_set_domain_attr("gznl", lonvalue = zlon,   & 
     1535         &                             latvalue = RESHAPE(plat(nldi:nlei, nldj:nlej),(/ ni*nj /)))   
     1536      CALL iom_set_zoom_domain_attr ("ptr", ibegin=ix-1, jbegin=0, ni=1, nj=jpjglo) 
     1537#else 
    14301538      CALL iom_set_domain_attr("gznl", ni_glo=jpiglo, nj_glo=jpjglo, ibegin=nimpp+nldi-1, jbegin=njmpp+nldj-1, ni=ni, nj=nj) 
    14311539      CALL iom_set_domain_attr("gznl", data_dim=2, data_ibegin = 1-nldi, data_ni = jpi, data_jbegin = 1-nldj, data_nj = jpj) 
    14321540      CALL iom_set_domain_attr("gznl", lonvalue = zlon,   & 
    14331541         &                             latvalue = RESHAPE(plat(nldi:nlei, nldj:nlej),(/ ni*nj /)))   
    1434       ! 
    1435       CALL dom_ngb( 180., 90., ix, iy, 'T' ) !  i-line that passes near the North Pole : Reference latitude (used in plots) 
    14361542      CALL iom_set_domain_attr ('ptr', zoom_ibegin=ix, zoom_nj=jpjglo) 
     1543#endif 
     1544      ! 
    14371545      CALL iom_update_file_name('ptr') 
    14381546      ! 
     
    14481556      REAL(wp), DIMENSION(1)   ::   zz = 1. 
    14491557      !!---------------------------------------------------------------------- 
     1558 
     1559#if defined key_xios2 
     1560      CALL iom_set_domain_attr('scalarpoint', ni_glo=jpnij, nj_glo=1, ibegin=narea-1, jbegin=0, ni=1, nj=1) 
     1561#else 
    14501562      CALL iom_set_domain_attr('scalarpoint', ni_glo=jpnij, nj_glo=1, ibegin=narea, jbegin=1, ni=1, nj=1) 
     1563#endif 
    14511564      CALL iom_set_domain_attr('scalarpoint', data_dim=2, data_ibegin = 1, data_ni = 1, data_jbegin = 1, data_nj = 1) 
    14521565       
     
    14771590      REAL(wp)        ,DIMENSION( 3) ::   zlonpira                 ! longitudes of pirata moorings 
    14781591      REAL(wp)        ,DIMENSION( 9) ::   zlatpira                 ! latitudes  of pirata moorings 
     1592#if  defined key_xios2 
     1593      TYPE(xios_duration)            ::   f_op, f_of 
     1594#endif 
    14791595      !!---------------------------------------------------------------------- 
    14801596      !  
    14811597      ! frequency of the call of iom_put (attribut: freq_op) 
    1482       WRITE(cl1,'(i1)')        1   ;   CALL iom_set_field_attr('field_definition', freq_op = cl1//'ts', freq_offset='0ts') 
    1483       WRITE(cl1,'(i1)')  nn_fsbc   ;   CALL iom_set_field_attr('SBC'             , freq_op = cl1//'ts', freq_offset='0ts') 
    1484       WRITE(cl1,'(i1)')  nn_fsbc   ;   CALL iom_set_field_attr('SBC_scalar'      , freq_op = cl1//'ts', freq_offset='0ts') 
    1485       WRITE(cl1,'(i1)') nn_dttrc   ;   CALL iom_set_field_attr('ptrc_T'          , freq_op = cl1//'ts', freq_offset='0ts') 
    1486       WRITE(cl1,'(i1)') nn_dttrc   ;   CALL iom_set_field_attr('diad_T'          , freq_op = cl1//'ts', freq_offset='0ts') 
    1487         
     1598#if defined key_xios2 
     1599      f_op%timestep = 1        ;  f_of%timestep = 0  ; CALL iom_set_field_attr('field_definition', freq_op=f_op, freq_offset=f_of) 
     1600      f_op%timestep = nn_fsbc  ;  f_of%timestep = 0  ; CALL iom_set_field_attr('SBC'             , freq_op=f_op, freq_offset=f_of) 
     1601      f_op%timestep = nn_fsbc  ;  f_of%timestep = 0  ; CALL iom_set_field_attr('SBC_scalar'      , freq_op=f_op, freq_offset=f_of) 
     1602      f_op%timestep = nn_dttrc ;  f_of%timestep = 0  ; CALL iom_set_field_attr('ptrc_T'          , freq_op=f_op, freq_offset=f_of) 
     1603      f_op%timestep = nn_dttrc ;  f_of%timestep = 0  ; CALL iom_set_field_attr('diad_T'          , freq_op=f_op, freq_offset=f_of) 
     1604#else 
     1605      WRITE(cl1,'(i1)')        1   ;   CALL iom_set_field_attr('field_definition', freq_op=cl1//'ts', freq_offset='0ts') 
     1606      WRITE(cl1,'(i1)')  nn_fsbc   ;   CALL iom_set_field_attr('SBC'             , freq_op=cl1//'ts', freq_offset='0ts') 
     1607      WRITE(cl1,'(i1)')  nn_fsbc   ;   CALL iom_set_field_attr('SBC_scalar'      , freq_op=cl1//'ts', freq_offset='0ts') 
     1608      WRITE(cl1,'(i1)') nn_dttrc   ;   CALL iom_set_field_attr('ptrc_T'          , freq_op=cl1//'ts', freq_offset='0ts') 
     1609      WRITE(cl1,'(i1)') nn_dttrc   ;   CALL iom_set_field_attr('diad_T'          , freq_op=cl1//'ts', freq_offset='0ts') 
     1610#endif 
     1611 
    14881612      ! output file names (attribut: name) 
    14891613      DO ji = 1, 9 
     
    15061630         ! Equatorial section (attributs: jbegin, ni, name_suffix) 
    15071631         CALL dom_ngb( 0., 0., ix, iy, cl1 ) 
     1632#if defined key_xios2 
     1633         CALL iom_set_zoom_domain_attr ('Eq'//cl1, jbegin=iy-1, ni=jpiglo) 
     1634#else 
    15081635         CALL iom_set_domain_attr ('Eq'//cl1, zoom_jbegin=iy, zoom_ni=jpiglo) 
     1636#endif 
    15091637         CALL iom_get_file_attr   ('Eq'//cl1, name_suffix = clsuff             ) 
    15101638         CALL iom_set_file_attr   ('Eq'//cl1, name_suffix = TRIM(clsuff)//'_Eq') 
     
    15861714               ENDIF 
    15871715               clname = TRIM(ADJUSTL(clat))//TRIM(ADJUSTL(clon)) 
     1716#if defined key_xios2 
     1717               CALL iom_set_zoom_domain_attr  (TRIM(clname)//cl1, ibegin= ix-1, jbegin= iy-1) 
     1718#else 
    15881719               CALL iom_set_domain_attr (TRIM(clname)//cl1, zoom_ibegin= ix, zoom_jbegin= iy) 
     1720#endif 
     1721 
    15891722               CALL iom_get_file_attr   (TRIM(clname)//cl1, name_suffix = clsuff                         ) 
    15901723               CALL iom_set_file_attr   (TRIM(clname)//cl1, name_suffix = TRIM(clsuff)//'_'//TRIM(clname)) 
     
    16151748      REAL(wp)           ::   zsec 
    16161749      LOGICAL            ::   llexist 
     1750#if  defined key_xios2 
     1751      TYPE(xios_duration)   ::   output_freq  
     1752#endif  
    16171753      !!---------------------------------------------------------------------- 
    16181754 
    16191755      DO jn = 1,2 
    16201756 
     1757#if defined key_xios2 
     1758         output_freq = xios_duration(0,0,0,0,0,0) 
     1759         IF( jn == 1 )   CALL iom_get_file_attr( cdid, name        = clname, output_freq = output_freq ) 
     1760#else 
    16211761         IF( jn == 1 )   CALL iom_get_file_attr( cdid, name        = clname, output_freq = clfreq ) 
     1762#endif 
    16221763         IF( jn == 2 )   CALL iom_get_file_attr( cdid, name_suffix = clname ) 
    16231764 
     
    16301771            END DO 
    16311772 
     1773#if defined key_xios2 
     1774            idx = INDEX(clname,'@freq@') + INDEX(clname,'@FREQ@') 
     1775            DO WHILE ( idx /= 0 )  
     1776              IF ( output_freq%timestep /= 0) THEN 
     1777                  WRITE(clfreq,'(I18,A2)')INT(output_freq%timestep),'ts'  
     1778                  itrlen = LEN_TRIM(ADJUSTL(clfreq)) 
     1779              ELSE IF ( output_freq%hour /= 0 ) THEN 
     1780                  WRITE(clfreq,'(I19,A1)')INT(output_freq%hour),'h'  
     1781                  itrlen = LEN_TRIM(ADJUSTL(clfreq)) 
     1782              ELSE IF ( output_freq%day /= 0 ) THEN 
     1783                  WRITE(clfreq,'(I19,A1)')INT(output_freq%day),'d'  
     1784                  itrlen = LEN_TRIM(ADJUSTL(clfreq)) 
     1785              ELSE IF ( output_freq%month /= 0 ) THEN    
     1786                  WRITE(clfreq,'(I19,A1)')INT(output_freq%month),'m'  
     1787                  itrlen = LEN_TRIM(ADJUSTL(clfreq)) 
     1788              ELSE IF ( output_freq%year /= 0 ) THEN    
     1789                  WRITE(clfreq,'(I19,A1)')INT(output_freq%year),'y'  
     1790                  itrlen = LEN_TRIM(ADJUSTL(clfreq)) 
     1791              ELSE 
     1792                  CALL ctl_stop('error in the name of file id '//TRIM(cdid),   & 
     1793                     & ' attribute output_freq is undefined -> cannot replace @freq@ in '//TRIM(clname) ) 
     1794              ENDIF 
     1795              clname = clname(1:idx-1)//TRIM(ADJUSTL(clfreq))//clname(idx+6:LEN_TRIM(clname)) 
     1796              idx = INDEX(clname,'@freq@') + INDEX(clname,'@FREQ@') 
     1797            END DO 
     1798#else 
    16321799            idx = INDEX(clname,'@freq@') + INDEX(clname,'@FREQ@') 
    16331800            DO WHILE ( idx /= 0 )  
     
    16421809               idx = INDEX(clname,'@freq@') + INDEX(clname,'@FREQ@') 
    16431810            END DO 
    1644  
     1811#endif 
    16451812            idx = INDEX(clname,'@startdate@') + INDEX(clname,'@STARTDATE@') 
    16461813            DO WHILE ( idx /= 0 )  
Note: See TracChangeset for help on using the changeset viewer.