Skip to content

Commit 4523aa2

Browse files
committed
%open, %close is for file. %open_group,%close_group for groups
also add destructor for files add auto-close test
1 parent 6971d8b commit 4523aa2

28 files changed

+187
-136
lines changed

API.md

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ type(hdf5_file) :: h1, h2, h3
2020
```
2121

2222
```fortran
23-
call h%initialize(filename,ierr, status,action,comp_lvl,verbose,debug)
23+
call h%open(filename,ierr, status,action,comp_lvl,verbose,debug)
2424
!! Opens hdf5 file
2525
2626
character(*), intent(in) :: filename
@@ -32,7 +32,7 @@ logical, intent(in), optional :: verbose, debug
3232
```
3333

3434
```fortran
35-
call h%finalize(ierr, close_hdf5_interface)
35+
call h%close(ierr, close_hdf5_interface)
3636
!! This must be called on each HDF5 file to flush buffers to disk
3737
!! data loss can occur if program terminates before this procedure
3838
!!

Examples.md

Lines changed: 24 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ type(hdf5_file) :: h5f
1010
* gzip compression may be applied for rank ≥ 2 arrays by setting `comp_lvl` to a value between 1 and 9.
1111
Shuffle filter is automatically applied for better compression
1212
* string attributes may be applied to any variable at time of writing or later.
13-
* h5f%initialize(..., `comp_lvl=1`) option enables GZIP compression., where comp_lvl is from 1 to 9. bigger comp_lvl gives more compression but isslower to write.
13+
* h5f%open(..., `comp_lvl=1`) option enables GZIP compression., where comp_lvl is from 1 to 9. bigger comp_lvl gives more compression but isslower to write.
1414

1515
`integer, intent(out) :: ierr` is an optional parameter. It will be non-zero if error detected.
1616
This value should be checked, particularly for write operations to avoid missing error conditions.
@@ -19,11 +19,11 @@ If `ierr` is omitted, then h5fortran will raise `error stop` if an error occurs.
1919
## Create new HDF5 file, with variable "value1"
2020

2121
```fortran
22-
call h5f%initialize('test.h5', status='new')
22+
call h5f%open('test.h5', status='new')
2323
2424
call h5f%write('/value1', 123.)
2525
26-
call h5f%finalize()
26+
call h5f%close()
2727
```
2828

2929
## create soft links to actual variable
@@ -47,11 +47,11 @@ This flushes and closes ALL HDF5 files, even those that may be invoked directly
4747
call hdf5_close()
4848
```
4949

50-
Normally, you should be calling `%finalize()` on each file to flush to disk when done using a file.
51-
If `%finalize()` or hdf5_close is not called, data loss can result.
50+
Normally, you should be calling `%close()` on each file to flush to disk when done using a file.
51+
If `%close()` or hdf5_close is not called, data loss can result.
5252

5353
```fortran
54-
call h5f%finalize()
54+
call h5f%close()
5555
```
5656

5757
At any time during the program, the `%flush()` method can be called to request the operating system to write a file to disk.
@@ -123,12 +123,12 @@ If the full path is not specified, the system temporary directory will be used i
123123
Otherwise, the current working directory + filename will be used.
124124

125125
```sh
126-
call h5%initialize('orbits.h5', status='scratch')
126+
call h5%open('orbits.h5', status='scratch')
127127

128128
...
129129

130-
call h5%finalize()
131-
!! scratch file deleted by %finalize
130+
call h5%close()
131+
!! scratch file deleted by %close
132132
```
133133

134134
## Add/append variable "value1" to existing HDF5 file "test.h5"
@@ -137,23 +137,23 @@ call h5%finalize()
137137
* if file `test.h5` does not exist, create it and add a variable to it.
138138

139139
```fortran
140-
call h5f%initialize('test.h5', status='unknown',action='rw')
140+
call h5f%open('test.h5', status='unknown',action='rw')
141141
142142
call h5f%write('/value1', 123.)
143143
144-
call h5f%finalize(ierr)
144+
call h5f%close(ierr)
145145
```
146146

147147
## Add gzip compressed 3-D array "value2" to existing HDF5 file "test.h5"
148148

149149
```fortran
150150
real :: val2(1000,1000,3) = 0.
151151
152-
call h5f%initialize('test.h5', comp_lvl=1)
152+
call h5f%open('test.h5', comp_lvl=1)
153153
154154
call h5f%write('/value2', val2)
155155
156-
call h5f%finalize(ierr)
156+
call h5f%close(ierr)
157157
```
158158

159159
chunk_size may optionally be set in the `%write()` method for 2-d to 7-d arrays.
@@ -164,7 +164,7 @@ Currently, data is written contiguous or compact if not compressed and is only c
164164

165165
## check if a variable exists
166166

167-
the logical method %exist() checks if a dataset (variable) exists in the initialized HDF5 file.
167+
the logical method %exist() checks if a dataset (variable) exists in the opened HDF5 file.
168168

169169
```fortran
170170
exists = h5f%exist("/foo")
@@ -181,7 +181,7 @@ exists = h5exist("my.h5", "/foo")
181181
`h5f%ndims` we didn't use `%rank` to avoid confusion with intrinsic "rank()"
182182

183183
```fortran
184-
call h5f%initialize('test.h5', status='old',action='r')
184+
call h5f%open('test.h5', status='old',action='r')
185185
186186
integer :: drank
187187
integer(hsize_t), allocatable :: dims(:)
@@ -192,11 +192,10 @@ call h5f%shape('/foo',dims)
192192
if (drank /= size(dims)) error stop
193193
```
194194

195-
196195
## Read scalar, 3-D array of unknown size
197196

198197
```fortran
199-
call h5f%initialize('test.h5', status='old',action='r')
198+
call h5f%open('test.h5', status='old',action='r')
200199
201200
integer(hsize_t), allocatable :: dims(:)
202201
real, allocatable :: A(:,:,:)
@@ -205,7 +204,7 @@ call h5f%shape('/foo',dims)
205204
allocate(A(dims(1), dims(2), dims(3)))
206205
call h5f%read('/foo', A)
207206
208-
call h5f%finalize()
207+
call h5f%close()
209208
```
210209

211210
## read slice (part of) a disk array
@@ -223,7 +222,7 @@ then do:
223222
```fortran
224223
real, dimension(3,5,7) :: A
225224
226-
call h5f%initialize('test.h5', status='old',action='r')
225+
call h5f%open('test.h5', status='old',action='r')
227226
228227
call h5f%read('/foo', A, istart=[5, 1, 2], iend=[7, 5, 8])
229228
```
@@ -243,18 +242,18 @@ then do:
243242
```fortran
244243
real, dimension(5,7,1) :: A
245244
246-
call h5f%initialize('test.h5', status='unknown')
245+
call h5f%open('test.h5', status='unknown')
247246
248247
call h5f%create('/foo', H5T_NATIVE_REAL, [5,7,1])
249248
call h5f%write('/foo', A, istart=[3, 4, 8], iend=[7, 10, 8])
250249
```
251250

252-
Note the h5f%create() call to initialize the disk variable.
251+
Note the h5f%create() call to open the disk variable.
253252
This step is also needed with h5py in Python or Matlab HDF5 h5create() before h5write().
254253

255254
## is dataset compact, contiguous, or chunked
256255

257-
Assume file handle h5f was already initialized, the logical status is inspected:
256+
Assume file handle h5f was already opened, the logical status is inspected:
258257

259258
```fortran
260259
is_compact = h5f%is_compact("/foo")
@@ -277,19 +276,19 @@ call h5f%chunks('/foo', chunk_size)
277276
```fortran
278277
real :: val2(1000,1000,3) = 0.
279278
280-
call h5f%initialize('test.h5')
279+
call h5f%open('test.h5')
281280
282281
call h5f%write_group('/scope/')
283282
284-
call h5f%finalize()
283+
call h5f%close()
285284
```
286285

287286
## verbose / debug
288287

289288
set options debug and /or verbose for diagnostics
290289

291290
```sh
292-
call h5f%initialize(..., verbose=.true., debug=.true.)
291+
call h5f%open(..., verbose=.true., debug=.true.)
293292
```
294293

295294
## Permissive syntax

Examples/example2.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -10,11 +10,11 @@ program example2
1010

1111
filename = 'h5fortran_example2.h5'
1212

13-
call h5f%initialize(filename, status='replace')
13+
call h5f%open(filename, status='replace')
1414
call h5f%write('/x', 123)
15-
call h5f%finalize()
15+
call h5f%close()
1616

17-
call h5f%initialize(filename, status='old', action='r')
17+
call h5f%open(filename, status='old', action='r')
1818
call h5f%read('/x', i32)
1919
if (i32 /= 123) error stop 'incorrect value read'
2020

Install.md

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -74,9 +74,9 @@ implicit none
7474
7575
type(hdf5_file) :: h5f
7676
77-
call h5f%initialize('h5fortran_example2.h5', status='replace')
77+
call h5f%open('h5fortran_example2.h5', status='replace')
7878
call h5f%write('/x', 123)
79-
call h5f%finalize()
79+
call h5f%close()
8080
8181
8282
end program

VERSION

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1 +1 @@
1-
3.8.1
1+
4.0.0

src/attributes.f90

Lines changed: 10 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -113,11 +113,11 @@
113113
type(hdf5_file) :: h
114114
integer :: ier
115115

116-
call h%initialize(filename, ier, status='old')
116+
call h%open(filename, ier, status='old')
117117

118118
call h%writeattr_char(dname, attr, attrval, ier)
119119

120-
if (ier == 0) call h%finalize(ier)
120+
if (ier == 0) call h%close(ier)
121121

122122
if (present(ierr)) ierr = ier
123123
if (check(ier, filename, dname)) then
@@ -133,11 +133,11 @@
133133
type(hdf5_file) :: h
134134
integer :: ier
135135

136-
call h%initialize(filename, ier, status='old')
136+
call h%open(filename, ier, status='old')
137137

138138
call h%writeattr_num(dname, attr, attrval, ier)
139139

140-
if (ier == 0) call h%finalize(ier)
140+
if (ier == 0) call h%close(ier)
141141

142142
if (present(ierr)) ierr = ier
143143
if (check(ier, filename, dname)) then
@@ -153,17 +153,14 @@
153153
type(hdf5_file) :: h
154154
integer :: ier
155155

156-
call h%initialize(filename, ier, status='old')
156+
call h%open(filename, ier, status='old')
157157

158158
call h%readattr_char(dname, attr, attrval, ier)
159159

160-
if (ier == 0) call h%finalize(ier)
160+
if (ier == 0) call h%close(ier)
161161

162162
if (present(ierr)) ierr = ier
163-
if (check(ier, filename, dname)) then
164-
if (present(ierr)) return
165-
error stop
166-
endif
163+
if (check(ier, filename, dname) .and. .not. present(ierr)) error stop
167164

168165
end procedure readattr_char_lt
169166

@@ -173,17 +170,14 @@
173170
type(hdf5_file) :: h
174171
integer :: ier
175172

176-
call h%initialize(filename, ier, status='old')
173+
call h%open(filename, ier, status='old')
177174

178175
call h%readattr_num(dname, attr, attrval, ier)
179176

180-
if (ier == 0) call h%finalize(ier)
177+
if (ier == 0) call h%close(ier)
181178

182179
if (present(ierr)) ierr = ier
183-
if (check(ier, filename, dname)) then
184-
if (present(ierr)) return
185-
error stop
186-
endif
180+
if (check(ier, filename, dname) .and. .not. present(ierr)) error stop
187181

188182
end procedure readattr_num_lt
189183

src/interface.f90

Lines changed: 22 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -40,9 +40,11 @@ module h5fortran
4040

4141
contains
4242
!> define methods (procedures) that don't need generic procedure
43-
procedure, public :: initialize => hdf_initialize, finalize => hdf_finalize, &
43+
procedure, public :: initialize => hdf_initialize, open => hdf_initialize, &
44+
finalize => hdf_finalize, close => hdf_finalize, &
4445
write_group, create => hdf_create, &
45-
open => hdf_open_group, close => hdf_close_group, flush => hdf_flush, &
46+
open_group => hdf_open_group, close_group => hdf_close_group, &
47+
flush => hdf_flush, &
4648
ndims => hdf_get_ndims, &
4749
shape => hdf_get_shape, layout => hdf_get_layout, chunks => hdf_get_chunk, &
4850
exist => hdf_check_exist, exists => hdf_check_exist, &
@@ -100,6 +102,9 @@ module h5fortran
100102
hdf_read_scalar, hdf_read_1d, hdf_read_2d, hdf_read_3d, hdf_read_4d, hdf_read_5d, hdf_read_6d, hdf_read_7d, &
101103
writeattr_char, writeattr_num, readattr_char, readattr_num
102104

105+
!> flush file to disk and close file if user forgets to do so.
106+
final :: destructor
107+
103108
end type hdf5_file
104109

105110

@@ -130,9 +135,9 @@ module h5fortran
130135
!> Submodules
131136

132137
interface !< pathlib.f90
133-
module logical function std_unlink(filename)
138+
module subroutine std_unlink(filename)
134139
character(*), intent(in) :: filename
135-
end function std_unlink
140+
end subroutine std_unlink
136141

137142
module logical function is_absolute_path(path)
138143
character(*), intent(in) :: path
@@ -1069,14 +1074,26 @@ subroutine hdf_finalize(self, ierr, close_hdf5_interface)
10691074
self%lid = 0
10701075

10711076
if(self%is_scratch) then
1072-
if (std_unlink(self%filename)) write(stderr,*) 'WARNING: could not delete scratch file: ' // self%filename
1077+
call std_unlink(self%filename)
10731078
endif
10741079

10751080
self%is_open = .false.
10761081

10771082
end subroutine hdf_finalize
10781083

10791084

1085+
subroutine destructor(self)
1086+
!! Close file and handle if user forgets to do so
1087+
1088+
type(hdf5_file), intent(inout) :: self
1089+
1090+
print *, "auto-closing " // self%filename
1091+
1092+
call self%close()
1093+
1094+
end subroutine destructor
1095+
1096+
10801097
subroutine hdf_flush(self, ierr)
10811098
!! request operating system flush data to disk.
10821099
!! The operating system can do this when it desires, which might be a while.

src/pathlib.in.f90

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -37,11 +37,15 @@
3737
module procedure std_unlink
3838
!! deletes file in Fortran standard manner.
3939
integer :: i, u
40+
logical :: exists
41+
42+
inquire(file=filename, exist=exists)
43+
if(.not. exists) return
4044

4145
open(newunit=u, file=filename, iostat=i)
4246
close(u, status='delete', iostat=i)
4347

44-
inquire(file=filename, exist=std_unlink)
48+
if(i/=0) write(stderr,*) "failed to delete file ", filename
4549

4650
end procedure std_unlink
4751

src/read/reader_lt.in.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -8,9 +8,9 @@
88

99
type(hdf5_file) :: h
1010

11-
call h%initialize(filename, status='old', action='r')
11+
call h%open(filename, status='old', action='r')
1212
h5exist = h%exist(dname)
13-
call h%finalize()
13+
call h%close()
1414

1515
end procedure h5exist
1616

src/read/reader_lt_template.in.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,9 @@
11
type(hdf5_file) :: h
22
integer :: ier
33

4-
call h%initialize(filename, ier, status='old', action='r')
4+
call h%open(filename, ier, status='old', action='r')
55
if (ier == 0) call h%read(dname, value, ier)
6-
if (ier == 0) call h%finalize(ier)
6+
if (ier == 0) call h%close(ier)
77

88
if (present(ierr)) ierr = ier
99
if (check(ier, filename, dname) .and. .not.present(ierr)) error stop

0 commit comments

Comments
 (0)