1! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
2!   Copyright by The HDF Group.                                               *
3!   Copyright by the Board of Trustees of the University of Illinois.         *
4!   All rights reserved.                                                      *
5!                                                                             *
6!   This file is part of HDF5.  The full HDF5 copyright notice, including     *
7!   terms governing use, modification, and redistribution, is contained in    *
8!   the COPYING file, which can be found at the root of the source code       *
9!   distribution tree, or in https://support.hdfgroup.org/ftp/HDF5/releases.  *
10!   If you do not have access to either file, you may request a copy from     *
11!   help@hdfgroup.org.                                                        *
12! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
13!
14! This example extends an HDF5 dataset. It is used in the HDF5 Tutorial.
15
16PROGRAM H5_EXTEND
17
18  USE HDF5 ! This module contains all necessary modules
19
20  IMPLICIT NONE
21
22  !
23  !the dataset is stored in file "extend.h5"
24  !
25  CHARACTER(LEN=9), PARAMETER :: filename = "extend.h5"
26
27  !
28  !dataset rank is 2 and name is "ExtendibleArray"
29  !
30  CHARACTER(LEN=15), PARAMETER :: dsetname = "ExtendibleArray"
31  INTEGER :: RANK = 2
32
33  INTEGER(HID_T) :: file_id       ! File identifier
34  INTEGER(HID_T) :: dset_id       ! Dataset identifier
35  INTEGER(HID_T) :: dataspace     ! Dataspace identifier
36  INTEGER(HID_T) :: memspace      ! Memory dataspace identifier
37  INTEGER(HID_T) :: crp_list      ! Dataset creation property identifier
38
39  !
40  !dataset dimensions at creation time
41  !
42  INTEGER(HSIZE_T), DIMENSION(1:2) :: dims = (/3,3/)
43
44  !
45  !data dimensions
46  !
47  INTEGER(HSIZE_T), DIMENSION(1:2) :: dimsc = (/2,5/)
48  INTEGER(HSIZE_T), DIMENSION(1:2) :: dimsm = (/3,7/)
49
50  !
51  !Maximum dimensions
52  !
53  INTEGER(HSIZE_T), DIMENSION(1:2) :: maxdims
54
55  INTEGER(HSIZE_T), DIMENSION(1:2) :: offset
56  INTEGER(HSIZE_T), DIMENSION(1:2) :: count
57
58  !
59  ! Variables for reading and writing
60  !
61  INTEGER, DIMENSION(1:3,1:3)  :: data1
62  INTEGER, DIMENSION(1:21) :: data2 = &
63       (/2, 3, 4, 2, 3, 4, 2, 3, 4, 2, 3, 4, 2, 3, 4, 2, 3, 4, 2, 3, 4/)
64  INTEGER(HSIZE_T), DIMENSION(1:2) :: data_dims
65
66  !
67  !Size of data in the file
68  !
69  INTEGER(HSIZE_T), DIMENSION(1:2) :: size
70
71  !
72  !general purpose integer
73  !
74  INTEGER(HSIZE_T) :: i, j
75
76  !
77  !flag to check operation success
78  !
79  INTEGER :: error
80
81  !
82  !Variables used in reading data back
83  !
84  INTEGER(HSIZE_T), DIMENSION(1:2) :: dimsr, maxdimsr
85  INTEGER :: rankr
86  INTEGER, DIMENSION(1:3,1:10)  :: rdata
87
88  !
89  !Initialize FORTRAN predifined datatypes
90  !
91  CALL h5open_f(error)
92
93  !
94  !Create a new file using default properties.
95  !
96  CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, error)
97
98  !
99  !Create the data space with unlimited dimensions.
100  !
101  maxdims = (/H5S_UNLIMITED_F, H5S_UNLIMITED_F/)
102
103  CALL h5screate_simple_f(RANK, dims, dataspace, error, maxdims)
104
105  !
106  !Modify dataset creation properties, i.e. enable chunking
107  !
108  CALL h5pcreate_f(H5P_DATASET_CREATE_F, crp_list, error)
109
110  CALL h5pset_chunk_f(crp_list, RANK, dimsc, error)
111
112  !
113  !Create a dataset with 3X3 dimensions using cparms creation propertie .
114  !
115  CALL h5dcreate_f(file_id, dsetname, H5T_NATIVE_INTEGER, dataspace, &
116       dset_id, error, crp_list )
117  CALL h5sclose_f(dataspace, error)
118
119  !
120  !Fill data array with 1's
121  !
122  DO i = 1, dims(1)
123     DO j = 1, dims(2)
124        data1(i,j) = 1
125     END DO
126  END DO
127
128  !
129  !Write data array to dataset
130  !
131  data_dims(1:2) = (/3,3/)
132  CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, data1, data_dims, error)
133
134  !
135  !Extend the dataset. Dataset becomes 10 x 3.
136  !
137  size(1:2)   = (/3,10/)
138  CALL h5dset_extent_f(dset_id, size, error)
139
140  offset(1:2) = (/0,3/)
141  count(1:2)  = (/3,7/)
142
143  CALL h5screate_simple_f (2, dimsm, memspace, error)
144
145  !
146  !Write to 3x7 extended part of dataset
147  !
148  CALL h5dget_space_f(dset_id, dataspace, error)
149  CALL h5sselect_hyperslab_f(dataspace, H5S_SELECT_SET_F, &
150       offset, count, error)
151
152  data_dims(1:2) = (/3,7/)
153  CALL H5dwrite_f(dset_id, H5T_NATIVE_INTEGER, data2, data_dims, error, &
154       memspace, dataspace)
155
156  !
157  !Close the objects that were opened.
158  !
159  CALL h5sclose_f(dataspace, error)
160  CALL h5pclose_f(crp_list, error)
161  CALL h5dclose_f(dset_id, error)
162  CALL h5fclose_f(file_id, error)
163
164  !
165  !read the data back
166  !
167  !Open the file.
168  !
169  CALL h5fopen_f (filename, H5F_ACC_RDONLY_F, file_id, error)
170
171  !
172  !Open the  dataset.
173  !
174  CALL h5dopen_f(file_id, dsetname, dset_id, error)
175
176  !
177  !Get dataset's dataspace handle.
178  !
179  CALL h5dget_space_f(dset_id, dataspace, error)
180
181  !
182  !Get dataspace's rank.
183  !
184  CALL h5sget_simple_extent_ndims_f(dataspace, rankr, error)
185
186  !
187  !Get dataspace's dimensions.
188  !
189  CALL h5sget_simple_extent_dims_f(dataspace, dimsr, maxdimsr, error)
190
191  !
192  !Get creation property list.
193  !
194  CALL h5dget_create_plist_f(dset_id, crp_list, error)
195
196  !
197  ! Fill read buffer with zeroes
198  !
199  rdata(1:dimsr(1),1:dimsr(2)) = 0
200
201  !
202  !create memory dataspace
203  !
204  CALL h5screate_simple_f(rankr, dimsr, memspace, error)
205
206  !
207  !Read data
208  !
209  data_dims(1:2) = (/3,10/)
210  CALL H5dread_f(dset_id, H5T_NATIVE_INTEGER, rdata, data_dims, &
211       error, memspace, dataspace)
212
213  WRITE(*,'(A)') "Dataset:"
214  DO i = 1, dimsr(1)
215     WRITE(*,'(100(I0,1X))') rdata(i,1:dimsr(2))
216  END DO
217
218  !
219  !Close the objects that were opened.
220  !
221  CALL h5sclose_f(dataspace, error)
222  CALL h5sclose_f(memspace, error)
223  CALL h5pclose_f(crp_list, error)
224  CALL h5dclose_f(dset_id, error)
225  CALL h5fclose_f(file_id, error)
226
227  !Close FORTRAN predefined datatypes
228  !
229  CALL h5close_f(error)
230
231END PROGRAM H5_EXTEND
232