Ignore:
Timestamp:
12/03/14 17:54:33 (10 years ago)
Author:
rlacroix
Message:

Add the ability to append data to existing output file(s).

By default existing file(s) will still be overwritten. Set the new file attribute "append" to true if you wish to append data to existing NetCDF file(s).

Note that the append mode is currently not supported when file splitting is used and that the structure of the output file cannot be changed.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • XIOS/trunk/src/interface/fortran_attr/filegroup_interface_attr.f90

    r517 r528  
    99     
    1010     
     11    SUBROUTINE cxios_set_filegroup_append(filegroup_hdl, append) BIND(C) 
     12      USE ISO_C_BINDING 
     13      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     14      LOGICAL (KIND=C_BOOL)      , VALUE :: append 
     15    END SUBROUTINE cxios_set_filegroup_append 
     16     
     17    SUBROUTINE cxios_get_filegroup_append(filegroup_hdl, append) BIND(C) 
     18      USE ISO_C_BINDING 
     19      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     20      LOGICAL (KIND=C_BOOL)             :: append 
     21    END SUBROUTINE cxios_get_filegroup_append 
     22     
     23    FUNCTION cxios_is_defined_filegroup_append(filegroup_hdl ) BIND(C) 
     24      USE ISO_C_BINDING 
     25      LOGICAL(kind=C_BOOL) :: cxios_is_defined_filegroup_append 
     26      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     27    END FUNCTION cxios_is_defined_filegroup_append 
     28     
     29     
    1130    SUBROUTINE cxios_set_filegroup_description(filegroup_hdl, description, description_size) BIND(C) 
    1231      USE ISO_C_BINDING 
Note: See TracChangeset for help on using the changeset viewer.