summaryrefslogtreecommitdiffstats
path: root/fortran
diff options
context:
space:
mode:
Diffstat (limited to 'fortran')
-rw-r--r--fortran/examples/refobjexample.f902
-rw-r--r--fortran/src/H5Dff.F9064
-rw-r--r--fortran/src/H5Iff.F902
-rw-r--r--fortran/src/H5Pff.F902
-rw-r--r--fortran/src/H5Tf.c2
-rw-r--r--fortran/src/H5Tff.F902
-rw-r--r--fortran/test/tH5A.F9042
-rw-r--r--fortran/test/tH5T.F904
8 files changed, 60 insertions, 60 deletions
diff --git a/fortran/examples/refobjexample.f90 b/fortran/examples/refobjexample.f90
index 873b420..0d6595c 100644
--- a/fortran/examples/refobjexample.f90
+++ b/fortran/examples/refobjexample.f90
@@ -65,7 +65,7 @@
!
CALL h5gcreate_f(file_id, groupname1, grp1_id, error)
!
- ! Create a group inside the created gorup
+ ! Create a group inside the created group
!
CALL h5gcreate_f(grp1_id, groupname2, grp2_id, error)
!
diff --git a/fortran/src/H5Dff.F90 b/fortran/src/H5Dff.F90
index 6b77a8c..216b005 100644
--- a/fortran/src/H5Dff.F90
+++ b/fortran/src/H5Dff.F90
@@ -746,8 +746,8 @@ CONTAINS
! element
INTEGER, INTENT(IN), DIMENSION(dims(1),dims(2)), TARGET :: buf ! Data buffer
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identfier
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identfier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identifier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identifier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp ! Transfer property list identifier
INTEGER(HID_T) :: xfer_prp_default
INTEGER(HID_T) :: mem_space_id_default
@@ -800,8 +800,8 @@ CONTAINS
DIMENSION(dims(1),dims(2)), TARGET :: buf ! Data buffer
INTEGER, INTENT(OUT) :: hdferr ! Error code
! -1 if failed, 0 otherwise
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identfier
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identfier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identifier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identifier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp ! Transfer property list identifier
INTEGER(HID_T) :: xfer_prp_default
INTEGER(HID_T) :: mem_space_id_default
@@ -856,8 +856,8 @@ CONTAINS
REAL, INTENT(IN), &
DIMENSION(dims(1),dims(2)) :: buf ! Data buffer
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identfier
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identfier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identifier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identifier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp ! Transfer property list identifier
INTEGER(HID_T) :: xfer_prp_default
@@ -911,8 +911,8 @@ CONTAINS
DIMENSION(dims(1),dims(2)) :: buf ! Data buffer
INTEGER, INTENT(OUT) :: hdferr ! Error code
! -1 if failed, 0 otherwise
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identfier
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identfier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identifier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identifier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp ! Transfer property list identifier
INTEGER(HID_T) :: xfer_prp_default
@@ -967,8 +967,8 @@ CONTAINS
INTEGER(SIZE_T), INTENT(IN), DIMENSION(*) :: str_len ! Array to store the length of each element
CHARACTER(LEN=*), INTENT(IN), DIMENSION(dims(2)) :: buf ! Data buffer
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identfier
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identfier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identifier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identifier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp ! Transfer property list identifier
INTEGER(HID_T) :: xfer_prp_default
@@ -1023,8 +1023,8 @@ CONTAINS
CHARACTER(LEN=*), INTENT(OUT), &
DIMENSION(dims(2)) :: buf ! Data buffer
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identfier
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identfier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identifier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identifier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp ! Transfer property list identifier
INTEGER(HID_T) :: xfer_prp_default
@@ -1198,8 +1198,8 @@ CONTAINS
INTEGER(HSIZE_T), DIMENSION(*), INTENT(IN) :: dims ! size of the buffer buf
TYPE(hobj_ref_t_f), DIMENSION(dims(1)), INTENT(IN), TARGET :: buf ! Data buffer
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identfier
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identfier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identifier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identifier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp ! Transfer property list identifier
INTEGER(HID_T) :: xfer_prp_default
@@ -1230,8 +1230,8 @@ CONTAINS
INTEGER(HSIZE_T), DIMENSION(*), INTENT(IN) :: dims ! size of the buffer buf
TYPE(hdset_reg_ref_t_f), DIMENSION(dims(1)), INTENT(IN), TARGET :: buf ! Data buffer
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identfier
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identfier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identifier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identifier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp ! Transfer property list identifier
INTEGER(HID_T) :: xfer_prp_default
@@ -1292,8 +1292,8 @@ CONTAINS
INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims
CHARACTER(*), INTENT(IN), TARGET :: buf ! Data buffer
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identfier
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identfier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identifier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identifier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp ! Transfer property list identifier
CALL h5dwrite_char_scalar_fix(dset_id, mem_type_id, buf, LEN(buf), dims, hdferr, &
@@ -1311,8 +1311,8 @@ CONTAINS
INTEGER, INTENT(IN) :: buf_len
CHARACTER(LEN=buf_len), INTENT(IN), TARGET :: buf ! Data buffer
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identfier
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identfier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identifier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identifier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp ! Transfer property list identifier
INTEGER(HID_T) :: xfer_prp_default
INTEGER(HID_T) :: mem_space_id_default
@@ -1344,8 +1344,8 @@ CONTAINS
TYPE(hobj_ref_t_f), INTENT(INOUT) , &
DIMENSION(dims(1)), TARGET :: buf
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identfier
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identfier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identifier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identifier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp ! Transfer property list identifier
INTEGER(HID_T) :: xfer_prp_default
@@ -1376,8 +1376,8 @@ CONTAINS
TYPE(hdset_reg_ref_t_f), INTENT(INOUT), &
DIMENSION(dims(1)), TARGET :: buf
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identfier
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identfier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identifier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identifier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp ! Transfer property list identifier
INTEGER(HID_T) :: xfer_prp_default
INTEGER(HID_T) :: mem_space_id_default
@@ -1438,8 +1438,8 @@ CONTAINS
INTEGER(HSIZE_T), INTENT(IN), DIMENSION(*) :: dims
CHARACTER(LEN=*), INTENT(INOUT) :: buf ! Data buffer
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identfier
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identfier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identifier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identifier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp ! Transfer property list identifier
INTEGER(HID_T) :: xfer_prp_default
@@ -1468,8 +1468,8 @@ CONTAINS
INTEGER, INTENT(IN) :: buf_len
CHARACTER(LEN=buf_len), INTENT(INOUT), TARGET :: buf ! Data buffer
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identfier
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identfier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identifier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identifier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp ! Transfer property list identifier
TYPE(C_PTR) :: f_ptr
@@ -1525,8 +1525,8 @@ CONTAINS
INTEGER(HID_T), INTENT(IN) :: mem_type_id ! Memory datatype identifier
TYPE(C_PTR), INTENT(IN) :: buf
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identfier
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identfier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identifier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identifier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp ! Transfer property list identifier
INTEGER(HID_T) :: xfer_prp_default
@@ -1590,8 +1590,8 @@ CONTAINS
INTEGER(HID_T), INTENT(IN) :: mem_type_id ! Memory datatype identifier
TYPE(C_PTR), INTENT(INOUT) :: buf
INTEGER, INTENT(OUT) :: hdferr ! Error code
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identfier
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identfier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: mem_space_id ! Memory dataspace identifier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: file_space_id ! File dataspace identifier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: xfer_prp ! Transfer property list identifier
INTEGER(HID_T) :: xfer_prp_default
diff --git a/fortran/src/H5Iff.F90 b/fortran/src/H5Iff.F90
index 07bcb20..cda26ed 100644
--- a/fortran/src/H5Iff.F90
+++ b/fortran/src/H5Iff.F90
@@ -108,7 +108,7 @@ CONTAINS
! h5iget_name_f
!
! PURPOSE
-! Gets a name of an object specified by its idetifier.
+! Gets a name of an object specified by its identifier.
!
! INPUTS
! obj_id - attribute identifier
diff --git a/fortran/src/H5Pff.F90 b/fortran/src/H5Pff.F90
index c55b7d9..96080ce 100644
--- a/fortran/src/H5Pff.F90
+++ b/fortran/src/H5Pff.F90
@@ -3564,7 +3564,7 @@ CONTAINS
SUBROUTINE h5pget_class_name_f(prp_id, name, size, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: prp_id ! Property list identifier
- CHARACTER(LEN=*), INTENT(OUT) :: name ! Buffer to retireve class name
+ CHARACTER(LEN=*), INTENT(OUT) :: name ! Buffer to retrieve class name
INTEGER, INTENT(OUT) :: size ! Actual length of the class name
INTEGER, INTENT(OUT) :: hdferr ! Error code
! 0 on success and -1 on failure
diff --git a/fortran/src/H5Tf.c b/fortran/src/H5Tf.c
index d9f75d9..eee0020 100644
--- a/fortran/src/H5Tf.c
+++ b/fortran/src/H5Tf.c
@@ -887,7 +887,7 @@ h5tget_ebias_c(hid_t_f *type_id, size_t_f *ebias)
* floating-point type of the datatype
* INPUTS
* type_id - identifier of the dataspace
- * ebias - exponent bias of a floating-point type of the datatyp
+ * ebias - exponent bias of a floating-point type of the datatype
* RETURNS
* 0 on success, -1 on failure
* AUTHOR
diff --git a/fortran/src/H5Tff.F90 b/fortran/src/H5Tff.F90
index 7582dab..0a11976 100644
--- a/fortran/src/H5Tff.F90
+++ b/fortran/src/H5Tff.F90
@@ -901,7 +901,7 @@ CONTAINS
! h5tset_sign_f
!
! PURPOSE
-! Sets the sign proprety for an integer type.
+! Sets the sign property for an integer type.
!
! INPUTS
! type_id - datatype identifier
diff --git a/fortran/test/tH5A.F90 b/fortran/test/tH5A.F90
index 115ce70..f846128 100644
--- a/fortran/test/tH5A.F90
+++ b/fortran/test/tH5A.F90
@@ -383,41 +383,41 @@ CONTAINS
CALL h5dopen_f(file_id, dsetname, dset_id, error)
CALL check("h5dopen_f",error,total_error)
!
- !open the String attrbute by name
+ !open the String attribute by name
!
CALL h5aopen_name_f(dset_id, aname, attr_id, error)
CALL check("h5aopen_name_f",error,total_error)
!
- !open the CHARACTER attrbute by name
+ !open the CHARACTER attribute by name
!
CALL h5aopen_name_f(dset_id, aname2, attr2_id, error)
CALL check("h5aopen_name_f",error,total_error)
!
- !open the DOUBLE attrbute by name
+ !open the DOUBLE attribute by name
!
CALL h5aopen_name_f(dset_id, aname3, attr3_id, error)
CALL check("h5aopen_name_f",error,total_error)
!
- !open the REAL attrbute by name
+ !open the REAL attribute by name
!
CALL h5aopen_name_f(dset_id, aname4, attr4_id, error)
CALL check("h5aopen_name_f",error,total_error)
!
- !open the INTEGER attrbute by name
+ !open the INTEGER attribute by name
!
CALL h5aopen_name_f(dset_id, aname5, attr5_id, error)
CALL check("h5aopen_name_f",error,total_error)
!
- !open the NULL attrbute by name
+ !open the NULL attribute by name
!
CALL h5aopen_name_f(dset_id, aname6, attr6_id, error)
CALL check("h5aopen_name_f",error,total_error)
!
- !get the attrbute name
+ !get the attribute name
!
CALL h5aget_name_f(attr5_id, name_size, attr_name, error)
CALL check("h5aget_name_f",error,total_error)
@@ -429,44 +429,44 @@ CONTAINS
END IF
!
- !get the STRING attrbute space
+ !get the STRING attribute space
!
CALL h5aget_space_f(attr_id, attr_space, error)
CALL check("h5aget_space_f",error,total_error)
!
- !get other attrbute space
+ !get other attribute space
!
CALL h5aget_space_f(attr2_id, attr2_space, error)
CALL check("h5aget_space_f",error,total_error)
!
- !get the string attrbute datatype
+ !get the string attribute datatype
!
CALL h5aget_type_f(attr_id, attr_type, error)
CALL check("h5aget_type_f",error,total_error)
!
- !get the character attrbute datatype
+ !get the character attribute datatype
!
CALL h5aget_type_f(attr2_id, attr2_type, error)
CALL check("h5aget_type_f",error,total_error)
!
- !get the double attrbute datatype
+ !get the double attribute datatype
!
CALL h5aget_type_f(attr3_id, attr3_type, error)
CALL check("h5aget_type_f",error,total_error)
!
- !get the real attrbute datatype
+ !get the real attribute datatype
!
CALL h5aget_type_f(attr4_id, attr4_type, error)
CALL check("h5aget_type_f",error,total_error)
!
- !get the integer attrbute datatype
+ !get the integer attribute datatype
!
CALL h5aget_type_f(attr5_id, attr5_type, error)
CALL check("h5aget_type_f",error,total_error)
!
- !get the null attrbute datatype
+ !get the null attribute datatype
!
CALL h5aget_type_f(attr6_id, attr6_type, error)
CALL check("h5aget_type_f",error,total_error)
@@ -497,7 +497,7 @@ CONTAINS
CALL check("h5aread_f",error,total_error)
IF ( (aread_data(1) .NE. attr_data(1)) .OR. (aread_data(2) .NE. attr_data(2)) ) THEN
- WRITE(*,*) "Read back string attrbute is wrong", aread_data(1), aread_data(2)
+ WRITE(*,*) "Read back string attribute is wrong", aread_data(1), aread_data(2)
total_error = total_error + 1
END IF
@@ -507,7 +507,7 @@ CONTAINS
CALL h5aread_f(attr2_id, H5T_NATIVE_CHARACTER, aread_character_data, data_dims, error)
CALL check("h5aread_f",error,total_error)
IF (aread_character_data .NE. 'A' ) THEN
- WRITE(*,*) "Read back character attrbute is wrong ",aread_character_data
+ WRITE(*,*) "Read back character attribute is wrong ",aread_character_data
total_error = total_error + 1
END IF
!
@@ -516,7 +516,7 @@ CONTAINS
data_dims(1) = 1
CALL h5aread_f(attr3_id, H5T_NATIVE_DOUBLE, aread_double_data, data_dims, error)
CALL check("h5aread_f",error,total_error)
- CALL VERIFY("Read back double attrbute is wrong", aread_double_data(1),3.459_Fortran_DOUBLE,total_error)
+ CALL VERIFY("Read back double attribute is wrong", aread_double_data(1),3.459_Fortran_DOUBLE,total_error)
!
!read the real attribute data back to memory
@@ -524,7 +524,7 @@ CONTAINS
data_dims(1) = 1
CALL h5aread_f(attr4_id, H5T_NATIVE_REAL, aread_real_data, data_dims, error)
CALL check("h5aread_f",error,total_error)
- CALL VERIFY("Read back real attrbute is wrong", aread_real_data(1),4.0,total_error)
+ CALL VERIFY("Read back real attribute is wrong", aread_real_data(1),4.0,total_error)
!
!read the Integer attribute data back to memory
!
@@ -532,7 +532,7 @@ CONTAINS
CALL h5aread_f(attr5_id, H5T_NATIVE_INTEGER, aread_integer_data, data_dims, error)
CALL check("h5aread_f",error,total_error)
IF (aread_integer_data(1) .NE. 5 ) THEN
- WRITE(*,*) "Read back integer attrbute is wrong ", aread_integer_data
+ WRITE(*,*) "Read back integer attribute is wrong ", aread_integer_data
total_error = total_error + 1
END IF
!
@@ -542,7 +542,7 @@ CONTAINS
CALL h5aread_f(attr6_id, H5T_NATIVE_INTEGER, aread_null_data, data_dims, error)
CALL check("h5aread_f",error,total_error)
IF (aread_null_data(1) .NE. 7 ) THEN
- WRITE(*,*) "Read back null attrbute is wrong ", aread_null_data
+ WRITE(*,*) "Read back null attribute is wrong ", aread_null_data
total_error = total_error + 1
END IF
diff --git a/fortran/test/tH5T.F90 b/fortran/test/tH5T.F90
index d24ac89..7673993 100644
--- a/fortran/test/tH5T.F90
+++ b/fortran/test/tH5T.F90
@@ -862,7 +862,7 @@ CONTAINS
CALL h5fcreate_f(fix_filename,H5F_ACC_TRUNC_F,file_id,error)
CALL check("h5fcreate_f", error, total_error)
!
- ! Create enumeration datatype with tow values
+ ! Create enumeration datatype with two values
!
CALL h5tenum_create_f(H5T_NATIVE_INTEGER,dtype_id,error)
CALL check("h5tenum_create_f", error, total_error)
@@ -871,7 +871,7 @@ CONTAINS
CALL h5tenum_insert_f(dtype_id,false,DATA(2),error)
CALL check("h5tenum_insert_f", error, total_error)
!
- ! Create write and close a dataset with enum datatype
+ ! Create write and close a dataset with enum datatype
!
CALL h5screate_simple_f(1,dsize,dspace_id,error)
CALL check("h5screate_simple_f", error, total_error)