! ! The following example shows how to create an external file. ! PROGRAM DSETEXTERNAL USE HDF5 ! This module contains all necessary modules IMPLICIT NONE CHARACTER(LEN=7), PARAMETER :: filename = 'extf.h5' ! File name CHARACTER(LEN=4), PARAMETER :: dsetname = "dset-external" ! Dataset name INTEGER(HID_T) :: file_id ! File identifier INTEGER(HID_T) :: dset_id ! Dataset identifier INTEGER(HID_T) :: dspace_id ! Dataspace identifier INTEGER(HID_T) :: dcpl ! Dataset Creation Property List ID INTEGER(HSIZE_T) :: size ! Size of external dataset INTEGER :: error ! Error flag INTEGER :: i, j INTEGER, DIMENSION(4,6) :: dset_data INTEGER(HSIZE_T), DIMENSION(2) :: data_dims INTEGER(HSIZE_T), DIMENSION(2) :: dims = (/4,6/) ! Dataset dimensions INTEGER :: rank = 2 ! Dataset rank ! Initialize FORTRAN predefined datatypes. ! CALL h5open_f (error) ! Create a new file ! CALL h5fcreate_f (filename, H5F_ACC_TRUNC_F, file_id, error, & H5P_DEFAULT_F, H5P_DEFAULT_F) ! Create the dataspace. ! CALL h5screate_simple_f (rank, dims, dspace_id, error) size = dims(1)* dims(2) * 4 ! Set Dataset Creation Property List to create external dataset. ! CALL h5pcreate_f(H5P_DATASET_CREATE_F, dcpl, error) CALL h5pset_external_f (dcpl, "extf.dat", 0, size, error) ! Create the dataset with default properties. ! CALL h5dcreate_f (file_id, dsetname, H5T_NATIVE_INTEGER, dspace_id, & dset_id, error, dcpl) ! Initialize the dset_data array. ! do i = 1, 4 do j = 1, 6 dset_data(i,j) = (i-1)*6 + j; end do end do ! Write the dataset. ! data_dims(1) = 4 data_dims(2) = 6 CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, dset_data, data_dims, error) ! End access to the dataset, dataspace, property list, and file. ! CALL h5pclose_f (dcpl, error) CALL h5dclose_f (dset_id, error) CALL h5sclose_f (dspace_id, error) CALL h5fclose_f (file_id, error) ! Close FORTRAN predefined datatypes. ! CALL h5close_f (error) END PROGRAM DSETEXTERNAL