hdf5/fortran/test/tH5P.f90
Bill Wendling 8055378bce [svn-r2576] Purpose:
Adding the Fortran interface to the HDF5 library
Description:
	Fortran is now a subdirectory of the HDF5 library tree.
Platforms tested:
	Solaris and IRIX (O2K)
2000-09-19 15:06:49 -05:00

102 lines
3.9 KiB
Fortran

SUBROUTINE external_test(total_error)
!THis subroutine tests following functionalities:
!h5pset_external_f, h5pget_external_count_f,
!h5pget_external_f
USE HDF5 ! This module contains all necessary modules
IMPLICIT NONE
INTEGER, INTENT(OUT) :: total_error
CHARACTER(LEN=11), PARAMETER :: filename = "external.h5"
INTEGER(HID_T) :: file_id
INTEGER(HID_T) :: plist_id
INTEGER(HID_T) :: space_id
INTEGER(HID_T) :: dataset_id
INTEGER(HSIZE_T), DIMENSION(1) :: cur_size !data space current size
INTEGER(HSIZE_T), DIMENSION(1) :: max_size !data space maximum size
CHARACTER*256 :: name !external file name
INTEGER :: file_offset !external file offset
INTEGER(HSIZE_T) :: file_size !sizeof external file segment
INTEGER :: error !error code
INTEGER(SIZE_T) :: int_size !size of integer
INTEGER(HSIZE_T) :: file_bytes !Number of bytes reserved
!in the file for the data
INTEGER :: RANK = 1 !dataset rank
INTEGER :: count !number of external files for the
!specified dataset
INTEGER(SIZE_T) :: namesize
!
! Initialize FORTRAN predefined datatypes
!
! CALL h5init_types_f(error)
! CALL check("h5init_types_f",error,total_error)
!
!Create file "external.h5" using default properties.
!
CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, error)
CALL check("h5fcreate_f",error,total_error)
CALL h5pcreate_f(H5P_DATASET_CREATE_F, plist_id, error)
CALL check("h5pcreate_f",error,total_error)
cur_size(1) =100
max_size(1) = 100;
call h5tget_size_f(H5T_NATIVE_INTEGER, int_size, error)
CALL check("h5tget_size_f",error,total_error)
file_size = int_size * max_size(1);
CALL h5pset_external_f(plist_id, "ext1.data", 0, file_size, error)
CALL check("h5pset_external_f",error,total_error)
CALL h5screate_simple_f(RANK, cur_size, space_id, error, max_size)
CALL check("h5screate_simple_f", error, total_error)
CALL h5dcreate_f(file_id, "dset1", H5T_NATIVE_INTEGER, space_id, &
dataset_id, error, plist_id)
CALL check("h5dcreate_f", error, total_error)
CALL h5dclose_f(dataset_id, error)
CALL check("h5dclose_f", error, total_error)
CALL h5pclose_f(plist_id, error)
CALL check("h5pclose_f", error, total_error)
CALL h5sclose_f(space_id, error)
CALL check("h5sclose_f", error, total_error)
! Read dataset creation information
CALL h5dopen_f(file_id, "dset1", dataset_id, error)
CALL check("h5dopen_f",error,total_error)
CALL h5dget_create_plist_f(dataset_id, plist_id, error)
CALL check("h5dget_create_plist_f",error,total_error)
CALL h5pget_external_count_f(plist_id, count, error)
CALL check("h5pget_external_count_f",error,total_error)
if(count .ne. 1 ) then
write (*,*) "got external_count is not correct"
total_error = total_error + 1
end if
namesize = 10
CALL h5pget_external_f(plist_id, 0, namesize, name, file_offset, &
file_bytes, error)
CALL check("h5pget_external_f",error,total_error)
if(file_offset .ne. 0 ) then
write (*,*) "got external file offset is not correct"
total_error = total_error + 1
end if
if(file_bytes .ne. file_size ) then
write (*,*) "got external file size is not correct"
total_error = total_error + 1
end if
CALL h5dclose_f(dataset_id, error)
CALL check("h5dclose_f", error, total_error)
CALL h5pclose_f(plist_id, error)
CALL check("h5pclose_f", error, total_error)
CALL h5fclose_f(file_id, error)
CALL check("h5fclose_f", error, total_error)
! CALL h5close_types_f(error)
! CALL check("h5close_types_f", error, total_error)
RETURN
END SUBROUTINE external_test