summaryrefslogtreecommitdiffstats
path: root/hl/fortran/src/H5IMff.f90
diff options
context:
space:
mode:
Diffstat (limited to 'hl/fortran/src/H5IMff.f90')
-rw-r--r--hl/fortran/src/H5IMff.f9012
1 files changed, 12 insertions, 0 deletions
diff --git a/hl/fortran/src/H5IMff.f90 b/hl/fortran/src/H5IMff.f90
index d78dc06..2a66597 100644
--- a/hl/fortran/src/H5IMff.f90
+++ b/hl/fortran/src/H5IMff.f90
@@ -67,6 +67,7 @@ subroutine h5immake_image_8bit_f(loc_id,&
interface
integer function h5immake_image_8bit_c(loc_id,namelen,dset_name,width,height,buf)
use h5global
+ IMPLICIT NONE
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5IMMAKE_IMAGE_8BIT_C'::h5immake_image_8bit_c
!DEC$ENDIF
@@ -127,6 +128,7 @@ subroutine h5imread_image_f(loc_id,&
interface
integer function h5imread_image_c(loc_id,namelen,dset_name,buf)
use h5global
+ IMPLICIT NONE
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5IMREAD_IMAGE_C'::h5imread_image_c
!DEC$ENDIF
@@ -191,6 +193,7 @@ subroutine h5immake_image_24bit_f(loc_id,&
interface
integer function h5immake_image_24bit_c(loc_id,namelen,dset_name,ilen,il,width,height,buf)
use h5global
+ IMPLICIT NONE
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5IMMAKE_IMAGE_24BIT_C'::h5immake_image_24bit_c
!DEC$ENDIF
@@ -265,6 +268,7 @@ subroutine h5imget_image_info_f(loc_id,&
interface
integer function h5imget_image_info_c(loc_id,namelen,dset_name,width,height,planes,npals,ilen,interlace)
use h5global
+ IMPLICIT NONE
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5IMGET_IMAGE_INFO_C'::h5imget_image_info_c
!DEC$ENDIF
@@ -326,6 +330,7 @@ integer function h5imis_image_f(loc_id,&
interface
integer function h5imis_image_c(loc_id,namelen,dset_name)
use h5global
+ IMPLICIT NONE
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5IMIS_IMAGE_C'::h5imis_image_c
!DEC$ENDIF
@@ -385,6 +390,7 @@ subroutine h5immake_palette_f(loc_id,&
interface
integer function h5immake_palette_c(loc_id,namelen,dset_name,pal_dims,buf)
use h5global
+ IMPLICIT NONE
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5IMMAKE_PALETTE_C'::h5immake_palette_c
!DEC$ENDIF
@@ -444,6 +450,7 @@ subroutine h5imlink_palette_f(loc_id,&
interface
integer function h5imlink_palette_c(loc_id,namelen,dset_name,ilen,pal_name)
use h5global
+ IMPLICIT NONE
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5IMLINK_PALETTE_C'::h5imlink_palette_c
!DEC$ENDIF
@@ -506,6 +513,7 @@ subroutine h5imunlink_palette_f(loc_id,&
interface
integer function h5imunlink_palette_c(loc_id,namelen,dset_name,ilen,pal_name)
use h5global
+ IMPLICIT NONE
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5IMUNLINK_PALETTE_C'::h5imunlink_palette_c
!DEC$ENDIF
@@ -567,6 +575,7 @@ subroutine h5imget_npalettes_f(loc_id,&
interface
integer function h5imget_npalettes_c(loc_id,namelen,dset_name,npals)
use h5global
+ IMPLICIT NONE
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5IMGET_NPALETTES_C'::h5imget_npalettes_c
!DEC$ENDIF
@@ -627,6 +636,7 @@ subroutine h5imget_palette_info_f(loc_id,&
interface
integer function h5imget_palette_info_c(loc_id,namelen,dset_name,pal_number,dims)
use h5global
+ IMPLICIT NONE
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5IMGET_PALETTE_INFO_C'::h5imget_palette_info_c
!DEC$ENDIF
@@ -689,6 +699,7 @@ subroutine h5imget_palette_f(loc_id,&
interface
integer function h5imget_palette_c(loc_id,namelen,dset_name,pal_number,buf)
use h5global
+ IMPLICIT NONE
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5IMGET_PALETTE_C'::h5imget_palette_c
!DEC$ENDIF
@@ -744,6 +755,7 @@ integer function h5imis_palette_f(loc_id,&
interface
integer function h5imis_palette_c(loc_id,namelen,dset_name)
use h5global
+ IMPLICIT NONE
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5IMIS_PALETTE_C'::h5imis_palette_c
!DEC$ENDIF