Ignore:
Timestamp:
09/22/15 14:01:30 (9 years ago)
Author:
rlacroix
Message:

XIOS 1.0: Add the Fortran interface for the new "time_counter" file attribute.

I forgot that the change had been made in XIOS 1.0 too...

File:
1 edited

Legend:

Unmodified
Added
Removed
  • XIOS/branchs/xios-1.0/src/interface/fortran_attr/file_interface_attr.f90

    r608 r703  
    253253     
    254254     
     255    SUBROUTINE cxios_set_file_time_counter(file_hdl, time_counter, time_counter_size) BIND(C) 
     256      USE ISO_C_BINDING 
     257      INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
     258      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: time_counter 
     259      INTEGER  (kind = C_INT)     , VALUE        :: time_counter_size 
     260    END SUBROUTINE cxios_set_file_time_counter 
     261     
     262    SUBROUTINE cxios_get_file_time_counter(file_hdl, time_counter, time_counter_size) BIND(C) 
     263      USE ISO_C_BINDING 
     264      INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
     265      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: time_counter 
     266      INTEGER  (kind = C_INT)     , VALUE        :: time_counter_size 
     267    END SUBROUTINE cxios_get_file_time_counter 
     268     
     269    FUNCTION cxios_is_defined_file_time_counter(file_hdl ) BIND(C) 
     270      USE ISO_C_BINDING 
     271      LOGICAL(kind=C_BOOL) :: cxios_is_defined_file_time_counter 
     272      INTEGER (kind = C_INTPTR_T), VALUE :: file_hdl 
     273    END FUNCTION cxios_is_defined_file_time_counter 
     274     
     275     
    255276    SUBROUTINE cxios_set_file_type(file_hdl, type, type_size) BIND(C) 
    256277      USE ISO_C_BINDING 
Note: See TracChangeset for help on using the changeset viewer.