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.f9038
1 files changed, 26 insertions, 12 deletions
diff --git a/fortran/test/tH5A_1_8.f90 b/fortran/test/tH5A_1_8.f90
index 65064ad..01ac2b7 100644
--- a/fortran/test/tH5A_1_8.f90
+++ b/fortran/test/tH5A_1_8.f90
@@ -93,7 +93,9 @@ SUBROUTINE attribute_test_1_8(cleanup, total_error)
END IF
ret_total_error = 0
CALL test_attr_basic_write(my_fapl, ret_total_error)
- CALL write_test_status(ret_total_error, ' - Tests INT attributes on both datasets and groups', total_error)
+ CALL write_test_status(ret_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)
@@ -121,7 +123,8 @@ SUBROUTINE attribute_test_1_8(cleanup, total_error)
ret_total_error = 0
CALL test_attr_dense_open(my_fcpl, my_fapl, ret_total_error)
CALL write_test_status(ret_total_error, &
- ' - Testing INT attributes on both datasets and groups', 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)
@@ -131,21 +134,26 @@ SUBROUTINE attribute_test_1_8(cleanup, total_error)
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)
+ ' - 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, ' - Testing storing lots of attributes', total_error)
+ CALL write_test_status(ret_total_error, &
+ ' - Testing storing lots of attributes', &
+ total_error)
ret_total_error = 0
CALL test_attr_corder_create_basic(my_fcpl, my_fapl, ret_total_error)
CALL write_test_status(ret_total_error, &
- ' - Testing creating objects with attribute creation order', total_error)
+ ' - Testing creating objects with attribute creation order', &
+ total_error)
ret_total_error = 0
CALL test_attr_corder_create_compact(my_fcpl, my_fapl, ret_total_error)
CALL write_test_status(ret_total_error, &
- ' - Testing compact storage on objects with attribute creation order', 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)
@@ -153,18 +161,23 @@ SUBROUTINE attribute_test_1_8(cleanup, total_error)
ret_total_error = 0
CALL test_attr_info_by_idx(new_format, my_fcpl, my_fapl, ret_total_error)
CALL write_test_status(ret_total_error, &
- ' - Testing querying attribute info by index', total_error)
+ ' - Testing querying attribute info by index', &
+ total_error)
ret_total_error = 0
CALL test_attr_delete_by_idx(new_format, my_fcpl, my_fapl, ret_total_error)
- CALL write_test_status(ret_total_error, ' - Testing deleting attribute by index', total_error)
+ CALL write_test_status(ret_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, ' - Testing creating attributes by name', total_error)
+ CALL write_test_status(ret_total_error, &
+ ' - Testing creating attributes by name', &
+ total_error)
! /* More complex tests with both "new format" and "shared" attributes */
IF( use_shared(j) ) THEN
@@ -172,12 +185,14 @@ SUBROUTINE attribute_test_1_8(cleanup, total_error)
ret_total_error = 0
CALL test_attr_shared_rename(my_fcpl, my_fapl, ret_total_error)
CALL write_test_status(ret_total_error,&
- ' - Testing renaming shared attributes in "compact" & "dense" storage', total_error)
+ ' - Testing renaming shared attributes in "compact" & "dense" storage', &
+ total_error)
ret_total_error = 0
CALL test_attr_shared_delete(my_fcpl, my_fapl, ret_total_error)
CALL write_test_status(ret_total_error,&
- ' - Testing deleting shared attributes in "compact" & "dense" storage', total_error)
+ ' - Testing deleting shared attributes in "compact" & "dense" storage', &
+ total_error)
!!$ CALL test_attr_shared_unlink(my_fcpl, my_fapl)
@@ -2944,7 +2959,6 @@ SUBROUTINE test_attr_basic_write(fapl, total_error)
INTEGER(HID_T) :: attr,attr2 !String Attribute identifier
INTEGER(HID_T) :: group
- INTEGER(HSIZE_T), DIMENSION(7) :: data_dims
CHARACTER(LEN=25) :: check_name
CHARACTER(LEN=18) :: chr_exact_size