@@ -106,10 +106,17 @@ module h5fortran
106106procedure lt0readattr, lt1readattr
107107end interface
108108
109+ interface read_char
110+ procedure read_char0, read_char1, read_char2, read_char3, read_char4 , read_char5, read_char6, read_char7
111+ end interface
109112
110113! ! for submodules only
111114public :: HSIZE_T, H5T_NATIVE_REAL, H5T_NATIVE_DOUBLE, H5T_NATIVE_INTEGER, H5T_NATIVE_CHARACTER, H5T_STD_I64LE
112115public :: H5T_INTEGER_F, H5T_FLOAT_F, H5T_STRING_F
116+ ! ! HDF5 types for end users
117+
118+
119+ ! > Submodules
113120
114121interface ! < write.f90
115122
@@ -272,55 +279,55 @@ module subroutine h5write_scalar(self, dname, A, compact)
272279module subroutine h5write_1d (self , dname , A , dset_dims , istart , iend , stride , chunk_size , compact )
273280class(hdf5_file), intent (in ) :: self
274281character (* ), intent (in ) :: dname
275- class(* ), intent (in ) :: A(:)
282+ class(* ), intent (in ), dimension (:) :: A
276283integer , intent (in ), dimension (1 ), optional :: chunk_size, istart, iend, stride, dset_dims
277284logical , intent (in ), optional :: compact
278285end subroutine
279286
280287module subroutine h5write_2d (self , dname , A , dset_dims , istart , iend , stride , chunk_size , compact )
281288class(hdf5_file), intent (in ) :: self
282289character (* ), intent (in ) :: dname
283- class(* ), intent (in ) :: A (:,:)
290+ class(* ), intent (in ), dimension (:,:):: A
284291integer , intent (in ), dimension (2 ), optional :: chunk_size, istart, iend, stride, dset_dims
285292logical , intent (in ), optional :: compact
286293end subroutine
287294
288295module subroutine h5write_3d (self , dname , A , dset_dims , istart , iend , stride , chunk_size , compact )
289296class(hdf5_file), intent (in ) :: self
290297character (* ), intent (in ) :: dname
291- class(* ), intent (in ) :: A (:,:,:)
298+ class(* ), intent (in ), dimension (:,:,:) :: A
292299integer , intent (in ), dimension (3 ), optional :: chunk_size, istart, iend, stride, dset_dims
293300logical , intent (in ), optional :: compact
294301end subroutine
295302
296303module subroutine h5write_4d (self , dname , A , dset_dims , istart , iend , stride , chunk_size , compact )
297304class(hdf5_file), intent (in ) :: self
298305character (* ), intent (in ) :: dname
299- class(* ), intent (in ) :: A (:,:,:,:)
306+ class(* ), intent (in ), dimension (:,:,:,:) :: A
300307integer , intent (in ), dimension (4 ), optional :: chunk_size, istart, iend, stride, dset_dims
301308logical , intent (in ), optional :: compact
302309end subroutine
303310
304311module subroutine h5write_5d (self , dname , A , dset_dims , istart , iend , stride , chunk_size , compact )
305312class(hdf5_file), intent (in ) :: self
306313character (* ), intent (in ) :: dname
307- class(* ), intent (in ) :: A (:,:,:,:,:)
314+ class(* ), intent (in ), dimension (:,:,:,:,:) :: A
308315integer , intent (in ), dimension (5 ), optional :: chunk_size, istart, iend, stride, dset_dims
309316logical , intent (in ), optional :: compact
310317end subroutine
311318
312319module subroutine h5write_6d (self , dname , A , dset_dims , istart , iend , stride , chunk_size , compact )
313320class(hdf5_file), intent (in ) :: self
314321character (* ), intent (in ) :: dname
315- class(* ), intent (in ) :: A (:,:,:,:,:,:)
322+ class(* ), intent (in ), dimension (:,:,:,:,:,:) :: A
316323integer , intent (in ), dimension (6 ), optional :: chunk_size, istart, iend, stride, dset_dims
317324logical , intent (in ), optional :: compact
318325end subroutine
319326
320327module subroutine h5write_7d (self , dname , A , dset_dims , istart , iend , stride , chunk_size , compact )
321328class(hdf5_file), intent (in ) :: self
322329character (* ), intent (in ) :: dname
323- class(* ), intent (in ) :: A (:,:,:,:,:,:,:)
330+ class(* ), intent (in ), dimension (:,:,:,:,:,:,:) :: A
324331integer , intent (in ), dimension (7 ), optional :: chunk_size, istart, iend, stride, dset_dims
325332logical , intent (in ), optional :: compact
326333end subroutine
@@ -399,58 +406,113 @@ module logical function hdf_check_exist(self, dname)
399406! ! * arrays: to work correctly when actual argument is allocatable
400407! ! * scalar: to work correctly with character type
401408
409+ module subroutine read_char0 (self , obj_name , A , obj_id , mem_space_id , file_space_id )
410+ class(hdf5_file), intent (in ) :: self
411+ character (* ), intent (in ) :: obj_name
412+ character (* ), intent (inout ) :: A
413+ integer (HID_T), intent (in ) :: obj_id, mem_space_id, file_space_id
414+ end subroutine
415+
416+ module subroutine read_char1 (self , obj_name , A , obj_id , mem_space_id , file_space_id )
417+ class(hdf5_file), intent (in ) :: self
418+ character (* ), intent (in ) :: obj_name
419+ character (* ), intent (inout ), dimension (:) :: A
420+ integer (HID_T), intent (in ) :: obj_id, mem_space_id, file_space_id
421+ end subroutine
422+
423+ module subroutine read_char2 (self , obj_name , A , obj_id , mem_space_id , file_space_id )
424+ class(hdf5_file), intent (in ) :: self
425+ character (* ), intent (in ) :: obj_name
426+ character (* ), intent (inout ), dimension (:,:) :: A
427+ integer (HID_T), intent (in ) :: obj_id, mem_space_id, file_space_id
428+ end subroutine
429+
430+ module subroutine read_char3 (self , obj_name , A , obj_id , mem_space_id , file_space_id )
431+ class(hdf5_file), intent (in ) :: self
432+ character (* ), intent (in ) :: obj_name
433+ character (* ), intent (inout ), dimension (:,:,:) :: A
434+ integer (HID_T), intent (in ) :: obj_id, mem_space_id, file_space_id
435+ end subroutine
436+
437+ module subroutine read_char4 (self , obj_name , A , obj_id , mem_space_id , file_space_id )
438+ class(hdf5_file), intent (in ) :: self
439+ character (* ), intent (in ) :: obj_name
440+ character (* ), intent (inout ), dimension (:,:,:,:) :: A
441+ integer (HID_T), intent (in ) :: obj_id, mem_space_id, file_space_id
442+ end subroutine
443+
444+ module subroutine read_char5 (self , obj_name , A , obj_id , mem_space_id , file_space_id )
445+ class(hdf5_file), intent (in ) :: self
446+ character (* ), intent (in ) :: obj_name
447+ character (* ), intent (inout ), dimension (:,:,:,:,:) :: A
448+ integer (HID_T), intent (in ) :: obj_id, mem_space_id, file_space_id
449+ end subroutine
450+
451+ module subroutine read_char6 (self , obj_name , A , obj_id , mem_space_id , file_space_id )
452+ class(hdf5_file), intent (in ) :: self
453+ character (* ), intent (in ) :: obj_name
454+ character (* ), intent (inout ), dimension (:,:,:,:,:,:) :: A
455+ integer (HID_T), intent (in ) :: obj_id, mem_space_id, file_space_id
456+ end subroutine
457+
458+ module subroutine read_char7 (self , obj_name , A , obj_id , mem_space_id , file_space_id )
459+ class(hdf5_file), intent (in ) :: self
460+ character (* ), intent (in ) :: obj_name
461+ character (* ), intent (inout ), dimension (:,:,:,:,:,:,:) :: A
462+ integer (HID_T), intent (in ) :: obj_id, mem_space_id, file_space_id
463+ end subroutine
402464module subroutine h5read_scalar (self , dname , A )
403465class(hdf5_file), intent (in ) :: self
404466character (* ), intent (in ) :: dname
405- class(* ), intent (inout ) :: A
467+ class(* ), intent (inout ) :: A
406468end subroutine
407469
408470module subroutine h5read_1d (self , dname , A , istart , iend , stride )
409471class(hdf5_file), intent (in ) :: self
410472character (* ), intent (in ) :: dname
411- class(* ), intent (inout ) :: A(:)
473+ class(* ), intent (inout ), dimension (:) :: A
412474integer , intent (in ), dimension (1 ), optional :: istart, iend, stride
413475end subroutine
414476
415477module subroutine h5read_2d (self , dname , A , istart , iend , stride )
416478class(hdf5_file), intent (in ) :: self
417479character (* ), intent (in ) :: dname
418- class(* ), intent (inout ) :: A (:,:)
480+ class(* ), intent (inout ), dimension (:,:) :: A
419481integer , intent (in ), dimension (2 ), optional :: istart, iend, stride
420482end subroutine
421483
422484module subroutine h5read_3d (self , dname , A , istart , iend , stride )
423485class(hdf5_file), intent (in ) :: self
424486character (* ), intent (in ) :: dname
425- class(* ), intent (inout ) :: A (:,:,:)
487+ class(* ), intent (inout ), dimension (:,:,:) :: A
426488integer , intent (in ), dimension (3 ), optional :: istart, iend, stride
427489end subroutine
428490
429491module subroutine h5read_4d (self , dname , A , istart , iend , stride )
430492class(hdf5_file), intent (in ) :: self
431493character (* ), intent (in ) :: dname
432- class(* ), intent (inout ) :: A (:,:,:,:)
494+ class(* ), intent (inout ), dimension (:,:,:,:) :: A
433495integer , intent (in ), dimension (4 ), optional :: istart, iend, stride
434496end subroutine
435497
436498module subroutine h5read_5d (self , dname , A , istart , iend , stride )
437499class(hdf5_file), intent (in ) :: self
438500character (* ), intent (in ) :: dname
439- class(* ), intent (inout ) :: A (:,:,:,:,:)
501+ class(* ), intent (inout ), dimension (:,:,:,:,:) :: A
440502integer , intent (in ), dimension (5 ), optional :: istart, iend, stride
441503end subroutine
442504
443505module subroutine h5read_6d (self , dname , A , istart , iend , stride )
444506class(hdf5_file), intent (in ) :: self
445507character (* ), intent (in ) :: dname
446- class(* ), intent (inout ) :: A (:,:,:,:,:,:)
508+ class(* ), intent (inout ), dimension (:,:,:,:,:,:) :: A
447509integer , intent (in ), dimension (6 ), optional :: istart, iend, stride
448510end subroutine
449511
450512module subroutine h5read_7d (self , dname , A , istart , iend , stride )
451513class(hdf5_file), intent (in ) :: self
452514character (* ), intent (in ) :: dname
453- class(* ), intent (inout ) :: A (:,:,:,:,:,:,:)
515+ class(* ), intent (inout ), dimension (:,:,:,:,:,:,:) :: A
454516integer , intent (in ), dimension (7 ), optional :: istart, iend, stride
455517end subroutine
456518
0 commit comments