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!
15!    This program shows how to create, store and dereference references
16!    to the dataset regions.
17!    Program creates a file and writes two dimensional integer dataset
18!    to it. Then program creates and stores references to the hyperslab
19!    and 3 points selected in the integer dataset, in the second dataset.
20!    Program reopens the second dataset, reads and dereferences region
21!    references, and then reads and displays selected data from the
22!    integer dataset.
23!
24     PROGRAM REG_REFERENCE
25
26        USE HDF5 ! This module contains all necessary modules
27
28     IMPLICIT NONE
29     CHARACTER(LEN=10), PARAMETER :: filename = "FORTRAN.h5"
30     CHARACTER(LEN=6), PARAMETER :: dsetnamev = "MATRIX"
31     CHARACTER(LEN=17), PARAMETER :: dsetnamer = "REGION_REFERENCES"
32
33     INTEGER(HID_T) :: file_id       ! File identifier
34     INTEGER(HID_T) :: space_id      ! Dataspace identifier
35     INTEGER(HID_T) :: spacer_id     ! Dataspace identifier
36     INTEGER(HID_T) :: dsetv_id      ! Dataset identifier
37     INTEGER(HID_T) :: dsetr_id      ! Dataset identifier
38     INTEGER     ::   error
39     TYPE(hdset_reg_ref_t_f) , DIMENSION(2) :: ref     ! Buffers to store references
40     TYPE(hdset_reg_ref_t_f) , DIMENSION(2) :: ref_out !
41     INTEGER(HSIZE_T), DIMENSION(2) :: dims = (/2,9/)  ! Datasets dimensions
42     INTEGER(HSIZE_T), DIMENSION(1) :: dimsr = (/2/)   !
43     INTEGER(HSIZE_T), DIMENSION(2) :: start
44     INTEGER(HSIZE_T), DIMENSION(2) :: count
45     INTEGER :: rankr = 1
46     INTEGER :: rank = 2
47     INTEGER , DIMENSION(2,9) ::  data
48     INTEGER , DIMENSION(2,9) ::  data_out = 0
49     INTEGER(HSIZE_T) , DIMENSION(2,3) :: coord
50     INTEGER(SIZE_T) ::num_points = 3  ! Number of selected points
51     INTEGER :: i, j
52     INTEGER(HSIZE_T), DIMENSION(1) :: ref_size
53     INTEGER(HSIZE_T), DIMENSION(2) :: data_dims
54     coord = reshape((/1,1,2,7,1,9/), (/2,3/))   ! Coordinates of selected points
55     data = reshape ((/1,1,1,2,2,2,3,3,3,4,4,4,5,5,5,6,6,6/), (/2,9/))
56     !
57     !  Initialize FORTRAN interface.
58     !
59     CALL h5open_f(error)
60     !
61     !  Create a new file.
62     !
63     CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, error)
64                                         ! Default file access and file creation
65                                         ! properties are used.
66     !
67     ! Create  dataspaces:
68     !
69     ! for dataset with references to dataset regions
70     !
71     CALL h5screate_simple_f(rankr, dimsr, spacer_id, error)
72     !
73     ! for integer dataset
74     !
75     CALL h5screate_simple_f(rank, dims, space_id, error)
76     !
77     ! Create  and write datasets:
78     !
79     ! Integer dataset
80     !
81     CALL h5dcreate_f(file_id, dsetnamev, H5T_NATIVE_INTEGER, space_id, &
82                      dsetv_id, error)
83     data_dims(1) = 2
84     data_dims(2) = 9
85     CALL h5dwrite_f(dsetv_id, H5T_NATIVE_INTEGER, data, data_dims, error)
86     CALL h5dclose_f(dsetv_id, error)
87     !
88     ! Dataset with references
89     !
90     CALL h5dcreate_f(file_id, dsetnamer, H5T_STD_REF_DSETREG, spacer_id, &
91                      dsetr_id, error)
92     !
93     ! Create a reference to the hyperslab selection.
94     !
95     start(1) = 0
96     start(2) = 3
97     count(1) = 2
98     count(2) = 3
99     CALL h5sselect_hyperslab_f(space_id, H5S_SELECT_SET_F, &
100                                start, count, error)
101     CALL h5rcreate_f(file_id, dsetnamev, space_id, ref(1), error)
102     !
103     ! Create a reference to elements selection.
104     !
105     CALL h5sselect_none_f(space_id, error)
106     CALL h5sselect_elements_f(space_id, H5S_SELECT_SET_F, rank, num_points,&
107                               coord, error)
108     CALL h5rcreate_f(file_id, dsetnamev, space_id, ref(2), error)
109     !
110     ! Write dataset with the references.
111     !
112     ref_size(1) = size(ref)
113     CALL h5dwrite_f(dsetr_id, H5T_STD_REF_DSETREG, ref, ref_size, error)
114     !
115     ! Close all objects.
116     !
117     CALL h5sclose_f(space_id, error)
118     CALL h5sclose_f(spacer_id, error)
119     CALL h5dclose_f(dsetr_id, error)
120     CALL h5fclose_f(file_id, error)
121     !
122     ! Reopen the file to test selections.
123     !
124     CALL h5fopen_f (filename, H5F_ACC_RDWR_F, file_id, error)
125     CALL h5dopen_f(file_id, dsetnamer, dsetr_id, error)
126     !
127     ! Read references to the dataset regions.
128     !
129     ref_size(1) = size(ref_out)
130     CALL h5dread_f(dsetr_id, H5T_STD_REF_DSETREG, ref_out, ref_size, error)
131     !
132     ! Dereference the first reference.
133     !
134     CALL H5rdereference_f(dsetr_id, ref_out(1), dsetv_id, error)
135     CALL H5rget_region_f(dsetr_id, ref_out(1), space_id, error)
136     !
137     ! Read selected data from the dataset.
138     !
139     CALL h5dread_f(dsetv_id, H5T_NATIVE_INTEGER, data_out, data_dims, error, &
140                     mem_space_id = space_id, file_space_id = space_id)
141          write(*,*) "Hypeslab selection"
142          write(*,*)
143          do i = 1,2
144          write(*,*) (data_out (i,j), j = 1,9)
145          enddo
146          write(*,*)
147     CALL h5sclose_f(space_id, error)
148     CALL h5dclose_f(dsetv_id, error)
149     data_out = 0
150     !
151     ! Dereference the second reference.
152     !
153     CALL H5rdereference_f(dsetr_id, ref_out(2), dsetv_id, error)
154     CALL H5rget_region_f(dsetr_id, ref_out(2), space_id, error)
155     !
156     ! Read selected data from the dataset.
157     !
158     CALL h5dread_f(dsetv_id, H5T_NATIVE_INTEGER, data_out, data_dims, error, &
159                     mem_space_id = space_id, file_space_id = space_id)
160          write(*,*) "Point selection"
161          write(*,*)
162          do i = 1,2
163          write(*,*) (data_out (i,j), j = 1,9)
164          enddo
165     !
166     ! Close all objects
167     !
168     CALL h5sclose_f(space_id, error)
169     CALL h5dclose_f(dsetv_id, error)
170     CALL h5dclose_f(dsetr_id, error)
171     !
172     ! Close FORTRAN interface.
173     !
174     CALL h5close_f(error)
175
176     END PROGRAM REG_REFERENCE
177
178
179