summaryrefslogtreecommitdiffstats
path: root/HDF5Examples/FORTRAN/H5D/h5ex_d_rdwr_kind_F03.F90
blob: e13a854edae9bf8ea37fad5aabfe8eb4022ac457 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
! ************************************************************
!
!  This example shows how to read and write real and integer
!  data where the precision is set by SELECTED_REAL_KIND and
!  SELECTED_INT_KIND.
!  
!  The program first writes integers
!  and reals to a dataset with dataspace dimensions of DIM0xDIM1, 
!  then closes the file.  Next, it reopens the file, reads back 
!  the data, and outputs it to the screen.
!
!  This file is intended for use with HDF5 Library version 1.8
!  with --enable-fortran2003
!
! ************************************************************

PROGRAM main

  USE HDF5
  USE ISO_C_BINDING

  IMPLICIT NONE

! Set the precision for the real KINDs

  INTEGER, PARAMETER :: sp = KIND(1.0),              &
       dp = SELECTED_REAL_KIND(2*PRECISION(1.0_sp)), &
       qp = SELECTED_REAL_KIND(2*PRECISION(1.0_dp))

  !                                                        -10      10
  ! Find the INTEGER KIND that can represent values from 10   to 10
  !
  INTEGER, PARAMETER :: ip = SELECTED_INT_KIND(10)
  !                                           
  CHARACTER(LEN=23), PARAMETER :: filename = "h5ex_d_rdwr_kind_F03.h5"
  CHARACTER(LEN=4) , PARAMETER :: dataset_r = "DS_R"
  CHARACTER(LEN=4) , PARAMETER :: dataset_i = "DS_I"
  INTEGER          , PARAMETER :: dim0     = 4
  INTEGER          , PARAMETER :: dim1     = 7

  INTEGER :: hdferr
  INTEGER(HID_T) :: file, space, dset_r, dset_i ! Handles
  INTEGER(HSIZE_T), DIMENSION(1:2)           :: dims = (/dim0, dim1/) ! Size read/write buffer
  INTEGER(KIND=ip), DIMENSION(1:dim0,1:dim1), TARGET :: wdata_i, rdata_i  ! Write/Read buffers
  REAL(kIND=dp), DIMENSION(1:dim0,1:dim1), TARGET    :: wdata_r, rdata_r  ! Write/Read buffers
  INTEGER :: i, j
  TYPE(C_PTR) :: f_ptr

  INTEGER(HID_T) :: h5_kind_type_r, h5_kind_type_i ! HDF type corresponding to the specified KIND

  !
  ! Initialize FORTRAN interface.
  !
  CALL h5open_f(hdferr)
  !
  ! Initialize data.
  !
  DO i = 1, dim0
     DO j = 1, dim1
        wdata_i(i,j) = (i-1)*(j-1)-(j-1)
        wdata_r(i,j) = (REAL(i,kind=ip)-1.0_ip)*(REAL(j,kind=ip)-1.0_ip)-(REAL(j,kind=ip)-1.0_ip)
     ENDDO
  ENDDO
  !
  ! Find the HDF type corresponding to the specified KIND
  !
  h5_kind_type_r = h5kind_to_type(dp,H5_REAL_KIND)
  h5_kind_type_i = h5kind_to_type(ip,H5_INTEGER_KIND)
  !
  ! Create a new file using the default properties.
  !
  CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file, hdferr)
  !
  ! Create dataspace.  Setting size to be the current size.
  !
  CALL h5screate_simple_f(2, dims, space, hdferr)
  !
  ! Create the dataset. 
  !
  CALL h5dcreate_f(file, dataset_i, h5_kind_type_i, space, dset_i, hdferr)
  CALL h5dcreate_f(file, dataset_r, h5_kind_type_r, space, dset_r, hdferr)
  !
  ! Write the data to the dataset.
  !
  f_ptr = C_LOC(wdata_i(1,1))
  CALL h5dwrite_f(dset_i, h5_kind_type_i, f_ptr, hdferr)
  f_ptr = C_LOC(wdata_r(1,1))
  CALL h5dwrite_f(dset_r, h5_kind_type_r, f_ptr, hdferr)
  !
  ! Close and release resources.
  !
  CALL h5dclose_f(dset_r, hdferr)
  CALL h5dclose_f(dset_i, hdferr)
  CALL h5sclose_f(space, hdferr)
  CALL h5fclose_f(file , hdferr)
  !
  ! Now we begin the read section of this example.
  !
  !
  ! Open file and dataset using the default properties.
  !
  CALL h5fopen_f(filename, H5F_ACC_RDONLY_F, file, hdferr)
  CALL h5dopen_f(file, dataset_i, dset_i, hdferr)
  CALL h5dopen_f(file, dataset_r, dset_r, hdferr)
  !
  ! Read the data using the default properties.
  !
  f_ptr = C_LOC(rdata_i(1,1))
  CALL h5dread_f(dset_i, h5_kind_type_i, f_ptr, hdferr)
  f_ptr = C_LOC(rdata_r(1,1))
  CALL h5dread_f(dset_r, h5_kind_type_r, f_ptr, hdferr)
  !
  ! Output the data to the screen.
  !
  WRITE(*, '(/,A,":")') dataset_i
  DO i=1, dim0
     WRITE(*,'(" [")', ADVANCE='NO')
     WRITE(*,'(80i3)', ADVANCE='NO') rdata_i(i,:)
     WRITE(*,'(" ]")')
  ENDDO
  WRITE(*, '(/,A,":")') dataset_r
  DO i=1, dim0
     WRITE(*,'(" [")', ADVANCE='NO')
     WRITE(*,'(80f7.3)', ADVANCE='NO') rdata_r(i,:)
     WRITE(*,'(" ]")')
  ENDDO
  WRITE(*, '(/)')
  !
  ! Close and release resources.
  !
  CALL h5dclose_f(dset_i , hdferr)
  CALL h5dclose_f(dset_r , hdferr)
  CALL h5fclose_f(file , hdferr)

END PROGRAM main