summaryrefslogtreecommitdiffstats
path: root/fortran/test/tH5MISC_1_8.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/test/tH5MISC_1_8.f90')
-rw-r--r--fortran/test/tH5MISC_1_8.f9070
1 files changed, 35 insertions, 35 deletions
diff --git a/fortran/test/tH5MISC_1_8.f90 b/fortran/test/tH5MISC_1_8.f90
index efc350e..9b33f8a 100644
--- a/fortran/test/tH5MISC_1_8.f90
+++ b/fortran/test/tH5MISC_1_8.f90
@@ -84,12 +84,12 @@ SUBROUTINE dtransform(cleanup, total_error)
END SUBROUTINE dtransform
-!/****************************************************************
+!***************************************************************
!**
!** test_genprop_basic_class(): Test basic generic property list code.
!** Tests creating new generic classes.
!**
-!****************************************************************/
+!***************************************************************
SUBROUTINE test_genprop_basic_class(cleanup, total_error)
@@ -100,18 +100,18 @@ SUBROUTINE test_genprop_basic_class(cleanup, total_error)
LOGICAL, INTENT(IN) :: cleanup
INTEGER, INTENT(INOUT) :: total_error
- INTEGER(HID_T) :: cid1 !/* Generic Property class ID */
- INTEGER(HID_T) :: cid2 !/* Generic Property class ID */
+ INTEGER(HID_T) :: cid1 ! Generic Property class ID
+ INTEGER(HID_T) :: cid2 ! Generic Property class ID
CHARACTER(LEN=7) :: CLASS1_NAME = "Class 1"
- CHARACTER(LEN=7) :: name ! /* Name of class */
- CHARACTER(LEN=10) :: name_big ! /* Name of class bigger buffer */
- CHARACTER(LEN=4) :: name_small ! /* Name of class smaller buffer*/
+ CHARACTER(LEN=7) :: name ! Name of class
+ CHARACTER(LEN=10) :: name_big ! Name of class bigger buffer
+ CHARACTER(LEN=4) :: name_small ! Name of class smaller buffer
INTEGER :: error
INTEGER :: size
LOGICAL :: flag
- !/* Output message about test being performed */
+ ! Output message about test being performed
!WRITE(*,*) "Testing Basic Generic Property List Class Creation Functionality"
@@ -121,11 +121,11 @@ SUBROUTINE test_genprop_basic_class(cleanup, total_error)
CALL H5Pget_class_name_f(cid1, name, size, error)
CALL VERIFY("H5Pget_class_name", error, -1, error)
- ! /* Create a new generic class, derived from the root of the class hierarchy */
+ ! Create a new generic class, derived from the root of the class hierarchy
CALL H5Pcreate_class_f(H5P_ROOT_F, CLASS1_NAME, cid1, error)
CALL check("H5Pcreate_class", error, total_error)
- ! /* Check class name */
+ ! Check class name
CALL H5Pget_class_name_f(cid1, name, size, error)
CALL check("H5Pget_class_name", error, total_error)
CALL VERIFY("H5Pget_class_name", size,7,error)
@@ -135,7 +135,7 @@ SUBROUTINE test_genprop_basic_class(cleanup, total_error)
total_error = total_error + 1
ENDIF
- ! /* Check class name smaller buffer*/
+ ! Check class name smaller buffer
CALL H5Pget_class_name_f(cid1, name_small, size, error)
CALL check("H5Pget_class_name", error, total_error)
CALL VERIFY("H5Pget_class_name", size,7,error)
@@ -145,7 +145,7 @@ SUBROUTINE test_genprop_basic_class(cleanup, total_error)
total_error = total_error + 1
ENDIF
- ! /* Check class name bigger buffer*/
+ ! Check class name bigger buffer
CALL H5Pget_class_name_f(cid1, name_big, size, error)
CALL check("H5Pget_class_name", error, total_error)
CALL VERIFY("H5Pget_class_name", size,7,error)
@@ -155,27 +155,27 @@ SUBROUTINE test_genprop_basic_class(cleanup, total_error)
total_error = total_error + 1
ENDIF
- ! /* Check class parent */
+ ! Check class parent
CALL H5Pget_class_parent_f(cid1, cid2, error)
CALL check("H5Pget_class_parent_f", error, total_error)
- ! /* Verify class parent correct */
+ ! Verify class parent correct
CALL H5Pequal_f(cid2, H5P_ROOT_F, flag, error)
CALL check("H5Pequal_f", error, total_error)
CALL verifylogical("H5Pequal_f", flag, .TRUE., total_error)
- ! /* Make certain false postives aren't being returned */
+ ! Make certain false postives aren't being returned
CALL H5Pequal_f(cid2, H5P_FILE_CREATE_F, flag, error)
CALL check("H5Pequal_f", error, total_error)
CALL verifylogical("H5Pequal_f", flag, .FALSE., total_error)
- !/* Close parent class */
+ ! Close parent class
CALL H5Pclose_class_f(cid2, error)
CALL check("H5Pclose_class_f", error, total_error)
- !/* Close class */
+ ! Close class
CALL H5Pclose_class_f(cid1, error)
CALL check("H5Pclose_class_f", error, total_error)
@@ -183,11 +183,11 @@ END SUBROUTINE test_genprop_basic_class
SUBROUTINE test_h5s_encode(cleanup, total_error)
-!/****************************************************************
+!***************************************************************
!**
!** test_h5s_encode(): Test H5S (dataspace) encoding and decoding.
!**
-!****************************************************************/
+!***************************************************************
USE HDF5 ! This module contains all necessary modules
USE TH5_MISC
@@ -195,16 +195,16 @@ SUBROUTINE test_h5s_encode(cleanup, total_error)
LOGICAL, INTENT(IN) :: cleanup
INTEGER, INTENT(INOUT) :: total_error
- INTEGER(hid_t) :: sid1, sid3! /* Dataspace ID */
+ INTEGER(hid_t) :: sid1, sid3! Dataspace ID
INTEGER(hid_t) :: decoded_sid1, decoded_sid3
- INTEGER :: rank !/* LOGICAL rank of dataspace */
+ INTEGER :: rank ! LOGICAL rank of dataspace
INTEGER(size_t) :: sbuf_size=0, scalar_size=0
! Make sure the size is large
CHARACTER(LEN=288) :: sbuf
CHARACTER(LEN=288) :: scalar_buf
- INTEGER(hsize_t) :: n ! /* Number of dataspace elements */
+ INTEGER(hsize_t) :: n ! Number of dataspace elements
INTEGER(hsize_t), DIMENSION(1:3) :: start = (/0, 0, 0/)
INTEGER(hsize_t), DIMENSION(1:3) :: stride = (/2, 5, 3/)
@@ -221,10 +221,10 @@ SUBROUTINE test_h5s_encode(cleanup, total_error)
INTEGER :: SPACE1_RANK = 3
INTEGER :: error
- !/*-------------------------------------------------------------------------
+ !-------------------------------------------------------------------------
! * Test encoding and decoding of simple dataspace and hyperslab selection.
! *-------------------------------------------------------------------------
- ! */
+ !
CALL H5Screate_simple_f(SPACE1_RANK, dims1, sid1, error)
CALL check("H5Screate_simple", error, total_error)
@@ -234,14 +234,14 @@ SUBROUTINE test_h5s_encode(cleanup, total_error)
CALL check("h5sselect_hyperslab_f", error, total_error)
- !/* Encode simple data space in a buffer */
+ ! Encode simple data space in a buffer
! First find the buffer size
CALL H5Sencode_f(sid1, sbuf, sbuf_size, error)
CALL check("H5Sencode", error, total_error)
- ! /* Try decoding bogus buffer */
+ ! Try decoding bogus buffer
CALL H5Sdecode_f(sbuf, decoded_sid1, error)
CALL VERIFY("H5Sdecode", error, -1, total_error)
@@ -249,12 +249,12 @@ SUBROUTINE test_h5s_encode(cleanup, total_error)
CALL H5Sencode_f(sid1, sbuf, sbuf_size, error)
CALL check("H5Sencode", error, total_error)
- ! /* Decode from the dataspace buffer and return an object handle */
+ ! Decode from the dataspace buffer and return an object handle
CALL H5Sdecode_f(sbuf, decoded_sid1, error)
CALL check("H5Sdecode", error, total_error)
- ! /* Verify the decoded dataspace */
+ ! Verify the decoded dataspace
CALL h5sget_simple_extent_npoints_f(decoded_sid1, n, error)
CALL check("h5sget_simple_extent_npoints_f", error, total_error)
CALL VERIFY("h5sget_simple_extent_npoints_f", INT(n), INT(SPACE1_DIM1 * SPACE1_DIM2 * SPACE1_DIM3), &
@@ -269,16 +269,16 @@ SUBROUTINE test_h5s_encode(cleanup, total_error)
CALL h5sclose_f(decoded_sid1, error)
CALL check("h5sclose_f", error, total_error)
- ! /*-------------------------------------------------------------------------
+ ! -------------------------------------------------------------------------
! * Test encoding and decoding of scalar dataspace.
! *-------------------------------------------------------------------------
- ! */
- ! /* Create scalar dataspace */
+ !
+ ! Create scalar dataspace
CALL H5Screate_f(H5S_SCALAR_F, sid3, error)
CALL check("H5Screate_f",error, total_error)
- ! /* Encode scalar data space in a buffer */
+ ! Encode scalar data space in a buffer
! First find the buffer size
CALL H5Sencode_f(sid3, scalar_buf, scalar_size, error)
@@ -290,19 +290,19 @@ SUBROUTINE test_h5s_encode(cleanup, total_error)
CALL check("H5Sencode_f", error, total_error)
- ! /* Decode from the dataspace buffer and return an object handle */
+ ! Decode from the dataspace buffer and return an object handle
CALL H5Sdecode_f(scalar_buf, decoded_sid3, error)
CALL check("H5Sdecode_f", error, total_error)
- ! /* Verify extent type */
+ ! Verify extent type
CALL H5Sget_simple_extent_type_f(decoded_sid3, space_type, error)
CALL check("H5Sget_simple_extent_type_f", error, total_error)
CALL VERIFY("H5Sget_simple_extent_type_f", space_type, H5S_SCALAR_F, total_error)
- ! /* Verify decoded dataspace */
+ ! Verify decoded dataspace
CALL h5sget_simple_extent_npoints_f(decoded_sid3, n, error)
CALL check("h5sget_simple_extent_npoints_f", error, total_error)
CALL VERIFY("h5sget_simple_extent_npoints_f", INT(n), 1, total_error)