diff options
author | Scot Breitenfeld <brtnfld@hdfgroup.org> | 2011-03-27 04:13:53 (GMT) |
---|---|---|
committer | Scot Breitenfeld <brtnfld@hdfgroup.org> | 2011-03-27 04:13:53 (GMT) |
commit | bcf7bc892eb2edc97456f4bce0700da2c6fd6bd2 (patch) | |
tree | e09a2cadd8dd019c5ef5973aedb6d7c41d7c2209 /hl/fortran/test/tsttable.f90 | |
parent | bbd2a41075b6ddd8a30844c1247fab46d55e238f (diff) | |
download | hdf5-bcf7bc892eb2edc97456f4bce0700da2c6fd6bd2.zip hdf5-bcf7bc892eb2edc97456f4bce0700da2c6fd6bd2.tar.gz hdf5-bcf7bc892eb2edc97456f4bce0700da2c6fd6bd2.tar.bz2 |
[svn-r20353] Bug 1752 - H5Lite Fortran APIs do not allow you to create 4 dimensional datasets (or greater)
* Fixed and tested the integer, real, double routines for creating and reading
dimensional dataset with ranks 4-7
Tested: jam (intel, gnu compilers)
Diffstat (limited to 'hl/fortran/test/tsttable.f90')
-rwxr-xr-x | hl/fortran/test/tsttable.f90 | 11 |
1 files changed, 5 insertions, 6 deletions
diff --git a/hl/fortran/test/tsttable.f90 b/hl/fortran/test/tsttable.f90 index 8191693..66ec5c6 100755 --- a/hl/fortran/test/tsttable.f90 +++ b/hl/fortran/test/tsttable.f90 @@ -39,14 +39,14 @@ SUBROUTINE test_table1() CHARACTER(len=8), PARAMETER :: filename = "f1tab.h5" ! File name CHARACTER(LEN=5), PARAMETER :: dsetname1 = "dset1" ! Dataset name INTEGER(HID_T) :: file_id ! File identifier - INTEGER(HSIZE_T), PARAMETER :: nfields = 4; ! nfields - INTEGER(HSIZE_T), PARAMETER :: nrecords = 5; ! nrecords + INTEGER(HSIZE_T), PARAMETER :: nfields = 4 ! nfields + INTEGER(HSIZE_T), PARAMETER :: nrecords = 5 ! nrecords CHARACTER(LEN=10),DIMENSION(1:nfields) :: field_names ! field names INTEGER(SIZE_T), DIMENSION(1:nfields) :: field_offset ! field offset INTEGER(HID_T), DIMENSION(1:nfields) :: field_types ! field types INTEGER(HSIZE_T), PARAMETER :: chunk_size = 5 ! chunk size INTEGER, PARAMETER :: compress = 0 ! compress - INTEGER :: errcode ! Error flag + INTEGER :: errcode = 0 ! Error flag INTEGER :: i ! general purpose integer INTEGER(SIZE_T) :: type_size ! Size of the datatype INTEGER(SIZE_T) :: type_sizec ! Size of the character datatype @@ -69,8 +69,8 @@ SUBROUTINE test_table1() CHARACTER(LEN=9), DIMENSION(1:nfields) :: field_namesr ! field names INTEGER(SIZE_T), DIMENSION(1:nfields) :: field_offsetr ! field offset INTEGER(SIZE_T), DIMENSION(1:nfields) :: field_sizesr ! field sizes - INTEGER(SIZE_T) :: type_sizeout ! size of the datatype - INTEGER :: maxlen ! max chararter length of a field name + INTEGER(SIZE_T) :: type_sizeout = 0 ! size of the datatype + INTEGER :: maxlen = 0 ! max chararter length of a field name ! @@ -376,7 +376,6 @@ SUBROUTINE test_table1() CALL passed() - !------------------------------------------------------------------------- ! Get information about fields !------------------------------------------------------------------------- |