summaryrefslogtreecommitdiffstats
path: root/fortran/examples/h5_cmprss.f90
diff options
context:
space:
mode:
authorLarry Knox <lrknox@hdfgroup.org>2021-07-06 18:21:42 (GMT)
committerLarry Knox <lrknox@hdfgroup.org>2021-07-06 18:21:42 (GMT)
commit820695a78e3a277daea1bdcbb8ad54b8ee6650a5 (patch)
treefe7545305c0a77db3b9671e5a82fdffc4b2cc82e /fortran/examples/h5_cmprss.f90
parent9f13ecfa2e93840d1cc45dbf0bfcf8b955814931 (diff)
parent18bbd3f0a7f14adeebf8f342ed242ff191f9b7c5 (diff)
downloadhdf5-hdf5-1_12_1.zip
hdf5-hdf5-1_12_1.tar.gz
hdf5-hdf5-1_12_1.tar.bz2
Merge remote-tracking branch 'origin/hdf5_1_12_1' into 1.12/master forhdf5-1_12_1
HDF5 1.12.1 release.
Diffstat (limited to 'fortran/examples/h5_cmprss.f90')
-rw-r--r--fortran/examples/h5_cmprss.f9028
1 files changed, 14 insertions, 14 deletions
diff --git a/fortran/examples/h5_cmprss.f90 b/fortran/examples/h5_cmprss.f90
index 61dd7b0..61efc30 100644
--- a/fortran/examples/h5_cmprss.f90
+++ b/fortran/examples/h5_cmprss.f90
@@ -6,21 +6,21 @@
! This file is part of HDF5. The full HDF5 copyright notice, including *
! terms governing use, modification, and redistribution, is contained in *
! the COPYING file, which can be found at the root of the source code *
-! distribution tree, or in https://support.hdfgroup.org/ftp/HDF5/releases. *
+! distribution tree, or in https://www.hdfgroup.org/licenses. *
! If you do not have access to either file, you may request a copy from *
! help@hdfgroup.org. *
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
-!
+!
! This example illustrates how to create a compressed dataset.
! It is used in the HDF5 Tutorial.
-!
+!
PROGRAM h5_cmprss
- USE HDF5 ! This module contains all necessary modules
+ USE HDF5 ! This module contains all necessary modules
IMPLICIT NONE
!
- ! The dataset is stored in file "h5_cmprss.h5"
+ ! The dataset is stored in file "h5_cmprss.h5"
!
CHARACTER(LEN=12), PARAMETER :: filename = "h5_cmprss.h5"
INTEGER, PARAMETER :: rank = 2 ! Rank of the data set
@@ -33,7 +33,7 @@ PROGRAM h5_cmprss
INTEGER :: error
INTEGER(hsize_t), DIMENSION(1:rank) :: dims ! dimensions of data
INTEGER(hsize_t), DIMENSION(1:rank) :: cdims ! sizes of chunked data
-
+
INTEGER :: i,j, numfilt
INTEGER, DIMENSION(1:dim0,1:dim1) :: buf ! write buffer
INTEGER, DIMENSION(1:dim0,1:dim1) :: rbuf ! read buffer
@@ -63,15 +63,15 @@ PROGRAM h5_cmprss
CALL h5screate_simple_f(rank, dims, dataspace_id, error)
CALL h5pcreate_f(H5P_DATASET_CREATE_F, plist_id, error)
!
- ! Dataset must be chunked for compression
+ ! Dataset must be chunked for compression
cdims(1:2) = 20
CALL h5pset_chunk_f(plist_id, 2, cdims, error)
! Set ZLIB / DEFLATE Compression using compression level 6.
- ! To use SZIP Compression comment out these lines.
+ ! To use SZIP Compression comment out these lines.
CALL h5pset_deflate_f(plist_id, 6, error)
- ! Uncomment these lines to set SZIP Compression
+ ! Uncomment these lines to set SZIP Compression
!szip_options_mask = H5_SZIP_NN_OM_F
!szip_pixels_per_block = 16
!CALL H5Pset_szip_f(plist_id, szip_options_mask, szip_pixels_per_block, error)
@@ -86,7 +86,7 @@ PROGRAM h5_cmprss
ENDDO
ENDDO
- data_dims(1:2) = (/dim0,dim1/)
+ data_dims(1:2) = (/dim0,dim1/)
CALL h5dwrite_f(dataset_id, H5T_NATIVE_INTEGER, buf, data_dims, error)
! Close resources
@@ -99,12 +99,12 @@ PROGRAM h5_cmprss
CALL h5fopen_f(filename, H5F_ACC_RDONLY_F, file_id, error)
CALL h5dopen_f(file_id, "Compressed_Data", dataset_id, error)
- ! Retrieve filter information.
+ ! Retrieve filter information.
CALL h5dget_create_plist_f(dataset_id, plist_id, error)
-
+
CALL h5pget_nfilters_f(plist_id, numfilt, error)
WRITE(*,'(A, I0)') "Number of filters associated with dataset: ", numfilt
-
+
DO i = 1, numfilt
nelmts = 1
CALL h5pget_filter_f(plist_id, 0, flags, nelmts, cd_values, &
@@ -121,7 +121,7 @@ PROGRAM h5_cmprss
ENDDO
data_dims(1:2) = (/dim0,dim1/)
CALL h5dread_f(dataset_id, H5T_NATIVE_INTEGER, rbuf, data_dims, error)
-
+
CALL h5dclose_f(dataset_id, error)
CALL h5pclose_f(plist_id, error)
CALL h5fclose_f(file_id, error)