summaryrefslogtreecommitdiffstats
path: root/hl/fortran/examples/ex_ds1.f90
diff options
context:
space:
mode:
Diffstat (limited to 'hl/fortran/examples/ex_ds1.f90')
-rw-r--r--hl/fortran/examples/ex_ds1.f9068
1 files changed, 33 insertions, 35 deletions
diff --git a/hl/fortran/examples/ex_ds1.f90 b/hl/fortran/examples/ex_ds1.f90
index 377a641..b34467e 100644
--- a/hl/fortran/examples/ex_ds1.f90
+++ b/hl/fortran/examples/ex_ds1.f90
@@ -1,16 +1,13 @@
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
-! * Copyright by The HDF Group. *
-! * Copyright by the Board of Trustees of the University of Illinois. *
-! * All rights reserved. *
-! * *
-! * This file is part of HDF5. The full HDF5 copyright notice, including *
-! * terms governing use, modification, and redistribution, is contained in *
-! * the files COPYING and Copyright.html. COPYING can be found at the root *
-! * of the source code distribution tree; Copyright.html can be found at the *
-! * root level of an installed copy of the electronic HDF5 document set and *
-! * is linked from the top-level documents page. It can also be found at *
-! * http://hdfgroup.org/HDF5/doc/Copyright.html. If you do not have *
-! * access to either file, you may request a copy from help@hdfgroup.org. *
+! Copyright by The HDF Group. *
+! All rights reserved. *
+! *
+! 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://www.hdfgroup.org/licenses. *
+! If you do not have access to either file, you may request a copy from *
+! help@hdfgroup.org. *
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
PROGRAM example_ds
@@ -20,7 +17,7 @@ PROGRAM example_ds
IMPLICIT NONE
- INTEGER, PARAMETER :: RANK = 2 ! rank of DATA dataset
+ INTEGER, PARAMETER :: RANK = 2 ! rank of DATA dataset
INTEGER, PARAMETER :: DIM_DATA = 12
INTEGER, PARAMETER :: DIM1_SIZE = 3
INTEGER, PARAMETER :: DIM2_SIZE = 4
@@ -35,13 +32,13 @@ PROGRAM example_ds
INTEGER(hid_t) :: fid ! file ID
INTEGER(hid_t) :: did ! dataset ID
INTEGER(hid_t) :: dsid ! DS dataset ID
- INTEGER :: rankds = 1 ! rank of DS dataset
- INTEGER(hsize_t), DIMENSION(1:rank) :: dims = (/DIM2_SIZE,DIM1_SIZE/) ! size of data dataset
- INTEGER, DIMENSION(1:DIM_DATA) :: buf = (/1,2,3,4,5,6,7,8,9,10,11,12/) ! data of data dataset
- INTEGER(hsize_t), DIMENSION(1:1) :: s1_dim = (/DIM1_SIZE/) ! size of DS 1 dataset
- INTEGER(hsize_t), DIMENSION(1:1) :: s2_dim = (/DIM2_SIZE/) ! size of DS 2 dataset
- REAL, DIMENSION(1:DIM1_SIZE) :: s1_wbuf = (/10,20,30/) ! data of DS 1 dataset
- REAL, DIMENSION(1:DIM2_SIZE) :: s2_wbuf = (/10,20,50,100/) ! data of DS 2 dataset
+ INTEGER :: rankds = 1 ! rank of DS dataset
+ INTEGER(hsize_t), DIMENSION(1:rank) :: dims = (/DIM2_SIZE,DIM1_SIZE/) ! size of data dataset
+ INTEGER, DIMENSION(1:DIM_DATA) :: buf = (/1,2,3,4,5,6,7,8,9,10,11,12/) ! data of data dataset
+ INTEGER(hsize_t), DIMENSION(1:1) :: s1_dim = (/DIM1_SIZE/) ! size of DS 1 dataset
+ INTEGER(hsize_t), DIMENSION(1:1) :: s2_dim = (/DIM2_SIZE/) ! size of DS 2 dataset
+ REAL, DIMENSION(1:DIM1_SIZE) :: s1_wbuf = (/10,20,30/) ! data of DS 1 dataset
+ REAL, DIMENSION(1:DIM2_SIZE) :: s2_wbuf = (/10,20,50,100/) ! data of DS 2 dataset
INTEGER :: err
INTEGER :: num_scales
INTEGER(size_t) :: name_len
@@ -58,7 +55,7 @@ PROGRAM example_ds
! create a file using default properties
CALL H5Fcreate_f("ex_ds1.h5",H5F_ACC_TRUNC_F, fid, err)
- ! make a dataset
+ ! make a dataset
CALL H5LTmake_dataset_int_f(fid, DSET_NAME, rank,dims,buf, err)
! make a DS dataset for the first dimension
@@ -71,7 +68,7 @@ PROGRAM example_ds
! attach the DS_1_NAME dimension scale to DSET_NAME at dimension 1
! and then detach it.
!-------------------------------------------------------------------------
-
+
! get the dataset id for DSET_NAME
CALL H5Dopen_f(fid, DSET_NAME, did, err)
@@ -84,11 +81,11 @@ PROGRAM example_ds
! attach the DS_1_NAME dimension scale to DSET_NAME at dimension index 1
CALL H5DSattach_scale_f(did, dsid, DIM1, err)
- ! Test if dimension Scale Attached
+ ! Test if dimension Scale Attached
CALL H5DSis_attached_f(did, dsid, DIM1, is_attached, err)
- WRITE(*,'(/,5X 3(A,1X),I0,A,L1)') 'Is',TRIM(DS_1_NAME),&
+ WRITE(*,'(/,5X,3(A,1X),I0,A,L1)') 'Is',TRIM(DS_1_NAME),&
'attached to dimension',DIM1,' ... ',is_attached
-
+
! Check to see how many Dimension Scales are attached
@@ -105,11 +102,11 @@ PROGRAM example_ds
CALL H5DSis_attached_f(did, dsid, DIM1, is_attached, err)
WRITE(*,'(/,5X,3(A,1X),I0,A,L1)') 'Is',TRIM(DS_1_NAME),&
'attached to dimension',DIM1,' ... ',is_attached
-
+
!-------------------------------------------------------------------------
! set the DS_1_NAME dimension scale to DSET_NAME at dimension 1
!-------------------------------------------------------------------------
-
+
WRITE(*,'(/,5A,I0)') &
'Set Dimension Scale "', TRIM(DS_1_NAME), '" to "', TRIM(DSET_NAME), '" at dimension ', DIM1
@@ -125,11 +122,11 @@ PROGRAM example_ds
name = ''
CALL H5DSget_scale_name_f(dsid, name, name_len, err)
- WRITE(*,'(/,5X,A,A)') 'The Dimension Scale name is ... ', name(1:name_len)
+ WRITE(*,'(/,5X,A,A)') 'The Dimension Scale name is ... ', name(1:name_len)
! Setting Dimension Scale Label
- WRITE(*,'(/,A,I0)') "Setting Dimension Scale label ""X"" for dimension ", DIM1
+ WRITE(*,'(/,A,I0)') "Setting Dimension Scale label ""X"" for dimension ", DIM1
CALL H5DSset_label_f(did, DIM1, "X", err)
@@ -141,11 +138,11 @@ PROGRAM example_ds
! close DS id
CALL H5Dclose_f(dsid, err)
-
+
!-------------------------------------------------------------------------
! attach the DS_2_NAME dimension scale to DSET_NAME
!-------------------------------------------------------------------------
-
+
! get the DS dataset id
CALL H5Dopen_f(fid, DS_2_NAME, dsid, err)
@@ -165,7 +162,7 @@ PROGRAM example_ds
name = ''
CALL H5DSget_scale_name_f(dsid, name(1:name_len), name_len, err)
- WRITE(*,'(/,5X,A,A)') 'The Dimension Scale name is ... ', name(1:name_len)
+ WRITE(*,'(/,5X,A,A)') 'The Dimension Scale name is ... ', name(1:name_len)
! Setting Dimension Scale Label
@@ -179,13 +176,14 @@ PROGRAM example_ds
label_len = 25
label = ''
CALL H5DSget_label_f(did, DIM2, label, label_len, err)
-
+
WRITE(*,'(/,5X,A,I0,2A,/)') 'Dimension Scale Label for dimension ', DIM2, ' is ... ', label(1:label_len)
- ! close DS id
+ ! close DS ids
CALL H5Dclose_f(dsid, err)
+ CALL H5Dclose_f(did, err)
- ! close file
+ ! close file
CALL H5Fclose_f(fid, err)
END PROGRAM example_ds