Ignore:
Timestamp:
11/26/14 12:06:21 (10 years ago)
Author:
rlacroix
Message:

Add a new attribute to the file definition so that the output format can be controlled.

Currently the supported formats are "netcdf4" and "netcdf4_classic". The "format" attribute is optional. The "netcdf4" format will be used when no format is explicitly defined. Since "netcdf4" is the format which was previously used by XIOS, existing configuration files will not be affected by this change.

If "netcdf4_classic" is used, the output file(s) will be created using the classic NetCDF format. This format can be used with the attribute "type" set to "one_file" if the NetCDF4 library was compiled with Parallel NetCDF support (--enable-pnetcdf).

File:
1 edited

Legend:

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

    r501 r517  
    4949     
    5050     
     51    SUBROUTINE cxios_set_filegroup_format(filegroup_hdl, format, format_size) BIND(C) 
     52      USE ISO_C_BINDING 
     53      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     54      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: format 
     55      INTEGER  (kind = C_INT)     , VALUE        :: format_size 
     56    END SUBROUTINE cxios_set_filegroup_format 
     57     
     58    SUBROUTINE cxios_get_filegroup_format(filegroup_hdl, format, format_size) BIND(C) 
     59      USE ISO_C_BINDING 
     60      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     61      CHARACTER(kind = C_CHAR)    , DIMENSION(*) :: format 
     62      INTEGER  (kind = C_INT)     , VALUE        :: format_size 
     63    END SUBROUTINE cxios_get_filegroup_format 
     64     
     65    FUNCTION cxios_is_defined_filegroup_format(filegroup_hdl ) BIND(C) 
     66      USE ISO_C_BINDING 
     67      LOGICAL(kind=C_BOOL) :: cxios_is_defined_filegroup_format 
     68      INTEGER (kind = C_INTPTR_T), VALUE :: filegroup_hdl 
     69    END FUNCTION cxios_is_defined_filegroup_format 
     70     
     71     
    5172    SUBROUTINE cxios_set_filegroup_group_ref(filegroup_hdl, group_ref, group_ref_size) BIND(C) 
    5273      USE ISO_C_BINDING 
Note: See TracChangeset for help on using the changeset viewer.