summaryrefslogtreecommitdiffstats
path: root/HDF5Examples/FORTRAN/H5T/h5ex_t_enum_F03.F90
blob: b0ba276dfb9618b7845e10ff953aa3b4daa1023d (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
136
137
138
139
140
141
142
143
144
145
!************************************************************
!
!  This example shows how to read and write enumerated
!  datatypes to a dataset.  The program first writes
!  enumerated values to a dataset with a dataspace 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
  CHARACTER(LEN=19), PARAMETER :: filename  = "h5ex_t_enum_F03.h5"
  CHARACTER(LEN=3) , PARAMETER :: dataset   = "DS1"
  INTEGER          , PARAMETER :: dim0      = 4
  INTEGER          , PARAMETER :: dim1      = 7
  INTEGER(HID_T)               :: F_BASET  ! File base type
  INTEGER(HID_T)               :: M_BASET  ! Memory base type
  INTEGER(SIZE_T)  , PARAMETER :: NAME_BUF_SIZE = 16

! Enumerated type
  ENUM, BIND(C)
     ENUMERATOR :: SOLID = 0, LIQUID, GAS, PLASMA
  END ENUM

  INTEGER(HID_T) :: file, filetype, memtype, space, dset ! Handles
  INTEGER :: hdferr

  INTEGER(hsize_t),   DIMENSION(1:2) :: dims = (/dim0, dim1/)
  INTEGER(kind(SOLID)), DIMENSION(1:dim0, 1:dim1), TARGET :: wdata ! Write buffer
  INTEGER(kind(SOLID)), DIMENSION(:,:), ALLOCATABLE, TARGET :: rdata ! Read buffer
  INTEGER(kind(SOLID)), TARGET :: val

  CHARACTER(LEN=6), DIMENSION(1:4) :: &
       names = (/"SOLID ", "LIQUID", "GAS   ", "PLASMA"/)
  CHARACTER(LEN=NAME_BUF_SIZE) :: name
  INTEGER(HSIZE_T), DIMENSION(1:2) :: maxdims
  INTEGER(kind(SOLID)) :: i, j
  TYPE(C_PTR) :: f_ptr
  !
  ! Initialize FORTRAN interface.
  !
  CALL h5open_f(hdferr)
  !
  ! Initialize DATA.
  !
  F_BASET   = H5T_STD_I16BE      ! File base type
  M_BASET   = h5kind_to_type(kind(SOLID), H5_INTEGER_KIND) ! Memory base type
  DO i = 1, dim0
     DO j = 1, dim1 
        wdata(i,j) = MOD( (j-1)*(i-1), PLASMA+1)
     ENDDO
  ENDDO
  !
  ! Create a new file using the default properties.
  !
  CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file, hdferr)
  !
  ! Create the enumerated datatypes for file and memory.  This
  ! process is simplified if native types are used for the file,
  ! as only one type must be defined.
  !
  CALL h5tenum_create_f (F_BASET, filetype, hdferr)
  CALL h5tenum_create_f (M_BASET, memtype, hdferr)

  DO i = SOLID, PLASMA
     !
     ! Insert enumerated value for memtype.
     !
     val = i
     CALL h5tenum_insert_f(memtype, TRIM(names(i+1)), val, hdferr)
     !
     ! Insert enumerated value for filetype.  We must first convert
     ! the numerical value val to the base type of the destination.
     !
     f_ptr = C_LOC(val)
     CALL h5tconvert_f (M_BASET, F_BASET, INT(1,SIZE_T), f_ptr, hdferr)
     CALL h5tenum_insert_f(filetype, TRIM(names(i+1)), val, hdferr)
  ENDDO
  !
  ! Create dataspace.  Setting maximum size to be the current size.
  !
  CALL h5screate_simple_f(2, dims, space, hdferr)
  !
  ! Create the dataset and write the enumerated data to it.
  ! 
  CALL h5dcreate_f(file, dataset, filetype, space, dset, hdferr)
  f_ptr = C_LOC(wdata(1,1))
  CALL h5dwrite_f(dset, memtype, f_ptr, hdferr)
  !
  ! Close and release resources.
  !
  CALL h5dclose_f(dset , hdferr)
  CALL h5sclose_f(space, hdferr)
  CALL h5tclose_f(filetype, hdferr)
  CALL h5fclose_f(file , hdferr)

  !
  ! Now we begin the read section of this example.
  !
  ! Open file and dataset.
  !
  CALL h5fopen_f(filename, H5F_ACC_RDONLY_F, file, hdferr)
  CALL h5dopen_f (file, dataset, dset, hdferr)
  !
  ! Get dataspace and allocate memory for read buffer.
  !
  CALL h5dget_space_f(dset,space, hdferr)
  CALL h5sget_simple_extent_dims_f (space, dims, maxdims, hdferr)
  ALLOCATE(rdata(1:dims(1),1:dims(2)))
  !
  ! Read the data.
  !
  f_ptr = C_LOC(rdata(1,1))
  CALL h5dread_f(dset, memtype, f_ptr, hdferr)
  !
  ! Output the data to the screen.
  !
  WRITE(*, '(A,":")') dataset
  DO i=1, dims(1)
     WRITE(*,'(" [")', ADVANCE='NO')
     DO j = 1, dims(2)
        !
        ! Get the name of the enumeration member.
        !
        CALL h5tenum_nameof_f( memtype, rdata(i,j), NAME_BUF_SIZE, name, hdferr) 
        WRITE(*,'(" ", A6," ")', ADVANCE='NO') TRIM(NAME)
     ENDDO
     WRITE(*,'("]")')
  ENDDO
  !
  ! Close and release resources.
  !
  DEALLOCATE(rdata)
  CALL h5dclose_f(dset , hdferr)
  CALL h5sclose_f(space, hdferr)
  CALL h5tclose_f(memtype, hdferr)
  CALL h5fclose_f(file , hdferr)
END PROGRAM main