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! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
13PROGRAM example_ds
14
15  USE HDF5
16  USE H5LT
17  USE H5DS
18
19  IMPLICIT NONE
20
21  INTEGER, PARAMETER :: RANK      = 2 ! rank of DATA dataset
22  INTEGER, PARAMETER :: DIM_DATA  = 12
23  INTEGER, PARAMETER :: DIM1_SIZE = 3
24  INTEGER, PARAMETER :: DIM2_SIZE = 4
25  INTEGER, PARAMETER :: DIM1      = 1
26  INTEGER, PARAMETER :: DIM2      = 2
27
28  CHARACTER(LEN=6), PARAMETER :: DSET_NAME = "MYDATA"
29  CHARACTER(LEN=5), PARAMETER :: DS_1_NAME = "Xaxis"
30  CHARACTER(LEN=5), PARAMETER :: DS_2_NAME = "Yaxis"
31
32
33  INTEGER(hid_t) :: fid    ! file ID
34  INTEGER(hid_t) :: did    ! dataset ID
35  INTEGER(hid_t) :: dsid   ! DS dataset ID
36  INTEGER :: rankds = 1    ! rank of DS dataset
37  INTEGER(hsize_t), DIMENSION(1:rank) ::  dims  = (/DIM2_SIZE,DIM1_SIZE/) ! size of data dataset
38  INTEGER, DIMENSION(1:DIM_DATA) :: buf = (/1,2,3,4,5,6,7,8,9,10,11,12/)  ! data of data dataset
39  INTEGER(hsize_t), DIMENSION(1:1) ::  s1_dim  = (/DIM1_SIZE/)  ! size of DS 1 dataset
40  INTEGER(hsize_t), DIMENSION(1:1) ::  s2_dim  = (/DIM2_SIZE/)  ! size of DS 2 dataset
41  REAL, DIMENSION(1:DIM1_SIZE) :: s1_wbuf = (/10,20,30/)     ! data of DS 1 dataset
42  REAL, DIMENSION(1:DIM2_SIZE) :: s2_wbuf = (/10,20,50,100/) ! data of DS 2 dataset
43  INTEGER :: err
44  INTEGER :: num_scales
45  INTEGER(size_t) :: name_len
46  CHARACTER(LEN=80) :: name
47  INTEGER(size_t) :: label_len
48  CHARACTER(LEN=80) :: label
49  LOGICAL :: is_attached, is_scale
50
51  !
52  ! Initialize FORTRAN predefined datatypes.
53  !
54  CALL h5open_f(err)
55
56  ! create a file using default properties
57  CALL H5Fcreate_f("ex_ds1.h5",H5F_ACC_TRUNC_F, fid, err)
58
59  ! make a dataset
60  CALL H5LTmake_dataset_int_f(fid, DSET_NAME, rank,dims,buf, err)
61
62  ! make a DS dataset for the first dimension
63  CALL H5LTmake_dataset_float_f(fid,DS_1_NAME,rankds,s1_dim,s1_wbuf,err)
64
65  ! make a DS dataset for the second dimension
66  CALL H5LTmake_dataset_float_f(fid,DS_2_NAME,rankds,s2_dim,s2_wbuf,err)
67
68  !-------------------------------------------------------------------------
69  ! attach the DS_1_NAME dimension scale to DSET_NAME at dimension 1
70  ! and then detach it.
71  !-------------------------------------------------------------------------
72
73  ! get the dataset id for DSET_NAME
74  CALL H5Dopen_f(fid, DSET_NAME, did, err)
75
76  ! get the DS dataset id
77  CALL H5Dopen_f(fid, DS_1_NAME, dsid, err)
78
79  WRITE(*,'(/,5A,I0)') &
80       "Attach Dimension Scale """,TRIM(DS_1_NAME),'" to "', TRIM(DSET_NAME), '" at dimension ', DIM1
81
82  ! attach the DS_1_NAME dimension scale to DSET_NAME at dimension index 1
83  CALL H5DSattach_scale_f(did, dsid, DIM1, err)
84
85  ! Test if dimension Scale Attached
86  CALL H5DSis_attached_f(did, dsid, DIM1, is_attached, err)
87  WRITE(*,'(/,5X,3(A,1X),I0,A,L1)') 'Is',TRIM(DS_1_NAME),&
88       'attached to dimension',DIM1,' ... ',is_attached
89
90
91  ! Check to see how many Dimension Scales are attached
92
93  CALL H5DSget_num_scales_f(did, DIM1, num_scales, err)
94
95  WRITE(*,'(5X,A,I0)') 'Total number of Dimension Scales Attached ... ', num_scales
96
97  ! Detach scale
98  CALL H5DSdetach_scale_f(did, dsid, DIM1, err)
99  WRITE(*,'(/,5A,I0)') &
100       "Detach Dimension Scale """,TRIM(DS_1_NAME),'" from "', TRIM(DSET_NAME), '" at dimension ', DIM1
101
102  ! Check to see if a dimension scale is attached, should be .false.
103  CALL H5DSis_attached_f(did, dsid, DIM1, is_attached, err)
104  WRITE(*,'(/,5X,3(A,1X),I0,A,L1)') 'Is',TRIM(DS_1_NAME),&
105       'attached to dimension',DIM1,' ... ',is_attached
106
107  !-------------------------------------------------------------------------
108  ! set the DS_1_NAME dimension scale to DSET_NAME at dimension 1
109  !-------------------------------------------------------------------------
110
111  WRITE(*,'(/,5A,I0)') &
112       'Set Dimension Scale "', TRIM(DS_1_NAME), '" to "', TRIM(DSET_NAME), '" at dimension ', DIM1
113
114  CALL H5DSset_scale_f(dsid, err, "Set X")
115
116  ! Test if Dimension Scale
117
118  CALL H5DSis_scale_f(dsid, is_scale, err)
119
120  ! Get scale name
121
122  name_len = 25
123  name = ''
124  CALL H5DSget_scale_name_f(dsid, name, name_len, err)
125
126  WRITE(*,'(/,5X,A,A)') 'The Dimension Scale name is ... ', name(1:name_len)
127
128  ! Setting Dimension Scale Label
129
130  WRITE(*,'(/,A,I0)') "Setting Dimension Scale label ""X"" for dimension ", DIM1
131
132  CALL H5DSset_label_f(did, DIM1, "X", err)
133
134  label_len = 25
135  label = ''
136  CALL H5DSget_label_f(did, DIM1, label, label_len, err)
137
138  WRITE(*,'(/,5X,A,I0,2A)') 'Dimension Scale Label for dimension ', DIM1, ' is ... ', label(1:label_len)
139
140  ! close DS id
141  CALL H5Dclose_f(dsid, err)
142
143  !-------------------------------------------------------------------------
144  ! attach the DS_2_NAME dimension scale to DSET_NAME
145  !-------------------------------------------------------------------------
146
147  ! get the DS dataset id
148  CALL H5Dopen_f(fid, DS_2_NAME, dsid, err)
149
150  ! attach the DS_2_NAME dimension scale to DSET_NAME as the 2nd dimension (index 2)
151
152  WRITE(*,'(/,5A,I0)') &
153       'Set Dimension Scale "', TRIM(DS_2_NAME), '" to "', TRIM(DSET_NAME), '" at dimension ', DIM2
154
155  CALL H5DSattach_scale_f(did, dsid, DIM2, err)
156
157  CALL H5DSis_attached_f(did, dsid, DIM2, is_attached, err)
158
159  CALL H5DSset_scale_f(dsid, err, "Set Y")
160
161  ! Get scale name
162  name_len = 25
163  name = ''
164  CALL H5DSget_scale_name_f(dsid, name(1:name_len), name_len, err)
165
166  WRITE(*,'(/,5X,A,A)') 'The Dimension Scale name is ... ', name(1:name_len)
167
168
169  ! Setting Dimension Scale Label
170
171  WRITE(*,'(/,A,I0)') "Setting Dimension Scale label ""Y"" for dimension ", DIM2
172
173  CALL H5DSset_label_f(did, DIM2, "Y", err)
174
175  ! Get Label
176
177  label_len = 25
178  label = ''
179  CALL H5DSget_label_f(did, DIM2, label, label_len, err)
180
181  WRITE(*,'(/,5X,A,I0,2A,/)') 'Dimension Scale Label for dimension ', DIM2, ' is ... ', label(1:label_len)
182
183 ! close DS id
184  CALL H5Dclose_f(dsid, err)
185
186 ! close file
187  CALL H5Fclose_f(fid, err)
188
189END PROGRAM example_ds
190
191