diff options
Diffstat (limited to 'fortran/src/H5_ff.f90')
-rw-r--r-- | fortran/src/H5_ff.f90 | 136 |
1 files changed, 68 insertions, 68 deletions
diff --git a/fortran/src/H5_ff.f90 b/fortran/src/H5_ff.f90 index 89360a3..7dffd0a 100644 --- a/fortran/src/H5_ff.f90 +++ b/fortran/src/H5_ff.f90 @@ -1,4 +1,4 @@ -! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * +! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * ! Copyright by The HDF Group. * ! Copyright by the Board of Trustees of the University of Illinois. * ! All rights reserved. * @@ -11,32 +11,32 @@ ! is linked from the top-level documents page. It can also be found at * ! http://hdfgroup.org/HDF5/doc/Copyright.html. If you do not have * ! access to either file, you may request a copy from help@hdfgroup.org. * -! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * +! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * ! MODULE H5LIB CONTAINS !---------------------------------------------------------------------- -! Name: h5open_f +! Name: h5open_f ! -! Purpose: Initializes the HDF5 library and Fortran90 interface. +! Purpose: Initializes the HDF5 library and Fortran90 interface. ! -! Inputs: -! Outputs: -! error: - error code +! Inputs: +! Outputs: +! error: - error code ! Success: 0 -! Failure: -1 +! Failure: -1 ! Optional parameters: -! NONE +! NONE ! ! Programmer: Elena Pourmal -! August 12, 1999 +! August 12, 1999 ! -! Modifications: Explicit Fortran interfaces were added for +! Modifications: Explicit Fortran interfaces were added for ! called C functions (it is needed for Windows -! port). February 28, 2001 +! port). February 28, 2001 ! -! Comment: +! Comment: !---------------------------------------------------------------------- SUBROUTINE h5open_f(error) USE H5GLOBAL @@ -48,7 +48,7 @@ CONTAINS ! INTEGER, EXTERNAL :: h5init_flags_c ! INTEGER, EXTERNAL :: h5init1_flags_c ! INTEGER, EXTERNAL :: h5open_c - + ! ! MS FORTRAN needs explicit interfaces for C functions called here. ! @@ -64,7 +64,7 @@ CONTAINS 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 + INTEGER(HID_T), DIMENSION(INTEGER_TYPES_LEN) :: i_types !DEC$IF DEFINED(HDF5F90_WINDOWS) !DEC$ATTRIBUTES C,reference,decorate,alias:'H5INIT_TYPES_C'::h5init_types_c !DEC$ENDIF @@ -83,7 +83,7 @@ CONTAINS i_H5P_flags_int, & i_H5R_flags, & i_H5S_flags, & - i_H5T_flags, & + i_H5T_flags, & i_H5Z_flags, & i_H5generic_flags) USE H5GLOBAL @@ -138,26 +138,26 @@ CONTAINS END SUBROUTINE h5open_f !---------------------------------------------------------------------- -! Name: h5close_f +! Name: h5close_f ! -! Purpose: Closes the HDF5 library and Fortran90 interface. +! Purpose: Closes the HDF5 library and Fortran90 interface. ! -! Inputs: -! Outputs: -! error: - error code +! Inputs: +! Outputs: +! error: - error code ! Success: 0 -! Failure: -1 +! Failure: -1 ! Optional parameters: -! NONE +! NONE ! ! Programmer: Elena Pourmal -! August 12, 1999 +! August 12, 1999 ! -! Modifications: Explicit Fortran interfaces were added for +! Modifications: Explicit Fortran interfaces were added for ! called C functions (it is needed for Windows -! port). February 28, 2001 +! port). February 28, 2001 ! -! Comment: +! Comment: !---------------------------------------------------------------------- SUBROUTINE h5close_f(error) @@ -184,7 +184,7 @@ CONTAINS 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 + INTEGER(HID_T), DIMENSION(I_TYPES_LEN) :: i_types !DEC$IF DEFINED(HDF5F90_WINDOWS) !DEC$ATTRIBUTES C,reference,decorate,alias:'H5CLOSE_TYPES_C'::h5close_types_c !DEC$ENDIF @@ -197,32 +197,32 @@ CONTAINS error = error_1 + error_2 END SUBROUTINE h5close_f - + !---------------------------------------------------------------------- -! Name: h5get_libversion_f +! Name: h5get_libversion_f ! ! Purpose: Returns the HDF5 LIbrary release number ! -! Inputs: -! Outputs: +! Inputs: +! Outputs: ! majnum: - major version of the library ! minum: - minor version of the library ! relnum: - release version of the library -! error: - error code +! error: - error code ! Success: 0 -! Failure: -1 +! Failure: -1 ! Optional parameters: -! NONE +! NONE ! ! Programmer: Elena Pourmal ! September 24, 2002 ! -! Comment: +! Comment: !---------------------------------------------------------------------- SUBROUTINE h5get_libversion_f(majnum, minnum, relnum, error) USE H5GLOBAL - + IMPLICIT NONE INTEGER, INTENT(OUT) :: majnum, minnum, relnum, error INTERFACE @@ -233,36 +233,36 @@ CONTAINS INTEGER, INTENT(OUT) :: majnum, minnum, relnum END FUNCTION h5get_libversion_c END INTERFACE - + error = h5get_libversion_c(majnum, minnum, relnum) - + END SUBROUTINE h5get_libversion_f !---------------------------------------------------------------------- -! Name: h5check_version_f +! Name: h5check_version_f ! ! Purpose: Verifies that library versions are consistent. ! -! Inputs: +! Inputs: ! majnum: - major version of the library ! minum: - minor version of the library ! relnum: - release version of the library -! Outputs: -! error: - error code +! Outputs: +! error: - error code ! Success: 0 ! Failure: application aborts ! Optional parameters: -! NONE +! NONE ! ! Programmer: Elena Pourmal ! September 24, 2002 ! -! Comment: +! Comment: !---------------------------------------------------------------------- SUBROUTINE h5check_version_f(majnum, minnum, relnum, error) USE H5GLOBAL - + IMPLICIT NONE INTEGER, INTENT(IN) :: majnum, minnum, relnum INTEGER, INTENT(OUT) :: error @@ -274,34 +274,34 @@ CONTAINS INTEGER, INTENT(IN) :: majnum, minnum, relnum END FUNCTION h5check_version_c END INTERFACE - + error = h5check_version_c(majnum, minnum, relnum) - + END SUBROUTINE h5check_version_f !---------------------------------------------------------------------- -! Name: h5garbage_collect_f +! Name: h5garbage_collect_f ! ! Purpose: Garbage collects on all free-lists of all types. ! -! Inputs: -! Outputs: -! error: - error code +! Inputs: +! Outputs: +! error: - error code ! Success: 0 -! Failure: -1 +! Failure: -1 ! Optional parameters: -! NONE +! NONE ! ! Programmer: Elena Pourmal ! September 24, 2002 ! ! -! Comment: +! Comment: !---------------------------------------------------------------------- SUBROUTINE h5garbage_collect_f(error) USE H5GLOBAL - + IMPLICIT NONE INTEGER, INTENT(OUT) :: error INTERFACE @@ -311,34 +311,34 @@ CONTAINS !DEC$ENDIF END FUNCTION h5garbage_collect_c END INTERFACE - + error = h5garbage_collect_c() END SUBROUTINE h5garbage_collect_f !---------------------------------------------------------------------- -! Name: h5dont_atexit_f +! Name: h5dont_atexit_f ! -! Purpose: Instructs library not to install atexit cleanup routine. +! Purpose: Instructs library not to install atexit cleanup routine. ! -! Inputs: -! Outputs: -! error: - error code +! Inputs: +! Outputs: +! error: - error code ! Success: 0 -! Failure: -1 +! Failure: -1 ! Optional parameters: -! NONE +! NONE ! ! Programmer: Elena Pourmal ! September 24, 2002 ! ! -! Comment: +! Comment: !---------------------------------------------------------------------- SUBROUTINE h5dont_atexit_f(error) USE H5GLOBAL - + IMPLICIT NONE INTEGER, INTENT(OUT) :: error INTERFACE @@ -348,8 +348,8 @@ CONTAINS !DEC$ENDIF END FUNCTION h5dont_atexit_c END INTERFACE - + error = h5dont_atexit_c() - + END SUBROUTINE h5dont_atexit_f END MODULE H5LIB |