summaryrefslogtreecommitdiffstats
path: root/hl
diff options
context:
space:
mode:
authorDana Robinson <derobins@hdfgroup.org>2020-05-26 20:07:43 (GMT)
committerDana Robinson <derobins@hdfgroup.org>2020-05-26 20:07:43 (GMT)
commit2477b6014582cd24a91d2b1daf0e5c451eda9b3e (patch)
tree1082eeda8c22c18bcd45cc11e18fb19281da817f /hl
parent7746c3a45a8c920e51ba88da7be14cc075be7f17 (diff)
downloadhdf5-2477b6014582cd24a91d2b1daf0e5c451eda9b3e.zip
hdf5-2477b6014582cd24a91d2b1daf0e5c451eda9b3e.tar.gz
hdf5-2477b6014582cd24a91d2b1daf0e5c451eda9b3e.tar.bz2
Removed trailing whitespace from source files.
Diffstat (limited to 'hl')
-rw-r--r--hl/fortran/src/H5DSff.F9068
-rw-r--r--hl/fortran/src/H5HL_buildiface.F9050
-rw-r--r--hl/fortran/src/H5IMff.F90102
-rw-r--r--hl/fortran/src/H5LTff.F9090
-rw-r--r--hl/fortran/src/H5TBff.F90128
-rw-r--r--hl/fortran/test/tstds.F9036
-rw-r--r--hl/fortran/test/tstlite.F9016
-rw-r--r--hl/fortran/test/tsttable.F9014
-rw-r--r--hl/src/H5LTanalyze.c150
-rw-r--r--hl/src/H5LTparse.c112
-rw-r--r--hl/src/H5LTparse.h10
11 files changed, 388 insertions, 388 deletions
diff --git a/hl/fortran/src/H5DSff.F90 b/hl/fortran/src/H5DSff.F90
index 5488bb2..6dcb450 100644
--- a/hl/fortran/src/H5DSff.F90
+++ b/hl/fortran/src/H5DSff.F90
@@ -26,7 +26,7 @@ CONTAINS
!-------------------------------------------------------------------------
! Function: H5DSset_scale_f
!
-! Purpose: Convert dataset dsid to a dimension scale, with optional name, dimname.
+! Purpose: Convert dataset dsid to a dimension scale, with optional name, dimname.
!
! Return: Success: 0, Failure: -1
!
@@ -93,28 +93,28 @@ CONTAINS
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: did ! the dataset
- INTEGER(hid_t), INTENT(in) :: dsid ! the scale to be attached
+ INTEGER(hid_t), INTENT(in) :: dsid ! the scale to be attached
INTEGER , INTENT(in) :: idx ! the dimension of did that dsid is associated with.
INTEGER :: errcode ! error code
INTEGER :: c_idx
-
+
INTERFACE
INTEGER FUNCTION H5DSattach_scale_c(did, dsid, idx) &
- BIND(C,NAME='h5dsattach_scale_c')
+ BIND(C,NAME='h5dsattach_scale_c')
IMPORT :: HID_T
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: did ! the dataset
- INTEGER(hid_t), INTENT(in) :: dsid ! the scale to be attached
+ INTEGER(hid_t), INTENT(in) :: dsid ! the scale to be attached
INTEGER , INTENT(in) :: idx ! the dimension of did that dsid is associated with.
END FUNCTION H5DSattach_scale_c
END INTERFACE
- c_idx = idx -1 ! account for C-dimensions starting at 0
-
+ c_idx = idx -1 ! account for C-dimensions starting at 0
+
errcode = H5DSattach_scale_c( did, dsid, c_idx)
-
+
END SUBROUTINE H5DSattach_scale_f
-
+
!-------------------------------------------------------------------------
! Function: H5DSdetach_scale_f
!
@@ -133,37 +133,37 @@ CONTAINS
!-------------------------------------------------------------------------
SUBROUTINE H5DSdetach_scale_f( did, dsid, idx, errcode)
-
+
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: did ! the dataset
- INTEGER(hid_t), INTENT(in) :: dsid ! the scale to be detached
+ INTEGER(hid_t), INTENT(in) :: dsid ! the scale to be detached
INTEGER , INTENT(in) :: idx ! the dimension of did to detach
INTEGER :: errcode ! error code
INTEGER :: c_idx
-
+
INTERFACE
INTEGER FUNCTION H5DSdetach_scale_c(did, dsid, idx) &
BIND(C,NAME='h5dsdetach_scale_c')
IMPORT :: HID_T
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: did ! the dataset
- INTEGER(hid_t), INTENT(in) :: dsid ! the scale to be detached
+ INTEGER(hid_t), INTENT(in) :: dsid ! the scale to be detached
INTEGER , INTENT(in) :: idx ! the dimension of did to detach
END FUNCTION H5DSdetach_scale_c
END INTERFACE
- c_idx = idx - 1 ! account for C-dimensions starting at 0
+ c_idx = idx - 1 ! account for C-dimensions starting at 0
errcode = H5DSdetach_scale_c( did, dsid, c_idx)
-
+
END SUBROUTINE H5DSdetach_scale_f
!-------------------------------------------------------------------------
! Function: H5DSis_attached_f
!
-! Purpose: Report if dimension scale dsid is currently attached to dimension idx of dataset did.
+! Purpose: Report if dimension scale dsid is currently attached to dimension idx of dataset did.
!
! Return: Success: 0, Failure: -1
!
@@ -178,32 +178,32 @@ CONTAINS
!-------------------------------------------------------------------------
SUBROUTINE H5DSis_attached_f( did, dsid, idx, is_attached, errcode)
-
+
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: did ! the dataset
INTEGER(hid_t), INTENT(in) :: dsid ! the scale to be attached
INTEGER , INTENT(in) :: idx ! the dimension of did that dsid is associated with
- LOGICAL , INTENT(out) :: is_attached ! logical: dimension scale dsid is currently attached to
+ LOGICAL , INTENT(out) :: is_attached ! logical: dimension scale dsid is currently attached to
! dimension idx of dataset did
INTEGER :: errcode ! error code
INTEGER :: c_is_attached
INTEGER :: c_idx
-
+
INTERFACE
INTEGER FUNCTION H5DSis_attached_c(did, dsid, idx, c_is_attached) &
BIND(C,NAME='h5dsis_attached_c')
IMPORT :: HID_T
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: did ! the dataset
- INTEGER(hid_t), INTENT(in) :: dsid ! the scale to be detached
+ INTEGER(hid_t), INTENT(in) :: dsid ! the scale to be detached
INTEGER , INTENT(in) :: idx ! the dimension of did to detach
- INTEGER , INTENT(out) :: c_is_attached ! dimension scale dsid is currently attached to
+ INTEGER , INTENT(out) :: c_is_attached ! dimension scale dsid is currently attached to
END FUNCTION H5DSis_attached_c
END INTERFACE
- c_idx = idx - 1 ! account for C-dimensions starting at 0
-
+ c_idx = idx - 1 ! account for C-dimensions starting at 0
+
errcode = H5DSis_attached_c(did, dsid, c_idx, c_is_attached)
is_attached = .FALSE. ! default
@@ -212,7 +212,7 @@ CONTAINS
ELSE IF(errcode.LT.0)THEN
errcode = -1
ENDIF
-
+
END SUBROUTINE H5DSis_attached_f
!
@@ -222,7 +222,7 @@ CONTAINS
!-------------------------------------------------------------------------
! Function: H5DSis_scale_f
!
-! Purpose: Determines whether dset is a Dimension Scale.
+! Purpose: Determines whether dset is a Dimension Scale.
!
! Return: Success: 0, Failure: -1
!
@@ -237,15 +237,15 @@ CONTAINS
!-------------------------------------------------------------------------
SUBROUTINE H5DSis_scale_f( did, is_scale, errcode)
-
+
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: did ! the data set to query
- LOGICAL , INTENT(out) :: is_scale ! logical:
+ LOGICAL , INTENT(out) :: is_scale ! logical:
! .TRUE. if did is a Dimension Scale
INTEGER :: errcode ! error code
INTEGER :: c_is_scale
-
+
INTERFACE
INTEGER FUNCTION H5DSis_scale_c(did,c_is_scale) &
BIND(C,NAME='h5dsis_scale_c')
@@ -255,7 +255,7 @@ CONTAINS
INTEGER, INTENT(out) :: c_is_scale
END FUNCTION H5DSis_scale_c
END INTERFACE
-
+
errcode = H5DSis_scale_c(did, c_is_scale)
is_scale = .FALSE. ! default
@@ -264,7 +264,7 @@ CONTAINS
ELSE IF(errcode.LT.0)THEN
errcode = -1
ENDIF
-
+
END SUBROUTINE H5DSis_scale_f
!-------------------------------------------------------------------------
@@ -319,7 +319,7 @@ CONTAINS
!-------------------------------------------------------------------------
! Function: H5DSget_label_f
!
-! Purpose: Read the label for dimension idx of did into buffer label.
+! Purpose: Read the label for dimension idx of did into buffer label.
!
! Return: Success: 0, Failure: -1
!
@@ -431,7 +431,7 @@ CONTAINS
INTEGER , INTENT(INOUT) :: num_scales ! the number of Dimension Scales associated with did
INTEGER :: errcode ! error code
INTEGER :: c_idx
-
+
INTERFACE
INTEGER FUNCTION H5DSget_num_scales_c(did, idx, num_scales) &
BIND(C,NAME='h5dsget_num_scales_c')
@@ -442,10 +442,10 @@ CONTAINS
INTEGER , INTENT(INOUT) :: num_scales ! the number of Dimension Scales associated with did
END FUNCTION H5DSget_num_scales_c
END INTERFACE
-
+
c_idx = idx - 1
errcode = H5DSget_num_scales_c(did, c_idx, num_scales)
-
+
END SUBROUTINE H5DSget_num_scales_f
END MODULE h5ds
diff --git a/hl/fortran/src/H5HL_buildiface.F90 b/hl/fortran/src/H5HL_buildiface.F90
index 1c5d9c8..7aac9a2 100644
--- a/hl/fortran/src/H5HL_buildiface.F90
+++ b/hl/fortran/src/H5HL_buildiface.F90
@@ -13,8 +13,8 @@
! depending on which of the KIND values are found.
!
! NOTES
-! This program uses the Fortran 2008 intrinsic function STORAGE_SIZE or SIZEOF
-! depending on availablity.It generates code that makes use of
+! This program uses the Fortran 2008 intrinsic function STORAGE_SIZE or SIZEOF
+! depending on availablity.It generates code that makes use of
! STORAGE_SIZE/SIZEOF in H5fortran_detect.f90. STORAGE_SIZE is standard
! compliant and should always be chosen over SIZEOF.
!
@@ -88,7 +88,7 @@ PROGRAM H5HL_buildiface
!
! Developer's notes:
!
-! Only interfaces with arrays of rank 7 and less are provided. Even-though the F2008
+! Only interfaces with arrays of rank 7 and less are provided. Even-though the F2008
! standard extended the maximum rank to 15, it was decided that they should use the
! new APIs to handle those use cases. Handling rank 7 and less is for backward compatibility
! with the Fortran 90/95 APIs codes which could never handle rank 8-15 array sizes.
@@ -266,7 +266,7 @@ PROGRAM H5HL_buildiface
WRITE(11,'(A)') ' INTEGER :: errcode '
WRITE(11,'(A)') ' TYPE(C_PTR) :: f_ptr'
WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
-
+
WRITE(11,'(A)') f_ptr_line(j)
WRITE(11,'(A)') ' namelen = LEN(dset_name)'
WRITE(11,'(A)') ' errcode = h5ltmake_dataset_c(loc_id,namelen,dset_name,rank,dims,type_id,f_ptr)'
@@ -297,7 +297,7 @@ PROGRAM H5HL_buildiface
WRITE(11,'(A)') ' INTEGER :: errcode '
WRITE(11,'(A)') ' TYPE(C_PTR) :: f_ptr'
WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
-
+
WRITE(11,'(A)') f_ptr_line(j)
WRITE(11,'(A)') ' namelen = LEN(dset_name)'
WRITE(11,'(A)') ' errcode = h5ltread_dataset_c(loc_id,namelen,dset_name,type_id,f_ptr)'
@@ -327,8 +327,8 @@ PROGRAM H5HL_buildiface
WRITE(11,'(A)') ' REAL(KIND='//TRIM(ADJUSTL(chr2))//'),INTENT(IN)'//TRIM(rank_dim_line(j))//', TARGET :: buf'
WRITE(11,'(A)') ' INTEGER :: errcode '
WRITE(11,'(A)') ' TYPE(C_PTR) :: f_ptr'
- WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
-
+ WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
+
WRITE(11,'(A)') f_ptr_line(j)
WRITE(11,'(A)') ' namelen = LEN(dset_name)'
WRITE(11,'(A)') ' errcode = h5ltmake_dataset_c(loc_id,namelen,dset_name,rank,dims,H5T_NATIVE_REAL,f_ptr)'
@@ -357,8 +357,8 @@ PROGRAM H5HL_buildiface
WRITE(11,'(A)') ' REAL(KIND='//TRIM(ADJUSTL(chr2))//'),INTENT(INOUT)'//TRIM(rank_dim_line(j))//', TARGET :: buf'
WRITE(11,'(A)') ' INTEGER :: errcode '
WRITE(11,'(A)') ' TYPE(C_PTR) :: f_ptr'
- WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
-
+ WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
+
WRITE(11,'(A)') f_ptr_line(j)
WRITE(11,'(A)') ' namelen = LEN(dset_name)'
WRITE(11,'(A)') ' errcode = h5ltread_dataset_c(loc_id,namelen,dset_name,H5T_NATIVE_REAL,f_ptr)'
@@ -387,8 +387,8 @@ PROGRAM H5HL_buildiface
WRITE(11,'(A)') ' REAL(KIND='//TRIM(ADJUSTL(chr2))//'),INTENT(IN)'//TRIM(rank_dim_line(j))//', TARGET :: buf'
WRITE(11,'(A)') ' INTEGER :: errcode '
WRITE(11,'(A)') ' TYPE(C_PTR) :: f_ptr'
- WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
-
+ WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
+
WRITE(11,'(A)') f_ptr_line(j)
WRITE(11,'(A)') ' namelen = LEN(dset_name)'
WRITE(11,'(A)') ' errcode = h5ltmake_dataset_c(loc_id,namelen,dset_name,rank,dims,H5T_NATIVE_DOUBLE,f_ptr)'
@@ -417,8 +417,8 @@ PROGRAM H5HL_buildiface
WRITE(11,'(A)') ' REAL(KIND='//TRIM(ADJUSTL(chr2))//'),INTENT(INOUT)'//TRIM(rank_dim_line(j))//', TARGET :: buf'
WRITE(11,'(A)') ' INTEGER :: errcode '
WRITE(11,'(A)') ' TYPE(C_PTR) :: f_ptr'
- WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
-
+ WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
+
WRITE(11,'(A)') f_ptr_line(j)
WRITE(11,'(A)') ' namelen = LEN(dset_name)'
WRITE(11,'(A)') ' errcode = h5ltread_dataset_c(loc_id,namelen,dset_name,H5T_NATIVE_DOUBLE,f_ptr)'
@@ -450,7 +450,7 @@ PROGRAM H5HL_buildiface
WRITE(11,'(A)') ' INTEGER :: errcode '
WRITE(11,'(A)') ' TYPE(C_PTR) :: f_ptr'
WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
-
+
WRITE(11,'(A)') f_ptr_line(j)
WRITE(11,'(A)') ' namelen = LEN(dset_name)'
WRITE(11,'(A)') ' errcode = h5ltmake_dataset_c(loc_id, namelen, dset_name, rank, dims, type_id, f_ptr)'
@@ -482,7 +482,7 @@ PROGRAM H5HL_buildiface
WRITE(11,'(A)') ' TYPE(C_PTR) :: f_ptr'
WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
WRITE(11,'(A)') ' INTEGER(hid_t) :: type_id'
-
+
WRITE(11,'(A)') f_ptr_line(j)
WRITE(11,'(A)') ' namelen = LEN(dset_name)'
WRITE(11,'(A)') ' type_id = h5kind_to_type(KIND('//f_ptr_line(j)(19:36)//'), H5_INTEGER_KIND)'
@@ -680,10 +680,10 @@ PROGRAM H5HL_buildiface
WRITE(11,'(A)') ' INTEGER(size_t), INTENT(in) :: type_size'
WRITE(11,'(A)') ' REAL(KIND='//TRIM(ADJUSTL(chr2))//'),INTENT(IN), DIMENSION(*), TARGET :: buf'
WRITE(11,'(A)') ' INTEGER :: errcode '
- WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
- WRITE(11,'(A)') ' INTEGER(size_t) :: namelen1'
+ WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
+ WRITE(11,'(A)') ' INTEGER(size_t) :: namelen1'
WRITE(11,'(A)') ' TYPE(C_PTR) :: f_ptr'
-
+
WRITE(11,'(A)') f_ptr_line(j)
WRITE(11,'(A)') ' namelen = LEN(dset_name)'
WRITE(11,'(A)') ' namelen1 = LEN(field_name)'
@@ -714,10 +714,10 @@ PROGRAM H5HL_buildiface
WRITE(11,'(A)') ' INTEGER(size_t), INTENT(in) :: type_size'
WRITE(11,'(A)') ' REAL(KIND='//TRIM(ADJUSTL(chr2))//'),INTENT(INOUT), DIMENSION(*), TARGET :: buf'
WRITE(11,'(A)') ' INTEGER :: errcode '
- WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
- WRITE(11,'(A)') ' INTEGER(size_t) :: namelen1'
+ WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
+ WRITE(11,'(A)') ' INTEGER(size_t) :: namelen1'
WRITE(11,'(A)') ' TYPE(C_PTR) :: f_ptr'
-
+
WRITE(11,'(A)') f_ptr_line(j)
WRITE(11,'(A)') ' namelen = LEN(dset_name)'
WRITE(11,'(A)') ' namelen1 = LEN(field_name)'
@@ -748,9 +748,9 @@ PROGRAM H5HL_buildiface
WRITE(11,'(A)') ' INTEGER(size_t), INTENT(in) :: type_size'
WRITE(11,'(A)') ' REAL(KIND='//TRIM(ADJUSTL(chr2))//'),INTENT(IN), DIMENSION(*), TARGET :: buf'
WRITE(11,'(A)') ' INTEGER :: errcode '
- WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
+ WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
WRITE(11,'(A)') ' TYPE(C_PTR) :: f_ptr'
-
+
WRITE(11,'(A)') f_ptr_line(j)
WRITE(11,'(A)') ' namelen = LEN(dset_name)'
WRITE(11,'(A)') &
@@ -782,7 +782,7 @@ PROGRAM H5HL_buildiface
WRITE(11,'(A)') ' INTEGER :: errcode '
WRITE(11,'(A)') ' INTEGER(size_t) :: namelen'
WRITE(11,'(A)') ' TYPE(C_PTR) :: f_ptr'
-
+
WRITE(11,'(A)') f_ptr_line(j)
WRITE(11,'(A)') ' namelen = LEN(dset_name)'
WRITE(11,'(A)') &
@@ -814,7 +814,7 @@ PROGRAM H5HL_buildiface
WRITE(11,'(A)') ' INTEGER(size_t) :: namelen1'
WRITE(11,'(A)') ' INTEGER :: errcode'
WRITE(11,'(A)') ' TYPE(C_PTR) :: f_ptr'
-
+
WRITE(11,'(A)') f_ptr_line(j)
WRITE(11,'(A)') ' namelen = LEN(dset_name)'
WRITE(11,'(A)') ' namelen1 = LEN(field_name)'
diff --git a/hl/fortran/src/H5IMff.F90 b/hl/fortran/src/H5IMff.F90
index ac4b794..ffa18aa 100644
--- a/hl/fortran/src/H5IMff.F90
+++ b/hl/fortran/src/H5IMff.F90
@@ -22,7 +22,7 @@
! **** | | | |\/| | ___/| | | | _ / | | / /\ \ | . ` | | | ****
! **** _| |_| | | | | | |__| | | \ \ | |/ ____ \| |\ | | | ****
! |_____|_| |_|_| \____/|_| \_\ |_/_/ \_\_| \_| |_|
-!
+!
! If you add a new function here then you MUST add the function name to the
! Windows dll file 'hdf5_hl_fortrandll.def.in' in the hl/fortran/src directory.
! This is needed for Windows based operating systems.
@@ -82,10 +82,10 @@ CONTAINS
INTEGER , INTENT(in), DIMENSION(*) :: buf ! buffer
END FUNCTION h5immake_image_8bit_c
END INTERFACE
-
+
namelen = LEN(dset_name)
errcode = h5immake_image_8bit_c(loc_id,namelen,dset_name,width,height,buf)
-
+
END SUBROUTINE h5immake_image_8bit_f
!-------------------------------------------------------------------------
@@ -110,7 +110,7 @@ CONTAINS
errcode )
IMPLICIT NONE
-
+
INTEGER(hid_t), INTENT(in) :: loc_id ! file or group identifier
CHARACTER(len=*), INTENT(in) :: dset_name ! name of the dataset
INTEGER, INTENT(inout), DIMENSION(*) :: buf ! buffer
@@ -129,10 +129,10 @@ CONTAINS
INTEGER, INTENT(inout), DIMENSION(*) :: buf ! buffer
END FUNCTION h5imread_image_c
END INTERFACE
-
+
namelen = LEN(dset_name)
errcode = h5imread_image_c(loc_id,namelen,dset_name,buf)
-
+
END SUBROUTINE h5imread_image_f
!-------------------------------------------------------------------------
@@ -159,7 +159,7 @@ CONTAINS
il,&
buf,&
errcode )
-
+
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: loc_id ! file or group identifier
@@ -171,7 +171,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER(size_t) :: ILEN ! name length
-
+
INTERFACE
INTEGER FUNCTION h5immake_image_24bit_c(loc_id,namelen,dset_name,ILEN,il,width,height,buf) &
BIND(C,NAME='h5immake_image_24bit_c')
@@ -186,14 +186,14 @@ CONTAINS
INTEGER, INTENT(in), DIMENSION(*) :: buf ! buffer
INTEGER(size_t) :: namelen ! length of name buffer
INTEGER(size_t) :: ILEN ! name length
-
+
END FUNCTION h5immake_image_24bit_c
END INTERFACE
-
+
namelen = LEN(dset_name)
ILEN = LEN(il)
errcode = h5immake_image_24bit_c(loc_id,namelen,dset_name,ILEN,il,width,height,buf)
-
+
END SUBROUTINE h5immake_image_24bit_f
!-------------------------------------------------------------------------
@@ -222,7 +222,7 @@ CONTAINS
interlace,&
npals,&
errcode )
-
+
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: loc_id ! file or group identifier
@@ -235,7 +235,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER(size_t) :: ILEN ! name length
-
+
INTERFACE
INTEGER FUNCTION h5imget_image_info_c(loc_id,namelen,dset_name,width,height,planes,npals,ILEN,interlace) &
BIND(C,NAME='h5imget_image_info_c')
@@ -253,11 +253,11 @@ CONTAINS
INTEGER(size_t) :: ILEN ! name length
END FUNCTION h5imget_image_info_c
END INTERFACE
-
+
namelen = LEN(dset_name)
ILEN = LEN(interlace)
errcode = h5imget_image_info_c(loc_id,namelen,dset_name,width,height,planes,npals,ILEN,interlace)
-
+
END SUBROUTINE h5imget_image_info_f
!-------------------------------------------------------------------------
@@ -286,7 +286,7 @@ CONTAINS
CHARACTER(len=*), INTENT(in) :: dset_name ! name of the dataset
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
-
+
INTERFACE
INTEGER FUNCTION h5imis_image_c(loc_id,namelen,dset_name) &
BIND(C,NAME='h5imis_image_c')
@@ -298,13 +298,13 @@ CONTAINS
CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(in) :: dset_name ! name of the dataset
END FUNCTION h5imis_image_c
END INTERFACE
-
+
namelen = LEN(dset_name)
errcode = h5imis_image_c(loc_id,namelen,dset_name)
h5imis_image_f = errcode
-
+
END FUNCTION h5imis_image_f
-
+
!-------------------------------------------------------------------------
! Function: h5immake_palette_f
@@ -328,16 +328,16 @@ CONTAINS
pal_dims,&
buf,&
errcode )
-
+
IMPLICIT NONE
-
+
INTEGER(hid_t), INTENT(in) :: loc_id ! file or group identifier
CHARACTER(len=*), INTENT(in) :: dset_name ! name of the dataset
INTEGER(hsize_t), INTENT(in), DIMENSION(*) :: pal_dims ! dimensions
INTEGER, INTENT(in), DIMENSION(*) :: buf ! buffer
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
-
+
INTERFACE
INTEGER FUNCTION h5immake_palette_c(loc_id,namelen,dset_name,pal_dims,buf) &
BIND(C,NAME='h5immake_palette_c')
@@ -351,12 +351,12 @@ CONTAINS
INTEGER, INTENT(in), DIMENSION(*) :: buf ! buffer
END FUNCTION h5immake_palette_c
END INTERFACE
-
+
namelen = LEN(dset_name)
errcode = h5immake_palette_c(loc_id,namelen,dset_name,pal_dims,buf)
-
+
END SUBROUTINE h5immake_palette_f
-
+
!-------------------------------------------------------------------------
! Function: h5imlink_palette_f
!
@@ -378,16 +378,16 @@ CONTAINS
dset_name,&
pal_name,&
errcode )
-
+
IMPLICIT NONE
-
+
INTEGER(hid_t), INTENT(in) :: loc_id ! file or group identifier
CHARACTER(len=*), INTENT(in) :: dset_name ! name of the dataset
CHARACTER(len=*), INTENT(in) :: pal_name ! palette name
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER(size_t) :: ILEN ! name length
-
+
INTERFACE
INTEGER FUNCTION h5imlink_palette_c(loc_id,namelen,dset_name,ILEN,pal_name) &
BIND(C,NAME='h5imlink_palette_c')
@@ -401,13 +401,13 @@ CONTAINS
INTEGER(size_t) :: ILEN ! name length
END FUNCTION h5imlink_palette_c
END INTERFACE
-
+
namelen = LEN(dset_name)
ILEN = LEN(pal_name)
errcode = h5imlink_palette_c(loc_id,namelen,dset_name,ILEN,pal_name)
-
+
END SUBROUTINE h5imlink_palette_f
-
+
!-------------------------------------------------------------------------
! Function: h5imunlink_palette_f
@@ -430,7 +430,7 @@ CONTAINS
dset_name,&
pal_name,&
errcode )
-
+
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: loc_id ! file or group identifier
@@ -439,7 +439,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER(size_t) :: ILEN ! name length
-
+
INTERFACE
INTEGER FUNCTION h5imunlink_palette_c(loc_id,namelen,dset_name,ILEN,pal_name) &
BIND(C,NAME='h5imunlink_palette_c')
@@ -453,13 +453,13 @@ CONTAINS
INTEGER(size_t) :: ILEN ! name length
END FUNCTION h5imunlink_palette_c
END INTERFACE
-
+
namelen = LEN(dset_name)
ILEN = LEN(pal_name)
errcode = h5imunlink_palette_c(loc_id,namelen,dset_name,ILEN,pal_name)
-
+
END SUBROUTINE h5imunlink_palette_f
-
+
!-------------------------------------------------------------------------
! Function: h5imget_npalettes_f
!
@@ -481,7 +481,7 @@ CONTAINS
dset_name,&
npals,&
errcode )
-
+
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: loc_id ! file or group identifier
@@ -489,7 +489,7 @@ CONTAINS
INTEGER(hsize_t), INTENT(inout) :: npals ! palettes
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
-
+
INTERFACE
INTEGER FUNCTION h5imget_npalettes_c(loc_id,namelen,dset_name,npals) &
BIND(C,NAME='h5imget_npalettes_c')
@@ -502,10 +502,10 @@ CONTAINS
INTEGER(size_t) :: namelen ! name length
END FUNCTION h5imget_npalettes_c
END INTERFACE
-
+
namelen = LEN(dset_name)
errcode = h5imget_npalettes_c(loc_id,namelen,dset_name,npals)
-
+
END SUBROUTINE h5imget_npalettes_f
@@ -531,7 +531,7 @@ CONTAINS
pal_number,&
dims,&
errcode )
-
+
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: loc_id ! file or group identifier
@@ -540,7 +540,7 @@ CONTAINS
INTEGER(hsize_t), DIMENSION(*), INTENT(inout) :: dims ! dimensions
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
-
+
INTERFACE
INTEGER FUNCTION h5imget_palette_info_c(loc_id,namelen,dset_name,pal_number,dims) &
BIND(C,NAME='h5imget_palette_info_c')
@@ -554,10 +554,10 @@ CONTAINS
INTEGER(size_t) :: namelen ! name length
END FUNCTION h5imget_palette_info_c
END INTERFACE
-
+
namelen = LEN(dset_name)
errcode = h5imget_palette_info_c(loc_id,namelen,dset_name,pal_number,dims)
-
+
END SUBROUTINE h5imget_palette_info_f
!-------------------------------------------------------------------------
@@ -582,7 +582,7 @@ CONTAINS
pal_number,&
buf,&
errcode )
-
+
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: loc_id ! file or group identifier
@@ -591,7 +591,7 @@ CONTAINS
INTEGER, INTENT(inout), DIMENSION(*) :: buf ! buffer
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
-
+
INTERFACE
INTEGER FUNCTION h5imget_palette_c(loc_id,namelen,dset_name,pal_number,buf) &
BIND(C,NAME='h5imget_palette_c')
@@ -605,10 +605,10 @@ CONTAINS
INTEGER, INTENT(inout), DIMENSION(*) :: buf ! buffer
END FUNCTION h5imget_palette_c
END INTERFACE
-
+
namelen = LEN(dset_name)
errcode = h5imget_palette_c(loc_id,namelen,dset_name,pal_number,buf)
-
+
END SUBROUTINE h5imget_palette_f
@@ -638,7 +638,7 @@ CONTAINS
CHARACTER(len=*), INTENT(in) :: dset_name ! name of the dataset
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
-
+
INTERFACE
INTEGER FUNCTION h5imis_palette_c(loc_id,namelen,dset_name) &
BIND(C,NAME='h5imis_palette_c')
@@ -650,11 +650,11 @@ CONTAINS
CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(in) :: dset_name ! name of the dataset
END FUNCTION h5imis_palette_c
END INTERFACE
-
+
namelen = LEN(dset_name)
errcode = h5imis_palette_c(loc_id,namelen,dset_name)
h5imis_palette_f = errcode
-
+
END FUNCTION h5imis_palette_f
END MODULE H5IM
diff --git a/hl/fortran/src/H5LTff.F90 b/hl/fortran/src/H5LTff.F90
index 80f6ac5..bc8734f 100644
--- a/hl/fortran/src/H5LTff.F90
+++ b/hl/fortran/src/H5LTff.F90
@@ -22,7 +22,7 @@
! **** | | | |\/| | ___/| | | | _ / | | / /\ \ | . ` | | | ****
! **** _| |_| | | | | | |__| | | \ \ | |/ ____ \| |\ | | | ****
! |_____|_| |_|_| \____/|_| \_\ |_/_/ \_\_| \_| |_|
-!
+!
! If you add a new function here then you MUST add the function name to the
! Windows dll file 'hdf5_hl_fortrandll.def.in' in the hl/fortran/src directory.
! This is needed for Windows based operating systems.
@@ -130,7 +130,7 @@ CONTAINS
!
! Comments:
!
- ! Modifications:
+ ! Modifications:
!
!-------------------------------------------------------------------------
@@ -321,7 +321,7 @@ CONTAINS
SUBROUTINE h5ltmake_dataset_f_int7(loc_id, dset_name, rank, dims, &
type_id, buf, errcode )
-
+
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: loc_id ! file or group identifier
CHARACTER(LEN=*), INTENT(in) :: dset_name ! name of the dataset
@@ -371,7 +371,7 @@ CONTAINS
INTEGER(hid_t), INTENT(in) :: type_id ! datatype identifier
TYPE(C_PTR) :: buf ! data buffer
INTEGER :: errcode ! error code
- INTEGER(size_t) :: namelen
+ INTEGER(size_t) :: namelen
namelen = LEN(dset_name)
errcode = h5ltread_dataset_c(loc_id,namelen,dset_name,type_id, buf)
@@ -409,7 +409,7 @@ CONTAINS
INTEGER(hsize_t), DIMENSION(*), INTENT(in) :: dims ! size of the buffer buf
INTEGER, INTENT(inout), DIMENSION(*), TARGET :: buf ! data buffer
INTEGER :: errcode ! error code
- INTEGER(size_t) :: namelen
+ INTEGER(size_t) :: namelen
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1))
@@ -451,7 +451,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(inout), &
- DIMENSION(dims(1),dims(2)), TARGET :: buf
+ DIMENSION(dims(1),dims(2)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1,1))
@@ -476,7 +476,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(inout), &
- DIMENSION(dims(1),dims(2),dims(3)), TARGET :: buf
+ DIMENSION(dims(1),dims(2),dims(3)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1,1,1))
@@ -497,7 +497,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(inout), &
- DIMENSION(dims(1),dims(2),dims(3),dims(4)), TARGET :: buf
+ DIMENSION(dims(1),dims(2),dims(3),dims(4)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1,1,1,1))
@@ -518,7 +518,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(inout), &
- DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5)), TARGET :: buf
+ DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1,1,1,1,1))
@@ -556,7 +556,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(inout), &
- DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6)), TARGET :: buf
+ DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1,1,1,1,1,1))
@@ -577,7 +577,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(inout), &
- DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6),dims(7)), TARGET :: buf
+ DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6),dims(7)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1,1,1,1,1,1,1))
@@ -621,7 +621,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
TYPE(C_PTR) :: f_ptr
-
+
f_ptr = C_LOC(buf(1))
namelen = LEN(dset_name)
@@ -644,7 +644,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(in), &
- DIMENSION(dims(1),dims(2)), TARGET :: buf
+ DIMENSION(dims(1),dims(2)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1,1))
@@ -669,7 +669,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(in), &
- DIMENSION(dims(1),dims(2),dims(3)), TARGET :: buf
+ DIMENSION(dims(1),dims(2),dims(3)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1,1,1))
@@ -690,7 +690,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(in), &
- DIMENSION(dims(1),dims(2),dims(3),dims(4)), TARGET :: buf
+ DIMENSION(dims(1),dims(2),dims(3),dims(4)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1,1,1,1))
@@ -711,7 +711,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(in), &
- DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5)), TARGET :: buf
+ DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1,1,1,1,1))
@@ -732,7 +732,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(in), &
- DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6)), TARGET :: buf
+ DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1,1,1,1,1,1))
@@ -753,7 +753,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(in), &
- DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6),dims(7)), TARGET :: buf
+ DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6),dims(7)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1,1,1,1,1,1,1))
@@ -793,7 +793,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(inout), &
- DIMENSION(dims(1)), TARGET :: buf
+ DIMENSION(dims(1)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1))
@@ -816,7 +816,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(inout), &
- DIMENSION(dims(1),dims(2)), TARGET :: buf
+ DIMENSION(dims(1),dims(2)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1,1))
@@ -839,7 +839,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(inout), &
- DIMENSION(dims(1),dims(2),dims(3)), TARGET :: buf
+ DIMENSION(dims(1),dims(2),dims(3)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1,1,1))
@@ -858,7 +858,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(inout), &
- DIMENSION(dims(1),dims(2),dims(3),dims(4)), TARGET :: buf
+ DIMENSION(dims(1),dims(2),dims(3),dims(4)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1,1,1,1))
@@ -877,7 +877,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(inout), &
- DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5)), TARGET :: buf
+ DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1,1,1,1,1))
@@ -896,7 +896,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(inout), &
- DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6)), TARGET :: buf
+ DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1,1,1,1,1,1))
@@ -915,7 +915,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER, INTENT(inout), &
- DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6),dims(7)), TARGET :: buf
+ DIMENSION(dims(1),dims(2),dims(3),dims(4),dims(5),dims(6),dims(7)), TARGET :: buf
TYPE(C_PTR) :: f_ptr
f_ptr = C_LOC(buf(1,1,1,1,1,1,1))
@@ -1059,14 +1059,14 @@ CONTAINS
TYPE(C_PTR) :: buf ! data buffer
CHARACTER(LEN=*), INTENT(in) :: buf_type ! valid data types are:
! CHARACTER, INTEGER or REAL
- ! NOTE: only the first character matters and is case insensitive
+ ! NOTE: only the first character matters and is case insensitive
INTEGER(size_t), INTENT(in) :: size ! size of attribute array
- INTEGER(size_t), INTENT(in) :: SizeOf_buf_type ! size of buf's data type
+ INTEGER(size_t), INTENT(in) :: SizeOf_buf_type ! size of buf's data type
INTEGER, INTENT(out) :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
- INTEGER(size_t) :: attrlen ! name length
- CHARACTER(KIND=C_CHAR) :: buf_type_uppercase
+ INTEGER(size_t) :: attrlen ! name length
+ CHARACTER(KIND=C_CHAR) :: buf_type_uppercase
namelen = LEN(dset_name)
attrlen = LEN(attr_name)
@@ -1117,7 +1117,7 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER, DIMENSION(*), TARGET :: buf ! data buffer
INTEGER(size_t) :: namelen ! name length
- INTEGER(size_t) :: attrlen ! name length
+ INTEGER(size_t) :: attrlen ! name length
TYPE(C_PTR) :: f_ptr
INTEGER(size_t) :: SizeOf_buf_type
@@ -1168,7 +1168,7 @@ CONTAINS
INTEGER :: errcode ! error code
REAL(KIND=C_FLOAT), INTENT(in), DIMENSION(*), TARGET :: buf ! data buffer
INTEGER(size_t) :: namelen ! name length
- INTEGER(size_t) :: attrlen ! name length
+ INTEGER(size_t) :: attrlen ! name length
TYPE(C_PTR) :: f_ptr
INTEGER(size_t) :: SizeOf_buf_type
@@ -1222,7 +1222,7 @@ CONTAINS
TYPE(C_PTR) :: f_ptr
INTEGER(size_t) :: SizeOf_buf_type
- f_ptr = C_LOC(buf(1))
+ f_ptr = C_LOC(buf(1))
#if H5_FORTRAN_HAVE_STORAGE_SIZE!=0
SizeOf_buf_type = STORAGE_SIZE(buf(1), c_size_t)/STORAGE_SIZE(c_char_'a',c_size_t)
@@ -1269,7 +1269,7 @@ CONTAINS
CHARACTER(LEN=*), DIMENSION(*), INTENT(in), TARGET :: buf ! data buffer
INTEGER(size_t) :: namelen ! name length
INTEGER(size_t) :: attrlen ! name length
- INTEGER(size_t) :: buflen ! data buffer length
+ INTEGER(size_t) :: buflen ! data buffer length
TYPE(C_PTR) :: f_ptr
INTEGER(size_t) :: SizeOf_buf_type
@@ -1321,7 +1321,7 @@ CONTAINS
! CHARACTER, INTEGER or REAL
! NOTE: only the first character matters and is case insensitive
INTEGER(size_t), INTENT(in) :: SizeOf_buf_type ! size of buf's data type
- INTEGER, INTENT(out) :: errcode ! error code
+ INTEGER, INTENT(out) :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
INTEGER(size_t) :: attrlen ! attr length
CHARACTER(KIND=C_CHAR) :: buf_type_uppercase
@@ -1373,11 +1373,11 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER, INTENT(inout), DIMENSION(*), TARGET :: buf! data buffer
INTEGER(size_t) :: namelen ! name length
- INTEGER(size_t) :: attrlen ! name length
+ INTEGER(size_t) :: attrlen ! name length
TYPE(C_PTR) :: f_ptr
INTEGER(size_t) :: SizeOf_buf
- f_ptr = C_LOC(buf(1))
+ f_ptr = C_LOC(buf(1))
#if H5_FORTRAN_HAVE_STORAGE_SIZE!=0
SizeOf_buf = STORAGE_SIZE(buf(1), c_size_t)/STORAGE_SIZE(c_char_'a',c_size_t)
@@ -1420,7 +1420,7 @@ CONTAINS
INTEGER :: errcode ! error code
REAL(KIND=C_FLOAT), INTENT(inout), DIMENSION(*), TARGET :: buf
INTEGER(size_t) :: namelen ! name length
- INTEGER(size_t) :: attrlen ! name length
+ INTEGER(size_t) :: attrlen ! name length
TYPE(C_PTR) :: f_ptr
INTEGER(size_t) :: SizeOf_buf
@@ -1470,7 +1470,7 @@ CONTAINS
TYPE(C_PTR) :: f_ptr
INTEGER(size_t) :: SizeOf_buf
- f_ptr = C_LOC(buf(1))
+ f_ptr = C_LOC(buf(1))
#if H5_FORTRAN_HAVE_STORAGE_SIZE!=0
SizeOf_buf = STORAGE_SIZE(buf(1), c_size_t)/STORAGE_SIZE(c_char_'a',c_size_t)
#else
@@ -1514,7 +1514,7 @@ CONTAINS
CHARACTER(LEN=*), INTENT(inout) :: buf
INTEGER(size_t) :: namelen ! name length
INTEGER(size_t) :: attrlen ! name length
- INTEGER(size_t) :: buf_size ! buf size
+ INTEGER(size_t) :: buf_size ! buf size
INTERFACE
INTEGER FUNCTION h5ltget_attribute_string_c(loc_id,namelen,dset_name,attrlen,attr_name,buf,buf_size) &
@@ -1812,7 +1812,7 @@ CONTAINS
!-------------------------------------------------------------------------
! Function: h5ltpath_valid_f
!
- ! Purpose: Validates a path
+ ! Purpose: Validates a path
!
! Return: Success: 0, Failure: -1
!
@@ -1831,8 +1831,8 @@ CONTAINS
IMPLICIT NONE
INTEGER(hid_t) , INTENT(IN) :: loc_id ! An identifier of an object in the file.
CHARACTER(LEN=*), INTENT(IN) :: path ! Path to the object to check, relative to loc_id.
- LOGICAL , INTENT(IN) :: check_object_valid ! Indicates whether to check if the final component
- ! of the path resolves to a valid object
+ LOGICAL , INTENT(IN) :: check_object_valid ! Indicates whether to check if the final component
+ ! of the path resolves to a valid object
LOGICAL , INTENT(OUT) :: path_valid ! Object status
INTEGER , INTENT(OUT) :: errcode ! Error code: 0 on success and -1 on failure
@@ -1846,7 +1846,7 @@ CONTAINS
IMPORT :: C_CHAR
IMPORT :: HID_T, SIZE_T, HSIZE_T
IMPLICIT NONE
- INTEGER(hid_t), INTENT(in) :: loc_id
+ INTEGER(hid_t), INTENT(in) :: loc_id
CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(in) :: path
INTEGER(size_t) :: pathlen
INTEGER :: check_object_valid_c
@@ -1856,7 +1856,7 @@ CONTAINS
! Initialize
path_valid = .FALSE.
errcode = 0
-
+
check_object_valid_c = 0
IF(check_object_valid) check_object_valid_c = 1
@@ -1868,7 +1868,7 @@ CONTAINS
ELSE IF(status.LT.0)THEN
errcode = -1
ENDIF
-
+
END SUBROUTINE h5ltpath_valid_f
END MODULE H5LT_CONST
diff --git a/hl/fortran/src/H5TBff.F90 b/hl/fortran/src/H5TBff.F90
index 40adf95..c3db01e 100644
--- a/hl/fortran/src/H5TBff.F90
+++ b/hl/fortran/src/H5TBff.F90
@@ -23,7 +23,7 @@
! **** | | | |\/| | ___/| | | | _ / | | / /\ \ | . ` | | | ****
! **** _| |_| | | | | | |__| | | \ \ | |/ ____ \| |\ | | | ****
! |_____|_| |_|_| \____/|_| \_\ |_/_/ \_\_| \_| |_|
-!
+!
! If you add a new function here then you MUST add the function name to the
! Windows dll file 'hdf5_hl_fortrandll.def.in' in the hl/fortran/src directory.
! This is needed for Windows based operating systems.
@@ -31,7 +31,7 @@
#include "H5config_f.inc"
MODULE h5tb_CONST
-
+
USE, INTRINSIC :: ISO_C_BINDING
USE h5fortran_types
USE hdf5
@@ -40,22 +40,22 @@ MODULE h5tb_CONST
MODULE PROCEDURE h5tbwrite_field_name_f_int
MODULE PROCEDURE h5tbwrite_field_name_f_string
END INTERFACE
-
+
INTERFACE h5tbread_field_name_f
MODULE PROCEDURE h5tbread_field_name_f_int
MODULE PROCEDURE h5tbread_field_name_f_string
END INTERFACE
-
+
INTERFACE h5tbwrite_field_index_f
MODULE PROCEDURE h5tbwrite_field_index_f_int
MODULE PROCEDURE h5tbwrite_field_index_f_string
END INTERFACE
-
+
INTERFACE h5tbread_field_index_f
MODULE PROCEDURE h5tbread_field_index_f_int
MODULE PROCEDURE h5tbread_field_index_f_string
END INTERFACE
-
+
INTERFACE h5tbinsert_field_f
MODULE PROCEDURE h5tbinsert_field_f_int
MODULE PROCEDURE h5tbinsert_field_f_string
@@ -162,7 +162,7 @@ MODULE h5tb_CONST
INTEGER(size_t) :: namelen1 ! name length length
END FUNCTION h5tbinsert_field_c
END INTERFACE
-
+
CONTAINS
!-------------------------------------------------------------------------
@@ -251,16 +251,16 @@ CONTAINS
INTEGER(size_t) :: max_char_size_field_names ! character len of field names
END FUNCTION h5tbmake_table_c
END INTERFACE
-
+
namelen = LEN(dset_name)
namelen1 = LEN(table_title)
-
+
! Find the size of each character string in the array
DO i = 1, nfields
char_len_field_names(i) = LEN_TRIM(field_names(i))
END DO
-
- max_char_size_field_names = LEN(field_names(1))
+
+ max_char_size_field_names = LEN(field_names(1))
errcode = h5tbmake_table_c(namelen1, table_title, loc_id, namelen, dset_name, nfields, nrecords,&
type_size, field_offset, field_types, chunk_size, compress, char_len_field_names, &
@@ -346,16 +346,16 @@ CONTAINS
TYPE(C_PTR), INTENT(in), VALUE :: data
END FUNCTION h5tbmake_table_ptr_c
END INTERFACE
-
+
namelen = LEN(dset_name)
namelen1 = LEN(table_title)
-
+
! Find the size of each character string in the array
DO i = 1, nfields
char_len_field_names(i) = LEN_TRIM(field_names(i))
END DO
-
- max_char_size_field_names = LEN(field_names(1))
+
+ max_char_size_field_names = LEN(field_names(1))
errcode = h5tbmake_table_ptr_c(namelen1, table_title, loc_id, namelen, dset_name, nfields, nrecords,&
type_size, field_offset, field_types, chunk_size, fill_data, compress, char_len_field_names, &
@@ -395,7 +395,7 @@ CONTAINS
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: loc_id ! file or group identifier
CHARACTER(LEN=1), INTENT(in) :: table_name ! name of the dataset
- INTEGER(hsize_t), INTENT(in) :: nfields
+ INTEGER(hsize_t), INTENT(in) :: nfields
INTEGER(size_t), INTENT(in) :: dst_size ! type size
INTEGER(size_t), DIMENSION(1:nfields), INTENT(in) :: dst_offset ! An array containing the sizes of the fields
INTEGER(size_t), DIMENSION(1:nfields), INTENT(in) :: dst_sizes ! An array containing the sizes of the fields
@@ -404,7 +404,7 @@ CONTAINS
END FUNCTION h5tbread_table_c
END INTERFACE
-
+
namelen = LEN(table_name)
errcode = h5tbread_table_c(loc_id,&
@@ -442,7 +442,7 @@ CONTAINS
type_size,&
buf,&
errcode )
-
+
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: loc_id ! file or group identifier
CHARACTER(LEN=*), INTENT(in) :: dset_name ! name of the dataset
@@ -455,14 +455,14 @@ CONTAINS
INTEGER(size_t) :: namelen ! name length
INTEGER(size_t) :: namelen1 ! name length
TYPE(C_PTR) :: f_ptr
-
+
f_ptr = C_LOC(buf(1))
namelen = LEN(dset_name)
namelen1 = LEN(field_name)
-
+
errcode = h5tbwrite_field_name_c(loc_id,namelen,dset_name,namelen1,field_name,&
start,nrecords,type_size,f_ptr)
-
+
END SUBROUTINE h5tbwrite_field_name_f_int
@@ -488,15 +488,15 @@ CONTAINS
INTEGER(size_t) :: namelen ! name length
INTEGER(size_t) :: namelen1
TYPE(C_PTR) :: f_ptr
-
+
f_ptr = C_LOC(buf(1)(1:1))
namelen = LEN(dset_name)
namelen1 = LEN(field_name)
-
+
errcode = h5tbwrite_field_name_c(loc_id,namelen,dset_name,namelen1,field_name,&
start,nrecords,type_size,f_ptr)
-
+
END SUBROUTINE h5tbwrite_field_name_f_string
@@ -537,15 +537,15 @@ CONTAINS
INTEGER(size_t) :: namelen ! name length
INTEGER(size_t) :: namelen1
TYPE(C_PTR) :: f_ptr
-
+
f_ptr = C_LOC(buf(1)) ! name length
namelen = LEN(dset_name)
namelen1 = LEN(field_name)
-
+
errcode = h5tbread_field_name_c(loc_id,namelen,dset_name,namelen1,field_name,&
start,nrecords,type_size,f_ptr)
-
+
END SUBROUTINE h5tbread_field_name_f_int
SUBROUTINE h5tbread_field_name_f_string(loc_id,&
@@ -569,15 +569,15 @@ CONTAINS
INTEGER(size_t) :: namelen ! name length
INTEGER(size_t) :: namelen1 ! name length
TYPE(C_PTR) :: f_ptr
-
- f_ptr = C_LOC(buf(1)(1:1))
+
+ f_ptr = C_LOC(buf(1)(1:1))
namelen = LEN(dset_name)
namelen1 = LEN(field_name)
-
+
errcode = h5tbread_field_name_c(loc_id,namelen,dset_name,namelen1,field_name,&
start,nrecords,type_size,f_ptr)
-
+
END SUBROUTINE h5tbread_field_name_f_string
@@ -595,7 +595,7 @@ CONTAINS
! Modifications:
!
!-------------------------------------------------------------------------
-
+
SUBROUTINE h5tbwrite_field_index_f_int(loc_id,&
dset_name,&
field_index,&
@@ -604,7 +604,7 @@ CONTAINS
type_size,&
buf,&
errcode )
-
+
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: loc_id ! file or group identifier
CHARACTER(LEN=*), INTENT(in) :: dset_name ! name of the dataset
@@ -616,14 +616,14 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
TYPE(C_PTR) :: f_ptr
-
+
f_ptr = C_LOC(buf(1))
namelen = LEN(dset_name)
-
+
errcode = h5tbwrite_field_index_c(loc_id,namelen,dset_name,field_index,&
start,nrecords,type_size,f_ptr)
-
+
END SUBROUTINE h5tbwrite_field_index_f_int
SUBROUTINE h5tbwrite_field_index_f_string(loc_id,&
@@ -634,7 +634,7 @@ CONTAINS
type_size,&
buf,&
errcode )
-
+
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: loc_id ! file or group identifier
CHARACTER(LEN=*), INTENT(in) :: dset_name ! name of the dataset
@@ -646,13 +646,13 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
TYPE(C_PTR) :: f_ptr
-
+
f_ptr = C_LOC(buf(1)(1:1))
namelen = LEN(dset_name)
-
+
errcode = h5tbwrite_field_index_c(loc_id,namelen,dset_name,field_index,&
start,nrecords,type_size,f_ptr)
-
+
END SUBROUTINE h5tbwrite_field_index_f_string
@@ -679,7 +679,7 @@ CONTAINS
type_size,&
buf,&
errcode )
-
+
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: loc_id ! file or group identifier
CHARACTER(LEN=*), INTENT(in) :: dset_name ! name of the dataset
@@ -691,13 +691,13 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
TYPE(C_PTR) :: f_ptr
-
+
f_ptr = C_LOC(buf(1))
namelen = LEN(dset_name)
-
+
errcode = h5tbread_field_index_c(loc_id,namelen,dset_name,field_index,&
start,nrecords,type_size,f_ptr)
-
+
END SUBROUTINE h5tbread_field_index_f_int
SUBROUTINE h5tbread_field_index_f_string(loc_id,&
@@ -720,13 +720,13 @@ CONTAINS
INTEGER :: errcode ! error code
INTEGER(size_t) :: namelen ! name length
TYPE(C_PTR) :: f_ptr
-
+
f_ptr = C_LOC(buf(1)(1:1))
namelen = LEN(dset_name)
-
+
errcode = h5tbread_field_index_c(loc_id,namelen,dset_name,field_index,&
start,nrecords,type_size,f_ptr)
-
+
END SUBROUTINE h5tbread_field_index_f_string
!-------------------------------------------------------------------------
@@ -762,12 +762,12 @@ CONTAINS
INTEGER(size_t) :: namelen1 ! name length
INTEGER :: errcode ! error code
TYPE(C_PTR) :: f_ptr
-
+
f_ptr = C_LOC(buf(1))
namelen = LEN(dset_name)
namelen1 = LEN(field_name)
-
+
errcode = h5tbinsert_field_c(loc_id,namelen,dset_name,namelen1,field_name,&
field_type,field_index,f_ptr)
@@ -791,15 +791,15 @@ CONTAINS
INTEGER(size_t) :: namelen1 ! name length
INTEGER :: errcode ! error code
TYPE(C_PTR) :: f_ptr
-
+
f_ptr = C_LOC(buf(1)(1:1))
-
+
namelen = LEN(dset_name)
namelen1 = LEN(field_name)
-
+
errcode = h5tbinsert_field_c(loc_id,namelen,dset_name,namelen1,field_name,&
field_type,field_index,f_ptr)
-
+
END SUBROUTINE h5tbinsert_field_f_string
!-------------------------------------------------------------------------
@@ -898,9 +898,9 @@ CONTAINS
namelen = LEN(dset_name)
errcode = h5tbget_table_info_c(loc_id,namelen,dset_name,nfields,nrecords)
-
+
END SUBROUTINE h5tbget_table_info_f
-
+
!-------------------------------------------------------------------------
! Function: h5tbget_field_info_f
@@ -915,9 +915,9 @@ CONTAINS
!
! Comments:
!
-! Modifications:
+! Modifications:
! Added optional parameter for returning the maximum character length
-! in the field name array. March 3, 2011
+! in the field name array. March 3, 2011
!
!-------------------------------------------------------------------------
@@ -929,7 +929,7 @@ CONTAINS
field_offsets,&
type_size,&
errcode, maxlen_out )
-
+
IMPLICIT NONE
INTEGER(hid_t), INTENT(in) :: loc_id ! file or group identifier
CHARACTER(LEN=*), INTENT(in) :: dset_name ! name of the dataset
@@ -945,7 +945,7 @@ CONTAINS
INTEGER(hsize_t) :: i ! general purpose integer
INTEGER(size_t) :: maxlen
INTEGER(size_t) :: c_maxlen_out
-
+
INTERFACE
INTEGER FUNCTION h5tbget_field_info_c(loc_id,namelen,dset_name,nfields,&
field_sizes,field_offsets,type_size,namelen2, maxlen, field_names, c_maxlen_out) &
@@ -963,7 +963,7 @@ CONTAINS
INTEGER(size_t) :: namelen ! name length
INTEGER(size_t) :: maxlen ! maxiumum length of input field names
INTEGER(size_t), DIMENSION(1:nfields) :: namelen2 ! name lengths
- INTEGER(size_t) :: c_maxlen_out ! maximum character length of a field array element
+ INTEGER(size_t) :: c_maxlen_out ! maximum character length of a field array element
END FUNCTION h5tbget_field_info_c
END INTERFACE
@@ -973,14 +973,14 @@ CONTAINS
END DO
maxlen = LEN(field_names(1))
c_maxlen_out = 0
-
+
errcode = h5tbget_field_info_c(loc_id, namelen,dset_name, nfields, &
field_sizes, field_offsets, type_size, namelen2, maxlen, field_names, c_maxlen_out)
-
+
IF(PRESENT(maxlen_out)) maxlen_out = c_maxlen_out
-
+
END SUBROUTINE h5tbget_field_info_f
-
+
END MODULE H5TB_CONST
diff --git a/hl/fortran/test/tstds.F90 b/hl/fortran/test/tstds.F90
index 387f524..e0335b6 100644
--- a/hl/fortran/test/tstds.F90
+++ b/hl/fortran/test/tstds.F90
@@ -46,7 +46,7 @@ SUBROUTINE write_test_status( test_result)
IF (test_result .EQ. 0) THEN
error_string = success
ENDIF
-
+
WRITE(*, fmt = '(T34, A)') error_string
END SUBROUTINE write_test_status
@@ -66,7 +66,7 @@ SUBROUTINE test_testds(err)
IMPLICIT NONE
- INTEGER, PARAMETER :: RANK = 2 ! rank of DATA dataset
+ INTEGER, PARAMETER :: RANK = 2 ! rank of DATA dataset
INTEGER, PARAMETER :: DIM_DATA = 12
INTEGER, PARAMETER :: DIM1_SIZE = 3
INTEGER, PARAMETER :: DIM2_SIZE = 4
@@ -82,13 +82,13 @@ SUBROUTINE test_testds(err)
INTEGER(hid_t) :: fid ! file ID
INTEGER(hid_t) :: did ! dataset ID
INTEGER(hid_t) :: dsid ! DS dataset ID
- INTEGER :: rankds = 1 ! rank of DS dataset
- INTEGER(hsize_t), DIMENSION(1:rank) :: dims = (/DIM2_SIZE,DIM1_SIZE/) ! size of DATA dataset
- INTEGER, DIMENSION(1:DIM_DATA) :: buf = (/1,2,3,4,5,6,7,8,9,10,11,12/) ! DATA of DATA dataset
- INTEGER(hsize_t), DIMENSION(1:1) :: s1_dim = (/DIM1_SIZE/) ! size of DS 1 dataset
- INTEGER(hsize_t), DIMENSION(1:1) :: s2_dim = (/DIM2_SIZE/) ! size of DS 2 dataset
- REAL, DIMENSION(1:DIM1_SIZE) :: s1_wbuf = (/10,20,30/) ! DATA of DS 1 dataset
- INTEGER, DIMENSION(1:DIM2_SIZE) :: s2_wbuf = (/10,20,50,100/) ! DATA of DS 2 dataset
+ INTEGER :: rankds = 1 ! rank of DS dataset
+ INTEGER(hsize_t), DIMENSION(1:rank) :: dims = (/DIM2_SIZE,DIM1_SIZE/) ! size of DATA dataset
+ INTEGER, DIMENSION(1:DIM_DATA) :: buf = (/1,2,3,4,5,6,7,8,9,10,11,12/) ! DATA of DATA dataset
+ INTEGER(hsize_t), DIMENSION(1:1) :: s1_dim = (/DIM1_SIZE/) ! size of DS 1 dataset
+ INTEGER(hsize_t), DIMENSION(1:1) :: s2_dim = (/DIM2_SIZE/) ! size of DS 2 dataset
+ REAL, DIMENSION(1:DIM1_SIZE) :: s1_wbuf = (/10,20,30/) ! DATA of DS 1 dataset
+ INTEGER, DIMENSION(1:DIM2_SIZE) :: s2_wbuf = (/10,20,50,100/) ! DATA of DS 2 dataset
INTEGER :: err
INTEGER :: num_scales
INTEGER(size_t) :: name_len
@@ -107,7 +107,7 @@ SUBROUTINE test_testds(err)
CALL H5Fcreate_f("tstds.h5",H5F_ACC_TRUNC_F, fid, err)
IF(err.LT.0) RETURN
- ! make a dataset
+ ! make a dataset
CALL H5LTmake_dataset_int_f(fid,DSET_NAME,rank,dims,buf, err)
IF(err.LT.0) RETURN
@@ -185,11 +185,11 @@ SUBROUTINE test_testds(err)
RETURN
ENDIF
CALL write_test_status(err)
-
+
!-------------------------------------------------------------------------
! set the DS_1_NAME dimension scale to DSET_NAME at dimension 0
!-------------------------------------------------------------------------
-
+
CALL test_begin(' Test Setting Dimension Scale ')
CALL H5DSset_scale_f(dsid, err, "Dimension Scale Set 1")
@@ -245,15 +245,15 @@ SUBROUTINE test_testds(err)
CALL write_test_status(err)
RETURN
ENDIF
-
+
! close DS id
CALL H5Dclose_f(dsid, err)
IF(err.LT.0) RETURN
-
+
!-------------------------------------------------------------------------
! attach the DS_2_NAME dimension scale to DSET_NAME
!-------------------------------------------------------------------------
-
+
! get the DS dataset id
CALL H5Dopen_f(fid, DS_2_NAME, dsid, err)
IF(err.LT.0) RETURN
@@ -301,7 +301,7 @@ SUBROUTINE test_testds(err)
ENDIF
! Test label where character length is to small
-
+
label_len = 5
label = ''
CALL H5DSget_label_f(did, DIM2, label(1:label_len), label_len, err)
@@ -341,7 +341,7 @@ SUBROUTINE test_testds(err)
CALL H5Dclose_f(dsid, err)
IF(err.LT.0) RETURN
- ! close file
+ ! close file
CALL H5Fclose_f(fid, err)
IF(err.LT.0) RETURN
@@ -352,7 +352,7 @@ END MODULE TSTDS_TESTS
PROGRAM test_ds
USE TSTDS_TESTS ! module for testing dataset routines
-
+
IMPLICIT NONE
INTEGER :: err
diff --git a/hl/fortran/test/tstlite.F90 b/hl/fortran/test/tstlite.F90
index 673807b..071bd3f 100644
--- a/hl/fortran/test/tstlite.F90
+++ b/hl/fortran/test/tstlite.F90
@@ -635,7 +635,7 @@ CONTAINS
DO k = 1, dims(3)
IF ( dset_data_i32(i,j,k) .NE. data_out_i32(i,j,k) ) THEN
PRINT *, 'read buffer differs from write buffer'
- PRINT *, dset_data_i32(i,j,k), ' and ', data_out_i32(i,j,k)
+ PRINT *, dset_data_i32(i,j,k), ' and ', data_out_i32(i,j,k)
STOP
ENDIF
END DO
@@ -660,7 +660,7 @@ CONTAINS
DO k = 1, dims(3)
IF ( dset_data_i32(i,j,k) .NE. data_out_i32(i,j,k) ) THEN
PRINT *, 'read buffer differs from write buffer'
- PRINT *, dset_data_i32(i,j,k), ' and ', data_out_i32(i,j,k)
+ PRINT *, dset_data_i32(i,j,k), ' and ', data_out_i32(i,j,k)
STOP
ENDIF
END DO
@@ -685,7 +685,7 @@ CONTAINS
DO k = 1, dims(3)
IF ( dset_data_i32(i,j,k) .NE. data_out_i32(i,j,k) ) THEN
PRINT *, 'read buffer differs from write buffer'
- PRINT *, dset_data_i32(i,j,k), ' and ', data_out_i32(i,j,k)
+ PRINT *, dset_data_i32(i,j,k), ' and ', data_out_i32(i,j,k)
STOP
ENDIF
END DO
@@ -1356,7 +1356,7 @@ CONTAINS
TYPE(hvl_t), DIMENSION(1:2), TARGET :: rdata ! Pointer to vlen structures
INTEGER(hsize_t), DIMENSION(1:1) :: dims_vl = (/2/)
INTEGER, DIMENSION(:), POINTER :: ptr_r
- INTEGER(HID_T) :: type_id
+ INTEGER(HID_T) :: type_id
!
! Initialize FORTRAN predefined datatypes.
@@ -1911,7 +1911,7 @@ CONTAINS
STOP
ENDIF
- !
+ !
! ** Test reading a string that was created with a C program **
!
@@ -1923,7 +1923,7 @@ CONTAINS
!!$ !
!!$ IF ( bufr_c .NE. buf_c ) THEN
!!$ PRINT *, 'read buffer differs from write buffer'
-!!$ PRINT *, bufr1, ' and ', buf_c
+!!$ PRINT *, bufr1, ' and ', buf_c
!!$ STOP
!!$ ENDIF
!!$ !
@@ -1936,9 +1936,9 @@ CONTAINS
!!$ !
!!$ IF ( buf_c(1:16) .NE. bufr_c_lg(1:16) .AND. bufr_c_lg(17:18) .NE. ' ' ) THEN
!!$ PRINT *, 'larger read buffer differs from write buffer'
-!!$ PRINT *, buf_c, ' and ', bufr_c_lg
+!!$ PRINT *, buf_c, ' and ', bufr_c_lg
!!$ STOP
-!!$ ENDIF
+!!$ ENDIF
!!$ CALL h5fclose_f(file_id1, errcode)
diff --git a/hl/fortran/test/tsttable.F90 b/hl/fortran/test/tsttable.F90
index 840d33d..55cdbf0 100644
--- a/hl/fortran/test/tsttable.F90
+++ b/hl/fortran/test/tsttable.F90
@@ -58,7 +58,7 @@ SUBROUTINE test_table1()
USE TSTTABLE ! module for testing table support routines
IMPLICIT NONE
-
+
CHARACTER(len=8), PARAMETER :: filename = "f1tab.h5" ! File name
CHARACTER(LEN=5), PARAMETER :: dsetname1 = "dset1" ! Dataset name
INTEGER(HID_T) :: file_id ! File identifier
@@ -106,7 +106,7 @@ SUBROUTINE test_table1()
SIZEOF_X = SIZEOF(bufd(1))
#endif
- ! If Fortran DOUBLE PRECISION and C DOUBLE sizeofs don't match then disable
+ ! If Fortran DOUBLE PRECISION and C DOUBLE sizeofs don't match then disable
! creating a DOUBLE RECISION field, and instead create a REAL field. This
! is needed to handle when DOUBLE PRECISION is promoted via a compiler flag.
Exclude_double = .FALSE.
@@ -511,7 +511,7 @@ SUBROUTINE test_table1()
IF ( maxlen .NE. 8 ) THEN
WRITE(*,'(/,5X,"H5TBGET_FIELD_INFO_F: INCORRECT MAXIMUM CHARACTER LENGTH OF THE FIELD NAMES")')
- WRITE(*,'(5X,"RETURNED VALUE = ", I0, ", CORRECT VALUE = ", I0)') maxlen, 8
+ WRITE(*,'(5X,"RETURNED VALUE = ", I0, ", CORRECT VALUE = ", I0)') maxlen, 8
STOP
ENDIF
@@ -552,7 +552,7 @@ SUBROUTINE test_table2()
USE TSTTABLE ! module for testing table support routines
IMPLICIT NONE
-
+
INTEGER, PARAMETER :: i8 = SELECTED_INT_KIND(9) !should map to INTEGER*4 on most modern processors
INTEGER, PARAMETER :: i16 = SELECTED_INT_KIND(9) ! (18) !should map to INTEGER*8 on most modern processors
INTEGER, PARAMETER :: sp = SELECTED_REAL_KIND(5) ! This should map to REAL*4 on most modern processors
@@ -605,7 +605,7 @@ SUBROUTINE test_table2()
test_txt = "Testing H5TBread_table_f and H5TBmake_table_f (F2003)"
CALL test_begin(test_txt)
-
+
! Define an array of Particles
p_data(1:nrecords) = (/ &
particle_t("zero ",0_i8,0_i16,0.0_sp,0.0_dp), &
@@ -641,7 +641,7 @@ SUBROUTINE test_table2()
/)
#endif
- dst_offset(1:nfields) = (/ &
+ dst_offset(1:nfields) = (/ &
H5OFFSETOF(C_LOC(dst_buf(1)), C_LOC(dst_buf(1)%name(1:1))), &
H5OFFSETOF(C_LOC(dst_buf(1)), C_LOC(dst_buf(1)%lati)), &
H5OFFSETOF(C_LOC(dst_buf(1)), C_LOC(dst_buf(1)%long)), &
@@ -693,7 +693,7 @@ SUBROUTINE test_table2()
f_ptr1 = C_LOC(p_data(1)%name(1:1))
f_ptr2 = C_NULL_PTR
-
+
CALL h5tbmake_table_f("Table Title",file_id, table_name, nfields, nrecords, &
dst_size, field_names, dst_offset, field_type, &
chunk_size, f_ptr2, compress, f_ptr1, errcode )
diff --git a/hl/src/H5LTanalyze.c b/hl/src/H5LTanalyze.c
index 1496fc1..5c25d26 100644
--- a/hl/src/H5LTanalyze.c
+++ b/hl/src/H5LTanalyze.c
@@ -1,25 +1,25 @@
-#if defined __GNUC__ && 402 <= __GNUC__ * 100 + __GNUC_MINOR__
-#pragma GCC diagnostic ignored "-Wconversion"
-#pragma GCC diagnostic ignored "-Wimplicit-function-declaration"
-#pragma GCC diagnostic ignored "-Wlarger-than="
-#pragma GCC diagnostic ignored "-Wmissing-prototypes"
-#pragma GCC diagnostic ignored "-Wnested-externs"
-#pragma GCC diagnostic ignored "-Wold-style-definition"
-#pragma GCC diagnostic ignored "-Wredundant-decls"
-#pragma GCC diagnostic ignored "-Wsign-compare"
-#pragma GCC diagnostic ignored "-Wsign-conversion"
-#pragma GCC diagnostic ignored "-Wstrict-overflow"
-#pragma GCC diagnostic ignored "-Wstrict-prototypes"
-#pragma GCC diagnostic ignored "-Wsuggest-attribute=pure"
-#pragma GCC diagnostic ignored "-Wswitch-default"
-#pragma GCC diagnostic ignored "-Wunused-function"
-#pragma GCC diagnostic ignored "-Wunused-macros"
-#pragma GCC diagnostic ignored "-Wunused-parameter"
-#elif defined __SUNPRO_CC
-#pragma disable_warn
-#elif defined _MSC_VER
-#pragma warning(push, 1)
-#endif
+#if defined __GNUC__ && 402 <= __GNUC__ * 100 + __GNUC_MINOR__
+#pragma GCC diagnostic ignored "-Wconversion"
+#pragma GCC diagnostic ignored "-Wimplicit-function-declaration"
+#pragma GCC diagnostic ignored "-Wlarger-than="
+#pragma GCC diagnostic ignored "-Wmissing-prototypes"
+#pragma GCC diagnostic ignored "-Wnested-externs"
+#pragma GCC diagnostic ignored "-Wold-style-definition"
+#pragma GCC diagnostic ignored "-Wredundant-decls"
+#pragma GCC diagnostic ignored "-Wsign-compare"
+#pragma GCC diagnostic ignored "-Wsign-conversion"
+#pragma GCC diagnostic ignored "-Wstrict-overflow"
+#pragma GCC diagnostic ignored "-Wstrict-prototypes"
+#pragma GCC diagnostic ignored "-Wsuggest-attribute=pure"
+#pragma GCC diagnostic ignored "-Wswitch-default"
+#pragma GCC diagnostic ignored "-Wunused-function"
+#pragma GCC diagnostic ignored "-Wunused-macros"
+#pragma GCC diagnostic ignored "-Wunused-parameter"
+#elif defined __SUNPRO_CC
+#pragma disable_warn
+#elif defined _MSC_VER
+#pragma warning(push, 1)
+#endif
#line 2 "hl/src/H5LTanalyze.c"
#line 4 "hl/src/H5LTanalyze.c"
@@ -75,7 +75,7 @@
#if defined (__STDC_VERSION__) && __STDC_VERSION__ >= 199901L
/* C99 says to define __STDC_LIMIT_MACROS before including stdint.h,
- * if you want the limit (max/min) macros for int types.
+ * if you want the limit (max/min) macros for int types.
*/
#ifndef __STDC_LIMIT_MACROS
#define __STDC_LIMIT_MACROS 1
@@ -92,7 +92,7 @@ typedef uint32_t flex_uint32_t;
typedef signed char flex_int8_t;
typedef short int flex_int16_t;
typedef int flex_int32_t;
-typedef unsigned char flex_uint8_t;
+typedef unsigned char flex_uint8_t;
typedef unsigned short int flex_uint16_t;
typedef unsigned int flex_uint32_t;
@@ -209,7 +209,7 @@ extern FILE *H5LTyyin, *H5LTyyout;
#define EOB_ACT_LAST_MATCH 2
#define YY_LESS_LINENO(n)
-
+
/* Return all but the first "n" matched characters back to the input stream. */
#define yyless(n) \
do \
@@ -266,7 +266,7 @@ struct yy_buffer_state
int yy_bs_lineno; /**< The line count. */
int yy_bs_column; /**< The column count. */
-
+
/* Whether to try to fill the input buffer when we reach the
* end of it.
*/
@@ -894,7 +894,7 @@ char *H5LTyytext;
#if defined __GNUC__ && 402 <= __GNUC__ * 100 + __GNUC_MINOR__
#pragma GCC diagnostic ignored "-Wsuggest-attribute=const"
#pragma GCC diagnostic ignored "-Wsuggest-attribute=malloc"
-#endif
+#endif
int my_yyinput(char *, int);
#undef YY_INPUT
@@ -997,7 +997,7 @@ extern int H5LTyywrap (void );
#endif
static void yyunput (int c,char *buf_ptr );
-
+
#ifndef yytext_ptr
static void yy_flex_strncpy (char *,yyconst char *,int );
#endif
@@ -1118,7 +1118,7 @@ YY_DECL
register yy_state_type yy_current_state;
register char *yy_cp, *yy_bp;
register int yy_act;
-
+
#line 83 "hl/src/H5LTanalyze.l"
@@ -1412,17 +1412,17 @@ YY_RULE_SETUP
case 40:
YY_RULE_SETUP
#line 128 "hl/src/H5LTanalyze.l"
-{return token(H5T_STR_NULLTERM_TOKEN);}
+{return token(H5T_STR_NULLTERM_TOKEN);}
YY_BREAK
case 41:
YY_RULE_SETUP
#line 129 "hl/src/H5LTanalyze.l"
-{return token(H5T_STR_NULLPAD_TOKEN);}
+{return token(H5T_STR_NULLPAD_TOKEN);}
YY_BREAK
case 42:
YY_RULE_SETUP
#line 130 "hl/src/H5LTanalyze.l"
-{return token(H5T_STR_SPACEPAD_TOKEN);}
+{return token(H5T_STR_SPACEPAD_TOKEN);}
YY_BREAK
case 43:
YY_RULE_SETUP
@@ -1487,12 +1487,12 @@ YY_RULE_SETUP
case 55:
YY_RULE_SETUP
#line 146 "hl/src/H5LTanalyze.l"
-{
- if( is_str_size || (is_enum && is_enum_memb) ||
+{
+ if( is_str_size || (is_enum && is_enum_memb) ||
is_opq_size || (asindex>-1 && arr_stack[asindex].is_dim) ||
(csindex>-1 && cmpd_stack[csindex].is_field) ) {
H5LTyylval.ival = atoi(H5LTyytext);
- return NUMBER;
+ return NUMBER;
} else
REJECT;
}
@@ -1502,7 +1502,7 @@ YY_RULE_SETUP
#line 156 "hl/src/H5LTanalyze.l"
{
/*if it's first quote, and is a compound field name or an enum symbol*/
- if((is_opq_tag || is_enum || (csindex>-1 && cmpd_stack[csindex].is_field))
+ if((is_opq_tag || is_enum || (csindex>-1 && cmpd_stack[csindex].is_field))
&& first_quote) {
first_quote = 0;
BEGIN TAG_STRING;
@@ -1822,7 +1822,7 @@ static int yy_get_next_buffer (void)
{
register yy_state_type yy_current_state;
register char *yy_cp;
-
+
yy_current_state = (yy_start);
(yy_state_ptr) = (yy_state_buf);
@@ -1852,7 +1852,7 @@ static int yy_get_next_buffer (void)
static yy_state_type yy_try_NUL_trans (yy_state_type yy_current_state )
{
register int yy_is_jam;
-
+
register YY_CHAR yy_c = 1;
while ( yy_chk[yy_base[yy_current_state] + yy_c] != yy_current_state )
{
@@ -1871,7 +1871,7 @@ static int yy_get_next_buffer (void)
static void yyunput (int c, register char * yy_bp )
{
register char *yy_cp;
-
+
yy_cp = (yy_c_buf_p);
/* undo effects of setting up H5LTyytext */
@@ -1914,7 +1914,7 @@ static int yy_get_next_buffer (void)
{
int c;
-
+
*(yy_c_buf_p) = (yy_hold_char);
if ( *(yy_c_buf_p) == YY_END_OF_BUFFER_CHAR )
@@ -1981,12 +1981,12 @@ static int yy_get_next_buffer (void)
/** Immediately switch to a different input stream.
* @param input_file A readable stream.
- *
+ *
* @note This function does not reset the start condition to @c INITIAL .
*/
void H5LTyyrestart (FILE * input_file )
{
-
+
if ( ! YY_CURRENT_BUFFER ){
H5LTyyensure_buffer_stack ();
YY_CURRENT_BUFFER_LVALUE =
@@ -1999,11 +1999,11 @@ static int yy_get_next_buffer (void)
/** Switch to a different input buffer.
* @param new_buffer The new input buffer.
- *
+ *
*/
void H5LTyy_switch_to_buffer (YY_BUFFER_STATE new_buffer )
{
-
+
/* TODO. We should be able to replace this entire function body
* with
* H5LTyypop_buffer_state();
@@ -2043,13 +2043,13 @@ static void H5LTyy_load_buffer_state (void)
/** Allocate and initialize an input buffer state.
* @param file A readable stream.
* @param size The character buffer size in bytes. When in doubt, use @c YY_BUF_SIZE.
- *
+ *
* @return the allocated buffer state.
*/
YY_BUFFER_STATE H5LTyy_create_buffer (FILE * file, int size )
{
YY_BUFFER_STATE b;
-
+
b = (YY_BUFFER_STATE) H5LTyyalloc(sizeof( struct yy_buffer_state ) );
if ( ! b )
YY_FATAL_ERROR( "out of dynamic memory in H5LTyy_create_buffer()" );
@@ -2072,11 +2072,11 @@ static void H5LTyy_load_buffer_state (void)
/** Destroy the buffer.
* @param b a buffer created with H5LTyy_create_buffer()
- *
+ *
*/
void H5LTyy_delete_buffer (YY_BUFFER_STATE b )
{
-
+
if ( ! b )
return;
@@ -2097,7 +2097,7 @@ static void H5LTyy_load_buffer_state (void)
{
int oerrno = errno;
-
+
H5LTyy_flush_buffer(b );
b->yy_input_file = file;
@@ -2113,13 +2113,13 @@ static void H5LTyy_load_buffer_state (void)
}
b->yy_is_interactive = file ? (isatty( fileno(file) ) > 0) : 0;
-
+
errno = oerrno;
}
/** Discard all buffered characters. On the next scan, YY_INPUT will be called.
* @param b the buffer state to be flushed, usually @c YY_CURRENT_BUFFER.
- *
+ *
*/
void H5LTyy_flush_buffer (YY_BUFFER_STATE b )
{
@@ -2148,7 +2148,7 @@ static void H5LTyy_load_buffer_state (void)
* the current state. This function will allocate the stack
* if necessary.
* @param new_buffer The new state.
- *
+ *
*/
void H5LTyypush_buffer_state (YY_BUFFER_STATE new_buffer )
{
@@ -2178,7 +2178,7 @@ void H5LTyypush_buffer_state (YY_BUFFER_STATE new_buffer )
/** Removes and deletes the top of the stack, if present.
* The next element becomes the new top.
- *
+ *
*/
void H5LTyypop_buffer_state (void)
{
@@ -2202,7 +2202,7 @@ void H5LTyypop_buffer_state (void)
static void H5LTyyensure_buffer_stack (void)
{
yy_size_t num_to_alloc;
-
+
if (!(yy_buffer_stack)) {
/* First allocation is just for 2 elements, since we don't know if this
@@ -2215,9 +2215,9 @@ static void H5LTyyensure_buffer_stack (void)
);
if ( ! (yy_buffer_stack) )
YY_FATAL_ERROR( "out of dynamic memory in H5LTyyensure_buffer_stack()" );
-
+
memset((yy_buffer_stack), 0, num_to_alloc * sizeof(struct yy_buffer_state*));
-
+
(yy_buffer_stack_max) = num_to_alloc;
(yy_buffer_stack_top) = 0;
return;
@@ -2245,13 +2245,13 @@ static void H5LTyyensure_buffer_stack (void)
/** Setup the input buffer state to scan directly from a user-specified character buffer.
* @param base the character buffer
* @param size the size in bytes of the character buffer
- *
- * @return the newly allocated buffer state object.
+ *
+ * @return the newly allocated buffer state object.
*/
YY_BUFFER_STATE H5LTyy_scan_buffer (char * base, yy_size_t size )
{
YY_BUFFER_STATE b;
-
+
if ( size < 2 ||
base[size-2] != YY_END_OF_BUFFER_CHAR ||
base[size-1] != YY_END_OF_BUFFER_CHAR )
@@ -2280,14 +2280,14 @@ YY_BUFFER_STATE H5LTyy_scan_buffer (char * base, yy_size_t size )
/** Setup the input buffer state to scan a string. The next call to H5LTyylex() will
* scan from a @e copy of @a str.
* @param yystr a NUL-terminated string to scan
- *
+ *
* @return the newly allocated buffer state object.
* @note If you want to scan bytes that may contain NUL values, then use
* H5LTyy_scan_bytes() instead.
*/
YY_BUFFER_STATE H5LTyy_scan_string (yyconst char * yystr )
{
-
+
return H5LTyy_scan_bytes(yystr,strlen(yystr) );
}
@@ -2295,7 +2295,7 @@ YY_BUFFER_STATE H5LTyy_scan_string (yyconst char * yystr )
* scan from a @e copy of @a bytes.
* @param yybytes the byte buffer to scan
* @param _yybytes_len the number of bytes in the buffer pointed to by @a bytes.
- *
+ *
* @return the newly allocated buffer state object.
*/
YY_BUFFER_STATE H5LTyy_scan_bytes (yyconst char * yybytes, yy_size_t _yybytes_len )
@@ -2304,7 +2304,7 @@ YY_BUFFER_STATE H5LTyy_scan_bytes (yyconst char * yybytes, yy_size_t _yybytes_
char *buf;
yy_size_t n;
int i;
-
+
/* Get memory for full buffer, including space for trailing EOB's. */
n = _yybytes_len + 2;
buf = (char *) H5LTyyalloc(n );
@@ -2358,16 +2358,16 @@ static void yy_fatal_error (yyconst char* msg )
/* Accessor methods (get/set functions) to struct members. */
/** Get the current line number.
- *
+ *
*/
int H5LTyyget_lineno (void)
{
-
+
return H5LTyylineno;
}
/** Get the input stream.
- *
+ *
*/
FILE *H5LTyyget_in (void)
{
@@ -2375,7 +2375,7 @@ FILE *H5LTyyget_in (void)
}
/** Get the output stream.
- *
+ *
*/
FILE *H5LTyyget_out (void)
{
@@ -2383,7 +2383,7 @@ FILE *H5LTyyget_out (void)
}
/** Get the length of the current token.
- *
+ *
*/
yy_size_t H5LTyyget_leng (void)
{
@@ -2391,7 +2391,7 @@ yy_size_t H5LTyyget_leng (void)
}
/** Get the current token.
- *
+ *
*/
char *H5LTyyget_text (void)
@@ -2401,18 +2401,18 @@ char *H5LTyyget_text (void)
/** Set the current line number.
* @param line_number
- *
+ *
*/
void H5LTyyset_lineno (int line_number )
{
-
+
H5LTyylineno = line_number;
}
/** Set the input stream. This does not discard the current
* input buffer.
* @param in_str A readable stream.
- *
+ *
* @see H5LTyy_switch_to_buffer
*/
void H5LTyyset_in (FILE * in_str )
@@ -2471,7 +2471,7 @@ static int yy_init_globals (void)
/* H5LTyylex_destroy is for both reentrant and non-reentrant scanners. */
int H5LTyylex_destroy (void)
{
-
+
/* Pop the buffer stack, destroying each element. */
while(YY_CURRENT_BUFFER){
H5LTyy_delete_buffer(YY_CURRENT_BUFFER );
@@ -2547,8 +2547,8 @@ void H5LTyyfree (void * ptr )
int my_yyinput(char *buf, int max_size)
{
int ret;
-
- memcpy(buf, myinput, input_len);
+
+ memcpy(buf, myinput, input_len);
ret = (int)input_len;
return ret;
}
diff --git a/hl/src/H5LTparse.c b/hl/src/H5LTparse.c
index 0275917..d8661a7 100644
--- a/hl/src/H5LTparse.c
+++ b/hl/src/H5LTparse.c
@@ -1,41 +1,41 @@
-#if defined __GNUC__ && 402 <= __GNUC__ * 100 + __GNUC_MINOR__
-#pragma GCC diagnostic ignored "-Wconversion"
-#pragma GCC diagnostic ignored "-Wimplicit-function-declaration"
-#pragma GCC diagnostic ignored "-Wlarger-than="
-#pragma GCC diagnostic ignored "-Wmissing-prototypes"
-#pragma GCC diagnostic ignored "-Wnested-externs"
-#pragma GCC diagnostic ignored "-Wold-style-definition"
-#pragma GCC diagnostic ignored "-Wredundant-decls"
-#pragma GCC diagnostic ignored "-Wsign-compare"
-#pragma GCC diagnostic ignored "-Wsign-conversion"
-#pragma GCC diagnostic ignored "-Wstrict-overflow"
-#pragma GCC diagnostic ignored "-Wstrict-prototypes"
-#pragma GCC diagnostic ignored "-Wsuggest-attribute=pure"
-#pragma GCC diagnostic ignored "-Wswitch-default"
-#pragma GCC diagnostic ignored "-Wunused-function"
-#pragma GCC diagnostic ignored "-Wunused-macros"
-#pragma GCC diagnostic ignored "-Wunused-parameter"
-#elif defined __SUNPRO_CC
-#pragma disable_warn
-#elif defined _MSC_VER
-#pragma warning(push, 1)
-#endif
+#if defined __GNUC__ && 402 <= __GNUC__ * 100 + __GNUC_MINOR__
+#pragma GCC diagnostic ignored "-Wconversion"
+#pragma GCC diagnostic ignored "-Wimplicit-function-declaration"
+#pragma GCC diagnostic ignored "-Wlarger-than="
+#pragma GCC diagnostic ignored "-Wmissing-prototypes"
+#pragma GCC diagnostic ignored "-Wnested-externs"
+#pragma GCC diagnostic ignored "-Wold-style-definition"
+#pragma GCC diagnostic ignored "-Wredundant-decls"
+#pragma GCC diagnostic ignored "-Wsign-compare"
+#pragma GCC diagnostic ignored "-Wsign-conversion"
+#pragma GCC diagnostic ignored "-Wstrict-overflow"
+#pragma GCC diagnostic ignored "-Wstrict-prototypes"
+#pragma GCC diagnostic ignored "-Wsuggest-attribute=pure"
+#pragma GCC diagnostic ignored "-Wswitch-default"
+#pragma GCC diagnostic ignored "-Wunused-function"
+#pragma GCC diagnostic ignored "-Wunused-macros"
+#pragma GCC diagnostic ignored "-Wunused-parameter"
+#elif defined __SUNPRO_CC
+#pragma disable_warn
+#elif defined _MSC_VER
+#pragma warning(push, 1)
+#endif
/* A Bison parser, made by GNU Bison 2.7. */
/* Bison implementation for Yacc-like parsers in C
-
+
Copyright (C) 1984, 1989-1990, 2000-2012 Free Software Foundation, Inc.
-
+
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation, either version 3 of the License, or
(at your option) any later version.
-
+
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
-
+
You should have received a copy of the GNU General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>. */
@@ -48,7 +48,7 @@
special exception, which will cause the skeleton and the resulting
Bison output files to be licensed under the GNU General Public
License without this special exception.
-
+
This special exception was added by the Free Software Foundation in
version 2.2 of Bison. */
@@ -127,7 +127,7 @@ struct arr_info {
};
/*stack for nested array type*/
struct arr_info arr_stack[STACK_SIZE];
-int asindex = -1; /*pointer to the top of array stack*/
+int asindex = -1; /*pointer to the top of array stack*/
hbool_t is_str_size = 0; /*flag to lexer for string size*/
hbool_t is_str_pad = 0; /*flag to lexer for string padding*/
@@ -135,7 +135,7 @@ H5T_str_t str_pad; /*variable for string padding*/
H5T_cset_t str_cset; /*variable for string character set*/
hbool_t is_variable = 0; /*variable for variable-length string*/
size_t str_size; /*variable for string size*/
-
+
hid_t enum_id; /*type ID*/
hbool_t is_enum = 0; /*flag to lexer for enum type*/
hbool_t is_enum_memb = 0; /*flag to lexer for enum member*/
@@ -1868,9 +1868,9 @@ yyreduce:
case 48:
/* Line 1792 of yacc.c */
#line 161 "hl/src/H5LTparse.y"
- { (yyval.hid) = cmpd_stack[csindex].id;
+ { (yyval.hid) = cmpd_stack[csindex].id;
cmpd_stack[csindex].id = 0;
- cmpd_stack[csindex].first_memb = 1;
+ cmpd_stack[csindex].first_memb = 1;
csindex--;
}
break;
@@ -1884,7 +1884,7 @@ yyreduce:
case 52:
/* Line 1792 of yacc.c */
#line 172 "hl/src/H5LTparse.y"
- {
+ {
size_t origin_size, new_size;
hid_t dtype_id = cmpd_stack[csindex].id;
@@ -1898,7 +1898,7 @@ yyreduce:
cmpd_stack[csindex].first_memb = 0;
} else {
origin_size = H5Tget_size(dtype_id);
-
+
if((yyvsp[(6) - (7)].ival) == 0) {
new_size = origin_size + H5Tget_size((yyvsp[(1) - (7)].hid));
H5Tset_size(dtype_id, new_size);
@@ -1915,7 +1915,7 @@ yyreduce:
}
cmpd_stack[csindex].is_field = 0;
H5Tclose((yyvsp[(1) - (7)].hid));
-
+
new_size = H5Tget_size(dtype_id);
}
break;
@@ -1951,7 +1951,7 @@ yyreduce:
case 58:
/* Line 1792 of yacc.c */
#line 223 "hl/src/H5LTparse.y"
- {
+ {
(yyval.hid) = H5Tarray_create2((yyvsp[(5) - (6)].hid), arr_stack[asindex].ndims, arr_stack[asindex].dims);
arr_stack[asindex].ndims = 0;
asindex--;
@@ -1969,9 +1969,9 @@ yyreduce:
/* Line 1792 of yacc.c */
#line 234 "hl/src/H5LTparse.y"
{ unsigned ndims = arr_stack[asindex].ndims;
- arr_stack[asindex].dims[ndims] = (hsize_t)yylval.ival;
+ arr_stack[asindex].dims[ndims] = (hsize_t)yylval.ival;
arr_stack[asindex].ndims++;
- arr_stack[asindex].is_dim = 0;
+ arr_stack[asindex].is_dim = 0;
}
break;
@@ -1990,10 +1990,10 @@ yyreduce:
case 67:
/* Line 1792 of yacc.c */
#line 251 "hl/src/H5LTparse.y"
- {
+ {
size_t size = (size_t)yylval.ival;
(yyval.hid) = H5Tcreate(H5T_OPAQUE, size);
- is_opq_size = 0;
+ is_opq_size = 0;
}
break;
@@ -2006,7 +2006,7 @@ yyreduce:
case 69:
/* Line 1792 of yacc.c */
#line 257 "hl/src/H5LTparse.y"
- {
+ {
H5Tset_tag((yyvsp[(7) - (13)].hid), yylval.sval);
free(yylval.sval);
yylval.sval = NULL;
@@ -2029,12 +2029,12 @@ yyreduce:
case 74:
/* Line 1792 of yacc.c */
#line 272 "hl/src/H5LTparse.y"
- {
+ {
if((yyvsp[(5) - (6)].ival) == H5T_VARIABLE_TOKEN)
is_variable = 1;
- else
+ else
str_size = yylval.ival;
- is_str_size = 0;
+ is_str_size = 0;
}
break;
@@ -2054,7 +2054,7 @@ yyreduce:
case 76:
/* Line 1792 of yacc.c */
#line 289 "hl/src/H5LTparse.y"
- {
+ {
if((yyvsp[(13) - (14)].ival) == H5T_CSET_ASCII_TOKEN)
str_cset = H5T_CSET_ASCII;
else if((yyvsp[(13) - (14)].ival) == H5T_CSET_UTF8_TOKEN)
@@ -2076,7 +2076,7 @@ yyreduce:
case 78:
/* Line 1792 of yacc.c */
#line 303 "hl/src/H5LTparse.y"
- {
+ {
hid_t str_id = (yyvsp[(19) - (20)].hid);
/*set string size*/
@@ -2085,12 +2085,12 @@ yyreduce:
is_variable = 0;
} else
H5Tset_size(str_id, str_size);
-
+
/*set string padding and character set*/
H5Tset_strpad(str_id, str_pad);
H5Tset_cset(str_id, str_cset);
- (yyval.hid) = str_id;
+ (yyval.hid) = str_id;
}
break;
@@ -2160,9 +2160,9 @@ yyreduce:
{
is_enum_memb = 1; /*indicate member of enum*/
#ifdef H5_HAVE_WIN32_API
- enum_memb_symbol = _strdup(yylval.sval);
+ enum_memb_symbol = _strdup(yylval.sval);
#else /* H5_HAVE_WIN32_API */
- enum_memb_symbol = strdup(yylval.sval);
+ enum_memb_symbol = strdup(yylval.sval);
#endif /* H5_HAVE_WIN32_API */
free(yylval.sval);
yylval.sval = NULL;
@@ -2182,32 +2182,32 @@ yyreduce:
hid_t native = H5Tget_native_type(super, H5T_DIR_ASCEND);
H5T_order_t super_order = H5Tget_order(super);
H5T_order_t native_order = H5Tget_order(native);
-
+
if(is_enum && is_enum_memb) { /*if it's an enum member*/
/*To handle machines of different endianness*/
if(H5Tequal(native, H5T_NATIVE_SCHAR) || H5Tequal(native, H5T_NATIVE_UCHAR)) {
if(super_order != native_order)
- H5Tconvert(native, super, 1, &char_val, NULL, H5P_DEFAULT);
+ H5Tconvert(native, super, 1, &char_val, NULL, H5P_DEFAULT);
H5Tenum_insert(enum_id, enum_memb_symbol, &char_val);
} else if(H5Tequal(native, H5T_NATIVE_SHORT) || H5Tequal(native, H5T_NATIVE_USHORT)) {
if(super_order != native_order)
- H5Tconvert(native, super, 1, &short_val, NULL, H5P_DEFAULT);
+ H5Tconvert(native, super, 1, &short_val, NULL, H5P_DEFAULT);
H5Tenum_insert(enum_id, enum_memb_symbol, &short_val);
} else if(H5Tequal(native, H5T_NATIVE_INT) || H5Tequal(native, H5T_NATIVE_UINT)) {
if(super_order != native_order)
- H5Tconvert(native, super, 1, &int_val, NULL, H5P_DEFAULT);
+ H5Tconvert(native, super, 1, &int_val, NULL, H5P_DEFAULT);
H5Tenum_insert(enum_id, enum_memb_symbol, &int_val);
} else if(H5Tequal(native, H5T_NATIVE_LONG) || H5Tequal(native, H5T_NATIVE_ULONG)) {
if(super_order != native_order)
- H5Tconvert(native, super, 1, &long_val, NULL, H5P_DEFAULT);
+ H5Tconvert(native, super, 1, &long_val, NULL, H5P_DEFAULT);
H5Tenum_insert(enum_id, enum_memb_symbol, &long_val);
} else if(H5Tequal(native, H5T_NATIVE_LLONG) || H5Tequal(native, H5T_NATIVE_ULLONG)) {
if(super_order != native_order)
- H5Tconvert(native, super, 1, &llong_val, NULL, H5P_DEFAULT);
+ H5Tconvert(native, super, 1, &llong_val, NULL, H5P_DEFAULT);
H5Tenum_insert(enum_id, enum_memb_symbol, &llong_val);
}
- is_enum_memb = 0;
+ is_enum_memb = 0;
if(enum_memb_symbol) free(enum_memb_symbol);
}
diff --git a/hl/src/H5LTparse.h b/hl/src/H5LTparse.h
index 30c5ea8..0ecd15d 100644
--- a/hl/src/H5LTparse.h
+++ b/hl/src/H5LTparse.h
@@ -1,19 +1,19 @@
/* A Bison parser, made by GNU Bison 2.7. */
/* Bison interface for Yacc-like parsers in C
-
+
Copyright (C) 1984, 1989-1990, 2000-2012 Free Software Foundation, Inc.
-
+
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation, either version 3 of the License, or
(at your option) any later version.
-
+
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
-
+
You should have received a copy of the GNU General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>. */
@@ -26,7 +26,7 @@
special exception, which will cause the skeleton and the resulting
Bison output files to be licensed under the GNU General Public
License without this special exception.
-
+
This special exception was added by the Free Software Foundation in
version 2.2 of Bison. */