KronLinInv  0.3
Kronecker-product-based linear inversion
rdwrhdf5.f08
Go to the documentation of this file.
1 
2 !------------------------------------------------------------------------
3 !
4 ! Copyright 2018, Andrea Zunino
5 !
6 ! This file is part of KronLinInv.
7 !
8 ! KronLinInv is free software: you can redistribute it and/or modify
9 ! it under the terms of the GNU General Public License as published by
10 ! the Free Software Foundation, either version 3 of the License, or
11 ! (at your option) any later version.
12 !
13 ! KronLinInv is distributed in the hope that it will be useful,
14 ! but WITHOUT ANY WARRANTY; without even the implied warranty of
15 ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
16 ! GNU General Public License for more details.
17 !
18 ! You should have received a copy of the GNU General Public License
19 ! along with KronLinInv. If not, see <http://www.gnu.org/licenses/>.
20 !
21 !------------------------------------------------------------------------
22 
23 !-------------------------------------------
24 !
26 !
30 !
31 !-------------------------------------------
33 
34  ! HDF5:
35  ! When a C application reads data stored from a Fortran program,
36  ! the data will appear to be transposed due to the difference in
37  ! the C and Fortran storage orders. For example, if Fortran writes
38  ! a 4x6 two-dimensional dataset to the file, a C program will read
39  ! it as a 6x4 two-dimensional dataset into memory. The HDF5 C
40  ! utilities h5dump and h5ls will also display transposed data, if
41  ! data is written from a Fortran program.
42 
43  use realprec
44  use hdf5
45  implicit none
46 
47 
48  logical,private :: h5firsttimeread = .true.
49 
50 contains
51 
52  !!=============================================================
53 
54  subroutine writereal1darrh5(outfile,dsetname,arr)
55 
56  character(len=1024),intent(in) :: outfile
57  real(dp),intent(in) :: arr(:)
58  character(len=*),intent(in) :: dsetname
59 
60  ! filename length must be the same than in dummy variable
61  integer(hid_t) :: file_id ! file identifier
62  integer(hid_t) :: dset_id ! dataset identifier
63  integer :: error ! error flag
64  integer(hid_t) :: dspace_id
65  integer(hsize_t), dimension(1) :: data_dims1
66  integer :: rank
67 
68  !! copmpression stuff
69  logical :: avail
70  integer :: filter_info
71  integer :: filter_info_both
72  integer(hid_t) :: dcpl
73  integer :: chunkingfactor
74  integer(hsize_t), dimension(1) :: chunk1
75 
76 
77  chunkingfactor = 10
78 
79  !##############################
80  !# initialize hdf5 #
81  !##############################
82  ! initialize fortran interface.
83  call h5open_f(error)
84  !-------------------------------------------------------------
85  ! check if gzip compression is available and can be used for both
86  ! compression and decompression. normally we do not perform error
87  ! checking in these examples for the sake of clarity, but in this
88  ! case we will make an exception because this filter is an
89  ! optional part of the hdf5 library.
90  call h5zfilter_avail_f(h5z_filter_deflate_f, avail, error)
91  if (.not.avail) then
92  write(*,'("gzip filter not available.",/)')
93  stop
94  endif
95  call h5zget_filter_info_f(h5z_filter_deflate_f, filter_info, error)
96  filter_info_both=ior(h5z_filter_encode_enabled_f,h5z_filter_decode_enabled_f)
97  if (filter_info .ne. filter_info_both) then
98  write(*,'("gzip filter not available for encoding and decoding.",/)')
99  stop
100  endif
101 
102  !-------------------------------------------------------------
103  if (h5firsttimeread.eqv..true.) then
104  call h5fcreate_f(trim(adjustl(outfile)), h5f_acc_trunc_f,file_id,error)
105  h5firsttimeread=.false.
106  else
107  ! open an existing file using the default properties.
108  call h5fopen_f(trim(adjustl(outfile)), h5f_acc_rdwr_f, file_id, error)
109  end if
110 
111 
112  !##############################
113  !# write arr #
114  !##############################
115  rank=1
116  data_dims1=shape(arr)
117  chunk1 = data_dims1/chunkingfactor
118  call checkchunking(chunk1)
119  ! create dataspace. setting maximum size to null sets the maximum
120  ! size to be the current size.
121  call h5screate_simple_f (rank, data_dims1, dspace_id, error)
122  !-------------------------------------------------------------
123  ! create the dataset creation property list, add the gzip
124  ! compression filter and set the chunk size.
125  call h5pcreate_f(h5p_dataset_create_f, dcpl, error)
126  call h5pset_deflate_f(dcpl, 9, error)
127  call h5pset_chunk_f(dcpl, rank, chunk1, error)
128  !-------------------------------------------------------------
129  ! create the dataset with default properties.
130  call h5dcreate_f(file_id, dsetname, h5t_ieee_f64le, dspace_id, &
131  dset_id, error, dcpl)
132  !-------------------------------------------------------------
133  ! write the data to the dataset.
134  call h5dwrite_f(dset_id,h5t_ieee_f64le, arr, data_dims1, error)
135  !-------------------------------------------------------------
136  ! close and release resources.
137  call h5pclose_f(dcpl,error)
138  !-------------------------------------------------------------
139  call h5sclose_f(dspace_id, error)
140  ! close the dataset.
141  call h5dclose_f(dset_id, error)
142 
143 
144  ! ##############################
145  ! # terminate hdf5 stuff #
146  ! ##############################
147  ! close the file.
148  call h5fclose_f(file_id, error)
149  ! close fortran interface.
150  call h5close_f(error)
151 
152  return
153  end subroutine writereal1darrh5
154 
155  !!=============================================================
156 
157  subroutine writereal2darrh5(outfile,dsetname,arr)
158 
159  character(len=1024),intent(in) :: outfile
160  real(dp),intent(in) :: arr(:,:)
161  character(len=*),intent(in) :: dsetname
162 
163  ! filename length must be the same than in dummy variable
164  integer(hid_t) :: file_id ! file identifier
165  integer(hid_t) :: dset_id ! dataset identifier
166  integer :: error ! error flag
167  integer(hid_t) :: dspace_id
168  integer(hsize_t), dimension(2) :: data_dims2
169  integer :: rank
170 
171  !! copmpression stuff
172  logical :: avail
173  integer :: filter_info
174  integer :: filter_info_both
175  integer(hid_t) :: dcpl
176  integer :: chunkingfactor
177  integer(hsize_t), dimension(2) :: chunk2
178 
179 
180  chunkingfactor = 10
181 
182  !##############################
183  !# initialize hdf5 #
184  !##############################
185  ! initialize fortran interface.
186  call h5open_f(error)
187  !-------------------------------------------------------------
188  ! check if gzip compression is available and can be used for both
189  ! compression and decompression. normally we do not perform error
190  ! checking in these examples for the sake of clarity, but in this
191  ! case we will make an exception because this filter is an
192  ! optional part of the hdf5 library.
193  call h5zfilter_avail_f(h5z_filter_deflate_f, avail, error)
194  if (.not.avail) then
195  write(*,'("gzip filter not available.",/)')
196  stop
197  endif
198  call h5zget_filter_info_f(h5z_filter_deflate_f, filter_info, error)
199  filter_info_both=ior(h5z_filter_encode_enabled_f,h5z_filter_decode_enabled_f)
200  if (filter_info .ne. filter_info_both) then
201  write(*,'("gzip filter not available for encoding and decoding.",/)')
202  stop
203  endif
204 
205  !-------------------------------------------------------------
206  if (h5firsttimeread.eqv..true.) then
207  call h5fcreate_f(trim(adjustl(outfile)), h5f_acc_trunc_f,file_id,error)
208  h5firsttimeread=.false.
209  else
210  ! open an existing file using the default properties.
211  call h5fopen_f(trim(adjustl(outfile)), h5f_acc_rdwr_f, file_id, error)
212  end if
213 
214 
215  !##############################
216  !# write arr #
217  !##############################
218  rank=2
219  data_dims2=shape(arr)
220  chunk2 = data_dims2/chunkingfactor
221  call checkchunking(chunk2)
222  ! create dataspace. setting maximum size to null sets the maximum
223  ! size to be the current size.
224  call h5screate_simple_f(rank, data_dims2, dspace_id, error)
225  !-------------------------------------------------------------
226  ! create the dataset creation property list, add the gzip
227  ! compression filter and set the chunk size.
228  call h5pcreate_f(h5p_dataset_create_f, dcpl, error)
229  call h5pset_deflate_f(dcpl, 9, error)
230  call h5pset_chunk_f(dcpl, rank, chunk2, error)
231  !-------------------------------------------------------------
232  ! create the dataset with default properties.
233  call h5dcreate_f(file_id, dsetname, h5t_ieee_f64le, dspace_id, &
234  dset_id, error, dcpl)
235  !-------------------------------------------------------------
236  ! write the data to the dataset.
237  call h5dwrite_f(dset_id,h5t_ieee_f64le, arr, data_dims2, error)
238  !-------------------------------------------------------------
239  ! close and release resources.
240  call h5pclose_f(dcpl,error)
241  !-------------------------------------------------------------
242  call h5sclose_f(dspace_id, error)
243  ! close the dataset.
244  call h5dclose_f(dset_id, error)
245 
246 
247  ! ##############################
248  ! # terminate hdf5 stuff #
249  ! ##############################
250  ! close the file.
251  call h5fclose_f(file_id, error)
252  ! close fortran interface.
253  call h5close_f(error)
254 
255  return
256  end subroutine writereal2darrh5
257 
258  !!============================================================
259 
260  subroutine readreal1darrh5(inpfile,dsetname,arr)
262  implicit none
263  character(len=1024),intent(in) :: inpfile
264  real(dp),allocatable,intent(inout) :: arr(:)
265  character(len=*),intent(in) :: dsetname
266 
267  ! filename length must be the same than in dummy variable
268  integer(hid_t) :: file_id,dset_id
269  integer :: rank,error
270  integer(hid_t) :: dataspace_id
271  integer(hsize_t),allocatable :: data_dims(:),maxdims(:)
272 
273  ! Initialize FORTRAN interface.
274  CALL h5open_f(error)
275  ! Open an existing file.
276  !print*, 'Reading ',trim(inpfile)
277  CALL h5fopen_f(trim(inpfile), h5f_acc_rdonly_f, file_id, error)
278  if (error/=0) then
279  write(*,*)
280  write(*,*) "Error opening file from hdf5. "
281  write(*,*) "filename: ",trim(inpfile)
282  stop
283  endif
284 
285  ! Open an existing dataset.
286  call h5dopen_f(file_id, trim(dsetname), dset_id, error)
287  if (error/=0) then
288  write(*,*)
289  write(*,*) "Error opening file from hdf5. "
290  write(*,*) "err dsetname: ",trim(dsetname)
291  stop
292  endif
293  ! get the dataspace id
294  call h5dget_space_f(dset_id, dataspace_id, error)
295  ! get the rank of the dataset
296  call h5sget_simple_extent_ndims_f(dataspace_id, rank, error)
297  allocate(data_dims(rank),maxdims(rank))
298  ! get the dimensions of the dataset
299  call h5sget_simple_extent_dims_f(dataspace_id, data_dims, maxdims, error)
300  !print*,'rank:',rank,'maxdims:',maxdims
301  ! get the datatype
302  !call h5dget_type_f(dset_id, datatype_id, error)
303  allocate(arr(data_dims(1)))
304  print*,"Reading ",trim(dsetname), " with shape ", data_dims
305  ! read data
306  CALL h5dread_f(dset_id, h5t_ieee_f64le, arr, data_dims, error)
307  ! Close the dataset.
308  CALL h5dclose_f(dset_id, error)
309  ! close the datatype
310 
311  ! Close the file.
312  CALL h5fclose_f(file_id, error)
313  ! Close FORTRAN interface.
314  CALL h5close_f(error)
315 
316  return
317  end subroutine readreal1darrh5
318 
319  !!===============================================================
320 
321  subroutine readreal2darrh5(inpfile,dsetname,arr)
323  implicit none
324  character(len=1024),intent(in) :: inpfile
325  real(dp),allocatable,intent(inout) :: arr(:,:)
326  character(len=*),intent(in) :: dsetname
327 
328  ! filename length must be the same than in dummy variable
329  integer(hid_t) :: file_id,dset_id
330  integer :: rank,error
331  integer(hid_t) :: dataspace_id
332  integer(hsize_t),allocatable :: data_dims(:),maxdims(:)
333 
334  ! Initialize FORTRAN interface.
335  CALL h5open_f(error)
336  ! Open an existing file.
337  !print*, 'Reading ',trim(inpfile)
338  CALL h5fopen_f(trim(inpfile), h5f_acc_rdonly_f, file_id, error)
339  if (error/=0) then
340  write(*,*)
341  write(*,*) "Error opening file from hdf5. "
342  write(*,*) "filename: ",trim(inpfile)
343  stop
344  endif
345 
346  ! Open an existing dataset.
347  call h5dopen_f(file_id, trim(dsetname), dset_id, error)
348  if (error/=0) then
349  write(*,*)
350  write(*,*) "Error opening file from hdf5. "
351  write(*,*) "err dsetname: ",trim(dsetname)
352  stop
353  endif
354  ! get the dataspace id
355  call h5dget_space_f(dset_id, dataspace_id, error)
356  ! get the rank of the dataset
357  call h5sget_simple_extent_ndims_f(dataspace_id, rank, error)
358  allocate(data_dims(rank),maxdims(rank))
359  ! get the dimensions of the dataset
360  call h5sget_simple_extent_dims_f(dataspace_id, data_dims, maxdims, error)
361  !print*,'rank:',rank,'maxdims:',maxdims
362  ! get the datatype
363  !call h5dget_type_f(dset_id, datatype_id, error)
364  allocate(arr(data_dims(1),data_dims(2)))
365  print*,"Reading ",trim(dsetname), " with shape ", data_dims
366  ! read data
367  CALL h5dread_f(dset_id, h5t_ieee_f64le, arr, data_dims, error)
368  ! Close the dataset.
369  CALL h5dclose_f(dset_id, error)
370  ! close the datatype
371 
372  ! Close the file.
373  CALL h5fclose_f(file_id, error)
374  ! Close FORTRAN interface.
375  CALL h5close_f(error)
376 
377  return
378  end subroutine readreal2darrh5
379 
380  !!!===========================================================
381 
382  subroutine checkchunking(chunk)
384  use hdf5 ! this module contains all necessary modules
385  use realprec
386  implicit none
387 
388  integer(hsize_t), dimension(:), intent(inout) :: chunk
389 
390  where ( chunk < 1 ) chunk=1
391 
392  return
393  end subroutine checkchunking
394 
395  !!=============================================================
396 
397 
398 end module readwriteh5
subroutine checkchunking(chunk)
Definition: rdwrhdf5.f08:383
subroutine writereal1darrh5(outfile, dsetname, arr)
Definition: rdwrhdf5.f08:55
Module to read and write HDF5 files.
Definition: rdwrhdf5.f08:32
subroutine readreal2darrh5(inpfile, dsetname, arr)
Definition: rdwrhdf5.f08:322
subroutine writereal2darrh5(outfile, dsetname, arr)
Definition: rdwrhdf5.f08:158
This file contains the parallel OpenMPI (distributed memory) version of KronLinInv. OpenMPI and LAPACK libraries are required to be installed in the system.
logical, private h5firsttimeread
Definition: rdwrhdf5.f08:48
subroutine readreal1darrh5(inpfile, dsetname, arr)
Definition: rdwrhdf5.f08:261