Ignore:
Timestamp:
12/11/14 16:07:42 (10 years ago)
Author:
rlacroix
Message:

Convert more attributes to use the new duration type:

  • field: freq_op and freq_offset
  • file: output_freq, sync_freq and split_freq.

Remember that you now have to use the "xios_duration" type instead of strings to get/set those attributes through the Fortran interface.

Location:
XIOS/trunk/src/interface/fortran_attr
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • XIOS/trunk/src/interface/fortran_attr/field_interface_attr.F90

    r532 r538  
    149149     
    150150     
    151     SUBROUTINE cxios_set_field_freq_offset(field_hdl, freq_offset, freq_offset_size) BIND(C) 
    152       USE ISO_C_BINDING 
    153       INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
    154       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: freq_offset 
    155       INTEGER  (kind = C_INT)     , VALUE        :: freq_offset_size 
     151    SUBROUTINE cxios_set_field_freq_offset(field_hdl, freq_offset) BIND(C) 
     152      USE ISO_C_BINDING 
     153      USE IDATE 
     154      INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
     155      TYPE(txios(duration)), VALUE :: freq_offset 
    156156    END SUBROUTINE cxios_set_field_freq_offset 
    157157     
    158     SUBROUTINE cxios_get_field_freq_offset(field_hdl, freq_offset, freq_offset_size) BIND(C) 
    159       USE ISO_C_BINDING 
    160       INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
    161       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: freq_offset 
    162       INTEGER  (kind = C_INT)     , VALUE        :: freq_offset_size 
     158    SUBROUTINE cxios_get_field_freq_offset(field_hdl, freq_offset) BIND(C) 
     159      USE ISO_C_BINDING 
     160      USE IDATE 
     161      INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
     162      TYPE(txios(duration)) :: freq_offset 
    163163    END SUBROUTINE cxios_get_field_freq_offset 
    164164     
     
    170170     
    171171     
    172     SUBROUTINE cxios_set_field_freq_op(field_hdl, freq_op, freq_op_size) BIND(C) 
    173       USE ISO_C_BINDING 
    174       INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
    175       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: freq_op 
    176       INTEGER  (kind = C_INT)     , VALUE        :: freq_op_size 
     172    SUBROUTINE cxios_set_field_freq_op(field_hdl, freq_op) BIND(C) 
     173      USE ISO_C_BINDING 
     174      USE IDATE 
     175      INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
     176      TYPE(txios(duration)), VALUE :: freq_op 
    177177    END SUBROUTINE cxios_set_field_freq_op 
    178178     
    179     SUBROUTINE cxios_get_field_freq_op(field_hdl, freq_op, freq_op_size) BIND(C) 
    180       USE ISO_C_BINDING 
    181       INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
    182       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: freq_op 
    183       INTEGER  (kind = C_INT)     , VALUE        :: freq_op_size 
     179    SUBROUTINE cxios_get_field_freq_op(field_hdl, freq_op) BIND(C) 
     180      USE ISO_C_BINDING 
     181      USE IDATE 
     182      INTEGER (kind = C_INTPTR_T), VALUE :: field_hdl 
     183      TYPE(txios(duration)) :: freq_op 
    184184    END SUBROUTINE cxios_get_field_freq_op 
    185185     
  • XIOS/trunk/src/interface/fortran_attr/fieldgroup_interface_attr.F90

    r532 r538  
    149149     
    150150     
    151     SUBROUTINE cxios_set_fieldgroup_freq_offset(fieldgroup_hdl, freq_offset, freq_offset_size) BIND(C) 
    152       USE ISO_C_BINDING 
    153       INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
    154       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: freq_offset 
    155       INTEGER  (kind = C_INT)     , VALUE        :: freq_offset_size 
     151    SUBROUTINE cxios_set_fieldgroup_freq_offset(fieldgroup_hdl, freq_offset) BIND(C) 
     152      USE ISO_C_BINDING 
     153      USE IDATE 
     154      INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
     155      TYPE(txios(duration)), VALUE :: freq_offset 
    156156    END SUBROUTINE cxios_set_fieldgroup_freq_offset 
    157157     
    158     SUBROUTINE cxios_get_fieldgroup_freq_offset(fieldgroup_hdl, freq_offset, freq_offset_size) BIND(C) 
    159       USE ISO_C_BINDING 
    160       INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
    161       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: freq_offset 
    162       INTEGER  (kind = C_INT)     , VALUE        :: freq_offset_size 
     158    SUBROUTINE cxios_get_fieldgroup_freq_offset(fieldgroup_hdl, freq_offset) BIND(C) 
     159      USE ISO_C_BINDING 
     160      USE IDATE 
     161      INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
     162      TYPE(txios(duration)) :: freq_offset 
    163163    END SUBROUTINE cxios_get_fieldgroup_freq_offset 
    164164     
     
    170170     
    171171     
    172     SUBROUTINE cxios_set_fieldgroup_freq_op(fieldgroup_hdl, freq_op, freq_op_size) BIND(C) 
    173       USE ISO_C_BINDING 
    174       INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
    175       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: freq_op 
    176       INTEGER  (kind = C_INT)     , VALUE        :: freq_op_size 
     172    SUBROUTINE cxios_set_fieldgroup_freq_op(fieldgroup_hdl, freq_op) BIND(C) 
     173      USE ISO_C_BINDING 
     174      USE IDATE 
     175      INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
     176      TYPE(txios(duration)), VALUE :: freq_op 
    177177    END SUBROUTINE cxios_set_fieldgroup_freq_op 
    178178     
    179     SUBROUTINE cxios_get_fieldgroup_freq_op(fieldgroup_hdl, freq_op, freq_op_size) BIND(C) 
    180       USE ISO_C_BINDING 
    181       INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
    182       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: freq_op 
    183       INTEGER  (kind = C_INT)     , VALUE        :: freq_op_size 
     179    SUBROUTINE cxios_get_fieldgroup_freq_op(fieldgroup_hdl, freq_op) BIND(C) 
     180      USE ISO_C_BINDING 
     181      USE IDATE 
     182      INTEGER (kind = C_INTPTR_T), VALUE :: fieldgroup_hdl 
     183      TYPE(txios(duration)) :: freq_op 
    184184    END SUBROUTINE cxios_get_fieldgroup_freq_op 
    185185     
  • XIOS/trunk/src/interface/fortran_attr/file_interface_attr.F90

    r532 r538  
    151151     
    152152     
    153     SUBROUTINE cxios_set_file_output_freq(file_hdl, output_freq, output_freq_size) BIND(C) 
    154       USE ISO_C_BINDING 
    155       INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
    156       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: output_freq 
    157       INTEGER  (kind = C_INT)     , VALUE        :: output_freq_size 
     153    SUBROUTINE cxios_set_file_output_freq(file_hdl, output_freq) BIND(C) 
     154      USE ISO_C_BINDING 
     155      USE IDATE 
     156      INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
     157      TYPE(txios(duration)), VALUE :: output_freq 
    158158    END SUBROUTINE cxios_set_file_output_freq 
    159159     
    160     SUBROUTINE cxios_get_file_output_freq(file_hdl, output_freq, output_freq_size) BIND(C) 
    161       USE ISO_C_BINDING 
    162       INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
    163       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: output_freq 
    164       INTEGER  (kind = C_INT)     , VALUE        :: output_freq_size 
     160    SUBROUTINE cxios_get_file_output_freq(file_hdl, output_freq) BIND(C) 
     161      USE ISO_C_BINDING 
     162      USE IDATE 
     163      INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
     164      TYPE(txios(duration)) :: output_freq 
    165165    END SUBROUTINE cxios_get_file_output_freq 
    166166     
     
    212212     
    213213     
    214     SUBROUTINE cxios_set_file_split_freq(file_hdl, split_freq, split_freq_size) BIND(C) 
    215       USE ISO_C_BINDING 
    216       INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
    217       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: split_freq 
    218       INTEGER  (kind = C_INT)     , VALUE        :: split_freq_size 
     214    SUBROUTINE cxios_set_file_split_freq(file_hdl, split_freq) BIND(C) 
     215      USE ISO_C_BINDING 
     216      USE IDATE 
     217      INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
     218      TYPE(txios(duration)), VALUE :: split_freq 
    219219    END SUBROUTINE cxios_set_file_split_freq 
    220220     
    221     SUBROUTINE cxios_get_file_split_freq(file_hdl, split_freq, split_freq_size) BIND(C) 
    222       USE ISO_C_BINDING 
    223       INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
    224       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: split_freq 
    225       INTEGER  (kind = C_INT)     , VALUE        :: split_freq_size 
     221    SUBROUTINE cxios_get_file_split_freq(file_hdl, split_freq) BIND(C) 
     222      USE ISO_C_BINDING 
     223      USE IDATE 
     224      INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
     225      TYPE(txios(duration)) :: split_freq 
    226226    END SUBROUTINE cxios_get_file_split_freq 
    227227     
     
    254254     
    255255     
    256     SUBROUTINE cxios_set_file_sync_freq(file_hdl, sync_freq, sync_freq_size) BIND(C) 
    257       USE ISO_C_BINDING 
    258       INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
    259       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: sync_freq 
    260       INTEGER  (kind = C_INT)     , VALUE        :: sync_freq_size 
     256    SUBROUTINE cxios_set_file_sync_freq(file_hdl, sync_freq) BIND(C) 
     257      USE ISO_C_BINDING 
     258      USE IDATE 
     259      INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
     260      TYPE(txios(duration)), VALUE :: sync_freq 
    261261    END SUBROUTINE cxios_set_file_sync_freq 
    262262     
    263     SUBROUTINE cxios_get_file_sync_freq(file_hdl, sync_freq, sync_freq_size) BIND(C) 
    264       USE ISO_C_BINDING 
    265       INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
    266       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: sync_freq 
    267       INTEGER  (kind = C_INT)     , VALUE        :: sync_freq_size 
     263    SUBROUTINE cxios_get_file_sync_freq(file_hdl, sync_freq) BIND(C) 
     264      USE ISO_C_BINDING 
     265      USE IDATE 
     266      INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
     267      TYPE(txios(duration)) :: sync_freq 
    268268    END SUBROUTINE cxios_get_file_sync_freq 
    269269     
  • XIOS/trunk/src/interface/fortran_attr/filegroup_interface_attr.F90

    r532 r538  
    172172     
    173173     
    174     SUBROUTINE cxios_set_filegroup_output_freq(filegroup_hdl, output_freq, output_freq_size) BIND(C) 
    175       USE ISO_C_BINDING 
    176       INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
    177       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: output_freq 
    178       INTEGER  (kind = C_INT)     , VALUE        :: output_freq_size 
     174    SUBROUTINE cxios_set_filegroup_output_freq(filegroup_hdl, output_freq) BIND(C) 
     175      USE ISO_C_BINDING 
     176      USE IDATE 
     177      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     178      TYPE(txios(duration)), VALUE :: output_freq 
    179179    END SUBROUTINE cxios_set_filegroup_output_freq 
    180180     
    181     SUBROUTINE cxios_get_filegroup_output_freq(filegroup_hdl, output_freq, output_freq_size) BIND(C) 
    182       USE ISO_C_BINDING 
    183       INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
    184       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: output_freq 
    185       INTEGER  (kind = C_INT)     , VALUE        :: output_freq_size 
     181    SUBROUTINE cxios_get_filegroup_output_freq(filegroup_hdl, output_freq) BIND(C) 
     182      USE ISO_C_BINDING 
     183      USE IDATE 
     184      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     185      TYPE(txios(duration)) :: output_freq 
    186186    END SUBROUTINE cxios_get_filegroup_output_freq 
    187187     
     
    233233     
    234234     
    235     SUBROUTINE cxios_set_filegroup_split_freq(filegroup_hdl, split_freq, split_freq_size) BIND(C) 
    236       USE ISO_C_BINDING 
    237       INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
    238       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: split_freq 
    239       INTEGER  (kind = C_INT)     , VALUE        :: split_freq_size 
     235    SUBROUTINE cxios_set_filegroup_split_freq(filegroup_hdl, split_freq) BIND(C) 
     236      USE ISO_C_BINDING 
     237      USE IDATE 
     238      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     239      TYPE(txios(duration)), VALUE :: split_freq 
    240240    END SUBROUTINE cxios_set_filegroup_split_freq 
    241241     
    242     SUBROUTINE cxios_get_filegroup_split_freq(filegroup_hdl, split_freq, split_freq_size) BIND(C) 
    243       USE ISO_C_BINDING 
    244       INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
    245       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: split_freq 
    246       INTEGER  (kind = C_INT)     , VALUE        :: split_freq_size 
     242    SUBROUTINE cxios_get_filegroup_split_freq(filegroup_hdl, split_freq) BIND(C) 
     243      USE ISO_C_BINDING 
     244      USE IDATE 
     245      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     246      TYPE(txios(duration)) :: split_freq 
    247247    END SUBROUTINE cxios_get_filegroup_split_freq 
    248248     
     
    275275     
    276276     
    277     SUBROUTINE cxios_set_filegroup_sync_freq(filegroup_hdl, sync_freq, sync_freq_size) BIND(C) 
    278       USE ISO_C_BINDING 
    279       INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
    280       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: sync_freq 
    281       INTEGER  (kind = C_INT)     , VALUE        :: sync_freq_size 
     277    SUBROUTINE cxios_set_filegroup_sync_freq(filegroup_hdl, sync_freq) BIND(C) 
     278      USE ISO_C_BINDING 
     279      USE IDATE 
     280      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     281      TYPE(txios(duration)), VALUE :: sync_freq 
    282282    END SUBROUTINE cxios_set_filegroup_sync_freq 
    283283     
    284     SUBROUTINE cxios_get_filegroup_sync_freq(filegroup_hdl, sync_freq, sync_freq_size) BIND(C) 
    285       USE ISO_C_BINDING 
    286       INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
    287       CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: sync_freq 
    288       INTEGER  (kind = C_INT)     , VALUE        :: sync_freq_size 
     284    SUBROUTINE cxios_get_filegroup_sync_freq(filegroup_hdl, sync_freq) BIND(C) 
     285      USE ISO_C_BINDING 
     286      USE IDATE 
     287      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     288      TYPE(txios(duration)) :: sync_freq 
    289289    END SUBROUTINE cxios_get_filegroup_sync_freq 
    290290     
  • XIOS/trunk/src/interface/fortran_attr/ifield_attr.F90

    r501 r538  
    2828      LOGICAL (KIND=C_BOOL) :: enabled_tmp 
    2929      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: field_ref 
    30       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: freq_offset 
    31       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: freq_op 
     30      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: freq_offset 
     31      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: freq_op 
    3232      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: grid_ref 
    3333      INTEGER  , OPTIONAL, INTENT(IN) :: level 
     
    6666      LOGICAL (KIND=C_BOOL) :: enabled_tmp 
    6767      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: field_ref 
    68       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: freq_offset 
    69       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: freq_op 
     68      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: freq_offset 
     69      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: freq_op 
    7070      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: grid_ref 
    7171      INTEGER  , OPTIONAL, INTENT(IN) :: level 
     
    103103      LOGICAL (KIND=C_BOOL) :: enabled__tmp 
    104104      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: field_ref_ 
    105       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: freq_offset_ 
    106       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: freq_op_ 
     105      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: freq_offset_ 
     106      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: freq_op_ 
    107107      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: grid_ref_ 
    108108      INTEGER  , OPTIONAL, INTENT(IN) :: level_ 
     
    148148       
    149149      IF (PRESENT(freq_offset_)) THEN 
    150         CALL cxios_set_field_freq_offset(field_hdl%daddr, freq_offset_, len(freq_offset_)) 
     150        CALL cxios_set_field_freq_offset(field_hdl%daddr, freq_offset_) 
    151151      ENDIF 
    152152       
    153153      IF (PRESENT(freq_op_)) THEN 
    154         CALL cxios_set_field_freq_op(field_hdl%daddr, freq_op_, len(freq_op_)) 
     154        CALL cxios_set_field_freq_op(field_hdl%daddr, freq_op_) 
    155155      ENDIF 
    156156       
     
    220220      LOGICAL (KIND=C_BOOL) :: enabled_tmp 
    221221      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: field_ref 
    222       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: freq_offset 
    223       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: freq_op 
     222      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: freq_offset 
     223      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: freq_op 
    224224      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: grid_ref 
    225225      INTEGER  , OPTIONAL, INTENT(OUT) :: level 
     
    258258      LOGICAL (KIND=C_BOOL) :: enabled_tmp 
    259259      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: field_ref 
    260       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: freq_offset 
    261       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: freq_op 
     260      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: freq_offset 
     261      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: freq_op 
    262262      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: grid_ref 
    263263      INTEGER  , OPTIONAL, INTENT(OUT) :: level 
     
    295295      LOGICAL (KIND=C_BOOL) :: enabled__tmp 
    296296      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: field_ref_ 
    297       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: freq_offset_ 
    298       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: freq_op_ 
     297      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: freq_offset_ 
     298      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: freq_op_ 
    299299      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: grid_ref_ 
    300300      INTEGER  , OPTIONAL, INTENT(OUT) :: level_ 
     
    340340       
    341341      IF (PRESENT(freq_offset_)) THEN 
    342         CALL cxios_get_field_freq_offset(field_hdl%daddr, freq_offset_, len(freq_offset_)) 
     342        CALL cxios_get_field_freq_offset(field_hdl%daddr, freq_offset_) 
    343343      ENDIF 
    344344       
    345345      IF (PRESENT(freq_op_)) THEN 
    346         CALL cxios_get_field_freq_op(field_hdl%daddr, freq_op_, len(freq_op_)) 
     346        CALL cxios_get_field_freq_op(field_hdl%daddr, freq_op_) 
    347347      ENDIF 
    348348       
  • XIOS/trunk/src/interface/fortran_attr/ifieldgroup_attr.F90

    r501 r538  
    2828      LOGICAL (KIND=C_BOOL) :: enabled_tmp 
    2929      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: field_ref 
    30       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: freq_offset 
    31       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: freq_op 
     30      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: freq_offset 
     31      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: freq_op 
    3232      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: grid_ref 
    3333      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: group_ref 
     
    6767      LOGICAL (KIND=C_BOOL) :: enabled_tmp 
    6868      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: field_ref 
    69       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: freq_offset 
    70       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: freq_op 
     69      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: freq_offset 
     70      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: freq_op 
    7171      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: grid_ref 
    7272      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: group_ref 
     
    105105      LOGICAL (KIND=C_BOOL) :: enabled__tmp 
    106106      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: field_ref_ 
    107       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: freq_offset_ 
    108       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: freq_op_ 
     107      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: freq_offset_ 
     108      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: freq_op_ 
    109109      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: grid_ref_ 
    110110      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: group_ref_ 
     
    151151       
    152152      IF (PRESENT(freq_offset_)) THEN 
    153         CALL cxios_set_fieldgroup_freq_offset(fieldgroup_hdl%daddr, freq_offset_, len(freq_offset_)) 
     153        CALL cxios_set_fieldgroup_freq_offset(fieldgroup_hdl%daddr, freq_offset_) 
    154154      ENDIF 
    155155       
    156156      IF (PRESENT(freq_op_)) THEN 
    157         CALL cxios_set_fieldgroup_freq_op(fieldgroup_hdl%daddr, freq_op_, len(freq_op_)) 
     157        CALL cxios_set_fieldgroup_freq_op(fieldgroup_hdl%daddr, freq_op_) 
    158158      ENDIF 
    159159       
     
    227227      LOGICAL (KIND=C_BOOL) :: enabled_tmp 
    228228      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: field_ref 
    229       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: freq_offset 
    230       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: freq_op 
     229      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: freq_offset 
     230      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: freq_op 
    231231      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: grid_ref 
    232232      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: group_ref 
     
    266266      LOGICAL (KIND=C_BOOL) :: enabled_tmp 
    267267      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: field_ref 
    268       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: freq_offset 
    269       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: freq_op 
     268      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: freq_offset 
     269      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: freq_op 
    270270      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: grid_ref 
    271271      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: group_ref 
     
    304304      LOGICAL (KIND=C_BOOL) :: enabled__tmp 
    305305      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: field_ref_ 
    306       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: freq_offset_ 
    307       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: freq_op_ 
     306      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: freq_offset_ 
     307      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: freq_op_ 
    308308      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: grid_ref_ 
    309309      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: group_ref_ 
     
    350350       
    351351      IF (PRESENT(freq_offset_)) THEN 
    352         CALL cxios_get_fieldgroup_freq_offset(fieldgroup_hdl%daddr, freq_offset_, len(freq_offset_)) 
     352        CALL cxios_get_fieldgroup_freq_offset(fieldgroup_hdl%daddr, freq_offset_) 
    353353      ENDIF 
    354354       
    355355      IF (PRESENT(freq_op_)) THEN 
    356         CALL cxios_get_fieldgroup_freq_op(fieldgroup_hdl%daddr, freq_op_, len(freq_op_)) 
     356        CALL cxios_get_fieldgroup_freq_op(fieldgroup_hdl%daddr, freq_op_) 
    357357      ENDIF 
    358358       
  • XIOS/trunk/src/interface/fortran_attr/ifile_attr.F90

    r528 r538  
    2727      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: name 
    2828      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: name_suffix 
    29       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: output_freq 
     29      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: output_freq 
    3030      INTEGER  , OPTIONAL, INTENT(IN) :: output_level 
    3131      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: par_access 
    32       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq 
     32      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: split_freq 
    3333      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq_format 
    34       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: sync_freq 
     34      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: sync_freq 
    3535      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type 
    3636       
     
    5757      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: name 
    5858      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: name_suffix 
    59       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: output_freq 
     59      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: output_freq 
    6060      INTEGER  , OPTIONAL, INTENT(IN) :: output_level 
    6161      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: par_access 
    62       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq 
     62      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: split_freq 
    6363      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq_format 
    64       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: sync_freq 
     64      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: sync_freq 
    6565      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type 
    6666       
     
    8686      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: name_ 
    8787      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: name_suffix_ 
    88       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: output_freq_ 
     88      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: output_freq_ 
    8989      INTEGER  , OPTIONAL, INTENT(IN) :: output_level_ 
    9090      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: par_access_ 
    91       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq_ 
     91      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: split_freq_ 
    9292      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq_format_ 
    93       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: sync_freq_ 
     93      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: sync_freq_ 
    9494      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type_ 
    9595       
     
    125125       
    126126      IF (PRESENT(output_freq_)) THEN 
    127         CALL cxios_set_file_output_freq(file_hdl%daddr, output_freq_, len(output_freq_)) 
     127        CALL cxios_set_file_output_freq(file_hdl%daddr, output_freq_) 
    128128      ENDIF 
    129129       
     
    137137       
    138138      IF (PRESENT(split_freq_)) THEN 
    139         CALL cxios_set_file_split_freq(file_hdl%daddr, split_freq_, len(split_freq_)) 
     139        CALL cxios_set_file_split_freq(file_hdl%daddr, split_freq_) 
    140140      ENDIF 
    141141       
     
    145145       
    146146      IF (PRESENT(sync_freq_)) THEN 
    147         CALL cxios_set_file_sync_freq(file_hdl%daddr, sync_freq_, len(sync_freq_)) 
     147        CALL cxios_set_file_sync_freq(file_hdl%daddr, sync_freq_) 
    148148      ENDIF 
    149149       
     
    172172      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: name 
    173173      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: name_suffix 
    174       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: output_freq 
     174      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: output_freq 
    175175      INTEGER  , OPTIONAL, INTENT(OUT) :: output_level 
    176176      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: par_access 
    177       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq 
     177      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: split_freq 
    178178      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq_format 
    179       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: sync_freq 
     179      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: sync_freq 
    180180      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type 
    181181       
     
    202202      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: name 
    203203      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: name_suffix 
    204       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: output_freq 
     204      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: output_freq 
    205205      INTEGER  , OPTIONAL, INTENT(OUT) :: output_level 
    206206      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: par_access 
    207       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq 
     207      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: split_freq 
    208208      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq_format 
    209       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: sync_freq 
     209      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: sync_freq 
    210210      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type 
    211211       
     
    231231      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: name_ 
    232232      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: name_suffix_ 
    233       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: output_freq_ 
     233      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: output_freq_ 
    234234      INTEGER  , OPTIONAL, INTENT(OUT) :: output_level_ 
    235235      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: par_access_ 
    236       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq_ 
     236      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: split_freq_ 
    237237      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq_format_ 
    238       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: sync_freq_ 
     238      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: sync_freq_ 
    239239      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type_ 
    240240       
     
    270270       
    271271      IF (PRESENT(output_freq_)) THEN 
    272         CALL cxios_get_file_output_freq(file_hdl%daddr, output_freq_, len(output_freq_)) 
     272        CALL cxios_get_file_output_freq(file_hdl%daddr, output_freq_) 
    273273      ENDIF 
    274274       
     
    282282       
    283283      IF (PRESENT(split_freq_)) THEN 
    284         CALL cxios_get_file_split_freq(file_hdl%daddr, split_freq_, len(split_freq_)) 
     284        CALL cxios_get_file_split_freq(file_hdl%daddr, split_freq_) 
    285285      ENDIF 
    286286       
     
    290290       
    291291      IF (PRESENT(sync_freq_)) THEN 
    292         CALL cxios_get_file_sync_freq(file_hdl%daddr, sync_freq_, len(sync_freq_)) 
     292        CALL cxios_get_file_sync_freq(file_hdl%daddr, sync_freq_) 
    293293      ENDIF 
    294294       
  • XIOS/trunk/src/interface/fortran_attr/ifilegroup_attr.F90

    r528 r538  
    2828      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: name 
    2929      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: name_suffix 
    30       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: output_freq 
     30      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: output_freq 
    3131      INTEGER  , OPTIONAL, INTENT(IN) :: output_level 
    3232      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: par_access 
    33       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq 
     33      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: split_freq 
    3434      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq_format 
    35       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: sync_freq 
     35      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: sync_freq 
    3636      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type 
    3737       
     
    5959      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: name 
    6060      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: name_suffix 
    61       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: output_freq 
     61      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: output_freq 
    6262      INTEGER  , OPTIONAL, INTENT(IN) :: output_level 
    6363      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: par_access 
    64       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq 
     64      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: split_freq 
    6565      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq_format 
    66       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: sync_freq 
     66      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: sync_freq 
    6767      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type 
    6868       
     
    9090      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: name_ 
    9191      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: name_suffix_ 
    92       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: output_freq_ 
     92      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: output_freq_ 
    9393      INTEGER  , OPTIONAL, INTENT(IN) :: output_level_ 
    9494      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: par_access_ 
    95       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq_ 
     95      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: split_freq_ 
    9696      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: split_freq_format_ 
    97       CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: sync_freq_ 
     97      TYPE(txios(duration)) , OPTIONAL, INTENT(IN) :: sync_freq_ 
    9898      CHARACTER(len = *) , OPTIONAL, INTENT(IN) :: type_ 
    9999       
     
    133133       
    134134      IF (PRESENT(output_freq_)) THEN 
    135         CALL cxios_set_filegroup_output_freq(filegroup_hdl%daddr, output_freq_, len(output_freq_)) 
     135        CALL cxios_set_filegroup_output_freq(filegroup_hdl%daddr, output_freq_) 
    136136      ENDIF 
    137137       
     
    145145       
    146146      IF (PRESENT(split_freq_)) THEN 
    147         CALL cxios_set_filegroup_split_freq(filegroup_hdl%daddr, split_freq_, len(split_freq_)) 
     147        CALL cxios_set_filegroup_split_freq(filegroup_hdl%daddr, split_freq_) 
    148148      ENDIF 
    149149       
     
    153153       
    154154      IF (PRESENT(sync_freq_)) THEN 
    155         CALL cxios_set_filegroup_sync_freq(filegroup_hdl%daddr, sync_freq_, len(sync_freq_)) 
     155        CALL cxios_set_filegroup_sync_freq(filegroup_hdl%daddr, sync_freq_) 
    156156      ENDIF 
    157157       
     
    181181      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: name 
    182182      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: name_suffix 
    183       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: output_freq 
     183      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: output_freq 
    184184      INTEGER  , OPTIONAL, INTENT(OUT) :: output_level 
    185185      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: par_access 
    186       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq 
     186      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: split_freq 
    187187      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq_format 
    188       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: sync_freq 
     188      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: sync_freq 
    189189      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type 
    190190       
     
    212212      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: name 
    213213      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: name_suffix 
    214       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: output_freq 
     214      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: output_freq 
    215215      INTEGER  , OPTIONAL, INTENT(OUT) :: output_level 
    216216      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: par_access 
    217       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq 
     217      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: split_freq 
    218218      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq_format 
    219       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: sync_freq 
     219      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: sync_freq 
    220220      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type 
    221221       
     
    243243      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: name_ 
    244244      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: name_suffix_ 
    245       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: output_freq_ 
     245      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: output_freq_ 
    246246      INTEGER  , OPTIONAL, INTENT(OUT) :: output_level_ 
    247247      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: par_access_ 
    248       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq_ 
     248      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: split_freq_ 
    249249      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: split_freq_format_ 
    250       CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: sync_freq_ 
     250      TYPE(txios(duration)) , OPTIONAL, INTENT(OUT) :: sync_freq_ 
    251251      CHARACTER(len = *) , OPTIONAL, INTENT(OUT) :: type_ 
    252252       
     
    286286       
    287287      IF (PRESENT(output_freq_)) THEN 
    288         CALL cxios_get_filegroup_output_freq(filegroup_hdl%daddr, output_freq_, len(output_freq_)) 
     288        CALL cxios_get_filegroup_output_freq(filegroup_hdl%daddr, output_freq_) 
    289289      ENDIF 
    290290       
     
    298298       
    299299      IF (PRESENT(split_freq_)) THEN 
    300         CALL cxios_get_filegroup_split_freq(filegroup_hdl%daddr, split_freq_, len(split_freq_)) 
     300        CALL cxios_get_filegroup_split_freq(filegroup_hdl%daddr, split_freq_) 
    301301      ENDIF 
    302302       
     
    306306       
    307307      IF (PRESENT(sync_freq_)) THEN 
    308         CALL cxios_get_filegroup_sync_freq(filegroup_hdl%daddr, sync_freq_, len(sync_freq_)) 
     308        CALL cxios_get_filegroup_sync_freq(filegroup_hdl%daddr, sync_freq_) 
    309309      ENDIF 
    310310       
Note: See TracChangeset for help on using the changeset viewer.