diff options
author | Elena Pourmal <epourmal@hdfgroup.org> | 2001-04-29 01:08:16 (GMT) |
---|---|---|
committer | Elena Pourmal <epourmal@hdfgroup.org> | 2001-04-29 01:08:16 (GMT) |
commit | 6ff2e7b303b0479bba8c4709a1fcac61fbdf9f2b (patch) | |
tree | d652324fca55cc851875f042bc7320ce5604f7d1 /fortran/src/H5_ff.f90 | |
parent | 2c8b1571d25f20cf8d00f346851ce3660364c149 (diff) | |
download | hdf5-6ff2e7b303b0479bba8c4709a1fcac61fbdf9f2b.zip hdf5-6ff2e7b303b0479bba8c4709a1fcac61fbdf9f2b.tar.gz hdf5-6ff2e7b303b0479bba8c4709a1fcac61fbdf9f2b.tar.bz2 |
[svn-r3872]
Purpose:
Windows port
Description:
Names of the H5f.c and H5ff.f90 files caused problems on Windows98.
Compilation of H5F.c (C Library) and H5Ff.f90 (Fortran library)
as compilation of H5f.c and H5ff.f90 creates the same H5F.o and H5FF.o
file names and linking stage fails.
Solution:
Rename the files to H5_f.c and H5_ff.f90
Platforms tested:
Linux (eirene) and Windows98
Diffstat (limited to 'fortran/src/H5_ff.f90')
-rw-r--r-- | fortran/src/H5_ff.f90 | 161 |
1 files changed, 161 insertions, 0 deletions
diff --git a/fortran/src/H5_ff.f90 b/fortran/src/H5_ff.f90 new file mode 100644 index 0000000..642bf40 --- /dev/null +++ b/fortran/src/H5_ff.f90 @@ -0,0 +1,161 @@ + +!---------------------------------------------------------------------- +! Name: h5open_f +! +! Purpose: Initializes the HDF5 library and Fortran90 interface. +! +! Inputs: +! Outputs: +! error: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: Elena Pourmal +! August 12, 1999 +! +! Modifications: Explicit Fortran interfaces were added for +! called C functions (it is needed for Windows +! port). February 28, 2001 +! +! Comment: +!---------------------------------------------------------------------- + SUBROUTINE h5open_f(error) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5open_f +!DEC$endif +! + 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 + +! +! MS FORTRAN needs explicit interfaces for C functions called here. +! + INTERFACE + INTEGER FUNCTION h5open_c() + !MS$ATTRIBUTES C,reference,alias:'_H5OPEN_C'::h5open_c + END FUNCTION h5open_c + END INTERFACE + INTERFACE + INTEGER FUNCTION h5init_types_c(p_types, f_types, i_types) + USE H5GLOBAL + INTEGER(HID_T), DIMENSION(PREDEF_TYPES_LEN) :: p_types + INTEGER(HID_T), DIMENSION(FLOATING_TYPES_LEN) :: f_types + INTEGER(HID_T), DIMENSION(INTEGER_TYPES_LEN) :: i_types + !MS$ATTRIBUTES C,reference,alias:'_H5INIT_TYPES_C'::h5init_types_c + END FUNCTION h5init_types_c + END INTERFACE + INTERFACE + INTEGER FUNCTION h5init_flags_c(i_H5D_flags, & + i_H5E_flags, & + i_H5F_flags, & + i_H5FD_flags, & + i_H5G_flags, & + i_H5I_flags, & + i_H5P_flags, & + i_H5R_flags, & + i_H5S_flags, & + i_H5T_flags ) + USE H5GLOBAL + INTEGER i_H5F_flags(H5F_FLAGS_LEN) + INTEGER i_H5G_flags(H5G_FLAGS_LEN) + INTEGER i_H5D_flags(H5D_FLAGS_LEN) + INTEGER i_H5FD_flags(H5FD_FLAGS_LEN) + INTEGER i_H5E_flags(H5E_FLAGS_LEN) + INTEGER i_H5I_flags(H5I_FLAGS_LEN) + INTEGER i_H5P_flags(H5P_FLAGS_LEN) + INTEGER i_H5R_flags(H5R_FLAGS_LEN) + INTEGER i_H5S_flags(H5S_FLAGS_LEN) + INTEGER i_H5T_flags(H5T_FLAGS_LEN) + + !MS$ATTRIBUTES C,reference,alias:'_H5INIT_FLAGS_C'::h5init_flags_c + END FUNCTION h5init_flags_c + END INTERFACE + error_0 = h5open_c() + error_1 = h5init_types_c(predef_types, floating_types, integer_types) + error_2 = 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 + +!---------------------------------------------------------------------- +! Name: h5close_f +! +! Purpose: Closes the HDF5 library and Fortran90 interface. +! +! Inputs: +! Outputs: +! error: - error code +! Success: 0 +! Failure: -1 +! Optional parameters: +! NONE +! +! Programmer: Elena Pourmal +! August 12, 1999 +! +! Modifications: Explicit Fortran interfaces were added for +! called C functions (it is needed for Windows +! port). February 28, 2001 +! +! Comment: +!---------------------------------------------------------------------- + + SUBROUTINE h5close_f(error) +! +!This definition is needed for Windows DLLs +!DEC$if defined(BUILD_HDF5_DLL) +!DEC$attributes dllexport :: h5close_f +!DEC$endif +! + USE H5GLOBAL + + IMPLICIT NONE + INTEGER :: error_1, error_2 + INTEGER, INTENT(OUT) :: error +! INTEGER, EXTERNAL :: h5close_types_c, h5close_c + INTERFACE + INTEGER FUNCTION h5close_c() + !MS$ATTRIBUTES C,reference,alias:'_H5CLOSE_C'::h5close_c + END FUNCTION h5close_c + END INTERFACE + INTERFACE + INTEGER FUNCTION h5close_types_c(p_types, P_TYPES_LEN, & + f_types, F_TYPES_LEN, & + i_types, I_TYPES_LEN ) + USE H5GLOBAL + INTEGER P_TYPES_LEN + INTEGER F_TYPES_LEN + INTEGER I_TYPES_LEN + INTEGER(HID_T), DIMENSION(P_TYPES_LEN) :: p_types + INTEGER(HID_T), DIMENSION(F_TYPES_LEN) :: f_types + INTEGER(HID_T), DIMENSION(I_TYPES_LEN) :: i_types + !MS$ATTRIBUTES C,reference,alias:'_H5CLOSE_TYPES_C'::h5close_types_c + END FUNCTION h5close_types_c + END INTERFACE + 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 + |