summaryrefslogtreecommitdiffstats
path: root/fortran/test/tH5E.f90
diff options
context:
space:
mode:
authorElena Pourmal <epourmal@hdfgroup.org>2001-11-27 15:11:56 (GMT)
committerElena Pourmal <epourmal@hdfgroup.org>2001-11-27 15:11:56 (GMT)
commit6336d12b0383b7adcf29a91cf3dbbe4ceaff6d42 (patch)
tree9f8d49005d12f8d7d248f429bc791af2fd48b796 /fortran/test/tH5E.f90
parent3adfa54afcb04b8b6fecfda31fc1585cea6ac6e4 (diff)
downloadhdf5-6336d12b0383b7adcf29a91cf3dbbe4ceaff6d42.zip
hdf5-6336d12b0383b7adcf29a91cf3dbbe4ceaff6d42.tar.gz
hdf5-6336d12b0383b7adcf29a91cf3dbbe4ceaff6d42.tar.bz2
[svn-r4638]
Purpose: Maintenance Description: Added tests for the H5E Fortran interface Platforms tested: arabica and eirene
Diffstat (limited to 'fortran/test/tH5E.f90')
-rw-r--r--fortran/test/tH5E.f9044
1 files changed, 44 insertions, 0 deletions
diff --git a/fortran/test/tH5E.f90 b/fortran/test/tH5E.f90
new file mode 100644
index 0000000..c14b101
--- /dev/null
+++ b/fortran/test/tH5E.f90
@@ -0,0 +1,44 @@
+ SUBROUTINE error_report_test(total_error)
+
+!THis subroutine tests following functionalities: h5eprint_f
+
+ USE HDF5 ! This module contains all necessary modules
+
+ IMPLICIT NONE
+ INTEGER, INTENT(OUT) :: total_error
+
+ CHARACTER(LEN=9), PARAMETER :: filename = "etestf.h5" ! File name
+ CHARACTER(LEN=12), PARAMETER :: err_file_name = "err_file.tmp"! Error output file
+
+
+
+ INTEGER(HID_T) :: file_id ! File identifier
+ INTEGER(HID_T) :: grp_id ! Group identifier
+ INTEGER :: error, tmp_error, err_flag
+
+ err_flag = 0
+ CALL h5eset_auto_f(err_flag, error)
+ CALL check("h5eprint_f",error, total_error)
+ !
+ ! Create a new file using default properties.
+ !
+ CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, error)
+ CALL check("h5fcreate_f",error,total_error)
+
+ !
+ ! Try to open non-existing group in the file.
+ ! Error message should go to the err_file_name file.
+ !
+ CALL h5gopen_f(file_id, "Doesnotexist1", grp_id, tmp_error)
+ CALL h5eprint_f(error, err_file_name)
+ CALL h5gopen_f(file_id, "Doesnotexist2", grp_id, tmp_error)
+ CALL h5eprint_f(error, err_file_name)
+
+ !
+ ! Close the file.
+ !
+ CALL h5fclose_f(file_id, error)
+ CALL check("h5fclose_f",error,total_error)
+
+ RETURN
+ END SUBROUTINE error_report_test