summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5ff.f90
diff options
context:
space:
mode:
authorElena Pourmal <epourmal@hdfgroup.org>2000-11-17 22:43:27 (GMT)
committerElena Pourmal <epourmal@hdfgroup.org>2000-11-17 22:43:27 (GMT)
commit5dad15399582249d6fa0d7100a84b46116925bf8 (patch)
tree9c021ed6bde61abd44769ade48de63c235186983 /fortran/src/H5ff.f90
parentcfac5f773e8fc360a69d8384674d7a557d5a43f6 (diff)
downloadhdf5-5dad15399582249d6fa0d7100a84b46116925bf8.zip
hdf5-5dad15399582249d6fa0d7100a84b46116925bf8.tar.gz
hdf5-5dad15399582249d6fa0d7100a84b46116925bf8.tar.bz2
[svn-r2975]
Purpose: Code maintenance and development Description: I added two functions h5open_f and h5close_f to initialize C library and Fortran interface (flags, predefined datatypes, etc). Those calls are required for any F90 program that uses HDF5. I renamed H5f90misc.c and H5f90miscf.f90 files to H5f.c and H5ff.f90. New functions are added to those new files. Platforms tested: Solaris 2.6
Diffstat (limited to 'fortran/src/H5ff.f90')
-rw-r--r--fortran/src/H5ff.f9040
1 files changed, 40 insertions, 0 deletions
diff --git a/fortran/src/H5ff.f90 b/fortran/src/H5ff.f90
new file mode 100644
index 0000000..198a616
--- /dev/null
+++ b/fortran/src/H5ff.f90
@@ -0,0 +1,40 @@
+ SUBROUTINE h5open_f(error)
+ USE H5GLOBAL
+
+ IMPLICIT NONE
+ INTEGER, INTENT(OUT) :: error
+ INTEGER :: error_0, error_1, error_2
+ INTEGER, EXTERNAL :: h5init_types_c
+ INTEGER, EXTERNAL :: h5init_flags_c
+ INTEGER, EXTERNAL :: h5open_c
+ error_0 = h5open_c()
+ error_1 = h5init_types_c(predef_types, floating_types, integer_types)
+ error_1 = h5init_flags_c(H5D_flags, &
+ H5E_flags, &
+ H5F_flags, &
+ H5FD_flags, &
+ H5G_flags, &
+ H5I_flags, &
+ H5P_flags, &
+ H5R_flags, &
+ H5S_flags, &
+ H5T_flags )
+ error = error_0 + error_1 + error_2
+
+ END SUBROUTINE h5open_f
+
+ SUBROUTINE h5close_f(error)
+ USE H5GLOBAL
+
+ IMPLICIT NONE
+ INTEGER :: error_1, error_2
+ INTEGER, INTENT(OUT) :: error
+ INTEGER, EXTERNAL :: h5close_types_c, h5close_c
+ error_1 = h5close_types_c(predef_types, PREDEF_TYPES_LEN, &
+ floating_types, FLOATING_TYPES_LEN, &
+ integer_types, INTEGER_TYPES_LEN )
+ error_2 = h5close_c()
+ error = error_1 + error_2
+
+ END SUBROUTINE h5close_f
+