summaryrefslogtreecommitdiffstats
path: root/fortran/test/tH5A_1_8.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/test/tH5A_1_8.f90')
-rw-r--r--fortran/test/tH5A_1_8.f90588
1 files changed, 31 insertions, 557 deletions
diff --git a/fortran/test/tH5A_1_8.f90 b/fortran/test/tH5A_1_8.f90
index c48420e..c1dca9d 100644
--- a/fortran/test/tH5A_1_8.f90
+++ b/fortran/test/tH5A_1_8.f90
@@ -1,3 +1,12 @@
+!****h* root/fortran/test/tH5A_1_8.f90
+!
+! NAME
+! tH5A_1_8.f90
+!
+! FUNCTION
+! Basic testing of Fortran H5A APIs introduced in 1.8.
+!
+! COPYRIGHT
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
! Copyright by The HDF Group. *
! Copyright by the Board of Trustees of the University of Illinois. *
@@ -13,6 +22,15 @@
! access to either file, you may request a copy from help@hdfgroup.org. *
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
!
+! CONTAINS SUBROUTINES
+! attribute_test_1_8, test_attr_corder_create_compact, test_attr_null_space,
+! test_attr_create_by_name, test_attr_info_by_idx, attr_info_by_idx_check,
+! test_attr_shared_rename, test_attr_delete_by_idx, test_attr_shared_delete,
+! test_attr_dense_open, test_attr_dense_verify, test_attr_corder_create_basic,
+! test_attr_basic_write, test_attr_many, attr_open_check,
+!
+!*****
+
SUBROUTINE attribute_test_1_8(cleanup, total_error)
! This subroutine tests following 1.8 functionalities:
@@ -96,18 +114,6 @@ SUBROUTINE attribute_test_1_8(cleanup, total_error)
' - Tests INT attributes on both datasets and groups', &
total_error)
-!!$ CALL test_attr_basic_read(my_fapl)
-!!$ CALL test_attr_flush(my_fapl)
-!!$ CALL test_attr_plist(my_fapl) ! this is next
-!!$ CALL test_attr_compound_write(my_fapl)
-!!$ CALL test_attr_compound_read(my_fapl)
-!!$ CALL test_attr_scalar_write(my_fapl)
-!!$ CALL test_attr_scalar_read(my_fapl)
-!!$ CALL test_attr_mult_write(my_fapl)
-!!$ CALL test_attr_mult_read(my_fapl)
-!!$ CALL test_attr_iterate(my_fapl)
-!!$ CALL test_attr_delete(my_fapl)
-!!$ CALL test_attr_dtype_shared(my_fapl)
IF(new_format(i)) THEN
DO j = 1, 2
IF (use_shared(j)) THEN
@@ -117,7 +123,6 @@ SUBROUTINE attribute_test_1_8(cleanup, total_error)
WRITE(*,*) " - Testing without shared attributes:"
my_fcpl = fcpl
END IF
-!!$ CALL test_attr_dense_create(my_fcpl, my_fapl)
ret_total_error = 0
CALL test_attr_dense_open(my_fcpl, my_fapl, ret_total_error)
@@ -125,17 +130,11 @@ SUBROUTINE attribute_test_1_8(cleanup, total_error)
' - Testing INT attributes on both datasets and groups', &
total_error)
-!!$ CALL test_attr_dense_delete(my_fcpl, my_fapl)
-!!$ CALL test_attr_dense_rename(my_fcpl, my_fapl)
-!!$ CALL test_attr_dense_unlink(my_fcpl, my_fapl)
-!!$ CALL test_attr_dense_limits(my_fcpl, my_fapl)
-!!$ CALL test_attr_big(my_fcpl, my_fapl)
ret_total_error = 0
CALL test_attr_null_space(my_fcpl, my_fapl, ret_total_error)
CALL write_test_status(ret_total_error, &
' - Testing storing attribute with "null" dataspace', &
total_error)
-!!$ CALL test_attr_deprec(fcpl, my_fapl)
ret_total_error = 0
CALL test_attr_many(new_format(i), my_fcpl, my_fapl, ret_total_error)
CALL write_test_status(ret_total_error, &
@@ -153,10 +152,6 @@ SUBROUTINE attribute_test_1_8(cleanup, total_error)
CALL write_test_status(ret_total_error, &
' - Testing compact storage on objects with attribute creation order', &
total_error)
-!!$ CALL test_attr_corder_create_dense(my_fcpl, my_fapl)
-!!$ CALL test_attr_corder_create_reopen(my_fcpl, my_fapl)
-!!$ CALL test_attr_corder_transition(my_fcpl, my_fapl)
-!!$ CALL test_attr_corder_delete(my_fcpl, my_fapl)
ret_total_error = 0
CALL test_attr_info_by_idx(new_format(i), my_fcpl, my_fapl, ret_total_error)
CALL write_test_status(ret_total_error, &
@@ -169,9 +164,6 @@ SUBROUTINE attribute_test_1_8(cleanup, total_error)
' - Testing deleting attribute by index', &
total_error)
-!!$ CALL test_attr_iterate2(new_format, my_fcpl, my_fapl)
-!!$ CALL test_attr_open_by_idx(new_format, my_fcpl, my_fapl)
-!!$ CALL test_attr_open_by_name(new_format, my_fcpl, my_fapl)
ret_total_error = 0
CALL test_attr_create_by_name(new_format(i), my_fcpl, my_fapl, ret_total_error)
CALL write_test_status(ret_total_error, &
@@ -180,7 +172,6 @@ SUBROUTINE attribute_test_1_8(cleanup, total_error)
! /* More complex tests with both "new format" and "shared" attributes */
IF( use_shared(j) ) THEN
-!!$ CALL test_attr_shared_write(my_fcpl, my_fapl)
ret_total_error = 0
CALL test_attr_shared_rename(my_fcpl, my_fapl, ret_total_error)
CALL write_test_status(ret_total_error,&
@@ -193,24 +184,8 @@ SUBROUTINE attribute_test_1_8(cleanup, total_error)
' - Testing deleting shared attributes in "compact" & "dense" storage', &
total_error)
-
-!!$ CALL test_attr_shared_unlink(my_fcpl, my_fapl)
END IF
-!!$ CALL test_attr_bug1(my_fcpl, my_fapl)
END DO
-!!$ ELSE
-!!$ CALL test_attr_big(fcpl, my_fapl)
-!!$ CALL test_attr_null_space(fcpl, my_fapl)
-!!$ CALL test_attr_deprec(fcpl, my_fapl)
-!!$ CALL test_attr_many(new_format, fcpl, my_fapl)
-!!$ CALL test_attr_info_by_idx(new_format, fcpl, my_fapl)
-!!$ CALL test_attr_delete_by_idx(new_format, fcpl, my_fapl)
-!!$ CALL test_attr_iterate2(new_format, fcpl, my_fapl)
-!!$ CALL test_attr_open_by_idx(new_format, fcpl, my_fapl)
-!!$ CALL test_attr_open_by_name(new_format, fcpl, my_fapl)
-!!$ CALL test_attr_create_by_name(new_format, fcpl, my_fapl)
-!!$ CALL test_attr_bug1(fcpl, my_fapl)
-
END IF
ENDDO
@@ -315,13 +290,7 @@ SUBROUTINE test_attr_corder_create_compact(fcpl,fapl, total_error)
my_dataset = dset2
CASE (2)
my_dataset = dset3
-! CASE DEFAULT
-! CALL HDassert(0.AND."Toomanydatasets!")
END SELECT
-!!$ is_empty = H5O_is_attr_empty_test(my_dataset)
-!!$ CALL VERIFY(is_empty, TRUE, "H5O_is_attr_empty_test")
-!!$ is_dense = H5O_is_attr_dense_test(my_dataset)
-!!$ CALL VERIFY(is_dense, FALSE, "H5O_is_attr_dense_test")
DO u = 0, max_compact - 1
! /* Create attribute */
WRITE(chr2,'(I2.2)') u
@@ -337,13 +306,6 @@ SUBROUTINE test_attr_corder_create_compact(fcpl,fapl, total_error)
CALL h5aclose_f(attr, error)
CALL check("h5aclose_f",error,total_error)
-!!$ ret = H5O_num_attrs_test(my_dataset, nattrs)
-!!$ CALL CHECK(ret, FAIL, "H5O_num_attrs_test")
-!!$ CALL VERIFY(nattrs, (u + 1))
-!!$ is_empty = H5O_is_attr_empty_test(my_dataset)
-!!$ CALL VERIFY(is_empty, FALSE, "H5O_is_attr_empty_test")
-!!$ is_dense = H5O_is_attr_dense_test(my_dataset)
-!!$ CALL VERIFY(is_dense, FALSE, "H5O_is_attr_dense_test")
END DO
END DO
@@ -387,14 +349,6 @@ SUBROUTINE test_attr_corder_create_compact(fcpl,fapl, total_error)
CASE DEFAULT
WRITE(*,*) " WARNING: To many data sets! "
END SELECT
-!!$ ret = H5O_num_attrs_test(my_dataset, nattrs)
-!!$ CALL CHECK(ret, FAIL, "H5O_num_attrs_test")
-!!$ CALL VERIFY(nattrs, max_compact, "H5O_num_attrs_test")
-!!$ is_empty = H5O_is_attr_empty_test(my_dataset)
-!!$ CALL VERIFY(is_empty, FALSE, "H5O_is_attr_empty_test")
-!!$ is_dense = H5O_is_attr_dense_test(my_dataset)
-!!$ CALL VERIFY(is_dense, FALSE, "H5O_is_attr_dense_test")
-
DO u = 0,max_compact-1
WRITE(chr2,'(I2.2)') u
attrname = 'attr '//chr2
@@ -483,8 +437,6 @@ SUBROUTINE test_attr_null_space(fcpl, fapl, total_error)
data_dims = 0
- ! /* Output message about test being performed */
-! WRITE(*,*) " - Testing Storing Attributes with 'null' dataspace"
! /* Create file */
CALL h5fcreate_f(FileName, H5F_ACC_TRUNC_F, fid, error, fcpl, fapl)
CALL check("h5fcreate_f",error,total_error)
@@ -533,9 +485,6 @@ SUBROUTINE test_attr_null_space(fcpl, fapl, total_error)
CALL check("H5Sextent_equal_f",error,total_error)
CALL Verifylogical("H5Sextent_equal_f",equal,.TRUE.,total_error)
-!!$ ret = H5Sclose(attr_sid)
-!!$ CALL CHECK(ret, FAIL, "H5Sclose")
-
CALL h5aget_storage_size_f(attr, storage_size, error)
CALL check("h5aget_storage_size_f",error,total_error)
CALL VERIFY("h5aget_storage_size_f",INT(storage_size),0,total_error)
@@ -639,11 +588,11 @@ SUBROUTINE test_attr_create_by_name(new_format,fcpl,fapl, total_error)
! /* Loop over using index for creation order value */
DO i = 1, 2
! /* Print appropriate test message */
-!!$ IF(use_index(i))THEN
-!!$ WRITE(*,*) " - Testing Creating Attributes By Name w/Creation Order Index"
-!!$ ELSE
-!!$ WRITE(*,*) " - Testing Creating Attributes By Name w/o Creation Order Index"
-!!$ ENDIF
+ IF(use_index(i))THEN
+ WRITE(*,*) " - Testing Creating Attributes By Name w/Creation Order Index"
+ ELSE
+ WRITE(*,*) " - Testing Creating Attributes By Name w/o Creation Order Index"
+ ENDIF
! /* Create file */
CALL h5fcreate_f(FileName, H5F_ACC_TRUNC_F, fid, error, fcpl, fapl)
CALL check("h5fcreate_f",error,total_error)
@@ -691,11 +640,6 @@ SUBROUTINE test_attr_create_by_name(new_format,fcpl,fapl, total_error)
! CALL HDassert(0.AND."Toomanydatasets!")
END SELECT
- ! /* Check on dataset's attribute storage status */
-!!$ is_empty = H5O_is_attr_empty_test(my_dataset);
-!!$ VERIFY(is_empty, TRUE, "H5O_is_attr_empty_test");
-!!$ is_dense = H5O_is_attr_dense_test(my_dataset);
-!!$ VERIFY(is_dense, FALSE, "H5O_is_attr_dense_test");
!/* Create attributes, up to limit of compact form */
@@ -722,15 +666,6 @@ SUBROUTINE test_attr_create_by_name(new_format,fcpl,fapl, total_error)
! CALL check("FAILED IN attr_info_by_idx_check",total_error)
ENDDO
- ! /* Verify state of object */
-!!$ ret = H5O_num_attrs_test(my_dataset, &nattrs);
-!!$ CHECK(ret, FAIL, "H5O_num_attrs_test");
-!!$ VERIFY(nattrs, max_compact, "H5O_num_attrs_test");
-!!$ is_empty = H5O_is_attr_empty_test(my_dataset);
-!!$ VERIFY(is_empty, FALSE, "H5O_is_attr_empty_test");
-!!$ is_dense = H5O_is_attr_dense_test(my_dataset);
-!!$ VERIFY(is_dense, FALSE, "H5O_is_attr_dense_test");
-
! /* Test opening attributes stored compactly */
CALL attr_open_check(fid, dsetname, my_dataset, u, total_error)
@@ -771,39 +706,8 @@ SUBROUTINE test_attr_create_by_name(new_format,fcpl,fapl, total_error)
CALL h5aclose_f(attr, error)
CALL check("h5aclose_f",error,total_error)
- ! /* Verify state of object */
-!!$ if(u >= max_compact) {
-!!$ is_dense = H5O_is_attr_dense_test(my_dataset);
-!!$ VERIFY(is_dense, (new_format ? TRUE : FALSE), "H5O_is_attr_dense_test");
-!!$ } /* end if */
-!!$
-!!$ /* Verify information for new attribute */
-!!$ ret = attr_info_by_idx_check(my_dataset, attrname, (hsize_t)u, use_index);
-!!$ CHECK(ret, FAIL, "attr_info_by_idx_check");
ENDDO
- ! /* Verify state of object */
-!!$ ret = H5O_num_attrs_test(my_dataset, &nattrs);
-!!$ CHECK(ret, FAIL, "H5O_num_attrs_test");
-!!$ VERIFY(nattrs, (max_compact * 2), "H5O_num_attrs_test");
-!!$ is_empty = H5O_is_attr_empty_test(my_dataset);
-!!$ VERIFY(is_empty, FALSE, "H5O_is_attr_empty_test");
-!!$ is_dense = H5O_is_attr_dense_test(my_dataset);
-!!$ VERIFY(is_dense, (new_format ? TRUE : FALSE), "H5O_is_attr_dense_test");
-
-!!$ if(new_format) {
-!!$ /* Retrieve & verify # of records in the name & creation order indices */
-!!$ ret = H5O_attr_dense_info_test(my_dataset, &name_count, &corder_count);
-!!$ CHECK(ret, FAIL, "H5O_attr_dense_info_test");
-!!$ if(use_index)
-!!$ VERIFY(name_count, corder_count, "H5O_attr_dense_info_test");
-!!$ VERIFY(name_count, (max_compact * 2), "H5O_attr_dense_info_test");
-!!$ } /* end if */
-
-!!$ /* Test opening attributes stored compactly */
-!!$ ret = attr_open_check(fid, dsetname, my_dataset, u);
-!!$ CHECK(ret, FAIL, "attr_open_check");
-
ENDDO
! /* Close Datasets */
@@ -914,13 +818,6 @@ SUBROUTINE test_attr_info_by_idx(new_format, fcpl, fapl, total_error)
DO i = 1, 2
- ! /* Output message about test being performed */
-!!$ IF(use_index(i))THEN
-!!$ WRITE(*,'(A72)') " - Testing Querying Attribute Info By Index w/Creation Order Index"
-!!$ ELSE
-!!$ WRITE(*,'(A74)') " - Testing Querying Attribute Info By Index w/o Creation Order Index"
-!!$ ENDIF
-
! /* Create file */
CALL h5fcreate_f(FileName, H5F_ACC_TRUNC_F, fid, error, fcpl, fapl)
CALL check("h5fcreate_f",error,total_error)
@@ -958,16 +855,8 @@ SUBROUTINE test_attr_info_by_idx(new_format, fcpl, fapl, total_error)
my_dataset = dset2
CASE (2)
my_dataset = dset3
- ! CASE DEFAULT
- ! CALL HDassert(0.AND."Toomanydatasets!")
END SELECT
- !/* Check on dataset's attribute storage status */
-!!$ is_empty = H5O_is_attr_empty_test(my_dataset);
-!!$ VERIFY(is_empty, TRUE, "H5O_is_attr_empty_test");
-!!$ is_dense = H5O_is_attr_dense_test(my_dataset);
-!!$ VERIFY(is_dense, FALSE, "H5O_is_attr_dense_test");
-
! /* Check for query on non-existant attribute */
n = 0
@@ -1005,7 +894,6 @@ SUBROUTINE test_attr_info_by_idx(new_format, fcpl, fapl, total_error)
WRITE(chr2,'(I2.2)') j
attrname = 'attr '//chr2
- ! attr = H5Acreate2(my_dataset, attrname, H5T_NATIVE_UINT, sid, H5P_DEFAULT, H5P_DEFAULT);
! check with the optional information create2 specs.
CALL h5acreate_f(my_dataset, attrname, H5T_NATIVE_INTEGER, sid, attr, error, H5P_DEFAULT_F, H5P_DEFAULT_F)
CALL check("h5acreate_f",error,total_error)
@@ -1138,7 +1026,6 @@ SUBROUTINE attr_info_by_idx_check(obj_id, attrname, n, use_index, total_error )
END IF
- ! CALL HDmemset(ainfo, 0, SIZEOF(ainfo)
CALL h5aget_info_by_idx_f(obj_id, ".", H5_INDEX_CRT_ORDER_F, H5_ITER_DEC_F, n, &
f_corder_valid, corder, cset, data_size, error)
CALL check("h5aget_info_by_idx_f",error,total_error)
@@ -1178,9 +1065,7 @@ SUBROUTINE attr_info_by_idx_check(obj_id, attrname, n, use_index, total_error )
f_corder_valid, corder, cset, data_size, error)
CALL check("h5aget_info_by_idx_f",error,total_error)
CALL VERIFY("h5aget_info_by_idx_f",corder,INT(n),total_error)
-!!$ ret = H5Aget_name_by_idx(obj_id, ".", H5_INDEX_NAME, H5_ITER_INC, n, tmpname, (size_t)NAME_BUF_SIZE, H5P_DEFAULT)
-!!$ CALL CHECK(ret, FAIL, "H5Aget_name_by_idx")
-!!$ IF (HDstrcmp(attrname, tmpname)) CALL TestErrPrintf("Line %d: attribute name size wrong!\n"C, __LINE__)
+
CALL h5aget_info_by_idx_f(obj_id, ".", H5_INDEX_NAME_F, H5_ITER_DEC_F, n, &
f_corder_valid, corder, cset, data_size, error)
CALL check("h5aget_info_by_idx_f",error,total_error)
@@ -1190,9 +1075,7 @@ SUBROUTINE attr_info_by_idx_check(obj_id, attrname, n, use_index, total_error )
f_corder_valid, corder, cset, data_size, error)
CALL check("h5aget_info_by_idx_f",error,total_error)
CALL VERIFY("h5aget_info_by_idx_f",corder,INT(n),total_error)
-!!$ ret = H5Aget_name_by_idx(obj_id, ".", H5_INDEX_NAME, H5_ITER_DEC, (hsize_t)0, tmpname, (size_t)NAME_BUF_SIZE, H5P_DEFAULT)
-!!$ CALL CHECK(ret, FAIL, "H5Aget_name_by_idx")
-!!$ IF (HDstrcmp(attrname, tmpname)) CALL TestErrPrintf("Line %d: attribute name size wrong!\n"C, __LINE__)
+
END SUBROUTINE attr_info_by_idx_check
@@ -1263,9 +1146,7 @@ SUBROUTINE test_attr_shared_rename( fcpl, fapl, total_error)
INTEGER(HSIZE_T), DIMENSION(1) :: adims2 = (/1/) ! Attribute dimension
INTEGER :: arank = 1 ! Attribure rank
- ! /* Output message about test being performed */
-! WRITE(*,*) " - Testing Renaming Shared & Unshared Attributes in Compact & Dense Storage"
-!!$ /* Initialize "big" attribute data */
+ ! /* Initialize "big" attribute data */
! /* Create dataspace for dataset */
CALL h5screate_f(H5S_SCALAR_F, sid, error)
@@ -1338,19 +1219,6 @@ SUBROUTINE test_attr_shared_rename( fcpl, fapl, total_error)
CALL h5dcreate_f(fid, DSET2_NAME, H5T_NATIVE_CHARACTER, sid, dataset2, error, dcpl_id=dcpl )
CALL check("h5dcreate_f",error,total_error)
- ! /* Check on dataset's message storage status */
-!!$ if(test_shared != 0) {
-!!$ /* Datasets' datatypes can be shared */
-!!$ ret = H5F_get_sohm_mesg_count_test(fid, H5O_DTYPE_ID, &mesg_count);
-!!$ CHECK(ret, FAIL, "H5F_get_sohm_mesg_count_test");
-!!$ VERIFY(mesg_count, 1, "H5F_get_sohm_mesg_count_test");
-!!$
-!!$ /* Datasets' dataspace can be shared */
-!!$ ret = H5F_get_sohm_mesg_count_test(fid, H5O_SDSPACE_ID, &mesg_count);
-!!$ CHECK(ret, FAIL, "H5F_get_sohm_mesg_count_test");
-!!$ VERIFY(mesg_count, 1, "H5F_get_sohm_mesg_count_test");
-!!$ } /* end if */
-
! /* Retrieve limits for compact/dense attribute storage */
CALL H5Pget_attr_phase_change_f(dcpl, max_compact, min_dense, error)
CALL check("H5Pget_attr_phase_change_f",error,total_error)
@@ -1358,16 +1226,8 @@ SUBROUTINE test_attr_shared_rename( fcpl, fapl, total_error)
! /* Close property list */
CALL h5pclose_f(dcpl,error)
CALL check("h5pclose_f", error, total_error)
-!!$
-!!$
-!!$ /* Check on datasets' attribute storage status */
-!!$ is_dense = H5O_is_attr_dense_test(dataset);
-!!$ VERIFY(is_dense, FALSE, "H5O_is_attr_dense_test");
-!!$ is_dense = H5O_is_attr_dense_test(dataset2);
-!!$ VERIFY(is_dense, FALSE, "H5O_is_attr_dense_test");
- ! /* Add attributes to each dataset, until after converting to dense storage */
-
+ ! /* Add attributes to each dataset, until after converting to dense storage */
DO u = 0, (max_compact * 2) - 1
! /* Create attribute name */
@@ -1382,10 +1242,6 @@ SUBROUTINE test_attr_shared_rename( fcpl, fapl, total_error)
CALL h5acreate_f(dataset, attrname, attr_tid, sid, attr, error, H5P_DEFAULT_F, H5P_DEFAULT_F)
CALL check("h5acreate_f",error,total_error)
-!!$ /* Check that attribute is not shared */
-!!$ is_shared = H5A_is_shared_test(attr);
-!!$ VERIFY(is_shared, FALSE, "H5A_is_shared_test");
-
! /* Write data into the attribute */
attr_integer_data(1) = u + 1
data_dims(1) = 1
@@ -1397,15 +1253,6 @@ SUBROUTINE test_attr_shared_rename( fcpl, fapl, total_error)
CALL h5acreate_f(dataset, attrname, attr_tid, big_sid, attr, error, H5P_DEFAULT_F, H5P_DEFAULT_F)
CALL check("h5acreate_f",error,total_error)
- ! Check that attribute is shared */
-!!$ is_shared = H5A_is_shared_test(attr);
-!!$ VERIFY(is_shared, TRUE, "H5A_is_shared_test");
-
- ! Check refcount for attribute */
-!!$ ret = H5A_get_shared_rc_test(attr, &shared_refcount);
-!!$ CHECK(ret, FAIL, "H5A_get_shared_rc_test");
-!!$ VERIFY(shared_refcount, 1, "H5A_get_shared_rc_test");
-!!$
! Write data into the attribute */
data_dims(1) = 1
@@ -1413,24 +1260,12 @@ SUBROUTINE test_attr_shared_rename( fcpl, fapl, total_error)
CALL h5awrite_f(attr, attr_tid, attr_integer_data, data_dims, error)
CALL check("h5awrite_f",error,total_error)
- ! Check refcount for attribute */
-!!$ ret = H5A_get_shared_rc_test(attr, &shared_refcount);
-!!$ CHECK(ret, FAIL, "H5A_get_shared_rc_test");
-!!$ VERIFY(shared_refcount, 1, "H5A_get_shared_rc_test");
ENDIF
! /* Close attribute */
CALL h5aclose_f(attr, error)
CALL check("h5aclose_f",error,total_error)
- ! /* Check on dataset's attribute storage status */
-!!$ is_dense = H5O_is_attr_dense_test(dataset);
-!!$ if(u < max_compact)
-!!$ VERIFY(is_dense, FALSE, "H5O_is_attr_dense_test");
-!!$ else
-!!$ VERIFY(is_dense, TRUE, "H5O_is_attr_dense_test");
-!!$
-!!$
! /* Alternate between creating "small" & "big" attributes */
IF(MOD(u+1,2).EQ.0)THEN
@@ -1439,10 +1274,6 @@ SUBROUTINE test_attr_shared_rename( fcpl, fapl, total_error)
CALL h5acreate_f(dataset2, attrname, attr_tid, sid, attr, error, H5P_DEFAULT_F, H5P_DEFAULT_F)
CALL check("h5acreate_f",error,total_error)
- ! /* Check that attribute is not shared */
-!!$ is_shared = H5A_is_shared_test(attr);
-!!$ VERIFY(is_shared, FALSE, "H5A_is_shared_test");
-!!$
! /* Write data into the attribute */
attr_integer_data(1) = u + 1
@@ -1456,15 +1287,6 @@ SUBROUTINE test_attr_shared_rename( fcpl, fapl, total_error)
CALL h5acreate_f(dataset2, attrname, attr_tid, big_sid, attr, error, H5P_DEFAULT_F, H5P_DEFAULT_F)
CALL check("h5acreate_f",error,total_error)
-! /* Check that attribute is shared */
-!!$ is_shared = H5A_is_shared_test(attr);
-!!$ VERIFY(is_shared, TRUE, "H5A_is_shared_test");
-!!$
-! /* Check refcount for attribute */
-!!$ ret = H5A_get_shared_rc_test(attr, &shared_refcount);
-!!$ CHECK(ret, FAIL, "H5A_get_shared_rc_test");
-!!$ VERIFY(shared_refcount, 1, "H5A_get_shared_rc_test");
-!!$
! /* Write data into the attribute */
@@ -1475,23 +1297,11 @@ SUBROUTINE test_attr_shared_rename( fcpl, fapl, total_error)
! /* Check refcount for attribute */
-!!$ ret = H5A_get_shared_rc_test(attr, &shared_refcount);
-!!$ CHECK(ret, FAIL, "H5A_get_shared_rc_test");
-!!$ VERIFY(shared_refcount, 2, "H5A_get_shared_rc_test");
-
ENDIF
! /* Close attribute */
CALL h5aclose_f(attr, error)
CALL check("h5aclose_f",error,total_error)
- ! /* Check on dataset's attribute storage status */
-!!$ is_dense = H5O_is_attr_dense_test(dataset2);
-!!$ if(u < max_compact)
-!!$ VERIFY(is_dense, FALSE, "H5O_is_attr_dense_test");
-!!$ else
-!!$ VERIFY(is_dense, TRUE, "H5O_is_attr_dense_test");
-
-
! /* Create new attribute name */
WRITE(chr2,'(I2.2)') u
@@ -1510,22 +1320,6 @@ SUBROUTINE test_attr_shared_rename( fcpl, fapl, total_error)
CALL H5Aopen_f(dataset2, attrname2, attr, error, aapl_id=H5P_DEFAULT_F)
CALL check("H5Aopen_f",error,total_error)
-!!$
-!!$ IF(MOD(u+1,2).EQ.0)THEN
-!!$ ! /* Check that attribute is not shared */
-!!$ is_shared = H5A_is_shared_test(attr);
-!!$ CALL VERIFY("H5A_is_shared_test", error, minusone)
-!!$ ELSE
-!!$ ! /* Check that attribute is shared */
-!!$ is_shared = H5A_is_shared_test(attr);
-!!$ VERIFY(is_shared, TRUE, "H5A_is_shared_test");
-!!$
-!!$ /* Check refcount for attribute */
-!!$ ret = H5A_get_shared_rc_test(attr, &shared_refcount);
-!!$ CHECK(ret, FAIL, "H5A_get_shared_rc_test");
-!!$ VERIFY(shared_refcount, 1, "H5A_get_shared_rc_test")
-!!$ ENDIF
-
! /* Close attribute */
CALL h5aclose_f(attr, error)
CALL check("h5aclose_f",error,total_error)
@@ -1534,22 +1328,6 @@ SUBROUTINE test_attr_shared_rename( fcpl, fapl, total_error)
CALL H5Aopen_f(dataset, attrname, attr, error)
CALL check("H5Aopen",error,total_error)
-!!$ if(u % 2) {
-!!$ /* Check that attribute is not shared */
-!!$ is_shared = H5A_is_shared_test(attr);
-!!$ VERIFY(is_shared, FALSE, "H5A_is_shared_test");
-!!$ } /* end if */
-!!$ else {
-!!$ /* Check that attribute is shared */
-!!$ is_shared = H5A_is_shared_test(attr);
-!!$ VERIFY(is_shared, TRUE, "H5A_is_shared_test");
-!!$
-!!$ /* Check refcount for attribute */
-!!$ ret = H5A_get_shared_rc_test(attr, &shared_refcount);
-!!$ CHECK(ret, FAIL, "H5A_get_shared_rc_test");
-!!$ VERIFY(shared_refcount, 1, "H5A_get_shared_rc_test");
-!!$ } /* end else */
-
! /* Close attribute */
CALL h5aclose_f(attr, error)
CALL check("h5aclose_f",error,total_error)
@@ -1565,22 +1343,6 @@ SUBROUTINE test_attr_shared_rename( fcpl, fapl, total_error)
! /* Check refcount on renamed attribute */
CALL H5Aopen_f(dataset2, attrname, attr, error)
CALL check("H5Aopen",error,total_error)
-!!$
-!!$ if(u % 2) {
-!!$ /* Check that attribute is not shared */
-!!$ is_shared = H5A_is_shared_test(attr);
-!!$ VERIFY(is_shared, FALSE, "H5A_is_shared_test");
-!!$ } /* end if */
-!!$ else {
-!!$ /* Check that attribute is shared */
-!!$ is_shared = H5A_is_shared_test(attr);
-!!$ VERIFY(is_shared, TRUE, "H5A_is_shared_test");
-!!$
-!!$ /* Check refcount for attribute */
-!!$ ret = H5A_get_shared_rc_test(attr, &shared_refcount);
-!!$ CHECK(ret, FAIL, "H5A_get_shared_rc_test");
-!!$ VERIFY(shared_refcount, 2, "H5A_get_shared_rc_test");
-!!$ } /* end else */
! /* Close attribute */
CALL h5aclose_f(attr, error)
@@ -1592,22 +1354,6 @@ SUBROUTINE test_attr_shared_rename( fcpl, fapl, total_error)
CALL H5Aopen_f(dataset, attrname, attr, error)
CALL check("H5Aopen",error,total_error)
-!!$ if(u % 2) {
-!!$ /* Check that attribute is not shared */
-!!$ is_shared = H5A_is_shared_test(attr);
-!!$ VERIFY(is_shared, FALSE, "H5A_is_shared_test");
-!!$ } /* end if */
-!!$ else {
-!!$ /* Check that attribute is shared */
-!!$ is_shared = H5A_is_shared_test(attr);
-!!$ VERIFY(is_shared, TRUE, "H5A_is_shared_test");
-!!$
-!!$ /* Check refcount for attribute */
-!!$ ret = H5A_get_shared_rc_test(attr, &shared_refcount);
-!!$ CHECK(ret, FAIL, "H5A_get_shared_rc_test");
-!!$ VERIFY(shared_refcount, 2, "H5A_get_shared_rc_test");
-!!$ } /* end else */
-
! /* Close attribute */
CALL h5aclose_f(attr, error)
CALL check("h5aclose_f",error,total_error)
@@ -1624,20 +1370,6 @@ SUBROUTINE test_attr_shared_rename( fcpl, fapl, total_error)
CALL h5dclose_f(dataset2, error)
CALL check("h5dclose_f",error,total_error)
-!!$ /* Check on shared message status now */
-!!$ if(test_shared != 0) {
-!!$ if(test_shared == 1) {
-!!$ /* Check on datatype storage status */
-!!$ ret = H5F_get_sohm_mesg_count_test(fid, H5O_DTYPE_ID, &mesg_count);
-!!$ CHECK(ret, FAIL, "H5F_get_sohm_mesg_count_test");
-!!$ VERIFY(mesg_count, 2, "H5F_get_sohm_mesg_count_test");
-!!$ } /* end if */
-!!$
-!!$ /* Check on dataspace storage status */
-!!$ ret = H5F_get_sohm_mesg_count_test(fid, H5O_SDSPACE_ID, &mesg_count);
-!!$ CHECK(ret, FAIL, "H5F_get_sohm_mesg_count_test");
-!!$ VERIFY(mesg_count, 2, "H5F_get_sohm_mesg_count_test");
-!!$ } /* end if */
! /* Unlink datasets with attributes */
CALL H5Ldelete_f(fid, DSET1_NAME, error, H5P_DEFAULT_F)
@@ -1651,23 +1383,6 @@ SUBROUTINE test_attr_shared_rename( fcpl, fapl, total_error)
CALL check("HLdelete_f",error,total_error)
ENDIF
- ! /* Check on attribute storage status */
-!!$ ret = H5F_get_sohm_mesg_count_test(fid, H5O_ATTR_ID, &mesg_count);
-!!$ CHECK(ret, FAIL, "H5F_get_sohm_mesg_count_test");
-!!$ VERIFY(mesg_count, 0, "H5F_get_sohm_mesg_count_test");
-!!$
-!!$ if(test_shared != 0) {
-!!$ /* Check on datatype storage status */
-!!$ ret = H5F_get_sohm_mesg_count_test(fid, H5O_DTYPE_ID, &mesg_count);
-!!$ CHECK(ret, FAIL, "H5F_get_sohm_mesg_count_test");
-!!$ VERIFY(mesg_count, 0, "H5F_get_sohm_mesg_count_test");
-!!$
-!!$ /* Check on dataspace storage status */
-!!$ ret = H5F_get_sohm_mesg_count_test(fid, H5O_SDSPACE_ID, &mesg_count);
-!!$ CHECK(ret, FAIL, "H5F_get_sohm_mesg_count_test");
-!!$ VERIFY(mesg_count, 0, "H5F_get_sohm_mesg_count_test");
-!!$ } /* end if */
-
! /* Close file */
CALL h5fclose_f(fid, error)
CALL check("h5fclose_f",error,total_error)
@@ -1774,41 +1489,6 @@ SUBROUTINE test_attr_delete_by_idx(new_format, fcpl, fapl, total_error)
! /* Loop over using index for creation order value */
DO i = 1, 2
- ! /* Print appropriate test message */
-!!$ IF(idx_type .EQ. H5_INDEX_CRT_ORDER_F)THEN
-!!$ IF(order .EQ. H5_ITER_INC_F) THEN
-!!$ IF(use_index(i))THEN
-!!$ WRITE(*,'(A102)') &
-!!$ " - Testing Deleting Attribute By Creation Order Index in Increasing Order w/Creation Order Index"
-!!$ ELSE
-!!$ WRITE(*,'(A104)') &
-!!$ " - Testing Deleting Attribute By Creation Order Index in Increasing Order w/o Creation Order Index"
-!!$ ENDIF
-!!$ ELSE
-!!$ IF(use_index(i))THEN
-!!$ WRITE(*,'(A102)') &
-!!$ " - Testing Deleting Attribute By Creation Order Index in Decreasing Order w/Creation Order Index"
-!!$ ELSE
-!!$ WRITE(*,'(A104)') &
-!!$ " - Testing Deleting Attribute By Creation Order Index in Decreasing Order w/o Creation Order Index"
-!!$ ENDIF
-!!$ ENDIF
-!!$ ELSE
-!!$ IF(order .EQ. H5_ITER_INC_F)THEN
-!!$ IF(use_index(i))THEN
-!!$ WRITE(*,'(7X,A86)')"- Testing Deleting Attribute By Name Index in Increasing Order w/Creation Order Index"
-!!$ ELSE
-!!$ WRITE(*,'(7X,A88)')"- Testing Deleting Attribute By Name Index in Increasing Order w/o Creation Order Index"
-!!$ ENDIF
-!!$ ELSE
-!!$ IF(use_index(i))THEN
-!!$ WRITE(*,'(7X,A86)') "- Testing Deleting Attribute By Name Index in Decreasing Order w/Creation Order Index"
-!!$ ELSE
-!!$ WRITE(*,'(7X,A88)') "- Testing Deleting Attribute By Name Index in Decreasing Order w/o Creation Order Index"
-!!$ ENDIF
-!!$ ENDIF
-!!$ ENDIF
-
! /* Create file */
CALL h5fcreate_f(FileName, H5F_ACC_TRUNC_F, fid, error, fcpl, fapl)
CALL check("h5fcreate_f",error,total_error)
@@ -1852,11 +1532,6 @@ SUBROUTINE test_attr_delete_by_idx(new_format, fcpl, fapl, total_error)
! CALL HDassert(0.AND."Toomanydatasets!")
END SELECT
- ! /* Check on dataset's attribute storage status */
-!!$ is_empty = H5O_is_attr_empty_test(my_dataset);
-!!$ VERIFY(is_empty, TRUE, "H5O_is_attr_empty_test");
-!!$ is_dense = H5O_is_attr_dense_test(my_dataset);
-!!$ VERIFY(is_dense, FALSE, "H5O_is_attr_dense_test");
! /* Check for deleting non-existant attribute */
!EP CALL H5Adelete_by_idx_f(my_dataset, '.', idx_type, order, 0_HSIZE_T,error, lapl_id=H5P_DEFAULT_F)
@@ -1887,18 +1562,6 @@ SUBROUTINE test_attr_delete_by_idx(new_format, fcpl, fapl, total_error)
ENDDO
-
-
- ! /* Verify state of object */
-
-!!$ ret = H5O_num_attrs_test(my_dataset, &nattrs);
-!!$ CHECK(ret, FAIL, "H5O_num_attrs_test");
-!!$ VERIFY(nattrs, max_compact, "H5O_num_attrs_test");
-!!$ is_empty = H5O_is_attr_empty_test(my_dataset);
-!!$ VERIFY(is_empty, FALSE, "H5O_is_attr_empty_test");
-!!$ is_dense = H5O_is_attr_dense_test(my_dataset);
-!!$ VERIFY(is_dense, FALSE, "H5O_is_attr_dense_test");
-
!/* Check for out of bound deletions */
CALL H5Adelete_by_idx_f(my_dataset, ".", idx_type, order, INT(u,HSIZE_T), error, lapl_id=H5P_DEFAULT_F)
CALL VERIFY("H5Adelete_by_idx_f",error,minusone,total_error)
@@ -1946,7 +1609,6 @@ SUBROUTINE test_attr_delete_by_idx(new_format, fcpl, fapl, total_error)
ENDIF
! /* Verify the name for first attribute in appropriate order */
- ! HDmemset(tmpname, 0, (size_t)NAME_BUF_SIZE);
size = 7 ! *CHECK* IF NOT THE SAME SIZE
CALL h5aget_name_by_idx_f(my_dataset, ".", idx_type, order,INT(0,hsize_t), &
@@ -1969,10 +1631,6 @@ SUBROUTINE test_attr_delete_by_idx(new_format, fcpl, fapl, total_error)
CALL H5Adelete_by_idx_f(my_dataset, ".", idx_type, order, hzero, error)
CALL check("H5Adelete_by_idx_f",error,total_error)
-
- ! /* Verify state of attribute storage (empty) */
-!!$ is_empty = H5O_is_attr_empty_test(my_dataset);
-!!$ VERIFY(is_empty, TRUE, "H5O_is_attr_empty_test");
ENDDO
! /* Work on all the datasets */
@@ -2011,34 +1669,8 @@ SUBROUTINE test_attr_delete_by_idx(new_format, fcpl, fapl, total_error)
CALL h5aclose_f(attr, error)
CALL check("h5aclose_f",error,total_error)
- ! /* Verify state of object */
- IF(u .GE. max_compact)THEN
-!!$ is_dense = H5O_is_attr_dense_test(my_dataset);
-!!$ VERIFY(is_dense, (new_format ? TRUE : FALSE), "H5O_is_attr_dense_test");
- ENDIF
- ! /* Verify information for new attribute */
-!!$ CALL check("attr_info_by_idx_check",error,total_error)
ENDDO
-
- ! /* Verify state of object */
-!!$ ret = H5O_num_attrs_test(my_dataset, &nattrs);
-!!$ CHECK(ret, FAIL, "H5O_num_attrs_test");
-!!$ VERIFY(nattrs, (max_compact * 2), "H5O_num_attrs_test");
-!!$ is_empty = H5O_is_attr_empty_test(my_dataset);
-!!$ VERIFY(is_empty, FALSE, "H5O_is_attr_empty_test");
-!!$ is_dense = H5O_is_attr_dense_test(my_dataset);
-!!$ VERIFY(is_dense, (new_format ? TRUE : FALSE), "H5O_is_attr_dense_test");
-!!$
- IF(new_format)THEN
-!!$ ! /* Retrieve & verify # of records in the name & creation order indices */
-!!$ ret = H5O_attr_dense_info_test(my_dataset, &name_count, &corder_count);
-!!$ CHECK(ret, FAIL, "H5O_attr_dense_info_test");
-!!$ IF(use_index)
-!!$ VERIFY(name_count, corder_count, "H5O_attr_dense_info_test");
-!!$ VERIFY(name_count, (max_compact * 2), "H5O_attr_dense_info_test");
- ENDIF
-
! /* Check for out of bound deletion */
CALL H5Adelete_by_idx_f(my_dataset, ".", idx_type, order, INT(u,HSIZE_T), error)
CALL VERIFY("H5Adelete_by_idx_f",error,minusone,total_error)
@@ -2054,8 +1686,6 @@ SUBROUTINE test_attr_delete_by_idx(new_format, fcpl, fapl, total_error)
my_dataset = dset2
CASE (2)
my_dataset = dset3
- ! CASE DEFAULT
- ! CALL HDassert(0.AND."Toomanydatasets!")
END SELECT
! /* Delete attributes from dense storage */
@@ -2101,9 +1731,6 @@ SUBROUTINE test_attr_delete_by_idx(new_format, fcpl, fapl, total_error)
CALL H5Adelete_by_idx_f(my_dataset, ".", idx_type, order, INT(0,HSIZE_T), error, lapl_id=H5P_DEFAULT_F)
CALL check("H5Adelete_by_idx_f",error,total_error)
- ! /* Verify state of attribute storage (empty) */
-!!$ is_empty = H5O_is_attr_empty_test(my_dataset);
-!!$ VERIFY(is_empty, TRUE, "H5O_is_attr_empty_test");
!/* Check for deletion on empty attribute storage again */
CALL H5Adelete_by_idx_f(my_dataset, ".", idx_type, order, INT(0,HSIZE_T), error)
@@ -2194,7 +1821,6 @@ SUBROUTINE test_attr_shared_delete(fcpl, fapl, total_error)
INTEGER :: arank = 1 ! Attribure rank
! /* Output message about test being performed */
-! WRITE(*,*) " - Testing Deleting Shared & Unshared Attributes in Compact & Dense Storage"
! /* Initialize "big" attribute DATA */
! /* Create dataspace for dataset */
@@ -2225,11 +1851,9 @@ SUBROUTINE test_attr_shared_delete(fcpl, fapl, total_error)
! /* Make attributes > 500 bytes shared */
CALL H5Pset_shared_mesg_nindexes_f(my_fcpl,1,error)
CALL check("H5Pset_shared_mesg_nindexes_f",error, total_error)
-!!$ CHECK_I(ret, "H5Pset_shared_mesg_nindexes");
CALL H5Pset_shared_mesg_index_f(my_fcpl, 0, H5O_SHMESG_ATTR_FLAG_F, 500,error)
CALL check(" H5Pset_shared_mesg_index_f",error, total_error)
-!!$ CHECK_I(ret, "H5Pset_shared_mesg_index");
ELSE
! /* Set up copy of file creation property list */
CALL H5Pset_shared_mesg_nindexes_f(my_fcpl,3,error)
@@ -2238,7 +1862,6 @@ SUBROUTINE test_attr_shared_delete(fcpl, fapl, total_error)
! /* Make datatypes & dataspaces > 1 byte shared (i.e. all of them :-) */
CALL H5Pset_shared_mesg_index_f(my_fcpl, 1, H5O_SHMESG_DTYPE_FLAG_F, 1,error)
CALL H5Pset_shared_mesg_index_f(my_fcpl, 2, H5O_SHMESG_SDSPACE_FLAG_F, 1,error)
-!!$ CHECK_I(ret, "H5Pset_shared_mesg_index");
ENDIF
! /* Create file */
@@ -2275,19 +1898,6 @@ SUBROUTINE test_attr_shared_delete(fcpl, fapl, total_error)
CALL h5dcreate_f(fid, DSET2_NAME, H5T_NATIVE_CHARACTER, sid, dataset2, error, dcpl_id=dcpl )
CALL check("h5dcreate_f",error,total_error)
- ! /* Check on dataset's message storage status */
-!!$ if(test_shared != 0) {
-!!$ /* Datasets' datatypes can be shared */
-!!$ ret = H5F_get_sohm_mesg_count_test(fid, H5O_DTYPE_ID, &mesg_count);
-!!$ CHECK(ret, FAIL, "H5F_get_sohm_mesg_count_test");
-!!$ VERIFY(mesg_count, 1, "H5F_get_sohm_mesg_count_test");
-!!$
-!!$ /* Datasets' dataspace can be shared */
-!!$ ret = H5F_get_sohm_mesg_count_test(fid, H5O_SDSPACE_ID, &mesg_count);
-!!$ CHECK(ret, FAIL, "H5F_get_sohm_mesg_count_test");
-!!$ VERIFY(mesg_count, 1, "H5F_get_sohm_mesg_count_test");
-!!$ } /* end if */
-!!$
! /* Retrieve limits for compact/dense attribute storage */
CALL H5Pget_attr_phase_change_f(dcpl, max_compact, min_dense, error)
CALL check("H5Pget_attr_phase_change_f",error,total_error)
@@ -2295,13 +1905,7 @@ SUBROUTINE test_attr_shared_delete(fcpl, fapl, total_error)
! /* Close property list */
CALL h5pclose_f(dcpl,error)
CALL check("h5pclose_f", error, total_error)
-!!$
-!!$ /* Check on datasets' attribute storage status */
-!!$ is_dense = H5O_is_attr_dense_test(dataset);
-!!$ VERIFY(is_dense, FALSE, "H5O_is_attr_dense_test");
-!!$ is_dense = H5O_is_attr_dense_test(dataset2);
-!!$ VERIFY(is_dense, FALSE, "H5O_is_attr_dense_test");
-!!$
+
! /* Add attributes to each dataset, until after converting to dense storage */
DO u = 0, (max_compact * 2) - 1
@@ -2318,10 +1922,6 @@ SUBROUTINE test_attr_shared_delete(fcpl, fapl, total_error)
CALL h5acreate_f(dataset, attrname, attr_tid, sid, attr, error, H5P_DEFAULT_F, H5P_DEFAULT_F)
CALL check("h5acreate_f",error,total_error)
-!!$ /* Check that attribute is not shared */
-!!$ is_shared = H5A_is_shared_test(attr);
-!!$ VERIFY(is_shared, FALSE, "H5A_is_shared_test");
-
! /* Write data into the attribute */
attr_integer_data(1) = u + 1
data_dims(1) = 1
@@ -2332,16 +1932,7 @@ SUBROUTINE test_attr_shared_delete(fcpl, fapl, total_error)
CALL h5acreate_f(dataset, attrname, attr_tid, big_sid, attr, error)
CALL check("h5acreate_f",error,total_error)
-!!$
- ! Check that attribute is shared */
-!!$ is_shared = H5A_is_shared_test(attr);
-!!$ VERIFY(is_shared, TRUE, "H5A_is_shared_test");
-
- ! Check refcount for attribute */
-!!$ ret = H5A_get_shared_rc_test(attr, &shared_refcount);
-!!$ CHECK(ret, FAIL, "H5A_get_shared_rc_test");
-!!$ VERIFY(shared_refcount, 1, "H5A_get_shared_rc_test");
-!!$
+
! Write data into the attribute */
attr_integer_data(1) = u + 1
@@ -2349,24 +1940,12 @@ SUBROUTINE test_attr_shared_delete(fcpl, fapl, total_error)
CALL h5awrite_f(attr, attr_tid, attr_integer_data, data_dims, error)
CALL check("h5awrite_f",error,total_error)
- ! Check refcount for attribute */
-!!$ ret = H5A_get_shared_rc_test(attr, &shared_refcount);
-!!$ CHECK(ret, FAIL, "H5A_get_shared_rc_test");
-!!$ VERIFY(shared_refcount, 1, "H5A_get_shared_rc_test");
ENDIF
! /* Close attribute */
CALL h5aclose_f(attr, error)
CALL check("h5aclose_f",error,total_error)
- ! /* Check on dataset's attribute storage status */
-!!$ is_dense = H5O_is_attr_dense_test(dataset);
-!!$ if(u < max_compact)
-!!$ VERIFY(is_dense, FALSE, "H5O_is_attr_dense_test");
-!!$ else
-!!$ VERIFY(is_dense, TRUE, "H5O_is_attr_dense_test");
-!!$
-!!$
! /* Alternate between creating "small" & "big" attributes */
IF(MOD(u+1,2).EQ.0)THEN
@@ -2375,10 +1954,6 @@ SUBROUTINE test_attr_shared_delete(fcpl, fapl, total_error)
CALL h5acreate_f(dataset2, attrname, attr_tid, sid, attr, error)
CALL check("h5acreate_f",error,total_error)
- ! /* Check that attribute is not shared */
-!!$ is_shared = H5A_is_shared_test(attr);
-!!$ VERIFY(is_shared, FALSE, "H5A_is_shared_test");
-!!$
! /* Write data into the attribute */
attr_integer_data(1) = u + 1
data_dims(1) = 1
@@ -2391,15 +1966,6 @@ SUBROUTINE test_attr_shared_delete(fcpl, fapl, total_error)
CALL h5acreate_f(dataset2, attrname, attr_tid, big_sid, attr, error, acpl_id=H5P_DEFAULT_F, aapl_id=H5P_DEFAULT_F)
CALL check("h5acreate_f",error,total_error)
-! /* Check that attribute is shared */
-!!$ is_shared = H5A_is_shared_test(attr);
-!!$ VERIFY(is_shared, TRUE, "H5A_is_shared_test");
-!!$
-! /* Check refcount for attribute */
-!!$ ret = H5A_get_shared_rc_test(attr, &shared_refcount);
-!!$ CHECK(ret, FAIL, "H5A_get_shared_rc_test");
-!!$ VERIFY(shared_refcount, 1, "H5A_get_shared_rc_test");
-!!$
! /* Write data into the attribute */
@@ -2408,23 +1974,11 @@ SUBROUTINE test_attr_shared_delete(fcpl, fapl, total_error)
CALL h5awrite_f(attr, attr_tid, attr_integer_data, data_dims, error)
CALL check("h5awrite_f",error,total_error)
-
-! /* Check refcount for attribute */
-!!$ ret = H5A_get_shared_rc_test(attr, &shared_refcount);
-!!$ CHECK(ret, FAIL, "H5A_get_shared_rc_test");
-!!$ VERIFY(shared_refcount, 2, "H5A_get_shared_rc_test");
-
ENDIF
! /* Close attribute */
CALL h5aclose_f(attr, error)
CALL check("h5aclose_f",error,total_error)
- ! /* Check on dataset's attribute storage status */
-!!$ is_dense = H5O_is_attr_dense_test(dataset2);
-!!$ if(u < max_compact)
-!!$ VERIFY(is_dense, FALSE, "H5O_is_attr_dense_test");
-!!$ else
-!!$ VERIFY(is_dense, TRUE, "H5O_is_attr_dense_test");
ENDDO
! /* Delete attributes from second dataset */
@@ -2439,29 +1993,9 @@ SUBROUTINE test_attr_shared_delete(fcpl, fapl, total_error)
CALL H5Adelete_by_name_f(fid, DSET2_NAME, attrname,error,lapl_id=H5P_DEFAULT_F)
CALL check("H5Adelete_by_name", error, total_error)
-!!$ /* Check refcount on attributes now */
-!!$
-!!$ /* Check refcount on first dataset's attribute */
-
CALL h5aopen_f(dataset, attrname, attr, error, aapl_id=H5P_DEFAULT_F)
CALL check("h5aopen_f",error,total_error)
-!!$
-!!$ if(u % 2) {
-! /* Check that attribute is not shared */
-!!$ is_shared = H5A_is_shared_test(attr);
-!!$ VERIFY(is_shared, FALSE, "H5A_is_shared_test");
-!!$ } /* end if */
-!!$ else {
-!/* Check that attribute is shared */
-!!$ is_shared = H5A_is_shared_test(attr);
-!!$ VERIFY(is_shared, TRUE, "H5A_is_shared_test");
-!!$
-!/* Check refcount for attribute */
-!!$ ret = H5A_get_shared_rc_test(attr, &shared_refcount);
-!!$ CHECK(ret, FAIL, "H5A_get_shared_rc_test");
-!!$ VERIFY(shared_refcount, 1, "H5A_get_shared_rc_test");
-!!$ } /* end else */
! /* Close attribute */
CALL h5aclose_f(attr, error)
@@ -2480,21 +2014,6 @@ SUBROUTINE test_attr_shared_delete(fcpl, fapl, total_error)
CALL h5dclose_f(dataset2, error)
CALL check("h5dclose_f",error,total_error)
- ! /* Check on shared message status now */
-!!$ if(test_shared != 0) {
-!!$ if(test_shared == 1) {
- ! /* Check on datatype storage status */
-!!$ ret = H5F_get_sohm_mesg_count_test(fid, H5O_DTYPE_ID, &mesg_count);
-!!$ CHECK(ret, FAIL, "H5F_get_sohm_mesg_count_test");
-!!$ VERIFY(mesg_count, 2, "H5F_get_sohm_mesg_count_test");
-!!$ } /* end if */
-!!$
-!!$ /* Check on dataspace storage status */
-!!$ ret = H5F_get_sohm_mesg_count_test(fid, H5O_SDSPACE_ID, &mesg_count);
-!!$ CHECK(ret, FAIL, "H5F_get_sohm_mesg_count_test");
-!!$ VERIFY(mesg_count, 2, "H5F_get_sohm_mesg_count_test");
-!!$ } /* end if */
-!!$
! /* Unlink datasets WITH attributes */
CALL h5ldelete_f(fid, DSET1_NAME, error, H5P_DEFAULT_F)
@@ -2509,31 +2028,11 @@ SUBROUTINE test_attr_shared_delete(fcpl, fapl, total_error)
CALL check("H5Ldelete_f", error, total_error)
ENDIF
- ! /* Check on attribute storage status */
-!!$ ret = H5F_get_sohm_mesg_count_test(fid, H5O_ATTR_ID, &mesg_count);
-!!$ CHECK(ret, FAIL, "H5F_get_sohm_mesg_count_test");
-!!$ VERIFY(mesg_count, 0, "H5F_get_sohm_mesg_count_test");
-!!$
-!!$ if(test_shared != 0) {
-!!$ /* Check on datatype storage status */
-!!$ ret = H5F_get_sohm_mesg_count_test(fid, H5O_DTYPE_ID, &mesg_count);
-!!$ CHECK(ret, FAIL, "H5F_get_sohm_mesg_count_test");
-!!$ VERIFY(mesg_count, 0, "H5F_get_sohm_mesg_count_test");
-!!$
-!!$ /* Check on dataspace storage status */
-!!$ ret = H5F_get_sohm_mesg_count_test(fid, H5O_SDSPACE_ID, &mesg_count);
-!!$ CHECK(ret, FAIL, "H5F_get_sohm_mesg_count_test");
-!!$ VERIFY(mesg_count, 0, "H5F_get_sohm_mesg_count_test");
-!!$ } /* end if */
-!!$
! /* Close file */
CALL h5fclose_f(fid, error)
CALL check("h5fclose_f",error,total_error)
-!!$
-!!$ /* Check size of file */
-!!$ filesize = h5_get_file_size(FILENAME);
-!!$ VERIFY(filesize, empty_filesize, "h5_get_file_size");
+
ENDDO
! /* Close dataspaces */
@@ -2587,8 +2086,6 @@ SUBROUTINE test_attr_dense_open( fcpl, fapl, total_error)
data_dims = 0
- ! /* Output message about test being performed */
-! WRITE(*,*) " - Testing Opening Attributes in Dense Storage"
! /* Create file */
@@ -2631,10 +2128,6 @@ SUBROUTINE test_attr_dense_open( fcpl, fapl, total_error)
CALL h5pclose_f(dcpl, error)
CALL check("h5pclose_f",error,total_error)
- ! /* Check on dataset's attribute storage status */
- ! is_dense = H5O_is_attr_dense_test(dataset);
- ! VERIFY(is_dense, FALSE, "H5O_is_attr_dense_test");
-
! /* Add attributes, until just before converting to dense storage */
DO u = 0, max_compact - 1
@@ -2657,13 +2150,8 @@ SUBROUTINE test_attr_dense_open( fcpl, fapl, total_error)
! /* Verify attributes written so far */
CALL test_attr_dense_verify(dataset, u, total_error)
- ! CHECK(ret, FAIL, "test_attr_dense_verify");
ENDDO
-
- ! /* Check on dataset's attribute storage status */
-!!$ is_dense = H5O_is_attr_dense_test(dataset);
-!!$ VERIFY(is_dense, FALSE, "H5O_is_attr_dense_test");
-
+!
! /* Add one more attribute, to push into "dense" storage */
! /* Create attribute */
@@ -2673,11 +2161,6 @@ SUBROUTINE test_attr_dense_open( fcpl, fapl, total_error)
CALL h5acreate_f(dataset, attrname, H5T_NATIVE_INTEGER, sid, attr, error, aapl_id=H5P_DEFAULT_F)
CALL check("h5acreate_f",error,total_error)
- ! /* Check on dataset's attribute storage status */
-!!$ is_dense = H5O_is_attr_dense_test(dataset);
-!!$ VERIFY(is_dense, TRUE, "H5O_is_attr_dense_test");
-
-
! /* Write data into the attribute */
data_dims(1) = 1
CALL h5awrite_f(attr, H5T_NATIVE_INTEGER, u, data_dims, error)
@@ -2990,8 +2473,6 @@ SUBROUTINE test_attr_basic_write(fapl, total_error)
attr_data1a(2) = 1087
attr_data1a(3) = -99890
- ! /* Output message about test being performed */
-! WRITE(*,*) " - Testing Basic Scalar Attribute Writing Functions"
! /* Create file */
CALL h5fcreate_f(FileName, H5F_ACC_TRUNC_F, fid1, error, H5P_DEFAULT_F, fapl)
@@ -3056,8 +2537,6 @@ SUBROUTINE test_attr_basic_write(fapl, total_error)
CALL check("h5aget_storage_size_f",error,total_error)
!EP CALL VERIFY("h5aget_storage_size_f", INT(attr_size), 2*HSIZE_T, total_error)
-! attr_size = H5Aget_storage_size(attr);
-! VERIFY(attr_size, (ATTR1_DIM1 * sizeof(int)), "H5A_get_storage_size");
! /* Read attribute information immediately, without closing attribute */
CALL h5aread_f(attr, H5T_NATIVE_INTEGER, read_data1, dimsa, error)
@@ -3156,9 +2635,6 @@ SUBROUTINE test_attr_many(new_format, fcpl, fapl, total_error)
INTEGER(HID_T) :: sid
INTEGER(HID_T) :: gid
INTEGER(HID_T) :: aid
-
-
-
INTEGER :: error
INTEGER(HSIZE_T), DIMENSION(7) :: data_dims
@@ -3175,8 +2651,6 @@ SUBROUTINE test_attr_many(new_format, fcpl, fapl, total_error)
data_dims = 0
- ! /* Output message about test being performed */
-! WRITE(*,*) " - Testing Storing Many Attributes"
!/* Create file */
CALL h5fcreate_f(FileName, H5F_ACC_TRUNC_F, fid, error, fcpl, fapl)